From 08300bdab74e0260399caf1d1bfd9d002a880da9 Mon Sep 17 00:00:00 2001 From: Teun van den Brand Date: Fri, 5 Apr 2024 15:47:07 +0200 Subject: [PATCH 01/41] draft new `geom` element in themes --- R/theme-defaults.R | 3 +++ R/theme-elements.R | 10 ++++++++++ R/theme.R | 1 + 3 files changed, 14 insertions(+) diff --git a/R/theme-defaults.R b/R/theme-defaults.R index 05260557e9..a16d3fef21 100644 --- a/R/theme-defaults.R +++ b/R/theme-defaults.R @@ -134,6 +134,9 @@ theme_grey <- function(base_size = 11, base_family = "", margin = margin(), debug = FALSE ), + geom = element_geom(ink = "black", paper = "white", accent = "#3366FF", + thin = base_line_size, thick = base_line_size * 2), + axis.line = element_blank(), axis.line.x = NULL, axis.line.y = NULL, diff --git a/R/theme-elements.R b/R/theme-elements.R index b8e83c75e4..e29842b734 100644 --- a/R/theme-elements.R +++ b/R/theme-elements.R @@ -144,6 +144,15 @@ element_text <- function(family = NULL, face = NULL, colour = NULL, ) } +element_geom <- function( + ink = NULL, paper = NULL, accent = NULL, thin = NULL, thick = NULL) { + + structure( + list(ink = ink, paper = paper, accent = accent, thin = thin, thick = thick), + class = c("element_geom", "element") + ) +} + #' @export print.element <- function(x, ...) utils::str(x) @@ -426,6 +435,7 @@ el_def <- function(class = NULL, inherit = NULL, description = NULL) { line = el_def("element_line"), rect = el_def("element_rect"), text = el_def("element_text"), + geom = el_def("element_geom"), title = el_def("element_text", "text"), axis.line = el_def("element_line", "line"), axis.text = el_def("element_text", "text"), diff --git a/R/theme.R b/R/theme.R index 3611af323e..14e346c013 100644 --- a/R/theme.R +++ b/R/theme.R @@ -311,6 +311,7 @@ theme <- function(..., rect, text, title, + geom, aspect.ratio, axis.title, axis.title.x, From 8c24ab954995a0348b31dccf61e857bdf0260fbb Mon Sep 17 00:00:00 2001 From: Teun van den Brand Date: Fri, 5 Apr 2024 15:51:07 +0200 Subject: [PATCH 02/41] plumbing for providing theme to Geom$use_defaults() --- R/geom-.R | 2 +- R/layer.R | 4 ++-- R/plot-build.R | 8 ++++++-- 3 files changed, 9 insertions(+), 5 deletions(-) diff --git a/R/geom-.R b/R/geom-.R index c1967a89c1..a6c4fb17c0 100644 --- a/R/geom-.R +++ b/R/geom-.R @@ -114,7 +114,7 @@ Geom <- ggproto("Geom", setup_data = function(data, params) data, # Combine data with defaults and set aesthetics from parameters - use_defaults = function(self, data, params = list(), modifiers = aes()) { + use_defaults = function(self, data, params = list(), modifiers = aes(), theme = NULL) { default_aes <- self$default_aes # Inherit size as linewidth if no linewidth aesthetic and param exist diff --git a/R/layer.R b/R/layer.R index 7df5119aae..5fb1a169b5 100644 --- a/R/layer.R +++ b/R/layer.R @@ -437,14 +437,14 @@ Layer <- ggproto("Layer", NULL, self$position$compute_layer(data, params, layout) }, - compute_geom_2 = function(self, data) { + compute_geom_2 = function(self, data, theme) { # Combine aesthetics, defaults, & params if (empty(data)) return(data) aesthetics <- self$computed_mapping modifiers <- aesthetics[is_scaled_aes(aesthetics) | is_staged_aes(aesthetics)] - self$geom$use_defaults(data, self$aes_params, modifiers) + self$geom$use_defaults(data, self$aes_params, modifiers, theme = theme) }, finish_statistics = function(self, data) { diff --git a/R/plot-build.R b/R/plot-build.R index d53f16ba85..82de6f2164 100644 --- a/R/plot-build.R +++ b/R/plot-build.R @@ -106,7 +106,11 @@ ggplot_build.ggplot <- function(plot) { data <- .expose_data(data) # Fill in defaults etc. - data <- by_layer(function(l, d) l$compute_geom_2(d), layers, data, "setting up geom aesthetics") + plot$theme <- plot_theme(plot) + data <- by_layer( + function(l, d) l$compute_geom_2(d, theme = plot$theme), + layers, data, "setting up geom aesthetics" + ) # Let layer stat have a final say before rendering data <- by_layer(function(l, d) l$finish_statistics(d), layers, data, "finishing layer stat") @@ -181,7 +185,7 @@ ggplot_gtable.ggplot_built <- function(data) { plot <- data$plot layout <- data$layout data <- data$data - theme <- plot_theme(plot) + theme <- plot$theme geom_grobs <- by_layer(function(l, d) l$draw_geom(d, layout), plot$layers, data, "converting geom to grob") From 60af7a3cfd2e8589af87f70614157b74471298c2 Mon Sep 17 00:00:00 2001 From: Teun van den Brand Date: Fri, 5 Apr 2024 15:56:44 +0200 Subject: [PATCH 03/41] make `from_theme()` as eval helper --- R/aes-evaluation.R | 14 ++++++++++++++ 1 file changed, 14 insertions(+) diff --git a/R/aes-evaluation.R b/R/aes-evaluation.R index e128fd2c15..69dc8ca4a0 100644 --- a/R/aes-evaluation.R +++ b/R/aes-evaluation.R @@ -192,6 +192,14 @@ stat <- function(x) { after_scale <- function(x) { x } + +#' @rdname aes_eval +#' @export +from_theme <- function(x) { + # TODO: This is just a placeholder + x +} + #' @rdname aes_eval #' @export stage <- function(start = NULL, after_stat = NULL, after_scale = NULL) { @@ -221,6 +229,9 @@ is_scaled_aes <- function(aesthetics) { is_staged_aes <- function(aesthetics) { vapply(aesthetics, is_staged, logical(1), USE.NAMES = FALSE) } +is_themed_aes <- function(aesthetics) { + vapply(aesthetics, is_themed, logical(1), USE.NAMES = FALSE) +} is_calculated <- function(x, warn = FALSE) { if (is_call(get_expr(x), "after_stat")) { return(TRUE) @@ -263,6 +274,9 @@ is_scaled <- function(x) { is_staged <- function(x) { is_call(get_expr(x), "stage") } +is_themed <- function(x) { + is_call(get_expr(x), "from_theme") +} # Strip dots from expressions strip_dots <- function(expr, env, strip_pronoun = FALSE) { From f551c8b7ac4555e1b6b578742cc701debb0c154a Mon Sep 17 00:00:00 2001 From: Teun van den Brand Date: Fri, 5 Apr 2024 16:05:15 +0200 Subject: [PATCH 04/41] Evaluate default aesthetics from theme --- R/geom-.R | 15 ++++++++++++++- 1 file changed, 14 insertions(+), 1 deletion(-) diff --git a/R/geom-.R b/R/geom-.R index a6c4fb17c0..b75fd9ce2f 100644 --- a/R/geom-.R +++ b/R/geom-.R @@ -131,8 +131,11 @@ Geom <- ggproto("Geom", # Fill in missing aesthetics with their defaults missing_aes <- setdiff(names(default_aes), names(data)) + default_aes <- default_aes[missing_aes] + themed_defaults <- eval_from_theme(default_aes, theme) + default_aes[names(themed_defaults)] <- themed_defaults - missing_eval <- lapply(default_aes[missing_aes], eval_tidy) + missing_eval <- lapply(default_aes, eval_tidy) # Needed for geoms with defaults set to NULL (e.g. GeomSf) missing_eval <- compact(missing_eval) @@ -223,6 +226,16 @@ Geom <- ggproto("Geom", ) +eval_from_theme <- function(aesthetics, theme) { + themed <- is_themed_aes(aesthetics) + if (!any(themed)) { + return(aesthetics) + } + settings <- calc_element("geom", theme) %||% + element_geom("black", "white", "#3366FF", 0.5, 2) + lapply(aesthetics[themed], eval_tidy, data = settings) +} + #' Graphical units #' #' Multiply size in mm by these constants in order to convert to the units From ced8c15b3ff19c47ce69cfa4d56b8dee6e21dcd9 Mon Sep 17 00:00:00 2001 From: Teun van den Brand Date: Fri, 5 Apr 2024 16:06:10 +0200 Subject: [PATCH 05/41] allow user-specified `from_theme()` --- R/geom-.R | 7 +++++++ R/layer.R | 5 +++-- 2 files changed, 10 insertions(+), 2 deletions(-) diff --git a/R/geom-.R b/R/geom-.R index b75fd9ce2f..1bee3a5fb6 100644 --- a/R/geom-.R +++ b/R/geom-.R @@ -145,6 +145,13 @@ Geom <- ggproto("Geom", data[names(missing_eval)] <- missing_eval } + themed <- is_themed_aes(modifiers) + if (any(themed)) { + themed <- eval_from_theme(modifiers[themed], theme) + modifiers <- modifiers[setdiff(names(modifiers), names(themed))] + data[names(themed)] <- themed + } + # If any after_scale mappings are detected they will be resolved here # This order means that they will have access to all default aesthetics if (length(modifiers) != 0) { diff --git a/R/layer.R b/R/layer.R index 5fb1a169b5..762090ff5f 100644 --- a/R/layer.R +++ b/R/layer.R @@ -289,8 +289,9 @@ Layer <- ggproto("Layer", NULL, set <- names(aesthetics) %in% names(self$aes_params) calculated <- is_calculated_aes(aesthetics, warn = TRUE) modifiers <- is_scaled_aes(aesthetics) + themed <- is_themed_aes(aesthetics) - aesthetics <- aesthetics[!set & !calculated & !modifiers] + aesthetics <- aesthetics[!set & !calculated & !modifiers & !themed] # Override grouping if set in layer if (!is.null(self$geom_params$group)) { @@ -442,7 +443,7 @@ Layer <- ggproto("Layer", NULL, if (empty(data)) return(data) aesthetics <- self$computed_mapping - modifiers <- aesthetics[is_scaled_aes(aesthetics) | is_staged_aes(aesthetics)] + modifiers <- aesthetics[is_scaled_aes(aesthetics) | is_staged_aes(aesthetics) | is_themed_aes(aesthetics)] self$geom$use_defaults(data, self$aes_params, modifiers, theme = theme) }, From 659fd099119364467fccd66284057673d1ade5e1 Mon Sep 17 00:00:00 2001 From: Teun van den Brand Date: Fri, 5 Apr 2024 16:51:05 +0200 Subject: [PATCH 06/41] plumbing for guides to observe theme --- R/guide-.R | 6 +++--- R/guide-axis-stack.R | 2 +- R/guide-colorbar.R | 2 +- R/guide-legend.R | 10 +++++----- R/guide-old.R | 2 +- R/guides-.R | 8 ++++---- R/plot-build.R | 6 ++++-- 7 files changed, 19 insertions(+), 17 deletions(-) diff --git a/R/guide-.R b/R/guide-.R index 0a334c4580..e1f789e26b 100644 --- a/R/guide-.R +++ b/R/guide-.R @@ -265,11 +265,11 @@ Guide <- ggproto( # Function for extracting information from the layers. # Mostly applies to `guide_legend()` and `guide_binned()` - process_layers = function(self, params, layers, data = NULL) { - self$get_layer_key(params, layers, data) + process_layers = function(self, params, layers, data = NULL, theme = NULL) { + self$get_layer_key(params, layers, data, theme) }, - get_layer_key = function(params, layers, data = NULL) { + get_layer_key = function(params, layers, data = NULL, theme = NULL) { return(params) }, diff --git a/R/guide-axis-stack.R b/R/guide-axis-stack.R index c645c29d99..400e1f6817 100644 --- a/R/guide-axis-stack.R +++ b/R/guide-axis-stack.R @@ -134,7 +134,7 @@ GuideAxisStack <- ggproto( }, # Just loops through guides - get_layer_key = function(params, layers) { + get_layer_key = function(params, layers, ...) { for (i in seq_along(params$guides)) { params$guide_params[[i]] <- params$guides[[i]]$get_layer_key( params = params$guide_params[[i]], diff --git a/R/guide-colorbar.R b/R/guide-colorbar.R index b8e62f82c9..3741907f04 100644 --- a/R/guide-colorbar.R +++ b/R/guide-colorbar.R @@ -269,7 +269,7 @@ GuideColourbar <- ggproto( return(list(guide = self, params = params)) }, - get_layer_key = function(params, layers, data = NULL) { + get_layer_key = function(params, layers, data = NULL, theme = NULL) { params }, diff --git a/R/guide-legend.R b/R/guide-legend.R index c685cdd8c7..b0aebfd836 100644 --- a/R/guide-legend.R +++ b/R/guide-legend.R @@ -209,7 +209,7 @@ GuideLegend <- ggproto( }, # Arrange common data for vertical and horizontal legends - process_layers = function(self, params, layers, data = NULL) { + process_layers = function(self, params, layers, data = NULL, theme = NULL) { include <- vapply(layers, function(layer) { aes <- matched_aes(layer, params) @@ -220,10 +220,10 @@ GuideLegend <- ggproto( return(NULL) } - self$get_layer_key(params, layers[include], data[include]) + self$get_layer_key(params, layers[include], data[include], theme) }, - get_layer_key = function(params, layers, data) { + get_layer_key = function(params, layers, data, theme) { decor <- Map(layer = layers, df = data, f = function(layer, df) { @@ -240,13 +240,13 @@ GuideLegend <- ggproto( data <- try_fetch( layer$geom$use_defaults(params$key[matched_aes], - layer_params, modifiers), + layer_params, modifiers, theme), error = function(cnd) { cli::cli_warn( "Failed to apply {.fn after_scale} modifications to legend", parent = cnd ) - layer$geom$use_defaults(params$key[matched_aes], layer_params, list()) + layer$geom$use_defaults(params$key[matched_aes], layer_params, list(), theme) } ) data$.draw <- keep_key_data(params$key, df, matched_aes, layer$show.legend) diff --git a/R/guide-old.R b/R/guide-old.R index b2a137fffd..de870965fd 100644 --- a/R/guide-old.R +++ b/R/guide-old.R @@ -103,7 +103,7 @@ GuideOld <- ggproto( guide_transform(params, coord, panel_params) }, - process_layers = function(self, params, layers, data = NULL) { + process_layers = function(self, params, layers, data = NULL, theme = NULL) { guide_geom(params, layers, default_mapping = NULL) }, diff --git a/R/guides-.R b/R/guides-.R index 2280c40def..b988b1e935 100644 --- a/R/guides-.R +++ b/R/guides-.R @@ -285,7 +285,7 @@ Guides <- ggproto( # # The resulting guide is then drawn in ggplot_gtable - build = function(self, scales, layers, labels, layer_data) { + build = function(self, scales, layers, labels, layer_data, theme) { # Empty guides list custom <- self$get_custom() @@ -312,7 +312,7 @@ Guides <- ggproto( # Merge and process layers guides$merge() - guides$process_layers(layers, layer_data) + guides$process_layers(layers, layer_data, theme) if (length(guides$guides) == 0) { return(no_guides) } @@ -460,9 +460,9 @@ Guides <- ggproto( }, # Loop over guides to let them extract information from layers - process_layers = function(self, layers, data = NULL) { + process_layers = function(self, layers, data = NULL, theme = NULL) { self$params <- Map( - function(guide, param) guide$process_layers(param, layers, data), + function(guide, param) guide$process_layers(param, layers, data, theme), guide = self$guides, param = self$params ) diff --git a/R/plot-build.R b/R/plot-build.R index 82de6f2164..a33d0a62a0 100644 --- a/R/plot-build.R +++ b/R/plot-build.R @@ -93,11 +93,14 @@ ggplot_build.ggplot <- function(plot) { # Hand off position guides to layout layout$setup_panel_guides(plot$guides, plot$layers) + # Complete the plot's theme + plot$theme <- plot_theme(plot) + # Train and map non-position scales and guides npscales <- scales$non_position_scales() if (npscales$n() > 0) { lapply(data, npscales$train_df) - plot$guides <- plot$guides$build(npscales, plot$layers, plot$labels, data) + plot$guides <- plot$guides$build(npscales, plot$layers, plot$labels, data, plot$theme) data <- lapply(data, npscales$map_df) } else { # Only keep custom guides if there are no non-position scales @@ -106,7 +109,6 @@ ggplot_build.ggplot <- function(plot) { data <- .expose_data(data) # Fill in defaults etc. - plot$theme <- plot_theme(plot) data <- by_layer( function(l, d) l$compute_geom_2(d, theme = plot$theme), layers, data, "setting up geom aesthetics" From 2cec833f0dca0354d57b93c9660f94518a019c11 Mon Sep 17 00:00:00 2001 From: Teun van den Brand Date: Mon, 8 Apr 2024 11:38:01 +0200 Subject: [PATCH 07/41] reoxygenate --- NAMESPACE | 1 + man/aes_eval.Rd | 3 +++ man/theme.Rd | 1 + 3 files changed, 5 insertions(+) diff --git a/NAMESPACE b/NAMESPACE index 67c7a4941a..f684a217c0 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -365,6 +365,7 @@ export(find_panel) export(flip_data) export(flipped_names) export(fortify) +export(from_theme) export(geom_abline) export(geom_area) export(geom_bar) diff --git a/man/aes_eval.Rd b/man/aes_eval.Rd index 827bc6a876..40b80dfc56 100644 --- a/man/aes_eval.Rd +++ b/man/aes_eval.Rd @@ -5,6 +5,7 @@ \alias{after_stat} \alias{stat} \alias{after_scale} +\alias{from_theme} \alias{stage} \title{Control aesthetic evaluation} \usage{ @@ -16,6 +17,8 @@ after_stat(x) after_scale(x) +from_theme(x) + stage(start = NULL, after_stat = NULL, after_scale = NULL) } \arguments{ diff --git a/man/theme.Rd b/man/theme.Rd index 5d51fd8643..db1576c67a 100644 --- a/man/theme.Rd +++ b/man/theme.Rd @@ -10,6 +10,7 @@ theme( rect, text, title, + geom, aspect.ratio, axis.title, axis.title.x, From 5637501480f73ef879ee7659146b35baa36508fa Mon Sep 17 00:00:00 2001 From: Teun van den Brand Date: Wed, 17 Apr 2024 11:22:49 +0200 Subject: [PATCH 08/41] Add text settings --- R/geom-label.R | 7 +++++-- R/geom-text.R | 7 +++++-- R/theme-defaults.R | 3 ++- R/theme-elements.R | 20 ++++++++++++++++++-- 4 files changed, 30 insertions(+), 7 deletions(-) diff --git a/R/geom-label.R b/R/geom-label.R index c292fa1a66..56122832ee 100644 --- a/R/geom-label.R +++ b/R/geom-label.R @@ -56,8 +56,11 @@ GeomLabel <- ggproto("GeomLabel", Geom, required_aes = c("x", "y", "label"), default_aes = aes( - colour = "black", fill = "white", size = 3.88, angle = 0, - hjust = 0.5, vjust = 0.5, alpha = NA, family = "", fontface = 1, + colour = "black", fill = "white", + family = from_theme(family), + size = from_theme(fontsize), + angle = 0, + hjust = 0.5, vjust = 0.5, alpha = NA, fontface = 1, lineheight = 1.2 ), diff --git a/R/geom-text.R b/R/geom-text.R index acfbb0337a..a3ddc1a437 100644 --- a/R/geom-text.R +++ b/R/geom-text.R @@ -215,8 +215,11 @@ GeomText <- ggproto("GeomText", Geom, non_missing_aes = "angle", default_aes = aes( - colour = "black", size = 3.88, angle = 0, hjust = 0.5, - vjust = 0.5, alpha = NA, family = "", fontface = 1, lineheight = 1.2 + colour = "black", + family = from_theme(family), + size = from_theme(fontsize), + angle = 0, hjust = 0.5, + vjust = 0.5, alpha = NA, fontface = 1, lineheight = 1.2 ), draw_panel = function(data, panel_params, coord, parse = FALSE, diff --git a/R/theme-defaults.R b/R/theme-defaults.R index a16d3fef21..37d1850eae 100644 --- a/R/theme-defaults.R +++ b/R/theme-defaults.R @@ -135,7 +135,8 @@ theme_grey <- function(base_size = 11, base_family = "", ), geom = element_geom(ink = "black", paper = "white", accent = "#3366FF", - thin = base_line_size, thick = base_line_size * 2), + thin = base_line_size, thick = base_line_size * 2, + family = base_family, fontsize = base_size), axis.line = element_blank(), axis.line.x = NULL, diff --git a/R/theme-elements.R b/R/theme-elements.R index e29842b734..681f48cbb8 100644 --- a/R/theme-elements.R +++ b/R/theme-elements.R @@ -145,10 +145,26 @@ element_text <- function(family = NULL, face = NULL, colour = NULL, } element_geom <- function( - ink = NULL, paper = NULL, accent = NULL, thin = NULL, thick = NULL) { + # colours + ink = NULL, paper = NULL, accent = NULL, + # linewidth + thin = NULL, thick = NULL, + # text + family = NULL, fontsize = NULL + ) { + + if (!is.null(fontsize)) { + fontsize <- fontsize / .pt + } structure( - list(ink = ink, paper = paper, accent = accent, thin = thin, thick = thick), + list( + ink = ink, + paper = paper, + accent = accent, + thin = thin, thick = thick, + family = family, fontsize = fontsize + ), class = c("element_geom", "element") ) } From 2d28202640fbc46534c1793fbd2eb75e29d2340b Mon Sep 17 00:00:00 2001 From: Teun van den Brand Date: Wed, 17 Apr 2024 11:22:49 +0200 Subject: [PATCH 09/41] Add text settings --- R/geom-.R | 3 +-- R/geom-label.R | 7 +++++-- R/geom-text.R | 7 +++++-- R/theme-defaults.R | 3 ++- R/theme-elements.R | 25 +++++++++++++++++++++++-- 5 files changed, 36 insertions(+), 9 deletions(-) diff --git a/R/geom-.R b/R/geom-.R index 1bee3a5fb6..f8363cac50 100644 --- a/R/geom-.R +++ b/R/geom-.R @@ -238,8 +238,7 @@ eval_from_theme <- function(aesthetics, theme) { if (!any(themed)) { return(aesthetics) } - settings <- calc_element("geom", theme) %||% - element_geom("black", "white", "#3366FF", 0.5, 2) + settings <- calc_element("geom", theme) %||% .default_geom_element lapply(aesthetics[themed], eval_tidy, data = settings) } diff --git a/R/geom-label.R b/R/geom-label.R index c292fa1a66..56122832ee 100644 --- a/R/geom-label.R +++ b/R/geom-label.R @@ -56,8 +56,11 @@ GeomLabel <- ggproto("GeomLabel", Geom, required_aes = c("x", "y", "label"), default_aes = aes( - colour = "black", fill = "white", size = 3.88, angle = 0, - hjust = 0.5, vjust = 0.5, alpha = NA, family = "", fontface = 1, + colour = "black", fill = "white", + family = from_theme(family), + size = from_theme(fontsize), + angle = 0, + hjust = 0.5, vjust = 0.5, alpha = NA, fontface = 1, lineheight = 1.2 ), diff --git a/R/geom-text.R b/R/geom-text.R index acfbb0337a..a3ddc1a437 100644 --- a/R/geom-text.R +++ b/R/geom-text.R @@ -215,8 +215,11 @@ GeomText <- ggproto("GeomText", Geom, non_missing_aes = "angle", default_aes = aes( - colour = "black", size = 3.88, angle = 0, hjust = 0.5, - vjust = 0.5, alpha = NA, family = "", fontface = 1, lineheight = 1.2 + colour = "black", + family = from_theme(family), + size = from_theme(fontsize), + angle = 0, hjust = 0.5, + vjust = 0.5, alpha = NA, fontface = 1, lineheight = 1.2 ), draw_panel = function(data, panel_params, coord, parse = FALSE, diff --git a/R/theme-defaults.R b/R/theme-defaults.R index a16d3fef21..37d1850eae 100644 --- a/R/theme-defaults.R +++ b/R/theme-defaults.R @@ -135,7 +135,8 @@ theme_grey <- function(base_size = 11, base_family = "", ), geom = element_geom(ink = "black", paper = "white", accent = "#3366FF", - thin = base_line_size, thick = base_line_size * 2), + thin = base_line_size, thick = base_line_size * 2, + family = base_family, fontsize = base_size), axis.line = element_blank(), axis.line.x = NULL, diff --git a/R/theme-elements.R b/R/theme-elements.R index e29842b734..0752f3a268 100644 --- a/R/theme-elements.R +++ b/R/theme-elements.R @@ -145,14 +145,35 @@ element_text <- function(family = NULL, face = NULL, colour = NULL, } element_geom <- function( - ink = NULL, paper = NULL, accent = NULL, thin = NULL, thick = NULL) { + # colours + ink = NULL, paper = NULL, accent = NULL, + # linewidth + thin = NULL, thick = NULL, + # text + family = NULL, fontsize = NULL + ) { + + if (!is.null(fontsize)) { + fontsize <- fontsize / .pt + } structure( - list(ink = ink, paper = paper, accent = accent, thin = thin, thick = thick), + list( + ink = ink, + paper = paper, + accent = accent, + thin = thin, thick = thick, + family = family, fontsize = fontsize + ), class = c("element_geom", "element") ) } +.default_geom_element <- element_geom( + ink = "black", paper = "white", accent = "#3366FF", + thin = 0.5, thick = 2, + family = "", fontsize = 11 +) #' @export print.element <- function(x, ...) utils::str(x) From 5f2ebf91328f8740086c6806bc1a99966852445d Mon Sep 17 00:00:00 2001 From: Teun van den Brand Date: Wed, 17 Apr 2024 11:51:30 +0200 Subject: [PATCH 10/41] accept minor fontsize difference (11.04pt -> 11.00pt) --- ...clip-on-by-default-only-inside-visible.svg | 16 ++++++------- ...ed-off-both-inside-and-outside-visible.svg | 16 ++++++------- .../bottom-half-circle-with-rotated-text.svg | 24 +++++++++---------- .../geom-sf/labels-for-north-carolina.svg | 4 ++-- .../geom-sf/texts-for-north-carolina.svg | 2 +- 5 files changed, 31 insertions(+), 31 deletions(-) diff --git a/tests/testthat/_snaps/coord-cartesian/clip-on-by-default-only-inside-visible.svg b/tests/testthat/_snaps/coord-cartesian/clip-on-by-default-only-inside-visible.svg index 6f424b0c4a..8532b083e3 100644 --- a/tests/testthat/_snaps/coord-cartesian/clip-on-by-default-only-inside-visible.svg +++ b/tests/testthat/_snaps/coord-cartesian/clip-on-by-default-only-inside-visible.svg @@ -27,14 +27,14 @@ -inside -inside -inside -inside -outside -outside -outside -outside +inside +inside +inside +inside +outside +outside +outside +outside clip on by default, only 'inside' visible diff --git a/tests/testthat/_snaps/coord-cartesian/clip-turned-off-both-inside-and-outside-visible.svg b/tests/testthat/_snaps/coord-cartesian/clip-turned-off-both-inside-and-outside-visible.svg index 89932b9196..b2120e5e14 100644 --- a/tests/testthat/_snaps/coord-cartesian/clip-turned-off-both-inside-and-outside-visible.svg +++ b/tests/testthat/_snaps/coord-cartesian/clip-turned-off-both-inside-and-outside-visible.svg @@ -20,14 +20,14 @@ -inside -inside -inside -inside -outside -outside -outside -outside +inside +inside +inside +inside +outside +outside +outside +outside clip turned off, both 'inside' and 'outside' visible diff --git a/tests/testthat/_snaps/coord-polar/bottom-half-circle-with-rotated-text.svg b/tests/testthat/_snaps/coord-polar/bottom-half-circle-with-rotated-text.svg index 30c4b0fc24..caa297b3f5 100644 --- a/tests/testthat/_snaps/coord-polar/bottom-half-circle-with-rotated-text.svg +++ b/tests/testthat/_snaps/coord-polar/bottom-half-circle-with-rotated-text.svg @@ -40,18 +40,18 @@ -cat -strawberry -cake -coffee -window -fluid -cat -strawberry -cake -coffee -window -fluid +cat +strawberry +cake +coffee +window +fluid +cat +strawberry +cake +coffee +window +fluid 1 2 3 diff --git a/tests/testthat/_snaps/geom-sf/labels-for-north-carolina.svg b/tests/testthat/_snaps/geom-sf/labels-for-north-carolina.svg index cf5ffdbbf2..f11f41251b 100644 --- a/tests/testthat/_snaps/geom-sf/labels-for-north-carolina.svg +++ b/tests/testthat/_snaps/geom-sf/labels-for-north-carolina.svg @@ -27,8 +27,8 @@ - -ashe + +ashe diff --git a/tests/testthat/_snaps/geom-sf/texts-for-north-carolina.svg b/tests/testthat/_snaps/geom-sf/texts-for-north-carolina.svg index 96ffe43109..ec2184a425 100644 --- a/tests/testthat/_snaps/geom-sf/texts-for-north-carolina.svg +++ b/tests/testthat/_snaps/geom-sf/texts-for-north-carolina.svg @@ -27,7 +27,7 @@ -ashe +ashe From f5034099dac18d8f1d2db5a7a7104981310cb0a4 Mon Sep 17 00:00:00 2001 From: Teun van den Brand Date: Wed, 17 Apr 2024 15:01:37 +0200 Subject: [PATCH 11/41] temporarily disable `sf_grob()` default lookups --- R/geom-sf.R | 13 +++++++++---- 1 file changed, 9 insertions(+), 4 deletions(-) diff --git a/R/geom-sf.R b/R/geom-sf.R index a8f70d7f4e..85de53d0b0 100644 --- a/R/geom-sf.R +++ b/R/geom-sf.R @@ -189,14 +189,19 @@ sf_grob <- function(x, lineend = "butt", linejoin = "round", linemitre = 10, type_ind <- type_ind[!remove] is_collection <- is_collection[!remove] } + # TODO: Wait for #5834 defaults <- list( - GeomPoint$default_aes, - GeomLine$default_aes, - modify_list(GeomPolygon$default_aes, list(fill = "grey90", colour = "grey35", linewidth = 0.2)) + # GeomPoint$default_aes, + aes(shape = 19, colour = "black", size = 1.5, fill = NA, alpha = NA, stroke = 0.5), + # GeomLine$default_aes, + aes(colour = "black", linewidth = 0.5, linetype = 1, alpha = NA), + # modify_list(GeomPolygon$default_aes, list(fill = "grey90", colour = "grey35", linewidth = 0.2)) + aes(colour = "grey35", fill = "grey90", linewidth = 0.2, linetype = 1, alpha = NA, subgroup = NULL) ) defaults[[4]] <- modify_list( defaults[[3]], - rename(GeomPoint$default_aes, c(size = "point_size", fill = "point_fill")) + # rename(GeomPoint$default_aes, c(size = "point_size", fill = "point_fill")) + aes(shape = 19, colour = "black", point_size = 1.5, point_fill = NA, alpha = NA, stroke = 0.5) ) default_names <- unique0(unlist(lapply(defaults, names))) defaults <- lapply(setNames(default_names, default_names), function(n) { From f08fcb6b588c279fedd09d836c0b4401a665ec47 Mon Sep 17 00:00:00 2001 From: Teun van den Brand Date: Wed, 17 Apr 2024 15:33:45 +0200 Subject: [PATCH 12/41] temporary shim for colour mixing --- R/utilities.R | 10 ++++++++++ 1 file changed, 10 insertions(+) diff --git a/R/utilities.R b/R/utilities.R index 9f9133a0b5..c78fad7541 100644 --- a/R/utilities.R +++ b/R/utilities.R @@ -817,3 +817,13 @@ as_unordered_factor <- function(x) { class(x) <- setdiff(class(x), "ordered") x } + +# Shim for scales/#424 +# TODO: prefer scales version over this one +col_mix <- function(a, b, amount = 0.5) { + input <- vec_recycle_common(a = a, b = b, amount = amount) + a <- col2rgb(input$a, TRUE) + b <- col2rgb(input$b, TRUE) + new <- (a * (1 - input$amount) + b * input$amount) + rgb(new["red", ], new["green", ], new["blue", ], alpha = new["alpha", ], maxColorValue = 255) +} From b5ffd327132537e8f5bdebc5899751d0791a5574 Mon Sep 17 00:00:00 2001 From: Teun van den Brand Date: Wed, 17 Apr 2024 16:31:53 +0200 Subject: [PATCH 13/41] Get all `colour`/`fill`/`linewidth` from theme --- R/annotation-logticks.R | 2 +- R/geom-abline.R | 2 +- R/geom-boxplot.R | 5 +++-- R/geom-contour.R | 4 ++-- R/geom-crossbar.R | 2 +- R/geom-curve.R | 2 +- R/geom-density.R | 2 +- R/geom-density2d.R | 2 +- R/geom-dotplot.R | 2 +- R/geom-errorbar.R | 2 +- R/geom-errorbarh.R | 2 +- R/geom-hex.R | 4 ++-- R/geom-hline.R | 2 +- R/geom-label.R | 2 +- R/geom-linerange.R | 2 +- R/geom-path.R | 2 +- R/geom-point.R | 3 ++- R/geom-pointrange.R | 2 +- R/geom-polygon.R | 8 ++++++-- R/geom-quantile.R | 2 +- R/geom-raster.R | 2 +- R/geom-rect.R | 7 +++++-- R/geom-ribbon.R | 11 ++++++++--- R/geom-rug.R | 2 +- R/geom-segment.R | 2 +- R/geom-smooth.R | 8 ++++++-- R/geom-text.R | 2 +- R/geom-tile.R | 8 ++++++-- R/geom-violin.R | 6 +++++- R/geom-vline.R | 2 +- 30 files changed, 65 insertions(+), 39 deletions(-) diff --git a/R/annotation-logticks.R b/R/annotation-logticks.R index 8f3e8a63c2..e20e0ee2a6 100644 --- a/R/annotation-logticks.R +++ b/R/annotation-logticks.R @@ -228,7 +228,7 @@ GeomLogticks <- ggproto("GeomLogticks", Geom, gTree(children = inject(gList(!!!ticks))) }, - default_aes = aes(colour = "black", linewidth = 0.5, linetype = 1, alpha = 1) + default_aes = aes(colour = from_theme(ink), linewidth = from_theme(thin), linetype = 1, alpha = 1) ) diff --git a/R/geom-abline.R b/R/geom-abline.R index da65483635..4bd215ff94 100644 --- a/R/geom-abline.R +++ b/R/geom-abline.R @@ -142,7 +142,7 @@ GeomAbline <- ggproto("GeomAbline", Geom, GeomSegment$draw_panel(unique0(data), panel_params, coord, lineend = lineend) }, - default_aes = aes(colour = "black", linewidth = 0.5, linetype = 1, alpha = NA), + default_aes = aes(colour = from_theme(ink), linewidth = from_theme(thin), linetype = 1, alpha = NA), required_aes = c("slope", "intercept"), draw_key = draw_key_abline, diff --git a/R/geom-boxplot.R b/R/geom-boxplot.R index 399f92d7a8..6e5a35f408 100644 --- a/R/geom-boxplot.R +++ b/R/geom-boxplot.R @@ -327,8 +327,9 @@ GeomBoxplot <- ggproto("GeomBoxplot", Geom, draw_key = draw_key_boxplot, - default_aes = aes(weight = 1, colour = "grey20", fill = "white", size = NULL, - alpha = NA, shape = 19, linetype = "solid", linewidth = 0.5), + default_aes = aes(weight = 1, colour = from_theme(col_mix(ink, paper, 0.2)), + fill = from_theme(paper), size = NULL, + alpha = NA, shape = 19, linetype = "solid", linewidth = from_theme(thin)), required_aes = c("x|y", "lower|xlower", "upper|xupper", "middle|xmiddle", "ymin|xmin", "ymax|xmax"), diff --git a/R/geom-contour.R b/R/geom-contour.R index 7dfe9fb228..945375dca2 100644 --- a/R/geom-contour.R +++ b/R/geom-contour.R @@ -126,8 +126,8 @@ geom_contour_filled <- function(mapping = NULL, data = NULL, GeomContour <- ggproto("GeomContour", GeomPath, default_aes = aes( weight = 1, - colour = "#3366FF", - linewidth = 0.5, + colour = from_theme(accent), + linewidth = from_theme(thin), linetype = 1, alpha = NA ) diff --git a/R/geom-crossbar.R b/R/geom-crossbar.R index 36c3d4b9ff..ffcc58785f 100644 --- a/R/geom-crossbar.R +++ b/R/geom-crossbar.R @@ -40,7 +40,7 @@ GeomCrossbar <- ggproto("GeomCrossbar", Geom, GeomErrorbar$setup_data(data, params) }, - default_aes = aes(colour = "black", fill = NA, linewidth = 0.5, linetype = 1, + default_aes = aes(colour = from_theme(ink), fill = NA, linewidth = from_theme(thin), linetype = 1, alpha = NA), required_aes = c("x", "y", "ymin|xmin", "ymax|xmax"), diff --git a/R/geom-curve.R b/R/geom-curve.R index a2597a8d72..3ca267f513 100644 --- a/R/geom-curve.R +++ b/R/geom-curve.R @@ -40,7 +40,7 @@ geom_curve <- function(mapping = NULL, data = NULL, #' @usage NULL #' @export GeomCurve <- ggproto("GeomCurve", GeomSegment, - default_aes = aes(colour = "black", linewidth = 0.5, linetype = 1, alpha = NA), + default_aes = aes(colour = from_theme(ink), linewidth = from_theme(thin), linetype = 1, alpha = NA), draw_panel = function(data, panel_params, coord, curvature = 0.5, angle = 90, ncp = 5, arrow = NULL, arrow.fill = NULL, lineend = "butt", na.rm = FALSE) { diff --git a/R/geom-density.R b/R/geom-density.R index c71a9f98eb..a4a7754f2e 100644 --- a/R/geom-density.R +++ b/R/geom-density.R @@ -93,7 +93,7 @@ geom_density <- function(mapping = NULL, data = NULL, #' @include geom-ribbon.R GeomDensity <- ggproto("GeomDensity", GeomArea, default_aes = defaults( - aes(fill = NA, weight = 1, colour = "black", alpha = NA), + aes(fill = NA, weight = 1, colour = from_theme(ink), alpha = NA), GeomArea$default_aes ) ) diff --git a/R/geom-density2d.R b/R/geom-density2d.R index e95a8b2c31..8d0e9fbff9 100644 --- a/R/geom-density2d.R +++ b/R/geom-density2d.R @@ -106,7 +106,7 @@ geom_density2d <- geom_density_2d #' @usage NULL #' @export GeomDensity2d <- ggproto("GeomDensity2d", GeomPath, - default_aes = aes(colour = "#3366FF", linewidth = 0.5, linetype = 1, alpha = NA) + default_aes = aes(colour = from_theme(accent), linewidth = from_theme(thin), linetype = 1, alpha = NA) ) #' @export diff --git a/R/geom-dotplot.R b/R/geom-dotplot.R index d79e6a823e..831b1ecd68 100644 --- a/R/geom-dotplot.R +++ b/R/geom-dotplot.R @@ -188,7 +188,7 @@ GeomDotplot <- ggproto("GeomDotplot", Geom, required_aes = c("x", "y"), non_missing_aes = c("size", "shape"), - default_aes = aes(colour = "black", fill = "black", alpha = NA, + default_aes = aes(colour = from_theme(ink), fill = from_theme(ink), alpha = NA, stroke = 1, linetype = "solid", weight = 1), setup_data = function(data, params) { diff --git a/R/geom-errorbar.R b/R/geom-errorbar.R index c02ab16ed9..93ef1d9b18 100644 --- a/R/geom-errorbar.R +++ b/R/geom-errorbar.R @@ -28,7 +28,7 @@ geom_errorbar <- function(mapping = NULL, data = NULL, #' @usage NULL #' @export GeomErrorbar <- ggproto("GeomErrorbar", Geom, - default_aes = aes(colour = "black", linewidth = 0.5, linetype = 1, width = 0.5, + default_aes = aes(colour = from_theme(ink), linewidth = from_theme(thin), linetype = 1, width = 0.5, alpha = NA), draw_key = draw_key_path, diff --git a/R/geom-errorbarh.R b/R/geom-errorbarh.R index b23d125da4..5db06ec04d 100644 --- a/R/geom-errorbarh.R +++ b/R/geom-errorbarh.R @@ -51,7 +51,7 @@ geom_errorbarh <- function(mapping = NULL, data = NULL, #' @usage NULL #' @export GeomErrorbarh <- ggproto("GeomErrorbarh", Geom, - default_aes = aes(colour = "black", linewidth = 0.5, linetype = 1, height = 0.5, + default_aes = aes(colour = from_theme(ink), linewidth = from_theme(thin), linetype = 1, height = 0.5, alpha = NA), draw_key = draw_key_path, diff --git a/R/geom-hex.R b/R/geom-hex.R index a220e12140..fd885b465e 100644 --- a/R/geom-hex.R +++ b/R/geom-hex.R @@ -107,8 +107,8 @@ GeomHex <- ggproto("GeomHex", Geom, default_aes = aes( colour = NA, - fill = "grey50", - linewidth = 0.5, + fill = from_theme(col_mix(ink, paper)), + linewidth = from_theme(thin), linetype = 1, alpha = NA ), diff --git a/R/geom-hline.R b/R/geom-hline.R index 924b41f40a..85bc109a53 100644 --- a/R/geom-hline.R +++ b/R/geom-hline.R @@ -55,7 +55,7 @@ GeomHline <- ggproto("GeomHline", Geom, GeomSegment$draw_panel(unique0(data), panel_params, coord, lineend = lineend) }, - default_aes = aes(colour = "black", linewidth = 0.5, linetype = 1, alpha = NA), + default_aes = aes(colour = from_theme(ink), linewidth = from_theme(thin), linetype = 1, alpha = NA), required_aes = "yintercept", draw_key = draw_key_path, diff --git a/R/geom-label.R b/R/geom-label.R index 56122832ee..0f2ae65b53 100644 --- a/R/geom-label.R +++ b/R/geom-label.R @@ -56,7 +56,7 @@ GeomLabel <- ggproto("GeomLabel", Geom, required_aes = c("x", "y", "label"), default_aes = aes( - colour = "black", fill = "white", + colour = from_theme(ink), fill = from_theme(paper), family = from_theme(family), size = from_theme(fontsize), angle = 0, diff --git a/R/geom-linerange.R b/R/geom-linerange.R index 7144d0084a..819e3c1000 100644 --- a/R/geom-linerange.R +++ b/R/geom-linerange.R @@ -91,7 +91,7 @@ geom_linerange <- function(mapping = NULL, data = NULL, #' @usage NULL #' @export GeomLinerange <- ggproto("GeomLinerange", Geom, - default_aes = aes(colour = "black", linewidth = 0.5, linetype = 1, alpha = NA), + default_aes = aes(colour = from_theme(ink), linewidth = from_theme(thin), linetype = 1, alpha = NA), draw_key = draw_key_linerange, diff --git a/R/geom-path.R b/R/geom-path.R index ad7589a028..ff6efb0ee7 100644 --- a/R/geom-path.R +++ b/R/geom-path.R @@ -130,7 +130,7 @@ geom_path <- function(mapping = NULL, data = NULL, GeomPath <- ggproto("GeomPath", Geom, required_aes = c("x", "y"), - default_aes = aes(colour = "black", linewidth = 0.5, linetype = 1, alpha = NA), + default_aes = aes(colour = from_theme(ink), linewidth = from_theme(thin), linetype = 1, alpha = NA), non_missing_aes = c("linewidth", "colour", "linetype"), diff --git a/R/geom-point.R b/R/geom-point.R index 20a7f46b58..45f5c77701 100644 --- a/R/geom-point.R +++ b/R/geom-point.R @@ -135,7 +135,8 @@ GeomPoint <- ggproto("GeomPoint", Geom, required_aes = c("x", "y"), non_missing_aes = c("size", "shape", "colour"), default_aes = aes( - shape = 19, colour = "black", size = 1.5, fill = NA, + shape = 19, + colour = from_theme(ink), size = 1.5, fill = NA, alpha = NA, stroke = 0.5 ), diff --git a/R/geom-pointrange.R b/R/geom-pointrange.R index ccecfc0d95..5d39685604 100644 --- a/R/geom-pointrange.R +++ b/R/geom-pointrange.R @@ -30,7 +30,7 @@ geom_pointrange <- function(mapping = NULL, data = NULL, #' @usage NULL #' @export GeomPointrange <- ggproto("GeomPointrange", Geom, - default_aes = aes(colour = "black", size = 0.5, linewidth = 0.5, linetype = 1, + default_aes = aes(colour = from_theme(ink), size = 0.5, linewidth = from_theme(thin), linetype = 1, shape = 19, fill = NA, alpha = NA, stroke = 1), draw_key = draw_key_pointrange, diff --git a/R/geom-polygon.R b/R/geom-polygon.R index c644d9daad..8e2bfc90eb 100644 --- a/R/geom-polygon.R +++ b/R/geom-polygon.R @@ -175,8 +175,12 @@ GeomPolygon <- ggproto("GeomPolygon", Geom, } }, - default_aes = aes(colour = NA, fill = "grey20", linewidth = 0.5, linetype = 1, - alpha = NA, subgroup = NULL), + default_aes = aes( + colour = NA, + fill = from_theme(col_mix(ink, paper, 0.2)), + linewidth = from_theme(thin), linetype = 1, + alpha = NA, subgroup = NULL + ), handle_na = function(data, params) { data diff --git a/R/geom-quantile.R b/R/geom-quantile.R index bb3ff581ab..b04940b78c 100644 --- a/R/geom-quantile.R +++ b/R/geom-quantile.R @@ -66,7 +66,7 @@ geom_quantile <- function(mapping = NULL, data = NULL, #' @include geom-path.R GeomQuantile <- ggproto("GeomQuantile", GeomPath, default_aes = defaults( - aes(weight = 1, colour = "#3366FF", linewidth = 0.5), + aes(weight = 1, colour = from_theme(accent), linewidth = from_theme(thin)), GeomPath$default_aes ) ) diff --git a/R/geom-raster.R b/R/geom-raster.R index 2cd591d879..43faacc219 100644 --- a/R/geom-raster.R +++ b/R/geom-raster.R @@ -44,7 +44,7 @@ geom_raster <- function(mapping = NULL, data = NULL, #' @usage NULL #' @export GeomRaster <- ggproto("GeomRaster", Geom, - default_aes = aes(fill = "grey20", alpha = NA), + default_aes = aes(fill = from_theme(col_mix(ink, paper, 0.2)), alpha = NA), non_missing_aes = c("fill", "xmin", "xmax", "ymin", "ymax"), required_aes = c("x", "y"), diff --git a/R/geom-rect.R b/R/geom-rect.R index d39978897a..ba6fa762ad 100644 --- a/R/geom-rect.R +++ b/R/geom-rect.R @@ -28,8 +28,11 @@ geom_rect <- function(mapping = NULL, data = NULL, #' @usage NULL #' @export GeomRect <- ggproto("GeomRect", Geom, - default_aes = aes(colour = NA, fill = "grey35", linewidth = 0.5, linetype = 1, - alpha = NA), + default_aes = aes( + colour = NA, fill = from_theme(col_mix(ink, paper, 0.35)), + linewidth = from_theme(thin), linetype = 1, + alpha = NA + ), required_aes = c("xmin", "xmax", "ymin", "ymax"), diff --git a/R/geom-ribbon.R b/R/geom-ribbon.R index d93df77850..e8760c11c9 100644 --- a/R/geom-ribbon.R +++ b/R/geom-ribbon.R @@ -96,7 +96,9 @@ geom_ribbon <- function(mapping = NULL, data = NULL, #' @usage NULL #' @export GeomRibbon <- ggproto("GeomRibbon", Geom, - default_aes = aes(colour = NA, fill = "grey20", linewidth = 0.5, linetype = 1, + default_aes = aes( + colour = NA, fill = from_theme(col_mix(ink, paper, 0.799)), + linewidth = from_theme(thin), linetype = 1, alpha = NA), required_aes = c("x|y", "ymin|xmin", "ymax|xmax"), @@ -259,8 +261,11 @@ geom_area <- function(mapping = NULL, data = NULL, stat = "align", #' @usage NULL #' @export GeomArea <- ggproto("GeomArea", GeomRibbon, - default_aes = aes(colour = NA, fill = "grey20", linewidth = 0.5, linetype = 1, - alpha = NA), + default_aes = aes( + colour = NA, fill = from_theme(col_mix(ink, paper, 0.2)), + linewidth = from_theme(thin), linetype = 1, + alpha = NA + ), required_aes = c("x", "y"), diff --git a/R/geom-rug.R b/R/geom-rug.R index 0fe393bb95..a68b9259b0 100644 --- a/R/geom-rug.R +++ b/R/geom-rug.R @@ -153,7 +153,7 @@ GeomRug <- ggproto("GeomRug", Geom, gTree(children = inject(gList(!!!rugs))) }, - default_aes = aes(colour = "black", linewidth = 0.5, linetype = 1, alpha = NA), + default_aes = aes(colour = from_theme(ink), linewidth = from_theme(thin), linetype = 1, alpha = NA), draw_key = draw_key_path, diff --git a/R/geom-segment.R b/R/geom-segment.R index f32b61f876..064d09d7fb 100644 --- a/R/geom-segment.R +++ b/R/geom-segment.R @@ -104,7 +104,7 @@ geom_segment <- function(mapping = NULL, data = NULL, GeomSegment <- ggproto("GeomSegment", Geom, required_aes = c("x", "y", "xend|yend"), non_missing_aes = c("linetype", "linewidth"), - default_aes = aes(colour = "black", linewidth = 0.5, linetype = 1, alpha = NA), + default_aes = aes(colour = from_theme(ink), linewidth = from_theme(thin), linetype = 1, alpha = NA), draw_panel = function(self, data, panel_params, coord, arrow = NULL, arrow.fill = NULL, lineend = "butt", linejoin = "round", na.rm = FALSE) { data$xend <- data$xend %||% data$x diff --git a/R/geom-smooth.R b/R/geom-smooth.R index 535b8965a8..c3d0dc2dc7 100644 --- a/R/geom-smooth.R +++ b/R/geom-smooth.R @@ -161,8 +161,12 @@ GeomSmooth <- ggproto("GeomSmooth", Geom, required_aes = c("x", "y"), optional_aes = c("ymin", "ymax"), - default_aes = aes(colour = "#3366FF", fill = "grey60", linewidth = 1, - linetype = 1, weight = 1, alpha = 0.4), + default_aes = aes( + colour = from_theme(accent), + fill = from_theme(col_mix(ink, paper, 0.6)), + linewidth = from_theme(thick), + linetype = 1, weight = 1, alpha = 0.4 + ), rename_size = TRUE ) diff --git a/R/geom-text.R b/R/geom-text.R index a3ddc1a437..6dce7ba1d4 100644 --- a/R/geom-text.R +++ b/R/geom-text.R @@ -215,7 +215,7 @@ GeomText <- ggproto("GeomText", Geom, non_missing_aes = "angle", default_aes = aes( - colour = "black", + colour = from_theme(ink), family = from_theme(family), size = from_theme(fontsize), angle = 0, hjust = 0.5, diff --git a/R/geom-tile.R b/R/geom-tile.R index 139d6f733e..50e5f549a3 100644 --- a/R/geom-tile.R +++ b/R/geom-tile.R @@ -118,8 +118,12 @@ GeomTile <- ggproto("GeomTile", GeomRect, ) }, - default_aes = aes(fill = "grey20", colour = NA, linewidth = 0.1, linetype = 1, - alpha = NA, width = NA, height = NA), + default_aes = aes( + fill = from_theme(col_mix(ink, paper, 0.2)), + colour = NA, + linewidth = from_theme(thick / 10), + linetype = 1, alpha = NA, width = NA, height = NA + ), required_aes = c("x", "y"), diff --git a/R/geom-violin.R b/R/geom-violin.R index 0ac6cd29df..3c9e6a4345 100644 --- a/R/geom-violin.R +++ b/R/geom-violin.R @@ -197,7 +197,11 @@ GeomViolin <- ggproto("GeomViolin", Geom, draw_key = draw_key_polygon, - default_aes = aes(weight = 1, colour = "grey20", fill = "white", linewidth = 0.5, + default_aes = aes( + weight = 1, + colour = from_theme(col_mix(ink, paper, 0.2)), + fill = from_theme(paper), + linewidth = from_theme(thin), alpha = NA, linetype = "solid"), required_aes = c("x", "y"), diff --git a/R/geom-vline.R b/R/geom-vline.R index 2705093f05..7687925cfa 100644 --- a/R/geom-vline.R +++ b/R/geom-vline.R @@ -55,7 +55,7 @@ GeomVline <- ggproto("GeomVline", Geom, GeomSegment$draw_panel(unique0(data), panel_params, coord, lineend = lineend) }, - default_aes = aes(colour = "black", linewidth = 0.5, linetype = 1, alpha = NA), + default_aes = aes(colour = from_theme(ink), linewidth = from_theme(thin), linetype = 1, alpha = NA), required_aes = "xintercept", draw_key = draw_key_vline, From 93a92583520bd0bb88616563bd8d524afad318a2 Mon Sep 17 00:00:00 2001 From: Teun van den Brand Date: Wed, 17 Apr 2024 16:32:16 +0200 Subject: [PATCH 14/41] test theme has `geom` element --- R/theme-defaults.R | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/R/theme-defaults.R b/R/theme-defaults.R index 37d1850eae..13553e7271 100644 --- a/R/theme-defaults.R +++ b/R/theme-defaults.R @@ -547,6 +547,10 @@ theme_test <- function(base_size = 11, base_family = "", margin = margin(), debug = FALSE ), + geom = element_geom(ink = "black", paper = "white", accent = "#3366FF", + thin = base_line_size, thick = base_line_size * 2, + family = base_family, fontsize = base_size), + axis.line = element_blank(), axis.line.x = NULL, axis.line.y = NULL, From 5e9136f85a583877fcd89dd1f340bebce87a7c58 Mon Sep 17 00:00:00 2001 From: Teun van den Brand Date: Wed, 17 Apr 2024 16:43:06 +0200 Subject: [PATCH 15/41] adapt tests --- tests/testthat/test-geom-.R | 3 ++- tests/testthat/test-stats.R | 2 +- 2 files changed, 3 insertions(+), 2 deletions(-) diff --git a/tests/testthat/test-geom-.R b/tests/testthat/test-geom-.R index 61063d5d95..f13236416e 100644 --- a/tests/testthat/test-geom-.R +++ b/tests/testthat/test-geom-.R @@ -8,13 +8,14 @@ test_that("aesthetic checking in geom throws correct errors", { test_that("geom defaults can be set and reset", { l <- geom_point() + orig <- l$geom$default_aes$colour test <- l$geom$use_defaults(data_frame0()) expect_equal(test$colour, "black") inv <- update_geom_defaults("point", list(colour = "red")) test <- l$geom$use_defaults(data_frame0()) expect_equal(test$colour, "red") - expect_equal(inv$colour, "black") + expect_equal(inv$colour, orig) inv <- update_geom_defaults("point", NULL) test <- l$geom$use_defaults(data_frame0()) diff --git a/tests/testthat/test-stats.R b/tests/testthat/test-stats.R index b1acda601e..7e8967f679 100644 --- a/tests/testthat/test-stats.R +++ b/tests/testthat/test-stats.R @@ -47,7 +47,7 @@ test_that("erroneously dropped aesthetics are found and issue a warning", { # colour is dropped because group a's colour is not constant (GeomBar$default_aes$colour is NA) expect_true(all(is.na(b2$data[[1]]$colour))) # fill is dropped because group b's fill is not constant - expect_true(all(b2$data[[1]]$fill == GeomBar$default_aes$fill)) + expect_true(all(b2$data[[1]]$fill == "#595959FF")) # case 2-1) dropped partially with NA From 6185e824bd6cde8d7455fb74b37ee067373c5ffb Mon Sep 17 00:00:00 2001 From: Teun van den Brand Date: Mon, 29 Apr 2024 11:48:22 +0200 Subject: [PATCH 16/41] `geom_sf()` has themed defaults --- R/geom-sf.R | 6 +++++- 1 file changed, 5 insertions(+), 1 deletion(-) diff --git a/R/geom-sf.R b/R/geom-sf.R index cbeb2ad9dc..7cf713289c 100644 --- a/R/geom-sf.R +++ b/R/geom-sf.R @@ -164,7 +164,11 @@ GeomSf <- ggproto("GeomSf", Geom, } other_default <- modify_list( GeomPolygon$default_aes, - list(fill = "grey90", colour = "grey35", linewidth = 0.2) + aes( + fill = from_theme(col_mix(ink, paper, 0.9)), + colour = from_theme(col_mix(ink, paper, 0.35)), + linewidth = 0.2 + ) ) if (length(index$other) > 0) { others <- GeomPolygon$use_defaults( From df571c00cb5ff0a8f5874a317876706ae729b5f5 Mon Sep 17 00:00:00 2001 From: Teun van den Brand Date: Mon, 29 Apr 2024 11:53:15 +0200 Subject: [PATCH 17/41] we don't expect complete themes anymore --- tests/testthat/test-theme.R | 2 -- 1 file changed, 2 deletions(-) diff --git a/tests/testthat/test-theme.R b/tests/testthat/test-theme.R index 895d4cf9fc..8c090c05de 100644 --- a/tests/testthat/test-theme.R +++ b/tests/testthat/test-theme.R @@ -240,14 +240,12 @@ test_that("complete and non-complete themes interact correctly with ggplot objec expect_identical(pt, tt) p <- ggplot_build(base + theme(text = element_text(colour = 'red', face = 'italic'))) - expect_false(attr(p$plot$theme, "complete")) expect_equal(p$plot$theme$text$colour, "red") expect_equal(p$plot$theme$text$face, "italic") p <- ggplot_build(base + theme(text = element_text(colour = 'red')) + theme(text = element_text(face = 'italic'))) - expect_false(attr(p$plot$theme, "complete")) expect_equal(p$plot$theme$text$colour, "red") expect_equal(p$plot$theme$text$face, "italic") }) From 92d2bbb3bac9e773353dad5f0ab30c79f830131c Mon Sep 17 00:00:00 2001 From: Teun van den Brand Date: Tue, 30 Apr 2024 10:03:42 +0200 Subject: [PATCH 18/41] shim auto-replaces itself when exported from scales --- R/utilities.R | 16 ++++++++++++---- 1 file changed, 12 insertions(+), 4 deletions(-) diff --git a/R/utilities.R b/R/utilities.R index afeb606585..9933266c35 100644 --- a/R/utilities.R +++ b/R/utilities.R @@ -820,11 +820,19 @@ as_unordered_factor <- function(x) { } # Shim for scales/#424 -# TODO: prefer scales version over this one col_mix <- function(a, b, amount = 0.5) { input <- vec_recycle_common(a = a, b = b, amount = amount) - a <- col2rgb(input$a, TRUE) - b <- col2rgb(input$b, TRUE) + a <- grDevices::col2rgb(input$a, TRUE) + b <- grDevices::col2rgb(input$b, TRUE) new <- (a * (1 - input$amount) + b * input$amount) - rgb(new["red", ], new["green", ], new["blue", ], alpha = new["alpha", ], maxColorValue = 255) + grDevices::rgb( + new["red", ], new["green", ], new["blue", ], + alpha = new["alpha", ], maxColorValue = 255 + ) } + +on_load({ + if ("col_mix" %in% getNamespaceExports("scales")) { + col_mix <- scales::col_mix + } +}) From 124dd5f72215330832d8ec3b4f1ef03c672b7b39 Mon Sep 17 00:00:00 2001 From: Teun van den Brand Date: Tue, 30 Apr 2024 10:18:55 +0200 Subject: [PATCH 19/41] theme defaults for point size/shape --- R/geom-point.R | 4 ++-- R/geom-pointrange.R | 7 +++++-- R/theme-defaults.R | 18 ++++++++++++------ R/theme-elements.R | 10 +++++++--- 4 files changed, 26 insertions(+), 13 deletions(-) diff --git a/R/geom-point.R b/R/geom-point.R index 1e70ab5248..70f80f39ba 100644 --- a/R/geom-point.R +++ b/R/geom-point.R @@ -135,8 +135,8 @@ GeomPoint <- ggproto("GeomPoint", Geom, required_aes = c("x", "y"), non_missing_aes = c("size", "shape", "colour"), default_aes = aes( - shape = 19, - colour = from_theme(ink), size = 1.5, fill = NA, + shape = from_theme(pointshape), + colour = from_theme(ink), size = from_theme(pointsize), fill = NA, alpha = NA, stroke = 0.5 ), diff --git a/R/geom-pointrange.R b/R/geom-pointrange.R index 5d39685604..dd01d67cbc 100644 --- a/R/geom-pointrange.R +++ b/R/geom-pointrange.R @@ -30,8 +30,11 @@ geom_pointrange <- function(mapping = NULL, data = NULL, #' @usage NULL #' @export GeomPointrange <- ggproto("GeomPointrange", Geom, - default_aes = aes(colour = from_theme(ink), size = 0.5, linewidth = from_theme(thin), linetype = 1, - shape = 19, fill = NA, alpha = NA, stroke = 1), + default_aes = aes( + colour = from_theme(ink), size = from_theme(pointsize / 3), + linewidth = from_theme(thin), linetype = 1, + shape = 19, fill = NA, alpha = NA, stroke = 1 + ), draw_key = draw_key_pointrange, diff --git a/R/theme-defaults.R b/R/theme-defaults.R index 13553e7271..ef0c156471 100644 --- a/R/theme-defaults.R +++ b/R/theme-defaults.R @@ -134,9 +134,12 @@ theme_grey <- function(base_size = 11, base_family = "", margin = margin(), debug = FALSE ), - geom = element_geom(ink = "black", paper = "white", accent = "#3366FF", - thin = base_line_size, thick = base_line_size * 2, - family = base_family, fontsize = base_size), + geom = element_geom( + ink = "black", paper = "white", accent = "#3366FF", + thin = base_line_size, thick = base_line_size * 2, + family = base_family, fontsize = base_size, + pointsize = (base_size / 11) * 1.5, pointshape = 19 + ), axis.line = element_blank(), axis.line.x = NULL, @@ -547,9 +550,12 @@ theme_test <- function(base_size = 11, base_family = "", margin = margin(), debug = FALSE ), - geom = element_geom(ink = "black", paper = "white", accent = "#3366FF", - thin = base_line_size, thick = base_line_size * 2, - family = base_family, fontsize = base_size), + geom = element_geom( + ink = "black", paper = "white", accent = "#3366FF", + thin = base_line_size, thick = base_line_size * 2, + family = base_family, fontsize = base_size, + pointsize = (base_size / 11) * 1.5, pointshape = 19 + ), axis.line = element_blank(), axis.line.x = NULL, diff --git a/R/theme-elements.R b/R/theme-elements.R index 34a309e120..e77391e96c 100644 --- a/R/theme-elements.R +++ b/R/theme-elements.R @@ -150,7 +150,9 @@ element_geom <- function( # linewidth thin = NULL, thick = NULL, # text - family = NULL, fontsize = NULL + family = NULL, fontsize = NULL, + # points + pointsize = NULL, pointshape = NULL ) { if (!is.null(fontsize)) { @@ -163,7 +165,8 @@ element_geom <- function( paper = paper, accent = accent, thin = thin, thick = thick, - family = family, fontsize = fontsize + family = family, fontsize = fontsize, + pointsize = pointsize, pointshape = pointshape ), class = c("element_geom", "element") ) @@ -172,7 +175,8 @@ element_geom <- function( .default_geom_element <- element_geom( ink = "black", paper = "white", accent = "#3366FF", thin = 0.5, thick = 2, - family = "", fontsize = 11 + family = "", fontsize = 11, + pointsize = 1.5, pointshape = 19 ) #' @export From 0ff60780be293038107441471ae5b369c9cd90e5 Mon Sep 17 00:00:00 2001 From: Teun van den Brand Date: Tue, 30 Apr 2024 10:19:54 +0200 Subject: [PATCH 20/41] boxplot point shape/size default from `GeomBoxplot$default_aes` --- R/geom-boxplot.R | 17 ++++++++++------- 1 file changed, 10 insertions(+), 7 deletions(-) diff --git a/R/geom-boxplot.R b/R/geom-boxplot.R index 6e5a35f408..30262cbf92 100644 --- a/R/geom-boxplot.R +++ b/R/geom-boxplot.R @@ -117,8 +117,8 @@ geom_boxplot <- function(mapping = NULL, data = NULL, outlier.colour = NULL, outlier.color = NULL, outlier.fill = NULL, - outlier.shape = 19, - outlier.size = 1.5, + outlier.shape = NULL, + outlier.size = NULL, outlier.stroke = 0.5, outlier.alpha = NULL, notch = FALSE, @@ -223,8 +223,8 @@ GeomBoxplot <- ggproto("GeomBoxplot", Geom, draw_group = function(self, data, panel_params, coord, lineend = "butt", linejoin = "mitre", fatten = 2, outlier.colour = NULL, - outlier.fill = NULL, outlier.shape = 19, - outlier.size = 1.5, outlier.stroke = 0.5, + outlier.fill = NULL, outlier.shape = NULL, + outlier.size = NULL, outlier.stroke = 0.5, outlier.alpha = NULL, notch = FALSE, notchwidth = 0.5, staplewidth = 0, varwidth = FALSE, flipped_aes = FALSE) { data <- check_linewidth(data, snake_class(self)) @@ -327,9 +327,12 @@ GeomBoxplot <- ggproto("GeomBoxplot", Geom, draw_key = draw_key_boxplot, - default_aes = aes(weight = 1, colour = from_theme(col_mix(ink, paper, 0.2)), - fill = from_theme(paper), size = NULL, - alpha = NA, shape = 19, linetype = "solid", linewidth = from_theme(thin)), + default_aes = aes( + weight = 1, colour = from_theme(col_mix(ink, paper, 0.2)), + fill = from_theme(paper), size = from_theme(pointsize), + alpha = NA, shape = from_theme(pointshape), linetype = "solid", + linewidth = from_theme(thin) + ), required_aes = c("x|y", "lower|xlower", "upper|xupper", "middle|xmiddle", "ymin|xmin", "ymax|xmax"), From 2dd3f37492790ad1b0be525b74f12e5d1203943a Mon Sep 17 00:00:00 2001 From: Teun van den Brand Date: Tue, 30 Apr 2024 10:20:47 +0200 Subject: [PATCH 21/41] accept larger points in large theme snapshots --- tests/testthat/_snaps/theme/theme-bw-large.svg | 10 +++++----- tests/testthat/_snaps/theme/theme-classic-large.svg | 10 +++++----- tests/testthat/_snaps/theme/theme-dark-large.svg | 10 +++++----- tests/testthat/_snaps/theme/theme-gray-large.svg | 10 +++++----- tests/testthat/_snaps/theme/theme-light-large.svg | 10 +++++----- tests/testthat/_snaps/theme/theme-linedraw-large.svg | 10 +++++----- tests/testthat/_snaps/theme/theme-minimal-large.svg | 10 +++++----- 7 files changed, 35 insertions(+), 35 deletions(-) diff --git a/tests/testthat/_snaps/theme/theme-bw-large.svg b/tests/testthat/_snaps/theme/theme-bw-large.svg index 148d1a93ca..14cfad040c 100644 --- a/tests/testthat/_snaps/theme/theme-bw-large.svg +++ b/tests/testthat/_snaps/theme/theme-bw-large.svg @@ -45,9 +45,9 @@ - - - + + + @@ -87,9 +87,9 @@ z - + - + a b theme_bw_large diff --git a/tests/testthat/_snaps/theme/theme-classic-large.svg b/tests/testthat/_snaps/theme/theme-classic-large.svg index 96767cc14f..fcc87d6c8c 100644 --- a/tests/testthat/_snaps/theme/theme-classic-large.svg +++ b/tests/testthat/_snaps/theme/theme-classic-large.svg @@ -27,9 +27,9 @@ - - - + + + @@ -70,9 +70,9 @@ z - + - + a b theme_classic_large diff --git a/tests/testthat/_snaps/theme/theme-dark-large.svg b/tests/testthat/_snaps/theme/theme-dark-large.svg index 9bad950947..6abbde1c37 100644 --- a/tests/testthat/_snaps/theme/theme-dark-large.svg +++ b/tests/testthat/_snaps/theme/theme-dark-large.svg @@ -45,9 +45,9 @@ - - - + + + @@ -86,9 +86,9 @@ z - + - + a b theme_dark_large diff --git a/tests/testthat/_snaps/theme/theme-gray-large.svg b/tests/testthat/_snaps/theme/theme-gray-large.svg index a827864db6..0e3a1f9408 100644 --- a/tests/testthat/_snaps/theme/theme-gray-large.svg +++ b/tests/testthat/_snaps/theme/theme-gray-large.svg @@ -45,9 +45,9 @@ - - - + + + @@ -86,9 +86,9 @@ z - + - + a b theme_gray_large diff --git a/tests/testthat/_snaps/theme/theme-light-large.svg b/tests/testthat/_snaps/theme/theme-light-large.svg index 727f55ae02..9a68882e46 100644 --- a/tests/testthat/_snaps/theme/theme-light-large.svg +++ b/tests/testthat/_snaps/theme/theme-light-large.svg @@ -45,9 +45,9 @@ - - - + + + @@ -87,9 +87,9 @@ z - + - + a b theme_light_large diff --git a/tests/testthat/_snaps/theme/theme-linedraw-large.svg b/tests/testthat/_snaps/theme/theme-linedraw-large.svg index 66998cd898..1702cbee8f 100644 --- a/tests/testthat/_snaps/theme/theme-linedraw-large.svg +++ b/tests/testthat/_snaps/theme/theme-linedraw-large.svg @@ -45,9 +45,9 @@ - - - + + + @@ -87,9 +87,9 @@ z - + - + a b theme_linedraw_large diff --git a/tests/testthat/_snaps/theme/theme-minimal-large.svg b/tests/testthat/_snaps/theme/theme-minimal-large.svg index 4673e9cc60..e58faabda9 100644 --- a/tests/testthat/_snaps/theme/theme-minimal-large.svg +++ b/tests/testthat/_snaps/theme/theme-minimal-large.svg @@ -43,9 +43,9 @@ - - - + + + @@ -71,8 +71,8 @@ x y z - - + + a b theme_minimal_large From 377a82c752de7999fd47cf0ff5182e4355248793 Mon Sep 17 00:00:00 2001 From: Teun van den Brand Date: Tue, 30 Apr 2024 10:30:40 +0200 Subject: [PATCH 22/41] document --- NAMESPACE | 1 + R/theme-elements.R | 19 ++++++++++++++++++- R/theme.R | 1 + man/element.Rd | 36 +++++++++++++++++++++++++++++++++++- man/geom_boxplot.Rd | 4 ++-- man/theme.Rd | 2 ++ 6 files changed, 59 insertions(+), 4 deletions(-) diff --git a/NAMESPACE b/NAMESPACE index 3a0ebd0af4..0494fb23ae 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -342,6 +342,7 @@ export(draw_key_vpath) export(dup_axis) export(el_def) export(element_blank) +export(element_geom) export(element_grob) export(element_line) export(element_rect) diff --git a/R/theme-elements.R b/R/theme-elements.R index e77391e96c..b00b08855c 100644 --- a/R/theme-elements.R +++ b/R/theme-elements.R @@ -8,6 +8,7 @@ #' - `element_rect()`: borders and backgrounds. #' - `element_line()`: lines. #' - `element_text()`: text. +#' - `element_geom()`: defaults for drawing layers. #' #' `rel()` is used to specify sizes relative to the parent, #' `margin()` is used to specify the margins of elements. @@ -15,7 +16,7 @@ #' @param fill Fill colour. #' @param colour,color Line/border colour. Color is an alias for colour. #' @param linewidth Line/border size in mm. -#' @param size text size in pts. +#' @param size,fontsize text size in pts. #' @param inherit.blank Should this element inherit the existence of an #' `element_blank` among its parents? If `TRUE` the existence of #' a blank element among its parents will cause this element to be blank as @@ -47,6 +48,14 @@ #' linewidth = 1 #' ) #' ) +#' +#' ggplot(mpg, aes(displ, hwy)) + +#' geom_point() + +#' geom_smooth(formula = y ~ x, method = "lm") + +#' theme(geom = element_geom( +#' ink = "red", accent = "black", +#' pointsize = 1, thick = 2 +#' )) #' @name element #' @aliases NULL NULL @@ -144,6 +153,14 @@ element_text <- function(family = NULL, face = NULL, colour = NULL, ) } +#' @param ink Foreground colour. +#' @param paper Background colour. +#' @param accent Accent colour. +#' @param thin,thick Linewidth for thin and thick lines in mm. +#' @param pointsize Size for points in mm. +#' @param pointshape Shape for points (1-25). +#' @export +#' @rdname element element_geom <- function( # colours ink = NULL, paper = NULL, accent = NULL, diff --git a/R/theme.R b/R/theme.R index 14e346c013..d1e48cae56 100644 --- a/R/theme.R +++ b/R/theme.R @@ -25,6 +25,7 @@ #' @param text all text elements ([element_text()]) #' @param title all title elements: plot, axes, legends ([element_text()]; #' inherits from `text`) +#' @param geom defaults for geoms ([element_geom()]) #' @param aspect.ratio aspect ratio of the panel #' #' @param axis.title,axis.title.x,axis.title.y,axis.title.x.top,axis.title.x.bottom,axis.title.y.left,axis.title.y.right diff --git a/man/element.Rd b/man/element.Rd index a3c27a259c..3945db465b 100644 --- a/man/element.Rd +++ b/man/element.Rd @@ -5,6 +5,7 @@ \alias{element_rect} \alias{element_line} \alias{element_text} +\alias{element_geom} \alias{rel} \alias{margin} \title{Theme elements} @@ -47,6 +48,18 @@ element_text( inherit.blank = FALSE ) +element_geom( + ink = NULL, + paper = NULL, + accent = NULL, + thin = NULL, + thick = NULL, + family = NULL, + fontsize = NULL, + pointsize = NULL, + pointshape = NULL +) + rel(x) margin(t = 0, r = 0, b = 0, l = 0, unit = "pt") @@ -69,7 +82,7 @@ a blank element among its parents will cause this element to be blank as well. If \code{FALSE} any blank parent element will be ignored when calculating final element state.} -\item{size}{text size in pts.} +\item{size, fontsize}{text size in pts.} \item{lineend}{Line end Line end style (round, butt, square)} @@ -95,6 +108,18 @@ side of the text facing towards the center of the plot.} rectangle behind the complete text area, and a point where each label is anchored.} +\item{ink}{Foreground colour.} + +\item{paper}{Background colour.} + +\item{accent}{Accent colour.} + +\item{thin, thick}{Linewidth for thin and thick lines in mm.} + +\item{pointsize}{Size for points in mm.} + +\item{pointshape}{Shape for points (1-25).} + \item{x}{A single number specifying size relative to parent element.} \item{t, r, b, l}{Dimensions of each margin. (To remember order, think trouble).} @@ -113,6 +138,7 @@ specify the display of how non-data components of the plot are drawn. \item \code{element_rect()}: borders and backgrounds. \item \code{element_line()}: lines. \item \code{element_text()}: text. +\item \code{element_geom()}: defaults for drawing layers. } \code{rel()} is used to specify sizes relative to the parent, @@ -143,4 +169,12 @@ plot + theme( linewidth = 1 ) ) + +ggplot(mpg, aes(displ, hwy)) + + geom_point() + + geom_smooth(formula = y ~ x, method = "lm") + + theme(geom = element_geom( + ink = "red", accent = "black", + pointsize = 1, thick = 2 + )) } diff --git a/man/geom_boxplot.Rd b/man/geom_boxplot.Rd index e995aa6635..d2aa1d06e3 100644 --- a/man/geom_boxplot.Rd +++ b/man/geom_boxplot.Rd @@ -15,8 +15,8 @@ geom_boxplot( outlier.colour = NULL, outlier.color = NULL, outlier.fill = NULL, - outlier.shape = 19, - outlier.size = 1.5, + outlier.shape = NULL, + outlier.size = NULL, outlier.stroke = 0.5, outlier.alpha = NULL, notch = FALSE, diff --git a/man/theme.Rd b/man/theme.Rd index db1576c67a..52a6effd3e 100644 --- a/man/theme.Rd +++ b/man/theme.Rd @@ -160,6 +160,8 @@ these should also be defined in the \verb{element tree} argument. \link[rlang:sp \item{title}{all title elements: plot, axes, legends (\code{\link[=element_text]{element_text()}}; inherits from \code{text})} +\item{geom}{defaults for geoms (\code{\link[=element_geom]{element_geom()}})} + \item{aspect.ratio}{aspect ratio of the panel} \item{axis.title, axis.title.x, axis.title.y, axis.title.x.top, axis.title.x.bottom, axis.title.y.left, axis.title.y.right}{labels of axes (\code{\link[=element_text]{element_text()}}). Specify all axes' labels (\code{axis.title}), From e584978eda5d18a64d5de8fe9586b68e9cc564ff Mon Sep 17 00:00:00 2001 From: Teun van den Brand Date: Tue, 30 Apr 2024 10:37:27 +0200 Subject: [PATCH 23/41] Point to theme setting in `update_geom_defaults()` --- R/geom-defaults.R | 3 +++ man/update_defaults.Rd | 4 ++++ 2 files changed, 7 insertions(+) diff --git a/R/geom-defaults.R b/R/geom-defaults.R index 8b81eeef94..55d019b886 100644 --- a/R/geom-defaults.R +++ b/R/geom-defaults.R @@ -7,6 +7,9 @@ #' * A named list of aesthetics to serve as new defaults. #' * `NULL` to reset the defaults. #' @keywords internal +#' @note +#' Please note that geom defaults can be set *en masse* via the `theme(geom)` +#' argument. #' @export #' @examples #' diff --git a/man/update_defaults.Rd b/man/update_defaults.Rd index 8006bf8246..3aaed3f5ac 100644 --- a/man/update_defaults.Rd +++ b/man/update_defaults.Rd @@ -23,6 +23,10 @@ update_stat_defaults(stat, new) \description{ Modify geom/stat aesthetic defaults for future plots } +\note{ +Please note that geom defaults can be set \emph{en masse} via the \code{theme(geom)} +argument. +} \examples{ # updating a geom's default aesthetic settings From 1143a9f6d23db721a6c3cc85dfb24552c1953731 Mon Sep 17 00:00:00 2001 From: Teun van den Brand Date: Tue, 30 Apr 2024 10:59:14 +0200 Subject: [PATCH 24/41] document `from_theme()` --- R/aes-evaluation.R | 8 +++++++- man/aes_eval.Rd | 8 ++++++++ 2 files changed, 15 insertions(+), 1 deletion(-) diff --git a/R/aes-evaluation.R b/R/aes-evaluation.R index 69dc8ca4a0..1a27f5cfef 100644 --- a/R/aes-evaluation.R +++ b/R/aes-evaluation.R @@ -109,6 +109,13 @@ #' fun.data = ~ round(data.frame(mean = mean(.x), sd = sd(.x)), 2) #' ) #' ``` +#' +#' ## Theme access +#' The `from_theme()` function can be used to acces the [`element_geom()`] +#' fields of the `theme(geom)` argument. Using `aes(colour = from_theme(ink))` +#' and `aes(colour = from_theme(accent))` allows swapping between foreground and +#' accent colours. +#' #' @rdname aes_eval #' @name aes_eval #' @@ -196,7 +203,6 @@ after_scale <- function(x) { #' @rdname aes_eval #' @export from_theme <- function(x) { - # TODO: This is just a placeholder x } diff --git a/man/aes_eval.Rd b/man/aes_eval.Rd index 40b80dfc56..11b8d2f1bd 100644 --- a/man/aes_eval.Rd +++ b/man/aes_eval.Rd @@ -130,6 +130,14 @@ ggplot(mpg, aes(class, displ)) + ) }\if{html}{\out{}} } + +\subsection{Theme access}{ + +The \code{from_theme()} function can be used to acces the \code{\link[=element_geom]{element_geom()}} +fields of the \code{theme(geom)} argument. Using \code{aes(colour = from_theme(ink))} +and \code{aes(colour = from_theme(accent))} allows swapping between foreground and +accent colours. +} } \examples{ From afca7813eaa90b26d70576afdf1de59f6dceef87 Mon Sep 17 00:00:00 2001 From: Teun van den Brand Date: Tue, 30 Apr 2024 10:59:22 +0200 Subject: [PATCH 25/41] add news bullet --- NEWS.md | 6 ++++++ 1 file changed, 6 insertions(+) diff --git a/NEWS.md b/NEWS.md index 070c74dd40..2909f301f3 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,5 +1,11 @@ # ggplot2 (development version) +* (Breaking) The defaults for all geoms can be set at one in the theme. + (@teunbrand based on pioneering work by @dpseidel, #2239) + * A new `theme(geom)` argument is used to track these defaults. + * The `element_geom()` function can be used to populate that argument. + * The `from_theme()` function allows access to the theme default fields from + inside the `aes()` function. * (Internal) Applying defaults in `geom_sf()` has moved from the internal `sf_grob()` to `GeomSf$use_defaults()` (@teunbrand). * `facet_wrap()` has new options for the `dir` argument to more precisely From f0b42793583806d78ae3c8b5a122279388626bab Mon Sep 17 00:00:00 2001 From: Teun van den Brand <49372158+teunbrand@users.noreply.github.com> Date: Tue, 30 Apr 2024 14:28:14 +0200 Subject: [PATCH 26/41] Update R/geom-pointrange.R Co-authored-by: Thomas Lin Pedersen --- R/geom-pointrange.R | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/R/geom-pointrange.R b/R/geom-pointrange.R index dd01d67cbc..649928d2e6 100644 --- a/R/geom-pointrange.R +++ b/R/geom-pointrange.R @@ -33,7 +33,7 @@ GeomPointrange <- ggproto("GeomPointrange", Geom, default_aes = aes( colour = from_theme(ink), size = from_theme(pointsize / 3), linewidth = from_theme(thin), linetype = 1, - shape = 19, fill = NA, alpha = NA, stroke = 1 + shape = from_theme(pointshape), fill = NA, alpha = NA, stroke = 1 ), draw_key = draw_key_pointrange, From b0251f3d2c9bfc22d161d925f8237c38fab792c4 Mon Sep 17 00:00:00 2001 From: Thomas Lin Pedersen Date: Wed, 15 May 2024 13:05:36 +0200 Subject: [PATCH 27/41] Run revdepcheck --- revdep/README.md | 373 +- revdep/cran.md | 883 +++- revdep/failures.md | 8765 +++++++++++++++++++++++++++++++-- revdep/problems.md | 11234 ++++++++++++++++++++++++++++++++++++++++++- 4 files changed, 20637 insertions(+), 618 deletions(-) diff --git a/revdep/README.md b/revdep/README.md index b6eff473f2..e4e8a84654 100644 --- a/revdep/README.md +++ b/revdep/README.md @@ -1,34 +1,351 @@ # Revdeps -## Failed to check (17) +## Failed to check (135) -|package |version |error |warning |note | -|:----------------|:-------|:-----|:-------|:----| -|bayesdfa |1.3.3 |1 | | | -|bmgarch |2.0.0 |1 | | | -|ctsem |3.9.1 |1 | | | -|EcoEnsemble |1.0.5 |1 | | | -|geostan |0.5.4 |1 | | | -|grandR |? | | | | -|multilevelcoda |1.2.3 |1 | | | -|multinma |0.6.1 |1 | | | -|rmsb |1.1-0 |1 | | | -|rstanarm |2.32.1 |1 | | | -|Seurat |? | | | | -|streamDAG |? | | | | -|treestats |1.0.5 |1 | | | -|TriDimRegression |1.0.2 |1 | | | -|triptych |0.1.2 |1 | | | -|ubms |1.2.6 |1 | | | -|valse |0.1-0 |1 | | | +|package |version |error |warning |note | +|:----------------------|:----------|:------|:-------|:----| +|abctools |1.1.7 |1 | | | +|animalEKF |1.2 |1 | | | +|ANOM |0.5 |1 | | | +|atRisk |0.1.0 |1 | | | +|AutoScore |1.0.0 |1 | | | +|bayesdfa |1.3.3 |1 | | | +|bayesDP |1.3.6 |1 | | | +|BayesianFactorZoo |0.0.0.2 |1 | | | +|BayesSurvive |0.0.1 |1 | | | +|BCClong |1.0.2 |1 | |1 | +|binsreg |1.0 |1 | | | +|bmgarch |2.0.0 |1 | | | +|bmstdr |0.7.9 |1 | | | +|bspcov |1.0.0 |1 | | | +|BuyseTest |3.0.2 |1 | | | +|CalibrationCurves |2.0.1 |1 | | | +|CARBayesST |4.0 |1 | | | +|CaseBasedReasoning |0.3 |1 | | | +|CGPfunctions |0.6.3 |1 | | | +|cmprskcoxmsm |0.2.1 |1 | | | +|contrast |0.24.2 |1 | | | +|coxed |0.3.3 |1 | | | +|CRMetrics |0.3.0 |1 | | | +|csmpv |1.0.3 |1 | | | +|ctsem |3.9.1 |1 | | | +|DepthProc |2.1.5 |1 | | | +|DR.SC |3.4 |1 | | | +|EcoEnsemble |1.0.5 |1 | | | +|ecolottery |1.0.0 |1 | | | +|EpiEstim |2.2-4 |1 | | | +|evolqg |0.3-4 |1 | | | +|ForecastComb |1.3.1 |1 | | | +|gapfill |0.9.6-1 |1 | |1 | +|GeomComb |1.0 |1 | | | +|geostan |0.6.0 |1 | | | +|ggpmisc |0.5.5 |1 | | | +|ggrcs |0.3.8 |1 | | | +|ggrisk |1.3 |1 | | | +|gJLS2 |0.2.0 |1 | | | +|Greg |2.0.2 |1 | | | +|greport |0.7-4 |1 | | | +|hettx |0.1.3 |1 | | | +|hIRT |0.3.0 |1 | | | +|Hmsc |3.0-13 |1 | | | +|[inventorize](failures.md#inventorize)|1.1.1 |__+1__ | | | +|iNZightPlots |2.15.3 |1 | | | +|iNZightRegression |1.3.4 |1 | | | +|IRexamples |0.0.4 |1 | | | +|joineRML |0.4.6 |1 | | | +|JWileymisc |1.4.1 |1 | | | +|kmc |0.4-2 |1 | | | +|L2E |2.0 |1 | | | +|llbayesireg |1.0.0 |1 | | | +|LorenzRegression |1.0.0 |1 | | | +|lsirm12pl |1.3.1 |1 | | | +|mbsts |3.0 |1 | | | +|MendelianRandomization |0.10.0 |1 | | | +|MetabolicSurv |1.1.2 |1 | | | +|miWQS |0.4.4 |1 | | | +|mlmts |1.1.1 |1 | | | +|MRZero |0.2.0 |1 | | | +|Multiaovbay |0.1.0 |1 | | | +|multilevelTools |0.1.1 |1 | | | +|multinma |0.6.1 |1 | | | +|NCA |4.0.1 |1 | | | +|netcmc |1.0.2 |1 | | | +|NetworkChange |0.8 |1 | | | +|nlmeVPC |2.6 |1 | | | +|NMADiagT |0.1.2 |1 | | | +|optweight |0.2.5 |1 | | | +|OVtool |1.0.3 |1 | | | +|paths |0.1.1 |1 | | | +|PLMIX |2.1.1 |1 | | | +|popstudy |1.0.1 |1 | | | +|pould |1.0.1 |1 | | | +|powerly |1.8.6 |1 | | | +|pre |1.0.7 |1 | | | +|ProFAST |? | | | | +|psbcSpeedUp |2.0.6 |1 | | | +|pscore |0.4.0 |1 | | | +|psfmi |1.4.0 |1 | | | +|qPCRtools |1.0.1 |1 | | | +|qreport |1.0-0 |1 | | | +|qris |1.1.1 |1 | | | +|qte |1.3.1 |1 | | | +|quid |0.0.1 |1 | | | +|RATest |0.1.10 |1 | | | +|RcmdrPlugin.RiskDemo |3.2 |1 | | | +|rddtools |1.6.0 |1 | | | +|riskRegression |2023.12.21 |1 | | | +|rms |6.8-0 |1 | |1 | +|rmsb |1.1-0 |1 | | | +|robmed |1.0.2 |1 | | | +|robmedExtra |0.1.0 |1 | | | +|RPPanalyzer |1.4.9 |1 | | | +|RQdeltaCT |1.3.0 |1 | | | +|rstanarm |2.32.1 |1 | | | +|scCustomize |2.1.2 |1 | |1 | +|SCdeconR |1.0.0 |1 | | | +|scGate |1.6.2 |1 | | | +|scMappR |1.0.11 |1 | | | +|scRNAstat |0.1.1 |1 | | | +|sectorgap |0.1.0 |1 | | | +|SEERaBomb |2019.2 |1 | | | +|semicmprskcoxmsm |0.2.0 |1 | | | +|SensMap |0.7 |1 | | | +|Seurat |5.0.3 |1 | | | +|shinyTempSignal |0.0.8 |1 | | | +|Signac |1.13.0 |1 | | | +|SimplyAgree |0.2.0 |1 | | | +|sMSROC |0.1.2 |1 | | | +|SNPassoc |2.1-0 |1 | | | +|snplinkage |? | | | | +|SoupX |1.6.2 |1 | | | +|sparsereg |1.2 |1 | | | +|spikeSlabGAM |1.1-19 |1 | | | +|statsr |0.3.0 |1 | | | +|streamDAG |? | | | | +|survHE |2.0.1 |1 | |1 | +|survidm |1.3.2 |1 | | | +|tempted |0.1.0 |1 | | | +|[tidydr](failures.md#tidydr)|0.0.5 |__+1__ | | | +|tidyEdSurvey |0.1.2 |1 | | | +|tidyseurat |0.8.0 |1 | | | +|tidyvpc |1.5.1 |1 | | | +|treestats |1.0.5 |1 | | | +|TriDimRegression |1.0.2 |1 | | | +|triptych |0.1.2 |1 | | | +|TSrepr |1.1.0 |1 | | | +|twang |2.6 |1 | | | +|ubms |1.2.6 |1 | | | +|valse |0.1-0 |1 | | | +|vdg |1.2.3 |1 | | | +|visa |0.1.0 |1 | | | +|WRTDStidal |1.1.4 |1 | | | -## New problems (5) +## New problems (204) -|package |version |error |warning |note | -|:----------------------|:-------|:------|:-------|:------| -|[ggh4x](problems.md#ggh4x)|0.2.8 |__+3__ | | | -|[MplusAutomation](problems.md#mplusautomation)|1.1.1 | | |__+1__ | -|[PlasmaMutationDetector](problems.md#plasmamutationdetector)|1.7.2 | | |__+1__ | -|[Superpower](problems.md#superpower)|0.2.0 |__+1__ | |1 | -|[xaringanthemer](problems.md#xaringanthemer)|0.4.2 |__+1__ | | | +|package |version |error |warning |note | +|:------------------|:--------|:--------|:--------|:--------| +|[actxps](problems.md#actxps)|1.4.0 |__+1__ | |__+1__ | +|[AeRobiology](problems.md#aerobiology)|2.0.1 |1 | |__+1__ | +|[afex](problems.md#afex)|1.3-1 |__+1__ | |__+1__ | +|[agricolaeplotr](problems.md#agricolaeplotr)|0.5.0 |__+1__ | | | +|[ammistability](problems.md#ammistability)|0.1.4 |__+1__ |-1 | | +|[AnalysisLin](problems.md#analysislin)|0.1.2 |__+1__ | | | +|[animbook](problems.md#animbook)|1.0.0 |__+1__ | | | +|[aopdata](problems.md#aopdata)|1.0.3 |__+1__ | |__+1__ | +|[ARPALData](problems.md#arpaldata)|1.5.2 |__+1__ | | | +|[asmbPLS](problems.md#asmbpls)|1.0.0 | |__+1__ |1 | +|[autoplotly](problems.md#autoplotly)|0.1.4 |__+2__ | | | +|[BayesGrowth](problems.md#bayesgrowth)|1.0.0 |__+1__ | |2 __+1__ | +|[bdl](problems.md#bdl)|1.0.5 | |__+1__ | | +|[BeeBDC](problems.md#beebdc)|1.1.1 |1 __+2__ | |1 | +|[blockCV](problems.md#blockcv)|3.1-3 |1 |1 |1 __+1__ | +|[boxly](problems.md#boxly)|0.1.1 |__+1__ | | | +|[bSi](problems.md#bsi)|1.0.0 | |__+1__ | | +|[cartograflow](problems.md#cartograflow)|1.0.5 |__+1__ | | | +|[cats](problems.md#cats)|1.0.2 |__+1__ | |1 | +|[cheem](problems.md#cheem)|0.4.0.0 |1 __+1__ | | | +|[chronicle](problems.md#chronicle)|0.3 |__+2__ | |1 __+1__ | +|[clinDataReview](problems.md#clindatareview)|1.5.1 |__+2__ | |1 __+1__ | +|[clinUtils](problems.md#clinutils)|0.1.5 |__+1__ |-1 |1 __+1__ | +|[ClusROC](problems.md#clusroc)|1.0.2 | |__+1__ | | +|[clustEff](problems.md#clusteff)|0.3.1 | |__+1__ | | +|[coda4microbiome](problems.md#coda4microbiome)|0.2.3 | |__+1__ | | +|[CohortPlat](problems.md#cohortplat)|1.0.5 |__+2__ | |__+1__ | +|[CompAREdesign](problems.md#comparedesign)|2.3.1 | |__+1__ | | +|[CoreMicrobiomeR](problems.md#coremicrobiomer)|0.1.0 |__+1__ | | | +|[correlationfunnel](problems.md#correlationfunnel)|0.2.0 |__+1__ | |1 | +|[corrViz](problems.md#corrviz)|0.1.0 |__+2__ | |1 __+1__ | +|[covidcast](problems.md#covidcast)|0.5.2 |__+2__ | |1 __+1__ | +|[Coxmos](problems.md#coxmos)|1.0.2 |1 |__+1__ |1 | +|[crosshap](problems.md#crosshap)|1.4.0 |__+1__ | | | +|[csa](problems.md#csa)|0.7.1 | |__+1__ | | +|[ctrialsgov](problems.md#ctrialsgov)|0.2.5 |__+1__ | |1 | +|[cubble](problems.md#cubble)|0.3.0 |__+1__ | |1 __+1__ | +|[dafishr](problems.md#dafishr)|1.0.0 |__+1__ | |2 | +|[damAOI](problems.md#damaoi)|0.0 |__+1__ | |__+1__ | +|[deeptime](problems.md#deeptime)|1.1.1 |__+2__ | | | +|[DEGRE](problems.md#degre)|0.2.0 | |__+1__ | | +|[densityarea](problems.md#densityarea)|0.1.0 |1 | |1 __+1__ | +|[did](problems.md#did)|2.1.2 | |1 __+1__ | | +|[distributional](problems.md#distributional)|0.4.0 |__+1__ | | | +|[dittoViz](problems.md#dittoviz)|1.0.1 |__+2__ | | | +|[dots](problems.md#dots)|0.0.2 |__+2__ | |1 __+1__ | +|[eks](problems.md#eks)|1.0.5 |__+2__ | |__+1__ | +|[entropart](problems.md#entropart)|1.6-13 |__+2__ | |__+1__ | +|[epiCleanr](problems.md#epicleanr)|0.2.0 |__+1__ | |1 | +|[epiR](problems.md#epir)|2.0.74 |__+1__ | |__+1__ | +|[esci](problems.md#esci)|1.0.2 |__+2__ | | | +|[evalITR](problems.md#evalitr)|1.0.0 |1 | |1 __+1__ | +|[explainer](problems.md#explainer)|1.0.1 |__+1__ | |1 | +|[fable.prophet](problems.md#fableprophet)|0.1.0 |__+1__ | |1 __+1__ | +|[fabletools](problems.md#fabletools)|0.4.2 |__+2__ | | | +|[ffp](problems.md#ffp)|0.2.2 |__+1__ | | | +|[fido](problems.md#fido)|1.0.4 |__+1__ | |1 | +|[flipr](problems.md#flipr)|0.3.3 |1 | |1 __+1__ | +|[fmesher](problems.md#fmesher)|0.1.5 |__+1__ | |1 | +|[forestecology](problems.md#forestecology)|0.2.0 |__+2__ | |1 __+1__ | +|[frailtyEM](problems.md#frailtyem)|1.0.1 |__+1__ | |2 | +|[FuncNN](problems.md#funcnn)|1.0 | |__+1__ |1 | +|[geomander](problems.md#geomander)|2.3.0 |__+2__ | |1 __+1__ | +|[geomtextpath](problems.md#geomtextpath)|0.1.3 |__+2__ | | | +|[germinationmetrics](problems.md#germinationmetrics)|0.1.8 |__+1__ |-1 | | +|[gganimate](problems.md#gganimate)|1.0.9 |__+2__ | |__+1__ | +|[ggautomap](problems.md#ggautomap)|0.3.2 |__+2__ | |__+1__ | +|[ggdark](problems.md#ggdark)|0.2.1 |__+2__ | |1 | +|[ggdist](problems.md#ggdist)|3.3.2 |1 __+2__ | |1 __+1__ | +|[ggedit](problems.md#ggedit)|0.4.1 |__+1__ | | | +|[ggfixest](problems.md#ggfixest)|0.1.0 |1 __+1__ | | | +|[ggfortify](problems.md#ggfortify)|0.4.17 |__+1__ | | | +|[ggh4x](problems.md#ggh4x)|0.2.8 |1 __+2__ | |__+1__ | +|[ggheatmap](problems.md#ggheatmap)|2.2 | |__+1__ | | +|[gghighlight](problems.md#gghighlight)|0.4.1 |__+3__ | |__+1__ | +|[ggiraph](problems.md#ggiraph)|0.8.9 |__+2__ | |1 | +|[ggmice](problems.md#ggmice)|0.1.0 |__+1__ | |__+1__ | +|[ggmulti](problems.md#ggmulti)|1.0.7 |__+3__ | |__+1__ | +|[ggparallel](problems.md#ggparallel)|0.4.0 |__+1__ | | | +|[ggplotlyExtra](problems.md#ggplotlyextra)|0.0.1 |__+1__ | |1 | +|[ggpol](problems.md#ggpol)|0.0.7 |__+1__ | |2 | +|[ggraph](problems.md#ggraph)|2.2.1 |1 __+1__ | |1 __+1__ | +|[ggredist](problems.md#ggredist)|0.0.2 |__+1__ | | | +|[ggResidpanel](problems.md#ggresidpanel)|0.3.0 |__+2__ | |__+1__ | +|[ggScatRidges](problems.md#ggscatridges)|0.1.1 | |__+1__ | | +|[ggseqplot](problems.md#ggseqplot)|0.8.3 |__+3__ | |__+1__ | +|[ggside](problems.md#ggside)|0.3.1 | |__+1__ | | +|[ggtern](problems.md#ggtern)|3.5.0 |__+1__ | |2 | +|[ggVennDiagram](problems.md#ggvenndiagram)|1.5.2 |__+1__ | |1 __+1__ | +|[GIFT](problems.md#gift)|1.3.2 |1 | |1 __+1__ | +|[GimmeMyPlot](problems.md#gimmemyplot)|0.1.0 | |__+1__ | | +|[gprofiler2](problems.md#gprofiler2)|0.2.3 |__+2__ | |__+1__ | +|[Greymodels](problems.md#greymodels)|2.0.1 |__+1__ | | | +|[h3jsr](problems.md#h3jsr)|1.3.1 |__+1__ | |__+1__ | +|[healthyR](problems.md#healthyr)|0.2.1 |__+1__ | |1 __+1__ | +|[healthyR.ai](problems.md#healthyrai)|0.0.13 |__+2__ | |__+1__ | +|[healthyR.ts](problems.md#healthyrts)|0.3.0 |__+2__ | |1 __+1__ | +|[heatmaply](problems.md#heatmaply)|1.5.0 |__+2__ | |1 __+1__ | +|[hilldiv](problems.md#hilldiv)|1.5.1 | |__+1__ | | +|[hJAM](problems.md#hjam)|1.0.0 | |__+1__ | | +|[HVT](problems.md#hvt)|23.11.1 |__+1__ | | | +|[HYPEtools](problems.md#hypetools)|1.6.1 |__+1__ | |__+1__ | +|[ImFoR](problems.md#imfor)|0.1.0 | |__+1__ | | +|[iNEXT.4steps](problems.md#inext4steps)|1.0.0 | |__+1__ | | +|[insane](problems.md#insane)|1.0.3 | |__+1__ | | +|[inTextSummaryTable](problems.md#intextsummarytable)|3.3.2 |1 __+1__ | |1 __+1__ | +|[itsdm](problems.md#itsdm)|0.2.1 |__+1__ | | | +|[karel](problems.md#karel)|0.1.1 |__+2__ | |1 | +|[latentcor](problems.md#latentcor)|2.0.1 |__+1__ | |1 | +|[mapSpain](problems.md#mapspain)|0.9.0 |1 __+1__ | |2 | +|[MBNMAdose](problems.md#mbnmadose)|0.4.3 |__+1__ | |1 __+1__ | +|[MBNMAtime](problems.md#mbnmatime)|0.2.4 |1 | |__+1__ | +|[mc2d](problems.md#mc2d)|0.2.0 | |__+1__ |1 | +|[MetaIntegrator](problems.md#metaintegrator)|2.1.3 | |__+1__ |2 | +|[MF.beta4](problems.md#mfbeta4)|1.0.3 | |1 __+1__ | | +|[MiMIR](problems.md#mimir)|1.5 |__+1__ | | | +|[miRetrieve](problems.md#miretrieve)|1.3.4 |__+1__ | | | +|[missingHE](problems.md#missinghe)|1.5.0 | |__+1__ |1 | +|[misspi](problems.md#misspi)|0.1.0 |__+1__ | | | +|[mlr3spatiotempcv](problems.md#mlr3spatiotempcv)|2.3.1 |1 __+2__ | |1 | +|[modeltime.resample](problems.md#modeltimeresample)|0.2.3 |__+1__ | |1 | +|[MSPRT](problems.md#msprt)|3.0 | |__+1__ |1 | +|[neatmaps](problems.md#neatmaps)|2.1.0 |__+1__ | |1 | +|[NetFACS](problems.md#netfacs)|0.5.0 |__+2__ | | | +|[NIMAA](problems.md#nimaa)|0.2.1 |__+3__ | |2 __+1__ | +|[nswgeo](problems.md#nswgeo)|0.4.0 |__+1__ | |1 | +|[OenoKPM](problems.md#oenokpm)|2.4.1 | |__+1__ | | +|[OmicNavigator](problems.md#omicnavigator)|1.13.13 |__+1__ | |1 | +|[otsad](problems.md#otsad)|0.2.0 |__+1__ | |1 | +|[pdxTrees](problems.md#pdxtrees)|0.4.0 |__+1__ | |1 __+1__ | +|[personalized](problems.md#personalized)|0.2.7 |__+1__ | | | +|[PGRdup](problems.md#pgrdup)|0.2.3.9 |__+1__ |-1 | | +|[plantTracker](problems.md#planttracker)|1.1.0 |__+1__ | |__+1__ | +|[Plasmidprofiler](problems.md#plasmidprofiler)|0.1.6 |__+1__ | | | +|[plotDK](problems.md#plotdk)|0.1.0 |__+1__ | |2 | +|[plotly](problems.md#plotly)|4.10.4 |__+2__ | |1 | +|[pmartR](problems.md#pmartr)|2.4.4 |__+1__ | |1 | +|[pmxTools](problems.md#pmxtools)|1.3 |__+1__ | |1 | +|[PointedSDMs](problems.md#pointedsdms)|1.3.2 |__+1__ |1 | | +|[posterior](problems.md#posterior)|1.5.0 |1 | |__+1__ | +|[PPQplan](problems.md#ppqplan)|1.1.0 |1 | |2 __+1__ | +|[ppseq](problems.md#ppseq)|0.2.4 |__+1__ | |1 __+1__ | +|[processmapR](problems.md#processmapr)|0.5.3 |__+1__ | | | +|[QuadratiK](problems.md#quadratik)|1.0.0 | |__+1__ |1 | +|[Radviz](problems.md#radviz)|0.9.3 |__+2__ | |1 __+1__ | +|[rangeMapper](problems.md#rangemapper)|2.0.3 |__+1__ | |__+1__ | +|[rassta](problems.md#rassta)|1.0.5 |__+3__ | | | +|[RCTrep](problems.md#rctrep)|1.2.0 | |__+1__ | | +|[redistmetrics](problems.md#redistmetrics)|1.0.7 |__+1__ | |1 __+1__ | +|[ref.ICAR](problems.md#reficar)|2.0.1 |__+1__ | |__+1__ | +|[remap](problems.md#remap)|0.3.1 |__+1__ | |__+1__ | +|[rKIN](problems.md#rkin)|1.0.2 |__+1__ | | | +|[rLFT](problems.md#rlft)|1.0.1 |__+1__ | |1 __+1__ | +|[roahd](problems.md#roahd)|1.4.3 |__+1__ | |1 | +|[roptions](problems.md#roptions)|1.0.3 |__+1__ | |1 | +|[scoringutils](problems.md#scoringutils)|1.2.2 |1 __+1__ | |__+1__ | +|[SCOUTer](problems.md#scouter)|1.0.0 | |__+1__ | | +|[SCVA](problems.md#scva)|1.3.1 |__+1__ | | | +|[see](problems.md#see)|0.8.4 |__+1__ | | | +|[sfnetworks](problems.md#sfnetworks)|0.6.4 |1 | |__+1__ | +|[sftrack](problems.md#sftrack)|0.5.4 |__+2__ | |__+1__ | +|[sglg](problems.md#sglg)|0.2.2 |__+1__ | | | +|[sievePH](problems.md#sieveph)|1.0.4 | |__+1__ | | +|[SouthParkRshiny](problems.md#southparkrshiny)|1.0.0 | |__+1__ |2 | +|[spatialrisk](problems.md#spatialrisk)|0.7.1 |__+1__ | |2 | +|[spatialsample](problems.md#spatialsample)|0.5.1 |__+3__ | |__+1__ | +|[spinifex](problems.md#spinifex)|0.3.7.0 |__+1__ | | | +|[spmodel](problems.md#spmodel)|0.6.0 |__+1__ | |1 __+1__ | +|[SqueakR](problems.md#squeakr)|1.3.0 |1 |__+1__ |1 __+1__ | +|[stats19](problems.md#stats19)|3.0.3 |1 | |__+1__ | +|[streamDepletr](problems.md#streamdepletr)|0.2.0 |__+1__ | |__+1__ | +|[survminer](problems.md#survminer)|0.4.9 | |__+1__ |1 | +|[symptomcheckR](problems.md#symptomcheckr)|0.1.3 | |__+1__ | | +|[tabledown](problems.md#tabledown)|1.0.0 |__+1__ | |1 | +|[tcgaViz](problems.md#tcgaviz)|1.0.2 | |__+1__ | | +|[TCIU](problems.md#tciu)|1.2.5 |__+2__ | |1 __+1__ | +|[TestGardener](problems.md#testgardener)|3.3.3 | |__+1__ | | +|[thematic](problems.md#thematic)|0.1.5 |__+2__ | | | +|[tidybayes](problems.md#tidybayes)|3.0.6 |1 __+2__ | |1 | +|[tidyCDISC](problems.md#tidycdisc)|0.2.1 |__+1__ | |1 | +|[tidysdm](problems.md#tidysdm)|0.9.4 |__+2__ | |__+1__ | +|[tidyterra](problems.md#tidyterra)|0.6.0 |__+1__ | | | +|[tidytransit](problems.md#tidytransit)|1.6.1 |__+1__ | |1 __+1__ | +|[tidytreatment](problems.md#tidytreatment)|0.2.2 |__+1__ | |1 __+1__ | +|[tilemaps](problems.md#tilemaps)|0.2.0 |__+1__ | |1 __+1__ | +|[timetk](problems.md#timetk)|2.9.0 |__+1__ | |1 | +|[tongfen](problems.md#tongfen)|0.3.5 |1 | |1 __+1__ | +|[TOSTER](problems.md#toster)|0.8.2 |__+3__ | |__+1__ | +|[TreatmentPatterns](problems.md#treatmentpatterns)|2.6.6 |__+1__ | | | +|[trelliscopejs](problems.md#trelliscopejs)|0.2.6 |__+1__ | | | +|[tsnet](problems.md#tsnet)|0.1.0 |__+1__ | |2 | +|[umiAnalyzer](problems.md#umianalyzer)|1.0.0 |__+1__ | | | +|[UniprotR](problems.md#uniprotr)|2.4.0 | |__+1__ | | +|[VALERIE](problems.md#valerie)|1.1.0 | |__+1__ |1 -1 | +|[VancouvR](problems.md#vancouvr)|0.1.8 |__+1__ | | | +|[vannstats](problems.md#vannstats)|1.3.4.14 | |__+1__ | | +|[vici](problems.md#vici)|0.7.3 | |__+1__ | | +|[vivaldi](problems.md#vivaldi)|1.0.1 |__+3__ | |1 __+1__ | +|[vvshiny](problems.md#vvshiny)|0.1.1 |__+2__ | | | +|[waywiser](problems.md#waywiser)|0.5.1 |__+1__ | |1 __+1__ | +|[wildlifeDI](problems.md#wildlifedi)|1.0.0 |__+1__ | |__+1__ | +|[wilson](problems.md#wilson)|2.4.2 |__+1__ | | | +|[WorldMapR](problems.md#worldmapr)|0.1.1 |__+2__ | |1 | +|[xaringanthemer](problems.md#xaringanthemer)|0.4.2 |1 __+1__ | | | diff --git a/revdep/cran.md b/revdep/cran.md index ff60632977..fce1e499de 100644 --- a/revdep/cran.md +++ b/revdep/cran.md @@ -1,27 +1,742 @@ ## revdepcheck results -We checked 5021 reverse dependencies, comparing R CMD check results across CRAN and dev versions of this package. +We checked 5027 reverse dependencies, comparing R CMD check results across CRAN and dev versions of this package. - * We saw 5 new problems - * We failed to check 17 packages + * We saw 204 new problems + * We failed to check 135 packages Issues with CRAN packages are summarised below. ### New problems (This reports the first line of each new failure) +* actxps + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE + +* AeRobiology + checking re-building of vignette outputs ... NOTE + +* afex + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE + +* agricolaeplotr + checking examples ... ERROR + +* ammistability + checking re-building of vignette outputs ... ERROR + +* AnalysisLin + checking examples ... ERROR + +* animbook + checking examples ... ERROR + +* aopdata + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE + +* ARPALData + checking examples ... ERROR + +* asmbPLS + checking whether package ‘asmbPLS’ can be installed ... WARNING + +* autoplotly + checking examples ... ERROR + checking tests ... ERROR + +* BayesGrowth + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE + +* bdl + checking whether package ‘bdl’ can be installed ... WARNING + +* BeeBDC + checking examples ... ERROR + checking tests ... ERROR + +* blockCV + checking re-building of vignette outputs ... NOTE + +* boxly + checking tests ... ERROR + +* bSi + checking whether package ‘bSi’ can be installed ... WARNING + +* cartograflow + checking examples ... ERROR + +* cats + checking examples ... ERROR + +* cheem + checking tests ... ERROR + +* chronicle + checking examples ... ERROR + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE + +* clinDataReview + checking examples ... ERROR + checking tests ... ERROR + checking re-building of vignette outputs ... NOTE + +* clinUtils + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE + +* ClusROC + checking whether package ‘ClusROC’ can be installed ... WARNING + +* clustEff + checking whether package ‘clustEff’ can be installed ... WARNING + +* coda4microbiome + checking whether package ‘coda4microbiome’ can be installed ... WARNING + +* CohortPlat + checking examples ... ERROR + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE + +* CompAREdesign + checking whether package ‘CompAREdesign’ can be installed ... WARNING + +* CoreMicrobiomeR + checking examples ... ERROR + +* correlationfunnel + checking tests ... ERROR + +* corrViz + checking examples ... ERROR + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE + +* covidcast + checking tests ... ERROR + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE + +* Coxmos + checking Rd files ... WARNING + +* crosshap + checking examples ... ERROR + +* csa + checking whether package ‘csa’ can be installed ... WARNING + +* ctrialsgov + checking tests ... ERROR + +* cubble + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE + +* dafishr + checking examples ... ERROR + +* damAOI + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE + +* deeptime + checking examples ... ERROR + checking tests ... ERROR + +* DEGRE + checking whether package ‘DEGRE’ can be installed ... WARNING + +* densityarea + checking re-building of vignette outputs ... NOTE + +* did + checking whether package ‘did’ can be installed ... WARNING + +* distributional + checking examples ... ERROR + +* dittoViz + checking examples ... ERROR + checking tests ... ERROR + +* dots + checking examples ... ERROR + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE + +* eks + checking examples ... ERROR + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE + +* entropart + checking examples ... ERROR + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE + +* epiCleanr + checking examples ... ERROR + +* epiR + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE + +* esci + checking examples ... ERROR + checking tests ... ERROR + +* evalITR + checking re-building of vignette outputs ... NOTE + +* explainer + checking examples ... ERROR + +* fable.prophet + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE + +* fabletools + checking examples ... ERROR + checking tests ... ERROR + +* ffp + checking examples ... ERROR + +* fido + checking examples ... ERROR + +* flipr + checking re-building of vignette outputs ... NOTE + +* fmesher + checking examples ... ERROR + +* forestecology + checking examples ... ERROR + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE + +* frailtyEM + checking examples ... ERROR + +* FuncNN + checking whether package ‘FuncNN’ can be installed ... WARNING + +* geomander + checking examples ... ERROR + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE + +* geomtextpath + checking examples ... ERROR + checking tests ... ERROR + +* germinationmetrics + checking re-building of vignette outputs ... ERROR + +* gganimate + checking tests ... ERROR + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE + +* ggautomap + checking examples ... ERROR + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE + +* ggdark + checking examples ... ERROR + checking tests ... ERROR + +* ggdist + checking examples ... ERROR + checking tests ... ERROR + checking re-building of vignette outputs ... NOTE + +* ggedit + checking examples ... ERROR + +* ggfixest + checking tests ... ERROR + +* ggfortify + checking tests ... ERROR + * ggh4x checking examples ... ERROR checking tests ... ERROR + checking re-building of vignette outputs ... NOTE + +* ggheatmap + checking whether package ‘ggheatmap’ can be installed ... WARNING + +* gghighlight + checking examples ... ERROR + checking tests ... ERROR + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE + +* ggiraph + checking examples ... ERROR + checking tests ... ERROR + +* ggmice + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE + +* ggmulti + checking examples ... ERROR + checking tests ... ERROR + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE + +* ggparallel + checking tests ... ERROR + +* ggplotlyExtra + checking examples ... ERROR + +* ggpol + checking examples ... ERROR + +* ggraph + checking examples ... ERROR + checking re-building of vignette outputs ... NOTE + +* ggredist + checking examples ... ERROR + +* ggResidpanel + checking examples ... ERROR + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE + +* ggScatRidges + checking whether package ‘ggScatRidges’ can be installed ... WARNING + +* ggseqplot + checking examples ... ERROR + checking tests ... ERROR + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE + +* ggside + checking for code/documentation mismatches ... WARNING + +* ggtern + checking examples ... ERROR + +* ggVennDiagram + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE + +* GIFT + checking re-building of vignette outputs ... NOTE + +* GimmeMyPlot + checking whether package ‘GimmeMyPlot’ can be installed ... WARNING + +* gprofiler2 + checking examples ... ERROR + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE + +* Greymodels + checking examples ... ERROR + +* h3jsr + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE + +* healthyR + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE + +* healthyR.ai + checking examples ... ERROR + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE + +* healthyR.ts + checking examples ... ERROR + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE + +* heatmaply + checking tests ... ERROR + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE + +* hilldiv + checking whether package ‘hilldiv’ can be installed ... WARNING + +* hJAM + checking whether package ‘hJAM’ can be installed ... WARNING + +* HVT + checking examples ... ERROR + +* HYPEtools + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE + +* ImFoR + checking whether package ‘ImFoR’ can be installed ... WARNING + +* iNEXT.4steps + checking whether package ‘iNEXT.4steps’ can be installed ... WARNING + +* insane + checking whether package ‘insane’ can be installed ... WARNING + +* inTextSummaryTable + checking tests ... ERROR + checking re-building of vignette outputs ... NOTE + +* itsdm + checking examples ... ERROR + +* karel + checking examples ... ERROR + checking tests ... ERROR + +* latentcor + checking examples ... ERROR + +* mapSpain + checking examples ... ERROR + +* MBNMAdose + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE + +* MBNMAtime + checking re-building of vignette outputs ... NOTE + +* mc2d + checking whether package ‘mc2d’ can be installed ... WARNING + +* MetaIntegrator + checking whether package ‘MetaIntegrator’ can be installed ... WARNING + +* MF.beta4 + checking whether package ‘MF.beta4’ can be installed ... WARNING + +* MiMIR + checking examples ... ERROR + +* miRetrieve + checking tests ... ERROR + +* missingHE + checking whether package ‘missingHE’ can be installed ... WARNING + +* misspi + checking examples ... ERROR + +* mlr3spatiotempcv + checking examples ... ERROR + checking tests ... ERROR + +* modeltime.resample + checking tests ... ERROR + +* MSPRT + checking whether package ‘MSPRT’ can be installed ... WARNING + +* neatmaps + checking examples ... ERROR + +* NetFACS + checking examples ... ERROR + checking running R code from vignettes ... ERROR + +* NIMAA + checking examples ... ERROR + checking tests ... ERROR + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE + +* nswgeo + checking examples ... ERROR + +* OenoKPM + checking whether package ‘OenoKPM’ can be installed ... WARNING + +* OmicNavigator + checking tests ... ERROR + +* otsad + checking examples ... ERROR + +* pdxTrees + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE + +* personalized + checking tests ... ERROR + +* PGRdup checking re-building of vignette outputs ... ERROR -* MplusAutomation - checking installed package size ... NOTE +* plantTracker + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE + +* Plasmidprofiler + checking examples ... ERROR + +* plotDK + checking tests ... ERROR + +* plotly + checking examples ... ERROR + checking tests ... ERROR + +* pmartR + checking tests ... ERROR + +* pmxTools + checking tests ... ERROR + +* PointedSDMs + checking examples ... ERROR + +* posterior + checking re-building of vignette outputs ... NOTE + +* PPQplan + checking re-building of vignette outputs ... NOTE + +* ppseq + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE + +* processmapR + checking tests ... ERROR + +* QuadratiK + checking whether package ‘QuadratiK’ can be installed ... WARNING + +* Radviz + checking examples ... ERROR + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE + +* rangeMapper + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE + +* rassta + checking examples ... ERROR + checking tests ... ERROR + checking running R code from vignettes ... ERROR + +* RCTrep + checking whether package ‘RCTrep’ can be installed ... WARNING + +* redistmetrics + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE + +* ref.ICAR + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE -* PlasmaMutationDetector - checking installed package size ... NOTE +* remap + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE -* Superpower +* rKIN + checking examples ... ERROR + +* rLFT + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE + +* roahd + checking examples ... ERROR + +* roptions + checking examples ... ERROR + +* scoringutils + checking examples ... ERROR + checking re-building of vignette outputs ... NOTE + +* SCOUTer + checking whether package ‘SCOUTer’ can be installed ... WARNING + +* SCVA + checking examples ... ERROR + +* see + checking examples ... ERROR + +* sfnetworks + checking re-building of vignette outputs ... NOTE + +* sftrack + checking examples ... ERROR + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE + +* sglg + checking examples ... ERROR + +* sievePH + checking whether package ‘sievePH’ can be installed ... WARNING + +* SouthParkRshiny + checking whether package ‘SouthParkRshiny’ can be installed ... WARNING + +* spatialrisk + checking examples ... ERROR + +* spatialsample + checking examples ... ERROR + checking tests ... ERROR + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE + +* spinifex + checking tests ... ERROR + +* spmodel + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE + +* SqueakR + checking whether package ‘SqueakR’ can be installed ... WARNING + checking re-building of vignette outputs ... NOTE + +* stats19 + checking re-building of vignette outputs ... NOTE + +* streamDepletr + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE + +* survminer + checking whether package ‘survminer’ can be installed ... WARNING + +* symptomcheckR + checking whether package ‘symptomcheckR’ can be installed ... WARNING + +* tabledown + checking examples ... ERROR + +* tcgaViz + checking whether package ‘tcgaViz’ can be installed ... WARNING + +* TCIU + checking examples ... ERROR + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE + +* TestGardener + checking whether package ‘TestGardener’ can be installed ... WARNING + +* thematic + checking examples ... ERROR + checking tests ... ERROR + +* tidybayes + checking examples ... ERROR + checking tests ... ERROR + +* tidyCDISC + checking tests ... ERROR + +* tidysdm + checking examples ... ERROR + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE + +* tidyterra + checking examples ... ERROR + +* tidytransit + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE + +* tidytreatment + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE + +* tilemaps + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE + +* timetk + checking tests ... ERROR + +* tongfen + checking re-building of vignette outputs ... NOTE + +* TOSTER + checking examples ... ERROR + checking tests ... ERROR + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE + +* TreatmentPatterns + checking tests ... ERROR + +* trelliscopejs + checking tests ... ERROR + +* tsnet + checking tests ... ERROR + +* umiAnalyzer + checking examples ... ERROR + +* UniprotR + checking whether package ‘UniprotR’ can be installed ... WARNING + +* VALERIE + checking whether package ‘VALERIE’ can be installed ... WARNING + +* VancouvR + checking running R code from vignettes ... ERROR + +* vannstats + checking whether package ‘vannstats’ can be installed ... WARNING + +* vici + checking whether package ‘vici’ can be installed ... WARNING + +* vivaldi + checking examples ... ERROR + checking tests ... ERROR + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE + +* vvshiny + checking examples ... ERROR + checking tests ... ERROR + +* waywiser + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE + +* wildlifeDI + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE + +* wilson + checking tests ... ERROR + +* WorldMapR + checking examples ... ERROR checking tests ... ERROR * xaringanthemer @@ -29,20 +744,138 @@ Issues with CRAN packages are summarised below. ### Failed to check -* bayesdfa (NA) -* bmgarch (NA) -* ctsem (NA) -* EcoEnsemble (NA) -* geostan (NA) -* grandR (NA) -* multilevelcoda (NA) -* multinma (NA) -* rmsb (NA) -* rstanarm (NA) -* Seurat (NA) -* streamDAG (NA) -* treestats (NA) -* TriDimRegression (NA) -* triptych (NA) -* ubms (NA) -* valse (NA) +* abctools (NA) +* animalEKF (NA) +* ANOM (NA) +* atRisk (NA) +* AutoScore (NA) +* bayesdfa (NA) +* bayesDP (NA) +* BayesianFactorZoo (NA) +* BayesSurvive (NA) +* BCClong (NA) +* binsreg (NA) +* bmgarch (NA) +* bmstdr (NA) +* bspcov (NA) +* BuyseTest (NA) +* CalibrationCurves (NA) +* CARBayesST (NA) +* CaseBasedReasoning (NA) +* CGPfunctions (NA) +* cmprskcoxmsm (NA) +* contrast (NA) +* coxed (NA) +* CRMetrics (NA) +* csmpv (NA) +* ctsem (NA) +* DepthProc (NA) +* DR.SC (NA) +* EcoEnsemble (NA) +* ecolottery (NA) +* EpiEstim (NA) +* evolqg (NA) +* ForecastComb (NA) +* gapfill (NA) +* GeomComb (NA) +* geostan (NA) +* ggpmisc (NA) +* ggrcs (NA) +* ggrisk (NA) +* gJLS2 (NA) +* Greg (NA) +* greport (NA) +* hettx (NA) +* hIRT (NA) +* Hmsc (NA) +* inventorize (NA) +* iNZightPlots (NA) +* iNZightRegression (NA) +* IRexamples (NA) +* joineRML (NA) +* JWileymisc (NA) +* kmc (NA) +* L2E (NA) +* llbayesireg (NA) +* LorenzRegression (NA) +* lsirm12pl (NA) +* mbsts (NA) +* MendelianRandomization (NA) +* MetabolicSurv (NA) +* miWQS (NA) +* mlmts (NA) +* MRZero (NA) +* Multiaovbay (NA) +* multilevelTools (NA) +* multinma (NA) +* NCA (NA) +* netcmc (NA) +* NetworkChange (NA) +* nlmeVPC (NA) +* NMADiagT (NA) +* optweight (NA) +* OVtool (NA) +* paths (NA) +* PLMIX (NA) +* popstudy (NA) +* pould (NA) +* powerly (NA) +* pre (NA) +* ProFAST (NA) +* psbcSpeedUp (NA) +* pscore (NA) +* psfmi (NA) +* qPCRtools (NA) +* qreport (NA) +* qris (NA) +* qte (NA) +* quid (NA) +* RATest (NA) +* RcmdrPlugin.RiskDemo (NA) +* rddtools (NA) +* riskRegression (NA) +* rms (NA) +* rmsb (NA) +* robmed (NA) +* robmedExtra (NA) +* RPPanalyzer (NA) +* RQdeltaCT (NA) +* rstanarm (NA) +* scCustomize (NA) +* SCdeconR (NA) +* scGate (NA) +* scMappR (NA) +* scRNAstat (NA) +* sectorgap (NA) +* SEERaBomb (NA) +* semicmprskcoxmsm (NA) +* SensMap (NA) +* Seurat (NA) +* shinyTempSignal (NA) +* Signac (NA) +* SimplyAgree (NA) +* sMSROC (NA) +* SNPassoc (NA) +* snplinkage (NA) +* SoupX (NA) +* sparsereg (NA) +* spikeSlabGAM (NA) +* statsr (NA) +* streamDAG (NA) +* survHE (NA) +* survidm (NA) +* tempted (NA) +* tidydr (NA) +* tidyEdSurvey (NA) +* tidyseurat (NA) +* tidyvpc (NA) +* treestats (NA) +* TriDimRegression (NA) +* triptych (NA) +* TSrepr (NA) +* twang (NA) +* ubms (NA) +* valse (NA) +* vdg (NA) +* visa (NA) +* WRTDStidal (NA) diff --git a/revdep/failures.md b/revdep/failures.md index ca00cbc9ae..28d5c9fdd6 100644 --- a/revdep/failures.md +++ b/revdep/failures.md @@ -1,3 +1,327 @@ +# abctools + +
+ +* Version: 1.1.7 +* GitHub: https://github.com/dennisprangle/abctools +* Source code: https://github.com/cran/abctools +* Date/Publication: 2023-09-18 10:40:02 UTC +* Number of recursive dependencies: 75 + +Run `revdepcheck::cloud_details(, "abctools")` for more info + +
+ +## In both + +* checking whether package ‘abctools’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/abctools/new/abctools.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘abctools’ ... +** package ‘abctools’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C compiler: ‘gcc (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ +gcc -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I/usr/local/include -fpic -g -O2 -c abctools.c -o abctools.o +gcc -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I/usr/local/include -fpic -g -O2 -c init.c -o init.o +gcc -shared -L/opt/R/4.3.1/lib/R/lib -L/usr/local/lib -o abctools.so abctools.o init.o -llapack -lblas -lgfortran -lm -lquadmath -L/opt/R/4.3.1/lib/R/lib -lR +installing to /tmp/workdir/abctools/new/abctools.Rcheck/00LOCK-abctools/00new/abctools/libs +** R +** data +** inst +** byte-compile and prepare package for lazy loading +Error: package or namespace load failed for ‘quantreg’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Execution halted +ERROR: lazy loading failed for package ‘abctools’ +* removing ‘/tmp/workdir/abctools/new/abctools.Rcheck/abctools’ + + +``` +### CRAN + +``` +* installing *source* package ‘abctools’ ... +** package ‘abctools’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C compiler: ‘gcc (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ +gcc -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I/usr/local/include -fpic -g -O2 -c abctools.c -o abctools.o +gcc -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I/usr/local/include -fpic -g -O2 -c init.c -o init.o +gcc -shared -L/opt/R/4.3.1/lib/R/lib -L/usr/local/lib -o abctools.so abctools.o init.o -llapack -lblas -lgfortran -lm -lquadmath -L/opt/R/4.3.1/lib/R/lib -lR +installing to /tmp/workdir/abctools/old/abctools.Rcheck/00LOCK-abctools/00new/abctools/libs +** R +** data +** inst +** byte-compile and prepare package for lazy loading +Error: package or namespace load failed for ‘quantreg’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Execution halted +ERROR: lazy loading failed for package ‘abctools’ +* removing ‘/tmp/workdir/abctools/old/abctools.Rcheck/abctools’ + + +``` +# animalEKF + +
+ +* Version: 1.2 +* GitHub: NA +* Source code: https://github.com/cran/animalEKF +* Date/Publication: 2023-09-29 15:32:41 UTC +* Number of recursive dependencies: 76 + +Run `revdepcheck::cloud_details(, "animalEKF")` for more info + +
+ +## In both + +* checking whether package ‘animalEKF’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/animalEKF/new/animalEKF.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘animalEKF’ ... +** package ‘animalEKF’ successfully unpacked and MD5 sums checked +** 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘animalEKF’ +* removing ‘/tmp/workdir/animalEKF/new/animalEKF.Rcheck/animalEKF’ + + +``` +### CRAN + +``` +* installing *source* package ‘animalEKF’ ... +** package ‘animalEKF’ successfully unpacked and MD5 sums checked +** 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘animalEKF’ +* removing ‘/tmp/workdir/animalEKF/old/animalEKF.Rcheck/animalEKF’ + + +``` +# ANOM + +
+ +* Version: 0.5 +* GitHub: https://github.com/PhilipPallmann/ANOM +* Source code: https://github.com/cran/ANOM +* Date/Publication: 2017-04-12 13:32:33 UTC +* Number of recursive dependencies: 77 + +Run `revdepcheck::cloud_details(, "ANOM")` for more info + +
+ +## In both + +* checking whether package ‘ANOM’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/ANOM/new/ANOM.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘ANOM’ ... +** package ‘ANOM’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘ANOM’ +* removing ‘/tmp/workdir/ANOM/new/ANOM.Rcheck/ANOM’ + + +``` +### CRAN + +``` +* installing *source* package ‘ANOM’ ... +** package ‘ANOM’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘ANOM’ +* removing ‘/tmp/workdir/ANOM/old/ANOM.Rcheck/ANOM’ + + +``` +# atRisk + +
+ +* Version: 0.1.0 +* GitHub: NA +* Source code: https://github.com/cran/atRisk +* Date/Publication: 2023-08-08 14:50:05 UTC +* Number of recursive dependencies: 37 + +Run `revdepcheck::cloud_details(, "atRisk")` for more info + +
+ +## In both + +* checking whether package ‘atRisk’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/atRisk/new/atRisk.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘atRisk’ ... +** package ‘atRisk’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** data +*** moving datasets to lazyload DB +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘atRisk’ +* removing ‘/tmp/workdir/atRisk/new/atRisk.Rcheck/atRisk’ + + +``` +### CRAN + +``` +* installing *source* package ‘atRisk’ ... +** package ‘atRisk’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** data +*** moving datasets to lazyload DB +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘atRisk’ +* removing ‘/tmp/workdir/atRisk/old/atRisk.Rcheck/atRisk’ + + +``` +# AutoScore + +
+ +* Version: 1.0.0 +* GitHub: https://github.com/nliulab/AutoScore +* Source code: https://github.com/cran/AutoScore +* Date/Publication: 2022-10-15 22:15:26 UTC +* Number of recursive dependencies: 180 + +Run `revdepcheck::cloud_details(, "AutoScore")` for more info + +
+ +## In both + +* checking whether package ‘AutoScore’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/AutoScore/new/AutoScore.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘AutoScore’ ... +** package ‘AutoScore’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘AutoScore’ +* removing ‘/tmp/workdir/AutoScore/new/AutoScore.Rcheck/AutoScore’ + + +``` +### CRAN + +``` +* installing *source* package ‘AutoScore’ ... +** package ‘AutoScore’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘AutoScore’ +* removing ‘/tmp/workdir/AutoScore/old/AutoScore.Rcheck/AutoScore’ + + +``` # bayesdfa
@@ -76,26 +400,26 @@ ERROR: compilation failed for package ‘bayesdfa’ ``` -# bmgarch +# bayesDP
-* Version: 2.0.0 -* GitHub: https://github.com/ph-rast/bmgarch -* Source code: https://github.com/cran/bmgarch -* Date/Publication: 2023-09-12 00:40:02 UTC -* Number of recursive dependencies: 82 +* Version: 1.3.6 +* GitHub: https://github.com/graemeleehickey/bayesDP +* Source code: https://github.com/cran/bayesDP +* Date/Publication: 2022-01-30 22:20:02 UTC +* Number of recursive dependencies: 80 -Run `revdepcheck::cloud_details(, "bmgarch")` for more info +Run `revdepcheck::cloud_details(, "bayesDP")` for more info
## In both -* checking whether package ‘bmgarch’ can be installed ... ERROR +* checking whether package ‘bayesDP’ can be installed ... ERROR ``` Installation failed. - See ‘/tmp/workdir/bmgarch/new/bmgarch.Rcheck/00install.out’ for details. + See ‘/tmp/workdir/bayesDP/new/bayesDP.Rcheck/00install.out’ for details. ``` ## Installation @@ -103,77 +427,7228 @@ Run `revdepcheck::cloud_details(, "bmgarch")` for more info ### Devel ``` -* installing *source* package ‘bmgarch’ ... -** package ‘bmgarch’ successfully unpacked and MD5 sums checked +* installing *source* package ‘bayesDP’ ... +** package ‘bayesDP’ successfully unpacked and MD5 sums checked ** using staged installation ** libs using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ -using C++17 +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c bdplm.cpp -o bdplm.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c ppexp.cpp -o ppexp.o +g++ -std=gnu++17 -shared -L/opt/R/4.3.1/lib/R/lib -L/usr/local/lib -o bayesDP.so RcppExports.o bdplm.o ppexp.o -llapack -lblas -lgfortran -lm -lquadmath -L/opt/R/4.3.1/lib/R/lib -lR +installing to /tmp/workdir/bayesDP/new/bayesDP.Rcheck/00LOCK-bayesDP/00new/bayesDP/libs +** R +** inst +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘bayesDP’ +* removing ‘/tmp/workdir/bayesDP/new/bayesDP.Rcheck/bayesDP’ -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I"../inst/include" -I"/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src" -DBOOST_DISABLE_ASSERTS -DEIGEN_NO_DEBUG -DBOOST_MATH_OVERFLOW_ERROR_POLICY=errno_on_error -DUSE_STANC3 -D_HAS_AUTO_PTR_ETC=0 -I'/opt/R/4.3.1/lib/R/site-library/BH/include' -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppEigen/include' -I'/opt/R/4.3.1/lib/R/site-library/rstan/include' -I'/opt/R/4.3.1/lib/R/site-library/StanHeaders/include' -I/usr/local/include -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -D_REENTRANT -DSTAN_THREADS -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o -In file included from /opt/R/4.3.1/lib/R/site-library/RcppEigen/include/Eigen/Core:205, -... -/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src/stan/mcmc/hmc/hamiltonians/dense_e_metric.hpp:22:56: required from ‘double stan::mcmc::dense_e_metric::T(stan::mcmc::dense_e_point&) [with Model = model_DCCMGARCH_namespace::model_DCCMGARCH; BaseRNG = boost::random::additive_combine_engine, boost::random::linear_congruential_engine >]’ -/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src/stan/mcmc/hmc/hamiltonians/dense_e_metric.hpp:21:10: required from here -/opt/R/4.3.1/lib/R/site-library/RcppEigen/include/Eigen/src/Core/DenseCoeffsBase.h:654:34: warning: ignoring attributes on template argument ‘Eigen::internal::packet_traits::type’ {aka ‘__vector(2) double’} [-Wignored-attributes] - 654 | return internal::first_aligned::alignment),Derived>(m); - | ^~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -g++: fatal error: Killed signal terminated program cc1plus -compilation terminated. -make: *** [/opt/R/4.3.1/lib/R/etc/Makeconf:198: stanExports_DCCMGARCH.o] Error 1 -ERROR: compilation failed for package ‘bmgarch’ -* removing ‘/tmp/workdir/bmgarch/new/bmgarch.Rcheck/bmgarch’ +``` +### CRAN + +``` +* installing *source* package ‘bayesDP’ ... +** package ‘bayesDP’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c bdplm.cpp -o bdplm.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c ppexp.cpp -o ppexp.o +g++ -std=gnu++17 -shared -L/opt/R/4.3.1/lib/R/lib -L/usr/local/lib -o bayesDP.so RcppExports.o bdplm.o ppexp.o -llapack -lblas -lgfortran -lm -lquadmath -L/opt/R/4.3.1/lib/R/lib -lR +installing to /tmp/workdir/bayesDP/old/bayesDP.Rcheck/00LOCK-bayesDP/00new/bayesDP/libs +** R +** inst +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘bayesDP’ +* removing ‘/tmp/workdir/bayesDP/old/bayesDP.Rcheck/bayesDP’ + + +``` +# BayesianFactorZoo + +
+ +* Version: 0.0.0.2 +* GitHub: NA +* Source code: https://github.com/cran/BayesianFactorZoo +* Date/Publication: 2023-11-14 12:43:44 UTC +* Number of recursive dependencies: 75 + +Run `revdepcheck::cloud_details(, "BayesianFactorZoo")` for more info + +
+ +## In both + +* checking whether package ‘BayesianFactorZoo’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/BayesianFactorZoo/new/BayesianFactorZoo.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘BayesianFactorZoo’ ... +** package ‘BayesianFactorZoo’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘BayesianFactorZoo’ +* removing ‘/tmp/workdir/BayesianFactorZoo/new/BayesianFactorZoo.Rcheck/BayesianFactorZoo’ + + +``` +### CRAN + +``` +* installing *source* package ‘BayesianFactorZoo’ ... +** package ‘BayesianFactorZoo’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘BayesianFactorZoo’ +* removing ‘/tmp/workdir/BayesianFactorZoo/old/BayesianFactorZoo.Rcheck/BayesianFactorZoo’ + + +``` +# BayesSurvive + +
+ +* Version: 0.0.1 +* GitHub: https://github.com/ocbe-uio/BayesSurvive +* Source code: https://github.com/cran/BayesSurvive +* Date/Publication: 2024-04-23 11:20:06 UTC +* Number of recursive dependencies: 129 + +Run `revdepcheck::cloud_details(, "BayesSurvive")` for more info + +
+ +## In both + +* checking whether package ‘BayesSurvive’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/BayesSurvive/new/BayesSurvive.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘BayesSurvive’ ... +** package ‘BayesSurvive’ successfully unpacked and MD5 sums checked +** using staged installation +checking whether the C++ compiler works... yes +checking for C++ compiler default output file name... a.out +checking for suffix of executables... +checking whether we are cross compiling... no +checking for suffix of object files... o +checking whether the compiler supports GNU C++... yes +checking whether g++ -std=gnu++17 accepts -g... yes +... +** R +** data +*** moving datasets to lazyload DB +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘BayesSurvive’ +* removing ‘/tmp/workdir/BayesSurvive/new/BayesSurvive.Rcheck/BayesSurvive’ + + +``` +### CRAN + +``` +* installing *source* package ‘BayesSurvive’ ... +** package ‘BayesSurvive’ successfully unpacked and MD5 sums checked +** using staged installation +checking whether the C++ compiler works... yes +checking for C++ compiler default output file name... a.out +checking for suffix of executables... +checking whether we are cross compiling... no +checking for suffix of object files... o +checking whether the compiler supports GNU C++... yes +checking whether g++ -std=gnu++17 accepts -g... yes +... +** R +** data +*** moving datasets to lazyload DB +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘BayesSurvive’ +* removing ‘/tmp/workdir/BayesSurvive/old/BayesSurvive.Rcheck/BayesSurvive’ + + +``` +# BCClong + +
+ +* Version: 1.0.2 +* GitHub: NA +* Source code: https://github.com/cran/BCClong +* Date/Publication: 2024-02-05 11:50:06 UTC +* Number of recursive dependencies: 142 + +Run `revdepcheck::cloud_details(, "BCClong")` for more info + +
+ +## In both + +* checking whether package ‘BCClong’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/BCClong/new/BCClong.Rcheck/00install.out’ for details. + ``` + +* checking package dependencies ... NOTE + ``` + Package suggested but not available for checking: ‘joineRML’ + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘BCClong’ ... +** package ‘BCClong’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c BCC.cpp -o BCC.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c Likelihood.cpp -o Likelihood.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c c_which.cpp -o c_which.o +g++ -std=gnu++17 -shared -L/opt/R/4.3.1/lib/R/lib -L/usr/local/lib -o BCClong.so BCC.o Likelihood.o RcppExports.o c_which.o -fopenmp -llapack -lblas -lgfortran -lm -lquadmath -L/opt/R/4.3.1/lib/R/lib -lR +... +installing to /tmp/workdir/BCClong/new/BCClong.Rcheck/00LOCK-BCClong/00new/BCClong/libs +** R +** inst +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘BCClong’ +* removing ‘/tmp/workdir/BCClong/new/BCClong.Rcheck/BCClong’ + + +``` +### CRAN + +``` +* installing *source* package ‘BCClong’ ... +** package ‘BCClong’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c BCC.cpp -o BCC.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c Likelihood.cpp -o Likelihood.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c c_which.cpp -o c_which.o +g++ -std=gnu++17 -shared -L/opt/R/4.3.1/lib/R/lib -L/usr/local/lib -o BCClong.so BCC.o Likelihood.o RcppExports.o c_which.o -fopenmp -llapack -lblas -lgfortran -lm -lquadmath -L/opt/R/4.3.1/lib/R/lib -lR +... +installing to /tmp/workdir/BCClong/old/BCClong.Rcheck/00LOCK-BCClong/00new/BCClong/libs +** R +** inst +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘BCClong’ +* removing ‘/tmp/workdir/BCClong/old/BCClong.Rcheck/BCClong’ + + +``` +# binsreg + +
+ +* Version: 1.0 +* GitHub: NA +* Source code: https://github.com/cran/binsreg +* Date/Publication: 2023-07-11 12:00:24 UTC +* Number of recursive dependencies: 35 + +Run `revdepcheck::cloud_details(, "binsreg")` for more info + +
+ +## In both + +* checking whether package ‘binsreg’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/binsreg/new/binsreg.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘binsreg’ ... +** package ‘binsreg’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘binsreg’ +* removing ‘/tmp/workdir/binsreg/new/binsreg.Rcheck/binsreg’ + + +``` +### CRAN + +``` +* installing *source* package ‘binsreg’ ... +** package ‘binsreg’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘binsreg’ +* removing ‘/tmp/workdir/binsreg/old/binsreg.Rcheck/binsreg’ + + +``` +# bmgarch + +
+ +* Version: 2.0.0 +* GitHub: https://github.com/ph-rast/bmgarch +* Source code: https://github.com/cran/bmgarch +* Date/Publication: 2023-09-12 00:40:02 UTC +* Number of recursive dependencies: 82 + +Run `revdepcheck::cloud_details(, "bmgarch")` for more info + +
+ +## In both + +* checking whether package ‘bmgarch’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/bmgarch/new/bmgarch.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘bmgarch’ ... +** package ‘bmgarch’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ +using C++17 + + +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I"../inst/include" -I"/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src" -DBOOST_DISABLE_ASSERTS -DEIGEN_NO_DEBUG -DBOOST_MATH_OVERFLOW_ERROR_POLICY=errno_on_error -DUSE_STANC3 -D_HAS_AUTO_PTR_ETC=0 -I'/opt/R/4.3.1/lib/R/site-library/BH/include' -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppEigen/include' -I'/opt/R/4.3.1/lib/R/site-library/rstan/include' -I'/opt/R/4.3.1/lib/R/site-library/StanHeaders/include' -I/usr/local/include -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -D_REENTRANT -DSTAN_THREADS -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +In file included from /opt/R/4.3.1/lib/R/site-library/RcppEigen/include/Eigen/Core:205, +... +/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src/stan/mcmc/hmc/hamiltonians/dense_e_metric.hpp:22:56: required from ‘double stan::mcmc::dense_e_metric::T(stan::mcmc::dense_e_point&) [with Model = model_DCCMGARCH_namespace::model_DCCMGARCH; BaseRNG = boost::random::additive_combine_engine, boost::random::linear_congruential_engine >]’ +/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src/stan/mcmc/hmc/hamiltonians/dense_e_metric.hpp:21:10: required from here +/opt/R/4.3.1/lib/R/site-library/RcppEigen/include/Eigen/src/Core/DenseCoeffsBase.h:654:34: warning: ignoring attributes on template argument ‘Eigen::internal::packet_traits::type’ {aka ‘__vector(2) double’} [-Wignored-attributes] + 654 | return internal::first_aligned::alignment),Derived>(m); + | ^~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +g++: fatal error: Killed signal terminated program cc1plus +compilation terminated. +make: *** [/opt/R/4.3.1/lib/R/etc/Makeconf:198: stanExports_DCCMGARCH.o] Error 1 +ERROR: compilation failed for package ‘bmgarch’ +* removing ‘/tmp/workdir/bmgarch/new/bmgarch.Rcheck/bmgarch’ + + +``` +### CRAN + +``` +* installing *source* package ‘bmgarch’ ... +** package ‘bmgarch’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ +using C++17 + + +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I"../inst/include" -I"/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src" -DBOOST_DISABLE_ASSERTS -DEIGEN_NO_DEBUG -DBOOST_MATH_OVERFLOW_ERROR_POLICY=errno_on_error -DUSE_STANC3 -D_HAS_AUTO_PTR_ETC=0 -I'/opt/R/4.3.1/lib/R/site-library/BH/include' -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppEigen/include' -I'/opt/R/4.3.1/lib/R/site-library/rstan/include' -I'/opt/R/4.3.1/lib/R/site-library/StanHeaders/include' -I/usr/local/include -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -D_REENTRANT -DSTAN_THREADS -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +In file included from /opt/R/4.3.1/lib/R/site-library/RcppEigen/include/Eigen/Core:205, +... +/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src/stan/mcmc/hmc/hamiltonians/dense_e_metric.hpp:22:56: required from ‘double stan::mcmc::dense_e_metric::T(stan::mcmc::dense_e_point&) [with Model = model_DCCMGARCH_namespace::model_DCCMGARCH; BaseRNG = boost::random::additive_combine_engine, boost::random::linear_congruential_engine >]’ +/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src/stan/mcmc/hmc/hamiltonians/dense_e_metric.hpp:21:10: required from here +/opt/R/4.3.1/lib/R/site-library/RcppEigen/include/Eigen/src/Core/DenseCoeffsBase.h:654:34: warning: ignoring attributes on template argument ‘Eigen::internal::packet_traits::type’ {aka ‘__vector(2) double’} [-Wignored-attributes] + 654 | return internal::first_aligned::alignment),Derived>(m); + | ^~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +g++: fatal error: Killed signal terminated program cc1plus +compilation terminated. +make: *** [/opt/R/4.3.1/lib/R/etc/Makeconf:198: stanExports_DCCMGARCH.o] Error 1 +ERROR: compilation failed for package ‘bmgarch’ +* removing ‘/tmp/workdir/bmgarch/old/bmgarch.Rcheck/bmgarch’ + + +``` +# bmstdr + +
+ +* Version: 0.7.9 +* GitHub: https://github.com/sujit-sahu/bmstdr +* Source code: https://github.com/cran/bmstdr +* Date/Publication: 2023-12-18 15:00:02 UTC +* Number of recursive dependencies: 212 + +Run `revdepcheck::cloud_details(, "bmstdr")` for more info + +
+ +## In both + +* checking whether package ‘bmstdr’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/bmstdr/new/bmstdr.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘bmstdr’ ... +** package ‘bmstdr’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ +using C++17 + + +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I"../inst/include" -I"/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src" -DBOOST_DISABLE_ASSERTS -DEIGEN_NO_DEBUG -DBOOST_MATH_OVERFLOW_ERROR_POLICY=errno_on_error -DUSE_STANC3 -D_HAS_AUTO_PTR_ETC=0 -I'/opt/R/4.3.1/lib/R/site-library/BH/include' -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppEigen/include' -I'/opt/R/4.3.1/lib/R/site-library/rstan/include' -I'/opt/R/4.3.1/lib/R/site-library/StanHeaders/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -I/usr/local/include -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -D_REENTRANT -DSTAN_THREADS -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +In file included from /opt/R/4.3.1/lib/R/site-library/RcppEigen/include/Eigen/Core:205, +... +** 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘bmstdr’ +* removing ‘/tmp/workdir/bmstdr/new/bmstdr.Rcheck/bmstdr’ + + +``` +### CRAN + +``` +* installing *source* package ‘bmstdr’ ... +** package ‘bmstdr’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ +using C++17 + + +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I"../inst/include" -I"/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src" -DBOOST_DISABLE_ASSERTS -DEIGEN_NO_DEBUG -DBOOST_MATH_OVERFLOW_ERROR_POLICY=errno_on_error -DUSE_STANC3 -D_HAS_AUTO_PTR_ETC=0 -I'/opt/R/4.3.1/lib/R/site-library/BH/include' -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppEigen/include' -I'/opt/R/4.3.1/lib/R/site-library/rstan/include' -I'/opt/R/4.3.1/lib/R/site-library/StanHeaders/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -I/usr/local/include -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -D_REENTRANT -DSTAN_THREADS -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +In file included from /opt/R/4.3.1/lib/R/site-library/RcppEigen/include/Eigen/Core:205, +... +** 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘bmstdr’ +* removing ‘/tmp/workdir/bmstdr/old/bmstdr.Rcheck/bmstdr’ + + +``` +# bspcov + +
+ +* Version: 1.0.0 +* GitHub: https://github.com/statjs/bspcov +* Source code: https://github.com/cran/bspcov +* Date/Publication: 2024-02-06 16:50:08 UTC +* Number of recursive dependencies: 122 + +Run `revdepcheck::cloud_details(, "bspcov")` for more info + +
+ +## In both + +* checking whether package ‘bspcov’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/bspcov/new/bspcov.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘bspcov’ ... +** package ‘bspcov’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** data +*** moving datasets to lazyload DB +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is being loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘bspcov’ +* removing ‘/tmp/workdir/bspcov/new/bspcov.Rcheck/bspcov’ + + +``` +### CRAN + +``` +* installing *source* package ‘bspcov’ ... +** package ‘bspcov’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** data +*** moving datasets to lazyload DB +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is being loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘bspcov’ +* removing ‘/tmp/workdir/bspcov/old/bspcov.Rcheck/bspcov’ + + +``` +# BuyseTest + +
+ +* Version: 3.0.2 +* GitHub: https://github.com/bozenne/BuyseTest +* Source code: https://github.com/cran/BuyseTest +* Date/Publication: 2024-01-23 15:12:56 UTC +* Number of recursive dependencies: 133 + +Run `revdepcheck::cloud_details(, "BuyseTest")` for more info + +
+ +## In both + +* checking whether package ‘BuyseTest’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/BuyseTest/new/BuyseTest.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘BuyseTest’ ... +** package ‘BuyseTest’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c FCT_buyseTest.cpp -o FCT_buyseTest.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c FCT_precompute.cpp -o FCT_precompute.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c utils-from-riskRegression.cpp -o utils-from-riskRegression.o +g++ -std=gnu++17 -shared -L/opt/R/4.3.1/lib/R/lib -L/usr/local/lib -o BuyseTest.so FCT_buyseTest.o FCT_precompute.o RcppExports.o utils-from-riskRegression.o -L/opt/R/4.3.1/lib/R/lib -lR +... +installing to /tmp/workdir/BuyseTest/new/BuyseTest.Rcheck/00LOCK-BuyseTest/00new/BuyseTest/libs +** R +** inst +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Error: unable to load R code in package ‘BuyseTest’ +Execution halted +ERROR: lazy loading failed for package ‘BuyseTest’ +* removing ‘/tmp/workdir/BuyseTest/new/BuyseTest.Rcheck/BuyseTest’ + + +``` +### CRAN + +``` +* installing *source* package ‘BuyseTest’ ... +** package ‘BuyseTest’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c FCT_buyseTest.cpp -o FCT_buyseTest.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c FCT_precompute.cpp -o FCT_precompute.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c utils-from-riskRegression.cpp -o utils-from-riskRegression.o +g++ -std=gnu++17 -shared -L/opt/R/4.3.1/lib/R/lib -L/usr/local/lib -o BuyseTest.so FCT_buyseTest.o FCT_precompute.o RcppExports.o utils-from-riskRegression.o -L/opt/R/4.3.1/lib/R/lib -lR +... +installing to /tmp/workdir/BuyseTest/old/BuyseTest.Rcheck/00LOCK-BuyseTest/00new/BuyseTest/libs +** R +** inst +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Error: unable to load R code in package ‘BuyseTest’ +Execution halted +ERROR: lazy loading failed for package ‘BuyseTest’ +* removing ‘/tmp/workdir/BuyseTest/old/BuyseTest.Rcheck/BuyseTest’ + + +``` +# CalibrationCurves + +
+ +* Version: 2.0.1 +* GitHub: NA +* Source code: https://github.com/cran/CalibrationCurves +* Date/Publication: 2024-03-01 10:12:35 UTC +* Number of recursive dependencies: 78 + +Run `revdepcheck::cloud_details(, "CalibrationCurves")` for more info + +
+ +## In both + +* checking whether package ‘CalibrationCurves’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/CalibrationCurves/new/CalibrationCurves.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘CalibrationCurves’ ... +** package ‘CalibrationCurves’ 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: package or namespace load failed for ‘rms’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Execution halted +ERROR: lazy loading failed for package ‘CalibrationCurves’ +* removing ‘/tmp/workdir/CalibrationCurves/new/CalibrationCurves.Rcheck/CalibrationCurves’ + + +``` +### CRAN + +``` +* installing *source* package ‘CalibrationCurves’ ... +** package ‘CalibrationCurves’ 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: package or namespace load failed for ‘rms’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Execution halted +ERROR: lazy loading failed for package ‘CalibrationCurves’ +* removing ‘/tmp/workdir/CalibrationCurves/old/CalibrationCurves.Rcheck/CalibrationCurves’ + + +``` +# CARBayesST + +
+ +* Version: 4.0 +* GitHub: https://github.com/duncanplee/CARBayesST +* Source code: https://github.com/cran/CARBayesST +* Date/Publication: 2023-10-30 16:40:02 UTC +* Number of recursive dependencies: 118 + +Run `revdepcheck::cloud_details(, "CARBayesST")` for more info + +
+ +## In both + +* checking whether package ‘CARBayesST’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/CARBayesST/new/CARBayesST.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘CARBayesST’ ... +** package ‘CARBayesST’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c CARBayesST.cpp -o CARBayesST.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +g++ -std=gnu++17 -shared -L/opt/R/4.3.1/lib/R/lib -L/usr/local/lib -o CARBayesST.so CARBayesST.o RcppExports.o -L/opt/R/4.3.1/lib/R/lib -lR +installing to /tmp/workdir/CARBayesST/new/CARBayesST.Rcheck/00LOCK-CARBayesST/00new/CARBayesST/libs +** R +** inst +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘CARBayesST’ +* removing ‘/tmp/workdir/CARBayesST/new/CARBayesST.Rcheck/CARBayesST’ + + +``` +### CRAN + +``` +* installing *source* package ‘CARBayesST’ ... +** package ‘CARBayesST’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c CARBayesST.cpp -o CARBayesST.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +g++ -std=gnu++17 -shared -L/opt/R/4.3.1/lib/R/lib -L/usr/local/lib -o CARBayesST.so CARBayesST.o RcppExports.o -L/opt/R/4.3.1/lib/R/lib -lR +installing to /tmp/workdir/CARBayesST/old/CARBayesST.Rcheck/00LOCK-CARBayesST/00new/CARBayesST/libs +** R +** inst +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘CARBayesST’ +* removing ‘/tmp/workdir/CARBayesST/old/CARBayesST.Rcheck/CARBayesST’ + + +``` +# CaseBasedReasoning + +
+ +* Version: 0.3 +* GitHub: https://github.com/sipemu/case-based-reasoning +* Source code: https://github.com/cran/CaseBasedReasoning +* Date/Publication: 2023-05-02 08:40:02 UTC +* Number of recursive dependencies: 106 + +Run `revdepcheck::cloud_details(, "CaseBasedReasoning")` for more info + +
+ +## In both + +* checking whether package ‘CaseBasedReasoning’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/CaseBasedReasoning/new/CaseBasedReasoning.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘CaseBasedReasoning’ ... +** package ‘CaseBasedReasoning’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -I/usr/local/include -fpic -g -O2 -c distanceAPI.cpp -o distanceAPI.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -I/usr/local/include -fpic -g -O2 -c distances.cpp -o distances.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -I/usr/local/include -fpic -g -O2 -c order.cpp -o order.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -I/usr/local/include -fpic -g -O2 -c weightedKNN.cpp -o weightedKNN.o +... +g++ -std=gnu++17 -shared -L/opt/R/4.3.1/lib/R/lib -L/usr/local/lib -o CaseBasedReasoning.so RcppExports.o distanceAPI.o distances.o order.o weightedKNN.o -L/opt/R/4.3.1/lib/R/lib -lR +installing to /tmp/workdir/CaseBasedReasoning/new/CaseBasedReasoning.Rcheck/00LOCK-CaseBasedReasoning/00new/CaseBasedReasoning/libs +** R +** inst +** byte-compile and prepare package for lazy loading +Error: package or namespace load failed for ‘rms’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Execution halted +ERROR: lazy loading failed for package ‘CaseBasedReasoning’ +* removing ‘/tmp/workdir/CaseBasedReasoning/new/CaseBasedReasoning.Rcheck/CaseBasedReasoning’ + + +``` +### CRAN + +``` +* installing *source* package ‘CaseBasedReasoning’ ... +** package ‘CaseBasedReasoning’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -I/usr/local/include -fpic -g -O2 -c distanceAPI.cpp -o distanceAPI.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -I/usr/local/include -fpic -g -O2 -c distances.cpp -o distances.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -I/usr/local/include -fpic -g -O2 -c order.cpp -o order.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -I/usr/local/include -fpic -g -O2 -c weightedKNN.cpp -o weightedKNN.o +... +g++ -std=gnu++17 -shared -L/opt/R/4.3.1/lib/R/lib -L/usr/local/lib -o CaseBasedReasoning.so RcppExports.o distanceAPI.o distances.o order.o weightedKNN.o -L/opt/R/4.3.1/lib/R/lib -lR +installing to /tmp/workdir/CaseBasedReasoning/old/CaseBasedReasoning.Rcheck/00LOCK-CaseBasedReasoning/00new/CaseBasedReasoning/libs +** R +** inst +** byte-compile and prepare package for lazy loading +Error: package or namespace load failed for ‘rms’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Execution halted +ERROR: lazy loading failed for package ‘CaseBasedReasoning’ +* removing ‘/tmp/workdir/CaseBasedReasoning/old/CaseBasedReasoning.Rcheck/CaseBasedReasoning’ + + +``` +# CGPfunctions + +
+ +* Version: 0.6.3 +* GitHub: https://github.com/ibecav/CGPfunctions +* Source code: https://github.com/cran/CGPfunctions +* Date/Publication: 2020-11-12 14:50:09 UTC +* Number of recursive dependencies: 158 + +Run `revdepcheck::cloud_details(, "CGPfunctions")` for more info + +
+ +## In both + +* checking whether package ‘CGPfunctions’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/CGPfunctions/new/CGPfunctions.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘CGPfunctions’ ... +** package ‘CGPfunctions’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘CGPfunctions’ +* removing ‘/tmp/workdir/CGPfunctions/new/CGPfunctions.Rcheck/CGPfunctions’ + + +``` +### CRAN + +``` +* installing *source* package ‘CGPfunctions’ ... +** package ‘CGPfunctions’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘CGPfunctions’ +* removing ‘/tmp/workdir/CGPfunctions/old/CGPfunctions.Rcheck/CGPfunctions’ + + +``` +# cmprskcoxmsm + +
+ +* Version: 0.2.1 +* GitHub: NA +* Source code: https://github.com/cran/cmprskcoxmsm +* Date/Publication: 2021-09-04 05:50:02 UTC +* Number of recursive dependencies: 71 + +Run `revdepcheck::cloud_details(, "cmprskcoxmsm")` for more info + +
+ +## In both + +* checking whether package ‘cmprskcoxmsm’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/cmprskcoxmsm/new/cmprskcoxmsm.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘cmprskcoxmsm’ ... +** package ‘cmprskcoxmsm’ successfully unpacked and MD5 sums checked +** 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘cmprskcoxmsm’ +* removing ‘/tmp/workdir/cmprskcoxmsm/new/cmprskcoxmsm.Rcheck/cmprskcoxmsm’ + + +``` +### CRAN + +``` +* installing *source* package ‘cmprskcoxmsm’ ... +** package ‘cmprskcoxmsm’ successfully unpacked and MD5 sums checked +** 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘cmprskcoxmsm’ +* removing ‘/tmp/workdir/cmprskcoxmsm/old/cmprskcoxmsm.Rcheck/cmprskcoxmsm’ + + +``` +# contrast + +
+ +* Version: 0.24.2 +* GitHub: https://github.com/Alanocallaghan/contrast +* Source code: https://github.com/cran/contrast +* Date/Publication: 2022-10-05 17:20:09 UTC +* Number of recursive dependencies: 112 + +Run `revdepcheck::cloud_details(, "contrast")` for more info + +
+ +## In both + +* checking whether package ‘contrast’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/contrast/new/contrast.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘contrast’ ... +** package ‘contrast’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘contrast’ +* removing ‘/tmp/workdir/contrast/new/contrast.Rcheck/contrast’ + + +``` +### CRAN + +``` +* installing *source* package ‘contrast’ ... +** package ‘contrast’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘contrast’ +* removing ‘/tmp/workdir/contrast/old/contrast.Rcheck/contrast’ + + +``` +# coxed + +
+ +* Version: 0.3.3 +* GitHub: https://github.com/jkropko/coxed +* Source code: https://github.com/cran/coxed +* Date/Publication: 2020-08-02 01:20:07 UTC +* Number of recursive dependencies: 109 + +Run `revdepcheck::cloud_details(, "coxed")` for more info + +
+ +## In both + +* checking whether package ‘coxed’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/coxed/new/coxed.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘coxed’ ... +** package ‘coxed’ 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: package or namespace load failed for ‘rms’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Execution halted +ERROR: lazy loading failed for package ‘coxed’ +* removing ‘/tmp/workdir/coxed/new/coxed.Rcheck/coxed’ + + +``` +### CRAN + +``` +* installing *source* package ‘coxed’ ... +** package ‘coxed’ 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: package or namespace load failed for ‘rms’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Execution halted +ERROR: lazy loading failed for package ‘coxed’ +* removing ‘/tmp/workdir/coxed/old/coxed.Rcheck/coxed’ + + +``` +# CRMetrics + +
+ +* Version: 0.3.0 +* GitHub: https://github.com/khodosevichlab/CRMetrics +* Source code: https://github.com/cran/CRMetrics +* Date/Publication: 2023-09-01 09:00:06 UTC +* Number of recursive dependencies: 235 + +Run `revdepcheck::cloud_details(, "CRMetrics")` for more info + +
+ +## In both + +* checking whether package ‘CRMetrics’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/CRMetrics/new/CRMetrics.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘CRMetrics’ ... +** package ‘CRMetrics’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘CRMetrics’ +* removing ‘/tmp/workdir/CRMetrics/new/CRMetrics.Rcheck/CRMetrics’ + + +``` +### CRAN + +``` +* installing *source* package ‘CRMetrics’ ... +** package ‘CRMetrics’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘CRMetrics’ +* removing ‘/tmp/workdir/CRMetrics/old/CRMetrics.Rcheck/CRMetrics’ + + +``` +# csmpv + +
+ +* Version: 1.0.3 +* GitHub: NA +* Source code: https://github.com/cran/csmpv +* Date/Publication: 2024-03-01 18:12:44 UTC +* Number of recursive dependencies: 175 + +Run `revdepcheck::cloud_details(, "csmpv")` for more info + +
+ +## In both + +* checking whether package ‘csmpv’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/csmpv/new/csmpv.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘csmpv’ ... +** package ‘csmpv’ 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 +Warning: replacing previous import ‘ggplot2::ggpar’ by ‘ggpubr::ggpar’ when loading ‘csmpv’ +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘csmpv’ +* removing ‘/tmp/workdir/csmpv/new/csmpv.Rcheck/csmpv’ + + +``` +### CRAN + +``` +* installing *source* package ‘csmpv’ ... +** package ‘csmpv’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘csmpv’ +* removing ‘/tmp/workdir/csmpv/old/csmpv.Rcheck/csmpv’ + + +``` +# ctsem + +
+ +* Version: 3.9.1 +* GitHub: https://github.com/cdriveraus/ctsem +* Source code: https://github.com/cran/ctsem +* Date/Publication: 2023-10-30 14:20:02 UTC +* Number of recursive dependencies: 159 + +Run `revdepcheck::cloud_details(, "ctsem")` for more info + +
+ +## In both + +* checking whether package ‘ctsem’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/ctsem/new/ctsem.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘ctsem’ ... +** package ‘ctsem’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ +using C++17 + + +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I"../inst/include" -I"/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src" -DBOOST_DISABLE_ASSERTS -DEIGEN_NO_DEBUG -DBOOST_MATH_OVERFLOW_ERROR_POLICY=errno_on_error -DUSE_STANC3 -D_HAS_AUTO_PTR_ETC=0 -I'/opt/R/4.3.1/lib/R/site-library/BH/include' -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppEigen/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -I'/opt/R/4.3.1/lib/R/site-library/rstan/include' -I'/opt/R/4.3.1/lib/R/site-library/StanHeaders/include' -I/usr/local/include -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -D_REENTRANT -DSTAN_THREADS -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +In file included from /opt/R/4.3.1/lib/R/site-library/RcppEigen/include/Eigen/Core:205, +... +/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src/stan/mcmc/hmc/hamiltonians/dense_e_metric.hpp:22:56: required from ‘double stan::mcmc::dense_e_metric::T(stan::mcmc::dense_e_point&) [with Model = model_ctsm_namespace::model_ctsm; BaseRNG = boost::random::additive_combine_engine, boost::random::linear_congruential_engine >]’ +/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src/stan/mcmc/hmc/hamiltonians/dense_e_metric.hpp:21:10: required from here +/opt/R/4.3.1/lib/R/site-library/RcppEigen/include/Eigen/src/Core/DenseCoeffsBase.h:654:34: warning: ignoring attributes on template argument ‘Eigen::internal::packet_traits::type’ {aka ‘__vector(2) double’} [-Wignored-attributes] + 654 | return internal::first_aligned::alignment),Derived>(m); + | ^~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +g++: fatal error: Killed signal terminated program cc1plus +compilation terminated. +make: *** [/opt/R/4.3.1/lib/R/etc/Makeconf:198: stanExports_ctsm.o] Error 1 +ERROR: compilation failed for package ‘ctsem’ +* removing ‘/tmp/workdir/ctsem/new/ctsem.Rcheck/ctsem’ + + +``` +### CRAN + +``` +* installing *source* package ‘ctsem’ ... +** package ‘ctsem’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ +using C++17 + + +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I"../inst/include" -I"/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src" -DBOOST_DISABLE_ASSERTS -DEIGEN_NO_DEBUG -DBOOST_MATH_OVERFLOW_ERROR_POLICY=errno_on_error -DUSE_STANC3 -D_HAS_AUTO_PTR_ETC=0 -I'/opt/R/4.3.1/lib/R/site-library/BH/include' -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppEigen/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -I'/opt/R/4.3.1/lib/R/site-library/rstan/include' -I'/opt/R/4.3.1/lib/R/site-library/StanHeaders/include' -I/usr/local/include -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -D_REENTRANT -DSTAN_THREADS -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +In file included from /opt/R/4.3.1/lib/R/site-library/RcppEigen/include/Eigen/Core:205, +... +/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src/stan/mcmc/hmc/hamiltonians/dense_e_metric.hpp:22:56: required from ‘double stan::mcmc::dense_e_metric::T(stan::mcmc::dense_e_point&) [with Model = model_ctsm_namespace::model_ctsm; BaseRNG = boost::random::additive_combine_engine, boost::random::linear_congruential_engine >]’ +/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src/stan/mcmc/hmc/hamiltonians/dense_e_metric.hpp:21:10: required from here +/opt/R/4.3.1/lib/R/site-library/RcppEigen/include/Eigen/src/Core/DenseCoeffsBase.h:654:34: warning: ignoring attributes on template argument ‘Eigen::internal::packet_traits::type’ {aka ‘__vector(2) double’} [-Wignored-attributes] + 654 | return internal::first_aligned::alignment),Derived>(m); + | ^~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +g++: fatal error: Killed signal terminated program cc1plus +compilation terminated. +make: *** [/opt/R/4.3.1/lib/R/etc/Makeconf:198: stanExports_ctsm.o] Error 1 +ERROR: compilation failed for package ‘ctsem’ +* removing ‘/tmp/workdir/ctsem/old/ctsem.Rcheck/ctsem’ + + +``` +# DepthProc + +
+ +* Version: 2.1.5 +* GitHub: https://github.com/zzawadz/DepthProc +* Source code: https://github.com/cran/DepthProc +* Date/Publication: 2022-02-03 20:30:02 UTC +* Number of recursive dependencies: 134 + +Run `revdepcheck::cloud_details(, "DepthProc")` for more info + +
+ +## In both + +* checking whether package ‘DepthProc’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/DepthProc/new/DepthProc.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘DepthProc’ ... +** package ‘DepthProc’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ +using C++11 +g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c Depth.cpp -o Depth.o +g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c LocationEstimators.cpp -o LocationEstimators.o +g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c LocationScaleDepth.cpp -o LocationScaleDepth.o +g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c LocationScaleDepthCPP.cpp -o LocationScaleDepthCPP.o +... +installing to /tmp/workdir/DepthProc/new/DepthProc.Rcheck/00LOCK-DepthProc/00new/DepthProc/libs +** R +** data +** inst +** byte-compile and prepare package for lazy loading +Error: package or namespace load failed for ‘np’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Execution halted +ERROR: lazy loading failed for package ‘DepthProc’ +* removing ‘/tmp/workdir/DepthProc/new/DepthProc.Rcheck/DepthProc’ + + +``` +### CRAN + +``` +* installing *source* package ‘DepthProc’ ... +** package ‘DepthProc’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ +using C++11 +g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c Depth.cpp -o Depth.o +g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c LocationEstimators.cpp -o LocationEstimators.o +g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c LocationScaleDepth.cpp -o LocationScaleDepth.o +g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c LocationScaleDepthCPP.cpp -o LocationScaleDepthCPP.o +... +installing to /tmp/workdir/DepthProc/old/DepthProc.Rcheck/00LOCK-DepthProc/00new/DepthProc/libs +** R +** data +** inst +** byte-compile and prepare package for lazy loading +Error: package or namespace load failed for ‘np’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Execution halted +ERROR: lazy loading failed for package ‘DepthProc’ +* removing ‘/tmp/workdir/DepthProc/old/DepthProc.Rcheck/DepthProc’ + + +``` +# DR.SC + +
+ +* Version: 3.4 +* GitHub: https://github.com/feiyoung/DR.SC +* Source code: https://github.com/cran/DR.SC +* Date/Publication: 2024-03-19 08:40:02 UTC +* Number of recursive dependencies: 150 + +Run `revdepcheck::cloud_details(, "DR.SC")` for more info + +
+ +## In both + +* checking whether package ‘DR.SC’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/DR.SC/new/DR.SC.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘DR.SC’ ... +** package ‘DR.SC’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ +using C++17 +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -DARMA_64BIT_WORD -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -DARMA_64BIT_WORD -fpic -g -O2 -c getNB_fast.cpp -o getNB_fast.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -DARMA_64BIT_WORD -fpic -g -O2 -c mt_paral_job.cpp -o mt_paral_job.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -DARMA_64BIT_WORD -fpic -g -O2 -c mt_paral_job2.cpp -o mt_paral_job2.o +... +** R +** data +** inst +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.3 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘DR.SC’ +* removing ‘/tmp/workdir/DR.SC/new/DR.SC.Rcheck/DR.SC’ + + +``` +### CRAN + +``` +* installing *source* package ‘DR.SC’ ... +** package ‘DR.SC’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ +using C++17 +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -DARMA_64BIT_WORD -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -DARMA_64BIT_WORD -fpic -g -O2 -c getNB_fast.cpp -o getNB_fast.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -DARMA_64BIT_WORD -fpic -g -O2 -c mt_paral_job.cpp -o mt_paral_job.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -DARMA_64BIT_WORD -fpic -g -O2 -c mt_paral_job2.cpp -o mt_paral_job2.o +... +** R +** data +** inst +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.3 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘DR.SC’ +* removing ‘/tmp/workdir/DR.SC/old/DR.SC.Rcheck/DR.SC’ + + +``` +# EcoEnsemble + +
+ +* Version: 1.0.5 +* GitHub: NA +* Source code: https://github.com/cran/EcoEnsemble +* Date/Publication: 2023-09-18 11:50:02 UTC +* Number of recursive dependencies: 91 + +Run `revdepcheck::cloud_details(, "EcoEnsemble")` for more info + +
+ +## In both + +* checking whether package ‘EcoEnsemble’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/EcoEnsemble/new/EcoEnsemble.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘EcoEnsemble’ ... +** package ‘EcoEnsemble’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ +using C++17 + + +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I"../inst/include" -I"/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src" -DBOOST_DISABLE_ASSERTS -DEIGEN_NO_DEBUG -DBOOST_MATH_OVERFLOW_ERROR_POLICY=errno_on_error -DUSE_STANC3 -D_HAS_AUTO_PTR_ETC=0 -I'/opt/R/4.3.1/lib/R/site-library/BH/include' -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppEigen/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -I'/opt/R/4.3.1/lib/R/site-library/rstan/include' -I'/opt/R/4.3.1/lib/R/site-library/StanHeaders/include' -I/usr/local/include -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -D_REENTRANT -DSTAN_THREADS -fpic -g -O2 -c KF_back.cpp -o KF_back.o +In file included from /opt/R/4.3.1/lib/R/site-library/RcppEigen/include/Eigen/Core:205, +... +/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src/stan/mcmc/hmc/hamiltonians/dense_e_metric.hpp:22:56: required from ‘double stan::mcmc::dense_e_metric::T(stan::mcmc::dense_e_point&) [with Model = model_ensemble_model_namespace::model_ensemble_model; BaseRNG = boost::random::additive_combine_engine, boost::random::linear_congruential_engine >]’ +/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src/stan/mcmc/hmc/hamiltonians/dense_e_metric.hpp:21:10: required from here +/opt/R/4.3.1/lib/R/site-library/RcppEigen/include/Eigen/src/Core/DenseCoeffsBase.h:654:34: warning: ignoring attributes on template argument ‘Eigen::internal::packet_traits::type’ {aka ‘__vector(2) double’} [-Wignored-attributes] + 654 | return internal::first_aligned::alignment),Derived>(m); + | ^~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +g++: fatal error: Killed signal terminated program cc1plus +compilation terminated. +make: *** [/opt/R/4.3.1/lib/R/etc/Makeconf:198: stanExports_ensemble_model.o] Error 1 +ERROR: compilation failed for package ‘EcoEnsemble’ +* removing ‘/tmp/workdir/EcoEnsemble/new/EcoEnsemble.Rcheck/EcoEnsemble’ + + +``` +### CRAN + +``` +* installing *source* package ‘EcoEnsemble’ ... +** package ‘EcoEnsemble’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ +using C++17 + + +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I"../inst/include" -I"/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src" -DBOOST_DISABLE_ASSERTS -DEIGEN_NO_DEBUG -DBOOST_MATH_OVERFLOW_ERROR_POLICY=errno_on_error -DUSE_STANC3 -D_HAS_AUTO_PTR_ETC=0 -I'/opt/R/4.3.1/lib/R/site-library/BH/include' -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppEigen/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -I'/opt/R/4.3.1/lib/R/site-library/rstan/include' -I'/opt/R/4.3.1/lib/R/site-library/StanHeaders/include' -I/usr/local/include -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -D_REENTRANT -DSTAN_THREADS -fpic -g -O2 -c KF_back.cpp -o KF_back.o +In file included from /opt/R/4.3.1/lib/R/site-library/RcppEigen/include/Eigen/Core:205, +... +/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src/stan/mcmc/hmc/hamiltonians/dense_e_metric.hpp:22:56: required from ‘double stan::mcmc::dense_e_metric::T(stan::mcmc::dense_e_point&) [with Model = model_ensemble_model_namespace::model_ensemble_model; BaseRNG = boost::random::additive_combine_engine, boost::random::linear_congruential_engine >]’ +/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src/stan/mcmc/hmc/hamiltonians/dense_e_metric.hpp:21:10: required from here +/opt/R/4.3.1/lib/R/site-library/RcppEigen/include/Eigen/src/Core/DenseCoeffsBase.h:654:34: warning: ignoring attributes on template argument ‘Eigen::internal::packet_traits::type’ {aka ‘__vector(2) double’} [-Wignored-attributes] + 654 | return internal::first_aligned::alignment),Derived>(m); + | ^~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +g++: fatal error: Killed signal terminated program cc1plus +compilation terminated. +make: *** [/opt/R/4.3.1/lib/R/etc/Makeconf:198: stanExports_ensemble_model.o] Error 1 +ERROR: compilation failed for package ‘EcoEnsemble’ +* removing ‘/tmp/workdir/EcoEnsemble/old/EcoEnsemble.Rcheck/EcoEnsemble’ + + +``` +# ecolottery + +
+ +* Version: 1.0.0 +* GitHub: https://github.com/frmunoz/ecolottery +* Source code: https://github.com/cran/ecolottery +* Date/Publication: 2017-07-03 11:01:29 UTC +* Number of recursive dependencies: 88 + +Run `revdepcheck::cloud_details(, "ecolottery")` for more info + +
+ +## In both + +* checking whether package ‘ecolottery’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/ecolottery/new/ecolottery.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘ecolottery’ ... +** package ‘ecolottery’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘ecolottery’ +* removing ‘/tmp/workdir/ecolottery/new/ecolottery.Rcheck/ecolottery’ + + +``` +### CRAN + +``` +* installing *source* package ‘ecolottery’ ... +** package ‘ecolottery’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘ecolottery’ +* removing ‘/tmp/workdir/ecolottery/old/ecolottery.Rcheck/ecolottery’ + + +``` +# EpiEstim + +
+ +* Version: 2.2-4 +* GitHub: https://github.com/mrc-ide/EpiEstim +* Source code: https://github.com/cran/EpiEstim +* Date/Publication: 2021-01-07 16:20:10 UTC +* Number of recursive dependencies: 91 + +Run `revdepcheck::cloud_details(, "EpiEstim")` for more info + +
+ +## In both + +* checking whether package ‘EpiEstim’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/EpiEstim/new/EpiEstim.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘EpiEstim’ ... +** package ‘EpiEstim’ successfully unpacked and MD5 sums checked +** 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘EpiEstim’ +* removing ‘/tmp/workdir/EpiEstim/new/EpiEstim.Rcheck/EpiEstim’ + + +``` +### CRAN + +``` +* installing *source* package ‘EpiEstim’ ... +** package ‘EpiEstim’ successfully unpacked and MD5 sums checked +** 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘EpiEstim’ +* removing ‘/tmp/workdir/EpiEstim/old/EpiEstim.Rcheck/EpiEstim’ + + +``` +# evolqg + +
+ +* Version: 0.3-4 +* GitHub: https://github.com/lem-usp/evolqg +* Source code: https://github.com/cran/evolqg +* Date/Publication: 2023-12-05 15:20:12 UTC +* Number of recursive dependencies: 111 + +Run `revdepcheck::cloud_details(, "evolqg")` for more info + +
+ +## In both + +* checking whether package ‘evolqg’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/evolqg/new/evolqg.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘evolqg’ ... +** package ‘evolqg’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c fast_RS.cpp -o fast_RS.o +g++ -std=gnu++17 -shared -L/opt/R/4.3.1/lib/R/lib -L/usr/local/lib -o evolqg.so RcppExports.o fast_RS.o -llapack -lblas -lgfortran -lm -lquadmath -L/opt/R/4.3.1/lib/R/lib -lR +installing to /tmp/workdir/evolqg/new/evolqg.Rcheck/00LOCK-evolqg/00new/evolqg/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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘evolqg’ +* removing ‘/tmp/workdir/evolqg/new/evolqg.Rcheck/evolqg’ + + +``` +### CRAN + +``` +* installing *source* package ‘evolqg’ ... +** package ‘evolqg’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c fast_RS.cpp -o fast_RS.o +g++ -std=gnu++17 -shared -L/opt/R/4.3.1/lib/R/lib -L/usr/local/lib -o evolqg.so RcppExports.o fast_RS.o -llapack -lblas -lgfortran -lm -lquadmath -L/opt/R/4.3.1/lib/R/lib -lR +installing to /tmp/workdir/evolqg/old/evolqg.Rcheck/00LOCK-evolqg/00new/evolqg/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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘evolqg’ +* removing ‘/tmp/workdir/evolqg/old/evolqg.Rcheck/evolqg’ + + +``` +# ForecastComb + +
+ +* Version: 1.3.1 +* GitHub: https://github.com/ceweiss/ForecastComb +* Source code: https://github.com/cran/ForecastComb +* Date/Publication: 2018-08-07 13:50:08 UTC +* Number of recursive dependencies: 73 + +Run `revdepcheck::cloud_details(, "ForecastComb")` for more info + +
+ +## In both + +* checking whether package ‘ForecastComb’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/ForecastComb/new/ForecastComb.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘ForecastComb’ ... +** package ‘ForecastComb’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** data +*** moving datasets to lazyload DB +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘ForecastComb’ +* removing ‘/tmp/workdir/ForecastComb/new/ForecastComb.Rcheck/ForecastComb’ + + +``` +### CRAN + +``` +* installing *source* package ‘ForecastComb’ ... +** package ‘ForecastComb’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** data +*** moving datasets to lazyload DB +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘ForecastComb’ +* removing ‘/tmp/workdir/ForecastComb/old/ForecastComb.Rcheck/ForecastComb’ + + +``` +# gapfill + +
+ +* Version: 0.9.6-1 +* GitHub: https://github.com/florafauna/gapfill +* Source code: https://github.com/cran/gapfill +* Date/Publication: 2021-02-12 10:10:05 UTC +* Number of recursive dependencies: 71 + +Run `revdepcheck::cloud_details(, "gapfill")` for more info + +
+ +## In both + +* checking whether package ‘gapfill’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/gapfill/new/gapfill.Rcheck/00install.out’ for details. + ``` + +* checking package dependencies ... NOTE + ``` + Packages which this enhances but not available for checking: + 'raster', 'doParallel', 'doMPI' + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘gapfill’ ... +** package ‘gapfill’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c gapfill.cpp -o gapfill.o +g++ -std=gnu++17 -shared -L/opt/R/4.3.1/lib/R/lib -L/usr/local/lib -o gapfill.so RcppExports.o gapfill.o -L/opt/R/4.3.1/lib/R/lib -lR +installing to /tmp/workdir/gapfill/new/gapfill.Rcheck/00LOCK-gapfill/00new/gapfill/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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘gapfill’ +* removing ‘/tmp/workdir/gapfill/new/gapfill.Rcheck/gapfill’ + + +``` +### CRAN + +``` +* installing *source* package ‘gapfill’ ... +** package ‘gapfill’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c gapfill.cpp -o gapfill.o +g++ -std=gnu++17 -shared -L/opt/R/4.3.1/lib/R/lib -L/usr/local/lib -o gapfill.so RcppExports.o gapfill.o -L/opt/R/4.3.1/lib/R/lib -lR +installing to /tmp/workdir/gapfill/old/gapfill.Rcheck/00LOCK-gapfill/00new/gapfill/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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘gapfill’ +* removing ‘/tmp/workdir/gapfill/old/gapfill.Rcheck/gapfill’ + + +``` +# GeomComb + +
+ +* Version: 1.0 +* GitHub: https://github.com/ceweiss/GeomComb +* Source code: https://github.com/cran/GeomComb +* Date/Publication: 2016-11-27 16:02:26 +* Number of recursive dependencies: 74 + +Run `revdepcheck::cloud_details(, "GeomComb")` for more info + +
+ +## In both + +* checking whether package ‘GeomComb’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/GeomComb/new/GeomComb.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘GeomComb’ ... +** package ‘GeomComb’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘GeomComb’ +* removing ‘/tmp/workdir/GeomComb/new/GeomComb.Rcheck/GeomComb’ + + +``` +### CRAN + +``` +* installing *source* package ‘GeomComb’ ... +** package ‘GeomComb’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘GeomComb’ +* removing ‘/tmp/workdir/GeomComb/old/GeomComb.Rcheck/GeomComb’ + + +``` +# geostan + +
+ +* Version: 0.6.0 +* GitHub: https://github.com/ConnorDonegan/geostan +* Source code: https://github.com/cran/geostan +* Date/Publication: 2024-04-16 14:00:02 UTC +* Number of recursive dependencies: 108 + +Run `revdepcheck::cloud_details(, "geostan")` for more info + +
+ +## In both + +* checking whether package ‘geostan’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/geostan/new/geostan.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘geostan’ ... +** package ‘geostan’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ +using C++17 + + +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I"../inst/include" -I"/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src" -DBOOST_DISABLE_ASSERTS -DEIGEN_NO_DEBUG -DBOOST_MATH_OVERFLOW_ERROR_POLICY=errno_on_error -DUSE_STANC3 -D_HAS_AUTO_PTR_ETC=0 -I'/opt/R/4.3.1/lib/R/site-library/BH/include' -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppEigen/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -I'/opt/R/4.3.1/lib/R/site-library/rstan/include' -I'/opt/R/4.3.1/lib/R/site-library/StanHeaders/include' -I/usr/local/include -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -D_REENTRANT -DSTAN_THREADS -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +In file included from /opt/R/4.3.1/lib/R/site-library/RcppEigen/include/Eigen/Core:205, +... +/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src/stan/mcmc/hmc/hamiltonians/dense_e_metric.hpp:22:56: required from ‘double stan::mcmc::dense_e_metric::T(stan::mcmc::dense_e_point&) [with Model = model_foundation_namespace::model_foundation; BaseRNG = boost::random::additive_combine_engine, boost::random::linear_congruential_engine >]’ +/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src/stan/mcmc/hmc/hamiltonians/dense_e_metric.hpp:21:10: required from here +/opt/R/4.3.1/lib/R/site-library/RcppEigen/include/Eigen/src/Core/DenseCoeffsBase.h:654:34: warning: ignoring attributes on template argument ‘Eigen::internal::packet_traits::type’ {aka ‘__vector(2) double’} [-Wignored-attributes] + 654 | return internal::first_aligned::alignment),Derived>(m); + | ^~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +g++: fatal error: Killed signal terminated program cc1plus +compilation terminated. +make: *** [/opt/R/4.3.1/lib/R/etc/Makeconf:198: stanExports_foundation.o] Error 1 +ERROR: compilation failed for package ‘geostan’ +* removing ‘/tmp/workdir/geostan/new/geostan.Rcheck/geostan’ + + +``` +### CRAN + +``` +* installing *source* package ‘geostan’ ... +** package ‘geostan’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ +using C++17 + + +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I"../inst/include" -I"/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src" -DBOOST_DISABLE_ASSERTS -DEIGEN_NO_DEBUG -DBOOST_MATH_OVERFLOW_ERROR_POLICY=errno_on_error -DUSE_STANC3 -D_HAS_AUTO_PTR_ETC=0 -I'/opt/R/4.3.1/lib/R/site-library/BH/include' -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppEigen/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -I'/opt/R/4.3.1/lib/R/site-library/rstan/include' -I'/opt/R/4.3.1/lib/R/site-library/StanHeaders/include' -I/usr/local/include -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -D_REENTRANT -DSTAN_THREADS -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +In file included from /opt/R/4.3.1/lib/R/site-library/RcppEigen/include/Eigen/Core:205, +... +/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src/stan/mcmc/hmc/hamiltonians/dense_e_metric.hpp:22:56: required from ‘double stan::mcmc::dense_e_metric::T(stan::mcmc::dense_e_point&) [with Model = model_foundation_namespace::model_foundation; BaseRNG = boost::random::additive_combine_engine, boost::random::linear_congruential_engine >]’ +/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src/stan/mcmc/hmc/hamiltonians/dense_e_metric.hpp:21:10: required from here +/opt/R/4.3.1/lib/R/site-library/RcppEigen/include/Eigen/src/Core/DenseCoeffsBase.h:654:34: warning: ignoring attributes on template argument ‘Eigen::internal::packet_traits::type’ {aka ‘__vector(2) double’} [-Wignored-attributes] + 654 | return internal::first_aligned::alignment),Derived>(m); + | ^~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +g++: fatal error: Killed signal terminated program cc1plus +compilation terminated. +make: *** [/opt/R/4.3.1/lib/R/etc/Makeconf:198: stanExports_foundation.o] Error 1 +ERROR: compilation failed for package ‘geostan’ +* removing ‘/tmp/workdir/geostan/old/geostan.Rcheck/geostan’ + + +``` +# ggpmisc + +
+ +* Version: 0.5.5 +* GitHub: https://github.com/aphalo/ggpmisc +* Source code: https://github.com/cran/ggpmisc +* Date/Publication: 2023-11-15 09:30:02 UTC +* Number of recursive dependencies: 109 + +Run `revdepcheck::cloud_details(, "ggpmisc")` for more info + +
+ +## In both + +* checking whether package ‘ggpmisc’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/ggpmisc/new/ggpmisc.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘ggpmisc’ ... +** package ‘ggpmisc’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘ggpmisc’ +* removing ‘/tmp/workdir/ggpmisc/new/ggpmisc.Rcheck/ggpmisc’ + + +``` +### CRAN + +``` +* installing *source* package ‘ggpmisc’ ... +** package ‘ggpmisc’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘ggpmisc’ +* removing ‘/tmp/workdir/ggpmisc/old/ggpmisc.Rcheck/ggpmisc’ + + +``` +# ggrcs + +
+ +* Version: 0.3.8 +* GitHub: NA +* Source code: https://github.com/cran/ggrcs +* Date/Publication: 2024-01-30 03:20:08 UTC +* Number of recursive dependencies: 78 + +Run `revdepcheck::cloud_details(, "ggrcs")` for more info + +
+ +## In both + +* checking whether package ‘ggrcs’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/ggrcs/new/ggrcs.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘ggrcs’ ... +** package ‘ggrcs’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘ggrcs’ +* removing ‘/tmp/workdir/ggrcs/new/ggrcs.Rcheck/ggrcs’ + + +``` +### CRAN + +``` +* installing *source* package ‘ggrcs’ ... +** package ‘ggrcs’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘ggrcs’ +* removing ‘/tmp/workdir/ggrcs/old/ggrcs.Rcheck/ggrcs’ + + +``` +# ggrisk + +
+ +* Version: 1.3 +* GitHub: https://github.com/yikeshu0611/ggrisk +* Source code: https://github.com/cran/ggrisk +* Date/Publication: 2021-08-09 07:40:06 UTC +* Number of recursive dependencies: 115 + +Run `revdepcheck::cloud_details(, "ggrisk")` for more info + +
+ +## In both + +* checking whether package ‘ggrisk’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/ggrisk/new/ggrisk.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘ggrisk’ ... +** package ‘ggrisk’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** data +*** moving datasets to lazyload DB +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘ggrisk’ +* removing ‘/tmp/workdir/ggrisk/new/ggrisk.Rcheck/ggrisk’ + + +``` +### CRAN + +``` +* installing *source* package ‘ggrisk’ ... +** package ‘ggrisk’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** data +*** moving datasets to lazyload DB +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘ggrisk’ +* removing ‘/tmp/workdir/ggrisk/old/ggrisk.Rcheck/ggrisk’ + + +``` +# gJLS2 + +
+ +* Version: 0.2.0 +* GitHub: NA +* Source code: https://github.com/cran/gJLS2 +* Date/Publication: 2021-09-30 09:00:05 UTC +* Number of recursive dependencies: 45 + +Run `revdepcheck::cloud_details(, "gJLS2")` for more info + +
+ +## In both + +* checking whether package ‘gJLS2’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/gJLS2/new/gJLS2.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘gJLS2’ ... +** package ‘gJLS2’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘gJLS2’ +* removing ‘/tmp/workdir/gJLS2/new/gJLS2.Rcheck/gJLS2’ + + +``` +### CRAN + +``` +* installing *source* package ‘gJLS2’ ... +** package ‘gJLS2’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘gJLS2’ +* removing ‘/tmp/workdir/gJLS2/old/gJLS2.Rcheck/gJLS2’ + + +``` +# Greg + +
+ +* Version: 2.0.2 +* GitHub: https://github.com/gforge/Greg +* Source code: https://github.com/cran/Greg +* Date/Publication: 2024-01-29 13:30:21 UTC +* Number of recursive dependencies: 152 + +Run `revdepcheck::cloud_details(, "Greg")` for more info + +
+ +## In both + +* checking whether package ‘Greg’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/Greg/new/Greg.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘Greg’ ... +** package ‘Greg’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘Greg’ +* removing ‘/tmp/workdir/Greg/new/Greg.Rcheck/Greg’ + + +``` +### CRAN + +``` +* installing *source* package ‘Greg’ ... +** package ‘Greg’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘Greg’ +* removing ‘/tmp/workdir/Greg/old/Greg.Rcheck/Greg’ + + +``` +# greport + +
+ +* Version: 0.7-4 +* GitHub: https://github.com/harrelfe/greport +* Source code: https://github.com/cran/greport +* Date/Publication: 2023-09-02 22:20:02 UTC +* Number of recursive dependencies: 84 + +Run `revdepcheck::cloud_details(, "greport")` for more info + +
+ +## In both + +* checking whether package ‘greport’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/greport/new/greport.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘greport’ ... +** package ‘greport’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘greport’ +* removing ‘/tmp/workdir/greport/new/greport.Rcheck/greport’ + + +``` +### CRAN + +``` +* installing *source* package ‘greport’ ... +** package ‘greport’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘greport’ +* removing ‘/tmp/workdir/greport/old/greport.Rcheck/greport’ + + +``` +# hettx + +
+ +* Version: 0.1.3 +* GitHub: https://github.com/bfifield/hettx +* Source code: https://github.com/cran/hettx +* Date/Publication: 2023-08-19 22:22:34 UTC +* Number of recursive dependencies: 85 + +Run `revdepcheck::cloud_details(, "hettx")` for more info + +
+ +## In both + +* checking whether package ‘hettx’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/hettx/new/hettx.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘hettx’ ... +** package ‘hettx’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘hettx’ +* removing ‘/tmp/workdir/hettx/new/hettx.Rcheck/hettx’ + + +``` +### CRAN + +``` +* installing *source* package ‘hettx’ ... +** package ‘hettx’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘hettx’ +* removing ‘/tmp/workdir/hettx/old/hettx.Rcheck/hettx’ + + +``` +# hIRT + +
+ +* Version: 0.3.0 +* GitHub: https://github.com/xiangzhou09/hIRT +* Source code: https://github.com/cran/hIRT +* Date/Publication: 2020-03-26 17:10:02 UTC +* Number of recursive dependencies: 88 + +Run `revdepcheck::cloud_details(, "hIRT")` for more info + +
+ +## In both + +* checking whether package ‘hIRT’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/hIRT/new/hIRT.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘hIRT’ ... +** package ‘hIRT’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** data +*** moving datasets to lazyload DB +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘hIRT’ +* removing ‘/tmp/workdir/hIRT/new/hIRT.Rcheck/hIRT’ + + +``` +### CRAN + +``` +* installing *source* package ‘hIRT’ ... +** package ‘hIRT’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** data +*** moving datasets to lazyload DB +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘hIRT’ +* removing ‘/tmp/workdir/hIRT/old/hIRT.Rcheck/hIRT’ + + +``` +# Hmsc + +
+ +* Version: 3.0-13 +* GitHub: https://github.com/hmsc-r/HMSC +* Source code: https://github.com/cran/Hmsc +* Date/Publication: 2022-08-11 14:10:14 UTC +* Number of recursive dependencies: 76 + +Run `revdepcheck::cloud_details(, "Hmsc")` for more info + +
+ +## In both + +* checking whether package ‘Hmsc’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/Hmsc/new/Hmsc.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘Hmsc’ ... +** package ‘Hmsc’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘Hmsc’ +* removing ‘/tmp/workdir/Hmsc/new/Hmsc.Rcheck/Hmsc’ + + +``` +### CRAN + +``` +* installing *source* package ‘Hmsc’ ... +** package ‘Hmsc’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘Hmsc’ +* removing ‘/tmp/workdir/Hmsc/old/Hmsc.Rcheck/Hmsc’ + + +``` +# inventorize + +
+ +* Version: 1.1.1 +* GitHub: NA +* Source code: https://github.com/cran/inventorize +* Date/Publication: 2022-05-31 22:20:09 UTC +* Number of recursive dependencies: 71 + +Run `revdepcheck::cloud_details(, "inventorize")` for more info + +
+ +## Newly broken + +* checking whether package ‘inventorize’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/inventorize/new/inventorize.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘inventorize’ ... +** package ‘inventorize’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** byte-compile and prepare package for lazy loading +Error in compute_geom_2(..., self = self) : + argument "theme" is missing, with no default +Error: unable to load R code in package ‘inventorize’ +Execution halted +ERROR: lazy loading failed for package ‘inventorize’ +* removing ‘/tmp/workdir/inventorize/new/inventorize.Rcheck/inventorize’ + + +``` +### CRAN + +``` +* installing *source* package ‘inventorize’ ... +** package ‘inventorize’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** byte-compile and prepare package for lazy loading +Warning in qgamma(service_level, alpha, beta) : NaNs produced +Warning in qgamma(service_level, alpha, beta) : NaNs produced +** help +*** installing help indices +** building package indices +** testing if installed package can be loaded from temporary location +** testing if installed package can be loaded from final location +** testing if installed package keeps a record of temporary installation path +* DONE (inventorize) + + +``` +# iNZightPlots + +
+ +* Version: 2.15.3 +* GitHub: https://github.com/iNZightVIT/iNZightPlots +* Source code: https://github.com/cran/iNZightPlots +* Date/Publication: 2023-10-14 05:00:02 UTC +* Number of recursive dependencies: 162 + +Run `revdepcheck::cloud_details(, "iNZightPlots")` for more info + +
+ +## In both + +* checking whether package ‘iNZightPlots’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/iNZightPlots/new/iNZightPlots.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘iNZightPlots’ ... +** package ‘iNZightPlots’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘iNZightPlots’ +* removing ‘/tmp/workdir/iNZightPlots/new/iNZightPlots.Rcheck/iNZightPlots’ + + +``` +### CRAN + +``` +* installing *source* package ‘iNZightPlots’ ... +** package ‘iNZightPlots’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘iNZightPlots’ +* removing ‘/tmp/workdir/iNZightPlots/old/iNZightPlots.Rcheck/iNZightPlots’ + + +``` +# iNZightRegression + +
+ +* Version: 1.3.4 +* GitHub: https://github.com/iNZightVIT/iNZightRegression +* Source code: https://github.com/cran/iNZightRegression +* Date/Publication: 2024-04-05 02:32:59 UTC +* Number of recursive dependencies: 154 + +Run `revdepcheck::cloud_details(, "iNZightRegression")` for more info + +
+ +## In both + +* checking whether package ‘iNZightRegression’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/iNZightRegression/new/iNZightRegression.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘iNZightRegression’ ... +** package ‘iNZightRegression’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘iNZightRegression’ +* removing ‘/tmp/workdir/iNZightRegression/new/iNZightRegression.Rcheck/iNZightRegression’ + + +``` +### CRAN + +``` +* installing *source* package ‘iNZightRegression’ ... +** package ‘iNZightRegression’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘iNZightRegression’ +* removing ‘/tmp/workdir/iNZightRegression/old/iNZightRegression.Rcheck/iNZightRegression’ + + +``` +# IRexamples + +
+ +* Version: 0.0.4 +* GitHub: https://github.com/vinhdizzo/IRexamples +* Source code: https://github.com/cran/IRexamples +* Date/Publication: 2023-10-06 06:40:02 UTC +* Number of recursive dependencies: 185 + +Run `revdepcheck::cloud_details(, "IRexamples")` for more info + +
+ +## In both + +* checking whether package ‘IRexamples’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/IRexamples/new/IRexamples.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘IRexamples’ ... +** package ‘IRexamples’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘IRexamples’ +* removing ‘/tmp/workdir/IRexamples/new/IRexamples.Rcheck/IRexamples’ + + +``` +### CRAN + +``` +* installing *source* package ‘IRexamples’ ... +** package ‘IRexamples’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘IRexamples’ +* removing ‘/tmp/workdir/IRexamples/old/IRexamples.Rcheck/IRexamples’ + + +``` +# joineRML + +
+ +* Version: 0.4.6 +* GitHub: https://github.com/graemeleehickey/joineRML +* Source code: https://github.com/cran/joineRML +* Date/Publication: 2023-01-20 04:50:02 UTC +* Number of recursive dependencies: 91 + +Run `revdepcheck::cloud_details(, "joineRML")` for more info + +
+ +## In both + +* checking whether package ‘joineRML’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/joineRML/new/joineRML.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘joineRML’ ... +** package ‘joineRML’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C compiler: ‘gcc (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ +using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ +using C++11 +g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c expW.cpp -o expW.o +g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c gammaUpdate.cpp -o gammaUpdate.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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘joineRML’ +* removing ‘/tmp/workdir/joineRML/new/joineRML.Rcheck/joineRML’ + + +``` +### CRAN + +``` +* installing *source* package ‘joineRML’ ... +** package ‘joineRML’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C compiler: ‘gcc (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ +using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ +using C++11 +g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c expW.cpp -o expW.o +g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c gammaUpdate.cpp -o gammaUpdate.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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘joineRML’ +* removing ‘/tmp/workdir/joineRML/old/joineRML.Rcheck/joineRML’ + + +``` +# JWileymisc + +
+ +* Version: 1.4.1 +* GitHub: https://github.com/JWiley/JWileymisc +* Source code: https://github.com/cran/JWileymisc +* Date/Publication: 2023-10-05 04:50:02 UTC +* Number of recursive dependencies: 164 + +Run `revdepcheck::cloud_details(, "JWileymisc")` for more info + +
+ +## In both + +* checking whether package ‘JWileymisc’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/JWileymisc/new/JWileymisc.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘JWileymisc’ ... +** package ‘JWileymisc’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘JWileymisc’ +* removing ‘/tmp/workdir/JWileymisc/new/JWileymisc.Rcheck/JWileymisc’ + + +``` +### CRAN + +``` +* installing *source* package ‘JWileymisc’ ... +** package ‘JWileymisc’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘JWileymisc’ +* removing ‘/tmp/workdir/JWileymisc/old/JWileymisc.Rcheck/JWileymisc’ + + +``` +# kmc + +
+ +* Version: 0.4-2 +* GitHub: https://github.com/yfyang86/kmc +* Source code: https://github.com/cran/kmc +* Date/Publication: 2022-11-22 08:30:02 UTC +* Number of recursive dependencies: 61 + +Run `revdepcheck::cloud_details(, "kmc")` for more info + +
+ +## In both + +* checking whether package ‘kmc’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/kmc/new/kmc.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘kmc’ ... +** package ‘kmc’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C compiler: ‘gcc (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ +using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c RcppExport.cpp -o RcppExport.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c kmc.cpp -o kmc.o +gcc -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c kmc_init.c -o kmc_init.o +gcc -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c surv2.c -o surv2.o +g++ -std=gnu++17 -shared -L/opt/R/4.3.1/lib/R/lib -L/usr/local/lib -o kmc.so RcppExport.o kmc.o kmc_init.o surv2.o -L/opt/R/4.3.1/lib/R/lib -lR +installing to /tmp/workdir/kmc/new/kmc.Rcheck/00LOCK-kmc/00new/kmc/libs +** R +** byte-compile and prepare package for lazy loading +Error: package or namespace load failed for ‘emplik’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Execution halted +ERROR: lazy loading failed for package ‘kmc’ +* removing ‘/tmp/workdir/kmc/new/kmc.Rcheck/kmc’ + + +``` +### CRAN + +``` +* installing *source* package ‘kmc’ ... +** package ‘kmc’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C compiler: ‘gcc (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ +using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c RcppExport.cpp -o RcppExport.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c kmc.cpp -o kmc.o +gcc -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c kmc_init.c -o kmc_init.o +gcc -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c surv2.c -o surv2.o +g++ -std=gnu++17 -shared -L/opt/R/4.3.1/lib/R/lib -L/usr/local/lib -o kmc.so RcppExport.o kmc.o kmc_init.o surv2.o -L/opt/R/4.3.1/lib/R/lib -lR +installing to /tmp/workdir/kmc/old/kmc.Rcheck/00LOCK-kmc/00new/kmc/libs +** R +** byte-compile and prepare package for lazy loading +Error: package or namespace load failed for ‘emplik’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Execution halted +ERROR: lazy loading failed for package ‘kmc’ +* removing ‘/tmp/workdir/kmc/old/kmc.Rcheck/kmc’ + + +``` +# L2E + +
+ +* Version: 2.0 +* GitHub: NA +* Source code: https://github.com/cran/L2E +* Date/Publication: 2022-09-08 21:13:00 UTC +* Number of recursive dependencies: 65 + +Run `revdepcheck::cloud_details(, "L2E")` for more info + +
+ +## In both + +* checking whether package ‘L2E’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/L2E/new/L2E.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘L2E’ ... +** package ‘L2E’ 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: package or namespace load failed for ‘osqp’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): + namespace ‘Matrix’ 1.5-4.1 is being loaded, but >= 1.6.1 is required +Execution halted +ERROR: lazy loading failed for package ‘L2E’ +* removing ‘/tmp/workdir/L2E/new/L2E.Rcheck/L2E’ + + +``` +### CRAN + +``` +* installing *source* package ‘L2E’ ... +** package ‘L2E’ 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: package or namespace load failed for ‘osqp’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): + namespace ‘Matrix’ 1.5-4.1 is being loaded, but >= 1.6.1 is required +Execution halted +ERROR: lazy loading failed for package ‘L2E’ +* removing ‘/tmp/workdir/L2E/old/L2E.Rcheck/L2E’ + + +``` +# llbayesireg + +
+ +* Version: 1.0.0 +* GitHub: NA +* Source code: https://github.com/cran/llbayesireg +* Date/Publication: 2019-04-04 16:20:03 UTC +* Number of recursive dependencies: 61 + +Run `revdepcheck::cloud_details(, "llbayesireg")` for more info + +
+ +## In both + +* checking whether package ‘llbayesireg’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/llbayesireg/new/llbayesireg.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘llbayesireg’ ... +** package ‘llbayesireg’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** data +*** moving datasets to lazyload DB +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘llbayesireg’ +* removing ‘/tmp/workdir/llbayesireg/new/llbayesireg.Rcheck/llbayesireg’ + + +``` +### CRAN + +``` +* installing *source* package ‘llbayesireg’ ... +** package ‘llbayesireg’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** data +*** moving datasets to lazyload DB +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘llbayesireg’ +* removing ‘/tmp/workdir/llbayesireg/old/llbayesireg.Rcheck/llbayesireg’ + + +``` +# LorenzRegression + +
+ +* Version: 1.0.0 +* GitHub: NA +* Source code: https://github.com/cran/LorenzRegression +* Date/Publication: 2023-02-28 17:32:34 UTC +* Number of recursive dependencies: 63 + +Run `revdepcheck::cloud_details(, "LorenzRegression")` for more info + +
+ +## In both + +* checking whether package ‘LorenzRegression’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/LorenzRegression/new/LorenzRegression.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘LorenzRegression’ ... +** package ‘LorenzRegression’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c GA_fitness.cpp -o GA_fitness.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c GA_meanrank.cpp -o GA_meanrank.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c PLR_derivative.cpp -o PLR_derivative.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c PLR_loss.cpp -o PLR_loss.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘LorenzRegression’ +* removing ‘/tmp/workdir/LorenzRegression/new/LorenzRegression.Rcheck/LorenzRegression’ + + +``` +### CRAN + +``` +* installing *source* package ‘LorenzRegression’ ... +** package ‘LorenzRegression’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c GA_fitness.cpp -o GA_fitness.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c GA_meanrank.cpp -o GA_meanrank.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c PLR_derivative.cpp -o PLR_derivative.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c PLR_loss.cpp -o PLR_loss.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘LorenzRegression’ +* removing ‘/tmp/workdir/LorenzRegression/old/LorenzRegression.Rcheck/LorenzRegression’ + + +``` +# lsirm12pl + +
+ +* Version: 1.3.1 +* GitHub: NA +* Source code: https://github.com/cran/lsirm12pl +* Date/Publication: 2023-06-22 14:12:35 UTC +* Number of recursive dependencies: 123 + +Run `revdepcheck::cloud_details(, "lsirm12pl")` for more info + +
+ +## In both + +* checking whether package ‘lsirm12pl’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/lsirm12pl/new/lsirm12pl.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘lsirm12pl’ ... +** package ‘lsirm12pl’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c log_likelihood.cpp -o log_likelihood.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c lsirm1pl.cpp -o lsirm1pl.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c lsirm1pl_fixed_gamma.cpp -o lsirm1pl_fixed_gamma.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c lsirm1pl_fixed_gamma_mar.cpp -o lsirm1pl_fixed_gamma_mar.o +... +** R +** data +*** moving datasets to lazyload DB +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘lsirm12pl’ +* removing ‘/tmp/workdir/lsirm12pl/new/lsirm12pl.Rcheck/lsirm12pl’ + + +``` +### CRAN + +``` +* installing *source* package ‘lsirm12pl’ ... +** package ‘lsirm12pl’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c log_likelihood.cpp -o log_likelihood.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c lsirm1pl.cpp -o lsirm1pl.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c lsirm1pl_fixed_gamma.cpp -o lsirm1pl_fixed_gamma.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c lsirm1pl_fixed_gamma_mar.cpp -o lsirm1pl_fixed_gamma_mar.o +... +** R +** data +*** moving datasets to lazyload DB +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘lsirm12pl’ +* removing ‘/tmp/workdir/lsirm12pl/old/lsirm12pl.Rcheck/lsirm12pl’ + + +``` +# mbsts + +
+ +* Version: 3.0 +* GitHub: NA +* Source code: https://github.com/cran/mbsts +* Date/Publication: 2023-01-07 01:10:02 UTC +* Number of recursive dependencies: 82 + +Run `revdepcheck::cloud_details(, "mbsts")` for more info + +
+ +## In both + +* checking whether package ‘mbsts’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/mbsts/new/mbsts.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘mbsts’ ... +** package ‘mbsts’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘mbsts’ +* removing ‘/tmp/workdir/mbsts/new/mbsts.Rcheck/mbsts’ + + +``` +### CRAN + +``` +* installing *source* package ‘mbsts’ ... +** package ‘mbsts’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘mbsts’ +* removing ‘/tmp/workdir/mbsts/old/mbsts.Rcheck/mbsts’ + + +``` +# MendelianRandomization + +
+ +* Version: 0.10.0 +* GitHub: NA +* Source code: https://github.com/cran/MendelianRandomization +* Date/Publication: 2024-04-12 10:10:02 UTC +* Number of recursive dependencies: 88 + +Run `revdepcheck::cloud_details(, "MendelianRandomization")` for more info + +
+ +## In both + +* checking whether package ‘MendelianRandomization’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/MendelianRandomization/new/MendelianRandomization.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘MendelianRandomization’ ... +** package ‘MendelianRandomization’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c mvmrcML.cpp -o mvmrcML.o +g++ -std=gnu++17 -shared -L/opt/R/4.3.1/lib/R/lib -L/usr/local/lib -o MendelianRandomization.so RcppExports.o mvmrcML.o -fopenmp -llapack -lblas -lgfortran -lm -lquadmath -L/opt/R/4.3.1/lib/R/lib -lR +installing to /tmp/workdir/MendelianRandomization/new/MendelianRandomization.Rcheck/00LOCK-MendelianRandomization/00new/MendelianRandomization/libs +** R +** inst +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘MendelianRandomization’ +* removing ‘/tmp/workdir/MendelianRandomization/new/MendelianRandomization.Rcheck/MendelianRandomization’ + + +``` +### CRAN + +``` +* installing *source* package ‘MendelianRandomization’ ... +** package ‘MendelianRandomization’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c mvmrcML.cpp -o mvmrcML.o +g++ -std=gnu++17 -shared -L/opt/R/4.3.1/lib/R/lib -L/usr/local/lib -o MendelianRandomization.so RcppExports.o mvmrcML.o -fopenmp -llapack -lblas -lgfortran -lm -lquadmath -L/opt/R/4.3.1/lib/R/lib -lR +installing to /tmp/workdir/MendelianRandomization/old/MendelianRandomization.Rcheck/00LOCK-MendelianRandomization/00new/MendelianRandomization/libs +** R +** inst +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘MendelianRandomization’ +* removing ‘/tmp/workdir/MendelianRandomization/old/MendelianRandomization.Rcheck/MendelianRandomization’ + + +``` +# MetabolicSurv + +
+ +* Version: 1.1.2 +* GitHub: https://github.com/OlajumokeEvangelina/MetabolicSurv +* Source code: https://github.com/cran/MetabolicSurv +* Date/Publication: 2021-06-11 08:30:02 UTC +* Number of recursive dependencies: 142 + +Run `revdepcheck::cloud_details(, "MetabolicSurv")` for more info + +
+ +## In both + +* checking whether package ‘MetabolicSurv’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/MetabolicSurv/new/MetabolicSurv.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘MetabolicSurv’ ... +** package ‘MetabolicSurv’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘MetabolicSurv’ +* removing ‘/tmp/workdir/MetabolicSurv/new/MetabolicSurv.Rcheck/MetabolicSurv’ + + +``` +### CRAN + +``` +* installing *source* package ‘MetabolicSurv’ ... +** package ‘MetabolicSurv’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘MetabolicSurv’ +* removing ‘/tmp/workdir/MetabolicSurv/old/MetabolicSurv.Rcheck/MetabolicSurv’ + + +``` +# miWQS + +
+ +* Version: 0.4.4 +* GitHub: https://github.com/phargarten2/miWQS +* Source code: https://github.com/cran/miWQS +* Date/Publication: 2021-04-02 21:50:02 UTC +* Number of recursive dependencies: 152 + +Run `revdepcheck::cloud_details(, "miWQS")` for more info + +
+ +## In both + +* checking whether package ‘miWQS’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/miWQS/new/miWQS.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘miWQS’ ... +** package ‘miWQS’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘miWQS’ +* removing ‘/tmp/workdir/miWQS/new/miWQS.Rcheck/miWQS’ + + +``` +### CRAN + +``` +* installing *source* package ‘miWQS’ ... +** package ‘miWQS’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘miWQS’ +* removing ‘/tmp/workdir/miWQS/old/miWQS.Rcheck/miWQS’ + + +``` +# mlmts + +
+ +* Version: 1.1.1 +* GitHub: NA +* Source code: https://github.com/cran/mlmts +* Date/Publication: 2023-01-22 21:30:02 UTC +* Number of recursive dependencies: 241 + +Run `revdepcheck::cloud_details(, "mlmts")` for more info + +
+ +## In both + +* checking whether package ‘mlmts’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/mlmts/new/mlmts.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘mlmts’ ... +** package ‘mlmts’ 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 : package or namespace load failed for ‘quantspec’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Error: unable to load R code in package ‘mlmts’ +Execution halted +ERROR: lazy loading failed for package ‘mlmts’ +* removing ‘/tmp/workdir/mlmts/new/mlmts.Rcheck/mlmts’ + + +``` +### CRAN + +``` +* installing *source* package ‘mlmts’ ... +** package ‘mlmts’ 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 : package or namespace load failed for ‘quantspec’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Error: unable to load R code in package ‘mlmts’ +Execution halted +ERROR: lazy loading failed for package ‘mlmts’ +* removing ‘/tmp/workdir/mlmts/old/mlmts.Rcheck/mlmts’ + + +``` +# MRZero + +
+ +* Version: 0.2.0 +* GitHub: NA +* Source code: https://github.com/cran/MRZero +* Date/Publication: 2024-04-14 09:30:03 UTC +* Number of recursive dependencies: 82 + +Run `revdepcheck::cloud_details(, "MRZero")` for more info + +
+ +## In both + +* checking whether package ‘MRZero’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/MRZero/new/MRZero.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘MRZero’ ... +** package ‘MRZero’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘MRZero’ +* removing ‘/tmp/workdir/MRZero/new/MRZero.Rcheck/MRZero’ + + +``` +### CRAN + +``` +* installing *source* package ‘MRZero’ ... +** package ‘MRZero’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘MRZero’ +* removing ‘/tmp/workdir/MRZero/old/MRZero.Rcheck/MRZero’ + + +``` +# Multiaovbay + +
+ +* Version: 0.1.0 +* GitHub: NA +* Source code: https://github.com/cran/Multiaovbay +* Date/Publication: 2023-03-17 17:20:02 UTC +* Number of recursive dependencies: 161 + +Run `revdepcheck::cloud_details(, "Multiaovbay")` for more info + +
+ +## In both + +* checking whether package ‘Multiaovbay’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/Multiaovbay/new/Multiaovbay.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘Multiaovbay’ ... +** package ‘Multiaovbay’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is being loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘Multiaovbay’ +* removing ‘/tmp/workdir/Multiaovbay/new/Multiaovbay.Rcheck/Multiaovbay’ + + +``` +### CRAN + +``` +* installing *source* package ‘Multiaovbay’ ... +** package ‘Multiaovbay’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is being loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘Multiaovbay’ +* removing ‘/tmp/workdir/Multiaovbay/old/Multiaovbay.Rcheck/Multiaovbay’ + + +``` +# multilevelTools + +
+ +* Version: 0.1.1 +* GitHub: https://github.com/JWiley/multilevelTools +* Source code: https://github.com/cran/multilevelTools +* Date/Publication: 2020-03-04 09:50:02 UTC +* Number of recursive dependencies: 164 + +Run `revdepcheck::cloud_details(, "multilevelTools")` for more info + +
+ +## In both + +* checking whether package ‘multilevelTools’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/multilevelTools/new/multilevelTools.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘multilevelTools’ ... +** package ‘multilevelTools’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘multilevelTools’ +* removing ‘/tmp/workdir/multilevelTools/new/multilevelTools.Rcheck/multilevelTools’ + + +``` +### CRAN + +``` +* installing *source* package ‘multilevelTools’ ... +** package ‘multilevelTools’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘multilevelTools’ +* removing ‘/tmp/workdir/multilevelTools/old/multilevelTools.Rcheck/multilevelTools’ + + +``` +# multinma + +
+ +* Version: 0.6.1 +* GitHub: https://github.com/dmphillippo/multinma +* Source code: https://github.com/cran/multinma +* Date/Publication: 2024-03-06 01:00:05 UTC +* Number of recursive dependencies: 152 + +Run `revdepcheck::cloud_details(, "multinma")` for more info + +
+ +## In both + +* checking whether package ‘multinma’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/multinma/new/multinma.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘multinma’ ... +** package ‘multinma’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ +using C++17 + + +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I"../inst/include" -I"/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src" -DBOOST_DISABLE_ASSERTS -DEIGEN_NO_DEBUG -DBOOST_MATH_OVERFLOW_ERROR_POLICY=errno_on_error -DUSE_STANC3 -D_HAS_AUTO_PTR_ETC=0 -I'/opt/R/4.3.1/lib/R/site-library/BH/include' -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppEigen/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -I'/opt/R/4.3.1/lib/R/site-library/rstan/include' -I'/opt/R/4.3.1/lib/R/site-library/StanHeaders/include' -I/usr/local/include -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -D_REENTRANT -DSTAN_THREADS -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +In file included from /opt/R/4.3.1/lib/R/site-library/RcppEigen/include/Eigen/Core:205, +... +In file included from stanExports_survival_mspline.cc:5: +stanExports_survival_mspline.h: In constructor ‘model_survival_mspline_namespace::model_survival_mspline::model_survival_mspline(stan::io::var_context&, unsigned int, std::ostream*)’: +stanExports_survival_mspline.h:2252:3: note: variable tracking size limit exceeded with ‘-fvar-tracking-assignments’, retrying without + 2252 | model_survival_mspline(stan::io::var_context& context__, unsigned int + | ^~~~~~~~~~~~~~~~~~~~~~ +g++: fatal error: Killed signal terminated program cc1plus +compilation terminated. +make: *** [/opt/R/4.3.1/lib/R/etc/Makeconf:198: stanExports_survival_mspline.o] Error 1 +ERROR: compilation failed for package ‘multinma’ +* removing ‘/tmp/workdir/multinma/new/multinma.Rcheck/multinma’ + + +``` +### CRAN + +``` +* installing *source* package ‘multinma’ ... +** package ‘multinma’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ +using C++17 + + +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I"../inst/include" -I"/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src" -DBOOST_DISABLE_ASSERTS -DEIGEN_NO_DEBUG -DBOOST_MATH_OVERFLOW_ERROR_POLICY=errno_on_error -DUSE_STANC3 -D_HAS_AUTO_PTR_ETC=0 -I'/opt/R/4.3.1/lib/R/site-library/BH/include' -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppEigen/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -I'/opt/R/4.3.1/lib/R/site-library/rstan/include' -I'/opt/R/4.3.1/lib/R/site-library/StanHeaders/include' -I/usr/local/include -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -D_REENTRANT -DSTAN_THREADS -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +In file included from /opt/R/4.3.1/lib/R/site-library/RcppEigen/include/Eigen/Core:205, +... +In file included from stanExports_survival_mspline.cc:5: +stanExports_survival_mspline.h: In constructor ‘model_survival_mspline_namespace::model_survival_mspline::model_survival_mspline(stan::io::var_context&, unsigned int, std::ostream*)’: +stanExports_survival_mspline.h:2252:3: note: variable tracking size limit exceeded with ‘-fvar-tracking-assignments’, retrying without + 2252 | model_survival_mspline(stan::io::var_context& context__, unsigned int + | ^~~~~~~~~~~~~~~~~~~~~~ +g++: fatal error: Killed signal terminated program cc1plus +compilation terminated. +make: *** [/opt/R/4.3.1/lib/R/etc/Makeconf:198: stanExports_survival_mspline.o] Error 1 +ERROR: compilation failed for package ‘multinma’ +* removing ‘/tmp/workdir/multinma/old/multinma.Rcheck/multinma’ + + +``` +# NCA + +
+ +* Version: 4.0.1 +* GitHub: NA +* Source code: https://github.com/cran/NCA +* Date/Publication: 2024-02-23 09:30:15 UTC +* Number of recursive dependencies: 99 + +Run `revdepcheck::cloud_details(, "NCA")` for more info + +
+ +## In both + +* checking whether package ‘NCA’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/NCA/new/NCA.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘NCA’ ... +** package ‘NCA’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** data +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘NCA’ +* removing ‘/tmp/workdir/NCA/new/NCA.Rcheck/NCA’ + + +``` +### CRAN + +``` +* installing *source* package ‘NCA’ ... +** package ‘NCA’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** data +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘NCA’ +* removing ‘/tmp/workdir/NCA/old/NCA.Rcheck/NCA’ + + +``` +# netcmc + +
+ +* Version: 1.0.2 +* GitHub: NA +* Source code: https://github.com/cran/netcmc +* Date/Publication: 2022-11-08 22:30:15 UTC +* Number of recursive dependencies: 61 + +Run `revdepcheck::cloud_details(, "netcmc")` for more info + +
+ +## In both + +* checking whether package ‘netcmc’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/netcmc/new/netcmc.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘netcmc’ ... +** package ‘netcmc’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ +using C++11 +g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppProgress/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppProgress/include' -I/usr/local/include -fpic -g -O2 -c choleskyDecompositionRcppConversion.cpp -o choleskyDecompositionRcppConversion.o +g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppProgress/include' -I/usr/local/include -fpic -g -O2 -c doubleMatrixMultiplicationRcpp.cpp -o doubleMatrixMultiplicationRcpp.o +g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppProgress/include' -I/usr/local/include -fpic -g -O2 -c doubleVectorMultiplicationRcpp.cpp -o doubleVectorMultiplicationRcpp.o +... +g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppProgress/include' -I/usr/local/include -fpic -g -O2 -c vectorVectorTransposeMultiplicationRcpp.cpp -o vectorVectorTransposeMultiplicationRcpp.o +g++ -std=gnu++11 -shared -L/opt/R/4.3.1/lib/R/lib -L/usr/local/lib -o netcmc.so RcppExports.o choleskyDecompositionRcppConversion.o doubleMatrixMultiplicationRcpp.o doubleVectorMultiplicationRcpp.o eigenValuesRcppConversion.o getDiagonalMatrix.o getExp.o getExpDividedByOnePlusExp.o getMeanCenteredRandomEffects.o getMultivariateBinomialNetworkLerouxDIC.o getMultivariateBinomialNetworkLerouxFittedValuesAndLikelihoodForDICEveryIteration.o getMultivariateGaussianNetworkLerouxDIC.o getMultivariateGaussianNetworkLerouxFittedValuesAndLikelihoodForDICEveryIteration.o getMultivariatePoissonNetworkLerouxDIC.o getMultivariatePoissonNetworkLerouxFittedValuesAndLikelihoodForDICEveryIteration.o getNonZeroEntries.o getSubvector.o getSubvectorIndecies.o getSumExpNetwork.o getSumExpNetworkIndecies.o getSumExpNetworkLeroux.o getSumExpNetworkLerouxIndecies.o getSumLogExp.o getSumLogExpIndecies.o getSumVector.o getTripletForm.o getUnivariateBinomialNetworkLerouxDIC.o getUnivariateBinomialNetworkLerouxFittedValuesAndLikelihoodForDICEveryIteration.o getUnivariateGaussianNetworkLerouxDIC.o getUnivariateGaussianNetworkLerouxFittedValuesAndLikelihoodForDICEveryIteration.o getUnivariatePoissonNetworkDIC.o getUnivariatePoissonNetworkFittedValuesAndLikelihoodForDICEveryIteration.o getUnivariatePoissonNetworkLerouxDIC.o getUnivariatePoissonNetworkLerouxFittedValuesAndLikelihoodForDICEveryIteration.o getVectorMean.o matrixInverseRcppConversion.o matrixMatrixAdditionRcpp.o matrixMatrixSubtractionRcpp.o matrixVectorMultiplicationRcpp.o multivariateBinomialNetworkLerouxAllUpdate.o multivariateBinomialNetworkLerouxBetaUpdate.o multivariateBinomialNetworkLerouxRhoUpdate.o multivariateBinomialNetworkLerouxSingleUpdate.o multivariateBinomialNetworkLerouxSpatialRandomEffectsUpdate.o multivariateBinomialNetworkLerouxTauSquaredUpdate.o multivariateBinomialNetworkLerouxURandomEffectsUpdate.o multivariateBinomialNetworkLerouxVRandomEffectsUpdate.o multivariateBinomialNetworkLerouxVarianceCovarianceUUpdate.o multivariateBinomialNetworkRandAllUpdate.o multivariateBinomialNetworkRandSingleUpdate.o multivariateGaussianNetworkLerouxAllMHUpdate.o multivariateGaussianNetworkLerouxBetaUpdate.o multivariateGaussianNetworkLerouxRhoUpdate.o multivariateGaussianNetworkLerouxSigmaSquaredEUpdate.o multivariateGaussianNetworkLerouxSingleMHUpdate.o multivariateGaussianNetworkLerouxSpatialRandomEffectsMHUpdate.o multivariateGaussianNetworkLerouxTauSquaredUpdate.o multivariateGaussianNetworkLerouxURandomEffectsUpdate.o multivariateGaussianNetworkLerouxVarianceCovarianceUUpdate.o multivariateGaussianNetworkRandAllUpdate.o multivariateGaussianNetworkRandSingleUpdate.o multivariateGaussianNetworkRandVRandomEffectsUpdate.o multivariatePoissonNetworkLerouxAllUpdate.o multivariatePoissonNetworkLerouxBetaUpdate.o multivariatePoissonNetworkLerouxRhoUpdate.o multivariatePoissonNetworkLerouxSingleUpdate.o multivariatePoissonNetworkLerouxSpatialRandomEffectsUpdate.o multivariatePoissonNetworkLerouxTauSquaredUpdate.o multivariatePoissonNetworkLerouxURandomEffectsUpdate.o multivariatePoissonNetworkLerouxVRandomEffectsUpdate.o multivariatePoissonNetworkLerouxVarianceCovarianceUUpdate.o multivariatePoissonNetworkRandAllUpdate.o multivariatePoissonNetworkRandSingleUpdate.o sumMatrix.o univariateBinomialNetworkLerouxAllUpdate.o univariateBinomialNetworkLerouxBetaUpdate.o univariateBinomialNetworkLerouxRhoUpdate.o univariateBinomialNetworkLerouxSigmaSquaredUpdate.o univariateBinomialNetworkLerouxSingleUpdate.o univariateBinomialNetworkLerouxSpatialRandomEffectsUpdate.o univariateBinomialNetworkLerouxTauSquaredUpdate.o univariateBinomialNetworkLerouxURandomEffectsUpdate.o univariateGaussianNetworkLerouxAllMHUpdate.o univariateGaussianNetworkLerouxBetaUpdate.o univariateGaussianNetworkLerouxRhoUpdate.o univariateGaussianNetworkLerouxSigmaSquaredEUpdate.o univariateGaussianNetworkLerouxSigmaSquaredUUpdate.o univariateGaussianNetworkLerouxSingleMHUpdate.o univariateGaussianNetworkLerouxSpatialRandomEffectsMHUpdate.o univariateGaussianNetworkLerouxTauSquaredUpdate.o univariateGaussianNetworkLerouxURandomEffectsUpdate.o univariatePoissonNetworkLerouxAllUpdate.o univariatePoissonNetworkLerouxBetaUpdate.o univariatePoissonNetworkLerouxRhoUpdate.o univariatePoissonNetworkLerouxSigmaSquaredUpdate.o univariatePoissonNetworkLerouxSingleUpdate.o univariatePoissonNetworkLerouxSpatialRandomEffectsUpdate.o univariatePoissonNetworkLerouxTauSquaredUpdate.o univariatePoissonNetworkLerouxURandomEffectsUpdate.o vectorTransposeVectorMultiplicationRcpp.o vectorVectorTransposeMultiplicationRcpp.o -llapack -lblas -lgfortran -lm -lquadmath -L/opt/R/4.3.1/lib/R/lib -lR +installing to /tmp/workdir/netcmc/new/netcmc.Rcheck/00LOCK-netcmc/00new/netcmc/libs +** R +** byte-compile and prepare package for lazy loading +Error: package or namespace load failed for ‘MCMCpack’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Execution halted +ERROR: lazy loading failed for package ‘netcmc’ +* removing ‘/tmp/workdir/netcmc/new/netcmc.Rcheck/netcmc’ + + +``` +### CRAN + +``` +* installing *source* package ‘netcmc’ ... +** package ‘netcmc’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ +using C++11 +g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppProgress/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppProgress/include' -I/usr/local/include -fpic -g -O2 -c choleskyDecompositionRcppConversion.cpp -o choleskyDecompositionRcppConversion.o +g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppProgress/include' -I/usr/local/include -fpic -g -O2 -c doubleMatrixMultiplicationRcpp.cpp -o doubleMatrixMultiplicationRcpp.o +g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppProgress/include' -I/usr/local/include -fpic -g -O2 -c doubleVectorMultiplicationRcpp.cpp -o doubleVectorMultiplicationRcpp.o +... +g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppProgress/include' -I/usr/local/include -fpic -g -O2 -c vectorVectorTransposeMultiplicationRcpp.cpp -o vectorVectorTransposeMultiplicationRcpp.o +g++ -std=gnu++11 -shared -L/opt/R/4.3.1/lib/R/lib -L/usr/local/lib -o netcmc.so RcppExports.o choleskyDecompositionRcppConversion.o doubleMatrixMultiplicationRcpp.o doubleVectorMultiplicationRcpp.o eigenValuesRcppConversion.o getDiagonalMatrix.o getExp.o getExpDividedByOnePlusExp.o getMeanCenteredRandomEffects.o getMultivariateBinomialNetworkLerouxDIC.o getMultivariateBinomialNetworkLerouxFittedValuesAndLikelihoodForDICEveryIteration.o getMultivariateGaussianNetworkLerouxDIC.o getMultivariateGaussianNetworkLerouxFittedValuesAndLikelihoodForDICEveryIteration.o getMultivariatePoissonNetworkLerouxDIC.o getMultivariatePoissonNetworkLerouxFittedValuesAndLikelihoodForDICEveryIteration.o getNonZeroEntries.o getSubvector.o getSubvectorIndecies.o getSumExpNetwork.o getSumExpNetworkIndecies.o getSumExpNetworkLeroux.o getSumExpNetworkLerouxIndecies.o getSumLogExp.o getSumLogExpIndecies.o getSumVector.o getTripletForm.o getUnivariateBinomialNetworkLerouxDIC.o getUnivariateBinomialNetworkLerouxFittedValuesAndLikelihoodForDICEveryIteration.o getUnivariateGaussianNetworkLerouxDIC.o getUnivariateGaussianNetworkLerouxFittedValuesAndLikelihoodForDICEveryIteration.o getUnivariatePoissonNetworkDIC.o getUnivariatePoissonNetworkFittedValuesAndLikelihoodForDICEveryIteration.o getUnivariatePoissonNetworkLerouxDIC.o getUnivariatePoissonNetworkLerouxFittedValuesAndLikelihoodForDICEveryIteration.o getVectorMean.o matrixInverseRcppConversion.o matrixMatrixAdditionRcpp.o matrixMatrixSubtractionRcpp.o matrixVectorMultiplicationRcpp.o multivariateBinomialNetworkLerouxAllUpdate.o multivariateBinomialNetworkLerouxBetaUpdate.o multivariateBinomialNetworkLerouxRhoUpdate.o multivariateBinomialNetworkLerouxSingleUpdate.o multivariateBinomialNetworkLerouxSpatialRandomEffectsUpdate.o multivariateBinomialNetworkLerouxTauSquaredUpdate.o multivariateBinomialNetworkLerouxURandomEffectsUpdate.o multivariateBinomialNetworkLerouxVRandomEffectsUpdate.o multivariateBinomialNetworkLerouxVarianceCovarianceUUpdate.o multivariateBinomialNetworkRandAllUpdate.o multivariateBinomialNetworkRandSingleUpdate.o multivariateGaussianNetworkLerouxAllMHUpdate.o multivariateGaussianNetworkLerouxBetaUpdate.o multivariateGaussianNetworkLerouxRhoUpdate.o multivariateGaussianNetworkLerouxSigmaSquaredEUpdate.o multivariateGaussianNetworkLerouxSingleMHUpdate.o multivariateGaussianNetworkLerouxSpatialRandomEffectsMHUpdate.o multivariateGaussianNetworkLerouxTauSquaredUpdate.o multivariateGaussianNetworkLerouxURandomEffectsUpdate.o multivariateGaussianNetworkLerouxVarianceCovarianceUUpdate.o multivariateGaussianNetworkRandAllUpdate.o multivariateGaussianNetworkRandSingleUpdate.o multivariateGaussianNetworkRandVRandomEffectsUpdate.o multivariatePoissonNetworkLerouxAllUpdate.o multivariatePoissonNetworkLerouxBetaUpdate.o multivariatePoissonNetworkLerouxRhoUpdate.o multivariatePoissonNetworkLerouxSingleUpdate.o multivariatePoissonNetworkLerouxSpatialRandomEffectsUpdate.o multivariatePoissonNetworkLerouxTauSquaredUpdate.o multivariatePoissonNetworkLerouxURandomEffectsUpdate.o multivariatePoissonNetworkLerouxVRandomEffectsUpdate.o multivariatePoissonNetworkLerouxVarianceCovarianceUUpdate.o multivariatePoissonNetworkRandAllUpdate.o multivariatePoissonNetworkRandSingleUpdate.o sumMatrix.o univariateBinomialNetworkLerouxAllUpdate.o univariateBinomialNetworkLerouxBetaUpdate.o univariateBinomialNetworkLerouxRhoUpdate.o univariateBinomialNetworkLerouxSigmaSquaredUpdate.o univariateBinomialNetworkLerouxSingleUpdate.o univariateBinomialNetworkLerouxSpatialRandomEffectsUpdate.o univariateBinomialNetworkLerouxTauSquaredUpdate.o univariateBinomialNetworkLerouxURandomEffectsUpdate.o univariateGaussianNetworkLerouxAllMHUpdate.o univariateGaussianNetworkLerouxBetaUpdate.o univariateGaussianNetworkLerouxRhoUpdate.o univariateGaussianNetworkLerouxSigmaSquaredEUpdate.o univariateGaussianNetworkLerouxSigmaSquaredUUpdate.o univariateGaussianNetworkLerouxSingleMHUpdate.o univariateGaussianNetworkLerouxSpatialRandomEffectsMHUpdate.o univariateGaussianNetworkLerouxTauSquaredUpdate.o univariateGaussianNetworkLerouxURandomEffectsUpdate.o univariatePoissonNetworkLerouxAllUpdate.o univariatePoissonNetworkLerouxBetaUpdate.o univariatePoissonNetworkLerouxRhoUpdate.o univariatePoissonNetworkLerouxSigmaSquaredUpdate.o univariatePoissonNetworkLerouxSingleUpdate.o univariatePoissonNetworkLerouxSpatialRandomEffectsUpdate.o univariatePoissonNetworkLerouxTauSquaredUpdate.o univariatePoissonNetworkLerouxURandomEffectsUpdate.o vectorTransposeVectorMultiplicationRcpp.o vectorVectorTransposeMultiplicationRcpp.o -llapack -lblas -lgfortran -lm -lquadmath -L/opt/R/4.3.1/lib/R/lib -lR +installing to /tmp/workdir/netcmc/old/netcmc.Rcheck/00LOCK-netcmc/00new/netcmc/libs +** R +** byte-compile and prepare package for lazy loading +Error: package or namespace load failed for ‘MCMCpack’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Execution halted +ERROR: lazy loading failed for package ‘netcmc’ +* removing ‘/tmp/workdir/netcmc/old/netcmc.Rcheck/netcmc’ + + +``` +# NetworkChange + +
+ +* Version: 0.8 +* GitHub: https://github.com/jongheepark/NetworkChange +* Source code: https://github.com/cran/NetworkChange +* Date/Publication: 2022-03-04 07:30:02 UTC +* Number of recursive dependencies: 132 + +Run `revdepcheck::cloud_details(, "NetworkChange")` for more info + +
+ +## In both + +* checking whether package ‘NetworkChange’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/NetworkChange/new/NetworkChange.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘NetworkChange’ ... +** package ‘NetworkChange’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** data +** byte-compile and prepare package for lazy loading +Error: package or namespace load failed for ‘MCMCpack’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Execution halted +ERROR: lazy loading failed for package ‘NetworkChange’ +* removing ‘/tmp/workdir/NetworkChange/new/NetworkChange.Rcheck/NetworkChange’ + + +``` +### CRAN + +``` +* installing *source* package ‘NetworkChange’ ... +** package ‘NetworkChange’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** data +** byte-compile and prepare package for lazy loading +Error: package or namespace load failed for ‘MCMCpack’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Execution halted +ERROR: lazy loading failed for package ‘NetworkChange’ +* removing ‘/tmp/workdir/NetworkChange/old/NetworkChange.Rcheck/NetworkChange’ + + +``` +# nlmeVPC + +
+ +* Version: 2.6 +* GitHub: NA +* Source code: https://github.com/cran/nlmeVPC +* Date/Publication: 2022-12-22 05:20:02 UTC +* Number of recursive dependencies: 91 + +Run `revdepcheck::cloud_details(, "nlmeVPC")` for more info + +
+ +## In both + +* checking whether package ‘nlmeVPC’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/nlmeVPC/new/nlmeVPC.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘nlmeVPC’ ... +** package ‘nlmeVPC’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ +using C++11 +g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c Misc.cpp -o Misc.o +g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +g++ -std=gnu++11 -shared -L/opt/R/4.3.1/lib/R/lib -L/usr/local/lib -o nlmeVPC.so Misc.o RcppExports.o -fopenmp -llapack -lblas -lgfortran -lm -lquadmath -L/opt/R/4.3.1/lib/R/lib -lR +installing to /tmp/workdir/nlmeVPC/new/nlmeVPC.Rcheck/00LOCK-nlmeVPC/00new/nlmeVPC/libs +** R +** data +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘nlmeVPC’ +* removing ‘/tmp/workdir/nlmeVPC/new/nlmeVPC.Rcheck/nlmeVPC’ + + +``` +### CRAN + +``` +* installing *source* package ‘nlmeVPC’ ... +** package ‘nlmeVPC’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ +using C++11 +g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c Misc.cpp -o Misc.o +g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +g++ -std=gnu++11 -shared -L/opt/R/4.3.1/lib/R/lib -L/usr/local/lib -o nlmeVPC.so Misc.o RcppExports.o -fopenmp -llapack -lblas -lgfortran -lm -lquadmath -L/opt/R/4.3.1/lib/R/lib -lR +installing to /tmp/workdir/nlmeVPC/old/nlmeVPC.Rcheck/00LOCK-nlmeVPC/00new/nlmeVPC/libs +** R +** data +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘nlmeVPC’ +* removing ‘/tmp/workdir/nlmeVPC/old/nlmeVPC.Rcheck/nlmeVPC’ + + +``` +# NMADiagT + +
+ +* Version: 0.1.2 +* GitHub: NA +* Source code: https://github.com/cran/NMADiagT +* Date/Publication: 2020-02-26 07:00:02 UTC +* Number of recursive dependencies: 79 + +Run `revdepcheck::cloud_details(, "NMADiagT")` for more info + +
+ +## In both + +* checking whether package ‘NMADiagT’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/NMADiagT/new/NMADiagT.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘NMADiagT’ ... +** package ‘NMADiagT’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘NMADiagT’ +* removing ‘/tmp/workdir/NMADiagT/new/NMADiagT.Rcheck/NMADiagT’ + + +``` +### CRAN + +``` +* installing *source* package ‘NMADiagT’ ... +** package ‘NMADiagT’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘NMADiagT’ +* removing ‘/tmp/workdir/NMADiagT/old/NMADiagT.Rcheck/NMADiagT’ + + +``` +# optweight + +
+ +* Version: 0.2.5 +* GitHub: NA +* Source code: https://github.com/cran/optweight +* Date/Publication: 2019-09-16 15:40:02 UTC +* Number of recursive dependencies: 55 + +Run `revdepcheck::cloud_details(, "optweight")` for more info + +
+ +## In both + +* checking whether package ‘optweight’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/optweight/new/optweight.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘optweight’ ... +** package ‘optweight’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.1 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘optweight’ +* removing ‘/tmp/workdir/optweight/new/optweight.Rcheck/optweight’ + + +``` +### CRAN + +``` +* installing *source* package ‘optweight’ ... +** package ‘optweight’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.1 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘optweight’ +* removing ‘/tmp/workdir/optweight/old/optweight.Rcheck/optweight’ + + +``` +# OVtool + +
+ +* Version: 1.0.3 +* GitHub: NA +* Source code: https://github.com/cran/OVtool +* Date/Publication: 2021-11-02 08:10:07 UTC +* Number of recursive dependencies: 158 + +Run `revdepcheck::cloud_details(, "OVtool")` for more info + +
+ +## In both + +* checking whether package ‘OVtool’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/OVtool/new/OVtool.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘OVtool’ ... +** package ‘OVtool’ 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: package or namespace load failed for ‘twang’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Execution halted +ERROR: lazy loading failed for package ‘OVtool’ +* removing ‘/tmp/workdir/OVtool/new/OVtool.Rcheck/OVtool’ + + +``` +### CRAN + +``` +* installing *source* package ‘OVtool’ ... +** package ‘OVtool’ 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: package or namespace load failed for ‘twang’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Execution halted +ERROR: lazy loading failed for package ‘OVtool’ +* removing ‘/tmp/workdir/OVtool/old/OVtool.Rcheck/OVtool’ + + +``` +# paths + +
+ +* Version: 0.1.1 +* GitHub: NA +* Source code: https://github.com/cran/paths +* Date/Publication: 2021-06-18 08:40:02 UTC +* Number of recursive dependencies: 103 + +Run `revdepcheck::cloud_details(, "paths")` for more info + +
+ +## In both + +* checking whether package ‘paths’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/paths/new/paths.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘paths’ ... +** package ‘paths’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘paths’ +* removing ‘/tmp/workdir/paths/new/paths.Rcheck/paths’ + + +``` +### CRAN + +``` +* installing *source* package ‘paths’ ... +** package ‘paths’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘paths’ +* removing ‘/tmp/workdir/paths/old/paths.Rcheck/paths’ + + +``` +# PLMIX + +
+ +* Version: 2.1.1 +* GitHub: NA +* Source code: https://github.com/cran/PLMIX +* Date/Publication: 2019-09-04 11:50:02 UTC +* Number of recursive dependencies: 151 + +Run `revdepcheck::cloud_details(, "PLMIX")` for more info + +
+ +## In both + +* checking whether package ‘PLMIX’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/PLMIX/new/PLMIX.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘PLMIX’ ... +** package ‘PLMIX’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c CompProbZpartial.cpp -o CompProbZpartial.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c CompRateP.cpp -o CompRateP.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c CompRateYpartial.cpp -o CompRateYpartial.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c Estep.cpp -o Estep.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c PLMIXsim.cpp -o PLMIXsim.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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘PLMIX’ +* removing ‘/tmp/workdir/PLMIX/new/PLMIX.Rcheck/PLMIX’ + + +``` +### CRAN + +``` +* installing *source* package ‘PLMIX’ ... +** package ‘PLMIX’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c CompProbZpartial.cpp -o CompProbZpartial.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c CompRateP.cpp -o CompRateP.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c CompRateYpartial.cpp -o CompRateYpartial.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c Estep.cpp -o Estep.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c PLMIXsim.cpp -o PLMIXsim.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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘PLMIX’ +* removing ‘/tmp/workdir/PLMIX/old/PLMIX.Rcheck/PLMIX’ + + +``` +# popstudy + +
+ +* Version: 1.0.1 +* GitHub: NA +* Source code: https://github.com/cran/popstudy +* Date/Publication: 2023-10-17 23:50:02 UTC +* Number of recursive dependencies: 236 + +Run `revdepcheck::cloud_details(, "popstudy")` for more info + +
+ +## In both + +* checking whether package ‘popstudy’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/popstudy/new/popstudy.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘popstudy’ ... +** package ‘popstudy’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘popstudy’ +* removing ‘/tmp/workdir/popstudy/new/popstudy.Rcheck/popstudy’ + + +``` +### CRAN + +``` +* installing *source* package ‘popstudy’ ... +** package ‘popstudy’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘popstudy’ +* removing ‘/tmp/workdir/popstudy/old/popstudy.Rcheck/popstudy’ + + +``` +# pould + +
+ +* Version: 1.0.1 +* GitHub: NA +* Source code: https://github.com/cran/pould +* Date/Publication: 2020-10-16 13:50:03 UTC +* Number of recursive dependencies: 104 + +Run `revdepcheck::cloud_details(, "pould")` for more info + +
+ +## In both + +* checking whether package ‘pould’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/pould/new/pould.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘pould’ ... +** package ‘pould’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘pould’ +* removing ‘/tmp/workdir/pould/new/pould.Rcheck/pould’ + + +``` +### CRAN + +``` +* installing *source* package ‘pould’ ... +** package ‘pould’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘pould’ +* removing ‘/tmp/workdir/pould/old/pould.Rcheck/pould’ + + +``` +# powerly + +
+ +* Version: 1.8.6 +* GitHub: https://github.com/mihaiconstantin/powerly +* Source code: https://github.com/cran/powerly +* Date/Publication: 2022-09-09 14:10:01 UTC +* Number of recursive dependencies: 176 + +Run `revdepcheck::cloud_details(, "powerly")` for more info + +
+ +## In both + +* checking whether package ‘powerly’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/powerly/new/powerly.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘powerly’ ... +** package ‘powerly’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.1 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘powerly’ +* removing ‘/tmp/workdir/powerly/new/powerly.Rcheck/powerly’ + + +``` +### CRAN + +``` +* installing *source* package ‘powerly’ ... +** package ‘powerly’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.1 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘powerly’ +* removing ‘/tmp/workdir/powerly/old/powerly.Rcheck/powerly’ + + +``` +# pre + +
+ +* Version: 1.0.7 +* GitHub: https://github.com/marjoleinF/pre +* Source code: https://github.com/cran/pre +* Date/Publication: 2024-01-12 19:30:02 UTC +* Number of recursive dependencies: 152 + +Run `revdepcheck::cloud_details(, "pre")` for more info + +
+ +## In both + +* checking whether package ‘pre’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/pre/new/pre.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘pre’ ... +** package ‘pre’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘pre’ +* removing ‘/tmp/workdir/pre/new/pre.Rcheck/pre’ + + +``` +### CRAN + +``` +* installing *source* package ‘pre’ ... +** package ‘pre’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘pre’ +* removing ‘/tmp/workdir/pre/old/pre.Rcheck/pre’ + + +``` +# ProFAST + +
+ +* Version: 1.4 +* GitHub: https://github.com/feiyoung/ProFAST +* Source code: https://github.com/cran/ProFAST +* Date/Publication: 2024-03-18 08:10:06 UTC +* Number of recursive dependencies: 253 + +Run `revdepcheck::cloud_details(, "ProFAST")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/ProFAST/new/ProFAST.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0 + GNU Fortran (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0 +* running under: Ubuntu 20.04.6 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘ProFAST/DESCRIPTION’ ... OK +... +* this is package ‘ProFAST’ version ‘1.4’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Packages required but not available: 'DR.SC', 'PRECAST' + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/ProFAST/old/ProFAST.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0 + GNU Fortran (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0 +* running under: Ubuntu 20.04.6 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘ProFAST/DESCRIPTION’ ... OK +... +* this is package ‘ProFAST’ version ‘1.4’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Packages required but not available: 'DR.SC', 'PRECAST' + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# psbcSpeedUp + +
+ +* Version: 2.0.6 +* GitHub: https://github.com/ocbe-uio/psbcSpeedUp +* Source code: https://github.com/cran/psbcSpeedUp +* Date/Publication: 2024-03-21 18:00:02 UTC +* Number of recursive dependencies: 130 + +Run `revdepcheck::cloud_details(, "psbcSpeedUp")` for more info + +
+ +## In both + +* checking whether package ‘psbcSpeedUp’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/psbcSpeedUp/new/psbcSpeedUp.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘psbcSpeedUp’ ... +** package ‘psbcSpeedUp’ successfully unpacked and MD5 sums checked +** using staged installation +checking whether the C++ compiler works... yes +checking for C++ compiler default output file name... a.out +checking for suffix of executables... +checking whether we are cross compiling... no +checking for suffix of object files... o +checking whether the compiler supports GNU C++... yes +checking whether g++ -std=gnu++17 accepts -g... yes +... +** 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘psbcSpeedUp’ +* removing ‘/tmp/workdir/psbcSpeedUp/new/psbcSpeedUp.Rcheck/psbcSpeedUp’ + + +``` +### CRAN + +``` +* installing *source* package ‘psbcSpeedUp’ ... +** package ‘psbcSpeedUp’ successfully unpacked and MD5 sums checked +** using staged installation +checking whether the C++ compiler works... yes +checking for C++ compiler default output file name... a.out +checking for suffix of executables... +checking whether we are cross compiling... no +checking for suffix of object files... o +checking whether the compiler supports GNU C++... yes +checking whether g++ -std=gnu++17 accepts -g... yes +... +** 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘psbcSpeedUp’ +* removing ‘/tmp/workdir/psbcSpeedUp/old/psbcSpeedUp.Rcheck/psbcSpeedUp’ + + +``` +# pscore + +
+ +* Version: 0.4.0 +* GitHub: https://github.com/JWiley/score-project +* Source code: https://github.com/cran/pscore +* Date/Publication: 2022-05-13 22:30:02 UTC +* Number of recursive dependencies: 165 + +Run `revdepcheck::cloud_details(, "pscore")` for more info + +
+ +## In both + +* checking whether package ‘pscore’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/pscore/new/pscore.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘pscore’ ... +** package ‘pscore’ successfully unpacked and MD5 sums checked +** 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘pscore’ +* removing ‘/tmp/workdir/pscore/new/pscore.Rcheck/pscore’ + + +``` +### CRAN + +``` +* installing *source* package ‘pscore’ ... +** package ‘pscore’ successfully unpacked and MD5 sums checked +** 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘pscore’ +* removing ‘/tmp/workdir/pscore/old/pscore.Rcheck/pscore’ + + +``` +# psfmi + +
+ +* Version: 1.4.0 +* GitHub: https://github.com/mwheymans/psfmi +* Source code: https://github.com/cran/psfmi +* Date/Publication: 2023-06-17 22:40:02 UTC +* Number of recursive dependencies: 160 + +Run `revdepcheck::cloud_details(, "psfmi")` for more info + +
+ +## In both + +* checking whether package ‘psfmi’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/psfmi/new/psfmi.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘psfmi’ ... +** package ‘psfmi’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘psfmi’ +* removing ‘/tmp/workdir/psfmi/new/psfmi.Rcheck/psfmi’ + + +``` +### CRAN + +``` +* installing *source* package ‘psfmi’ ... +** package ‘psfmi’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘psfmi’ +* removing ‘/tmp/workdir/psfmi/old/psfmi.Rcheck/psfmi’ + + +``` +# qPCRtools + +
+ +* Version: 1.0.1 +* GitHub: https://github.com/lixiang117423/qPCRtools +* Source code: https://github.com/cran/qPCRtools +* Date/Publication: 2023-11-02 13:10:05 UTC +* Number of recursive dependencies: 116 + +Run `revdepcheck::cloud_details(, "qPCRtools")` for more info + +
+ +## In both + +* checking whether package ‘qPCRtools’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/qPCRtools/new/qPCRtools.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘qPCRtools’ ... +** package ‘qPCRtools’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘qPCRtools’ +* removing ‘/tmp/workdir/qPCRtools/new/qPCRtools.Rcheck/qPCRtools’ + + +``` +### CRAN + +``` +* installing *source* package ‘qPCRtools’ ... +** package ‘qPCRtools’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘qPCRtools’ +* removing ‘/tmp/workdir/qPCRtools/old/qPCRtools.Rcheck/qPCRtools’ + + +``` +# qreport + +
+ +* Version: 1.0-0 +* GitHub: NA +* Source code: https://github.com/cran/qreport +* Date/Publication: 2023-09-12 22:10:02 UTC +* Number of recursive dependencies: 77 + +Run `revdepcheck::cloud_details(, "qreport")` for more info + +
+ +## In both + +* checking whether package ‘qreport’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/qreport/new/qreport.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘qreport’ ... +** package ‘qreport’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘qreport’ +* removing ‘/tmp/workdir/qreport/new/qreport.Rcheck/qreport’ + + +``` +### CRAN + +``` +* installing *source* package ‘qreport’ ... +** package ‘qreport’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘qreport’ +* removing ‘/tmp/workdir/qreport/old/qreport.Rcheck/qreport’ + + +``` +# qris + +
+ +* Version: 1.1.1 +* GitHub: https://github.com/Kyuhyun07/qris +* Source code: https://github.com/cran/qris +* Date/Publication: 2024-03-05 14:40:03 UTC +* Number of recursive dependencies: 55 + +Run `revdepcheck::cloud_details(, "qris")` for more info + +
+ +## In both + +* checking whether package ‘qris’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/qris/new/qris.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘qris’ ... +** package ‘qris’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C compiler: ‘gcc (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ +using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ +using C++11 +g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c Amat.cpp -o Amat.o +g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c ghat.cpp -o ghat.o +... +installing to /tmp/workdir/qris/new/qris.Rcheck/00LOCK-qris/00new/qris/libs +** R +** inst +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘qris’ +* removing ‘/tmp/workdir/qris/new/qris.Rcheck/qris’ + + +``` +### CRAN + +``` +* installing *source* package ‘qris’ ... +** package ‘qris’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C compiler: ‘gcc (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ +using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ +using C++11 +g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c Amat.cpp -o Amat.o +g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c ghat.cpp -o ghat.o +... +installing to /tmp/workdir/qris/old/qris.Rcheck/00LOCK-qris/00new/qris/libs +** R +** inst +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘qris’ +* removing ‘/tmp/workdir/qris/old/qris.Rcheck/qris’ + + +``` +# qte + +
+ +* Version: 1.3.1 +* GitHub: NA +* Source code: https://github.com/cran/qte +* Date/Publication: 2022-09-01 14:30:02 UTC +* Number of recursive dependencies: 87 + +Run `revdepcheck::cloud_details(, "qte")` for more info + +
+ +## In both + +* checking whether package ‘qte’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/qte/new/qte.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘qte’ ... +** package ‘qte’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘qte’ +* removing ‘/tmp/workdir/qte/new/qte.Rcheck/qte’ + + +``` +### CRAN + +``` +* installing *source* package ‘qte’ ... +** package ‘qte’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘qte’ +* removing ‘/tmp/workdir/qte/old/qte.Rcheck/qte’ + + +``` +# quid + +
+ +* Version: 0.0.1 +* GitHub: NA +* Source code: https://github.com/cran/quid +* Date/Publication: 2021-12-09 09:00:02 UTC +* Number of recursive dependencies: 95 + +Run `revdepcheck::cloud_details(, "quid")` for more info + +
+ +## In both + +* checking whether package ‘quid’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/quid/new/quid.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘quid’ ... +** package ‘quid’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘quid’ +* removing ‘/tmp/workdir/quid/new/quid.Rcheck/quid’ + + +``` +### CRAN + +``` +* installing *source* package ‘quid’ ... +** package ‘quid’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘quid’ +* removing ‘/tmp/workdir/quid/old/quid.Rcheck/quid’ + + +``` +# RATest + +
+ +* Version: 0.1.10 +* GitHub: https://github.com/ignaciomsarmiento/RATest +* Source code: https://github.com/cran/RATest +* Date/Publication: 2022-09-29 04:30:02 UTC +* Number of recursive dependencies: 54 + +Run `revdepcheck::cloud_details(, "RATest")` for more info + +
+ +## In both + +* checking whether package ‘RATest’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/RATest/new/RATest.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘RATest’ ... +** package ‘RATest’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘RATest’ +* removing ‘/tmp/workdir/RATest/new/RATest.Rcheck/RATest’ + + +``` +### CRAN + +``` +* installing *source* package ‘RATest’ ... +** package ‘RATest’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘RATest’ +* removing ‘/tmp/workdir/RATest/old/RATest.Rcheck/RATest’ + + +``` +# RcmdrPlugin.RiskDemo + +
+ +* Version: 3.2 +* GitHub: NA +* Source code: https://github.com/cran/RcmdrPlugin.RiskDemo +* Date/Publication: 2024-02-06 09:20:02 UTC +* Number of recursive dependencies: 208 + +Run `revdepcheck::cloud_details(, "RcmdrPlugin.RiskDemo")` for more info + +
+ +## In both + +* checking whether package ‘RcmdrPlugin.RiskDemo’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/RcmdrPlugin.RiskDemo/new/RcmdrPlugin.RiskDemo.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘RcmdrPlugin.RiskDemo’ ... +** package ‘RcmdrPlugin.RiskDemo’ successfully unpacked and MD5 sums checked +** 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘RcmdrPlugin.RiskDemo’ +* removing ‘/tmp/workdir/RcmdrPlugin.RiskDemo/new/RcmdrPlugin.RiskDemo.Rcheck/RcmdrPlugin.RiskDemo’ + + +``` +### CRAN + +``` +* installing *source* package ‘RcmdrPlugin.RiskDemo’ ... +** package ‘RcmdrPlugin.RiskDemo’ successfully unpacked and MD5 sums checked +** 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘RcmdrPlugin.RiskDemo’ +* removing ‘/tmp/workdir/RcmdrPlugin.RiskDemo/old/RcmdrPlugin.RiskDemo.Rcheck/RcmdrPlugin.RiskDemo’ + + +``` +# rddtools + +
+ +* Version: 1.6.0 +* GitHub: https://github.com/bquast/rddtools +* Source code: https://github.com/cran/rddtools +* Date/Publication: 2022-01-10 12:42:49 UTC +* Number of recursive dependencies: 102 + +Run `revdepcheck::cloud_details(, "rddtools")` for more info + +
+ +## In both + +* checking whether package ‘rddtools’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/rddtools/new/rddtools.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘rddtools’ ... +** package ‘rddtools’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** data +** inst +** byte-compile and prepare package for lazy loading +Error: package or namespace load failed for ‘np’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Execution halted +ERROR: lazy loading failed for package ‘rddtools’ +* removing ‘/tmp/workdir/rddtools/new/rddtools.Rcheck/rddtools’ + + +``` +### CRAN + +``` +* installing *source* package ‘rddtools’ ... +** package ‘rddtools’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** data +** inst +** byte-compile and prepare package for lazy loading +Error: package or namespace load failed for ‘np’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Execution halted +ERROR: lazy loading failed for package ‘rddtools’ +* removing ‘/tmp/workdir/rddtools/old/rddtools.Rcheck/rddtools’ + + +``` +# riskRegression + +
+ +* Version: 2023.12.21 +* GitHub: https://github.com/tagteam/riskRegression +* Source code: https://github.com/cran/riskRegression +* Date/Publication: 2023-12-19 17:00:02 UTC +* Number of recursive dependencies: 186 + +Run `revdepcheck::cloud_details(, "riskRegression")` for more info + +
+ +## In both + +* checking whether package ‘riskRegression’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/riskRegression/new/riskRegression.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘riskRegression’ ... +** package ‘riskRegression’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c IC-Nelson-Aalen-cens-time.cpp -o IC-Nelson-Aalen-cens-time.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c aucCVFun.cpp -o aucCVFun.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c baseHaz.cpp -o baseHaz.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c calcSeCSC.cpp -o calcSeCSC.o +... +** R +** data +** inst +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘riskRegression’ +* removing ‘/tmp/workdir/riskRegression/new/riskRegression.Rcheck/riskRegression’ + + +``` +### CRAN + +``` +* installing *source* package ‘riskRegression’ ... +** package ‘riskRegression’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c IC-Nelson-Aalen-cens-time.cpp -o IC-Nelson-Aalen-cens-time.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c aucCVFun.cpp -o aucCVFun.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c baseHaz.cpp -o baseHaz.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c calcSeCSC.cpp -o calcSeCSC.o +... +** R +** data +** inst +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘riskRegression’ +* removing ‘/tmp/workdir/riskRegression/old/riskRegression.Rcheck/riskRegression’ + + +``` +# rms + +
+ +* Version: 6.8-0 +* GitHub: https://github.com/harrelfe/rms +* Source code: https://github.com/cran/rms +* Date/Publication: 2024-03-11 16:20:02 UTC +* Number of recursive dependencies: 154 + +Run `revdepcheck::cloud_details(, "rms")` for more info + +
+ +## In both + +* checking whether package ‘rms’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/rms/new/rms.Rcheck/00install.out’ for details. + ``` + +* checking package dependencies ... NOTE + ``` + Package suggested but not available for checking: ‘rmsb’ + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘rms’ ... +** package ‘rms’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C compiler: ‘gcc (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ +using Fortran compiler: ‘GNU Fortran (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ +gcc -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I/usr/local/include -fpic -g -O2 -c init.c -o init.o +gfortran -fpic -g -O2 -c lrmfit.f -o lrmfit.o +gfortran -fpic -g -O2 -c mlmats.f -o mlmats.o +gfortran -fpic -g -O2 -c ormuv.f -o ormuv.o +... +** R +** demo +** inst +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘rms’ +* removing ‘/tmp/workdir/rms/new/rms.Rcheck/rms’ + + +``` +### CRAN + +``` +* installing *source* package ‘rms’ ... +** package ‘rms’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C compiler: ‘gcc (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ +using Fortran compiler: ‘GNU Fortran (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ +gcc -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I/usr/local/include -fpic -g -O2 -c init.c -o init.o +gfortran -fpic -g -O2 -c lrmfit.f -o lrmfit.o +gfortran -fpic -g -O2 -c mlmats.f -o mlmats.o +gfortran -fpic -g -O2 -c ormuv.f -o ormuv.o +... +** R +** demo +** inst +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘rms’ +* removing ‘/tmp/workdir/rms/old/rms.Rcheck/rms’ + + +``` +# rmsb + +
+ +* Version: 1.1-0 +* GitHub: NA +* Source code: https://github.com/cran/rmsb +* Date/Publication: 2024-03-12 15:50:02 UTC +* Number of recursive dependencies: 144 + +Run `revdepcheck::cloud_details(, "rmsb")` for more info + +
+ +## In both + +* checking whether package ‘rmsb’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/rmsb/new/rmsb.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘rmsb’ ... +** package ‘rmsb’ successfully unpacked and MD5 sums checked +** using staged installation +Error in loadNamespace(x) : there is no package called ‘rstantools’ +Calls: loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Execution halted +ERROR: configuration failed for package ‘rmsb’ +* removing ‘/tmp/workdir/rmsb/new/rmsb.Rcheck/rmsb’ + + +``` +### CRAN + +``` +* installing *source* package ‘rmsb’ ... +** package ‘rmsb’ successfully unpacked and MD5 sums checked +** using staged installation +Error in loadNamespace(x) : there is no package called ‘rstantools’ +Calls: loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Execution halted +ERROR: configuration failed for package ‘rmsb’ +* removing ‘/tmp/workdir/rmsb/old/rmsb.Rcheck/rmsb’ + + +``` +# robmed + +
+ +* Version: 1.0.2 +* GitHub: https://github.com/aalfons/robmed +* Source code: https://github.com/cran/robmed +* Date/Publication: 2023-06-16 23:00:02 UTC +* Number of recursive dependencies: 60 + +Run `revdepcheck::cloud_details(, "robmed")` for more info + +
+ +## In both + +* checking whether package ‘robmed’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/robmed/new/robmed.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘robmed’ ... +** package ‘robmed’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘robmed’ +* removing ‘/tmp/workdir/robmed/new/robmed.Rcheck/robmed’ + + +``` +### CRAN + +``` +* installing *source* package ‘robmed’ ... +** package ‘robmed’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘robmed’ +* removing ‘/tmp/workdir/robmed/old/robmed.Rcheck/robmed’ + + +``` +# robmedExtra + +
+ +* Version: 0.1.0 +* GitHub: https://github.com/aalfons/robmedExtra +* Source code: https://github.com/cran/robmedExtra +* Date/Publication: 2023-06-02 14:40:02 UTC +* Number of recursive dependencies: 96 + +Run `revdepcheck::cloud_details(, "robmedExtra")` for more info + +
+ +## In both + +* checking whether package ‘robmedExtra’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/robmedExtra/new/robmedExtra.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘robmedExtra’ ... +** package ‘robmedExtra’ 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 ‘robmed’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Execution halted +ERROR: lazy loading failed for package ‘robmedExtra’ +* removing ‘/tmp/workdir/robmedExtra/new/robmedExtra.Rcheck/robmedExtra’ + + +``` +### CRAN + +``` +* installing *source* package ‘robmedExtra’ ... +** package ‘robmedExtra’ 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 ‘robmed’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Execution halted +ERROR: lazy loading failed for package ‘robmedExtra’ +* removing ‘/tmp/workdir/robmedExtra/old/robmedExtra.Rcheck/robmedExtra’ + + +``` +# RPPanalyzer + +
+ +* Version: 1.4.9 +* GitHub: NA +* Source code: https://github.com/cran/RPPanalyzer +* Date/Publication: 2024-01-25 11:00:02 UTC +* Number of recursive dependencies: 82 + +Run `revdepcheck::cloud_details(, "RPPanalyzer")` for more info + +
+ +## In both + +* checking whether package ‘RPPanalyzer’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/RPPanalyzer/new/RPPanalyzer.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘RPPanalyzer’ ... +** package ‘RPPanalyzer’ successfully unpacked and MD5 sums checked +** 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘RPPanalyzer’ +* removing ‘/tmp/workdir/RPPanalyzer/new/RPPanalyzer.Rcheck/RPPanalyzer’ + + +``` +### CRAN + +``` +* installing *source* package ‘RPPanalyzer’ ... +** package ‘RPPanalyzer’ successfully unpacked and MD5 sums checked +** 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘RPPanalyzer’ +* removing ‘/tmp/workdir/RPPanalyzer/old/RPPanalyzer.Rcheck/RPPanalyzer’ + + +``` +# RQdeltaCT + +
+ +* Version: 1.3.0 +* GitHub: NA +* Source code: https://github.com/cran/RQdeltaCT +* Date/Publication: 2024-04-17 15:50:02 UTC +* Number of recursive dependencies: 165 + +Run `revdepcheck::cloud_details(, "RQdeltaCT")` for more info + +
+ +## In both + +* checking whether package ‘RQdeltaCT’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/RQdeltaCT/new/RQdeltaCT.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘RQdeltaCT’ ... +** package ‘RQdeltaCT’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘RQdeltaCT’ +* removing ‘/tmp/workdir/RQdeltaCT/new/RQdeltaCT.Rcheck/RQdeltaCT’ + + +``` +### CRAN + +``` +* installing *source* package ‘RQdeltaCT’ ... +** package ‘RQdeltaCT’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘RQdeltaCT’ +* removing ‘/tmp/workdir/RQdeltaCT/old/RQdeltaCT.Rcheck/RQdeltaCT’ + + +``` +# rstanarm + +
+ +* Version: 2.32.1 +* GitHub: https://github.com/stan-dev/rstanarm +* Source code: https://github.com/cran/rstanarm +* Date/Publication: 2024-01-18 23:00:03 UTC +* Number of recursive dependencies: 138 + +Run `revdepcheck::cloud_details(, "rstanarm")` for more info + +
+ +## In both + +* checking whether package ‘rstanarm’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/rstanarm/new/rstanarm.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘rstanarm’ ... +** package ‘rstanarm’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ +using C++17 +"/opt/R/4.3.1/lib/R/bin/Rscript" -e "source(file.path('..', 'tools', 'make_cc.R')); make_cc(commandArgs(TRUE))" stan_files/lm.stan +Wrote C++ file "stan_files/lm.cc" + + +... +/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src/stan/mcmc/hmc/hamiltonians/dense_e_metric.hpp:21:10: required from here +/opt/R/4.3.1/lib/R/site-library/RcppEigen/include/Eigen/src/Core/DenseCoeffsBase.h:654:34: warning: ignoring attributes on template argument ‘Eigen::internal::packet_traits::type’ {aka ‘__vector(2) double’} [-Wignored-attributes] + 654 | return internal::first_aligned::alignment),Derived>(m); + | ^~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +g++: fatal error: Killed signal terminated program cc1plus +compilation terminated. +make: *** [/opt/R/4.3.1/lib/R/etc/Makeconf:198: stan_files/mvmer.o] Error 1 +rm stan_files/lm.cc stan_files/mvmer.cc +ERROR: compilation failed for package ‘rstanarm’ +* removing ‘/tmp/workdir/rstanarm/new/rstanarm.Rcheck/rstanarm’ + + +``` +### CRAN + +``` +* installing *source* package ‘rstanarm’ ... +** package ‘rstanarm’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ +using C++17 +"/opt/R/4.3.1/lib/R/bin/Rscript" -e "source(file.path('..', 'tools', 'make_cc.R')); make_cc(commandArgs(TRUE))" stan_files/lm.stan +Wrote C++ file "stan_files/lm.cc" + + +... +/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src/stan/mcmc/hmc/hamiltonians/dense_e_metric.hpp:21:10: required from here +/opt/R/4.3.1/lib/R/site-library/RcppEigen/include/Eigen/src/Core/DenseCoeffsBase.h:654:34: warning: ignoring attributes on template argument ‘Eigen::internal::packet_traits::type’ {aka ‘__vector(2) double’} [-Wignored-attributes] + 654 | return internal::first_aligned::alignment),Derived>(m); + | ^~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +g++: fatal error: Killed signal terminated program cc1plus +compilation terminated. +make: *** [/opt/R/4.3.1/lib/R/etc/Makeconf:198: stan_files/mvmer.o] Error 1 +rm stan_files/lm.cc stan_files/mvmer.cc +ERROR: compilation failed for package ‘rstanarm’ +* removing ‘/tmp/workdir/rstanarm/old/rstanarm.Rcheck/rstanarm’ + + +``` +# scCustomize + +
+ +* Version: 2.1.2 +* GitHub: https://github.com/samuel-marsh/scCustomize +* Source code: https://github.com/cran/scCustomize +* Date/Publication: 2024-02-28 19:40:02 UTC +* Number of recursive dependencies: 274 + +Run `revdepcheck::cloud_details(, "scCustomize")` for more info + +
+ +## In both + +* checking whether package ‘scCustomize’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/scCustomize/new/scCustomize.Rcheck/00install.out’ for details. + ``` + +* checking package dependencies ... NOTE + ``` + Package suggested but not available for checking: ‘Nebulosa’ + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘scCustomize’ ... +** package ‘scCustomize’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** data +*** moving datasets to lazyload DB +** byte-compile and prepare package for lazy loading +Error: package or namespace load failed for ‘SeuratObject’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): + namespace ‘Matrix’ 1.5-4.1 is being loaded, but >= 1.6.3 is required +Execution halted +ERROR: lazy loading failed for package ‘scCustomize’ +* removing ‘/tmp/workdir/scCustomize/new/scCustomize.Rcheck/scCustomize’ + + +``` +### CRAN + +``` +* installing *source* package ‘scCustomize’ ... +** package ‘scCustomize’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** data +*** moving datasets to lazyload DB +** byte-compile and prepare package for lazy loading +Error: package or namespace load failed for ‘SeuratObject’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): + namespace ‘Matrix’ 1.5-4.1 is being loaded, but >= 1.6.3 is required +Execution halted +ERROR: lazy loading failed for package ‘scCustomize’ +* removing ‘/tmp/workdir/scCustomize/old/scCustomize.Rcheck/scCustomize’ + + +``` +# SCdeconR + +
+ +* Version: 1.0.0 +* GitHub: https://github.com/Liuy12/SCdeconR +* Source code: https://github.com/cran/SCdeconR +* Date/Publication: 2024-03-22 19:20:02 UTC +* Number of recursive dependencies: 235 + +Run `revdepcheck::cloud_details(, "SCdeconR")` for more info + +
+ +## In both + +* checking whether package ‘SCdeconR’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/SCdeconR/new/SCdeconR.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘SCdeconR’ ... +** package ‘SCdeconR’ 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 ‘SeuratObject’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): + namespace ‘Matrix’ 1.5-4.1 is being loaded, but >= 1.6.3 is required +Execution halted +ERROR: lazy loading failed for package ‘SCdeconR’ +* removing ‘/tmp/workdir/SCdeconR/new/SCdeconR.Rcheck/SCdeconR’ + + +``` +### CRAN + +``` +* installing *source* package ‘SCdeconR’ ... +** package ‘SCdeconR’ 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 ‘SeuratObject’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): + namespace ‘Matrix’ 1.5-4.1 is being loaded, but >= 1.6.3 is required +Execution halted +ERROR: lazy loading failed for package ‘SCdeconR’ +* removing ‘/tmp/workdir/SCdeconR/old/SCdeconR.Rcheck/SCdeconR’ + + +``` +# scGate + +
+ +* Version: 1.6.2 +* GitHub: https://github.com/carmonalab/scGate +* Source code: https://github.com/cran/scGate +* Date/Publication: 2024-04-23 08:50:02 UTC +* Number of recursive dependencies: 178 + +Run `revdepcheck::cloud_details(, "scGate")` for more info + +
+ +## In both + +* checking whether package ‘scGate’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/scGate/new/scGate.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘scGate’ ... +** package ‘scGate’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** data +*** moving datasets to lazyload DB +Warning: namespace ‘Seurat’ is not available and has been replaced +by .GlobalEnv when processing object ‘query.seurat’ +Warning: namespace ‘Seurat’ is not available and has been replaced +by .GlobalEnv when processing object ‘query.seurat’ +** inst +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.3 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘scGate’ +* removing ‘/tmp/workdir/scGate/new/scGate.Rcheck/scGate’ + + +``` +### CRAN + +``` +* installing *source* package ‘scGate’ ... +** package ‘scGate’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** data +*** moving datasets to lazyload DB +Warning: namespace ‘Seurat’ is not available and has been replaced +by .GlobalEnv when processing object ‘query.seurat’ +Warning: namespace ‘Seurat’ is not available and has been replaced +by .GlobalEnv when processing object ‘query.seurat’ +** inst +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.3 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘scGate’ +* removing ‘/tmp/workdir/scGate/old/scGate.Rcheck/scGate’ + + +``` +# scMappR + +
+ +* Version: 1.0.11 +* GitHub: NA +* Source code: https://github.com/cran/scMappR +* Date/Publication: 2023-06-30 08:40:08 UTC +* Number of recursive dependencies: 233 + +Run `revdepcheck::cloud_details(, "scMappR")` for more info + +
+ +## In both + +* checking whether package ‘scMappR’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/scMappR/new/scMappR.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘scMappR’ ... +** package ‘scMappR’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.3 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘scMappR’ +* removing ‘/tmp/workdir/scMappR/new/scMappR.Rcheck/scMappR’ + + +``` +### CRAN + +``` +* installing *source* package ‘scMappR’ ... +** package ‘scMappR’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.3 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘scMappR’ +* removing ‘/tmp/workdir/scMappR/old/scMappR.Rcheck/scMappR’ + + +``` +# scRNAstat + +
+ +* Version: 0.1.1 +* GitHub: NA +* Source code: https://github.com/cran/scRNAstat +* Date/Publication: 2021-09-22 08:10:02 UTC +* Number of recursive dependencies: 155 + +Run `revdepcheck::cloud_details(, "scRNAstat")` for more info + +
+ +## In both + +* checking whether package ‘scRNAstat’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/scRNAstat/new/scRNAstat.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘scRNAstat’ ... +** package ‘scRNAstat’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** data +*** moving datasets to lazyload DB +Warning: namespace ‘Seurat’ is not available and has been replaced +by .GlobalEnv when processing object ‘AJ064_small_last_sce’ +Warning: namespace ‘SeuratObject’ is not available and has been replaced +by .GlobalEnv when processing object ‘AJ064_small_last_sce’ +... +by .GlobalEnv when processing object ‘AJ064_small_last_sce’ +Warning: namespace ‘DBI’ is not available and has been replaced +by .GlobalEnv when processing object ‘AJ064_small_last_sce’ +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.3 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘scRNAstat’ +* removing ‘/tmp/workdir/scRNAstat/new/scRNAstat.Rcheck/scRNAstat’ + + +``` +### CRAN + +``` +* installing *source* package ‘scRNAstat’ ... +** package ‘scRNAstat’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** data +*** moving datasets to lazyload DB +Warning: namespace ‘Seurat’ is not available and has been replaced +by .GlobalEnv when processing object ‘AJ064_small_last_sce’ +Warning: namespace ‘SeuratObject’ is not available and has been replaced +by .GlobalEnv when processing object ‘AJ064_small_last_sce’ +... +by .GlobalEnv when processing object ‘AJ064_small_last_sce’ +Warning: namespace ‘DBI’ is not available and has been replaced +by .GlobalEnv when processing object ‘AJ064_small_last_sce’ +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.3 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘scRNAstat’ +* removing ‘/tmp/workdir/scRNAstat/old/scRNAstat.Rcheck/scRNAstat’ + + +``` +# sectorgap + +
+ +* Version: 0.1.0 +* GitHub: NA +* Source code: https://github.com/cran/sectorgap +* Date/Publication: 2024-01-22 17:40:02 UTC +* Number of recursive dependencies: 46 + +Run `revdepcheck::cloud_details(, "sectorgap")` for more info + +
+ +## In both + +* checking whether package ‘sectorgap’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/sectorgap/new/sectorgap.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘sectorgap’ ... +** package ‘sectorgap’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘sectorgap’ +* removing ‘/tmp/workdir/sectorgap/new/sectorgap.Rcheck/sectorgap’ + + +``` +### CRAN + +``` +* installing *source* package ‘sectorgap’ ... +** package ‘sectorgap’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘sectorgap’ +* removing ‘/tmp/workdir/sectorgap/old/sectorgap.Rcheck/sectorgap’ + + +``` +# SEERaBomb + +
+ +* Version: 2019.2 +* GitHub: NA +* Source code: https://github.com/cran/SEERaBomb +* Date/Publication: 2019-12-12 18:50:03 UTC +* Number of recursive dependencies: 184 + +Run `revdepcheck::cloud_details(, "SEERaBomb")` for more info + +
+ +## In both + +* checking whether package ‘SEERaBomb’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/SEERaBomb/new/SEERaBomb.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘SEERaBomb’ ... +** package ‘SEERaBomb’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C compiler: ‘gcc (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ +using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +gcc -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c SEERaBomb_init.c -o SEERaBomb_init.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c fillPYM.cpp -o fillPYM.o +g++ -std=gnu++17 -shared -L/opt/R/4.3.1/lib/R/lib -L/usr/local/lib -o SEERaBomb.so RcppExports.o SEERaBomb_init.o fillPYM.o -L/opt/R/4.3.1/lib/R/lib -lR +... +** R +** data +*** moving datasets to lazyload DB +** inst +** byte-compile and prepare package for lazy loading +Error: package or namespace load failed for ‘demography’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Execution halted +ERROR: lazy loading failed for package ‘SEERaBomb’ +* removing ‘/tmp/workdir/SEERaBomb/new/SEERaBomb.Rcheck/SEERaBomb’ + + +``` +### CRAN + +``` +* installing *source* package ‘SEERaBomb’ ... +** package ‘SEERaBomb’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C compiler: ‘gcc (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ +using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +gcc -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c SEERaBomb_init.c -o SEERaBomb_init.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c fillPYM.cpp -o fillPYM.o +g++ -std=gnu++17 -shared -L/opt/R/4.3.1/lib/R/lib -L/usr/local/lib -o SEERaBomb.so RcppExports.o SEERaBomb_init.o fillPYM.o -L/opt/R/4.3.1/lib/R/lib -lR +... +** R +** data +*** moving datasets to lazyload DB +** inst +** byte-compile and prepare package for lazy loading +Error: package or namespace load failed for ‘demography’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Execution halted +ERROR: lazy loading failed for package ‘SEERaBomb’ +* removing ‘/tmp/workdir/SEERaBomb/old/SEERaBomb.Rcheck/SEERaBomb’ + + +``` +# semicmprskcoxmsm + +
+ +* Version: 0.2.0 +* GitHub: NA +* Source code: https://github.com/cran/semicmprskcoxmsm +* Date/Publication: 2022-04-29 23:40:02 UTC +* Number of recursive dependencies: 70 + +Run `revdepcheck::cloud_details(, "semicmprskcoxmsm")` for more info + +
+ +## In both + +* checking whether package ‘semicmprskcoxmsm’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/semicmprskcoxmsm/new/semicmprskcoxmsm.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘semicmprskcoxmsm’ ... +** package ‘semicmprskcoxmsm’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘semicmprskcoxmsm’ +* removing ‘/tmp/workdir/semicmprskcoxmsm/new/semicmprskcoxmsm.Rcheck/semicmprskcoxmsm’ + + +``` +### CRAN + +``` +* installing *source* package ‘semicmprskcoxmsm’ ... +** package ‘semicmprskcoxmsm’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘semicmprskcoxmsm’ +* removing ‘/tmp/workdir/semicmprskcoxmsm/old/semicmprskcoxmsm.Rcheck/semicmprskcoxmsm’ + + +``` +# SensMap + +
+ +* Version: 0.7 +* GitHub: https://github.com/IbtihelRebhi/SensMap +* Source code: https://github.com/cran/SensMap +* Date/Publication: 2022-07-04 19:00:02 UTC +* Number of recursive dependencies: 146 + +Run `revdepcheck::cloud_details(, "SensMap")` for more info + +
+ +## In both + +* checking whether package ‘SensMap’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/SensMap/new/SensMap.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘SensMap’ ... +** package ‘SensMap’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘SensMap’ +* removing ‘/tmp/workdir/SensMap/new/SensMap.Rcheck/SensMap’ + + +``` +### CRAN + +``` +* installing *source* package ‘SensMap’ ... +** package ‘SensMap’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘SensMap’ +* removing ‘/tmp/workdir/SensMap/old/SensMap.Rcheck/SensMap’ + + +``` +# Seurat + +
+ +* Version: 5.0.3 +* GitHub: https://github.com/satijalab/seurat +* Source code: https://github.com/cran/Seurat +* Date/Publication: 2024-03-18 23:40:02 UTC +* Number of recursive dependencies: 265 + +Run `revdepcheck::cloud_details(, "Seurat")` for more info + +
+ +## In both + +* checking whether package ‘Seurat’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/Seurat/new/Seurat.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘Seurat’ ... +** package ‘Seurat’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C compiler: ‘gcc (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ +using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ +using C++17 +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppEigen/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppProgress/include' -I/usr/local/include -fpic -g -O2 -c ModularityOptimizer.cpp -o ModularityOptimizer.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppEigen/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppProgress/include' -I/usr/local/include -fpic -g -O2 -c RModularityOptimizer.cpp -o RModularityOptimizer.o +In file included from /opt/R/4.3.1/lib/R/site-library/RcppEigen/include/Eigen/Core:205, +... +** R +** data +*** moving datasets to lazyload DB +** inst +** byte-compile and prepare package for lazy loading +Error: package or namespace load failed for ‘SeuratObject’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): + namespace ‘Matrix’ 1.5-4.1 is being loaded, but >= 1.6.3 is required +Execution halted +ERROR: lazy loading failed for package ‘Seurat’ +* removing ‘/tmp/workdir/Seurat/new/Seurat.Rcheck/Seurat’ + + +``` +### CRAN + +``` +* installing *source* package ‘Seurat’ ... +** package ‘Seurat’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C compiler: ‘gcc (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ +using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ +using C++17 +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppEigen/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppProgress/include' -I/usr/local/include -fpic -g -O2 -c ModularityOptimizer.cpp -o ModularityOptimizer.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppEigen/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppProgress/include' -I/usr/local/include -fpic -g -O2 -c RModularityOptimizer.cpp -o RModularityOptimizer.o +In file included from /opt/R/4.3.1/lib/R/site-library/RcppEigen/include/Eigen/Core:205, +... +** R +** data +*** moving datasets to lazyload DB +** inst +** byte-compile and prepare package for lazy loading +Error: package or namespace load failed for ‘SeuratObject’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): + namespace ‘Matrix’ 1.5-4.1 is being loaded, but >= 1.6.3 is required +Execution halted +ERROR: lazy loading failed for package ‘Seurat’ +* removing ‘/tmp/workdir/Seurat/old/Seurat.Rcheck/Seurat’ + + +``` +# shinyTempSignal + +
+ +* Version: 0.0.8 +* GitHub: https://github.com/YuLab-SMU/shinyTempSignal +* Source code: https://github.com/cran/shinyTempSignal +* Date/Publication: 2024-03-06 08:00:02 UTC +* Number of recursive dependencies: 137 + +Run `revdepcheck::cloud_details(, "shinyTempSignal")` for more info + +
+ +## In both + +* checking whether package ‘shinyTempSignal’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/shinyTempSignal/new/shinyTempSignal.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘shinyTempSignal’ ... +** package ‘shinyTempSignal’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘shinyTempSignal’ +* removing ‘/tmp/workdir/shinyTempSignal/new/shinyTempSignal.Rcheck/shinyTempSignal’ + + +``` +### CRAN + +``` +* installing *source* package ‘shinyTempSignal’ ... +** package ‘shinyTempSignal’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘shinyTempSignal’ +* removing ‘/tmp/workdir/shinyTempSignal/old/shinyTempSignal.Rcheck/shinyTempSignal’ + + +``` +# Signac + +
+ +* Version: 1.13.0 +* GitHub: https://github.com/stuart-lab/signac +* Source code: https://github.com/cran/Signac +* Date/Publication: 2024-04-04 02:42:57 UTC +* Number of recursive dependencies: 249 + +Run `revdepcheck::cloud_details(, "Signac")` for more info + +
+ +## In both + +* checking whether package ‘Signac’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/Signac/new/Signac.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘Signac’ ... +** package ‘Signac’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c filter.cpp -o filter.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c group.cpp -o group.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c split.cpp -o split.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c validate.cpp -o validate.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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.3 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘Signac’ +* removing ‘/tmp/workdir/Signac/new/Signac.Rcheck/Signac’ + + +``` +### CRAN + +``` +* installing *source* package ‘Signac’ ... +** package ‘Signac’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c filter.cpp -o filter.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c group.cpp -o group.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c split.cpp -o split.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c validate.cpp -o validate.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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.3 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘Signac’ +* removing ‘/tmp/workdir/Signac/old/Signac.Rcheck/Signac’ + + +``` +# SimplyAgree + +
+ +* Version: 0.2.0 +* GitHub: https://github.com/arcaldwell49/SimplyAgree +* Source code: https://github.com/cran/SimplyAgree +* Date/Publication: 2024-03-21 14:20:06 UTC +* Number of recursive dependencies: 111 + +Run `revdepcheck::cloud_details(, "SimplyAgree")` for more info + +
+ +## In both + +* checking whether package ‘SimplyAgree’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/SimplyAgree/new/SimplyAgree.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘SimplyAgree’ ... +** package ‘SimplyAgree’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘SimplyAgree’ +* removing ‘/tmp/workdir/SimplyAgree/new/SimplyAgree.Rcheck/SimplyAgree’ + + +``` +### CRAN + +``` +* installing *source* package ‘SimplyAgree’ ... +** package ‘SimplyAgree’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘SimplyAgree’ +* removing ‘/tmp/workdir/SimplyAgree/old/SimplyAgree.Rcheck/SimplyAgree’ + + +``` +# sMSROC + +
+ +* Version: 0.1.2 +* GitHub: NA +* Source code: https://github.com/cran/sMSROC +* Date/Publication: 2023-12-07 15:50:02 UTC +* Number of recursive dependencies: 119 + +Run `revdepcheck::cloud_details(, "sMSROC")` for more info + +
+ +## In both + +* checking whether package ‘sMSROC’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/sMSROC/new/sMSROC.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘sMSROC’ ... +** package ‘sMSROC’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** data +*** moving datasets to lazyload DB +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘sMSROC’ +* removing ‘/tmp/workdir/sMSROC/new/sMSROC.Rcheck/sMSROC’ + + +``` +### CRAN + +``` +* installing *source* package ‘sMSROC’ ... +** package ‘sMSROC’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** data +*** moving datasets to lazyload DB +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘sMSROC’ +* removing ‘/tmp/workdir/sMSROC/old/sMSROC.Rcheck/sMSROC’ + + +``` +# SNPassoc + +
+ +* Version: 2.1-0 +* GitHub: https://github.com/isglobal-brge/SNPassoc +* Source code: https://github.com/cran/SNPassoc +* Date/Publication: 2022-12-14 20:20:02 UTC +* Number of recursive dependencies: 166 + +Run `revdepcheck::cloud_details(, "SNPassoc")` for more info + +
+ +## In both + +* checking whether package ‘SNPassoc’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/SNPassoc/new/SNPassoc.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘SNPassoc’ ... +** package ‘SNPassoc’ successfully unpacked and MD5 sums checked +** 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘SNPassoc’ +* removing ‘/tmp/workdir/SNPassoc/new/SNPassoc.Rcheck/SNPassoc’ + + +``` +### CRAN + +``` +* installing *source* package ‘SNPassoc’ ... +** package ‘SNPassoc’ successfully unpacked and MD5 sums checked +** 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘SNPassoc’ +* removing ‘/tmp/workdir/SNPassoc/old/SNPassoc.Rcheck/SNPassoc’ + + +``` +# snplinkage + +
+ +* Version: 1.0.0 +* GitHub: NA +* Source code: https://github.com/cran/snplinkage +* Date/Publication: 2023-05-04 08:10:02 UTC +* Number of recursive dependencies: 146 + +Run `revdepcheck::cloud_details(, "snplinkage")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/snplinkage/new/snplinkage.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0 + GNU Fortran (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0 +* running under: Ubuntu 20.04.6 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘snplinkage/DESCRIPTION’ ... OK +... +* this is package ‘snplinkage’ version ‘1.0.0’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘GWASTools’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/snplinkage/old/snplinkage.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0 + GNU Fortran (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0 +* running under: Ubuntu 20.04.6 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘snplinkage/DESCRIPTION’ ... OK +... +* this is package ‘snplinkage’ version ‘1.0.0’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘GWASTools’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# SoupX + +
+ +* Version: 1.6.2 +* GitHub: https://github.com/constantAmateur/SoupX +* Source code: https://github.com/cran/SoupX +* Date/Publication: 2022-11-01 14:00:03 UTC +* Number of recursive dependencies: 200 + +Run `revdepcheck::cloud_details(, "SoupX")` for more info + +
+ +## In both + +* checking whether package ‘SoupX’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/SoupX/new/SoupX.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘SoupX’ ... +** package ‘SoupX’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.3 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘SoupX’ +* removing ‘/tmp/workdir/SoupX/new/SoupX.Rcheck/SoupX’ ``` ### CRAN ``` -* installing *source* package ‘bmgarch’ ... -** package ‘bmgarch’ successfully unpacked and MD5 sums checked +* installing *source* package ‘SoupX’ ... +** package ‘SoupX’ successfully unpacked and MD5 sums checked ** using staged installation -** libs -using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ -using C++17 - - -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I"../inst/include" -I"/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src" -DBOOST_DISABLE_ASSERTS -DEIGEN_NO_DEBUG -DBOOST_MATH_OVERFLOW_ERROR_POLICY=errno_on_error -DUSE_STANC3 -D_HAS_AUTO_PTR_ETC=0 -I'/opt/R/4.3.1/lib/R/site-library/BH/include' -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppEigen/include' -I'/opt/R/4.3.1/lib/R/site-library/rstan/include' -I'/opt/R/4.3.1/lib/R/site-library/StanHeaders/include' -I/usr/local/include -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -D_REENTRANT -DSTAN_THREADS -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o -In file included from /opt/R/4.3.1/lib/R/site-library/RcppEigen/include/Eigen/Core:205, -... -/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src/stan/mcmc/hmc/hamiltonians/dense_e_metric.hpp:22:56: required from ‘double stan::mcmc::dense_e_metric::T(stan::mcmc::dense_e_point&) [with Model = model_DCCMGARCH_namespace::model_DCCMGARCH; BaseRNG = boost::random::additive_combine_engine, boost::random::linear_congruential_engine >]’ -/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src/stan/mcmc/hmc/hamiltonians/dense_e_metric.hpp:21:10: required from here -/opt/R/4.3.1/lib/R/site-library/RcppEigen/include/Eigen/src/Core/DenseCoeffsBase.h:654:34: warning: ignoring attributes on template argument ‘Eigen::internal::packet_traits::type’ {aka ‘__vector(2) double’} [-Wignored-attributes] - 654 | return internal::first_aligned::alignment),Derived>(m); - | ^~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -g++: fatal error: Killed signal terminated program cc1plus -compilation terminated. -make: *** [/opt/R/4.3.1/lib/R/etc/Makeconf:198: stanExports_DCCMGARCH.o] Error 1 -ERROR: compilation failed for package ‘bmgarch’ -* removing ‘/tmp/workdir/bmgarch/old/bmgarch.Rcheck/bmgarch’ +** 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.3 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘SoupX’ +* removing ‘/tmp/workdir/SoupX/old/SoupX.Rcheck/SoupX’ ``` -# ctsem +# sparsereg
-* Version: 3.9.1 -* GitHub: https://github.com/cdriveraus/ctsem -* Source code: https://github.com/cran/ctsem -* Date/Publication: 2023-10-30 14:20:02 UTC -* Number of recursive dependencies: 143 +* Version: 1.2 +* GitHub: NA +* Source code: https://github.com/cran/sparsereg +* Date/Publication: 2016-03-10 23:32:18 +* Number of recursive dependencies: 49 -Run `revdepcheck::cloud_details(, "ctsem")` for more info +Run `revdepcheck::cloud_details(, "sparsereg")` for more info
## In both -* checking whether package ‘ctsem’ can be installed ... ERROR +* checking whether package ‘sparsereg’ can be installed ... ERROR ``` Installation failed. - See ‘/tmp/workdir/ctsem/new/ctsem.Rcheck/00install.out’ for details. + See ‘/tmp/workdir/sparsereg/new/sparsereg.Rcheck/00install.out’ for details. ``` ## Installation @@ -181,77 +7656,73 @@ Run `revdepcheck::cloud_details(, "ctsem")` for more info ### Devel ``` -* installing *source* package ‘ctsem’ ... -** package ‘ctsem’ successfully unpacked and MD5 sums checked +* installing *source* package ‘sparsereg’ ... +** package ‘sparsereg’ successfully unpacked and MD5 sums checked ** using staged installation ** libs using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ -using C++17 - - -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I"../inst/include" -I"/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src" -DBOOST_DISABLE_ASSERTS -DEIGEN_NO_DEBUG -DBOOST_MATH_OVERFLOW_ERROR_POLICY=errno_on_error -DUSE_STANC3 -D_HAS_AUTO_PTR_ETC=0 -I'/opt/R/4.3.1/lib/R/site-library/BH/include' -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppEigen/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -I'/opt/R/4.3.1/lib/R/site-library/rstan/include' -I'/opt/R/4.3.1/lib/R/site-library/StanHeaders/include' -I/usr/local/include -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -D_REENTRANT -DSTAN_THREADS -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o -In file included from /opt/R/4.3.1/lib/R/site-library/RcppEigen/include/Eigen/Core:205, -... -/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src/stan/mcmc/hmc/hamiltonians/dense_e_metric.hpp:22:56: required from ‘double stan::mcmc::dense_e_metric::T(stan::mcmc::dense_e_point&) [with Model = model_ctsm_namespace::model_ctsm; BaseRNG = boost::random::additive_combine_engine, boost::random::linear_congruential_engine >]’ -/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src/stan/mcmc/hmc/hamiltonians/dense_e_metric.hpp:21:10: required from here -/opt/R/4.3.1/lib/R/site-library/RcppEigen/include/Eigen/src/Core/DenseCoeffsBase.h:654:34: warning: ignoring attributes on template argument ‘Eigen::internal::packet_traits::type’ {aka ‘__vector(2) double’} [-Wignored-attributes] - 654 | return internal::first_aligned::alignment),Derived>(m); - | ^~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -g++: fatal error: Killed signal terminated program cc1plus -compilation terminated. -make: *** [/opt/R/4.3.1/lib/R/etc/Makeconf:198: stanExports_ctsm.o] Error 1 -ERROR: compilation failed for package ‘ctsem’ -* removing ‘/tmp/workdir/ctsem/new/ctsem.Rcheck/ctsem’ +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c makeinter.cpp -o makeinter.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c makethreeinter.cpp -o makethreeinter.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c subgroup.cpp -o subgroup.o +g++ -std=gnu++17 -shared -L/opt/R/4.3.1/lib/R/lib -L/usr/local/lib -o sparsereg.so RcppExports.o makeinter.o makethreeinter.o subgroup.o -llapack -lblas -lgfortran -lm -lquadmath -L/opt/R/4.3.1/lib/R/lib -lR +installing to /tmp/workdir/sparsereg/new/sparsereg.Rcheck/00LOCK-sparsereg/00new/sparsereg/libs +** R +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘sparsereg’ +* removing ‘/tmp/workdir/sparsereg/new/sparsereg.Rcheck/sparsereg’ ``` ### CRAN ``` -* installing *source* package ‘ctsem’ ... -** package ‘ctsem’ successfully unpacked and MD5 sums checked +* installing *source* package ‘sparsereg’ ... +** package ‘sparsereg’ successfully unpacked and MD5 sums checked ** using staged installation ** libs using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ -using C++17 - - -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I"../inst/include" -I"/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src" -DBOOST_DISABLE_ASSERTS -DEIGEN_NO_DEBUG -DBOOST_MATH_OVERFLOW_ERROR_POLICY=errno_on_error -DUSE_STANC3 -D_HAS_AUTO_PTR_ETC=0 -I'/opt/R/4.3.1/lib/R/site-library/BH/include' -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppEigen/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -I'/opt/R/4.3.1/lib/R/site-library/rstan/include' -I'/opt/R/4.3.1/lib/R/site-library/StanHeaders/include' -I/usr/local/include -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -D_REENTRANT -DSTAN_THREADS -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o -In file included from /opt/R/4.3.1/lib/R/site-library/RcppEigen/include/Eigen/Core:205, -... -/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src/stan/mcmc/hmc/hamiltonians/dense_e_metric.hpp:22:56: required from ‘double stan::mcmc::dense_e_metric::T(stan::mcmc::dense_e_point&) [with Model = model_ctsm_namespace::model_ctsm; BaseRNG = boost::random::additive_combine_engine, boost::random::linear_congruential_engine >]’ -/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src/stan/mcmc/hmc/hamiltonians/dense_e_metric.hpp:21:10: required from here -/opt/R/4.3.1/lib/R/site-library/RcppEigen/include/Eigen/src/Core/DenseCoeffsBase.h:654:34: warning: ignoring attributes on template argument ‘Eigen::internal::packet_traits::type’ {aka ‘__vector(2) double’} [-Wignored-attributes] - 654 | return internal::first_aligned::alignment),Derived>(m); - | ^~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -g++: fatal error: Killed signal terminated program cc1plus -compilation terminated. -make: *** [/opt/R/4.3.1/lib/R/etc/Makeconf:198: stanExports_ctsm.o] Error 1 -ERROR: compilation failed for package ‘ctsem’ -* removing ‘/tmp/workdir/ctsem/old/ctsem.Rcheck/ctsem’ +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c makeinter.cpp -o makeinter.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c makethreeinter.cpp -o makethreeinter.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c subgroup.cpp -o subgroup.o +g++ -std=gnu++17 -shared -L/opt/R/4.3.1/lib/R/lib -L/usr/local/lib -o sparsereg.so RcppExports.o makeinter.o makethreeinter.o subgroup.o -llapack -lblas -lgfortran -lm -lquadmath -L/opt/R/4.3.1/lib/R/lib -lR +installing to /tmp/workdir/sparsereg/old/sparsereg.Rcheck/00LOCK-sparsereg/00new/sparsereg/libs +** R +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘sparsereg’ +* removing ‘/tmp/workdir/sparsereg/old/sparsereg.Rcheck/sparsereg’ ``` -# EcoEnsemble +# spikeSlabGAM
-* Version: 1.0.5 -* GitHub: NA -* Source code: https://github.com/cran/EcoEnsemble -* Date/Publication: 2023-09-18 11:50:02 UTC -* Number of recursive dependencies: 91 +* Version: 1.1-19 +* GitHub: https://github.com/fabian-s/spikeSlabGAM +* Source code: https://github.com/cran/spikeSlabGAM +* Date/Publication: 2022-06-10 15:50:07 UTC +* Number of recursive dependencies: 77 -Run `revdepcheck::cloud_details(, "EcoEnsemble")` for more info +Run `revdepcheck::cloud_details(, "spikeSlabGAM")` for more info
## In both -* checking whether package ‘EcoEnsemble’ can be installed ... ERROR +* checking whether package ‘spikeSlabGAM’ can be installed ... ERROR ``` Installation failed. - See ‘/tmp/workdir/EcoEnsemble/new/EcoEnsemble.Rcheck/00install.out’ for details. + See ‘/tmp/workdir/spikeSlabGAM/new/spikeSlabGAM.Rcheck/00install.out’ for details. ``` ## Installation @@ -259,77 +7730,71 @@ Run `revdepcheck::cloud_details(, "EcoEnsemble")` for more info ### Devel ``` -* installing *source* package ‘EcoEnsemble’ ... -** package ‘EcoEnsemble’ successfully unpacked and MD5 sums checked +* installing *source* package ‘spikeSlabGAM’ ... +** package ‘spikeSlabGAM’ successfully unpacked and MD5 sums checked ** using staged installation ** libs -using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ -using C++17 - - -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I"../inst/include" -I"/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src" -DBOOST_DISABLE_ASSERTS -DEIGEN_NO_DEBUG -DBOOST_MATH_OVERFLOW_ERROR_POLICY=errno_on_error -DUSE_STANC3 -D_HAS_AUTO_PTR_ETC=0 -I'/opt/R/4.3.1/lib/R/site-library/BH/include' -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppEigen/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -I'/opt/R/4.3.1/lib/R/site-library/rstan/include' -I'/opt/R/4.3.1/lib/R/site-library/StanHeaders/include' -I/usr/local/include -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -D_REENTRANT -DSTAN_THREADS -fpic -g -O2 -c KF_back.cpp -o KF_back.o -In file included from /opt/R/4.3.1/lib/R/site-library/RcppEigen/include/Eigen/Core:205, -... -/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src/stan/mcmc/hmc/hamiltonians/dense_e_metric.hpp:22:56: required from ‘double stan::mcmc::dense_e_metric::T(stan::mcmc::dense_e_point&) [with Model = model_ensemble_model_namespace::model_ensemble_model; BaseRNG = boost::random::additive_combine_engine, boost::random::linear_congruential_engine >]’ -/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src/stan/mcmc/hmc/hamiltonians/dense_e_metric.hpp:21:10: required from here -/opt/R/4.3.1/lib/R/site-library/RcppEigen/include/Eigen/src/Core/DenseCoeffsBase.h:654:34: warning: ignoring attributes on template argument ‘Eigen::internal::packet_traits::type’ {aka ‘__vector(2) double’} [-Wignored-attributes] - 654 | return internal::first_aligned::alignment),Derived>(m); - | ^~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -g++: fatal error: Killed signal terminated program cc1plus -compilation terminated. -make: *** [/opt/R/4.3.1/lib/R/etc/Makeconf:198: stanExports_ensemble_model.o] Error 1 -ERROR: compilation failed for package ‘EcoEnsemble’ -* removing ‘/tmp/workdir/EcoEnsemble/new/EcoEnsemble.Rcheck/EcoEnsemble’ +using C compiler: ‘gcc (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ +gcc -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I/usr/local/include -fpic -g -O2 -c sampler.c -o sampler.o +gcc -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I/usr/local/include -fpic -g -O2 -c spikeSlabGAM_init.c -o spikeSlabGAM_init.o +gcc -shared -L/opt/R/4.3.1/lib/R/lib -L/usr/local/lib -o spikeSlabGAM.so sampler.o spikeSlabGAM_init.o -llapack -lblas -lgfortran -lm -lquadmath -L/opt/R/4.3.1/lib/R/lib -lR +installing to /tmp/workdir/spikeSlabGAM/new/spikeSlabGAM.Rcheck/00LOCK-spikeSlabGAM/00new/spikeSlabGAM/libs +** R +** inst +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘spikeSlabGAM’ +* removing ‘/tmp/workdir/spikeSlabGAM/new/spikeSlabGAM.Rcheck/spikeSlabGAM’ ``` ### CRAN ``` -* installing *source* package ‘EcoEnsemble’ ... -** package ‘EcoEnsemble’ successfully unpacked and MD5 sums checked +* installing *source* package ‘spikeSlabGAM’ ... +** package ‘spikeSlabGAM’ successfully unpacked and MD5 sums checked ** using staged installation ** libs -using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ -using C++17 - - -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I"../inst/include" -I"/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src" -DBOOST_DISABLE_ASSERTS -DEIGEN_NO_DEBUG -DBOOST_MATH_OVERFLOW_ERROR_POLICY=errno_on_error -DUSE_STANC3 -D_HAS_AUTO_PTR_ETC=0 -I'/opt/R/4.3.1/lib/R/site-library/BH/include' -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppEigen/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -I'/opt/R/4.3.1/lib/R/site-library/rstan/include' -I'/opt/R/4.3.1/lib/R/site-library/StanHeaders/include' -I/usr/local/include -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -D_REENTRANT -DSTAN_THREADS -fpic -g -O2 -c KF_back.cpp -o KF_back.o -In file included from /opt/R/4.3.1/lib/R/site-library/RcppEigen/include/Eigen/Core:205, -... -/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src/stan/mcmc/hmc/hamiltonians/dense_e_metric.hpp:22:56: required from ‘double stan::mcmc::dense_e_metric::T(stan::mcmc::dense_e_point&) [with Model = model_ensemble_model_namespace::model_ensemble_model; BaseRNG = boost::random::additive_combine_engine, boost::random::linear_congruential_engine >]’ -/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src/stan/mcmc/hmc/hamiltonians/dense_e_metric.hpp:21:10: required from here -/opt/R/4.3.1/lib/R/site-library/RcppEigen/include/Eigen/src/Core/DenseCoeffsBase.h:654:34: warning: ignoring attributes on template argument ‘Eigen::internal::packet_traits::type’ {aka ‘__vector(2) double’} [-Wignored-attributes] - 654 | return internal::first_aligned::alignment),Derived>(m); - | ^~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -g++: fatal error: Killed signal terminated program cc1plus -compilation terminated. -make: *** [/opt/R/4.3.1/lib/R/etc/Makeconf:198: stanExports_ensemble_model.o] Error 1 -ERROR: compilation failed for package ‘EcoEnsemble’ -* removing ‘/tmp/workdir/EcoEnsemble/old/EcoEnsemble.Rcheck/EcoEnsemble’ +using C compiler: ‘gcc (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ +gcc -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I/usr/local/include -fpic -g -O2 -c sampler.c -o sampler.o +gcc -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I/usr/local/include -fpic -g -O2 -c spikeSlabGAM_init.c -o spikeSlabGAM_init.o +gcc -shared -L/opt/R/4.3.1/lib/R/lib -L/usr/local/lib -o spikeSlabGAM.so sampler.o spikeSlabGAM_init.o -llapack -lblas -lgfortran -lm -lquadmath -L/opt/R/4.3.1/lib/R/lib -lR +installing to /tmp/workdir/spikeSlabGAM/old/spikeSlabGAM.Rcheck/00LOCK-spikeSlabGAM/00new/spikeSlabGAM/libs +** R +** inst +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘spikeSlabGAM’ +* removing ‘/tmp/workdir/spikeSlabGAM/old/spikeSlabGAM.Rcheck/spikeSlabGAM’ ``` -# geostan +# statsr
-* Version: 0.5.4 -* GitHub: https://github.com/ConnorDonegan/geostan -* Source code: https://github.com/cran/geostan -* Date/Publication: 2024-03-03 15:22:39 UTC -* Number of recursive dependencies: 108 +* Version: 0.3.0 +* GitHub: https://github.com/StatsWithR/statsr +* Source code: https://github.com/cran/statsr +* Date/Publication: 2021-01-22 20:40:03 UTC +* Number of recursive dependencies: 98 -Run `revdepcheck::cloud_details(, "geostan")` for more info +Run `revdepcheck::cloud_details(, "statsr")` for more info
## In both -* checking whether package ‘geostan’ can be installed ... ERROR +* checking whether package ‘statsr’ can be installed ... ERROR ``` Installation failed. - See ‘/tmp/workdir/geostan/new/geostan.Rcheck/00install.out’ for details. + See ‘/tmp/workdir/statsr/new/statsr.Rcheck/00install.out’ for details. ``` ## Installation @@ -337,68 +7802,52 @@ Run `revdepcheck::cloud_details(, "geostan")` for more info ### Devel ``` -* installing *source* package ‘geostan’ ... -** package ‘geostan’ successfully unpacked and MD5 sums checked +* installing *source* package ‘statsr’ ... +** package ‘statsr’ successfully unpacked and MD5 sums checked ** using staged installation -** libs -using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ -using C++17 - - -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I"../inst/include" -I"/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src" -DBOOST_DISABLE_ASSERTS -DEIGEN_NO_DEBUG -DBOOST_MATH_OVERFLOW_ERROR_POLICY=errno_on_error -DUSE_STANC3 -D_HAS_AUTO_PTR_ETC=0 -I'/opt/R/4.3.1/lib/R/site-library/BH/include' -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppEigen/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -I'/opt/R/4.3.1/lib/R/site-library/rstan/include' -I'/opt/R/4.3.1/lib/R/site-library/StanHeaders/include' -I/usr/local/include -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -D_REENTRANT -DSTAN_THREADS -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o -In file included from /opt/R/4.3.1/lib/R/site-library/RcppEigen/include/Eigen/Core:205, -... -/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src/stan/mcmc/hmc/hamiltonians/dense_e_metric.hpp:22:56: required from ‘double stan::mcmc::dense_e_metric::T(stan::mcmc::dense_e_point&) [with Model = model_foundation_namespace::model_foundation; BaseRNG = boost::random::additive_combine_engine, boost::random::linear_congruential_engine >]’ -/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src/stan/mcmc/hmc/hamiltonians/dense_e_metric.hpp:21:10: required from here -/opt/R/4.3.1/lib/R/site-library/RcppEigen/include/Eigen/src/Core/DenseCoeffsBase.h:654:34: warning: ignoring attributes on template argument ‘Eigen::internal::packet_traits::type’ {aka ‘__vector(2) double’} [-Wignored-attributes] - 654 | return internal::first_aligned::alignment),Derived>(m); - | ^~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -g++: fatal error: Killed signal terminated program cc1plus -compilation terminated. -make: *** [/opt/R/4.3.1/lib/R/etc/Makeconf:198: stanExports_foundation.o] Error 1 -ERROR: compilation failed for package ‘geostan’ -* removing ‘/tmp/workdir/geostan/new/geostan.Rcheck/geostan’ +** R +** data +*** moving datasets to lazyload DB +** inst +** byte-compile and prepare package for lazy loading +Error: package or namespace load failed for ‘BayesFactor’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Execution halted +ERROR: lazy loading failed for package ‘statsr’ +* removing ‘/tmp/workdir/statsr/new/statsr.Rcheck/statsr’ ``` ### CRAN ``` -* installing *source* package ‘geostan’ ... -** package ‘geostan’ successfully unpacked and MD5 sums checked +* installing *source* package ‘statsr’ ... +** package ‘statsr’ successfully unpacked and MD5 sums checked ** using staged installation -** libs -using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ -using C++17 - - -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I"../inst/include" -I"/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src" -DBOOST_DISABLE_ASSERTS -DEIGEN_NO_DEBUG -DBOOST_MATH_OVERFLOW_ERROR_POLICY=errno_on_error -DUSE_STANC3 -D_HAS_AUTO_PTR_ETC=0 -I'/opt/R/4.3.1/lib/R/site-library/BH/include' -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppEigen/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -I'/opt/R/4.3.1/lib/R/site-library/rstan/include' -I'/opt/R/4.3.1/lib/R/site-library/StanHeaders/include' -I/usr/local/include -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -D_REENTRANT -DSTAN_THREADS -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o -In file included from /opt/R/4.3.1/lib/R/site-library/RcppEigen/include/Eigen/Core:205, -... -/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src/stan/mcmc/hmc/hamiltonians/dense_e_metric.hpp:22:56: required from ‘double stan::mcmc::dense_e_metric::T(stan::mcmc::dense_e_point&) [with Model = model_foundation_namespace::model_foundation; BaseRNG = boost::random::additive_combine_engine, boost::random::linear_congruential_engine >]’ -/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src/stan/mcmc/hmc/hamiltonians/dense_e_metric.hpp:21:10: required from here -/opt/R/4.3.1/lib/R/site-library/RcppEigen/include/Eigen/src/Core/DenseCoeffsBase.h:654:34: warning: ignoring attributes on template argument ‘Eigen::internal::packet_traits::type’ {aka ‘__vector(2) double’} [-Wignored-attributes] - 654 | return internal::first_aligned::alignment),Derived>(m); - | ^~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -g++: fatal error: Killed signal terminated program cc1plus -compilation terminated. -make: *** [/opt/R/4.3.1/lib/R/etc/Makeconf:198: stanExports_foundation.o] Error 1 -ERROR: compilation failed for package ‘geostan’ -* removing ‘/tmp/workdir/geostan/old/geostan.Rcheck/geostan’ +** R +** data +*** moving datasets to lazyload DB +** inst +** byte-compile and prepare package for lazy loading +Error: package or namespace load failed for ‘BayesFactor’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Execution halted +ERROR: lazy loading failed for package ‘statsr’ +* removing ‘/tmp/workdir/statsr/old/statsr.Rcheck/statsr’ ``` -# grandR +# streamDAG
-* Version: 0.2.5 -* GitHub: https://github.com/erhard-lab/grandR -* Source code: https://github.com/cran/grandR -* Date/Publication: 2024-02-15 15:30:02 UTC -* Number of recursive dependencies: 266 +* Version: 1.5 +* GitHub: NA +* Source code: https://github.com/cran/streamDAG +* Date/Publication: 2023-10-06 18:50:02 UTC +* Number of recursive dependencies: 133 -Run `revdepcheck::cloud_details(, "grandR")` for more info +Run `revdepcheck::cloud_details(, "streamDAG")` for more info
@@ -407,7 +7856,7 @@ Run `revdepcheck::cloud_details(, "grandR")` for more info ### Devel ``` -* using log directory ‘/tmp/workdir/grandR/new/grandR.Rcheck’ +* using log directory ‘/tmp/workdir/streamDAG/new/streamDAG.Rcheck’ * using R version 4.3.1 (2023-06-16) * using platform: x86_64-pc-linux-gnu (64-bit) * R was compiled by @@ -416,18 +7865,16 @@ Run `revdepcheck::cloud_details(, "grandR")` for more info * running under: Ubuntu 20.04.6 LTS * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘grandR/DESCRIPTION’ ... OK -... -* checking installed files from ‘inst/doc’ ... OK -* checking files in ‘vignettes’ ... OK -* checking examples ... OK -* checking for unstated dependencies in vignettes ... OK -* checking package vignettes in ‘inst/doc’ ... OK -* checking running R code from vignettes ... NONE - ‘getting-started.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK +* checking for file ‘streamDAG/DESCRIPTION’ ... OK +* this is package ‘streamDAG’ version ‘1.5’ +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘asbio’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. * DONE -Status: 2 NOTEs +Status: 1 ERROR @@ -437,7 +7884,7 @@ Status: 2 NOTEs ### CRAN ``` -* using log directory ‘/tmp/workdir/grandR/old/grandR.Rcheck’ +* using log directory ‘/tmp/workdir/streamDAG/old/streamDAG.Rcheck’ * using R version 4.3.1 (2023-06-16) * using platform: x86_64-pc-linux-gnu (64-bit) * R was compiled by @@ -446,44 +7893,112 @@ Status: 2 NOTEs * running under: Ubuntu 20.04.6 LTS * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘grandR/DESCRIPTION’ ... OK -... -* checking installed files from ‘inst/doc’ ... OK -* checking files in ‘vignettes’ ... OK -* checking examples ... OK -* checking for unstated dependencies in vignettes ... OK -* checking package vignettes in ‘inst/doc’ ... OK -* checking running R code from vignettes ... NONE - ‘getting-started.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK +* checking for file ‘streamDAG/DESCRIPTION’ ... OK +* this is package ‘streamDAG’ version ‘1.5’ +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘asbio’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. * DONE -Status: 2 NOTEs +Status: 1 ERROR + + + + + +``` +# survHE + +
+ +* Version: 2.0.1 +* GitHub: https://github.com/giabaio/survHE +* Source code: https://github.com/cran/survHE +* Date/Publication: 2023-03-19 22:10:02 UTC +* Number of recursive dependencies: 130 + +Run `revdepcheck::cloud_details(, "survHE")` for more info + +
+ +## In both + +* checking whether package ‘survHE’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/survHE/new/survHE.Rcheck/00install.out’ for details. + ``` + +* checking package dependencies ... NOTE + ``` + Packages suggested but not available for checking: + 'survHEinla', 'survHEhmc' + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘survHE’ ... +** package ‘survHE’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘survHE’ +* removing ‘/tmp/workdir/survHE/new/survHE.Rcheck/survHE’ +``` +### CRAN +``` +* installing *source* package ‘survHE’ ... +** package ‘survHE’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘survHE’ +* removing ‘/tmp/workdir/survHE/old/survHE.Rcheck/survHE’ ``` -# multilevelcoda +# survidm
-* Version: 1.2.3 -* GitHub: https://github.com/florale/multilevelcoda -* Source code: https://github.com/cran/multilevelcoda -* Date/Publication: 2024-03-10 23:00:03 UTC -* Number of recursive dependencies: 159 +* Version: 1.3.2 +* GitHub: NA +* Source code: https://github.com/cran/survidm +* Date/Publication: 2021-06-24 23:20:02 UTC +* Number of recursive dependencies: 87 -Run `revdepcheck::cloud_details(, "multilevelcoda")` for more info +Run `revdepcheck::cloud_details(, "survidm")` for more info
## In both -* checking whether package ‘multilevelcoda’ can be installed ... ERROR +* checking whether package ‘survidm’ can be installed ... ERROR ``` Installation failed. - See ‘/tmp/workdir/multilevelcoda/new/multilevelcoda.Rcheck/00install.out’ for details. + See ‘/tmp/workdir/survidm/new/survidm.Rcheck/00install.out’ for details. ``` ## Installation @@ -491,59 +8006,73 @@ Run `revdepcheck::cloud_details(, "multilevelcoda")` for more info ### Devel ``` -* installing *source* package ‘multilevelcoda’ ... -** package ‘multilevelcoda’ successfully unpacked and MD5 sums checked +* installing *source* package ‘survidm’ ... +** package ‘survidm’ successfully unpacked and MD5 sums checked ** using staged installation +** libs +using C compiler: ‘gcc (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ +gcc -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c survidm_init.c -o survidm_init.o +gcc -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c survivalBIV.c -o survivalBIV.o +gcc -shared -L/opt/R/4.3.1/lib/R/lib -L/usr/local/lib -o survidm.so survidm_init.o survivalBIV.o -L/opt/R/4.3.1/lib/R/lib -lR +installing to /tmp/workdir/survidm/new/survidm.Rcheck/00LOCK-survidm/00new/survidm/libs ** R ** data *** moving datasets to lazyload DB -** inst ** byte-compile and prepare package for lazy loading -Error: object ‘launch_shinystan’ is not exported by 'namespace:brms' +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace Execution halted -ERROR: lazy loading failed for package ‘multilevelcoda’ -* removing ‘/tmp/workdir/multilevelcoda/new/multilevelcoda.Rcheck/multilevelcoda’ +ERROR: lazy loading failed for package ‘survidm’ +* removing ‘/tmp/workdir/survidm/new/survidm.Rcheck/survidm’ ``` ### CRAN ``` -* installing *source* package ‘multilevelcoda’ ... -** package ‘multilevelcoda’ successfully unpacked and MD5 sums checked +* installing *source* package ‘survidm’ ... +** package ‘survidm’ successfully unpacked and MD5 sums checked ** using staged installation +** libs +using C compiler: ‘gcc (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ +gcc -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c survidm_init.c -o survidm_init.o +gcc -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c survivalBIV.c -o survivalBIV.o +gcc -shared -L/opt/R/4.3.1/lib/R/lib -L/usr/local/lib -o survidm.so survidm_init.o survivalBIV.o -L/opt/R/4.3.1/lib/R/lib -lR +installing to /tmp/workdir/survidm/old/survidm.Rcheck/00LOCK-survidm/00new/survidm/libs ** R ** data *** moving datasets to lazyload DB -** inst ** byte-compile and prepare package for lazy loading -Error: object ‘launch_shinystan’ is not exported by 'namespace:brms' +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace Execution halted -ERROR: lazy loading failed for package ‘multilevelcoda’ -* removing ‘/tmp/workdir/multilevelcoda/old/multilevelcoda.Rcheck/multilevelcoda’ +ERROR: lazy loading failed for package ‘survidm’ +* removing ‘/tmp/workdir/survidm/old/survidm.Rcheck/survidm’ ``` -# multinma +# tempted
-* Version: 0.6.1 -* GitHub: https://github.com/dmphillippo/multinma -* Source code: https://github.com/cran/multinma -* Date/Publication: 2024-03-06 01:00:05 UTC -* Number of recursive dependencies: 151 +* Version: 0.1.0 +* GitHub: https://github.com/pixushi/tempted +* Source code: https://github.com/cran/tempted +* Date/Publication: 2024-01-11 10:10:02 UTC +* Number of recursive dependencies: 37 -Run `revdepcheck::cloud_details(, "multinma")` for more info +Run `revdepcheck::cloud_details(, "tempted")` for more info
## In both -* checking whether package ‘multinma’ can be installed ... ERROR +* checking whether package ‘tempted’ can be installed ... ERROR ``` Installation failed. - See ‘/tmp/workdir/multinma/new/multinma.Rcheck/00install.out’ for details. + See ‘/tmp/workdir/tempted/new/tempted.Rcheck/00install.out’ for details. ``` ## Installation @@ -551,77 +8080,61 @@ Run `revdepcheck::cloud_details(, "multinma")` for more info ### Devel ``` -* installing *source* package ‘multinma’ ... -** package ‘multinma’ successfully unpacked and MD5 sums checked +* installing *source* package ‘tempted’ ... +** package ‘tempted’ successfully unpacked and MD5 sums checked ** using staged installation -** libs -using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ -using C++17 - - -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I"../inst/include" -I"/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src" -DBOOST_DISABLE_ASSERTS -DEIGEN_NO_DEBUG -DBOOST_MATH_OVERFLOW_ERROR_POLICY=errno_on_error -DUSE_STANC3 -D_HAS_AUTO_PTR_ETC=0 -I'/opt/R/4.3.1/lib/R/site-library/BH/include' -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppEigen/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -I'/opt/R/4.3.1/lib/R/site-library/rstan/include' -I'/opt/R/4.3.1/lib/R/site-library/StanHeaders/include' -I/usr/local/include -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -D_REENTRANT -DSTAN_THREADS -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o -In file included from /opt/R/4.3.1/lib/R/site-library/RcppEigen/include/Eigen/Core:205, -... -In file included from stanExports_survival_mspline.cc:5: -stanExports_survival_mspline.h: In constructor ‘model_survival_mspline_namespace::model_survival_mspline::model_survival_mspline(stan::io::var_context&, unsigned int, std::ostream*)’: -stanExports_survival_mspline.h:2252:3: note: variable tracking size limit exceeded with ‘-fvar-tracking-assignments’, retrying without - 2252 | model_survival_mspline(stan::io::var_context& context__, unsigned int - | ^~~~~~~~~~~~~~~~~~~~~~ -g++: fatal error: Killed signal terminated program cc1plus -compilation terminated. -make: *** [/opt/R/4.3.1/lib/R/etc/Makeconf:198: stanExports_survival_mspline.o] Error 1 -ERROR: compilation failed for package ‘multinma’ -* removing ‘/tmp/workdir/multinma/new/multinma.Rcheck/multinma’ +** R +** data +*** moving datasets to lazyload DB +** inst +** byte-compile and prepare package for lazy loading +Error: package or namespace load failed for ‘np’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Execution halted +ERROR: lazy loading failed for package ‘tempted’ +* removing ‘/tmp/workdir/tempted/new/tempted.Rcheck/tempted’ ``` ### CRAN ``` -* installing *source* package ‘multinma’ ... -** package ‘multinma’ successfully unpacked and MD5 sums checked +* installing *source* package ‘tempted’ ... +** package ‘tempted’ successfully unpacked and MD5 sums checked ** using staged installation -** libs -using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ -using C++17 - - -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I"../inst/include" -I"/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src" -DBOOST_DISABLE_ASSERTS -DEIGEN_NO_DEBUG -DBOOST_MATH_OVERFLOW_ERROR_POLICY=errno_on_error -DUSE_STANC3 -D_HAS_AUTO_PTR_ETC=0 -I'/opt/R/4.3.1/lib/R/site-library/BH/include' -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppEigen/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -I'/opt/R/4.3.1/lib/R/site-library/rstan/include' -I'/opt/R/4.3.1/lib/R/site-library/StanHeaders/include' -I/usr/local/include -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -D_REENTRANT -DSTAN_THREADS -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o -In file included from /opt/R/4.3.1/lib/R/site-library/RcppEigen/include/Eigen/Core:205, -... -In file included from stanExports_survival_mspline.cc:5: -stanExports_survival_mspline.h: In constructor ‘model_survival_mspline_namespace::model_survival_mspline::model_survival_mspline(stan::io::var_context&, unsigned int, std::ostream*)’: -stanExports_survival_mspline.h:2252:3: note: variable tracking size limit exceeded with ‘-fvar-tracking-assignments’, retrying without - 2252 | model_survival_mspline(stan::io::var_context& context__, unsigned int - | ^~~~~~~~~~~~~~~~~~~~~~ -g++: fatal error: Killed signal terminated program cc1plus -compilation terminated. -make: *** [/opt/R/4.3.1/lib/R/etc/Makeconf:198: stanExports_survival_mspline.o] Error 1 -ERROR: compilation failed for package ‘multinma’ -* removing ‘/tmp/workdir/multinma/old/multinma.Rcheck/multinma’ +** R +** data +*** moving datasets to lazyload DB +** inst +** byte-compile and prepare package for lazy loading +Error: package or namespace load failed for ‘np’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Execution halted +ERROR: lazy loading failed for package ‘tempted’ +* removing ‘/tmp/workdir/tempted/old/tempted.Rcheck/tempted’ ``` -# rmsb +# tidydr
-* Version: 1.1-0 -* GitHub: NA -* Source code: https://github.com/cran/rmsb -* Date/Publication: 2024-03-12 15:50:02 UTC -* Number of recursive dependencies: 144 +* Version: 0.0.5 +* GitHub: https://github.com/YuLab-SMU/tidydr +* Source code: https://github.com/cran/tidydr +* Date/Publication: 2023-03-08 09:20:02 UTC +* Number of recursive dependencies: 71 -Run `revdepcheck::cloud_details(, "rmsb")` for more info +Run `revdepcheck::cloud_details(, "tidydr")` for more info
-## In both +## Newly broken -* checking whether package ‘rmsb’ can be installed ... ERROR +* checking whether package ‘tidydr’ can be installed ... ERROR ``` Installation failed. - See ‘/tmp/workdir/rmsb/new/rmsb.Rcheck/00install.out’ for details. + See ‘/tmp/workdir/tidydr/new/tidydr.Rcheck/00install.out’ for details. ``` ## Installation @@ -629,51 +8142,61 @@ Run `revdepcheck::cloud_details(, "rmsb")` for more info ### Devel ``` -* installing *source* package ‘rmsb’ ... -** package ‘rmsb’ successfully unpacked and MD5 sums checked +* installing *source* package ‘tidydr’ ... +** package ‘tidydr’ successfully unpacked and MD5 sums checked ** using staged installation -Error in loadNamespace(x) : there is no package called ‘rstantools’ -Calls: loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +** R +** inst +** byte-compile and prepare package for lazy loading +Error in get(x, envir = ns, inherits = FALSE) : + object 'len0_null' not found +Error: unable to load R code in package ‘tidydr’ Execution halted -ERROR: configuration failed for package ‘rmsb’ -* removing ‘/tmp/workdir/rmsb/new/rmsb.Rcheck/rmsb’ +ERROR: lazy loading failed for package ‘tidydr’ +* removing ‘/tmp/workdir/tidydr/new/tidydr.Rcheck/tidydr’ ``` ### CRAN ``` -* installing *source* package ‘rmsb’ ... -** package ‘rmsb’ successfully unpacked and MD5 sums checked +* installing *source* package ‘tidydr’ ... +** package ‘tidydr’ successfully unpacked and MD5 sums checked ** using staged installation -Error in loadNamespace(x) : there is no package called ‘rstantools’ -Calls: loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart -Execution halted -ERROR: configuration failed for package ‘rmsb’ -* removing ‘/tmp/workdir/rmsb/old/rmsb.Rcheck/rmsb’ +** R +** inst +** byte-compile and prepare package for lazy loading +** help +*** installing help indices +** building package indices +** installing vignettes +** testing if installed package can be loaded from temporary location +** testing if installed package can be loaded from final location +** testing if installed package keeps a record of temporary installation path +* DONE (tidydr) ``` -# rstanarm +# tidyEdSurvey
-* Version: 2.32.1 -* GitHub: https://github.com/stan-dev/rstanarm -* Source code: https://github.com/cran/rstanarm -* Date/Publication: 2024-01-18 23:00:03 UTC -* Number of recursive dependencies: 138 +* Version: 0.1.2 +* GitHub: NA +* Source code: https://github.com/cran/tidyEdSurvey +* Date/Publication: 2023-06-19 15:00:02 UTC +* Number of recursive dependencies: 107 -Run `revdepcheck::cloud_details(, "rstanarm")` for more info +Run `revdepcheck::cloud_details(, "tidyEdSurvey")` for more info
## In both -* checking whether package ‘rstanarm’ can be installed ... ERROR +* checking whether package ‘tidyEdSurvey’ can be installed ... ERROR ``` Installation failed. - See ‘/tmp/workdir/rstanarm/new/rstanarm.Rcheck/00install.out’ for details. + See ‘/tmp/workdir/tidyEdSurvey/new/tidyEdSurvey.Rcheck/00install.out’ for details. ``` ## Installation @@ -681,202 +8204,158 @@ Run `revdepcheck::cloud_details(, "rstanarm")` for more info ### Devel ``` -* installing *source* package ‘rstanarm’ ... -** package ‘rstanarm’ successfully unpacked and MD5 sums checked +* installing *source* package ‘tidyEdSurvey’ ... +** package ‘tidyEdSurvey’ successfully unpacked and MD5 sums checked ** using staged installation -** libs -using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ -using C++17 -"/opt/R/4.3.1/lib/R/bin/Rscript" -e "source(file.path('..', 'tools', 'make_cc.R')); make_cc(commandArgs(TRUE))" stan_files/lm.stan -Wrote C++ file "stan_files/lm.cc" - - -... -/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src/stan/mcmc/hmc/hamiltonians/dense_e_metric.hpp:21:10: required from here -/opt/R/4.3.1/lib/R/site-library/RcppEigen/include/Eigen/src/Core/DenseCoeffsBase.h:654:34: warning: ignoring attributes on template argument ‘Eigen::internal::packet_traits::type’ {aka ‘__vector(2) double’} [-Wignored-attributes] - 654 | return internal::first_aligned::alignment),Derived>(m); - | ^~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -g++: fatal error: Killed signal terminated program cc1plus -compilation terminated. -make: *** [/opt/R/4.3.1/lib/R/etc/Makeconf:198: stan_files/mvmer.o] Error 1 -rm stan_files/lm.cc stan_files/mvmer.cc -ERROR: compilation failed for package ‘rstanarm’ -* removing ‘/tmp/workdir/rstanarm/new/rstanarm.Rcheck/rstanarm’ +** R +** byte-compile and prepare package for lazy loading +Error: package or namespace load failed for ‘EdSurvey’ in loadNamespace(i, c(lib.loc, .libPaths()), versionCheck = vI[[i]]): + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.1.1 is required +Execution halted +ERROR: lazy loading failed for package ‘tidyEdSurvey’ +* removing ‘/tmp/workdir/tidyEdSurvey/new/tidyEdSurvey.Rcheck/tidyEdSurvey’ ``` ### CRAN ``` -* installing *source* package ‘rstanarm’ ... -** package ‘rstanarm’ successfully unpacked and MD5 sums checked +* installing *source* package ‘tidyEdSurvey’ ... +** package ‘tidyEdSurvey’ successfully unpacked and MD5 sums checked ** using staged installation -** libs -using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ -using C++17 -"/opt/R/4.3.1/lib/R/bin/Rscript" -e "source(file.path('..', 'tools', 'make_cc.R')); make_cc(commandArgs(TRUE))" stan_files/lm.stan -Wrote C++ file "stan_files/lm.cc" - - -... -/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src/stan/mcmc/hmc/hamiltonians/dense_e_metric.hpp:21:10: required from here -/opt/R/4.3.1/lib/R/site-library/RcppEigen/include/Eigen/src/Core/DenseCoeffsBase.h:654:34: warning: ignoring attributes on template argument ‘Eigen::internal::packet_traits::type’ {aka ‘__vector(2) double’} [-Wignored-attributes] - 654 | return internal::first_aligned::alignment),Derived>(m); - | ^~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -g++: fatal error: Killed signal terminated program cc1plus -compilation terminated. -make: *** [/opt/R/4.3.1/lib/R/etc/Makeconf:198: stan_files/mvmer.o] Error 1 -rm stan_files/lm.cc stan_files/mvmer.cc -ERROR: compilation failed for package ‘rstanarm’ -* removing ‘/tmp/workdir/rstanarm/old/rstanarm.Rcheck/rstanarm’ +** R +** byte-compile and prepare package for lazy loading +Error: package or namespace load failed for ‘EdSurvey’ in loadNamespace(i, c(lib.loc, .libPaths()), versionCheck = vI[[i]]): + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.1.1 is required +Execution halted +ERROR: lazy loading failed for package ‘tidyEdSurvey’ +* removing ‘/tmp/workdir/tidyEdSurvey/old/tidyEdSurvey.Rcheck/tidyEdSurvey’ ``` -# Seurat +# tidyseurat
-* Version: 5.0.3 -* GitHub: https://github.com/satijalab/seurat -* Source code: https://github.com/cran/Seurat -* Date/Publication: 2024-03-18 23:40:02 UTC -* Number of recursive dependencies: 264 +* Version: 0.8.0 +* GitHub: https://github.com/stemangiola/tidyseurat +* Source code: https://github.com/cran/tidyseurat +* Date/Publication: 2024-01-10 04:50:02 UTC +* Number of recursive dependencies: 206 -Run `revdepcheck::cloud_details(, "Seurat")` for more info +Run `revdepcheck::cloud_details(, "tidyseurat")` for more info
-## Error before installation - -### Devel +## In both -``` -* using log directory ‘/tmp/workdir/Seurat/new/Seurat.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0 - GNU Fortran (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0 -* running under: Ubuntu 20.04.6 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘Seurat/DESCRIPTION’ ... OK -... -* checking for GNU extensions in Makefiles ... OK -* checking for portable use of $(BLAS_LIBS) and $(LAPACK_LIBS) ... OK -* checking use of PKG_*FLAGS in Makefiles ... OK -* checking compiled code ... OK -* checking examples ... OK -* checking for unstated dependencies in ‘tests’ ... OK -* checking tests ... OK - Running ‘testthat.R’ -* DONE -Status: 3 NOTEs +* checking whether package ‘tidyseurat’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/tidyseurat/new/tidyseurat.Rcheck/00install.out’ for details. + ``` +## Installation +### Devel +``` +* installing *source* package ‘tidyseurat’ ... +** package ‘tidyseurat’ 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: package or namespace load failed for ‘SeuratObject’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.3 is required +Execution halted +ERROR: lazy loading failed for package ‘tidyseurat’ +* removing ‘/tmp/workdir/tidyseurat/new/tidyseurat.Rcheck/tidyseurat’ ``` ### CRAN ``` -* using log directory ‘/tmp/workdir/Seurat/old/Seurat.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0 - GNU Fortran (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0 -* running under: Ubuntu 20.04.6 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘Seurat/DESCRIPTION’ ... OK -... -* checking for GNU extensions in Makefiles ... OK -* checking for portable use of $(BLAS_LIBS) and $(LAPACK_LIBS) ... OK -* checking use of PKG_*FLAGS in Makefiles ... OK -* checking compiled code ... OK -* checking examples ... OK -* checking for unstated dependencies in ‘tests’ ... OK -* checking tests ... OK - Running ‘testthat.R’ -* DONE -Status: 3 NOTEs - - - +* installing *source* package ‘tidyseurat’ ... +** package ‘tidyseurat’ 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: package or namespace load failed for ‘SeuratObject’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.3 is required +Execution halted +ERROR: lazy loading failed for package ‘tidyseurat’ +* removing ‘/tmp/workdir/tidyseurat/old/tidyseurat.Rcheck/tidyseurat’ ``` -# streamDAG +# tidyvpc
-* Version: 1.5 -* GitHub: NA -* Source code: https://github.com/cran/streamDAG -* Date/Publication: 2023-10-06 18:50:02 UTC -* Number of recursive dependencies: 133 +* Version: 1.5.1 +* GitHub: https://github.com/certara/tidyvpc +* Source code: https://github.com/cran/tidyvpc +* Date/Publication: 2024-01-18 13:10:02 UTC +* Number of recursive dependencies: 176 -Run `revdepcheck::cloud_details(, "streamDAG")` for more info +Run `revdepcheck::cloud_details(, "tidyvpc")` for more info
-## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/streamDAG/new/streamDAG.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0 - GNU Fortran (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0 -* running under: Ubuntu 20.04.6 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘streamDAG/DESCRIPTION’ ... OK -* this is package ‘streamDAG’ version ‘1.5’ -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘asbio’ +## In both -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR +* checking whether package ‘tidyvpc’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/tidyvpc/new/tidyvpc.Rcheck/00install.out’ for details. + ``` +## Installation +### Devel +``` +* installing *source* package ‘tidyvpc’ ... +** package ‘tidyvpc’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘tidyvpc’ +* removing ‘/tmp/workdir/tidyvpc/new/tidyvpc.Rcheck/tidyvpc’ ``` ### CRAN ``` -* using log directory ‘/tmp/workdir/streamDAG/old/streamDAG.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0 - GNU Fortran (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0 -* running under: Ubuntu 20.04.6 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘streamDAG/DESCRIPTION’ ... OK -* this is package ‘streamDAG’ version ‘1.5’ -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘asbio’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - +* installing *source* package ‘tidyvpc’ ... +** package ‘tidyvpc’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘tidyvpc’ +* removing ‘/tmp/workdir/tidyvpc/old/tidyvpc.Rcheck/tidyvpc’ ``` @@ -1027,6 +8506,158 @@ Error: C++20 standard requested but CXX20 is not defined * removing ‘/tmp/workdir/triptych/old/triptych.Rcheck/triptych’ +``` +# TSrepr + +
+ +* Version: 1.1.0 +* GitHub: https://github.com/PetoLau/TSrepr +* Source code: https://github.com/cran/TSrepr +* Date/Publication: 2020-07-13 06:50:15 UTC +* Number of recursive dependencies: 72 + +Run `revdepcheck::cloud_details(, "TSrepr")` for more info + +
+ +## In both + +* checking whether package ‘TSrepr’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/TSrepr/new/TSrepr.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘TSrepr’ ... +** package ‘TSrepr’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c FeatureClippingTrending.cpp -o FeatureClippingTrending.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c helpers.cpp -o helpers.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c measures.cpp -o measures.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c normalizations.cpp -o normalizations.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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘TSrepr’ +* removing ‘/tmp/workdir/TSrepr/new/TSrepr.Rcheck/TSrepr’ + + +``` +### CRAN + +``` +* installing *source* package ‘TSrepr’ ... +** package ‘TSrepr’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c FeatureClippingTrending.cpp -o FeatureClippingTrending.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c helpers.cpp -o helpers.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c measures.cpp -o measures.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c normalizations.cpp -o normalizations.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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘TSrepr’ +* removing ‘/tmp/workdir/TSrepr/old/TSrepr.Rcheck/TSrepr’ + + +``` +# twang + +
+ +* Version: 2.6 +* GitHub: NA +* Source code: https://github.com/cran/twang +* Date/Publication: 2023-12-06 00:30:02 UTC +* Number of recursive dependencies: 53 + +Run `revdepcheck::cloud_details(, "twang")` for more info + +
+ +## In both + +* checking whether package ‘twang’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/twang/new/twang.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘twang’ ... +** package ‘twang’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C compiler: ‘gcc (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ +gcc -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I/usr/local/include -fpic -g -O2 -c init.c -o init.o +gcc -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I/usr/local/include -fpic -g -O2 -c ks.c -o ks.o +gcc -shared -L/opt/R/4.3.1/lib/R/lib -L/usr/local/lib -o twang.so init.o ks.o -llapack -lblas -lgfortran -lm -lquadmath -L/opt/R/4.3.1/lib/R/lib -lR +installing to /tmp/workdir/twang/new/twang.Rcheck/00LOCK-twang/00new/twang/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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘twang’ +* removing ‘/tmp/workdir/twang/new/twang.Rcheck/twang’ + + +``` +### CRAN + +``` +* installing *source* package ‘twang’ ... +** package ‘twang’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C compiler: ‘gcc (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ +gcc -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I/usr/local/include -fpic -g -O2 -c init.c -o init.o +gcc -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I/usr/local/include -fpic -g -O2 -c ks.c -o ks.o +gcc -shared -L/opt/R/4.3.1/lib/R/lib -L/usr/local/lib -o twang.so init.o ks.o -llapack -lblas -lgfortran -lm -lquadmath -L/opt/R/4.3.1/lib/R/lib -lR +installing to /tmp/workdir/twang/old/twang.Rcheck/00LOCK-twang/00new/twang/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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘twang’ +* removing ‘/tmp/workdir/twang/old/twang.Rcheck/twang’ + + ``` # ubms @@ -1183,4 +8814,204 @@ ERROR: loading failed * removing ‘/tmp/workdir/valse/old/valse.Rcheck/valse’ +``` +# vdg + +
+ +* Version: 1.2.3 +* GitHub: NA +* Source code: https://github.com/cran/vdg +* Date/Publication: 2024-04-23 13:00:02 UTC +* Number of recursive dependencies: 45 + +Run `revdepcheck::cloud_details(, "vdg")` for more info + +
+ +## In both + +* checking whether package ‘vdg’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/vdg/new/vdg.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘vdg’ ... +** package ‘vdg’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using Fortran compiler: ‘GNU Fortran (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ +gfortran -fpic -g -O2 -c FDS.f -o FDS.o +gcc -shared -L/opt/R/4.3.1/lib/R/lib -L/usr/local/lib -o vdg.so FDS.o -lgfortran -lm -lquadmath -L/opt/R/4.3.1/lib/R/lib -lR +installing to /tmp/workdir/vdg/new/vdg.Rcheck/00LOCK-vdg/00new/vdg/libs +** R +** data +*** moving datasets to lazyload DB +** inst +** byte-compile and prepare package for lazy loading +Error: package or namespace load failed for ‘quantreg’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Execution halted +ERROR: lazy loading failed for package ‘vdg’ +* removing ‘/tmp/workdir/vdg/new/vdg.Rcheck/vdg’ + + +``` +### CRAN + +``` +* installing *source* package ‘vdg’ ... +** package ‘vdg’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using Fortran compiler: ‘GNU Fortran (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ +gfortran -fpic -g -O2 -c FDS.f -o FDS.o +gcc -shared -L/opt/R/4.3.1/lib/R/lib -L/usr/local/lib -o vdg.so FDS.o -lgfortran -lm -lquadmath -L/opt/R/4.3.1/lib/R/lib -lR +installing to /tmp/workdir/vdg/old/vdg.Rcheck/00LOCK-vdg/00new/vdg/libs +** R +** data +*** moving datasets to lazyload DB +** inst +** byte-compile and prepare package for lazy loading +Error: package or namespace load failed for ‘quantreg’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Execution halted +ERROR: lazy loading failed for package ‘vdg’ +* removing ‘/tmp/workdir/vdg/old/vdg.Rcheck/vdg’ + + +``` +# visa + +
+ +* Version: 0.1.0 +* GitHub: https://github.com/kang-yu/visa +* Source code: https://github.com/cran/visa +* Date/Publication: 2021-04-20 07:20:02 UTC +* Number of recursive dependencies: 141 + +Run `revdepcheck::cloud_details(, "visa")` for more info + +
+ +## In both + +* checking whether package ‘visa’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/visa/new/visa.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘visa’ ... +** package ‘visa’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘visa’ +* removing ‘/tmp/workdir/visa/new/visa.Rcheck/visa’ + + +``` +### CRAN + +``` +* installing *source* package ‘visa’ ... +** package ‘visa’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘visa’ +* removing ‘/tmp/workdir/visa/old/visa.Rcheck/visa’ + + +``` +# WRTDStidal + +
+ +* Version: 1.1.4 +* GitHub: https://github.com/fawda123/WRTDStidal +* Source code: https://github.com/cran/WRTDStidal +* Date/Publication: 2023-10-20 09:00:11 UTC +* Number of recursive dependencies: 140 + +Run `revdepcheck::cloud_details(, "WRTDStidal")` for more info + +
+ +## In both + +* checking whether package ‘WRTDStidal’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/WRTDStidal/new/WRTDStidal.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘WRTDStidal’ ... +** package ‘WRTDStidal’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘WRTDStidal’ +* removing ‘/tmp/workdir/WRTDStidal/new/WRTDStidal.Rcheck/WRTDStidal’ + + +``` +### CRAN + +``` +* installing *source* package ‘WRTDStidal’ ... +** package ‘WRTDStidal’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘WRTDStidal’ +* removing ‘/tmp/workdir/WRTDStidal/old/WRTDStidal.Rcheck/WRTDStidal’ + + ``` diff --git a/revdep/problems.md b/revdep/problems.md index 8151dae476..100afd3e3a 100644 --- a/revdep/problems.md +++ b/revdep/problems.md @@ -1,14 +1,10833 @@ +# actxps + +
+ +* Version: 1.4.0 +* GitHub: https://github.com/mattheaphy/actxps +* Source code: https://github.com/cran/actxps +* Date/Publication: 2023-11-26 16:10:02 UTC +* Number of recursive dependencies: 131 + +Run `revdepcheck::cloud_details(, "actxps")` for more info + +
+ +## Newly broken + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘actxps.Rmd’ + ... + # ℹ 2 more variables: ae_expected_1 , ae_expected_2 + + > autoplot(exp_res) + Warning: thematic was unable to resolve `bg='auto'`. Try providing an actual color (or `NA`) to the `bg` argument of `thematic_on()`. By the way, 'auto' is only officially supported in `shiny::renderPlot()`, some rmarkdown scenarios (specifically, `html_document()` with `theme!=NULL`), in RStudio, or if `auto_config_set()` is used. + Warning: thematic was unable to resolve `fg='auto'`. Try providing an actual color (or `NA`) to the `fg` argument of `thematic_on()`. By the way, 'auto' is only officially supported in `shiny::renderPlot()`, some rmarkdown scenarios (specifically, `html_document()` with `theme!=NULL`), in RStudio, or if `auto_config_set()` is used. + Warning: thematic was unable to resolve `accent='auto'`. Try providing an actual color (or `NA`) to the `accent` argument of `thematic_on()`. By the way, 'auto' is only officially supported in `shiny::renderPlot()`, some rmarkdown scenarios (specifically, `html_document()` with `theme!=NULL`), in RStudio, or if `auto_config_set()` is used. + + ... + + When sourcing ‘transactions.R’: + Error: Internal error: adjust_color() expects an input of length 1 + Execution halted + + ‘actxps.Rmd’ using ‘UTF-8’... failed + ‘exp_summary.Rmd’ using ‘UTF-8’... OK + ‘exposures.Rmd’ using ‘UTF-8’... OK + ‘misc.Rmd’ using ‘UTF-8’... failed + ‘transactions.Rmd’ using ‘UTF-8’... failed + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘actxps.Rmd’ using rmarkdown + Warning: thematic was unable to resolve `bg='auto'`. Try providing an actual color (or `NA`) to the `bg` argument of `thematic_on()`. By the way, 'auto' is only officially supported in `shiny::renderPlot()`, some rmarkdown scenarios (specifically, `html_document()` with `theme!=NULL`), in RStudio, or if `auto_config_set()` is used. + Warning: thematic was unable to resolve `fg='auto'`. Try providing an actual color (or `NA`) to the `fg` argument of `thematic_on()`. By the way, 'auto' is only officially supported in `shiny::renderPlot()`, some rmarkdown scenarios (specifically, `html_document()` with `theme!=NULL`), in RStudio, or if `auto_config_set()` is used. + Warning: thematic was unable to resolve `accent='auto'`. Try providing an actual color (or `NA`) to the `accent` argument of `thematic_on()`. By the way, 'auto' is only officially supported in `shiny::renderPlot()`, some rmarkdown scenarios (specifically, `html_document()` with `theme!=NULL`), in RStudio, or if `auto_config_set()` is used. + + Quitting from lines at lines 131-132 [plot] (actxps.Rmd) + Error: processing vignette 'actxps.Rmd' failed with diagnostics: + Internal error: adjust_color() expects an input of length 1 + --- failed re-building ‘actxps.Rmd’ + ... + Quitting from lines at lines 205-211 [trx-plot] (transactions.Rmd) + Error: processing vignette 'transactions.Rmd' failed with diagnostics: + Internal error: adjust_color() expects an input of length 1 + --- failed re-building ‘transactions.Rmd’ + + SUMMARY: processing the following files failed: + ‘actxps.Rmd’ ‘misc.Rmd’ ‘transactions.Rmd’ + + Error: Vignette re-building failed. + Execution halted + ``` + +# AeRobiology + +
+ +* Version: 2.0.1 +* GitHub: NA +* Source code: https://github.com/cran/AeRobiology +* Date/Publication: 2019-06-03 06:20:03 UTC +* Number of recursive dependencies: 98 + +Run `revdepcheck::cloud_details(, "AeRobiology")` for more info + +
+ +## Newly broken + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘my-vignette.Rmd’ using rmarkdown + ``` + +## In both + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘my-vignette.Rmd’ + ... + + export.plot = FALSE, export.result = FALSE, n.types = 3, + + y.start = 2011, y.end = .... [TRUNCATED] + + > iplot_abundance(munich_pollen, interpolation = FALSE, + + export.plot = FALSE, export.result = FALSE, n.types = 3, + + y.start = 2011, y.end = .... [TRUNCATED] + + When sourcing ‘my-vignette.R’: + Error: argument "theme" is missing, with no default + Execution halted + + ‘my-vignette.Rmd’ using ‘UTF-8’... failed + ``` + +# afex + +
+ +* Version: 1.3-1 +* GitHub: https://github.com/singmann/afex +* Source code: https://github.com/cran/afex +* Date/Publication: 2024-02-25 14:40:02 UTC +* Number of recursive dependencies: 227 + +Run `revdepcheck::cloud_details(, "afex")` for more info + +
+ +## Newly broken + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘afex_plot_supported_models.Rmd’ + ... + + > grid::grid.draw(b34) + + When sourcing ‘afex_plot_supported_models.R’: + Error: Problem while setting up geom aesthetics. + ℹ Error occurred in the 1st layer. + Caused by error in `compute_geom_2()`: + ... + 14, NULL, NULL, list(), 15.4, NULL, NULL, 7, NULL, NULL, NULL, NULL, 0.2, NULL, list(NULL, NULL, NULL, 0.857142857142857, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, NULL, NULL, NULL, TRUE), NULL, "none", NULL, NULL, NULL, "center", NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, c(0, 0, 0, 0), list(), 14, li + Execution halted + + ‘afex_analysing_accuracy_data.Rmd’ using ‘UTF-8’... OK + ‘afex_anova_example.Rmd’ using ‘UTF-8’... OK + ‘afex_mixed_example.Rmd’ using ‘UTF-8’... OK + ‘afex_plot_introduction.Rmd’ using ‘UTF-8’... OK + ‘afex_plot_supported_models.Rmd’ using ‘UTF-8’... failed + ‘assumptions_of_ANOVAs.Rmd’ using ‘UTF-8’... OK + ‘introduction-mixed-models.pdf.asis’ using ‘UTF-8’... OK + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘afex_analysing_accuracy_data.Rmd’ using rmarkdown + ``` + +# agricolaeplotr + +
+ +* Version: 0.5.0 +* GitHub: https://github.com/jensharbers/agricolaeplotr +* Source code: https://github.com/cran/agricolaeplotr +* Date/Publication: 2024-01-17 16:42:04 UTC +* Number of recursive dependencies: 144 + +Run `revdepcheck::cloud_details(, "agricolaeplotr")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘agricolaeplotr-Ex.R’ failed + The error most likely occurred in: + + > ### Name: sample_locations + > ### Title: Sample Locations + > ### Aliases: sample_locations + > + > ### ** Examples + > + > library(agricolaeplotr) + ... + 16. └─ggplot2 (local) FUN(X[[i]], ...) + 17. └─base::lapply(...) + 18. └─ggplot2 (local) FUN(X[[i]], ...) + 19. └─g$draw_key(data, g$params, key_size) + 20. └─ggplot2 (local) draw_key(...) + 21. └─ggplot2::draw_key_polygon(data, params, size) + 22. └─rlang:::Summary.quosure(from_theme(thin), 1.524, na.rm = FALSE) + 23. └─rlang:::abort_quosure_op("Summary", .Generic) + 24. └─rlang::abort(...) + Execution halted + ``` + +# ammistability + +
+ +* Version: 0.1.4 +* GitHub: https://github.com/ajaygpb/ammistability +* Source code: https://github.com/cran/ammistability +* Date/Publication: 2023-05-24 07:40:08 UTC +* Number of recursive dependencies: 70 + +Run `revdepcheck::cloud_details(, "ammistability")` for more info + +
+ +## Newly broken + +* checking re-building of vignette outputs ... ERROR + ``` + Error(s) in re-building vignettes: + ... + --- re-building ‘Introduction.Rmd’ using rmarkdown_notangle + ! Undefined control sequence. + l.108 \NewDocumentCommand + \citeproctext{}{} + + Error: processing vignette 'Introduction.Rmd' failed with diagnostics: + LaTeX failed to compile /tmp/workdir/ammistability/new/ammistability.Rcheck/vign_test/ammistability/vignettes/Introduction.tex. See https://yihui.org/tinytex/r/#debugging for debugging tips. See Introduction.log for more info. + --- failed re-building ‘Introduction.Rmd’ + + SUMMARY: processing the following file failed: + ‘Introduction.Rmd’ + + Error: Vignette re-building failed. + Execution halted + ``` + +## Newly fixed + +* checking re-building of vignette outputs ... WARNING + ``` + Error(s) in re-building vignettes: + --- re-building ‘Introduction.Rmd’ using rmarkdown_notangle + Trying to upgrade TinyTeX automatically now... + If reinstallation fails, try install_tinytex() again. Then install the following packages: + + tinytex::tlmgr_install(c("amscls", "amsfonts", "amsmath", "atbegshi", "atveryend", "auxhook", "babel", "bibtex", "bigintcalc", "bitset", "booktabs", "cm", "ctablestack", "dehyph", "dvipdfmx", "dvips", "ec", "epstopdf-pkg", "etex", "etexcmds", "etoolbox", "euenc", "everyshi", "fancyvrb", "filehook", "firstaid", "float", "fontspec", "framed", "geometry", "gettitlestring", "glyphlist", "graphics", "graphics-cfg", "graphics-def", "helvetic", "hycolor", "hyperref", "hyph-utf8", "hyphen-base", "iftex", "inconsolata", "infwarerr", "intcalc", "knuth-lib", "kpathsea", "kvdefinekeys", "kvoptions", "kvsetkeys", "l3backend", "l3kernel", "l3packages", "latex", "latex-amsmath-dev", "latex-bin", "latex-fonts", "latex-tools-dev", "latexconfig", "latexmk", "letltxmacro", "lm", "lm-math", "ltxcmds", "lua-alt-getopt", "lua-uni-algos", "luahbtex", "lualatex-math", "lualibs", "luaotfload", "luatex", "luatexbase", "mdwtools", "metafont", "mfware", "modes", "natbib", "pdfescape", "pdftex", "pdftexcmds", "plain", "psnfss", "refcount", "rerunfilecheck", "scheme-infraonly", "selnolig", "stringenc", "symbol", "tex", "tex-ini-files", "texlive-scripts", "texlive.infra", "times", "tipa", "tools", "unicode-data", "unicode-math", "uniquecounter", "url", "xcolor", "xetex", "xetexconfig", "xkeyval", "xunicode", "zapfding")) + + The directory /opt/TinyTeX/texmf-local is not empty. It will be backed up to /tmp/RtmpCfJ2Ma/filed896b38a178 and restored later. + + tlmgr: no auxiliary texmf trees defined, so nothing removed + ... + + Error: processing vignette 'Introduction.Rmd' failed with diagnostics: + LaTeX failed to compile /tmp/workdir/ammistability/old/ammistability.Rcheck/vign_test/ammistability/vignettes/Introduction.tex. See https://yihui.org/tinytex/r/#debugging for debugging tips. See Introduction.log for more info. + --- failed re-building ‘Introduction.Rmd’ + + SUMMARY: processing the following file failed: + ‘Introduction.Rmd’ + + Error: Vignette re-building failed. + Execution halted + ``` + +# AnalysisLin + +
+ +* Version: 0.1.2 +* GitHub: NA +* Source code: https://github.com/cran/AnalysisLin +* Date/Publication: 2024-01-30 00:10:10 UTC +* Number of recursive dependencies: 120 + +Run `revdepcheck::cloud_details(, "AnalysisLin")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘AnalysisLin-Ex.R’ failed + The error most likely occurred in: + + > ### Name: bar_plot + > ### Title: Bar Plots for Categorical Variables + > ### Aliases: bar_plot + > + > ### ** Examples + > + > data(iris) + > bar_plot(iris) + Error in compute_geom_2(..., self = self) : + argument "theme" is missing, with no default + Calls: bar_plot ... use_defaults -> eval_from_theme -> %||% -> calc_element + Execution halted + ``` + +# animbook + +
+ +* Version: 1.0.0 +* GitHub: https://github.com/KrisanatA/animbook +* Source code: https://github.com/cran/animbook +* Date/Publication: 2023-12-05 17:50:07 UTC +* Number of recursive dependencies: 88 + +Run `revdepcheck::cloud_details(, "animbook")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘animbook-Ex.R’ failed + The error most likely occurred in: + + > ### Name: anim_animate + > ### Title: Modified the ggplot object + > ### Aliases: anim_animate + > + > ### ** Examples + > + > animbook <- anim_prep(data = osiris, id = ID, values = sales, time = year, group = japan) + ... + > + > animate <- anim_animate(plot) + You can now pass it to gganimate::animate(). + The recommended setting is nframes = 89 + > + > plotly::ggplotly(animate) + Error in compute_geom_2(..., self = self) : + argument "theme" is missing, with no default + Calls: ... use_defaults -> eval_from_theme -> %||% -> calc_element + Execution halted + ``` + +# aopdata + +
+ +* Version: 1.0.3 +* GitHub: https://github.com/ipeaGIT/aopdata +* Source code: https://github.com/cran/aopdata +* Date/Publication: 2023-08-31 07:20:02 UTC +* Number of recursive dependencies: 88 + +Run `revdepcheck::cloud_details(, "aopdata")` for more info + +
+ +## Newly broken + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘landuse_maps.Rmd’ + ... + + direction = 1 .... [TRUNCATED] + + When sourcing ‘landuse_maps.R’: + Error: Summary operations are not defined for quosures. Do you need to unquote + the quosure? + + # Bad: min(myquosure) + ... + # Good: min(!!myquosure) + Execution halted + + ‘access_inequality.Rmd’ using ‘UTF-8’... OK + ‘access_maps.Rmd’ using ‘UTF-8’... OK + ‘data_dic_en.Rmd’ using ‘UTF-8’... OK + ‘data_dic_pt.Rmd’ using ‘UTF-8’... OK + ‘intro_to_aopdata.Rmd’ using ‘UTF-8’... OK + ‘landuse_maps.Rmd’ using ‘UTF-8’... failed + ‘population_maps.Rmd’ using ‘UTF-8’... failed + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘access_inequality.Rmd’ using rmarkdown + ``` + +# ARPALData + +
+ +* Version: 1.5.2 +* GitHub: NA +* Source code: https://github.com/cran/ARPALData +* Date/Publication: 2024-03-17 00:00:05 UTC +* Number of recursive dependencies: 141 + +Run `revdepcheck::cloud_details(, "ARPALData")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘ARPALData-Ex.R’ failed + The error most likely occurred in: + + > ### Name: get_ARPA_Lombardia_zoning + > ### Title: Download ARPA Lombardia zoning geometries + > ### Aliases: get_ARPA_Lombardia_zoning + > + > ### ** Examples + > + > zones <- get_ARPA_Lombardia_zoning(plot_map = TRUE) + ... + 16. └─ggplot2 (local) FUN(X[[i]], ...) + 17. └─base::lapply(...) + 18. └─ggplot2 (local) FUN(X[[i]], ...) + 19. └─g$draw_key(data, g$params, key_size) + 20. └─ggplot2 (local) draw_key(...) + 21. └─ggplot2::draw_key_polygon(data, params, size) + 22. └─rlang:::Summary.quosure(from_theme(thin), 1.524, na.rm = FALSE) + 23. └─rlang:::abort_quosure_op("Summary", .Generic) + 24. └─rlang::abort(...) + Execution halted + ``` + +# asmbPLS + +
+ +* Version: 1.0.0 +* GitHub: NA +* Source code: https://github.com/cran/asmbPLS +* Date/Publication: 2023-04-17 09:50:05 UTC +* Number of recursive dependencies: 100 + +Run `revdepcheck::cloud_details(, "asmbPLS")` for more info + +
+ +## Newly broken + +* checking whether package ‘asmbPLS’ can be installed ... WARNING + ``` + Found the following significant warnings: + Warning: replacing previous import ‘ggplot2::ggpar’ by ‘ggpubr::ggpar’ when loading ‘asmbPLS’ + See ‘/tmp/workdir/asmbPLS/new/asmbPLS.Rcheck/00install.out’ for details. + ``` + +## In both + +* checking installed package size ... NOTE + ``` + installed size is 37.6Mb + sub-directories of 1Mb or more: + data 2.1Mb + libs 34.4Mb + ``` + +# autoplotly + +
+ +* Version: 0.1.4 +* GitHub: https://github.com/terrytangyuan/autoplotly +* Source code: https://github.com/cran/autoplotly +* Date/Publication: 2021-04-18 06:50:11 UTC +* Number of recursive dependencies: 88 + +Run `revdepcheck::cloud_details(, "autoplotly")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘autoplotly-Ex.R’ failed + The error most likely occurred in: + + > ### Name: autoplotly + > ### Title: Automatic Visualization of Popular Statistical Results Using + > ### 'plotly.js' and 'ggplot2' + > ### Aliases: autoplotly + > + > ### ** Examples + > + > # Automatically generate interactive plot for results produced by `stats::prcomp` + > p <- autoplotly(prcomp(iris[c(1, 2, 3, 4)]), data = iris, + + colour = 'Species', label = TRUE, label.size = 3, frame = TRUE) + Error in compute_geom_2(..., self = self) : + argument "theme" is missing, with no default + Calls: autoplotly ... use_defaults -> eval_from_theme -> %||% -> calc_element + Execution halted + ``` + +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(autoplotly) + > + > test_check("autoplotly") + [ FAIL 3 | WARN 0 | SKIP 0 | PASS 1 ] + + ══ Failed tests ════════════════════════════════════════════════════════════════ + ... + 10. └─ggplot2 (local) compute_geom_2(..., self = self) + 11. └─self$geom$use_defaults(data, self$aes_params, modifiers, theme = theme) + 12. └─ggplot2 (local) use_defaults(..., self = self) + 13. └─ggplot2:::eval_from_theme(default_aes, theme) + 14. ├─calc_element("geom", theme) %||% .default_geom_element + 15. └─ggplot2::calc_element("geom", theme) + + [ FAIL 3 | WARN 0 | SKIP 0 | PASS 1 ] + Error: Test failures + Execution halted + ``` + +# BayesGrowth + +
+ +* Version: 1.0.0 +* GitHub: https://github.com/jonathansmart/BayesGrowth +* Source code: https://github.com/cran/BayesGrowth +* Date/Publication: 2023-11-21 18:10:08 UTC +* Number of recursive dependencies: 110 + +Run `revdepcheck::cloud_details(, "BayesGrowth")` for more info + +
+ +## Newly broken + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘MCMC-example.Rmd’ + ... + 2.75, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 1, NULL, NULL, NULL, c(0, 2.2, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, NULL, c(0, 0, 0, 2.2 + ), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0.5, NULL, NULL, NULL, c(0, 2.2, 0, 2.2), NULL, TRUE), list("grey20", NULL, NULL, NULL, FALSE, TRUE), NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 2.75, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 0.75, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, list(), NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, list(NULL, NA, NULL, NULL, TRUE), c(5.5, 5.5, 5.5, 5.5), 11, NULL, NULL, NULL, 1.2, NULL, NULL, 5.5, + NULL, NULL, NULL, NULL, 0.2, NULL, list(NULL, NULL, NULL, 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, NULL, NULL, NULL, TRUE), NULL, "right", NULL, NULL, NULL, "center", NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, c(0, 0, 0, 0), list(), 11, list("white", NA, NULL, NULL, TRUE), list(NA, "grey20", NULL, NULL, TRUE), 5.5, NULL, NULL, list("grey92", NULL, NULL, NULL, FALSE, TRUE), NULL, list(NULL, 0.5, NULL, NULL, FALSE, TRUE), NULL, NULL, + NULL, NULL, FALSE, list(NULL, "white", NULL, NULL, TRUE), list(NULL, NULL, NULL, 1.2, 0, 1, NULL, NULL, c(0, 0, 5.5, 0), NULL, TRUE), "panel", list(NULL, NULL, NULL, NULL, 0, 1, NULL, NULL, c(0, 0, 5.5, 0), NULL, TRUE), list(NULL, NULL, NULL, 0.8, 1, 1, NULL, NULL, c(5.5, 0, 0, 0), NULL, TRUE), "panel", list(NULL, NULL, NULL, 1.2, 0.5, 0.5, NULL, NULL, NULL, NULL, TRUE), "topleft", NULL, c(5.5, 5.5, 5.5, 5.5), list("grey85", "grey20", NULL, NULL, TRUE), NULL, NULL, "inherit", "inside", list(NULL, + NULL, "grey10", 0.8, NULL, NULL, NULL, NULL, c(4.4, 4.4, 4.4, 4.4), NULL, TRUE), NULL, NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, NULL, -90, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, NULL, 90, NULL, NULL, NULL, TRUE), NULL, 2.75, 2.75)) + + When sourcing ‘MCMC-example.R’: + Error: unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 14, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, FALSE), NULL, list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.75, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, 90, NULL, c(0, + 2.75, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 1, NULL, NULL, NULL, c(0, 2.2, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, + Execution halted + + ‘MCMC-example.Rmd’ using ‘UTF-8’... failed + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘MCMC-example.Rmd’ using rmarkdown + ``` + +## In both + +* checking installed package size ... NOTE + ``` + installed size is 109.3Mb + sub-directories of 1Mb or more: + libs 107.7Mb + ``` + +* checking for GNU extensions in Makefiles ... NOTE + ``` + GNU make is a SystemRequirements. + ``` + +# bdl + +
+ +* Version: 1.0.5 +* GitHub: https://github.com/statisticspoland/R_Package_to_API_BDL +* Source code: https://github.com/cran/bdl +* Date/Publication: 2023-02-24 15:00:02 UTC +* Number of recursive dependencies: 144 + +Run `revdepcheck::cloud_details(, "bdl")` for more info + +
+ +## Newly broken + +* checking whether package ‘bdl’ can be installed ... WARNING + ``` + Found the following significant warnings: + Warning: replacing previous import ‘ggplot2::ggpar’ by ‘ggpubr::ggpar’ when loading ‘bdl’ + See ‘/tmp/workdir/bdl/new/bdl.Rcheck/00install.out’ for details. + ``` + +# BeeBDC + +
+ +* Version: 1.1.1 +* GitHub: https://github.com/jbdorey/BeeBDC +* Source code: https://github.com/cran/BeeBDC +* Date/Publication: 2024-04-03 23:53:03 UTC +* Number of recursive dependencies: 219 + +Run `revdepcheck::cloud_details(, "BeeBDC")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘BeeBDC-Ex.R’ failed + The error most likely occurred in: + + > ### Name: summaryMaps + > ### Title: Create country-level summary maps of species and occurrence + > ### numbers + > ### Aliases: summaryMaps + > + > ### ** Examples + > + ... + 23. └─ggplot2 (local) FUN(X[[i]], ...) + 24. └─base::lapply(...) + 25. └─ggplot2 (local) FUN(X[[i]], ...) + 26. └─g$draw_key(data, g$params, key_size) + 27. └─ggplot2 (local) draw_key(...) + 28. └─ggplot2::draw_key_polygon(data, params, size) + 29. └─rlang:::Summary.quosure(from_theme(thin), 1.524, na.rm = FALSE) + 30. └─rlang:::abort_quosure_op("Summary", .Generic) + 31. └─rlang::abort(...) + Execution halted + ``` + +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > # This file is part of the standard setup for testthat. + > # It is recommended that you do not modify it. + > # + > # Where should you do additional test configuration? + > # Learn more about the roles of various files in: + > # * https://r-pkgs.org/tests.html + > # * https://testthat.r-lib.org/reference/test_package.html#special-files + ... + 28. └─ggplot2::draw_key_polygon(data, params, size) + 29. └─rlang:::Summary.quosure(from_theme(thin), 1.524, na.rm = FALSE) + 30. └─rlang:::abort_quosure_op("Summary", .Generic) + 31. └─rlang::abort(...) + + [ FAIL 1 | WARN 4 | SKIP 0 | PASS 241 ] + Error: Test failures + Execution halted + Warning message: + Connection is garbage-collected, use dbDisconnect() to avoid this. + ``` + +## In both + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘BeeBDC_main.Rmd’ + ... + + > rm(testChecklist) + + > check_space <- BeeBDC::countryOutlieRs(checklist = checklistFile, + + data = check_space, keepAdjacentCountry = TRUE, pointBuffer = 0.05, + + .... [TRUNCATED] + + ... + Error: Summary operations are not defined for quosures. Do you need to unquote + the quosure? + + # Bad: min(myquosure) + + # Good: min(!!myquosure) + Execution halted + + ‘BeeBDC_main.Rmd’ using ‘UTF-8’... failed + ‘basic_workflow.Rmd’ using ‘UTF-8’... failed + ``` + +* checking data for non-ASCII characters ... NOTE + ``` + Note: found 107 marked UTF-8 strings + ``` + +# blockCV + +
+ +* Version: 3.1-3 +* GitHub: https://github.com/rvalavi/blockCV +* Source code: https://github.com/cran/blockCV +* Date/Publication: 2023-06-04 13:20:02 UTC +* Number of recursive dependencies: 139 + +Run `revdepcheck::cloud_details(, "blockCV")` for more info + +
+ +## Newly broken + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘tutorial_1.Rmd’ using rmarkdown + ``` + +## In both + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘tutorial_1.Rmd’ + ... + > cv_plot(cv = scv, x = pa_data) + + When sourcing ‘tutorial_1.R’: + Error: Base operators are not defined for quosures. Do you need to unquote the + quosure? + + # Bad: myquosure * rhs + ... + Error: Base operators are not defined for quosures. Do you need to unquote the + quosure? + + # Bad: myquosure * rhs + + # Good: !!myquosure * rhs + Execution halted + + ‘tutorial_1.Rmd’ using ‘UTF-8’... failed + ‘tutorial_2.Rmd’ using ‘UTF-8’... failed + ``` + +* checking Rd cross-references ... WARNING + ``` + Missing link or links in documentation object 'cv_spatial.Rd': + ‘[biomod2]{BIOMOD_cv}’ + + See section 'Cross-references' in the 'Writing R Extensions' manual. + ``` + +* checking installed package size ... NOTE + ``` + installed size is 5.5Mb + sub-directories of 1Mb or more: + doc 1.9Mb + extdata 1.9Mb + libs 1.4Mb + ``` + +# boxly + +
+ +* Version: 0.1.1 +* GitHub: https://github.com/Merck/boxly +* Source code: https://github.com/cran/boxly +* Date/Publication: 2023-10-24 02:40:02 UTC +* Number of recursive dependencies: 91 + +Run `revdepcheck::cloud_details(, "boxly")` for more info + +
+ +## Newly broken + +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > # This file is part of the standard setup for testthat. + > # It is recommended that you do not modify it. + > # + > # Where should you do additional test configuration? + > # Learn more about the roles of various files in: + > # * https://r-pkgs.org/tests.html + > # * https://testthat.r-lib.org/reference/test_package.html#special-files + ... + 26. └─ggplot2 (local) compute_geom_2(..., self = self) + 27. └─self$geom$use_defaults(data, self$aes_params, modifiers, theme = theme) + 28. └─ggplot2 (local) use_defaults(..., self = self) + 29. └─ggplot2:::eval_from_theme(default_aes, theme) + 30. ├─calc_element("geom", theme) %||% .default_geom_element + 31. └─ggplot2::calc_element("geom", theme) + + [ FAIL 2 | WARN 0 | SKIP 0 | PASS 25 ] + Error: Test failures + Execution halted + ``` + +# bSi + +
+ +* Version: 1.0.0 +* GitHub: NA +* Source code: https://github.com/cran/bSi +* Date/Publication: 2024-01-24 15:52:57 UTC +* Number of recursive dependencies: 99 + +Run `revdepcheck::cloud_details(, "bSi")` for more info + +
+ +## Newly broken + +* checking whether package ‘bSi’ can be installed ... WARNING + ``` + Found the following significant warnings: + Warning: replacing previous import ‘ggplot2::ggpar’ by ‘ggpubr::ggpar’ when loading ‘bSi’ + See ‘/tmp/workdir/bSi/new/bSi.Rcheck/00install.out’ for details. + ``` + +# cartograflow + +
+ +* Version: 1.0.5 +* GitHub: https://github.com/fbahoken/cartogRaflow +* Source code: https://github.com/cran/cartograflow +* Date/Publication: 2023-10-17 22:40:21 UTC +* Number of recursive dependencies: 102 + +Run `revdepcheck::cloud_details(, "cartograflow")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘cartograflow-Ex.R’ failed + The error most likely occurred in: + + > ### Name: flowgini + > ### Title: Analysis of flow concentration (Gini coefficient) + > ### Aliases: flowgini + > + > ### ** Examples + > + > library(cartograflow) + ... + Warning: Use of `x$linkcum` is discouraged. + ℹ Use `linkcum` instead. + Warning: Use of `x$flowcum` is discouraged. + ℹ Use `flowcum` instead. + Warning: Use of `x$flowcum` is discouraged. + ℹ Use `flowcum` instead. + Error in compute_geom_2(..., self = self) : + argument "theme" is missing, with no default + Calls: flowgini ... use_defaults -> eval_from_theme -> %||% -> calc_element + Execution halted + ``` + +# cats + +
+ +* Version: 1.0.2 +* GitHub: NA +* Source code: https://github.com/cran/cats +* Date/Publication: 2022-03-11 10:20:07 UTC +* Number of recursive dependencies: 83 + +Run `revdepcheck::cloud_details(, "cats")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘cats-Ex.R’ failed + The error most likely occurred in: + + > ### Name: trial_ocs + > ### Title: Calculates the operating characteristics of the cohort trial + > ### Aliases: trial_ocs + > + > ### ** Examples + > + > + ... + + cohort_offset = cohort_offset, sr_first_pos = sr_first_pos, + + missing_prob = missing_prob, cohort_fixed = cohort_fixed, accrual_type = accrual_type, + + accrual_param = accrual_param, hist_lag = hist_lag, analysis_times = analysis_times, + + time_trend = time_trend, cohorts_start = cohorts_start, cohorts_sim = cohorts_sim, + + iter = 2, coresnum = 1, save = FALSE, ret_list = TRUE, plot_ocs = TRUE + + ) + Error in compute_geom_2(..., self = self) : + argument "theme" is missing, with no default + Calls: trial_ocs ... use_defaults -> eval_from_theme -> %||% -> calc_element + Execution halted + ``` + +## In both + +* checking dependencies in R code ... NOTE + ``` + Namespaces in Imports field not imported from: + ‘epitools’ ‘forcats’ ‘purrr’ + All declared Imports should be used. + ``` + +# cheem + +
+ +* Version: 0.4.0.0 +* GitHub: https://github.com/nspyrison/cheem +* Source code: https://github.com/cran/cheem +* Date/Publication: 2023-11-08 21:30:02 UTC +* Number of recursive dependencies: 152 + +Run `revdepcheck::cloud_details(, "cheem")` for more info + +
+ +## Newly broken + +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(cheem) + -------------------------------------------------------- + cheem --- version 0.4.0.0 + Please share bugs, suggestions, and feature requests at: + https://github.com/nspyrison/cheem/issues/ + -------------------------------------------------------- + ... + 23. └─ggplot2 (local) compute_geom_2(..., self = self) + 24. └─self$geom$use_defaults(data, self$aes_params, modifiers, theme = theme) + 25. └─ggplot2 (local) use_defaults(..., self = self) + 26. └─ggplot2:::eval_from_theme(default_aes, theme) + 27. ├─calc_element("geom", theme) %||% .default_geom_element + 28. └─ggplot2::calc_element("geom", theme) + + [ FAIL 1 | WARN 0 | SKIP 0 | PASS 10 ] + Error: Test failures + Execution halted + ``` + +## In both + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘getting-started-with-cheem.Rmd’ + ... + + > knitr::opts_chunk$set(echo = TRUE, include = TRUE, + + results = "show", eval = FALSE, message = FALSE, warning = FALSE, + + error = FALSE, co .... [TRUNCATED] + + > knitr::include_graphics("../inst/shiny_apps/cheem/www/lime_nonlinear.png") + + When sourcing ‘getting-started-with-cheem.R’: + Error: Cannot find the file(s): "../inst/shiny_apps/cheem/www/lime_nonlinear.png" + Execution halted + + ‘getting-started-with-cheem.Rmd’ using ‘UTF-8’... failed + ``` + +# chronicle + +
+ +* Version: 0.3 +* GitHub: NA +* Source code: https://github.com/cran/chronicle +* Date/Publication: 2021-06-25 05:00:02 UTC +* Number of recursive dependencies: 146 + +Run `revdepcheck::cloud_details(, "chronicle")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘chronicle-Ex.R’ failed + The error most likely occurred in: + + > ### Name: make_barplot + > ### Title: Create a bar plot from a data frame through ggplotly + > ### Aliases: make_barplot + > + > ### ** Examples + > + > make_barplot(dt = iris, bars = 'Species', value = 'Sepal.Length') + Error in compute_geom_2(..., self = self) : + argument "theme" is missing, with no default + Calls: make_barplot ... use_defaults -> eval_from_theme -> %||% -> calc_element + Execution halted + ``` + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘chronicle.Rmd’ + ... + + filename = "quick_demo", title = "A quick chronicle demo", + + author = .... [TRUNCATED] + + Quitting from lines at lines 34-46 [unnamed-chunk-3] (quick_demo.Rmd) + + When sourcing ‘chronicle.R’: + Error: ℹ In index: 1. + Caused by error in `compute_geom_2()`: + ! argument "theme" is missing, with no default + Execution halted + + ‘chronicle.Rmd’ using ‘UTF-8’... failed + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + ... + --- re-building ‘chronicle.Rmd’ using rmarkdown + + Quitting from lines at lines 34-46 [unnamed-chunk-3] (quick_demo.Rmd) + Error: processing vignette 'chronicle.Rmd' failed with diagnostics: + ℹ In index: 1. + Caused by error in `compute_geom_2()`: + ! argument "theme" is missing, with no default + --- failed re-building ‘chronicle.Rmd’ + + SUMMARY: processing the following file failed: + ‘chronicle.Rmd’ + + Error: Vignette re-building failed. + Execution halted + ``` + +## In both + +* checking dependencies in R code ... NOTE + ``` + Namespaces in Imports field not imported from: + ‘DT’ ‘dplyr’ ‘prettydoc’ ‘rmdformats’ ‘skimr’ + All declared Imports should be used. + ``` + +# clinDataReview + +
+ +* Version: 1.5.1 +* GitHub: https://github.com/openanalytics/clinDataReview +* Source code: https://github.com/cran/clinDataReview +* Date/Publication: 2024-04-24 20:10:03 UTC +* Number of recursive dependencies: 130 + +Run `revdepcheck::cloud_details(, "clinDataReview")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘clinDataReview-Ex.R’ failed + The error most likely occurred in: + + > ### Name: scatterplotClinData + > ### Title: Scatterplot of variables of interest for clinical data + > ### visualization. + > ### Aliases: scatterplotClinData + > + > ### ** Examples + > + ... + + xVar = "ADY", + + yVar = "LBSTRESN", + + aesPointVar = list(color = "TRTP", fill = "TRTP"), + + aesLineVar = list(group = "USUBJID", color = "TRTP"), + + labelVars = labelVars + + ) + Error in compute_geom_2(..., self = self) : + argument "theme" is missing, with no default + Calls: scatterplotClinData ... use_defaults -> eval_from_theme -> %||% -> calc_element + Execution halted + ``` + +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(clinDataReview) + > + > test_check("clinDataReview") + adding: report.html (deflated 63%) + adding: report_dependencies1dcd775cc9bd/ (stored 0%) + adding: report_dependencies1dcd775cc9bd/file1dcd27c26d11.html (deflated 8%) + ... + 9. └─ggplot2 (local) compute_geom_2(..., self = self) + 10. └─self$geom$use_defaults(data, self$aes_params, modifiers, theme = theme) + 11. └─ggplot2 (local) use_defaults(..., self = self) + 12. └─ggplot2:::eval_from_theme(default_aes, theme) + 13. ├─calc_element("geom", theme) %||% .default_geom_element + 14. └─ggplot2::calc_element("geom", theme) + + [ FAIL 23 | WARN 8 | SKIP 30 | PASS 450 ] + Error: Test failures + Execution halted + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + ... + --- re-building ‘clinDataReview-dataPreprocessing.Rmd’ using rmarkdown + --- finished re-building ‘clinDataReview-dataPreprocessing.Rmd’ + + --- re-building ‘clinDataReview-dataVisualization.Rmd’ using rmarkdown + + Quitting from lines at lines 167-208 [timeProfiles] (clinDataReview-dataVisualization.Rmd) + Error: processing vignette 'clinDataReview-dataVisualization.Rmd' failed with diagnostics: + argument "theme" is missing, with no default + ... + --- failed re-building ‘clinDataReview-dataVisualization.Rmd’ + + --- re-building ‘clinDataReview-reporting.Rmd’ using rmarkdown + --- finished re-building ‘clinDataReview-reporting.Rmd’ + + SUMMARY: processing the following file failed: + ‘clinDataReview-dataVisualization.Rmd’ + + Error: Vignette re-building failed. + Execution halted + ``` + +## In both + +* checking installed package size ... NOTE + ``` + installed size is 6.0Mb + sub-directories of 1Mb or more: + doc 4.3Mb + ``` + +# clinUtils + +
+ +* Version: 0.1.5 +* GitHub: https://github.com/openanalytics/clinUtils +* Source code: https://github.com/cran/clinUtils +* Date/Publication: 2024-04-23 20:50:31 UTC +* Number of recursive dependencies: 120 + +Run `revdepcheck::cloud_details(, "clinUtils")` for more info + +
+ +## Newly broken + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘clinUtils-vignette.Rmd’ + ... + + layout + + + > listPlotsInteractiveLB <- sapply(listPlotsLB, function(ggplot) ggplotly(ggplot) %>% + + partial_bundle(), simplify = FALSE) + + When sourcing ‘clinUtils-vignette.R’: + Error: argument "theme" is missing, with no default + Execution halted + + ‘clinUtils-vignette.Rmd’ using ‘UTF-8’... failed + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘clinUtils-vignette.Rmd’ using rmarkdown + ``` + +## Newly fixed + +* checking running R code from vignettes ... WARNING + ``` + Errors in running code in vignettes: + when running code in ‘clinUtils-vignette.Rmd’ + ... + + + > knitPrintListPlots(plotsList = listPlotsInteractiveLB, + + generalLabel = "lab-hist-interactive", type = "plotly", titles = simpleCap(tolower(nam .... [TRUNCATED] + + Quitting from lines at lines 2-4 [lab-hist-interactive1] + + When sourcing ‘clinUtils-vignette.R’: + Error: there is no package called 'webshot' + Execution halted + + ‘clinUtils-vignette.Rmd’ using ‘UTF-8’... failed + ``` + +## In both + +* checking installed package size ... NOTE + ``` + installed size is 7.9Mb + sub-directories of 1Mb or more: + doc 6.5Mb + ``` + +# ClusROC + +
+ +* Version: 1.0.2 +* GitHub: https://github.com/toduckhanh/ClusROC +* Source code: https://github.com/cran/ClusROC +* Date/Publication: 2022-11-17 15:00:02 UTC +* Number of recursive dependencies: 107 + +Run `revdepcheck::cloud_details(, "ClusROC")` for more info + +
+ +## Newly broken + +* checking whether package ‘ClusROC’ can be installed ... WARNING + ``` + Found the following significant warnings: + Warning: replacing previous import ‘ggplot2::ggpar’ by ‘ggpubr::ggpar’ when loading ‘ClusROC’ + See ‘/tmp/workdir/ClusROC/new/ClusROC.Rcheck/00install.out’ for details. + ``` + +# clustEff + +
+ +* Version: 0.3.1 +* GitHub: NA +* Source code: https://github.com/cran/clustEff +* Date/Publication: 2024-01-23 08:52:55 UTC +* Number of recursive dependencies: 136 + +Run `revdepcheck::cloud_details(, "clustEff")` for more info + +
+ +## Newly broken + +* checking whether package ‘clustEff’ can be installed ... WARNING + ``` + Found the following significant warnings: + Warning: replacing previous import ‘ggplot2::ggpar’ by ‘ggpubr::ggpar’ when loading ‘clustEff’ + See ‘/tmp/workdir/clustEff/new/clustEff.Rcheck/00install.out’ for details. + ``` + +# coda4microbiome + +
+ +* Version: 0.2.3 +* GitHub: https://github.com/malucalle/coda4microbiome +* Source code: https://github.com/cran/coda4microbiome +* Date/Publication: 2024-02-21 08:30:06 UTC +* Number of recursive dependencies: 136 + +Run `revdepcheck::cloud_details(, "coda4microbiome")` for more info + +
+ +## Newly broken + +* checking whether package ‘coda4microbiome’ can be installed ... WARNING + ``` + Found the following significant warnings: + Warning: replacing previous import ‘ggplot2::ggpar’ by ‘ggpubr::ggpar’ when loading ‘coda4microbiome’ + See ‘/tmp/workdir/coda4microbiome/new/coda4microbiome.Rcheck/00install.out’ for details. + ``` + +# CohortPlat + +
+ +* Version: 1.0.5 +* GitHub: NA +* Source code: https://github.com/cran/CohortPlat +* Date/Publication: 2022-02-14 09:30:02 UTC +* Number of recursive dependencies: 82 + +Run `revdepcheck::cloud_details(, "CohortPlat")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘CohortPlat-Ex.R’ failed + The error most likely occurred in: + + > ### Name: plot_trial + > ### Title: Plots the cohort trial study overview given stage data. + > ### Aliases: plot_trial + > + > ### ** Examples + > + > + ... + + sr_drugs_pos = sr_drugs_pos, target_rr = target_rr, sharing_type = sharing_type, + + safety_prob = safety_prob, Bayes_Sup = Bayes_Sup, prob_rr_transform = prob_rr_transform, + + cohort_offset = cohort_offset, Bayes_Fut = Bayes_Fut, sr_first_pos = sr_first_pos + + ) + > + > plot_trial(res_list, unit = "n") + Error in compute_geom_2(..., self = self) : + argument "theme" is missing, with no default + Calls: plot_trial ... use_defaults -> eval_from_theme -> %||% -> calc_element + Execution halted + ``` + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘my-vignette.Rmd’ + ... + + > set.seed(50) + + > ocs1 <- trial_ocs(n_int = n_int, n_fin = n_fin, rr_comb = rr_comb, + + rr_mono = rr_mono, rr_back = rr_back, rr_plac = rr_plac, + + rr_transfo .... [TRUNCATED] + + When sourcing ‘my-vignette.R’: + Error: argument "theme" is missing, with no default + Execution halted + + ‘my-vignette.Rmd’ using ‘UTF-8’... failed + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + ... + --- re-building ‘my-vignette.Rmd’ using rmarkdown + + Quitting from lines at lines 1043-1073 [unnamed-chunk-20] (my-vignette.Rmd) + Error: processing vignette 'my-vignette.Rmd' failed with diagnostics: + argument "theme" is missing, with no default + --- failed re-building ‘my-vignette.Rmd’ + + SUMMARY: processing the following file failed: + ‘my-vignette.Rmd’ + + Error: Vignette re-building failed. + Execution halted + ``` + +# CompAREdesign + +
+ +* Version: 2.3.1 +* GitHub: NA +* Source code: https://github.com/cran/CompAREdesign +* Date/Publication: 2024-02-15 13:00:02 UTC +* Number of recursive dependencies: 90 + +Run `revdepcheck::cloud_details(, "CompAREdesign")` for more info + +
+ +## Newly broken + +* checking whether package ‘CompAREdesign’ can be installed ... WARNING + ``` + Found the following significant warnings: + Warning: replacing previous import ‘ggplot2::ggpar’ by ‘ggpubr::ggpar’ when loading ‘CompAREdesign’ + See ‘/tmp/workdir/CompAREdesign/new/CompAREdesign.Rcheck/00install.out’ for details. + ``` + +# CoreMicrobiomeR + +
+ +* Version: 0.1.0 +* GitHub: NA +* Source code: https://github.com/cran/CoreMicrobiomeR +* Date/Publication: 2024-04-03 20:03:02 UTC +* Number of recursive dependencies: 91 + +Run `revdepcheck::cloud_details(, "CoreMicrobiomeR")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘CoreMicrobiomeR-Ex.R’ failed + The error most likely occurred in: + + > ### Name: group_bar_plots + > ### Title: Grouped Bar Plots Based on Sample Size + > ### Aliases: group_bar_plots + > + > ### ** Examples + > + > #To run input data + ... + + ) + Warning encountered during diversity analysis:you have empty rows: their dissimilarities may be + meaningless in method “bray” + > #To run grouped bar plot function + > plot_group_bar <- group_bar_plots(core_1$final_otu_table_bef_filter, + + core_1$final_otu_aft_filter, 10) + Error in compute_geom_2(..., self = self) : + argument "theme" is missing, with no default + Calls: group_bar_plots ... use_defaults -> eval_from_theme -> %||% -> calc_element + Execution halted + ``` + +# correlationfunnel + +
+ +* Version: 0.2.0 +* GitHub: https://github.com/business-science/correlationfunnel +* Source code: https://github.com/cran/correlationfunnel +* Date/Publication: 2020-06-09 04:40:03 UTC +* Number of recursive dependencies: 117 + +Run `revdepcheck::cloud_details(, "correlationfunnel")` for more info + +
+ +## Newly broken + +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(dplyr) + + Attaching package: 'dplyr' + + The following object is masked from 'package:testthat': + + ... + 10. └─ggplot2 (local) compute_geom_2(..., self = self) + 11. └─self$geom$use_defaults(data, self$aes_params, modifiers, theme = theme) + 12. └─ggplot2 (local) use_defaults(..., self = self) + 13. └─ggplot2:::eval_from_theme(default_aes, theme) + 14. ├─calc_element("geom", theme) %||% .default_geom_element + 15. └─ggplot2::calc_element("geom", theme) + + [ FAIL 1 | WARN 3 | SKIP 0 | PASS 17 ] + Error: Test failures + Execution halted + ``` + +## In both + +* checking dependencies in R code ... NOTE + ``` + Namespace in Imports field not imported from: ‘utils’ + All declared Imports should be used. + ``` + +# corrViz + +
+ +* Version: 0.1.0 +* GitHub: NA +* Source code: https://github.com/cran/corrViz +* Date/Publication: 2023-06-30 11:40:07 UTC +* Number of recursive dependencies: 140 + +Run `revdepcheck::cloud_details(, "corrViz")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘corrViz-Ex.R’ failed + The error most likely occurred in: + + > ### Name: animSolar + > ### Title: animSolar + > ### Aliases: animSolar + > + > ### ** Examples + > + > cm <- cor(mtcars) + ... + ℹ Please consider using `annotate()` or provide this layer with data containing + a single row. + Warning in geom_text(data = solar_system, aes(x = 0, y = 0, label = sun), : + All aesthetics have length 1, but the data has 250 rows. + ℹ Please consider using `annotate()` or provide this layer with data containing + a single row. + Error in compute_geom_2(..., self = self) : + argument "theme" is missing, with no default + Calls: animSolar ... use_defaults -> eval_from_theme -> %||% -> calc_element + Execution halted + ``` + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘corrViz.Rmd’ + ... + > library(corrViz) + + > cm <- cor(mtcars) + + > corrHeatmap(mat = cm, display = "all", reorder = TRUE, + + pal = colorRampPalette(c("darkblue", "white", "darkred"))(100)) + + When sourcing ‘corrViz.R’: + Error: argument "theme" is missing, with no default + Execution halted + + ‘corrViz.Rmd’ using ‘UTF-8’... failed + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + ... + --- re-building ‘corrViz.Rmd’ using rmarkdown + + Quitting from lines at lines 76-81 [heatmap] (corrViz.Rmd) + Error: processing vignette 'corrViz.Rmd' failed with diagnostics: + argument "theme" is missing, with no default + --- failed re-building ‘corrViz.Rmd’ + + SUMMARY: processing the following file failed: + ‘corrViz.Rmd’ + + Error: Vignette re-building failed. + Execution halted + ``` + +## In both + +* checking installed package size ... NOTE + ``` + installed size is 7.2Mb + sub-directories of 1Mb or more: + doc 6.7Mb + ``` + +# covidcast + +
+ +* Version: 0.5.2 +* GitHub: https://github.com/cmu-delphi/covidcast +* Source code: https://github.com/cran/covidcast +* Date/Publication: 2023-07-12 23:40:06 UTC +* Number of recursive dependencies: 93 + +Run `revdepcheck::cloud_details(, "covidcast")` for more info + +
+ +## Newly broken + +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(covidcast) + We encourage COVIDcast API users to register on our mailing list: + https://lists.andrew.cmu.edu/mailman/listinfo/delphi-covidcast-api + We'll send announcements about new data sources, package updates, + server maintenance, and new features. + > + ... + • plot/default-county-choropleth.svg + • plot/default-hrr-choropleth-with-include.svg + • plot/default-msa-choropleth-with-include.svg + • plot/default-state-choropleth-with-include.svg + • plot/default-state-choropleth-with-range.svg + • plot/state-choropleth-with-no-metadata.svg + • plot/state-line-graph-with-range.svg + • plot/state-line-graph-with-stderrs.svg + Error: Test failures + Execution halted + ``` + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘multi-signals.Rmd’ + ... + + > signals <- covidcast_signals(data_source = "jhu-csse", + + signal = c("confirmed_7dav_incidence_prop", "deaths_7dav_incidence_prop"), + + star .... [TRUNCATED] + + When sourcing ‘multi-signals.R’: + Error: Rate limit exceeded when fetching data from API anonymously. See the "API keys" section of the `covidcast_signal()` documentation for information on registering for an API key. + ... + Error: Rate limit exceeded when fetching data from API anonymously. See the "API keys" section of the `covidcast_signal()` documentation for information on registering for an API key. + ℹ Message from server: + ℹ Rate limit exceeded for anonymous queries. To remove this limit, register a free API key at https://api.delphi.cmu.edu/epidata/admin/registration_form + Execution halted + + ‘correlation-utils.Rmd’ using ‘UTF-8’... OK + ‘covidcast.Rmd’ using ‘UTF-8’... OK + ‘external-data.Rmd’ using ‘UTF-8’... OK + ‘multi-signals.Rmd’ using ‘UTF-8’... failed + ‘plotting-signals.Rmd’ using ‘UTF-8’... failed + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘correlation-utils.Rmd’ using rmarkdown + --- finished re-building ‘correlation-utils.Rmd’ + + --- re-building ‘covidcast.Rmd’ using rmarkdown + + Quitting from lines at lines 38-45 [unnamed-chunk-1] (covidcast.Rmd) + Error: processing vignette 'covidcast.Rmd' failed with diagnostics: + Rate limit exceeded when fetching data from API anonymously. See the "API keys" section of the `covidcast_signal()` documentation for information on registering for an API key. + ℹ Message from server: + ℹ Rate limit exceeded for anonymous queries. To remove this limit, register a free API key at https://api.delphi.cmu.edu/epidata/admin/registration_form + --- failed re-building ‘covidcast.Rmd’ + + --- re-building ‘external-data.Rmd’ using rmarkdown + ``` + +## In both + +* checking data for non-ASCII characters ... NOTE + ``` + Note: found 20 marked UTF-8 strings + ``` + +# Coxmos + +
+ +* Version: 1.0.2 +* GitHub: https://github.com/BiostatOmics/Coxmos +* Source code: https://github.com/cran/Coxmos +* Date/Publication: 2024-03-25 20:32:38 UTC +* Number of recursive dependencies: 204 + +Run `revdepcheck::cloud_details(, "Coxmos")` for more info + +
+ +## Newly broken + +* checking Rd files ... WARNING + ``` + prepare_Rd: replacing previous import ‘ggplot2::ggpar’ by ‘ggpubr::ggpar’ when loading ‘survminer’ + ``` + +## In both + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘Coxmos-pipeline.Rmd’ + ... + Warning in data("X_proteomic") : data set ‘X_proteomic’ not found + + > data("Y_proteomic") + Warning in data("Y_proteomic") : data set ‘Y_proteomic’ not found + + > X <- X_proteomic + + When sourcing ‘Coxmos-pipeline.R’: + Error: object 'X_proteomic' not found + Execution halted + + ‘Coxmos-MO-pipeline.Rmd’ using ‘UTF-8’... OK + ‘Coxmos-pipeline.Rmd’ using ‘UTF-8’... failed + ``` + +* checking installed package size ... NOTE + ``` + installed size is 6.5Mb + sub-directories of 1Mb or more: + data 2.1Mb + doc 2.9Mb + ``` + +# crosshap + +
+ +* Version: 1.4.0 +* GitHub: https://github.com/jacobimarsh/crosshap +* Source code: https://github.com/cran/crosshap +* Date/Publication: 2024-03-31 15:40:02 UTC +* Number of recursive dependencies: 117 + +Run `revdepcheck::cloud_details(, "crosshap")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘crosshap-Ex.R’ failed + The error most likely occurred in: + + > ### Name: build_bot_halfeyeplot + > ### Title: Bot hap-pheno raincloud plot + > ### Aliases: build_bot_halfeyeplot + > + > ### ** Examples + > + > + ... + 12. │ └─ggplot2 (local) f(l = layers[[i]], d = data[[i]]) + 13. │ └─l$compute_geom_2(d, theme = plot$theme) + 14. │ └─ggplot2 (local) compute_geom_2(..., self = self) + 15. │ └─self$geom$use_defaults(data, self$aes_params, modifiers, theme = theme) + 16. └─base::.handleSimpleError(...) + 17. └─rlang (local) h(simpleError(msg, call)) + 18. └─handlers[[1L]](cnd) + 19. └─cli::cli_abort(...) + 20. └─rlang::abort(...) + Execution halted + ``` + +# csa + +
+ +* Version: 0.7.1 +* GitHub: https://github.com/imarkonis/csa +* Source code: https://github.com/cran/csa +* Date/Publication: 2023-10-24 13:40:11 UTC +* Number of recursive dependencies: 95 + +Run `revdepcheck::cloud_details(, "csa")` for more info + +
+ +## Newly broken + +* checking whether package ‘csa’ can be installed ... WARNING + ``` + Found the following significant warnings: + Warning: replacing previous import ‘ggplot2::ggpar’ by ‘ggpubr::ggpar’ when loading ‘csa’ + See ‘/tmp/workdir/csa/new/csa.Rcheck/00install.out’ for details. + ``` + +# ctrialsgov + +
+ +* Version: 0.2.5 +* GitHub: NA +* Source code: https://github.com/cran/ctrialsgov +* Date/Publication: 2021-10-18 16:00:02 UTC +* Number of recursive dependencies: 100 + +Run `revdepcheck::cloud_details(, "ctrialsgov")` for more info + +
+ +## Newly broken + +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(ctrialsgov) + > + > test_check("ctrialsgov") + [NCT04553939] ible Local Advanved |Bladder| Cancer + [NCT03517995] of Sulforaphane in |Bladder| Cancer Chemoprevent + [NCT04210479] Comparison of |Bladder| Filling vs. Non-Fil + ... + 10. └─ggplot2 (local) compute_geom_2(..., self = self) + 11. └─self$geom$use_defaults(data, self$aes_params, modifiers, theme = theme) + 12. └─ggplot2 (local) use_defaults(..., self = self) + 13. └─ggplot2:::eval_from_theme(default_aes, theme) + 14. ├─calc_element("geom", theme) %||% .default_geom_element + 15. └─ggplot2::calc_element("geom", theme) + + [ FAIL 1 | WARN 6 | SKIP 0 | PASS 43 ] + Error: Test failures + Execution halted + ``` + +## In both + +* checking data for non-ASCII characters ... NOTE + ``` + Note: found 1350 marked UTF-8 strings + ``` + +# cubble + +
+ +* Version: 0.3.0 +* GitHub: https://github.com/huizezhang-sherry/cubble +* Source code: https://github.com/cran/cubble +* Date/Publication: 2023-06-30 03:40:02 UTC +* Number of recursive dependencies: 144 + +Run `revdepcheck::cloud_details(, "cubble")` for more info + +
+ +## Newly broken + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘cb6interactive.Rmd’ + ... + + y .... [TRUNCATED] + Warning: Using `size` aesthetic for lines was deprecated in ggplot2 3.4.0. + ℹ Please use `linewidth` instead. + + > ts_interactive <- ggplotly(ts_static, width = 600, + + height = 300) %>% highlight(on = "plotly_selected", opacityDim = 0.012) + + ... + When sourcing ‘cb6interactive.R’: + Error: argument "theme" is missing, with no default + Execution halted + + ‘cb1class.Rmd’ using ‘UTF-8’... OK + ‘cb2create.Rmd’ using ‘UTF-8’... OK + ‘cb3tsibblesf.Rmd’ using ‘UTF-8’... OK + ‘cb4glyph.Rmd’ using ‘UTF-8’... OK + ‘cb5match.Rmd’ using ‘UTF-8’... OK + ‘cb6interactive.Rmd’ using ‘UTF-8’... failed + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘cb1class.Rmd’ using rmarkdown + --- finished re-building ‘cb1class.Rmd’ + + --- re-building ‘cb2create.Rmd’ using rmarkdown + --- finished re-building ‘cb2create.Rmd’ + + --- re-building ‘cb3tsibblesf.Rmd’ using rmarkdown + --- finished re-building ‘cb3tsibblesf.Rmd’ + + --- re-building ‘cb4glyph.Rmd’ using rmarkdown + ``` + +## In both + +* checking installed package size ... NOTE + ``` + installed size is 5.5Mb + sub-directories of 1Mb or more: + data 3.0Mb + doc 1.3Mb + ``` + +# dafishr + +
+ +* Version: 1.0.0 +* GitHub: https://github.com/CBMC-GCMP/dafishr +* Source code: https://github.com/cran/dafishr +* Date/Publication: 2022-12-06 13:10:02 UTC +* Number of recursive dependencies: 114 + +Run `revdepcheck::cloud_details(, "dafishr")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘dafishr-Ex.R’ failed + The error most likely occurred in: + + > ### Name: join_mpa_data + > ### Title: Detect fishing vessel presence within Marine Protected Areas + > ### polygons in Mexico + > ### Aliases: join_mpa_data + > + > ### ** Examples + > + ... + 17. └─ggplot2 (local) FUN(X[[i]], ...) + 18. └─g$draw_key(data, g$params, key_size) + 19. └─ggplot2 (local) draw_key(...) + 20. └─ggplot2::draw_key_point(data, params, size) + 21. ├─grid::pointsGrob(...) + 22. │ └─grid::grob(...) + 23. └─ggplot2::ggpar(...) + 24. └─rlang:::Ops.quosure(pointsize, .pt) + 25. └─rlang::abort(...) + Execution halted + ``` + +## In both + +* checking installed package size ... NOTE + ``` + installed size is 7.9Mb + sub-directories of 1Mb or more: + data 7.6Mb + ``` + +* checking data for non-ASCII characters ... NOTE + ``` + Note: found 2020 marked UTF-8 strings + ``` + +# damAOI + +
+ +* Version: 0.0 +* GitHub: NA +* Source code: https://github.com/cran/damAOI +* Date/Publication: 2024-02-07 18:00:02 UTC +* Number of recursive dependencies: 101 + +Run `revdepcheck::cloud_details(, "damAOI")` for more info + +
+ +## Newly broken + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘damAOI.Rmd’ + ... + + ggplot2::aes(fill = as.factor(area)), alpha = 0.3) + ggplot2::geom_sf(data = bufferandcli .... [TRUNCATED] + + When sourcing ‘damAOI.R’: + Error: Summary operations are not defined for quosures. Do you need to unquote + the quosure? + + # Bad: min(myquosure) + + # Good: min(!!myquosure) + Execution halted + + ‘damAOI.Rmd’ using ‘UTF-8’... failed + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘damAOI.Rmd’ using rmarkdown + ``` + +# deeptime + +
+ +* Version: 1.1.1 +* GitHub: https://github.com/willgearty/deeptime +* Source code: https://github.com/cran/deeptime +* Date/Publication: 2024-03-08 17:10:10 UTC +* Number of recursive dependencies: 181 + +Run `revdepcheck::cloud_details(, "deeptime")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘deeptime-Ex.R’ failed + The error most likely occurred in: + + > ### Name: facet_wrap_color + > ### Title: Wrap a 1d ribbon of panels into 2d with colored strips + > ### Aliases: facet_wrap_color FacetWrapColor + > ### Keywords: datasets + > + > ### ** Examples + > + ... + 6. │ └─ggplot2 (local) setup(..., self = self) + 7. │ └─self$facet$compute_layout(data, self$facet_params) + 8. │ └─ggplot2 (local) compute_layout(..., self = self) + 9. │ └─ggplot2:::wrap_layout(id, dims, params$dir) + 10. │ └─ggplot2:::data_frame0(...) + 11. │ └─vctrs::data_frame(..., .name_repair = "minimal") + 12. └─vctrs:::stop_recycle_incompatible_size(...) + 13. └─vctrs:::stop_vctrs(...) + 14. └─rlang::abort(message, class = c(class, "vctrs_error"), ..., call = call) + Execution halted + ``` + +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(deeptime) + > + > test_check("deeptime") + Scale for y is already present. + Adding another scale for y, which will replace the existing scale. + Scale for y is already present. + ... + • gggeo_scale/gggeo-scale-top-new.svg + • gggeo_scale/gggeo-scale-top-old.svg + • points_range/geom-points-range-aes-new.svg + • points_range/geom-points-range-aes-old.svg + • points_range/geom-points-range-bg-new.svg + • points_range/geom-points-range-bg-old.svg + • points_range/geom-points-range-h-new.svg + • points_range/geom-points-range-h-old.svg + Error: Test failures + Execution halted + ``` + +# DEGRE + +
+ +* Version: 0.2.0 +* GitHub: NA +* Source code: https://github.com/cran/DEGRE +* Date/Publication: 2022-11-02 09:32:57 UTC +* Number of recursive dependencies: 89 + +Run `revdepcheck::cloud_details(, "DEGRE")` for more info + +
+ +## Newly broken + +* checking whether package ‘DEGRE’ can be installed ... WARNING + ``` + Found the following significant warnings: + Warning: replacing previous import ‘ggplot2::ggpar’ by ‘ggpubr::ggpar’ when loading ‘DEGRE’ + See ‘/tmp/workdir/DEGRE/new/DEGRE.Rcheck/00install.out’ for details. + ``` + +# densityarea + +
+ +* Version: 0.1.0 +* GitHub: https://github.com/JoFrhwld/densityarea +* Source code: https://github.com/cran/densityarea +* Date/Publication: 2023-10-02 10:20:06 UTC +* Number of recursive dependencies: 98 + +Run `revdepcheck::cloud_details(, "densityarea")` for more info + +
+ +## Newly broken + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘densityarea.Rmd’ using rmarkdown + ``` + +## In both + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘sf-operations.Rmd’ + ... + > vowel_intersections <- relocate(mutate(vowel_intersections, + + groups = map_chr(origins, .f = new_label, labels = vowel_polygons$plt_vclass)), + .... [TRUNCATED] + + When sourcing ‘sf-operations.R’: + Error: ℹ In argument: `groups = map_chr(origins, .f = new_label, labels = + vowel_polygons$plt_vclass)`. + Caused by error: + ! object 'new_label' not found + Execution halted + + ‘densityarea.Rmd’ using ‘UTF-8’... OK + ‘sf-operations.Rmd’ using ‘UTF-8’... failed + ``` + +* checking data for non-ASCII characters ... NOTE + ``` + Note: found 2534 marked UTF-8 strings + ``` + +# did + +
+ +* Version: 2.1.2 +* GitHub: https://github.com/bcallaway11/did +* Source code: https://github.com/cran/did +* Date/Publication: 2022-07-20 16:00:05 UTC +* Number of recursive dependencies: 125 + +Run `revdepcheck::cloud_details(, "did")` for more info + +
+ +## Newly broken + +* checking whether package ‘did’ can be installed ... WARNING + ``` + Found the following significant warnings: + Warning: replacing previous import ‘ggplot2::ggpar’ by ‘ggpubr::ggpar’ when loading ‘did’ + See ‘/tmp/workdir/did/new/did.Rcheck/00install.out’ for details. + ``` + +## In both + +* checking running R code from vignettes ... WARNING + ``` + Errors in running code in vignettes: + when running code in ‘TWFE.Rmd’ + ... + + > knitr::opts_chunk$set(collapse = TRUE, comment = "#>", + + echo = TRUE, eval = FALSE) + + > library(tidyverse) + + When sourcing ‘TWFE.R’: + ... + + When sourcing ‘pre-testing.R’: + Error: cannot open the connection + Execution halted + + ‘TWFE.Rmd’ using ‘UTF-8’... failed + ‘did-basics.Rmd’ using ‘UTF-8’... OK + ‘extensions.Rmd’ using ‘UTF-8’... failed + ‘multi-period-did.Rmd’ using ‘UTF-8’... OK + ‘pre-testing.Rmd’ using ‘UTF-8’... failed + ``` + +# distributional + +
+ +* Version: 0.4.0 +* GitHub: https://github.com/mitchelloharawild/distributional +* Source code: https://github.com/cran/distributional +* Date/Publication: 2024-02-07 13:30:02 UTC +* Number of recursive dependencies: 64 + +Run `revdepcheck::cloud_details(, "distributional")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘distributional-Ex.R’ failed + The error most likely occurred in: + + > ### Name: dist_truncated + > ### Title: Truncate a distribution + > ### Aliases: dist_truncated + > + > ### ** Examples + > + > dist <- dist_truncated(dist_normal(2,1), lower = 0) + ... + 12. │ └─ggplot2 (local) f(l = layers[[i]], d = data[[i]]) + 13. │ └─l$compute_geom_2(d, theme = plot$theme) + 14. │ └─ggplot2 (local) compute_geom_2(..., self = self) + 15. │ └─self$geom$use_defaults(data, self$aes_params, modifiers, theme = theme) + 16. └─base::.handleSimpleError(...) + 17. └─rlang (local) h(simpleError(msg, call)) + 18. └─handlers[[1L]](cnd) + 19. └─cli::cli_abort(...) + 20. └─rlang::abort(...) + Execution halted + ``` + +# dittoViz + +
+ +* Version: 1.0.1 +* GitHub: https://github.com/dtm2451/dittoViz +* Source code: https://github.com/cran/dittoViz +* Date/Publication: 2024-02-02 00:00:12 UTC +* Number of recursive dependencies: 99 + +Run `revdepcheck::cloud_details(, "dittoViz")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘dittoViz-Ex.R’ failed + The error most likely occurred in: + + > ### Name: barPlot + > ### Title: Outputs a stacked bar plot to show the percent composition of + > ### samples, groups, clusters, or other groupings + > ### Aliases: barPlot + > + > ### ** Examples + > + ... + 16 4 D 8 32 0.2500000 + > # through hovering the cursor over the relevant parts of the plot + > if (requireNamespace("plotly", quietly = TRUE)) { + + barPlot(example_df, "clustering", group.by = "groups", + + do.hover = TRUE) + + } + Error in compute_geom_2(..., self = self) : + argument "theme" is missing, with no default + Calls: barPlot ... use_defaults -> eval_from_theme -> %||% -> calc_element + Execution halted + ``` + +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(dittoViz) + Loading required package: ggplot2 + > test_check("dittoViz") + [ FAIL 12 | WARN 12 | SKIP 0 | PASS 307 ] + + ══ Failed tests ════════════════════════════════════════════════════════════════ + ... + 12. └─ggplot2 (local) compute_geom_2(..., self = self) + 13. └─self$geom$use_defaults(data, self$aes_params, modifiers, theme = theme) + 14. └─ggplot2 (local) use_defaults(..., self = self) + 15. └─ggplot2:::eval_from_theme(default_aes, theme) + 16. ├─calc_element("geom", theme) %||% .default_geom_element + 17. └─ggplot2::calc_element("geom", theme) + + [ FAIL 12 | WARN 12 | SKIP 0 | PASS 307 ] + Error: Test failures + Execution halted + ``` + +# dots + +
+ +* Version: 0.0.2 +* GitHub: https://github.com/christopherkenny/dots +* Source code: https://github.com/cran/dots +* Date/Publication: 2022-07-15 08:40:07 UTC +* Number of recursive dependencies: 99 + +Run `revdepcheck::cloud_details(, "dots")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘dots-Ex.R’ failed + The error most likely occurred in: + + > ### Name: dots + > ### Title: Make dot density plots + > ### Aliases: dots + > + > ### ** Examples + > + > data('suffolk') + ... + 17. └─ggplot2 (local) FUN(X[[i]], ...) + 18. └─g$draw_key(data, g$params, key_size) + 19. └─ggplot2 (local) draw_key(...) + 20. └─ggplot2::draw_key_point(data, params, size) + 21. ├─grid::pointsGrob(...) + 22. │ └─grid::grob(...) + 23. └─ggplot2::ggpar(...) + 24. └─rlang:::Ops.quosure(pointsize, .pt) + 25. └─rlang::abort(...) + Execution halted + ``` + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘making_dot_density_maps.Rmd’ + ... + > dots::dots(shp = suffolk, cols = vap_hisp) + + When sourcing ‘making_dot_density_maps.R’: + Error: Base operators are not defined for quosures. Do you need to unquote the + quosure? + + # Bad: myquosure * rhs + + # Good: !!myquosure * rhs + Execution halted + + ‘making_dot_density_maps.Rmd’ using ‘UTF-8’... failed + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + ... + --- re-building ‘making_dot_density_maps.Rmd’ using rmarkdown + + Quitting from lines at lines 50-51 [unnamed-chunk-3] (making_dot_density_maps.Rmd) + Error: processing vignette 'making_dot_density_maps.Rmd' failed with diagnostics: + Base operators are not defined for quosures. Do you need to unquote the + quosure? + + # Bad: myquosure * rhs + + # Good: !!myquosure * rhs + --- failed re-building ‘making_dot_density_maps.Rmd’ + + SUMMARY: processing the following file failed: + ‘making_dot_density_maps.Rmd’ + + Error: Vignette re-building failed. + Execution halted + ``` + +## In both + +* checking data for non-ASCII characters ... NOTE + ``` + Note: found 2 marked UTF-8 strings + ``` + +# eks + +
+ +* Version: 1.0.5 +* GitHub: NA +* Source code: https://github.com/cran/eks +* Date/Publication: 2024-05-01 23:24:46 UTC +* Number of recursive dependencies: 89 + +Run `revdepcheck::cloud_details(, "eks")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘eks-Ex.R’ failed + The error most likely occurred in: + + > ### Name: tidyst_kms + > ### Title: Tidy and geospatial kernel mean shift clustering + > ### Aliases: tidy_kms st_kms + > ### Keywords: smooth + > + > ### ** Examples + > + ... + 17. └─ggplot2 (local) FUN(X[[i]], ...) + 18. └─g$draw_key(data, g$params, key_size) + 19. └─ggplot2 (local) draw_key(...) + 20. └─ggplot2::draw_key_point(data, params, size) + 21. ├─grid::pointsGrob(...) + 22. │ └─grid::grob(...) + 23. └─ggplot2::ggpar(...) + 24. └─rlang:::Ops.quosure(pointsize, .pt) + 25. └─rlang::abort(...) + Execution halted + ``` + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘tidysf_kde.Rmd’ + ... + + scale_fill_discrete_sequential(h1 = 275) + coord_sf(xlim = .... [TRUNCATED] + + When sourcing ‘tidysf_kde.R’: + Error: Summary operations are not defined for quosures. Do you need to unquote + the quosure? + + # Bad: min(myquosure) + + # Good: min(!!myquosure) + Execution halted + + ‘tidysf_kde.Rmd’ using ‘UTF-8’... failed + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘tidysf_kde.Rmd’ using rmarkdown + ``` + +# entropart + +
+ +* Version: 1.6-13 +* GitHub: https://github.com/EricMarcon/entropart +* Source code: https://github.com/cran/entropart +* Date/Publication: 2023-09-26 14:40:02 UTC +* Number of recursive dependencies: 122 + +Run `revdepcheck::cloud_details(, "entropart")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘entropart-Ex.R’ failed + The error most likely occurred in: + + > ### Name: Accumulation + > ### Title: Diversity accumulation. + > ### Aliases: DivAC EntAC as.AccumCurve is.AccumCurve autoplot.AccumCurve + > ### plot.AccumCurve + > + > ### ** Examples + > + ... + 11. │ └─base::withCallingHandlers(...) + 12. └─ggplot2 (local) f(l = layers[[i]], d = data[[i]]) + 13. └─l$compute_geom_2(d, theme = plot$theme) + 14. └─ggplot2 (local) compute_geom_2(..., self = self) + 15. └─self$geom$use_defaults(data, self$aes_params, modifiers, theme = theme) + 16. └─ggplot2 (local) use_defaults(..., self = self) + 17. └─ggplot2:::check_aesthetics(new_params, nrow(data)) + 18. └─cli::cli_abort(...) + 19. └─rlang::abort(...) + Execution halted + ``` + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘entropart.Rmd’ + ... + + > autoplot(Abd18, Distribution = "lnorm") + + When sourcing ‘entropart.R’: + Error: Problem while setting up geom aesthetics. + ℹ Error occurred in the 1st layer. + Caused by error in `check_aesthetics()`: + ! Aesthetics must be either length 1 or the same as the data (149). + ✖ Fix the following mappings: `shape`, `colour`, and `size`. + Execution halted + + ‘entropart.Rmd’ using ‘UTF-8’... failed + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + ... + --- re-building ‘entropart.Rmd’ using rmarkdown + + Quitting from lines at lines 53-55 [PlotN18] (entropart.Rmd) + Error: processing vignette 'entropart.Rmd' failed with diagnostics: + Problem while setting up geom aesthetics. + ℹ Error occurred in the 1st layer. + Caused by error in `check_aesthetics()`: + ! Aesthetics must be either length 1 or the same as the data (149). + ✖ Fix the following mappings: `shape`, `colour`, and `size`. + --- failed re-building ‘entropart.Rmd’ + + SUMMARY: processing the following file failed: + ‘entropart.Rmd’ + + Error: Vignette re-building failed. + Execution halted + ``` + +# epiCleanr + +
+ +* Version: 0.2.0 +* GitHub: https://github.com/truenomad/epiCleanr +* Source code: https://github.com/cran/epiCleanr +* Date/Publication: 2023-09-28 12:20:05 UTC +* Number of recursive dependencies: 129 + +Run `revdepcheck::cloud_details(, "epiCleanr")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘epiCleanr-Ex.R’ failed + The error most likely occurred in: + + > ### Name: handle_outliers + > ### Title: Detect and Handle Outliers in Dataset + > ### Aliases: handle_outliers + > + > ### ** Examples + > + > + ... + 12. │ └─ggplot2 (local) f(l = layers[[i]], d = data[[i]]) + 13. │ └─l$compute_geom_2(d, theme = plot$theme) + 14. │ └─ggplot2 (local) compute_geom_2(..., self = self) + 15. │ └─self$geom$use_defaults(data, self$aes_params, modifiers, theme = theme) + 16. └─base::.handleSimpleError(...) + 17. └─rlang (local) h(simpleError(msg, call)) + 18. └─handlers[[1L]](cnd) + 19. └─cli::cli_abort(...) + 20. └─rlang::abort(...) + Execution halted + ``` + +## In both + +* checking installed package size ... NOTE + ``` + installed size is 5.6Mb + sub-directories of 1Mb or more: + doc 2.9Mb + help 2.5Mb + ``` + +# epiR + +
+ +* Version: 2.0.74 +* GitHub: NA +* Source code: https://github.com/cran/epiR +* Date/Publication: 2024-04-27 12:30:02 UTC +* Number of recursive dependencies: 125 + +Run `revdepcheck::cloud_details(, "epiR")` for more info + +
+ +## Newly broken + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘epiR_descriptive.Rmd’ + ... + + fill = "tra ..." ... [TRUNCATED] + + When sourcing ‘epiR_descriptive.R’: + Error: Base operators are not defined for quosures. Do you need to unquote the + quosure? + + # Bad: myquosure * rhs + + # Good: !!myquosure * rhs + Execution halted + + ‘epiR_descriptive.Rmd’... failed + ‘epiR_measures_of_association.Rmd’... OK + ‘epiR_sample_size.Rmd’... OK + ‘epiR_surveillance.Rmd’... OK + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘epiR_descriptive.Rmd’ using rmarkdown + ``` + +# esci + +
+ +* Version: 1.0.2 +* GitHub: https://github.com/rcalinjageman/esci +* Source code: https://github.com/cran/esci +* Date/Publication: 2024-03-21 18:10:02 UTC +* Number of recursive dependencies: 93 + +Run `revdepcheck::cloud_details(, "esci")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘esci-Ex.R’ failed + The error most likely occurred in: + + > ### Name: estimate_mdiff_2x2_between + > ### Title: Estimates for a 2x2 between-subjects design with a continuous + > ### outcome variable + > ### Aliases: estimate_mdiff_2x2_between + > + > ### ** Examples + > + ... + 2.75, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 1, NULL, NULL, NULL, c(0, 2.2, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, NULL, c(0, 0, 0, 2.2 + ), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0.5, NULL, NULL, NULL, c(0, 2.2, 0, 2.2), NULL, TRUE), list("grey20", NULL, NULL, NULL, FALSE, TRUE), NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 2.75, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 0.75, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, list("black", 1, NULL, NULL, FALSE, TRUE), NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, list(NULL, NA, NULL, NULL, TRUE), c(5.5, 5.5, 5.5, 5.5), 11, NULL, + NULL, NULL, 1.2, NULL, NULL, 5.5, NULL, NULL, NULL, NULL, 0.2, NULL, list(NULL, NULL, NULL, 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, NULL, NULL, NULL, TRUE), NULL, "right", NULL, NULL, NULL, "center", NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, c(0, 0, 0, 0), list(), 11, list("white", NA, NULL, NULL, TRUE), list(), 5.5, NULL, NULL, list("grey92", NULL, NULL, NULL, FALSE, TRUE), list(), list(), NULL, NULL, NULL, NULL, FALSE, list(NULL, + "white", NULL, NULL, TRUE), list(NULL, NULL, NULL, 1.2, 0, 1, NULL, NULL, c(0, 0, 5.5, 0), NULL, TRUE), "panel", list(NULL, NULL, NULL, NULL, 0, 1, NULL, NULL, c(0, 0, 5.5, 0), NULL, TRUE), list(NULL, NULL, NULL, 0.8, 1, 1, NULL, NULL, c(5.5, 0, 0, 0), NULL, TRUE), "panel", list(NULL, NULL, NULL, 1.2, 0.5, 0.5, NULL, NULL, NULL, NULL, TRUE), "topleft", NULL, c(5.5, 5.5, 5.5, 5.5), list("white", "black", 2, NULL, TRUE), NULL, NULL, "inherit", "inside", list(NULL, NULL, "grey10", 0.8, NULL, + NULL, NULL, NULL, c(4.4, 4.4, 4.4, 4.4), NULL, TRUE), NULL, NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, NULL, -90, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, NULL, 90, NULL, NULL, NULL, TRUE), NULL, 2.75, 2.75)) + Error in use_defaults(..., self = self) : + unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), NULL, list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.75, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, 90, NULL, c(0, + 2.75, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 1, NULL, NULL, NULL, c(0, 2.2, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL + Calls: ... .handleSimpleError -> h -> -> + Execution halted + ``` + +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(esci) + > + > test_check("esci") + Loading required package: Matrix + Loading required package: metadat + Loading required package: numDeriv + ... + 17. │ └─self$geom$use_defaults(data, self$aes_params, modifiers, theme = theme) + 18. └─base::.handleSimpleError(...) + 19. └─rlang (local) h(simpleError(msg, call)) + 20. └─handlers[[1L]](cnd) + 21. └─cli::cli_abort(...) + 22. └─rlang::abort(...) + + [ FAIL 14 | WARN 15 | SKIP 0 | PASS 3182 ] + Error: Test failures + Execution halted + ``` + +# evalITR + +
+ +* Version: 1.0.0 +* GitHub: https://github.com/MichaelLLi/evalITR +* Source code: https://github.com/cran/evalITR +* Date/Publication: 2023-08-25 23:10:06 UTC +* Number of recursive dependencies: 168 + +Run `revdepcheck::cloud_details(, "evalITR")` for more info + +
+ +## Newly broken + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘cv_multiple_alg.Rmd’ using rmarkdown + ``` + +## In both + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘cv_multiple_alg.Rmd’ + ... + intersect, setdiff, setequal, union + + + > load("../data/star.rda") + Warning in readChar(con, 5L, useBytes = TRUE) : + cannot open compressed file '../data/star.rda', probable reason 'No such file or directory' + + ... + Execution halted + + ‘cv_multiple_alg.Rmd’ using ‘UTF-8’... failed + ‘cv_single_alg.Rmd’ using ‘UTF-8’... failed + ‘install.Rmd’ using ‘UTF-8’... OK + ‘paper_alg1.Rmd’ using ‘UTF-8’... OK + ‘sample_split.Rmd’ using ‘UTF-8’... failed + ‘sample_split_caret.Rmd’ using ‘UTF-8’... failed + ‘user_itr.Rmd’ using ‘UTF-8’... failed + ‘user_itr_algs.Rmd’ using ‘UTF-8’... failed + ``` + +* checking dependencies in R code ... NOTE + ``` + Namespaces in Imports field not imported from: + ‘forcats’ ‘rqPen’ ‘utils’ + All declared Imports should be used. + ``` + +# explainer + +
+ +* Version: 1.0.1 +* GitHub: https://github.com/PERSIMUNE/explainer +* Source code: https://github.com/cran/explainer +* Date/Publication: 2024-04-18 09:00:02 UTC +* Number of recursive dependencies: 193 + +Run `revdepcheck::cloud_details(, "explainer")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘explainer-Ex.R’ failed + The error most likely occurred in: + + > ### Name: eDecisionCurve + > ### Title: Decision Curve Plot + > ### Aliases: eDecisionCurve + > + > ### ** Examples + > + > library("explainer") + ... + > myplot <- eDecisionCurve( + + task = maintask, + + trained_model = mylrn, + + splits = splits, + + seed = seed + + ) + Error in compute_geom_2(..., self = self) : + argument "theme" is missing, with no default + Calls: eDecisionCurve ... use_defaults -> eval_from_theme -> %||% -> calc_element + Execution halted + ``` + +## In both + +* checking dependencies in R code ... NOTE + ``` + Namespace in Imports field not imported from: ‘ggpmisc’ + All declared Imports should be used. + ``` + +# fable.prophet + +
+ +* Version: 0.1.0 +* GitHub: https://github.com/mitchelloharawild/fable.prophet +* Source code: https://github.com/cran/fable.prophet +* Date/Publication: 2020-08-20 09:30:03 UTC +* Number of recursive dependencies: 114 + +Run `revdepcheck::cloud_details(, "fable.prophet")` for more info + +
+ +## Newly broken + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘intro.Rmd’ + ... + 2.75, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 1, NULL, NULL, NULL, c(0, 2.2, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, NULL, c(0, 0, 0, 2.2 + ), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0.5, NULL, NULL, NULL, c(0, 2.2, 0, 2.2), NULL, TRUE), list("grey20", NULL, NULL, NULL, FALSE, TRUE), NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 2.75, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 0.75, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, list(), NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, list(NULL, NA, NULL, NULL, TRUE), c(5.5, 5.5, 5.5, 5.5), 11, NULL, NULL, NULL, 1.2, NULL, NULL, 5.5, + NULL, NULL, NULL, NULL, 0.2, NULL, list(NULL, NULL, NULL, 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, NULL, NULL, NULL, TRUE), NULL, "right", NULL, NULL, NULL, "center", NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, c(0, 0, 0, 0), list(), 11, list("grey92", NA, NULL, NULL, TRUE), list(), 5.5, NULL, NULL, list("white", NULL, NULL, NULL, FALSE, TRUE), NULL, list(NULL, 0.5, NULL, NULL, FALSE, TRUE), NULL, NULL, NULL, NULL, FALSE, list(NULL, + "white", NULL, NULL, TRUE), list(NULL, NULL, NULL, 1.2, 0, 1, NULL, NULL, c(0, 0, 5.5, 0), NULL, TRUE), "panel", list(NULL, NULL, NULL, NULL, 0, 1, NULL, NULL, c(0, 0, 5.5, 0), NULL, TRUE), list(NULL, NULL, NULL, 0.8, 1, 1, NULL, NULL, c(5.5, 0, 0, 0), NULL, TRUE), "panel", list(NULL, NULL, NULL, 1.2, 0.5, 0.5, NULL, NULL, NULL, NULL, TRUE), "topleft", NULL, c(5.5, 5.5, 5.5, 5.5), list("grey85", NA, NULL, NULL, TRUE), NULL, NULL, "inherit", "inside", list(NULL, NULL, "grey10", 0.8, NULL, + NULL, NULL, NULL, c(4.4, 4.4, 4.4, 4.4), NULL, TRUE), NULL, NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, NULL, -90, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, NULL, 90, NULL, NULL, NULL, TRUE), NULL, 2.75, 2.75)) + + When sourcing ‘intro.R’: + Error: unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), NULL, list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.75, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, 90, NULL, c(0, + 2.75, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 1, NULL, NULL, NULL, c(0, 2.2, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, + Execution halted + + ‘intro.Rmd’ using ‘UTF-8’... failed + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘intro.Rmd’ using rmarkdown + ``` + +## In both + +* checking LazyData ... NOTE + ``` + 'LazyData' is specified without a 'data' directory + ``` + +# fabletools + +
+ +* Version: 0.4.2 +* GitHub: https://github.com/tidyverts/fabletools +* Source code: https://github.com/cran/fabletools +* Date/Publication: 2024-04-22 11:22:41 UTC +* Number of recursive dependencies: 106 + +Run `revdepcheck::cloud_details(, "fabletools")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘fabletools-Ex.R’ failed + The error most likely occurred in: + + > ### Name: autoplot.fbl_ts + > ### Title: Plot a set of forecasts + > ### Aliases: autoplot.fbl_ts autolayer.fbl_ts + > + > ### ** Examples + > + > ## Don't show: + ... + 2.75, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 1, NULL, NULL, NULL, c(0, 2.2, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, NULL, c(0, 0, 0, 2.2 + ), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0.5, NULL, NULL, NULL, c(0, 2.2, 0, 2.2), NULL, TRUE), list("grey20", NULL, NULL, NULL, FALSE, TRUE), NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 2.75, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 0.75, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, list(), NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, list(NULL, NA, NULL, NULL, TRUE), c(5.5, 5.5, 5.5, 5.5), 11, NULL, NULL, NULL, 1.2, NULL, NULL, 5.5, + NULL, NULL, NULL, NULL, 0.2, NULL, list(NULL, NULL, NULL, 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, NULL, NULL, NULL, TRUE), NULL, "right", NULL, NULL, NULL, "center", NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, c(0, 0, 0, 0), list(), 11, list("grey92", NA, NULL, NULL, TRUE), list(), 5.5, NULL, NULL, list("white", NULL, NULL, NULL, FALSE, TRUE), NULL, list(NULL, 0.5, NULL, NULL, FALSE, TRUE), NULL, NULL, NULL, NULL, FALSE, list(NULL, + "white", NULL, NULL, TRUE), list(NULL, NULL, NULL, 1.2, 0, 1, NULL, NULL, c(0, 0, 5.5, 0), NULL, TRUE), "panel", list(NULL, NULL, NULL, NULL, 0, 1, NULL, NULL, c(0, 0, 5.5, 0), NULL, TRUE), list(NULL, NULL, NULL, 0.8, 1, 1, NULL, NULL, c(5.5, 0, 0, 0), NULL, TRUE), "panel", list(NULL, NULL, NULL, 1.2, 0.5, 0.5, NULL, NULL, NULL, NULL, TRUE), "topleft", NULL, c(5.5, 5.5, 5.5, 5.5), list("grey85", NA, NULL, NULL, TRUE), NULL, NULL, "inherit", "inside", list(NULL, NULL, "grey10", 0.8, NULL, + NULL, NULL, NULL, c(4.4, 4.4, 4.4, 4.4), NULL, TRUE), NULL, NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, NULL, -90, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, NULL, 90, NULL, NULL, NULL, TRUE), NULL, 2.75, 2.75)) + Error in use_defaults(..., self = self) : + unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), NULL, list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.75, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, 90, NULL, c(0, + 2.75, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 1, NULL, NULL, NULL, c(0, 2.2, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL + Calls: ... .handleSimpleError -> h -> -> + Execution halted + ``` + +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(dplyr) + + Attaching package: 'dplyr' + + The following object is masked from 'package:testthat': + + ... + 32. │ │ └─base::withCallingHandlers(...) + 33. │ └─layer$geom$use_defaults(...) + 34. └─base::.handleSimpleError(...) + 35. └─rlang (local) h(simpleError(msg, call)) + 36. └─handlers[[1L]](cnd) + 37. └─layer$geom$use_defaults(...) + + [ FAIL 2 | WARN 0 | SKIP 1 | PASS 269 ] + Error: Test failures + Execution halted + ``` + +# ffp + +
+ +* Version: 0.2.2 +* GitHub: https://github.com/Reckziegel/FFP +* Source code: https://github.com/cran/ffp +* Date/Publication: 2022-09-29 15:10:06 UTC +* Number of recursive dependencies: 107 + +Run `revdepcheck::cloud_details(, "ffp")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘ffp-Ex.R’ failed + The error most likely occurred in: + + > ### Name: scenario_density + > ### Title: Plot Scenarios + > ### Aliases: scenario_density scenario_histogram + > + > ### ** Examples + > + > x <- diff(log(EuStockMarkets))[, 1] + ... + 2.75, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, NULL, c(0, 0, 0, 2.2), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0.5, NULL, NULL, NULL, + c(0, 2.2, 0, 2.2), NULL, TRUE), list("grey20", NULL, NULL, NULL, FALSE, TRUE), NULL, NULL, NULL, list(), NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 2.75, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 0.75, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, list(), NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, list(NULL, NA, NULL, NULL, TRUE), c(5.5, 5.5, 5.5, 5.5), 11, NULL, NULL, NULL, 1.2, NULL, NULL, 5.5, NULL, NULL, NULL, NULL, 0.2, NULL, list(NULL, NULL, NULL, 0.8, NULL, + NULL, NULL, NULL, NULL, NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, NULL, NULL, NULL, TRUE), NULL, "right", NULL, NULL, NULL, "center", NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, c(0, 0, 0, 0), list(), 11, list("grey92", NA, NULL, NULL, TRUE), list(), 5.5, NULL, NULL, list("white", NULL, NULL, NULL, FALSE, TRUE), NULL, list(NULL, 0.5, NULL, NULL, FALSE, TRUE), NULL, NULL, NULL, NULL, FALSE, list(NULL, "white", NULL, NULL, TRUE), list(NULL, NULL, NULL, 1.2, 0, 1, NULL, + NULL, c(0, 0, 5.5, 0), NULL, TRUE), "panel", list(NULL, NULL, NULL, NULL, 0, 1, NULL, NULL, c(0, 0, 5.5, 0), NULL, TRUE), list(NULL, NULL, NULL, 0.8, 1, 1, NULL, NULL, c(5.5, 0, 0, 0), NULL, TRUE), "panel", list(NULL, NULL, NULL, 1.2, 0.5, 0.5, NULL, NULL, NULL, NULL, TRUE), "topleft", NULL, c(5.5, 5.5, 5.5, 5.5), list("grey85", NA, NULL, NULL, TRUE), NULL, NULL, "inherit", "inside", list(NULL, NULL, "grey10", 0.8, NULL, NULL, NULL, NULL, c(4.4, 4.4, 4.4, 4.4), NULL, TRUE), NULL, NULL, NULL, + list(NULL, NULL, NULL, NULL, NULL, NULL, -90, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, NULL, 90, NULL, NULL, NULL, TRUE), NULL, 2.75, 2.75)) + Error in use_defaults(..., self = self) : + unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), NULL, list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.75, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, 90, NULL, c(0, + 2.75, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, NULL, c(0, 0, 0, 2.2), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, + Calls: ... .handleSimpleError -> h -> -> + Execution halted + ``` + +# fido + +
+ +* Version: 1.0.4 +* GitHub: https://github.com/jsilve24/fido +* Source code: https://github.com/cran/fido +* Date/Publication: 2023-03-24 12:00:10 UTC +* Number of recursive dependencies: 130 + +Run `revdepcheck::cloud_details(, "fido")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘fido-Ex.R’ failed + The error most likely occurred in: + + > ### Name: plot.pibblefit + > ### Title: Plot Summaries of Posterior Distribution of pibblefit Parameters + > ### Aliases: plot.pibblefit + > + > ### ** Examples + > + > sim <- pibble_sim(N=10, D=4, Q=3) + ... + ! unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), NULL, list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.75, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, + NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 1, NULL, NULL, NULL, c(0, 2.2, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, NULL, c(0, 0, 0, 2.2), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0.5, NULL, NULL, NULL, + c(0, 2.2, 0, 2.2), NULL, TRUE), list(), NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 2.75, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 0.75, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, list(), NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, list(), c(5.5, 5.5, 5.5, 5.5), 11, NULL, NULL, list(), 1.2, NULL, NULL, 5.5, NULL, NULL, NULL, NULL, 0.2, NULL, list(NULL, NULL, NULL, 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), NULL, list(NULL, NULL, NULL, + NULL, 0, NULL, NULL, NULL, NULL, NULL, TRUE), NULL, "right", NULL, NULL, NULL, "center", NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, c(0, 0, 0, 0), list(), 11, list(), list(), 5.5, NULL, NULL, list("grey92", NULL, NULL, NULL, FALSE, TRUE), NULL, list(NULL, 0.5, NULL, NULL, FALSE, TRUE), NULL, NULL, NULL, NULL, FALSE, list(), list(NULL, NULL, NULL, 1.2, 0, 1, NULL, NULL, c(0, 0, 5.5, 0), NULL, TRUE), "panel", list(NULL, NULL, NULL, NULL, 0, 1, NULL, NULL, c(0, 0, 5.5, 0), NULL, TRUE), list( + NULL, NULL, NULL, 0.8, 1, 1, NULL, NULL, c(5.5, 0, 0, 0), NULL, TRUE), "panel", list(NULL, NULL, NULL, 1.2, 0.5, 0.5, NULL, NULL, NULL, NULL, TRUE), "topleft", NULL, c(5.5, 5.5, 5.5, 5.5), list(), NULL, NULL, "inherit", "inside", list(NULL, NULL, "grey10", 0.8, NULL, NULL, NULL, NULL, c(4.4, 4.4, 4.4, 4.4), NULL, TRUE), NULL, NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, NULL, -90, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, NULL, 90, NULL, NULL, NULL, TRUE), NULL, 2.75, 2.75)) + Error in use_defaults(..., self = self) : + unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), NULL, list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.75, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, + NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 1, NULL, NULL, NULL, c(0, 2.2, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, NULL, c(0, 0, 0, 2.2), NULL, TRUE), NULL, list(NULL, NULL, NULL, + Calls: ... .handleSimpleError -> h -> -> + Execution halted + ``` + +## In both + +* checking installed package size ... NOTE + ``` + installed size is 116.1Mb + sub-directories of 1Mb or more: + libs 114.1Mb + ``` + +# flipr + +
+ +* Version: 0.3.3 +* GitHub: https://github.com/LMJL-Alea/flipr +* Source code: https://github.com/cran/flipr +* Date/Publication: 2023-08-23 09:00:02 UTC +* Number of recursive dependencies: 106 + +Run `revdepcheck::cloud_details(, "flipr")` for more info + +
+ +## Newly broken + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘alternative.Rmd’ using rmarkdown + --- finished re-building ‘alternative.Rmd’ + + --- re-building ‘exactness.Rmd’ using rmarkdown + + Quitting from lines at lines 142-177 [unnamed-chunk-1] (exactness.Rmd) + Error: processing vignette 'exactness.Rmd' failed with diagnostics: + argument "theme" is missing, with no default + --- failed re-building ‘exactness.Rmd’ + + --- re-building ‘flipr.Rmd’ using rmarkdown + ``` + +## In both + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘exactness.Rmd’ + ... + + > library(flipr) + + > load("../R/sysdata.rda") + Warning in readChar(con, 5L, useBytes = TRUE) : + cannot open compressed file '../R/sysdata.rda', probable reason 'No such file or directory' + + ... + cannot open compressed file '../R/sysdata.rda', probable reason 'No such file or directory' + + When sourcing ‘plausibility.R’: + Error: cannot open the connection + Execution halted + + ‘alternative.Rmd’ using ‘UTF-8’... OK + ‘exactness.Rmd’ using ‘UTF-8’... failed + ‘flipr.Rmd’ using ‘UTF-8’... failed + ‘plausibility.Rmd’ using ‘UTF-8’... failed + ``` + +* checking installed package size ... NOTE + ``` + installed size is 11.6Mb + sub-directories of 1Mb or more: + doc 9.1Mb + libs 1.6Mb + ``` + +# fmesher + +
+ +* Version: 0.1.5 +* GitHub: https://github.com/inlabru-org/fmesher +* Source code: https://github.com/cran/fmesher +* Date/Publication: 2023-12-20 21:50:08 UTC +* Number of recursive dependencies: 94 + +Run `revdepcheck::cloud_details(, "fmesher")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘fmesher-Ex.R’ failed + The error most likely occurred in: + + > ### Name: fm_int + > ### Title: Multi-domain integration + > ### Aliases: fm_int fm_int.list fm_int.numeric fm_int.character + > ### fm_int.factor fm_int.SpatRaster fm_int.fm_lattice_2d + > ### fm_int.fm_mesh_1d fm_int.fm_mesh_2d fm_int.inla.mesh.lattice + > ### fm_int.inla.mesh.1d fm_int.inla.mesh + > + ... + + geom_sf(data = fm_as_sfc(fmexample$mesh, multi = TRUE), alpha = 0.5) + + + geom_sf(data = fmexample$boundary_sf[[1]], fill = "red", alpha = 0.5) + + + geom_sf(data = ips, aes(size = weight)) + + + scale_size_area() + + } + Warning: Using `as.character()` on a quosure is deprecated as of rlang 0.3.0. Please use + `as_label()` or `as_name()` instead. + This warning is displayed once every 8 hours. + Error: Unknown colour name: ~ + Execution halted + ``` + +## In both + +* checking installed package size ... NOTE + ``` + installed size is 16.7Mb + sub-directories of 1Mb or more: + libs 14.1Mb + ``` + +# forestecology + +
+ +* Version: 0.2.0 +* GitHub: https://github.com/rudeboybert/forestecology +* Source code: https://github.com/cran/forestecology +* Date/Publication: 2021-10-02 13:30:05 UTC +* Number of recursive dependencies: 102 + +Run `revdepcheck::cloud_details(, "forestecology")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘forestecology-Ex.R’ failed + The error most likely occurred in: + + > ### Name: add_buffer_variable + > ### Title: Identify trees in the buffer region + > ### Aliases: add_buffer_variable + > + > ### ** Examples + > + > library(tibble) + ... + 17. └─ggplot2 (local) FUN(X[[i]], ...) + 18. └─g$draw_key(data, g$params, key_size) + 19. └─ggplot2 (local) draw_key(...) + 20. └─ggplot2::draw_key_point(data, params, size) + 21. ├─grid::pointsGrob(...) + 22. │ └─grid::grob(...) + 23. └─ggplot2::ggpar(...) + 24. └─rlang:::Ops.quosure(pointsize, .pt) + 25. └─rlang::abort(...) + Execution halted + ``` + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘forestecology.Rmd’ + ... + + > ggplot() + geom_sf(data = census_1_ex %>% sf::st_as_sf(coords = c("gx", + + "gy")), aes(col = sp, size = dbh)) + Warning: Using `as.character()` on a quosure is deprecated as of rlang 0.3.0. Please use + `as_label()` or `as_name()` instead. + This warning is displayed once every 8 hours. + + When sourcing ‘forestecology.R’: + Error: Unknown colour name: ~ + Execution halted + + ‘forestecology.Rmd’ using ‘UTF-8’... failed + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + ... + --- re-building ‘forestecology.Rmd’ using rmarkdown + + Quitting from lines at lines 64-69 [unnamed-chunk-3] (forestecology.Rmd) + Error: processing vignette 'forestecology.Rmd' failed with diagnostics: + Unknown colour name: ~ + --- failed re-building ‘forestecology.Rmd’ + + SUMMARY: processing the following file failed: + ‘forestecology.Rmd’ + + Error: Vignette re-building failed. + Execution halted + ``` + +## In both + +* checking dependencies in R code ... NOTE + ``` + Namespaces in Imports field not imported from: + ‘blockCV’ ‘patchwork’ + All declared Imports should be used. + ``` + +# frailtyEM + +
+ +* Version: 1.0.1 +* GitHub: https://github.com/tbalan/frailtyEM +* Source code: https://github.com/cran/frailtyEM +* Date/Publication: 2019-09-22 13:00:10 UTC +* Number of recursive dependencies: 78 + +Run `revdepcheck::cloud_details(, "frailtyEM")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘frailtyEM-Ex.R’ failed + The error most likely occurred in: + + > ### Name: summary.emfrail + > ### Title: Summary for 'emfrail' objects + > ### Aliases: summary.emfrail + > + > ### ** Examples + > + > data("bladder") + ... + + The following object is masked from ‘package:graphics’: + + layout + + > ggplotly(pl2) + Error in compute_geom_2(..., self = self) : + argument "theme" is missing, with no default + Calls: ggplotly ... use_defaults -> eval_from_theme -> %||% -> calc_element + Execution halted + ``` + +## In both + +* checking LazyData ... NOTE + ``` + 'LazyData' is specified without a 'data' directory + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘frailtyEM_manual.Rnw’ using Sweave + Loading required package: survival + Loading required package: gridExtra + Warning: The `` argument of `guides()` cannot be `FALSE`. Use + "none" instead as of ggplot2 3.3.4. + Warning: Removed 2 rows containing missing values or values outside + the scale range (`geom_path()`). + Warning in data("kidney") : data set ‘kidney’ not found + Warning in emfrail(Surv(time, status) ~ age + sex + cluster(id), data = kidney, : + ... + l.179 \RequirePackage{grfext}\relax + ^^M + ! ==> Fatal error occurred, no output PDF file produced! + --- failed re-building ‘frailtyEM_manual.Rnw’ + + SUMMARY: processing the following file failed: + ‘frailtyEM_manual.Rnw’ + + Error: Vignette re-building failed. + Execution halted + ``` + +# FuncNN + +
+ +* Version: 1.0 +* GitHub: https://github.com/b-thi/FuncNN +* Source code: https://github.com/cran/FuncNN +* Date/Publication: 2020-09-15 09:40:15 UTC +* Number of recursive dependencies: 170 + +Run `revdepcheck::cloud_details(, "FuncNN")` for more info + +
+ +## Newly broken + +* checking whether package ‘FuncNN’ can be installed ... WARNING + ``` + Found the following significant warnings: + Warning: replacing previous import ‘ggplot2::ggpar’ by ‘ggpubr::ggpar’ when loading ‘FuncNN’ + See ‘/tmp/workdir/FuncNN/new/FuncNN.Rcheck/00install.out’ for details. + ``` + +## In both + +* checking dependencies in R code ... NOTE + ``` + Namespace in Imports field not imported from: ‘foreach’ + All declared Imports should be used. + ``` + +# geomander + +
+ +* Version: 2.3.0 +* GitHub: https://github.com/christopherkenny/geomander +* Source code: https://github.com/cran/geomander +* Date/Publication: 2024-02-15 21:20:02 UTC +* Number of recursive dependencies: 124 + +Run `revdepcheck::cloud_details(, "geomander")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘geomander-Ex.R’ failed + The error most likely occurred in: + + > ### Name: geo_plot_group + > ### Title: Create Plots of Shapes by Group with Connected Components + > ### Colored + > ### Aliases: geo_plot_group + > + > ### ** Examples + > + ... + 15. └─ggplot2 (local) FUN(X[[i]], ...) + 16. └─base::lapply(...) + 17. └─ggplot2 (local) FUN(X[[i]], ...) + 18. └─g$draw_key(data, g$params, key_size) + 19. └─ggplot2 (local) draw_key(...) + 20. └─ggplot2::draw_key_polygon(data, params, size) + 21. └─rlang:::Summary.quosure(from_theme(thin), 1.524, na.rm = FALSE) + 22. └─rlang:::abort_quosure_op("Summary", .Generic) + 23. └─rlang::abort(...) + Execution halted + ``` + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘Redistricting_School_Districts.Rmd’ + ... + + fill = NA, lwd = 1.5) + + When sourcing ‘Redistricting_School_Districts.R’: + Error: Summary operations are not defined for quosures. Do you need to unquote + the quosure? + + # Bad: min(myquosure) + + # Good: min(!!myquosure) + Execution halted + + ‘Merging_Election_Data.Rmd’ using ‘UTF-8’... OK + ‘Redistricting_School_Districts.Rmd’ using ‘UTF-8’... failed + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘Merging_Election_Data.Rmd’ using rmarkdown + ``` + +## In both + +* checking installed package size ... NOTE + ``` + installed size is 8.3Mb + sub-directories of 1Mb or more: + data 3.3Mb + libs 4.1Mb + ``` + +# geomtextpath + +
+ +* Version: 0.1.3 +* GitHub: https://github.com/AllanCameron/geomtextpath +* Source code: https://github.com/cran/geomtextpath +* Date/Publication: 2024-03-12 16:30:03 UTC +* Number of recursive dependencies: 94 + +Run `revdepcheck::cloud_details(, "geomtextpath")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘geomtextpath-Ex.R’ failed + The error most likely occurred in: + + > ### Name: geom_textsf + > ### Title: Visualise sf objects with labels + > ### Aliases: geom_textsf geom_labelsf + > + > ### ** Examples + > + > ggplot(waterways) + + ... + 19. │ ├─rlang::inject(self$draw_panel(data, panel_params, coord, !!!params)) + 20. │ └─self$draw_panel(data, panel_params, coord, na.rm = FALSE, legend = "polygon") + 21. │ └─geomtextpath (local) draw_panel(...) + 22. │ └─geomtextpath:::sf_textgrob(...) + 23. └─base::.handleSimpleError(...) + 24. └─rlang (local) h(simpleError(msg, call)) + 25. └─handlers[[1L]](cnd) + 26. └─cli::cli_abort(...) + 27. └─rlang::abort(...) + Execution halted + ``` + +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(geomtextpath) + Loading required package: ggplot2 + > + > test_check("geomtextpath") + [ FAIL 1 | WARN 0 | SKIP 3 | PASS 465 ] + + ... + ══ Failed tests ════════════════════════════════════════════════════════════════ + ── Error ('test-sf.R:91:3'): We can make grobs from sf features ──────────────── + Error in `(x$boxlinewidth %||% defaults$linewidth[type_ind]) * 3.779528`: non-numeric argument to binary operator + Backtrace: + ▆ + 1. └─geomtextpath:::sf_textgrob(river, as_textbox = TRUE) at test-sf.R:91:3 + + [ FAIL 1 | WARN 0 | SKIP 3 | PASS 465 ] + Error: Test failures + Execution halted + ``` + +# germinationmetrics + +
+ +* Version: 0.1.8 +* GitHub: https://github.com/aravind-j/germinationmetrics +* Source code: https://github.com/cran/germinationmetrics +* Date/Publication: 2023-08-18 18:02:32 UTC +* Number of recursive dependencies: 92 + +Run `revdepcheck::cloud_details(, "germinationmetrics")` for more info + +
+ +## Newly broken + +* checking re-building of vignette outputs ... ERROR + ``` + Error(s) in re-building vignettes: + ... + --- re-building ‘Introduction.Rmd’ using rmarkdown_notangle + ! Undefined control sequence. + l.108 \NewDocumentCommand + \citeproctext{}{} + + Error: processing vignette 'Introduction.Rmd' failed with diagnostics: + LaTeX failed to compile /tmp/workdir/germinationmetrics/new/germinationmetrics.Rcheck/vign_test/germinationmetrics/vignettes/Introduction.tex. See https://yihui.org/tinytex/r/#debugging for debugging tips. See Introduction.log for more info. + --- failed re-building ‘Introduction.Rmd’ + + SUMMARY: processing the following file failed: + ‘Introduction.Rmd’ + + Error: Vignette re-building failed. + Execution halted + ``` + +## Newly fixed + +* checking re-building of vignette outputs ... WARNING + ``` + Error(s) in re-building vignettes: + --- re-building ‘Introduction.Rmd’ using rmarkdown_notangle + Trying to upgrade TinyTeX automatically now... + If reinstallation fails, try install_tinytex() again. Then install the following packages: + + tinytex::tlmgr_install(c("amscls", "amsfonts", "amsmath", "atbegshi", "atveryend", "auxhook", "babel", "bibtex", "bigintcalc", "bitset", "booktabs", "cm", "ctablestack", "dehyph", "dvipdfmx", "dvips", "ec", "epstopdf-pkg", "etex", "etexcmds", "etoolbox", "euenc", "everyshi", "fancyvrb", "filehook", "firstaid", "float", "fontspec", "framed", "geometry", "gettitlestring", "glyphlist", "graphics", "graphics-cfg", "graphics-def", "helvetic", "hycolor", "hyperref", "hyph-utf8", "hyphen-base", "iftex", "inconsolata", "infwarerr", "intcalc", "knuth-lib", "kpathsea", "kvdefinekeys", "kvoptions", "kvsetkeys", "l3backend", "l3kernel", "l3packages", "latex", "latex-amsmath-dev", "latex-bin", "latex-fonts", "latex-tools-dev", "latexconfig", "latexmk", "letltxmacro", "lm", "lm-math", "ltxcmds", "lua-alt-getopt", "lua-uni-algos", "luahbtex", "lualatex-math", "lualibs", "luaotfload", "luatex", "luatexbase", "mdwtools", "metafont", "mfware", "modes", "natbib", "pdfescape", "pdftex", "pdftexcmds", "plain", "psnfss", "refcount", "rerunfilecheck", "scheme-infraonly", "selnolig", "stringenc", "symbol", "tex", "tex-ini-files", "texlive-scripts", "texlive.infra", "times", "tipa", "tools", "unicode-data", "unicode-math", "uniquecounter", "url", "xcolor", "xetex", "xetexconfig", "xkeyval", "xunicode", "zapfding")) + + The directory /opt/TinyTeX/texmf-local is not empty. It will be backed up to /tmp/RtmpSUduR6/filefb36377d31c and restored later. + + tlmgr: no auxiliary texmf trees defined, so nothing removed + ... + + Error: processing vignette 'Introduction.Rmd' failed with diagnostics: + LaTeX failed to compile /tmp/workdir/germinationmetrics/old/germinationmetrics.Rcheck/vign_test/germinationmetrics/vignettes/Introduction.tex. See https://yihui.org/tinytex/r/#debugging for debugging tips. See Introduction.log for more info. + --- failed re-building ‘Introduction.Rmd’ + + SUMMARY: processing the following file failed: + ‘Introduction.Rmd’ + + Error: Vignette re-building failed. + Execution halted + ``` + +# gganimate + +
+ +* Version: 1.0.9 +* GitHub: https://github.com/thomasp85/gganimate +* Source code: https://github.com/cran/gganimate +* Date/Publication: 2024-02-27 14:00:03 UTC +* Number of recursive dependencies: 97 + +Run `revdepcheck::cloud_details(, "gganimate")` for more info + +
+ +## Newly broken + +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(gganimate) + Loading required package: ggplot2 + > + > test_check("gganimate") + [ FAIL 6 | WARN 0 | SKIP 1 | PASS 0 ] + + ... + 26. │ └─ggplot2::calc_element("geom", theme) + 27. └─base::.handleSimpleError(...) + 28. └─rlang (local) h(simpleError(msg, call)) + 29. └─handlers[[1L]](cnd) + 30. └─cli::cli_abort(...) + 31. └─rlang::abort(...) + + [ FAIL 6 | WARN 0 | SKIP 1 | PASS 0 ] + Error: Test failures + Execution halted + ``` + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘gganimate.Rmd’ + ... + + state_length = 1) + + > anim + + When sourcing ‘gganimate.R’: + Error: Problem while setting up geom aesthetics. + ℹ Error occurred in the 1st layer. + Caused by error in `compute_geom_2()`: + ! argument "theme" is missing, with no default + Execution halted + + ‘gganimate.Rmd’ using ‘UTF-8’... failed + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘gganimate.Rmd’ using rmarkdown + ``` + +# ggautomap + +
+ +* Version: 0.3.2 +* GitHub: https://github.com/cidm-ph/ggautomap +* Source code: https://github.com/cran/ggautomap +* Date/Publication: 2023-05-24 09:00:02 UTC +* Number of recursive dependencies: 73 + +Run `revdepcheck::cloud_details(, "ggautomap")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘ggautomap-Ex.R’ failed + The error most likely occurred in: + + > ### Name: geom_centroids + > ### Title: Geographic centroid of locations + > ### Aliases: geom_centroids + > + > ### ** Examples + > + > library(ggplot2) + ... + > cartographer::nc_type_example_2 |> + + head(n = 100) |> + + ggplot(aes(location = county)) + + + geom_boundaries(feature_type = "sf.nc") + + + geom_centroids(aes(colour = type), position = position_circle_repel_sf(scale = 6), size = 0.5) + + + coord_automap(feature_type = "sf.nc") + Error in valid.pch(x$pch) : + 'language' object cannot be coerced to type 'integer' + Calls: ... validGrob.grob -> validDetails -> validDetails.points -> valid.pch + Execution halted + ``` + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘ggautomap.Rmd’ + ... + 5 2768 Blacktown Western Sydney 2021 A + 6 2766 Blacktown Western Sydney 2021 B + + > covid_cases_nsw %>% ggplot(aes(location = lga)) + + + geom_boundaries(feature_type = "nswgeo.lga") + geom_geoscatter(aes(colour = type), + + s .... [TRUNCATED] + + When sourcing ‘ggautomap.R’: + Error: 'language' object cannot be coerced to type 'integer' + Execution halted + + ‘ggautomap.Rmd’ using ‘UTF-8’... failed + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + ... + --- re-building ‘ggautomap.Rmd’ using rmarkdown + + Quitting from lines at lines 47-54 [scatter] (ggautomap.Rmd) + Error: processing vignette 'ggautomap.Rmd' failed with diagnostics: + 'language' object cannot be coerced to type 'integer' + --- failed re-building ‘ggautomap.Rmd’ + + SUMMARY: processing the following file failed: + ‘ggautomap.Rmd’ + + Error: Vignette re-building failed. + Execution halted + ``` + +# ggdark + +
+ +* Version: 0.2.1 +* GitHub: NA +* Source code: https://github.com/cran/ggdark +* Date/Publication: 2019-01-11 17:30:06 UTC +* Number of recursive dependencies: 46 + +Run `revdepcheck::cloud_details(, "ggdark")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘ggdark-Ex.R’ failed + The error most likely occurred in: + + > ### Name: dark_mode + > ### Title: Activate dark mode on a 'ggplot2' theme + > ### Aliases: dark_mode + > + > ### ** Examples + > + > library(ggplot2) + ... + > + > p1 <- ggplot(iris, aes(Sepal.Width, Sepal.Length, color = Species)) + + + geom_point() + > + > p1 # theme returned by theme_get() + > p1 + dark_mode() # activate dark mode on theme returned by theme_get() + Error in match(x, table, nomatch = 0L) : + 'match' requires vector arguments + Calls: dark_mode -> %in% + Execution halted + ``` + +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(ggdark) + > + > test_check("ggdark") + [ FAIL 1 | WARN 0 | SKIP 0 | PASS 0 ] + + ══ Failed tests ════════════════════════════════════════════════════════════════ + ... + ── Error ('test_dark_mode.R:10:1'): (code run outside of `test_that()`) ──────── + Error in `match(x, table, nomatch = 0L)`: 'match' requires vector arguments + Backtrace: + ▆ + 1. └─ggdark::dark_mode(light_theme) at test_dark_mode.R:10:1 + 2. └─geoms[["GeomPoint"]]$default_aes$colour %in% ... + + [ FAIL 1 | WARN 0 | SKIP 0 | PASS 0 ] + Error: Test failures + Execution halted + ``` + +## In both + +* checking LazyData ... NOTE + ``` + 'LazyData' is specified without a 'data' directory + ``` + +# ggdist + +
+ +* Version: 3.3.2 +* GitHub: https://github.com/mjskay/ggdist +* Source code: https://github.com/cran/ggdist +* Date/Publication: 2024-03-05 05:30:23 UTC +* Number of recursive dependencies: 127 + +Run `revdepcheck::cloud_details(, "ggdist")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘ggdist-Ex.R’ failed + The error most likely occurred in: + + > ### Name: Pr_ + > ### Title: Probability expressions in ggdist aesthetics + > ### Aliases: Pr_ p_ + > + > ### ** Examples + > + > library(ggplot2) + ... + 2.75, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 1, NULL, NULL, NULL, c(0, 2.2, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, NULL, c(0, 0, 0, 2.2 + ), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0.5, NULL, NULL, NULL, c(0, 2.2, 0, 2.2), NULL, TRUE), list("grey20", NULL, NULL, NULL, FALSE, TRUE), NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 2.75, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 0.75, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, list(), NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, list(NULL, NA, NULL, NULL, TRUE), c(5.5, 5.5, 5.5, 5.5), 11, NULL, NULL, NULL, 1.2, NULL, NULL, 5.5, + NULL, NULL, NULL, NULL, 0.2, NULL, list(NULL, NULL, NULL, 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, NULL, NULL, NULL, TRUE), NULL, "right", NULL, NULL, NULL, "center", NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, c(0, 0, 0, 0), list(), 11, list("grey92", NA, NULL, NULL, TRUE), list(), 5.5, NULL, NULL, list("white", NULL, NULL, NULL, FALSE, TRUE), NULL, list(NULL, 0.5, NULL, NULL, FALSE, TRUE), NULL, NULL, NULL, NULL, FALSE, list(NULL, + "white", NULL, NULL, TRUE), list(NULL, NULL, NULL, 1.2, 0, 1, NULL, NULL, c(0, 0, 5.5, 0), NULL, TRUE), "panel", list(NULL, NULL, NULL, NULL, 0, 1, NULL, NULL, c(0, 0, 5.5, 0), NULL, TRUE), list(NULL, NULL, NULL, 0.8, 1, 1, NULL, NULL, c(5.5, 0, 0, 0), NULL, TRUE), "panel", list(NULL, NULL, NULL, 1.2, 0.5, 0.5, NULL, NULL, NULL, NULL, TRUE), "topleft", NULL, c(5.5, 5.5, 5.5, 5.5), list("grey85", NA, NULL, NULL, TRUE), NULL, NULL, "inherit", "inside", list(NULL, NULL, "grey10", 0.8, NULL, + NULL, NULL, NULL, c(4.4, 4.4, 4.4, 4.4), NULL, TRUE), NULL, NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, NULL, -90, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, NULL, 90, NULL, NULL, NULL, TRUE), NULL, 2.75, 2.75)) + Error in use_defaults(..., self = self) : + unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), NULL, list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.75, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, 90, NULL, c(0, + 2.75, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 1, NULL, NULL, NULL, c(0, 2.2, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL + Calls: ... .handleSimpleError -> h -> -> + Execution halted + ``` + +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > # This file is part of the standard setup for testthat. + > # It is recommended that you do not modify it. + > # + > # Where should you do additional test configuration? + > # Learn more about the roles of various files in: + > # * https://r-pkgs.org/testing-design.html#sec-tests-files-overview + > # * https://testthat.r-lib.org/articles/special-files.html + ... + • test.stat_sample_slabinterval/nas-with-na-rm-true.svg + • test.subguide/dots-subguide-with-side-vertical.svg + • test.subguide/integer-subguide-with-zero-range.svg + • test.subguide/slab-subguide-with-inside-labels-vertical.svg + • test.subguide/slab-subguide-with-outside-labels-vert.svg + • test.subguide/slab-subguide-with-outside-labels.svg + • test.subguide/slab-subguide-with-side-vertical.svg + • test.theme_ggdist/facet-titles-on-left.svg + Error: Test failures + Execution halted + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘dotsinterval.Rmd’ using rmarkdown + Warning in hook_png(..., cmd = "pngquant", post_process = function(x) { : + cannot find pngquant; please install and put it in PATH + Warning in hook_png(..., cmd = "pngquant", post_process = function(x) { : + cannot find pngquant; please install and put it in PATH + + Quitting from lines at lines 49-161 [dotsinterval_components] (dotsinterval.Rmd) + Error: processing vignette 'dotsinterval.Rmd' failed with diagnostics: + Problem while setting up geom aesthetics. + ... + + --- re-building ‘freq-uncertainty-vis.Rmd’ using rmarkdown + Warning in hook_png(..., cmd = "pngquant", post_process = function(x) { : + cannot find pngquant; please install and put it in PATH + Warning in hook_png(..., cmd = "pngquant", post_process = function(x) { : + cannot find pngquant; please install and put it in PATH + Warning in hook_png(..., cmd = "pngquant", post_process = function(x) { : + cannot find pngquant; please install and put it in PATH + Warning in hook_png(..., cmd = "pngquant", post_process = function(x) { : + cannot find pngquant; please install and put it in PATH + ``` + +## In both + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘dotsinterval.Rmd’ + ... + + xdist = dist)) + geom_hline(yintercept = 0:1, color = "gray95") + + + stat_dotsin .... [TRUNCATED] + + When sourcing ‘dotsinterval.R’: + Error: Problem while setting up geom aesthetics. + ℹ Error occurred in the 2nd layer. + Caused by error in `use_defaults()`: + ... + ℹ Error occurred in the 1st layer. + Caused by error in `use_defaults()`: + ! unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), NULL, list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(7, 0, 0, 0), NULL, FALSE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, 90, NULL, c(0, 7, + 0, 0), NULL, FALSE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(NULL, NULL, + Execution halted + + ‘dotsinterval.Rmd’ using ‘UTF-8’... failed + ‘freq-uncertainty-vis.Rmd’ using ‘UTF-8’... failed + ‘lineribbon.Rmd’ using ‘UTF-8’... failed + ‘slabinterval.Rmd’ using ‘UTF-8’... failed + ``` + +* checking installed package size ... NOTE + ``` + installed size is 5.6Mb + sub-directories of 1Mb or more: + doc 1.3Mb + help 2.0Mb + libs 1.0Mb + ``` + +# ggedit + +
+ +* Version: 0.4.1 +* GitHub: https://github.com/yonicd/ggedit +* Source code: https://github.com/cran/ggedit +* Date/Publication: 2024-03-04 14:40:02 UTC +* Number of recursive dependencies: 95 + +Run `revdepcheck::cloud_details(, "ggedit")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘ggedit-Ex.R’ failed + The error most likely occurred in: + + > ### Name: dput.ggedit + > ### Title: Convert ggplot object to a string call + > ### Aliases: dput.ggedit + > + > ### ** Examples + > + > + ... + 10. │ │ │ └─base (local) doTryCatch(return(expr), name, parentenv, handler) + 11. │ │ └─base::withCallingHandlers(...) + 12. │ └─ggplot2 (local) f(l = layers[[i]], d = data[[i]]) + 13. │ └─l$compute_geom_2(d, theme = plot$theme) + 14. └─base::.handleSimpleError(...) + 15. └─rlang (local) h(simpleError(msg, call)) + 16. └─handlers[[1L]](cnd) + 17. └─cli::cli_abort(...) + 18. └─rlang::abort(...) + Execution halted + ``` + +# ggfixest + +
+ +* Version: 0.1.0 +* GitHub: https://github.com/grantmcdermott/ggfixest +* Source code: https://github.com/cran/ggfixest +* Date/Publication: 2023-12-14 08:00:06 UTC +* Number of recursive dependencies: 78 + +Run `revdepcheck::cloud_details(, "ggfixest")` for more info + +
+ +## Newly broken + +* checking tests ... ERROR + ``` + Running ‘tinytest.R’ + Running the tests in ‘tests/tinytest.R’ failed. + Complete output: + > ## Throttle CPU threads if R CMD check (for CRAN) + > + > if (any(grepl("_R_CHECK", names(Sys.getenv()), fixed = TRUE))) { + + # fixest + + if (requireNamespace("fixest", quietly = TRUE)) { + + library(fixest) + + setFixest_nthreads(1) + ... + test_nthreads.R............... 0 tests ----- FAILED[]: test_ggiplot.R<52--52> + call| expect_snapshot_plot(p3, label = "ggiplot_simple_ribbon") + diff| 84719 + info| Diff plot saved to: _tinysnapshot_review/ggiplot_simple_ribbon.png + ----- FAILED[]: test_ggiplot.R<54--54> + call| expect_snapshot_plot(p5, label = "ggiplot_simple_mci_ribbon") + diff| 84507 + info| Diff plot saved to: _tinysnapshot_review/ggiplot_simple_mci_ribbon.png + Error: 2 out of 101 tests failed + Execution halted + ``` + +## In both + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘ggiplot.Rmd’ + ... + > iplot(list(TWFE = est_twfe_grp, `Sun & Abraham (2020)` = est_sa20_grp), + + ref.line = -1, main = "Staggered treatment: Split mutli-sample") + The degrees of freedom for the t distribution could not be deduced. Using a Normal distribution instead. + Note that you can provide the argument `df.t` directly. + + When sourcing ‘ggiplot.R’: + Error: in iplot(list(TWFE = est_twfe_grp, `Sun & Abraham (2...: + The 1st element of 'object' raises and error: + Error in nb * sd : non-numeric argument to binary operator + Execution halted + + ‘ggiplot.Rmd’ using ‘UTF-8’... failed + ``` + +# ggfortify + +
+ +* Version: 0.4.17 +* GitHub: https://github.com/sinhrks/ggfortify +* Source code: https://github.com/cran/ggfortify +* Date/Publication: 2024-04-17 04:30:04 UTC +* Number of recursive dependencies: 125 + +Run `revdepcheck::cloud_details(, "ggfortify")` for more info + +
+ +## Newly broken + +* checking tests ... ERROR + ``` + Running ‘test-all.R’ + Running the tests in ‘tests/test-all.R’ failed. + Complete output: + > library(testthat) + > + > suppressWarnings(RNGversion("3.5.0")) + > set.seed(1, sample.kind = "Rejection") + > + > test_check('ggfortify') + Loading required package: ggfortify + ... + + x[3]: "#595959FF" + y[3]: "grey35" + + x[4]: "#595959FF" + y[4]: "grey35" + + [ FAIL 5 | WARN 12 | SKIP 48 | PASS 734 ] + Error: Test failures + Execution halted + ``` + # ggh4x
-* Version: 0.2.8 -* GitHub: https://github.com/teunbrand/ggh4x -* Source code: https://github.com/cran/ggh4x -* Date/Publication: 2024-01-23 21:00:02 UTC -* Number of recursive dependencies: 77 +* Version: 0.2.8 +* GitHub: https://github.com/teunbrand/ggh4x +* Source code: https://github.com/cran/ggh4x +* Date/Publication: 2024-01-23 21:00:02 UTC +* Number of recursive dependencies: 77 + +Run `revdepcheck::cloud_details(, "ggh4x")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘ggh4x-Ex.R’ failed + The error most likely occurred in: + + > ### Name: facet_nested_wrap + > ### Title: Ribbon of panels with nested strips. + > ### Aliases: facet_nested_wrap + > + > ### ** Examples + > + > # A standard plot + ... + 6. │ └─ggplot2 (local) setup(..., self = self) + 7. │ └─self$facet$compute_layout(data, self$facet_params) + 8. │ └─ggplot2 (local) compute_layout(..., self = self) + 9. │ └─ggplot2:::wrap_layout(id, dims, params$dir) + 10. │ └─ggplot2:::data_frame0(...) + 11. │ └─vctrs::data_frame(..., .name_repair = "minimal") + 12. └─vctrs:::stop_recycle_incompatible_size(...) + 13. └─vctrs:::stop_vctrs(...) + 14. └─rlang::abort(message, class = c(class, "vctrs_error"), ..., call = call) + Execution halted + ``` + +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(ggh4x) + Loading required package: ggplot2 + > + > test_check("ggh4x") + [ FAIL 9 | WARN 1 | SKIP 18 | PASS 719 ] + + ... + 11. │ └─ggplot2:::wrap_layout(id, dims, params$dir) + 12. │ └─ggplot2:::data_frame0(...) + 13. │ └─vctrs::data_frame(..., .name_repair = "minimal") + 14. └─vctrs:::stop_recycle_incompatible_size(...) + 15. └─vctrs:::stop_vctrs(...) + 16. └─rlang::abort(message, class = c(class, "vctrs_error"), ..., call = call) + + [ FAIL 9 | WARN 1 | SKIP 18 | PASS 719 ] + Error: Test failures + Execution halted + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘Facets.Rmd’ using rmarkdown + + Quitting from lines at lines 33-39 [wrap_mimick] (Facets.Rmd) + Error: processing vignette 'Facets.Rmd' failed with diagnostics: + Can't recycle `ROW` (size 0) to size 7. + --- failed re-building ‘Facets.Rmd’ + + --- re-building ‘Miscellaneous.Rmd’ using rmarkdown + ``` + +## In both + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘Facets.Rmd’ + ... + Loading required package: ggplot2 + + > p <- ggplot(mpg, aes(displ, hwy, colour = as.factor(cyl))) + + + geom_point() + labs(x = "Engine displacement", y = "Highway miles per gallon") + .... [TRUNCATED] + + > p + facet_wrap2(vars(class)) + + ... + ℹ Error occurred in the 1st layer. + Caused by error in `setup_params()`: + ! A discrete 'nbinom' distribution cannot be fitted to continuous data. + Execution halted + + ‘Facets.Rmd’ using ‘UTF-8’... failed + ‘Miscellaneous.Rmd’ using ‘UTF-8’... failed + ‘PositionGuides.Rmd’ using ‘UTF-8’... OK + ‘Statistics.Rmd’ using ‘UTF-8’... failed + ‘ggh4x.Rmd’ using ‘UTF-8’... OK + ``` + +# ggheatmap + +
+ +* Version: 2.2 +* GitHub: NA +* Source code: https://github.com/cran/ggheatmap +* Date/Publication: 2022-09-10 13:32:55 UTC +* Number of recursive dependencies: 127 + +Run `revdepcheck::cloud_details(, "ggheatmap")` for more info + +
+ +## Newly broken + +* checking whether package ‘ggheatmap’ can be installed ... WARNING + ``` + Found the following significant warnings: + Warning: replacing previous import ‘ggplot2::ggpar’ by ‘ggpubr::ggpar’ when loading ‘ggheatmap’ + See ‘/tmp/workdir/ggheatmap/new/ggheatmap.Rcheck/00install.out’ for details. + ``` + +# gghighlight + +
+ +* Version: 0.4.1 +* GitHub: https://github.com/yutannihilation/gghighlight +* Source code: https://github.com/cran/gghighlight +* Date/Publication: 2023-12-16 01:00:02 UTC +* Number of recursive dependencies: 85 + +Run `revdepcheck::cloud_details(, "gghighlight")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘gghighlight-Ex.R’ failed + The error most likely occurred in: + + > ### Name: gghighlight + > ### Title: Highlight Data With Predicate + > ### Aliases: gghighlight + > + > ### ** Examples + > + > d <- data.frame( + ... + 8. │ ├─purrr:::with_indexed_errors(...) + 9. │ │ └─base::withCallingHandlers(...) + 10. │ ├─purrr:::call_with_cleanup(...) + 11. │ └─gghighlight (local) .f(.x[[i]], .y[[i]], ...) + 12. │ └─gghighlight:::get_default_aes_param(nm, layer$geom, layer$mapping) + 13. └─base::.handleSimpleError(...) + 14. └─purrr (local) h(simpleError(msg, call)) + 15. └─cli::cli_abort(...) + 16. └─rlang::abort(...) + Execution halted + ``` + +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(gghighlight) + Loading required package: ggplot2 + > + > test_check("gghighlight") + label_key: type + label_key: type + ... + 15. └─cli::cli_abort(...) + 16. └─rlang::abort(...) + + [ FAIL 2 | WARN 2 | SKIP 1 | PASS 178 ] + Deleting unused snapshots: + • vdiffr/simple-bar-chart-with-facet.svg + • vdiffr/simple-line-chart.svg + • vdiffr/simple-point-chart.svg + Error: Test failures + Execution halted + ``` + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘gghighlight.Rmd’ + ... + + 0, label_key = type) + Warning in is.na(non_null_default_aes[[aes_param_name]]) : + is.na() applied to non-(list or vector) of type 'language' + + When sourcing ‘gghighlight.R’: + Error: ℹ In index: 1. + Caused by error in `aes_param_name %in% names(non_null_default_aes) && is.na(non_null_default_aes[[ + aes_param_name]])`: + ! 'length = 2' in coercion to 'logical(1)' + Execution halted + + ‘gghighlight.Rmd’ using ‘UTF-8’... failed + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘gghighlight.Rmd’ using rmarkdown + ``` + +# ggiraph + +
+ +* Version: 0.8.9 +* GitHub: https://github.com/davidgohel/ggiraph +* Source code: https://github.com/cran/ggiraph +* Date/Publication: 2024-02-24 16:20:13 UTC +* Number of recursive dependencies: 95 + +Run `revdepcheck::cloud_details(, "ggiraph")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘ggiraph-Ex.R’ failed + The error most likely occurred in: + + > ### Name: geom_sf_interactive + > ### Title: Create interactive sf objects + > ### Aliases: geom_sf_interactive geom_sf_label_interactive + > ### geom_sf_text_interactive + > + > ### ** Examples + > + ... + + x <- girafe( ggobj = gg) + + if( interactive() ) print(x) + + } + Warning in CPL_crs_from_input(x) : + GDAL Message 1: +init=epsg:XXXX syntax is deprecated. It might return a CRS with a non-EPSG compliant axis order. + Warning: Using `as.character()` on a quosure is deprecated as of rlang 0.3.0. Please use + `as_label()` or `as_name()` instead. + This warning is displayed once every 8 hours. + Error: Unknown colour name: ~ + Execution halted + ``` + +* checking tests ... ERROR + ``` + Running ‘tinytest.R’ + Running the tests in ‘tests/tinytest.R’ failed. + Complete output: + > if (requireNamespace("tinytest", quietly = TRUE)) { + + tinytest::test_package("ggiraph") + + } + + test-annotate_interactive.R... 0 tests + test-annotate_interactive.R... 0 tests + test-annotate_interactive.R... 0 tests + ... + test-utils.R.................. 7 tests 1 fails + test-utils.R.................. 8 tests 1 fails + test-utils.R.................. 11 tests 1 fails Error in as.data.frame.default(x[[i]], optional = TRUE) : + cannot coerce class 'c("quosure", "formula")' to a data.frame + Calls: ... -> as.data.frame -> as.data.frame.default + In addition: Warning message: + 'ggiraph' is deprecated. + Use 'girafe' instead. + See help("Deprecated") + Execution halted + ``` + +## In both + +* checking installed package size ... NOTE + ``` + installed size is 11.9Mb + sub-directories of 1Mb or more: + libs 9.5Mb + ``` + +# ggmice + +
+ +* Version: 0.1.0 +* GitHub: https://github.com/amices/ggmice +* Source code: https://github.com/cran/ggmice +* Date/Publication: 2023-08-07 14:20:02 UTC +* Number of recursive dependencies: 121 + +Run `revdepcheck::cloud_details(, "ggmice")` for more info + +
+ +## Newly broken + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘old_friends.Rmd’ + ... + layout + + + > p <- plot_flux(dat) + + > ggplotly(p) + + When sourcing ‘old_friends.R’: + Error: argument "theme" is missing, with no default + Execution halted + + ‘ggmice.Rmd’ using ‘UTF-8’... OK + ‘old_friends.Rmd’ using ‘UTF-8’... failed + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘ggmice.Rmd’ using rmarkdown + ``` + +# ggmulti + +
+ +* Version: 1.0.7 +* GitHub: NA +* Source code: https://github.com/cran/ggmulti +* Date/Publication: 2024-04-09 09:40:05 UTC +* Number of recursive dependencies: 126 + +Run `revdepcheck::cloud_details(, "ggmulti")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘ggmulti-Ex.R’ failed + The error most likely occurred in: + + > ### Name: coord_radial + > ### Title: Radial axes + > ### Aliases: coord_radial + > + > ### ** Examples + > + > if(require("dplyr")) { + ... + 2.75, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 1, NULL, NULL, NULL, c(0, 2.2, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, NULL, c(0, 0, 0, 2.2 + ), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0.5, NULL, NULL, NULL, c(0, 2.2, 0, 2.2), NULL, TRUE), list("grey20", NULL, NULL, NULL, FALSE, TRUE), NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 2.75, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 0.75, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, list(), NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, list(NULL, NA, NULL, NULL, TRUE), c(5.5, 5.5, 5.5, 5.5), 11, NULL, NULL, NULL, 1.2, NULL, NULL, 5.5, + NULL, NULL, NULL, NULL, 0.2, NULL, list(NULL, NULL, NULL, 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, NULL, NULL, NULL, TRUE), NULL, "right", NULL, NULL, NULL, "center", NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, c(0, 0, 0, 0), list(), 11, list("grey92", NA, NULL, NULL, TRUE), list(), 5.5, NULL, NULL, list("white", NULL, NULL, NULL, FALSE, TRUE), NULL, list(NULL, 0.5, NULL, NULL, FALSE, TRUE), NULL, NULL, NULL, NULL, FALSE, list(NULL, + "white", NULL, NULL, TRUE), list(NULL, NULL, NULL, 1.2, 0, 1, NULL, NULL, c(0, 0, 5.5, 0), NULL, TRUE), "panel", list(NULL, NULL, NULL, NULL, 0, 1, NULL, NULL, c(0, 0, 5.5, 0), NULL, TRUE), list(NULL, NULL, NULL, 0.8, 1, 1, NULL, NULL, c(5.5, 0, 0, 0), NULL, TRUE), "panel", list(NULL, NULL, NULL, 1.2, 0.5, 0.5, NULL, NULL, NULL, NULL, TRUE), "topleft", NULL, c(5.5, 5.5, 5.5, 5.5), list("grey85", NA, NULL, NULL, TRUE), NULL, NULL, "inherit", "inside", list(NULL, NULL, "grey10", 0.8, NULL, + NULL, NULL, NULL, c(4.4, 4.4, 4.4, 4.4), NULL, TRUE), NULL, NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, NULL, -90, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, NULL, 90, NULL, NULL, NULL, TRUE), NULL, 2.75, 2.75)) + Error in use_defaults(..., self = self) : + unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), NULL, list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.75, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, 90, NULL, c(0, + 2.75, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 1, NULL, NULL, NULL, c(0, 2.2, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL + Calls: ... .handleSimpleError -> h -> -> + Execution halted + ``` + +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > + > + > library(testthat) + > library(ggmulti) + Loading required package: ggplot2 + + Attaching package: 'ggmulti' + ... + 24. │ │ └─base::withCallingHandlers(...) + 25. │ └─layer$geom$use_defaults(...) + 26. └─base::.handleSimpleError(...) + 27. └─rlang (local) h(simpleError(msg, call)) + 28. └─handlers[[1L]](cnd) + 29. └─layer$geom$use_defaults(...) + + [ FAIL 4 | WARN 3 | SKIP 0 | PASS 30 ] + Error: Test failures + Execution halted + ``` + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘glyph.Rmd’ + ... + + Sepal.Width, colour = Species), serialaxes.data = iris, axes.layout = "radia ..." ... [TRUNCATED] + + When sourcing ‘glyph.R’: + Error: Base operators are not defined for quosures. Do you need to unquote the + quosure? + + # Bad: myquosure / rhs + ... + 0, 0, 0), NULL, TRUE), "panel", list(NULL, NULL, NULL, 1.2, 0.5, 0.5, NULL, NULL, NULL, NULL, TRUE), "topleft", NULL, c(5, 12, 5, 12), list("grey85", NA, NULL, NULL, TRUE), NULL, NULL, "inherit", "inside", list(NULL, NULL, "grey10", 0.8, NULL, NULL, NULL, NULL, c(4.4, 4.4, 4.4, 4.4), NULL, TRUE), NULL, NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, NULL, -90, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, NULL, 90, NULL, NULL, NULL, TRUE), NULL, 2.75, 2.75)) + + When sourcing ‘highDim.R’: + Error: unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), NULL, list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), NULL, NULL, list(), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, + NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, NULL, c(0, 0, 0, 2.2), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0.5, NULL, NULL, NULL, c(0, 2.2, 0, 2.2), NULL, TRUE), list("grey20", NULL, NULL, NULL, FALSE, TRUE), NULL, NULL, NULL, list(), NULL, NULL, N + Execution halted + + ‘glyph.Rmd’ using ‘UTF-8’... failed + ‘highDim.Rmd’ using ‘UTF-8’... failed + ‘histogram-density-.Rmd’ using ‘UTF-8’... OK + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘glyph.Rmd’ using rmarkdown + ``` + +# ggparallel + +
+ +* Version: 0.4.0 +* GitHub: https://github.com/heike/ggparallel +* Source code: https://github.com/cran/ggparallel +* Date/Publication: 2024-03-09 22:00:02 UTC +* Number of recursive dependencies: 51 + +Run `revdepcheck::cloud_details(, "ggparallel")` for more info + +
+ +## Newly broken + +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > # This file is part of the standard setup for testthat. + > # It is recommended that you do not modify it. + > # + > # Where should you do additional test configuration? + > # Learn more about the roles of various files in: + > # * https://r-pkgs.org/testing-design.html#sec-tests-files-overview + > # * https://testthat.r-lib.org/articles/special-files.html + ... + 11. │ └─l$compute_geom_2(d, theme = plot$theme) + 12. └─base::.handleSimpleError(...) + 13. └─rlang (local) h(simpleError(msg, call)) + 14. └─handlers[[1L]](cnd) + 15. └─cli::cli_abort(...) + 16. └─rlang::abort(...) + + [ FAIL 1 | WARN 0 | SKIP 0 | PASS 0 ] + Error: Test failures + Execution halted + ``` + +# ggplotlyExtra + +
+ +* Version: 0.0.1 +* GitHub: NA +* Source code: https://github.com/cran/ggplotlyExtra +* Date/Publication: 2019-12-02 16:20:06 UTC +* Number of recursive dependencies: 70 + +Run `revdepcheck::cloud_details(, "ggplotlyExtra")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘ggplotlyExtra-Ex.R’ failed + The error most likely occurred in: + + > ### Name: ggplotly_histogram + > ### Title: Clean 'ggplot2' Histogram to be Converted to 'Plotly' + > ### Aliases: ggplotly_histogram + > + > ### ** Examples + > + > + ... + `stat_bin()` using `bins = 30`. Pick better value with `binwidth`. + Warning in geom_bar(data = layerdata, mapping = aes(x = .data$x, y = .data$count, : + Ignoring unknown aesthetics: label1, label2, and label3 + > + > # convert `ggplot` object to `plotly` object + > ggplotly(p, tooltip = c("Range", "count", "density")) + Error in compute_geom_2(..., self = self) : + argument "theme" is missing, with no default + Calls: ggplotly ... use_defaults -> eval_from_theme -> %||% -> calc_element + Execution halted + ``` + +## In both + +* checking LazyData ... NOTE + ``` + 'LazyData' is specified without a 'data' directory + ``` + +# ggpol + +
+ +* Version: 0.0.7 +* GitHub: https://github.com/erocoar/ggpol +* Source code: https://github.com/cran/ggpol +* Date/Publication: 2020-11-08 13:40:02 UTC +* Number of recursive dependencies: 54 + +Run `revdepcheck::cloud_details(, "ggpol")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘ggpol-Ex.R’ failed + The error most likely occurred in: + + > ### Name: GeomConfmat + > ### Title: Confusion Matrix + > ### Aliases: GeomConfmat geom_confmat stat_confmat + > + > ### ** Examples + > + > x <- sample(LETTERS[seq(4)], 50, replace = TRUE) + ... + 21. │ └─ggpol (local) draw_panel(...) + 22. │ └─base::lapply(GeomText$default_aes[missing_aes], rlang::eval_tidy) + 23. │ └─rlang (local) FUN(X[[i]], ...) + 24. ├─ggplot2::from_theme(fontsize) + 25. └─base::.handleSimpleError(...) + 26. └─rlang (local) h(simpleError(msg, call)) + 27. └─handlers[[1L]](cnd) + 28. └─cli::cli_abort(...) + 29. └─rlang::abort(...) + Execution halted + ``` + +## In both + +* checking dependencies in R code ... NOTE + ``` + Namespaces in Imports field not imported from: + ‘dplyr’ ‘grDevices’ + All declared Imports should be used. + ``` + +* checking LazyData ... NOTE + ``` + 'LazyData' is specified without a 'data' directory + ``` + +# ggraph + +
+ +* Version: 2.2.1 +* GitHub: https://github.com/thomasp85/ggraph +* Source code: https://github.com/cran/ggraph +* Date/Publication: 2024-03-07 12:40:02 UTC +* Number of recursive dependencies: 115 + +Run `revdepcheck::cloud_details(, "ggraph")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘ggraph-Ex.R’ failed + The error most likely occurred in: + + > ### Name: geom_conn_bundle + > ### Title: Create hierarchical edge bundles between node connections + > ### Aliases: geom_conn_bundle geom_conn_bundle2 geom_conn_bundle0 + > + > ### ** Examples + > + > # Create a graph of the flare class system + ... + + ) + + + geom_node_point(aes(filter = leaf, colour = class)) + + + scale_edge_colour_distiller('', direction = 1, guide = 'edge_direction') + + + coord_fixed() + + + ggforce::theme_no_axes() + Error in get_layer_key(...) : + unused argument (list(list("black", 0.5, 1, "butt", FALSE, TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), NULL, list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), NULL, list(), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.75, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, 90, NULL, c(0, 2.75, + 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 1, NULL, NULL, NULL, c(0, 2.2, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, NULL, c(0, 0, 0, 2.2), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, + Calls: ... -> -> process_layers -> + Execution halted + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘Edges.Rmd’ using rmarkdown + ``` + +## In both + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘Edges.Rmd’ + ... + Warning in grid.Call.graphics(C_text, as.graphicsAnnot(x$label), x$x, x$y, : + font family 'Arial Narrow' not found in PostScript font database + Warning in grid.Call.graphics(C_text, as.graphicsAnnot(x$label), x$x, x$y, : + font family 'Arial Narrow' not found in PostScript font database + Warning in grid.Call.graphics(C_text, as.graphicsAnnot(x$label), x$x, x$y, : + font family 'Arial Narrow' not found in PostScript font database + + ... + font family 'Arial' not found in PostScript font database + + When sourcing ‘tidygraph.R’: + Error: invalid font type + Execution halted + + ‘Edges.Rmd’ using ‘UTF-8’... failed + ‘Layouts.Rmd’ using ‘UTF-8’... failed + ‘Nodes.Rmd’ using ‘UTF-8’... failed + ‘tidygraph.Rmd’ using ‘UTF-8’... failed + ``` + +* checking installed package size ... NOTE + ``` + installed size is 9.9Mb + sub-directories of 1Mb or more: + doc 3.9Mb + libs 4.4Mb + ``` + +# ggredist + +
+ +* Version: 0.0.2 +* GitHub: https://github.com/alarm-redist/ggredist +* Source code: https://github.com/cran/ggredist +* Date/Publication: 2022-11-23 11:20:02 UTC +* Number of recursive dependencies: 67 + +Run `revdepcheck::cloud_details(, "ggredist")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘ggredist-Ex.R’ failed + The error most likely occurred in: + + > ### Name: scale_fill_dra + > ### Title: Dave's Redistricting App classic scale for 'ggplot2' + > ### Aliases: scale_fill_dra scale_color_dra scale_colour_dra + > + > ### ** Examples + > + > library(ggplot2) + ... + 15. └─ggplot2 (local) FUN(X[[i]], ...) + 16. └─base::lapply(...) + 17. └─ggplot2 (local) FUN(X[[i]], ...) + 18. └─g$draw_key(data, g$params, key_size) + 19. └─ggplot2 (local) draw_key(...) + 20. └─ggplot2::draw_key_polygon(data, params, size) + 21. └─rlang:::Summary.quosure(from_theme(thin), 1.524, na.rm = FALSE) + 22. └─rlang:::abort_quosure_op("Summary", .Generic) + 23. └─rlang::abort(...) + Execution halted + ``` + +# ggResidpanel + +
+ +* Version: 0.3.0 +* GitHub: NA +* Source code: https://github.com/cran/ggResidpanel +* Date/Publication: 2019-05-31 23:20:04 UTC +* Number of recursive dependencies: 112 + +Run `revdepcheck::cloud_details(, "ggResidpanel")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘ggResidpanel-Ex.R’ failed + The error most likely occurred in: + + > ### Name: resid_interact + > ### Title: Panel of Interactive Versions of Diagnostic Residual Plots. + > ### Aliases: resid_interact + > + > ### ** Examples + > + > + > # Fit a model to the penguin data + > penguin_model <- lme4::lmer(heartrate ~ depth + duration + (1|bird), data = penguins) + > + > # Create the default interactive panel + > resid_interact(penguin_model) + Error in compute_geom_2(..., self = self) : + argument "theme" is missing, with no default + Calls: resid_interact ... use_defaults -> eval_from_theme -> %||% -> calc_element + Execution halted + ``` + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘introduction.Rmd’ + ... + > resid_interact(penguin_model, plots = c("resid", "qq")) + Warning: The following aesthetics were dropped during statistical transformation: label. + ℹ This can happen when ggplot fails to infer the correct grouping structure in + the data. + ℹ Did you forget to specify a `group` aesthetic or to convert a numerical + variable into a factor? + + When sourcing ‘introduction.R’: + Error: argument "theme" is missing, with no default + Execution halted + + ‘introduction.Rmd’ using ‘UTF-8’... failed + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘introduction.Rmd’ using rmarkdown + ``` + +# ggScatRidges + +
+ +* Version: 0.1.1 +* GitHub: https://github.com/matbou85/ggScatRidges +* Source code: https://github.com/cran/ggScatRidges +* Date/Publication: 2024-03-25 10:20:05 UTC +* Number of recursive dependencies: 117 + +Run `revdepcheck::cloud_details(, "ggScatRidges")` for more info + +
+ +## Newly broken + +* checking whether package ‘ggScatRidges’ can be installed ... WARNING + ``` + Found the following significant warnings: + Warning: replacing previous import ‘ggplot2::ggpar’ by ‘ggpubr::ggpar’ when loading ‘ggScatRidges’ + See ‘/tmp/workdir/ggScatRidges/new/ggScatRidges.Rcheck/00install.out’ for details. + ``` + +# ggseqplot + +
+ +* Version: 0.8.3 +* GitHub: https://github.com/maraab23/ggseqplot +* Source code: https://github.com/cran/ggseqplot +* Date/Publication: 2023-09-22 21:30:02 UTC +* Number of recursive dependencies: 130 + +Run `revdepcheck::cloud_details(, "ggseqplot")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘ggseqplot-Ex.R’ failed + The error most likely occurred in: + + > ### Name: ggseqtrplot + > ### Title: Sequence Transition Rate Plot + > ### Aliases: ggseqtrplot + > + > ### ** Examples + > + > # Use example data from TraMineR: biofam data set + ... + 8 7 7 Divorced + [>] sum of weights: 330.07 - min/max: 0/6.02881860733032 + [>] 300 sequences in the data set + [>] min/max sequence length: 16/16 + > + > # Basic transition rate plot (with adjusted x-axis labels) + > ggseqtrplot(biofam.seq, x_n.dodge = 2) + Error in ggseqtrplot(biofam.seq, x_n.dodge = 2) : + labsize must be a single number + Execution halted + ``` + +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(ggseqplot) + Loading required package: TraMineR + + TraMineR stable version 2.2-9 (Built: 2024-01-09) + Website: http://traminer.unige.ch + Please type 'citation("TraMineR")' for citation information. + ... + Backtrace: + ▆ + 1. ├─testthat::expect_s3_class(ggseqtrplot(biofam.seq), "ggplot") at test-ggseqtrplot.R:35:3 + 2. │ └─testthat::quasi_label(enquo(object), arg = "object") + 3. │ └─rlang::eval_bare(expr, quo_get_env(quo)) + 4. └─ggseqplot::ggseqtrplot(biofam.seq) + + [ FAIL 1 | WARN 1036 | SKIP 0 | PASS 131 ] + Error: Test failures + Execution halted + ``` + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘ggseqplot.Rmd’ + ... + Scale for fill is already present. + Adding another scale for fill, which will replace the existing scale. + Scale for fill is already present. + Adding another scale for fill, which will replace the existing scale. + + > ggseqtrplot(actcal.seq, group = actcal$sex) + + When sourcing ‘ggseqplot.R’: + Error: labsize must be a single number + Execution halted + + ‘ggseqplot.Rmd’ using ‘UTF-8’... failed + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘ggseqplot.Rmd’ using rmarkdown + ``` + +# ggside + +
+ +* Version: 0.3.1 +* GitHub: https://github.com/jtlandis/ggside +* Source code: https://github.com/cran/ggside +* Date/Publication: 2024-03-01 09:12:37 UTC +* Number of recursive dependencies: 76 + +Run `revdepcheck::cloud_details(, "ggside")` for more info + +
+ +## Newly broken + +* checking for code/documentation mismatches ... WARNING + ``` + Codoc mismatches from documentation object 'geom_xsideboxplot': + geom_xsideboxplot + Code: function(mapping = NULL, data = NULL, stat = "boxplot", + position = "dodge2", ..., outliers = TRUE, + outlier.colour = NULL, outlier.color = NULL, + outlier.fill = NULL, outlier.shape = NULL, + outlier.size = NULL, outlier.stroke = 0.5, + outlier.alpha = NULL, notch = FALSE, notchwidth = 0.5, + staplewidth = 0, varwidth = FALSE, na.rm = FALSE, + orientation = "x", show.legend = NA, inherit.aes = + ... + position = "dodge2", ..., outliers = TRUE, + outlier.colour = NULL, outlier.color = NULL, + outlier.fill = NULL, outlier.shape = 19, outlier.size + = 1.5, outlier.stroke = 0.5, outlier.alpha = NULL, + notch = FALSE, notchwidth = 0.5, staplewidth = 0, + varwidth = FALSE, na.rm = FALSE, orientation = "y", + show.legend = NA, inherit.aes = TRUE) + Mismatches in argument default values: + Name: 'outlier.shape' Code: NULL Docs: 19 + Name: 'outlier.size' Code: NULL Docs: 1.5 + ``` + +# ggtern + +
+ +* Version: 3.5.0 +* GitHub: NA +* Source code: https://github.com/cran/ggtern +* Date/Publication: 2024-03-24 21:50:02 UTC +* Number of recursive dependencies: 42 + +Run `revdepcheck::cloud_details(, "ggtern")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘ggtern-Ex.R’ failed + The error most likely occurred in: + + > ### Name: annotate + > ### Title: Create an annotation layer (ggtern version). + > ### Aliases: annotate + > + > ### ** Examples + > + > ggtern() + + ... + 16. │ └─ggplot2 (local) use_defaults(..., self = self) + 17. │ └─ggplot2:::eval_from_theme(default_aes, theme) + 18. │ ├─calc_element("geom", theme) %||% .default_geom_element + 19. │ └─ggplot2::calc_element("geom", theme) + 20. └─base::.handleSimpleError(...) + 21. └─rlang (local) h(simpleError(msg, call)) + 22. └─handlers[[1L]](cnd) + 23. └─cli::cli_abort(...) + 24. └─rlang::abort(...) + Execution halted + ``` + +## In both + +* checking package dependencies ... NOTE + ``` + Package which this enhances but not available for checking: ‘sp’ + ``` + +* checking Rd cross-references ... NOTE + ``` + Package unavailable to check Rd xrefs: ‘chemometrics’ + ``` + +# ggVennDiagram + +
+ +* Version: 1.5.2 +* GitHub: https://github.com/gaospecial/ggVennDiagram +* Source code: https://github.com/cran/ggVennDiagram +* Date/Publication: 2024-02-20 08:10:02 UTC +* Number of recursive dependencies: 98 + +Run `revdepcheck::cloud_details(, "ggVennDiagram")` for more info + +
+ +## Newly broken + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘fully-customed.Rmd’ + ... + [1] "b" "c" "e" "h" "k" "q" "s" "y" + + + > ggVennDiagram(y, show_intersect = TRUE, set_color = "black") + Warning in geom_text(aes(label = .data$count, text = .data$item), data = region_label) : + Ignoring unknown aesthetics: text + + ... + Ignoring unknown aesthetics: text + + When sourcing ‘using-ggVennDiagram.R’: + Error: argument "theme" is missing, with no default + Execution halted + + ‘VennCalculator.Rmd’ using ‘UTF-8’... OK + ‘fully-customed.Rmd’ using ‘UTF-8’... failed + ‘using-ggVennDiagram.Rmd’ using ‘UTF-8’... failed + ‘using-new-shapes.Rmd’ using ‘UTF-8’... OK + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘VennCalculator.Rmd’ using rmarkdown + --- finished re-building ‘VennCalculator.Rmd’ + + --- re-building ‘fully-customed.Rmd’ using rmarkdown + ``` + +## In both + +* checking installed package size ... NOTE + ``` + installed size is 11.0Mb + sub-directories of 1Mb or more: + doc 9.5Mb + help 1.1Mb + ``` + +# GIFT + +
+ +* Version: 1.3.2 +* GitHub: https://github.com/BioGeoMacro/GIFT +* Source code: https://github.com/cran/GIFT +* Date/Publication: 2024-02-27 10:50:02 UTC +* Number of recursive dependencies: 119 + +Run `revdepcheck::cloud_details(, "GIFT")` for more info + +
+ +## Newly broken + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘GIFT.Rmd’ using rmarkdown + ``` + +## In both + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘GIFT.Rmd’ + ... + + library("knitr") + + .... [TRUNCATED] + + > options(tinytex.verbose = TRUE) + + > knitr::include_graphics("../man/figures/biodiv_gottingen_logo.png") + + ... + + > knitr::include_graphics("../man/figures/biodiv_gottingen_logo.png") + + When sourcing ‘GIFT_advanced_users.R’: + Error: Cannot find the file(s): "../man/figures/biodiv_gottingen_logo.png" + Execution halted + + ‘GIFT.Rmd’ using ‘UTF-8’... failed + ‘GIFT_API.Rmd’ using ‘UTF-8’... failed + ‘GIFT_advanced_users.Rmd’ using ‘UTF-8’... failed + ``` + +* checking installed package size ... NOTE + ``` + installed size is 6.2Mb + sub-directories of 1Mb or more: + doc 3.3Mb + help 2.6Mb + ``` + +# GimmeMyPlot + +
+ +* Version: 0.1.0 +* GitHub: NA +* Source code: https://github.com/cran/GimmeMyPlot +* Date/Publication: 2023-10-18 16:10:02 UTC +* Number of recursive dependencies: 111 + +Run `revdepcheck::cloud_details(, "GimmeMyPlot")` for more info + +
+ +## Newly broken + +* checking whether package ‘GimmeMyPlot’ can be installed ... WARNING + ``` + Found the following significant warnings: + Warning: replacing previous import ‘ggplot2::ggpar’ by ‘ggpubr::ggpar’ when loading ‘GimmeMyPlot’ + See ‘/tmp/workdir/GimmeMyPlot/new/GimmeMyPlot.Rcheck/00install.out’ for details. + ``` + +# gprofiler2 + +
+ +* Version: 0.2.3 +* GitHub: NA +* Source code: https://github.com/cran/gprofiler2 +* Date/Publication: 2024-02-23 21:50:02 UTC +* Number of recursive dependencies: 74 + +Run `revdepcheck::cloud_details(, "gprofiler2")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘gprofiler2-Ex.R’ failed + The error most likely occurred in: + + > ### Name: gostplot + > ### Title: Manhattan plot of functional enrichment results. + > ### Aliases: gostplot + > + > ### ** Examples + > + > gostres <- gost(c("Klf4", "Pax5", "Sox2", "Nanog"), organism = "mmusculus") + > gostplot(gostres) + Error in compute_geom_2(..., self = self) : + argument "theme" is missing, with no default + Calls: gostplot ... use_defaults -> eval_from_theme -> %||% -> calc_element + Execution halted + ``` + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘gprofiler2.Rmd’ + ... + effective_domain_size source_order parents + 1 20212 1236 GO:0005003 + 2 20212 1234 GO:0004714 + 3 21031 12892 GO:0007169 + + > gostplot(gostres, capped = TRUE, interactive = TRUE) + + When sourcing ‘gprofiler2.R’: + Error: argument "theme" is missing, with no default + Execution halted + + ‘gprofiler2.Rmd’ using ‘UTF-8’... failed + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + ... + --- re-building ‘gprofiler2.Rmd’ using rmarkdown + + Quitting from lines at lines 246-247 [unnamed-chunk-14] (gprofiler2.Rmd) + Error: processing vignette 'gprofiler2.Rmd' failed with diagnostics: + argument "theme" is missing, with no default + --- failed re-building ‘gprofiler2.Rmd’ + + SUMMARY: processing the following file failed: + ‘gprofiler2.Rmd’ + + Error: Vignette re-building failed. + Execution halted + ``` + +# Greymodels + +
+ +* Version: 2.0.1 +* GitHub: https://github.com/havishaJ/Greymodels +* Source code: https://github.com/cran/Greymodels +* Date/Publication: 2022-12-05 12:42:35 UTC +* Number of recursive dependencies: 91 + +Run `revdepcheck::cloud_details(, "Greymodels")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘Greymodels-Ex.R’ failed + The error most likely occurred in: + + > ### Name: Plots + > ### Title: plots + > ### Aliases: plots plotrm plotsmv1 plotsmv2 plotsigndgm plots_mdbgm12 + > + > ### ** Examples + > + > # Plots - EPGM (1, 1) model + ... + + geom_line(data = xy1, aes(x = x, y = y,color = "Raw Data")) + + + geom_line(data = xy2, aes(x = x, y = y,color = "Fitted&Forecasts")) + + + geom_line(data = set3, aes(x = CI, y = y,color = "LowerBound"), linetype=2) + + + geom_line(data = set4, aes(x = CI, y = y,color = "UpperBound"), linetype=2) + + + scale_color_manual(name = "Label",values = colors) + > r <- ggplotly(p) + Error in compute_geom_2(..., self = self) : + argument "theme" is missing, with no default + Calls: ggplotly ... use_defaults -> eval_from_theme -> %||% -> calc_element + Execution halted + ``` + +# h3jsr + +
+ +* Version: 1.3.1 +* GitHub: NA +* Source code: https://github.com/cran/h3jsr +* Date/Publication: 2023-01-21 09:20:10 UTC +* Number of recursive dependencies: 96 + +Run `revdepcheck::cloud_details(, "h3jsr")` for more info + +
+ +## Newly broken + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘intro-to-h3jsr.Rmd’ + ... + + scale_fill_ .... [TRUNCATED] + + When sourcing ‘intro-to-h3jsr.R’: + Error: Summary operations are not defined for quosures. Do you need to unquote + the quosure? + + # Bad: min(myquosure) + + # Good: min(!!myquosure) + Execution halted + + ‘intro-to-h3jsr.Rmd’ using ‘UTF-8’... failed + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + ... + --- re-building ‘intro-to-h3jsr.Rmd’ using rmarkdown + + Quitting from lines at lines 79-89 [c4] (intro-to-h3jsr.Rmd) + Error: processing vignette 'intro-to-h3jsr.Rmd' failed with diagnostics: + Summary operations are not defined for quosures. Do you need to unquote + the quosure? + + # Bad: min(myquosure) + + # Good: min(!!myquosure) + --- failed re-building ‘intro-to-h3jsr.Rmd’ + + SUMMARY: processing the following file failed: + ‘intro-to-h3jsr.Rmd’ + + Error: Vignette re-building failed. + Execution halted + ``` + +# healthyR + +
+ +* Version: 0.2.1 +* GitHub: https://github.com/spsanderson/healthyR +* Source code: https://github.com/cran/healthyR +* Date/Publication: 2023-04-06 22:20:03 UTC +* Number of recursive dependencies: 157 + +Run `revdepcheck::cloud_details(, "healthyR")` for more info + +
+ +## Newly broken + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘getting-started.Rmd’ + ... + + > ts_alos_plt(.data = df_tbl, .date_col = Date, .value_col = Values, + + .by = "month", .interactive = FALSE) + + > ts_alos_plt(.data = df_tbl, .date_col = Date, .value_col = Values, + + .by = "month", .interactive = TRUE) + + When sourcing ‘getting-started.R’: + Error: argument "theme" is missing, with no default + Execution halted + + ‘getting-started.Rmd’ using ‘UTF-8’... failed + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘getting-started.Rmd’ using rmarkdown + ``` + +## In both + +* checking installed package size ... NOTE + ``` + installed size is 6.5Mb + sub-directories of 1Mb or more: + data 2.4Mb + doc 3.7Mb + ``` + +# healthyR.ai + +
+ +* Version: 0.0.13 +* GitHub: https://github.com/spsanderson/healthyR.ai +* Source code: https://github.com/cran/healthyR.ai +* Date/Publication: 2023-04-03 00:20:02 UTC +* Number of recursive dependencies: 228 + +Run `revdepcheck::cloud_details(, "healthyR.ai")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘healthyR.ai-Ex.R’ failed + The error most likely occurred in: + + > ### Name: pca_your_recipe + > ### Title: Perform PCA + > ### Aliases: pca_your_recipe + > + > ### ** Examples + > + > suppressPackageStartupMessages(library(timetk)) + ... + > + > output_list <- pca_your_recipe(rec_obj, .data = data_tbl) + Warning: ! The following columns have zero variance so scaling cannot be used: + date_col_day, date_col_mday, date_col_mweek, and date_col_mday7. + ℹ Consider using ?step_zv (`?recipes::step_zv()`) to remove those columns + before normalizing. + Error in compute_geom_2(..., self = self) : + argument "theme" is missing, with no default + Calls: pca_your_recipe ... use_defaults -> eval_from_theme -> %||% -> calc_element + Execution halted + ``` + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘getting-started.Rmd’ + ... + > pca_list <- pca_your_recipe(.recipe_object = rec_obj, + + .data = data_tbl, .threshold = 0.8, .top_n = 5) + Warning: ! The following columns have zero variance so scaling cannot be used: + date_col_day, date_col_mday, date_col_mweek, and date_col_mday7. + ℹ Consider using ?step_zv (`?recipes::step_zv()`) to remove those columns + before normalizing. + + When sourcing ‘getting-started.R’: + Error: argument "theme" is missing, with no default + Execution halted + + ‘auto-kmeans.Rmd’ using ‘UTF-8’... OK + ‘getting-started.Rmd’ using ‘UTF-8’... failed + ‘kmeans-umap.Rmd’ using ‘UTF-8’... OK + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘auto-kmeans.Rmd’ using rmarkdown + --- finished re-building ‘auto-kmeans.Rmd’ + + --- re-building ‘getting-started.Rmd’ using rmarkdown + + Quitting from lines at lines 107-113 [pca_your_rec] (getting-started.Rmd) + Error: processing vignette 'getting-started.Rmd' failed with diagnostics: + argument "theme" is missing, with no default + --- failed re-building ‘getting-started.Rmd’ + + --- re-building ‘kmeans-umap.Rmd’ using rmarkdown + ``` + +# healthyR.ts + +
+ +* Version: 0.3.0 +* GitHub: https://github.com/spsanderson/healthyR.ts +* Source code: https://github.com/cran/healthyR.ts +* Date/Publication: 2023-11-15 06:00:05 UTC +* Number of recursive dependencies: 222 + +Run `revdepcheck::cloud_details(, "healthyR.ts")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘healthyR.ts-Ex.R’ failed + The error most likely occurred in: + + > ### Name: tidy_fft + > ### Title: Tidy Style FFT + > ### Aliases: tidy_fft + > + > ### ** Examples + > + > suppressPackageStartupMessages(library(dplyr)) + ... + + .data = data_tbl, + + .value_col = value, + + .date_col = date_col, + + .harmonics = 3, + + .frequency = 12 + + ) + Error in compute_geom_2(..., self = self) : + argument "theme" is missing, with no default + Calls: tidy_fft ... use_defaults -> eval_from_theme -> %||% -> calc_element + Execution halted + ``` + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘using-tidy-fft.Rmd’ + ... + $ value 112, 118, 132, 129, 121, 135, 148, 148, 136, 119, 104, 118, 1… + + > suppressPackageStartupMessages(library(timetk)) + + > data_tbl %>% plot_time_series(.date_var = date_col, + + .value = value) + + When sourcing ‘using-tidy-fft.R’: + Error: argument "theme" is missing, with no default + Execution halted + + ‘getting-started.Rmd’ using ‘UTF-8’... OK + ‘using-tidy-fft.Rmd’ using ‘UTF-8’... failed + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘getting-started.Rmd’ using rmarkdown + ``` + +## In both + +* checking installed package size ... NOTE + ``` + installed size is 6.5Mb + sub-directories of 1Mb or more: + doc 5.2Mb + ``` + +# heatmaply + +
+ +* Version: 1.5.0 +* GitHub: https://github.com/talgalili/heatmaply +* Source code: https://github.com/cran/heatmaply +* Date/Publication: 2023-10-06 20:50:02 UTC +* Number of recursive dependencies: 111 + +Run `revdepcheck::cloud_details(, "heatmaply")` for more info + +
+ +## Newly broken + +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(heatmaply) + Loading required package: plotly + Loading required package: ggplot2 + + Attaching package: 'plotly' + + ... + 14. └─ggplot2 (local) compute_geom_2(..., self = self) + 15. └─self$geom$use_defaults(data, self$aes_params, modifiers, theme = theme) + 16. └─ggplot2 (local) use_defaults(..., self = self) + 17. └─ggplot2:::eval_from_theme(default_aes, theme) + 18. ├─calc_element("geom", theme) %||% .default_geom_element + 19. └─ggplot2::calc_element("geom", theme) + + [ FAIL 58 | WARN 0 | SKIP 0 | PASS 193 ] + Error: Test failures + Execution halted + ``` + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘heatmaply.Rmd’ + ... + + > library("heatmaply") + + > library("heatmaply") + + > heatmaply(mtcars) + + When sourcing ‘heatmaply.R’: + Error: argument "theme" is missing, with no default + Execution halted + + ‘heatmaply.Rmd’ using ‘UTF-8’... failed + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + ... + --- re-building ‘heatmaply.Rmd’ using rmarkdown + + Quitting from lines at lines 109-111 [unnamed-chunk-5] (heatmaply.Rmd) + Error: processing vignette 'heatmaply.Rmd' failed with diagnostics: + argument "theme" is missing, with no default + --- failed re-building ‘heatmaply.Rmd’ + + SUMMARY: processing the following file failed: + ‘heatmaply.Rmd’ + + Error: Vignette re-building failed. + Execution halted + ``` + +## In both + +* checking installed package size ... NOTE + ``` + installed size is 5.7Mb + sub-directories of 1Mb or more: + doc 5.1Mb + ``` + +# hilldiv + +
+ +* Version: 1.5.1 +* GitHub: https://github.com/anttonalberdi/hilldiv +* Source code: https://github.com/cran/hilldiv +* Date/Publication: 2019-10-01 14:40:02 UTC +* Number of recursive dependencies: 153 + +Run `revdepcheck::cloud_details(, "hilldiv")` for more info + +
+ +## Newly broken + +* checking whether package ‘hilldiv’ can be installed ... WARNING + ``` + Found the following significant warnings: + Warning: replacing previous import ‘ggplot2::ggpar’ by ‘ggpubr::ggpar’ when loading ‘hilldiv’ + See ‘/tmp/workdir/hilldiv/new/hilldiv.Rcheck/00install.out’ for details. + ``` + +# hJAM + +
+ +* Version: 1.0.0 +* GitHub: https://github.com/lailylajiang/hJAM +* Source code: https://github.com/cran/hJAM +* Date/Publication: 2020-02-20 14:50:05 UTC +* Number of recursive dependencies: 101 + +Run `revdepcheck::cloud_details(, "hJAM")` for more info + +
+ +## Newly broken + +* checking whether package ‘hJAM’ can be installed ... WARNING + ``` + Found the following significant warnings: + Warning: replacing previous import ‘ggplot2::ggpar’ by ‘ggpubr::ggpar’ when loading ‘hJAM’ + See ‘/tmp/workdir/hJAM/new/hJAM.Rcheck/00install.out’ for details. + ``` + +# HVT + +
+ +* Version: 23.11.1 +* GitHub: https://github.com/Mu-Sigma/HVT +* Source code: https://github.com/cran/HVT +* Date/Publication: 2023-11-19 15:20:12 UTC +* Number of recursive dependencies: 200 + +Run `revdepcheck::cloud_details(, "HVT")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘HVT-Ex.R’ failed + The error most likely occurred in: + + > ### Name: diagPlot + > ### Title: Diagnosis Plot + > ### Aliases: diagPlot + > ### Keywords: hplot internal + > + > ### ** Examples + > + ... + Scale for x is already present. + Adding another scale for x, which will replace the existing scale. + Scale for y is already present. + Adding another scale for y, which will replace the existing scale. + Warning in geom_polygon(data = boundaryCoords2, aes(x = bp.x, y = bp.y, : + Ignoring unknown aesthetics: text + Error in compute_geom_2(..., self = self) : + argument "theme" is missing, with no default + Calls: HVT ... use_defaults -> eval_from_theme -> %||% -> calc_element + Execution halted + ``` + +# HYPEtools + +
+ +* Version: 1.6.1 +* GitHub: https://github.com/rcapell/HYPEtools +* Source code: https://github.com/cran/HYPEtools +* Date/Publication: 2024-01-12 17:20:02 UTC +* Number of recursive dependencies: 164 + +Run `revdepcheck::cloud_details(, "HYPEtools")` for more info + +
+ +## Newly broken + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘plot_map_statistics.Rmd’ + ... + + > stat.nm.plot <- "NSE" + + > PlotMapPoints(x = stats.cout[, c(1, stat.col.plot)], + + sites = map.Qobs, sites.subid.column = 3, bg = map.subid) + Joining "SUBID" from GIS Data (sites) To "SUBID" from subass (x) + + ... + When sourcing ‘plot_map_statistics.R’: + Error: 'language' object cannot be coerced to type 'integer' + Execution halted + + ‘analyze_hype_ts.Rmd’ using ‘UTF-8’... OK + ‘basin_characteristics.Rmd’ using ‘UTF-8’... OK + ‘basin_network.Rmd’ using ‘UTF-8’... OK + ‘import_files.Rmd’ using ‘UTF-8’... OK + ‘modify_par.Rmd’ using ‘UTF-8’... OK + ‘plot_map_statistics.Rmd’ using ‘UTF-8’... failed + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘analyze_hype_ts.Rmd’ using rmarkdown + ``` + +# ImFoR + +
+ +* Version: 0.1.0 +* GitHub: NA +* Source code: https://github.com/cran/ImFoR +* Date/Publication: 2023-09-21 18:50:02 UTC +* Number of recursive dependencies: 173 + +Run `revdepcheck::cloud_details(, "ImFoR")` for more info + +
+ +## Newly broken + +* checking whether package ‘ImFoR’ can be installed ... WARNING + ``` + Found the following significant warnings: + Warning: replacing previous import ‘ggplot2::ggpar’ by ‘ggpubr::ggpar’ when loading ‘ImFoR’ + See ‘/tmp/workdir/ImFoR/new/ImFoR.Rcheck/00install.out’ for details. + ``` + +# iNEXT.4steps + +
+ +* Version: 1.0.0 +* GitHub: https://github.com/KaiHsiangHu/iNEXT.4steps +* Source code: https://github.com/cran/iNEXT.4steps +* Date/Publication: 2024-04-10 20:00:05 UTC +* Number of recursive dependencies: 107 + +Run `revdepcheck::cloud_details(, "iNEXT.4steps")` for more info + +
+ +## Newly broken + +* checking whether package ‘iNEXT.4steps’ can be installed ... WARNING + ``` + Found the following significant warnings: + Warning: replacing previous import ‘ggplot2::ggpar’ by ‘ggpubr::ggpar’ when loading ‘iNEXT.4steps’ + See ‘/tmp/workdir/iNEXT.4steps/new/iNEXT.4steps.Rcheck/00install.out’ for details. + ``` + +# insane + +
+ +* Version: 1.0.3 +* GitHub: https://github.com/mcanouil/insane +* Source code: https://github.com/cran/insane +* Date/Publication: 2023-11-14 21:50:02 UTC +* Number of recursive dependencies: 127 + +Run `revdepcheck::cloud_details(, "insane")` for more info + +
+ +## Newly broken + +* checking whether package ‘insane’ can be installed ... WARNING + ``` + Found the following significant warnings: + Warning: replacing previous import ‘ggplot2::ggpar’ by ‘ggpubr::ggpar’ when loading ‘insane’ + See ‘/tmp/workdir/insane/new/insane.Rcheck/00install.out’ for details. + ``` + +# inTextSummaryTable + +
+ +* Version: 3.3.2 +* GitHub: https://github.com/openanalytics/inTextSummaryTable +* Source code: https://github.com/cran/inTextSummaryTable +* Date/Publication: 2024-03-09 16:20:02 UTC +* Number of recursive dependencies: 120 + +Run `revdepcheck::cloud_details(, "inTextSummaryTable")` for more info + +
+ +## Newly broken + +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(inTextSummaryTable) + > + > test_check("inTextSummaryTable") + [ FAIL 59 | WARN 1 | SKIP 0 | PASS 881 ] + + ══ Failed tests ════════════════════════════════════════════════════════════════ + ... + 5. │ └─rlang::eval_bare(quo_get_expr(.quo), quo_get_env(.quo)) + 6. └─inTextSummaryTable::subjectProfileSummaryPlot(...) + 7. ├─base::do.call(plyr::rbind.fill, ggplot_build(gg)$data) + 8. └─plyr (local) ``(``, ``) + 9. └─plyr:::output_template(dfs, nrows) + 10. └─plyr:::allocate_column(df[[var]], nrows, dfs, var) + + [ FAIL 59 | WARN 1 | SKIP 0 | PASS 881 ] + Error: Test failures + Execution halted + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘inTextSummaryTable-advanced.Rmd’ using rmarkdown + --- finished re-building ‘inTextSummaryTable-advanced.Rmd’ + + --- re-building ‘inTextSummaryTable-aesthetics.Rmd’ using rmarkdown + + Quitting from lines at lines 211-224 [aesthetics-defaultsVisualization] (inTextSummaryTable-aesthetics.Rmd) + Error: processing vignette 'inTextSummaryTable-aesthetics.Rmd' failed with diagnostics: + Problem while setting up geom aesthetics. + ℹ Error occurred in the 2nd layer. + ... + ! Aesthetics must be either length 1 or the same as the data (28). + ✖ Fix the following mappings: `size`. + --- failed re-building ‘inTextSummaryTable-visualization.Rmd’ + + SUMMARY: processing the following files failed: + ‘inTextSummaryTable-aesthetics.Rmd’ + ‘inTextSummaryTable-visualization.Rmd’ + + Error: Vignette re-building failed. + Execution halted + ``` + +## In both + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘inTextSummaryTable-aesthetics.Rmd’ + ... + > subjectProfileSummaryPlot(data = summaryTable, xVar = "visit", + + colorVar = "TRT") + + When sourcing ‘inTextSummaryTable-aesthetics.R’: + Error: Problem while setting up geom aesthetics. + ℹ Error occurred in the 2nd layer. + Caused by error in `check_aesthetics()`: + ... + ✖ Fix the following mappings: `size`. + Execution halted + + ‘inTextSummaryTable-advanced.Rmd’ using ‘UTF-8’... OK + ‘inTextSummaryTable-aesthetics.Rmd’ using ‘UTF-8’... failed + ‘inTextSummaryTable-createTables.Rmd’ using ‘UTF-8’... OK + ‘inTextSummaryTable-exportTables.Rmd’ using ‘UTF-8’... OK + ‘inTextSummaryTable-introduction.Rmd’ using ‘UTF-8’... OK + ‘inTextSummaryTable-standardTables.Rmd’ using ‘UTF-8’... OK + ‘inTextSummaryTable-visualization.Rmd’ using ‘UTF-8’... failed + ``` + +* checking installed package size ... NOTE + ``` + installed size is 10.9Mb + sub-directories of 1Mb or more: + doc 9.9Mb + ``` + +# inventorize + +
+ +* Version: 1.1.1 +* GitHub: NA +* Source code: https://github.com/cran/inventorize +* Date/Publication: 2022-05-31 22:20:09 UTC +* Number of recursive dependencies: 71 + +Run `revdepcheck::cloud_details(, "inventorize")` for more info + +
+ +## Newly broken + +* checking whether package ‘inventorize’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/inventorize/new/inventorize.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘inventorize’ ... +** package ‘inventorize’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** byte-compile and prepare package for lazy loading +Error in compute_geom_2(..., self = self) : + argument "theme" is missing, with no default +Error: unable to load R code in package ‘inventorize’ +Execution halted +ERROR: lazy loading failed for package ‘inventorize’ +* removing ‘/tmp/workdir/inventorize/new/inventorize.Rcheck/inventorize’ + + +``` +### CRAN + +``` +* installing *source* package ‘inventorize’ ... +** package ‘inventorize’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** byte-compile and prepare package for lazy loading +Warning in qgamma(service_level, alpha, beta) : NaNs produced +Warning in qgamma(service_level, alpha, beta) : NaNs produced +** help +*** installing help indices +** building package indices +** testing if installed package can be loaded from temporary location +** testing if installed package can be loaded from final location +** testing if installed package keeps a record of temporary installation path +* DONE (inventorize) + + +``` +# itsdm + +
+ +* Version: 0.2.1 +* GitHub: https://github.com/LLeiSong/itsdm +* Source code: https://github.com/cran/itsdm +* Date/Publication: 2023-06-11 00:00:02 UTC +* Number of recursive dependencies: 83 + +Run `revdepcheck::cloud_details(, "itsdm")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘itsdm-Ex.R’ failed + The error most likely occurred in: + + > ### Name: suspicious_env_outliers + > ### Title: Function to detect suspicious outliers based on environmental + > ### variables. + > ### Aliases: suspicious_env_outliers + > + > ### ** Examples + > + ... + row [51] - suspicious column: [bio12] - suspicious value: [380.00] + distribution: 97.143% >= 777.00 - [mean: 1058.20] - [sd: 190.90] - [norm. obs: 102] + given: + [bio1] > [24.01] (value: 24.41) + + + Error in valid.pch(x$pch) : + 'language' object cannot be coerced to type 'integer' + Calls: suspicious_env_outliers ... validGrob.grob -> validDetails -> validDetails.points -> valid.pch + Execution halted + ``` + +# karel + +
+ +* Version: 0.1.1 +* GitHub: https://github.com/mpru/karel +* Source code: https://github.com/cran/karel +* Date/Publication: 2022-03-26 21:50:02 UTC +* Number of recursive dependencies: 90 + +Run `revdepcheck::cloud_details(, "karel")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘karel-Ex.R’ failed + The error most likely occurred in: + + > ### Name: acciones + > ### Title: Acciones que Karel puede realizar + > ### Aliases: acciones avanzar girar_izquierda poner_coso juntar_coso + > ### girar_derecha darse_vuelta + > + > ### ** Examples + > + ... + 20. │ └─ggplot2 (local) use_defaults(..., self = self) + 21. │ └─ggplot2:::eval_from_theme(default_aes, theme) + 22. │ ├─calc_element("geom", theme) %||% .default_geom_element + 23. │ └─ggplot2::calc_element("geom", theme) + 24. └─base::.handleSimpleError(...) + 25. └─rlang (local) h(simpleError(msg, call)) + 26. └─handlers[[1L]](cnd) + 27. └─cli::cli_abort(...) + 28. └─rlang::abort(...) + Execution halted + ``` + +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(karel) + > + > test_check("karel") + [ FAIL 2 | WARN 2 | SKIP 0 | PASS 78 ] + + ══ Failed tests ════════════════════════════════════════════════════════════════ + ... + 24. │ └─ggplot2::calc_element("geom", theme) + 25. └─base::.handleSimpleError(...) + 26. └─rlang (local) h(simpleError(msg, call)) + 27. └─handlers[[1L]](cnd) + 28. └─cli::cli_abort(...) + 29. └─rlang::abort(...) + + [ FAIL 2 | WARN 2 | SKIP 0 | PASS 78 ] + Error: Test failures + Execution halted + ``` + +## In both + +* checking dependencies in R code ... NOTE + ``` + Namespace in Imports field not imported from: ‘gifski’ + All declared Imports should be used. + ``` + +# latentcor + +
+ +* Version: 2.0.1 +* GitHub: NA +* Source code: https://github.com/cran/latentcor +* Date/Publication: 2022-09-05 20:50:02 UTC +* Number of recursive dependencies: 143 + +Run `revdepcheck::cloud_details(, "latentcor")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘latentcor-Ex.R’ failed + The error most likely occurred in: + + > ### Name: latentcor + > ### Title: Estimate latent correlation for mixed types. + > ### Aliases: latentcor + > + > ### ** Examples + > + > # Example 1 - truncated data type, same type for all variables + ... + > proc.time() - start_time + user system elapsed + 0.036 0.000 0.036 + > # Heatmap for latent correlation matrix. + > Heatmap_R_approx = latentcor(X = X, types = "tru", method = "approx", + + showplot = TRUE)$plotR + Error in compute_geom_2(..., self = self) : + argument "theme" is missing, with no default + Calls: latentcor ... use_defaults -> eval_from_theme -> %||% -> calc_element + Execution halted + ``` + +## In both + +* checking installed package size ... NOTE + ``` + installed size is 7.3Mb + sub-directories of 1Mb or more: + R 6.9Mb + ``` + +# mapSpain + +
+ +* Version: 0.9.0 +* GitHub: https://github.com/rOpenSpain/mapSpain +* Source code: https://github.com/cran/mapSpain +* Date/Publication: 2024-01-23 20:50:02 UTC +* Number of recursive dependencies: 101 + +Run `revdepcheck::cloud_details(, "mapSpain")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘mapSpain-Ex.R’ failed + The error most likely occurred in: + + > ### Name: esp_munic.sf + > ### Title: All Municipalities 'POLYGON' object of Spain (2019) + > ### Aliases: esp_munic.sf + > + > ### ** Examples + > + > data("esp_munic.sf") + ... + 15. └─ggplot2 (local) FUN(X[[i]], ...) + 16. └─base::lapply(...) + 17. └─ggplot2 (local) FUN(X[[i]], ...) + 18. └─g$draw_key(data, g$params, key_size) + 19. └─ggplot2 (local) draw_key(...) + 20. └─ggplot2::draw_key_polygon(data, params, size) + 21. └─rlang:::Summary.quosure(from_theme(thin), 1.524, na.rm = FALSE) + 22. └─rlang:::abort_quosure_op("Summary", .Generic) + 23. └─rlang::abort(...) + Execution halted + ``` + +## In both + +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(mapSpain) + > + > test_check("mapSpain") + Starting 2 test processes + [ FAIL 1 | WARN 0 | SKIP 29 | PASS 158 ] + + ... + 'test-esp_move_can.R:42:3', 'test-esp_make_provider.R:8:3', + 'test-esp_make_provider.R:31:3' + + ══ Failed tests ════════════════════════════════════════════════════════════════ + ── Failure ('test-esp_get_nuts.R:50:3'): Test local NUTS ─────────────────────── + `esp_get_nuts(resolution = "20")` produced warnings. + + [ FAIL 1 | WARN 0 | SKIP 29 | PASS 158 ] + Error: Test failures + Execution halted + ``` + +* checking installed package size ... NOTE + ``` + installed size is 8.1Mb + sub-directories of 1Mb or more: + data 7.0Mb + ``` + +* checking data for non-ASCII characters ... NOTE + ``` + Note: found 13138 marked UTF-8 strings + ``` + +# MBNMAdose + +
+ +* Version: 0.4.3 +* GitHub: NA +* Source code: https://github.com/cran/MBNMAdose +* Date/Publication: 2024-04-18 12:42:47 UTC +* Number of recursive dependencies: 118 + +Run `revdepcheck::cloud_details(, "MBNMAdose")` for more info + +
+ +## Newly broken + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘outputs-4.Rmd’ + ... + + > plot(trip.emax) + + When sourcing ‘outputs-4.R’: + Error: Problem while setting up geom aesthetics. + ℹ Error occurred in the 1st layer. + Caused by error in `use_defaults()`: + ... + Execution halted + + ‘consistencychecking-3.Rmd’ using ‘UTF-8’... OK + ‘dataexploration-1.Rmd’ using ‘UTF-8’... OK + ‘mbnmadose-overview.Rmd’ using ‘UTF-8’... OK + ‘metaregression-6.Rmd’ using ‘UTF-8’... OK + ‘nma_in_mbnmadose.Rmd’ using ‘UTF-8’... OK + ‘outputs-4.Rmd’ using ‘UTF-8’... failed + ‘predictions-5.Rmd’ using ‘UTF-8’... OK + ‘runmbnmadose-2.Rmd’ using ‘UTF-8’... OK + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘consistencychecking-3.Rmd’ using rmarkdown + ``` + +## In both + +* checking data for non-ASCII characters ... NOTE + ``` + Note: found 6 marked Latin-1 strings + ``` + +# MBNMAtime + +
+ +* Version: 0.2.4 +* GitHub: NA +* Source code: https://github.com/cran/MBNMAtime +* Date/Publication: 2023-10-14 15:20:02 UTC +* Number of recursive dependencies: 106 + +Run `revdepcheck::cloud_details(, "MBNMAtime")` for more info + +
+ +## Newly broken + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘consistencychecking-3.Rmd’ using rmarkdown + + Quitting from lines at lines 141-146 [unnamed-chunk-8] (consistencychecking-3.Rmd) + Error: processing vignette 'consistencychecking-3.Rmd' failed with diagnostics: + unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), NULL, list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.75, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, 90, NULL, c(0, + 2.75, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 1, NULL, NULL, NULL, c(0, 2.2, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, NULL, c(0, 0, 0, 2.2 + ), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0.5, NULL, NULL, NULL, c(0, 2.2, 0, 2.2), NULL, TRUE), list("grey20", NULL, NULL, NULL, FALSE, TRUE), NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 2.75, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 0.75, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, list(), NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, list("transparent", NA, NULL, NULL, FALSE), c(5.5, 5.5, 5.5, 5.5), 11, NULL, NULL, list("transparent", + NA, NULL, NULL, FALSE), 1.2, NULL, NULL, 5.5, NULL, NULL, NULL, NULL, 0.2, NULL, list(NULL, NULL, NULL, 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, NULL, NULL, NULL, TRUE), NULL, "right", NULL, NULL, NULL, "center", NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, c(0, 0, 0, 0), list(), 11, list(), list(NA, "grey20", NULL, NULL, TRUE), 5.5, NULL, NULL, list("grey92", NULL, NULL, NULL, FALSE, TRUE), list("grey95", NULL, NULL, NULL, FALSE, FALSE), + list("grey95", 0.5, NULL, NULL, FALSE, FALSE), NULL, NULL, NULL, NULL, FALSE, list("white", NA, NULL, NULL, FALSE), list(NULL, NULL, NULL, 1.2, 0, 1, NULL, NULL, c(0, 0, 5.5, 0), NULL, TRUE), "panel", list(NULL, NULL, NULL, NULL, 0, 1, NULL, NULL, c(0, 0, 5.5, 0), NULL, TRUE), list(NULL, NULL, NULL, 0.8, 1, 1, NULL, NULL, c(5.5, 0, 0, 0), NULL, TRUE), "panel", list(NULL, NULL, NULL, 1.2, 0.5, 0.5, NULL, NULL, NULL, NULL, TRUE), "topleft", NULL, c(5.5, 5.5, 5.5, 5.5), list("lightsteelblue1", "black", + NULL, NULL, FALSE), NULL, NULL, "inherit", "inside", list(NULL, NULL, "black", 0.8, NULL, NULL, NULL, NULL, c(4.4, 4.4, 4.4, 4.4), NULL, FALSE), NULL, NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, NULL, -90, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, NULL, 90, NULL, NULL, NULL, TRUE), NULL, 2.75, 2.75)) + --- failed re-building ‘consistencychecking-3.Rmd’ + + --- re-building ‘dataexploration-1.Rmd’ using rmarkdown + ``` + +## In both + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘consistencychecking-3.Rmd’ + ... + 2.75, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 1, NULL, NULL, NULL, c(0, 2.2, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, NULL, c(0, 0, 0, 2.2 + ), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0.5, NULL, NULL, NULL, c(0, 2.2, 0, 2.2), NULL, TRUE), list("grey20", NULL, NULL, NULL, FALSE, TRUE), NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 2.75, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 0.75, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, list(), NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, list("transparent", NA, NULL, NULL, FALSE), c(5.5, 5.5, 5.5, 5.5), 11, NULL, NULL, list("transparent", + NA, NULL, NULL, FALSE), 1.2, NULL, NULL, 5.5, NULL, NULL, NULL, NULL, 0.2, NULL, list(NULL, NULL, NULL, 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, NULL, NULL, NULL, TRUE), NULL, "right", NULL, NULL, NULL, "center", NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, c(0, 0, 0, 0), list(), 11, list(), list(NA, "grey20", NULL, NULL, TRUE), 5.5, NULL, NULL, list("grey92", NULL, NULL, NULL, FALSE, TRUE), list("grey95", NULL, NULL, NULL, FALSE, FALSE), + list("grey95", 0.5, NULL, NULL, FALSE, FALSE), NULL, NULL, NULL, NULL, FALSE, list("white", NA, NULL, NULL, FALSE), list(NULL, NULL, NULL, 1.2, 0, 1, NULL, NULL, c(0, 0, 5.5, 0), NULL, TRUE), "panel", list(NULL, NULL, NULL, NULL, 0, 1, NULL, NULL, c(0, 0, 5.5, 0), NULL, TRUE), list(NULL, NULL, NULL, 0.8, 1, 1, NULL, NULL, c(5.5, 0, 0, 0), NULL, TRUE), "panel", list(NULL, NULL, NULL, 1.2, 0.5, 0.5, NULL, NULL, NULL, NULL, TRUE), "topleft", NULL, c(5.5, 5.5, 5.5, 5.5), list("lightsteelblue1", "black", + NULL, NULL, FALSE), NULL, NULL, "inherit", "inside", list(NULL, NULL, "black", 0.8, NULL, NULL, NULL, NULL, c(4.4, 4.4, 4.4, 4.4), NULL, FALSE), NULL, NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, NULL, -90, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, NULL, 90, NULL, NULL, NULL, TRUE), NULL, 2.75, 2.75)) + + When sourcing ‘consistencychecking-3.R’: + ... + ! unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), NULL, list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.75, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, 90, NULL, c(0, + 2.75, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(NULL, N + Execution halted + + ‘consistencychecking-3.Rmd’ using ‘UTF-8’... failed + ‘dataexploration-1.Rmd’ using ‘UTF-8’... failed + ‘mbnmatime-overview.Rmd’ using ‘UTF-8’... OK + ‘outputs-4.Rmd’ using ‘UTF-8’... failed + ‘predictions-5.Rmd’ using ‘UTF-8’... OK + ‘runmbnmatime-2.Rmd’ using ‘UTF-8’... OK + ``` + +# mc2d + +
+ +* Version: 0.2.0 +* GitHub: NA +* Source code: https://github.com/cran/mc2d +* Date/Publication: 2023-07-17 16:00:02 UTC +* Number of recursive dependencies: 84 + +Run `revdepcheck::cloud_details(, "mc2d")` for more info + +
+ +## Newly broken + +* checking whether package ‘mc2d’ can be installed ... WARNING + ``` + Found the following significant warnings: + Warning: replacing previous import ‘ggplot2::ggpar’ by ‘ggpubr::ggpar’ when loading ‘mc2d’ + See ‘/tmp/workdir/mc2d/new/mc2d.Rcheck/00install.out’ for details. + ``` + +## In both + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘docmcEnglish.Rnw’ using Sweave + Loading required package: mvtnorm + Warning: replacing previous import ‘ggplot2::ggpar’ by ‘ggpubr::ggpar’ when loading ‘mc2d’ + + Attaching package: ‘mc2d’ + + The following objects are masked from ‘package:base’: + + pmax, pmin + ... + l.179 \RequirePackage{grfext}\relax + ^^M + ! ==> Fatal error occurred, no output PDF file produced! + --- failed re-building ‘mc2dLmEnglish.rnw’ + + SUMMARY: processing the following files failed: + ‘docmcEnglish.Rnw’ ‘mc2dLmEnglish.rnw’ + + Error: Vignette re-building failed. + Execution halted + ``` + +# MetaIntegrator + +
+ +* Version: 2.1.3 +* GitHub: NA +* Source code: https://github.com/cran/MetaIntegrator +* Date/Publication: 2020-02-26 13:00:11 UTC +* Number of recursive dependencies: 178 + +Run `revdepcheck::cloud_details(, "MetaIntegrator")` for more info + +
+ +## Newly broken + +* checking whether package ‘MetaIntegrator’ can be installed ... WARNING + ``` + Found the following significant warnings: + Warning: replacing previous import ‘ggplot2::ggpar’ by ‘ggpubr::ggpar’ when loading ‘MetaIntegrator’ + See ‘/tmp/workdir/MetaIntegrator/new/MetaIntegrator.Rcheck/00install.out’ for details. + ``` + +## In both + +* checking installed package size ... NOTE + ``` + installed size is 6.8Mb + sub-directories of 1Mb or more: + data 3.9Mb + doc 2.1Mb + ``` + +* checking dependencies in R code ... NOTE + ``` + Namespaces in Imports field not imported from: + ‘BiocManager’ ‘DT’ ‘GEOmetadb’ ‘RMySQL’ ‘RSQLite’ ‘gplots’ ‘pheatmap’ + ‘readr’ + All declared Imports should be used. + ``` + +# MF.beta4 + +
+ +* Version: 1.0.3 +* GitHub: https://github.com/AnneChao/MF.beta4 +* Source code: https://github.com/cran/MF.beta4 +* Date/Publication: 2024-04-16 16:30:02 UTC +* Number of recursive dependencies: 173 + +Run `revdepcheck::cloud_details(, "MF.beta4")` for more info + +
+ +## Newly broken + +* checking whether package ‘MF.beta4’ can be installed ... WARNING + ``` + Found the following significant warnings: + Warning: replacing previous import ‘ggplot2::ggpar’ by ‘ggpubr::ggpar’ when loading ‘MF.beta4’ + See ‘/tmp/workdir/MF.beta4/new/MF.beta4.Rcheck/00install.out’ for details. + ``` + +## In both + +* checking re-building of vignette outputs ... WARNING + ``` + Error(s) in re-building vignettes: + ... + --- re-building ‘Introduction.Rnw’ using Sweave + Error: processing vignette 'Introduction.Rnw' failed with diagnostics: + Running 'texi2dvi' on 'Introduction.tex' failed. + LaTeX errors: + ! LaTeX Error: File `pdfpages.sty' not found. + + Type X to quit or to proceed, + or enter new name. (Default extension: sty) + ... + l.4 ^^M + + ! ==> Fatal error occurred, no output PDF file produced! + --- failed re-building ‘Introduction.Rnw’ + + SUMMARY: processing the following file failed: + ‘Introduction.Rnw’ + + Error: Vignette re-building failed. + Execution halted + ``` + +# MiMIR + +
+ +* Version: 1.5 +* GitHub: NA +* Source code: https://github.com/cran/MiMIR +* Date/Publication: 2024-02-01 08:50:02 UTC +* Number of recursive dependencies: 188 + +Run `revdepcheck::cloud_details(, "MiMIR")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘MiMIR-Ex.R’ failed + The error most likely occurred in: + + > ### Name: LOBOV_accuracies + > ### Title: LOBOV_accuracies + > ### Aliases: LOBOV_accuracies + > + > ### ** Examples + > + > require(pROC) + ... + | Pruning samples on5SD: + 56 metabolites x 500 samples + | Performing scaling ... DONE! + | Imputation ... DONE! + > p_avail<-colnames(b_p)[c(1:5)] + > LOBOV_accuracies(sur$surrogates, b_p, p_avail, MiMIR::acc_LOBOV) + Error in compute_geom_2(..., self = self) : + argument "theme" is missing, with no default + Calls: LOBOV_accuracies ... use_defaults -> eval_from_theme -> %||% -> calc_element + Execution halted + ``` + +# miRetrieve + +
+ +* Version: 1.3.4 +* GitHub: NA +* Source code: https://github.com/cran/miRetrieve +* Date/Publication: 2021-09-18 17:30:02 UTC +* Number of recursive dependencies: 126 + +Run `revdepcheck::cloud_details(, "miRetrieve")` for more info + +
+ +## Newly broken + +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(miRetrieve) + > + > test_check("miRetrieve") + [ FAIL 1 | WARN 11 | SKIP 0 | PASS 202 ] + + ══ Failed tests ════════════════════════════════════════════════════════════════ + ... + 9. └─ggplot2 (local) compute_geom_2(..., self = self) + 10. └─self$geom$use_defaults(data, self$aes_params, modifiers, theme = theme) + 11. └─ggplot2 (local) use_defaults(..., self = self) + 12. └─ggplot2:::eval_from_theme(default_aes, theme) + 13. ├─calc_element("geom", theme) %||% .default_geom_element + 14. └─ggplot2::calc_element("geom", theme) + + [ FAIL 1 | WARN 11 | SKIP 0 | PASS 202 ] + Error: Test failures + Execution halted + ``` + +# missingHE + +
+ +* Version: 1.5.0 +* GitHub: NA +* Source code: https://github.com/cran/missingHE +* Date/Publication: 2023-03-21 08:50:02 UTC +* Number of recursive dependencies: 151 + +Run `revdepcheck::cloud_details(, "missingHE")` for more info + +
+ +## Newly broken + +* checking whether package ‘missingHE’ can be installed ... WARNING + ``` + Found the following significant warnings: + Warning: replacing previous import ‘ggplot2::ggpar’ by ‘ggpubr::ggpar’ when loading ‘missingHE’ + See ‘/tmp/workdir/missingHE/new/missingHE.Rcheck/00install.out’ for details. + ``` + +## In both + +* checking dependencies in R code ... NOTE + ``` + Namespace in Imports field not imported from: ‘mcmcr’ + All declared Imports should be used. + ``` + +# misspi + +
+ +* Version: 0.1.0 +* GitHub: NA +* Source code: https://github.com/cran/misspi +* Date/Publication: 2023-10-17 09:50:02 UTC +* Number of recursive dependencies: 88 + +Run `revdepcheck::cloud_details(, "misspi")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘misspi-Ex.R’ failed + The error most likely occurred in: + + > ### Name: evaliq + > ### Title: Evaluate the Imputation Quality + > ### Aliases: evaliq + > + > ### ** Examples + > + > # A very quick example + ... + > er.eval <- evaliq(x.true[na.idx], x.est[na.idx]) + `geom_smooth()` using formula = 'y ~ x' + > + > # Interactive plot + > er.eval <- evaliq(x.true[na.idx], x.est[na.idx], interactive = TRUE) + `geom_smooth()` using formula = 'y ~ x' + Error in compute_geom_2(..., self = self) : + argument "theme" is missing, with no default + Calls: evaliq ... use_defaults -> eval_from_theme -> %||% -> calc_element + Execution halted + ``` + +# mlr3spatiotempcv + +
+ +* Version: 2.3.1 +* GitHub: https://github.com/mlr-org/mlr3spatiotempcv +* Source code: https://github.com/cran/mlr3spatiotempcv +* Date/Publication: 2024-04-17 12:10:05 UTC +* Number of recursive dependencies: 168 + +Run `revdepcheck::cloud_details(, "mlr3spatiotempcv")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘mlr3spatiotempcv-Ex.R’ failed + The error most likely occurred in: + + > ### Name: autoplot.ResamplingCustomCV + > ### Title: Visualization Functions for Non-Spatial CV Methods. + > ### Aliases: autoplot.ResamplingCustomCV plot.ResamplingCustomCV + > + > ### ** Examples + > + > if (mlr3misc::require_namespaces(c("sf", "patchwork"), quietly = TRUE)) { + ... + 22. └─ggplot2 (local) FUN(X[[i]], ...) + 23. └─g$draw_key(data, g$params, key_size) + 24. └─ggplot2 (local) draw_key(...) + 25. └─ggplot2::draw_key_point(data, params, size) + 26. ├─grid::pointsGrob(...) + 27. │ └─grid::grob(...) + 28. └─ggplot2::ggpar(...) + 29. └─rlang:::Ops.quosure(pointsize, .pt) + 30. └─rlang::abort(...) + Execution halted + ``` + +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > if (requireNamespace("testthat", quietly = TRUE)) { + + library("checkmate") + + library("testthat") + + library("mlr3spatiotempcv") + + test_check("mlr3spatiotempcv") + + } + Loading required package: mlr3 + ... + • 2-autoplot/sptcvcstf-2d-time-var-fold-1-rep-2.svg + • 2-autoplot/sptcvcstf-2d-time-var-fold-1-sample-fold-n.svg + • 2-autoplot/sptcvcstf-2d-time-var-fold-1.svg + • 2-autoplot/sptcvcstf-2d-time-var-sample-fold-n.svg + • 2-autoplot/sptcvcstf-3d-time-var-fold-1-2-sample-fold-n.svg + • 2-autoplot/sptcvcstf-3d-time-var-fold-1-2.svg + • 2-autoplot/sptcvcstf-3d-time-var-fold-1-sample-fold-n.svg + • autoplot_buffer/spcvbuffer-fold-1-2.svg + Error: Test failures + Execution halted + ``` + +## In both + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘spatiotemp-viz.Rmd’ + ... + + > knitr::opts_chunk$set(collapse = TRUE, comment = "#>") + + > knitr::include_graphics("../man/figures/sptcv_cstf_multiplot.png") + + When sourcing ‘spatiotemp-viz.R’: + Error: Cannot find the file(s): "../man/figures/sptcv_cstf_multiplot.png" + Execution halted + + ‘mlr3spatiotempcv.Rmd’ using ‘UTF-8’... OK + ‘spatiotemp-viz.Rmd’ using ‘UTF-8’... failed + ``` + +* checking installed package size ... NOTE + ``` + installed size is 6.4Mb + sub-directories of 1Mb or more: + data 3.4Mb + help 1.2Mb + ``` + +# modeltime.resample + +
+ +* Version: 0.2.3 +* GitHub: https://github.com/business-science/modeltime.resample +* Source code: https://github.com/cran/modeltime.resample +* Date/Publication: 2023-04-12 15:50:02 UTC +* Number of recursive dependencies: 229 + +Run `revdepcheck::cloud_details(, "modeltime.resample")` for more info + +
+ +## Newly broken + +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > + > # Machine Learning + > library(tidymodels) + ── Attaching packages ────────────────────────────────────── tidymodels 1.2.0 ── + ✔ broom 1.0.5 ✔ recipes 1.0.10 + ✔ dials 1.2.1 ✔ rsample 1.2.1 + ... + 10. └─ggplot2 (local) compute_geom_2(..., self = self) + 11. └─self$geom$use_defaults(data, self$aes_params, modifiers, theme = theme) + 12. └─ggplot2 (local) use_defaults(..., self = self) + 13. └─ggplot2:::eval_from_theme(default_aes, theme) + 14. ├─calc_element("geom", theme) %||% .default_geom_element + 15. └─ggplot2::calc_element("geom", theme) + + [ FAIL 1 | WARN 4 | SKIP 0 | PASS 16 ] + Error: Test failures + Execution halted + ``` + +## In both + +* checking dependencies in R code ... NOTE + ``` + Namespaces in Imports field not imported from: + ‘crayon’ ‘dials’ ‘glue’ ‘parsnip’ + All declared Imports should be used. + ``` + +# MSPRT + +
+ +* Version: 3.0 +* GitHub: NA +* Source code: https://github.com/cran/MSPRT +* Date/Publication: 2020-11-13 10:20:05 UTC +* Number of recursive dependencies: 87 + +Run `revdepcheck::cloud_details(, "MSPRT")` for more info + +
+ +## Newly broken + +* checking whether package ‘MSPRT’ can be installed ... WARNING + ``` + Found the following significant warnings: + Warning: replacing previous import ‘ggplot2::ggpar’ by ‘ggpubr::ggpar’ when loading ‘MSPRT’ + See ‘/tmp/workdir/MSPRT/new/MSPRT.Rcheck/00install.out’ for details. + ``` + +## In both + +* checking dependencies in R code ... NOTE + ``` + Namespaces in Imports field not imported from: + ‘datasets’ ‘grDevices’ ‘graphics’ ‘iterators’ ‘methods’ + All declared Imports should be used. + ``` + +# neatmaps + +
+ +* Version: 2.1.0 +* GitHub: https://github.com/PhilBoileau/neatmaps +* Source code: https://github.com/cran/neatmaps +* Date/Publication: 2019-05-12 19:10:03 UTC +* Number of recursive dependencies: 99 + +Run `revdepcheck::cloud_details(, "neatmaps")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘neatmaps-Ex.R’ failed + The error most likely occurred in: + + > ### Name: consClustResTable + > ### Title: Consensus Cluster Results in a Table + > ### Aliases: consClustResTable + > + > ### ** Examples + > + > # create the data frame using the network, node and edge attributes + ... + + node_attr_df, + + edge_df) + > + > # run the neatmap code on df + > neat_res <- neatmap(df, scale_df = "ecdf", max_k = 3, reps = 100, + + xlab = "vars", ylab = "nets", xlab_cex = 1, ylab_cex = 1) + Error in compute_geom_2(..., self = self) : + argument "theme" is missing, with no default + Calls: neatmap ... use_defaults -> eval_from_theme -> %||% -> calc_element + Execution halted + ``` + +## In both + +* checking installed package size ... NOTE + ``` + installed size is 6.3Mb + ``` + +# NetFACS + +
+ +* Version: 0.5.0 +* GitHub: NA +* Source code: https://github.com/cran/NetFACS +* Date/Publication: 2022-12-06 17:32:35 UTC +* Number of recursive dependencies: 101 + +Run `revdepcheck::cloud_details(, "NetFACS")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘NetFACS-Ex.R’ failed + The error most likely occurred in: + + > ### Name: network_conditional + > ### Title: Create a network based on conditional probabilities of dyads of + > ### elements + > ### Aliases: network_conditional + > + > ### ** Examples + > + ... + Warning in grid.Call.graphics(C_text, as.graphicsAnnot(x$label), x$x, x$y, : + font family 'Arial Narrow' not found in PostScript font database + Warning in grid.Call.graphics(C_text, as.graphicsAnnot(x$label), x$x, x$y, : + font family 'Arial Narrow' not found in PostScript font database + Warning in grid.Call.graphics(C_text, as.graphicsAnnot(x$label), x$x, x$y, : + font family 'Arial Narrow' not found in PostScript font database + Error in grid.Call.graphics(C_text, as.graphicsAnnot(x$label), x$x, x$y, : + invalid font type + Calls: ... drawDetails -> drawDetails.text -> grid.Call.graphics + Execution halted + ``` + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘netfacs_tutorial.Rmd’ + ... + Warning in grid.Call.graphics(C_text, as.graphicsAnnot(x$label), x$x, x$y, : + font family 'Arial Narrow' not found in PostScript font database + Warning in grid.Call.graphics(C_text, as.graphicsAnnot(x$label), x$x, x$y, : + font family 'Arial Narrow' not found in PostScript font database + Warning in grid.Call.graphics(C_text, as.graphicsAnnot(x$label), x$x, x$y, : + font family 'Arial Narrow' not found in PostScript font database + + When sourcing ‘netfacs_tutorial.R’: + Error: invalid font type + Execution halted + + ‘netfacs_tutorial.Rmd’ using ‘UTF-8’... failed + ``` + +# NIMAA + +
+ +* Version: 0.2.1 +* GitHub: https://github.com/jafarilab/NIMAA +* Source code: https://github.com/cran/NIMAA +* Date/Publication: 2022-04-11 14:12:45 UTC +* Number of recursive dependencies: 173 + +Run `revdepcheck::cloud_details(, "NIMAA")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘NIMAA-Ex.R’ failed + The error most likely occurred in: + + > ### Name: extractSubMatrix + > ### Title: Extract the non-missing submatrices from a given matrix. + > ### Aliases: extractSubMatrix + > + > ### ** Examples + > + > # load part of the beatAML data + ... + binmatnest.temperature + 13.21221 + Size of Square: 66 rows x 66 columns + Size of Rectangular_row: 6 rows x 105 columns + Size of Rectangular_col: 99 rows x 2 columns + Size of Rectangular_element_max: 59 rows x 79 columns + Error in compute_geom_2(..., self = self) : + argument "theme" is missing, with no default + Calls: extractSubMatrix ... use_defaults -> eval_from_theme -> %||% -> calc_element + Execution halted + ``` + +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(NIMAA) + > + > test_check("NIMAA") + binmatnest.temperature + 13.21246 + Size of Square: 66 rows x 66 columns + ... + 11. └─ggplot2 (local) compute_geom_2(..., self = self) + 12. └─self$geom$use_defaults(data, self$aes_params, modifiers, theme = theme) + 13. └─ggplot2 (local) use_defaults(..., self = self) + 14. └─ggplot2:::eval_from_theme(default_aes, theme) + 15. ├─calc_element("geom", theme) %||% .default_geom_element + 16. └─ggplot2::calc_element("geom", theme) + + [ FAIL 1 | WARN 4 | SKIP 0 | PASS 7 ] + Error: Test failures + Execution halted + ``` + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘NIMAA-vignette.Rmd’ + ... + + shape = c("Square", "Rectangular_element_max"), row.vars = "patient_id", + + .... [TRUNCATED] + binmatnest.temperature + 20.12109 + Size of Square: 96 rows x 96 columns + Size of Rectangular_element_max: 87 rows x 140 columns + + When sourcing ‘NIMAA-vignette.R’: + Error: argument "theme" is missing, with no default + Execution halted + + ‘NIMAA-vignette.Rmd’ using ‘UTF-8’... failed + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘NIMAA-vignette.Rmd’ using rmarkdown + ``` + +## In both + +* checking installed package size ... NOTE + ``` + installed size is 5.5Mb + sub-directories of 1Mb or more: + data 1.0Mb + doc 4.0Mb + ``` + +* checking data for non-ASCII characters ... NOTE + ``` + Note: found 24 marked UTF-8 strings + ``` + +# nswgeo + +
+ +* Version: 0.4.0 +* GitHub: https://github.com/cidm-ph/nswgeo +* Source code: https://github.com/cran/nswgeo +* Date/Publication: 2024-01-29 13:40:05 UTC +* Number of recursive dependencies: 61 + +Run `revdepcheck::cloud_details(, "nswgeo")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘nswgeo-Ex.R’ failed + The error most likely occurred in: + + > ### Name: australia + > ### Title: Geospatial data of the Australian state and territory + > ### administrative boundaries. + > ### Aliases: australia states + > ### Keywords: datasets + > + > ### ** Examples + ... + 15. └─ggplot2 (local) FUN(X[[i]], ...) + 16. └─base::lapply(...) + 17. └─ggplot2 (local) FUN(X[[i]], ...) + 18. └─g$draw_key(data, g$params, key_size) + 19. └─ggplot2 (local) draw_key(...) + 20. └─ggplot2::draw_key_polygon(data, params, size) + 21. └─rlang:::Summary.quosure(from_theme(thin), 1.524, na.rm = FALSE) + 22. └─rlang:::abort_quosure_op("Summary", .Generic) + 23. └─rlang::abort(...) + Execution halted + ``` + +## In both + +* checking data for non-ASCII characters ... NOTE + ``` + Note: found 1 marked UTF-8 string + ``` + +# OenoKPM + +
+ +* Version: 2.4.1 +* GitHub: NA +* Source code: https://github.com/cran/OenoKPM +* Date/Publication: 2024-04-08 19:20:10 UTC +* Number of recursive dependencies: 85 + +Run `revdepcheck::cloud_details(, "OenoKPM")` for more info + +
+ +## Newly broken + +* checking whether package ‘OenoKPM’ can be installed ... WARNING + ``` + Found the following significant warnings: + Warning: replacing previous import ‘ggplot2::ggpar’ by ‘ggpubr::ggpar’ when loading ‘OenoKPM’ + See ‘/tmp/workdir/OenoKPM/new/OenoKPM.Rcheck/00install.out’ for details. + ``` + +# OmicNavigator + +
+ +* Version: 1.13.13 +* GitHub: https://github.com/abbvie-external/OmicNavigator +* Source code: https://github.com/cran/OmicNavigator +* Date/Publication: 2023-08-25 20:40:02 UTC +* Number of recursive dependencies: 86 + +Run `revdepcheck::cloud_details(, "OmicNavigator")` for more info + +
+ +## Newly broken + +* checking tests ... ERROR + ``` + Running ‘tinytest.R’ + Running the tests in ‘tests/tinytest.R’ failed. + Complete output: + > # Test files in inst/tinytest/ + > if (requireNamespace("tinytest", quietly = TRUE)) { + + suppressMessages(tinytest::test_package("OmicNavigator")) + + } + + testAdd.R..................... 0 tests + testAdd.R..................... 0 tests + ... + testPlot.R.................... 140 tests OK + testPlot.R.................... 141 tests OK + testPlot.R.................... 141 tests OK + testPlot.R.................... 141 tests OK + testPlot.R.................... 142 tests OK + testPlot.R.................... 142 tests OK + testPlot.R.................... 143 tests OK Error in compute_geom_2(..., self = self) : + argument "theme" is missing, with no default + Calls: suppressMessages ... use_defaults -> eval_from_theme -> %||% -> calc_element + Execution halted + ``` + +## In both + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘OmicNavigatorAPI.Rnw’ using Sweave + OmicNavigator R package version: 1.13.13 + The app is not installed. Install it with installApp() + Installing study "ABC" in /tmp/Rtmpc8E08Z/file279050a9efa7 + Exporting study "ABC" as an R package + Note: No maintainer email was specified. Using the placeholder: Unknown + Calculating pairwise overlaps. This may take a while... + Exported study to /tmp/Rtmpc8E08Z/ONstudyABC + Success! + ... + l.14 ^^M + + ! ==> Fatal error occurred, no output PDF file produced! + --- failed re-building ‘OmicNavigatorUsersGuide.Rnw’ + + SUMMARY: processing the following files failed: + ‘OmicNavigatorAPI.Rnw’ ‘OmicNavigatorUsersGuide.Rnw’ + + Error: Vignette re-building failed. + Execution halted + ``` + +# otsad + +
+ +* Version: 0.2.0 +* GitHub: https://github.com/alaineiturria/otsad +* Source code: https://github.com/cran/otsad +* Date/Publication: 2019-09-06 09:50:02 UTC +* Number of recursive dependencies: 109 + +Run `revdepcheck::cloud_details(, "otsad")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘otsad-Ex.R’ failed + The error most likely occurred in: + + > ### Name: CpKnnCad + > ### Title: Classic processing KNN based Conformal Anomaly Detector + > ### (KNN-CAD) + > ### Aliases: CpKnnCad + > + > ### ** Examples + > + ... + + reducefp = TRUE + + ) + > + > ## Plot results + > res <- cbind(df, result) + > PlotDetections(res, title = "KNN-CAD ANOMALY DETECTOR") + Error in compute_geom_2(..., self = self) : + argument "theme" is missing, with no default + Calls: PlotDetections ... use_defaults -> eval_from_theme -> %||% -> calc_element + Execution halted + ``` + +## In both + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + ... + --- re-building ‘otsad.Rnw’ using knitr + Error: processing vignette 'otsad.Rnw' failed with diagnostics: + Running 'texi2dvi' on 'otsad.tex' failed. + LaTeX errors: + ! LaTeX Error: File `colortbl.sty' not found. + + Type X to quit or to proceed, + or enter new name. (Default extension: sty) + ... + l.270 \long + \def\@secondoffive#1#2#3#4#5{#2}^^M + ! ==> Fatal error occurred, no output PDF file produced! + --- failed re-building ‘otsad.Rnw’ + + SUMMARY: processing the following file failed: + ‘otsad.Rnw’ + + Error: Vignette re-building failed. + Execution halted + ``` + +# pdxTrees + +
+ +* Version: 0.4.0 +* GitHub: https://github.com/mcconvil/pdxTrees +* Source code: https://github.com/cran/pdxTrees +* Date/Publication: 2020-08-17 14:00:02 UTC +* Number of recursive dependencies: 106 + +Run `revdepcheck::cloud_details(, "pdxTrees")` for more info + +
+ +## Newly broken + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘pdxTrees-vignette.Rmd’ + ... + > berkeley_graph + transition_states(states = Mature_Size, + + transition_length = 10, state_length = 8) + enter_grow() + + + exit_shrink() + Warning: Failed to apply `after_scale()` modifications to legend + Caused by error in `build()`: + ! argument "theme" is missing, with no default + + When sourcing ‘pdxTrees-vignette.R’: + Error: promise already under evaluation: recursive default argument reference or earlier problems? + Execution halted + + ‘pdxTrees-vignette.Rmd’ using ‘UTF-8’... failed + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘pdxTrees-vignette.Rmd’ using rmarkdown + ``` + +## In both + +* checking LazyData ... NOTE + ``` + 'LazyData' is specified without a 'data' directory + ``` + +# personalized + +
+ +* Version: 0.2.7 +* GitHub: https://github.com/jaredhuling/personalized +* Source code: https://github.com/cran/personalized +* Date/Publication: 2022-06-27 20:20:03 UTC +* Number of recursive dependencies: 94 + +Run `revdepcheck::cloud_details(, "personalized")` for more info + +
+ +## Newly broken + +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > Sys.setenv("R_TESTS" = "") + > library(testthat) + > library(personalized) + Loading required package: glmnet + Loading required package: Matrix + Loaded glmnet 4.1-8 + Loading required package: mgcv + ... + 14. └─ggplot2 (local) compute_geom_2(..., self = self) + 15. └─self$geom$use_defaults(data, self$aes_params, modifiers, theme = theme) + 16. └─ggplot2 (local) use_defaults(..., self = self) + 17. └─ggplot2:::eval_from_theme(default_aes, theme) + 18. ├─calc_element("geom", theme) %||% .default_geom_element + 19. └─ggplot2::calc_element("geom", theme) + + [ FAIL 1 | WARN 2 | SKIP 0 | PASS 215 ] + Error: Test failures + Execution halted + ``` + +# PGRdup + +
+ +* Version: 0.2.3.9 +* GitHub: https://github.com/aravind-j/PGRdup +* Source code: https://github.com/cran/PGRdup +* Date/Publication: 2023-08-31 22:10:16 UTC +* Number of recursive dependencies: 69 + +Run `revdepcheck::cloud_details(, "PGRdup")` for more info + +
+ +## Newly broken + +* checking re-building of vignette outputs ... ERROR + ``` + Error(s) in re-building vignettes: + ... + --- re-building ‘Introduction.Rmd’ using rmarkdown_notangle + ! Undefined control sequence. + l.108 \NewDocumentCommand + \citeproctext{}{} + + Error: processing vignette 'Introduction.Rmd' failed with diagnostics: + LaTeX failed to compile /tmp/workdir/PGRdup/new/PGRdup.Rcheck/vign_test/PGRdup/vignettes/Introduction.tex. See https://yihui.org/tinytex/r/#debugging for debugging tips. See Introduction.log for more info. + --- failed re-building ‘Introduction.Rmd’ + + SUMMARY: processing the following file failed: + ‘Introduction.Rmd’ + + Error: Vignette re-building failed. + Execution halted + ``` + +## Newly fixed + +* checking re-building of vignette outputs ... WARNING + ``` + Error(s) in re-building vignettes: + --- re-building ‘Introduction.Rmd’ using rmarkdown_notangle + Trying to upgrade TinyTeX automatically now... + If reinstallation fails, try install_tinytex() again. Then install the following packages: + + tinytex::tlmgr_install(c("amscls", "amsfonts", "amsmath", "atbegshi", "atveryend", "auxhook", "babel", "bibtex", "bigintcalc", "bitset", "booktabs", "cm", "ctablestack", "dehyph", "dvipdfmx", "dvips", "ec", "epstopdf-pkg", "etex", "etexcmds", "etoolbox", "euenc", "everyshi", "fancyvrb", "filehook", "firstaid", "float", "fontspec", "framed", "geometry", "gettitlestring", "glyphlist", "graphics", "graphics-cfg", "graphics-def", "helvetic", "hycolor", "hyperref", "hyph-utf8", "hyphen-base", "iftex", "inconsolata", "infwarerr", "intcalc", "knuth-lib", "kpathsea", "kvdefinekeys", "kvoptions", "kvsetkeys", "l3backend", "l3kernel", "l3packages", "latex", "latex-amsmath-dev", "latex-bin", "latex-fonts", "latex-tools-dev", "latexconfig", "latexmk", "letltxmacro", "lm", "lm-math", "ltxcmds", "lua-alt-getopt", "lua-uni-algos", "luahbtex", "lualatex-math", "lualibs", "luaotfload", "luatex", "luatexbase", "mdwtools", "metafont", "mfware", "modes", "natbib", "pdfescape", "pdftex", "pdftexcmds", "plain", "psnfss", "refcount", "rerunfilecheck", "scheme-infraonly", "selnolig", "stringenc", "symbol", "tex", "tex-ini-files", "texlive-scripts", "texlive.infra", "times", "tipa", "tools", "unicode-data", "unicode-math", "uniquecounter", "url", "xcolor", "xetex", "xetexconfig", "xkeyval", "xunicode", "zapfding")) + + The directory /opt/TinyTeX/texmf-local is not empty. It will be backed up to /tmp/RtmpQwt2mx/filed245f15abf1 and restored later. + + tlmgr: no auxiliary texmf trees defined, so nothing removed + ... + + Error: processing vignette 'Introduction.Rmd' failed with diagnostics: + LaTeX failed to compile /tmp/workdir/PGRdup/old/PGRdup.Rcheck/vign_test/PGRdup/vignettes/Introduction.tex. See https://yihui.org/tinytex/r/#debugging for debugging tips. See Introduction.log for more info. + --- failed re-building ‘Introduction.Rmd’ + + SUMMARY: processing the following file failed: + ‘Introduction.Rmd’ + + Error: Vignette re-building failed. + Execution halted + ``` + +# plantTracker + +
+ +* Version: 1.1.0 +* GitHub: https://github.com/aestears/plantTracker +* Source code: https://github.com/cran/plantTracker +* Date/Publication: 2023-05-05 18:20:02 UTC +* Number of recursive dependencies: 84 + +Run `revdepcheck::cloud_details(, "plantTracker")` for more info + +
+ +## Newly broken + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘Suggested_plantTracker_Workflow.Rmd’ + ... + a single row. + + When sourcing ‘Suggested_plantTracker_Workflow.R’: + Error: Summary operations are not defined for quosures. Do you need to unquote + the quosure? + + # Bad: min(myquosure) + ... + Error: Summary operations are not defined for quosures. Do you need to unquote + the quosure? + + # Bad: min(myquosure) + + # Good: min(!!myquosure) + Execution halted + + ‘Suggested_plantTracker_Workflow.Rmd’ using ‘UTF-8’... failed + ‘Using_the_plantTracker_trackSpp_function.Rmd’ using ‘UTF-8’... failed + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘Suggested_plantTracker_Workflow.Rmd’ using rmarkdown + Warning in options[opts_class] <- Map(code_folding_class, options[opts_class], : + number of items to replace is not a multiple of replacement length + Warning in options[opts_attr] <- Map(code_folding_attr, options[opts_attr], : + number of items to replace is not a multiple of replacement length + Warning in options[opts_class] <- Map(code_folding_class, options[opts_class], : + number of items to replace is not a multiple of replacement length + Warning in options[opts_attr] <- Map(code_folding_attr, options[opts_attr], : + number of items to replace is not a multiple of replacement length + ... + + # Good: min(!!myquosure) + --- failed re-building ‘Using_the_plantTracker_trackSpp_function.Rmd’ + + SUMMARY: processing the following files failed: + ‘Suggested_plantTracker_Workflow.Rmd’ + ‘Using_the_plantTracker_trackSpp_function.Rmd’ + + Error: Vignette re-building failed. + Execution halted + ``` + +# Plasmidprofiler + +
+ +* Version: 0.1.6 +* GitHub: NA +* Source code: https://github.com/cran/Plasmidprofiler +* Date/Publication: 2017-01-06 01:10:47 +* Number of recursive dependencies: 90 + +Run `revdepcheck::cloud_details(, "Plasmidprofiler")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘Plasmidprofiler-Ex.R’ failed + The error most likely occurred in: + + > ### Name: main + > ### Title: Main: Run everything + > ### Aliases: main + > + > ### ** Examples + > + > main(blastdata, + ... + Warning: Vectorized input to `element_text()` is not officially supported. + ℹ Results may be unexpected or may change in future versions of ggplot2. + Warning in geom_tile(aes(x = Plasmid, y = Sample, label = AMR_gene, fill = Inc_group, : + Ignoring unknown aesthetics: label and text + Warning: Use of `report$Sureness` is discouraged. + ℹ Use `Sureness` instead. + Error in compute_geom_2(..., self = self) : + argument "theme" is missing, with no default + Calls: main ... use_defaults -> eval_from_theme -> %||% -> calc_element + Execution halted + ``` + +# plotDK + +
+ +* Version: 0.1.0 +* GitHub: NA +* Source code: https://github.com/cran/plotDK +* Date/Publication: 2021-10-01 08:00:02 UTC +* Number of recursive dependencies: 86 + +Run `revdepcheck::cloud_details(, "plotDK")` for more info + +
+ +## Newly broken + +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(plotDK) + > + > test_check("plotDK") + [ FAIL 1 | WARN 0 | SKIP 0 | PASS 49 ] + + ══ Failed tests ════════════════════════════════════════════════════════════════ + ... + 9. └─ggplot2 (local) compute_geom_2(..., self = self) + 10. └─self$geom$use_defaults(data, self$aes_params, modifiers, theme = theme) + 11. └─ggplot2 (local) use_defaults(..., self = self) + 12. └─ggplot2:::eval_from_theme(default_aes, theme) + 13. ├─calc_element("geom", theme) %||% .default_geom_element + 14. └─ggplot2::calc_element("geom", theme) + + [ FAIL 1 | WARN 0 | SKIP 0 | PASS 49 ] + Error: Test failures + Execution halted + ``` + +## In both + +* checking dependencies in R code ... NOTE + ``` + Namespace in Imports field not imported from: ‘mapproj’ + All declared Imports should be used. + ``` + +* checking data for non-ASCII characters ... NOTE + ``` + Note: found 12992 marked UTF-8 strings + ``` + +# plotly + +
+ +* Version: 4.10.4 +* GitHub: https://github.com/plotly/plotly.R +* Source code: https://github.com/cran/plotly +* Date/Publication: 2024-01-13 22:40:02 UTC +* Number of recursive dependencies: 148 + +Run `revdepcheck::cloud_details(, "plotly")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘plotly-Ex.R’ failed + The error most likely occurred in: + + > ### Name: style + > ### Title: Modify trace(s) + > ### Aliases: style + > + > ### ** Examples + > + > ## Don't show: + ... + + style(p, marker.line = list(width = 2.5), marker.size = 10) + + ## Don't show: + + }) # examplesIf + > (p <- ggplotly(qplot(data = mtcars, wt, mpg, geom = c("point", "smooth")))) + Warning: `qplot()` was deprecated in ggplot2 3.4.0. + `geom_smooth()` using method = 'loess' and formula = 'y ~ x' + Error in compute_geom_2(..., self = self) : + argument "theme" is missing, with no default + Calls: ... use_defaults -> eval_from_theme -> %||% -> calc_element + Execution halted + ``` + +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library("testthat") + > library("plotly") + Loading required package: ggplot2 + + Attaching package: 'plotly' + + The following object is masked from 'package:ggplot2': + ... + • plotly-subplot/subplot-bump-axis-annotation.svg + • plotly-subplot/subplot-bump-axis-image.svg + • plotly-subplot/subplot-bump-axis-shape-shared.svg + • plotly-subplot/subplot-bump-axis-shape.svg + • plotly-subplot/subplot-reposition-annotation.svg + • plotly-subplot/subplot-reposition-image.svg + • plotly-subplot/subplot-reposition-shape-fixed.svg + • plotly-subplot/subplot-reposition-shape.svg + Error: Test failures + Execution halted + ``` + +## In both + +* checking installed package size ... NOTE + ``` + installed size is 7.9Mb + sub-directories of 1Mb or more: + R 1.5Mb + htmlwidgets 4.0Mb + ``` + +# pmartR + +
+ +* Version: 2.4.4 +* GitHub: https://github.com/pmartR/pmartR +* Source code: https://github.com/cran/pmartR +* Date/Publication: 2024-02-27 21:20:02 UTC +* Number of recursive dependencies: 150 + +Run `revdepcheck::cloud_details(, "pmartR")` for more info + +
+ +## Newly broken + +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(pmartR) + > + > test_check("pmartR") + [ FAIL 1 | WARN 0 | SKIP 6 | PASS 2575 ] + + ══ Skipped tests (6) ═══════════════════════════════════════════════════════════ + ... + • plots/plot-spansres-color-high-color-low.svg + • plots/plot-spansres.svg + • plots/plot-statres-anova-volcano.svg + • plots/plot-statres-anova.svg + • plots/plot-statres-combined-volcano.svg + • plots/plot-statres-combined.svg + • plots/plot-statres-gtest.svg + • plots/plot-totalcountfilt.svg + Error: Test failures + Execution halted + ``` + +## In both + +* checking installed package size ... NOTE + ``` + installed size is 14.3Mb + sub-directories of 1Mb or more: + libs 11.4Mb + ``` + +# pmxTools + +
+ +* Version: 1.3 +* GitHub: https://github.com/kestrel99/pmxTools +* Source code: https://github.com/cran/pmxTools +* Date/Publication: 2023-02-21 16:00:08 UTC +* Number of recursive dependencies: 85 + +Run `revdepcheck::cloud_details(, "pmxTools")` for more info + +
+ +## Newly broken + +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(pmxTools) + Loading required package: patchwork + > + > test_check("pmxTools") + [ FAIL 1 | WARN 1 | SKIP 12 | PASS 110 ] + + ... + 24. └─handlers[[1L]](cnd) + 25. └─cli::cli_abort(...) + 26. └─rlang::abort(...) + + [ FAIL 1 | WARN 1 | SKIP 12 | PASS 110 ] + Deleting unused snapshots: + • plot/conditioned-distplot.svg + • plot/perc.svg + Error: Test failures + Execution halted + ``` + +## In both + +* checking Rd cross-references ... NOTE + ``` + Package unavailable to check Rd xrefs: ‘DiagrammeR’ + ``` + +# PointedSDMs + +
+ +* Version: 1.3.2 +* GitHub: https://github.com/PhilipMostert/PointedSDMs +* Source code: https://github.com/cran/PointedSDMs +* Date/Publication: 2024-02-02 09:50:02 UTC +* Number of recursive dependencies: 143 + +Run `revdepcheck::cloud_details(, "PointedSDMs")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘PointedSDMs-Ex.R’ failed + The error most likely occurred in: + + > ### Name: dataSDM + > ### Title: R6 class for creating a 'dataSDM' object. + > ### Aliases: dataSDM + > + > ### ** Examples + > + > + ... + 17. └─ggplot2 (local) FUN(X[[i]], ...) + 18. └─g$draw_key(data, g$params, key_size) + 19. └─ggplot2 (local) draw_key(...) + 20. └─ggplot2::draw_key_point(data, params, size) + 21. ├─grid::pointsGrob(...) + 22. │ └─grid::grob(...) + 23. └─ggplot2::ggpar(...) + 24. └─rlang:::Ops.quosure(pointsize, .pt) + 25. └─rlang::abort(...) + Execution halted + ``` + +## In both + +* checking running R code from vignettes ... WARNING + ``` + Errors in running code in vignettes: + when running code in ‘Marked_Point_Process.Rmd’ + ... + + > knitr::opts_chunk$set(collapse = TRUE, comment = "#>", + + eval = FALSE, warning = FALSE, message = FALSE) + + > library(spatstat) + + When sourcing ‘Marked_Point_Process.R’: + ... + + resolution = "high") + + When sourcing ‘Spatiotemporal_example.R’: + Error: there is no package called ‘USAboundaries’ + Execution halted + + ‘Marked_Point_Process.Rmd’ using ‘UTF-8’... failed + ‘Setophaga.Rmd’ using ‘UTF-8’... failed + ‘Solitary_tinamou.Rmd’ using ‘UTF-8’... failed + ‘Spatiotemporal_example.Rmd’ using ‘UTF-8’... failed + ``` + +# posterior + +
+ +* Version: 1.5.0 +* GitHub: https://github.com/stan-dev/posterior +* Source code: https://github.com/cran/posterior +* Date/Publication: 2023-10-31 08:30:02 UTC +* Number of recursive dependencies: 120 + +Run `revdepcheck::cloud_details(, "posterior")` for more info + +
+ +## Newly broken + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + ... + --- re-building ‘posterior.Rmd’ using rmarkdown + --- finished re-building ‘posterior.Rmd’ + + --- re-building ‘rvar.Rmd’ using rmarkdown + + Quitting from lines at lines 526-529 [mixture] (rvar.Rmd) + Error: processing vignette 'rvar.Rmd' failed with diagnostics: + Problem while setting up geom aesthetics. + ... + NULL, NULL, NULL, NULL, 0.2, NULL, list(NULL, NULL, NULL, 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, NULL, NULL, NULL, TRUE), NULL, "right", NULL, NULL, NULL, "center", NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, c(0, 0, 0, 0), list(), 11, list("grey92", NA, NULL, NULL, TRUE), list(), 5.5, NULL, NULL, list("white", NULL, NULL, NULL, FALSE, TRUE), NULL, list(NULL, 0.5, NULL, NULL, FALSE, TRUE), NULL, NULL, NULL, NULL, FALSE, list(NULL, + "white", NULL, NULL, TRUE), list(NULL, NULL, NULL, 1.2, 0, 1, NULL, NULL, c(0, 0, 5.5, 0), NULL, TRUE), "panel", list(NULL, NULL, NULL, NULL, 0, 1, NULL, NULL, c(0, 0, 5.5, 0), NULL, TRUE), list(NULL, NULL, NULL, 0.8, 1, 1, NULL, NULL, c(5.5, 0, 0, 0), NULL, TRUE), "panel", list(NULL, NULL, NULL, 1.2, 0.5, 0.5, NULL, NULL, NULL, NULL, TRUE), "topleft", NULL, c(5.5, 5.5, 5.5, 5.5), list("grey85", NA, NULL, NULL, TRUE), NULL, NULL, "inherit", "inside", list(NULL, NULL, "grey10", 0.8, NULL, + NULL, NULL, NULL, c(4.4, 4.4, 4.4, 4.4), NULL, TRUE), NULL, NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, NULL, -90, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, NULL, 90, NULL, NULL, NULL, TRUE), NULL, 2.75, 2.75)) + --- failed re-building ‘rvar.Rmd’ + + SUMMARY: processing the following file failed: + ‘rvar.Rmd’ + + Error: Vignette re-building failed. + Execution halted + ``` + +## In both + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘rvar.Rmd’ + ... + > y + rvar<4000>[3] mean ± sd: + [1] 3.00 ± 1.00 2.02 ± 0.99 0.96 ± 0.99 + + > X + y + + When sourcing ‘rvar.R’: + Error: Cannot broadcast array of shape [4000,3,1] to array of shape [4000,4,3]: + All dimensions must be 1 or equal. + Execution halted + + ‘posterior.Rmd’ using ‘UTF-8’... OK + ‘rvar.Rmd’ using ‘UTF-8’... failed + ``` + +# PPQplan + +
+ +* Version: 1.1.0 +* GitHub: https://github.com/allenzhuaz/PPQplan +* Source code: https://github.com/cran/PPQplan +* Date/Publication: 2020-10-08 04:30:06 UTC +* Number of recursive dependencies: 119 + +Run `revdepcheck::cloud_details(, "PPQplan")` for more info + +
+ +## Newly broken + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘PPQnote.Rmd’ using rmarkdown + --- finished re-building ‘PPQnote.Rmd’ + + --- re-building ‘PPQplan-vignette.Rmd’ using rmarkdown + ``` + +## In both + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘PPQplan-vignette.Rmd’ + ... + + > devtools::load_all() + + When sourcing ‘PPQplan-vignette.R’: + Error: Could not find a root 'DESCRIPTION' file that starts with '^Package' in + '/tmp/Rtmpv5CY0G/file171e30ae70cd/vignettes'. + ℹ Are you in your project directory and does your project have a 'DESCRIPTION' + file? + Execution halted + + ‘PPQnote.Rmd’ using ‘UTF-8’... OK + ‘PPQplan-vignette.Rmd’ using ‘UTF-8’... failed + ``` + +* checking installed package size ... NOTE + ``` + installed size is 12.1Mb + sub-directories of 1Mb or more: + doc 12.0Mb + ``` + +* checking LazyData ... NOTE + ``` + 'LazyData' is specified without a 'data' directory + ``` + +# ppseq + +
+ +* Version: 0.2.4 +* GitHub: https://github.com/zabore/ppseq +* Source code: https://github.com/cran/ppseq +* Date/Publication: 2024-04-04 18:20:02 UTC +* Number of recursive dependencies: 106 + +Run `revdepcheck::cloud_details(, "ppseq")` for more info + +
+ +## Newly broken + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘one_sample_expansion.Rmd’ + ... + + + + + > ptest <- plot(one_sample_cal_tbl, type1_range = c(0.05, + + 0.1), minimum_power = 0.7, plotly = TRUE) + + ... + + > ptest <- plot(two_sample_cal_tbl, type1_range = c(0.05, + + 0.1), minimum_power = 0.7, plotly = TRUE) + + When sourcing ‘two_sample_randomized.R’: + Error: argument "theme" is missing, with no default + Execution halted + + ‘one_sample_expansion.Rmd’ using ‘UTF-8’... failed + ‘two_sample_randomized.Rmd’ using ‘UTF-8’... failed + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + ... + --- re-building ‘one_sample_expansion.Rmd’ using rmarkdown + + Quitting from lines at lines 183-188 [unnamed-chunk-13] (one_sample_expansion.Rmd) + Error: processing vignette 'one_sample_expansion.Rmd' failed with diagnostics: + argument "theme" is missing, with no default + --- failed re-building ‘one_sample_expansion.Rmd’ + + --- re-building ‘two_sample_randomized.Rmd’ using rmarkdown + ... + Quitting from lines at lines 179-184 [unnamed-chunk-13] (two_sample_randomized.Rmd) + Error: processing vignette 'two_sample_randomized.Rmd' failed with diagnostics: + argument "theme" is missing, with no default + --- failed re-building ‘two_sample_randomized.Rmd’ + + SUMMARY: processing the following files failed: + ‘one_sample_expansion.Rmd’ ‘two_sample_randomized.Rmd’ + + Error: Vignette re-building failed. + Execution halted + ``` + +## In both + +* checking installed package size ... NOTE + ``` + installed size is 11.0Mb + sub-directories of 1Mb or more: + doc 10.5Mb + ``` + +# processmapR + +
+ +* Version: 0.5.3 +* GitHub: https://github.com/bupaverse/processmapr +* Source code: https://github.com/cran/processmapR +* Date/Publication: 2023-04-06 12:50:02 UTC +* Number of recursive dependencies: 118 + +Run `revdepcheck::cloud_details(, "processmapR")` for more info + +
+ +## Newly broken + +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(processmapR) + + Attaching package: 'processmapR' + + The following object is masked from 'package:stats': + + ... + 20. └─ggplot2 (local) use_defaults(..., self = self) + 21. └─ggplot2:::eval_from_theme(default_aes, theme) + 22. ├─calc_element("geom", theme) %||% .default_geom_element + 23. └─ggplot2::calc_element("geom", theme) + ── Failure ('test_trace_explorer.R:240:3'): test trace_explorer on eventlog with param `plotly` ── + `chart` inherits from 'gg'/'ggplot' not 'plotly'. + + [ FAIL 6 | WARN 0 | SKIP 10 | PASS 107 ] + Error: Test failures + Execution halted + ``` + +# QuadratiK + +
+ +* Version: 1.0.0 +* GitHub: NA +* Source code: https://github.com/cran/QuadratiK +* Date/Publication: 2024-02-23 18:30:05 UTC +* Number of recursive dependencies: 131 + +Run `revdepcheck::cloud_details(, "QuadratiK")` for more info + +
+ +## Newly broken + +* checking whether package ‘QuadratiK’ can be installed ... WARNING + ``` + Found the following significant warnings: + Warning: replacing previous import ‘ggplot2::ggpar’ by ‘ggpubr::ggpar’ when loading ‘QuadratiK’ + See ‘/tmp/workdir/QuadratiK/new/QuadratiK.Rcheck/00install.out’ for details. + ``` + +## In both + +* checking installed package size ... NOTE + ``` + installed size is 15.9Mb + sub-directories of 1Mb or more: + libs 15.2Mb + ``` + +# Radviz + +
+ +* Version: 0.9.3 +* GitHub: https://github.com/yannabraham/Radviz +* Source code: https://github.com/cran/Radviz +* Date/Publication: 2022-03-25 18:10:02 UTC +* Number of recursive dependencies: 64 + +Run `revdepcheck::cloud_details(, "Radviz")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘Radviz-Ex.R’ failed + The error most likely occurred in: + + > ### Name: Radviz + > ### Title: Radviz Projection of Multidimensional Data + > ### Aliases: Radviz + > + > ### ** Examples + > + > data(iris) + > das <- c('Sepal.Length','Sepal.Width','Petal.Length','Petal.Width') + > S <- make.S(das) + > rv <- do.radviz(iris,S) + > plot(rv,anchors.only=FALSE) + Error in plot.radviz(rv, anchors.only = FALSE) : + 'language' object cannot be coerced to type 'double' + Calls: plot -> plot.radviz + Execution halted + ``` + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘multivariate_analysis.Rmd’ + ... + + > classic.S <- make.S(get.optim(classic.optim)) + + > btcells.rv <- do.radviz(btcells.df, classic.S) + + > plot(btcells.rv) + geom_point(aes(color = Treatment)) + + ... + [1] 15792 18 + + > ct.rv + + When sourcing ‘single_cell_projections.R’: + Error: 'language' object cannot be coerced to type 'double' + Execution halted + + ‘multivariate_analysis.Rmd’ using ‘UTF-8’... failed + ‘single_cell_projections.Rmd’ using ‘UTF-8’... failed + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘multivariate_analysis.Rmd’ using rmarkdown + ``` + +## In both + +* checking installed package size ... NOTE + ``` + installed size is 5.9Mb + sub-directories of 1Mb or more: + libs 4.7Mb + ``` + +# 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: 112 + +Run `revdepcheck::cloud_details(, "rangeMapper")` for more info + +
+ +## Newly broken + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘Case_studies_Valcu_et_al_2012.Rmd’ + ... + + geom_sf(data = bmr, aes(fill = value), size = 0.05) + scale_fill_gradientn(co .... [TRUNCATED] + + When sourcing ‘Case_studies_Valcu_et_al_2012.R’: + Error: Summary operations are not defined for quosures. Do you need to unquote + the quosure? + + # Bad: min(myquosure) + + # Good: min(!!myquosure) + Execution halted + + ‘Case_studies_Valcu_et_al_2012.Rmd’ using ‘UTF-8’... failed + ‘rangeMapper.Rmd’ using ‘UTF-8’... OK + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘Case_studies_Valcu_et_al_2012.Rmd’ using rmarkdown + ``` + +# rassta + +
+ +* Version: 1.0.5 +* GitHub: https://github.com/bafuentes/rassta +* Source code: https://github.com/cran/rassta +* Date/Publication: 2022-08-30 22:30:02 UTC +* Number of recursive dependencies: 121 + +Run `revdepcheck::cloud_details(, "rassta")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘rassta-Ex.R’ failed + The error most likely occurred in: + + > ### Name: select_functions + > ### Title: Select Constrained Univariate Distribution Functions + > ### Aliases: select_functions + > + > ### ** Examples + > + > require(terra) + ... + > # Single-layer SpatRaster of topographic classification units + > ## 5 classification units + > tcf <- list.files(path = p, pattern = "topography.tif", full.names = TRUE) + > tcu <- terra::rast(tcf) + > # Automatic selection of distribution functions + > tdif <- select_functions(cu.rast = tcu, var.rast = tvars, fun = mean) + Error in compute_geom_2(..., self = self) : + argument "theme" is missing, with no default + Calls: select_functions ... use_defaults -> eval_from_theme -> %||% -> calc_element + Execution halted + ``` + +* checking tests ... ERROR + ``` + Running ‘tinytest.R’ + Running the tests in ‘tests/tinytest.R’ failed. + Complete output: + > + > if ( requireNamespace("tinytest", quietly=TRUE) ){ + + tinytest::test_package("rassta") + + } + + Attaching package: 'rassta' + + ... + test_select_functions.R....... 0 tests + test_select_functions.R....... 0 tests + test_select_functions.R....... 0 tests + test_select_functions.R....... 0 tests + test_select_functions.R....... 0 tests + test_select_functions.R....... 0 tests + test_select_functions.R....... 0 tests Error in compute_geom_2(..., self = self) : + argument "theme" is missing, with no default + Calls: ... use_defaults -> eval_from_theme -> %||% -> calc_element + Execution halted + ``` + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘signature.Rmd’ + ... + > clim.var <- rast(vardir) + + > clim.cu <- rast(paste(d, "/climate.tif", sep = "")) + + > clim.difun <- select_functions(cu.rast = clim.cu, + + var.rast = clim.var, mode = "auto") + + ... + When sourcing ‘signature.R’: + Error: argument "theme" is missing, with no default + Execution halted + + ‘classunits.Rmd’ using ‘UTF-8’... OK + ‘modeling.Rmd’ using ‘UTF-8’... OK + ‘sampling.Rmd’ using ‘UTF-8’... OK + ‘signature.Rmd’ using ‘UTF-8’... failed + ‘similarity.Rmd’ using ‘UTF-8’... OK + ‘stratunits.Rmd’ using ‘UTF-8’... OK + ``` + +# RCTrep + +
+ +* Version: 1.2.0 +* GitHub: https://github.com/duolajiang/RCTrep +* Source code: https://github.com/cran/RCTrep +* Date/Publication: 2023-11-02 14:40:02 UTC +* Number of recursive dependencies: 166 + +Run `revdepcheck::cloud_details(, "RCTrep")` for more info + +
+ +## Newly broken + +* checking whether package ‘RCTrep’ can be installed ... WARNING + ``` + Found the following significant warnings: + Warning: replacing previous import ‘ggplot2::ggpar’ by ‘ggpubr::ggpar’ when loading ‘RCTrep’ + See ‘/tmp/workdir/RCTrep/new/RCTrep.Rcheck/00install.out’ for details. + ``` + +# redistmetrics + +
+ +* Version: 1.0.7 +* GitHub: https://github.com/alarm-redist/redistmetrics +* Source code: https://github.com/cran/redistmetrics +* Date/Publication: 2023-12-12 19:30:02 UTC +* Number of recursive dependencies: 85 + +Run `revdepcheck::cloud_details(, "redistmetrics")` for more info + +
+ +## Newly broken + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘compactness.Rmd’ + ... + + labs(fill = "none") + + When sourcing ‘compactness.R’: + Error: Summary operations are not defined for quosures. Do you need to unquote + the quosure? + + # Bad: min(myquosure) + ... + + # Good: min(!!myquosure) + Execution halted + + ‘compactness.Rmd’ using ‘UTF-8’... failed + ‘distances.Rmd’ using ‘UTF-8’... OK + ‘other.Rmd’ using ‘UTF-8’... OK + ‘party.Rmd’ using ‘UTF-8’... OK + ‘redistmetrics.Rmd’ using ‘UTF-8’... OK + ‘splits.Rmd’ using ‘UTF-8’... OK + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘compactness.Rmd’ using rmarkdown + + Quitting from lines at lines 29-35 [unnamed-chunk-2] (compactness.Rmd) + Error: processing vignette 'compactness.Rmd' failed with diagnostics: + Summary operations are not defined for quosures. Do you need to unquote + the quosure? + + # Bad: min(myquosure) + + ... + # Good: min(!!myquosure) + --- failed re-building ‘compactness.Rmd’ + + --- re-building ‘distances.Rmd’ using rmarkdown + --- finished re-building ‘distances.Rmd’ + + --- re-building ‘other.Rmd’ using rmarkdown + --- finished re-building ‘other.Rmd’ + + --- re-building ‘party.Rmd’ using rmarkdown + ``` + +## In both + +* checking installed package size ... NOTE + ``` + installed size is 13.7Mb + sub-directories of 1Mb or more: + libs 12.6Mb + ``` + +# ref.ICAR + +
+ +* Version: 2.0.1 +* GitHub: NA +* Source code: https://github.com/cran/ref.ICAR +* Date/Publication: 2023-08-22 08:50:02 UTC +* Number of recursive dependencies: 103 + +Run `revdepcheck::cloud_details(, "ref.ICAR")` for more info + +
+ +## Newly broken + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘ref-icar-vignette.Rmd’ + ... + + scale_fill_brewer(palette = "OrRd") + labs(title = "Plot of observed \n verbal SAT s ..." ... [TRUNCATED] + + When sourcing ‘ref-icar-vignette.R’: + Error: Summary operations are not defined for quosures. Do you need to unquote + the quosure? + + # Bad: min(myquosure) + + # Good: min(!!myquosure) + Execution halted + + ‘ref-icar-vignette.Rmd’ using ‘UTF-8’... failed + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘ref-icar-vignette.Rmd’ using rmarkdown + Warning in eng_r(options) : + Failed to tidy R code in chunk 'unnamed-chunk-1'. Reason: + Error : The formatR package is required by the chunk option tidy = TRUE but not installed; tidy = TRUE will be ignored. + + Warning in eng_r(options) : + Failed to tidy R code in chunk 'unnamed-chunk-2'. Reason: + Error : The formatR package is required by the chunk option tidy = TRUE but not installed; tidy = TRUE will be ignored. + + ... + # Bad: min(myquosure) + + # Good: min(!!myquosure) + --- failed re-building ‘ref-icar-vignette.Rmd’ + + SUMMARY: processing the following file failed: + ‘ref-icar-vignette.Rmd’ + + Error: Vignette re-building failed. + Execution halted + ``` + +# remap + +
+ +* Version: 0.3.1 +* GitHub: https://github.com/jadonwagstaff/remap +* Source code: https://github.com/cran/remap +* Date/Publication: 2023-06-14 20:50:02 UTC +* Number of recursive dependencies: 64 + +Run `revdepcheck::cloud_details(, "remap")` for more info + +
+ +## Newly broken + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘Introduction_to_remap.Rmd’ + ... + + ggti .... [TRUNCATED] + + When sourcing ‘Introduction_to_remap.R’: + Error: Summary operations are not defined for quosures. Do you need to unquote + the quosure? + + # Bad: min(myquosure) + + # Good: min(!!myquosure) + Execution halted + + ‘Introduction_to_remap.Rmd’ using ‘UTF-8’... failed + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + ... + --- re-building ‘Introduction_to_remap.Rmd’ using rmarkdown + + Quitting from lines at lines 43-54 [initial_map] (Introduction_to_remap.Rmd) + Error: processing vignette 'Introduction_to_remap.Rmd' failed with diagnostics: + Summary operations are not defined for quosures. Do you need to unquote + the quosure? + + # Bad: min(myquosure) + + # Good: min(!!myquosure) + --- failed re-building ‘Introduction_to_remap.Rmd’ + + SUMMARY: processing the following file failed: + ‘Introduction_to_remap.Rmd’ + + Error: Vignette re-building failed. + Execution halted + ``` + +# rKIN + +
+ +* Version: 1.0.2 +* GitHub: https://github.com/salbeke/rKIN +* Source code: https://github.com/cran/rKIN +* Date/Publication: 2023-10-02 22:20:02 UTC +* Number of recursive dependencies: 92 + +Run `revdepcheck::cloud_details(, "rKIN")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘rKIN-Ex.R’ failed + The error most likely occurred in: + + > ### Name: estEllipse + > ### Title: Estimate Bivariate Normal Ellipse Isotope Niche + > ### Aliases: estEllipse + > + > ### ** Examples + > + > library(rKIN) + ... + 15. └─ggplot2 (local) FUN(X[[i]], ...) + 16. └─base::lapply(...) + 17. └─ggplot2 (local) FUN(X[[i]], ...) + 18. └─g$draw_key(data, g$params, key_size) + 19. └─ggplot2 (local) draw_key(...) + 20. └─ggplot2::draw_key_polygon(data, params, size) + 21. └─rlang:::Summary.quosure(from_theme(thin), 1.524, na.rm = FALSE) + 22. └─rlang:::abort_quosure_op("Summary", .Generic) + 23. └─rlang::abort(...) + Execution halted + ``` + +# rLFT + +
+ +* Version: 1.0.1 +* GitHub: NA +* Source code: https://github.com/cran/rLFT +* Date/Publication: 2021-09-24 04:10:02 UTC +* Number of recursive dependencies: 74 + +Run `revdepcheck::cloud_details(, "rLFT")` for more info + +
+ +## Newly broken + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘rLFT_Introduction.Rmd’ + ... + old-style crs object detected; please recreate object with a recent sf::st_crs() + + When sourcing ‘rLFT_Introduction.R’: + Error: Summary operations are not defined for quosures. Do you need to unquote + the quosure? + + # Bad: min(myquosure) + + # Good: min(!!myquosure) + Execution halted + + ‘rLFT_Introduction.Rmd’ using ‘UTF-8’... failed + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + ... + --- re-building ‘rLFT_Introduction.Rmd’ using rmarkdown + + Quitting from lines at lines 56-66 [unnamed-chunk-2] (rLFT_Introduction.Rmd) + Error: processing vignette 'rLFT_Introduction.Rmd' failed with diagnostics: + Summary operations are not defined for quosures. Do you need to unquote + the quosure? + + # Bad: min(myquosure) + + # Good: min(!!myquosure) + --- failed re-building ‘rLFT_Introduction.Rmd’ + + SUMMARY: processing the following file failed: + ‘rLFT_Introduction.Rmd’ + + Error: Vignette re-building failed. + Execution halted + ``` + +## In both + +* checking installed package size ... NOTE + ``` + installed size is 6.0Mb + sub-directories of 1Mb or more: + help 1.8Mb + libs 4.0Mb + ``` + +# roahd + +
+ +* Version: 1.4.3 +* GitHub: https://github.com/astamm/roahd +* Source code: https://github.com/cran/roahd +* Date/Publication: 2021-11-04 00:10:02 UTC +* Number of recursive dependencies: 88 + +Run `revdepcheck::cloud_details(, "roahd")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘roahd-Ex.R’ failed + The error most likely occurred in: + + > ### Name: plot.depthgram + > ### Title: Specialized method to plot 'depthgram' objects + > ### Aliases: plot.depthgram + > + > ### ** Examples + > + > N <- 50 + ... + + centerline = sin(2 * pi * grid), + + Cov = Cov + + ) + > names <- paste0("id_", 1:nrow(Data[[1]])) + > DG <- depthgram(Data, marginal_outliers = TRUE, ids = names) + > plot(DG) + Error in compute_geom_2(..., self = self) : + argument "theme" is missing, with no default + Calls: plot ... use_defaults -> eval_from_theme -> %||% -> calc_element + Execution halted + ``` + +## In both + +* checking installed package size ... NOTE + ``` + installed size is 7.2Mb + sub-directories of 1Mb or more: + data 4.8Mb + doc 1.7Mb + ``` + +# roptions + +
+ +* Version: 1.0.3 +* GitHub: NA +* Source code: https://github.com/cran/roptions +* Date/Publication: 2020-05-11 11:10:06 UTC +* Number of recursive dependencies: 70 + +Run `revdepcheck::cloud_details(, "roptions")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘roptions-Ex.R’ failed + The error most likely occurred in: + + > ### Name: box.spread + > ### Title: Box Spread Strategy Function + > ### Aliases: box.spread + > + > ### ** Examples + > + > box.spread(100, 105, 95, 110, 3.2, 2.6, 1.1, 2.4) + ... + 36 5.7 + 37 5.7 + 38 5.7 + 39 5.7 + 40 5.7 + 41 5.7 + Error in compute_geom_2(..., self = self) : + argument "theme" is missing, with no default + Calls: box.spread ... use_defaults -> eval_from_theme -> %||% -> calc_element + Execution halted + ``` + +## In both + +* checking LazyData ... NOTE + ``` + 'LazyData' is specified without a 'data' directory + ``` + +# scoringutils + +
+ +* Version: 1.2.2 +* GitHub: https://github.com/epiforecasts/scoringutils +* Source code: https://github.com/cran/scoringutils +* Date/Publication: 2023-11-29 15:50:10 UTC +* Number of recursive dependencies: 81 + +Run `revdepcheck::cloud_details(, "scoringutils")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘scoringutils-Ex.R’ failed + The error most likely occurred in: + + > ### Name: plot_predictions + > ### Title: Plot Predictions vs True Values + > ### Aliases: plot_predictions + > + > ### ** Examples + > + > library(ggplot2) + ... + 2.75, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 1, NULL, NULL, NULL, c(0, 2.2, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, NULL, c(0, 0, 0, 2.2 + ), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0.5, NULL, NULL, NULL, c(0, 2.2, 0, 2.2), NULL, TRUE), list("grey80", NULL, NULL, NULL, FALSE, FALSE), NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 2.75, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 0.75, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, list("grey80", NULL, NULL, NULL, FALSE, FALSE), NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, list(), c(5.5, 5.5, 5.5, 5.5), 11, NULL, NULL, list(), 1.2, + NULL, NULL, 5.5, NULL, NULL, NULL, NULL, 0.2, NULL, list(NULL, NULL, NULL, 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, NULL, NULL, NULL, TRUE), NULL, "bottom", NULL, NULL, NULL, "center", NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, c(0, 0, 0, 0), list(), 11, list(), list(), 5.5, NULL, NULL, list("grey92", NULL, NULL, NULL, FALSE, TRUE), list(), list(), NULL, NULL, NULL, NULL, FALSE, list(), list(NULL, NULL, NULL, 1.2, 0, 1, NULL, NULL, + c(0, 0, 5.5, 0), NULL, TRUE), "panel", list(NULL, NULL, NULL, NULL, 0, 1, NULL, NULL, c(0, 0, 5.5, 0), NULL, TRUE), list(NULL, NULL, NULL, 0.8, 1, 1, NULL, NULL, c(5.5, 0, 0, 0), NULL, TRUE), "panel", list(NULL, NULL, NULL, 1.2, 0.5, 0.5, NULL, NULL, NULL, NULL, TRUE), "topleft", NULL, c(5.5, 5.5, 5.5, 5.5), list(), NULL, NULL, "inherit", "inside", list(NULL, NULL, "grey10", 0.8, NULL, NULL, NULL, NULL, c(4.4, 4.4, 4.4, 4.4), NULL, TRUE), NULL, NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, + NULL, -90, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, NULL, 90, NULL, NULL, NULL, TRUE), NULL, 2.75, 2.75)) + Error in use_defaults(..., self = self) : + unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), NULL, list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.75, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, 90, NULL, c(0, + 2.75, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 1, NULL, NULL, NULL, c(0, 2.2, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL + Calls: ... .handleSimpleError -> h -> -> + Execution halted + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘metric-details.Rmd’ using rmarkdown + --- finished re-building ‘metric-details.Rmd’ + + --- re-building ‘scoring-forecasts-directly.Rmd’ using rmarkdown + --- finished re-building ‘scoring-forecasts-directly.Rmd’ + + --- re-building ‘scoringutils.Rmd’ using rmarkdown + ``` + +## In both + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘scoringutils.Rmd’ + ... + 2.75, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 1, NULL, NULL, NULL, c(0, 2.2, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, NULL, c(0, 0, 0, 2.2 + ), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0.5, NULL, NULL, NULL, c(0, 2.2, 0, 2.2), NULL, TRUE), list("grey80", NULL, NULL, NULL, FALSE, FALSE), NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 2.75, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 0.75, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, list("grey80", NULL, NULL, NULL, FALSE, FALSE), NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, list(), c(5.5, 5.5, 5.5, 5.5), 11, NULL, NULL, list(), 1.2, + NULL, NULL, 5.5, NULL, NULL, NULL, NULL, 0.2, NULL, list(NULL, NULL, NULL, 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, NULL, NULL, NULL, TRUE), NULL, "bottom", NULL, NULL, NULL, "center", NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, c(0, 0, 0, 0), list(), 11, list(), list(), 5.5, NULL, NULL, list("grey92", NULL, NULL, NULL, FALSE, TRUE), list(), list(), NULL, NULL, NULL, NULL, FALSE, list(), list(NULL, NULL, NULL, 1.2, 0, 1, NULL, NULL, + c(0, 0, 5.5, 0), NULL, TRUE), "panel", list(NULL, NULL, NULL, NULL, 0, 1, NULL, NULL, c(0, 0, 5.5, 0), NULL, TRUE), list(NULL, NULL, NULL, 0.8, 1, 1, NULL, NULL, c(5.5, 0, 0, 0), NULL, TRUE), "panel", list(NULL, NULL, NULL, 1.2, 0.5, 0.5, NULL, NULL, NULL, NULL, TRUE), "topleft", NULL, c(5.5, 5.5, 5.5, 5.5), list(), NULL, NULL, "inherit", "inside", list(NULL, NULL, "grey10", 0.8, NULL, NULL, NULL, NULL, c(4.4, 4.4, 4.4, 4.4), NULL, TRUE), NULL, NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, + NULL, -90, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, NULL, 90, NULL, NULL, NULL, TRUE), NULL, 2.75, 2.75)) + + When sourcing ‘scoringutils.R’: + Error: unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), NULL, list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.75, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, 90, NULL, c(0, + 2.75, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 1, NULL, NULL, NULL, c(0, 2.2, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, + Execution halted + + ‘metric-details.Rmd’ using ‘UTF-8’... OK + ‘scoring-forecasts-directly.Rmd’ using ‘UTF-8’... OK + ‘scoringutils.Rmd’ using ‘UTF-8’... failed + ``` + +# SCOUTer + +
+ +* Version: 1.0.0 +* GitHub: NA +* Source code: https://github.com/cran/SCOUTer +* Date/Publication: 2020-06-30 09:30:03 UTC +* Number of recursive dependencies: 99 + +Run `revdepcheck::cloud_details(, "SCOUTer")` for more info + +
+ +## Newly broken + +* checking whether package ‘SCOUTer’ can be installed ... WARNING + ``` + Found the following significant warnings: + Warning: replacing previous import ‘ggplot2::ggpar’ by ‘ggpubr::ggpar’ when loading ‘SCOUTer’ + See ‘/tmp/workdir/SCOUTer/new/SCOUTer.Rcheck/00install.out’ for details. + ``` + +# SCVA + +
+ +* Version: 1.3.1 +* GitHub: NA +* Source code: https://github.com/cran/SCVA +* Date/Publication: 2020-01-09 22:50:10 UTC +* Number of recursive dependencies: 80 + +Run `revdepcheck::cloud_details(, "SCVA")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘SCVA-Ex.R’ failed + The error most likely occurred in: + + > ### Name: graphly + > ### Title: Interactive plot of single-case data + > ### Aliases: graphly + > ### Keywords: Single-case design Graph + > + > ### ** Examples + > + > data(AB) + > graphly(design = "AB", data = AB) + Error in compute_geom_2(..., self = self) : + argument "theme" is missing, with no default + Calls: graphly ... use_defaults -> eval_from_theme -> %||% -> calc_element + Execution halted + ``` + +# see + +
+ +* Version: 0.8.4 +* GitHub: https://github.com/easystats/see +* Source code: https://github.com/cran/see +* Date/Publication: 2024-04-29 04:40:03 UTC +* Number of recursive dependencies: 234 + +Run `revdepcheck::cloud_details(, "see")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘see-Ex.R’ failed + The error most likely occurred in: + + > ### Name: geom_binomdensity + > ### Title: Add dot-densities for binary 'y' variables + > ### Aliases: geom_binomdensity + > + > ### ** Examples + > + > ## Don't show: + ... + 14. │ └─ggplot2 (local) f(l = layers[[i]], d = data[[i]]) + 15. │ └─l$compute_geom_2(d, theme = plot$theme) + 16. │ └─ggplot2 (local) compute_geom_2(..., self = self) + 17. │ └─self$geom$use_defaults(data, self$aes_params, modifiers, theme = theme) + 18. └─base::.handleSimpleError(...) + 19. └─rlang (local) h(simpleError(msg, call)) + 20. └─handlers[[1L]](cnd) + 21. └─cli::cli_abort(...) + 22. └─rlang::abort(...) + Execution halted + ``` + +# sfnetworks + +
+ +* Version: 0.6.4 +* GitHub: https://github.com/luukvdmeer/sfnetworks +* Source code: https://github.com/cran/sfnetworks +* Date/Publication: 2024-04-09 22:40:02 UTC +* Number of recursive dependencies: 106 + +Run `revdepcheck::cloud_details(, "sfnetworks")` for more info + +
+ +## Newly broken + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘sfn01_structure.Rmd’ using rmarkdown + ``` + +## In both + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘sfn01_structure.Rmd’ + ... + > plot(other_net, cex = 2, lwd = 2, main = "Straight lines") + + > st_geometry(edges) = st_sfc(c(l2, l3, l1), crs = 4326) + + > net = sfnetwork(nodes, edges) + Checking if spatial network structure is valid... + + ... + Error: ℹ In argument: `azimuth = edge_azimuth()`. + Caused by error in `st_geod_azimuth()`: + ! st_is_longlat(x) is not TRUE + Execution halted + + ‘sfn01_structure.Rmd’ using ‘UTF-8’... failed + ‘sfn02_preprocess_clean.Rmd’ using ‘UTF-8’... OK + ‘sfn03_join_filter.Rmd’ using ‘UTF-8’... OK + ‘sfn04_routing.Rmd’ using ‘UTF-8’... OK + ‘sfn05_morphers.Rmd’ using ‘UTF-8’... failed + ``` + +# sftrack + +
+ +* Version: 0.5.4 +* GitHub: https://github.com/mablab/sftrack +* Source code: https://github.com/cran/sftrack +* Date/Publication: 2023-03-16 12:20:02 UTC +* Number of recursive dependencies: 92 + +Run `revdepcheck::cloud_details(, "sftrack")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘sftrack-Ex.R’ failed + The error most likely occurred in: + + > ### Name: geom_sftrack + > ### Title: Function to plot sftrack objects in ggplot + > ### Aliases: geom_sftrack geom_sftrack.sftrack geom_sftrack.sftraj + > + > ### ** Examples + > + > #' + ... + 17. └─ggplot2 (local) FUN(X[[i]], ...) + 18. └─g$draw_key(data, g$params, key_size) + 19. └─ggplot2 (local) draw_key(...) + 20. └─ggplot2::draw_key_path(data, params, size) + 21. ├─grid::segmentsGrob(...) + 22. │ └─grid::grob(...) + 23. └─ggplot2::ggpar(...) + 24. └─rlang:::Ops.quosure(args$lwd, .pt) + 25. └─rlang::abort(...) + Execution halted + ``` + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘sftrack5_spatial.Rmd’ + ... + > ggplot() + geom_sftrack(data = my_sftraj) + + When sourcing ‘sftrack5_spatial.R’: + Error: Base operators are not defined for quosures. Do you need to unquote the + quosure? + + # Bad: myquosure * rhs + + # Good: !!myquosure * rhs + Execution halted + + ‘sftrack1_overview.Rmd’ using ‘UTF-8’... OK + ‘sftrack2_reading.Rmd’ using ‘UTF-8’... OK + ‘sftrack3_workingwith.Rmd’ using ‘UTF-8’... OK + ‘sftrack4_groups.Rmd’ using ‘UTF-8’... OK + ‘sftrack5_spatial.Rmd’ using ‘UTF-8’... failed + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘sftrack1_overview.Rmd’ using rmarkdown + ``` + +# sglg + +
+ +* Version: 0.2.2 +* GitHub: NA +* Source code: https://github.com/cran/sglg +* Date/Publication: 2022-09-04 03:50:01 UTC +* Number of recursive dependencies: 96 + +Run `revdepcheck::cloud_details(, "sglg")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘sglg-Ex.R’ failed + The error most likely occurred in: + + > ### Name: deviance_residuals + > ### Title: Deviance Residuals for a Generalized Log-gamma Regression Model + > ### Aliases: deviance_residuals + > + > ### ** Examples + > + > # Example 1 + > n <- 300 + > error <- rglg(n,0,1,1) + > y <- 0.5 + error + > fit <- glg(y~1,data=as.data.frame(y)) + > deviance_residuals(fit) + Error in compute_geom_2(..., self = self) : + argument "theme" is missing, with no default + Calls: deviance_residuals ... use_defaults -> eval_from_theme -> %||% -> calc_element + Execution halted + ``` + +# sievePH + +
+ +* Version: 1.0.4 +* GitHub: https://github.com/mjuraska/sievePH +* Source code: https://github.com/cran/sievePH +* Date/Publication: 2023-02-03 18:40:02 UTC +* Number of recursive dependencies: 82 + +Run `revdepcheck::cloud_details(, "sievePH")` for more info + +
+ +## Newly broken + +* checking whether package ‘sievePH’ can be installed ... WARNING + ``` + Found the following significant warnings: + Warning: replacing previous import ‘ggplot2::ggpar’ by ‘ggpubr::ggpar’ when loading ‘sievePH’ + See ‘/tmp/workdir/sievePH/new/sievePH.Rcheck/00install.out’ for details. + ``` + +# SouthParkRshiny + +
+ +* Version: 1.0.0 +* GitHub: https://github.com/Amalan-ConStat/SouthParkRshiny +* Source code: https://github.com/cran/SouthParkRshiny +* Date/Publication: 2024-03-09 11:10:08 UTC +* Number of recursive dependencies: 118 + +Run `revdepcheck::cloud_details(, "SouthParkRshiny")` for more info + +
+ +## Newly broken + +* checking whether package ‘SouthParkRshiny’ can be installed ... WARNING + ``` + Found the following significant warnings: + Warning: replacing previous import ‘ggplot2::ggpar’ by ‘ggpubr::ggpar’ when loading ‘SouthParkRshiny’ + See ‘/tmp/workdir/SouthParkRshiny/new/SouthParkRshiny.Rcheck/00install.out’ for details. + ``` + +## In both + +* checking installed package size ... NOTE + ``` + installed size is 8.6Mb + sub-directories of 1Mb or more: + data 8.0Mb + ``` + +* checking data for non-ASCII characters ... NOTE + ``` + Note: found 1562 marked UTF-8 strings + ``` + +# spatialrisk + +
+ +* Version: 0.7.1 +* GitHub: https://github.com/mharinga/spatialrisk +* Source code: https://github.com/cran/spatialrisk +* Date/Publication: 2024-02-21 12:50:02 UTC +* Number of recursive dependencies: 129 + +Run `revdepcheck::cloud_details(, "spatialrisk")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘spatialrisk-Ex.R’ failed + The error most likely occurred in: + + > ### Name: choropleth_ggplot2 + > ### Title: Map object of class sf using ggplot2 + > ### Aliases: choropleth_ggplot2 + > + > ### ** Examples + > + > test <- points_to_polygon(nl_postcode2, insurance, sum(amount, na.rm = TRUE)) + ... + 15. └─ggplot2 (local) FUN(X[[i]], ...) + 16. └─base::lapply(...) + 17. └─ggplot2 (local) FUN(X[[i]], ...) + 18. └─g$draw_key(data, g$params, key_size) + 19. └─ggplot2 (local) draw_key(...) + 20. └─ggplot2::draw_key_polygon(data, params, size) + 21. └─rlang:::Summary.quosure(from_theme(thin), 1.524, na.rm = FALSE) + 22. └─rlang:::abort_quosure_op("Summary", .Generic) + 23. └─rlang::abort(...) + Execution halted + ``` + +## In both + +* checking installed package size ... NOTE + ``` + installed size is 11.0Mb + sub-directories of 1Mb or more: + data 6.5Mb + help 1.7Mb + libs 2.7Mb + ``` + +* checking data for non-ASCII characters ... NOTE + ``` + Note: found 283 marked UTF-8 strings + ``` + +# spatialsample + +
+ +* Version: 0.5.1 +* GitHub: https://github.com/tidymodels/spatialsample +* Source code: https://github.com/cran/spatialsample +* Date/Publication: 2023-11-08 00:20:02 UTC +* Number of recursive dependencies: 107 + +Run `revdepcheck::cloud_details(, "spatialsample")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘spatialsample-Ex.R’ failed + The error most likely occurred in: + + > ### Name: autoplot.spatial_rset + > ### Title: Create a ggplot for spatial resamples. + > ### Aliases: autoplot.spatial_rset autoplot.spatial_block_cv + > + > ### ** Examples + > + > + ... + 15. └─ggplot2 (local) FUN(X[[i]], ...) + 16. └─base::lapply(...) + 17. └─ggplot2 (local) FUN(X[[i]], ...) + 18. └─g$draw_key(data, g$params, key_size) + 19. └─ggplot2 (local) draw_key(...) + 20. └─ggplot2::draw_key_polygon(data, params, size) + 21. └─rlang:::Summary.quosure(from_theme(thin), 1.524, na.rm = FALSE) + 22. └─rlang:::abort_quosure_op("Summary", .Generic) + 23. └─rlang::abort(...) + Execution halted + ``` + +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(spatialsample) + > + > sf::sf_extSoftVersion() + GEOS GDAL proj.4 GDAL_with_GEOS USE_PROJ_H + "3.8.0" "3.0.4" "6.3.1" "true" "true" + PROJ + ... + • autoplot/buffered-rset-plot.svg + • autoplot/buffered-vfold-plot.svg + • autoplot/buffered-vfold-split.svg + • autoplot/cluster-split-plots.svg + • autoplot/repeated-block-cv.svg + • autoplot/repeated-llo.svg + • autoplot/repeated-vfold.svg + • autoplot/snake-flips-rows-the-right-way.svg + Error: Test failures + Execution halted + ``` + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘spatialsample.Rmd’ + ... + > autoplot(cluster_folds) + + When sourcing ‘spatialsample.R’: + Error: Base operators are not defined for quosures. Do you need to unquote the + quosure? + + # Bad: myquosure * rhs + + # Good: !!myquosure * rhs + Execution halted + + ‘spatialsample.Rmd’ using ‘UTF-8’... failed + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + ... + --- re-building ‘spatialsample.Rmd’ using rmarkdown + + Quitting from lines at lines 56-62 [unnamed-chunk-6] (spatialsample.Rmd) + Error: processing vignette 'spatialsample.Rmd' failed with diagnostics: + Base operators are not defined for quosures. Do you need to unquote the + quosure? + + # Bad: myquosure * rhs + + # Good: !!myquosure * rhs + --- failed re-building ‘spatialsample.Rmd’ + + SUMMARY: processing the following file failed: + ‘spatialsample.Rmd’ + + Error: Vignette re-building failed. + Execution halted + ``` + +# spinifex + +
+ +* Version: 0.3.7.0 +* GitHub: https://github.com/nspyrison/spinifex +* Source code: https://github.com/cran/spinifex +* Date/Publication: 2024-01-29 14:40:02 UTC +* Number of recursive dependencies: 164 + +Run `revdepcheck::cloud_details(, "spinifex")` for more info + +
+ +## Newly broken + +* checking tests ... ERROR + ``` + Running ‘spelling.R’ + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(spinifex) + Loading required package: tourr + -------------------------------------------------------- + spinifex --- version 0.3.7.0 + Please share bugs, suggestions, and feature requests at: + ... + 12. └─ggplot2 (local) compute_geom_2(..., self = self) + 13. └─self$geom$use_defaults(data, self$aes_params, modifiers, theme = theme) + 14. └─ggplot2 (local) use_defaults(..., self = self) + 15. └─ggplot2:::eval_from_theme(default_aes, theme) + 16. ├─calc_element("geom", theme) %||% .default_geom_element + 17. └─ggplot2::calc_element("geom", theme) + + [ FAIL 3 | WARN 4 | SKIP 0 | PASS 78 ] + Error: Test failures + Execution halted + ``` + +# spmodel + +
+ +* Version: 0.6.0 +* GitHub: https://github.com/USEPA/spmodel +* Source code: https://github.com/cran/spmodel +* Date/Publication: 2024-04-16 23:40:02 UTC +* Number of recursive dependencies: 78 + +Run `revdepcheck::cloud_details(, "spmodel")` for more info + +
+ +## Newly broken + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘introduction.Rmd’ + ... + 8 186.3500 L 0 0 POINT (279050.9 1517324) + 9 362.3125 L 0 0 POINT (346145.9 1512479) + 10 430.5000 L 0 0 POINT (321354.6 1509966) + + > ggplot(moose, aes(color = presence)) + scale_color_viridis_d(option = "H") + + + geom_sf(size = 2) + + When sourcing ‘introduction.R’: + Error: 'language' object cannot be coerced to type 'integer' + Execution halted + + ‘introduction.Rmd’ using ‘UTF-8’... failed + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘introduction.Rmd’ using rmarkdown + ``` + +## In both + +* checking installed package size ... NOTE + ``` + installed size is 5.8Mb + sub-directories of 1Mb or more: + R 1.9Mb + data 1.7Mb + doc 1.5Mb + ``` + +# SqueakR + +
+ +* Version: 1.3.0 +* GitHub: https://github.com/osimon81/SqueakR +* Source code: https://github.com/cran/SqueakR +* Date/Publication: 2022-06-28 09:20:04 UTC +* Number of recursive dependencies: 142 + +Run `revdepcheck::cloud_details(, "SqueakR")` for more info + +
+ +## Newly broken + +* checking whether package ‘SqueakR’ can be installed ... WARNING + ``` + Found the following significant warnings: + Warning: replacing previous import ‘ggplot2::ggpar’ by ‘ggpubr::ggpar’ when loading ‘SqueakR’ + See ‘/tmp/workdir/SqueakR/new/SqueakR.Rcheck/00install.out’ for details. + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘SqueakR.Rmd’ using rmarkdown + ``` + +## In both + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘SqueakR.Rmd’ + ... + $ experimenters : NULL + $ experimental_data: list() + + > my_new_data <- add_timepoint_data(data_path = "../inst/extdata/Example_Mouse_Data.xlsx", + + t1 = 5, t2 = 25) + Adding call features Excel file to workspace... + + When sourcing ‘SqueakR.R’: + Error: `path` does not exist: ‘../inst/extdata/Example_Mouse_Data.xlsx’ + Execution halted + + ‘SqueakR.Rmd’ using ‘UTF-8’... failed + ``` + +* checking installed package size ... NOTE + ``` + installed size is 8.8Mb + sub-directories of 1Mb or more: + doc 8.2Mb + ``` + +# stats19 + +
+ +* Version: 3.0.3 +* GitHub: https://github.com/ropensci/stats19 +* Source code: https://github.com/cran/stats19 +* Date/Publication: 2024-02-09 00:30:07 UTC +* Number of recursive dependencies: 161 + +Run `revdepcheck::cloud_details(, "stats19")` for more info + +
+ +## Newly broken + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘blog.Rmd’ using rmarkdown + [WARNING] Citeproc: citation sarkar_street_2018 not found + --- finished re-building ‘blog.Rmd’ + + --- re-building ‘stats19-training-setup.Rmd’ using rmarkdown + --- finished re-building ‘stats19-training-setup.Rmd’ + + --- re-building ‘stats19-training.Rmd’ using rmarkdown + ``` + +## In both + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘blog.Rmd’ + ... + Try running dl_stats19(), change arguments or try later.FALSE + Reading in: + + + When sourcing ‘blog.R’: + Error: `file` is not one of the supported inputs: + • A filepath or character vector of filepaths + ... + + When sourcing ‘stats19.R’: + Error: Unknown colour name: ~ + Execution halted + + ‘blog.Rmd’ using ‘UTF-8’... failed + ‘stats19-training-setup.Rmd’ using ‘UTF-8’... OK + ‘stats19-training.Rmd’ using ‘UTF-8’... failed + ‘stats19-vehicles.Rmd’ using ‘UTF-8’... failed + ‘stats19.Rmd’ using ‘UTF-8’... failed + ``` + +# streamDepletr + +
+ +* Version: 0.2.0 +* GitHub: https://github.com/FoundrySpatial/streamDepletr +* Source code: https://github.com/cran/streamDepletr +* Date/Publication: 2023-07-19 21:30:02 UTC +* Number of recursive dependencies: 70 + +Run `revdepcheck::cloud_details(, "streamDepletr")` for more info + +
+ +## Newly broken + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘intro-to-streamDepletr.Rmd’ + ... + + .... [TRUNCATED] + + When sourcing ‘intro-to-streamDepletr.R’: + Error: Base operators are not defined for quosures. Do you need to unquote the + quosure? + + # Bad: myquosure * rhs + + # Good: !!myquosure * rhs + Execution halted + + ‘intro-to-streamDepletr.Rmd’ using ‘UTF-8’... failed + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘intro-to-streamDepletr.Rmd’ using rmarkdown + ``` + +# survminer + +
+ +* Version: 0.4.9 +* GitHub: https://github.com/kassambara/survminer +* Source code: https://github.com/cran/survminer +* Date/Publication: 2021-03-09 09:50:03 UTC +* Number of recursive dependencies: 130 + +Run `revdepcheck::cloud_details(, "survminer")` for more info + +
+ +## Newly broken + +* checking whether package ‘survminer’ can be installed ... WARNING + ``` + Found the following significant warnings: + Warning: replacing previous import ‘ggplot2::ggpar’ by ‘ggpubr::ggpar’ when loading ‘survminer’ + See ‘/tmp/workdir/survminer/new/survminer.Rcheck/00install.out’ for details. + ``` + +## In both + +* checking installed package size ... NOTE + ``` + installed size is 6.3Mb + sub-directories of 1Mb or more: + doc 5.5Mb + ``` + +# symptomcheckR + +
+ +* Version: 0.1.3 +* GitHub: https://github.com/ma-kopka/symptomcheckR +* Source code: https://github.com/cran/symptomcheckR +* Date/Publication: 2024-04-16 20:40:06 UTC +* Number of recursive dependencies: 101 + +Run `revdepcheck::cloud_details(, "symptomcheckR")` for more info + +
+ +## Newly broken + +* checking whether package ‘symptomcheckR’ can be installed ... WARNING + ``` + Found the following significant warnings: + Warning: replacing previous import ‘ggplot2::ggpar’ by ‘ggpubr::ggpar’ when loading ‘symptomcheckR’ + See ‘/tmp/workdir/symptomcheckR/new/symptomcheckR.Rcheck/00install.out’ for details. + ``` + +# tabledown + +
+ +* Version: 1.0.0 +* GitHub: https://github.com/masiraji/tabledown +* Source code: https://github.com/cran/tabledown +* Date/Publication: 2024-05-02 13:40:03 UTC +* Number of recursive dependencies: 145 + +Run `revdepcheck::cloud_details(, "tabledown")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘tabledown-Ex.R’ failed + The error most likely occurred in: + + > ### Name: ggreliability_plotly + > ### Title: A Function for Creating Item Response Theory based reliability + > ### plot based on plotly. + > ### Aliases: ggreliability_plotly + > + > ### ** Examples + > + ... + Iteration: 18, Log-Lik: -5351.363, Max-Change: 0.00054 + Iteration: 19, Log-Lik: -5351.363, Max-Change: 0.00012 + Iteration: 20, Log-Lik: -5351.363, Max-Change: 0.00035 + Iteration: 21, Log-Lik: -5351.363, Max-Change: 0.00010 + > + > plot <- ggreliability_plotly(data, model) + Error in compute_geom_2(..., self = self) : + argument "theme" is missing, with no default + Calls: ggreliability_plotly ... use_defaults -> eval_from_theme -> %||% -> calc_element + Execution halted + ``` + +## In both + +* checking data for non-ASCII characters ... NOTE + ``` + Note: found 551 marked UTF-8 strings + ``` + +# tcgaViz + +
+ +* Version: 1.0.2 +* GitHub: NA +* Source code: https://github.com/cran/tcgaViz +* Date/Publication: 2023-04-04 15:40:02 UTC +* Number of recursive dependencies: 139 + +Run `revdepcheck::cloud_details(, "tcgaViz")` for more info + +
+ +## Newly broken + +* checking whether package ‘tcgaViz’ can be installed ... WARNING + ``` + Found the following significant warnings: + Warning: replacing previous import ‘ggplot2::ggpar’ by ‘ggpubr::ggpar’ when loading ‘tcgaViz’ + See ‘/tmp/workdir/tcgaViz/new/tcgaViz.Rcheck/00install.out’ for details. + ``` + +# TCIU + +
+ +* Version: 1.2.5 +* GitHub: https://github.com/SOCR/TCIU +* Source code: https://github.com/cran/TCIU +* Date/Publication: 2024-03-08 17:00:05 UTC +* Number of recursive dependencies: 172 + +Run `revdepcheck::cloud_details(, "TCIU")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘TCIU-Ex.R’ failed + The error most likely occurred in: + + > ### Name: fmri_image + > ### Title: interactive graph object of the fMRI image + > ### Aliases: fmri_image + > + > ### ** Examples + > + > fmri_generate = fmri_simulate_func(dim_data = c(64, 64, 40), mask = mask) + > fmri_image(fmri_generate$fmri_data, option='manually', voxel_location = c(40,22,33), time = 4) + Error in compute_geom_2(..., self = self) : + argument "theme" is missing, with no default + Calls: fmri_image ... use_defaults -> eval_from_theme -> %||% -> calc_element + Execution halted + ``` + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘tciu-LT-kimesurface.Rmd’ + ... + + > sample_save[[2]] + + When sourcing ‘tciu-LT-kimesurface.R’: + Error: Problem while setting up geom aesthetics. + ℹ Error occurred in the 1st layer. + Caused by error in `compute_geom_2()`: + ... + + > fmri_image(fmri_generate$fmri_data, option = "manually", + + voxel_location = c(40, 22, 33), time = 4) + + When sourcing ‘tciu-fMRI-analytics.R’: + Error: argument "theme" is missing, with no default + Execution halted + + ‘tciu-LT-kimesurface.Rmd’ using ‘UTF-8’... failed + ‘tciu-fMRI-analytics.Rmd’ using ‘UTF-8’... failed + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘tciu-LT-kimesurface.Rmd’ using rmarkdown + + Quitting from lines at lines 159-160 [unnamed-chunk-5] (tciu-LT-kimesurface.Rmd) + Error: processing vignette 'tciu-LT-kimesurface.Rmd' failed with diagnostics: + Problem while setting up geom aesthetics. + ℹ Error occurred in the 1st layer. + Caused by error in `compute_geom_2()`: + ! unused argument (theme = list(list("black", 0.727272727272727, 1, "butt", FALSE, TRUE), list("white", "black", 0.727272727272727, 1, TRUE), list("", "plain", "black", 16, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), NULL, NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(4, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 4, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, 90, NULL, c(0, 4, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, + NULL, 1, -90, NULL, c(0, 0, 0, 4), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(3.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 3.2, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 1, NULL, NULL, NULL, c(0, 3.2, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, NULL, c(0, 0, 0, 3.2), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0.5, NULL, + ... + Quitting from lines at lines 184-185 [unnamed-chunk-5] (tciu-fMRI-analytics.Rmd) + Error: processing vignette 'tciu-fMRI-analytics.Rmd' failed with diagnostics: + argument "theme" is missing, with no default + --- failed re-building ‘tciu-fMRI-analytics.Rmd’ + + SUMMARY: processing the following files failed: + ‘tciu-LT-kimesurface.Rmd’ ‘tciu-fMRI-analytics.Rmd’ + + Error: Vignette re-building failed. + Execution halted + ``` + +## In both + +* checking installed package size ... NOTE + ``` + installed size is 14.7Mb + sub-directories of 1Mb or more: + data 1.8Mb + doc 12.3Mb + ``` + +# TestGardener + +
+ +* Version: 3.3.3 +* GitHub: NA +* Source code: https://github.com/cran/TestGardener +* Date/Publication: 2024-03-20 13:50:02 UTC +* Number of recursive dependencies: 131 + +Run `revdepcheck::cloud_details(, "TestGardener")` for more info + +
+ +## Newly broken + +* checking whether package ‘TestGardener’ can be installed ... WARNING + ``` + Found the following significant warnings: + Warning: replacing previous import ‘ggplot2::ggpar’ by ‘ggpubr::ggpar’ when loading ‘TestGardener’ + See ‘/tmp/workdir/TestGardener/new/TestGardener.Rcheck/00install.out’ for details. + ``` + +# thematic + +
+ +* Version: 0.1.5 +* GitHub: https://github.com/rstudio/thematic +* Source code: https://github.com/cran/thematic +* Date/Publication: 2024-02-14 00:20:03 UTC +* Number of recursive dependencies: 106 + +Run `revdepcheck::cloud_details(, "thematic")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘thematic-Ex.R’ failed + The error most likely occurred in: + + > ### Name: sequential_gradient + > ### Title: Control parameters of the sequential colorscale + > ### Aliases: sequential_gradient + > + > ### ** Examples + > + > + > # Gradient from fg to accent + > fg <- sequential_gradient(1, 0) + > thematic_on("black", "white", "salmon", sequential = fg) + > ggplot2::qplot(1:10, 1:10, color = 1:10) + Warning: `qplot()` was deprecated in ggplot2 3.4.0. + Error in adjust_color(user_default$colour, bg, fg, accent) : + Internal error: adjust_color() expects an input of length 1 + Calls: ... -> -> update_defaults -> adjust_color + Execution halted + ``` + +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(thematic) + > + > test_check("thematic") + [ FAIL 9 | WARN 1 | SKIP 7 | PASS 27 ] + + ══ Skipped tests (7) ═══════════════════════════════════════════════════════════ + ... + 10. └─base::Map(...) + 11. └─base::mapply(FUN = f, ..., SIMPLIFY = FALSE) + 12. └─thematic (local) ``(dots[[1L]][[1L]], dots[[2L]][[1L]]) + 13. ├─ggplot2::update_geom_defaults(...) + 14. │ └─ggplot2:::update_defaults(geom, "Geom", new, env = parent.frame()) + 15. └─thematic:::adjust_color(user_default$colour, bg, fg, accent) + + [ FAIL 9 | WARN 1 | SKIP 7 | PASS 27 ] + Error: Test failures + Execution halted + ``` + +# tidybayes + +
+ +* Version: 3.0.6 +* GitHub: https://github.com/mjskay/tidybayes +* Source code: https://github.com/cran/tidybayes +* Date/Publication: 2023-08-12 23:30:02 UTC +* Number of recursive dependencies: 193 + +Run `revdepcheck::cloud_details(, "tidybayes")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘tidybayes-Ex.R’ failed + The error most likely occurred in: + + > ### Name: compare_levels + > ### Title: Compare the value of draws of some variable from a Bayesian + > ### model for different levels of a factor + > ### Aliases: compare_levels + > ### Keywords: manip + > + > ### ** Examples + ... + 12. │ └─ggplot2 (local) f(l = layers[[i]], d = data[[i]]) + 13. │ └─l$compute_geom_2(d, theme = plot$theme) + 14. │ └─ggplot2 (local) compute_geom_2(..., self = self) + 15. │ └─self$geom$use_defaults(data, self$aes_params, modifiers, theme = theme) + 16. └─base::.handleSimpleError(...) + 17. └─rlang (local) h(simpleError(msg, call)) + 18. └─handlers[[1L]](cnd) + 19. └─cli::cli_abort(...) + 20. └─rlang::abort(...) + Execution halted + ``` + +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > # This is necessary because some tests fail otherwise; see https://github.com/hadley/testthat/issues/144 + > Sys.setenv("R_TESTS" = "") + > + > library(testthat) + > library(tidybayes) + > + > test_check("tidybayes") + ... + • test.geom_interval/grouped-intervals-h-stat.svg + • test.geom_pointinterval/grouped-pointintervals-h-stat.svg + • test.stat_dist_slabinterval/ccdfintervalh-using-args.svg + • test.stat_eye/one-parameter-horizontal-eye-mode-hdi.svg + • test.stat_eye/one-parameter-horizontal-half-eye.svg + • test.stat_eye/one-parameter-vertical-eye.svg + • test.stat_eye/one-parameter-vertical-halfeye.svg + • test.stat_eye/two-parameter-factor-horizontal-eye-fill.svg + Error: Test failures + Execution halted + ``` + +## In both + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘tidy-brms.Rmd’ + ... + + ]) %>% median_qi(condition_mean = b_Intercept + r_condition, + + .width = c(0.95, 0 .... [TRUNCATED] + + When sourcing ‘tidy-brms.R’: + Error: Problem while setting up geom aesthetics. + ℹ Error occurred in the 1st layer. + Caused by error in `use_defaults()`: + ... + + When sourcing ‘tidybayes.R’: + Error: error in evaluating the argument 'object' in selecting a method for function 'sampling': object 'ABC_stan' not found + Execution halted + + ‘tidy-brms.Rmd’ using ‘UTF-8’... failed + ‘tidy-posterior.Rmd’ using ‘UTF-8’... failed + ‘tidy-rstanarm.Rmd’ using ‘UTF-8’... failed + ‘tidybayes-residuals.Rmd’ using ‘UTF-8’... failed + ‘tidybayes.Rmd’ using ‘UTF-8’... failed + ``` + +* checking package dependencies ... NOTE + ``` + Package suggested but not available for checking: ‘dotwhisker’ + ``` + +# tidyCDISC + +
+ +* Version: 0.2.1 +* GitHub: https://github.com/Biogen-Inc/tidyCDISC +* Source code: https://github.com/cran/tidyCDISC +* Date/Publication: 2023-03-16 14:20:02 UTC +* Number of recursive dependencies: 141 + +Run `revdepcheck::cloud_details(, "tidyCDISC")` for more info + +
+ +## Newly broken + +* checking tests ... ERROR + ``` + Running ‘spelling.R’ + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(tidyCDISC) + > library(shinyjs) + + Attaching package: 'shinyjs' + + ... + 16. ├─plotly::config(...) + 17. │ └─plotly:::modify_list(p$x$config, args) + 18. │ ├─utils::modifyList(x %||% list(), y %||% list(), ...) + 19. │ │ └─base::stopifnot(is.list(x), is.list(val)) + 20. │ └─x %||% list() + 21. └─plotly::layout(...) + + [ FAIL 1 | WARN 1 | SKIP 15 | PASS 91 ] + Error: Test failures + Execution halted + ``` + +## In both + +* checking installed package size ... NOTE + ``` + installed size is 5.6Mb + sub-directories of 1Mb or more: + data 1.6Mb + doc 1.8Mb + ``` + +# tidydr + +
+ +* Version: 0.0.5 +* GitHub: https://github.com/YuLab-SMU/tidydr +* Source code: https://github.com/cran/tidydr +* Date/Publication: 2023-03-08 09:20:02 UTC +* Number of recursive dependencies: 71 + +Run `revdepcheck::cloud_details(, "tidydr")` for more info + +
+ +## Newly broken + +* checking whether package ‘tidydr’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/tidydr/new/tidydr.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘tidydr’ ... +** package ‘tidydr’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** inst +** byte-compile and prepare package for lazy loading +Error in get(x, envir = ns, inherits = FALSE) : + object 'len0_null' not found +Error: unable to load R code in package ‘tidydr’ +Execution halted +ERROR: lazy loading failed for package ‘tidydr’ +* removing ‘/tmp/workdir/tidydr/new/tidydr.Rcheck/tidydr’ + + +``` +### CRAN + +``` +* installing *source* package ‘tidydr’ ... +** package ‘tidydr’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** inst +** byte-compile and prepare package for lazy loading +** help +*** installing help indices +** building package indices +** installing vignettes +** testing if installed package can be loaded from temporary location +** testing if installed package can be loaded from final location +** testing if installed package keeps a record of temporary installation path +* DONE (tidydr) + + +``` +# tidysdm + +
+ +* Version: 0.9.4 +* GitHub: https://github.com/EvolEcolGroup/tidysdm +* Source code: https://github.com/cran/tidysdm +* Date/Publication: 2024-03-05 20:30:02 UTC +* Number of recursive dependencies: 167 + +Run `revdepcheck::cloud_details(, "tidysdm")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘tidysdm-Ex.R’ failed + The error most likely occurred in: + + > ### Name: autoplot.spatial_initial_split + > ### Title: Create a ggplot for a spatial initial rsplit. + > ### Aliases: autoplot.spatial_initial_split + > + > ### ** Examples + > + > + ... + 15. └─ggplot2 (local) FUN(X[[i]], ...) + 16. └─base::lapply(...) + 17. └─ggplot2 (local) FUN(X[[i]], ...) + 18. └─g$draw_key(data, g$params, key_size) + 19. └─ggplot2 (local) draw_key(...) + 20. └─ggplot2::draw_key_polygon(data, params, size) + 21. └─rlang:::Summary.quosure(from_theme(thin), 1.524, na.rm = FALSE) + 22. └─rlang:::abort_quosure_op("Summary", .Generic) + 23. └─rlang::abort(...) + Execution halted + ``` + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘a0_tidysdm_overview.Rmd’ + ... + + geom_sf(data = lacerta_thin, aes(col = class)) + + When sourcing ‘a0_tidysdm_overview.R’: + Error: Base operators are not defined for quosures. Do you need to unquote the + quosure? + + # Bad: myquosure * rhs + ... + + # Bad: myquosure * rhs + + # Good: !!myquosure * rhs + Execution halted + + ‘a0_tidysdm_overview.Rmd’ using ‘UTF-8’... failed + ‘a1_palaeodata_application.Rmd’ using ‘UTF-8’... failed + ‘a2_tidymodels_additions.Rmd’ using ‘UTF-8’... failed + ‘a3_troubleshooting.Rmd’ using ‘UTF-8’... OK + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘a0_tidysdm_overview.Rmd’ using rmarkdown + ``` + +# tidyterra + +
+ +* Version: 0.6.0 +* GitHub: https://github.com/dieghernan/tidyterra +* Source code: https://github.com/cran/tidyterra +* Date/Publication: 2024-04-22 23:50:02 UTC +* Number of recursive dependencies: 102 + +Run `revdepcheck::cloud_details(, "tidyterra")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘tidyterra-Ex.R’ failed + The error most likely occurred in: + + > ### Name: filter-joins.SpatVector + > ### Title: Filtering joins for 'SpatVector' objects + > ### Aliases: filter-joins.SpatVector semi_join.SpatVector + > ### anti_join.SpatVector + > + > ### ** Examples + > + ... + 15. └─ggplot2 (local) FUN(X[[i]], ...) + 16. └─base::lapply(...) + 17. └─ggplot2 (local) FUN(X[[i]], ...) + 18. └─g$draw_key(data, g$params, key_size) + 19. └─ggplot2 (local) draw_key(...) + 20. └─ggplot2::draw_key_polygon(data, params, size) + 21. └─rlang:::Summary.quosure(from_theme(thin), 1.524, na.rm = FALSE) + 22. └─rlang:::abort_quosure_op("Summary", .Generic) + 23. └─rlang::abort(...) + Execution halted + ``` + +# tidytransit + +
+ +* Version: 1.6.1 +* GitHub: https://github.com/r-transit/tidytransit +* Source code: https://github.com/cran/tidytransit +* Date/Publication: 2023-12-07 13:40:02 UTC +* Number of recursive dependencies: 96 + +Run `revdepcheck::cloud_details(, "tidytransit")` for more info + +
+ +## Newly broken + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘frequency.Rmd’ + ... + + labs(color = "H ..." ... [TRUNCATED] + + When sourcing ‘frequency.R’: + Error: Base operators are not defined for quosures. Do you need to unquote the + quosure? + + # Bad: myquosure * rhs + + # Good: !!myquosure * rhs + Execution halted + + ‘frequency.Rmd’ using ‘UTF-8’... failed + ‘introduction.Rmd’ using ‘UTF-8’... OK + ‘servicepatterns.Rmd’ using ‘UTF-8’... OK + ‘timetable.Rmd’ using ‘UTF-8’... OK + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘frequency.Rmd’ using rmarkdown + ``` + +## In both + +* checking installed package size ... NOTE + ``` + installed size is 7.1Mb + sub-directories of 1Mb or more: + doc 2.0Mb + extdata 4.5Mb + ``` + +# tidytreatment + +
+ +* Version: 0.2.2 +* GitHub: https://github.com/bonStats/tidytreatment +* Source code: https://github.com/cran/tidytreatment +* Date/Publication: 2022-02-21 09:00:07 UTC +* Number of recursive dependencies: 98 + +Run `revdepcheck::cloud_details(, "tidytreatment")` for more info + +
+ +## Newly broken + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘use-tidytreatment-BART.Rmd’ + ... + + by = ".row") %>% ggplot() + stat_halfeye(aes(x = z, y = fit)) + + + facet_wrap(~c1, l .... [TRUNCATED] + + When sourcing ‘use-tidytreatment-BART.R’: + Error: Problem while setting up geom aesthetics. + ℹ Error occurred in the 1st layer. + Caused by error in `use_defaults()`: + ! unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), NULL, list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.75, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, 90, NULL, c(0, + 2.75, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(NULL, N + Execution halted + + ‘use-tidytreatment-BART.Rmd’ using ‘UTF-8’... failed + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + ... + --- re-building ‘use-tidytreatment-BART.Rmd’ using rmarkdown + + Quitting from lines at lines 163-177 [plot-tidy-bart] (use-tidytreatment-BART.Rmd) + Error: processing vignette 'use-tidytreatment-BART.Rmd' failed with diagnostics: + Problem while setting up geom aesthetics. + ℹ Error occurred in the 1st layer. + Caused by error in `use_defaults()`: + ! unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), NULL, list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.75, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, 90, NULL, c(0, + ... + NULL, NULL, NULL, NULL, 0.2, NULL, list(NULL, NULL, NULL, 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, NULL, NULL, NULL, TRUE), NULL, "right", NULL, NULL, NULL, "center", NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, c(0, 0, 0, 0), list(), 11, list("white", NA, NULL, NULL, TRUE), list(NA, "grey20", NULL, NULL, TRUE), 5.5, NULL, NULL, list("grey92", NULL, NULL, NULL, FALSE, TRUE), NULL, list(NULL, 0.5, NULL, NULL, FALSE, TRUE), NULL, NULL, + NULL, NULL, FALSE, list(NULL, "white", NULL, NULL, TRUE), list(NULL, NULL, NULL, 1.2, 0, 1, NULL, NULL, c(0, 0, 5.5, 0), NULL, TRUE), "panel", list(NULL, NULL, NULL, NULL, 0, 1, NULL, NULL, c(0, 0, 5.5, 0), NULL, TRUE), list(NULL, NULL, NULL, 0.8, 1, 1, NULL, NULL, c(5.5, 0, 0, 0), NULL, TRUE), "panel", list(NULL, NULL, NULL, 1.2, 0.5, 0.5, NULL, NULL, NULL, NULL, TRUE), "topleft", NULL, c(5.5, 5.5, 5.5, 5.5), list("grey85", "grey20", NULL, NULL, TRUE), NULL, NULL, "inherit", "inside", list(NULL, + NULL, "grey10", 0.8, NULL, NULL, NULL, NULL, c(4.4, 4.4, 4.4, 4.4), NULL, TRUE), NULL, NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, NULL, -90, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, NULL, 90, NULL, NULL, NULL, TRUE), NULL, 2.75, 2.75)) + --- failed re-building ‘use-tidytreatment-BART.Rmd’ + + SUMMARY: processing the following file failed: + ‘use-tidytreatment-BART.Rmd’ + + Error: Vignette re-building failed. + Execution halted + ``` + +## In both + +* checking package dependencies ... NOTE + ``` + Package which this enhances but not available for checking: ‘bartMachine’ + ``` + +# tilemaps + +
+ +* Version: 0.2.0 +* GitHub: https://github.com/kaerosen/tilemaps +* Source code: https://github.com/cran/tilemaps +* Date/Publication: 2020-07-10 04:20:02 UTC +* Number of recursive dependencies: 72 + +Run `revdepcheck::cloud_details(, "tilemaps")` for more info + +
+ +## Newly broken + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘tilemaps.Rmd’ + ... + + fu .... [TRUNCATED] + + When sourcing ‘tilemaps.R’: + Error: Summary operations are not defined for quosures. Do you need to unquote + the quosure? + + # Bad: min(myquosure) + + # Good: min(!!myquosure) + Execution halted + + ‘tilemaps.Rmd’ using ‘UTF-8’... failed + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘tilemaps.Rmd’ using rmarkdown + ``` + +## In both + +* checking dependencies in R code ... NOTE + ``` + Namespace in Imports field not imported from: ‘lwgeom’ + All declared Imports should be used. + ``` + +# timetk + +
+ +* Version: 2.9.0 +* GitHub: https://github.com/business-science/timetk +* Source code: https://github.com/cran/timetk +* Date/Publication: 2023-10-31 22:30:02 UTC +* Number of recursive dependencies: 226 + +Run `revdepcheck::cloud_details(, "timetk")` for more info + +
+ +## Newly broken + +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > # This file is part of the standard setup for testthat. + > # It is recommended that you do not modify it. + > # + > # Where should you do additional test configuration? + > # Learn more about the roles of various files in: + > # * https://r-pkgs.org/testing-design.html#sec-tests-files-overview + > # * https://testthat.r-lib.org/articles/special-files.html + ... + 17. └─ggplot2 (local) compute_geom_2(..., self = self) + 18. └─self$geom$use_defaults(data, self$aes_params, modifiers, theme = theme) + 19. └─ggplot2 (local) use_defaults(..., self = self) + 20. └─ggplot2:::eval_from_theme(default_aes, theme) + 21. ├─calc_element("geom", theme) %||% .default_geom_element + 22. └─ggplot2::calc_element("geom", theme) + + [ FAIL 1 | WARN 0 | SKIP 0 | PASS 406 ] + Error: Test failures + Execution halted + ``` + +## In both + +* checking data for non-ASCII characters ... NOTE + ``` + Note: found 2750 marked UTF-8 strings + ``` + +# tongfen + +
+ +* Version: 0.3.5 +* GitHub: https://github.com/mountainMath/tongfen +* Source code: https://github.com/cran/tongfen +* Date/Publication: 2022-04-28 18:50:02 UTC +* Number of recursive dependencies: 101 + +Run `revdepcheck::cloud_details(, "tongfen")` for more info + +
+ +## Newly broken + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘polling_districts.Rmd’ using rmarkdown + + Quitting from lines at lines 44-79 [unnamed-chunk-3] (polling_districts.Rmd) + Error: processing vignette 'polling_districts.Rmd' failed with diagnostics: + Summary operations are not defined for quosures. Do you need to unquote + the quosure? + + # Bad: min(myquosure) + + ... + --- finished re-building ‘tongfen_ca.Rmd’ + + --- re-building ‘tongfen_us.Rmd’ using rmarkdown + --- finished re-building ‘tongfen_us.Rmd’ + + SUMMARY: processing the following file failed: + ‘polling_districts.Rmd’ + + Error: Vignette re-building failed. + Execution halted + ``` + +## In both + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘polling_districts.Rmd’ + ... + + size = 0.2, color = "black") + facet_wrap("Year") + scale_fill_manual(values = party_colou .... [TRUNCATED] + + When sourcing ‘polling_districts.R’: + Error: Summary operations are not defined for quosures. Do you need to unquote + the quosure? + + # Bad: min(myquosure) + ... + # Bad: min(myquosure) + + # Good: min(!!myquosure) + Execution halted + + ‘polling_districts.Rmd’ using ‘UTF-8’... failed + ‘tongfen-ca-estimate.Rmd’ using ‘UTF-8’... failed + ‘tongfen.Rmd’ using ‘UTF-8’... failed + ‘tongfen_ca.Rmd’ using ‘UTF-8’... failed + ‘tongfen_us.Rmd’ using ‘UTF-8’... failed + ``` + +* checking data for non-ASCII characters ... NOTE + ``` + Note: found 160 marked UTF-8 strings + ``` + +# TOSTER + +
+ +* Version: 0.8.2 +* GitHub: NA +* Source code: https://github.com/cran/TOSTER +* Date/Publication: 2024-04-16 16:40:02 UTC +* Number of recursive dependencies: 103 + +Run `revdepcheck::cloud_details(, "TOSTER")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘TOSTER-Ex.R’ failed + The error most likely occurred in: + + > ### Name: dataTOSTone + > ### Title: TOST One Sample T-Test + > ### Aliases: dataTOSTone + > + > ### ** Examples + > + > library("TOSTER") + ... + N Mean Median SD SE + ───────────────────────────────────────────────────────────────────────── + Sepal.Width 150 3.057333 3.000000 0.4358663 0.03558833 + ───────────────────────────────────────────────────────────────────────── + + Error in use_defaults(..., self = self) : + unused argument (theme = list(list("black", 0.727272727272727, 1, "butt", FALSE, TRUE), list("white", "black", 0.727272727272727, 1, TRUE), list("", "plain", "black", 16, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), NULL, list("black", "white", "#3366FF", 0.727272727272727, 1.45454545454545, "", 5.62335685623357, 2.18181818181818, 19, TRUE), NULL, NULL, list(NULL, NULL, "#333333", NULL, NULL, NULL, NULL, NULL, c(10, 0, 0, 0), NULL, FALSE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 4, 0), + NULL, TRUE), NULL, list(NULL, NULL, "#333333", NULL, NULL, NULL, 90, NULL, c(0, 10, 0, 0), NULL, FALSE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 4), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, "#333333", NULL, NULL, NULL, NULL, NULL, c(5, 0, 0, 0), NULL, FALSE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 3.2, 0), NULL, TRUE), NULL, list(), NULL, list(NULL, NULL, NULL, NU + Calls: ... -> -> -> + Execution halted + ``` + +* checking tests ... ERROR + ``` + Running ‘spelling.R’ + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(TOSTER) + + Attaching package: 'TOSTER' + + The following object is masked from 'package:testthat': + ... + 34. │ │ └─base::withCallingHandlers(...) + 35. │ └─layer$geom$use_defaults(...) + 36. └─base::.handleSimpleError(...) + 37. └─rlang (local) h(simpleError(msg, call)) + 38. └─handlers[[1L]](cnd) + 39. └─layer$geom$use_defaults(...) + + [ FAIL 8 | WARN 0 | SKIP 0 | PASS 1029 ] + Error: Test failures + Execution halted + ``` + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘IntroTOSTt.Rmd’ + ... + mean of x mean of y + 0.75 2.33 + + + > plot(res1, type = "cd") + + When sourcing ‘IntroTOSTt.R’: + ... + Error: unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), NULL, list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(7, 0, 0, 0), NULL, FALSE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, 90, NULL, c(0, 7, + 0, 0), NULL, FALSE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, "bold", NULL, 11, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, FALSE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, NULL, c(0, 0, 0, 2.2), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0.5, + Execution halted + + ‘IntroTOSTt.Rmd’ using ‘UTF-8’... failed + ‘IntroductionToTOSTER.Rmd’ using ‘UTF-8’... OK + ‘SMD_calcs.Rmd’ using ‘UTF-8’... OK + ‘correlations.Rmd’ using ‘UTF-8’... OK + ‘robustTOST.Rmd’ using ‘UTF-8’... failed + ‘the_ftestTOSTER.Rmd’ using ‘UTF-8’... OK + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘IntroTOSTt.Rmd’ using rmarkdown + ``` + +# TreatmentPatterns + +
+ +* Version: 2.6.6 +* GitHub: https://github.com/darwin-eu-dev/TreatmentPatterns +* Source code: https://github.com/cran/TreatmentPatterns +* Date/Publication: 2024-04-16 15:10:06 UTC +* Number of recursive dependencies: 142 + +Run `revdepcheck::cloud_details(, "TreatmentPatterns")` for more info + +
+ +## Newly broken + +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > # This file is part of the standard setup for testthat. + > # It is recommended that you do not modify it. + > # + > # Where should you do additional test configuration? + > # Learn more about the roles of various files in: + > # * https://r-pkgs.org/tests.html + > # * https://testthat.r-lib.org/reference/test_package.html#special-files + ... + 22. ├─testthat::expect_s3_class(output$charAgePlot$html, "html") at test-CharacterizationPlots.R:47:9 + 23. │ └─testthat::quasi_label(enquo(object), arg = "object") + 24. │ └─rlang::eval_bare(expr, quo_get_env(quo)) + 25. ├─output$charAgePlot + 26. └─shiny:::`$.shinyoutput`(output, charAgePlot) + 27. └─.subset2(x, "impl")$getOutput(name) + + [ FAIL 1 | WARN 0 | SKIP 31 | PASS 95 ] + Error: Test failures + Execution halted + ``` + +# trelliscopejs + +
+ +* Version: 0.2.6 +* GitHub: https://github.com/hafen/trelliscopejs +* Source code: https://github.com/cran/trelliscopejs +* Date/Publication: 2021-02-01 08:00:02 UTC +* Number of recursive dependencies: 107 + +Run `revdepcheck::cloud_details(, "trelliscopejs")` for more info + +
+ +## Newly broken + +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(trelliscopejs) + > + > test_check("trelliscopejs") + [ FAIL 1 | WARN 2 | SKIP 0 | PASS 0 ] + + ══ Failed tests ════════════════════════════════════════════════════════════════ + ... + 14. └─ggplot2 (local) compute_geom_2(..., self = self) + 15. └─self$geom$use_defaults(data, self$aes_params, modifiers, theme = theme) + 16. └─ggplot2 (local) use_defaults(..., self = self) + 17. └─ggplot2:::eval_from_theme(default_aes, theme) + 18. ├─calc_element("geom", theme) %||% .default_geom_element + 19. └─ggplot2::calc_element("geom", theme) + + [ FAIL 1 | WARN 2 | SKIP 0 | PASS 0 ] + Error: Test failures + Execution halted + ``` + +# tsnet + +
+ +* Version: 0.1.0 +* GitHub: https://github.com/bsiepe/tsnet +* Source code: https://github.com/cran/tsnet +* Date/Publication: 2024-02-28 11:30:02 UTC +* Number of recursive dependencies: 77 + +Run `revdepcheck::cloud_details(, "tsnet")` for more info + +
+ +## Newly broken + +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > # This file is part of the standard setup for testthat. + > # It is recommended that you do not modify it. + > # + > # Where should you do additional test configuration? + > # Learn more about the roles of various files in: + > # * https://r-pkgs.org/tests.html + > # * https://testthat.r-lib.org/reference/test_package.html#special-files + ... + unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), NULL, list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(7, 0, 0, 0), NULL, FALSE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, 90, NULL, c(0, 7, + 0, 0), NULL, FALSE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 1, NULL, NULL, NULL, c(0, 2.2, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, NULL, c(0, 0, 0, 2.2), + NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0.5, NULL, NULL, NULL, c(0, 2.2, 0, 2.2), NULL, TRUE), list("grey70", 0.5, NULL, NULL, FALSE, TRUE), NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 2.75, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 0.75, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, list(), list("gray70", 0.5, NULL, NULL, FALSE, FALSE), NULL, NULL, list("gray70", 0.5, NULL, NULL, FALSE, FALSE), NULL, NULL, NULL, NULL, list(NULL, NA, NULL, + NULL, TRUE), c(5.5, 5.5, 5.5, 5.5), 11, NULL, NULL, NULL, 1.2, NULL, NULL, 5.5, NULL, NULL, NULL, NULL, 0.2, NULL, list(NULL, NULL, NULL, 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, NULL, NULL, NULL, TRUE), NULL, "right", NULL, NULL, NULL, "center", NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, c(0, 0, 0, 0), list(), 11, list("white", NA, NULL, NULL, TRUE), list(), 5.5, NULL, NULL, list("grey87", NULL, NULL, NULL, FALSE, TRUE), list(), list(), + NULL, NULL, NULL, NULL, FALSE, list(NULL, "white", NULL, NULL, TRUE), list(NULL, NULL, NULL, 1.2, 0, 1, NULL, NULL, c(0, 0, 5.5, 0), NULL, TRUE), "panel", list(NULL, NULL, NULL, NULL, 0, 1, NULL, NULL, c(0, 0, 5.5, 0), NULL, TRUE), list(NULL, NULL, NULL, 0.8, 1, 1, NULL, NULL, c(5.5, 0, 0, 0), NULL, TRUE), "panel", list(NULL, NULL, NULL, 1.2, 0.5, 0.5, NULL, NULL, NULL, NULL, TRUE), "topleft", NULL, c(5.5, 5.5, 5.5, 5.5), list("gray90", NA, NULL, NULL, FALSE), NULL, NULL, "inherit", "inside", + list(NULL, NULL, "black", 0.8, NULL, NULL, NULL, NULL, c(6, 6, 6, 6), NULL, FALSE), NULL, NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, NULL, -90, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, NULL, 90, NULL, NULL, NULL, TRUE), NULL, 2.75, 2.75)) + + [ FAIL 1 | WARN 15 | SKIP 0 | PASS 108 ] + Error: Test failures + Execution halted + ``` + +## In both + +* checking installed package size ... NOTE + ``` + installed size is 206.1Mb + sub-directories of 1Mb or more: + libs 204.6Mb + ``` + +* checking for GNU extensions in Makefiles ... NOTE + ``` + GNU make is a SystemRequirements. + ``` + +# umiAnalyzer + +
+ +* Version: 1.0.0 +* GitHub: https://github.com/sfilges/umiAnalyzer +* Source code: https://github.com/cran/umiAnalyzer +* Date/Publication: 2021-11-25 08:40:02 UTC +* Number of recursive dependencies: 116 + +Run `revdepcheck::cloud_details(, "umiAnalyzer")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘umiAnalyzer-Ex.R’ failed + The error most likely occurred in: + + > ### Name: AmpliconPlot + > ### Title: Generate Amplicon plots + > ### Aliases: AmpliconPlot + > + > ### ** Examples + > + > library(umiAnalyzer) + ... + > main = system.file('extdata', package = 'umiAnalyzer') + > samples <- list.dirs(path = main, full.names = FALSE, recursive = FALSE) + > simsen <- createUmiExperiment(experimentName = 'example',mainDir = main,sampleNames = samples) + > simsen <- filterUmiObject(simsen) + > + > amplicon_plot <- AmpliconPlot(simsen) + Error in compute_geom_2(..., self = self) : + argument "theme" is missing, with no default + Calls: AmpliconPlot ... use_defaults -> eval_from_theme -> %||% -> calc_element + Execution halted + ``` + +# UniprotR + +
+ +* Version: 2.4.0 +* GitHub: https://github.com/Proteomicslab57357/UniprotR +* Source code: https://github.com/cran/UniprotR +* Date/Publication: 2024-03-05 15:10:02 UTC +* Number of recursive dependencies: 192 -Run `revdepcheck::cloud_details(, "ggh4x")` for more info +Run `revdepcheck::cloud_details(, "UniprotR")` for more info + +
+ +## Newly broken + +* checking whether package ‘UniprotR’ can be installed ... WARNING + ``` + Found the following significant warnings: + Warning: replacing previous import ‘ggplot2::ggpar’ by ‘ggpubr::ggpar’ when loading ‘UniprotR’ + See ‘/tmp/workdir/UniprotR/new/UniprotR.Rcheck/00install.out’ for details. + ``` + +# VALERIE + +
+ +* Version: 1.1.0 +* GitHub: NA +* Source code: https://github.com/cran/VALERIE +* Date/Publication: 2020-07-10 10:20:13 UTC +* Number of recursive dependencies: 133 + +Run `revdepcheck::cloud_details(, "VALERIE")` for more info + +
+ +## Newly broken + +* checking whether package ‘VALERIE’ can be installed ... WARNING + ``` + Found the following significant warnings: + Warning: replacing previous import ‘ggplot2::ggpar’ by ‘ggpubr::ggpar’ when loading ‘VALERIE’ + See ‘/tmp/workdir/VALERIE/new/VALERIE.Rcheck/00install.out’ for details. + ``` + +## Newly fixed + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘VALERIE.Rmd’ using rmarkdown + Trying to upgrade TinyTeX automatically now... + If reinstallation fails, try install_tinytex() again. Then install the following packages: + + tinytex::tlmgr_install(c("amscls", "amsfonts", "amsmath", "atbegshi", "atveryend", "auxhook", "babel", "bibtex", "bigintcalc", "bitset", "booktabs", "cm", "ctablestack", "dehyph", "dvipdfmx", "dvips", "ec", "epstopdf-pkg", "etex", "etexcmds", "etoolbox", "euenc", "everyshi", "fancyvrb", "filehook", "firstaid", "float", "fontspec", "framed", "geometry", "gettitlestring", "glyphlist", "graphics", "graphics-cfg", "graphics-def", "helvetic", "hycolor", "hyperref", "hyph-utf8", "hyphen-base", "iftex", "inconsolata", "infwarerr", "intcalc", "knuth-lib", "kpathsea", "kvdefinekeys", "kvoptions", "kvsetkeys", "l3backend", "l3kernel", "l3packages", "latex", "latex-amsmath-dev", "latex-bin", "latex-fonts", "latex-tools-dev", "latexconfig", "latexmk", "letltxmacro", "lm", "lm-math", "ltxcmds", "lua-alt-getopt", "lua-uni-algos", "luahbtex", "lualatex-math", "lualibs", "luaotfload", "luatex", "luatexbase", "mdwtools", "metafont", "mfware", "modes", "natbib", "pdfescape", "pdftex", "pdftexcmds", "plain", "psnfss", "refcount", "rerunfilecheck", "scheme-infraonly", "selnolig", "stringenc", "symbol", "tex", "tex-ini-files", "texlive-scripts", "texlive.infra", "times", "tipa", "tools", "unicode-data", "unicode-math", "uniquecounter", "url", "xcolor", "xetex", "xetexconfig", "xkeyval", "xunicode", "zapfding")) + + The directory /opt/TinyTeX/texmf-local is not empty. It will be backed up to /tmp/RtmpbQSeNG/file20363012f5cc and restored later. + + tlmgr: no auxiliary texmf trees defined, so nothing removed + ... + + Error: processing vignette 'VALERIE.Rmd' failed with diagnostics: + LaTeX failed to compile /tmp/workdir/VALERIE/old/VALERIE.Rcheck/vign_test/VALERIE/vignettes/VALERIE.tex. See https://yihui.org/tinytex/r/#debugging for debugging tips. See VALERIE.log for more info. + --- failed re-building ‘VALERIE.Rmd’ + + SUMMARY: processing the following file failed: + ‘VALERIE.Rmd’ + + Error: Vignette re-building failed. + Execution halted + ``` + +## In both + +* checking installed package size ... NOTE + ``` + installed size is 9.6Mb + sub-directories of 1Mb or more: + extdata 8.7Mb + ``` + +# VancouvR + +
+ +* Version: 0.1.8 +* GitHub: https://github.com/mountainMath/VancouvR +* Source code: https://github.com/cran/VancouvR +* Date/Publication: 2024-04-18 16:12:35 UTC +* Number of recursive dependencies: 91 + +Run `revdepcheck::cloud_details(, "VancouvR")` for more info + +
+ +## Newly broken + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘Demo.Rmd’ + ... + + labs(title .... [TRUNCATED] + + When sourcing ‘Demo.R’: + Error: Summary operations are not defined for quosures. Do you need to unquote + the quosure? + + # Bad: min(myquosure) + + # Good: min(!!myquosure) + Execution halted + + ‘Demo.Rmd’ using ‘UTF-8’... failed + ‘Isolines.Rmd’ using ‘UTF-8’... OK + ``` + +# vannstats + +
+ +* Version: 1.3.4.14 +* GitHub: NA +* Source code: https://github.com/cran/vannstats +* Date/Publication: 2023-04-15 04:30:02 UTC +* Number of recursive dependencies: 101 + +Run `revdepcheck::cloud_details(, "vannstats")` for more info + +
+ +## Newly broken + +* checking whether package ‘vannstats’ can be installed ... WARNING + ``` + Found the following significant warnings: + Warning: replacing previous import ‘ggplot2::ggpar’ by ‘ggpubr::ggpar’ when loading ‘vannstats’ + See ‘/tmp/workdir/vannstats/new/vannstats.Rcheck/00install.out’ for details. + ``` + +# vici + +
+ +* Version: 0.7.3 +* GitHub: https://github.com/sistm/vici +* Source code: https://github.com/cran/vici +* Date/Publication: 2024-02-02 16:20:02 UTC +* Number of recursive dependencies: 113 + +Run `revdepcheck::cloud_details(, "vici")` for more info + +
+ +## Newly broken + +* checking whether package ‘vici’ can be installed ... WARNING + ``` + Found the following significant warnings: + Warning: replacing previous import ‘ggplot2::ggpar’ by ‘ggpubr::ggpar’ when loading ‘vici’ + See ‘/tmp/workdir/vici/new/vici.Rcheck/00install.out’ for details. + ``` + +# vivaldi + +
+ +* Version: 1.0.1 +* GitHub: https://github.com/GreshamLab/vivaldi +* Source code: https://github.com/cran/vivaldi +* Date/Publication: 2023-03-21 20:10:02 UTC +* Number of recursive dependencies: 102 + +Run `revdepcheck::cloud_details(, "vivaldi")` for more info
@@ -16,26 +10835,26 @@ Run `revdepcheck::cloud_details(, "ggh4x")` for more info * checking examples ... ERROR ``` - Running examples in ‘ggh4x-Ex.R’ failed + Running examples in ‘vivaldi-Ex.R’ failed The error most likely occurred in: - > ### Name: coord_axes_inside - > ### Title: Cartesian coordinates with interior axes - > ### Aliases: coord_axes_inside + > ### Name: snv_location + > ### Title: snv_location + > ### Aliases: snv_location > > ### ** Examples > - > # A standard plot + > # Example 1: ... - > p + coord_axes_inside() - Theme element `panel.background` is missing - Theme element `panel.grid.minor.y` is missing - Theme element `panel.grid.minor.x` is missing - Theme element `panel.grid.major.y` is missing - Theme element `panel.grid.major.x` is missing - Error in UseMethod("element_grob") : - no applicable method for 'element_grob' applied to an object of class "NULL" - Calls: ... lapply -> FUN -> draw_axis_labels -> exec -> + 7 m2 PB1 266 G A minor 0.022 0.978 + 8 m2 PB2 199 A G minor 0.043 0.957 + 9 m2 PB2 88 G A major 0.055 0.945 + 10 m2 PB2 180 C T minor 0.011 0.989 + > + > snv_location(df) + Error in compute_geom_2(..., self = self) : + argument "theme" is missing, with no default + Calls: snv_location ... use_defaults -> eval_from_theme -> %||% -> calc_element Execution halted ``` @@ -44,146 +10863,344 @@ Run `revdepcheck::cloud_details(, "ggh4x")` for more info Running ‘testthat.R’ Running the tests in ‘tests/testthat.R’ failed. Complete output: - > library(testthat) - > library(ggh4x) - Loading required package: ggplot2 - > - > test_check("ggh4x") - Theme element `panel.background` is missing - Theme element `panel.grid.minor.y` is missing + > # This file is part of the standard setup for testthat. + > # It is recommended that you do not modify it. + > # + > # Where should you do additional test configuration? + > # Learn more about the roles of various files in: + > # * https://r-pkgs.org/tests.html + > # * https://testthat.r-lib.org/reference/test_package.html#special-files ... - 16. └─ggplot2 (local) build_labels(...) - 17. └─base::lapply(...) - 18. └─ggplot2 (local) FUN(X[[i]], ...) - 19. └─ggplot2:::draw_axis_labels(...) - 20. ├─rlang::exec(...) - 21. └─ggplot2 (local) ``(...) - [ FAIL 1 | WARN 0 | SKIP 18 | PASS 750 ] + ══ Failed tests ════════════════════════════════════════════════════════════════ + ── Failure ('test-snv_location.R:13:3'): expect output ───────────────────────── + Expected `snv_location(df)` to run without any errors. + i Actually got a with text: + argument "theme" is missing, with no default + + [ FAIL 1 | WARN 2 | SKIP 0 | PASS 29 ] Error: Test failures Execution halted ``` -* checking re-building of vignette outputs ... ERROR +* checking running R code from vignettes ... ERROR ``` - Error(s) in re-building vignettes: + Errors in running code in vignettes: + when running code in ‘vignette.Rmd’ ... - --- re-building ‘Facets.Rmd’ using rmarkdown - --- finished re-building ‘Facets.Rmd’ + |a_3_fb | 96| + |a_3_iv | 94| + |b_1_fb | 82| + |b_1_iv | 91| - --- re-building ‘Miscellaneous.Rmd’ using rmarkdown + > snv_location(DF_filt_SNVs) + + When sourcing ‘vignette.R’: + Error: argument "theme" is missing, with no default + Execution halted + + ‘vignette.Rmd’ using ‘UTF-8’... failed + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘vignette.Rmd’ using rmarkdown + ``` + +## In both + +* checking installed package size ... NOTE + ``` + installed size is 6.8Mb + sub-directories of 1Mb or more: + doc 5.4Mb + extdata 1.1Mb + ``` + +# vvshiny + +
+ +* Version: 0.1.1 +* GitHub: NA +* Source code: https://github.com/cran/vvshiny +* Date/Publication: 2023-07-19 15:30:02 UTC +* Number of recursive dependencies: 132 + +Run `revdepcheck::cloud_details(, "vvshiny")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘vvshiny-Ex.R’ failed + The error most likely occurred in: - Quitting from lines 199-204 [unnamed-chunk-13] (Miscellaneous.Rmd) - Error: processing vignette 'Miscellaneous.Rmd' failed with diagnostics: - no applicable method for 'element_grob' applied to an object of class "NULL" + > ### Name: ggplotly_with_legend + > ### Title: Make ggplotly and add legend with color as title + > ### Aliases: ggplotly_with_legend + > + > ### ** Examples + > + > df <- data.frame(x_var = rnorm(100), + ... + > ggplot_instellingen <- ggplot2::geom_point() + > scale_y <- ggplot2::scale_y_continuous() + > plot <- basic_plot(df, "x_var", "y_var", "color_var", xlab_setting, + + ylab_setting, ggplot_instellingen, "none", scale_y) + > mapping_table <- list(color_var = "user friendly name var") + > plotly_object <- ggplotly_with_legend(plot, "color_var", mapping_table) + Error in compute_geom_2(..., self = self) : + argument "theme" is missing, with no default + Calls: ggplotly_with_legend ... use_defaults -> eval_from_theme -> %||% -> calc_element + Execution halted + ``` + +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > # This file is part of the standard setup for testthat. + > # It is recommended that you do not modify it. + > # + > # Where should you do additional test configuration? + > # Learn more about the roles of various files in: + > # * https://r-pkgs.org/testing-design.html#sec-tests-files-overview + > # * https://testthat.r-lib.org/articles/special-files.html ... - --- finished re-building ‘Statistics.Rmd’ + 11. │ └─self$geom$use_defaults(data, self$aes_params, modifiers, theme = theme) + 12. │ └─ggplot2 (local) use_defaults(..., self = self) + 13. │ └─ggplot2:::eval_from_theme(default_aes, theme) + 14. │ ├─calc_element("geom", theme) %||% .default_geom_element + 15. │ └─ggplot2::calc_element("geom", theme) + 16. └─plotly::layout(...) + + [ FAIL 1 | WARN 2 | SKIP 0 | PASS 60 ] + Error: Test failures + Execution halted + ``` + +# waywiser + +
+ +* Version: 0.5.1 +* GitHub: https://github.com/ropensci/waywiser +* Source code: https://github.com/cran/waywiser +* Date/Publication: 2023-10-31 15:50:02 UTC +* Number of recursive dependencies: 172 + +Run `revdepcheck::cloud_details(, "waywiser")` for more info + +
+ +## Newly broken + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘residual-autocorrelation.Rmd’ + ... + + weights)) %>% sf::st_ .... [TRUNCATED] - --- re-building ‘ggh4x.Rmd’ using rmarkdown - --- finished re-building ‘ggh4x.Rmd’ + When sourcing ‘residual-autocorrelation.R’: + Error: Summary operations are not defined for quosures. Do you need to unquote + the quosure? - SUMMARY: processing the following file failed: - ‘Miscellaneous.Rmd’ + # Bad: min(myquosure) - Error: Vignette re-building failed. + # Good: min(!!myquosure) Execution halted + + ‘multi-scale-assessment.Rmd’ using ‘UTF-8’... OK + ‘residual-autocorrelation.Rmd’ using ‘UTF-8’... failed + ‘waywiser.Rmd’ using ‘UTF-8’... OK + ``` + +* checking re-building of vignette outputs ... NOTE ``` + Error(s) in re-building vignettes: + --- re-building ‘multi-scale-assessment.Rmd’ using rmarkdown + ``` + +## In both -# MplusAutomation +* checking data for non-ASCII characters ... NOTE + ``` + Note: found 1 marked UTF-8 string + ``` + +# wildlifeDI
-* Version: 1.1.1 -* GitHub: https://github.com/michaelhallquist/MplusAutomation -* Source code: https://github.com/cran/MplusAutomation -* Date/Publication: 2024-01-30 23:40:02 UTC -* Number of recursive dependencies: 89 +* Version: 1.0.0 +* GitHub: https://github.com/jedalong/wildlifeDI +* Source code: https://github.com/cran/wildlifeDI +* Date/Publication: 2024-03-22 19:30:02 UTC +* Number of recursive dependencies: 84 -Run `revdepcheck::cloud_details(, "MplusAutomation")` for more info +Run `revdepcheck::cloud_details(, "wildlifeDI")` for more info
## Newly broken -* checking installed package size ... NOTE +* checking running R code from vignettes ... ERROR ``` - installed size is 5.4Mb - sub-directories of 1Mb or more: - R 3.1Mb - data 1.0Mb + Errors in running code in vignettes: + when running code in ‘wildlifeDI-vignette-contact_analysis.Rmd’ + ... + GDAL Error 1: PROJ: proj_as_wkt: DatumEnsemble can only be exported to WKT2:2019 + + When sourcing ‘wildlifeDI-vignette-contact_analysis.R’: + Error: Base operators are not defined for quosures. Do you need to unquote the + quosure? + + # Bad: myquosure * rhs + + # Good: !!myquosure * rhs + Execution halted + + ‘wildlifeDI-vignette-contact_analysis.Rmd’ using ‘UTF-8’... failed + ‘wildlifeDI-vignette.rmd’ using ‘UTF-8’... OK + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘wildlifeDI-vignette-contact_analysis.Rmd’ using rmarkdown + + Quitting from lines at lines 53-55 [unnamed-chunk-3] (wildlifeDI-vignette-contact_analysis.Rmd) + Error: processing vignette 'wildlifeDI-vignette-contact_analysis.Rmd' failed with diagnostics: + Base operators are not defined for quosures. Do you need to unquote the + quosure? + + # Bad: myquosure * rhs + + # Good: !!myquosure * rhs + --- failed re-building ‘wildlifeDI-vignette-contact_analysis.Rmd’ + + --- re-building ‘wildlifeDI-vignette.rmd’ using rmarkdown ``` -# PlasmaMutationDetector +# wilson
-* Version: 1.7.2 -* GitHub: NA -* Source code: https://github.com/cran/PlasmaMutationDetector -* Date/Publication: 2018-06-11 07:43:09 UTC -* Number of recursive dependencies: 107 +* Version: 2.4.2 +* GitHub: https://github.com/loosolab/wilson +* Source code: https://github.com/cran/wilson +* Date/Publication: 2021-04-19 09:40:02 UTC +* Number of recursive dependencies: 200 -Run `revdepcheck::cloud_details(, "PlasmaMutationDetector")` for more info +Run `revdepcheck::cloud_details(, "wilson")` for more info
## Newly broken -* checking installed package size ... NOTE +* checking tests ... ERROR ``` - installed size is 5.1Mb - sub-directories of 1Mb or more: - extdata 4.0Mb + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(wilson) + + Attaching package: 'wilson' + + The following object is masked from 'package:stats': + + ... + 9. └─ggplot2 (local) compute_geom_2(..., self = self) + 10. └─self$geom$use_defaults(data, self$aes_params, modifiers, theme = theme) + 11. └─ggplot2 (local) use_defaults(..., self = self) + 12. └─ggplot2:::eval_from_theme(default_aes, theme) + 13. ├─calc_element("geom", theme) %||% .default_geom_element + 14. └─ggplot2::calc_element("geom", theme) + + [ FAIL 3 | WARN 11 | SKIP 1 | PASS 74 ] + Error: Test failures + Execution halted ``` -# Superpower +# WorldMapR
-* Version: 0.2.0 -* GitHub: https://github.com/arcaldwell49/Superpower -* Source code: https://github.com/cran/Superpower -* Date/Publication: 2022-05-17 13:50:02 UTC -* Number of recursive dependencies: 112 +* Version: 0.1.1 +* GitHub: https://github.com/Luigi-Annic/WorldMapR +* Source code: https://github.com/cran/WorldMapR +* Date/Publication: 2024-04-22 19:30:07 UTC +* Number of recursive dependencies: 92 -Run `revdepcheck::cloud_details(, "Superpower")` for more info +Run `revdepcheck::cloud_details(, "WorldMapR")` for more info
## Newly broken +* checking examples ... ERROR + ``` + Running examples in ‘WorldMapR-Ex.R’ failed + The error most likely occurred in: + + > ### Name: worldplotCat + > ### Title: worldplotCat + > ### Aliases: worldplotCat + > + > ### ** Examples + > + > data(testdata1b) + ... + 16. └─ggplot2 (local) FUN(X[[i]], ...) + 17. └─base::lapply(...) + 18. └─ggplot2 (local) FUN(X[[i]], ...) + 19. └─g$draw_key(data, g$params, key_size) + 20. └─ggplot2 (local) draw_key(...) + 21. └─ggplot2::draw_key_polygon(data, params, size) + 22. └─rlang:::Summary.quosure(from_theme(thin), 1.27, na.rm = FALSE) + 23. └─rlang:::abort_quosure_op("Summary", .Generic) + 24. └─rlang::abort(...) + Execution halted + ``` + * checking tests ... ERROR ``` - Running ‘spelling.R’ Running ‘testthat.R’ Running the tests in ‘tests/testthat.R’ failed. Complete output: - > library(testthat) - > library(Superpower) - > - > - > test_check("Superpower") - [ FAIL 2 | WARN 18 | SKIP 13 | PASS 397 ] + > # This file is part of the standard setup for testthat. + > # It is recommended that you do not modify it. + > # + > # Where should you do additional test configuration? + > # Learn more about the roles of various files in: + > # * https://r-pkgs.org/testing-design.html#sec-tests-files-overview + > # * https://testthat.r-lib.org/articles/special-files.html ... - 1/1 mismatches - [1] -0.00304 - 0 == -0.00304 - ── Failure ('test_sim_cor.R:38:3'): simulated correlations fit expected values ── - `res5` not equal to 0. - 1/1 mismatches - [1] -0.00322 - 0 == -0.00322 + 19. └─g$draw_key(data, g$params, key_size) + 20. └─ggplot2 (local) draw_key(...) + 21. └─ggplot2::draw_key_polygon(data, params, size) + 22. └─rlang:::Summary.quosure(from_theme(thin), 1.27, na.rm = FALSE) + 23. └─rlang:::abort_quosure_op("Summary", .Generic) + 24. └─rlang::abort(...) - [ FAIL 2 | WARN 18 | SKIP 13 | PASS 397 ] + [ FAIL 2 | WARN 1 | SKIP 0 | PASS 0 ] Error: Test failures Execution halted ``` ## In both -* checking dependencies in R code ... NOTE +* checking data for non-ASCII characters ... NOTE ``` - Namespaces in Imports field not imported from: - ‘gridExtra’ ‘mvtnorm’ - All declared Imports should be used. + Note: found 4 marked Latin-1 strings + Note: found 5 marked UTF-8 strings ``` # xaringanthemer @@ -219,11 +11236,32 @@ Run `revdepcheck::cloud_details(, "xaringanthemer")` for more info ── Failure ('test-ggplot2.R:267:3'): theme_xaringan_restore_defaults() restores defaults ── res$after_restore$line_colour (`actual`) not equal to res$original$colour (`expected`). - `actual`: "#0088ff" - `expected`: "black" + `actual` is a character vector ('#0088ff') + `expected` is an S3 object of class , a call [ FAIL 1 | WARN 18 | SKIP 1 | PASS 308 ] Error: Test failures Execution halted ``` +## In both + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘xaringanthemer.Rmd’ + ... + Warning in file(con, "r") : + cannot open file './../man/fragments/_quick-intro.Rmd': No such file or directory + + Quitting from lines at lines 43-43 [unnamed-chunk-2] (./../man/fragments/_quick-intro.Rmd) + + When tangling ‘xaringanthemer.Rmd’: + Error: cannot open the connection + Execution halted + + ‘ggplot2-themes.Rmd’ using ‘UTF-8’... OK + ‘template-variables.Rmd’ using ‘UTF-8’... OK + ‘xaringanthemer.Rmd’ using ‘UTF-8’... failed + ``` + From d41758fbf1c1dd6bba438cd66703c8e47dd132f5 Mon Sep 17 00:00:00 2001 From: Teun van den Brand Date: Wed, 22 May 2024 09:39:36 +0200 Subject: [PATCH 28/41] implement @yutannihilation's suggestion --- R/layer.R | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/R/layer.R b/R/layer.R index 762090ff5f..50b23f2a3a 100644 --- a/R/layer.R +++ b/R/layer.R @@ -438,7 +438,7 @@ Layer <- ggproto("Layer", NULL, self$position$compute_layer(data, params, layout) }, - compute_geom_2 = function(self, data, theme) { + compute_geom_2 = function(self, data, theme = NULL) { # Combine aesthetics, defaults, & params if (empty(data)) return(data) From 99a3b58945729a663ccecd9e606d8c838e1c1573 Mon Sep 17 00:00:00 2001 From: Thomas Lin Pedersen Date: Tue, 4 Jun 2024 20:30:13 +0200 Subject: [PATCH 29/41] run revdepcheck --- revdep/README.md | 908 +- revdep/cran.md | 1342 ++- revdep/failures.md | 14388 +++++++++++++++++--------- revdep/problems.md | 23635 +++++++++++++++++++++++++++++++------------ 4 files changed, 28574 insertions(+), 11699 deletions(-) diff --git a/revdep/README.md b/revdep/README.md index e4e8a84654..89a1d9a3d1 100644 --- a/revdep/README.md +++ b/revdep/README.md @@ -1,351 +1,569 @@ # Revdeps -## Failed to check (135) +## Failed to check (191) -|package |version |error |warning |note | -|:----------------------|:----------|:------|:-------|:----| -|abctools |1.1.7 |1 | | | -|animalEKF |1.2 |1 | | | -|ANOM |0.5 |1 | | | -|atRisk |0.1.0 |1 | | | -|AutoScore |1.0.0 |1 | | | -|bayesdfa |1.3.3 |1 | | | -|bayesDP |1.3.6 |1 | | | -|BayesianFactorZoo |0.0.0.2 |1 | | | -|BayesSurvive |0.0.1 |1 | | | -|BCClong |1.0.2 |1 | |1 | -|binsreg |1.0 |1 | | | -|bmgarch |2.0.0 |1 | | | -|bmstdr |0.7.9 |1 | | | -|bspcov |1.0.0 |1 | | | -|BuyseTest |3.0.2 |1 | | | -|CalibrationCurves |2.0.1 |1 | | | -|CARBayesST |4.0 |1 | | | -|CaseBasedReasoning |0.3 |1 | | | -|CGPfunctions |0.6.3 |1 | | | -|cmprskcoxmsm |0.2.1 |1 | | | -|contrast |0.24.2 |1 | | | -|coxed |0.3.3 |1 | | | -|CRMetrics |0.3.0 |1 | | | -|csmpv |1.0.3 |1 | | | -|ctsem |3.9.1 |1 | | | -|DepthProc |2.1.5 |1 | | | -|DR.SC |3.4 |1 | | | -|EcoEnsemble |1.0.5 |1 | | | -|ecolottery |1.0.0 |1 | | | -|EpiEstim |2.2-4 |1 | | | -|evolqg |0.3-4 |1 | | | -|ForecastComb |1.3.1 |1 | | | -|gapfill |0.9.6-1 |1 | |1 | -|GeomComb |1.0 |1 | | | -|geostan |0.6.0 |1 | | | -|ggpmisc |0.5.5 |1 | | | -|ggrcs |0.3.8 |1 | | | -|ggrisk |1.3 |1 | | | -|gJLS2 |0.2.0 |1 | | | -|Greg |2.0.2 |1 | | | -|greport |0.7-4 |1 | | | -|hettx |0.1.3 |1 | | | -|hIRT |0.3.0 |1 | | | -|Hmsc |3.0-13 |1 | | | -|[inventorize](failures.md#inventorize)|1.1.1 |__+1__ | | | -|iNZightPlots |2.15.3 |1 | | | -|iNZightRegression |1.3.4 |1 | | | -|IRexamples |0.0.4 |1 | | | -|joineRML |0.4.6 |1 | | | -|JWileymisc |1.4.1 |1 | | | -|kmc |0.4-2 |1 | | | -|L2E |2.0 |1 | | | -|llbayesireg |1.0.0 |1 | | | -|LorenzRegression |1.0.0 |1 | | | -|lsirm12pl |1.3.1 |1 | | | -|mbsts |3.0 |1 | | | -|MendelianRandomization |0.10.0 |1 | | | -|MetabolicSurv |1.1.2 |1 | | | -|miWQS |0.4.4 |1 | | | -|mlmts |1.1.1 |1 | | | -|MRZero |0.2.0 |1 | | | -|Multiaovbay |0.1.0 |1 | | | -|multilevelTools |0.1.1 |1 | | | -|multinma |0.6.1 |1 | | | -|NCA |4.0.1 |1 | | | -|netcmc |1.0.2 |1 | | | -|NetworkChange |0.8 |1 | | | -|nlmeVPC |2.6 |1 | | | -|NMADiagT |0.1.2 |1 | | | -|optweight |0.2.5 |1 | | | -|OVtool |1.0.3 |1 | | | -|paths |0.1.1 |1 | | | -|PLMIX |2.1.1 |1 | | | -|popstudy |1.0.1 |1 | | | -|pould |1.0.1 |1 | | | -|powerly |1.8.6 |1 | | | -|pre |1.0.7 |1 | | | -|ProFAST |? | | | | -|psbcSpeedUp |2.0.6 |1 | | | -|pscore |0.4.0 |1 | | | -|psfmi |1.4.0 |1 | | | -|qPCRtools |1.0.1 |1 | | | -|qreport |1.0-0 |1 | | | -|qris |1.1.1 |1 | | | -|qte |1.3.1 |1 | | | -|quid |0.0.1 |1 | | | -|RATest |0.1.10 |1 | | | -|RcmdrPlugin.RiskDemo |3.2 |1 | | | -|rddtools |1.6.0 |1 | | | -|riskRegression |2023.12.21 |1 | | | -|rms |6.8-0 |1 | |1 | -|rmsb |1.1-0 |1 | | | -|robmed |1.0.2 |1 | | | -|robmedExtra |0.1.0 |1 | | | -|RPPanalyzer |1.4.9 |1 | | | -|RQdeltaCT |1.3.0 |1 | | | -|rstanarm |2.32.1 |1 | | | -|scCustomize |2.1.2 |1 | |1 | -|SCdeconR |1.0.0 |1 | | | -|scGate |1.6.2 |1 | | | -|scMappR |1.0.11 |1 | | | -|scRNAstat |0.1.1 |1 | | | -|sectorgap |0.1.0 |1 | | | -|SEERaBomb |2019.2 |1 | | | -|semicmprskcoxmsm |0.2.0 |1 | | | -|SensMap |0.7 |1 | | | -|Seurat |5.0.3 |1 | | | -|shinyTempSignal |0.0.8 |1 | | | -|Signac |1.13.0 |1 | | | -|SimplyAgree |0.2.0 |1 | | | -|sMSROC |0.1.2 |1 | | | -|SNPassoc |2.1-0 |1 | | | -|snplinkage |? | | | | -|SoupX |1.6.2 |1 | | | -|sparsereg |1.2 |1 | | | -|spikeSlabGAM |1.1-19 |1 | | | -|statsr |0.3.0 |1 | | | -|streamDAG |? | | | | -|survHE |2.0.1 |1 | |1 | -|survidm |1.3.2 |1 | | | -|tempted |0.1.0 |1 | | | -|[tidydr](failures.md#tidydr)|0.0.5 |__+1__ | | | -|tidyEdSurvey |0.1.2 |1 | | | -|tidyseurat |0.8.0 |1 | | | -|tidyvpc |1.5.1 |1 | | | -|treestats |1.0.5 |1 | | | -|TriDimRegression |1.0.2 |1 | | | -|triptych |0.1.2 |1 | | | -|TSrepr |1.1.0 |1 | | | -|twang |2.6 |1 | | | -|ubms |1.2.6 |1 | | | -|valse |0.1-0 |1 | | | -|vdg |1.2.3 |1 | | | -|visa |0.1.0 |1 | | | -|WRTDStidal |1.1.4 |1 | | | +|package |version |error |warning |note | +|:--------------------|:-------|:------|:-------|:----| +|abctools |1.1.7 |1 | | | +|adjustedCurves |? | | | | +|AnanseSeurat |? | | | | +|animalEKF |1.2 |1 | | | +|ANOM |0.5 |1 | | | +|aorsf |? | | | | +|APackOfTheClones |? | | | | +|autoReg |? | | | | +|AutoScore |? | | | | +|bayesdfa |1.3.3 |1 | | | +|bayesDP |1.3.6 |1 | | | +|BayesianFactorZoo |0.0.0.2 |1 | | | +|BayesSurvive |? | | | | +|bbmle |? | | | | +|BCClong |1.0.2 |1 | |1 | +|bmstdr |0.7.9 |1 | | | +|bspcov |1.0.0 |1 | | | +|BuyseTest |? | | | | +|calibmsm |? | | | | +|CalibrationCurves |? | | | | +|Canek |? | | | | +|CARBayesST |4.0 |1 | | | +|CaseBasedReasoning |? | | | | +|cellpypes |? | | | | +|CGPfunctions |0.6.3 |1 | | | +|chem16S |? | | | | +|CIARA |? | | | | +|clarify |? | | | | +|ClustAssess |? | | | | +|clustree |? | | | | +|cmprskcoxmsm |0.2.1 |1 | | | +|combiroc |? | | | | +|conos |? | | | | +|contrast |? | | | | +|contsurvplot |? | | | | +|countland |? | | | | +|coveffectsplot |? | | | | +|coxed |? | | | | +|CRMetrics |? | | | | +|crosslag |? | | | | +|csmpv |? | | | | +|ctsem |3.10.0 |1 | | | +|CytoSimplex |? | | | | +|depigner |? | | | | +|DepthProc |2.1.5 |1 | | | +|DIscBIO |? | | | | +|diversityForest |? | | | | +|DR.SC |? | | | | +|DynForest |? | | | | +|dyngen |? | | | | +|EcoEnsemble |1.0.5 |1 | | | +|ecolottery |1.0.0 |1 | | | +|EpiEstim |2.2-4 |1 | | | +|evalITR |? | | | | +|evolqg |0.3-4 |1 | | | +|explainer |? | | | | +|flexrsurv |? | | | | +|forestmangr |? | | | | +|gap |? | | | | +|GeomComb |1.0 |1 | | | +|ggeffects |? | | | | +|ggquickeda |? | | | | +|ggrcs |? | | | | +|ggrisk |? | | | | +|ggsector |? | | | | +|grandR |? | | | | +|Greg |? | | | | +|greport |? | | | | +|harmony |? | | | | +|hIRT |? | | | | +|Hmisc |? | | | | +|Hmsc |3.0-13 |1 | | | +|hydroroute |? | | | | +|[inventorize](failures.md#inventorize)|1.1.1 |__+1__ | | | +|iNZightRegression |1.3.4 |1 | | | +|IRexamples |0.0.4 |1 | | | +|jmBIG |? | | | | +|joineRML |0.4.6 |1 | | | +|jsmodule |? | | | | +|JWileymisc |? | | | | +|kmc |0.4-2 |1 | | | +|KMunicate |? | | | | +|L2E |2.0 |1 | | | +|Landmarking |? | | | | +|lavaSearch2 |? | | | | +|llbayesireg |1.0.0 |1 | | | +|LorenzRegression |1.0.0 |1 | | | +|lsirm12pl |1.3.1 |1 | | | +|MachineShop |? | | | | +|marginaleffects |? | | | | +|mbsts |3.0 |1 | | | +|MetabolicSurv |? | | | | +|MetaNet |? | | | | +|miWQS |0.4.4 |1 | | | +|mlmts |1.1.1 |1 | | | +|mlr |? | | | | +|MOSS |? | | | | +|mrbayes |? | | | | +|mstate |? | | | | +|Multiaovbay |0.1.0 |1 | | | +|multilevelTools |? | | | | +|multipleOutcomes |? | | | | +|netcmc |1.0.2 |1 | | | +|NetworkChange |0.8 |1 | | | +|neutralitytestr |? | | | | +|NMADiagT |0.1.2 |1 | | | +|obliqueRSF |? | | | | +|optweight |0.2.5 |1 | | | +|ormPlot |? | | | | +|OVtool |1.0.3 |1 | | | +|pagoda2 |? | | | | +|pammtools |? | | | | +|pander |? | | | | +|parameters |? | | | | +|PAsso |? | | | | +|paths |0.1.1 |1 | | | +|pctax |? | | | | +|pcutils |? | | | | +|PLMIX |2.1.1 |1 | | | +|pmcalibration |? | | | | +|popstudy |1.0.1 |1 | | | +|pould |? | | | | +|powerly |1.8.6 |1 | | | +|pre |1.0.7 |1 | | | +|PRECAST |? | | | | +|ProFAST |? | | | | +|psbcSpeedUp |? | | | | +|pscore |? | | | | +|psfmi |? | | | | +|pubh |? | | | | +|qPCRtools |? | | | | +|qreport |? | | | | +|quid |0.0.1 |1 | | | +|RcmdrPlugin.RiskDemo |3.2 |1 | | | +|rcssci |? | | | | +|rddtools |1.6.0 |1 | | | +|relsurv |? | | | | +|riskRegression |? | | | | +|rliger |? | | | | +|rms |? | | | | +|rmsb |? | | | | +|robber |? | | | | +|robmedExtra |0.1.0 |1 | | | +|rprev |? | | | | +|RQdeltaCT |? | | | | +|rstanarm |2.32.1 |1 | | | +|rTwig |? | | | | +|scCustomize |? | | | | +|SCdeconR |? | | | | +|scDiffCom |? | | | | +|scGate |? | | | | +|scMappR |? | | | | +|SCORPIUS |? | | | | +|scpi |? | | | | +|scpoisson |? | | | | +|SCpubr |? | | | | +|scRNAstat |? | | | | +|sectorgap |0.1.0 |1 | | | +|SEERaBomb |2019.2 |1 | | | +|semicmprskcoxmsm |0.2.0 |1 | | | +|SensMap |0.7 |1 | | | +|shinyTempSignal |? | | | | +|sievePH |1.1 |1 | | | +|Signac |? | | | | +|simET |? | | | | +|simstudy |? | | | | +|sMSROC |? | | | | +|SNPassoc |? | | | | +|snplinkage |? | | | | +|SoupX |? | | | | +|sparsereg |1.2 |1 | | | +|SPECK |? | | | | +|spikeSlabGAM |1.1-19 |1 | | | +|statsr |0.3.0 |1 | | | +|streamDAG |? | | | | +|sure |? | | | | +|Surrogate |? | | | | +|survex |? | | | | +|survHE |? | | | | +|survidm |1.3.2 |1 | | | +|SurvMetrics |? | | | | +|tempted |0.1.1 |1 | | | +|[tidydr](failures.md#tidydr)|0.0.5 |__+1__ | | | +|tidyEdSurvey |? | | | | +|tidyseurat |? | | | | +|treefit |? | | | | +|TriDimRegression |1.0.2 |1 | | | +|twang |2.6 |1 | | | +|valse |0.1-0 |1 | | | +|visa |? | | | | +|WpProj |? | | | | -## New problems (204) +## New problems (366) -|package |version |error |warning |note | -|:------------------|:--------|:--------|:--------|:--------| -|[actxps](problems.md#actxps)|1.4.0 |__+1__ | |__+1__ | -|[AeRobiology](problems.md#aerobiology)|2.0.1 |1 | |__+1__ | -|[afex](problems.md#afex)|1.3-1 |__+1__ | |__+1__ | -|[agricolaeplotr](problems.md#agricolaeplotr)|0.5.0 |__+1__ | | | -|[ammistability](problems.md#ammistability)|0.1.4 |__+1__ |-1 | | -|[AnalysisLin](problems.md#analysislin)|0.1.2 |__+1__ | | | -|[animbook](problems.md#animbook)|1.0.0 |__+1__ | | | -|[aopdata](problems.md#aopdata)|1.0.3 |__+1__ | |__+1__ | -|[ARPALData](problems.md#arpaldata)|1.5.2 |__+1__ | | | -|[asmbPLS](problems.md#asmbpls)|1.0.0 | |__+1__ |1 | -|[autoplotly](problems.md#autoplotly)|0.1.4 |__+2__ | | | -|[BayesGrowth](problems.md#bayesgrowth)|1.0.0 |__+1__ | |2 __+1__ | -|[bdl](problems.md#bdl)|1.0.5 | |__+1__ | | -|[BeeBDC](problems.md#beebdc)|1.1.1 |1 __+2__ | |1 | -|[blockCV](problems.md#blockcv)|3.1-3 |1 |1 |1 __+1__ | -|[boxly](problems.md#boxly)|0.1.1 |__+1__ | | | -|[bSi](problems.md#bsi)|1.0.0 | |__+1__ | | -|[cartograflow](problems.md#cartograflow)|1.0.5 |__+1__ | | | -|[cats](problems.md#cats)|1.0.2 |__+1__ | |1 | -|[cheem](problems.md#cheem)|0.4.0.0 |1 __+1__ | | | -|[chronicle](problems.md#chronicle)|0.3 |__+2__ | |1 __+1__ | -|[clinDataReview](problems.md#clindatareview)|1.5.1 |__+2__ | |1 __+1__ | -|[clinUtils](problems.md#clinutils)|0.1.5 |__+1__ |-1 |1 __+1__ | -|[ClusROC](problems.md#clusroc)|1.0.2 | |__+1__ | | -|[clustEff](problems.md#clusteff)|0.3.1 | |__+1__ | | -|[coda4microbiome](problems.md#coda4microbiome)|0.2.3 | |__+1__ | | -|[CohortPlat](problems.md#cohortplat)|1.0.5 |__+2__ | |__+1__ | -|[CompAREdesign](problems.md#comparedesign)|2.3.1 | |__+1__ | | -|[CoreMicrobiomeR](problems.md#coremicrobiomer)|0.1.0 |__+1__ | | | -|[correlationfunnel](problems.md#correlationfunnel)|0.2.0 |__+1__ | |1 | -|[corrViz](problems.md#corrviz)|0.1.0 |__+2__ | |1 __+1__ | -|[covidcast](problems.md#covidcast)|0.5.2 |__+2__ | |1 __+1__ | -|[Coxmos](problems.md#coxmos)|1.0.2 |1 |__+1__ |1 | -|[crosshap](problems.md#crosshap)|1.4.0 |__+1__ | | | -|[csa](problems.md#csa)|0.7.1 | |__+1__ | | -|[ctrialsgov](problems.md#ctrialsgov)|0.2.5 |__+1__ | |1 | -|[cubble](problems.md#cubble)|0.3.0 |__+1__ | |1 __+1__ | -|[dafishr](problems.md#dafishr)|1.0.0 |__+1__ | |2 | -|[damAOI](problems.md#damaoi)|0.0 |__+1__ | |__+1__ | -|[deeptime](problems.md#deeptime)|1.1.1 |__+2__ | | | -|[DEGRE](problems.md#degre)|0.2.0 | |__+1__ | | -|[densityarea](problems.md#densityarea)|0.1.0 |1 | |1 __+1__ | -|[did](problems.md#did)|2.1.2 | |1 __+1__ | | -|[distributional](problems.md#distributional)|0.4.0 |__+1__ | | | -|[dittoViz](problems.md#dittoviz)|1.0.1 |__+2__ | | | -|[dots](problems.md#dots)|0.0.2 |__+2__ | |1 __+1__ | -|[eks](problems.md#eks)|1.0.5 |__+2__ | |__+1__ | -|[entropart](problems.md#entropart)|1.6-13 |__+2__ | |__+1__ | -|[epiCleanr](problems.md#epicleanr)|0.2.0 |__+1__ | |1 | -|[epiR](problems.md#epir)|2.0.74 |__+1__ | |__+1__ | -|[esci](problems.md#esci)|1.0.2 |__+2__ | | | -|[evalITR](problems.md#evalitr)|1.0.0 |1 | |1 __+1__ | -|[explainer](problems.md#explainer)|1.0.1 |__+1__ | |1 | -|[fable.prophet](problems.md#fableprophet)|0.1.0 |__+1__ | |1 __+1__ | -|[fabletools](problems.md#fabletools)|0.4.2 |__+2__ | | | -|[ffp](problems.md#ffp)|0.2.2 |__+1__ | | | -|[fido](problems.md#fido)|1.0.4 |__+1__ | |1 | -|[flipr](problems.md#flipr)|0.3.3 |1 | |1 __+1__ | -|[fmesher](problems.md#fmesher)|0.1.5 |__+1__ | |1 | -|[forestecology](problems.md#forestecology)|0.2.0 |__+2__ | |1 __+1__ | -|[frailtyEM](problems.md#frailtyem)|1.0.1 |__+1__ | |2 | -|[FuncNN](problems.md#funcnn)|1.0 | |__+1__ |1 | -|[geomander](problems.md#geomander)|2.3.0 |__+2__ | |1 __+1__ | -|[geomtextpath](problems.md#geomtextpath)|0.1.3 |__+2__ | | | -|[germinationmetrics](problems.md#germinationmetrics)|0.1.8 |__+1__ |-1 | | -|[gganimate](problems.md#gganimate)|1.0.9 |__+2__ | |__+1__ | -|[ggautomap](problems.md#ggautomap)|0.3.2 |__+2__ | |__+1__ | -|[ggdark](problems.md#ggdark)|0.2.1 |__+2__ | |1 | -|[ggdist](problems.md#ggdist)|3.3.2 |1 __+2__ | |1 __+1__ | -|[ggedit](problems.md#ggedit)|0.4.1 |__+1__ | | | -|[ggfixest](problems.md#ggfixest)|0.1.0 |1 __+1__ | | | -|[ggfortify](problems.md#ggfortify)|0.4.17 |__+1__ | | | -|[ggh4x](problems.md#ggh4x)|0.2.8 |1 __+2__ | |__+1__ | -|[ggheatmap](problems.md#ggheatmap)|2.2 | |__+1__ | | -|[gghighlight](problems.md#gghighlight)|0.4.1 |__+3__ | |__+1__ | -|[ggiraph](problems.md#ggiraph)|0.8.9 |__+2__ | |1 | -|[ggmice](problems.md#ggmice)|0.1.0 |__+1__ | |__+1__ | -|[ggmulti](problems.md#ggmulti)|1.0.7 |__+3__ | |__+1__ | -|[ggparallel](problems.md#ggparallel)|0.4.0 |__+1__ | | | -|[ggplotlyExtra](problems.md#ggplotlyextra)|0.0.1 |__+1__ | |1 | -|[ggpol](problems.md#ggpol)|0.0.7 |__+1__ | |2 | -|[ggraph](problems.md#ggraph)|2.2.1 |1 __+1__ | |1 __+1__ | -|[ggredist](problems.md#ggredist)|0.0.2 |__+1__ | | | -|[ggResidpanel](problems.md#ggresidpanel)|0.3.0 |__+2__ | |__+1__ | -|[ggScatRidges](problems.md#ggscatridges)|0.1.1 | |__+1__ | | -|[ggseqplot](problems.md#ggseqplot)|0.8.3 |__+3__ | |__+1__ | -|[ggside](problems.md#ggside)|0.3.1 | |__+1__ | | -|[ggtern](problems.md#ggtern)|3.5.0 |__+1__ | |2 | -|[ggVennDiagram](problems.md#ggvenndiagram)|1.5.2 |__+1__ | |1 __+1__ | -|[GIFT](problems.md#gift)|1.3.2 |1 | |1 __+1__ | -|[GimmeMyPlot](problems.md#gimmemyplot)|0.1.0 | |__+1__ | | -|[gprofiler2](problems.md#gprofiler2)|0.2.3 |__+2__ | |__+1__ | -|[Greymodels](problems.md#greymodels)|2.0.1 |__+1__ | | | -|[h3jsr](problems.md#h3jsr)|1.3.1 |__+1__ | |__+1__ | -|[healthyR](problems.md#healthyr)|0.2.1 |__+1__ | |1 __+1__ | -|[healthyR.ai](problems.md#healthyrai)|0.0.13 |__+2__ | |__+1__ | -|[healthyR.ts](problems.md#healthyrts)|0.3.0 |__+2__ | |1 __+1__ | -|[heatmaply](problems.md#heatmaply)|1.5.0 |__+2__ | |1 __+1__ | -|[hilldiv](problems.md#hilldiv)|1.5.1 | |__+1__ | | -|[hJAM](problems.md#hjam)|1.0.0 | |__+1__ | | -|[HVT](problems.md#hvt)|23.11.1 |__+1__ | | | -|[HYPEtools](problems.md#hypetools)|1.6.1 |__+1__ | |__+1__ | -|[ImFoR](problems.md#imfor)|0.1.0 | |__+1__ | | -|[iNEXT.4steps](problems.md#inext4steps)|1.0.0 | |__+1__ | | -|[insane](problems.md#insane)|1.0.3 | |__+1__ | | -|[inTextSummaryTable](problems.md#intextsummarytable)|3.3.2 |1 __+1__ | |1 __+1__ | -|[itsdm](problems.md#itsdm)|0.2.1 |__+1__ | | | -|[karel](problems.md#karel)|0.1.1 |__+2__ | |1 | -|[latentcor](problems.md#latentcor)|2.0.1 |__+1__ | |1 | -|[mapSpain](problems.md#mapspain)|0.9.0 |1 __+1__ | |2 | -|[MBNMAdose](problems.md#mbnmadose)|0.4.3 |__+1__ | |1 __+1__ | -|[MBNMAtime](problems.md#mbnmatime)|0.2.4 |1 | |__+1__ | -|[mc2d](problems.md#mc2d)|0.2.0 | |__+1__ |1 | -|[MetaIntegrator](problems.md#metaintegrator)|2.1.3 | |__+1__ |2 | -|[MF.beta4](problems.md#mfbeta4)|1.0.3 | |1 __+1__ | | -|[MiMIR](problems.md#mimir)|1.5 |__+1__ | | | -|[miRetrieve](problems.md#miretrieve)|1.3.4 |__+1__ | | | -|[missingHE](problems.md#missinghe)|1.5.0 | |__+1__ |1 | -|[misspi](problems.md#misspi)|0.1.0 |__+1__ | | | -|[mlr3spatiotempcv](problems.md#mlr3spatiotempcv)|2.3.1 |1 __+2__ | |1 | -|[modeltime.resample](problems.md#modeltimeresample)|0.2.3 |__+1__ | |1 | -|[MSPRT](problems.md#msprt)|3.0 | |__+1__ |1 | -|[neatmaps](problems.md#neatmaps)|2.1.0 |__+1__ | |1 | -|[NetFACS](problems.md#netfacs)|0.5.0 |__+2__ | | | -|[NIMAA](problems.md#nimaa)|0.2.1 |__+3__ | |2 __+1__ | -|[nswgeo](problems.md#nswgeo)|0.4.0 |__+1__ | |1 | -|[OenoKPM](problems.md#oenokpm)|2.4.1 | |__+1__ | | -|[OmicNavigator](problems.md#omicnavigator)|1.13.13 |__+1__ | |1 | -|[otsad](problems.md#otsad)|0.2.0 |__+1__ | |1 | -|[pdxTrees](problems.md#pdxtrees)|0.4.0 |__+1__ | |1 __+1__ | -|[personalized](problems.md#personalized)|0.2.7 |__+1__ | | | -|[PGRdup](problems.md#pgrdup)|0.2.3.9 |__+1__ |-1 | | -|[plantTracker](problems.md#planttracker)|1.1.0 |__+1__ | |__+1__ | -|[Plasmidprofiler](problems.md#plasmidprofiler)|0.1.6 |__+1__ | | | -|[plotDK](problems.md#plotdk)|0.1.0 |__+1__ | |2 | -|[plotly](problems.md#plotly)|4.10.4 |__+2__ | |1 | -|[pmartR](problems.md#pmartr)|2.4.4 |__+1__ | |1 | -|[pmxTools](problems.md#pmxtools)|1.3 |__+1__ | |1 | -|[PointedSDMs](problems.md#pointedsdms)|1.3.2 |__+1__ |1 | | -|[posterior](problems.md#posterior)|1.5.0 |1 | |__+1__ | -|[PPQplan](problems.md#ppqplan)|1.1.0 |1 | |2 __+1__ | -|[ppseq](problems.md#ppseq)|0.2.4 |__+1__ | |1 __+1__ | -|[processmapR](problems.md#processmapr)|0.5.3 |__+1__ | | | -|[QuadratiK](problems.md#quadratik)|1.0.0 | |__+1__ |1 | -|[Radviz](problems.md#radviz)|0.9.3 |__+2__ | |1 __+1__ | -|[rangeMapper](problems.md#rangemapper)|2.0.3 |__+1__ | |__+1__ | -|[rassta](problems.md#rassta)|1.0.5 |__+3__ | | | -|[RCTrep](problems.md#rctrep)|1.2.0 | |__+1__ | | -|[redistmetrics](problems.md#redistmetrics)|1.0.7 |__+1__ | |1 __+1__ | -|[ref.ICAR](problems.md#reficar)|2.0.1 |__+1__ | |__+1__ | -|[remap](problems.md#remap)|0.3.1 |__+1__ | |__+1__ | -|[rKIN](problems.md#rkin)|1.0.2 |__+1__ | | | -|[rLFT](problems.md#rlft)|1.0.1 |__+1__ | |1 __+1__ | -|[roahd](problems.md#roahd)|1.4.3 |__+1__ | |1 | -|[roptions](problems.md#roptions)|1.0.3 |__+1__ | |1 | -|[scoringutils](problems.md#scoringutils)|1.2.2 |1 __+1__ | |__+1__ | -|[SCOUTer](problems.md#scouter)|1.0.0 | |__+1__ | | -|[SCVA](problems.md#scva)|1.3.1 |__+1__ | | | -|[see](problems.md#see)|0.8.4 |__+1__ | | | -|[sfnetworks](problems.md#sfnetworks)|0.6.4 |1 | |__+1__ | -|[sftrack](problems.md#sftrack)|0.5.4 |__+2__ | |__+1__ | -|[sglg](problems.md#sglg)|0.2.2 |__+1__ | | | -|[sievePH](problems.md#sieveph)|1.0.4 | |__+1__ | | -|[SouthParkRshiny](problems.md#southparkrshiny)|1.0.0 | |__+1__ |2 | -|[spatialrisk](problems.md#spatialrisk)|0.7.1 |__+1__ | |2 | -|[spatialsample](problems.md#spatialsample)|0.5.1 |__+3__ | |__+1__ | -|[spinifex](problems.md#spinifex)|0.3.7.0 |__+1__ | | | -|[spmodel](problems.md#spmodel)|0.6.0 |__+1__ | |1 __+1__ | -|[SqueakR](problems.md#squeakr)|1.3.0 |1 |__+1__ |1 __+1__ | -|[stats19](problems.md#stats19)|3.0.3 |1 | |__+1__ | -|[streamDepletr](problems.md#streamdepletr)|0.2.0 |__+1__ | |__+1__ | -|[survminer](problems.md#survminer)|0.4.9 | |__+1__ |1 | -|[symptomcheckR](problems.md#symptomcheckr)|0.1.3 | |__+1__ | | -|[tabledown](problems.md#tabledown)|1.0.0 |__+1__ | |1 | -|[tcgaViz](problems.md#tcgaviz)|1.0.2 | |__+1__ | | -|[TCIU](problems.md#tciu)|1.2.5 |__+2__ | |1 __+1__ | -|[TestGardener](problems.md#testgardener)|3.3.3 | |__+1__ | | -|[thematic](problems.md#thematic)|0.1.5 |__+2__ | | | -|[tidybayes](problems.md#tidybayes)|3.0.6 |1 __+2__ | |1 | -|[tidyCDISC](problems.md#tidycdisc)|0.2.1 |__+1__ | |1 | -|[tidysdm](problems.md#tidysdm)|0.9.4 |__+2__ | |__+1__ | -|[tidyterra](problems.md#tidyterra)|0.6.0 |__+1__ | | | -|[tidytransit](problems.md#tidytransit)|1.6.1 |__+1__ | |1 __+1__ | -|[tidytreatment](problems.md#tidytreatment)|0.2.2 |__+1__ | |1 __+1__ | -|[tilemaps](problems.md#tilemaps)|0.2.0 |__+1__ | |1 __+1__ | -|[timetk](problems.md#timetk)|2.9.0 |__+1__ | |1 | -|[tongfen](problems.md#tongfen)|0.3.5 |1 | |1 __+1__ | -|[TOSTER](problems.md#toster)|0.8.2 |__+3__ | |__+1__ | -|[TreatmentPatterns](problems.md#treatmentpatterns)|2.6.6 |__+1__ | | | -|[trelliscopejs](problems.md#trelliscopejs)|0.2.6 |__+1__ | | | -|[tsnet](problems.md#tsnet)|0.1.0 |__+1__ | |2 | -|[umiAnalyzer](problems.md#umianalyzer)|1.0.0 |__+1__ | | | -|[UniprotR](problems.md#uniprotr)|2.4.0 | |__+1__ | | -|[VALERIE](problems.md#valerie)|1.1.0 | |__+1__ |1 -1 | -|[VancouvR](problems.md#vancouvr)|0.1.8 |__+1__ | | | -|[vannstats](problems.md#vannstats)|1.3.4.14 | |__+1__ | | -|[vici](problems.md#vici)|0.7.3 | |__+1__ | | -|[vivaldi](problems.md#vivaldi)|1.0.1 |__+3__ | |1 __+1__ | -|[vvshiny](problems.md#vvshiny)|0.1.1 |__+2__ | | | -|[waywiser](problems.md#waywiser)|0.5.1 |__+1__ | |1 __+1__ | -|[wildlifeDI](problems.md#wildlifedi)|1.0.0 |__+1__ | |__+1__ | -|[wilson](problems.md#wilson)|2.4.2 |__+1__ | | | -|[WorldMapR](problems.md#worldmapr)|0.1.1 |__+2__ | |1 | -|[xaringanthemer](problems.md#xaringanthemer)|0.4.2 |1 __+1__ | | | +|package |version |error |warning |note | +|:-----------------------|:---------|:--------|:-------|:--------| +|[accSDA](problems.md#accsda)|1.1.3 |__+1__ | | | +|[activAnalyzer](problems.md#activanalyzer)|2.1.1 |__+1__ | |1 __+1__ | +|[actxps](problems.md#actxps)|1.4.0 |__+1__ | |__+1__ | +|[add2ggplot](problems.md#add2ggplot)|0.3.0 |__+2__ | |1 __+1__ | +|[AeRobiology](problems.md#aerobiology)|2.0.1 |1 | |__+1__ | +|[afex](problems.md#afex)|1.3-1 |__+1__ | |__+1__ | +|[AgroR](problems.md#agror)|1.3.6 |__+1__ | | | +|[allMT](problems.md#allmt)|0.1.0 |__+1__ | | | +|[AnalysisLin](problems.md#analysislin)|0.1.2 |__+1__ | | | +|[animbook](problems.md#animbook)|1.0.0 |__+1__ | | | +|[aplot](problems.md#aplot)|0.2.2 |__+1__ | | | +|[ASRgenomics](problems.md#asrgenomics)|1.1.4 |__+2__ | |1 | +|[auditor](problems.md#auditor)|1.3.5 |__+2__ | |__+1__ | +|[augmentedRCBD](problems.md#augmentedrcbd)|0.1.7 |__+2__ |-1 | | +|[autoplotly](problems.md#autoplotly)|0.1.4 |__+2__ | | | +|[baggr](problems.md#baggr)|0.7.8 |__+2__ | |2 __+1__ | +|[bayefdr](problems.md#bayefdr)|0.2.1 |__+2__ | | | +|[BayesGrowth](problems.md#bayesgrowth)|1.0.0 |__+1__ | |2 __+1__ | +|[BayesianReasoning](problems.md#bayesianreasoning)|0.4.2 |__+1__ | |__+1__ | +|[bayestestR](problems.md#bayestestr)|0.13.2 |1 __+1__ | | | +|[bdots](problems.md#bdots)|1.2.5 |__+1__ | |__+1__ | +|[bdrc](problems.md#bdrc)|1.1.0 |__+1__ | |__+1__ | +|[BeeBDC](problems.md#beebdc)|1.1.1 |1 __+1__ | |1 | +|[besthr](problems.md#besthr)|0.3.2 |__+2__ | |__+1__ | +|[BetaPASS](problems.md#betapass)|1.1-2 |__+2__ | |__+1__ | +|[biblioverlap](problems.md#biblioverlap)|1.0.2 |__+1__ | |1 | +|[biscale](problems.md#biscale)|1.0.0 |1 __+1__ | |1 | +|[BlandAltmanLeh](problems.md#blandaltmanleh)|0.3.1 |__+1__ | | | +|[bnma](problems.md#bnma)|1.6.0 |__+1__ | |__+1__ | +|[boxly](problems.md#boxly)|0.1.1 |__+1__ | | | +|[braidReports](problems.md#braidreports)|0.5.4 |__+1__ | | | +|[brolgar](problems.md#brolgar)|1.0.1 |__+2__ | |__+1__ | +|[calendR](problems.md#calendr)|1.2 |__+1__ | | | +|[calendRio](problems.md#calendrio)|0.2.0 |__+1__ | | | +|[capm](problems.md#capm)|0.14.0 |__+1__ | |1 | +|[cartograflow](problems.md#cartograflow)|1.0.5 |__+1__ | | | +|[cats](problems.md#cats)|1.0.2 |__+1__ | |1 | +|[cheem](problems.md#cheem)|0.4.0.0 |1 __+1__ | | | +|[chillR](problems.md#chillr)|0.75 |__+1__ | | | +|[chronicle](problems.md#chronicle)|0.3 |__+2__ | |1 __+1__ | +|[circumplex](problems.md#circumplex)|0.3.10 |__+1__ | |__+1__ | +|[cities](problems.md#cities)|0.1.3 |__+2__ | |__+1__ | +|[CleaningValidation](problems.md#cleaningvalidation)|1.0 |__+1__ | | | +|[clinDataReview](problems.md#clindatareview)|1.5.2 |__+2__ | |1 __+1__ | +|[clinUtils](problems.md#clinutils)|0.2.0 |__+1__ |-1 |1 __+1__ | +|[ClustImpute](problems.md#clustimpute)|0.2.4 |__+1__ | |1 | +|[cogmapr](problems.md#cogmapr)|0.9.3 |__+1__ | | | +|[CohortPlat](problems.md#cohortplat)|1.0.5 |__+2__ | |__+1__ | +|[CoMiRe](problems.md#comire)|0.8 |__+1__ | | | +|[CommKern](problems.md#commkern)|1.0.1 |__+2__ | |1 __+1__ | +|[conText](problems.md#context)|1.4.3 |__+2__ | |1 __+1__ | +|[CoreMicrobiomeR](problems.md#coremicrobiomer)|0.1.0 |__+1__ | | | +|[correlationfunnel](problems.md#correlationfunnel)|0.2.0 |__+1__ | |1 | +|[corrViz](problems.md#corrviz)|0.1.0 |__+2__ | |1 __+1__ | +|[covidcast](problems.md#covidcast)|0.5.2 |__+2__ | |1 __+1__ | +|[cricketdata](problems.md#cricketdata)|0.2.3 |1 | |1 __+1__ | +|[crosshap](problems.md#crosshap)|1.4.0 |__+1__ | | | +|[crplyr](problems.md#crplyr)|0.4.0 |__+2__ | |__+1__ | +|[ctrialsgov](problems.md#ctrialsgov)|0.2.5 |__+1__ | |1 | +|[cubble](problems.md#cubble)|0.3.0 |__+1__ | |1 __+1__ | +|[dabestr](problems.md#dabestr)|2023.9.12 |__+3__ | |__+1__ | +|[DAISIEprep](problems.md#daisieprep)|0.4.0 |__+1__ | | | +|[dataresqc](problems.md#dataresqc)|1.1.1 |__+1__ | | | +|[ddtlcm](problems.md#ddtlcm)|0.2.1 |__+3__ | |1 __+1__ | +|[dfoliatR](problems.md#dfoliatr)|0.3.0 |__+3__ | |__+1__ | +|[directlabels](problems.md#directlabels)|2024.1.21 |__+1__ | |__+1__ | +|[disprofas](problems.md#disprofas)|0.1.3 |__+2__ | | | +|[distributional](problems.md#distributional)|0.4.0 |__+1__ | | | +|[dittoViz](problems.md#dittoviz)|1.0.1 |__+2__ | | | +|[dobin](problems.md#dobin)|1.0.4 |__+1__ | |__+1__ | +|[dogesr](problems.md#dogesr)|0.5.0 |1 | |1 __+1__ | +|[dotsViolin](problems.md#dotsviolin)|0.0.1 |__+1__ | |1 | +|[ds4psy](problems.md#ds4psy)|1.0.0 |__+1__ | | | +|[edecob](problems.md#edecob)|1.2.2 |__+1__ | | | +|[entropart](problems.md#entropart)|1.6-13 |__+2__ | |__+1__ | +|[envalysis](problems.md#envalysis)|0.7.0 |__+3__ | |__+1__ | +|[epiCleanr](problems.md#epicleanr)|0.2.0 |__+1__ | |1 | +|[EpiInvert](problems.md#epiinvert)|0.3.1 |__+1__ | |1 | +|[esci](problems.md#esci)|1.0.2 |__+2__ | | | +|[EvidenceSynthesis](problems.md#evidencesynthesis)|0.5.0 |__+3__ | |__+1__ | +|[EvolutionaryGames](problems.md#evolutionarygames)|0.1.2 |__+2__ | |__+1__ | +|[EvoPhylo](problems.md#evophylo)|0.3.2 |1 __+1__ | |1 __+1__ | +|[evprof](problems.md#evprof)|1.1.2 |__+2__ | |1 | +|[expirest](problems.md#expirest)|0.1.6 |__+1__ | | | +|[explore](problems.md#explore)|1.3.0 |__+2__ | |__+1__ | +|[ezplot](problems.md#ezplot)|0.7.13 |__+2__ | |__+1__ | +|[fable.prophet](problems.md#fableprophet)|0.1.0 |__+1__ | |1 __+1__ | +|[fabletools](problems.md#fabletools)|0.4.2 |__+2__ | | | +|[factoextra](problems.md#factoextra)|1.0.7 |__+1__ | | | +|[faux](problems.md#faux)|1.2.1 |1 __+1__ | |__+1__ | +|[fddm](problems.md#fddm)|0.5-2 |__+1__ | |1 | +|[fdrci](problems.md#fdrci)|2.4 |__+1__ | | | +|[ffp](problems.md#ffp) |0.2.2 |__+1__ | | | +|[fido](problems.md#fido)|1.1.0 |__+2__ |1 |2 | +|[figuRes2](problems.md#figures2)|1.0.0 |__+2__ | | | +|[flipr](problems.md#flipr)|0.3.3 |1 | |1 __+1__ | +|[FMM](problems.md#fmm) |0.3.1 |__+1__ | |__+1__ | +|[fmriqa](problems.md#fmriqa)|0.3.0 |__+1__ | |1 | +|[foreSIGHT](problems.md#foresight)|1.2.0 |__+2__ | |1 | +|[frailtyEM](problems.md#frailtyem)|1.0.1 |__+1__ | |2 | +|[funcharts](problems.md#funcharts)|1.4.1 |__+1__ | | | +|[gapmap](problems.md#gapmap)|1.0.0 |__+2__ | |__+1__ | +|[gasper](problems.md#gasper)|1.1.6 |__+2__ | |1 | +|[gaussplotR](problems.md#gaussplotr)|0.2.5 |__+1__ | |__+1__ | +|[gg.gap](problems.md#gggap)|1.3 |__+1__ | |1 | +|[ggalignment](problems.md#ggalignment)|1.0.1 |__+2__ | |__+1__ | +|[ggalt](problems.md#ggalt)|0.4.0 |1 | |2 __+1__ | +|[gganimate](problems.md#gganimate)|1.0.9 |__+2__ | |__+1__ | +|[ggbrace](problems.md#ggbrace)|0.1.1 |__+1__ | | | +|[ggbrain](problems.md#ggbrain)|0.8.1 |__+1__ | |1 __+1__ | +|[ggbreak](problems.md#ggbreak)|0.1.2 |__+2__ | |__+1__ | +|[ggdark](problems.md#ggdark)|0.2.1 |__+2__ | |1 | +|[ggdist](problems.md#ggdist)|3.3.2 |1 __+2__ | |1 __+1__ | +|[ggedit](problems.md#ggedit)|0.4.1 |__+1__ | | | +|[ggExtra](problems.md#ggextra)|0.10.1 |__+1__ | |1 __+1__ | +|[ggfixest](problems.md#ggfixest)|0.1.0 |1 __+1__ | | | +|[ggflowchart](problems.md#ggflowchart)|1.0.0 |__+2__ | |__+1__ | +|[ggforce](problems.md#ggforce)|0.4.2 |__+1__ | |1 | +|[ggfortify](problems.md#ggfortify)|0.4.17 |__+1__ | | | +|[ggfoundry](problems.md#ggfoundry)|0.1.1 |__+1__ | |__+1__ | +|[gggap](problems.md#gggap)|1.0.1 |__+1__ | |1 | +|[ggh4x](problems.md#ggh4x)|0.2.8 |1 __+2__ | |__+1__ | +|[gghdx](problems.md#gghdx)|0.1.3 |1 __+1__ | |__+1__ | +|[gghighlight](problems.md#gghighlight)|0.4.1 |1 __+2__ | |1 | +|[ggHoriPlot](problems.md#gghoriplot)|1.0.1 |__+1__ | |__+1__ | +|[ggiraph](problems.md#ggiraph)|0.8.10 |__+2__ | |2 | +|[ggiraphExtra](problems.md#ggiraphextra)|0.3.0 |__+2__ | |__+1__ | +|[ggmap](problems.md#ggmap)|4.0.0 |__+1__ | |1 | +|[ggmice](problems.md#ggmice)|0.1.0 |__+1__ | |__+1__ | +|[ggmulti](problems.md#ggmulti)|1.0.7 |__+3__ | |__+1__ | +|[ggparallel](problems.md#ggparallel)|0.4.0 |__+1__ | | | +|[ggpicrust2](problems.md#ggpicrust2)|1.7.3 |__+1__ | |1 | +|[ggpie](problems.md#ggpie)|0.2.5 |__+2__ | |__+1__ | +|[ggplotlyExtra](problems.md#ggplotlyextra)|0.0.1 |__+1__ | |1 | +|[ggpol](problems.md#ggpol)|0.0.7 |__+1__ | |2 | +|[ggprism](problems.md#ggprism)|1.0.5 |__+1__ | | | +|[ggpubr](problems.md#ggpubr)|0.6.0 |__+2__ | | | +|[ggraph](problems.md#ggraph)|2.2.1 |1 __+1__ | |1 __+1__ | +|[ggredist](problems.md#ggredist)|0.0.2 |__+1__ | | | +|[ggResidpanel](problems.md#ggresidpanel)|0.3.0 |__+2__ | |__+1__ | +|[ggseqplot](problems.md#ggseqplot)|0.8.4 |__+3__ | |__+1__ | +|[ggside](problems.md#ggside)|0.3.1 |__+1__ |__+1__ | | +|[ggstatsplot](problems.md#ggstatsplot)|0.12.3 |1 __+1__ | | | +|[ggtern](problems.md#ggtern)|3.5.0 |__+1__ | |2 | +|[ggthemes](problems.md#ggthemes)|5.1.0 |__+1__ | |2 | +|[ggupset](problems.md#ggupset)|0.3.0 |__+1__ | | | +|[ggVennDiagram](problems.md#ggvenndiagram)|1.5.2 |__+1__ | |1 __+1__ | +|[graphPAF](problems.md#graphpaf)|2.0.0 |__+1__ | | | +|[greatR](problems.md#greatr)|2.0.0 |__+1__ | |__+1__ | +|[Greymodels](problems.md#greymodels)|2.0.1 |__+1__ | | | +|[groupdata2](problems.md#groupdata2)|2.0.3 |__+1__ | |__+1__ | +|[GSD](problems.md#gsd) |1.0.0 |__+1__ | | | +|[gtExtras](problems.md#gtextras)|0.5.0 |__+1__ | | | +|[HaploCatcher](problems.md#haplocatcher)|1.0.4 |__+1__ | |__+1__ | +|[hdnom](problems.md#hdnom)|6.0.3 |__+2__ | |__+1__ | +|[healthyR](problems.md#healthyr)|0.2.1 |__+1__ | |1 __+1__ | +|[healthyR.ai](problems.md#healthyrai)|0.0.13 |__+2__ | |__+1__ | +|[healthyR.ts](problems.md#healthyrts)|0.3.0 |__+2__ | |1 __+1__ | +|[heatmaply](problems.md#heatmaply)|1.5.0 |__+3__ | |1 __+1__ | +|[hermiter](problems.md#hermiter)|2.3.1 |__+1__ | |2 __+1__ | +|[heumilkr](problems.md#heumilkr)|0.2.0 |__+1__ | |__+1__ | +|[heuristicsmineR](problems.md#heuristicsminer)|0.3.0 | | |__+1__ | +|[HistDAWass](problems.md#histdawass)|1.0.8 |__+1__ | |1 | +|[huito](problems.md#huito)|0.2.4 |1 __+1__ | |__+1__ | +|[hurricaneexposure](problems.md#hurricaneexposure)|0.1.1 |__+2__ | |2 __+1__ | +|[HVT](problems.md#hvt) |24.5.2 |__+1__ | | | +|[hydraulics](problems.md#hydraulics)|0.7.0 |__+2__ | |__+1__ | +|[hyperSpec](problems.md#hyperspec)|0.100.2 |__+1__ | | | +|[hypsoLoop](problems.md#hypsoloop)|0.2.0 | |__+1__ | | +|[ICvectorfields](problems.md#icvectorfields)|0.1.2 |__+1__ | |__+1__ | +|[idiogramFISH](problems.md#idiogramfish)|2.0.13 |1 | |__+1__ | +|[idopNetwork](problems.md#idopnetwork)|0.1.2 |__+1__ | |__+1__ | +|[iglu](problems.md#iglu)|4.0.0 |__+2__ | |__+1__ | +|[igoR](problems.md#igor)|0.2.0 |__+1__ | |1 __+1__ | +|[immunarch](problems.md#immunarch)|0.9.1 |__+1__ | |1 | +|[immuneSIM](problems.md#immunesim)|0.8.7 |__+1__ | |2 | +|[iNEXT.4steps](problems.md#inext4steps)|1.0.0 |__+3__ | |__+1__ | +|[iNEXT.beta3D](problems.md#inextbeta3d)|1.0.2 |__+1__ |1 | | +|[insurancerating](problems.md#insurancerating)|0.7.4 |__+1__ | | | +|[inTextSummaryTable](problems.md#intextsummarytable)|3.3.2 |1 __+1__ | |1 __+1__ | +|[jskm](problems.md#jskm)|0.5.3 |__+3__ | |__+1__ | +|[KaradaColor](problems.md#karadacolor)|0.1.5 |__+1__ | | | +|[karel](problems.md#karel)|0.1.1 |__+2__ | |1 | +|[kDGLM](problems.md#kdglm)|1.2.0 |1 __+1__ | | | +|[labsimplex](problems.md#labsimplex)|0.1.2 |__+2__ | |__+1__ | +|[landscapemetrics](problems.md#landscapemetrics)|2.1.2 |__+1__ | |1 | +|[landscapetools](problems.md#landscapetools)|0.5.0 |__+2__ | |__+1__ | +|[latentcor](problems.md#latentcor)|2.0.1 |__+1__ | | | +|[latte](problems.md#latte)|0.2.1 |__+1__ | |1 | +|[lemon](problems.md#lemon)|0.4.9 |__+3__ | |__+1__ | +|[lfproQC](problems.md#lfproqc)|0.1.0 |__+2__ | |1 __+1__ | +|[LLSR](problems.md#llsr)|0.0.3.1 |__+1__ | | | +|[LMoFit](problems.md#lmofit)|0.1.7 |__+1__ | |1 __+1__ | +|[lomb](problems.md#lomb)|2.5.0 |__+1__ | |1 | +|[LongDat](problems.md#longdat)|1.1.2 |__+1__ | |__+1__ | +|[longitudinalcascade](problems.md#longitudinalcascade)|0.3.2.6 |__+1__ | | | +|[longmixr](problems.md#longmixr)|1.0.0 |__+1__ | |__+1__ | +|[manhplot](problems.md#manhplot)|1.1 |__+1__ | | | +|[mau](problems.md#mau) |0.1.2 |__+1__ | | | +|[MBNMAdose](problems.md#mbnmadose)|0.4.3 |__+1__ | |1 __+1__ | +|[MBNMAtime](problems.md#mbnmatime)|0.2.4 |1 | |__+1__ | +|[metaforest](problems.md#metaforest)|0.1.4 |1 __+1__ | | | +|[metan](problems.md#metan)|1.18.0 |__+1__ | | | +|[metaplot](problems.md#metaplot)|0.8.4 |__+1__ | | | +|[metR](problems.md#metr)|0.15.0 |__+2__ | |1 __+1__ | +|[miceFast](problems.md#micefast)|0.8.2 |__+3__ | |2 __+1__ | +|[MicrobiomeStat](problems.md#microbiomestat)|1.2 |__+1__ | | | +|[micromap](problems.md#micromap)|1.9.8 |__+2__ | |1 | +|[MiMIR](problems.md#mimir)|1.5 |__+1__ | | | +|[MIMSunit](problems.md#mimsunit)|0.11.2 |__+1__ | | | +|[miRetrieve](problems.md#miretrieve)|1.3.4 |__+1__ | | | +|[misspi](problems.md#misspi)|0.1.0 |__+1__ | | | +|[mizer](problems.md#mizer)|2.5.1 |__+1__ | |1 | +|[mlr3spatiotempcv](problems.md#mlr3spatiotempcv)|2.3.1 |1 __+1__ | |1 | +|[mlr3viz](problems.md#mlr3viz)|0.8.0 |__+1__ | | | +|[modeltime.resample](problems.md#modeltimeresample)|0.2.3 |__+1__ | |1 | +|[mosaic](problems.md#mosaic)|1.9.1 |1 __+2__ | |4 | +|[motifr](problems.md#motifr)|1.0.0 |__+1__ | | | +|[mpwR](problems.md#mpwr)|0.1.5 |__+3__ | |__+1__ | +|[mrfDepth](problems.md#mrfdepth)|1.0.17 |__+1__ | |1 | +|[musclesyneRgies](problems.md#musclesynergies)|1.2.5 |__+3__ | |__+1__ | +|[naniar](problems.md#naniar)|1.1.0 |__+1__ | |__+1__ | +|[neatmaps](problems.md#neatmaps)|2.1.0 |__+1__ | |1 | +|[NetFACS](problems.md#netfacs)|0.5.0 |__+2__ | |__+1__ | +|[NHSRplotthedots](problems.md#nhsrplotthedots)|0.1.0 |__+2__ | |1 __+1__ | +|[nima](problems.md#nima)|0.6.2 |__+1__ | |1 | +|[NIMAA](problems.md#nimaa)|0.2.1 |__+3__ | |2 __+1__ | +|[nparACT](problems.md#nparact)|0.8 |__+1__ | | | +|[nullabor](problems.md#nullabor)|0.3.9 |__+1__ | |1 | +|[OBIC](problems.md#obic)|3.0.2 |__+1__ | |1 __+1__ | +|[OddsPlotty](problems.md#oddsplotty)|1.0.2 |__+1__ | |1 __+1__ | +|[ofpetrial](problems.md#ofpetrial)|0.1.1 |__+1__ | | | +|[OmicNavigator](problems.md#omicnavigator)|1.13.13 |__+2__ | |1 | +|[oncomsm](problems.md#oncomsm)|0.1.4 |__+2__ | |2 __+1__ | +|[ontophylo](problems.md#ontophylo)|1.1.3 |__+1__ | |2 | +|[OpenLand](problems.md#openland)|1.0.3 |__+2__ | |__+1__ | +|[ordbetareg](problems.md#ordbetareg)|0.7.2 |__+1__ | |2 __+1__ | +|[otsad](problems.md#otsad)|0.2.0 |__+1__ | |1 | +|[OutliersO3](problems.md#outlierso3)|0.6.3 |__+1__ | |__+1__ | +|[palettes](problems.md#palettes)|0.2.0 |__+1__ | |__+1__ | +|[ParBayesianOptimization](problems.md#parbayesianoptimization)|1.2.6 |__+1__ | | | +|[patchwork](problems.md#patchwork)|1.2.0 |__+1__ | | | +|[pathfindR](problems.md#pathfindr)|2.4.1 |1 __+1__ | |__+1__ | +|[pdSpecEst](problems.md#pdspecest)|1.2.4 |__+1__ | |3 __+1__ | +|[pdxTrees](problems.md#pdxtrees)|0.4.0 |__+1__ | |1 __+1__ | +|[personalized](problems.md#personalized)|0.2.7 |__+1__ | | | +|[PGRdup](problems.md#pgrdup)|0.2.3.9 |__+1__ |-1 | | +|[Plasmidprofiler](problems.md#plasmidprofiler)|0.1.6 |__+1__ | | | +|[plotDK](problems.md#plotdk)|0.1.0 |__+1__ | |2 | +|[plotly](problems.md#plotly)|4.10.4 |__+2__ | |1 | +|[pmartR](problems.md#pmartr)|2.4.5 |__+1__ | |1 | +|[pmxTools](problems.md#pmxtools)|1.3 |__+1__ | |1 | +|[politeness](problems.md#politeness)|0.9.3 |__+2__ | |1 __+1__ | +|[posterior](problems.md#posterior)|1.5.0 |1 | |__+1__ | +|[PPQplan](problems.md#ppqplan)|1.1.0 |1 | |2 __+1__ | +|[ppseq](problems.md#ppseq)|0.2.4 |__+1__ | |1 __+1__ | +|[PPtreeregViz](problems.md#pptreeregviz)|2.0.5 |__+2__ | |1 __+1__ | +|[precrec](problems.md#precrec)|0.14.4 |__+1__ | |1 __+1__ | +|[prevR](problems.md#prevr)|5.0.0 |__+1__ | |1 __+1__ | +|[primerTree](problems.md#primertree)|1.0.6 |__+1__ | | | +|[processmapR](problems.md#processmapr)|0.5.3 |__+1__ | | | +|[PTXQC](problems.md#ptxqc)|1.1.1 |__+1__ | |1 | +|[qacBase](problems.md#qacbase)|1.0.3 |__+1__ | | | +|[qgcomp](problems.md#qgcomp)|2.15.2 |__+2__ | |__+1__ | +|[qgcompint](problems.md#qgcompint)|0.7.0 |__+2__ | |__+1__ | +|[qpNCA](problems.md#qpnca)|1.1.6 |__+1__ | |__+1__ | +|[QurvE](problems.md#qurve)|1.1.1 |__+1__ | |1 | +|[r2dii.plot](problems.md#r2diiplot)|0.4.0 |__+2__ | | | +|[Radviz](problems.md#radviz)|0.9.3 |__+2__ | |__+1__ | +|[rainette](problems.md#rainette)|0.3.1.1 |__+1__ | | | +|[rassta](problems.md#rassta)|1.0.5 |__+3__ | | | +|[RAT](problems.md#rat) |0.3.1 |__+1__ | | | +|[Rcan](problems.md#rcan)|1.3.82 |__+1__ | |1 | +|[redist](problems.md#redist)|4.2.0 |__+1__ | |1 __+1__ | +|[Relectoral](problems.md#relectoral)|0.1.0 |1 __+1__ | |2 | +|[reliabilitydiag](problems.md#reliabilitydiag)|0.2.1 |__+1__ | | | +|[relliptical](problems.md#relliptical)|1.3.0 |__+1__ | |1 | +|[Repliscope](problems.md#repliscope)|1.1.1 |__+1__ | | | +|[reportRmd](problems.md#reportrmd)|0.1.0 |__+2__ | |__+1__ | +|[reReg](problems.md#rereg)|1.4.6 |__+1__ | | | +|[reservr](problems.md#reservr)|0.0.2 |__+2__ | |2 __+1__ | +|[restriktor](problems.md#restriktor)|0.5-60 |__+1__ | | | +|[RevGadgets](problems.md#revgadgets)|1.2.1 |__+1__ | | | +|[rimu](problems.md#rimu)|0.6 |1 __+1__ | |__+1__ | +|[rKOMICS](problems.md#rkomics)|1.3 |__+1__ | |2 | +|[rmcorr](problems.md#rmcorr)|0.6.0 |1 | |__+1__ | +|[RNAseqQC](problems.md#rnaseqqc)|0.1.4 |__+1__ | |1 __+1__ | +|[roahd](problems.md#roahd)|1.4.3 |__+1__ | |1 | +|[robustbase](problems.md#robustbase)|0.99-2 |__+1__ | |3 | +|[romic](problems.md#romic)|1.1.3 |__+1__ | | | +|[roptions](problems.md#roptions)|1.0.3 |__+1__ | |1 | +|[rotations](problems.md#rotations)|1.6.5 |__+2__ | |3 | +|[rreg](problems.md#rreg)|0.2.1 |__+1__ | | | +|[rSDI](problems.md#rsdi)|0.2.1 |__+1__ | |__+1__ | +|[SangerTools](problems.md#sangertools)|1.0.2 |__+2__ | |__+1__ | +|[santaR](problems.md#santar)|1.2.4 |1 | |__+1__ | +|[scoringutils](problems.md#scoringutils)|1.2.2 |1 __+1__ | |__+1__ | +|[SCVA](problems.md#scva)|1.3.1 |__+1__ | | | +|[SDLfilter](problems.md#sdlfilter)|2.3.3 |__+1__ | | | +|[see](problems.md#see) |0.8.4 |__+1__ | | | +|[sentimentr](problems.md#sentimentr)|2.9.0 |__+1__ | |1 | +|[sentometrics](problems.md#sentometrics)|1.0.0 |__+1__ | |4 | +|[sglg](problems.md#sglg)|0.2.2 |__+1__ | | | +|[SHAPforxgboost](problems.md#shapforxgboost)|0.1.3 |__+1__ | | | +|[shazam](problems.md#shazam)|1.2.0 |__+2__ | |__+1__ | +|[simulariatools](problems.md#simulariatools)|2.5.1 |__+1__ | | | +|[sjPlot](problems.md#sjplot)|2.8.16 |__+2__ | |__+1__ | +|[SleepCycles](problems.md#sleepcycles)|1.1.4 |__+1__ | | | +|[smallsets](problems.md#smallsets)|2.0.0 |__+2__ | |1 __+1__ | +|[smdi](problems.md#smdi)|0.2.2 |1 | |__+1__ | +|[soc.ca](problems.md#socca)|0.8.0 |__+1__ | |2 | +|[spbal](problems.md#spbal)|1.0.0 |__+1__ | |__+1__ | +|[speccurvieR](problems.md#speccurvier)|0.3.0 |__+1__ | |1 | +|[spinifex](problems.md#spinifex)|0.3.7.0 |__+1__ | | | +|[spotoroo](problems.md#spotoroo)|0.1.4 |__+2__ | |1 __+1__ | +|[SqueakR](problems.md#squeakr)|1.3.0 |1 | |1 __+1__ | +|[stabm](problems.md#stabm)|1.2.2 |__+3__ | |__+1__ | +|[starvz](problems.md#starvz)|0.8.0 |__+1__ | | | +|[statgenMPP](problems.md#statgenmpp)|1.0.2 |__+2__ | |__+1__ | +|[statVisual](problems.md#statvisual)|1.2.1 |__+2__ | |1 __+1__ | +|[superheat](problems.md#superheat)|0.1.0 |__+2__ | |1 | +|[surveyexplorer](problems.md#surveyexplorer)|0.1.0 |__+1__ | | | +|[survivalAnalysis](problems.md#survivalanalysis)|0.3.0 |1 __+1__ | |__+1__ | +|[Sysrecon](problems.md#sysrecon)|0.1.3 |__+1__ | |1 | +|[tabledown](problems.md#tabledown)|1.0.0 |__+1__ | |1 | +|[tabr](problems.md#tabr)|0.4.9 |__+1__ | | | +|[TcGSA](problems.md#tcgsa)|0.12.10 |__+1__ | | | +|[TCIU](problems.md#tciu)|1.2.6 |__+2__ | |1 __+1__ | +|[thematic](problems.md#thematic)|0.1.5 |__+2__ | | | +|[tidybayes](problems.md#tidybayes)|3.0.6 |1 __+2__ | |1 | +|[tidyCDISC](problems.md#tidycdisc)|0.2.1 |__+1__ | |1 | +|[tidysdm](problems.md#tidysdm)|0.9.4 |__+1__ | |__+1__ | +|[tidytreatment](problems.md#tidytreatment)|0.2.2 |__+1__ | |1 __+1__ | +|[timetk](problems.md#timetk)|2.9.0 |__+1__ | |1 | +|[tinyarray](problems.md#tinyarray)|2.4.1 |__+1__ | |1 | +|[tmap](problems.md#tmap)|3.3-4 |__+1__ | | | +|[TOmicsVis](problems.md#tomicsvis)|2.0.0 |__+2__ | |1 __+1__ | +|[tornado](problems.md#tornado)|0.1.3 |__+3__ | |__+1__ | +|[TOSTER](problems.md#toster)|0.8.3 |__+3__ | |__+1__ | +|[toxEval](problems.md#toxeval)|1.3.2 |__+1__ | |1 | +|[TreatmentPatterns](problems.md#treatmentpatterns)|2.6.7 |__+1__ | | | +|[TreatmentSelection](problems.md#treatmentselection)|2.1.1 |__+1__ | | | +|[TreeDep](problems.md#treedep)|0.1.3 |__+1__ | | | +|[TreeDist](problems.md#treedist)|2.7.0 |__+1__ | |1 __+1__ | +|[treeheatr](problems.md#treeheatr)|0.2.1 |__+2__ | |__+1__ | +|[trelliscopejs](problems.md#trelliscopejs)|0.2.6 |__+2__ | | | +|[tricolore](problems.md#tricolore)|1.2.4 |__+2__ | |1 __+1__ | +|[tsnet](problems.md#tsnet)|0.1.0 |__+1__ | |2 | +|[umiAnalyzer](problems.md#umianalyzer)|1.0.0 |__+1__ | | | +|[UnalR](problems.md#unalr)|1.0.0 |__+1__ | |2 | +|[UpSetR](problems.md#upsetr)|1.4.0 |__+2__ | |2 | +|[vDiveR](problems.md#vdiver)|1.2.1 |__+1__ | |1 | +|[VDSM](problems.md#vdsm)|0.1.1 |__+2__ | | | +|[virtualPollen](problems.md#virtualpollen)|1.0.1 |__+2__ | |__+1__ | +|[viscomp](problems.md#viscomp)|1.0.0 |__+1__ | | | +|[visR](problems.md#visr)|0.4.1 |__+3__ | |__+1__ | +|[vivainsights](problems.md#vivainsights)|0.5.2 |__+1__ | | | +|[vivaldi](problems.md#vivaldi)|1.0.1 |__+3__ | |1 __+1__ | +|[vvshiny](problems.md#vvshiny)|0.1.1 |__+1__ | | | +|[WASP](problems.md#wasp)|1.4.3 |__+1__ | |1 | +|[Wats](problems.md#wats)|1.0.1 |__+1__ | |__+1__ | +|[whomds](problems.md#whomds)|1.1.1 |__+1__ |1 | | +|[wilson](problems.md#wilson)|2.4.2 |__+1__ | | | +|[WVPlots](problems.md#wvplots)|1.3.8 |__+3__ | |__+1__ | +|[xaringanthemer](problems.md#xaringanthemer)|0.4.2 |1 __+1__ | | | +|[xpose](problems.md#xpose)|0.4.18 |__+3__ | |__+1__ | diff --git a/revdep/cran.md b/revdep/cran.md index fce1e499de..a1302e8947 100644 --- a/revdep/cran.md +++ b/revdep/cran.md @@ -1,19 +1,31 @@ ## revdepcheck results -We checked 5027 reverse dependencies, comparing R CMD check results across CRAN and dev versions of this package. +We checked 5085 reverse dependencies, comparing R CMD check results across CRAN and dev versions of this package. - * We saw 204 new problems - * We failed to check 135 packages + * We saw 366 new problems + * We failed to check 191 packages Issues with CRAN packages are summarised below. ### New problems (This reports the first line of each new failure) +* accSDA + checking examples ... ERROR + +* activAnalyzer + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE + * actxps checking running R code from vignettes ... ERROR checking re-building of vignette outputs ... NOTE +* add2ggplot + checking examples ... ERROR + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE + * AeRobiology checking re-building of vignette outputs ... NOTE @@ -21,11 +33,11 @@ Issues with CRAN packages are summarised below. checking running R code from vignettes ... ERROR checking re-building of vignette outputs ... NOTE -* agricolaeplotr +* AgroR checking examples ... ERROR -* ammistability - checking re-building of vignette outputs ... ERROR +* allMT + checking examples ... ERROR * AnalysisLin checking examples ... ERROR @@ -33,39 +45,99 @@ Issues with CRAN packages are summarised below. * animbook checking examples ... ERROR -* aopdata +* aplot + checking examples ... ERROR + +* ASRgenomics + checking examples ... ERROR + checking tests ... ERROR + +* auditor + checking examples ... ERROR checking running R code from vignettes ... ERROR checking re-building of vignette outputs ... NOTE -* ARPALData +* augmentedRCBD checking examples ... ERROR - -* asmbPLS - checking whether package ‘asmbPLS’ can be installed ... WARNING + checking re-building of vignette outputs ... ERROR * autoplotly checking examples ... ERROR checking tests ... ERROR +* baggr + checking examples ... ERROR + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE + +* bayefdr + checking examples ... ERROR + checking tests ... ERROR + * BayesGrowth checking running R code from vignettes ... ERROR checking re-building of vignette outputs ... NOTE -* bdl - checking whether package ‘bdl’ can be installed ... WARNING +* BayesianReasoning + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE -* BeeBDC +* bayestestR checking examples ... ERROR + +* bdots + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE + +* bdrc + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE + +* BeeBDC checking tests ... ERROR -* blockCV +* besthr + checking examples ... ERROR + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE + +* BetaPASS + checking examples ... ERROR + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE + +* biblioverlap + checking examples ... ERROR + +* biscale + checking examples ... ERROR + +* BlandAltmanLeh + checking running R code from vignettes ... ERROR + +* bnma + checking running R code from vignettes ... ERROR checking re-building of vignette outputs ... NOTE * boxly checking tests ... ERROR -* bSi - checking whether package ‘bSi’ can be installed ... WARNING +* braidReports + checking examples ... ERROR + +* brolgar + checking examples ... ERROR + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE + +* calendR + checking examples ... ERROR + +* calendRio + checking examples ... ERROR + +* capm + checking examples ... ERROR * cartograflow checking examples ... ERROR @@ -76,11 +148,26 @@ Issues with CRAN packages are summarised below. * cheem checking tests ... ERROR +* chillR + checking examples ... ERROR + * chronicle checking examples ... ERROR checking running R code from vignettes ... ERROR checking re-building of vignette outputs ... NOTE +* circumplex + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE + +* cities + checking examples ... ERROR + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE + +* CleaningValidation + checking examples ... ERROR + * clinDataReview checking examples ... ERROR checking tests ... ERROR @@ -90,22 +177,29 @@ Issues with CRAN packages are summarised below. checking running R code from vignettes ... ERROR checking re-building of vignette outputs ... NOTE -* ClusROC - checking whether package ‘ClusROC’ can be installed ... WARNING - -* clustEff - checking whether package ‘clustEff’ can be installed ... WARNING +* ClustImpute + checking running R code from vignettes ... ERROR -* coda4microbiome - checking whether package ‘coda4microbiome’ can be installed ... WARNING +* cogmapr + checking examples ... ERROR * CohortPlat checking examples ... ERROR checking running R code from vignettes ... ERROR checking re-building of vignette outputs ... NOTE -* CompAREdesign - checking whether package ‘CompAREdesign’ can be installed ... WARNING +* CoMiRe + checking examples ... ERROR + +* CommKern + checking examples ... ERROR + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE + +* conText + checking examples ... ERROR + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE * CoreMicrobiomeR checking examples ... ERROR @@ -123,14 +217,16 @@ Issues with CRAN packages are summarised below. checking running R code from vignettes ... ERROR checking re-building of vignette outputs ... NOTE -* Coxmos - checking Rd files ... WARNING +* cricketdata + checking re-building of vignette outputs ... NOTE * crosshap checking examples ... ERROR -* csa - checking whether package ‘csa’ can be installed ... WARNING +* crplyr + checking tests ... ERROR + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE * ctrialsgov checking tests ... ERROR @@ -139,25 +235,37 @@ Issues with CRAN packages are summarised below. checking running R code from vignettes ... ERROR checking re-building of vignette outputs ... NOTE -* dafishr +* dabestr checking examples ... ERROR - -* damAOI + checking tests ... ERROR checking running R code from vignettes ... ERROR checking re-building of vignette outputs ... NOTE -* deeptime +* DAISIEprep + checking tests ... ERROR + +* dataresqc + checking examples ... ERROR + +* ddtlcm checking examples ... ERROR checking tests ... ERROR + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE -* DEGRE - checking whether package ‘DEGRE’ can be installed ... WARNING +* dfoliatR + checking examples ... ERROR + checking tests ... ERROR + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE -* densityarea +* directlabels + checking running R code from vignettes ... ERROR checking re-building of vignette outputs ... NOTE -* did - checking whether package ‘did’ can be installed ... WARNING +* disprofas + checking examples ... ERROR + checking tests ... ERROR * distributional checking examples ... ERROR @@ -166,37 +274,74 @@ Issues with CRAN packages are summarised below. checking examples ... ERROR checking tests ... ERROR -* dots - checking examples ... ERROR +* dobin checking running R code from vignettes ... ERROR checking re-building of vignette outputs ... NOTE -* eks +* dogesr + checking re-building of vignette outputs ... NOTE + +* dotsViolin + checking examples ... ERROR + +* ds4psy + checking examples ... ERROR + +* edecob + checking examples ... ERROR + +* entropart checking examples ... ERROR checking running R code from vignettes ... ERROR checking re-building of vignette outputs ... NOTE -* entropart +* envalysis checking examples ... ERROR + checking tests ... ERROR checking running R code from vignettes ... ERROR checking re-building of vignette outputs ... NOTE * epiCleanr checking examples ... ERROR -* epiR +* EpiInvert + checking examples ... ERROR + +* esci + checking examples ... ERROR + checking tests ... ERROR + +* EvidenceSynthesis + checking examples ... ERROR + checking tests ... ERROR checking running R code from vignettes ... ERROR checking re-building of vignette outputs ... NOTE -* esci +* EvolutionaryGames + checking examples ... ERROR + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE + +* EvoPhylo + checking examples ... ERROR + checking re-building of vignette outputs ... NOTE + +* evprof checking examples ... ERROR checking tests ... ERROR -* evalITR +* expirest + checking tests ... ERROR + +* explore + checking examples ... ERROR + checking running R code from vignettes ... ERROR checking re-building of vignette outputs ... NOTE -* explainer +* ezplot checking examples ... ERROR + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE * fable.prophet checking running R code from vignettes ... ERROR @@ -206,47 +351,87 @@ Issues with CRAN packages are summarised below. checking examples ... ERROR checking tests ... ERROR +* factoextra + checking examples ... ERROR + +* faux + checking examples ... ERROR + checking re-building of vignette outputs ... NOTE + +* fddm + checking running R code from vignettes ... ERROR + +* fdrci + checking examples ... ERROR + * ffp checking examples ... ERROR * fido checking examples ... ERROR + checking tests ... ERROR + +* figuRes2 + checking examples ... ERROR + checking running R code from vignettes ... ERROR * flipr checking re-building of vignette outputs ... NOTE -* fmesher - checking examples ... ERROR - -* forestecology - checking examples ... ERROR +* FMM checking running R code from vignettes ... ERROR checking re-building of vignette outputs ... NOTE +* fmriqa + checking tests ... ERROR + +* foreSIGHT + checking examples ... ERROR + checking re-building of vignette outputs ... ERROR + * frailtyEM checking examples ... ERROR -* FuncNN - checking whether package ‘FuncNN’ can be installed ... WARNING +* funcharts + checking examples ... ERROR + +* gapmap + checking examples ... ERROR + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE -* geomander +* gasper checking examples ... ERROR checking running R code from vignettes ... ERROR + +* gaussplotR + checking running R code from vignettes ... ERROR checking re-building of vignette outputs ... NOTE -* geomtextpath +* gg.gap checking examples ... ERROR + +* ggalignment checking tests ... ERROR + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE -* germinationmetrics - checking re-building of vignette outputs ... ERROR +* ggalt + checking re-building of vignette outputs ... NOTE * gganimate checking tests ... ERROR checking running R code from vignettes ... ERROR checking re-building of vignette outputs ... NOTE -* ggautomap +* ggbrace + checking examples ... ERROR + +* ggbrain + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE + +* ggbreak checking examples ... ERROR checking running R code from vignettes ... ERROR checking re-building of vignette outputs ... NOTE @@ -263,23 +448,45 @@ Issues with CRAN packages are summarised below. * ggedit checking examples ... ERROR +* ggExtra + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE + * ggfixest checking tests ... ERROR +* ggflowchart + checking examples ... ERROR + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE + +* ggforce + checking examples ... ERROR + * ggfortify checking tests ... ERROR +* ggfoundry + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE + +* gggap + checking examples ... ERROR + * ggh4x checking examples ... ERROR checking tests ... ERROR checking re-building of vignette outputs ... NOTE -* ggheatmap - checking whether package ‘ggheatmap’ can be installed ... WARNING +* gghdx + checking examples ... ERROR + checking re-building of vignette outputs ... NOTE * gghighlight checking examples ... ERROR checking tests ... ERROR + +* ggHoriPlot checking running R code from vignettes ... ERROR checking re-building of vignette outputs ... NOTE @@ -287,6 +494,14 @@ Issues with CRAN packages are summarised below. checking examples ... ERROR checking tests ... ERROR +* ggiraphExtra + checking examples ... ERROR + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE + +* ggmap + checking examples ... ERROR + * ggmice checking running R code from vignettes ... ERROR checking re-building of vignette outputs ... NOTE @@ -300,12 +515,27 @@ Issues with CRAN packages are summarised below. * ggparallel checking tests ... ERROR +* ggpicrust2 + checking examples ... ERROR + +* ggpie + checking examples ... ERROR + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE + * ggplotlyExtra checking examples ... ERROR * ggpol checking examples ... ERROR +* ggprism + checking examples ... ERROR + +* ggpubr + checking examples ... ERROR + checking tests ... ERROR + * ggraph checking examples ... ERROR checking re-building of vignette outputs ... NOTE @@ -318,9 +548,6 @@ Issues with CRAN packages are summarised below. checking running R code from vignettes ... ERROR checking re-building of vignette outputs ... NOTE -* ggScatRidges - checking whether package ‘ggScatRidges’ can be installed ... WARNING - * ggseqplot checking examples ... ERROR checking tests ... ERROR @@ -328,30 +555,51 @@ Issues with CRAN packages are summarised below. checking re-building of vignette outputs ... NOTE * ggside + checking tests ... ERROR checking for code/documentation mismatches ... WARNING +* ggstatsplot + checking tests ... ERROR + * ggtern checking examples ... ERROR +* ggthemes + checking examples ... ERROR + +* ggupset + checking examples ... ERROR + * ggVennDiagram checking running R code from vignettes ... ERROR checking re-building of vignette outputs ... NOTE -* GIFT - checking re-building of vignette outputs ... NOTE +* graphPAF + checking examples ... ERROR -* GimmeMyPlot - checking whether package ‘GimmeMyPlot’ can be installed ... WARNING +* greatR + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE -* gprofiler2 +* Greymodels checking examples ... ERROR + +* groupdata2 checking running R code from vignettes ... ERROR checking re-building of vignette outputs ... NOTE -* Greymodels +* GSD checking examples ... ERROR -* h3jsr +* gtExtras + checking tests ... ERROR + +* HaploCatcher + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE + +* hdnom + checking examples ... ERROR checking running R code from vignettes ... ERROR checking re-building of vignette outputs ... NOTE @@ -370,86 +618,246 @@ Issues with CRAN packages are summarised below. checking re-building of vignette outputs ... NOTE * heatmaply + checking examples ... ERROR checking tests ... ERROR checking running R code from vignettes ... ERROR checking re-building of vignette outputs ... NOTE -* hilldiv - checking whether package ‘hilldiv’ can be installed ... WARNING - -* hJAM - checking whether package ‘hJAM’ can be installed ... WARNING - -* HVT - checking examples ... ERROR - -* HYPEtools +* hermiter checking running R code from vignettes ... ERROR checking re-building of vignette outputs ... NOTE -* ImFoR - checking whether package ‘ImFoR’ can be installed ... WARNING +* heumilkr + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE -* iNEXT.4steps - checking whether package ‘iNEXT.4steps’ can be installed ... WARNING +* heuristicsmineR + checking installed package size ... NOTE -* insane - checking whether package ‘insane’ can be installed ... WARNING +* HistDAWass + checking examples ... ERROR -* inTextSummaryTable - checking tests ... ERROR +* huito + checking examples ... ERROR checking re-building of vignette outputs ... NOTE -* itsdm +* hurricaneexposure checking examples ... ERROR + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE -* karel +* HVT checking examples ... ERROR - checking tests ... ERROR -* latentcor +* hydraulics checking examples ... ERROR + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE -* mapSpain +* hyperSpec checking examples ... ERROR -* MBNMAdose +* hypsoLoop + checking whether package ‘hypsoLoop’ can be installed ... WARNING + +* ICvectorfields checking running R code from vignettes ... ERROR checking re-building of vignette outputs ... NOTE -* MBNMAtime +* idiogramFISH + checking installed package size ... NOTE + +* idopNetwork + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE + +* iglu + checking examples ... ERROR + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE + +* igoR + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE + +* immunarch + checking examples ... ERROR + +* immuneSIM + checking examples ... ERROR + +* iNEXT.4steps + checking examples ... ERROR + checking tests ... ERROR + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE + +* iNEXT.beta3D + checking examples ... ERROR + +* insurancerating + checking examples ... ERROR + +* inTextSummaryTable + checking tests ... ERROR + checking re-building of vignette outputs ... NOTE + +* jskm + checking examples ... ERROR + checking tests ... ERROR + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE + +* KaradaColor + checking examples ... ERROR + +* karel + checking examples ... ERROR + checking tests ... ERROR + +* kDGLM + checking examples ... ERROR + +* labsimplex + checking examples ... ERROR + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE + +* landscapemetrics + checking examples ... ERROR + +* landscapetools + checking examples ... ERROR + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE + +* latentcor + checking examples ... ERROR + +* latte + checking examples ... ERROR + +* lemon + checking examples ... ERROR + checking tests ... ERROR + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE + +* lfproQC + checking examples ... ERROR + checking running R code from vignettes ... ERROR checking re-building of vignette outputs ... NOTE -* mc2d - checking whether package ‘mc2d’ can be installed ... WARNING +* LLSR + checking examples ... ERROR + +* LMoFit + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE -* MetaIntegrator - checking whether package ‘MetaIntegrator’ can be installed ... WARNING +* lomb + checking examples ... ERROR -* MF.beta4 - checking whether package ‘MF.beta4’ can be installed ... WARNING +* LongDat + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE + +* longitudinalcascade + checking examples ... ERROR + +* longmixr + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE + +* manhplot + checking tests ... ERROR + +* mau + checking examples ... ERROR + +* MBNMAdose + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE + +* MBNMAtime + checking re-building of vignette outputs ... NOTE + +* metaforest + checking tests ... ERROR + +* metan + checking examples ... ERROR + +* metaplot + checking examples ... ERROR + +* metR + checking examples ... ERROR + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE + +* miceFast + checking examples ... ERROR + checking tests ... ERROR + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE + +* MicrobiomeStat + checking examples ... ERROR + +* micromap + checking examples ... ERROR + checking running R code from vignettes ... ERROR * MiMIR checking examples ... ERROR +* MIMSunit + checking examples ... ERROR + * miRetrieve checking tests ... ERROR -* missingHE - checking whether package ‘missingHE’ can be installed ... WARNING - * misspi checking examples ... ERROR +* mizer + checking tests ... ERROR + * mlr3spatiotempcv checking examples ... ERROR - checking tests ... ERROR + +* mlr3viz + checking examples ... ERROR * modeltime.resample checking tests ... ERROR -* MSPRT - checking whether package ‘MSPRT’ can be installed ... WARNING +* mosaic + checking examples ... ERROR + checking tests ... ERROR + +* motifr + checking examples ... ERROR + +* mpwR + checking examples ... ERROR + checking tests ... ERROR + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE + +* mrfDepth + checking examples ... ERROR + +* musclesyneRgies + checking examples ... ERROR + checking tests ... ERROR + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE + +* naniar + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE * neatmaps checking examples ... ERROR @@ -457,6 +865,15 @@ Issues with CRAN packages are summarised below. * NetFACS checking examples ... ERROR checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE + +* NHSRplotthedots + checking examples ... ERROR + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE + +* nima + checking examples ... ERROR * NIMAA checking examples ... ERROR @@ -464,18 +881,69 @@ Issues with CRAN packages are summarised below. checking running R code from vignettes ... ERROR checking re-building of vignette outputs ... NOTE -* nswgeo +* nparACT checking examples ... ERROR -* OenoKPM - checking whether package ‘OenoKPM’ can be installed ... WARNING +* nullabor + checking running R code from vignettes ... ERROR + +* OBIC + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE + +* OddsPlotty + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE + +* ofpetrial + checking examples ... ERROR * OmicNavigator checking tests ... ERROR + checking running R code from vignettes ... ERROR + +* oncomsm + checking tests ... ERROR + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE + +* ontophylo + checking examples ... ERROR + +* OpenLand + checking tests ... ERROR + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE + +* ordbetareg + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE * otsad checking examples ... ERROR +* OutliersO3 + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE + +* palettes + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE + +* ParBayesianOptimization + checking examples ... ERROR + +* patchwork + checking examples ... ERROR + +* pathfindR + checking examples ... ERROR + checking re-building of vignette outputs ... NOTE + +* pdSpecEst + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE + * pdxTrees checking running R code from vignettes ... ERROR checking re-building of vignette outputs ... NOTE @@ -486,10 +954,6 @@ Issues with CRAN packages are summarised below. * PGRdup checking re-building of vignette outputs ... ERROR -* plantTracker - checking running R code from vignettes ... ERROR - checking re-building of vignette outputs ... NOTE - * Plasmidprofiler checking examples ... ERROR @@ -506,8 +970,10 @@ Issues with CRAN packages are summarised below. * pmxTools checking tests ... ERROR -* PointedSDMs +* politeness checking examples ... ERROR + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE * posterior checking re-building of vignette outputs ... NOTE @@ -519,131 +985,268 @@ Issues with CRAN packages are summarised below. checking running R code from vignettes ... ERROR checking re-building of vignette outputs ... NOTE +* PPtreeregViz + checking examples ... ERROR + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE + +* precrec + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE + +* prevR + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE + +* primerTree + checking examples ... ERROR + * processmapR checking tests ... ERROR -* QuadratiK - checking whether package ‘QuadratiK’ can be installed ... WARNING +* PTXQC + checking tests ... ERROR -* Radviz +* qacBase + checking examples ... ERROR + +* qgcomp + checking examples ... ERROR + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE + +* qgcompint checking examples ... ERROR checking running R code from vignettes ... ERROR checking re-building of vignette outputs ... NOTE -* rangeMapper +* qpNCA checking running R code from vignettes ... ERROR checking re-building of vignette outputs ... NOTE +* QurvE + checking examples ... ERROR + +* r2dii.plot + checking examples ... ERROR + checking tests ... ERROR + +* Radviz + checking examples ... ERROR + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE + +* rainette + checking tests ... ERROR + * rassta checking examples ... ERROR checking tests ... ERROR checking running R code from vignettes ... ERROR -* RCTrep - checking whether package ‘RCTrep’ can be installed ... WARNING +* RAT + checking examples ... ERROR + +* Rcan + checking examples ... ERROR -* redistmetrics +* redist checking running R code from vignettes ... ERROR checking re-building of vignette outputs ... NOTE -* ref.ICAR +* Relectoral + checking examples ... ERROR + +* reliabilitydiag + checking examples ... ERROR + +* relliptical + checking examples ... ERROR + +* Repliscope + checking examples ... ERROR + +* reportRmd + checking examples ... ERROR checking running R code from vignettes ... ERROR checking re-building of vignette outputs ... NOTE -* remap +* reReg + checking examples ... ERROR + +* reservr + checking examples ... ERROR checking running R code from vignettes ... ERROR checking re-building of vignette outputs ... NOTE -* rKIN +* restriktor checking examples ... ERROR -* rLFT +* RevGadgets + checking tests ... ERROR + +* rimu + checking examples ... ERROR + checking re-building of vignette outputs ... NOTE + +* rKOMICS + checking examples ... ERROR + +* rmcorr + checking re-building of vignette outputs ... NOTE + +* RNAseqQC checking running R code from vignettes ... ERROR checking re-building of vignette outputs ... NOTE * roahd checking examples ... ERROR +* robustbase + checking running R code from vignettes ... ERROR + +* romic + checking tests ... ERROR + * roptions checking examples ... ERROR -* scoringutils +* rotations checking examples ... ERROR + checking running R code from vignettes ... ERROR + +* rreg + checking examples ... ERROR + +* rSDI + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE + +* SangerTools + checking examples ... ERROR + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE + +* santaR checking re-building of vignette outputs ... NOTE -* SCOUTer - checking whether package ‘SCOUTer’ can be installed ... WARNING +* scoringutils + checking examples ... ERROR + checking re-building of vignette outputs ... NOTE * SCVA checking examples ... ERROR +* SDLfilter + checking examples ... ERROR + * see checking examples ... ERROR -* sfnetworks - checking re-building of vignette outputs ... NOTE +* sentimentr + checking examples ... ERROR + +* sentometrics + checking examples ... ERROR + +* sglg + checking examples ... ERROR -* sftrack +* SHAPforxgboost + checking examples ... ERROR + +* shazam checking examples ... ERROR checking running R code from vignettes ... ERROR checking re-building of vignette outputs ... NOTE -* sglg +* simulariatools checking examples ... ERROR -* sievePH - checking whether package ‘sievePH’ can be installed ... WARNING +* sjPlot + checking examples ... ERROR + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE -* SouthParkRshiny - checking whether package ‘SouthParkRshiny’ can be installed ... WARNING +* SleepCycles + checking examples ... ERROR -* spatialrisk +* smallsets checking examples ... ERROR + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE + +* smdi + checking re-building of vignette outputs ... NOTE -* spatialsample +* soc.ca checking examples ... ERROR - checking tests ... ERROR + +* spbal checking running R code from vignettes ... ERROR checking re-building of vignette outputs ... NOTE +* speccurvieR + checking examples ... ERROR + * spinifex checking tests ... ERROR -* spmodel +* spotoroo + checking tests ... ERROR checking running R code from vignettes ... ERROR checking re-building of vignette outputs ... NOTE * SqueakR - checking whether package ‘SqueakR’ can be installed ... WARNING checking re-building of vignette outputs ... NOTE -* stats19 +* stabm + checking examples ... ERROR + checking tests ... ERROR + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE + +* starvz + checking examples ... ERROR + +* statgenMPP + checking tests ... ERROR + checking running R code from vignettes ... ERROR checking re-building of vignette outputs ... NOTE -* streamDepletr +* statVisual + checking examples ... ERROR checking running R code from vignettes ... ERROR checking re-building of vignette outputs ... NOTE -* survminer - checking whether package ‘survminer’ can be installed ... WARNING +* superheat + checking examples ... ERROR + checking tests ... ERROR + +* surveyexplorer + checking examples ... ERROR + +* survivalAnalysis + checking examples ... ERROR + checking re-building of vignette outputs ... NOTE -* symptomcheckR - checking whether package ‘symptomcheckR’ can be installed ... WARNING +* Sysrecon + checking examples ... ERROR * tabledown checking examples ... ERROR -* tcgaViz - checking whether package ‘tcgaViz’ can be installed ... WARNING +* tabr + checking examples ... ERROR + +* TcGSA + checking running R code from vignettes ... ERROR * TCIU checking examples ... ERROR checking running R code from vignettes ... ERROR checking re-building of vignette outputs ... NOTE -* TestGardener - checking whether package ‘TestGardener’ can be installed ... WARNING - * thematic checking examples ... ERROR checking tests ... ERROR @@ -656,14 +1259,6 @@ Issues with CRAN packages are summarised below. checking tests ... ERROR * tidysdm - checking examples ... ERROR - checking running R code from vignettes ... ERROR - checking re-building of vignette outputs ... NOTE - -* tidyterra - checking examples ... ERROR - -* tidytransit checking running R code from vignettes ... ERROR checking re-building of vignette outputs ... NOTE @@ -671,14 +1266,24 @@ Issues with CRAN packages are summarised below. checking running R code from vignettes ... ERROR checking re-building of vignette outputs ... NOTE -* tilemaps +* timetk + checking tests ... ERROR + +* tinyarray + checking examples ... ERROR + +* tmap + checking examples ... ERROR + +* TOmicsVis + checking examples ... ERROR checking running R code from vignettes ... ERROR checking re-building of vignette outputs ... NOTE -* timetk +* tornado + checking examples ... ERROR checking tests ... ERROR - -* tongfen + checking running R code from vignettes ... ERROR checking re-building of vignette outputs ... NOTE * TOSTER @@ -687,32 +1292,72 @@ Issues with CRAN packages are summarised below. checking running R code from vignettes ... ERROR checking re-building of vignette outputs ... NOTE +* toxEval + checking examples ... ERROR + * TreatmentPatterns checking tests ... ERROR +* TreatmentSelection + checking examples ... ERROR + +* TreeDep + checking examples ... ERROR + +* TreeDist + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE + +* treeheatr + checking examples ... ERROR + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE + * trelliscopejs + checking examples ... ERROR checking tests ... ERROR +* tricolore + checking examples ... ERROR + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE + * tsnet checking tests ... ERROR * umiAnalyzer checking examples ... ERROR -* UniprotR - checking whether package ‘UniprotR’ can be installed ... WARNING +* UnalR + checking examples ... ERROR -* VALERIE - checking whether package ‘VALERIE’ can be installed ... WARNING +* UpSetR + checking examples ... ERROR + checking running R code from vignettes ... ERROR + +* vDiveR + checking examples ... ERROR + +* VDSM + checking examples ... ERROR + checking tests ... ERROR -* VancouvR +* virtualPollen + checking examples ... ERROR checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE -* vannstats - checking whether package ‘vannstats’ can be installed ... WARNING +* viscomp + checking examples ... ERROR + +* visR + checking examples ... ERROR + checking tests ... ERROR + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE -* vici - checking whether package ‘vici’ can be installed ... WARNING +* vivainsights + checking examples ... ERROR * vivaldi checking examples ... ERROR @@ -721,161 +1366,226 @@ Issues with CRAN packages are summarised below. checking re-building of vignette outputs ... NOTE * vvshiny - checking examples ... ERROR checking tests ... ERROR -* waywiser - checking running R code from vignettes ... ERROR - checking re-building of vignette outputs ... NOTE +* WASP + checking examples ... ERROR -* wildlifeDI +* Wats checking running R code from vignettes ... ERROR checking re-building of vignette outputs ... NOTE +* whomds + checking examples ... ERROR + * wilson checking tests ... ERROR -* WorldMapR +* WVPlots checking examples ... ERROR checking tests ... ERROR + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE * xaringanthemer checking tests ... ERROR +* xpose + checking examples ... ERROR + checking tests ... ERROR + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE + ### Failed to check -* abctools (NA) -* animalEKF (NA) -* ANOM (NA) -* atRisk (NA) -* AutoScore (NA) -* bayesdfa (NA) -* bayesDP (NA) -* BayesianFactorZoo (NA) -* BayesSurvive (NA) -* BCClong (NA) -* binsreg (NA) -* bmgarch (NA) -* bmstdr (NA) -* bspcov (NA) -* BuyseTest (NA) -* CalibrationCurves (NA) -* CARBayesST (NA) -* CaseBasedReasoning (NA) -* CGPfunctions (NA) -* cmprskcoxmsm (NA) -* contrast (NA) -* coxed (NA) -* CRMetrics (NA) -* csmpv (NA) -* ctsem (NA) -* DepthProc (NA) -* DR.SC (NA) -* EcoEnsemble (NA) -* ecolottery (NA) -* EpiEstim (NA) -* evolqg (NA) -* ForecastComb (NA) -* gapfill (NA) -* GeomComb (NA) -* geostan (NA) -* ggpmisc (NA) -* ggrcs (NA) -* ggrisk (NA) -* gJLS2 (NA) -* Greg (NA) -* greport (NA) -* hettx (NA) -* hIRT (NA) -* Hmsc (NA) -* inventorize (NA) -* iNZightPlots (NA) -* iNZightRegression (NA) -* IRexamples (NA) -* joineRML (NA) -* JWileymisc (NA) -* kmc (NA) -* L2E (NA) -* llbayesireg (NA) -* LorenzRegression (NA) -* lsirm12pl (NA) -* mbsts (NA) -* MendelianRandomization (NA) -* MetabolicSurv (NA) -* miWQS (NA) -* mlmts (NA) -* MRZero (NA) -* Multiaovbay (NA) -* multilevelTools (NA) -* multinma (NA) -* NCA (NA) -* netcmc (NA) -* NetworkChange (NA) -* nlmeVPC (NA) -* NMADiagT (NA) -* optweight (NA) -* OVtool (NA) -* paths (NA) -* PLMIX (NA) -* popstudy (NA) -* pould (NA) -* powerly (NA) -* pre (NA) -* ProFAST (NA) -* psbcSpeedUp (NA) -* pscore (NA) -* psfmi (NA) -* qPCRtools (NA) -* qreport (NA) -* qris (NA) -* qte (NA) -* quid (NA) -* RATest (NA) -* RcmdrPlugin.RiskDemo (NA) -* rddtools (NA) -* riskRegression (NA) -* rms (NA) -* rmsb (NA) -* robmed (NA) -* robmedExtra (NA) -* RPPanalyzer (NA) -* RQdeltaCT (NA) -* rstanarm (NA) -* scCustomize (NA) -* SCdeconR (NA) -* scGate (NA) -* scMappR (NA) -* scRNAstat (NA) -* sectorgap (NA) -* SEERaBomb (NA) -* semicmprskcoxmsm (NA) -* SensMap (NA) -* Seurat (NA) -* shinyTempSignal (NA) -* Signac (NA) -* SimplyAgree (NA) -* sMSROC (NA) -* SNPassoc (NA) -* snplinkage (NA) -* SoupX (NA) -* sparsereg (NA) -* spikeSlabGAM (NA) -* statsr (NA) -* streamDAG (NA) -* survHE (NA) -* survidm (NA) -* tempted (NA) -* tidydr (NA) -* tidyEdSurvey (NA) -* tidyseurat (NA) -* tidyvpc (NA) -* treestats (NA) -* TriDimRegression (NA) -* triptych (NA) -* TSrepr (NA) -* twang (NA) -* ubms (NA) -* valse (NA) -* vdg (NA) -* visa (NA) -* WRTDStidal (NA) +* abctools (NA) +* adjustedCurves (NA) +* AnanseSeurat (NA) +* animalEKF (NA) +* ANOM (NA) +* aorsf (NA) +* APackOfTheClones (NA) +* autoReg (NA) +* AutoScore (NA) +* bayesdfa (NA) +* bayesDP (NA) +* BayesianFactorZoo (NA) +* BayesSurvive (NA) +* bbmle (NA) +* BCClong (NA) +* bmstdr (NA) +* bspcov (NA) +* BuyseTest (NA) +* calibmsm (NA) +* CalibrationCurves (NA) +* Canek (NA) +* CARBayesST (NA) +* CaseBasedReasoning (NA) +* cellpypes (NA) +* CGPfunctions (NA) +* chem16S (NA) +* CIARA (NA) +* clarify (NA) +* ClustAssess (NA) +* clustree (NA) +* cmprskcoxmsm (NA) +* combiroc (NA) +* conos (NA) +* contrast (NA) +* contsurvplot (NA) +* countland (NA) +* coveffectsplot (NA) +* coxed (NA) +* CRMetrics (NA) +* crosslag (NA) +* csmpv (NA) +* ctsem (NA) +* CytoSimplex (NA) +* depigner (NA) +* DepthProc (NA) +* DIscBIO (NA) +* diversityForest (NA) +* DR.SC (NA) +* DynForest (NA) +* dyngen (NA) +* EcoEnsemble (NA) +* ecolottery (NA) +* EpiEstim (NA) +* evalITR (NA) +* evolqg (NA) +* explainer (NA) +* flexrsurv (NA) +* forestmangr (NA) +* gap (NA) +* GeomComb (NA) +* ggeffects (NA) +* ggquickeda (NA) +* ggrcs (NA) +* ggrisk (NA) +* ggsector (NA) +* grandR (NA) +* Greg (NA) +* greport (NA) +* harmony (NA) +* hIRT (NA) +* Hmisc (NA) +* Hmsc (NA) +* hydroroute (NA) +* inventorize (NA) +* iNZightRegression (NA) +* IRexamples (NA) +* jmBIG (NA) +* joineRML (NA) +* jsmodule (NA) +* JWileymisc (NA) +* kmc (NA) +* KMunicate (NA) +* L2E (NA) +* Landmarking (NA) +* lavaSearch2 (NA) +* llbayesireg (NA) +* LorenzRegression (NA) +* lsirm12pl (NA) +* MachineShop (NA) +* marginaleffects (NA) +* mbsts (NA) +* MetabolicSurv (NA) +* MetaNet (NA) +* miWQS (NA) +* mlmts (NA) +* mlr (NA) +* MOSS (NA) +* mrbayes (NA) +* mstate (NA) +* Multiaovbay (NA) +* multilevelTools (NA) +* multipleOutcomes (NA) +* netcmc (NA) +* NetworkChange (NA) +* neutralitytestr (NA) +* NMADiagT (NA) +* obliqueRSF (NA) +* optweight (NA) +* ormPlot (NA) +* OVtool (NA) +* pagoda2 (NA) +* pammtools (NA) +* pander (NA) +* parameters (NA) +* PAsso (NA) +* paths (NA) +* pctax (NA) +* pcutils (NA) +* PLMIX (NA) +* pmcalibration (NA) +* popstudy (NA) +* pould (NA) +* powerly (NA) +* pre (NA) +* PRECAST (NA) +* ProFAST (NA) +* psbcSpeedUp (NA) +* pscore (NA) +* psfmi (NA) +* pubh (NA) +* qPCRtools (NA) +* qreport (NA) +* quid (NA) +* RcmdrPlugin.RiskDemo (NA) +* rcssci (NA) +* rddtools (NA) +* relsurv (NA) +* riskRegression (NA) +* rliger (NA) +* rms (NA) +* rmsb (NA) +* robber (NA) +* robmedExtra (NA) +* rprev (NA) +* RQdeltaCT (NA) +* rstanarm (NA) +* rTwig (NA) +* scCustomize (NA) +* SCdeconR (NA) +* scDiffCom (NA) +* scGate (NA) +* scMappR (NA) +* SCORPIUS (NA) +* scpi (NA) +* scpoisson (NA) +* SCpubr (NA) +* scRNAstat (NA) +* sectorgap (NA) +* SEERaBomb (NA) +* semicmprskcoxmsm (NA) +* SensMap (NA) +* shinyTempSignal (NA) +* sievePH (NA) +* Signac (NA) +* simET (NA) +* simstudy (NA) +* sMSROC (NA) +* SNPassoc (NA) +* snplinkage (NA) +* SoupX (NA) +* sparsereg (NA) +* SPECK (NA) +* spikeSlabGAM (NA) +* statsr (NA) +* streamDAG (NA) +* sure (NA) +* Surrogate (NA) +* survex (NA) +* survHE (NA) +* survidm (NA) +* SurvMetrics (NA) +* tempted (NA) +* tidydr (NA) +* tidyEdSurvey (NA) +* tidyseurat (NA) +* treefit (NA) +* TriDimRegression (NA) +* twang (NA) +* valse (NA) +* visa (NA) +* WpProj (NA) diff --git a/revdep/failures.md b/revdep/failures.md index 28d5c9fdd6..331d6eb296 100644 --- a/revdep/failures.md +++ b/revdep/failures.md @@ -29,7 +29,7 @@ Run `revdepcheck::cloud_details(, "abctools")` for more info ** package ‘abctools’ successfully unpacked and MD5 sums checked ** using staged installation ** libs -using C compiler: ‘gcc (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ +using C compiler: ‘gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ gcc -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I/usr/local/include -fpic -g -O2 -c abctools.c -o abctools.o gcc -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I/usr/local/include -fpic -g -O2 -c init.c -o init.o gcc -shared -L/opt/R/4.3.1/lib/R/lib -L/usr/local/lib -o abctools.so abctools.o init.o -llapack -lblas -lgfortran -lm -lquadmath -L/opt/R/4.3.1/lib/R/lib -lR @@ -38,8 +38,7 @@ installing to /tmp/workdir/abctools/new/abctools.Rcheck/00LOCK-abctools/00new/ab ** data ** inst ** byte-compile and prepare package for lazy loading -Error: package or namespace load failed for ‘quantreg’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Error: package ‘quantreg’ required by ‘abc’ could not be found Execution halted ERROR: lazy loading failed for package ‘abctools’ * removing ‘/tmp/workdir/abctools/new/abctools.Rcheck/abctools’ @@ -53,7 +52,7 @@ ERROR: lazy loading failed for package ‘abctools’ ** package ‘abctools’ successfully unpacked and MD5 sums checked ** using staged installation ** libs -using C compiler: ‘gcc (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ +using C compiler: ‘gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ gcc -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I/usr/local/include -fpic -g -O2 -c abctools.c -o abctools.o gcc -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I/usr/local/include -fpic -g -O2 -c init.c -o init.o gcc -shared -L/opt/R/4.3.1/lib/R/lib -L/usr/local/lib -o abctools.so abctools.o init.o -llapack -lblas -lgfortran -lm -lquadmath -L/opt/R/4.3.1/lib/R/lib -lR @@ -62,13 +61,164 @@ installing to /tmp/workdir/abctools/old/abctools.Rcheck/00LOCK-abctools/00new/ab ** data ** inst ** byte-compile and prepare package for lazy loading -Error: package or namespace load failed for ‘quantreg’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Error: package ‘quantreg’ required by ‘abc’ could not be found Execution halted ERROR: lazy loading failed for package ‘abctools’ * removing ‘/tmp/workdir/abctools/old/abctools.Rcheck/abctools’ +``` +# adjustedCurves + +
+ +* Version: 0.11.1 +* GitHub: https://github.com/RobinDenz1/adjustedCurves +* Source code: https://github.com/cran/adjustedCurves +* Date/Publication: 2024-04-10 18:30:02 UTC +* Number of recursive dependencies: 175 + +Run `revdepcheck::cloud_details(, "adjustedCurves")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/adjustedCurves/new/adjustedCurves.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘adjustedCurves/DESCRIPTION’ ... OK +... +--- finished re-building ‘plot_customization.rmd’ + +SUMMARY: processing the following file failed: + ‘introduction.Rmd’ + +Error: Vignette re-building failed. +Execution halted + +* DONE +Status: 2 ERRORs, 1 WARNING, 3 NOTEs + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/adjustedCurves/old/adjustedCurves.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘adjustedCurves/DESCRIPTION’ ... OK +... +--- finished re-building ‘plot_customization.rmd’ + +SUMMARY: processing the following file failed: + ‘introduction.Rmd’ + +Error: Vignette re-building failed. +Execution halted + +* DONE +Status: 2 ERRORs, 1 WARNING, 3 NOTEs + + + + + +``` +# AnanseSeurat + +
+ +* Version: 1.2.0 +* GitHub: https://github.com/JGASmits/AnanseSeurat +* Source code: https://github.com/cran/AnanseSeurat +* Date/Publication: 2023-11-11 21:43:17 UTC +* Number of recursive dependencies: 200 + +Run `revdepcheck::cloud_details(, "AnanseSeurat")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/AnanseSeurat/new/AnanseSeurat.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘AnanseSeurat/DESCRIPTION’ ... OK +... +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘Seurat’ + +Package suggested but not available for checking: ‘Signac’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/AnanseSeurat/old/AnanseSeurat.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘AnanseSeurat/DESCRIPTION’ ... OK +... +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘Seurat’ + +Package suggested but not available for checking: ‘Signac’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + ``` # animalEKF @@ -104,9 +254,9 @@ Run `revdepcheck::cloud_details(, "animalEKF")` for more info ** data ** inst ** byte-compile and prepare package for lazy loading -Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Error in loadNamespace(i, c(lib.loc, .libPaths()), versionCheck = vI[[i]]) : + there is no package called ‘quantreg’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart Execution halted ERROR: lazy loading failed for package ‘animalEKF’ * removing ‘/tmp/workdir/animalEKF/new/animalEKF.Rcheck/animalEKF’ @@ -123,9 +273,9 @@ ERROR: lazy loading failed for package ‘animalEKF’ ** data ** inst ** byte-compile and prepare package for lazy loading -Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Error in loadNamespace(i, c(lib.loc, .libPaths()), versionCheck = vI[[i]]) : + there is no package called ‘quantreg’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart Execution halted ERROR: lazy loading failed for package ‘animalEKF’ * removing ‘/tmp/workdir/animalEKF/old/animalEKF.Rcheck/animalEKF’ @@ -167,9 +317,9 @@ Run `revdepcheck::cloud_details(, "ANOM")` for more info *** 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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Error in loadNamespace(i, c(lib.loc, .libPaths()), versionCheck = vI[[i]]) : + there is no package called ‘quantreg’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart Execution halted ERROR: lazy loading failed for package ‘ANOM’ * removing ‘/tmp/workdir/ANOM/new/ANOM.Rcheck/ANOM’ @@ -187,164 +337,342 @@ ERROR: lazy loading failed for package ‘ANOM’ *** 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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Error in loadNamespace(i, c(lib.loc, .libPaths()), versionCheck = vI[[i]]) : + there is no package called ‘quantreg’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart Execution halted ERROR: lazy loading failed for package ‘ANOM’ * removing ‘/tmp/workdir/ANOM/old/ANOM.Rcheck/ANOM’ ``` -# atRisk +# aorsf
-* Version: 0.1.0 -* GitHub: NA -* Source code: https://github.com/cran/atRisk -* Date/Publication: 2023-08-08 14:50:05 UTC -* Number of recursive dependencies: 37 +* Version: 0.1.5 +* GitHub: https://github.com/ropensci/aorsf +* Source code: https://github.com/cran/aorsf +* Date/Publication: 2024-05-30 03:40:02 UTC +* Number of recursive dependencies: 181 -Run `revdepcheck::cloud_details(, "atRisk")` for more info +Run `revdepcheck::cloud_details(, "aorsf")` for more info
-## In both - -* checking whether package ‘atRisk’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/atRisk/new/atRisk.Rcheck/00install.out’ for details. - ``` - -## Installation +## Error before installation ### Devel ``` -* installing *source* package ‘atRisk’ ... -** package ‘atRisk’ successfully unpacked and MD5 sums checked -** using staged installation -** R -** data -*** moving datasets to lazyload DB -** byte-compile and prepare package for lazy loading -Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘atRisk’ -* removing ‘/tmp/workdir/atRisk/new/atRisk.Rcheck/atRisk’ +* using log directory ‘/tmp/workdir/aorsf/new/aorsf.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘aorsf/DESCRIPTION’ ... OK +... +* checking for unstated dependencies in vignettes ... OK +* checking package vignettes in ‘inst/doc’ ... OK +* checking running R code from vignettes ... OK + ‘aorsf.Rmd’ using ‘UTF-8’... OK + ‘fast.Rmd’ using ‘UTF-8’... OK + ‘oobag.Rmd’ using ‘UTF-8’... OK + ‘pd.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 1 NOTE + + + ``` ### CRAN ``` -* installing *source* package ‘atRisk’ ... -** package ‘atRisk’ successfully unpacked and MD5 sums checked -** using staged installation -** R -** data -*** moving datasets to lazyload DB -** byte-compile and prepare package for lazy loading -Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘atRisk’ -* removing ‘/tmp/workdir/atRisk/old/atRisk.Rcheck/atRisk’ +* using log directory ‘/tmp/workdir/aorsf/old/aorsf.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘aorsf/DESCRIPTION’ ... OK +... +* checking for unstated dependencies in vignettes ... OK +* checking package vignettes in ‘inst/doc’ ... OK +* checking running R code from vignettes ... OK + ‘aorsf.Rmd’ using ‘UTF-8’... OK + ‘fast.Rmd’ using ‘UTF-8’... OK + ‘oobag.Rmd’ using ‘UTF-8’... OK + ‘pd.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 1 NOTE + + + ``` -# AutoScore +# APackOfTheClones
-* Version: 1.0.0 -* GitHub: https://github.com/nliulab/AutoScore -* Source code: https://github.com/cran/AutoScore -* Date/Publication: 2022-10-15 22:15:26 UTC -* Number of recursive dependencies: 180 +* Version: 1.2.0 +* GitHub: https://github.com/Qile0317/APackOfTheClones +* Source code: https://github.com/cran/APackOfTheClones +* Date/Publication: 2024-04-16 09:50:02 UTC +* Number of recursive dependencies: 176 -Run `revdepcheck::cloud_details(, "AutoScore")` for more info +Run `revdepcheck::cloud_details(, "APackOfTheClones")` for more info
-## In both - -* checking whether package ‘AutoScore’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/AutoScore/new/AutoScore.Rcheck/00install.out’ for details. - ``` - -## Installation +## Error before installation ### Devel ``` -* installing *source* package ‘AutoScore’ ... -** package ‘AutoScore’ 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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘AutoScore’ -* removing ‘/tmp/workdir/AutoScore/new/AutoScore.Rcheck/AutoScore’ +* using log directory ‘/tmp/workdir/APackOfTheClones/new/APackOfTheClones.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘APackOfTheClones/DESCRIPTION’ ... OK +... +* this is package ‘APackOfTheClones’ version ‘1.2.0’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Packages required but not available: 'Seurat', 'SeuratObject' + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + ``` ### CRAN ``` -* installing *source* package ‘AutoScore’ ... -** package ‘AutoScore’ 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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘AutoScore’ -* removing ‘/tmp/workdir/AutoScore/old/AutoScore.Rcheck/AutoScore’ +* using log directory ‘/tmp/workdir/APackOfTheClones/old/APackOfTheClones.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘APackOfTheClones/DESCRIPTION’ ... OK +... +* this is package ‘APackOfTheClones’ version ‘1.2.0’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Packages required but not available: 'Seurat', 'SeuratObject' + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + ``` -# bayesdfa +# autoReg
-* Version: 1.3.3 -* GitHub: https://github.com/fate-ewi/bayesdfa -* Source code: https://github.com/cran/bayesdfa -* Date/Publication: 2024-02-26 20:50:06 UTC -* Number of recursive dependencies: 89 +* Version: 0.3.3 +* GitHub: https://github.com/cardiomoon/autoReg +* Source code: https://github.com/cran/autoReg +* Date/Publication: 2023-11-14 05:53:27 UTC +* Number of recursive dependencies: 232 -Run `revdepcheck::cloud_details(, "bayesdfa")` for more info +Run `revdepcheck::cloud_details(, "autoReg")` for more info
-## In both +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/autoReg/new/autoReg.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘autoReg/DESCRIPTION’ ... OK +... + +SUMMARY: processing the following files failed: + ‘Automatic_Regression_Modeling.Rmd’ ‘Getting_started.Rmd’ + ‘Survival.Rmd’ + +Error: Vignette re-building failed. +Execution halted + +* DONE +Status: 2 ERRORs, 1 NOTE + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/autoReg/old/autoReg.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘autoReg/DESCRIPTION’ ... OK +... +* checking package vignettes in ‘inst/doc’ ... OK +* checking running R code from vignettes ... OK + ‘Automatic_Regression_Modeling.Rmd’ using ‘UTF-8’... OK + ‘Bootstrap_Prediction.Rmd’ using ‘UTF-8’... OK + ‘Getting_started.Rmd’ using ‘UTF-8’... OK + ‘Statiastical_test_in_gaze.Rmd’ using ‘UTF-8’... OK + ‘Survival.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: OK + + + + + +``` +# AutoScore + +
+ +* Version: 1.0.0 +* GitHub: https://github.com/nliulab/AutoScore +* Source code: https://github.com/cran/AutoScore +* Date/Publication: 2022-10-15 22:15:26 UTC +* Number of recursive dependencies: 179 + +Run `revdepcheck::cloud_details(, "AutoScore")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/AutoScore/new/AutoScore.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘AutoScore/DESCRIPTION’ ... OK +... +* checking if there is a namespace ... OK +* checking for executable files ... OK +* checking for hidden files and directories ... OK +* checking for portable file names ... OK +* checking for sufficient/correct file permissions ... OK +* checking whether package ‘AutoScore’ can be installed ... ERROR +Installation failed. +See ‘/tmp/workdir/AutoScore/new/AutoScore.Rcheck/00install.out’ for details. +* DONE +Status: 1 ERROR + + -* checking whether package ‘bayesdfa’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/bayesdfa/new/bayesdfa.Rcheck/00install.out’ for details. - ``` -## Installation + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/AutoScore/old/AutoScore.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘AutoScore/DESCRIPTION’ ... OK +... +* checking if there is a namespace ... OK +* checking for executable files ... OK +* checking for hidden files and directories ... OK +* checking for portable file names ... OK +* checking for sufficient/correct file permissions ... OK +* checking whether package ‘AutoScore’ can be installed ... ERROR +Installation failed. +See ‘/tmp/workdir/AutoScore/old/AutoScore.Rcheck/00install.out’ for details. +* DONE +Status: 1 ERROR + + + + + +``` +# bayesdfa + +
+ +* Version: 1.3.3 +* GitHub: https://github.com/fate-ewi/bayesdfa +* Source code: https://github.com/cran/bayesdfa +* Date/Publication: 2024-02-26 20:50:06 UTC +* Number of recursive dependencies: 89 + +Run `revdepcheck::cloud_details(, "bayesdfa")` for more info + +
+ +## In both + +* checking whether package ‘bayesdfa’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/bayesdfa/new/bayesdfa.Rcheck/00install.out’ for details. + ``` + +## Installation ### Devel @@ -353,7 +681,7 @@ Run `revdepcheck::cloud_details(, "bayesdfa")` for more info ** package ‘bayesdfa’ successfully unpacked and MD5 sums checked ** using staged installation ** libs -using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ +using C++ compiler: ‘g++ (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ using C++17 @@ -362,9 +690,9 @@ In file included from /opt/R/4.3.1/lib/R/site-library/RcppEigen/include/Eigen/Co ... /opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src/stan/mcmc/hmc/hamiltonians/dense_e_metric.hpp:22:56: required from ‘double stan::mcmc::dense_e_metric::T(stan::mcmc::dense_e_point&) [with Model = model_dfa_namespace::model_dfa; BaseRNG = boost::random::additive_combine_engine, boost::random::linear_congruential_engine >]’ /opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src/stan/mcmc/hmc/hamiltonians/dense_e_metric.hpp:21:10: required from here -/opt/R/4.3.1/lib/R/site-library/RcppEigen/include/Eigen/src/Core/DenseCoeffsBase.h:654:34: warning: ignoring attributes on template argument ‘Eigen::internal::packet_traits::type’ {aka ‘__vector(2) double’} [-Wignored-attributes] +/opt/R/4.3.1/lib/R/site-library/RcppEigen/include/Eigen/src/Core/DenseCoeffsBase.h:654:74: warning: ignoring attributes on template argument ‘Eigen::internal::packet_traits::type’ {aka ‘__m128d’} [-Wignored-attributes] 654 | return internal::first_aligned::alignment),Derived>(m); - | ^~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ + | ^~~~~~~~~ g++: fatal error: Killed signal terminated program cc1plus compilation terminated. make: *** [/opt/R/4.3.1/lib/R/etc/Makeconf:198: stanExports_dfa.o] Error 1 @@ -380,7 +708,7 @@ ERROR: compilation failed for package ‘bayesdfa’ ** package ‘bayesdfa’ successfully unpacked and MD5 sums checked ** using staged installation ** libs -using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ +using C++ compiler: ‘g++ (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ using C++17 @@ -389,9 +717,9 @@ In file included from /opt/R/4.3.1/lib/R/site-library/RcppEigen/include/Eigen/Co ... /opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src/stan/mcmc/hmc/hamiltonians/dense_e_metric.hpp:22:56: required from ‘double stan::mcmc::dense_e_metric::T(stan::mcmc::dense_e_point&) [with Model = model_dfa_namespace::model_dfa; BaseRNG = boost::random::additive_combine_engine, boost::random::linear_congruential_engine >]’ /opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src/stan/mcmc/hmc/hamiltonians/dense_e_metric.hpp:21:10: required from here -/opt/R/4.3.1/lib/R/site-library/RcppEigen/include/Eigen/src/Core/DenseCoeffsBase.h:654:34: warning: ignoring attributes on template argument ‘Eigen::internal::packet_traits::type’ {aka ‘__vector(2) double’} [-Wignored-attributes] +/opt/R/4.3.1/lib/R/site-library/RcppEigen/include/Eigen/src/Core/DenseCoeffsBase.h:654:74: warning: ignoring attributes on template argument ‘Eigen::internal::packet_traits::type’ {aka ‘__m128d’} [-Wignored-attributes] 654 | return internal::first_aligned::alignment),Derived>(m); - | ^~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ + | ^~~~~~~~~ g++: fatal error: Killed signal terminated program cc1plus compilation terminated. make: *** [/opt/R/4.3.1/lib/R/etc/Makeconf:198: stanExports_dfa.o] Error 1 @@ -431,7 +759,7 @@ Run `revdepcheck::cloud_details(, "bayesDP")` for more info ** package ‘bayesDP’ successfully unpacked and MD5 sums checked ** using staged installation ** libs -using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ +using C++ compiler: ‘g++ (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c bdplm.cpp -o bdplm.o g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c ppexp.cpp -o ppexp.o @@ -440,9 +768,9 @@ installing to /tmp/workdir/bayesDP/new/bayesDP.Rcheck/00LOCK-bayesDP/00new/bayes ** R ** inst ** byte-compile and prepare package for lazy loading -Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Error in loadNamespace(i, c(lib.loc, .libPaths()), versionCheck = vI[[i]]) : + there is no package called ‘quantreg’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart Execution halted ERROR: lazy loading failed for package ‘bayesDP’ * removing ‘/tmp/workdir/bayesDP/new/bayesDP.Rcheck/bayesDP’ @@ -456,7 +784,7 @@ ERROR: lazy loading failed for package ‘bayesDP’ ** package ‘bayesDP’ successfully unpacked and MD5 sums checked ** using staged installation ** libs -using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ +using C++ compiler: ‘g++ (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c bdplm.cpp -o bdplm.o g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c ppexp.cpp -o ppexp.o @@ -465,9 +793,9 @@ installing to /tmp/workdir/bayesDP/old/bayesDP.Rcheck/00LOCK-bayesDP/00new/bayes ** R ** inst ** byte-compile and prepare package for lazy loading -Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Error in loadNamespace(i, c(lib.loc, .libPaths()), versionCheck = vI[[i]]) : + there is no package called ‘quantreg’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart Execution halted ERROR: lazy loading failed for package ‘bayesDP’ * removing ‘/tmp/workdir/bayesDP/old/bayesDP.Rcheck/bayesDP’ @@ -510,8 +838,8 @@ Run `revdepcheck::cloud_details(, "BayesianFactorZoo")` for more info ** inst ** byte-compile and prepare package for lazy loading Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace + there is no package called ‘quantreg’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart Execution halted ERROR: lazy loading failed for package ‘BayesianFactorZoo’ * removing ‘/tmp/workdir/BayesianFactorZoo/new/BayesianFactorZoo.Rcheck/BayesianFactorZoo’ @@ -530,8 +858,8 @@ ERROR: lazy loading failed for package ‘BayesianFactorZoo’ ** inst ** byte-compile and prepare package for lazy loading Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace + there is no package called ‘quantreg’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart Execution halted ERROR: lazy loading failed for package ‘BayesianFactorZoo’ * removing ‘/tmp/workdir/BayesianFactorZoo/old/BayesianFactorZoo.Rcheck/BayesianFactorZoo’ @@ -546,73 +874,147 @@ ERROR: lazy loading failed for package ‘BayesianFactorZoo’ * GitHub: https://github.com/ocbe-uio/BayesSurvive * Source code: https://github.com/cran/BayesSurvive * Date/Publication: 2024-04-23 11:20:06 UTC -* Number of recursive dependencies: 129 +* Number of recursive dependencies: 128 Run `revdepcheck::cloud_details(, "BayesSurvive")` for more info
-## In both +## Error before installation -* checking whether package ‘BayesSurvive’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/BayesSurvive/new/BayesSurvive.Rcheck/00install.out’ for details. - ``` +### Devel -## Installation +``` +* using log directory ‘/tmp/workdir/BayesSurvive/new/BayesSurvive.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘BayesSurvive/DESCRIPTION’ ... OK +... +* this is package ‘BayesSurvive’ version ‘0.0.1’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘riskRegression’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/BayesSurvive/old/BayesSurvive.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘BayesSurvive/DESCRIPTION’ ... OK +... +* this is package ‘BayesSurvive’ version ‘0.0.1’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘riskRegression’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# bbmle + +
+ +* Version: 1.0.25.1 +* GitHub: https://github.com/bbolker/bbmle +* Source code: https://github.com/cran/bbmle +* Date/Publication: 2023-12-09 01:00:02 UTC +* Number of recursive dependencies: 113 + +Run `revdepcheck::cloud_details(, "bbmle")` for more info + +
+ +## Error before installation ### Devel ``` -* installing *source* package ‘BayesSurvive’ ... -** package ‘BayesSurvive’ successfully unpacked and MD5 sums checked -** using staged installation -checking whether the C++ compiler works... yes -checking for C++ compiler default output file name... a.out -checking for suffix of executables... -checking whether we are cross compiling... no -checking for suffix of object files... o -checking whether the compiler supports GNU C++... yes -checking whether g++ -std=gnu++17 accepts -g... yes +* using log directory ‘/tmp/workdir/bbmle/new/bbmle.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘bbmle/DESCRIPTION’ ... OK ... -** R -** data -*** moving datasets to lazyload DB -** byte-compile and prepare package for lazy loading -Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +--- failed re-building ‘quasi.Rnw’ + +SUMMARY: processing the following files failed: + ‘mle2.Rnw’ ‘quasi.Rnw’ + +Error: Vignette re-building failed. Execution halted -ERROR: lazy loading failed for package ‘BayesSurvive’ -* removing ‘/tmp/workdir/BayesSurvive/new/BayesSurvive.Rcheck/BayesSurvive’ + +* DONE +Status: 2 NOTEs + + + ``` ### CRAN ``` -* installing *source* package ‘BayesSurvive’ ... -** package ‘BayesSurvive’ successfully unpacked and MD5 sums checked -** using staged installation -checking whether the C++ compiler works... yes -checking for C++ compiler default output file name... a.out -checking for suffix of executables... -checking whether we are cross compiling... no -checking for suffix of object files... o -checking whether the compiler supports GNU C++... yes -checking whether g++ -std=gnu++17 accepts -g... yes +* using log directory ‘/tmp/workdir/bbmle/old/bbmle.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘bbmle/DESCRIPTION’ ... OK ... -** R -** data -*** moving datasets to lazyload DB -** byte-compile and prepare package for lazy loading -Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +--- failed re-building ‘quasi.Rnw’ + +SUMMARY: processing the following files failed: + ‘mle2.Rnw’ ‘quasi.Rnw’ + +Error: Vignette re-building failed. Execution halted -ERROR: lazy loading failed for package ‘BayesSurvive’ -* removing ‘/tmp/workdir/BayesSurvive/old/BayesSurvive.Rcheck/BayesSurvive’ + +* DONE +Status: 2 NOTEs + + + ``` @@ -624,7 +1026,7 @@ ERROR: lazy loading failed for package ‘BayesSurvive’ * GitHub: NA * Source code: https://github.com/cran/BCClong * Date/Publication: 2024-02-05 11:50:06 UTC -* Number of recursive dependencies: 142 +* Number of recursive dependencies: 141 Run `revdepcheck::cloud_details(, "BCClong")` for more info @@ -652,7 +1054,7 @@ Run `revdepcheck::cloud_details(, "BCClong")` for more info ** package ‘BCClong’ successfully unpacked and MD5 sums checked ** using staged installation ** libs -using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ +using C++ compiler: ‘g++ (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c BCC.cpp -o BCC.o g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c Likelihood.cpp -o Likelihood.o g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o @@ -663,9 +1065,9 @@ installing to /tmp/workdir/BCClong/new/BCClong.Rcheck/00LOCK-BCClong/00new/BCClo ** R ** inst ** byte-compile and prepare package for lazy loading -Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Error in loadNamespace(i, c(lib.loc, .libPaths()), versionCheck = vI[[i]]) : + there is no package called ‘quantreg’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart Execution halted ERROR: lazy loading failed for package ‘BCClong’ * removing ‘/tmp/workdir/BCClong/new/BCClong.Rcheck/BCClong’ @@ -679,7 +1081,7 @@ ERROR: lazy loading failed for package ‘BCClong’ ** package ‘BCClong’ successfully unpacked and MD5 sums checked ** using staged installation ** libs -using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ +using C++ compiler: ‘g++ (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c BCC.cpp -o BCC.o g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c Likelihood.cpp -o Likelihood.o g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o @@ -690,35 +1092,35 @@ installing to /tmp/workdir/BCClong/old/BCClong.Rcheck/00LOCK-BCClong/00new/BCClo ** R ** inst ** byte-compile and prepare package for lazy loading -Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Error in loadNamespace(i, c(lib.loc, .libPaths()), versionCheck = vI[[i]]) : + there is no package called ‘quantreg’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart Execution halted ERROR: lazy loading failed for package ‘BCClong’ * removing ‘/tmp/workdir/BCClong/old/BCClong.Rcheck/BCClong’ ``` -# binsreg +# bmstdr
-* Version: 1.0 -* GitHub: NA -* Source code: https://github.com/cran/binsreg -* Date/Publication: 2023-07-11 12:00:24 UTC -* Number of recursive dependencies: 35 +* Version: 0.7.9 +* GitHub: https://github.com/sujit-sahu/bmstdr +* Source code: https://github.com/cran/bmstdr +* Date/Publication: 2023-12-18 15:00:02 UTC +* Number of recursive dependencies: 211 -Run `revdepcheck::cloud_details(, "binsreg")` for more info +Run `revdepcheck::cloud_details(, "bmstdr")` for more info
## In both -* checking whether package ‘binsreg’ can be installed ... ERROR +* checking whether package ‘bmstdr’ can be installed ... ERROR ``` Installation failed. - See ‘/tmp/workdir/binsreg/new/binsreg.Rcheck/00install.out’ for details. + See ‘/tmp/workdir/bmstdr/new/bmstdr.Rcheck/00install.out’ for details. ``` ## Installation @@ -726,174 +1128,38 @@ Run `revdepcheck::cloud_details(, "binsreg")` for more info ### Devel ``` -* installing *source* package ‘binsreg’ ... -** package ‘binsreg’ successfully unpacked and MD5 sums checked +* installing *source* package ‘bmstdr’ ... +** package ‘bmstdr’ successfully unpacked and MD5 sums checked ** using staged installation -** R +** libs +using C++ compiler: ‘g++ (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ +using C++17 + + +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I"../inst/include" -I"/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src" -DBOOST_DISABLE_ASSERTS -DEIGEN_NO_DEBUG -DBOOST_MATH_OVERFLOW_ERROR_POLICY=errno_on_error -DUSE_STANC3 -D_HAS_AUTO_PTR_ETC=0 -I'/opt/R/4.3.1/lib/R/site-library/BH/include' -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppEigen/include' -I'/opt/R/4.3.1/lib/R/site-library/rstan/include' -I'/opt/R/4.3.1/lib/R/site-library/StanHeaders/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -I/usr/local/include -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -D_REENTRANT -DSTAN_THREADS -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +In file included from /opt/R/4.3.1/lib/R/site-library/RcppEigen/include/Eigen/Core:205, +... +** 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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Error in loadNamespace(i, c(lib.loc, .libPaths()), versionCheck = vI[[i]]) : + there is no package called ‘quantreg’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart Execution halted -ERROR: lazy loading failed for package ‘binsreg’ -* removing ‘/tmp/workdir/binsreg/new/binsreg.Rcheck/binsreg’ +ERROR: lazy loading failed for package ‘bmstdr’ +* removing ‘/tmp/workdir/bmstdr/new/bmstdr.Rcheck/bmstdr’ ``` ### CRAN ``` -* installing *source* package ‘binsreg’ ... -** package ‘binsreg’ successfully unpacked and MD5 sums checked -** using staged installation -** R -** byte-compile and prepare package for lazy loading -Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘binsreg’ -* removing ‘/tmp/workdir/binsreg/old/binsreg.Rcheck/binsreg’ - - -``` -# bmgarch - -
- -* Version: 2.0.0 -* GitHub: https://github.com/ph-rast/bmgarch -* Source code: https://github.com/cran/bmgarch -* Date/Publication: 2023-09-12 00:40:02 UTC -* Number of recursive dependencies: 82 - -Run `revdepcheck::cloud_details(, "bmgarch")` for more info - -
- -## In both - -* checking whether package ‘bmgarch’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/bmgarch/new/bmgarch.Rcheck/00install.out’ for details. - ``` - -## Installation - -### Devel - -``` -* installing *source* package ‘bmgarch’ ... -** package ‘bmgarch’ successfully unpacked and MD5 sums checked -** using staged installation -** libs -using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ -using C++17 - - -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I"../inst/include" -I"/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src" -DBOOST_DISABLE_ASSERTS -DEIGEN_NO_DEBUG -DBOOST_MATH_OVERFLOW_ERROR_POLICY=errno_on_error -DUSE_STANC3 -D_HAS_AUTO_PTR_ETC=0 -I'/opt/R/4.3.1/lib/R/site-library/BH/include' -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppEigen/include' -I'/opt/R/4.3.1/lib/R/site-library/rstan/include' -I'/opt/R/4.3.1/lib/R/site-library/StanHeaders/include' -I/usr/local/include -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -D_REENTRANT -DSTAN_THREADS -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o -In file included from /opt/R/4.3.1/lib/R/site-library/RcppEigen/include/Eigen/Core:205, -... -/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src/stan/mcmc/hmc/hamiltonians/dense_e_metric.hpp:22:56: required from ‘double stan::mcmc::dense_e_metric::T(stan::mcmc::dense_e_point&) [with Model = model_DCCMGARCH_namespace::model_DCCMGARCH; BaseRNG = boost::random::additive_combine_engine, boost::random::linear_congruential_engine >]’ -/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src/stan/mcmc/hmc/hamiltonians/dense_e_metric.hpp:21:10: required from here -/opt/R/4.3.1/lib/R/site-library/RcppEigen/include/Eigen/src/Core/DenseCoeffsBase.h:654:34: warning: ignoring attributes on template argument ‘Eigen::internal::packet_traits::type’ {aka ‘__vector(2) double’} [-Wignored-attributes] - 654 | return internal::first_aligned::alignment),Derived>(m); - | ^~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -g++: fatal error: Killed signal terminated program cc1plus -compilation terminated. -make: *** [/opt/R/4.3.1/lib/R/etc/Makeconf:198: stanExports_DCCMGARCH.o] Error 1 -ERROR: compilation failed for package ‘bmgarch’ -* removing ‘/tmp/workdir/bmgarch/new/bmgarch.Rcheck/bmgarch’ - - -``` -### CRAN - -``` -* installing *source* package ‘bmgarch’ ... -** package ‘bmgarch’ successfully unpacked and MD5 sums checked -** using staged installation -** libs -using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ -using C++17 - - -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I"../inst/include" -I"/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src" -DBOOST_DISABLE_ASSERTS -DEIGEN_NO_DEBUG -DBOOST_MATH_OVERFLOW_ERROR_POLICY=errno_on_error -DUSE_STANC3 -D_HAS_AUTO_PTR_ETC=0 -I'/opt/R/4.3.1/lib/R/site-library/BH/include' -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppEigen/include' -I'/opt/R/4.3.1/lib/R/site-library/rstan/include' -I'/opt/R/4.3.1/lib/R/site-library/StanHeaders/include' -I/usr/local/include -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -D_REENTRANT -DSTAN_THREADS -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o -In file included from /opt/R/4.3.1/lib/R/site-library/RcppEigen/include/Eigen/Core:205, -... -/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src/stan/mcmc/hmc/hamiltonians/dense_e_metric.hpp:22:56: required from ‘double stan::mcmc::dense_e_metric::T(stan::mcmc::dense_e_point&) [with Model = model_DCCMGARCH_namespace::model_DCCMGARCH; BaseRNG = boost::random::additive_combine_engine, boost::random::linear_congruential_engine >]’ -/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src/stan/mcmc/hmc/hamiltonians/dense_e_metric.hpp:21:10: required from here -/opt/R/4.3.1/lib/R/site-library/RcppEigen/include/Eigen/src/Core/DenseCoeffsBase.h:654:34: warning: ignoring attributes on template argument ‘Eigen::internal::packet_traits::type’ {aka ‘__vector(2) double’} [-Wignored-attributes] - 654 | return internal::first_aligned::alignment),Derived>(m); - | ^~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -g++: fatal error: Killed signal terminated program cc1plus -compilation terminated. -make: *** [/opt/R/4.3.1/lib/R/etc/Makeconf:198: stanExports_DCCMGARCH.o] Error 1 -ERROR: compilation failed for package ‘bmgarch’ -* removing ‘/tmp/workdir/bmgarch/old/bmgarch.Rcheck/bmgarch’ - - -``` -# bmstdr - -
- -* Version: 0.7.9 -* GitHub: https://github.com/sujit-sahu/bmstdr -* Source code: https://github.com/cran/bmstdr -* Date/Publication: 2023-12-18 15:00:02 UTC -* Number of recursive dependencies: 212 - -Run `revdepcheck::cloud_details(, "bmstdr")` for more info - -
- -## In both - -* checking whether package ‘bmstdr’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/bmstdr/new/bmstdr.Rcheck/00install.out’ for details. - ``` - -## Installation - -### Devel - -``` -* installing *source* package ‘bmstdr’ ... -** package ‘bmstdr’ successfully unpacked and MD5 sums checked -** using staged installation -** libs -using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ -using C++17 - - -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I"../inst/include" -I"/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src" -DBOOST_DISABLE_ASSERTS -DEIGEN_NO_DEBUG -DBOOST_MATH_OVERFLOW_ERROR_POLICY=errno_on_error -DUSE_STANC3 -D_HAS_AUTO_PTR_ETC=0 -I'/opt/R/4.3.1/lib/R/site-library/BH/include' -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppEigen/include' -I'/opt/R/4.3.1/lib/R/site-library/rstan/include' -I'/opt/R/4.3.1/lib/R/site-library/StanHeaders/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -I/usr/local/include -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -D_REENTRANT -DSTAN_THREADS -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o -In file included from /opt/R/4.3.1/lib/R/site-library/RcppEigen/include/Eigen/Core:205, -... -** 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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘bmstdr’ -* removing ‘/tmp/workdir/bmstdr/new/bmstdr.Rcheck/bmstdr’ - - -``` -### CRAN - -``` -* installing *source* package ‘bmstdr’ ... -** package ‘bmstdr’ successfully unpacked and MD5 sums checked +* installing *source* package ‘bmstdr’ ... +** package ‘bmstdr’ successfully unpacked and MD5 sums checked ** using staged installation ** libs -using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ +using C++ compiler: ‘g++ (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ using C++17 @@ -904,9 +1170,9 @@ In file included from /opt/R/4.3.1/lib/R/site-library/RcppEigen/include/Eigen/Co *** 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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Error in loadNamespace(i, c(lib.loc, .libPaths()), versionCheck = vI[[i]]) : + there is no package called ‘quantreg’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart Execution halted ERROR: lazy loading failed for package ‘bmstdr’ * removing ‘/tmp/workdir/bmstdr/old/bmstdr.Rcheck/bmstdr’ @@ -989,151 +1255,315 @@ Run `revdepcheck::cloud_details(, "BuyseTest")` for more info -## In both - -* checking whether package ‘BuyseTest’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/BuyseTest/new/BuyseTest.Rcheck/00install.out’ for details. - ``` - -## Installation +## Error before installation ### Devel ``` -* installing *source* package ‘BuyseTest’ ... -** package ‘BuyseTest’ successfully unpacked and MD5 sums checked -** using staged installation -** libs -using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c FCT_buyseTest.cpp -o FCT_buyseTest.o -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c FCT_precompute.cpp -o FCT_precompute.o -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c utils-from-riskRegression.cpp -o utils-from-riskRegression.o -g++ -std=gnu++17 -shared -L/opt/R/4.3.1/lib/R/lib -L/usr/local/lib -o BuyseTest.so FCT_buyseTest.o FCT_precompute.o RcppExports.o utils-from-riskRegression.o -L/opt/R/4.3.1/lib/R/lib -lR +* using log directory ‘/tmp/workdir/BuyseTest/new/BuyseTest.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘BuyseTest/DESCRIPTION’ ... OK ... -installing to /tmp/workdir/BuyseTest/new/BuyseTest.Rcheck/00LOCK-BuyseTest/00new/BuyseTest/libs -** R -** inst -** byte-compile and prepare package for lazy loading -Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Error: unable to load R code in package ‘BuyseTest’ -Execution halted -ERROR: lazy loading failed for package ‘BuyseTest’ -* removing ‘/tmp/workdir/BuyseTest/new/BuyseTest.Rcheck/BuyseTest’ +* this is package ‘BuyseTest’ version ‘3.0.2’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘riskRegression’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + ``` ### CRAN ``` -* installing *source* package ‘BuyseTest’ ... -** package ‘BuyseTest’ successfully unpacked and MD5 sums checked -** using staged installation -** libs -using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c FCT_buyseTest.cpp -o FCT_buyseTest.o -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c FCT_precompute.cpp -o FCT_precompute.o -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c utils-from-riskRegression.cpp -o utils-from-riskRegression.o -g++ -std=gnu++17 -shared -L/opt/R/4.3.1/lib/R/lib -L/usr/local/lib -o BuyseTest.so FCT_buyseTest.o FCT_precompute.o RcppExports.o utils-from-riskRegression.o -L/opt/R/4.3.1/lib/R/lib -lR +* using log directory ‘/tmp/workdir/BuyseTest/old/BuyseTest.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘BuyseTest/DESCRIPTION’ ... OK ... -installing to /tmp/workdir/BuyseTest/old/BuyseTest.Rcheck/00LOCK-BuyseTest/00new/BuyseTest/libs -** R -** inst -** byte-compile and prepare package for lazy loading -Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Error: unable to load R code in package ‘BuyseTest’ -Execution halted -ERROR: lazy loading failed for package ‘BuyseTest’ -* removing ‘/tmp/workdir/BuyseTest/old/BuyseTest.Rcheck/BuyseTest’ +* this is package ‘BuyseTest’ version ‘3.0.2’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘riskRegression’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + ``` -# CalibrationCurves +# calibmsm
-* Version: 2.0.1 +* Version: 1.1.0 * GitHub: NA -* Source code: https://github.com/cran/CalibrationCurves -* Date/Publication: 2024-03-01 10:12:35 UTC -* Number of recursive dependencies: 78 +* Source code: https://github.com/cran/calibmsm +* Date/Publication: 2024-05-13 11:33:07 UTC +* Number of recursive dependencies: 143 -Run `revdepcheck::cloud_details(, "CalibrationCurves")` for more info +Run `revdepcheck::cloud_details(, "calibmsm")` for more info
-## In both - -* checking whether package ‘CalibrationCurves’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/CalibrationCurves/new/CalibrationCurves.Rcheck/00install.out’ for details. - ``` - -## Installation +## Error before installation ### Devel ``` -* installing *source* package ‘CalibrationCurves’ ... -** package ‘CalibrationCurves’ 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: package or namespace load failed for ‘rms’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Execution halted -ERROR: lazy loading failed for package ‘CalibrationCurves’ -* removing ‘/tmp/workdir/CalibrationCurves/new/CalibrationCurves.Rcheck/CalibrationCurves’ +* using log directory ‘/tmp/workdir/calibmsm/new/calibmsm.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘calibmsm/DESCRIPTION’ ... OK +... +* this is package ‘calibmsm’ version ‘1.1.0’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘rms’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + ``` ### CRAN ``` -* installing *source* package ‘CalibrationCurves’ ... -** package ‘CalibrationCurves’ 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: package or namespace load failed for ‘rms’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Execution halted -ERROR: lazy loading failed for package ‘CalibrationCurves’ -* removing ‘/tmp/workdir/CalibrationCurves/old/CalibrationCurves.Rcheck/CalibrationCurves’ +* using log directory ‘/tmp/workdir/calibmsm/old/calibmsm.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘calibmsm/DESCRIPTION’ ... OK +... +* this is package ‘calibmsm’ version ‘1.1.0’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘rms’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + ``` -# CARBayesST +# CalibrationCurves
-* Version: 4.0 -* GitHub: https://github.com/duncanplee/CARBayesST -* Source code: https://github.com/cran/CARBayesST -* Date/Publication: 2023-10-30 16:40:02 UTC -* Number of recursive dependencies: 118 +* Version: 2.0.1 +* GitHub: NA +* Source code: https://github.com/cran/CalibrationCurves +* Date/Publication: 2024-03-01 10:12:35 UTC +* Number of recursive dependencies: 78 -Run `revdepcheck::cloud_details(, "CARBayesST")` for more info +Run `revdepcheck::cloud_details(, "CalibrationCurves")` for more info
-## In both +## Error before installation -* checking whether package ‘CARBayesST’ can be installed ... ERROR - ``` - Installation failed. +### Devel + +``` +* using log directory ‘/tmp/workdir/CalibrationCurves/new/CalibrationCurves.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘CalibrationCurves/DESCRIPTION’ ... OK +... +* this is package ‘CalibrationCurves’ version ‘2.0.1’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘rms’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/CalibrationCurves/old/CalibrationCurves.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘CalibrationCurves/DESCRIPTION’ ... OK +... +* this is package ‘CalibrationCurves’ version ‘2.0.1’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘rms’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# Canek + +
+ +* Version: 0.2.5 +* GitHub: https://github.com/MartinLoza/Canek +* Source code: https://github.com/cran/Canek +* Date/Publication: 2023-12-08 05:30:02 UTC +* Number of recursive dependencies: 220 + +Run `revdepcheck::cloud_details(, "Canek")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/Canek/new/Canek.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘Canek/DESCRIPTION’ ... OK +... + [ FAIL 1 | WARN 0 | SKIP 0 | PASS 74 ] + Error: Test failures + Execution halted +* checking for unstated dependencies in vignettes ... OK +* checking package vignettes in ‘inst/doc’ ... OK +* checking running R code from vignettes ... OK + ‘toy_example.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 1 ERROR, 1 NOTE + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/Canek/old/Canek.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘Canek/DESCRIPTION’ ... OK +... + [ FAIL 1 | WARN 0 | SKIP 0 | PASS 74 ] + Error: Test failures + Execution halted +* checking for unstated dependencies in vignettes ... OK +* checking package vignettes in ‘inst/doc’ ... OK +* checking running R code from vignettes ... OK + ‘toy_example.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 1 ERROR, 1 NOTE + + + + + +``` +# CARBayesST + +
+ +* Version: 4.0 +* GitHub: https://github.com/duncanplee/CARBayesST +* Source code: https://github.com/cran/CARBayesST +* Date/Publication: 2023-10-30 16:40:02 UTC +* Number of recursive dependencies: 117 + +Run `revdepcheck::cloud_details(, "CARBayesST")` for more info + +
+ +## In both + +* checking whether package ‘CARBayesST’ can be installed ... ERROR + ``` + Installation failed. See ‘/tmp/workdir/CARBayesST/new/CARBayesST.Rcheck/00install.out’ for details. ``` @@ -1146,7 +1576,7 @@ Run `revdepcheck::cloud_details(, "CARBayesST")` for more info ** package ‘CARBayesST’ successfully unpacked and MD5 sums checked ** using staged installation ** libs -using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ +using C++ compiler: ‘g++ (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c CARBayesST.cpp -o CARBayesST.o g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o g++ -std=gnu++17 -shared -L/opt/R/4.3.1/lib/R/lib -L/usr/local/lib -o CARBayesST.so CARBayesST.o RcppExports.o -L/opt/R/4.3.1/lib/R/lib -lR @@ -1154,9 +1584,9 @@ installing to /tmp/workdir/CARBayesST/new/CARBayesST.Rcheck/00LOCK-CARBayesST/00 ** R ** inst ** byte-compile and prepare package for lazy loading -Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Error in loadNamespace(i, c(lib.loc, .libPaths()), versionCheck = vI[[i]]) : + there is no package called ‘quantreg’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart Execution halted ERROR: lazy loading failed for package ‘CARBayesST’ * removing ‘/tmp/workdir/CARBayesST/new/CARBayesST.Rcheck/CARBayesST’ @@ -1170,7 +1600,7 @@ ERROR: lazy loading failed for package ‘CARBayesST’ ** package ‘CARBayesST’ successfully unpacked and MD5 sums checked ** using staged installation ** libs -using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ +using C++ compiler: ‘g++ (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c CARBayesST.cpp -o CARBayesST.o g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o g++ -std=gnu++17 -shared -L/opt/R/4.3.1/lib/R/lib -L/usr/local/lib -o CARBayesST.so CARBayesST.o RcppExports.o -L/opt/R/4.3.1/lib/R/lib -lR @@ -1178,9 +1608,9 @@ installing to /tmp/workdir/CARBayesST/old/CARBayesST.Rcheck/00LOCK-CARBayesST/00 ** R ** inst ** byte-compile and prepare package for lazy loading -Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Error in loadNamespace(i, c(lib.loc, .libPaths()), versionCheck = vI[[i]]) : + there is no package called ‘quantreg’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart Execution halted ERROR: lazy loading failed for package ‘CARBayesST’ * removing ‘/tmp/workdir/CARBayesST/old/CARBayesST.Rcheck/CARBayesST’ @@ -1201,67 +1631,141 @@ Run `revdepcheck::cloud_details(, "CaseBasedReasoning")` for more info -## In both +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/CaseBasedReasoning/new/CaseBasedReasoning.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘CaseBasedReasoning/DESCRIPTION’ ... OK +... +* this is package ‘CaseBasedReasoning’ version ‘0.3’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘rms’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/CaseBasedReasoning/old/CaseBasedReasoning.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘CaseBasedReasoning/DESCRIPTION’ ... OK +... +* this is package ‘CaseBasedReasoning’ version ‘0.3’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘rms’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + -* checking whether package ‘CaseBasedReasoning’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/CaseBasedReasoning/new/CaseBasedReasoning.Rcheck/00install.out’ for details. - ``` -## Installation + + +``` +# cellpypes + +
+ +* Version: 0.3.0 +* GitHub: https://github.com/FelixTheStudent/cellpypes +* Source code: https://github.com/cran/cellpypes +* Date/Publication: 2024-01-27 07:30:07 UTC +* Number of recursive dependencies: 183 + +Run `revdepcheck::cloud_details(, "cellpypes")` for more info + +
+ +## Error before installation ### Devel ``` -* installing *source* package ‘CaseBasedReasoning’ ... -** package ‘CaseBasedReasoning’ successfully unpacked and MD5 sums checked -** using staged installation -** libs -using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -I/usr/local/include -fpic -g -O2 -c distanceAPI.cpp -o distanceAPI.o -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -I/usr/local/include -fpic -g -O2 -c distances.cpp -o distances.o -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -I/usr/local/include -fpic -g -O2 -c order.cpp -o order.o -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -I/usr/local/include -fpic -g -O2 -c weightedKNN.cpp -o weightedKNN.o -... -g++ -std=gnu++17 -shared -L/opt/R/4.3.1/lib/R/lib -L/usr/local/lib -o CaseBasedReasoning.so RcppExports.o distanceAPI.o distances.o order.o weightedKNN.o -L/opt/R/4.3.1/lib/R/lib -lR -installing to /tmp/workdir/CaseBasedReasoning/new/CaseBasedReasoning.Rcheck/00LOCK-CaseBasedReasoning/00new/CaseBasedReasoning/libs -** R -** inst -** byte-compile and prepare package for lazy loading -Error: package or namespace load failed for ‘rms’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Execution halted -ERROR: lazy loading failed for package ‘CaseBasedReasoning’ -* removing ‘/tmp/workdir/CaseBasedReasoning/new/CaseBasedReasoning.Rcheck/CaseBasedReasoning’ +* using log directory ‘/tmp/workdir/cellpypes/new/cellpypes.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘cellpypes/DESCRIPTION’ ... OK +... +* checking contents of ‘data’ directory ... OK +* checking data for non-ASCII characters ... OK +* checking LazyData ... OK +* checking data for ASCII and uncompressed saves ... OK +* checking examples ... OK +* checking for unstated dependencies in ‘tests’ ... OK +* checking tests ... OK + Running ‘testthat.R’ +* DONE +Status: 1 NOTE + + + ``` ### CRAN ``` -* installing *source* package ‘CaseBasedReasoning’ ... -** package ‘CaseBasedReasoning’ successfully unpacked and MD5 sums checked -** using staged installation -** libs -using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -I/usr/local/include -fpic -g -O2 -c distanceAPI.cpp -o distanceAPI.o -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -I/usr/local/include -fpic -g -O2 -c distances.cpp -o distances.o -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -I/usr/local/include -fpic -g -O2 -c order.cpp -o order.o -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -I/usr/local/include -fpic -g -O2 -c weightedKNN.cpp -o weightedKNN.o -... -g++ -std=gnu++17 -shared -L/opt/R/4.3.1/lib/R/lib -L/usr/local/lib -o CaseBasedReasoning.so RcppExports.o distanceAPI.o distances.o order.o weightedKNN.o -L/opt/R/4.3.1/lib/R/lib -lR -installing to /tmp/workdir/CaseBasedReasoning/old/CaseBasedReasoning.Rcheck/00LOCK-CaseBasedReasoning/00new/CaseBasedReasoning/libs -** R -** inst -** byte-compile and prepare package for lazy loading -Error: package or namespace load failed for ‘rms’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Execution halted -ERROR: lazy loading failed for package ‘CaseBasedReasoning’ -* removing ‘/tmp/workdir/CaseBasedReasoning/old/CaseBasedReasoning.Rcheck/CaseBasedReasoning’ +* using log directory ‘/tmp/workdir/cellpypes/old/cellpypes.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘cellpypes/DESCRIPTION’ ... OK +... +* checking contents of ‘data’ directory ... OK +* checking data for non-ASCII characters ... OK +* checking LazyData ... OK +* checking data for ASCII and uncompressed saves ... OK +* checking examples ... OK +* checking for unstated dependencies in ‘tests’ ... OK +* checking tests ... OK + Running ‘testthat.R’ +* DONE +Status: 1 NOTE + + + ``` @@ -1329,274 +1833,406 @@ ERROR: lazy loading failed for package ‘CGPfunctions’ ``` -# cmprskcoxmsm +# chem16S
-* Version: 0.2.1 -* GitHub: NA -* Source code: https://github.com/cran/cmprskcoxmsm -* Date/Publication: 2021-09-04 05:50:02 UTC -* Number of recursive dependencies: 71 +* Version: 1.0.0 +* GitHub: https://github.com/jedick/chem16S +* Source code: https://github.com/cran/chem16S +* Date/Publication: 2023-07-17 17:10:02 UTC +* Number of recursive dependencies: 112 -Run `revdepcheck::cloud_details(, "cmprskcoxmsm")` for more info +Run `revdepcheck::cloud_details(, "chem16S")` for more info
-## In both - -* checking whether package ‘cmprskcoxmsm’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/cmprskcoxmsm/new/cmprskcoxmsm.Rcheck/00install.out’ for details. - ``` - -## Installation +## Error before installation ### Devel ``` -* installing *source* package ‘cmprskcoxmsm’ ... -** package ‘cmprskcoxmsm’ successfully unpacked and MD5 sums checked -** 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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +* using log directory ‘/tmp/workdir/chem16S/new/chem16S.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘chem16S/DESCRIPTION’ ... OK +... + When sourcing ‘plotting.R’: +Error: could not find function "stat_poly_line" Execution halted -ERROR: lazy loading failed for package ‘cmprskcoxmsm’ -* removing ‘/tmp/workdir/cmprskcoxmsm/new/cmprskcoxmsm.Rcheck/cmprskcoxmsm’ + + ‘metrics.Rmd’ using ‘UTF-8’... OK + ‘phyloseq.Rmd’ using ‘UTF-8’... OK + ‘plotting.Rmd’ using ‘UTF-8’... failed +* checking re-building of vignette outputs ... OK +* DONE +Status: 1 ERROR, 1 NOTE + + + ``` ### CRAN ``` -* installing *source* package ‘cmprskcoxmsm’ ... -** package ‘cmprskcoxmsm’ successfully unpacked and MD5 sums checked -** 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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +* using log directory ‘/tmp/workdir/chem16S/old/chem16S.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘chem16S/DESCRIPTION’ ... OK +... + When sourcing ‘plotting.R’: +Error: could not find function "stat_poly_line" Execution halted -ERROR: lazy loading failed for package ‘cmprskcoxmsm’ -* removing ‘/tmp/workdir/cmprskcoxmsm/old/cmprskcoxmsm.Rcheck/cmprskcoxmsm’ + + ‘metrics.Rmd’ using ‘UTF-8’... OK + ‘phyloseq.Rmd’ using ‘UTF-8’... OK + ‘plotting.Rmd’ using ‘UTF-8’... failed +* checking re-building of vignette outputs ... OK +* DONE +Status: 1 ERROR, 1 NOTE + + + ``` -# contrast +# CIARA
-* Version: 0.24.2 -* GitHub: https://github.com/Alanocallaghan/contrast -* Source code: https://github.com/cran/contrast -* Date/Publication: 2022-10-05 17:20:09 UTC -* Number of recursive dependencies: 112 +* Version: 0.1.0 +* GitHub: NA +* Source code: https://github.com/cran/CIARA +* Date/Publication: 2022-02-22 20:00:02 UTC +* Number of recursive dependencies: 181 -Run `revdepcheck::cloud_details(, "contrast")` for more info +Run `revdepcheck::cloud_details(, "CIARA")` for more info
-## In both - -* checking whether package ‘contrast’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/contrast/new/contrast.Rcheck/00install.out’ for details. - ``` - -## Installation +## Error before installation ### Devel ``` -* installing *source* package ‘contrast’ ... -** package ‘contrast’ 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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘contrast’ -* removing ‘/tmp/workdir/contrast/new/contrast.Rcheck/contrast’ +* using log directory ‘/tmp/workdir/CIARA/new/CIARA.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘CIARA/DESCRIPTION’ ... OK +... +* checking tests ... OK + Running ‘testthat.R’ +* checking for unstated dependencies in vignettes ... OK +* checking package vignettes in ‘inst/doc’ ... OK +* checking running R code from vignettes ... OK + ‘CIARA.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... NOTE +Note: skipping ‘CIARA.Rmd’ due to unavailable dependencies: 'Seurat' +* DONE +Status: 3 NOTEs + + + ``` ### CRAN ``` -* installing *source* package ‘contrast’ ... -** package ‘contrast’ 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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘contrast’ -* removing ‘/tmp/workdir/contrast/old/contrast.Rcheck/contrast’ +* using log directory ‘/tmp/workdir/CIARA/old/CIARA.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘CIARA/DESCRIPTION’ ... OK +... +* checking tests ... OK + Running ‘testthat.R’ +* checking for unstated dependencies in vignettes ... OK +* checking package vignettes in ‘inst/doc’ ... OK +* checking running R code from vignettes ... OK + ‘CIARA.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... NOTE +Note: skipping ‘CIARA.Rmd’ due to unavailable dependencies: 'Seurat' +* DONE +Status: 3 NOTEs + + + ``` -# coxed +# clarify
-* Version: 0.3.3 -* GitHub: https://github.com/jkropko/coxed -* Source code: https://github.com/cran/coxed -* Date/Publication: 2020-08-02 01:20:07 UTC -* Number of recursive dependencies: 109 +* Version: 0.2.1 +* GitHub: https://github.com/iqss/clarify +* Source code: https://github.com/cran/clarify +* Date/Publication: 2024-05-30 16:50:02 UTC +* Number of recursive dependencies: 163 -Run `revdepcheck::cloud_details(, "coxed")` for more info +Run `revdepcheck::cloud_details(, "clarify")` for more info
-## In both +## Error before installation -* checking whether package ‘coxed’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/coxed/new/coxed.Rcheck/00install.out’ for details. - ``` +### Devel + +``` +* using log directory ‘/tmp/workdir/clarify/new/clarify.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘clarify/DESCRIPTION’ ... OK +... +* checking tests ... OK + Running ‘testthat.R’ +* checking for unstated dependencies in vignettes ... OK +* checking package vignettes in ‘inst/doc’ ... OK +* checking running R code from vignettes ... OK + ‘Zelig.Rmd’ using ‘UTF-8’... OK + ‘clarify.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 1 NOTE -## Installation + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/clarify/old/clarify.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘clarify/DESCRIPTION’ ... OK +... +* checking tests ... OK + Running ‘testthat.R’ +* checking for unstated dependencies in vignettes ... OK +* checking package vignettes in ‘inst/doc’ ... OK +* checking running R code from vignettes ... OK + ‘Zelig.Rmd’ using ‘UTF-8’... OK + ‘clarify.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 1 NOTE + + + + + +``` +# ClustAssess + +
+ +* Version: 0.3.0 +* GitHub: https://github.com/Core-Bioinformatics/ClustAssess +* Source code: https://github.com/cran/ClustAssess +* Date/Publication: 2022-01-26 16:52:46 UTC +* Number of recursive dependencies: 164 + +Run `revdepcheck::cloud_details(, "ClustAssess")` for more info + +
+ +## Error before installation ### Devel ``` -* installing *source* package ‘coxed’ ... -** package ‘coxed’ 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: package or namespace load failed for ‘rms’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +* using log directory ‘/tmp/workdir/ClustAssess/new/ClustAssess.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘ClustAssess/DESCRIPTION’ ... OK +... +--- finished re-building ‘comparing-soft-and-hierarchical.Rmd’ + +SUMMARY: processing the following file failed: + ‘ClustAssess.Rmd’ + +Error: Vignette re-building failed. Execution halted -ERROR: lazy loading failed for package ‘coxed’ -* removing ‘/tmp/workdir/coxed/new/coxed.Rcheck/coxed’ + +* DONE +Status: 1 ERROR, 1 WARNING, 2 NOTEs + + + ``` ### CRAN ``` -* installing *source* package ‘coxed’ ... -** package ‘coxed’ 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: package or namespace load failed for ‘rms’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +* using log directory ‘/tmp/workdir/ClustAssess/old/ClustAssess.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘ClustAssess/DESCRIPTION’ ... OK +... +--- finished re-building ‘comparing-soft-and-hierarchical.Rmd’ + +SUMMARY: processing the following file failed: + ‘ClustAssess.Rmd’ + +Error: Vignette re-building failed. Execution halted -ERROR: lazy loading failed for package ‘coxed’ -* removing ‘/tmp/workdir/coxed/old/coxed.Rcheck/coxed’ + +* DONE +Status: 1 ERROR, 1 WARNING, 2 NOTEs + + + ``` -# CRMetrics +# clustree
-* Version: 0.3.0 -* GitHub: https://github.com/khodosevichlab/CRMetrics -* Source code: https://github.com/cran/CRMetrics -* Date/Publication: 2023-09-01 09:00:06 UTC -* Number of recursive dependencies: 235 +* Version: 0.5.1 +* GitHub: https://github.com/lazappi/clustree +* Source code: https://github.com/cran/clustree +* Date/Publication: 2023-11-05 19:10:02 UTC +* Number of recursive dependencies: 192 -Run `revdepcheck::cloud_details(, "CRMetrics")` for more info +Run `revdepcheck::cloud_details(, "clustree")` for more info
-## In both - -* checking whether package ‘CRMetrics’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/CRMetrics/new/CRMetrics.Rcheck/00install.out’ for details. - ``` - -## Installation +## Error before installation ### Devel ``` -* installing *source* package ‘CRMetrics’ ... -** package ‘CRMetrics’ 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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘CRMetrics’ -* removing ‘/tmp/workdir/CRMetrics/new/CRMetrics.Rcheck/CRMetrics’ +* using log directory ‘/tmp/workdir/clustree/new/clustree.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘clustree/DESCRIPTION’ ... OK +... +* checking tests ... OK + Running ‘spelling.R’ + Running ‘testthat.R’ +* checking for unstated dependencies in vignettes ... OK +* checking package vignettes in ‘inst/doc’ ... OK +* checking running R code from vignettes ... OK + ‘clustree.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 1 NOTE + + + ``` ### CRAN ``` -* installing *source* package ‘CRMetrics’ ... -** package ‘CRMetrics’ 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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘CRMetrics’ -* removing ‘/tmp/workdir/CRMetrics/old/CRMetrics.Rcheck/CRMetrics’ +* using log directory ‘/tmp/workdir/clustree/old/clustree.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘clustree/DESCRIPTION’ ... OK +... +* checking tests ... OK + Running ‘spelling.R’ + Running ‘testthat.R’ +* checking for unstated dependencies in vignettes ... OK +* checking package vignettes in ‘inst/doc’ ... OK +* checking running R code from vignettes ... OK + ‘clustree.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 1 NOTE + + + ``` -# csmpv +# cmprskcoxmsm
-* Version: 1.0.3 +* Version: 0.2.1 * GitHub: NA -* Source code: https://github.com/cran/csmpv -* Date/Publication: 2024-03-01 18:12:44 UTC -* Number of recursive dependencies: 175 +* Source code: https://github.com/cran/cmprskcoxmsm +* Date/Publication: 2021-09-04 05:50:02 UTC +* Number of recursive dependencies: 71 -Run `revdepcheck::cloud_details(, "csmpv")` for more info +Run `revdepcheck::cloud_details(, "cmprskcoxmsm")` for more info
## In both -* checking whether package ‘csmpv’ can be installed ... ERROR +* checking whether package ‘cmprskcoxmsm’ can be installed ... ERROR ``` Installation failed. - See ‘/tmp/workdir/csmpv/new/csmpv.Rcheck/00install.out’ for details. + See ‘/tmp/workdir/cmprskcoxmsm/new/cmprskcoxmsm.Rcheck/00install.out’ for details. ``` ## Installation @@ -1604,776 +2240,821 @@ Run `revdepcheck::cloud_details(, "csmpv")` for more info ### Devel ``` -* installing *source* package ‘csmpv’ ... -** package ‘csmpv’ successfully unpacked and MD5 sums checked +* installing *source* package ‘cmprskcoxmsm’ ... +** package ‘cmprskcoxmsm’ 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 -Warning: replacing previous import ‘ggplot2::ggpar’ by ‘ggpubr::ggpar’ when loading ‘csmpv’ Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace Execution halted -ERROR: lazy loading failed for package ‘csmpv’ -* removing ‘/tmp/workdir/csmpv/new/csmpv.Rcheck/csmpv’ +ERROR: lazy loading failed for package ‘cmprskcoxmsm’ +* removing ‘/tmp/workdir/cmprskcoxmsm/new/cmprskcoxmsm.Rcheck/cmprskcoxmsm’ ``` ### CRAN ``` -* installing *source* package ‘csmpv’ ... -** package ‘csmpv’ successfully unpacked and MD5 sums checked +* installing *source* package ‘cmprskcoxmsm’ ... +** package ‘cmprskcoxmsm’ 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]]) : namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace Execution halted -ERROR: lazy loading failed for package ‘csmpv’ -* removing ‘/tmp/workdir/csmpv/old/csmpv.Rcheck/csmpv’ +ERROR: lazy loading failed for package ‘cmprskcoxmsm’ +* removing ‘/tmp/workdir/cmprskcoxmsm/old/cmprskcoxmsm.Rcheck/cmprskcoxmsm’ ``` -# ctsem +# combiroc
-* Version: 3.9.1 -* GitHub: https://github.com/cdriveraus/ctsem -* Source code: https://github.com/cran/ctsem -* Date/Publication: 2023-10-30 14:20:02 UTC -* Number of recursive dependencies: 159 +* Version: 0.3.4 +* GitHub: https://github.com/ingmbioinfo/combiroc +* Source code: https://github.com/cran/combiroc +* Date/Publication: 2023-07-06 12:53:12 UTC +* Number of recursive dependencies: 160 -Run `revdepcheck::cloud_details(, "ctsem")` for more info +Run `revdepcheck::cloud_details(, "combiroc")` for more info
-## In both +## Error before installation -* checking whether package ‘ctsem’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/ctsem/new/ctsem.Rcheck/00install.out’ for details. - ``` +### Devel -## Installation +``` +* using log directory ‘/tmp/workdir/combiroc/new/combiroc.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘combiroc/DESCRIPTION’ ... OK +... -### Devel + When sourcing ‘combiroc_vignette_2.R’: +Error: Cannot find the file(s): "/tmp/Rtmpkgsj1K/file17bc502b97ef/vignettes/vignettes/atlas_dimplot.png" +Execution halted + + ‘combiroc_vignette_1.Rmd’ using ‘UTF-8’... OK + ‘combiroc_vignette_2.Rmd’ using ‘UTF-8’... failed +* checking re-building of vignette outputs ... OK +* DONE +Status: 1 ERROR, 1 NOTE -``` -* installing *source* package ‘ctsem’ ... -** package ‘ctsem’ successfully unpacked and MD5 sums checked -** using staged installation -** libs -using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ -using C++17 -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I"../inst/include" -I"/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src" -DBOOST_DISABLE_ASSERTS -DEIGEN_NO_DEBUG -DBOOST_MATH_OVERFLOW_ERROR_POLICY=errno_on_error -DUSE_STANC3 -D_HAS_AUTO_PTR_ETC=0 -I'/opt/R/4.3.1/lib/R/site-library/BH/include' -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppEigen/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -I'/opt/R/4.3.1/lib/R/site-library/rstan/include' -I'/opt/R/4.3.1/lib/R/site-library/StanHeaders/include' -I/usr/local/include -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -D_REENTRANT -DSTAN_THREADS -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o -In file included from /opt/R/4.3.1/lib/R/site-library/RcppEigen/include/Eigen/Core:205, -... -/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src/stan/mcmc/hmc/hamiltonians/dense_e_metric.hpp:22:56: required from ‘double stan::mcmc::dense_e_metric::T(stan::mcmc::dense_e_point&) [with Model = model_ctsm_namespace::model_ctsm; BaseRNG = boost::random::additive_combine_engine, boost::random::linear_congruential_engine >]’ -/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src/stan/mcmc/hmc/hamiltonians/dense_e_metric.hpp:21:10: required from here -/opt/R/4.3.1/lib/R/site-library/RcppEigen/include/Eigen/src/Core/DenseCoeffsBase.h:654:34: warning: ignoring attributes on template argument ‘Eigen::internal::packet_traits::type’ {aka ‘__vector(2) double’} [-Wignored-attributes] - 654 | return internal::first_aligned::alignment),Derived>(m); - | ^~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -g++: fatal error: Killed signal terminated program cc1plus -compilation terminated. -make: *** [/opt/R/4.3.1/lib/R/etc/Makeconf:198: stanExports_ctsm.o] Error 1 -ERROR: compilation failed for package ‘ctsem’ -* removing ‘/tmp/workdir/ctsem/new/ctsem.Rcheck/ctsem’ ``` ### CRAN ``` -* installing *source* package ‘ctsem’ ... -** package ‘ctsem’ successfully unpacked and MD5 sums checked -** using staged installation -** libs -using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ -using C++17 +* using log directory ‘/tmp/workdir/combiroc/old/combiroc.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘combiroc/DESCRIPTION’ ... OK +... + + When sourcing ‘combiroc_vignette_2.R’: +Error: Cannot find the file(s): "/tmp/Rtmp21gOJ2/file108d3edb788a/vignettes/vignettes/atlas_dimplot.png" +Execution halted + + ‘combiroc_vignette_1.Rmd’ using ‘UTF-8’... OK + ‘combiroc_vignette_2.Rmd’ using ‘UTF-8’... failed +* checking re-building of vignette outputs ... OK +* DONE +Status: 1 ERROR, 1 NOTE + -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I"../inst/include" -I"/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src" -DBOOST_DISABLE_ASSERTS -DEIGEN_NO_DEBUG -DBOOST_MATH_OVERFLOW_ERROR_POLICY=errno_on_error -DUSE_STANC3 -D_HAS_AUTO_PTR_ETC=0 -I'/opt/R/4.3.1/lib/R/site-library/BH/include' -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppEigen/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -I'/opt/R/4.3.1/lib/R/site-library/rstan/include' -I'/opt/R/4.3.1/lib/R/site-library/StanHeaders/include' -I/usr/local/include -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -D_REENTRANT -DSTAN_THREADS -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o -In file included from /opt/R/4.3.1/lib/R/site-library/RcppEigen/include/Eigen/Core:205, -... -/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src/stan/mcmc/hmc/hamiltonians/dense_e_metric.hpp:22:56: required from ‘double stan::mcmc::dense_e_metric::T(stan::mcmc::dense_e_point&) [with Model = model_ctsm_namespace::model_ctsm; BaseRNG = boost::random::additive_combine_engine, boost::random::linear_congruential_engine >]’ -/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src/stan/mcmc/hmc/hamiltonians/dense_e_metric.hpp:21:10: required from here -/opt/R/4.3.1/lib/R/site-library/RcppEigen/include/Eigen/src/Core/DenseCoeffsBase.h:654:34: warning: ignoring attributes on template argument ‘Eigen::internal::packet_traits::type’ {aka ‘__vector(2) double’} [-Wignored-attributes] - 654 | return internal::first_aligned::alignment),Derived>(m); - | ^~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -g++: fatal error: Killed signal terminated program cc1plus -compilation terminated. -make: *** [/opt/R/4.3.1/lib/R/etc/Makeconf:198: stanExports_ctsm.o] Error 1 -ERROR: compilation failed for package ‘ctsem’ -* removing ‘/tmp/workdir/ctsem/old/ctsem.Rcheck/ctsem’ ``` -# DepthProc +# conos
-* Version: 2.1.5 -* GitHub: https://github.com/zzawadz/DepthProc -* Source code: https://github.com/cran/DepthProc -* Date/Publication: 2022-02-03 20:30:02 UTC -* Number of recursive dependencies: 134 +* Version: 1.5.2 +* GitHub: https://github.com/kharchenkolab/conos +* Source code: https://github.com/cran/conos +* Date/Publication: 2024-02-26 19:30:05 UTC +* Number of recursive dependencies: 239 -Run `revdepcheck::cloud_details(, "DepthProc")` for more info +Run `revdepcheck::cloud_details(, "conos")` for more info
-## In both - -* checking whether package ‘DepthProc’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/DepthProc/new/DepthProc.Rcheck/00install.out’ for details. - ``` - -## Installation +## Error before installation ### Devel ``` -* installing *source* package ‘DepthProc’ ... -** package ‘DepthProc’ successfully unpacked and MD5 sums checked -** using staged installation -** libs -using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ -using C++11 -g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c Depth.cpp -o Depth.o -g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c LocationEstimators.cpp -o LocationEstimators.o -g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c LocationScaleDepth.cpp -o LocationScaleDepth.o -g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c LocationScaleDepthCPP.cpp -o LocationScaleDepthCPP.o +* using log directory ‘/tmp/workdir/conos/new/conos.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘conos/DESCRIPTION’ ... OK ... -installing to /tmp/workdir/DepthProc/new/DepthProc.Rcheck/00LOCK-DepthProc/00new/DepthProc/libs -** R -** data -** inst -** byte-compile and prepare package for lazy loading -Error: package or namespace load failed for ‘np’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Execution halted -ERROR: lazy loading failed for package ‘DepthProc’ -* removing ‘/tmp/workdir/DepthProc/new/DepthProc.Rcheck/DepthProc’ +* checking for GNU extensions in Makefiles ... OK +* checking for portable use of $(BLAS_LIBS) and $(LAPACK_LIBS) ... OK +* checking use of PKG_*FLAGS in Makefiles ... OK +* checking compiled code ... OK +* checking examples ... OK +* checking for unstated dependencies in ‘tests’ ... OK +* checking tests ... OK + Running ‘testthat.R’ +* DONE +Status: 2 NOTEs + + + ``` ### CRAN ``` -* installing *source* package ‘DepthProc’ ... -** package ‘DepthProc’ successfully unpacked and MD5 sums checked -** using staged installation -** libs -using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ -using C++11 -g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c Depth.cpp -o Depth.o -g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c LocationEstimators.cpp -o LocationEstimators.o -g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c LocationScaleDepth.cpp -o LocationScaleDepth.o -g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c LocationScaleDepthCPP.cpp -o LocationScaleDepthCPP.o +* using log directory ‘/tmp/workdir/conos/old/conos.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘conos/DESCRIPTION’ ... OK ... -installing to /tmp/workdir/DepthProc/old/DepthProc.Rcheck/00LOCK-DepthProc/00new/DepthProc/libs -** R -** data -** inst -** byte-compile and prepare package for lazy loading -Error: package or namespace load failed for ‘np’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Execution halted -ERROR: lazy loading failed for package ‘DepthProc’ -* removing ‘/tmp/workdir/DepthProc/old/DepthProc.Rcheck/DepthProc’ +* checking for GNU extensions in Makefiles ... OK +* checking for portable use of $(BLAS_LIBS) and $(LAPACK_LIBS) ... OK +* checking use of PKG_*FLAGS in Makefiles ... OK +* checking compiled code ... OK +* checking examples ... OK +* checking for unstated dependencies in ‘tests’ ... OK +* checking tests ... OK + Running ‘testthat.R’ +* DONE +Status: 2 NOTEs + + + ``` -# DR.SC +# contrast
-* Version: 3.4 -* GitHub: https://github.com/feiyoung/DR.SC -* Source code: https://github.com/cran/DR.SC -* Date/Publication: 2024-03-19 08:40:02 UTC -* Number of recursive dependencies: 150 +* Version: 0.24.2 +* GitHub: https://github.com/Alanocallaghan/contrast +* Source code: https://github.com/cran/contrast +* Date/Publication: 2022-10-05 17:20:09 UTC +* Number of recursive dependencies: 111 -Run `revdepcheck::cloud_details(, "DR.SC")` for more info +Run `revdepcheck::cloud_details(, "contrast")` for more info
-## In both - -* checking whether package ‘DR.SC’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/DR.SC/new/DR.SC.Rcheck/00install.out’ for details. - ``` - -## Installation +## Error before installation ### Devel ``` -* installing *source* package ‘DR.SC’ ... -** package ‘DR.SC’ successfully unpacked and MD5 sums checked -** using staged installation -** libs -using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ -using C++17 -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -DARMA_64BIT_WORD -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -DARMA_64BIT_WORD -fpic -g -O2 -c getNB_fast.cpp -o getNB_fast.o -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -DARMA_64BIT_WORD -fpic -g -O2 -c mt_paral_job.cpp -o mt_paral_job.o -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -DARMA_64BIT_WORD -fpic -g -O2 -c mt_paral_job2.cpp -o mt_paral_job2.o +* using log directory ‘/tmp/workdir/contrast/new/contrast.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘contrast/DESCRIPTION’ ... OK ... -** R -** data -** inst -** byte-compile and prepare package for lazy loading -Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.3 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘DR.SC’ -* removing ‘/tmp/workdir/DR.SC/new/DR.SC.Rcheck/DR.SC’ +* this is package ‘contrast’ version ‘0.24.2’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘rms’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + ``` ### CRAN ``` -* installing *source* package ‘DR.SC’ ... -** package ‘DR.SC’ successfully unpacked and MD5 sums checked -** using staged installation -** libs -using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ -using C++17 -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -DARMA_64BIT_WORD -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -DARMA_64BIT_WORD -fpic -g -O2 -c getNB_fast.cpp -o getNB_fast.o -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -DARMA_64BIT_WORD -fpic -g -O2 -c mt_paral_job.cpp -o mt_paral_job.o -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -DARMA_64BIT_WORD -fpic -g -O2 -c mt_paral_job2.cpp -o mt_paral_job2.o +* using log directory ‘/tmp/workdir/contrast/old/contrast.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘contrast/DESCRIPTION’ ... OK ... -** R -** data -** inst -** byte-compile and prepare package for lazy loading -Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.3 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘DR.SC’ -* removing ‘/tmp/workdir/DR.SC/old/DR.SC.Rcheck/DR.SC’ +* this is package ‘contrast’ version ‘0.24.2’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘rms’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + ``` -# EcoEnsemble +# contsurvplot
-* Version: 1.0.5 -* GitHub: NA -* Source code: https://github.com/cran/EcoEnsemble -* Date/Publication: 2023-09-18 11:50:02 UTC -* Number of recursive dependencies: 91 +* Version: 0.2.1 +* GitHub: https://github.com/RobinDenz1/contsurvplot +* Source code: https://github.com/cran/contsurvplot +* Date/Publication: 2023-08-15 08:00:03 UTC +* Number of recursive dependencies: 157 -Run `revdepcheck::cloud_details(, "EcoEnsemble")` for more info +Run `revdepcheck::cloud_details(, "contsurvplot")` for more info
-## In both - -* checking whether package ‘EcoEnsemble’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/EcoEnsemble/new/EcoEnsemble.Rcheck/00install.out’ for details. - ``` - -## Installation +## Error before installation ### Devel ``` -* installing *source* package ‘EcoEnsemble’ ... -** package ‘EcoEnsemble’ successfully unpacked and MD5 sums checked -** using staged installation -** libs -using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ -using C++17 +* using log directory ‘/tmp/workdir/contsurvplot/new/contsurvplot.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘contsurvplot/DESCRIPTION’ ... OK +... +* this is package ‘contsurvplot’ version ‘0.2.1’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘riskRegression’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I"../inst/include" -I"/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src" -DBOOST_DISABLE_ASSERTS -DEIGEN_NO_DEBUG -DBOOST_MATH_OVERFLOW_ERROR_POLICY=errno_on_error -DUSE_STANC3 -D_HAS_AUTO_PTR_ETC=0 -I'/opt/R/4.3.1/lib/R/site-library/BH/include' -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppEigen/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -I'/opt/R/4.3.1/lib/R/site-library/rstan/include' -I'/opt/R/4.3.1/lib/R/site-library/StanHeaders/include' -I/usr/local/include -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -D_REENTRANT -DSTAN_THREADS -fpic -g -O2 -c KF_back.cpp -o KF_back.o -In file included from /opt/R/4.3.1/lib/R/site-library/RcppEigen/include/Eigen/Core:205, -... -/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src/stan/mcmc/hmc/hamiltonians/dense_e_metric.hpp:22:56: required from ‘double stan::mcmc::dense_e_metric::T(stan::mcmc::dense_e_point&) [with Model = model_ensemble_model_namespace::model_ensemble_model; BaseRNG = boost::random::additive_combine_engine, boost::random::linear_congruential_engine >]’ -/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src/stan/mcmc/hmc/hamiltonians/dense_e_metric.hpp:21:10: required from here -/opt/R/4.3.1/lib/R/site-library/RcppEigen/include/Eigen/src/Core/DenseCoeffsBase.h:654:34: warning: ignoring attributes on template argument ‘Eigen::internal::packet_traits::type’ {aka ‘__vector(2) double’} [-Wignored-attributes] - 654 | return internal::first_aligned::alignment),Derived>(m); - | ^~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -g++: fatal error: Killed signal terminated program cc1plus -compilation terminated. -make: *** [/opt/R/4.3.1/lib/R/etc/Makeconf:198: stanExports_ensemble_model.o] Error 1 -ERROR: compilation failed for package ‘EcoEnsemble’ -* removing ‘/tmp/workdir/EcoEnsemble/new/EcoEnsemble.Rcheck/EcoEnsemble’ ``` ### CRAN ``` -* installing *source* package ‘EcoEnsemble’ ... -** package ‘EcoEnsemble’ successfully unpacked and MD5 sums checked -** using staged installation -** libs -using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ -using C++17 - - -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I"../inst/include" -I"/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src" -DBOOST_DISABLE_ASSERTS -DEIGEN_NO_DEBUG -DBOOST_MATH_OVERFLOW_ERROR_POLICY=errno_on_error -DUSE_STANC3 -D_HAS_AUTO_PTR_ETC=0 -I'/opt/R/4.3.1/lib/R/site-library/BH/include' -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppEigen/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -I'/opt/R/4.3.1/lib/R/site-library/rstan/include' -I'/opt/R/4.3.1/lib/R/site-library/StanHeaders/include' -I/usr/local/include -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -D_REENTRANT -DSTAN_THREADS -fpic -g -O2 -c KF_back.cpp -o KF_back.o -In file included from /opt/R/4.3.1/lib/R/site-library/RcppEigen/include/Eigen/Core:205, +* using log directory ‘/tmp/workdir/contsurvplot/old/contsurvplot.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘contsurvplot/DESCRIPTION’ ... OK ... -/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src/stan/mcmc/hmc/hamiltonians/dense_e_metric.hpp:22:56: required from ‘double stan::mcmc::dense_e_metric::T(stan::mcmc::dense_e_point&) [with Model = model_ensemble_model_namespace::model_ensemble_model; BaseRNG = boost::random::additive_combine_engine, boost::random::linear_congruential_engine >]’ -/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src/stan/mcmc/hmc/hamiltonians/dense_e_metric.hpp:21:10: required from here -/opt/R/4.3.1/lib/R/site-library/RcppEigen/include/Eigen/src/Core/DenseCoeffsBase.h:654:34: warning: ignoring attributes on template argument ‘Eigen::internal::packet_traits::type’ {aka ‘__vector(2) double’} [-Wignored-attributes] - 654 | return internal::first_aligned::alignment),Derived>(m); - | ^~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -g++: fatal error: Killed signal terminated program cc1plus -compilation terminated. -make: *** [/opt/R/4.3.1/lib/R/etc/Makeconf:198: stanExports_ensemble_model.o] Error 1 -ERROR: compilation failed for package ‘EcoEnsemble’ -* removing ‘/tmp/workdir/EcoEnsemble/old/EcoEnsemble.Rcheck/EcoEnsemble’ +* this is package ‘contsurvplot’ version ‘0.2.1’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘riskRegression’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + ``` -# ecolottery +# countland
-* Version: 1.0.0 -* GitHub: https://github.com/frmunoz/ecolottery -* Source code: https://github.com/cran/ecolottery -* Date/Publication: 2017-07-03 11:01:29 UTC -* Number of recursive dependencies: 88 +* Version: 0.1.2 +* GitHub: https://github.com/shchurch/countland +* Source code: https://github.com/cran/countland +* Date/Publication: 2024-02-01 18:00:02 UTC +* Number of recursive dependencies: 198 -Run `revdepcheck::cloud_details(, "ecolottery")` for more info +Run `revdepcheck::cloud_details(, "countland")` for more info
-## In both - -* checking whether package ‘ecolottery’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/ecolottery/new/ecolottery.Rcheck/00install.out’ for details. - ``` - -## Installation +## Error before installation ### Devel ``` -* installing *source* package ‘ecolottery’ ... -** package ‘ecolottery’ 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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘ecolottery’ -* removing ‘/tmp/workdir/ecolottery/new/ecolottery.Rcheck/ecolottery’ +* using log directory ‘/tmp/workdir/countland/new/countland.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘countland/DESCRIPTION’ ... OK +... + 1. └─base::loadNamespace(x) at test-countland_subset.R:2:1 + 2. └─base::withRestarts(stop(cond), retry_loadNamespace = function() NULL) + 3. └─base (local) withOneRestart(expr, restarts[[1L]]) + 4. └─base (local) doWithOneRestart(return(expr), restart) + + [ FAIL 7 | WARN 0 | SKIP 0 | PASS 13 ] + Error: Test failures + Execution halted +* DONE +Status: 2 ERRORs, 1 NOTE + + + ``` ### CRAN ``` -* installing *source* package ‘ecolottery’ ... -** package ‘ecolottery’ 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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘ecolottery’ -* removing ‘/tmp/workdir/ecolottery/old/ecolottery.Rcheck/ecolottery’ +* using log directory ‘/tmp/workdir/countland/old/countland.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘countland/DESCRIPTION’ ... OK +... + 1. └─base::loadNamespace(x) at test-countland_subset.R:2:1 + 2. └─base::withRestarts(stop(cond), retry_loadNamespace = function() NULL) + 3. └─base (local) withOneRestart(expr, restarts[[1L]]) + 4. └─base (local) doWithOneRestart(return(expr), restart) + + [ FAIL 7 | WARN 0 | SKIP 0 | PASS 13 ] + Error: Test failures + Execution halted +* DONE +Status: 2 ERRORs, 1 NOTE + + + ``` -# EpiEstim +# coveffectsplot
-* Version: 2.2-4 -* GitHub: https://github.com/mrc-ide/EpiEstim -* Source code: https://github.com/cran/EpiEstim -* Date/Publication: 2021-01-07 16:20:10 UTC -* Number of recursive dependencies: 91 +* Version: 1.0.5 +* GitHub: https://github.com/smouksassi/coveffectsplot +* Source code: https://github.com/cran/coveffectsplot +* Date/Publication: 2024-01-18 14:10:02 UTC +* Number of recursive dependencies: 148 -Run `revdepcheck::cloud_details(, "EpiEstim")` for more info +Run `revdepcheck::cloud_details(, "coveffectsplot")` for more info
-## In both - -* checking whether package ‘EpiEstim’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/EpiEstim/new/EpiEstim.Rcheck/00install.out’ for details. - ``` - -## Installation +## Error before installation ### Devel ``` -* installing *source* package ‘EpiEstim’ ... -** package ‘EpiEstim’ successfully unpacked and MD5 sums checked -** 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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +* using log directory ‘/tmp/workdir/coveffectsplot/new/coveffectsplot.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘coveffectsplot/DESCRIPTION’ ... OK +... +--- finished re-building ‘introduction_to_coveffectsplot.Rmd’ + +SUMMARY: processing the following files failed: + ‘Exposure_Response_Example.Rmd’ ‘Pediatric_Cov_Sim.Rmd’ + +Error: Vignette re-building failed. Execution halted -ERROR: lazy loading failed for package ‘EpiEstim’ -* removing ‘/tmp/workdir/EpiEstim/new/EpiEstim.Rcheck/EpiEstim’ + +* DONE +Status: 1 WARNING, 2 NOTEs + + + ``` ### CRAN ``` -* installing *source* package ‘EpiEstim’ ... -** package ‘EpiEstim’ successfully unpacked and MD5 sums checked -** 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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +* using log directory ‘/tmp/workdir/coveffectsplot/old/coveffectsplot.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘coveffectsplot/DESCRIPTION’ ... OK +... +--- finished re-building ‘introduction_to_coveffectsplot.Rmd’ + +SUMMARY: processing the following file failed: + ‘Pediatric_Cov_Sim.Rmd’ + +Error: Vignette re-building failed. Execution halted -ERROR: lazy loading failed for package ‘EpiEstim’ -* removing ‘/tmp/workdir/EpiEstim/old/EpiEstim.Rcheck/EpiEstim’ + +* DONE +Status: 1 WARNING, 2 NOTEs + + + ``` -# evolqg +# coxed
-* Version: 0.3-4 -* GitHub: https://github.com/lem-usp/evolqg -* Source code: https://github.com/cran/evolqg -* Date/Publication: 2023-12-05 15:20:12 UTC -* Number of recursive dependencies: 111 +* Version: 0.3.3 +* GitHub: https://github.com/jkropko/coxed +* Source code: https://github.com/cran/coxed +* Date/Publication: 2020-08-02 01:20:07 UTC +* Number of recursive dependencies: 109 -Run `revdepcheck::cloud_details(, "evolqg")` for more info +Run `revdepcheck::cloud_details(, "coxed")` for more info
-## In both - -* checking whether package ‘evolqg’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/evolqg/new/evolqg.Rcheck/00install.out’ for details. - ``` - -## Installation +## Error before installation ### Devel ``` -* installing *source* package ‘evolqg’ ... -** package ‘evolqg’ successfully unpacked and MD5 sums checked -** using staged installation -** libs -using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c fast_RS.cpp -o fast_RS.o -g++ -std=gnu++17 -shared -L/opt/R/4.3.1/lib/R/lib -L/usr/local/lib -o evolqg.so RcppExports.o fast_RS.o -llapack -lblas -lgfortran -lm -lquadmath -L/opt/R/4.3.1/lib/R/lib -lR -installing to /tmp/workdir/evolqg/new/evolqg.Rcheck/00LOCK-evolqg/00new/evolqg/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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘evolqg’ -* removing ‘/tmp/workdir/evolqg/new/evolqg.Rcheck/evolqg’ +* using log directory ‘/tmp/workdir/coxed/new/coxed.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘coxed/DESCRIPTION’ ... OK +... +* this is package ‘coxed’ version ‘0.3.3’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘rms’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + ``` ### CRAN ``` -* installing *source* package ‘evolqg’ ... -** package ‘evolqg’ successfully unpacked and MD5 sums checked -** using staged installation -** libs -using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c fast_RS.cpp -o fast_RS.o -g++ -std=gnu++17 -shared -L/opt/R/4.3.1/lib/R/lib -L/usr/local/lib -o evolqg.so RcppExports.o fast_RS.o -llapack -lblas -lgfortran -lm -lquadmath -L/opt/R/4.3.1/lib/R/lib -lR -installing to /tmp/workdir/evolqg/old/evolqg.Rcheck/00LOCK-evolqg/00new/evolqg/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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘evolqg’ -* removing ‘/tmp/workdir/evolqg/old/evolqg.Rcheck/evolqg’ +* using log directory ‘/tmp/workdir/coxed/old/coxed.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘coxed/DESCRIPTION’ ... OK +... +* this is package ‘coxed’ version ‘0.3.3’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘rms’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + ``` -# ForecastComb +# CRMetrics
-* Version: 1.3.1 -* GitHub: https://github.com/ceweiss/ForecastComb -* Source code: https://github.com/cran/ForecastComb -* Date/Publication: 2018-08-07 13:50:08 UTC -* Number of recursive dependencies: 73 +* Version: 0.3.0 +* GitHub: https://github.com/khodosevichlab/CRMetrics +* Source code: https://github.com/cran/CRMetrics +* Date/Publication: 2023-09-01 09:00:06 UTC +* Number of recursive dependencies: 234 -Run `revdepcheck::cloud_details(, "ForecastComb")` for more info +Run `revdepcheck::cloud_details(, "CRMetrics")` for more info
-## In both - -* checking whether package ‘ForecastComb’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/ForecastComb/new/ForecastComb.Rcheck/00install.out’ for details. - ``` - -## Installation +## Error before installation ### Devel ``` -* installing *source* package ‘ForecastComb’ ... -** package ‘ForecastComb’ successfully unpacked and MD5 sums checked -** using staged installation -** R -** data -*** moving datasets to lazyload DB -** byte-compile and prepare package for lazy loading -Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘ForecastComb’ -* removing ‘/tmp/workdir/ForecastComb/new/ForecastComb.Rcheck/ForecastComb’ +* using log directory ‘/tmp/workdir/CRMetrics/new/CRMetrics.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘CRMetrics/DESCRIPTION’ ... OK +... +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘ggpmisc’ + +Package suggested but not available for checking: ‘Seurat’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + ``` ### CRAN ``` -* installing *source* package ‘ForecastComb’ ... -** package ‘ForecastComb’ successfully unpacked and MD5 sums checked -** using staged installation -** R -** data -*** moving datasets to lazyload DB -** byte-compile and prepare package for lazy loading -Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘ForecastComb’ -* removing ‘/tmp/workdir/ForecastComb/old/ForecastComb.Rcheck/ForecastComb’ +* using log directory ‘/tmp/workdir/CRMetrics/old/CRMetrics.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘CRMetrics/DESCRIPTION’ ... OK +... +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘ggpmisc’ +Package suggested but not available for checking: ‘Seurat’ -``` -# gapfill +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR -
-* Version: 0.9.6-1 -* GitHub: https://github.com/florafauna/gapfill -* Source code: https://github.com/cran/gapfill -* Date/Publication: 2021-02-12 10:10:05 UTC -* Number of recursive dependencies: 71 -Run `revdepcheck::cloud_details(, "gapfill")` for more info -
-## In both +``` +# crosslag -* checking whether package ‘gapfill’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/gapfill/new/gapfill.Rcheck/00install.out’ for details. - ``` +
-* checking package dependencies ... NOTE - ``` - Packages which this enhances but not available for checking: - 'raster', 'doParallel', 'doMPI' - ``` +* Version: 0.1.0 +* GitHub: NA +* Source code: https://github.com/cran/crosslag +* Date/Publication: 2024-05-17 10:10:03 UTC +* Number of recursive dependencies: 122 -## Installation +Run `revdepcheck::cloud_details(, "crosslag")` for more info + +
+ +## Error before installation ### Devel ``` -* installing *source* package ‘gapfill’ ... -** package ‘gapfill’ successfully unpacked and MD5 sums checked -** using staged installation -** libs -using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c gapfill.cpp -o gapfill.o -g++ -std=gnu++17 -shared -L/opt/R/4.3.1/lib/R/lib -L/usr/local/lib -o gapfill.so RcppExports.o gapfill.o -L/opt/R/4.3.1/lib/R/lib -lR -installing to /tmp/workdir/gapfill/new/gapfill.Rcheck/00LOCK-gapfill/00new/gapfill/libs -** R +* using log directory ‘/tmp/workdir/crosslag/new/crosslag.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘crosslag/DESCRIPTION’ ... OK ... -** 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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘gapfill’ -* removing ‘/tmp/workdir/gapfill/new/gapfill.Rcheck/gapfill’ +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘rms’ + +Packages required and available but unsuitable versions: 'mgcv', 'stats' + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + ``` ### CRAN ``` -* installing *source* package ‘gapfill’ ... -** package ‘gapfill’ successfully unpacked and MD5 sums checked -** using staged installation -** libs -using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c gapfill.cpp -o gapfill.o -g++ -std=gnu++17 -shared -L/opt/R/4.3.1/lib/R/lib -L/usr/local/lib -o gapfill.so RcppExports.o gapfill.o -L/opt/R/4.3.1/lib/R/lib -lR -installing to /tmp/workdir/gapfill/old/gapfill.Rcheck/00LOCK-gapfill/00new/gapfill/libs -** R +* using log directory ‘/tmp/workdir/crosslag/old/crosslag.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘crosslag/DESCRIPTION’ ... OK ... -** 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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘gapfill’ -* removing ‘/tmp/workdir/gapfill/old/gapfill.Rcheck/gapfill’ +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘rms’ + +Packages required and available but unsuitable versions: 'mgcv', 'stats' + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + ``` -# GeomComb +# csmpv
-* Version: 1.0 -* GitHub: https://github.com/ceweiss/GeomComb -* Source code: https://github.com/cran/GeomComb -* Date/Publication: 2016-11-27 16:02:26 -* Number of recursive dependencies: 74 +* Version: 1.0.3 +* GitHub: NA +* Source code: https://github.com/cran/csmpv +* Date/Publication: 2024-03-01 18:12:44 UTC +* Number of recursive dependencies: 175 -Run `revdepcheck::cloud_details(, "GeomComb")` for more info +Run `revdepcheck::cloud_details(, "csmpv")` for more info
-## In both - -* checking whether package ‘GeomComb’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/GeomComb/new/GeomComb.Rcheck/00install.out’ for details. - ``` - -## Installation +## Error before installation ### Devel ``` -* installing *source* package ‘GeomComb’ ... -** package ‘GeomComb’ successfully unpacked and MD5 sums checked -** using staged installation -** R -** byte-compile and prepare package for lazy loading -Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘GeomComb’ -* removing ‘/tmp/workdir/GeomComb/new/GeomComb.Rcheck/GeomComb’ +* using log directory ‘/tmp/workdir/csmpv/new/csmpv.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘csmpv/DESCRIPTION’ ... OK +... +* this is package ‘csmpv’ version ‘1.0.3’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘rms’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + ``` ### CRAN ``` -* installing *source* package ‘GeomComb’ ... -** package ‘GeomComb’ successfully unpacked and MD5 sums checked -** using staged installation -** R -** byte-compile and prepare package for lazy loading -Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘GeomComb’ -* removing ‘/tmp/workdir/GeomComb/old/GeomComb.Rcheck/GeomComb’ +* using log directory ‘/tmp/workdir/csmpv/old/csmpv.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘csmpv/DESCRIPTION’ ... OK +... +* this is package ‘csmpv’ version ‘1.0.3’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘rms’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + ``` -# geostan +# ctsem
-* Version: 0.6.0 -* GitHub: https://github.com/ConnorDonegan/geostan -* Source code: https://github.com/cran/geostan -* Date/Publication: 2024-04-16 14:00:02 UTC -* Number of recursive dependencies: 108 +* Version: 3.10.0 +* GitHub: https://github.com/cdriveraus/ctsem +* Source code: https://github.com/cran/ctsem +* Date/Publication: 2024-05-09 14:40:03 UTC +* Number of recursive dependencies: 159 -Run `revdepcheck::cloud_details(, "geostan")` for more info +Run `revdepcheck::cloud_details(, "ctsem")` for more info
## In both -* checking whether package ‘geostan’ can be installed ... ERROR +* checking whether package ‘ctsem’ can be installed ... ERROR ``` Installation failed. - See ‘/tmp/workdir/geostan/new/geostan.Rcheck/00install.out’ for details. + See ‘/tmp/workdir/ctsem/new/ctsem.Rcheck/00install.out’ for details. ``` ## Installation @@ -2381,263 +3062,229 @@ Run `revdepcheck::cloud_details(, "geostan")` for more info ### Devel ``` -* installing *source* package ‘geostan’ ... -** package ‘geostan’ successfully unpacked and MD5 sums checked +* installing *source* package ‘ctsem’ ... +** package ‘ctsem’ successfully unpacked and MD5 sums checked ** using staged installation ** libs -using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ +using C++ compiler: ‘g++ (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ using C++17 g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I"../inst/include" -I"/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src" -DBOOST_DISABLE_ASSERTS -DEIGEN_NO_DEBUG -DBOOST_MATH_OVERFLOW_ERROR_POLICY=errno_on_error -DUSE_STANC3 -D_HAS_AUTO_PTR_ETC=0 -I'/opt/R/4.3.1/lib/R/site-library/BH/include' -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppEigen/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -I'/opt/R/4.3.1/lib/R/site-library/rstan/include' -I'/opt/R/4.3.1/lib/R/site-library/StanHeaders/include' -I/usr/local/include -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -D_REENTRANT -DSTAN_THREADS -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o In file included from /opt/R/4.3.1/lib/R/site-library/RcppEigen/include/Eigen/Core:205, ... -/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src/stan/mcmc/hmc/hamiltonians/dense_e_metric.hpp:22:56: required from ‘double stan::mcmc::dense_e_metric::T(stan::mcmc::dense_e_point&) [with Model = model_foundation_namespace::model_foundation; BaseRNG = boost::random::additive_combine_engine, boost::random::linear_congruential_engine >]’ +/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src/stan/mcmc/hmc/hamiltonians/dense_e_metric.hpp:22:56: required from ‘double stan::mcmc::dense_e_metric::T(stan::mcmc::dense_e_point&) [with Model = model_ctsm_namespace::model_ctsm; BaseRNG = boost::random::additive_combine_engine, boost::random::linear_congruential_engine >]’ /opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src/stan/mcmc/hmc/hamiltonians/dense_e_metric.hpp:21:10: required from here -/opt/R/4.3.1/lib/R/site-library/RcppEigen/include/Eigen/src/Core/DenseCoeffsBase.h:654:34: warning: ignoring attributes on template argument ‘Eigen::internal::packet_traits::type’ {aka ‘__vector(2) double’} [-Wignored-attributes] +/opt/R/4.3.1/lib/R/site-library/RcppEigen/include/Eigen/src/Core/DenseCoeffsBase.h:654:74: warning: ignoring attributes on template argument ‘Eigen::internal::packet_traits::type’ {aka ‘__m128d’} [-Wignored-attributes] 654 | return internal::first_aligned::alignment),Derived>(m); - | ^~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ + | ^~~~~~~~~ g++: fatal error: Killed signal terminated program cc1plus compilation terminated. -make: *** [/opt/R/4.3.1/lib/R/etc/Makeconf:198: stanExports_foundation.o] Error 1 -ERROR: compilation failed for package ‘geostan’ -* removing ‘/tmp/workdir/geostan/new/geostan.Rcheck/geostan’ +make: *** [/opt/R/4.3.1/lib/R/etc/Makeconf:198: stanExports_ctsm.o] Error 1 +ERROR: compilation failed for package ‘ctsem’ +* removing ‘/tmp/workdir/ctsem/new/ctsem.Rcheck/ctsem’ ``` ### CRAN ``` -* installing *source* package ‘geostan’ ... -** package ‘geostan’ successfully unpacked and MD5 sums checked +* installing *source* package ‘ctsem’ ... +** package ‘ctsem’ successfully unpacked and MD5 sums checked ** using staged installation ** libs -using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ +using C++ compiler: ‘g++ (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ using C++17 g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I"../inst/include" -I"/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src" -DBOOST_DISABLE_ASSERTS -DEIGEN_NO_DEBUG -DBOOST_MATH_OVERFLOW_ERROR_POLICY=errno_on_error -DUSE_STANC3 -D_HAS_AUTO_PTR_ETC=0 -I'/opt/R/4.3.1/lib/R/site-library/BH/include' -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppEigen/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -I'/opt/R/4.3.1/lib/R/site-library/rstan/include' -I'/opt/R/4.3.1/lib/R/site-library/StanHeaders/include' -I/usr/local/include -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -D_REENTRANT -DSTAN_THREADS -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o In file included from /opt/R/4.3.1/lib/R/site-library/RcppEigen/include/Eigen/Core:205, ... -/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src/stan/mcmc/hmc/hamiltonians/dense_e_metric.hpp:22:56: required from ‘double stan::mcmc::dense_e_metric::T(stan::mcmc::dense_e_point&) [with Model = model_foundation_namespace::model_foundation; BaseRNG = boost::random::additive_combine_engine, boost::random::linear_congruential_engine >]’ +/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src/stan/mcmc/hmc/hamiltonians/dense_e_metric.hpp:22:56: required from ‘double stan::mcmc::dense_e_metric::T(stan::mcmc::dense_e_point&) [with Model = model_ctsm_namespace::model_ctsm; BaseRNG = boost::random::additive_combine_engine, boost::random::linear_congruential_engine >]’ /opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src/stan/mcmc/hmc/hamiltonians/dense_e_metric.hpp:21:10: required from here -/opt/R/4.3.1/lib/R/site-library/RcppEigen/include/Eigen/src/Core/DenseCoeffsBase.h:654:34: warning: ignoring attributes on template argument ‘Eigen::internal::packet_traits::type’ {aka ‘__vector(2) double’} [-Wignored-attributes] +/opt/R/4.3.1/lib/R/site-library/RcppEigen/include/Eigen/src/Core/DenseCoeffsBase.h:654:74: warning: ignoring attributes on template argument ‘Eigen::internal::packet_traits::type’ {aka ‘__m128d’} [-Wignored-attributes] 654 | return internal::first_aligned::alignment),Derived>(m); - | ^~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ + | ^~~~~~~~~ g++: fatal error: Killed signal terminated program cc1plus compilation terminated. -make: *** [/opt/R/4.3.1/lib/R/etc/Makeconf:198: stanExports_foundation.o] Error 1 -ERROR: compilation failed for package ‘geostan’ -* removing ‘/tmp/workdir/geostan/old/geostan.Rcheck/geostan’ +make: *** [/opt/R/4.3.1/lib/R/etc/Makeconf:198: stanExports_ctsm.o] Error 1 +ERROR: compilation failed for package ‘ctsem’ +* removing ‘/tmp/workdir/ctsem/old/ctsem.Rcheck/ctsem’ ``` -# ggpmisc +# CytoSimplex
-* Version: 0.5.5 -* GitHub: https://github.com/aphalo/ggpmisc -* Source code: https://github.com/cran/ggpmisc -* Date/Publication: 2023-11-15 09:30:02 UTC -* Number of recursive dependencies: 109 +* Version: 0.1.1 +* GitHub: https://github.com/welch-lab/CytoSimplex +* Source code: https://github.com/cran/CytoSimplex +* Date/Publication: 2023-12-15 09:30:06 UTC +* Number of recursive dependencies: 177 -Run `revdepcheck::cloud_details(, "ggpmisc")` for more info +Run `revdepcheck::cloud_details(, "CytoSimplex")` for more info
-## In both +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/CytoSimplex/new/CytoSimplex.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘CytoSimplex/DESCRIPTION’ ... OK +... +* checking for unstated dependencies in ‘tests’ ... OK +* checking tests ... OK + Running ‘testthat.R’ +* checking for unstated dependencies in vignettes ... OK +* checking package vignettes in ‘inst/doc’ ... OK +* checking running R code from vignettes ... OK + ‘CytoSimplex.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 2 NOTEs + -* checking whether package ‘ggpmisc’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/ggpmisc/new/ggpmisc.Rcheck/00install.out’ for details. - ``` -## Installation - -### Devel - -``` -* installing *source* package ‘ggpmisc’ ... -** package ‘ggpmisc’ 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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘ggpmisc’ -* removing ‘/tmp/workdir/ggpmisc/new/ggpmisc.Rcheck/ggpmisc’ ``` ### CRAN ``` -* installing *source* package ‘ggpmisc’ ... -** package ‘ggpmisc’ 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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘ggpmisc’ -* removing ‘/tmp/workdir/ggpmisc/old/ggpmisc.Rcheck/ggpmisc’ +* using log directory ‘/tmp/workdir/CytoSimplex/old/CytoSimplex.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘CytoSimplex/DESCRIPTION’ ... OK +... +* checking for unstated dependencies in ‘tests’ ... OK +* checking tests ... OK + Running ‘testthat.R’ +* checking for unstated dependencies in vignettes ... OK +* checking package vignettes in ‘inst/doc’ ... OK +* checking running R code from vignettes ... OK + ‘CytoSimplex.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 2 NOTEs + + + ``` -# ggrcs +# depigner
-* Version: 0.3.8 -* GitHub: NA -* Source code: https://github.com/cran/ggrcs -* Date/Publication: 2024-01-30 03:20:08 UTC -* Number of recursive dependencies: 78 +* Version: 0.9.1 +* GitHub: https://github.com/CorradoLanera/depigner +* Source code: https://github.com/cran/depigner +* Date/Publication: 2023-04-24 12:40:05 UTC +* Number of recursive dependencies: 132 -Run `revdepcheck::cloud_details(, "ggrcs")` for more info +Run `revdepcheck::cloud_details(, "depigner")` for more info
-## In both - -* checking whether package ‘ggrcs’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/ggrcs/new/ggrcs.Rcheck/00install.out’ for details. - ``` - -## Installation +## Error before installation ### Devel ``` -* installing *source* package ‘ggrcs’ ... -** package ‘ggrcs’ 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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘ggrcs’ -* removing ‘/tmp/workdir/ggrcs/new/ggrcs.Rcheck/ggrcs’ - - -``` -### CRAN - -``` -* installing *source* package ‘ggrcs’ ... -** package ‘ggrcs’ 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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘ggrcs’ -* removing ‘/tmp/workdir/ggrcs/old/ggrcs.Rcheck/ggrcs’ - - -``` -# ggrisk - -
- -* Version: 1.3 -* GitHub: https://github.com/yikeshu0611/ggrisk -* Source code: https://github.com/cran/ggrisk -* Date/Publication: 2021-08-09 07:40:06 UTC -* Number of recursive dependencies: 115 +* using log directory ‘/tmp/workdir/depigner/new/depigner.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘depigner/DESCRIPTION’ ... OK +... +* this is package ‘depigner’ version ‘0.9.1’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘rms’ -Run `revdepcheck::cloud_details(, "ggrisk")` for more info +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR -
-## In both -* checking whether package ‘ggrisk’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/ggrisk/new/ggrisk.Rcheck/00install.out’ for details. - ``` -## Installation -### Devel +``` +### CRAN ``` -* installing *source* package ‘ggrisk’ ... -** package ‘ggrisk’ successfully unpacked and MD5 sums checked -** using staged installation -** R -** data -*** moving datasets to lazyload DB -** byte-compile and prepare package for lazy loading -Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘ggrisk’ -* removing ‘/tmp/workdir/ggrisk/new/ggrisk.Rcheck/ggrisk’ +* using log directory ‘/tmp/workdir/depigner/old/depigner.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘depigner/DESCRIPTION’ ... OK +... +* this is package ‘depigner’ version ‘0.9.1’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘rms’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR -``` -### CRAN -``` -* installing *source* package ‘ggrisk’ ... -** package ‘ggrisk’ successfully unpacked and MD5 sums checked -** using staged installation -** R -** data -*** moving datasets to lazyload DB -** byte-compile and prepare package for lazy loading -Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘ggrisk’ -* removing ‘/tmp/workdir/ggrisk/old/ggrisk.Rcheck/ggrisk’ ``` -# gJLS2 +# DepthProc
-* Version: 0.2.0 -* GitHub: NA -* Source code: https://github.com/cran/gJLS2 -* Date/Publication: 2021-09-30 09:00:05 UTC -* Number of recursive dependencies: 45 +* Version: 2.1.5 +* GitHub: https://github.com/zzawadz/DepthProc +* Source code: https://github.com/cran/DepthProc +* Date/Publication: 2022-02-03 20:30:02 UTC +* Number of recursive dependencies: 134 -Run `revdepcheck::cloud_details(, "gJLS2")` for more info +Run `revdepcheck::cloud_details(, "DepthProc")` for more info
## In both -* checking whether package ‘gJLS2’ can be installed ... ERROR +* checking whether package ‘DepthProc’ can be installed ... ERROR ``` Installation failed. - See ‘/tmp/workdir/gJLS2/new/gJLS2.Rcheck/00install.out’ for details. + See ‘/tmp/workdir/DepthProc/new/DepthProc.Rcheck/00install.out’ for details. ``` ## Installation @@ -2645,373 +3292,457 @@ Run `revdepcheck::cloud_details(, "gJLS2")` for more info ### Devel ``` -* installing *source* package ‘gJLS2’ ... -** package ‘gJLS2’ successfully unpacked and MD5 sums checked +* installing *source* package ‘DepthProc’ ... +** package ‘DepthProc’ successfully unpacked and MD5 sums checked ** using staged installation +** libs +using C++ compiler: ‘g++ (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ +using C++11 +g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c Depth.cpp -o Depth.o +g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c LocationEstimators.cpp -o LocationEstimators.o +g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c LocationScaleDepth.cpp -o LocationScaleDepth.o +g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c LocationScaleDepthCPP.cpp -o LocationScaleDepthCPP.o +... +installing to /tmp/workdir/DepthProc/new/DepthProc.Rcheck/00LOCK-DepthProc/00new/DepthProc/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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Error: package or namespace load failed for ‘np’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): + there is no package called ‘quantreg’ Execution halted -ERROR: lazy loading failed for package ‘gJLS2’ -* removing ‘/tmp/workdir/gJLS2/new/gJLS2.Rcheck/gJLS2’ +ERROR: lazy loading failed for package ‘DepthProc’ +* removing ‘/tmp/workdir/DepthProc/new/DepthProc.Rcheck/DepthProc’ ``` ### CRAN ``` -* installing *source* package ‘gJLS2’ ... -** package ‘gJLS2’ successfully unpacked and MD5 sums checked +* installing *source* package ‘DepthProc’ ... +** package ‘DepthProc’ successfully unpacked and MD5 sums checked ** using staged installation +** libs +using C++ compiler: ‘g++ (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ +using C++11 +g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c Depth.cpp -o Depth.o +g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c LocationEstimators.cpp -o LocationEstimators.o +g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c LocationScaleDepth.cpp -o LocationScaleDepth.o +g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c LocationScaleDepthCPP.cpp -o LocationScaleDepthCPP.o +... +installing to /tmp/workdir/DepthProc/old/DepthProc.Rcheck/00LOCK-DepthProc/00new/DepthProc/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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Error: package or namespace load failed for ‘np’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): + there is no package called ‘quantreg’ Execution halted -ERROR: lazy loading failed for package ‘gJLS2’ -* removing ‘/tmp/workdir/gJLS2/old/gJLS2.Rcheck/gJLS2’ +ERROR: lazy loading failed for package ‘DepthProc’ +* removing ‘/tmp/workdir/DepthProc/old/DepthProc.Rcheck/DepthProc’ ``` -# Greg +# DIscBIO
-* Version: 2.0.2 -* GitHub: https://github.com/gforge/Greg -* Source code: https://github.com/cran/Greg -* Date/Publication: 2024-01-29 13:30:21 UTC -* Number of recursive dependencies: 152 +* Version: 1.2.2 +* GitHub: https://github.com/ocbe-uio/DIscBIO +* Source code: https://github.com/cran/DIscBIO +* Date/Publication: 2023-11-06 10:50:02 UTC +* Number of recursive dependencies: 209 -Run `revdepcheck::cloud_details(, "Greg")` for more info +Run `revdepcheck::cloud_details(, "DIscBIO")` for more info
-## In both - -* checking whether package ‘Greg’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/Greg/new/Greg.Rcheck/00install.out’ for details. - ``` - -## Installation +## Error before installation ### Devel ``` -* installing *source* package ‘Greg’ ... -** package ‘Greg’ 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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘Greg’ -* removing ‘/tmp/workdir/Greg/new/Greg.Rcheck/Greg’ +* using log directory ‘/tmp/workdir/DIscBIO/new/DIscBIO.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘DIscBIO/DESCRIPTION’ ... OK +... +* checking Rd \usage sections ... OK +* checking Rd contents ... OK +* checking for unstated dependencies in examples ... OK +* checking contents of ‘data’ directory ... OK +* checking data for non-ASCII characters ... OK +* checking LazyData ... OK +* checking data for ASCII and uncompressed saves ... OK +* checking examples ... OK +* DONE +Status: 1 NOTE + + + ``` ### CRAN ``` -* installing *source* package ‘Greg’ ... -** package ‘Greg’ 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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘Greg’ -* removing ‘/tmp/workdir/Greg/old/Greg.Rcheck/Greg’ +* using log directory ‘/tmp/workdir/DIscBIO/old/DIscBIO.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘DIscBIO/DESCRIPTION’ ... OK +... +* checking Rd \usage sections ... OK +* checking Rd contents ... OK +* checking for unstated dependencies in examples ... OK +* checking contents of ‘data’ directory ... OK +* checking data for non-ASCII characters ... OK +* checking LazyData ... OK +* checking data for ASCII and uncompressed saves ... OK +* checking examples ... OK +* DONE +Status: 1 NOTE + + + ``` -# greport +# diversityForest
-* Version: 0.7-4 -* GitHub: https://github.com/harrelfe/greport -* Source code: https://github.com/cran/greport -* Date/Publication: 2023-09-02 22:20:02 UTC -* Number of recursive dependencies: 84 +* Version: 0.4.0 +* GitHub: NA +* Source code: https://github.com/cran/diversityForest +* Date/Publication: 2023-03-08 08:20:02 UTC +* Number of recursive dependencies: 135 -Run `revdepcheck::cloud_details(, "greport")` for more info +Run `revdepcheck::cloud_details(, "diversityForest")` for more info
-## In both - -* checking whether package ‘greport’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/greport/new/greport.Rcheck/00install.out’ for details. - ``` - -## Installation +## Error before installation ### Devel ``` -* installing *source* package ‘greport’ ... -** package ‘greport’ 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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘greport’ -* removing ‘/tmp/workdir/greport/new/greport.Rcheck/greport’ +* using log directory ‘/tmp/workdir/diversityForest/new/diversityForest.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘diversityForest/DESCRIPTION’ ... OK +... +* this is package ‘diversityForest’ version ‘0.4.0’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘rms’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + ``` ### CRAN ``` -* installing *source* package ‘greport’ ... -** package ‘greport’ 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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘greport’ -* removing ‘/tmp/workdir/greport/old/greport.Rcheck/greport’ +* using log directory ‘/tmp/workdir/diversityForest/old/diversityForest.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘diversityForest/DESCRIPTION’ ... OK +... +* this is package ‘diversityForest’ version ‘0.4.0’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘rms’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + ``` -# hettx +# DR.SC
-* Version: 0.1.3 -* GitHub: https://github.com/bfifield/hettx -* Source code: https://github.com/cran/hettx -* Date/Publication: 2023-08-19 22:22:34 UTC -* Number of recursive dependencies: 85 +* Version: 3.4 +* GitHub: https://github.com/feiyoung/DR.SC +* Source code: https://github.com/cran/DR.SC +* Date/Publication: 2024-03-19 08:40:02 UTC +* Number of recursive dependencies: 150 -Run `revdepcheck::cloud_details(, "hettx")` for more info +Run `revdepcheck::cloud_details(, "DR.SC")` for more info
-## In both - -* checking whether package ‘hettx’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/hettx/new/hettx.Rcheck/00install.out’ for details. - ``` - -## Installation +## Error before installation ### Devel ``` -* installing *source* package ‘hettx’ ... -** package ‘hettx’ 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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘hettx’ -* removing ‘/tmp/workdir/hettx/new/hettx.Rcheck/hettx’ +* using log directory ‘/tmp/workdir/DR.SC/new/DR.SC.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘DR.SC/DESCRIPTION’ ... OK +... +* this is package ‘DR.SC’ version ‘3.4’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘Seurat’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + ``` ### CRAN ``` -* installing *source* package ‘hettx’ ... -** package ‘hettx’ 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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘hettx’ -* removing ‘/tmp/workdir/hettx/old/hettx.Rcheck/hettx’ +* using log directory ‘/tmp/workdir/DR.SC/old/DR.SC.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘DR.SC/DESCRIPTION’ ... OK +... +* this is package ‘DR.SC’ version ‘3.4’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘Seurat’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + ``` -# hIRT +# DynForest
-* Version: 0.3.0 -* GitHub: https://github.com/xiangzhou09/hIRT -* Source code: https://github.com/cran/hIRT -* Date/Publication: 2020-03-26 17:10:02 UTC -* Number of recursive dependencies: 88 +* Version: 1.1.3 +* GitHub: https://github.com/anthonydevaux/DynForest +* Source code: https://github.com/cran/DynForest +* Date/Publication: 2024-03-22 11:30:05 UTC +* Number of recursive dependencies: 134 -Run `revdepcheck::cloud_details(, "hIRT")` for more info +Run `revdepcheck::cloud_details(, "DynForest")` for more info
-## In both - -* checking whether package ‘hIRT’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/hIRT/new/hIRT.Rcheck/00install.out’ for details. - ``` - -## Installation +## Error before installation ### Devel ``` -* installing *source* package ‘hIRT’ ... -** package ‘hIRT’ successfully unpacked and MD5 sums checked -** using staged installation -** R -** data -*** moving datasets to lazyload DB -** byte-compile and prepare package for lazy loading -Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘hIRT’ -* removing ‘/tmp/workdir/hIRT/new/hIRT.Rcheck/hIRT’ +* using log directory ‘/tmp/workdir/DynForest/new/DynForest.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘DynForest/DESCRIPTION’ ... OK +... +* checking for unstated dependencies in vignettes ... OK +* checking package vignettes in ‘inst/doc’ ... OK +* checking running R code from vignettes ... OK + ‘Introduction.Rmd’ using ‘UTF-8’... OK + ‘factor.Rmd’ using ‘UTF-8’... OK + ‘numeric.Rmd’ using ‘UTF-8’... OK + ‘surv.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: OK + + + ``` ### CRAN ``` -* installing *source* package ‘hIRT’ ... -** package ‘hIRT’ successfully unpacked and MD5 sums checked -** using staged installation -** R -** data -*** moving datasets to lazyload DB -** byte-compile and prepare package for lazy loading -Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘hIRT’ -* removing ‘/tmp/workdir/hIRT/old/hIRT.Rcheck/hIRT’ +* using log directory ‘/tmp/workdir/DynForest/old/DynForest.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘DynForest/DESCRIPTION’ ... OK +... +* checking for unstated dependencies in vignettes ... OK +* checking package vignettes in ‘inst/doc’ ... OK +* checking running R code from vignettes ... OK + ‘Introduction.Rmd’ using ‘UTF-8’... OK + ‘factor.Rmd’ using ‘UTF-8’... OK + ‘numeric.Rmd’ using ‘UTF-8’... OK + ‘surv.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: OK + + + ``` -# Hmsc +# dyngen
-* Version: 3.0-13 -* GitHub: https://github.com/hmsc-r/HMSC -* Source code: https://github.com/cran/Hmsc -* Date/Publication: 2022-08-11 14:10:14 UTC -* Number of recursive dependencies: 76 +* Version: 1.0.5 +* GitHub: https://github.com/dynverse/dyngen +* Source code: https://github.com/cran/dyngen +* Date/Publication: 2022-10-12 15:22:39 UTC +* Number of recursive dependencies: 209 -Run `revdepcheck::cloud_details(, "Hmsc")` for more info +Run `revdepcheck::cloud_details(, "dyngen")` for more info
-## In both - -* checking whether package ‘Hmsc’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/Hmsc/new/Hmsc.Rcheck/00install.out’ for details. - ``` - -## Installation +## Error before installation ### Devel ``` -* installing *source* package ‘Hmsc’ ... -** package ‘Hmsc’ 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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘Hmsc’ -* removing ‘/tmp/workdir/Hmsc/new/Hmsc.Rcheck/Hmsc’ +* using log directory ‘/tmp/workdir/dyngen/new/dyngen.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘dyngen/DESCRIPTION’ ... OK +... +* checking tests ... OK + Running ‘testthat.R’ +* checking for unstated dependencies in vignettes ... OK +* checking package vignettes in ‘inst/doc’ ... OK +* checking running R code from vignettes ... NONE + ‘getting_started.html.asis’ using ‘UTF-8’... OK + ‘installation.html.asis’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 1 NOTE + + + ``` ### CRAN ``` -* installing *source* package ‘Hmsc’ ... -** package ‘Hmsc’ 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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘Hmsc’ -* removing ‘/tmp/workdir/Hmsc/old/Hmsc.Rcheck/Hmsc’ +* using log directory ‘/tmp/workdir/dyngen/old/dyngen.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘dyngen/DESCRIPTION’ ... OK +... +* checking tests ... OK + Running ‘testthat.R’ +* checking for unstated dependencies in vignettes ... OK +* checking package vignettes in ‘inst/doc’ ... OK +* checking running R code from vignettes ... NONE + ‘getting_started.html.asis’ using ‘UTF-8’... OK + ‘installation.html.asis’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 1 NOTE + + + ``` -# inventorize +# EcoEnsemble
-* Version: 1.1.1 +* Version: 1.0.5 * GitHub: NA -* Source code: https://github.com/cran/inventorize -* Date/Publication: 2022-05-31 22:20:09 UTC -* Number of recursive dependencies: 71 +* Source code: https://github.com/cran/EcoEnsemble +* Date/Publication: 2023-09-18 11:50:02 UTC +* Number of recursive dependencies: 91 -Run `revdepcheck::cloud_details(, "inventorize")` for more info +Run `revdepcheck::cloud_details(, "EcoEnsemble")` for more info
-## Newly broken +## In both -* checking whether package ‘inventorize’ can be installed ... ERROR +* checking whether package ‘EcoEnsemble’ can be installed ... ERROR ``` Installation failed. - See ‘/tmp/workdir/inventorize/new/inventorize.Rcheck/00install.out’ for details. + See ‘/tmp/workdir/EcoEnsemble/new/EcoEnsemble.Rcheck/00install.out’ for details. ``` ## Installation @@ -3019,60 +3750,77 @@ Run `revdepcheck::cloud_details(, "inventorize")` for more info ### Devel ``` -* installing *source* package ‘inventorize’ ... -** package ‘inventorize’ successfully unpacked and MD5 sums checked -** using staged installation -** R -** byte-compile and prepare package for lazy loading -Error in compute_geom_2(..., self = self) : - argument "theme" is missing, with no default -Error: unable to load R code in package ‘inventorize’ -Execution halted -ERROR: lazy loading failed for package ‘inventorize’ -* removing ‘/tmp/workdir/inventorize/new/inventorize.Rcheck/inventorize’ +* installing *source* package ‘EcoEnsemble’ ... +** package ‘EcoEnsemble’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C++ compiler: ‘g++ (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ +using C++17 + + +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I"../inst/include" -I"/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src" -DBOOST_DISABLE_ASSERTS -DEIGEN_NO_DEBUG -DBOOST_MATH_OVERFLOW_ERROR_POLICY=errno_on_error -DUSE_STANC3 -D_HAS_AUTO_PTR_ETC=0 -I'/opt/R/4.3.1/lib/R/site-library/BH/include' -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppEigen/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -I'/opt/R/4.3.1/lib/R/site-library/rstan/include' -I'/opt/R/4.3.1/lib/R/site-library/StanHeaders/include' -I/usr/local/include -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -D_REENTRANT -DSTAN_THREADS -fpic -g -O2 -c KF_back.cpp -o KF_back.o +In file included from /opt/R/4.3.1/lib/R/site-library/RcppEigen/include/Eigen/Core:205, +... +/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src/stan/mcmc/hmc/hamiltonians/dense_e_metric.hpp:22:56: required from ‘double stan::mcmc::dense_e_metric::T(stan::mcmc::dense_e_point&) [with Model = model_ensemble_model_hierarchical_namespace::model_ensemble_model_hierarchical; BaseRNG = boost::random::additive_combine_engine, boost::random::linear_congruential_engine >]’ +/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src/stan/mcmc/hmc/hamiltonians/dense_e_metric.hpp:21:10: required from here +/opt/R/4.3.1/lib/R/site-library/RcppEigen/include/Eigen/src/Core/DenseCoeffsBase.h:654:74: warning: ignoring attributes on template argument ‘Eigen::internal::packet_traits::type’ {aka ‘__m128d’} [-Wignored-attributes] + 654 | return internal::first_aligned::alignment),Derived>(m); + | ^~~~~~~~~ +g++: fatal error: Killed signal terminated program cc1plus +compilation terminated. +make: *** [/opt/R/4.3.1/lib/R/etc/Makeconf:198: stanExports_ensemble_model_hierarchical.o] Error 1 +ERROR: compilation failed for package ‘EcoEnsemble’ +* removing ‘/tmp/workdir/EcoEnsemble/new/EcoEnsemble.Rcheck/EcoEnsemble’ ``` ### CRAN ``` -* installing *source* package ‘inventorize’ ... -** package ‘inventorize’ successfully unpacked and MD5 sums checked +* installing *source* package ‘EcoEnsemble’ ... +** package ‘EcoEnsemble’ successfully unpacked and MD5 sums checked ** using staged installation -** R -** byte-compile and prepare package for lazy loading -Warning in qgamma(service_level, alpha, beta) : NaNs produced -Warning in qgamma(service_level, alpha, beta) : NaNs produced -** help -*** installing help indices -** building package indices -** testing if installed package can be loaded from temporary location -** testing if installed package can be loaded from final location -** testing if installed package keeps a record of temporary installation path -* DONE (inventorize) +** libs +using C++ compiler: ‘g++ (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ +using C++17 + + +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I"../inst/include" -I"/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src" -DBOOST_DISABLE_ASSERTS -DEIGEN_NO_DEBUG -DBOOST_MATH_OVERFLOW_ERROR_POLICY=errno_on_error -DUSE_STANC3 -D_HAS_AUTO_PTR_ETC=0 -I'/opt/R/4.3.1/lib/R/site-library/BH/include' -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppEigen/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -I'/opt/R/4.3.1/lib/R/site-library/rstan/include' -I'/opt/R/4.3.1/lib/R/site-library/StanHeaders/include' -I/usr/local/include -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -D_REENTRANT -DSTAN_THREADS -fpic -g -O2 -c KF_back.cpp -o KF_back.o +In file included from /opt/R/4.3.1/lib/R/site-library/RcppEigen/include/Eigen/Core:205, +... +/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src/stan/mcmc/hmc/hamiltonians/dense_e_metric.hpp:22:56: required from ‘double stan::mcmc::dense_e_metric::T(stan::mcmc::dense_e_point&) [with Model = model_ensemble_model_hierarchical_namespace::model_ensemble_model_hierarchical; BaseRNG = boost::random::additive_combine_engine, boost::random::linear_congruential_engine >]’ +/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src/stan/mcmc/hmc/hamiltonians/dense_e_metric.hpp:21:10: required from here +/opt/R/4.3.1/lib/R/site-library/RcppEigen/include/Eigen/src/Core/DenseCoeffsBase.h:654:74: warning: ignoring attributes on template argument ‘Eigen::internal::packet_traits::type’ {aka ‘__m128d’} [-Wignored-attributes] + 654 | return internal::first_aligned::alignment),Derived>(m); + | ^~~~~~~~~ +g++: fatal error: Killed signal terminated program cc1plus +compilation terminated. +make: *** [/opt/R/4.3.1/lib/R/etc/Makeconf:198: stanExports_ensemble_model_hierarchical.o] Error 1 +ERROR: compilation failed for package ‘EcoEnsemble’ +* removing ‘/tmp/workdir/EcoEnsemble/old/EcoEnsemble.Rcheck/EcoEnsemble’ ``` -# iNZightPlots +# ecolottery
-* Version: 2.15.3 -* GitHub: https://github.com/iNZightVIT/iNZightPlots -* Source code: https://github.com/cran/iNZightPlots -* Date/Publication: 2023-10-14 05:00:02 UTC -* Number of recursive dependencies: 162 +* Version: 1.0.0 +* GitHub: https://github.com/frmunoz/ecolottery +* Source code: https://github.com/cran/ecolottery +* Date/Publication: 2017-07-03 11:01:29 UTC +* Number of recursive dependencies: 88 -Run `revdepcheck::cloud_details(, "iNZightPlots")` for more info +Run `revdepcheck::cloud_details(, "ecolottery")` for more info
## In both -* checking whether package ‘iNZightPlots’ can be installed ... ERROR +* checking whether package ‘ecolottery’ can be installed ... ERROR ``` Installation failed. - See ‘/tmp/workdir/iNZightPlots/new/iNZightPlots.Rcheck/00install.out’ for details. + See ‘/tmp/workdir/ecolottery/new/ecolottery.Rcheck/00install.out’ for details. ``` ## Installation @@ -3080,59 +3828,59 @@ Run `revdepcheck::cloud_details(, "iNZightPlots")` for more info ### Devel ``` -* installing *source* package ‘iNZightPlots’ ... -** package ‘iNZightPlots’ successfully unpacked and MD5 sums checked +* installing *source* package ‘ecolottery’ ... +** package ‘ecolottery’ 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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace + there is no package called ‘quantreg’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart Execution halted -ERROR: lazy loading failed for package ‘iNZightPlots’ -* removing ‘/tmp/workdir/iNZightPlots/new/iNZightPlots.Rcheck/iNZightPlots’ +ERROR: lazy loading failed for package ‘ecolottery’ +* removing ‘/tmp/workdir/ecolottery/new/ecolottery.Rcheck/ecolottery’ ``` ### CRAN ``` -* installing *source* package ‘iNZightPlots’ ... -** package ‘iNZightPlots’ successfully unpacked and MD5 sums checked +* installing *source* package ‘ecolottery’ ... +** package ‘ecolottery’ 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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace + there is no package called ‘quantreg’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart Execution halted -ERROR: lazy loading failed for package ‘iNZightPlots’ -* removing ‘/tmp/workdir/iNZightPlots/old/iNZightPlots.Rcheck/iNZightPlots’ +ERROR: lazy loading failed for package ‘ecolottery’ +* removing ‘/tmp/workdir/ecolottery/old/ecolottery.Rcheck/ecolottery’ ``` -# iNZightRegression +# EpiEstim
-* Version: 1.3.4 -* GitHub: https://github.com/iNZightVIT/iNZightRegression -* Source code: https://github.com/cran/iNZightRegression -* Date/Publication: 2024-04-05 02:32:59 UTC -* Number of recursive dependencies: 154 +* Version: 2.2-4 +* GitHub: https://github.com/mrc-ide/EpiEstim +* Source code: https://github.com/cran/EpiEstim +* Date/Publication: 2021-01-07 16:20:10 UTC +* Number of recursive dependencies: 91 -Run `revdepcheck::cloud_details(, "iNZightRegression")` for more info +Run `revdepcheck::cloud_details(, "EpiEstim")` for more info
## In both -* checking whether package ‘iNZightRegression’ can be installed ... ERROR +* checking whether package ‘EpiEstim’ can be installed ... ERROR ``` Installation failed. - See ‘/tmp/workdir/iNZightRegression/new/iNZightRegression.Rcheck/00install.out’ for details. + See ‘/tmp/workdir/EpiEstim/new/EpiEstim.Rcheck/00install.out’ for details. ``` ## Installation @@ -3140,123 +3888,137 @@ Run `revdepcheck::cloud_details(, "iNZightRegression")` for more info ### Devel ``` -* installing *source* package ‘iNZightRegression’ ... -** package ‘iNZightRegression’ successfully unpacked and MD5 sums checked +* installing *source* package ‘EpiEstim’ ... +** package ‘EpiEstim’ successfully unpacked and MD5 sums checked ** 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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Error in loadNamespace(i, c(lib.loc, .libPaths()), versionCheck = vI[[i]]) : + there is no package called ‘quantreg’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart Execution halted -ERROR: lazy loading failed for package ‘iNZightRegression’ -* removing ‘/tmp/workdir/iNZightRegression/new/iNZightRegression.Rcheck/iNZightRegression’ +ERROR: lazy loading failed for package ‘EpiEstim’ +* removing ‘/tmp/workdir/EpiEstim/new/EpiEstim.Rcheck/EpiEstim’ ``` ### CRAN ``` -* installing *source* package ‘iNZightRegression’ ... -** package ‘iNZightRegression’ successfully unpacked and MD5 sums checked +* installing *source* package ‘EpiEstim’ ... +** package ‘EpiEstim’ successfully unpacked and MD5 sums checked ** 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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Error in loadNamespace(i, c(lib.loc, .libPaths()), versionCheck = vI[[i]]) : + there is no package called ‘quantreg’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart Execution halted -ERROR: lazy loading failed for package ‘iNZightRegression’ -* removing ‘/tmp/workdir/iNZightRegression/old/iNZightRegression.Rcheck/iNZightRegression’ +ERROR: lazy loading failed for package ‘EpiEstim’ +* removing ‘/tmp/workdir/EpiEstim/old/EpiEstim.Rcheck/EpiEstim’ ``` -# IRexamples +# evalITR
-* Version: 0.0.4 -* GitHub: https://github.com/vinhdizzo/IRexamples -* Source code: https://github.com/cran/IRexamples -* Date/Publication: 2023-10-06 06:40:02 UTC -* Number of recursive dependencies: 185 +* Version: 1.0.0 +* GitHub: https://github.com/MichaelLLi/evalITR +* Source code: https://github.com/cran/evalITR +* Date/Publication: 2023-08-25 23:10:06 UTC +* Number of recursive dependencies: 168 -Run `revdepcheck::cloud_details(, "IRexamples")` for more info +Run `revdepcheck::cloud_details(, "evalITR")` for more info
-## In both - -* checking whether package ‘IRexamples’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/IRexamples/new/IRexamples.Rcheck/00install.out’ for details. - ``` - -## Installation +## Error before installation ### Devel ``` -* installing *source* package ‘IRexamples’ ... -** package ‘IRexamples’ 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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘IRexamples’ -* removing ‘/tmp/workdir/IRexamples/new/IRexamples.Rcheck/IRexamples’ +* using log directory ‘/tmp/workdir/evalITR/new/evalITR.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘evalITR/DESCRIPTION’ ... OK +... +* this is package ‘evalITR’ version ‘1.0.0’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘rqPen’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + ``` ### CRAN ``` -* installing *source* package ‘IRexamples’ ... -** package ‘IRexamples’ 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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘IRexamples’ -* removing ‘/tmp/workdir/IRexamples/old/IRexamples.Rcheck/IRexamples’ +* using log directory ‘/tmp/workdir/evalITR/old/evalITR.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘evalITR/DESCRIPTION’ ... OK +... +* this is package ‘evalITR’ version ‘1.0.0’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘rqPen’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + ``` -# joineRML +# evolqg
-* Version: 0.4.6 -* GitHub: https://github.com/graemeleehickey/joineRML -* Source code: https://github.com/cran/joineRML -* Date/Publication: 2023-01-20 04:50:02 UTC -* Number of recursive dependencies: 91 +* Version: 0.3-4 +* GitHub: https://github.com/lem-usp/evolqg +* Source code: https://github.com/cran/evolqg +* Date/Publication: 2023-12-05 15:20:12 UTC +* Number of recursive dependencies: 111 -Run `revdepcheck::cloud_details(, "joineRML")` for more info +Run `revdepcheck::cloud_details(, "evolqg")` for more info
## In both -* checking whether package ‘joineRML’ can be installed ... ERROR +* checking whether package ‘evolqg’ can be installed ... ERROR ``` Installation failed. - See ‘/tmp/workdir/joineRML/new/joineRML.Rcheck/00install.out’ for details. + See ‘/tmp/workdir/evolqg/new/evolqg.Rcheck/00install.out’ for details. ``` ## Installation @@ -3264,141 +4026,3275 @@ Run `revdepcheck::cloud_details(, "joineRML")` for more info ### Devel ``` -* installing *source* package ‘joineRML’ ... -** package ‘joineRML’ successfully unpacked and MD5 sums checked +* installing *source* package ‘evolqg’ ... +** package ‘evolqg’ successfully unpacked and MD5 sums checked ** using staged installation ** libs -using C compiler: ‘gcc (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ -using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ -using C++11 -g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o -g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c expW.cpp -o expW.o -g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c gammaUpdate.cpp -o gammaUpdate.o -... +using C++ compiler: ‘g++ (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c fast_RS.cpp -o fast_RS.o +g++ -std=gnu++17 -shared -L/opt/R/4.3.1/lib/R/lib -L/usr/local/lib -o evolqg.so RcppExports.o fast_RS.o -llapack -lblas -lgfortran -lm -lquadmath -L/opt/R/4.3.1/lib/R/lib -lR +installing to /tmp/workdir/evolqg/new/evolqg.Rcheck/00LOCK-evolqg/00new/evolqg/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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Error in loadNamespace(i, c(lib.loc, .libPaths()), versionCheck = vI[[i]]) : + there is no package called ‘quantreg’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart Execution halted -ERROR: lazy loading failed for package ‘joineRML’ -* removing ‘/tmp/workdir/joineRML/new/joineRML.Rcheck/joineRML’ +ERROR: lazy loading failed for package ‘evolqg’ +* removing ‘/tmp/workdir/evolqg/new/evolqg.Rcheck/evolqg’ ``` ### CRAN ``` -* installing *source* package ‘joineRML’ ... -** package ‘joineRML’ successfully unpacked and MD5 sums checked +* installing *source* package ‘evolqg’ ... +** package ‘evolqg’ successfully unpacked and MD5 sums checked ** using staged installation ** libs -using C compiler: ‘gcc (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ -using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ -using C++11 -g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o -g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c expW.cpp -o expW.o -g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c gammaUpdate.cpp -o gammaUpdate.o -... +using C++ compiler: ‘g++ (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c fast_RS.cpp -o fast_RS.o +g++ -std=gnu++17 -shared -L/opt/R/4.3.1/lib/R/lib -L/usr/local/lib -o evolqg.so RcppExports.o fast_RS.o -llapack -lblas -lgfortran -lm -lquadmath -L/opt/R/4.3.1/lib/R/lib -lR +installing to /tmp/workdir/evolqg/old/evolqg.Rcheck/00LOCK-evolqg/00new/evolqg/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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Error in loadNamespace(i, c(lib.loc, .libPaths()), versionCheck = vI[[i]]) : + there is no package called ‘quantreg’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart Execution halted -ERROR: lazy loading failed for package ‘joineRML’ -* removing ‘/tmp/workdir/joineRML/old/joineRML.Rcheck/joineRML’ +ERROR: lazy loading failed for package ‘evolqg’ +* removing ‘/tmp/workdir/evolqg/old/evolqg.Rcheck/evolqg’ ``` -# JWileymisc +# explainer
-* Version: 1.4.1 +* Version: 1.0.1 +* GitHub: https://github.com/PERSIMUNE/explainer +* Source code: https://github.com/cran/explainer +* Date/Publication: 2024-04-18 09:00:02 UTC +* Number of recursive dependencies: 193 + +Run `revdepcheck::cloud_details(, "explainer")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/explainer/new/explainer.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘explainer/DESCRIPTION’ ... OK +... +* this is package ‘explainer’ version ‘1.0.1’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘ggpmisc’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/explainer/old/explainer.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘explainer/DESCRIPTION’ ... OK +... +* this is package ‘explainer’ version ‘1.0.1’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘ggpmisc’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# flexrsurv + +
+ +* Version: 2.0.18 +* GitHub: NA +* Source code: https://github.com/cran/flexrsurv +* Date/Publication: 2024-02-09 16:10:02 UTC +* Number of recursive dependencies: 129 + +Run `revdepcheck::cloud_details(, "flexrsurv")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/flexrsurv/new/flexrsurv.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘flexrsurv/DESCRIPTION’ ... OK +... +* checking for missing documentation entries ... OK +* checking for code/documentation mismatches ... OK +* checking Rd \usage sections ... OK +* checking Rd contents ... OK +* checking for unstated dependencies in examples ... OK +* checking line endings in C/C++/Fortran sources/headers ... OK +* checking compiled code ... OK +* checking examples ... OK +* DONE +Status: OK + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/flexrsurv/old/flexrsurv.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘flexrsurv/DESCRIPTION’ ... OK +... +* checking for missing documentation entries ... OK +* checking for code/documentation mismatches ... OK +* checking Rd \usage sections ... OK +* checking Rd contents ... OK +* checking for unstated dependencies in examples ... OK +* checking line endings in C/C++/Fortran sources/headers ... OK +* checking compiled code ... OK +* checking examples ... OK +* DONE +Status: OK + + + + + +``` +# forestmangr + +
+ +* Version: 0.9.6 +* GitHub: https://github.com/sollano/forestmangr +* Source code: https://github.com/cran/forestmangr +* Date/Publication: 2023-11-23 18:30:02 UTC +* Number of recursive dependencies: 126 + +Run `revdepcheck::cloud_details(, "forestmangr")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/forestmangr/new/forestmangr.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘forestmangr/DESCRIPTION’ ... OK +... +* this is package ‘forestmangr’ version ‘0.9.6’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘ggpmisc’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/forestmangr/old/forestmangr.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘forestmangr/DESCRIPTION’ ... OK +... +* this is package ‘forestmangr’ version ‘0.9.6’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘ggpmisc’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# gap + +
+ +* Version: 1.5-3 +* GitHub: https://github.com/jinghuazhao/R +* Source code: https://github.com/cran/gap +* Date/Publication: 2023-08-26 14:10:07 UTC +* Number of recursive dependencies: 177 + +Run `revdepcheck::cloud_details(, "gap")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/gap/new/gap.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘gap/DESCRIPTION’ ... OK +... +--- failed re-building ‘jss.Rnw’ + +SUMMARY: processing the following file failed: + ‘jss.Rnw’ + +Error: Vignette re-building failed. +Execution halted + +* DONE +Status: 4 NOTEs + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/gap/old/gap.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘gap/DESCRIPTION’ ... OK +... +--- failed re-building ‘jss.Rnw’ + +SUMMARY: processing the following file failed: + ‘jss.Rnw’ + +Error: Vignette re-building failed. +Execution halted + +* DONE +Status: 4 NOTEs + + + + + +``` +# GeomComb + +
+ +* Version: 1.0 +* GitHub: https://github.com/ceweiss/GeomComb +* Source code: https://github.com/cran/GeomComb +* Date/Publication: 2016-11-27 16:02:26 +* Number of recursive dependencies: 74 + +Run `revdepcheck::cloud_details(, "GeomComb")` for more info + +
+ +## In both + +* checking whether package ‘GeomComb’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/GeomComb/new/GeomComb.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘GeomComb’ ... +** package ‘GeomComb’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** byte-compile and prepare package for lazy loading +Error in loadNamespace(i, c(lib.loc, .libPaths()), versionCheck = vI[[i]]) : + there is no package called ‘quantreg’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Execution halted +ERROR: lazy loading failed for package ‘GeomComb’ +* removing ‘/tmp/workdir/GeomComb/new/GeomComb.Rcheck/GeomComb’ + + +``` +### CRAN + +``` +* installing *source* package ‘GeomComb’ ... +** package ‘GeomComb’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** byte-compile and prepare package for lazy loading +Error in loadNamespace(i, c(lib.loc, .libPaths()), versionCheck = vI[[i]]) : + there is no package called ‘quantreg’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Execution halted +ERROR: lazy loading failed for package ‘GeomComb’ +* removing ‘/tmp/workdir/GeomComb/old/GeomComb.Rcheck/GeomComb’ + + +``` +# ggeffects + +
+ +* Version: 1.6.0 +* GitHub: https://github.com/strengejacke/ggeffects +* Source code: https://github.com/cran/ggeffects +* Date/Publication: 2024-05-18 20:00:03 UTC +* Number of recursive dependencies: 265 + +Run `revdepcheck::cloud_details(, "ggeffects")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/ggeffects/new/ggeffects.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘ggeffects/DESCRIPTION’ ... OK +... +* checking for unstated dependencies in ‘tests’ ... OK +* checking tests ... OK + Running ‘testthat.R’ +* checking for unstated dependencies in vignettes ... OK +* checking package vignettes in ‘inst/doc’ ... OK +* checking running R code from vignettes ... OK + ‘content.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 1 NOTE + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/ggeffects/old/ggeffects.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘ggeffects/DESCRIPTION’ ... OK +... +* checking for unstated dependencies in ‘tests’ ... OK +* checking tests ... OK + Running ‘testthat.R’ +* checking for unstated dependencies in vignettes ... OK +* checking package vignettes in ‘inst/doc’ ... OK +* checking running R code from vignettes ... OK + ‘content.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 1 NOTE + + + + + +``` +# ggquickeda + +
+ +* Version: 0.3.1 +* GitHub: https://github.com/smouksassi/ggquickeda +* Source code: https://github.com/cran/ggquickeda +* Date/Publication: 2024-01-15 10:20:02 UTC +* Number of recursive dependencies: 187 + +Run `revdepcheck::cloud_details(, "ggquickeda")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/ggquickeda/new/ggquickeda.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘ggquickeda/DESCRIPTION’ ... OK +... +* this is package ‘ggquickeda’ version ‘0.3.1’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Packages required but not available: 'ggpmisc', 'quantreg', 'rms' + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/ggquickeda/old/ggquickeda.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘ggquickeda/DESCRIPTION’ ... OK +... +* this is package ‘ggquickeda’ version ‘0.3.1’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Packages required but not available: 'ggpmisc', 'quantreg', 'rms' + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# ggrcs + +
+ +* Version: 0.3.8 +* GitHub: NA +* Source code: https://github.com/cran/ggrcs +* Date/Publication: 2024-01-30 03:20:08 UTC +* Number of recursive dependencies: 78 + +Run `revdepcheck::cloud_details(, "ggrcs")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/ggrcs/new/ggrcs.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘ggrcs/DESCRIPTION’ ... OK +... +* this is package ‘ggrcs’ version ‘0.3.8’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘rms’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/ggrcs/old/ggrcs.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘ggrcs/DESCRIPTION’ ... OK +... +* this is package ‘ggrcs’ version ‘0.3.8’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘rms’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# ggrisk + +
+ +* Version: 1.3 +* GitHub: https://github.com/yikeshu0611/ggrisk +* Source code: https://github.com/cran/ggrisk +* Date/Publication: 2021-08-09 07:40:06 UTC +* Number of recursive dependencies: 115 + +Run `revdepcheck::cloud_details(, "ggrisk")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/ggrisk/new/ggrisk.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘ggrisk/DESCRIPTION’ ... OK +... +* this is package ‘ggrisk’ version ‘1.3’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘rms’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/ggrisk/old/ggrisk.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘ggrisk/DESCRIPTION’ ... OK +... +* this is package ‘ggrisk’ version ‘1.3’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘rms’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# ggsector + +
+ +* Version: 1.6.6 +* GitHub: https://github.com/yanpd01/ggsector +* Source code: https://github.com/cran/ggsector +* Date/Publication: 2022-12-05 15:20:02 UTC +* Number of recursive dependencies: 159 + +Run `revdepcheck::cloud_details(, "ggsector")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/ggsector/new/ggsector.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘ggsector/DESCRIPTION’ ... OK +... +* this is package ‘ggsector’ version ‘1.6.6’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘Seurat’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/ggsector/old/ggsector.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘ggsector/DESCRIPTION’ ... OK +... +* this is package ‘ggsector’ version ‘1.6.6’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘Seurat’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# grandR + +
+ +* Version: 0.2.5 +* GitHub: https://github.com/erhard-lab/grandR +* Source code: https://github.com/cran/grandR +* Date/Publication: 2024-02-15 15:30:02 UTC +* Number of recursive dependencies: 265 + +Run `revdepcheck::cloud_details(, "grandR")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/grandR/new/grandR.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘grandR/DESCRIPTION’ ... OK +... +* checking installed files from ‘inst/doc’ ... OK +* checking files in ‘vignettes’ ... OK +* checking examples ... OK +* checking for unstated dependencies in vignettes ... OK +* checking package vignettes in ‘inst/doc’ ... OK +* checking running R code from vignettes ... OK + ‘getting-started.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 1 NOTE + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/grandR/old/grandR.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘grandR/DESCRIPTION’ ... OK +... +* checking installed files from ‘inst/doc’ ... OK +* checking files in ‘vignettes’ ... OK +* checking examples ... OK +* checking for unstated dependencies in vignettes ... OK +* checking package vignettes in ‘inst/doc’ ... OK +* checking running R code from vignettes ... OK + ‘getting-started.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 1 NOTE + + + + + +``` +# Greg + +
+ +* Version: 2.0.2 +* GitHub: https://github.com/gforge/Greg +* Source code: https://github.com/cran/Greg +* Date/Publication: 2024-01-29 13:30:21 UTC +* Number of recursive dependencies: 151 + +Run `revdepcheck::cloud_details(, "Greg")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/Greg/new/Greg.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘Greg/DESCRIPTION’ ... OK +... +* this is package ‘Greg’ version ‘2.0.2’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘rms’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/Greg/old/Greg.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘Greg/DESCRIPTION’ ... OK +... +* this is package ‘Greg’ version ‘2.0.2’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘rms’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# greport + +
+ +* Version: 0.7-4 +* GitHub: https://github.com/harrelfe/greport +* Source code: https://github.com/cran/greport +* Date/Publication: 2023-09-02 22:20:02 UTC +* Number of recursive dependencies: 84 + +Run `revdepcheck::cloud_details(, "greport")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/greport/new/greport.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘greport/DESCRIPTION’ ... OK +* this is package ‘greport’ version ‘0.7-4’ +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘rms’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/greport/old/greport.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘greport/DESCRIPTION’ ... OK +* this is package ‘greport’ version ‘0.7-4’ +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘rms’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# harmony + +
+ +* Version: 1.2.0 +* GitHub: NA +* Source code: https://github.com/cran/harmony +* Date/Publication: 2023-11-29 08:30:04 UTC +* Number of recursive dependencies: 213 + +Run `revdepcheck::cloud_details(, "harmony")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/harmony/new/harmony.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘harmony/DESCRIPTION’ ... OK +... +--- finished re-building ‘quickstart.Rmd’ + +SUMMARY: processing the following file failed: + ‘Seurat.Rmd’ + +Error: Vignette re-building failed. +Execution halted + +* DONE +Status: 1 WARNING, 3 NOTEs + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/harmony/old/harmony.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘harmony/DESCRIPTION’ ... OK +... +--- finished re-building ‘quickstart.Rmd’ + +SUMMARY: processing the following file failed: + ‘Seurat.Rmd’ + +Error: Vignette re-building failed. +Execution halted + +* DONE +Status: 1 WARNING, 3 NOTEs + + + + + +``` +# hIRT + +
+ +* Version: 0.3.0 +* GitHub: https://github.com/xiangzhou09/hIRT +* Source code: https://github.com/cran/hIRT +* Date/Publication: 2020-03-26 17:10:02 UTC +* Number of recursive dependencies: 88 + +Run `revdepcheck::cloud_details(, "hIRT")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/hIRT/new/hIRT.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘hIRT/DESCRIPTION’ ... OK +... +* this is package ‘hIRT’ version ‘0.3.0’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘rms’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/hIRT/old/hIRT.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘hIRT/DESCRIPTION’ ... OK +... +* this is package ‘hIRT’ version ‘0.3.0’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘rms’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# Hmisc + +
+ +* Version: 5.1-3 +* GitHub: NA +* Source code: https://github.com/cran/Hmisc +* Date/Publication: 2024-05-28 07:10:02 UTC +* Number of recursive dependencies: 183 + +Run `revdepcheck::cloud_details(, "Hmisc")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/Hmisc/new/Hmisc.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘Hmisc/DESCRIPTION’ ... OK +... +* checking for missing documentation entries ... OK +* checking for code/documentation mismatches ... OK +* checking Rd \usage sections ... OK +* checking Rd contents ... OK +* checking for unstated dependencies in examples ... OK +* checking line endings in C/C++/Fortran sources/headers ... OK +* checking compiled code ... OK +* checking examples ... OK +* DONE +Status: 4 NOTEs + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/Hmisc/old/Hmisc.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘Hmisc/DESCRIPTION’ ... OK +... +* checking for missing documentation entries ... OK +* checking for code/documentation mismatches ... OK +* checking Rd \usage sections ... OK +* checking Rd contents ... OK +* checking for unstated dependencies in examples ... OK +* checking line endings in C/C++/Fortran sources/headers ... OK +* checking compiled code ... OK +* checking examples ... OK +* DONE +Status: 4 NOTEs + + + + + +``` +# Hmsc + +
+ +* Version: 3.0-13 +* GitHub: https://github.com/hmsc-r/HMSC +* Source code: https://github.com/cran/Hmsc +* Date/Publication: 2022-08-11 14:10:14 UTC +* Number of recursive dependencies: 76 + +Run `revdepcheck::cloud_details(, "Hmsc")` for more info + +
+ +## In both + +* checking whether package ‘Hmsc’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/Hmsc/new/Hmsc.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘Hmsc’ ... +** package ‘Hmsc’ 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(i, c(lib.loc, .libPaths()), versionCheck = vI[[i]]) : + there is no package called ‘quantreg’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Execution halted +ERROR: lazy loading failed for package ‘Hmsc’ +* removing ‘/tmp/workdir/Hmsc/new/Hmsc.Rcheck/Hmsc’ + + +``` +### CRAN + +``` +* installing *source* package ‘Hmsc’ ... +** package ‘Hmsc’ 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(i, c(lib.loc, .libPaths()), versionCheck = vI[[i]]) : + there is no package called ‘quantreg’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Execution halted +ERROR: lazy loading failed for package ‘Hmsc’ +* removing ‘/tmp/workdir/Hmsc/old/Hmsc.Rcheck/Hmsc’ + + +``` +# hydroroute + +
+ +* Version: 0.1.2 +* GitHub: NA +* Source code: https://github.com/cran/hydroroute +* Date/Publication: 2023-02-08 13:20:02 UTC +* Number of recursive dependencies: 81 + +Run `revdepcheck::cloud_details(, "hydroroute")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/hydroroute/new/hydroroute.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘hydroroute/DESCRIPTION’ ... OK +... +* this is package ‘hydroroute’ version ‘0.1.2’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘ggpmisc’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/hydroroute/old/hydroroute.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘hydroroute/DESCRIPTION’ ... OK +... +* this is package ‘hydroroute’ version ‘0.1.2’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘ggpmisc’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# inventorize + +
+ +* Version: 1.1.1 +* GitHub: NA +* Source code: https://github.com/cran/inventorize +* Date/Publication: 2022-05-31 22:20:09 UTC +* Number of recursive dependencies: 71 + +Run `revdepcheck::cloud_details(, "inventorize")` for more info + +
+ +## Newly broken + +* checking whether package ‘inventorize’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/inventorize/new/inventorize.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘inventorize’ ... +** package ‘inventorize’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** byte-compile and prepare package for lazy loading +Error in pm[[2]] : subscript out of bounds +Error: unable to load R code in package ‘inventorize’ +Execution halted +ERROR: lazy loading failed for package ‘inventorize’ +* removing ‘/tmp/workdir/inventorize/new/inventorize.Rcheck/inventorize’ + + +``` +### CRAN + +``` +* installing *source* package ‘inventorize’ ... +** package ‘inventorize’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** byte-compile and prepare package for lazy loading +Warning in qgamma(service_level, alpha, beta) : NaNs produced +Warning in qgamma(service_level, alpha, beta) : NaNs produced +** help +*** installing help indices +** building package indices +** testing if installed package can be loaded from temporary location +** testing if installed package can be loaded from final location +** testing if installed package keeps a record of temporary installation path +* DONE (inventorize) + + +``` +# iNZightRegression + +
+ +* Version: 1.3.4 +* GitHub: https://github.com/iNZightVIT/iNZightRegression +* Source code: https://github.com/cran/iNZightRegression +* Date/Publication: 2024-04-05 02:32:59 UTC +* Number of recursive dependencies: 153 + +Run `revdepcheck::cloud_details(, "iNZightRegression")` for more info + +
+ +## In both + +* checking whether package ‘iNZightRegression’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/iNZightRegression/new/iNZightRegression.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘iNZightRegression’ ... +** package ‘iNZightRegression’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** 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 ‘quantreg’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Execution halted +ERROR: lazy loading failed for package ‘iNZightRegression’ +* removing ‘/tmp/workdir/iNZightRegression/new/iNZightRegression.Rcheck/iNZightRegression’ + + +``` +### CRAN + +``` +* installing *source* package ‘iNZightRegression’ ... +** package ‘iNZightRegression’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** 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 ‘quantreg’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Execution halted +ERROR: lazy loading failed for package ‘iNZightRegression’ +* removing ‘/tmp/workdir/iNZightRegression/old/iNZightRegression.Rcheck/iNZightRegression’ + + +``` +# IRexamples + +
+ +* Version: 0.0.4 +* GitHub: https://github.com/vinhdizzo/IRexamples +* Source code: https://github.com/cran/IRexamples +* Date/Publication: 2023-10-06 06:40:02 UTC +* Number of recursive dependencies: 185 + +Run `revdepcheck::cloud_details(, "IRexamples")` for more info + +
+ +## In both + +* checking whether package ‘IRexamples’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/IRexamples/new/IRexamples.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘IRexamples’ ... +** package ‘IRexamples’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘IRexamples’ +* removing ‘/tmp/workdir/IRexamples/new/IRexamples.Rcheck/IRexamples’ + + +``` +### CRAN + +``` +* installing *source* package ‘IRexamples’ ... +** package ‘IRexamples’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘IRexamples’ +* removing ‘/tmp/workdir/IRexamples/old/IRexamples.Rcheck/IRexamples’ + + +``` +# jmBIG + +
+ +* Version: 0.1.2 +* GitHub: NA +* Source code: https://github.com/cran/jmBIG +* Date/Publication: 2024-03-20 23:40:02 UTC +* Number of recursive dependencies: 193 + +Run `revdepcheck::cloud_details(, "jmBIG")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/jmBIG/new/jmBIG.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘jmBIG/DESCRIPTION’ ... OK +... +* this is package ‘jmBIG’ version ‘0.1.2’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘joineRML’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/jmBIG/old/jmBIG.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘jmBIG/DESCRIPTION’ ... OK +... +* this is package ‘jmBIG’ version ‘0.1.2’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘joineRML’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# joineRML + +
+ +* Version: 0.4.6 +* GitHub: https://github.com/graemeleehickey/joineRML +* Source code: https://github.com/cran/joineRML +* Date/Publication: 2023-01-20 04:50:02 UTC +* Number of recursive dependencies: 91 + +Run `revdepcheck::cloud_details(, "joineRML")` for more info + +
+ +## In both + +* checking whether package ‘joineRML’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/joineRML/new/joineRML.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘joineRML’ ... +** package ‘joineRML’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C compiler: ‘gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ +using C++ compiler: ‘g++ (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ +using C++11 +g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c expW.cpp -o expW.o +g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c gammaUpdate.cpp -o gammaUpdate.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 ‘quantreg’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Execution halted +ERROR: lazy loading failed for package ‘joineRML’ +* removing ‘/tmp/workdir/joineRML/new/joineRML.Rcheck/joineRML’ + + +``` +### CRAN + +``` +* installing *source* package ‘joineRML’ ... +** package ‘joineRML’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C compiler: ‘gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ +using C++ compiler: ‘g++ (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ +using C++11 +g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c expW.cpp -o expW.o +g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c gammaUpdate.cpp -o gammaUpdate.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 ‘quantreg’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Execution halted +ERROR: lazy loading failed for package ‘joineRML’ +* removing ‘/tmp/workdir/joineRML/old/joineRML.Rcheck/joineRML’ + + +``` +# jsmodule + +
+ +* Version: 1.5.4 +* GitHub: https://github.com/jinseob2kim/jsmodule +* Source code: https://github.com/cran/jsmodule +* Date/Publication: 2024-05-07 16:00:05 UTC +* Number of recursive dependencies: 240 + +Run `revdepcheck::cloud_details(, "jsmodule")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/jsmodule/new/jsmodule.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘jsmodule/DESCRIPTION’ ... OK +... +* checking for unstated dependencies in ‘tests’ ... OK +* checking tests ... OK + Running ‘testthat.R’ +* checking for unstated dependencies in vignettes ... OK +* checking package vignettes in ‘inst/doc’ ... OK +* checking running R code from vignettes ... OK + ‘jsmodule.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: OK + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/jsmodule/old/jsmodule.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘jsmodule/DESCRIPTION’ ... OK +... +* checking for unstated dependencies in ‘tests’ ... OK +* checking tests ... OK + Running ‘testthat.R’ +* checking for unstated dependencies in vignettes ... OK +* checking package vignettes in ‘inst/doc’ ... OK +* checking running R code from vignettes ... OK + ‘jsmodule.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: OK + + + + + +``` +# JWileymisc + +
+ +* Version: 1.4.1 * GitHub: https://github.com/JWiley/JWileymisc * Source code: https://github.com/cran/JWileymisc * Date/Publication: 2023-10-05 04:50:02 UTC -* Number of recursive dependencies: 164 +* Number of recursive dependencies: 163 + +Run `revdepcheck::cloud_details(, "JWileymisc")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/JWileymisc/new/JWileymisc.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘JWileymisc/DESCRIPTION’ ... OK +... +* this is package ‘JWileymisc’ version ‘1.4.1’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Packages required but not available: 'rms', 'quantreg' + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/JWileymisc/old/JWileymisc.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘JWileymisc/DESCRIPTION’ ... OK +... +* this is package ‘JWileymisc’ version ‘1.4.1’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Packages required but not available: 'rms', 'quantreg' + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# kmc + +
+ +* Version: 0.4-2 +* GitHub: https://github.com/yfyang86/kmc +* Source code: https://github.com/cran/kmc +* Date/Publication: 2022-11-22 08:30:02 UTC +* Number of recursive dependencies: 61 + +Run `revdepcheck::cloud_details(, "kmc")` for more info + +
+ +## In both + +* checking whether package ‘kmc’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/kmc/new/kmc.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘kmc’ ... +** package ‘kmc’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C compiler: ‘gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ +using C++ compiler: ‘g++ (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c RcppExport.cpp -o RcppExport.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c kmc.cpp -o kmc.o +gcc -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c kmc_init.c -o kmc_init.o +gcc -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c surv2.c -o surv2.o +g++ -std=gnu++17 -shared -L/opt/R/4.3.1/lib/R/lib -L/usr/local/lib -o kmc.so RcppExport.o kmc.o kmc_init.o surv2.o -L/opt/R/4.3.1/lib/R/lib -lR +installing to /tmp/workdir/kmc/new/kmc.Rcheck/00LOCK-kmc/00new/kmc/libs +** R +** byte-compile and prepare package for lazy loading +Error: package or namespace load failed for ‘emplik’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): + there is no package called ‘quantreg’ +Execution halted +ERROR: lazy loading failed for package ‘kmc’ +* removing ‘/tmp/workdir/kmc/new/kmc.Rcheck/kmc’ + + +``` +### CRAN + +``` +* installing *source* package ‘kmc’ ... +** package ‘kmc’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C compiler: ‘gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ +using C++ compiler: ‘g++ (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c RcppExport.cpp -o RcppExport.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c kmc.cpp -o kmc.o +gcc -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c kmc_init.c -o kmc_init.o +gcc -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c surv2.c -o surv2.o +g++ -std=gnu++17 -shared -L/opt/R/4.3.1/lib/R/lib -L/usr/local/lib -o kmc.so RcppExport.o kmc.o kmc_init.o surv2.o -L/opt/R/4.3.1/lib/R/lib -lR +installing to /tmp/workdir/kmc/old/kmc.Rcheck/00LOCK-kmc/00new/kmc/libs +** R +** byte-compile and prepare package for lazy loading +Error: package or namespace load failed for ‘emplik’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): + there is no package called ‘quantreg’ +Execution halted +ERROR: lazy loading failed for package ‘kmc’ +* removing ‘/tmp/workdir/kmc/old/kmc.Rcheck/kmc’ + + +``` +# KMunicate + +
+ +* Version: 0.2.5 +* GitHub: https://github.com/ellessenne/KMunicate-package +* Source code: https://github.com/cran/KMunicate +* Date/Publication: 2024-05-16 11:50:08 UTC +* Number of recursive dependencies: 172 + +Run `revdepcheck::cloud_details(, "KMunicate")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/KMunicate/new/KMunicate.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘KMunicate/DESCRIPTION’ ... OK +... +--- failed re-building ‘KMunicate.Rmd’ + +SUMMARY: processing the following file failed: + ‘KMunicate.Rmd’ + +Error: Vignette re-building failed. +Execution halted + +* DONE +Status: 3 ERRORs, 1 NOTE + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/KMunicate/old/KMunicate.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘KMunicate/DESCRIPTION’ ... OK +... +* checking for unstated dependencies in ‘tests’ ... OK +* checking tests ... OK + Running ‘testthat.R’ +* checking for unstated dependencies in vignettes ... OK +* checking package vignettes in ‘inst/doc’ ... OK +* checking running R code from vignettes ... OK + ‘KMunicate.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: OK + + + + + +``` +# L2E + +
+ +* Version: 2.0 +* GitHub: NA +* Source code: https://github.com/cran/L2E +* Date/Publication: 2022-09-08 21:13:00 UTC +* Number of recursive dependencies: 65 + +Run `revdepcheck::cloud_details(, "L2E")` for more info + +
+ +## In both + +* checking whether package ‘L2E’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/L2E/new/L2E.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘L2E’ ... +** package ‘L2E’ 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: package or namespace load failed for ‘osqp’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): + namespace ‘Matrix’ 1.5-4.1 is being loaded, but >= 1.6.1 is required +Execution halted +ERROR: lazy loading failed for package ‘L2E’ +* removing ‘/tmp/workdir/L2E/new/L2E.Rcheck/L2E’ + + +``` +### CRAN + +``` +* installing *source* package ‘L2E’ ... +** package ‘L2E’ 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: package or namespace load failed for ‘osqp’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): + namespace ‘Matrix’ 1.5-4.1 is being loaded, but >= 1.6.1 is required +Execution halted +ERROR: lazy loading failed for package ‘L2E’ +* removing ‘/tmp/workdir/L2E/old/L2E.Rcheck/L2E’ + + +``` +# Landmarking + +
+ +* Version: 1.0.0 +* GitHub: https://github.com/isobelbarrott/Landmarking +* Source code: https://github.com/cran/Landmarking +* Date/Publication: 2022-02-15 20:00:07 UTC +* Number of recursive dependencies: 123 + +Run `revdepcheck::cloud_details(, "Landmarking")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/Landmarking/new/Landmarking.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘Landmarking/DESCRIPTION’ ... OK +... +* this is package ‘Landmarking’ version ‘1.0.0’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘riskRegression’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/Landmarking/old/Landmarking.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘Landmarking/DESCRIPTION’ ... OK +... +* this is package ‘Landmarking’ version ‘1.0.0’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘riskRegression’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# lavaSearch2 + +
+ +* Version: 2.0.3 +* GitHub: https://github.com/bozenne/lavaSearch2 +* Source code: https://github.com/cran/lavaSearch2 +* Date/Publication: 2024-02-23 09:10:02 UTC +* Number of recursive dependencies: 142 + +Run `revdepcheck::cloud_details(, "lavaSearch2")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/lavaSearch2/new/lavaSearch2.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘lavaSearch2/DESCRIPTION’ ... OK +... +* checking for unstated dependencies in ‘tests’ ... OK +* checking tests ... OK + Running ‘test-all.R’ +* checking for unstated dependencies in vignettes ... OK +* checking package vignettes in ‘inst/doc’ ... OK +* checking running R code from vignettes ... NONE + ‘overview.pdf.asis’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 1 NOTE + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/lavaSearch2/old/lavaSearch2.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘lavaSearch2/DESCRIPTION’ ... OK +... +* checking for unstated dependencies in ‘tests’ ... OK +* checking tests ... OK + Running ‘test-all.R’ +* checking for unstated dependencies in vignettes ... OK +* checking package vignettes in ‘inst/doc’ ... OK +* checking running R code from vignettes ... NONE + ‘overview.pdf.asis’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 1 NOTE + + + + + +``` +# llbayesireg + +
+ +* Version: 1.0.0 +* GitHub: NA +* Source code: https://github.com/cran/llbayesireg +* Date/Publication: 2019-04-04 16:20:03 UTC +* Number of recursive dependencies: 60 + +Run `revdepcheck::cloud_details(, "llbayesireg")` for more info + +
+ +## In both + +* checking whether package ‘llbayesireg’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/llbayesireg/new/llbayesireg.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘llbayesireg’ ... +** package ‘llbayesireg’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** data +*** moving datasets to lazyload DB +** byte-compile and prepare package for lazy loading +Error in loadNamespace(i, c(lib.loc, .libPaths()), versionCheck = vI[[i]]) : + there is no package called ‘quantreg’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Execution halted +ERROR: lazy loading failed for package ‘llbayesireg’ +* removing ‘/tmp/workdir/llbayesireg/new/llbayesireg.Rcheck/llbayesireg’ + + +``` +### CRAN + +``` +* installing *source* package ‘llbayesireg’ ... +** package ‘llbayesireg’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** data +*** moving datasets to lazyload DB +** byte-compile and prepare package for lazy loading +Error in loadNamespace(i, c(lib.loc, .libPaths()), versionCheck = vI[[i]]) : + there is no package called ‘quantreg’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Execution halted +ERROR: lazy loading failed for package ‘llbayesireg’ +* removing ‘/tmp/workdir/llbayesireg/old/llbayesireg.Rcheck/llbayesireg’ + + +``` +# LorenzRegression + +
+ +* Version: 1.0.0 +* GitHub: NA +* Source code: https://github.com/cran/LorenzRegression +* Date/Publication: 2023-02-28 17:32:34 UTC +* Number of recursive dependencies: 63 + +Run `revdepcheck::cloud_details(, "LorenzRegression")` for more info + +
+ +## In both + +* checking whether package ‘LorenzRegression’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/LorenzRegression/new/LorenzRegression.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘LorenzRegression’ ... +** package ‘LorenzRegression’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C++ compiler: ‘g++ (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c GA_fitness.cpp -o GA_fitness.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c GA_meanrank.cpp -o GA_meanrank.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c PLR_derivative.cpp -o PLR_derivative.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c PLR_loss.cpp -o PLR_loss.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +... +** data +*** moving datasets to lazyload DB +** 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 ‘quantreg’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Execution halted +ERROR: lazy loading failed for package ‘LorenzRegression’ +* removing ‘/tmp/workdir/LorenzRegression/new/LorenzRegression.Rcheck/LorenzRegression’ + + +``` +### CRAN + +``` +* installing *source* package ‘LorenzRegression’ ... +** package ‘LorenzRegression’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C++ compiler: ‘g++ (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c GA_fitness.cpp -o GA_fitness.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c GA_meanrank.cpp -o GA_meanrank.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c PLR_derivative.cpp -o PLR_derivative.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c PLR_loss.cpp -o PLR_loss.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +... +** data +*** moving datasets to lazyload DB +** 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 ‘quantreg’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Execution halted +ERROR: lazy loading failed for package ‘LorenzRegression’ +* removing ‘/tmp/workdir/LorenzRegression/old/LorenzRegression.Rcheck/LorenzRegression’ + + +``` +# lsirm12pl + +
+ +* Version: 1.3.1 +* GitHub: NA +* Source code: https://github.com/cran/lsirm12pl +* Date/Publication: 2023-06-22 14:12:35 UTC +* Number of recursive dependencies: 123 + +Run `revdepcheck::cloud_details(, "lsirm12pl")` for more info + +
+ +## In both + +* checking whether package ‘lsirm12pl’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/lsirm12pl/new/lsirm12pl.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘lsirm12pl’ ... +** package ‘lsirm12pl’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C++ compiler: ‘g++ (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c log_likelihood.cpp -o log_likelihood.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c lsirm1pl.cpp -o lsirm1pl.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c lsirm1pl_fixed_gamma.cpp -o lsirm1pl_fixed_gamma.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c lsirm1pl_fixed_gamma_mar.cpp -o lsirm1pl_fixed_gamma_mar.o +... +** R +** data +*** moving datasets to lazyload DB +** byte-compile and prepare package for lazy loading +Error in loadNamespace(i, c(lib.loc, .libPaths()), versionCheck = vI[[i]]) : + there is no package called ‘quantreg’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Execution halted +ERROR: lazy loading failed for package ‘lsirm12pl’ +* removing ‘/tmp/workdir/lsirm12pl/new/lsirm12pl.Rcheck/lsirm12pl’ + + +``` +### CRAN + +``` +* installing *source* package ‘lsirm12pl’ ... +** package ‘lsirm12pl’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C++ compiler: ‘g++ (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c log_likelihood.cpp -o log_likelihood.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c lsirm1pl.cpp -o lsirm1pl.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c lsirm1pl_fixed_gamma.cpp -o lsirm1pl_fixed_gamma.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c lsirm1pl_fixed_gamma_mar.cpp -o lsirm1pl_fixed_gamma_mar.o +... +** R +** data +*** moving datasets to lazyload DB +** byte-compile and prepare package for lazy loading +Error in loadNamespace(i, c(lib.loc, .libPaths()), versionCheck = vI[[i]]) : + there is no package called ‘quantreg’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Execution halted +ERROR: lazy loading failed for package ‘lsirm12pl’ +* removing ‘/tmp/workdir/lsirm12pl/old/lsirm12pl.Rcheck/lsirm12pl’ + + +``` +# MachineShop + +
+ +* Version: 3.7.0 +* GitHub: https://github.com/brian-j-smith/MachineShop +* Source code: https://github.com/cran/MachineShop +* Date/Publication: 2023-09-18 14:00:02 UTC +* Number of recursive dependencies: 227 + +Run `revdepcheck::cloud_details(, "MachineShop")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/MachineShop/new/MachineShop.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘MachineShop/DESCRIPTION’ ... OK +... +* checking tests ... OK + Running ‘testthat.R’ +* checking for unstated dependencies in vignettes ... OK +* checking package vignettes in ‘inst/doc’ ... OK +* checking running R code from vignettes ... OK + ‘MLModels.Rmd’ using ‘UTF-8’... OK + ‘UserGuide.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 3 NOTEs + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/MachineShop/old/MachineShop.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘MachineShop/DESCRIPTION’ ... OK +... +* checking tests ... OK + Running ‘testthat.R’ +* checking for unstated dependencies in vignettes ... OK +* checking package vignettes in ‘inst/doc’ ... OK +* checking running R code from vignettes ... OK + ‘MLModels.Rmd’ using ‘UTF-8’... OK + ‘UserGuide.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 3 NOTEs + + + + + +``` +# marginaleffects + +
+ +* Version: 0.20.1 +* GitHub: https://github.com/vincentarelbundock/marginaleffects +* Source code: https://github.com/cran/marginaleffects +* Date/Publication: 2024-05-08 12:10:03 UTC +* Number of recursive dependencies: 438 + +Run `revdepcheck::cloud_details(, "marginaleffects")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/marginaleffects/new/marginaleffects.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘marginaleffects/DESCRIPTION’ ... OK +... +* checking for unstated dependencies in examples ... OK +* checking line endings in C/C++/Fortran sources/headers ... OK +* checking compiled code ... OK +* checking examples ... OK +* checking for unstated dependencies in ‘tests’ ... OK +* checking tests ... OK + Running ‘spelling.R’ + Running ‘tinytest.R’ +* DONE +Status: 2 NOTEs + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/marginaleffects/old/marginaleffects.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘marginaleffects/DESCRIPTION’ ... OK +... +* checking for unstated dependencies in examples ... OK +* checking line endings in C/C++/Fortran sources/headers ... OK +* checking compiled code ... OK +* checking examples ... OK +* checking for unstated dependencies in ‘tests’ ... OK +* checking tests ... OK + Running ‘spelling.R’ + Running ‘tinytest.R’ +* DONE +Status: 2 NOTEs + + + + + +``` +# mbsts + +
+ +* Version: 3.0 +* GitHub: NA +* Source code: https://github.com/cran/mbsts +* Date/Publication: 2023-01-07 01:10:02 UTC +* Number of recursive dependencies: 82 + +Run `revdepcheck::cloud_details(, "mbsts")` for more info + +
+ +## In both + +* checking whether package ‘mbsts’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/mbsts/new/mbsts.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘mbsts’ ... +** package ‘mbsts’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** 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 ‘quantreg’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Execution halted +ERROR: lazy loading failed for package ‘mbsts’ +* removing ‘/tmp/workdir/mbsts/new/mbsts.Rcheck/mbsts’ + + +``` +### CRAN + +``` +* installing *source* package ‘mbsts’ ... +** package ‘mbsts’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** 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 ‘quantreg’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Execution halted +ERROR: lazy loading failed for package ‘mbsts’ +* removing ‘/tmp/workdir/mbsts/old/mbsts.Rcheck/mbsts’ + + +``` +# MetabolicSurv + +
+ +* Version: 1.1.2 +* GitHub: https://github.com/OlajumokeEvangelina/MetabolicSurv +* Source code: https://github.com/cran/MetabolicSurv +* Date/Publication: 2021-06-11 08:30:02 UTC +* Number of recursive dependencies: 141 + +Run `revdepcheck::cloud_details(, "MetabolicSurv")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/MetabolicSurv/new/MetabolicSurv.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘MetabolicSurv/DESCRIPTION’ ... OK +... +* this is package ‘MetabolicSurv’ version ‘1.1.2’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘rms’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/MetabolicSurv/old/MetabolicSurv.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘MetabolicSurv/DESCRIPTION’ ... OK +... +* this is package ‘MetabolicSurv’ version ‘1.1.2’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘rms’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# MetaNet + +
+ +* Version: 0.1.2 +* GitHub: https://github.com/Asa12138/MetaNet +* Source code: https://github.com/cran/MetaNet +* Date/Publication: 2024-03-25 20:40:07 UTC +* Number of recursive dependencies: 161 + +Run `revdepcheck::cloud_details(, "MetaNet")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/MetaNet/new/MetaNet.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘MetaNet/DESCRIPTION’ ... OK +... + 6. └─cli::cli_abort(...) + 7. └─rlang::abort(...) +Execution halted +* checking for unstated dependencies in vignettes ... OK +* checking package vignettes in ‘inst/doc’ ... OK +* checking running R code from vignettes ... OK + ‘MetaNet.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 1 ERROR, 1 NOTE + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/MetaNet/old/MetaNet.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘MetaNet/DESCRIPTION’ ... OK +... +* checking installed files from ‘inst/doc’ ... OK +* checking files in ‘vignettes’ ... OK +* checking examples ... OK +* checking for unstated dependencies in vignettes ... OK +* checking package vignettes in ‘inst/doc’ ... OK +* checking running R code from vignettes ... OK + ‘MetaNet.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 1 NOTE + -Run `revdepcheck::cloud_details(, "JWileymisc")` for more info - -## In both -* checking whether package ‘JWileymisc’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/JWileymisc/new/JWileymisc.Rcheck/00install.out’ for details. - ``` +``` +# miWQS + +
+ +* Version: 0.4.4 +* GitHub: https://github.com/phargarten2/miWQS +* Source code: https://github.com/cran/miWQS +* Date/Publication: 2021-04-02 21:50:02 UTC +* Number of recursive dependencies: 151 + +Run `revdepcheck::cloud_details(, "miWQS")` for more info + +
+ +## In both + +* checking whether package ‘miWQS’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/miWQS/new/miWQS.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘miWQS’ ... +** package ‘miWQS’ 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(i, c(lib.loc, .libPaths()), versionCheck = vI[[i]]) : + there is no package called ‘quantreg’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Execution halted +ERROR: lazy loading failed for package ‘miWQS’ +* removing ‘/tmp/workdir/miWQS/new/miWQS.Rcheck/miWQS’ + + +``` +### CRAN + +``` +* installing *source* package ‘miWQS’ ... +** package ‘miWQS’ 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(i, c(lib.loc, .libPaths()), versionCheck = vI[[i]]) : + there is no package called ‘quantreg’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Execution halted +ERROR: lazy loading failed for package ‘miWQS’ +* removing ‘/tmp/workdir/miWQS/old/miWQS.Rcheck/miWQS’ + + +``` +# mlmts + +
+ +* Version: 1.1.1 +* GitHub: NA +* Source code: https://github.com/cran/mlmts +* Date/Publication: 2023-01-22 21:30:02 UTC +* Number of recursive dependencies: 242 + +Run `revdepcheck::cloud_details(, "mlmts")` for more info + +
+ +## In both + +* checking whether package ‘mlmts’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/mlmts/new/mlmts.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘mlmts’ ... +** package ‘mlmts’ 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 : package or namespace load failed for ‘quantspec’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): + there is no package called ‘quantreg’ +Error: unable to load R code in package ‘mlmts’ +Execution halted +ERROR: lazy loading failed for package ‘mlmts’ +* removing ‘/tmp/workdir/mlmts/new/mlmts.Rcheck/mlmts’ + + +``` +### CRAN + +``` +* installing *source* package ‘mlmts’ ... +** package ‘mlmts’ 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 : package or namespace load failed for ‘quantspec’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): + there is no package called ‘quantreg’ +Error: unable to load R code in package ‘mlmts’ +Execution halted +ERROR: lazy loading failed for package ‘mlmts’ +* removing ‘/tmp/workdir/mlmts/old/mlmts.Rcheck/mlmts’ + + +``` +# mlr + +
+ +* Version: 2.19.1 +* GitHub: https://github.com/mlr-org/mlr +* Source code: https://github.com/cran/mlr +* Date/Publication: 2022-09-29 13:30:14 UTC +* Number of recursive dependencies: 369 + +Run `revdepcheck::cloud_details(, "mlr")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/mlr/new/mlr.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘mlr/DESCRIPTION’ ... OK +... +* checking for unstated dependencies in ‘tests’ ... OK +* checking tests ... OK + Running ‘testthat.R’ +* checking for unstated dependencies in vignettes ... OK +* checking package vignettes in ‘inst/doc’ ... OK +* checking running R code from vignettes ... OK + ‘mlr.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 1 ERROR, 3 NOTEs + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/mlr/old/mlr.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘mlr/DESCRIPTION’ ... OK +... +* checking for unstated dependencies in ‘tests’ ... OK +* checking tests ... OK + Running ‘testthat.R’ +* checking for unstated dependencies in vignettes ... OK +* checking package vignettes in ‘inst/doc’ ... OK +* checking running R code from vignettes ... OK + ‘mlr.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 1 ERROR, 3 NOTEs + + + + + +``` +# MOSS + +
+ +* Version: 0.2.2 +* GitHub: https://github.com/agugonrey/MOSS +* Source code: https://github.com/cran/MOSS +* Date/Publication: 2022-03-25 15:50:05 UTC +* Number of recursive dependencies: 183 + +Run `revdepcheck::cloud_details(, "MOSS")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/MOSS/new/MOSS.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘MOSS/DESCRIPTION’ ... OK +... +--- failed re-building ‘MOSS_working_example.Rmd’ + +SUMMARY: processing the following file failed: + ‘MOSS_working_example.Rmd’ + +Error: Vignette re-building failed. +Execution halted + +* DONE +Status: 2 ERRORs, 2 NOTEs + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/MOSS/old/MOSS.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘MOSS/DESCRIPTION’ ... OK +... +--- failed re-building ‘MOSS_working_example.Rmd’ + +SUMMARY: processing the following file failed: + ‘MOSS_working_example.Rmd’ + +Error: Vignette re-building failed. +Execution halted + +* DONE +Status: 2 ERRORs, 2 NOTEs + + + + + +``` +# mrbayes + +
+ +* Version: 0.5.1 +* GitHub: https://github.com/okezie94/mrbayes +* Source code: https://github.com/cran/mrbayes +* Date/Publication: 2021-10-02 14:50:02 UTC +* Number of recursive dependencies: 189 + +Run `revdepcheck::cloud_details(, "mrbayes")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/mrbayes/new/mrbayes.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘mrbayes/DESCRIPTION’ ... OK +... +GNU make is a SystemRequirements. +* checking for portable use of $(BLAS_LIBS) and $(LAPACK_LIBS) ... OK +* checking use of PKG_*FLAGS in Makefiles ... OK +* checking compiled code ... OK +* checking examples ... OK +* checking for unstated dependencies in ‘tests’ ... OK +* checking tests ... OK + Running ‘testthat.R’ +* DONE +Status: 5 NOTEs + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/mrbayes/old/mrbayes.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘mrbayes/DESCRIPTION’ ... OK +... +GNU make is a SystemRequirements. +* checking for portable use of $(BLAS_LIBS) and $(LAPACK_LIBS) ... OK +* checking use of PKG_*FLAGS in Makefiles ... OK +* checking compiled code ... OK +* checking examples ... OK +* checking for unstated dependencies in ‘tests’ ... OK +* checking tests ... OK + Running ‘testthat.R’ +* DONE +Status: 5 NOTEs + + + + + +``` +# mstate + +
+ +* Version: 0.3.2 +* GitHub: https://github.com/hputter/mstate +* Source code: https://github.com/cran/mstate +* Date/Publication: 2021-11-08 11:50:02 UTC +* Number of recursive dependencies: 114 + +Run `revdepcheck::cloud_details(, "mstate")` for more info + +
-## Installation +## Error before installation ### Devel ``` -* installing *source* package ‘JWileymisc’ ... -** package ‘JWileymisc’ 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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +* using log directory ‘/tmp/workdir/mstate/new/mstate.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘mstate/DESCRIPTION’ ... OK +... +--- failed re-building ‘Tutorial.Rnw’ + +SUMMARY: processing the following files failed: + ‘visuals_demo.Rmd’ ‘Tutorial.Rnw’ + +Error: Vignette re-building failed. Execution halted -ERROR: lazy loading failed for package ‘JWileymisc’ -* removing ‘/tmp/workdir/JWileymisc/new/JWileymisc.Rcheck/JWileymisc’ + +* DONE +Status: 2 ERRORs, 1 NOTE + + + ``` ### CRAN ``` -* installing *source* package ‘JWileymisc’ ... -** package ‘JWileymisc’ 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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +* using log directory ‘/tmp/workdir/mstate/old/mstate.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘mstate/DESCRIPTION’ ... OK +... +--- failed re-building ‘Tutorial.Rnw’ + +SUMMARY: processing the following file failed: + ‘Tutorial.Rnw’ + +Error: Vignette re-building failed. Execution halted -ERROR: lazy loading failed for package ‘JWileymisc’ -* removing ‘/tmp/workdir/JWileymisc/old/JWileymisc.Rcheck/JWileymisc’ + +* DONE +Status: 1 NOTE + + + ``` -# kmc +# Multiaovbay
-* Version: 0.4-2 -* GitHub: https://github.com/yfyang86/kmc -* Source code: https://github.com/cran/kmc -* Date/Publication: 2022-11-22 08:30:02 UTC -* Number of recursive dependencies: 61 +* Version: 0.1.0 +* GitHub: NA +* Source code: https://github.com/cran/Multiaovbay +* Date/Publication: 2023-03-17 17:20:02 UTC +* Number of recursive dependencies: 160 -Run `revdepcheck::cloud_details(, "kmc")` for more info +Run `revdepcheck::cloud_details(, "Multiaovbay")` for more info
## In both -* checking whether package ‘kmc’ can be installed ... ERROR +* checking whether package ‘Multiaovbay’ can be installed ... ERROR ``` Installation failed. - See ‘/tmp/workdir/kmc/new/kmc.Rcheck/00install.out’ for details. + See ‘/tmp/workdir/Multiaovbay/new/Multiaovbay.Rcheck/00install.out’ for details. ``` ## Installation @@ -3406,197 +7302,209 @@ Run `revdepcheck::cloud_details(, "kmc")` for more info ### Devel ``` -* installing *source* package ‘kmc’ ... -** package ‘kmc’ successfully unpacked and MD5 sums checked +* installing *source* package ‘Multiaovbay’ ... +** package ‘Multiaovbay’ successfully unpacked and MD5 sums checked ** using staged installation -** libs -using C compiler: ‘gcc (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ -using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c RcppExport.cpp -o RcppExport.o -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c kmc.cpp -o kmc.o -gcc -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c kmc_init.c -o kmc_init.o -gcc -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c surv2.c -o surv2.o -g++ -std=gnu++17 -shared -L/opt/R/4.3.1/lib/R/lib -L/usr/local/lib -o kmc.so RcppExport.o kmc.o kmc_init.o surv2.o -L/opt/R/4.3.1/lib/R/lib -lR -installing to /tmp/workdir/kmc/new/kmc.Rcheck/00LOCK-kmc/00new/kmc/libs ** R ** byte-compile and prepare package for lazy loading -Error: package or namespace load failed for ‘emplik’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is being loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace Execution halted -ERROR: lazy loading failed for package ‘kmc’ -* removing ‘/tmp/workdir/kmc/new/kmc.Rcheck/kmc’ +ERROR: lazy loading failed for package ‘Multiaovbay’ +* removing ‘/tmp/workdir/Multiaovbay/new/Multiaovbay.Rcheck/Multiaovbay’ ``` ### CRAN ``` -* installing *source* package ‘kmc’ ... -** package ‘kmc’ successfully unpacked and MD5 sums checked +* installing *source* package ‘Multiaovbay’ ... +** package ‘Multiaovbay’ successfully unpacked and MD5 sums checked ** using staged installation -** libs -using C compiler: ‘gcc (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ -using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c RcppExport.cpp -o RcppExport.o -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c kmc.cpp -o kmc.o -gcc -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c kmc_init.c -o kmc_init.o -gcc -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c surv2.c -o surv2.o -g++ -std=gnu++17 -shared -L/opt/R/4.3.1/lib/R/lib -L/usr/local/lib -o kmc.so RcppExport.o kmc.o kmc_init.o surv2.o -L/opt/R/4.3.1/lib/R/lib -lR -installing to /tmp/workdir/kmc/old/kmc.Rcheck/00LOCK-kmc/00new/kmc/libs ** R ** byte-compile and prepare package for lazy loading -Error: package or namespace load failed for ‘emplik’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is being loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace Execution halted -ERROR: lazy loading failed for package ‘kmc’ -* removing ‘/tmp/workdir/kmc/old/kmc.Rcheck/kmc’ +ERROR: lazy loading failed for package ‘Multiaovbay’ +* removing ‘/tmp/workdir/Multiaovbay/old/Multiaovbay.Rcheck/Multiaovbay’ ``` -# L2E +# multilevelTools
-* Version: 2.0 -* GitHub: NA -* Source code: https://github.com/cran/L2E -* Date/Publication: 2022-09-08 21:13:00 UTC -* Number of recursive dependencies: 65 +* Version: 0.1.1 +* GitHub: https://github.com/JWiley/multilevelTools +* Source code: https://github.com/cran/multilevelTools +* Date/Publication: 2020-03-04 09:50:02 UTC +* Number of recursive dependencies: 163 -Run `revdepcheck::cloud_details(, "L2E")` for more info +Run `revdepcheck::cloud_details(, "multilevelTools")` for more info
-## In both - -* checking whether package ‘L2E’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/L2E/new/L2E.Rcheck/00install.out’ for details. - ``` - -## Installation +## Error before installation ### Devel ``` -* installing *source* package ‘L2E’ ... -** package ‘L2E’ 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: package or namespace load failed for ‘osqp’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): - namespace ‘Matrix’ 1.5-4.1 is being loaded, but >= 1.6.1 is required -Execution halted -ERROR: lazy loading failed for package ‘L2E’ -* removing ‘/tmp/workdir/L2E/new/L2E.Rcheck/L2E’ +* using log directory ‘/tmp/workdir/multilevelTools/new/multilevelTools.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘multilevelTools/DESCRIPTION’ ... OK +... +* checking if there is a namespace ... OK +* checking for executable files ... OK +* checking for hidden files and directories ... OK +* checking for portable file names ... OK +* checking for sufficient/correct file permissions ... OK +* checking whether package ‘multilevelTools’ can be installed ... ERROR +Installation failed. +See ‘/tmp/workdir/multilevelTools/new/multilevelTools.Rcheck/00install.out’ for details. +* DONE +Status: 1 ERROR + + + ``` ### CRAN ``` -* installing *source* package ‘L2E’ ... -** package ‘L2E’ 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: package or namespace load failed for ‘osqp’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): - namespace ‘Matrix’ 1.5-4.1 is being loaded, but >= 1.6.1 is required -Execution halted -ERROR: lazy loading failed for package ‘L2E’ -* removing ‘/tmp/workdir/L2E/old/L2E.Rcheck/L2E’ +* using log directory ‘/tmp/workdir/multilevelTools/old/multilevelTools.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘multilevelTools/DESCRIPTION’ ... OK +... +* checking if there is a namespace ... OK +* checking for executable files ... OK +* checking for hidden files and directories ... OK +* checking for portable file names ... OK +* checking for sufficient/correct file permissions ... OK +* checking whether package ‘multilevelTools’ can be installed ... ERROR +Installation failed. +See ‘/tmp/workdir/multilevelTools/old/multilevelTools.Rcheck/00install.out’ for details. +* DONE +Status: 1 ERROR + + + ``` -# llbayesireg +# multipleOutcomes
-* Version: 1.0.0 +* Version: 0.4 * GitHub: NA -* Source code: https://github.com/cran/llbayesireg -* Date/Publication: 2019-04-04 16:20:03 UTC -* Number of recursive dependencies: 61 +* Source code: https://github.com/cran/multipleOutcomes +* Date/Publication: 2024-05-30 15:00:03 UTC +* Number of recursive dependencies: 182 -Run `revdepcheck::cloud_details(, "llbayesireg")` for more info +Run `revdepcheck::cloud_details(, "multipleOutcomes")` for more info
-## In both - -* checking whether package ‘llbayesireg’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/llbayesireg/new/llbayesireg.Rcheck/00install.out’ for details. - ``` - -## Installation +## Error before installation ### Devel ``` -* installing *source* package ‘llbayesireg’ ... -** package ‘llbayesireg’ successfully unpacked and MD5 sums checked -** using staged installation -** R -** data -*** moving datasets to lazyload DB -** byte-compile and prepare package for lazy loading -Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘llbayesireg’ -* removing ‘/tmp/workdir/llbayesireg/new/llbayesireg.Rcheck/llbayesireg’ +* using log directory ‘/tmp/workdir/multipleOutcomes/new/multipleOutcomes.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘multipleOutcomes/DESCRIPTION’ ... OK +... +* checking installed files from ‘inst/doc’ ... OK +* checking files in ‘vignettes’ ... OK +* checking examples ... OK +* checking for unstated dependencies in vignettes ... OK +* checking package vignettes in ‘inst/doc’ ... OK +* checking running R code from vignettes ... OK + ‘test.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: OK + + + ``` ### CRAN ``` -* installing *source* package ‘llbayesireg’ ... -** package ‘llbayesireg’ successfully unpacked and MD5 sums checked -** using staged installation -** R -** data -*** moving datasets to lazyload DB -** byte-compile and prepare package for lazy loading -Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘llbayesireg’ -* removing ‘/tmp/workdir/llbayesireg/old/llbayesireg.Rcheck/llbayesireg’ +* using log directory ‘/tmp/workdir/multipleOutcomes/old/multipleOutcomes.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘multipleOutcomes/DESCRIPTION’ ... OK +... +* checking installed files from ‘inst/doc’ ... OK +* checking files in ‘vignettes’ ... OK +* checking examples ... OK +* checking for unstated dependencies in vignettes ... OK +* checking package vignettes in ‘inst/doc’ ... OK +* checking running R code from vignettes ... OK + ‘test.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: OK + + + ``` -# LorenzRegression +# netcmc
-* Version: 1.0.0 +* Version: 1.0.2 * GitHub: NA -* Source code: https://github.com/cran/LorenzRegression -* Date/Publication: 2023-02-28 17:32:34 UTC -* Number of recursive dependencies: 63 +* Source code: https://github.com/cran/netcmc +* Date/Publication: 2022-11-08 22:30:15 UTC +* Number of recursive dependencies: 61 -Run `revdepcheck::cloud_details(, "LorenzRegression")` for more info +Run `revdepcheck::cloud_details(, "netcmc")` for more info
## In both -* checking whether package ‘LorenzRegression’ can be installed ... ERROR +* checking whether package ‘netcmc’ can be installed ... ERROR ``` Installation failed. - See ‘/tmp/workdir/LorenzRegression/new/LorenzRegression.Rcheck/00install.out’ for details. + See ‘/tmp/workdir/netcmc/new/netcmc.Rcheck/00install.out’ for details. ``` ## Installation @@ -3604,77 +7512,77 @@ Run `revdepcheck::cloud_details(, "LorenzRegression")` for more info ### Devel ``` -* installing *source* package ‘LorenzRegression’ ... -** package ‘LorenzRegression’ successfully unpacked and MD5 sums checked +* installing *source* package ‘netcmc’ ... +** package ‘netcmc’ successfully unpacked and MD5 sums checked ** using staged installation ** libs -using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c GA_fitness.cpp -o GA_fitness.o -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c GA_meanrank.cpp -o GA_meanrank.o -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c PLR_derivative.cpp -o PLR_derivative.o -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c PLR_loss.cpp -o PLR_loss.o -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +using C++ compiler: ‘g++ (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ +using C++11 +g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppProgress/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppProgress/include' -I/usr/local/include -fpic -g -O2 -c choleskyDecompositionRcppConversion.cpp -o choleskyDecompositionRcppConversion.o +g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppProgress/include' -I/usr/local/include -fpic -g -O2 -c doubleMatrixMultiplicationRcpp.cpp -o doubleMatrixMultiplicationRcpp.o +g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppProgress/include' -I/usr/local/include -fpic -g -O2 -c doubleVectorMultiplicationRcpp.cpp -o doubleVectorMultiplicationRcpp.o ... -** data -*** moving datasets to lazyload DB -** inst +g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppProgress/include' -I/usr/local/include -fpic -g -O2 -c vectorVectorTransposeMultiplicationRcpp.cpp -o vectorVectorTransposeMultiplicationRcpp.o +g++ -std=gnu++11 -shared -L/opt/R/4.3.1/lib/R/lib -L/usr/local/lib -o netcmc.so RcppExports.o choleskyDecompositionRcppConversion.o doubleMatrixMultiplicationRcpp.o doubleVectorMultiplicationRcpp.o eigenValuesRcppConversion.o getDiagonalMatrix.o getExp.o getExpDividedByOnePlusExp.o getMeanCenteredRandomEffects.o getMultivariateBinomialNetworkLerouxDIC.o getMultivariateBinomialNetworkLerouxFittedValuesAndLikelihoodForDICEveryIteration.o getMultivariateGaussianNetworkLerouxDIC.o getMultivariateGaussianNetworkLerouxFittedValuesAndLikelihoodForDICEveryIteration.o getMultivariatePoissonNetworkLerouxDIC.o getMultivariatePoissonNetworkLerouxFittedValuesAndLikelihoodForDICEveryIteration.o getNonZeroEntries.o getSubvector.o getSubvectorIndecies.o getSumExpNetwork.o getSumExpNetworkIndecies.o getSumExpNetworkLeroux.o getSumExpNetworkLerouxIndecies.o getSumLogExp.o getSumLogExpIndecies.o getSumVector.o getTripletForm.o getUnivariateBinomialNetworkLerouxDIC.o getUnivariateBinomialNetworkLerouxFittedValuesAndLikelihoodForDICEveryIteration.o getUnivariateGaussianNetworkLerouxDIC.o getUnivariateGaussianNetworkLerouxFittedValuesAndLikelihoodForDICEveryIteration.o getUnivariatePoissonNetworkDIC.o getUnivariatePoissonNetworkFittedValuesAndLikelihoodForDICEveryIteration.o getUnivariatePoissonNetworkLerouxDIC.o getUnivariatePoissonNetworkLerouxFittedValuesAndLikelihoodForDICEveryIteration.o getVectorMean.o matrixInverseRcppConversion.o matrixMatrixAdditionRcpp.o matrixMatrixSubtractionRcpp.o matrixVectorMultiplicationRcpp.o multivariateBinomialNetworkLerouxAllUpdate.o multivariateBinomialNetworkLerouxBetaUpdate.o multivariateBinomialNetworkLerouxRhoUpdate.o multivariateBinomialNetworkLerouxSingleUpdate.o multivariateBinomialNetworkLerouxSpatialRandomEffectsUpdate.o multivariateBinomialNetworkLerouxTauSquaredUpdate.o multivariateBinomialNetworkLerouxURandomEffectsUpdate.o multivariateBinomialNetworkLerouxVRandomEffectsUpdate.o multivariateBinomialNetworkLerouxVarianceCovarianceUUpdate.o multivariateBinomialNetworkRandAllUpdate.o multivariateBinomialNetworkRandSingleUpdate.o multivariateGaussianNetworkLerouxAllMHUpdate.o multivariateGaussianNetworkLerouxBetaUpdate.o multivariateGaussianNetworkLerouxRhoUpdate.o multivariateGaussianNetworkLerouxSigmaSquaredEUpdate.o multivariateGaussianNetworkLerouxSingleMHUpdate.o multivariateGaussianNetworkLerouxSpatialRandomEffectsMHUpdate.o multivariateGaussianNetworkLerouxTauSquaredUpdate.o multivariateGaussianNetworkLerouxURandomEffectsUpdate.o multivariateGaussianNetworkLerouxVarianceCovarianceUUpdate.o multivariateGaussianNetworkRandAllUpdate.o multivariateGaussianNetworkRandSingleUpdate.o multivariateGaussianNetworkRandVRandomEffectsUpdate.o multivariatePoissonNetworkLerouxAllUpdate.o multivariatePoissonNetworkLerouxBetaUpdate.o multivariatePoissonNetworkLerouxRhoUpdate.o multivariatePoissonNetworkLerouxSingleUpdate.o multivariatePoissonNetworkLerouxSpatialRandomEffectsUpdate.o multivariatePoissonNetworkLerouxTauSquaredUpdate.o multivariatePoissonNetworkLerouxURandomEffectsUpdate.o multivariatePoissonNetworkLerouxVRandomEffectsUpdate.o multivariatePoissonNetworkLerouxVarianceCovarianceUUpdate.o multivariatePoissonNetworkRandAllUpdate.o multivariatePoissonNetworkRandSingleUpdate.o sumMatrix.o univariateBinomialNetworkLerouxAllUpdate.o univariateBinomialNetworkLerouxBetaUpdate.o univariateBinomialNetworkLerouxRhoUpdate.o univariateBinomialNetworkLerouxSigmaSquaredUpdate.o univariateBinomialNetworkLerouxSingleUpdate.o univariateBinomialNetworkLerouxSpatialRandomEffectsUpdate.o univariateBinomialNetworkLerouxTauSquaredUpdate.o univariateBinomialNetworkLerouxURandomEffectsUpdate.o univariateGaussianNetworkLerouxAllMHUpdate.o univariateGaussianNetworkLerouxBetaUpdate.o univariateGaussianNetworkLerouxRhoUpdate.o univariateGaussianNetworkLerouxSigmaSquaredEUpdate.o univariateGaussianNetworkLerouxSigmaSquaredUUpdate.o univariateGaussianNetworkLerouxSingleMHUpdate.o univariateGaussianNetworkLerouxSpatialRandomEffectsMHUpdate.o univariateGaussianNetworkLerouxTauSquaredUpdate.o univariateGaussianNetworkLerouxURandomEffectsUpdate.o univariatePoissonNetworkLerouxAllUpdate.o univariatePoissonNetworkLerouxBetaUpdate.o univariatePoissonNetworkLerouxRhoUpdate.o univariatePoissonNetworkLerouxSigmaSquaredUpdate.o univariatePoissonNetworkLerouxSingleUpdate.o univariatePoissonNetworkLerouxSpatialRandomEffectsUpdate.o univariatePoissonNetworkLerouxTauSquaredUpdate.o univariatePoissonNetworkLerouxURandomEffectsUpdate.o vectorTransposeVectorMultiplicationRcpp.o vectorVectorTransposeMultiplicationRcpp.o -llapack -lblas -lgfortran -lm -lquadmath -L/opt/R/4.3.1/lib/R/lib -lR +installing to /tmp/workdir/netcmc/new/netcmc.Rcheck/00LOCK-netcmc/00new/netcmc/libs +** R ** byte-compile and prepare package for lazy loading -Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Error: package or namespace load failed for ‘MCMCpack’ in loadNamespace(i, c(lib.loc, .libPaths()), versionCheck = vI[[i]]): + there is no package called ‘quantreg’ Execution halted -ERROR: lazy loading failed for package ‘LorenzRegression’ -* removing ‘/tmp/workdir/LorenzRegression/new/LorenzRegression.Rcheck/LorenzRegression’ +ERROR: lazy loading failed for package ‘netcmc’ +* removing ‘/tmp/workdir/netcmc/new/netcmc.Rcheck/netcmc’ ``` ### CRAN ``` -* installing *source* package ‘LorenzRegression’ ... -** package ‘LorenzRegression’ successfully unpacked and MD5 sums checked +* installing *source* package ‘netcmc’ ... +** package ‘netcmc’ successfully unpacked and MD5 sums checked ** using staged installation ** libs -using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c GA_fitness.cpp -o GA_fitness.o -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c GA_meanrank.cpp -o GA_meanrank.o -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c PLR_derivative.cpp -o PLR_derivative.o -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c PLR_loss.cpp -o PLR_loss.o -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +using C++ compiler: ‘g++ (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ +using C++11 +g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppProgress/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppProgress/include' -I/usr/local/include -fpic -g -O2 -c choleskyDecompositionRcppConversion.cpp -o choleskyDecompositionRcppConversion.o +g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppProgress/include' -I/usr/local/include -fpic -g -O2 -c doubleMatrixMultiplicationRcpp.cpp -o doubleMatrixMultiplicationRcpp.o +g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppProgress/include' -I/usr/local/include -fpic -g -O2 -c doubleVectorMultiplicationRcpp.cpp -o doubleVectorMultiplicationRcpp.o ... -** data -*** moving datasets to lazyload DB -** inst +g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppProgress/include' -I/usr/local/include -fpic -g -O2 -c vectorVectorTransposeMultiplicationRcpp.cpp -o vectorVectorTransposeMultiplicationRcpp.o +g++ -std=gnu++11 -shared -L/opt/R/4.3.1/lib/R/lib -L/usr/local/lib -o netcmc.so RcppExports.o choleskyDecompositionRcppConversion.o doubleMatrixMultiplicationRcpp.o doubleVectorMultiplicationRcpp.o eigenValuesRcppConversion.o getDiagonalMatrix.o getExp.o getExpDividedByOnePlusExp.o getMeanCenteredRandomEffects.o getMultivariateBinomialNetworkLerouxDIC.o getMultivariateBinomialNetworkLerouxFittedValuesAndLikelihoodForDICEveryIteration.o getMultivariateGaussianNetworkLerouxDIC.o getMultivariateGaussianNetworkLerouxFittedValuesAndLikelihoodForDICEveryIteration.o getMultivariatePoissonNetworkLerouxDIC.o getMultivariatePoissonNetworkLerouxFittedValuesAndLikelihoodForDICEveryIteration.o getNonZeroEntries.o getSubvector.o getSubvectorIndecies.o getSumExpNetwork.o getSumExpNetworkIndecies.o getSumExpNetworkLeroux.o getSumExpNetworkLerouxIndecies.o getSumLogExp.o getSumLogExpIndecies.o getSumVector.o getTripletForm.o getUnivariateBinomialNetworkLerouxDIC.o getUnivariateBinomialNetworkLerouxFittedValuesAndLikelihoodForDICEveryIteration.o getUnivariateGaussianNetworkLerouxDIC.o getUnivariateGaussianNetworkLerouxFittedValuesAndLikelihoodForDICEveryIteration.o getUnivariatePoissonNetworkDIC.o getUnivariatePoissonNetworkFittedValuesAndLikelihoodForDICEveryIteration.o getUnivariatePoissonNetworkLerouxDIC.o getUnivariatePoissonNetworkLerouxFittedValuesAndLikelihoodForDICEveryIteration.o getVectorMean.o matrixInverseRcppConversion.o matrixMatrixAdditionRcpp.o matrixMatrixSubtractionRcpp.o matrixVectorMultiplicationRcpp.o multivariateBinomialNetworkLerouxAllUpdate.o multivariateBinomialNetworkLerouxBetaUpdate.o multivariateBinomialNetworkLerouxRhoUpdate.o multivariateBinomialNetworkLerouxSingleUpdate.o multivariateBinomialNetworkLerouxSpatialRandomEffectsUpdate.o multivariateBinomialNetworkLerouxTauSquaredUpdate.o multivariateBinomialNetworkLerouxURandomEffectsUpdate.o multivariateBinomialNetworkLerouxVRandomEffectsUpdate.o multivariateBinomialNetworkLerouxVarianceCovarianceUUpdate.o multivariateBinomialNetworkRandAllUpdate.o multivariateBinomialNetworkRandSingleUpdate.o multivariateGaussianNetworkLerouxAllMHUpdate.o multivariateGaussianNetworkLerouxBetaUpdate.o multivariateGaussianNetworkLerouxRhoUpdate.o multivariateGaussianNetworkLerouxSigmaSquaredEUpdate.o multivariateGaussianNetworkLerouxSingleMHUpdate.o multivariateGaussianNetworkLerouxSpatialRandomEffectsMHUpdate.o multivariateGaussianNetworkLerouxTauSquaredUpdate.o multivariateGaussianNetworkLerouxURandomEffectsUpdate.o multivariateGaussianNetworkLerouxVarianceCovarianceUUpdate.o multivariateGaussianNetworkRandAllUpdate.o multivariateGaussianNetworkRandSingleUpdate.o multivariateGaussianNetworkRandVRandomEffectsUpdate.o multivariatePoissonNetworkLerouxAllUpdate.o multivariatePoissonNetworkLerouxBetaUpdate.o multivariatePoissonNetworkLerouxRhoUpdate.o multivariatePoissonNetworkLerouxSingleUpdate.o multivariatePoissonNetworkLerouxSpatialRandomEffectsUpdate.o multivariatePoissonNetworkLerouxTauSquaredUpdate.o multivariatePoissonNetworkLerouxURandomEffectsUpdate.o multivariatePoissonNetworkLerouxVRandomEffectsUpdate.o multivariatePoissonNetworkLerouxVarianceCovarianceUUpdate.o multivariatePoissonNetworkRandAllUpdate.o multivariatePoissonNetworkRandSingleUpdate.o sumMatrix.o univariateBinomialNetworkLerouxAllUpdate.o univariateBinomialNetworkLerouxBetaUpdate.o univariateBinomialNetworkLerouxRhoUpdate.o univariateBinomialNetworkLerouxSigmaSquaredUpdate.o univariateBinomialNetworkLerouxSingleUpdate.o univariateBinomialNetworkLerouxSpatialRandomEffectsUpdate.o univariateBinomialNetworkLerouxTauSquaredUpdate.o univariateBinomialNetworkLerouxURandomEffectsUpdate.o univariateGaussianNetworkLerouxAllMHUpdate.o univariateGaussianNetworkLerouxBetaUpdate.o univariateGaussianNetworkLerouxRhoUpdate.o univariateGaussianNetworkLerouxSigmaSquaredEUpdate.o univariateGaussianNetworkLerouxSigmaSquaredUUpdate.o univariateGaussianNetworkLerouxSingleMHUpdate.o univariateGaussianNetworkLerouxSpatialRandomEffectsMHUpdate.o univariateGaussianNetworkLerouxTauSquaredUpdate.o univariateGaussianNetworkLerouxURandomEffectsUpdate.o univariatePoissonNetworkLerouxAllUpdate.o univariatePoissonNetworkLerouxBetaUpdate.o univariatePoissonNetworkLerouxRhoUpdate.o univariatePoissonNetworkLerouxSigmaSquaredUpdate.o univariatePoissonNetworkLerouxSingleUpdate.o univariatePoissonNetworkLerouxSpatialRandomEffectsUpdate.o univariatePoissonNetworkLerouxTauSquaredUpdate.o univariatePoissonNetworkLerouxURandomEffectsUpdate.o vectorTransposeVectorMultiplicationRcpp.o vectorVectorTransposeMultiplicationRcpp.o -llapack -lblas -lgfortran -lm -lquadmath -L/opt/R/4.3.1/lib/R/lib -lR +installing to /tmp/workdir/netcmc/old/netcmc.Rcheck/00LOCK-netcmc/00new/netcmc/libs +** R ** byte-compile and prepare package for lazy loading -Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Error: package or namespace load failed for ‘MCMCpack’ in loadNamespace(i, c(lib.loc, .libPaths()), versionCheck = vI[[i]]): + there is no package called ‘quantreg’ Execution halted -ERROR: lazy loading failed for package ‘LorenzRegression’ -* removing ‘/tmp/workdir/LorenzRegression/old/LorenzRegression.Rcheck/LorenzRegression’ +ERROR: lazy loading failed for package ‘netcmc’ +* removing ‘/tmp/workdir/netcmc/old/netcmc.Rcheck/netcmc’ ``` -# lsirm12pl +# NetworkChange
-* Version: 1.3.1 -* GitHub: NA -* Source code: https://github.com/cran/lsirm12pl -* Date/Publication: 2023-06-22 14:12:35 UTC -* Number of recursive dependencies: 123 +* Version: 0.8 +* GitHub: https://github.com/jongheepark/NetworkChange +* Source code: https://github.com/cran/NetworkChange +* Date/Publication: 2022-03-04 07:30:02 UTC +* Number of recursive dependencies: 131 -Run `revdepcheck::cloud_details(, "lsirm12pl")` for more info +Run `revdepcheck::cloud_details(, "NetworkChange")` for more info
## In both -* checking whether package ‘lsirm12pl’ can be installed ... ERROR +* checking whether package ‘NetworkChange’ can be installed ... ERROR ``` Installation failed. - See ‘/tmp/workdir/lsirm12pl/new/lsirm12pl.Rcheck/00install.out’ for details. + See ‘/tmp/workdir/NetworkChange/new/NetworkChange.Rcheck/00install.out’ for details. ``` ## Installation @@ -3682,77 +7590,133 @@ Run `revdepcheck::cloud_details(, "lsirm12pl")` for more info ### Devel ``` -* installing *source* package ‘lsirm12pl’ ... -** package ‘lsirm12pl’ successfully unpacked and MD5 sums checked +* installing *source* package ‘NetworkChange’ ... +** package ‘NetworkChange’ successfully unpacked and MD5 sums checked ** using staged installation -** libs -using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c log_likelihood.cpp -o log_likelihood.o -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c lsirm1pl.cpp -o lsirm1pl.o -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c lsirm1pl_fixed_gamma.cpp -o lsirm1pl_fixed_gamma.o -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c lsirm1pl_fixed_gamma_mar.cpp -o lsirm1pl_fixed_gamma_mar.o -... ** R ** data -*** moving datasets to lazyload DB ** byte-compile and prepare package for lazy loading -Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Error: package or namespace load failed for ‘MCMCpack’ in loadNamespace(i, c(lib.loc, .libPaths()), versionCheck = vI[[i]]): + there is no package called ‘quantreg’ Execution halted -ERROR: lazy loading failed for package ‘lsirm12pl’ -* removing ‘/tmp/workdir/lsirm12pl/new/lsirm12pl.Rcheck/lsirm12pl’ +ERROR: lazy loading failed for package ‘NetworkChange’ +* removing ‘/tmp/workdir/NetworkChange/new/NetworkChange.Rcheck/NetworkChange’ ``` ### CRAN ``` -* installing *source* package ‘lsirm12pl’ ... -** package ‘lsirm12pl’ successfully unpacked and MD5 sums checked +* installing *source* package ‘NetworkChange’ ... +** package ‘NetworkChange’ successfully unpacked and MD5 sums checked ** using staged installation -** libs -using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c log_likelihood.cpp -o log_likelihood.o -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c lsirm1pl.cpp -o lsirm1pl.o -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c lsirm1pl_fixed_gamma.cpp -o lsirm1pl_fixed_gamma.o -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c lsirm1pl_fixed_gamma_mar.cpp -o lsirm1pl_fixed_gamma_mar.o -... ** R ** data -*** moving datasets to lazyload DB ** byte-compile and prepare package for lazy loading -Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Error: package or namespace load failed for ‘MCMCpack’ in loadNamespace(i, c(lib.loc, .libPaths()), versionCheck = vI[[i]]): + there is no package called ‘quantreg’ Execution halted -ERROR: lazy loading failed for package ‘lsirm12pl’ -* removing ‘/tmp/workdir/lsirm12pl/old/lsirm12pl.Rcheck/lsirm12pl’ +ERROR: lazy loading failed for package ‘NetworkChange’ +* removing ‘/tmp/workdir/NetworkChange/old/NetworkChange.Rcheck/NetworkChange’ ``` -# mbsts +# neutralitytestr
-* Version: 3.0 +* Version: 0.0.3 +* GitHub: https://github.com/marcjwilliams1/neutralitytestr +* Source code: https://github.com/cran/neutralitytestr +* Date/Publication: 2021-02-16 18:00:06 UTC +* Number of recursive dependencies: 95 + +Run `revdepcheck::cloud_details(, "neutralitytestr")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/neutralitytestr/new/neutralitytestr.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘neutralitytestr/DESCRIPTION’ ... OK +... +* this is package ‘neutralitytestr’ version ‘0.0.3’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘ggpmisc’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/neutralitytestr/old/neutralitytestr.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘neutralitytestr/DESCRIPTION’ ... OK +... +* this is package ‘neutralitytestr’ version ‘0.0.3’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘ggpmisc’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# NMADiagT + +
+ +* Version: 0.1.2 * GitHub: NA -* Source code: https://github.com/cran/mbsts -* Date/Publication: 2023-01-07 01:10:02 UTC -* Number of recursive dependencies: 82 +* Source code: https://github.com/cran/NMADiagT +* Date/Publication: 2020-02-26 07:00:02 UTC +* Number of recursive dependencies: 79 -Run `revdepcheck::cloud_details(, "mbsts")` for more info +Run `revdepcheck::cloud_details(, "NMADiagT")` for more info
## In both -* checking whether package ‘mbsts’ can be installed ... ERROR +* checking whether package ‘NMADiagT’ can be installed ... ERROR ``` Installation failed. - See ‘/tmp/workdir/mbsts/new/mbsts.Rcheck/00install.out’ for details. + See ‘/tmp/workdir/NMADiagT/new/NMADiagT.Rcheck/00install.out’ for details. ``` ## Installation @@ -3760,131 +7724,135 @@ Run `revdepcheck::cloud_details(, "mbsts")` for more info ### Devel ``` -* installing *source* package ‘mbsts’ ... -** package ‘mbsts’ successfully unpacked and MD5 sums checked +* installing *source* package ‘NMADiagT’ ... +** package ‘NMADiagT’ 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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Error in loadNamespace(i, c(lib.loc, .libPaths()), versionCheck = vI[[i]]) : + there is no package called ‘quantreg’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart Execution halted -ERROR: lazy loading failed for package ‘mbsts’ -* removing ‘/tmp/workdir/mbsts/new/mbsts.Rcheck/mbsts’ +ERROR: lazy loading failed for package ‘NMADiagT’ +* removing ‘/tmp/workdir/NMADiagT/new/NMADiagT.Rcheck/NMADiagT’ ``` ### CRAN ``` -* installing *source* package ‘mbsts’ ... -** package ‘mbsts’ successfully unpacked and MD5 sums checked +* installing *source* package ‘NMADiagT’ ... +** package ‘NMADiagT’ 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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Error in loadNamespace(i, c(lib.loc, .libPaths()), versionCheck = vI[[i]]) : + there is no package called ‘quantreg’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart Execution halted -ERROR: lazy loading failed for package ‘mbsts’ -* removing ‘/tmp/workdir/mbsts/old/mbsts.Rcheck/mbsts’ +ERROR: lazy loading failed for package ‘NMADiagT’ +* removing ‘/tmp/workdir/NMADiagT/old/NMADiagT.Rcheck/NMADiagT’ ``` -# MendelianRandomization +# obliqueRSF
-* Version: 0.10.0 +* Version: 0.1.2 * GitHub: NA -* Source code: https://github.com/cran/MendelianRandomization -* Date/Publication: 2024-04-12 10:10:02 UTC -* Number of recursive dependencies: 88 +* Source code: https://github.com/cran/obliqueRSF +* Date/Publication: 2022-08-28 20:50:02 UTC +* Number of recursive dependencies: 117 -Run `revdepcheck::cloud_details(, "MendelianRandomization")` for more info +Run `revdepcheck::cloud_details(, "obliqueRSF")` for more info
-## In both - -* checking whether package ‘MendelianRandomization’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/MendelianRandomization/new/MendelianRandomization.Rcheck/00install.out’ for details. - ``` - -## Installation +## Error before installation ### Devel ``` -* installing *source* package ‘MendelianRandomization’ ... -** package ‘MendelianRandomization’ successfully unpacked and MD5 sums checked -** using staged installation -** libs -using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c mvmrcML.cpp -o mvmrcML.o -g++ -std=gnu++17 -shared -L/opt/R/4.3.1/lib/R/lib -L/usr/local/lib -o MendelianRandomization.so RcppExports.o mvmrcML.o -fopenmp -llapack -lblas -lgfortran -lm -lquadmath -L/opt/R/4.3.1/lib/R/lib -lR -installing to /tmp/workdir/MendelianRandomization/new/MendelianRandomization.Rcheck/00LOCK-MendelianRandomization/00new/MendelianRandomization/libs -** R -** inst -** byte-compile and prepare package for lazy loading -Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘MendelianRandomization’ -* removing ‘/tmp/workdir/MendelianRandomization/new/MendelianRandomization.Rcheck/MendelianRandomization’ +* using log directory ‘/tmp/workdir/obliqueRSF/new/obliqueRSF.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘obliqueRSF/DESCRIPTION’ ... OK +... +* checking for missing documentation entries ... OK +* checking for code/documentation mismatches ... OK +* checking Rd \usage sections ... OK +* checking Rd contents ... OK +* checking for unstated dependencies in examples ... OK +* checking line endings in C/C++/Fortran sources/headers ... OK +* checking compiled code ... OK +* checking examples ... OK +* DONE +Status: OK + + + ``` ### CRAN ``` -* installing *source* package ‘MendelianRandomization’ ... -** package ‘MendelianRandomization’ successfully unpacked and MD5 sums checked -** using staged installation -** libs -using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c mvmrcML.cpp -o mvmrcML.o -g++ -std=gnu++17 -shared -L/opt/R/4.3.1/lib/R/lib -L/usr/local/lib -o MendelianRandomization.so RcppExports.o mvmrcML.o -fopenmp -llapack -lblas -lgfortran -lm -lquadmath -L/opt/R/4.3.1/lib/R/lib -lR -installing to /tmp/workdir/MendelianRandomization/old/MendelianRandomization.Rcheck/00LOCK-MendelianRandomization/00new/MendelianRandomization/libs -** R -** inst -** byte-compile and prepare package for lazy loading -Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘MendelianRandomization’ -* removing ‘/tmp/workdir/MendelianRandomization/old/MendelianRandomization.Rcheck/MendelianRandomization’ +* using log directory ‘/tmp/workdir/obliqueRSF/old/obliqueRSF.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘obliqueRSF/DESCRIPTION’ ... OK +... +* checking for missing documentation entries ... OK +* checking for code/documentation mismatches ... OK +* checking Rd \usage sections ... OK +* checking Rd contents ... OK +* checking for unstated dependencies in examples ... OK +* checking line endings in C/C++/Fortran sources/headers ... OK +* checking compiled code ... OK +* checking examples ... OK +* DONE +Status: OK + + + ``` -# MetabolicSurv +# optweight
-* Version: 1.1.2 -* GitHub: https://github.com/OlajumokeEvangelina/MetabolicSurv -* Source code: https://github.com/cran/MetabolicSurv -* Date/Publication: 2021-06-11 08:30:02 UTC -* Number of recursive dependencies: 142 +* Version: 0.2.5 +* GitHub: NA +* Source code: https://github.com/cran/optweight +* Date/Publication: 2019-09-16 15:40:02 UTC +* Number of recursive dependencies: 55 -Run `revdepcheck::cloud_details(, "MetabolicSurv")` for more info +Run `revdepcheck::cloud_details(, "optweight")` for more info
## In both -* checking whether package ‘MetabolicSurv’ can be installed ... ERROR +* checking whether package ‘optweight’ can be installed ... ERROR ``` Installation failed. - See ‘/tmp/workdir/MetabolicSurv/new/MetabolicSurv.Rcheck/00install.out’ for details. + See ‘/tmp/workdir/optweight/new/optweight.Rcheck/00install.out’ for details. ``` ## Installation @@ -3892,127 +7860,133 @@ Run `revdepcheck::cloud_details(, "MetabolicSurv")` for more info ### Devel ``` -* installing *source* package ‘MetabolicSurv’ ... -** package ‘MetabolicSurv’ successfully unpacked and MD5 sums checked +* installing *source* package ‘optweight’ ... +** package ‘optweight’ 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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.1 is required Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace Execution halted -ERROR: lazy loading failed for package ‘MetabolicSurv’ -* removing ‘/tmp/workdir/MetabolicSurv/new/MetabolicSurv.Rcheck/MetabolicSurv’ +ERROR: lazy loading failed for package ‘optweight’ +* removing ‘/tmp/workdir/optweight/new/optweight.Rcheck/optweight’ ``` ### CRAN ``` -* installing *source* package ‘MetabolicSurv’ ... -** package ‘MetabolicSurv’ successfully unpacked and MD5 sums checked +* installing *source* package ‘optweight’ ... +** package ‘optweight’ 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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.1 is required Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace Execution halted -ERROR: lazy loading failed for package ‘MetabolicSurv’ -* removing ‘/tmp/workdir/MetabolicSurv/old/MetabolicSurv.Rcheck/MetabolicSurv’ +ERROR: lazy loading failed for package ‘optweight’ +* removing ‘/tmp/workdir/optweight/old/optweight.Rcheck/optweight’ ``` -# miWQS +# ormPlot
-* Version: 0.4.4 -* GitHub: https://github.com/phargarten2/miWQS -* Source code: https://github.com/cran/miWQS -* Date/Publication: 2021-04-02 21:50:02 UTC -* Number of recursive dependencies: 152 +* Version: 0.3.6 +* GitHub: NA +* Source code: https://github.com/cran/ormPlot +* Date/Publication: 2023-09-13 14:40:02 UTC +* Number of recursive dependencies: 96 -Run `revdepcheck::cloud_details(, "miWQS")` for more info +Run `revdepcheck::cloud_details(, "ormPlot")` for more info
-## In both - -* checking whether package ‘miWQS’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/miWQS/new/miWQS.Rcheck/00install.out’ for details. - ``` - -## Installation +## Error before installation ### Devel ``` -* installing *source* package ‘miWQS’ ... -** package ‘miWQS’ 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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘miWQS’ -* removing ‘/tmp/workdir/miWQS/new/miWQS.Rcheck/miWQS’ +* using log directory ‘/tmp/workdir/ormPlot/new/ormPlot.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘ormPlot/DESCRIPTION’ ... OK +... +* this is package ‘ormPlot’ version ‘0.3.6’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘rms’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + ``` ### CRAN ``` -* installing *source* package ‘miWQS’ ... -** package ‘miWQS’ 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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘miWQS’ -* removing ‘/tmp/workdir/miWQS/old/miWQS.Rcheck/miWQS’ +* using log directory ‘/tmp/workdir/ormPlot/old/ormPlot.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘ormPlot/DESCRIPTION’ ... OK +... +* this is package ‘ormPlot’ version ‘0.3.6’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘rms’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + ``` -# mlmts +# OVtool
-* Version: 1.1.1 +* Version: 1.0.3 * GitHub: NA -* Source code: https://github.com/cran/mlmts -* Date/Publication: 2023-01-22 21:30:02 UTC -* Number of recursive dependencies: 241 +* Source code: https://github.com/cran/OVtool +* Date/Publication: 2021-11-02 08:10:07 UTC +* Number of recursive dependencies: 158 -Run `revdepcheck::cloud_details(, "mlmts")` for more info +Run `revdepcheck::cloud_details(, "OVtool")` for more info
## In both -* checking whether package ‘mlmts’ can be installed ... ERROR +* checking whether package ‘OVtool’ can be installed ... ERROR ``` Installation failed. - See ‘/tmp/workdir/mlmts/new/mlmts.Rcheck/00install.out’ for details. + See ‘/tmp/workdir/OVtool/new/OVtool.Rcheck/00install.out’ for details. ``` ## Installation @@ -4020,317 +7994,441 @@ Run `revdepcheck::cloud_details(, "mlmts")` for more info ### Devel ``` -* installing *source* package ‘mlmts’ ... -** package ‘mlmts’ successfully unpacked and MD5 sums checked +* installing *source* package ‘OVtool’ ... +** package ‘OVtool’ 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 : package or namespace load failed for ‘quantspec’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): +Error: package or namespace load failed for ‘twang’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Error: unable to load R code in package ‘mlmts’ Execution halted -ERROR: lazy loading failed for package ‘mlmts’ -* removing ‘/tmp/workdir/mlmts/new/mlmts.Rcheck/mlmts’ +ERROR: lazy loading failed for package ‘OVtool’ +* removing ‘/tmp/workdir/OVtool/new/OVtool.Rcheck/OVtool’ ``` ### CRAN ``` -* installing *source* package ‘mlmts’ ... -** package ‘mlmts’ successfully unpacked and MD5 sums checked +* installing *source* package ‘OVtool’ ... +** package ‘OVtool’ 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 : package or namespace load failed for ‘quantspec’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): +Error: package or namespace load failed for ‘twang’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Error: unable to load R code in package ‘mlmts’ Execution halted -ERROR: lazy loading failed for package ‘mlmts’ -* removing ‘/tmp/workdir/mlmts/old/mlmts.Rcheck/mlmts’ +ERROR: lazy loading failed for package ‘OVtool’ +* removing ‘/tmp/workdir/OVtool/old/OVtool.Rcheck/OVtool’ ``` -# MRZero +# pagoda2
-* Version: 0.2.0 -* GitHub: NA -* Source code: https://github.com/cran/MRZero -* Date/Publication: 2024-04-14 09:30:03 UTC -* Number of recursive dependencies: 82 +* Version: 1.0.12 +* GitHub: https://github.com/kharchenkolab/pagoda2 +* Source code: https://github.com/cran/pagoda2 +* Date/Publication: 2024-02-27 00:50:02 UTC +* Number of recursive dependencies: 163 -Run `revdepcheck::cloud_details(, "MRZero")` for more info +Run `revdepcheck::cloud_details(, "pagoda2")` for more info
-## In both +## Error before installation -* checking whether package ‘MRZero’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/MRZero/new/MRZero.Rcheck/00install.out’ for details. - ``` +### Devel -## Installation +``` +* using log directory ‘/tmp/workdir/pagoda2/new/pagoda2.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘pagoda2/DESCRIPTION’ ... OK +... +* checking for GNU extensions in Makefiles ... OK +* checking for portable use of $(BLAS_LIBS) and $(LAPACK_LIBS) ... OK +* checking use of PKG_*FLAGS in Makefiles ... OK +* checking compiled code ... OK +* checking examples ... OK +* checking for unstated dependencies in ‘tests’ ... OK +* checking tests ... OK + Running ‘testthat.R’ +* DONE +Status: 2 NOTEs + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/pagoda2/old/pagoda2.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘pagoda2/DESCRIPTION’ ... OK +... +* checking for GNU extensions in Makefiles ... OK +* checking for portable use of $(BLAS_LIBS) and $(LAPACK_LIBS) ... OK +* checking use of PKG_*FLAGS in Makefiles ... OK +* checking compiled code ... OK +* checking examples ... OK +* checking for unstated dependencies in ‘tests’ ... OK +* checking tests ... OK + Running ‘testthat.R’ +* DONE +Status: 2 NOTEs + + + + + +``` +# pammtools + +
+ +* Version: 0.5.93 +* GitHub: https://github.com/adibender/pammtools +* Source code: https://github.com/cran/pammtools +* Date/Publication: 2024-02-25 10:10:02 UTC +* Number of recursive dependencies: 125 + +Run `revdepcheck::cloud_details(, "pammtools")` for more info + +
+ +## Error before installation ### Devel ``` -* installing *source* package ‘MRZero’ ... -** package ‘MRZero’ successfully unpacked and MD5 sums checked -** using staged installation -** R -** byte-compile and prepare package for lazy loading -Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘MRZero’ -* removing ‘/tmp/workdir/MRZero/new/MRZero.Rcheck/MRZero’ +* using log directory ‘/tmp/workdir/pammtools/new/pammtools.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘pammtools/DESCRIPTION’ ... OK +... +* checking data for non-ASCII characters ... OK +* checking LazyData ... OK +* checking data for ASCII and uncompressed saves ... OK +* checking R/sysdata.rda ... OK +* checking examples ... OK +* checking for unstated dependencies in ‘tests’ ... OK +* checking tests ... OK + Running ‘testthat.R’ +* DONE +Status: OK + + + ``` ### CRAN ``` -* installing *source* package ‘MRZero’ ... -** package ‘MRZero’ successfully unpacked and MD5 sums checked -** using staged installation -** R -** byte-compile and prepare package for lazy loading -Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘MRZero’ -* removing ‘/tmp/workdir/MRZero/old/MRZero.Rcheck/MRZero’ +* using log directory ‘/tmp/workdir/pammtools/old/pammtools.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘pammtools/DESCRIPTION’ ... OK +... +* checking data for non-ASCII characters ... OK +* checking LazyData ... OK +* checking data for ASCII and uncompressed saves ... OK +* checking R/sysdata.rda ... OK +* checking examples ... OK +* checking for unstated dependencies in ‘tests’ ... OK +* checking tests ... OK + Running ‘testthat.R’ +* DONE +Status: OK + + + ``` -# Multiaovbay +# pander
-* Version: 0.1.0 -* GitHub: NA -* Source code: https://github.com/cran/Multiaovbay -* Date/Publication: 2023-03-17 17:20:02 UTC -* Number of recursive dependencies: 161 +* Version: 0.6.5 +* GitHub: https://github.com/rapporter/pander +* Source code: https://github.com/cran/pander +* Date/Publication: 2022-03-18 09:20:02 UTC +* Number of recursive dependencies: 108 -Run `revdepcheck::cloud_details(, "Multiaovbay")` for more info +Run `revdepcheck::cloud_details(, "pander")` for more info
-## In both +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/pander/new/pander.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘pander/DESCRIPTION’ ... OK +... +Error: Pandoc does not support newlines in simple or Rmarkdown table format! +Execution halted -* checking whether package ‘Multiaovbay’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/Multiaovbay/new/Multiaovbay.Rcheck/00install.out’ for details. - ``` + ‘evals.Rmd’ using ‘UTF-8’... OK + ‘knitr.Rmd’ using ‘UTF-8’... failed + ‘pander.Rmd’ using ‘UTF-8’... OK + ‘pandoc_table.Rmd’ using ‘UTF-8’... failed +* checking re-building of vignette outputs ... OK +* DONE +Status: 1 ERROR, 1 NOTE -## Installation -### Devel -``` -* installing *source* package ‘Multiaovbay’ ... -** package ‘Multiaovbay’ successfully unpacked and MD5 sums checked -** using staged installation -** R -** byte-compile and prepare package for lazy loading -Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - namespace ‘Matrix’ 1.5-4.1 is being loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘Multiaovbay’ -* removing ‘/tmp/workdir/Multiaovbay/new/Multiaovbay.Rcheck/Multiaovbay’ ``` ### CRAN ``` -* installing *source* package ‘Multiaovbay’ ... -** package ‘Multiaovbay’ successfully unpacked and MD5 sums checked -** using staged installation -** R -** byte-compile and prepare package for lazy loading -Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - namespace ‘Matrix’ 1.5-4.1 is being loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +* using log directory ‘/tmp/workdir/pander/old/pander.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘pander/DESCRIPTION’ ... OK +... +Error: Pandoc does not support newlines in simple or Rmarkdown table format! Execution halted -ERROR: lazy loading failed for package ‘Multiaovbay’ -* removing ‘/tmp/workdir/Multiaovbay/old/Multiaovbay.Rcheck/Multiaovbay’ + + ‘evals.Rmd’ using ‘UTF-8’... OK + ‘knitr.Rmd’ using ‘UTF-8’... failed + ‘pander.Rmd’ using ‘UTF-8’... OK + ‘pandoc_table.Rmd’ using ‘UTF-8’... failed +* checking re-building of vignette outputs ... OK +* DONE +Status: 1 ERROR, 1 NOTE + + + ``` -# multilevelTools +# parameters
-* Version: 0.1.1 -* GitHub: https://github.com/JWiley/multilevelTools -* Source code: https://github.com/cran/multilevelTools -* Date/Publication: 2020-03-04 09:50:02 UTC -* Number of recursive dependencies: 164 +* Version: 0.21.7 +* GitHub: https://github.com/easystats/parameters +* Source code: https://github.com/cran/parameters +* Date/Publication: 2024-05-14 08:13:17 UTC +* Number of recursive dependencies: 440 -Run `revdepcheck::cloud_details(, "multilevelTools")` for more info +Run `revdepcheck::cloud_details(, "parameters")` for more info
-## In both - -* checking whether package ‘multilevelTools’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/multilevelTools/new/multilevelTools.Rcheck/00install.out’ for details. - ``` - -## Installation +## Error before installation ### Devel ``` -* installing *source* package ‘multilevelTools’ ... -** package ‘multilevelTools’ 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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘multilevelTools’ -* removing ‘/tmp/workdir/multilevelTools/new/multilevelTools.Rcheck/multilevelTools’ +* using log directory ‘/tmp/workdir/parameters/new/parameters.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘parameters/DESCRIPTION’ ... OK +... +* checking for unstated dependencies in ‘tests’ ... OK +* checking tests ... OK + Running ‘testthat.R’ +* checking for unstated dependencies in vignettes ... OK +* checking package vignettes in ‘inst/doc’ ... OK +* checking running R code from vignettes ... OK + ‘overview_of_vignettes.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 1 NOTE + + + ``` ### CRAN ``` -* installing *source* package ‘multilevelTools’ ... -** package ‘multilevelTools’ 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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘multilevelTools’ -* removing ‘/tmp/workdir/multilevelTools/old/multilevelTools.Rcheck/multilevelTools’ +* using log directory ‘/tmp/workdir/parameters/old/parameters.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘parameters/DESCRIPTION’ ... OK +... +* checking for unstated dependencies in ‘tests’ ... OK +* checking tests ... OK + Running ‘testthat.R’ +* checking for unstated dependencies in vignettes ... OK +* checking package vignettes in ‘inst/doc’ ... OK +* checking running R code from vignettes ... OK + ‘overview_of_vignettes.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 1 NOTE + + + ``` -# multinma +# PAsso
-* Version: 0.6.1 -* GitHub: https://github.com/dmphillippo/multinma -* Source code: https://github.com/cran/multinma -* Date/Publication: 2024-03-06 01:00:05 UTC -* Number of recursive dependencies: 152 +* Version: 0.1.10 +* GitHub: https://github.com/XiaoruiZhu/PAsso +* Source code: https://github.com/cran/PAsso +* Date/Publication: 2021-06-18 09:20:08 UTC +* Number of recursive dependencies: 179 -Run `revdepcheck::cloud_details(, "multinma")` for more info +Run `revdepcheck::cloud_details(, "PAsso")` for more info
-## In both - -* checking whether package ‘multinma’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/multinma/new/multinma.Rcheck/00install.out’ for details. - ``` - -## Installation +## Error before installation ### Devel ``` -* installing *source* package ‘multinma’ ... -** package ‘multinma’ successfully unpacked and MD5 sums checked -** using staged installation -** libs -using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ -using C++17 +* using log directory ‘/tmp/workdir/PAsso/new/PAsso.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘PAsso/DESCRIPTION’ ... OK +... +* checking LazyData ... OK +* checking data for ASCII and uncompressed saves ... OK +* checking line endings in C/C++/Fortran sources/headers ... OK +* checking compiled code ... OK +* checking examples ... OK +* checking for unstated dependencies in ‘tests’ ... OK +* checking tests ... OK + Running ‘testthat.R’ +* DONE +Status: 2 NOTEs + -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I"../inst/include" -I"/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src" -DBOOST_DISABLE_ASSERTS -DEIGEN_NO_DEBUG -DBOOST_MATH_OVERFLOW_ERROR_POLICY=errno_on_error -DUSE_STANC3 -D_HAS_AUTO_PTR_ETC=0 -I'/opt/R/4.3.1/lib/R/site-library/BH/include' -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppEigen/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -I'/opt/R/4.3.1/lib/R/site-library/rstan/include' -I'/opt/R/4.3.1/lib/R/site-library/StanHeaders/include' -I/usr/local/include -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -D_REENTRANT -DSTAN_THREADS -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o -In file included from /opt/R/4.3.1/lib/R/site-library/RcppEigen/include/Eigen/Core:205, -... -In file included from stanExports_survival_mspline.cc:5: -stanExports_survival_mspline.h: In constructor ‘model_survival_mspline_namespace::model_survival_mspline::model_survival_mspline(stan::io::var_context&, unsigned int, std::ostream*)’: -stanExports_survival_mspline.h:2252:3: note: variable tracking size limit exceeded with ‘-fvar-tracking-assignments’, retrying without - 2252 | model_survival_mspline(stan::io::var_context& context__, unsigned int - | ^~~~~~~~~~~~~~~~~~~~~~ -g++: fatal error: Killed signal terminated program cc1plus -compilation terminated. -make: *** [/opt/R/4.3.1/lib/R/etc/Makeconf:198: stanExports_survival_mspline.o] Error 1 -ERROR: compilation failed for package ‘multinma’ -* removing ‘/tmp/workdir/multinma/new/multinma.Rcheck/multinma’ ``` ### CRAN ``` -* installing *source* package ‘multinma’ ... -** package ‘multinma’ successfully unpacked and MD5 sums checked -** using staged installation -** libs -using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ -using C++17 +* using log directory ‘/tmp/workdir/PAsso/old/PAsso.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘PAsso/DESCRIPTION’ ... OK +... +* checking LazyData ... OK +* checking data for ASCII and uncompressed saves ... OK +* checking line endings in C/C++/Fortran sources/headers ... OK +* checking compiled code ... OK +* checking examples ... OK +* checking for unstated dependencies in ‘tests’ ... OK +* checking tests ... OK + Running ‘testthat.R’ +* DONE +Status: 2 NOTEs + -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I"../inst/include" -I"/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src" -DBOOST_DISABLE_ASSERTS -DEIGEN_NO_DEBUG -DBOOST_MATH_OVERFLOW_ERROR_POLICY=errno_on_error -DUSE_STANC3 -D_HAS_AUTO_PTR_ETC=0 -I'/opt/R/4.3.1/lib/R/site-library/BH/include' -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppEigen/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -I'/opt/R/4.3.1/lib/R/site-library/rstan/include' -I'/opt/R/4.3.1/lib/R/site-library/StanHeaders/include' -I/usr/local/include -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -D_REENTRANT -DSTAN_THREADS -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o -In file included from /opt/R/4.3.1/lib/R/site-library/RcppEigen/include/Eigen/Core:205, -... -In file included from stanExports_survival_mspline.cc:5: -stanExports_survival_mspline.h: In constructor ‘model_survival_mspline_namespace::model_survival_mspline::model_survival_mspline(stan::io::var_context&, unsigned int, std::ostream*)’: -stanExports_survival_mspline.h:2252:3: note: variable tracking size limit exceeded with ‘-fvar-tracking-assignments’, retrying without - 2252 | model_survival_mspline(stan::io::var_context& context__, unsigned int - | ^~~~~~~~~~~~~~~~~~~~~~ -g++: fatal error: Killed signal terminated program cc1plus -compilation terminated. -make: *** [/opt/R/4.3.1/lib/R/etc/Makeconf:198: stanExports_survival_mspline.o] Error 1 -ERROR: compilation failed for package ‘multinma’ -* removing ‘/tmp/workdir/multinma/old/multinma.Rcheck/multinma’ ``` -# NCA +# paths
-* Version: 4.0.1 +* Version: 0.1.1 * GitHub: NA -* Source code: https://github.com/cran/NCA -* Date/Publication: 2024-02-23 09:30:15 UTC -* Number of recursive dependencies: 99 +* Source code: https://github.com/cran/paths +* Date/Publication: 2021-06-18 08:40:02 UTC +* Number of recursive dependencies: 103 -Run `revdepcheck::cloud_details(, "NCA")` for more info +Run `revdepcheck::cloud_details(, "paths")` for more info
## In both -* checking whether package ‘NCA’ can be installed ... ERROR +* checking whether package ‘paths’ can be installed ... ERROR ``` Installation failed. - See ‘/tmp/workdir/NCA/new/NCA.Rcheck/00install.out’ for details. + See ‘/tmp/workdir/paths/new/paths.Rcheck/00install.out’ for details. ``` ## Installation @@ -4338,137 +8436,215 @@ Run `revdepcheck::cloud_details(, "NCA")` for more info ### Devel ``` -* installing *source* package ‘NCA’ ... -** package ‘NCA’ successfully unpacked and MD5 sums checked +* installing *source* package ‘paths’ ... +** package ‘paths’ 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]]) : namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace Execution halted -ERROR: lazy loading failed for package ‘NCA’ -* removing ‘/tmp/workdir/NCA/new/NCA.Rcheck/NCA’ +ERROR: lazy loading failed for package ‘paths’ +* removing ‘/tmp/workdir/paths/new/paths.Rcheck/paths’ ``` ### CRAN ``` -* installing *source* package ‘NCA’ ... -** package ‘NCA’ successfully unpacked and MD5 sums checked +* installing *source* package ‘paths’ ... +** package ‘paths’ 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]]) : namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace Execution halted -ERROR: lazy loading failed for package ‘NCA’ -* removing ‘/tmp/workdir/NCA/old/NCA.Rcheck/NCA’ +ERROR: lazy loading failed for package ‘paths’ +* removing ‘/tmp/workdir/paths/old/paths.Rcheck/paths’ ``` -# netcmc +# pctax
-* Version: 1.0.2 -* GitHub: NA -* Source code: https://github.com/cran/netcmc -* Date/Publication: 2022-11-08 22:30:15 UTC -* Number of recursive dependencies: 61 +* Version: 0.1.1 +* GitHub: https://github.com/Asa12138/pctax +* Source code: https://github.com/cran/pctax +* Date/Publication: 2024-04-10 17:10:05 UTC +* Number of recursive dependencies: 267 -Run `revdepcheck::cloud_details(, "netcmc")` for more info +Run `revdepcheck::cloud_details(, "pctax")` for more info
-## In both - -* checking whether package ‘netcmc’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/netcmc/new/netcmc.Rcheck/00install.out’ for details. - ``` - -## Installation +## Error before installation ### Devel ``` -* installing *source* package ‘netcmc’ ... -** package ‘netcmc’ successfully unpacked and MD5 sums checked -** using staged installation -** libs -using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ -using C++11 -g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppProgress/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o -g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppProgress/include' -I/usr/local/include -fpic -g -O2 -c choleskyDecompositionRcppConversion.cpp -o choleskyDecompositionRcppConversion.o -g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppProgress/include' -I/usr/local/include -fpic -g -O2 -c doubleMatrixMultiplicationRcpp.cpp -o doubleMatrixMultiplicationRcpp.o -g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppProgress/include' -I/usr/local/include -fpic -g -O2 -c doubleVectorMultiplicationRcpp.cpp -o doubleVectorMultiplicationRcpp.o +* using log directory ‘/tmp/workdir/pctax/new/pctax.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘pctax/DESCRIPTION’ ... OK ... -g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppProgress/include' -I/usr/local/include -fpic -g -O2 -c vectorVectorTransposeMultiplicationRcpp.cpp -o vectorVectorTransposeMultiplicationRcpp.o -g++ -std=gnu++11 -shared -L/opt/R/4.3.1/lib/R/lib -L/usr/local/lib -o netcmc.so RcppExports.o choleskyDecompositionRcppConversion.o doubleMatrixMultiplicationRcpp.o doubleVectorMultiplicationRcpp.o eigenValuesRcppConversion.o getDiagonalMatrix.o getExp.o getExpDividedByOnePlusExp.o getMeanCenteredRandomEffects.o getMultivariateBinomialNetworkLerouxDIC.o getMultivariateBinomialNetworkLerouxFittedValuesAndLikelihoodForDICEveryIteration.o getMultivariateGaussianNetworkLerouxDIC.o getMultivariateGaussianNetworkLerouxFittedValuesAndLikelihoodForDICEveryIteration.o getMultivariatePoissonNetworkLerouxDIC.o getMultivariatePoissonNetworkLerouxFittedValuesAndLikelihoodForDICEveryIteration.o getNonZeroEntries.o getSubvector.o getSubvectorIndecies.o getSumExpNetwork.o getSumExpNetworkIndecies.o getSumExpNetworkLeroux.o getSumExpNetworkLerouxIndecies.o getSumLogExp.o getSumLogExpIndecies.o getSumVector.o getTripletForm.o getUnivariateBinomialNetworkLerouxDIC.o getUnivariateBinomialNetworkLerouxFittedValuesAndLikelihoodForDICEveryIteration.o getUnivariateGaussianNetworkLerouxDIC.o getUnivariateGaussianNetworkLerouxFittedValuesAndLikelihoodForDICEveryIteration.o getUnivariatePoissonNetworkDIC.o getUnivariatePoissonNetworkFittedValuesAndLikelihoodForDICEveryIteration.o getUnivariatePoissonNetworkLerouxDIC.o getUnivariatePoissonNetworkLerouxFittedValuesAndLikelihoodForDICEveryIteration.o getVectorMean.o matrixInverseRcppConversion.o matrixMatrixAdditionRcpp.o matrixMatrixSubtractionRcpp.o matrixVectorMultiplicationRcpp.o multivariateBinomialNetworkLerouxAllUpdate.o multivariateBinomialNetworkLerouxBetaUpdate.o multivariateBinomialNetworkLerouxRhoUpdate.o multivariateBinomialNetworkLerouxSingleUpdate.o multivariateBinomialNetworkLerouxSpatialRandomEffectsUpdate.o multivariateBinomialNetworkLerouxTauSquaredUpdate.o multivariateBinomialNetworkLerouxURandomEffectsUpdate.o multivariateBinomialNetworkLerouxVRandomEffectsUpdate.o multivariateBinomialNetworkLerouxVarianceCovarianceUUpdate.o multivariateBinomialNetworkRandAllUpdate.o multivariateBinomialNetworkRandSingleUpdate.o multivariateGaussianNetworkLerouxAllMHUpdate.o multivariateGaussianNetworkLerouxBetaUpdate.o multivariateGaussianNetworkLerouxRhoUpdate.o multivariateGaussianNetworkLerouxSigmaSquaredEUpdate.o multivariateGaussianNetworkLerouxSingleMHUpdate.o multivariateGaussianNetworkLerouxSpatialRandomEffectsMHUpdate.o multivariateGaussianNetworkLerouxTauSquaredUpdate.o multivariateGaussianNetworkLerouxURandomEffectsUpdate.o multivariateGaussianNetworkLerouxVarianceCovarianceUUpdate.o multivariateGaussianNetworkRandAllUpdate.o multivariateGaussianNetworkRandSingleUpdate.o multivariateGaussianNetworkRandVRandomEffectsUpdate.o multivariatePoissonNetworkLerouxAllUpdate.o multivariatePoissonNetworkLerouxBetaUpdate.o multivariatePoissonNetworkLerouxRhoUpdate.o multivariatePoissonNetworkLerouxSingleUpdate.o multivariatePoissonNetworkLerouxSpatialRandomEffectsUpdate.o multivariatePoissonNetworkLerouxTauSquaredUpdate.o multivariatePoissonNetworkLerouxURandomEffectsUpdate.o multivariatePoissonNetworkLerouxVRandomEffectsUpdate.o multivariatePoissonNetworkLerouxVarianceCovarianceUUpdate.o multivariatePoissonNetworkRandAllUpdate.o multivariatePoissonNetworkRandSingleUpdate.o sumMatrix.o univariateBinomialNetworkLerouxAllUpdate.o univariateBinomialNetworkLerouxBetaUpdate.o univariateBinomialNetworkLerouxRhoUpdate.o univariateBinomialNetworkLerouxSigmaSquaredUpdate.o univariateBinomialNetworkLerouxSingleUpdate.o univariateBinomialNetworkLerouxSpatialRandomEffectsUpdate.o univariateBinomialNetworkLerouxTauSquaredUpdate.o univariateBinomialNetworkLerouxURandomEffectsUpdate.o univariateGaussianNetworkLerouxAllMHUpdate.o univariateGaussianNetworkLerouxBetaUpdate.o univariateGaussianNetworkLerouxRhoUpdate.o univariateGaussianNetworkLerouxSigmaSquaredEUpdate.o univariateGaussianNetworkLerouxSigmaSquaredUUpdate.o univariateGaussianNetworkLerouxSingleMHUpdate.o univariateGaussianNetworkLerouxSpatialRandomEffectsMHUpdate.o univariateGaussianNetworkLerouxTauSquaredUpdate.o univariateGaussianNetworkLerouxURandomEffectsUpdate.o univariatePoissonNetworkLerouxAllUpdate.o univariatePoissonNetworkLerouxBetaUpdate.o univariatePoissonNetworkLerouxRhoUpdate.o univariatePoissonNetworkLerouxSigmaSquaredUpdate.o univariatePoissonNetworkLerouxSingleUpdate.o univariatePoissonNetworkLerouxSpatialRandomEffectsUpdate.o univariatePoissonNetworkLerouxTauSquaredUpdate.o univariatePoissonNetworkLerouxURandomEffectsUpdate.o vectorTransposeVectorMultiplicationRcpp.o vectorVectorTransposeMultiplicationRcpp.o -llapack -lblas -lgfortran -lm -lquadmath -L/opt/R/4.3.1/lib/R/lib -lR -installing to /tmp/workdir/netcmc/new/netcmc.Rcheck/00LOCK-netcmc/00new/netcmc/libs -** R -** byte-compile and prepare package for lazy loading -Error: package or namespace load failed for ‘MCMCpack’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Execution halted -ERROR: lazy loading failed for package ‘netcmc’ -* removing ‘/tmp/workdir/netcmc/new/netcmc.Rcheck/netcmc’ +1. ggpmisc +Calls: -> lib_ps +Execution halted +* checking for unstated dependencies in vignettes ... OK +* checking package vignettes in ‘inst/doc’ ... OK +* checking running R code from vignettes ... OK + ‘pctax.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 1 ERROR, 1 NOTE + + + ``` ### CRAN ``` -* installing *source* package ‘netcmc’ ... -** package ‘netcmc’ successfully unpacked and MD5 sums checked -** using staged installation -** libs -using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ -using C++11 -g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppProgress/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o -g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppProgress/include' -I/usr/local/include -fpic -g -O2 -c choleskyDecompositionRcppConversion.cpp -o choleskyDecompositionRcppConversion.o -g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppProgress/include' -I/usr/local/include -fpic -g -O2 -c doubleMatrixMultiplicationRcpp.cpp -o doubleMatrixMultiplicationRcpp.o -g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppProgress/include' -I/usr/local/include -fpic -g -O2 -c doubleVectorMultiplicationRcpp.cpp -o doubleVectorMultiplicationRcpp.o +* using log directory ‘/tmp/workdir/pctax/old/pctax.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘pctax/DESCRIPTION’ ... OK ... -g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppProgress/include' -I/usr/local/include -fpic -g -O2 -c vectorVectorTransposeMultiplicationRcpp.cpp -o vectorVectorTransposeMultiplicationRcpp.o -g++ -std=gnu++11 -shared -L/opt/R/4.3.1/lib/R/lib -L/usr/local/lib -o netcmc.so RcppExports.o choleskyDecompositionRcppConversion.o doubleMatrixMultiplicationRcpp.o doubleVectorMultiplicationRcpp.o eigenValuesRcppConversion.o getDiagonalMatrix.o getExp.o getExpDividedByOnePlusExp.o getMeanCenteredRandomEffects.o getMultivariateBinomialNetworkLerouxDIC.o getMultivariateBinomialNetworkLerouxFittedValuesAndLikelihoodForDICEveryIteration.o getMultivariateGaussianNetworkLerouxDIC.o getMultivariateGaussianNetworkLerouxFittedValuesAndLikelihoodForDICEveryIteration.o getMultivariatePoissonNetworkLerouxDIC.o getMultivariatePoissonNetworkLerouxFittedValuesAndLikelihoodForDICEveryIteration.o getNonZeroEntries.o getSubvector.o getSubvectorIndecies.o getSumExpNetwork.o getSumExpNetworkIndecies.o getSumExpNetworkLeroux.o getSumExpNetworkLerouxIndecies.o getSumLogExp.o getSumLogExpIndecies.o getSumVector.o getTripletForm.o getUnivariateBinomialNetworkLerouxDIC.o getUnivariateBinomialNetworkLerouxFittedValuesAndLikelihoodForDICEveryIteration.o getUnivariateGaussianNetworkLerouxDIC.o getUnivariateGaussianNetworkLerouxFittedValuesAndLikelihoodForDICEveryIteration.o getUnivariatePoissonNetworkDIC.o getUnivariatePoissonNetworkFittedValuesAndLikelihoodForDICEveryIteration.o getUnivariatePoissonNetworkLerouxDIC.o getUnivariatePoissonNetworkLerouxFittedValuesAndLikelihoodForDICEveryIteration.o getVectorMean.o matrixInverseRcppConversion.o matrixMatrixAdditionRcpp.o matrixMatrixSubtractionRcpp.o matrixVectorMultiplicationRcpp.o multivariateBinomialNetworkLerouxAllUpdate.o multivariateBinomialNetworkLerouxBetaUpdate.o multivariateBinomialNetworkLerouxRhoUpdate.o multivariateBinomialNetworkLerouxSingleUpdate.o multivariateBinomialNetworkLerouxSpatialRandomEffectsUpdate.o multivariateBinomialNetworkLerouxTauSquaredUpdate.o multivariateBinomialNetworkLerouxURandomEffectsUpdate.o multivariateBinomialNetworkLerouxVRandomEffectsUpdate.o multivariateBinomialNetworkLerouxVarianceCovarianceUUpdate.o multivariateBinomialNetworkRandAllUpdate.o multivariateBinomialNetworkRandSingleUpdate.o multivariateGaussianNetworkLerouxAllMHUpdate.o multivariateGaussianNetworkLerouxBetaUpdate.o multivariateGaussianNetworkLerouxRhoUpdate.o multivariateGaussianNetworkLerouxSigmaSquaredEUpdate.o multivariateGaussianNetworkLerouxSingleMHUpdate.o multivariateGaussianNetworkLerouxSpatialRandomEffectsMHUpdate.o multivariateGaussianNetworkLerouxTauSquaredUpdate.o multivariateGaussianNetworkLerouxURandomEffectsUpdate.o multivariateGaussianNetworkLerouxVarianceCovarianceUUpdate.o multivariateGaussianNetworkRandAllUpdate.o multivariateGaussianNetworkRandSingleUpdate.o multivariateGaussianNetworkRandVRandomEffectsUpdate.o multivariatePoissonNetworkLerouxAllUpdate.o multivariatePoissonNetworkLerouxBetaUpdate.o multivariatePoissonNetworkLerouxRhoUpdate.o multivariatePoissonNetworkLerouxSingleUpdate.o multivariatePoissonNetworkLerouxSpatialRandomEffectsUpdate.o multivariatePoissonNetworkLerouxTauSquaredUpdate.o multivariatePoissonNetworkLerouxURandomEffectsUpdate.o multivariatePoissonNetworkLerouxVRandomEffectsUpdate.o multivariatePoissonNetworkLerouxVarianceCovarianceUUpdate.o multivariatePoissonNetworkRandAllUpdate.o multivariatePoissonNetworkRandSingleUpdate.o sumMatrix.o univariateBinomialNetworkLerouxAllUpdate.o univariateBinomialNetworkLerouxBetaUpdate.o univariateBinomialNetworkLerouxRhoUpdate.o univariateBinomialNetworkLerouxSigmaSquaredUpdate.o univariateBinomialNetworkLerouxSingleUpdate.o univariateBinomialNetworkLerouxSpatialRandomEffectsUpdate.o univariateBinomialNetworkLerouxTauSquaredUpdate.o univariateBinomialNetworkLerouxURandomEffectsUpdate.o univariateGaussianNetworkLerouxAllMHUpdate.o univariateGaussianNetworkLerouxBetaUpdate.o univariateGaussianNetworkLerouxRhoUpdate.o univariateGaussianNetworkLerouxSigmaSquaredEUpdate.o univariateGaussianNetworkLerouxSigmaSquaredUUpdate.o univariateGaussianNetworkLerouxSingleMHUpdate.o univariateGaussianNetworkLerouxSpatialRandomEffectsMHUpdate.o univariateGaussianNetworkLerouxTauSquaredUpdate.o univariateGaussianNetworkLerouxURandomEffectsUpdate.o univariatePoissonNetworkLerouxAllUpdate.o univariatePoissonNetworkLerouxBetaUpdate.o univariatePoissonNetworkLerouxRhoUpdate.o univariatePoissonNetworkLerouxSigmaSquaredUpdate.o univariatePoissonNetworkLerouxSingleUpdate.o univariatePoissonNetworkLerouxSpatialRandomEffectsUpdate.o univariatePoissonNetworkLerouxTauSquaredUpdate.o univariatePoissonNetworkLerouxURandomEffectsUpdate.o vectorTransposeVectorMultiplicationRcpp.o vectorVectorTransposeMultiplicationRcpp.o -llapack -lblas -lgfortran -lm -lquadmath -L/opt/R/4.3.1/lib/R/lib -lR -installing to /tmp/workdir/netcmc/old/netcmc.Rcheck/00LOCK-netcmc/00new/netcmc/libs -** R -** byte-compile and prepare package for lazy loading -Error: package or namespace load failed for ‘MCMCpack’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +1. ggpmisc +Calls: -> lib_ps +Execution halted +* checking for unstated dependencies in vignettes ... OK +* checking package vignettes in ‘inst/doc’ ... OK +* checking running R code from vignettes ... OK + ‘pctax.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 1 ERROR, 1 NOTE + + + + + +``` +# pcutils + +
+ +* Version: 0.2.5 +* GitHub: https://github.com/Asa12138/pcutils +* Source code: https://github.com/cran/pcutils +* Date/Publication: 2024-03-19 16:50:07 UTC +* Number of recursive dependencies: 277 + +Run `revdepcheck::cloud_details(, "pcutils")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/pcutils/new/pcutils.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘pcutils/DESCRIPTION’ ... OK +... + 1. ├─base (local) ``(x) + 2. └─ggplot2:::print.ggplot(x) + 3. ├─ggplot2::ggplot_gtable(data) + 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) + 5. └─ggplot2::calc_element("plot.margin", theme) + 6. └─cli::cli_abort(...) + 7. └─rlang::abort(...) Execution halted -ERROR: lazy loading failed for package ‘netcmc’ -* removing ‘/tmp/workdir/netcmc/old/netcmc.Rcheck/netcmc’ +* DONE +Status: 1 ERROR, 1 NOTE + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/pcutils/old/pcutils.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘pcutils/DESCRIPTION’ ... OK +... +* checking for code/documentation mismatches ... OK +* checking Rd \usage sections ... OK +* checking Rd contents ... OK +* checking for unstated dependencies in examples ... OK +* checking contents of ‘data’ directory ... OK +* checking data for non-ASCII characters ... OK +* checking data for ASCII and uncompressed saves ... OK +* checking examples ... OK +* DONE +Status: 1 NOTE + + + ``` -# NetworkChange +# PLMIX
-* Version: 0.8 -* GitHub: https://github.com/jongheepark/NetworkChange -* Source code: https://github.com/cran/NetworkChange -* Date/Publication: 2022-03-04 07:30:02 UTC -* Number of recursive dependencies: 132 +* Version: 2.1.1 +* GitHub: NA +* Source code: https://github.com/cran/PLMIX +* Date/Publication: 2019-09-04 11:50:02 UTC +* Number of recursive dependencies: 150 -Run `revdepcheck::cloud_details(, "NetworkChange")` for more info +Run `revdepcheck::cloud_details(, "PLMIX")` for more info
## In both -* checking whether package ‘NetworkChange’ can be installed ... ERROR +* checking whether package ‘PLMIX’ can be installed ... ERROR ``` Installation failed. - See ‘/tmp/workdir/NetworkChange/new/NetworkChange.Rcheck/00install.out’ for details. + See ‘/tmp/workdir/PLMIX/new/PLMIX.Rcheck/00install.out’ for details. ``` ## Installation @@ -4476,131 +8652,153 @@ Run `revdepcheck::cloud_details(, "NetworkChange")` for more info ### Devel ``` -* installing *source* package ‘NetworkChange’ ... -** package ‘NetworkChange’ successfully unpacked and MD5 sums checked +* installing *source* package ‘PLMIX’ ... +** package ‘PLMIX’ successfully unpacked and MD5 sums checked ** using staged installation -** R +** libs +using C++ compiler: ‘g++ (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c CompProbZpartial.cpp -o CompProbZpartial.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c CompRateP.cpp -o CompRateP.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c CompRateYpartial.cpp -o CompRateYpartial.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c Estep.cpp -o Estep.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c PLMIXsim.cpp -o PLMIXsim.o +... ** data +*** moving datasets to lazyload DB +** inst ** byte-compile and prepare package for lazy loading -Error: package or namespace load failed for ‘MCMCpack’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Error in loadNamespace(i, c(lib.loc, .libPaths()), versionCheck = vI[[i]]) : + there is no package called ‘quantreg’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart Execution halted -ERROR: lazy loading failed for package ‘NetworkChange’ -* removing ‘/tmp/workdir/NetworkChange/new/NetworkChange.Rcheck/NetworkChange’ +ERROR: lazy loading failed for package ‘PLMIX’ +* removing ‘/tmp/workdir/PLMIX/new/PLMIX.Rcheck/PLMIX’ ``` ### CRAN ``` -* installing *source* package ‘NetworkChange’ ... -** package ‘NetworkChange’ successfully unpacked and MD5 sums checked +* installing *source* package ‘PLMIX’ ... +** package ‘PLMIX’ successfully unpacked and MD5 sums checked ** using staged installation -** R +** libs +using C++ compiler: ‘g++ (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c CompProbZpartial.cpp -o CompProbZpartial.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c CompRateP.cpp -o CompRateP.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c CompRateYpartial.cpp -o CompRateYpartial.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c Estep.cpp -o Estep.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c PLMIXsim.cpp -o PLMIXsim.o +... ** data +*** moving datasets to lazyload DB +** inst ** byte-compile and prepare package for lazy loading -Error: package or namespace load failed for ‘MCMCpack’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Error in loadNamespace(i, c(lib.loc, .libPaths()), versionCheck = vI[[i]]) : + there is no package called ‘quantreg’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart Execution halted -ERROR: lazy loading failed for package ‘NetworkChange’ -* removing ‘/tmp/workdir/NetworkChange/old/NetworkChange.Rcheck/NetworkChange’ +ERROR: lazy loading failed for package ‘PLMIX’ +* removing ‘/tmp/workdir/PLMIX/old/PLMIX.Rcheck/PLMIX’ ``` -# nlmeVPC +# pmcalibration
-* Version: 2.6 -* GitHub: NA -* Source code: https://github.com/cran/nlmeVPC -* Date/Publication: 2022-12-22 05:20:02 UTC -* Number of recursive dependencies: 91 +* Version: 0.1.0 +* GitHub: https://github.com/stephenrho/pmcalibration +* Source code: https://github.com/cran/pmcalibration +* Date/Publication: 2023-09-06 17:50:02 UTC +* Number of recursive dependencies: 80 -Run `revdepcheck::cloud_details(, "nlmeVPC")` for more info +Run `revdepcheck::cloud_details(, "pmcalibration")` for more info
-## In both - -* checking whether package ‘nlmeVPC’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/nlmeVPC/new/nlmeVPC.Rcheck/00install.out’ for details. - ``` - -## Installation +## Error before installation ### Devel ``` -* installing *source* package ‘nlmeVPC’ ... -** package ‘nlmeVPC’ successfully unpacked and MD5 sums checked -** using staged installation -** libs -using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ -using C++11 -g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c Misc.cpp -o Misc.o -g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o -g++ -std=gnu++11 -shared -L/opt/R/4.3.1/lib/R/lib -L/usr/local/lib -o nlmeVPC.so Misc.o RcppExports.o -fopenmp -llapack -lblas -lgfortran -lm -lquadmath -L/opt/R/4.3.1/lib/R/lib -lR -installing to /tmp/workdir/nlmeVPC/new/nlmeVPC.Rcheck/00LOCK-nlmeVPC/00new/nlmeVPC/libs -** R -** data -** byte-compile and prepare package for lazy loading -Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +* using log directory ‘/tmp/workdir/pmcalibration/new/pmcalibration.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘pmcalibration/DESCRIPTION’ ... OK +... +--- finished re-building ‘internal-validation.Rmd’ + +SUMMARY: processing the following file failed: + ‘external-validation.Rmd’ + +Error: Vignette re-building failed. Execution halted -ERROR: lazy loading failed for package ‘nlmeVPC’ -* removing ‘/tmp/workdir/nlmeVPC/new/nlmeVPC.Rcheck/nlmeVPC’ + +* DONE +Status: 1 WARNING, 2 NOTEs + + + ``` ### CRAN ``` -* installing *source* package ‘nlmeVPC’ ... -** package ‘nlmeVPC’ successfully unpacked and MD5 sums checked -** using staged installation -** libs -using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ -using C++11 -g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c Misc.cpp -o Misc.o -g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o -g++ -std=gnu++11 -shared -L/opt/R/4.3.1/lib/R/lib -L/usr/local/lib -o nlmeVPC.so Misc.o RcppExports.o -fopenmp -llapack -lblas -lgfortran -lm -lquadmath -L/opt/R/4.3.1/lib/R/lib -lR -installing to /tmp/workdir/nlmeVPC/old/nlmeVPC.Rcheck/00LOCK-nlmeVPC/00new/nlmeVPC/libs -** R -** data -** byte-compile and prepare package for lazy loading -Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +* using log directory ‘/tmp/workdir/pmcalibration/old/pmcalibration.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘pmcalibration/DESCRIPTION’ ... OK +... +--- finished re-building ‘internal-validation.Rmd’ + +SUMMARY: processing the following file failed: + ‘external-validation.Rmd’ + +Error: Vignette re-building failed. Execution halted -ERROR: lazy loading failed for package ‘nlmeVPC’ -* removing ‘/tmp/workdir/nlmeVPC/old/nlmeVPC.Rcheck/nlmeVPC’ + +* DONE +Status: 1 WARNING, 2 NOTEs + + + ``` -# NMADiagT +# popstudy
-* Version: 0.1.2 +* Version: 1.0.1 * GitHub: NA -* Source code: https://github.com/cran/NMADiagT -* Date/Publication: 2020-02-26 07:00:02 UTC -* Number of recursive dependencies: 79 +* Source code: https://github.com/cran/popstudy +* Date/Publication: 2023-10-17 23:50:02 UTC +* Number of recursive dependencies: 235 -Run `revdepcheck::cloud_details(, "NMADiagT")` for more info +Run `revdepcheck::cloud_details(, "popstudy")` for more info
## In both -* checking whether package ‘NMADiagT’ can be installed ... ERROR +* checking whether package ‘popstudy’ can be installed ... ERROR ``` Installation failed. - See ‘/tmp/workdir/NMADiagT/new/NMADiagT.Rcheck/00install.out’ for details. + See ‘/tmp/workdir/popstudy/new/popstudy.Rcheck/00install.out’ for details. ``` ## Installation @@ -4608,117 +8806,139 @@ Run `revdepcheck::cloud_details(, "NMADiagT")` for more info ### Devel ``` -* installing *source* package ‘NMADiagT’ ... -** package ‘NMADiagT’ successfully unpacked and MD5 sums checked +* installing *source* package ‘popstudy’ ... +** package ‘popstudy’ 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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace + there is no package called ‘quantreg’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart Execution halted -ERROR: lazy loading failed for package ‘NMADiagT’ -* removing ‘/tmp/workdir/NMADiagT/new/NMADiagT.Rcheck/NMADiagT’ +ERROR: lazy loading failed for package ‘popstudy’ +* removing ‘/tmp/workdir/popstudy/new/popstudy.Rcheck/popstudy’ ``` ### CRAN ``` -* installing *source* package ‘NMADiagT’ ... -** package ‘NMADiagT’ successfully unpacked and MD5 sums checked +* installing *source* package ‘popstudy’ ... +** package ‘popstudy’ 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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace + there is no package called ‘quantreg’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart Execution halted -ERROR: lazy loading failed for package ‘NMADiagT’ -* removing ‘/tmp/workdir/NMADiagT/old/NMADiagT.Rcheck/NMADiagT’ +ERROR: lazy loading failed for package ‘popstudy’ +* removing ‘/tmp/workdir/popstudy/old/popstudy.Rcheck/popstudy’ ``` -# optweight +# pould
-* Version: 0.2.5 +* Version: 1.0.1 * GitHub: NA -* Source code: https://github.com/cran/optweight -* Date/Publication: 2019-09-16 15:40:02 UTC -* Number of recursive dependencies: 55 +* Source code: https://github.com/cran/pould +* Date/Publication: 2020-10-16 13:50:03 UTC +* Number of recursive dependencies: 104 -Run `revdepcheck::cloud_details(, "optweight")` for more info +Run `revdepcheck::cloud_details(, "pould")` for more info
-## In both - -* checking whether package ‘optweight’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/optweight/new/optweight.Rcheck/00install.out’ for details. - ``` - -## Installation +## Error before installation ### Devel ``` -* installing *source* package ‘optweight’ ... -** package ‘optweight’ successfully unpacked and MD5 sums checked -** using staged installation -** R -** byte-compile and prepare package for lazy loading -Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.1 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘optweight’ -* removing ‘/tmp/workdir/optweight/new/optweight.Rcheck/optweight’ +* using log directory ‘/tmp/workdir/pould/new/pould.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘pould/DESCRIPTION’ ... OK +... +* checking if there is a namespace ... OK +* checking for executable files ... OK +* checking for hidden files and directories ... OK +* checking for portable file names ... OK +* checking for sufficient/correct file permissions ... OK +* checking whether package ‘pould’ can be installed ... ERROR +Installation failed. +See ‘/tmp/workdir/pould/new/pould.Rcheck/00install.out’ for details. +* DONE +Status: 1 ERROR + + + ``` ### CRAN ``` -* installing *source* package ‘optweight’ ... -** package ‘optweight’ successfully unpacked and MD5 sums checked -** using staged installation -** R -** byte-compile and prepare package for lazy loading -Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.1 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘optweight’ -* removing ‘/tmp/workdir/optweight/old/optweight.Rcheck/optweight’ +* using log directory ‘/tmp/workdir/pould/old/pould.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘pould/DESCRIPTION’ ... OK +... +* checking if there is a namespace ... OK +* checking for executable files ... OK +* checking for hidden files and directories ... OK +* checking for portable file names ... OK +* checking for sufficient/correct file permissions ... OK +* checking whether package ‘pould’ can be installed ... ERROR +Installation failed. +See ‘/tmp/workdir/pould/old/pould.Rcheck/00install.out’ for details. +* DONE +Status: 1 ERROR + + + ``` -# OVtool +# powerly
-* Version: 1.0.3 -* GitHub: NA -* Source code: https://github.com/cran/OVtool -* Date/Publication: 2021-11-02 08:10:07 UTC -* Number of recursive dependencies: 158 +* Version: 1.8.6 +* GitHub: https://github.com/mihaiconstantin/powerly +* Source code: https://github.com/cran/powerly +* Date/Publication: 2022-09-09 14:10:01 UTC +* Number of recursive dependencies: 175 -Run `revdepcheck::cloud_details(, "OVtool")` for more info +Run `revdepcheck::cloud_details(, "powerly")` for more info
## In both -* checking whether package ‘OVtool’ can be installed ... ERROR +* checking whether package ‘powerly’ can be installed ... ERROR ``` Installation failed. - See ‘/tmp/workdir/OVtool/new/OVtool.Rcheck/00install.out’ for details. + See ‘/tmp/workdir/powerly/new/powerly.Rcheck/00install.out’ for details. ``` ## Installation @@ -4726,61 +8946,59 @@ Run `revdepcheck::cloud_details(, "OVtool")` for more info ### Devel ``` -* installing *source* package ‘OVtool’ ... -** package ‘OVtool’ successfully unpacked and MD5 sums checked +* installing *source* package ‘powerly’ ... +** package ‘powerly’ successfully unpacked and MD5 sums checked ** using staged installation -** R -** data -*** moving datasets to lazyload DB +** R ** inst ** byte-compile and prepare package for lazy loading -Error: package or namespace load failed for ‘twang’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.1 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace Execution halted -ERROR: lazy loading failed for package ‘OVtool’ -* removing ‘/tmp/workdir/OVtool/new/OVtool.Rcheck/OVtool’ +ERROR: lazy loading failed for package ‘powerly’ +* removing ‘/tmp/workdir/powerly/new/powerly.Rcheck/powerly’ ``` ### CRAN ``` -* installing *source* package ‘OVtool’ ... -** package ‘OVtool’ successfully unpacked and MD5 sums checked +* installing *source* package ‘powerly’ ... +** package ‘powerly’ 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: package or namespace load failed for ‘twang’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.1 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace Execution halted -ERROR: lazy loading failed for package ‘OVtool’ -* removing ‘/tmp/workdir/OVtool/old/OVtool.Rcheck/OVtool’ +ERROR: lazy loading failed for package ‘powerly’ +* removing ‘/tmp/workdir/powerly/old/powerly.Rcheck/powerly’ ``` -# paths +# pre
-* Version: 0.1.1 -* GitHub: NA -* Source code: https://github.com/cran/paths -* Date/Publication: 2021-06-18 08:40:02 UTC -* Number of recursive dependencies: 103 +* Version: 1.0.7 +* GitHub: https://github.com/marjoleinF/pre +* Source code: https://github.com/cran/pre +* Date/Publication: 2024-01-12 19:30:02 UTC +* Number of recursive dependencies: 152 -Run `revdepcheck::cloud_details(, "paths")` for more info +Run `revdepcheck::cloud_details(, "pre")` for more info
## In both -* checking whether package ‘paths’ can be installed ... ERROR +* checking whether package ‘pre’ can be installed ... ERROR ``` Installation failed. - See ‘/tmp/workdir/paths/new/paths.Rcheck/00install.out’ for details. + See ‘/tmp/workdir/pre/new/pre.Rcheck/00install.out’ for details. ``` ## Installation @@ -4788,8 +9006,8 @@ Run `revdepcheck::cloud_details(, "paths")` for more info ### Devel ``` -* installing *source* package ‘paths’ ... -** package ‘paths’ successfully unpacked and MD5 sums checked +* installing *source* package ‘pre’ ... +** package ‘pre’ successfully unpacked and MD5 sums checked ** using staged installation ** R ** data @@ -4800,16 +9018,16 @@ Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[ namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace Execution halted -ERROR: lazy loading failed for package ‘paths’ -* removing ‘/tmp/workdir/paths/new/paths.Rcheck/paths’ +ERROR: lazy loading failed for package ‘pre’ +* removing ‘/tmp/workdir/pre/new/pre.Rcheck/pre’ ``` ### CRAN ``` -* installing *source* package ‘paths’ ... -** package ‘paths’ successfully unpacked and MD5 sums checked +* installing *source* package ‘pre’ ... +** package ‘pre’ successfully unpacked and MD5 sums checked ** using staged installation ** R ** data @@ -4820,352 +9038,550 @@ Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[ namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace Execution halted -ERROR: lazy loading failed for package ‘paths’ -* removing ‘/tmp/workdir/paths/old/paths.Rcheck/paths’ +ERROR: lazy loading failed for package ‘pre’ +* removing ‘/tmp/workdir/pre/old/pre.Rcheck/pre’ ``` -# PLMIX +# PRECAST
-* Version: 2.1.1 -* GitHub: NA -* Source code: https://github.com/cran/PLMIX -* Date/Publication: 2019-09-04 11:50:02 UTC -* Number of recursive dependencies: 151 +* Version: 1.6.5 +* GitHub: https://github.com/feiyoung/PRECAST +* Source code: https://github.com/cran/PRECAST +* Date/Publication: 2024-03-19 08:30:02 UTC +* Number of recursive dependencies: 224 -Run `revdepcheck::cloud_details(, "PLMIX")` for more info +Run `revdepcheck::cloud_details(, "PRECAST")` for more info
-## In both +## Error before installation -* checking whether package ‘PLMIX’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/PLMIX/new/PLMIX.Rcheck/00install.out’ for details. - ``` +### Devel -## Installation +``` +* using log directory ‘/tmp/workdir/PRECAST/new/PRECAST.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘PRECAST/DESCRIPTION’ ... OK +... +* this is package ‘PRECAST’ version ‘1.6.5’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Packages required but not available: 'Seurat', 'DR.SC' + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/PRECAST/old/PRECAST.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘PRECAST/DESCRIPTION’ ... OK +... +* this is package ‘PRECAST’ version ‘1.6.5’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Packages required but not available: 'Seurat', 'DR.SC' + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# ProFAST + +
+ +* Version: 1.4 +* GitHub: https://github.com/feiyoung/ProFAST +* Source code: https://github.com/cran/ProFAST +* Date/Publication: 2024-03-18 08:10:06 UTC +* Number of recursive dependencies: 252 + +Run `revdepcheck::cloud_details(, "ProFAST")` for more info + +
+ +## Error before installation ### Devel ``` -* installing *source* package ‘PLMIX’ ... -** package ‘PLMIX’ successfully unpacked and MD5 sums checked -** using staged installation -** libs -using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c CompProbZpartial.cpp -o CompProbZpartial.o -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c CompRateP.cpp -o CompRateP.o -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c CompRateYpartial.cpp -o CompRateYpartial.o -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c Estep.cpp -o Estep.o -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c PLMIXsim.cpp -o PLMIXsim.o +* using log directory ‘/tmp/workdir/ProFAST/new/ProFAST.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘ProFAST/DESCRIPTION’ ... OK ... -** 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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘PLMIX’ -* removing ‘/tmp/workdir/PLMIX/new/PLMIX.Rcheck/PLMIX’ +* this is package ‘ProFAST’ version ‘1.4’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Packages required but not available: 'DR.SC', 'PRECAST', 'Seurat' + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + ``` ### CRAN ``` -* installing *source* package ‘PLMIX’ ... -** package ‘PLMIX’ successfully unpacked and MD5 sums checked -** using staged installation -** libs -using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c CompProbZpartial.cpp -o CompProbZpartial.o -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c CompRateP.cpp -o CompRateP.o -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c CompRateYpartial.cpp -o CompRateYpartial.o -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c Estep.cpp -o Estep.o -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c PLMIXsim.cpp -o PLMIXsim.o +* using log directory ‘/tmp/workdir/ProFAST/old/ProFAST.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘ProFAST/DESCRIPTION’ ... OK ... -** 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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘PLMIX’ -* removing ‘/tmp/workdir/PLMIX/old/PLMIX.Rcheck/PLMIX’ +* this is package ‘ProFAST’ version ‘1.4’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Packages required but not available: 'DR.SC', 'PRECAST', 'Seurat' + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# psbcSpeedUp + +
+ +* Version: 2.0.6 +* GitHub: https://github.com/ocbe-uio/psbcSpeedUp +* Source code: https://github.com/cran/psbcSpeedUp +* Date/Publication: 2024-03-21 18:00:02 UTC +* Number of recursive dependencies: 129 + +Run `revdepcheck::cloud_details(, "psbcSpeedUp")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/psbcSpeedUp/new/psbcSpeedUp.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘psbcSpeedUp/DESCRIPTION’ ... OK +... +* this is package ‘psbcSpeedUp’ version ‘2.0.6’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘riskRegression’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/psbcSpeedUp/old/psbcSpeedUp.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘psbcSpeedUp/DESCRIPTION’ ... OK +... +* this is package ‘psbcSpeedUp’ version ‘2.0.6’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘riskRegression’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + ``` -# popstudy +# pscore
-* Version: 1.0.1 -* GitHub: NA -* Source code: https://github.com/cran/popstudy -* Date/Publication: 2023-10-17 23:50:02 UTC -* Number of recursive dependencies: 236 +* Version: 0.4.0 +* GitHub: https://github.com/JWiley/score-project +* Source code: https://github.com/cran/pscore +* Date/Publication: 2022-05-13 22:30:02 UTC +* Number of recursive dependencies: 164 -Run `revdepcheck::cloud_details(, "popstudy")` for more info +Run `revdepcheck::cloud_details(, "pscore")` for more info
-## In both - -* checking whether package ‘popstudy’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/popstudy/new/popstudy.Rcheck/00install.out’ for details. - ``` - -## Installation +## Error before installation ### Devel ``` -* installing *source* package ‘popstudy’ ... -** package ‘popstudy’ 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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘popstudy’ -* removing ‘/tmp/workdir/popstudy/new/popstudy.Rcheck/popstudy’ +* using log directory ‘/tmp/workdir/pscore/new/pscore.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘pscore/DESCRIPTION’ ... OK +... +* checking if there is a namespace ... OK +* checking for executable files ... OK +* checking for hidden files and directories ... OK +* checking for portable file names ... OK +* checking for sufficient/correct file permissions ... OK +* checking whether package ‘pscore’ can be installed ... ERROR +Installation failed. +See ‘/tmp/workdir/pscore/new/pscore.Rcheck/00install.out’ for details. +* DONE +Status: 1 ERROR + + + ``` ### CRAN ``` -* installing *source* package ‘popstudy’ ... -** package ‘popstudy’ 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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘popstudy’ -* removing ‘/tmp/workdir/popstudy/old/popstudy.Rcheck/popstudy’ +* using log directory ‘/tmp/workdir/pscore/old/pscore.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘pscore/DESCRIPTION’ ... OK +... +* checking if there is a namespace ... OK +* checking for executable files ... OK +* checking for hidden files and directories ... OK +* checking for portable file names ... OK +* checking for sufficient/correct file permissions ... OK +* checking whether package ‘pscore’ can be installed ... ERROR +Installation failed. +See ‘/tmp/workdir/pscore/old/pscore.Rcheck/00install.out’ for details. +* DONE +Status: 1 ERROR + + + ``` -# pould +# psfmi
-* Version: 1.0.1 -* GitHub: NA -* Source code: https://github.com/cran/pould -* Date/Publication: 2020-10-16 13:50:03 UTC -* Number of recursive dependencies: 104 +* Version: 1.4.0 +* GitHub: https://github.com/mwheymans/psfmi +* Source code: https://github.com/cran/psfmi +* Date/Publication: 2023-06-17 22:40:02 UTC +* Number of recursive dependencies: 159 -Run `revdepcheck::cloud_details(, "pould")` for more info +Run `revdepcheck::cloud_details(, "psfmi")` for more info
-## In both - -* checking whether package ‘pould’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/pould/new/pould.Rcheck/00install.out’ for details. - ``` - -## Installation +## Error before installation ### Devel ``` -* installing *source* package ‘pould’ ... -** package ‘pould’ 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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘pould’ -* removing ‘/tmp/workdir/pould/new/pould.Rcheck/pould’ +* using log directory ‘/tmp/workdir/psfmi/new/psfmi.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘psfmi/DESCRIPTION’ ... OK +... +* this is package ‘psfmi’ version ‘1.4.0’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘rms’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + ``` ### CRAN ``` -* installing *source* package ‘pould’ ... -** package ‘pould’ 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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘pould’ -* removing ‘/tmp/workdir/pould/old/pould.Rcheck/pould’ +* using log directory ‘/tmp/workdir/psfmi/old/psfmi.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘psfmi/DESCRIPTION’ ... OK +... +* this is package ‘psfmi’ version ‘1.4.0’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘rms’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + ``` -# powerly +# pubh
-* Version: 1.8.6 -* GitHub: https://github.com/mihaiconstantin/powerly -* Source code: https://github.com/cran/powerly -* Date/Publication: 2022-09-09 14:10:01 UTC -* Number of recursive dependencies: 176 +* Version: 1.3.2 +* GitHub: https://github.com/josie-athens/pubh +* Source code: https://github.com/cran/pubh +* Date/Publication: 2024-01-11 21:30:12 UTC +* Number of recursive dependencies: 229 -Run `revdepcheck::cloud_details(, "powerly")` for more info +Run `revdepcheck::cloud_details(, "pubh")` for more info
-## In both - -* checking whether package ‘powerly’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/powerly/new/powerly.Rcheck/00install.out’ for details. - ``` - -## Installation +## Error before installation ### Devel ``` -* installing *source* package ‘powerly’ ... -** package ‘powerly’ 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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.1 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘powerly’ -* removing ‘/tmp/workdir/powerly/new/powerly.Rcheck/powerly’ +* using log directory ‘/tmp/workdir/pubh/new/pubh.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘pubh/DESCRIPTION’ ... OK +... +* checking files in ‘vignettes’ ... OK +* checking examples ... OK +* checking for unstated dependencies in vignettes ... OK +* checking package vignettes in ‘inst/doc’ ... OK +* checking running R code from vignettes ... OK + ‘introduction.Rmd’ using ‘UTF-8’... OK + ‘regression.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 1 NOTE + + + ``` ### CRAN ``` -* installing *source* package ‘powerly’ ... -** package ‘powerly’ 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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.1 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘powerly’ -* removing ‘/tmp/workdir/powerly/old/powerly.Rcheck/powerly’ +* using log directory ‘/tmp/workdir/pubh/old/pubh.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘pubh/DESCRIPTION’ ... OK +... +* checking files in ‘vignettes’ ... OK +* checking examples ... OK +* checking for unstated dependencies in vignettes ... OK +* checking package vignettes in ‘inst/doc’ ... OK +* checking running R code from vignettes ... OK + ‘introduction.Rmd’ using ‘UTF-8’... OK + ‘regression.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 1 NOTE + + + ``` -# pre +# qPCRtools
-* Version: 1.0.7 -* GitHub: https://github.com/marjoleinF/pre -* Source code: https://github.com/cran/pre -* Date/Publication: 2024-01-12 19:30:02 UTC -* Number of recursive dependencies: 152 +* Version: 1.0.1 +* GitHub: https://github.com/lixiang117423/qPCRtools +* Source code: https://github.com/cran/qPCRtools +* Date/Publication: 2023-11-02 13:10:05 UTC +* Number of recursive dependencies: 115 -Run `revdepcheck::cloud_details(, "pre")` for more info +Run `revdepcheck::cloud_details(, "qPCRtools")` for more info
-## In both +## Error before installation -* checking whether package ‘pre’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/pre/new/pre.Rcheck/00install.out’ for details. - ``` +### Devel + +``` +* using log directory ‘/tmp/workdir/qPCRtools/new/qPCRtools.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘qPCRtools/DESCRIPTION’ ... OK +* this is package ‘qPCRtools’ version ‘1.0.1’ +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘ggpmisc’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR -## Installation -### Devel -``` -* installing *source* package ‘pre’ ... -** package ‘pre’ 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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘pre’ -* removing ‘/tmp/workdir/pre/new/pre.Rcheck/pre’ ``` ### CRAN ``` -* installing *source* package ‘pre’ ... -** package ‘pre’ 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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘pre’ -* removing ‘/tmp/workdir/pre/old/pre.Rcheck/pre’ +* using log directory ‘/tmp/workdir/qPCRtools/old/qPCRtools.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘qPCRtools/DESCRIPTION’ ... OK +* this is package ‘qPCRtools’ version ‘1.0.1’ +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘ggpmisc’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + ``` -# ProFAST +# qreport
-* Version: 1.4 -* GitHub: https://github.com/feiyoung/ProFAST -* Source code: https://github.com/cran/ProFAST -* Date/Publication: 2024-03-18 08:10:06 UTC -* Number of recursive dependencies: 253 +* Version: 1.0-1 +* GitHub: NA +* Source code: https://github.com/cran/qreport +* Date/Publication: 2024-05-26 21:50:03 UTC +* Number of recursive dependencies: 77 -Run `revdepcheck::cloud_details(, "ProFAST")` for more info +Run `revdepcheck::cloud_details(, "qreport")` for more info
@@ -5174,22 +9590,22 @@ Run `revdepcheck::cloud_details(, "ProFAST")` for more info ### Devel ``` -* using log directory ‘/tmp/workdir/ProFAST/new/ProFAST.Rcheck’ +* using log directory ‘/tmp/workdir/qreport/new/qreport.Rcheck’ * using R version 4.3.1 (2023-06-16) * using platform: x86_64-pc-linux-gnu (64-bit) * R was compiled by - gcc (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0 - GNU Fortran (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0 -* running under: Ubuntu 20.04.6 LTS + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘ProFAST/DESCRIPTION’ ... OK +* checking for file ‘qreport/DESCRIPTION’ ... OK ... -* this is package ‘ProFAST’ version ‘1.4’ +* this is package ‘qreport’ version ‘1.0-1’ * package encoding: UTF-8 * checking package namespace information ... OK * checking package dependencies ... ERROR -Packages required but not available: 'DR.SC', 'PRECAST' +Package required but not available: ‘rms’ See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ manual. @@ -5204,22 +9620,22 @@ Status: 1 ERROR ### CRAN ``` -* using log directory ‘/tmp/workdir/ProFAST/old/ProFAST.Rcheck’ +* using log directory ‘/tmp/workdir/qreport/old/qreport.Rcheck’ * using R version 4.3.1 (2023-06-16) * using platform: x86_64-pc-linux-gnu (64-bit) * R was compiled by - gcc (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0 - GNU Fortran (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0 -* running under: Ubuntu 20.04.6 LTS + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘ProFAST/DESCRIPTION’ ... OK +* checking for file ‘qreport/DESCRIPTION’ ... OK ... -* this is package ‘ProFAST’ version ‘1.4’ +* this is package ‘qreport’ version ‘1.0-1’ * package encoding: UTF-8 * checking package namespace information ... OK * checking package dependencies ... ERROR -Packages required but not available: 'DR.SC', 'PRECAST' +Package required but not available: ‘rms’ See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ manual. @@ -5231,26 +9647,26 @@ Status: 1 ERROR ``` -# psbcSpeedUp +# quid
-* Version: 2.0.6 -* GitHub: https://github.com/ocbe-uio/psbcSpeedUp -* Source code: https://github.com/cran/psbcSpeedUp -* Date/Publication: 2024-03-21 18:00:02 UTC -* Number of recursive dependencies: 130 +* Version: 0.0.1 +* GitHub: NA +* Source code: https://github.com/cran/quid +* Date/Publication: 2021-12-09 09:00:02 UTC +* Number of recursive dependencies: 95 -Run `revdepcheck::cloud_details(, "psbcSpeedUp")` for more info +Run `revdepcheck::cloud_details(, "quid")` for more info
## In both -* checking whether package ‘psbcSpeedUp’ can be installed ... ERROR +* checking whether package ‘quid’ can be installed ... ERROR ``` Installation failed. - See ‘/tmp/workdir/psbcSpeedUp/new/psbcSpeedUp.Rcheck/00install.out’ for details. + See ‘/tmp/workdir/quid/new/quid.Rcheck/00install.out’ for details. ``` ## Installation @@ -5258,17 +9674,10 @@ Run `revdepcheck::cloud_details(, "psbcSpeedUp")` for more info ### Devel ``` -* installing *source* package ‘psbcSpeedUp’ ... -** package ‘psbcSpeedUp’ successfully unpacked and MD5 sums checked +* installing *source* package ‘quid’ ... +** package ‘quid’ successfully unpacked and MD5 sums checked ** using staged installation -checking whether the C++ compiler works... yes -checking for C++ compiler default output file name... a.out -checking for suffix of executables... -checking whether we are cross compiling... no -checking for suffix of object files... o -checking whether the compiler supports GNU C++... yes -checking whether g++ -std=gnu++17 accepts -g... yes -... +** R ** data *** moving datasets to lazyload DB ** inst @@ -5277,25 +9686,18 @@ Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[ namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace Execution halted -ERROR: lazy loading failed for package ‘psbcSpeedUp’ -* removing ‘/tmp/workdir/psbcSpeedUp/new/psbcSpeedUp.Rcheck/psbcSpeedUp’ +ERROR: lazy loading failed for package ‘quid’ +* removing ‘/tmp/workdir/quid/new/quid.Rcheck/quid’ ``` ### CRAN ``` -* installing *source* package ‘psbcSpeedUp’ ... -** package ‘psbcSpeedUp’ successfully unpacked and MD5 sums checked +* installing *source* package ‘quid’ ... +** package ‘quid’ successfully unpacked and MD5 sums checked ** using staged installation -checking whether the C++ compiler works... yes -checking for C++ compiler default output file name... a.out -checking for suffix of executables... -checking whether we are cross compiling... no -checking for suffix of object files... o -checking whether the compiler supports GNU C++... yes -checking whether g++ -std=gnu++17 accepts -g... yes -... +** R ** data *** moving datasets to lazyload DB ** inst @@ -5304,31 +9706,31 @@ Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[ namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace Execution halted -ERROR: lazy loading failed for package ‘psbcSpeedUp’ -* removing ‘/tmp/workdir/psbcSpeedUp/old/psbcSpeedUp.Rcheck/psbcSpeedUp’ +ERROR: lazy loading failed for package ‘quid’ +* removing ‘/tmp/workdir/quid/old/quid.Rcheck/quid’ ``` -# pscore +# RcmdrPlugin.RiskDemo
-* Version: 0.4.0 -* GitHub: https://github.com/JWiley/score-project -* Source code: https://github.com/cran/pscore -* Date/Publication: 2022-05-13 22:30:02 UTC -* Number of recursive dependencies: 165 +* Version: 3.2 +* GitHub: NA +* Source code: https://github.com/cran/RcmdrPlugin.RiskDemo +* Date/Publication: 2024-02-06 09:20:02 UTC +* Number of recursive dependencies: 207 -Run `revdepcheck::cloud_details(, "pscore")` for more info +Run `revdepcheck::cloud_details(, "RcmdrPlugin.RiskDemo")` for more info
## In both -* checking whether package ‘pscore’ can be installed ... ERROR +* checking whether package ‘RcmdrPlugin.RiskDemo’ can be installed ... ERROR ``` Installation failed. - See ‘/tmp/workdir/pscore/new/pscore.Rcheck/00install.out’ for details. + See ‘/tmp/workdir/RcmdrPlugin.RiskDemo/new/RcmdrPlugin.RiskDemo.Rcheck/00install.out’ for details. ``` ## Installation @@ -5336,61 +9738,137 @@ Run `revdepcheck::cloud_details(, "pscore")` for more info ### Devel ``` -* installing *source* package ‘pscore’ ... -** package ‘pscore’ successfully unpacked and MD5 sums checked +* installing *source* package ‘RcmdrPlugin.RiskDemo’ ... +** package ‘RcmdrPlugin.RiskDemo’ successfully unpacked and MD5 sums checked ** 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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace + there is no package called ‘quantreg’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart Execution halted -ERROR: lazy loading failed for package ‘pscore’ -* removing ‘/tmp/workdir/pscore/new/pscore.Rcheck/pscore’ +ERROR: lazy loading failed for package ‘RcmdrPlugin.RiskDemo’ +* removing ‘/tmp/workdir/RcmdrPlugin.RiskDemo/new/RcmdrPlugin.RiskDemo.Rcheck/RcmdrPlugin.RiskDemo’ ``` ### CRAN ``` -* installing *source* package ‘pscore’ ... -** package ‘pscore’ successfully unpacked and MD5 sums checked +* installing *source* package ‘RcmdrPlugin.RiskDemo’ ... +** package ‘RcmdrPlugin.RiskDemo’ successfully unpacked and MD5 sums checked ** 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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace + there is no package called ‘quantreg’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart Execution halted -ERROR: lazy loading failed for package ‘pscore’ -* removing ‘/tmp/workdir/pscore/old/pscore.Rcheck/pscore’ +ERROR: lazy loading failed for package ‘RcmdrPlugin.RiskDemo’ +* removing ‘/tmp/workdir/RcmdrPlugin.RiskDemo/old/RcmdrPlugin.RiskDemo.Rcheck/RcmdrPlugin.RiskDemo’ ``` -# psfmi +# rcssci
-* Version: 1.4.0 -* GitHub: https://github.com/mwheymans/psfmi -* Source code: https://github.com/cran/psfmi -* Date/Publication: 2023-06-17 22:40:02 UTC -* Number of recursive dependencies: 160 +* Version: 0.4.0 +* GitHub: https://github.com/popnie/RCSsci +* Source code: https://github.com/cran/rcssci +* Date/Publication: 2023-02-15 21:20:02 UTC +* Number of recursive dependencies: 137 -Run `revdepcheck::cloud_details(, "psfmi")` for more info +Run `revdepcheck::cloud_details(, "rcssci")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/rcssci/new/rcssci.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘rcssci/DESCRIPTION’ ... OK +... +* this is package ‘rcssci’ version ‘0.4.0’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘rms’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/rcssci/old/rcssci.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘rcssci/DESCRIPTION’ ... OK +... +* this is package ‘rcssci’ version ‘0.4.0’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘rms’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# rddtools + +
+ +* Version: 1.6.0 +* GitHub: https://github.com/bquast/rddtools +* Source code: https://github.com/cran/rddtools +* Date/Publication: 2022-01-10 12:42:49 UTC +* Number of recursive dependencies: 101 + +Run `revdepcheck::cloud_details(, "rddtools")` for more info
## In both -* checking whether package ‘psfmi’ can be installed ... ERROR +* checking whether package ‘rddtools’ can be installed ... ERROR ``` Installation failed. - See ‘/tmp/workdir/psfmi/new/psfmi.Rcheck/00install.out’ for details. + See ‘/tmp/workdir/rddtools/new/rddtools.Rcheck/00install.out’ for details. ``` ## Installation @@ -5398,451 +9876,515 @@ Run `revdepcheck::cloud_details(, "psfmi")` for more info ### Devel ``` -* installing *source* package ‘psfmi’ ... -** package ‘psfmi’ successfully unpacked and MD5 sums checked +* installing *source* package ‘rddtools’ ... +** package ‘rddtools’ 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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Error: package or namespace load failed for ‘np’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): + there is no package called ‘quantreg’ Execution halted -ERROR: lazy loading failed for package ‘psfmi’ -* removing ‘/tmp/workdir/psfmi/new/psfmi.Rcheck/psfmi’ +ERROR: lazy loading failed for package ‘rddtools’ +* removing ‘/tmp/workdir/rddtools/new/rddtools.Rcheck/rddtools’ ``` ### CRAN ``` -* installing *source* package ‘psfmi’ ... -** package ‘psfmi’ successfully unpacked and MD5 sums checked +* installing *source* package ‘rddtools’ ... +** package ‘rddtools’ 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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Error: package or namespace load failed for ‘np’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): + there is no package called ‘quantreg’ Execution halted -ERROR: lazy loading failed for package ‘psfmi’ -* removing ‘/tmp/workdir/psfmi/old/psfmi.Rcheck/psfmi’ +ERROR: lazy loading failed for package ‘rddtools’ +* removing ‘/tmp/workdir/rddtools/old/rddtools.Rcheck/rddtools’ ``` -# qPCRtools +# relsurv
-* Version: 1.0.1 -* GitHub: https://github.com/lixiang117423/qPCRtools -* Source code: https://github.com/cran/qPCRtools -* Date/Publication: 2023-11-02 13:10:05 UTC -* Number of recursive dependencies: 116 +* Version: 2.2-9 +* GitHub: NA +* Source code: https://github.com/cran/relsurv +* Date/Publication: 2022-12-22 13:30:02 UTC +* Number of recursive dependencies: 113 -Run `revdepcheck::cloud_details(, "qPCRtools")` for more info +Run `revdepcheck::cloud_details(, "relsurv")` for more info
-## In both - -* checking whether package ‘qPCRtools’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/qPCRtools/new/qPCRtools.Rcheck/00install.out’ for details. - ``` - -## Installation +## Error before installation ### Devel ``` -* installing *source* package ‘qPCRtools’ ... -** package ‘qPCRtools’ 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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘qPCRtools’ -* removing ‘/tmp/workdir/qPCRtools/new/qPCRtools.Rcheck/qPCRtools’ +* using log directory ‘/tmp/workdir/relsurv/new/relsurv.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘relsurv/DESCRIPTION’ ... OK +... +* checking for unstated dependencies in examples ... OK +* checking contents of ‘data’ directory ... OK +* checking data for non-ASCII characters ... OK +* checking LazyData ... OK +* checking data for ASCII and uncompressed saves ... OK +* checking line endings in C/C++/Fortran sources/headers ... OK +* checking compiled code ... OK +* checking examples ... OK +* DONE +Status: OK + + + ``` ### CRAN ``` -* installing *source* package ‘qPCRtools’ ... -** package ‘qPCRtools’ 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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘qPCRtools’ -* removing ‘/tmp/workdir/qPCRtools/old/qPCRtools.Rcheck/qPCRtools’ +* using log directory ‘/tmp/workdir/relsurv/old/relsurv.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘relsurv/DESCRIPTION’ ... OK +... +* checking for unstated dependencies in examples ... OK +* checking contents of ‘data’ directory ... OK +* checking data for non-ASCII characters ... OK +* checking LazyData ... OK +* checking data for ASCII and uncompressed saves ... OK +* checking line endings in C/C++/Fortran sources/headers ... OK +* checking compiled code ... OK +* checking examples ... OK +* DONE +Status: OK + + + ``` -# qreport +# riskRegression
-* Version: 1.0-0 -* GitHub: NA -* Source code: https://github.com/cran/qreport -* Date/Publication: 2023-09-12 22:10:02 UTC -* Number of recursive dependencies: 77 +* Version: 2023.12.21 +* GitHub: https://github.com/tagteam/riskRegression +* Source code: https://github.com/cran/riskRegression +* Date/Publication: 2023-12-19 17:00:02 UTC +* Number of recursive dependencies: 186 -Run `revdepcheck::cloud_details(, "qreport")` for more info +Run `revdepcheck::cloud_details(, "riskRegression")` for more info
-## In both - -* checking whether package ‘qreport’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/qreport/new/qreport.Rcheck/00install.out’ for details. - ``` - -## Installation +## Error before installation ### Devel ``` -* installing *source* package ‘qreport’ ... -** package ‘qreport’ successfully unpacked and MD5 sums checked -** using staged installation -** R -** byte-compile and prepare package for lazy loading -Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘qreport’ -* removing ‘/tmp/workdir/qreport/new/qreport.Rcheck/qreport’ +* using log directory ‘/tmp/workdir/riskRegression/new/riskRegression.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘riskRegression/DESCRIPTION’ ... OK +... +* this is package ‘riskRegression’ version ‘2023.12.21’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘rms’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + ``` ### CRAN ``` -* installing *source* package ‘qreport’ ... -** package ‘qreport’ successfully unpacked and MD5 sums checked -** using staged installation -** R -** byte-compile and prepare package for lazy loading -Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘qreport’ -* removing ‘/tmp/workdir/qreport/old/qreport.Rcheck/qreport’ +* using log directory ‘/tmp/workdir/riskRegression/old/riskRegression.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘riskRegression/DESCRIPTION’ ... OK +... +* this is package ‘riskRegression’ version ‘2023.12.21’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘rms’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + ``` -# qris +# rliger
-* Version: 1.1.1 -* GitHub: https://github.com/Kyuhyun07/qris -* Source code: https://github.com/cran/qris -* Date/Publication: 2024-03-05 14:40:03 UTC -* Number of recursive dependencies: 55 +* Version: 2.0.1 +* GitHub: https://github.com/welch-lab/liger +* Source code: https://github.com/cran/rliger +* Date/Publication: 2024-04-04 23:20:02 UTC +* Number of recursive dependencies: 218 -Run `revdepcheck::cloud_details(, "qris")` for more info +Run `revdepcheck::cloud_details(, "rliger")` for more info
-## In both - -* checking whether package ‘qris’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/qris/new/qris.Rcheck/00install.out’ for details. - ``` - -## Installation +## Error before installation ### Devel ``` -* installing *source* package ‘qris’ ... -** package ‘qris’ successfully unpacked and MD5 sums checked -** using staged installation -** libs -using C compiler: ‘gcc (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ -using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ -using C++11 -g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c Amat.cpp -o Amat.o -g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o -g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c ghat.cpp -o ghat.o +* using log directory ‘/tmp/workdir/rliger/new/rliger.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘rliger/DESCRIPTION’ ... OK ... -installing to /tmp/workdir/qris/new/qris.Rcheck/00LOCK-qris/00new/qris/libs -** R -** inst -** byte-compile and prepare package for lazy loading -Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘qris’ -* removing ‘/tmp/workdir/qris/new/qris.Rcheck/qris’ + [ FAIL 2 | WARN 0 | SKIP 5 | PASS 1233 ] + Error: Test failures + Execution halted +* checking for unstated dependencies in vignettes ... OK +* checking package vignettes in ‘inst/doc’ ... OK +* checking running R code from vignettes ... OK + ‘liger-vignette.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 2 ERRORs, 2 NOTEs + + + ``` ### CRAN ``` -* installing *source* package ‘qris’ ... -** package ‘qris’ successfully unpacked and MD5 sums checked -** using staged installation -** libs -using C compiler: ‘gcc (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ -using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ -using C++11 -g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c Amat.cpp -o Amat.o -g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o -g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c ghat.cpp -o ghat.o +* using log directory ‘/tmp/workdir/rliger/old/rliger.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘rliger/DESCRIPTION’ ... OK ... -installing to /tmp/workdir/qris/old/qris.Rcheck/00LOCK-qris/00new/qris/libs -** R -** inst -** byte-compile and prepare package for lazy loading -Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘qris’ -* removing ‘/tmp/workdir/qris/old/qris.Rcheck/qris’ + [ FAIL 1 | WARN 0 | SKIP 5 | PASS 1234 ] + Error: Test failures + Execution halted +* checking for unstated dependencies in vignettes ... OK +* checking package vignettes in ‘inst/doc’ ... OK +* checking running R code from vignettes ... OK + ‘liger-vignette.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 2 ERRORs, 2 NOTEs + + + ``` -# qte +# rms
-* Version: 1.3.1 -* GitHub: NA -* Source code: https://github.com/cran/qte -* Date/Publication: 2022-09-01 14:30:02 UTC -* Number of recursive dependencies: 87 +* Version: 6.8-1 +* GitHub: https://github.com/harrelfe/rms +* Source code: https://github.com/cran/rms +* Date/Publication: 2024-05-27 12:00:02 UTC +* Number of recursive dependencies: 153 -Run `revdepcheck::cloud_details(, "qte")` for more info +Run `revdepcheck::cloud_details(, "rms")` for more info
-## In both - -* checking whether package ‘qte’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/qte/new/qte.Rcheck/00install.out’ for details. - ``` - -## Installation +## Error before installation ### Devel ``` -* installing *source* package ‘qte’ ... -** package ‘qte’ 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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘qte’ -* removing ‘/tmp/workdir/qte/new/qte.Rcheck/qte’ +* using log directory ‘/tmp/workdir/rms/new/rms.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘rms/DESCRIPTION’ ... OK +... +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘quantreg’ + +Package suggested but not available for checking: ‘rmsb’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + ``` ### CRAN ``` -* installing *source* package ‘qte’ ... -** package ‘qte’ 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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘qte’ -* removing ‘/tmp/workdir/qte/old/qte.Rcheck/qte’ +* using log directory ‘/tmp/workdir/rms/old/rms.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘rms/DESCRIPTION’ ... OK +... +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘quantreg’ + +Package suggested but not available for checking: ‘rmsb’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + ``` -# quid +# rmsb
-* Version: 0.0.1 +* Version: 1.1-0 * GitHub: NA -* Source code: https://github.com/cran/quid -* Date/Publication: 2021-12-09 09:00:02 UTC -* Number of recursive dependencies: 95 +* Source code: https://github.com/cran/rmsb +* Date/Publication: 2024-03-12 15:50:02 UTC +* Number of recursive dependencies: 143 -Run `revdepcheck::cloud_details(, "quid")` for more info +Run `revdepcheck::cloud_details(, "rmsb")` for more info
-## In both +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/rmsb/new/rmsb.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘rmsb/DESCRIPTION’ ... OK +... +* this is package ‘rmsb’ version ‘1.1-0’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘rms’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + -* checking whether package ‘quid’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/quid/new/quid.Rcheck/00install.out’ for details. - ``` -## Installation -### Devel ``` -* installing *source* package ‘quid’ ... -** package ‘quid’ 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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘quid’ -* removing ‘/tmp/workdir/quid/new/quid.Rcheck/quid’ +### CRAN + +``` +* using log directory ‘/tmp/workdir/rmsb/old/rmsb.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘rmsb/DESCRIPTION’ ... OK +... +* this is package ‘rmsb’ version ‘1.1-0’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘rms’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR -``` -### CRAN -``` -* installing *source* package ‘quid’ ... -** package ‘quid’ 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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘quid’ -* removing ‘/tmp/workdir/quid/old/quid.Rcheck/quid’ ``` -# RATest +# robber
-* Version: 0.1.10 -* GitHub: https://github.com/ignaciomsarmiento/RATest -* Source code: https://github.com/cran/RATest -* Date/Publication: 2022-09-29 04:30:02 UTC -* Number of recursive dependencies: 54 +* Version: 0.2.4 +* GitHub: https://github.com/Chabert-Liddell/robber +* Source code: https://github.com/cran/robber +* Date/Publication: 2024-02-07 13:50:02 UTC +* Number of recursive dependencies: 144 -Run `revdepcheck::cloud_details(, "RATest")` for more info +Run `revdepcheck::cloud_details(, "robber")` for more info
-## In both - -* checking whether package ‘RATest’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/RATest/new/RATest.Rcheck/00install.out’ for details. - ``` - -## Installation +## Error before installation ### Devel ``` -* installing *source* package ‘RATest’ ... -** package ‘RATest’ 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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘RATest’ -* removing ‘/tmp/workdir/RATest/new/RATest.Rcheck/RATest’ +* using log directory ‘/tmp/workdir/robber/new/robber.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘robber/DESCRIPTION’ ... OK +... +* checking tests ... OK + Running ‘spelling.R’ + Running ‘testthat.R’ +* checking for unstated dependencies in vignettes ... OK +* checking package vignettes in ‘inst/doc’ ... OK +* checking running R code from vignettes ... OK + ‘topological-analysis.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: OK + + + ``` ### CRAN ``` -* installing *source* package ‘RATest’ ... -** package ‘RATest’ 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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘RATest’ -* removing ‘/tmp/workdir/RATest/old/RATest.Rcheck/RATest’ +* using log directory ‘/tmp/workdir/robber/old/robber.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘robber/DESCRIPTION’ ... OK +... +* checking tests ... OK + Running ‘spelling.R’ + Running ‘testthat.R’ +* checking for unstated dependencies in vignettes ... OK +* checking package vignettes in ‘inst/doc’ ... OK +* checking running R code from vignettes ... OK + ‘topological-analysis.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: OK + + + ``` -# RcmdrPlugin.RiskDemo +# robmedExtra
-* Version: 3.2 -* GitHub: NA -* Source code: https://github.com/cran/RcmdrPlugin.RiskDemo -* Date/Publication: 2024-02-06 09:20:02 UTC -* Number of recursive dependencies: 208 +* Version: 0.1.0 +* GitHub: https://github.com/aalfons/robmedExtra +* Source code: https://github.com/cran/robmedExtra +* Date/Publication: 2023-06-02 14:40:02 UTC +* Number of recursive dependencies: 96 -Run `revdepcheck::cloud_details(, "RcmdrPlugin.RiskDemo")` for more info +Run `revdepcheck::cloud_details(, "robmedExtra")` for more info
## In both -* checking whether package ‘RcmdrPlugin.RiskDemo’ can be installed ... ERROR +* checking whether package ‘robmedExtra’ can be installed ... ERROR ``` Installation failed. - See ‘/tmp/workdir/RcmdrPlugin.RiskDemo/new/RcmdrPlugin.RiskDemo.Rcheck/00install.out’ for details. + See ‘/tmp/workdir/robmedExtra/new/robmedExtra.Rcheck/00install.out’ for details. ``` ## Installation @@ -5850,204 +10392,209 @@ Run `revdepcheck::cloud_details(, "RcmdrPlugin.RiskDemo")` for more info ### Devel ``` -* installing *source* package ‘RcmdrPlugin.RiskDemo’ ... -** package ‘RcmdrPlugin.RiskDemo’ successfully unpacked and MD5 sums checked +* installing *source* package ‘robmedExtra’ ... +** package ‘robmedExtra’ successfully unpacked and MD5 sums checked ** 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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Error: package or namespace load failed for ‘robmed’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): + there is no package called ‘quantreg’ Execution halted -ERROR: lazy loading failed for package ‘RcmdrPlugin.RiskDemo’ -* removing ‘/tmp/workdir/RcmdrPlugin.RiskDemo/new/RcmdrPlugin.RiskDemo.Rcheck/RcmdrPlugin.RiskDemo’ +ERROR: lazy loading failed for package ‘robmedExtra’ +* removing ‘/tmp/workdir/robmedExtra/new/robmedExtra.Rcheck/robmedExtra’ ``` ### CRAN ``` -* installing *source* package ‘RcmdrPlugin.RiskDemo’ ... -** package ‘RcmdrPlugin.RiskDemo’ successfully unpacked and MD5 sums checked +* installing *source* package ‘robmedExtra’ ... +** package ‘robmedExtra’ successfully unpacked and MD5 sums checked ** 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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Error: package or namespace load failed for ‘robmed’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): + there is no package called ‘quantreg’ Execution halted -ERROR: lazy loading failed for package ‘RcmdrPlugin.RiskDemo’ -* removing ‘/tmp/workdir/RcmdrPlugin.RiskDemo/old/RcmdrPlugin.RiskDemo.Rcheck/RcmdrPlugin.RiskDemo’ +ERROR: lazy loading failed for package ‘robmedExtra’ +* removing ‘/tmp/workdir/robmedExtra/old/robmedExtra.Rcheck/robmedExtra’ ``` -# rddtools +# rprev
-* Version: 1.6.0 -* GitHub: https://github.com/bquast/rddtools -* Source code: https://github.com/cran/rddtools -* Date/Publication: 2022-01-10 12:42:49 UTC -* Number of recursive dependencies: 102 +* Version: 1.0.5 +* GitHub: https://github.com/stulacy/rprev-dev +* Source code: https://github.com/cran/rprev +* Date/Publication: 2021-05-04 16:40:03 UTC +* Number of recursive dependencies: 124 -Run `revdepcheck::cloud_details(, "rddtools")` for more info +Run `revdepcheck::cloud_details(, "rprev")` for more info
-## In both - -* checking whether package ‘rddtools’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/rddtools/new/rddtools.Rcheck/00install.out’ for details. - ``` - -## Installation +## Error before installation ### Devel ``` -* installing *source* package ‘rddtools’ ... -** package ‘rddtools’ successfully unpacked and MD5 sums checked -** using staged installation -** R -** data -** inst -** byte-compile and prepare package for lazy loading -Error: package or namespace load failed for ‘np’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +* using log directory ‘/tmp/workdir/rprev/new/rprev.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘rprev/DESCRIPTION’ ... OK +... +--- finished re-building ‘user_guide.Rmd’ + +SUMMARY: processing the following file failed: + ‘diagnostics.Rmd’ + +Error: Vignette re-building failed. Execution halted -ERROR: lazy loading failed for package ‘rddtools’ -* removing ‘/tmp/workdir/rddtools/new/rddtools.Rcheck/rddtools’ + +* DONE +Status: 1 WARNING, 2 NOTEs + + + ``` ### CRAN ``` -* installing *source* package ‘rddtools’ ... -** package ‘rddtools’ successfully unpacked and MD5 sums checked -** using staged installation -** R -** data -** inst -** byte-compile and prepare package for lazy loading -Error: package or namespace load failed for ‘np’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +* using log directory ‘/tmp/workdir/rprev/old/rprev.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘rprev/DESCRIPTION’ ... OK +... +--- finished re-building ‘user_guide.Rmd’ + +SUMMARY: processing the following file failed: + ‘diagnostics.Rmd’ + +Error: Vignette re-building failed. Execution halted -ERROR: lazy loading failed for package ‘rddtools’ -* removing ‘/tmp/workdir/rddtools/old/rddtools.Rcheck/rddtools’ + +* DONE +Status: 1 WARNING, 2 NOTEs + + + ``` -# riskRegression +# RQdeltaCT
-* Version: 2023.12.21 -* GitHub: https://github.com/tagteam/riskRegression -* Source code: https://github.com/cran/riskRegression -* Date/Publication: 2023-12-19 17:00:02 UTC -* Number of recursive dependencies: 186 +* Version: 1.3.0 +* GitHub: NA +* Source code: https://github.com/cran/RQdeltaCT +* Date/Publication: 2024-04-17 15:50:02 UTC +* Number of recursive dependencies: 164 -Run `revdepcheck::cloud_details(, "riskRegression")` for more info +Run `revdepcheck::cloud_details(, "RQdeltaCT")` for more info
-## In both - -* checking whether package ‘riskRegression’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/riskRegression/new/riskRegression.Rcheck/00install.out’ for details. - ``` - -## Installation +## Error before installation ### Devel ``` -* installing *source* package ‘riskRegression’ ... -** package ‘riskRegression’ successfully unpacked and MD5 sums checked -** using staged installation -** libs -using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c IC-Nelson-Aalen-cens-time.cpp -o IC-Nelson-Aalen-cens-time.o -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c aucCVFun.cpp -o aucCVFun.o -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c baseHaz.cpp -o baseHaz.o -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c calcSeCSC.cpp -o calcSeCSC.o +* using log directory ‘/tmp/workdir/RQdeltaCT/new/RQdeltaCT.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘RQdeltaCT/DESCRIPTION’ ... OK ... -** R -** data -** inst -** byte-compile and prepare package for lazy loading -Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘riskRegression’ -* removing ‘/tmp/workdir/riskRegression/new/riskRegression.Rcheck/riskRegression’ +* this is package ‘RQdeltaCT’ version ‘1.3.0’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘ggpmisc’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + ``` ### CRAN ``` -* installing *source* package ‘riskRegression’ ... -** package ‘riskRegression’ successfully unpacked and MD5 sums checked -** using staged installation -** libs -using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c IC-Nelson-Aalen-cens-time.cpp -o IC-Nelson-Aalen-cens-time.o -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c aucCVFun.cpp -o aucCVFun.o -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c baseHaz.cpp -o baseHaz.o -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c calcSeCSC.cpp -o calcSeCSC.o +* using log directory ‘/tmp/workdir/RQdeltaCT/old/RQdeltaCT.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘RQdeltaCT/DESCRIPTION’ ... OK ... -** R -** data -** inst -** byte-compile and prepare package for lazy loading -Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘riskRegression’ -* removing ‘/tmp/workdir/riskRegression/old/riskRegression.Rcheck/riskRegression’ +* this is package ‘RQdeltaCT’ version ‘1.3.0’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘ggpmisc’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + ``` -# rms +# rstanarm
-* Version: 6.8-0 -* GitHub: https://github.com/harrelfe/rms -* Source code: https://github.com/cran/rms -* Date/Publication: 2024-03-11 16:20:02 UTC -* Number of recursive dependencies: 154 +* Version: 2.32.1 +* GitHub: https://github.com/stan-dev/rstanarm +* Source code: https://github.com/cran/rstanarm +* Date/Publication: 2024-01-18 23:00:03 UTC +* Number of recursive dependencies: 138 -Run `revdepcheck::cloud_details(, "rms")` for more info +Run `revdepcheck::cloud_details(, "rstanarm")` for more info
## In both -* checking whether package ‘rms’ can be installed ... ERROR +* checking whether package ‘rstanarm’ can be installed ... ERROR ``` Installation failed. - See ‘/tmp/workdir/rms/new/rms.Rcheck/00install.out’ for details. - ``` - -* checking package dependencies ... NOTE - ``` - Package suggested but not available for checking: ‘rmsb’ + See ‘/tmp/workdir/rstanarm/new/rstanarm.Rcheck/00install.out’ for details. ``` ## Installation @@ -6055,691 +10602,814 @@ Run `revdepcheck::cloud_details(, "rms")` for more info ### Devel ``` -* installing *source* package ‘rms’ ... -** package ‘rms’ successfully unpacked and MD5 sums checked +* installing *source* package ‘rstanarm’ ... +** package ‘rstanarm’ successfully unpacked and MD5 sums checked ** using staged installation ** libs -using C compiler: ‘gcc (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ -using Fortran compiler: ‘GNU Fortran (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ -gcc -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I/usr/local/include -fpic -g -O2 -c init.c -o init.o -gfortran -fpic -g -O2 -c lrmfit.f -o lrmfit.o -gfortran -fpic -g -O2 -c mlmats.f -o mlmats.o -gfortran -fpic -g -O2 -c ormuv.f -o ormuv.o +using C++ compiler: ‘g++ (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ +using C++17 +"/opt/R/4.3.1/lib/R/bin/Rscript" -e "source(file.path('..', 'tools', 'make_cc.R')); make_cc(commandArgs(TRUE))" stan_files/bernoulli.stan +Wrote C++ file "stan_files/bernoulli.cc" + + ... -** R -** demo -** inst -** byte-compile and prepare package for lazy loading -Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘rms’ -* removing ‘/tmp/workdir/rms/new/rms.Rcheck/rms’ +/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src/stan/mcmc/hmc/hamiltonians/dense_e_metric.hpp:21:10: required from here +/opt/R/4.3.1/lib/R/site-library/RcppEigen/include/Eigen/src/Core/DenseCoeffsBase.h:654:74: warning: ignoring attributes on template argument ‘Eigen::internal::packet_traits::type’ {aka ‘__m128d’} [-Wignored-attributes] + 654 | return internal::first_aligned::alignment),Derived>(m); + | ^~~~~~~~~ +g++: fatal error: Killed signal terminated program cc1plus +compilation terminated. +make: *** [/opt/R/4.3.1/lib/R/etc/Makeconf:198: stan_files/bernoulli.o] Error 1 +rm stan_files/bernoulli.cc +ERROR: compilation failed for package ‘rstanarm’ +* removing ‘/tmp/workdir/rstanarm/new/rstanarm.Rcheck/rstanarm’ ``` ### CRAN ``` -* installing *source* package ‘rms’ ... -** package ‘rms’ successfully unpacked and MD5 sums checked +* installing *source* package ‘rstanarm’ ... +** package ‘rstanarm’ successfully unpacked and MD5 sums checked ** using staged installation ** libs -using C compiler: ‘gcc (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ -using Fortran compiler: ‘GNU Fortran (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ -gcc -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I/usr/local/include -fpic -g -O2 -c init.c -o init.o -gfortran -fpic -g -O2 -c lrmfit.f -o lrmfit.o -gfortran -fpic -g -O2 -c mlmats.f -o mlmats.o -gfortran -fpic -g -O2 -c ormuv.f -o ormuv.o +using C++ compiler: ‘g++ (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ +using C++17 +"/opt/R/4.3.1/lib/R/bin/Rscript" -e "source(file.path('..', 'tools', 'make_cc.R')); make_cc(commandArgs(TRUE))" stan_files/bernoulli.stan +Wrote C++ file "stan_files/bernoulli.cc" + + ... -** R -** demo -** inst -** byte-compile and prepare package for lazy loading -Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘rms’ -* removing ‘/tmp/workdir/rms/old/rms.Rcheck/rms’ +/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src/stan/mcmc/hmc/hamiltonians/dense_e_metric.hpp:21:10: required from here +/opt/R/4.3.1/lib/R/site-library/RcppEigen/include/Eigen/src/Core/DenseCoeffsBase.h:654:74: warning: ignoring attributes on template argument ‘Eigen::internal::packet_traits::type’ {aka ‘__m128d’} [-Wignored-attributes] + 654 | return internal::first_aligned::alignment),Derived>(m); + | ^~~~~~~~~ +g++: fatal error: Killed signal terminated program cc1plus +compilation terminated. +make: *** [/opt/R/4.3.1/lib/R/etc/Makeconf:198: stan_files/bernoulli.o] Error 1 +rm stan_files/bernoulli.cc +ERROR: compilation failed for package ‘rstanarm’ +* removing ‘/tmp/workdir/rstanarm/old/rstanarm.Rcheck/rstanarm’ ``` -# rmsb +# rTwig
-* Version: 1.1-0 -* GitHub: NA -* Source code: https://github.com/cran/rmsb -* Date/Publication: 2024-03-12 15:50:02 UTC -* Number of recursive dependencies: 144 +* Version: 1.0.2 +* GitHub: https://github.com/aidanmorales/rTwig +* Source code: https://github.com/cran/rTwig +* Date/Publication: 2024-04-08 15:00:02 UTC +* Number of recursive dependencies: 188 -Run `revdepcheck::cloud_details(, "rmsb")` for more info +Run `revdepcheck::cloud_details(, "rTwig")` for more info
-## In both - -* checking whether package ‘rmsb’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/rmsb/new/rmsb.Rcheck/00install.out’ for details. - ``` - -## Installation +## Error before installation ### Devel ``` -* installing *source* package ‘rmsb’ ... -** package ‘rmsb’ successfully unpacked and MD5 sums checked -** using staged installation -Error in loadNamespace(x) : there is no package called ‘rstantools’ -Calls: loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart -Execution halted -ERROR: configuration failed for package ‘rmsb’ -* removing ‘/tmp/workdir/rmsb/new/rmsb.Rcheck/rmsb’ +* using log directory ‘/tmp/workdir/rTwig/new/rTwig.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘rTwig/DESCRIPTION’ ... OK +... +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required and available but unsuitable version: ‘Matrix’ + +Package suggested but not available for checking: ‘ggpmisc’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + ``` ### CRAN ``` -* installing *source* package ‘rmsb’ ... -** package ‘rmsb’ successfully unpacked and MD5 sums checked -** using staged installation -Error in loadNamespace(x) : there is no package called ‘rstantools’ -Calls: loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart -Execution halted -ERROR: configuration failed for package ‘rmsb’ -* removing ‘/tmp/workdir/rmsb/old/rmsb.Rcheck/rmsb’ +* using log directory ‘/tmp/workdir/rTwig/old/rTwig.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘rTwig/DESCRIPTION’ ... OK +... +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required and available but unsuitable version: ‘Matrix’ + +Package suggested but not available for checking: ‘ggpmisc’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + ``` -# robmed +# scCustomize
-* Version: 1.0.2 -* GitHub: https://github.com/aalfons/robmed -* Source code: https://github.com/cran/robmed -* Date/Publication: 2023-06-16 23:00:02 UTC -* Number of recursive dependencies: 60 +* Version: 2.1.2 +* GitHub: https://github.com/samuel-marsh/scCustomize +* Source code: https://github.com/cran/scCustomize +* Date/Publication: 2024-02-28 19:40:02 UTC +* Number of recursive dependencies: 273 -Run `revdepcheck::cloud_details(, "robmed")` for more info +Run `revdepcheck::cloud_details(, "scCustomize")` for more info
-## In both - -* checking whether package ‘robmed’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/robmed/new/robmed.Rcheck/00install.out’ for details. - ``` - -## Installation +## Error before installation ### Devel ``` -* installing *source* package ‘robmed’ ... -** package ‘robmed’ 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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘robmed’ -* removing ‘/tmp/workdir/robmed/new/robmed.Rcheck/robmed’ +* using log directory ‘/tmp/workdir/scCustomize/new/scCustomize.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘scCustomize/DESCRIPTION’ ... OK +... +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Packages required but not available: 'Seurat', 'SeuratObject' + +Package suggested but not available for checking: ‘Nebulosa’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + ``` ### CRAN ``` -* installing *source* package ‘robmed’ ... -** package ‘robmed’ 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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘robmed’ -* removing ‘/tmp/workdir/robmed/old/robmed.Rcheck/robmed’ +* using log directory ‘/tmp/workdir/scCustomize/old/scCustomize.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘scCustomize/DESCRIPTION’ ... OK +... +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Packages required but not available: 'Seurat', 'SeuratObject' + +Package suggested but not available for checking: ‘Nebulosa’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + ``` -# robmedExtra +# SCdeconR
-* Version: 0.1.0 -* GitHub: https://github.com/aalfons/robmedExtra -* Source code: https://github.com/cran/robmedExtra -* Date/Publication: 2023-06-02 14:40:02 UTC -* Number of recursive dependencies: 96 +* Version: 1.0.0 +* GitHub: https://github.com/Liuy12/SCdeconR +* Source code: https://github.com/cran/SCdeconR +* Date/Publication: 2024-03-22 19:20:02 UTC +* Number of recursive dependencies: 235 -Run `revdepcheck::cloud_details(, "robmedExtra")` for more info +Run `revdepcheck::cloud_details(, "SCdeconR")` for more info
-## In both +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/SCdeconR/new/SCdeconR.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘SCdeconR/DESCRIPTION’ ... OK +... +* this is package ‘SCdeconR’ version ‘1.0.0’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘Seurat’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + -* checking whether package ‘robmedExtra’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/robmedExtra/new/robmedExtra.Rcheck/00install.out’ for details. - ``` -## Installation -### Devel ``` -* installing *source* package ‘robmedExtra’ ... -** package ‘robmedExtra’ 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 ‘robmed’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Execution halted -ERROR: lazy loading failed for package ‘robmedExtra’ -* removing ‘/tmp/workdir/robmedExtra/new/robmedExtra.Rcheck/robmedExtra’ +### CRAN + +``` +* using log directory ‘/tmp/workdir/SCdeconR/old/SCdeconR.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘SCdeconR/DESCRIPTION’ ... OK +... +* this is package ‘SCdeconR’ version ‘1.0.0’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘Seurat’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR -``` -### CRAN -``` -* installing *source* package ‘robmedExtra’ ... -** package ‘robmedExtra’ 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 ‘robmed’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Execution halted -ERROR: lazy loading failed for package ‘robmedExtra’ -* removing ‘/tmp/workdir/robmedExtra/old/robmedExtra.Rcheck/robmedExtra’ ``` -# RPPanalyzer +# scDiffCom
-* Version: 1.4.9 +* Version: 1.0.0 * GitHub: NA -* Source code: https://github.com/cran/RPPanalyzer -* Date/Publication: 2024-01-25 11:00:02 UTC -* Number of recursive dependencies: 82 +* Source code: https://github.com/cran/scDiffCom +* Date/Publication: 2023-11-03 18:40:02 UTC +* Number of recursive dependencies: 259 -Run `revdepcheck::cloud_details(, "RPPanalyzer")` for more info +Run `revdepcheck::cloud_details(, "scDiffCom")` for more info
-## In both - -* checking whether package ‘RPPanalyzer’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/RPPanalyzer/new/RPPanalyzer.Rcheck/00install.out’ for details. - ``` - -## Installation +## Error before installation ### Devel ``` -* installing *source* package ‘RPPanalyzer’ ... -** package ‘RPPanalyzer’ successfully unpacked and MD5 sums checked -** 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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘RPPanalyzer’ -* removing ‘/tmp/workdir/RPPanalyzer/new/RPPanalyzer.Rcheck/RPPanalyzer’ +* using log directory ‘/tmp/workdir/scDiffCom/new/scDiffCom.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘scDiffCom/DESCRIPTION’ ... OK +... +* this is package ‘scDiffCom’ version ‘1.0.0’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘Seurat’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + ``` ### CRAN ``` -* installing *source* package ‘RPPanalyzer’ ... -** package ‘RPPanalyzer’ successfully unpacked and MD5 sums checked -** 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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘RPPanalyzer’ -* removing ‘/tmp/workdir/RPPanalyzer/old/RPPanalyzer.Rcheck/RPPanalyzer’ +* using log directory ‘/tmp/workdir/scDiffCom/old/scDiffCom.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘scDiffCom/DESCRIPTION’ ... OK +... +* this is package ‘scDiffCom’ version ‘1.0.0’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘Seurat’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + ``` -# RQdeltaCT +# scGate
-* Version: 1.3.0 -* GitHub: NA -* Source code: https://github.com/cran/RQdeltaCT -* Date/Publication: 2024-04-17 15:50:02 UTC -* Number of recursive dependencies: 165 +* Version: 1.6.2 +* GitHub: https://github.com/carmonalab/scGate +* Source code: https://github.com/cran/scGate +* Date/Publication: 2024-04-23 08:50:02 UTC +* Number of recursive dependencies: 178 -Run `revdepcheck::cloud_details(, "RQdeltaCT")` for more info +Run `revdepcheck::cloud_details(, "scGate")` for more info
-## In both - -* checking whether package ‘RQdeltaCT’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/RQdeltaCT/new/RQdeltaCT.Rcheck/00install.out’ for details. - ``` - -## Installation +## Error before installation ### Devel ``` -* installing *source* package ‘RQdeltaCT’ ... -** package ‘RQdeltaCT’ 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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘RQdeltaCT’ -* removing ‘/tmp/workdir/RQdeltaCT/new/RQdeltaCT.Rcheck/RQdeltaCT’ +* using log directory ‘/tmp/workdir/scGate/new/scGate.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘scGate/DESCRIPTION’ ... OK +... +* this is package ‘scGate’ version ‘1.6.2’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘Seurat’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + ``` ### CRAN ``` -* installing *source* package ‘RQdeltaCT’ ... -** package ‘RQdeltaCT’ 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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘RQdeltaCT’ -* removing ‘/tmp/workdir/RQdeltaCT/old/RQdeltaCT.Rcheck/RQdeltaCT’ +* using log directory ‘/tmp/workdir/scGate/old/scGate.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘scGate/DESCRIPTION’ ... OK +... +* this is package ‘scGate’ version ‘1.6.2’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘Seurat’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + ``` -# rstanarm +# scMappR
-* Version: 2.32.1 -* GitHub: https://github.com/stan-dev/rstanarm -* Source code: https://github.com/cran/rstanarm -* Date/Publication: 2024-01-18 23:00:03 UTC -* Number of recursive dependencies: 138 +* Version: 1.0.11 +* GitHub: NA +* Source code: https://github.com/cran/scMappR +* Date/Publication: 2023-06-30 08:40:08 UTC +* Number of recursive dependencies: 233 -Run `revdepcheck::cloud_details(, "rstanarm")` for more info +Run `revdepcheck::cloud_details(, "scMappR")` for more info
-## In both - -* checking whether package ‘rstanarm’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/rstanarm/new/rstanarm.Rcheck/00install.out’ for details. - ``` - -## Installation +## Error before installation ### Devel ``` -* installing *source* package ‘rstanarm’ ... -** package ‘rstanarm’ successfully unpacked and MD5 sums checked -** using staged installation -** libs -using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ -using C++17 -"/opt/R/4.3.1/lib/R/bin/Rscript" -e "source(file.path('..', 'tools', 'make_cc.R')); make_cc(commandArgs(TRUE))" stan_files/lm.stan -Wrote C++ file "stan_files/lm.cc" +* using log directory ‘/tmp/workdir/scMappR/new/scMappR.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘scMappR/DESCRIPTION’ ... OK +... +* this is package ‘scMappR’ version ‘1.0.11’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘Seurat’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + -... -/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src/stan/mcmc/hmc/hamiltonians/dense_e_metric.hpp:21:10: required from here -/opt/R/4.3.1/lib/R/site-library/RcppEigen/include/Eigen/src/Core/DenseCoeffsBase.h:654:34: warning: ignoring attributes on template argument ‘Eigen::internal::packet_traits::type’ {aka ‘__vector(2) double’} [-Wignored-attributes] - 654 | return internal::first_aligned::alignment),Derived>(m); - | ^~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -g++: fatal error: Killed signal terminated program cc1plus -compilation terminated. -make: *** [/opt/R/4.3.1/lib/R/etc/Makeconf:198: stan_files/mvmer.o] Error 1 -rm stan_files/lm.cc stan_files/mvmer.cc -ERROR: compilation failed for package ‘rstanarm’ -* removing ‘/tmp/workdir/rstanarm/new/rstanarm.Rcheck/rstanarm’ ``` ### CRAN ``` -* installing *source* package ‘rstanarm’ ... -** package ‘rstanarm’ successfully unpacked and MD5 sums checked -** using staged installation -** libs -using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ -using C++17 -"/opt/R/4.3.1/lib/R/bin/Rscript" -e "source(file.path('..', 'tools', 'make_cc.R')); make_cc(commandArgs(TRUE))" stan_files/lm.stan -Wrote C++ file "stan_files/lm.cc" +* using log directory ‘/tmp/workdir/scMappR/old/scMappR.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘scMappR/DESCRIPTION’ ... OK +... +* this is package ‘scMappR’ version ‘1.0.11’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘Seurat’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + -... -/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src/stan/mcmc/hmc/hamiltonians/dense_e_metric.hpp:21:10: required from here -/opt/R/4.3.1/lib/R/site-library/RcppEigen/include/Eigen/src/Core/DenseCoeffsBase.h:654:34: warning: ignoring attributes on template argument ‘Eigen::internal::packet_traits::type’ {aka ‘__vector(2) double’} [-Wignored-attributes] - 654 | return internal::first_aligned::alignment),Derived>(m); - | ^~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -g++: fatal error: Killed signal terminated program cc1plus -compilation terminated. -make: *** [/opt/R/4.3.1/lib/R/etc/Makeconf:198: stan_files/mvmer.o] Error 1 -rm stan_files/lm.cc stan_files/mvmer.cc -ERROR: compilation failed for package ‘rstanarm’ -* removing ‘/tmp/workdir/rstanarm/old/rstanarm.Rcheck/rstanarm’ ``` -# scCustomize +# SCORPIUS
-* Version: 2.1.2 -* GitHub: https://github.com/samuel-marsh/scCustomize -* Source code: https://github.com/cran/scCustomize -* Date/Publication: 2024-02-28 19:40:02 UTC -* Number of recursive dependencies: 274 +* Version: 1.0.9 +* GitHub: https://github.com/rcannood/SCORPIUS +* Source code: https://github.com/cran/SCORPIUS +* Date/Publication: 2023-08-07 17:30:05 UTC +* Number of recursive dependencies: 202 -Run `revdepcheck::cloud_details(, "scCustomize")` for more info +Run `revdepcheck::cloud_details(, "SCORPIUS")` for more info
-## In both - -* checking whether package ‘scCustomize’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/scCustomize/new/scCustomize.Rcheck/00install.out’ for details. - ``` - -* checking package dependencies ... NOTE - ``` - Package suggested but not available for checking: ‘Nebulosa’ - ``` - -## Installation +## Error before installation ### Devel ``` -* installing *source* package ‘scCustomize’ ... -** package ‘scCustomize’ successfully unpacked and MD5 sums checked -** using staged installation -** R -** data -*** moving datasets to lazyload DB -** byte-compile and prepare package for lazy loading -Error: package or namespace load failed for ‘SeuratObject’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): - namespace ‘Matrix’ 1.5-4.1 is being loaded, but >= 1.6.3 is required +* using log directory ‘/tmp/workdir/SCORPIUS/new/SCORPIUS.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘SCORPIUS/DESCRIPTION’ ... OK +... +Run `reticulate::py_last_error()` for details. Execution halted -ERROR: lazy loading failed for package ‘scCustomize’ -* removing ‘/tmp/workdir/scCustomize/new/scCustomize.Rcheck/scCustomize’ + + ‘anndata.Rmd’ using ‘UTF-8’... failed + ‘ginhoux.Rmd’ using ‘UTF-8’... OK + ‘simulated-data.Rmd’ using ‘UTF-8’... OK + ‘singlecellexperiment.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 1 ERROR, 1 NOTE + + + ``` ### CRAN ``` -* installing *source* package ‘scCustomize’ ... -** package ‘scCustomize’ successfully unpacked and MD5 sums checked -** using staged installation -** R -** data -*** moving datasets to lazyload DB -** byte-compile and prepare package for lazy loading -Error: package or namespace load failed for ‘SeuratObject’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): - namespace ‘Matrix’ 1.5-4.1 is being loaded, but >= 1.6.3 is required +* using log directory ‘/tmp/workdir/SCORPIUS/old/SCORPIUS.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘SCORPIUS/DESCRIPTION’ ... OK +... +Run `reticulate::py_last_error()` for details. Execution halted -ERROR: lazy loading failed for package ‘scCustomize’ -* removing ‘/tmp/workdir/scCustomize/old/scCustomize.Rcheck/scCustomize’ + + ‘anndata.Rmd’ using ‘UTF-8’... failed + ‘ginhoux.Rmd’ using ‘UTF-8’... OK + ‘simulated-data.Rmd’ using ‘UTF-8’... OK + ‘singlecellexperiment.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 1 ERROR, 1 NOTE + + + ``` -# SCdeconR +# scpi
-* Version: 1.0.0 -* GitHub: https://github.com/Liuy12/SCdeconR -* Source code: https://github.com/cran/SCdeconR -* Date/Publication: 2024-03-22 19:20:02 UTC -* Number of recursive dependencies: 235 +* Version: 2.2.5 +* GitHub: NA +* Source code: https://github.com/cran/scpi +* Date/Publication: 2023-11-01 06:10:07 UTC +* Number of recursive dependencies: 97 -Run `revdepcheck::cloud_details(, "SCdeconR")` for more info +Run `revdepcheck::cloud_details(, "scpi")` for more info
-## In both - -* checking whether package ‘SCdeconR’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/SCdeconR/new/SCdeconR.Rcheck/00install.out’ for details. - ``` - -## Installation +## Error before installation ### Devel ``` -* installing *source* package ‘SCdeconR’ ... -** package ‘SCdeconR’ 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 ‘SeuratObject’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): - namespace ‘Matrix’ 1.5-4.1 is being loaded, but >= 1.6.3 is required -Execution halted -ERROR: lazy loading failed for package ‘SCdeconR’ -* removing ‘/tmp/workdir/SCdeconR/new/SCdeconR.Rcheck/SCdeconR’ +* using log directory ‘/tmp/workdir/scpi/new/scpi.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘scpi/DESCRIPTION’ ... OK +... +* this is package ‘scpi’ version ‘2.2.5’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘Qtools’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + ``` ### CRAN ``` -* installing *source* package ‘SCdeconR’ ... -** package ‘SCdeconR’ 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 ‘SeuratObject’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): - namespace ‘Matrix’ 1.5-4.1 is being loaded, but >= 1.6.3 is required -Execution halted -ERROR: lazy loading failed for package ‘SCdeconR’ -* removing ‘/tmp/workdir/SCdeconR/old/SCdeconR.Rcheck/SCdeconR’ +* using log directory ‘/tmp/workdir/scpi/old/scpi.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘scpi/DESCRIPTION’ ... OK +... +* this is package ‘scpi’ version ‘2.2.5’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘Qtools’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + ``` -# scGate +# scpoisson
-* Version: 1.6.2 -* GitHub: https://github.com/carmonalab/scGate -* Source code: https://github.com/cran/scGate -* Date/Publication: 2024-04-23 08:50:02 UTC -* Number of recursive dependencies: 178 +* Version: 0.0.1 +* GitHub: NA +* Source code: https://github.com/cran/scpoisson +* Date/Publication: 2022-08-17 06:50:02 UTC +* Number of recursive dependencies: 202 -Run `revdepcheck::cloud_details(, "scGate")` for more info +Run `revdepcheck::cloud_details(, "scpoisson")` for more info
-## In both - -* checking whether package ‘scGate’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/scGate/new/scGate.Rcheck/00install.out’ for details. - ``` - -## Installation +## Error before installation ### Devel ``` -* installing *source* package ‘scGate’ ... -** package ‘scGate’ successfully unpacked and MD5 sums checked -** using staged installation -** R -** data -*** moving datasets to lazyload DB -Warning: namespace ‘Seurat’ is not available and has been replaced -by .GlobalEnv when processing object ‘query.seurat’ -Warning: namespace ‘Seurat’ is not available and has been replaced -by .GlobalEnv when processing object ‘query.seurat’ -** inst -** byte-compile and prepare package for lazy loading -Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.3 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘scGate’ -* removing ‘/tmp/workdir/scGate/new/scGate.Rcheck/scGate’ +* using log directory ‘/tmp/workdir/scpoisson/new/scpoisson.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘scpoisson/DESCRIPTION’ ... OK +... +* this is package ‘scpoisson’ version ‘0.0.1’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Packages required but not available: 'Seurat', 'SeuratObject' + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + ``` ### CRAN ``` -* installing *source* package ‘scGate’ ... -** package ‘scGate’ successfully unpacked and MD5 sums checked -** using staged installation -** R -** data -*** moving datasets to lazyload DB -Warning: namespace ‘Seurat’ is not available and has been replaced -by .GlobalEnv when processing object ‘query.seurat’ -Warning: namespace ‘Seurat’ is not available and has been replaced -by .GlobalEnv when processing object ‘query.seurat’ -** inst -** byte-compile and prepare package for lazy loading -Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.3 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘scGate’ -* removing ‘/tmp/workdir/scGate/old/scGate.Rcheck/scGate’ +* using log directory ‘/tmp/workdir/scpoisson/old/scpoisson.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘scpoisson/DESCRIPTION’ ... OK +... +* this is package ‘scpoisson’ version ‘0.0.1’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Packages required but not available: 'Seurat', 'SeuratObject' + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + ``` -# scMappR +# SCpubr
-* Version: 1.0.11 -* GitHub: NA -* Source code: https://github.com/cran/scMappR -* Date/Publication: 2023-06-30 08:40:08 UTC -* Number of recursive dependencies: 233 +* Version: 2.0.2 +* GitHub: https://github.com/enblacar/SCpubr +* Source code: https://github.com/cran/SCpubr +* Date/Publication: 2023-10-11 09:50:02 UTC +* Number of recursive dependencies: 305 -Run `revdepcheck::cloud_details(, "scMappR")` for more info +Run `revdepcheck::cloud_details(, "SCpubr")` for more info
-## In both - -* checking whether package ‘scMappR’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/scMappR/new/scMappR.Rcheck/00install.out’ for details. - ``` - -## Installation +## Error before installation ### Devel ``` -* installing *source* package ‘scMappR’ ... -** package ‘scMappR’ 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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.3 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘scMappR’ -* removing ‘/tmp/workdir/scMappR/new/scMappR.Rcheck/scMappR’ +* using log directory ‘/tmp/workdir/SCpubr/new/SCpubr.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘SCpubr/DESCRIPTION’ ... OK +... +* checking for unstated dependencies in ‘tests’ ... OK +* checking tests ... OK + Running ‘testthat.R’ +* checking for unstated dependencies in vignettes ... OK +* checking package vignettes in ‘inst/doc’ ... OK +* checking running R code from vignettes ... NONE + ‘reference_manual.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 2 NOTEs + + + ``` ### CRAN ``` -* installing *source* package ‘scMappR’ ... -** package ‘scMappR’ 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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.3 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘scMappR’ -* removing ‘/tmp/workdir/scMappR/old/scMappR.Rcheck/scMappR’ +* using log directory ‘/tmp/workdir/SCpubr/old/SCpubr.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘SCpubr/DESCRIPTION’ ... OK +... +* checking for unstated dependencies in ‘tests’ ... OK +* checking tests ... OK + Running ‘testthat.R’ +* checking for unstated dependencies in vignettes ... OK +* checking package vignettes in ‘inst/doc’ ... OK +* checking running R code from vignettes ... NONE + ‘reference_manual.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 2 NOTEs + + + ``` @@ -6757,67 +11427,65 @@ Run `revdepcheck::cloud_details(, "scRNAstat")` for more info -## In both +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/scRNAstat/new/scRNAstat.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘scRNAstat/DESCRIPTION’ ... OK +... +* this is package ‘scRNAstat’ version ‘0.1.1’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘Seurat’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + -* checking whether package ‘scRNAstat’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/scRNAstat/new/scRNAstat.Rcheck/00install.out’ for details. - ``` -## Installation -### Devel ``` -* installing *source* package ‘scRNAstat’ ... -** package ‘scRNAstat’ successfully unpacked and MD5 sums checked -** using staged installation -** R -** data -*** moving datasets to lazyload DB -Warning: namespace ‘Seurat’ is not available and has been replaced -by .GlobalEnv when processing object ‘AJ064_small_last_sce’ -Warning: namespace ‘SeuratObject’ is not available and has been replaced -by .GlobalEnv when processing object ‘AJ064_small_last_sce’ -... -by .GlobalEnv when processing object ‘AJ064_small_last_sce’ -Warning: namespace ‘DBI’ is not available and has been replaced -by .GlobalEnv when processing object ‘AJ064_small_last_sce’ -** byte-compile and prepare package for lazy loading -Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.3 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘scRNAstat’ -* removing ‘/tmp/workdir/scRNAstat/new/scRNAstat.Rcheck/scRNAstat’ +### CRAN + +``` +* using log directory ‘/tmp/workdir/scRNAstat/old/scRNAstat.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘scRNAstat/DESCRIPTION’ ... OK +... +* this is package ‘scRNAstat’ version ‘0.1.1’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘Seurat’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR -``` -### CRAN -``` -* installing *source* package ‘scRNAstat’ ... -** package ‘scRNAstat’ successfully unpacked and MD5 sums checked -** using staged installation -** R -** data -*** moving datasets to lazyload DB -Warning: namespace ‘Seurat’ is not available and has been replaced -by .GlobalEnv when processing object ‘AJ064_small_last_sce’ -Warning: namespace ‘SeuratObject’ is not available and has been replaced -by .GlobalEnv when processing object ‘AJ064_small_last_sce’ -... -by .GlobalEnv when processing object ‘AJ064_small_last_sce’ -Warning: namespace ‘DBI’ is not available and has been replaced -by .GlobalEnv when processing object ‘AJ064_small_last_sce’ -** byte-compile and prepare package for lazy loading -Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.3 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘scRNAstat’ -* removing ‘/tmp/workdir/scRNAstat/old/scRNAstat.Rcheck/scRNAstat’ ``` @@ -6856,9 +11524,9 @@ Run `revdepcheck::cloud_details(, "sectorgap")` for more info *** 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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Error in loadNamespace(i, c(lib.loc, .libPaths()), versionCheck = vI[[i]]) : + there is no package called ‘quantreg’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart Execution halted ERROR: lazy loading failed for package ‘sectorgap’ * removing ‘/tmp/workdir/sectorgap/new/sectorgap.Rcheck/sectorgap’ @@ -6876,9 +11544,9 @@ ERROR: lazy loading failed for package ‘sectorgap’ *** 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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Error in loadNamespace(i, c(lib.loc, .libPaths()), versionCheck = vI[[i]]) : + there is no package called ‘quantreg’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart Execution halted ERROR: lazy loading failed for package ‘sectorgap’ * removing ‘/tmp/workdir/sectorgap/old/sectorgap.Rcheck/sectorgap’ @@ -6916,8 +11584,8 @@ Run `revdepcheck::cloud_details(, "SEERaBomb")` for more info ** package ‘SEERaBomb’ successfully unpacked and MD5 sums checked ** using staged installation ** libs -using C compiler: ‘gcc (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ -using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ +using C compiler: ‘gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ +using C++ compiler: ‘g++ (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o gcc -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c SEERaBomb_init.c -o SEERaBomb_init.o g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c fillPYM.cpp -o fillPYM.o @@ -6929,7 +11597,7 @@ g++ -std=gnu++17 -shared -L/opt/R/4.3.1/lib/R/lib -L/usr/local/lib -o SEERaBomb. ** inst ** byte-compile and prepare package for lazy loading Error: package or namespace load failed for ‘demography’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required + there is no package called ‘quantreg’ Execution halted ERROR: lazy loading failed for package ‘SEERaBomb’ * removing ‘/tmp/workdir/SEERaBomb/new/SEERaBomb.Rcheck/SEERaBomb’ @@ -6943,8 +11611,8 @@ ERROR: lazy loading failed for package ‘SEERaBomb’ ** package ‘SEERaBomb’ successfully unpacked and MD5 sums checked ** using staged installation ** libs -using C compiler: ‘gcc (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ -using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ +using C compiler: ‘gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ +using C++ compiler: ‘g++ (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o gcc -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c SEERaBomb_init.c -o SEERaBomb_init.o g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c fillPYM.cpp -o fillPYM.o @@ -6956,7 +11624,7 @@ g++ -std=gnu++17 -shared -L/opt/R/4.3.1/lib/R/lib -L/usr/local/lib -o SEERaBomb. ** inst ** byte-compile and prepare package for lazy loading Error: package or namespace load failed for ‘demography’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required + there is no package called ‘quantreg’ Execution halted ERROR: lazy loading failed for package ‘SEERaBomb’ * removing ‘/tmp/workdir/SEERaBomb/old/SEERaBomb.Rcheck/SEERaBomb’ @@ -7029,7 +11697,7 @@ ERROR: lazy loading failed for package ‘semicmprskcoxmsm’ * GitHub: https://github.com/IbtihelRebhi/SensMap * Source code: https://github.com/cran/SensMap * Date/Publication: 2022-07-04 19:00:02 UTC -* Number of recursive dependencies: 146 +* Number of recursive dependencies: 145 Run `revdepcheck::cloud_details(, "SensMap")` for more info @@ -7056,9 +11724,9 @@ Run `revdepcheck::cloud_details(, "SensMap")` for more info *** 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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Error in loadNamespace(i, c(lib.loc, .libPaths()), versionCheck = vI[[i]]) : + there is no package called ‘quantreg’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart Execution halted ERROR: lazy loading failed for package ‘SensMap’ * removing ‘/tmp/workdir/SensMap/new/SensMap.Rcheck/SensMap’ @@ -7076,113 +11744,111 @@ ERROR: lazy loading failed for package ‘SensMap’ *** 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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Error in loadNamespace(i, c(lib.loc, .libPaths()), versionCheck = vI[[i]]) : + there is no package called ‘quantreg’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart Execution halted ERROR: lazy loading failed for package ‘SensMap’ * removing ‘/tmp/workdir/SensMap/old/SensMap.Rcheck/SensMap’ ``` -# Seurat +# shinyTempSignal
-* Version: 5.0.3 -* GitHub: https://github.com/satijalab/seurat -* Source code: https://github.com/cran/Seurat -* Date/Publication: 2024-03-18 23:40:02 UTC -* Number of recursive dependencies: 265 +* Version: 0.0.8 +* GitHub: https://github.com/YuLab-SMU/shinyTempSignal +* Source code: https://github.com/cran/shinyTempSignal +* Date/Publication: 2024-03-06 08:00:02 UTC +* Number of recursive dependencies: 137 -Run `revdepcheck::cloud_details(, "Seurat")` for more info +Run `revdepcheck::cloud_details(, "shinyTempSignal")` for more info
-## In both - -* checking whether package ‘Seurat’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/Seurat/new/Seurat.Rcheck/00install.out’ for details. - ``` - -## Installation +## Error before installation ### Devel ``` -* installing *source* package ‘Seurat’ ... -** package ‘Seurat’ successfully unpacked and MD5 sums checked -** using staged installation -** libs -using C compiler: ‘gcc (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ -using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ -using C++17 -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppEigen/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppProgress/include' -I/usr/local/include -fpic -g -O2 -c ModularityOptimizer.cpp -o ModularityOptimizer.o -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppEigen/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppProgress/include' -I/usr/local/include -fpic -g -O2 -c RModularityOptimizer.cpp -o RModularityOptimizer.o -In file included from /opt/R/4.3.1/lib/R/site-library/RcppEigen/include/Eigen/Core:205, +* using log directory ‘/tmp/workdir/shinyTempSignal/new/shinyTempSignal.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘shinyTempSignal/DESCRIPTION’ ... OK ... -** R -** data -*** moving datasets to lazyload DB -** inst -** byte-compile and prepare package for lazy loading -Error: package or namespace load failed for ‘SeuratObject’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): - namespace ‘Matrix’ 1.5-4.1 is being loaded, but >= 1.6.3 is required -Execution halted -ERROR: lazy loading failed for package ‘Seurat’ -* removing ‘/tmp/workdir/Seurat/new/Seurat.Rcheck/Seurat’ +* this is package ‘shinyTempSignal’ version ‘0.0.8’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘ggpmisc’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + ``` ### CRAN ``` -* installing *source* package ‘Seurat’ ... -** package ‘Seurat’ successfully unpacked and MD5 sums checked -** using staged installation -** libs -using C compiler: ‘gcc (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ -using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ -using C++17 -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppEigen/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppProgress/include' -I/usr/local/include -fpic -g -O2 -c ModularityOptimizer.cpp -o ModularityOptimizer.o -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppEigen/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppProgress/include' -I/usr/local/include -fpic -g -O2 -c RModularityOptimizer.cpp -o RModularityOptimizer.o -In file included from /opt/R/4.3.1/lib/R/site-library/RcppEigen/include/Eigen/Core:205, +* using log directory ‘/tmp/workdir/shinyTempSignal/old/shinyTempSignal.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘shinyTempSignal/DESCRIPTION’ ... OK ... -** R -** data -*** moving datasets to lazyload DB -** inst -** byte-compile and prepare package for lazy loading -Error: package or namespace load failed for ‘SeuratObject’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): - namespace ‘Matrix’ 1.5-4.1 is being loaded, but >= 1.6.3 is required -Execution halted -ERROR: lazy loading failed for package ‘Seurat’ -* removing ‘/tmp/workdir/Seurat/old/Seurat.Rcheck/Seurat’ +* this is package ‘shinyTempSignal’ version ‘0.0.8’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘ggpmisc’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + ``` -# shinyTempSignal +# sievePH
-* Version: 0.0.8 -* GitHub: https://github.com/YuLab-SMU/shinyTempSignal -* Source code: https://github.com/cran/shinyTempSignal -* Date/Publication: 2024-03-06 08:00:02 UTC -* Number of recursive dependencies: 137 +* Version: 1.1 +* GitHub: https://github.com/mjuraska/sievePH +* Source code: https://github.com/cran/sievePH +* Date/Publication: 2024-05-17 23:40:02 UTC +* Number of recursive dependencies: 86 -Run `revdepcheck::cloud_details(, "shinyTempSignal")` for more info +Run `revdepcheck::cloud_details(, "sievePH")` for more info
## In both -* checking whether package ‘shinyTempSignal’ can be installed ... ERROR +* checking whether package ‘sievePH’ can be installed ... ERROR ``` Installation failed. - See ‘/tmp/workdir/shinyTempSignal/new/shinyTempSignal.Rcheck/00install.out’ for details. + See ‘/tmp/workdir/sievePH/new/sievePH.Rcheck/00install.out’ for details. ``` ## Installation @@ -7190,36 +11856,46 @@ Run `revdepcheck::cloud_details(, "shinyTempSignal")` for more info ### Devel ``` -* installing *source* package ‘shinyTempSignal’ ... -** package ‘shinyTempSignal’ successfully unpacked and MD5 sums checked +* installing *source* package ‘sievePH’ ... +** package ‘sievePH’ successfully unpacked and MD5 sums checked ** using staged installation +** libs +using C++ compiler: ‘g++ (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c kernel_sievePH_utils.cpp -o kernel_sievePH_utils.o +g++ -std=gnu++17 -shared -L/opt/R/4.3.1/lib/R/lib -L/usr/local/lib -o sievePH.so RcppExports.o kernel_sievePH_utils.o -fopenmp -llapack -lblas -lgfortran -lm -lquadmath -L/opt/R/4.3.1/lib/R/lib -lR +installing to /tmp/workdir/sievePH/new/sievePH.Rcheck/00LOCK-sievePH/00new/sievePH/libs ** R -** inst ** byte-compile and prepare package for lazy loading Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace + there is no package called ‘quantreg’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart Execution halted -ERROR: lazy loading failed for package ‘shinyTempSignal’ -* removing ‘/tmp/workdir/shinyTempSignal/new/shinyTempSignal.Rcheck/shinyTempSignal’ +ERROR: lazy loading failed for package ‘sievePH’ +* removing ‘/tmp/workdir/sievePH/new/sievePH.Rcheck/sievePH’ ``` ### CRAN ``` -* installing *source* package ‘shinyTempSignal’ ... -** package ‘shinyTempSignal’ successfully unpacked and MD5 sums checked +* installing *source* package ‘sievePH’ ... +** package ‘sievePH’ successfully unpacked and MD5 sums checked ** using staged installation +** libs +using C++ compiler: ‘g++ (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c kernel_sievePH_utils.cpp -o kernel_sievePH_utils.o +g++ -std=gnu++17 -shared -L/opt/R/4.3.1/lib/R/lib -L/usr/local/lib -o sievePH.so RcppExports.o kernel_sievePH_utils.o -fopenmp -llapack -lblas -lgfortran -lm -lquadmath -L/opt/R/4.3.1/lib/R/lib -lR +installing to /tmp/workdir/sievePH/old/sievePH.Rcheck/00LOCK-sievePH/00new/sievePH/libs ** R -** inst ** byte-compile and prepare package for lazy loading Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace + there is no package called ‘quantreg’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart Execution halted -ERROR: lazy loading failed for package ‘shinyTempSignal’ -* removing ‘/tmp/workdir/shinyTempSignal/old/shinyTempSignal.Rcheck/shinyTempSignal’ +ERROR: lazy loading failed for package ‘sievePH’ +* removing ‘/tmp/workdir/sievePH/old/sievePH.Rcheck/sievePH’ ``` @@ -7237,131 +11913,217 @@ Run `revdepcheck::cloud_details(, "Signac")` for more info -## In both - -* checking whether package ‘Signac’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/Signac/new/Signac.Rcheck/00install.out’ for details. - ``` - -## Installation +## Error before installation ### Devel ``` -* installing *source* package ‘Signac’ ... -** package ‘Signac’ successfully unpacked and MD5 sums checked -** using staged installation -** libs -using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c filter.cpp -o filter.o -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c group.cpp -o group.o -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c split.cpp -o split.o -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c validate.cpp -o validate.o +* using log directory ‘/tmp/workdir/Signac/new/Signac.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘Signac/DESCRIPTION’ ... OK ... -** 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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.3 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘Signac’ -* removing ‘/tmp/workdir/Signac/new/Signac.Rcheck/Signac’ +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘SeuratObject’ + +Package suggested but not available for checking: ‘Seurat’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + ``` ### CRAN ``` -* installing *source* package ‘Signac’ ... -** package ‘Signac’ successfully unpacked and MD5 sums checked -** using staged installation -** libs -using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c filter.cpp -o filter.o -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c group.cpp -o group.o -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c split.cpp -o split.o -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c validate.cpp -o validate.o +* using log directory ‘/tmp/workdir/Signac/old/Signac.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘Signac/DESCRIPTION’ ... OK ... -** 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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.3 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘Signac’ -* removing ‘/tmp/workdir/Signac/old/Signac.Rcheck/Signac’ +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘SeuratObject’ + +Package suggested but not available for checking: ‘Seurat’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + ``` -# SimplyAgree +# simET
-* Version: 0.2.0 -* GitHub: https://github.com/arcaldwell49/SimplyAgree -* Source code: https://github.com/cran/SimplyAgree -* Date/Publication: 2024-03-21 14:20:06 UTC -* Number of recursive dependencies: 111 +* Version: 1.0.3 +* GitHub: NA +* Source code: https://github.com/cran/simET +* Date/Publication: 2023-08-19 14:40:02 UTC +* Number of recursive dependencies: 97 -Run `revdepcheck::cloud_details(, "SimplyAgree")` for more info +Run `revdepcheck::cloud_details(, "simET")` for more info
-## In both +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/simET/new/simET.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘simET/DESCRIPTION’ ... OK +... +* this is package ‘simET’ version ‘1.0.3’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘ggpmisc’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/simET/old/simET.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘simET/DESCRIPTION’ ... OK +... +* this is package ‘simET’ version ‘1.0.3’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘ggpmisc’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + -* checking whether package ‘SimplyAgree’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/SimplyAgree/new/SimplyAgree.Rcheck/00install.out’ for details. - ``` -## Installation + + +``` +# simstudy + +
+ +* Version: 0.8.0 +* GitHub: https://github.com/kgoldfeld/simstudy +* Source code: https://github.com/cran/simstudy +* Date/Publication: 2024-05-15 13:50:02 UTC +* Number of recursive dependencies: 176 + +Run `revdepcheck::cloud_details(, "simstudy")` for more info + +
+ +## Error before installation ### Devel ``` -* installing *source* package ‘SimplyAgree’ ... -** package ‘SimplyAgree’ 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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +* using log directory ‘/tmp/workdir/simstudy/new/simstudy.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘simstudy/DESCRIPTION’ ... OK +... +--- finished re-building ‘treat_and_exposure.Rmd’ + +SUMMARY: processing the following file failed: + ‘logisticCoefs.Rmd’ + +Error: Vignette re-building failed. Execution halted -ERROR: lazy loading failed for package ‘SimplyAgree’ -* removing ‘/tmp/workdir/SimplyAgree/new/SimplyAgree.Rcheck/SimplyAgree’ + +* DONE +Status: 1 WARNING, 2 NOTEs + + + ``` ### CRAN ``` -* installing *source* package ‘SimplyAgree’ ... -** package ‘SimplyAgree’ 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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +* using log directory ‘/tmp/workdir/simstudy/old/simstudy.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘simstudy/DESCRIPTION’ ... OK +... +--- finished re-building ‘treat_and_exposure.Rmd’ + +SUMMARY: processing the following file failed: + ‘logisticCoefs.Rmd’ + +Error: Vignette re-building failed. Execution halted -ERROR: lazy loading failed for package ‘SimplyAgree’ -* removing ‘/tmp/workdir/SimplyAgree/old/SimplyAgree.Rcheck/SimplyAgree’ + +* DONE +Status: 1 WARNING, 2 NOTEs + + + ``` @@ -7379,51 +12141,65 @@ Run `revdepcheck::cloud_details(, "sMSROC")` for more info -## In both - -* checking whether package ‘sMSROC’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/sMSROC/new/sMSROC.Rcheck/00install.out’ for details. - ``` - -## Installation +## Error before installation ### Devel ``` -* installing *source* package ‘sMSROC’ ... -** package ‘sMSROC’ successfully unpacked and MD5 sums checked -** using staged installation -** R -** data -*** moving datasets to lazyload DB -** byte-compile and prepare package for lazy loading -Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘sMSROC’ -* removing ‘/tmp/workdir/sMSROC/new/sMSROC.Rcheck/sMSROC’ +* using log directory ‘/tmp/workdir/sMSROC/new/sMSROC.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘sMSROC/DESCRIPTION’ ... OK +... +* this is package ‘sMSROC’ version ‘0.1.2’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘rms’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + ``` ### CRAN ``` -* installing *source* package ‘sMSROC’ ... -** package ‘sMSROC’ successfully unpacked and MD5 sums checked -** using staged installation -** R -** data -*** moving datasets to lazyload DB -** byte-compile and prepare package for lazy loading -Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘sMSROC’ -* removing ‘/tmp/workdir/sMSROC/old/sMSROC.Rcheck/sMSROC’ +* using log directory ‘/tmp/workdir/sMSROC/old/sMSROC.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘sMSROC/DESCRIPTION’ ... OK +... +* this is package ‘sMSROC’ version ‘0.1.2’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘rms’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + ``` @@ -7441,51 +12217,65 @@ Run `revdepcheck::cloud_details(, "SNPassoc")` for more info -## In both - -* checking whether package ‘SNPassoc’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/SNPassoc/new/SNPassoc.Rcheck/00install.out’ for details. - ``` - -## Installation +## Error before installation ### Devel ``` -* installing *source* package ‘SNPassoc’ ... -** package ‘SNPassoc’ successfully unpacked and MD5 sums checked -** 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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘SNPassoc’ -* removing ‘/tmp/workdir/SNPassoc/new/SNPassoc.Rcheck/SNPassoc’ +* using log directory ‘/tmp/workdir/SNPassoc/new/SNPassoc.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘SNPassoc/DESCRIPTION’ ... OK +... +* checking if there is a namespace ... OK +* checking for executable files ... OK +* checking for hidden files and directories ... OK +* checking for portable file names ... OK +* checking for sufficient/correct file permissions ... OK +* checking whether package ‘SNPassoc’ can be installed ... ERROR +Installation failed. +See ‘/tmp/workdir/SNPassoc/new/SNPassoc.Rcheck/00install.out’ for details. +* DONE +Status: 1 ERROR + + + ``` ### CRAN ``` -* installing *source* package ‘SNPassoc’ ... -** package ‘SNPassoc’ successfully unpacked and MD5 sums checked -** 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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘SNPassoc’ -* removing ‘/tmp/workdir/SNPassoc/old/SNPassoc.Rcheck/SNPassoc’ +* using log directory ‘/tmp/workdir/SNPassoc/old/SNPassoc.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘SNPassoc/DESCRIPTION’ ... OK +... +* checking if there is a namespace ... OK +* checking for executable files ... OK +* checking for hidden files and directories ... OK +* checking for portable file names ... OK +* checking for sufficient/correct file permissions ... OK +* checking whether package ‘SNPassoc’ can be installed ... ERROR +Installation failed. +See ‘/tmp/workdir/SNPassoc/old/SNPassoc.Rcheck/00install.out’ for details. +* DONE +Status: 1 ERROR + + + ``` @@ -7497,7 +12287,7 @@ ERROR: lazy loading failed for package ‘SNPassoc’ * GitHub: NA * Source code: https://github.com/cran/snplinkage * Date/Publication: 2023-05-04 08:10:02 UTC -* Number of recursive dependencies: 146 +* Number of recursive dependencies: 145 Run `revdepcheck::cloud_details(, "snplinkage")` for more info @@ -7512,9 +12302,9 @@ Run `revdepcheck::cloud_details(, "snplinkage")` for more info * using R version 4.3.1 (2023-06-16) * using platform: x86_64-pc-linux-gnu (64-bit) * R was compiled by - gcc (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0 - GNU Fortran (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0 -* running under: Ubuntu 20.04.6 LTS + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS * using session charset: UTF-8 * using option ‘--no-manual’ * checking for file ‘snplinkage/DESCRIPTION’ ... OK @@ -7542,9 +12332,9 @@ Status: 1 ERROR * using R version 4.3.1 (2023-06-16) * using platform: x86_64-pc-linux-gnu (64-bit) * R was compiled by - gcc (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0 - GNU Fortran (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0 -* running under: Ubuntu 20.04.6 LTS + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS * using session charset: UTF-8 * using option ‘--no-manual’ * checking for file ‘snplinkage/DESCRIPTION’ ... OK @@ -7579,53 +12369,65 @@ Run `revdepcheck::cloud_details(, "SoupX")` for more info -## In both - -* checking whether package ‘SoupX’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/SoupX/new/SoupX.Rcheck/00install.out’ for details. - ``` - -## Installation +## Error before installation ### Devel ``` -* installing *source* package ‘SoupX’ ... -** package ‘SoupX’ 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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.3 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘SoupX’ -* removing ‘/tmp/workdir/SoupX/new/SoupX.Rcheck/SoupX’ +* using log directory ‘/tmp/workdir/SoupX/new/SoupX.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘SoupX/DESCRIPTION’ ... OK +... +* this is package ‘SoupX’ version ‘1.6.2’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘Seurat’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + ``` ### CRAN ``` -* installing *source* package ‘SoupX’ ... -** package ‘SoupX’ 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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.3 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘SoupX’ -* removing ‘/tmp/workdir/SoupX/old/SoupX.Rcheck/SoupX’ +* using log directory ‘/tmp/workdir/SoupX/old/SoupX.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘SoupX/DESCRIPTION’ ... OK +... +* this is package ‘SoupX’ version ‘1.6.2’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘Seurat’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + ``` @@ -7660,7 +12462,7 @@ Run `revdepcheck::cloud_details(, "sparsereg")` for more info ** package ‘sparsereg’ successfully unpacked and MD5 sums checked ** using staged installation ** libs -using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ +using C++ compiler: ‘g++ (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c makeinter.cpp -o makeinter.o g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c makethreeinter.cpp -o makethreeinter.o @@ -7669,9 +12471,9 @@ g++ -std=gnu++17 -shared -L/opt/R/4.3.1/lib/R/lib -L/usr/local/lib -o sparsereg. installing to /tmp/workdir/sparsereg/new/sparsereg.Rcheck/00LOCK-sparsereg/00new/sparsereg/libs ** R ** byte-compile and prepare package for lazy loading -Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Error in loadNamespace(i, c(lib.loc, .libPaths()), versionCheck = vI[[i]]) : + there is no package called ‘quantreg’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart Execution halted ERROR: lazy loading failed for package ‘sparsereg’ * removing ‘/tmp/workdir/sparsereg/new/sparsereg.Rcheck/sparsereg’ @@ -7685,7 +12487,7 @@ ERROR: lazy loading failed for package ‘sparsereg’ ** package ‘sparsereg’ successfully unpacked and MD5 sums checked ** using staged installation ** libs -using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ +using C++ compiler: ‘g++ (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c makeinter.cpp -o makeinter.o g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c makethreeinter.cpp -o makethreeinter.o @@ -7694,14 +12496,90 @@ g++ -std=gnu++17 -shared -L/opt/R/4.3.1/lib/R/lib -L/usr/local/lib -o sparsereg. installing to /tmp/workdir/sparsereg/old/sparsereg.Rcheck/00LOCK-sparsereg/00new/sparsereg/libs ** R ** byte-compile and prepare package for lazy loading -Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Error in loadNamespace(i, c(lib.loc, .libPaths()), versionCheck = vI[[i]]) : + there is no package called ‘quantreg’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart Execution halted ERROR: lazy loading failed for package ‘sparsereg’ * removing ‘/tmp/workdir/sparsereg/old/sparsereg.Rcheck/sparsereg’ +``` +# SPECK + +
+ +* Version: 1.0.0 +* GitHub: NA +* Source code: https://github.com/cran/SPECK +* Date/Publication: 2023-11-17 17:30:02 UTC +* Number of recursive dependencies: 161 + +Run `revdepcheck::cloud_details(, "SPECK")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/SPECK/new/SPECK.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘SPECK/DESCRIPTION’ ... OK +... +Package required but not available: ‘Seurat’ + +Package required and available but unsuitable version: ‘Matrix’ + +Package suggested but not available for checking: ‘SeuratObject’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/SPECK/old/SPECK.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘SPECK/DESCRIPTION’ ... OK +... +Package required but not available: ‘Seurat’ + +Package required and available but unsuitable version: ‘Matrix’ + +Package suggested but not available for checking: ‘SeuratObject’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + ``` # spikeSlabGAM @@ -7734,7 +12612,7 @@ Run `revdepcheck::cloud_details(, "spikeSlabGAM")` for more info ** package ‘spikeSlabGAM’ successfully unpacked and MD5 sums checked ** using staged installation ** libs -using C compiler: ‘gcc (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ +using C compiler: ‘gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ gcc -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I/usr/local/include -fpic -g -O2 -c sampler.c -o sampler.o gcc -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I/usr/local/include -fpic -g -O2 -c spikeSlabGAM_init.c -o spikeSlabGAM_init.o gcc -shared -L/opt/R/4.3.1/lib/R/lib -L/usr/local/lib -o spikeSlabGAM.so sampler.o spikeSlabGAM_init.o -llapack -lblas -lgfortran -lm -lquadmath -L/opt/R/4.3.1/lib/R/lib -lR @@ -7742,9 +12620,9 @@ installing to /tmp/workdir/spikeSlabGAM/new/spikeSlabGAM.Rcheck/00LOCK-spikeSlab ** R ** inst ** byte-compile and prepare package for lazy loading -Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Error in loadNamespace(i, c(lib.loc, .libPaths()), versionCheck = vI[[i]]) : + there is no package called ‘quantreg’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart Execution halted ERROR: lazy loading failed for package ‘spikeSlabGAM’ * removing ‘/tmp/workdir/spikeSlabGAM/new/spikeSlabGAM.Rcheck/spikeSlabGAM’ @@ -7758,7 +12636,7 @@ ERROR: lazy loading failed for package ‘spikeSlabGAM’ ** package ‘spikeSlabGAM’ successfully unpacked and MD5 sums checked ** using staged installation ** libs -using C compiler: ‘gcc (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ +using C compiler: ‘gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ gcc -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I/usr/local/include -fpic -g -O2 -c sampler.c -o sampler.o gcc -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I/usr/local/include -fpic -g -O2 -c spikeSlabGAM_init.c -o spikeSlabGAM_init.o gcc -shared -L/opt/R/4.3.1/lib/R/lib -L/usr/local/lib -o spikeSlabGAM.so sampler.o spikeSlabGAM_init.o -llapack -lblas -lgfortran -lm -lquadmath -L/opt/R/4.3.1/lib/R/lib -lR @@ -7766,9 +12644,9 @@ installing to /tmp/workdir/spikeSlabGAM/old/spikeSlabGAM.Rcheck/00LOCK-spikeSlab ** R ** inst ** byte-compile and prepare package for lazy loading -Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Error in loadNamespace(i, c(lib.loc, .libPaths()), versionCheck = vI[[i]]) : + there is no package called ‘quantreg’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart Execution halted ERROR: lazy loading failed for package ‘spikeSlabGAM’ * removing ‘/tmp/workdir/spikeSlabGAM/old/spikeSlabGAM.Rcheck/spikeSlabGAM’ @@ -7783,7 +12661,7 @@ ERROR: lazy loading failed for package ‘spikeSlabGAM’ * GitHub: https://github.com/StatsWithR/statsr * Source code: https://github.com/cran/statsr * Date/Publication: 2021-01-22 20:40:03 UTC -* Number of recursive dependencies: 98 +* Number of recursive dependencies: 97 Run `revdepcheck::cloud_details(, "statsr")` for more info @@ -7860,9 +12738,9 @@ Run `revdepcheck::cloud_details(, "streamDAG")` for more info * using R version 4.3.1 (2023-06-16) * using platform: x86_64-pc-linux-gnu (64-bit) * R was compiled by - gcc (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0 - GNU Fortran (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0 -* running under: Ubuntu 20.04.6 LTS + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS * using session charset: UTF-8 * using option ‘--no-manual’ * checking for file ‘streamDAG/DESCRIPTION’ ... OK @@ -7888,9 +12766,9 @@ Status: 1 ERROR * using R version 4.3.1 (2023-06-16) * using platform: x86_64-pc-linux-gnu (64-bit) * R was compiled by - gcc (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0 - GNU Fortran (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0 -* running under: Ubuntu 20.04.6 LTS + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS * using session charset: UTF-8 * using option ‘--no-manual’ * checking for file ‘streamDAG/DESCRIPTION’ ... OK @@ -7908,6 +12786,234 @@ Status: 1 ERROR +``` +# sure + +
+ +* Version: 0.2.0 +* GitHub: https://github.com/AFIT-R/sure +* Source code: https://github.com/cran/sure +* Date/Publication: 2017-09-19 18:04:46 UTC +* Number of recursive dependencies: 96 + +Run `revdepcheck::cloud_details(, "sure")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/sure/new/sure.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘sure/DESCRIPTION’ ... OK +... +* checking contents of ‘data’ directory ... OK +* checking data for non-ASCII characters ... OK +* checking LazyData ... OK +* checking data for ASCII and uncompressed saves ... OK +* checking examples ... OK +* checking for unstated dependencies in ‘tests’ ... OK +* checking tests ... OK + Running ‘testthat.R’ +* DONE +Status: 2 NOTEs + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/sure/old/sure.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘sure/DESCRIPTION’ ... OK +... +* checking contents of ‘data’ directory ... OK +* checking data for non-ASCII characters ... OK +* checking LazyData ... OK +* checking data for ASCII and uncompressed saves ... OK +* checking examples ... OK +* checking for unstated dependencies in ‘tests’ ... OK +* checking tests ... OK + Running ‘testthat.R’ +* DONE +Status: 2 NOTEs + + + + + +``` +# Surrogate + +
+ +* Version: 3.2.6 +* GitHub: https://github.com/florianstijven/Surrogate-development +* Source code: https://github.com/cran/Surrogate +* Date/Publication: 2024-05-27 12:30:02 UTC +* Number of recursive dependencies: 194 + +Run `revdepcheck::cloud_details(, "Surrogate")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/Surrogate/new/Surrogate.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘Surrogate/DESCRIPTION’ ... OK +... +* this is package ‘Surrogate’ version ‘3.2.6’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘rms’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/Surrogate/old/Surrogate.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘Surrogate/DESCRIPTION’ ... OK +... +* this is package ‘Surrogate’ version ‘3.2.6’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘rms’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# survex + +
+ +* Version: 1.2.0 +* GitHub: https://github.com/ModelOriented/survex +* Source code: https://github.com/cran/survex +* Date/Publication: 2023-10-24 18:50:07 UTC +* Number of recursive dependencies: 182 + +Run `revdepcheck::cloud_details(, "survex")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/survex/new/survex.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘survex/DESCRIPTION’ ... OK +... +  A new explainer has been created!  +> +> y <- cph_exp$y +> times <- cph_exp$times +> surv <- cph_exp$predict_survival_function(cph, cph_exp$data, times) +Error in loadNamespace(x) : there is no package called ‘riskRegression’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Execution halted +* DONE +Status: 1 ERROR, 1 NOTE + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/survex/old/survex.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘survex/DESCRIPTION’ ... OK +... +  A new explainer has been created!  +> +> y <- cph_exp$y +> times <- cph_exp$times +> surv <- cph_exp$predict_survival_function(cph, cph_exp$data, times) +Error in loadNamespace(x) : there is no package called ‘riskRegression’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Execution halted +* DONE +Status: 1 ERROR, 1 NOTE + + + + + ``` # survHE @@ -7923,59 +13029,65 @@ Run `revdepcheck::cloud_details(, "survHE")` for more info -## In both +## Error before installation -* checking whether package ‘survHE’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/survHE/new/survHE.Rcheck/00install.out’ for details. - ``` +### Devel -* checking package dependencies ... NOTE - ``` - Packages suggested but not available for checking: - 'survHEinla', 'survHEhmc' - ``` +``` +* using log directory ‘/tmp/workdir/survHE/new/survHE.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘survHE/DESCRIPTION’ ... OK +... +* checking package dependencies ... ERROR +Package required but not available: ‘rms’ + +Packages suggested but not available for checking: + 'survHEinla', 'survHEhmc' + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR -## Installation -### Devel -``` -* installing *source* package ‘survHE’ ... -** package ‘survHE’ 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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘survHE’ -* removing ‘/tmp/workdir/survHE/new/survHE.Rcheck/survHE’ ``` ### CRAN ``` -* installing *source* package ‘survHE’ ... -** package ‘survHE’ 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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘survHE’ -* removing ‘/tmp/workdir/survHE/old/survHE.Rcheck/survHE’ +* using log directory ‘/tmp/workdir/survHE/old/survHE.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘survHE/DESCRIPTION’ ... OK +... +* checking package dependencies ... ERROR +Package required but not available: ‘rms’ + +Packages suggested but not available for checking: + 'survHEinla', 'survHEhmc' + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + ``` @@ -8010,7 +13122,7 @@ Run `revdepcheck::cloud_details(, "survidm")` for more info ** package ‘survidm’ successfully unpacked and MD5 sums checked ** using staged installation ** libs -using C compiler: ‘gcc (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ +using C compiler: ‘gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ gcc -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c survidm_init.c -o survidm_init.o gcc -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c survivalBIV.c -o survivalBIV.o gcc -shared -L/opt/R/4.3.1/lib/R/lib -L/usr/local/lib -o survidm.so survidm_init.o survivalBIV.o -L/opt/R/4.3.1/lib/R/lib -lR @@ -8020,8 +13132,8 @@ installing to /tmp/workdir/survidm/new/survidm.Rcheck/00LOCK-survidm/00new/survi *** moving datasets to lazyload DB ** byte-compile and prepare package for lazy loading Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace + there is no package called ‘quantreg’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart Execution halted ERROR: lazy loading failed for package ‘survidm’ * removing ‘/tmp/workdir/survidm/new/survidm.Rcheck/survidm’ @@ -8035,7 +13147,7 @@ ERROR: lazy loading failed for package ‘survidm’ ** package ‘survidm’ successfully unpacked and MD5 sums checked ** using staged installation ** libs -using C compiler: ‘gcc (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ +using C compiler: ‘gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ gcc -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c survidm_init.c -o survidm_init.o gcc -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c survivalBIV.c -o survivalBIV.o gcc -shared -L/opt/R/4.3.1/lib/R/lib -L/usr/local/lib -o survidm.so survidm_init.o survivalBIV.o -L/opt/R/4.3.1/lib/R/lib -lR @@ -8045,22 +13157,98 @@ installing to /tmp/workdir/survidm/old/survidm.Rcheck/00LOCK-survidm/00new/survi *** moving datasets to lazyload DB ** byte-compile and prepare package for lazy loading Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace + there is no package called ‘quantreg’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart Execution halted ERROR: lazy loading failed for package ‘survidm’ * removing ‘/tmp/workdir/survidm/old/survidm.Rcheck/survidm’ +``` +# SurvMetrics + +
+ +* Version: 0.5.0 +* GitHub: https://github.com/skyee1/SurvMetrics +* Source code: https://github.com/cran/SurvMetrics +* Date/Publication: 2022-09-03 21:40:23 UTC +* Number of recursive dependencies: 187 + +Run `revdepcheck::cloud_details(, "SurvMetrics")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/SurvMetrics/new/SurvMetrics.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘SurvMetrics/DESCRIPTION’ ... OK +... +--- failed re-building ‘SurvMetrics-vignette.Rmd’ + +SUMMARY: processing the following file failed: + ‘SurvMetrics-vignette.Rmd’ + +Error: Vignette re-building failed. +Execution halted + +* DONE +Status: 1 ERROR, 1 WARNING, 1 NOTE + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/SurvMetrics/old/SurvMetrics.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘SurvMetrics/DESCRIPTION’ ... OK +... +--- failed re-building ‘SurvMetrics-vignette.Rmd’ + +SUMMARY: processing the following file failed: + ‘SurvMetrics-vignette.Rmd’ + +Error: Vignette re-building failed. +Execution halted + +* DONE +Status: 1 ERROR, 1 WARNING, 1 NOTE + + + + + ``` # tempted
-* Version: 0.1.0 +* Version: 0.1.1 * GitHub: https://github.com/pixushi/tempted * Source code: https://github.com/cran/tempted -* Date/Publication: 2024-01-11 10:10:02 UTC +* Date/Publication: 2024-05-09 02:40:02 UTC * Number of recursive dependencies: 37 Run `revdepcheck::cloud_details(, "tempted")` for more info @@ -8089,7 +13277,7 @@ Run `revdepcheck::cloud_details(, "tempted")` for more info ** inst ** byte-compile and prepare package for lazy loading Error: package or namespace load failed for ‘np’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required + there is no package called ‘quantreg’ Execution halted ERROR: lazy loading failed for package ‘tempted’ * removing ‘/tmp/workdir/tempted/new/tempted.Rcheck/tempted’ @@ -8108,7 +13296,7 @@ ERROR: lazy loading failed for package ‘tempted’ ** inst ** byte-compile and prepare package for lazy loading Error: package or namespace load failed for ‘np’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required + there is no package called ‘quantreg’ Execution halted ERROR: lazy loading failed for package ‘tempted’ * removing ‘/tmp/workdir/tempted/old/tempted.Rcheck/tempted’ @@ -8123,7 +13311,7 @@ ERROR: lazy loading failed for package ‘tempted’ * GitHub: https://github.com/YuLab-SMU/tidydr * Source code: https://github.com/cran/tidydr * Date/Publication: 2023-03-08 09:20:02 UTC -* Number of recursive dependencies: 71 +* Number of recursive dependencies: 74 Run `revdepcheck::cloud_details(, "tidydr")` for more info @@ -8181,55 +13369,75 @@ ERROR: lazy loading failed for package ‘tidydr’
-* Version: 0.1.2 +* Version: 0.1.3 * GitHub: NA * Source code: https://github.com/cran/tidyEdSurvey -* Date/Publication: 2023-06-19 15:00:02 UTC -* Number of recursive dependencies: 107 +* Date/Publication: 2024-05-14 20:20:03 UTC +* Number of recursive dependencies: 106 Run `revdepcheck::cloud_details(, "tidyEdSurvey")` for more info
-## In both - -* checking whether package ‘tidyEdSurvey’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/tidyEdSurvey/new/tidyEdSurvey.Rcheck/00install.out’ for details. - ``` - -## Installation +## Error before installation ### Devel ``` -* installing *source* package ‘tidyEdSurvey’ ... -** package ‘tidyEdSurvey’ successfully unpacked and MD5 sums checked -** using staged installation -** R -** byte-compile and prepare package for lazy loading -Error: package or namespace load failed for ‘EdSurvey’ in loadNamespace(i, c(lib.loc, .libPaths()), versionCheck = vI[[i]]): - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.1.1 is required -Execution halted -ERROR: lazy loading failed for package ‘tidyEdSurvey’ -* removing ‘/tmp/workdir/tidyEdSurvey/new/tidyEdSurvey.Rcheck/tidyEdSurvey’ +* using log directory ‘/tmp/workdir/tidyEdSurvey/new/tidyEdSurvey.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘tidyEdSurvey/DESCRIPTION’ ... OK +... +* this is package ‘tidyEdSurvey’ version ‘0.1.3’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘EdSurvey’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + ``` ### CRAN ``` -* installing *source* package ‘tidyEdSurvey’ ... -** package ‘tidyEdSurvey’ successfully unpacked and MD5 sums checked -** using staged installation -** R -** byte-compile and prepare package for lazy loading -Error: package or namespace load failed for ‘EdSurvey’ in loadNamespace(i, c(lib.loc, .libPaths()), versionCheck = vI[[i]]): - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.1.1 is required -Execution halted -ERROR: lazy loading failed for package ‘tidyEdSurvey’ -* removing ‘/tmp/workdir/tidyEdSurvey/old/tidyEdSurvey.Rcheck/tidyEdSurvey’ +* using log directory ‘/tmp/workdir/tidyEdSurvey/old/tidyEdSurvey.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘tidyEdSurvey/DESCRIPTION’ ... OK +... +* this is package ‘tidyEdSurvey’ version ‘0.1.3’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘EdSurvey’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + ``` @@ -8247,286 +13455,164 @@ Run `revdepcheck::cloud_details(, "tidyseurat")` for more info
-## In both - -* checking whether package ‘tidyseurat’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/tidyseurat/new/tidyseurat.Rcheck/00install.out’ for details. - ``` - -## Installation +## Error before installation ### Devel ``` -* installing *source* package ‘tidyseurat’ ... -** package ‘tidyseurat’ 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: package or namespace load failed for ‘SeuratObject’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.3 is required -Execution halted -ERROR: lazy loading failed for package ‘tidyseurat’ -* removing ‘/tmp/workdir/tidyseurat/new/tidyseurat.Rcheck/tidyseurat’ - - -``` -### CRAN - -``` -* installing *source* package ‘tidyseurat’ ... -** package ‘tidyseurat’ 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: package or namespace load failed for ‘SeuratObject’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.3 is required -Execution halted -ERROR: lazy loading failed for package ‘tidyseurat’ -* removing ‘/tmp/workdir/tidyseurat/old/tidyseurat.Rcheck/tidyseurat’ - - -``` -# tidyvpc - -
- -* Version: 1.5.1 -* GitHub: https://github.com/certara/tidyvpc -* Source code: https://github.com/cran/tidyvpc -* Date/Publication: 2024-01-18 13:10:02 UTC -* Number of recursive dependencies: 176 - -Run `revdepcheck::cloud_details(, "tidyvpc")` for more info - -
- -## In both +* using log directory ‘/tmp/workdir/tidyseurat/new/tidyseurat.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘tidyseurat/DESCRIPTION’ ... OK +... +* this is package ‘tidyseurat’ version ‘0.8.0’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Packages required but not available: 'SeuratObject', 'Seurat' -* checking whether package ‘tidyvpc’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/tidyvpc/new/tidyvpc.Rcheck/00install.out’ for details. - ``` +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR -## Installation -### Devel -``` -* installing *source* package ‘tidyvpc’ ... -** package ‘tidyvpc’ 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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘tidyvpc’ -* removing ‘/tmp/workdir/tidyvpc/new/tidyvpc.Rcheck/tidyvpc’ ``` ### CRAN ``` -* installing *source* package ‘tidyvpc’ ... -** package ‘tidyvpc’ 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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘tidyvpc’ -* removing ‘/tmp/workdir/tidyvpc/old/tidyvpc.Rcheck/tidyvpc’ - - -``` -# treestats - -
- -* Version: 1.0.5 -* GitHub: https://github.com/thijsjanzen/treestats -* Source code: https://github.com/cran/treestats -* Date/Publication: 2024-01-30 15:50:02 UTC -* Number of recursive dependencies: 232 - -Run `revdepcheck::cloud_details(, "treestats")` for more info - -
- -## In both - -* checking whether package ‘treestats’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/treestats/new/treestats.Rcheck/00install.out’ for details. - ``` - -## Installation - -### Devel +* using log directory ‘/tmp/workdir/tidyseurat/old/tidyseurat.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘tidyseurat/DESCRIPTION’ ... OK +... +* this is package ‘tidyseurat’ version ‘0.8.0’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Packages required but not available: 'SeuratObject', 'Seurat' -``` -* installing *source* package ‘treestats’ ... -** package ‘treestats’ successfully unpacked and MD5 sums checked -** using staged installation -** libs -Error: C++20 standard requested but CXX20 is not defined -* removing ‘/tmp/workdir/treestats/new/treestats.Rcheck/treestats’ +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR -``` -### CRAN -``` -* installing *source* package ‘treestats’ ... -** package ‘treestats’ successfully unpacked and MD5 sums checked -** using staged installation -** libs -Error: C++20 standard requested but CXX20 is not defined -* removing ‘/tmp/workdir/treestats/old/treestats.Rcheck/treestats’ ``` -# TriDimRegression +# treefit
* Version: 1.0.2 -* GitHub: https://github.com/alexander-pastukhov/tridim-regression -* Source code: https://github.com/cran/TriDimRegression -* Date/Publication: 2023-09-13 14:10:03 UTC -* Number of recursive dependencies: 99 +* GitHub: https://github.com/hayamizu-lab/treefit-r +* Source code: https://github.com/cran/treefit +* Date/Publication: 2022-01-18 07:50:02 UTC +* Number of recursive dependencies: 159 -Run `revdepcheck::cloud_details(, "TriDimRegression")` for more info +Run `revdepcheck::cloud_details(, "treefit")` for more info
-## In both - -* checking whether package ‘TriDimRegression’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/TriDimRegression/new/TriDimRegression.Rcheck/00install.out’ for details. - ``` - -## Installation +## Error before installation ### Devel ``` -* installing *source* package ‘TriDimRegression’ ... -** package ‘TriDimRegression’ successfully unpacked and MD5 sums checked -** using staged installation -Error in loadNamespace(x) : there is no package called ‘rstantools’ -Calls: loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart -Execution halted -ERROR: configuration failed for package ‘TriDimRegression’ -* removing ‘/tmp/workdir/TriDimRegression/new/TriDimRegression.Rcheck/TriDimRegression’ - - -``` -### CRAN +* using log directory ‘/tmp/workdir/treefit/new/treefit.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘treefit/DESCRIPTION’ ... OK +... -``` -* installing *source* package ‘TriDimRegression’ ... -** package ‘TriDimRegression’ successfully unpacked and MD5 sums checked -** using staged installation -Error in loadNamespace(x) : there is no package called ‘rstantools’ -Calls: loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart + When sourcing ‘working-with-seurat.R’: +Error: there is no package called ‘Seurat’ Execution halted -ERROR: configuration failed for package ‘TriDimRegression’ -* removing ‘/tmp/workdir/TriDimRegression/old/TriDimRegression.Rcheck/TriDimRegression’ - - -``` -# triptych -
+ ‘treefit.Rmd’ using ‘UTF-8’... OK + ‘working-with-seurat.Rmd’ using ‘UTF-8’... failed +* checking re-building of vignette outputs ... OK +* DONE +Status: 1 WARNING, 1 NOTE -* Version: 0.1.2 -* GitHub: https://github.com/aijordan/triptych -* Source code: https://github.com/cran/triptych -* Date/Publication: 2023-10-03 16:30:02 UTC -* Number of recursive dependencies: 64 -Run `revdepcheck::cloud_details(, "triptych")` for more info -
-## In both -* checking whether package ‘triptych’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/triptych/new/triptych.Rcheck/00install.out’ for details. - ``` +``` +### CRAN -## Installation +``` +* using log directory ‘/tmp/workdir/treefit/old/treefit.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘treefit/DESCRIPTION’ ... OK +... -### Devel + When sourcing ‘working-with-seurat.R’: +Error: there is no package called ‘Seurat’ +Execution halted -``` -* installing *source* package ‘triptych’ ... -** package ‘triptych’ successfully unpacked and MD5 sums checked -** using staged installation -** libs -Error: C++20 standard requested but CXX20 is not defined -* removing ‘/tmp/workdir/triptych/new/triptych.Rcheck/triptych’ + ‘treefit.Rmd’ using ‘UTF-8’... OK + ‘working-with-seurat.Rmd’ using ‘UTF-8’... failed +* checking re-building of vignette outputs ... OK +* DONE +Status: 1 WARNING, 1 NOTE -``` -### CRAN -``` -* installing *source* package ‘triptych’ ... -** package ‘triptych’ successfully unpacked and MD5 sums checked -** using staged installation -** libs -Error: C++20 standard requested but CXX20 is not defined -* removing ‘/tmp/workdir/triptych/old/triptych.Rcheck/triptych’ ``` -# TSrepr +# TriDimRegression
-* Version: 1.1.0 -* GitHub: https://github.com/PetoLau/TSrepr -* Source code: https://github.com/cran/TSrepr -* Date/Publication: 2020-07-13 06:50:15 UTC -* Number of recursive dependencies: 72 +* Version: 1.0.2 +* GitHub: https://github.com/alexander-pastukhov/tridim-regression +* Source code: https://github.com/cran/TriDimRegression +* Date/Publication: 2023-09-13 14:10:03 UTC +* Number of recursive dependencies: 99 -Run `revdepcheck::cloud_details(, "TSrepr")` for more info +Run `revdepcheck::cloud_details(, "TriDimRegression")` for more info
## In both -* checking whether package ‘TSrepr’ can be installed ... ERROR +* checking whether package ‘TriDimRegression’ can be installed ... ERROR ``` Installation failed. - See ‘/tmp/workdir/TSrepr/new/TSrepr.Rcheck/00install.out’ for details. + See ‘/tmp/workdir/TriDimRegression/new/TriDimRegression.Rcheck/00install.out’ for details. ``` ## Installation @@ -8534,54 +13620,28 @@ Run `revdepcheck::cloud_details(, "TSrepr")` for more info ### Devel ``` -* installing *source* package ‘TSrepr’ ... -** package ‘TSrepr’ successfully unpacked and MD5 sums checked +* installing *source* package ‘TriDimRegression’ ... +** package ‘TriDimRegression’ successfully unpacked and MD5 sums checked ** using staged installation -** libs -using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c FeatureClippingTrending.cpp -o FeatureClippingTrending.o -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c helpers.cpp -o helpers.o -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c measures.cpp -o measures.o -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c normalizations.cpp -o normalizations.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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Error in loadNamespace(x) : there is no package called ‘rstantools’ +Calls: loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart Execution halted -ERROR: lazy loading failed for package ‘TSrepr’ -* removing ‘/tmp/workdir/TSrepr/new/TSrepr.Rcheck/TSrepr’ +ERROR: configuration failed for package ‘TriDimRegression’ +* removing ‘/tmp/workdir/TriDimRegression/new/TriDimRegression.Rcheck/TriDimRegression’ ``` ### CRAN ``` -* installing *source* package ‘TSrepr’ ... -** package ‘TSrepr’ successfully unpacked and MD5 sums checked +* installing *source* package ‘TriDimRegression’ ... +** package ‘TriDimRegression’ successfully unpacked and MD5 sums checked ** using staged installation -** libs -using C++ compiler: ‘g++ (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c FeatureClippingTrending.cpp -o FeatureClippingTrending.o -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c helpers.cpp -o helpers.o -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c measures.cpp -o measures.o -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c normalizations.cpp -o normalizations.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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Error in loadNamespace(x) : there is no package called ‘rstantools’ +Calls: loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart Execution halted -ERROR: lazy loading failed for package ‘TSrepr’ -* removing ‘/tmp/workdir/TSrepr/old/TSrepr.Rcheck/TSrepr’ +ERROR: configuration failed for package ‘TriDimRegression’ +* removing ‘/tmp/workdir/TriDimRegression/old/TriDimRegression.Rcheck/TriDimRegression’ ``` @@ -8616,7 +13676,7 @@ Run `revdepcheck::cloud_details(, "twang")` for more info ** package ‘twang’ successfully unpacked and MD5 sums checked ** using staged installation ** libs -using C compiler: ‘gcc (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ +using C compiler: ‘gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ gcc -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I/usr/local/include -fpic -g -O2 -c init.c -o init.o gcc -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I/usr/local/include -fpic -g -O2 -c ks.c -o ks.o gcc -shared -L/opt/R/4.3.1/lib/R/lib -L/usr/local/lib -o twang.so init.o ks.o -llapack -lblas -lgfortran -lm -lquadmath -L/opt/R/4.3.1/lib/R/lib -lR @@ -8641,7 +13701,7 @@ ERROR: lazy loading failed for package ‘twang’ ** package ‘twang’ successfully unpacked and MD5 sums checked ** using staged installation ** libs -using C compiler: ‘gcc (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ +using C compiler: ‘gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ gcc -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I/usr/local/include -fpic -g -O2 -c init.c -o init.o gcc -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I/usr/local/include -fpic -g -O2 -c ks.c -o ks.o gcc -shared -L/opt/R/4.3.1/lib/R/lib -L/usr/local/lib -o twang.so init.o ks.o -llapack -lblas -lgfortran -lm -lquadmath -L/opt/R/4.3.1/lib/R/lib -lR @@ -8658,84 +13718,6 @@ ERROR: lazy loading failed for package ‘twang’ * removing ‘/tmp/workdir/twang/old/twang.Rcheck/twang’ -``` -# ubms - -
- -* Version: 1.2.6 -* GitHub: https://github.com/kenkellner/ubms -* Source code: https://github.com/cran/ubms -* Date/Publication: 2023-09-11 18:50:02 UTC -* Number of recursive dependencies: 145 - -Run `revdepcheck::cloud_details(, "ubms")` for more info - -
- -## In both - -* checking whether package ‘ubms’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/ubms/new/ubms.Rcheck/00install.out’ for details. - ``` - -## Installation - -### Devel - -``` -* installing *source* package ‘ubms’ ... -** package ‘ubms’ successfully unpacked and MD5 sums checked -** using staged installation -Registered S3 methods overwritten by 'RcppEigen': - method from - predict.fastLm RcppArmadillo - print.fastLm RcppArmadillo - summary.fastLm RcppArmadillo - print.summary.fastLm RcppArmadillo -Warning message: -... -/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src/stan/mcmc/hmc/hamiltonians/dense_e_metric.hpp:22:56: required from ‘double stan::mcmc::dense_e_metric::T(stan::mcmc::dense_e_point&) [with Model = model_colext_namespace::model_colext; BaseRNG = boost::random::additive_combine_engine, boost::random::linear_congruential_engine >]’ -/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src/stan/mcmc/hmc/hamiltonians/dense_e_metric.hpp:21:10: required from here -/opt/R/4.3.1/lib/R/site-library/RcppEigen/include/Eigen/src/Core/DenseCoeffsBase.h:654:34: warning: ignoring attributes on template argument ‘Eigen::internal::packet_traits::type’ {aka ‘__vector(2) double’} [-Wignored-attributes] - 654 | return internal::first_aligned::alignment),Derived>(m); - | ^~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -g++: fatal error: Killed signal terminated program cc1plus -compilation terminated. -make: *** [/opt/R/4.3.1/lib/R/etc/Makeconf:198: stanExports_colext.o] Error 1 -ERROR: compilation failed for package ‘ubms’ -* removing ‘/tmp/workdir/ubms/new/ubms.Rcheck/ubms’ - - -``` -### CRAN - -``` -* installing *source* package ‘ubms’ ... -** package ‘ubms’ successfully unpacked and MD5 sums checked -** using staged installation -Registered S3 methods overwritten by 'RcppEigen': - method from - predict.fastLm RcppArmadillo - print.fastLm RcppArmadillo - summary.fastLm RcppArmadillo - print.summary.fastLm RcppArmadillo -Warning message: -... -/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src/stan/mcmc/hmc/hamiltonians/dense_e_metric.hpp:22:56: required from ‘double stan::mcmc::dense_e_metric::T(stan::mcmc::dense_e_point&) [with Model = model_colext_namespace::model_colext; BaseRNG = boost::random::additive_combine_engine, boost::random::linear_congruential_engine >]’ -/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src/stan/mcmc/hmc/hamiltonians/dense_e_metric.hpp:21:10: required from here -/opt/R/4.3.1/lib/R/site-library/RcppEigen/include/Eigen/src/Core/DenseCoeffsBase.h:654:34: warning: ignoring attributes on template argument ‘Eigen::internal::packet_traits::type’ {aka ‘__vector(2) double’} [-Wignored-attributes] - 654 | return internal::first_aligned::alignment),Derived>(m); - | ^~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -g++: fatal error: Killed signal terminated program cc1plus -compilation terminated. -make: *** [/opt/R/4.3.1/lib/R/etc/Makeconf:198: stanExports_colext.o] Error 1 -ERROR: compilation failed for package ‘ubms’ -* removing ‘/tmp/workdir/ubms/old/ubms.Rcheck/ubms’ - - ``` # valse @@ -8768,7 +13750,7 @@ Run `revdepcheck::cloud_details(, "valse")` for more info ** package ‘valse’ successfully unpacked and MD5 sums checked ** using staged installation ** libs -using C compiler: ‘gcc (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ +using C compiler: ‘gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ gcc -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I/usr/local/include -fpic -g -O2 -c EMGLLF.c -o EMGLLF.o gcc -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I/usr/local/include -fpic -g -O2 -c EMGrank.c -o EMGrank.o gcc -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I/usr/local/include -fpic -g -O2 -c a.EMGLLF.c -o a.EMGLLF.o @@ -8780,7 +13762,7 @@ gcc -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I/usr/local/include -fpic -g ** testing if installed package can be loaded from temporary location Error: package or namespace load failed for ‘valse’ in dyn.load(file, DLLpath = DLLpath, ...): unable to load shared object '/tmp/workdir/valse/new/valse.Rcheck/00LOCK-valse/00new/valse/libs/valse.so': - /tmp/workdir/valse/new/valse.Rcheck/00LOCK-valse/00new/valse/libs/valse.so: undefined symbol: gsl_vector_free + /tmp/workdir/valse/new/valse.Rcheck/00LOCK-valse/00new/valse/libs/valse.so: undefined symbol: gsl_permutation_free Error: loading failed Execution halted ERROR: loading failed @@ -8795,7 +13777,7 @@ ERROR: loading failed ** package ‘valse’ successfully unpacked and MD5 sums checked ** using staged installation ** libs -using C compiler: ‘gcc (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ +using C compiler: ‘gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ gcc -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I/usr/local/include -fpic -g -O2 -c EMGLLF.c -o EMGLLF.o gcc -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I/usr/local/include -fpic -g -O2 -c EMGrank.c -o EMGrank.o gcc -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I/usr/local/include -fpic -g -O2 -c a.EMGLLF.c -o a.EMGLLF.o @@ -8807,85 +13789,13 @@ gcc -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I/usr/local/include -fpic -g ** testing if installed package can be loaded from temporary location Error: package or namespace load failed for ‘valse’ in dyn.load(file, DLLpath = DLLpath, ...): unable to load shared object '/tmp/workdir/valse/old/valse.Rcheck/00LOCK-valse/00new/valse/libs/valse.so': - /tmp/workdir/valse/old/valse.Rcheck/00LOCK-valse/00new/valse/libs/valse.so: undefined symbol: gsl_vector_free + /tmp/workdir/valse/old/valse.Rcheck/00LOCK-valse/00new/valse/libs/valse.so: undefined symbol: gsl_permutation_free Error: loading failed Execution halted ERROR: loading failed * removing ‘/tmp/workdir/valse/old/valse.Rcheck/valse’ -``` -# vdg - -
- -* Version: 1.2.3 -* GitHub: NA -* Source code: https://github.com/cran/vdg -* Date/Publication: 2024-04-23 13:00:02 UTC -* Number of recursive dependencies: 45 - -Run `revdepcheck::cloud_details(, "vdg")` for more info - -
- -## In both - -* checking whether package ‘vdg’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/vdg/new/vdg.Rcheck/00install.out’ for details. - ``` - -## Installation - -### Devel - -``` -* installing *source* package ‘vdg’ ... -** package ‘vdg’ successfully unpacked and MD5 sums checked -** using staged installation -** libs -using Fortran compiler: ‘GNU Fortran (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ -gfortran -fpic -g -O2 -c FDS.f -o FDS.o -gcc -shared -L/opt/R/4.3.1/lib/R/lib -L/usr/local/lib -o vdg.so FDS.o -lgfortran -lm -lquadmath -L/opt/R/4.3.1/lib/R/lib -lR -installing to /tmp/workdir/vdg/new/vdg.Rcheck/00LOCK-vdg/00new/vdg/libs -** R -** data -*** moving datasets to lazyload DB -** inst -** byte-compile and prepare package for lazy loading -Error: package or namespace load failed for ‘quantreg’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Execution halted -ERROR: lazy loading failed for package ‘vdg’ -* removing ‘/tmp/workdir/vdg/new/vdg.Rcheck/vdg’ - - -``` -### CRAN - -``` -* installing *source* package ‘vdg’ ... -** package ‘vdg’ successfully unpacked and MD5 sums checked -** using staged installation -** libs -using Fortran compiler: ‘GNU Fortran (Ubuntu 9.4.0-1ubuntu1~20.04.2) 9.4.0’ -gfortran -fpic -g -O2 -c FDS.f -o FDS.o -gcc -shared -L/opt/R/4.3.1/lib/R/lib -L/usr/local/lib -o vdg.so FDS.o -lgfortran -lm -lquadmath -L/opt/R/4.3.1/lib/R/lib -lR -installing to /tmp/workdir/vdg/old/vdg.Rcheck/00LOCK-vdg/00new/vdg/libs -** R -** data -*** moving datasets to lazyload DB -** inst -** byte-compile and prepare package for lazy loading -Error: package or namespace load failed for ‘quantreg’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Execution halted -ERROR: lazy loading failed for package ‘vdg’ -* removing ‘/tmp/workdir/vdg/old/vdg.Rcheck/vdg’ - - ``` # visa @@ -8901,117 +13811,141 @@ Run `revdepcheck::cloud_details(, "visa")` for more info -## In both - -* checking whether package ‘visa’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/visa/new/visa.Rcheck/00install.out’ for details. - ``` - -## Installation +## Error before installation ### Devel ``` -* installing *source* package ‘visa’ ... -** package ‘visa’ 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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘visa’ -* removing ‘/tmp/workdir/visa/new/visa.Rcheck/visa’ +* using log directory ‘/tmp/workdir/visa/new/visa.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘visa/DESCRIPTION’ ... OK +... +* this is package ‘visa’ version ‘0.1.0’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘ggpmisc’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + ``` ### CRAN ``` -* installing *source* package ‘visa’ ... -** package ‘visa’ 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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘visa’ -* removing ‘/tmp/workdir/visa/old/visa.Rcheck/visa’ +* using log directory ‘/tmp/workdir/visa/old/visa.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘visa/DESCRIPTION’ ... OK +... +* this is package ‘visa’ version ‘0.1.0’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘ggpmisc’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + ``` -# WRTDStidal +# WpProj
-* Version: 1.1.4 -* GitHub: https://github.com/fawda123/WRTDStidal -* Source code: https://github.com/cran/WRTDStidal -* Date/Publication: 2023-10-20 09:00:11 UTC -* Number of recursive dependencies: 140 +* Version: 0.2.1 +* GitHub: https://github.com/ericdunipace/WpProj +* Source code: https://github.com/cran/WpProj +* Date/Publication: 2024-02-02 10:10:05 UTC +* Number of recursive dependencies: 100 -Run `revdepcheck::cloud_details(, "WRTDStidal")` for more info +Run `revdepcheck::cloud_details(, "WpProj")` for more info
-## In both - -* checking whether package ‘WRTDStidal’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/WRTDStidal/new/WRTDStidal.Rcheck/00install.out’ for details. - ``` - -## Installation +## Error before installation ### Devel ``` -* installing *source* package ‘WRTDStidal’ ... -** package ‘WRTDStidal’ 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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘WRTDStidal’ -* removing ‘/tmp/workdir/WRTDStidal/new/WRTDStidal.Rcheck/WRTDStidal’ +* using log directory ‘/tmp/workdir/WpProj/new/WpProj.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘WpProj/DESCRIPTION’ ... OK +... +* this is package ‘WpProj’ version ‘0.2.1’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Packages required but not available: 'rqPen', 'quantreg' + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + ``` ### CRAN ``` -* installing *source* package ‘WRTDStidal’ ... -** package ‘WRTDStidal’ 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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘WRTDStidal’ -* removing ‘/tmp/workdir/WRTDStidal/old/WRTDStidal.Rcheck/WRTDStidal’ +* using log directory ‘/tmp/workdir/WpProj/old/WpProj.Rcheck’ +* using R version 4.3.1 (2023-06-16) +* using platform: x86_64-pc-linux-gnu (64-bit) +* R was compiled by + gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 + GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 +* running under: Ubuntu 22.04.4 LTS +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘WpProj/DESCRIPTION’ ... OK +... +* this is package ‘WpProj’ version ‘0.2.1’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Packages required but not available: 'rqPen', 'quantreg' + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + ``` diff --git a/revdep/problems.md b/revdep/problems.md index 100afd3e3a..ac4d68ce5f 100644 --- a/revdep/problems.md +++ b/revdep/problems.md @@ -1,3 +1,96 @@ +# accSDA + +
+ +* Version: 1.1.3 +* GitHub: https://github.com/gumeo/accSDA +* Source code: https://github.com/cran/accSDA +* Date/Publication: 2024-03-06 18:50:02 UTC +* Number of recursive dependencies: 29 + +Run `revdepcheck::cloud_details(, "accSDA")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘accSDA-Ex.R’ failed + The error most likely occurred in: + + > ### Name: ASDABarPlot + > ### Title: barplot for ASDA objects + > ### Aliases: ASDABarPlot + > + > ### ** Examples + > + > # Generate and ASDA object with your data, e.g. + ... + 3. ├─base::do.call(arrangeGrob, c(list(grobs = groups[[g]]), params)) + 4. └─gridExtra (local) ``(grobs = ``, layout_matrix = ``) + 5. └─base::lapply(grobs[toconv], ggplot2::ggplotGrob) + 6. └─ggplot2 (local) FUN(X[[i]], ...) + 7. ├─ggplot2::ggplot_gtable(ggplot_build(x)) + 8. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) + 9. └─ggplot2::calc_element("plot.margin", theme) + 10. └─cli::cli_abort(...) + 11. └─rlang::abort(...) + Execution halted + ``` + +# activAnalyzer + +
+ +* Version: 2.1.1 +* GitHub: https://github.com/pydemull/activAnalyzer +* Source code: https://github.com/cran/activAnalyzer +* Date/Publication: 2024-05-05 22:40:03 UTC +* Number of recursive dependencies: 152 + +Run `revdepcheck::cloud_details(, "activAnalyzer")` for more info + +
+ +## Newly broken + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘activAnalyzer.Rmd’ + ... + > p3 <- accum_metrics_sed$p_UBD + + > p4 <- accum_metrics_sed$p_gini + + > (p1 | p2)/(p3 | p4) + plot_layout(guides = "collect") & + + theme(legend.position = "bottom") + + When sourcing ‘activAnalyzer.R’: + Error: object is not a unit + Execution halted + + ‘activAnalyzer.Rmd’ using ‘UTF-8’... failed + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘activAnalyzer.Rmd’ using rmarkdown + ``` + +## In both + +* checking installed package size ... NOTE + ``` + installed size is 5.8Mb + sub-directories of 1Mb or more: + R 1.5Mb + doc 1.0Mb + extdata 2.0Mb + ``` + # actxps
@@ -47,12 +140,12 @@ Run `revdepcheck::cloud_details(, "actxps")` for more info Warning: thematic was unable to resolve `fg='auto'`. Try providing an actual color (or `NA`) to the `fg` argument of `thematic_on()`. By the way, 'auto' is only officially supported in `shiny::renderPlot()`, some rmarkdown scenarios (specifically, `html_document()` with `theme!=NULL`), in RStudio, or if `auto_config_set()` is used. Warning: thematic was unable to resolve `accent='auto'`. Try providing an actual color (or `NA`) to the `accent` argument of `thematic_on()`. By the way, 'auto' is only officially supported in `shiny::renderPlot()`, some rmarkdown scenarios (specifically, `html_document()` with `theme!=NULL`), in RStudio, or if `auto_config_set()` is used. - Quitting from lines at lines 131-132 [plot] (actxps.Rmd) + Quitting from lines 131-132 [plot] (actxps.Rmd) Error: processing vignette 'actxps.Rmd' failed with diagnostics: Internal error: adjust_color() expects an input of length 1 --- failed re-building ‘actxps.Rmd’ ... - Quitting from lines at lines 205-211 [trx-plot] (transactions.Rmd) + Quitting from lines 205-211 [trx-plot] (transactions.Rmd) Error: processing vignette 'transactions.Rmd' failed with diagnostics: Internal error: adjust_color() expects an input of length 1 --- failed re-building ‘transactions.Rmd’ @@ -64,6 +157,79 @@ Run `revdepcheck::cloud_details(, "actxps")` for more info Execution halted ``` +# add2ggplot + +
+ +* Version: 0.3.0 +* GitHub: https://github.com/JiaxiangBU/add2ggplot +* Source code: https://github.com/cran/add2ggplot +* Date/Publication: 2020-02-07 11:50:02 UTC +* Number of recursive dependencies: 53 + +Run `revdepcheck::cloud_details(, "add2ggplot")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘add2ggplot-Ex.R’ failed + The error most likely occurred in: + + > ### Name: theme_ilo + > ### Title: One ggplot theme + > ### Aliases: theme_ilo + > + > ### ** Examples + > + > datasets::mtcars %>% + ... + Backtrace: + ▆ + 1. ├─base (local) ``(x) + 2. └─ggplot2:::print.ggplot(x) + 3. ├─ggplot2::ggplot_gtable(data) + 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) + 5. └─ggplot2::calc_element("plot.margin", theme) + 6. └─cli::cli_abort(...) + 7. └─rlang::abort(...) + Execution halted + ``` + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘intro.Rmd’ + ... + + > mtcars %>% ggplot2::ggplot(ggplot2::aes(mpg, disp)) + + + ggplot2::geom_point() + theme_grey_and_red() + + > mtcars %>% ggplot2::ggplot(ggplot2::aes(mpg, disp)) + + + ggplot2::geom_point() + theme_ilo() + + When sourcing ‘intro.R’: + Error: Theme element `plot.margin` must have class . + Execution halted + + ‘intro.Rmd’ using ‘UTF-8’... failed + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘intro.Rmd’ using rmarkdown + ``` + +## In both + +* checking LazyData ... NOTE + ``` + 'LazyData' is specified without a 'data' directory + ``` + # AeRobiology
@@ -101,7 +267,7 @@ Run `revdepcheck::cloud_details(, "AeRobiology")` for more info + y.start = 2011, y.end = .... [TRUNCATED] When sourcing ‘my-vignette.R’: - Error: argument "theme" is missing, with no default + Error: subscript out of bounds Execution halted ‘my-vignette.Rmd’ using ‘UTF-8’... failed @@ -115,7 +281,7 @@ Run `revdepcheck::cloud_details(, "AeRobiology")` for more info * GitHub: https://github.com/singmann/afex * Source code: https://github.com/cran/afex * Date/Publication: 2024-02-25 14:40:02 UTC -* Number of recursive dependencies: 227 +* Number of recursive dependencies: 226 Run `revdepcheck::cloud_details(, "afex")` for more info @@ -154,17 +320,17 @@ Run `revdepcheck::cloud_details(, "afex")` for more info --- re-building ‘afex_analysing_accuracy_data.Rmd’ using rmarkdown ``` -# agricolaeplotr +# AgroR
-* Version: 0.5.0 -* GitHub: https://github.com/jensharbers/agricolaeplotr -* Source code: https://github.com/cran/agricolaeplotr -* Date/Publication: 2024-01-17 16:42:04 UTC -* Number of recursive dependencies: 144 +* Version: 1.3.6 +* GitHub: NA +* Source code: https://github.com/cran/AgroR +* Date/Publication: 2024-04-24 02:20:18 UTC +* Number of recursive dependencies: 118 -Run `revdepcheck::cloud_details(, "agricolaeplotr")` for more info +Run `revdepcheck::cloud_details(, "AgroR")` for more info
@@ -172,89 +338,67 @@ Run `revdepcheck::cloud_details(, "agricolaeplotr")` for more info * checking examples ... ERROR ``` - Running examples in ‘agricolaeplotr-Ex.R’ failed + Running examples in ‘AgroR-Ex.R’ failed The error most likely occurred in: - > ### Name: sample_locations - > ### Title: Sample Locations - > ### Aliases: sample_locations + > ### Name: DBC + > ### Title: Analysis: Randomized block design + > ### Aliases: DBC + > ### Keywords: DBC Experimental > > ### ** Examples > - > library(agricolaeplotr) ... - 16. └─ggplot2 (local) FUN(X[[i]], ...) - 17. └─base::lapply(...) - 18. └─ggplot2 (local) FUN(X[[i]], ...) - 19. └─g$draw_key(data, g$params, key_size) - 20. └─ggplot2 (local) draw_key(...) - 21. └─ggplot2::draw_key_polygon(data, params, size) - 22. └─rlang:::Summary.quosure(from_theme(thin), 1.524, na.rm = FALSE) - 23. └─rlang:::abort_quosure_op("Summary", .Generic) - 24. └─rlang::abort(...) + 12. │ └─base::withCallingHandlers(...) + 13. └─ggplot2 (local) f(l = layers[[i]], d = data[[i]]) + 14. └─l$compute_geom_2(d, theme = plot$theme) + 15. └─ggplot2 (local) compute_geom_2(..., self = self) + 16. └─self$geom$use_defaults(...) + 17. └─ggplot2 (local) use_defaults(..., self = self) + 18. └─ggplot2:::check_aesthetics(new_params, nrow(data)) + 19. └─cli::cli_abort(...) + 20. └─rlang::abort(...) Execution halted ``` -# ammistability +# allMT
-* Version: 0.1.4 -* GitHub: https://github.com/ajaygpb/ammistability -* Source code: https://github.com/cran/ammistability -* Date/Publication: 2023-05-24 07:40:08 UTC -* Number of recursive dependencies: 70 +* Version: 0.1.0 +* GitHub: https://github.com/tmungle/allMT +* Source code: https://github.com/cran/allMT +* Date/Publication: 2023-04-20 17:32:33 UTC +* Number of recursive dependencies: 144 -Run `revdepcheck::cloud_details(, "ammistability")` for more info +Run `revdepcheck::cloud_details(, "allMT")` for more info
## Newly broken -* checking re-building of vignette outputs ... ERROR - ``` - Error(s) in re-building vignettes: - ... - --- re-building ‘Introduction.Rmd’ using rmarkdown_notangle - ! Undefined control sequence. - l.108 \NewDocumentCommand - \citeproctext{}{} - - Error: processing vignette 'Introduction.Rmd' failed with diagnostics: - LaTeX failed to compile /tmp/workdir/ammistability/new/ammistability.Rcheck/vign_test/ammistability/vignettes/Introduction.tex. See https://yihui.org/tinytex/r/#debugging for debugging tips. See Introduction.log for more info. - --- failed re-building ‘Introduction.Rmd’ - - SUMMARY: processing the following file failed: - ‘Introduction.Rmd’ - - Error: Vignette re-building failed. - Execution halted - ``` - -## Newly fixed - -* checking re-building of vignette outputs ... WARNING +* checking examples ... ERROR ``` - Error(s) in re-building vignettes: - --- re-building ‘Introduction.Rmd’ using rmarkdown_notangle - Trying to upgrade TinyTeX automatically now... - If reinstallation fails, try install_tinytex() again. Then install the following packages: - - tinytex::tlmgr_install(c("amscls", "amsfonts", "amsmath", "atbegshi", "atveryend", "auxhook", "babel", "bibtex", "bigintcalc", "bitset", "booktabs", "cm", "ctablestack", "dehyph", "dvipdfmx", "dvips", "ec", "epstopdf-pkg", "etex", "etexcmds", "etoolbox", "euenc", "everyshi", "fancyvrb", "filehook", "firstaid", "float", "fontspec", "framed", "geometry", "gettitlestring", "glyphlist", "graphics", "graphics-cfg", "graphics-def", "helvetic", "hycolor", "hyperref", "hyph-utf8", "hyphen-base", "iftex", "inconsolata", "infwarerr", "intcalc", "knuth-lib", "kpathsea", "kvdefinekeys", "kvoptions", "kvsetkeys", "l3backend", "l3kernel", "l3packages", "latex", "latex-amsmath-dev", "latex-bin", "latex-fonts", "latex-tools-dev", "latexconfig", "latexmk", "letltxmacro", "lm", "lm-math", "ltxcmds", "lua-alt-getopt", "lua-uni-algos", "luahbtex", "lualatex-math", "lualibs", "luaotfload", "luatex", "luatexbase", "mdwtools", "metafont", "mfware", "modes", "natbib", "pdfescape", "pdftex", "pdftexcmds", "plain", "psnfss", "refcount", "rerunfilecheck", "scheme-infraonly", "selnolig", "stringenc", "symbol", "tex", "tex-ini-files", "texlive-scripts", "texlive.infra", "times", "tipa", "tools", "unicode-data", "unicode-math", "uniquecounter", "url", "xcolor", "xetex", "xetexconfig", "xkeyval", "xunicode", "zapfding")) - - The directory /opt/TinyTeX/texmf-local is not empty. It will be backed up to /tmp/RtmpCfJ2Ma/filed896b38a178 and restored later. + Running examples in ‘allMT-Ex.R’ failed + The error most likely occurred in: - tlmgr: no auxiliary texmf trees defined, so nothing removed + > ### Name: compare_cohorts + > ### Title: Plot summarized maintenance therapy (MT) data to compare two or + > ### more cohorts + > ### Aliases: compare_cohorts + > + > ### ** Examples + > ... - - Error: processing vignette 'Introduction.Rmd' failed with diagnostics: - LaTeX failed to compile /tmp/workdir/ammistability/old/ammistability.Rcheck/vign_test/ammistability/vignettes/Introduction.tex. See https://yihui.org/tinytex/r/#debugging for debugging tips. See Introduction.log for more info. - --- failed re-building ‘Introduction.Rmd’ - - SUMMARY: processing the following file failed: - ‘Introduction.Rmd’ - - Error: Vignette re-building failed. + Backtrace: + ▆ + 1. ├─base (local) ``(x) + 2. └─ggplot2:::print.ggplot(x) + 3. ├─ggplot2::ggplot_gtable(data) + 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) + 5. └─ggplot2::calc_element("plot.margin", theme) + 6. └─cli::cli_abort(...) + 7. └─rlang::abort(...) Execution halted ``` @@ -287,9 +431,8 @@ Run `revdepcheck::cloud_details(, "AnalysisLin")` for more info > > data(iris) > bar_plot(iris) - Error in compute_geom_2(..., self = self) : - argument "theme" is missing, with no default - Calls: bar_plot ... use_defaults -> eval_from_theme -> %||% -> calc_element + Error in pm[[2]] : subscript out of bounds + Calls: bar_plot ... plotly_build -> ggplotly -> ggplotly.ggplot -> gg2list Execution halted ``` @@ -322,76 +465,70 @@ Run `revdepcheck::cloud_details(, "animbook")` for more info > > animbook <- anim_prep(data = osiris, id = ID, values = sales, time = year, group = japan) ... + transform it into an animated object > > animate <- anim_animate(plot) You can now pass it to gganimate::animate(). The recommended setting is nframes = 89 > > plotly::ggplotly(animate) - Error in compute_geom_2(..., self = self) : - argument "theme" is missing, with no default - Calls: ... use_defaults -> eval_from_theme -> %||% -> calc_element + Error in pm[[2]] : subscript out of bounds + Calls: -> ggplotly.ggplot -> gg2list Execution halted ``` -# aopdata +# aplot
-* Version: 1.0.3 -* GitHub: https://github.com/ipeaGIT/aopdata -* Source code: https://github.com/cran/aopdata -* Date/Publication: 2023-08-31 07:20:02 UTC -* Number of recursive dependencies: 88 +* Version: 0.2.2 +* GitHub: https://github.com/YuLab-SMU/aplot +* Source code: https://github.com/cran/aplot +* Date/Publication: 2023-10-06 04:30:02 UTC +* Number of recursive dependencies: 53 -Run `revdepcheck::cloud_details(, "aopdata")` for more info +Run `revdepcheck::cloud_details(, "aplot")` for more info
## Newly broken -* checking running R code from vignettes ... ERROR +* checking examples ... ERROR ``` - Errors in running code in vignettes: - when running code in ‘landuse_maps.Rmd’ - ... - + direction = 1 .... [TRUNCATED] - - When sourcing ‘landuse_maps.R’: - Error: Summary operations are not defined for quosures. Do you need to unquote - the quosure? + Running examples in ‘aplot-Ex.R’ failed + The error most likely occurred in: - # Bad: min(myquosure) + > ### Name: insert_left + > ### Title: plot-insertion + > ### Aliases: insert_left insert_right insert_top insert_bottom + > + > ### ** Examples + > + > library(ggplot2) ... - # Good: min(!!myquosure) + > ap + > ap[2, 1] <- ap[2, 1] + theme_bw() + > ap[2, 1] <- ap[2, 1] + + + aes(color = as.factor(am)) + + + scale_color_manual(values = c('steelblue', 'darkgreen')) + > ap[1, 1] <- ap[1, 1] + theme(axis.line.x.bottom=element_line()) + > ap + Error in identicalUnits(x) : object is not a unit + Calls: ... assemble_guides -> guides_build -> unit.c -> identicalUnits Execution halted - - ‘access_inequality.Rmd’ using ‘UTF-8’... OK - ‘access_maps.Rmd’ using ‘UTF-8’... OK - ‘data_dic_en.Rmd’ using ‘UTF-8’... OK - ‘data_dic_pt.Rmd’ using ‘UTF-8’... OK - ‘intro_to_aopdata.Rmd’ using ‘UTF-8’... OK - ‘landuse_maps.Rmd’ using ‘UTF-8’... failed - ‘population_maps.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘access_inequality.Rmd’ using rmarkdown ``` -# ARPALData +# ASRgenomics
-* Version: 1.5.2 +* Version: 1.1.4 * GitHub: NA -* Source code: https://github.com/cran/ARPALData -* Date/Publication: 2024-03-17 00:00:05 UTC -* Number of recursive dependencies: 141 +* Source code: https://github.com/cran/ASRgenomics +* Date/Publication: 2024-01-29 21:20:02 UTC +* Number of recursive dependencies: 132 -Run `revdepcheck::cloud_details(, "ARPALData")` for more info +Run `revdepcheck::cloud_details(, "ASRgenomics")` for more info
@@ -399,73 +536,74 @@ Run `revdepcheck::cloud_details(, "ARPALData")` for more info * checking examples ... ERROR ``` - Running examples in ‘ARPALData-Ex.R’ failed + Running examples in ‘ASRgenomics-Ex.R’ failed The error most likely occurred in: - > ### Name: get_ARPA_Lombardia_zoning - > ### Title: Download ARPA Lombardia zoning geometries - > ### Aliases: get_ARPA_Lombardia_zoning + > ### Name: kinship.heatmap + > ### Title: Enhanced heatmap plot for a kinship matrix K + > ### Aliases: kinship.heatmap > > ### ** Examples > - > zones <- get_ARPA_Lombardia_zoning(plot_map = TRUE) + > # Get G matrix. ... - 16. └─ggplot2 (local) FUN(X[[i]], ...) - 17. └─base::lapply(...) - 18. └─ggplot2 (local) FUN(X[[i]], ...) - 19. └─g$draw_key(data, g$params, key_size) - 20. └─ggplot2 (local) draw_key(...) - 21. └─ggplot2::draw_key_polygon(data, params, size) - 22. └─rlang:::Summary.quosure(from_theme(thin), 1.524, na.rm = FALSE) - 23. └─rlang:::abort_quosure_op("Summary", .Generic) - 24. └─rlang::abort(...) + 7. ├─gtable::gtable_filter(...) + 8. │ └─base::grepl(pattern, .subset2(x$layout, "name"), fixed = fixed) + 9. │ └─base::is.factor(x) + 10. └─ggplot2::ggplotGrob(gg.left) + 11. ├─ggplot2::ggplot_gtable(ggplot_build(x)) + 12. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) + 13. └─ggplot2::calc_element("plot.margin", theme) + 14. └─cli::cli_abort(...) + 15. └─rlang::abort(...) Execution halted ``` -# asmbPLS - -
- -* Version: 1.0.0 -* GitHub: NA -* Source code: https://github.com/cran/asmbPLS -* Date/Publication: 2023-04-17 09:50:05 UTC -* Number of recursive dependencies: 100 - -Run `revdepcheck::cloud_details(, "asmbPLS")` for more info - -
- -## Newly broken - -* checking whether package ‘asmbPLS’ can be installed ... WARNING +* checking tests ... ERROR ``` - Found the following significant warnings: - Warning: replacing previous import ‘ggplot2::ggpar’ by ‘ggpubr::ggpar’ when loading ‘asmbPLS’ - See ‘/tmp/workdir/asmbPLS/new/asmbPLS.Rcheck/00install.out’ for details. + Running ‘spelling.R’ + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > # This file is part of the standard setup for testthat. + > # It is recommended that you do not modify it. + > # + > # Where should you do additional test configuration? + > # Learn more about the roles of various files in: + > # * https://r-pkgs.org/tests.html + ... + + ══ Failed tests ════════════════════════════════════════════════════════════════ + ── Failure ('test-kinshipheat.R:11:3'): kinship heatmap works ────────────────── + Expected `... <- NULL` to run without any errors. + i Actually got a with text: + Theme element `plot.margin` must have class . + + [ FAIL 1 | WARN 0 | SKIP 0 | PASS 263 ] + Error: Test failures + Execution halted ``` ## In both * checking installed package size ... NOTE ``` - installed size is 37.6Mb + installed size is 8.9Mb sub-directories of 1Mb or more: - data 2.1Mb - libs 34.4Mb + data 8.5Mb ``` -# autoplotly +# auditor
-* Version: 0.1.4 -* GitHub: https://github.com/terrytangyuan/autoplotly -* Source code: https://github.com/cran/autoplotly -* Date/Publication: 2021-04-18 06:50:11 UTC -* Number of recursive dependencies: 88 +* Version: 1.3.5 +* GitHub: https://github.com/ModelOriented/auditor +* Source code: https://github.com/cran/auditor +* Date/Publication: 2023-10-30 15:40:07 UTC +* Number of recursive dependencies: 87 -Run `revdepcheck::cloud_details(, "autoplotly")` for more info +Run `revdepcheck::cloud_details(, "auditor")` for more info
@@ -473,139 +611,162 @@ Run `revdepcheck::cloud_details(, "autoplotly")` for more info * checking examples ... ERROR ``` - Running examples in ‘autoplotly-Ex.R’ failed + Running examples in ‘auditor-Ex.R’ failed The error most likely occurred in: - > ### Name: autoplotly - > ### Title: Automatic Visualization of Popular Statistical Results Using - > ### 'plotly.js' and 'ggplot2' - > ### Aliases: autoplotly + > ### Name: plot_lift + > ### Title: LIFT Chart + > ### Aliases: plot_lift plotLIFT > > ### ** Examples > - > # Automatically generate interactive plot for results produced by `stats::prcomp` - > p <- autoplotly(prcomp(iris[c(1, 2, 3, 4)]), data = iris, - + colour = 'Species', label = TRUE, label.size = 3, frame = TRUE) - Error in compute_geom_2(..., self = self) : - argument "theme" is missing, with no default - Calls: autoplotly ... use_defaults -> eval_from_theme -> %||% -> calc_element + > data(titanic_imputed, package = "DALEX") + ... + Backtrace: + ▆ + 1. ├─base (local) ``(x) + 2. └─ggplot2:::print.ggplot(x) + 3. ├─ggplot2::ggplot_gtable(data) + 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) + 5. └─ggplot2::calc_element("plot.margin", theme) + 6. └─cli::cli_abort(...) + 7. └─rlang::abort(...) Execution halted ``` -* checking tests ... ERROR +* checking running R code from vignettes ... ERROR ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(autoplotly) - > - > test_check("autoplotly") - [ FAIL 3 | WARN 0 | SKIP 0 | PASS 1 ] - - ══ Failed tests ════════════════════════════════════════════════════════════════ - ... - 10. └─ggplot2 (local) compute_geom_2(..., self = self) - 11. └─self$geom$use_defaults(data, self$aes_params, modifiers, theme = theme) - 12. └─ggplot2 (local) use_defaults(..., self = self) - 13. └─ggplot2:::eval_from_theme(default_aes, theme) - 14. ├─calc_element("geom", theme) %||% .default_geom_element - 15. └─ggplot2::calc_element("geom", theme) - - [ FAIL 3 | WARN 0 | SKIP 0 | PASS 1 ] - Error: Test failures - Execution halted + Errors in running code in vignettes: + when running code in ‘model_evaluation_audit.Rmd’ + ... + > plot(eva_glm, eva_rf, type = "lift") + Warning: The `guide` argument in `scale_*()` cannot be `FALSE`. This was deprecated in + ggplot2 3.3.4. + ℹ Please use "none" instead. + ℹ The deprecated feature was likely used in the auditor package. + Please report the issue at . + + When sourcing ‘model_evaluation_audit.R’: + Error: Theme element `plot.margin` must have class . + Execution halted + + ‘model_evaluation_audit.Rmd’ using ‘UTF-8’... failed + ‘model_fit_audit.Rmd’ using ‘UTF-8’... OK + ‘model_performance_audit.Rmd’ using ‘UTF-8’... OK + ‘model_residuals_audit.Rmd’ using ‘UTF-8’... OK + ‘observation_influence_audit.Rmd’ using ‘UTF-8’... OK ``` -# BayesGrowth +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘model_evaluation_audit.Rmd’ using knitr + ``` + +# augmentedRCBD
-* Version: 1.0.0 -* GitHub: https://github.com/jonathansmart/BayesGrowth -* Source code: https://github.com/cran/BayesGrowth -* Date/Publication: 2023-11-21 18:10:08 UTC -* Number of recursive dependencies: 110 +* Version: 0.1.7 +* GitHub: https://github.com/aravind-j/augmentedRCBD +* Source code: https://github.com/cran/augmentedRCBD +* Date/Publication: 2023-08-19 00:12:38 UTC +* Number of recursive dependencies: 128 -Run `revdepcheck::cloud_details(, "BayesGrowth")` for more info +Run `revdepcheck::cloud_details(, "augmentedRCBD")` for more info
## Newly broken -* checking running R code from vignettes ... ERROR +* checking examples ... ERROR ``` - Errors in running code in vignettes: - when running code in ‘MCMC-example.Rmd’ - ... - 2.75, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 1, NULL, NULL, NULL, c(0, 2.2, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, NULL, c(0, 0, 0, 2.2 - ), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0.5, NULL, NULL, NULL, c(0, 2.2, 0, 2.2), NULL, TRUE), list("grey20", NULL, NULL, NULL, FALSE, TRUE), NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 2.75, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 0.75, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, list(), NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, list(NULL, NA, NULL, NULL, TRUE), c(5.5, 5.5, 5.5, 5.5), 11, NULL, NULL, NULL, 1.2, NULL, NULL, 5.5, - NULL, NULL, NULL, NULL, 0.2, NULL, list(NULL, NULL, NULL, 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, NULL, NULL, NULL, TRUE), NULL, "right", NULL, NULL, NULL, "center", NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, c(0, 0, 0, 0), list(), 11, list("white", NA, NULL, NULL, TRUE), list(NA, "grey20", NULL, NULL, TRUE), 5.5, NULL, NULL, list("grey92", NULL, NULL, NULL, FALSE, TRUE), NULL, list(NULL, 0.5, NULL, NULL, FALSE, TRUE), NULL, NULL, - NULL, NULL, FALSE, list(NULL, "white", NULL, NULL, TRUE), list(NULL, NULL, NULL, 1.2, 0, 1, NULL, NULL, c(0, 0, 5.5, 0), NULL, TRUE), "panel", list(NULL, NULL, NULL, NULL, 0, 1, NULL, NULL, c(0, 0, 5.5, 0), NULL, TRUE), list(NULL, NULL, NULL, 0.8, 1, 1, NULL, NULL, c(5.5, 0, 0, 0), NULL, TRUE), "panel", list(NULL, NULL, NULL, 1.2, 0.5, 0.5, NULL, NULL, NULL, NULL, TRUE), "topleft", NULL, c(5.5, 5.5, 5.5, 5.5), list("grey85", "grey20", NULL, NULL, TRUE), NULL, NULL, "inherit", "inside", list(NULL, - NULL, "grey10", 0.8, NULL, NULL, NULL, NULL, c(4.4, 4.4, 4.4, 4.4), NULL, TRUE), NULL, NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, NULL, -90, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, NULL, 90, NULL, NULL, NULL, TRUE), NULL, 2.75, 2.75)) + Running examples in ‘augmentedRCBD-Ex.R’ failed + The error most likely occurred in: - When sourcing ‘MCMC-example.R’: - Error: unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 14, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, FALSE), NULL, list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.75, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, 90, NULL, c(0, - 2.75, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 1, NULL, NULL, NULL, c(0, 2.2, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, + > ### Name: augmentedRCBD.bulk + > ### Title: Analysis of Augmented Randomised Complete Block Design for + > ### Multiple Traits/Characters + > ### Aliases: augmentedRCBD.bulk + > + > ### ** Examples + > + ... + 2. ├─base::withCallingHandlers(...) + 3. └─augmentedRCBD::freqdist.augmentedRCBD(...) + 4. ├─base::rbind(ggplotGrob(G2), ggplotGrob(G1), size = "max") + 5. └─ggplot2::ggplotGrob(G2) + 6. ├─ggplot2::ggplot_gtable(ggplot_build(x)) + 7. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) + 8. └─ggplot2::calc_element("plot.margin", theme) + 9. └─cli::cli_abort(...) + 10. └─rlang::abort(...) Execution halted - - ‘MCMC-example.Rmd’ using ‘UTF-8’... failed ``` -* checking re-building of vignette outputs ... NOTE +* checking re-building of vignette outputs ... ERROR ``` Error(s) in re-building vignettes: - --- re-building ‘MCMC-example.Rmd’ using rmarkdown - ``` - -## In both - -* checking installed package size ... NOTE - ``` - installed size is 109.3Mb - sub-directories of 1Mb or more: - libs 107.7Mb - ``` - -* checking for GNU extensions in Makefiles ... NOTE - ``` - GNU make is a SystemRequirements. + --- re-building ‘Data_Analysis_with_augmentedRCBD.Rmd’ using rmarkdown_notangle + trying URL 'https://www.r-project.org/logo/Rlogo.png' + Content type 'image/png' length 48148 bytes (47 KB) + ================================================== + downloaded 47 KB + + trying URL 'https://raw.githubusercontent.com/aravind-j/augmentedRCBD/master/vignettes/rbase.png' + Content type 'image/png' length 57299 bytes (55 KB) + ================================================== + ... + Quitting from lines 970-977 [unnamed-chunk-70] (Data_Analysis_with_augmentedRCBD.Rmd) + Error: processing vignette 'Data_Analysis_with_augmentedRCBD.Rmd' failed with diagnostics: + Theme element `plot.margin` must have class . + --- failed re-building ‘Data_Analysis_with_augmentedRCBD.Rmd’ + + SUMMARY: processing the following file failed: + ‘Data_Analysis_with_augmentedRCBD.Rmd’ + + Error: Vignette re-building failed. + Execution halted ``` -# bdl - -
- -* Version: 1.0.5 -* GitHub: https://github.com/statisticspoland/R_Package_to_API_BDL -* Source code: https://github.com/cran/bdl -* Date/Publication: 2023-02-24 15:00:02 UTC -* Number of recursive dependencies: 144 - -Run `revdepcheck::cloud_details(, "bdl")` for more info - -
- -## Newly broken +## Newly fixed -* checking whether package ‘bdl’ can be installed ... WARNING +* checking re-building of vignette outputs ... WARNING ``` - Found the following significant warnings: - Warning: replacing previous import ‘ggplot2::ggpar’ by ‘ggpubr::ggpar’ when loading ‘bdl’ - See ‘/tmp/workdir/bdl/new/bdl.Rcheck/00install.out’ for details. + Error(s) in re-building vignettes: + --- re-building ‘Data_Analysis_with_augmentedRCBD.Rmd’ using rmarkdown_notangle + trying URL 'https://www.r-project.org/logo/Rlogo.png' + Content type 'image/png' length 48148 bytes (47 KB) + ================================================== + downloaded 47 KB + + trying URL 'https://raw.githubusercontent.com/aravind-j/augmentedRCBD/master/vignettes/rbase.png' + Content type 'image/png' length 57299 bytes (55 KB) + ================================================== + ... + + Error: processing vignette 'Data_Analysis_with_augmentedRCBD.Rmd' failed with diagnostics: + LaTeX failed to compile /tmp/workdir/augmentedRCBD/old/augmentedRCBD.Rcheck/vign_test/augmentedRCBD/vignettes/Data_Analysis_with_augmentedRCBD.tex. See https://yihui.org/tinytex/r/#debugging for debugging tips. See Data_Analysis_with_augmentedRCBD.log for more info. + --- failed re-building ‘Data_Analysis_with_augmentedRCBD.Rmd’ + + SUMMARY: processing the following file failed: + ‘Data_Analysis_with_augmentedRCBD.Rmd’ + + Error: Vignette re-building failed. + Execution halted ``` -# BeeBDC +# autoplotly
-* Version: 1.1.1 -* GitHub: https://github.com/jbdorey/BeeBDC -* Source code: https://github.com/cran/BeeBDC -* Date/Publication: 2024-04-03 23:53:03 UTC -* Number of recursive dependencies: 219 +* Version: 0.1.4 +* GitHub: https://github.com/terrytangyuan/autoplotly +* Source code: https://github.com/cran/autoplotly +* Date/Publication: 2021-04-18 06:50:11 UTC +* Number of recursive dependencies: 88 -Run `revdepcheck::cloud_details(, "BeeBDC")` for more info +Run `revdepcheck::cloud_details(, "autoplotly")` for more info
@@ -613,26 +774,21 @@ Run `revdepcheck::cloud_details(, "BeeBDC")` for more info * checking examples ... ERROR ``` - Running examples in ‘BeeBDC-Ex.R’ failed + Running examples in ‘autoplotly-Ex.R’ failed The error most likely occurred in: - > ### Name: summaryMaps - > ### Title: Create country-level summary maps of species and occurrence - > ### numbers - > ### Aliases: summaryMaps + > ### Name: autoplotly + > ### Title: Automatic Visualization of Popular Statistical Results Using + > ### 'plotly.js' and 'ggplot2' + > ### Aliases: autoplotly > > ### ** Examples > - ... - 23. └─ggplot2 (local) FUN(X[[i]], ...) - 24. └─base::lapply(...) - 25. └─ggplot2 (local) FUN(X[[i]], ...) - 26. └─g$draw_key(data, g$params, key_size) - 27. └─ggplot2 (local) draw_key(...) - 28. └─ggplot2::draw_key_polygon(data, params, size) - 29. └─rlang:::Summary.quosure(from_theme(thin), 1.524, na.rm = FALSE) - 30. └─rlang:::abort_quosure_op("Summary", .Generic) - 31. └─rlang::abort(...) + > # Automatically generate interactive plot for results produced by `stats::prcomp` + > p <- autoplotly(prcomp(iris[c(1, 2, 3, 4)]), data = iris, + + colour = 'Species', label = TRUE, label.size = 3, frame = TRUE) + Error in pm[[2]] : subscript out of bounds + Calls: autoplotly ... autoplotly.default -> ggplotly -> ggplotly.ggplot -> gg2list Execution halted ``` @@ -641,240 +797,273 @@ Run `revdepcheck::cloud_details(, "BeeBDC")` for more info Running ‘testthat.R’ Running the tests in ‘tests/testthat.R’ failed. Complete output: - > # This file is part of the standard setup for testthat. - > # It is recommended that you do not modify it. - > # - > # Where should you do additional test configuration? - > # Learn more about the roles of various files in: - > # * https://r-pkgs.org/tests.html - > # * https://testthat.r-lib.org/reference/test_package.html#special-files + > library(testthat) + > library(autoplotly) + > + > test_check("autoplotly") + [ FAIL 3 | WARN 0 | SKIP 0 | PASS 1 ] + + ══ Failed tests ════════════════════════════════════════════════════════════════ ... - 28. └─ggplot2::draw_key_polygon(data, params, size) - 29. └─rlang:::Summary.quosure(from_theme(thin), 1.524, na.rm = FALSE) - 30. └─rlang:::abort_quosure_op("Summary", .Generic) - 31. └─rlang::abort(...) + ▆ + 1. ├─autoplotly::autoplotly(...) at test_all.R:26:3 + 2. └─autoplotly:::autoplotly.default(...) + 3. ├─plotly::ggplotly(...) + 4. └─plotly:::ggplotly.ggplot(...) + 5. └─plotly::gg2list(...) - [ FAIL 1 | WARN 4 | SKIP 0 | PASS 241 ] + [ FAIL 3 | WARN 0 | SKIP 0 | PASS 1 ] Error: Test failures Execution halted - Warning message: - Connection is garbage-collected, use dbDisconnect() to avoid this. - ``` - -## In both - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘BeeBDC_main.Rmd’ - ... - - > rm(testChecklist) - - > check_space <- BeeBDC::countryOutlieRs(checklist = checklistFile, - + data = check_space, keepAdjacentCountry = TRUE, pointBuffer = 0.05, - + .... [TRUNCATED] - - ... - Error: Summary operations are not defined for quosures. Do you need to unquote - the quosure? - - # Bad: min(myquosure) - - # Good: min(!!myquosure) - Execution halted - - ‘BeeBDC_main.Rmd’ using ‘UTF-8’... failed - ‘basic_workflow.Rmd’ using ‘UTF-8’... failed - ``` - -* checking data for non-ASCII characters ... NOTE - ``` - Note: found 107 marked UTF-8 strings ``` -# blockCV +# baggr
-* Version: 3.1-3 -* GitHub: https://github.com/rvalavi/blockCV -* Source code: https://github.com/cran/blockCV -* Date/Publication: 2023-06-04 13:20:02 UTC -* Number of recursive dependencies: 139 +* Version: 0.7.8 +* GitHub: https://github.com/wwiecek/baggr +* Source code: https://github.com/cran/baggr +* Date/Publication: 2024-02-12 18:20:02 UTC +* Number of recursive dependencies: 104 -Run `revdepcheck::cloud_details(, "blockCV")` for more info +Run `revdepcheck::cloud_details(, "baggr")` for more info
## Newly broken -* checking re-building of vignette outputs ... NOTE +* checking examples ... ERROR ``` - Error(s) in re-building vignettes: - --- re-building ‘tutorial_1.Rmd’ using rmarkdown + Running examples in ‘baggr-Ex.R’ failed + The error most likely occurred in: + + > ### Name: baggr_plot + > ### Title: Plotting method in baggr package + > ### Aliases: baggr_plot + > + > ### ** Examples + > + > fit <- baggr(schools, pooling = "none") + Automatically chose Rubin model with aggregate data based on input data. + Setting prior for mean in each group using 10 times the max effect : ``` -## In both - * checking running R code from vignettes ... ERROR ``` Errors in running code in vignettes: - when running code in ‘tutorial_1.Rmd’ + when running code in ‘baggr.Rmd’ ... - > cv_plot(cv = scv, x = pa_data) - - When sourcing ‘tutorial_1.R’: - Error: Base operators are not defined for quosures. Do you need to unquote the - quosure? + [1] -1.866291 - # Bad: myquosure * rhs - ... - Error: Base operators are not defined for quosures. Do you need to unquote the - quosure? + > my_baggr_comparison <- baggr_compare(schools) + There is no predicted effect when pooling = 'none'. - # Bad: myquosure * rhs + > plot(my_baggr_comparison) + ggtitle("8 schools: model comparison") - # Good: !!myquosure * rhs + When sourcing ‘baggr.R’: + Error: Theme element `plot.margin` must have class . Execution halted - ‘tutorial_1.Rmd’ using ‘UTF-8’... failed - ‘tutorial_2.Rmd’ using ‘UTF-8’... failed + ‘baggr.Rmd’ using ‘UTF-8’... failed + ‘baggr_binary.Rmd’ using ‘UTF-8’... OK ``` -* checking Rd cross-references ... WARNING +* checking re-building of vignette outputs ... NOTE ``` - Missing link or links in documentation object 'cv_spatial.Rd': - ‘[biomod2]{BIOMOD_cv}’ - - See section 'Cross-references' in the 'Writing R Extensions' manual. + Error(s) in re-building vignettes: + --- re-building ‘baggr.Rmd’ using rmarkdown ``` +## In both + * checking installed package size ... NOTE ``` - installed size is 5.5Mb + installed size is 195.7Mb sub-directories of 1Mb or more: - doc 1.9Mb - extdata 1.9Mb - libs 1.4Mb + libs 193.9Mb ``` -# boxly +* checking for GNU extensions in Makefiles ... NOTE + ``` + GNU make is a SystemRequirements. + ``` + +# bayefdr
-* Version: 0.1.1 -* GitHub: https://github.com/Merck/boxly -* Source code: https://github.com/cran/boxly -* Date/Publication: 2023-10-24 02:40:02 UTC -* Number of recursive dependencies: 91 +* Version: 0.2.1 +* GitHub: https://github.com/VallejosGroup/bayefdr +* Source code: https://github.com/cran/bayefdr +* Date/Publication: 2022-10-26 19:35:06 UTC +* Number of recursive dependencies: 96 -Run `revdepcheck::cloud_details(, "boxly")` for more info +Run `revdepcheck::cloud_details(, "bayefdr")` for more info
## Newly broken +* checking examples ... ERROR + ``` + Running examples in ‘bayefdr-Ex.R’ failed + The error most likely occurred in: + + > ### Name: traceplot + > ### Title: Trace, marginal density histogram, and autocorrelation plot of + > ### MCMC draws. + > ### Aliases: traceplot + > + > ### ** Examples + > + ... + ▆ + 1. └─bayefdr::traceplot(x) + 2. └─ggExtra::ggMarginal(p1, type = "histogram", margins = "y") + 3. └─ggplot2::ggplotGrob(scatP) + 4. ├─ggplot2::ggplot_gtable(ggplot_build(x)) + 5. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) + 6. └─ggplot2::calc_element("plot.margin", theme) + 7. └─cli::cli_abort(...) + 8. └─rlang::abort(...) + Execution halted + ``` + * checking tests ... ERROR ``` Running ‘testthat.R’ Running the tests in ‘tests/testthat.R’ failed. Complete output: - > # This file is part of the standard setup for testthat. - > # It is recommended that you do not modify it. - > # - > # Where should you do additional test configuration? - > # Learn more about the roles of various files in: - > # * https://r-pkgs.org/tests.html - > # * https://testthat.r-lib.org/reference/test_package.html#special-files + > library(testthat) + > library(bayefdr) + > + > test_check("bayefdr") + [ FAIL 1 | WARN 1 | SKIP 0 | PASS 14 ] + + ══ Failed tests ════════════════════════════════════════════════════════════════ ... - 26. └─ggplot2 (local) compute_geom_2(..., self = self) - 27. └─self$geom$use_defaults(data, self$aes_params, modifiers, theme = theme) - 28. └─ggplot2 (local) use_defaults(..., self = self) - 29. └─ggplot2:::eval_from_theme(default_aes, theme) - 30. ├─calc_element("geom", theme) %||% .default_geom_element - 31. └─ggplot2::calc_element("geom", theme) + 6. └─ggplot2::ggplotGrob(scatP) + 7. ├─ggplot2::ggplot_gtable(ggplot_build(x)) + 8. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) + 9. └─ggplot2::calc_element("plot.margin", theme) + 10. └─cli::cli_abort(...) + 11. └─rlang::abort(...) - [ FAIL 2 | WARN 0 | SKIP 0 | PASS 25 ] + [ FAIL 1 | WARN 1 | SKIP 0 | PASS 14 ] Error: Test failures Execution halted ``` -# bSi +# BayesGrowth
* Version: 1.0.0 -* GitHub: NA -* Source code: https://github.com/cran/bSi -* Date/Publication: 2024-01-24 15:52:57 UTC -* Number of recursive dependencies: 99 +* GitHub: https://github.com/jonathansmart/BayesGrowth +* Source code: https://github.com/cran/BayesGrowth +* Date/Publication: 2023-11-21 18:10:08 UTC +* Number of recursive dependencies: 109 -Run `revdepcheck::cloud_details(, "bSi")` for more info +Run `revdepcheck::cloud_details(, "BayesGrowth")` for more info
## Newly broken -* checking whether package ‘bSi’ can be installed ... WARNING +* checking running R code from vignettes ... ERROR ``` - Found the following significant warnings: - Warning: replacing previous import ‘ggplot2::ggpar’ by ‘ggpubr::ggpar’ when loading ‘bSi’ - See ‘/tmp/workdir/bSi/new/bSi.Rcheck/00install.out’ for details. + Errors in running code in vignettes: + when running code in ‘MCMC-example.Rmd’ + ... + > ggplot(growth_curve, aes(Age, LAA)) + geom_point(data = example_data, + + aes(Age, Length), alpha = 0.3) + geom_lineribbon(aes(ymin = .lower, + + .... [TRUNCATED] + Warning: Using `size` aesthetic for lines was deprecated in ggplot2 3.4.0. + ℹ Please use `linewidth` instead. + + When sourcing ‘MCMC-example.R’: + Error: unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, "black", TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 14, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, FALSE), NULL, list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), 5.5, c(5.5, 5.5, 5.5, 5.5), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.75, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, + NULL, NULL, NULL, 1, 90, NULL, c(0, 2.75, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 1, NULL, NULL, NULL, c(0, 2.2, 0, 0), NULL, TRUE), NULL, li + Execution halted + + ‘MCMC-example.Rmd’ using ‘UTF-8’... failed ``` -# cartograflow +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘MCMC-example.Rmd’ using rmarkdown + ``` + +## In both + +* checking installed package size ... NOTE + ``` + installed size is 84.5Mb + sub-directories of 1Mb or more: + data 1.5Mb + libs 82.3Mb + ``` + +* checking for GNU extensions in Makefiles ... NOTE + ``` + GNU make is a SystemRequirements. + ``` + +# BayesianReasoning
-* Version: 1.0.5 -* GitHub: https://github.com/fbahoken/cartogRaflow -* Source code: https://github.com/cran/cartograflow -* Date/Publication: 2023-10-17 22:40:21 UTC -* Number of recursive dependencies: 102 +* Version: 0.4.2 +* GitHub: https://github.com/gorkang/BayesianReasoning +* Source code: https://github.com/cran/BayesianReasoning +* Date/Publication: 2023-11-14 11:33:20 UTC +* Number of recursive dependencies: 107 -Run `revdepcheck::cloud_details(, "cartograflow")` for more info +Run `revdepcheck::cloud_details(, "BayesianReasoning")` for more info
## Newly broken -* checking examples ... ERROR +* checking running R code from vignettes ... ERROR ``` - Running examples in ‘cartograflow-Ex.R’ failed - The error most likely occurred in: + Errors in running code in vignettes: + when running code in ‘PPV_NPV.Rmd’ + ... + ℹ Please consider using `annotate()` or provide this layer with data containing + a single row. + Warning in ggforce::geom_mark_rect(aes(label = paste0(translated_labels$label_PPV_NPV, : + All aesthetics have length 1, but the data has 10201 rows. + ℹ Please consider using `annotate()` or provide this layer with data containing + a single row. - > ### Name: flowgini - > ### Title: Analysis of flow concentration (Gini coefficient) - > ### Aliases: flowgini - > - > ### ** Examples - > - > library(cartograflow) - ... - Warning: Use of `x$linkcum` is discouraged. - ℹ Use `linkcum` instead. - Warning: Use of `x$flowcum` is discouraged. - ℹ Use `flowcum` instead. - Warning: Use of `x$flowcum` is discouraged. - ℹ Use `flowcum` instead. - Error in compute_geom_2(..., self = self) : - argument "theme" is missing, with no default - Calls: flowgini ... use_defaults -> eval_from_theme -> %||% -> calc_element + When sourcing ‘PPV_NPV.R’: + Error: object is not coercible to a unit Execution halted + + ‘PPV_NPV.Rmd’ using ‘UTF-8’... failed + ‘introduction.Rmd’ using ‘UTF-8’... OK ``` -# cats +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘PPV_NPV.Rmd’ using rmarkdown + ``` + +# bayestestR
-* Version: 1.0.2 -* GitHub: NA -* Source code: https://github.com/cran/cats -* Date/Publication: 2022-03-11 10:20:07 UTC -* Number of recursive dependencies: 83 +* Version: 0.13.2 +* GitHub: https://github.com/easystats/bayestestR +* Source code: https://github.com/cran/bayestestR +* Date/Publication: 2024-02-12 11:40:02 UTC +* Number of recursive dependencies: 186 -Run `revdepcheck::cloud_details(, "cats")` for more info +Run `revdepcheck::cloud_details(, "bayestestR")` for more info
@@ -882,49 +1071,157 @@ Run `revdepcheck::cloud_details(, "cats")` for more info * checking examples ... ERROR ``` - Running examples in ‘cats-Ex.R’ failed + Running examples in ‘bayestestR-Ex.R’ failed The error most likely occurred in: - > ### Name: trial_ocs - > ### Title: Calculates the operating characteristics of the cohort trial - > ### Aliases: trial_ocs + > ### Name: bayesfactor_restricted + > ### Title: Bayes Factors (BF) for Order Restricted Models + > ### Aliases: bayesfactor_restricted bf_restricted + > ### bayesfactor_restricted.stanreg bayesfactor_restricted.brmsfit + > ### bayesfactor_restricted.blavaan bayesfactor_restricted.emmGrid + > ### as.logical.bayesfactor_restricted > - > ### ** Examples + ... + + ) > > + > (b <- bayesfactor_restricted(posterior, hypothesis = hyps, prior = prior)) + Bayes Factor (Order-Restriction) + + Hypothesis P(Prior) P(Posterior) BF + A > B & B > C 0.16 0.23 1.39 + A > B & A > C 0.36 0.59 1.61 + C > A 0.46 0.34 0.742 + ``` + +## In both + +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(bayestestR) + > + > test_check("bayestestR") + Starting 2 test processes + [ FAIL 2 | WARN 3 | SKIP 75 | PASS 186 ] + ... - + cohort_offset = cohort_offset, sr_first_pos = sr_first_pos, - + missing_prob = missing_prob, cohort_fixed = cohort_fixed, accrual_type = accrual_type, - + accrual_param = accrual_param, hist_lag = hist_lag, analysis_times = analysis_times, - + time_trend = time_trend, cohorts_start = cohorts_start, cohorts_sim = cohorts_sim, - + iter = 2, coresnum = 1, save = FALSE, ret_list = TRUE, plot_ocs = TRUE - + ) - Error in compute_geom_2(..., self = self) : - argument "theme" is missing, with no default - Calls: trial_ocs ... use_defaults -> eval_from_theme -> %||% -> calc_element + 14. └─brms:::eval2(call, envir = args, enclos = envir) + 15. └─base::eval(expr, envir, ...) + 16. └─base::eval(expr, envir, ...) + 17. └─rstan (local) .fun(model_code = .x1) + 18. └─rstan:::cxxfunctionplus(...) + 19. └─base::sink(type = "output") + + [ FAIL 2 | WARN 3 | SKIP 75 | PASS 186 ] + Error: Test failures + Execution halted + ``` + +# bdots + +
+ +* Version: 1.2.5 +* GitHub: https://github.com/collinn/bdots +* Source code: https://github.com/cran/bdots +* Date/Publication: 2023-01-06 23:20:02 UTC +* Number of recursive dependencies: 53 + +Run `revdepcheck::cloud_details(, "bdots")` for more info + +
+ +## Newly broken + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘bdots.Rmd’ + ... + Adjusted alpha: 0.01182815 + Significant Intervals at adjusted alpha: + [,1] [,2] + [1,] 556 940 + + > plot(boot1) + + When sourcing ‘bdots.R’: + Error: Theme element `plot.margin` must have class . Execution halted + + ‘bdots.Rmd’ using ‘UTF-8’... failed + ‘correlations.Rmd’ using ‘UTF-8’... OK + ‘customCurves.Rmd’ using ‘UTF-8’... OK + ‘refitCoef.Rmd’ using ‘UTF-8’... OK ``` -## In both +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘bdots.Rmd’ using rmarkdown + ``` -* checking dependencies in R code ... NOTE +# bdrc + +
+ +* Version: 1.1.0 +* GitHub: https://github.com/sor16/bdrc +* Source code: https://github.com/cran/bdrc +* Date/Publication: 2023-03-19 17:10:03 UTC +* Number of recursive dependencies: 75 + +Run `revdepcheck::cloud_details(, "bdrc")` for more info + +
+ +## Newly broken + +* checking running R code from vignettes ... ERROR ``` - Namespaces in Imports field not imported from: - ‘epitools’ ‘forcats’ ‘purrr’ - All declared Imports should be used. + Errors in running code in vignettes: + when running code in ‘tournament.Rmd’ + ... + 3 1 2 plm -8.903540 4.249257 26.305595 -0.3185195 FALSE + 4 1 2 plm0 -8.873488 4.120050 25.987075 NA TRUE + 5 2 3 gplm0 5.884914 6.692781 1.615733 24.3713418 TRUE + 6 2 3 plm0 -8.873488 4.120050 25.987075 NA FALSE + + > plot(t_obj) + + When sourcing ‘tournament.R’: + Error: Theme element `plot.margin` must have class . + Execution halted + + ‘background.Rmd’ using ‘UTF-8’... OK + ‘introduction.Rmd’ using ‘UTF-8’... OK + ‘tournament.Rmd’ using ‘UTF-8’... failed ``` -# cheem +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘background.Rmd’ using rmarkdown + --- finished re-building ‘background.Rmd’ + + --- re-building ‘introduction.Rmd’ using rmarkdown + ``` + +# BeeBDC
-* Version: 0.4.0.0 -* GitHub: https://github.com/nspyrison/cheem -* Source code: https://github.com/cran/cheem -* Date/Publication: 2023-11-08 21:30:02 UTC -* Number of recursive dependencies: 152 +* Version: 1.1.1 +* GitHub: https://github.com/jbdorey/BeeBDC +* Source code: https://github.com/cran/BeeBDC +* Date/Publication: 2024-04-03 23:53:03 UTC +* Number of recursive dependencies: 219 -Run `revdepcheck::cloud_details(, "cheem")` for more info +Run `revdepcheck::cloud_details(, "BeeBDC")` for more info
@@ -935,24 +1232,24 @@ Run `revdepcheck::cloud_details(, "cheem")` for more info Running ‘testthat.R’ Running the tests in ‘tests/testthat.R’ failed. Complete output: - > library(testthat) - > library(cheem) - -------------------------------------------------------- - cheem --- version 0.4.0.0 - Please share bugs, suggestions, and feature requests at: - https://github.com/nspyrison/cheem/issues/ - -------------------------------------------------------- + > # This file is part of the standard setup for testthat. + > # It is recommended that you do not modify it. + > # + > # Where should you do additional test configuration? + > # Learn more about the roles of various files in: + > # * https://r-pkgs.org/tests.html + > # * https://testthat.r-lib.org/reference/test_package.html#special-files ... - 23. └─ggplot2 (local) compute_geom_2(..., self = self) - 24. └─self$geom$use_defaults(data, self$aes_params, modifiers, theme = theme) - 25. └─ggplot2 (local) use_defaults(..., self = self) - 26. └─ggplot2:::eval_from_theme(default_aes, theme) - 27. ├─calc_element("geom", theme) %||% .default_geom_element - 28. └─ggplot2::calc_element("geom", theme) + 8. └─ggplot2:::ggplot_gtable.ggplot_built(data) + 9. └─ggplot2::calc_element("plot.margin", theme) + 10. └─cli::cli_abort(...) + 11. └─rlang::abort(...) - [ FAIL 1 | WARN 0 | SKIP 0 | PASS 10 ] + [ FAIL 1 | WARN 4 | SKIP 0 | PASS 235 ] Error: Test failures Execution halted + Warning message: + Connection is garbage-collected, use dbDisconnect() to avoid this. ``` ## In both @@ -960,33 +1257,39 @@ Run `revdepcheck::cloud_details(, "cheem")` for more info * checking running R code from vignettes ... ERROR ``` Errors in running code in vignettes: - when running code in ‘getting-started-with-cheem.Rmd’ + when running code in ‘BeeBDC_main.Rmd’ ... - > knitr::opts_chunk$set(echo = TRUE, include = TRUE, - + results = "show", eval = FALSE, message = FALSE, warning = FALSE, - + error = FALSE, co .... [TRUNCATED] + > rm(testChecklist) - > knitr::include_graphics("../inst/shiny_apps/cheem/www/lime_nonlinear.png") + > check_space <- BeeBDC::countryOutlieRs(checklist = checklistFile, + + data = check_space, keepAdjacentCountry = TRUE, pointBuffer = 0.05, + + .... [TRUNCATED] - When sourcing ‘getting-started-with-cheem.R’: - Error: Cannot find the file(s): "../inst/shiny_apps/cheem/www/lime_nonlinear.png" + When sourcing ‘BeeBDC_main.R’: + Error: object 'checklistFile' not found Execution halted - ‘getting-started-with-cheem.Rmd’ using ‘UTF-8’... failed + ‘BeeBDC_main.Rmd’ using ‘UTF-8’... failed + ‘basic_workflow.Rmd’ using ‘UTF-8’... OK ``` -# chronicle +* checking data for non-ASCII characters ... NOTE + ``` + Note: found 107 marked UTF-8 strings + ``` + +# besthr
-* Version: 0.3 +* Version: 0.3.2 * GitHub: NA -* Source code: https://github.com/cran/chronicle -* Date/Publication: 2021-06-25 05:00:02 UTC -* Number of recursive dependencies: 146 +* Source code: https://github.com/cran/besthr +* Date/Publication: 2023-04-14 08:50:08 UTC +* Number of recursive dependencies: 67 -Run `revdepcheck::cloud_details(, "chronicle")` for more info +Run `revdepcheck::cloud_details(, "besthr")` for more info
@@ -994,81 +1297,73 @@ Run `revdepcheck::cloud_details(, "chronicle")` for more info * checking examples ... ERROR ``` - Running examples in ‘chronicle-Ex.R’ failed + Running examples in ‘besthr-Ex.R’ failed The error most likely occurred in: - > ### Name: make_barplot - > ### Title: Create a bar plot from a data frame through ggplotly - > ### Aliases: make_barplot + > ### Name: plot.hrest + > ### Title: plots the 'hrest' object + > ### Aliases: plot.hrest > > ### ** Examples > - > make_barplot(dt = iris, bars = 'Species', value = 'Sepal.Length') - Error in compute_geom_2(..., self = self) : - argument "theme" is missing, with no default - Calls: make_barplot ... use_defaults -> eval_from_theme -> %||% -> calc_element + > + > d1 <- make_data() + > hr_est <- estimate(d1, score, group) + > plot(hr_est) + Picking joint bandwidth of 0.68 + Error in as.unit(value) : object is not coercible to a unit + Calls: ... assemble_guides -> guides_build -> [<- -> [<-.unit -> as.unit Execution halted ``` * checking running R code from vignettes ... ERROR ``` Errors in running code in vignettes: - when running code in ‘chronicle.Rmd’ + when running code in ‘basic-use.Rmd’ ... - + filename = "quick_demo", title = "A quick chronicle demo", - + author = .... [TRUNCATED] + Confidence Intervals (0.025, 0.975) + 4.07125, 8.62625 - Quitting from lines at lines 34-46 [unnamed-chunk-3] (quick_demo.Rmd) + 100 bootstrap resamples. + > plot(hr_est_1) + Picking joint bandwidth of 0.412 - When sourcing ‘chronicle.R’: - Error: ℹ In index: 1. - Caused by error in `compute_geom_2()`: - ! argument "theme" is missing, with no default + When sourcing ‘basic-use.R’: + Error: object is not coercible to a unit Execution halted - ‘chronicle.Rmd’ using ‘UTF-8’... failed + ‘basic-use.Rmd’ using ‘UTF-8’... failed ``` * checking re-building of vignette outputs ... NOTE ``` Error(s) in re-building vignettes: ... - --- re-building ‘chronicle.Rmd’ using rmarkdown + --- re-building ‘basic-use.Rmd’ using rmarkdown - Quitting from lines at lines 34-46 [unnamed-chunk-3] (quick_demo.Rmd) - Error: processing vignette 'chronicle.Rmd' failed with diagnostics: - ℹ In index: 1. - Caused by error in `compute_geom_2()`: - ! argument "theme" is missing, with no default - --- failed re-building ‘chronicle.Rmd’ + Quitting from lines 34-44 [unnamed-chunk-2] (basic-use.Rmd) + Error: processing vignette 'basic-use.Rmd' failed with diagnostics: + object is not coercible to a unit + --- failed re-building ‘basic-use.Rmd’ SUMMARY: processing the following file failed: - ‘chronicle.Rmd’ + ‘basic-use.Rmd’ Error: Vignette re-building failed. Execution halted ``` -## In both - -* checking dependencies in R code ... NOTE - ``` - Namespaces in Imports field not imported from: - ‘DT’ ‘dplyr’ ‘prettydoc’ ‘rmdformats’ ‘skimr’ - All declared Imports should be used. - ``` - -# clinDataReview +# BetaPASS
-* Version: 1.5.1 -* GitHub: https://github.com/openanalytics/clinDataReview -* Source code: https://github.com/cran/clinDataReview -* Date/Publication: 2024-04-24 20:10:03 UTC -* Number of recursive dependencies: 130 +* Version: 1.1-2 +* GitHub: NA +* Source code: https://github.com/cran/BetaPASS +* Date/Publication: 2023-10-18 21:00:08 UTC +* Number of recursive dependencies: 58 -Run `revdepcheck::cloud_details(, "clinDataReview")` for more info +Run `revdepcheck::cloud_details(, "BetaPASS")` for more info
@@ -1076,239 +1371,370 @@ Run `revdepcheck::cloud_details(, "clinDataReview")` for more info * checking examples ... ERROR ``` - Running examples in ‘clinDataReview-Ex.R’ failed + Running examples in ‘BetaPASS-Ex.R’ failed The error most likely occurred in: - > ### Name: scatterplotClinData - > ### Title: Scatterplot of variables of interest for clinical data - > ### visualization. - > ### Aliases: scatterplotClinData + > ### Name: betapower + > ### Title: Find Power with Beta distribution + > ### Aliases: betapower > > ### ** Examples > + > BPmat <- betapower(mu0 = 0.56, sd0 = 0.255, mu1.start = .70, mu1.end = .75, mu1.by = .05, ... - + xVar = "ADY", - + yVar = "LBSTRESN", - + aesPointVar = list(color = "TRTP", fill = "TRTP"), - + aesLineVar = list(group = "USUBJID", color = "TRTP"), - + labelVars = labelVars - + ) - Error in compute_geom_2(..., self = self) : - argument "theme" is missing, with no default - Calls: scatterplotClinData ... use_defaults -> eval_from_theme -> %||% -> calc_element + Backtrace: + ▆ + 1. ├─base (local) ``(x) + 2. └─ggplot2:::print.ggplot(x) + 3. ├─ggplot2::ggplot_gtable(data) + 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) + 5. └─ggplot2::calc_element("plot.margin", theme) + 6. └─cli::cli_abort(...) + 7. └─rlang::abort(...) Execution halted ``` -* checking tests ... ERROR +* checking running R code from vignettes ... ERROR ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(clinDataReview) - > - > test_check("clinDataReview") - adding: report.html (deflated 63%) - adding: report_dependencies1dcd775cc9bd/ (stored 0%) - adding: report_dependencies1dcd775cc9bd/file1dcd27c26d11.html (deflated 8%) - ... - 9. └─ggplot2 (local) compute_geom_2(..., self = self) - 10. └─self$geom$use_defaults(data, self$aes_params, modifiers, theme = theme) - 11. └─ggplot2 (local) use_defaults(..., self = self) - 12. └─ggplot2:::eval_from_theme(default_aes, theme) - 13. ├─calc_element("geom", theme) %||% .default_geom_element - 14. └─ggplot2::calc_element("geom", theme) - - [ FAIL 23 | WARN 8 | SKIP 30 | PASS 450 ] - Error: Test failures - Execution halted + Errors in running code in vignettes: + when running code in ‘BetaPASS.Rmd’ + ... + | 0.825| 0.775| 45| 0.70| + | 0.975| 0.975| 45| 0.75| + | 0.925| 0.875| 50| 0.70| + | 1.000| 0.975| 50| 0.75| + + > plot(Power.mat, link.type = "logit", by = "mu1") + + When sourcing ‘BetaPASS.R’: + Error: Theme element `plot.margin` must have class . + Execution halted + + ‘BetaPASS.Rmd’ using ‘UTF-8’... failed ``` * checking re-building of vignette outputs ... NOTE ``` Error(s) in re-building vignettes: ... - --- re-building ‘clinDataReview-dataPreprocessing.Rmd’ using rmarkdown - --- finished re-building ‘clinDataReview-dataPreprocessing.Rmd’ - - --- re-building ‘clinDataReview-dataVisualization.Rmd’ using rmarkdown - - Quitting from lines at lines 167-208 [timeProfiles] (clinDataReview-dataVisualization.Rmd) - Error: processing vignette 'clinDataReview-dataVisualization.Rmd' failed with diagnostics: - argument "theme" is missing, with no default - ... - --- failed re-building ‘clinDataReview-dataVisualization.Rmd’ + --- re-building ‘BetaPASS.Rmd’ using rmarkdown - --- re-building ‘clinDataReview-reporting.Rmd’ using rmarkdown - --- finished re-building ‘clinDataReview-reporting.Rmd’ + Quitting from lines 101-102 [unnamed-chunk-4] (BetaPASS.Rmd) + Error: processing vignette 'BetaPASS.Rmd' failed with diagnostics: + Theme element `plot.margin` must have class . + --- failed re-building ‘BetaPASS.Rmd’ SUMMARY: processing the following file failed: - ‘clinDataReview-dataVisualization.Rmd’ + ‘BetaPASS.Rmd’ Error: Vignette re-building failed. Execution halted ``` -## In both +# biblioverlap -* checking installed package size ... NOTE - ``` - installed size is 6.0Mb - sub-directories of 1Mb or more: - doc 4.3Mb - ``` +
-# clinUtils +* Version: 1.0.2 +* GitHub: https://github.com/gavieira/biblioverlap +* Source code: https://github.com/cran/biblioverlap +* Date/Publication: 2023-11-07 19:50:02 UTC +* Number of recursive dependencies: 93 -
+Run `revdepcheck::cloud_details(, "biblioverlap")` for more info -* Version: 0.1.5 -* GitHub: https://github.com/openanalytics/clinUtils -* Source code: https://github.com/cran/clinUtils -* Date/Publication: 2024-04-23 20:50:31 UTC -* Number of recursive dependencies: 120 +
-Run `revdepcheck::cloud_details(, "clinUtils")` for more info +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘biblioverlap-Ex.R’ failed + The error most likely occurred in: + + > ### Name: plot_upset + > ### Title: Plotting UpSet plot from biblioverlap results + > ### Aliases: plot_upset + > + > ### ** Examples + > + > #Running document-level matching procedure + ... + 3. ├─base::suppressMessages(...) + 4. │ └─base::withCallingHandlers(...) + 5. └─UpSetR:::Make_main_bar(...) + 6. └─ggplot2::ggplotGrob(Main_bar_plot) + 7. ├─ggplot2::ggplot_gtable(ggplot_build(x)) + 8. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) + 9. └─ggplot2::calc_element("plot.margin", theme) + 10. └─cli::cli_abort(...) + 11. └─rlang::abort(...) + Execution halted + ``` + +## In both + +* checking data for non-ASCII characters ... NOTE + ``` + Note: found 573 marked UTF-8 strings + ``` + +# biscale + +
+ +* Version: 1.0.0 +* GitHub: https://github.com/chris-prener/biscale +* Source code: https://github.com/cran/biscale +* Date/Publication: 2022-05-27 08:40:09 UTC +* Number of recursive dependencies: 83 + +Run `revdepcheck::cloud_details(, "biscale")` for more info
## Newly broken +* checking examples ... ERROR + ``` + Running examples in ‘biscale-Ex.R’ failed + The error most likely occurred in: + + > ### Name: bi_legend + > ### Title: Create Object for Drawing Legend + > ### Aliases: bi_legend + > + > ### ** Examples + > + > # sample 3x3 legend + ... + Backtrace: + ▆ + 1. ├─base (local) ``(x) + 2. └─ggplot2:::print.ggplot(x) + 3. ├─ggplot2::ggplot_gtable(data) + 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) + 5. └─ggplot2::calc_element("plot.margin", theme) + 6. └─cli::cli_abort(...) + 7. └─rlang::abort(...) + Execution halted + ``` + +## In both + * checking running R code from vignettes ... ERROR ``` Errors in running code in vignettes: - when running code in ‘clinUtils-vignette.Rmd’ + when running code in ‘biscale.Rmd’ ... - layout + > knitr::opts_chunk$set(collapse = TRUE, comment = "#>") + > knitr::include_graphics("../man/figures/biscale.001.jpeg") - > listPlotsInteractiveLB <- sapply(listPlotsLB, function(ggplot) ggplotly(ggplot) %>% - + partial_bundle(), simplify = FALSE) + When sourcing ‘biscale.R’: + Error: Cannot find the file(s): "../man/figures/biscale.001.jpeg" + ... + > knitr::include_graphics("../man/figures/raster.jpeg") - When sourcing ‘clinUtils-vignette.R’: - Error: argument "theme" is missing, with no default + When sourcing ‘rasters.R’: + Error: Cannot find the file(s): "../man/figures/raster.jpeg" Execution halted - ‘clinUtils-vignette.Rmd’ using ‘UTF-8’... failed + ‘biscale.Rmd’ using ‘UTF-8’... failed + ‘bivariate_palettes.Rmd’ using ‘UTF-8’... failed + ‘breaks.Rmd’ using ‘UTF-8’... failed + ‘rasters.Rmd’ using ‘UTF-8’... failed ``` -* checking re-building of vignette outputs ... NOTE +* checking dependencies in R code ... NOTE ``` - Error(s) in re-building vignettes: - --- re-building ‘clinUtils-vignette.Rmd’ using rmarkdown + Namespaces in Imports field not imported from: + ‘stats’ ‘utils’ + All declared Imports should be used. ``` -## Newly fixed +# BlandAltmanLeh -* checking running R code from vignettes ... WARNING +
+ +* Version: 0.3.1 +* GitHub: NA +* Source code: https://github.com/cran/BlandAltmanLeh +* Date/Publication: 2015-12-23 23:32:17 +* Number of recursive dependencies: 63 + +Run `revdepcheck::cloud_details(, "BlandAltmanLeh")` for more info + +
+ +## Newly broken + +* checking running R code from vignettes ... ERROR ``` Errors in running code in vignettes: - when running code in ‘clinUtils-vignette.Rmd’ + when running code in ‘Intro.Rmd’ ... - + > b <- 0.02 * a + 0.3 * rnorm(150) - > knitPrintListPlots(plotsList = listPlotsInteractiveLB, - + generalLabel = "lab-hist-interactive", type = "plotly", titles = simpleCap(tolower(nam .... [TRUNCATED] + > library(ggExtra) - Quitting from lines at lines 2-4 [lab-hist-interactive1] + > print(ggMarginal(bland.altman.plot(a, b, graph.sys = "ggplot2"), + + type = "histogram", size = 4)) - When sourcing ‘clinUtils-vignette.R’: - Error: there is no package called 'webshot' + When sourcing ‘Intro.R’: + Error: Theme element `plot.margin` must have class . Execution halted - ‘clinUtils-vignette.Rmd’ using ‘UTF-8’... failed - ``` - -## In both - -* checking installed package size ... NOTE - ``` - installed size is 7.9Mb - sub-directories of 1Mb or more: - doc 6.5Mb + ‘Intro.Rmd’... failed ``` -# ClusROC +# bnma
-* Version: 1.0.2 -* GitHub: https://github.com/toduckhanh/ClusROC -* Source code: https://github.com/cran/ClusROC -* Date/Publication: 2022-11-17 15:00:02 UTC -* Number of recursive dependencies: 107 +* Version: 1.6.0 +* GitHub: NA +* Source code: https://github.com/cran/bnma +* Date/Publication: 2024-02-11 01:10:02 UTC +* Number of recursive dependencies: 53 -Run `revdepcheck::cloud_details(, "ClusROC")` for more info +Run `revdepcheck::cloud_details(, "bnma")` for more info
## Newly broken -* checking whether package ‘ClusROC’ can be installed ... WARNING +* checking running R code from vignettes ... ERROR ``` - Found the following significant warnings: - Warning: replacing previous import ‘ggplot2::ggpar’ by ‘ggpubr::ggpar’ when loading ‘ClusROC’ - See ‘/tmp/workdir/ClusROC/new/ClusROC.Rcheck/00install.out’ for details. + Errors in running code in vignettes: + when running code in ‘bnma.Rmd’ + ... + + > network.forest.plot(result, label.margin = 15) + Warning in geom_text(aes(label = "Median [95% Crl]"), y = xlim.range[2] + : + All aesthetics have length 1, but the data has 6 rows. + ℹ Please consider using `annotate()` or provide this layer with data containing + a single row. + + When sourcing ‘bnma.R’: + Error: Theme element `plot.margin` must have class . + Execution halted + + ‘bnma.Rmd’ using ‘UTF-8’... failed + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + ... + --- re-building ‘bnma.Rmd’ using rmarkdown + + Quitting from lines 88-99 [unnamed-chunk-8] (bnma.Rmd) + Error: processing vignette 'bnma.Rmd' failed with diagnostics: + Theme element `plot.margin` must have class . + --- failed re-building ‘bnma.Rmd’ + + SUMMARY: processing the following file failed: + ‘bnma.Rmd’ + + Error: Vignette re-building failed. + Execution halted ``` -# clustEff +# boxly
-* Version: 0.3.1 -* GitHub: NA -* Source code: https://github.com/cran/clustEff -* Date/Publication: 2024-01-23 08:52:55 UTC -* Number of recursive dependencies: 136 +* Version: 0.1.1 +* GitHub: https://github.com/Merck/boxly +* Source code: https://github.com/cran/boxly +* Date/Publication: 2023-10-24 02:40:02 UTC +* Number of recursive dependencies: 91 -Run `revdepcheck::cloud_details(, "clustEff")` for more info +Run `revdepcheck::cloud_details(, "boxly")` for more info
## Newly broken -* checking whether package ‘clustEff’ can be installed ... WARNING +* checking tests ... ERROR ``` - Found the following significant warnings: - Warning: replacing previous import ‘ggplot2::ggpar’ by ‘ggpubr::ggpar’ when loading ‘clustEff’ - See ‘/tmp/workdir/clustEff/new/clustEff.Rcheck/00install.out’ for details. + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > # This file is part of the standard setup for testthat. + > # It is recommended that you do not modify it. + > # + > # Where should you do additional test configuration? + > # Learn more about the roles of various files in: + > # * https://r-pkgs.org/tests.html + > # * https://testthat.r-lib.org/reference/test_package.html#special-files + ... + 16. ├─plotly::add_trace(...) + 17. │ └─plotly::add_data(p, data) + 18. │ └─plotly:::is.plotly(p) + 19. ├─plotly::ggplotly(p, tooltip = "text", dynamicTicks = TRUE) + 20. └─plotly:::ggplotly.ggplot(p, tooltip = "text", dynamicTicks = TRUE) + 21. └─plotly::gg2list(...) + + [ FAIL 2 | WARN 0 | SKIP 0 | PASS 25 ] + Error: Test failures + Execution halted ``` -# coda4microbiome +# braidReports
-* Version: 0.2.3 -* GitHub: https://github.com/malucalle/coda4microbiome -* Source code: https://github.com/cran/coda4microbiome -* Date/Publication: 2024-02-21 08:30:06 UTC -* Number of recursive dependencies: 136 +* Version: 0.5.4 +* GitHub: NA +* Source code: https://github.com/cran/braidReports +* Date/Publication: 2021-01-05 18:20:09 UTC +* Number of recursive dependencies: 30 -Run `revdepcheck::cloud_details(, "coda4microbiome")` for more info +Run `revdepcheck::cloud_details(, "braidReports")` for more info
## Newly broken -* checking whether package ‘coda4microbiome’ can be installed ... WARNING +* checking examples ... ERROR ``` - Found the following significant warnings: - Warning: replacing previous import ‘ggplot2::ggpar’ by ‘ggpubr::ggpar’ when loading ‘coda4microbiome’ - See ‘/tmp/workdir/coda4microbiome/new/coda4microbiome.Rcheck/00install.out’ for details. + Running examples in ‘braidReports-Ex.R’ failed + The error most likely occurred in: + + > ### Name: makeBRAIDreport + > ### Title: Make a BRAID Report Page + > ### Aliases: makeBRAIDreport + > ### Keywords: hplot + > + > ### ** Examples + > + ... + 22. │ └─grid::convertUnit(short, "cm", valueOnly = TRUE) + 23. │ ├─grid:::upgradeUnit(x) + 24. │ └─grid:::upgradeUnit.default(x) + 25. │ └─base::stop("Not a unit object") + 26. └─base::.handleSimpleError(``, "Not a unit object", base::quote(upgradeUnit.default(x))) + 27. └─rlang (local) h(simpleError(msg, call)) + 28. └─handlers[[1L]](cnd) + 29. └─cli::cli_abort(...) + 30. └─rlang::abort(...) + Execution halted ``` -# CohortPlat +# brolgar
-* Version: 1.0.5 -* GitHub: NA -* Source code: https://github.com/cran/CohortPlat -* Date/Publication: 2022-02-14 09:30:02 UTC -* Number of recursive dependencies: 82 +* Version: 1.0.1 +* GitHub: https://github.com/njtierney/brolgar +* Source code: https://github.com/cran/brolgar +* Date/Publication: 2024-05-10 14:50:34 UTC +* Number of recursive dependencies: 101 -Run `revdepcheck::cloud_details(, "CohortPlat")` for more info +Run `revdepcheck::cloud_details(, "brolgar")` for more info
@@ -1316,100 +1742,120 @@ Run `revdepcheck::cloud_details(, "CohortPlat")` for more info * checking examples ... ERROR ``` - Running examples in ‘CohortPlat-Ex.R’ failed + Running examples in ‘brolgar-Ex.R’ failed The error most likely occurred in: - > ### Name: plot_trial - > ### Title: Plots the cohort trial study overview given stage data. - > ### Aliases: plot_trial + > ### Name: facet_sample + > ### Title: Facet data into groups to facilitate exploration + > ### Aliases: facet_sample > > ### ** Examples > - > - ... - + sr_drugs_pos = sr_drugs_pos, target_rr = target_rr, sharing_type = sharing_type, - + safety_prob = safety_prob, Bayes_Sup = Bayes_Sup, prob_rr_transform = prob_rr_transform, - + cohort_offset = cohort_offset, Bayes_Fut = Bayes_Fut, sr_first_pos = sr_first_pos - + ) - > - > plot_trial(res_list, unit = "n") - Error in compute_geom_2(..., self = self) : - argument "theme" is missing, with no default - Calls: plot_trial ... use_defaults -> eval_from_theme -> %||% -> calc_element + > library(ggplot2) + > ggplot(heights, + + aes(x = year, + + y = height_cm, + + group = country)) + + + geom_line() + + + facet_sample() + Error in if (params$as.table) { : argument is of length zero + Calls: ... -> setup -> -> compute_layout Execution halted ``` * checking running R code from vignettes ... ERROR ``` Errors in running code in vignettes: - when running code in ‘my-vignette.Rmd’ + when running code in ‘exploratory-modelling.Rmd’ ... + + 0) + Warning in is.na(non_null_default_aes[[aes_param_name]]) : + is.na() applied to non-(list or vector) of type 'language' - > set.seed(50) - - > ocs1 <- trial_ocs(n_int = n_int, n_fin = n_fin, rr_comb = rr_comb, - + rr_mono = rr_mono, rr_back = rr_back, rr_plac = rr_plac, - + rr_transfo .... [TRUNCATED] - - When sourcing ‘my-vignette.R’: - Error: argument "theme" is missing, with no default + When sourcing ‘exploratory-modelling.R’: + Error: ℹ In index: 1. + Caused by error in `aes_param_name %in% names(non_null_default_aes) && is.na(non_null_default_aes[[ + ... + Error: argument is of length zero Execution halted - ‘my-vignette.Rmd’ using ‘UTF-8’... failed + ‘exploratory-modelling.Rmd’ using ‘UTF-8’... failed + ‘finding-features.Rmd’ using ‘UTF-8’... failed + ‘getting-started.Rmd’ using ‘UTF-8’... failed + ‘id-interesting-obs.Rmd’ using ‘UTF-8’... OK + ‘longitudinal-data-structures.Rmd’ using ‘UTF-8’... OK + ‘mixed-effects-models.Rmd’ using ‘UTF-8’... failed + ‘visualisation-gallery.Rmd’ using ‘UTF-8’... failed ``` * checking re-building of vignette outputs ... NOTE ``` Error(s) in re-building vignettes: - ... - --- re-building ‘my-vignette.Rmd’ using rmarkdown - - Quitting from lines at lines 1043-1073 [unnamed-chunk-20] (my-vignette.Rmd) - Error: processing vignette 'my-vignette.Rmd' failed with diagnostics: - argument "theme" is missing, with no default - --- failed re-building ‘my-vignette.Rmd’ + --- re-building ‘exploratory-modelling.Rmd’ using rmarkdown - SUMMARY: processing the following file failed: - ‘my-vignette.Rmd’ + Quitting from lines 47-56 [use-gg-highlight] (exploratory-modelling.Rmd) + Error: processing vignette 'exploratory-modelling.Rmd' failed with diagnostics: + ℹ In index: 1. + Caused by error in `aes_param_name %in% names(non_null_default_aes) && is.na(non_null_default_aes[[ + aes_param_name]])`: + ! 'length = 2' in coercion to 'logical(1)' + --- failed re-building ‘exploratory-modelling.Rmd’ - Error: Vignette re-building failed. - Execution halted + --- re-building ‘finding-features.Rmd’ using rmarkdown ``` -# CompAREdesign +# calendR
-* Version: 2.3.1 +* Version: 1.2 * GitHub: NA -* Source code: https://github.com/cran/CompAREdesign -* Date/Publication: 2024-02-15 13:00:02 UTC -* Number of recursive dependencies: 90 +* Source code: https://github.com/cran/calendR +* Date/Publication: 2023-10-05 17:30:02 UTC +* Number of recursive dependencies: 52 -Run `revdepcheck::cloud_details(, "CompAREdesign")` for more info +Run `revdepcheck::cloud_details(, "calendR")` for more info
## Newly broken -* checking whether package ‘CompAREdesign’ can be installed ... WARNING +* checking examples ... ERROR ``` - Found the following significant warnings: - Warning: replacing previous import ‘ggplot2::ggpar’ by ‘ggpubr::ggpar’ when loading ‘CompAREdesign’ - See ‘/tmp/workdir/CompAREdesign/new/CompAREdesign.Rcheck/00install.out’ for details. + Running examples in ‘calendR-Ex.R’ failed + The error most likely occurred in: + + > ### Name: calendR + > ### Title: Monthly and yearly calendars + > ### Aliases: calendR + > + > ### ** Examples + > + > # Calendar of the current year + ... + Backtrace: + ▆ + 1. ├─base (local) ``(x) + 2. └─ggplot2:::print.ggplot(x) + 3. ├─ggplot2::ggplot_gtable(data) + 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) + 5. └─ggplot2::calc_element("plot.margin", theme) + 6. └─cli::cli_abort(...) + 7. └─rlang::abort(...) + Execution halted ``` -# CoreMicrobiomeR +# calendRio
-* Version: 0.1.0 +* Version: 0.2.0 * GitHub: NA -* Source code: https://github.com/cran/CoreMicrobiomeR -* Date/Publication: 2024-04-03 20:03:02 UTC -* Number of recursive dependencies: 91 +* Source code: https://github.com/cran/calendRio +* Date/Publication: 2022-03-10 07:50:02 UTC +* Number of recursive dependencies: 52 -Run `revdepcheck::cloud_details(, "CoreMicrobiomeR")` for more info +Run `revdepcheck::cloud_details(, "calendRio")` for more info
@@ -1417,89 +1863,88 @@ Run `revdepcheck::cloud_details(, "CoreMicrobiomeR")` for more info * checking examples ... ERROR ``` - Running examples in ‘CoreMicrobiomeR-Ex.R’ failed + Running examples in ‘calendRio-Ex.R’ failed The error most likely occurred in: - > ### Name: group_bar_plots - > ### Title: Grouped Bar Plots Based on Sample Size - > ### Aliases: group_bar_plots + > ### Name: calendR + > ### Title: Monthly and yearly calendars + > ### Aliases: calendR > > ### ** Examples > - > #To run input data + > # Calendar of the current year ... - + ) - Warning encountered during diversity analysis:you have empty rows: their dissimilarities may be - meaningless in method “bray” - > #To run grouped bar plot function - > plot_group_bar <- group_bar_plots(core_1$final_otu_table_bef_filter, - + core_1$final_otu_aft_filter, 10) - Error in compute_geom_2(..., self = self) : - argument "theme" is missing, with no default - Calls: group_bar_plots ... use_defaults -> eval_from_theme -> %||% -> calc_element + Backtrace: + ▆ + 1. ├─base (local) ``(x) + 2. └─ggplot2:::print.ggplot(x) + 3. ├─ggplot2::ggplot_gtable(data) + 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) + 5. └─ggplot2::calc_element("plot.margin", theme) + 6. └─cli::cli_abort(...) + 7. └─rlang::abort(...) Execution halted ``` -# correlationfunnel +# capm
-* Version: 0.2.0 -* GitHub: https://github.com/business-science/correlationfunnel -* Source code: https://github.com/cran/correlationfunnel -* Date/Publication: 2020-06-09 04:40:03 UTC -* Number of recursive dependencies: 117 +* Version: 0.14.0 +* GitHub: NA +* Source code: https://github.com/cran/capm +* Date/Publication: 2019-10-24 16:50:05 UTC +* Number of recursive dependencies: 61 -Run `revdepcheck::cloud_details(, "correlationfunnel")` for more info +Run `revdepcheck::cloud_details(, "capm")` for more info
## Newly broken -* checking tests ... ERROR +* checking examples ... ERROR ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(dplyr) - - Attaching package: 'dplyr' - - The following object is masked from 'package:testthat': - - ... - 10. └─ggplot2 (local) compute_geom_2(..., self = self) - 11. └─self$geom$use_defaults(data, self$aes_params, modifiers, theme = theme) - 12. └─ggplot2 (local) use_defaults(..., self = self) - 13. └─ggplot2:::eval_from_theme(default_aes, theme) - 14. ├─calc_element("geom", theme) %||% .default_geom_element - 15. └─ggplot2::calc_element("geom", theme) - - [ FAIL 1 | WARN 3 | SKIP 0 | PASS 17 ] - Error: Test failures - Execution halted + Running examples in ‘capm-Ex.R’ failed + The error most likely occurred in: + + > ### Name: PlotPopPyramid + > ### Title: Population PlotPopPyramid + > ### Aliases: PlotPopPyramid + > + > ### ** Examples + > + > data(dogs) + ... + Backtrace: + ▆ + 1. ├─base (local) ``(x) + 2. └─ggplot2:::print.ggplot(x) + 3. ├─ggplot2::ggplot_gtable(data) + 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) + 5. └─ggplot2::calc_element("plot.margin", theme) + 6. └─cli::cli_abort(...) + 7. └─rlang::abort(...) + Execution halted ``` ## In both -* checking dependencies in R code ... NOTE +* checking data for non-ASCII characters ... NOTE ``` - Namespace in Imports field not imported from: ‘utils’ - All declared Imports should be used. + Note: found 59 marked UTF-8 strings ``` -# corrViz +# cartograflow
-* Version: 0.1.0 -* GitHub: NA -* Source code: https://github.com/cran/corrViz -* Date/Publication: 2023-06-30 11:40:07 UTC -* Number of recursive dependencies: 140 +* Version: 1.0.5 +* GitHub: https://github.com/fbahoken/cartogRaflow +* Source code: https://github.com/cran/cartograflow +* Date/Publication: 2023-10-17 22:40:21 UTC +* Number of recursive dependencies: 102 -Run `revdepcheck::cloud_details(, "corrViz")` for more info +Run `revdepcheck::cloud_details(, "cartograflow")` for more info
@@ -1507,86 +1952,90 @@ Run `revdepcheck::cloud_details(, "corrViz")` for more info * checking examples ... ERROR ``` - Running examples in ‘corrViz-Ex.R’ failed + Running examples in ‘cartograflow-Ex.R’ failed The error most likely occurred in: - > ### Name: animSolar - > ### Title: animSolar - > ### Aliases: animSolar + > ### Name: flowgini + > ### Title: Analysis of flow concentration (Gini coefficient) + > ### Aliases: flowgini > > ### ** Examples > - > cm <- cor(mtcars) + > library(cartograflow) ... - ℹ Please consider using `annotate()` or provide this layer with data containing - a single row. - Warning in geom_text(data = solar_system, aes(x = 0, y = 0, label = sun), : - All aesthetics have length 1, but the data has 250 rows. - ℹ Please consider using `annotate()` or provide this layer with data containing - a single row. - Error in compute_geom_2(..., self = self) : - argument "theme" is missing, with no default - Calls: animSolar ... use_defaults -> eval_from_theme -> %||% -> calc_element + ℹ Use `flowcum` instead. + Warning: Use of `x$linkcum` is discouraged. + ℹ Use `linkcum` instead. + Warning: Use of `x$flowcum` is discouraged. + ℹ Use `flowcum` instead. + Warning: Use of `x$flowcum` is discouraged. + ℹ Use `flowcum` instead. + Error in pm[[2]] : subscript out of bounds + Calls: flowgini ... %>% -> layout -> ggplotly -> ggplotly.ggplot -> gg2list Execution halted ``` -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘corrViz.Rmd’ - ... - > library(corrViz) - - > cm <- cor(mtcars) - - > corrHeatmap(mat = cm, display = "all", reorder = TRUE, - + pal = colorRampPalette(c("darkblue", "white", "darkred"))(100)) - - When sourcing ‘corrViz.R’: - Error: argument "theme" is missing, with no default - Execution halted - - ‘corrViz.Rmd’ using ‘UTF-8’... failed - ``` +# cats -* checking re-building of vignette outputs ... NOTE +
+ +* Version: 1.0.2 +* GitHub: NA +* Source code: https://github.com/cran/cats +* Date/Publication: 2022-03-11 10:20:07 UTC +* Number of recursive dependencies: 83 + +Run `revdepcheck::cloud_details(, "cats")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR ``` - Error(s) in re-building vignettes: - ... - --- re-building ‘corrViz.Rmd’ using rmarkdown - - Quitting from lines at lines 76-81 [heatmap] (corrViz.Rmd) - Error: processing vignette 'corrViz.Rmd' failed with diagnostics: - argument "theme" is missing, with no default - --- failed re-building ‘corrViz.Rmd’ - - SUMMARY: processing the following file failed: - ‘corrViz.Rmd’ + Running examples in ‘cats-Ex.R’ failed + The error most likely occurred in: - Error: Vignette re-building failed. + > ### Name: trial_ocs + > ### Title: Calculates the operating characteristics of the cohort trial + > ### Aliases: trial_ocs + > + > ### ** Examples + > + > + ... + + safety_prob = safety_prob, Bayes_Sup1 = Bayes_Sup1, Bayes_Sup2 = Bayes_Sup2, + + cohort_offset = cohort_offset, sr_first_pos = sr_first_pos, + + missing_prob = missing_prob, cohort_fixed = cohort_fixed, accrual_type = accrual_type, + + accrual_param = accrual_param, hist_lag = hist_lag, analysis_times = analysis_times, + + time_trend = time_trend, cohorts_start = cohorts_start, cohorts_sim = cohorts_sim, + + iter = 2, coresnum = 1, save = FALSE, ret_list = TRUE, plot_ocs = TRUE + + ) + Error in pm[[2]] : subscript out of bounds + Calls: trial_ocs -> -> ggplotly.ggplot -> gg2list Execution halted ``` ## In both -* checking installed package size ... NOTE +* checking dependencies in R code ... NOTE ``` - installed size is 7.2Mb - sub-directories of 1Mb or more: - doc 6.7Mb + Namespaces in Imports field not imported from: + ‘epitools’ ‘forcats’ ‘purrr’ + All declared Imports should be used. ``` -# covidcast +# cheem
-* Version: 0.5.2 -* GitHub: https://github.com/cmu-delphi/covidcast -* Source code: https://github.com/cran/covidcast -* Date/Publication: 2023-07-12 23:40:06 UTC -* Number of recursive dependencies: 93 +* Version: 0.4.0.0 +* GitHub: https://github.com/nspyrison/cheem +* Source code: https://github.com/cran/cheem +* Date/Publication: 2023-11-08 21:30:02 UTC +* Number of recursive dependencies: 152 -Run `revdepcheck::cloud_details(, "covidcast")` for more info +Run `revdepcheck::cloud_details(, "cheem")` for more info
@@ -1598,249 +2047,179 @@ Run `revdepcheck::cloud_details(, "covidcast")` for more info Running the tests in ‘tests/testthat.R’ failed. Complete output: > library(testthat) - > library(covidcast) - We encourage COVIDcast API users to register on our mailing list: - https://lists.andrew.cmu.edu/mailman/listinfo/delphi-covidcast-api - We'll send announcements about new data sources, package updates, - server maintenance, and new features. - > + > library(cheem) + -------------------------------------------------------- + cheem --- version 0.4.0.0 + Please share bugs, suggestions, and feature requests at: + https://github.com/nspyrison/cheem/issues/ + -------------------------------------------------------- ... - • plot/default-county-choropleth.svg - • plot/default-hrr-choropleth-with-include.svg - • plot/default-msa-choropleth-with-include.svg - • plot/default-state-choropleth-with-include.svg - • plot/default-state-choropleth-with-range.svg - • plot/state-choropleth-with-no-metadata.svg - • plot/state-line-graph-with-range.svg - • plot/state-line-graph-with-stderrs.svg + 13. │ ├─utils::modifyList(x %||% list(), y %||% list(), ...) + 14. │ │ └─base::stopifnot(is.list(x), is.list(val)) + 15. │ └─x %||% list() + 16. ├─plotly::ggplotly(...) + 17. └─plotly:::ggplotly.ggplot(...) + 18. └─plotly::gg2list(...) + + [ FAIL 1 | WARN 0 | SKIP 0 | PASS 10 ] Error: Test failures Execution halted ``` +## In both + * checking running R code from vignettes ... ERROR ``` Errors in running code in vignettes: - when running code in ‘multi-signals.Rmd’ + when running code in ‘getting-started-with-cheem.Rmd’ ... - > signals <- covidcast_signals(data_source = "jhu-csse", - + signal = c("confirmed_7dav_incidence_prop", "deaths_7dav_incidence_prop"), - + star .... [TRUNCATED] + > knitr::opts_chunk$set(echo = TRUE, include = TRUE, + + results = "show", eval = FALSE, message = FALSE, warning = FALSE, + + error = FALSE, co .... [TRUNCATED] - When sourcing ‘multi-signals.R’: - Error: Rate limit exceeded when fetching data from API anonymously. See the "API keys" section of the `covidcast_signal()` documentation for information on registering for an API key. - ... - Error: Rate limit exceeded when fetching data from API anonymously. See the "API keys" section of the `covidcast_signal()` documentation for information on registering for an API key. - ℹ Message from server: - ℹ Rate limit exceeded for anonymous queries. To remove this limit, register a free API key at https://api.delphi.cmu.edu/epidata/admin/registration_form + > knitr::include_graphics("../inst/shiny_apps/cheem/www/lime_nonlinear.png") + + When sourcing ‘getting-started-with-cheem.R’: + Error: Cannot find the file(s): "../inst/shiny_apps/cheem/www/lime_nonlinear.png" Execution halted - ‘correlation-utils.Rmd’ using ‘UTF-8’... OK - ‘covidcast.Rmd’ using ‘UTF-8’... OK - ‘external-data.Rmd’ using ‘UTF-8’... OK - ‘multi-signals.Rmd’ using ‘UTF-8’... failed - ‘plotting-signals.Rmd’ using ‘UTF-8’... failed + ‘getting-started-with-cheem.Rmd’ using ‘UTF-8’... failed ``` -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘correlation-utils.Rmd’ using rmarkdown - --- finished re-building ‘correlation-utils.Rmd’ - - --- re-building ‘covidcast.Rmd’ using rmarkdown - - Quitting from lines at lines 38-45 [unnamed-chunk-1] (covidcast.Rmd) - Error: processing vignette 'covidcast.Rmd' failed with diagnostics: - Rate limit exceeded when fetching data from API anonymously. See the "API keys" section of the `covidcast_signal()` documentation for information on registering for an API key. - ℹ Message from server: - ℹ Rate limit exceeded for anonymous queries. To remove this limit, register a free API key at https://api.delphi.cmu.edu/epidata/admin/registration_form - --- failed re-building ‘covidcast.Rmd’ - - --- re-building ‘external-data.Rmd’ using rmarkdown - ``` +# chillR -## In both +
-* checking data for non-ASCII characters ... NOTE +* Version: 0.75 +* GitHub: NA +* Source code: https://github.com/cran/chillR +* Date/Publication: 2023-11-27 22:20:02 UTC +* Number of recursive dependencies: 139 + +Run `revdepcheck::cloud_details(, "chillR")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR ``` - Note: found 20 marked UTF-8 strings + Running examples in ‘chillR-Ex.R’ failed + The error most likely occurred in: + + > ### Name: plot_scenarios + > ### Title: Plot historic and future scenarios for climate-related metrics + > ### ('ggplot2' version) + > ### Aliases: plot_scenarios + > + > ### ** Examples + > + ... + > + > # Plot the climate scenarios + > + > plot_scenarios(climate_scenario_list, metric = 'Chill_Portions', + + add_historic = TRUE, size = 2, shape = 3, color = 'blue', + + outlier_shape = 12, historic_color = 'skyblue', + + group_by = c("Year", "Scenario")) + Error in identicalUnits(x) : object is not a unit + Calls: ... assemble_guides -> guides_build -> unit.c -> identicalUnits + Execution halted ``` -# Coxmos +# chronicle
-* Version: 1.0.2 -* GitHub: https://github.com/BiostatOmics/Coxmos -* Source code: https://github.com/cran/Coxmos -* Date/Publication: 2024-03-25 20:32:38 UTC -* Number of recursive dependencies: 204 +* Version: 0.3 +* GitHub: NA +* Source code: https://github.com/cran/chronicle +* Date/Publication: 2021-06-25 05:00:02 UTC +* Number of recursive dependencies: 146 -Run `revdepcheck::cloud_details(, "Coxmos")` for more info +Run `revdepcheck::cloud_details(, "chronicle")` for more info
## Newly broken -* checking Rd files ... WARNING +* checking examples ... ERROR ``` - prepare_Rd: replacing previous import ‘ggplot2::ggpar’ by ‘ggpubr::ggpar’ when loading ‘survminer’ + Running examples in ‘chronicle-Ex.R’ failed + The error most likely occurred in: + + > ### Name: make_barplot + > ### Title: Create a bar plot from a data frame through ggplotly + > ### Aliases: make_barplot + > + > ### ** Examples + > + > make_barplot(dt = iris, bars = 'Species', value = 'Sepal.Length') + Error in pm[[2]] : subscript out of bounds + Calls: make_barplot -> -> ggplotly.ggplot -> gg2list + Execution halted ``` -## In both - * checking running R code from vignettes ... ERROR ``` Errors in running code in vignettes: - when running code in ‘Coxmos-pipeline.Rmd’ + when running code in ‘chronicle.Rmd’ ... - Warning in data("X_proteomic") : data set ‘X_proteomic’ not found - - > data("Y_proteomic") - Warning in data("Y_proteomic") : data set ‘Y_proteomic’ not found + + filename = "quick_demo", title = "A quick chronicle demo", + + author = .... [TRUNCATED] - > X <- X_proteomic + Quitting from lines 34-46 [unnamed-chunk-3] (quick_demo.Rmd) - When sourcing ‘Coxmos-pipeline.R’: - Error: object 'X_proteomic' not found + When sourcing ‘chronicle.R’: + Error: ℹ In index: 1. + Caused by error in `pm[[2]]`: + ! subscript out of bounds Execution halted - ‘Coxmos-MO-pipeline.Rmd’ using ‘UTF-8’... OK - ‘Coxmos-pipeline.Rmd’ using ‘UTF-8’... failed + ‘chronicle.Rmd’ using ‘UTF-8’... failed ``` -* checking installed package size ... NOTE - ``` - installed size is 6.5Mb - sub-directories of 1Mb or more: - data 2.1Mb - doc 2.9Mb +* checking re-building of vignette outputs ... NOTE ``` - -# crosshap - -
- -* Version: 1.4.0 -* GitHub: https://github.com/jacobimarsh/crosshap -* Source code: https://github.com/cran/crosshap -* Date/Publication: 2024-03-31 15:40:02 UTC -* Number of recursive dependencies: 117 - -Run `revdepcheck::cloud_details(, "crosshap")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘crosshap-Ex.R’ failed - The error most likely occurred in: + Error(s) in re-building vignettes: + ... + --- re-building ‘chronicle.Rmd’ using rmarkdown - > ### Name: build_bot_halfeyeplot - > ### Title: Bot hap-pheno raincloud plot - > ### Aliases: build_bot_halfeyeplot - > - > ### ** Examples - > - > - ... - 12. │ └─ggplot2 (local) f(l = layers[[i]], d = data[[i]]) - 13. │ └─l$compute_geom_2(d, theme = plot$theme) - 14. │ └─ggplot2 (local) compute_geom_2(..., self = self) - 15. │ └─self$geom$use_defaults(data, self$aes_params, modifiers, theme = theme) - 16. └─base::.handleSimpleError(...) - 17. └─rlang (local) h(simpleError(msg, call)) - 18. └─handlers[[1L]](cnd) - 19. └─cli::cli_abort(...) - 20. └─rlang::abort(...) + Quitting from lines 38-67 [unnamed-chunk-3] (chronicle.Rmd) + Error: processing vignette 'chronicle.Rmd' failed with diagnostics: + ℹ In index: 1. + Caused by error in `pm[[2]]`: + ! subscript out of bounds + --- failed re-building ‘chronicle.Rmd’ + + SUMMARY: processing the following file failed: + ‘chronicle.Rmd’ + + Error: Vignette re-building failed. Execution halted ``` -# csa - -
- -* Version: 0.7.1 -* GitHub: https://github.com/imarkonis/csa -* Source code: https://github.com/cran/csa -* Date/Publication: 2023-10-24 13:40:11 UTC -* Number of recursive dependencies: 95 - -Run `revdepcheck::cloud_details(, "csa")` for more info - -
- -## Newly broken - -* checking whether package ‘csa’ can be installed ... WARNING - ``` - Found the following significant warnings: - Warning: replacing previous import ‘ggplot2::ggpar’ by ‘ggpubr::ggpar’ when loading ‘csa’ - See ‘/tmp/workdir/csa/new/csa.Rcheck/00install.out’ for details. - ``` - -# ctrialsgov - -
- -* Version: 0.2.5 -* GitHub: NA -* Source code: https://github.com/cran/ctrialsgov -* Date/Publication: 2021-10-18 16:00:02 UTC -* Number of recursive dependencies: 100 - -Run `revdepcheck::cloud_details(, "ctrialsgov")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(ctrialsgov) - > - > test_check("ctrialsgov") - [NCT04553939] ible Local Advanved |Bladder| Cancer - [NCT03517995] of Sulforaphane in |Bladder| Cancer Chemoprevent - [NCT04210479] Comparison of |Bladder| Filling vs. Non-Fil - ... - 10. └─ggplot2 (local) compute_geom_2(..., self = self) - 11. └─self$geom$use_defaults(data, self$aes_params, modifiers, theme = theme) - 12. └─ggplot2 (local) use_defaults(..., self = self) - 13. └─ggplot2:::eval_from_theme(default_aes, theme) - 14. ├─calc_element("geom", theme) %||% .default_geom_element - 15. └─ggplot2::calc_element("geom", theme) - - [ FAIL 1 | WARN 6 | SKIP 0 | PASS 43 ] - Error: Test failures - Execution halted - ``` - ## In both -* checking data for non-ASCII characters ... NOTE +* checking dependencies in R code ... NOTE ``` - Note: found 1350 marked UTF-8 strings + Namespaces in Imports field not imported from: + ‘DT’ ‘dplyr’ ‘prettydoc’ ‘rmdformats’ ‘skimr’ + All declared Imports should be used. ``` -# cubble +# circumplex
-* Version: 0.3.0 -* GitHub: https://github.com/huizezhang-sherry/cubble -* Source code: https://github.com/cran/cubble -* Date/Publication: 2023-06-30 03:40:02 UTC -* Number of recursive dependencies: 144 +* Version: 0.3.10 +* GitHub: https://github.com/jmgirard/circumplex +* Source code: https://github.com/cran/circumplex +* Date/Publication: 2023-08-22 07:20:05 UTC +* Number of recursive dependencies: 101 -Run `revdepcheck::cloud_details(, "cubble")` for more info +Run `revdepcheck::cloud_details(, "circumplex")` for more info
@@ -1849,64 +2228,41 @@ Run `revdepcheck::cloud_details(, "cubble")` for more info * checking running R code from vignettes ... ERROR ``` Errors in running code in vignettes: - when running code in ‘cb6interactive.Rmd’ + when running code in ‘introduction-to-ssm-analysis.Rmd’ ... - + y .... [TRUNCATED] - Warning: Using `size` aesthetic for lines was deprecated in ggplot2 3.4.0. - ℹ Please use `linewidth` instead. + + "BC", "DE", "FG", "HI", "JK", "LM", "NO"), levels = c("PA", + + "BC", "DE", "FG", "HI ..." ... [TRUNCATED] - > ts_interactive <- ggplotly(ts_static, width = 600, - + height = 300) %>% highlight(on = "plotly_selected", opacityDim = 0.012) + > ggplot2::ggplot(dat_r, ggplot2::aes(x = Angle, y = est)) + + + ggplot2::geom_hline(yintercept = 0, size = 1.25, color = "darkgray") + + + ggpl .... [TRUNCATED] - ... - When sourcing ‘cb6interactive.R’: - Error: argument "theme" is missing, with no default + When sourcing ‘introduction-to-ssm-analysis.R’: + Error: Theme element `plot.margin` must have class . Execution halted - ‘cb1class.Rmd’ using ‘UTF-8’... OK - ‘cb2create.Rmd’ using ‘UTF-8’... OK - ‘cb3tsibblesf.Rmd’ using ‘UTF-8’... OK - ‘cb4glyph.Rmd’ using ‘UTF-8’... OK - ‘cb5match.Rmd’ using ‘UTF-8’... OK - ‘cb6interactive.Rmd’ using ‘UTF-8’... failed + ‘intermediate-ssm-analysis.Rmd’ using ‘UTF-8’... OK + ‘introduction-to-ssm-analysis.Rmd’ using ‘UTF-8’... failed + ‘using-instruments.Rmd’ using ‘UTF-8’... OK ``` * checking re-building of vignette outputs ... NOTE ``` Error(s) in re-building vignettes: - --- re-building ‘cb1class.Rmd’ using rmarkdown - --- finished re-building ‘cb1class.Rmd’ - - --- re-building ‘cb2create.Rmd’ using rmarkdown - --- finished re-building ‘cb2create.Rmd’ - - --- re-building ‘cb3tsibblesf.Rmd’ using rmarkdown - --- finished re-building ‘cb3tsibblesf.Rmd’ - - --- re-building ‘cb4glyph.Rmd’ using rmarkdown - ``` - -## In both - -* checking installed package size ... NOTE - ``` - installed size is 5.5Mb - sub-directories of 1Mb or more: - data 3.0Mb - doc 1.3Mb + --- re-building ‘intermediate-ssm-analysis.Rmd’ using rmarkdown ``` -# dafishr +# cities
-* Version: 1.0.0 -* GitHub: https://github.com/CBMC-GCMP/dafishr -* Source code: https://github.com/cran/dafishr -* Date/Publication: 2022-12-06 13:10:02 UTC -* Number of recursive dependencies: 114 +* Version: 0.1.3 +* GitHub: NA +* Source code: https://github.com/cran/cities +* Date/Publication: 2023-08-08 07:50:10 UTC +* Number of recursive dependencies: 85 -Run `revdepcheck::cloud_details(, "dafishr")` for more info +Run `revdepcheck::cloud_details(, "cities")` for more info
@@ -1914,95 +2270,106 @@ Run `revdepcheck::cloud_details(, "dafishr")` for more info * checking examples ... ERROR ``` - Running examples in ‘dafishr-Ex.R’ failed + Running examples in ‘cities-Ex.R’ failed The error most likely occurred in: - > ### Name: join_mpa_data - > ### Title: Detect fishing vessel presence within Marine Protected Areas - > ### polygons in Mexico - > ### Aliases: join_mpa_data + > ### Name: plot_dc + > ### Title: plot_dc + > ### Aliases: plot_dc > > ### ** Examples > + > total_data = 3 ... - 17. └─ggplot2 (local) FUN(X[[i]], ...) - 18. └─g$draw_key(data, g$params, key_size) - 19. └─ggplot2 (local) draw_key(...) - 20. └─ggplot2::draw_key_point(data, params, size) - 21. ├─grid::pointsGrob(...) - 22. │ └─grid::grob(...) - 23. └─ggplot2::ggpar(...) - 24. └─rlang:::Ops.quosure(pointsize, .pt) - 25. └─rlang::abort(...) + ▆ + 1. └─cities::plot_estimates(...) + 2. ├─base::print(p_estimands) + 3. └─ggplot2:::print.ggplot(p_estimands) + 4. ├─ggplot2::ggplot_gtable(data) + 5. └─ggplot2:::ggplot_gtable.ggplot_built(data) + 6. └─ggplot2::calc_element("plot.margin", theme) + 7. └─cli::cli_abort(...) + 8. └─rlang::abort(...) Execution halted ``` -## In both - -* checking installed package size ... NOTE +* checking running R code from vignettes ... ERROR ``` - installed size is 7.9Mb - sub-directories of 1Mb or more: - data 7.6Mb + Errors in running code in vignettes: + when running code in ‘CITIES_demo.Rmd’ + ... + | + |==================================================| 100% + > estimates_out = plot_estimates(data_out = data_out, + + total_data = total_data, timepoints = timepoints, reference_id = reference_id, + + IR_ .... [TRUNCATED] + Warning: Using shapes for an ordinal variable is not advised + + When sourcing ‘CITIES_demo.R’: + Error: Theme element `plot.margin` must have class . + Execution halted + + ‘CITIES_demo.Rmd’ using ‘UTF-8’... failed ``` -* checking data for non-ASCII characters ... NOTE +* checking re-building of vignette outputs ... NOTE ``` - Note: found 2020 marked UTF-8 strings + Error(s) in re-building vignettes: + --- re-building ‘CITIES_demo.Rmd’ using rmarkdown ``` -# damAOI +# CleaningValidation
-* Version: 0.0 -* GitHub: NA -* Source code: https://github.com/cran/damAOI -* Date/Publication: 2024-02-07 18:00:02 UTC -* Number of recursive dependencies: 101 +* Version: 1.0 +* GitHub: https://github.com/ChandlerXiandeYang/CleaningValidation +* Source code: https://github.com/cran/CleaningValidation +* Date/Publication: 2024-05-17 09:10:21 UTC +* Number of recursive dependencies: 79 -Run `revdepcheck::cloud_details(, "damAOI")` for more info +Run `revdepcheck::cloud_details(, "CleaningValidation")` for more info
## Newly broken -* checking running R code from vignettes ... ERROR +* checking examples ... ERROR ``` - Errors in running code in vignettes: - when running code in ‘damAOI.Rmd’ - ... - + ggplot2::aes(fill = as.factor(area)), alpha = 0.3) + ggplot2::geom_sf(data = bufferandcli .... [TRUNCATED] - - When sourcing ‘damAOI.R’: - Error: Summary operations are not defined for quosures. Do you need to unquote - the quosure? - - # Bad: min(myquosure) + Running examples in ‘CleaningValidation-Ex.R’ failed + The error most likely occurred in: - # Good: min(!!myquosure) + > ### Name: cv16_u_chart + > ### Title: Create a u-Chart for Poisson-distributed Data + > ### Aliases: cv16_u_chart + > + > ### ** Examples + > + > cv16_u_chart(data = Eq_Mic, residue_col = "Mic", cleaning_event_col = "CleaningEvent") + ... + Backtrace: + ▆ + 1. ├─base (local) ``(x) + 2. └─ggplot2:::print.ggplot(x) + 3. ├─ggplot2::ggplot_gtable(data) + 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) + 5. └─ggplot2::calc_element("plot.margin", theme) + 6. └─cli::cli_abort(...) + 7. └─rlang::abort(...) Execution halted - - ‘damAOI.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘damAOI.Rmd’ using rmarkdown ``` -# deeptime +# clinDataReview
-* Version: 1.1.1 -* GitHub: https://github.com/willgearty/deeptime -* Source code: https://github.com/cran/deeptime -* Date/Publication: 2024-03-08 17:10:10 UTC -* Number of recursive dependencies: 181 +* Version: 1.5.2 +* GitHub: https://github.com/openanalytics/clinDataReview +* Source code: https://github.com/cran/clinDataReview +* Date/Publication: 2024-05-17 16:30:05 UTC +* Number of recursive dependencies: 130 -Run `revdepcheck::cloud_details(, "deeptime")` for more info +Run `revdepcheck::cloud_details(, "clinDataReview")` for more info
@@ -2010,26 +2377,26 @@ Run `revdepcheck::cloud_details(, "deeptime")` for more info * checking examples ... ERROR ``` - Running examples in ‘deeptime-Ex.R’ failed + Running examples in ‘clinDataReview-Ex.R’ failed The error most likely occurred in: - > ### Name: facet_wrap_color - > ### Title: Wrap a 1d ribbon of panels into 2d with colored strips - > ### Aliases: facet_wrap_color FacetWrapColor - > ### Keywords: datasets + > ### Name: scatterplotClinData + > ### Title: Scatterplot of variables of interest for clinical data + > ### visualization. + > ### Aliases: scatterplotClinData > > ### ** Examples > ... - 6. │ └─ggplot2 (local) setup(..., self = self) - 7. │ └─self$facet$compute_layout(data, self$facet_params) - 8. │ └─ggplot2 (local) compute_layout(..., self = self) - 9. │ └─ggplot2:::wrap_layout(id, dims, params$dir) - 10. │ └─ggplot2:::data_frame0(...) - 11. │ └─vctrs::data_frame(..., .name_repair = "minimal") - 12. └─vctrs:::stop_recycle_incompatible_size(...) - 13. └─vctrs:::stop_vctrs(...) - 14. └─rlang::abort(message, class = c(class, "vctrs_error"), ..., call = call) + + data = dataPlot, + + xVar = "ADY", + + yVar = "LBSTRESN", + + aesPointVar = list(color = "TRTP", fill = "TRTP"), + + aesLineVar = list(group = "USUBJID", color = "TRTP"), + + labelVars = labelVars + + ) + Error in pm[[2]] : subscript out of bounds + Calls: scatterplotClinData -> ggplotly -> ggplotly.ggplot -> gg2list Execution halted ``` @@ -2039,199 +2406,204 @@ Run `revdepcheck::cloud_details(, "deeptime")` for more info Running the tests in ‘tests/testthat.R’ failed. Complete output: > library(testthat) - > library(deeptime) + > library(clinDataReview) > - > test_check("deeptime") - Scale for y is already present. - Adding another scale for y, which will replace the existing scale. - Scale for y is already present. - ... - • gggeo_scale/gggeo-scale-top-new.svg - • gggeo_scale/gggeo-scale-top-old.svg - • points_range/geom-points-range-aes-new.svg - • points_range/geom-points-range-aes-old.svg - • points_range/geom-points-range-bg-new.svg - • points_range/geom-points-range-bg-old.svg - • points_range/geom-points-range-h-new.svg - • points_range/geom-points-range-h-old.svg + > test_check("clinDataReview") + adding: report.html (deflated 63%) + adding: report_dependencies12051d006778/ (stored 0%) + adding: report_dependencies12051d006778/file12056baf983f.html (deflated 8%) + ... + Backtrace: + ▆ + 1. └─clinDataReview::scatterplotClinData(...) at test_scatterplotClinData.R:851:3 + 2. ├─plotly::ggplotly(p = gg, width = width, height = height, tooltip = if (!is.null(hoverVars)) "text") + 3. └─plotly:::ggplotly.ggplot(...) + 4. └─plotly::gg2list(...) + + [ FAIL 25 | WARN 8 | SKIP 30 | PASS 450 ] Error: Test failures Execution halted ``` -# DEGRE - -
- -* Version: 0.2.0 -* GitHub: NA -* Source code: https://github.com/cran/DEGRE -* Date/Publication: 2022-11-02 09:32:57 UTC -* Number of recursive dependencies: 89 - -Run `revdepcheck::cloud_details(, "DEGRE")` for more info - -
+* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + ... + --- re-building ‘clinDataReview-dataPreprocessing.Rmd’ using rmarkdown + --- finished re-building ‘clinDataReview-dataPreprocessing.Rmd’ + + --- re-building ‘clinDataReview-dataVisualization.Rmd’ using rmarkdown + + Quitting from lines 167-208 [timeProfiles] (clinDataReview-dataVisualization.Rmd) + Error: processing vignette 'clinDataReview-dataVisualization.Rmd' failed with diagnostics: + subscript out of bounds + ... + --- failed re-building ‘clinDataReview-dataVisualization.Rmd’ + + --- re-building ‘clinDataReview-reporting.Rmd’ using rmarkdown + --- finished re-building ‘clinDataReview-reporting.Rmd’ + + SUMMARY: processing the following file failed: + ‘clinDataReview-dataVisualization.Rmd’ + + Error: Vignette re-building failed. + Execution halted + ``` -## Newly broken +## In both -* checking whether package ‘DEGRE’ can be installed ... WARNING +* checking installed package size ... NOTE ``` - Found the following significant warnings: - Warning: replacing previous import ‘ggplot2::ggpar’ by ‘ggpubr::ggpar’ when loading ‘DEGRE’ - See ‘/tmp/workdir/DEGRE/new/DEGRE.Rcheck/00install.out’ for details. + installed size is 5.7Mb + sub-directories of 1Mb or more: + doc 4.3Mb ``` -# densityarea +# clinUtils
-* Version: 0.1.0 -* GitHub: https://github.com/JoFrhwld/densityarea -* Source code: https://github.com/cran/densityarea -* Date/Publication: 2023-10-02 10:20:06 UTC -* Number of recursive dependencies: 98 +* Version: 0.2.0 +* GitHub: https://github.com/openanalytics/clinUtils +* Source code: https://github.com/cran/clinUtils +* Date/Publication: 2024-05-17 14:50:06 UTC +* Number of recursive dependencies: 120 -Run `revdepcheck::cloud_details(, "densityarea")` for more info +Run `revdepcheck::cloud_details(, "clinUtils")` for more info
## Newly broken -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘densityarea.Rmd’ using rmarkdown - ``` - -## In both - -* checking running R code from vignettes ... ERROR +* checking running R code from vignettes ... ERROR ``` Errors in running code in vignettes: - when running code in ‘sf-operations.Rmd’ + when running code in ‘clinUtils-vignette.Rmd’ ... - > vowel_intersections <- relocate(mutate(vowel_intersections, - + groups = map_chr(origins, .f = new_label, labels = vowel_polygons$plt_vclass)), - .... [TRUNCATED] - When sourcing ‘sf-operations.R’: - Error: ℹ In argument: `groups = map_chr(origins, .f = new_label, labels = - vowel_polygons$plt_vclass)`. - Caused by error: - ! object 'new_label' not found + layout + + + > listPlotsInteractiveLB <- sapply(listPlotsLB, function(ggplot) ggplotly(ggplot) %>% + + partial_bundle(), simplify = FALSE) + + When sourcing ‘clinUtils-vignette.R’: + Error: subscript out of bounds Execution halted - ‘densityarea.Rmd’ using ‘UTF-8’... OK - ‘sf-operations.Rmd’ using ‘UTF-8’... failed - ``` - -* checking data for non-ASCII characters ... NOTE - ``` - Note: found 2534 marked UTF-8 strings + ‘clinUtils-vignette.Rmd’ using ‘UTF-8’... failed ``` -# did - -
- -* Version: 2.1.2 -* GitHub: https://github.com/bcallaway11/did -* Source code: https://github.com/cran/did -* Date/Publication: 2022-07-20 16:00:05 UTC -* Number of recursive dependencies: 125 - -Run `revdepcheck::cloud_details(, "did")` for more info - -
- -## Newly broken - -* checking whether package ‘did’ can be installed ... WARNING +* checking re-building of vignette outputs ... NOTE ``` - Found the following significant warnings: - Warning: replacing previous import ‘ggplot2::ggpar’ by ‘ggpubr::ggpar’ when loading ‘did’ - See ‘/tmp/workdir/did/new/did.Rcheck/00install.out’ for details. + Error(s) in re-building vignettes: + --- re-building ‘clinUtils-vignette.Rmd’ using rmarkdown ``` -## In both +## Newly fixed * checking running R code from vignettes ... WARNING ``` Errors in running code in vignettes: - when running code in ‘TWFE.Rmd’ + when running code in ‘clinUtils-vignette.Rmd’ ... - > knitr::opts_chunk$set(collapse = TRUE, comment = "#>", - + echo = TRUE, eval = FALSE) - > library(tidyverse) - When sourcing ‘TWFE.R’: - ... - When sourcing ‘pre-testing.R’: - Error: cannot open the connection + + Quitting from lines 2-4 [lab-hist-interactive1] + + When sourcing ‘clinUtils-vignette.R’: + Error: there is no package called 'webshot' Execution halted - ‘TWFE.Rmd’ using ‘UTF-8’... failed - ‘did-basics.Rmd’ using ‘UTF-8’... OK - ‘extensions.Rmd’ using ‘UTF-8’... failed - ‘multi-period-did.Rmd’ using ‘UTF-8’... OK - ‘pre-testing.Rmd’ using ‘UTF-8’... failed + ‘clinUtils-vignette.Rmd’ using ‘UTF-8’... failed ``` -# distributional +## In both + +* checking installed package size ... NOTE + ``` + installed size is 7.7Mb + sub-directories of 1Mb or more: + doc 6.5Mb + ``` + +# ClustImpute
-* Version: 0.4.0 -* GitHub: https://github.com/mitchelloharawild/distributional -* Source code: https://github.com/cran/distributional -* Date/Publication: 2024-02-07 13:30:02 UTC -* Number of recursive dependencies: 64 +* Version: 0.2.4 +* GitHub: NA +* Source code: https://github.com/cran/ClustImpute +* Date/Publication: 2021-05-31 07:40:11 UTC +* Number of recursive dependencies: 121 -Run `revdepcheck::cloud_details(, "distributional")` for more info +Run `revdepcheck::cloud_details(, "ClustImpute")` for more info
## Newly broken -* checking examples ... ERROR +* checking running R code from vignettes ... ERROR ``` - Running examples in ‘distributional-Ex.R’ failed - The error most likely occurred in: + Errors in running code in vignettes: + when running code in ‘Example_on_simulated_data.Rmd’ + ... + > dat4plot$true_clust_fct <- factor(true_clust) - > ### Name: dist_truncated - > ### Title: Truncate a distribution - > ### Aliases: dist_truncated - > - > ### ** Examples - > - > dist <- dist_truncated(dist_normal(2,1), lower = 0) + > p_base <- ggplot(dat4plot, aes(x = x, y = y, color = true_clust_fct)) + + + geom_point() + + > ggExtra::ggMarginal(p_base, groupColour = TRUE, groupFill = TRUE) + + When sourcing ‘Example_on_simulated_data.R’: + Error: Theme element `plot.margin` must have class . + Execution halted + + ‘Example_on_simulated_data.Rmd’ using ‘UTF-8’... failed + ‘description_of_algorithm.Rnw’ using ‘UTF-8’... OK + ``` + +## In both + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘Example_on_simulated_data.Rmd’ using rmarkdown + + Quitting from lines 49-53 [unnamed-chunk-3] (Example_on_simulated_data.Rmd) + Error: processing vignette 'Example_on_simulated_data.Rmd' failed with diagnostics: + Theme element `plot.margin` must have class . + --- failed re-building ‘Example_on_simulated_data.Rmd’ + + --- re-building ‘description_of_algorithm.Rnw’ using Sweave + Error: processing vignette 'description_of_algorithm.Rnw' failed with diagnostics: ... - 12. │ └─ggplot2 (local) f(l = layers[[i]], d = data[[i]]) - 13. │ └─l$compute_geom_2(d, theme = plot$theme) - 14. │ └─ggplot2 (local) compute_geom_2(..., self = self) - 15. │ └─self$geom$use_defaults(data, self$aes_params, modifiers, theme = theme) - 16. └─base::.handleSimpleError(...) - 17. └─rlang (local) h(simpleError(msg, call)) - 18. └─handlers[[1L]](cnd) - 19. └─cli::cli_abort(...) - 20. └─rlang::abort(...) + l.6 \usepackage + {Sweave}^^M + ! ==> Fatal error occurred, no output PDF file produced! + --- failed re-building ‘description_of_algorithm.Rnw’ + + SUMMARY: processing the following files failed: + ‘Example_on_simulated_data.Rmd’ ‘description_of_algorithm.Rnw’ + + Error: Vignette re-building failed. Execution halted ``` -# dittoViz +# cogmapr
-* Version: 1.0.1 -* GitHub: https://github.com/dtm2451/dittoViz -* Source code: https://github.com/cran/dittoViz -* Date/Publication: 2024-02-02 00:00:12 UTC -* Number of recursive dependencies: 99 +* Version: 0.9.3 +* GitHub: NA +* Source code: https://github.com/cran/cogmapr +* Date/Publication: 2022-01-04 15:40:07 UTC +* Number of recursive dependencies: 75 -Run `revdepcheck::cloud_details(, "dittoViz")` for more info +Run `revdepcheck::cloud_details(, "cogmapr")` for more info
@@ -2239,65 +2611,40 @@ Run `revdepcheck::cloud_details(, "dittoViz")` for more info * checking examples ... ERROR ``` - Running examples in ‘dittoViz-Ex.R’ failed + Running examples in ‘cogmapr-Ex.R’ failed The error most likely occurred in: - > ### Name: barPlot - > ### Title: Outputs a stacked bar plot to show the percent composition of - > ### samples, groups, clusters, or other groupings - > ### Aliases: barPlot + > ### Name: ggCMap + > ### Title: Plot a social cognitive map using ggplot2 + > ### Aliases: ggCMap > > ### ** Examples > + > project_name <- "a_new_project" ... - 16 4 D 8 32 0.2500000 - > # through hovering the cursor over the relevant parts of the plot - > if (requireNamespace("plotly", quietly = TRUE)) { - + barPlot(example_df, "clustering", group.by = "groups", - + do.hover = TRUE) - + } - Error in compute_geom_2(..., self = self) : - argument "theme" is missing, with no default - Calls: barPlot ... use_defaults -> eval_from_theme -> %||% -> calc_element + Backtrace: + ▆ + 1. ├─base (local) ``(x) + 2. └─ggplot2:::print.ggplot(x) + 3. ├─ggplot2::ggplot_gtable(data) + 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) + 5. └─ggplot2::calc_element("plot.margin", theme) + 6. └─cli::cli_abort(...) + 7. └─rlang::abort(...) Execution halted ``` -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(dittoViz) - Loading required package: ggplot2 - > test_check("dittoViz") - [ FAIL 12 | WARN 12 | SKIP 0 | PASS 307 ] - - ══ Failed tests ════════════════════════════════════════════════════════════════ - ... - 12. └─ggplot2 (local) compute_geom_2(..., self = self) - 13. └─self$geom$use_defaults(data, self$aes_params, modifiers, theme = theme) - 14. └─ggplot2 (local) use_defaults(..., self = self) - 15. └─ggplot2:::eval_from_theme(default_aes, theme) - 16. ├─calc_element("geom", theme) %||% .default_geom_element - 17. └─ggplot2::calc_element("geom", theme) - - [ FAIL 12 | WARN 12 | SKIP 0 | PASS 307 ] - Error: Test failures - Execution halted - ``` - -# dots +# CohortPlat
-* Version: 0.0.2 -* GitHub: https://github.com/christopherkenny/dots -* Source code: https://github.com/cran/dots -* Date/Publication: 2022-07-15 08:40:07 UTC -* Number of recursive dependencies: 99 +* Version: 1.0.5 +* GitHub: NA +* Source code: https://github.com/cran/CohortPlat +* Date/Publication: 2022-02-14 09:30:02 UTC +* Number of recursive dependencies: 82 -Run `revdepcheck::cloud_details(, "dots")` for more info +Run `revdepcheck::cloud_details(, "CohortPlat")` for more info
@@ -2305,89 +2652,118 @@ Run `revdepcheck::cloud_details(, "dots")` for more info * checking examples ... ERROR ``` - Running examples in ‘dots-Ex.R’ failed + Running examples in ‘CohortPlat-Ex.R’ failed The error most likely occurred in: - > ### Name: dots - > ### Title: Make dot density plots - > ### Aliases: dots + > ### Name: plot_trial + > ### Title: Plots the cohort trial study overview given stage data. + > ### Aliases: plot_trial > > ### ** Examples > - > data('suffolk') + > ... - 17. └─ggplot2 (local) FUN(X[[i]], ...) - 18. └─g$draw_key(data, g$params, key_size) - 19. └─ggplot2 (local) draw_key(...) - 20. └─ggplot2::draw_key_point(data, params, size) - 21. ├─grid::pointsGrob(...) - 22. │ └─grid::grob(...) - 23. └─ggplot2::ggpar(...) - 24. └─rlang:::Ops.quosure(pointsize, .pt) - 25. └─rlang::abort(...) + + stage_data = stage_data, cohort_random = cohort_random, cohorts_max = cohorts_max, + + sr_drugs_pos = sr_drugs_pos, target_rr = target_rr, sharing_type = sharing_type, + + safety_prob = safety_prob, Bayes_Sup = Bayes_Sup, prob_rr_transform = prob_rr_transform, + + cohort_offset = cohort_offset, Bayes_Fut = Bayes_Fut, sr_first_pos = sr_first_pos + + ) + > + > plot_trial(res_list, unit = "n") + Error in pm[[2]] : subscript out of bounds + Calls: plot_trial -> -> ggplotly.ggplot -> gg2list Execution halted ``` * checking running R code from vignettes ... ERROR ``` Errors in running code in vignettes: - when running code in ‘making_dot_density_maps.Rmd’ + when running code in ‘my-vignette.Rmd’ ... - > dots::dots(shp = suffolk, cols = vap_hisp) - When sourcing ‘making_dot_density_maps.R’: - Error: Base operators are not defined for quosures. Do you need to unquote the - quosure? + > set.seed(50) - # Bad: myquosure * rhs + > ocs1 <- trial_ocs(n_int = n_int, n_fin = n_fin, rr_comb = rr_comb, + + rr_mono = rr_mono, rr_back = rr_back, rr_plac = rr_plac, + + rr_transfo .... [TRUNCATED] - # Good: !!myquosure * rhs + When sourcing ‘my-vignette.R’: + Error: subscript out of bounds Execution halted - ‘making_dot_density_maps.Rmd’ using ‘UTF-8’... failed + ‘my-vignette.Rmd’ using ‘UTF-8’... failed ``` * checking re-building of vignette outputs ... NOTE ``` Error(s) in re-building vignettes: ... - --- re-building ‘making_dot_density_maps.Rmd’ using rmarkdown - - Quitting from lines at lines 50-51 [unnamed-chunk-3] (making_dot_density_maps.Rmd) - Error: processing vignette 'making_dot_density_maps.Rmd' failed with diagnostics: - Base operators are not defined for quosures. Do you need to unquote the - quosure? - - # Bad: myquosure * rhs + --- re-building ‘my-vignette.Rmd’ using rmarkdown - # Good: !!myquosure * rhs - --- failed re-building ‘making_dot_density_maps.Rmd’ + Quitting from lines 1043-1073 [unnamed-chunk-20] (my-vignette.Rmd) + Error: processing vignette 'my-vignette.Rmd' failed with diagnostics: + subscript out of bounds + --- failed re-building ‘my-vignette.Rmd’ SUMMARY: processing the following file failed: - ‘making_dot_density_maps.Rmd’ + ‘my-vignette.Rmd’ Error: Vignette re-building failed. Execution halted ``` -## In both +# CoMiRe -* checking data for non-ASCII characters ... NOTE +
+ +* Version: 0.8 +* GitHub: NA +* Source code: https://github.com/cran/CoMiRe +* Date/Publication: 2023-08-23 09:10:06 UTC +* Number of recursive dependencies: 35 + +Run `revdepcheck::cloud_details(, "CoMiRe")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR ``` - Note: found 2 marked UTF-8 strings + Running examples in ‘CoMiRe-Ex.R’ failed + The error most likely occurred in: + + > ### Name: BMD + > ### Title: Benchmark dose + > ### Aliases: BMD + > + > ### ** Examples + > + > { + ... + Backtrace: + ▆ + 1. ├─base (local) ``(x) + 2. └─ggplot2:::print.ggplot(x) + 3. ├─ggplot2::ggplot_gtable(data) + 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) + 5. └─ggplot2::calc_element("plot.margin", theme) + 6. └─cli::cli_abort(...) + 7. └─rlang::abort(...) + Execution halted ``` -# eks +# CommKern
-* Version: 1.0.5 -* GitHub: NA -* Source code: https://github.com/cran/eks -* Date/Publication: 2024-05-01 23:24:46 UTC -* Number of recursive dependencies: 89 +* Version: 1.0.1 +* GitHub: https://github.com/aljensen89/CommKern +* Source code: https://github.com/cran/CommKern +* Date/Publication: 2022-09-23 10:20:06 UTC +* Number of recursive dependencies: 58 -Run `revdepcheck::cloud_details(, "eks")` for more info +Run `revdepcheck::cloud_details(, "CommKern")` for more info
@@ -2395,65 +2771,74 @@ Run `revdepcheck::cloud_details(, "eks")` for more info * checking examples ... ERROR ``` - Running examples in ‘eks-Ex.R’ failed + Running examples in ‘CommKern-Ex.R’ failed The error most likely occurred in: - > ### Name: tidyst_kms - > ### Title: Tidy and geospatial kernel mean shift clustering - > ### Aliases: tidy_kms st_kms - > ### Keywords: smooth + > ### Name: hms + > ### Title: Hierarchical multimodal spinglass algorithm + > ### Aliases: hms > > ### ** Examples > + > ... - 17. └─ggplot2 (local) FUN(X[[i]], ...) - 18. └─g$draw_key(data, g$params, key_size) - 19. └─ggplot2 (local) draw_key(...) - 20. └─ggplot2::draw_key_point(data, params, size) - 21. ├─grid::pointsGrob(...) - 22. │ └─grid::grob(...) - 23. └─ggplot2::ggpar(...) - 24. └─rlang:::Ops.quosure(pointsize, .pt) - 25. └─rlang::abort(...) + ▆ + 1. ├─CommKern::community_plot(hms_object) + 2. └─CommKern:::community_plot.spinglass_hms(hms_object) + 3. └─ggplot2::ggplotGrob(comm_plot) + 4. ├─ggplot2::ggplot_gtable(ggplot_build(x)) + 5. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) + 6. └─ggplot2::calc_element("plot.margin", theme) + 7. └─cli::cli_abort(...) + 8. └─rlang::abort(...) Execution halted ``` * checking running R code from vignettes ... ERROR ``` Errors in running code in vignettes: - when running code in ‘tidysf_kde.Rmd’ + when running code in ‘CommKern.Rmd’ ... - + scale_fill_discrete_sequential(h1 = 275) + coord_sf(xlim = .... [TRUNCATED] + .. .. ..$ : chr [1:80] "1" "2" "3" "4" ... + ..- attr(*, "class")= chr "spinglass_net" + $ best_hamiltonian: num -286 + - attr(*, "class")= chr "spinglass_hms" - When sourcing ‘tidysf_kde.R’: - Error: Summary operations are not defined for quosures. Do you need to unquote - the quosure? + > community_plot(hms_object) - # Bad: min(myquosure) - - # Good: min(!!myquosure) + When sourcing ‘CommKern.R’: + Error: Theme element `plot.margin` must have class . Execution halted - ‘tidysf_kde.Rmd’ using ‘UTF-8’... failed + ‘CommKern.Rmd’ using ‘UTF-8’... failed ``` * checking re-building of vignette outputs ... NOTE ``` Error(s) in re-building vignettes: - --- re-building ‘tidysf_kde.Rmd’ using rmarkdown + --- re-building ‘CommKern.Rmd’ using rmarkdown ``` -# entropart +## In both + +* checking installed package size ... NOTE + ``` + installed size is 7.2Mb + sub-directories of 1Mb or more: + data 6.5Mb + ``` + +# conText
-* Version: 1.6-13 -* GitHub: https://github.com/EricMarcon/entropart -* Source code: https://github.com/cran/entropart -* Date/Publication: 2023-09-26 14:40:02 UTC -* Number of recursive dependencies: 122 +* Version: 1.4.3 +* GitHub: https://github.com/prodriguezsosa/ConText +* Source code: https://github.com/cran/conText +* Date/Publication: 2023-02-09 21:10:02 UTC +* Number of recursive dependencies: 78 -Run `revdepcheck::cloud_details(, "entropart")` for more info +Run `revdepcheck::cloud_details(, "conText")` for more info
@@ -2461,298 +2846,177 @@ Run `revdepcheck::cloud_details(, "entropart")` for more info * checking examples ... ERROR ``` - Running examples in ‘entropart-Ex.R’ failed + Running examples in ‘conText-Ex.R’ failed The error most likely occurred in: - > ### Name: Accumulation - > ### Title: Diversity accumulation. - > ### Aliases: DivAC EntAC as.AccumCurve is.AccumCurve autoplot.AccumCurve - > ### plot.AccumCurve + > ### Name: plot_nns_ratio + > ### Title: Plot output of 'get_nns_ratio()' + > ### Aliases: plot_nns_ratio + > ### Keywords: plot_nns_ratio > > ### ** Examples > ... - 11. │ └─base::withCallingHandlers(...) - 12. └─ggplot2 (local) f(l = layers[[i]], d = data[[i]]) - 13. └─l$compute_geom_2(d, theme = plot$theme) - 14. └─ggplot2 (local) compute_geom_2(..., self = self) - 15. └─self$geom$use_defaults(data, self$aes_params, modifiers, theme = theme) - 16. └─ggplot2 (local) use_defaults(..., self = self) - 17. └─ggplot2:::check_aesthetics(new_params, nrow(data)) - 18. └─cli::cli_abort(...) - 19. └─rlang::abort(...) + Backtrace: + ▆ + 1. ├─base (local) ``(x) + 2. └─ggplot2:::print.ggplot(x) + 3. ├─ggplot2::ggplot_gtable(data) + 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) + 5. └─ggplot2::calc_element("plot.margin", theme) + 6. └─cli::cli_abort(...) + 7. └─rlang::abort(...) Execution halted ``` * checking running R code from vignettes ... ERROR ``` Errors in running code in vignettes: - when running code in ‘entropart.Rmd’ + when running code in ‘quickstart.Rmd’ ... + 4 illegally 1.12 0.0290 1.08 1.18 0 shared + 5 laws 1.09 0.0351 1.03 1.15 0 R + 6 legal 1.03 0.0341 0.973 1.08 0.39 R - > autoplot(Abd18, Distribution = "lnorm") + > plot_nns_ratio(x = immig_nns_ratio, alpha = 0.01, + + horizontal = TRUE) - When sourcing ‘entropart.R’: - Error: Problem while setting up geom aesthetics. - ℹ Error occurred in the 1st layer. - Caused by error in `check_aesthetics()`: - ! Aesthetics must be either length 1 or the same as the data (149). - ✖ Fix the following mappings: `shape`, `colour`, and `size`. + When sourcing ‘quickstart.R’: + Error: Theme element `plot.margin` must have class . Execution halted - ‘entropart.Rmd’ using ‘UTF-8’... failed + ‘quickstart.Rmd’ using ‘UTF-8’... failed ``` * checking re-building of vignette outputs ... NOTE ``` Error(s) in re-building vignettes: ... - --- re-building ‘entropart.Rmd’ using rmarkdown + --- re-building ‘quickstart.Rmd’ using rmarkdown - Quitting from lines at lines 53-55 [PlotN18] (entropart.Rmd) - Error: processing vignette 'entropart.Rmd' failed with diagnostics: - Problem while setting up geom aesthetics. - ℹ Error occurred in the 1st layer. - Caused by error in `check_aesthetics()`: - ! Aesthetics must be either length 1 or the same as the data (149). - ✖ Fix the following mappings: `shape`, `colour`, and `size`. - --- failed re-building ‘entropart.Rmd’ + Quitting from lines 342-343 [unnamed-chunk-21] (quickstart.Rmd) + Error: processing vignette 'quickstart.Rmd' failed with diagnostics: + Theme element `plot.margin` must have class . + --- failed re-building ‘quickstart.Rmd’ SUMMARY: processing the following file failed: - ‘entropart.Rmd’ + ‘quickstart.Rmd’ Error: Vignette re-building failed. Execution halted ``` -# epiCleanr - -
- -* Version: 0.2.0 -* GitHub: https://github.com/truenomad/epiCleanr -* Source code: https://github.com/cran/epiCleanr -* Date/Publication: 2023-09-28 12:20:05 UTC -* Number of recursive dependencies: 129 - -Run `revdepcheck::cloud_details(, "epiCleanr")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘epiCleanr-Ex.R’ failed - The error most likely occurred in: - - > ### Name: handle_outliers - > ### Title: Detect and Handle Outliers in Dataset - > ### Aliases: handle_outliers - > - > ### ** Examples - > - > - ... - 12. │ └─ggplot2 (local) f(l = layers[[i]], d = data[[i]]) - 13. │ └─l$compute_geom_2(d, theme = plot$theme) - 14. │ └─ggplot2 (local) compute_geom_2(..., self = self) - 15. │ └─self$geom$use_defaults(data, self$aes_params, modifiers, theme = theme) - 16. └─base::.handleSimpleError(...) - 17. └─rlang (local) h(simpleError(msg, call)) - 18. └─handlers[[1L]](cnd) - 19. └─cli::cli_abort(...) - 20. └─rlang::abort(...) - Execution halted - ``` - -## In both +## In both * checking installed package size ... NOTE ``` - installed size is 5.6Mb + installed size is 5.4Mb sub-directories of 1Mb or more: - doc 2.9Mb - help 2.5Mb + data 3.5Mb + doc 1.5Mb ``` -# epiR +# CoreMicrobiomeR
-* Version: 2.0.74 +* Version: 0.1.0 * GitHub: NA -* Source code: https://github.com/cran/epiR -* Date/Publication: 2024-04-27 12:30:02 UTC -* Number of recursive dependencies: 125 +* Source code: https://github.com/cran/CoreMicrobiomeR +* Date/Publication: 2024-04-03 20:03:02 UTC +* Number of recursive dependencies: 91 -Run `revdepcheck::cloud_details(, "epiR")` for more info +Run `revdepcheck::cloud_details(, "CoreMicrobiomeR")` for more info
## Newly broken -* checking running R code from vignettes ... ERROR +* checking examples ... ERROR ``` - Errors in running code in vignettes: - when running code in ‘epiR_descriptive.Rmd’ - ... - + fill = "tra ..." ... [TRUNCATED] - - When sourcing ‘epiR_descriptive.R’: - Error: Base operators are not defined for quosures. Do you need to unquote the - quosure? - - # Bad: myquosure * rhs + Running examples in ‘CoreMicrobiomeR-Ex.R’ failed + The error most likely occurred in: - # Good: !!myquosure * rhs + > ### Name: group_bar_plots + > ### Title: Grouped Bar Plots Based on Sample Size + > ### Aliases: group_bar_plots + > + > ### ** Examples + > + > #To run input data + ... + + top_percentage = 10 # Adjust the percentage as needed for core/non-core OTUs + + ) + Warning encountered during diversity analysis:you have empty rows: their dissimilarities may be + meaningless in method “bray” + > #To run grouped bar plot function + > plot_group_bar <- group_bar_plots(core_1$final_otu_table_bef_filter, + + core_1$final_otu_aft_filter, 10) + Error in pm[[2]] : subscript out of bounds + Calls: group_bar_plots -> -> ggplotly.ggplot -> gg2list Execution halted - - ‘epiR_descriptive.Rmd’... failed - ‘epiR_measures_of_association.Rmd’... OK - ‘epiR_sample_size.Rmd’... OK - ‘epiR_surveillance.Rmd’... OK - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘epiR_descriptive.Rmd’ using rmarkdown ``` -# esci +# correlationfunnel
-* Version: 1.0.2 -* GitHub: https://github.com/rcalinjageman/esci -* Source code: https://github.com/cran/esci -* Date/Publication: 2024-03-21 18:10:02 UTC -* Number of recursive dependencies: 93 +* Version: 0.2.0 +* GitHub: https://github.com/business-science/correlationfunnel +* Source code: https://github.com/cran/correlationfunnel +* Date/Publication: 2020-06-09 04:40:03 UTC +* Number of recursive dependencies: 117 -Run `revdepcheck::cloud_details(, "esci")` for more info +Run `revdepcheck::cloud_details(, "correlationfunnel")` for more info
## Newly broken -* checking examples ... ERROR - ``` - Running examples in ‘esci-Ex.R’ failed - The error most likely occurred in: - - > ### Name: estimate_mdiff_2x2_between - > ### Title: Estimates for a 2x2 between-subjects design with a continuous - > ### outcome variable - > ### Aliases: estimate_mdiff_2x2_between - > - > ### ** Examples - > - ... - 2.75, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 1, NULL, NULL, NULL, c(0, 2.2, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, NULL, c(0, 0, 0, 2.2 - ), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0.5, NULL, NULL, NULL, c(0, 2.2, 0, 2.2), NULL, TRUE), list("grey20", NULL, NULL, NULL, FALSE, TRUE), NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 2.75, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 0.75, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, list("black", 1, NULL, NULL, FALSE, TRUE), NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, list(NULL, NA, NULL, NULL, TRUE), c(5.5, 5.5, 5.5, 5.5), 11, NULL, - NULL, NULL, 1.2, NULL, NULL, 5.5, NULL, NULL, NULL, NULL, 0.2, NULL, list(NULL, NULL, NULL, 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, NULL, NULL, NULL, TRUE), NULL, "right", NULL, NULL, NULL, "center", NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, c(0, 0, 0, 0), list(), 11, list("white", NA, NULL, NULL, TRUE), list(), 5.5, NULL, NULL, list("grey92", NULL, NULL, NULL, FALSE, TRUE), list(), list(), NULL, NULL, NULL, NULL, FALSE, list(NULL, - "white", NULL, NULL, TRUE), list(NULL, NULL, NULL, 1.2, 0, 1, NULL, NULL, c(0, 0, 5.5, 0), NULL, TRUE), "panel", list(NULL, NULL, NULL, NULL, 0, 1, NULL, NULL, c(0, 0, 5.5, 0), NULL, TRUE), list(NULL, NULL, NULL, 0.8, 1, 1, NULL, NULL, c(5.5, 0, 0, 0), NULL, TRUE), "panel", list(NULL, NULL, NULL, 1.2, 0.5, 0.5, NULL, NULL, NULL, NULL, TRUE), "topleft", NULL, c(5.5, 5.5, 5.5, 5.5), list("white", "black", 2, NULL, TRUE), NULL, NULL, "inherit", "inside", list(NULL, NULL, "grey10", 0.8, NULL, - NULL, NULL, NULL, c(4.4, 4.4, 4.4, 4.4), NULL, TRUE), NULL, NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, NULL, -90, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, NULL, 90, NULL, NULL, NULL, TRUE), NULL, 2.75, 2.75)) - Error in use_defaults(..., self = self) : - unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), NULL, list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.75, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, 90, NULL, c(0, - 2.75, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 1, NULL, NULL, NULL, c(0, 2.2, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL - Calls: ... .handleSimpleError -> h -> -> - Execution halted - ``` - * checking tests ... ERROR ``` Running ‘testthat.R’ Running the tests in ‘tests/testthat.R’ failed. Complete output: > library(testthat) - > library(esci) - > - > test_check("esci") - Loading required package: Matrix - Loading required package: metadat - Loading required package: numDeriv + > library(dplyr) + + Attaching package: 'dplyr' + + The following object is masked from 'package:testthat': + ... - 17. │ └─self$geom$use_defaults(data, self$aes_params, modifiers, theme = theme) - 18. └─base::.handleSimpleError(...) - 19. └─rlang (local) h(simpleError(msg, call)) - 20. └─handlers[[1L]](cnd) - 21. └─cli::cli_abort(...) - 22. └─rlang::abort(...) + ▆ + 1. ├─correlationfunnel::plot_correlation_funnel(...) at test-plot_correlation_funnel.R:23:1 + 2. └─correlationfunnel:::plot_correlation_funnel.data.frame(...) + 3. ├─plotly::ggplotly(g, tooltip = "text") + 4. └─plotly:::ggplotly.ggplot(g, tooltip = "text") + 5. └─plotly::gg2list(...) - [ FAIL 14 | WARN 15 | SKIP 0 | PASS 3182 ] + [ FAIL 1 | WARN 3 | SKIP 0 | PASS 17 ] Error: Test failures Execution halted ``` -# evalITR - -
- -* Version: 1.0.0 -* GitHub: https://github.com/MichaelLLi/evalITR -* Source code: https://github.com/cran/evalITR -* Date/Publication: 2023-08-25 23:10:06 UTC -* Number of recursive dependencies: 168 - -Run `revdepcheck::cloud_details(, "evalITR")` for more info - -
- -## Newly broken - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘cv_multiple_alg.Rmd’ using rmarkdown - ``` - ## In both -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘cv_multiple_alg.Rmd’ - ... - intersect, setdiff, setequal, union - - - > load("../data/star.rda") - Warning in readChar(con, 5L, useBytes = TRUE) : - cannot open compressed file '../data/star.rda', probable reason 'No such file or directory' - - ... - Execution halted - - ‘cv_multiple_alg.Rmd’ using ‘UTF-8’... failed - ‘cv_single_alg.Rmd’ using ‘UTF-8’... failed - ‘install.Rmd’ using ‘UTF-8’... OK - ‘paper_alg1.Rmd’ using ‘UTF-8’... OK - ‘sample_split.Rmd’ using ‘UTF-8’... failed - ‘sample_split_caret.Rmd’ using ‘UTF-8’... failed - ‘user_itr.Rmd’ using ‘UTF-8’... failed - ‘user_itr_algs.Rmd’ using ‘UTF-8’... failed - ``` - * checking dependencies in R code ... NOTE ``` - Namespaces in Imports field not imported from: - ‘forcats’ ‘rqPen’ ‘utils’ + Namespace in Imports field not imported from: ‘utils’ All declared Imports should be used. ``` -# explainer +# corrViz
-* Version: 1.0.1 -* GitHub: https://github.com/PERSIMUNE/explainer -* Source code: https://github.com/cran/explainer -* Date/Publication: 2024-04-18 09:00:02 UTC -* Number of recursive dependencies: 193 +* Version: 0.1.0 +* GitHub: NA +* Source code: https://github.com/cran/corrViz +* Date/Publication: 2023-06-30 11:40:07 UTC +* Number of recursive dependencies: 139 -Run `revdepcheck::cloud_details(, "explainer")` for more info +Run `revdepcheck::cloud_details(, "corrViz")` for more info
@@ -2760,253 +3024,177 @@ Run `revdepcheck::cloud_details(, "explainer")` for more info * checking examples ... ERROR ``` - Running examples in ‘explainer-Ex.R’ failed + Running examples in ‘corrViz-Ex.R’ failed The error most likely occurred in: - > ### Name: eDecisionCurve - > ### Title: Decision Curve Plot - > ### Aliases: eDecisionCurve + > ### Name: animSolar + > ### Title: animSolar + > ### Aliases: animSolar > > ### ** Examples > - > library("explainer") + > cm <- cor(mtcars) ... - > myplot <- eDecisionCurve( - + task = maintask, - + trained_model = mylrn, - + splits = splits, - + seed = seed - + ) - Error in compute_geom_2(..., self = self) : - argument "theme" is missing, with no default - Calls: eDecisionCurve ... use_defaults -> eval_from_theme -> %||% -> calc_element + All aesthetics have length 1, but the data has 250 rows. + ℹ Please consider using `annotate()` or provide this layer with data containing + a single row. + Warning in geom_text(data = solar_system, aes(x = 0, y = 0, label = sun), : + All aesthetics have length 1, but the data has 250 rows. + ℹ Please consider using `annotate()` or provide this layer with data containing + a single row. + Error in pm[[2]] : subscript out of bounds + Calls: animSolar -> ggplotly -> ggplotly.ggplot -> gg2list Execution halted ``` -## In both - -* checking dependencies in R code ... NOTE - ``` - Namespace in Imports field not imported from: ‘ggpmisc’ - All declared Imports should be used. - ``` - -# fable.prophet - -
- -* Version: 0.1.0 -* GitHub: https://github.com/mitchelloharawild/fable.prophet -* Source code: https://github.com/cran/fable.prophet -* Date/Publication: 2020-08-20 09:30:03 UTC -* Number of recursive dependencies: 114 - -Run `revdepcheck::cloud_details(, "fable.prophet")` for more info - -
- -## Newly broken - * checking running R code from vignettes ... ERROR ``` Errors in running code in vignettes: - when running code in ‘intro.Rmd’ + when running code in ‘corrViz.Rmd’ ... - 2.75, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 1, NULL, NULL, NULL, c(0, 2.2, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, NULL, c(0, 0, 0, 2.2 - ), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0.5, NULL, NULL, NULL, c(0, 2.2, 0, 2.2), NULL, TRUE), list("grey20", NULL, NULL, NULL, FALSE, TRUE), NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 2.75, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 0.75, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, list(), NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, list(NULL, NA, NULL, NULL, TRUE), c(5.5, 5.5, 5.5, 5.5), 11, NULL, NULL, NULL, 1.2, NULL, NULL, 5.5, - NULL, NULL, NULL, NULL, 0.2, NULL, list(NULL, NULL, NULL, 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, NULL, NULL, NULL, TRUE), NULL, "right", NULL, NULL, NULL, "center", NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, c(0, 0, 0, 0), list(), 11, list("grey92", NA, NULL, NULL, TRUE), list(), 5.5, NULL, NULL, list("white", NULL, NULL, NULL, FALSE, TRUE), NULL, list(NULL, 0.5, NULL, NULL, FALSE, TRUE), NULL, NULL, NULL, NULL, FALSE, list(NULL, - "white", NULL, NULL, TRUE), list(NULL, NULL, NULL, 1.2, 0, 1, NULL, NULL, c(0, 0, 5.5, 0), NULL, TRUE), "panel", list(NULL, NULL, NULL, NULL, 0, 1, NULL, NULL, c(0, 0, 5.5, 0), NULL, TRUE), list(NULL, NULL, NULL, 0.8, 1, 1, NULL, NULL, c(5.5, 0, 0, 0), NULL, TRUE), "panel", list(NULL, NULL, NULL, 1.2, 0.5, 0.5, NULL, NULL, NULL, NULL, TRUE), "topleft", NULL, c(5.5, 5.5, 5.5, 5.5), list("grey85", NA, NULL, NULL, TRUE), NULL, NULL, "inherit", "inside", list(NULL, NULL, "grey10", 0.8, NULL, - NULL, NULL, NULL, c(4.4, 4.4, 4.4, 4.4), NULL, TRUE), NULL, NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, NULL, -90, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, NULL, 90, NULL, NULL, NULL, TRUE), NULL, 2.75, 2.75)) + > library(corrViz) - When sourcing ‘intro.R’: - Error: unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), NULL, list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.75, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, 90, NULL, c(0, - 2.75, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 1, NULL, NULL, NULL, c(0, 2.2, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, + > cm <- cor(mtcars) + + > corrHeatmap(mat = cm, display = "all", reorder = TRUE, + + pal = colorRampPalette(c("darkblue", "white", "darkred"))(100)) + + When sourcing ‘corrViz.R’: + Error: subscript out of bounds Execution halted - ‘intro.Rmd’ using ‘UTF-8’... failed + ‘corrViz.Rmd’ using ‘UTF-8’... failed ``` * checking re-building of vignette outputs ... NOTE ``` Error(s) in re-building vignettes: - --- re-building ‘intro.Rmd’ using rmarkdown + ... + --- re-building ‘corrViz.Rmd’ using rmarkdown + + Quitting from lines 76-81 [heatmap] (corrViz.Rmd) + Error: processing vignette 'corrViz.Rmd' failed with diagnostics: + subscript out of bounds + --- failed re-building ‘corrViz.Rmd’ + + SUMMARY: processing the following file failed: + ‘corrViz.Rmd’ + + Error: Vignette re-building failed. + Execution halted ``` ## In both -* checking LazyData ... NOTE +* checking installed package size ... NOTE ``` - 'LazyData' is specified without a 'data' directory + installed size is 7.2Mb + sub-directories of 1Mb or more: + doc 6.7Mb ``` -# fabletools +# covidcast
-* Version: 0.4.2 -* GitHub: https://github.com/tidyverts/fabletools -* Source code: https://github.com/cran/fabletools -* Date/Publication: 2024-04-22 11:22:41 UTC -* Number of recursive dependencies: 106 +* Version: 0.5.2 +* GitHub: https://github.com/cmu-delphi/covidcast +* Source code: https://github.com/cran/covidcast +* Date/Publication: 2023-07-12 23:40:06 UTC +* Number of recursive dependencies: 93 -Run `revdepcheck::cloud_details(, "fabletools")` for more info +Run `revdepcheck::cloud_details(, "covidcast")` for more info
## Newly broken -* checking examples ... ERROR - ``` - Running examples in ‘fabletools-Ex.R’ failed - The error most likely occurred in: - - > ### Name: autoplot.fbl_ts - > ### Title: Plot a set of forecasts - > ### Aliases: autoplot.fbl_ts autolayer.fbl_ts - > - > ### ** Examples - > - > ## Don't show: - ... - 2.75, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 1, NULL, NULL, NULL, c(0, 2.2, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, NULL, c(0, 0, 0, 2.2 - ), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0.5, NULL, NULL, NULL, c(0, 2.2, 0, 2.2), NULL, TRUE), list("grey20", NULL, NULL, NULL, FALSE, TRUE), NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 2.75, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 0.75, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, list(), NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, list(NULL, NA, NULL, NULL, TRUE), c(5.5, 5.5, 5.5, 5.5), 11, NULL, NULL, NULL, 1.2, NULL, NULL, 5.5, - NULL, NULL, NULL, NULL, 0.2, NULL, list(NULL, NULL, NULL, 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, NULL, NULL, NULL, TRUE), NULL, "right", NULL, NULL, NULL, "center", NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, c(0, 0, 0, 0), list(), 11, list("grey92", NA, NULL, NULL, TRUE), list(), 5.5, NULL, NULL, list("white", NULL, NULL, NULL, FALSE, TRUE), NULL, list(NULL, 0.5, NULL, NULL, FALSE, TRUE), NULL, NULL, NULL, NULL, FALSE, list(NULL, - "white", NULL, NULL, TRUE), list(NULL, NULL, NULL, 1.2, 0, 1, NULL, NULL, c(0, 0, 5.5, 0), NULL, TRUE), "panel", list(NULL, NULL, NULL, NULL, 0, 1, NULL, NULL, c(0, 0, 5.5, 0), NULL, TRUE), list(NULL, NULL, NULL, 0.8, 1, 1, NULL, NULL, c(5.5, 0, 0, 0), NULL, TRUE), "panel", list(NULL, NULL, NULL, 1.2, 0.5, 0.5, NULL, NULL, NULL, NULL, TRUE), "topleft", NULL, c(5.5, 5.5, 5.5, 5.5), list("grey85", NA, NULL, NULL, TRUE), NULL, NULL, "inherit", "inside", list(NULL, NULL, "grey10", 0.8, NULL, - NULL, NULL, NULL, c(4.4, 4.4, 4.4, 4.4), NULL, TRUE), NULL, NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, NULL, -90, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, NULL, 90, NULL, NULL, NULL, TRUE), NULL, 2.75, 2.75)) - Error in use_defaults(..., self = self) : - unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), NULL, list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.75, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, 90, NULL, c(0, - 2.75, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 1, NULL, NULL, NULL, c(0, 2.2, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL - Calls: ... .handleSimpleError -> h -> -> - Execution halted - ``` - -* checking tests ... ERROR +* checking tests ... ERROR ``` Running ‘testthat.R’ Running the tests in ‘tests/testthat.R’ failed. Complete output: > library(testthat) - > library(dplyr) - - Attaching package: 'dplyr' - - The following object is masked from 'package:testthat': - + > library(covidcast) + We encourage COVIDcast API users to register on our mailing list: + https://lists.andrew.cmu.edu/mailman/listinfo/delphi-covidcast-api + We'll send announcements about new data sources, package updates, + server maintenance, and new features. + > ... - 32. │ │ └─base::withCallingHandlers(...) - 33. │ └─layer$geom$use_defaults(...) - 34. └─base::.handleSimpleError(...) - 35. └─rlang (local) h(simpleError(msg, call)) - 36. └─handlers[[1L]](cnd) - 37. └─layer$geom$use_defaults(...) - - [ FAIL 2 | WARN 0 | SKIP 1 | PASS 269 ] + • plot/default-county-choropleth.svg + • plot/default-hrr-choropleth-with-include.svg + • plot/default-msa-choropleth-with-include.svg + • plot/default-state-choropleth-with-include.svg + • plot/default-state-choropleth-with-range.svg + • plot/state-choropleth-with-no-metadata.svg + • plot/state-line-graph-with-range.svg + • plot/state-line-graph-with-stderrs.svg Error: Test failures Execution halted ``` -# ffp - -
- -* Version: 0.2.2 -* GitHub: https://github.com/Reckziegel/FFP -* Source code: https://github.com/cran/ffp -* Date/Publication: 2022-09-29 15:10:06 UTC -* Number of recursive dependencies: 107 - -Run `revdepcheck::cloud_details(, "ffp")` for more info - -
- -## Newly broken - -* checking examples ... ERROR +* checking running R code from vignettes ... ERROR ``` - Running examples in ‘ffp-Ex.R’ failed - The error most likely occurred in: + Errors in running code in vignettes: + when running code in ‘multi-signals.Rmd’ + ... - > ### Name: scenario_density - > ### Title: Plot Scenarios - > ### Aliases: scenario_density scenario_histogram - > - > ### ** Examples - > - > x <- diff(log(EuStockMarkets))[, 1] + > signals <- covidcast_signals(data_source = "jhu-csse", + + signal = c("confirmed_7dav_incidence_prop", "deaths_7dav_incidence_prop"), + + star .... [TRUNCATED] + + When sourcing ‘multi-signals.R’: + Error: Rate limit exceeded when fetching data from API anonymously. See the "API keys" section of the `covidcast_signal()` documentation for information on registering for an API key. ... - 2.75, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, NULL, c(0, 0, 0, 2.2), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0.5, NULL, NULL, NULL, - c(0, 2.2, 0, 2.2), NULL, TRUE), list("grey20", NULL, NULL, NULL, FALSE, TRUE), NULL, NULL, NULL, list(), NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 2.75, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 0.75, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, list(), NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, list(NULL, NA, NULL, NULL, TRUE), c(5.5, 5.5, 5.5, 5.5), 11, NULL, NULL, NULL, 1.2, NULL, NULL, 5.5, NULL, NULL, NULL, NULL, 0.2, NULL, list(NULL, NULL, NULL, 0.8, NULL, - NULL, NULL, NULL, NULL, NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, NULL, NULL, NULL, TRUE), NULL, "right", NULL, NULL, NULL, "center", NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, c(0, 0, 0, 0), list(), 11, list("grey92", NA, NULL, NULL, TRUE), list(), 5.5, NULL, NULL, list("white", NULL, NULL, NULL, FALSE, TRUE), NULL, list(NULL, 0.5, NULL, NULL, FALSE, TRUE), NULL, NULL, NULL, NULL, FALSE, list(NULL, "white", NULL, NULL, TRUE), list(NULL, NULL, NULL, 1.2, 0, 1, NULL, - NULL, c(0, 0, 5.5, 0), NULL, TRUE), "panel", list(NULL, NULL, NULL, NULL, 0, 1, NULL, NULL, c(0, 0, 5.5, 0), NULL, TRUE), list(NULL, NULL, NULL, 0.8, 1, 1, NULL, NULL, c(5.5, 0, 0, 0), NULL, TRUE), "panel", list(NULL, NULL, NULL, 1.2, 0.5, 0.5, NULL, NULL, NULL, NULL, TRUE), "topleft", NULL, c(5.5, 5.5, 5.5, 5.5), list("grey85", NA, NULL, NULL, TRUE), NULL, NULL, "inherit", "inside", list(NULL, NULL, "grey10", 0.8, NULL, NULL, NULL, NULL, c(4.4, 4.4, 4.4, 4.4), NULL, TRUE), NULL, NULL, NULL, - list(NULL, NULL, NULL, NULL, NULL, NULL, -90, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, NULL, 90, NULL, NULL, NULL, TRUE), NULL, 2.75, 2.75)) - Error in use_defaults(..., self = self) : - unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), NULL, list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.75, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, 90, NULL, c(0, - 2.75, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, NULL, c(0, 0, 0, 2.2), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, - Calls: ... .handleSimpleError -> h -> -> + Error: Rate limit exceeded when fetching data from API anonymously. See the "API keys" section of the `covidcast_signal()` documentation for information on registering for an API key. + ℹ Message from server: + ℹ Rate limit exceeded for anonymous queries. To remove this limit, register a free API key at https://api.delphi.cmu.edu/epidata/admin/registration_form Execution halted + + ‘correlation-utils.Rmd’ using ‘UTF-8’... OK + ‘covidcast.Rmd’ using ‘UTF-8’... OK + ‘external-data.Rmd’ using ‘UTF-8’... OK + ‘multi-signals.Rmd’ using ‘UTF-8’... failed + ‘plotting-signals.Rmd’ using ‘UTF-8’... failed ``` -# fido - -
- -* Version: 1.0.4 -* GitHub: https://github.com/jsilve24/fido -* Source code: https://github.com/cran/fido -* Date/Publication: 2023-03-24 12:00:10 UTC -* Number of recursive dependencies: 130 - -Run `revdepcheck::cloud_details(, "fido")` for more info - -
- -## Newly broken - -* checking examples ... ERROR +* checking re-building of vignette outputs ... NOTE ``` - Running examples in ‘fido-Ex.R’ failed - The error most likely occurred in: + Error(s) in re-building vignettes: + --- re-building ‘correlation-utils.Rmd’ using rmarkdown + --- finished re-building ‘correlation-utils.Rmd’ - > ### Name: plot.pibblefit - > ### Title: Plot Summaries of Posterior Distribution of pibblefit Parameters - > ### Aliases: plot.pibblefit - > - > ### ** Examples - > - > sim <- pibble_sim(N=10, D=4, Q=3) - ... - ! unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), NULL, list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.75, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, - NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 1, NULL, NULL, NULL, c(0, 2.2, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, NULL, c(0, 0, 0, 2.2), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0.5, NULL, NULL, NULL, - c(0, 2.2, 0, 2.2), NULL, TRUE), list(), NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 2.75, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 0.75, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, list(), NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, list(), c(5.5, 5.5, 5.5, 5.5), 11, NULL, NULL, list(), 1.2, NULL, NULL, 5.5, NULL, NULL, NULL, NULL, 0.2, NULL, list(NULL, NULL, NULL, 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), NULL, list(NULL, NULL, NULL, - NULL, 0, NULL, NULL, NULL, NULL, NULL, TRUE), NULL, "right", NULL, NULL, NULL, "center", NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, c(0, 0, 0, 0), list(), 11, list(), list(), 5.5, NULL, NULL, list("grey92", NULL, NULL, NULL, FALSE, TRUE), NULL, list(NULL, 0.5, NULL, NULL, FALSE, TRUE), NULL, NULL, NULL, NULL, FALSE, list(), list(NULL, NULL, NULL, 1.2, 0, 1, NULL, NULL, c(0, 0, 5.5, 0), NULL, TRUE), "panel", list(NULL, NULL, NULL, NULL, 0, 1, NULL, NULL, c(0, 0, 5.5, 0), NULL, TRUE), list( - NULL, NULL, NULL, 0.8, 1, 1, NULL, NULL, c(5.5, 0, 0, 0), NULL, TRUE), "panel", list(NULL, NULL, NULL, 1.2, 0.5, 0.5, NULL, NULL, NULL, NULL, TRUE), "topleft", NULL, c(5.5, 5.5, 5.5, 5.5), list(), NULL, NULL, "inherit", "inside", list(NULL, NULL, "grey10", 0.8, NULL, NULL, NULL, NULL, c(4.4, 4.4, 4.4, 4.4), NULL, TRUE), NULL, NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, NULL, -90, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, NULL, 90, NULL, NULL, NULL, TRUE), NULL, 2.75, 2.75)) - Error in use_defaults(..., self = self) : - unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), NULL, list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.75, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, - NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 1, NULL, NULL, NULL, c(0, 2.2, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, NULL, c(0, 0, 0, 2.2), NULL, TRUE), NULL, list(NULL, NULL, NULL, - Calls: ... .handleSimpleError -> h -> -> - Execution halted + --- re-building ‘covidcast.Rmd’ using rmarkdown + + Quitting from lines 38-45 [unnamed-chunk-1] (covidcast.Rmd) + Error: processing vignette 'covidcast.Rmd' failed with diagnostics: + Rate limit exceeded when fetching data from API anonymously. See the "API keys" section of the `covidcast_signal()` documentation for information on registering for an API key. + ℹ Message from server: + ℹ Rate limit exceeded for anonymous queries. To remove this limit, register a free API key at https://api.delphi.cmu.edu/epidata/admin/registration_form + --- failed re-building ‘covidcast.Rmd’ + + --- re-building ‘external-data.Rmd’ using rmarkdown ``` ## In both -* checking installed package size ... NOTE +* checking data for non-ASCII characters ... NOTE ``` - installed size is 116.1Mb - sub-directories of 1Mb or more: - libs 114.1Mb + Note: found 20 marked UTF-8 strings ``` -# flipr +# cricketdata
-* Version: 0.3.3 -* GitHub: https://github.com/LMJL-Alea/flipr -* Source code: https://github.com/cran/flipr -* Date/Publication: 2023-08-23 09:00:02 UTC -* Number of recursive dependencies: 106 +* Version: 0.2.3 +* GitHub: https://github.com/robjhyndman/cricketdata +* Source code: https://github.com/cran/cricketdata +* Date/Publication: 2023-08-29 10:30:09 UTC +* Number of recursive dependencies: 104 -Run `revdepcheck::cloud_details(, "flipr")` for more info +Run `revdepcheck::cloud_details(, "cricketdata")` for more info
@@ -3015,17 +3203,7 @@ Run `revdepcheck::cloud_details(, "flipr")` for more info * checking re-building of vignette outputs ... NOTE ``` Error(s) in re-building vignettes: - --- re-building ‘alternative.Rmd’ using rmarkdown - --- finished re-building ‘alternative.Rmd’ - - --- re-building ‘exactness.Rmd’ using rmarkdown - - Quitting from lines at lines 142-177 [unnamed-chunk-1] (exactness.Rmd) - Error: processing vignette 'exactness.Rmd' failed with diagnostics: - argument "theme" is missing, with no default - --- failed re-building ‘exactness.Rmd’ - - --- re-building ‘flipr.Rmd’ using rmarkdown + --- re-building ‘cricinfo.Rmd’ using rmarkdown ``` ## In both @@ -3033,47 +3211,44 @@ Run `revdepcheck::cloud_details(, "flipr")` for more info * checking running R code from vignettes ... ERROR ``` Errors in running code in vignettes: - when running code in ‘exactness.Rmd’ + when running code in ‘cricinfo.Rmd’ ... - > library(flipr) + > library(ggplot2) - > load("../R/sysdata.rda") - Warning in readChar(con, 5L, useBytes = TRUE) : - cannot open compressed file '../R/sysdata.rda', probable reason 'No such file or directory' + > wt20 <- readRDS("../inst/extdata/wt20.rds") + Warning in gzfile(file, "rb") : + cannot open compressed file '../inst/extdata/wt20.rds', probable reason 'No such file or directory' ... - cannot open compressed file '../R/sysdata.rda', probable reason 'No such file or directory' + Warning in gzfile(file, "rb") : + cannot open compressed file '../inst/extdata/wbbl_bbb.rds', probable reason 'No such file or directory' - When sourcing ‘plausibility.R’: + When sourcing ‘cricsheet.R’: Error: cannot open the connection Execution halted - ‘alternative.Rmd’ using ‘UTF-8’... OK - ‘exactness.Rmd’ using ‘UTF-8’... failed - ‘flipr.Rmd’ using ‘UTF-8’... failed - ‘plausibility.Rmd’ using ‘UTF-8’... failed + ‘cricinfo.Rmd’ using ‘UTF-8’... failed + ‘cricketdata_R_pkg.Rmd’ using ‘UTF-8’... failed + ‘cricsheet.Rmd’ using ‘UTF-8’... failed ``` -* checking installed package size ... NOTE +* checking data for non-ASCII characters ... NOTE ``` - installed size is 11.6Mb - sub-directories of 1Mb or more: - doc 9.1Mb - libs 1.6Mb + Note: found 37 marked UTF-8 strings ``` -# fmesher +# crosshap
-* Version: 0.1.5 -* GitHub: https://github.com/inlabru-org/fmesher -* Source code: https://github.com/cran/fmesher -* Date/Publication: 2023-12-20 21:50:08 UTC -* Number of recursive dependencies: 94 +* Version: 1.4.0 +* GitHub: https://github.com/jacobimarsh/crosshap +* Source code: https://github.com/cran/crosshap +* Date/Publication: 2024-03-31 15:40:02 UTC +* Number of recursive dependencies: 117 -Run `revdepcheck::cloud_details(, "fmesher")` for more info +Run `revdepcheck::cloud_details(, "crosshap")` for more info
@@ -3081,317 +3256,232 @@ Run `revdepcheck::cloud_details(, "fmesher")` for more info * checking examples ... ERROR ``` - Running examples in ‘fmesher-Ex.R’ failed + Running examples in ‘crosshap-Ex.R’ failed The error most likely occurred in: - > ### Name: fm_int - > ### Title: Multi-domain integration - > ### Aliases: fm_int fm_int.list fm_int.numeric fm_int.character - > ### fm_int.factor fm_int.SpatRaster fm_int.fm_lattice_2d - > ### fm_int.fm_mesh_1d fm_int.fm_mesh_2d fm_int.inla.mesh.lattice - > ### fm_int.inla.mesh.1d fm_int.inla.mesh + > ### Name: build_bot_halfeyeplot + > ### Title: Bot hap-pheno raincloud plot + > ### Aliases: build_bot_halfeyeplot + > + > ### ** Examples + > > ... - + geom_sf(data = fm_as_sfc(fmexample$mesh, multi = TRUE), alpha = 0.5) + - + geom_sf(data = fmexample$boundary_sf[[1]], fill = "red", alpha = 0.5) + - + geom_sf(data = ips, aes(size = weight)) + - + scale_size_area() - + } - Warning: Using `as.character()` on a quosure is deprecated as of rlang 0.3.0. Please use - `as_label()` or `as_name()` instead. - This warning is displayed once every 8 hours. - Error: Unknown colour name: ~ + 12. │ └─ggplot2 (local) f(l = layers[[i]], d = data[[i]]) + 13. │ └─l$compute_geom_2(d, theme = plot$theme) + 14. │ └─ggplot2 (local) compute_geom_2(..., self = self) + 15. │ └─self$geom$use_defaults(...) + 16. └─base::.handleSimpleError(...) + 17. └─rlang (local) h(simpleError(msg, call)) + 18. └─handlers[[1L]](cnd) + 19. └─cli::cli_abort(...) + 20. └─rlang::abort(...) Execution halted ``` -## In both - -* checking installed package size ... NOTE - ``` - installed size is 16.7Mb - sub-directories of 1Mb or more: - libs 14.1Mb - ``` - -# forestecology +# crplyr
-* Version: 0.2.0 -* GitHub: https://github.com/rudeboybert/forestecology -* Source code: https://github.com/cran/forestecology -* Date/Publication: 2021-10-02 13:30:05 UTC -* Number of recursive dependencies: 102 +* Version: 0.4.0 +* GitHub: https://github.com/Crunch-io/crplyr +* Source code: https://github.com/cran/crplyr +* Date/Publication: 2023-03-21 21:50:02 UTC +* Number of recursive dependencies: 88 -Run `revdepcheck::cloud_details(, "forestecology")` for more info +Run `revdepcheck::cloud_details(, "crplyr")` for more info
## Newly broken -* checking examples ... ERROR +* checking tests ... ERROR ``` - Running examples in ‘forestecology-Ex.R’ failed - The error most likely occurred in: - - > ### Name: add_buffer_variable - > ### Title: Identify trees in the buffer region - > ### Aliases: add_buffer_variable - > - > ### ** Examples - > - > library(tibble) + Running ‘spelling.R’ + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(httptest) + Loading required package: testthat + > test_check("crplyr") + Loading required package: crplyr + Loading required package: crunch + ... - 17. └─ggplot2 (local) FUN(X[[i]], ...) - 18. └─g$draw_key(data, g$params, key_size) - 19. └─ggplot2 (local) draw_key(...) - 20. └─ggplot2::draw_key_point(data, params, size) - 21. ├─grid::pointsGrob(...) - 22. │ └─grid::grob(...) - 23. └─ggplot2::ggpar(...) - 24. └─rlang:::Ops.quosure(pointsize, .pt) - 25. └─rlang::abort(...) - Execution halted + 7. └─ggplot2:::print.ggplot(p) + 8. ├─ggplot2::ggplot_gtable(data) + 9. └─ggplot2:::ggplot_gtable.ggplot_built(data) + 10. └─ggplot2::calc_element("plot.margin", theme) + 11. └─cli::cli_abort(...) + 12. └─rlang::abort(...) + + [ FAIL 1 | WARN 0 | SKIP 0 | PASS 172 ] + Error: Test failures + Execution halted ``` * checking running R code from vignettes ... ERROR ``` Errors in running code in vignettes: - when running code in ‘forestecology.Rmd’ + when running code in ‘plotting.Rmd’ ... + equals, is_less_than, not + - > ggplot() + geom_sf(data = census_1_ex %>% sf::st_as_sf(coords = c("gx", - + "gy")), aes(col = sp, size = dbh)) - Warning: Using `as.character()` on a quosure is deprecated as of rlang 0.3.0. Please use - `as_label()` or `as_name()` instead. - This warning is displayed once every 8 hours. + > ds <- loadDataset("https://app.crunch.io/api/datasets/5c9336/") - When sourcing ‘forestecology.R’: - Error: Unknown colour name: ~ + > autoplot(ds$CompanySize) + + When sourcing ‘plotting.R’: + Error: Theme element `plot.margin` must have class . Execution halted - ‘forestecology.Rmd’ using ‘UTF-8’... failed + ‘plotting.Rmd’ using ‘UTF-8’... failed ``` * checking re-building of vignette outputs ... NOTE ``` Error(s) in re-building vignettes: ... - --- re-building ‘forestecology.Rmd’ using rmarkdown + --- re-building ‘plotting.Rmd’ using rmarkdown - Quitting from lines at lines 64-69 [unnamed-chunk-3] (forestecology.Rmd) - Error: processing vignette 'forestecology.Rmd' failed with diagnostics: - Unknown colour name: ~ - --- failed re-building ‘forestecology.Rmd’ + Quitting from lines 35-36 [basic-card-plots] (plotting.Rmd) + Error: processing vignette 'plotting.Rmd' failed with diagnostics: + Theme element `plot.margin` must have class . + --- failed re-building ‘plotting.Rmd’ SUMMARY: processing the following file failed: - ‘forestecology.Rmd’ + ‘plotting.Rmd’ Error: Vignette re-building failed. Execution halted ``` -## In both - -* checking dependencies in R code ... NOTE - ``` - Namespaces in Imports field not imported from: - ‘blockCV’ ‘patchwork’ - All declared Imports should be used. - ``` - -# frailtyEM +# ctrialsgov
-* Version: 1.0.1 -* GitHub: https://github.com/tbalan/frailtyEM -* Source code: https://github.com/cran/frailtyEM -* Date/Publication: 2019-09-22 13:00:10 UTC -* Number of recursive dependencies: 78 +* Version: 0.2.5 +* GitHub: NA +* Source code: https://github.com/cran/ctrialsgov +* Date/Publication: 2021-10-18 16:00:02 UTC +* Number of recursive dependencies: 100 -Run `revdepcheck::cloud_details(, "frailtyEM")` for more info +Run `revdepcheck::cloud_details(, "ctrialsgov")` for more info
## Newly broken -* checking examples ... ERROR +* checking tests ... ERROR ``` - Running examples in ‘frailtyEM-Ex.R’ failed - The error most likely occurred in: - - > ### Name: summary.emfrail - > ### Title: Summary for 'emfrail' objects - > ### Aliases: summary.emfrail - > - > ### ** Examples - > - > data("bladder") - ... - - The following object is masked from ‘package:graphics’: - - layout - - > ggplotly(pl2) - Error in compute_geom_2(..., self = self) : - argument "theme" is missing, with no default - Calls: ggplotly ... use_defaults -> eval_from_theme -> %||% -> calc_element - Execution halted - ``` - -## In both - -* checking LazyData ... NOTE - ``` - 'LazyData' is specified without a 'data' directory - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘frailtyEM_manual.Rnw’ using Sweave - Loading required package: survival - Loading required package: gridExtra - Warning: The `` argument of `guides()` cannot be `FALSE`. Use - "none" instead as of ggplot2 3.3.4. - Warning: Removed 2 rows containing missing values or values outside - the scale range (`geom_path()`). - Warning in data("kidney") : data set ‘kidney’ not found - Warning in emfrail(Surv(time, status) ~ age + sex + cluster(id), data = kidney, : + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(ctrialsgov) + > + > test_check("ctrialsgov") + [NCT04553939] ible Local Advanved |Bladder| Cancer + [NCT03517995] of Sulforaphane in |Bladder| Cancer Chemoprevent + [NCT04210479] Comparison of |Bladder| Filling vs. Non-Fil ... - l.179 \RequirePackage{grfext}\relax - ^^M - ! ==> Fatal error occurred, no output PDF file produced! - --- failed re-building ‘frailtyEM_manual.Rnw’ - - SUMMARY: processing the following file failed: - ‘frailtyEM_manual.Rnw’ - - Error: Vignette re-building failed. - Execution halted - ``` - -# FuncNN - -
- -* Version: 1.0 -* GitHub: https://github.com/b-thi/FuncNN -* Source code: https://github.com/cran/FuncNN -* Date/Publication: 2020-09-15 09:40:15 UTC -* Number of recursive dependencies: 170 - -Run `revdepcheck::cloud_details(, "FuncNN")` for more info - -
- -## Newly broken - -* checking whether package ‘FuncNN’ can be installed ... WARNING - ``` - Found the following significant warnings: - Warning: replacing previous import ‘ggplot2::ggpar’ by ‘ggpubr::ggpar’ when loading ‘FuncNN’ - See ‘/tmp/workdir/FuncNN/new/FuncNN.Rcheck/00install.out’ for details. + ▆ + 1. ├─ctrialsgov::ctgov_to_plotly(p) at test-plot.R:12:3 + 2. └─ctrialsgov:::ctgov_to_plotly.ctgov_bar_plot(p) + 3. ├─plotly::ggplotly(p, tooltip = "text") + 4. └─plotly:::ggplotly.ggplot(p, tooltip = "text") + 5. └─plotly::gg2list(...) + + [ FAIL 1 | WARN 6 | SKIP 0 | PASS 43 ] + Error: Test failures + Execution halted ``` ## In both -* checking dependencies in R code ... NOTE +* checking data for non-ASCII characters ... NOTE ``` - Namespace in Imports field not imported from: ‘foreach’ - All declared Imports should be used. + Note: found 1350 marked UTF-8 strings ``` -# geomander +# cubble
-* Version: 2.3.0 -* GitHub: https://github.com/christopherkenny/geomander -* Source code: https://github.com/cran/geomander -* Date/Publication: 2024-02-15 21:20:02 UTC -* Number of recursive dependencies: 124 +* Version: 0.3.0 +* GitHub: https://github.com/huizezhang-sherry/cubble +* Source code: https://github.com/cran/cubble +* Date/Publication: 2023-06-30 03:40:02 UTC +* Number of recursive dependencies: 144 -Run `revdepcheck::cloud_details(, "geomander")` for more info +Run `revdepcheck::cloud_details(, "cubble")` for more info
## Newly broken -* checking examples ... ERROR - ``` - Running examples in ‘geomander-Ex.R’ failed - The error most likely occurred in: - - > ### Name: geo_plot_group - > ### Title: Create Plots of Shapes by Group with Connected Components - > ### Colored - > ### Aliases: geo_plot_group - > - > ### ** Examples - > - ... - 15. └─ggplot2 (local) FUN(X[[i]], ...) - 16. └─base::lapply(...) - 17. └─ggplot2 (local) FUN(X[[i]], ...) - 18. └─g$draw_key(data, g$params, key_size) - 19. └─ggplot2 (local) draw_key(...) - 20. └─ggplot2::draw_key_polygon(data, params, size) - 21. └─rlang:::Summary.quosure(from_theme(thin), 1.524, na.rm = FALSE) - 22. └─rlang:::abort_quosure_op("Summary", .Generic) - 23. └─rlang::abort(...) - Execution halted - ``` - * checking running R code from vignettes ... ERROR ``` Errors in running code in vignettes: - when running code in ‘Redistricting_School_Districts.Rmd’ + when running code in ‘cb5match.Rmd’ ... - + fill = NA, lwd = 1.5) - - When sourcing ‘Redistricting_School_Districts.R’: - Error: Summary operations are not defined for quosures. Do you need to unquote - the quosure? + > p2 <- res_tm_long %>% ggplot(aes(x = date, y = matched, + + group = type, color = type)) + geom_line() + facet_wrap(vars(group)) + + + scale_c .... [TRUNCATED] - # Bad: min(myquosure) + > (p1 | p2) + patchwork::plot_layout(guides = "collect") + + + plot_annotation(tag_levels = "a") & theme(legend.position = "bottom") - # Good: min(!!myquosure) + ... + When sourcing ‘cb6interactive.R’: + Error: subscript out of bounds Execution halted - ‘Merging_Election_Data.Rmd’ using ‘UTF-8’... OK - ‘Redistricting_School_Districts.Rmd’ using ‘UTF-8’... failed + ‘cb1class.Rmd’ using ‘UTF-8’... OK + ‘cb2create.Rmd’ using ‘UTF-8’... OK + ‘cb3tsibblesf.Rmd’ using ‘UTF-8’... OK + ‘cb4glyph.Rmd’ using ‘UTF-8’... OK + ‘cb5match.Rmd’ using ‘UTF-8’... failed + ‘cb6interactive.Rmd’ using ‘UTF-8’... failed ``` * checking re-building of vignette outputs ... NOTE ``` Error(s) in re-building vignettes: - --- re-building ‘Merging_Election_Data.Rmd’ using rmarkdown + --- re-building ‘cb1class.Rmd’ using rmarkdown + --- finished re-building ‘cb1class.Rmd’ + + --- re-building ‘cb2create.Rmd’ using rmarkdown + --- finished re-building ‘cb2create.Rmd’ + + --- re-building ‘cb3tsibblesf.Rmd’ using rmarkdown + --- finished re-building ‘cb3tsibblesf.Rmd’ + + --- re-building ‘cb4glyph.Rmd’ using rmarkdown ``` ## In both * checking installed package size ... NOTE ``` - installed size is 8.3Mb + installed size is 5.6Mb sub-directories of 1Mb or more: - data 3.3Mb - libs 4.1Mb + data 3.0Mb + doc 1.3Mb ``` -# geomtextpath +# dabestr
-* Version: 0.1.3 -* GitHub: https://github.com/AllanCameron/geomtextpath -* Source code: https://github.com/cran/geomtextpath -* Date/Publication: 2024-03-12 16:30:03 UTC -* Number of recursive dependencies: 94 +* Version: 2023.9.12 +* GitHub: https://github.com/ACCLAB/dabestr +* Source code: https://github.com/cran/dabestr +* Date/Publication: 2023-10-13 11:50:06 UTC +* Number of recursive dependencies: 85 -Run `revdepcheck::cloud_details(, "geomtextpath")` for more info +Run `revdepcheck::cloud_details(, "dabestr")` for more info
@@ -3399,26 +3489,26 @@ Run `revdepcheck::cloud_details(, "geomtextpath")` for more info * checking examples ... ERROR ``` - Running examples in ‘geomtextpath-Ex.R’ failed + Running examples in ‘dabestr-Ex.R’ failed The error most likely occurred in: - > ### Name: geom_textsf - > ### Title: Visualise sf objects with labels - > ### Aliases: geom_textsf geom_labelsf + > ### Name: dabest_plot + > ### Title: Producing an estimation plot + > ### Aliases: dabest_plot > > ### ** Examples > - > ggplot(waterways) + + > # Loading of the dataset ... - 19. │ ├─rlang::inject(self$draw_panel(data, panel_params, coord, !!!params)) - 20. │ └─self$draw_panel(data, panel_params, coord, na.rm = FALSE, legend = "polygon") - 21. │ └─geomtextpath (local) draw_panel(...) - 22. │ └─geomtextpath:::sf_textgrob(...) - 23. └─base::.handleSimpleError(...) - 24. └─rlang (local) h(simpleError(msg, call)) - 25. └─handlers[[1L]](cnd) - 26. └─cli::cli_abort(...) - 27. └─rlang::abort(...) + 7. └─cowplot:::as_gtable.default(x) + 8. ├─cowplot::as_grob(plot) + 9. └─cowplot:::as_grob.ggplot(plot) + 10. └─ggplot2::ggplotGrob(plot) + 11. ├─ggplot2::ggplot_gtable(ggplot_build(x)) + 12. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) + 13. └─ggplot2::calc_element("plot.margin", theme) + 14. └─cli::cli_abort(...) + 15. └─rlang::abort(...) Execution halted ``` @@ -3427,100 +3517,87 @@ Run `revdepcheck::cloud_details(, "geomtextpath")` for more info Running ‘testthat.R’ Running the tests in ‘tests/testthat.R’ failed. Complete output: - > library(testthat) - > library(geomtextpath) - Loading required package: ggplot2 - > - > test_check("geomtextpath") - [ FAIL 1 | WARN 0 | SKIP 3 | PASS 465 ] - + > # This file is part of the standard setup for testthat. + > # It is recommended that you do not modify it. + > # + > # Where should you do additional test configuration? + > # Learn more about the roles of various files in: + > # * https://r-pkgs.org/tests.html + > # * https://testthat.r-lib.org/reference/test_package.html#special-files ... - ══ Failed tests ════════════════════════════════════════════════════════════════ - ── Error ('test-sf.R:91:3'): We can make grobs from sf features ──────────────── - Error in `(x$boxlinewidth %||% defaults$linewidth[type_ind]) * 3.779528`: non-numeric argument to binary operator - Backtrace: - ▆ - 1. └─geomtextpath:::sf_textgrob(river, as_textbox = TRUE) at test-sf.R:91:3 - - [ FAIL 1 | WARN 0 | SKIP 3 | PASS 465 ] + • 001_plotter/proportion-sequential-mean-diff.svg + • 001_plotter/proportion-unpaired-mean-diff-float-false.svg + • 001_plotter/proportion-unpaired-mean-diff-float-true.svg + • 001_plotter/proportion-unpaired-multigroup-mean-diff.svg + • 001_plotter/two-groups-unpaired-mean-diff-colour-float-false.svg + • 001_plotter/two-groups-unpaired-mean-diff-colour-float-true.svg + • 001_plotter/two-groups-unpaired-mean-diff-float-false.svg + • 001_plotter/two-groups-unpaired-mean-diff-float-true.svg Error: Test failures Execution halted ``` -# germinationmetrics - -
- -* Version: 0.1.8 -* GitHub: https://github.com/aravind-j/germinationmetrics -* Source code: https://github.com/cran/germinationmetrics -* Date/Publication: 2023-08-18 18:02:32 UTC -* Number of recursive dependencies: 92 - -Run `revdepcheck::cloud_details(, "germinationmetrics")` for more info - -
- -## Newly broken - -* checking re-building of vignette outputs ... ERROR +* checking running R code from vignettes ... ERROR ``` - Error(s) in re-building vignettes: + Errors in running code in vignettes: + when running code in ‘plot_aesthetics.Rmd’ ... - --- re-building ‘Introduction.Rmd’ using rmarkdown_notangle - ! Undefined control sequence. - l.108 \NewDocumentCommand - \citeproctext{}{} - - Error: processing vignette 'Introduction.Rmd' failed with diagnostics: - LaTeX failed to compile /tmp/workdir/germinationmetrics/new/germinationmetrics.Rcheck/vign_test/germinationmetrics/vignettes/Introduction.tex. See https://yihui.org/tinytex/r/#debugging for debugging tips. See Introduction.log for more info. - --- failed re-building ‘Introduction.Rmd’ + + x = Group, y = Success, idx = list(c("Control 1", "Test 1", + + "Test 2", "Te ..." ... [TRUNCATED] - SUMMARY: processing the following file failed: - ‘Introduction.Rmd’ + > dabest_plot(dabest_twogroup_obj.mean_diff, float_contrast = TRUE, + + swarm_x_text = 30, swarm_y_text = 1, contrast_x_text = 30, + + contrast_ .... [TRUNCATED] - Error: Vignette re-building failed. + ... + Error: Theme element `plot.margin` must have class . Execution halted + + ‘datasets.Rmd’ using ‘UTF-8’... OK + ‘plot_aesthetics.Rmd’ using ‘UTF-8’... failed + ‘tutorial_basics.Rmd’ using ‘UTF-8’... failed + ‘tutorial_deltadelta.Rmd’ using ‘UTF-8’... failed + ‘tutorial_minimeta.Rmd’ using ‘UTF-8’... failed + ‘tutorial_proportion_plots.Rmd’ using ‘UTF-8’... failed + ‘tutorial_repeated_measures.Rmd’ using ‘UTF-8’... failed ``` -## Newly fixed - -* checking re-building of vignette outputs ... WARNING +* checking re-building of vignette outputs ... NOTE ``` Error(s) in re-building vignettes: - --- re-building ‘Introduction.Rmd’ using rmarkdown_notangle - Trying to upgrade TinyTeX automatically now... - If reinstallation fails, try install_tinytex() again. Then install the following packages: + --- re-building ‘datasets.Rmd’ using rmarkdown + --- finished re-building ‘datasets.Rmd’ - tinytex::tlmgr_install(c("amscls", "amsfonts", "amsmath", "atbegshi", "atveryend", "auxhook", "babel", "bibtex", "bigintcalc", "bitset", "booktabs", "cm", "ctablestack", "dehyph", "dvipdfmx", "dvips", "ec", "epstopdf-pkg", "etex", "etexcmds", "etoolbox", "euenc", "everyshi", "fancyvrb", "filehook", "firstaid", "float", "fontspec", "framed", "geometry", "gettitlestring", "glyphlist", "graphics", "graphics-cfg", "graphics-def", "helvetic", "hycolor", "hyperref", "hyph-utf8", "hyphen-base", "iftex", "inconsolata", "infwarerr", "intcalc", "knuth-lib", "kpathsea", "kvdefinekeys", "kvoptions", "kvsetkeys", "l3backend", "l3kernel", "l3packages", "latex", "latex-amsmath-dev", "latex-bin", "latex-fonts", "latex-tools-dev", "latexconfig", "latexmk", "letltxmacro", "lm", "lm-math", "ltxcmds", "lua-alt-getopt", "lua-uni-algos", "luahbtex", "lualatex-math", "lualibs", "luaotfload", "luatex", "luatexbase", "mdwtools", "metafont", "mfware", "modes", "natbib", "pdfescape", "pdftex", "pdftexcmds", "plain", "psnfss", "refcount", "rerunfilecheck", "scheme-infraonly", "selnolig", "stringenc", "symbol", "tex", "tex-ini-files", "texlive-scripts", "texlive.infra", "times", "tipa", "tools", "unicode-data", "unicode-math", "uniquecounter", "url", "xcolor", "xetex", "xetexconfig", "xkeyval", "xunicode", "zapfding")) + --- re-building ‘plot_aesthetics.Rmd’ using rmarkdown - The directory /opt/TinyTeX/texmf-local is not empty. It will be backed up to /tmp/RtmpSUduR6/filefb36377d31c and restored later. - - tlmgr: no auxiliary texmf trees defined, so nothing removed + Quitting from lines 81-89 [unnamed-chunk-3] (plot_aesthetics.Rmd) + Error: processing vignette 'plot_aesthetics.Rmd' failed with diagnostics: + Theme element `plot.margin` must have class . + --- failed re-building ‘plot_aesthetics.Rmd’ ... + Theme element `plot.margin` must have class . + --- failed re-building ‘tutorial_repeated_measures.Rmd’ - Error: processing vignette 'Introduction.Rmd' failed with diagnostics: - LaTeX failed to compile /tmp/workdir/germinationmetrics/old/germinationmetrics.Rcheck/vign_test/germinationmetrics/vignettes/Introduction.tex. See https://yihui.org/tinytex/r/#debugging for debugging tips. See Introduction.log for more info. - --- failed re-building ‘Introduction.Rmd’ - - SUMMARY: processing the following file failed: - ‘Introduction.Rmd’ + SUMMARY: processing the following files failed: + ‘plot_aesthetics.Rmd’ ‘tutorial_basics.Rmd’ ‘tutorial_deltadelta.Rmd’ + ‘tutorial_minimeta.Rmd’ ‘tutorial_proportion_plots.Rmd’ + ‘tutorial_repeated_measures.Rmd’ Error: Vignette re-building failed. Execution halted ``` -# gganimate +# DAISIEprep
-* Version: 1.0.9 -* GitHub: https://github.com/thomasp85/gganimate -* Source code: https://github.com/cran/gganimate -* Date/Publication: 2024-02-27 14:00:03 UTC -* Number of recursive dependencies: 97 +* Version: 0.4.0 +* GitHub: https://github.com/joshwlambert/DAISIEprep +* Source code: https://github.com/cran/DAISIEprep +* Date/Publication: 2024-04-02 11:30:06 UTC +* Number of recursive dependencies: 149 -Run `revdepcheck::cloud_details(, "gganimate")` for more info +Run `revdepcheck::cloud_details(, "DAISIEprep")` for more info
@@ -3532,61 +3609,77 @@ Run `revdepcheck::cloud_details(, "gganimate")` for more info Running the tests in ‘tests/testthat.R’ failed. Complete output: > library(testthat) - > library(gganimate) - Loading required package: ggplot2 + > library(DAISIEprep) > - > test_check("gganimate") - [ FAIL 6 | WARN 0 | SKIP 1 | PASS 0 ] + > test_check("DAISIEprep") + [ FAIL 2 | WARN 2 | SKIP 14 | PASS 2213 ] + ══ Skipped tests (14) ══════════════════════════════════════════════════════════ ... - 26. │ └─ggplot2::calc_element("geom", theme) - 27. └─base::.handleSimpleError(...) - 28. └─rlang (local) h(simpleError(msg, call)) - 29. └─handlers[[1L]](cnd) - 30. └─cli::cli_abort(...) - 31. └─rlang::abort(...) + 23. └─ggplot2::ggplotGrob(plot) + 24. ├─ggplot2::ggplot_gtable(ggplot_build(x)) + 25. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) + 26. └─ggplot2::calc_element("plot.margin", theme) + 27. └─cli::cli_abort(...) + 28. └─rlang::abort(...) - [ FAIL 6 | WARN 0 | SKIP 1 | PASS 0 ] + [ FAIL 2 | WARN 2 | SKIP 14 | PASS 2213 ] Error: Test failures Execution halted ``` -* checking running R code from vignettes ... ERROR +# dataresqc + +
+ +* Version: 1.1.1 +* GitHub: NA +* Source code: https://github.com/cran/dataresqc +* Date/Publication: 2023-04-02 22:00:02 UTC +* Number of recursive dependencies: 49 + +Run `revdepcheck::cloud_details(, "dataresqc")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR ``` - Errors in running code in vignettes: - when running code in ‘gganimate.Rmd’ - ... - + state_length = 1) - - > anim + Running examples in ‘dataresqc-Ex.R’ failed + The error most likely occurred in: - When sourcing ‘gganimate.R’: - Error: Problem while setting up geom aesthetics. - ℹ Error occurred in the 1st layer. - Caused by error in `compute_geom_2()`: - ! argument "theme" is missing, with no default + > ### Name: plot_decimals + > ### Title: Plot decimals + > ### Aliases: plot_decimals + > + > ### ** Examples + > + > plot_decimals(Rosario$Tx, outfile = paste0(tempdir(),"/test.pdf")) + ... + 1. └─dataresqc::plot_decimals(...) + 2. └─dataresqc:::multiplot(plotlist = plots) + 3. ├─base::print(plots[[1]]) + 4. └─ggplot2:::print.ggplot(plots[[1]]) + 5. ├─ggplot2::ggplot_gtable(data) + 6. └─ggplot2:::ggplot_gtable.ggplot_built(data) + 7. └─ggplot2::calc_element("plot.margin", theme) + 8. └─cli::cli_abort(...) + 9. └─rlang::abort(...) Execution halted - - ‘gganimate.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘gganimate.Rmd’ using rmarkdown ``` -# ggautomap +# ddtlcm
-* Version: 0.3.2 -* GitHub: https://github.com/cidm-ph/ggautomap -* Source code: https://github.com/cran/ggautomap -* Date/Publication: 2023-05-24 09:00:02 UTC -* Number of recursive dependencies: 73 +* Version: 0.2.1 +* GitHub: https://github.com/limengbinggz/ddtlcm +* Source code: https://github.com/cran/ddtlcm +* Date/Publication: 2024-04-04 02:32:57 UTC +* Number of recursive dependencies: 150 -Run `revdepcheck::cloud_details(, "ggautomap")` for more info +Run `revdepcheck::cloud_details(, "ddtlcm")` for more info
@@ -3594,77 +3687,111 @@ Run `revdepcheck::cloud_details(, "ggautomap")` for more info * checking examples ... ERROR ``` - Running examples in ‘ggautomap-Ex.R’ failed + Running examples in ‘ddtlcm-Ex.R’ failed The error most likely occurred in: - > ### Name: geom_centroids - > ### Title: Geographic centroid of locations - > ### Aliases: geom_centroids + > ### Name: plot.summary.ddt_lcm + > ### Title: Plot the MAP tree and class profiles of summarized DDT-LCM + > ### results + > ### Aliases: plot.summary.ddt_lcm > > ### ** Examples > - > library(ggplot2) ... - > cartographer::nc_type_example_2 |> - + head(n = 100) |> - + ggplot(aes(location = county)) + - + geom_boundaries(feature_type = "sf.nc") + - + geom_centroids(aes(colour = type), position = position_circle_repel_sf(scale = 6), size = 0.5) + - + coord_automap(feature_type = "sf.nc") - Error in valid.pch(x$pch) : - 'language' object cannot be coerced to type 'integer' - Calls: ... validGrob.grob -> validDetails -> validDetails.points -> valid.pch + 15. └─cowplot:::as_gtable.default(x) + 16. ├─cowplot::as_grob(plot) + 17. └─cowplot:::as_grob.ggplot(plot) + 18. └─ggplot2::ggplotGrob(plot) + 19. ├─ggplot2::ggplot_gtable(ggplot_build(x)) + 20. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) + 21. └─ggplot2::calc_element("plot.margin", theme) + 22. └─cli::cli_abort(...) + 23. └─rlang::abort(...) Execution halted ``` +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > # This file is part of the standard setup for testthat. + > # It is recommended that you do not modify it. + > # + > # Where should you do additional test configuration? + > # Learn more about the roles of various files in: + > # * https://r-pkgs.org/tests.html + > # * https://testthat.r-lib.org/reference/test_package.html#special-files + ... + label_size = .lab$size, label_fontfamily = .lab$family, label_fontface = .lab$face, + label_colour = .lab$color, label_x = .lab$label.x, label_y = .lab$label.y, + hjust = .lab$hjust, vjust = .lab$vjust, align = align, rel_widths = widths, + rel_heights = heights, legend = legend, common.legend.grob = legend.grob)`: i In index: 1. + Caused by error in `ggplot_gtable()`: + ! Theme element `plot.margin` must have class . + + [ FAIL 1 | WARN 30 | SKIP 0 | PASS 62 ] + Error: Test failures + Execution halted + ``` + * checking running R code from vignettes ... ERROR ``` Errors in running code in vignettes: - when running code in ‘ggautomap.Rmd’ + when running code in ‘ddtlcm-demo.Rmd’ ... - 5 2768 Blacktown Western Sydney 2021 A - 6 2766 Blacktown Western Sydney 2021 B + > response_prob <- sim_data$response_prob + + > tree_with_parameter <- sim_data$tree_with_parameter - > covid_cases_nsw %>% ggplot(aes(location = lga)) + - + geom_boundaries(feature_type = "nswgeo.lga") + geom_geoscatter(aes(colour = type), - + s .... [TRUNCATED] + > plot_tree_with_heatmap(tree_with_parameter, response_prob, + + item_membership_list) - When sourcing ‘ggautomap.R’: - Error: 'language' object cannot be coerced to type 'integer' + When sourcing ‘ddtlcm-demo.R’: + Error: Theme element `plot.margin` must have class . Execution halted - ‘ggautomap.Rmd’ using ‘UTF-8’... failed + ‘ddtlcm-demo.Rmd’ using ‘UTF-8’... failed ``` * checking re-building of vignette outputs ... NOTE ``` Error(s) in re-building vignettes: ... - --- re-building ‘ggautomap.Rmd’ using rmarkdown + --- re-building ‘ddtlcm-demo.Rmd’ using rmarkdown - Quitting from lines at lines 47-54 [scatter] (ggautomap.Rmd) - Error: processing vignette 'ggautomap.Rmd' failed with diagnostics: - 'language' object cannot be coerced to type 'integer' - --- failed re-building ‘ggautomap.Rmd’ + Quitting from lines 134-139 [unnamed-chunk-5] (ddtlcm-demo.Rmd) + Error: processing vignette 'ddtlcm-demo.Rmd' failed with diagnostics: + Theme element `plot.margin` must have class . + --- failed re-building ‘ddtlcm-demo.Rmd’ SUMMARY: processing the following file failed: - ‘ggautomap.Rmd’ + ‘ddtlcm-demo.Rmd’ Error: Vignette re-building failed. Execution halted ``` -# ggdark +## In both + +* checking installed package size ... NOTE + ``` + installed size is 9.3Mb + sub-directories of 1Mb or more: + data 8.0Mb + ``` + +# dfoliatR
-* Version: 0.2.1 -* GitHub: NA -* Source code: https://github.com/cran/ggdark -* Date/Publication: 2019-01-11 17:30:06 UTC -* Number of recursive dependencies: 46 +* Version: 0.3.0 +* GitHub: https://github.com/chguiterman/dfoliatR +* Source code: https://github.com/cran/dfoliatR +* Date/Publication: 2023-08-09 22:10:02 UTC +* Number of recursive dependencies: 109 -Run `revdepcheck::cloud_details(, "ggdark")` for more info +Run `revdepcheck::cloud_details(, "dfoliatR")` for more info
@@ -3672,26 +3799,26 @@ Run `revdepcheck::cloud_details(, "ggdark")` for more info * checking examples ... ERROR ``` - Running examples in ‘ggdark-Ex.R’ failed + Running examples in ‘dfoliatR-Ex.R’ failed The error most likely occurred in: - > ### Name: dark_mode - > ### Title: Activate dark mode on a 'ggplot2' theme - > ### Aliases: dark_mode + > ### Name: plot_outbreak + > ### Title: Produce a stacked plot to present composited, site-level insect + > ### outbreak chronologies + > ### Aliases: plot_outbreak > > ### ** Examples > - > library(ggplot2) ... - > - > p1 <- ggplot(iris, aes(Sepal.Width, Sepal.Length, color = Species)) + - + geom_point() - > - > p1 # theme returned by theme_get() - > p1 + dark_mode() # activate dark mode on theme returned by theme_get() - Error in match(x, table, nomatch = 0L) : - 'match' requires vector arguments - Calls: dark_mode -> %in% + 14. └─cowplot:::as_gtable.default(x) + 15. ├─cowplot::as_grob(plot) + 16. └─cowplot:::as_grob.ggplot(plot) + 17. └─ggplot2::ggplotGrob(plot) + 18. ├─ggplot2::ggplot_gtable(ggplot_build(x)) + 19. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) + 20. └─ggplot2::calc_element("plot.margin", theme) + 21. └─cli::cli_abort(...) + 22. └─rlang::abort(...) Execution halted ``` @@ -3701,43 +3828,102 @@ Run `revdepcheck::cloud_details(, "ggdark")` for more info Running the tests in ‘tests/testthat.R’ failed. Complete output: > library(testthat) - > library(ggdark) + > library(dfoliatR) > - > test_check("ggdark") - [ FAIL 1 | WARN 0 | SKIP 0 | PASS 0 ] + > test_check("dfoliatR") + [ FAIL 1 | WARN 9 | SKIP 2 | PASS 12 ] - ══ Failed tests ════════════════════════════════════════════════════════════════ + ══ Skipped tests (2) ═══════════════════════════════════════════════════════════ ... - ── Error ('test_dark_mode.R:10:1'): (code run outside of `test_that()`) ──────── - Error in `match(x, table, nomatch = 0L)`: 'match' requires vector arguments - Backtrace: - ▆ - 1. └─ggdark::dark_mode(light_theme) at test_dark_mode.R:10:1 - 2. └─geoms[["GeomPoint"]]$default_aes$colour %in% ... + label_size = .lab$size, label_fontfamily = .lab$family, label_fontface = .lab$face, + label_colour = .lab$color, label_x = .lab$label.x, label_y = .lab$label.y, + hjust = .lab$hjust, vjust = .lab$vjust, align = align, rel_widths = widths, + rel_heights = heights, legend = legend, common.legend.grob = legend.grob)`: ℹ In index: 1. + Caused by error in `ggplot_gtable()`: + ! Theme element `plot.margin` must have class . - [ FAIL 1 | WARN 0 | SKIP 0 | PASS 0 ] + [ FAIL 1 | WARN 9 | SKIP 2 | PASS 12 ] Error: Test failures Execution halted ``` -## In both +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘intro-to-dfoliatR.Rmd’ + ... + | 1683| 3| 2| 66.7| 1| 33.3| 0.3466| -1.7847|outbreak | + | 1684| 3| 2| 66.7| 0| 0.0| 0.6063| -1.0589|outbreak | + + > plot_outbreak(dmj_obr) + + When sourcing ‘intro-to-dfoliatR.R’: + Error: ℹ In index: 1. + Caused by error in `ggplot_gtable()`: + ! Theme element `plot.margin` must have class . + Execution halted + + ‘intro-to-dfoliatR.Rmd’ using ‘UTF-8’... failed + ``` -* checking LazyData ... NOTE +* checking re-building of vignette outputs ... NOTE ``` - 'LazyData' is specified without a 'data' directory + Error(s) in re-building vignettes: + --- re-building ‘intro-to-dfoliatR.Rmd’ using rmarkdown ``` -# ggdist +# directlabels
-* Version: 3.3.2 -* GitHub: https://github.com/mjskay/ggdist -* Source code: https://github.com/cran/ggdist -* Date/Publication: 2024-03-05 05:30:23 UTC -* Number of recursive dependencies: 127 +* Version: 2024.1.21 +* GitHub: https://github.com/tdhock/directlabels +* Source code: https://github.com/cran/directlabels +* Date/Publication: 2024-01-24 19:20:07 UTC +* Number of recursive dependencies: 81 -Run `revdepcheck::cloud_details(, "ggdist")` for more info +Run `revdepcheck::cloud_details(, "directlabels")` for more info + +
+ +## Newly broken + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘examples.Rmd’ + ... + 6 23 1669 aaa + 7 22 1315 aaa + 8 21 951 aaa + 9 20 610 aaa + 10 19 543 aaa + # ℹ 14 more rows + + When sourcing ‘examples.R’: + Error: Theme element `plot.margin` must have class . + Execution halted + + ‘examples.Rmd’... failed + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘examples.Rmd’ using knitr + ``` + +# disprofas + +
+ +* Version: 0.1.3 +* GitHub: https://github.com/piusdahinden/disprofas +* Source code: https://github.com/cran/disprofas +* Date/Publication: 2021-12-08 12:40:02 UTC +* Number of recursive dependencies: 48 + +Run `revdepcheck::cloud_details(, "disprofas")` for more info
@@ -3745,26 +3931,26 @@ Run `revdepcheck::cloud_details(, "ggdist")` for more info * checking examples ... ERROR ``` - Running examples in ‘ggdist-Ex.R’ failed + Running examples in ‘disprofas-Ex.R’ failed The error most likely occurred in: - > ### Name: Pr_ - > ### Title: Probability expressions in ggdist aesthetics - > ### Aliases: Pr_ p_ + > ### Name: plot.plot_mztia + > ### Title: Plot of the mztia simulation + > ### Aliases: plot.plot_mztia > > ### ** Examples > - > library(ggplot2) + > # Dissolution data of one reference batch and one test batch of n = 6 ... - 2.75, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 1, NULL, NULL, NULL, c(0, 2.2, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, NULL, c(0, 0, 0, 2.2 - ), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0.5, NULL, NULL, NULL, c(0, 2.2, 0, 2.2), NULL, TRUE), list("grey20", NULL, NULL, NULL, FALSE, TRUE), NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 2.75, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 0.75, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, list(), NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, list(NULL, NA, NULL, NULL, TRUE), c(5.5, 5.5, 5.5, 5.5), 11, NULL, NULL, NULL, 1.2, NULL, NULL, 5.5, - NULL, NULL, NULL, NULL, 0.2, NULL, list(NULL, NULL, NULL, 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, NULL, NULL, NULL, TRUE), NULL, "right", NULL, NULL, NULL, "center", NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, c(0, 0, 0, 0), list(), 11, list("grey92", NA, NULL, NULL, TRUE), list(), 5.5, NULL, NULL, list("white", NULL, NULL, NULL, FALSE, TRUE), NULL, list(NULL, 0.5, NULL, NULL, FALSE, TRUE), NULL, NULL, NULL, NULL, FALSE, list(NULL, - "white", NULL, NULL, TRUE), list(NULL, NULL, NULL, 1.2, 0, 1, NULL, NULL, c(0, 0, 5.5, 0), NULL, TRUE), "panel", list(NULL, NULL, NULL, NULL, 0, 1, NULL, NULL, c(0, 0, 5.5, 0), NULL, TRUE), list(NULL, NULL, NULL, 0.8, 1, 1, NULL, NULL, c(5.5, 0, 0, 0), NULL, TRUE), "panel", list(NULL, NULL, NULL, 1.2, 0.5, 0.5, NULL, NULL, NULL, NULL, TRUE), "topleft", NULL, c(5.5, 5.5, 5.5, 5.5), list("grey85", NA, NULL, NULL, TRUE), NULL, NULL, "inherit", "inside", list(NULL, NULL, "grey10", 0.8, NULL, - NULL, NULL, NULL, c(4.4, 4.4, 4.4, 4.4), NULL, TRUE), NULL, NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, NULL, -90, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, NULL, 90, NULL, NULL, NULL, TRUE), NULL, 2.75, 2.75)) - Error in use_defaults(..., self = self) : - unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), NULL, list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.75, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, 90, NULL, c(0, - 2.75, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 1, NULL, NULL, NULL, c(0, 2.2, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL - Calls: ... .handleSimpleError -> h -> -> + 1. ├─base::plot(gg1) + 2. └─disprofas:::plot.plot_mztia(gg1) + 3. ├─base::plot(x$Graph, ...) + 4. └─ggplot2:::plot.ggplot(x$Graph, ...) + 5. ├─ggplot2::ggplot_gtable(data) + 6. └─ggplot2:::ggplot_gtable.ggplot_built(data) + 7. └─ggplot2::calc_element("plot.margin", theme) + 8. └─cli::cli_abort(...) + 9. └─rlang::abort(...) Execution halted ``` @@ -3773,98 +3959,37 @@ Run `revdepcheck::cloud_details(, "ggdist")` for more info Running ‘testthat.R’ Running the tests in ‘tests/testthat.R’ failed. Complete output: - > # This file is part of the standard setup for testthat. - > # It is recommended that you do not modify it. - > # - > # Where should you do additional test configuration? - > # Learn more about the roles of various files in: - > # * https://r-pkgs.org/testing-design.html#sec-tests-files-overview - > # * https://testthat.r-lib.org/articles/special-files.html + > library(testthat) + > library(disprofas) + > + > test_check("disprofas") + [ FAIL 2 | WARN 3 | SKIP 0 | PASS 479 ] + + ══ Failed tests ════════════════════════════════════════════════════════════════ ... - • test.stat_sample_slabinterval/nas-with-na-rm-true.svg - • test.subguide/dots-subguide-with-side-vertical.svg - • test.subguide/integer-subguide-with-zero-range.svg - • test.subguide/slab-subguide-with-inside-labels-vertical.svg - • test.subguide/slab-subguide-with-outside-labels-vert.svg - • test.subguide/slab-subguide-with-outside-labels.svg - • test.subguide/slab-subguide-with-side-vertical.svg - • test.theme_ggdist/facet-titles-on-left.svg + 8. └─ggplot2:::plot.ggplot(x$Graph, ...) + 9. ├─ggplot2::ggplot_gtable(data) + 10. └─ggplot2:::ggplot_gtable.ggplot_built(data) + 11. └─ggplot2::calc_element("plot.margin", theme) + 12. └─cli::cli_abort(...) + 13. └─rlang::abort(...) + + [ FAIL 2 | WARN 3 | SKIP 0 | PASS 479 ] Error: Test failures Execution halted ``` -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘dotsinterval.Rmd’ using rmarkdown - Warning in hook_png(..., cmd = "pngquant", post_process = function(x) { : - cannot find pngquant; please install and put it in PATH - Warning in hook_png(..., cmd = "pngquant", post_process = function(x) { : - cannot find pngquant; please install and put it in PATH - - Quitting from lines at lines 49-161 [dotsinterval_components] (dotsinterval.Rmd) - Error: processing vignette 'dotsinterval.Rmd' failed with diagnostics: - Problem while setting up geom aesthetics. - ... - - --- re-building ‘freq-uncertainty-vis.Rmd’ using rmarkdown - Warning in hook_png(..., cmd = "pngquant", post_process = function(x) { : - cannot find pngquant; please install and put it in PATH - Warning in hook_png(..., cmd = "pngquant", post_process = function(x) { : - cannot find pngquant; please install and put it in PATH - Warning in hook_png(..., cmd = "pngquant", post_process = function(x) { : - cannot find pngquant; please install and put it in PATH - Warning in hook_png(..., cmd = "pngquant", post_process = function(x) { : - cannot find pngquant; please install and put it in PATH - ``` - -## In both - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘dotsinterval.Rmd’ - ... - + xdist = dist)) + geom_hline(yintercept = 0:1, color = "gray95") + - + stat_dotsin .... [TRUNCATED] - - When sourcing ‘dotsinterval.R’: - Error: Problem while setting up geom aesthetics. - ℹ Error occurred in the 2nd layer. - Caused by error in `use_defaults()`: - ... - ℹ Error occurred in the 1st layer. - Caused by error in `use_defaults()`: - ! unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), NULL, list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(7, 0, 0, 0), NULL, FALSE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, 90, NULL, c(0, 7, - 0, 0), NULL, FALSE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(NULL, NULL, - Execution halted - - ‘dotsinterval.Rmd’ using ‘UTF-8’... failed - ‘freq-uncertainty-vis.Rmd’ using ‘UTF-8’... failed - ‘lineribbon.Rmd’ using ‘UTF-8’... failed - ‘slabinterval.Rmd’ using ‘UTF-8’... failed - ``` - -* checking installed package size ... NOTE - ``` - installed size is 5.6Mb - sub-directories of 1Mb or more: - doc 1.3Mb - help 2.0Mb - libs 1.0Mb - ``` - -# ggedit +# distributional
-* Version: 0.4.1 -* GitHub: https://github.com/yonicd/ggedit -* Source code: https://github.com/cran/ggedit -* Date/Publication: 2024-03-04 14:40:02 UTC -* Number of recursive dependencies: 95 +* Version: 0.4.0 +* GitHub: https://github.com/mitchelloharawild/distributional +* Source code: https://github.com/cran/distributional +* Date/Publication: 2024-02-07 13:30:02 UTC +* Number of recursive dependencies: 64 -Run `revdepcheck::cloud_details(, "ggedit")` for more info +Run `revdepcheck::cloud_details(, "distributional")` for more info
@@ -3872,143 +3997,214 @@ Run `revdepcheck::cloud_details(, "ggedit")` for more info * checking examples ... ERROR ``` - Running examples in ‘ggedit-Ex.R’ failed + Running examples in ‘distributional-Ex.R’ failed The error most likely occurred in: - > ### Name: dput.ggedit - > ### Title: Convert ggplot object to a string call - > ### Aliases: dput.ggedit + > ### Name: dist_truncated + > ### Title: Truncate a distribution + > ### Aliases: dist_truncated > > ### ** Examples > - > + > dist <- dist_truncated(dist_normal(2,1), lower = 0) ... - 10. │ │ │ └─base (local) doTryCatch(return(expr), name, parentenv, handler) - 11. │ │ └─base::withCallingHandlers(...) 12. │ └─ggplot2 (local) f(l = layers[[i]], d = data[[i]]) 13. │ └─l$compute_geom_2(d, theme = plot$theme) - 14. └─base::.handleSimpleError(...) - 15. └─rlang (local) h(simpleError(msg, call)) - 16. └─handlers[[1L]](cnd) - 17. └─cli::cli_abort(...) - 18. └─rlang::abort(...) + 14. │ └─ggplot2 (local) compute_geom_2(..., self = self) + 15. │ └─self$geom$use_defaults(...) + 16. └─base::.handleSimpleError(...) + 17. └─rlang (local) h(simpleError(msg, call)) + 18. └─handlers[[1L]](cnd) + 19. └─cli::cli_abort(...) + 20. └─rlang::abort(...) Execution halted ``` -# ggfixest +# dittoViz
-* Version: 0.1.0 -* GitHub: https://github.com/grantmcdermott/ggfixest -* Source code: https://github.com/cran/ggfixest -* Date/Publication: 2023-12-14 08:00:06 UTC -* Number of recursive dependencies: 78 +* Version: 1.0.1 +* GitHub: https://github.com/dtm2451/dittoViz +* Source code: https://github.com/cran/dittoViz +* Date/Publication: 2024-02-02 00:00:12 UTC +* Number of recursive dependencies: 99 -Run `revdepcheck::cloud_details(, "ggfixest")` for more info +Run `revdepcheck::cloud_details(, "dittoViz")` for more info
## Newly broken +* checking examples ... ERROR + ``` + Running examples in ‘dittoViz-Ex.R’ failed + The error most likely occurred in: + + > ### Name: barPlot + > ### Title: Outputs a stacked bar plot to show the percent composition of + > ### samples, groups, clusters, or other groupings + > ### Aliases: barPlot + > + > ### ** Examples + > + ... + 15 3 D 12 32 0.3750000 + 16 4 D 8 32 0.2500000 + > # through hovering the cursor over the relevant parts of the plot + > if (requireNamespace("plotly", quietly = TRUE)) { + + barPlot(example_df, "clustering", group.by = "groups", + + do.hover = TRUE) + + } + Error in pm[[2]] : subscript out of bounds + Calls: barPlot -> -> ggplotly.ggplot -> gg2list + Execution halted + ``` + * checking tests ... ERROR ``` - Running ‘tinytest.R’ - Running the tests in ‘tests/tinytest.R’ failed. + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. Complete output: - > ## Throttle CPU threads if R CMD check (for CRAN) - > - > if (any(grepl("_R_CHECK", names(Sys.getenv()), fixed = TRUE))) { - + # fixest - + if (requireNamespace("fixest", quietly = TRUE)) { - + library(fixest) - + setFixest_nthreads(1) + > library(testthat) + > library(dittoViz) + Loading required package: ggplot2 + > test_check("dittoViz") + [ FAIL 12 | WARN 12 | SKIP 0 | PASS 307 ] + + ══ Failed tests ════════════════════════════════════════════════════════════════ ... - test_nthreads.R............... 0 tests ----- FAILED[]: test_ggiplot.R<52--52> - call| expect_snapshot_plot(p3, label = "ggiplot_simple_ribbon") - diff| 84719 - info| Diff plot saved to: _tinysnapshot_review/ggiplot_simple_ribbon.png - ----- FAILED[]: test_ggiplot.R<54--54> - call| expect_snapshot_plot(p5, label = "ggiplot_simple_mci_ribbon") - diff| 84507 - info| Diff plot saved to: _tinysnapshot_review/ggiplot_simple_mci_ribbon.png - Error: 2 out of 101 tests failed + 2. └─dittoViz::freqPlot(...) + 3. └─dittoViz::yPlot(...) + 4. └─dittoViz:::.warn_or_apply_plotly(p, plots) + 5. ├─plotly::ggplotly(p, tooltip = "text") + 6. └─plotly:::ggplotly.ggplot(p, tooltip = "text") + 7. └─plotly::gg2list(...) + + [ FAIL 12 | WARN 12 | SKIP 0 | PASS 307 ] + Error: Test failures Execution halted ``` -## In both +# dobin + +
+ +* Version: 1.0.4 +* GitHub: NA +* Source code: https://github.com/cran/dobin +* Date/Publication: 2022-08-25 22:52:33 UTC +* Number of recursive dependencies: 147 + +Run `revdepcheck::cloud_details(, "dobin")` for more info + +
+ +## Newly broken * checking running R code from vignettes ... ERROR ``` Errors in running code in vignettes: - when running code in ‘ggiplot.Rmd’ + when running code in ‘dobin.Rmd’ ... - > iplot(list(TWFE = est_twfe_grp, `Sun & Abraham (2020)` = est_sa20_grp), - + ref.line = -1, main = "Staggered treatment: Split mutli-sample") - The degrees of freedom for the t distribution could not be deduced. Using a Normal distribution instead. - Note that you can provide the argument `df.t` directly. + + boxplotLimits = 10) - When sourcing ‘ggiplot.R’: - Error: in iplot(list(TWFE = est_twfe_grp, `Sun & Abraham (2...: - The 1st element of 'object' raises and error: - Error in nb * sd : non-numeric argument to binary operator + > pPx <- O3plotM(pPa) + + > pPx$gO3x + theme(plot.margin = unit(c(0, 2, 0, 0), + + "cm")) + + When sourcing ‘dobin.R’: + Error: Theme element `plot.margin` must have class . Execution halted - ‘ggiplot.Rmd’ using ‘UTF-8’... failed + ‘dobin.Rmd’ using ‘UTF-8’... failed ``` -# ggfortify +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘dobin.Rmd’ using rmarkdown + ``` + +# dogesr
-* Version: 0.4.17 -* GitHub: https://github.com/sinhrks/ggfortify -* Source code: https://github.com/cran/ggfortify -* Date/Publication: 2024-04-17 04:30:04 UTC -* Number of recursive dependencies: 125 +* Version: 0.5.0 +* GitHub: NA +* Source code: https://github.com/cran/dogesr +* Date/Publication: 2023-08-21 11:40:05 UTC +* Number of recursive dependencies: 121 -Run `revdepcheck::cloud_details(, "ggfortify")` for more info +Run `revdepcheck::cloud_details(, "dogesr")` for more info
## Newly broken -* checking tests ... ERROR +* checking re-building of vignette outputs ... NOTE ``` - Running ‘test-all.R’ - Running the tests in ‘tests/test-all.R’ failed. - Complete output: - > library(testthat) - > - > suppressWarnings(RNGversion("3.5.0")) - > set.seed(1, sample.kind = "Rejection") - > - > test_check('ggfortify') - Loading required package: ggfortify + Error(s) in re-building vignettes: + --- re-building ‘counting-doge-families.Rmd’ using rmarkdown + --- finished re-building ‘counting-doge-families.Rmd’ + + --- re-building ‘doge-types.Rmd’ using rmarkdown + + Quitting from lines 48-51 [plot] (doge-types.Rmd) + Error: processing vignette 'doge-types.Rmd' failed with diagnostics: + Theme element `plot.margin` must have class . + --- failed re-building ‘doge-types.Rmd’ + + --- re-building ‘doges-family-types.Rmd’ using rmarkdown + --- finished re-building ‘doges-family-types.Rmd’ + + --- re-building ‘doges-social-network.Rmd’ using rmarkdown + ``` + +## In both + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘counting-doge-families.Rmd’ + ... + > knitr::opts_chunk$set(collapse = TRUE, comment = "#>") + + > devtools::load_all(".") + + When sourcing ‘counting-doge-families.R’: + Error: Could not find a root 'DESCRIPTION' file that starts with '^Package' in + '/tmp/Rtmpt416E4/file12ff49ee8180/vignettes'. ... - - x[3]: "#595959FF" - y[3]: "grey35" - - x[4]: "#595959FF" - y[4]: "grey35" - - [ FAIL 5 | WARN 12 | SKIP 48 | PASS 734 ] - Error: Test failures - Execution halted + ℹ Are you in your project directory and does your project have a 'DESCRIPTION' + file? + Execution halted + + ‘counting-doge-families.Rmd’ using ‘UTF-8’... failed + ‘doge-types.Rmd’ using ‘UTF-8’... failed + ‘doges-family-types.Rmd’ using ‘UTF-8’... failed + ‘doges-social-network.Rmd’ using ‘UTF-8’... OK + ‘doges-split-social-network.Rmd’ using ‘UTF-8’... OK + ‘doges-terms.Rmd’ using ‘UTF-8’... OK ``` -# ggh4x +* checking data for non-ASCII characters ... NOTE + ``` + Note: found 3 marked UTF-8 strings + ``` + +# dotsViolin
-* Version: 0.2.8 -* GitHub: https://github.com/teunbrand/ggh4x -* Source code: https://github.com/cran/ggh4x -* Date/Publication: 2024-01-23 21:00:02 UTC -* Number of recursive dependencies: 77 +* Version: 0.0.1 +* GitHub: NA +* Source code: https://github.com/cran/dotsViolin +* Date/Publication: 2023-10-30 13:20:02 UTC +* Number of recursive dependencies: 39 -Run `revdepcheck::cloud_details(, "ggh4x")` for more info +Run `revdepcheck::cloud_details(, "dotsViolin")` for more info
@@ -4016,128 +4212,129 @@ Run `revdepcheck::cloud_details(, "ggh4x")` for more info * checking examples ... ERROR ``` - Running examples in ‘ggh4x-Ex.R’ failed + Running examples in ‘dotsViolin-Ex.R’ failed The error most likely occurred in: - > ### Name: facet_nested_wrap - > ### Title: Ribbon of panels with nested strips. - > ### Aliases: facet_nested_wrap + > ### Name: dots_and_violin + > ### Title: Makes a composite dot-plot and violin-plot + > ### Aliases: dots_and_violin + > ### Keywords: dot-plot violin-plot > > ### ** Examples > - > # A standard plot ... - 6. │ └─ggplot2 (local) setup(..., self = self) - 7. │ └─self$facet$compute_layout(data, self$facet_params) - 8. │ └─ggplot2 (local) compute_layout(..., self = self) - 9. │ └─ggplot2:::wrap_layout(id, dims, params$dir) - 10. │ └─ggplot2:::data_frame0(...) - 11. │ └─vctrs::data_frame(..., .name_repair = "minimal") - 12. └─vctrs:::stop_recycle_incompatible_size(...) - 13. └─vctrs:::stop_vctrs(...) - 14. └─rlang::abort(message, class = c(class, "vctrs_error"), ..., call = call) + 3. │ └─gridExtra::arrangeGrob(...) + 4. └─gridExtra::arrangeGrob(...) + 5. └─base::lapply(grobs[toconv], ggplot2::ggplotGrob) + 6. └─ggplot2 (local) FUN(X[[i]], ...) + 7. ├─ggplot2::ggplot_gtable(ggplot_build(x)) + 8. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) + 9. └─ggplot2::calc_element("plot.margin", theme) + 10. └─cli::cli_abort(...) + 11. └─rlang::abort(...) Execution halted ``` -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(ggh4x) - Loading required package: ggplot2 - > - > test_check("ggh4x") - [ FAIL 9 | WARN 1 | SKIP 18 | PASS 719 ] - - ... - 11. │ └─ggplot2:::wrap_layout(id, dims, params$dir) - 12. │ └─ggplot2:::data_frame0(...) - 13. │ └─vctrs::data_frame(..., .name_repair = "minimal") - 14. └─vctrs:::stop_recycle_incompatible_size(...) - 15. └─vctrs:::stop_vctrs(...) - 16. └─rlang::abort(message, class = c(class, "vctrs_error"), ..., call = call) - - [ FAIL 9 | WARN 1 | SKIP 18 | PASS 719 ] - Error: Test failures - Execution halted - ``` +## In both -* checking re-building of vignette outputs ... NOTE +* checking data for non-ASCII characters ... NOTE ``` - Error(s) in re-building vignettes: - --- re-building ‘Facets.Rmd’ using rmarkdown - - Quitting from lines at lines 33-39 [wrap_mimick] (Facets.Rmd) - Error: processing vignette 'Facets.Rmd' failed with diagnostics: - Can't recycle `ROW` (size 0) to size 7. - --- failed re-building ‘Facets.Rmd’ - - --- re-building ‘Miscellaneous.Rmd’ using rmarkdown + Note: found 2 marked UTF-8 strings ``` -## In both +# ds4psy -* checking running R code from vignettes ... ERROR +
+ +* Version: 1.0.0 +* GitHub: https://github.com/hneth/ds4psy +* Source code: https://github.com/cran/ds4psy +* Date/Publication: 2023-09-15 07:30:02 UTC +* Number of recursive dependencies: 55 + +Run `revdepcheck::cloud_details(, "ds4psy")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR ``` - Errors in running code in vignettes: - when running code in ‘Facets.Rmd’ - ... - Loading required package: ggplot2 - - > p <- ggplot(mpg, aes(displ, hwy, colour = as.factor(cyl))) + - + geom_point() + labs(x = "Engine displacement", y = "Highway miles per gallon") + .... [TRUNCATED] - - > p + facet_wrap2(vars(class)) + Running examples in ‘ds4psy-Ex.R’ failed + The error most likely occurred in: + > ### Name: plot_charmap + > ### Title: Plot a character map as a tile plot with text labels. + > ### Aliases: plot_charmap + > + > ### ** Examples + > + > # (0) Prepare: ... - ℹ Error occurred in the 1st layer. - Caused by error in `setup_params()`: - ! A discrete 'nbinom' distribution cannot be fitted to continuous data. + Backtrace: + ▆ + 1. ├─base (local) ``(x) + 2. └─ggplot2:::print.ggplot(x) + 3. ├─ggplot2::ggplot_gtable(data) + 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) + 5. └─ggplot2::calc_element("plot.margin", theme) + 6. └─cli::cli_abort(...) + 7. └─rlang::abort(...) Execution halted - - ‘Facets.Rmd’ using ‘UTF-8’... failed - ‘Miscellaneous.Rmd’ using ‘UTF-8’... failed - ‘PositionGuides.Rmd’ using ‘UTF-8’... OK - ‘Statistics.Rmd’ using ‘UTF-8’... failed - ‘ggh4x.Rmd’ using ‘UTF-8’... OK ``` -# ggheatmap +# edecob
-* Version: 2.2 +* Version: 1.2.2 * GitHub: NA -* Source code: https://github.com/cran/ggheatmap -* Date/Publication: 2022-09-10 13:32:55 UTC -* Number of recursive dependencies: 127 +* Source code: https://github.com/cran/edecob +* Date/Publication: 2022-11-04 12:00:02 UTC +* Number of recursive dependencies: 29 -Run `revdepcheck::cloud_details(, "ggheatmap")` for more info +Run `revdepcheck::cloud_details(, "edecob")` for more info
## Newly broken -* checking whether package ‘ggheatmap’ can be installed ... WARNING +* checking examples ... ERROR ``` - Found the following significant warnings: - Warning: replacing previous import ‘ggplot2::ggpar’ by ‘ggpubr::ggpar’ when loading ‘ggheatmap’ - See ‘/tmp/workdir/ggheatmap/new/ggheatmap.Rcheck/00install.out’ for details. + Running examples in ‘edecob-Ex.R’ failed + The error most likely occurred in: + + > ### Name: edecob + > ### Title: Event DEtection using COnfidence Bounds + > ### Aliases: edecob + > + > ### ** Examples + > + > library(edecob) + ... + ▆ + 1. ├─base::plot(example_event$`Subject 1`) + 2. └─edecob:::plot.edecob(example_event$`Subject 1`) + 3. └─ggplot2::ggplotGrob(patient_plot) + 4. ├─ggplot2::ggplot_gtable(ggplot_build(x)) + 5. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) + 6. └─ggplot2::calc_element("plot.margin", theme) + 7. └─cli::cli_abort(...) + 8. └─rlang::abort(...) + Execution halted ``` -# gghighlight +# entropart
-* Version: 0.4.1 -* GitHub: https://github.com/yutannihilation/gghighlight -* Source code: https://github.com/cran/gghighlight -* Date/Publication: 2023-12-16 01:00:02 UTC -* Number of recursive dependencies: 85 +* Version: 1.6-13 +* GitHub: https://github.com/EricMarcon/entropart +* Source code: https://github.com/cran/entropart +* Date/Publication: 2023-09-26 14:40:02 UTC +* Number of recursive dependencies: 121 -Run `revdepcheck::cloud_details(, "gghighlight")` for more info +Run `revdepcheck::cloud_details(, "entropart")` for more info
@@ -4145,90 +4342,81 @@ Run `revdepcheck::cloud_details(, "gghighlight")` for more info * checking examples ... ERROR ``` - Running examples in ‘gghighlight-Ex.R’ failed + Running examples in ‘entropart-Ex.R’ failed The error most likely occurred in: - > ### Name: gghighlight - > ### Title: Highlight Data With Predicate - > ### Aliases: gghighlight + > ### Name: Accumulation + > ### Title: Diversity accumulation. + > ### Aliases: DivAC EntAC as.AccumCurve is.AccumCurve autoplot.AccumCurve + > ### plot.AccumCurve > > ### ** Examples > - > d <- data.frame( ... - 8. │ ├─purrr:::with_indexed_errors(...) - 9. │ │ └─base::withCallingHandlers(...) - 10. │ ├─purrr:::call_with_cleanup(...) - 11. │ └─gghighlight (local) .f(.x[[i]], .y[[i]], ...) - 12. │ └─gghighlight:::get_default_aes_param(nm, layer$geom, layer$mapping) - 13. └─base::.handleSimpleError(...) - 14. └─purrr (local) h(simpleError(msg, call)) - 15. └─cli::cli_abort(...) - 16. └─rlang::abort(...) + 11. │ └─base::withCallingHandlers(...) + 12. └─ggplot2 (local) f(l = layers[[i]], d = data[[i]]) + 13. └─l$compute_geom_2(d, theme = plot$theme) + 14. └─ggplot2 (local) compute_geom_2(..., self = self) + 15. └─self$geom$use_defaults(...) + 16. └─ggplot2 (local) use_defaults(..., self = self) + 17. └─ggplot2:::check_aesthetics(new_params, nrow(data)) + 18. └─cli::cli_abort(...) + 19. └─rlang::abort(...) Execution halted ``` -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(gghighlight) - Loading required package: ggplot2 - > - > test_check("gghighlight") - label_key: type - label_key: type - ... - 15. └─cli::cli_abort(...) - 16. └─rlang::abort(...) - - [ FAIL 2 | WARN 2 | SKIP 1 | PASS 178 ] - Deleting unused snapshots: - • vdiffr/simple-bar-chart-with-facet.svg - • vdiffr/simple-line-chart.svg - • vdiffr/simple-point-chart.svg - Error: Test failures - Execution halted - ``` - * checking running R code from vignettes ... ERROR ``` Errors in running code in vignettes: - when running code in ‘gghighlight.Rmd’ + when running code in ‘entropart.Rmd’ ... - + 0, label_key = type) - Warning in is.na(non_null_default_aes[[aes_param_name]]) : - is.na() applied to non-(list or vector) of type 'language' - When sourcing ‘gghighlight.R’: - Error: ℹ In index: 1. - Caused by error in `aes_param_name %in% names(non_null_default_aes) && is.na(non_null_default_aes[[ - aes_param_name]])`: - ! 'length = 2' in coercion to 'logical(1)' + > autoplot(Abd18, Distribution = "lnorm") + + When sourcing ‘entropart.R’: + Error: Problem while setting up geom aesthetics. + ℹ Error occurred in the 1st layer. + Caused by error in `check_aesthetics()`: + ! Aesthetics must be either length 1 or the same as the data (149). + ✖ Fix the following mappings: `shape`, `colour`, and `size`. Execution halted - ‘gghighlight.Rmd’ using ‘UTF-8’... failed + ‘entropart.Rmd’ using ‘UTF-8’... failed ``` * checking re-building of vignette outputs ... NOTE ``` Error(s) in re-building vignettes: - --- re-building ‘gghighlight.Rmd’ using rmarkdown + ... + --- re-building ‘entropart.Rmd’ using rmarkdown + + Quitting from lines 53-55 [PlotN18] (entropart.Rmd) + Error: processing vignette 'entropart.Rmd' failed with diagnostics: + Problem while setting up geom aesthetics. + ℹ Error occurred in the 1st layer. + Caused by error in `check_aesthetics()`: + ! Aesthetics must be either length 1 or the same as the data (149). + ✖ Fix the following mappings: `shape`, `colour`, and `size`. + --- failed re-building ‘entropart.Rmd’ + + SUMMARY: processing the following file failed: + ‘entropart.Rmd’ + + Error: Vignette re-building failed. + Execution halted ``` -# ggiraph +# envalysis
-* Version: 0.8.9 -* GitHub: https://github.com/davidgohel/ggiraph -* Source code: https://github.com/cran/ggiraph -* Date/Publication: 2024-02-24 16:20:13 UTC -* Number of recursive dependencies: 95 +* Version: 0.7.0 +* GitHub: https://github.com/zsteinmetz/envalysis +* Source code: https://github.com/cran/envalysis +* Date/Publication: 2024-03-20 15:10:02 UTC +* Number of recursive dependencies: 103 -Run `revdepcheck::cloud_details(, "ggiraph")` for more info +Run `revdepcheck::cloud_details(, "envalysis")` for more info
@@ -4236,116 +4424,96 @@ Run `revdepcheck::cloud_details(, "ggiraph")` for more info * checking examples ... ERROR ``` - Running examples in ‘ggiraph-Ex.R’ failed + Running examples in ‘envalysis-Ex.R’ failed The error most likely occurred in: - > ### Name: geom_sf_interactive - > ### Title: Create interactive sf objects - > ### Aliases: geom_sf_interactive geom_sf_label_interactive - > ### geom_sf_text_interactive + > ### Name: theme_publish + > ### Title: ggplot2 theme for scientific publications + > ### Aliases: theme_publish > > ### ** Examples > + > library(ggplot2) ... - + x <- girafe( ggobj = gg) - + if( interactive() ) print(x) - + } - Warning in CPL_crs_from_input(x) : - GDAL Message 1: +init=epsg:XXXX syntax is deprecated. It might return a CRS with a non-EPSG compliant axis order. - Warning: Using `as.character()` on a quosure is deprecated as of rlang 0.3.0. Please use - `as_label()` or `as_name()` instead. - This warning is displayed once every 8 hours. - Error: Unknown colour name: ~ + Backtrace: + ▆ + 1. ├─base (local) ``(x) + 2. └─ggplot2:::print.ggplot(x) + 3. ├─ggplot2::ggplot_gtable(data) + 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) + 5. └─ggplot2::calc_element("plot.margin", theme) + 6. └─cli::cli_abort(...) + 7. └─rlang::abort(...) Execution halted ``` * checking tests ... ERROR ``` - Running ‘tinytest.R’ - Running the tests in ‘tests/tinytest.R’ failed. + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. Complete output: - > if (requireNamespace("tinytest", quietly = TRUE)) { - + tinytest::test_package("ggiraph") - + } - - test-annotate_interactive.R... 0 tests - test-annotate_interactive.R... 0 tests - test-annotate_interactive.R... 0 tests + > library(testthat) + > library(envalysis) + > + > test_check("envalysis") + number of blank values <= 1; LOD is estimated from the calibration curve + number of blank values <= 1; LOD is estimated from the calibration curve + number of blank values <= 1; LOD is estimated from the calibration curve ... - test-utils.R.................. 7 tests 1 fails - test-utils.R.................. 8 tests 1 fails - test-utils.R.................. 11 tests 1 fails Error in as.data.frame.default(x[[i]], optional = TRUE) : - cannot coerce class 'c("quosure", "formula")' to a data.frame - Calls: ... -> as.data.frame -> as.data.frame.default - In addition: Warning message: - 'ggiraph' is deprecated. - Use 'girafe' instead. - See help("Deprecated") + 13. └─ggplot2::calc_element("plot.margin", theme) + 14. └─cli::cli_abort(...) + 15. └─rlang::abort(...) + + [ FAIL 1 | WARN 0 | SKIP 3 | PASS 139 ] + Deleting unused snapshots: + • calibration/plot.png + • texture/plot.png + Error: Test failures Execution halted ``` -## In both - -* checking installed package size ... NOTE - ``` - installed size is 11.9Mb - sub-directories of 1Mb or more: - libs 9.5Mb - ``` - -# ggmice - -
- -* Version: 0.1.0 -* GitHub: https://github.com/amices/ggmice -* Source code: https://github.com/cran/ggmice -* Date/Publication: 2023-08-07 14:20:02 UTC -* Number of recursive dependencies: 121 - -Run `revdepcheck::cloud_details(, "ggmice")` for more info - -
- -## Newly broken - * checking running R code from vignettes ... ERROR ``` Errors in running code in vignettes: - when running code in ‘old_friends.Rmd’ + when running code in ‘calibration.Rmd’ ... - layout + > dt$sum <- dt$res[, .(Content = mean(Content, na.rm = T), + + CI = CI(Content, na.rm = T)), by = .(Compound, Treatment, + + Day)] + > ggplot(dt$sum, aes(x = Day, y = Content)) + geom_errorbar(aes(ymin = Content - + + CI, ymax = Content + CI, group = Treatment), width = 1, positi .... [TRUNCATED] - > p <- plot_flux(dat) + ... - > ggplotly(p) + > p + theme_publish() - When sourcing ‘old_friends.R’: - Error: argument "theme" is missing, with no default + When sourcing ‘theme_publish.R’: + Error: Theme element `plot.margin` must have class . Execution halted - ‘ggmice.Rmd’ using ‘UTF-8’... OK - ‘old_friends.Rmd’ using ‘UTF-8’... failed + ‘calibration.Rmd’ using ‘UTF-8’... failed + ‘texture.Rmd’ using ‘UTF-8’... OK + ‘theme_publish.Rmd’ using ‘UTF-8’... failed ``` * checking re-building of vignette outputs ... NOTE ``` Error(s) in re-building vignettes: - --- re-building ‘ggmice.Rmd’ using rmarkdown + --- re-building ‘calibration.Rmd’ using rmarkdown ``` -# ggmulti +# epiCleanr
-* Version: 1.0.7 -* GitHub: NA -* Source code: https://github.com/cran/ggmulti -* Date/Publication: 2024-04-09 09:40:05 UTC -* Number of recursive dependencies: 126 +* Version: 0.2.0 +* GitHub: https://github.com/truenomad/epiCleanr +* Source code: https://github.com/cran/epiCleanr +* Date/Publication: 2023-09-28 12:20:05 UTC +* Number of recursive dependencies: 130 -Run `revdepcheck::cloud_details(, "ggmulti")` for more info +Run `revdepcheck::cloud_details(, "epiCleanr")` for more info
@@ -4353,137 +4521,101 @@ Run `revdepcheck::cloud_details(, "ggmulti")` for more info * checking examples ... ERROR ``` - Running examples in ‘ggmulti-Ex.R’ failed + Running examples in ‘epiCleanr-Ex.R’ failed The error most likely occurred in: - > ### Name: coord_radial - > ### Title: Radial axes - > ### Aliases: coord_radial + > ### Name: handle_outliers + > ### Title: Detect and Handle Outliers in Dataset + > ### Aliases: handle_outliers > > ### ** Examples > - > if(require("dplyr")) { + > ... - 2.75, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 1, NULL, NULL, NULL, c(0, 2.2, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, NULL, c(0, 0, 0, 2.2 - ), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0.5, NULL, NULL, NULL, c(0, 2.2, 0, 2.2), NULL, TRUE), list("grey20", NULL, NULL, NULL, FALSE, TRUE), NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 2.75, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 0.75, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, list(), NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, list(NULL, NA, NULL, NULL, TRUE), c(5.5, 5.5, 5.5, 5.5), 11, NULL, NULL, NULL, 1.2, NULL, NULL, 5.5, - NULL, NULL, NULL, NULL, 0.2, NULL, list(NULL, NULL, NULL, 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, NULL, NULL, NULL, TRUE), NULL, "right", NULL, NULL, NULL, "center", NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, c(0, 0, 0, 0), list(), 11, list("grey92", NA, NULL, NULL, TRUE), list(), 5.5, NULL, NULL, list("white", NULL, NULL, NULL, FALSE, TRUE), NULL, list(NULL, 0.5, NULL, NULL, FALSE, TRUE), NULL, NULL, NULL, NULL, FALSE, list(NULL, - "white", NULL, NULL, TRUE), list(NULL, NULL, NULL, 1.2, 0, 1, NULL, NULL, c(0, 0, 5.5, 0), NULL, TRUE), "panel", list(NULL, NULL, NULL, NULL, 0, 1, NULL, NULL, c(0, 0, 5.5, 0), NULL, TRUE), list(NULL, NULL, NULL, 0.8, 1, 1, NULL, NULL, c(5.5, 0, 0, 0), NULL, TRUE), "panel", list(NULL, NULL, NULL, 1.2, 0.5, 0.5, NULL, NULL, NULL, NULL, TRUE), "topleft", NULL, c(5.5, 5.5, 5.5, 5.5), list("grey85", NA, NULL, NULL, TRUE), NULL, NULL, "inherit", "inside", list(NULL, NULL, "grey10", 0.8, NULL, - NULL, NULL, NULL, c(4.4, 4.4, 4.4, 4.4), NULL, TRUE), NULL, NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, NULL, -90, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, NULL, 90, NULL, NULL, NULL, TRUE), NULL, 2.75, 2.75)) - Error in use_defaults(..., self = self) : - unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), NULL, list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.75, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, 90, NULL, c(0, - 2.75, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 1, NULL, NULL, NULL, c(0, 2.2, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL - Calls: ... .handleSimpleError -> h -> -> + 12. │ └─ggplot2 (local) f(l = layers[[i]], d = data[[i]]) + 13. │ └─l$compute_geom_2(d, theme = plot$theme) + 14. │ └─ggplot2 (local) compute_geom_2(..., self = self) + 15. │ └─self$geom$use_defaults(...) + 16. └─base::.handleSimpleError(...) + 17. └─rlang (local) h(simpleError(msg, call)) + 18. └─handlers[[1L]](cnd) + 19. └─cli::cli_abort(...) + 20. └─rlang::abort(...) Execution halted ``` -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > - > - > library(testthat) - > library(ggmulti) - Loading required package: ggplot2 - - Attaching package: 'ggmulti' - ... - 24. │ │ └─base::withCallingHandlers(...) - 25. │ └─layer$geom$use_defaults(...) - 26. └─base::.handleSimpleError(...) - 27. └─rlang (local) h(simpleError(msg, call)) - 28. └─handlers[[1L]](cnd) - 29. └─layer$geom$use_defaults(...) - - [ FAIL 4 | WARN 3 | SKIP 0 | PASS 30 ] - Error: Test failures - Execution halted - ``` - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘glyph.Rmd’ - ... - + Sepal.Width, colour = Species), serialaxes.data = iris, axes.layout = "radia ..." ... [TRUNCATED] - - When sourcing ‘glyph.R’: - Error: Base operators are not defined for quosures. Do you need to unquote the - quosure? - - # Bad: myquosure / rhs - ... - 0, 0, 0), NULL, TRUE), "panel", list(NULL, NULL, NULL, 1.2, 0.5, 0.5, NULL, NULL, NULL, NULL, TRUE), "topleft", NULL, c(5, 12, 5, 12), list("grey85", NA, NULL, NULL, TRUE), NULL, NULL, "inherit", "inside", list(NULL, NULL, "grey10", 0.8, NULL, NULL, NULL, NULL, c(4.4, 4.4, 4.4, 4.4), NULL, TRUE), NULL, NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, NULL, -90, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, NULL, 90, NULL, NULL, NULL, TRUE), NULL, 2.75, 2.75)) - - When sourcing ‘highDim.R’: - Error: unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), NULL, list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), NULL, NULL, list(), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, - NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, NULL, c(0, 0, 0, 2.2), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0.5, NULL, NULL, NULL, c(0, 2.2, 0, 2.2), NULL, TRUE), list("grey20", NULL, NULL, NULL, FALSE, TRUE), NULL, NULL, NULL, list(), NULL, NULL, N - Execution halted - - ‘glyph.Rmd’ using ‘UTF-8’... failed - ‘highDim.Rmd’ using ‘UTF-8’... failed - ‘histogram-density-.Rmd’ using ‘UTF-8’... OK - ``` +## In both -* checking re-building of vignette outputs ... NOTE +* checking installed package size ... NOTE ``` - Error(s) in re-building vignettes: - --- re-building ‘glyph.Rmd’ using rmarkdown + installed size is 5.6Mb + sub-directories of 1Mb or more: + doc 2.9Mb + help 2.5Mb ``` -# ggparallel +# EpiInvert
-* Version: 0.4.0 -* GitHub: https://github.com/heike/ggparallel -* Source code: https://github.com/cran/ggparallel -* Date/Publication: 2024-03-09 22:00:02 UTC -* Number of recursive dependencies: 51 +* Version: 0.3.1 +* GitHub: https://github.com/lalvarezmat/EpiInvert +* Source code: https://github.com/cran/EpiInvert +* Date/Publication: 2022-12-14 14:40:03 UTC +* Number of recursive dependencies: 98 -Run `revdepcheck::cloud_details(, "ggparallel")` for more info +Run `revdepcheck::cloud_details(, "EpiInvert")` for more info
## Newly broken -* checking tests ... ERROR +* checking examples ... ERROR ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > # This file is part of the standard setup for testthat. - > # It is recommended that you do not modify it. - > # - > # Where should you do additional test configuration? - > # Learn more about the roles of various files in: - > # * https://r-pkgs.org/testing-design.html#sec-tests-files-overview - > # * https://testthat.r-lib.org/articles/special-files.html + Running examples in ‘EpiInvert-Ex.R’ failed + The error most likely occurred in: + + > ### Name: EpiInvert + > ### Title: 'EpiInvert' estimates the reproduction number Rt and a restored + > ### incidence curve from the original daily incidence curve and the + > ### serial interval distribution. EpiInvert also corrects the festive and + > ### weekly biases present in the registered daily incidence. + > ### Aliases: EpiInvert + > ... - 11. │ └─l$compute_geom_2(d, theme = plot$theme) - 12. └─base::.handleSimpleError(...) - 13. └─rlang (local) h(simpleError(msg, call)) - 14. └─handlers[[1L]](cnd) - 15. └─cli::cli_abort(...) - 16. └─rlang::abort(...) - - [ FAIL 1 | WARN 0 | SKIP 0 | PASS 0 ] - Error: Test failures - Execution halted + Backtrace: + ▆ + 1. └─EpiInvert::EpiInvert_plot(res) + 2. └─ggplot2::ggplotGrob(g1) + 3. ├─ggplot2::ggplot_gtable(ggplot_build(x)) + 4. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) + 5. └─ggplot2::calc_element("plot.margin", theme) + 6. └─cli::cli_abort(...) + 7. └─rlang::abort(...) + Execution halted ``` -# ggplotlyExtra +## In both + +* checking installed package size ... NOTE + ``` + installed size is 7.7Mb + sub-directories of 1Mb or more: + data 3.2Mb + libs 4.3Mb + ``` + +# esci
-* Version: 0.0.1 -* GitHub: NA -* Source code: https://github.com/cran/ggplotlyExtra -* Date/Publication: 2019-12-02 16:20:06 UTC -* Number of recursive dependencies: 70 +* Version: 1.0.2 +* GitHub: https://github.com/rcalinjageman/esci +* Source code: https://github.com/cran/esci +* Date/Publication: 2024-03-21 18:10:02 UTC +* Number of recursive dependencies: 93 -Run `revdepcheck::cloud_details(, "ggplotlyExtra")` for more info +Run `revdepcheck::cloud_details(, "esci")` for more info
@@ -4491,47 +4623,65 @@ Run `revdepcheck::cloud_details(, "ggplotlyExtra")` for more info * checking examples ... ERROR ``` - Running examples in ‘ggplotlyExtra-Ex.R’ failed + Running examples in ‘esci-Ex.R’ failed The error most likely occurred in: - > ### Name: ggplotly_histogram - > ### Title: Clean 'ggplot2' Histogram to be Converted to 'Plotly' - > ### Aliases: ggplotly_histogram + > ### Name: estimate_mdiff_2x2_between + > ### Title: Estimates for a 2x2 between-subjects design with a continuous + > ### outcome variable + > ### Aliases: estimate_mdiff_2x2_between > > ### ** Examples > - > ... - `stat_bin()` using `bins = 30`. Pick better value with `binwidth`. - Warning in geom_bar(data = layerdata, mapping = aes(x = .data$x, y = .data$count, : - Ignoring unknown aesthetics: label1, label2, and label3 - > - > # convert `ggplot` object to `plotly` object - > ggplotly(p, tooltip = c("Range", "count", "density")) - Error in compute_geom_2(..., self = self) : - argument "theme" is missing, with no default - Calls: ggplotly ... use_defaults -> eval_from_theme -> %||% -> calc_element + + estimates_from_summary$interaction, + + effect_size = "mean" + + ) + Warning: Using size for a discrete variable is not advised. + Warning: Using alpha for a discrete variable is not advised. + Error in use_defaults(..., self = self) : + unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, "black", TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), NULL, list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), 5.5, c(5.5, 5.5, 5.5, 5.5), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.75, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, + NULL, NULL, NULL, 1, 90, NULL, c(0, 2.75, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 1, NULL, NULL, NULL, c(0, 2.2, 0, 0), NULL, TRUE), NULL, l + Calls: ... -> -> compute_geom_2 -> Execution halted ``` -## In both - -* checking LazyData ... NOTE +* checking tests ... ERROR ``` - 'LazyData' is specified without a 'data' directory + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(esci) + > + > test_check("esci") + Loading required package: Matrix + Loading required package: metadat + Loading required package: numDeriv + ... + 17. │ └─self$geom$use_defaults(...) + 18. └─base::.handleSimpleError(...) + 19. └─rlang (local) h(simpleError(msg, call)) + 20. └─handlers[[1L]](cnd) + 21. └─cli::cli_abort(...) + 22. └─rlang::abort(...) + + [ FAIL 14 | WARN 15 | SKIP 0 | PASS 3182 ] + Error: Test failures + Execution halted ``` -# ggpol +# EvidenceSynthesis
-* Version: 0.0.7 -* GitHub: https://github.com/erocoar/ggpol -* Source code: https://github.com/cran/ggpol -* Date/Publication: 2020-11-08 13:40:02 UTC -* Number of recursive dependencies: 54 +* Version: 0.5.0 +* GitHub: https://github.com/OHDSI/EvidenceSynthesis +* Source code: https://github.com/cran/EvidenceSynthesis +* Date/Publication: 2023-05-08 12:20:02 UTC +* Number of recursive dependencies: 117 -Run `revdepcheck::cloud_details(, "ggpol")` for more info +Run `revdepcheck::cloud_details(, "EvidenceSynthesis")` for more info
@@ -4539,54 +4689,115 @@ Run `revdepcheck::cloud_details(, "ggpol")` for more info * checking examples ... ERROR ``` - Running examples in ‘ggpol-Ex.R’ failed + Running examples in ‘EvidenceSynthesis-Ex.R’ failed The error most likely occurred in: - > ### Name: GeomConfmat - > ### Title: Confusion Matrix - > ### Aliases: GeomConfmat geom_confmat stat_confmat + > ### Name: plotCovariateBalances + > ### Title: Plot covariate balances + > ### Aliases: plotCovariateBalances > > ### ** Examples > - > x <- sample(LETTERS[seq(4)], 50, replace = TRUE) + > # Some example data: ... - 21. │ └─ggpol (local) draw_panel(...) - 22. │ └─base::lapply(GeomText$default_aes[missing_aes], rlang::eval_tidy) - 23. │ └─rlang (local) FUN(X[[i]], ...) - 24. ├─ggplot2::from_theme(fontsize) - 25. └─base::.handleSimpleError(...) - 26. └─rlang (local) h(simpleError(msg, call)) - 27. └─handlers[[1L]](cnd) - 28. └─cli::cli_abort(...) - 29. └─rlang::abort(...) + 2. └─gridExtra::grid.arrange(data_table, plot, ncol = 2) + 3. └─gridExtra::arrangeGrob(...) + 4. └─base::lapply(grobs[toconv], ggplot2::ggplotGrob) + 5. └─ggplot2 (local) FUN(X[[i]], ...) + 6. ├─ggplot2::ggplot_gtable(ggplot_build(x)) + 7. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) + 8. └─ggplot2::calc_element("plot.margin", theme) + 9. └─cli::cli_abort(...) + 10. └─rlang::abort(...) Execution halted ``` -## In both - -* checking dependencies in R code ... NOTE - ``` - Namespaces in Imports field not imported from: - ‘dplyr’ ‘grDevices’ - All declared Imports should be used. +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > test_check("EvidenceSynthesis") + Loading required package: EvidenceSynthesis + Loading required package: survival + + | | 0% + |=============================================================== | 90%df = 4.0 + ... + 5. └─ggplot2 (local) FUN(X[[i]], ...) + 6. ├─ggplot2::ggplot_gtable(ggplot_build(x)) + 7. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) + 8. └─ggplot2::calc_element("plot.margin", theme) + 9. └─cli::cli_abort(...) + 10. └─rlang::abort(...) + + [ FAIL 3 | WARN 8 | SKIP 0 | PASS 57 ] + Error: Test failures + Execution halted ``` -* checking LazyData ... NOTE +* checking running R code from vignettes ... ERROR ``` - 'LazyData' is specified without a 'data' directory + Errors in running code in vignettes: + when running code in ‘NonNormalEffectSynthesis.Rmd’ + ... + 1 2.097148 1.104696 3.783668 + + > labels <- paste("Data site", LETTERS[1:length(populations)]) + + > plotMetaAnalysisForest(data = approximations, labels = labels, + + estimate = estimate, xLabel = "Hazard Ratio", showLikelihood = TRUE) + + ... + > plotMetaAnalysisForest(data = normalApproximations, + + labels = paste("Site", 1:10), estimate = fixedFxNormal, xLabel = "Hazard Ratio") + + When sourcing ‘VideoVignette.R’: + Error: Theme element `plot.margin` must have class . + Execution halted + + ‘BayesianBiasCorrection.Rmd’ using ‘UTF-8’... OK + ‘NonNormalEffectSynthesis.Rmd’ using ‘UTF-8’... failed + ‘VideoVignette.Rmd’ using ‘UTF-8’... failed ``` -# ggraph +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘BayesianBiasCorrection.Rmd’ using rmarkdown + + | | 0% + |====== | 9% + |============ | 18% + |=================== | 27% + |========================= | 36% + |=============================== | 45% + |====================================== | 54% + ... + Quitting from lines 158-164 [unnamed-chunk-9] (VideoVignette.Rmd) + Error: processing vignette 'VideoVignette.Rmd' failed with diagnostics: + Theme element `plot.margin` must have class . + --- failed re-building ‘VideoVignette.Rmd’ + + SUMMARY: processing the following files failed: + ‘NonNormalEffectSynthesis.Rmd’ ‘VideoVignette.Rmd’ + + Error: Vignette re-building failed. + Execution halted + ``` + +# EvolutionaryGames
-* Version: 2.2.1 -* GitHub: https://github.com/thomasp85/ggraph -* Source code: https://github.com/cran/ggraph -* Date/Publication: 2024-03-07 12:40:02 UTC -* Number of recursive dependencies: 115 +* Version: 0.1.2 +* GitHub: NA +* Source code: https://github.com/cran/EvolutionaryGames +* Date/Publication: 2022-08-29 00:10:02 UTC +* Number of recursive dependencies: 66 -Run `revdepcheck::cloud_details(, "ggraph")` for more info +Run `revdepcheck::cloud_details(, "EvolutionaryGames")` for more info
@@ -4594,81 +4805,71 @@ Run `revdepcheck::cloud_details(, "ggraph")` for more info * checking examples ... ERROR ``` - Running examples in ‘ggraph-Ex.R’ failed + Running examples in ‘EvolutionaryGames-Ex.R’ failed The error most likely occurred in: - > ### Name: geom_conn_bundle - > ### Title: Create hierarchical edge bundles between node connections - > ### Aliases: geom_conn_bundle geom_conn_bundle2 geom_conn_bundle0 + > ### Name: phaseDiagram2S + > ### Title: Phase Diagram for two-player games with two strategies + > ### Aliases: phaseDiagram2S > > ### ** Examples > - > # Create a graph of the flare class system + > A <- matrix(c(-1, 4, 0, 2), 2, 2, byrow=TRUE) ... - + ) + - + geom_node_point(aes(filter = leaf, colour = class)) + - + scale_edge_colour_distiller('', direction = 1, guide = 'edge_direction') + - + coord_fixed() + - + ggforce::theme_no_axes() - Error in get_layer_key(...) : - unused argument (list(list("black", 0.5, 1, "butt", FALSE, TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), NULL, list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), NULL, list(), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.75, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, 90, NULL, c(0, 2.75, - 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 1, NULL, NULL, NULL, c(0, 2.2, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, NULL, c(0, 0, 0, 2.2), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, - Calls: ... -> -> process_layers -> + ▆ + 1. └─EvolutionaryGames::phaseDiagram2S(...) + 2. ├─base::print(p + vField) + 3. └─ggplot2:::print.ggplot(p + vField) + 4. ├─ggplot2::ggplot_gtable(data) + 5. └─ggplot2:::ggplot_gtable.ggplot_built(data) + 6. └─ggplot2::calc_element("plot.margin", theme) + 7. └─cli::cli_abort(...) + 8. └─rlang::abort(...) Execution halted ``` -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘Edges.Rmd’ using rmarkdown - ``` - -## In both - * checking running R code from vignettes ... ERROR ``` Errors in running code in vignettes: - when running code in ‘Edges.Rmd’ + when running code in ‘UsingEvolutionaryGames.Rmd’ ... - Warning in grid.Call.graphics(C_text, as.graphicsAnnot(x$label), x$x, x$y, : - font family 'Arial Narrow' not found in PostScript font database - Warning in grid.Call.graphics(C_text, as.graphicsAnnot(x$label), x$x, x$y, : - font family 'Arial Narrow' not found in PostScript font database - Warning in grid.Call.graphics(C_text, as.graphicsAnnot(x$label), x$x, x$y, : - font family 'Arial Narrow' not found in PostScript font database + > library(EvolutionaryGames) + + > A <- matrix(c(-1, 4, 0, 2), 2, byrow = TRUE) + + > phaseDiagram2S(A, Replicator, strategies = c("Hawk", + + "Dove")) ... - font family 'Arial' not found in PostScript font database - When sourcing ‘tidygraph.R’: - Error: invalid font type + > phaseDiagram2S(A, Replicator, strategies = c("Hawk", + + "Dove")) + + When sourcing ‘UsingEvolutionaryGames_pdf.R’: + Error: Theme element `plot.margin` must have class . Execution halted - ‘Edges.Rmd’ using ‘UTF-8’... failed - ‘Layouts.Rmd’ using ‘UTF-8’... failed - ‘Nodes.Rmd’ using ‘UTF-8’... failed - ‘tidygraph.Rmd’ using ‘UTF-8’... failed + ‘UsingEvolutionaryGames.Rmd’ using ‘UTF-8’... failed + ‘UsingEvolutionaryGames_pdf.Rmd’ using ‘UTF-8’... failed ``` -* checking installed package size ... NOTE +* checking re-building of vignette outputs ... NOTE ``` - installed size is 9.9Mb - sub-directories of 1Mb or more: - doc 3.9Mb - libs 4.4Mb + Error(s) in re-building vignettes: + --- re-building ‘UsingEvolutionaryGames.Rmd’ using rmarkdown ``` -# ggredist +# EvoPhylo
-* Version: 0.0.2 -* GitHub: https://github.com/alarm-redist/ggredist -* Source code: https://github.com/cran/ggredist -* Date/Publication: 2022-11-23 11:20:02 UTC -* Number of recursive dependencies: 67 +* Version: 0.3.2 +* GitHub: https://github.com/tiago-simoes/EvoPhylo +* Source code: https://github.com/cran/EvoPhylo +* Date/Publication: 2022-11-03 17:00:02 UTC +* Number of recursive dependencies: 164 -Run `revdepcheck::cloud_details(, "ggredist")` for more info +Run `revdepcheck::cloud_details(, "EvoPhylo")` for more info
@@ -4676,40 +4877,82 @@ Run `revdepcheck::cloud_details(, "ggredist")` for more info * checking examples ... ERROR ``` - Running examples in ‘ggredist-Ex.R’ failed + Running examples in ‘EvoPhylo-Ex.R’ failed The error most likely occurred in: - > ### Name: scale_fill_dra - > ### Title: Dave's Redistricting App classic scale for 'ggplot2' - > ### Aliases: scale_fill_dra scale_color_dra scale_colour_dra + > ### Name: make_clusters + > ### Title: Estimate and plot character partitions + > ### Aliases: make_clusters plot.cluster_df > > ### ** Examples > - > library(ggplot2) + > # See vignette("char-part") for how to use this ... - 15. └─ggplot2 (local) FUN(X[[i]], ...) - 16. └─base::lapply(...) - 17. └─ggplot2 (local) FUN(X[[i]], ...) - 18. └─g$draw_key(data, g$params, key_size) - 19. └─ggplot2 (local) draw_key(...) - 20. └─ggplot2::draw_key_polygon(data, params, size) - 21. └─rlang:::Summary.quosure(from_theme(thin), 1.524, na.rm = FALSE) - 22. └─rlang:::abort_quosure_op("Summary", .Generic) - 23. └─rlang::abort(...) + > # tSNE (3 dimensions; default is 2) + > cluster_df_tsne <- make_clusters(Dmatrix, k = 3, tsne = TRUE, + + tsne_dim = 2) + > + > # Plot clusters, plots divided into 2 rows, and increasing + > # overlap of text labels (default = 10) + > plot(cluster_df_tsne, nrow = 2, max.overlaps = 20) + Error in identicalUnits(x) : object is not a unit + Calls: ... assemble_guides -> guides_build -> unit.c -> identicalUnits Execution halted ``` -# ggResidpanel +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘char-part.Rmd’ using rmarkdown + ``` + +## In both + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘char-part.Rmd’ + ... + + collapse = TRUE, dpi = 300) + + > devtools::load_all(".") + + When sourcing ‘char-part.R’: + Error: Could not find a root 'DESCRIPTION' file that starts with '^Package' in + '/tmp/RtmpjL0Rwa/file19d43c89cd22/vignettes'. + ... + ℹ Are you in your project directory and does your project have a 'DESCRIPTION' + file? + Execution halted + + ‘char-part.Rmd’ using ‘UTF-8’... failed + ‘data_treatment.Rmd’ using ‘UTF-8’... OK + ‘fbd-params.Rmd’ using ‘UTF-8’... failed + ‘offset_handling.Rmd’ using ‘UTF-8’... failed + ‘rates-selection_BEAST2.Rmd’ using ‘UTF-8’... failed + ‘rates-selection_MrBayes.Rmd’ using ‘UTF-8’... failed + ``` + +* checking installed package size ... NOTE + ``` + installed size is 6.8Mb + sub-directories of 1Mb or more: + data 2.5Mb + doc 1.6Mb + extdata 2.4Mb + ``` + +# evprof
-* Version: 0.3.0 -* GitHub: NA -* Source code: https://github.com/cran/ggResidpanel -* Date/Publication: 2019-05-31 23:20:04 UTC -* Number of recursive dependencies: 112 +* Version: 1.1.2 +* GitHub: https://github.com/mcanigueral/evprof +* Source code: https://github.com/cran/evprof +* Date/Publication: 2024-03-14 14:50:05 UTC +* Number of recursive dependencies: 93 -Run `revdepcheck::cloud_details(, "ggResidpanel")` for more info +Run `revdepcheck::cloud_details(, "evprof")` for more info
@@ -4717,86 +4960,116 @@ Run `revdepcheck::cloud_details(, "ggResidpanel")` for more info * checking examples ... ERROR ``` - Running examples in ‘ggResidpanel-Ex.R’ failed + Running examples in ‘evprof-Ex.R’ failed The error most likely occurred in: - > ### Name: resid_interact - > ### Title: Panel of Interactive Versions of Diagnostic Residual Plots. - > ### Aliases: resid_interact + > ### Name: plot_energy_models + > ### Title: Compare density of estimated energy with density of real energy + > ### vector + > ### Aliases: plot_energy_models > > ### ** Examples > - > - > # Fit a model to the penguin data - > penguin_model <- lme4::lmer(heartrate ~ depth + duration + (1|bird), data = penguins) - > - > # Create the default interactive panel - > resid_interact(penguin_model) - Error in compute_geom_2(..., self = self) : - argument "theme" is missing, with no default - Calls: resid_interact ... use_defaults -> eval_from_theme -> %||% -> calc_element + ... + 7. └─cowplot:::as_gtable.default(x) + 8. ├─cowplot::as_grob(plot) + 9. └─cowplot:::as_grob.ggplot(plot) + 10. └─ggplot2::ggplotGrob(plot) + 11. ├─ggplot2::ggplot_gtable(ggplot_build(x)) + 12. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) + 13. └─ggplot2::calc_element("plot.margin", theme) + 14. └─cli::cli_abort(...) + 15. └─rlang::abort(...) Execution halted ``` -* checking running R code from vignettes ... ERROR +* checking tests ... ERROR ``` - Errors in running code in vignettes: - when running code in ‘introduction.Rmd’ - ... - > resid_interact(penguin_model, plots = c("resid", "qq")) - Warning: The following aesthetics were dropped during statistical transformation: label. - ℹ This can happen when ggplot fails to infer the correct grouping structure in - the data. - ℹ Did you forget to specify a `group` aesthetic or to convert a numerical - variable into a factor? - - When sourcing ‘introduction.R’: - Error: argument "theme" is missing, with no default - Execution halted - - ‘introduction.Rmd’ using ‘UTF-8’... failed + Running ‘spelling.R’ + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > # This file is part of the standard setup for testthat. + > # It is recommended that you do not modify it. + > # + > # Where should you do additional test configuration? + > # Learn more about the roles of various files in: + > # * https://r-pkgs.org/tests.html + ... + 10. └─ggplot2::ggplotGrob(plot) + 11. ├─ggplot2::ggplot_gtable(ggplot_build(x)) + 12. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) + 13. └─ggplot2::calc_element("plot.margin", theme) + 14. └─cli::cli_abort(...) + 15. └─rlang::abort(...) + + [ FAIL 2 | WARN 0 | SKIP 4 | PASS 48 ] + Error: Test failures + Execution halted ``` -* checking re-building of vignette outputs ... NOTE +## In both + +* checking installed package size ... NOTE ``` - Error(s) in re-building vignettes: - --- re-building ‘introduction.Rmd’ using rmarkdown + installed size is 5.1Mb + sub-directories of 1Mb or more: + data 3.5Mb + doc 1.2Mb ``` -# ggScatRidges +# expirest
-* Version: 0.1.1 -* GitHub: https://github.com/matbou85/ggScatRidges -* Source code: https://github.com/cran/ggScatRidges -* Date/Publication: 2024-03-25 10:20:05 UTC -* Number of recursive dependencies: 117 +* Version: 0.1.6 +* GitHub: https://github.com/piusdahinden/expirest +* Source code: https://github.com/cran/expirest +* Date/Publication: 2024-03-25 16:30:02 UTC +* Number of recursive dependencies: 46 -Run `revdepcheck::cloud_details(, "ggScatRidges")` for more info +Run `revdepcheck::cloud_details(, "expirest")` for more info
## Newly broken -* checking whether package ‘ggScatRidges’ can be installed ... WARNING +* checking tests ... ERROR ``` - Found the following significant warnings: - Warning: replacing previous import ‘ggplot2::ggpar’ by ‘ggpubr::ggpar’ when loading ‘ggScatRidges’ - See ‘/tmp/workdir/ggScatRidges/new/ggScatRidges.Rcheck/00install.out’ for details. + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(expirest) + > + > test_check("expirest") + [ FAIL 2 | WARN 0 | SKIP 0 | PASS 1121 ] + + ══ Failed tests ════════════════════════════════════════════════════════════════ + ... + 9. └─ggplot2:::plot.ggplot(x = x$Graph, ...) + 10. ├─ggplot2::ggplot_gtable(data) + 11. └─ggplot2:::ggplot_gtable.ggplot_built(data) + 12. └─ggplot2::calc_element("plot.margin", theme) + 13. └─cli::cli_abort(...) + 14. └─rlang::abort(...) + + [ FAIL 2 | WARN 0 | SKIP 0 | PASS 1121 ] + Error: Test failures + Execution halted ``` -# ggseqplot +# explore
-* Version: 0.8.3 -* GitHub: https://github.com/maraab23/ggseqplot -* Source code: https://github.com/cran/ggseqplot -* Date/Publication: 2023-09-22 21:30:02 UTC -* Number of recursive dependencies: 130 +* Version: 1.3.0 +* GitHub: https://github.com/rolkra/explore +* Source code: https://github.com/cran/explore +* Date/Publication: 2024-04-15 15:50:09 UTC +* Number of recursive dependencies: 97 -Run `revdepcheck::cloud_details(, "ggseqplot")` for more info +Run `revdepcheck::cloud_details(, "explore")` for more info
@@ -4804,184 +5077,154 @@ Run `revdepcheck::cloud_details(, "ggseqplot")` for more info * checking examples ... ERROR ``` - Running examples in ‘ggseqplot-Ex.R’ failed + Running examples in ‘explore-Ex.R’ failed The error most likely occurred in: - > ### Name: ggseqtrplot - > ### Title: Sequence Transition Rate Plot - > ### Aliases: ggseqtrplot + > ### Name: explore_targetpct + > ### Title: Explore variable + binary target (values 0/1) + > ### Aliases: explore_targetpct > > ### ** Examples > - > # Use example data from TraMineR: biofam data set + > iris$target01 <- ifelse(iris$Species == "versicolor",1,0) ... - 8 7 7 Divorced - [>] sum of weights: 330.07 - min/max: 0/6.02881860733032 - [>] 300 sequences in the data set - [>] min/max sequence length: 16/16 - > - > # Basic transition rate plot (with adjusted x-axis labels) - > ggseqtrplot(biofam.seq, x_n.dodge = 2) - Error in ggseqtrplot(biofam.seq, x_n.dodge = 2) : - labsize must be a single number + Backtrace: + ▆ + 1. ├─base (local) ``(x) + 2. └─ggplot2:::print.ggplot(x) + 3. ├─ggplot2::ggplot_gtable(data) + 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) + 5. └─ggplot2::calc_element("plot.margin", theme) + 6. └─cli::cli_abort(...) + 7. └─rlang::abort(...) Execution halted ``` -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(ggseqplot) - Loading required package: TraMineR - - TraMineR stable version 2.2-9 (Built: 2024-01-09) - Website: http://traminer.unige.ch - Please type 'citation("TraMineR")' for citation information. - ... - Backtrace: - ▆ - 1. ├─testthat::expect_s3_class(ggseqtrplot(biofam.seq), "ggplot") at test-ggseqtrplot.R:35:3 - 2. │ └─testthat::quasi_label(enquo(object), arg = "object") - 3. │ └─rlang::eval_bare(expr, quo_get_env(quo)) - 4. └─ggseqplot::ggseqtrplot(biofam.seq) - - [ FAIL 1 | WARN 1036 | SKIP 0 | PASS 131 ] - Error: Test failures - Execution halted - ``` - * checking running R code from vignettes ... ERROR ``` Errors in running code in vignettes: - when running code in ‘ggseqplot.Rmd’ + when running code in ‘explore-mtcars.Rmd’ ... - Scale for fill is already present. - Adding another scale for fill, which will replace the existing scale. - Scale for fill is already present. - Adding another scale for fill, which will replace the existing scale. + > data %>% explain_tree(target = highmpg) - > ggseqtrplot(actcal.seq, group = actcal$sex) + > data %>% explore(wt, target = highmpg) - When sourcing ‘ggseqplot.R’: - Error: labsize must be a single number - Execution halted + > data %>% explore(wt, target = highmpg, split = FALSE) + Warning: `position_dodge()` requires non-overlapping x intervals. - ‘ggseqplot.Rmd’ using ‘UTF-8’... failed + ... + ‘explain.Rmd’ using ‘UTF-8’... OK + ‘explore-mtcars.Rmd’ using ‘UTF-8’... failed + ‘explore-penguins.Rmd’ using ‘UTF-8’... OK + ‘explore-titanic.Rmd’ using ‘UTF-8’... OK + ‘explore.Rmd’ using ‘UTF-8’... failed + ‘predict.Rmd’ using ‘UTF-8’... OK + ‘report-target.Rmd’ using ‘UTF-8’... OK + ‘report-targetpct.Rmd’ using ‘UTF-8’... failed + ‘report.Rmd’ using ‘UTF-8’... OK + ‘tips-tricks.Rmd’ using ‘UTF-8’... OK ``` * checking re-building of vignette outputs ... NOTE ``` Error(s) in re-building vignettes: - --- re-building ‘ggseqplot.Rmd’ using rmarkdown + --- re-building ‘abtest.Rmd’ using rmarkdown ``` -# ggside +# ezplot
-* Version: 0.3.1 -* GitHub: https://github.com/jtlandis/ggside -* Source code: https://github.com/cran/ggside -* Date/Publication: 2024-03-01 09:12:37 UTC -* Number of recursive dependencies: 76 +* Version: 0.7.13 +* GitHub: NA +* Source code: https://github.com/cran/ezplot +* Date/Publication: 2024-01-28 11:30:05 UTC +* Number of recursive dependencies: 109 -Run `revdepcheck::cloud_details(, "ggside")` for more info +Run `revdepcheck::cloud_details(, "ezplot")` for more info
## Newly broken -* checking for code/documentation mismatches ... WARNING - ``` - Codoc mismatches from documentation object 'geom_xsideboxplot': - geom_xsideboxplot - Code: function(mapping = NULL, data = NULL, stat = "boxplot", - position = "dodge2", ..., outliers = TRUE, - outlier.colour = NULL, outlier.color = NULL, - outlier.fill = NULL, outlier.shape = NULL, - outlier.size = NULL, outlier.stroke = 0.5, - outlier.alpha = NULL, notch = FALSE, notchwidth = 0.5, - staplewidth = 0, varwidth = FALSE, na.rm = FALSE, - orientation = "x", show.legend = NA, inherit.aes = - ... - position = "dodge2", ..., outliers = TRUE, - outlier.colour = NULL, outlier.color = NULL, - outlier.fill = NULL, outlier.shape = 19, outlier.size - = 1.5, outlier.stroke = 0.5, outlier.alpha = NULL, - notch = FALSE, notchwidth = 0.5, staplewidth = 0, - varwidth = FALSE, na.rm = FALSE, orientation = "y", - show.legend = NA, inherit.aes = TRUE) - Mismatches in argument default values: - Name: 'outlier.shape' Code: NULL Docs: 19 - Name: 'outlier.size' Code: NULL Docs: 1.5 +* checking examples ... ERROR ``` - -# ggtern - -
- -* Version: 3.5.0 -* GitHub: NA -* Source code: https://github.com/cran/ggtern -* Date/Publication: 2024-03-24 21:50:02 UTC -* Number of recursive dependencies: 42 - -Run `revdepcheck::cloud_details(, "ggtern")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘ggtern-Ex.R’ failed + Running examples in ‘ezplot-Ex.R’ failed The error most likely occurred in: - > ### Name: annotate - > ### Title: Create an annotation layer (ggtern version). - > ### Aliases: annotate + > ### Name: bar_plot + > ### Title: bar_plot + > ### Aliases: bar_plot > > ### ** Examples > - > ggtern() + + > library(tsibble) ... - 16. │ └─ggplot2 (local) use_defaults(..., self = self) - 17. │ └─ggplot2:::eval_from_theme(default_aes, theme) - 18. │ ├─calc_element("geom", theme) %||% .default_geom_element - 19. │ └─ggplot2::calc_element("geom", theme) - 20. └─base::.handleSimpleError(...) - 21. └─rlang (local) h(simpleError(msg, call)) - 22. └─handlers[[1L]](cnd) - 23. └─cli::cli_abort(...) - 24. └─rlang::abort(...) + 11. │ └─base::withCallingHandlers(...) + 12. └─ggplot2 (local) f(l = layers[[i]], d = data[[i]]) + 13. └─l$compute_geom_2(d, theme = plot$theme) + 14. └─ggplot2 (local) compute_geom_2(..., self = self) + 15. └─self$geom$use_defaults(...) + 16. └─ggplot2 (local) use_defaults(..., self = self) + 17. └─ggplot2:::check_aesthetics(new_params, nrow(data)) + 18. └─cli::cli_abort(...) + 19. └─rlang::abort(...) Execution halted ``` -## In both - -* checking package dependencies ... NOTE +* checking running R code from vignettes ... ERROR ``` - Package which this enhances but not available for checking: ‘sp’ + Errors in running code in vignettes: + when running code in ‘bar_plot.Rmd’ + ... + + > bar_plot(ansett, "year(Week)", "Passengers", size = 16) + + When sourcing ‘bar_plot.R’: + Error: Problem while setting up geom aesthetics. + ℹ Error occurred in the 1st layer. + Caused by error in `check_aesthetics()`: + ... + Caused by error in `check_aesthetics()`: + ! Aesthetics must be either length 1 or the same as the data (9). + ✖ Fix the following mappings: `width`. + Execution halted + + ‘bar_plot.Rmd’ using ‘UTF-8’... failed + ‘basics.Rmd’ using ‘UTF-8’... failed + ‘line_plot.Rmd’ using ‘UTF-8’... OK + ‘overview.Rmd’ using ‘UTF-8’... failed + ‘variable_plot.Rmd’ using ‘UTF-8’... OK ``` -* checking Rd cross-references ... NOTE +* checking re-building of vignette outputs ... NOTE ``` - Package unavailable to check Rd xrefs: ‘chemometrics’ + Error(s) in re-building vignettes: + --- re-building ‘bar_plot.Rmd’ using rmarkdown + + Quitting from lines 28-29 [unnamed-chunk-2] (bar_plot.Rmd) + Error: processing vignette 'bar_plot.Rmd' failed with diagnostics: + Problem while setting up geom aesthetics. + ℹ Error occurred in the 1st layer. + Caused by error in `check_aesthetics()`: + ! Aesthetics must be either length 1 or the same as the data (6). + ✖ Fix the following mappings: `width`. + --- failed re-building ‘bar_plot.Rmd’ + + --- re-building ‘basics.Rmd’ using rmarkdown ``` -# ggVennDiagram +# fable.prophet
-* Version: 1.5.2 -* GitHub: https://github.com/gaospecial/ggVennDiagram -* Source code: https://github.com/cran/ggVennDiagram -* Date/Publication: 2024-02-20 08:10:02 UTC -* Number of recursive dependencies: 98 +* Version: 0.1.0 +* GitHub: https://github.com/mitchelloharawild/fable.prophet +* Source code: https://github.com/cran/fable.prophet +* Date/Publication: 2020-08-20 09:30:03 UTC +* Number of recursive dependencies: 114 -Run `revdepcheck::cloud_details(, "ggVennDiagram")` for more info +Run `revdepcheck::cloud_details(, "fable.prophet")` for more info
@@ -4990,138 +5233,153 @@ Run `revdepcheck::cloud_details(, "ggVennDiagram")` for more info * checking running R code from vignettes ... ERROR ``` Errors in running code in vignettes: - when running code in ‘fully-customed.Rmd’ + when running code in ‘intro.Rmd’ ... - [1] "b" "c" "e" "h" "k" "q" "s" "y" - - - > ggVennDiagram(y, show_intersect = TRUE, set_color = "black") - Warning in geom_text(aes(label = .data$count, text = .data$item), data = region_label) : - Ignoring unknown aesthetics: text + 9 Domestic mdl 2019 Dec sample[5000] 5335212. + 10 Domestic mdl 2020 Jan sample[5000] 4888063. + # ℹ 62 more rows - ... - Ignoring unknown aesthetics: text + > fc %>% autoplot(lax_passengers) - When sourcing ‘using-ggVennDiagram.R’: - Error: argument "theme" is missing, with no default + When sourcing ‘intro.R’: + Error: unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, "black", TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), NULL, list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), 5.5, c(5.5, 5.5, 5.5, 5.5), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.75, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, + NULL, NULL, NULL, 1, 90, NULL, c(0, 2.75, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 1, NULL, NULL, NULL, c(0, 2.2, 0, 0), NULL, TRUE), NULL, lis Execution halted - ‘VennCalculator.Rmd’ using ‘UTF-8’... OK - ‘fully-customed.Rmd’ using ‘UTF-8’... failed - ‘using-ggVennDiagram.Rmd’ using ‘UTF-8’... failed - ‘using-new-shapes.Rmd’ using ‘UTF-8’... OK + ‘intro.Rmd’ using ‘UTF-8’... failed ``` * checking re-building of vignette outputs ... NOTE ``` Error(s) in re-building vignettes: - --- re-building ‘VennCalculator.Rmd’ using rmarkdown - --- finished re-building ‘VennCalculator.Rmd’ - - --- re-building ‘fully-customed.Rmd’ using rmarkdown + --- re-building ‘intro.Rmd’ using rmarkdown ``` ## In both -* checking installed package size ... NOTE +* checking LazyData ... NOTE ``` - installed size is 11.0Mb - sub-directories of 1Mb or more: - doc 9.5Mb - help 1.1Mb + 'LazyData' is specified without a 'data' directory ``` -# GIFT +# fabletools
-* Version: 1.3.2 -* GitHub: https://github.com/BioGeoMacro/GIFT -* Source code: https://github.com/cran/GIFT -* Date/Publication: 2024-02-27 10:50:02 UTC -* Number of recursive dependencies: 119 +* Version: 0.4.2 +* GitHub: https://github.com/tidyverts/fabletools +* Source code: https://github.com/cran/fabletools +* Date/Publication: 2024-04-22 11:22:41 UTC +* Number of recursive dependencies: 106 -Run `revdepcheck::cloud_details(, "GIFT")` for more info +Run `revdepcheck::cloud_details(, "fabletools")` for more info
## Newly broken -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘GIFT.Rmd’ using rmarkdown - ``` - -## In both - -* checking running R code from vignettes ... ERROR +* checking examples ... ERROR ``` - Errors in running code in vignettes: - when running code in ‘GIFT.Rmd’ - ... - + library("knitr") - + .... [TRUNCATED] - - > options(tinytex.verbose = TRUE) - - > knitr::include_graphics("../man/figures/biodiv_gottingen_logo.png") + Running examples in ‘fabletools-Ex.R’ failed + The error most likely occurred in: + > ### Name: autoplot.fbl_ts + > ### Title: Plot a set of forecasts + > ### Aliases: autoplot.fbl_ts autolayer.fbl_ts + > + > ### ** Examples + > + > ## Don't show: ... - - > knitr::include_graphics("../man/figures/biodiv_gottingen_logo.png") - - When sourcing ‘GIFT_advanced_users.R’: - Error: Cannot find the file(s): "../man/figures/biodiv_gottingen_logo.png" + > library(fable) + > library(tsibbledata) + > fc <- aus_production %>% model(ets = ETS(log(Beer) ~ error("M") + trend("Ad") + + + season("A"))) %>% forecast(h = "3 years") + > fc %>% autoplot(aus_production) + Error in use_defaults(..., self = self) : + unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, "black", TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), NULL, list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), 5.5, c(5.5, 5.5, 5.5, 5.5), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.75, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, + NULL, NULL, NULL, 1, 90, NULL, c(0, 2.75, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 1, NULL, NULL, NULL, c(0, 2.2, 0, 0), NULL, TRUE), NULL, l + Calls: ... -> -> compute_geom_2 -> Execution halted - - ‘GIFT.Rmd’ using ‘UTF-8’... failed - ‘GIFT_API.Rmd’ using ‘UTF-8’... failed - ‘GIFT_advanced_users.Rmd’ using ‘UTF-8’... failed ``` -* checking installed package size ... NOTE +* checking tests ... ERROR ``` - installed size is 6.2Mb - sub-directories of 1Mb or more: - doc 3.3Mb - help 2.6Mb + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(dplyr) + + Attaching package: 'dplyr' + + The following object is masked from 'package:testthat': + + ... + 24. └─base::Map(...) + 25. └─base::mapply(FUN = f, ..., SIMPLIFY = FALSE) + 26. └─ggplot2 (local) ``(layer = dots[[1L]][[1L]], df = dots[[2L]][[1L]]) + 27. └─layer$compute_geom_2(key, single_params, theme) + 28. └─ggplot2 (local) compute_geom_2(..., self = self) + 29. └─self$geom$use_defaults(...) + + [ FAIL 2 | WARN 0 | SKIP 1 | PASS 269 ] + Error: Test failures + Execution halted ``` -# GimmeMyPlot +# factoextra
-* Version: 0.1.0 -* GitHub: NA -* Source code: https://github.com/cran/GimmeMyPlot -* Date/Publication: 2023-10-18 16:10:02 UTC -* Number of recursive dependencies: 111 +* Version: 1.0.7 +* GitHub: https://github.com/kassambara/factoextra +* Source code: https://github.com/cran/factoextra +* Date/Publication: 2020-04-01 21:20:02 UTC +* Number of recursive dependencies: 126 -Run `revdepcheck::cloud_details(, "GimmeMyPlot")` for more info +Run `revdepcheck::cloud_details(, "factoextra")` for more info
## Newly broken -* checking whether package ‘GimmeMyPlot’ can be installed ... WARNING +* checking examples ... ERROR ``` - Found the following significant warnings: - Warning: replacing previous import ‘ggplot2::ggpar’ by ‘ggpubr::ggpar’ when loading ‘GimmeMyPlot’ - See ‘/tmp/workdir/GimmeMyPlot/new/GimmeMyPlot.Rcheck/00install.out’ for details. + Running examples in ‘factoextra-Ex.R’ failed + The error most likely occurred in: + + > ### Name: eigenvalue + > ### Title: Extract and visualize the eigenvalues/variances of dimensions + > ### Aliases: eigenvalue get_eig get_eigenvalue fviz_eig fviz_screeplot + > + > ### ** Examples + > + > # Principal Component Analysis + ... + 11. │ └─base::withCallingHandlers(...) + 12. └─ggplot2 (local) f(l = layers[[i]], d = data[[i]]) + 13. └─l$compute_geom_2(d, theme = plot$theme) + 14. └─ggplot2 (local) compute_geom_2(..., self = self) + 15. └─self$geom$use_defaults(...) + 16. └─ggplot2 (local) use_defaults(..., self = self) + 17. └─ggplot2:::check_aesthetics(new_params, nrow(data)) + 18. └─cli::cli_abort(...) + 19. └─rlang::abort(...) + Execution halted ``` -# gprofiler2 +# faux
-* Version: 0.2.3 -* GitHub: NA -* Source code: https://github.com/cran/gprofiler2 -* Date/Publication: 2024-02-23 21:50:02 UTC -* Number of recursive dependencies: 74 +* Version: 1.2.1 +* GitHub: https://github.com/debruine/faux +* Source code: https://github.com/cran/faux +* Date/Publication: 2023-04-20 07:00:11 UTC +* Number of recursive dependencies: 131 -Run `revdepcheck::cloud_details(, "gprofiler2")` for more info +Run `revdepcheck::cloud_details(, "faux")` for more info
@@ -5129,71 +5387,124 @@ Run `revdepcheck::cloud_details(, "gprofiler2")` for more info * checking examples ... ERROR ``` - Running examples in ‘gprofiler2-Ex.R’ failed + Running examples in ‘faux-Ex.R’ failed The error most likely occurred in: - > ### Name: gostplot - > ### Title: Manhattan plot of functional enrichment results. - > ### Aliases: gostplot + > ### Name: beta2norm + > ### Title: Convert beta to normal + > ### Aliases: beta2norm > > ### ** Examples > - > gostres <- gost(c("Klf4", "Pax5", "Sox2", "Nanog"), organism = "mmusculus") - > gostplot(gostres) - Error in compute_geom_2(..., self = self) : - argument "theme" is missing, with no default - Calls: gostplot ... use_defaults -> eval_from_theme -> %||% -> calc_element + > + ... + Backtrace: + ▆ + 1. └─ggExtra::ggMarginal(g, type = "histogram") + 2. └─ggplot2::ggplotGrob(scatP) + 3. ├─ggplot2::ggplot_gtable(ggplot_build(x)) + 4. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) + 5. └─ggplot2::calc_element("plot.margin", theme) + 6. └─cli::cli_abort(...) + 7. └─rlang::abort(...) Execution halted ``` +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘codebook.Rmd’ using rmarkdown + --- finished re-building ‘codebook.Rmd’ + + --- re-building ‘continuous.Rmd’ using rmarkdown + ``` + +## In both + * checking running R code from vignettes ... ERROR ``` Errors in running code in vignettes: - when running code in ‘gprofiler2.Rmd’ + when running code in ‘norta.Rmd’ ... - effective_domain_size source_order parents - 1 20212 1236 GO:0005003 - 2 20212 1234 GO:0004714 - 3 21031 12892 GO:0007169 + > p <- ggplot(dat, aes(uniform_var, poisson_var)) + + + geom_point() + geom_smooth() - > gostplot(gostres, capped = TRUE, interactive = TRUE) + > ggMarginal(p, type = "histogram") + `geom_smooth()` using method = 'gam' and formula = 'y ~ s(x, bs = "cs")' + `geom_smooth()` using method = 'gam' and formula = 'y ~ s(x, bs = "cs")' - When sourcing ‘gprofiler2.R’: - Error: argument "theme" is missing, with no default + ... + Error: Theme element `plot.margin` must have class . Execution halted - ‘gprofiler2.Rmd’ using ‘UTF-8’... failed + ‘codebook.Rmd’ using ‘UTF-8’... OK + ‘continuous.Rmd’ using ‘UTF-8’... OK + ‘contrasts.Rmd’ using ‘UTF-8’... OK + ‘norta.Rmd’ using ‘UTF-8’... failed + ‘rnorm_multi.Rmd’ using ‘UTF-8’... OK + ‘sim_design.Rmd’ using ‘UTF-8’... OK + ‘sim_df.Rmd’ using ‘UTF-8’... OK ``` -* checking re-building of vignette outputs ... NOTE +# fddm + +
+ +* Version: 0.5-2 +* GitHub: https://github.com/rtdists/fddm +* Source code: https://github.com/cran/fddm +* Date/Publication: 2022-09-09 19:02:54 UTC +* Number of recursive dependencies: 86 + +Run `revdepcheck::cloud_details(, "fddm")` for more info + +
+ +## Newly broken + +* checking running R code from vignettes ... ERROR ``` - Error(s) in re-building vignettes: + Errors in running code in vignettes: + when running code in ‘benchmark.Rmd’ ... - --- re-building ‘gprofiler2.Rmd’ using rmarkdown + > ma <- max(bm_vec[, (t_idx + 1):(ncol(bm_vec) - 4)]) - Quitting from lines at lines 246-247 [unnamed-chunk-14] (gprofiler2.Rmd) - Error: processing vignette 'gprofiler2.Rmd' failed with diagnostics: - argument "theme" is missing, with no default - --- failed re-building ‘gprofiler2.Rmd’ + > ggplot(mbm_vec, aes(x = factor(FuncName, levels = Names_vec), + + y = time, color = factor(FuncName, levels = Names_vec), fill = factor(FuncName, .... [TRUNCATED] + Warning: The dot-dot notation (`..y..`) was deprecated in ggplot2 3.4.0. + ℹ Please use `after_stat(y)` instead. - SUMMARY: processing the following file failed: - ‘gprofiler2.Rmd’ + ... - Error: Vignette re-building failed. + When sourcing ‘pfddm.R’: + Error: Not a unit object Execution halted + + ‘benchmark.Rmd’ using ‘UTF-8’... failed + ‘example.Rmd’ using ‘UTF-8’... OK + ‘math.Rmd’ using ‘UTF-8’... OK + ‘pfddm.Rmd’ using ‘UTF-8’... failed + ‘validity.Rmd’ using ‘UTF-8’... OK ``` -# Greymodels +## In both + +* checking C++ specification ... NOTE + ``` + Specified C++11: please drop specification unless essential + ``` + +# fdrci
-* Version: 2.0.1 -* GitHub: https://github.com/havishaJ/Greymodels -* Source code: https://github.com/cran/Greymodels -* Date/Publication: 2022-12-05 12:42:35 UTC -* Number of recursive dependencies: 91 +* Version: 2.4 +* GitHub: NA +* Source code: https://github.com/cran/fdrci +* Date/Publication: 2022-10-18 02:12:32 UTC +* Number of recursive dependencies: 81 -Run `revdepcheck::cloud_details(, "Greymodels")` for more info +Run `revdepcheck::cloud_details(, "fdrci")` for more info
@@ -5201,149 +5512,187 @@ Run `revdepcheck::cloud_details(, "Greymodels")` for more info * checking examples ... ERROR ``` - Running examples in ‘Greymodels-Ex.R’ failed + Running examples in ‘fdrci-Ex.R’ failed The error most likely occurred in: - > ### Name: Plots - > ### Title: plots - > ### Aliases: plots plotrm plotsmv1 plotsmv2 plotsigndgm plots_mdbgm12 + > ### Name: FDRplot + > ### Title: Plot results of FDR table generated by fdrTbl() + > ### Aliases: FDRplot > > ### ** Examples > - > # Plots - EPGM (1, 1) model + > ss = 100 ... - + geom_line(data = xy1, aes(x = x, y = y,color = "Raw Data")) + - + geom_line(data = xy2, aes(x = x, y = y,color = "Fitted&Forecasts")) + - + geom_line(data = set3, aes(x = CI, y = y,color = "LowerBound"), linetype=2) + - + geom_line(data = set4, aes(x = CI, y = y,color = "UpperBound"), linetype=2) + - + scale_color_manual(name = "Label",values = colors) - > r <- ggplotly(p) - Error in compute_geom_2(..., self = self) : - argument "theme" is missing, with no default - Calls: ggplotly ... use_defaults -> eval_from_theme -> %||% -> calc_element + Backtrace: + ▆ + 1. ├─base (local) ``(x) + 2. └─ggplot2:::print.ggplot(x) + 3. ├─ggplot2::ggplot_gtable(data) + 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) + 5. └─ggplot2::calc_element("plot.margin", theme) + 6. └─cli::cli_abort(...) + 7. └─rlang::abort(...) Execution halted ``` -# h3jsr +# ffp
-* Version: 1.3.1 -* GitHub: NA -* Source code: https://github.com/cran/h3jsr -* Date/Publication: 2023-01-21 09:20:10 UTC -* Number of recursive dependencies: 96 +* Version: 0.2.2 +* GitHub: https://github.com/Reckziegel/FFP +* Source code: https://github.com/cran/ffp +* Date/Publication: 2022-09-29 15:10:06 UTC +* Number of recursive dependencies: 107 -Run `revdepcheck::cloud_details(, "h3jsr")` for more info +Run `revdepcheck::cloud_details(, "ffp")` for more info
## Newly broken -* checking running R code from vignettes ... ERROR +* checking examples ... ERROR ``` - Errors in running code in vignettes: - when running code in ‘intro-to-h3jsr.Rmd’ - ... - + scale_fill_ .... [TRUNCATED] - - When sourcing ‘intro-to-h3jsr.R’: - Error: Summary operations are not defined for quosures. Do you need to unquote - the quosure? - - # Bad: min(myquosure) - - # Good: min(!!myquosure) - Execution halted - - ‘intro-to-h3jsr.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - ... - --- re-building ‘intro-to-h3jsr.Rmd’ using rmarkdown - - Quitting from lines at lines 79-89 [c4] (intro-to-h3jsr.Rmd) - Error: processing vignette 'intro-to-h3jsr.Rmd' failed with diagnostics: - Summary operations are not defined for quosures. Do you need to unquote - the quosure? - - # Bad: min(myquosure) - - # Good: min(!!myquosure) - --- failed re-building ‘intro-to-h3jsr.Rmd’ - - SUMMARY: processing the following file failed: - ‘intro-to-h3jsr.Rmd’ + Running examples in ‘ffp-Ex.R’ failed + The error most likely occurred in: - Error: Vignette re-building failed. + > ### Name: scenario_density + > ### Title: Plot Scenarios + > ### Aliases: scenario_density scenario_histogram + > + > ### ** Examples + > + > x <- diff(log(EuStockMarkets))[, 1] + > p <- exp_decay(x, 0.005) + > + > scenario_density(x, p, 500) + Error in use_defaults(..., self = self) : + unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, "black", TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), NULL, list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), 5.5, c(5.5, 5.5, 5.5, 5.5), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.75, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, + NULL, NULL, NULL, 1, 90, NULL, c(0, 2.75, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, NULL, c(0, 0, 0, 2.2), NULL, + Calls: ... -> -> compute_geom_2 -> Execution halted ``` -# healthyR +# fido
-* Version: 0.2.1 -* GitHub: https://github.com/spsanderson/healthyR -* Source code: https://github.com/cran/healthyR -* Date/Publication: 2023-04-06 22:20:03 UTC -* Number of recursive dependencies: 157 +* Version: 1.1.0 +* GitHub: https://github.com/jsilve24/fido +* Source code: https://github.com/cran/fido +* Date/Publication: 2024-05-30 07:00:24 UTC +* Number of recursive dependencies: 130 -Run `revdepcheck::cloud_details(, "healthyR")` for more info +Run `revdepcheck::cloud_details(, "fido")` for more info
## Newly broken -* checking running R code from vignettes ... ERROR +* checking examples ... ERROR + ``` + Running examples in ‘fido-Ex.R’ failed + The error most likely occurred in: + + > ### Name: plot.pibblefit + > ### Title: Plot Summaries of Posterior Distribution of pibblefit Parameters + > ### Aliases: plot.pibblefit + > + > ### ** Examples + > + > sim <- pibble_sim(N=10, D=4, Q=3) + > fit <- pibble(sim$Y, sim$X) + > plot(fit, par="Lambda") + Scale for colour is already present. + Adding another scale for colour, which will replace the existing scale. + Error in use_defaults(..., self = self) : + unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, "black", TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), NULL, list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), 5.5, c(5.5, 5.5, 5.5, 5.5), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.75, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(), NULL, list( + NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 1, NULL, NULL, NULL, c(0, 2.2, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, NULL, c(0, 0, 0, 2.2), NULL, + Calls: ... -> -> compute_geom_2 -> + Execution halted + ``` + +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(fido) + > + > #Sys.setenv(KMP_DUPLICATE_LIB_OK="TRUE") + > test_check("fido") + [1] 0.27980164 -0.69169550 -0.53205652 0.11488451 -0.42419872 2.20261388 + [7] -1.62190133 -0.90893172 0.07891428 0.75060681 0.43593605 0.26819442 + ... + 21. └─base::Map(...) + 22. └─base::mapply(FUN = f, ..., SIMPLIFY = FALSE) + 23. └─ggplot2 (local) ``(layer = dots[[1L]][[1L]], df = dots[[2L]][[1L]]) + 24. └─layer$compute_geom_2(key, single_params, theme) + 25. └─ggplot2 (local) compute_geom_2(..., self = self) + 26. └─self$geom$use_defaults(...) + + [ FAIL 1 | WARN 0 | SKIP 0 | PASS 114 ] + Error: Test failures + Execution halted + ``` + +## In both + +* checking running R code from vignettes ... WARNING ``` Errors in running code in vignettes: - when running code in ‘getting-started.Rmd’ + when running code in ‘non-linear-models.Rmd’ ... - > ts_alos_plt(.data = df_tbl, .date_col = Date, .value_col = Values, - + .by = "month", .interactive = FALSE) + The following object is masked from ‘package:dplyr’: - > ts_alos_plt(.data = df_tbl, .date_col = Date, .value_col = Values, - + .by = "month", .interactive = TRUE) + select - When sourcing ‘getting-started.R’: - Error: argument "theme" is missing, with no default + + When sourcing ‘non-linear-models.R’: + Error: package or namespace load failed for ‘MCMCpack’ in loadNamespace(i, c(lib.loc, .libPaths()), versionCheck = vI[[i]]): + there is no package called ‘quantreg’ Execution halted - ‘getting-started.Rmd’ using ‘UTF-8’... failed + ‘introduction-to-fido.Rmd’ using ‘UTF-8’... OK + ‘mitigating-pcrbias.Rmd’ using ‘UTF-8’... OK + ‘non-linear-models.Rmd’ using ‘UTF-8’... failed + ‘orthus.Rmd’ using ‘UTF-8’... OK + ‘picking_priors.Rmd’ using ‘UTF-8’... OK ``` -* checking re-building of vignette outputs ... NOTE +* checking installed package size ... NOTE ``` - Error(s) in re-building vignettes: - --- re-building ‘getting-started.Rmd’ using rmarkdown + installed size is 106.2Mb + sub-directories of 1Mb or more: + data 4.0Mb + libs 100.5Mb ``` -## In both - -* checking installed package size ... NOTE +* checking re-building of vignette outputs ... NOTE ``` - installed size is 6.5Mb - sub-directories of 1Mb or more: - data 2.4Mb - doc 3.7Mb + Error(s) in re-building vignettes: + --- re-building ‘introduction-to-fido.Rmd’ using rmarkdown + --- finished re-building ‘introduction-to-fido.Rmd’ + + --- re-building ‘mitigating-pcrbias.Rmd’ using rmarkdown + --- finished re-building ‘mitigating-pcrbias.Rmd’ + + --- re-building ‘non-linear-models.Rmd’ using rmarkdown ``` -# healthyR.ai +# figuRes2
-* Version: 0.0.13 -* GitHub: https://github.com/spsanderson/healthyR.ai -* Source code: https://github.com/cran/healthyR.ai -* Date/Publication: 2023-04-03 00:20:02 UTC -* Number of recursive dependencies: 228 +* Version: 1.0.0 +* GitHub: https://github.com/gcicc/figures2 +* Source code: https://github.com/cran/figuRes2 +* Date/Publication: 2022-09-09 08:02:55 UTC +* Number of recursive dependencies: 112 -Run `revdepcheck::cloud_details(, "healthyR.ai")` for more info +Run `revdepcheck::cloud_details(, "figuRes2")` for more info
@@ -5351,286 +5700,352 @@ Run `revdepcheck::cloud_details(, "healthyR.ai")` for more info * checking examples ... ERROR ``` - Running examples in ‘healthyR.ai-Ex.R’ failed + Running examples in ‘figuRes2-Ex.R’ failed The error most likely occurred in: - > ### Name: pca_your_recipe - > ### Title: Perform PCA - > ### Aliases: pca_your_recipe + > ### Name: km.plot + > ### Title: km.plot + > ### Aliases: km.plot > > ### ** Examples > - > suppressPackageStartupMessages(library(timetk)) + > { ... - > - > output_list <- pca_your_recipe(rec_obj, .data = data_tbl) - Warning: ! The following columns have zero variance so scaling cannot be used: - date_col_day, date_col_mday, date_col_mweek, and date_col_mday7. - ℹ Consider using ?step_zv (`?recipes::step_zv()`) to remove those columns - before normalizing. - Error in compute_geom_2(..., self = self) : - argument "theme" is missing, with no default - Calls: pca_your_recipe ... use_defaults -> eval_from_theme -> %||% -> calc_element + Backtrace: + ▆ + 1. ├─base::print(km.M[[2]]) + 2. └─ggplot2:::print.ggplot(km.M[[2]]) + 3. ├─ggplot2::ggplot_gtable(data) + 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) + 5. └─ggplot2::calc_element("plot.margin", theme) + 6. └─cli::cli_abort(...) + 7. └─rlang::abort(...) Execution halted ``` * checking running R code from vignettes ... ERROR ``` Errors in running code in vignettes: - when running code in ‘getting-started.Rmd’ + when running code in ‘basics.Rmd’ ... - > pca_list <- pca_your_recipe(.recipe_object = rec_obj, - + .data = data_tbl, .threshold = 0.8, .top_n = 5) - Warning: ! The following columns have zero variance so scaling cannot be used: - date_col_day, date_col_mday, date_col_mweek, and date_col_mday7. - ℹ Consider using ?step_zv (`?recipes::step_zv()`) to remove those columns - before normalizing. - When sourcing ‘getting-started.R’: - Error: argument "theme" is missing, with no default - Execution halted + > ex.bar <- ggplot(data = working.df, aes(x = group, + + fill = group)) + geom_bar() + labs(x = "Group", y = "Frequency", + + title = "", fill = .... [TRUNCATED] - ‘auto-kmeans.Rmd’ using ‘UTF-8’... OK - ‘getting-started.Rmd’ using ‘UTF-8’... failed - ‘kmeans-umap.Rmd’ using ‘UTF-8’... OK - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘auto-kmeans.Rmd’ using rmarkdown - --- finished re-building ‘auto-kmeans.Rmd’ + > print(ex.bar) - --- re-building ‘getting-started.Rmd’ using rmarkdown + ... + > km.M[[2]] - Quitting from lines at lines 107-113 [pca_your_rec] (getting-started.Rmd) - Error: processing vignette 'getting-started.Rmd' failed with diagnostics: - argument "theme" is missing, with no default - --- failed re-building ‘getting-started.Rmd’ + When sourcing ‘km.R’: + Error: Theme element `plot.margin` must have class . + Execution halted - --- re-building ‘kmeans-umap.Rmd’ using rmarkdown + ‘basics.Rmd’ using ‘UTF-8’... failed + ‘forest-plots.Rmd’ using ‘UTF-8’... OK + ‘km.Rmd’ using ‘UTF-8’... failed + ‘large-scale.Rmd’ using ‘UTF-8’... OK ``` -# healthyR.ts +# flipr
-* Version: 0.3.0 -* GitHub: https://github.com/spsanderson/healthyR.ts -* Source code: https://github.com/cran/healthyR.ts -* Date/Publication: 2023-11-15 06:00:05 UTC -* Number of recursive dependencies: 222 +* Version: 0.3.3 +* GitHub: https://github.com/LMJL-Alea/flipr +* Source code: https://github.com/cran/flipr +* Date/Publication: 2023-08-23 09:00:02 UTC +* Number of recursive dependencies: 106 -Run `revdepcheck::cloud_details(, "healthyR.ts")` for more info +Run `revdepcheck::cloud_details(, "flipr")` for more info
## Newly broken -* checking examples ... ERROR +* checking re-building of vignette outputs ... NOTE ``` - Running examples in ‘healthyR.ts-Ex.R’ failed - The error most likely occurred in: + Error(s) in re-building vignettes: + --- re-building ‘alternative.Rmd’ using rmarkdown + --- finished re-building ‘alternative.Rmd’ - > ### Name: tidy_fft - > ### Title: Tidy Style FFT - > ### Aliases: tidy_fft - > - > ### ** Examples - > - > suppressPackageStartupMessages(library(dplyr)) - ... - + .data = data_tbl, - + .value_col = value, - + .date_col = date_col, - + .harmonics = 3, - + .frequency = 12 - + ) - Error in compute_geom_2(..., self = self) : - argument "theme" is missing, with no default - Calls: tidy_fft ... use_defaults -> eval_from_theme -> %||% -> calc_element - Execution halted + --- re-building ‘exactness.Rmd’ using rmarkdown + + Quitting from lines 142-177 [unnamed-chunk-1] (exactness.Rmd) + Error: processing vignette 'exactness.Rmd' failed with diagnostics: + subscript out of bounds + --- failed re-building ‘exactness.Rmd’ + + --- re-building ‘flipr.Rmd’ using rmarkdown ``` +## In both + * checking running R code from vignettes ... ERROR ``` Errors in running code in vignettes: - when running code in ‘using-tidy-fft.Rmd’ + when running code in ‘exactness.Rmd’ ... - $ value 112, 118, 132, 129, 121, 135, 148, 148, 136, 119, 104, 118, 1… - > suppressPackageStartupMessages(library(timetk)) + > library(flipr) - > data_tbl %>% plot_time_series(.date_var = date_col, - + .value = value) + > load("../R/sysdata.rda") + Warning in readChar(con, 5L, useBytes = TRUE) : + cannot open compressed file '../R/sysdata.rda', probable reason 'No such file or directory' - When sourcing ‘using-tidy-fft.R’: - Error: argument "theme" is missing, with no default + ... + cannot open compressed file '../R/sysdata.rda', probable reason 'No such file or directory' + + When sourcing ‘plausibility.R’: + Error: cannot open the connection Execution halted - ‘getting-started.Rmd’ using ‘UTF-8’... OK - ‘using-tidy-fft.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘getting-started.Rmd’ using rmarkdown + ‘alternative.Rmd’ using ‘UTF-8’... OK + ‘exactness.Rmd’ using ‘UTF-8’... failed + ‘flipr.Rmd’ using ‘UTF-8’... failed + ‘plausibility.Rmd’ using ‘UTF-8’... failed ``` -## In both - * checking installed package size ... NOTE ``` - installed size is 6.5Mb + installed size is 11.0Mb sub-directories of 1Mb or more: - doc 5.2Mb + doc 9.1Mb + libs 1.2Mb ``` -# heatmaply +# FMM
-* Version: 1.5.0 -* GitHub: https://github.com/talgalili/heatmaply -* Source code: https://github.com/cran/heatmaply -* Date/Publication: 2023-10-06 20:50:02 UTC -* Number of recursive dependencies: 111 +* Version: 0.3.1 +* GitHub: https://github.com/alexARC26/FMM +* Source code: https://github.com/cran/FMM +* Date/Publication: 2021-12-17 12:52:03 UTC +* Number of recursive dependencies: 68 -Run `revdepcheck::cloud_details(, "heatmaply")` for more info +Run `revdepcheck::cloud_details(, "FMM")` for more info
## Newly broken -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(heatmaply) - Loading required package: plotly - Loading required package: ggplot2 - - Attaching package: 'plotly' - - ... - 14. └─ggplot2 (local) compute_geom_2(..., self = self) - 15. └─self$geom$use_defaults(data, self$aes_params, modifiers, theme = theme) - 16. └─ggplot2 (local) use_defaults(..., self = self) - 17. └─ggplot2:::eval_from_theme(default_aes, theme) - 18. ├─calc_element("geom", theme) %||% .default_geom_element - 19. └─ggplot2::calc_element("geom", theme) - - [ FAIL 58 | WARN 0 | SKIP 0 | PASS 193 ] - Error: Test failures - Execution halted - ``` - * checking running R code from vignettes ... ERROR ``` Errors in running code in vignettes: - when running code in ‘heatmaply.Rmd’ + when running code in ‘FMMVignette.Rmd’ ... + + 0.25, 0, 1), "cm")) + ylim(-5, 6) + scale_color_manual(values = brewer.pal("Set1", + + .... [TRUNCATED] + Scale for colour is already present. + Adding another scale for colour, which will replace the existing scale. - > library("heatmaply") - - > library("heatmaply") - - > heatmaply(mtcars) + > grid.arrange(defaultrFMM2, comprFMM2, nrow = 1) - When sourcing ‘heatmaply.R’: - Error: argument "theme" is missing, with no default + When sourcing ‘FMMVignette.R’: + Error: Theme element `plot.margin` must have class . Execution halted - ‘heatmaply.Rmd’ using ‘UTF-8’... failed + ‘FMMVignette.Rmd’ using ‘UTF-8’... failed ``` * checking re-building of vignette outputs ... NOTE ``` Error(s) in re-building vignettes: - ... - --- re-building ‘heatmaply.Rmd’ using rmarkdown - - Quitting from lines at lines 109-111 [unnamed-chunk-5] (heatmaply.Rmd) - Error: processing vignette 'heatmaply.Rmd' failed with diagnostics: - argument "theme" is missing, with no default - --- failed re-building ‘heatmaply.Rmd’ - - SUMMARY: processing the following file failed: - ‘heatmaply.Rmd’ - - Error: Vignette re-building failed. - Execution halted + --- re-building ‘FMMVignette.Rmd’ using rmarkdown + ``` + +# fmriqa + +
+ +* Version: 0.3.0 +* GitHub: https://github.com/martin3141/fmriqa +* Source code: https://github.com/cran/fmriqa +* Date/Publication: 2018-02-19 15:59:01 UTC +* Number of recursive dependencies: 96 + +Run `revdepcheck::cloud_details(, "fmriqa")` for more info + +
+ +## Newly broken + +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(fmriqa) + > + > test_check("fmriqa") + Reading data : /tmp/workdir/fmriqa/new/fmriqa.Rcheck/fmriqa/extdata/qa_data.nii.gz + + Basic analysis parameters + ... + 5. └─ggplot2 (local) FUN(X[[i]], ...) + 6. ├─ggplot2::ggplot_gtable(ggplot_build(x)) + 7. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) + 8. └─ggplot2::calc_element("plot.margin", theme) + 9. └─cli::cli_abort(...) + 10. └─rlang::abort(...) + + [ FAIL 2 | WARN 2 | SKIP 1 | PASS 0 ] + Error: Test failures + Execution halted ``` ## In both -* checking installed package size ... NOTE +* checking LazyData ... NOTE ``` - installed size is 5.7Mb - sub-directories of 1Mb or more: - doc 5.1Mb + 'LazyData' is specified without a 'data' directory ``` -# hilldiv +# foreSIGHT
-* Version: 1.5.1 -* GitHub: https://github.com/anttonalberdi/hilldiv -* Source code: https://github.com/cran/hilldiv -* Date/Publication: 2019-10-01 14:40:02 UTC -* Number of recursive dependencies: 153 +* Version: 1.2.0 +* GitHub: https://github.com/ClimateAnalytics/foreSIGHT +* Source code: https://github.com/cran/foreSIGHT +* Date/Publication: 2023-10-19 07:00:08 UTC +* Number of recursive dependencies: 92 -Run `revdepcheck::cloud_details(, "hilldiv")` for more info +Run `revdepcheck::cloud_details(, "foreSIGHT")` for more info
## Newly broken -* checking whether package ‘hilldiv’ can be installed ... WARNING +* checking examples ... ERROR ``` - Found the following significant warnings: - Warning: replacing previous import ‘ggplot2::ggpar’ by ‘ggpubr::ggpar’ when loading ‘hilldiv’ - See ‘/tmp/workdir/hilldiv/new/hilldiv.Rcheck/00install.out’ for details. + Running examples in ‘foreSIGHT-Ex.R’ failed + The error most likely occurred in: + + > ### Name: plotOptions + > ### Title: Plots the differences in performance metrics from two system + > ### options + > ### Aliases: plotOptions + > + > ### ** Examples + > + ... + 1. └─foreSIGHT::plotOptions(...) + 2. ├─base::print(p1) + 3. ├─base::print(p1) + 4. └─ggplot2:::print.ggplot(p1) + 5. ├─ggplot2::ggplot_gtable(data) + 6. └─ggplot2:::ggplot_gtable.ggplot_built(data) + 7. └─ggplot2::calc_element("plot.margin", theme) + 8. └─cli::cli_abort(...) + 9. └─rlang::abort(...) + Execution halted + ``` + +* checking re-building of vignette outputs ... ERROR + ``` + Error(s) in re-building vignettes: + --- re-building ‘Vignette_QuickStart_simpleScal.Rmd’ using rmarkdown_notangle + ``` + +## In both + +* checking installed package size ... NOTE + ``` + installed size is 5.7Mb + sub-directories of 1Mb or more: + data 2.0Mb + doc 1.3Mb + libs 1.7Mb ``` -# hJAM +# frailtyEM
-* Version: 1.0.0 -* GitHub: https://github.com/lailylajiang/hJAM -* Source code: https://github.com/cran/hJAM -* Date/Publication: 2020-02-20 14:50:05 UTC -* Number of recursive dependencies: 101 +* Version: 1.0.1 +* GitHub: https://github.com/tbalan/frailtyEM +* Source code: https://github.com/cran/frailtyEM +* Date/Publication: 2019-09-22 13:00:10 UTC +* Number of recursive dependencies: 78 -Run `revdepcheck::cloud_details(, "hJAM")` for more info +Run `revdepcheck::cloud_details(, "frailtyEM")` for more info
## Newly broken -* checking whether package ‘hJAM’ can be installed ... WARNING +* checking examples ... ERROR ``` - Found the following significant warnings: - Warning: replacing previous import ‘ggplot2::ggpar’ by ‘ggpubr::ggpar’ when loading ‘hJAM’ - See ‘/tmp/workdir/hJAM/new/hJAM.Rcheck/00install.out’ for details. + Running examples in ‘frailtyEM-Ex.R’ failed + The error most likely occurred in: + + > ### Name: summary.emfrail + > ### Title: Summary for 'emfrail' objects + > ### Aliases: summary.emfrail + > + > ### ** Examples + > + > data("bladder") + ... + filter + + The following object is masked from ‘package:graphics’: + + layout + + > ggplotly(pl2) + Error in pm[[2]] : subscript out of bounds + Calls: ggplotly -> ggplotly.ggplot -> gg2list + Execution halted ``` -# HVT +## In both + +* checking LazyData ... NOTE + ``` + 'LazyData' is specified without a 'data' directory + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘frailtyEM_manual.Rnw’ using Sweave + Loading required package: survival + Loading required package: gridExtra + Warning: The `` argument of `guides()` cannot be `FALSE`. Use + "none" instead as of ggplot2 3.3.4. + Warning: Removed 2 rows containing missing values or values outside + the scale range (`geom_path()`). + Warning in data("kidney") : data set ‘kidney’ not found + Warning in emfrail(Surv(time, status) ~ age + sex + cluster(id), data = kidney, : + ... + l.179 \RequirePackage{grfext}\relax + ^^M + ! ==> Fatal error occurred, no output PDF file produced! + --- failed re-building ‘frailtyEM_manual.Rnw’ + + SUMMARY: processing the following file failed: + ‘frailtyEM_manual.Rnw’ + + Error: Vignette re-building failed. + Execution halted + ``` + +# funcharts
-* Version: 23.11.1 -* GitHub: https://github.com/Mu-Sigma/HVT -* Source code: https://github.com/cran/HVT -* Date/Publication: 2023-11-19 15:20:12 UTC -* Number of recursive dependencies: 200 +* Version: 1.4.1 +* GitHub: https://github.com/unina-sfere/funcharts +* Source code: https://github.com/cran/funcharts +* Date/Publication: 2024-02-22 08:50:02 UTC +* Number of recursive dependencies: 123 -Run `revdepcheck::cloud_details(, "HVT")` for more info +Run `revdepcheck::cloud_details(, "funcharts")` for more info
@@ -5638,317 +6053,495 @@ Run `revdepcheck::cloud_details(, "HVT")` for more info * checking examples ... ERROR ``` - Running examples in ‘HVT-Ex.R’ failed + Running examples in ‘funcharts-Ex.R’ failed The error most likely occurred in: - > ### Name: diagPlot - > ### Title: Diagnosis Plot - > ### Aliases: diagPlot - > ### Keywords: hplot internal + > ### Name: pca_mfd + > ### Title: Multivariate functional principal components analysis + > ### Aliases: pca_mfd > > ### ** Examples > - ... - Scale for x is already present. - Adding another scale for x, which will replace the existing scale. - Scale for y is already present. - Adding another scale for y, which will replace the existing scale. - Warning in geom_polygon(data = boundaryCoords2, aes(x = bp.x, y = bp.y, : - Ignoring unknown aesthetics: text - Error in compute_geom_2(..., self = self) : - argument "theme" is missing, with no default - Calls: HVT ... use_defaults -> eval_from_theme -> %||% -> calc_element + > library(funcharts) + > mfdobj <- data_sim_mfd() + > pca_obj <- pca_mfd(mfdobj) + > plot_pca_mfd(pca_obj) + Error in identicalUnits(x) : object is not a unit + Calls: ... assemble_guides -> guides_build -> unit.c -> identicalUnits Execution halted ``` -# HYPEtools +# gapmap
-* Version: 1.6.1 -* GitHub: https://github.com/rcapell/HYPEtools -* Source code: https://github.com/cran/HYPEtools -* Date/Publication: 2024-01-12 17:20:02 UTC -* Number of recursive dependencies: 164 +* Version: 1.0.0 +* GitHub: https://github.com/evanbiederstedt/gapmap +* Source code: https://github.com/cran/gapmap +* Date/Publication: 2024-01-22 20:50:02 UTC +* Number of recursive dependencies: 55 -Run `revdepcheck::cloud_details(, "HYPEtools")` for more info +Run `revdepcheck::cloud_details(, "gapmap")` for more info
## Newly broken +* checking examples ... ERROR + ``` + Running examples in ‘gapmap-Ex.R’ failed + The error most likely occurred in: + + > ### Name: gapmap + > ### Title: Function to draw a gapped cluster heatmap + > ### Aliases: gapmap + > + > ### ** Examples + > + > set.seed(1234) + ... + ! Theme element `plot.margin` must have class . + Backtrace: + ▆ + 1. └─gapmap::gapmap(m = as.matrix(distxy), d_row = rev(dend), d_col = dend) + 2. ├─ggplot2::ggplot_gtable(ggplot2::ggplot_build(hm)) + 3. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot2::ggplot_build(hm)) + 4. └─ggplot2::calc_element("plot.margin", theme) + 5. └─cli::cli_abort(...) + 6. └─rlang::abort(...) + Execution halted + ``` + * checking running R code from vignettes ... ERROR ``` Errors in running code in vignettes: - when running code in ‘plot_map_statistics.Rmd’ + when running code in ‘simple_example.Rmd’ ... - - > stat.nm.plot <- "NSE" - - > PlotMapPoints(x = stats.cout[, c(1, stat.col.plot)], - + sites = map.Qobs, sites.subid.column = 3, bg = map.subid) - Joining "SUBID" from GIS Data (sites) To "SUBID" from subass (x) + + col = grey_scale) + Warning: The `panel.margin` argument of `theme()` is deprecated as of ggplot2 2.2.0. + ℹ Please use the `panel.spacing` argument instead. + ℹ The deprecated feature was likely used in the gapmap package. + Please report the issue at + . ... - When sourcing ‘plot_map_statistics.R’: - Error: 'language' object cannot be coerced to type 'integer' + ℹ The deprecated feature was likely used in the gapmap package. + Please report the issue at + . + + When sourcing ‘tcga_example.R’: + Error: Theme element `plot.margin` must have class . Execution halted - ‘analyze_hype_ts.Rmd’ using ‘UTF-8’... OK - ‘basin_characteristics.Rmd’ using ‘UTF-8’... OK - ‘basin_network.Rmd’ using ‘UTF-8’... OK - ‘import_files.Rmd’ using ‘UTF-8’... OK - ‘modify_par.Rmd’ using ‘UTF-8’... OK - ‘plot_map_statistics.Rmd’ using ‘UTF-8’... failed + ‘simple_example.Rmd’ using ‘UTF-8’... failed + ‘tcga_example.Rmd’ using ‘UTF-8’... failed ``` * checking re-building of vignette outputs ... NOTE ``` Error(s) in re-building vignettes: - --- re-building ‘analyze_hype_ts.Rmd’ using rmarkdown + ... + --- re-building ‘simple_example.Rmd’ using rmarkdown + + Quitting from lines 36-38 [unnamed-chunk-3] (simple_example.Rmd) + Error: processing vignette 'simple_example.Rmd' failed with diagnostics: + Theme element `plot.margin` must have class . + --- failed re-building ‘simple_example.Rmd’ + + --- re-building ‘tcga_example.Rmd’ using rmarkdown + ... + Quitting from lines 43-45 [unnamed-chunk-3] (tcga_example.Rmd) + Error: processing vignette 'tcga_example.Rmd' failed with diagnostics: + Theme element `plot.margin` must have class . + --- failed re-building ‘tcga_example.Rmd’ + + SUMMARY: processing the following files failed: + ‘simple_example.Rmd’ ‘tcga_example.Rmd’ + + Error: Vignette re-building failed. + Execution halted ``` -# ImFoR +# gasper
-* Version: 0.1.0 -* GitHub: NA -* Source code: https://github.com/cran/ImFoR -* Date/Publication: 2023-09-21 18:50:02 UTC -* Number of recursive dependencies: 173 +* Version: 1.1.6 +* GitHub: https://github.com/fabnavarro/gasper +* Source code: https://github.com/cran/gasper +* Date/Publication: 2024-02-28 11:10:02 UTC +* Number of recursive dependencies: 68 -Run `revdepcheck::cloud_details(, "ImFoR")` for more info +Run `revdepcheck::cloud_details(, "gasper")` for more info
## Newly broken -* checking whether package ‘ImFoR’ can be installed ... WARNING +* checking examples ... ERROR ``` - Found the following significant warnings: - Warning: replacing previous import ‘ggplot2::ggpar’ by ‘ggpubr::ggpar’ when loading ‘ImFoR’ - See ‘/tmp/workdir/ImFoR/new/ImFoR.Rcheck/00install.out’ for details. + Running examples in ‘gasper-Ex.R’ failed + The error most likely occurred in: + + > ### Name: plot_signal + > ### Title: Plot a Signal on Top of a Given Graph + > ### Aliases: plot_signal + > + > ### ** Examples + > + > f <- rnorm(length(grid1$xy[,1])) + ... + ▆ + 1. └─gasper::plot_signal(grid1, f) + 2. ├─base::print(p2) + 3. └─ggplot2:::print.ggplot(p2) + 4. ├─ggplot2::ggplot_gtable(data) + 5. └─ggplot2:::ggplot_gtable.ggplot_built(data) + 6. └─ggplot2::calc_element("plot.margin", theme) + 7. └─cli::cli_abort(...) + 8. └─rlang::abort(...) + Execution halted ``` -# iNEXT.4steps - -
- -* Version: 1.0.0 -* GitHub: https://github.com/KaiHsiangHu/iNEXT.4steps -* Source code: https://github.com/cran/iNEXT.4steps -* Date/Publication: 2024-04-10 20:00:05 UTC -* Number of recursive dependencies: 107 - -Run `revdepcheck::cloud_details(, "iNEXT.4steps")` for more info - -
+* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘gasper_vignette.rmd’ + ... + + > f <- rnorm(nrow(grid1$sA)) + + > plot_graph(grid1) + + > plot_signal(grid1, f, size = 2) + + When sourcing ‘gasper_vignette.R’: + Error: Theme element `plot.margin` must have class . + Execution halted + + ‘gasper_vignette.rmd’ using ‘UTF-8’... failed + ``` -## Newly broken +## In both -* checking whether package ‘iNEXT.4steps’ can be installed ... WARNING +* checking re-building of vignette outputs ... NOTE ``` - Found the following significant warnings: - Warning: replacing previous import ‘ggplot2::ggpar’ by ‘ggpubr::ggpar’ when loading ‘iNEXT.4steps’ - See ‘/tmp/workdir/iNEXT.4steps/new/iNEXT.4steps.Rcheck/00install.out’ for details. + Error(s) in re-building vignettes: + ... + --- re-building ‘gasper_vignette.rmd’ using rmarkdown + + Quitting from lines 173-176 [unnamed-chunk-17] (gasper_vignette.rmd) + Error: processing vignette 'gasper_vignette.rmd' failed with diagnostics: + Theme element `plot.margin` must have class . + --- failed re-building ‘gasper_vignette.rmd’ + + SUMMARY: processing the following file failed: + ‘gasper_vignette.rmd’ + + Error: Vignette re-building failed. + Execution halted ``` -# insane +# gaussplotR
-* Version: 1.0.3 -* GitHub: https://github.com/mcanouil/insane -* Source code: https://github.com/cran/insane -* Date/Publication: 2023-11-14 21:50:02 UTC -* Number of recursive dependencies: 127 +* Version: 0.2.5 +* GitHub: https://github.com/vbaliga/gaussplotR +* Source code: https://github.com/cran/gaussplotR +* Date/Publication: 2021-05-02 20:10:02 UTC +* Number of recursive dependencies: 91 -Run `revdepcheck::cloud_details(, "insane")` for more info +Run `revdepcheck::cloud_details(, "gaussplotR")` for more info
## Newly broken -* checking whether package ‘insane’ can be installed ... WARNING +* checking running R code from vignettes ... ERROR ``` - Found the following significant warnings: - Warning: replacing previous import ‘ggplot2::ggpar’ by ‘ggpubr::ggpar’ when loading ‘insane’ - See ‘/tmp/workdir/insane/new/insane.Rcheck/00install.out’ for details. + Errors in running code in vignettes: + when running code in ‘fit_gaussian_2D.Rmd’ + ... + + by = 0.1), Y_values = seq(from = -1, to = 4, by = 0.1)) + + > gauss_data_ue <- predict_gaussian_2D(fit_object = gauss_fit_ue, + + X_values = grid$X_values, Y_values = grid$Y_values, ) + + > ggplot_gaussian_2D(gauss_data_ue) + + When sourcing ‘fit_gaussian_2D.R’: + Error: Theme element `plot.margin` must have class . + Execution halted + + ‘fit_gaussian_2D.Rmd’ using ‘UTF-8’... failed + ‘formulas-used-by-fit-gaussian-2D.Rmd’ using ‘UTF-8’... OK + ‘troubleshooting-model-fits.Rmd’ using ‘UTF-8’... OK ``` -# inTextSummaryTable +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘fit_gaussian_2D.Rmd’ using rmarkdown + ``` + +# gg.gap
-* Version: 3.3.2 -* GitHub: https://github.com/openanalytics/inTextSummaryTable -* Source code: https://github.com/cran/inTextSummaryTable -* Date/Publication: 2024-03-09 16:20:02 UTC -* Number of recursive dependencies: 120 +* Version: 1.3 +* GitHub: https://github.com/ChrisLou-bioinfo/gg.gap +* Source code: https://github.com/cran/gg.gap +* Date/Publication: 2019-09-30 16:10:02 UTC +* Number of recursive dependencies: 29 -Run `revdepcheck::cloud_details(, "inTextSummaryTable")` for more info +Run `revdepcheck::cloud_details(, "gg.gap")` for more info
## Newly broken -* checking tests ... ERROR +* checking examples ... ERROR ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. + Running examples in ‘gg.gap-Ex.R’ failed + The error most likely occurred in: + + > ### Name: add.legend + > ### Title: Add Legend to gg.gap() + > ### Aliases: add.legend + > + > ### ** Examples + > + > library(ggplot2) + ... + Backtrace: + ▆ + 1. ├─base (local) ``(x) + 2. └─ggplot2:::print.ggplot(x) + 3. ├─ggplot2::ggplot_gtable(data) + 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) + 5. └─ggplot2::calc_element("plot.margin", theme) + 6. └─cli::cli_abort(...) + 7. └─rlang::abort(...) + Execution halted + ``` + +## In both + +* checking LazyData ... NOTE + ``` + 'LazyData' is specified without a 'data' directory + ``` + +# ggalignment + +
+ +* Version: 1.0.1 +* GitHub: NA +* Source code: https://github.com/cran/ggalignment +* Date/Publication: 2022-11-04 10:20:02 UTC +* Number of recursive dependencies: 83 + +Run `revdepcheck::cloud_details(, "ggalignment")` for more info + +
+ +## Newly broken + +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. Complete output: > library(testthat) - > library(inTextSummaryTable) + > library(ggalignment) > - > test_check("inTextSummaryTable") - [ FAIL 59 | WARN 1 | SKIP 0 | PASS 881 ] + > test_check("ggalignment") + [ FAIL 1 | WARN 0 | SKIP 0 | PASS 8 ] ══ Failed tests ════════════════════════════════════════════════════════════════ ... - 5. │ └─rlang::eval_bare(quo_get_expr(.quo), quo_get_env(.quo)) - 6. └─inTextSummaryTable::subjectProfileSummaryPlot(...) - 7. ├─base::do.call(plyr::rbind.fill, ggplot_build(gg)$data) - 8. └─plyr (local) ``(``, ``) - 9. └─plyr:::output_template(dfs, nrows) - 10. └─plyr:::allocate_column(df[[var]], nrows, dfs, var) + 6. └─ggplot2:::print.ggplot(p) + 7. ├─ggplot2::ggplot_gtable(data) + 8. └─ggplot2:::ggplot_gtable.ggplot_built(data) + 9. └─ggplot2::calc_element("plot.margin", theme) + 10. └─cli::cli_abort(...) + 11. └─rlang::abort(...) - [ FAIL 59 | WARN 1 | SKIP 0 | PASS 881 ] + [ FAIL 1 | WARN 0 | SKIP 0 | PASS 8 ] Error: Test failures Execution halted ``` +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘ggalignment.Rmd’ + ... + + intersect, setdiff, setequal, union + + + > ggalignment(alignment = data.frame(img = character(), + + alignment = character()), font_size = 3) + + When sourcing ‘ggalignment.R’: + Error: Theme element `plot.margin` must have class . + Execution halted + + ‘ggalignment.Rmd’ using ‘UTF-8’... failed + ``` + * checking re-building of vignette outputs ... NOTE ``` Error(s) in re-building vignettes: - --- re-building ‘inTextSummaryTable-advanced.Rmd’ using rmarkdown - --- finished re-building ‘inTextSummaryTable-advanced.Rmd’ - - --- re-building ‘inTextSummaryTable-aesthetics.Rmd’ using rmarkdown + ... + --- re-building ‘ggalignment.Rmd’ using rmarkdown - Quitting from lines at lines 211-224 [aesthetics-defaultsVisualization] (inTextSummaryTable-aesthetics.Rmd) - Error: processing vignette 'inTextSummaryTable-aesthetics.Rmd' failed with diagnostics: - Problem while setting up geom aesthetics. - ℹ Error occurred in the 2nd layer. - ... - ! Aesthetics must be either length 1 or the same as the data (28). - ✖ Fix the following mappings: `size`. - --- failed re-building ‘inTextSummaryTable-visualization.Rmd’ + Quitting from lines 27-33 [example-alignment-plot] (ggalignment.Rmd) + Error: processing vignette 'ggalignment.Rmd' failed with diagnostics: + Theme element `plot.margin` must have class . + --- failed re-building ‘ggalignment.Rmd’ - SUMMARY: processing the following files failed: - ‘inTextSummaryTable-aesthetics.Rmd’ - ‘inTextSummaryTable-visualization.Rmd’ + SUMMARY: processing the following file failed: + ‘ggalignment.Rmd’ Error: Vignette re-building failed. Execution halted ``` +# ggalt + +
+ +* Version: 0.4.0 +* GitHub: https://github.com/hrbrmstr/ggalt +* Source code: https://github.com/cran/ggalt +* Date/Publication: 2017-02-15 18:16:00 +* Number of recursive dependencies: 95 + +Run `revdepcheck::cloud_details(, "ggalt")` for more info + +
+ +## Newly broken + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘ggalt_examples.Rmd’ using rmarkdown + ``` + ## In both * checking running R code from vignettes ... ERROR ``` Errors in running code in vignettes: - when running code in ‘inTextSummaryTable-aesthetics.Rmd’ + when running code in ‘ggalt_examples.Rmd’ ... - > subjectProfileSummaryPlot(data = summaryTable, xVar = "visit", - + colorVar = "TRT") + Warning in grid.Call.graphics(C_text, as.graphicsAnnot(x$label), x$x, x$y, : + font family 'StateFace' not found in PostScript font database + Warning in grid.Call.graphics(C_text, as.graphicsAnnot(x$label), x$x, x$y, : + font family 'StateFace' not found in PostScript font database + Warning in grid.Call.graphics(C_text, as.graphicsAnnot(x$label), x$x, x$y, : + font family 'StateFace' not found in PostScript font database - When sourcing ‘inTextSummaryTable-aesthetics.R’: - Error: Problem while setting up geom aesthetics. - ℹ Error occurred in the 2nd layer. - Caused by error in `check_aesthetics()`: - ... - ✖ Fix the following mappings: `size`. + When sourcing ‘ggalt_examples.R’: + Error: invalid font type Execution halted - ‘inTextSummaryTable-advanced.Rmd’ using ‘UTF-8’... OK - ‘inTextSummaryTable-aesthetics.Rmd’ using ‘UTF-8’... failed - ‘inTextSummaryTable-createTables.Rmd’ using ‘UTF-8’... OK - ‘inTextSummaryTable-exportTables.Rmd’ using ‘UTF-8’... OK - ‘inTextSummaryTable-introduction.Rmd’ using ‘UTF-8’... OK - ‘inTextSummaryTable-standardTables.Rmd’ using ‘UTF-8’... OK - ‘inTextSummaryTable-visualization.Rmd’ using ‘UTF-8’... failed + ‘ggalt_examples.Rmd’ using ‘UTF-8’... failed ``` -* checking installed package size ... NOTE +* checking dependencies in R code ... NOTE ``` - installed size is 10.9Mb - sub-directories of 1Mb or more: - doc 9.9Mb + Namespace in Imports field not imported from: ‘plotly’ + All declared Imports should be used. ``` -# inventorize +* checking LazyData ... NOTE + ``` + 'LazyData' is specified without a 'data' directory + ``` + +# gganimate
-* Version: 1.1.1 -* GitHub: NA -* Source code: https://github.com/cran/inventorize -* Date/Publication: 2022-05-31 22:20:09 UTC -* Number of recursive dependencies: 71 +* Version: 1.0.9 +* GitHub: https://github.com/thomasp85/gganimate +* Source code: https://github.com/cran/gganimate +* Date/Publication: 2024-02-27 14:00:03 UTC +* Number of recursive dependencies: 97 -Run `revdepcheck::cloud_details(, "inventorize")` for more info +Run `revdepcheck::cloud_details(, "gganimate")` for more info
## Newly broken -* checking whether package ‘inventorize’ can be installed ... ERROR +* checking tests ... ERROR ``` - Installation failed. - See ‘/tmp/workdir/inventorize/new/inventorize.Rcheck/00install.out’ for details. + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(gganimate) + Loading required package: ggplot2 + > + > test_check("gganimate") + [ FAIL 1 | WARN 3 | SKIP 1 | PASS 5 ] + + ... + 3. ├─gganimate::animate(p, nframes = 2) at test-anim_save.R:14:5 + 4. └─gganimate:::animate.gganim(p, nframes = 2) + 5. └─args$renderer(frames_vars$frame_source, args$fps) + 6. └─gganimate:::png_dim(frames[1]) + 7. └─cli::cli_abort("Provided file ({file}) does not exist") + 8. └─rlang::abort(...) + + [ FAIL 1 | WARN 3 | SKIP 1 | PASS 5 ] + Error: Test failures + Execution halted ``` -## Installation - -### Devel - -``` -* installing *source* package ‘inventorize’ ... -** package ‘inventorize’ successfully unpacked and MD5 sums checked -** using staged installation -** R -** byte-compile and prepare package for lazy loading -Error in compute_geom_2(..., self = self) : - argument "theme" is missing, with no default -Error: unable to load R code in package ‘inventorize’ -Execution halted -ERROR: lazy loading failed for package ‘inventorize’ -* removing ‘/tmp/workdir/inventorize/new/inventorize.Rcheck/inventorize’ - - -``` -### CRAN - -``` -* installing *source* package ‘inventorize’ ... -** package ‘inventorize’ successfully unpacked and MD5 sums checked -** using staged installation -** R -** byte-compile and prepare package for lazy loading -Warning in qgamma(service_level, alpha, beta) : NaNs produced -Warning in qgamma(service_level, alpha, beta) : NaNs produced -** help -*** installing help indices -** building package indices -** testing if installed package can be loaded from temporary location -** testing if installed package can be loaded from final location -** testing if installed package keeps a record of temporary installation path -* DONE (inventorize) +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘gganimate.Rmd’ + ... + Theme element `panel.grid.major.y` is missing + Theme element `panel.grid.major.x` is missing + Warning: Failed to plot frame + Caused by error in `UseMethod()`: + ! no applicable method for 'element_grob' applied to an object of class "NULL" + + When sourcing ‘gganimate.R’: + Error: Provided file (/tmp/RtmpEoDH6s/16eb8d7241d/gganim_plot0001.png) does not + exist + Execution halted + + ‘gganimate.Rmd’ using ‘UTF-8’... failed + ``` +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘gganimate.Rmd’ using rmarkdown + ``` -``` -# itsdm +# ggbrace
-* Version: 0.2.1 -* GitHub: https://github.com/LLeiSong/itsdm -* Source code: https://github.com/cran/itsdm -* Date/Publication: 2023-06-11 00:00:02 UTC -* Number of recursive dependencies: 83 +* Version: 0.1.1 +* GitHub: NA +* Source code: https://github.com/cran/ggbrace +* Date/Publication: 2024-02-20 20:30:02 UTC +* Number of recursive dependencies: 49 -Run `revdepcheck::cloud_details(, "itsdm")` for more info +Run `revdepcheck::cloud_details(, "ggbrace")` for more info
@@ -5956,114 +6549,117 @@ Run `revdepcheck::cloud_details(, "itsdm")` for more info * checking examples ... ERROR ``` - Running examples in ‘itsdm-Ex.R’ failed + Running examples in ‘ggbrace-Ex.R’ failed The error most likely occurred in: - > ### Name: suspicious_env_outliers - > ### Title: Function to detect suspicious outliers based on environmental - > ### variables. - > ### Aliases: suspicious_env_outliers + > ### Name: stat_brace + > ### Title: create curly braces as a layer in ggplot + > ### Aliases: stat_brace > > ### ** Examples > + > library(ggbrace) ... - row [51] - suspicious column: [bio12] - suspicious value: [380.00] - distribution: 97.143% >= 777.00 - [mean: 1058.20] - [sd: 190.90] - [norm. obs: 102] - given: - [bio1] > [24.01] (value: 24.41) - - - Error in valid.pch(x$pch) : - 'language' object cannot be coerced to type 'integer' - Calls: suspicious_env_outliers ... validGrob.grob -> validDetails -> validDetails.points -> valid.pch + Backtrace: + ▆ + 1. ├─base (local) ``(x) + 2. └─ggplot2:::print.ggplot(x) + 3. ├─ggplot2::ggplot_gtable(data) + 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) + 5. └─ggplot2::calc_element("plot.margin", theme) + 6. └─cli::cli_abort(...) + 7. └─rlang::abort(...) Execution halted ``` -# karel +# ggbrain
-* Version: 0.1.1 -* GitHub: https://github.com/mpru/karel -* Source code: https://github.com/cran/karel -* Date/Publication: 2022-03-26 21:50:02 UTC -* Number of recursive dependencies: 90 +* Version: 0.8.1 +* GitHub: https://github.com/michaelhallquist/ggbrain +* Source code: https://github.com/cran/ggbrain +* Date/Publication: 2023-03-21 18:00:05 UTC +* Number of recursive dependencies: 74 -Run `revdepcheck::cloud_details(, "karel")` for more info +Run `revdepcheck::cloud_details(, "ggbrain")` for more info
## Newly broken -* checking examples ... ERROR +* checking running R code from vignettes ... ERROR ``` - Running examples in ‘karel-Ex.R’ failed - The error most likely occurred in: + Errors in running code in vignettes: + when running code in ‘ggbrain_introduction.Rmd’ + ... + + > gg_obj <- gg_base + geom_brain(definition = "underlay", + + fill_scale = scale_fill_gradient(low = "grey8", high = "grey62"), + + show_legend .... [TRUNCATED] + + > gg_obj$render() - > ### Name: acciones - > ### Title: Acciones que Karel puede realizar - > ### Aliases: acciones avanzar girar_izquierda poner_coso juntar_coso - > ### girar_derecha darse_vuelta - > - > ### ** Examples - > ... - 20. │ └─ggplot2 (local) use_defaults(..., self = self) - 21. │ └─ggplot2:::eval_from_theme(default_aes, theme) - 22. │ ├─calc_element("geom", theme) %||% .default_geom_element - 23. │ └─ggplot2::calc_element("geom", theme) - 24. └─base::.handleSimpleError(...) - 25. └─rlang (local) h(simpleError(msg, call)) - 26. └─handlers[[1L]](cnd) - 27. └─cli::cli_abort(...) - 28. └─rlang::abort(...) + + > plot(gg_obj) + + When sourcing ‘ggbrain_labels.R’: + Error: Theme element `plot.margin` must have class . Execution halted + + ‘ggbrain_aesthetics.Rmd’ using ‘UTF-8’... OK + ‘ggbrain_introduction.Rmd’ using ‘UTF-8’... failed + ‘ggbrain_labels.Rmd’ using ‘UTF-8’... failed ``` -* checking tests ... ERROR +* checking re-building of vignette outputs ... NOTE ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(karel) - > - > test_check("karel") - [ FAIL 2 | WARN 2 | SKIP 0 | PASS 78 ] - - ══ Failed tests ════════════════════════════════════════════════════════════════ + Error(s) in re-building vignettes: + ... + --- re-building ‘ggbrain_aesthetics.Rmd’ using rmarkdown + --- finished re-building ‘ggbrain_aesthetics.Rmd’ + + --- re-building ‘ggbrain_introduction.Rmd’ using rmarkdown + + Quitting from lines 238-239 [unnamed-chunk-16] (ggbrain_introduction.Rmd) + Error: processing vignette 'ggbrain_introduction.Rmd' failed with diagnostics: + Theme element `plot.margin` must have class . ... - 24. │ └─ggplot2::calc_element("geom", theme) - 25. └─base::.handleSimpleError(...) - 26. └─rlang (local) h(simpleError(msg, call)) - 27. └─handlers[[1L]](cnd) - 28. └─cli::cli_abort(...) - 29. └─rlang::abort(...) - - [ FAIL 2 | WARN 2 | SKIP 0 | PASS 78 ] - Error: Test failures - Execution halted + Quitting from lines 47-54 [unnamed-chunk-2] (ggbrain_labels.Rmd) + Error: processing vignette 'ggbrain_labels.Rmd' failed with diagnostics: + Theme element `plot.margin` must have class . + --- failed re-building ‘ggbrain_labels.Rmd’ + + SUMMARY: processing the following files failed: + ‘ggbrain_introduction.Rmd’ ‘ggbrain_labels.Rmd’ + + Error: Vignette re-building failed. + Execution halted ``` ## In both -* checking dependencies in R code ... NOTE +* checking installed package size ... NOTE ``` - Namespace in Imports field not imported from: ‘gifski’ - All declared Imports should be used. + installed size is 10.5Mb + sub-directories of 1Mb or more: + doc 3.0Mb + extdata 1.6Mb + libs 5.2Mb ``` -# latentcor +# ggbreak
-* Version: 2.0.1 -* GitHub: NA -* Source code: https://github.com/cran/latentcor -* Date/Publication: 2022-09-05 20:50:02 UTC -* Number of recursive dependencies: 143 +* Version: 0.1.2 +* GitHub: https://github.com/YuLab-SMU/ggbreak +* Source code: https://github.com/cran/ggbreak +* Date/Publication: 2023-06-26 05:40:02 UTC +* Number of recursive dependencies: 64 -Run `revdepcheck::cloud_details(, "latentcor")` for more info +Run `revdepcheck::cloud_details(, "ggbreak")` for more info
@@ -6071,49 +6667,61 @@ Run `revdepcheck::cloud_details(, "latentcor")` for more info * checking examples ... ERROR ``` - Running examples in ‘latentcor-Ex.R’ failed + Running examples in ‘ggbreak-Ex.R’ failed The error most likely occurred in: - > ### Name: latentcor - > ### Title: Estimate latent correlation for mixed types. - > ### Aliases: latentcor + > ### Name: scale_wrap + > ### Title: scale-wrap + > ### Aliases: scale_wrap > > ### ** Examples > - > # Example 1 - truncated data type, same type for all variables - ... - > proc.time() - start_time - user system elapsed - 0.036 0.000 0.036 - > # Heatmap for latent correlation matrix. - > Heatmap_R_approx = latentcor(X = X, types = "tru", method = "approx", - + showplot = TRUE)$plotR - Error in compute_geom_2(..., self = self) : - argument "theme" is missing, with no default - Calls: latentcor ... use_defaults -> eval_from_theme -> %||% -> calc_element + > library(ggplot2) + > library(ggbreak) + > p <- ggplot(economics, aes(x=date, y = unemploy, colour = uempmed)) + + + geom_line() + > p + scale_wrap(n=4) + Error in identicalUnits(x) : object is not a unit + Calls: -> print.ggwrap Execution halted ``` -## In both +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘ggbreak.Rmd’ + ... + + > print(pg) + + > pg <- pg + aes(fill = group) + theme(legend.position = "bottom") + + > print(pg) + + When sourcing ‘ggbreak.R’: + Error: object is not a unit + Execution halted + + ‘ggbreak.Rmd’ using ‘UTF-8’... failed + ``` -* checking installed package size ... NOTE +* checking re-building of vignette outputs ... NOTE ``` - installed size is 7.3Mb - sub-directories of 1Mb or more: - R 6.9Mb + Error(s) in re-building vignettes: + --- re-building ‘ggbreak.Rmd’ using rmarkdown ``` -# mapSpain +# ggdark
-* Version: 0.9.0 -* GitHub: https://github.com/rOpenSpain/mapSpain -* Source code: https://github.com/cran/mapSpain -* Date/Publication: 2024-01-23 20:50:02 UTC -* Number of recursive dependencies: 101 +* Version: 0.2.1 +* GitHub: NA +* Source code: https://github.com/cran/ggdark +* Date/Publication: 2019-01-11 17:30:06 UTC +* Number of recursive dependencies: 46 -Run `revdepcheck::cloud_details(, "mapSpain")` for more info +Run `revdepcheck::cloud_details(, "ggdark")` for more info
@@ -6121,79 +6729,9004 @@ Run `revdepcheck::cloud_details(, "mapSpain")` for more info * checking examples ... ERROR ``` - Running examples in ‘mapSpain-Ex.R’ failed + Running examples in ‘ggdark-Ex.R’ failed The error most likely occurred in: - > ### Name: esp_munic.sf - > ### Title: All Municipalities 'POLYGON' object of Spain (2019) - > ### Aliases: esp_munic.sf + > ### Name: dark_mode + > ### Title: Activate dark mode on a 'ggplot2' theme + > ### Aliases: dark_mode > > ### ** Examples > - > data("esp_munic.sf") + > library(ggplot2) ... - 15. └─ggplot2 (local) FUN(X[[i]], ...) - 16. └─base::lapply(...) - 17. └─ggplot2 (local) FUN(X[[i]], ...) - 18. └─g$draw_key(data, g$params, key_size) - 19. └─ggplot2 (local) draw_key(...) - 20. └─ggplot2::draw_key_polygon(data, params, size) - 21. └─rlang:::Summary.quosure(from_theme(thin), 1.524, na.rm = FALSE) - 22. └─rlang:::abort_quosure_op("Summary", .Generic) - 23. └─rlang::abort(...) + > + > p1 <- ggplot(iris, aes(Sepal.Width, Sepal.Length, color = Species)) + + + geom_point() + > + > p1 # theme returned by theme_get() + > p1 + dark_mode() # activate dark mode on theme returned by theme_get() + Error in match(x, table, nomatch = 0L) : + 'match' requires vector arguments + Calls: dark_mode -> %in% Execution halted ``` -## In both - * checking tests ... ERROR ``` Running ‘testthat.R’ Running the tests in ‘tests/testthat.R’ failed. Complete output: > library(testthat) - > library(mapSpain) + > library(ggdark) > - > test_check("mapSpain") - Starting 2 test processes - [ FAIL 1 | WARN 0 | SKIP 29 | PASS 158 ] - - ... - 'test-esp_move_can.R:42:3', 'test-esp_make_provider.R:8:3', - 'test-esp_make_provider.R:31:3' + > test_check("ggdark") + [ FAIL 1 | WARN 0 | SKIP 0 | PASS 0 ] ══ Failed tests ════════════════════════════════════════════════════════════════ - ── Failure ('test-esp_get_nuts.R:50:3'): Test local NUTS ─────────────────────── - `esp_get_nuts(resolution = "20")` produced warnings. + ... + ── Error ('test_dark_mode.R:10:1'): (code run outside of `test_that()`) ──────── + Error in `match(x, table, nomatch = 0L)`: 'match' requires vector arguments + Backtrace: + ▆ + 1. └─ggdark::dark_mode(light_theme) at test_dark_mode.R:10:1 + 2. └─geoms[["GeomPoint"]]$default_aes$colour %in% ... - [ FAIL 1 | WARN 0 | SKIP 29 | PASS 158 ] + [ FAIL 1 | WARN 0 | SKIP 0 | PASS 0 ] + Error: Test failures + Execution halted + ``` + +## In both + +* checking LazyData ... NOTE + ``` + 'LazyData' is specified without a 'data' directory + ``` + +# ggdist + +
+ +* Version: 3.3.2 +* GitHub: https://github.com/mjskay/ggdist +* Source code: https://github.com/cran/ggdist +* Date/Publication: 2024-03-05 05:30:23 UTC +* Number of recursive dependencies: 126 + +Run `revdepcheck::cloud_details(, "ggdist")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘ggdist-Ex.R’ failed + The error most likely occurred in: + + > ### Name: Pr_ + > ### Title: Probability expressions in ggdist aesthetics + > ### Aliases: Pr_ p_ + > + > ### ** Examples + > + > library(ggplot2) + ... + + ) + > + > # map density onto alpha of the fill + > ggplot(df, aes(y = name, xdist = d)) + + + stat_slabinterval(aes(alpha = !!p_(x))) + Error in use_defaults(..., self = self) : + unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, "black", TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), NULL, list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), 5.5, c(5.5, 5.5, 5.5, 5.5), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.75, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, + NULL, NULL, NULL, 1, 90, NULL, c(0, 2.75, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 1, NULL, NULL, NULL, c(0, 2.2, 0, 0), NULL, TRUE), NULL, l + Calls: ... -> -> compute_geom_2 -> + Execution halted + ``` + +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > # This file is part of the standard setup for testthat. + > # It is recommended that you do not modify it. + > # + > # Where should you do additional test configuration? + > # Learn more about the roles of various files in: + > # * https://r-pkgs.org/testing-design.html#sec-tests-files-overview + > # * https://testthat.r-lib.org/articles/special-files.html + ... + • test.stat_sample_slabinterval/nas-with-na-rm-true.svg + • test.subguide/dots-subguide-with-side-vertical.svg + • test.subguide/integer-subguide-with-zero-range.svg + • test.subguide/slab-subguide-with-inside-labels-vertical.svg + • test.subguide/slab-subguide-with-outside-labels-vert.svg + • test.subguide/slab-subguide-with-outside-labels.svg + • test.subguide/slab-subguide-with-side-vertical.svg + • test.theme_ggdist/facet-titles-on-left.svg Error: Test failures Execution halted ``` -* checking installed package size ... NOTE +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘dotsinterval.Rmd’ using rmarkdown + Warning in hook_png(..., cmd = "pngquant", post_process = function(x) { : + cannot find pngquant; please install and put it in PATH + Warning in hook_png(..., cmd = "pngquant", post_process = function(x) { : + cannot find pngquant; please install and put it in PATH + + Quitting from lines 49-161 [dotsinterval_components] (dotsinterval.Rmd) + Error: processing vignette 'dotsinterval.Rmd' failed with diagnostics: + Problem while setting up geom aesthetics. + ... + + --- re-building ‘freq-uncertainty-vis.Rmd’ using rmarkdown + Warning in hook_png(..., cmd = "pngquant", post_process = function(x) { : + cannot find pngquant; please install and put it in PATH + Warning in hook_png(..., cmd = "pngquant", post_process = function(x) { : + cannot find pngquant; please install and put it in PATH + Warning in hook_png(..., cmd = "pngquant", post_process = function(x) { : + cannot find pngquant; please install and put it in PATH + Warning in hook_png(..., cmd = "pngquant", post_process = function(x) { : + cannot find pngquant; please install and put it in PATH + ``` + +## In both + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘dotsinterval.Rmd’ + ... + + xdist = dist)) + geom_hline(yintercept = 0:1, color = "gray95") + + + stat_dotsin .... [TRUNCATED] + + When sourcing ‘dotsinterval.R’: + Error: Problem while setting up geom aesthetics. + ℹ Error occurred in the 2nd layer. + Caused by error in `use_defaults()`: + ... + ℹ Error occurred in the 1st layer. + Caused by error in `use_defaults()`: + ! unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, "black", TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), NULL, list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), 5.5, c(5.5, 5.5, 5.5, 5.5), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(7, 0, 0, 0), NULL, FALSE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, + NULL, NULL, 1, 90, NULL, c(0, 7, 0, 0), NULL, FALSE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2 + Execution halted + + ‘dotsinterval.Rmd’ using ‘UTF-8’... failed + ‘freq-uncertainty-vis.Rmd’ using ‘UTF-8’... failed + ‘lineribbon.Rmd’ using ‘UTF-8’... failed + ‘slabinterval.Rmd’ using ‘UTF-8’... failed + ``` + +* checking installed package size ... NOTE + ``` + installed size is 5.4Mb + sub-directories of 1Mb or more: + R 1.5Mb + doc 1.3Mb + help 1.5Mb + ``` + +# ggedit + +
+ +* Version: 0.4.1 +* GitHub: https://github.com/yonicd/ggedit +* Source code: https://github.com/cran/ggedit +* Date/Publication: 2024-03-04 14:40:02 UTC +* Number of recursive dependencies: 95 + +Run `revdepcheck::cloud_details(, "ggedit")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘ggedit-Ex.R’ failed + The error most likely occurred in: + + > ### Name: dput.ggedit + > ### Title: Convert ggplot object to a string call + > ### Aliases: dput.ggedit + > + > ### ** Examples + > + > + > pList$pointSmooth #original compiled plot + `geom_smooth()` using formula = 'y ~ x' + Error in compute_geom_2(..., self = self) : + unused arguments (list(6), list(list("black", 0.5, 1, "butt", FALSE, "black", TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), NULL, list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), 5.5, c(5.5, 5.5, 5.5, 5.5), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.75, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, + NULL, NULL, NULL, 1, 90, NULL, c(0, 2.75, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 1, NULL, NULL, NULL, c(0, 2.2, 0, 0), NULL, TRUE), NULL, + Calls: ... get_layer_key -> Map -> mapply -> -> + Execution halted + ``` + +# ggExtra + +
+ +* Version: 0.10.1 +* GitHub: https://github.com/daattali/ggExtra +* Source code: https://github.com/cran/ggExtra +* Date/Publication: 2023-08-21 14:40:02 UTC +* Number of recursive dependencies: 118 + +Run `revdepcheck::cloud_details(, "ggExtra")` for more info + +
+ +## Newly broken + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘ggExtra.Rmd’ + ... + + > p1 <- ggplot(df1, aes(x, y)) + geom_point() + theme_bw() + + > p1 + + > ggMarginal(p1) + + When sourcing ‘ggExtra.R’: + Error: Theme element `plot.margin` must have class . + Execution halted + + ‘ggExtra.Rmd’... failed + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘ggExtra.Rmd’ using rmarkdown + ``` + +## In both + +* checking dependencies in R code ... NOTE + ``` + Namespaces in Imports field not imported from: + ‘R6’ ‘scales’ ‘utils’ + All declared Imports should be used. + ``` + +# ggfixest + +
+ +* Version: 0.1.0 +* GitHub: https://github.com/grantmcdermott/ggfixest +* Source code: https://github.com/cran/ggfixest +* Date/Publication: 2023-12-14 08:00:06 UTC +* Number of recursive dependencies: 78 + +Run `revdepcheck::cloud_details(, "ggfixest")` for more info + +
+ +## Newly broken + +* checking tests ... ERROR + ``` + Running ‘tinytest.R’ + Running the tests in ‘tests/tinytest.R’ failed. + Complete output: + > ## Throttle CPU threads if R CMD check (for CRAN) + > + > if (any(grepl("_R_CHECK", names(Sys.getenv()), fixed = TRUE))) { + + # fixest + + if (requireNamespace("fixest", quietly = TRUE)) { + + library(fixest) + + setFixest_nthreads(1) + ... + test_nthreads.R............... 0 tests ----- FAILED[]: test_ggiplot.R<52--52> + call| expect_snapshot_plot(p3, label = "ggiplot_simple_ribbon") + diff| 54503 + info| Diff plot saved to: _tinysnapshot_review/ggiplot_simple_ribbon.png + ----- FAILED[]: test_ggiplot.R<54--54> + call| expect_snapshot_plot(p5, label = "ggiplot_simple_mci_ribbon") + diff| 54400 + info| Diff plot saved to: _tinysnapshot_review/ggiplot_simple_mci_ribbon.png + Error: 2 out of 101 tests failed + Execution halted + ``` + +## In both + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘ggiplot.Rmd’ + ... + > iplot(list(TWFE = est_twfe_grp, `Sun & Abraham (2020)` = est_sa20_grp), + + ref.line = -1, main = "Staggered treatment: Split mutli-sample") + The degrees of freedom for the t distribution could not be deduced. Using a Normal distribution instead. + Note that you can provide the argument `df.t` directly. + + When sourcing ‘ggiplot.R’: + Error: in iplot(list(TWFE = est_twfe_grp, `Sun & Abraham (2...: + The 1st element of 'object' raises and error: + Error in nb * sd : non-numeric argument to binary operator + Execution halted + + ‘ggiplot.Rmd’ using ‘UTF-8’... failed + ``` + +# ggflowchart + +
+ +* Version: 1.0.0 +* GitHub: NA +* Source code: https://github.com/cran/ggflowchart +* Date/Publication: 2023-05-11 10:10:05 UTC +* Number of recursive dependencies: 59 + +Run `revdepcheck::cloud_details(, "ggflowchart")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘ggflowchart-Ex.R’ failed + The error most likely occurred in: + + > ### Name: ggflowchart + > ### Title: Generate a flowchart in ggplot2 + > ### Aliases: ggflowchart + > + > ### ** Examples + > + > data <- tibble::tibble(from = c("A", "A", "A", "B", "C", "F"), to = c("B", "C", "D", "E", "F", "G")) + ... + Backtrace: + ▆ + 1. ├─base (local) ``(x) + 2. └─ggplot2:::print.ggplot(x) + 3. ├─ggplot2::ggplot_gtable(data) + 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) + 5. └─ggplot2::calc_element("plot.margin", theme) + 6. └─cli::cli_abort(...) + 7. └─rlang::abort(...) + Execution halted + ``` + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘decision-tree-example.Rmd’ + ... + + > node_data <- tibble::tibble(name = c("Goldilocks", + + "Porridge", "Just right", "Chairs", "Just right2", "Beds", + + "Just right3", "Too cold ..." ... [TRUNCATED] + + > ggflowchart(goldilocks, node_data) + + ... + + "C", "F"), to = c("B", "C", "D", "E", "F", "G")) + + > ggflowchart(data) + + When sourcing ‘minimal-example.R’: + Error: Theme element `plot.margin` must have class . + Execution halted + + ‘decision-tree-example.Rmd’ using ‘UTF-8’... failed + ‘minimal-example.Rmd’ using ‘UTF-8’... failed + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + ... + --- re-building ‘decision-tree-example.Rmd’ using rmarkdown + + Quitting from lines 64-65 [flowchart] (decision-tree-example.Rmd) + Error: processing vignette 'decision-tree-example.Rmd' failed with diagnostics: + Theme element `plot.margin` must have class . + --- failed re-building ‘decision-tree-example.Rmd’ + + --- re-building ‘minimal-example.Rmd’ using rmarkdown + ... + Quitting from lines 31-32 [flowchart] (minimal-example.Rmd) + Error: processing vignette 'minimal-example.Rmd' failed with diagnostics: + Theme element `plot.margin` must have class . + --- failed re-building ‘minimal-example.Rmd’ + + SUMMARY: processing the following files failed: + ‘decision-tree-example.Rmd’ ‘minimal-example.Rmd’ + + Error: Vignette re-building failed. + Execution halted + ``` + +# ggforce + +
+ +* Version: 0.4.2 +* GitHub: https://github.com/thomasp85/ggforce +* Source code: https://github.com/cran/ggforce +* Date/Publication: 2024-02-19 11:00:02 UTC +* Number of recursive dependencies: 69 + +Run `revdepcheck::cloud_details(, "ggforce")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘ggforce-Ex.R’ failed + The error most likely occurred in: + + > ### Name: facet_zoom + > ### Title: Facet data for zoom with context + > ### Aliases: facet_zoom + > + > ### ** Examples + > + > # Zoom in on the versicolor species on the x-axis + > ggplot(iris, aes(Petal.Length, Petal.Width, colour = Species)) + + + geom_point() + + + facet_zoom(x = Species == 'versicolor') + Error in upgradeUnit.default(x) : Not a unit object + Calls: ... is.unit -> convertUnit -> upgradeUnit -> upgradeUnit.default + Execution halted + ``` + +## In both + +* checking installed package size ... NOTE + ``` + installed size is 27.7Mb + sub-directories of 1Mb or more: + R 1.5Mb + help 1.2Mb + libs 24.9Mb + ``` + +# ggfortify + +
+ +* Version: 0.4.17 +* GitHub: https://github.com/sinhrks/ggfortify +* Source code: https://github.com/cran/ggfortify +* Date/Publication: 2024-04-17 04:30:04 UTC +* Number of recursive dependencies: 125 + +Run `revdepcheck::cloud_details(, "ggfortify")` for more info + +
+ +## Newly broken + +* checking tests ... ERROR + ``` + Running ‘test-all.R’ + Running the tests in ‘tests/test-all.R’ failed. + Complete output: + > library(testthat) + > + > suppressWarnings(RNGversion("3.5.0")) + > set.seed(1, sample.kind = "Rejection") + > + > test_check('ggfortify') + Loading required package: ggfortify + ... + + x[3]: "#595959FF" + y[3]: "grey35" + + x[4]: "#595959FF" + y[4]: "grey35" + + [ FAIL 5 | WARN 12 | SKIP 48 | PASS 734 ] + Error: Test failures + Execution halted + ``` + +# ggfoundry + +
+ +* Version: 0.1.1 +* GitHub: https://github.com/cgoo4/ggfoundry +* Source code: https://github.com/cran/ggfoundry +* Date/Publication: 2024-05-28 11:40:02 UTC +* Number of recursive dependencies: 107 + +Run `revdepcheck::cloud_details(, "ggfoundry")` for more info + +
+ +## Newly broken + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘ggfoundry.Rmd’ + ... + + > p2 <- p + geom_point(size = 4) + scale_shape_manual(values = c("▼", + + "●", "▲")) + labs(title = "geom_point with unicodes", + + subtitle = " ..." ... [TRUNCATED] + + > p1 + p2 + plot_layout(guides = "collect", axes = "collect") + + When sourcing ‘ggfoundry.R’: + Error: object is not coercible to a unit + Execution halted + + ‘ggfoundry.Rmd’ using ‘UTF-8’... failed + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + ... + --- re-building ‘ggfoundry.Rmd’ using rmarkdown + + Quitting from lines 50-94 [unicodes] (ggfoundry.Rmd) + Error: processing vignette 'ggfoundry.Rmd' failed with diagnostics: + object is not coercible to a unit + --- failed re-building ‘ggfoundry.Rmd’ + + SUMMARY: processing the following file failed: + ‘ggfoundry.Rmd’ + + Error: Vignette re-building failed. + Execution halted + ``` + +# gggap + +
+ +* Version: 1.0.1 +* GitHub: https://github.com/cmoralesmx/gggap +* Source code: https://github.com/cran/gggap +* Date/Publication: 2020-11-20 09:20:02 UTC +* Number of recursive dependencies: 29 + +Run `revdepcheck::cloud_details(, "gggap")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘gggap-Ex.R’ failed + The error most likely occurred in: + + > ### Name: gggap + > ### Title: Define Segments in y-Axis for 'ggplot2' + > ### Aliases: gggap + > + > ### ** Examples + > + > data(mtcars) + ... + Backtrace: + ▆ + 1. ├─base (local) ``(x) + 2. └─ggplot2:::print.ggplot(x) + 3. ├─ggplot2::ggplot_gtable(data) + 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) + 5. └─ggplot2::calc_element("plot.margin", theme) + 6. └─cli::cli_abort(...) + 7. └─rlang::abort(...) + Execution halted + ``` + +## In both + +* checking LazyData ... NOTE + ``` + 'LazyData' is specified without a 'data' directory + ``` + +# ggh4x + +
+ +* Version: 0.2.8 +* GitHub: https://github.com/teunbrand/ggh4x +* Source code: https://github.com/cran/ggh4x +* Date/Publication: 2024-01-23 21:00:02 UTC +* Number of recursive dependencies: 77 + +Run `revdepcheck::cloud_details(, "ggh4x")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘ggh4x-Ex.R’ failed + The error most likely occurred in: + + > ### Name: guide_dendro + > ### Title: Dendrogram guide + > ### Aliases: guide_dendro + > + > ### ** Examples + > + > clust <- hclust(dist(USArrests), "ave") + ... + 9. └─ggplot2:::scale_apply(layer_data, y_vars, "map", SCALE_Y, self$panel_scales_y) + 10. └─base::lapply(...) + 11. └─ggplot2 (local) FUN(X[[i]], ...) + 12. └─base::lapply(...) + 13. └─ggplot2 (local) FUN(X[[i]], ...) + 14. └─scales[[i]][[method]](data[[var]][scale_index[[i]]]) + 15. └─ggplot2 (local) map(..., self = self) + 16. └─cli::cli_abort(...) + 17. └─rlang::abort(...) + Execution halted + ``` + +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(ggh4x) + Loading required package: ggplot2 + > + > test_check("ggh4x") + [ FAIL 7 | WARN 20 | SKIP 18 | PASS 740 ] + + ... + 14. └─base::lapply(...) + 15. └─ggplot2 (local) FUN(X[[i]], ...) + 16. └─scales[[i]][[method]](data[[var]][scale_index[[i]]]) + 17. └─ggplot2 (local) map(..., self = self) + 18. └─cli::cli_abort(...) + 19. └─rlang::abort(...) + + [ FAIL 7 | WARN 20 | SKIP 18 | PASS 740 ] + Error: Test failures + Execution halted + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘Facets.Rmd’ using rmarkdown + ``` + +## In both + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘Miscellaneous.Rmd’ + ... + + > ggplot(diamonds, aes(price, carat, colour = clarity)) + + + geom_point(shape = ".") + scale_colour_brewer(palette = "Dark2", + + guide = "stri ..." ... [TRUNCATED] + Warning: The S3 guide system was deprecated in ggplot2 3.5.0. + ℹ It has been replaced by a ggproto system that can be extended. + + ... + ℹ Error occurred in the 1st layer. + Caused by error in `setup_params()`: + ! A discrete 'nbinom' distribution cannot be fitted to continuous data. + Execution halted + + ‘Facets.Rmd’ using ‘UTF-8’... OK + ‘Miscellaneous.Rmd’ using ‘UTF-8’... failed + ‘PositionGuides.Rmd’ using ‘UTF-8’... failed + ‘Statistics.Rmd’ using ‘UTF-8’... failed + ‘ggh4x.Rmd’ using ‘UTF-8’... OK + ``` + +# gghdx + +
+ +* Version: 0.1.3 +* GitHub: https://github.com/OCHA-DAP/gghdx +* Source code: https://github.com/cran/gghdx +* Date/Publication: 2024-05-14 19:50:02 UTC +* Number of recursive dependencies: 82 + +Run `revdepcheck::cloud_details(, "gghdx")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘gghdx-Ex.R’ failed + The error most likely occurred in: + + > ### Name: gghdx + > ### Title: Set HDX theme and aesthetics + > ### Aliases: gghdx gghdx_reset + > + > ### ** Examples + > + > + ... + Backtrace: + ▆ + 1. ├─base (local) ``(x) + 2. └─ggplot2:::print.ggplot(x) + 3. ├─ggplot2::ggplot_gtable(data) + 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) + 5. └─ggplot2::calc_element("plot.margin", theme) + 6. └─cli::cli_abort(...) + 7. └─rlang::abort(...) + Execution halted + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘gghdx.Rmd’ using rmarkdown + ``` + +## In both + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘gghdx.Rmd’ + ... + + > p + + > library(gghdx) + + > p + theme_hdx(base_family = "sans") + + When sourcing ‘gghdx.R’: + Error: Theme element `plot.margin` must have class . + Execution halted + + ‘gghdx.Rmd’ using ‘UTF-8’... failed + ``` + +# gghighlight + +
+ +* Version: 0.4.1 +* GitHub: https://github.com/yutannihilation/gghighlight +* Source code: https://github.com/cran/gghighlight +* Date/Publication: 2023-12-16 01:00:02 UTC +* Number of recursive dependencies: 85 + +Run `revdepcheck::cloud_details(, "gghighlight")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘gghighlight-Ex.R’ failed + The error most likely occurred in: + + > ### Name: gghighlight + > ### Title: Highlight Data With Predicate + > ### Aliases: gghighlight + > + > ### ** Examples + > + > d <- data.frame( + ... + 8. │ ├─purrr:::with_indexed_errors(...) + 9. │ │ └─base::withCallingHandlers(...) + 10. │ ├─purrr:::call_with_cleanup(...) + 11. │ └─gghighlight (local) .f(.x[[i]], .y[[i]], ...) + 12. │ └─gghighlight:::get_default_aes_param(nm, layer$geom, layer$mapping) + 13. └─base::.handleSimpleError(...) + 14. └─purrr (local) h(simpleError(msg, call)) + 15. └─cli::cli_abort(...) + 16. └─rlang::abort(...) + Execution halted + ``` + +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(gghighlight) + Loading required package: ggplot2 + > + > test_check("gghighlight") + label_key: type + label_key: type + ... + 15. └─cli::cli_abort(...) + 16. └─rlang::abort(...) + + [ FAIL 2 | WARN 2 | SKIP 1 | PASS 178 ] + Deleting unused snapshots: + • vdiffr/simple-bar-chart-with-facet.svg + • vdiffr/simple-line-chart.svg + • vdiffr/simple-point-chart.svg + Error: Test failures + Execution halted + ``` + +## In both + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘gghighlight.Rmd’ + ... + + 0, label_key = type) + Warning in is.na(non_null_default_aes[[aes_param_name]]) : + is.na() applied to non-(list or vector) of type 'language' + + When sourcing ‘gghighlight.R’: + Error: ℹ In index: 1. + Caused by error in `aes_param_name %in% names(non_null_default_aes) && is.na(non_null_default_aes[[ + aes_param_name]])`: + ! 'length = 2' in coercion to 'logical(1)' + Execution halted + + ‘gghighlight.Rmd’ using ‘UTF-8’... failed + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘gghighlight.Rmd’ using rmarkdown + ``` + +# ggHoriPlot + +
+ +* Version: 1.0.1 +* GitHub: https://github.com/rivasiker/ggHoriPlot +* Source code: https://github.com/cran/ggHoriPlot +* Date/Publication: 2022-10-11 16:22:33 UTC +* Number of recursive dependencies: 117 + +Run `revdepcheck::cloud_details(, "ggHoriPlot")` for more info + +
+ +## Newly broken + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘ggHoriPlot.Rmd’ + ... + > mid <- sum(range(dat_tab$y, na.rm = T))/2 + + > b <- plotAllLayers(dat_tab, mid, cutpoints$cuts, cutpoints$color) + + > b/a + plot_layout(guides = "collect", heights = c(6, + + 1)) + + When sourcing ‘ggHoriPlot.R’: + Error: object is not a unit + Execution halted + + ‘examples.Rmd’ using ‘UTF-8’... OK + ‘ggHoriPlot.Rmd’ using ‘UTF-8’... failed + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘examples.Rmd’ using rmarkdown + ``` + +# ggiraph + +
+ +* Version: 0.8.10 +* GitHub: https://github.com/davidgohel/ggiraph +* Source code: https://github.com/cran/ggiraph +* Date/Publication: 2024-05-17 12:10:02 UTC +* Number of recursive dependencies: 95 + +Run `revdepcheck::cloud_details(, "ggiraph")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘ggiraph-Ex.R’ failed + The error most likely occurred in: + + > ### Name: geom_path_interactive + > ### Title: Create interactive observations connections + > ### Aliases: geom_path_interactive geom_line_interactive + > ### geom_step_interactive + > + > ### ** Examples + > + ... + 20. │ └─base::lapply(...) + 21. │ └─ggplot2 (local) FUN(X[[i]], ...) + 22. │ ├─rlang::inject(self$draw_panel(data, panel_params, coord, !!!params)) + 23. │ └─self$draw_panel(...) + 24. └─base::.handleSimpleError(...) + 25. └─rlang (local) h(simpleError(msg, call)) + 26. └─handlers[[1L]](cnd) + 27. └─cli::cli_abort(...) + 28. └─rlang::abort(...) + Execution halted + ``` + +* checking tests ... ERROR + ``` + Running ‘tinytest.R’ + Running the tests in ‘tests/tinytest.R’ failed. + Complete output: + > if (requireNamespace("tinytest", quietly = TRUE)) { + + tinytest::test_package("ggiraph") + + } + + test-annotate_interactive.R... 0 tests + test-annotate_interactive.R... 0 tests + test-annotate_interactive.R... 0 tests + ... + 30. │ └─base::lapply(...) + 31. │ └─ggplot2 (local) FUN(X[[i]], ...) + 32. │ ├─rlang::inject(self$draw_panel(data, panel_params, coord, !!!params)) + 33. │ └─self$draw_panel(...) + 34. └─base::.handleSimpleError(...) + 35. └─rlang (local) h(simpleError(msg, call)) + 36. └─handlers[[1L]](cnd) + 37. └─cli::cli_abort(...) + 38. └─rlang::abort(...) + Execution halted + ``` + +## In both + +* checking package dependencies ... NOTE + ``` + Package suggested but not available for checking: ‘quantreg’ + ``` + +* checking installed package size ... NOTE + ``` + installed size is 9.7Mb + sub-directories of 1Mb or more: + R 1.5Mb + libs 6.9Mb + ``` + +# ggiraphExtra + +
+ +* Version: 0.3.0 +* GitHub: https://github.com/cardiomoon/ggiraphExtra +* Source code: https://github.com/cran/ggiraphExtra +* Date/Publication: 2020-10-06 07:00:02 UTC +* Number of recursive dependencies: 124 + +Run `revdepcheck::cloud_details(, "ggiraphExtra")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘ggiraphExtra-Ex.R’ failed + The error most likely occurred in: + + > ### Name: ggAncova + > ### Title: Make an interactive plot for an ANCOVA model + > ### Aliases: ggAncova ggAncova.default ggAncova.formula ggAncova.lm + > + > ### ** Examples + > + > require(moonBook) + ... + 24. │ └─base::lapply(...) + 25. │ └─ggplot2 (local) FUN(X[[i]], ...) + 26. │ ├─rlang::inject(self$draw_panel(data, panel_params, coord, !!!params)) + 27. │ └─self$draw_panel(...) + 28. └─base::.handleSimpleError(...) + 29. └─rlang (local) h(simpleError(msg, call)) + 30. └─handlers[[1L]](cnd) + 31. └─cli::cli_abort(...) + 32. └─rlang::abort(...) + Execution halted + ``` + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘introduction.Rmd’ + ... + + > ggPoints(aes(x = wt, y = mpg, color = am), data = mtcars, + + method = "lm", interactive = TRUE) + + When sourcing ‘introduction.R’: + Error: Problem while converting geom to grob. + ℹ Error occurred in the 3rd layer. + Caused by error in `draw_panel()`: + ! unused argument (arrow.fill = NULL) + Execution halted + + ‘ggPredict.Rmd’ using ‘UTF-8’... OK + ‘introduction.Rmd’ using ‘UTF-8’... failed + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘ggPredict.Rmd’ using rmarkdown + ``` + +# ggmap + +
+ +* Version: 4.0.0 +* GitHub: https://github.com/dkahle/ggmap +* Source code: https://github.com/cran/ggmap +* Date/Publication: 2023-11-19 08:10:02 UTC +* Number of recursive dependencies: 66 + +Run `revdepcheck::cloud_details(, "ggmap")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘ggmap-Ex.R’ failed + The error most likely occurred in: + + > ### Name: theme_nothing + > ### Title: Make a blank ggplot2 theme. + > ### Aliases: theme_nothing + > + > ### ** Examples + > + > + ... + Backtrace: + ▆ + 1. ├─base (local) ``(x) + 2. └─ggplot2:::print.ggplot(x) + 3. ├─ggplot2::ggplot_gtable(data) + 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) + 5. └─ggplot2::calc_element("plot.margin", theme) + 6. └─cli::cli_abort(...) + 7. └─rlang::abort(...) + Execution halted + ``` + +## In both + +* checking installed package size ... NOTE + ``` + installed size is 7.4Mb + sub-directories of 1Mb or more: + data 7.0Mb + ``` + +# ggmice + +
+ +* Version: 0.1.0 +* GitHub: https://github.com/amices/ggmice +* Source code: https://github.com/cran/ggmice +* Date/Publication: 2023-08-07 14:20:02 UTC +* Number of recursive dependencies: 120 + +Run `revdepcheck::cloud_details(, "ggmice")` for more info + +
+ +## Newly broken + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘old_friends.Rmd’ + ... + layout + + + > p <- plot_flux(dat) + + > ggplotly(p) + + When sourcing ‘old_friends.R’: + Error: subscript out of bounds + Execution halted + + ‘ggmice.Rmd’ using ‘UTF-8’... OK + ‘old_friends.Rmd’ using ‘UTF-8’... failed + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘ggmice.Rmd’ using rmarkdown + ``` + +# ggmulti + +
+ +* Version: 1.0.7 +* GitHub: NA +* Source code: https://github.com/cran/ggmulti +* Date/Publication: 2024-04-09 09:40:05 UTC +* Number of recursive dependencies: 125 + +Run `revdepcheck::cloud_details(, "ggmulti")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘ggmulti-Ex.R’ failed + The error most likely occurred in: + + > ### Name: coord_radial + > ### Title: Radial axes + > ### Aliases: coord_radial + > + > ### ** Examples + > + > if(require("dplyr")) { + ... + + The following objects are masked from ‘package:base’: + + intersect, setdiff, setequal, union + + Error in use_defaults(..., self = self) : + unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, "black", TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), NULL, list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), 5.5, c(5.5, 5.5, 5.5, 5.5), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.75, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, + NULL, NULL, NULL, 1, 90, NULL, c(0, 2.75, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 1, NULL, NULL, NULL, c(0, 2.2, 0, 0), NULL, TRUE), NULL, l + Calls: ... -> -> compute_geom_2 -> + Execution halted + ``` + +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > + > + > library(testthat) + > library(ggmulti) + Loading required package: ggplot2 + + Attaching package: 'ggmulti' + ... + ── Error ('test_stat.R:18:3'): test stat ─────────────────────────────────────── + Error in `stat_hist_(prop = 0.5)`: Problem while setting up geom aesthetics. + ℹ Error occurred in the 1st layer. + Caused by error in `check_aesthetics()`: + ! Aesthetics must be either length 1 or the same as the data (83). + ✖ Fix the following mappings: `width`. + + [ FAIL 5 | WARN 1 | SKIP 0 | PASS 21 ] + Error: Test failures + Execution halted + ``` + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘glyph.Rmd’ + ... + + Sepal.Width, colour = Species), serialaxes.data = iris, axes.layout = "radia ..." ... [TRUNCATED] + + When sourcing ‘glyph.R’: + Error: Base operators are not defined for quosures. Do you need to unquote the + quosure? + + # Bad: myquosure / rhs + ... + > p + + When sourcing ‘highDim.R’: + Error: unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, "black", TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), NULL, list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), 5.5, c(5.5, 5.5, 5.5, 5.5), NULL, NULL, list(), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), + list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, NULL, c(0, 0, 0, 2.2), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0.5, NULL, NULL, NULL, c(0, 2.2, 0, 2.2), NULL, TRUE), list("grey20", NULL, NULL, NULL, FALSE, "grey20", + Execution halted + + ‘glyph.Rmd’ using ‘UTF-8’... failed + ‘highDim.Rmd’ using ‘UTF-8’... failed + ‘histogram-density-.Rmd’ using ‘UTF-8’... OK + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘glyph.Rmd’ using rmarkdown + ``` + +# ggparallel + +
+ +* Version: 0.4.0 +* GitHub: https://github.com/heike/ggparallel +* Source code: https://github.com/cran/ggparallel +* Date/Publication: 2024-03-09 22:00:02 UTC +* Number of recursive dependencies: 51 + +Run `revdepcheck::cloud_details(, "ggparallel")` for more info + +
+ +## Newly broken + +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > # This file is part of the standard setup for testthat. + > # It is recommended that you do not modify it. + > # + > # Where should you do additional test configuration? + > # Learn more about the roles of various files in: + > # * https://r-pkgs.org/testing-design.html#sec-tests-files-overview + > # * https://testthat.r-lib.org/articles/special-files.html + ... + 12. └─self$get_layer_key(params, layers[include], data[include], theme) + 13. └─ggplot2 (local) get_layer_key(...) + 14. └─base::Map(...) + 15. └─base::mapply(FUN = f, ..., SIMPLIFY = FALSE) + 16. └─ggplot2 (local) ``(layer = dots[[1L]][[1L]], df = dots[[2L]][[1L]]) + 17. └─layer$compute_geom_2(key, single_params, theme) + + [ FAIL 1 | WARN 0 | SKIP 0 | PASS 0 ] + Error: Test failures + Execution halted + ``` + +# ggpicrust2 + +
+ +* Version: 1.7.3 +* GitHub: https://github.com/cafferychen777/ggpicrust2 +* Source code: https://github.com/cran/ggpicrust2 +* Date/Publication: 2023-11-08 16:10:02 UTC +* Number of recursive dependencies: 238 + +Run `revdepcheck::cloud_details(, "ggpicrust2")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘ggpicrust2-Ex.R’ failed + The error most likely occurred in: + + > ### Name: pathway_pca + > ### Title: Perform Principal Component Analysis (PCA) on functional pathway + > ### abundance data and create visualizations of the PCA results. + > ### Aliases: pathway_pca + > + > ### ** Examples + > + ... + > + > # Create example metadata + > # Please ensure the sample IDs in the metadata have the column name "sample_name" + > metadata_example <- data.frame(sample_name = colnames(kegg_abundance_example), + + group = factor(rep(c("Control", "Treatment"), each = 5))) + > + > pca_plot <- pathway_pca(kegg_abundance_example, metadata_example, "group") + Error in identicalUnits(x) : object is not a unit + Calls: pathway_pca ... assemble_guides -> guides_build -> unit.c -> identicalUnits + Execution halted + ``` + +## In both + +* checking installed package size ... NOTE + ``` + installed size is 5.5Mb + sub-directories of 1Mb or more: + R 2.1Mb + data 2.0Mb + ``` + +# ggpie + +
+ +* Version: 0.2.5 +* GitHub: https://github.com/showteeth/ggpie +* Source code: https://github.com/cran/ggpie +* Date/Publication: 2022-11-16 07:40:06 UTC +* Number of recursive dependencies: 59 + +Run `revdepcheck::cloud_details(, "ggpie")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘ggpie-Ex.R’ failed + The error most likely occurred in: + + > ### Name: ggdonut + > ### Title: Create donut plot. + > ### Aliases: ggdonut + > + > ### ** Examples + > + > library(ggpie) + ... + Backtrace: + ▆ + 1. ├─base (local) ``(x) + 2. └─ggplot2:::print.ggplot(x) + 3. ├─ggplot2::ggplot_gtable(data) + 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) + 5. └─ggplot2::calc_element("plot.margin", theme) + 6. └─cli::cli_abort(...) + 7. └─rlang::abort(...) + Execution halted + ``` + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘ggpie.Rmd’ + ... + $ x : num [1:53940] 3.95 3.89 4.05 4.2 4.34 3.94 3.95 4.07 3.87 4 ... + $ y : num [1:53940] 3.98 3.84 4.07 4.23 4.35 3.96 3.98 4.11 3.78 4.05 ... + $ z : num [1:53940] 2.43 2.31 2.31 2.63 2.75 2.48 2.47 2.53 2.49 2.39 ... + + > ggpie(data = diamonds, group_key = "cut", count_type = "full", + + label_type = "none") + + When sourcing ‘ggpie.R’: + Error: Theme element `plot.margin` must have class . + Execution halted + + ‘ggpie.Rmd’ using ‘UTF-8’... failed + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + ... + --- re-building ‘ggpie.Rmd’ using rmarkdown + + Quitting from lines 73-75 [pie_basic_no_label] (ggpie.Rmd) + Error: processing vignette 'ggpie.Rmd' failed with diagnostics: + Theme element `plot.margin` must have class . + --- failed re-building ‘ggpie.Rmd’ + + SUMMARY: processing the following file failed: + ‘ggpie.Rmd’ + + Error: Vignette re-building failed. + Execution halted + ``` + +# ggplotlyExtra + +
+ +* Version: 0.0.1 +* GitHub: NA +* Source code: https://github.com/cran/ggplotlyExtra +* Date/Publication: 2019-12-02 16:20:06 UTC +* Number of recursive dependencies: 70 + +Run `revdepcheck::cloud_details(, "ggplotlyExtra")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘ggplotlyExtra-Ex.R’ failed + The error most likely occurred in: + + > ### Name: ggplotly_histogram + > ### Title: Clean 'ggplot2' Histogram to be Converted to 'Plotly' + > ### Aliases: ggplotly_histogram + > + > ### ** Examples + > + > + ... + + xlab("len") + `stat_bin()` using `bins = 30`. Pick better value with `binwidth`. + Warning in geom_bar(data = layerdata, mapping = aes(x = .data$x, y = .data$count, : + Ignoring unknown aesthetics: label1, label2, and label3 + > + > # convert `ggplot` object to `plotly` object + > ggplotly(p, tooltip = c("Range", "count", "density")) + Error in pm[[2]] : subscript out of bounds + Calls: ggplotly -> ggplotly.ggplot -> gg2list + Execution halted + ``` + +## In both + +* checking LazyData ... NOTE + ``` + 'LazyData' is specified without a 'data' directory + ``` + +# ggpol + +
+ +* Version: 0.0.7 +* GitHub: https://github.com/erocoar/ggpol +* Source code: https://github.com/cran/ggpol +* Date/Publication: 2020-11-08 13:40:02 UTC +* Number of recursive dependencies: 54 + +Run `revdepcheck::cloud_details(, "ggpol")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘ggpol-Ex.R’ failed + The error most likely occurred in: + + > ### Name: GeomConfmat + > ### Title: Confusion Matrix + > ### Aliases: GeomConfmat geom_confmat stat_confmat + > + > ### ** Examples + > + > x <- sample(LETTERS[seq(4)], 50, replace = TRUE) + ... + 21. │ └─ggpol (local) draw_panel(...) + 22. │ └─base::lapply(GeomText$default_aes[missing_aes], rlang::eval_tidy) + 23. │ └─rlang (local) FUN(X[[i]], ...) + 24. ├─ggplot2::from_theme(fontsize) + 25. └─base::.handleSimpleError(...) + 26. └─rlang (local) h(simpleError(msg, call)) + 27. └─handlers[[1L]](cnd) + 28. └─cli::cli_abort(...) + 29. └─rlang::abort(...) + Execution halted + ``` + +## In both + +* checking dependencies in R code ... NOTE + ``` + Namespaces in Imports field not imported from: + ‘dplyr’ ‘grDevices’ + All declared Imports should be used. + ``` + +* checking LazyData ... NOTE + ``` + 'LazyData' is specified without a 'data' directory + ``` + +# ggprism + +
+ +* Version: 1.0.5 +* GitHub: https://github.com/csdaw/ggprism +* Source code: https://github.com/cran/ggprism +* Date/Publication: 2024-03-21 10:50:02 UTC +* Number of recursive dependencies: 105 + +Run `revdepcheck::cloud_details(, "ggprism")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘ggprism-Ex.R’ failed + The error most likely occurred in: + + > ### Name: annotation_ticks + > ### Title: Add ticks as ggplot annotation + > ### Aliases: annotation_ticks + > + > ### ** Examples + > + > ## Generally it is better to use the guide_prism_minor function. + ... + Backtrace: + ▆ + 1. ├─base (local) ``(x) + 2. └─ggplot2:::print.ggplot(x) + 3. ├─ggplot2::ggplot_gtable(data) + 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) + 5. └─ggplot2::calc_element("plot.margin", theme) + 6. └─cli::cli_abort(...) + 7. └─rlang::abort(...) + Execution halted + ``` + +# ggpubr + +
+ +* Version: 0.6.0 +* GitHub: https://github.com/kassambara/ggpubr +* Source code: https://github.com/cran/ggpubr +* Date/Publication: 2023-02-10 16:20:02 UTC +* Number of recursive dependencies: 84 + +Run `revdepcheck::cloud_details(, "ggpubr")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘ggpubr-Ex.R’ failed + The error most likely occurred in: + + > ### Name: ggpie + > ### Title: Pie chart + > ### Aliases: ggpie + > + > ### ** Examples + > + > + ... + Backtrace: + ▆ + 1. ├─base (local) ``(x) + 2. └─ggplot2:::print.ggplot(x) + 3. ├─ggplot2::ggplot_gtable(data) + 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) + 5. └─ggplot2::calc_element("plot.margin", theme) + 6. └─cli::cli_abort(...) + 7. └─rlang::abort(...) + Execution halted + ``` + +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(ggpubr) + Loading required package: ggplot2 + > + > test_check("ggpubr") + [ FAIL 2 | WARN 5 | SKIP 0 | PASS 183 ] + + ... + [6] 6 - 10 == -4 + [7] 19 - 9 == 10 + [9] 1 - 7 == -6 + [10] 6 - 7 == -1 + [11] 13 - 6 == 7 + ... + + [ FAIL 2 | WARN 5 | SKIP 0 | PASS 183 ] + Error: Test failures + Execution halted + ``` + +# ggraph + +
+ +* Version: 2.2.1 +* GitHub: https://github.com/thomasp85/ggraph +* Source code: https://github.com/cran/ggraph +* Date/Publication: 2024-03-07 12:40:02 UTC +* Number of recursive dependencies: 115 + +Run `revdepcheck::cloud_details(, "ggraph")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘ggraph-Ex.R’ failed + The error most likely occurred in: + + > ### Name: geom_conn_bundle + > ### Title: Create hierarchical edge bundles between node connections + > ### Aliases: geom_conn_bundle geom_conn_bundle2 geom_conn_bundle0 + > + > ### ** Examples + > + > # Create a graph of the flare class system + ... + + ) + + + geom_node_point(aes(filter = leaf, colour = class)) + + + scale_edge_colour_distiller('', direction = 1, guide = 'edge_direction') + + + coord_fixed() + + + ggforce::theme_no_axes() + Error in get_layer_key(...) : + unused argument (list(list("black", 0.5, 1, "butt", FALSE, "black", TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), NULL, list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), 5.5, c(5.5, 5.5, 5.5, 5.5), NULL, list(), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.75, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, + NULL, NULL, 1, 90, NULL, c(0, 2.75, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 1, NULL, NULL, NULL, c(0, 2.2, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, NULL, c(0, 0, 0, 2.2), NULL, T + Calls: ... -> -> process_layers -> + Execution halted + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘Edges.Rmd’ using rmarkdown + ``` + +## In both + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘Edges.Rmd’ + ... + Warning in grid.Call.graphics(C_text, as.graphicsAnnot(x$label), x$x, x$y, : + font family 'Arial Narrow' not found in PostScript font database + Warning in grid.Call.graphics(C_text, as.graphicsAnnot(x$label), x$x, x$y, : + font family 'Arial Narrow' not found in PostScript font database + Warning in grid.Call.graphics(C_text, as.graphicsAnnot(x$label), x$x, x$y, : + font family 'Arial Narrow' not found in PostScript font database + + ... + font family 'Arial' not found in PostScript font database + + When sourcing ‘tidygraph.R’: + Error: invalid font type + Execution halted + + ‘Edges.Rmd’ using ‘UTF-8’... failed + ‘Layouts.Rmd’ using ‘UTF-8’... failed + ‘Nodes.Rmd’ using ‘UTF-8’... failed + ‘tidygraph.Rmd’ using ‘UTF-8’... failed + ``` + +* checking installed package size ... NOTE + ``` + installed size is 9.0Mb + sub-directories of 1Mb or more: + R 1.5Mb + doc 3.9Mb + libs 2.9Mb + ``` + +# ggredist + +
+ +* Version: 0.0.2 +* GitHub: https://github.com/alarm-redist/ggredist +* Source code: https://github.com/cran/ggredist +* Date/Publication: 2022-11-23 11:20:02 UTC +* Number of recursive dependencies: 67 + +Run `revdepcheck::cloud_details(, "ggredist")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘ggredist-Ex.R’ failed + The error most likely occurred in: + + > ### Name: geom_district_text + > ### Title: Label Map Regions + > ### Aliases: geom_district_text geom_district_label + > ### stat_district_coordinates StatDistrictCoordinates GeomDistrictText + > ### Keywords: datasets + > + > ### ** Examples + ... + 22. │ └─coord$transform(data, panel_params) + 23. │ └─ggplot2 (local) transform(..., self = self) + 24. │ └─ggplot2:::sf_rescale01(...) + 25. │ └─sf::st_normalize(x, c(x_range[1], y_range[1], x_range[2], y_range[2])) + 26. └─base::.handleSimpleError(...) + 27. └─rlang (local) h(simpleError(msg, call)) + 28. └─handlers[[1L]](cnd) + 29. └─cli::cli_abort(...) + 30. └─rlang::abort(...) + Execution halted + ``` + +# ggResidpanel + +
+ +* Version: 0.3.0 +* GitHub: NA +* Source code: https://github.com/cran/ggResidpanel +* Date/Publication: 2019-05-31 23:20:04 UTC +* Number of recursive dependencies: 112 + +Run `revdepcheck::cloud_details(, "ggResidpanel")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘ggResidpanel-Ex.R’ failed + The error most likely occurred in: + + > ### Name: resid_interact + > ### Title: Panel of Interactive Versions of Diagnostic Residual Plots. + > ### Aliases: resid_interact + > + > ### ** Examples + > + > + > # Fit a model to the penguin data + > penguin_model <- lme4::lmer(heartrate ~ depth + duration + (1|bird), data = penguins) + > + > # Create the default interactive panel + > resid_interact(penguin_model) + Error in pm[[2]] : subscript out of bounds + Calls: resid_interact ... %>% -> layout -> ggplotly -> ggplotly.ggplot -> gg2list + Execution halted + ``` + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘introduction.Rmd’ + ... + > resid_interact(penguin_model, plots = c("resid", "qq")) + Warning: The following aesthetics were dropped during statistical transformation: label. + ℹ This can happen when ggplot fails to infer the correct grouping structure in + the data. + ℹ Did you forget to specify a `group` aesthetic or to convert a numerical + variable into a factor? + + When sourcing ‘introduction.R’: + Error: subscript out of bounds + Execution halted + + ‘introduction.Rmd’ using ‘UTF-8’... failed + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘introduction.Rmd’ using rmarkdown + ``` + +# ggseqplot + +
+ +* Version: 0.8.4 +* GitHub: https://github.com/maraab23/ggseqplot +* Source code: https://github.com/cran/ggseqplot +* Date/Publication: 2024-05-17 21:40:03 UTC +* Number of recursive dependencies: 139 + +Run `revdepcheck::cloud_details(, "ggseqplot")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘ggseqplot-Ex.R’ failed + The error most likely occurred in: + + > ### Name: ggseqmsplot + > ### Title: Modal State Sequence Plot + > ### Aliases: ggseqmsplot + > + > ### ** Examples + > + > # Use example data from TraMineR: actcal data set + ... + 11. │ └─base::withCallingHandlers(...) + 12. └─ggplot2 (local) f(l = layers[[i]], d = data[[i]]) + 13. └─l$compute_geom_2(d, theme = plot$theme) + 14. └─ggplot2 (local) compute_geom_2(..., self = self) + 15. └─self$geom$use_defaults(...) + 16. └─ggplot2 (local) use_defaults(..., self = self) + 17. └─ggplot2:::check_aesthetics(new_params, nrow(data)) + 18. └─cli::cli_abort(...) + 19. └─rlang::abort(...) + Execution halted + ``` + +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(ggseqplot) + Loading required package: TraMineR + + TraMineR stable version 2.2-10 (Built: 2024-05-22) + Website: http://traminer.unige.ch + Please type 'citation("TraMineR")' for citation information. + ... + Backtrace: + ▆ + 1. ├─testthat::expect_s3_class(ggseqtrplot(biofam.seq), "ggplot") at test-ggseqtrplot.R:35:3 + 2. │ └─testthat::quasi_label(enquo(object), arg = "object") + 3. │ └─rlang::eval_bare(expr, quo_get_env(quo)) + 4. └─ggseqplot::ggseqtrplot(biofam.seq) + + [ FAIL 1 | WARN 1036 | SKIP 0 | PASS 131 ] + Error: Test failures + Execution halted + ``` + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘ggseqplot.Rmd’ + ... + > p1 + p2 + plot_layout(guides = "collect") & scale_fill_manual(values = canva_palettes$`Fun and tropical`[1:4]) & + + theme_ipsum(base_family = "" .... [TRUNCATED] + Scale for fill is already present. + Adding another scale for fill, which will replace the existing scale. + Scale for fill is already present. + Adding another scale for fill, which will replace the existing scale. + + When sourcing ‘ggseqplot.R’: + Error: object is not coercible to a unit + Execution halted + + ‘ggseqplot.Rmd’ using ‘UTF-8’... failed + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘ggseqplot.Rmd’ using rmarkdown + ``` + +# ggside + +
+ +* Version: 0.3.1 +* GitHub: https://github.com/jtlandis/ggside +* Source code: https://github.com/cran/ggside +* Date/Publication: 2024-03-01 09:12:37 UTC +* Number of recursive dependencies: 76 + +Run `revdepcheck::cloud_details(, "ggside")` for more info + +
+ +## Newly broken + +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(ggplot2) + > library(ggside) + Registered S3 method overwritten by 'ggside': + method from + +.gg ggplot2 + > + ... + • ops_meaningful/alpha-0-5-from-function.svg + • side_layers/boxplot2.svg + • vdiff_irisScatter/collapsed-histo.svg + • vdiff_irisScatter/facetgrid-collapsed-density.svg + • vdiff_irisScatter/facetgrid-histo.svg + • vdiff_irisScatter/facetgrid-side-density.svg + • vdiff_irisScatter/stacked-side-density.svg + • vdiff_irisScatter/yside-histo.svg + Error: Test failures + Execution halted + ``` + +* checking for code/documentation mismatches ... WARNING + ``` + Codoc mismatches from documentation object 'geom_xsidebar': + geom_xsidebar + Code: function(mapping = NULL, data = NULL, stat = "count", position + = "stack", ..., just = 0.5, na.rm = FALSE, orientation + = "x", show.legend = NA, inherit.aes = TRUE) + Docs: function(mapping = NULL, data = NULL, stat = "count", position + = "stack", ..., just = 0.5, width = NULL, na.rm = + FALSE, orientation = "x", show.legend = NA, + inherit.aes = TRUE) + Argument names in docs not in code: + ... + Docs: function(mapping = NULL, data = NULL, stat = "identity", + position = "identity", ..., lineend = "butt", linejoin + = "round", linemitre = 10, arrow = NULL, na.rm = + FALSE, show.legend = NA, inherit.aes = TRUE) + Argument names in code not in docs: + arrow.fill + Mismatches in argument names: + Position: 10 Code: arrow.fill Docs: na.rm + Position: 11 Code: na.rm Docs: show.legend + Position: 12 Code: show.legend Docs: inherit.aes + ``` + +# ggstatsplot + +
+ +* Version: 0.12.3 +* GitHub: https://github.com/IndrajeetPatil/ggstatsplot +* Source code: https://github.com/cran/ggstatsplot +* Date/Publication: 2024-04-06 17:42:59 UTC +* Number of recursive dependencies: 168 + +Run `revdepcheck::cloud_details(, "ggstatsplot")` for more info + +
+ +## Newly broken + +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > # graphics engine changed in this version, and so snapshots generated on + > # previous R version won't work + > if (getRversion() < "4.4.0") { + + library(testthat) + + suppressPackageStartupMessages(library(ggstatsplot)) + + + + test_check("ggstatsplot") + ... + • pairwise-ggsignif/within-non-parametric-all.svg + • pairwise-ggsignif/within-non-parametric-only-non-significant.svg + • pairwise-ggsignif/within-non-parametric-only-significant.svg + • pairwise-ggsignif/within-parametric-all.svg + • pairwise-ggsignif/within-parametric-only-significant.svg + • pairwise-ggsignif/within-robust-all.svg + • pairwise-ggsignif/within-robust-only-non-significant.svg + • pairwise-ggsignif/within-robust-only-significant.svg + Error: Test failures + Execution halted + ``` + +## In both + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘ggstatsplot.Rmd’ + ... + journal = {{Journal of Open Source Software}}, + } + + > ggbetweenstats(iris, Species, Sepal.Length) + + > knitr::include_graphics("../man/figures/stats_reporting_format.png") + + When sourcing ‘ggstatsplot.R’: + Error: Cannot find the file(s): "../man/figures/stats_reporting_format.png" + Execution halted + + ‘additional.Rmd’ using ‘UTF-8’... OK + ‘ggstatsplot.Rmd’ using ‘UTF-8’... failed + ``` + +# ggtern + +
+ +* Version: 3.5.0 +* GitHub: NA +* Source code: https://github.com/cran/ggtern +* Date/Publication: 2024-03-24 21:50:02 UTC +* Number of recursive dependencies: 42 + +Run `revdepcheck::cloud_details(, "ggtern")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘ggtern-Ex.R’ failed + The error most likely occurred in: + + > ### Name: annotate + > ### Title: Create an annotation layer (ggtern version). + > ### Aliases: annotate + > + > ### ** Examples + > + > ggtern() + + ... + 3. ├─ggtern::ggplot_build(x) + 4. └─ggtern:::ggplot_build.ggplot(x) + 5. └─ggtern:::layers_add_or_remove_mask(plot) + 6. └─ggint$plot_theme(plot) + 7. └─ggplot2:::validate_theme(theme) + 8. └─base::mapply(...) + 9. └─ggplot2 (local) ``(...) + 10. └─cli::cli_abort(...) + 11. └─rlang::abort(...) + Execution halted + ``` + +## In both + +* checking package dependencies ... NOTE + ``` + Package which this enhances but not available for checking: ‘sp’ + ``` + +* checking Rd cross-references ... NOTE + ``` + Package unavailable to check Rd xrefs: ‘chemometrics’ + ``` + +# ggthemes + +
+ +* Version: 5.1.0 +* GitHub: https://github.com/jrnold/ggthemes +* Source code: https://github.com/cran/ggthemes +* Date/Publication: 2024-02-10 00:30:02 UTC +* Number of recursive dependencies: 101 + +Run `revdepcheck::cloud_details(, "ggthemes")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘ggthemes-Ex.R’ failed + The error most likely occurred in: + + > ### Name: theme_economist + > ### Title: ggplot color theme based on the Economist + > ### Aliases: theme_economist theme_economist_white + > + > ### ** Examples + > + > library("ggplot2") + ... + Backtrace: + ▆ + 1. ├─base (local) ``(x) + 2. └─ggplot2:::print.ggplot(x) + 3. ├─ggplot2::ggplot_gtable(data) + 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) + 5. └─ggplot2::calc_element("plot.margin", theme) + 6. └─cli::cli_abort(...) + 7. └─rlang::abort(...) + Execution halted + ``` + +## In both + +* checking package dependencies ... NOTE + ``` + Package suggested but not available for checking: ‘quantreg’ + ``` + +* checking data for non-ASCII characters ... NOTE + ``` + Note: found 138 marked UTF-8 strings + ``` + +# ggupset + +
+ +* Version: 0.3.0 +* GitHub: https://github.com/const-ae/ggupset +* Source code: https://github.com/cran/ggupset +* Date/Publication: 2020-05-05 10:40:03 UTC +* Number of recursive dependencies: 46 + +Run `revdepcheck::cloud_details(, "ggupset")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘ggupset-Ex.R’ failed + The error most likely occurred in: + + > ### Name: axis_combmatrix + > ### Title: Convert delimited text labels into a combination matrix axis + > ### Aliases: axis_combmatrix + > + > ### ** Examples + > + > library(ggplot2) + ... + Datsun 710 Cyl: 4_Gears: 4 + Hornet 4 Drive Cyl: 6_Gears: 3 + Hornet Sportabout Cyl: 8_Gears: 3 + Valiant Cyl: 6_Gears: 3 + > ggplot(mtcars, aes(x=combined)) + + + geom_bar() + + + axis_combmatrix(sep = "_") + Error in as.unit(e2) : object is not coercible to a unit + Calls: ... polylineGrob -> is.unit -> unit.c -> Ops.unit -> as.unit + Execution halted + ``` + +# ggVennDiagram + +
+ +* Version: 1.5.2 +* GitHub: https://github.com/gaospecial/ggVennDiagram +* Source code: https://github.com/cran/ggVennDiagram +* Date/Publication: 2024-02-20 08:10:02 UTC +* Number of recursive dependencies: 98 + +Run `revdepcheck::cloud_details(, "ggVennDiagram")` for more info + +
+ +## Newly broken + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘fully-customed.Rmd’ + ... + [1] "b" "c" "e" "h" "k" "q" "s" "y" + + + > ggVennDiagram(y, show_intersect = TRUE, set_color = "black") + Warning in geom_text(aes(label = .data$count, text = .data$item), data = region_label) : + Ignoring unknown aesthetics: text + + ... + Ignoring unknown aesthetics: text + + When sourcing ‘using-ggVennDiagram.R’: + Error: subscript out of bounds + Execution halted + + ‘VennCalculator.Rmd’ using ‘UTF-8’... OK + ‘fully-customed.Rmd’ using ‘UTF-8’... failed + ‘using-ggVennDiagram.Rmd’ using ‘UTF-8’... failed + ‘using-new-shapes.Rmd’ using ‘UTF-8’... OK + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘VennCalculator.Rmd’ using rmarkdown + --- finished re-building ‘VennCalculator.Rmd’ + + --- re-building ‘fully-customed.Rmd’ using rmarkdown + ``` + +## In both + +* checking installed package size ... NOTE + ``` + installed size is 11.1Mb + sub-directories of 1Mb or more: + doc 9.5Mb + help 1.1Mb + ``` + +# graphPAF + +
+ +* Version: 2.0.0 +* GitHub: https://github.com/johnfergusonNUIG/graphPAF +* Source code: https://github.com/cran/graphPAF +* Date/Publication: 2023-12-21 00:50:06 UTC +* Number of recursive dependencies: 50 + +Run `revdepcheck::cloud_details(, "graphPAF")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘graphPAF-Ex.R’ failed + The error most likely occurred in: + + > ### Name: plot.rf.data.frame + > ### Title: Create a fan_plot of a rf.data.frame object + > ### Aliases: plot.rf.data.frame + > + > ### ** Examples + > + > library(ggplot2) + ... + Backtrace: + ▆ + 1. ├─base (local) ``(x) + 2. └─ggplot2:::print.ggplot(x) + 3. ├─ggplot2::ggplot_gtable(data) + 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) + 5. └─ggplot2::calc_element("plot.margin", theme) + 6. └─cli::cli_abort(...) + 7. └─rlang::abort(...) + Execution halted + ``` + +# greatR + +
+ +* Version: 2.0.0 +* GitHub: https://github.com/ruthkr/greatR +* Source code: https://github.com/cran/greatR +* Date/Publication: 2024-04-09 22:40:07 UTC +* Number of recursive dependencies: 77 + +Run `revdepcheck::cloud_details(, "greatR")` for more info + +
+ +## Newly broken + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘process-results.Rmd’ + ... + + > reg_summary$non_registered_genes + [1] "BRAA02G018970.3C" + + > plot(reg_summary, type = "registered", scatterplot_size = c(4, + + 3.5)) + + When sourcing ‘process-results.R’: + Error: object is not a unit + Execution halted + + ‘data-requirement.Rmd’ using ‘UTF-8’... OK + ‘process-results.Rmd’ using ‘UTF-8’... failed + ‘register-data-manually.Rmd’ using ‘UTF-8’... OK + ‘register-data.Rmd’ using ‘UTF-8’... OK + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + ... + --- re-building ‘data-requirement.Rmd’ using rmarkdown + --- finished re-building ‘data-requirement.Rmd’ + + --- re-building ‘process-results.Rmd’ using rmarkdown + + Quitting from lines 76-81 [plot-summary-results] (process-results.Rmd) + Error: processing vignette 'process-results.Rmd' failed with diagnostics: + object is not a unit + ... + --- finished re-building ‘register-data-manually.Rmd’ + + --- re-building ‘register-data.Rmd’ using rmarkdown + --- finished re-building ‘register-data.Rmd’ + + SUMMARY: processing the following file failed: + ‘process-results.Rmd’ + + Error: Vignette re-building failed. + Execution halted + ``` + +# Greymodels + +
+ +* Version: 2.0.1 +* GitHub: https://github.com/havishaJ/Greymodels +* Source code: https://github.com/cran/Greymodels +* Date/Publication: 2022-12-05 12:42:35 UTC +* Number of recursive dependencies: 91 + +Run `revdepcheck::cloud_details(, "Greymodels")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘Greymodels-Ex.R’ failed + The error most likely occurred in: + + > ### Name: Plots + > ### Title: plots + > ### Aliases: plots plotrm plotsmv1 plotsmv2 plotsigndgm plots_mdbgm12 + > + > ### ** Examples + > + > # Plots - EPGM (1, 1) model + ... + + geom_point(data = set4, aes(x = CI, y = y), shape = 23, color = "black") + + + geom_line(data = xy1, aes(x = x, y = y,color = "Raw Data")) + + + geom_line(data = xy2, aes(x = x, y = y,color = "Fitted&Forecasts")) + + + geom_line(data = set3, aes(x = CI, y = y,color = "LowerBound"), linetype=2) + + + geom_line(data = set4, aes(x = CI, y = y,color = "UpperBound"), linetype=2) + + + scale_color_manual(name = "Label",values = colors) + > r <- ggplotly(p) + Error in pm[[2]] : subscript out of bounds + Calls: ggplotly -> ggplotly.ggplot -> gg2list + Execution halted + ``` + +# groupdata2 + +
+ +* Version: 2.0.3 +* GitHub: https://github.com/ludvigolsen/groupdata2 +* Source code: https://github.com/cran/groupdata2 +* Date/Publication: 2023-06-18 12:30:02 UTC +* Number of recursive dependencies: 96 + +Run `revdepcheck::cloud_details(, "groupdata2")` for more info + +
+ +## Newly broken + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘description_of_groupdata2.Rmd’ + ... + + > greedy_plot <- ggplot(greedy_data, aes(x, freq, color = Size)) + + > greedy_plot + geom_point() + labs(x = "group", y = "group Size", + + title = "Greedy Distribution of Elements in groups", color = "Size") + + + .... [TRUNCATED] + + When sourcing ‘description_of_groupdata2.R’: + Error: Theme element `plot.margin` must have class . + Execution halted + + ‘automatic_groups_with_groupdata2.Rmd’ using ‘UTF-8’... OK + ‘cross-validation_with_groupdata2.Rmd’ using ‘UTF-8’... OK + ‘description_of_groupdata2.Rmd’ using ‘UTF-8’... failed + ‘introduction_to_groupdata2.Rmd’ using ‘UTF-8’... OK + ‘time_series_with_groupdata2.Rmd’ using ‘UTF-8’... OK + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘automatic_groups_with_groupdata2.Rmd’ using rmarkdown + --- finished re-building ‘automatic_groups_with_groupdata2.Rmd’ + + --- re-building ‘cross-validation_with_groupdata2.Rmd’ using rmarkdown + Loading required namespace: broom + --- finished re-building ‘cross-validation_with_groupdata2.Rmd’ + + --- re-building ‘description_of_groupdata2.Rmd’ using rmarkdown + ``` + +# GSD + +
+ +* Version: 1.0.0 +* GitHub: NA +* Source code: https://github.com/cran/GSD +* Date/Publication: 2024-02-05 20:40:13 UTC +* Number of recursive dependencies: 32 + +Run `revdepcheck::cloud_details(, "GSD")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘GSD-Ex.R’ failed + The error most likely occurred in: + + > ### Name: gfdecomp + > ### Title: Graph Fourier Decomposition + > ### Aliases: gfdecomp + > ### Keywords: nonparametric + > + > ### ** Examples + > + ... + Backtrace: + ▆ + 1. ├─base (local) ``(x) + 2. └─ggplot2:::print.ggplot(x) + 3. ├─ggplot2::ggplot_gtable(data) + 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) + 5. └─ggplot2::calc_element("plot.margin", theme) + 6. └─cli::cli_abort(...) + 7. └─rlang::abort(...) + Execution halted + ``` + +# gtExtras + +
+ +* Version: 0.5.0 +* GitHub: https://github.com/jthomasmock/gtExtras +* Source code: https://github.com/cran/gtExtras +* Date/Publication: 2023-09-15 22:32:06 UTC +* Number of recursive dependencies: 105 + +Run `revdepcheck::cloud_details(, "gtExtras")` for more info + +
+ +## Newly broken + +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(gtExtras) + Loading required package: gt + + Attaching package: 'gt' + + The following object is masked from 'package:testthat': + ... + 18. └─ggplot2:::print.ggplot(x) + 19. ├─ggplot2::ggplot_gtable(data) + 20. └─ggplot2:::ggplot_gtable.ggplot_built(data) + 21. └─ggplot2::calc_element("plot.margin", theme) + 22. └─cli::cli_abort(...) + 23. └─rlang::abort(...) + + [ FAIL 1 | WARN 14 | SKIP 23 | PASS 112 ] + Error: Test failures + Execution halted + ``` + +# HaploCatcher + +
+ +* Version: 1.0.4 +* GitHub: NA +* Source code: https://github.com/cran/HaploCatcher +* Date/Publication: 2023-04-21 23:32:39 UTC +* Number of recursive dependencies: 113 + +Run `revdepcheck::cloud_details(, "HaploCatcher")` for more info + +
+ +## Newly broken + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘An_Intro_to_HaploCatcher.Rmd’ + ... + > set.seed(NULL) + + > results1 <- auto_locus(geno_mat = geno_mat, gene_file = gene_comp, + + gene_name = "sst1_solid_stem", marker_info = marker_info, + + chromosom .... [TRUNCATED] + Loading required package: lattice + + When sourcing ‘An_Intro_to_HaploCatcher.R’: + Error: object is not a unit + Execution halted + + ‘An_Intro_to_HaploCatcher.Rmd’ using ‘UTF-8’... failed + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + ... + --- re-building ‘An_Intro_to_HaploCatcher.Rmd’ using rmarkdown + + Quitting from lines 242-253 [example_models_1] (An_Intro_to_HaploCatcher.Rmd) + Error: processing vignette 'An_Intro_to_HaploCatcher.Rmd' failed with diagnostics: + object is not a unit + --- failed re-building ‘An_Intro_to_HaploCatcher.Rmd’ + + SUMMARY: processing the following file failed: + ‘An_Intro_to_HaploCatcher.Rmd’ + + Error: Vignette re-building failed. + Execution halted + ``` + +# hdnom + +
+ +* Version: 6.0.3 +* GitHub: https://github.com/nanxstats/hdnom +* Source code: https://github.com/cran/hdnom +* Date/Publication: 2024-03-03 03:20:02 UTC +* Number of recursive dependencies: 66 + +Run `revdepcheck::cloud_details(, "hdnom")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘hdnom-Ex.R’ failed + The error most likely occurred in: + + > ### Name: calibrate + > ### Title: Calibrate high-dimensional Cox models + > ### Aliases: calibrate + > + > ### ** Examples + > + > data("smart") + ... + Backtrace: + ▆ + 1. ├─base (local) ``(x) + 2. └─ggplot2:::print.ggplot(x) + 3. ├─ggplot2::ggplot_gtable(data) + 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) + 5. └─ggplot2::calc_element("plot.margin", theme) + 6. └─cli::cli_abort(...) + 7. └─rlang::abort(...) + Execution halted + ``` + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘hdnom.Rmd’ + ... + Mean 0.6841580 0.6935303 + Min 0.6770945 0.6800316 + 0.25 Qt. 0.6821133 0.6924729 + Median 0.6831368 0.6956285 + 0.75 Qt. 0.6864527 0.6966638 + Max 0.6939574 0.6997908 + + When sourcing ‘hdnom.R’: + Error: Theme element `plot.margin` must have class . + Execution halted + + ‘hdnom.Rmd’ using ‘UTF-8’... failed + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘hdnom.Rmd’ using rmarkdown + ``` + +# healthyR + +
+ +* Version: 0.2.1 +* GitHub: https://github.com/spsanderson/healthyR +* Source code: https://github.com/cran/healthyR +* Date/Publication: 2023-04-06 22:20:03 UTC +* Number of recursive dependencies: 158 + +Run `revdepcheck::cloud_details(, "healthyR")` for more info + +
+ +## Newly broken + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘getting-started.Rmd’ + ... + + > ts_alos_plt(.data = df_tbl, .date_col = Date, .value_col = Values, + + .by = "month", .interactive = FALSE) + + > ts_alos_plt(.data = df_tbl, .date_col = Date, .value_col = Values, + + .by = "month", .interactive = TRUE) + + When sourcing ‘getting-started.R’: + Error: subscript out of bounds + Execution halted + + ‘getting-started.Rmd’ using ‘UTF-8’... failed + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘getting-started.Rmd’ using rmarkdown + ``` + +## In both + +* checking installed package size ... NOTE + ``` + installed size is 6.6Mb + sub-directories of 1Mb or more: + data 2.5Mb + doc 3.7Mb + ``` + +# healthyR.ai + +
+ +* Version: 0.0.13 +* GitHub: https://github.com/spsanderson/healthyR.ai +* Source code: https://github.com/cran/healthyR.ai +* Date/Publication: 2023-04-03 00:20:02 UTC +* Number of recursive dependencies: 229 + +Run `revdepcheck::cloud_details(, "healthyR.ai")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘healthyR.ai-Ex.R’ failed + The error most likely occurred in: + + > ### Name: pca_your_recipe + > ### Title: Perform PCA + > ### Aliases: pca_your_recipe + > + > ### ** Examples + > + > suppressPackageStartupMessages(library(timetk)) + ... + + step_rm(matches("(iso$)|(xts$)|(hour)|(min)|(sec)|(am.pm)")) + > + > output_list <- pca_your_recipe(rec_obj, .data = data_tbl) + Warning: ! The following columns have zero variance so scaling cannot be used: + date_col_day, date_col_mday, date_col_mweek, and date_col_mday7. + ℹ Consider using ?step_zv (`?recipes::step_zv()`) to remove those columns + before normalizing. + Error in pm[[2]] : subscript out of bounds + Calls: pca_your_recipe -> -> ggplotly.ggplot -> gg2list + Execution halted + ``` + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘getting-started.Rmd’ + ... + > pca_list <- pca_your_recipe(.recipe_object = rec_obj, + + .data = data_tbl, .threshold = 0.8, .top_n = 5) + Warning: ! The following columns have zero variance so scaling cannot be used: + date_col_day, date_col_mday, date_col_mweek, and date_col_mday7. + ℹ Consider using ?step_zv (`?recipes::step_zv()`) to remove those columns + before normalizing. + + When sourcing ‘getting-started.R’: + Error: subscript out of bounds + Execution halted + + ‘auto-kmeans.Rmd’ using ‘UTF-8’... OK + ‘getting-started.Rmd’ using ‘UTF-8’... failed + ‘kmeans-umap.Rmd’ using ‘UTF-8’... OK + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘auto-kmeans.Rmd’ using rmarkdown + --- finished re-building ‘auto-kmeans.Rmd’ + + --- re-building ‘getting-started.Rmd’ using rmarkdown + + Quitting from lines 107-113 [pca_your_rec] (getting-started.Rmd) + Error: processing vignette 'getting-started.Rmd' failed with diagnostics: + subscript out of bounds + --- failed re-building ‘getting-started.Rmd’ + + --- re-building ‘kmeans-umap.Rmd’ using rmarkdown + ``` + +# healthyR.ts + +
+ +* Version: 0.3.0 +* GitHub: https://github.com/spsanderson/healthyR.ts +* Source code: https://github.com/cran/healthyR.ts +* Date/Publication: 2023-11-15 06:00:05 UTC +* Number of recursive dependencies: 222 + +Run `revdepcheck::cloud_details(, "healthyR.ts")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘healthyR.ts-Ex.R’ failed + The error most likely occurred in: + + > ### Name: tidy_fft + > ### Title: Tidy Style FFT + > ### Aliases: tidy_fft + > + > ### ** Examples + > + > suppressPackageStartupMessages(library(dplyr)) + ... + > a <- tidy_fft( + + .data = data_tbl, + + .value_col = value, + + .date_col = date_col, + + .harmonics = 3, + + .frequency = 12 + + ) + Error in pm[[2]] : subscript out of bounds + Calls: tidy_fft -> -> ggplotly.ggplot -> gg2list + Execution halted + ``` + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘using-tidy-fft.Rmd’ + ... + $ value 112, 118, 132, 129, 121, 135, 148, 148, 136, 119, 104, 118, 1… + + > suppressPackageStartupMessages(library(timetk)) + + > data_tbl %>% plot_time_series(.date_var = date_col, + + .value = value) + + When sourcing ‘using-tidy-fft.R’: + Error: subscript out of bounds + Execution halted + + ‘getting-started.Rmd’ using ‘UTF-8’... OK + ‘using-tidy-fft.Rmd’ using ‘UTF-8’... failed + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘getting-started.Rmd’ using rmarkdown + ``` + +## In both + +* checking installed package size ... NOTE + ``` + installed size is 6.3Mb + sub-directories of 1Mb or more: + doc 5.2Mb + ``` + +# heatmaply + +
+ +* Version: 1.5.0 +* GitHub: https://github.com/talgalili/heatmaply +* Source code: https://github.com/cran/heatmaply +* Date/Publication: 2023-10-06 20:50:02 UTC +* Number of recursive dependencies: 111 + +Run `revdepcheck::cloud_details(, "heatmaply")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘heatmaply-Ex.R’ failed + The error most likely occurred in: + + > ### Name: ggheatmap + > ### Title: ggplot heatmap equivalent to heatmaply + > ### Aliases: ggheatmap + > + > ### ** Examples + > + > ggheatmap(mtcars) + ... + 2. └─heatmaply:::arrange_plots(...) + 3. └─egg::ggarrange(...) + 4. └─base::lapply(plots, ggplot2::ggplotGrob) + 5. └─ggplot2 (local) FUN(X[[i]], ...) + 6. ├─ggplot2::ggplot_gtable(ggplot_build(x)) + 7. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) + 8. └─ggplot2::calc_element("plot.margin", theme) + 9. └─cli::cli_abort(...) + 10. └─rlang::abort(...) + Execution halted + ``` + +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(heatmaply) + Loading required package: plotly + Loading required package: ggplot2 + + Attaching package: 'plotly' + + ... + 4. │ │ └─base::withCallingHandlers(...) + 5. │ └─rlang::eval_bare(quo_get_expr(.quo), quo_get_env(.quo)) + 6. ├─heatmaply:::predict_colors(ggplotly(g), plot_method = "ggplot") + 7. ├─plotly::ggplotly(g) + 8. └─plotly:::ggplotly.ggplot(g) + 9. └─plotly::gg2list(...) + + [ FAIL 59 | WARN 0 | SKIP 0 | PASS 185 ] + Error: Test failures + Execution halted + ``` + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘heatmaply.Rmd’ + ... + + > library("heatmaply") + + > library("heatmaply") + + > heatmaply(mtcars) + + When sourcing ‘heatmaply.R’: + Error: subscript out of bounds + Execution halted + + ‘heatmaply.Rmd’ using ‘UTF-8’... failed + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + ... + --- re-building ‘heatmaply.Rmd’ using rmarkdown + + Quitting from lines 109-111 [unnamed-chunk-5] (heatmaply.Rmd) + Error: processing vignette 'heatmaply.Rmd' failed with diagnostics: + subscript out of bounds + --- failed re-building ‘heatmaply.Rmd’ + + SUMMARY: processing the following file failed: + ‘heatmaply.Rmd’ + + Error: Vignette re-building failed. + Execution halted + ``` + +## In both + +* checking installed package size ... NOTE + ``` + installed size is 5.5Mb + sub-directories of 1Mb or more: + doc 5.1Mb + ``` + +# hermiter + +
+ +* Version: 2.3.1 +* GitHub: https://github.com/MikeJaredS/hermiter +* Source code: https://github.com/cran/hermiter +* Date/Publication: 2024-03-06 23:50:02 UTC +* Number of recursive dependencies: 79 + +Run `revdepcheck::cloud_details(, "hermiter")` for more info + +
+ +## Newly broken + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘hermiter.Rmd’ + ... + > p2 <- ggplot(df_pdf_cdf) + geom_tile(aes(X, Y, fill = pdf_est)) + + + scale_fill_continuous_sequential(palette = "Oslo", breaks = seq(0, + + .... [TRUNCATED] + + > p1 + ggtitle("Actual PDF") + theme(legend.title = element_blank()) + + + p2 + ggtitle("Estimated PDF") + theme(legend.title = element_blank()) + .... [TRUNCATED] + + When sourcing ‘hermiter.R’: + Error: object is not a unit + Execution halted + + ‘hermiter.Rmd’ using ‘UTF-8’... failed + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘hermiter.Rmd’ using rmarkdown + ``` + +## In both + +* checking installed package size ... NOTE + ``` + installed size is 6.5Mb + sub-directories of 1Mb or more: + R 2.6Mb + doc 1.9Mb + libs 1.8Mb + ``` + +* checking for GNU extensions in Makefiles ... NOTE + ``` + GNU make is a SystemRequirements. + ``` + +# heumilkr + +
+ +* Version: 0.2.0 +* GitHub: https://github.com/lschneiderbauer/heumilkr +* Source code: https://github.com/cran/heumilkr +* Date/Publication: 2024-04-01 13:50:06 UTC +* Number of recursive dependencies: 80 + +Run `revdepcheck::cloud_details(, "heumilkr")` for more info + +
+ +## Newly broken + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘clarke_wright_performance.Rmd’ + ... + + "F", "tai"), group_desc = c("Augerat A, 1995", "Augerat B, 1995", + + "Christofides and ..." ... [TRUNCATED] + + > ggMarginal(ggplot(merge(result, description, by = "group"), + + aes(x = n_site, y = clarke_wright_perf_xi, color = group_desc)) + + + geom_poi .... [TRUNCATED] + + When sourcing ‘clarke_wright_performance.R’: + Error: Theme element `plot.margin` must have class . + Execution halted + + ‘clarke_wright_performance.Rmd’ using ‘UTF-8’... failed + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + ... + --- re-building ‘clarke_wright_performance.Rmd’ using rmarkdown + + Quitting from lines 69-97 [perf_scale_based_graph] (clarke_wright_performance.Rmd) + Error: processing vignette 'clarke_wright_performance.Rmd' failed with diagnostics: + Theme element `plot.margin` must have class . + --- failed re-building ‘clarke_wright_performance.Rmd’ + + SUMMARY: processing the following file failed: + ‘clarke_wright_performance.Rmd’ + + Error: Vignette re-building failed. + Execution halted + ``` + +# heuristicsmineR + +
+ +* Version: 0.3.0 +* GitHub: https://github.com/bupaverse/heuristicsmineR +* Source code: https://github.com/cran/heuristicsmineR +* Date/Publication: 2023-04-04 13:20:06 UTC +* Number of recursive dependencies: 106 + +Run `revdepcheck::cloud_details(, "heuristicsmineR")` for more info + +
+ +## Newly broken + +* checking installed package size ... NOTE + ``` + installed size is 5.4Mb + sub-directories of 1Mb or more: + data 2.0Mb + libs 3.1Mb + ``` + +# HistDAWass + +
+ +* Version: 1.0.8 +* GitHub: NA +* Source code: https://github.com/cran/HistDAWass +* Date/Publication: 2024-01-24 17:42:31 UTC +* Number of recursive dependencies: 111 + +Run `revdepcheck::cloud_details(, "HistDAWass")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘HistDAWass-Ex.R’ failed + The error most likely occurred in: + + > ### Name: plot-HTS + > ### Title: Method plot for a histogram time series + > ### Aliases: plot-HTS plot,HTS-method + > + > ### ** Examples + > + > plot(subsetHTS(RetHTS, from = 1, to = 10)) # plots RetHTS dataset + ... + 4. └─HistDAWass:::plot.HTS.1v(x, type = type, border = border, maxno.perplot = maxno.perplot) + 5. └─HistDAWass:::multiplot(listofP) + 6. ├─base::print(plots[[1]]) + 7. └─ggplot2:::print.ggplot(plots[[1]]) + 8. ├─ggplot2::ggplot_gtable(data) + 9. └─ggplot2:::ggplot_gtable.ggplot_built(data) + 10. └─ggplot2::calc_element("plot.margin", theme) + 11. └─cli::cli_abort(...) + 12. └─rlang::abort(...) + Execution halted + ``` + +## In both + +* checking installed package size ... NOTE + ``` + installed size is 9.3Mb + sub-directories of 1Mb or more: + R 1.5Mb + data 2.0Mb + libs 5.6Mb + ``` + +# huito + +
+ +* Version: 0.2.4 +* GitHub: https://github.com/flavjack/huito +* Source code: https://github.com/cran/huito +* Date/Publication: 2023-10-25 16:30:02 UTC +* Number of recursive dependencies: 137 + +Run `revdepcheck::cloud_details(, "huito")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘huito-Ex.R’ failed + The error most likely occurred in: + + > ### Name: include_shape + > ### Title: Shape layer + > ### Aliases: include_shape + > + > ### ** Examples + > + > + ... + 5. └─cowplot::draw_plot(...) + 6. ├─cowplot::as_grob(plot) + 7. └─cowplot:::as_grob.ggplot(plot) + 8. └─ggplot2::ggplotGrob(plot) + 9. ├─ggplot2::ggplot_gtable(ggplot_build(x)) + 10. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) + 11. └─ggplot2::calc_element("plot.margin", theme) + 12. └─cli::cli_abort(...) + 13. └─rlang::abort(...) + Execution halted + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘germinar.Rmd’ using rmarkdown + + Quitting from lines 67-69 [unnamed-chunk-2] (germinar.Rmd) + Error: processing vignette 'germinar.Rmd' failed with diagnostics: + Theme element `plot.margin` must have class . + --- failed re-building ‘germinar.Rmd’ + + --- re-building ‘huito.Rmd’ using rmarkdown + --- finished re-building ‘huito.Rmd’ + ... + Quitting from lines 68-70 [unnamed-chunk-2] (stickers.Rmd) + Error: processing vignette 'stickers.Rmd' failed with diagnostics: + Theme element `plot.margin` must have class . + --- failed re-building ‘stickers.Rmd’ + + SUMMARY: processing the following files failed: + ‘germinar.Rmd’ ‘labels.Rmd’ ‘stickers.Rmd’ + + Error: Vignette re-building failed. + Execution halted + ``` + +## In both + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘germinar.Rmd’ + ... + > huito_fonts(font) + + > label <- label_layout(size = c(5.08, 5.08), border_width = 0, + + background = "#b1d842") %>% include_image(value = "https://germinar.inkaverse.c ..." ... [TRUNCATED] + + > label %>% label_print(mode = "preview") + + ... + > label %>% label_print(mode = "preview") + + When sourcing ‘stickers.R’: + Error: Theme element `plot.margin` must have class . + Execution halted + + ‘germinar.Rmd’ using ‘UTF-8’... failed + ‘huito.Rmd’ using ‘UTF-8’... failed + ‘labels.Rmd’ using ‘UTF-8’... failed + ‘stickers.Rmd’ using ‘UTF-8’... failed + ``` + +# hurricaneexposure + +
+ +* Version: 0.1.1 +* GitHub: https://github.com/geanders/hurricaneexposure +* Source code: https://github.com/cran/hurricaneexposure +* Date/Publication: 2020-02-13 14:30:02 UTC +* Number of recursive dependencies: 77 + +Run `revdepcheck::cloud_details(, "hurricaneexposure")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘hurricaneexposure-Ex.R’ failed + The error most likely occurred in: + + > ### Name: default_map + > ### Title: Create a default map with eastern US states + > ### Aliases: default_map + > + > ### ** Examples + > + > default_map() + ... + Backtrace: + ▆ + 1. ├─base (local) ``(x) + 2. └─ggplot2:::print.ggplot(x) + 3. ├─ggplot2::ggplot_gtable(data) + 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) + 5. └─ggplot2::calc_element("plot.margin", theme) + 6. └─cli::cli_abort(...) + 7. └─rlang::abort(...) + Execution halted + ``` + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘hurricaneexposure.Rmd’ + ... + + > map_event_exposure(storm = "Floyd-1999", event_type = "flood") + + > map_event_exposure(storm = "Ivan-2004", event_type = "tornado") + + > map_tracks(storms = "Floyd-1999") + + When sourcing ‘hurricaneexposure.R’: + Error: Theme element `plot.margin` must have class . + Execution halted + + ‘hurricaneexposure.Rmd’ using ‘UTF-8’... failed + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘hurricaneexposure.Rmd’ using rmarkdown + ``` + +## In both + +* checking dependencies in R code ... NOTE + ``` + Namespace in Imports field not imported from: ‘mapproj’ + All declared Imports should be used. + ``` + +* checking LazyData ... NOTE + ``` + 'LazyData' is specified without a 'data' directory + ``` + +# HVT + +
+ +* Version: 24.5.2 +* GitHub: https://github.com/Mu-Sigma/HVT +* Source code: https://github.com/cran/HVT +* Date/Publication: 2024-05-15 08:50:21 UTC +* Number of recursive dependencies: 200 + +Run `revdepcheck::cloud_details(, "HVT")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘HVT-Ex.R’ failed + The error most likely occurred in: + + > ### Name: getTransitionProbability + > ### Title: Creating Transition Probabilities list + > ### Aliases: getTransitionProbability + > ### Keywords: Transition_or_Prediction + > + > ### ** Examples + > + ... + Ignoring unknown parameters: `check_overlap` + Scale for x is already present. + Adding another scale for x, which will replace the existing scale. + Scale for y is already present. + Adding another scale for y, which will replace the existing scale. + Warning in geom_polygon(data = boundaryCoords2, aes(x = bp.x, y = bp.y, : + Ignoring unknown aesthetics: text + Error in pm[[2]] : subscript out of bounds + Calls: scoreHVT -> -> ggplotly.ggplot -> gg2list + Execution halted + ``` + +# hydraulics + +
+ +* Version: 0.7.0 +* GitHub: https://github.com/EdM44/hydraulics +* Source code: https://github.com/cran/hydraulics +* Date/Publication: 2024-03-06 13:10:08 UTC +* Number of recursive dependencies: 70 + +Run `revdepcheck::cloud_details(, "hydraulics")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘hydraulics-Ex.R’ failed + The error most likely occurred in: + + > ### Name: moody + > ### Title: Creates a Moody diagram with optional manually added points + > ### Aliases: moody + > + > ### ** Examples + > + > + ... + Backtrace: + ▆ + 1. └─hydraulics::moody() + 2. └─ggplot2::ggplotGrob(p4) + 3. ├─ggplot2::ggplot_gtable(ggplot_build(x)) + 4. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) + 5. └─ggplot2::calc_element("plot.margin", theme) + 6. └─cli::cli_abort(...) + 7. └─rlang::abort(...) + Execution halted + ``` + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘hydraulics_vignette.Rmd’ + ... + Mean Roughness, ks = 0.000434 m + > Re_values <- unlist((as.data.frame(t(ans)))$Re) + + > f_values <- unlist((as.data.frame(t(ans)))$f) + + > moody(Re = Re_values, f = f_values) + + When sourcing ‘hydraulics_vignette.R’: + Error: Theme element `plot.margin` must have class . + Execution halted + + ‘hydraulics_vignette.Rmd’ using ‘UTF-8’... failed + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘hydraulics_vignette.Rmd’ using rmarkdown + ``` + +# hyperSpec + +
+ +* Version: 0.100.2 +* GitHub: https://github.com/r-hyperspec/hyperSpec +* Source code: https://github.com/cran/hyperSpec +* Date/Publication: 2024-05-01 16:02:11 UTC +* Number of recursive dependencies: 141 + +Run `revdepcheck::cloud_details(, "hyperSpec")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘hyperSpec-Ex.R’ failed + The error most likely occurred in: + + > ### Name: qplotmixmap + > ### Title: qplotmap with colour mixing for multivariate overlay + > ### Aliases: qplotmixmap + > + > ### ** Examples + > + > chondro <- chondro - spc.fit.poly.below (chondro) + ... + 2. └─hyperSpec::legendright(p, l) + 3. ├─base::print(l, viewport(layout.pos.col = 2), newpage = FALSE) + 4. ├─base::print(l, viewport(layout.pos.col = 2), newpage = FALSE) + 5. └─ggplot2:::print.ggplot(l, viewport(layout.pos.col = 2), newpage = FALSE) + 6. ├─ggplot2::ggplot_gtable(data) + 7. └─ggplot2:::ggplot_gtable.ggplot_built(data) + 8. └─ggplot2::calc_element("plot.margin", theme) + 9. └─cli::cli_abort(...) + 10. └─rlang::abort(...) + Execution halted + ``` + +# hypsoLoop + +
+ +* Version: 0.2.0 +* GitHub: NA +* Source code: https://github.com/cran/hypsoLoop +* Date/Publication: 2022-02-08 09:00:02 UTC +* Number of recursive dependencies: 97 + +Run `revdepcheck::cloud_details(, "hypsoLoop")` for more info + +
+ +## Newly broken + +* checking whether package ‘hypsoLoop’ can be installed ... WARNING + ``` + Found the following significant warnings: + Warning: replacing previous import ‘ggplot2::set_theme’ by ‘sjPlot::set_theme’ when loading ‘hypsoLoop’ + See ‘/tmp/workdir/hypsoLoop/new/hypsoLoop.Rcheck/00install.out’ for details. + ``` + +# ICvectorfields + +
+ +* Version: 0.1.2 +* GitHub: https://github.com/goodsman/ICvectorfields +* Source code: https://github.com/cran/ICvectorfields +* Date/Publication: 2022-02-26 22:30:02 UTC +* Number of recursive dependencies: 93 + +Run `revdepcheck::cloud_details(, "ICvectorfields")` for more info + +
+ +## Newly broken + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘Using_ICvectorfields.Rmd’ + ... + + > SimVF + Warning: The `scale_name` argument of `continuous_scale()` is deprecated as of ggplot2 + 3.5.0. + Warning: The S3 guide system was deprecated in ggplot2 3.5.0. + ℹ It has been replaced by a ggproto system that can be extended. + + When sourcing ‘Using_ICvectorfields.R’: + Error: argument "theme" is missing, with no default + Execution halted + + ‘Using_ICvectorfields.Rmd’ using ‘UTF-8’... failed + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘Using_ICvectorfields.Rmd’ using rmarkdown + ``` + +# idiogramFISH + +
+ +* Version: 2.0.13 +* GitHub: NA +* Source code: https://github.com/cran/idiogramFISH +* Date/Publication: 2023-08-22 16:50:02 UTC +* Number of recursive dependencies: 170 + +Run `revdepcheck::cloud_details(, "idiogramFISH")` for more info + +
+ +## Newly broken + +* checking installed package size ... NOTE + ``` + installed size is 5.1Mb + sub-directories of 1Mb or more: + R 1.5Mb + doc 2.0Mb + ``` + +## In both + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘index.Rmd’ + ... + > if (requireNamespace("RCurl", quietly = TRUE)) { + + v <- sub("Version: ", "", readLines("../DESCRIPTION")[3]) + + pkg <- "idiogramFISH" + + l .... [TRUNCATED] + Warning in file(con, "r") : + cannot open file '../DESCRIPTION': No such file or directory + + When sourcing ‘index.R’: + Error: cannot open the connection + Execution halted + + ‘AVignette.Rmd’ using ‘UTF-8’... OK + ‘index.Rmd’ using ‘UTF-8’... failed + ``` + +# idopNetwork + +
+ +* Version: 0.1.2 +* GitHub: https://github.com/cxzdsa2332/idopNetwork +* Source code: https://github.com/cran/idopNetwork +* Date/Publication: 2023-04-18 06:50:02 UTC +* Number of recursive dependencies: 77 + +Run `revdepcheck::cloud_details(, "idopNetwork")` for more info + +
+ +## Newly broken + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘idopNetwork_vignette.Rmd’ + ... + + > df = data_cleaning(gut_microbe) + + > result1 = test_result$d1_power_fitting + + > power_equation_plot(result1) + + When sourcing ‘idopNetwork_vignette.R’: + Error: Theme element `plot.margin` must have class . + Execution halted + + ‘idopNetwork_vignette.Rmd’ using ‘UTF-8’... failed + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + ... + --- re-building ‘idopNetwork_vignette.Rmd’ using rmarkdown + + Quitting from lines 86-87 [unnamed-chunk-9] (idopNetwork_vignette.Rmd) + Error: processing vignette 'idopNetwork_vignette.Rmd' failed with diagnostics: + Theme element `plot.margin` must have class . + --- failed re-building ‘idopNetwork_vignette.Rmd’ + + SUMMARY: processing the following file failed: + ‘idopNetwork_vignette.Rmd’ + + Error: Vignette re-building failed. + Execution halted + ``` + +# iglu + +
+ +* Version: 4.0.0 +* GitHub: https://github.com/irinagain/iglu +* Source code: https://github.com/cran/iglu +* Date/Publication: 2024-02-23 17:50:02 UTC +* Number of recursive dependencies: 124 + +Run `revdepcheck::cloud_details(, "iglu")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘iglu-Ex.R’ failed + The error most likely occurred in: + + > ### Name: agp + > ### Title: Display Ambulatory Glucose Profile (AGP) statistics for selected + > ### subject + > ### Aliases: agp + > + > ### ** Examples + > + ... + 4. └─base::lapply(x$plots, plot_table, guides = guides) + 5. ├─patchwork (local) FUN(X[[i]], ...) + 6. └─patchwork:::plot_table.ggplot(X[[i]], ...) + 7. └─ggplot2::ggplotGrob(x) + 8. ├─ggplot2::ggplot_gtable(ggplot_build(x)) + 9. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) + 10. └─ggplot2::calc_element("plot.margin", theme) + 11. └─cli::cli_abort(...) + 12. └─rlang::abort(...) + Execution halted + ``` + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘AGP_and_Episodes.Rmd’ + ... + + > knitr::opts_chunk$set(collapse = TRUE, comment = "#>") + + > library(iglu) + + > agp(example_data_1_subject) + + When sourcing ‘AGP_and_Episodes.R’: + Error: Theme element `plot.margin` must have class . + Execution halted + + ‘AGP_and_Episodes.Rmd’ using ‘UTF-8’... failed + ‘MAGE.Rmd’ using ‘UTF-8’... OK + ‘iglu.Rmd’ using ‘UTF-8’... OK + ‘lasagna_plots.Rmd’ using ‘UTF-8’... OK + ‘metrics_list.Rmd’ using ‘UTF-8’... OK + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘AGP_and_Episodes.Rmd’ using rmarkdown + + Quitting from lines 24-25 [unnamed-chunk-1] (AGP_and_Episodes.Rmd) + Error: processing vignette 'AGP_and_Episodes.Rmd' failed with diagnostics: + Theme element `plot.margin` must have class . + --- failed re-building ‘AGP_and_Episodes.Rmd’ + + --- re-building ‘MAGE.Rmd’ using rmarkdown + ``` + +# igoR + +
+ +* Version: 0.2.0 +* GitHub: https://github.com/dieghernan/igoR +* Source code: https://github.com/cran/igoR +* Date/Publication: 2024-02-05 15:30:02 UTC +* Number of recursive dependencies: 67 + +Run `revdepcheck::cloud_details(, "igoR")` for more info + +
+ +## Newly broken + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘igoR.Rmd’ + ... + + mutate(variable = factor(variable, levels = c("Total IGOs", + + "Numb ..." ... [TRUNCATED] + + > ggplot(all_by_year, aes(x = year, y = value)) + geom_line(color = "black", + + aes(linetype = variable)) + scale_x_continuous(limits = c(1800, + + .... [TRUNCATED] + + When sourcing ‘igoR.R’: + Error: Theme element `plot.margin` must have class . + Execution halted + + ‘igoR.Rmd’ using ‘UTF-8’... failed + ‘mapping.Rmd’ using ‘UTF-8’... OK + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + ... + --- re-building ‘igoR.Rmd’ using rmarkdown + + Quitting from lines 123-150 [Fig1] (igoR.Rmd) + Error: processing vignette 'igoR.Rmd' failed with diagnostics: + Theme element `plot.margin` must have class . + --- failed re-building ‘igoR.Rmd’ + + --- re-building ‘mapping.Rmd’ using rmarkdown + --- finished re-building ‘mapping.Rmd’ + + SUMMARY: processing the following file failed: + ‘igoR.Rmd’ + + Error: Vignette re-building failed. + Execution halted + ``` + +## In both + +* checking data for non-ASCII characters ... NOTE + ``` + Note: found 160 marked UTF-8 strings + ``` + +# immunarch + +
+ +* Version: 0.9.1 +* GitHub: https://github.com/immunomind/immunarch +* Source code: https://github.com/cran/immunarch +* Date/Publication: 2024-03-18 19:10:06 UTC +* Number of recursive dependencies: 194 + +Run `revdepcheck::cloud_details(, "immunarch")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘immunarch-Ex.R’ failed + The error most likely occurred in: + + > ### Name: pubRepStatistics + > ### Title: Statistics of number of public clonotypes for each possible + > ### combinations of repertoires + > ### Aliases: pubRepStatistics + > + > ### ** Examples + > + ... + 5. ├─base::suppressMessages(...) + 6. │ └─base::withCallingHandlers(...) + 7. └─UpSetR:::Make_main_bar(...) + 8. └─ggplot2::ggplotGrob(Main_bar_plot) + 9. ├─ggplot2::ggplot_gtable(ggplot_build(x)) + 10. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) + 11. └─ggplot2::calc_element("plot.margin", theme) + 12. └─cli::cli_abort(...) + 13. └─rlang::abort(...) + Execution halted + ``` + +## In both + +* checking installed package size ... NOTE + ``` + installed size is 10.5Mb + sub-directories of 1Mb or more: + R 1.5Mb + data 5.5Mb + doc 1.6Mb + ``` + +# immuneSIM + +
+ +* Version: 0.8.7 +* GitHub: https://github.com/GreiffLab/immuneSIM +* Source code: https://github.com/cran/immuneSIM +* Date/Publication: 2019-09-27 10:30:06 UTC +* Number of recursive dependencies: 66 + +Run `revdepcheck::cloud_details(, "immuneSIM")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘immuneSIM-Ex.R’ failed + The error most likely occurred in: + + > ### Name: plot_repertoire_A_vs_B + > ### Title: Comparative plots of main repertoire features of two input + > ### repertoires (length distribution, amino acid frequency, VDJ usage, + > ### kmer occurrence) + > ### Aliases: plot_repertoire_A_vs_B + > + > ### ** Examples + ... + ▆ + 1. └─immuneSIM::plot_repertoire_A_vs_B(...) + 2. ├─base::print(plots_aa_freq_list_imgt[[1]], vp = vplayout(1, 1)) + 3. └─ggplot2:::print.ggplot(...) + 4. ├─ggplot2::ggplot_gtable(data) + 5. └─ggplot2:::ggplot_gtable.ggplot_built(data) + 6. └─ggplot2::calc_element("plot.margin", theme) + 7. └─cli::cli_abort(...) + 8. └─rlang::abort(...) + Execution halted + ``` + +## In both + +* checking installed package size ... NOTE + ``` + installed size is 8.2Mb + sub-directories of 1Mb or more: + R 8.1Mb + ``` + +* checking LazyData ... NOTE + ``` + 'LazyData' is specified without a 'data' directory + ``` + +# iNEXT.4steps + +
+ +* Version: 1.0.0 +* GitHub: https://github.com/KaiHsiangHu/iNEXT.4steps +* Source code: https://github.com/cran/iNEXT.4steps +* Date/Publication: 2024-04-10 20:00:05 UTC +* Number of recursive dependencies: 106 + +Run `revdepcheck::cloud_details(, "iNEXT.4steps")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘iNEXT.4steps-Ex.R’ failed + The error most likely occurred in: + + > ### Name: ggCompleteness + > ### Title: ggplot for depicting sample completeness profiles + > ### Aliases: ggCompleteness + > + > ### ** Examples + > + > + ... + Backtrace: + ▆ + 1. ├─base (local) ``(x) + 2. └─ggplot2:::print.ggplot(x) + 3. ├─ggplot2::ggplot_gtable(data) + 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) + 5. └─ggplot2::calc_element("plot.margin", theme) + 6. └─cli::cli_abort(...) + 7. └─rlang::abort(...) + Execution halted + ``` + +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(iNEXT.4steps) + > + > test_check("iNEXT.4steps") + [ FAIL 2 | WARN 5 | SKIP 0 | PASS 10 ] + + ══ Failed tests ════════════════════════════════════════════════════════════════ + ... + 3. └─ggpubr:::.get_legend(p, position = position) + 4. ├─ggplot2::ggplot_gtable(ggplot_build(p)) + 5. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(p)) + 6. └─ggplot2::calc_element("plot.margin", theme) + 7. └─cli::cli_abort(...) + 8. └─rlang::abort(...) + + [ FAIL 2 | WARN 5 | SKIP 0 | PASS 10 ] + Error: Test failures + Execution halted + ``` + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘Vignette-iNEXT.4steps-April10.Rmd’ + ... + + + > data(Data_spider) + + > Four_Steps_out1 <- iNEXT4steps(data = Data_spider, + + datatype = "abundance") + + When sourcing ‘Vignette-iNEXT.4steps-April10.R’: + Error: Theme element `plot.margin` must have class . + Execution halted + + ‘Vignette-iNEXT.4steps-April10.Rmd’ using ‘UTF-8’... failed + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + ... + --- re-building ‘Vignette-iNEXT.4steps-April10.Rmd’ using rmarkdown + + Quitting from lines 209-213 [unnamed-chunk-8] (Vignette-iNEXT.4steps-April10.Rmd) + Error: processing vignette 'Vignette-iNEXT.4steps-April10.Rmd' failed with diagnostics: + Theme element `plot.margin` must have class . + --- failed re-building ‘Vignette-iNEXT.4steps-April10.Rmd’ + + SUMMARY: processing the following file failed: + ‘Vignette-iNEXT.4steps-April10.Rmd’ + + Error: Vignette re-building failed. + Execution halted + ``` + +# iNEXT.beta3D + +
+ +* Version: 1.0.2 +* GitHub: https://github.com/AnneChao/iNEXT.beta3D +* Source code: https://github.com/cran/iNEXT.beta3D +* Date/Publication: 2024-04-17 19:40:11 UTC +* Number of recursive dependencies: 88 + +Run `revdepcheck::cloud_details(, "iNEXT.beta3D")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘iNEXT.beta3D-Ex.R’ failed + The error most likely occurred in: + + > ### Name: ggiNEXTbeta3D + > ### Title: ggplot2 extension for the iNEXTbeta3D object + > ### Aliases: ggiNEXTbeta3D + > + > ### ** Examples + > + > + ... + Backtrace: + ▆ + 1. ├─base (local) ``(x) + 2. └─ggplot2:::print.ggplot(x) + 3. ├─ggplot2::ggplot_gtable(data) + 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) + 5. └─ggplot2::calc_element("plot.margin", theme) + 6. └─cli::cli_abort(...) + 7. └─rlang::abort(...) + Execution halted + ``` + +## In both + +* checking re-building of vignette outputs ... WARNING + ``` + Error(s) in re-building vignettes: + ... + --- re-building ‘Introduction.Rnw’ using Sweave + Error: processing vignette 'Introduction.Rnw' failed with diagnostics: + Running 'texi2dvi' on 'Introduction.tex' failed. + LaTeX errors: + ! LaTeX Error: File `pdfpages.sty' not found. + + Type X to quit or to proceed, + or enter new name. (Default extension: sty) + ... + l.4 ^^M + + ! ==> Fatal error occurred, no output PDF file produced! + --- failed re-building ‘Introduction.Rnw’ + + SUMMARY: processing the following file failed: + ‘Introduction.Rnw’ + + Error: Vignette re-building failed. + Execution halted + ``` + +# insurancerating + +
+ +* Version: 0.7.4 +* GitHub: https://github.com/mharinga/insurancerating +* Source code: https://github.com/cran/insurancerating +* Date/Publication: 2024-05-20 11:30:03 UTC +* Number of recursive dependencies: 133 + +Run `revdepcheck::cloud_details(, "insurancerating")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘insurancerating-Ex.R’ failed + The error most likely occurred in: + + > ### Name: autoplot.univariate + > ### Title: Automatically create a ggplot for objects obtained from + > ### univariate() + > ### Aliases: autoplot.univariate + > + > ### ** Examples + > + ... + > xzip <- univariate(MTPL, x = bm, severity = amount, nclaims = nclaims, + + exposure = exposure, by = zip) + > autoplot(xzip, show_plots = 1:2) + Warning: Removed 16 rows containing missing values or values outside the scale range + (`geom_point()`). + Warning: Removed 5 rows containing missing values or values outside the scale range + (`geom_line()`). + Error in identicalUnits(x) : object is not a unit + Calls: ... assemble_guides -> guides_build -> unit.c -> identicalUnits + Execution halted + ``` + +# inTextSummaryTable + +
+ +* Version: 3.3.2 +* GitHub: https://github.com/openanalytics/inTextSummaryTable +* Source code: https://github.com/cran/inTextSummaryTable +* Date/Publication: 2024-03-09 16:20:02 UTC +* Number of recursive dependencies: 120 + +Run `revdepcheck::cloud_details(, "inTextSummaryTable")` for more info + +
+ +## Newly broken + +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(inTextSummaryTable) + > + > test_check("inTextSummaryTable") + [ FAIL 59 | WARN 1 | SKIP 0 | PASS 881 ] + + ══ Failed tests ════════════════════════════════════════════════════════════════ + ... + 5. │ └─rlang::eval_bare(quo_get_expr(.quo), quo_get_env(.quo)) + 6. └─inTextSummaryTable::subjectProfileSummaryPlot(...) + 7. ├─base::do.call(plyr::rbind.fill, ggplot_build(gg)$data) + 8. └─plyr (local) ``(``, ``) + 9. └─plyr:::output_template(dfs, nrows) + 10. └─plyr:::allocate_column(df[[var]], nrows, dfs, var) + + [ FAIL 59 | WARN 1 | SKIP 0 | PASS 881 ] + Error: Test failures + Execution halted + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘inTextSummaryTable-advanced.Rmd’ using rmarkdown + --- finished re-building ‘inTextSummaryTable-advanced.Rmd’ + + --- re-building ‘inTextSummaryTable-aesthetics.Rmd’ using rmarkdown + + Quitting from lines 211-224 [aesthetics-defaultsVisualization] (inTextSummaryTable-aesthetics.Rmd) + Error: processing vignette 'inTextSummaryTable-aesthetics.Rmd' failed with diagnostics: + Problem while setting up geom aesthetics. + ℹ Error occurred in the 2nd layer. + ... + ! Aesthetics must be either length 1 or the same as the data (28). + ✖ Fix the following mappings: `size`. + --- failed re-building ‘inTextSummaryTable-visualization.Rmd’ + + SUMMARY: processing the following files failed: + ‘inTextSummaryTable-aesthetics.Rmd’ + ‘inTextSummaryTable-visualization.Rmd’ + + Error: Vignette re-building failed. + Execution halted + ``` + +## In both + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘inTextSummaryTable-aesthetics.Rmd’ + ... + > subjectProfileSummaryPlot(data = summaryTable, xVar = "visit", + + colorVar = "TRT") + + When sourcing ‘inTextSummaryTable-aesthetics.R’: + Error: Problem while setting up geom aesthetics. + ℹ Error occurred in the 2nd layer. + Caused by error in `check_aesthetics()`: + ... + ✖ Fix the following mappings: `size`. + Execution halted + + ‘inTextSummaryTable-advanced.Rmd’ using ‘UTF-8’... OK + ‘inTextSummaryTable-aesthetics.Rmd’ using ‘UTF-8’... failed + ‘inTextSummaryTable-createTables.Rmd’ using ‘UTF-8’... OK + ‘inTextSummaryTable-exportTables.Rmd’ using ‘UTF-8’... OK + ‘inTextSummaryTable-introduction.Rmd’ using ‘UTF-8’... OK + ‘inTextSummaryTable-standardTables.Rmd’ using ‘UTF-8’... OK + ‘inTextSummaryTable-visualization.Rmd’ using ‘UTF-8’... failed + ``` + +* checking installed package size ... NOTE + ``` + installed size is 10.5Mb + sub-directories of 1Mb or more: + doc 9.9Mb + ``` + +# inventorize + +
+ +* Version: 1.1.1 +* GitHub: NA +* Source code: https://github.com/cran/inventorize +* Date/Publication: 2022-05-31 22:20:09 UTC +* Number of recursive dependencies: 71 + +Run `revdepcheck::cloud_details(, "inventorize")` for more info + +
+ +## Newly broken + +* checking whether package ‘inventorize’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/inventorize/new/inventorize.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘inventorize’ ... +** package ‘inventorize’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** byte-compile and prepare package for lazy loading +Error in pm[[2]] : subscript out of bounds +Error: unable to load R code in package ‘inventorize’ +Execution halted +ERROR: lazy loading failed for package ‘inventorize’ +* removing ‘/tmp/workdir/inventorize/new/inventorize.Rcheck/inventorize’ + + +``` +### CRAN + +``` +* installing *source* package ‘inventorize’ ... +** package ‘inventorize’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** byte-compile and prepare package for lazy loading +Warning in qgamma(service_level, alpha, beta) : NaNs produced +Warning in qgamma(service_level, alpha, beta) : NaNs produced +** help +*** installing help indices +** building package indices +** testing if installed package can be loaded from temporary location +** testing if installed package can be loaded from final location +** testing if installed package keeps a record of temporary installation path +* DONE (inventorize) + + +``` +# jskm + +
+ +* Version: 0.5.3 +* GitHub: https://github.com/jinseob2kim/jstable +* Source code: https://github.com/cran/jskm +* Date/Publication: 2024-01-26 06:20:08 UTC +* Number of recursive dependencies: 103 + +Run `revdepcheck::cloud_details(, "jskm")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘jskm-Ex.R’ failed + The error most likely occurred in: + + > ### Name: jskm + > ### Title: Creates a Kaplan-Meier plot for survfit object. + > ### Aliases: jskm + > + > ### ** Examples + > + > library(survival) + ... + Backtrace: + ▆ + 1. ├─base (local) ``(x) + 2. └─ggplot2:::print.ggplot(x) + 3. ├─ggplot2::ggplot_gtable(data) + 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) + 5. └─ggplot2::calc_element("plot.margin", theme) + 6. └─cli::cli_abort(...) + 7. └─rlang::abort(...) + Execution halted + ``` + +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(jskm) + > + > test_check("jskm") + [ FAIL 2 | WARN 1 | SKIP 0 | PASS 2 ] + + ══ Failed tests ════════════════════════════════════════════════════════════════ + ... + label_size = .lab$size, label_fontfamily = .lab$family, label_fontface = .lab$face, + label_colour = .lab$color, label_x = .lab$label.x, label_y = .lab$label.y, + hjust = .lab$hjust, vjust = .lab$vjust, align = align, rel_widths = widths, + rel_heights = heights, legend = legend, common.legend.grob = legend.grob)`: ℹ In index: 1. + Caused by error in `ggplot_gtable()`: + ! Theme element `plot.margin` must have class . + + [ FAIL 2 | WARN 1 | SKIP 0 | PASS 2 ] + Error: Test failures + Execution halted + ``` + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘jskm.Rmd’ + ... + > data(colon) + Warning in data(colon) : data set ‘colon’ not found + + > fit <- survfit(Surv(time, status) ~ rx, data = colon) + + > jskm(fit) + + When sourcing ‘jskm.R’: + Error: Theme element `plot.margin` must have class . + Execution halted + + ‘jskm.Rmd’ using ‘UTF-8’... failed + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + ... + --- re-building ‘jskm.Rmd’ using rmarkdown + + Quitting from lines 35-47 [unnamed-chunk-1] (jskm.Rmd) + Error: processing vignette 'jskm.Rmd' failed with diagnostics: + Theme element `plot.margin` must have class . + --- failed re-building ‘jskm.Rmd’ + + SUMMARY: processing the following file failed: + ‘jskm.Rmd’ + + Error: Vignette re-building failed. + Execution halted + ``` + +# KaradaColor + +
+ +* Version: 0.1.5 +* GitHub: https://github.com/KaradaGood/KaradaColor +* Source code: https://github.com/cran/KaradaColor +* Date/Publication: 2023-04-21 08:02:37 UTC +* Number of recursive dependencies: 40 + +Run `revdepcheck::cloud_details(, "KaradaColor")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘KaradaColor-Ex.R’ failed + The error most likely occurred in: + + > ### Name: kg_get_color + > ### Title: Get color palette data + > ### Aliases: kg_get_color kg_get_palette + > + > ### ** Examples + > + > library("scales") + ... + Backtrace: + ▆ + 1. ├─base (local) ``(x) + 2. └─ggplot2:::print.ggplot(x) + 3. ├─ggplot2::ggplot_gtable(data) + 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) + 5. └─ggplot2::calc_element("plot.margin", theme) + 6. └─cli::cli_abort(...) + 7. └─rlang::abort(...) + Execution halted + ``` + +# karel + +
+ +* Version: 0.1.1 +* GitHub: https://github.com/mpru/karel +* Source code: https://github.com/cran/karel +* Date/Publication: 2022-03-26 21:50:02 UTC +* Number of recursive dependencies: 90 + +Run `revdepcheck::cloud_details(, "karel")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘karel-Ex.R’ failed + The error most likely occurred in: + + > ### Name: acciones + > ### Title: Acciones que Karel puede realizar + > ### Aliases: acciones avanzar girar_izquierda poner_coso juntar_coso + > ### girar_derecha darse_vuelta + > + > ### ** Examples + > + ... + 1. └─karel::ejecutar_acciones() + 2. ├─base::suppressWarnings(...) + 3. │ └─base::withCallingHandlers(...) + 4. ├─gganimate::animate(...) + 5. └─gganimate:::animate.gganim(...) + 6. └─args$renderer(frames_vars$frame_source, args$fps) + 7. └─gganimate:::png_dim(frames[1]) + 8. └─cli::cli_abort("Provided file ({file}) does not exist") + 9. └─rlang::abort(...) + Execution halted + ``` + +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(karel) + > + > test_check("karel") + [ FAIL 2 | WARN 2 | SKIP 0 | PASS 78 ] + + ══ Failed tests ════════════════════════════════════════════════════════════════ + ... + 5. ├─gganimate::animate(...) + 6. └─gganimate:::animate.gganim(...) + 7. └─args$renderer(frames_vars$frame_source, args$fps) + 8. └─gganimate:::png_dim(frames[1]) + 9. └─cli::cli_abort("Provided file ({file}) does not exist") + 10. └─rlang::abort(...) + + [ FAIL 2 | WARN 2 | SKIP 0 | PASS 78 ] + Error: Test failures + Execution halted + ``` + +## In both + +* checking dependencies in R code ... NOTE + ``` + Namespace in Imports field not imported from: ‘gifski’ + All declared Imports should be used. + ``` + +# kDGLM + +
+ +* Version: 1.2.0 +* GitHub: https://github.com/silvaneojunior/kDGLM +* Source code: https://github.com/cran/kDGLM +* Date/Publication: 2024-05-25 09:50:03 UTC +* Number of recursive dependencies: 136 + +Run `revdepcheck::cloud_details(, "kDGLM")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘kDGLM-Ex.R’ failed + The error most likely occurred in: + + > ### Name: forecast.fitted_dlm + > ### Title: Auxiliary function for forecasting + > ### Aliases: forecast.fitted_dlm + > + > ### ** Examples + > + > + ... + > forecast(fitted.data, 24, + + chickenPox = list(Total = rep(175, 24)), # Optional + + Vaccine.1.Covariate = rep(TRUE, 24), + + Vaccine.2.Covariate = rep(TRUE, 24) + + ) + Scale for y is already present. + Adding another scale for y, which will replace the existing scale. + Error in pm[[2]] : subscript out of bounds + Calls: forecast ... lapply -> -> ggplotly.ggplot -> gg2list + Execution halted + ``` + +## In both + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘fitting.Rmd’ + ... + > outcome <- Multinom(p = c("p.1", "p.2"), data = chickenPox[, + + c(2, 3, 5)]) + + > fitted.model <- fit_model(structure * 2, chickenPox = outcome) + + > forecast(fitted.model, t = 24, plot = "base") + + When sourcing ‘fitting.R’: + Error: Error: Missing extra argument: Vaccine.1.Covariate + Execution halted + + ‘example1.Rmd’ using ‘UTF-8’... OK + ‘fitting.Rmd’ using ‘UTF-8’... failed + ‘intro.Rmd’ using ‘UTF-8’... OK + ‘outcomes.Rmd’ using ‘UTF-8’... OK + ‘structures.Rmd’ using ‘UTF-8’... OK + ``` + +# labsimplex + +
+ +* Version: 0.1.2 +* GitHub: NA +* Source code: https://github.com/cran/labsimplex +* Date/Publication: 2020-06-03 16:10:06 UTC +* Number of recursive dependencies: 68 + +Run `revdepcheck::cloud_details(, "labsimplex")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘labsimplex-Ex.R’ failed + The error most likely occurred in: + + > ### Name: addSimplex2Surface + > ### Title: Adds the simplex movements to a response surface contour + > ### Aliases: addSimplex2Surface + > + > ### ** Examples + > + > simplex <- exampleOptimization(surface = exampleSurfaceR2, + ... + Backtrace: + ▆ + 1. ├─base::print(p) + 2. └─ggplot2:::print.ggplot(p) + 3. ├─ggplot2::ggplot_gtable(data) + 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) + 5. └─ggplot2::calc_element("plot.margin", theme) + 6. └─cli::cli_abort(...) + 7. └─rlang::abort(...) + Execution halted + ``` + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘labsimplex.Rmd’ + ... + + 0.6, 0, 0)), phi = 30, theta = 30, ltheta = -120, expand = 0.6, + + xlab = "Te ..." ... [TRUNCATED] + + > (cont.surf <- cntr(surface = exampleSurfaceR2, length = 200)) + Warning: Removed 796 rows containing missing values or values outside the scale range + (`geom_tile()`). + + When sourcing ‘labsimplex.R’: + Error: Theme element `plot.margin` must have class . + Execution halted + + ‘labsimplex.Rmd’ using ‘UTF-8’... failed + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + ... + --- re-building ‘labsimplex.Rmd’ using rmarkdown + + Quitting from lines 66-69 [surfaces1] (labsimplex.Rmd) + Error: processing vignette 'labsimplex.Rmd' failed with diagnostics: + Theme element `plot.margin` must have class . + --- failed re-building ‘labsimplex.Rmd’ + + SUMMARY: processing the following file failed: + ‘labsimplex.Rmd’ + + Error: Vignette re-building failed. + Execution halted + ``` + +# landscapemetrics + +
+ +* Version: 2.1.2 +* GitHub: https://github.com/r-spatialecology/landscapemetrics +* Source code: https://github.com/cran/landscapemetrics +* Date/Publication: 2024-05-02 12:52:46 UTC +* Number of recursive dependencies: 96 + +Run `revdepcheck::cloud_details(, "landscapemetrics")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘landscapemetrics-Ex.R’ failed + The error most likely occurred in: + + > ### Name: show_cores + > ### Title: Show core area + > ### Aliases: show_cores + > + > ### ** Examples + > + > landscape <- terra::rast(landscapemetrics::landscape) + ... + Backtrace: + ▆ + 1. ├─base (local) ``(x) + 2. └─ggplot2:::print.ggplot(x) + 3. ├─ggplot2::ggplot_gtable(data) + 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) + 5. └─ggplot2::calc_element("plot.margin", theme) + 6. └─cli::cli_abort(...) + 7. └─rlang::abort(...) + Execution halted + ``` + +## In both + +* checking installed package size ... NOTE + ``` + installed size is 7.9Mb + sub-directories of 1Mb or more: + libs 6.3Mb + ``` + +# landscapetools + +
+ +* Version: 0.5.0 +* GitHub: https://github.com/ropensci/landscapetools +* Source code: https://github.com/cran/landscapetools +* Date/Publication: 2019-02-25 22:40:03 UTC +* Number of recursive dependencies: 75 + +Run `revdepcheck::cloud_details(, "landscapetools")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘landscapetools-Ex.R’ failed + The error most likely occurred in: + + > ### Name: util_merge + > ### Title: util_merge + > ### Aliases: util_merge util_merge.RasterLayer + > + > ### ** Examples + > + > x <- util_merge(gradient_landscape, random_landscape) + ... + Backtrace: + ▆ + 1. ├─base (local) ``(x) + 2. └─ggplot2:::print.ggplot(x) + 3. ├─ggplot2::ggplot_gtable(data) + 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) + 5. └─ggplot2::calc_element("plot.margin", theme) + 6. └─cli::cli_abort(...) + 7. └─rlang::abort(...) + Execution halted + ``` + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘overview.Rmd’ + ... + + > library(landscapetools) + + > show_landscape(gradient_landscape) + Loading required package: raster + Loading required package: sp + + When sourcing ‘overview.R’: + Error: Theme element `plot.margin` must have class . + Execution halted + + ‘overview.Rmd’ using ‘UTF-8’... failed + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + ... + --- re-building ‘overview.Rmd’ using rmarkdown + + Quitting from lines 31-46 [unnamed-chunk-1] (overview.Rmd) + Error: processing vignette 'overview.Rmd' failed with diagnostics: + Theme element `plot.margin` must have class . + --- failed re-building ‘overview.Rmd’ + + SUMMARY: processing the following file failed: + ‘overview.Rmd’ + + Error: Vignette re-building failed. + Execution halted + ``` + +# latentcor + +
+ +* Version: 2.0.1 +* GitHub: NA +* Source code: https://github.com/cran/latentcor +* Date/Publication: 2022-09-05 20:50:02 UTC +* Number of recursive dependencies: 143 + +Run `revdepcheck::cloud_details(, "latentcor")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘latentcor-Ex.R’ failed + The error most likely occurred in: + + > ### Name: latentcor + > ### Title: Estimate latent correlation for mixed types. + > ### Aliases: latentcor + > + > ### ** Examples + > + > # Example 1 - truncated data type, same type for all variables + ... + > R_approx = latentcor(X = X, types = "tru", method = "approx")$R + > proc.time() - start_time + user system elapsed + 0.020 0.000 0.021 + > # Heatmap for latent correlation matrix. + > Heatmap_R_approx = latentcor(X = X, types = "tru", method = "approx", + + showplot = TRUE)$plotR + Error in pm[[2]] : subscript out of bounds + Calls: latentcor ... %>% -> layout -> ggplotly -> ggplotly.ggplot -> gg2list + Execution halted + ``` + +# latte + +
+ +* Version: 0.2.1 +* GitHub: https://github.com/dkahle/latte +* Source code: https://github.com/cran/latte +* Date/Publication: 2019-03-25 10:50:03 UTC +* Number of recursive dependencies: 86 + +Run `revdepcheck::cloud_details(, "latte")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘latte-Ex.R’ failed + The error most likely occurred in: + + > ### Name: plot-matrix + > ### Title: Plot a matrix + > ### Aliases: plot-matrix plot_matrix + > + > ### ** Examples + > + > + ... + Backtrace: + ▆ + 1. ├─base (local) ``(x) + 2. └─ggplot2:::print.ggplot(x) + 3. ├─ggplot2::ggplot_gtable(data) + 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) + 5. └─ggplot2::calc_element("plot.margin", theme) + 6. └─cli::cli_abort(...) + 7. └─rlang::abort(...) + Execution halted + ``` + +## In both + +* checking LazyData ... NOTE + ``` + 'LazyData' is specified without a 'data' directory + ``` + +# lemon + +
+ +* Version: 0.4.9 +* GitHub: https://github.com/stefanedwards/lemon +* Source code: https://github.com/cran/lemon +* Date/Publication: 2024-02-08 08:00:08 UTC +* Number of recursive dependencies: 76 + +Run `revdepcheck::cloud_details(, "lemon")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘lemon-Ex.R’ failed + The error most likely occurred in: + + > ### Name: annotate_y_axis + > ### Title: Annotations on the axis + > ### Aliases: annotate_y_axis annotate_x_axis + > + > ### ** Examples + > + > library(ggplot2) + > + > p <- ggplot(mtcars, aes(mpg, hp, colour=disp)) + geom_point() + > + > l <- p + annotate_y_axis('mark at', y=200, tick=TRUE) + > l + Error in identicalUnits(x) : object is not a unit + Calls: ... polylineGrob -> is.unit -> unit.c -> identicalUnits + Execution halted + ``` + +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(lemon) + > + > + > if (TRUE) { + + test_check("lemon") + + } #else { + ... + 17. ├─grid::unit.c(unit(1, "npc"), unit(1, "npc") - tick.length) + 18. └─grid:::Ops.unit(unit(1, "npc"), tick.length) + 19. └─grid:::as.unit(e2) + + [ FAIL 1 | WARN 0 | SKIP 3 | PASS 138 ] + Deleting unused snapshots: + • facet/facet-rep-wrap-spacing.svg + • facet_aux/facet-rep-wrap.svg + Error: Test failures + Execution halted + ``` + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘capped-axes.Rmd’ + ... + > p + coord_capped_cart(bottom = "right") + + > p + coord_capped_cart(bottom = "right", left = "none") + + > ggplot(dat1, aes(gp, y)) + geom_point(position = position_jitter(width = 0.2, + + height = 0)) + coord_capped_cart(left = "none", bottom = bracke .... [TRUNCATED] + + ... + When sourcing ‘legends.R’: + Error: object is not coercible to a unit + Execution halted + + ‘capped-axes.Rmd’ using ‘UTF-8’... failed + ‘facet-rep-labels.Rmd’ using ‘UTF-8’... failed + ‘geoms.Rmd’ using ‘UTF-8’... OK + ‘gtable_show_lemonade.Rmd’ using ‘UTF-8’... OK + ‘legends.Rmd’ using ‘UTF-8’... failed + ‘lemon_print.Rmd’ using ‘UTF-8’... OK + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘capped-axes.Rmd’ using rmarkdown + ``` + +# lfproQC + +
+ +* Version: 0.1.0 +* GitHub: NA +* Source code: https://github.com/cran/lfproQC +* Date/Publication: 2024-05-23 16:10:02 UTC +* Number of recursive dependencies: 138 + +Run `revdepcheck::cloud_details(, "lfproQC")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘lfproQC-Ex.R’ failed + The error most likely occurred in: + + > ### Name: Boxplot_data + > ### Title: Creating Boxplot for a dataset + > ### Aliases: Boxplot_data + > + > ### ** Examples + > + > Boxplot_data(yeast_data) + Using Majority protein IDs as id variables + Warning: Removed 266 rows containing non-finite outside the scale range + (`stat_boxplot()`). + Error in pm[[2]] : subscript out of bounds + Calls: Boxplot_data -> -> ggplotly.ggplot -> gg2list + Execution halted + ``` + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘user_guide.Rmd’ + ... + > yeast$`Best combinations` + PCV_best_combination PEV_best_combination PMAD_best_combination + 1 knn_rlr lls_loess lls_rlr + + > Boxplot_data(yeast$knn_rlr_data) + Using Majority protein IDs as id variables + + When sourcing ‘user_guide.R’: + Error: subscript out of bounds + Execution halted + + ‘user_guide.Rmd’ using ‘UTF-8’... failed + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + ... + --- re-building ‘user_guide.Rmd’ using rmarkdown + + Quitting from lines 53-54 [unnamed-chunk-8] (user_guide.Rmd) + Error: processing vignette 'user_guide.Rmd' failed with diagnostics: + subscript out of bounds + --- failed re-building ‘user_guide.Rmd’ + + SUMMARY: processing the following file failed: + ‘user_guide.Rmd’ + + Error: Vignette re-building failed. + Execution halted + ``` + +## In both + +* checking installed package size ... NOTE + ``` + installed size is 6.2Mb + sub-directories of 1Mb or more: + doc 5.9Mb + ``` + +# LLSR + +
+ +* Version: 0.0.3.1 +* GitHub: https://github.com/diegofcoelho/LLSR +* Source code: https://github.com/cran/LLSR +* Date/Publication: 2021-02-17 18:20:02 UTC +* Number of recursive dependencies: 62 + +Run `revdepcheck::cloud_details(, "LLSR")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘LLSR-Ex.R’ failed + The error most likely occurred in: + + > ### Name: AQSys.plot + > ### Title: Dataset and Fitted Function plot + > ### Aliases: AQSys.plot + > + > ### ** Examples + > + > #Populating variable dataSET with binodal data + ... + ▆ + 1. └─LLSR::AQSys.plot(dataSET) + 2. ├─base::print(plot_image) + 3. └─ggplot2:::print.ggplot(plot_image) + 4. ├─ggplot2::ggplot_gtable(data) + 5. └─ggplot2:::ggplot_gtable.ggplot_built(data) + 6. └─ggplot2::calc_element("plot.margin", theme) + 7. └─cli::cli_abort(...) + 8. └─rlang::abort(...) + Execution halted + ``` + +# LMoFit + +
+ +* Version: 0.1.7 +* GitHub: NA +* Source code: https://github.com/cran/LMoFit +* Date/Publication: 2024-05-14 07:33:23 UTC +* Number of recursive dependencies: 62 + +Run `revdepcheck::cloud_details(, "LMoFit")` for more info + +
+ +## Newly broken + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘LMoFit.Rmd’ + ... + + > lspace_BrIII + + When sourcing ‘LMoFit.R’: + Error: Problem while setting up geom aesthetics. + ℹ Error occurred in the 1st layer. + Caused by error in `compute_geom_2()`: + ! unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), NULL, NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.75, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, 90, NULL, c(0, 2.75, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, + c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 1, NULL, NULL, NULL, c(0, 2.2, 0, 0), NULL, TRUE), NULL, + Execution halted + + ‘LMoFit.Rmd’ using ‘UTF-8’... failed + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + ... + --- re-building ‘LMoFit.Rmd’ using rmarkdown + + Quitting from lines 236-237 [unnamed-chunk-15] (LMoFit.Rmd) + Error: processing vignette 'LMoFit.Rmd' failed with diagnostics: + Problem while setting up geom aesthetics. + ℹ Error occurred in the 1st layer. + Caused by error in `compute_geom_2()`: + ! unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), NULL, NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.75, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, 90, NULL, c(0, 2.75, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, + ... + NULL, NULL, 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, NULL, NULL, NULL, TRUE), NULL, "right", NULL, NULL, NULL, "center", NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, c(0, 0, 0, 0), list(), 11, list("white", NA, NULL, NULL, TRUE), list(), 5.5, NULL, NULL, list("grey92", NULL, NULL, NULL, FALSE, TRUE), list(), list(), NULL, NULL, NULL, NULL, FALSE, list(NULL, "white", NULL, NULL, TRUE), list(NULL, NULL, NULL, 1.2, 0, 1, NULL, NULL, c(0, + 0, 5.5, 0), NULL, TRUE), "panel", list(NULL, NULL, NULL, NULL, 0, 1, NULL, NULL, c(0, 0, 5.5, 0), NULL, TRUE), list(NULL, NULL, NULL, 0.8, 1, 1, NULL, NULL, c(5.5, 0, 0, 0), NULL, TRUE), "panel", list(NULL, NULL, NULL, 1.2, 0.5, 0.5, NULL, NULL, NULL, NULL, TRUE), "topleft", NULL, c(5.5, 5.5, 5.5, 5.5), list("white", "black", 2, NULL, TRUE), NULL, NULL, "inherit", "inside", list(NULL, NULL, "grey10", 0.8, NULL, NULL, NULL, NULL, c(4.4, 4.4, 4.4, 4.4), NULL, TRUE), NULL, NULL, NULL, list(NULL, NULL, + NULL, NULL, NULL, NULL, -90, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, NULL, 90, NULL, NULL, NULL, TRUE), NULL, 2.75, 2.75, list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), 5.5, c(5.5, 5.5, 5.5, 5.5))) + --- failed re-building ‘LMoFit.Rmd’ + + SUMMARY: processing the following file failed: + ‘LMoFit.Rmd’ + + Error: Vignette re-building failed. + Execution halted + ``` + +## In both + +* checking installed package size ... NOTE + ``` + installed size is 7.0Mb + sub-directories of 1Mb or more: + data 6.5Mb + ``` + +# lomb + +
+ +* Version: 2.5.0 +* GitHub: NA +* Source code: https://github.com/cran/lomb +* Date/Publication: 2024-03-26 15:10:05 UTC +* Number of recursive dependencies: 86 + +Run `revdepcheck::cloud_details(, "lomb")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘lomb-Ex.R’ failed + The error most likely occurred in: + + > ### Name: getpeaks + > ### Title: Retrieve periodogram peaks + > ### Aliases: getpeaks + > ### Keywords: ts + > + > ### ** Examples + > + ... + 2. ├─base::plot(sp.out, ...) + 3. └─lomb::plot.lsp(sp.out, ...) + 4. ├─base::print(p) + 5. └─ggplot2:::print.ggplot(p) + 6. ├─ggplot2::ggplot_gtable(data) + 7. └─ggplot2:::ggplot_gtable.ggplot_built(data) + 8. └─ggplot2::calc_element("plot.margin", theme) + 9. └─cli::cli_abort(...) + 10. └─rlang::abort(...) + Execution halted + ``` + +## In both + +* checking installed package size ... NOTE + ``` + installed size is 7.0Mb + sub-directories of 1Mb or more: + data 6.5Mb + ``` + +# LongDat + +
+ +* Version: 1.1.2 +* GitHub: https://github.com/CCY-dev/LongDat +* Source code: https://github.com/cran/LongDat +* Date/Publication: 2023-07-17 05:40:02 UTC +* Number of recursive dependencies: 144 + +Run `revdepcheck::cloud_details(, "LongDat")` for more info + +
+ +## Newly broken + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘LongDat_cont_tutorial.Rmd’ + ... + + > test_plot <- cuneiform_plot(result_table = test_cont[[1]], + + title_size = 15) + [1] "Finished plotting successfully!" + + > test_plot + + ... + [1] "Finished plotting successfully!" + + > test_plot + + When sourcing ‘LongDat_disc_tutorial.R’: + Error: object is not coercible to a unit + Execution halted + + ‘LongDat_cont_tutorial.Rmd’ using ‘UTF-8’... failed + ‘LongDat_disc_tutorial.Rmd’ using ‘UTF-8’... failed + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘LongDat_cont_tutorial.Rmd’ using rmarkdown + Warning in eng_r(options) : + Failed to tidy R code in chunk 'unnamed-chunk-3'. Reason: + Error : The formatR package is required by the chunk option tidy = TRUE but not installed; tidy = TRUE will be ignored. + + Warning in eng_r(options) : + Failed to tidy R code in chunk 'unnamed-chunk-4'. Reason: + Error : The formatR package is required by the chunk option tidy = TRUE but not installed; tidy = TRUE will be ignored. + + ... + Quitting from lines 181-182 [unnamed-chunk-11] (LongDat_disc_tutorial.Rmd) + Error: processing vignette 'LongDat_disc_tutorial.Rmd' failed with diagnostics: + object is not coercible to a unit + --- failed re-building ‘LongDat_disc_tutorial.Rmd’ + + SUMMARY: processing the following files failed: + ‘LongDat_cont_tutorial.Rmd’ ‘LongDat_disc_tutorial.Rmd’ + + Error: Vignette re-building failed. + Execution halted + ``` + +# longitudinalcascade + +
+ +* Version: 0.3.2.6 +* GitHub: NA +* Source code: https://github.com/cran/longitudinalcascade +* Date/Publication: 2023-05-02 20:50:02 UTC +* Number of recursive dependencies: 40 + +Run `revdepcheck::cloud_details(, "longitudinalcascade")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘longitudinalcascade-Ex.R’ failed + The error most likely occurred in: + + > ### Name: longitudinalcascade + > ### Title: Longitudinal cascade statistics and charts + > ### Aliases: longitudinalcascade + > ### Keywords: cascade longitudinal survival + > + > ### ** Examples + > + ... + Backtrace: + ▆ + 1. ├─base (local) ``(x) + 2. └─ggplot2:::print.ggplot(x) + 3. ├─ggplot2::ggplot_gtable(data) + 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) + 5. └─ggplot2::calc_element("plot.margin", theme) + 6. └─cli::cli_abort(...) + 7. └─rlang::abort(...) + Execution halted + ``` + +# longmixr + +
+ +* Version: 1.0.0 +* GitHub: https://github.com/cellmapslab/longmixr +* Source code: https://github.com/cran/longmixr +* Date/Publication: 2022-01-13 20:32:42 UTC +* Number of recursive dependencies: 135 + +Run `revdepcheck::cloud_details(, "longmixr")` for more info + +
+ +## Newly broken + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘analysis_workflow.Rmd’ + ... + + > fviz_screeplot(quest_A_dim, main = "Questionnaire A") + + When sourcing ‘analysis_workflow.R’: + Error: Problem while setting up geom aesthetics. + ℹ Error occurred in the 1st layer. + Caused by error in `check_aesthetics()`: + ! Aesthetics must be either length 1 or the same as the data (5). + ✖ Fix the following mappings: `width`. + Execution halted + + ‘analysis_workflow.Rmd’ using ‘UTF-8’... failed + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘analysis_workflow.Rmd’ using rmarkdown + ``` + +# manhplot + +
+ +* Version: 1.1 +* GitHub: https://github.com/cgrace1978/manhplot +* Source code: https://github.com/cran/manhplot +* Date/Publication: 2019-11-25 16:40:03 UTC +* Number of recursive dependencies: 56 + +Run `revdepcheck::cloud_details(, "manhplot")` for more info + +
+ +## Newly broken + +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(manhplot) + > + > test_check("manhplot") + [ FAIL 2 | WARN 3 | SKIP 0 | PASS 0 ] + + ══ Failed tests ════════════════════════════════════════════════════════════════ + ... + 1. └─manhplot::manhplusplot(...) at testmanhplusplot.R:17:3 + 2. ├─ggplot2::ggplot_gtable(ggplot_build(final.table.plot)) + 3. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(final.table.plot)) + 4. └─ggplot2::calc_element("plot.margin", theme) + 5. └─cli::cli_abort(...) + 6. └─rlang::abort(...) + + [ FAIL 2 | WARN 3 | SKIP 0 | PASS 0 ] + Error: Test failures + Execution halted + ``` + +# mau + +
+ +* Version: 0.1.2 +* GitHub: https://github.com/pedroguarderas/mau +* Source code: https://github.com/cran/mau +* Date/Publication: 2018-01-17 05:35:14 UTC +* Number of recursive dependencies: 57 + +Run `revdepcheck::cloud_details(, "mau")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘mau-Ex.R’ failed + The error most likely occurred in: + + > ### Name: Spider.Plot + > ### Title: Spider plot + > ### Aliases: Spider.Plot + > + > ### ** Examples + > + > # Preparing data + ... + Backtrace: + ▆ + 1. ├─base::plot(p) + 2. └─ggplot2:::plot.ggplot(p) + 3. ├─ggplot2::ggplot_gtable(data) + 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) + 5. └─ggplot2::calc_element("plot.margin", theme) + 6. └─cli::cli_abort(...) + 7. └─rlang::abort(...) + Execution halted + ``` + +# MBNMAdose + +
+ +* Version: 0.4.3 +* GitHub: NA +* Source code: https://github.com/cran/MBNMAdose +* Date/Publication: 2024-04-18 12:42:47 UTC +* Number of recursive dependencies: 118 + +Run `revdepcheck::cloud_details(, "MBNMAdose")` for more info + +
+ +## Newly broken + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘outputs-4.Rmd’ + ... + + > plot(trip.emax) + + When sourcing ‘outputs-4.R’: + Error: Problem while setting up geom aesthetics. + ℹ Error occurred in the 1st layer. + Caused by error in `use_defaults()`: + ... + Execution halted + + ‘consistencychecking-3.Rmd’ using ‘UTF-8’... OK + ‘dataexploration-1.Rmd’ using ‘UTF-8’... OK + ‘mbnmadose-overview.Rmd’ using ‘UTF-8’... OK + ‘metaregression-6.Rmd’ using ‘UTF-8’... OK + ‘nma_in_mbnmadose.Rmd’ using ‘UTF-8’... OK + ‘outputs-4.Rmd’ using ‘UTF-8’... failed + ‘predictions-5.Rmd’ using ‘UTF-8’... OK + ‘runmbnmadose-2.Rmd’ using ‘UTF-8’... OK + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘consistencychecking-3.Rmd’ using rmarkdown + ``` + +## In both + +* checking data for non-ASCII characters ... NOTE + ``` + Note: found 6 marked Latin-1 strings + ``` + +# MBNMAtime + +
+ +* Version: 0.2.4 +* GitHub: NA +* Source code: https://github.com/cran/MBNMAtime +* Date/Publication: 2023-10-14 15:20:02 UTC +* Number of recursive dependencies: 106 + +Run `revdepcheck::cloud_details(, "MBNMAtime")` for more info + +
+ +## Newly broken + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘consistencychecking-3.Rmd’ using rmarkdown + + Quitting from lines 141-146 [unnamed-chunk-8] (consistencychecking-3.Rmd) + Error: processing vignette 'consistencychecking-3.Rmd' failed with diagnostics: + unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, "black", TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), NULL, list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), 5.5, c(5.5, 5.5, 5.5, 5.5), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.75, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, + NULL, NULL, NULL, 1, 90, NULL, c(0, 2.75, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 1, NULL, NULL, NULL, c(0, 2.2, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, + NULL, 0, NULL, NULL, NULL, c(0, 0, 0, 2.2), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0.5, NULL, NULL, NULL, c(0, 2.2, 0, 2.2), NULL, TRUE), list("grey20", NULL, NULL, NULL, FALSE, "grey20", TRUE), NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 0.5, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 0.75, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, list(), NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, list("transparent", NA, NULL, NULL, FALSE), NULL, + 2, NULL, NULL, list("transparent", NA, NULL, NULL, FALSE), 1.2, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 0.2, NULL, list(NULL, NULL, NULL, 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, NULL, NULL, NULL, TRUE), NULL, "right", NULL, NULL, NULL, "center", NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 0, list(), 2, list(), list(NULL, "grey20", NULL, NULL, TRUE), NULL, NULL, NULL, list("grey92", NULL, NULL, NULL, FALSE, "grey92", TRUE), list("grey95", + NULL, NULL, NULL, FALSE, "grey95", FALSE), list("grey95", 0.5, NULL, NULL, FALSE, "grey95", FALSE), NULL, NULL, NULL, NULL, FALSE, list("white", NA, NULL, NULL, FALSE), list(NULL, NULL, NULL, 1.2, 0, 1, NULL, NULL, c(0, 0, 5.5, 0), NULL, TRUE), "panel", list(NULL, NULL, NULL, NULL, 0, 1, NULL, NULL, c(0, 0, 5.5, 0), NULL, TRUE), list(NULL, NULL, NULL, 0.8, 1, 1, NULL, NULL, c(5.5, 0, 0, 0), NULL, TRUE), "panel", list(NULL, NULL, NULL, 1.2, 0.5, 0.5, NULL, NULL, NULL, NULL, TRUE), "topleft", + NULL, NULL, list("lightsteelblue1", "black", NULL, NULL, FALSE), NULL, NULL, "inherit", "inside", list(NULL, NULL, "black", 0.8, NULL, NULL, NULL, NULL, c(4.4, 4.4, 4.4, 4.4), NULL, FALSE), NULL, NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, NULL, -90, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, NULL, 90, NULL, NULL, NULL, TRUE), NULL, 2.75, 2.75)) + --- failed re-building ‘consistencychecking-3.Rmd’ + + --- re-building ‘dataexploration-1.Rmd’ using rmarkdown + ``` + +## In both + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘consistencychecking-3.Rmd’ + ... + |-> direct | | 0.228| -0.213| 0.684| + |-> indirect | | -0.515| -0.891| -0.137| + | | | | | | + + > plot(nodesplit, plot.type = "forest") + + When sourcing ‘consistencychecking-3.R’: + ... + ! unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, "black", TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), NULL, list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), 5.5, c(5.5, 5.5, 5.5, 5.5), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.75, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, + NULL, NULL, NULL, 1, 90, NULL, c(0, 2.75, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, + Execution halted + + ‘consistencychecking-3.Rmd’ using ‘UTF-8’... failed + ‘dataexploration-1.Rmd’ using ‘UTF-8’... failed + ‘mbnmatime-overview.Rmd’ using ‘UTF-8’... OK + ‘outputs-4.Rmd’ using ‘UTF-8’... failed + ‘predictions-5.Rmd’ using ‘UTF-8’... OK + ‘runmbnmatime-2.Rmd’ using ‘UTF-8’... OK + ``` + +# metaforest + +
+ +* Version: 0.1.4 +* GitHub: NA +* Source code: https://github.com/cran/metaforest +* Date/Publication: 2024-01-26 09:40:05 UTC +* Number of recursive dependencies: 124 + +Run `revdepcheck::cloud_details(, "metaforest")` for more info + +
+ +## Newly broken + +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > rm(list=ls()) + > library(testthat) + > library(caret) + Loading required package: ggplot2 + Loading required package: lattice + > library(metaforest) + Loading required package: metafor + ... + 6. └─ggplot2::ggplotGrob(plots[[x]] + theme(axis.title.y = element_blank())) + 7. ├─ggplot2::ggplot_gtable(ggplot_build(x)) + 8. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) + 9. └─ggplot2::calc_element("plot.margin", theme) + 10. └─cli::cli_abort(...) + 11. └─rlang::abort(...) + + [ FAIL 1 | WARN 3 | SKIP 0 | PASS 18 ] + Error: Test failures + Execution halted + ``` + +## In both + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘Introduction_to_metaforest.Rmd’ + ... + + > set.seed(62) + + > check_conv <- readRDS("C:/Git_Repositories/S4_meta-analysis/check_conv.RData") + Warning in gzfile(file, "rb") : + cannot open compressed file 'C:/Git_Repositories/S4_meta-analysis/check_conv.RData', probable reason 'No such file or directory' + + When sourcing ‘Introduction_to_metaforest.R’: + Error: cannot open the connection + Execution halted + + ‘Introduction_to_metaforest.Rmd’ using ‘UTF-8’... failed + ``` + +# metan + +
+ +* Version: 1.18.0 +* GitHub: https://github.com/TiagoOlivoto/metan +* Source code: https://github.com/cran/metan +* Date/Publication: 2023-03-05 22:00:15 UTC +* Number of recursive dependencies: 116 + +Run `revdepcheck::cloud_details(, "metan")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘metan-Ex.R’ failed + The error most likely occurred in: + + > ### Name: network_plot + > ### Title: Network plot of a correlation matrix + > ### Aliases: network_plot + > + > ### ** Examples + > + > cor <- corr_coef(iris) + ... + Backtrace: + ▆ + 1. ├─base (local) ``(x) + 2. └─ggplot2:::print.ggplot(x) + 3. ├─ggplot2::ggplot_gtable(data) + 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) + 5. └─ggplot2::calc_element("plot.margin", theme) + 6. └─cli::cli_abort(...) + 7. └─rlang::abort(...) + Execution halted + ``` + +# metaplot + +
+ +* Version: 0.8.4 +* GitHub: NA +* Source code: https://github.com/cran/metaplot +* Date/Publication: 2024-02-18 05:30:10 UTC +* Number of recursive dependencies: 40 + +Run `revdepcheck::cloud_details(, "metaplot")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘metaplot-Ex.R’ failed + The error most likely occurred in: + + > ### Name: boxplot.data.frame + > ### Title: Boxplot Method for Data Frame + > ### Aliases: boxplot.data.frame + > + > ### ** Examples + > + > library(dplyr) + ... + Backtrace: + ▆ + 1. ├─base (local) ``(x) + 2. └─ggplot2:::print.ggplot(x) + 3. ├─ggplot2::ggplot_gtable(data) + 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) + 5. └─ggplot2::calc_element("plot.margin", theme) + 6. └─cli::cli_abort(...) + 7. └─rlang::abort(...) + Execution halted + ``` + +# metR + +
+ +* Version: 0.15.0 +* GitHub: https://github.com/eliocamp/metR +* Source code: https://github.com/cran/metR +* Date/Publication: 2024-02-09 00:40:02 UTC +* Number of recursive dependencies: 120 + +Run `revdepcheck::cloud_details(, "metR")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘metR-Ex.R’ failed + The error most likely occurred in: + + > ### Name: GeostrophicWind + > ### Title: Calculate geostrophic winds + > ### Aliases: GeostrophicWind + > + > ### ** Examples + > + > data(geopotential) + ... + > ggplot(geopotential[date == date[1]], aes(lon, lat)) + + + geom_contour(aes(z = gh)) + + + geom_vector(aes(dx = u, dy = v), skip = 2) + + + scale_mag() + Warning: The S3 guide system was deprecated in ggplot2 3.5.0. + ℹ It has been replaced by a ggproto system that can be extended. + Error in (function (layer, df) : + argument "theme" is missing, with no default + Calls: ... use_defaults -> eval_from_theme -> %||% -> calc_element + Execution halted + ``` + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘Visualization-tools.Rmd’ + ... + + > (g <- ggplot(temperature[lev == 500], aes(lon, lat)) + + + geom_contour_fill(aes(z = air.z)) + geom_vector(aes(dx = t.dx, + + dy = t.dy), skip .... [TRUNCATED] + Warning: The S3 guide system was deprecated in ggplot2 3.5.0. + ℹ It has been replaced by a ggproto system that can be extended. + + ... + + dy = gh.dlat), s .... [TRUNCATED] + Warning: The S3 guide system was deprecated in ggplot2 3.5.0. + ℹ It has been replaced by a ggproto system that can be extended. + + When sourcing ‘Working-with-data.R’: + Error: argument "theme" is missing, with no default + Execution halted + + ‘Visualization-tools.Rmd’ using ‘UTF-8’... failed + ‘Working-with-data.Rmd’ using ‘UTF-8’... failed + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + ... + --- re-building ‘Visualization-tools.Rmd’ using knitr + + Quitting from lines 284-293 [unnamed-chunk-19] (Visualization-tools.Rmd) + Error: processing vignette 'Visualization-tools.Rmd' failed with diagnostics: + argument "theme" is missing, with no default + --- failed re-building ‘Visualization-tools.Rmd’ + + --- re-building ‘Working-with-data.Rmd’ using knitr + ... + Quitting from lines 199-210 [unnamed-chunk-13] (Working-with-data.Rmd) + Error: processing vignette 'Working-with-data.Rmd' failed with diagnostics: + argument "theme" is missing, with no default + --- failed re-building ‘Working-with-data.Rmd’ + + SUMMARY: processing the following files failed: + ‘Visualization-tools.Rmd’ ‘Working-with-data.Rmd’ + + Error: Vignette re-building failed. + Execution halted + ``` + +## In both + +* checking installed package size ... NOTE + ``` + installed size is 6.6Mb + sub-directories of 1Mb or more: + R 1.5Mb + data 2.0Mb + doc 1.8Mb + ``` + +# miceFast + +
+ +* Version: 0.8.2 +* GitHub: https://github.com/Polkas/miceFast +* Source code: https://github.com/cran/miceFast +* Date/Publication: 2022-11-17 21:10:02 UTC +* Number of recursive dependencies: 112 + +Run `revdepcheck::cloud_details(, "miceFast")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘miceFast-Ex.R’ failed + The error most likely occurred in: + + > ### Name: upset_NA + > ### Title: upset plot for NA values + > ### Aliases: upset_NA + > + > ### ** Examples + > + > library(miceFast) + ... + 4. ├─base::suppressMessages(...) + 5. │ └─base::withCallingHandlers(...) + 6. └─UpSetR:::Make_main_bar(...) + 7. └─ggplot2::ggplotGrob(Main_bar_plot) + 8. ├─ggplot2::ggplot_gtable(ggplot_build(x)) + 9. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) + 10. └─ggplot2::calc_element("plot.margin", theme) + 11. └─cli::cli_abort(...) + 12. └─rlang::abort(...) + Execution halted + ``` + +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(miceFast) + > library(data.table) + > library(dplyr) + + Attaching package: 'dplyr' + + ... + 15. └─ggplot2::ggplotGrob(Main_bar_plot) + 16. ├─ggplot2::ggplot_gtable(ggplot_build(x)) + 17. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) + 18. └─ggplot2::calc_element("plot.margin", theme) + 19. └─cli::cli_abort(...) + 20. └─rlang::abort(...) + + [ FAIL 1 | WARN 0 | SKIP 0 | PASS 103 ] + Error: Test failures + Execution halted + ``` + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘miceFast-intro.Rmd’ + ... + + > set.seed(123456) + + > data(air_miss) + + > upset_NA(air_miss, 6) + + When sourcing ‘miceFast-intro.R’: + Error: Theme element `plot.margin` must have class . + Execution halted + + ‘miceFast-intro.Rmd’ using ‘UTF-8’... failed + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + ... + --- re-building ‘miceFast-intro.Rmd’ using rmarkdown + + Quitting from lines 84-85 [unnamed-chunk-6] (miceFast-intro.Rmd) + Error: processing vignette 'miceFast-intro.Rmd' failed with diagnostics: + Theme element `plot.margin` must have class . + --- failed re-building ‘miceFast-intro.Rmd’ + + SUMMARY: processing the following file failed: + ‘miceFast-intro.Rmd’ + + Error: Vignette re-building failed. + Execution halted + ``` + +## In both + +* checking C++ specification ... NOTE + ``` + Specified C++11: please drop specification unless essential + ``` + +* checking installed package size ... NOTE + ``` + installed size is 12.1Mb + sub-directories of 1Mb or more: + libs 10.9Mb + ``` + +# MicrobiomeStat + +
+ +* Version: 1.2 +* GitHub: NA +* Source code: https://github.com/cran/MicrobiomeStat +* Date/Publication: 2024-04-01 22:30:02 UTC +* Number of recursive dependencies: 73 + +Run `revdepcheck::cloud_details(, "MicrobiomeStat")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘MicrobiomeStat-Ex.R’ failed + The error most likely occurred in: + + > ### Name: linda + > ### Title: Linear (Lin) Model for Differential Abundance (DA) Analysis of + > ### High-dimensional Compositional Data + > ### Aliases: linda + > + > ### ** Examples + > + ... + Backtrace: + ▆ + 1. ├─base (local) ``(x) + 2. └─ggplot2:::print.ggplot(x) + 3. ├─ggplot2::ggplot_gtable(data) + 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) + 5. └─ggplot2::calc_element("plot.margin", theme) + 6. └─cli::cli_abort(...) + 7. └─rlang::abort(...) + Execution halted + ``` + +# micromap + +
+ +* Version: 1.9.8 +* GitHub: https://github.com/USEPA/micromap +* Source code: https://github.com/cran/micromap +* Date/Publication: 2024-02-06 14:00:02 UTC +* Number of recursive dependencies: 45 + +Run `revdepcheck::cloud_details(, "micromap")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘micromap-Ex.R’ failed + The error most likely occurred in: + + > ### Name: lmgroupedplot + > ### Title: Linked Micromaps + > ### Aliases: lmgroupedplot lmplot mmgroupedplot mmplot + > ### mmplot.SpatialPolygonsDataFrame mmplot.sf mmplot.default + > ### Keywords: hplot + > + > ### ** Examples + ... + 6. ├─base::suppressWarnings(...) + 7. │ └─base::withCallingHandlers(...) + 8. ├─base::print(plobject[[p]], vp = subplot(1, p * 2)) + 9. └─ggplot2:::print.ggplot(plobject[[p]], vp = subplot(1, p * 2)) + 10. ├─ggplot2::ggplot_gtable(data) + 11. └─ggplot2:::ggplot_gtable.ggplot_built(data) + 12. └─ggplot2::calc_element("plot.margin", theme) + 13. └─cli::cli_abort(...) + 14. └─rlang::abort(...) + Execution halted + ``` + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘Introduction_Guide.Rnw’ + ... + 6 AK 1 1 4 17 0 1 0 + + > mmplot(stat.data = edPov, map.data = statePolys, panel.types = c("labels", + + "dot", "dot", "map"), panel.data = list("state", "pov", "ed", + + .... [TRUNCATED] + + When sourcing ‘Introduction_Guide.R’: + Error: Theme element `plot.margin` must have class + . + Execution halted + + ‘Introduction_Guide.Rnw’ using ‘UTF-8’... failed + ``` + +## In both + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + ... + --- re-building ‘Introduction_Guide.Rnw’ using Sweave + Loading required package: RColorBrewer + Loading required package: sp + Loading required package: sf + Linking to GEOS 3.10.2, GDAL 3.4.1, PROJ 8.2.1; sf_use_s2() + is TRUE + + Error: processing vignette 'Introduction_Guide.Rnw' failed with diagnostics: + ... + Theme element `plot.margin` must have class + . + + --- failed re-building ‘Introduction_Guide.Rnw’ + + SUMMARY: processing the following file failed: + ‘Introduction_Guide.Rnw’ + + Error: Vignette re-building failed. + Execution halted + ``` + +# MiMIR + +
+ +* Version: 1.5 +* GitHub: NA +* Source code: https://github.com/cran/MiMIR +* Date/Publication: 2024-02-01 08:50:02 UTC +* Number of recursive dependencies: 188 + +Run `revdepcheck::cloud_details(, "MiMIR")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘MiMIR-Ex.R’ failed + The error most likely occurred in: + + > ### Name: LOBOV_accuracies + > ### Title: LOBOV_accuracies + > ### Aliases: LOBOV_accuracies + > + > ### ** Examples + > + > require(pROC) + ... + 56 metabolites x 500 samples + | Pruning samples on5SD: + 56 metabolites x 500 samples + | Performing scaling ... DONE! + | Imputation ... DONE! + > p_avail<-colnames(b_p)[c(1:5)] + > LOBOV_accuracies(sur$surrogates, b_p, p_avail, MiMIR::acc_LOBOV) + Error in pm[[2]] : subscript out of bounds + Calls: LOBOV_accuracies -> -> ggplotly.ggplot -> gg2list + Execution halted + ``` + +# MIMSunit + +
+ +* Version: 0.11.2 +* GitHub: https://github.com/mhealthgroup/MIMSunit +* Source code: https://github.com/cran/MIMSunit +* Date/Publication: 2022-06-21 11:00:09 UTC +* Number of recursive dependencies: 114 + +Run `revdepcheck::cloud_details(, "MIMSunit")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘MIMSunit-Ex.R’ failed + The error most likely occurred in: + + > ### Name: bandlimited_interp + > ### Title: Apply a bandlimited interpolation filter to the signal to change + > ### the sampling rate + > ### Aliases: bandlimited_interp + > + > ### ** Examples + > + ... + Backtrace: + ▆ + 1. ├─base (local) ``(x) + 2. └─ggplot2:::print.ggplot(x) + 3. ├─ggplot2::ggplot_gtable(data) + 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) + 5. └─ggplot2::calc_element("plot.margin", theme) + 6. └─cli::cli_abort(...) + 7. └─rlang::abort(...) + Execution halted + ``` + +# miRetrieve + +
+ +* Version: 1.3.4 +* GitHub: NA +* Source code: https://github.com/cran/miRetrieve +* Date/Publication: 2021-09-18 17:30:02 UTC +* Number of recursive dependencies: 126 + +Run `revdepcheck::cloud_details(, "miRetrieve")` for more info + +
+ +## Newly broken + +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(miRetrieve) + > + > test_check("miRetrieve") + [ FAIL 1 | WARN 11 | SKIP 0 | PASS 202 ] + + ══ Failed tests ════════════════════════════════════════════════════════════════ + ... + Backtrace: + ▆ + 1. └─miRetrieve::compare_mir_terms_scatter(df_merged, "miR-21", title = "Test_title") at test-comparemirterms.R:56:1 + 2. ├─plotly::ggplotly(plot) + 3. └─plotly:::ggplotly.ggplot(plot) + 4. └─plotly::gg2list(...) + + [ FAIL 1 | WARN 11 | SKIP 0 | PASS 202 ] + Error: Test failures + Execution halted + ``` + +# misspi + +
+ +* Version: 0.1.0 +* GitHub: NA +* Source code: https://github.com/cran/misspi +* Date/Publication: 2023-10-17 09:50:02 UTC +* Number of recursive dependencies: 88 + +Run `revdepcheck::cloud_details(, "misspi")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘misspi-Ex.R’ failed + The error most likely occurred in: + + > ### Name: evaliq + > ### Title: Evaluate the Imputation Quality + > ### Aliases: evaliq + > + > ### ** Examples + > + > # A very quick example + ... + > # Default plot + > er.eval <- evaliq(x.true[na.idx], x.est[na.idx]) + `geom_smooth()` using formula = 'y ~ x' + > + > # Interactive plot + > er.eval <- evaliq(x.true[na.idx], x.est[na.idx], interactive = TRUE) + `geom_smooth()` using formula = 'y ~ x' + Error in pm[[2]] : subscript out of bounds + Calls: evaliq -> print -> ggplotly -> ggplotly.ggplot -> gg2list + Execution halted + ``` + +# mizer + +
+ +* Version: 2.5.1 +* GitHub: https://github.com/sizespectrum/mizer +* Source code: https://github.com/cran/mizer +* Date/Publication: 2024-03-08 23:10:02 UTC +* Number of recursive dependencies: 109 + +Run `revdepcheck::cloud_details(, "mizer")` for more info + +
+ +## Newly broken + +* checking tests ... ERROR + ``` + Running ‘spelling.R’ + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(mizer) + > + > test_check("mizer") + [ FAIL 10 | WARN 0 | SKIP 5 | PASS 1251 ] + + ... + • plots/plot-spectra.svg + • plots/plot-yield-by-gear.svg + • plots/plot-yield.svg + • plots/plotfishing-mortality.svg + • plots/plotfmort-truncated.svg + • plots/plotpredation-mortality.svg + • plots/plotpredmort-truncated.new.svg + • plots/plotpredmort-truncated.svg + Error: Test failures + Execution halted + ``` + +## In both + +* checking installed package size ... NOTE + ``` + installed size is 6.1Mb + sub-directories of 1Mb or more: + doc 1.5Mb + help 1.8Mb + ``` + +# mlr3spatiotempcv + +
+ +* Version: 2.3.1 +* GitHub: https://github.com/mlr-org/mlr3spatiotempcv +* Source code: https://github.com/cran/mlr3spatiotempcv +* Date/Publication: 2024-04-17 12:10:05 UTC +* Number of recursive dependencies: 168 + +Run `revdepcheck::cloud_details(, "mlr3spatiotempcv")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘mlr3spatiotempcv-Ex.R’ failed + The error most likely occurred in: + + > ### Name: autoplot.ResamplingCustomCV + > ### Title: Visualization Functions for Non-Spatial CV Methods. + > ### Aliases: autoplot.ResamplingCustomCV plot.ResamplingCustomCV + > + > ### ** Examples + > + > if (mlr3misc::require_namespaces(c("sf", "patchwork"), quietly = TRUE)) { + ... + + + + autoplot(resampling, task) + + + ggplot2::scale_x_continuous(breaks = seq(-79.085, -79.055, 0.01)) + + autoplot(resampling, task, fold_id = 1) + + autoplot(resampling, task, fold_id = c(1, 2)) * + + ggplot2::scale_x_continuous(breaks = seq(-79.085, -79.055, 0.01)) + + } + Error in identicalUnits(x) : object is not a unit + Calls: ... assemble_guides -> guides_build -> unit.c -> identicalUnits + Execution halted + ``` + +## In both + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘spatiotemp-viz.Rmd’ + ... + + > knitr::opts_chunk$set(collapse = TRUE, comment = "#>") + + > knitr::include_graphics("../man/figures/sptcv_cstf_multiplot.png") + + When sourcing ‘spatiotemp-viz.R’: + Error: Cannot find the file(s): "../man/figures/sptcv_cstf_multiplot.png" + Execution halted + + ‘mlr3spatiotempcv.Rmd’ using ‘UTF-8’... OK + ‘spatiotemp-viz.Rmd’ using ‘UTF-8’... failed + ``` + +* checking installed package size ... NOTE + ``` + installed size is 5.9Mb + sub-directories of 1Mb or more: + data 3.5Mb + ``` + +# mlr3viz + +
+ +* Version: 0.8.0 +* GitHub: https://github.com/mlr-org/mlr3viz +* Source code: https://github.com/cran/mlr3viz +* Date/Publication: 2024-03-05 12:50:03 UTC +* Number of recursive dependencies: 140 + +Run `revdepcheck::cloud_details(, "mlr3viz")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘mlr3viz-Ex.R’ failed + The error most likely occurred in: + + > ### Name: autoplot.OptimInstanceSingleCrit + > ### Title: Plots for Optimization Instances + > ### Aliases: autoplot.OptimInstanceSingleCrit + > + > ### ** Examples + > + > if (requireNamespace("mlr3") && requireNamespace("bbotk") && requireNamespace("patchwork")) { + ... + INFO [11:58:58.325] [bbotk] 5.884797 2.2371095 -32.51896 + INFO [11:58:58.325] [bbotk] -7.841127 -0.8872557 -91.31148 + INFO [11:58:58.334] [bbotk] Finished optimizing after 20 evaluation(s) + INFO [11:58:58.335] [bbotk] Result: + INFO [11:58:58.338] [bbotk] x1 x2 x_domain y + INFO [11:58:58.338] [bbotk] + INFO [11:58:58.338] [bbotk] 2.582281 -2.940254 9.657379 + Error in identicalUnits(x) : object is not a unit + Calls: print ... assemble_guides -> guides_build -> unit.c -> identicalUnits + Execution halted + ``` + +# modeltime.resample + +
+ +* Version: 0.2.3 +* GitHub: https://github.com/business-science/modeltime.resample +* Source code: https://github.com/cran/modeltime.resample +* Date/Publication: 2023-04-12 15:50:02 UTC +* Number of recursive dependencies: 229 + +Run `revdepcheck::cloud_details(, "modeltime.resample")` for more info + +
+ +## Newly broken + +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > + > # Machine Learning + > library(tidymodels) + ── Attaching packages ────────────────────────────────────── tidymodels 1.2.0 ── + ✔ broom 1.0.6 ✔ recipes 1.0.10 + ✔ dials 1.2.1 ✔ rsample 1.2.1 + ... + ▆ + 1. ├─m750_models_resample %>% ... at test-modeltime_fit_resamples.R:116:5 + 2. └─modeltime.resample::plot_modeltime_resamples(., .interactive = TRUE) + 3. ├─plotly::ggplotly(g) + 4. └─plotly:::ggplotly.ggplot(g) + 5. └─plotly::gg2list(...) + + [ FAIL 1 | WARN 4 | SKIP 0 | PASS 16 ] + Error: Test failures + Execution halted + ``` + +## In both + +* checking dependencies in R code ... NOTE + ``` + Namespaces in Imports field not imported from: + ‘crayon’ ‘dials’ ‘glue’ ‘parsnip’ + All declared Imports should be used. + ``` + +# mosaic + +
+ +* Version: 1.9.1 +* GitHub: https://github.com/ProjectMOSAIC/mosaic +* Source code: https://github.com/cran/mosaic +* Date/Publication: 2024-02-23 14:30:06 UTC +* Number of recursive dependencies: 131 + +Run `revdepcheck::cloud_details(, "mosaic")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘mosaic-Ex.R’ failed + The error most likely occurred in: + + > ### Name: mUSMap + > ### Title: Make a US map with 'ggplot2' + > ### Aliases: mUSMap + > + > ### ** Examples + > + > USArrests2 <- USArrests |> tibble::rownames_to_column("state") + ... + Backtrace: + ▆ + 1. ├─base (local) ``(x) + 2. └─ggplot2:::print.ggplot(x) + 3. ├─ggplot2::ggplot_gtable(data) + 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) + 5. └─ggplot2::calc_element("plot.margin", theme) + 6. └─cli::cli_abort(...) + 7. └─rlang::abort(...) + Execution halted + ``` + +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(mosaic) + Registered S3 method overwritten by 'mosaic': + method from + fortify.SpatialPolygonsDataFrame ggplot2 + + The 'mosaic' package masks several functions from core packages in order to add + ... + • plotModel/plotmodel2.svg + • plotModel/plotmodel3.svg + • plotPoints/plotpoints2.svg + • plotPoints/plotpoints3.svg + • rfun/rfun2.svg + • statTally/stattally2.svg + • statTally/stattally3.svg + • xpnorm/xpnorm2.svg + Error: Test failures + Execution halted + ``` + +## In both + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘MinimalRgg.Rnw’ + ... + > set.seed(123) + + > knitr::opts_chunk$set(dev = "pdf", eval = FALSE, tidy = FALSE, + + fig.align = "center", fig.show = "hold", message = FALSE) + + > apropos() + + When sourcing ‘MinimalRgg.R’: + Error: argument "what" is missing, with no default + Execution halted + + ‘Resampling.Rmd’ using ‘UTF-8’... OK + ‘mosaic-resources.Rmd’ using ‘UTF-8’... OK + ‘MinimalRgg.Rnw’ using ‘UTF-8’... failed + ``` + +* checking package dependencies ... NOTE + ``` + Package which this enhances but not available for checking: ‘manipulate’ + ``` + +* checking installed package size ... NOTE + ``` + installed size is 6.8Mb + sub-directories of 1Mb or more: + R 5.0Mb + doc 1.2Mb + ``` + +* checking Rd cross-references ... NOTE + ``` + Package unavailable to check Rd xrefs: ‘cubature’ + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘Resampling.Rmd’ using rmarkdown + ``` + +# motifr + +
+ +* Version: 1.0.0 +* GitHub: https://github.com/marioangst/motifr +* Source code: https://github.com/cran/motifr +* Date/Publication: 2020-12-10 15:40:02 UTC +* Number of recursive dependencies: 121 + +Run `revdepcheck::cloud_details(, "motifr")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘motifr-Ex.R’ failed + The error most likely occurred in: + + > ### Name: directed_dummy_net + > ### Title: Two-level directed network dummy example + > ### Aliases: directed_dummy_net + > ### Keywords: datasets + > + > ### ** Examples + > + ... + Backtrace: + ▆ + 1. ├─base (local) ``(x) + 2. └─ggplot2:::print.ggplot(x) + 3. ├─ggplot2::ggplot_gtable(data) + 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) + 5. └─ggplot2::calc_element("plot.margin", theme) + 6. └─cli::cli_abort(...) + 7. └─rlang::abort(...) + Execution halted + ``` + +# mpwR + +
+ +* Version: 0.1.5 +* GitHub: NA +* Source code: https://github.com/cran/mpwR +* Date/Publication: 2023-11-13 23:33:26 UTC +* Number of recursive dependencies: 112 + +Run `revdepcheck::cloud_details(, "mpwR")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘mpwR-Ex.R’ failed + The error most likely occurred in: + + > ### Name: plot_Upset + > ### Title: Upset Plot + > ### Aliases: plot_Upset + > + > ### ** Examples + > + > # Load libraries + ... + 3. ├─base::suppressMessages(...) + 4. │ └─base::withCallingHandlers(...) + 5. └─UpSetR:::Make_main_bar(...) + 6. └─ggplot2::ggplotGrob(Main_bar_plot) + 7. ├─ggplot2::ggplot_gtable(ggplot_build(x)) + 8. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) + 9. └─ggplot2::calc_element("plot.margin", theme) + 10. └─cli::cli_abort(...) + 11. └─rlang::abort(...) + Execution halted + ``` + +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(mpwR) + > + > test_check("mpwR") + For DIA-NN no quantitative LFQ data on peptide-level. + For PD no quantitative LFQ data on peptide-level. + For DIA-NN no quantitative LFQ data on peptide-level. + ... + 6. └─ggplot2::ggplotGrob(Main_bar_plot) + 7. ├─ggplot2::ggplot_gtable(ggplot_build(x)) + 8. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) + 9. └─ggplot2::calc_element("plot.margin", theme) + 10. └─cli::cli_abort(...) + 11. └─rlang::abort(...) + + [ FAIL 1 | WARN 123 | SKIP 0 | PASS 658 ] + Error: Test failures + Execution halted + ``` + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘Workflow.Rmd’ + ... + > plot_CV_density(input_list = CV_LFQ_PG, cv_col = "PG_quant") + + > Upset_prepared <- get_Upset_list(input_list = files, + + level = "ProteinGroup.IDs") + + > plot_Upset(input_list = Upset_prepared, label = "ProteinGroup.IDs") + + When sourcing ‘Workflow.R’: + Error: Theme element `plot.margin` must have class . + Execution halted + + ‘Import.Rmd’ using ‘UTF-8’... OK + ‘Output_Explanations.Rmd’ using ‘UTF-8’... OK + ‘Requirements.Rmd’ using ‘UTF-8’... OK + ‘Workflow.Rmd’ using ‘UTF-8’... failed + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘Import.Rmd’ using rmarkdown + --- finished re-building ‘Import.Rmd’ + + --- re-building ‘Output_Explanations.Rmd’ using rmarkdown + --- finished re-building ‘Output_Explanations.Rmd’ + + --- re-building ‘Requirements.Rmd’ using rmarkdown + --- finished re-building ‘Requirements.Rmd’ + + --- re-building ‘Workflow.Rmd’ using rmarkdown + ``` + +# mrfDepth + +
+ +* Version: 1.0.17 +* GitHub: NA +* Source code: https://github.com/cran/mrfDepth +* Date/Publication: 2024-05-24 21:20:02 UTC +* Number of recursive dependencies: 44 + +Run `revdepcheck::cloud_details(, "mrfDepth")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘mrfDepth-Ex.R’ failed + The error most likely occurred in: + + > ### Name: bagplot + > ### Title: Draws a bagplot, a bivariate boxplot + > ### Aliases: bagplot + > ### Keywords: Graphical + > + > ### ** Examples + > + ... + Backtrace: + ▆ + 1. ├─base (local) ``(x) + 2. └─ggplot2:::print.ggplot(x) + 3. ├─ggplot2::ggplot_gtable(data) + 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) + 5. └─ggplot2::calc_element("plot.margin", theme) + 6. └─cli::cli_abort(...) + 7. └─rlang::abort(...) + Execution halted + ``` + +## In both + +* checking installed package size ... NOTE + ``` + installed size is 20.2Mb + sub-directories of 1Mb or more: + data 1.6Mb + libs 18.1Mb + ``` + +# musclesyneRgies + +
+ +* Version: 1.2.5 +* GitHub: https://github.com/alesantuz/musclesyneRgies +* Source code: https://github.com/cran/musclesyneRgies +* Date/Publication: 2022-07-19 17:10:02 UTC +* Number of recursive dependencies: 82 + +Run `revdepcheck::cloud_details(, "musclesyneRgies")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘musclesyneRgies-Ex.R’ failed + The error most likely occurred in: + + > ### Name: plot_classified_syns + > ### Title: Plot muscle synergies + > ### Aliases: plot_classified_syns + > + > ### ** Examples + > + > # Load some data + ... + 3. │ └─base::withCallingHandlers(...) + 4. └─gridExtra::arrangeGrob(...) + 5. └─base::lapply(grobs[toconv], ggplot2::ggplotGrob) + 6. └─ggplot2 (local) FUN(X[[i]], ...) + 7. ├─ggplot2::ggplot_gtable(ggplot_build(x)) + 8. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) + 9. └─ggplot2::calc_element("plot.margin", theme) + 10. └─cli::cli_abort(...) + 11. └─rlang::abort(...) + Execution halted + ``` + +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(musclesyneRgies) + > + > test_check("musclesyneRgies") + [ FAIL 1 | WARN 13 | SKIP 0 | PASS 45 ] + + ══ Failed tests ════════════════════════════════════════════════════════════════ + ... + 4. └─ggplot2 (local) FUN(X[[i]], ...) + 5. ├─ggplot2::ggplot_gtable(ggplot_build(x)) + 6. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) + 7. └─ggplot2::calc_element("plot.margin", theme) + 8. └─cli::cli_abort(...) + 9. └─rlang::abort(...) + + [ FAIL 1 | WARN 13 | SKIP 0 | PASS 45 ] + Error: Test failures + Execution halted + ``` + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘plots.Rmd’ + ... + > library(musclesyneRgies) + + > data("RAW_DATA") + + > pp <- plot_rawEMG(RAW_DATA[[1]], trial = names(RAW_DATA)[1], + + row_number = 4, col_number = 4, line_col = "tomato3") + + When sourcing ‘plots.R’: + Error: Theme element `plot.margin` must have class . + Execution halted + + ‘analysis.Rmd’ using ‘UTF-8’... OK + ‘plots.Rmd’ using ‘UTF-8’... failed + ‘pro_tips.Rmd’ using ‘UTF-8’... OK + ‘workflow.Rmd’ using ‘UTF-8’... OK + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘analysis.Rmd’ using rmarkdown + ``` + +# naniar + +
+ +* Version: 1.1.0 +* GitHub: https://github.com/njtierney/naniar +* Source code: https://github.com/cran/naniar +* Date/Publication: 2024-03-05 10:10:02 UTC +* Number of recursive dependencies: 173 + +Run `revdepcheck::cloud_details(, "naniar")` for more info + +
+ +## Newly broken + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘naniar-visualisation.Rmd’ + ... + + > library(naniar) + + > vis_miss(airquality) + + > gg_miss_upset(airquality) + + When sourcing ‘naniar-visualisation.R’: + Error: Theme element `plot.margin` must have class . + Execution halted + + ‘exploring-imputed-values.Rmd’ using ‘UTF-8’... OK + ‘getting-started-w-naniar.Rmd’ using ‘UTF-8’... OK + ‘naniar-visualisation.Rmd’ using ‘UTF-8’... failed + ‘replace-with-na.Rmd’ using ‘UTF-8’... OK + ‘special-missing-values.Rmd’ using ‘UTF-8’... OK + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘exploring-imputed-values.Rmd’ using rmarkdown + ``` + +# neatmaps + +
+ +* Version: 2.1.0 +* GitHub: https://github.com/PhilBoileau/neatmaps +* Source code: https://github.com/cran/neatmaps +* Date/Publication: 2019-05-12 19:10:03 UTC +* Number of recursive dependencies: 99 + +Run `revdepcheck::cloud_details(, "neatmaps")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘neatmaps-Ex.R’ failed + The error most likely occurred in: + + > ### Name: consClustResTable + > ### Title: Consensus Cluster Results in a Table + > ### Aliases: consClustResTable + > + > ### ** Examples + > + > # create the data frame using the network, node and edge attributes + ... + > df <- netsDataFrame(network_attr_df, + + node_attr_df, + + edge_df) + > + > # run the neatmap code on df + > neat_res <- neatmap(df, scale_df = "ecdf", max_k = 3, reps = 100, + + xlab = "vars", ylab = "nets", xlab_cex = 1, ylab_cex = 1) + Error in pm[[2]] : subscript out of bounds + Calls: neatmap ... %>% -> layout -> ggplotly -> ggplotly.ggplot -> gg2list + Execution halted + ``` + +## In both + +* checking installed package size ... NOTE + ``` + installed size is 6.3Mb + ``` + +# NetFACS + +
+ +* Version: 0.5.0 +* GitHub: NA +* Source code: https://github.com/cran/NetFACS +* Date/Publication: 2022-12-06 17:32:35 UTC +* Number of recursive dependencies: 101 + +Run `revdepcheck::cloud_details(, "NetFACS")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘NetFACS-Ex.R’ failed + The error most likely occurred in: + + > ### Name: multiple_network_plot + > ### Title: Plots networks for multiple conditions + > ### Aliases: multiple_network_plot multiple.network.plot + > + > ### ** Examples + > + > data(emotions_set) + ... + 4. └─base::lapply(x$plots, plot_table, guides = guides) + 5. ├─patchwork (local) FUN(X[[i]], ...) + 6. └─patchwork:::plot_table.ggplot(X[[i]], ...) + 7. └─ggplot2::ggplotGrob(x) + 8. ├─ggplot2::ggplot_gtable(ggplot_build(x)) + 9. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) + 10. └─ggplot2::calc_element("plot.margin", theme) + 11. └─cli::cli_abort(...) + 12. └─rlang::abort(...) + Execution halted + ``` + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘netfacs_tutorial.Rmd’ + ... + Warning in grid.Call.graphics(C_text, as.graphicsAnnot(x$label), x$x, x$y, : + font family 'Arial Narrow' not found in PostScript font database + Warning in grid.Call.graphics(C_text, as.graphicsAnnot(x$label), x$x, x$y, : + font family 'Arial Narrow' not found in PostScript font database + Warning in grid.Call.graphics(C_text, as.graphicsAnnot(x$label), x$x, x$y, : + font family 'Arial Narrow' not found in PostScript font database + + When sourcing ‘netfacs_tutorial.R’: + Error: invalid font type + Execution halted + + ‘netfacs_tutorial.Rmd’ using ‘UTF-8’... failed + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘netfacs_tutorial.Rmd’ using rmarkdown + ``` + +# NHSRplotthedots + +
+ +* Version: 0.1.0 +* GitHub: NA +* Source code: https://github.com/cran/NHSRplotthedots +* Date/Publication: 2021-11-03 20:20:10 UTC +* Number of recursive dependencies: 88 + +Run `revdepcheck::cloud_details(, "NHSRplotthedots")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘NHSRplotthedots-Ex.R’ failed + The error most likely occurred in: + + > ### Name: ptd_spc + > ### Title: SPC Plotting Function + > ### Aliases: ptd_spc + > + > ### ** Examples + > + > library(NHSRdatasets) + ... + 1. ├─base (local) ``(x) + 2. └─NHSRplotthedots:::print.ptd_spc_df(x) + 3. ├─base::print(p) + 4. └─ggplot2:::print.ggplot(p) + 5. ├─ggplot2::ggplot_gtable(data) + 6. └─ggplot2:::ggplot_gtable.ggplot_built(data) + 7. └─ggplot2::calc_element("plot.margin", theme) + 8. └─cli::cli_abort(...) + 9. └─rlang::abort(...) + Execution halted + ``` + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘deviations.Rmd’ + ... + + > spc_data <- ptd_spc(df, value_field = data, date_field = date) + + > spc_data %>% plot() + labs(caption = paste("UPL = ", + + round(spc_data$upl[1], 2), ", Mean = ", round(spc_data$mean[1], + + 2), ", LPL = ..." ... [TRUNCATED] + + ... + > ptd_spc(stable_set, value_field = breaches, date_field = period, + + improvement_direction = "decrease") + + When sourcing ‘intro.R’: + Error: Theme element `plot.margin` must have class . + Execution halted + + ‘deviations.Rmd’ using ‘UTF-8’... failed + ‘intro.Rmd’ using ‘UTF-8’... failed + ‘number-of-points-required.Rmd’ using ‘UTF-8’... OK + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘deviations.Rmd’ using rmarkdown + + Quitting from lines 60-74 [unnamed-chunk-1] (deviations.Rmd) + Error: processing vignette 'deviations.Rmd' failed with diagnostics: + Theme element `plot.margin` must have class . + --- failed re-building ‘deviations.Rmd’ + + --- re-building ‘intro.Rmd’ using rmarkdown + ``` + +## In both + +* checking dependencies in R code ... NOTE + ``` + Namespaces in Imports field not imported from: + ‘NHSRdatasets’ ‘grid’ ‘utils’ + All declared Imports should be used. + ``` + +# nima + +
+ +* Version: 0.6.2 +* GitHub: https://github.com/nhejazi/nima +* Source code: https://github.com/cran/nima +* Date/Publication: 2020-03-06 06:10:03 UTC +* Number of recursive dependencies: 65 + +Run `revdepcheck::cloud_details(, "nima")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘nima-Ex.R’ failed + The error most likely occurred in: + + > ### Name: theme_jetblack + > ### Title: A jet black theme with inverted colors + > ### Aliases: theme_jetblack + > + > ### ** Examples + > + > library(ggplot2) + ... + Backtrace: + ▆ + 1. ├─base (local) ``(x) + 2. └─ggplot2:::print.ggplot(x) + 3. ├─ggplot2::ggplot_gtable(data) + 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) + 5. └─ggplot2::calc_element("plot.margin", theme) + 6. └─cli::cli_abort(...) + 7. └─rlang::abort(...) + Execution halted + ``` + +## In both + +* checking LazyData ... NOTE + ``` + 'LazyData' is specified without a 'data' directory + ``` + +# NIMAA + +
+ +* Version: 0.2.1 +* GitHub: https://github.com/jafarilab/NIMAA +* Source code: https://github.com/cran/NIMAA +* Date/Publication: 2022-04-11 14:12:45 UTC +* Number of recursive dependencies: 172 + +Run `revdepcheck::cloud_details(, "NIMAA")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘NIMAA-Ex.R’ failed + The error most likely occurred in: + + > ### Name: extractSubMatrix + > ### Title: Extract the non-missing submatrices from a given matrix. + > ### Aliases: extractSubMatrix + > + > ### ** Examples + > + > # load part of the beatAML data + ... + + row.vars = "inhibitor") + binmatnest.temperature + 13.21221 + Size of Square: 66 rows x 66 columns + Size of Rectangular_row: 6 rows x 105 columns + Size of Rectangular_col: 99 rows x 2 columns + Size of Rectangular_element_max: 59 rows x 79 columns + Error in pm[[2]] : subscript out of bounds + Calls: extractSubMatrix ... plotSubmatrix -> print -> -> ggplotly.ggplot -> gg2list + Execution halted + ``` + +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(NIMAA) + > + > test_check("NIMAA") + binmatnest.temperature + 13.21249 + Size of Square: 66 rows x 66 columns + ... + 1. └─NIMAA::extractSubMatrix(...) at test-extract-nonmissing-submatrix.R:5:3 + 2. └─NIMAA:::plotSubmatrix(...) + 3. ├─base::print(plotly::ggplotly(p)) + 4. ├─plotly::ggplotly(p) + 5. └─plotly:::ggplotly.ggplot(p) + 6. └─plotly::gg2list(...) + + [ FAIL 1 | WARN 4 | SKIP 0 | PASS 7 ] + Error: Test failures + Execution halted + ``` + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘NIMAA-vignette.Rmd’ + ... + + > beatAML_incidence_matrix <- plotIncMatrix(x = beatAML_data, + + index_nominal = c(2, 1), index_numeric = 3, print_skim = FALSE, + + plot_weigh .... [TRUNCATED] + + Na/missing values Proportion: 0.2603 + + When sourcing ‘NIMAA-vignette.R’: + Error: subscript out of bounds + Execution halted + + ‘NIMAA-vignette.Rmd’ using ‘UTF-8’... failed + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + ... + --- re-building ‘NIMAA-vignette.Rmd’ using rmarkdown + + Quitting from lines 49-57 [plotIncMatrix function] (NIMAA-vignette.Rmd) + Error: processing vignette 'NIMAA-vignette.Rmd' failed with diagnostics: + subscript out of bounds + --- failed re-building ‘NIMAA-vignette.Rmd’ + + SUMMARY: processing the following file failed: + ‘NIMAA-vignette.Rmd’ + + Error: Vignette re-building failed. + Execution halted + ``` + +## In both + +* checking installed package size ... NOTE + ``` + installed size is 6.5Mb + sub-directories of 1Mb or more: + data 2.0Mb + doc 4.0Mb + ``` + +* checking data for non-ASCII characters ... NOTE + ``` + Note: found 24 marked UTF-8 strings + ``` + +# nparACT + +
+ +* Version: 0.8 +* GitHub: NA +* Source code: https://github.com/cran/nparACT +* Date/Publication: 2017-12-20 14:25:17 UTC +* Number of recursive dependencies: 31 + +Run `revdepcheck::cloud_details(, "nparACT")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘nparACT-Ex.R’ failed + The error most likely occurred in: + + > ### Name: nparACT-package + > ### Title: Non-Parametric Measures of Actigraphy Data + > ### Aliases: nparACT-package nparACT + > ### Keywords: package + > + > ### ** Examples + > + ... + 1. └─nparACT::nparACT_base("sleepstudy", SR = 4/60) + 2. └─nparACT_auxfunctions2$nparACT_plot_hourly(data, data_hrs, SR) + 3. ├─base::print(p) + 4. └─ggplot2:::print.ggplot(p) + 5. ├─ggplot2::ggplot_gtable(data) + 6. └─ggplot2:::ggplot_gtable.ggplot_built(data) + 7. └─ggplot2::calc_element("plot.margin", theme) + 8. └─cli::cli_abort(...) + 9. └─rlang::abort(...) + Execution halted + ``` + +# nullabor + +
+ +* Version: 0.3.9 +* GitHub: https://github.com/dicook/nullabor +* Source code: https://github.com/cran/nullabor +* Date/Publication: 2020-02-25 21:50:02 UTC +* Number of recursive dependencies: 79 + +Run `revdepcheck::cloud_details(, "nullabor")` for more info + +
+ +## Newly broken + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘nullabor-examples.Rmd’ + ... + + data = dframe) + scale_colour_manual(values = c("red", "blue"), + + guide = "n ..." ... [TRUNCATED] + Warning: Using `size` aesthetic for lines was deprecated in ggplot2 3.4.0. + ℹ Please use `linewidth` instead. + Warning: Removed 20 rows containing missing values or values outside the scale range + (`geom_rect()`). + + When sourcing ‘nullabor-examples.R’: + Error: Theme element `plot.margin` must have class . + Execution halted + + ‘distances.Rmd’ using ‘UTF-8’... OK + ‘nullabor-examples.Rmd’ using ‘UTF-8’... failed + ‘nullabor.Rmd’ using ‘UTF-8’... OK + ``` + +## In both + +* checking dependencies in R code ... NOTE + ``` + Namespaces in Imports field not imported from: + ‘forecast’ ‘rlang’ ‘tsibble’ ‘viridis’ + All declared Imports should be used. + ``` + +# OBIC + +
+ +* Version: 3.0.2 +* GitHub: https://github.com/AgroCares/Open-Bodem-Index-Calculator +* Source code: https://github.com/cran/OBIC +* Date/Publication: 2024-03-05 12:40:08 UTC +* Number of recursive dependencies: 75 + +Run `revdepcheck::cloud_details(, "OBIC")` for more info + +
+ +## Newly broken + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘obic_workability.Rmd’ + ... + > gg2 <- ggplot(data = dt, aes(x = field, fill = field)) + + + geom_col(aes(y = I_P_WO)) + theme_bw() + theme(axis.text = element_text(size = 10, + .... [TRUNCATED] + + > (gg | gg2) + plot_layout(guides = "collect") + plot_annotation(caption = "Baseline workability scores.", + + theme = theme(plot.caption = element .... [TRUNCATED] + + When sourcing ‘obic_workability.R’: + Error: object is not a unit + Execution halted + + ‘description-of-the-columns.Rmd’ using ‘UTF-8’... OK + ‘obic_introduction.Rmd’ using ‘UTF-8’... OK + ‘obic_score_aggregation.Rmd’ using ‘UTF-8’... OK + ‘obic_water_functions.Rmd’ using ‘UTF-8’... OK + ‘obic_workability.Rmd’ using ‘UTF-8’... failed + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘description-of-the-columns.Rmd’ using rmarkdown + --- finished re-building ‘description-of-the-columns.Rmd’ + + --- re-building ‘obic_introduction.Rmd’ using rmarkdown + ``` + +## In both + +* checking installed package size ... NOTE + ``` + installed size is 6.0Mb + sub-directories of 1Mb or more: + data 4.0Mb + doc 1.4Mb + ``` + +# OddsPlotty + +
+ +* Version: 1.0.2 +* GitHub: https://github.com/StatsGary/OddsPlotty +* Source code: https://github.com/cran/OddsPlotty +* Date/Publication: 2021-11-13 14:40:02 UTC +* Number of recursive dependencies: 146 + +Run `revdepcheck::cloud_details(, "OddsPlotty")` for more info + +
+ +## Newly broken + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘introduction.Rmd’ + ... + > plot <- plotty$odds_plot + + > plot <- plot + ggthemes::theme_economist() + theme(legend.position = "NULL") + + > plot + geom_text(label = round(plotty$odds_plot$data$OR, + + digits = 2), hjust = 0.1, vjust = 1, color = "navy") + + When sourcing ‘introduction.R’: + Error: Theme element `plot.margin` must have class . + Execution halted + + ‘introduction.Rmd’ using ‘UTF-8’... failed + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘introduction.Rmd’ using rmarkdown + ``` + +## In both + +* checking dependencies in R code ... NOTE + ``` + Namespaces in Imports field not imported from: + ‘caret’ ‘e1071’ ‘ggthemes’ ‘mlbench’ ‘rmarkdown’ ‘tidymodels’ + All declared Imports should be used. + ``` + +# ofpetrial + +
+ +* Version: 0.1.1 +* GitHub: https://github.com/DIFM-Brain/ofpetrial +* Source code: https://github.com/cran/ofpetrial +* Date/Publication: 2024-05-15 08:50:03 UTC +* Number of recursive dependencies: 145 + +Run `revdepcheck::cloud_details(, "ofpetrial")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘ofpetrial-Ex.R’ failed + The error most likely occurred in: + + > ### Name: check_ortho_with_chars + > ### Title: Check the orthogonality with field/topographic characteristics + > ### Aliases: check_ortho_with_chars + > + > ### ** Examples + > + > data(td_single_input) + ... + 27. ├─dplyr::bind_rows(.) + 28. │ └─rlang::list2(...) + 29. └─ggExtra::ggMarginal(., type = "histogram") + 30. └─ggplot2::ggplotGrob(scatP) + 31. ├─ggplot2::ggplot_gtable(ggplot_build(x)) + 32. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) + 33. └─ggplot2::calc_element("plot.margin", theme) + 34. └─cli::cli_abort(...) + 35. └─rlang::abort(...) + Execution halted + ``` + +# OmicNavigator + +
+ +* Version: 1.13.13 +* GitHub: https://github.com/abbvie-external/OmicNavigator +* Source code: https://github.com/cran/OmicNavigator +* Date/Publication: 2023-08-25 20:40:02 UTC +* Number of recursive dependencies: 86 + +Run `revdepcheck::cloud_details(, "OmicNavigator")` for more info + +
+ +## Newly broken + +* checking tests ... ERROR + ``` + Running ‘tinytest.R’ + Running the tests in ‘tests/tinytest.R’ failed. + Complete output: + > # Test files in inst/tinytest/ + > if (requireNamespace("tinytest", quietly = TRUE)) { + + suppressMessages(tinytest::test_package("OmicNavigator")) + + } + + testAdd.R..................... 0 tests + testAdd.R..................... 0 tests + ... + testPlot.R.................... 140 tests OK + testPlot.R.................... 140 tests OK + testPlot.R.................... 141 tests OK + testPlot.R.................... 141 tests OK + testPlot.R.................... 141 tests OK + testPlot.R.................... 142 tests OK + testPlot.R.................... 142 tests OK + testPlot.R.................... 143 tests OK Error in pm[[2]] : subscript out of bounds + Calls: suppressMessages ... plotStudy -> f -> -> ggplotly.ggplot -> gg2list + Execution halted + ``` + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘OmicNavigatorAPI.Rnw’ + ... + "test_02": 0.07 + } + ] + + > resultsUpset <- getResultsUpset(study = "ABC", modelID = "model_01", + + sigValue = 0.5, operator = "<", column = "p_val") + + When sourcing ‘OmicNavigatorAPI.R’: + Error: Theme element `plot.margin` must have class . + Execution halted + + ‘OmicNavigatorAPI.Rnw’ using ‘UTF-8’... failed + ‘OmicNavigatorUsersGuide.Rnw’ using ‘UTF-8’... OK + ``` + +## In both + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘OmicNavigatorAPI.Rnw’ using Sweave + OmicNavigator R package version: 1.13.13 + The app is not installed. Install it with installApp() + Installing study "ABC" in /tmp/RtmpZpDw4T/file231e3ed1b448 + Exporting study "ABC" as an R package + Note: No maintainer email was specified. Using the placeholder: Unknown + Calculating pairwise overlaps. This may take a while... + Exported study to /tmp/RtmpZpDw4T/ONstudyABC + Success! + ... + write + l.14 + + --- failed re-building ‘OmicNavigatorUsersGuide.Rnw’ + + SUMMARY: processing the following files failed: + ‘OmicNavigatorAPI.Rnw’ ‘OmicNavigatorUsersGuide.Rnw’ + + Error: Vignette re-building failed. + Execution halted + ``` + +# oncomsm + +
+ +* Version: 0.1.4 +* GitHub: https://github.com/Boehringer-Ingelheim/oncomsm +* Source code: https://github.com/cran/oncomsm +* Date/Publication: 2023-04-17 07:00:02 UTC +* Number of recursive dependencies: 126 + +Run `revdepcheck::cloud_details(, "oncomsm")` for more info + +
+ +## Newly broken + +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(dplyr) + + Attaching package: 'dplyr' + + The following objects are masked from 'package:stats': + + filter, lag + ... + 10. └─grid::unit.c(legend.box.margin[4], widths, legend.box.margin[2]) + 11. └─grid:::identicalUnits(x) + + [ FAIL 1 | WARN 0 | SKIP 2 | PASS 59 ] + Deleting unused snapshots: + • plots/plot-mstate-srp-model-2.svg + • plots/plot-mstate-srp-model-3.svg + • plots/plot-srp-model-2.svg + Error: Test failures + Execution halted + ``` + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘avoiding-bias.Rmd’ + ... + + > mdl <- create_srpmodel(A = define_srp_prior(median_t_q05 = c(1, + + 4, 12), median_t_q95 = c(6, 8, 36), shape_q05 = c(0.99, 0.99, + + 0.99), s .... [TRUNCATED] + + > plot(mdl, confidence = 0.9) + + ... + + > plot(mdl, parameter_sample = smpl_prior, confidence = 0.75) + + When sourcing ‘oncomsm.R’: + Error: object is not a unit + Execution halted + + ‘avoiding-bias.Rmd’ using ‘UTF-8’... failed + ‘oncomsm.Rmd’ using ‘UTF-8’... failed + ‘prior-choice.Rmd’ using ‘UTF-8’... OK + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘avoiding-bias.Rmd’ using rmarkdown + + Quitting from lines 35-46 [unnamed-chunk-2] (avoiding-bias.Rmd) + Error: processing vignette 'avoiding-bias.Rmd' failed with diagnostics: + object is not a unit + --- failed re-building ‘avoiding-bias.Rmd’ + + --- re-building ‘oncomsm.Rmd’ using rmarkdown + + Quitting from lines 211-215 [plotting-the-prior] (oncomsm.Rmd) + Error: processing vignette 'oncomsm.Rmd' failed with diagnostics: + object is not a unit + --- failed re-building ‘oncomsm.Rmd’ + + --- re-building ‘prior-choice.Rmd’ using rmarkdown + ``` + +## In both + +* checking installed package size ... NOTE + ``` + installed size is 59.1Mb + sub-directories of 1Mb or more: + doc 1.1Mb + libs 56.9Mb + ``` + +* checking for GNU extensions in Makefiles ... NOTE + ``` + GNU make is a SystemRequirements. + ``` + +# ontophylo + +
+ +* Version: 1.1.3 +* GitHub: https://github.com/diegosasso/ontophylo +* Source code: https://github.com/cran/ontophylo +* Date/Publication: 2024-01-10 10:33:17 UTC +* Number of recursive dependencies: 101 + +Run `revdepcheck::cloud_details(, "ontophylo")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘ontophylo-Ex.R’ failed + The error most likely occurred in: + + > ### Name: edgeplot + > ### Title: Plot edge profiles and contMap + > ### Aliases: edgeplot + > + > ### ** Examples + > + > data("hym_tree", "hym_kde") + ... + 2. │ └─base::withCallingHandlers(...) + 3. └─ontophylo::edgeplot(map_stat, prof_stat) + 4. ├─base::print(plot_edgeprof, vp = vp) + 5. └─ggplot2:::print.ggplot(plot_edgeprof, vp = vp) + 6. ├─ggplot2::ggplot_gtable(data) + 7. └─ggplot2:::ggplot_gtable.ggplot_built(data) + 8. └─ggplot2::calc_element("plot.margin", theme) + 9. └─cli::cli_abort(...) + 10. └─rlang::abort(...) + Execution halted + ``` + +## In both + +* checking installed package size ... NOTE + ``` + installed size is 7.3Mb + sub-directories of 1Mb or more: + data 7.0Mb + ``` + +* checking data for non-ASCII characters ... NOTE + ``` + Note: found 42 marked UTF-8 strings + ``` + +# OpenLand + +
+ +* Version: 1.0.3 +* GitHub: https://github.com/reginalexavier/OpenLand +* Source code: https://github.com/cran/OpenLand +* Date/Publication: 2024-05-03 13:40:02 UTC +* Number of recursive dependencies: 119 + +Run `revdepcheck::cloud_details(, "OpenLand")` for more info + +
+ +## Newly broken + +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(OpenLand) + > + > test_check("OpenLand") + [ FAIL 1 | WARN 0 | SKIP 0 | PASS 103 ] + + ══ Failed tests ════════════════════════════════════════════════════════════════ + ... + 9. └─ggplot2 (local) FUN(X[[i]], ...) + 10. ├─ggplot2::ggplot_gtable(ggplot_build(x)) + 11. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) + 12. └─ggplot2::calc_element("plot.margin", theme) + 13. └─cli::cli_abort(...) + 14. └─rlang::abort(...) + + [ FAIL 1 | WARN 0 | SKIP 0 | PASS 103 ] + Error: Test failures + Execution halted + ``` + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘openland_vignette.Rmd’ + ... + + + + > plot(testSL$interval_lvl, labels = c(leftlabel = "Interval Change Area (%)", + + rightlabel = "Annual Change Area (%)"), marginplot = c(-8, + + .... [TRUNCATED] + + When sourcing ‘openland_vignette.R’: + Error: Theme element `plot.margin` must have class . + Execution halted + + ‘openland_vignette.Rmd’ using ‘UTF-8’... failed + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + ... + --- re-building ‘openland_vignette.Rmd’ using rmarkdown + trying URL 'https://zenodo.org/record/3685230/files/SaoLourencoBasin.rda?download=1' + Content type 'application/octet-stream' length 5309066 bytes (5.1 MB) + ================================================== + downloaded 5.1 MB + + + Quitting from lines 184-191 [unnamed-chunk-10] (openland_vignette.Rmd) + Error: processing vignette 'openland_vignette.Rmd' failed with diagnostics: + Theme element `plot.margin` must have class . + --- failed re-building ‘openland_vignette.Rmd’ + + SUMMARY: processing the following file failed: + ‘openland_vignette.Rmd’ + + Error: Vignette re-building failed. + Execution halted + ``` + +# ordbetareg + +
+ +* Version: 0.7.2 +* GitHub: https://github.com/saudiwin/ordbetareg_pack +* Source code: https://github.com/cran/ordbetareg +* Date/Publication: 2023-08-10 07:30:02 UTC +* Number of recursive dependencies: 182 + +Run `revdepcheck::cloud_details(, "ordbetareg")` for more info + +
+ +## Newly broken + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘package_introduction.Rmd’ + ... + + theme_minimal() + theme(panel.grid = element_blank()) + scale_x_continuous(brea .... [TRUNCATED] + + > plots <- pp_check_ordbeta(ord_fit_mean, ndraws = 100, + + outcome_label = "Thermometer Rating", new_theme = ggthemes::theme_economist()) + + > plots$discrete + + When sourcing ‘package_introduction.R’: + Error: Theme element `plot.margin` must have class . + Execution halted + + ‘package_introduction.Rmd’ using ‘UTF-8’... failed + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘package_introduction.Rmd’ using rmarkdown + ``` + +## In both + +* checking installed package size ... NOTE + ``` + installed size is 8.1Mb + sub-directories of 1Mb or more: + data 7.5Mb + ``` + +* checking data for non-ASCII characters ... NOTE + ``` + Note: found 36 marked UTF-8 strings + ``` + +# otsad + +
+ +* Version: 0.2.0 +* GitHub: https://github.com/alaineiturria/otsad +* Source code: https://github.com/cran/otsad +* Date/Publication: 2019-09-06 09:50:02 UTC +* Number of recursive dependencies: 109 + +Run `revdepcheck::cloud_details(, "otsad")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘otsad-Ex.R’ failed + The error most likely occurred in: + + > ### Name: CpKnnCad + > ### Title: Classic processing KNN based Conformal Anomaly Detector + > ### (KNN-CAD) + > ### Aliases: CpKnnCad + > + > ### ** Examples + > + ... + + ncm.type = "ICAD", + + reducefp = TRUE + + ) + > + > ## Plot results + > res <- cbind(df, result) + > PlotDetections(res, title = "KNN-CAD ANOMALY DETECTOR") + Error in pm[[2]] : subscript out of bounds + Calls: PlotDetections -> -> ggplotly.ggplot -> gg2list + Execution halted + ``` + +## In both + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + ... + --- re-building ‘otsad.Rnw’ using knitr + Error: processing vignette 'otsad.Rnw' failed with diagnostics: + Running 'texi2dvi' on 'otsad.tex' failed. + LaTeX errors: + ! LaTeX Error: File `colortbl.sty' not found. + + Type X to quit or to proceed, + or enter new name. (Default extension: sty) + ... + l.12 \makeatletter + ^^M + ! ==> Fatal error occurred, no output PDF file produced! + --- failed re-building ‘otsad.Rnw’ + + SUMMARY: processing the following file failed: + ‘otsad.Rnw’ + + Error: Vignette re-building failed. + Execution halted + ``` + +# OutliersO3 + +
+ +* Version: 0.6.3 +* GitHub: NA +* Source code: https://github.com/cran/OutliersO3 +* Date/Publication: 2020-04-25 00:10:02 UTC +* Number of recursive dependencies: 145 + +Run `revdepcheck::cloud_details(, "OutliersO3")` for more info + +
+ +## Newly broken + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘DrawingO3plots.Rmd’ + ... + > O3s <- O3prep(data, method = "HDo", tols = 0.05, boxplotLimits = 6) + + > O3s1 <- O3plotT(O3s, caseNames = Election2005$Name) + + > O3s1$gO3 + theme(plot.margin = unit(c(0, 2, 0, 0), + + "cm")) + + ... + + 1, 0, 0), "cm")), O3r1$gpcp, ncol = 1, heights = c(2, 1)) + + When sourcing ‘MultTolLevels.R’: + Error: Theme element `plot.margin` must have class . + Execution halted + + ‘DrawingO3plots.Rmd’ using ‘UTF-8’... failed + ‘MultTolLevels.Rmd’ using ‘UTF-8’... failed + ‘PCPsO3.Rmd’ using ‘UTF-8’... OK + ‘xtraO3methods.Rmd’ using ‘UTF-8’... OK + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘DrawingO3plots.Rmd’ using rmarkdown + + Quitting from lines 25-32 [unnamed-chunk-1] (DrawingO3plots.Rmd) + Error: processing vignette 'DrawingO3plots.Rmd' failed with diagnostics: + Theme element `plot.margin` must have class . + --- failed re-building ‘DrawingO3plots.Rmd’ + + --- re-building ‘MultTolLevels.Rmd’ using rmarkdown + ``` + +# palettes + +
+ +* Version: 0.2.0 +* GitHub: https://github.com/mccarthy-m-g/palettes +* Source code: https://github.com/cran/palettes +* Date/Publication: 2024-02-05 11:50:02 UTC +* Number of recursive dependencies: 110 + +Run `revdepcheck::cloud_details(, "palettes")` for more info + +
+ +## Newly broken + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘biscale.Rmd’ + ... + + "2-2") + + > names(unnamed_colour_vector) + [1] "1-1" "2-1" "1-2" "2-2" + + > bi_pal(named_colour_vector, dim = 2) + + ... + When sourcing ‘biscale.R’: + Error: Theme element `plot.margin` must have class . + Execution halted + + ‘biscale.Rmd’ using ‘UTF-8’... failed + ‘compatibility.Rmd’ using ‘UTF-8’... OK + ‘creating-packages.Rmd’ using ‘UTF-8’... OK + ‘ggplot2.Rmd’ using ‘UTF-8’... OK + ‘gt.Rmd’ using ‘UTF-8’... OK + ‘palettes.Rmd’ using ‘UTF-8’... OK + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘biscale.Rmd’ using rmarkdown + + Quitting from lines 66-67 [unnamed-chunk-4] (biscale.Rmd) + Error: processing vignette 'biscale.Rmd' failed with diagnostics: + Theme element `plot.margin` must have class . + --- failed re-building ‘biscale.Rmd’ + + --- re-building ‘compatibility.Rmd’ using rmarkdown + --- finished re-building ‘compatibility.Rmd’ + + --- re-building ‘creating-packages.Rmd’ using rmarkdown + --- finished re-building ‘creating-packages.Rmd’ + + --- re-building ‘ggplot2.Rmd’ using rmarkdown + ``` + +# ParBayesianOptimization + +
+ +* Version: 1.2.6 +* GitHub: https://github.com/AnotherSamWilson/ParBayesianOptimization +* Source code: https://github.com/cran/ParBayesianOptimization +* Date/Publication: 2022-10-18 14:47:54 UTC +* Number of recursive dependencies: 107 + +Run `revdepcheck::cloud_details(, "ParBayesianOptimization")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘ParBayesianOptimization-Ex.R’ failed + The error most likely occurred in: + + > ### Name: plot.bayesOpt + > ### Title: Plot a 'bayesOpt' object + > ### Aliases: plot.bayesOpt + > + > ### ** Examples + > + > scoringFunction <- function(x) { + ... + 3. └─ParBayesianOptimization:::plot.bayesOpt(Results) + 4. └─ggpubr::ggarrange(...) + 5. └─ggpubr::get_legend(plots) + 6. └─ggpubr:::.get_legend(p[[i]], position = position) + 7. ├─ggplot2::ggplot_gtable(ggplot_build(p)) + 8. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(p)) + 9. └─ggplot2::calc_element("plot.margin", theme) + 10. └─cli::cli_abort(...) + 11. └─rlang::abort(...) + Execution halted + ``` + +# patchwork + +
+ +* Version: 1.2.0 +* GitHub: https://github.com/thomasp85/patchwork +* Source code: https://github.com/cran/patchwork +* Date/Publication: 2024-01-08 14:40:02 UTC +* Number of recursive dependencies: 80 + +Run `revdepcheck::cloud_details(, "patchwork")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘patchwork-Ex.R’ failed + The error most likely occurred in: + + > ### Name: free + > ### Title: Free a plot from alignment + > ### Aliases: free + > + > ### ** Examples + > + > # Sometimes you have a plot that defies good composition alginment, e.g. due + ... + > p1 / p2 + > + > # We can fix this be using free + > free(p1) / p2 + > + > # We can still collect guides like before + > free(p1) / p2 + plot_layout(guides = "collect") + Error in identicalUnits(x) : object is not a unit + Calls: ... assemble_guides -> guides_build -> unit.c -> identicalUnits + Execution halted + ``` + +# pathfindR + +
+ +* Version: 2.4.1 +* GitHub: https://github.com/egeulgen/pathfindR +* Source code: https://github.com/cran/pathfindR +* Date/Publication: 2024-05-04 15:30:05 UTC +* Number of recursive dependencies: 150 + +Run `revdepcheck::cloud_details(, "pathfindR")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘pathfindR-Ex.R’ failed + The error most likely occurred in: + + > ### Name: UpSet_plot + > ### Title: Create UpSet Plot of Enriched Terms + > ### Aliases: UpSet_plot + > + > ### ** Examples + > + > UpSet_plot(example_pathfindR_output) + ... + 9. └─ggplot2:::scale_apply(layer_data, x_vars, "map", SCALE_X, self$panel_scales_x) + 10. └─base::lapply(...) + 11. └─ggplot2 (local) FUN(X[[i]], ...) + 12. └─base::lapply(...) + 13. └─ggplot2 (local) FUN(X[[i]], ...) + 14. └─scales[[i]][[method]](data[[var]][scale_index[[i]]]) + 15. └─ggplot2 (local) map(..., self = self) + 16. └─cli::cli_abort(...) + 17. └─rlang::abort(...) + Execution halted + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘comparing_results.Rmd’ using rmarkdown + ``` + +## In both + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘intro_vignette.Rmd’ + ... + + + + > output_df <- run_pathfindR(example_pathfindR_input, + + pin_name_path = "/path/to/myPIN.sif") + + When sourcing ‘intro_vignette.R’: + ... + When sourcing ‘visualization_vignette.R’: + Error: The `palette` function must return at least 21 values. + Execution halted + + ‘comparing_results.Rmd’ using ‘UTF-8’... OK + ‘intro_vignette.Rmd’ using ‘UTF-8’... failed + ‘manual_execution.Rmd’ using ‘UTF-8’... failed + ‘non_hs_analysis.Rmd’ using ‘UTF-8’... failed + ‘obtain_data.Rmd’ using ‘UTF-8’... failed + ‘visualization_vignette.Rmd’ using ‘UTF-8’... failed + ``` + +# pdSpecEst + +
+ +* Version: 1.2.4 +* GitHub: https://github.com/JorisChau/pdSpecEst +* Source code: https://github.com/cran/pdSpecEst +* Date/Publication: 2020-01-08 09:10:07 UTC +* Number of recursive dependencies: 88 + +Run `revdepcheck::cloud_details(, "pdSpecEst")` for more info + +
+ +## Newly broken + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘wavelet_est_clust.Rmd’ + ... + Warning: Use of `longdata$Var1` is discouraged. + ℹ Use `Var1` instead. + Warning: Use of `longdata$Var2` is discouraged. + ℹ Use `Var2` instead. + Warning: Use of `longdata$value` is discouraged. + ℹ Use `value` instead. + + When sourcing ‘wavelet_est_clust.R’: + Error: Theme element `plot.margin` must have class . + Execution halted + + ‘depth_ranktests.Rmd’ using ‘UTF-8’... OK + ‘wavelet_est_clust.Rmd’ using ‘UTF-8’... failed + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘depth_ranktests.Rmd’ using rmarkdown + + warning: logmat_sympd(): imaginary components on diagonal are non-zero + + warning: logmat_sympd(): given matrix is not hermitian + --- finished re-building ‘depth_ranktests.Rmd’ + + --- re-building ‘wavelet_est_clust.Rmd’ using rmarkdown + ``` + +## In both + +* checking C++ specification ... NOTE + ``` + Specified C++11: please drop specification unless essential + ``` + +* checking installed package size ... NOTE + ``` + installed size is 9.1Mb + sub-directories of 1Mb or more: + libs 8.0Mb + ``` + +* checking LazyData ... NOTE + ``` + 'LazyData' is specified without a 'data' directory + ``` + +# pdxTrees + +
+ +* Version: 0.4.0 +* GitHub: https://github.com/mcconvil/pdxTrees +* Source code: https://github.com/cran/pdxTrees +* Date/Publication: 2020-08-17 14:00:02 UTC +* Number of recursive dependencies: 105 + +Run `revdepcheck::cloud_details(, "pdxTrees")` for more info + +
+ +## Newly broken + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘pdxTrees-vignette.Rmd’ + ... + + y = Pollution_Removal_value, color = Mature_Size)) + geom_point(size = 2, + + .... [TRUNCATED] + + > berkeley_graph + transition_states(states = Mature_Size, + + transition_length = 10, state_length = 8) + enter_grow() + + + exit_shrink() + + When sourcing ‘pdxTrees-vignette.R’: + Error: argument "theme" is missing, with no default + Execution halted + + ‘pdxTrees-vignette.Rmd’ using ‘UTF-8’... failed + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘pdxTrees-vignette.Rmd’ using rmarkdown + ``` + +## In both + +* checking LazyData ... NOTE + ``` + 'LazyData' is specified without a 'data' directory + ``` + +# personalized + +
+ +* Version: 0.2.7 +* GitHub: https://github.com/jaredhuling/personalized +* Source code: https://github.com/cran/personalized +* Date/Publication: 2022-06-27 20:20:03 UTC +* Number of recursive dependencies: 94 + +Run `revdepcheck::cloud_details(, "personalized")` for more info + +
+ +## Newly broken + +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > Sys.setenv("R_TESTS" = "") + > library(testthat) + > library(personalized) + Loading required package: glmnet + Loading required package: Matrix + Loaded glmnet 4.1-8 + Loading required package: mgcv + ... + 4. └─personalized:::plot.subgroup_validated(subgrp.val, type = "stability") + 5. ├─plotly::subplot(...) + 6. │ └─plotly:::dots2plots(...) + 7. ├─plotly::ggplotly(p.primary, tooltip = paste0("tooltip", 1:4)) + 8. └─plotly:::ggplotly.ggplot(...) + 9. └─plotly::gg2list(...) + + [ FAIL 1 | WARN 2 | SKIP 0 | PASS 215 ] + Error: Test failures + Execution halted + ``` + +# PGRdup + +
+ +* Version: 0.2.3.9 +* GitHub: https://github.com/aravind-j/PGRdup +* Source code: https://github.com/cran/PGRdup +* Date/Publication: 2023-08-31 22:10:16 UTC +* Number of recursive dependencies: 69 + +Run `revdepcheck::cloud_details(, "PGRdup")` for more info + +
+ +## Newly broken + +* checking re-building of vignette outputs ... ERROR + ``` + Error(s) in re-building vignettes: + ... + --- re-building ‘Introduction.Rmd’ using rmarkdown_notangle + + Quitting from lines 1195-1203 [unnamed-chunk-59] (Introduction.Rmd) + Error: processing vignette 'Introduction.Rmd' failed with diagnostics: + Theme element `plot.margin` must have class . + --- failed re-building ‘Introduction.Rmd’ + + SUMMARY: processing the following file failed: + ‘Introduction.Rmd’ + + Error: Vignette re-building failed. + Execution halted + ``` + +## Newly fixed + +* checking re-building of vignette outputs ... WARNING + ``` + Error(s) in re-building vignettes: + --- re-building ‘Introduction.Rmd’ using rmarkdown_notangle + tlmgr: package repository https://mirrors.rit.edu/CTAN/systems/texlive/tlnet (verified) + [1/1, ??:??/??:??] install: colortbl [4k] + running mktexlsr ... + done running mktexlsr. + tlmgr: package log updated: /opt/TinyTeX/texmf-var/web2c/tlmgr.log + tlmgr: command log updated: /opt/TinyTeX/texmf-var/web2c/tlmgr-commands.log + + tlmgr: Remote database (revision 71410 of the texlive-scripts package) + ... + + Error: processing vignette 'Introduction.Rmd' failed with diagnostics: + LaTeX failed to compile /tmp/workdir/PGRdup/old/PGRdup.Rcheck/vign_test/PGRdup/vignettes/Introduction.tex. See https://yihui.org/tinytex/r/#debugging for debugging tips. See Introduction.log for more info. + --- failed re-building ‘Introduction.Rmd’ + + SUMMARY: processing the following file failed: + ‘Introduction.Rmd’ + + Error: Vignette re-building failed. + Execution halted + ``` + +# Plasmidprofiler + +
+ +* Version: 0.1.6 +* GitHub: NA +* Source code: https://github.com/cran/Plasmidprofiler +* Date/Publication: 2017-01-06 01:10:47 +* Number of recursive dependencies: 90 + +Run `revdepcheck::cloud_details(, "Plasmidprofiler")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘Plasmidprofiler-Ex.R’ failed + The error most likely occurred in: + + > ### Name: main + > ### Title: Main: Run everything + > ### Aliases: main + > + > ### ** Examples + > + > main(blastdata, + ... + Saving 12 x 7 in image + Warning: Vectorized input to `element_text()` is not officially supported. + ℹ Results may be unexpected or may change in future versions of ggplot2. + Warning in geom_tile(aes(x = Plasmid, y = Sample, label = AMR_gene, fill = Inc_group, : + Ignoring unknown aesthetics: label and text + Warning: Use of `report$Sureness` is discouraged. + ℹ Use `Sureness` instead. + Error in pm[[2]] : subscript out of bounds + Calls: main ... -> ggplotly -> ggplotly.ggplot -> gg2list + Execution halted + ``` + +# plotDK + +
+ +* Version: 0.1.0 +* GitHub: NA +* Source code: https://github.com/cran/plotDK +* Date/Publication: 2021-10-01 08:00:02 UTC +* Number of recursive dependencies: 86 + +Run `revdepcheck::cloud_details(, "plotDK")` for more info + +
+ +## Newly broken + +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(plotDK) + > + > test_check("plotDK") + [ FAIL 1 | WARN 0 | SKIP 0 | PASS 49 ] + + ══ Failed tests ════════════════════════════════════════════════════════════════ + ... + Backtrace: + ▆ + 1. └─plotDK::plotDK(...) at test-plotDK.R:32:5 + 2. ├─plotly::ggplotly(p, tooltip = c("text", "fill")) + 3. └─plotly:::ggplotly.ggplot(p, tooltip = c("text", "fill")) + 4. └─plotly::gg2list(...) + + [ FAIL 1 | WARN 0 | SKIP 0 | PASS 49 ] + Error: Test failures + Execution halted + ``` + +## In both + +* checking dependencies in R code ... NOTE + ``` + Namespace in Imports field not imported from: ‘mapproj’ + All declared Imports should be used. + ``` + +* checking data for non-ASCII characters ... NOTE + ``` + Note: found 12992 marked UTF-8 strings + ``` + +# plotly + +
+ +* Version: 4.10.4 +* GitHub: https://github.com/plotly/plotly.R +* Source code: https://github.com/cran/plotly +* Date/Publication: 2024-01-13 22:40:02 UTC +* Number of recursive dependencies: 147 + +Run `revdepcheck::cloud_details(, "plotly")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘plotly-Ex.R’ failed + The error most likely occurred in: + + > ### Name: style + > ### Title: Modify trace(s) + > ### Aliases: style + > + > ### ** Examples + > + > ## Don't show: + ... + + # this clobbers the previously supplied marker.line.color + + style(p, marker.line = list(width = 2.5), marker.size = 10) + + ## Don't show: + + }) # examplesIf + > (p <- ggplotly(qplot(data = mtcars, wt, mpg, geom = c("point", "smooth")))) + Warning: `qplot()` was deprecated in ggplot2 3.4.0. + `geom_smooth()` using method = 'loess' and formula = 'y ~ x' + Error in pm[[2]] : subscript out of bounds + Calls: ... eval -> eval -> ggplotly -> ggplotly.ggplot -> gg2list + Execution halted + ``` + +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library("testthat") + > library("plotly") + Loading required package: ggplot2 + + Attaching package: 'plotly' + + The following object is masked from 'package:ggplot2': + ... + • plotly-subplot/subplot-bump-axis-annotation.svg + • plotly-subplot/subplot-bump-axis-image.svg + • plotly-subplot/subplot-bump-axis-shape-shared.svg + • plotly-subplot/subplot-bump-axis-shape.svg + • plotly-subplot/subplot-reposition-annotation.svg + • plotly-subplot/subplot-reposition-image.svg + • plotly-subplot/subplot-reposition-shape-fixed.svg + • plotly-subplot/subplot-reposition-shape.svg + Error: Test failures + Execution halted + ``` + +## In both + +* checking installed package size ... NOTE + ``` + installed size is 7.1Mb + sub-directories of 1Mb or more: + R 1.0Mb + htmlwidgets 4.0Mb + ``` + +# pmartR + +
+ +* Version: 2.4.5 +* GitHub: https://github.com/pmartR/pmartR +* Source code: https://github.com/cran/pmartR +* Date/Publication: 2024-05-21 15:50:02 UTC +* Number of recursive dependencies: 149 + +Run `revdepcheck::cloud_details(, "pmartR")` for more info + +
+ +## Newly broken + +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(pmartR) + > + > test_check("pmartR") + [ FAIL 1 | WARN 1 | SKIP 11 | PASS 2375 ] + + ══ Skipped tests (11) ══════════════════════════════════════════════════════════ + ... + • plots/plot-spansres-color-high-color-low.svg + • plots/plot-spansres.svg + • plots/plot-statres-anova-volcano.svg + • plots/plot-statres-anova.svg + • plots/plot-statres-combined-volcano.svg + • plots/plot-statres-combined.svg + • plots/plot-statres-gtest.svg + • plots/plot-totalcountfilt.svg + Error: Test failures + Execution halted + ``` + +## In both + +* checking installed package size ... NOTE + ``` + installed size is 10.4Mb + sub-directories of 1Mb or more: + R 1.5Mb + help 1.5Mb + libs 6.3Mb + ``` + +# pmxTools + +
+ +* Version: 1.3 +* GitHub: https://github.com/kestrel99/pmxTools +* Source code: https://github.com/cran/pmxTools +* Date/Publication: 2023-02-21 16:00:08 UTC +* Number of recursive dependencies: 85 + +Run `revdepcheck::cloud_details(, "pmxTools")` for more info + +
+ +## Newly broken + +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(pmxTools) + Loading required package: patchwork + > + > test_check("pmxTools") + [ FAIL 1 | WARN 1 | SKIP 12 | PASS 110 ] + + ... + 24. └─handlers[[1L]](cnd) + 25. └─cli::cli_abort(...) + 26. └─rlang::abort(...) + + [ FAIL 1 | WARN 1 | SKIP 12 | PASS 110 ] + Deleting unused snapshots: + • plot/conditioned-distplot.svg + • plot/perc.svg + Error: Test failures + Execution halted + ``` + +## In both + +* checking Rd cross-references ... NOTE + ``` + Package unavailable to check Rd xrefs: ‘DiagrammeR’ + ``` + +# politeness + +
+ +* Version: 0.9.3 +* GitHub: NA +* Source code: https://github.com/cran/politeness +* Date/Publication: 2023-11-12 13:13:26 UTC +* Number of recursive dependencies: 93 + +Run `revdepcheck::cloud_details(, "politeness")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘politeness-Ex.R’ failed + The error most likely occurred in: + + > ### Name: politenessPlot + > ### Title: Politeness plot + > ### Aliases: politenessPlot + > + > ### ** Examples + > + > + ... + Backtrace: + ▆ + 1. ├─base (local) ``(x) + 2. └─ggplot2:::print.ggplot(x) + 3. ├─ggplot2::ggplot_gtable(data) + 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) + 5. └─ggplot2::calc_element("plot.margin", theme) + 6. └─cli::cli_abort(...) + 7. └─rlang::abort(...) + Execution halted + ``` + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘politeness.Rmd’ + ... + 28 0 0 0 0 0 + 29 0 1 0 0 0 + 30 0 1 0 1 0 + + > politeness::politenessPlot(df_politeness, split = phone_offers$condition, + + split_levels = c("Tough", "Warm"), split_name = "Condition") + + When sourcing ‘politeness.R’: + Error: Theme element `plot.margin` must have class . + Execution halted + + ‘politeness.Rmd’ using ‘UTF-8’... failed + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + ... + --- re-building ‘politeness.Rmd’ using rmarkdown + + Quitting from lines 119-123 [unnamed-chunk-8] (politeness.Rmd) + Error: processing vignette 'politeness.Rmd' failed with diagnostics: + Theme element `plot.margin` must have class . + --- failed re-building ‘politeness.Rmd’ + + SUMMARY: processing the following file failed: + ‘politeness.Rmd’ + + Error: Vignette re-building failed. + Execution halted + ``` + +## In both + +* checking data for non-ASCII characters ... NOTE + ``` + Note: found 52 marked UTF-8 strings + ``` + +# posterior + +
+ +* Version: 1.5.0 +* GitHub: https://github.com/stan-dev/posterior +* Source code: https://github.com/cran/posterior +* Date/Publication: 2023-10-31 08:30:02 UTC +* Number of recursive dependencies: 120 + +Run `revdepcheck::cloud_details(, "posterior")` for more info + +
+ +## Newly broken + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + ... + --- re-building ‘posterior.Rmd’ using rmarkdown + --- finished re-building ‘posterior.Rmd’ + + --- re-building ‘rvar.Rmd’ using rmarkdown + + Quitting from lines 526-529 [mixture] (rvar.Rmd) + Error: processing vignette 'rvar.Rmd' failed with diagnostics: + Problem while setting up geom aesthetics. + ... + NULL, NULL, 1.2, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 0.2, NULL, list(NULL, NULL, NULL, 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, NULL, NULL, NULL, TRUE), NULL, "right", NULL, NULL, NULL, "center", NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 0, list(), 2, list("grey92", NA, NULL, NULL, TRUE), list(), NULL, NULL, NULL, list("white", NULL, NULL, NULL, FALSE, "white", TRUE), NULL, list(NULL, 0.5, NULL, NULL, FALSE, NULL, TRUE), NULL, + NULL, NULL, NULL, FALSE, list(NULL, "white", NULL, NULL, TRUE), list(NULL, NULL, NULL, 1.2, 0, 1, NULL, NULL, c(0, 0, 5.5, 0), NULL, TRUE), "panel", list(NULL, NULL, NULL, NULL, 0, 1, NULL, NULL, c(0, 0, 5.5, 0), NULL, TRUE), list(NULL, NULL, NULL, 0.8, 1, 1, NULL, NULL, c(5.5, 0, 0, 0), NULL, TRUE), "panel", list(NULL, NULL, NULL, 1.2, 0.5, 0.5, NULL, NULL, NULL, NULL, TRUE), "topleft", NULL, NULL, list("grey85", NA, NULL, NULL, TRUE), NULL, NULL, "inherit", "inside", list(NULL, NULL, "grey10", + 0.8, NULL, NULL, NULL, NULL, c(4.4, 4.4, 4.4, 4.4), NULL, TRUE), NULL, NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, NULL, -90, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, NULL, 90, NULL, NULL, NULL, TRUE), NULL, 2.75, 2.75)) + --- failed re-building ‘rvar.Rmd’ + + SUMMARY: processing the following file failed: + ‘rvar.Rmd’ + + Error: Vignette re-building failed. + Execution halted + ``` + +## In both + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘rvar.Rmd’ + ... + > y + rvar<4000>[3] mean ± sd: + [1] 3.00 ± 1.00 2.02 ± 0.99 0.96 ± 0.99 + + > X + y + + When sourcing ‘rvar.R’: + Error: Cannot broadcast array of shape [4000,3,1] to array of shape [4000,4,3]: + All dimensions must be 1 or equal. + Execution halted + + ‘posterior.Rmd’ using ‘UTF-8’... OK + ‘rvar.Rmd’ using ‘UTF-8’... failed + ``` + +# PPQplan + +
+ +* Version: 1.1.0 +* GitHub: https://github.com/allenzhuaz/PPQplan +* Source code: https://github.com/cran/PPQplan +* Date/Publication: 2020-10-08 04:30:06 UTC +* Number of recursive dependencies: 119 + +Run `revdepcheck::cloud_details(, "PPQplan")` for more info + +
+ +## Newly broken + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘PPQnote.Rmd’ using rmarkdown + --- finished re-building ‘PPQnote.Rmd’ + + --- re-building ‘PPQplan-vignette.Rmd’ using rmarkdown + ``` + +## In both + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘PPQplan-vignette.Rmd’ + ... + + > devtools::load_all() + + When sourcing ‘PPQplan-vignette.R’: + Error: Could not find a root 'DESCRIPTION' file that starts with '^Package' in + '/tmp/RtmpklfDYr/file150247a66b97/vignettes'. + ℹ Are you in your project directory and does your project have a 'DESCRIPTION' + file? + Execution halted + + ‘PPQnote.Rmd’ using ‘UTF-8’... OK + ‘PPQplan-vignette.Rmd’ using ‘UTF-8’... failed + ``` + +* checking installed package size ... NOTE + ``` + installed size is 12.1Mb + sub-directories of 1Mb or more: + doc 12.0Mb + ``` + +* checking LazyData ... NOTE + ``` + 'LazyData' is specified without a 'data' directory + ``` + +# ppseq + +
+ +* Version: 0.2.4 +* GitHub: https://github.com/zabore/ppseq +* Source code: https://github.com/cran/ppseq +* Date/Publication: 2024-04-04 18:20:02 UTC +* Number of recursive dependencies: 106 + +Run `revdepcheck::cloud_details(, "ppseq")` for more info + +
+ +## Newly broken + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘one_sample_expansion.Rmd’ + ... + + + + + > ptest <- plot(one_sample_cal_tbl, type1_range = c(0.05, + + 0.1), minimum_power = 0.7, plotly = TRUE) + + ... + + > ptest <- plot(two_sample_cal_tbl, type1_range = c(0.05, + + 0.1), minimum_power = 0.7, plotly = TRUE) + + When sourcing ‘two_sample_randomized.R’: + Error: subscript out of bounds + Execution halted + + ‘one_sample_expansion.Rmd’ using ‘UTF-8’... failed + ‘two_sample_randomized.Rmd’ using ‘UTF-8’... failed + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + ... + --- re-building ‘one_sample_expansion.Rmd’ using rmarkdown + + Quitting from lines 183-188 [unnamed-chunk-13] (one_sample_expansion.Rmd) + Error: processing vignette 'one_sample_expansion.Rmd' failed with diagnostics: + subscript out of bounds + --- failed re-building ‘one_sample_expansion.Rmd’ + + --- re-building ‘two_sample_randomized.Rmd’ using rmarkdown + ... + Quitting from lines 179-184 [unnamed-chunk-13] (two_sample_randomized.Rmd) + Error: processing vignette 'two_sample_randomized.Rmd' failed with diagnostics: + subscript out of bounds + --- failed re-building ‘two_sample_randomized.Rmd’ + + SUMMARY: processing the following files failed: + ‘one_sample_expansion.Rmd’ ‘two_sample_randomized.Rmd’ + + Error: Vignette re-building failed. + Execution halted + ``` + +## In both + +* checking installed package size ... NOTE + ``` + installed size is 11.0Mb + sub-directories of 1Mb or more: + doc 10.5Mb + ``` + +# PPtreeregViz + +
+ +* Version: 2.0.5 +* GitHub: https://github.com/sunsmiling/PPtreeregViz +* Source code: https://github.com/cran/PPtreeregViz +* Date/Publication: 2022-12-23 19:20:05 UTC +* Number of recursive dependencies: 125 + +Run `revdepcheck::cloud_details(, "PPtreeregViz")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘PPtreeregViz-Ex.R’ failed + The error most likely occurred in: + + > ### Name: PPregNodeViz + > ### Title: Node visualization + > ### Aliases: PPregNodeViz + > ### Keywords: tree + > + > ### ** Examples + > + ... + ▆ + 1. └─PPtreeregViz::PPregNodeViz(Model, node.id = 1) + 2. └─ggExtra::ggMarginal(...) + 3. └─ggplot2::ggplotGrob(scatP) + 4. ├─ggplot2::ggplot_gtable(ggplot_build(x)) + 5. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) + 6. └─ggplot2::calc_element("plot.margin", theme) + 7. └─cli::cli_abort(...) + 8. └─rlang::abort(...) + Execution halted + ``` + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘PPtreeregViz.Rmd’ + ... + + > plot(Tree.Imp) + + > plot(Tree.Imp, marginal = TRUE, num_var = 5) + + > PPregNodeViz(Model, node.id = 1) + + When sourcing ‘PPtreeregViz.R’: + Error: Theme element `plot.margin` must have class . + Execution halted + + ‘PPtreeregViz.Rmd’ using ‘UTF-8’... failed + ``` + +* checking re-building of vignette outputs ... NOTE ``` - installed size is 8.1Mb - sub-directories of 1Mb or more: - data 7.0Mb + Error(s) in re-building vignettes: + --- re-building ‘PPtreeregViz.Rmd’ using rmarkdown ``` -* checking data for non-ASCII characters ... NOTE +## In both + +* checking C++ specification ... NOTE ``` - Note: found 13138 marked UTF-8 strings + Specified C++11: please drop specification unless essential ``` -# MBNMAdose +# precrec
-* Version: 0.4.3 -* GitHub: NA -* Source code: https://github.com/cran/MBNMAdose -* Date/Publication: 2024-04-18 12:42:47 UTC -* Number of recursive dependencies: 118 +* Version: 0.14.4 +* GitHub: https://github.com/evalclass/precrec +* Source code: https://github.com/cran/precrec +* Date/Publication: 2023-10-11 22:10:02 UTC +* Number of recursive dependencies: 71 -Run `revdepcheck::cloud_details(, "MBNMAdose")` for more info +Run `revdepcheck::cloud_details(, "precrec")` for more info
@@ -6202,254 +15735,273 @@ Run `revdepcheck::cloud_details(, "MBNMAdose")` for more info * checking running R code from vignettes ... ERROR ``` Errors in running code in vignettes: - when running code in ‘outputs-4.Rmd’ + when running code in ‘introduction.Rmd’ ... + > msmdat3 <- mmdata(samps2[["scores"]], samps2[["labels"]], + + modnames = samps2[["modnames"]]) - > plot(trip.emax) + > mscurves <- evalmod(msmdat3) - When sourcing ‘outputs-4.R’: - Error: Problem while setting up geom aesthetics. - ℹ Error occurred in the 1st layer. - Caused by error in `use_defaults()`: - ... + > autoplot(mscurves) + + When sourcing ‘introduction.R’: + Error: object is not a unit Execution halted - ‘consistencychecking-3.Rmd’ using ‘UTF-8’... OK - ‘dataexploration-1.Rmd’ using ‘UTF-8’... OK - ‘mbnmadose-overview.Rmd’ using ‘UTF-8’... OK - ‘metaregression-6.Rmd’ using ‘UTF-8’... OK - ‘nma_in_mbnmadose.Rmd’ using ‘UTF-8’... OK - ‘outputs-4.Rmd’ using ‘UTF-8’... failed - ‘predictions-5.Rmd’ using ‘UTF-8’... OK - ‘runmbnmadose-2.Rmd’ using ‘UTF-8’... OK + ‘introduction.Rmd’ using ‘UTF-8’... failed ``` * checking re-building of vignette outputs ... NOTE ``` Error(s) in re-building vignettes: - --- re-building ‘consistencychecking-3.Rmd’ using rmarkdown + --- re-building ‘introduction.Rmd’ using rmarkdown ``` ## In both -* checking data for non-ASCII characters ... NOTE +* checking installed package size ... NOTE ``` - Note: found 6 marked Latin-1 strings + installed size is 6.5Mb + sub-directories of 1Mb or more: + libs 4.2Mb ``` -# MBNMAtime +# prevR
-* Version: 0.2.4 -* GitHub: NA -* Source code: https://github.com/cran/MBNMAtime -* Date/Publication: 2023-10-14 15:20:02 UTC -* Number of recursive dependencies: 106 +* Version: 5.0.0 +* GitHub: https://github.com/larmarange/prevR +* Source code: https://github.com/cran/prevR +* Date/Publication: 2023-05-15 18:50:03 UTC +* Number of recursive dependencies: 82 -Run `revdepcheck::cloud_details(, "MBNMAtime")` for more info +Run `revdepcheck::cloud_details(, "prevR")` for more info
## Newly broken -* checking re-building of vignette outputs ... NOTE +* checking running R code from vignettes ... ERROR ``` - Error(s) in re-building vignettes: - --- re-building ‘consistencychecking-3.Rmd’ using rmarkdown + Errors in running code in vignettes: + when running code in ‘intro_prevR.Rmd’ + ... + > plot(dhs, axes = TRUE) - Quitting from lines at lines 141-146 [unnamed-chunk-8] (consistencychecking-3.Rmd) - Error: processing vignette 'consistencychecking-3.Rmd' failed with diagnostics: - unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), NULL, list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.75, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, 90, NULL, c(0, - 2.75, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 1, NULL, NULL, NULL, c(0, 2.2, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, NULL, c(0, 0, 0, 2.2 - ), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0.5, NULL, NULL, NULL, c(0, 2.2, 0, 2.2), NULL, TRUE), list("grey20", NULL, NULL, NULL, FALSE, TRUE), NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 2.75, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 0.75, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, list(), NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, list("transparent", NA, NULL, NULL, FALSE), c(5.5, 5.5, 5.5, 5.5), 11, NULL, NULL, list("transparent", - NA, NULL, NULL, FALSE), 1.2, NULL, NULL, 5.5, NULL, NULL, NULL, NULL, 0.2, NULL, list(NULL, NULL, NULL, 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, NULL, NULL, NULL, TRUE), NULL, "right", NULL, NULL, NULL, "center", NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, c(0, 0, 0, 0), list(), 11, list(), list(NA, "grey20", NULL, NULL, TRUE), 5.5, NULL, NULL, list("grey92", NULL, NULL, NULL, FALSE, TRUE), list("grey95", NULL, NULL, NULL, FALSE, FALSE), - list("grey95", 0.5, NULL, NULL, FALSE, FALSE), NULL, NULL, NULL, NULL, FALSE, list("white", NA, NULL, NULL, FALSE), list(NULL, NULL, NULL, 1.2, 0, 1, NULL, NULL, c(0, 0, 5.5, 0), NULL, TRUE), "panel", list(NULL, NULL, NULL, NULL, 0, 1, NULL, NULL, c(0, 0, 5.5, 0), NULL, TRUE), list(NULL, NULL, NULL, 0.8, 1, 1, NULL, NULL, c(5.5, 0, 0, 0), NULL, TRUE), "panel", list(NULL, NULL, NULL, 1.2, 0.5, 0.5, NULL, NULL, NULL, NULL, TRUE), "topleft", NULL, c(5.5, 5.5, 5.5, 5.5), list("lightsteelblue1", "black", - NULL, NULL, FALSE), NULL, NULL, "inherit", "inside", list(NULL, NULL, "black", 0.8, NULL, NULL, NULL, NULL, c(4.4, 4.4, 4.4, 4.4), NULL, FALSE), NULL, NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, NULL, -90, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, NULL, 90, NULL, NULL, NULL, TRUE), NULL, 2.75, 2.75)) - --- failed re-building ‘consistencychecking-3.Rmd’ + > qa <- quick.prevR(fdhs, return.results = TRUE, return.plot = TRUE, + + plot.results = FALSE, progression = FALSE) - --- re-building ‘dataexploration-1.Rmd’ using rmarkdown + > qa$plot + + When sourcing ‘intro_prevR.R’: + Error: Theme element `plot.margin` must have class . + Execution halted + + ‘intro_prevR.Rmd’ using ‘UTF-8’... failed + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘intro_prevR.Rmd’ using rmarkdown ``` ## In both -* checking running R code from vignettes ... ERROR +* checking installed package size ... NOTE ``` - Errors in running code in vignettes: - when running code in ‘consistencychecking-3.Rmd’ - ... - 2.75, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 1, NULL, NULL, NULL, c(0, 2.2, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, NULL, c(0, 0, 0, 2.2 - ), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0.5, NULL, NULL, NULL, c(0, 2.2, 0, 2.2), NULL, TRUE), list("grey20", NULL, NULL, NULL, FALSE, TRUE), NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 2.75, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 0.75, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, list(), NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, list("transparent", NA, NULL, NULL, FALSE), c(5.5, 5.5, 5.5, 5.5), 11, NULL, NULL, list("transparent", - NA, NULL, NULL, FALSE), 1.2, NULL, NULL, 5.5, NULL, NULL, NULL, NULL, 0.2, NULL, list(NULL, NULL, NULL, 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, NULL, NULL, NULL, TRUE), NULL, "right", NULL, NULL, NULL, "center", NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, c(0, 0, 0, 0), list(), 11, list(), list(NA, "grey20", NULL, NULL, TRUE), 5.5, NULL, NULL, list("grey92", NULL, NULL, NULL, FALSE, TRUE), list("grey95", NULL, NULL, NULL, FALSE, FALSE), - list("grey95", 0.5, NULL, NULL, FALSE, FALSE), NULL, NULL, NULL, NULL, FALSE, list("white", NA, NULL, NULL, FALSE), list(NULL, NULL, NULL, 1.2, 0, 1, NULL, NULL, c(0, 0, 5.5, 0), NULL, TRUE), "panel", list(NULL, NULL, NULL, NULL, 0, 1, NULL, NULL, c(0, 0, 5.5, 0), NULL, TRUE), list(NULL, NULL, NULL, 0.8, 1, 1, NULL, NULL, c(5.5, 0, 0, 0), NULL, TRUE), "panel", list(NULL, NULL, NULL, 1.2, 0.5, 0.5, NULL, NULL, NULL, NULL, TRUE), "topleft", NULL, c(5.5, 5.5, 5.5, 5.5), list("lightsteelblue1", "black", - NULL, NULL, FALSE), NULL, NULL, "inherit", "inside", list(NULL, NULL, "black", 0.8, NULL, NULL, NULL, NULL, c(4.4, 4.4, 4.4, 4.4), NULL, FALSE), NULL, NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, NULL, -90, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, NULL, 90, NULL, NULL, NULL, TRUE), NULL, 2.75, 2.75)) - - When sourcing ‘consistencychecking-3.R’: - ... - ! unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), NULL, list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.75, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, 90, NULL, c(0, - 2.75, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(NULL, N - Execution halted - - ‘consistencychecking-3.Rmd’ using ‘UTF-8’... failed - ‘dataexploration-1.Rmd’ using ‘UTF-8’... failed - ‘mbnmatime-overview.Rmd’ using ‘UTF-8’... OK - ‘outputs-4.Rmd’ using ‘UTF-8’... failed - ‘predictions-5.Rmd’ using ‘UTF-8’... OK - ‘runmbnmatime-2.Rmd’ using ‘UTF-8’... OK + installed size is 8.4Mb + sub-directories of 1Mb or more: + data 7.5Mb ``` -# mc2d +# primerTree
-* Version: 0.2.0 +* Version: 1.0.6 * GitHub: NA -* Source code: https://github.com/cran/mc2d -* Date/Publication: 2023-07-17 16:00:02 UTC -* Number of recursive dependencies: 84 +* Source code: https://github.com/cran/primerTree +* Date/Publication: 2022-04-05 14:30:02 UTC +* Number of recursive dependencies: 53 -Run `revdepcheck::cloud_details(, "mc2d")` for more info +Run `revdepcheck::cloud_details(, "primerTree")` for more info
## Newly broken -* checking whether package ‘mc2d’ can be installed ... WARNING +* checking examples ... ERROR ``` - Found the following significant warnings: - Warning: replacing previous import ‘ggplot2::ggpar’ by ‘ggpubr::ggpar’ when loading ‘mc2d’ - See ‘/tmp/workdir/mc2d/new/mc2d.Rcheck/00install.out’ for details. + Running examples in ‘primerTree-Ex.R’ failed + The error most likely occurred in: + + > ### Name: plot.primerTree + > ### Title: plot function for a primerTree object, calls plot_tree_ranks + > ### Aliases: plot.primerTree + > + > ### ** Examples + > + > library(gridExtra) + ... + 4. ├─base::do.call(arrangeGrob, plots) + 5. └─gridExtra (local) ``(...) + 6. └─base::lapply(grobs[toconv], ggplot2::ggplotGrob) + 7. └─ggplot2 (local) FUN(X[[i]], ...) + 8. ├─ggplot2::ggplot_gtable(ggplot_build(x)) + 9. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) + 10. └─ggplot2::calc_element("plot.margin", theme) + 11. └─cli::cli_abort(...) + 12. └─rlang::abort(...) + Execution halted ``` -## In both +# processmapR -* checking re-building of vignette outputs ... NOTE +
+ +* Version: 0.5.3 +* GitHub: https://github.com/bupaverse/processmapr +* Source code: https://github.com/cran/processmapR +* Date/Publication: 2023-04-06 12:50:02 UTC +* Number of recursive dependencies: 118 + +Run `revdepcheck::cloud_details(, "processmapR")` for more info + +
+ +## Newly broken + +* checking tests ... ERROR ``` - Error(s) in re-building vignettes: - --- re-building ‘docmcEnglish.Rnw’ using Sweave - Loading required package: mvtnorm - Warning: replacing previous import ‘ggplot2::ggpar’ by ‘ggpubr::ggpar’ when loading ‘mc2d’ - - Attaching package: ‘mc2d’ - - The following objects are masked from ‘package:base’: - - pmax, pmin + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(processmapR) + + Attaching package: 'processmapR' + + The following object is masked from 'package:stats': + ... - l.179 \RequirePackage{grfext}\relax - ^^M - ! ==> Fatal error occurred, no output PDF file produced! - --- failed re-building ‘mc2dLmEnglish.rnw’ - - SUMMARY: processing the following files failed: - ‘docmcEnglish.Rnw’ ‘mc2dLmEnglish.rnw’ - - Error: Vignette re-building failed. - Execution halted + 10. └─processmapR:::return_plotly(p, plotly) + 11. ├─plotly::ggplotly(p) + 12. └─plotly:::ggplotly.ggplot(p) + 13. └─plotly::gg2list(...) + ── Failure ('test_trace_explorer.R:240:3'): test trace_explorer on eventlog with param `plotly` ── + `chart` inherits from 'gg'/'ggplot' not 'plotly'. + + [ FAIL 6 | WARN 0 | SKIP 10 | PASS 107 ] + Error: Test failures + Execution halted ``` -# MetaIntegrator +# PTXQC
-* Version: 2.1.3 -* GitHub: NA -* Source code: https://github.com/cran/MetaIntegrator -* Date/Publication: 2020-02-26 13:00:11 UTC -* Number of recursive dependencies: 178 +* Version: 1.1.1 +* GitHub: https://github.com/cbielow/PTXQC +* Source code: https://github.com/cran/PTXQC +* Date/Publication: 2024-03-11 19:50:02 UTC +* Number of recursive dependencies: 97 -Run `revdepcheck::cloud_details(, "MetaIntegrator")` for more info +Run `revdepcheck::cloud_details(, "PTXQC")` for more info
## Newly broken -* checking whether package ‘MetaIntegrator’ can be installed ... WARNING +* checking tests ... ERROR ``` - Found the following significant warnings: - Warning: replacing previous import ‘ggplot2::ggpar’ by ‘ggpubr::ggpar’ when loading ‘MetaIntegrator’ - See ‘/tmp/workdir/MetaIntegrator/new/MetaIntegrator.Rcheck/00install.out’ for details. + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(PTXQC) + Loading package PTXQC (version 1.1.1) + > + > ## + > ## calls all code in PTXQC/tests/testthat/test*.R + > ## + ... + 8. └─ggplot2::ggplotGrob(Main_bar_plot) + 9. ├─ggplot2::ggplot_gtable(ggplot_build(x)) + 10. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) + 11. └─ggplot2::calc_element("plot.margin", theme) + 12. └─cli::cli_abort(...) + 13. └─rlang::abort(...) + + [ FAIL 1 | WARN 20 | SKIP 0 | PASS 131 ] + Error: Test failures + Execution halted ``` ## In both * checking installed package size ... NOTE ``` - installed size is 6.8Mb + installed size is 8.5Mb sub-directories of 1Mb or more: - data 3.9Mb - doc 2.1Mb - ``` - -* checking dependencies in R code ... NOTE - ``` - Namespaces in Imports field not imported from: - ‘BiocManager’ ‘DT’ ‘GEOmetadb’ ‘RMySQL’ ‘RSQLite’ ‘gplots’ ‘pheatmap’ - ‘readr’ - All declared Imports should be used. + R 1.5Mb + doc 4.0Mb + examples 2.6Mb ``` -# MF.beta4 +# qacBase
* Version: 1.0.3 -* GitHub: https://github.com/AnneChao/MF.beta4 -* Source code: https://github.com/cran/MF.beta4 -* Date/Publication: 2024-04-16 16:30:02 UTC -* Number of recursive dependencies: 173 +* GitHub: https://github.com/rkabacoff/qacBase +* Source code: https://github.com/cran/qacBase +* Date/Publication: 2022-02-09 22:20:02 UTC +* Number of recursive dependencies: 99 -Run `revdepcheck::cloud_details(, "MF.beta4")` for more info +Run `revdepcheck::cloud_details(, "qacBase")` for more info
## Newly broken -* checking whether package ‘MF.beta4’ can be installed ... WARNING - ``` - Found the following significant warnings: - Warning: replacing previous import ‘ggplot2::ggpar’ by ‘ggpubr::ggpar’ when loading ‘MF.beta4’ - See ‘/tmp/workdir/MF.beta4/new/MF.beta4.Rcheck/00install.out’ for details. - ``` - -## In both - -* checking re-building of vignette outputs ... WARNING +* checking examples ... ERROR ``` - Error(s) in re-building vignettes: - ... - --- re-building ‘Introduction.Rnw’ using Sweave - Error: processing vignette 'Introduction.Rnw' failed with diagnostics: - Running 'texi2dvi' on 'Introduction.tex' failed. - LaTeX errors: - ! LaTeX Error: File `pdfpages.sty' not found. + Running examples in ‘qacBase-Ex.R’ failed + The error most likely occurred in: - Type X to quit or to proceed, - or enter new name. (Default extension: sty) + > ### Name: scatter + > ### Title: Scatterplot + > ### Aliases: scatter + > + > ### ** Examples + > + > scatter(cars74, hp, mpg) ... - l.4 ^^M - - ! ==> Fatal error occurred, no output PDF file produced! - --- failed re-building ‘Introduction.Rnw’ - - SUMMARY: processing the following file failed: - ‘Introduction.Rnw’ - - Error: Vignette re-building failed. + ▆ + 1. └─qacBase::scatter(...) + 2. └─ggExtra::ggMarginal(p, size = 8, type = margin, fill = margin_color) + 3. └─ggplot2::ggplotGrob(scatP) + 4. ├─ggplot2::ggplot_gtable(ggplot_build(x)) + 5. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) + 6. └─ggplot2::calc_element("plot.margin", theme) + 7. └─cli::cli_abort(...) + 8. └─rlang::abort(...) Execution halted ``` -# MiMIR +# qgcomp
-* Version: 1.5 -* GitHub: NA -* Source code: https://github.com/cran/MiMIR -* Date/Publication: 2024-02-01 08:50:02 UTC -* Number of recursive dependencies: 188 +* Version: 2.15.2 +* GitHub: https://github.com/alexpkeil1/qgcomp +* Source code: https://github.com/cran/qgcomp +* Date/Publication: 2023-08-10 09:10:06 UTC +* Number of recursive dependencies: 157 -Run `revdepcheck::cloud_details(, "MiMIR")` for more info +Run `revdepcheck::cloud_details(, "qgcomp")` for more info
@@ -6457,112 +16009,221 @@ Run `revdepcheck::cloud_details(, "MiMIR")` for more info * checking examples ... ERROR ``` - Running examples in ‘MiMIR-Ex.R’ failed + Running examples in ‘qgcomp-Ex.R’ failed The error most likely occurred in: - > ### Name: LOBOV_accuracies - > ### Title: LOBOV_accuracies - > ### Aliases: LOBOV_accuracies + > ### Name: plot.qgcompfit + > ### Title: Default plotting method for a qgcompfit object + > ### Aliases: plot.qgcompfit plot.qgcompmultfit > > ### ** Examples > - > require(pROC) + > set.seed(12) ... - | Pruning samples on5SD: - 56 metabolites x 500 samples - | Performing scaling ... DONE! - | Imputation ... DONE! - > p_avail<-colnames(b_p)[c(1:5)] - > LOBOV_accuracies(sur$surrogates, b_p, p_avail, MiMIR::acc_LOBOV) - Error in compute_geom_2(..., self = self) : - argument "theme" is missing, with no default - Calls: LOBOV_accuracies ... use_defaults -> eval_from_theme -> %||% -> calc_element + 3. └─qgcomp:::.plot_noboot_base(x, nms, theme_butterfly_r, theme_butterfly_l) + 4. └─gridExtra::arrangeGrob(...) + 5. └─base::lapply(grobs[toconv], ggplot2::ggplotGrob) + 6. └─ggplot2 (local) FUN(X[[i]], ...) + 7. ├─ggplot2::ggplot_gtable(ggplot_build(x)) + 8. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) + 9. └─ggplot2::calc_element("plot.margin", theme) + 10. └─cli::cli_abort(...) + 11. └─rlang::abort(...) Execution halted ``` -# miRetrieve +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘qgcomp-vignette.Rmd’ + ... + + Estimate Std. Error Lower CI Upper CI t value Pr(>|t|) + (Intercept) -0.348084 0.108037 -0.55983 -0.13634 -3.2219 0.0013688 + psi1 0.256969 0.071459 0.11691 0.39703 3.5960 0.0003601 + + > plot(qc.fit3) + + When sourcing ‘qgcomp-vignette.R’: + Error: Theme element `plot.margin` must have class . + Execution halted + + ‘qgcomp-vignette.Rmd’ using ‘UTF-8’... failed + ``` -
+* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + ... + --- re-building ‘qgcomp-vignette.Rmd’ using knitr + + Quitting from lines 234-242 [adjusting for covariates a] (qgcomp-vignette.Rmd) + Error: processing vignette 'qgcomp-vignette.Rmd' failed with diagnostics: + Theme element `plot.margin` must have class . + --- failed re-building ‘qgcomp-vignette.Rmd’ + + SUMMARY: processing the following file failed: + ‘qgcomp-vignette.Rmd’ + + Error: Vignette re-building failed. + Execution halted + ``` -* Version: 1.3.4 -* GitHub: NA -* Source code: https://github.com/cran/miRetrieve -* Date/Publication: 2021-09-18 17:30:02 UTC -* Number of recursive dependencies: 126 +# qgcompint -Run `revdepcheck::cloud_details(, "miRetrieve")` for more info +
+ +* Version: 0.7.0 +* GitHub: https://github.com/alexpkeil1/qgcomp +* Source code: https://github.com/cran/qgcompint +* Date/Publication: 2022-03-22 16:00:02 UTC +* Number of recursive dependencies: 132 + +Run `revdepcheck::cloud_details(, "qgcompint")` for more info
## Newly broken -* checking tests ... ERROR +* checking examples ... ERROR ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(miRetrieve) - > - > test_check("miRetrieve") - [ FAIL 1 | WARN 11 | SKIP 0 | PASS 202 ] - - ══ Failed tests ════════════════════════════════════════════════════════════════ + Running examples in ‘qgcompint-Ex.R’ failed + The error most likely occurred in: + + > ### Name: plot.qgcompemmfit + > ### Title: Default plotting method for a qgcompfit object + > ### Aliases: plot.qgcompemmfit + > + > ### ** Examples + > + > set.seed(50) ... - 9. └─ggplot2 (local) compute_geom_2(..., self = self) - 10. └─self$geom$use_defaults(data, self$aes_params, modifiers, theme = theme) - 11. └─ggplot2 (local) use_defaults(..., self = self) - 12. └─ggplot2:::eval_from_theme(default_aes, theme) - 13. ├─calc_element("geom", theme) %||% .default_geom_element - 14. └─ggplot2::calc_element("geom", theme) - - [ FAIL 1 | WARN 11 | SKIP 0 | PASS 202 ] - Error: Test failures - Execution halted + 5. └─qgcomp:::.plot_noboot_base(x, nms, theme_butterfly_r, theme_butterfly_l) + 6. └─gridExtra::arrangeGrob(...) + 7. └─base::lapply(grobs[toconv], ggplot2::ggplotGrob) + 8. └─ggplot2 (local) FUN(X[[i]], ...) + 9. ├─ggplot2::ggplot_gtable(ggplot_build(x)) + 10. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) + 11. └─ggplot2::calc_element("plot.margin", theme) + 12. └─cli::cli_abort(...) + 13. └─rlang::abort(...) + Execution halted + ``` + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘qgcompint-vignette.Rmd’ + ... + 1 1 + 2 1 + 3 1 + 4 1 + + > plot(qfit1, emmval = 0) + + When sourcing ‘qgcompint-vignette.R’: + Error: Theme element `plot.margin` must have class . + Execution halted + + ‘qgcompint-vignette.Rmd’ using ‘UTF-8’... failed + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + ... + --- re-building ‘qgcompint-vignette.Rmd’ using knitr + + Quitting from lines 119-121 [first_step_plot] (qgcompint-vignette.Rmd) + Error: processing vignette 'qgcompint-vignette.Rmd' failed with diagnostics: + Theme element `plot.margin` must have class . + --- failed re-building ‘qgcompint-vignette.Rmd’ + + SUMMARY: processing the following file failed: + ‘qgcompint-vignette.Rmd’ + + Error: Vignette re-building failed. + Execution halted ``` -# missingHE +# qpNCA
-* Version: 1.5.0 +* Version: 1.1.6 * GitHub: NA -* Source code: https://github.com/cran/missingHE -* Date/Publication: 2023-03-21 08:50:02 UTC -* Number of recursive dependencies: 151 +* Source code: https://github.com/cran/qpNCA +* Date/Publication: 2021-08-16 12:50:02 UTC +* Number of recursive dependencies: 81 -Run `revdepcheck::cloud_details(, "missingHE")` for more info +Run `revdepcheck::cloud_details(, "qpNCA")` for more info
## Newly broken -* checking whether package ‘missingHE’ can be installed ... WARNING +* checking running R code from vignettes ... ERROR ``` - Found the following significant warnings: - Warning: replacing previous import ‘ggplot2::ggpar’ by ‘ggpubr::ggpar’ when loading ‘missingHE’ - See ‘/tmp/workdir/missingHE/new/missingHE.Rcheck/00install.out’ for details. + Errors in running code in vignettes: + when running code in ‘Example-full-nca-analysis.rmd’ + ... + + Performing Thalf estimation... + + Creating regression plots in standard output... + + [[1]] + + ... + [[1]] + + When sourcing ‘Example-stepwise-nca-analysis.R’: + Error: Theme element `plot.margin` must have class . + Execution halted + + ‘Parameter_Guidelines.rmd’ using ‘UTF-8’... OK + ‘User_Guide.rmd’ using ‘UTF-8’... OK + ‘Example-full-nca-analysis.rmd’ using ‘UTF-8’... failed + ‘Example-stepwise-nca-analysis.rmd’ using ‘UTF-8’... failed ``` -## In both - -* checking dependencies in R code ... NOTE +* checking re-building of vignette outputs ... NOTE ``` - Namespace in Imports field not imported from: ‘mcmcr’ - All declared Imports should be used. + Error(s) in re-building vignettes: + --- re-building ‘Parameter_Guidelines.rmd’ using rmarkdown + --- finished re-building ‘Parameter_Guidelines.rmd’ + + --- re-building ‘User_Guide.rmd’ using rmarkdown + --- finished re-building ‘User_Guide.rmd’ + + --- re-building ‘Example-full-nca-analysis.rmd’ using knitr + + Quitting from lines 81-114 [unnamed-chunk-4] (Example-full-nca-analysis.rmd) + ... + Quitting from lines 121-135 [unnamed-chunk-6] (Example-stepwise-nca-analysis.rmd) + Error: processing vignette 'Example-stepwise-nca-analysis.rmd' failed with diagnostics: + Theme element `plot.margin` must have class . + --- failed re-building ‘Example-stepwise-nca-analysis.rmd’ + + SUMMARY: processing the following files failed: + ‘Example-full-nca-analysis.rmd’ ‘Example-stepwise-nca-analysis.rmd’ + + Error: Vignette re-building failed. + Execution halted ``` -# misspi +# QurvE
-* Version: 0.1.0 -* GitHub: NA -* Source code: https://github.com/cran/misspi -* Date/Publication: 2023-10-17 09:50:02 UTC -* Number of recursive dependencies: 88 +* Version: 1.1.1 +* GitHub: https://github.com/NicWir/QurvE +* Source code: https://github.com/cran/QurvE +* Date/Publication: 2024-01-26 12:40:14 UTC +* Number of recursive dependencies: 145 -Run `revdepcheck::cloud_details(, "misspi")` for more info +Run `revdepcheck::cloud_details(, "QurvE")` for more info
@@ -6570,40 +16231,51 @@ Run `revdepcheck::cloud_details(, "misspi")` for more info * checking examples ... ERROR ``` - Running examples in ‘misspi-Ex.R’ failed + Running examples in ‘QurvE-Ex.R’ failed The error most likely occurred in: - > ### Name: evaliq - > ### Title: Evaluate the Imputation Quality - > ### Aliases: evaliq + > ### Name: flFitSpline + > ### Title: Perform a smooth spline fit on fluorescence data + > ### Aliases: flFitSpline > > ### ** Examples > - > # A very quick example + > # load example dataset ... - > er.eval <- evaliq(x.true[na.idx], x.est[na.idx]) - `geom_smooth()` using formula = 'y ~ x' - > - > # Interactive plot - > er.eval <- evaliq(x.true[na.idx], x.est[na.idx], interactive = TRUE) - `geom_smooth()` using formula = 'y ~ x' - Error in compute_geom_2(..., self = self) : - argument "theme" is missing, with no default - Calls: evaliq ... use_defaults -> eval_from_theme -> %||% -> calc_element + 17. └─cowplot:::as_gtable.default(x) + 18. ├─cowplot::as_grob(plot) + 19. └─cowplot:::as_grob.ggplot(plot) + 20. └─ggplot2::ggplotGrob(plot) + 21. ├─ggplot2::ggplot_gtable(ggplot_build(x)) + 22. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) + 23. └─ggplot2::calc_element("plot.margin", theme) + 24. └─cli::cli_abort(...) + 25. └─rlang::abort(...) Execution halted ``` -# mlr3spatiotempcv +## In both + +* checking installed package size ... NOTE + ``` + installed size is 5.9Mb + sub-directories of 1Mb or more: + R 1.5Mb + doc 2.1Mb + shiny_app 1.2Mb + ``` + +# r2dii.plot
-* Version: 2.3.1 -* GitHub: https://github.com/mlr-org/mlr3spatiotempcv -* Source code: https://github.com/cran/mlr3spatiotempcv -* Date/Publication: 2024-04-17 12:10:05 UTC -* Number of recursive dependencies: 168 +* Version: 0.4.0 +* GitHub: https://github.com/RMI-PACTA/r2dii.plot +* Source code: https://github.com/cran/r2dii.plot +* Date/Publication: 2024-02-29 16:40:02 UTC +* Number of recursive dependencies: 91 -Run `revdepcheck::cloud_details(, "mlr3spatiotempcv")` for more info +Run `revdepcheck::cloud_details(, "r2dii.plot")` for more info
@@ -6611,93 +16283,134 @@ Run `revdepcheck::cloud_details(, "mlr3spatiotempcv")` for more info * checking examples ... ERROR ``` - Running examples in ‘mlr3spatiotempcv-Ex.R’ failed + Running examples in ‘r2dii.plot-Ex.R’ failed The error most likely occurred in: - > ### Name: autoplot.ResamplingCustomCV - > ### Title: Visualization Functions for Non-Spatial CV Methods. - > ### Aliases: autoplot.ResamplingCustomCV plot.ResamplingCustomCV + > ### Name: plot_emission_intensity + > ### Title: Create an emission intensity plot + > ### Aliases: plot_emission_intensity > > ### ** Examples > - > if (mlr3misc::require_namespaces(c("sf", "patchwork"), quietly = TRUE)) { + > # plot with `qplot_emission_intensity()` parameters ... - 22. └─ggplot2 (local) FUN(X[[i]], ...) - 23. └─g$draw_key(data, g$params, key_size) - 24. └─ggplot2 (local) draw_key(...) - 25. └─ggplot2::draw_key_point(data, params, size) - 26. ├─grid::pointsGrob(...) - 27. │ └─grid::grob(...) - 28. └─ggplot2::ggpar(...) - 29. └─rlang:::Ops.quosure(pointsize, .pt) - 30. └─rlang::abort(...) + Backtrace: + ▆ + 1. ├─base (local) ``(x) + 2. └─ggplot2:::print.ggplot(x) + 3. ├─ggplot2::ggplot_gtable(data) + 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) + 5. └─ggplot2::calc_element("plot.margin", theme) + 6. └─cli::cli_abort(...) + 7. └─rlang::abort(...) Execution halted ``` * checking tests ... ERROR ``` + Running ‘spelling.R’ Running ‘testthat.R’ Running the tests in ‘tests/testthat.R’ failed. Complete output: - > if (requireNamespace("testthat", quietly = TRUE)) { - + library("checkmate") - + library("testthat") - + library("mlr3spatiotempcv") - + test_check("mlr3spatiotempcv") - + } - Loading required package: mlr3 - ... - • 2-autoplot/sptcvcstf-2d-time-var-fold-1-rep-2.svg - • 2-autoplot/sptcvcstf-2d-time-var-fold-1-sample-fold-n.svg - • 2-autoplot/sptcvcstf-2d-time-var-fold-1.svg - • 2-autoplot/sptcvcstf-2d-time-var-sample-fold-n.svg - • 2-autoplot/sptcvcstf-3d-time-var-fold-1-2-sample-fold-n.svg - • 2-autoplot/sptcvcstf-3d-time-var-fold-1-2.svg - • 2-autoplot/sptcvcstf-3d-time-var-fold-1-sample-fold-n.svg - • autoplot_buffer/spcvbuffer-fold-1-2.svg + > library(testthat) + > library(r2dii.plot) + > + > test_check("r2dii.plot") + Scale for colour is already present. + Adding another scale for colour, which will replace the existing scale. + ... + 10. └─ggplot2:::print.ggplot(x) + 11. ├─ggplot2::ggplot_gtable(data) + 12. └─ggplot2:::ggplot_gtable.ggplot_built(data) + 13. └─ggplot2::calc_element("plot.margin", theme) + 14. └─cli::cli_abort(...) + 15. └─rlang::abort(...) + + [ FAIL 1 | WARN 2 | SKIP 39 | PASS 124 ] Error: Test failures Execution halted ``` -## In both +# Radviz + +
+ +* Version: 0.9.3 +* GitHub: https://github.com/yannabraham/Radviz +* Source code: https://github.com/cran/Radviz +* Date/Publication: 2022-03-25 18:10:02 UTC +* Number of recursive dependencies: 64 + +Run `revdepcheck::cloud_details(, "Radviz")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘Radviz-Ex.R’ failed + The error most likely occurred in: + + > ### Name: Radviz + > ### Title: Radviz Projection of Multidimensional Data + > ### Aliases: Radviz + > + > ### ** Examples + > + > data(iris) + > das <- c('Sepal.Length','Sepal.Width','Petal.Length','Petal.Width') + > S <- make.S(das) + > rv <- do.radviz(iris,S) + > plot(rv,anchors.only=FALSE) + Error in plot.radviz(rv, anchors.only = FALSE) : + 'language' object cannot be coerced to type 'double' + Calls: plot -> plot.radviz + Execution halted + ``` * checking running R code from vignettes ... ERROR ``` Errors in running code in vignettes: - when running code in ‘spatiotemp-viz.Rmd’ + when running code in ‘multivariate_analysis.Rmd’ ... - > knitr::opts_chunk$set(collapse = TRUE, comment = "#>") + > classic.S <- make.S(get.optim(classic.optim)) - > knitr::include_graphics("../man/figures/sptcv_cstf_multiplot.png") + > btcells.rv <- do.radviz(btcells.df, classic.S) - When sourcing ‘spatiotemp-viz.R’: - Error: Cannot find the file(s): "../man/figures/sptcv_cstf_multiplot.png" + > plot(btcells.rv) + geom_point(aes(color = Treatment)) + + ... + [1] 15792 18 + + > ct.rv + + When sourcing ‘single_cell_projections.R’: + Error: 'language' object cannot be coerced to type 'double' Execution halted - ‘mlr3spatiotempcv.Rmd’ using ‘UTF-8’... OK - ‘spatiotemp-viz.Rmd’ using ‘UTF-8’... failed + ‘multivariate_analysis.Rmd’ using ‘UTF-8’... failed + ‘single_cell_projections.Rmd’ using ‘UTF-8’... failed ``` -* checking installed package size ... NOTE +* checking re-building of vignette outputs ... NOTE ``` - installed size is 6.4Mb - sub-directories of 1Mb or more: - data 3.4Mb - help 1.2Mb + Error(s) in re-building vignettes: + --- re-building ‘multivariate_analysis.Rmd’ using rmarkdown ``` -# modeltime.resample +# rainette
-* Version: 0.2.3 -* GitHub: https://github.com/business-science/modeltime.resample -* Source code: https://github.com/cran/modeltime.resample -* Date/Publication: 2023-04-12 15:50:02 UTC -* Number of recursive dependencies: 229 +* Version: 0.3.1.1 +* GitHub: https://github.com/juba/rainette +* Source code: https://github.com/cran/rainette +* Date/Publication: 2023-03-28 16:50:02 UTC +* Number of recursive dependencies: 117 -Run `revdepcheck::cloud_details(, "modeltime.resample")` for more info +Run `revdepcheck::cloud_details(, "rainette")` for more info
@@ -6709,77 +16422,36 @@ Run `revdepcheck::cloud_details(, "modeltime.resample")` for more info Running the tests in ‘tests/testthat.R’ failed. Complete output: > library(testthat) - > - > # Machine Learning - > library(tidymodels) - ── Attaching packages ────────────────────────────────────── tidymodels 1.2.0 ── - ✔ broom 1.0.5 ✔ recipes 1.0.10 - ✔ dials 1.2.1 ✔ rsample 1.2.1 - ... - 10. └─ggplot2 (local) compute_geom_2(..., self = self) - 11. └─self$geom$use_defaults(data, self$aes_params, modifiers, theme = theme) - 12. └─ggplot2 (local) use_defaults(..., self = self) - 13. └─ggplot2:::eval_from_theme(default_aes, theme) - 14. ├─calc_element("geom", theme) %||% .default_geom_element - 15. └─ggplot2::calc_element("geom", theme) + > library(rainette) - [ FAIL 1 | WARN 4 | SKIP 0 | PASS 16 ] + Attaching package: 'rainette' + + The following object is masked from 'package:stats': + + ... + • plots/base-rainette2-plot-measure-frequency.svg + • plots/base-rainette2-plot-measure-lr.svg + • plots/base-rainette2-plot-with-complete-groups.svg + • plots/base-rainette2-plot-with-free-scales.svg + • plots/base-rainette2-plot-with-k-5.svg + • plots/base-rainette2-plot-with-k-and-without-negative.svg + • plots/base-rainette2-plot-with-k-n-terms-and-font-size.svg + • plots/base-rainette2-plot.svg Error: Test failures Execution halted ``` -## In both - -* checking dependencies in R code ... NOTE - ``` - Namespaces in Imports field not imported from: - ‘crayon’ ‘dials’ ‘glue’ ‘parsnip’ - All declared Imports should be used. - ``` - -# MSPRT - -
- -* Version: 3.0 -* GitHub: NA -* Source code: https://github.com/cran/MSPRT -* Date/Publication: 2020-11-13 10:20:05 UTC -* Number of recursive dependencies: 87 - -Run `revdepcheck::cloud_details(, "MSPRT")` for more info - -
- -## Newly broken - -* checking whether package ‘MSPRT’ can be installed ... WARNING - ``` - Found the following significant warnings: - Warning: replacing previous import ‘ggplot2::ggpar’ by ‘ggpubr::ggpar’ when loading ‘MSPRT’ - See ‘/tmp/workdir/MSPRT/new/MSPRT.Rcheck/00install.out’ for details. - ``` - -## In both - -* checking dependencies in R code ... NOTE - ``` - Namespaces in Imports field not imported from: - ‘datasets’ ‘grDevices’ ‘graphics’ ‘iterators’ ‘methods’ - All declared Imports should be used. - ``` - -# neatmaps +# rassta
-* Version: 2.1.0 -* GitHub: https://github.com/PhilBoileau/neatmaps -* Source code: https://github.com/cran/neatmaps -* Date/Publication: 2019-05-12 19:10:03 UTC -* Number of recursive dependencies: 99 +* Version: 1.0.5 +* GitHub: https://github.com/bafuentes/rassta +* Source code: https://github.com/cran/rassta +* Date/Publication: 2022-08-30 22:30:02 UTC +* Number of recursive dependencies: 120 -Run `revdepcheck::cloud_details(, "neatmaps")` for more info +Run `revdepcheck::cloud_details(, "rassta")` for more info
@@ -6787,47 +16459,90 @@ Run `revdepcheck::cloud_details(, "neatmaps")` for more info * checking examples ... ERROR ``` - Running examples in ‘neatmaps-Ex.R’ failed + Running examples in ‘rassta-Ex.R’ failed The error most likely occurred in: - > ### Name: consClustResTable - > ### Title: Consensus Cluster Results in a Table - > ### Aliases: consClustResTable + > ### Name: select_functions + > ### Title: Select Constrained Univariate Distribution Functions + > ### Aliases: select_functions > > ### ** Examples > - > # create the data frame using the network, node and edge attributes + > require(terra) ... - + node_attr_df, - + edge_df) - > - > # run the neatmap code on df - > neat_res <- neatmap(df, scale_df = "ecdf", max_k = 3, reps = 100, - + xlab = "vars", ylab = "nets", xlab_cex = 1, ylab_cex = 1) - Error in compute_geom_2(..., self = self) : - argument "theme" is missing, with no default - Calls: neatmap ... use_defaults -> eval_from_theme -> %||% -> calc_element + > tvars <- terra::rast(tf) + > # Single-layer SpatRaster of topographic classification units + > ## 5 classification units + > tcf <- list.files(path = p, pattern = "topography.tif", full.names = TRUE) + > tcu <- terra::rast(tcf) + > # Automatic selection of distribution functions + > tdif <- select_functions(cu.rast = tcu, var.rast = tvars, fun = mean) + Error in pm[[2]] : subscript out of bounds + Calls: select_functions -> -> ggplotly.ggplot -> gg2list Execution halted ``` -## In both +* checking tests ... ERROR + ``` + Running ‘tinytest.R’ + Running the tests in ‘tests/tinytest.R’ failed. + Complete output: + > + > if ( requireNamespace("tinytest", quietly=TRUE) ){ + + tinytest::test_package("rassta") + + } + + Attaching package: 'rassta' + + ... + test_select_functions.R....... 0 tests + test_select_functions.R....... 0 tests + test_select_functions.R....... 0 tests + test_select_functions.R....... 0 tests + test_select_functions.R....... 0 tests + test_select_functions.R....... 0 tests + test_select_functions.R....... 0 tests + test_select_functions.R....... 0 tests Error in pm[[2]] : subscript out of bounds + Calls: ... select_functions -> -> ggplotly.ggplot -> gg2list + Execution halted + ``` -* checking installed package size ... NOTE +* checking running R code from vignettes ... ERROR ``` - installed size is 6.3Mb + Errors in running code in vignettes: + when running code in ‘signature.Rmd’ + ... + > clim.var <- rast(vardir) + + > clim.cu <- rast(paste(d, "/climate.tif", sep = "")) + + > clim.difun <- select_functions(cu.rast = clim.cu, + + var.rast = clim.var, mode = "auto") + + ... + When sourcing ‘signature.R’: + Error: subscript out of bounds + Execution halted + + ‘classunits.Rmd’ using ‘UTF-8’... OK + ‘modeling.Rmd’ using ‘UTF-8’... OK + ‘sampling.Rmd’ using ‘UTF-8’... OK + ‘signature.Rmd’ using ‘UTF-8’... failed + ‘similarity.Rmd’ using ‘UTF-8’... OK + ‘stratunits.Rmd’ using ‘UTF-8’... OK ``` -# NetFACS +# RAT
-* Version: 0.5.0 +* Version: 0.3.1 * GitHub: NA -* Source code: https://github.com/cran/NetFACS -* Date/Publication: 2022-12-06 17:32:35 UTC -* Number of recursive dependencies: 101 +* Source code: https://github.com/cran/RAT +* Date/Publication: 2022-08-24 07:00:23 UTC +* Number of recursive dependencies: 32 -Run `revdepcheck::cloud_details(, "NetFACS")` for more info +Run `revdepcheck::cloud_details(, "RAT")` for more info
@@ -6835,59 +16550,40 @@ Run `revdepcheck::cloud_details(, "NetFACS")` for more info * checking examples ... ERROR ``` - Running examples in ‘NetFACS-Ex.R’ failed + Running examples in ‘RAT-Ex.R’ failed The error most likely occurred in: - > ### Name: network_conditional - > ### Title: Create a network based on conditional probabilities of dyads of - > ### elements - > ### Aliases: network_conditional + > ### Name: i.map + > ### Title: Map of international collaboration. + > ### Aliases: i.map > > ### ** Examples > + > data(biblio) ... - Warning in grid.Call.graphics(C_text, as.graphicsAnnot(x$label), x$x, x$y, : - font family 'Arial Narrow' not found in PostScript font database - Warning in grid.Call.graphics(C_text, as.graphicsAnnot(x$label), x$x, x$y, : - font family 'Arial Narrow' not found in PostScript font database - Warning in grid.Call.graphics(C_text, as.graphicsAnnot(x$label), x$x, x$y, : - font family 'Arial Narrow' not found in PostScript font database - Error in grid.Call.graphics(C_text, as.graphicsAnnot(x$label), x$x, x$y, : - invalid font type - Calls: ... drawDetails -> drawDetails.text -> grid.Call.graphics - Execution halted - ``` - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘netfacs_tutorial.Rmd’ - ... - Warning in grid.Call.graphics(C_text, as.graphicsAnnot(x$label), x$x, x$y, : - font family 'Arial Narrow' not found in PostScript font database - Warning in grid.Call.graphics(C_text, as.graphicsAnnot(x$label), x$x, x$y, : - font family 'Arial Narrow' not found in PostScript font database - Warning in grid.Call.graphics(C_text, as.graphicsAnnot(x$label), x$x, x$y, : - font family 'Arial Narrow' not found in PostScript font database - - When sourcing ‘netfacs_tutorial.R’: - Error: invalid font type + Backtrace: + ▆ + 1. ├─base (local) ``(x) + 2. └─ggplot2:::print.ggplot(x) + 3. ├─ggplot2::ggplot_gtable(data) + 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) + 5. └─ggplot2::calc_element("plot.margin", theme) + 6. └─cli::cli_abort(...) + 7. └─rlang::abort(...) Execution halted - - ‘netfacs_tutorial.Rmd’ using ‘UTF-8’... failed ``` -# NIMAA +# Rcan
-* Version: 0.2.1 -* GitHub: https://github.com/jafarilab/NIMAA -* Source code: https://github.com/cran/NIMAA -* Date/Publication: 2022-04-11 14:12:45 UTC -* Number of recursive dependencies: 173 +* Version: 1.3.82 +* GitHub: https://github.com/timat35/Rcan +* Source code: https://github.com/cran/Rcan +* Date/Publication: 2020-05-19 11:40:07 UTC +* Number of recursive dependencies: 47 -Run `revdepcheck::cloud_details(, "NIMAA")` for more info +Run `revdepcheck::cloud_details(, "Rcan")` for more info
@@ -6895,105 +16591,101 @@ Run `revdepcheck::cloud_details(, "NIMAA")` for more info * checking examples ... ERROR ``` - Running examples in ‘NIMAA-Ex.R’ failed + Running examples in ‘Rcan-Ex.R’ failed The error most likely occurred in: - > ### Name: extractSubMatrix - > ### Title: Extract the non-missing submatrices from a given matrix. - > ### Aliases: extractSubMatrix + > ### Name: csu_trendCohortPeriod + > ### Title: csu_trendCohortPeriod + > ### Aliases: csu_trendCohortPeriod > > ### ** Examples > - > # load part of the beatAML data + > ... - binmatnest.temperature - 13.21221 - Size of Square: 66 rows x 66 columns - Size of Rectangular_row: 6 rows x 105 columns - Size of Rectangular_col: 99 rows x 2 columns - Size of Rectangular_element_max: 59 rows x 79 columns - Error in compute_geom_2(..., self = self) : - argument "theme" is missing, with no default - Calls: extractSubMatrix ... use_defaults -> eval_from_theme -> %||% -> calc_element + ! Theme element `plot.margin` must have class . + Backtrace: + ▆ + 1. └─Rcan::csu_trendCohortPeriod(...) + 2. ├─ggplot2::ggplot_gtable(gb_plot) + 3. └─ggplot2:::ggplot_gtable.ggplot_built(gb_plot) + 4. └─ggplot2::calc_element("plot.margin", theme) + 5. └─cli::cli_abort(...) + 6. └─rlang::abort(...) Execution halted ``` -* checking tests ... ERROR +## In both + +* checking data for non-ASCII characters ... NOTE ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(NIMAA) - > - > test_check("NIMAA") - binmatnest.temperature - 13.21246 - Size of Square: 66 rows x 66 columns - ... - 11. └─ggplot2 (local) compute_geom_2(..., self = self) - 12. └─self$geom$use_defaults(data, self$aes_params, modifiers, theme = theme) - 13. └─ggplot2 (local) use_defaults(..., self = self) - 14. └─ggplot2:::eval_from_theme(default_aes, theme) - 15. ├─calc_element("geom", theme) %||% .default_geom_element - 16. └─ggplot2::calc_element("geom", theme) - - [ FAIL 1 | WARN 4 | SKIP 0 | PASS 7 ] - Error: Test failures - Execution halted + Note: found 26334 marked UTF-8 strings ``` +# redist + +
+ +* Version: 4.2.0 +* GitHub: https://github.com/alarm-redist/redist +* Source code: https://github.com/cran/redist +* Date/Publication: 2024-01-13 13:20:02 UTC +* Number of recursive dependencies: 132 + +Run `revdepcheck::cloud_details(, "redist")` for more info + +
+ +## Newly broken + * checking running R code from vignettes ... ERROR ``` Errors in running code in vignettes: - when running code in ‘NIMAA-vignette.Rmd’ + when running code in ‘redist.Rmd’ ... - + shape = c("Square", "Rectangular_element_max"), row.vars = "patient_id", - + .... [TRUNCATED] - binmatnest.temperature - 20.12109 - Size of Square: 96 rows x 96 columns - Size of Rectangular_element_max: 87 rows x 140 columns + # ℹ 991 more rows - When sourcing ‘NIMAA-vignette.R’: - Error: argument "theme" is missing, with no default + > library(patchwork) + + > hist(plan_sum, max_dev) + hist(iowa_plans, comp) + + + plot_layout(guides = "collect") + + When sourcing ‘redist.R’: + Error: object is not a unit Execution halted - ‘NIMAA-vignette.Rmd’ using ‘UTF-8’... failed + ‘common_args.Rmd’ using ‘UTF-8’... OK + ‘flip.Rmd’ using ‘UTF-8’... OK + ‘map-preproc.Rmd’ using ‘UTF-8’... OK + ‘redist.Rmd’ using ‘UTF-8’... failed ``` * checking re-building of vignette outputs ... NOTE ``` Error(s) in re-building vignettes: - --- re-building ‘NIMAA-vignette.Rmd’ using rmarkdown + --- re-building ‘common_args.Rmd’ using rmarkdown ``` ## In both * checking installed package size ... NOTE ``` - installed size is 5.5Mb + installed size is 27.4Mb sub-directories of 1Mb or more: - data 1.0Mb - doc 4.0Mb - ``` - -* checking data for non-ASCII characters ... NOTE - ``` - Note: found 24 marked UTF-8 strings + data 1.2Mb + libs 23.4Mb ``` -# nswgeo +# Relectoral
-* Version: 0.4.0 -* GitHub: https://github.com/cidm-ph/nswgeo -* Source code: https://github.com/cran/nswgeo -* Date/Publication: 2024-01-29 13:40:05 UTC -* Number of recursive dependencies: 61 +* Version: 0.1.0 +* GitHub: NA +* Source code: https://github.com/cran/Relectoral +* Date/Publication: 2020-06-14 14:20:02 UTC +* Number of recursive dependencies: 79 -Run `revdepcheck::cloud_details(, "nswgeo")` for more info +Run `revdepcheck::cloud_details(, "Relectoral")` for more info
@@ -7001,138 +16693,204 @@ Run `revdepcheck::cloud_details(, "nswgeo")` for more info * checking examples ... ERROR ``` - Running examples in ‘nswgeo-Ex.R’ failed + Running examples in ‘Relectoral-Ex.R’ failed The error most likely occurred in: - > ### Name: australia - > ### Title: Geospatial data of the Australian state and territory - > ### administrative boundaries. - > ### Aliases: australia states - > ### Keywords: datasets + > ### Name: mapa + > ### Title: Graphs. Representation on maps. Choropleth map + > ### Aliases: mapa > > ### ** Examples + > + > ... - 15. └─ggplot2 (local) FUN(X[[i]], ...) - 16. └─base::lapply(...) - 17. └─ggplot2 (local) FUN(X[[i]], ...) - 18. └─g$draw_key(data, g$params, key_size) - 19. └─ggplot2 (local) draw_key(...) - 20. └─ggplot2::draw_key_polygon(data, params, size) - 21. └─rlang:::Summary.quosure(from_theme(thin), 1.524, na.rm = FALSE) - 22. └─rlang:::abort_quosure_op("Summary", .Generic) - 23. └─rlang::abort(...) + Backtrace: + ▆ + 1. ├─base (local) ``(x) + 2. └─ggplot2:::print.ggplot(x) + 3. ├─ggplot2::ggplot_gtable(data) + 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) + 5. └─ggplot2::calc_element("plot.margin", theme) + 6. └─cli::cli_abort(...) + 7. └─rlang::abort(...) Execution halted ``` ## In both -* checking data for non-ASCII characters ... NOTE +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘Volatilidad.Rmd’ + ... + Loading required package: readxl + + > require("readxl") + + > dat1 <- read_xlsx("../inst/data_raw/volatilidad/abril_19.xlsx", + + col_names = TRUE) + + When sourcing ‘Volatilidad.R’: + Error: `path` does not exist: ‘../inst/data_raw/volatilidad/abril_19.xlsx’ + Execution halted + + ‘Volatilidad.Rmd’ using ‘UTF-8’... failed + ``` + +* checking dependencies in R code ... NOTE + ``` + Namespace in Imports field not imported from: ‘rmarkdown’ + All declared Imports should be used. + ``` + +* checking LazyData ... NOTE ``` - Note: found 1 marked UTF-8 string + 'LazyData' is specified without a 'data' directory ``` -# OenoKPM +# reliabilitydiag
-* Version: 2.4.1 -* GitHub: NA -* Source code: https://github.com/cran/OenoKPM -* Date/Publication: 2024-04-08 19:20:10 UTC -* Number of recursive dependencies: 85 +* Version: 0.2.1 +* GitHub: https://github.com/aijordan/reliabilitydiag +* Source code: https://github.com/cran/reliabilitydiag +* Date/Publication: 2022-06-29 00:20:06 UTC +* Number of recursive dependencies: 73 -Run `revdepcheck::cloud_details(, "OenoKPM")` for more info +Run `revdepcheck::cloud_details(, "reliabilitydiag")` for more info
## Newly broken -* checking whether package ‘OenoKPM’ can be installed ... WARNING +* checking examples ... ERROR ``` - Found the following significant warnings: - Warning: replacing previous import ‘ggplot2::ggpar’ by ‘ggpubr::ggpar’ when loading ‘OenoKPM’ - See ‘/tmp/workdir/OenoKPM/new/OenoKPM.Rcheck/00install.out’ for details. + Running examples in ‘reliabilitydiag-Ex.R’ failed + The error most likely occurred in: + + > ### Name: plot.reliabilitydiag + > ### Title: Plotting reliability diagram objects + > ### Aliases: plot.reliabilitydiag autoplot.reliabilitydiag + > ### autolayer.reliabilitydiag + > + > ### ** Examples + > + ... + 2. └─reliabilitydiag:::autoplot.reliabilitydiag(r["EMOS"], type = "discrimination") + 3. ├─base::do.call(...) + 4. └─ggExtra (local) ``(...) + 5. └─ggplot2::ggplotGrob(scatP) + 6. ├─ggplot2::ggplot_gtable(ggplot_build(x)) + 7. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) + 8. └─ggplot2::calc_element("plot.margin", theme) + 9. └─cli::cli_abort(...) + 10. └─rlang::abort(...) + Execution halted ``` -# OmicNavigator +# relliptical
-* Version: 1.13.13 -* GitHub: https://github.com/abbvie-external/OmicNavigator -* Source code: https://github.com/cran/OmicNavigator -* Date/Publication: 2023-08-25 20:40:02 UTC -* Number of recursive dependencies: 86 +* Version: 1.3.0 +* GitHub: NA +* Source code: https://github.com/cran/relliptical +* Date/Publication: 2024-02-07 12:50:02 UTC +* Number of recursive dependencies: 73 -Run `revdepcheck::cloud_details(, "OmicNavigator")` for more info +Run `revdepcheck::cloud_details(, "relliptical")` for more info
## Newly broken -* checking tests ... ERROR +* checking examples ... ERROR ``` - Running ‘tinytest.R’ - Running the tests in ‘tests/tinytest.R’ failed. - Complete output: - > # Test files in inst/tinytest/ - > if (requireNamespace("tinytest", quietly = TRUE)) { - + suppressMessages(tinytest::test_package("OmicNavigator")) - + } - - testAdd.R..................... 0 tests - testAdd.R..................... 0 tests + Running examples in ‘relliptical-Ex.R’ failed + The error most likely occurred in: + + > ### Name: rtelliptical + > ### Title: Sampling Random Numbers from Truncated Multivariate Elliptical + > ### Distributions + > ### Aliases: rtelliptical + > + > ### ** Examples + > ... - testPlot.R.................... 140 tests OK - testPlot.R.................... 141 tests OK - testPlot.R.................... 141 tests OK - testPlot.R.................... 141 tests OK - testPlot.R.................... 142 tests OK - testPlot.R.................... 142 tests OK - testPlot.R.................... 143 tests OK Error in compute_geom_2(..., self = self) : - argument "theme" is missing, with no default - Calls: suppressMessages ... use_defaults -> eval_from_theme -> %||% -> calc_element - Execution halted + Backtrace: + ▆ + 1. └─ggExtra::ggMarginal(f1, type = "histogram", fill = "grey") + 2. └─ggplot2::ggplotGrob(scatP) + 3. ├─ggplot2::ggplot_gtable(ggplot_build(x)) + 4. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) + 5. └─ggplot2::calc_element("plot.margin", theme) + 6. └─cli::cli_abort(...) + 7. └─rlang::abort(...) + Execution halted + ``` + +## In both + +* checking installed package size ... NOTE + ``` + installed size is 6.5Mb + sub-directories of 1Mb or more: + libs 6.4Mb ``` -## In both +# Repliscope + +
+ +* Version: 1.1.1 +* GitHub: NA +* Source code: https://github.com/cran/Repliscope +* Date/Publication: 2022-09-13 07:20:02 UTC +* Number of recursive dependencies: 62 -* checking re-building of vignette outputs ... NOTE +Run `revdepcheck::cloud_details(, "Repliscope")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR ``` - Error(s) in re-building vignettes: - --- re-building ‘OmicNavigatorAPI.Rnw’ using Sweave - OmicNavigator R package version: 1.13.13 - The app is not installed. Install it with installApp() - Installing study "ABC" in /tmp/Rtmpc8E08Z/file279050a9efa7 - Exporting study "ABC" as an R package - Note: No maintainer email was specified. Using the placeholder: Unknown - Calculating pairwise overlaps. This may take a while... - Exported study to /tmp/Rtmpc8E08Z/ONstudyABC - Success! - ... - l.14 ^^M - - ! ==> Fatal error occurred, no output PDF file produced! - --- failed re-building ‘OmicNavigatorUsersGuide.Rnw’ - - SUMMARY: processing the following files failed: - ‘OmicNavigatorAPI.Rnw’ ‘OmicNavigatorUsersGuide.Rnw’ + Running examples in ‘Repliscope-Ex.R’ failed + The error most likely occurred in: - Error: Vignette re-building failed. + > ### Name: plotBed + > ### Title: A function to boxplot 'score' column of a BED dataframe, per + > ### unique chromosome name in the 'chrom' column. The resulting plot also + > ### highlights outliers based on the inter quartile range (IQR). The + > ### genome wide median is plotted as a pink line through the boxplots. + > ### Aliases: plotBed + > ### Keywords: BED bioinformatics boxplot genomics + ... + Backtrace: + ▆ + 1. ├─base (local) ``(x) + 2. └─ggplot2:::print.ggplot(x) + 3. ├─ggplot2::ggplot_gtable(data) + 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) + 5. └─ggplot2::calc_element("plot.margin", theme) + 6. └─cli::cli_abort(...) + 7. └─rlang::abort(...) Execution halted ``` -# otsad +# reportRmd
-* Version: 0.2.0 -* GitHub: https://github.com/alaineiturria/otsad -* Source code: https://github.com/cran/otsad -* Date/Publication: 2019-09-06 09:50:02 UTC -* Number of recursive dependencies: 109 +* Version: 0.1.0 +* GitHub: NA +* Source code: https://github.com/cran/reportRmd +* Date/Publication: 2023-11-16 17:00:03 UTC +* Number of recursive dependencies: 108 -Run `revdepcheck::cloud_details(, "otsad")` for more info +Run `revdepcheck::cloud_details(, "reportRmd")` for more info
@@ -7140,115 +16898,256 @@ Run `revdepcheck::cloud_details(, "otsad")` for more info * checking examples ... ERROR ``` - Running examples in ‘otsad-Ex.R’ failed + Running examples in ‘reportRmd-Ex.R’ failed The error most likely occurred in: - > ### Name: CpKnnCad - > ### Title: Classic processing KNN based Conformal Anomaly Detector - > ### (KNN-CAD) - > ### Aliases: CpKnnCad + > ### Name: ggkmcif + > ### Title: Plot KM and CIF curves with ggplot + > ### Aliases: ggkmcif > > ### ** Examples > + > data("pembrolizumab") ... - + reducefp = TRUE - + ) - > - > ## Plot results - > res <- cbind(df, result) - > PlotDetections(res, title = "KNN-CAD ANOMALY DETECTOR") - Error in compute_geom_2(..., self = self) : - argument "theme" is missing, with no default - Calls: PlotDetections ... use_defaults -> eval_from_theme -> %||% -> calc_element + Backtrace: + ▆ + 1. └─reportRmd::ggkmcif(...) + 2. └─ggplot2::ggplotGrob(data.table) + 3. ├─ggplot2::ggplot_gtable(ggplot_build(x)) + 4. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) + 5. └─ggplot2::calc_element("plot.margin", theme) + 6. └─cli::cli_abort(...) + 7. └─rlang::abort(...) Execution halted ``` -## In both +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘reportRmd.Rmd’ + ... + > ctDNA <- clear_labels(ctDNA) + + > plotuv(data = pembrolizumab, response = "orr", covs = c("age", + + "cohort", "pdl1", "change_ctdna_group")) + Boxplots not shown for categories with fewer than 20 observations. + Boxplots not shown for categories with fewer than 20 observations. + + When sourcing ‘reportRmd.R’: + Error: Theme element `plot.margin` must have class . + Execution halted + + ‘reportRmd.Rmd’ using ‘UTF-8’... failed + ``` * checking re-building of vignette outputs ... NOTE ``` Error(s) in re-building vignettes: ... - --- re-building ‘otsad.Rnw’ using knitr - Error: processing vignette 'otsad.Rnw' failed with diagnostics: - Running 'texi2dvi' on 'otsad.tex' failed. - LaTeX errors: - ! LaTeX Error: File `colortbl.sty' not found. + --- re-building ‘reportRmd.Rmd’ using rmarkdown - Type X to quit or to proceed, - or enter new name. (Default extension: sty) - ... - l.270 \long - \def\@secondoffive#1#2#3#4#5{#2}^^M - ! ==> Fatal error occurred, no output PDF file produced! - --- failed re-building ‘otsad.Rnw’ + Quitting from lines 380-383 [unnamed-chunk-30] (reportRmd.Rmd) + Error: processing vignette 'reportRmd.Rmd' failed with diagnostics: + Theme element `plot.margin` must have class . + --- failed re-building ‘reportRmd.Rmd’ SUMMARY: processing the following file failed: - ‘otsad.Rnw’ + ‘reportRmd.Rmd’ Error: Vignette re-building failed. Execution halted ``` -# pdxTrees +# reReg
-* Version: 0.4.0 -* GitHub: https://github.com/mcconvil/pdxTrees -* Source code: https://github.com/cran/pdxTrees -* Date/Publication: 2020-08-17 14:00:02 UTC -* Number of recursive dependencies: 106 +* Version: 1.4.6 +* GitHub: https://github.com/stc04003/reReg +* Source code: https://github.com/cran/reReg +* Date/Publication: 2023-09-20 08:00:02 UTC +* Number of recursive dependencies: 63 -Run `revdepcheck::cloud_details(, "pdxTrees")` for more info +Run `revdepcheck::cloud_details(, "reReg")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘reReg-Ex.R’ failed + The error most likely occurred in: + + > ### Name: plot.Recur + > ### Title: Produce Event Plot or Mean Cumulative Function Plot + > ### Aliases: plot.Recur + > ### Keywords: Plots + > + > ### ** Examples + > + ... + 11. │ └─base::withCallingHandlers(...) + 12. └─ggplot2 (local) f(l = layers[[i]], d = data[[i]]) + 13. └─l$compute_geom_2(d, theme = plot$theme) + 14. └─ggplot2 (local) compute_geom_2(..., self = self) + 15. └─self$geom$use_defaults(...) + 16. └─ggplot2 (local) use_defaults(..., self = self) + 17. └─ggplot2:::check_aesthetics(new_params, nrow(data)) + 18. └─cli::cli_abort(...) + 19. └─rlang::abort(...) + Execution halted + ``` + +# reservr + +
+ +* Version: 0.0.2 +* GitHub: https://github.com/AshesITR/reservr +* Source code: https://github.com/cran/reservr +* Date/Publication: 2023-10-18 20:50:05 UTC +* Number of recursive dependencies: 142 + +Run `revdepcheck::cloud_details(, "reservr")` for more info
## Newly broken +* checking examples ... ERROR + ``` + Running examples in ‘reservr-Ex.R’ failed + The error most likely occurred in: + + > ### Name: dist_bdegp + > ### Title: Construct a BDEGP-Family + > ### Aliases: dist_bdegp + > + > ### ** Examples + > + > dist <- dist_bdegp(n = 1, m = 2, u = 10, epsilon = 3) + ... + + theoretical = dist, + + empirical = dist_empirical(x), + + .x = seq(0, 20, length.out = 101), + + with_params = list(theoretical = params) + + ) + Warning: Removed 9 rows containing missing values or values outside the scale range + (`geom_line()`). + Error in as.unit(value) : object is not coercible to a unit + Calls: ... assemble_guides -> guides_build -> [<- -> [<-.unit -> as.unit + Execution halted + ``` + * checking running R code from vignettes ... ERROR ``` Errors in running code in vignettes: - when running code in ‘pdxTrees-vignette.Rmd’ + when running code in ‘distributions.Rmd’ ... - > berkeley_graph + transition_states(states = Mature_Size, - + transition_length = 10, state_length = 8) + enter_grow() + - + exit_shrink() - Warning: Failed to apply `after_scale()` modifications to legend - Caused by error in `build()`: - ! argument "theme" is missing, with no default - When sourcing ‘pdxTrees-vignette.R’: - Error: promise already under evaluation: recursive default argument reference or earlier problems? + > attr(trunc_fit$logLik, "nobs") + [1] 62 + + > plot_distributions(true = norm, fit1 = norm, fit2 = norm2, + + fit3 = dist_normal(3), .x = seq(-2, 7, 0.01), with_params = list(true = list(mean .... [TRUNCATED] + + When sourcing ‘distributions.R’: + Error: object is not a unit Execution halted - ‘pdxTrees-vignette.Rmd’ using ‘UTF-8’... failed + ‘distributions.Rmd’ using ‘UTF-8’... failed + ‘tensorflow.Rmd’ using ‘UTF-8’... OK ``` * checking re-building of vignette outputs ... NOTE ``` Error(s) in re-building vignettes: - --- re-building ‘pdxTrees-vignette.Rmd’ using rmarkdown + ... + --- re-building ‘distributions.Rmd’ using rmarkdown + + Quitting from lines 170-227 [unnamed-chunk-10] (distributions.Rmd) + Error: processing vignette 'distributions.Rmd' failed with diagnostics: + object is not a unit + --- failed re-building ‘distributions.Rmd’ + + --- re-building ‘tensorflow.Rmd’ using rmarkdown + --- finished re-building ‘tensorflow.Rmd’ + + SUMMARY: processing the following file failed: + ‘distributions.Rmd’ + + Error: Vignette re-building failed. + Execution halted ``` ## In both -* checking LazyData ... NOTE +* checking installed package size ... NOTE ``` - 'LazyData' is specified without a 'data' directory + installed size is 16.5Mb + sub-directories of 1Mb or more: + R 3.5Mb + libs 12.4Mb ``` -# personalized +* checking for GNU extensions in Makefiles ... NOTE + ``` + GNU make is a SystemRequirements. + ``` + +# restriktor
-* Version: 0.2.7 -* GitHub: https://github.com/jaredhuling/personalized -* Source code: https://github.com/cran/personalized -* Date/Publication: 2022-06-27 20:20:03 UTC -* Number of recursive dependencies: 94 +* Version: 0.5-60 +* GitHub: NA +* Source code: https://github.com/cran/restriktor +* Date/Publication: 2024-05-24 11:00:03 UTC +* Number of recursive dependencies: 81 -Run `revdepcheck::cloud_details(, "personalized")` for more info +Run `revdepcheck::cloud_details(, "restriktor")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘restriktor-Ex.R’ failed + The error most likely occurred in: + + > ### Name: evSyn + > ### Title: GORIC(A) Evidence synthesis + > ### Aliases: evSyn evsyn evSyn_est.list evSyn_ICweights.list + > ### evSyn_ICvalues.list evSyn_LL.list print.evSyn print.summary.evSyn + > ### summary.evSyn plot.evSyn + > + > ### ** Examples + ... + Backtrace: + ▆ + 1. ├─base (local) ``(x) + 2. └─ggplot2:::print.ggplot(x) + 3. ├─ggplot2::ggplot_gtable(data) + 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) + 5. └─ggplot2::calc_element("plot.margin", theme) + 6. └─cli::cli_abort(...) + 7. └─rlang::abort(...) + Execution halted + ``` + +# RevGadgets + +
+ +* Version: 1.2.1 +* GitHub: https://github.com/revbayes/RevGadgets +* Source code: https://github.com/cran/RevGadgets +* Date/Publication: 2023-11-29 20:30:02 UTC +* Number of recursive dependencies: 131 + +Run `revdepcheck::cloud_details(, "RevGadgets")` for more info
@@ -7259,261 +17158,315 @@ Run `revdepcheck::cloud_details(, "personalized")` for more info Running ‘testthat.R’ Running the tests in ‘tests/testthat.R’ failed. Complete output: - > Sys.setenv("R_TESTS" = "") > library(testthat) - > library(personalized) - Loading required package: glmnet - Loading required package: Matrix - Loaded glmnet 4.1-8 - Loading required package: mgcv + > library(RevGadgets) + > + > test_check("RevGadgets") + + | + | | 0% ... - 14. └─ggplot2 (local) compute_geom_2(..., self = self) - 15. └─self$geom$use_defaults(data, self$aes_params, modifiers, theme = theme) - 16. └─ggplot2 (local) use_defaults(..., self = self) - 17. └─ggplot2:::eval_from_theme(default_aes, theme) - 18. ├─calc_element("geom", theme) %||% .default_geom_element - 19. └─ggplot2::calc_element("geom", theme) + 6. └─ggplot2:::print.ggplot(x) + 7. ├─ggplot2::ggplot_gtable(data) + 8. └─ggplot2:::ggplot_gtable.ggplot_built(data) + 9. └─ggplot2::calc_element("plot.margin", theme) + 10. └─cli::cli_abort(...) + 11. └─rlang::abort(...) - [ FAIL 1 | WARN 2 | SKIP 0 | PASS 215 ] + [ FAIL 1 | WARN 44 | SKIP 0 | PASS 138 ] Error: Test failures Execution halted ``` -# PGRdup +# rimu
-* Version: 0.2.3.9 -* GitHub: https://github.com/aravind-j/PGRdup -* Source code: https://github.com/cran/PGRdup -* Date/Publication: 2023-08-31 22:10:16 UTC -* Number of recursive dependencies: 69 +* Version: 0.6 +* GitHub: NA +* Source code: https://github.com/cran/rimu +* Date/Publication: 2022-10-06 04:50:02 UTC +* Number of recursive dependencies: 53 -Run `revdepcheck::cloud_details(, "PGRdup")` for more info +Run `revdepcheck::cloud_details(, "rimu")` for more info
## Newly broken -* checking re-building of vignette outputs ... ERROR +* checking examples ... ERROR + ``` + Running examples in ‘rimu-Ex.R’ failed + The error most likely occurred in: + + > ### Name: plot.mr + > ### Title: Plot multiple-response objects + > ### Aliases: plot.mr image.mr + > + > ### ** Examples + > + > data(rstudiosurvey) + ... + 4. ├─base::suppressMessages(...) + 5. │ └─base::withCallingHandlers(...) + 6. └─UpSetR:::Make_main_bar(...) + 7. └─ggplot2::ggplotGrob(Main_bar_plot) + 8. ├─ggplot2::ggplot_gtable(ggplot_build(x)) + 9. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) + 10. └─ggplot2::calc_element("plot.margin", theme) + 11. └─cli::cli_abort(...) + 12. └─rlang::abort(...) + Execution halted + ``` + +* checking re-building of vignette outputs ... NOTE ``` Error(s) in re-building vignettes: ... - --- re-building ‘Introduction.Rmd’ using rmarkdown_notangle - ! Undefined control sequence. - l.108 \NewDocumentCommand - \citeproctext{}{} + --- re-building ‘backyard-birds.Rmd’ using rmarkdown - Error: processing vignette 'Introduction.Rmd' failed with diagnostics: - LaTeX failed to compile /tmp/workdir/PGRdup/new/PGRdup.Rcheck/vign_test/PGRdup/vignettes/Introduction.tex. See https://yihui.org/tinytex/r/#debugging for debugging tips. See Introduction.log for more info. - --- failed re-building ‘Introduction.Rmd’ + Quitting from lines 63-64 [unnamed-chunk-6] (backyard-birds.Rmd) + Error: processing vignette 'backyard-birds.Rmd' failed with diagnostics: + Theme element `plot.margin` must have class . + --- failed re-building ‘backyard-birds.Rmd’ - SUMMARY: processing the following file failed: - ‘Introduction.Rmd’ + --- re-building ‘ethnicity.Rmd’ using rmarkdown + ... + --- failed re-building ‘ethnicity.Rmd’ + + --- re-building ‘internals.Rmd’ using rmarkdown + --- finished re-building ‘internals.Rmd’ + + SUMMARY: processing the following files failed: + ‘backyard-birds.Rmd’ ‘ethnicity.Rmd’ Error: Vignette re-building failed. Execution halted ``` -## Newly fixed +## In both -* checking re-building of vignette outputs ... WARNING +* checking running R code from vignettes ... ERROR ``` - Error(s) in re-building vignettes: - --- re-building ‘Introduction.Rmd’ using rmarkdown_notangle - Trying to upgrade TinyTeX automatically now... - If reinstallation fails, try install_tinytex() again. Then install the following packages: - - tinytex::tlmgr_install(c("amscls", "amsfonts", "amsmath", "atbegshi", "atveryend", "auxhook", "babel", "bibtex", "bigintcalc", "bitset", "booktabs", "cm", "ctablestack", "dehyph", "dvipdfmx", "dvips", "ec", "epstopdf-pkg", "etex", "etexcmds", "etoolbox", "euenc", "everyshi", "fancyvrb", "filehook", "firstaid", "float", "fontspec", "framed", "geometry", "gettitlestring", "glyphlist", "graphics", "graphics-cfg", "graphics-def", "helvetic", "hycolor", "hyperref", "hyph-utf8", "hyphen-base", "iftex", "inconsolata", "infwarerr", "intcalc", "knuth-lib", "kpathsea", "kvdefinekeys", "kvoptions", "kvsetkeys", "l3backend", "l3kernel", "l3packages", "latex", "latex-amsmath-dev", "latex-bin", "latex-fonts", "latex-tools-dev", "latexconfig", "latexmk", "letltxmacro", "lm", "lm-math", "ltxcmds", "lua-alt-getopt", "lua-uni-algos", "luahbtex", "lualatex-math", "lualibs", "luaotfload", "luatex", "luatexbase", "mdwtools", "metafont", "mfware", "modes", "natbib", "pdfescape", "pdftex", "pdftexcmds", "plain", "psnfss", "refcount", "rerunfilecheck", "scheme-infraonly", "selnolig", "stringenc", "symbol", "tex", "tex-ini-files", "texlive-scripts", "texlive.infra", "times", "tipa", "tools", "unicode-data", "unicode-math", "uniquecounter", "url", "xcolor", "xetex", "xetexconfig", "xkeyval", "xunicode", "zapfding")) + Errors in running code in vignettes: + when running code in ‘backyard-birds.Rmd’ + ... + Aythya collaris Xanthocephalus xanthocephalus Gracula religiosa + 1090 80 1 + Icterus parisorum Coccyzus erythropthalmus + 8 1 - The directory /opt/TinyTeX/texmf-local is not empty. It will be backed up to /tmp/RtmpQwt2mx/filed245f15abf1 and restored later. + > plot(bird_presence, nsets = 12) - tlmgr: no auxiliary texmf trees defined, so nothing removed ... - Error: processing vignette 'Introduction.Rmd' failed with diagnostics: - LaTeX failed to compile /tmp/workdir/PGRdup/old/PGRdup.Rcheck/vign_test/PGRdup/vignettes/Introduction.tex. See https://yihui.org/tinytex/r/#debugging for debugging tips. See Introduction.log for more info. - --- failed re-building ‘Introduction.Rmd’ - - SUMMARY: processing the following file failed: - ‘Introduction.Rmd’ + > plot(ethnicity, nsets = 6) - Error: Vignette re-building failed. + When sourcing ‘ethnicity.R’: + Error: Theme element `plot.margin` must have class . Execution halted + + ‘backyard-birds.Rmd’ using ‘UTF-8’... failed + ‘ethnicity.Rmd’ using ‘UTF-8’... failed + ‘internals.Rmd’ using ‘UTF-8’... OK ``` -# plantTracker +# rKOMICS
-* Version: 1.1.0 -* GitHub: https://github.com/aestears/plantTracker -* Source code: https://github.com/cran/plantTracker -* Date/Publication: 2023-05-05 18:20:02 UTC -* Number of recursive dependencies: 84 +* Version: 1.3 +* GitHub: NA +* Source code: https://github.com/cran/rKOMICS +* Date/Publication: 2023-06-29 22:40:03 UTC +* Number of recursive dependencies: 137 -Run `revdepcheck::cloud_details(, "plantTracker")` for more info +Run `revdepcheck::cloud_details(, "rKOMICS")` for more info
## Newly broken -* checking running R code from vignettes ... ERROR +* checking examples ... ERROR ``` - Errors in running code in vignettes: - when running code in ‘Suggested_plantTracker_Workflow.Rmd’ - ... - a single row. - - When sourcing ‘Suggested_plantTracker_Workflow.R’: - Error: Summary operations are not defined for quosures. Do you need to unquote - the quosure? + Running examples in ‘rKOMICS-Ex.R’ failed + The error most likely occurred in: - # Bad: min(myquosure) + > ### Name: msc.pca + > ### Title: Prinicple Component Analysis based on MSC + > ### Aliases: msc.pca + > + > ### ** Examples + > + > data(matrices) ... - Error: Summary operations are not defined for quosures. Do you need to unquote - the quosure? - - # Bad: min(myquosure) - - # Good: min(!!myquosure) + 11. │ └─base::withCallingHandlers(...) + 12. └─ggplot2 (local) f(l = layers[[i]], d = data[[i]]) + 13. └─l$compute_geom_2(d, theme = plot$theme) + 14. └─ggplot2 (local) compute_geom_2(..., self = self) + 15. └─self$geom$use_defaults(...) + 16. └─ggplot2 (local) use_defaults(..., self = self) + 17. └─ggplot2:::check_aesthetics(new_params, nrow(data)) + 18. └─cli::cli_abort(...) + 19. └─rlang::abort(...) Execution halted - - ‘Suggested_plantTracker_Workflow.Rmd’ using ‘UTF-8’... failed - ‘Using_the_plantTracker_trackSpp_function.Rmd’ using ‘UTF-8’... failed + ``` + +## In both + +* checking installed package size ... NOTE + ``` + installed size is 24.8Mb + sub-directories of 1Mb or more: + extdata 24.0Mb ``` * checking re-building of vignette outputs ... NOTE ``` Error(s) in re-building vignettes: - --- re-building ‘Suggested_plantTracker_Workflow.Rmd’ using rmarkdown - Warning in options[opts_class] <- Map(code_folding_class, options[opts_class], : - number of items to replace is not a multiple of replacement length - Warning in options[opts_attr] <- Map(code_folding_attr, options[opts_attr], : - number of items to replace is not a multiple of replacement length - Warning in options[opts_class] <- Map(code_folding_class, options[opts_class], : - number of items to replace is not a multiple of replacement length - Warning in options[opts_attr] <- Map(code_folding_attr, options[opts_attr], : - number of items to replace is not a multiple of replacement length + --- re-building ‘example.Rnw’ using Sweave + Loading required package: viridisLite + Warning: Removed 95 rows containing non-finite outside the scale range + (`stat_boxplot()`). + Warning: Removed 89 rows containing non-finite outside the scale range + (`stat_boxplot()`). + Warning: Removed 149 rows containing non-finite outside the scale range + (`stat_boxplot()`). + Warning: Removed 286 rows containing non-finite outside the scale range ... + l.5 \usepackage + {xcolor}^^M + ! ==> Fatal error occurred, no output PDF file produced! + --- failed re-building ‘example.Rnw’ - # Good: min(!!myquosure) - --- failed re-building ‘Using_the_plantTracker_trackSpp_function.Rmd’ - - SUMMARY: processing the following files failed: - ‘Suggested_plantTracker_Workflow.Rmd’ - ‘Using_the_plantTracker_trackSpp_function.Rmd’ + SUMMARY: processing the following file failed: + ‘example.Rnw’ Error: Vignette re-building failed. Execution halted ``` -# Plasmidprofiler +# rmcorr
-* Version: 0.1.6 -* GitHub: NA -* Source code: https://github.com/cran/Plasmidprofiler -* Date/Publication: 2017-01-06 01:10:47 -* Number of recursive dependencies: 90 +* Version: 0.6.0 +* GitHub: https://github.com/lmarusich/rmcorr +* Source code: https://github.com/cran/rmcorr +* Date/Publication: 2023-08-09 16:40:10 UTC +* Number of recursive dependencies: 140 -Run `revdepcheck::cloud_details(, "Plasmidprofiler")` for more info +Run `revdepcheck::cloud_details(, "rmcorr")` for more info
## Newly broken -* checking examples ... ERROR +* checking re-building of vignette outputs ... NOTE ``` - Running examples in ‘Plasmidprofiler-Ex.R’ failed - The error most likely occurred in: + Error(s) in re-building vignettes: + --- re-building ‘CI_fix.Rmd’ using rmarkdown + --- finished re-building ‘CI_fix.Rmd’ + + --- re-building ‘FAQ_and_limitations.Rmd’ using rmarkdown + --- finished re-building ‘FAQ_and_limitations.Rmd’ + + --- re-building ‘New_rmcorr_paper_analyses_figures.Rmd’ using rmarkdown + ``` + +## In both + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘estimates_w_NaN.Rmd’ + ... + + > library(ggExtra) + + > load(file = "../man/data/ghosh_synth.rda") + Warning in readChar(con, 5L, useBytes = TRUE) : + cannot open compressed file '../man/data/ghosh_synth.rda', probable reason 'No such file or directory' - > ### Name: main - > ### Title: Main: Run everything - > ### Aliases: main - > - > ### ** Examples - > - > main(blastdata, ... - Warning: Vectorized input to `element_text()` is not officially supported. - ℹ Results may be unexpected or may change in future versions of ggplot2. - Warning in geom_tile(aes(x = Plasmid, y = Sample, label = AMR_gene, fill = Inc_group, : - Ignoring unknown aesthetics: label and text - Warning: Use of `report$Sureness` is discouraged. - ℹ Use `Sureness` instead. - Error in compute_geom_2(..., self = self) : - argument "theme" is missing, with no default - Calls: main ... use_defaults -> eval_from_theme -> %||% -> calc_element Execution halted + + ‘CI_fix.Rmd’ using ‘UTF-8’... OK + ‘FAQ_and_limitations.Rmd’ using ‘UTF-8’... OK + ‘New_rmcorr_paper_analyses_figures.Rmd’ using ‘UTF-8’... OK + ‘compcor.Rmd’ using ‘UTF-8’... OK + ‘estimates_w_NaN.Rmd’ using ‘UTF-8’... failed + ‘model_diag.Rmd’ using ‘UTF-8’... OK + ‘repro_bootstrapping.Rmd’ using ‘UTF-8’... OK + ‘rmcorr_mat.Rmd’ using ‘UTF-8’... OK ``` -# plotDK +# RNAseqQC
-* Version: 0.1.0 +* Version: 0.1.4 * GitHub: NA -* Source code: https://github.com/cran/plotDK -* Date/Publication: 2021-10-01 08:00:02 UTC -* Number of recursive dependencies: 86 +* Source code: https://github.com/cran/RNAseqQC +* Date/Publication: 2022-06-15 09:50:06 UTC +* Number of recursive dependencies: 176 -Run `revdepcheck::cloud_details(, "plotDK")` for more info +Run `revdepcheck::cloud_details(, "RNAseqQC")` for more info
## Newly broken -* checking tests ... ERROR +* checking running R code from vignettes ... ERROR ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(plotDK) - > - > test_check("plotDK") - [ FAIL 1 | WARN 0 | SKIP 0 | PASS 49 ] - - ══ Failed tests ════════════════════════════════════════════════════════════════ - ... - 9. └─ggplot2 (local) compute_geom_2(..., self = self) - 10. └─self$geom$use_defaults(data, self$aes_params, modifiers, theme = theme) - 11. └─ggplot2 (local) use_defaults(..., self = self) - 12. └─ggplot2:::eval_from_theme(default_aes, theme) - 13. ├─calc_element("geom", theme) %||% .default_geom_element - 14. └─ggplot2::calc_element("geom", theme) - - [ FAIL 1 | WARN 0 | SKIP 0 | PASS 49 ] - Error: Test failures - Execution halted + Errors in running code in vignettes: + when running code in ‘introduction.Rmd’ + ... + + show_plot = F)$plot + theme(legend.position = "bottom") + + > plot_loadings(pca_res, PC = 2, color_by = "gc_content") + + > plot_pca_scatters(vsd, n_PCs = 5, color_by = "treatment", + + shape_by = "mutation") + + When sourcing 'introduction.R': + Error: object is not coercible to a unit + Execution halted + + ‘data.Rmd’ using ‘UTF-8’... OK + ‘introduction.Rmd’ using ‘UTF-8’... failed ``` -## In both - -* checking dependencies in R code ... NOTE +* checking re-building of vignette outputs ... NOTE ``` - Namespace in Imports field not imported from: ‘mapproj’ - All declared Imports should be used. + Error(s) in re-building vignettes: + --- re-building ‘data.Rmd’ using rmarkdown + --- finished re-building ‘data.Rmd’ + + --- re-building ‘introduction.Rmd’ using rmarkdown ``` -* checking data for non-ASCII characters ... NOTE +## In both + +* checking installed package size ... NOTE ``` - Note: found 12992 marked UTF-8 strings + installed size is 9.9Mb + sub-directories of 1Mb or more: + data 7.5Mb + doc 2.2Mb ``` -# plotly +# roahd
-* Version: 4.10.4 -* GitHub: https://github.com/plotly/plotly.R -* Source code: https://github.com/cran/plotly -* Date/Publication: 2024-01-13 22:40:02 UTC -* Number of recursive dependencies: 148 +* Version: 1.4.3 +* GitHub: https://github.com/astamm/roahd +* Source code: https://github.com/cran/roahd +* Date/Publication: 2021-11-04 00:10:02 UTC +* Number of recursive dependencies: 88 -Run `revdepcheck::cloud_details(, "plotly")` for more info +Run `revdepcheck::cloud_details(, "roahd")` for more info
@@ -7521,125 +17474,125 @@ Run `revdepcheck::cloud_details(, "plotly")` for more info * checking examples ... ERROR ``` - Running examples in ‘plotly-Ex.R’ failed + Running examples in ‘roahd-Ex.R’ failed The error most likely occurred in: - > ### Name: style - > ### Title: Modify trace(s) - > ### Aliases: style + > ### Name: plot.depthgram + > ### Title: Specialized method to plot 'depthgram' objects + > ### Aliases: plot.depthgram > > ### ** Examples > - > ## Don't show: + > N <- 50 ... - + style(p, marker.line = list(width = 2.5), marker.size = 10) - + ## Don't show: - + }) # examplesIf - > (p <- ggplotly(qplot(data = mtcars, wt, mpg, geom = c("point", "smooth")))) - Warning: `qplot()` was deprecated in ggplot2 3.4.0. - `geom_smooth()` using method = 'loess' and formula = 'y ~ x' - Error in compute_geom_2(..., self = self) : - argument "theme" is missing, with no default - Calls: ... use_defaults -> eval_from_theme -> %||% -> calc_element + + N, + + centerline = sin(2 * pi * grid), + + Cov = Cov + + ) + > names <- paste0("id_", 1:nrow(Data[[1]])) + > DG <- depthgram(Data, marginal_outliers = TRUE, ids = names) + > plot(DG) + Error in pm[[2]] : subscript out of bounds + Calls: plot ... plotly_build -> ggplotly -> ggplotly.ggplot -> gg2list Execution halted ``` -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library("testthat") - > library("plotly") - Loading required package: ggplot2 - - Attaching package: 'plotly' - - The following object is masked from 'package:ggplot2': - ... - • plotly-subplot/subplot-bump-axis-annotation.svg - • plotly-subplot/subplot-bump-axis-image.svg - • plotly-subplot/subplot-bump-axis-shape-shared.svg - • plotly-subplot/subplot-bump-axis-shape.svg - • plotly-subplot/subplot-reposition-annotation.svg - • plotly-subplot/subplot-reposition-image.svg - • plotly-subplot/subplot-reposition-shape-fixed.svg - • plotly-subplot/subplot-reposition-shape.svg - Error: Test failures - Execution halted - ``` - ## In both * checking installed package size ... NOTE ``` - installed size is 7.9Mb + installed size is 7.4Mb sub-directories of 1Mb or more: - R 1.5Mb - htmlwidgets 4.0Mb + data 5.0Mb + doc 1.7Mb ``` -# pmartR +# robustbase
-* Version: 2.4.4 -* GitHub: https://github.com/pmartR/pmartR -* Source code: https://github.com/cran/pmartR -* Date/Publication: 2024-02-27 21:20:02 UTC -* Number of recursive dependencies: 150 +* Version: 0.99-2 +* GitHub: NA +* Source code: https://github.com/cran/robustbase +* Date/Publication: 2024-01-27 16:30:02 UTC +* Number of recursive dependencies: 77 -Run `revdepcheck::cloud_details(, "pmartR")` for more info +Run `revdepcheck::cloud_details(, "robustbase")` for more info
## Newly broken -* checking tests ... ERROR +* checking running R code from vignettes ... ERROR ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(pmartR) - > - > test_check("pmartR") - [ FAIL 1 | WARN 0 | SKIP 6 | PASS 2575 ] - - ══ Skipped tests (6) ═══════════════════════════════════════════════════════════ - ... - • plots/plot-spansres-color-high-color-low.svg - • plots/plot-spansres.svg - • plots/plot-statres-anova-volcano.svg - • plots/plot-statres-anova.svg - • plots/plot-statres-combined-volcano.svg - • plots/plot-statres-combined.svg - • plots/plot-statres-gtest.svg - • plots/plot-totalcountfilt.svg - Error: Test failures - Execution halted + Errors in running code in vignettes: + when running code in ‘lmrob_simulation.Rnw’ + ... + + d.x_psi(x, "lqq"), d.x_psi(x, "hampel")) + + > print(ggplot(tmp, aes(x, value, color = psi)) + geom_line(lwd = 1.25) + + + ylab(quote(psi(x))) + scale_color_discrete(name = quote(psi ~ + + .... [TRUNCATED] + + When sourcing ‘lmrob_simulation.R’: + Error: Theme element `plot.margin` must have class + . + Execution halted + + ‘fastMcd-kmini.Rnw’ using ‘UTF-8’... OK + ‘lmrob_simulation.Rnw’ using ‘UTF-8’... failed + ‘psi_functions.Rnw’ using ‘UTF-8’... OK ``` ## In both -* checking installed package size ... NOTE +* checking package dependencies ... NOTE ``` - installed size is 14.3Mb - sub-directories of 1Mb or more: - libs 11.4Mb + Packages which this enhances but not available for checking: + 'robustX', 'matrixStats', 'quantreg', 'Hmisc' ``` -# pmxTools +* checking Rd cross-references ... NOTE + ``` + Packages unavailable to check Rd xrefs: ‘matrixStats’, ‘robustX’, ‘quantreg’, ‘Hmisc’ + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘fastMcd-kmini.Rnw’ using Sweave + Loading required package: robustbase + Error: processing vignette 'fastMcd-kmini.Rnw' failed with diagnostics: + Running 'texi2dvi' on 'fastMcd-kmini.tex' failed. + LaTeX errors: + ! LaTeX Error: File `mathtools.sty' not found. + + Type X to quit or to proceed, + or enter new name. (Default extension: sty) + ... + l.179 \RequirePackage{grfext}\relax + ^^M + ! ==> Fatal error occurred, no output PDF file produced! + --- failed re-building ‘psi_functions.Rnw’ + + SUMMARY: processing the following files failed: + ‘fastMcd-kmini.Rnw’ ‘lmrob_simulation.Rnw’ ‘psi_functions.Rnw’ + + Error: Vignette re-building failed. + Execution halted + ``` + +# romic
-* Version: 1.3 -* GitHub: https://github.com/kestrel99/pmxTools -* Source code: https://github.com/cran/pmxTools -* Date/Publication: 2023-02-21 16:00:08 UTC -* Number of recursive dependencies: 85 +* Version: 1.1.3 +* GitHub: NA +* Source code: https://github.com/cran/romic +* Date/Publication: 2023-09-21 05:40:02 UTC +* Number of recursive dependencies: 113 -Run `revdepcheck::cloud_details(, "pmxTools")` for more info +Run `revdepcheck::cloud_details(, "romic")` for more info
@@ -7650,44 +17603,37 @@ Run `revdepcheck::cloud_details(, "pmxTools")` for more info Running ‘testthat.R’ Running the tests in ‘tests/testthat.R’ failed. Complete output: - > library(testthat) - > library(pmxTools) - Loading required package: patchwork - > - > test_check("pmxTools") - [ FAIL 1 | WARN 1 | SKIP 12 | PASS 110 ] - - ... - 24. └─handlers[[1L]](cnd) - 25. └─cli::cli_abort(...) - 26. └─rlang::abort(...) + > # This file is part of the standard setup for testthat. + > # It is recommended that you do not modify it. + > # + > # Where should you do additional test configuration? + > # Learn more about the roles of various files in: + > # * https://r-pkgs.org/testing-design.html#sec-tests-files-overview + > # * https://testthat.r-lib.org/articles/special-files.html + ... + 3. │ │ └─base::withCallingHandlers(...) + 4. │ ├─plotly::ggplotly(heatmap_plot) %>% plotly::layout(margin = 0) + 5. │ ├─plotly::ggplotly(heatmap_plot) + 6. │ └─plotly:::ggplotly.ggplot(heatmap_plot) + 7. │ └─plotly::gg2list(...) + 8. └─plotly::layout(., margin = 0) - [ FAIL 1 | WARN 1 | SKIP 12 | PASS 110 ] - Deleting unused snapshots: - • plot/conditioned-distplot.svg - • plot/perc.svg + [ FAIL 1 | WARN 0 | SKIP 7 | PASS 66 ] Error: Test failures Execution halted ``` -## In both - -* checking Rd cross-references ... NOTE - ``` - Package unavailable to check Rd xrefs: ‘DiagrammeR’ - ``` - -# PointedSDMs +# roptions
-* Version: 1.3.2 -* GitHub: https://github.com/PhilipMostert/PointedSDMs -* Source code: https://github.com/cran/PointedSDMs -* Date/Publication: 2024-02-02 09:50:02 UTC -* Number of recursive dependencies: 143 +* Version: 1.0.3 +* GitHub: NA +* Source code: https://github.com/cran/roptions +* Date/Publication: 2020-05-11 11:10:06 UTC +* Number of recursive dependencies: 70 -Run `revdepcheck::cloud_details(, "PointedSDMs")` for more info +Run `revdepcheck::cloud_details(, "roptions")` for more info
@@ -7695,336 +17641,235 @@ Run `revdepcheck::cloud_details(, "PointedSDMs")` for more info * checking examples ... ERROR ``` - Running examples in ‘PointedSDMs-Ex.R’ failed + Running examples in ‘roptions-Ex.R’ failed The error most likely occurred in: - > ### Name: dataSDM - > ### Title: R6 class for creating a 'dataSDM' object. - > ### Aliases: dataSDM + > ### Name: box.spread + > ### Title: Box Spread Strategy Function + > ### Aliases: box.spread > > ### ** Examples > - > + > box.spread(100, 105, 95, 110, 3.2, 2.6, 1.1, 2.4) ... - 17. └─ggplot2 (local) FUN(X[[i]], ...) - 18. └─g$draw_key(data, g$params, key_size) - 19. └─ggplot2 (local) draw_key(...) - 20. └─ggplot2::draw_key_point(data, params, size) - 21. ├─grid::pointsGrob(...) - 22. │ └─grid::grob(...) - 23. └─ggplot2::ggpar(...) - 24. └─rlang:::Ops.quosure(pointsize, .pt) - 25. └─rlang::abort(...) + 35 5.7 + 36 5.7 + 37 5.7 + 38 5.7 + 39 5.7 + 40 5.7 + 41 5.7 + Error in pm[[2]] : subscript out of bounds + Calls: box.spread -> print -> ggplotly -> ggplotly.ggplot -> gg2list Execution halted ``` ## In both -* checking running R code from vignettes ... WARNING +* checking LazyData ... NOTE ``` - Errors in running code in vignettes: - when running code in ‘Marked_Point_Process.Rmd’ - ... - - > knitr::opts_chunk$set(collapse = TRUE, comment = "#>", - + eval = FALSE, warning = FALSE, message = FALSE) - - > library(spatstat) - - When sourcing ‘Marked_Point_Process.R’: - ... - + resolution = "high") - - When sourcing ‘Spatiotemporal_example.R’: - Error: there is no package called ‘USAboundaries’ - Execution halted - - ‘Marked_Point_Process.Rmd’ using ‘UTF-8’... failed - ‘Setophaga.Rmd’ using ‘UTF-8’... failed - ‘Solitary_tinamou.Rmd’ using ‘UTF-8’... failed - ‘Spatiotemporal_example.Rmd’ using ‘UTF-8’... failed + 'LazyData' is specified without a 'data' directory ``` -# posterior +# rotations
-* Version: 1.5.0 -* GitHub: https://github.com/stan-dev/posterior -* Source code: https://github.com/cran/posterior -* Date/Publication: 2023-10-31 08:30:02 UTC -* Number of recursive dependencies: 120 +* Version: 1.6.5 +* GitHub: https://github.com/stanfill/rotationsC +* Source code: https://github.com/cran/rotations +* Date/Publication: 2023-12-08 00:10:02 UTC +* Number of recursive dependencies: 79 -Run `revdepcheck::cloud_details(, "posterior")` for more info +Run `revdepcheck::cloud_details(, "rotations")` for more info
## Newly broken -* checking re-building of vignette outputs ... NOTE +* checking examples ... ERROR ``` - Error(s) in re-building vignettes: - ... - --- re-building ‘posterior.Rmd’ using rmarkdown - --- finished re-building ‘posterior.Rmd’ - - --- re-building ‘rvar.Rmd’ using rmarkdown + Running examples in ‘rotations-Ex.R’ failed + The error most likely occurred in: - Quitting from lines at lines 526-529 [mixture] (rvar.Rmd) - Error: processing vignette 'rvar.Rmd' failed with diagnostics: - Problem while setting up geom aesthetics. + > ### Name: plot + > ### Title: Visualizing random rotations + > ### Aliases: plot plot.SO3 plot.Q4 + > + > ### ** Examples + > + > r <- rvmises(200, kappa = 1.0) ... - NULL, NULL, NULL, NULL, 0.2, NULL, list(NULL, NULL, NULL, 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, NULL, NULL, NULL, TRUE), NULL, "right", NULL, NULL, NULL, "center", NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, c(0, 0, 0, 0), list(), 11, list("grey92", NA, NULL, NULL, TRUE), list(), 5.5, NULL, NULL, list("white", NULL, NULL, NULL, FALSE, TRUE), NULL, list(NULL, 0.5, NULL, NULL, FALSE, TRUE), NULL, NULL, NULL, NULL, FALSE, list(NULL, - "white", NULL, NULL, TRUE), list(NULL, NULL, NULL, 1.2, 0, 1, NULL, NULL, c(0, 0, 5.5, 0), NULL, TRUE), "panel", list(NULL, NULL, NULL, NULL, 0, 1, NULL, NULL, c(0, 0, 5.5, 0), NULL, TRUE), list(NULL, NULL, NULL, 0.8, 1, 1, NULL, NULL, c(5.5, 0, 0, 0), NULL, TRUE), "panel", list(NULL, NULL, NULL, 1.2, 0.5, 0.5, NULL, NULL, NULL, NULL, TRUE), "topleft", NULL, c(5.5, 5.5, 5.5, 5.5), list("grey85", NA, NULL, NULL, TRUE), NULL, NULL, "inherit", "inside", list(NULL, NULL, "grey10", 0.8, NULL, - NULL, NULL, NULL, c(4.4, 4.4, 4.4, 4.4), NULL, TRUE), NULL, NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, NULL, -90, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, NULL, 90, NULL, NULL, NULL, TRUE), NULL, 2.75, 2.75)) - --- failed re-building ‘rvar.Rmd’ - - SUMMARY: processing the following file failed: - ‘rvar.Rmd’ - - Error: Vignette re-building failed. + Backtrace: + ▆ + 1. ├─base (local) ``(x) + 2. └─ggplot2:::print.ggplot(x) + 3. ├─ggplot2::ggplot_gtable(data) + 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) + 5. └─ggplot2::calc_element("plot.margin", theme) + 6. └─cli::cli_abort(...) + 7. └─rlang::abort(...) Execution halted ``` -## In both - * checking running R code from vignettes ... ERROR ``` Errors in running code in vignettes: - when running code in ‘rvar.Rmd’ + when running code in ‘rotations-intro.Rnw’ ... - > y - rvar<4000>[3] mean ± sd: - [1] 3.00 ± 1.00 2.02 ± 0.99 0.96 ± 0.99 - > X + y + > region(x = Rs, method = "direct", type = "bootstrap", + + estimator = "median", alp = 0.05, m = 300) + [1] 0.238 - When sourcing ‘rvar.R’: - Error: Cannot broadcast array of shape [4000,3,1] to array of shape [4000,4,3]: - All dimensions must be 1 or equal. - Execution halted + > plot(x = Rs, center = mean(Rs), show_estimates = "all") - ‘posterior.Rmd’ using ‘UTF-8’... OK - ‘rvar.Rmd’ using ‘UTF-8’... failed - ``` - -# PPQplan - -
- -* Version: 1.1.0 -* GitHub: https://github.com/allenzhuaz/PPQplan -* Source code: https://github.com/cran/PPQplan -* Date/Publication: 2020-10-08 04:30:06 UTC -* Number of recursive dependencies: 119 - -Run `revdepcheck::cloud_details(, "PPQplan")` for more info - -
- -## Newly broken - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘PPQnote.Rmd’ using rmarkdown - --- finished re-building ‘PPQnote.Rmd’ + When sourcing ‘rotations-intro.R’: + Error: Theme element `plot.margin` must have class . + Execution halted - --- re-building ‘PPQplan-vignette.Rmd’ using rmarkdown + ‘rotations-intro.Rnw’ using ‘UTF-8’... failed ``` ## In both -* checking running R code from vignettes ... ERROR +* checking C++ specification ... NOTE ``` - Errors in running code in vignettes: - when running code in ‘PPQplan-vignette.Rmd’ - ... - - > devtools::load_all() - - When sourcing ‘PPQplan-vignette.R’: - Error: Could not find a root 'DESCRIPTION' file that starts with '^Package' in - '/tmp/Rtmpv5CY0G/file171e30ae70cd/vignettes'. - ℹ Are you in your project directory and does your project have a 'DESCRIPTION' - file? - Execution halted - - ‘PPQnote.Rmd’ using ‘UTF-8’... OK - ‘PPQplan-vignette.Rmd’ using ‘UTF-8’... failed + Specified C++11: please drop specification unless essential ``` * checking installed package size ... NOTE ``` - installed size is 12.1Mb + installed size is 19.1Mb sub-directories of 1Mb or more: - doc 12.0Mb - ``` - -* checking LazyData ... NOTE - ``` - 'LazyData' is specified without a 'data' directory - ``` - -# ppseq - -
- -* Version: 0.2.4 -* GitHub: https://github.com/zabore/ppseq -* Source code: https://github.com/cran/ppseq -* Date/Publication: 2024-04-04 18:20:02 UTC -* Number of recursive dependencies: 106 - -Run `revdepcheck::cloud_details(, "ppseq")` for more info - -
- -## Newly broken - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘one_sample_expansion.Rmd’ - ... - - - - - > ptest <- plot(one_sample_cal_tbl, type1_range = c(0.05, - + 0.1), minimum_power = 0.7, plotly = TRUE) - - ... - - > ptest <- plot(two_sample_cal_tbl, type1_range = c(0.05, - + 0.1), minimum_power = 0.7, plotly = TRUE) - - When sourcing ‘two_sample_randomized.R’: - Error: argument "theme" is missing, with no default - Execution halted - - ‘one_sample_expansion.Rmd’ using ‘UTF-8’... failed - ‘two_sample_randomized.Rmd’ using ‘UTF-8’... failed + R 3.5Mb + data 7.0Mb + libs 8.0Mb ``` * checking re-building of vignette outputs ... NOTE ``` Error(s) in re-building vignettes: ... - --- re-building ‘one_sample_expansion.Rmd’ using rmarkdown + --- re-building ‘rotations-intro.Rnw’ using knitr - Quitting from lines at lines 183-188 [unnamed-chunk-13] (one_sample_expansion.Rmd) - Error: processing vignette 'one_sample_expansion.Rmd' failed with diagnostics: - argument "theme" is missing, with no default - --- failed re-building ‘one_sample_expansion.Rmd’ - - --- re-building ‘two_sample_randomized.Rmd’ using rmarkdown - ... - Quitting from lines at lines 179-184 [unnamed-chunk-13] (two_sample_randomized.Rmd) - Error: processing vignette 'two_sample_randomized.Rmd' failed with diagnostics: - argument "theme" is missing, with no default - --- failed re-building ‘two_sample_randomized.Rmd’ + Quitting from lines 324-336 [ex7] (rotations-intro.Rnw) + Error: processing vignette 'rotations-intro.Rnw' failed with diagnostics: + Theme element `plot.margin` must have class . + --- failed re-building ‘rotations-intro.Rnw’ - SUMMARY: processing the following files failed: - ‘one_sample_expansion.Rmd’ ‘two_sample_randomized.Rmd’ + SUMMARY: processing the following file failed: + ‘rotations-intro.Rnw’ Error: Vignette re-building failed. Execution halted ``` -## In both - -* checking installed package size ... NOTE - ``` - installed size is 11.0Mb - sub-directories of 1Mb or more: - doc 10.5Mb - ``` - -# processmapR +# rreg
-* Version: 0.5.3 -* GitHub: https://github.com/bupaverse/processmapr -* Source code: https://github.com/cran/processmapR -* Date/Publication: 2023-04-06 12:50:02 UTC -* Number of recursive dependencies: 118 +* Version: 0.2.1 +* GitHub: NA +* Source code: https://github.com/cran/rreg +* Date/Publication: 2018-03-22 14:11:31 UTC +* Number of recursive dependencies: 50 -Run `revdepcheck::cloud_details(, "processmapR")` for more info +Run `revdepcheck::cloud_details(, "rreg")` for more info
## Newly broken -* checking tests ... ERROR +* checking examples ... ERROR ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(processmapR) - - Attaching package: 'processmapR' - - The following object is masked from 'package:stats': - + Running examples in ‘rreg-Ex.R’ failed + The error most likely occurred in: + + > ### Name: regbar + > ### Title: Barplot with explicit data comparison + > ### Aliases: regbar + > + > ### ** Examples + > + > # basic usage ... - 20. └─ggplot2 (local) use_defaults(..., self = self) - 21. └─ggplot2:::eval_from_theme(default_aes, theme) - 22. ├─calc_element("geom", theme) %||% .default_geom_element - 23. └─ggplot2::calc_element("geom", theme) - ── Failure ('test_trace_explorer.R:240:3'): test trace_explorer on eventlog with param `plotly` ── - `chart` inherits from 'gg'/'ggplot' not 'plotly'. - - [ FAIL 6 | WARN 0 | SKIP 10 | PASS 107 ] - Error: Test failures - Execution halted + Backtrace: + ▆ + 1. ├─base (local) ``(x) + 2. └─ggplot2:::print.ggplot(x) + 3. ├─ggplot2::ggplot_gtable(data) + 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) + 5. └─ggplot2::calc_element("plot.margin", theme) + 6. └─cli::cli_abort(...) + 7. └─rlang::abort(...) + Execution halted ``` -# QuadratiK +# rSDI
-* Version: 1.0.0 -* GitHub: NA -* Source code: https://github.com/cran/QuadratiK -* Date/Publication: 2024-02-23 18:30:05 UTC -* Number of recursive dependencies: 131 +* Version: 0.2.1 +* GitHub: https://github.com/ehengirmen/rSDI +* Source code: https://github.com/cran/rSDI +* Date/Publication: 2024-05-30 07:40:02 UTC +* Number of recursive dependencies: 93 -Run `revdepcheck::cloud_details(, "QuadratiK")` for more info +Run `revdepcheck::cloud_details(, "rSDI")` for more info
## Newly broken -* checking whether package ‘QuadratiK’ can be installed ... WARNING +* checking running R code from vignettes ... ERROR ``` - Found the following significant warnings: - Warning: replacing previous import ‘ggplot2::ggpar’ by ‘ggpubr::ggpar’ when loading ‘QuadratiK’ - See ‘/tmp/workdir/QuadratiK/new/QuadratiK.Rcheck/00install.out’ for details. + Errors in running code in vignettes: + when running code in ‘rSDI.Rmd’ + ... + |A | 0| 3| + |B | 4| 0| + |C | 0| 0| + |D | 4| 3| + + > p + + When sourcing ‘rSDI.R’: + Error: Theme element `plot.margin` must have class . + Execution halted + + ‘rSDI.Rmd’ using ‘UTF-8’... failed ``` -## In both - -* checking installed package size ... NOTE +* checking re-building of vignette outputs ... NOTE ``` - installed size is 15.9Mb - sub-directories of 1Mb or more: - libs 15.2Mb + Error(s) in re-building vignettes: + ... + --- re-building ‘rSDI.Rmd’ using rmarkdown + + Quitting from lines 82-83 [unnamed-chunk-5] (rSDI.Rmd) + Error: processing vignette 'rSDI.Rmd' failed with diagnostics: + Theme element `plot.margin` must have class . + --- failed re-building ‘rSDI.Rmd’ + + SUMMARY: processing the following file failed: + ‘rSDI.Rmd’ + + Error: Vignette re-building failed. + Execution halted ``` -# Radviz +# SangerTools
-* Version: 0.9.3 -* GitHub: https://github.com/yannabraham/Radviz -* Source code: https://github.com/cran/Radviz -* Date/Publication: 2022-03-25 18:10:02 UTC -* Number of recursive dependencies: 64 +* Version: 1.0.2 +* GitHub: NA +* Source code: https://github.com/cran/SangerTools +* Date/Publication: 2022-02-20 13:10:02 UTC +* Number of recursive dependencies: 104 -Run `revdepcheck::cloud_details(, "Radviz")` for more info +Run `revdepcheck::cloud_details(, "SangerTools")` for more info
@@ -8032,119 +17877,237 @@ Run `revdepcheck::cloud_details(, "Radviz")` for more info * checking examples ... ERROR ``` - Running examples in ‘Radviz-Ex.R’ failed + Running examples in ‘SangerTools-Ex.R’ failed The error most likely occurred in: - > ### Name: Radviz - > ### Title: Radviz Projection of Multidimensional Data - > ### Aliases: Radviz + > ### Name: categorical_col_chart + > ### Title: Plot Counts of Categorical Variables + > ### Aliases: categorical_col_chart > > ### ** Examples > - > data(iris) - > das <- c('Sepal.Length','Sepal.Width','Petal.Length','Petal.Width') - > S <- make.S(das) - > rv <- do.radviz(iris,S) - > plot(rv,anchors.only=FALSE) - Error in plot.radviz(rv, anchors.only = FALSE) : - 'language' object cannot be coerced to type 'double' - Calls: plot -> plot.radviz + > library(SangerTools) + ... + Backtrace: + ▆ + 1. ├─base (local) ``(x) + 2. └─ggplot2:::print.ggplot(x) + 3. ├─ggplot2::ggplot_gtable(data) + 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) + 5. └─ggplot2::calc_element("plot.margin", theme) + 6. └─cli::cli_abort(...) + 7. └─rlang::abort(...) Execution halted ``` * checking running R code from vignettes ... ERROR ``` Errors in running code in vignettes: - when running code in ‘multivariate_analysis.Rmd’ + when running code in ‘SangerTools_Vignette.Rmd’ ... + + > diabetes_df <- health_data %>% dplyr::filter(Diabetes == + + 1) - > classic.S <- make.S(get.optim(classic.optim)) + > SangerTools::categorical_col_chart(df = diabetes_df, + + grouping_var = Ethnicity) + scale_fill_sanger() + labs(title = "Diabetic Patients by Eth ..." ... [TRUNCATED] - > btcells.rv <- do.radviz(btcells.df, classic.S) + When sourcing ‘SangerTools_Vignette.R’: + Error: Theme element `plot.margin` must have class . + Execution halted - > plot(btcells.rv) + geom_point(aes(color = Treatment)) + ‘SangerTools_Vignette.Rmd’ using ‘UTF-8’... failed + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + ... + --- re-building ‘SangerTools_Vignette.Rmd’ using rmarkdown - ... - [1] 15792 18 + Quitting from lines 119-140 [categorical_column_chart] (SangerTools_Vignette.Rmd) + Error: processing vignette 'SangerTools_Vignette.Rmd' failed with diagnostics: + Theme element `plot.margin` must have class . + --- failed re-building ‘SangerTools_Vignette.Rmd’ - > ct.rv + SUMMARY: processing the following file failed: + ‘SangerTools_Vignette.Rmd’ - When sourcing ‘single_cell_projections.R’: - Error: 'language' object cannot be coerced to type 'double' + Error: Vignette re-building failed. Execution halted - - ‘multivariate_analysis.Rmd’ using ‘UTF-8’... failed - ‘single_cell_projections.Rmd’ using ‘UTF-8’... failed ``` +# santaR + +
+ +* Version: 1.2.4 +* GitHub: https://github.com/adwolfer/santaR +* Source code: https://github.com/cran/santaR +* Date/Publication: 2024-03-07 00:30:02 UTC +* Number of recursive dependencies: 93 + +Run `revdepcheck::cloud_details(, "santaR")` for more info + +
+ +## Newly broken + * checking re-building of vignette outputs ... NOTE ``` Error(s) in re-building vignettes: - --- re-building ‘multivariate_analysis.Rmd’ using rmarkdown + --- re-building ‘advanced-command-line-functions.Rmd’ using rmarkdown ``` ## In both -* checking installed package size ... NOTE +* checking running R code from vignettes ... ERROR ``` - installed size is 5.9Mb - sub-directories of 1Mb or more: - libs 4.7Mb + Errors in running code in vignettes: + when running code in ‘getting-started.Rmd’ + ... + + > knitr::include_graphics("../man/figures/santaR-approach.jpg") + + When sourcing ‘getting-started.R’: + Error: Cannot find the file(s): "../man/figures/santaR-approach.jpg" + Execution halted + when running code in ‘selecting-optimal-df.Rmd’ + ... + Execution halted + + ‘advanced-command-line-functions.Rmd’ using ‘UTF-8’... OK + ‘automated-command-line.Rmd’ using ‘UTF-8’... OK + ‘getting-started.Rmd’ using ‘UTF-8’... failed + ‘plotting-options.Rmd’ using ‘UTF-8’... OK + ‘prepare-input-data.Rmd’ using ‘UTF-8’... OK + ‘selecting-optimal-df.Rmd’ using ‘UTF-8’... failed + ‘theoretical-background.Rmd’ using ‘UTF-8’... failed + ‘santaR-GUI.pdf.asis’ using ‘UTF-8’... OK ``` -# rangeMapper +# scoringutils
-* 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: 112 +* Version: 1.2.2 +* GitHub: https://github.com/epiforecasts/scoringutils +* Source code: https://github.com/cran/scoringutils +* Date/Publication: 2023-11-29 15:50:10 UTC +* Number of recursive dependencies: 81 -Run `revdepcheck::cloud_details(, "rangeMapper")` for more info +Run `revdepcheck::cloud_details(, "scoringutils")` for more info
## Newly broken +* checking examples ... ERROR + ``` + Running examples in ‘scoringutils-Ex.R’ failed + The error most likely occurred in: + + > ### Name: plot_predictions + > ### Title: Plot Predictions vs True Values + > ### Aliases: plot_predictions + > + > ### ** Examples + > + > library(ggplot2) + ... + + by = c("target_type", "location"), + + range = c(0, 50, 90, 95) + + ) + + + facet_wrap(~ location + target_type, scales = "free_y") + + + aes(fill = model, color = model) + Error in use_defaults(..., self = self) : + unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, "black", TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), NULL, list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), 5.5, c(5.5, 5.5, 5.5, 5.5), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.75, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, + NULL, NULL, NULL, 1, 90, NULL, c(0, 2.75, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 1, NULL, NULL, NULL, c(0, 2.2, 0, 0), NULL, TRUE), NULL, l + Calls: ... -> -> compute_geom_2 -> + Execution halted + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘metric-details.Rmd’ using rmarkdown + --- finished re-building ‘metric-details.Rmd’ + + --- re-building ‘scoring-forecasts-directly.Rmd’ using rmarkdown + --- finished re-building ‘scoring-forecasts-directly.Rmd’ + + --- re-building ‘scoringutils.Rmd’ using rmarkdown + ``` + +## In both + * checking running R code from vignettes ... ERROR ``` Errors in running code in vignettes: - when running code in ‘Case_studies_Valcu_et_al_2012.Rmd’ + when running code in ‘scoringutils.Rmd’ ... - + geom_sf(data = bmr, aes(fill = value), size = 0.05) + scale_fill_gradientn(co .... [TRUNCATED] + The following messages were produced when checking inputs: + 1. 144 values for `prediction` are NA in the data provided and the corresponding rows were removed. This may indicate a problem if unexpected. - When sourcing ‘Case_studies_Valcu_et_al_2012.R’: - Error: Summary operations are not defined for quosures. Do you need to unquote - the quosure? + > example_quantile %>% make_NA(what = "truth", target_end_date >= + + "2021-07-15", target_end_date < "2021-05-22") %>% make_NA(what = "forecast", .... [TRUNCATED] - # Bad: min(myquosure) - - # Good: min(!!myquosure) + When sourcing ‘scoringutils.R’: + Error: unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, "black", TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), NULL, list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), 5.5, c(5.5, 5.5, 5.5, 5.5), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.75, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, + NULL, NULL, NULL, 1, 90, NULL, c(0, 2.75, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 1, NULL, NULL, NULL, c(0, 2.2, 0, 0), NULL, TRUE), NULL, lis Execution halted - ‘Case_studies_Valcu_et_al_2012.Rmd’ using ‘UTF-8’... failed - ‘rangeMapper.Rmd’ using ‘UTF-8’... OK + ‘metric-details.Rmd’ using ‘UTF-8’... OK + ‘scoring-forecasts-directly.Rmd’ using ‘UTF-8’... OK + ‘scoringutils.Rmd’ using ‘UTF-8’... failed ``` -* checking re-building of vignette outputs ... NOTE +# SCVA + +
+ +* Version: 1.3.1 +* GitHub: NA +* Source code: https://github.com/cran/SCVA +* Date/Publication: 2020-01-09 22:50:10 UTC +* Number of recursive dependencies: 80 + +Run `revdepcheck::cloud_details(, "SCVA")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR ``` - Error(s) in re-building vignettes: - --- re-building ‘Case_studies_Valcu_et_al_2012.Rmd’ using rmarkdown + Running examples in ‘SCVA-Ex.R’ failed + The error most likely occurred in: + + > ### Name: graphly + > ### Title: Interactive plot of single-case data + > ### Aliases: graphly + > ### Keywords: Single-case design Graph + > + > ### ** Examples + > + > data(AB) + > graphly(design = "AB", data = AB) + Error in pm[[2]] : subscript out of bounds + Calls: graphly -> ggplotly -> ggplotly.ggplot -> gg2list + Execution halted ``` -# rassta +# SDLfilter
-* Version: 1.0.5 -* GitHub: https://github.com/bafuentes/rassta -* Source code: https://github.com/cran/rassta -* Date/Publication: 2022-08-30 22:30:02 UTC -* Number of recursive dependencies: 121 +* Version: 2.3.3 +* GitHub: https://github.com/TakahiroShimada/SDLfilter +* Source code: https://github.com/cran/SDLfilter +* Date/Publication: 2023-11-10 00:00:11 UTC +* Number of recursive dependencies: 80 -Run `revdepcheck::cloud_details(, "rassta")` for more info +Run `revdepcheck::cloud_details(, "SDLfilter")` for more info
@@ -8152,306 +18115,235 @@ Run `revdepcheck::cloud_details(, "rassta")` for more info * checking examples ... ERROR ``` - Running examples in ‘rassta-Ex.R’ failed + Running examples in ‘SDLfilter-Ex.R’ failed The error most likely occurred in: - > ### Name: select_functions - > ### Title: Select Constrained Univariate Distribution Functions - > ### Aliases: select_functions + > ### Name: ddfilter + > ### Title: Filter locations using a data driven filter + > ### Aliases: ddfilter > > ### ** Examples > - > require(terra) + > #### Load data sets ... - > # Single-layer SpatRaster of topographic classification units - > ## 5 classification units - > tcf <- list.files(path = p, pattern = "topography.tif", full.names = TRUE) - > tcu <- terra::rast(tcf) - > # Automatic selection of distribution functions - > tdif <- select_functions(cu.rast = tcu, var.rast = tvars, fun = mean) - Error in compute_geom_2(..., self = self) : - argument "theme" is missing, with no default - Calls: select_functions ... use_defaults -> eval_from_theme -> %||% -> calc_element + 2. ├─base::do.call(arrangeGrob, c(list(grobs = groups[[g]]), params)) + 3. └─gridExtra (local) ``(grobs = ``, top = "page 1 of 1", layout_matrix = ``) + 4. └─base::lapply(grobs[toconv], ggplot2::ggplotGrob) + 5. └─ggplot2 (local) FUN(X[[i]], ...) + 6. ├─ggplot2::ggplot_gtable(ggplot_build(x)) + 7. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) + 8. └─ggplot2::calc_element("plot.margin", theme) + 9. └─cli::cli_abort(...) + 10. └─rlang::abort(...) Execution halted ``` -* checking tests ... ERROR - ``` - Running ‘tinytest.R’ - Running the tests in ‘tests/tinytest.R’ failed. - Complete output: - > - > if ( requireNamespace("tinytest", quietly=TRUE) ){ - + tinytest::test_package("rassta") - + } - - Attaching package: 'rassta' - - ... - test_select_functions.R....... 0 tests - test_select_functions.R....... 0 tests - test_select_functions.R....... 0 tests - test_select_functions.R....... 0 tests - test_select_functions.R....... 0 tests - test_select_functions.R....... 0 tests - test_select_functions.R....... 0 tests Error in compute_geom_2(..., self = self) : - argument "theme" is missing, with no default - Calls: ... use_defaults -> eval_from_theme -> %||% -> calc_element - Execution halted - ``` +# see -* checking running R code from vignettes ... ERROR +
+ +* Version: 0.8.4 +* GitHub: https://github.com/easystats/see +* Source code: https://github.com/cran/see +* Date/Publication: 2024-04-29 04:40:03 UTC +* Number of recursive dependencies: 233 + +Run `revdepcheck::cloud_details(, "see")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR ``` - Errors in running code in vignettes: - when running code in ‘signature.Rmd’ - ... - > clim.var <- rast(vardir) - - > clim.cu <- rast(paste(d, "/climate.tif", sep = "")) - - > clim.difun <- select_functions(cu.rast = clim.cu, - + var.rast = clim.var, mode = "auto") + Running examples in ‘see-Ex.R’ failed + The error most likely occurred in: + > ### Name: geom_binomdensity + > ### Title: Add dot-densities for binary 'y' variables + > ### Aliases: geom_binomdensity + > + > ### ** Examples + > + > ## Don't show: ... - When sourcing ‘signature.R’: - Error: argument "theme" is missing, with no default + 14. │ └─ggplot2 (local) f(l = layers[[i]], d = data[[i]]) + 15. │ └─l$compute_geom_2(d, theme = plot$theme) + 16. │ └─ggplot2 (local) compute_geom_2(..., self = self) + 17. │ └─self$geom$use_defaults(...) + 18. └─base::.handleSimpleError(...) + 19. └─rlang (local) h(simpleError(msg, call)) + 20. └─handlers[[1L]](cnd) + 21. └─cli::cli_abort(...) + 22. └─rlang::abort(...) Execution halted - - ‘classunits.Rmd’ using ‘UTF-8’... OK - ‘modeling.Rmd’ using ‘UTF-8’... OK - ‘sampling.Rmd’ using ‘UTF-8’... OK - ‘signature.Rmd’ using ‘UTF-8’... failed - ‘similarity.Rmd’ using ‘UTF-8’... OK - ‘stratunits.Rmd’ using ‘UTF-8’... OK ``` -# RCTrep +# sentimentr
-* Version: 1.2.0 -* GitHub: https://github.com/duolajiang/RCTrep -* Source code: https://github.com/cran/RCTrep -* Date/Publication: 2023-11-02 14:40:02 UTC -* Number of recursive dependencies: 166 +* Version: 2.9.0 +* GitHub: https://github.com/trinker/sentimentr +* Source code: https://github.com/cran/sentimentr +* Date/Publication: 2021-10-12 08:30:02 UTC +* Number of recursive dependencies: 66 -Run `revdepcheck::cloud_details(, "RCTrep")` for more info +Run `revdepcheck::cloud_details(, "sentimentr")` for more info
## Newly broken -* checking whether package ‘RCTrep’ can be installed ... WARNING +* checking examples ... ERROR + ``` + Running examples in ‘sentimentr-Ex.R’ failed + The error most likely occurred in: + + > ### Name: sentiment + > ### Title: Polarity Score (Sentiment Analysis) + > ### Aliases: sentiment + > + > ### ** Examples + > + > mytext <- c( + ... + Backtrace: + ▆ + 1. ├─base (local) ``(x) + 2. └─ggplot2:::print.ggplot(x) + 3. ├─ggplot2::ggplot_gtable(data) + 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) + 5. └─ggplot2::calc_element("plot.margin", theme) + 6. └─cli::cli_abort(...) + 7. └─rlang::abort(...) + Execution halted + ``` + +## In both + +* checking installed package size ... NOTE ``` - Found the following significant warnings: - Warning: replacing previous import ‘ggplot2::ggpar’ by ‘ggpubr::ggpar’ when loading ‘RCTrep’ - See ‘/tmp/workdir/RCTrep/new/RCTrep.Rcheck/00install.out’ for details. + installed size is 5.5Mb + sub-directories of 1Mb or more: + data 5.0Mb ``` -# redistmetrics +# sentometrics
-* Version: 1.0.7 -* GitHub: https://github.com/alarm-redist/redistmetrics -* Source code: https://github.com/cran/redistmetrics -* Date/Publication: 2023-12-12 19:30:02 UTC -* Number of recursive dependencies: 85 +* Version: 1.0.0 +* GitHub: https://github.com/SentometricsResearch/sentometrics +* Source code: https://github.com/cran/sentometrics +* Date/Publication: 2021-08-18 07:50:02 UTC +* Number of recursive dependencies: 127 -Run `revdepcheck::cloud_details(, "redistmetrics")` for more info +Run `revdepcheck::cloud_details(, "sentometrics")` for more info
## Newly broken -* checking running R code from vignettes ... ERROR +* checking examples ... ERROR ``` - Errors in running code in vignettes: - when running code in ‘compactness.Rmd’ - ... - + labs(fill = "none") - - When sourcing ‘compactness.R’: - Error: Summary operations are not defined for quosures. Do you need to unquote - the quosure? + Running examples in ‘sentometrics-Ex.R’ failed + The error most likely occurred in: - # Bad: min(myquosure) + > ### Name: plot.sento_measures + > ### Title: Plot sentiment measures + > ### Aliases: plot.sento_measures + > + > ### ** Examples + > + > # construct a sento_measures object to start with ... - - # Good: min(!!myquosure) + Backtrace: + ▆ + 1. ├─base (local) ``(x) + 2. └─ggplot2:::print.ggplot(x) + 3. ├─ggplot2::ggplot_gtable(data) + 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) + 5. └─ggplot2::calc_element("plot.margin", theme) + 6. └─cli::cli_abort(...) + 7. └─rlang::abort(...) Execution halted - - ‘compactness.Rmd’ using ‘UTF-8’... failed - ‘distances.Rmd’ using ‘UTF-8’... OK - ‘other.Rmd’ using ‘UTF-8’... OK - ‘party.Rmd’ using ‘UTF-8’... OK - ‘redistmetrics.Rmd’ using ‘UTF-8’... OK - ‘splits.Rmd’ using ‘UTF-8’... OK ``` -* checking re-building of vignette outputs ... NOTE +## In both + +* checking C++ specification ... NOTE ``` - Error(s) in re-building vignettes: - --- re-building ‘compactness.Rmd’ using rmarkdown - - Quitting from lines at lines 29-35 [unnamed-chunk-2] (compactness.Rmd) - Error: processing vignette 'compactness.Rmd' failed with diagnostics: - Summary operations are not defined for quosures. Do you need to unquote - the quosure? - - # Bad: min(myquosure) - - ... - # Good: min(!!myquosure) - --- failed re-building ‘compactness.Rmd’ - - --- re-building ‘distances.Rmd’ using rmarkdown - --- finished re-building ‘distances.Rmd’ - - --- re-building ‘other.Rmd’ using rmarkdown - --- finished re-building ‘other.Rmd’ - - --- re-building ‘party.Rmd’ using rmarkdown + Specified C++11: please drop specification unless essential ``` -## In both - * checking installed package size ... NOTE ``` - installed size is 13.7Mb + installed size is 9.7Mb sub-directories of 1Mb or more: - libs 12.6Mb + data 2.3Mb + libs 6.2Mb ``` -# ref.ICAR - -
- -* Version: 2.0.1 -* GitHub: NA -* Source code: https://github.com/cran/ref.ICAR -* Date/Publication: 2023-08-22 08:50:02 UTC -* Number of recursive dependencies: 103 - -Run `revdepcheck::cloud_details(, "ref.ICAR")` for more info - -
- -## Newly broken - -* checking running R code from vignettes ... ERROR +* checking data for non-ASCII characters ... NOTE ``` - Errors in running code in vignettes: - when running code in ‘ref-icar-vignette.Rmd’ - ... - + scale_fill_brewer(palette = "OrRd") + labs(title = "Plot of observed \n verbal SAT s ..." ... [TRUNCATED] - - When sourcing ‘ref-icar-vignette.R’: - Error: Summary operations are not defined for quosures. Do you need to unquote - the quosure? - - # Bad: min(myquosure) - - # Good: min(!!myquosure) - Execution halted - - ‘ref-icar-vignette.Rmd’ using ‘UTF-8’... failed + Note: found 4436 marked UTF-8 strings ``` -* checking re-building of vignette outputs ... NOTE +* checking for GNU extensions in Makefiles ... NOTE ``` - Error(s) in re-building vignettes: - --- re-building ‘ref-icar-vignette.Rmd’ using rmarkdown - Warning in eng_r(options) : - Failed to tidy R code in chunk 'unnamed-chunk-1'. Reason: - Error : The formatR package is required by the chunk option tidy = TRUE but not installed; tidy = TRUE will be ignored. - - Warning in eng_r(options) : - Failed to tidy R code in chunk 'unnamed-chunk-2'. Reason: - Error : The formatR package is required by the chunk option tidy = TRUE but not installed; tidy = TRUE will be ignored. - - ... - # Bad: min(myquosure) - - # Good: min(!!myquosure) - --- failed re-building ‘ref-icar-vignette.Rmd’ - - SUMMARY: processing the following file failed: - ‘ref-icar-vignette.Rmd’ - - Error: Vignette re-building failed. - Execution halted + GNU make is a SystemRequirements. ``` -# remap +# sglg
-* Version: 0.3.1 -* GitHub: https://github.com/jadonwagstaff/remap -* Source code: https://github.com/cran/remap -* Date/Publication: 2023-06-14 20:50:02 UTC -* Number of recursive dependencies: 64 +* Version: 0.2.2 +* GitHub: NA +* Source code: https://github.com/cran/sglg +* Date/Publication: 2022-09-04 03:50:01 UTC +* Number of recursive dependencies: 96 -Run `revdepcheck::cloud_details(, "remap")` for more info +Run `revdepcheck::cloud_details(, "sglg")` for more info
## Newly broken -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘Introduction_to_remap.Rmd’ - ... - + ggti .... [TRUNCATED] - - When sourcing ‘Introduction_to_remap.R’: - Error: Summary operations are not defined for quosures. Do you need to unquote - the quosure? - - # Bad: min(myquosure) - - # Good: min(!!myquosure) - Execution halted - - ‘Introduction_to_remap.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE +* checking examples ... ERROR ``` - Error(s) in re-building vignettes: - ... - --- re-building ‘Introduction_to_remap.Rmd’ using rmarkdown - - Quitting from lines at lines 43-54 [initial_map] (Introduction_to_remap.Rmd) - Error: processing vignette 'Introduction_to_remap.Rmd' failed with diagnostics: - Summary operations are not defined for quosures. Do you need to unquote - the quosure? - - # Bad: min(myquosure) - - # Good: min(!!myquosure) - --- failed re-building ‘Introduction_to_remap.Rmd’ - - SUMMARY: processing the following file failed: - ‘Introduction_to_remap.Rmd’ + Running examples in ‘sglg-Ex.R’ failed + The error most likely occurred in: - Error: Vignette re-building failed. + > ### Name: deviance_residuals + > ### Title: Deviance Residuals for a Generalized Log-gamma Regression Model + > ### Aliases: deviance_residuals + > + > ### ** Examples + > + > # Example 1 + > n <- 300 + > error <- rglg(n,0,1,1) + > y <- 0.5 + error + > fit <- glg(y~1,data=as.data.frame(y)) + > deviance_residuals(fit) + Error in pm[[2]] : subscript out of bounds + Calls: deviance_residuals ... dots2plots -> ggplotly -> ggplotly.ggplot -> gg2list Execution halted ``` -# rKIN +# SHAPforxgboost
-* Version: 1.0.2 -* GitHub: https://github.com/salbeke/rKIN -* Source code: https://github.com/cran/rKIN -* Date/Publication: 2023-10-02 22:20:02 UTC -* Number of recursive dependencies: 92 +* Version: 0.1.3 +* GitHub: https://github.com/liuyanguu/SHAPforxgboost +* Source code: https://github.com/cran/SHAPforxgboost +* Date/Publication: 2023-05-29 17:20:07 UTC +* Number of recursive dependencies: 120 -Run `revdepcheck::cloud_details(, "rKIN")` for more info +Run `revdepcheck::cloud_details(, "SHAPforxgboost")` for more info
@@ -8459,159 +18351,129 @@ Run `revdepcheck::cloud_details(, "rKIN")` for more info * checking examples ... ERROR ``` - Running examples in ‘rKIN-Ex.R’ failed + Running examples in ‘SHAPforxgboost-Ex.R’ failed The error most likely occurred in: - > ### Name: estEllipse - > ### Title: Estimate Bivariate Normal Ellipse Isotope Niche - > ### Aliases: estEllipse + > ### Name: scatter.plot.diagonal + > ### Title: Make customized scatter plot with diagonal line and R2 printed. + > ### Aliases: scatter.plot.diagonal > > ### ** Examples > - > library(rKIN) + > scatter.plot.diagonal(data = iris, x = "Sepal.Length", y = "Petal.Length") ... - 15. └─ggplot2 (local) FUN(X[[i]], ...) - 16. └─base::lapply(...) - 17. └─ggplot2 (local) FUN(X[[i]], ...) - 18. └─g$draw_key(data, g$params, key_size) - 19. └─ggplot2 (local) draw_key(...) - 20. └─ggplot2::draw_key_polygon(data, params, size) - 21. └─rlang:::Summary.quosure(from_theme(thin), 1.524, na.rm = FALSE) - 22. └─rlang:::abort_quosure_op("Summary", .Generic) - 23. └─rlang::abort(...) + ▆ + 1. └─SHAPforxgboost::scatter.plot.diagonal(...) + 2. └─ggExtra::ggMarginal(...) + 3. └─ggplot2::ggplotGrob(scatP) + 4. ├─ggplot2::ggplot_gtable(ggplot_build(x)) + 5. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) + 6. └─ggplot2::calc_element("plot.margin", theme) + 7. └─cli::cli_abort(...) + 8. └─rlang::abort(...) Execution halted ``` -# rLFT +# shazam
-* Version: 1.0.1 +* Version: 1.2.0 * GitHub: NA -* Source code: https://github.com/cran/rLFT -* Date/Publication: 2021-09-24 04:10:02 UTC -* Number of recursive dependencies: 74 +* Source code: https://github.com/cran/shazam +* Date/Publication: 2023-10-02 18:50:02 UTC +* Number of recursive dependencies: 127 -Run `revdepcheck::cloud_details(, "rLFT")` for more info +Run `revdepcheck::cloud_details(, "shazam")` for more info
## Newly broken +* checking examples ... ERROR + ``` + Running examples in ‘shazam-Ex.R’ failed + The error most likely occurred in: + + > ### Name: plotMutability + > ### Title: Plot mutability probabilities + > ### Aliases: plotMutability + > + > ### ** Examples + > + > # Plot one nucleotide in circular style + ... + 3. └─alakazam (local) ``(C = ``, ncol = 1L) + 4. ├─base::plot(p[[1]]) + 5. ├─base::plot(p[[1]]) + 6. └─ggplot2:::plot.ggplot(p[[1]]) + 7. ├─ggplot2::ggplot_gtable(data) + 8. └─ggplot2:::ggplot_gtable.ggplot_built(data) + 9. └─ggplot2::calc_element("plot.margin", theme) + 10. └─cli::cli_abort(...) + 11. └─rlang::abort(...) + Execution halted + ``` + * checking running R code from vignettes ... ERROR ``` Errors in running code in vignettes: - when running code in ‘rLFT_Introduction.Rmd’ + when running code in ‘Targeting-Vignette.Rmd’ ... - old-style crs object detected; please recreate object with a recent sf::st_crs() - - When sourcing ‘rLFT_Introduction.R’: - Error: Summary operations are not defined for quosures. Do you need to unquote - the quosure? + + sequenceColumn = "clonal_sequence", germlineColumn = "clonal_germline", + + vCallColu .... [TRUNCATED] + Warning in createMutabilityMatrix(db, sub_mat, model = model, sequenceColumn = sequenceColumn, : + Insufficient number of mutations to infer some 5-mers. Filled with 0. - # Bad: min(myquosure) + > plotMutability(model, nucleotides = "A", style = "hedgehog") - # Good: min(!!myquosure) + When sourcing ‘Targeting-Vignette.R’: + Error: Theme element `plot.margin` must have class . Execution halted - ‘rLFT_Introduction.Rmd’ using ‘UTF-8’... failed + ‘Baseline-Vignette.Rmd’ using ‘UTF-8’... OK + ‘DistToNearest-Vignette.Rmd’ using ‘UTF-8’... OK + ‘Mutation-Vignette.Rmd’ using ‘UTF-8’... OK + ‘Shmulate-Vignette.Rmd’ using ‘UTF-8’... OK + ‘Targeting-Vignette.Rmd’ using ‘UTF-8’... failed ``` * checking re-building of vignette outputs ... NOTE ``` Error(s) in re-building vignettes: ... - --- re-building ‘rLFT_Introduction.Rmd’ using rmarkdown + --- re-building ‘Baseline-Vignette.Rmd’ using rmarkdown + --- finished re-building ‘Baseline-Vignette.Rmd’ - Quitting from lines at lines 56-66 [unnamed-chunk-2] (rLFT_Introduction.Rmd) - Error: processing vignette 'rLFT_Introduction.Rmd' failed with diagnostics: - Summary operations are not defined for quosures. Do you need to unquote - the quosure? + --- re-building ‘DistToNearest-Vignette.Rmd’ using rmarkdown + --- finished re-building ‘DistToNearest-Vignette.Rmd’ - # Bad: min(myquosure) - - # Good: min(!!myquosure) - --- failed re-building ‘rLFT_Introduction.Rmd’ + --- re-building ‘Mutation-Vignette.Rmd’ using rmarkdown + --- finished re-building ‘Mutation-Vignette.Rmd’ + ... + Quitting from lines 167-170 [unnamed-chunk-8] (Targeting-Vignette.Rmd) + Error: processing vignette 'Targeting-Vignette.Rmd' failed with diagnostics: + Theme element `plot.margin` must have class . + --- failed re-building ‘Targeting-Vignette.Rmd’ SUMMARY: processing the following file failed: - ‘rLFT_Introduction.Rmd’ + ‘Targeting-Vignette.Rmd’ Error: Vignette re-building failed. Execution halted ``` -## In both - -* checking installed package size ... NOTE - ``` - installed size is 6.0Mb - sub-directories of 1Mb or more: - help 1.8Mb - libs 4.0Mb - ``` - -# roahd - -
- -* Version: 1.4.3 -* GitHub: https://github.com/astamm/roahd -* Source code: https://github.com/cran/roahd -* Date/Publication: 2021-11-04 00:10:02 UTC -* Number of recursive dependencies: 88 - -Run `revdepcheck::cloud_details(, "roahd")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘roahd-Ex.R’ failed - The error most likely occurred in: - - > ### Name: plot.depthgram - > ### Title: Specialized method to plot 'depthgram' objects - > ### Aliases: plot.depthgram - > - > ### ** Examples - > - > N <- 50 - ... - + centerline = sin(2 * pi * grid), - + Cov = Cov - + ) - > names <- paste0("id_", 1:nrow(Data[[1]])) - > DG <- depthgram(Data, marginal_outliers = TRUE, ids = names) - > plot(DG) - Error in compute_geom_2(..., self = self) : - argument "theme" is missing, with no default - Calls: plot ... use_defaults -> eval_from_theme -> %||% -> calc_element - Execution halted - ``` - -## In both - -* checking installed package size ... NOTE - ``` - installed size is 7.2Mb - sub-directories of 1Mb or more: - data 4.8Mb - doc 1.7Mb - ``` - -# roptions +# simulariatools
-* Version: 1.0.3 -* GitHub: NA -* Source code: https://github.com/cran/roptions -* Date/Publication: 2020-05-11 11:10:06 UTC -* Number of recursive dependencies: 70 +* Version: 2.5.1 +* GitHub: https://github.com/Simularia/simulariatools +* Source code: https://github.com/cran/simulariatools +* Date/Publication: 2023-11-08 14:10:02 UTC +* Number of recursive dependencies: 96 -Run `revdepcheck::cloud_details(, "roptions")` for more info +Run `revdepcheck::cloud_details(, "simulariatools")` for more info
@@ -8619,47 +18481,40 @@ Run `revdepcheck::cloud_details(, "roptions")` for more info * checking examples ... ERROR ``` - Running examples in ‘roptions-Ex.R’ failed + Running examples in ‘simulariatools-Ex.R’ failed The error most likely occurred in: - > ### Name: box.spread - > ### Title: Box Spread Strategy Function - > ### Aliases: box.spread + > ### Name: plotAvgTemp + > ### Title: Plot average temperature + > ### Aliases: plotAvgTemp > > ### ** Examples > - > box.spread(100, 105, 95, 110, 3.2, 2.6, 1.1, 2.4) + > # Plot histogram with monthly averages together with maxima and minima ... - 36 5.7 - 37 5.7 - 38 5.7 - 39 5.7 - 40 5.7 - 41 5.7 - Error in compute_geom_2(..., self = self) : - argument "theme" is missing, with no default - Calls: box.spread ... use_defaults -> eval_from_theme -> %||% -> calc_element + 1. └─simulariatools::plotAvgTemp(stMeteo) + 2. └─simulariatools (local) mmplot(v, data_table) + 3. ├─base::print(b, vp = subplot(2, 1)) + 4. └─ggplot2:::print.ggplot(b, vp = subplot(2, 1)) + 5. ├─ggplot2::ggplot_gtable(data) + 6. └─ggplot2:::ggplot_gtable.ggplot_built(data) + 7. └─ggplot2::calc_element("plot.margin", theme) + 8. └─cli::cli_abort(...) + 9. └─rlang::abort(...) Execution halted ``` -## In both - -* checking LazyData ... NOTE - ``` - 'LazyData' is specified without a 'data' directory - ``` - -# scoringutils +# sjPlot
-* Version: 1.2.2 -* GitHub: https://github.com/epiforecasts/scoringutils -* Source code: https://github.com/cran/scoringutils -* Date/Publication: 2023-11-29 15:50:10 UTC -* Number of recursive dependencies: 81 +* Version: 2.8.16 +* GitHub: https://github.com/strengejacke/sjPlot +* Source code: https://github.com/cran/sjPlot +* Date/Publication: 2024-05-13 17:50:02 UTC +* Number of recursive dependencies: 187 -Run `revdepcheck::cloud_details(, "scoringutils")` for more info +Run `revdepcheck::cloud_details(, "sjPlot")` for more info
@@ -8667,98 +18522,71 @@ Run `revdepcheck::cloud_details(, "scoringutils")` for more info * checking examples ... ERROR ``` - Running examples in ‘scoringutils-Ex.R’ failed + Running examples in ‘sjPlot-Ex.R’ failed The error most likely occurred in: - > ### Name: plot_predictions - > ### Title: Plot Predictions vs True Values - > ### Aliases: plot_predictions + > ### Name: plot_frq + > ### Title: Plot frequencies of variables + > ### Aliases: plot_frq > > ### ** Examples > - > library(ggplot2) + > library(sjlabelled) ... - 2.75, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 1, NULL, NULL, NULL, c(0, 2.2, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, NULL, c(0, 0, 0, 2.2 - ), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0.5, NULL, NULL, NULL, c(0, 2.2, 0, 2.2), NULL, TRUE), list("grey80", NULL, NULL, NULL, FALSE, FALSE), NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 2.75, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 0.75, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, list("grey80", NULL, NULL, NULL, FALSE, FALSE), NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, list(), c(5.5, 5.5, 5.5, 5.5), 11, NULL, NULL, list(), 1.2, - NULL, NULL, 5.5, NULL, NULL, NULL, NULL, 0.2, NULL, list(NULL, NULL, NULL, 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, NULL, NULL, NULL, TRUE), NULL, "bottom", NULL, NULL, NULL, "center", NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, c(0, 0, 0, 0), list(), 11, list(), list(), 5.5, NULL, NULL, list("grey92", NULL, NULL, NULL, FALSE, TRUE), list(), list(), NULL, NULL, NULL, NULL, FALSE, list(), list(NULL, NULL, NULL, 1.2, 0, 1, NULL, NULL, - c(0, 0, 5.5, 0), NULL, TRUE), "panel", list(NULL, NULL, NULL, NULL, 0, 1, NULL, NULL, c(0, 0, 5.5, 0), NULL, TRUE), list(NULL, NULL, NULL, 0.8, 1, 1, NULL, NULL, c(5.5, 0, 0, 0), NULL, TRUE), "panel", list(NULL, NULL, NULL, 1.2, 0.5, 0.5, NULL, NULL, NULL, NULL, TRUE), "topleft", NULL, c(5.5, 5.5, 5.5, 5.5), list(), NULL, NULL, "inherit", "inside", list(NULL, NULL, "grey10", 0.8, NULL, NULL, NULL, NULL, c(4.4, 4.4, 4.4, 4.4), NULL, TRUE), NULL, NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, - NULL, -90, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, NULL, 90, NULL, NULL, NULL, TRUE), NULL, 2.75, 2.75)) - Error in use_defaults(..., self = self) : - unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), NULL, list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.75, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, 90, NULL, c(0, - 2.75, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 1, NULL, NULL, NULL, c(0, 2.2, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL - Calls: ... .handleSimpleError -> h -> -> + 4. └─gridExtra (local) ``(``, ``, ``, ``, nrow = 2, ncol = 2) + 5. └─gridExtra::arrangeGrob(...) + 6. └─base::lapply(grobs[toconv], ggplot2::ggplotGrob) + 7. └─ggplot2 (local) FUN(X[[i]], ...) + 8. ├─ggplot2::ggplot_gtable(ggplot_build(x)) + 9. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) + 10. └─ggplot2::calc_element("plot.margin", theme) + 11. └─cli::cli_abort(...) + 12. └─rlang::abort(...) Execution halted ``` -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘metric-details.Rmd’ using rmarkdown - --- finished re-building ‘metric-details.Rmd’ - - --- re-building ‘scoring-forecasts-directly.Rmd’ using rmarkdown - --- finished re-building ‘scoring-forecasts-directly.Rmd’ - - --- re-building ‘scoringutils.Rmd’ using rmarkdown - ``` - -## In both - * checking running R code from vignettes ... ERROR ``` Errors in running code in vignettes: - when running code in ‘scoringutils.Rmd’ + when running code in ‘custplot.Rmd’ ... - 2.75, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 1, NULL, NULL, NULL, c(0, 2.2, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, NULL, c(0, 0, 0, 2.2 - ), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0.5, NULL, NULL, NULL, c(0, 2.2, 0, 2.2), NULL, TRUE), list("grey80", NULL, NULL, NULL, FALSE, FALSE), NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 2.75, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 0.75, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, list("grey80", NULL, NULL, NULL, FALSE, FALSE), NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, list(), c(5.5, 5.5, 5.5, 5.5), 11, NULL, NULL, list(), 1.2, - NULL, NULL, 5.5, NULL, NULL, NULL, NULL, 0.2, NULL, list(NULL, NULL, NULL, 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, NULL, NULL, NULL, TRUE), NULL, "bottom", NULL, NULL, NULL, "center", NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, c(0, 0, 0, 0), list(), 11, list(), list(), 5.5, NULL, NULL, list("grey92", NULL, NULL, NULL, FALSE, TRUE), list(), list(), NULL, NULL, NULL, NULL, FALSE, list(), list(NULL, NULL, NULL, 1.2, 0, 1, NULL, NULL, - c(0, 0, 5.5, 0), NULL, TRUE), "panel", list(NULL, NULL, NULL, NULL, 0, 1, NULL, NULL, c(0, 0, 5.5, 0), NULL, TRUE), list(NULL, NULL, NULL, 0.8, 1, 1, NULL, NULL, c(5.5, 0, 0, 0), NULL, TRUE), "panel", list(NULL, NULL, NULL, 1.2, 0.5, 0.5, NULL, NULL, NULL, NULL, TRUE), "topleft", NULL, c(5.5, 5.5, 5.5, 5.5), list(), NULL, NULL, "inherit", "inside", list(NULL, NULL, "grey10", 0.8, NULL, NULL, NULL, NULL, c(4.4, 4.4, 4.4, 4.4), NULL, TRUE), NULL, NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, - NULL, -90, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, NULL, 90, NULL, NULL, NULL, TRUE), NULL, 2.75, 2.75)) - When sourcing ‘scoringutils.R’: - Error: unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), NULL, list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.75, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, 90, NULL, c(0, - 2.75, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 1, NULL, NULL, NULL, c(0, 2.2, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, - Execution halted - ‘metric-details.Rmd’ using ‘UTF-8’... OK - ‘scoring-forecasts-directly.Rmd’ using ‘UTF-8’... OK - ‘scoringutils.Rmd’ using ‘UTF-8’... failed + > data(efc) + + > set_theme(geom.outline.color = "antiquewhite4", geom.outline.size = 1, + + geom.label.size = 2, geom.label.color = "grey50", title.color = "red", .... [TRUNCATED] + + ... + ‘plot_interactions.Rmd’ using ‘UTF-8’... OK + ‘plot_likert_scales.Rmd’ using ‘UTF-8’... OK + ‘plot_marginal_effects.Rmd’ using ‘UTF-8’... OK + ‘plot_model_estimates.Rmd’ using ‘UTF-8’... OK + ‘sjtitemanalysis.Rmd’ using ‘UTF-8’... OK + ‘tab_bayes.Rmd’ using ‘UTF-8’... OK + ‘tab_mixed.Rmd’ using ‘UTF-8’... OK + ‘tab_model_estimates.Rmd’ using ‘UTF-8’... OK + ‘tab_model_robust.Rmd’ using ‘UTF-8’... OK + ‘table_css.Rmd’ using ‘UTF-8’... OK ``` -# SCOUTer - -
- -* Version: 1.0.0 -* GitHub: NA -* Source code: https://github.com/cran/SCOUTer -* Date/Publication: 2020-06-30 09:30:03 UTC -* Number of recursive dependencies: 99 - -Run `revdepcheck::cloud_details(, "SCOUTer")` for more info - -
- -## Newly broken - -* checking whether package ‘SCOUTer’ can be installed ... WARNING +* checking re-building of vignette outputs ... NOTE ``` - Found the following significant warnings: - Warning: replacing previous import ‘ggplot2::ggpar’ by ‘ggpubr::ggpar’ when loading ‘SCOUTer’ - See ‘/tmp/workdir/SCOUTer/new/SCOUTer.Rcheck/00install.out’ for details. + Error(s) in re-building vignettes: + --- re-building ‘blackwhitefigures.Rmd’ using rmarkdown ``` -# SCVA +# SleepCycles
-* Version: 1.3.1 +* Version: 1.1.4 * GitHub: NA -* Source code: https://github.com/cran/SCVA -* Date/Publication: 2020-01-09 22:50:10 UTC -* Number of recursive dependencies: 80 +* Source code: https://github.com/cran/SleepCycles +* Date/Publication: 2021-09-27 13:50:10 UTC +* Number of recursive dependencies: 56 -Run `revdepcheck::cloud_details(, "SCVA")` for more info +Run `revdepcheck::cloud_details(, "SleepCycles")` for more info
@@ -8766,35 +18594,40 @@ Run `revdepcheck::cloud_details(, "SCVA")` for more info * checking examples ... ERROR ``` - Running examples in ‘SCVA-Ex.R’ failed + Running examples in ‘SleepCycles-Ex.R’ failed The error most likely occurred in: - > ### Name: graphly - > ### Title: Interactive plot of single-case data - > ### Aliases: graphly - > ### Keywords: Single-case design Graph + > ### Name: SleepCycles + > ### Title: Sleep Cycle Detection + > ### Aliases: SleepCycles > > ### ** Examples > - > data(AB) - > graphly(design = "AB", data = AB) - Error in compute_geom_2(..., self = self) : - argument "theme" is missing, with no default - Calls: graphly ... use_defaults -> eval_from_theme -> %||% -> calc_element + > data(sleepstages) + ... + 4. ├─grid::grid.draw(plot) + 5. └─ggplot2:::grid.draw.ggplot(plot) + 6. ├─base::print(x) + 7. └─ggplot2:::print.ggplot(x) + 8. ├─ggplot2::ggplot_gtable(data) + 9. └─ggplot2:::ggplot_gtable.ggplot_built(data) + 10. └─ggplot2::calc_element("plot.margin", theme) + 11. └─cli::cli_abort(...) + 12. └─rlang::abort(...) Execution halted ``` -# see +# smallsets
-* Version: 0.8.4 -* GitHub: https://github.com/easystats/see -* Source code: https://github.com/cran/see -* Date/Publication: 2024-04-29 04:40:03 UTC -* Number of recursive dependencies: 234 +* Version: 2.0.0 +* GitHub: https://github.com/lydialucchesi/smallsets +* Source code: https://github.com/cran/smallsets +* Date/Publication: 2023-12-05 00:00:02 UTC +* Number of recursive dependencies: 107 -Run `revdepcheck::cloud_details(, "see")` for more info +Run `revdepcheck::cloud_details(, "smallsets")` for more info
@@ -8802,40 +18635,81 @@ Run `revdepcheck::cloud_details(, "see")` for more info * checking examples ... ERROR ``` - Running examples in ‘see-Ex.R’ failed + Running examples in ‘smallsets-Ex.R’ failed The error most likely occurred in: - > ### Name: geom_binomdensity - > ### Title: Add dot-densities for binary 'y' variables - > ### Aliases: geom_binomdensity + > ### Name: Smallset_Timeline + > ### Title: Smallset Timeline + > ### Aliases: Smallset_Timeline > > ### ** Examples > - > ## Don't show: - ... - 14. │ └─ggplot2 (local) f(l = layers[[i]], d = data[[i]]) - 15. │ └─l$compute_geom_2(d, theme = plot$theme) - 16. │ └─ggplot2 (local) compute_geom_2(..., self = self) - 17. │ └─self$geom$use_defaults(data, self$aes_params, modifiers, theme = theme) - 18. └─base::.handleSimpleError(...) - 19. └─rlang (local) h(simpleError(msg, call)) - 20. └─handlers[[1L]](cnd) - 21. └─cli::cli_abort(...) - 22. └─rlang::abort(...) + > set.seed(145) + > + > Smallset_Timeline( + + data = s_data, + + code = system.file("s_data_preprocess.R", package = "smallsets") + + ) + Error in as.unit(value) : object is not coercible to a unit + Calls: ... assemble_guides -> guides_build -> [<- -> [<-.unit -> as.unit + Execution halted + ``` + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘smallsets.Rmd’ + ... + > library(smallsets) + + > set.seed(145) + + > Smallset_Timeline(data = s_data, code = system.file("s_data_preprocess.R", + + package = "smallsets")) + + When sourcing ‘smallsets.R’: + Error: object is not coercible to a unit + Execution halted + + ‘smallsets.Rmd’ using ‘UTF-8’... failed + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + ... + --- re-building ‘smallsets.Rmd’ using rmarkdown + + Quitting from lines 36-42 [timeline1] (smallsets.Rmd) + Error: processing vignette 'smallsets.Rmd' failed with diagnostics: + object is not coercible to a unit + --- failed re-building ‘smallsets.Rmd’ + + SUMMARY: processing the following file failed: + ‘smallsets.Rmd’ + + Error: Vignette re-building failed. Execution halted ``` -# sfnetworks +## In both + +* checking package dependencies ... NOTE + ``` + Package suggested but not available for checking: ‘gurobi’ + ``` + +# smdi
-* Version: 0.6.4 -* GitHub: https://github.com/luukvdmeer/sfnetworks -* Source code: https://github.com/cran/sfnetworks -* Date/Publication: 2024-04-09 22:40:02 UTC -* Number of recursive dependencies: 106 +* Version: 0.2.2 +* GitHub: NA +* Source code: https://github.com/cran/smdi +* Date/Publication: 2023-07-17 14:20:02 UTC +* Number of recursive dependencies: 188 -Run `revdepcheck::cloud_details(, "sfnetworks")` for more info +Run `revdepcheck::cloud_details(, "smdi")` for more info
@@ -8844,7 +18718,7 @@ Run `revdepcheck::cloud_details(, "sfnetworks")` for more info * checking re-building of vignette outputs ... NOTE ``` Error(s) in re-building vignettes: - --- re-building ‘sfn01_structure.Rmd’ using rmarkdown + --- re-building ‘a_data_generation.Rmd’ using rmarkdown ``` ## In both @@ -8852,39 +18726,39 @@ Run `revdepcheck::cloud_details(, "sfnetworks")` for more info * checking running R code from vignettes ... ERROR ``` Errors in running code in vignettes: - when running code in ‘sfn01_structure.Rmd’ + when running code in ‘a_data_generation.Rmd’ ... - > plot(other_net, cex = 2, lwd = 2, main = "Straight lines") - - > st_geometry(edges) = st_sfc(c(l2, l3, l1), crs = 4326) - - > net = sfnetwork(nodes, edges) - Checking if spatial network structure is valid... + > usethis::use_data(smdi_data_complete, overwrite = TRUE) + Warning in path_file(base_path) : + restarting interrupted promise evaluation + When sourcing ‘a_data_generation.R’: + Error: Failed to evaluate glue component {ui_value(project_name())} + Caused by error: ... - Error: ℹ In argument: `azimuth = edge_azimuth()`. - Caused by error in `st_geod_azimuth()`: - ! st_is_longlat(x) is not TRUE + + When sourcing ‘c_multivariate_missingness.R’: + Error: Theme element `plot.margin` must have class . Execution halted - ‘sfn01_structure.Rmd’ using ‘UTF-8’... failed - ‘sfn02_preprocess_clean.Rmd’ using ‘UTF-8’... OK - ‘sfn03_join_filter.Rmd’ using ‘UTF-8’... OK - ‘sfn04_routing.Rmd’ using ‘UTF-8’... OK - ‘sfn05_morphers.Rmd’ using ‘UTF-8’... failed + ‘a_data_generation.Rmd’ using ‘UTF-8’... failed + ‘b_routine_diagnostics.Rmd’ using ‘UTF-8’... failed + ‘c_multivariate_missingness.Rmd’ using ‘UTF-8’... failed + ‘d_narfcs_sensitivity_analysis.Rmd’ using ‘UTF-8’... OK + ‘smdi.Rmd’ using ‘UTF-8’... OK ``` -# sftrack +# soc.ca
-* Version: 0.5.4 -* GitHub: https://github.com/mablab/sftrack -* Source code: https://github.com/cran/sftrack -* Date/Publication: 2023-03-16 12:20:02 UTC -* Number of recursive dependencies: 92 +* Version: 0.8.0 +* GitHub: https://github.com/Rsoc/soc.ca +* Source code: https://github.com/cran/soc.ca +* Date/Publication: 2021-09-02 22:50:02 UTC +* Number of recursive dependencies: 140 -Run `revdepcheck::cloud_details(, "sftrack")` for more info +Run `revdepcheck::cloud_details(, "soc.ca")` for more info
@@ -8892,69 +18766,110 @@ Run `revdepcheck::cloud_details(, "sftrack")` for more info * checking examples ... ERROR ``` - Running examples in ‘sftrack-Ex.R’ failed + Running examples in ‘soc.ca-Ex.R’ failed The error most likely occurred in: - > ### Name: geom_sftrack - > ### Title: Function to plot sftrack objects in ggplot - > ### Aliases: geom_sftrack geom_sftrack.sftrack geom_sftrack.sftraj + > ### Name: add.to.label + > ### Title: Add values to label + > ### Aliases: add.to.label > > ### ** Examples > - > #' + > example(soc.ca) ... - 17. └─ggplot2 (local) FUN(X[[i]], ...) - 18. └─g$draw_key(data, g$params, key_size) - 19. └─ggplot2 (local) draw_key(...) - 20. └─ggplot2::draw_key_path(data, params, size) - 21. ├─grid::segmentsGrob(...) - 22. │ └─grid::grob(...) - 23. └─ggplot2::ggpar(...) - 24. └─rlang:::Ops.quosure(args$lwd, .pt) - 25. └─rlang::abort(...) + Backtrace: + ▆ + 1. ├─base (local) ``(x) + 2. └─ggplot2:::print.ggplot(x) + 3. ├─ggplot2::ggplot_gtable(data) + 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) + 5. └─ggplot2::calc_element("plot.margin", theme) + 6. └─cli::cli_abort(...) + 7. └─rlang::abort(...) Execution halted ``` +## In both + +* checking dependencies in R code ... NOTE + ``` + Namespaces in Imports field not imported from: + ‘FactoMineR’ ‘flextable’ ‘htmlTable’ ‘stringr’ + All declared Imports should be used. + ``` + +* checking data for non-ASCII characters ... NOTE + ``` + Note: found 938 marked UTF-8 strings + ``` + +# spbal + +
+ +* Version: 1.0.0 +* GitHub: NA +* Source code: https://github.com/cran/spbal +* Date/Publication: 2024-05-17 16:00:02 UTC +* Number of recursive dependencies: 77 + +Run `revdepcheck::cloud_details(, "spbal")` for more info + +
+ +## Newly broken + * checking running R code from vignettes ... ERROR ``` Errors in running code in vignettes: - when running code in ‘sftrack5_spatial.Rmd’ + when running code in ‘spbal.Rmd’ ... - > ggplot() + geom_sftrack(data = my_sftraj) - - When sourcing ‘sftrack5_spatial.R’: - Error: Base operators are not defined for quosures. Do you need to unquote the - quosure? - - # Bad: myquosure * rhs + st_point_on_surface may not give correct results for longitude/latitude data + Warning in st_point_on_surface.sfc(sf::st_zm(x)) : + st_point_on_surface may not give correct results for longitude/latitude data - # Good: !!myquosure * rhs + When sourcing ‘spbal.R’: + Error: Problem while setting up geom aesthetics. + ℹ Error occurred in the 1st layer. + Caused by error in `$<-.data.frame`: + ! replacement has 1 row, data has 0 Execution halted - ‘sftrack1_overview.Rmd’ using ‘UTF-8’... OK - ‘sftrack2_reading.Rmd’ using ‘UTF-8’... OK - ‘sftrack3_workingwith.Rmd’ using ‘UTF-8’... OK - ‘sftrack4_groups.Rmd’ using ‘UTF-8’... OK - ‘sftrack5_spatial.Rmd’ using ‘UTF-8’... failed + ‘spbal.Rmd’ using ‘UTF-8’... failed ``` * checking re-building of vignette outputs ... NOTE ``` Error(s) in re-building vignettes: - --- re-building ‘sftrack1_overview.Rmd’ using rmarkdown + ... + --- re-building ‘spbal.Rmd’ using rmarkdown + + Quitting from lines 159-187 [BASex1c] (spbal.Rmd) + Error: processing vignette 'spbal.Rmd' failed with diagnostics: + Problem while setting up geom aesthetics. + ℹ Error occurred in the 1st layer. + Caused by error in `$<-.data.frame`: + ! replacement has 1 row, data has 0 + --- failed re-building ‘spbal.Rmd’ + + SUMMARY: processing the following file failed: + ‘spbal.Rmd’ + + Error: Vignette re-building failed. + Execution halted ``` -# sglg +# speccurvieR
-* Version: 0.2.2 -* GitHub: NA -* Source code: https://github.com/cran/sglg -* Date/Publication: 2022-09-04 03:50:01 UTC -* Number of recursive dependencies: 96 +* Version: 0.3.0 +* GitHub: https://github.com/zaynesember/speccurvieR +* Source code: https://github.com/cran/speccurvieR +* Date/Publication: 2024-01-24 19:40:02 UTC +* Number of recursive dependencies: 46 -Run `revdepcheck::cloud_details(, "sglg")` for more info +Run `revdepcheck::cloud_details(, "speccurvieR")` for more info
@@ -8962,155 +18877,212 @@ Run `revdepcheck::cloud_details(, "sglg")` for more info * checking examples ... ERROR ``` - Running examples in ‘sglg-Ex.R’ failed + Running examples in ‘speccurvieR-Ex.R’ failed The error most likely occurred in: - > ### Name: deviance_residuals - > ### Title: Deviance Residuals for a Generalized Log-gamma Regression Model - > ### Aliases: deviance_residuals + > ### Name: plotCurve + > ### Title: Plots a specification curve. + > ### Aliases: plotCurve > > ### ** Examples > - > # Example 1 - > n <- 300 - > error <- rglg(n,0,1,1) - > y <- 0.5 + error - > fit <- glg(y~1,data=as.data.frame(y)) - > deviance_residuals(fit) - Error in compute_geom_2(..., self = self) : - argument "theme" is missing, with no default - Calls: deviance_residuals ... use_defaults -> eval_from_theme -> %||% -> calc_element + > plotCurve(sca_data = sca(y="Salnty", x="T_degC", c("ChlorA", "O2Sat"), + ... + 1. └─speccurvieR::plotCurve(...) + 2. ├─grid::grid.draw(rbind(ggplotGrob(sc1), ggplotGrob(sc2))) + 3. ├─base::rbind(ggplotGrob(sc1), ggplotGrob(sc2)) + 4. └─ggplot2::ggplotGrob(sc1) + 5. ├─ggplot2::ggplot_gtable(ggplot_build(x)) + 6. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) + 7. └─ggplot2::calc_element("plot.margin", theme) + 8. └─cli::cli_abort(...) + 9. └─rlang::abort(...) Execution halted ``` -# sievePH +## In both + +* checking data for non-ASCII characters ... NOTE + ``` + Note: found 2 marked UTF-8 strings + ``` + +# spinifex
-* Version: 1.0.4 -* GitHub: https://github.com/mjuraska/sievePH -* Source code: https://github.com/cran/sievePH -* Date/Publication: 2023-02-03 18:40:02 UTC -* Number of recursive dependencies: 82 +* Version: 0.3.7.0 +* GitHub: https://github.com/nspyrison/spinifex +* Source code: https://github.com/cran/spinifex +* Date/Publication: 2024-01-29 14:40:02 UTC +* Number of recursive dependencies: 163 -Run `revdepcheck::cloud_details(, "sievePH")` for more info +Run `revdepcheck::cloud_details(, "spinifex")` for more info
## Newly broken -* checking whether package ‘sievePH’ can be installed ... WARNING +* checking tests ... ERROR ``` - Found the following significant warnings: - Warning: replacing previous import ‘ggplot2::ggpar’ by ‘ggpubr::ggpar’ when loading ‘sievePH’ - See ‘/tmp/workdir/sievePH/new/sievePH.Rcheck/00install.out’ for details. + Running ‘spelling.R’ + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(spinifex) + Loading required package: tourr + -------------------------------------------------------- + spinifex --- version 0.3.7.0 + Please share bugs, suggestions, and feature requests at: + ... + 2. │ └─base::withCallingHandlers(...) + 3. └─spinifex::play_tour_path(tour_path = tpath, data = dat_std, angle = 1) + 4. └─spinifex (local) render_type(frames = tour_df, ...) + 5. ├─plotly::ggplotly(p = gg, tooltip = "tooltip") + 6. └─plotly:::ggplotly.ggplot(p = gg, tooltip = "tooltip") + 7. └─plotly::gg2list(...) + + [ FAIL 3 | WARN 0 | SKIP 0 | PASS 80 ] + Error: Test failures + Execution halted ``` -# SouthParkRshiny +# spotoroo
-* Version: 1.0.0 -* GitHub: https://github.com/Amalan-ConStat/SouthParkRshiny -* Source code: https://github.com/cran/SouthParkRshiny -* Date/Publication: 2024-03-09 11:10:08 UTC -* Number of recursive dependencies: 118 +* Version: 0.1.4 +* GitHub: https://github.com/TengMCing/spotoroo +* Source code: https://github.com/cran/spotoroo +* Date/Publication: 2023-08-21 05:50:02 UTC +* Number of recursive dependencies: 107 -Run `revdepcheck::cloud_details(, "SouthParkRshiny")` for more info +Run `revdepcheck::cloud_details(, "spotoroo")` for more info
## Newly broken -* checking whether package ‘SouthParkRshiny’ can be installed ... WARNING +* checking tests ... ERROR ``` - Found the following significant warnings: - Warning: replacing previous import ‘ggplot2::ggpar’ by ‘ggpubr::ggpar’ when loading ‘SouthParkRshiny’ - See ‘/tmp/workdir/SouthParkRshiny/new/SouthParkRshiny.Rcheck/00install.out’ for details. + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(spotoroo) + > + > test_check("spotoroo") + + -------------------------------- SPOTOROO 0.1.4 -------------------------------- + + ... + i Actually got a with text: + Theme element `plot.margin` must have class . + ── Failure ('test-plot_spotoroo.R:64:3'): plot_spotoroo() works ──────────────── + Expected `plot_spotoroo(result, type = "timeline")` to run without any errors. + i Actually got a with text: + Theme element `plot.margin` must have class . + + [ FAIL 2 | WARN 5 | SKIP 0 | PASS 65 ] + Error: Test failures + Execution halted ``` -## In both +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘Clustering-hot-spots.Rmd’ + ... + + ──────────────────────────────────────────────────────────────────────────────── + + > plot_spotoroo(result, type = "def") + + > plot_spotoroo(result, type = "timeline") + + When sourcing ‘Clustering-hot-spots.R’: + Error: Theme element `plot.margin` must have class . + Execution halted + + ‘Clustering-hot-spots.Rmd’ using ‘UTF-8’... failed + ``` -* checking installed package size ... NOTE +* checking re-building of vignette outputs ... NOTE ``` - installed size is 8.6Mb - sub-directories of 1Mb or more: - data 8.0Mb + Error(s) in re-building vignettes: + --- re-building ‘Clustering-hot-spots.Rmd’ using rmarkdown ``` -* checking data for non-ASCII characters ... NOTE +## In both + +* checking dependencies in R code ... NOTE ``` - Note: found 1562 marked UTF-8 strings + Namespace in Imports field not imported from: ‘utils’ + All declared Imports should be used. ``` -# spatialrisk +# SqueakR
-* Version: 0.7.1 -* GitHub: https://github.com/mharinga/spatialrisk -* Source code: https://github.com/cran/spatialrisk -* Date/Publication: 2024-02-21 12:50:02 UTC -* Number of recursive dependencies: 129 +* Version: 1.3.0 +* GitHub: https://github.com/osimon81/SqueakR +* Source code: https://github.com/cran/SqueakR +* Date/Publication: 2022-06-28 09:20:04 UTC +* Number of recursive dependencies: 141 -Run `revdepcheck::cloud_details(, "spatialrisk")` for more info +Run `revdepcheck::cloud_details(, "SqueakR")` for more info
## Newly broken -* checking examples ... ERROR +* checking re-building of vignette outputs ... NOTE ``` - Running examples in ‘spatialrisk-Ex.R’ failed - The error most likely occurred in: + Error(s) in re-building vignettes: + --- re-building ‘SqueakR.Rmd’ using rmarkdown + ``` + +## In both + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘SqueakR.Rmd’ + ... + $ experimenters : NULL + $ experimental_data: list() + + > my_new_data <- add_timepoint_data(data_path = "../inst/extdata/Example_Mouse_Data.xlsx", + + t1 = 5, t2 = 25) + Adding call features Excel file to workspace... - > ### Name: choropleth_ggplot2 - > ### Title: Map object of class sf using ggplot2 - > ### Aliases: choropleth_ggplot2 - > - > ### ** Examples - > - > test <- points_to_polygon(nl_postcode2, insurance, sum(amount, na.rm = TRUE)) - ... - 15. └─ggplot2 (local) FUN(X[[i]], ...) - 16. └─base::lapply(...) - 17. └─ggplot2 (local) FUN(X[[i]], ...) - 18. └─g$draw_key(data, g$params, key_size) - 19. └─ggplot2 (local) draw_key(...) - 20. └─ggplot2::draw_key_polygon(data, params, size) - 21. └─rlang:::Summary.quosure(from_theme(thin), 1.524, na.rm = FALSE) - 22. └─rlang:::abort_quosure_op("Summary", .Generic) - 23. └─rlang::abort(...) + When sourcing ‘SqueakR.R’: + Error: `path` does not exist: ‘../inst/extdata/Example_Mouse_Data.xlsx’ Execution halted + + ‘SqueakR.Rmd’ using ‘UTF-8’... failed ``` -## In both - * checking installed package size ... NOTE ``` - installed size is 11.0Mb + installed size is 8.8Mb sub-directories of 1Mb or more: - data 6.5Mb - help 1.7Mb - libs 2.7Mb - ``` - -* checking data for non-ASCII characters ... NOTE - ``` - Note: found 283 marked UTF-8 strings + doc 8.2Mb ``` -# spatialsample +# stabm
-* Version: 0.5.1 -* GitHub: https://github.com/tidymodels/spatialsample -* Source code: https://github.com/cran/spatialsample -* Date/Publication: 2023-11-08 00:20:02 UTC -* Number of recursive dependencies: 107 +* Version: 1.2.2 +* GitHub: https://github.com/bommert/stabm +* Source code: https://github.com/cran/stabm +* Date/Publication: 2023-04-04 13:20:02 UTC +* Number of recursive dependencies: 71 -Run `revdepcheck::cloud_details(, "spatialsample")` for more info +Run `revdepcheck::cloud_details(, "stabm")` for more info
@@ -9118,26 +19090,26 @@ Run `revdepcheck::cloud_details(, "spatialsample")` for more info * checking examples ... ERROR ``` - Running examples in ‘spatialsample-Ex.R’ failed + Running examples in ‘stabm-Ex.R’ failed The error most likely occurred in: - > ### Name: autoplot.spatial_rset - > ### Title: Create a ggplot for spatial resamples. - > ### Aliases: autoplot.spatial_rset autoplot.spatial_block_cv + > ### Name: plotFeatures + > ### Title: Plot Selected Features + > ### Aliases: plotFeatures > > ### ** Examples > - > + > feats = list(1:3, 1:4, 1:5) ... - 15. └─ggplot2 (local) FUN(X[[i]], ...) - 16. └─base::lapply(...) - 17. └─ggplot2 (local) FUN(X[[i]], ...) - 18. └─g$draw_key(data, g$params, key_size) - 19. └─ggplot2 (local) draw_key(...) - 20. └─ggplot2::draw_key_polygon(data, params, size) - 21. └─rlang:::Summary.quosure(from_theme(thin), 1.524, na.rm = FALSE) - 22. └─rlang:::abort_quosure_op("Summary", .Generic) - 23. └─rlang::abort(...) + 5. └─cowplot:::as_gtable.default(plot) + 6. ├─cowplot::as_grob(plot) + 7. └─cowplot:::as_grob.ggplot(plot) + 8. └─ggplot2::ggplotGrob(plot) + 9. ├─ggplot2::ggplot_gtable(ggplot_build(x)) + 10. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) + 11. └─ggplot2::calc_element("plot.margin", theme) + 12. └─cli::cli_abort(...) + 13. └─rlang::abort(...) Execution halted ``` @@ -9147,21 +19119,21 @@ Run `revdepcheck::cloud_details(, "spatialsample")` for more info Running the tests in ‘tests/testthat.R’ failed. Complete output: > library(testthat) - > library(spatialsample) + > library(stabm) > - > sf::sf_extSoftVersion() - GEOS GDAL proj.4 GDAL_with_GEOS USE_PROJ_H - "3.8.0" "3.0.4" "6.3.1" "true" "true" - PROJ - ... - • autoplot/buffered-rset-plot.svg - • autoplot/buffered-vfold-plot.svg - • autoplot/buffered-vfold-split.svg - • autoplot/cluster-split-plots.svg - • autoplot/repeated-block-cv.svg - • autoplot/repeated-llo.svg - • autoplot/repeated-vfold.svg - • autoplot/snake-flips-rows-the-right-way.svg + > test_check("stabm") + [ FAIL 10 | WARN 3 | SKIP 0 | PASS 290 ] + + ══ Failed tests ════════════════════════════════════════════════════════════════ + ... + 10. └─ggplot2::ggplotGrob(plot) + 11. ├─ggplot2::ggplot_gtable(ggplot_build(x)) + 12. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) + 13. └─ggplot2::calc_element("plot.margin", theme) + 14. └─cli::cli_abort(...) + 15. └─rlang::abort(...) + + [ FAIL 10 | WARN 3 | SKIP 0 | PASS 290 ] Error: Test failures Execution halted ``` @@ -9169,345 +19141,463 @@ Run `revdepcheck::cloud_details(, "spatialsample")` for more info * checking running R code from vignettes ... ERROR ``` Errors in running code in vignettes: - when running code in ‘spatialsample.Rmd’ + when running code in ‘stabm.Rmd’ ... - > autoplot(cluster_folds) - - When sourcing ‘spatialsample.R’: - Error: Base operators are not defined for quosures. Do you need to unquote the - quosure? + [1] 0.4353893 - # Bad: myquosure * rhs + > plotFeatures(feats) + Loading required namespace: ggplot2 + Loading required namespace: cowplot + Loading required namespace: ggdendro - # Good: !!myquosure * rhs + When sourcing ‘stabm.R’: + Error: Theme element `plot.margin` must have class . Execution halted - ‘spatialsample.Rmd’ using ‘UTF-8’... failed + ‘stabm.Rmd’ using ‘UTF-8’... failed ``` * checking re-building of vignette outputs ... NOTE ``` Error(s) in re-building vignettes: ... - --- re-building ‘spatialsample.Rmd’ using rmarkdown - - Quitting from lines at lines 56-62 [unnamed-chunk-6] (spatialsample.Rmd) - Error: processing vignette 'spatialsample.Rmd' failed with diagnostics: - Base operators are not defined for quosures. Do you need to unquote the - quosure? + --- re-building ‘stabm.Rmd’ using rmarkdown - # Bad: myquosure * rhs - - # Good: !!myquosure * rhs - --- failed re-building ‘spatialsample.Rmd’ + Quitting from lines 65-66 [unnamed-chunk-5] (stabm.Rmd) + Error: processing vignette 'stabm.Rmd' failed with diagnostics: + Theme element `plot.margin` must have class . + --- failed re-building ‘stabm.Rmd’ SUMMARY: processing the following file failed: - ‘spatialsample.Rmd’ + ‘stabm.Rmd’ Error: Vignette re-building failed. Execution halted ``` -# spinifex +# starvz
-* Version: 0.3.7.0 -* GitHub: https://github.com/nspyrison/spinifex -* Source code: https://github.com/cran/spinifex -* Date/Publication: 2024-01-29 14:40:02 UTC -* Number of recursive dependencies: 164 +* Version: 0.8.0 +* GitHub: https://github.com/schnorr/starvz +* Source code: https://github.com/cran/starvz +* Date/Publication: 2024-02-23 23:50:02 UTC +* Number of recursive dependencies: 96 -Run `revdepcheck::cloud_details(, "spinifex")` for more info +Run `revdepcheck::cloud_details(, "starvz")` for more info
## Newly broken -* checking tests ... ERROR +* checking examples ... ERROR ``` - Running ‘spelling.R’ - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(spinifex) - Loading required package: tourr - -------------------------------------------------------- - spinifex --- version 0.3.7.0 - Please share bugs, suggestions, and feature requests at: + Running examples in ‘starvz-Ex.R’ failed + The error most likely occurred in: + + > ### Name: panel_gpubandwidth + > ### Title: Create a line chart panel with GPU bandwidth + > ### Aliases: panel_gpubandwidth + > + > ### ** Examples + > + > panel_gpubandwidth(data = starvz_sample_lu) ... - 12. └─ggplot2 (local) compute_geom_2(..., self = self) - 13. └─self$geom$use_defaults(data, self$aes_params, modifiers, theme = theme) - 14. └─ggplot2 (local) use_defaults(..., self = self) - 15. └─ggplot2:::eval_from_theme(default_aes, theme) - 16. ├─calc_element("geom", theme) %||% .default_geom_element - 17. └─ggplot2::calc_element("geom", theme) - - [ FAIL 3 | WARN 4 | SKIP 0 | PASS 78 ] - Error: Test failures - Execution halted + Backtrace: + ▆ + 1. ├─base (local) ``(x) + 2. └─ggplot2:::print.ggplot(x) + 3. ├─ggplot2::ggplot_gtable(data) + 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) + 5. └─ggplot2::calc_element("plot.margin", theme) + 6. └─cli::cli_abort(...) + 7. └─rlang::abort(...) + Execution halted ``` -# spmodel +# statgenMPP
-* Version: 0.6.0 -* GitHub: https://github.com/USEPA/spmodel -* Source code: https://github.com/cran/spmodel -* Date/Publication: 2024-04-16 23:40:02 UTC +* Version: 1.0.2 +* GitHub: NA +* Source code: https://github.com/cran/statgenMPP +* Date/Publication: 2022-12-02 22:00:02 UTC * Number of recursive dependencies: 78 -Run `revdepcheck::cloud_details(, "spmodel")` for more info +Run `revdepcheck::cloud_details(, "statgenMPP")` for more info
## Newly broken +* checking tests ... ERROR + ``` + Running ‘tinytest.R’ + Running the tests in ‘tests/tinytest.R’ failed. + Complete output: + > + > if ( requireNamespace("tinytest", quietly=TRUE) ){ + + tinytest::test_package("statgenMPP") + + } + Loading required package: statgenGWAS + + test_calcIBDmpp.R............. 0 tests + ... + 7. ├─base::plot(ABC_MQM, plotType = "QTLProfileExt") + 8. └─statgenMPP:::plot.QTLMPP(ABC_MQM, plotType = "QTLProfileExt") + 9. └─ggplot2::ggplotGrob(p1) + 10. ├─ggplot2::ggplot_gtable(ggplot_build(x)) + 11. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) + 12. └─ggplot2::calc_element("plot.margin", theme) + 13. └─cli::cli_abort(...) + 14. └─rlang::abort(...) + There were 50 or more warnings (use warnings() to see the first 50) + Execution halted + ``` + * checking running R code from vignettes ... ERROR ``` Errors in running code in vignettes: - when running code in ‘introduction.Rmd’ + when running code in ‘QTLMapping_in_MultiParentPopulations.Rmd’ ... - 8 186.3500 L 0 0 POINT (279050.9 1517324) - 9 362.3125 L 0 0 POINT (346145.9 1512479) - 10 430.5000 L 0 0 POINT (321354.6 1509966) - > ggplot(moose, aes(color = presence)) + scale_color_viridis_d(option = "H") + - + geom_sf(size = 2) + > plot(ABCMQM, plotType = "QTLProfile") - When sourcing ‘introduction.R’: - Error: 'language' object cannot be coerced to type 'integer' + > plot(ABCMQM, plotType = "parEffs") + + > plot(ABCMQM, plotType = "QTLProfileExt") + + When sourcing ‘QTLMapping_in_MultiParentPopulations.R’: + Error: Theme element `plot.margin` must have class . Execution halted - ‘introduction.Rmd’ using ‘UTF-8’... failed + ‘QTLMapping_in_MultiParentPopulations.Rmd’ using ‘UTF-8’... failed ``` * checking re-building of vignette outputs ... NOTE ``` Error(s) in re-building vignettes: - --- re-building ‘introduction.Rmd’ using rmarkdown - ``` - -## In both - -* checking installed package size ... NOTE - ``` - installed size is 5.8Mb - sub-directories of 1Mb or more: - R 1.9Mb - data 1.7Mb - doc 1.5Mb + --- re-building ‘QTLMapping_in_MultiParentPopulations.Rmd’ using rmarkdown ``` -# SqueakR +# statVisual
-* Version: 1.3.0 -* GitHub: https://github.com/osimon81/SqueakR -* Source code: https://github.com/cran/SqueakR -* Date/Publication: 2022-06-28 09:20:04 UTC -* Number of recursive dependencies: 142 +* Version: 1.2.1 +* GitHub: NA +* Source code: https://github.com/cran/statVisual +* Date/Publication: 2020-02-20 19:30:02 UTC +* Number of recursive dependencies: 193 -Run `revdepcheck::cloud_details(, "SqueakR")` for more info +Run `revdepcheck::cloud_details(, "statVisual")` for more info
## Newly broken -* checking whether package ‘SqueakR’ can be installed ... WARNING - ``` - Found the following significant warnings: - Warning: replacing previous import ‘ggplot2::ggpar’ by ‘ggpubr::ggpar’ when loading ‘SqueakR’ - See ‘/tmp/workdir/SqueakR/new/SqueakR.Rcheck/00install.out’ for details. - ``` - -* checking re-building of vignette outputs ... NOTE +* checking examples ... ERROR ``` - Error(s) in re-building vignettes: - --- re-building ‘SqueakR.Rmd’ using rmarkdown + Running examples in ‘statVisual-Ex.R’ failed + The error most likely occurred in: + + > ### Name: PCA_score + > ### Title: Scatter Plot of 2 Specified Principal Components + > ### Aliases: PCA_score + > ### Keywords: method + > + > ### ** Examples + > + ... + 11. │ └─base::withCallingHandlers(...) + 12. └─ggplot2 (local) f(l = layers[[i]], d = data[[i]]) + 13. └─l$compute_geom_2(d, theme = plot$theme) + 14. └─ggplot2 (local) compute_geom_2(..., self = self) + 15. └─self$geom$use_defaults(...) + 16. └─ggplot2 (local) use_defaults(..., self = self) + 17. └─ggplot2:::check_aesthetics(new_params, nrow(data)) + 18. └─cli::cli_abort(...) + 19. └─rlang::abort(...) + Execution halted ``` -## In both - * checking running R code from vignettes ... ERROR ``` Errors in running code in vignettes: - when running code in ‘SqueakR.Rmd’ + when running code in ‘statVisual.Rmd’ ... - $ experimenters : NULL - $ experimental_data: list() - > my_new_data <- add_timepoint_data(data_path = "../inst/extdata/Example_Mouse_Data.xlsx", - + t1 = 5, t2 = 25) - Adding call features Excel file to workspace... + > factoextra::fviz_eig(pca.obj, addlabels = TRUE) - When sourcing ‘SqueakR.R’: - Error: `path` does not exist: ‘../inst/extdata/Example_Mouse_Data.xlsx’ + When sourcing ‘statVisual.R’: + Error: Problem while setting up geom aesthetics. + ℹ Error occurred in the 1st layer. + Caused by error in `check_aesthetics()`: + ! Aesthetics must be either length 1 or the same as the data (6). + ✖ Fix the following mappings: `width`. Execution halted - ‘SqueakR.Rmd’ using ‘UTF-8’... failed + ‘statVisual.Rmd’ using ‘UTF-8’... failed ``` -* checking installed package size ... NOTE +* checking re-building of vignette outputs ... NOTE ``` - installed size is 8.8Mb - sub-directories of 1Mb or more: - doc 8.2Mb + Error(s) in re-building vignettes: + --- re-building ‘statVisual.Rmd’ using rmarkdown + ``` + +## In both + +* checking dependencies in R code ... NOTE + ``` + Namespaces in Imports field not imported from: + ‘gbm’ ‘ggfortify’ ‘tibble’ ‘tidyverse’ + All declared Imports should be used. ``` -# stats19 +# superheat
-* Version: 3.0.3 -* GitHub: https://github.com/ropensci/stats19 -* Source code: https://github.com/cran/stats19 -* Date/Publication: 2024-02-09 00:30:07 UTC -* Number of recursive dependencies: 161 +* Version: 0.1.0 +* GitHub: NA +* Source code: https://github.com/cran/superheat +* Date/Publication: 2017-02-04 23:35:29 +* Number of recursive dependencies: 69 -Run `revdepcheck::cloud_details(, "stats19")` for more info +Run `revdepcheck::cloud_details(, "superheat")` for more info
## Newly broken -* checking re-building of vignette outputs ... NOTE +* checking examples ... ERROR ``` - Error(s) in re-building vignettes: - --- re-building ‘blog.Rmd’ using rmarkdown - [WARNING] Citeproc: citation sarkar_street_2018 not found - --- finished re-building ‘blog.Rmd’ - - --- re-building ‘stats19-training-setup.Rmd’ using rmarkdown - --- finished re-building ‘stats19-training-setup.Rmd’ + Running examples in ‘superheat-Ex.R’ failed + The error most likely occurred in: - --- re-building ‘stats19-training.Rmd’ using rmarkdown + > ### Name: superheat + > ### Title: Generate supervised heatmaps. + > ### Aliases: superheat + > + > ### ** Examples + > + > # plot a heatmap of the numerical iris variables + ... + 6. ├─gtable::gtable_filter(...) + 7. │ └─base::grepl(pattern, .subset2(x$layout, "name"), fixed = fixed) + 8. │ └─base::is.factor(x) + 9. └─ggplot2::ggplotGrob(gg.right) + 10. ├─ggplot2::ggplot_gtable(ggplot_build(x)) + 11. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) + 12. └─ggplot2::calc_element("plot.margin", theme) + 13. └─cli::cli_abort(...) + 14. └─rlang::abort(...) + Execution halted + ``` + +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(superheat) + > + > test_check("superheat") + [ FAIL 58 | WARN 256 | SKIP 0 | PASS 0 ] + + ══ Failed tests ════════════════════════════════════════════════════════════════ + ... + 9. └─ggplot2::ggplotGrob(gg.top) + 10. ├─ggplot2::ggplot_gtable(ggplot_build(x)) + 11. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) + 12. └─ggplot2::calc_element("plot.margin", theme) + 13. └─cli::cli_abort(...) + 14. └─rlang::abort(...) + + [ FAIL 58 | WARN 256 | SKIP 0 | PASS 0 ] + Error: Test failures + Execution halted ``` ## In both -* checking running R code from vignettes ... ERROR +* checking LazyData ... NOTE ``` - Errors in running code in vignettes: - when running code in ‘blog.Rmd’ - ... - Try running dl_stats19(), change arguments or try later.FALSE - Reading in: - - - When sourcing ‘blog.R’: - Error: `file` is not one of the supported inputs: - • A filepath or character vector of filepaths - ... - - When sourcing ‘stats19.R’: - Error: Unknown colour name: ~ - Execution halted - - ‘blog.Rmd’ using ‘UTF-8’... failed - ‘stats19-training-setup.Rmd’ using ‘UTF-8’... OK - ‘stats19-training.Rmd’ using ‘UTF-8’... failed - ‘stats19-vehicles.Rmd’ using ‘UTF-8’... failed - ‘stats19.Rmd’ using ‘UTF-8’... failed + 'LazyData' is specified without a 'data' directory ``` -# streamDepletr +# surveyexplorer
-* Version: 0.2.0 -* GitHub: https://github.com/FoundrySpatial/streamDepletr -* Source code: https://github.com/cran/streamDepletr -* Date/Publication: 2023-07-19 21:30:02 UTC -* Number of recursive dependencies: 70 +* Version: 0.1.0 +* GitHub: NA +* Source code: https://github.com/cran/surveyexplorer +* Date/Publication: 2023-12-21 16:40:02 UTC +* Number of recursive dependencies: 87 -Run `revdepcheck::cloud_details(, "streamDepletr")` for more info +Run `revdepcheck::cloud_details(, "surveyexplorer")` for more info
## Newly broken -* checking running R code from vignettes ... ERROR +* checking examples ... ERROR ``` - Errors in running code in vignettes: - when running code in ‘intro-to-streamDepletr.Rmd’ - ... - + .... [TRUNCATED] - - When sourcing ‘intro-to-streamDepletr.R’: - Error: Base operators are not defined for quosures. Do you need to unquote the - quosure? - - # Bad: myquosure * rhs + Running examples in ‘surveyexplorer-Ex.R’ failed + The error most likely occurred in: - # Good: !!myquosure * rhs + > ### Name: multi_freq + > ### Title: Generate an UpSet plot for multiple-choice questions + > ### Aliases: multi_freq + > + > ### ** Examples + > + > + ... + 9. └─ggplot2:::scale_apply(layer_data, x_vars, "map", SCALE_X, self$panel_scales_x) + 10. └─base::lapply(...) + 11. └─ggplot2 (local) FUN(X[[i]], ...) + 12. └─base::lapply(...) + 13. └─ggplot2 (local) FUN(X[[i]], ...) + 14. └─scales[[i]][[method]](data[[var]][scale_index[[i]]]) + 15. └─ggplot2 (local) map(..., self = self) + 16. └─cli::cli_abort(...) + 17. └─rlang::abort(...) Execution halted - - ‘intro-to-streamDepletr.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘intro-to-streamDepletr.Rmd’ using rmarkdown ``` -# survminer +# survivalAnalysis
-* Version: 0.4.9 -* GitHub: https://github.com/kassambara/survminer -* Source code: https://github.com/cran/survminer -* Date/Publication: 2021-03-09 09:50:03 UTC -* Number of recursive dependencies: 130 +* Version: 0.3.0 +* GitHub: NA +* Source code: https://github.com/cran/survivalAnalysis +* Date/Publication: 2022-02-11 14:00:02 UTC +* Number of recursive dependencies: 159 -Run `revdepcheck::cloud_details(, "survminer")` for more info +Run `revdepcheck::cloud_details(, "survivalAnalysis")` for more info
## Newly broken -* checking whether package ‘survminer’ can be installed ... WARNING +* checking examples ... ERROR ``` - Found the following significant warnings: - Warning: replacing previous import ‘ggplot2::ggpar’ by ‘ggpubr::ggpar’ when loading ‘survminer’ - See ‘/tmp/workdir/survminer/new/survminer.Rcheck/00install.out’ for details. + Running examples in ‘survivalAnalysis-Ex.R’ failed + The error most likely occurred in: + + > ### Name: forest_plot + > ### Title: Forest plots for survival analysis. + > ### Aliases: forest_plot forest_plot.df + > + > ### ** Examples + > + > library(magrittr) + ... + 10. └─cowplot:::as_gtable.default(x) + 11. ├─cowplot::as_grob(plot) + 12. └─cowplot:::as_grob.ggplot(plot) + 13. └─ggplot2::ggplotGrob(plot) + 14. ├─ggplot2::ggplot_gtable(ggplot_build(x)) + 15. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) + 16. └─ggplot2::calc_element("plot.margin", theme) + 17. └─cli::cli_abort(...) + 18. └─rlang::abort(...) + Execution halted + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘multivariate.Rmd’ using rmarkdown + + Quitting from lines 88-89 [unnamed-chunk-6] (multivariate.Rmd) + Error: processing vignette 'multivariate.Rmd' failed with diagnostics: + Theme element `plot.margin` must have class . + --- failed re-building ‘multivariate.Rmd’ + + --- re-building ‘univariate.Rmd’ using rmarkdown ``` ## In both -* checking installed package size ... NOTE +* checking running R code from vignettes ... ERROR ``` - installed size is 6.3Mb - sub-directories of 1Mb or more: - doc 5.5Mb + Errors in running code in vignettes: + when running code in ‘multivariate.Rmd’ + ... + Warning in strwidth(., family = ggtheme$text$family, units = "in") : + conversion failure on '(0.98–1.00)' in 'mbcsToSbcs': dot substituted for + Warning in strwidth(., family = ggtheme$text$family, units = "in") : + conversion failure on '(0.98–1.00)' in 'mbcsToSbcs': dot substituted for <80> + Warning in strwidth(., family = ggtheme$text$family, units = "in") : + conversion failure on '(0.98–1.00)' in 'mbcsToSbcs': dot substituted for <93> + + ... + font family 'Arial' not found in PostScript font database + Warning in grid.Call.graphics(C_text, as.graphicsAnnot(x$label), x$x, x$y, : + font family 'Arial' not found in PostScript font database + + When sourcing ‘univariate.R’: + Error: invalid font type + Execution halted + + ‘multivariate.Rmd’ using ‘UTF-8’... failed + ‘univariate.Rmd’ using ‘UTF-8’... failed ``` -# symptomcheckR +# Sysrecon
* Version: 0.1.3 -* GitHub: https://github.com/ma-kopka/symptomcheckR -* Source code: https://github.com/cran/symptomcheckR -* Date/Publication: 2024-04-16 20:40:06 UTC -* Number of recursive dependencies: 101 +* GitHub: NA +* Source code: https://github.com/cran/Sysrecon +* Date/Publication: 2023-02-20 08:50:02 UTC +* Number of recursive dependencies: 61 -Run `revdepcheck::cloud_details(, "symptomcheckR")` for more info +Run `revdepcheck::cloud_details(, "Sysrecon")` for more info
## Newly broken -* checking whether package ‘symptomcheckR’ can be installed ... WARNING +* checking examples ... ERROR ``` - Found the following significant warnings: - Warning: replacing previous import ‘ggplot2::ggpar’ by ‘ggpubr::ggpar’ when loading ‘symptomcheckR’ - See ‘/tmp/workdir/symptomcheckR/new/symptomcheckR.Rcheck/00install.out’ for details. + Running examples in ‘Sysrecon-Ex.R’ failed + The error most likely occurred in: + + > ### Name: Sysrecon + > ### Title: Sysrecon + > ### Aliases: Sysrecon + > + > ### ** Examples + > + > + ... + no non-missing arguments to min; returning Inf + Warning in min(freq[grepl(i, allwords, ignore.case = T)]) : + no non-missing arguments to min; returning Inf + Warning in min(freq[grepl(i, allwords, ignore.case = T)]) : + no non-missing arguments to min; returning Inf + Warning in min(freq[grepl(i, allwords, ignore.case = T)]) : + no non-missing arguments to min; returning Inf + Error in as.unit(value) : object is not coercible to a unit + Calls: Sysrecon ... assemble_guides -> guides_build -> [<- -> [<-.unit -> as.unit + Execution halted + ``` + +## In both + +* checking data for non-ASCII characters ... NOTE + ``` + Note: found 38 marked UTF-8 strings ``` # tabledown @@ -9518,7 +19608,7 @@ Run `revdepcheck::cloud_details(, "symptomcheckR")` for more info * GitHub: https://github.com/masiraji/tabledown * Source code: https://github.com/cran/tabledown * Date/Publication: 2024-05-02 13:40:03 UTC -* Number of recursive dependencies: 145 +* Number of recursive dependencies: 144 Run `revdepcheck::cloud_details(, "tabledown")` for more info @@ -9539,15 +19629,15 @@ Run `revdepcheck::cloud_details(, "tabledown")` for more info > ### ** Examples > ... + Iteration: 17, Log-Lik: -5351.363, Max-Change: 0.00011 Iteration: 18, Log-Lik: -5351.363, Max-Change: 0.00054 Iteration: 19, Log-Lik: -5351.363, Max-Change: 0.00012 Iteration: 20, Log-Lik: -5351.363, Max-Change: 0.00035 Iteration: 21, Log-Lik: -5351.363, Max-Change: 0.00010 > > plot <- ggreliability_plotly(data, model) - Error in compute_geom_2(..., self = self) : - argument "theme" is missing, with no default - Calls: ggreliability_plotly ... use_defaults -> eval_from_theme -> %||% -> calc_element + Error in pm[[2]] : subscript out of bounds + Calls: ggreliability_plotly -> -> ggplotly.ggplot -> gg2list Execution halted ``` @@ -9558,37 +19648,90 @@ Run `revdepcheck::cloud_details(, "tabledown")` for more info Note: found 551 marked UTF-8 strings ``` -# tcgaViz +# tabr
-* Version: 1.0.2 -* GitHub: NA -* Source code: https://github.com/cran/tcgaViz -* Date/Publication: 2023-04-04 15:40:02 UTC -* Number of recursive dependencies: 139 +* Version: 0.4.9 +* GitHub: https://github.com/leonawicz/tabr +* Source code: https://github.com/cran/tabr +* Date/Publication: 2023-09-21 16:50:02 UTC +* Number of recursive dependencies: 80 -Run `revdepcheck::cloud_details(, "tcgaViz")` for more info +Run `revdepcheck::cloud_details(, "tabr")` for more info
## Newly broken -* checking whether package ‘tcgaViz’ can be installed ... WARNING +* checking examples ... ERROR ``` - Found the following significant warnings: - Warning: replacing previous import ‘ggplot2::ggpar’ by ‘ggpubr::ggpar’ when loading ‘tcgaViz’ - See ‘/tmp/workdir/tcgaViz/new/tcgaViz.Rcheck/00install.out’ for details. + Running examples in ‘tabr-Ex.R’ failed + The error most likely occurred in: + + > ### Name: plot_fretboard + > ### Title: Chord and fretboard diagram plots + > ### Aliases: plot_fretboard plot_chord + > + > ### ** Examples + > + > # General patterns: scale shifting exercise + ... + Backtrace: + ▆ + 1. ├─base (local) ``(x) + 2. └─ggplot2:::print.ggplot(x) + 3. ├─ggplot2::ggplot_gtable(data) + 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) + 5. └─ggplot2::calc_element("plot.margin", theme) + 6. └─cli::cli_abort(...) + 7. └─rlang::abort(...) + Execution halted + ``` + +# TcGSA + +
+ +* Version: 0.12.10 +* GitHub: https://github.com/sistm/TcGSA +* Source code: https://github.com/cran/TcGSA +* Date/Publication: 2022-02-28 21:40:02 UTC +* Number of recursive dependencies: 122 + +Run `revdepcheck::cloud_details(, "TcGSA")` for more info + +
+ +## Newly broken + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘TcGSA_userguide.Rmd’ + ... + Optimally clustering... + + DONE + + Scale for y is already present. + Adding another scale for y, which will replace the existing scale. + + When sourcing ‘TcGSA_userguide.R’: + Error: Theme element `plot.margin` must have class . + Execution halted + + ‘TcGSA_userguide.Rmd’ using ‘UTF-8’... failed ``` # TCIU
-* Version: 1.2.5 +* Version: 1.2.6 * GitHub: https://github.com/SOCR/TCIU * Source code: https://github.com/cran/TCIU -* Date/Publication: 2024-03-08 17:00:05 UTC +* Date/Publication: 2024-05-17 23:40:21 UTC * Number of recursive dependencies: 172 Run `revdepcheck::cloud_details(, "TCIU")` for more info @@ -9610,9 +19753,8 @@ Run `revdepcheck::cloud_details(, "TCIU")` for more info > > fmri_generate = fmri_simulate_func(dim_data = c(64, 64, 40), mask = mask) > fmri_image(fmri_generate$fmri_data, option='manually', voxel_location = c(40,22,33), time = 4) - Error in compute_geom_2(..., self = self) : - argument "theme" is missing, with no default - Calls: fmri_image ... use_defaults -> eval_from_theme -> %||% -> calc_element + Error in pm[[2]] : subscript out of bounds + Calls: fmri_image ... add_trace -> add_data -> ggplotly -> ggplotly.ggplot -> gg2list Execution halted ``` @@ -9621,20 +19763,20 @@ Run `revdepcheck::cloud_details(, "TCIU")` for more info Errors in running code in vignettes: when running code in ‘tciu-LT-kimesurface.Rmd’ ... + > require(ggplot2) + + > sample_save[[1]] > sample_save[[2]] When sourcing ‘tciu-LT-kimesurface.R’: - Error: Problem while setting up geom aesthetics. - ℹ Error occurred in the 1st layer. - Caused by error in `compute_geom_2()`: ... > fmri_image(fmri_generate$fmri_data, option = "manually", + voxel_location = c(40, 22, 33), time = 4) When sourcing ‘tciu-fMRI-analytics.R’: - Error: argument "theme" is missing, with no default + Error: subscript out of bounds Execution halted ‘tciu-LT-kimesurface.Rmd’ using ‘UTF-8’... failed @@ -9644,19 +19786,19 @@ Run `revdepcheck::cloud_details(, "TCIU")` for more info * checking re-building of vignette outputs ... NOTE ``` Error(s) in re-building vignettes: + ... --- re-building ‘tciu-LT-kimesurface.Rmd’ using rmarkdown - Quitting from lines at lines 159-160 [unnamed-chunk-5] (tciu-LT-kimesurface.Rmd) + Quitting from lines 159-160 [unnamed-chunk-5] (tciu-LT-kimesurface.Rmd) Error: processing vignette 'tciu-LT-kimesurface.Rmd' failed with diagnostics: - Problem while setting up geom aesthetics. - ℹ Error occurred in the 1st layer. - Caused by error in `compute_geom_2()`: - ! unused argument (theme = list(list("black", 0.727272727272727, 1, "butt", FALSE, TRUE), list("white", "black", 0.727272727272727, 1, TRUE), list("", "plain", "black", 16, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), NULL, NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(4, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 4, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, 90, NULL, c(0, 4, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, + unused arguments (list(1, 2), list(list("black", 0.727272727272727, 1, "butt", FALSE, TRUE), list("white", "black", 0.727272727272727, 1, TRUE), list("", "plain", "black", 16, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), NULL, NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(4, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 4, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, 90, NULL, c(0, 4, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 4), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(3.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 3.2, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 1, NULL, NULL, NULL, c(0, 3.2, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, NULL, c(0, 0, 0, 3.2), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0.5, NULL, + NULL, NULL, c(0, 3.2, 0, 3.2), NULL, TRUE), list("grey20", NULL, NULL, NULL, FALSE, TRUE), NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 4, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 0.75, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, list(), NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, list(NULL, NA, NULL, NULL, TRUE), c(8, 8, 8, 8), 16, NULL, NULL, NULL, 1.2, NULL, NULL, 8, NULL, NULL, NULL, NULL, 0.2, NULL, list(NULL, NULL, NULL, 0.8, NULL, NULL, + NULL, NULL, NULL, NULL, TRUE), NULL, list(NULL, "bold", "black", 14, 0, NULL, NULL, NULL, NULL, NULL, FALSE), NULL, "right", NULL, NULL, NULL, "center", NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, c(0, 0, 0, 0), list(), 16, list("grey92", NA, NULL, NULL, TRUE), list(), 8, NULL, NULL, list("white", NULL, NULL, NULL, FALSE, TRUE), NULL, list(NULL, 0.5, NULL, NULL, FALSE, TRUE), NULL, list(), NULL, list(), FALSE, list(NULL, "white", NULL, NULL, TRUE), list(NULL, NULL, NULL, 1.2, 0.5, 1, NULL, ... - Quitting from lines at lines 184-185 [unnamed-chunk-5] (tciu-fMRI-analytics.Rmd) + Quitting from lines 184-185 [unnamed-chunk-5] (tciu-fMRI-analytics.Rmd) Error: processing vignette 'tciu-fMRI-analytics.Rmd' failed with diagnostics: - argument "theme" is missing, with no default + subscript out of bounds --- failed re-building ‘tciu-fMRI-analytics.Rmd’ SUMMARY: processing the following files failed: @@ -9670,33 +19812,10 @@ Run `revdepcheck::cloud_details(, "TCIU")` for more info * checking installed package size ... NOTE ``` - installed size is 14.7Mb + installed size is 14.1Mb sub-directories of 1Mb or more: - data 1.8Mb - doc 12.3Mb - ``` - -# TestGardener - -
- -* Version: 3.3.3 -* GitHub: NA -* Source code: https://github.com/cran/TestGardener -* Date/Publication: 2024-03-20 13:50:02 UTC -* Number of recursive dependencies: 131 - -Run `revdepcheck::cloud_details(, "TestGardener")` for more info - -
- -## Newly broken - -* checking whether package ‘TestGardener’ can be installed ... WARNING - ``` - Found the following significant warnings: - Warning: replacing previous import ‘ggplot2::ggpar’ by ‘ggpubr::ggpar’ when loading ‘TestGardener’ - See ‘/tmp/workdir/TestGardener/new/TestGardener.Rcheck/00install.out’ for details. + data 1.5Mb + doc 12.0Mb ``` # thematic @@ -9771,7 +19890,7 @@ Run `revdepcheck::cloud_details(, "thematic")` for more info * GitHub: https://github.com/mjskay/tidybayes * Source code: https://github.com/cran/tidybayes * Date/Publication: 2023-08-12 23:30:02 UTC -* Number of recursive dependencies: 193 +* Number of recursive dependencies: 192 Run `revdepcheck::cloud_details(, "tidybayes")` for more info @@ -9795,7 +19914,7 @@ Run `revdepcheck::cloud_details(, "tidybayes")` for more info 12. │ └─ggplot2 (local) f(l = layers[[i]], d = data[[i]]) 13. │ └─l$compute_geom_2(d, theme = plot$theme) 14. │ └─ggplot2 (local) compute_geom_2(..., self = self) - 15. │ └─self$geom$use_defaults(data, self$aes_params, modifiers, theme = theme) + 15. │ └─self$geom$use_defaults(...) 16. └─base::.handleSimpleError(...) 17. └─rlang (local) h(simpleError(msg, call)) 18. └─handlers[[1L]](cnd) @@ -9869,7 +19988,7 @@ Run `revdepcheck::cloud_details(, "tidybayes")` for more info * GitHub: https://github.com/Biogen-Inc/tidyCDISC * Source code: https://github.com/cran/tidyCDISC * Date/Publication: 2023-03-16 14:20:02 UTC -* Number of recursive dependencies: 141 +* Number of recursive dependencies: 140 Run `revdepcheck::cloud_details(, "tidyCDISC")` for more info @@ -9890,12 +20009,12 @@ Run `revdepcheck::cloud_details(, "tidyCDISC")` for more info Attaching package: 'shinyjs' ... - 16. ├─plotly::config(...) - 17. │ └─plotly:::modify_list(p$x$config, args) - 18. │ ├─utils::modifyList(x %||% list(), y %||% list(), ...) - 19. │ │ └─base::stopifnot(is.list(x), is.list(val)) - 20. │ └─x %||% list() - 21. └─plotly::layout(...) + 6. ├─plotly::config(...) + 7. │ └─plotly:::modify_list(p$x$config, args) + 8. │ ├─utils::modifyList(x %||% list(), y %||% list(), ...) + 9. │ │ └─base::stopifnot(is.list(x), is.list(val)) + 10. │ └─x %||% list() + 11. └─plotly::layout(...) [ FAIL 1 | WARN 1 | SKIP 15 | PASS 91 ] Error: Test failures @@ -9906,9 +20025,10 @@ Run `revdepcheck::cloud_details(, "tidyCDISC")` for more info * checking installed package size ... NOTE ``` - installed size is 5.6Mb + installed size is 6.0Mb sub-directories of 1Mb or more: - data 1.6Mb + R 1.0Mb + data 2.0Mb doc 1.8Mb ``` @@ -9920,7 +20040,7 @@ Run `revdepcheck::cloud_details(, "tidyCDISC")` for more info * GitHub: https://github.com/YuLab-SMU/tidydr * Source code: https://github.com/cran/tidydr * Date/Publication: 2023-03-08 09:20:02 UTC -* Number of recursive dependencies: 71 +* Number of recursive dependencies: 74 Run `revdepcheck::cloud_details(, "tidydr")` for more info @@ -9990,53 +20110,25 @@ Run `revdepcheck::cloud_details(, "tidysdm")` for more info ## Newly broken -* checking examples ... ERROR - ``` - Running examples in ‘tidysdm-Ex.R’ failed - The error most likely occurred in: - - > ### Name: autoplot.spatial_initial_split - > ### Title: Create a ggplot for a spatial initial rsplit. - > ### Aliases: autoplot.spatial_initial_split - > - > ### ** Examples - > - > - ... - 15. └─ggplot2 (local) FUN(X[[i]], ...) - 16. └─base::lapply(...) - 17. └─ggplot2 (local) FUN(X[[i]], ...) - 18. └─g$draw_key(data, g$params, key_size) - 19. └─ggplot2 (local) draw_key(...) - 20. └─ggplot2::draw_key_polygon(data, params, size) - 21. └─rlang:::Summary.quosure(from_theme(thin), 1.524, na.rm = FALSE) - 22. └─rlang:::abort_quosure_op("Summary", .Generic) - 23. └─rlang::abort(...) - Execution halted - ``` - * checking running R code from vignettes ... ERROR ``` Errors in running code in vignettes: when running code in ‘a0_tidysdm_overview.Rmd’ ... - + geom_sf(data = lacerta_thin, aes(col = class)) - - When sourcing ‘a0_tidysdm_overview.R’: - Error: Base operators are not defined for quosures. Do you need to unquote the - quosure? + > climate_vars <- names(climate_present) - # Bad: myquosure * rhs - ... + > lacerta_thin <- lacerta_thin %>% bind_cols(terra::extract(climate_present, + + lacerta_thin, ID = FALSE)) - # Bad: myquosure * rhs + > lacerta_thin %>% plot_pres_vs_bg(class) - # Good: !!myquosure * rhs + When sourcing ‘a0_tidysdm_overview.R’: + Error: object is not a unit Execution halted ‘a0_tidysdm_overview.Rmd’ using ‘UTF-8’... failed - ‘a1_palaeodata_application.Rmd’ using ‘UTF-8’... failed - ‘a2_tidymodels_additions.Rmd’ using ‘UTF-8’... failed + ‘a1_palaeodata_application.Rmd’ using ‘UTF-8’... OK + ‘a2_tidymodels_additions.Rmd’ using ‘UTF-8’... OK ‘a3_troubleshooting.Rmd’ using ‘UTF-8’... OK ``` @@ -10046,101 +20138,6 @@ Run `revdepcheck::cloud_details(, "tidysdm")` for more info --- re-building ‘a0_tidysdm_overview.Rmd’ using rmarkdown ``` -# tidyterra - -
- -* Version: 0.6.0 -* GitHub: https://github.com/dieghernan/tidyterra -* Source code: https://github.com/cran/tidyterra -* Date/Publication: 2024-04-22 23:50:02 UTC -* Number of recursive dependencies: 102 - -Run `revdepcheck::cloud_details(, "tidyterra")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘tidyterra-Ex.R’ failed - The error most likely occurred in: - - > ### Name: filter-joins.SpatVector - > ### Title: Filtering joins for 'SpatVector' objects - > ### Aliases: filter-joins.SpatVector semi_join.SpatVector - > ### anti_join.SpatVector - > - > ### ** Examples - > - ... - 15. └─ggplot2 (local) FUN(X[[i]], ...) - 16. └─base::lapply(...) - 17. └─ggplot2 (local) FUN(X[[i]], ...) - 18. └─g$draw_key(data, g$params, key_size) - 19. └─ggplot2 (local) draw_key(...) - 20. └─ggplot2::draw_key_polygon(data, params, size) - 21. └─rlang:::Summary.quosure(from_theme(thin), 1.524, na.rm = FALSE) - 22. └─rlang:::abort_quosure_op("Summary", .Generic) - 23. └─rlang::abort(...) - Execution halted - ``` - -# tidytransit - -
- -* Version: 1.6.1 -* GitHub: https://github.com/r-transit/tidytransit -* Source code: https://github.com/cran/tidytransit -* Date/Publication: 2023-12-07 13:40:02 UTC -* Number of recursive dependencies: 96 - -Run `revdepcheck::cloud_details(, "tidytransit")` for more info - -
- -## Newly broken - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘frequency.Rmd’ - ... - + labs(color = "H ..." ... [TRUNCATED] - - When sourcing ‘frequency.R’: - Error: Base operators are not defined for quosures. Do you need to unquote the - quosure? - - # Bad: myquosure * rhs - - # Good: !!myquosure * rhs - Execution halted - - ‘frequency.Rmd’ using ‘UTF-8’... failed - ‘introduction.Rmd’ using ‘UTF-8’... OK - ‘servicepatterns.Rmd’ using ‘UTF-8’... OK - ‘timetable.Rmd’ using ‘UTF-8’... OK - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘frequency.Rmd’ using rmarkdown - ``` - -## In both - -* checking installed package size ... NOTE - ``` - installed size is 7.1Mb - sub-directories of 1Mb or more: - doc 2.0Mb - extdata 4.5Mb - ``` - # tidytreatment
@@ -10169,8 +20166,8 @@ Run `revdepcheck::cloud_details(, "tidytreatment")` for more info Error: Problem while setting up geom aesthetics. ℹ Error occurred in the 1st layer. Caused by error in `use_defaults()`: - ! unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), NULL, list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.75, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, 90, NULL, c(0, - 2.75, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(NULL, N + ! unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, "black", TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), NULL, list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), 5.5, c(5.5, 5.5, 5.5, 5.5), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.75, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, + NULL, NULL, NULL, 1, 90, NULL, c(0, 2.75, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, Execution halted ‘use-tidytreatment-BART.Rmd’ using ‘UTF-8’... failed @@ -10182,16 +20179,16 @@ Run `revdepcheck::cloud_details(, "tidytreatment")` for more info ... --- re-building ‘use-tidytreatment-BART.Rmd’ using rmarkdown - Quitting from lines at lines 163-177 [plot-tidy-bart] (use-tidytreatment-BART.Rmd) + Quitting from lines 163-177 [plot-tidy-bart] (use-tidytreatment-BART.Rmd) Error: processing vignette 'use-tidytreatment-BART.Rmd' failed with diagnostics: Problem while setting up geom aesthetics. ℹ Error occurred in the 1st layer. Caused by error in `use_defaults()`: - ! unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), NULL, list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.75, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, 90, NULL, c(0, + ! unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, "black", TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), NULL, list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), 5.5, c(5.5, 5.5, 5.5, 5.5), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.75, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, ... - NULL, NULL, NULL, NULL, 0.2, NULL, list(NULL, NULL, NULL, 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, NULL, NULL, NULL, TRUE), NULL, "right", NULL, NULL, NULL, "center", NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, c(0, 0, 0, 0), list(), 11, list("white", NA, NULL, NULL, TRUE), list(NA, "grey20", NULL, NULL, TRUE), 5.5, NULL, NULL, list("grey92", NULL, NULL, NULL, FALSE, TRUE), NULL, list(NULL, 0.5, NULL, NULL, FALSE, TRUE), NULL, NULL, - NULL, NULL, FALSE, list(NULL, "white", NULL, NULL, TRUE), list(NULL, NULL, NULL, 1.2, 0, 1, NULL, NULL, c(0, 0, 5.5, 0), NULL, TRUE), "panel", list(NULL, NULL, NULL, NULL, 0, 1, NULL, NULL, c(0, 0, 5.5, 0), NULL, TRUE), list(NULL, NULL, NULL, 0.8, 1, 1, NULL, NULL, c(5.5, 0, 0, 0), NULL, TRUE), "panel", list(NULL, NULL, NULL, 1.2, 0.5, 0.5, NULL, NULL, NULL, NULL, TRUE), "topleft", NULL, c(5.5, 5.5, 5.5, 5.5), list("grey85", "grey20", NULL, NULL, TRUE), NULL, NULL, "inherit", "inside", list(NULL, - NULL, "grey10", 0.8, NULL, NULL, NULL, NULL, c(4.4, 4.4, 4.4, 4.4), NULL, TRUE), NULL, NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, NULL, -90, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, NULL, 90, NULL, NULL, NULL, TRUE), NULL, 2.75, 2.75)) + NULL, NULL, 1.2, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 0.2, NULL, list(NULL, NULL, NULL, 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, NULL, NULL, NULL, TRUE), NULL, "right", NULL, NULL, NULL, "center", NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 0, list(), 2, list("white", NA, NULL, NULL, TRUE), list(NULL, "grey20", NULL, NULL, TRUE), NULL, NULL, NULL, list("grey92", NULL, NULL, NULL, FALSE, "grey92", TRUE), NULL, list(NULL, 0.5, NULL, + NULL, FALSE, NULL, TRUE), NULL, NULL, NULL, NULL, FALSE, list(NULL, "white", NULL, NULL, TRUE), list(NULL, NULL, NULL, 1.2, 0, 1, NULL, NULL, c(0, 0, 5.5, 0), NULL, TRUE), "panel", list(NULL, NULL, NULL, NULL, 0, 1, NULL, NULL, c(0, 0, 5.5, 0), NULL, TRUE), list(NULL, NULL, NULL, 0.8, 1, 1, NULL, NULL, c(5.5, 0, 0, 0), NULL, TRUE), "panel", list(NULL, NULL, NULL, 1.2, 0.5, 0.5, NULL, NULL, NULL, NULL, TRUE), "topleft", NULL, NULL, list("grey85", "grey20", NULL, NULL, TRUE), NULL, NULL, "inherit", + "inside", list(NULL, NULL, "grey10", 0.8, NULL, NULL, NULL, NULL, c(4.4, 4.4, 4.4, 4.4), NULL, TRUE), NULL, NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, NULL, -90, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, NULL, 90, NULL, NULL, NULL, TRUE), NULL, 2.75, 2.75)) --- failed re-building ‘use-tidytreatment-BART.Rmd’ SUMMARY: processing the following file failed: @@ -10208,185 +20205,314 @@ Run `revdepcheck::cloud_details(, "tidytreatment")` for more info Package which this enhances but not available for checking: ‘bartMachine’ ``` -# tilemaps +# timetk + +
+ +* Version: 2.9.0 +* GitHub: https://github.com/business-science/timetk +* Source code: https://github.com/cran/timetk +* Date/Publication: 2023-10-31 22:30:02 UTC +* Number of recursive dependencies: 226 + +Run `revdepcheck::cloud_details(, "timetk")` for more info + +
+ +## Newly broken + +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > # This file is part of the standard setup for testthat. + > # It is recommended that you do not modify it. + > # + > # Where should you do additional test configuration? + > # Learn more about the roles of various files in: + > # * https://r-pkgs.org/testing-design.html#sec-tests-files-overview + > # * https://testthat.r-lib.org/articles/special-files.html + ... + 7. └─timetk:::plot_time_series.grouped_df(...) + 8. ├─timetk::plot_time_series(...) + 9. └─timetk:::plot_time_series.data.frame(...) + 10. ├─plotly::ggplotly(g, dynamicTicks = TRUE) + 11. └─plotly:::ggplotly.ggplot(g, dynamicTicks = TRUE) + 12. └─plotly::gg2list(...) + + [ FAIL 1 | WARN 0 | SKIP 0 | PASS 406 ] + Error: Test failures + Execution halted + ``` + +## In both + +* checking data for non-ASCII characters ... NOTE + ``` + Note: found 2750 marked UTF-8 strings + ``` + +# tinyarray + +
+ +* Version: 2.4.1 +* GitHub: https://github.com/xjsun1221/tinyarray +* Source code: https://github.com/cran/tinyarray +* Date/Publication: 2024-06-04 09:45:15 UTC +* Number of recursive dependencies: 240 + +Run `revdepcheck::cloud_details(, "tinyarray")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘tinyarray-Ex.R’ failed + The error most likely occurred in: + + > ### Name: exp_surv + > ### Title: exp_surv + > ### Aliases: exp_surv + > + > ### ** Examples + > + > tmp = exp_surv(exprSet_hub1,meta1) + > patchwork::wrap_plots(tmp)+patchwork::plot_layout(guides = "collect") + Error in identicalUnits(x) : object is not a unit + Calls: ... assemble_guides -> guides_build -> unit.c -> identicalUnits + Execution halted + ``` + +## In both + +* checking data for non-ASCII characters ... NOTE + ``` + Note: found 2 marked UTF-8 strings + ``` + +# tmap + +
+ +* Version: 3.3-4 +* GitHub: https://github.com/r-tmap/tmap +* Source code: https://github.com/cran/tmap +* Date/Publication: 2023-09-12 21:20:02 UTC +* Number of recursive dependencies: 145 + +Run `revdepcheck::cloud_details(, "tmap")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘tmap-Ex.R’ failed + The error most likely occurred in: + + > ### Name: tm_symbols + > ### Title: Draw symbols + > ### Aliases: tm_symbols tm_squares tm_bubbles tm_dots tm_markers + > + > ### ** Examples + > + > data(World, metro) + ... + ▆ + 1. └─base::lapply(...) + 2. └─global FUN(X[[i]], ...) + 3. └─ggplot2::ggplotGrob(...) + 4. ├─ggplot2::ggplot_gtable(ggplot_build(x)) + 5. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) + 6. └─ggplot2::calc_element("plot.margin", theme) + 7. └─cli::cli_abort(...) + 8. └─rlang::abort(...) + Execution halted + ``` + +# TOmicsVis
-* Version: 0.2.0 -* GitHub: https://github.com/kaerosen/tilemaps -* Source code: https://github.com/cran/tilemaps -* Date/Publication: 2020-07-10 04:20:02 UTC -* Number of recursive dependencies: 72 +* Version: 2.0.0 +* GitHub: https://github.com/benben-miao/TOmicsVis +* Source code: https://github.com/cran/TOmicsVis +* Date/Publication: 2023-08-28 18:30:02 UTC +* Number of recursive dependencies: 264 -Run `revdepcheck::cloud_details(, "tilemaps")` for more info +Run `revdepcheck::cloud_details(, "TOmicsVis")` for more info
## Newly broken +* checking examples ... ERROR + ``` + Running examples in ‘TOmicsVis-Ex.R’ failed + The error most likely occurred in: + + > ### Name: upsetr_plot + > ### Title: UpSet plot for stat common and unique gene among multiple sets. + > ### Aliases: upsetr_plot + > + > ### ** Examples + > + > # 1. Library TOmicsVis package + ... + 3. ├─base::suppressMessages(...) + 4. │ └─base::withCallingHandlers(...) + 5. └─UpSetR:::Make_main_bar(...) + 6. └─ggplot2::ggplotGrob(Main_bar_plot) + 7. ├─ggplot2::ggplot_gtable(ggplot_build(x)) + 8. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) + 9. └─ggplot2::calc_element("plot.margin", theme) + 10. └─cli::cli_abort(...) + 11. └─rlang::abort(...) + Execution halted + ``` + * checking running R code from vignettes ... ERROR ``` Errors in running code in vignettes: - when running code in ‘tilemaps.Rmd’ + when running code in ‘Tutorials.Rmd’ ... - + fu .... [TRUNCATED] - - When sourcing ‘tilemaps.R’: - Error: Summary operations are not defined for quosures. Do you need to unquote - the quosure? + 5 transcript_8832 transcript_3069 transcript_10224 transcript_9881 + 6 transcript_74 transcript_9809 transcript_3151 transcript_8836 - # Bad: min(myquosure) + > upsetr_plot(data = degs_lists, sets_num = 4, keep_order = FALSE, + + order_by = "freq", decrease = TRUE, mainbar_color = "#006600", + + number .... [TRUNCATED] - # Good: min(!!myquosure) + When sourcing ‘Tutorials.R’: + Error: Theme element `plot.margin` must have class . Execution halted - ‘tilemaps.Rmd’ using ‘UTF-8’... failed + ‘Tutorials.Rmd’ using ‘UTF-8’... failed ``` * checking re-building of vignette outputs ... NOTE ``` Error(s) in re-building vignettes: - --- re-building ‘tilemaps.Rmd’ using rmarkdown + --- re-building ‘Tutorials.Rmd’ using rmarkdown ``` ## In both -* checking dependencies in R code ... NOTE +* checking installed package size ... NOTE ``` - Namespace in Imports field not imported from: ‘lwgeom’ - All declared Imports should be used. + installed size is 7.3Mb + sub-directories of 1Mb or more: + data 1.5Mb + data-tables 1.5Mb + doc 1.9Mb + help 1.2Mb ``` -# timetk +# tornado
-* Version: 2.9.0 -* GitHub: https://github.com/business-science/timetk -* Source code: https://github.com/cran/timetk -* Date/Publication: 2023-10-31 22:30:02 UTC -* Number of recursive dependencies: 226 +* Version: 0.1.3 +* GitHub: https://github.com/bertcarnell/tornado +* Source code: https://github.com/cran/tornado +* Date/Publication: 2024-01-21 17:30:02 UTC +* Number of recursive dependencies: 115 -Run `revdepcheck::cloud_details(, "timetk")` for more info +Run `revdepcheck::cloud_details(, "tornado")` for more info
## Newly broken +* checking examples ... ERROR + ``` + Running examples in ‘tornado-Ex.R’ failed + The error most likely occurred in: + + > ### Name: plot.tornado_plot + > ### Title: Plot a Tornado Plot object + > ### Aliases: plot.tornado_plot + > + > ### ** Examples + > + > gtest <- lm(mpg ~ cyl*wt*hp, data = mtcars) + ... + 13. │ └─base::withCallingHandlers(...) + 14. └─ggplot2 (local) f(l = layers[[i]], d = data[[i]]) + 15. └─l$compute_geom_2(d, theme = plot$theme) + 16. └─ggplot2 (local) compute_geom_2(..., self = self) + 17. └─self$geom$use_defaults(...) + 18. └─ggplot2 (local) use_defaults(..., self = self) + 19. └─ggplot2:::check_aesthetics(new_params, nrow(data)) + 20. └─cli::cli_abort(...) + 21. └─rlang::abort(...) + Execution halted + ``` + * checking tests ... ERROR ``` Running ‘testthat.R’ Running the tests in ‘tests/testthat.R’ failed. Complete output: - > # This file is part of the standard setup for testthat. - > # It is recommended that you do not modify it. - > # - > # Where should you do additional test configuration? - > # Learn more about the roles of various files in: - > # * https://r-pkgs.org/testing-design.html#sec-tests-files-overview - > # * https://testthat.r-lib.org/articles/special-files.html + > if (require(testthat)) + + { + + library(tornado) + + + + test_check("tornado") + + } + Loading required package: testthat ... - 17. └─ggplot2 (local) compute_geom_2(..., self = self) - 18. └─self$geom$use_defaults(data, self$aes_params, modifiers, theme = theme) - 19. └─ggplot2 (local) use_defaults(..., self = self) - 20. └─ggplot2:::eval_from_theme(default_aes, theme) - 21. ├─calc_element("geom", theme) %||% .default_geom_element - 22. └─ggplot2::calc_element("geom", theme) + ...)) + })(position = "identity", stat = "identity", width = NULL)`: Problem while setting up geom aesthetics. + ℹ Error occurred in the 1st layer. + Caused by error in `check_aesthetics()`: + ! Aesthetics must be either length 1 or the same as the data (20). + ✖ Fix the following mappings: `width`. - [ FAIL 1 | WARN 0 | SKIP 0 | PASS 406 ] + [ FAIL 14 | WARN 0 | SKIP 0 | PASS 101 ] Error: Test failures Execution halted ``` -## In both - -* checking data for non-ASCII characters ... NOTE - ``` - Note: found 2750 marked UTF-8 strings - ``` - -# tongfen - -
- -* Version: 0.3.5 -* GitHub: https://github.com/mountainMath/tongfen -* Source code: https://github.com/cran/tongfen -* Date/Publication: 2022-04-28 18:50:02 UTC -* Number of recursive dependencies: 101 - -Run `revdepcheck::cloud_details(, "tongfen")` for more info - -
- -## Newly broken - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘polling_districts.Rmd’ using rmarkdown - - Quitting from lines at lines 44-79 [unnamed-chunk-3] (polling_districts.Rmd) - Error: processing vignette 'polling_districts.Rmd' failed with diagnostics: - Summary operations are not defined for quosures. Do you need to unquote - the quosure? - - # Bad: min(myquosure) - - ... - --- finished re-building ‘tongfen_ca.Rmd’ - - --- re-building ‘tongfen_us.Rmd’ using rmarkdown - --- finished re-building ‘tongfen_us.Rmd’ - - SUMMARY: processing the following file failed: - ‘polling_districts.Rmd’ - - Error: Vignette re-building failed. - Execution halted - ``` - -## In both - * checking running R code from vignettes ... ERROR ``` Errors in running code in vignettes: - when running code in ‘polling_districts.Rmd’ + when running code in ‘tornadoVignette.Rmd’ ... - + size = 0.2, color = "black") + facet_wrap("Year") + scale_fill_manual(values = party_colou .... [TRUNCATED] - - When sourcing ‘polling_districts.R’: - Error: Summary operations are not defined for quosures. Do you need to unquote - the quosure? - - # Bad: min(myquosure) - ... - # Bad: min(myquosure) + + .... [TRUNCATED] + Loading required package: lattice - # Good: min(!!myquosure) + When sourcing ‘tornadoVignette.R’: + Error: Problem while setting up geom aesthetics. + ℹ Error occurred in the 1st layer. + Caused by error in `check_aesthetics()`: + ! Aesthetics must be either length 1 or the same as the data (20). + ✖ Fix the following mappings: `width`. Execution halted - ‘polling_districts.Rmd’ using ‘UTF-8’... failed - ‘tongfen-ca-estimate.Rmd’ using ‘UTF-8’... failed - ‘tongfen.Rmd’ using ‘UTF-8’... failed - ‘tongfen_ca.Rmd’ using ‘UTF-8’... failed - ‘tongfen_us.Rmd’ using ‘UTF-8’... failed + ‘tornadoVignette.Rmd’ using ‘UTF-8’... failed ``` -* checking data for non-ASCII characters ... NOTE +* checking re-building of vignette outputs ... NOTE ``` - Note: found 160 marked UTF-8 strings + Error(s) in re-building vignettes: + --- re-building ‘tornadoVignette.Rmd’ using rmarkdown ``` # TOSTER
-* Version: 0.8.2 +* Version: 0.8.3 * GitHub: NA * Source code: https://github.com/cran/TOSTER -* Date/Publication: 2024-04-16 16:40:02 UTC -* Number of recursive dependencies: 103 +* Date/Publication: 2024-05-08 16:40:02 UTC +* Number of recursive dependencies: 102 Run `revdepcheck::cloud_details(, "TOSTER")` for more info @@ -10413,8 +20539,8 @@ Run `revdepcheck::cloud_details(, "TOSTER")` for more info ───────────────────────────────────────────────────────────────────────── Error in use_defaults(..., self = self) : - unused argument (theme = list(list("black", 0.727272727272727, 1, "butt", FALSE, TRUE), list("white", "black", 0.727272727272727, 1, TRUE), list("", "plain", "black", 16, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), NULL, list("black", "white", "#3366FF", 0.727272727272727, 1.45454545454545, "", 5.62335685623357, 2.18181818181818, 19, TRUE), NULL, NULL, list(NULL, NULL, "#333333", NULL, NULL, NULL, NULL, NULL, c(10, 0, 0, 0), NULL, FALSE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 4, 0), - NULL, TRUE), NULL, list(NULL, NULL, "#333333", NULL, NULL, NULL, 90, NULL, c(0, 10, 0, 0), NULL, FALSE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 4), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, "#333333", NULL, NULL, NULL, NULL, NULL, c(5, 0, 0, 0), NULL, FALSE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 3.2, 0), NULL, TRUE), NULL, list(), NULL, list(NULL, NULL, NULL, NU + unused argument (theme = list(list("black", 0.727272727272727, 1, "butt", FALSE, "black", TRUE), list("white", "black", 0.727272727272727, 1, TRUE), list("", "plain", "black", 16, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), NULL, list("black", "white", "#3366FF", 0.727272727272727, 1.45454545454545, "", 5.62335685623357, 2.18181818181818, 19, TRUE), 8, c(8, 8, 8, 8), NULL, NULL, list(NULL, NULL, "#333333", NULL, NULL, NULL, NULL, NULL, c(10, 0, 0, 0), NULL, FALSE), list(NULL, NULL, NULL, NULL, NULL, 0, + NULL, NULL, c(0, 0, 4, 0), NULL, TRUE), NULL, list(NULL, NULL, "#333333", NULL, NULL, NULL, 90, NULL, c(0, 10, 0, 0), NULL, FALSE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 4), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, "#333333", NULL, NULL, NULL, NULL, NULL, c(5, 0, 0, 0), NULL, FALSE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 3.2, 0), NULL, TRUE), NULL, list(), NULL Calls: ... -> -> -> Execution halted ``` @@ -10432,14 +20558,14 @@ Run `revdepcheck::cloud_details(, "TOSTER")` for more info The following object is masked from 'package:testthat': ... - 34. │ │ └─base::withCallingHandlers(...) - 35. │ └─layer$geom$use_defaults(...) - 36. └─base::.handleSimpleError(...) - 37. └─rlang (local) h(simpleError(msg, call)) - 38. └─handlers[[1L]](cnd) - 39. └─layer$geom$use_defaults(...) + 26. └─base::Map(...) + 27. └─base::mapply(FUN = f, ..., SIMPLIFY = FALSE) + 28. └─ggplot2 (local) ``(layer = dots[[1L]][[1L]], df = dots[[2L]][[1L]]) + 29. └─layer$compute_geom_2(key, single_params, theme) + 30. └─ggplot2 (local) compute_geom_2(..., self = self) + 31. └─self$geom$use_defaults(...) - [ FAIL 8 | WARN 0 | SKIP 0 | PASS 1029 ] + [ FAIL 8 | WARN 0 | SKIP 0 | PASS 1034 ] Error: Test failures Execution halted ``` @@ -10457,8 +20583,8 @@ Run `revdepcheck::cloud_details(, "TOSTER")` for more info When sourcing ‘IntroTOSTt.R’: ... - Error: unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), NULL, list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(7, 0, 0, 0), NULL, FALSE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, 90, NULL, c(0, 7, - 0, 0), NULL, FALSE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, "bold", NULL, 11, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, FALSE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, NULL, c(0, 0, 0, 2.2), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0.5, + Error: unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, "black", TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), NULL, list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), 5.5, c(5.5, 5.5, 5.5, 5.5), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(7, 0, 0, 0), NULL, FALSE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, + NULL, NULL, 1, 90, NULL, c(0, 7, 0, 0), NULL, FALSE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, "bold", NULL, 11, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, FALSE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, NULL, c(0, 0, 0, 2.2), NULL, TRUE) Execution halted ‘IntroTOSTt.Rmd’ using ‘UTF-8’... failed @@ -10475,14 +20601,64 @@ Run `revdepcheck::cloud_details(, "TOSTER")` for more info --- re-building ‘IntroTOSTt.Rmd’ using rmarkdown ``` +# toxEval + +
+ +* Version: 1.3.2 +* GitHub: https://github.com/DOI-USGS/toxEval +* Source code: https://github.com/cran/toxEval +* Date/Publication: 2024-02-08 07:30:02 UTC +* Number of recursive dependencies: 127 + +Run `revdepcheck::cloud_details(, "toxEval")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘toxEval-Ex.R’ failed + The error most likely occurred in: + + > ### Name: plot_tox_stacks + > ### Title: Plot stacked bar charts + > ### Aliases: plot_tox_stacks + > + > ### ** Examples + > + > # This is the example workflow: + ... + Backtrace: + ▆ + 1. ├─base (local) ``(x) + 2. └─ggplot2:::print.ggplot(x) + 3. ├─ggplot2::ggplot_gtable(data) + 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) + 5. └─ggplot2::calc_element("plot.margin", theme) + 6. └─cli::cli_abort(...) + 7. └─rlang::abort(...) + Execution halted + ``` + +## In both + +* checking installed package size ... NOTE + ``` + installed size is 8.1Mb + sub-directories of 1Mb or more: + R 7.2Mb + ``` + # TreatmentPatterns
-* Version: 2.6.6 -* GitHub: https://github.com/darwin-eu-dev/TreatmentPatterns +* Version: 2.6.7 +* GitHub: https://github.com/darwin-eu/TreatmentPatterns * Source code: https://github.com/cran/TreatmentPatterns -* Date/Publication: 2024-04-16 15:10:06 UTC +* Date/Publication: 2024-05-24 08:30:32 UTC * Number of recursive dependencies: 142 Run `revdepcheck::cloud_details(, "TreatmentPatterns")` for more info @@ -10491,29 +20667,246 @@ Run `revdepcheck::cloud_details(, "TreatmentPatterns")` for more info ## Newly broken -* checking tests ... ERROR +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > # This file is part of the standard setup for testthat. + > # It is recommended that you do not modify it. + > # + > # Where should you do additional test configuration? + > # Learn more about the roles of various files in: + > # * https://r-pkgs.org/tests.html + > # * https://testthat.r-lib.org/reference/test_package.html#special-files + ... + 22. ├─testthat::expect_s3_class(output$charAgePlot$html, "html") at test-CharacterizationPlots.R:47:9 + 23. │ └─testthat::quasi_label(enquo(object), arg = "object") + 24. │ └─rlang::eval_bare(expr, quo_get_env(quo)) + 25. ├─output$charAgePlot + 26. └─shiny:::`$.shinyoutput`(output, charAgePlot) + 27. └─.subset2(x, "impl")$getOutput(name) + + [ FAIL 1 | WARN 0 | SKIP 21 | PASS 134 ] + Error: Test failures + Execution halted + ``` + +# TreatmentSelection + +
+ +* Version: 2.1.1 +* GitHub: NA +* Source code: https://github.com/cran/TreatmentSelection +* Date/Publication: 2017-08-11 18:55:47 UTC +* Number of recursive dependencies: 30 + +Run `revdepcheck::cloud_details(, "TreatmentSelection")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘TreatmentSelection-Ex.R’ failed + The error most likely occurred in: + + > ### Name: plot.trtsel + > ### Title: plot risk curves, treatment effect curves or cdf of risk for a + > ### trtsel object. + > ### Aliases: plot.trtsel plot + > + > ### ** Examples + > + ... + 1. ├─base::plot(...) + 2. └─TreatmentSelection:::plot.trtsel(...) + 3. └─TreatmentSelection (local) tmp.plotfun(...) + 4. └─ggplot2::ggplotGrob((p)) + 5. ├─ggplot2::ggplot_gtable(ggplot_build(x)) + 6. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) + 7. └─ggplot2::calc_element("plot.margin", theme) + 8. └─cli::cli_abort(...) + 9. └─rlang::abort(...) + Execution halted + ``` + +# TreeDep + +
+ +* Version: 0.1.3 +* GitHub: NA +* Source code: https://github.com/cran/TreeDep +* Date/Publication: 2018-12-02 17:50:03 UTC +* Number of recursive dependencies: 32 + +Run `revdepcheck::cloud_details(, "TreeDep")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘TreeDep-Ex.R’ failed + The error most likely occurred in: + + > ### Name: TreeDep_plot + > ### Title: TreeDep_plot - Generates a plot for selected variables and + > ### dates. + > ### Aliases: TreeDep_plot + > + > ### ** Examples + > + ... + Backtrace: + ▆ + 1. ├─base (local) ``(x) + 2. └─ggplot2:::print.ggplot(x) + 3. ├─ggplot2::ggplot_gtable(data) + 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) + 5. └─ggplot2::calc_element("plot.margin", theme) + 6. └─cli::cli_abort(...) + 7. └─rlang::abort(...) + Execution halted + ``` + +# TreeDist + +
+ +* Version: 2.7.0 +* GitHub: https://github.com/ms609/TreeDist +* Source code: https://github.com/cran/TreeDist +* Date/Publication: 2023-10-25 22:10:02 UTC +* Number of recursive dependencies: 230 + +Run `revdepcheck::cloud_details(, "TreeDist")` for more info + +
+ +## Newly broken + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘treespace.Rmd’ + ... + [1] "Epoch: 3 finished. 212 datapoints changed bestmatch" + [1] "Epoch: 4 started" + [1] "Epoch: 4 finished. 203 datapoints changed bestmatch" + [1] "Epoch: 5 started" + [1] "Epoch: 5 finished. 165 datapoints changed bestmatch" + [1] "---- Esom Training Finished ----" + + ... + + ‘Generalized-RF.Rmd’ using ‘UTF-8’... OK + ‘Robinson-Foulds.Rmd’ using ‘UTF-8’... OK + ‘Using-TreeDist.Rmd’ using ‘UTF-8’... OK + ‘compare-treesets.Rmd’ using ‘UTF-8’... OK + ‘different-leaves.Rmd’ using ‘UTF-8’... OK + ‘information.Rmd’ using ‘UTF-8’... OK + ‘landscapes.Rmd’ using ‘UTF-8’... OK + ‘treespace.Rmd’ using ‘UTF-8’... failed + ‘using-distances.Rmd’ using ‘UTF-8’... OK + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘Generalized-RF.Rmd’ using rmarkdown + ``` + +## In both + +* checking installed package size ... NOTE + ``` + installed size is 9.2Mb + sub-directories of 1Mb or more: + doc 5.0Mb + libs 3.6Mb + ``` + +# treeheatr + +
+ +* Version: 0.2.1 +* GitHub: https://github.com/trang1618/treeheatr +* Source code: https://github.com/cran/treeheatr +* Date/Publication: 2020-11-19 21:00:03 UTC +* Number of recursive dependencies: 97 + +Run `revdepcheck::cloud_details(, "treeheatr")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘treeheatr-Ex.R’ failed + The error most likely occurred in: + + > ### Name: draw_heat + > ### Title: Draws the heatmap. + > ### Aliases: draw_heat + > + > ### ** Examples + > + > x <- compute_tree(penguins, target_lab = 'species') + ... + Backtrace: + ▆ + 1. ├─base (local) ``(x) + 2. └─ggplot2:::print.ggplot(x) + 3. ├─ggplot2::ggplot_gtable(data) + 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) + 5. └─ggplot2::calc_element("plot.margin", theme) + 6. └─cli::cli_abort(...) + 7. └─rlang::abort(...) + Execution halted + ``` + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘explore.Rmd’ + ... + Please report the issue at . + Warning: The `guide` argument in `scale_*()` cannot be `FALSE`. This was deprecated in + ggplot2 3.3.4. + ℹ Please use "none" instead. + ℹ The deprecated feature was likely used in the treeheatr package. + Please report the issue at . + + When sourcing ‘explore.R’: + Error: Theme element `plot.margin` must have class . + Execution halted + + ‘explore.Rmd’ using ‘UTF-8’... failed + ``` + +* checking re-building of vignette outputs ... NOTE ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > # This file is part of the standard setup for testthat. - > # It is recommended that you do not modify it. - > # - > # Where should you do additional test configuration? - > # Learn more about the roles of various files in: - > # * https://r-pkgs.org/tests.html - > # * https://testthat.r-lib.org/reference/test_package.html#special-files - ... - 22. ├─testthat::expect_s3_class(output$charAgePlot$html, "html") at test-CharacterizationPlots.R:47:9 - 23. │ └─testthat::quasi_label(enquo(object), arg = "object") - 24. │ └─rlang::eval_bare(expr, quo_get_env(quo)) - 25. ├─output$charAgePlot - 26. └─shiny:::`$.shinyoutput`(output, charAgePlot) - 27. └─.subset2(x, "impl")$getOutput(name) - - [ FAIL 1 | WARN 0 | SKIP 31 | PASS 95 ] - Error: Test failures - Execution halted + Error(s) in re-building vignettes: + ... + --- re-building ‘explore.Rmd’ using rmarkdown + + Quitting from lines 33-36 [unnamed-chunk-2] (explore.Rmd) + Error: processing vignette 'explore.Rmd' failed with diagnostics: + Theme element `plot.margin` must have class . + --- failed re-building ‘explore.Rmd’ + + SUMMARY: processing the following file failed: + ‘explore.Rmd’ + + Error: Vignette re-building failed. + Execution halted ``` # trelliscopejs @@ -10524,7 +20917,7 @@ Run `revdepcheck::cloud_details(, "TreatmentPatterns")` for more info * GitHub: https://github.com/hafen/trelliscopejs * Source code: https://github.com/cran/trelliscopejs * Date/Publication: 2021-02-01 08:00:02 UTC -* Number of recursive dependencies: 107 +* Number of recursive dependencies: 106 Run `revdepcheck::cloud_details(, "trelliscopejs")` for more info @@ -10532,6 +20925,31 @@ Run `revdepcheck::cloud_details(, "trelliscopejs")` for more info ## Newly broken +* checking examples ... ERROR + ``` + Running examples in ‘trelliscopejs-Ex.R’ failed + The error most likely occurred in: + + > ### Name: cog + > ### Title: Cast Column as a Cognostic + > ### Aliases: cog + > + > ### ** Examples + > + > library(dplyr) + ... + 8. ├─base::tryCatch(...) + 9. │ └─base (local) tryCatchList(expr, classes, parentenv, handlers) + 10. ├─base::print(p) + 11. └─ggplot2:::print.ggplot(p) + 12. ├─ggplot2::ggplot_gtable(data) + 13. └─ggplot2:::ggplot_gtable.ggplot_built(data) + 14. └─ggplot2::calc_element("plot.margin", theme) + 15. └─cli::cli_abort(...) + 16. └─rlang::abort(...) + Execution halted + ``` + * checking tests ... ERROR ``` Running ‘testthat.R’ @@ -10541,22 +20959,108 @@ Run `revdepcheck::cloud_details(, "trelliscopejs")` for more info > library(trelliscopejs) > > test_check("trelliscopejs") - [ FAIL 1 | WARN 2 | SKIP 0 | PASS 0 ] + [ FAIL 1 | WARN 0 | SKIP 0 | PASS 0 ] ══ Failed tests ════════════════════════════════════════════════════════════════ ... - 14. └─ggplot2 (local) compute_geom_2(..., self = self) - 15. └─self$geom$use_defaults(data, self$aes_params, modifiers, theme = theme) - 16. └─ggplot2 (local) use_defaults(..., self = self) - 17. └─ggplot2:::eval_from_theme(default_aes, theme) - 18. ├─calc_element("geom", theme) %||% .default_geom_element - 19. └─ggplot2::calc_element("geom", theme) + 12. └─ggplot2:::print.ggplot(p) + 13. ├─ggplot2::ggplot_gtable(data) + 14. └─ggplot2:::ggplot_gtable.ggplot_built(data) + 15. └─ggplot2::calc_element("plot.margin", theme) + 16. └─cli::cli_abort(...) + 17. └─rlang::abort(...) - [ FAIL 1 | WARN 2 | SKIP 0 | PASS 0 ] + [ FAIL 1 | WARN 0 | SKIP 0 | PASS 0 ] Error: Test failures Execution halted ``` +# tricolore + +
+ +* Version: 1.2.4 +* GitHub: https://github.com/jschoeley/tricolore +* Source code: https://github.com/cran/tricolore +* Date/Publication: 2024-05-15 15:00:02 UTC +* Number of recursive dependencies: 108 + +Run `revdepcheck::cloud_details(, "tricolore")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘tricolore-Ex.R’ failed + The error most likely occurred in: + + > ### Name: ColorKeySextant + > ### Title: Sextant Scheme Legend + > ### Aliases: ColorKeySextant + > ### Keywords: internal + > + > ### ** Examples + > + ... + 3. ├─ggtern::ggplot_build(x) + 4. └─ggtern:::ggplot_build.ggplot(x) + 5. └─ggtern:::layers_add_or_remove_mask(plot) + 6. └─ggint$plot_theme(plot) + 7. └─ggplot2:::validate_theme(theme) + 8. └─base::mapply(...) + 9. └─ggplot2 (local) ``(...) + 10. └─cli::cli_abort(...) + 11. └─rlang::abort(...) + Execution halted + ``` + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘choropleth_maps_with_tricolore.Rmd’ + ... + + > plot_educ <- ggplot(euro_example) + geom_sf(aes(fill = rgb, + + geometry = geometry), size = 0.1) + scale_fill_identity() + + > plot_educ + + When sourcing ‘choropleth_maps_with_tricolore.R’: + Error: The `tern.axis.ticks.length.major` theme element must be a + object. + Execution halted + + ‘choropleth_maps_with_tricolore.Rmd’ using ‘UTF-8’... failed + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + ... + --- re-building ‘choropleth_maps_with_tricolore.Rmd’ using rmarkdown + + Quitting from lines 61-72 [unnamed-chunk-4] (choropleth_maps_with_tricolore.Rmd) + Error: processing vignette 'choropleth_maps_with_tricolore.Rmd' failed with diagnostics: + The `tern.axis.ticks.length.major` theme element must be a + object. + --- failed re-building ‘choropleth_maps_with_tricolore.Rmd’ + + SUMMARY: processing the following file failed: + ‘choropleth_maps_with_tricolore.Rmd’ + + Error: Vignette re-building failed. + Execution halted + ``` + +## In both + +* checking data for non-ASCII characters ... NOTE + ``` + Note: found 2 marked UTF-8 strings + ``` + # tsnet
@@ -10586,14 +21090,14 @@ Run `revdepcheck::cloud_details(, "tsnet")` for more info > # * https://r-pkgs.org/tests.html > # * https://testthat.r-lib.org/reference/test_package.html#special-files ... - unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), NULL, list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(7, 0, 0, 0), NULL, FALSE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, 90, NULL, c(0, 7, - 0, 0), NULL, FALSE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 1, NULL, NULL, NULL, c(0, 2.2, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, NULL, c(0, 0, 0, 2.2), - NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0.5, NULL, NULL, NULL, c(0, 2.2, 0, 2.2), NULL, TRUE), list("grey70", 0.5, NULL, NULL, FALSE, TRUE), NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 2.75, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 0.75, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, list(), list("gray70", 0.5, NULL, NULL, FALSE, FALSE), NULL, NULL, list("gray70", 0.5, NULL, NULL, FALSE, FALSE), NULL, NULL, NULL, NULL, list(NULL, NA, NULL, - NULL, TRUE), c(5.5, 5.5, 5.5, 5.5), 11, NULL, NULL, NULL, 1.2, NULL, NULL, 5.5, NULL, NULL, NULL, NULL, 0.2, NULL, list(NULL, NULL, NULL, 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, NULL, NULL, NULL, TRUE), NULL, "right", NULL, NULL, NULL, "center", NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, c(0, 0, 0, 0), list(), 11, list("white", NA, NULL, NULL, TRUE), list(), 5.5, NULL, NULL, list("grey87", NULL, NULL, NULL, FALSE, TRUE), list(), list(), - NULL, NULL, NULL, NULL, FALSE, list(NULL, "white", NULL, NULL, TRUE), list(NULL, NULL, NULL, 1.2, 0, 1, NULL, NULL, c(0, 0, 5.5, 0), NULL, TRUE), "panel", list(NULL, NULL, NULL, NULL, 0, 1, NULL, NULL, c(0, 0, 5.5, 0), NULL, TRUE), list(NULL, NULL, NULL, 0.8, 1, 1, NULL, NULL, c(5.5, 0, 0, 0), NULL, TRUE), "panel", list(NULL, NULL, NULL, 1.2, 0.5, 0.5, NULL, NULL, NULL, NULL, TRUE), "topleft", NULL, c(5.5, 5.5, 5.5, 5.5), list("gray90", NA, NULL, NULL, FALSE), NULL, NULL, "inherit", "inside", - list(NULL, NULL, "black", 0.8, NULL, NULL, NULL, NULL, c(6, 6, 6, 6), NULL, FALSE), NULL, NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, NULL, -90, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, NULL, 90, NULL, NULL, NULL, TRUE), NULL, 2.75, 2.75)) + unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, "black", TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), NULL, list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), 5.5, c(5.5, 5.5, 5.5, 5.5), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(7, 0, 0, 0), NULL, FALSE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, + NULL, NULL, 1, 90, NULL, c(0, 7, 0, 0), NULL, FALSE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 1, NULL, NULL, NULL, c(0, 2.2, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0, + NULL, NULL, NULL, c(0, 0, 0, 2.2), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0.5, NULL, NULL, NULL, c(0, 2.2, 0, 2.2), NULL, TRUE), list("grey70", 0.5, NULL, NULL, FALSE, "grey70", TRUE), NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 0.5, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 0.75, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, list(), list("gray70", 0.5, NULL, NULL, FALSE, "gray70", FALSE), NULL, NULL, list("gray70", 0.5, NULL, NULL, FALSE, + "gray70", FALSE), NULL, NULL, NULL, NULL, list(NULL, NA, NULL, NULL, TRUE), NULL, 2, NULL, NULL, NULL, 1.2, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 0.2, NULL, list(NULL, NULL, NULL, 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, NULL, NULL, NULL, TRUE), NULL, "right", NULL, NULL, NULL, "center", NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 0, list(), 2, list("white", NA, NULL, NULL, TRUE), list(), NULL, NULL, NULL, list("grey87", NULL, NULL, + NULL, FALSE, "grey87", TRUE), list(), list(), NULL, NULL, NULL, NULL, FALSE, list(NULL, "white", NULL, NULL, TRUE), list(NULL, NULL, NULL, 1.2, 0, 1, NULL, NULL, c(0, 0, 5.5, 0), NULL, TRUE), "panel", list(NULL, NULL, NULL, NULL, 0, 1, NULL, NULL, c(0, 0, 5.5, 0), NULL, TRUE), list(NULL, NULL, NULL, 0.8, 1, 1, NULL, NULL, c(5.5, 0, 0, 0), NULL, TRUE), "panel", list(NULL, NULL, NULL, 1.2, 0.5, 0.5, NULL, NULL, NULL, NULL, TRUE), "topleft", NULL, NULL, list("gray90", NA, NULL, NULL, FALSE), NULL, + NULL, "inherit", "inside", list(NULL, NULL, "black", 0.8, NULL, NULL, NULL, NULL, c(6, 6, 6, 6), NULL, FALSE), NULL, NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, NULL, -90, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, NULL, 90, NULL, NULL, NULL, TRUE), NULL, 2.75, 2.75)) - [ FAIL 1 | WARN 15 | SKIP 0 | PASS 108 ] + [ FAIL 1 | WARN 14 | SKIP 0 | PASS 108 ] Error: Test failures Execution halted ``` @@ -10602,9 +21106,9 @@ Run `revdepcheck::cloud_details(, "tsnet")` for more info * checking installed package size ... NOTE ``` - installed size is 206.1Mb + installed size is 163.0Mb sub-directories of 1Mb or more: - libs 204.6Mb + libs 162.0Mb ``` * checking for GNU extensions in Makefiles ... NOTE @@ -10641,180 +21145,521 @@ Run `revdepcheck::cloud_details(, "umiAnalyzer")` for more info > > library(umiAnalyzer) ... + > > main = system.file('extdata', package = 'umiAnalyzer') > samples <- list.dirs(path = main, full.names = FALSE, recursive = FALSE) > simsen <- createUmiExperiment(experimentName = 'example',mainDir = main,sampleNames = samples) > simsen <- filterUmiObject(simsen) > > amplicon_plot <- AmpliconPlot(simsen) - Error in compute_geom_2(..., self = self) : - argument "theme" is missing, with no default - Calls: AmpliconPlot ... use_defaults -> eval_from_theme -> %||% -> calc_element + Error in pm[[2]] : subscript out of bounds + Calls: AmpliconPlot -> -> ggplotly.ggplot -> gg2list Execution halted ``` -# UniprotR +# UnalR
-* Version: 2.4.0 -* GitHub: https://github.com/Proteomicslab57357/UniprotR -* Source code: https://github.com/cran/UniprotR -* Date/Publication: 2024-03-05 15:10:02 UTC -* Number of recursive dependencies: 192 +* Version: 1.0.0 +* GitHub: https://github.com/estadisticaun/UnalR +* Source code: https://github.com/cran/UnalR +* Date/Publication: 2024-05-25 17:20:05 UTC +* Number of recursive dependencies: 168 -Run `revdepcheck::cloud_details(, "UniprotR")` for more info +Run `revdepcheck::cloud_details(, "UnalR")` for more info
## Newly broken -* checking whether package ‘UniprotR’ can be installed ... WARNING +* checking examples ... ERROR ``` - Found the following significant warnings: - Warning: replacing previous import ‘ggplot2::ggpar’ by ‘ggpubr::ggpar’ when loading ‘UniprotR’ - See ‘/tmp/workdir/UniprotR/new/UniprotR.Rcheck/00install.out’ for details. + Running examples in ‘UnalR-Ex.R’ failed + The error most likely occurred in: + + > ### Name: Plot.Barras + > ### Title: Cree un gráfico de barras que muestre la información de forma + > ### horizontal o vertical, para variables nominales u ordinales con dos + > ### diferentes paquetes + > ### Aliases: Plot.Barras + > + > ### ** Examples + ... + 1. └─(if (getRversion() >= "3.4") withAutoprint else force)(...) + 2. └─base::source(...) + 3. ├─base::print(yy$value) + 4. └─ggplot2:::print.ggplot(yy$value) + 5. ├─ggplot2::ggplot_gtable(data) + 6. └─ggplot2:::ggplot_gtable.ggplot_built(data) + 7. └─ggplot2::calc_element("plot.margin", theme) + 8. └─cli::cli_abort(...) + 9. └─rlang::abort(...) + Execution halted + ``` + +## In both + +* checking installed package size ... NOTE + ``` + installed size is 7.0Mb + sub-directories of 1Mb or more: + R 2.3Mb + data 2.0Mb + help 2.6Mb + ``` + +* checking data for non-ASCII characters ... NOTE + ``` + Note: found 312859 marked UTF-8 strings ``` -# VALERIE +# UpSetR
-* Version: 1.1.0 -* GitHub: NA -* Source code: https://github.com/cran/VALERIE -* Date/Publication: 2020-07-10 10:20:13 UTC -* Number of recursive dependencies: 133 +* Version: 1.4.0 +* GitHub: https://github.com/hms-dbmi/UpSetR +* Source code: https://github.com/cran/UpSetR +* Date/Publication: 2019-05-22 23:30:03 UTC +* Number of recursive dependencies: 36 -Run `revdepcheck::cloud_details(, "VALERIE")` for more info +Run `revdepcheck::cloud_details(, "UpSetR")` for more info
## Newly broken -* checking whether package ‘VALERIE’ can be installed ... WARNING +* checking examples ... ERROR ``` - Found the following significant warnings: - Warning: replacing previous import ‘ggplot2::ggpar’ by ‘ggpubr::ggpar’ when loading ‘VALERIE’ - See ‘/tmp/workdir/VALERIE/new/VALERIE.Rcheck/00install.out’ for details. + Running examples in ‘UpSetR-Ex.R’ failed + The error most likely occurred in: + + > ### Name: upset + > ### Title: UpSetR Plot + > ### Aliases: upset + > + > ### ** Examples + > + > movies <- read.csv( system.file("extdata", "movies.csv", package = "UpSetR"), header=TRUE, sep=";" ) + ... + 2. ├─base::suppressMessages(...) + 3. │ └─base::withCallingHandlers(...) + 4. └─UpSetR:::Make_main_bar(...) + 5. └─ggplot2::ggplotGrob(Main_bar_plot) + 6. ├─ggplot2::ggplot_gtable(ggplot_build(x)) + 7. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) + 8. └─ggplot2::calc_element("plot.margin", theme) + 9. └─cli::cli_abort(...) + 10. └─rlang::abort(...) + Execution halted ``` -## Newly fixed - -* checking re-building of vignette outputs ... NOTE +* checking running R code from vignettes ... ERROR ``` - Error(s) in re-building vignettes: - --- re-building ‘VALERIE.Rmd’ using rmarkdown - Trying to upgrade TinyTeX automatically now... - If reinstallation fails, try install_tinytex() again. Then install the following packages: + Errors in running code in vignettes: + when running code in ‘attribute.plots.Rmd’ + ... - tinytex::tlmgr_install(c("amscls", "amsfonts", "amsmath", "atbegshi", "atveryend", "auxhook", "babel", "bibtex", "bigintcalc", "bitset", "booktabs", "cm", "ctablestack", "dehyph", "dvipdfmx", "dvips", "ec", "epstopdf-pkg", "etex", "etexcmds", "etoolbox", "euenc", "everyshi", "fancyvrb", "filehook", "firstaid", "float", "fontspec", "framed", "geometry", "gettitlestring", "glyphlist", "graphics", "graphics-cfg", "graphics-def", "helvetic", "hycolor", "hyperref", "hyph-utf8", "hyphen-base", "iftex", "inconsolata", "infwarerr", "intcalc", "knuth-lib", "kpathsea", "kvdefinekeys", "kvoptions", "kvsetkeys", "l3backend", "l3kernel", "l3packages", "latex", "latex-amsmath-dev", "latex-bin", "latex-fonts", "latex-tools-dev", "latexconfig", "latexmk", "letltxmacro", "lm", "lm-math", "ltxcmds", "lua-alt-getopt", "lua-uni-algos", "luahbtex", "lualatex-math", "lualibs", "luaotfload", "luatex", "luatexbase", "mdwtools", "metafont", "mfware", "modes", "natbib", "pdfescape", "pdftex", "pdftexcmds", "plain", "psnfss", "refcount", "rerunfilecheck", "scheme-infraonly", "selnolig", "stringenc", "symbol", "tex", "tex-ini-files", "texlive-scripts", "texlive.infra", "times", "tipa", "tools", "unicode-data", "unicode-math", "uniquecounter", "url", "xcolor", "xetex", "xetexconfig", "xkeyval", "xunicode", "zapfding")) + > movies <- read.csv(system.file("extdata", "movies.csv", + + package = "UpSetR"), header = T, sep = ";") - The directory /opt/TinyTeX/texmf-local is not empty. It will be backed up to /tmp/RtmpbQSeNG/file20363012f5cc and restored later. + > upset(movies, main.bar.color = "black", queries = list(list(query = intersects, + + params = list("Drama"), active = T)), attribute.plots = list( .... [TRUNCATED] - tlmgr: no auxiliary texmf trees defined, so nothing removed ... + + assign = 20 .... [TRUNCATED] - Error: processing vignette 'VALERIE.Rmd' failed with diagnostics: - LaTeX failed to compile /tmp/workdir/VALERIE/old/VALERIE.Rcheck/vign_test/VALERIE/vignettes/VALERIE.tex. See https://yihui.org/tinytex/r/#debugging for debugging tips. See VALERIE.log for more info. - --- failed re-building ‘VALERIE.Rmd’ + When sourcing ‘set.metadata.plots.R’: + Error: Theme element `plot.margin` must have class . + Execution halted - SUMMARY: processing the following file failed: - ‘VALERIE.Rmd’ + ‘attribute.plots.Rmd’ using ‘UTF-8’... failed + ‘basic.usage.Rmd’ using ‘UTF-8’... failed + ‘queries.Rmd’ using ‘UTF-8’... failed + ‘set.metadata.plots.Rmd’ using ‘UTF-8’... failed + ``` + +## In both + +* checking installed package size ... NOTE + ``` + installed size is 8.1Mb + sub-directories of 1Mb or more: + doc 7.6Mb + ``` + +* checking LazyData ... NOTE + ``` + 'LazyData' is specified without a 'data' directory + ``` + +# vDiveR + +
+ +* Version: 1.2.1 +* GitHub: NA +* Source code: https://github.com/cran/vDiveR +* Date/Publication: 2024-01-09 20:20:02 UTC +* Number of recursive dependencies: 131 + +Run `revdepcheck::cloud_details(, "vDiveR")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘vDiveR-Ex.R’ failed + The error most likely occurred in: - Error: Vignette re-building failed. + > ### Name: plot_conservationLevel + > ### Title: Conservation Levels Distribution Plot + > ### Aliases: plot_conservationLevel + > + > ### ** Examples + > + > plot_conservationLevel(proteins_1host, conservation_label = 1,alpha=0.8, base_size = 15) + ... + Backtrace: + ▆ + 1. ├─base (local) ``(x) + 2. └─ggplot2:::print.ggplot(x) + 3. ├─ggplot2::ggplot_gtable(data) + 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) + 5. └─ggplot2::calc_element("plot.margin", theme) + 6. └─cli::cli_abort(...) + 7. └─rlang::abort(...) Execution halted ``` ## In both -* checking installed package size ... NOTE +* checking dependencies in R code ... NOTE + ``` + Namespaces in Imports field not imported from: + ‘DT’ ‘maps’ ‘readr’ + All declared Imports should be used. + ``` + +# VDSM + +
+ +* Version: 0.1.1 +* GitHub: NA +* Source code: https://github.com/cran/VDSM +* Date/Publication: 2021-04-16 09:00:02 UTC +* Number of recursive dependencies: 57 + +Run `revdepcheck::cloud_details(, "VDSM")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘VDSM-Ex.R’ failed + The error most likely occurred in: + + > ### Name: Gplot + > ### Title: Gplot. + > ### Aliases: Gplot + > + > ### ** Examples + > + > data(exampleX) + ... + ▆ + 1. └─VDSM::Gplot(X, f, p) + 2. ├─base::suppressWarnings(ggplot_gtable(ggplot_build(p1.common.y))) + 3. │ └─base::withCallingHandlers(...) + 4. ├─ggplot2::ggplot_gtable(ggplot_build(p1.common.y)) + 5. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(p1.common.y)) + 6. └─ggplot2::calc_element("plot.margin", theme) + 7. └─cli::cli_abort(...) + 8. └─rlang::abort(...) + Execution halted + ``` + +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(VDSM) + > + > test_check("VDSM") + [ FAIL 1 | WARN 1 | SKIP 0 | PASS 0 ] + + ══ Failed tests ════════════════════════════════════════════════════════════════ + ... + 3. │ └─base::withCallingHandlers(...) + 4. ├─ggplot2::ggplot_gtable(ggplot_build(p1.common.y)) + 5. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(p1.common.y)) + 6. └─ggplot2::calc_element("plot.margin", theme) + 7. └─cli::cli_abort(...) + 8. └─rlang::abort(...) + + [ FAIL 1 | WARN 1 | SKIP 0 | PASS 0 ] + Error: Test failures + Execution halted + ``` + +# virtualPollen + +
+ +* Version: 1.0.1 +* GitHub: https://github.com/BlasBenito/virtualPollen +* Source code: https://github.com/cran/virtualPollen +* Date/Publication: 2022-02-13 13:00:02 UTC +* Number of recursive dependencies: 122 + +Run `revdepcheck::cloud_details(, "virtualPollen")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘virtualPollen-Ex.R’ failed + The error most likely occurred in: + + > ### Name: simulateDriverS + > ### Title: Generates drivers for 'simulatePopulation'. + > ### Aliases: simulateDriverS + > + > ### ** Examples + > + > + ... + 8. └─cowplot:::as_gtable.default(x) + 9. ├─cowplot::as_grob(plot) + 10. └─cowplot:::as_grob.ggplot(plot) + 11. └─ggplot2::ggplotGrob(plot) + 12. ├─ggplot2::ggplot_gtable(ggplot_build(x)) + 13. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) + 14. └─ggplot2::calc_element("plot.margin", theme) + 15. └─cli::cli_abort(...) + 16. └─rlang::abort(...) + Execution halted + ``` + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘using_virtualPollen.Rmd’ + ... + + > p7 <- ggplot(data = acfToDf(moves.100, 200, 50), aes(x = lag, + + y = acf)) + geom_hline(aes(yintercept = 0)) + geom_hline(aes(yintercept = ci.ma .... [TRUNCATED] + + > plot_grid(p4, p5, p6, p7, labels = c("a", "b", "c", + + "d"), align = "v", nrow = 2) + + When sourcing ‘using_virtualPollen.R’: + Error: Theme element `plot.margin` must have class . + Execution halted + + ‘using_virtualPollen.Rmd’ using ‘UTF-8’... failed + ``` + +* checking re-building of vignette outputs ... NOTE ``` - installed size is 9.6Mb - sub-directories of 1Mb or more: - extdata 8.7Mb + Error(s) in re-building vignettes: + --- re-building ‘using_virtualPollen.Rmd’ using rmarkdown ``` -# VancouvR +# viscomp
-* Version: 0.1.8 -* GitHub: https://github.com/mountainMath/VancouvR -* Source code: https://github.com/cran/VancouvR -* Date/Publication: 2024-04-18 16:12:35 UTC -* Number of recursive dependencies: 91 +* Version: 1.0.0 +* GitHub: https://github.com/georgiosseitidis/viscomp +* Source code: https://github.com/cran/viscomp +* Date/Publication: 2023-01-16 09:50:02 UTC +* Number of recursive dependencies: 149 -Run `revdepcheck::cloud_details(, "VancouvR")` for more info +Run `revdepcheck::cloud_details(, "viscomp")` for more info
## Newly broken -* checking running R code from vignettes ... ERROR +* checking examples ... ERROR ``` - Errors in running code in vignettes: - when running code in ‘Demo.Rmd’ - ... - + labs(title .... [TRUNCATED] - - When sourcing ‘Demo.R’: - Error: Summary operations are not defined for quosures. Do you need to unquote - the quosure? - - # Bad: min(myquosure) + Running examples in ‘viscomp-Ex.R’ failed + The error most likely occurred in: - # Good: min(!!myquosure) + > ### Name: loccos + > ### Title: Leaving One Component Combination Out Scatter plot + > ### Aliases: loccos + > + > ### ** Examples + > + > data(nmaMACE) + ... + ▆ + 1. └─viscomp::loccos(model = nmaMACE, combination = c("B")) + 2. └─ggExtra::ggMarginal(p, type = "histogram", fill = histogram.color) + 3. └─ggplot2::ggplotGrob(scatP) + 4. ├─ggplot2::ggplot_gtable(ggplot_build(x)) + 5. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) + 6. └─ggplot2::calc_element("plot.margin", theme) + 7. └─cli::cli_abort(...) + 8. └─rlang::abort(...) Execution halted - - ‘Demo.Rmd’ using ‘UTF-8’... failed - ‘Isolines.Rmd’ using ‘UTF-8’... OK ``` -# vannstats +# visR
-* Version: 1.3.4.14 -* GitHub: NA -* Source code: https://github.com/cran/vannstats -* Date/Publication: 2023-04-15 04:30:02 UTC -* Number of recursive dependencies: 101 +* Version: 0.4.1 +* GitHub: https://github.com/openpharma/visR +* Source code: https://github.com/cran/visR +* Date/Publication: 2024-03-15 21:50:02 UTC +* Number of recursive dependencies: 148 -Run `revdepcheck::cloud_details(, "vannstats")` for more info +Run `revdepcheck::cloud_details(, "visR")` for more info
## Newly broken -* checking whether package ‘vannstats’ can be installed ... WARNING +* checking examples ... ERROR ``` - Found the following significant warnings: - Warning: replacing previous import ‘ggplot2::ggpar’ by ‘ggpubr::ggpar’ when loading ‘vannstats’ - See ‘/tmp/workdir/vannstats/new/vannstats.Rcheck/00install.out’ for details. + Running examples in ‘visR-Ex.R’ failed + The error most likely occurred in: + + > ### Name: add_risktable + > ### Title: Add risk tables to visR plots through an S3 method + > ### Aliases: add_risktable add_risktable.ggsurvfit + > ### add_risktable.ggtidycuminc + > + > ### ** Examples + > + ... + 4. │ └─gglist %>% align_plots() + 5. └─visR::align_plots(.) + 6. └─base::lapply(pltlist, ggplot2::ggplotGrob) + 7. └─ggplot2 (local) FUN(X[[i]], ...) + 8. ├─ggplot2::ggplot_gtable(ggplot_build(x)) + 9. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) + 10. └─ggplot2::calc_element("plot.margin", theme) + 11. └─cli::cli_abort(...) + 12. └─rlang::abort(...) + Execution halted + ``` + +* checking tests ... ERROR + ``` + Running ‘spelling.R’ + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(visR) + > library(vdiffr) + > library(survival) + > + > test_check("visR") + ... + 10. └─ggplot2::calc_element("plot.margin", theme) + 11. └─cli::cli_abort(...) + 12. └─rlang::abort(...) + + [ FAIL 14 | WARN 28 | SKIP 24 | PASS 991 ] + Error: Test failures + In addition: Warning message: + In .Internal(delayedAssign(x, substitute(value), eval.env, assign.env)) : + closing unused connection 4 (https://raw.githubusercontent.com/vntkumar8/covid-survival/main/data/final.csv) + Execution halted + ``` + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘CDISC_ADaM.Rmd’ + ... + + + + > visr(survfit_object) %>% visR::add_CI() %>% visR::add_risktable() + Warning: `visr.survfit()` was deprecated in visR 0.4.0. + ℹ Please use `ggsurvfit::ggsurvfit()` instead. + + ... + + size = 2) %>% visR::add_risktable() + + When sourcing ‘Time_to_event_analysis.R’: + Error: Theme element `plot.margin` must have class . + Execution halted + + ‘CDISC_ADaM.Rmd’ using ‘UTF-8’... failed + ‘Consort_flow_diagram.Rmd’ using ‘UTF-8’... OK + ‘Styling_KM_plots.Rmd’ using ‘UTF-8’... OK + ‘Time_to_event_analysis.Rmd’ using ‘UTF-8’... failed + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘CDISC_ADaM.Rmd’ using rmarkdown + + Quitting from lines 86-90 [km_plot_1] (CDISC_ADaM.Rmd) + Error: processing vignette 'CDISC_ADaM.Rmd' failed with diagnostics: + Theme element `plot.margin` must have class . + --- failed re-building ‘CDISC_ADaM.Rmd’ + + --- re-building ‘Consort_flow_diagram.Rmd’ using rmarkdown ``` -# vici +# vivainsights
-* Version: 0.7.3 -* GitHub: https://github.com/sistm/vici -* Source code: https://github.com/cran/vici -* Date/Publication: 2024-02-02 16:20:02 UTC -* Number of recursive dependencies: 113 +* Version: 0.5.2 +* GitHub: https://github.com/microsoft/vivainsights +* Source code: https://github.com/cran/vivainsights +* Date/Publication: 2024-03-14 17:40:02 UTC +* Number of recursive dependencies: 114 -Run `revdepcheck::cloud_details(, "vici")` for more info +Run `revdepcheck::cloud_details(, "vivainsights")` for more info
## Newly broken -* checking whether package ‘vici’ can be installed ... WARNING +* checking examples ... ERROR ``` - Found the following significant warnings: - Warning: replacing previous import ‘ggplot2::ggpar’ by ‘ggpubr::ggpar’ when loading ‘vici’ - See ‘/tmp/workdir/vici/new/vici.Rcheck/00install.out’ for details. + Running examples in ‘vivainsights-Ex.R’ failed + The error most likely occurred in: + + > ### Name: tm_freq + > ### Title: Perform a Word or Ngram Frequency Analysis and return a Circular + > ### Bar Plot + > ### Aliases: tm_freq + > + > ### ** Examples + > + ... + Backtrace: + ▆ + 1. ├─base (local) ``(x) + 2. └─ggplot2:::print.ggplot(x) + 3. ├─ggplot2::ggplot_gtable(data) + 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) + 5. └─ggplot2::calc_element("plot.margin", theme) + 6. └─cli::cli_abort(...) + 7. └─rlang::abort(...) + Execution halted ``` # vivaldi @@ -10846,15 +21691,15 @@ Run `revdepcheck::cloud_details(, "vivaldi")` for more info > > # Example 1: ... + 6 m2 PB1 234 G A minor 0.010 0.990 7 m2 PB1 266 G A minor 0.022 0.978 8 m2 PB2 199 A G minor 0.043 0.957 9 m2 PB2 88 G A major 0.055 0.945 10 m2 PB2 180 C T minor 0.011 0.989 > > snv_location(df) - Error in compute_geom_2(..., self = self) : - argument "theme" is missing, with no default - Calls: snv_location ... use_defaults -> eval_from_theme -> %||% -> calc_element + Error in pm[[2]] : subscript out of bounds + Calls: snv_location -> -> ggplotly.ggplot -> gg2list Execution halted ``` @@ -10875,8 +21720,8 @@ Run `revdepcheck::cloud_details(, "vivaldi")` for more info ══ Failed tests ════════════════════════════════════════════════════════════════ ── Failure ('test-snv_location.R:13:3'): expect output ───────────────────────── Expected `snv_location(df)` to run without any errors. - i Actually got a with text: - argument "theme" is missing, with no default + i Actually got a with text: + subscript out of bounds [ FAIL 1 | WARN 2 | SKIP 0 | PASS 29 ] Error: Test failures @@ -10896,7 +21741,7 @@ Run `revdepcheck::cloud_details(, "vivaldi")` for more info > snv_location(DF_filt_SNVs) When sourcing ‘vignette.R’: - Error: argument "theme" is missing, with no default + Error: subscript out of bounds Execution halted ‘vignette.Rmd’ using ‘UTF-8’... failed @@ -10926,7 +21771,7 @@ Run `revdepcheck::cloud_details(, "vivaldi")` for more info * GitHub: NA * Source code: https://github.com/cran/vvshiny * Date/Publication: 2023-07-19 15:30:02 UTC -* Number of recursive dependencies: 132 +* Number of recursive dependencies: 131 Run `revdepcheck::cloud_details(, "vvshiny")` for more info @@ -10934,31 +21779,6 @@ Run `revdepcheck::cloud_details(, "vvshiny")` for more info ## Newly broken -* checking examples ... ERROR - ``` - Running examples in ‘vvshiny-Ex.R’ failed - The error most likely occurred in: - - > ### Name: ggplotly_with_legend - > ### Title: Make ggplotly and add legend with color as title - > ### Aliases: ggplotly_with_legend - > - > ### ** Examples - > - > df <- data.frame(x_var = rnorm(100), - ... - > ggplot_instellingen <- ggplot2::geom_point() - > scale_y <- ggplot2::scale_y_continuous() - > plot <- basic_plot(df, "x_var", "y_var", "color_var", xlab_setting, - + ylab_setting, ggplot_instellingen, "none", scale_y) - > mapping_table <- list(color_var = "user friendly name var") - > plotly_object <- ggplotly_with_legend(plot, "color_var", mapping_table) - Error in compute_geom_2(..., self = self) : - argument "theme" is missing, with no default - Calls: ggplotly_with_legend ... use_defaults -> eval_from_theme -> %||% -> calc_element - Execution halted - ``` - * checking tests ... ERROR ``` Running ‘testthat.R’ @@ -10972,79 +21792,78 @@ Run `revdepcheck::cloud_details(, "vvshiny")` for more info > # * https://r-pkgs.org/testing-design.html#sec-tests-files-overview > # * https://testthat.r-lib.org/articles/special-files.html ... - 11. │ └─self$geom$use_defaults(data, self$aes_params, modifiers, theme = theme) - 12. │ └─ggplot2 (local) use_defaults(..., self = self) - 13. │ └─ggplot2:::eval_from_theme(default_aes, theme) - 14. │ ├─calc_element("geom", theme) %||% .default_geom_element - 15. │ └─ggplot2::calc_element("geom", theme) - 16. └─plotly::layout(...) + 1. ├─vvshiny::ggplotly_with_legend(p, color = "grp", mapping_table = list(grp = "Group")) at test-ggplotly_with_legend.R:15:3 + 2. │ ├─plotly::ggplotly(plot) %>% ... + 3. │ ├─plotly::ggplotly(plot) + 4. │ └─plotly:::ggplotly.ggplot(plot) + 5. │ └─plotly::gg2list(...) + 6. └─plotly::layout(...) [ FAIL 1 | WARN 2 | SKIP 0 | PASS 60 ] Error: Test failures Execution halted ``` -# waywiser +# WASP
-* Version: 0.5.1 -* GitHub: https://github.com/ropensci/waywiser -* Source code: https://github.com/cran/waywiser -* Date/Publication: 2023-10-31 15:50:02 UTC -* Number of recursive dependencies: 172 +* Version: 1.4.3 +* GitHub: https://github.com/zejiang-unsw/WASP +* Source code: https://github.com/cran/WASP +* Date/Publication: 2022-08-22 07:50:24 UTC +* Number of recursive dependencies: 153 -Run `revdepcheck::cloud_details(, "waywiser")` for more info +Run `revdepcheck::cloud_details(, "WASP")` for more info
## Newly broken -* checking running R code from vignettes ... ERROR +* checking examples ... ERROR ``` - Errors in running code in vignettes: - when running code in ‘residual-autocorrelation.Rmd’ - ... - + weights)) %>% sf::st_ .... [TRUNCATED] - - When sourcing ‘residual-autocorrelation.R’: - Error: Summary operations are not defined for quosures. Do you need to unquote - the quosure? - - # Bad: min(myquosure) + Running examples in ‘WASP-Ex.R’ failed + The error most likely occurred in: - # Good: min(!!myquosure) + > ### Name: fig.dwt.vt + > ### Title: Plot function: Variance structure before and after variance + > ### transformation + > ### Aliases: fig.dwt.vt + > + > ### ** Examples + > + ... + Backtrace: + ▆ + 1. ├─base (local) ``(x) + 2. └─ggplot2:::print.ggplot(x) + 3. ├─ggplot2::ggplot_gtable(data) + 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) + 5. └─ggplot2::calc_element("plot.margin", theme) + 6. └─cli::cli_abort(...) + 7. └─rlang::abort(...) Execution halted - - ‘multi-scale-assessment.Rmd’ using ‘UTF-8’... OK - ‘residual-autocorrelation.Rmd’ using ‘UTF-8’... failed - ‘waywiser.Rmd’ using ‘UTF-8’... OK - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘multi-scale-assessment.Rmd’ using rmarkdown ``` ## In both -* checking data for non-ASCII characters ... NOTE +* checking dependencies in R code ... NOTE ``` - Note: found 1 marked UTF-8 string + Namespace in Imports field not imported from: ‘rlang’ + All declared Imports should be used. ``` -# wildlifeDI +# Wats
-* Version: 1.0.0 -* GitHub: https://github.com/jedalong/wildlifeDI -* Source code: https://github.com/cran/wildlifeDI -* Date/Publication: 2024-03-22 19:30:02 UTC -* Number of recursive dependencies: 84 +* Version: 1.0.1 +* GitHub: https://github.com/OuhscBbmc/Wats +* Source code: https://github.com/cran/Wats +* Date/Publication: 2023-03-10 22:50:05 UTC +* Number of recursive dependencies: 122 -Run `revdepcheck::cloud_details(, "wildlifeDI")` for more info +Run `revdepcheck::cloud_details(, "Wats")` for more info
@@ -11053,39 +21872,94 @@ Run `revdepcheck::cloud_details(, "wildlifeDI")` for more info * checking running R code from vignettes ... ERROR ``` Errors in running code in vignettes: - when running code in ‘wildlifeDI-vignette-contact_analysis.Rmd’ + when running code in ‘mbr-figures.Rmd’ ... - GDAL Error 1: PROJ: proj_as_wkt: DatumEnsemble can only be exported to WKT2:2019 + > grid::grid.newpage() - When sourcing ‘wildlifeDI-vignette-contact_analysis.R’: - Error: Base operators are not defined for quosures. Do you need to unquote the - quosure? + > grid::pushViewport(grid::viewport(layout = grid::grid.layout(3, + + 1))) - # Bad: myquosure * rhs + > print(top_panel, vp = vp_layout(1, 1)) - # Good: !!myquosure * rhs + When sourcing ‘mbr-figures.R’: + Error: Theme element `plot.margin` must have class . Execution halted - ‘wildlifeDI-vignette-contact_analysis.Rmd’ using ‘UTF-8’... failed - ‘wildlifeDI-vignette.rmd’ using ‘UTF-8’... OK + ‘mbr-figures.Rmd’ using ‘UTF-8’... failed ``` * checking re-building of vignette outputs ... NOTE ``` Error(s) in re-building vignettes: - --- re-building ‘wildlifeDI-vignette-contact_analysis.Rmd’ using rmarkdown - - Quitting from lines at lines 53-55 [unnamed-chunk-3] (wildlifeDI-vignette-contact_analysis.Rmd) - Error: processing vignette 'wildlifeDI-vignette-contact_analysis.Rmd' failed with diagnostics: - Base operators are not defined for quosures. Do you need to unquote the - quosure? + --- re-building ‘mbr-figures.Rmd’ using rmarkdown + ``` + +# whomds + +
+ +* Version: 1.1.1 +* GitHub: https://github.com/lindsayevanslee/whomds +* Source code: https://github.com/cran/whomds +* Date/Publication: 2023-09-08 04:30:02 UTC +* Number of recursive dependencies: 123 + +Run `revdepcheck::cloud_details(, "whomds")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘whomds-Ex.R’ failed + The error most likely occurred in: - # Bad: myquosure * rhs + > ### Name: fig_density + > ### Title: Plot a density of a score + > ### Aliases: fig_density + > + > ### ** Examples + > + > fig_density(df_adults, score = "disability_score", cutoffs = c(19.1, 34.4, 49.6), + ... + Backtrace: + ▆ + 1. ├─base (local) ``(x) + 2. └─ggplot2:::print.ggplot(x) + 3. ├─ggplot2::ggplot_gtable(data) + 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) + 5. └─ggplot2::calc_element("plot.margin", theme) + 6. └─cli::cli_abort(...) + 7. └─rlang::abort(...) + Execution halted + ``` + +## In both + +* checking running R code from vignettes ... WARNING + ``` + Errors in running code in vignettes: + when running code in ‘c2_getting_started_EN.Rmd’ + ... + + out.width = "80%", fig.align = "center", collapse = TRUE, + + comment = "#> ..." ... [TRUNCATED] - # Good: !!myquosure * rhs - --- failed re-building ‘wildlifeDI-vignette-contact_analysis.Rmd’ + > install.packages("whomds") + Installing package into ‘/tmp/workdir/whomds/new/whomds.Rcheck’ + (as ‘lib’ is unspecified) - --- re-building ‘wildlifeDI-vignette.rmd’ using rmarkdown + ... + ‘c2_getting_started_EN.Rmd’ using ‘UTF-8’... failed + ‘c2_getting_started_ES.Rmd’ using ‘UTF-8’... failed + ‘c3_rasch_adults_EN.Rmd’ using ‘UTF-8’... failed + ‘c3_rasch_adults_ES.Rmd’ using ‘UTF-8’... failed + ‘c4_rasch_children_EN.Rmd’ using ‘UTF-8’... failed + ‘c4_rasch_children_ES.Rmd’ using ‘UTF-8’... failed + ‘c5_best_practices_EN.Rmd’ using ‘UTF-8’... OK + ‘c5_best_practices_ES.Rmd’ using ‘UTF-8’... OK + ‘c6_after_rasch_EN.Rmd’ using ‘UTF-8’... failed + ‘c6_after_rasch_ES.Rmd’ using ‘UTF-8’... failed ``` # wilson @@ -11096,7 +21970,7 @@ Run `revdepcheck::cloud_details(, "wildlifeDI")` for more info * GitHub: https://github.com/loosolab/wilson * Source code: https://github.com/cran/wilson * Date/Publication: 2021-04-19 09:40:02 UTC -* Number of recursive dependencies: 200 +* Number of recursive dependencies: 199 Run `revdepcheck::cloud_details(, "wilson")` for more info @@ -11117,29 +21991,29 @@ Run `revdepcheck::cloud_details(, "wilson")` for more info The following object is masked from 'package:stats': ... - 9. └─ggplot2 (local) compute_geom_2(..., self = self) - 10. └─self$geom$use_defaults(data, self$aes_params, modifiers, theme = theme) - 11. └─ggplot2 (local) use_defaults(..., self = self) - 12. └─ggplot2:::eval_from_theme(default_aes, theme) - 13. ├─calc_element("geom", theme) %||% .default_geom_element - 14. └─ggplot2::calc_element("geom", theme) + Backtrace: + ▆ + 1. └─wilson::create_geneview(...) at test-interactive-plots.R:21:3 + 2. ├─plotly::ggplotly(...) + 3. └─plotly:::ggplotly.ggplot(...) + 4. └─plotly::gg2list(...) [ FAIL 3 | WARN 11 | SKIP 1 | PASS 74 ] Error: Test failures Execution halted ``` -# WorldMapR +# WVPlots
-* Version: 0.1.1 -* GitHub: https://github.com/Luigi-Annic/WorldMapR -* Source code: https://github.com/cran/WorldMapR -* Date/Publication: 2024-04-22 19:30:07 UTC -* Number of recursive dependencies: 92 +* Version: 1.3.8 +* GitHub: https://github.com/WinVector/WVPlots +* Source code: https://github.com/cran/WVPlots +* Date/Publication: 2024-04-22 20:40:07 UTC +* Number of recursive dependencies: 78 -Run `revdepcheck::cloud_details(, "WorldMapR")` for more info +Run `revdepcheck::cloud_details(, "WVPlots")` for more info
@@ -11147,60 +22021,83 @@ Run `revdepcheck::cloud_details(, "WorldMapR")` for more info * checking examples ... ERROR ``` - Running examples in ‘WorldMapR-Ex.R’ failed + Running examples in ‘WVPlots-Ex.R’ failed The error most likely occurred in: - > ### Name: worldplotCat - > ### Title: worldplotCat - > ### Aliases: worldplotCat + > ### Name: ScatterHist + > ### Title: Plot a scatter plot with marginals. + > ### Aliases: ScatterHist > > ### ** Examples > - > data(testdata1b) + > ... - 16. └─ggplot2 (local) FUN(X[[i]], ...) - 17. └─base::lapply(...) - 18. └─ggplot2 (local) FUN(X[[i]], ...) - 19. └─g$draw_key(data, g$params, key_size) - 20. └─ggplot2 (local) draw_key(...) - 21. └─ggplot2::draw_key_polygon(data, params, size) - 22. └─rlang:::Summary.quosure(from_theme(thin), 1.27, na.rm = FALSE) - 23. └─rlang:::abort_quosure_op("Summary", .Generic) - 24. └─rlang::abort(...) + 2. └─gridExtra::grid.arrange(...) + 3. └─gridExtra::arrangeGrob(...) + 4. └─base::lapply(grobs[toconv], ggplot2::ggplotGrob) + 5. └─ggplot2 (local) FUN(X[[i]], ...) + 6. ├─ggplot2::ggplot_gtable(ggplot_build(x)) + 7. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) + 8. └─ggplot2::calc_element("plot.margin", theme) + 9. └─cli::cli_abort(...) + 10. └─rlang::abort(...) Execution halted ``` * checking tests ... ERROR ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. + Running ‘tinytest.R’ + Running the tests in ‘tests/tinytest.R’ failed. Complete output: - > # This file is part of the standard setup for testthat. - > # It is recommended that you do not modify it. - > # - > # Where should you do additional test configuration? - > # Learn more about the roles of various files in: - > # * https://r-pkgs.org/testing-design.html#sec-tests-files-overview - > # * https://testthat.r-lib.org/articles/special-files.html + > + > if (requireNamespace("tinytest", quietly=TRUE) ) { + + if (requireNamespace('data.table', quietly = TRUE)) { + + # don't multi-thread during CRAN checks + + data.table::setDTthreads(1) + + } + + tinytest::test_package("WVPlots") ... - 19. └─g$draw_key(data, g$params, key_size) - 20. └─ggplot2 (local) draw_key(...) - 21. └─ggplot2::draw_key_polygon(data, params, size) - 22. └─rlang:::Summary.quosure(from_theme(thin), 1.27, na.rm = FALSE) - 23. └─rlang:::abort_quosure_op("Summary", .Generic) - 24. └─rlang::abort(...) - - [ FAIL 2 | WARN 1 | SKIP 0 | PASS 0 ] - Error: Test failures + 10. └─gridExtra::grid.arrange(...) + 11. └─gridExtra::arrangeGrob(...) + 12. └─base::lapply(grobs[toconv], ggplot2::ggplotGrob) + 13. └─ggplot2 (local) FUN(X[[i]], ...) + 14. ├─ggplot2::ggplot_gtable(ggplot_build(x)) + 15. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) + 16. └─ggplot2::calc_element("plot.margin", theme) + 17. └─cli::cli_abort(...) + 18. └─rlang::abort(...) Execution halted ``` -## In both +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘WVPlots_concept.Rmd’ + ... + > frm$absY <- abs(frm$y) + + > frm$posY = frm$y > 0 + + > WVPlots::ScatterHist(frm, "x", "y", smoothmethod = "lm", + + title = "Example Linear Fit") + + ... + > frm$posY = frm$y > 0 + + > WVPlots::ScatterHist(frm, "x", "y", title = "Example Fit") + + When sourcing ‘WVPlots_examples.R’: + Error: Theme element `plot.margin` must have class . + Execution halted + + ‘WVPlots_concept.Rmd’ using ‘UTF-8’... failed + ‘WVPlots_examples.Rmd’ using ‘UTF-8’... failed + ``` -* checking data for non-ASCII characters ... NOTE +* checking re-building of vignette outputs ... NOTE ``` - Note: found 4 marked Latin-1 strings - Note: found 5 marked UTF-8 strings + Error(s) in re-building vignettes: + --- re-building ‘WVPlots_concept.Rmd’ using rmarkdown ``` # xaringanthemer @@ -11254,7 +22151,7 @@ Run `revdepcheck::cloud_details(, "xaringanthemer")` for more info Warning in file(con, "r") : cannot open file './../man/fragments/_quick-intro.Rmd': No such file or directory - Quitting from lines at lines 43-43 [unnamed-chunk-2] (./../man/fragments/_quick-intro.Rmd) + Quitting from lines 43-43 [unnamed-chunk-2] (xaringanthemer.Rmd) When tangling ‘xaringanthemer.Rmd’: Error: cannot open the connection @@ -11265,3 +22162,119 @@ Run `revdepcheck::cloud_details(, "xaringanthemer")` for more info ‘xaringanthemer.Rmd’ using ‘UTF-8’... failed ``` +# xpose + +
+ +* Version: 0.4.18 +* GitHub: https://github.com/UUPharmacometrics/xpose +* Source code: https://github.com/cran/xpose +* Date/Publication: 2024-02-01 16:20:02 UTC +* Number of recursive dependencies: 109 + +Run `revdepcheck::cloud_details(, "xpose")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘xpose-Ex.R’ failed + The error most likely occurred in: + + > ### Name: amt_vs_idv + > ### Title: Compartment kinetics + > ### Aliases: amt_vs_idv + > + > ### ** Examples + > + > amt_vs_idv(xpdb_ex_pk, nrow = 2, ncol = 1) + ... + 1. ├─base (local) ``(x) + 2. ├─xpose:::print.xpose_plot(x) + 3. │ └─x %>% paginate(page_2_draw, page_tot) %>% print.ggplot(...) + 4. └─ggplot2:::print.ggplot(., ...) + 5. ├─ggplot2::ggplot_gtable(data) + 6. └─ggplot2:::ggplot_gtable.ggplot_built(data) + 7. └─ggplot2::calc_element("plot.margin", theme) + 8. └─cli::cli_abort(...) + 9. └─rlang::abort(...) + Execution halted + ``` + +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(xpose) + Loading required package: ggplot2 + + Attaching package: 'xpose' + + The following object is masked from 'package:stats': + ... + 8. └─ggplot2:::print.ggplot(., ...) + 9. ├─ggplot2::ggplot_gtable(data) + 10. └─ggplot2:::ggplot_gtable.ggplot_built(data) + 11. └─ggplot2::calc_element("plot.margin", theme) + 12. └─cli::cli_abort(...) + 13. └─rlang::abort(...) + + [ FAIL 4 | WARN 0 | SKIP 8 | PASS 510 ] + Error: Test failures + Execution halted + ``` + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘customize_plots.Rmd’ + ... + Using data from $prob no.1 + Filtering data by EVID == 0 + Using data from $prob no.1 + Filtering data by EVID == 0 + Using data from $prob no.1 + Filtering data by EVID == 0 + + ... + When sourcing ‘vpc.R’: + Error: Theme element `plot.margin` must have class . + Execution halted + + ‘access_xpdb_data.Rmd’ using ‘UTF-8’... OK + ‘customize_plots.Rmd’ using ‘UTF-8’... failed + ‘import_model_outputs.Rmd’ using ‘UTF-8’... OK + ‘introduction.Rmd’ using ‘UTF-8’... failed + ‘multiple_pages.Rmd’ using ‘UTF-8’... failed + ‘vpc.Rmd’ using ‘UTF-8’... failed + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘access_xpdb_data.Rmd’ using rmarkdown + --- finished re-building ‘access_xpdb_data.Rmd’ + + --- re-building ‘customize_plots.Rmd’ using rmarkdown + + Quitting from lines 36-42 [demo type scatter] (customize_plots.Rmd) + Error: processing vignette 'customize_plots.Rmd' failed with diagnostics: + Theme element `plot.margin` must have class . + --- failed re-building ‘customize_plots.Rmd’ + ... + Error: processing vignette 'vpc.Rmd' failed with diagnostics: + Theme element `plot.margin` must have class . + --- failed re-building ‘vpc.Rmd’ + + SUMMARY: processing the following files failed: + ‘customize_plots.Rmd’ ‘introduction.Rmd’ ‘multiple_pages.Rmd’ + ‘vpc.Rmd’ + + Error: Vignette re-building failed. + Execution halted + ``` + From dbea0a6f605b03b4bf13f08edeb05039c97247a3 Mon Sep 17 00:00:00 2001 From: Thomas Lin Pedersen Date: Wed, 17 Jul 2024 09:42:13 +0200 Subject: [PATCH 30/41] revdepcheck once again --- revdep/README.md | 943 +- revdep/cran.md | 1162 +-- revdep/failures.md | 14681 +++++++++------------------ revdep/problems.md | 23657 ++++++++++++++----------------------------- 4 files changed, 13118 insertions(+), 27325 deletions(-) diff --git a/revdep/README.md b/revdep/README.md index 89a1d9a3d1..8976e81c90 100644 --- a/revdep/README.md +++ b/revdep/README.md @@ -1,569 +1,386 @@ # Revdeps -## Failed to check (191) +## Failed to check (132) -|package |version |error |warning |note | -|:--------------------|:-------|:------|:-------|:----| -|abctools |1.1.7 |1 | | | -|adjustedCurves |? | | | | -|AnanseSeurat |? | | | | -|animalEKF |1.2 |1 | | | -|ANOM |0.5 |1 | | | -|aorsf |? | | | | -|APackOfTheClones |? | | | | -|autoReg |? | | | | -|AutoScore |? | | | | -|bayesdfa |1.3.3 |1 | | | -|bayesDP |1.3.6 |1 | | | -|BayesianFactorZoo |0.0.0.2 |1 | | | -|BayesSurvive |? | | | | -|bbmle |? | | | | -|BCClong |1.0.2 |1 | |1 | -|bmstdr |0.7.9 |1 | | | -|bspcov |1.0.0 |1 | | | -|BuyseTest |? | | | | -|calibmsm |? | | | | -|CalibrationCurves |? | | | | -|Canek |? | | | | -|CARBayesST |4.0 |1 | | | -|CaseBasedReasoning |? | | | | -|cellpypes |? | | | | -|CGPfunctions |0.6.3 |1 | | | -|chem16S |? | | | | -|CIARA |? | | | | -|clarify |? | | | | -|ClustAssess |? | | | | -|clustree |? | | | | -|cmprskcoxmsm |0.2.1 |1 | | | -|combiroc |? | | | | -|conos |? | | | | -|contrast |? | | | | -|contsurvplot |? | | | | -|countland |? | | | | -|coveffectsplot |? | | | | -|coxed |? | | | | -|CRMetrics |? | | | | -|crosslag |? | | | | -|csmpv |? | | | | -|ctsem |3.10.0 |1 | | | -|CytoSimplex |? | | | | -|depigner |? | | | | -|DepthProc |2.1.5 |1 | | | -|DIscBIO |? | | | | -|diversityForest |? | | | | -|DR.SC |? | | | | -|DynForest |? | | | | -|dyngen |? | | | | -|EcoEnsemble |1.0.5 |1 | | | -|ecolottery |1.0.0 |1 | | | -|EpiEstim |2.2-4 |1 | | | -|evalITR |? | | | | -|evolqg |0.3-4 |1 | | | -|explainer |? | | | | -|flexrsurv |? | | | | -|forestmangr |? | | | | -|gap |? | | | | -|GeomComb |1.0 |1 | | | -|ggeffects |? | | | | -|ggquickeda |? | | | | -|ggrcs |? | | | | -|ggrisk |? | | | | -|ggsector |? | | | | -|grandR |? | | | | -|Greg |? | | | | -|greport |? | | | | -|harmony |? | | | | -|hIRT |? | | | | -|Hmisc |? | | | | -|Hmsc |3.0-13 |1 | | | -|hydroroute |? | | | | -|[inventorize](failures.md#inventorize)|1.1.1 |__+1__ | | | -|iNZightRegression |1.3.4 |1 | | | -|IRexamples |0.0.4 |1 | | | -|jmBIG |? | | | | -|joineRML |0.4.6 |1 | | | -|jsmodule |? | | | | -|JWileymisc |? | | | | -|kmc |0.4-2 |1 | | | -|KMunicate |? | | | | -|L2E |2.0 |1 | | | -|Landmarking |? | | | | -|lavaSearch2 |? | | | | -|llbayesireg |1.0.0 |1 | | | -|LorenzRegression |1.0.0 |1 | | | -|lsirm12pl |1.3.1 |1 | | | -|MachineShop |? | | | | -|marginaleffects |? | | | | -|mbsts |3.0 |1 | | | -|MetabolicSurv |? | | | | -|MetaNet |? | | | | -|miWQS |0.4.4 |1 | | | -|mlmts |1.1.1 |1 | | | -|mlr |? | | | | -|MOSS |? | | | | -|mrbayes |? | | | | -|mstate |? | | | | -|Multiaovbay |0.1.0 |1 | | | -|multilevelTools |? | | | | -|multipleOutcomes |? | | | | -|netcmc |1.0.2 |1 | | | -|NetworkChange |0.8 |1 | | | -|neutralitytestr |? | | | | -|NMADiagT |0.1.2 |1 | | | -|obliqueRSF |? | | | | -|optweight |0.2.5 |1 | | | -|ormPlot |? | | | | -|OVtool |1.0.3 |1 | | | -|pagoda2 |? | | | | -|pammtools |? | | | | -|pander |? | | | | -|parameters |? | | | | -|PAsso |? | | | | -|paths |0.1.1 |1 | | | -|pctax |? | | | | -|pcutils |? | | | | -|PLMIX |2.1.1 |1 | | | -|pmcalibration |? | | | | -|popstudy |1.0.1 |1 | | | -|pould |? | | | | -|powerly |1.8.6 |1 | | | -|pre |1.0.7 |1 | | | -|PRECAST |? | | | | -|ProFAST |? | | | | -|psbcSpeedUp |? | | | | -|pscore |? | | | | -|psfmi |? | | | | -|pubh |? | | | | -|qPCRtools |? | | | | -|qreport |? | | | | -|quid |0.0.1 |1 | | | -|RcmdrPlugin.RiskDemo |3.2 |1 | | | -|rcssci |? | | | | -|rddtools |1.6.0 |1 | | | -|relsurv |? | | | | -|riskRegression |? | | | | -|rliger |? | | | | -|rms |? | | | | -|rmsb |? | | | | -|robber |? | | | | -|robmedExtra |0.1.0 |1 | | | -|rprev |? | | | | -|RQdeltaCT |? | | | | -|rstanarm |2.32.1 |1 | | | -|rTwig |? | | | | -|scCustomize |? | | | | -|SCdeconR |? | | | | -|scDiffCom |? | | | | -|scGate |? | | | | -|scMappR |? | | | | -|SCORPIUS |? | | | | -|scpi |? | | | | -|scpoisson |? | | | | -|SCpubr |? | | | | -|scRNAstat |? | | | | -|sectorgap |0.1.0 |1 | | | -|SEERaBomb |2019.2 |1 | | | -|semicmprskcoxmsm |0.2.0 |1 | | | -|SensMap |0.7 |1 | | | -|shinyTempSignal |? | | | | -|sievePH |1.1 |1 | | | -|Signac |? | | | | -|simET |? | | | | -|simstudy |? | | | | -|sMSROC |? | | | | -|SNPassoc |? | | | | -|snplinkage |? | | | | -|SoupX |? | | | | -|sparsereg |1.2 |1 | | | -|SPECK |? | | | | -|spikeSlabGAM |1.1-19 |1 | | | -|statsr |0.3.0 |1 | | | -|streamDAG |? | | | | -|sure |? | | | | -|Surrogate |? | | | | -|survex |? | | | | -|survHE |? | | | | -|survidm |1.3.2 |1 | | | -|SurvMetrics |? | | | | -|tempted |0.1.1 |1 | | | -|[tidydr](failures.md#tidydr)|0.0.5 |__+1__ | | | -|tidyEdSurvey |? | | | | -|tidyseurat |? | | | | -|treefit |? | | | | -|TriDimRegression |1.0.2 |1 | | | -|twang |2.6 |1 | | | -|valse |0.1-0 |1 | | | -|visa |? | | | | -|WpProj |? | | | | +|package |version |error |warning |note | +|:----------------------|:----------|:------|:-------|:----| +|abctools |1.1.7 |1 | | | +|animalEKF |1.2 |1 | | | +|ANOM |0.5 |1 | | | +|atRisk |0.1.0 |1 | | | +|AutoScore |1.0.0 |1 | | | +|bayesdfa |1.3.3 |1 | | | +|bayesDP |1.3.6 |1 | | | +|BayesianFactorZoo |0.0.0.2 |1 | | | +|BayesSurvive |0.0.2 |1 | | | +|BCClong |1.0.3 |1 | | | +|BGGM |2.1.3 |1 | | | +|binsreg |1.0 |1 | | | +|bmstdr |0.7.9 |1 | | | +|bspcov |1.0.0 |1 | | | +|BuyseTest |3.0.4 |1 | | | +|CalibrationCurves |2.0.3 |1 | | | +|CARBayesST |4.0 |1 | | | +|CaseBasedReasoning |0.3 |1 | | | +|CGPfunctions |0.6.3 |1 | | | +|cmprskcoxmsm |0.2.1 |1 | | | +|contrast |0.24.2 |1 | | | +|coxed |0.3.3 |1 | | | +|CRMetrics |0.3.0 |1 | | | +|csmpv |1.0.3 |1 | | | +|ctsem |3.10.0 |1 | | | +|DepthProc |2.1.5 |1 | | | +|DR.SC |3.4 |1 | | | +|DynNom |5.1 |1 | | | +|easybgm |0.1.2 |1 | | | +|ecolottery |1.0.0 |1 | | | +|EpiEstim |2.2-4 |1 | | | +|evolqg |0.3-4 |1 | | | +|ForecastComb |1.3.1 |1 | | | +|gapfill |0.9.6-1 |1 | |1 | +|GeomComb |1.0 |1 | | | +|ggrcs |0.4.0 |1 | | | +|ggrisk |1.3 |1 | | | +|gJLS2 |0.2.0 |1 | | | +|Greg |2.0.2 |1 | | | +|greport |0.7-4 |1 | | | +|hettx |0.1.3 |1 | | | +|hIRT |0.3.0 |1 | | | +|Hmsc |3.0-13 |1 | | | +|[inventorize](failures.md#inventorize)|1.1.1 |__+1__ | | | +|iNZightPlots |2.15.3 |1 | | | +|iNZightRegression |1.3.4 |1 | | | +|IRexamples |0.0.4 |1 | | | +|jmBIG |0.1.2 |1 | | | +|joineRML |0.4.6 |1 | | | +|JWileymisc |1.4.1 |1 | | | +|kmc |0.4-2 |1 | | | +|L2E |2.0 |1 | | | +|llbayesireg |1.0.0 |1 | | | +|LorenzRegression |1.0.0 |1 | | | +|lsirm12pl |1.3.1 |1 | | | +|mbsts |3.0 |1 | | | +|MendelianRandomization |0.10.0 |1 | | | +|MetabolicSurv |1.1.2 |1 | | | +|miWQS |0.4.4 |1 | | | +|MRZero |0.2.0 |1 | | | +|Multiaovbay |0.1.0 |1 | | | +|multilevelTools |0.1.1 |1 | | | +|multinma |0.7.1 |1 | | | +|NCA |4.0.1 |1 | | | +|netcmc |1.0.2 |1 | | | +|NetworkChange |0.8 |1 | | | +|nlmeVPC |2.6 |1 | | | +|NMADiagT |0.1.2 |1 | | | +|optweight |0.2.5 |1 | | | +|OVtool |1.0.3 |1 | | | +|paths |0.1.1 |1 | | | +|PLMIX |2.1.1 |1 | | | +|popstudy |1.0.1 |1 | | | +|pould |1.0.1 |1 | | | +|powerly |1.8.6 |1 | | | +|pre |1.0.7 |1 | | | +|ProFAST |? | | | | +|psbcSpeedUp |2.0.7 |1 | | | +|pscore |0.4.0 |1 | | | +|psfmi |1.4.0 |1 | | | +|qPCRtools |1.0.1 |1 | | | +|qreport |1.0-1 |1 | | | +|qris |1.1.1 |1 | | | +|qte |1.3.1 |1 | | | +|quid |0.0.1 |1 | | | +|RATest |0.1.10 |1 | | | +|RcmdrPlugin.RiskDemo |3.2 |1 | | | +|rddtools |1.6.0 |1 | | | +|riskRegression |2023.12.21 |1 | | | +|rms |6.8-1 |1 | |1 | +|rmsb |1.1-1 |1 | | | +|robmed |1.0.2 |1 | | | +|robmedExtra |0.1.0 |1 | | | +|RPPanalyzer |1.4.9 |1 | | | +|RQdeltaCT |1.3.0 |1 | | | +|scCustomize |2.1.2 |1 | |1 | +|SCdeconR |1.0.0 |1 | | | +|scGate |1.6.2 |1 | | | +|SCIntRuler |0.99.6 |1 | | | +|scMappR |1.0.11 |1 | | | +|scpi |2.2.5 |1 | | | +|scRNAstat |0.1.1 |1 | | | +|sectorgap |0.1.0 |1 | | | +|SEERaBomb |2019.2 |1 | | | +|semicmprskcoxmsm |0.2.0 |1 | | | +|SensMap |0.7 |1 | | | +|Seurat |5.1.0 |1 | | | +|shinyTempSignal |0.0.8 |1 | | | +|sievePH |1.1 |1 | | | +|Signac |1.13.0 |1 | | | +|SimplyAgree |0.2.0 |1 | | | +|sMSROC |0.1.2 |1 | | | +|SNPassoc |2.1-0 |1 | | | +|snplinkage |? | | | | +|SoupX |1.6.2 |1 | | | +|sparsereg |1.2 |1 | | | +|spikeSlabGAM |1.1-19 |1 | | | +|statsr |0.3.0 |1 | | | +|streamDAG |? | | | | +|survHE |2.0.1 |1 | |1 | +|survidm |1.3.2 |1 | | | +|tempted |0.1.1 |1 | | | +|[tidydr](failures.md#tidydr)|0.0.5 |__+1__ | | | +|tidyEdSurvey |0.1.3 |1 | | | +|tidyseurat |0.8.0 |1 | | | +|tidyvpc |1.5.1 |1 | | | +|TriDimRegression |1.0.2 |1 | | | +|TSrepr |1.1.0 |1 | | | +|twang |2.6 |1 | | | +|vdg |1.2.3 |1 | | | +|visa |0.1.0 |1 | | | +|WRTDStidal |1.1.4 |1 | | | -## New problems (366) +## New problems (242) -|package |version |error |warning |note | -|:-----------------------|:---------|:--------|:-------|:--------| -|[accSDA](problems.md#accsda)|1.1.3 |__+1__ | | | -|[activAnalyzer](problems.md#activanalyzer)|2.1.1 |__+1__ | |1 __+1__ | -|[actxps](problems.md#actxps)|1.4.0 |__+1__ | |__+1__ | -|[add2ggplot](problems.md#add2ggplot)|0.3.0 |__+2__ | |1 __+1__ | -|[AeRobiology](problems.md#aerobiology)|2.0.1 |1 | |__+1__ | -|[afex](problems.md#afex)|1.3-1 |__+1__ | |__+1__ | -|[AgroR](problems.md#agror)|1.3.6 |__+1__ | | | -|[allMT](problems.md#allmt)|0.1.0 |__+1__ | | | -|[AnalysisLin](problems.md#analysislin)|0.1.2 |__+1__ | | | -|[animbook](problems.md#animbook)|1.0.0 |__+1__ | | | -|[aplot](problems.md#aplot)|0.2.2 |__+1__ | | | -|[ASRgenomics](problems.md#asrgenomics)|1.1.4 |__+2__ | |1 | -|[auditor](problems.md#auditor)|1.3.5 |__+2__ | |__+1__ | -|[augmentedRCBD](problems.md#augmentedrcbd)|0.1.7 |__+2__ |-1 | | -|[autoplotly](problems.md#autoplotly)|0.1.4 |__+2__ | | | -|[baggr](problems.md#baggr)|0.7.8 |__+2__ | |2 __+1__ | -|[bayefdr](problems.md#bayefdr)|0.2.1 |__+2__ | | | -|[BayesGrowth](problems.md#bayesgrowth)|1.0.0 |__+1__ | |2 __+1__ | -|[BayesianReasoning](problems.md#bayesianreasoning)|0.4.2 |__+1__ | |__+1__ | -|[bayestestR](problems.md#bayestestr)|0.13.2 |1 __+1__ | | | -|[bdots](problems.md#bdots)|1.2.5 |__+1__ | |__+1__ | -|[bdrc](problems.md#bdrc)|1.1.0 |__+1__ | |__+1__ | -|[BeeBDC](problems.md#beebdc)|1.1.1 |1 __+1__ | |1 | -|[besthr](problems.md#besthr)|0.3.2 |__+2__ | |__+1__ | -|[BetaPASS](problems.md#betapass)|1.1-2 |__+2__ | |__+1__ | -|[biblioverlap](problems.md#biblioverlap)|1.0.2 |__+1__ | |1 | -|[biscale](problems.md#biscale)|1.0.0 |1 __+1__ | |1 | -|[BlandAltmanLeh](problems.md#blandaltmanleh)|0.3.1 |__+1__ | | | -|[bnma](problems.md#bnma)|1.6.0 |__+1__ | |__+1__ | -|[boxly](problems.md#boxly)|0.1.1 |__+1__ | | | -|[braidReports](problems.md#braidreports)|0.5.4 |__+1__ | | | -|[brolgar](problems.md#brolgar)|1.0.1 |__+2__ | |__+1__ | -|[calendR](problems.md#calendr)|1.2 |__+1__ | | | -|[calendRio](problems.md#calendrio)|0.2.0 |__+1__ | | | -|[capm](problems.md#capm)|0.14.0 |__+1__ | |1 | -|[cartograflow](problems.md#cartograflow)|1.0.5 |__+1__ | | | -|[cats](problems.md#cats)|1.0.2 |__+1__ | |1 | -|[cheem](problems.md#cheem)|0.4.0.0 |1 __+1__ | | | -|[chillR](problems.md#chillr)|0.75 |__+1__ | | | -|[chronicle](problems.md#chronicle)|0.3 |__+2__ | |1 __+1__ | -|[circumplex](problems.md#circumplex)|0.3.10 |__+1__ | |__+1__ | -|[cities](problems.md#cities)|0.1.3 |__+2__ | |__+1__ | -|[CleaningValidation](problems.md#cleaningvalidation)|1.0 |__+1__ | | | -|[clinDataReview](problems.md#clindatareview)|1.5.2 |__+2__ | |1 __+1__ | -|[clinUtils](problems.md#clinutils)|0.2.0 |__+1__ |-1 |1 __+1__ | -|[ClustImpute](problems.md#clustimpute)|0.2.4 |__+1__ | |1 | -|[cogmapr](problems.md#cogmapr)|0.9.3 |__+1__ | | | -|[CohortPlat](problems.md#cohortplat)|1.0.5 |__+2__ | |__+1__ | -|[CoMiRe](problems.md#comire)|0.8 |__+1__ | | | -|[CommKern](problems.md#commkern)|1.0.1 |__+2__ | |1 __+1__ | -|[conText](problems.md#context)|1.4.3 |__+2__ | |1 __+1__ | -|[CoreMicrobiomeR](problems.md#coremicrobiomer)|0.1.0 |__+1__ | | | -|[correlationfunnel](problems.md#correlationfunnel)|0.2.0 |__+1__ | |1 | -|[corrViz](problems.md#corrviz)|0.1.0 |__+2__ | |1 __+1__ | -|[covidcast](problems.md#covidcast)|0.5.2 |__+2__ | |1 __+1__ | -|[cricketdata](problems.md#cricketdata)|0.2.3 |1 | |1 __+1__ | -|[crosshap](problems.md#crosshap)|1.4.0 |__+1__ | | | -|[crplyr](problems.md#crplyr)|0.4.0 |__+2__ | |__+1__ | -|[ctrialsgov](problems.md#ctrialsgov)|0.2.5 |__+1__ | |1 | -|[cubble](problems.md#cubble)|0.3.0 |__+1__ | |1 __+1__ | -|[dabestr](problems.md#dabestr)|2023.9.12 |__+3__ | |__+1__ | -|[DAISIEprep](problems.md#daisieprep)|0.4.0 |__+1__ | | | -|[dataresqc](problems.md#dataresqc)|1.1.1 |__+1__ | | | -|[ddtlcm](problems.md#ddtlcm)|0.2.1 |__+3__ | |1 __+1__ | -|[dfoliatR](problems.md#dfoliatr)|0.3.0 |__+3__ | |__+1__ | -|[directlabels](problems.md#directlabels)|2024.1.21 |__+1__ | |__+1__ | -|[disprofas](problems.md#disprofas)|0.1.3 |__+2__ | | | -|[distributional](problems.md#distributional)|0.4.0 |__+1__ | | | -|[dittoViz](problems.md#dittoviz)|1.0.1 |__+2__ | | | -|[dobin](problems.md#dobin)|1.0.4 |__+1__ | |__+1__ | -|[dogesr](problems.md#dogesr)|0.5.0 |1 | |1 __+1__ | -|[dotsViolin](problems.md#dotsviolin)|0.0.1 |__+1__ | |1 | -|[ds4psy](problems.md#ds4psy)|1.0.0 |__+1__ | | | -|[edecob](problems.md#edecob)|1.2.2 |__+1__ | | | -|[entropart](problems.md#entropart)|1.6-13 |__+2__ | |__+1__ | -|[envalysis](problems.md#envalysis)|0.7.0 |__+3__ | |__+1__ | -|[epiCleanr](problems.md#epicleanr)|0.2.0 |__+1__ | |1 | -|[EpiInvert](problems.md#epiinvert)|0.3.1 |__+1__ | |1 | -|[esci](problems.md#esci)|1.0.2 |__+2__ | | | -|[EvidenceSynthesis](problems.md#evidencesynthesis)|0.5.0 |__+3__ | |__+1__ | -|[EvolutionaryGames](problems.md#evolutionarygames)|0.1.2 |__+2__ | |__+1__ | -|[EvoPhylo](problems.md#evophylo)|0.3.2 |1 __+1__ | |1 __+1__ | -|[evprof](problems.md#evprof)|1.1.2 |__+2__ | |1 | -|[expirest](problems.md#expirest)|0.1.6 |__+1__ | | | -|[explore](problems.md#explore)|1.3.0 |__+2__ | |__+1__ | -|[ezplot](problems.md#ezplot)|0.7.13 |__+2__ | |__+1__ | -|[fable.prophet](problems.md#fableprophet)|0.1.0 |__+1__ | |1 __+1__ | -|[fabletools](problems.md#fabletools)|0.4.2 |__+2__ | | | -|[factoextra](problems.md#factoextra)|1.0.7 |__+1__ | | | -|[faux](problems.md#faux)|1.2.1 |1 __+1__ | |__+1__ | -|[fddm](problems.md#fddm)|0.5-2 |__+1__ | |1 | -|[fdrci](problems.md#fdrci)|2.4 |__+1__ | | | -|[ffp](problems.md#ffp) |0.2.2 |__+1__ | | | -|[fido](problems.md#fido)|1.1.0 |__+2__ |1 |2 | -|[figuRes2](problems.md#figures2)|1.0.0 |__+2__ | | | -|[flipr](problems.md#flipr)|0.3.3 |1 | |1 __+1__ | -|[FMM](problems.md#fmm) |0.3.1 |__+1__ | |__+1__ | -|[fmriqa](problems.md#fmriqa)|0.3.0 |__+1__ | |1 | -|[foreSIGHT](problems.md#foresight)|1.2.0 |__+2__ | |1 | -|[frailtyEM](problems.md#frailtyem)|1.0.1 |__+1__ | |2 | -|[funcharts](problems.md#funcharts)|1.4.1 |__+1__ | | | -|[gapmap](problems.md#gapmap)|1.0.0 |__+2__ | |__+1__ | -|[gasper](problems.md#gasper)|1.1.6 |__+2__ | |1 | -|[gaussplotR](problems.md#gaussplotr)|0.2.5 |__+1__ | |__+1__ | -|[gg.gap](problems.md#gggap)|1.3 |__+1__ | |1 | -|[ggalignment](problems.md#ggalignment)|1.0.1 |__+2__ | |__+1__ | -|[ggalt](problems.md#ggalt)|0.4.0 |1 | |2 __+1__ | -|[gganimate](problems.md#gganimate)|1.0.9 |__+2__ | |__+1__ | -|[ggbrace](problems.md#ggbrace)|0.1.1 |__+1__ | | | -|[ggbrain](problems.md#ggbrain)|0.8.1 |__+1__ | |1 __+1__ | -|[ggbreak](problems.md#ggbreak)|0.1.2 |__+2__ | |__+1__ | -|[ggdark](problems.md#ggdark)|0.2.1 |__+2__ | |1 | -|[ggdist](problems.md#ggdist)|3.3.2 |1 __+2__ | |1 __+1__ | -|[ggedit](problems.md#ggedit)|0.4.1 |__+1__ | | | -|[ggExtra](problems.md#ggextra)|0.10.1 |__+1__ | |1 __+1__ | -|[ggfixest](problems.md#ggfixest)|0.1.0 |1 __+1__ | | | -|[ggflowchart](problems.md#ggflowchart)|1.0.0 |__+2__ | |__+1__ | -|[ggforce](problems.md#ggforce)|0.4.2 |__+1__ | |1 | -|[ggfortify](problems.md#ggfortify)|0.4.17 |__+1__ | | | -|[ggfoundry](problems.md#ggfoundry)|0.1.1 |__+1__ | |__+1__ | -|[gggap](problems.md#gggap)|1.0.1 |__+1__ | |1 | -|[ggh4x](problems.md#ggh4x)|0.2.8 |1 __+2__ | |__+1__ | -|[gghdx](problems.md#gghdx)|0.1.3 |1 __+1__ | |__+1__ | -|[gghighlight](problems.md#gghighlight)|0.4.1 |1 __+2__ | |1 | -|[ggHoriPlot](problems.md#gghoriplot)|1.0.1 |__+1__ | |__+1__ | -|[ggiraph](problems.md#ggiraph)|0.8.10 |__+2__ | |2 | -|[ggiraphExtra](problems.md#ggiraphextra)|0.3.0 |__+2__ | |__+1__ | -|[ggmap](problems.md#ggmap)|4.0.0 |__+1__ | |1 | -|[ggmice](problems.md#ggmice)|0.1.0 |__+1__ | |__+1__ | -|[ggmulti](problems.md#ggmulti)|1.0.7 |__+3__ | |__+1__ | -|[ggparallel](problems.md#ggparallel)|0.4.0 |__+1__ | | | -|[ggpicrust2](problems.md#ggpicrust2)|1.7.3 |__+1__ | |1 | -|[ggpie](problems.md#ggpie)|0.2.5 |__+2__ | |__+1__ | -|[ggplotlyExtra](problems.md#ggplotlyextra)|0.0.1 |__+1__ | |1 | -|[ggpol](problems.md#ggpol)|0.0.7 |__+1__ | |2 | -|[ggprism](problems.md#ggprism)|1.0.5 |__+1__ | | | -|[ggpubr](problems.md#ggpubr)|0.6.0 |__+2__ | | | -|[ggraph](problems.md#ggraph)|2.2.1 |1 __+1__ | |1 __+1__ | -|[ggredist](problems.md#ggredist)|0.0.2 |__+1__ | | | -|[ggResidpanel](problems.md#ggresidpanel)|0.3.0 |__+2__ | |__+1__ | -|[ggseqplot](problems.md#ggseqplot)|0.8.4 |__+3__ | |__+1__ | -|[ggside](problems.md#ggside)|0.3.1 |__+1__ |__+1__ | | -|[ggstatsplot](problems.md#ggstatsplot)|0.12.3 |1 __+1__ | | | -|[ggtern](problems.md#ggtern)|3.5.0 |__+1__ | |2 | -|[ggthemes](problems.md#ggthemes)|5.1.0 |__+1__ | |2 | -|[ggupset](problems.md#ggupset)|0.3.0 |__+1__ | | | -|[ggVennDiagram](problems.md#ggvenndiagram)|1.5.2 |__+1__ | |1 __+1__ | -|[graphPAF](problems.md#graphpaf)|2.0.0 |__+1__ | | | -|[greatR](problems.md#greatr)|2.0.0 |__+1__ | |__+1__ | -|[Greymodels](problems.md#greymodels)|2.0.1 |__+1__ | | | -|[groupdata2](problems.md#groupdata2)|2.0.3 |__+1__ | |__+1__ | -|[GSD](problems.md#gsd) |1.0.0 |__+1__ | | | -|[gtExtras](problems.md#gtextras)|0.5.0 |__+1__ | | | -|[HaploCatcher](problems.md#haplocatcher)|1.0.4 |__+1__ | |__+1__ | -|[hdnom](problems.md#hdnom)|6.0.3 |__+2__ | |__+1__ | -|[healthyR](problems.md#healthyr)|0.2.1 |__+1__ | |1 __+1__ | -|[healthyR.ai](problems.md#healthyrai)|0.0.13 |__+2__ | |__+1__ | -|[healthyR.ts](problems.md#healthyrts)|0.3.0 |__+2__ | |1 __+1__ | -|[heatmaply](problems.md#heatmaply)|1.5.0 |__+3__ | |1 __+1__ | -|[hermiter](problems.md#hermiter)|2.3.1 |__+1__ | |2 __+1__ | -|[heumilkr](problems.md#heumilkr)|0.2.0 |__+1__ | |__+1__ | -|[heuristicsmineR](problems.md#heuristicsminer)|0.3.0 | | |__+1__ | -|[HistDAWass](problems.md#histdawass)|1.0.8 |__+1__ | |1 | -|[huito](problems.md#huito)|0.2.4 |1 __+1__ | |__+1__ | -|[hurricaneexposure](problems.md#hurricaneexposure)|0.1.1 |__+2__ | |2 __+1__ | -|[HVT](problems.md#hvt) |24.5.2 |__+1__ | | | -|[hydraulics](problems.md#hydraulics)|0.7.0 |__+2__ | |__+1__ | -|[hyperSpec](problems.md#hyperspec)|0.100.2 |__+1__ | | | -|[hypsoLoop](problems.md#hypsoloop)|0.2.0 | |__+1__ | | -|[ICvectorfields](problems.md#icvectorfields)|0.1.2 |__+1__ | |__+1__ | -|[idiogramFISH](problems.md#idiogramfish)|2.0.13 |1 | |__+1__ | -|[idopNetwork](problems.md#idopnetwork)|0.1.2 |__+1__ | |__+1__ | -|[iglu](problems.md#iglu)|4.0.0 |__+2__ | |__+1__ | -|[igoR](problems.md#igor)|0.2.0 |__+1__ | |1 __+1__ | -|[immunarch](problems.md#immunarch)|0.9.1 |__+1__ | |1 | -|[immuneSIM](problems.md#immunesim)|0.8.7 |__+1__ | |2 | -|[iNEXT.4steps](problems.md#inext4steps)|1.0.0 |__+3__ | |__+1__ | -|[iNEXT.beta3D](problems.md#inextbeta3d)|1.0.2 |__+1__ |1 | | -|[insurancerating](problems.md#insurancerating)|0.7.4 |__+1__ | | | -|[inTextSummaryTable](problems.md#intextsummarytable)|3.3.2 |1 __+1__ | |1 __+1__ | -|[jskm](problems.md#jskm)|0.5.3 |__+3__ | |__+1__ | -|[KaradaColor](problems.md#karadacolor)|0.1.5 |__+1__ | | | -|[karel](problems.md#karel)|0.1.1 |__+2__ | |1 | -|[kDGLM](problems.md#kdglm)|1.2.0 |1 __+1__ | | | -|[labsimplex](problems.md#labsimplex)|0.1.2 |__+2__ | |__+1__ | -|[landscapemetrics](problems.md#landscapemetrics)|2.1.2 |__+1__ | |1 | -|[landscapetools](problems.md#landscapetools)|0.5.0 |__+2__ | |__+1__ | -|[latentcor](problems.md#latentcor)|2.0.1 |__+1__ | | | -|[latte](problems.md#latte)|0.2.1 |__+1__ | |1 | -|[lemon](problems.md#lemon)|0.4.9 |__+3__ | |__+1__ | -|[lfproQC](problems.md#lfproqc)|0.1.0 |__+2__ | |1 __+1__ | -|[LLSR](problems.md#llsr)|0.0.3.1 |__+1__ | | | -|[LMoFit](problems.md#lmofit)|0.1.7 |__+1__ | |1 __+1__ | -|[lomb](problems.md#lomb)|2.5.0 |__+1__ | |1 | -|[LongDat](problems.md#longdat)|1.1.2 |__+1__ | |__+1__ | -|[longitudinalcascade](problems.md#longitudinalcascade)|0.3.2.6 |__+1__ | | | -|[longmixr](problems.md#longmixr)|1.0.0 |__+1__ | |__+1__ | -|[manhplot](problems.md#manhplot)|1.1 |__+1__ | | | -|[mau](problems.md#mau) |0.1.2 |__+1__ | | | -|[MBNMAdose](problems.md#mbnmadose)|0.4.3 |__+1__ | |1 __+1__ | -|[MBNMAtime](problems.md#mbnmatime)|0.2.4 |1 | |__+1__ | -|[metaforest](problems.md#metaforest)|0.1.4 |1 __+1__ | | | -|[metan](problems.md#metan)|1.18.0 |__+1__ | | | -|[metaplot](problems.md#metaplot)|0.8.4 |__+1__ | | | -|[metR](problems.md#metr)|0.15.0 |__+2__ | |1 __+1__ | -|[miceFast](problems.md#micefast)|0.8.2 |__+3__ | |2 __+1__ | -|[MicrobiomeStat](problems.md#microbiomestat)|1.2 |__+1__ | | | -|[micromap](problems.md#micromap)|1.9.8 |__+2__ | |1 | -|[MiMIR](problems.md#mimir)|1.5 |__+1__ | | | -|[MIMSunit](problems.md#mimsunit)|0.11.2 |__+1__ | | | -|[miRetrieve](problems.md#miretrieve)|1.3.4 |__+1__ | | | -|[misspi](problems.md#misspi)|0.1.0 |__+1__ | | | -|[mizer](problems.md#mizer)|2.5.1 |__+1__ | |1 | -|[mlr3spatiotempcv](problems.md#mlr3spatiotempcv)|2.3.1 |1 __+1__ | |1 | -|[mlr3viz](problems.md#mlr3viz)|0.8.0 |__+1__ | | | -|[modeltime.resample](problems.md#modeltimeresample)|0.2.3 |__+1__ | |1 | -|[mosaic](problems.md#mosaic)|1.9.1 |1 __+2__ | |4 | -|[motifr](problems.md#motifr)|1.0.0 |__+1__ | | | -|[mpwR](problems.md#mpwr)|0.1.5 |__+3__ | |__+1__ | -|[mrfDepth](problems.md#mrfdepth)|1.0.17 |__+1__ | |1 | -|[musclesyneRgies](problems.md#musclesynergies)|1.2.5 |__+3__ | |__+1__ | -|[naniar](problems.md#naniar)|1.1.0 |__+1__ | |__+1__ | -|[neatmaps](problems.md#neatmaps)|2.1.0 |__+1__ | |1 | -|[NetFACS](problems.md#netfacs)|0.5.0 |__+2__ | |__+1__ | -|[NHSRplotthedots](problems.md#nhsrplotthedots)|0.1.0 |__+2__ | |1 __+1__ | -|[nima](problems.md#nima)|0.6.2 |__+1__ | |1 | -|[NIMAA](problems.md#nimaa)|0.2.1 |__+3__ | |2 __+1__ | -|[nparACT](problems.md#nparact)|0.8 |__+1__ | | | -|[nullabor](problems.md#nullabor)|0.3.9 |__+1__ | |1 | -|[OBIC](problems.md#obic)|3.0.2 |__+1__ | |1 __+1__ | -|[OddsPlotty](problems.md#oddsplotty)|1.0.2 |__+1__ | |1 __+1__ | -|[ofpetrial](problems.md#ofpetrial)|0.1.1 |__+1__ | | | -|[OmicNavigator](problems.md#omicnavigator)|1.13.13 |__+2__ | |1 | -|[oncomsm](problems.md#oncomsm)|0.1.4 |__+2__ | |2 __+1__ | -|[ontophylo](problems.md#ontophylo)|1.1.3 |__+1__ | |2 | -|[OpenLand](problems.md#openland)|1.0.3 |__+2__ | |__+1__ | -|[ordbetareg](problems.md#ordbetareg)|0.7.2 |__+1__ | |2 __+1__ | -|[otsad](problems.md#otsad)|0.2.0 |__+1__ | |1 | -|[OutliersO3](problems.md#outlierso3)|0.6.3 |__+1__ | |__+1__ | -|[palettes](problems.md#palettes)|0.2.0 |__+1__ | |__+1__ | -|[ParBayesianOptimization](problems.md#parbayesianoptimization)|1.2.6 |__+1__ | | | -|[patchwork](problems.md#patchwork)|1.2.0 |__+1__ | | | -|[pathfindR](problems.md#pathfindr)|2.4.1 |1 __+1__ | |__+1__ | -|[pdSpecEst](problems.md#pdspecest)|1.2.4 |__+1__ | |3 __+1__ | -|[pdxTrees](problems.md#pdxtrees)|0.4.0 |__+1__ | |1 __+1__ | -|[personalized](problems.md#personalized)|0.2.7 |__+1__ | | | -|[PGRdup](problems.md#pgrdup)|0.2.3.9 |__+1__ |-1 | | -|[Plasmidprofiler](problems.md#plasmidprofiler)|0.1.6 |__+1__ | | | -|[plotDK](problems.md#plotdk)|0.1.0 |__+1__ | |2 | -|[plotly](problems.md#plotly)|4.10.4 |__+2__ | |1 | -|[pmartR](problems.md#pmartr)|2.4.5 |__+1__ | |1 | -|[pmxTools](problems.md#pmxtools)|1.3 |__+1__ | |1 | -|[politeness](problems.md#politeness)|0.9.3 |__+2__ | |1 __+1__ | -|[posterior](problems.md#posterior)|1.5.0 |1 | |__+1__ | -|[PPQplan](problems.md#ppqplan)|1.1.0 |1 | |2 __+1__ | -|[ppseq](problems.md#ppseq)|0.2.4 |__+1__ | |1 __+1__ | -|[PPtreeregViz](problems.md#pptreeregviz)|2.0.5 |__+2__ | |1 __+1__ | -|[precrec](problems.md#precrec)|0.14.4 |__+1__ | |1 __+1__ | -|[prevR](problems.md#prevr)|5.0.0 |__+1__ | |1 __+1__ | -|[primerTree](problems.md#primertree)|1.0.6 |__+1__ | | | -|[processmapR](problems.md#processmapr)|0.5.3 |__+1__ | | | -|[PTXQC](problems.md#ptxqc)|1.1.1 |__+1__ | |1 | -|[qacBase](problems.md#qacbase)|1.0.3 |__+1__ | | | -|[qgcomp](problems.md#qgcomp)|2.15.2 |__+2__ | |__+1__ | -|[qgcompint](problems.md#qgcompint)|0.7.0 |__+2__ | |__+1__ | -|[qpNCA](problems.md#qpnca)|1.1.6 |__+1__ | |__+1__ | -|[QurvE](problems.md#qurve)|1.1.1 |__+1__ | |1 | -|[r2dii.plot](problems.md#r2diiplot)|0.4.0 |__+2__ | | | -|[Radviz](problems.md#radviz)|0.9.3 |__+2__ | |__+1__ | -|[rainette](problems.md#rainette)|0.3.1.1 |__+1__ | | | -|[rassta](problems.md#rassta)|1.0.5 |__+3__ | | | -|[RAT](problems.md#rat) |0.3.1 |__+1__ | | | -|[Rcan](problems.md#rcan)|1.3.82 |__+1__ | |1 | -|[redist](problems.md#redist)|4.2.0 |__+1__ | |1 __+1__ | -|[Relectoral](problems.md#relectoral)|0.1.0 |1 __+1__ | |2 | -|[reliabilitydiag](problems.md#reliabilitydiag)|0.2.1 |__+1__ | | | -|[relliptical](problems.md#relliptical)|1.3.0 |__+1__ | |1 | -|[Repliscope](problems.md#repliscope)|1.1.1 |__+1__ | | | -|[reportRmd](problems.md#reportrmd)|0.1.0 |__+2__ | |__+1__ | -|[reReg](problems.md#rereg)|1.4.6 |__+1__ | | | -|[reservr](problems.md#reservr)|0.0.2 |__+2__ | |2 __+1__ | -|[restriktor](problems.md#restriktor)|0.5-60 |__+1__ | | | -|[RevGadgets](problems.md#revgadgets)|1.2.1 |__+1__ | | | -|[rimu](problems.md#rimu)|0.6 |1 __+1__ | |__+1__ | -|[rKOMICS](problems.md#rkomics)|1.3 |__+1__ | |2 | -|[rmcorr](problems.md#rmcorr)|0.6.0 |1 | |__+1__ | -|[RNAseqQC](problems.md#rnaseqqc)|0.1.4 |__+1__ | |1 __+1__ | -|[roahd](problems.md#roahd)|1.4.3 |__+1__ | |1 | -|[robustbase](problems.md#robustbase)|0.99-2 |__+1__ | |3 | -|[romic](problems.md#romic)|1.1.3 |__+1__ | | | -|[roptions](problems.md#roptions)|1.0.3 |__+1__ | |1 | -|[rotations](problems.md#rotations)|1.6.5 |__+2__ | |3 | -|[rreg](problems.md#rreg)|0.2.1 |__+1__ | | | -|[rSDI](problems.md#rsdi)|0.2.1 |__+1__ | |__+1__ | -|[SangerTools](problems.md#sangertools)|1.0.2 |__+2__ | |__+1__ | -|[santaR](problems.md#santar)|1.2.4 |1 | |__+1__ | -|[scoringutils](problems.md#scoringutils)|1.2.2 |1 __+1__ | |__+1__ | -|[SCVA](problems.md#scva)|1.3.1 |__+1__ | | | -|[SDLfilter](problems.md#sdlfilter)|2.3.3 |__+1__ | | | -|[see](problems.md#see) |0.8.4 |__+1__ | | | -|[sentimentr](problems.md#sentimentr)|2.9.0 |__+1__ | |1 | -|[sentometrics](problems.md#sentometrics)|1.0.0 |__+1__ | |4 | -|[sglg](problems.md#sglg)|0.2.2 |__+1__ | | | -|[SHAPforxgboost](problems.md#shapforxgboost)|0.1.3 |__+1__ | | | -|[shazam](problems.md#shazam)|1.2.0 |__+2__ | |__+1__ | -|[simulariatools](problems.md#simulariatools)|2.5.1 |__+1__ | | | -|[sjPlot](problems.md#sjplot)|2.8.16 |__+2__ | |__+1__ | -|[SleepCycles](problems.md#sleepcycles)|1.1.4 |__+1__ | | | -|[smallsets](problems.md#smallsets)|2.0.0 |__+2__ | |1 __+1__ | -|[smdi](problems.md#smdi)|0.2.2 |1 | |__+1__ | -|[soc.ca](problems.md#socca)|0.8.0 |__+1__ | |2 | -|[spbal](problems.md#spbal)|1.0.0 |__+1__ | |__+1__ | -|[speccurvieR](problems.md#speccurvier)|0.3.0 |__+1__ | |1 | -|[spinifex](problems.md#spinifex)|0.3.7.0 |__+1__ | | | -|[spotoroo](problems.md#spotoroo)|0.1.4 |__+2__ | |1 __+1__ | -|[SqueakR](problems.md#squeakr)|1.3.0 |1 | |1 __+1__ | -|[stabm](problems.md#stabm)|1.2.2 |__+3__ | |__+1__ | -|[starvz](problems.md#starvz)|0.8.0 |__+1__ | | | -|[statgenMPP](problems.md#statgenmpp)|1.0.2 |__+2__ | |__+1__ | -|[statVisual](problems.md#statvisual)|1.2.1 |__+2__ | |1 __+1__ | -|[superheat](problems.md#superheat)|0.1.0 |__+2__ | |1 | -|[surveyexplorer](problems.md#surveyexplorer)|0.1.0 |__+1__ | | | -|[survivalAnalysis](problems.md#survivalanalysis)|0.3.0 |1 __+1__ | |__+1__ | -|[Sysrecon](problems.md#sysrecon)|0.1.3 |__+1__ | |1 | -|[tabledown](problems.md#tabledown)|1.0.0 |__+1__ | |1 | -|[tabr](problems.md#tabr)|0.4.9 |__+1__ | | | -|[TcGSA](problems.md#tcgsa)|0.12.10 |__+1__ | | | -|[TCIU](problems.md#tciu)|1.2.6 |__+2__ | |1 __+1__ | -|[thematic](problems.md#thematic)|0.1.5 |__+2__ | | | -|[tidybayes](problems.md#tidybayes)|3.0.6 |1 __+2__ | |1 | -|[tidyCDISC](problems.md#tidycdisc)|0.2.1 |__+1__ | |1 | -|[tidysdm](problems.md#tidysdm)|0.9.4 |__+1__ | |__+1__ | -|[tidytreatment](problems.md#tidytreatment)|0.2.2 |__+1__ | |1 __+1__ | -|[timetk](problems.md#timetk)|2.9.0 |__+1__ | |1 | -|[tinyarray](problems.md#tinyarray)|2.4.1 |__+1__ | |1 | -|[tmap](problems.md#tmap)|3.3-4 |__+1__ | | | -|[TOmicsVis](problems.md#tomicsvis)|2.0.0 |__+2__ | |1 __+1__ | -|[tornado](problems.md#tornado)|0.1.3 |__+3__ | |__+1__ | -|[TOSTER](problems.md#toster)|0.8.3 |__+3__ | |__+1__ | -|[toxEval](problems.md#toxeval)|1.3.2 |__+1__ | |1 | -|[TreatmentPatterns](problems.md#treatmentpatterns)|2.6.7 |__+1__ | | | -|[TreatmentSelection](problems.md#treatmentselection)|2.1.1 |__+1__ | | | -|[TreeDep](problems.md#treedep)|0.1.3 |__+1__ | | | -|[TreeDist](problems.md#treedist)|2.7.0 |__+1__ | |1 __+1__ | -|[treeheatr](problems.md#treeheatr)|0.2.1 |__+2__ | |__+1__ | -|[trelliscopejs](problems.md#trelliscopejs)|0.2.6 |__+2__ | | | -|[tricolore](problems.md#tricolore)|1.2.4 |__+2__ | |1 __+1__ | -|[tsnet](problems.md#tsnet)|0.1.0 |__+1__ | |2 | -|[umiAnalyzer](problems.md#umianalyzer)|1.0.0 |__+1__ | | | -|[UnalR](problems.md#unalr)|1.0.0 |__+1__ | |2 | -|[UpSetR](problems.md#upsetr)|1.4.0 |__+2__ | |2 | -|[vDiveR](problems.md#vdiver)|1.2.1 |__+1__ | |1 | -|[VDSM](problems.md#vdsm)|0.1.1 |__+2__ | | | -|[virtualPollen](problems.md#virtualpollen)|1.0.1 |__+2__ | |__+1__ | -|[viscomp](problems.md#viscomp)|1.0.0 |__+1__ | | | -|[visR](problems.md#visr)|0.4.1 |__+3__ | |__+1__ | -|[vivainsights](problems.md#vivainsights)|0.5.2 |__+1__ | | | -|[vivaldi](problems.md#vivaldi)|1.0.1 |__+3__ | |1 __+1__ | -|[vvshiny](problems.md#vvshiny)|0.1.1 |__+1__ | | | -|[WASP](problems.md#wasp)|1.4.3 |__+1__ | |1 | -|[Wats](problems.md#wats)|1.0.1 |__+1__ | |__+1__ | -|[whomds](problems.md#whomds)|1.1.1 |__+1__ |1 | | -|[wilson](problems.md#wilson)|2.4.2 |__+1__ | | | -|[WVPlots](problems.md#wvplots)|1.3.8 |__+3__ | |__+1__ | -|[xaringanthemer](problems.md#xaringanthemer)|0.4.2 |1 __+1__ | | | -|[xpose](problems.md#xpose)|0.4.18 |__+3__ | |__+1__ | +|package |version |error |warning |note | +|:------------------|:-------|:--------|:-------|:--------| +|[activAnalyzer](problems.md#activanalyzer)|2.1.1 |__+1__ | |1 __+1__ | +|[actxps](problems.md#actxps)|1.5.0 |__+1__ | |__+1__ | +|[AeRobiology](problems.md#aerobiology)|2.0.1 |1 | |__+1__ | +|[agricolaeplotr](problems.md#agricolaeplotr)|0.5.0 |__+1__ | | | +|[AnalysisLin](problems.md#analysislin)|0.1.2 |__+1__ | | | +|[animbook](problems.md#animbook)|1.0.0 |__+1__ | | | +|[ANN2](problems.md#ann2)|2.3.4 |__+1__ | |3 | +|[aplot](problems.md#aplot)|0.2.3 |__+1__ | | | +|[applicable](problems.md#applicable)|0.1.1 |__+1__ | | | +|[ASRgenomics](problems.md#asrgenomics)|1.1.4 |__+1__ | |1 | +|[autoplotly](problems.md#autoplotly)|0.1.4 |__+2__ | | | +|[autoReg](problems.md#autoreg)|0.3.3 |__+2__ | |__+1__ | +|[bartMan](problems.md#bartman)|0.1.0 |__+1__ | | | +|[bayesAB](problems.md#bayesab)|1.1.3 |__+1__ | | | +|[BayesGrowth](problems.md#bayesgrowth)|1.0.0 |__+1__ | |2 __+1__ | +|[BayesianReasoning](problems.md#bayesianreasoning)|0.4.2 |__+2__ | |__+1__ | +|[BayesMallows](problems.md#bayesmallows)|2.2.1 |__+1__ | |1 | +|[bayesplot](problems.md#bayesplot)|1.11.1 |1 __+1__ | |1 | +|[bayestestR](problems.md#bayestestr)|0.13.2 |1 __+1__ | | | +|[beastt](problems.md#beastt)|0.0.1 |__+2__ | |__+1__ | +|[besthr](problems.md#besthr)|0.3.2 |__+2__ | |__+1__ | +|[biclustermd](problems.md#biclustermd)|0.2.3 |__+1__ | |1 | +|[biodosetools](problems.md#biodosetools)|3.6.1 |__+1__ | | | +|[boxly](problems.md#boxly)|0.1.1 |__+1__ | | | +|[braidReports](problems.md#braidreports)|0.5.4 |__+1__ | | | +|[breathtestcore](problems.md#breathtestcore)|0.8.7 |__+1__ | | | +|[brolgar](problems.md#brolgar)|1.0.1 |1 __+1__ | |1 | +|[cartograflow](problems.md#cartograflow)|1.0.5 |__+1__ | | | +|[cartographr](problems.md#cartographr)|0.2.2 |__+1__ | |1 | +|[cats](problems.md#cats)|1.0.2 |__+1__ | |1 | +|[cheem](problems.md#cheem)|0.4.0.0 |1 __+1__ | | | +|[chillR](problems.md#chillr)|0.75 |__+1__ | | | +|[chronicle](problems.md#chronicle)|0.3 |__+2__ | |1 __+1__ | +|[circhelp](problems.md#circhelp)|1.1 |__+2__ | |__+1__ | +|[clifro](problems.md#clifro)|3.2-5 |__+1__ | | | +|[clinDataReview](problems.md#clindatareview)|1.6.1 |__+2__ | |1 __+1__ | +|[clinUtils](problems.md#clinutils)|0.2.0 |__+1__ |-1 |1 __+1__ | +|[CohortPlat](problems.md#cohortplat)|1.0.5 |__+2__ | |__+1__ | +|[CoreMicrobiomeR](problems.md#coremicrobiomer)|0.1.0 |__+1__ | | | +|[correlationfunnel](problems.md#correlationfunnel)|0.2.0 |__+1__ | |1 | +|[corrViz](problems.md#corrviz)|0.1.0 |__+2__ | |1 __+1__ | +|[countfitteR](problems.md#countfitter)|1.4 |__+1__ | | | +|[covidcast](problems.md#covidcast)|0.5.2 |__+2__ | |1 __+1__ | +|[crosshap](problems.md#crosshap)|1.4.0 |__+1__ | | | +|[ctrialsgov](problems.md#ctrialsgov)|0.2.5 |__+1__ | |1 | +|[cubble](problems.md#cubble)|0.3.1 |__+1__ | |1 __+1__ | +|[deeptime](problems.md#deeptime)|1.1.1 |__+1__ | | | +|[distributional](problems.md#distributional)|0.4.0 |__+1__ | | | +|[dittoViz](problems.md#dittoviz)|1.0.1 |__+2__ | | | +|[EGM](problems.md#egm)|0.1.0 |__+1__ | | | +|[entropart](problems.md#entropart)|1.6-13 |__+2__ | |__+1__ | +|[epiCleanr](problems.md#epicleanr)|0.2.0 |__+1__ | |1 | +|[esci](problems.md#esci)|1.0.3 |__+2__ | | | +|[evalITR](problems.md#evalitr)|1.0.0 |1 | |1 __+1__ | +|[eventstudyr](problems.md#eventstudyr)|1.1.3 |__+1__ | | | +|[EvoPhylo](problems.md#evophylo)|0.3.2 |1 __+1__ | |1 __+1__ | +|[expirest](problems.md#expirest)|0.1.6 |__+1__ | | | +|[explainer](problems.md#explainer)|1.0.1 |__+1__ | |1 | +|[ezEDA](problems.md#ezeda)|0.1.1 |__+1__ | | | +|[ezplot](problems.md#ezplot)|0.7.13 |__+2__ | |__+1__ | +|[fable.prophet](problems.md#fableprophet)|0.1.0 |__+1__ | |1 __+1__ | +|[fabletools](problems.md#fabletools)|0.4.2 |__+2__ | | | +|[factoextra](problems.md#factoextra)|1.0.7 |__+1__ | | | +|[fairmodels](problems.md#fairmodels)|1.2.1 |__+1__ | | | +|[fddm](problems.md#fddm)|1.0-2 |__+1__ | |1 | +|[feasts](problems.md#feasts)|0.3.2 |__+1__ | | | +|[ffp](problems.md#ffp)|0.2.2 |__+1__ | | | +|[fido](problems.md#fido)|1.1.1 |1 __+2__ | |2 | +|[flipr](problems.md#flipr)|0.3.3 |1 | |1 __+1__ | +|[foqat](problems.md#foqat)|2.0.8.2 |__+1__ | |__+1__ | +|[forestly](problems.md#forestly)|0.1.1 |__+1__ | |__+1__ | +|[frailtyEM](problems.md#frailtyem)|1.0.1 |__+1__ | |2 | +|[funcharts](problems.md#funcharts)|1.4.1 |__+1__ | | | +|[geomtextpath](problems.md#geomtextpath)|0.1.4 |__+2__ | | | +|[GGally](problems.md#ggally)|2.2.1 |__+1__ | | | +|[gganimate](problems.md#gganimate)|1.0.9 |__+2__ | |__+1__ | +|[ggbrain](problems.md#ggbrain)|0.8.1 |__+1__ | |1 __+1__ | +|[ggbreak](problems.md#ggbreak)|0.1.2 |__+2__ | |__+1__ | +|[ggdark](problems.md#ggdark)|0.2.1 |__+2__ | |1 | +|[ggdist](problems.md#ggdist)|3.3.2 |1 __+2__ | |1 __+1__ | +|[ggDoubleHeat](problems.md#ggdoubleheat)|0.1.2 |__+1__ | | | +|[ggeasy](problems.md#ggeasy)|0.1.4 |__+3__ | |__+1__ | +|[ggedit](problems.md#ggedit)|0.4.1 |__+1__ | | | +|[ggESDA](problems.md#ggesda)|0.2.0 |__+1__ | | | +|[ggfixest](problems.md#ggfixest)|0.1.0 |1 __+1__ | | | +|[ggforce](problems.md#ggforce)|0.4.2 |__+1__ | |1 | +|[ggformula](problems.md#ggformula)|0.12.0 | |__+1__ |1 | +|[ggfortify](problems.md#ggfortify)|0.4.17 |__+1__ | | | +|[gggenomes](problems.md#gggenomes)|1.0.0 |__+2__ | |__+1__ | +|[ggh4x](problems.md#ggh4x)|0.2.8 |1 __+2__ | |__+1__ | +|[gghighlight](problems.md#gghighlight)|0.4.1 |__+3__ | |__+1__ | +|[ggHoriPlot](problems.md#gghoriplot)|1.0.1 |__+1__ | |__+1__ | +|[ggiraph](problems.md#ggiraph)|0.8.10 |__+2__ | |1 | +|[ggiraphExtra](problems.md#ggiraphextra)|0.3.0 |__+2__ | |__+1__ | +|[ggmice](problems.md#ggmice)|0.1.0 |__+1__ | |__+1__ | +|[ggmulti](problems.md#ggmulti)|1.0.7 |__+3__ | |__+1__ | +|[ggnewscale](problems.md#ggnewscale)|0.4.10 |__+2__ | | | +|[ggparallel](problems.md#ggparallel)|0.4.0 |__+1__ | | | +|[ggpicrust2](problems.md#ggpicrust2)|1.7.3 |__+1__ | |1 | +|[ggpie](problems.md#ggpie)|0.2.5 |__+2__ | |__+1__ | +|[ggplotlyExtra](problems.md#ggplotlyextra)|0.0.1 |__+1__ | |1 | +|[ggpol](problems.md#ggpol)|0.0.7 |__+1__ | |2 | +|[ggpubr](problems.md#ggpubr)|0.6.0 |__+1__ | | | +|[ggraph](problems.md#ggraph)|2.2.1 |1 __+1__ | |1 __+1__ | +|[ggredist](problems.md#ggredist)|0.0.2 |__+1__ | | | +|[ggRtsy](problems.md#ggrtsy)|0.1.0 |__+2__ | |1 __+1__ | +|[ggseqplot](problems.md#ggseqplot)|0.8.4 |__+3__ | |__+1__ | +|[ggside](problems.md#ggside)|0.3.1 |__+1__ |__+1__ | | +|[ggspatial](problems.md#ggspatial)|1.1.9 |__+2__ | | | +|[ggtern](problems.md#ggtern)|3.5.0 |__+1__ | |2 | +|[ggupset](problems.md#ggupset)|0.4.0 |__+1__ | | | +|[ggVennDiagram](problems.md#ggvenndiagram)|1.5.2 |__+1__ | |1 __+1__ | +|[greatR](problems.md#greatr)|2.0.0 |__+1__ | |__+1__ | +|[Greymodels](problems.md#greymodels)|2.0.1 |__+1__ | | | +|[gtExtras](problems.md#gtextras)|0.5.0 |__+1__ | | | +|[HaploCatcher](problems.md#haplocatcher)|1.0.4 |__+1__ | |__+1__ | +|[healthyR](problems.md#healthyr)|0.2.2 |__+1__ | |1 __+1__ | +|[healthyR.ts](problems.md#healthyrts)|0.3.0 |__+2__ | |1 __+1__ | +|[heatmaply](problems.md#heatmaply)|1.5.0 |__+2__ | |1 __+1__ | +|[hermiter](problems.md#hermiter)|2.3.1 |__+1__ | |2 __+1__ | +|[hesim](problems.md#hesim)|0.5.4 |__+1__ | |2 | +|[hidecan](problems.md#hidecan)|1.1.0 |1 __+1__ | |__+1__ | +|[HVT](problems.md#hvt)|24.5.2 |__+1__ | | | +|[hypsoLoop](problems.md#hypsoloop)|0.2.0 | |__+1__ | | +|[ICvectorfields](problems.md#icvectorfields)|0.1.2 |__+1__ | |__+1__ | +|[idopNetwork](problems.md#idopnetwork)|0.1.2 |__+1__ | |__+1__ | +|[inferCSN](problems.md#infercsn)|1.0.5 |__+1__ | |1 | +|[insurancerating](problems.md#insurancerating)|0.7.4 |__+1__ | | | +|[inTextSummaryTable](problems.md#intextsummarytable)|3.3.3 |__+2__ | |1 __+1__ | +|[karel](problems.md#karel)|0.1.1 |__+2__ | |1 | +|[kDGLM](problems.md#kdglm)|1.2.0 |1 __+1__ | | | +|[latentcor](problems.md#latentcor)|2.0.1 |__+1__ | | | +|[lcars](problems.md#lcars)|0.3.8 |__+2__ | | | +|[lemon](problems.md#lemon)|0.4.9 |__+3__ | |__+1__ | +|[lfproQC](problems.md#lfproqc)|0.1.0 |__+2__ | |1 __+1__ | +|[LMoFit](problems.md#lmofit)|0.1.7 |__+1__ | |1 __+1__ | +|[manydata](problems.md#manydata)|0.9.3 |__+1__ | |1 | +|[MARVEL](problems.md#marvel)|1.4.0 |__+2__ | |__+1__ | +|[MBNMAdose](problems.md#mbnmadose)|0.4.3 |__+1__ | |1 __+1__ | +|[MBNMAtime](problems.md#mbnmatime)|0.2.4 |1 | |__+1__ | +|[MetaNet](problems.md#metanet)|0.1.2 |__+1__ | | | +|[metR](problems.md#metr)|0.15.0 |__+2__ | |1 __+1__ | +|[migraph](problems.md#migraph)|1.3.4 |__+1__ | | | +|[MiMIR](problems.md#mimir)|1.5 |__+1__ | | | +|[miRetrieve](problems.md#miretrieve)|1.3.4 |__+1__ | | | +|[misspi](problems.md#misspi)|0.1.0 |__+1__ | | | +|[mizer](problems.md#mizer)|2.5.1 |__+1__ | |1 | +|[mlr3spatiotempcv](problems.md#mlr3spatiotempcv)|2.3.1 |1 __+1__ | |1 | +|[mlr3viz](problems.md#mlr3viz)|0.9.0 |__+1__ | | | +|[modeltime.resample](problems.md#modeltimeresample)|0.2.3 |__+1__ | |1 | +|[move](problems.md#move)|4.2.4 |1 | |__+1__ | +|[mtb](problems.md#mtb)|0.1.8 |__+1__ | | | +|[neatmaps](problems.md#neatmaps)|2.1.0 |__+1__ | |1 | +|[NetFACS](problems.md#netfacs)|0.5.0 |__+2__ | | | +|[NeuralSens](problems.md#neuralsens)|1.1.3 |__+1__ | | | +|[NHSRplotthedots](problems.md#nhsrplotthedots)|0.1.0 |__+1__ | |1 | +|[NIMAA](problems.md#nimaa)|0.2.1 |__+3__ | |2 __+1__ | +|[OBIC](problems.md#obic)|3.0.2 |__+1__ | |1 __+1__ | +|[OmicNavigator](problems.md#omicnavigator)|1.13.13 |__+1__ | |1 | +|[oncomsm](problems.md#oncomsm)|0.1.4 |__+2__ | |2 __+1__ | +|[pafr](problems.md#pafr)|0.0.2 |__+1__ | |1 | +|[patchwork](problems.md#patchwork)|1.2.0 |__+1__ | | | +|[pathviewr](problems.md#pathviewr)|1.1.7 |__+1__ | | | +|[pcutils](problems.md#pcutils)|0.2.6 |__+1__ | | | +|[pdxTrees](problems.md#pdxtrees)|0.4.0 |__+1__ | |1 __+1__ | +|[personalized](problems.md#personalized)|0.2.7 |__+1__ | | | +|[phylepic](problems.md#phylepic)|0.2.0 |__+1__ | |__+1__ | +|[Plasmidprofiler](problems.md#plasmidprofiler)|0.1.6 |__+1__ | | | +|[platetools](problems.md#platetools)|0.1.7 |__+1__ | | | +|[plotDK](problems.md#plotdk)|0.1.0 |__+1__ | |2 | +|[plotly](problems.md#plotly)|4.10.4 |__+2__ | |1 | +|[pmartR](problems.md#pmartr)|2.4.5 |__+1__ | |1 | +|[pmxTools](problems.md#pmxtools)|1.3 |__+1__ | |1 | +|[posterior](problems.md#posterior)|1.6.0 |1 | |__+1__ | +|[PPQplan](problems.md#ppqplan)|1.1.0 |1 | |2 __+1__ | +|[ppseq](problems.md#ppseq)|0.2.4 |__+1__ | |1 __+1__ | +|[precrec](problems.md#precrec)|0.14.4 |__+1__ | |1 __+1__ | +|[priorsense](problems.md#priorsense)|1.0.1 |__+2__ | |__+1__ | +|[ProAE](problems.md#proae)|1.0.1 |__+1__ | |__+1__ | +|[probably](problems.md#probably)|1.0.3 |__+1__ | | | +|[processmapR](problems.md#processmapr)|0.5.4 |__+1__ | | | +|[psborrow](problems.md#psborrow)|0.2.1 |__+1__ | | | +|[r2dii.plot](problems.md#r2diiplot)|0.4.0 |__+1__ | | | +|[Radviz](problems.md#radviz)|0.9.3 |__+2__ | |__+1__ | +|[rassta](problems.md#rassta)|1.0.5 |__+3__ | | | +|[REddyProc](problems.md#reddyproc)|1.3.3 | | |__+1__ | +|[redist](problems.md#redist)|4.2.0 |__+1__ | |1 __+1__ | +|[reReg](problems.md#rereg)|1.4.6 |__+1__ | | | +|[reservr](problems.md#reservr)|0.0.3 |1 __+1__ | |2 __+1__ | +|[rKOMICS](problems.md#rkomics)|1.3 |__+1__ | |2 | +|[RKorAPClient](problems.md#rkorapclient)|0.8.1 |__+1__ | | | +|[RNAseqQC](problems.md#rnaseqqc)|0.2.1 |__+1__ | |1 __+1__ | +|[roahd](problems.md#roahd)|1.4.3 |__+1__ | |1 | +|[romic](problems.md#romic)|1.1.3 |__+1__ | | | +|[roptions](problems.md#roptions)|1.0.3 |__+1__ | |1 | +|[santaR](problems.md#santar)|1.2.4 |1 __+1__ | | | +|[scdtb](problems.md#scdtb)|0.1.0 |__+1__ | | | +|[scoringutils](problems.md#scoringutils)|1.2.2 |1 __+1__ | |__+1__ | +|[scUtils](problems.md#scutils)|0.1.0 |__+1__ | |1 | +|[SCVA](problems.md#scva)|1.3.1 |__+1__ | | | +|[SDMtune](problems.md#sdmtune)|1.3.1 |1 __+1__ | |1 | +|[SeaVal](problems.md#seaval)|1.2.0 |__+1__ | |1 | +|[sglg](problems.md#sglg)|0.2.2 |__+1__ | | | +|[sgsR](problems.md#sgsr)|1.4.5 |__+1__ | | | +|[SHAPforxgboost](problems.md#shapforxgboost)|0.1.3 |__+1__ | | | +|[SHELF](problems.md#shelf)|1.10.0 | | |__+1__ | +|[shinipsum](problems.md#shinipsum)|0.1.1 |__+1__ | | | +|[SimNPH](problems.md#simnph)|0.5.5 |__+1__ | | | +|[smallsets](problems.md#smallsets)|2.0.0 |__+2__ | |1 __+1__ | +|[spbal](problems.md#spbal)|1.0.0 |__+1__ | |__+1__ | +|[spinifex](problems.md#spinifex)|0.3.7.0 |__+1__ | | | +|[sport](problems.md#sport)|0.2.1 |__+1__ | |1 | +|[SqueakR](problems.md#squeakr)|1.3.0 |1 | |1 __+1__ | +|[statgenGWAS](problems.md#statgengwas)|1.0.9 |__+1__ | |2 | +|[surveyexplorer](problems.md#surveyexplorer)|0.2.0 |__+1__ | | | +|[Sysrecon](problems.md#sysrecon)|0.1.3 |__+1__ | |1 | +|[tabledown](problems.md#tabledown)|1.0.0 |__+1__ | |1 | +|[TCIU](problems.md#tciu)|1.2.6 |__+2__ | |1 __+1__ | +|[tensorEVD](problems.md#tensorevd)|0.1.3 |__+1__ | |__+1__ | +|[thematic](problems.md#thematic)|0.1.5 |__+2__ | | | +|[tidybayes](problems.md#tidybayes)|3.0.6 |2 __+1__ | | | +|[tidycat](problems.md#tidycat)|0.1.2 |__+2__ | |1 __+1__ | +|[tidyCDISC](problems.md#tidycdisc)|0.2.1 |__+1__ | |1 | +|[tidysdm](problems.md#tidysdm)|0.9.5 |__+1__ | |1 __+1__ | +|[tidytreatment](problems.md#tidytreatment)|0.2.2 |__+1__ | |1 __+1__ | +|[timetk](problems.md#timetk)|2.9.0 |__+1__ | |1 | +|[tinyarray](problems.md#tinyarray)|2.4.2 |__+1__ | | | +|[tornado](problems.md#tornado)|0.1.3 |__+3__ | |__+1__ | +|[TOSTER](problems.md#toster)|0.8.3 |__+3__ | |__+1__ | +|[TreatmentPatterns](problems.md#treatmentpatterns)|2.6.7 |__+1__ | | | +|[trelliscopejs](problems.md#trelliscopejs)|0.2.6 |__+1__ | | | +|[tricolore](problems.md#tricolore)|1.2.4 |__+2__ | |1 __+1__ | +|[triptych](problems.md#triptych)|0.1.3 |__+1__ | | | +|[tsnet](problems.md#tsnet)|0.1.0 |__+1__ | |2 | +|[umiAnalyzer](problems.md#umianalyzer)|1.0.0 |__+1__ | | | +|[valr](problems.md#valr)|0.8.1 |__+1__ | |1 | +|[vivaldi](problems.md#vivaldi)|1.0.1 |__+3__ | |1 __+1__ | +|[vivid](problems.md#vivid)|0.2.8 |__+1__ | | | +|[vvshiny](problems.md#vvshiny)|0.1.1 |__+1__ | | | +|[wilson](problems.md#wilson)|2.4.2 |__+1__ | | | +|[xaringanthemer](problems.md#xaringanthemer)|0.4.2 |1 __+1__ | | | +|[yamlet](problems.md#yamlet)|1.0.3 |__+2__ | | | diff --git a/revdep/cran.md b/revdep/cran.md index a1302e8947..4a9f813633 100644 --- a/revdep/cran.md +++ b/revdep/cran.md @@ -1,18 +1,15 @@ ## revdepcheck results -We checked 5085 reverse dependencies, comparing R CMD check results across CRAN and dev versions of this package. +We checked 5166 reverse dependencies, comparing R CMD check results across CRAN and dev versions of this package. - * We saw 366 new problems - * We failed to check 191 packages + * We saw 242 new problems + * We failed to check 132 packages Issues with CRAN packages are summarised below. ### New problems (This reports the first line of each new failure) -* accSDA - checking examples ... ERROR - * activAnalyzer checking running R code from vignettes ... ERROR checking re-building of vignette outputs ... NOTE @@ -21,23 +18,11 @@ Issues with CRAN packages are summarised below. checking running R code from vignettes ... ERROR checking re-building of vignette outputs ... NOTE -* add2ggplot - checking examples ... ERROR - checking running R code from vignettes ... ERROR - checking re-building of vignette outputs ... NOTE - * AeRobiology checking re-building of vignette outputs ... NOTE -* afex - checking running R code from vignettes ... ERROR - checking re-building of vignette outputs ... NOTE - -* AgroR - checking examples ... ERROR - -* allMT - checking examples ... ERROR +* agricolaeplotr + checking tests ... ERROR * AnalysisLin checking examples ... ERROR @@ -45,33 +30,31 @@ Issues with CRAN packages are summarised below. * animbook checking examples ... ERROR +* ANN2 + checking tests ... ERROR + * aplot checking examples ... ERROR -* ASRgenomics - checking examples ... ERROR +* applicable checking tests ... ERROR -* auditor - checking examples ... ERROR - checking running R code from vignettes ... ERROR - checking re-building of vignette outputs ... NOTE - -* augmentedRCBD +* ASRgenomics checking examples ... ERROR - checking re-building of vignette outputs ... ERROR * autoplotly checking examples ... ERROR checking tests ... ERROR -* baggr +* autoReg checking examples ... ERROR checking running R code from vignettes ... ERROR checking re-building of vignette outputs ... NOTE -* bayefdr +* bartMan checking examples ... ERROR + +* bayesAB checking tests ... ERROR * BayesGrowth @@ -79,69 +62,53 @@ Issues with CRAN packages are summarised below. checking re-building of vignette outputs ... NOTE * BayesianReasoning + checking tests ... ERROR checking running R code from vignettes ... ERROR checking re-building of vignette outputs ... NOTE -* bayestestR - checking examples ... ERROR - -* bdots - checking running R code from vignettes ... ERROR - checking re-building of vignette outputs ... NOTE - -* bdrc - checking running R code from vignettes ... ERROR - checking re-building of vignette outputs ... NOTE +* BayesMallows + checking tests ... ERROR -* BeeBDC +* bayesplot checking tests ... ERROR -* besthr +* bayestestR checking examples ... ERROR - checking running R code from vignettes ... ERROR - checking re-building of vignette outputs ... NOTE -* BetaPASS +* beastt checking examples ... ERROR checking running R code from vignettes ... ERROR checking re-building of vignette outputs ... NOTE -* biblioverlap - checking examples ... ERROR - -* biscale +* besthr checking examples ... ERROR - -* BlandAltmanLeh - checking running R code from vignettes ... ERROR - -* bnma checking running R code from vignettes ... ERROR checking re-building of vignette outputs ... NOTE -* boxly +* biclustermd checking tests ... ERROR -* braidReports - checking examples ... ERROR +* biodosetools + checking tests ... ERROR -* brolgar - checking examples ... ERROR - checking running R code from vignettes ... ERROR - checking re-building of vignette outputs ... NOTE +* boxly + checking tests ... ERROR -* calendR +* braidReports checking examples ... ERROR -* calendRio - checking examples ... ERROR +* breathtestcore + checking tests ... ERROR -* capm +* brolgar checking examples ... ERROR * cartograflow checking examples ... ERROR +* cartographr + checking tests ... ERROR + * cats checking examples ... ERROR @@ -156,17 +123,13 @@ Issues with CRAN packages are summarised below. checking running R code from vignettes ... ERROR checking re-building of vignette outputs ... NOTE -* circumplex - checking running R code from vignettes ... ERROR - checking re-building of vignette outputs ... NOTE - -* cities +* circhelp checking examples ... ERROR checking running R code from vignettes ... ERROR checking re-building of vignette outputs ... NOTE -* CleaningValidation - checking examples ... ERROR +* clifro + checking tests ... ERROR * clinDataReview checking examples ... ERROR @@ -177,30 +140,11 @@ Issues with CRAN packages are summarised below. checking running R code from vignettes ... ERROR checking re-building of vignette outputs ... NOTE -* ClustImpute - checking running R code from vignettes ... ERROR - -* cogmapr - checking examples ... ERROR - * CohortPlat checking examples ... ERROR checking running R code from vignettes ... ERROR checking re-building of vignette outputs ... NOTE -* CoMiRe - checking examples ... ERROR - -* CommKern - checking examples ... ERROR - checking running R code from vignettes ... ERROR - checking re-building of vignette outputs ... NOTE - -* conText - checking examples ... ERROR - checking running R code from vignettes ... ERROR - checking re-building of vignette outputs ... NOTE - * CoreMicrobiomeR checking examples ... ERROR @@ -212,22 +156,17 @@ Issues with CRAN packages are summarised below. checking running R code from vignettes ... ERROR checking re-building of vignette outputs ... NOTE +* countfitteR + checking tests ... ERROR + * covidcast checking tests ... ERROR checking running R code from vignettes ... ERROR checking re-building of vignette outputs ... NOTE -* cricketdata - checking re-building of vignette outputs ... NOTE - * crosshap checking examples ... ERROR -* crplyr - checking tests ... ERROR - checking running R code from vignettes ... ERROR - checking re-building of vignette outputs ... NOTE - * ctrialsgov checking tests ... ERROR @@ -235,37 +174,8 @@ Issues with CRAN packages are summarised below. checking running R code from vignettes ... ERROR checking re-building of vignette outputs ... NOTE -* dabestr - checking examples ... ERROR - checking tests ... ERROR - checking running R code from vignettes ... ERROR - checking re-building of vignette outputs ... NOTE - -* DAISIEprep - checking tests ... ERROR - -* dataresqc - checking examples ... ERROR - -* ddtlcm - checking examples ... ERROR - checking tests ... ERROR - checking running R code from vignettes ... ERROR - checking re-building of vignette outputs ... NOTE - -* dfoliatR - checking examples ... ERROR - checking tests ... ERROR - checking running R code from vignettes ... ERROR - checking re-building of vignette outputs ... NOTE - -* directlabels - checking running R code from vignettes ... ERROR - checking re-building of vignette outputs ... NOTE - -* disprofas +* deeptime checking examples ... ERROR - checking tests ... ERROR * distributional checking examples ... ERROR @@ -274,69 +184,39 @@ Issues with CRAN packages are summarised below. checking examples ... ERROR checking tests ... ERROR -* dobin - checking running R code from vignettes ... ERROR - checking re-building of vignette outputs ... NOTE - -* dogesr - checking re-building of vignette outputs ... NOTE - -* dotsViolin - checking examples ... ERROR - -* ds4psy - checking examples ... ERROR - -* edecob - checking examples ... ERROR +* EGM + checking tests ... ERROR * entropart checking examples ... ERROR checking running R code from vignettes ... ERROR checking re-building of vignette outputs ... NOTE -* envalysis - checking examples ... ERROR - checking tests ... ERROR - checking running R code from vignettes ... ERROR - checking re-building of vignette outputs ... NOTE - * epiCleanr checking examples ... ERROR -* EpiInvert - checking examples ... ERROR - * esci checking examples ... ERROR checking tests ... ERROR -* EvidenceSynthesis - checking examples ... ERROR - checking tests ... ERROR - checking running R code from vignettes ... ERROR +* evalITR checking re-building of vignette outputs ... NOTE -* EvolutionaryGames - checking examples ... ERROR - checking running R code from vignettes ... ERROR - checking re-building of vignette outputs ... NOTE +* eventstudyr + checking tests ... ERROR * EvoPhylo checking examples ... ERROR checking re-building of vignette outputs ... NOTE -* evprof - checking examples ... ERROR - checking tests ... ERROR - * expirest checking tests ... ERROR -* explore +* explainer checking examples ... ERROR - checking running R code from vignettes ... ERROR - checking re-building of vignette outputs ... NOTE + +* ezEDA + checking tests ... ERROR * ezplot checking examples ... ERROR @@ -354,15 +234,14 @@ Issues with CRAN packages are summarised below. * factoextra checking examples ... ERROR -* faux - checking examples ... ERROR - checking re-building of vignette outputs ... NOTE +* fairmodels + checking tests ... ERROR * fddm checking running R code from vignettes ... ERROR -* fdrci - checking examples ... ERROR +* feasts + checking tests ... ERROR * ffp checking examples ... ERROR @@ -371,23 +250,16 @@ Issues with CRAN packages are summarised below. checking examples ... ERROR checking tests ... ERROR -* figuRes2 - checking examples ... ERROR - checking running R code from vignettes ... ERROR - * flipr checking re-building of vignette outputs ... NOTE -* FMM +* foqat checking running R code from vignettes ... ERROR checking re-building of vignette outputs ... NOTE -* fmriqa - checking tests ... ERROR - -* foreSIGHT - checking examples ... ERROR - checking re-building of vignette outputs ... ERROR +* forestly + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE * frailtyEM checking examples ... ERROR @@ -395,38 +267,18 @@ Issues with CRAN packages are summarised below. * funcharts checking examples ... ERROR -* gapmap - checking examples ... ERROR - checking running R code from vignettes ... ERROR - checking re-building of vignette outputs ... NOTE - -* gasper - checking examples ... ERROR - checking running R code from vignettes ... ERROR - -* gaussplotR - checking running R code from vignettes ... ERROR - checking re-building of vignette outputs ... NOTE - -* gg.gap +* geomtextpath checking examples ... ERROR - -* ggalignment checking tests ... ERROR - checking running R code from vignettes ... ERROR - checking re-building of vignette outputs ... NOTE -* ggalt - checking re-building of vignette outputs ... NOTE +* GGally + checking tests ... ERROR * gganimate checking tests ... ERROR checking running R code from vignettes ... ERROR checking re-building of vignette outputs ... NOTE -* ggbrace - checking examples ... ERROR - * ggbrain checking running R code from vignettes ... ERROR checking re-building of vignette outputs ... NOTE @@ -445,46 +297,48 @@ Issues with CRAN packages are summarised below. checking tests ... ERROR checking re-building of vignette outputs ... NOTE -* ggedit +* ggDoubleHeat checking examples ... ERROR -* ggExtra +* ggeasy + checking examples ... ERROR + checking tests ... ERROR checking running R code from vignettes ... ERROR checking re-building of vignette outputs ... NOTE -* ggfixest - checking tests ... ERROR +* ggedit + checking examples ... ERROR -* ggflowchart +* ggESDA checking examples ... ERROR - checking running R code from vignettes ... ERROR - checking re-building of vignette outputs ... NOTE + +* ggfixest + checking tests ... ERROR * ggforce checking examples ... ERROR +* ggformula + checking for code/documentation mismatches ... WARNING + * ggfortify checking tests ... ERROR -* ggfoundry +* gggenomes + checking examples ... ERROR checking running R code from vignettes ... ERROR checking re-building of vignette outputs ... NOTE -* gggap - checking examples ... ERROR - * ggh4x checking examples ... ERROR checking tests ... ERROR checking re-building of vignette outputs ... NOTE -* gghdx - checking examples ... ERROR - checking re-building of vignette outputs ... NOTE - * gghighlight checking examples ... ERROR checking tests ... ERROR + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE * ggHoriPlot checking running R code from vignettes ... ERROR @@ -499,9 +353,6 @@ Issues with CRAN packages are summarised below. checking running R code from vignettes ... ERROR checking re-building of vignette outputs ... NOTE -* ggmap - checking examples ... ERROR - * ggmice checking running R code from vignettes ... ERROR checking re-building of vignette outputs ... NOTE @@ -512,6 +363,10 @@ Issues with CRAN packages are summarised below. checking running R code from vignettes ... ERROR checking re-building of vignette outputs ... NOTE +* ggnewscale + checking examples ... ERROR + checking tests ... ERROR + * ggparallel checking tests ... ERROR @@ -529,11 +384,7 @@ Issues with CRAN packages are summarised below. * ggpol checking examples ... ERROR -* ggprism - checking examples ... ERROR - * ggpubr - checking examples ... ERROR checking tests ... ERROR * ggraph @@ -543,8 +394,8 @@ Issues with CRAN packages are summarised below. * ggredist checking examples ... ERROR -* ggResidpanel - checking examples ... ERROR +* ggRtsy + checking tests ... ERROR checking running R code from vignettes ... ERROR checking re-building of vignette outputs ... NOTE @@ -558,15 +409,13 @@ Issues with CRAN packages are summarised below. checking tests ... ERROR checking for code/documentation mismatches ... WARNING -* ggstatsplot +* ggspatial + checking examples ... ERROR checking tests ... ERROR * ggtern checking examples ... ERROR -* ggthemes - checking examples ... ERROR - * ggupset checking examples ... ERROR @@ -574,9 +423,6 @@ Issues with CRAN packages are summarised below. checking running R code from vignettes ... ERROR checking re-building of vignette outputs ... NOTE -* graphPAF - checking examples ... ERROR - * greatR checking running R code from vignettes ... ERROR checking re-building of vignette outputs ... NOTE @@ -584,13 +430,6 @@ Issues with CRAN packages are summarised below. * Greymodels checking examples ... ERROR -* groupdata2 - checking running R code from vignettes ... ERROR - checking re-building of vignette outputs ... NOTE - -* GSD - checking examples ... ERROR - * gtExtras checking tests ... ERROR @@ -598,27 +437,16 @@ Issues with CRAN packages are summarised below. checking running R code from vignettes ... ERROR checking re-building of vignette outputs ... NOTE -* hdnom - checking examples ... ERROR - checking running R code from vignettes ... ERROR - checking re-building of vignette outputs ... NOTE - * healthyR checking running R code from vignettes ... ERROR checking re-building of vignette outputs ... NOTE -* healthyR.ai - checking examples ... ERROR - checking running R code from vignettes ... ERROR - checking re-building of vignette outputs ... NOTE - * healthyR.ts checking examples ... ERROR checking running R code from vignettes ... ERROR checking re-building of vignette outputs ... NOTE * heatmaply - checking examples ... ERROR checking tests ... ERROR checking running R code from vignettes ... ERROR checking re-building of vignette outputs ... NOTE @@ -627,36 +455,16 @@ Issues with CRAN packages are summarised below. checking running R code from vignettes ... ERROR checking re-building of vignette outputs ... NOTE -* heumilkr - checking running R code from vignettes ... ERROR - checking re-building of vignette outputs ... NOTE - -* heuristicsmineR - checking installed package size ... NOTE - -* HistDAWass - checking examples ... ERROR - -* huito - checking examples ... ERROR - checking re-building of vignette outputs ... NOTE +* hesim + checking tests ... ERROR -* hurricaneexposure - checking examples ... ERROR - checking running R code from vignettes ... ERROR +* hidecan + checking tests ... ERROR checking re-building of vignette outputs ... NOTE * HVT checking examples ... ERROR -* hydraulics - checking examples ... ERROR - checking running R code from vignettes ... ERROR - checking re-building of vignette outputs ... NOTE - -* hyperSpec - checking examples ... ERROR - * hypsoLoop checking whether package ‘hypsoLoop’ can be installed ... WARNING @@ -664,78 +472,34 @@ Issues with CRAN packages are summarised below. checking running R code from vignettes ... ERROR checking re-building of vignette outputs ... NOTE -* idiogramFISH - checking installed package size ... NOTE - * idopNetwork checking running R code from vignettes ... ERROR checking re-building of vignette outputs ... NOTE -* iglu - checking examples ... ERROR - checking running R code from vignettes ... ERROR - checking re-building of vignette outputs ... NOTE - -* igoR - checking running R code from vignettes ... ERROR - checking re-building of vignette outputs ... NOTE - -* immunarch +* inferCSN checking examples ... ERROR -* immuneSIM +* insurancerating checking examples ... ERROR -* iNEXT.4steps - checking examples ... ERROR +* inTextSummaryTable checking tests ... ERROR checking running R code from vignettes ... ERROR checking re-building of vignette outputs ... NOTE -* iNEXT.beta3D +* karel checking examples ... ERROR - -* insurancerating - checking examples ... ERROR - -* inTextSummaryTable - checking tests ... ERROR - checking re-building of vignette outputs ... NOTE - -* jskm - checking examples ... ERROR - checking tests ... ERROR - checking running R code from vignettes ... ERROR - checking re-building of vignette outputs ... NOTE - -* KaradaColor - checking examples ... ERROR - -* karel - checking examples ... ERROR - checking tests ... ERROR + checking tests ... ERROR * kDGLM checking examples ... ERROR -* labsimplex - checking examples ... ERROR - checking running R code from vignettes ... ERROR - checking re-building of vignette outputs ... NOTE - -* landscapemetrics - checking examples ... ERROR - -* landscapetools - checking examples ... ERROR - checking running R code from vignettes ... ERROR - checking re-building of vignette outputs ... NOTE - * latentcor checking examples ... ERROR -* latte +* lcars checking examples ... ERROR + checking running R code from vignettes ... ERROR * lemon checking examples ... ERROR @@ -748,33 +512,18 @@ Issues with CRAN packages are summarised below. checking running R code from vignettes ... ERROR checking re-building of vignette outputs ... NOTE -* LLSR - checking examples ... ERROR - * LMoFit checking running R code from vignettes ... ERROR checking re-building of vignette outputs ... NOTE -* lomb - checking examples ... ERROR - -* LongDat - checking running R code from vignettes ... ERROR - checking re-building of vignette outputs ... NOTE +* manydata + checking tests ... ERROR -* longitudinalcascade +* MARVEL checking examples ... ERROR - -* longmixr checking running R code from vignettes ... ERROR checking re-building of vignette outputs ... NOTE -* manhplot - checking tests ... ERROR - -* mau - checking examples ... ERROR - * MBNMAdose checking running R code from vignettes ... ERROR checking re-building of vignette outputs ... NOTE @@ -782,13 +531,7 @@ Issues with CRAN packages are summarised below. * MBNMAtime checking re-building of vignette outputs ... NOTE -* metaforest - checking tests ... ERROR - -* metan - checking examples ... ERROR - -* metaplot +* MetaNet checking examples ... ERROR * metR @@ -796,25 +539,12 @@ Issues with CRAN packages are summarised below. checking running R code from vignettes ... ERROR checking re-building of vignette outputs ... NOTE -* miceFast - checking examples ... ERROR +* migraph checking tests ... ERROR - checking running R code from vignettes ... ERROR - checking re-building of vignette outputs ... NOTE - -* MicrobiomeStat - checking examples ... ERROR - -* micromap - checking examples ... ERROR - checking running R code from vignettes ... ERROR * MiMIR checking examples ... ERROR -* MIMSunit - checking examples ... ERROR - * miRetrieve checking tests ... ERROR @@ -833,31 +563,11 @@ Issues with CRAN packages are summarised below. * modeltime.resample checking tests ... ERROR -* mosaic - checking examples ... ERROR - checking tests ... ERROR - -* motifr - checking examples ... ERROR +* move + checking installed package size ... NOTE -* mpwR - checking examples ... ERROR +* mtb checking tests ... ERROR - checking running R code from vignettes ... ERROR - checking re-building of vignette outputs ... NOTE - -* mrfDepth - checking examples ... ERROR - -* musclesyneRgies - checking examples ... ERROR - checking tests ... ERROR - checking running R code from vignettes ... ERROR - checking re-building of vignette outputs ... NOTE - -* naniar - checking running R code from vignettes ... ERROR - checking re-building of vignette outputs ... NOTE * neatmaps checking examples ... ERROR @@ -865,15 +575,12 @@ Issues with CRAN packages are summarised below. * NetFACS checking examples ... ERROR checking running R code from vignettes ... ERROR - checking re-building of vignette outputs ... NOTE -* NHSRplotthedots +* NeuralSens checking examples ... ERROR - checking running R code from vignettes ... ERROR - checking re-building of vignette outputs ... NOTE -* nima - checking examples ... ERROR +* NHSRplotthedots + checking tests ... ERROR * NIMAA checking examples ... ERROR @@ -881,68 +588,29 @@ Issues with CRAN packages are summarised below. checking running R code from vignettes ... ERROR checking re-building of vignette outputs ... NOTE -* nparACT - checking examples ... ERROR - -* nullabor - checking running R code from vignettes ... ERROR - * OBIC checking running R code from vignettes ... ERROR checking re-building of vignette outputs ... NOTE -* OddsPlotty - checking running R code from vignettes ... ERROR - checking re-building of vignette outputs ... NOTE - -* ofpetrial - checking examples ... ERROR - * OmicNavigator checking tests ... ERROR - checking running R code from vignettes ... ERROR * oncomsm checking tests ... ERROR checking running R code from vignettes ... ERROR checking re-building of vignette outputs ... NOTE -* ontophylo - checking examples ... ERROR - -* OpenLand +* pafr checking tests ... ERROR - checking running R code from vignettes ... ERROR - checking re-building of vignette outputs ... NOTE - -* ordbetareg - checking running R code from vignettes ... ERROR - checking re-building of vignette outputs ... NOTE - -* otsad - checking examples ... ERROR - -* OutliersO3 - checking running R code from vignettes ... ERROR - checking re-building of vignette outputs ... NOTE - -* palettes - checking running R code from vignettes ... ERROR - checking re-building of vignette outputs ... NOTE - -* ParBayesianOptimization - checking examples ... ERROR * patchwork checking examples ... ERROR -* pathfindR - checking examples ... ERROR - checking re-building of vignette outputs ... NOTE +* pathviewr + checking tests ... ERROR -* pdSpecEst - checking running R code from vignettes ... ERROR - checking re-building of vignette outputs ... NOTE +* pcutils + checking examples ... ERROR * pdxTrees checking running R code from vignettes ... ERROR @@ -951,12 +619,16 @@ Issues with CRAN packages are summarised below. * personalized checking tests ... ERROR -* PGRdup - checking re-building of vignette outputs ... ERROR +* phylepic + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE * Plasmidprofiler checking examples ... ERROR +* platetools + checking tests ... ERROR + * plotDK checking tests ... ERROR @@ -970,11 +642,6 @@ Issues with CRAN packages are summarised below. * pmxTools checking tests ... ERROR -* politeness - checking examples ... ERROR - checking running R code from vignettes ... ERROR - checking re-building of vignette outputs ... NOTE - * posterior checking re-building of vignette outputs ... NOTE @@ -985,50 +652,29 @@ Issues with CRAN packages are summarised below. checking running R code from vignettes ... ERROR checking re-building of vignette outputs ... NOTE -* PPtreeregViz - checking examples ... ERROR +* precrec checking running R code from vignettes ... ERROR checking re-building of vignette outputs ... NOTE -* precrec +* priorsense + checking examples ... ERROR checking running R code from vignettes ... ERROR checking re-building of vignette outputs ... NOTE -* prevR +* ProAE checking running R code from vignettes ... ERROR checking re-building of vignette outputs ... NOTE -* primerTree - checking examples ... ERROR +* probably + checking tests ... ERROR * processmapR checking tests ... ERROR -* PTXQC +* psborrow checking tests ... ERROR -* qacBase - checking examples ... ERROR - -* qgcomp - checking examples ... ERROR - checking running R code from vignettes ... ERROR - checking re-building of vignette outputs ... NOTE - -* qgcompint - checking examples ... ERROR - checking running R code from vignettes ... ERROR - checking re-building of vignette outputs ... NOTE - -* qpNCA - checking running R code from vignettes ... ERROR - checking re-building of vignette outputs ... NOTE - -* QurvE - checking examples ... ERROR - * r2dii.plot - checking examples ... ERROR checking tests ... ERROR * Radviz @@ -1036,64 +682,30 @@ Issues with CRAN packages are summarised below. checking running R code from vignettes ... ERROR checking re-building of vignette outputs ... NOTE -* rainette - checking tests ... ERROR - * rassta checking examples ... ERROR checking tests ... ERROR checking running R code from vignettes ... ERROR -* RAT - checking examples ... ERROR - -* Rcan - checking examples ... ERROR +* REddyProc + checking installed package size ... NOTE * redist checking running R code from vignettes ... ERROR checking re-building of vignette outputs ... NOTE -* Relectoral - checking examples ... ERROR - -* reliabilitydiag - checking examples ... ERROR - -* relliptical - checking examples ... ERROR - -* Repliscope - checking examples ... ERROR - -* reportRmd - checking examples ... ERROR - checking running R code from vignettes ... ERROR - checking re-building of vignette outputs ... NOTE - * reReg checking examples ... ERROR * reservr - checking examples ... ERROR - checking running R code from vignettes ... ERROR - checking re-building of vignette outputs ... NOTE - -* restriktor - checking examples ... ERROR - -* RevGadgets - checking tests ... ERROR - -* rimu checking examples ... ERROR checking re-building of vignette outputs ... NOTE * rKOMICS checking examples ... ERROR -* rmcorr - checking re-building of vignette outputs ... NOTE +* RKorAPClient + checking tests ... ERROR * RNAseqQC checking running R code from vignettes ... ERROR @@ -1102,148 +714,88 @@ Issues with CRAN packages are summarised below. * roahd checking examples ... ERROR -* robustbase - checking running R code from vignettes ... ERROR - * romic checking tests ... ERROR * roptions checking examples ... ERROR -* rotations - checking examples ... ERROR - checking running R code from vignettes ... ERROR - -* rreg - checking examples ... ERROR - -* rSDI - checking running R code from vignettes ... ERROR - checking re-building of vignette outputs ... NOTE - -* SangerTools - checking examples ... ERROR - checking running R code from vignettes ... ERROR - checking re-building of vignette outputs ... NOTE - * santaR - checking re-building of vignette outputs ... NOTE + checking tests ... ERROR + +* scdtb + checking tests ... ERROR * scoringutils checking examples ... ERROR checking re-building of vignette outputs ... NOTE -* SCVA - checking examples ... ERROR - -* SDLfilter - checking examples ... ERROR +* scUtils + checking tests ... ERROR -* see +* SCVA checking examples ... ERROR -* sentimentr - checking examples ... ERROR +* SDMtune + checking tests ... ERROR -* sentometrics +* SeaVal checking examples ... ERROR * sglg checking examples ... ERROR +* sgsR + checking tests ... ERROR + * SHAPforxgboost checking examples ... ERROR -* shazam - checking examples ... ERROR - checking running R code from vignettes ... ERROR +* SHELF checking re-building of vignette outputs ... NOTE -* simulariatools - checking examples ... ERROR - -* sjPlot - checking examples ... ERROR - checking running R code from vignettes ... ERROR - checking re-building of vignette outputs ... NOTE +* shinipsum + checking tests ... ERROR -* SleepCycles - checking examples ... ERROR +* SimNPH + checking tests ... ERROR * smallsets checking examples ... ERROR checking running R code from vignettes ... ERROR checking re-building of vignette outputs ... NOTE -* smdi - checking re-building of vignette outputs ... NOTE - -* soc.ca - checking examples ... ERROR - * spbal checking running R code from vignettes ... ERROR checking re-building of vignette outputs ... NOTE -* speccurvieR - checking examples ... ERROR - * spinifex checking tests ... ERROR -* spotoroo +* sport checking tests ... ERROR - checking running R code from vignettes ... ERROR - checking re-building of vignette outputs ... NOTE * SqueakR checking re-building of vignette outputs ... NOTE -* stabm - checking examples ... ERROR - checking tests ... ERROR - checking running R code from vignettes ... ERROR - checking re-building of vignette outputs ... NOTE - -* starvz - checking examples ... ERROR - -* statgenMPP - checking tests ... ERROR - checking running R code from vignettes ... ERROR - checking re-building of vignette outputs ... NOTE - -* statVisual - checking examples ... ERROR - checking running R code from vignettes ... ERROR - checking re-building of vignette outputs ... NOTE - -* superheat - checking examples ... ERROR +* statgenGWAS checking tests ... ERROR * surveyexplorer checking examples ... ERROR -* survivalAnalysis - checking examples ... ERROR - checking re-building of vignette outputs ... NOTE - * Sysrecon checking examples ... ERROR * tabledown checking examples ... ERROR -* tabr +* TCIU checking examples ... ERROR - -* TcGSA checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE -* TCIU - checking examples ... ERROR +* tensorEVD checking running R code from vignettes ... ERROR checking re-building of vignette outputs ... NOTE @@ -1253,7 +805,11 @@ Issues with CRAN packages are summarised below. * tidybayes checking examples ... ERROR - checking tests ... ERROR + +* tidycat + checking examples ... ERROR + checking running R code from vignettes ... ERROR + checking re-building of vignette outputs ... NOTE * tidyCDISC checking tests ... ERROR @@ -1272,14 +828,6 @@ Issues with CRAN packages are summarised below. * tinyarray checking examples ... ERROR -* tmap - checking examples ... ERROR - -* TOmicsVis - checking examples ... ERROR - checking running R code from vignettes ... ERROR - checking re-building of vignette outputs ... NOTE - * tornado checking examples ... ERROR checking tests ... ERROR @@ -1292,29 +840,10 @@ Issues with CRAN packages are summarised below. checking running R code from vignettes ... ERROR checking re-building of vignette outputs ... NOTE -* toxEval - checking examples ... ERROR - * TreatmentPatterns checking tests ... ERROR -* TreatmentSelection - checking examples ... ERROR - -* TreeDep - checking examples ... ERROR - -* TreeDist - checking running R code from vignettes ... ERROR - checking re-building of vignette outputs ... NOTE - -* treeheatr - checking examples ... ERROR - checking running R code from vignettes ... ERROR - checking re-building of vignette outputs ... NOTE - * trelliscopejs - checking examples ... ERROR checking tests ... ERROR * tricolore @@ -1322,270 +851,171 @@ Issues with CRAN packages are summarised below. checking running R code from vignettes ... ERROR checking re-building of vignette outputs ... NOTE +* triptych + checking examples ... ERROR + * tsnet checking tests ... ERROR * umiAnalyzer checking examples ... ERROR -* UnalR - checking examples ... ERROR - -* UpSetR - checking examples ... ERROR - checking running R code from vignettes ... ERROR - -* vDiveR - checking examples ... ERROR - -* VDSM - checking examples ... ERROR +* valr checking tests ... ERROR -* virtualPollen - checking examples ... ERROR - checking running R code from vignettes ... ERROR - checking re-building of vignette outputs ... NOTE - -* viscomp - checking examples ... ERROR - -* visR +* vivaldi checking examples ... ERROR checking tests ... ERROR checking running R code from vignettes ... ERROR checking re-building of vignette outputs ... NOTE -* vivainsights +* vivid checking examples ... ERROR -* vivaldi - checking examples ... ERROR - checking tests ... ERROR - checking running R code from vignettes ... ERROR - checking re-building of vignette outputs ... NOTE - * vvshiny checking tests ... ERROR -* WASP - checking examples ... ERROR - -* Wats - checking running R code from vignettes ... ERROR - checking re-building of vignette outputs ... NOTE - -* whomds - checking examples ... ERROR - * wilson checking tests ... ERROR -* WVPlots - checking examples ... ERROR - checking tests ... ERROR - checking running R code from vignettes ... ERROR - checking re-building of vignette outputs ... NOTE - * xaringanthemer checking tests ... ERROR -* xpose +* yamlet checking examples ... ERROR checking tests ... ERROR - checking running R code from vignettes ... ERROR - checking re-building of vignette outputs ... NOTE ### Failed to check -* abctools (NA) -* adjustedCurves (NA) -* AnanseSeurat (NA) -* animalEKF (NA) -* ANOM (NA) -* aorsf (NA) -* APackOfTheClones (NA) -* autoReg (NA) -* AutoScore (NA) -* bayesdfa (NA) -* bayesDP (NA) -* BayesianFactorZoo (NA) -* BayesSurvive (NA) -* bbmle (NA) -* BCClong (NA) -* bmstdr (NA) -* bspcov (NA) -* BuyseTest (NA) -* calibmsm (NA) -* CalibrationCurves (NA) -* Canek (NA) -* CARBayesST (NA) -* CaseBasedReasoning (NA) -* cellpypes (NA) -* CGPfunctions (NA) -* chem16S (NA) -* CIARA (NA) -* clarify (NA) -* ClustAssess (NA) -* clustree (NA) -* cmprskcoxmsm (NA) -* combiroc (NA) -* conos (NA) -* contrast (NA) -* contsurvplot (NA) -* countland (NA) -* coveffectsplot (NA) -* coxed (NA) -* CRMetrics (NA) -* crosslag (NA) -* csmpv (NA) -* ctsem (NA) -* CytoSimplex (NA) -* depigner (NA) -* DepthProc (NA) -* DIscBIO (NA) -* diversityForest (NA) -* DR.SC (NA) -* DynForest (NA) -* dyngen (NA) -* EcoEnsemble (NA) -* ecolottery (NA) -* EpiEstim (NA) -* evalITR (NA) -* evolqg (NA) -* explainer (NA) -* flexrsurv (NA) -* forestmangr (NA) -* gap (NA) -* GeomComb (NA) -* ggeffects (NA) -* ggquickeda (NA) -* ggrcs (NA) -* ggrisk (NA) -* ggsector (NA) -* grandR (NA) -* Greg (NA) -* greport (NA) -* harmony (NA) -* hIRT (NA) -* Hmisc (NA) -* Hmsc (NA) -* hydroroute (NA) -* inventorize (NA) -* iNZightRegression (NA) -* IRexamples (NA) -* jmBIG (NA) -* joineRML (NA) -* jsmodule (NA) -* JWileymisc (NA) -* kmc (NA) -* KMunicate (NA) -* L2E (NA) -* Landmarking (NA) -* lavaSearch2 (NA) -* llbayesireg (NA) -* LorenzRegression (NA) -* lsirm12pl (NA) -* MachineShop (NA) -* marginaleffects (NA) -* mbsts (NA) -* MetabolicSurv (NA) -* MetaNet (NA) -* miWQS (NA) -* mlmts (NA) -* mlr (NA) -* MOSS (NA) -* mrbayes (NA) -* mstate (NA) -* Multiaovbay (NA) -* multilevelTools (NA) -* multipleOutcomes (NA) -* netcmc (NA) -* NetworkChange (NA) -* neutralitytestr (NA) -* NMADiagT (NA) -* obliqueRSF (NA) -* optweight (NA) -* ormPlot (NA) -* OVtool (NA) -* pagoda2 (NA) -* pammtools (NA) -* pander (NA) -* parameters (NA) -* PAsso (NA) -* paths (NA) -* pctax (NA) -* pcutils (NA) -* PLMIX (NA) -* pmcalibration (NA) -* popstudy (NA) -* pould (NA) -* powerly (NA) -* pre (NA) -* PRECAST (NA) -* ProFAST (NA) -* psbcSpeedUp (NA) -* pscore (NA) -* psfmi (NA) -* pubh (NA) -* qPCRtools (NA) -* qreport (NA) -* quid (NA) -* RcmdrPlugin.RiskDemo (NA) -* rcssci (NA) -* rddtools (NA) -* relsurv (NA) -* riskRegression (NA) -* rliger (NA) -* rms (NA) -* rmsb (NA) -* robber (NA) -* robmedExtra (NA) -* rprev (NA) -* RQdeltaCT (NA) -* rstanarm (NA) -* rTwig (NA) -* scCustomize (NA) -* SCdeconR (NA) -* scDiffCom (NA) -* scGate (NA) -* scMappR (NA) -* SCORPIUS (NA) -* scpi (NA) -* scpoisson (NA) -* SCpubr (NA) -* scRNAstat (NA) -* sectorgap (NA) -* SEERaBomb (NA) -* semicmprskcoxmsm (NA) -* SensMap (NA) -* shinyTempSignal (NA) -* sievePH (NA) -* Signac (NA) -* simET (NA) -* simstudy (NA) -* sMSROC (NA) -* SNPassoc (NA) -* snplinkage (NA) -* SoupX (NA) -* sparsereg (NA) -* SPECK (NA) -* spikeSlabGAM (NA) -* statsr (NA) -* streamDAG (NA) -* sure (NA) -* Surrogate (NA) -* survex (NA) -* survHE (NA) -* survidm (NA) -* SurvMetrics (NA) -* tempted (NA) -* tidydr (NA) -* tidyEdSurvey (NA) -* tidyseurat (NA) -* treefit (NA) -* TriDimRegression (NA) -* twang (NA) -* valse (NA) -* visa (NA) -* WpProj (NA) +* abctools (NA) +* animalEKF (NA) +* ANOM (NA) +* atRisk (NA) +* AutoScore (NA) +* bayesdfa (NA) +* bayesDP (NA) +* BayesianFactorZoo (NA) +* BayesSurvive (NA) +* BCClong (NA) +* BGGM (NA) +* binsreg (NA) +* bmstdr (NA) +* bspcov (NA) +* BuyseTest (NA) +* CalibrationCurves (NA) +* CARBayesST (NA) +* CaseBasedReasoning (NA) +* CGPfunctions (NA) +* cmprskcoxmsm (NA) +* contrast (NA) +* coxed (NA) +* CRMetrics (NA) +* csmpv (NA) +* ctsem (NA) +* DepthProc (NA) +* DR.SC (NA) +* DynNom (NA) +* easybgm (NA) +* ecolottery (NA) +* EpiEstim (NA) +* evolqg (NA) +* ForecastComb (NA) +* gapfill (NA) +* GeomComb (NA) +* ggrcs (NA) +* ggrisk (NA) +* gJLS2 (NA) +* Greg (NA) +* greport (NA) +* hettx (NA) +* hIRT (NA) +* Hmsc (NA) +* inventorize (NA) +* iNZightPlots (NA) +* iNZightRegression (NA) +* IRexamples (NA) +* jmBIG (NA) +* joineRML (NA) +* JWileymisc (NA) +* kmc (NA) +* L2E (NA) +* llbayesireg (NA) +* LorenzRegression (NA) +* lsirm12pl (NA) +* mbsts (NA) +* MendelianRandomization (NA) +* MetabolicSurv (NA) +* miWQS (NA) +* MRZero (NA) +* Multiaovbay (NA) +* multilevelTools (NA) +* multinma (NA) +* NCA (NA) +* netcmc (NA) +* NetworkChange (NA) +* nlmeVPC (NA) +* NMADiagT (NA) +* optweight (NA) +* OVtool (NA) +* paths (NA) +* PLMIX (NA) +* popstudy (NA) +* pould (NA) +* powerly (NA) +* pre (NA) +* ProFAST (NA) +* psbcSpeedUp (NA) +* pscore (NA) +* psfmi (NA) +* qPCRtools (NA) +* qreport (NA) +* qris (NA) +* qte (NA) +* quid (NA) +* RATest (NA) +* RcmdrPlugin.RiskDemo (NA) +* rddtools (NA) +* riskRegression (NA) +* rms (NA) +* rmsb (NA) +* robmed (NA) +* robmedExtra (NA) +* RPPanalyzer (NA) +* RQdeltaCT (NA) +* scCustomize (NA) +* SCdeconR (NA) +* scGate (NA) +* SCIntRuler (NA) +* scMappR (NA) +* scpi (NA) +* scRNAstat (NA) +* sectorgap (NA) +* SEERaBomb (NA) +* semicmprskcoxmsm (NA) +* SensMap (NA) +* Seurat (NA) +* shinyTempSignal (NA) +* sievePH (NA) +* Signac (NA) +* SimplyAgree (NA) +* sMSROC (NA) +* SNPassoc (NA) +* snplinkage (NA) +* SoupX (NA) +* sparsereg (NA) +* spikeSlabGAM (NA) +* statsr (NA) +* streamDAG (NA) +* survHE (NA) +* survidm (NA) +* tempted (NA) +* tidydr (NA) +* tidyEdSurvey (NA) +* tidyseurat (NA) +* tidyvpc (NA) +* TriDimRegression (NA) +* TSrepr (NA) +* twang (NA) +* vdg (NA) +* visa (NA) +* WRTDStidal (NA) diff --git a/revdep/failures.md b/revdep/failures.md index 331d6eb296..84ae909aa5 100644 --- a/revdep/failures.md +++ b/revdep/failures.md @@ -38,7 +38,8 @@ installing to /tmp/workdir/abctools/new/abctools.Rcheck/00LOCK-abctools/00new/ab ** data ** inst ** byte-compile and prepare package for lazy loading -Error: package ‘quantreg’ required by ‘abc’ could not be found +Error: package or namespace load failed for ‘quantreg’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required Execution halted ERROR: lazy loading failed for package ‘abctools’ * removing ‘/tmp/workdir/abctools/new/abctools.Rcheck/abctools’ @@ -61,164 +62,13 @@ installing to /tmp/workdir/abctools/old/abctools.Rcheck/00LOCK-abctools/00new/ab ** data ** inst ** byte-compile and prepare package for lazy loading -Error: package ‘quantreg’ required by ‘abc’ could not be found +Error: package or namespace load failed for ‘quantreg’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required Execution halted ERROR: lazy loading failed for package ‘abctools’ * removing ‘/tmp/workdir/abctools/old/abctools.Rcheck/abctools’ -``` -# adjustedCurves - -
- -* Version: 0.11.1 -* GitHub: https://github.com/RobinDenz1/adjustedCurves -* Source code: https://github.com/cran/adjustedCurves -* Date/Publication: 2024-04-10 18:30:02 UTC -* Number of recursive dependencies: 175 - -Run `revdepcheck::cloud_details(, "adjustedCurves")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/adjustedCurves/new/adjustedCurves.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘adjustedCurves/DESCRIPTION’ ... OK -... ---- finished re-building ‘plot_customization.rmd’ - -SUMMARY: processing the following file failed: - ‘introduction.Rmd’ - -Error: Vignette re-building failed. -Execution halted - -* DONE -Status: 2 ERRORs, 1 WARNING, 3 NOTEs - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/adjustedCurves/old/adjustedCurves.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘adjustedCurves/DESCRIPTION’ ... OK -... ---- finished re-building ‘plot_customization.rmd’ - -SUMMARY: processing the following file failed: - ‘introduction.Rmd’ - -Error: Vignette re-building failed. -Execution halted - -* DONE -Status: 2 ERRORs, 1 WARNING, 3 NOTEs - - - - - -``` -# AnanseSeurat - -
- -* Version: 1.2.0 -* GitHub: https://github.com/JGASmits/AnanseSeurat -* Source code: https://github.com/cran/AnanseSeurat -* Date/Publication: 2023-11-11 21:43:17 UTC -* Number of recursive dependencies: 200 - -Run `revdepcheck::cloud_details(, "AnanseSeurat")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/AnanseSeurat/new/AnanseSeurat.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘AnanseSeurat/DESCRIPTION’ ... OK -... -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘Seurat’ - -Package suggested but not available for checking: ‘Signac’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/AnanseSeurat/old/AnanseSeurat.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘AnanseSeurat/DESCRIPTION’ ... OK -... -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘Seurat’ - -Package suggested but not available for checking: ‘Signac’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - ``` # animalEKF @@ -254,9 +104,9 @@ Run `revdepcheck::cloud_details(, "animalEKF")` for more info ** 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 ‘quantreg’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace Execution halted ERROR: lazy loading failed for package ‘animalEKF’ * removing ‘/tmp/workdir/animalEKF/new/animalEKF.Rcheck/animalEKF’ @@ -273,9 +123,9 @@ ERROR: lazy loading failed for package ‘animalEKF’ ** 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 ‘quantreg’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace Execution halted ERROR: lazy loading failed for package ‘animalEKF’ * removing ‘/tmp/workdir/animalEKF/old/animalEKF.Rcheck/animalEKF’ @@ -290,7 +140,7 @@ ERROR: lazy loading failed for package ‘animalEKF’ * GitHub: https://github.com/PhilipPallmann/ANOM * Source code: https://github.com/cran/ANOM * Date/Publication: 2017-04-12 13:32:33 UTC -* Number of recursive dependencies: 77 +* Number of recursive dependencies: 60 Run `revdepcheck::cloud_details(, "ANOM")` for more info @@ -317,9 +167,9 @@ Run `revdepcheck::cloud_details(, "ANOM")` for more info *** moving datasets to lazyload DB ** 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 ‘quantreg’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace Execution halted ERROR: lazy loading failed for package ‘ANOM’ * removing ‘/tmp/workdir/ANOM/new/ANOM.Rcheck/ANOM’ @@ -337,316 +187,138 @@ ERROR: lazy loading failed for package ‘ANOM’ *** moving datasets to lazyload DB ** 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 ‘quantreg’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace Execution halted ERROR: lazy loading failed for package ‘ANOM’ * removing ‘/tmp/workdir/ANOM/old/ANOM.Rcheck/ANOM’ ``` -# aorsf +# atRisk
-* Version: 0.1.5 -* GitHub: https://github.com/ropensci/aorsf -* Source code: https://github.com/cran/aorsf -* Date/Publication: 2024-05-30 03:40:02 UTC -* Number of recursive dependencies: 181 +* Version: 0.1.0 +* GitHub: NA +* Source code: https://github.com/cran/atRisk +* Date/Publication: 2023-08-08 14:50:05 UTC +* Number of recursive dependencies: 37 -Run `revdepcheck::cloud_details(, "aorsf")` for more info +Run `revdepcheck::cloud_details(, "atRisk")` for more info
-## Error before installation - -### Devel +## In both -``` -* using log directory ‘/tmp/workdir/aorsf/new/aorsf.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘aorsf/DESCRIPTION’ ... OK -... -* checking for unstated dependencies in vignettes ... OK -* checking package vignettes in ‘inst/doc’ ... OK -* checking running R code from vignettes ... OK - ‘aorsf.Rmd’ using ‘UTF-8’... OK - ‘fast.Rmd’ using ‘UTF-8’... OK - ‘oobag.Rmd’ using ‘UTF-8’... OK - ‘pd.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: 1 NOTE +* checking whether package ‘atRisk’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/atRisk/new/atRisk.Rcheck/00install.out’ for details. + ``` +## Installation +### Devel +``` +* installing *source* package ‘atRisk’ ... +** package ‘atRisk’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** data +*** moving datasets to lazyload DB +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘atRisk’ +* removing ‘/tmp/workdir/atRisk/new/atRisk.Rcheck/atRisk’ ``` ### CRAN ``` -* using log directory ‘/tmp/workdir/aorsf/old/aorsf.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘aorsf/DESCRIPTION’ ... OK -... -* checking for unstated dependencies in vignettes ... OK -* checking package vignettes in ‘inst/doc’ ... OK -* checking running R code from vignettes ... OK - ‘aorsf.Rmd’ using ‘UTF-8’... OK - ‘fast.Rmd’ using ‘UTF-8’... OK - ‘oobag.Rmd’ using ‘UTF-8’... OK - ‘pd.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: 1 NOTE - - - +* installing *source* package ‘atRisk’ ... +** package ‘atRisk’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** data +*** moving datasets to lazyload DB +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘atRisk’ +* removing ‘/tmp/workdir/atRisk/old/atRisk.Rcheck/atRisk’ ``` -# APackOfTheClones +# AutoScore
-* Version: 1.2.0 -* GitHub: https://github.com/Qile0317/APackOfTheClones -* Source code: https://github.com/cran/APackOfTheClones -* Date/Publication: 2024-04-16 09:50:02 UTC -* Number of recursive dependencies: 176 +* Version: 1.0.0 +* GitHub: https://github.com/nliulab/AutoScore +* Source code: https://github.com/cran/AutoScore +* Date/Publication: 2022-10-15 22:15:26 UTC +* Number of recursive dependencies: 170 -Run `revdepcheck::cloud_details(, "APackOfTheClones")` for more info +Run `revdepcheck::cloud_details(, "AutoScore")` for more info
-## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/APackOfTheClones/new/APackOfTheClones.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘APackOfTheClones/DESCRIPTION’ ... OK -... -* this is package ‘APackOfTheClones’ version ‘1.2.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Packages required but not available: 'Seurat', 'SeuratObject' +## In both -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR +* checking whether package ‘AutoScore’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/AutoScore/new/AutoScore.Rcheck/00install.out’ for details. + ``` +## Installation +### Devel +``` +* installing *source* package ‘AutoScore’ ... +** package ‘AutoScore’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘AutoScore’ +* removing ‘/tmp/workdir/AutoScore/new/AutoScore.Rcheck/AutoScore’ ``` ### CRAN ``` -* using log directory ‘/tmp/workdir/APackOfTheClones/old/APackOfTheClones.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘APackOfTheClones/DESCRIPTION’ ... OK -... -* this is package ‘APackOfTheClones’ version ‘1.2.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Packages required but not available: 'Seurat', 'SeuratObject' - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# autoReg - -
- -* Version: 0.3.3 -* GitHub: https://github.com/cardiomoon/autoReg -* Source code: https://github.com/cran/autoReg -* Date/Publication: 2023-11-14 05:53:27 UTC -* Number of recursive dependencies: 232 - -Run `revdepcheck::cloud_details(, "autoReg")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/autoReg/new/autoReg.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘autoReg/DESCRIPTION’ ... OK -... - -SUMMARY: processing the following files failed: - ‘Automatic_Regression_Modeling.Rmd’ ‘Getting_started.Rmd’ - ‘Survival.Rmd’ - -Error: Vignette re-building failed. -Execution halted - -* DONE -Status: 2 ERRORs, 1 NOTE - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/autoReg/old/autoReg.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘autoReg/DESCRIPTION’ ... OK -... -* checking package vignettes in ‘inst/doc’ ... OK -* checking running R code from vignettes ... OK - ‘Automatic_Regression_Modeling.Rmd’ using ‘UTF-8’... OK - ‘Bootstrap_Prediction.Rmd’ using ‘UTF-8’... OK - ‘Getting_started.Rmd’ using ‘UTF-8’... OK - ‘Statiastical_test_in_gaze.Rmd’ using ‘UTF-8’... OK - ‘Survival.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: OK - - - - - -``` -# AutoScore - -
- -* Version: 1.0.0 -* GitHub: https://github.com/nliulab/AutoScore -* Source code: https://github.com/cran/AutoScore -* Date/Publication: 2022-10-15 22:15:26 UTC -* Number of recursive dependencies: 179 - -Run `revdepcheck::cloud_details(, "AutoScore")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/AutoScore/new/AutoScore.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘AutoScore/DESCRIPTION’ ... OK -... -* checking if there is a namespace ... OK -* checking for executable files ... OK -* checking for hidden files and directories ... OK -* checking for portable file names ... OK -* checking for sufficient/correct file permissions ... OK -* checking whether package ‘AutoScore’ can be installed ... ERROR -Installation failed. -See ‘/tmp/workdir/AutoScore/new/AutoScore.Rcheck/00install.out’ for details. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/AutoScore/old/AutoScore.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘AutoScore/DESCRIPTION’ ... OK -... -* checking if there is a namespace ... OK -* checking for executable files ... OK -* checking for hidden files and directories ... OK -* checking for portable file names ... OK -* checking for sufficient/correct file permissions ... OK -* checking whether package ‘AutoScore’ can be installed ... ERROR -Installation failed. -See ‘/tmp/workdir/AutoScore/old/AutoScore.Rcheck/00install.out’ for details. -* DONE -Status: 1 ERROR - - - +* installing *source* package ‘AutoScore’ ... +** package ‘AutoScore’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘AutoScore’ +* removing ‘/tmp/workdir/AutoScore/old/AutoScore.Rcheck/AutoScore’ ``` @@ -768,9 +440,9 @@ installing to /tmp/workdir/bayesDP/new/bayesDP.Rcheck/00LOCK-bayesDP/00new/bayes ** R ** 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 ‘quantreg’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace Execution halted ERROR: lazy loading failed for package ‘bayesDP’ * removing ‘/tmp/workdir/bayesDP/new/bayesDP.Rcheck/bayesDP’ @@ -793,9 +465,9 @@ installing to /tmp/workdir/bayesDP/old/bayesDP.Rcheck/00LOCK-bayesDP/00new/bayes ** R ** 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 ‘quantreg’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace Execution halted ERROR: lazy loading failed for package ‘bayesDP’ * removing ‘/tmp/workdir/bayesDP/old/bayesDP.Rcheck/bayesDP’ @@ -838,8 +510,8 @@ Run `revdepcheck::cloud_details(, "BayesianFactorZoo")` for more info ** 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 ‘quantreg’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace Execution halted ERROR: lazy loading failed for package ‘BayesianFactorZoo’ * removing ‘/tmp/workdir/BayesianFactorZoo/new/BayesianFactorZoo.Rcheck/BayesianFactorZoo’ @@ -858,8 +530,8 @@ ERROR: lazy loading failed for package ‘BayesianFactorZoo’ ** 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 ‘quantreg’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace Execution halted ERROR: lazy loading failed for package ‘BayesianFactorZoo’ * removing ‘/tmp/workdir/BayesianFactorZoo/old/BayesianFactorZoo.Rcheck/BayesianFactorZoo’ @@ -870,151 +542,77 @@ ERROR: lazy loading failed for package ‘BayesianFactorZoo’
-* Version: 0.0.1 +* Version: 0.0.2 * GitHub: https://github.com/ocbe-uio/BayesSurvive * Source code: https://github.com/cran/BayesSurvive -* Date/Publication: 2024-04-23 11:20:06 UTC +* Date/Publication: 2024-06-04 13:20:12 UTC * Number of recursive dependencies: 128 Run `revdepcheck::cloud_details(, "BayesSurvive")` for more info
-## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/BayesSurvive/new/BayesSurvive.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘BayesSurvive/DESCRIPTION’ ... OK -... -* this is package ‘BayesSurvive’ version ‘0.0.1’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘riskRegression’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/BayesSurvive/old/BayesSurvive.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘BayesSurvive/DESCRIPTION’ ... OK -... -* this is package ‘BayesSurvive’ version ‘0.0.1’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘riskRegression’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# bbmle - -
- -* Version: 1.0.25.1 -* GitHub: https://github.com/bbolker/bbmle -* Source code: https://github.com/cran/bbmle -* Date/Publication: 2023-12-09 01:00:02 UTC -* Number of recursive dependencies: 113 - -Run `revdepcheck::cloud_details(, "bbmle")` for more info +## In both -
+* checking whether package ‘BayesSurvive’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/BayesSurvive/new/BayesSurvive.Rcheck/00install.out’ for details. + ``` -## Error before installation +## Installation ### Devel ``` -* using log directory ‘/tmp/workdir/bbmle/new/bbmle.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘bbmle/DESCRIPTION’ ... OK +* installing *source* package ‘BayesSurvive’ ... +** package ‘BayesSurvive’ successfully unpacked and MD5 sums checked +** using staged installation +checking whether the C++ compiler works... yes +checking for C++ compiler default output file name... a.out +checking for suffix of executables... +checking whether we are cross compiling... no +checking for suffix of object files... o +checking whether the compiler supports GNU C++... yes +checking whether g++ -std=gnu++17 accepts -g... yes ... ---- failed re-building ‘quasi.Rnw’ - -SUMMARY: processing the following files failed: - ‘mle2.Rnw’ ‘quasi.Rnw’ - -Error: Vignette re-building failed. +** 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace Execution halted - -* DONE -Status: 2 NOTEs - - - +ERROR: lazy loading failed for package ‘BayesSurvive’ +* removing ‘/tmp/workdir/BayesSurvive/new/BayesSurvive.Rcheck/BayesSurvive’ ``` ### CRAN ``` -* using log directory ‘/tmp/workdir/bbmle/old/bbmle.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘bbmle/DESCRIPTION’ ... OK +* installing *source* package ‘BayesSurvive’ ... +** package ‘BayesSurvive’ successfully unpacked and MD5 sums checked +** using staged installation +checking whether the C++ compiler works... yes +checking for C++ compiler default output file name... a.out +checking for suffix of executables... +checking whether we are cross compiling... no +checking for suffix of object files... o +checking whether the compiler supports GNU C++... yes +checking whether g++ -std=gnu++17 accepts -g... yes ... ---- failed re-building ‘quasi.Rnw’ - -SUMMARY: processing the following files failed: - ‘mle2.Rnw’ ‘quasi.Rnw’ - -Error: Vignette re-building failed. +** 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace Execution halted - -* DONE -Status: 2 NOTEs - - - +ERROR: lazy loading failed for package ‘BayesSurvive’ +* removing ‘/tmp/workdir/BayesSurvive/old/BayesSurvive.Rcheck/BayesSurvive’ ``` @@ -1022,11 +620,11 @@ Status: 2 NOTEs
-* Version: 1.0.2 +* Version: 1.0.3 * GitHub: NA * Source code: https://github.com/cran/BCClong -* Date/Publication: 2024-02-05 11:50:06 UTC -* Number of recursive dependencies: 141 +* Date/Publication: 2024-06-24 00:00:02 UTC +* Number of recursive dependencies: 145 Run `revdepcheck::cloud_details(, "BCClong")` for more info @@ -1040,11 +638,6 @@ Run `revdepcheck::cloud_details(, "BCClong")` for more info See ‘/tmp/workdir/BCClong/new/BCClong.Rcheck/00install.out’ for details. ``` -* checking package dependencies ... NOTE - ``` - Package suggested but not available for checking: ‘joineRML’ - ``` - ## Installation ### Devel @@ -1061,13 +654,13 @@ g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/ g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c c_which.cpp -o c_which.o g++ -std=gnu++17 -shared -L/opt/R/4.3.1/lib/R/lib -L/usr/local/lib -o BCClong.so BCC.o Likelihood.o RcppExports.o c_which.o -fopenmp -llapack -lblas -lgfortran -lm -lquadmath -L/opt/R/4.3.1/lib/R/lib -lR ... -installing to /tmp/workdir/BCClong/new/BCClong.Rcheck/00LOCK-BCClong/00new/BCClong/libs ** 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 ‘quantreg’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace Execution halted ERROR: lazy loading failed for package ‘BCClong’ * removing ‘/tmp/workdir/BCClong/new/BCClong.Rcheck/BCClong’ @@ -1088,28 +681,164 @@ g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/ g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c c_which.cpp -o c_which.o g++ -std=gnu++17 -shared -L/opt/R/4.3.1/lib/R/lib -L/usr/local/lib -o BCClong.so BCC.o Likelihood.o RcppExports.o c_which.o -fopenmp -llapack -lblas -lgfortran -lm -lquadmath -L/opt/R/4.3.1/lib/R/lib -lR ... -installing to /tmp/workdir/BCClong/old/BCClong.Rcheck/00LOCK-BCClong/00new/BCClong/libs ** 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 ‘quantreg’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace Execution halted ERROR: lazy loading failed for package ‘BCClong’ * removing ‘/tmp/workdir/BCClong/old/BCClong.Rcheck/BCClong’ ``` -# bmstdr +# BGGM
-* Version: 0.7.9 -* GitHub: https://github.com/sujit-sahu/bmstdr +* Version: 2.1.3 +* GitHub: https://github.com/donaldRwilliams/BGGM +* Source code: https://github.com/cran/BGGM +* Date/Publication: 2024-07-05 20:30:02 UTC +* Number of recursive dependencies: 208 + +Run `revdepcheck::cloud_details(, "BGGM")` for more info + +
+ +## In both + +* checking whether package ‘BGGM’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/BGGM/new/BGGM.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘BGGM’ ... +** package ‘BGGM’ successfully unpacked and MD5 sums checked +** using staged installation +checking whether the C++ compiler works... yes +checking for C++ compiler default output file name... a.out +checking for suffix of executables... +checking whether we are cross compiling... no +checking for suffix of object files... o +checking whether we are using the GNU C++ compiler... yes +checking whether g++ -std=gnu++17 accepts -g... yes +... +** 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘BGGM’ +* removing ‘/tmp/workdir/BGGM/new/BGGM.Rcheck/BGGM’ + + +``` +### CRAN + +``` +* installing *source* package ‘BGGM’ ... +** package ‘BGGM’ successfully unpacked and MD5 sums checked +** using staged installation +checking whether the C++ compiler works... yes +checking for C++ compiler default output file name... a.out +checking for suffix of executables... +checking whether we are cross compiling... no +checking for suffix of object files... o +checking whether we are using the GNU C++ compiler... yes +checking whether g++ -std=gnu++17 accepts -g... yes +... +** 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘BGGM’ +* removing ‘/tmp/workdir/BGGM/old/BGGM.Rcheck/BGGM’ + + +``` +# binsreg + +
+ +* Version: 1.0 +* GitHub: NA +* Source code: https://github.com/cran/binsreg +* Date/Publication: 2023-07-11 12:00:24 UTC +* Number of recursive dependencies: 35 + +Run `revdepcheck::cloud_details(, "binsreg")` for more info + +
+ +## In both + +* checking whether package ‘binsreg’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/binsreg/new/binsreg.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘binsreg’ ... +** package ‘binsreg’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘binsreg’ +* removing ‘/tmp/workdir/binsreg/new/binsreg.Rcheck/binsreg’ + + +``` +### CRAN + +``` +* installing *source* package ‘binsreg’ ... +** package ‘binsreg’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘binsreg’ +* removing ‘/tmp/workdir/binsreg/old/binsreg.Rcheck/binsreg’ + + +``` +# bmstdr + +
+ +* Version: 0.7.9 +* GitHub: https://github.com/sujit-sahu/bmstdr * Source code: https://github.com/cran/bmstdr * Date/Publication: 2023-12-18 15:00:02 UTC -* Number of recursive dependencies: 211 +* Number of recursive dependencies: 215 Run `revdepcheck::cloud_details(, "bmstdr")` for more info @@ -1143,9 +872,9 @@ In file included from /opt/R/4.3.1/lib/R/site-library/RcppEigen/include/Eigen/Co *** moving datasets to lazyload DB ** 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 ‘quantreg’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace Execution halted ERROR: lazy loading failed for package ‘bmstdr’ * removing ‘/tmp/workdir/bmstdr/new/bmstdr.Rcheck/bmstdr’ @@ -1170,9 +899,9 @@ In file included from /opt/R/4.3.1/lib/R/site-library/RcppEigen/include/Eigen/Co *** moving datasets to lazyload DB ** 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 ‘quantreg’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace Execution halted ERROR: lazy loading failed for package ‘bmstdr’ * removing ‘/tmp/workdir/bmstdr/old/bmstdr.Rcheck/bmstdr’ @@ -1187,7 +916,7 @@ ERROR: lazy loading failed for package ‘bmstdr’ * GitHub: https://github.com/statjs/bspcov * Source code: https://github.com/cran/bspcov * Date/Publication: 2024-02-06 16:50:08 UTC -* Number of recursive dependencies: 122 +* Number of recursive dependencies: 121 Run `revdepcheck::cloud_details(, "bspcov")` for more info @@ -1245,327 +974,163 @@ ERROR: lazy loading failed for package ‘bspcov’
-* Version: 3.0.2 +* Version: 3.0.4 * GitHub: https://github.com/bozenne/BuyseTest * Source code: https://github.com/cran/BuyseTest -* Date/Publication: 2024-01-23 15:12:56 UTC +* Date/Publication: 2024-07-01 09:20:02 UTC * Number of recursive dependencies: 133 Run `revdepcheck::cloud_details(, "BuyseTest")` for more info
-## Error before installation +## In both + +* checking whether package ‘BuyseTest’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/BuyseTest/new/BuyseTest.Rcheck/00install.out’ for details. + ``` + +## Installation ### Devel ``` -* using log directory ‘/tmp/workdir/BuyseTest/new/BuyseTest.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘BuyseTest/DESCRIPTION’ ... OK +* installing *source* package ‘BuyseTest’ ... +** package ‘BuyseTest’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C++ compiler: ‘g++ (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c FCT_buyseTest.cpp -o FCT_buyseTest.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c FCT_precompute.cpp -o FCT_precompute.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c utils-from-riskRegression.cpp -o utils-from-riskRegression.o +g++ -std=gnu++17 -shared -L/opt/R/4.3.1/lib/R/lib -L/usr/local/lib -o BuyseTest.so FCT_buyseTest.o FCT_precompute.o RcppExports.o utils-from-riskRegression.o -L/opt/R/4.3.1/lib/R/lib -lR ... -* this is package ‘BuyseTest’ version ‘3.0.2’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘riskRegression’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - +installing to /tmp/workdir/BuyseTest/new/BuyseTest.Rcheck/00LOCK-BuyseTest/00new/BuyseTest/libs +** R +** inst +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Error: unable to load R code in package ‘BuyseTest’ +Execution halted +ERROR: lazy loading failed for package ‘BuyseTest’ +* removing ‘/tmp/workdir/BuyseTest/new/BuyseTest.Rcheck/BuyseTest’ ``` ### CRAN ``` -* using log directory ‘/tmp/workdir/BuyseTest/old/BuyseTest.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘BuyseTest/DESCRIPTION’ ... OK +* installing *source* package ‘BuyseTest’ ... +** package ‘BuyseTest’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C++ compiler: ‘g++ (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c FCT_buyseTest.cpp -o FCT_buyseTest.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c FCT_precompute.cpp -o FCT_precompute.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c utils-from-riskRegression.cpp -o utils-from-riskRegression.o +g++ -std=gnu++17 -shared -L/opt/R/4.3.1/lib/R/lib -L/usr/local/lib -o BuyseTest.so FCT_buyseTest.o FCT_precompute.o RcppExports.o utils-from-riskRegression.o -L/opt/R/4.3.1/lib/R/lib -lR ... -* this is package ‘BuyseTest’ version ‘3.0.2’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘riskRegression’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - +installing to /tmp/workdir/BuyseTest/old/BuyseTest.Rcheck/00LOCK-BuyseTest/00new/BuyseTest/libs +** R +** inst +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Error: unable to load R code in package ‘BuyseTest’ +Execution halted +ERROR: lazy loading failed for package ‘BuyseTest’ +* removing ‘/tmp/workdir/BuyseTest/old/BuyseTest.Rcheck/BuyseTest’ ``` -# calibmsm +# CalibrationCurves
-* Version: 1.1.0 +* Version: 2.0.3 * GitHub: NA -* Source code: https://github.com/cran/calibmsm -* Date/Publication: 2024-05-13 11:33:07 UTC -* Number of recursive dependencies: 143 +* Source code: https://github.com/cran/CalibrationCurves +* Date/Publication: 2024-07-02 08:50:02 UTC +* Number of recursive dependencies: 78 -Run `revdepcheck::cloud_details(, "calibmsm")` for more info +Run `revdepcheck::cloud_details(, "CalibrationCurves")` for more info
-## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/calibmsm/new/calibmsm.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘calibmsm/DESCRIPTION’ ... OK -... -* this is package ‘calibmsm’ version ‘1.1.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘rms’ +## In both -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR +* checking whether package ‘CalibrationCurves’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/CalibrationCurves/new/CalibrationCurves.Rcheck/00install.out’ for details. + ``` +## Installation +### Devel +``` +* installing *source* package ‘CalibrationCurves’ ... +** package ‘CalibrationCurves’ 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: package or namespace load failed for ‘rms’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Execution halted +ERROR: lazy loading failed for package ‘CalibrationCurves’ +* removing ‘/tmp/workdir/CalibrationCurves/new/CalibrationCurves.Rcheck/CalibrationCurves’ ``` ### CRAN ``` -* using log directory ‘/tmp/workdir/calibmsm/old/calibmsm.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘calibmsm/DESCRIPTION’ ... OK -... -* this is package ‘calibmsm’ version ‘1.1.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘rms’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - +* installing *source* package ‘CalibrationCurves’ ... +** package ‘CalibrationCurves’ 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: package or namespace load failed for ‘rms’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Execution halted +ERROR: lazy loading failed for package ‘CalibrationCurves’ +* removing ‘/tmp/workdir/CalibrationCurves/old/CalibrationCurves.Rcheck/CalibrationCurves’ ``` -# CalibrationCurves +# CARBayesST
-* Version: 2.0.1 -* GitHub: NA -* Source code: https://github.com/cran/CalibrationCurves -* Date/Publication: 2024-03-01 10:12:35 UTC -* Number of recursive dependencies: 78 +* Version: 4.0 +* GitHub: https://github.com/duncanplee/CARBayesST +* Source code: https://github.com/cran/CARBayesST +* Date/Publication: 2023-10-30 16:40:02 UTC +* Number of recursive dependencies: 117 -Run `revdepcheck::cloud_details(, "CalibrationCurves")` for more info +Run `revdepcheck::cloud_details(, "CARBayesST")` for more info
-## Error before installation +## In both -### Devel - -``` -* using log directory ‘/tmp/workdir/CalibrationCurves/new/CalibrationCurves.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘CalibrationCurves/DESCRIPTION’ ... OK -... -* this is package ‘CalibrationCurves’ version ‘2.0.1’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘rms’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/CalibrationCurves/old/CalibrationCurves.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘CalibrationCurves/DESCRIPTION’ ... OK -... -* this is package ‘CalibrationCurves’ version ‘2.0.1’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘rms’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# Canek - -
- -* Version: 0.2.5 -* GitHub: https://github.com/MartinLoza/Canek -* Source code: https://github.com/cran/Canek -* Date/Publication: 2023-12-08 05:30:02 UTC -* Number of recursive dependencies: 220 - -Run `revdepcheck::cloud_details(, "Canek")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/Canek/new/Canek.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘Canek/DESCRIPTION’ ... OK -... - [ FAIL 1 | WARN 0 | SKIP 0 | PASS 74 ] - Error: Test failures - Execution halted -* checking for unstated dependencies in vignettes ... OK -* checking package vignettes in ‘inst/doc’ ... OK -* checking running R code from vignettes ... OK - ‘toy_example.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: 1 ERROR, 1 NOTE - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/Canek/old/Canek.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘Canek/DESCRIPTION’ ... OK -... - [ FAIL 1 | WARN 0 | SKIP 0 | PASS 74 ] - Error: Test failures - Execution halted -* checking for unstated dependencies in vignettes ... OK -* checking package vignettes in ‘inst/doc’ ... OK -* checking running R code from vignettes ... OK - ‘toy_example.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: 1 ERROR, 1 NOTE - - - - - -``` -# CARBayesST - -
- -* Version: 4.0 -* GitHub: https://github.com/duncanplee/CARBayesST -* Source code: https://github.com/cran/CARBayesST -* Date/Publication: 2023-10-30 16:40:02 UTC -* Number of recursive dependencies: 117 - -Run `revdepcheck::cloud_details(, "CARBayesST")` for more info - -
- -## In both - -* checking whether package ‘CARBayesST’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/CARBayesST/new/CARBayesST.Rcheck/00install.out’ for details. - ``` +* checking whether package ‘CARBayesST’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/CARBayesST/new/CARBayesST.Rcheck/00install.out’ for details. + ``` ## Installation @@ -1584,9 +1149,9 @@ installing to /tmp/workdir/CARBayesST/new/CARBayesST.Rcheck/00LOCK-CARBayesST/00 ** R ** 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 ‘quantreg’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace Execution halted ERROR: lazy loading failed for package ‘CARBayesST’ * removing ‘/tmp/workdir/CARBayesST/new/CARBayesST.Rcheck/CARBayesST’ @@ -1608,9 +1173,9 @@ installing to /tmp/workdir/CARBayesST/old/CARBayesST.Rcheck/00LOCK-CARBayesST/00 ** R ** 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 ‘quantreg’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace Execution halted ERROR: lazy loading failed for package ‘CARBayesST’ * removing ‘/tmp/workdir/CARBayesST/old/CARBayesST.Rcheck/CARBayesST’ @@ -1631,141 +1196,67 @@ Run `revdepcheck::cloud_details(, "CaseBasedReasoning")` for more info
-## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/CaseBasedReasoning/new/CaseBasedReasoning.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘CaseBasedReasoning/DESCRIPTION’ ... OK -... -* this is package ‘CaseBasedReasoning’ version ‘0.3’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘rms’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/CaseBasedReasoning/old/CaseBasedReasoning.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘CaseBasedReasoning/DESCRIPTION’ ... OK -... -* this is package ‘CaseBasedReasoning’ version ‘0.3’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘rms’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# cellpypes - -
- -* Version: 0.3.0 -* GitHub: https://github.com/FelixTheStudent/cellpypes -* Source code: https://github.com/cran/cellpypes -* Date/Publication: 2024-01-27 07:30:07 UTC -* Number of recursive dependencies: 183 - -Run `revdepcheck::cloud_details(, "cellpypes")` for more info +## In both -
+* checking whether package ‘CaseBasedReasoning’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/CaseBasedReasoning/new/CaseBasedReasoning.Rcheck/00install.out’ for details. + ``` -## Error before installation +## Installation ### Devel ``` -* using log directory ‘/tmp/workdir/cellpypes/new/cellpypes.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘cellpypes/DESCRIPTION’ ... OK -... -* checking contents of ‘data’ directory ... OK -* checking data for non-ASCII characters ... OK -* checking LazyData ... OK -* checking data for ASCII and uncompressed saves ... OK -* checking examples ... OK -* checking for unstated dependencies in ‘tests’ ... OK -* checking tests ... OK - Running ‘testthat.R’ -* DONE -Status: 1 NOTE - - - +* installing *source* package ‘CaseBasedReasoning’ ... +** package ‘CaseBasedReasoning’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C++ compiler: ‘g++ (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -I/usr/local/include -fpic -g -O2 -c distanceAPI.cpp -o distanceAPI.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -I/usr/local/include -fpic -g -O2 -c distances.cpp -o distances.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -I/usr/local/include -fpic -g -O2 -c order.cpp -o order.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -I/usr/local/include -fpic -g -O2 -c weightedKNN.cpp -o weightedKNN.o +... +g++ -std=gnu++17 -shared -L/opt/R/4.3.1/lib/R/lib -L/usr/local/lib -o CaseBasedReasoning.so RcppExports.o distanceAPI.o distances.o order.o weightedKNN.o -L/opt/R/4.3.1/lib/R/lib -lR +installing to /tmp/workdir/CaseBasedReasoning/new/CaseBasedReasoning.Rcheck/00LOCK-CaseBasedReasoning/00new/CaseBasedReasoning/libs +** R +** inst +** byte-compile and prepare package for lazy loading +Error: package or namespace load failed for ‘rms’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Execution halted +ERROR: lazy loading failed for package ‘CaseBasedReasoning’ +* removing ‘/tmp/workdir/CaseBasedReasoning/new/CaseBasedReasoning.Rcheck/CaseBasedReasoning’ ``` ### CRAN ``` -* using log directory ‘/tmp/workdir/cellpypes/old/cellpypes.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘cellpypes/DESCRIPTION’ ... OK -... -* checking contents of ‘data’ directory ... OK -* checking data for non-ASCII characters ... OK -* checking LazyData ... OK -* checking data for ASCII and uncompressed saves ... OK -* checking examples ... OK -* checking for unstated dependencies in ‘tests’ ... OK -* checking tests ... OK - Running ‘testthat.R’ -* DONE -Status: 1 NOTE - - - +* installing *source* package ‘CaseBasedReasoning’ ... +** package ‘CaseBasedReasoning’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C++ compiler: ‘g++ (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -I/usr/local/include -fpic -g -O2 -c distanceAPI.cpp -o distanceAPI.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -I/usr/local/include -fpic -g -O2 -c distances.cpp -o distances.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -I/usr/local/include -fpic -g -O2 -c order.cpp -o order.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -I/usr/local/include -fpic -g -O2 -c weightedKNN.cpp -o weightedKNN.o +... +g++ -std=gnu++17 -shared -L/opt/R/4.3.1/lib/R/lib -L/usr/local/lib -o CaseBasedReasoning.so RcppExports.o distanceAPI.o distances.o order.o weightedKNN.o -L/opt/R/4.3.1/lib/R/lib -lR +installing to /tmp/workdir/CaseBasedReasoning/old/CaseBasedReasoning.Rcheck/00LOCK-CaseBasedReasoning/00new/CaseBasedReasoning/libs +** R +** inst +** byte-compile and prepare package for lazy loading +Error: package or namespace load failed for ‘rms’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Execution halted +ERROR: lazy loading failed for package ‘CaseBasedReasoning’ +* removing ‘/tmp/workdir/CaseBasedReasoning/old/CaseBasedReasoning.Rcheck/CaseBasedReasoning’ ``` @@ -1833,406 +1324,416 @@ ERROR: lazy loading failed for package ‘CGPfunctions’ ``` -# chem16S +# cmprskcoxmsm
-* Version: 1.0.0 -* GitHub: https://github.com/jedick/chem16S -* Source code: https://github.com/cran/chem16S -* Date/Publication: 2023-07-17 17:10:02 UTC -* Number of recursive dependencies: 112 +* Version: 0.2.1 +* GitHub: NA +* Source code: https://github.com/cran/cmprskcoxmsm +* Date/Publication: 2021-09-04 05:50:02 UTC +* Number of recursive dependencies: 71 -Run `revdepcheck::cloud_details(, "chem16S")` for more info +Run `revdepcheck::cloud_details(, "cmprskcoxmsm")` for more info
-## Error before installation +## In both + +* checking whether package ‘cmprskcoxmsm’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/cmprskcoxmsm/new/cmprskcoxmsm.Rcheck/00install.out’ for details. + ``` + +## Installation ### Devel ``` -* using log directory ‘/tmp/workdir/chem16S/new/chem16S.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘chem16S/DESCRIPTION’ ... OK -... - When sourcing ‘plotting.R’: -Error: could not find function "stat_poly_line" +* installing *source* package ‘cmprskcoxmsm’ ... +** package ‘cmprskcoxmsm’ successfully unpacked and MD5 sums checked +** 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace Execution halted - - ‘metrics.Rmd’ using ‘UTF-8’... OK - ‘phyloseq.Rmd’ using ‘UTF-8’... OK - ‘plotting.Rmd’ using ‘UTF-8’... failed -* checking re-building of vignette outputs ... OK -* DONE -Status: 1 ERROR, 1 NOTE - - - +ERROR: lazy loading failed for package ‘cmprskcoxmsm’ +* removing ‘/tmp/workdir/cmprskcoxmsm/new/cmprskcoxmsm.Rcheck/cmprskcoxmsm’ ``` ### CRAN ``` -* using log directory ‘/tmp/workdir/chem16S/old/chem16S.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘chem16S/DESCRIPTION’ ... OK -... - When sourcing ‘plotting.R’: -Error: could not find function "stat_poly_line" +* installing *source* package ‘cmprskcoxmsm’ ... +** package ‘cmprskcoxmsm’ successfully unpacked and MD5 sums checked +** 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace Execution halted - - ‘metrics.Rmd’ using ‘UTF-8’... OK - ‘phyloseq.Rmd’ using ‘UTF-8’... OK - ‘plotting.Rmd’ using ‘UTF-8’... failed -* checking re-building of vignette outputs ... OK -* DONE -Status: 1 ERROR, 1 NOTE - - - +ERROR: lazy loading failed for package ‘cmprskcoxmsm’ +* removing ‘/tmp/workdir/cmprskcoxmsm/old/cmprskcoxmsm.Rcheck/cmprskcoxmsm’ ``` -# CIARA +# contrast
-* Version: 0.1.0 -* GitHub: NA -* Source code: https://github.com/cran/CIARA -* Date/Publication: 2022-02-22 20:00:02 UTC -* Number of recursive dependencies: 181 +* Version: 0.24.2 +* GitHub: https://github.com/Alanocallaghan/contrast +* Source code: https://github.com/cran/contrast +* Date/Publication: 2022-10-05 17:20:09 UTC +* Number of recursive dependencies: 111 -Run `revdepcheck::cloud_details(, "CIARA")` for more info +Run `revdepcheck::cloud_details(, "contrast")` for more info
-## Error before installation - -### Devel +## In both -``` -* using log directory ‘/tmp/workdir/CIARA/new/CIARA.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘CIARA/DESCRIPTION’ ... OK -... -* checking tests ... OK - Running ‘testthat.R’ -* checking for unstated dependencies in vignettes ... OK -* checking package vignettes in ‘inst/doc’ ... OK -* checking running R code from vignettes ... OK - ‘CIARA.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... NOTE -Note: skipping ‘CIARA.Rmd’ due to unavailable dependencies: 'Seurat' -* DONE -Status: 3 NOTEs +* checking whether package ‘contrast’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/contrast/new/contrast.Rcheck/00install.out’ for details. + ``` +## Installation +### Devel +``` +* installing *source* package ‘contrast’ ... +** package ‘contrast’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘contrast’ +* removing ‘/tmp/workdir/contrast/new/contrast.Rcheck/contrast’ ``` ### CRAN ``` -* using log directory ‘/tmp/workdir/CIARA/old/CIARA.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘CIARA/DESCRIPTION’ ... OK -... -* checking tests ... OK - Running ‘testthat.R’ -* checking for unstated dependencies in vignettes ... OK -* checking package vignettes in ‘inst/doc’ ... OK -* checking running R code from vignettes ... OK - ‘CIARA.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... NOTE -Note: skipping ‘CIARA.Rmd’ due to unavailable dependencies: 'Seurat' -* DONE -Status: 3 NOTEs - - - +* installing *source* package ‘contrast’ ... +** package ‘contrast’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘contrast’ +* removing ‘/tmp/workdir/contrast/old/contrast.Rcheck/contrast’ ``` -# clarify +# coxed
-* Version: 0.2.1 -* GitHub: https://github.com/iqss/clarify -* Source code: https://github.com/cran/clarify -* Date/Publication: 2024-05-30 16:50:02 UTC -* Number of recursive dependencies: 163 +* Version: 0.3.3 +* GitHub: https://github.com/jkropko/coxed +* Source code: https://github.com/cran/coxed +* Date/Publication: 2020-08-02 01:20:07 UTC +* Number of recursive dependencies: 95 -Run `revdepcheck::cloud_details(, "clarify")` for more info +Run `revdepcheck::cloud_details(, "coxed")` for more info
-## Error before installation - -### Devel +## In both -``` -* using log directory ‘/tmp/workdir/clarify/new/clarify.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘clarify/DESCRIPTION’ ... OK -... -* checking tests ... OK - Running ‘testthat.R’ -* checking for unstated dependencies in vignettes ... OK -* checking package vignettes in ‘inst/doc’ ... OK -* checking running R code from vignettes ... OK - ‘Zelig.Rmd’ using ‘UTF-8’... OK - ‘clarify.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: 1 NOTE +* checking whether package ‘coxed’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/coxed/new/coxed.Rcheck/00install.out’ for details. + ``` +## Installation +### Devel +``` +* installing *source* package ‘coxed’ ... +** package ‘coxed’ 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: package or namespace load failed for ‘rms’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Execution halted +ERROR: lazy loading failed for package ‘coxed’ +* removing ‘/tmp/workdir/coxed/new/coxed.Rcheck/coxed’ ``` ### CRAN ``` -* using log directory ‘/tmp/workdir/clarify/old/clarify.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘clarify/DESCRIPTION’ ... OK -... -* checking tests ... OK - Running ‘testthat.R’ -* checking for unstated dependencies in vignettes ... OK -* checking package vignettes in ‘inst/doc’ ... OK -* checking running R code from vignettes ... OK - ‘Zelig.Rmd’ using ‘UTF-8’... OK - ‘clarify.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: 1 NOTE - - - +* installing *source* package ‘coxed’ ... +** package ‘coxed’ 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: package or namespace load failed for ‘rms’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Execution halted +ERROR: lazy loading failed for package ‘coxed’ +* removing ‘/tmp/workdir/coxed/old/coxed.Rcheck/coxed’ ``` -# ClustAssess +# CRMetrics
* Version: 0.3.0 -* GitHub: https://github.com/Core-Bioinformatics/ClustAssess -* Source code: https://github.com/cran/ClustAssess -* Date/Publication: 2022-01-26 16:52:46 UTC -* Number of recursive dependencies: 164 +* GitHub: https://github.com/khodosevichlab/CRMetrics +* Source code: https://github.com/cran/CRMetrics +* Date/Publication: 2023-09-01 09:00:06 UTC +* Number of recursive dependencies: 239 -Run `revdepcheck::cloud_details(, "ClustAssess")` for more info +Run `revdepcheck::cloud_details(, "CRMetrics")` for more info
-## Error before installation +## In both -### Devel +* checking whether package ‘CRMetrics’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/CRMetrics/new/CRMetrics.Rcheck/00install.out’ for details. + ``` -``` -* using log directory ‘/tmp/workdir/ClustAssess/new/ClustAssess.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘ClustAssess/DESCRIPTION’ ... OK -... ---- finished re-building ‘comparing-soft-and-hierarchical.Rmd’ +## Installation -SUMMARY: processing the following file failed: - ‘ClustAssess.Rmd’ +### Devel -Error: Vignette re-building failed. +``` +* installing *source* package ‘CRMetrics’ ... +** package ‘CRMetrics’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace Execution halted - -* DONE -Status: 1 ERROR, 1 WARNING, 2 NOTEs - - - +ERROR: lazy loading failed for package ‘CRMetrics’ +* removing ‘/tmp/workdir/CRMetrics/new/CRMetrics.Rcheck/CRMetrics’ ``` ### CRAN ``` -* using log directory ‘/tmp/workdir/ClustAssess/old/ClustAssess.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘ClustAssess/DESCRIPTION’ ... OK -... ---- finished re-building ‘comparing-soft-and-hierarchical.Rmd’ - -SUMMARY: processing the following file failed: - ‘ClustAssess.Rmd’ - -Error: Vignette re-building failed. +* installing *source* package ‘CRMetrics’ ... +** package ‘CRMetrics’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace Execution halted - -* DONE -Status: 1 ERROR, 1 WARNING, 2 NOTEs - - - +ERROR: lazy loading failed for package ‘CRMetrics’ +* removing ‘/tmp/workdir/CRMetrics/old/CRMetrics.Rcheck/CRMetrics’ ``` -# clustree +# csmpv
-* Version: 0.5.1 -* GitHub: https://github.com/lazappi/clustree -* Source code: https://github.com/cran/clustree -* Date/Publication: 2023-11-05 19:10:02 UTC -* Number of recursive dependencies: 192 +* Version: 1.0.3 +* GitHub: NA +* Source code: https://github.com/cran/csmpv +* Date/Publication: 2024-03-01 18:12:44 UTC +* Number of recursive dependencies: 178 -Run `revdepcheck::cloud_details(, "clustree")` for more info +Run `revdepcheck::cloud_details(, "csmpv")` for more info
-## Error before installation +## In both + +* checking whether package ‘csmpv’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/csmpv/new/csmpv.Rcheck/00install.out’ for details. + ``` + +## Installation ### Devel ``` -* using log directory ‘/tmp/workdir/clustree/new/clustree.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘clustree/DESCRIPTION’ ... OK -... -* checking tests ... OK - Running ‘spelling.R’ - Running ‘testthat.R’ -* checking for unstated dependencies in vignettes ... OK -* checking package vignettes in ‘inst/doc’ ... OK -* checking running R code from vignettes ... OK - ‘clustree.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: 1 NOTE +* installing *source* package ‘csmpv’ ... +** package ‘csmpv’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘csmpv’ +* removing ‘/tmp/workdir/csmpv/new/csmpv.Rcheck/csmpv’ +``` +### CRAN +``` +* installing *source* package ‘csmpv’ ... +** package ‘csmpv’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘csmpv’ +* removing ‘/tmp/workdir/csmpv/old/csmpv.Rcheck/csmpv’ ``` -### CRAN +# ctsem + +
+ +* Version: 3.10.0 +* GitHub: https://github.com/cdriveraus/ctsem +* Source code: https://github.com/cran/ctsem +* Date/Publication: 2024-05-09 14:40:03 UTC +* Number of recursive dependencies: 158 + +Run `revdepcheck::cloud_details(, "ctsem")` for more info + +
+ +## In both + +* checking whether package ‘ctsem’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/ctsem/new/ctsem.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel ``` -* using log directory ‘/tmp/workdir/clustree/old/clustree.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘clustree/DESCRIPTION’ ... OK +* installing *source* package ‘ctsem’ ... +** package ‘ctsem’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C++ compiler: ‘g++ (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ +using C++17 + + +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I"../inst/include" -I"/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src" -DBOOST_DISABLE_ASSERTS -DEIGEN_NO_DEBUG -DBOOST_MATH_OVERFLOW_ERROR_POLICY=errno_on_error -DUSE_STANC3 -D_HAS_AUTO_PTR_ETC=0 -I'/opt/R/4.3.1/lib/R/site-library/BH/include' -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppEigen/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -I'/opt/R/4.3.1/lib/R/site-library/rstan/include' -I'/opt/R/4.3.1/lib/R/site-library/StanHeaders/include' -I/usr/local/include -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -D_REENTRANT -DSTAN_THREADS -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +In file included from /opt/R/4.3.1/lib/R/site-library/RcppEigen/include/Eigen/Core:205, ... -* checking tests ... OK - Running ‘spelling.R’ - Running ‘testthat.R’ -* checking for unstated dependencies in vignettes ... OK -* checking package vignettes in ‘inst/doc’ ... OK -* checking running R code from vignettes ... OK - ‘clustree.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: 1 NOTE +/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src/stan/mcmc/hmc/hamiltonians/dense_e_metric.hpp:22:56: required from ‘double stan::mcmc::dense_e_metric::T(stan::mcmc::dense_e_point&) [with Model = model_ctsm_namespace::model_ctsm; BaseRNG = boost::random::additive_combine_engine, boost::random::linear_congruential_engine >]’ +/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src/stan/mcmc/hmc/hamiltonians/dense_e_metric.hpp:21:10: required from here +/opt/R/4.3.1/lib/R/site-library/RcppEigen/include/Eigen/src/Core/DenseCoeffsBase.h:654:74: warning: ignoring attributes on template argument ‘Eigen::internal::packet_traits::type’ {aka ‘__m128d’} [-Wignored-attributes] + 654 | return internal::first_aligned::alignment),Derived>(m); + | ^~~~~~~~~ +g++: fatal error: Killed signal terminated program cc1plus +compilation terminated. +make: *** [/opt/R/4.3.1/lib/R/etc/Makeconf:198: stanExports_ctsm.o] Error 1 +ERROR: compilation failed for package ‘ctsem’ +* removing ‘/tmp/workdir/ctsem/new/ctsem.Rcheck/ctsem’ + + +``` +### CRAN +``` +* installing *source* package ‘ctsem’ ... +** package ‘ctsem’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C++ compiler: ‘g++ (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ +using C++17 +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I"../inst/include" -I"/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src" -DBOOST_DISABLE_ASSERTS -DEIGEN_NO_DEBUG -DBOOST_MATH_OVERFLOW_ERROR_POLICY=errno_on_error -DUSE_STANC3 -D_HAS_AUTO_PTR_ETC=0 -I'/opt/R/4.3.1/lib/R/site-library/BH/include' -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppEigen/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -I'/opt/R/4.3.1/lib/R/site-library/rstan/include' -I'/opt/R/4.3.1/lib/R/site-library/StanHeaders/include' -I/usr/local/include -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -D_REENTRANT -DSTAN_THREADS -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +In file included from /opt/R/4.3.1/lib/R/site-library/RcppEigen/include/Eigen/Core:205, +... +/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src/stan/mcmc/hmc/hamiltonians/dense_e_metric.hpp:22:56: required from ‘double stan::mcmc::dense_e_metric::T(stan::mcmc::dense_e_point&) [with Model = model_ctsm_namespace::model_ctsm; BaseRNG = boost::random::additive_combine_engine, boost::random::linear_congruential_engine >]’ +/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src/stan/mcmc/hmc/hamiltonians/dense_e_metric.hpp:21:10: required from here +/opt/R/4.3.1/lib/R/site-library/RcppEigen/include/Eigen/src/Core/DenseCoeffsBase.h:654:74: warning: ignoring attributes on template argument ‘Eigen::internal::packet_traits::type’ {aka ‘__m128d’} [-Wignored-attributes] + 654 | return internal::first_aligned::alignment),Derived>(m); + | ^~~~~~~~~ +g++: fatal error: Killed signal terminated program cc1plus +compilation terminated. +make: *** [/opt/R/4.3.1/lib/R/etc/Makeconf:198: stanExports_ctsm.o] Error 1 +ERROR: compilation failed for package ‘ctsem’ +* removing ‘/tmp/workdir/ctsem/old/ctsem.Rcheck/ctsem’ ``` -# cmprskcoxmsm +# DepthProc
-* Version: 0.2.1 -* GitHub: NA -* Source code: https://github.com/cran/cmprskcoxmsm -* Date/Publication: 2021-09-04 05:50:02 UTC -* Number of recursive dependencies: 71 +* Version: 2.1.5 +* GitHub: https://github.com/zzawadz/DepthProc +* Source code: https://github.com/cran/DepthProc +* Date/Publication: 2022-02-03 20:30:02 UTC +* Number of recursive dependencies: 134 -Run `revdepcheck::cloud_details(, "cmprskcoxmsm")` for more info +Run `revdepcheck::cloud_details(, "DepthProc")` for more info
## In both -* checking whether package ‘cmprskcoxmsm’ can be installed ... ERROR +* checking whether package ‘DepthProc’ can be installed ... ERROR ``` Installation failed. - See ‘/tmp/workdir/cmprskcoxmsm/new/cmprskcoxmsm.Rcheck/00install.out’ for details. + See ‘/tmp/workdir/DepthProc/new/DepthProc.Rcheck/00install.out’ for details. ``` ## Installation @@ -2240,821 +1741,735 @@ Run `revdepcheck::cloud_details(, "cmprskcoxmsm")` for more info ### Devel ``` -* installing *source* package ‘cmprskcoxmsm’ ... -** package ‘cmprskcoxmsm’ successfully unpacked and MD5 sums checked +* installing *source* package ‘DepthProc’ ... +** package ‘DepthProc’ successfully unpacked and MD5 sums checked ** using staged installation +** libs +using C++ compiler: ‘g++ (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ +using C++11 +g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c Depth.cpp -o Depth.o +g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c LocationEstimators.cpp -o LocationEstimators.o +g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c LocationScaleDepth.cpp -o LocationScaleDepth.o +g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c LocationScaleDepthCPP.cpp -o LocationScaleDepthCPP.o +... +installing to /tmp/workdir/DepthProc/new/DepthProc.Rcheck/00LOCK-DepthProc/00new/DepthProc/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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Error: package or namespace load failed for ‘np’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required Execution halted -ERROR: lazy loading failed for package ‘cmprskcoxmsm’ -* removing ‘/tmp/workdir/cmprskcoxmsm/new/cmprskcoxmsm.Rcheck/cmprskcoxmsm’ +ERROR: lazy loading failed for package ‘DepthProc’ +* removing ‘/tmp/workdir/DepthProc/new/DepthProc.Rcheck/DepthProc’ ``` ### CRAN ``` -* installing *source* package ‘cmprskcoxmsm’ ... -** package ‘cmprskcoxmsm’ successfully unpacked and MD5 sums checked +* installing *source* package ‘DepthProc’ ... +** package ‘DepthProc’ successfully unpacked and MD5 sums checked ** using staged installation +** libs +using C++ compiler: ‘g++ (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ +using C++11 +g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c Depth.cpp -o Depth.o +g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c LocationEstimators.cpp -o LocationEstimators.o +g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c LocationScaleDepth.cpp -o LocationScaleDepth.o +g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c LocationScaleDepthCPP.cpp -o LocationScaleDepthCPP.o +... +installing to /tmp/workdir/DepthProc/old/DepthProc.Rcheck/00LOCK-DepthProc/00new/DepthProc/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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Error: package or namespace load failed for ‘np’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required Execution halted -ERROR: lazy loading failed for package ‘cmprskcoxmsm’ -* removing ‘/tmp/workdir/cmprskcoxmsm/old/cmprskcoxmsm.Rcheck/cmprskcoxmsm’ +ERROR: lazy loading failed for package ‘DepthProc’ +* removing ‘/tmp/workdir/DepthProc/old/DepthProc.Rcheck/DepthProc’ ``` -# combiroc +# DR.SC
-* Version: 0.3.4 -* GitHub: https://github.com/ingmbioinfo/combiroc -* Source code: https://github.com/cran/combiroc -* Date/Publication: 2023-07-06 12:53:12 UTC -* Number of recursive dependencies: 160 +* Version: 3.4 +* GitHub: https://github.com/feiyoung/DR.SC +* Source code: https://github.com/cran/DR.SC +* Date/Publication: 2024-03-19 08:40:02 UTC +* Number of recursive dependencies: 151 -Run `revdepcheck::cloud_details(, "combiroc")` for more info +Run `revdepcheck::cloud_details(, "DR.SC")` for more info
-## Error before installation +## In both + +* checking whether package ‘DR.SC’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/DR.SC/new/DR.SC.Rcheck/00install.out’ for details. + ``` + +## Installation ### Devel ``` -* using log directory ‘/tmp/workdir/combiroc/new/combiroc.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘combiroc/DESCRIPTION’ ... OK +* installing *source* package ‘DR.SC’ ... +** package ‘DR.SC’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C++ compiler: ‘g++ (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ +using C++17 +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -DARMA_64BIT_WORD -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -DARMA_64BIT_WORD -fpic -g -O2 -c getNB_fast.cpp -o getNB_fast.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -DARMA_64BIT_WORD -fpic -g -O2 -c mt_paral_job.cpp -o mt_paral_job.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -DARMA_64BIT_WORD -fpic -g -O2 -c mt_paral_job2.cpp -o mt_paral_job2.o ... - - When sourcing ‘combiroc_vignette_2.R’: -Error: Cannot find the file(s): "/tmp/Rtmpkgsj1K/file17bc502b97ef/vignettes/vignettes/atlas_dimplot.png" +** R +** data +** inst +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.4 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace Execution halted - - ‘combiroc_vignette_1.Rmd’ using ‘UTF-8’... OK - ‘combiroc_vignette_2.Rmd’ using ‘UTF-8’... failed -* checking re-building of vignette outputs ... OK -* DONE -Status: 1 ERROR, 1 NOTE - - - +ERROR: lazy loading failed for package ‘DR.SC’ +* removing ‘/tmp/workdir/DR.SC/new/DR.SC.Rcheck/DR.SC’ ``` ### CRAN ``` -* using log directory ‘/tmp/workdir/combiroc/old/combiroc.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘combiroc/DESCRIPTION’ ... OK +* installing *source* package ‘DR.SC’ ... +** package ‘DR.SC’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C++ compiler: ‘g++ (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ +using C++17 +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -DARMA_64BIT_WORD -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -DARMA_64BIT_WORD -fpic -g -O2 -c getNB_fast.cpp -o getNB_fast.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -DARMA_64BIT_WORD -fpic -g -O2 -c mt_paral_job.cpp -o mt_paral_job.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -DARMA_64BIT_WORD -fpic -g -O2 -c mt_paral_job2.cpp -o mt_paral_job2.o ... - - When sourcing ‘combiroc_vignette_2.R’: -Error: Cannot find the file(s): "/tmp/Rtmp21gOJ2/file108d3edb788a/vignettes/vignettes/atlas_dimplot.png" +** R +** data +** inst +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.4 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace Execution halted - - ‘combiroc_vignette_1.Rmd’ using ‘UTF-8’... OK - ‘combiroc_vignette_2.Rmd’ using ‘UTF-8’... failed -* checking re-building of vignette outputs ... OK -* DONE -Status: 1 ERROR, 1 NOTE - - - +ERROR: lazy loading failed for package ‘DR.SC’ +* removing ‘/tmp/workdir/DR.SC/old/DR.SC.Rcheck/DR.SC’ ``` -# conos +# DynNom
-* Version: 1.5.2 -* GitHub: https://github.com/kharchenkolab/conos -* Source code: https://github.com/cran/conos -* Date/Publication: 2024-02-26 19:30:05 UTC -* Number of recursive dependencies: 239 +* Version: 5.1 +* GitHub: NA +* Source code: https://github.com/cran/DynNom +* Date/Publication: 2024-06-07 12:20:21 UTC +* Number of recursive dependencies: 104 -Run `revdepcheck::cloud_details(, "conos")` for more info +Run `revdepcheck::cloud_details(, "DynNom")` for more info
-## Error before installation +## In both + +* checking whether package ‘DynNom’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/DynNom/new/DynNom.Rcheck/00install.out’ for details. + ``` + +## Installation ### Devel ``` -* using log directory ‘/tmp/workdir/conos/new/conos.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘conos/DESCRIPTION’ ... OK -... -* checking for GNU extensions in Makefiles ... OK -* checking for portable use of $(BLAS_LIBS) and $(LAPACK_LIBS) ... OK -* checking use of PKG_*FLAGS in Makefiles ... OK -* checking compiled code ... OK -* checking examples ... OK -* checking for unstated dependencies in ‘tests’ ... OK -* checking tests ... OK - Running ‘testthat.R’ -* DONE -Status: 2 NOTEs - - - +* installing *source* package ‘DynNom’ ... +** package ‘DynNom’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘DynNom’ +* removing ‘/tmp/workdir/DynNom/new/DynNom.Rcheck/DynNom’ ``` ### CRAN ``` -* using log directory ‘/tmp/workdir/conos/old/conos.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘conos/DESCRIPTION’ ... OK -... -* checking for GNU extensions in Makefiles ... OK -* checking for portable use of $(BLAS_LIBS) and $(LAPACK_LIBS) ... OK -* checking use of PKG_*FLAGS in Makefiles ... OK -* checking compiled code ... OK -* checking examples ... OK -* checking for unstated dependencies in ‘tests’ ... OK -* checking tests ... OK - Running ‘testthat.R’ -* DONE -Status: 2 NOTEs - - - +* installing *source* package ‘DynNom’ ... +** package ‘DynNom’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘DynNom’ +* removing ‘/tmp/workdir/DynNom/old/DynNom.Rcheck/DynNom’ ``` -# contrast +# easybgm
-* Version: 0.24.2 -* GitHub: https://github.com/Alanocallaghan/contrast -* Source code: https://github.com/cran/contrast -* Date/Publication: 2022-10-05 17:20:09 UTC -* Number of recursive dependencies: 111 +* Version: 0.1.2 +* GitHub: https://github.com/KarolineHuth/easybgm +* Source code: https://github.com/cran/easybgm +* Date/Publication: 2024-03-13 13:40:02 UTC +* Number of recursive dependencies: 174 -Run `revdepcheck::cloud_details(, "contrast")` for more info +Run `revdepcheck::cloud_details(, "easybgm")` for more info
-## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/contrast/new/contrast.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘contrast/DESCRIPTION’ ... OK -... -* this is package ‘contrast’ version ‘0.24.2’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘rms’ +## In both -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR +* checking whether package ‘easybgm’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/easybgm/new/easybgm.Rcheck/00install.out’ for details. + ``` +## Installation +### Devel +``` +* installing *source* package ‘easybgm’ ... +** package ‘easybgm’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘easybgm’ +* removing ‘/tmp/workdir/easybgm/new/easybgm.Rcheck/easybgm’ ``` ### CRAN ``` -* using log directory ‘/tmp/workdir/contrast/old/contrast.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘contrast/DESCRIPTION’ ... OK -... -* this is package ‘contrast’ version ‘0.24.2’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘rms’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - +* installing *source* package ‘easybgm’ ... +** package ‘easybgm’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘easybgm’ +* removing ‘/tmp/workdir/easybgm/old/easybgm.Rcheck/easybgm’ ``` -# contsurvplot +# ecolottery
-* Version: 0.2.1 -* GitHub: https://github.com/RobinDenz1/contsurvplot -* Source code: https://github.com/cran/contsurvplot -* Date/Publication: 2023-08-15 08:00:03 UTC -* Number of recursive dependencies: 157 +* Version: 1.0.0 +* GitHub: https://github.com/frmunoz/ecolottery +* Source code: https://github.com/cran/ecolottery +* Date/Publication: 2017-07-03 11:01:29 UTC +* Number of recursive dependencies: 88 -Run `revdepcheck::cloud_details(, "contsurvplot")` for more info +Run `revdepcheck::cloud_details(, "ecolottery")` for more info
-## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/contsurvplot/new/contsurvplot.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘contsurvplot/DESCRIPTION’ ... OK -... -* this is package ‘contsurvplot’ version ‘0.2.1’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘riskRegression’ +## In both -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR +* checking whether package ‘ecolottery’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/ecolottery/new/ecolottery.Rcheck/00install.out’ for details. + ``` +## Installation +### Devel +``` +* installing *source* package ‘ecolottery’ ... +** package ‘ecolottery’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘ecolottery’ +* removing ‘/tmp/workdir/ecolottery/new/ecolottery.Rcheck/ecolottery’ ``` ### CRAN ``` -* using log directory ‘/tmp/workdir/contsurvplot/old/contsurvplot.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘contsurvplot/DESCRIPTION’ ... OK -... -* this is package ‘contsurvplot’ version ‘0.2.1’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘riskRegression’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - +* installing *source* package ‘ecolottery’ ... +** package ‘ecolottery’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘ecolottery’ +* removing ‘/tmp/workdir/ecolottery/old/ecolottery.Rcheck/ecolottery’ ``` -# countland +# EpiEstim
-* Version: 0.1.2 -* GitHub: https://github.com/shchurch/countland -* Source code: https://github.com/cran/countland -* Date/Publication: 2024-02-01 18:00:02 UTC -* Number of recursive dependencies: 198 +* Version: 2.2-4 +* GitHub: https://github.com/mrc-ide/EpiEstim +* Source code: https://github.com/cran/EpiEstim +* Date/Publication: 2021-01-07 16:20:10 UTC +* Number of recursive dependencies: 91 -Run `revdepcheck::cloud_details(, "countland")` for more info +Run `revdepcheck::cloud_details(, "EpiEstim")` for more info
-## Error before installation - -### Devel +## In both -``` -* using log directory ‘/tmp/workdir/countland/new/countland.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘countland/DESCRIPTION’ ... OK -... - 1. └─base::loadNamespace(x) at test-countland_subset.R:2:1 - 2. └─base::withRestarts(stop(cond), retry_loadNamespace = function() NULL) - 3. └─base (local) withOneRestart(expr, restarts[[1L]]) - 4. └─base (local) doWithOneRestart(return(expr), restart) - - [ FAIL 7 | WARN 0 | SKIP 0 | PASS 13 ] - Error: Test failures - Execution halted -* DONE -Status: 2 ERRORs, 1 NOTE +* checking whether package ‘EpiEstim’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/EpiEstim/new/EpiEstim.Rcheck/00install.out’ for details. + ``` +## Installation +### Devel +``` +* installing *source* package ‘EpiEstim’ ... +** package ‘EpiEstim’ successfully unpacked and MD5 sums checked +** 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘EpiEstim’ +* removing ‘/tmp/workdir/EpiEstim/new/EpiEstim.Rcheck/EpiEstim’ ``` ### CRAN ``` -* using log directory ‘/tmp/workdir/countland/old/countland.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘countland/DESCRIPTION’ ... OK -... - 1. └─base::loadNamespace(x) at test-countland_subset.R:2:1 - 2. └─base::withRestarts(stop(cond), retry_loadNamespace = function() NULL) - 3. └─base (local) withOneRestart(expr, restarts[[1L]]) - 4. └─base (local) doWithOneRestart(return(expr), restart) - - [ FAIL 7 | WARN 0 | SKIP 0 | PASS 13 ] - Error: Test failures - Execution halted -* DONE -Status: 2 ERRORs, 1 NOTE - - - +* installing *source* package ‘EpiEstim’ ... +** package ‘EpiEstim’ successfully unpacked and MD5 sums checked +** 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘EpiEstim’ +* removing ‘/tmp/workdir/EpiEstim/old/EpiEstim.Rcheck/EpiEstim’ ``` -# coveffectsplot +# evolqg
-* Version: 1.0.5 -* GitHub: https://github.com/smouksassi/coveffectsplot -* Source code: https://github.com/cran/coveffectsplot -* Date/Publication: 2024-01-18 14:10:02 UTC -* Number of recursive dependencies: 148 +* Version: 0.3-4 +* GitHub: https://github.com/lem-usp/evolqg +* Source code: https://github.com/cran/evolqg +* Date/Publication: 2023-12-05 15:20:12 UTC +* Number of recursive dependencies: 111 -Run `revdepcheck::cloud_details(, "coveffectsplot")` for more info +Run `revdepcheck::cloud_details(, "evolqg")` for more info
-## Error before installation - -### Devel +## In both -``` -* using log directory ‘/tmp/workdir/coveffectsplot/new/coveffectsplot.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘coveffectsplot/DESCRIPTION’ ... OK -... ---- finished re-building ‘introduction_to_coveffectsplot.Rmd’ - -SUMMARY: processing the following files failed: - ‘Exposure_Response_Example.Rmd’ ‘Pediatric_Cov_Sim.Rmd’ - -Error: Vignette re-building failed. -Execution halted - -* DONE -Status: 1 WARNING, 2 NOTEs +* checking whether package ‘evolqg’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/evolqg/new/evolqg.Rcheck/00install.out’ for details. + ``` +## Installation +### Devel +``` +* installing *source* package ‘evolqg’ ... +** package ‘evolqg’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C++ compiler: ‘g++ (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c fast_RS.cpp -o fast_RS.o +g++ -std=gnu++17 -shared -L/opt/R/4.3.1/lib/R/lib -L/usr/local/lib -o evolqg.so RcppExports.o fast_RS.o -llapack -lblas -lgfortran -lm -lquadmath -L/opt/R/4.3.1/lib/R/lib -lR +installing to /tmp/workdir/evolqg/new/evolqg.Rcheck/00LOCK-evolqg/00new/evolqg/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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘evolqg’ +* removing ‘/tmp/workdir/evolqg/new/evolqg.Rcheck/evolqg’ ``` ### CRAN ``` -* using log directory ‘/tmp/workdir/coveffectsplot/old/coveffectsplot.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘coveffectsplot/DESCRIPTION’ ... OK -... ---- finished re-building ‘introduction_to_coveffectsplot.Rmd’ - -SUMMARY: processing the following file failed: - ‘Pediatric_Cov_Sim.Rmd’ - -Error: Vignette re-building failed. +* installing *source* package ‘evolqg’ ... +** package ‘evolqg’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C++ compiler: ‘g++ (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c fast_RS.cpp -o fast_RS.o +g++ -std=gnu++17 -shared -L/opt/R/4.3.1/lib/R/lib -L/usr/local/lib -o evolqg.so RcppExports.o fast_RS.o -llapack -lblas -lgfortran -lm -lquadmath -L/opt/R/4.3.1/lib/R/lib -lR +installing to /tmp/workdir/evolqg/old/evolqg.Rcheck/00LOCK-evolqg/00new/evolqg/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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace Execution halted - -* DONE -Status: 1 WARNING, 2 NOTEs - - - +ERROR: lazy loading failed for package ‘evolqg’ +* removing ‘/tmp/workdir/evolqg/old/evolqg.Rcheck/evolqg’ ``` -# coxed +# ForecastComb
-* Version: 0.3.3 -* GitHub: https://github.com/jkropko/coxed -* Source code: https://github.com/cran/coxed -* Date/Publication: 2020-08-02 01:20:07 UTC -* Number of recursive dependencies: 109 +* Version: 1.3.1 +* GitHub: https://github.com/ceweiss/ForecastComb +* Source code: https://github.com/cran/ForecastComb +* Date/Publication: 2018-08-07 13:50:08 UTC +* Number of recursive dependencies: 74 -Run `revdepcheck::cloud_details(, "coxed")` for more info +Run `revdepcheck::cloud_details(, "ForecastComb")` for more info
-## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/coxed/new/coxed.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘coxed/DESCRIPTION’ ... OK -... -* this is package ‘coxed’ version ‘0.3.3’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘rms’ +## In both -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR +* checking whether package ‘ForecastComb’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/ForecastComb/new/ForecastComb.Rcheck/00install.out’ for details. + ``` +## Installation +### Devel +``` +* installing *source* package ‘ForecastComb’ ... +** package ‘ForecastComb’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** data +*** moving datasets to lazyload DB +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘ForecastComb’ +* removing ‘/tmp/workdir/ForecastComb/new/ForecastComb.Rcheck/ForecastComb’ ``` ### CRAN ``` -* using log directory ‘/tmp/workdir/coxed/old/coxed.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘coxed/DESCRIPTION’ ... OK -... -* this is package ‘coxed’ version ‘0.3.3’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘rms’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - +* installing *source* package ‘ForecastComb’ ... +** package ‘ForecastComb’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** data +*** moving datasets to lazyload DB +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘ForecastComb’ +* removing ‘/tmp/workdir/ForecastComb/old/ForecastComb.Rcheck/ForecastComb’ ``` -# CRMetrics +# gapfill
-* Version: 0.3.0 -* GitHub: https://github.com/khodosevichlab/CRMetrics -* Source code: https://github.com/cran/CRMetrics -* Date/Publication: 2023-09-01 09:00:06 UTC -* Number of recursive dependencies: 234 +* Version: 0.9.6-1 +* GitHub: https://github.com/florafauna/gapfill +* Source code: https://github.com/cran/gapfill +* Date/Publication: 2021-02-12 10:10:05 UTC +* Number of recursive dependencies: 71 -Run `revdepcheck::cloud_details(, "CRMetrics")` for more info +Run `revdepcheck::cloud_details(, "gapfill")` for more info
-## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/CRMetrics/new/CRMetrics.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘CRMetrics/DESCRIPTION’ ... OK -... -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘ggpmisc’ +## In both -Package suggested but not available for checking: ‘Seurat’ +* checking whether package ‘gapfill’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/gapfill/new/gapfill.Rcheck/00install.out’ for details. + ``` -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR +* checking package dependencies ... NOTE + ``` + Packages which this enhances but not available for checking: + 'raster', 'doParallel', 'doMPI' + ``` +## Installation +### Devel +``` +* installing *source* package ‘gapfill’ ... +** package ‘gapfill’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C++ compiler: ‘g++ (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c gapfill.cpp -o gapfill.o +g++ -std=gnu++17 -shared -L/opt/R/4.3.1/lib/R/lib -L/usr/local/lib -o gapfill.so RcppExports.o gapfill.o -L/opt/R/4.3.1/lib/R/lib -lR +installing to /tmp/workdir/gapfill/new/gapfill.Rcheck/00LOCK-gapfill/00new/gapfill/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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘gapfill’ +* removing ‘/tmp/workdir/gapfill/new/gapfill.Rcheck/gapfill’ ``` ### CRAN ``` -* using log directory ‘/tmp/workdir/CRMetrics/old/CRMetrics.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘CRMetrics/DESCRIPTION’ ... OK +* installing *source* package ‘gapfill’ ... +** package ‘gapfill’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C++ compiler: ‘g++ (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c gapfill.cpp -o gapfill.o +g++ -std=gnu++17 -shared -L/opt/R/4.3.1/lib/R/lib -L/usr/local/lib -o gapfill.so RcppExports.o gapfill.o -L/opt/R/4.3.1/lib/R/lib -lR +installing to /tmp/workdir/gapfill/old/gapfill.Rcheck/00LOCK-gapfill/00new/gapfill/libs +** R ... -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘ggpmisc’ - -Package suggested but not available for checking: ‘Seurat’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - +** 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘gapfill’ +* removing ‘/tmp/workdir/gapfill/old/gapfill.Rcheck/gapfill’ ``` -# crosslag +# GeomComb
-* Version: 0.1.0 -* GitHub: NA -* Source code: https://github.com/cran/crosslag -* Date/Publication: 2024-05-17 10:10:03 UTC -* Number of recursive dependencies: 122 +* Version: 1.0 +* GitHub: https://github.com/ceweiss/GeomComb +* Source code: https://github.com/cran/GeomComb +* Date/Publication: 2016-11-27 16:02:26 +* Number of recursive dependencies: 75 -Run `revdepcheck::cloud_details(, "crosslag")` for more info +Run `revdepcheck::cloud_details(, "GeomComb")` for more info
-## Error before installation +## In both + +* checking whether package ‘GeomComb’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/GeomComb/new/GeomComb.Rcheck/00install.out’ for details. + ``` + +## Installation ### Devel ``` -* using log directory ‘/tmp/workdir/crosslag/new/crosslag.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘crosslag/DESCRIPTION’ ... OK -... -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘rms’ - -Packages required and available but unsuitable versions: 'mgcv', 'stats' - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - +* installing *source* package ‘GeomComb’ ... +** package ‘GeomComb’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘GeomComb’ +* removing ‘/tmp/workdir/GeomComb/new/GeomComb.Rcheck/GeomComb’ ``` ### CRAN ``` -* using log directory ‘/tmp/workdir/crosslag/old/crosslag.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘crosslag/DESCRIPTION’ ... OK -... -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘rms’ - -Packages required and available but unsuitable versions: 'mgcv', 'stats' - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - +* installing *source* package ‘GeomComb’ ... +** package ‘GeomComb’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘GeomComb’ +* removing ‘/tmp/workdir/GeomComb/old/GeomComb.Rcheck/GeomComb’ ``` -# csmpv +# ggrcs
-* Version: 1.0.3 +* Version: 0.4.0 * GitHub: NA -* Source code: https://github.com/cran/csmpv -* Date/Publication: 2024-03-01 18:12:44 UTC -* Number of recursive dependencies: 175 +* Source code: https://github.com/cran/ggrcs +* Date/Publication: 2024-06-29 02:40:02 UTC +* Number of recursive dependencies: 78 -Run `revdepcheck::cloud_details(, "csmpv")` for more info +Run `revdepcheck::cloud_details(, "ggrcs")` for more info
-## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/csmpv/new/csmpv.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘csmpv/DESCRIPTION’ ... OK -... -* this is package ‘csmpv’ version ‘1.0.3’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘rms’ +## In both -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR +* checking whether package ‘ggrcs’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/ggrcs/new/ggrcs.Rcheck/00install.out’ for details. + ``` +## Installation +### Devel +``` +* installing *source* package ‘ggrcs’ ... +** package ‘ggrcs’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘ggrcs’ +* removing ‘/tmp/workdir/ggrcs/new/ggrcs.Rcheck/ggrcs’ ``` ### CRAN ``` -* using log directory ‘/tmp/workdir/csmpv/old/csmpv.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘csmpv/DESCRIPTION’ ... OK -... -* this is package ‘csmpv’ version ‘1.0.3’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘rms’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - +* installing *source* package ‘ggrcs’ ... +** package ‘ggrcs’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘ggrcs’ +* removing ‘/tmp/workdir/ggrcs/old/ggrcs.Rcheck/ggrcs’ ``` -# ctsem +# ggrisk
-* Version: 3.10.0 -* GitHub: https://github.com/cdriveraus/ctsem -* Source code: https://github.com/cran/ctsem -* Date/Publication: 2024-05-09 14:40:03 UTC -* Number of recursive dependencies: 159 +* Version: 1.3 +* GitHub: https://github.com/yikeshu0611/ggrisk +* Source code: https://github.com/cran/ggrisk +* Date/Publication: 2021-08-09 07:40:06 UTC +* Number of recursive dependencies: 115 -Run `revdepcheck::cloud_details(, "ctsem")` for more info +Run `revdepcheck::cloud_details(, "ggrisk")` for more info
## In both -* checking whether package ‘ctsem’ can be installed ... ERROR +* checking whether package ‘ggrisk’ can be installed ... ERROR ``` Installation failed. - See ‘/tmp/workdir/ctsem/new/ctsem.Rcheck/00install.out’ for details. + See ‘/tmp/workdir/ggrisk/new/ggrisk.Rcheck/00install.out’ for details. ``` ## Installation @@ -3062,229 +2477,245 @@ Run `revdepcheck::cloud_details(, "ctsem")` for more info ### Devel ``` -* installing *source* package ‘ctsem’ ... -** package ‘ctsem’ successfully unpacked and MD5 sums checked +* installing *source* package ‘ggrisk’ ... +** package ‘ggrisk’ successfully unpacked and MD5 sums checked ** using staged installation -** libs -using C++ compiler: ‘g++ (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ -using C++17 - - -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I"../inst/include" -I"/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src" -DBOOST_DISABLE_ASSERTS -DEIGEN_NO_DEBUG -DBOOST_MATH_OVERFLOW_ERROR_POLICY=errno_on_error -DUSE_STANC3 -D_HAS_AUTO_PTR_ETC=0 -I'/opt/R/4.3.1/lib/R/site-library/BH/include' -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppEigen/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -I'/opt/R/4.3.1/lib/R/site-library/rstan/include' -I'/opt/R/4.3.1/lib/R/site-library/StanHeaders/include' -I/usr/local/include -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -D_REENTRANT -DSTAN_THREADS -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o -In file included from /opt/R/4.3.1/lib/R/site-library/RcppEigen/include/Eigen/Core:205, -... -/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src/stan/mcmc/hmc/hamiltonians/dense_e_metric.hpp:22:56: required from ‘double stan::mcmc::dense_e_metric::T(stan::mcmc::dense_e_point&) [with Model = model_ctsm_namespace::model_ctsm; BaseRNG = boost::random::additive_combine_engine, boost::random::linear_congruential_engine >]’ -/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src/stan/mcmc/hmc/hamiltonians/dense_e_metric.hpp:21:10: required from here -/opt/R/4.3.1/lib/R/site-library/RcppEigen/include/Eigen/src/Core/DenseCoeffsBase.h:654:74: warning: ignoring attributes on template argument ‘Eigen::internal::packet_traits::type’ {aka ‘__m128d’} [-Wignored-attributes] - 654 | return internal::first_aligned::alignment),Derived>(m); - | ^~~~~~~~~ -g++: fatal error: Killed signal terminated program cc1plus -compilation terminated. -make: *** [/opt/R/4.3.1/lib/R/etc/Makeconf:198: stanExports_ctsm.o] Error 1 -ERROR: compilation failed for package ‘ctsem’ -* removing ‘/tmp/workdir/ctsem/new/ctsem.Rcheck/ctsem’ +** R +** data +*** moving datasets to lazyload DB +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘ggrisk’ +* removing ‘/tmp/workdir/ggrisk/new/ggrisk.Rcheck/ggrisk’ ``` ### CRAN ``` -* installing *source* package ‘ctsem’ ... -** package ‘ctsem’ successfully unpacked and MD5 sums checked +* installing *source* package ‘ggrisk’ ... +** package ‘ggrisk’ successfully unpacked and MD5 sums checked ** using staged installation -** libs -using C++ compiler: ‘g++ (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ -using C++17 - - -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I"../inst/include" -I"/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src" -DBOOST_DISABLE_ASSERTS -DEIGEN_NO_DEBUG -DBOOST_MATH_OVERFLOW_ERROR_POLICY=errno_on_error -DUSE_STANC3 -D_HAS_AUTO_PTR_ETC=0 -I'/opt/R/4.3.1/lib/R/site-library/BH/include' -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppEigen/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -I'/opt/R/4.3.1/lib/R/site-library/rstan/include' -I'/opt/R/4.3.1/lib/R/site-library/StanHeaders/include' -I/usr/local/include -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -D_REENTRANT -DSTAN_THREADS -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o -In file included from /opt/R/4.3.1/lib/R/site-library/RcppEigen/include/Eigen/Core:205, -... -/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src/stan/mcmc/hmc/hamiltonians/dense_e_metric.hpp:22:56: required from ‘double stan::mcmc::dense_e_metric::T(stan::mcmc::dense_e_point&) [with Model = model_ctsm_namespace::model_ctsm; BaseRNG = boost::random::additive_combine_engine, boost::random::linear_congruential_engine >]’ -/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src/stan/mcmc/hmc/hamiltonians/dense_e_metric.hpp:21:10: required from here -/opt/R/4.3.1/lib/R/site-library/RcppEigen/include/Eigen/src/Core/DenseCoeffsBase.h:654:74: warning: ignoring attributes on template argument ‘Eigen::internal::packet_traits::type’ {aka ‘__m128d’} [-Wignored-attributes] - 654 | return internal::first_aligned::alignment),Derived>(m); - | ^~~~~~~~~ -g++: fatal error: Killed signal terminated program cc1plus -compilation terminated. -make: *** [/opt/R/4.3.1/lib/R/etc/Makeconf:198: stanExports_ctsm.o] Error 1 -ERROR: compilation failed for package ‘ctsem’ -* removing ‘/tmp/workdir/ctsem/old/ctsem.Rcheck/ctsem’ +** R +** data +*** moving datasets to lazyload DB +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘ggrisk’ +* removing ‘/tmp/workdir/ggrisk/old/ggrisk.Rcheck/ggrisk’ ``` -# CytoSimplex +# gJLS2
-* Version: 0.1.1 -* GitHub: https://github.com/welch-lab/CytoSimplex -* Source code: https://github.com/cran/CytoSimplex -* Date/Publication: 2023-12-15 09:30:06 UTC -* Number of recursive dependencies: 177 +* Version: 0.2.0 +* GitHub: NA +* Source code: https://github.com/cran/gJLS2 +* Date/Publication: 2021-09-30 09:00:05 UTC +* Number of recursive dependencies: 45 -Run `revdepcheck::cloud_details(, "CytoSimplex")` for more info +Run `revdepcheck::cloud_details(, "gJLS2")` for more info
-## Error before installation +## In both + +* checking whether package ‘gJLS2’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/gJLS2/new/gJLS2.Rcheck/00install.out’ for details. + ``` + +## Installation ### Devel ``` -* using log directory ‘/tmp/workdir/CytoSimplex/new/CytoSimplex.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘CytoSimplex/DESCRIPTION’ ... OK -... -* checking for unstated dependencies in ‘tests’ ... OK -* checking tests ... OK - Running ‘testthat.R’ -* checking for unstated dependencies in vignettes ... OK -* checking package vignettes in ‘inst/doc’ ... OK -* checking running R code from vignettes ... OK - ‘CytoSimplex.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: 2 NOTEs +* installing *source* package ‘gJLS2’ ... +** package ‘gJLS2’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘gJLS2’ +* removing ‘/tmp/workdir/gJLS2/new/gJLS2.Rcheck/gJLS2’ +``` +### CRAN +``` +* installing *source* package ‘gJLS2’ ... +** package ‘gJLS2’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘gJLS2’ +* removing ‘/tmp/workdir/gJLS2/old/gJLS2.Rcheck/gJLS2’ ``` -### CRAN +# Greg -``` -* using log directory ‘/tmp/workdir/CytoSimplex/old/CytoSimplex.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘CytoSimplex/DESCRIPTION’ ... OK -... -* checking for unstated dependencies in ‘tests’ ... OK -* checking tests ... OK - Running ‘testthat.R’ -* checking for unstated dependencies in vignettes ... OK -* checking package vignettes in ‘inst/doc’ ... OK -* checking running R code from vignettes ... OK - ‘CytoSimplex.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: 2 NOTEs +
+ +* Version: 2.0.2 +* GitHub: https://github.com/gforge/Greg +* Source code: https://github.com/cran/Greg +* Date/Publication: 2024-01-29 13:30:21 UTC +* Number of recursive dependencies: 151 +Run `revdepcheck::cloud_details(, "Greg")` for more info +
+## In both +* checking whether package ‘Greg’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/Greg/new/Greg.Rcheck/00install.out’ for details. + ``` -``` -# depigner +## Installation -
+### Devel -* Version: 0.9.1 -* GitHub: https://github.com/CorradoLanera/depigner -* Source code: https://github.com/cran/depigner -* Date/Publication: 2023-04-24 12:40:05 UTC -* Number of recursive dependencies: 132 +``` +* installing *source* package ‘Greg’ ... +** package ‘Greg’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘Greg’ +* removing ‘/tmp/workdir/Greg/new/Greg.Rcheck/Greg’ -Run `revdepcheck::cloud_details(, "depigner")` for more info -
+``` +### CRAN -## Error before installation +``` +* installing *source* package ‘Greg’ ... +** package ‘Greg’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘Greg’ +* removing ‘/tmp/workdir/Greg/old/Greg.Rcheck/Greg’ -### Devel ``` -* using log directory ‘/tmp/workdir/depigner/new/depigner.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘depigner/DESCRIPTION’ ... OK -... -* this is package ‘depigner’ version ‘0.9.1’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘rms’ +# greport -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR +
+* Version: 0.7-4 +* GitHub: https://github.com/harrelfe/greport +* Source code: https://github.com/cran/greport +* Date/Publication: 2023-09-02 22:20:02 UTC +* Number of recursive dependencies: 84 +Run `revdepcheck::cloud_details(, "greport")` for more info +
+## In both -``` -### CRAN +* checking whether package ‘greport’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/greport/new/greport.Rcheck/00install.out’ for details. + ``` -``` -* using log directory ‘/tmp/workdir/depigner/old/depigner.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘depigner/DESCRIPTION’ ... OK -... -* this is package ‘depigner’ version ‘0.9.1’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘rms’ +## Installation -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR +### Devel + +``` +* installing *source* package ‘greport’ ... +** package ‘greport’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘greport’ +* removing ‘/tmp/workdir/greport/new/greport.Rcheck/greport’ +``` +### CRAN +``` +* installing *source* package ‘greport’ ... +** package ‘greport’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘greport’ +* removing ‘/tmp/workdir/greport/old/greport.Rcheck/greport’ ``` -# DepthProc +# hettx
-* Version: 2.1.5 -* GitHub: https://github.com/zzawadz/DepthProc -* Source code: https://github.com/cran/DepthProc -* Date/Publication: 2022-02-03 20:30:02 UTC -* Number of recursive dependencies: 134 +* Version: 0.1.3 +* GitHub: https://github.com/bfifield/hettx +* Source code: https://github.com/cran/hettx +* Date/Publication: 2023-08-19 22:22:34 UTC +* Number of recursive dependencies: 85 -Run `revdepcheck::cloud_details(, "DepthProc")` for more info +Run `revdepcheck::cloud_details(, "hettx")` for more info
## In both -* checking whether package ‘DepthProc’ can be installed ... ERROR +* checking whether package ‘hettx’ can be installed ... ERROR ``` Installation failed. - See ‘/tmp/workdir/DepthProc/new/DepthProc.Rcheck/00install.out’ for details. + See ‘/tmp/workdir/hettx/new/hettx.Rcheck/00install.out’ for details. ``` ## Installation @@ -3292,457 +2723,309 @@ Run `revdepcheck::cloud_details(, "DepthProc")` for more info ### Devel ``` -* installing *source* package ‘DepthProc’ ... -** package ‘DepthProc’ successfully unpacked and MD5 sums checked +* installing *source* package ‘hettx’ ... +** package ‘hettx’ successfully unpacked and MD5 sums checked ** using staged installation -** libs -using C++ compiler: ‘g++ (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ -using C++11 -g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c Depth.cpp -o Depth.o -g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c LocationEstimators.cpp -o LocationEstimators.o -g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c LocationScaleDepth.cpp -o LocationScaleDepth.o -g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c LocationScaleDepthCPP.cpp -o LocationScaleDepthCPP.o -... -installing to /tmp/workdir/DepthProc/new/DepthProc.Rcheck/00LOCK-DepthProc/00new/DepthProc/libs ** R ** data +*** moving datasets to lazyload DB ** inst ** byte-compile and prepare package for lazy loading -Error: package or namespace load failed for ‘np’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): - there is no package called ‘quantreg’ +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace Execution halted -ERROR: lazy loading failed for package ‘DepthProc’ -* removing ‘/tmp/workdir/DepthProc/new/DepthProc.Rcheck/DepthProc’ +ERROR: lazy loading failed for package ‘hettx’ +* removing ‘/tmp/workdir/hettx/new/hettx.Rcheck/hettx’ ``` ### CRAN ``` -* installing *source* package ‘DepthProc’ ... -** package ‘DepthProc’ successfully unpacked and MD5 sums checked +* installing *source* package ‘hettx’ ... +** package ‘hettx’ successfully unpacked and MD5 sums checked ** using staged installation -** libs -using C++ compiler: ‘g++ (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ -using C++11 -g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c Depth.cpp -o Depth.o -g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c LocationEstimators.cpp -o LocationEstimators.o -g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c LocationScaleDepth.cpp -o LocationScaleDepth.o -g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c LocationScaleDepthCPP.cpp -o LocationScaleDepthCPP.o -... -installing to /tmp/workdir/DepthProc/old/DepthProc.Rcheck/00LOCK-DepthProc/00new/DepthProc/libs ** R ** data +*** moving datasets to lazyload DB ** inst ** byte-compile and prepare package for lazy loading -Error: package or namespace load failed for ‘np’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): - there is no package called ‘quantreg’ +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace Execution halted -ERROR: lazy loading failed for package ‘DepthProc’ -* removing ‘/tmp/workdir/DepthProc/old/DepthProc.Rcheck/DepthProc’ +ERROR: lazy loading failed for package ‘hettx’ +* removing ‘/tmp/workdir/hettx/old/hettx.Rcheck/hettx’ ``` -# DIscBIO +# hIRT
-* Version: 1.2.2 -* GitHub: https://github.com/ocbe-uio/DIscBIO -* Source code: https://github.com/cran/DIscBIO -* Date/Publication: 2023-11-06 10:50:02 UTC -* Number of recursive dependencies: 209 +* Version: 0.3.0 +* GitHub: https://github.com/xiangzhou09/hIRT +* Source code: https://github.com/cran/hIRT +* Date/Publication: 2020-03-26 17:10:02 UTC +* Number of recursive dependencies: 88 -Run `revdepcheck::cloud_details(, "DIscBIO")` for more info +Run `revdepcheck::cloud_details(, "hIRT")` for more info
-## Error before installation - -### Devel +## In both -``` -* using log directory ‘/tmp/workdir/DIscBIO/new/DIscBIO.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘DIscBIO/DESCRIPTION’ ... OK -... -* checking Rd \usage sections ... OK -* checking Rd contents ... OK -* checking for unstated dependencies in examples ... OK -* checking contents of ‘data’ directory ... OK -* checking data for non-ASCII characters ... OK -* checking LazyData ... OK -* checking data for ASCII and uncompressed saves ... OK -* checking examples ... OK -* DONE -Status: 1 NOTE +* checking whether package ‘hIRT’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/hIRT/new/hIRT.Rcheck/00install.out’ for details. + ``` +## Installation +### Devel +``` +* installing *source* package ‘hIRT’ ... +** package ‘hIRT’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** data +*** moving datasets to lazyload DB +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘hIRT’ +* removing ‘/tmp/workdir/hIRT/new/hIRT.Rcheck/hIRT’ ``` ### CRAN ``` -* using log directory ‘/tmp/workdir/DIscBIO/old/DIscBIO.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘DIscBIO/DESCRIPTION’ ... OK -... -* checking Rd \usage sections ... OK -* checking Rd contents ... OK -* checking for unstated dependencies in examples ... OK -* checking contents of ‘data’ directory ... OK -* checking data for non-ASCII characters ... OK -* checking LazyData ... OK -* checking data for ASCII and uncompressed saves ... OK -* checking examples ... OK -* DONE -Status: 1 NOTE - - - +* installing *source* package ‘hIRT’ ... +** package ‘hIRT’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** data +*** moving datasets to lazyload DB +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘hIRT’ +* removing ‘/tmp/workdir/hIRT/old/hIRT.Rcheck/hIRT’ ``` -# diversityForest +# Hmsc
-* Version: 0.4.0 -* GitHub: NA -* Source code: https://github.com/cran/diversityForest -* Date/Publication: 2023-03-08 08:20:02 UTC -* Number of recursive dependencies: 135 +* Version: 3.0-13 +* GitHub: https://github.com/hmsc-r/HMSC +* Source code: https://github.com/cran/Hmsc +* Date/Publication: 2022-08-11 14:10:14 UTC +* Number of recursive dependencies: 76 -Run `revdepcheck::cloud_details(, "diversityForest")` for more info +Run `revdepcheck::cloud_details(, "Hmsc")` for more info
-## Error before installation +## In both + +* checking whether package ‘Hmsc’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/Hmsc/new/Hmsc.Rcheck/00install.out’ for details. + ``` + +## Installation ### Devel ``` -* using log directory ‘/tmp/workdir/diversityForest/new/diversityForest.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘diversityForest/DESCRIPTION’ ... OK -... -* this is package ‘diversityForest’ version ‘0.4.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘rms’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - +* installing *source* package ‘Hmsc’ ... +** package ‘Hmsc’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘Hmsc’ +* removing ‘/tmp/workdir/Hmsc/new/Hmsc.Rcheck/Hmsc’ ``` ### CRAN ``` -* using log directory ‘/tmp/workdir/diversityForest/old/diversityForest.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘diversityForest/DESCRIPTION’ ... OK -... -* this is package ‘diversityForest’ version ‘0.4.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘rms’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - +* installing *source* package ‘Hmsc’ ... +** package ‘Hmsc’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘Hmsc’ +* removing ‘/tmp/workdir/Hmsc/old/Hmsc.Rcheck/Hmsc’ ``` -# DR.SC +# inventorize
-* Version: 3.4 -* GitHub: https://github.com/feiyoung/DR.SC -* Source code: https://github.com/cran/DR.SC -* Date/Publication: 2024-03-19 08:40:02 UTC -* Number of recursive dependencies: 150 +* Version: 1.1.1 +* GitHub: NA +* Source code: https://github.com/cran/inventorize +* Date/Publication: 2022-05-31 22:20:09 UTC +* Number of recursive dependencies: 71 -Run `revdepcheck::cloud_details(, "DR.SC")` for more info +Run `revdepcheck::cloud_details(, "inventorize")` for more info
-## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/DR.SC/new/DR.SC.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘DR.SC/DESCRIPTION’ ... OK -... -* this is package ‘DR.SC’ version ‘3.4’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘Seurat’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/DR.SC/old/DR.SC.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘DR.SC/DESCRIPTION’ ... OK -... -* this is package ‘DR.SC’ version ‘3.4’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘Seurat’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# DynForest - -
- -* Version: 1.1.3 -* GitHub: https://github.com/anthonydevaux/DynForest -* Source code: https://github.com/cran/DynForest -* Date/Publication: 2024-03-22 11:30:05 UTC -* Number of recursive dependencies: 134 - -Run `revdepcheck::cloud_details(, "DynForest")` for more info +## Newly broken -
+* checking whether package ‘inventorize’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/inventorize/new/inventorize.Rcheck/00install.out’ for details. + ``` -## Error before installation +## Installation ### Devel ``` -* using log directory ‘/tmp/workdir/DynForest/new/DynForest.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘DynForest/DESCRIPTION’ ... OK -... -* checking for unstated dependencies in vignettes ... OK -* checking package vignettes in ‘inst/doc’ ... OK -* checking running R code from vignettes ... OK - ‘Introduction.Rmd’ using ‘UTF-8’... OK - ‘factor.Rmd’ using ‘UTF-8’... OK - ‘numeric.Rmd’ using ‘UTF-8’... OK - ‘surv.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: OK - - - +* installing *source* package ‘inventorize’ ... +** package ‘inventorize’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** byte-compile and prepare package for lazy loading +Error in pm[[2]] : subscript out of bounds +Error: unable to load R code in package ‘inventorize’ +Execution halted +ERROR: lazy loading failed for package ‘inventorize’ +* removing ‘/tmp/workdir/inventorize/new/inventorize.Rcheck/inventorize’ ``` ### CRAN ``` -* using log directory ‘/tmp/workdir/DynForest/old/DynForest.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘DynForest/DESCRIPTION’ ... OK -... -* checking for unstated dependencies in vignettes ... OK -* checking package vignettes in ‘inst/doc’ ... OK -* checking running R code from vignettes ... OK - ‘Introduction.Rmd’ using ‘UTF-8’... OK - ‘factor.Rmd’ using ‘UTF-8’... OK - ‘numeric.Rmd’ using ‘UTF-8’... OK - ‘surv.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: OK - - - +* installing *source* package ‘inventorize’ ... +** package ‘inventorize’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** byte-compile and prepare package for lazy loading +Warning in qgamma(service_level, alpha, beta) : NaNs produced +Warning in qgamma(service_level, alpha, beta) : NaNs produced +** help +*** installing help indices +** building package indices +** testing if installed package can be loaded from temporary location +** testing if installed package can be loaded from final location +** testing if installed package keeps a record of temporary installation path +* DONE (inventorize) ``` -# dyngen +# iNZightPlots
-* Version: 1.0.5 -* GitHub: https://github.com/dynverse/dyngen -* Source code: https://github.com/cran/dyngen -* Date/Publication: 2022-10-12 15:22:39 UTC -* Number of recursive dependencies: 209 +* Version: 2.15.3 +* GitHub: https://github.com/iNZightVIT/iNZightPlots +* Source code: https://github.com/cran/iNZightPlots +* Date/Publication: 2023-10-14 05:00:02 UTC +* Number of recursive dependencies: 162 -Run `revdepcheck::cloud_details(, "dyngen")` for more info +Run `revdepcheck::cloud_details(, "iNZightPlots")` for more info
-## Error before installation - -### Devel +## In both -``` -* using log directory ‘/tmp/workdir/dyngen/new/dyngen.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘dyngen/DESCRIPTION’ ... OK -... -* checking tests ... OK - Running ‘testthat.R’ -* checking for unstated dependencies in vignettes ... OK -* checking package vignettes in ‘inst/doc’ ... OK -* checking running R code from vignettes ... NONE - ‘getting_started.html.asis’ using ‘UTF-8’... OK - ‘installation.html.asis’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: 1 NOTE +* checking whether package ‘iNZightPlots’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/iNZightPlots/new/iNZightPlots.Rcheck/00install.out’ for details. + ``` +## Installation +### Devel +``` +* installing *source* package ‘iNZightPlots’ ... +** package ‘iNZightPlots’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘iNZightPlots’ +* removing ‘/tmp/workdir/iNZightPlots/new/iNZightPlots.Rcheck/iNZightPlots’ ``` ### CRAN ``` -* using log directory ‘/tmp/workdir/dyngen/old/dyngen.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘dyngen/DESCRIPTION’ ... OK -... -* checking tests ... OK - Running ‘testthat.R’ -* checking for unstated dependencies in vignettes ... OK -* checking package vignettes in ‘inst/doc’ ... OK -* checking running R code from vignettes ... NONE - ‘getting_started.html.asis’ using ‘UTF-8’... OK - ‘installation.html.asis’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: 1 NOTE - - - +* installing *source* package ‘iNZightPlots’ ... +** package ‘iNZightPlots’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘iNZightPlots’ +* removing ‘/tmp/workdir/iNZightPlots/old/iNZightPlots.Rcheck/iNZightPlots’ ``` -# EcoEnsemble +# iNZightRegression
-* Version: 1.0.5 -* GitHub: NA -* Source code: https://github.com/cran/EcoEnsemble -* Date/Publication: 2023-09-18 11:50:02 UTC -* Number of recursive dependencies: 91 +* Version: 1.3.4 +* GitHub: https://github.com/iNZightVIT/iNZightRegression +* Source code: https://github.com/cran/iNZightRegression +* Date/Publication: 2024-04-05 02:32:59 UTC +* Number of recursive dependencies: 158 -Run `revdepcheck::cloud_details(, "EcoEnsemble")` for more info +Run `revdepcheck::cloud_details(, "iNZightRegression")` for more info
## In both -* checking whether package ‘EcoEnsemble’ can be installed ... ERROR +* checking whether package ‘iNZightRegression’ can be installed ... ERROR ``` Installation failed. - See ‘/tmp/workdir/EcoEnsemble/new/EcoEnsemble.Rcheck/00install.out’ for details. + See ‘/tmp/workdir/iNZightRegression/new/iNZightRegression.Rcheck/00install.out’ for details. ``` ## Installation @@ -3750,77 +3033,59 @@ Run `revdepcheck::cloud_details(, "EcoEnsemble")` for more info ### Devel ``` -* installing *source* package ‘EcoEnsemble’ ... -** package ‘EcoEnsemble’ successfully unpacked and MD5 sums checked +* installing *source* package ‘iNZightRegression’ ... +** package ‘iNZightRegression’ successfully unpacked and MD5 sums checked ** using staged installation -** libs -using C++ compiler: ‘g++ (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ -using C++17 - - -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I"../inst/include" -I"/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src" -DBOOST_DISABLE_ASSERTS -DEIGEN_NO_DEBUG -DBOOST_MATH_OVERFLOW_ERROR_POLICY=errno_on_error -DUSE_STANC3 -D_HAS_AUTO_PTR_ETC=0 -I'/opt/R/4.3.1/lib/R/site-library/BH/include' -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppEigen/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -I'/opt/R/4.3.1/lib/R/site-library/rstan/include' -I'/opt/R/4.3.1/lib/R/site-library/StanHeaders/include' -I/usr/local/include -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -D_REENTRANT -DSTAN_THREADS -fpic -g -O2 -c KF_back.cpp -o KF_back.o -In file included from /opt/R/4.3.1/lib/R/site-library/RcppEigen/include/Eigen/Core:205, -... -/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src/stan/mcmc/hmc/hamiltonians/dense_e_metric.hpp:22:56: required from ‘double stan::mcmc::dense_e_metric::T(stan::mcmc::dense_e_point&) [with Model = model_ensemble_model_hierarchical_namespace::model_ensemble_model_hierarchical; BaseRNG = boost::random::additive_combine_engine, boost::random::linear_congruential_engine >]’ -/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src/stan/mcmc/hmc/hamiltonians/dense_e_metric.hpp:21:10: required from here -/opt/R/4.3.1/lib/R/site-library/RcppEigen/include/Eigen/src/Core/DenseCoeffsBase.h:654:74: warning: ignoring attributes on template argument ‘Eigen::internal::packet_traits::type’ {aka ‘__m128d’} [-Wignored-attributes] - 654 | return internal::first_aligned::alignment),Derived>(m); - | ^~~~~~~~~ -g++: fatal error: Killed signal terminated program cc1plus -compilation terminated. -make: *** [/opt/R/4.3.1/lib/R/etc/Makeconf:198: stanExports_ensemble_model_hierarchical.o] Error 1 -ERROR: compilation failed for package ‘EcoEnsemble’ -* removing ‘/tmp/workdir/EcoEnsemble/new/EcoEnsemble.Rcheck/EcoEnsemble’ +** R +** inst +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘iNZightRegression’ +* removing ‘/tmp/workdir/iNZightRegression/new/iNZightRegression.Rcheck/iNZightRegression’ ``` ### CRAN ``` -* installing *source* package ‘EcoEnsemble’ ... -** package ‘EcoEnsemble’ successfully unpacked and MD5 sums checked +* installing *source* package ‘iNZightRegression’ ... +** package ‘iNZightRegression’ successfully unpacked and MD5 sums checked ** using staged installation -** libs -using C++ compiler: ‘g++ (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ -using C++17 - - -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I"../inst/include" -I"/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src" -DBOOST_DISABLE_ASSERTS -DEIGEN_NO_DEBUG -DBOOST_MATH_OVERFLOW_ERROR_POLICY=errno_on_error -DUSE_STANC3 -D_HAS_AUTO_PTR_ETC=0 -I'/opt/R/4.3.1/lib/R/site-library/BH/include' -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppEigen/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -I'/opt/R/4.3.1/lib/R/site-library/rstan/include' -I'/opt/R/4.3.1/lib/R/site-library/StanHeaders/include' -I/usr/local/include -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -D_REENTRANT -DSTAN_THREADS -fpic -g -O2 -c KF_back.cpp -o KF_back.o -In file included from /opt/R/4.3.1/lib/R/site-library/RcppEigen/include/Eigen/Core:205, -... -/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src/stan/mcmc/hmc/hamiltonians/dense_e_metric.hpp:22:56: required from ‘double stan::mcmc::dense_e_metric::T(stan::mcmc::dense_e_point&) [with Model = model_ensemble_model_hierarchical_namespace::model_ensemble_model_hierarchical; BaseRNG = boost::random::additive_combine_engine, boost::random::linear_congruential_engine >]’ -/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src/stan/mcmc/hmc/hamiltonians/dense_e_metric.hpp:21:10: required from here -/opt/R/4.3.1/lib/R/site-library/RcppEigen/include/Eigen/src/Core/DenseCoeffsBase.h:654:74: warning: ignoring attributes on template argument ‘Eigen::internal::packet_traits::type’ {aka ‘__m128d’} [-Wignored-attributes] - 654 | return internal::first_aligned::alignment),Derived>(m); - | ^~~~~~~~~ -g++: fatal error: Killed signal terminated program cc1plus -compilation terminated. -make: *** [/opt/R/4.3.1/lib/R/etc/Makeconf:198: stanExports_ensemble_model_hierarchical.o] Error 1 -ERROR: compilation failed for package ‘EcoEnsemble’ -* removing ‘/tmp/workdir/EcoEnsemble/old/EcoEnsemble.Rcheck/EcoEnsemble’ +** R +** inst +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘iNZightRegression’ +* removing ‘/tmp/workdir/iNZightRegression/old/iNZightRegression.Rcheck/iNZightRegression’ ``` -# ecolottery +# IRexamples
-* Version: 1.0.0 -* GitHub: https://github.com/frmunoz/ecolottery -* Source code: https://github.com/cran/ecolottery -* Date/Publication: 2017-07-03 11:01:29 UTC -* Number of recursive dependencies: 88 +* Version: 0.0.4 +* GitHub: https://github.com/vinhdizzo/IRexamples +* Source code: https://github.com/cran/IRexamples +* Date/Publication: 2023-10-06 06:40:02 UTC +* Number of recursive dependencies: 177 -Run `revdepcheck::cloud_details(, "ecolottery")` for more info +Run `revdepcheck::cloud_details(, "IRexamples")` for more info
## In both -* checking whether package ‘ecolottery’ can be installed ... ERROR +* checking whether package ‘IRexamples’ can be installed ... ERROR ``` Installation failed. - See ‘/tmp/workdir/ecolottery/new/ecolottery.Rcheck/00install.out’ for details. + See ‘/tmp/workdir/IRexamples/new/IRexamples.Rcheck/00install.out’ for details. ``` ## Installation @@ -3828,59 +3093,73 @@ Run `revdepcheck::cloud_details(, "ecolottery")` for more info ### Devel ``` -* installing *source* package ‘ecolottery’ ... -** package ‘ecolottery’ successfully unpacked and MD5 sums checked +* installing *source* package ‘IRexamples’ ... +** package ‘IRexamples’ 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 +Warning in check_dep_version() : + ABI version mismatch: +lme4 was built with Matrix ABI version 1 +Current Matrix ABI version is 0 +Please re-install lme4 from source or restore original ‘Matrix’ package Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - there is no package called ‘quantreg’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace Execution halted -ERROR: lazy loading failed for package ‘ecolottery’ -* removing ‘/tmp/workdir/ecolottery/new/ecolottery.Rcheck/ecolottery’ +ERROR: lazy loading failed for package ‘IRexamples’ +* removing ‘/tmp/workdir/IRexamples/new/IRexamples.Rcheck/IRexamples’ ``` ### CRAN ``` -* installing *source* package ‘ecolottery’ ... -** package ‘ecolottery’ successfully unpacked and MD5 sums checked +* installing *source* package ‘IRexamples’ ... +** package ‘IRexamples’ 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 +Warning in check_dep_version() : + ABI version mismatch: +lme4 was built with Matrix ABI version 1 +Current Matrix ABI version is 0 +Please re-install lme4 from source or restore original ‘Matrix’ package Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - there is no package called ‘quantreg’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace Execution halted -ERROR: lazy loading failed for package ‘ecolottery’ -* removing ‘/tmp/workdir/ecolottery/old/ecolottery.Rcheck/ecolottery’ +ERROR: lazy loading failed for package ‘IRexamples’ +* removing ‘/tmp/workdir/IRexamples/old/IRexamples.Rcheck/IRexamples’ ``` -# EpiEstim +# jmBIG
-* Version: 2.2-4 -* GitHub: https://github.com/mrc-ide/EpiEstim -* Source code: https://github.com/cran/EpiEstim -* Date/Publication: 2021-01-07 16:20:10 UTC -* Number of recursive dependencies: 91 +* Version: 0.1.2 +* GitHub: NA +* Source code: https://github.com/cran/jmBIG +* Date/Publication: 2024-03-20 23:40:02 UTC +* Number of recursive dependencies: 184 -Run `revdepcheck::cloud_details(, "EpiEstim")` for more info +Run `revdepcheck::cloud_details(, "jmBIG")` for more info
## In both -* checking whether package ‘EpiEstim’ can be installed ... ERROR +* checking whether package ‘jmBIG’ can be installed ... ERROR ``` Installation failed. - See ‘/tmp/workdir/EpiEstim/new/EpiEstim.Rcheck/00install.out’ for details. + See ‘/tmp/workdir/jmBIG/new/jmBIG.Rcheck/00install.out’ for details. ``` ## Installation @@ -3888,137 +3167,139 @@ Run `revdepcheck::cloud_details(, "EpiEstim")` for more info ### Devel ``` -* installing *source* package ‘EpiEstim’ ... -** package ‘EpiEstim’ successfully unpacked and MD5 sums checked +* installing *source* package ‘jmBIG’ ... +** package ‘jmBIG’ successfully unpacked and MD5 sums checked ** using staged installation ** R ** data -** inst +*** moving datasets to lazyload DB ** byte-compile and prepare package for lazy loading -Error in loadNamespace(i, c(lib.loc, .libPaths()), versionCheck = vI[[i]]) : - there is no package called ‘quantreg’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace Execution halted -ERROR: lazy loading failed for package ‘EpiEstim’ -* removing ‘/tmp/workdir/EpiEstim/new/EpiEstim.Rcheck/EpiEstim’ +ERROR: lazy loading failed for package ‘jmBIG’ +* removing ‘/tmp/workdir/jmBIG/new/jmBIG.Rcheck/jmBIG’ ``` ### CRAN ``` -* installing *source* package ‘EpiEstim’ ... -** package ‘EpiEstim’ successfully unpacked and MD5 sums checked +* installing *source* package ‘jmBIG’ ... +** package ‘jmBIG’ successfully unpacked and MD5 sums checked ** using staged installation ** R ** data -** inst +*** moving datasets to lazyload DB ** byte-compile and prepare package for lazy loading -Error in loadNamespace(i, c(lib.loc, .libPaths()), versionCheck = vI[[i]]) : - there is no package called ‘quantreg’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace Execution halted -ERROR: lazy loading failed for package ‘EpiEstim’ -* removing ‘/tmp/workdir/EpiEstim/old/EpiEstim.Rcheck/EpiEstim’ +ERROR: lazy loading failed for package ‘jmBIG’ +* removing ‘/tmp/workdir/jmBIG/old/jmBIG.Rcheck/jmBIG’ ``` -# evalITR +# joineRML
-* Version: 1.0.0 -* GitHub: https://github.com/MichaelLLi/evalITR -* Source code: https://github.com/cran/evalITR -* Date/Publication: 2023-08-25 23:10:06 UTC -* Number of recursive dependencies: 168 +* Version: 0.4.6 +* GitHub: https://github.com/graemeleehickey/joineRML +* Source code: https://github.com/cran/joineRML +* Date/Publication: 2023-01-20 04:50:02 UTC +* Number of recursive dependencies: 91 -Run `revdepcheck::cloud_details(, "evalITR")` for more info +Run `revdepcheck::cloud_details(, "joineRML")` for more info
-## Error before installation +## In both + +* checking whether package ‘joineRML’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/joineRML/new/joineRML.Rcheck/00install.out’ for details. + ``` + +## Installation ### Devel ``` -* using log directory ‘/tmp/workdir/evalITR/new/evalITR.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘evalITR/DESCRIPTION’ ... OK +* installing *source* package ‘joineRML’ ... +** package ‘joineRML’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C compiler: ‘gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ +using C++ compiler: ‘g++ (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ +using C++11 +g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c expW.cpp -o expW.o +g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c gammaUpdate.cpp -o gammaUpdate.o ... -* this is package ‘evalITR’ version ‘1.0.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘rqPen’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - +** 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘joineRML’ +* removing ‘/tmp/workdir/joineRML/new/joineRML.Rcheck/joineRML’ ``` ### CRAN ``` -* using log directory ‘/tmp/workdir/evalITR/old/evalITR.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘evalITR/DESCRIPTION’ ... OK +* installing *source* package ‘joineRML’ ... +** package ‘joineRML’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C compiler: ‘gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ +using C++ compiler: ‘g++ (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ +using C++11 +g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c expW.cpp -o expW.o +g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c gammaUpdate.cpp -o gammaUpdate.o ... -* this is package ‘evalITR’ version ‘1.0.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘rqPen’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - +** 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘joineRML’ +* removing ‘/tmp/workdir/joineRML/old/joineRML.Rcheck/joineRML’ ``` -# evolqg +# JWileymisc
-* Version: 0.3-4 -* GitHub: https://github.com/lem-usp/evolqg -* Source code: https://github.com/cran/evolqg -* Date/Publication: 2023-12-05 15:20:12 UTC -* Number of recursive dependencies: 111 +* Version: 1.4.1 +* GitHub: https://github.com/JWiley/JWileymisc +* Source code: https://github.com/cran/JWileymisc +* Date/Publication: 2023-10-05 04:50:02 UTC +* Number of recursive dependencies: 167 -Run `revdepcheck::cloud_details(, "evolqg")` for more info +Run `revdepcheck::cloud_details(, "JWileymisc")` for more info
## In both -* checking whether package ‘evolqg’ can be installed ... ERROR +* checking whether package ‘JWileymisc’ can be installed ... ERROR ``` Installation failed. - See ‘/tmp/workdir/evolqg/new/evolqg.Rcheck/00install.out’ for details. + See ‘/tmp/workdir/JWileymisc/new/JWileymisc.Rcheck/00install.out’ for details. ``` ## Installation @@ -4026,377 +3307,349 @@ Run `revdepcheck::cloud_details(, "evolqg")` for more info ### Devel ``` -* installing *source* package ‘evolqg’ ... -** package ‘evolqg’ successfully unpacked and MD5 sums checked +* installing *source* package ‘JWileymisc’ ... +** package ‘JWileymisc’ successfully unpacked and MD5 sums checked ** using staged installation -** libs -using C++ compiler: ‘g++ (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c fast_RS.cpp -o fast_RS.o -g++ -std=gnu++17 -shared -L/opt/R/4.3.1/lib/R/lib -L/usr/local/lib -o evolqg.so RcppExports.o fast_RS.o -llapack -lblas -lgfortran -lm -lquadmath -L/opt/R/4.3.1/lib/R/lib -lR -installing to /tmp/workdir/evolqg/new/evolqg.Rcheck/00LOCK-evolqg/00new/evolqg/libs ** R ** data +*** moving datasets to lazyload DB ** 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 ‘quantreg’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Warning in check_dep_version() : + ABI version mismatch: +lme4 was built with Matrix ABI version 1 +Current Matrix ABI version is 0 +Please re-install lme4 from source or restore original ‘Matrix’ package +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace Execution halted -ERROR: lazy loading failed for package ‘evolqg’ -* removing ‘/tmp/workdir/evolqg/new/evolqg.Rcheck/evolqg’ +ERROR: lazy loading failed for package ‘JWileymisc’ +* removing ‘/tmp/workdir/JWileymisc/new/JWileymisc.Rcheck/JWileymisc’ ``` ### CRAN ``` -* installing *source* package ‘evolqg’ ... -** package ‘evolqg’ successfully unpacked and MD5 sums checked +* installing *source* package ‘JWileymisc’ ... +** package ‘JWileymisc’ successfully unpacked and MD5 sums checked ** using staged installation -** libs -using C++ compiler: ‘g++ (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c fast_RS.cpp -o fast_RS.o -g++ -std=gnu++17 -shared -L/opt/R/4.3.1/lib/R/lib -L/usr/local/lib -o evolqg.so RcppExports.o fast_RS.o -llapack -lblas -lgfortran -lm -lquadmath -L/opt/R/4.3.1/lib/R/lib -lR -installing to /tmp/workdir/evolqg/old/evolqg.Rcheck/00LOCK-evolqg/00new/evolqg/libs ** R ** data +*** moving datasets to lazyload DB ** 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 ‘quantreg’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart -Execution halted -ERROR: lazy loading failed for package ‘evolqg’ -* removing ‘/tmp/workdir/evolqg/old/evolqg.Rcheck/evolqg’ +Warning in check_dep_version() : + ABI version mismatch: +lme4 was built with Matrix ABI version 1 +Current Matrix ABI version is 0 +Please re-install lme4 from source or restore original ‘Matrix’ package +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘JWileymisc’ +* removing ‘/tmp/workdir/JWileymisc/old/JWileymisc.Rcheck/JWileymisc’ ``` -# explainer +# kmc
-* Version: 1.0.1 -* GitHub: https://github.com/PERSIMUNE/explainer -* Source code: https://github.com/cran/explainer -* Date/Publication: 2024-04-18 09:00:02 UTC -* Number of recursive dependencies: 193 +* Version: 0.4-2 +* GitHub: https://github.com/yfyang86/kmc +* Source code: https://github.com/cran/kmc +* Date/Publication: 2022-11-22 08:30:02 UTC +* Number of recursive dependencies: 61 -Run `revdepcheck::cloud_details(, "explainer")` for more info +Run `revdepcheck::cloud_details(, "kmc")` for more info
-## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/explainer/new/explainer.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘explainer/DESCRIPTION’ ... OK -... -* this is package ‘explainer’ version ‘1.0.1’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘ggpmisc’ +## In both -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR +* checking whether package ‘kmc’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/kmc/new/kmc.Rcheck/00install.out’ for details. + ``` +## Installation +### Devel +``` +* installing *source* package ‘kmc’ ... +** package ‘kmc’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C compiler: ‘gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ +using C++ compiler: ‘g++ (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c RcppExport.cpp -o RcppExport.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c kmc.cpp -o kmc.o +gcc -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c kmc_init.c -o kmc_init.o +gcc -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c surv2.c -o surv2.o +g++ -std=gnu++17 -shared -L/opt/R/4.3.1/lib/R/lib -L/usr/local/lib -o kmc.so RcppExport.o kmc.o kmc_init.o surv2.o -L/opt/R/4.3.1/lib/R/lib -lR +installing to /tmp/workdir/kmc/new/kmc.Rcheck/00LOCK-kmc/00new/kmc/libs +** R +** byte-compile and prepare package for lazy loading +Error: package or namespace load failed for ‘emplik’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Execution halted +ERROR: lazy loading failed for package ‘kmc’ +* removing ‘/tmp/workdir/kmc/new/kmc.Rcheck/kmc’ ``` ### CRAN ``` -* using log directory ‘/tmp/workdir/explainer/old/explainer.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘explainer/DESCRIPTION’ ... OK -... -* this is package ‘explainer’ version ‘1.0.1’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘ggpmisc’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - +* installing *source* package ‘kmc’ ... +** package ‘kmc’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C compiler: ‘gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ +using C++ compiler: ‘g++ (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c RcppExport.cpp -o RcppExport.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c kmc.cpp -o kmc.o +gcc -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c kmc_init.c -o kmc_init.o +gcc -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c surv2.c -o surv2.o +g++ -std=gnu++17 -shared -L/opt/R/4.3.1/lib/R/lib -L/usr/local/lib -o kmc.so RcppExport.o kmc.o kmc_init.o surv2.o -L/opt/R/4.3.1/lib/R/lib -lR +installing to /tmp/workdir/kmc/old/kmc.Rcheck/00LOCK-kmc/00new/kmc/libs +** R +** byte-compile and prepare package for lazy loading +Error: package or namespace load failed for ‘emplik’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Execution halted +ERROR: lazy loading failed for package ‘kmc’ +* removing ‘/tmp/workdir/kmc/old/kmc.Rcheck/kmc’ ``` -# flexrsurv +# L2E
-* Version: 2.0.18 +* Version: 2.0 * GitHub: NA -* Source code: https://github.com/cran/flexrsurv -* Date/Publication: 2024-02-09 16:10:02 UTC -* Number of recursive dependencies: 129 +* Source code: https://github.com/cran/L2E +* Date/Publication: 2022-09-08 21:13:00 UTC +* Number of recursive dependencies: 65 -Run `revdepcheck::cloud_details(, "flexrsurv")` for more info +Run `revdepcheck::cloud_details(, "L2E")` for more info
-## Error before installation - -### Devel +## In both -``` -* using log directory ‘/tmp/workdir/flexrsurv/new/flexrsurv.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘flexrsurv/DESCRIPTION’ ... OK -... -* checking for missing documentation entries ... OK -* checking for code/documentation mismatches ... OK -* checking Rd \usage sections ... OK -* checking Rd contents ... OK -* checking for unstated dependencies in examples ... OK -* checking line endings in C/C++/Fortran sources/headers ... OK -* checking compiled code ... OK -* checking examples ... OK -* DONE -Status: OK +* checking whether package ‘L2E’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/L2E/new/L2E.Rcheck/00install.out’ for details. + ``` +## Installation +### Devel +``` +* installing *source* package ‘L2E’ ... +** package ‘L2E’ 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: package or namespace load failed for ‘osqp’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): + namespace ‘Matrix’ 1.5-4.1 is being loaded, but >= 1.6.1 is required +Execution halted +ERROR: lazy loading failed for package ‘L2E’ +* removing ‘/tmp/workdir/L2E/new/L2E.Rcheck/L2E’ ``` ### CRAN ``` -* using log directory ‘/tmp/workdir/flexrsurv/old/flexrsurv.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘flexrsurv/DESCRIPTION’ ... OK -... -* checking for missing documentation entries ... OK -* checking for code/documentation mismatches ... OK -* checking Rd \usage sections ... OK -* checking Rd contents ... OK -* checking for unstated dependencies in examples ... OK -* checking line endings in C/C++/Fortran sources/headers ... OK -* checking compiled code ... OK -* checking examples ... OK -* DONE -Status: OK - - - +* installing *source* package ‘L2E’ ... +** package ‘L2E’ 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: package or namespace load failed for ‘osqp’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): + namespace ‘Matrix’ 1.5-4.1 is being loaded, but >= 1.6.1 is required +Execution halted +ERROR: lazy loading failed for package ‘L2E’ +* removing ‘/tmp/workdir/L2E/old/L2E.Rcheck/L2E’ ``` -# forestmangr +# llbayesireg
-* Version: 0.9.6 -* GitHub: https://github.com/sollano/forestmangr -* Source code: https://github.com/cran/forestmangr -* Date/Publication: 2023-11-23 18:30:02 UTC -* Number of recursive dependencies: 126 +* Version: 1.0.0 +* GitHub: NA +* Source code: https://github.com/cran/llbayesireg +* Date/Publication: 2019-04-04 16:20:03 UTC +* Number of recursive dependencies: 60 -Run `revdepcheck::cloud_details(, "forestmangr")` for more info +Run `revdepcheck::cloud_details(, "llbayesireg")` for more info
-## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/forestmangr/new/forestmangr.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘forestmangr/DESCRIPTION’ ... OK -... -* this is package ‘forestmangr’ version ‘0.9.6’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘ggpmisc’ +## In both -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR +* checking whether package ‘llbayesireg’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/llbayesireg/new/llbayesireg.Rcheck/00install.out’ for details. + ``` +## Installation +### Devel +``` +* installing *source* package ‘llbayesireg’ ... +** package ‘llbayesireg’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** data +*** moving datasets to lazyload DB +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘llbayesireg’ +* removing ‘/tmp/workdir/llbayesireg/new/llbayesireg.Rcheck/llbayesireg’ ``` ### CRAN ``` -* using log directory ‘/tmp/workdir/forestmangr/old/forestmangr.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘forestmangr/DESCRIPTION’ ... OK -... -* this is package ‘forestmangr’ version ‘0.9.6’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘ggpmisc’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - +* installing *source* package ‘llbayesireg’ ... +** package ‘llbayesireg’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** data +*** moving datasets to lazyload DB +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘llbayesireg’ +* removing ‘/tmp/workdir/llbayesireg/old/llbayesireg.Rcheck/llbayesireg’ ``` -# gap +# LorenzRegression
-* Version: 1.5-3 -* GitHub: https://github.com/jinghuazhao/R -* Source code: https://github.com/cran/gap -* Date/Publication: 2023-08-26 14:10:07 UTC -* Number of recursive dependencies: 177 - -Run `revdepcheck::cloud_details(, "gap")` for more info +* Version: 1.0.0 +* GitHub: NA +* Source code: https://github.com/cran/LorenzRegression +* Date/Publication: 2023-02-28 17:32:34 UTC +* Number of recursive dependencies: 63 + +Run `revdepcheck::cloud_details(, "LorenzRegression")` for more info
-## Error before installation +## In both + +* checking whether package ‘LorenzRegression’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/LorenzRegression/new/LorenzRegression.Rcheck/00install.out’ for details. + ``` + +## Installation ### Devel ``` -* using log directory ‘/tmp/workdir/gap/new/gap.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘gap/DESCRIPTION’ ... OK +* installing *source* package ‘LorenzRegression’ ... +** package ‘LorenzRegression’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C++ compiler: ‘g++ (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c GA_fitness.cpp -o GA_fitness.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c GA_meanrank.cpp -o GA_meanrank.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c PLR_derivative.cpp -o PLR_derivative.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c PLR_loss.cpp -o PLR_loss.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o ... ---- failed re-building ‘jss.Rnw’ - -SUMMARY: processing the following file failed: - ‘jss.Rnw’ - -Error: Vignette re-building failed. +** 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace Execution halted - -* DONE -Status: 4 NOTEs - - - +ERROR: lazy loading failed for package ‘LorenzRegression’ +* removing ‘/tmp/workdir/LorenzRegression/new/LorenzRegression.Rcheck/LorenzRegression’ ``` ### CRAN ``` -* using log directory ‘/tmp/workdir/gap/old/gap.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘gap/DESCRIPTION’ ... OK +* installing *source* package ‘LorenzRegression’ ... +** package ‘LorenzRegression’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C++ compiler: ‘g++ (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c GA_fitness.cpp -o GA_fitness.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c GA_meanrank.cpp -o GA_meanrank.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c PLR_derivative.cpp -o PLR_derivative.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c PLR_loss.cpp -o PLR_loss.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o ... ---- failed re-building ‘jss.Rnw’ - -SUMMARY: processing the following file failed: - ‘jss.Rnw’ - -Error: Vignette re-building failed. +** 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace Execution halted - -* DONE -Status: 4 NOTEs - - - +ERROR: lazy loading failed for package ‘LorenzRegression’ +* removing ‘/tmp/workdir/LorenzRegression/old/LorenzRegression.Rcheck/LorenzRegression’ ``` -# GeomComb +# lsirm12pl
-* Version: 1.0 -* GitHub: https://github.com/ceweiss/GeomComb -* Source code: https://github.com/cran/GeomComb -* Date/Publication: 2016-11-27 16:02:26 -* Number of recursive dependencies: 74 +* Version: 1.3.1 +* GitHub: NA +* Source code: https://github.com/cran/lsirm12pl +* Date/Publication: 2023-06-22 14:12:35 UTC +* Number of recursive dependencies: 124 -Run `revdepcheck::cloud_details(, "GeomComb")` for more info +Run `revdepcheck::cloud_details(, "lsirm12pl")` for more info
## In both -* checking whether package ‘GeomComb’ can be installed ... ERROR +* checking whether package ‘lsirm12pl’ can be installed ... ERROR ``` Installation failed. - See ‘/tmp/workdir/GeomComb/new/GeomComb.Rcheck/00install.out’ for details. + See ‘/tmp/workdir/lsirm12pl/new/lsirm12pl.Rcheck/00install.out’ for details. ``` ## Installation @@ -4404,889 +3657,797 @@ Run `revdepcheck::cloud_details(, "GeomComb")` for more info ### Devel ``` -* installing *source* package ‘GeomComb’ ... -** package ‘GeomComb’ successfully unpacked and MD5 sums checked +* installing *source* package ‘lsirm12pl’ ... +** package ‘lsirm12pl’ successfully unpacked and MD5 sums checked ** using staged installation +** libs +using C++ compiler: ‘g++ (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c log_likelihood.cpp -o log_likelihood.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c lsirm1pl.cpp -o lsirm1pl.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c lsirm1pl_fixed_gamma.cpp -o lsirm1pl_fixed_gamma.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c lsirm1pl_fixed_gamma_mar.cpp -o lsirm1pl_fixed_gamma_mar.o +... ** R +** data +*** moving datasets to lazyload DB ** byte-compile and prepare package for lazy loading -Error in loadNamespace(i, c(lib.loc, .libPaths()), versionCheck = vI[[i]]) : - there is no package called ‘quantreg’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace Execution halted -ERROR: lazy loading failed for package ‘GeomComb’ -* removing ‘/tmp/workdir/GeomComb/new/GeomComb.Rcheck/GeomComb’ +ERROR: lazy loading failed for package ‘lsirm12pl’ +* removing ‘/tmp/workdir/lsirm12pl/new/lsirm12pl.Rcheck/lsirm12pl’ ``` ### CRAN ``` -* installing *source* package ‘GeomComb’ ... -** package ‘GeomComb’ successfully unpacked and MD5 sums checked +* installing *source* package ‘lsirm12pl’ ... +** package ‘lsirm12pl’ successfully unpacked and MD5 sums checked ** using staged installation +** libs +using C++ compiler: ‘g++ (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c log_likelihood.cpp -o log_likelihood.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c lsirm1pl.cpp -o lsirm1pl.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c lsirm1pl_fixed_gamma.cpp -o lsirm1pl_fixed_gamma.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c lsirm1pl_fixed_gamma_mar.cpp -o lsirm1pl_fixed_gamma_mar.o +... ** R +** data +*** moving datasets to lazyload DB ** byte-compile and prepare package for lazy loading -Error in loadNamespace(i, c(lib.loc, .libPaths()), versionCheck = vI[[i]]) : - there is no package called ‘quantreg’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace Execution halted -ERROR: lazy loading failed for package ‘GeomComb’ -* removing ‘/tmp/workdir/GeomComb/old/GeomComb.Rcheck/GeomComb’ +ERROR: lazy loading failed for package ‘lsirm12pl’ +* removing ‘/tmp/workdir/lsirm12pl/old/lsirm12pl.Rcheck/lsirm12pl’ ``` -# ggeffects +# mbsts
-* Version: 1.6.0 -* GitHub: https://github.com/strengejacke/ggeffects -* Source code: https://github.com/cran/ggeffects -* Date/Publication: 2024-05-18 20:00:03 UTC -* Number of recursive dependencies: 265 +* Version: 3.0 +* GitHub: NA +* Source code: https://github.com/cran/mbsts +* Date/Publication: 2023-01-07 01:10:02 UTC +* Number of recursive dependencies: 82 -Run `revdepcheck::cloud_details(, "ggeffects")` for more info +Run `revdepcheck::cloud_details(, "mbsts")` for more info
-## Error before installation - -### Devel +## In both -``` -* using log directory ‘/tmp/workdir/ggeffects/new/ggeffects.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘ggeffects/DESCRIPTION’ ... OK -... -* checking for unstated dependencies in ‘tests’ ... OK -* checking tests ... OK - Running ‘testthat.R’ -* checking for unstated dependencies in vignettes ... OK -* checking package vignettes in ‘inst/doc’ ... OK -* checking running R code from vignettes ... OK - ‘content.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: 1 NOTE +* checking whether package ‘mbsts’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/mbsts/new/mbsts.Rcheck/00install.out’ for details. + ``` +## Installation +### Devel +``` +* installing *source* package ‘mbsts’ ... +** package ‘mbsts’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘mbsts’ +* removing ‘/tmp/workdir/mbsts/new/mbsts.Rcheck/mbsts’ ``` ### CRAN ``` -* using log directory ‘/tmp/workdir/ggeffects/old/ggeffects.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘ggeffects/DESCRIPTION’ ... OK -... -* checking for unstated dependencies in ‘tests’ ... OK -* checking tests ... OK - Running ‘testthat.R’ -* checking for unstated dependencies in vignettes ... OK -* checking package vignettes in ‘inst/doc’ ... OK -* checking running R code from vignettes ... OK - ‘content.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: 1 NOTE - - - +* installing *source* package ‘mbsts’ ... +** package ‘mbsts’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘mbsts’ +* removing ‘/tmp/workdir/mbsts/old/mbsts.Rcheck/mbsts’ ``` -# ggquickeda +# MendelianRandomization
-* Version: 0.3.1 -* GitHub: https://github.com/smouksassi/ggquickeda -* Source code: https://github.com/cran/ggquickeda -* Date/Publication: 2024-01-15 10:20:02 UTC -* Number of recursive dependencies: 187 +* Version: 0.10.0 +* GitHub: NA +* Source code: https://github.com/cran/MendelianRandomization +* Date/Publication: 2024-04-12 10:10:02 UTC +* Number of recursive dependencies: 88 -Run `revdepcheck::cloud_details(, "ggquickeda")` for more info +Run `revdepcheck::cloud_details(, "MendelianRandomization")` for more info
-## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/ggquickeda/new/ggquickeda.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘ggquickeda/DESCRIPTION’ ... OK -... -* this is package ‘ggquickeda’ version ‘0.3.1’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Packages required but not available: 'ggpmisc', 'quantreg', 'rms' +## In both -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR +* checking whether package ‘MendelianRandomization’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/MendelianRandomization/new/MendelianRandomization.Rcheck/00install.out’ for details. + ``` +## Installation +### Devel +``` +* installing *source* package ‘MendelianRandomization’ ... +** package ‘MendelianRandomization’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C++ compiler: ‘g++ (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c mvmrcML.cpp -o mvmrcML.o +g++ -std=gnu++17 -shared -L/opt/R/4.3.1/lib/R/lib -L/usr/local/lib -o MendelianRandomization.so RcppExports.o mvmrcML.o -fopenmp -llapack -lblas -lgfortran -lm -lquadmath -L/opt/R/4.3.1/lib/R/lib -lR +installing to /tmp/workdir/MendelianRandomization/new/MendelianRandomization.Rcheck/00LOCK-MendelianRandomization/00new/MendelianRandomization/libs +** R +** inst +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘MendelianRandomization’ +* removing ‘/tmp/workdir/MendelianRandomization/new/MendelianRandomization.Rcheck/MendelianRandomization’ ``` ### CRAN ``` -* using log directory ‘/tmp/workdir/ggquickeda/old/ggquickeda.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘ggquickeda/DESCRIPTION’ ... OK -... -* this is package ‘ggquickeda’ version ‘0.3.1’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Packages required but not available: 'ggpmisc', 'quantreg', 'rms' - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - +* installing *source* package ‘MendelianRandomization’ ... +** package ‘MendelianRandomization’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C++ compiler: ‘g++ (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c mvmrcML.cpp -o mvmrcML.o +g++ -std=gnu++17 -shared -L/opt/R/4.3.1/lib/R/lib -L/usr/local/lib -o MendelianRandomization.so RcppExports.o mvmrcML.o -fopenmp -llapack -lblas -lgfortran -lm -lquadmath -L/opt/R/4.3.1/lib/R/lib -lR +installing to /tmp/workdir/MendelianRandomization/old/MendelianRandomization.Rcheck/00LOCK-MendelianRandomization/00new/MendelianRandomization/libs +** R +** inst +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘MendelianRandomization’ +* removing ‘/tmp/workdir/MendelianRandomization/old/MendelianRandomization.Rcheck/MendelianRandomization’ ``` -# ggrcs +# MetabolicSurv
-* Version: 0.3.8 -* GitHub: NA -* Source code: https://github.com/cran/ggrcs -* Date/Publication: 2024-01-30 03:20:08 UTC -* Number of recursive dependencies: 78 +* Version: 1.1.2 +* GitHub: https://github.com/OlajumokeEvangelina/MetabolicSurv +* Source code: https://github.com/cran/MetabolicSurv +* Date/Publication: 2021-06-11 08:30:02 UTC +* Number of recursive dependencies: 131 -Run `revdepcheck::cloud_details(, "ggrcs")` for more info +Run `revdepcheck::cloud_details(, "MetabolicSurv")` for more info
-## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/ggrcs/new/ggrcs.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘ggrcs/DESCRIPTION’ ... OK -... -* this is package ‘ggrcs’ version ‘0.3.8’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘rms’ +## In both -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR +* checking whether package ‘MetabolicSurv’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/MetabolicSurv/new/MetabolicSurv.Rcheck/00install.out’ for details. + ``` +## Installation +### Devel +``` +* installing *source* package ‘MetabolicSurv’ ... +** package ‘MetabolicSurv’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘MetabolicSurv’ +* removing ‘/tmp/workdir/MetabolicSurv/new/MetabolicSurv.Rcheck/MetabolicSurv’ ``` ### CRAN ``` -* using log directory ‘/tmp/workdir/ggrcs/old/ggrcs.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘ggrcs/DESCRIPTION’ ... OK -... -* this is package ‘ggrcs’ version ‘0.3.8’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘rms’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - +* installing *source* package ‘MetabolicSurv’ ... +** package ‘MetabolicSurv’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘MetabolicSurv’ +* removing ‘/tmp/workdir/MetabolicSurv/old/MetabolicSurv.Rcheck/MetabolicSurv’ ``` -# ggrisk +# miWQS
-* Version: 1.3 -* GitHub: https://github.com/yikeshu0611/ggrisk -* Source code: https://github.com/cran/ggrisk -* Date/Publication: 2021-08-09 07:40:06 UTC -* Number of recursive dependencies: 115 +* Version: 0.4.4 +* GitHub: https://github.com/phargarten2/miWQS +* Source code: https://github.com/cran/miWQS +* Date/Publication: 2021-04-02 21:50:02 UTC +* Number of recursive dependencies: 151 -Run `revdepcheck::cloud_details(, "ggrisk")` for more info +Run `revdepcheck::cloud_details(, "miWQS")` for more info
-## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/ggrisk/new/ggrisk.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘ggrisk/DESCRIPTION’ ... OK -... -* this is package ‘ggrisk’ version ‘1.3’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘rms’ +## In both -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR +* checking whether package ‘miWQS’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/miWQS/new/miWQS.Rcheck/00install.out’ for details. + ``` +## Installation +### Devel +``` +* installing *source* package ‘miWQS’ ... +** package ‘miWQS’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘miWQS’ +* removing ‘/tmp/workdir/miWQS/new/miWQS.Rcheck/miWQS’ ``` ### CRAN ``` -* using log directory ‘/tmp/workdir/ggrisk/old/ggrisk.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘ggrisk/DESCRIPTION’ ... OK -... -* this is package ‘ggrisk’ version ‘1.3’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘rms’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - +* installing *source* package ‘miWQS’ ... +** package ‘miWQS’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘miWQS’ +* removing ‘/tmp/workdir/miWQS/old/miWQS.Rcheck/miWQS’ ``` -# ggsector +# MRZero
-* Version: 1.6.6 -* GitHub: https://github.com/yanpd01/ggsector -* Source code: https://github.com/cran/ggsector -* Date/Publication: 2022-12-05 15:20:02 UTC -* Number of recursive dependencies: 159 +* Version: 0.2.0 +* GitHub: NA +* Source code: https://github.com/cran/MRZero +* Date/Publication: 2024-04-14 09:30:03 UTC +* Number of recursive dependencies: 82 -Run `revdepcheck::cloud_details(, "ggsector")` for more info +Run `revdepcheck::cloud_details(, "MRZero")` for more info
-## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/ggsector/new/ggsector.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘ggsector/DESCRIPTION’ ... OK -... -* this is package ‘ggsector’ version ‘1.6.6’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘Seurat’ +## In both -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR +* checking whether package ‘MRZero’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/MRZero/new/MRZero.Rcheck/00install.out’ for details. + ``` +## Installation +### Devel +``` +* installing *source* package ‘MRZero’ ... +** package ‘MRZero’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘MRZero’ +* removing ‘/tmp/workdir/MRZero/new/MRZero.Rcheck/MRZero’ ``` ### CRAN ``` -* using log directory ‘/tmp/workdir/ggsector/old/ggsector.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘ggsector/DESCRIPTION’ ... OK -... -* this is package ‘ggsector’ version ‘1.6.6’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘Seurat’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - +* installing *source* package ‘MRZero’ ... +** package ‘MRZero’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘MRZero’ +* removing ‘/tmp/workdir/MRZero/old/MRZero.Rcheck/MRZero’ ``` -# grandR +# Multiaovbay
-* Version: 0.2.5 -* GitHub: https://github.com/erhard-lab/grandR -* Source code: https://github.com/cran/grandR -* Date/Publication: 2024-02-15 15:30:02 UTC -* Number of recursive dependencies: 265 +* Version: 0.1.0 +* GitHub: NA +* Source code: https://github.com/cran/Multiaovbay +* Date/Publication: 2023-03-17 17:20:02 UTC +* Number of recursive dependencies: 153 -Run `revdepcheck::cloud_details(, "grandR")` for more info +Run `revdepcheck::cloud_details(, "Multiaovbay")` for more info
-## Error before installation - -### Devel +## In both -``` -* using log directory ‘/tmp/workdir/grandR/new/grandR.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘grandR/DESCRIPTION’ ... OK -... -* checking installed files from ‘inst/doc’ ... OK -* checking files in ‘vignettes’ ... OK -* checking examples ... OK -* checking for unstated dependencies in vignettes ... OK -* checking package vignettes in ‘inst/doc’ ... OK -* checking running R code from vignettes ... OK - ‘getting-started.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: 1 NOTE +* checking whether package ‘Multiaovbay’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/Multiaovbay/new/Multiaovbay.Rcheck/00install.out’ for details. + ``` +## Installation +### Devel +``` +* installing *source* package ‘Multiaovbay’ ... +** package ‘Multiaovbay’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is being loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘Multiaovbay’ +* removing ‘/tmp/workdir/Multiaovbay/new/Multiaovbay.Rcheck/Multiaovbay’ ``` ### CRAN ``` -* using log directory ‘/tmp/workdir/grandR/old/grandR.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘grandR/DESCRIPTION’ ... OK -... -* checking installed files from ‘inst/doc’ ... OK -* checking files in ‘vignettes’ ... OK -* checking examples ... OK -* checking for unstated dependencies in vignettes ... OK -* checking package vignettes in ‘inst/doc’ ... OK -* checking running R code from vignettes ... OK - ‘getting-started.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: 1 NOTE - - - +* installing *source* package ‘Multiaovbay’ ... +** package ‘Multiaovbay’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is being loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘Multiaovbay’ +* removing ‘/tmp/workdir/Multiaovbay/old/Multiaovbay.Rcheck/Multiaovbay’ ``` -# Greg +# multilevelTools
-* Version: 2.0.2 -* GitHub: https://github.com/gforge/Greg -* Source code: https://github.com/cran/Greg -* Date/Publication: 2024-01-29 13:30:21 UTC -* Number of recursive dependencies: 151 +* Version: 0.1.1 +* GitHub: https://github.com/JWiley/multilevelTools +* Source code: https://github.com/cran/multilevelTools +* Date/Publication: 2020-03-04 09:50:02 UTC +* Number of recursive dependencies: 168 -Run `revdepcheck::cloud_details(, "Greg")` for more info +Run `revdepcheck::cloud_details(, "multilevelTools")` for more info
-## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/Greg/new/Greg.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘Greg/DESCRIPTION’ ... OK -... -* this is package ‘Greg’ version ‘2.0.2’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘rms’ +## In both -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR +* checking whether package ‘multilevelTools’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/multilevelTools/new/multilevelTools.Rcheck/00install.out’ for details. + ``` +## Installation +### Devel +``` +* installing *source* package ‘multilevelTools’ ... +** package ‘multilevelTools’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** inst +** byte-compile and prepare package for lazy loading +Warning in check_dep_version() : + ABI version mismatch: +lme4 was built with Matrix ABI version 1 +Current Matrix ABI version is 0 +Please re-install lme4 from source or restore original ‘Matrix’ package +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘multilevelTools’ +* removing ‘/tmp/workdir/multilevelTools/new/multilevelTools.Rcheck/multilevelTools’ ``` ### CRAN ``` -* using log directory ‘/tmp/workdir/Greg/old/Greg.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘Greg/DESCRIPTION’ ... OK -... -* this is package ‘Greg’ version ‘2.0.2’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘rms’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - +* installing *source* package ‘multilevelTools’ ... +** package ‘multilevelTools’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** inst +** byte-compile and prepare package for lazy loading +Warning in check_dep_version() : + ABI version mismatch: +lme4 was built with Matrix ABI version 1 +Current Matrix ABI version is 0 +Please re-install lme4 from source or restore original ‘Matrix’ package +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘multilevelTools’ +* removing ‘/tmp/workdir/multilevelTools/old/multilevelTools.Rcheck/multilevelTools’ ``` -# greport +# multinma
-* Version: 0.7-4 -* GitHub: https://github.com/harrelfe/greport -* Source code: https://github.com/cran/greport -* Date/Publication: 2023-09-02 22:20:02 UTC -* Number of recursive dependencies: 84 +* Version: 0.7.1 +* GitHub: https://github.com/dmphillippo/multinma +* Source code: https://github.com/cran/multinma +* Date/Publication: 2024-06-11 12:20:06 UTC +* Number of recursive dependencies: 152 -Run `revdepcheck::cloud_details(, "greport")` for more info +Run `revdepcheck::cloud_details(, "multinma")` for more info
-## Error before installation +## In both -### Devel +* checking whether package ‘multinma’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/multinma/new/multinma.Rcheck/00install.out’ for details. + ``` -``` -* using log directory ‘/tmp/workdir/greport/new/greport.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘greport/DESCRIPTION’ ... OK -* this is package ‘greport’ version ‘0.7-4’ -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘rms’ +## Installation -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR +### Devel +``` +* installing *source* package ‘multinma’ ... +** package ‘multinma’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C++ compiler: ‘g++ (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ +using C++17 +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I"../inst/include" -I"/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src" -DBOOST_DISABLE_ASSERTS -DEIGEN_NO_DEBUG -DBOOST_MATH_OVERFLOW_ERROR_POLICY=errno_on_error -DUSE_STANC3 -D_HAS_AUTO_PTR_ETC=0 -I'/opt/R/4.3.1/lib/R/site-library/BH/include' -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppEigen/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -I'/opt/R/4.3.1/lib/R/site-library/rstan/include' -I'/opt/R/4.3.1/lib/R/site-library/StanHeaders/include' -I/usr/local/include -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -D_REENTRANT -DSTAN_THREADS -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +In file included from /opt/R/4.3.1/lib/R/site-library/RcppEigen/include/Eigen/Core:205, +... +/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src/stan/mcmc/hmc/hamiltonians/dense_e_metric.hpp:22:56: required from ‘double stan::mcmc::dense_e_metric::T(stan::mcmc::dense_e_point&) [with Model = model_survival_mspline_namespace::model_survival_mspline; BaseRNG = boost::random::additive_combine_engine, boost::random::linear_congruential_engine >]’ +/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src/stan/mcmc/hmc/hamiltonians/dense_e_metric.hpp:21:10: required from here +/opt/R/4.3.1/lib/R/site-library/RcppEigen/include/Eigen/src/Core/DenseCoeffsBase.h:654:74: warning: ignoring attributes on template argument ‘Eigen::internal::packet_traits::type’ {aka ‘__m128d’} [-Wignored-attributes] + 654 | return internal::first_aligned::alignment),Derived>(m); + | ^~~~~~~~~ +g++: fatal error: Killed signal terminated program cc1plus +compilation terminated. +make: *** [/opt/R/4.3.1/lib/R/etc/Makeconf:198: stanExports_survival_mspline.o] Error 1 +ERROR: compilation failed for package ‘multinma’ +* removing ‘/tmp/workdir/multinma/new/multinma.Rcheck/multinma’ ``` ### CRAN ``` -* using log directory ‘/tmp/workdir/greport/old/greport.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘greport/DESCRIPTION’ ... OK -* this is package ‘greport’ version ‘0.7-4’ -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘rms’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - +* installing *source* package ‘multinma’ ... +** package ‘multinma’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C++ compiler: ‘g++ (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ +using C++17 +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I"../inst/include" -I"/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src" -DBOOST_DISABLE_ASSERTS -DEIGEN_NO_DEBUG -DBOOST_MATH_OVERFLOW_ERROR_POLICY=errno_on_error -DUSE_STANC3 -D_HAS_AUTO_PTR_ETC=0 -I'/opt/R/4.3.1/lib/R/site-library/BH/include' -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppEigen/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -I'/opt/R/4.3.1/lib/R/site-library/rstan/include' -I'/opt/R/4.3.1/lib/R/site-library/StanHeaders/include' -I/usr/local/include -I'/opt/R/4.3.1/lib/R/site-library/RcppParallel/include' -D_REENTRANT -DSTAN_THREADS -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +In file included from /opt/R/4.3.1/lib/R/site-library/RcppEigen/include/Eigen/Core:205, +... +/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src/stan/mcmc/hmc/hamiltonians/dense_e_metric.hpp:22:56: required from ‘double stan::mcmc::dense_e_metric::T(stan::mcmc::dense_e_point&) [with Model = model_survival_mspline_namespace::model_survival_mspline; BaseRNG = boost::random::additive_combine_engine, boost::random::linear_congruential_engine >]’ +/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src/stan/mcmc/hmc/hamiltonians/dense_e_metric.hpp:21:10: required from here +/opt/R/4.3.1/lib/R/site-library/RcppEigen/include/Eigen/src/Core/DenseCoeffsBase.h:654:74: warning: ignoring attributes on template argument ‘Eigen::internal::packet_traits::type’ {aka ‘__m128d’} [-Wignored-attributes] + 654 | return internal::first_aligned::alignment),Derived>(m); + | ^~~~~~~~~ +g++: fatal error: Killed signal terminated program cc1plus +compilation terminated. +make: *** [/opt/R/4.3.1/lib/R/etc/Makeconf:198: stanExports_survival_mspline.o] Error 1 +ERROR: compilation failed for package ‘multinma’ +* removing ‘/tmp/workdir/multinma/old/multinma.Rcheck/multinma’ ``` -# harmony +# NCA
-* Version: 1.2.0 +* Version: 4.0.1 * GitHub: NA -* Source code: https://github.com/cran/harmony -* Date/Publication: 2023-11-29 08:30:04 UTC -* Number of recursive dependencies: 213 +* Source code: https://github.com/cran/NCA +* Date/Publication: 2024-02-23 09:30:15 UTC +* Number of recursive dependencies: 99 -Run `revdepcheck::cloud_details(, "harmony")` for more info +Run `revdepcheck::cloud_details(, "NCA")` for more info
-## Error before installation +## In both -### Devel +* checking whether package ‘NCA’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/NCA/new/NCA.Rcheck/00install.out’ for details. + ``` -``` -* using log directory ‘/tmp/workdir/harmony/new/harmony.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘harmony/DESCRIPTION’ ... OK -... ---- finished re-building ‘quickstart.Rmd’ +## Installation -SUMMARY: processing the following file failed: - ‘Seurat.Rmd’ +### Devel -Error: Vignette re-building failed. +``` +* installing *source* package ‘NCA’ ... +** package ‘NCA’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** data +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace Execution halted +ERROR: lazy loading failed for package ‘NCA’ +* removing ‘/tmp/workdir/NCA/new/NCA.Rcheck/NCA’ -* DONE -Status: 1 WARNING, 3 NOTEs - - - - -``` -### CRAN +``` +### CRAN ``` -* using log directory ‘/tmp/workdir/harmony/old/harmony.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘harmony/DESCRIPTION’ ... OK -... ---- finished re-building ‘quickstart.Rmd’ - -SUMMARY: processing the following file failed: - ‘Seurat.Rmd’ - -Error: Vignette re-building failed. +* installing *source* package ‘NCA’ ... +** package ‘NCA’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** data +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace Execution halted - -* DONE -Status: 1 WARNING, 3 NOTEs - - - +ERROR: lazy loading failed for package ‘NCA’ +* removing ‘/tmp/workdir/NCA/old/NCA.Rcheck/NCA’ ``` -# hIRT +# netcmc
-* Version: 0.3.0 -* GitHub: https://github.com/xiangzhou09/hIRT -* Source code: https://github.com/cran/hIRT -* Date/Publication: 2020-03-26 17:10:02 UTC -* Number of recursive dependencies: 88 +* Version: 1.0.2 +* GitHub: NA +* Source code: https://github.com/cran/netcmc +* Date/Publication: 2022-11-08 22:30:15 UTC +* Number of recursive dependencies: 61 -Run `revdepcheck::cloud_details(, "hIRT")` for more info +Run `revdepcheck::cloud_details(, "netcmc")` for more info
-## Error before installation +## In both + +* checking whether package ‘netcmc’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/netcmc/new/netcmc.Rcheck/00install.out’ for details. + ``` + +## Installation ### Devel ``` -* using log directory ‘/tmp/workdir/hIRT/new/hIRT.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘hIRT/DESCRIPTION’ ... OK +* installing *source* package ‘netcmc’ ... +** package ‘netcmc’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C++ compiler: ‘g++ (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ +using C++11 +g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppProgress/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppProgress/include' -I/usr/local/include -fpic -g -O2 -c choleskyDecompositionRcppConversion.cpp -o choleskyDecompositionRcppConversion.o +g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppProgress/include' -I/usr/local/include -fpic -g -O2 -c doubleMatrixMultiplicationRcpp.cpp -o doubleMatrixMultiplicationRcpp.o +g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppProgress/include' -I/usr/local/include -fpic -g -O2 -c doubleVectorMultiplicationRcpp.cpp -o doubleVectorMultiplicationRcpp.o ... -* this is package ‘hIRT’ version ‘0.3.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘rms’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - +g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppProgress/include' -I/usr/local/include -fpic -g -O2 -c vectorVectorTransposeMultiplicationRcpp.cpp -o vectorVectorTransposeMultiplicationRcpp.o +g++ -std=gnu++11 -shared -L/opt/R/4.3.1/lib/R/lib -L/usr/local/lib -o netcmc.so RcppExports.o choleskyDecompositionRcppConversion.o doubleMatrixMultiplicationRcpp.o doubleVectorMultiplicationRcpp.o eigenValuesRcppConversion.o getDiagonalMatrix.o getExp.o getExpDividedByOnePlusExp.o getMeanCenteredRandomEffects.o getMultivariateBinomialNetworkLerouxDIC.o getMultivariateBinomialNetworkLerouxFittedValuesAndLikelihoodForDICEveryIteration.o getMultivariateGaussianNetworkLerouxDIC.o getMultivariateGaussianNetworkLerouxFittedValuesAndLikelihoodForDICEveryIteration.o getMultivariatePoissonNetworkLerouxDIC.o getMultivariatePoissonNetworkLerouxFittedValuesAndLikelihoodForDICEveryIteration.o getNonZeroEntries.o getSubvector.o getSubvectorIndecies.o getSumExpNetwork.o getSumExpNetworkIndecies.o getSumExpNetworkLeroux.o getSumExpNetworkLerouxIndecies.o getSumLogExp.o getSumLogExpIndecies.o getSumVector.o getTripletForm.o getUnivariateBinomialNetworkLerouxDIC.o getUnivariateBinomialNetworkLerouxFittedValuesAndLikelihoodForDICEveryIteration.o getUnivariateGaussianNetworkLerouxDIC.o getUnivariateGaussianNetworkLerouxFittedValuesAndLikelihoodForDICEveryIteration.o getUnivariatePoissonNetworkDIC.o getUnivariatePoissonNetworkFittedValuesAndLikelihoodForDICEveryIteration.o getUnivariatePoissonNetworkLerouxDIC.o getUnivariatePoissonNetworkLerouxFittedValuesAndLikelihoodForDICEveryIteration.o getVectorMean.o matrixInverseRcppConversion.o matrixMatrixAdditionRcpp.o matrixMatrixSubtractionRcpp.o matrixVectorMultiplicationRcpp.o multivariateBinomialNetworkLerouxAllUpdate.o multivariateBinomialNetworkLerouxBetaUpdate.o multivariateBinomialNetworkLerouxRhoUpdate.o multivariateBinomialNetworkLerouxSingleUpdate.o multivariateBinomialNetworkLerouxSpatialRandomEffectsUpdate.o multivariateBinomialNetworkLerouxTauSquaredUpdate.o multivariateBinomialNetworkLerouxURandomEffectsUpdate.o multivariateBinomialNetworkLerouxVRandomEffectsUpdate.o multivariateBinomialNetworkLerouxVarianceCovarianceUUpdate.o multivariateBinomialNetworkRandAllUpdate.o multivariateBinomialNetworkRandSingleUpdate.o multivariateGaussianNetworkLerouxAllMHUpdate.o multivariateGaussianNetworkLerouxBetaUpdate.o multivariateGaussianNetworkLerouxRhoUpdate.o multivariateGaussianNetworkLerouxSigmaSquaredEUpdate.o multivariateGaussianNetworkLerouxSingleMHUpdate.o multivariateGaussianNetworkLerouxSpatialRandomEffectsMHUpdate.o multivariateGaussianNetworkLerouxTauSquaredUpdate.o multivariateGaussianNetworkLerouxURandomEffectsUpdate.o multivariateGaussianNetworkLerouxVarianceCovarianceUUpdate.o multivariateGaussianNetworkRandAllUpdate.o multivariateGaussianNetworkRandSingleUpdate.o multivariateGaussianNetworkRandVRandomEffectsUpdate.o multivariatePoissonNetworkLerouxAllUpdate.o multivariatePoissonNetworkLerouxBetaUpdate.o multivariatePoissonNetworkLerouxRhoUpdate.o multivariatePoissonNetworkLerouxSingleUpdate.o multivariatePoissonNetworkLerouxSpatialRandomEffectsUpdate.o multivariatePoissonNetworkLerouxTauSquaredUpdate.o multivariatePoissonNetworkLerouxURandomEffectsUpdate.o multivariatePoissonNetworkLerouxVRandomEffectsUpdate.o multivariatePoissonNetworkLerouxVarianceCovarianceUUpdate.o multivariatePoissonNetworkRandAllUpdate.o multivariatePoissonNetworkRandSingleUpdate.o sumMatrix.o univariateBinomialNetworkLerouxAllUpdate.o univariateBinomialNetworkLerouxBetaUpdate.o univariateBinomialNetworkLerouxRhoUpdate.o univariateBinomialNetworkLerouxSigmaSquaredUpdate.o univariateBinomialNetworkLerouxSingleUpdate.o univariateBinomialNetworkLerouxSpatialRandomEffectsUpdate.o univariateBinomialNetworkLerouxTauSquaredUpdate.o univariateBinomialNetworkLerouxURandomEffectsUpdate.o univariateGaussianNetworkLerouxAllMHUpdate.o univariateGaussianNetworkLerouxBetaUpdate.o univariateGaussianNetworkLerouxRhoUpdate.o univariateGaussianNetworkLerouxSigmaSquaredEUpdate.o univariateGaussianNetworkLerouxSigmaSquaredUUpdate.o univariateGaussianNetworkLerouxSingleMHUpdate.o univariateGaussianNetworkLerouxSpatialRandomEffectsMHUpdate.o univariateGaussianNetworkLerouxTauSquaredUpdate.o univariateGaussianNetworkLerouxURandomEffectsUpdate.o univariatePoissonNetworkLerouxAllUpdate.o univariatePoissonNetworkLerouxBetaUpdate.o univariatePoissonNetworkLerouxRhoUpdate.o univariatePoissonNetworkLerouxSigmaSquaredUpdate.o univariatePoissonNetworkLerouxSingleUpdate.o univariatePoissonNetworkLerouxSpatialRandomEffectsUpdate.o univariatePoissonNetworkLerouxTauSquaredUpdate.o univariatePoissonNetworkLerouxURandomEffectsUpdate.o vectorTransposeVectorMultiplicationRcpp.o vectorVectorTransposeMultiplicationRcpp.o -llapack -lblas -lgfortran -lm -lquadmath -L/opt/R/4.3.1/lib/R/lib -lR +installing to /tmp/workdir/netcmc/new/netcmc.Rcheck/00LOCK-netcmc/00new/netcmc/libs +** R +** byte-compile and prepare package for lazy loading +Error: package or namespace load failed for ‘MCMCpack’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Execution halted +ERROR: lazy loading failed for package ‘netcmc’ +* removing ‘/tmp/workdir/netcmc/new/netcmc.Rcheck/netcmc’ ``` ### CRAN ``` -* using log directory ‘/tmp/workdir/hIRT/old/hIRT.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘hIRT/DESCRIPTION’ ... OK +* installing *source* package ‘netcmc’ ... +** package ‘netcmc’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C++ compiler: ‘g++ (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ +using C++11 +g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppProgress/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppProgress/include' -I/usr/local/include -fpic -g -O2 -c choleskyDecompositionRcppConversion.cpp -o choleskyDecompositionRcppConversion.o +g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppProgress/include' -I/usr/local/include -fpic -g -O2 -c doubleMatrixMultiplicationRcpp.cpp -o doubleMatrixMultiplicationRcpp.o +g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppProgress/include' -I/usr/local/include -fpic -g -O2 -c doubleVectorMultiplicationRcpp.cpp -o doubleVectorMultiplicationRcpp.o ... -* this is package ‘hIRT’ version ‘0.3.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘rms’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - +g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppProgress/include' -I/usr/local/include -fpic -g -O2 -c vectorVectorTransposeMultiplicationRcpp.cpp -o vectorVectorTransposeMultiplicationRcpp.o +g++ -std=gnu++11 -shared -L/opt/R/4.3.1/lib/R/lib -L/usr/local/lib -o netcmc.so RcppExports.o choleskyDecompositionRcppConversion.o doubleMatrixMultiplicationRcpp.o doubleVectorMultiplicationRcpp.o eigenValuesRcppConversion.o getDiagonalMatrix.o getExp.o getExpDividedByOnePlusExp.o getMeanCenteredRandomEffects.o getMultivariateBinomialNetworkLerouxDIC.o getMultivariateBinomialNetworkLerouxFittedValuesAndLikelihoodForDICEveryIteration.o getMultivariateGaussianNetworkLerouxDIC.o getMultivariateGaussianNetworkLerouxFittedValuesAndLikelihoodForDICEveryIteration.o getMultivariatePoissonNetworkLerouxDIC.o getMultivariatePoissonNetworkLerouxFittedValuesAndLikelihoodForDICEveryIteration.o getNonZeroEntries.o getSubvector.o getSubvectorIndecies.o getSumExpNetwork.o getSumExpNetworkIndecies.o getSumExpNetworkLeroux.o getSumExpNetworkLerouxIndecies.o getSumLogExp.o getSumLogExpIndecies.o getSumVector.o getTripletForm.o getUnivariateBinomialNetworkLerouxDIC.o getUnivariateBinomialNetworkLerouxFittedValuesAndLikelihoodForDICEveryIteration.o getUnivariateGaussianNetworkLerouxDIC.o getUnivariateGaussianNetworkLerouxFittedValuesAndLikelihoodForDICEveryIteration.o getUnivariatePoissonNetworkDIC.o getUnivariatePoissonNetworkFittedValuesAndLikelihoodForDICEveryIteration.o getUnivariatePoissonNetworkLerouxDIC.o getUnivariatePoissonNetworkLerouxFittedValuesAndLikelihoodForDICEveryIteration.o getVectorMean.o matrixInverseRcppConversion.o matrixMatrixAdditionRcpp.o matrixMatrixSubtractionRcpp.o matrixVectorMultiplicationRcpp.o multivariateBinomialNetworkLerouxAllUpdate.o multivariateBinomialNetworkLerouxBetaUpdate.o multivariateBinomialNetworkLerouxRhoUpdate.o multivariateBinomialNetworkLerouxSingleUpdate.o multivariateBinomialNetworkLerouxSpatialRandomEffectsUpdate.o multivariateBinomialNetworkLerouxTauSquaredUpdate.o multivariateBinomialNetworkLerouxURandomEffectsUpdate.o multivariateBinomialNetworkLerouxVRandomEffectsUpdate.o multivariateBinomialNetworkLerouxVarianceCovarianceUUpdate.o multivariateBinomialNetworkRandAllUpdate.o multivariateBinomialNetworkRandSingleUpdate.o multivariateGaussianNetworkLerouxAllMHUpdate.o multivariateGaussianNetworkLerouxBetaUpdate.o multivariateGaussianNetworkLerouxRhoUpdate.o multivariateGaussianNetworkLerouxSigmaSquaredEUpdate.o multivariateGaussianNetworkLerouxSingleMHUpdate.o multivariateGaussianNetworkLerouxSpatialRandomEffectsMHUpdate.o multivariateGaussianNetworkLerouxTauSquaredUpdate.o multivariateGaussianNetworkLerouxURandomEffectsUpdate.o multivariateGaussianNetworkLerouxVarianceCovarianceUUpdate.o multivariateGaussianNetworkRandAllUpdate.o multivariateGaussianNetworkRandSingleUpdate.o multivariateGaussianNetworkRandVRandomEffectsUpdate.o multivariatePoissonNetworkLerouxAllUpdate.o multivariatePoissonNetworkLerouxBetaUpdate.o multivariatePoissonNetworkLerouxRhoUpdate.o multivariatePoissonNetworkLerouxSingleUpdate.o multivariatePoissonNetworkLerouxSpatialRandomEffectsUpdate.o multivariatePoissonNetworkLerouxTauSquaredUpdate.o multivariatePoissonNetworkLerouxURandomEffectsUpdate.o multivariatePoissonNetworkLerouxVRandomEffectsUpdate.o multivariatePoissonNetworkLerouxVarianceCovarianceUUpdate.o multivariatePoissonNetworkRandAllUpdate.o multivariatePoissonNetworkRandSingleUpdate.o sumMatrix.o univariateBinomialNetworkLerouxAllUpdate.o univariateBinomialNetworkLerouxBetaUpdate.o univariateBinomialNetworkLerouxRhoUpdate.o univariateBinomialNetworkLerouxSigmaSquaredUpdate.o univariateBinomialNetworkLerouxSingleUpdate.o univariateBinomialNetworkLerouxSpatialRandomEffectsUpdate.o univariateBinomialNetworkLerouxTauSquaredUpdate.o univariateBinomialNetworkLerouxURandomEffectsUpdate.o univariateGaussianNetworkLerouxAllMHUpdate.o univariateGaussianNetworkLerouxBetaUpdate.o univariateGaussianNetworkLerouxRhoUpdate.o univariateGaussianNetworkLerouxSigmaSquaredEUpdate.o univariateGaussianNetworkLerouxSigmaSquaredUUpdate.o univariateGaussianNetworkLerouxSingleMHUpdate.o univariateGaussianNetworkLerouxSpatialRandomEffectsMHUpdate.o univariateGaussianNetworkLerouxTauSquaredUpdate.o univariateGaussianNetworkLerouxURandomEffectsUpdate.o univariatePoissonNetworkLerouxAllUpdate.o univariatePoissonNetworkLerouxBetaUpdate.o univariatePoissonNetworkLerouxRhoUpdate.o univariatePoissonNetworkLerouxSigmaSquaredUpdate.o univariatePoissonNetworkLerouxSingleUpdate.o univariatePoissonNetworkLerouxSpatialRandomEffectsUpdate.o univariatePoissonNetworkLerouxTauSquaredUpdate.o univariatePoissonNetworkLerouxURandomEffectsUpdate.o vectorTransposeVectorMultiplicationRcpp.o vectorVectorTransposeMultiplicationRcpp.o -llapack -lblas -lgfortran -lm -lquadmath -L/opt/R/4.3.1/lib/R/lib -lR +installing to /tmp/workdir/netcmc/old/netcmc.Rcheck/00LOCK-netcmc/00new/netcmc/libs +** R +** byte-compile and prepare package for lazy loading +Error: package or namespace load failed for ‘MCMCpack’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Execution halted +ERROR: lazy loading failed for package ‘netcmc’ +* removing ‘/tmp/workdir/netcmc/old/netcmc.Rcheck/netcmc’ ``` -# Hmisc +# NetworkChange
-* Version: 5.1-3 -* GitHub: NA -* Source code: https://github.com/cran/Hmisc -* Date/Publication: 2024-05-28 07:10:02 UTC -* Number of recursive dependencies: 183 +* Version: 0.8 +* GitHub: https://github.com/jongheepark/NetworkChange +* Source code: https://github.com/cran/NetworkChange +* Date/Publication: 2022-03-04 07:30:02 UTC +* Number of recursive dependencies: 132 -Run `revdepcheck::cloud_details(, "Hmisc")` for more info +Run `revdepcheck::cloud_details(, "NetworkChange")` for more info
-## Error before installation - -### Devel +## In both -``` -* using log directory ‘/tmp/workdir/Hmisc/new/Hmisc.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘Hmisc/DESCRIPTION’ ... OK -... -* checking for missing documentation entries ... OK -* checking for code/documentation mismatches ... OK -* checking Rd \usage sections ... OK -* checking Rd contents ... OK -* checking for unstated dependencies in examples ... OK -* checking line endings in C/C++/Fortran sources/headers ... OK -* checking compiled code ... OK -* checking examples ... OK -* DONE -Status: 4 NOTEs +* checking whether package ‘NetworkChange’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/NetworkChange/new/NetworkChange.Rcheck/00install.out’ for details. + ``` +## Installation +### Devel +``` +* installing *source* package ‘NetworkChange’ ... +** package ‘NetworkChange’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** data +** byte-compile and prepare package for lazy loading +Error: package or namespace load failed for ‘MCMCpack’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Execution halted +ERROR: lazy loading failed for package ‘NetworkChange’ +* removing ‘/tmp/workdir/NetworkChange/new/NetworkChange.Rcheck/NetworkChange’ ``` ### CRAN ``` -* using log directory ‘/tmp/workdir/Hmisc/old/Hmisc.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘Hmisc/DESCRIPTION’ ... OK -... -* checking for missing documentation entries ... OK -* checking for code/documentation mismatches ... OK -* checking Rd \usage sections ... OK -* checking Rd contents ... OK -* checking for unstated dependencies in examples ... OK -* checking line endings in C/C++/Fortran sources/headers ... OK -* checking compiled code ... OK -* checking examples ... OK -* DONE -Status: 4 NOTEs - - - +* installing *source* package ‘NetworkChange’ ... +** package ‘NetworkChange’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** data +** byte-compile and prepare package for lazy loading +Error: package or namespace load failed for ‘MCMCpack’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Execution halted +ERROR: lazy loading failed for package ‘NetworkChange’ +* removing ‘/tmp/workdir/NetworkChange/old/NetworkChange.Rcheck/NetworkChange’ ``` -# Hmsc +# nlmeVPC
-* Version: 3.0-13 -* GitHub: https://github.com/hmsc-r/HMSC -* Source code: https://github.com/cran/Hmsc -* Date/Publication: 2022-08-11 14:10:14 UTC -* Number of recursive dependencies: 76 +* Version: 2.6 +* GitHub: NA +* Source code: https://github.com/cran/nlmeVPC +* Date/Publication: 2022-12-22 05:20:02 UTC +* Number of recursive dependencies: 77 -Run `revdepcheck::cloud_details(, "Hmsc")` for more info +Run `revdepcheck::cloud_details(, "nlmeVPC")` for more info
## In both -* checking whether package ‘Hmsc’ can be installed ... ERROR +* checking whether package ‘nlmeVPC’ can be installed ... ERROR ``` Installation failed. - See ‘/tmp/workdir/Hmsc/new/Hmsc.Rcheck/00install.out’ for details. + See ‘/tmp/workdir/nlmeVPC/new/nlmeVPC.Rcheck/00install.out’ for details. ``` ## Installation @@ -5294,199 +4455,133 @@ Run `revdepcheck::cloud_details(, "Hmsc")` for more info ### Devel ``` -* installing *source* package ‘Hmsc’ ... -** package ‘Hmsc’ successfully unpacked and MD5 sums checked +* installing *source* package ‘nlmeVPC’ ... +** package ‘nlmeVPC’ successfully unpacked and MD5 sums checked ** using staged installation +** libs +using C++ compiler: ‘g++ (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ +using C++11 +g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c Misc.cpp -o Misc.o +g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +g++ -std=gnu++11 -shared -L/opt/R/4.3.1/lib/R/lib -L/usr/local/lib -o nlmeVPC.so Misc.o RcppExports.o -fopenmp -llapack -lblas -lgfortran -lm -lquadmath -L/opt/R/4.3.1/lib/R/lib -lR +installing to /tmp/workdir/nlmeVPC/new/nlmeVPC.Rcheck/00LOCK-nlmeVPC/00new/nlmeVPC/libs ** R ** data -*** moving datasets to lazyload DB -** 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 ‘quantreg’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace Execution halted -ERROR: lazy loading failed for package ‘Hmsc’ -* removing ‘/tmp/workdir/Hmsc/new/Hmsc.Rcheck/Hmsc’ +ERROR: lazy loading failed for package ‘nlmeVPC’ +* removing ‘/tmp/workdir/nlmeVPC/new/nlmeVPC.Rcheck/nlmeVPC’ ``` ### CRAN ``` -* installing *source* package ‘Hmsc’ ... -** package ‘Hmsc’ successfully unpacked and MD5 sums checked +* installing *source* package ‘nlmeVPC’ ... +** package ‘nlmeVPC’ successfully unpacked and MD5 sums checked ** using staged installation +** libs +using C++ compiler: ‘g++ (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ +using C++11 +g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c Misc.cpp -o Misc.o +g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +g++ -std=gnu++11 -shared -L/opt/R/4.3.1/lib/R/lib -L/usr/local/lib -o nlmeVPC.so Misc.o RcppExports.o -fopenmp -llapack -lblas -lgfortran -lm -lquadmath -L/opt/R/4.3.1/lib/R/lib -lR +installing to /tmp/workdir/nlmeVPC/old/nlmeVPC.Rcheck/00LOCK-nlmeVPC/00new/nlmeVPC/libs ** R ** data -*** moving datasets to lazyload DB -** 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 ‘quantreg’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace Execution halted -ERROR: lazy loading failed for package ‘Hmsc’ -* removing ‘/tmp/workdir/Hmsc/old/Hmsc.Rcheck/Hmsc’ +ERROR: lazy loading failed for package ‘nlmeVPC’ +* removing ‘/tmp/workdir/nlmeVPC/old/nlmeVPC.Rcheck/nlmeVPC’ ``` -# hydroroute +# NMADiagT
* Version: 0.1.2 * GitHub: NA -* Source code: https://github.com/cran/hydroroute -* Date/Publication: 2023-02-08 13:20:02 UTC -* Number of recursive dependencies: 81 +* Source code: https://github.com/cran/NMADiagT +* Date/Publication: 2020-02-26 07:00:02 UTC +* Number of recursive dependencies: 79 -Run `revdepcheck::cloud_details(, "hydroroute")` for more info +Run `revdepcheck::cloud_details(, "NMADiagT")` for more info
-## Error before installation +## In both + +* checking whether package ‘NMADiagT’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/NMADiagT/new/NMADiagT.Rcheck/00install.out’ for details. + ``` + +## Installation ### Devel ``` -* using log directory ‘/tmp/workdir/hydroroute/new/hydroroute.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘hydroroute/DESCRIPTION’ ... OK -... -* this is package ‘hydroroute’ version ‘0.1.2’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘ggpmisc’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/hydroroute/old/hydroroute.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘hydroroute/DESCRIPTION’ ... OK -... -* this is package ‘hydroroute’ version ‘0.1.2’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘ggpmisc’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# inventorize - -
- -* Version: 1.1.1 -* GitHub: NA -* Source code: https://github.com/cran/inventorize -* Date/Publication: 2022-05-31 22:20:09 UTC -* Number of recursive dependencies: 71 - -Run `revdepcheck::cloud_details(, "inventorize")` for more info - -
- -## Newly broken - -* checking whether package ‘inventorize’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/inventorize/new/inventorize.Rcheck/00install.out’ for details. - ``` - -## Installation - -### Devel - -``` -* installing *source* package ‘inventorize’ ... -** package ‘inventorize’ successfully unpacked and MD5 sums checked +* installing *source* package ‘NMADiagT’ ... +** package ‘NMADiagT’ successfully unpacked and MD5 sums checked ** using staged installation ** R +** inst ** byte-compile and prepare package for lazy loading -Error in pm[[2]] : subscript out of bounds -Error: unable to load R code in package ‘inventorize’ +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace Execution halted -ERROR: lazy loading failed for package ‘inventorize’ -* removing ‘/tmp/workdir/inventorize/new/inventorize.Rcheck/inventorize’ +ERROR: lazy loading failed for package ‘NMADiagT’ +* removing ‘/tmp/workdir/NMADiagT/new/NMADiagT.Rcheck/NMADiagT’ ``` ### CRAN ``` -* installing *source* package ‘inventorize’ ... -** package ‘inventorize’ successfully unpacked and MD5 sums checked +* installing *source* package ‘NMADiagT’ ... +** package ‘NMADiagT’ successfully unpacked and MD5 sums checked ** using staged installation ** R +** inst ** byte-compile and prepare package for lazy loading -Warning in qgamma(service_level, alpha, beta) : NaNs produced -Warning in qgamma(service_level, alpha, beta) : NaNs produced -** help -*** installing help indices -** building package indices -** testing if installed package can be loaded from temporary location -** testing if installed package can be loaded from final location -** testing if installed package keeps a record of temporary installation path -* DONE (inventorize) +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘NMADiagT’ +* removing ‘/tmp/workdir/NMADiagT/old/NMADiagT.Rcheck/NMADiagT’ ``` -# iNZightRegression +# optweight
-* Version: 1.3.4 -* GitHub: https://github.com/iNZightVIT/iNZightRegression -* Source code: https://github.com/cran/iNZightRegression -* Date/Publication: 2024-04-05 02:32:59 UTC -* Number of recursive dependencies: 153 +* Version: 0.2.5 +* GitHub: NA +* Source code: https://github.com/cran/optweight +* Date/Publication: 2019-09-16 15:40:02 UTC +* Number of recursive dependencies: 55 -Run `revdepcheck::cloud_details(, "iNZightRegression")` for more info +Run `revdepcheck::cloud_details(, "optweight")` for more info
## In both -* checking whether package ‘iNZightRegression’ can be installed ... ERROR +* checking whether package ‘optweight’ can be installed ... ERROR ``` Installation failed. - See ‘/tmp/workdir/iNZightRegression/new/iNZightRegression.Rcheck/00install.out’ for details. + See ‘/tmp/workdir/optweight/new/optweight.Rcheck/00install.out’ for details. ``` ## Installation @@ -5494,59 +4589,57 @@ Run `revdepcheck::cloud_details(, "iNZightRegression")` for more info ### Devel ``` -* installing *source* package ‘iNZightRegression’ ... -** package ‘iNZightRegression’ successfully unpacked and MD5 sums checked +* installing *source* package ‘optweight’ ... +** package ‘optweight’ successfully unpacked and MD5 sums checked ** using staged installation ** R -** 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 ‘quantreg’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.1 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace Execution halted -ERROR: lazy loading failed for package ‘iNZightRegression’ -* removing ‘/tmp/workdir/iNZightRegression/new/iNZightRegression.Rcheck/iNZightRegression’ +ERROR: lazy loading failed for package ‘optweight’ +* removing ‘/tmp/workdir/optweight/new/optweight.Rcheck/optweight’ ``` ### CRAN ``` -* installing *source* package ‘iNZightRegression’ ... -** package ‘iNZightRegression’ successfully unpacked and MD5 sums checked +* installing *source* package ‘optweight’ ... +** package ‘optweight’ successfully unpacked and MD5 sums checked ** using staged installation ** R -** 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 ‘quantreg’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.1 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace Execution halted -ERROR: lazy loading failed for package ‘iNZightRegression’ -* removing ‘/tmp/workdir/iNZightRegression/old/iNZightRegression.Rcheck/iNZightRegression’ +ERROR: lazy loading failed for package ‘optweight’ +* removing ‘/tmp/workdir/optweight/old/optweight.Rcheck/optweight’ ``` -# IRexamples +# OVtool
-* Version: 0.0.4 -* GitHub: https://github.com/vinhdizzo/IRexamples -* Source code: https://github.com/cran/IRexamples -* Date/Publication: 2023-10-06 06:40:02 UTC -* Number of recursive dependencies: 185 +* Version: 1.0.3 +* GitHub: NA +* Source code: https://github.com/cran/OVtool +* Date/Publication: 2021-11-02 08:10:07 UTC +* Number of recursive dependencies: 157 -Run `revdepcheck::cloud_details(, "IRexamples")` for more info +Run `revdepcheck::cloud_details(, "OVtool")` for more info
## In both -* checking whether package ‘IRexamples’ can be installed ... ERROR +* checking whether package ‘OVtool’ can be installed ... ERROR ``` Installation failed. - See ‘/tmp/workdir/IRexamples/new/IRexamples.Rcheck/00install.out’ for details. + See ‘/tmp/workdir/OVtool/new/OVtool.Rcheck/00install.out’ for details. ``` ## Installation @@ -5554,4119 +4647,331 @@ Run `revdepcheck::cloud_details(, "IRexamples")` for more info ### Devel ``` -* installing *source* package ‘IRexamples’ ... -** package ‘IRexamples’ successfully unpacked and MD5 sums checked +* installing *source* package ‘OVtool’ ... +** package ‘OVtool’ 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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Error: package or namespace load failed for ‘twang’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required Execution halted -ERROR: lazy loading failed for package ‘IRexamples’ -* removing ‘/tmp/workdir/IRexamples/new/IRexamples.Rcheck/IRexamples’ +ERROR: lazy loading failed for package ‘OVtool’ +* removing ‘/tmp/workdir/OVtool/new/OVtool.Rcheck/OVtool’ ``` ### CRAN ``` -* installing *source* package ‘IRexamples’ ... -** package ‘IRexamples’ successfully unpacked and MD5 sums checked +* installing *source* package ‘OVtool’ ... +** package ‘OVtool’ 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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Error: package or namespace load failed for ‘twang’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required Execution halted -ERROR: lazy loading failed for package ‘IRexamples’ -* removing ‘/tmp/workdir/IRexamples/old/IRexamples.Rcheck/IRexamples’ +ERROR: lazy loading failed for package ‘OVtool’ +* removing ‘/tmp/workdir/OVtool/old/OVtool.Rcheck/OVtool’ ``` -# jmBIG +# paths
-* Version: 0.1.2 +* Version: 0.1.1 * GitHub: NA -* Source code: https://github.com/cran/jmBIG -* Date/Publication: 2024-03-20 23:40:02 UTC -* Number of recursive dependencies: 193 +* Source code: https://github.com/cran/paths +* Date/Publication: 2021-06-18 08:40:02 UTC +* Number of recursive dependencies: 102 -Run `revdepcheck::cloud_details(, "jmBIG")` for more info +Run `revdepcheck::cloud_details(, "paths")` for more info
-## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/jmBIG/new/jmBIG.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘jmBIG/DESCRIPTION’ ... OK -... -* this is package ‘jmBIG’ version ‘0.1.2’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘joineRML’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/jmBIG/old/jmBIG.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘jmBIG/DESCRIPTION’ ... OK -... -* this is package ‘jmBIG’ version ‘0.1.2’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘joineRML’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - +## In both +* checking whether package ‘paths’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/paths/new/paths.Rcheck/00install.out’ for details. + ``` +## Installation +### Devel ``` -# joineRML - -
- -* Version: 0.4.6 -* GitHub: https://github.com/graemeleehickey/joineRML -* Source code: https://github.com/cran/joineRML -* Date/Publication: 2023-01-20 04:50:02 UTC -* Number of recursive dependencies: 91 - -Run `revdepcheck::cloud_details(, "joineRML")` for more info - -
- -## In both - -* checking whether package ‘joineRML’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/joineRML/new/joineRML.Rcheck/00install.out’ for details. - ``` - -## Installation - -### Devel - -``` -* installing *source* package ‘joineRML’ ... -** package ‘joineRML’ successfully unpacked and MD5 sums checked -** using staged installation -** libs -using C compiler: ‘gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ -using C++ compiler: ‘g++ (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ -using C++11 -g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o -g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c expW.cpp -o expW.o -g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c gammaUpdate.cpp -o gammaUpdate.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 ‘quantreg’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart -Execution halted -ERROR: lazy loading failed for package ‘joineRML’ -* removing ‘/tmp/workdir/joineRML/new/joineRML.Rcheck/joineRML’ - - -``` -### CRAN - -``` -* installing *source* package ‘joineRML’ ... -** package ‘joineRML’ successfully unpacked and MD5 sums checked -** using staged installation -** libs -using C compiler: ‘gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ -using C++ compiler: ‘g++ (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ -using C++11 -g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o -g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c expW.cpp -o expW.o -g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c gammaUpdate.cpp -o gammaUpdate.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 ‘quantreg’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart -Execution halted -ERROR: lazy loading failed for package ‘joineRML’ -* removing ‘/tmp/workdir/joineRML/old/joineRML.Rcheck/joineRML’ - - -``` -# jsmodule - -
- -* Version: 1.5.4 -* GitHub: https://github.com/jinseob2kim/jsmodule -* Source code: https://github.com/cran/jsmodule -* Date/Publication: 2024-05-07 16:00:05 UTC -* Number of recursive dependencies: 240 - -Run `revdepcheck::cloud_details(, "jsmodule")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/jsmodule/new/jsmodule.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘jsmodule/DESCRIPTION’ ... OK -... -* checking for unstated dependencies in ‘tests’ ... OK -* checking tests ... OK - Running ‘testthat.R’ -* checking for unstated dependencies in vignettes ... OK -* checking package vignettes in ‘inst/doc’ ... OK -* checking running R code from vignettes ... OK - ‘jsmodule.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: OK - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/jsmodule/old/jsmodule.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘jsmodule/DESCRIPTION’ ... OK -... -* checking for unstated dependencies in ‘tests’ ... OK -* checking tests ... OK - Running ‘testthat.R’ -* checking for unstated dependencies in vignettes ... OK -* checking package vignettes in ‘inst/doc’ ... OK -* checking running R code from vignettes ... OK - ‘jsmodule.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: OK - - - - - -``` -# JWileymisc - -
- -* Version: 1.4.1 -* GitHub: https://github.com/JWiley/JWileymisc -* Source code: https://github.com/cran/JWileymisc -* Date/Publication: 2023-10-05 04:50:02 UTC -* Number of recursive dependencies: 163 - -Run `revdepcheck::cloud_details(, "JWileymisc")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/JWileymisc/new/JWileymisc.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘JWileymisc/DESCRIPTION’ ... OK -... -* this is package ‘JWileymisc’ version ‘1.4.1’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Packages required but not available: 'rms', 'quantreg' - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/JWileymisc/old/JWileymisc.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘JWileymisc/DESCRIPTION’ ... OK -... -* this is package ‘JWileymisc’ version ‘1.4.1’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Packages required but not available: 'rms', 'quantreg' - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# kmc - -
- -* Version: 0.4-2 -* GitHub: https://github.com/yfyang86/kmc -* Source code: https://github.com/cran/kmc -* Date/Publication: 2022-11-22 08:30:02 UTC -* Number of recursive dependencies: 61 - -Run `revdepcheck::cloud_details(, "kmc")` for more info - -
- -## In both - -* checking whether package ‘kmc’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/kmc/new/kmc.Rcheck/00install.out’ for details. - ``` - -## Installation - -### Devel - -``` -* installing *source* package ‘kmc’ ... -** package ‘kmc’ successfully unpacked and MD5 sums checked -** using staged installation -** libs -using C compiler: ‘gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ -using C++ compiler: ‘g++ (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c RcppExport.cpp -o RcppExport.o -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c kmc.cpp -o kmc.o -gcc -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c kmc_init.c -o kmc_init.o -gcc -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c surv2.c -o surv2.o -g++ -std=gnu++17 -shared -L/opt/R/4.3.1/lib/R/lib -L/usr/local/lib -o kmc.so RcppExport.o kmc.o kmc_init.o surv2.o -L/opt/R/4.3.1/lib/R/lib -lR -installing to /tmp/workdir/kmc/new/kmc.Rcheck/00LOCK-kmc/00new/kmc/libs -** R -** byte-compile and prepare package for lazy loading -Error: package or namespace load failed for ‘emplik’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): - there is no package called ‘quantreg’ -Execution halted -ERROR: lazy loading failed for package ‘kmc’ -* removing ‘/tmp/workdir/kmc/new/kmc.Rcheck/kmc’ - - -``` -### CRAN - -``` -* installing *source* package ‘kmc’ ... -** package ‘kmc’ successfully unpacked and MD5 sums checked -** using staged installation -** libs -using C compiler: ‘gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ -using C++ compiler: ‘g++ (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c RcppExport.cpp -o RcppExport.o -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c kmc.cpp -o kmc.o -gcc -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c kmc_init.c -o kmc_init.o -gcc -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c surv2.c -o surv2.o -g++ -std=gnu++17 -shared -L/opt/R/4.3.1/lib/R/lib -L/usr/local/lib -o kmc.so RcppExport.o kmc.o kmc_init.o surv2.o -L/opt/R/4.3.1/lib/R/lib -lR -installing to /tmp/workdir/kmc/old/kmc.Rcheck/00LOCK-kmc/00new/kmc/libs -** R -** byte-compile and prepare package for lazy loading -Error: package or namespace load failed for ‘emplik’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): - there is no package called ‘quantreg’ -Execution halted -ERROR: lazy loading failed for package ‘kmc’ -* removing ‘/tmp/workdir/kmc/old/kmc.Rcheck/kmc’ - - -``` -# KMunicate - -
- -* Version: 0.2.5 -* GitHub: https://github.com/ellessenne/KMunicate-package -* Source code: https://github.com/cran/KMunicate -* Date/Publication: 2024-05-16 11:50:08 UTC -* Number of recursive dependencies: 172 - -Run `revdepcheck::cloud_details(, "KMunicate")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/KMunicate/new/KMunicate.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘KMunicate/DESCRIPTION’ ... OK -... ---- failed re-building ‘KMunicate.Rmd’ - -SUMMARY: processing the following file failed: - ‘KMunicate.Rmd’ - -Error: Vignette re-building failed. -Execution halted - -* DONE -Status: 3 ERRORs, 1 NOTE - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/KMunicate/old/KMunicate.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘KMunicate/DESCRIPTION’ ... OK -... -* checking for unstated dependencies in ‘tests’ ... OK -* checking tests ... OK - Running ‘testthat.R’ -* checking for unstated dependencies in vignettes ... OK -* checking package vignettes in ‘inst/doc’ ... OK -* checking running R code from vignettes ... OK - ‘KMunicate.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: OK - - - - - -``` -# L2E - -
- -* Version: 2.0 -* GitHub: NA -* Source code: https://github.com/cran/L2E -* Date/Publication: 2022-09-08 21:13:00 UTC -* Number of recursive dependencies: 65 - -Run `revdepcheck::cloud_details(, "L2E")` for more info - -
- -## In both - -* checking whether package ‘L2E’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/L2E/new/L2E.Rcheck/00install.out’ for details. - ``` - -## Installation - -### Devel - -``` -* installing *source* package ‘L2E’ ... -** package ‘L2E’ 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: package or namespace load failed for ‘osqp’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): - namespace ‘Matrix’ 1.5-4.1 is being loaded, but >= 1.6.1 is required -Execution halted -ERROR: lazy loading failed for package ‘L2E’ -* removing ‘/tmp/workdir/L2E/new/L2E.Rcheck/L2E’ - - -``` -### CRAN - -``` -* installing *source* package ‘L2E’ ... -** package ‘L2E’ 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: package or namespace load failed for ‘osqp’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): - namespace ‘Matrix’ 1.5-4.1 is being loaded, but >= 1.6.1 is required -Execution halted -ERROR: lazy loading failed for package ‘L2E’ -* removing ‘/tmp/workdir/L2E/old/L2E.Rcheck/L2E’ - - -``` -# Landmarking - -
- -* Version: 1.0.0 -* GitHub: https://github.com/isobelbarrott/Landmarking -* Source code: https://github.com/cran/Landmarking -* Date/Publication: 2022-02-15 20:00:07 UTC -* Number of recursive dependencies: 123 - -Run `revdepcheck::cloud_details(, "Landmarking")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/Landmarking/new/Landmarking.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘Landmarking/DESCRIPTION’ ... OK -... -* this is package ‘Landmarking’ version ‘1.0.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘riskRegression’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/Landmarking/old/Landmarking.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘Landmarking/DESCRIPTION’ ... OK -... -* this is package ‘Landmarking’ version ‘1.0.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘riskRegression’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# lavaSearch2 - -
- -* Version: 2.0.3 -* GitHub: https://github.com/bozenne/lavaSearch2 -* Source code: https://github.com/cran/lavaSearch2 -* Date/Publication: 2024-02-23 09:10:02 UTC -* Number of recursive dependencies: 142 - -Run `revdepcheck::cloud_details(, "lavaSearch2")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/lavaSearch2/new/lavaSearch2.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘lavaSearch2/DESCRIPTION’ ... OK -... -* checking for unstated dependencies in ‘tests’ ... OK -* checking tests ... OK - Running ‘test-all.R’ -* checking for unstated dependencies in vignettes ... OK -* checking package vignettes in ‘inst/doc’ ... OK -* checking running R code from vignettes ... NONE - ‘overview.pdf.asis’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: 1 NOTE - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/lavaSearch2/old/lavaSearch2.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘lavaSearch2/DESCRIPTION’ ... OK -... -* checking for unstated dependencies in ‘tests’ ... OK -* checking tests ... OK - Running ‘test-all.R’ -* checking for unstated dependencies in vignettes ... OK -* checking package vignettes in ‘inst/doc’ ... OK -* checking running R code from vignettes ... NONE - ‘overview.pdf.asis’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: 1 NOTE - - - - - -``` -# llbayesireg - -
- -* Version: 1.0.0 -* GitHub: NA -* Source code: https://github.com/cran/llbayesireg -* Date/Publication: 2019-04-04 16:20:03 UTC -* Number of recursive dependencies: 60 - -Run `revdepcheck::cloud_details(, "llbayesireg")` for more info - -
- -## In both - -* checking whether package ‘llbayesireg’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/llbayesireg/new/llbayesireg.Rcheck/00install.out’ for details. - ``` - -## Installation - -### Devel - -``` -* installing *source* package ‘llbayesireg’ ... -** package ‘llbayesireg’ successfully unpacked and MD5 sums checked +* installing *source* package ‘paths’ ... +** package ‘paths’ successfully unpacked and MD5 sums checked ** using staged installation ** R ** data -*** moving datasets to lazyload DB -** byte-compile and prepare package for lazy loading -Error in loadNamespace(i, c(lib.loc, .libPaths()), versionCheck = vI[[i]]) : - there is no package called ‘quantreg’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart -Execution halted -ERROR: lazy loading failed for package ‘llbayesireg’ -* removing ‘/tmp/workdir/llbayesireg/new/llbayesireg.Rcheck/llbayesireg’ - - -``` -### CRAN - -``` -* installing *source* package ‘llbayesireg’ ... -** package ‘llbayesireg’ successfully unpacked and MD5 sums checked -** using staged installation -** R -** data -*** moving datasets to lazyload DB -** byte-compile and prepare package for lazy loading -Error in loadNamespace(i, c(lib.loc, .libPaths()), versionCheck = vI[[i]]) : - there is no package called ‘quantreg’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart -Execution halted -ERROR: lazy loading failed for package ‘llbayesireg’ -* removing ‘/tmp/workdir/llbayesireg/old/llbayesireg.Rcheck/llbayesireg’ - - -``` -# LorenzRegression - -
- -* Version: 1.0.0 -* GitHub: NA -* Source code: https://github.com/cran/LorenzRegression -* Date/Publication: 2023-02-28 17:32:34 UTC -* Number of recursive dependencies: 63 - -Run `revdepcheck::cloud_details(, "LorenzRegression")` for more info - -
- -## In both - -* checking whether package ‘LorenzRegression’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/LorenzRegression/new/LorenzRegression.Rcheck/00install.out’ for details. - ``` - -## Installation - -### Devel - -``` -* installing *source* package ‘LorenzRegression’ ... -** package ‘LorenzRegression’ successfully unpacked and MD5 sums checked -** using staged installation -** libs -using C++ compiler: ‘g++ (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c GA_fitness.cpp -o GA_fitness.o -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c GA_meanrank.cpp -o GA_meanrank.o -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c PLR_derivative.cpp -o PLR_derivative.o -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c PLR_loss.cpp -o PLR_loss.o -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o -... -** data -*** moving datasets to lazyload DB -** 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 ‘quantreg’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart -Execution halted -ERROR: lazy loading failed for package ‘LorenzRegression’ -* removing ‘/tmp/workdir/LorenzRegression/new/LorenzRegression.Rcheck/LorenzRegression’ - - -``` -### CRAN - -``` -* installing *source* package ‘LorenzRegression’ ... -** package ‘LorenzRegression’ successfully unpacked and MD5 sums checked -** using staged installation -** libs -using C++ compiler: ‘g++ (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c GA_fitness.cpp -o GA_fitness.o -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c GA_meanrank.cpp -o GA_meanrank.o -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c PLR_derivative.cpp -o PLR_derivative.o -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c PLR_loss.cpp -o PLR_loss.o -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o -... -** data -*** moving datasets to lazyload DB -** 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 ‘quantreg’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart -Execution halted -ERROR: lazy loading failed for package ‘LorenzRegression’ -* removing ‘/tmp/workdir/LorenzRegression/old/LorenzRegression.Rcheck/LorenzRegression’ - - -``` -# lsirm12pl - -
- -* Version: 1.3.1 -* GitHub: NA -* Source code: https://github.com/cran/lsirm12pl -* Date/Publication: 2023-06-22 14:12:35 UTC -* Number of recursive dependencies: 123 - -Run `revdepcheck::cloud_details(, "lsirm12pl")` for more info - -
- -## In both - -* checking whether package ‘lsirm12pl’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/lsirm12pl/new/lsirm12pl.Rcheck/00install.out’ for details. - ``` - -## Installation - -### Devel - -``` -* installing *source* package ‘lsirm12pl’ ... -** package ‘lsirm12pl’ successfully unpacked and MD5 sums checked -** using staged installation -** libs -using C++ compiler: ‘g++ (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c log_likelihood.cpp -o log_likelihood.o -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c lsirm1pl.cpp -o lsirm1pl.o -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c lsirm1pl_fixed_gamma.cpp -o lsirm1pl_fixed_gamma.o -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c lsirm1pl_fixed_gamma_mar.cpp -o lsirm1pl_fixed_gamma_mar.o -... -** R -** data -*** moving datasets to lazyload DB -** byte-compile and prepare package for lazy loading -Error in loadNamespace(i, c(lib.loc, .libPaths()), versionCheck = vI[[i]]) : - there is no package called ‘quantreg’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart -Execution halted -ERROR: lazy loading failed for package ‘lsirm12pl’ -* removing ‘/tmp/workdir/lsirm12pl/new/lsirm12pl.Rcheck/lsirm12pl’ - - -``` -### CRAN - -``` -* installing *source* package ‘lsirm12pl’ ... -** package ‘lsirm12pl’ successfully unpacked and MD5 sums checked -** using staged installation -** libs -using C++ compiler: ‘g++ (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c log_likelihood.cpp -o log_likelihood.o -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c lsirm1pl.cpp -o lsirm1pl.o -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c lsirm1pl_fixed_gamma.cpp -o lsirm1pl_fixed_gamma.o -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c lsirm1pl_fixed_gamma_mar.cpp -o lsirm1pl_fixed_gamma_mar.o -... -** R -** data -*** moving datasets to lazyload DB -** byte-compile and prepare package for lazy loading -Error in loadNamespace(i, c(lib.loc, .libPaths()), versionCheck = vI[[i]]) : - there is no package called ‘quantreg’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart -Execution halted -ERROR: lazy loading failed for package ‘lsirm12pl’ -* removing ‘/tmp/workdir/lsirm12pl/old/lsirm12pl.Rcheck/lsirm12pl’ - - -``` -# MachineShop - -
- -* Version: 3.7.0 -* GitHub: https://github.com/brian-j-smith/MachineShop -* Source code: https://github.com/cran/MachineShop -* Date/Publication: 2023-09-18 14:00:02 UTC -* Number of recursive dependencies: 227 - -Run `revdepcheck::cloud_details(, "MachineShop")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/MachineShop/new/MachineShop.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘MachineShop/DESCRIPTION’ ... OK -... -* checking tests ... OK - Running ‘testthat.R’ -* checking for unstated dependencies in vignettes ... OK -* checking package vignettes in ‘inst/doc’ ... OK -* checking running R code from vignettes ... OK - ‘MLModels.Rmd’ using ‘UTF-8’... OK - ‘UserGuide.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: 3 NOTEs - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/MachineShop/old/MachineShop.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘MachineShop/DESCRIPTION’ ... OK -... -* checking tests ... OK - Running ‘testthat.R’ -* checking for unstated dependencies in vignettes ... OK -* checking package vignettes in ‘inst/doc’ ... OK -* checking running R code from vignettes ... OK - ‘MLModels.Rmd’ using ‘UTF-8’... OK - ‘UserGuide.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: 3 NOTEs - - - - - -``` -# marginaleffects - -
- -* Version: 0.20.1 -* GitHub: https://github.com/vincentarelbundock/marginaleffects -* Source code: https://github.com/cran/marginaleffects -* Date/Publication: 2024-05-08 12:10:03 UTC -* Number of recursive dependencies: 438 - -Run `revdepcheck::cloud_details(, "marginaleffects")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/marginaleffects/new/marginaleffects.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘marginaleffects/DESCRIPTION’ ... OK -... -* checking for unstated dependencies in examples ... OK -* checking line endings in C/C++/Fortran sources/headers ... OK -* checking compiled code ... OK -* checking examples ... OK -* checking for unstated dependencies in ‘tests’ ... OK -* checking tests ... OK - Running ‘spelling.R’ - Running ‘tinytest.R’ -* DONE -Status: 2 NOTEs - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/marginaleffects/old/marginaleffects.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘marginaleffects/DESCRIPTION’ ... OK -... -* checking for unstated dependencies in examples ... OK -* checking line endings in C/C++/Fortran sources/headers ... OK -* checking compiled code ... OK -* checking examples ... OK -* checking for unstated dependencies in ‘tests’ ... OK -* checking tests ... OK - Running ‘spelling.R’ - Running ‘tinytest.R’ -* DONE -Status: 2 NOTEs - - - - - -``` -# mbsts - -
- -* Version: 3.0 -* GitHub: NA -* Source code: https://github.com/cran/mbsts -* Date/Publication: 2023-01-07 01:10:02 UTC -* Number of recursive dependencies: 82 - -Run `revdepcheck::cloud_details(, "mbsts")` for more info - -
- -## In both - -* checking whether package ‘mbsts’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/mbsts/new/mbsts.Rcheck/00install.out’ for details. - ``` - -## Installation - -### Devel - -``` -* installing *source* package ‘mbsts’ ... -** package ‘mbsts’ successfully unpacked and MD5 sums checked -** using staged installation -** R -** 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 ‘quantreg’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart -Execution halted -ERROR: lazy loading failed for package ‘mbsts’ -* removing ‘/tmp/workdir/mbsts/new/mbsts.Rcheck/mbsts’ - - -``` -### CRAN - -``` -* installing *source* package ‘mbsts’ ... -** package ‘mbsts’ successfully unpacked and MD5 sums checked -** using staged installation -** R -** 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 ‘quantreg’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart -Execution halted -ERROR: lazy loading failed for package ‘mbsts’ -* removing ‘/tmp/workdir/mbsts/old/mbsts.Rcheck/mbsts’ - - -``` -# MetabolicSurv - -
- -* Version: 1.1.2 -* GitHub: https://github.com/OlajumokeEvangelina/MetabolicSurv -* Source code: https://github.com/cran/MetabolicSurv -* Date/Publication: 2021-06-11 08:30:02 UTC -* Number of recursive dependencies: 141 - -Run `revdepcheck::cloud_details(, "MetabolicSurv")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/MetabolicSurv/new/MetabolicSurv.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘MetabolicSurv/DESCRIPTION’ ... OK -... -* this is package ‘MetabolicSurv’ version ‘1.1.2’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘rms’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/MetabolicSurv/old/MetabolicSurv.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘MetabolicSurv/DESCRIPTION’ ... OK -... -* this is package ‘MetabolicSurv’ version ‘1.1.2’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘rms’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# MetaNet - -
- -* Version: 0.1.2 -* GitHub: https://github.com/Asa12138/MetaNet -* Source code: https://github.com/cran/MetaNet -* Date/Publication: 2024-03-25 20:40:07 UTC -* Number of recursive dependencies: 161 - -Run `revdepcheck::cloud_details(, "MetaNet")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/MetaNet/new/MetaNet.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘MetaNet/DESCRIPTION’ ... OK -... - 6. └─cli::cli_abort(...) - 7. └─rlang::abort(...) -Execution halted -* checking for unstated dependencies in vignettes ... OK -* checking package vignettes in ‘inst/doc’ ... OK -* checking running R code from vignettes ... OK - ‘MetaNet.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: 1 ERROR, 1 NOTE - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/MetaNet/old/MetaNet.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘MetaNet/DESCRIPTION’ ... OK -... -* checking installed files from ‘inst/doc’ ... OK -* checking files in ‘vignettes’ ... OK -* checking examples ... OK -* checking for unstated dependencies in vignettes ... OK -* checking package vignettes in ‘inst/doc’ ... OK -* checking running R code from vignettes ... OK - ‘MetaNet.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: 1 NOTE - - - - - -``` -# miWQS - -
- -* Version: 0.4.4 -* GitHub: https://github.com/phargarten2/miWQS -* Source code: https://github.com/cran/miWQS -* Date/Publication: 2021-04-02 21:50:02 UTC -* Number of recursive dependencies: 151 - -Run `revdepcheck::cloud_details(, "miWQS")` for more info - -
- -## In both - -* checking whether package ‘miWQS’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/miWQS/new/miWQS.Rcheck/00install.out’ for details. - ``` - -## Installation - -### Devel - -``` -* installing *source* package ‘miWQS’ ... -** package ‘miWQS’ 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(i, c(lib.loc, .libPaths()), versionCheck = vI[[i]]) : - there is no package called ‘quantreg’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart -Execution halted -ERROR: lazy loading failed for package ‘miWQS’ -* removing ‘/tmp/workdir/miWQS/new/miWQS.Rcheck/miWQS’ - - -``` -### CRAN - -``` -* installing *source* package ‘miWQS’ ... -** package ‘miWQS’ 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(i, c(lib.loc, .libPaths()), versionCheck = vI[[i]]) : - there is no package called ‘quantreg’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart -Execution halted -ERROR: lazy loading failed for package ‘miWQS’ -* removing ‘/tmp/workdir/miWQS/old/miWQS.Rcheck/miWQS’ - - -``` -# mlmts - -
- -* Version: 1.1.1 -* GitHub: NA -* Source code: https://github.com/cran/mlmts -* Date/Publication: 2023-01-22 21:30:02 UTC -* Number of recursive dependencies: 242 - -Run `revdepcheck::cloud_details(, "mlmts")` for more info - -
- -## In both - -* checking whether package ‘mlmts’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/mlmts/new/mlmts.Rcheck/00install.out’ for details. - ``` - -## Installation - -### Devel - -``` -* installing *source* package ‘mlmts’ ... -** package ‘mlmts’ 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 : package or namespace load failed for ‘quantspec’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): - there is no package called ‘quantreg’ -Error: unable to load R code in package ‘mlmts’ -Execution halted -ERROR: lazy loading failed for package ‘mlmts’ -* removing ‘/tmp/workdir/mlmts/new/mlmts.Rcheck/mlmts’ - - -``` -### CRAN - -``` -* installing *source* package ‘mlmts’ ... -** package ‘mlmts’ 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 : package or namespace load failed for ‘quantspec’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): - there is no package called ‘quantreg’ -Error: unable to load R code in package ‘mlmts’ -Execution halted -ERROR: lazy loading failed for package ‘mlmts’ -* removing ‘/tmp/workdir/mlmts/old/mlmts.Rcheck/mlmts’ - - -``` -# mlr - -
- -* Version: 2.19.1 -* GitHub: https://github.com/mlr-org/mlr -* Source code: https://github.com/cran/mlr -* Date/Publication: 2022-09-29 13:30:14 UTC -* Number of recursive dependencies: 369 - -Run `revdepcheck::cloud_details(, "mlr")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/mlr/new/mlr.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘mlr/DESCRIPTION’ ... OK -... -* checking for unstated dependencies in ‘tests’ ... OK -* checking tests ... OK - Running ‘testthat.R’ -* checking for unstated dependencies in vignettes ... OK -* checking package vignettes in ‘inst/doc’ ... OK -* checking running R code from vignettes ... OK - ‘mlr.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: 1 ERROR, 3 NOTEs - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/mlr/old/mlr.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘mlr/DESCRIPTION’ ... OK -... -* checking for unstated dependencies in ‘tests’ ... OK -* checking tests ... OK - Running ‘testthat.R’ -* checking for unstated dependencies in vignettes ... OK -* checking package vignettes in ‘inst/doc’ ... OK -* checking running R code from vignettes ... OK - ‘mlr.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: 1 ERROR, 3 NOTEs - - - - - -``` -# MOSS - -
- -* Version: 0.2.2 -* GitHub: https://github.com/agugonrey/MOSS -* Source code: https://github.com/cran/MOSS -* Date/Publication: 2022-03-25 15:50:05 UTC -* Number of recursive dependencies: 183 - -Run `revdepcheck::cloud_details(, "MOSS")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/MOSS/new/MOSS.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘MOSS/DESCRIPTION’ ... OK -... ---- failed re-building ‘MOSS_working_example.Rmd’ - -SUMMARY: processing the following file failed: - ‘MOSS_working_example.Rmd’ - -Error: Vignette re-building failed. -Execution halted - -* DONE -Status: 2 ERRORs, 2 NOTEs - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/MOSS/old/MOSS.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘MOSS/DESCRIPTION’ ... OK -... ---- failed re-building ‘MOSS_working_example.Rmd’ - -SUMMARY: processing the following file failed: - ‘MOSS_working_example.Rmd’ - -Error: Vignette re-building failed. -Execution halted - -* DONE -Status: 2 ERRORs, 2 NOTEs - - - - - -``` -# mrbayes - -
- -* Version: 0.5.1 -* GitHub: https://github.com/okezie94/mrbayes -* Source code: https://github.com/cran/mrbayes -* Date/Publication: 2021-10-02 14:50:02 UTC -* Number of recursive dependencies: 189 - -Run `revdepcheck::cloud_details(, "mrbayes")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/mrbayes/new/mrbayes.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘mrbayes/DESCRIPTION’ ... OK -... -GNU make is a SystemRequirements. -* checking for portable use of $(BLAS_LIBS) and $(LAPACK_LIBS) ... OK -* checking use of PKG_*FLAGS in Makefiles ... OK -* checking compiled code ... OK -* checking examples ... OK -* checking for unstated dependencies in ‘tests’ ... OK -* checking tests ... OK - Running ‘testthat.R’ -* DONE -Status: 5 NOTEs - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/mrbayes/old/mrbayes.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘mrbayes/DESCRIPTION’ ... OK -... -GNU make is a SystemRequirements. -* checking for portable use of $(BLAS_LIBS) and $(LAPACK_LIBS) ... OK -* checking use of PKG_*FLAGS in Makefiles ... OK -* checking compiled code ... OK -* checking examples ... OK -* checking for unstated dependencies in ‘tests’ ... OK -* checking tests ... OK - Running ‘testthat.R’ -* DONE -Status: 5 NOTEs - - - - - -``` -# mstate - -
- -* Version: 0.3.2 -* GitHub: https://github.com/hputter/mstate -* Source code: https://github.com/cran/mstate -* Date/Publication: 2021-11-08 11:50:02 UTC -* Number of recursive dependencies: 114 - -Run `revdepcheck::cloud_details(, "mstate")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/mstate/new/mstate.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘mstate/DESCRIPTION’ ... OK -... ---- failed re-building ‘Tutorial.Rnw’ - -SUMMARY: processing the following files failed: - ‘visuals_demo.Rmd’ ‘Tutorial.Rnw’ - -Error: Vignette re-building failed. -Execution halted - -* DONE -Status: 2 ERRORs, 1 NOTE - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/mstate/old/mstate.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘mstate/DESCRIPTION’ ... OK -... ---- failed re-building ‘Tutorial.Rnw’ - -SUMMARY: processing the following file failed: - ‘Tutorial.Rnw’ - -Error: Vignette re-building failed. -Execution halted - -* DONE -Status: 1 NOTE - - - - - -``` -# Multiaovbay - -
- -* Version: 0.1.0 -* GitHub: NA -* Source code: https://github.com/cran/Multiaovbay -* Date/Publication: 2023-03-17 17:20:02 UTC -* Number of recursive dependencies: 160 - -Run `revdepcheck::cloud_details(, "Multiaovbay")` for more info - -
- -## In both - -* checking whether package ‘Multiaovbay’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/Multiaovbay/new/Multiaovbay.Rcheck/00install.out’ for details. - ``` - -## Installation - -### Devel - -``` -* installing *source* package ‘Multiaovbay’ ... -** package ‘Multiaovbay’ successfully unpacked and MD5 sums checked -** using staged installation -** R -** byte-compile and prepare package for lazy loading -Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - namespace ‘Matrix’ 1.5-4.1 is being loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘Multiaovbay’ -* removing ‘/tmp/workdir/Multiaovbay/new/Multiaovbay.Rcheck/Multiaovbay’ - - -``` -### CRAN - -``` -* installing *source* package ‘Multiaovbay’ ... -** package ‘Multiaovbay’ successfully unpacked and MD5 sums checked -** using staged installation -** R -** byte-compile and prepare package for lazy loading -Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - namespace ‘Matrix’ 1.5-4.1 is being loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘Multiaovbay’ -* removing ‘/tmp/workdir/Multiaovbay/old/Multiaovbay.Rcheck/Multiaovbay’ - - -``` -# multilevelTools - -
- -* Version: 0.1.1 -* GitHub: https://github.com/JWiley/multilevelTools -* Source code: https://github.com/cran/multilevelTools -* Date/Publication: 2020-03-04 09:50:02 UTC -* Number of recursive dependencies: 163 - -Run `revdepcheck::cloud_details(, "multilevelTools")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/multilevelTools/new/multilevelTools.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘multilevelTools/DESCRIPTION’ ... OK -... -* checking if there is a namespace ... OK -* checking for executable files ... OK -* checking for hidden files and directories ... OK -* checking for portable file names ... OK -* checking for sufficient/correct file permissions ... OK -* checking whether package ‘multilevelTools’ can be installed ... ERROR -Installation failed. -See ‘/tmp/workdir/multilevelTools/new/multilevelTools.Rcheck/00install.out’ for details. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/multilevelTools/old/multilevelTools.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘multilevelTools/DESCRIPTION’ ... OK -... -* checking if there is a namespace ... OK -* checking for executable files ... OK -* checking for hidden files and directories ... OK -* checking for portable file names ... OK -* checking for sufficient/correct file permissions ... OK -* checking whether package ‘multilevelTools’ can be installed ... ERROR -Installation failed. -See ‘/tmp/workdir/multilevelTools/old/multilevelTools.Rcheck/00install.out’ for details. -* DONE -Status: 1 ERROR - - - - - -``` -# multipleOutcomes - -
- -* Version: 0.4 -* GitHub: NA -* Source code: https://github.com/cran/multipleOutcomes -* Date/Publication: 2024-05-30 15:00:03 UTC -* Number of recursive dependencies: 182 - -Run `revdepcheck::cloud_details(, "multipleOutcomes")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/multipleOutcomes/new/multipleOutcomes.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘multipleOutcomes/DESCRIPTION’ ... OK -... -* checking installed files from ‘inst/doc’ ... OK -* checking files in ‘vignettes’ ... OK -* checking examples ... OK -* checking for unstated dependencies in vignettes ... OK -* checking package vignettes in ‘inst/doc’ ... OK -* checking running R code from vignettes ... OK - ‘test.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: OK - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/multipleOutcomes/old/multipleOutcomes.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘multipleOutcomes/DESCRIPTION’ ... OK -... -* checking installed files from ‘inst/doc’ ... OK -* checking files in ‘vignettes’ ... OK -* checking examples ... OK -* checking for unstated dependencies in vignettes ... OK -* checking package vignettes in ‘inst/doc’ ... OK -* checking running R code from vignettes ... OK - ‘test.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: OK - - - - - -``` -# netcmc - -
- -* Version: 1.0.2 -* GitHub: NA -* Source code: https://github.com/cran/netcmc -* Date/Publication: 2022-11-08 22:30:15 UTC -* Number of recursive dependencies: 61 - -Run `revdepcheck::cloud_details(, "netcmc")` for more info - -
- -## In both - -* checking whether package ‘netcmc’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/netcmc/new/netcmc.Rcheck/00install.out’ for details. - ``` - -## Installation - -### Devel - -``` -* installing *source* package ‘netcmc’ ... -** package ‘netcmc’ successfully unpacked and MD5 sums checked -** using staged installation -** libs -using C++ compiler: ‘g++ (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ -using C++11 -g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppProgress/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o -g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppProgress/include' -I/usr/local/include -fpic -g -O2 -c choleskyDecompositionRcppConversion.cpp -o choleskyDecompositionRcppConversion.o -g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppProgress/include' -I/usr/local/include -fpic -g -O2 -c doubleMatrixMultiplicationRcpp.cpp -o doubleMatrixMultiplicationRcpp.o -g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppProgress/include' -I/usr/local/include -fpic -g -O2 -c doubleVectorMultiplicationRcpp.cpp -o doubleVectorMultiplicationRcpp.o -... -g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppProgress/include' -I/usr/local/include -fpic -g -O2 -c vectorVectorTransposeMultiplicationRcpp.cpp -o vectorVectorTransposeMultiplicationRcpp.o -g++ -std=gnu++11 -shared -L/opt/R/4.3.1/lib/R/lib -L/usr/local/lib -o netcmc.so RcppExports.o choleskyDecompositionRcppConversion.o doubleMatrixMultiplicationRcpp.o doubleVectorMultiplicationRcpp.o eigenValuesRcppConversion.o getDiagonalMatrix.o getExp.o getExpDividedByOnePlusExp.o getMeanCenteredRandomEffects.o getMultivariateBinomialNetworkLerouxDIC.o getMultivariateBinomialNetworkLerouxFittedValuesAndLikelihoodForDICEveryIteration.o getMultivariateGaussianNetworkLerouxDIC.o getMultivariateGaussianNetworkLerouxFittedValuesAndLikelihoodForDICEveryIteration.o getMultivariatePoissonNetworkLerouxDIC.o getMultivariatePoissonNetworkLerouxFittedValuesAndLikelihoodForDICEveryIteration.o getNonZeroEntries.o getSubvector.o getSubvectorIndecies.o getSumExpNetwork.o getSumExpNetworkIndecies.o getSumExpNetworkLeroux.o getSumExpNetworkLerouxIndecies.o getSumLogExp.o getSumLogExpIndecies.o getSumVector.o getTripletForm.o getUnivariateBinomialNetworkLerouxDIC.o getUnivariateBinomialNetworkLerouxFittedValuesAndLikelihoodForDICEveryIteration.o getUnivariateGaussianNetworkLerouxDIC.o getUnivariateGaussianNetworkLerouxFittedValuesAndLikelihoodForDICEveryIteration.o getUnivariatePoissonNetworkDIC.o getUnivariatePoissonNetworkFittedValuesAndLikelihoodForDICEveryIteration.o getUnivariatePoissonNetworkLerouxDIC.o getUnivariatePoissonNetworkLerouxFittedValuesAndLikelihoodForDICEveryIteration.o getVectorMean.o matrixInverseRcppConversion.o matrixMatrixAdditionRcpp.o matrixMatrixSubtractionRcpp.o matrixVectorMultiplicationRcpp.o multivariateBinomialNetworkLerouxAllUpdate.o multivariateBinomialNetworkLerouxBetaUpdate.o multivariateBinomialNetworkLerouxRhoUpdate.o multivariateBinomialNetworkLerouxSingleUpdate.o multivariateBinomialNetworkLerouxSpatialRandomEffectsUpdate.o multivariateBinomialNetworkLerouxTauSquaredUpdate.o multivariateBinomialNetworkLerouxURandomEffectsUpdate.o multivariateBinomialNetworkLerouxVRandomEffectsUpdate.o multivariateBinomialNetworkLerouxVarianceCovarianceUUpdate.o multivariateBinomialNetworkRandAllUpdate.o multivariateBinomialNetworkRandSingleUpdate.o multivariateGaussianNetworkLerouxAllMHUpdate.o multivariateGaussianNetworkLerouxBetaUpdate.o multivariateGaussianNetworkLerouxRhoUpdate.o multivariateGaussianNetworkLerouxSigmaSquaredEUpdate.o multivariateGaussianNetworkLerouxSingleMHUpdate.o multivariateGaussianNetworkLerouxSpatialRandomEffectsMHUpdate.o multivariateGaussianNetworkLerouxTauSquaredUpdate.o multivariateGaussianNetworkLerouxURandomEffectsUpdate.o multivariateGaussianNetworkLerouxVarianceCovarianceUUpdate.o multivariateGaussianNetworkRandAllUpdate.o multivariateGaussianNetworkRandSingleUpdate.o multivariateGaussianNetworkRandVRandomEffectsUpdate.o multivariatePoissonNetworkLerouxAllUpdate.o multivariatePoissonNetworkLerouxBetaUpdate.o multivariatePoissonNetworkLerouxRhoUpdate.o multivariatePoissonNetworkLerouxSingleUpdate.o multivariatePoissonNetworkLerouxSpatialRandomEffectsUpdate.o multivariatePoissonNetworkLerouxTauSquaredUpdate.o multivariatePoissonNetworkLerouxURandomEffectsUpdate.o multivariatePoissonNetworkLerouxVRandomEffectsUpdate.o multivariatePoissonNetworkLerouxVarianceCovarianceUUpdate.o multivariatePoissonNetworkRandAllUpdate.o multivariatePoissonNetworkRandSingleUpdate.o sumMatrix.o univariateBinomialNetworkLerouxAllUpdate.o univariateBinomialNetworkLerouxBetaUpdate.o univariateBinomialNetworkLerouxRhoUpdate.o univariateBinomialNetworkLerouxSigmaSquaredUpdate.o univariateBinomialNetworkLerouxSingleUpdate.o univariateBinomialNetworkLerouxSpatialRandomEffectsUpdate.o univariateBinomialNetworkLerouxTauSquaredUpdate.o univariateBinomialNetworkLerouxURandomEffectsUpdate.o univariateGaussianNetworkLerouxAllMHUpdate.o univariateGaussianNetworkLerouxBetaUpdate.o univariateGaussianNetworkLerouxRhoUpdate.o univariateGaussianNetworkLerouxSigmaSquaredEUpdate.o univariateGaussianNetworkLerouxSigmaSquaredUUpdate.o univariateGaussianNetworkLerouxSingleMHUpdate.o univariateGaussianNetworkLerouxSpatialRandomEffectsMHUpdate.o univariateGaussianNetworkLerouxTauSquaredUpdate.o univariateGaussianNetworkLerouxURandomEffectsUpdate.o univariatePoissonNetworkLerouxAllUpdate.o univariatePoissonNetworkLerouxBetaUpdate.o univariatePoissonNetworkLerouxRhoUpdate.o univariatePoissonNetworkLerouxSigmaSquaredUpdate.o univariatePoissonNetworkLerouxSingleUpdate.o univariatePoissonNetworkLerouxSpatialRandomEffectsUpdate.o univariatePoissonNetworkLerouxTauSquaredUpdate.o univariatePoissonNetworkLerouxURandomEffectsUpdate.o vectorTransposeVectorMultiplicationRcpp.o vectorVectorTransposeMultiplicationRcpp.o -llapack -lblas -lgfortran -lm -lquadmath -L/opt/R/4.3.1/lib/R/lib -lR -installing to /tmp/workdir/netcmc/new/netcmc.Rcheck/00LOCK-netcmc/00new/netcmc/libs -** R -** byte-compile and prepare package for lazy loading -Error: package or namespace load failed for ‘MCMCpack’ in loadNamespace(i, c(lib.loc, .libPaths()), versionCheck = vI[[i]]): - there is no package called ‘quantreg’ -Execution halted -ERROR: lazy loading failed for package ‘netcmc’ -* removing ‘/tmp/workdir/netcmc/new/netcmc.Rcheck/netcmc’ - - -``` -### CRAN - -``` -* installing *source* package ‘netcmc’ ... -** package ‘netcmc’ successfully unpacked and MD5 sums checked -** using staged installation -** libs -using C++ compiler: ‘g++ (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ -using C++11 -g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppProgress/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o -g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppProgress/include' -I/usr/local/include -fpic -g -O2 -c choleskyDecompositionRcppConversion.cpp -o choleskyDecompositionRcppConversion.o -g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppProgress/include' -I/usr/local/include -fpic -g -O2 -c doubleMatrixMultiplicationRcpp.cpp -o doubleMatrixMultiplicationRcpp.o -g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppProgress/include' -I/usr/local/include -fpic -g -O2 -c doubleVectorMultiplicationRcpp.cpp -o doubleVectorMultiplicationRcpp.o -... -g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppProgress/include' -I/usr/local/include -fpic -g -O2 -c vectorVectorTransposeMultiplicationRcpp.cpp -o vectorVectorTransposeMultiplicationRcpp.o -g++ -std=gnu++11 -shared -L/opt/R/4.3.1/lib/R/lib -L/usr/local/lib -o netcmc.so RcppExports.o choleskyDecompositionRcppConversion.o doubleMatrixMultiplicationRcpp.o doubleVectorMultiplicationRcpp.o eigenValuesRcppConversion.o getDiagonalMatrix.o getExp.o getExpDividedByOnePlusExp.o getMeanCenteredRandomEffects.o getMultivariateBinomialNetworkLerouxDIC.o getMultivariateBinomialNetworkLerouxFittedValuesAndLikelihoodForDICEveryIteration.o getMultivariateGaussianNetworkLerouxDIC.o getMultivariateGaussianNetworkLerouxFittedValuesAndLikelihoodForDICEveryIteration.o getMultivariatePoissonNetworkLerouxDIC.o getMultivariatePoissonNetworkLerouxFittedValuesAndLikelihoodForDICEveryIteration.o getNonZeroEntries.o getSubvector.o getSubvectorIndecies.o getSumExpNetwork.o getSumExpNetworkIndecies.o getSumExpNetworkLeroux.o getSumExpNetworkLerouxIndecies.o getSumLogExp.o getSumLogExpIndecies.o getSumVector.o getTripletForm.o getUnivariateBinomialNetworkLerouxDIC.o getUnivariateBinomialNetworkLerouxFittedValuesAndLikelihoodForDICEveryIteration.o getUnivariateGaussianNetworkLerouxDIC.o getUnivariateGaussianNetworkLerouxFittedValuesAndLikelihoodForDICEveryIteration.o getUnivariatePoissonNetworkDIC.o getUnivariatePoissonNetworkFittedValuesAndLikelihoodForDICEveryIteration.o getUnivariatePoissonNetworkLerouxDIC.o getUnivariatePoissonNetworkLerouxFittedValuesAndLikelihoodForDICEveryIteration.o getVectorMean.o matrixInverseRcppConversion.o matrixMatrixAdditionRcpp.o matrixMatrixSubtractionRcpp.o matrixVectorMultiplicationRcpp.o multivariateBinomialNetworkLerouxAllUpdate.o multivariateBinomialNetworkLerouxBetaUpdate.o multivariateBinomialNetworkLerouxRhoUpdate.o multivariateBinomialNetworkLerouxSingleUpdate.o multivariateBinomialNetworkLerouxSpatialRandomEffectsUpdate.o multivariateBinomialNetworkLerouxTauSquaredUpdate.o multivariateBinomialNetworkLerouxURandomEffectsUpdate.o multivariateBinomialNetworkLerouxVRandomEffectsUpdate.o multivariateBinomialNetworkLerouxVarianceCovarianceUUpdate.o multivariateBinomialNetworkRandAllUpdate.o multivariateBinomialNetworkRandSingleUpdate.o multivariateGaussianNetworkLerouxAllMHUpdate.o multivariateGaussianNetworkLerouxBetaUpdate.o multivariateGaussianNetworkLerouxRhoUpdate.o multivariateGaussianNetworkLerouxSigmaSquaredEUpdate.o multivariateGaussianNetworkLerouxSingleMHUpdate.o multivariateGaussianNetworkLerouxSpatialRandomEffectsMHUpdate.o multivariateGaussianNetworkLerouxTauSquaredUpdate.o multivariateGaussianNetworkLerouxURandomEffectsUpdate.o multivariateGaussianNetworkLerouxVarianceCovarianceUUpdate.o multivariateGaussianNetworkRandAllUpdate.o multivariateGaussianNetworkRandSingleUpdate.o multivariateGaussianNetworkRandVRandomEffectsUpdate.o multivariatePoissonNetworkLerouxAllUpdate.o multivariatePoissonNetworkLerouxBetaUpdate.o multivariatePoissonNetworkLerouxRhoUpdate.o multivariatePoissonNetworkLerouxSingleUpdate.o multivariatePoissonNetworkLerouxSpatialRandomEffectsUpdate.o multivariatePoissonNetworkLerouxTauSquaredUpdate.o multivariatePoissonNetworkLerouxURandomEffectsUpdate.o multivariatePoissonNetworkLerouxVRandomEffectsUpdate.o multivariatePoissonNetworkLerouxVarianceCovarianceUUpdate.o multivariatePoissonNetworkRandAllUpdate.o multivariatePoissonNetworkRandSingleUpdate.o sumMatrix.o univariateBinomialNetworkLerouxAllUpdate.o univariateBinomialNetworkLerouxBetaUpdate.o univariateBinomialNetworkLerouxRhoUpdate.o univariateBinomialNetworkLerouxSigmaSquaredUpdate.o univariateBinomialNetworkLerouxSingleUpdate.o univariateBinomialNetworkLerouxSpatialRandomEffectsUpdate.o univariateBinomialNetworkLerouxTauSquaredUpdate.o univariateBinomialNetworkLerouxURandomEffectsUpdate.o univariateGaussianNetworkLerouxAllMHUpdate.o univariateGaussianNetworkLerouxBetaUpdate.o univariateGaussianNetworkLerouxRhoUpdate.o univariateGaussianNetworkLerouxSigmaSquaredEUpdate.o univariateGaussianNetworkLerouxSigmaSquaredUUpdate.o univariateGaussianNetworkLerouxSingleMHUpdate.o univariateGaussianNetworkLerouxSpatialRandomEffectsMHUpdate.o univariateGaussianNetworkLerouxTauSquaredUpdate.o univariateGaussianNetworkLerouxURandomEffectsUpdate.o univariatePoissonNetworkLerouxAllUpdate.o univariatePoissonNetworkLerouxBetaUpdate.o univariatePoissonNetworkLerouxRhoUpdate.o univariatePoissonNetworkLerouxSigmaSquaredUpdate.o univariatePoissonNetworkLerouxSingleUpdate.o univariatePoissonNetworkLerouxSpatialRandomEffectsUpdate.o univariatePoissonNetworkLerouxTauSquaredUpdate.o univariatePoissonNetworkLerouxURandomEffectsUpdate.o vectorTransposeVectorMultiplicationRcpp.o vectorVectorTransposeMultiplicationRcpp.o -llapack -lblas -lgfortran -lm -lquadmath -L/opt/R/4.3.1/lib/R/lib -lR -installing to /tmp/workdir/netcmc/old/netcmc.Rcheck/00LOCK-netcmc/00new/netcmc/libs -** R -** byte-compile and prepare package for lazy loading -Error: package or namespace load failed for ‘MCMCpack’ in loadNamespace(i, c(lib.loc, .libPaths()), versionCheck = vI[[i]]): - there is no package called ‘quantreg’ -Execution halted -ERROR: lazy loading failed for package ‘netcmc’ -* removing ‘/tmp/workdir/netcmc/old/netcmc.Rcheck/netcmc’ - - -``` -# NetworkChange - -
- -* Version: 0.8 -* GitHub: https://github.com/jongheepark/NetworkChange -* Source code: https://github.com/cran/NetworkChange -* Date/Publication: 2022-03-04 07:30:02 UTC -* Number of recursive dependencies: 131 - -Run `revdepcheck::cloud_details(, "NetworkChange")` for more info - -
- -## In both - -* checking whether package ‘NetworkChange’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/NetworkChange/new/NetworkChange.Rcheck/00install.out’ for details. - ``` - -## Installation - -### Devel - -``` -* installing *source* package ‘NetworkChange’ ... -** package ‘NetworkChange’ successfully unpacked and MD5 sums checked -** using staged installation -** R -** data -** byte-compile and prepare package for lazy loading -Error: package or namespace load failed for ‘MCMCpack’ in loadNamespace(i, c(lib.loc, .libPaths()), versionCheck = vI[[i]]): - there is no package called ‘quantreg’ -Execution halted -ERROR: lazy loading failed for package ‘NetworkChange’ -* removing ‘/tmp/workdir/NetworkChange/new/NetworkChange.Rcheck/NetworkChange’ - - -``` -### CRAN - -``` -* installing *source* package ‘NetworkChange’ ... -** package ‘NetworkChange’ successfully unpacked and MD5 sums checked -** using staged installation -** R -** data -** byte-compile and prepare package for lazy loading -Error: package or namespace load failed for ‘MCMCpack’ in loadNamespace(i, c(lib.loc, .libPaths()), versionCheck = vI[[i]]): - there is no package called ‘quantreg’ -Execution halted -ERROR: lazy loading failed for package ‘NetworkChange’ -* removing ‘/tmp/workdir/NetworkChange/old/NetworkChange.Rcheck/NetworkChange’ - - -``` -# neutralitytestr - -
- -* Version: 0.0.3 -* GitHub: https://github.com/marcjwilliams1/neutralitytestr -* Source code: https://github.com/cran/neutralitytestr -* Date/Publication: 2021-02-16 18:00:06 UTC -* Number of recursive dependencies: 95 - -Run `revdepcheck::cloud_details(, "neutralitytestr")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/neutralitytestr/new/neutralitytestr.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘neutralitytestr/DESCRIPTION’ ... OK -... -* this is package ‘neutralitytestr’ version ‘0.0.3’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘ggpmisc’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/neutralitytestr/old/neutralitytestr.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘neutralitytestr/DESCRIPTION’ ... OK -... -* this is package ‘neutralitytestr’ version ‘0.0.3’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘ggpmisc’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# NMADiagT - -
- -* Version: 0.1.2 -* GitHub: NA -* Source code: https://github.com/cran/NMADiagT -* Date/Publication: 2020-02-26 07:00:02 UTC -* Number of recursive dependencies: 79 - -Run `revdepcheck::cloud_details(, "NMADiagT")` for more info - -
- -## In both - -* checking whether package ‘NMADiagT’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/NMADiagT/new/NMADiagT.Rcheck/00install.out’ for details. - ``` - -## Installation - -### Devel - -``` -* installing *source* package ‘NMADiagT’ ... -** package ‘NMADiagT’ successfully unpacked and MD5 sums checked -** using staged installation -** R -** 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 ‘quantreg’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart -Execution halted -ERROR: lazy loading failed for package ‘NMADiagT’ -* removing ‘/tmp/workdir/NMADiagT/new/NMADiagT.Rcheck/NMADiagT’ - - -``` -### CRAN - -``` -* installing *source* package ‘NMADiagT’ ... -** package ‘NMADiagT’ successfully unpacked and MD5 sums checked -** using staged installation -** R -** 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 ‘quantreg’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart -Execution halted -ERROR: lazy loading failed for package ‘NMADiagT’ -* removing ‘/tmp/workdir/NMADiagT/old/NMADiagT.Rcheck/NMADiagT’ - - -``` -# obliqueRSF - -
- -* Version: 0.1.2 -* GitHub: NA -* Source code: https://github.com/cran/obliqueRSF -* Date/Publication: 2022-08-28 20:50:02 UTC -* Number of recursive dependencies: 117 - -Run `revdepcheck::cloud_details(, "obliqueRSF")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/obliqueRSF/new/obliqueRSF.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘obliqueRSF/DESCRIPTION’ ... OK -... -* checking for missing documentation entries ... OK -* checking for code/documentation mismatches ... OK -* checking Rd \usage sections ... OK -* checking Rd contents ... OK -* checking for unstated dependencies in examples ... OK -* checking line endings in C/C++/Fortran sources/headers ... OK -* checking compiled code ... OK -* checking examples ... OK -* DONE -Status: OK - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/obliqueRSF/old/obliqueRSF.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘obliqueRSF/DESCRIPTION’ ... OK -... -* checking for missing documentation entries ... OK -* checking for code/documentation mismatches ... OK -* checking Rd \usage sections ... OK -* checking Rd contents ... OK -* checking for unstated dependencies in examples ... OK -* checking line endings in C/C++/Fortran sources/headers ... OK -* checking compiled code ... OK -* checking examples ... OK -* DONE -Status: OK - - - - - -``` -# optweight - -
- -* Version: 0.2.5 -* GitHub: NA -* Source code: https://github.com/cran/optweight -* Date/Publication: 2019-09-16 15:40:02 UTC -* Number of recursive dependencies: 55 - -Run `revdepcheck::cloud_details(, "optweight")` for more info - -
- -## In both - -* checking whether package ‘optweight’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/optweight/new/optweight.Rcheck/00install.out’ for details. - ``` - -## Installation - -### Devel - -``` -* installing *source* package ‘optweight’ ... -** package ‘optweight’ successfully unpacked and MD5 sums checked -** using staged installation -** R -** byte-compile and prepare package for lazy loading -Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.1 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘optweight’ -* removing ‘/tmp/workdir/optweight/new/optweight.Rcheck/optweight’ - - -``` -### CRAN - -``` -* installing *source* package ‘optweight’ ... -** package ‘optweight’ successfully unpacked and MD5 sums checked -** using staged installation -** R -** byte-compile and prepare package for lazy loading -Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.1 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘optweight’ -* removing ‘/tmp/workdir/optweight/old/optweight.Rcheck/optweight’ - - -``` -# ormPlot - -
- -* Version: 0.3.6 -* GitHub: NA -* Source code: https://github.com/cran/ormPlot -* Date/Publication: 2023-09-13 14:40:02 UTC -* Number of recursive dependencies: 96 - -Run `revdepcheck::cloud_details(, "ormPlot")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/ormPlot/new/ormPlot.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘ormPlot/DESCRIPTION’ ... OK -... -* this is package ‘ormPlot’ version ‘0.3.6’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘rms’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/ormPlot/old/ormPlot.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘ormPlot/DESCRIPTION’ ... OK -... -* this is package ‘ormPlot’ version ‘0.3.6’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘rms’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# OVtool - -
- -* Version: 1.0.3 -* GitHub: NA -* Source code: https://github.com/cran/OVtool -* Date/Publication: 2021-11-02 08:10:07 UTC -* Number of recursive dependencies: 158 - -Run `revdepcheck::cloud_details(, "OVtool")` for more info - -
- -## In both - -* checking whether package ‘OVtool’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/OVtool/new/OVtool.Rcheck/00install.out’ for details. - ``` - -## Installation - -### Devel - -``` -* installing *source* package ‘OVtool’ ... -** package ‘OVtool’ 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: package or namespace load failed for ‘twang’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Execution halted -ERROR: lazy loading failed for package ‘OVtool’ -* removing ‘/tmp/workdir/OVtool/new/OVtool.Rcheck/OVtool’ - - -``` -### CRAN - -``` -* installing *source* package ‘OVtool’ ... -** package ‘OVtool’ 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: package or namespace load failed for ‘twang’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Execution halted -ERROR: lazy loading failed for package ‘OVtool’ -* removing ‘/tmp/workdir/OVtool/old/OVtool.Rcheck/OVtool’ - - -``` -# pagoda2 - -
- -* Version: 1.0.12 -* GitHub: https://github.com/kharchenkolab/pagoda2 -* Source code: https://github.com/cran/pagoda2 -* Date/Publication: 2024-02-27 00:50:02 UTC -* Number of recursive dependencies: 163 - -Run `revdepcheck::cloud_details(, "pagoda2")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/pagoda2/new/pagoda2.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘pagoda2/DESCRIPTION’ ... OK -... -* checking for GNU extensions in Makefiles ... OK -* checking for portable use of $(BLAS_LIBS) and $(LAPACK_LIBS) ... OK -* checking use of PKG_*FLAGS in Makefiles ... OK -* checking compiled code ... OK -* checking examples ... OK -* checking for unstated dependencies in ‘tests’ ... OK -* checking tests ... OK - Running ‘testthat.R’ -* DONE -Status: 2 NOTEs - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/pagoda2/old/pagoda2.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘pagoda2/DESCRIPTION’ ... OK -... -* checking for GNU extensions in Makefiles ... OK -* checking for portable use of $(BLAS_LIBS) and $(LAPACK_LIBS) ... OK -* checking use of PKG_*FLAGS in Makefiles ... OK -* checking compiled code ... OK -* checking examples ... OK -* checking for unstated dependencies in ‘tests’ ... OK -* checking tests ... OK - Running ‘testthat.R’ -* DONE -Status: 2 NOTEs - - - - - -``` -# pammtools - -
- -* Version: 0.5.93 -* GitHub: https://github.com/adibender/pammtools -* Source code: https://github.com/cran/pammtools -* Date/Publication: 2024-02-25 10:10:02 UTC -* Number of recursive dependencies: 125 - -Run `revdepcheck::cloud_details(, "pammtools")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/pammtools/new/pammtools.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘pammtools/DESCRIPTION’ ... OK -... -* checking data for non-ASCII characters ... OK -* checking LazyData ... OK -* checking data for ASCII and uncompressed saves ... OK -* checking R/sysdata.rda ... OK -* checking examples ... OK -* checking for unstated dependencies in ‘tests’ ... OK -* checking tests ... OK - Running ‘testthat.R’ -* DONE -Status: OK - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/pammtools/old/pammtools.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘pammtools/DESCRIPTION’ ... OK -... -* checking data for non-ASCII characters ... OK -* checking LazyData ... OK -* checking data for ASCII and uncompressed saves ... OK -* checking R/sysdata.rda ... OK -* checking examples ... OK -* checking for unstated dependencies in ‘tests’ ... OK -* checking tests ... OK - Running ‘testthat.R’ -* DONE -Status: OK - - - - - -``` -# pander - -
- -* Version: 0.6.5 -* GitHub: https://github.com/rapporter/pander -* Source code: https://github.com/cran/pander -* Date/Publication: 2022-03-18 09:20:02 UTC -* Number of recursive dependencies: 108 - -Run `revdepcheck::cloud_details(, "pander")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/pander/new/pander.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘pander/DESCRIPTION’ ... OK -... -Error: Pandoc does not support newlines in simple or Rmarkdown table format! -Execution halted - - ‘evals.Rmd’ using ‘UTF-8’... OK - ‘knitr.Rmd’ using ‘UTF-8’... failed - ‘pander.Rmd’ using ‘UTF-8’... OK - ‘pandoc_table.Rmd’ using ‘UTF-8’... failed -* checking re-building of vignette outputs ... OK -* DONE -Status: 1 ERROR, 1 NOTE - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/pander/old/pander.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘pander/DESCRIPTION’ ... OK -... -Error: Pandoc does not support newlines in simple or Rmarkdown table format! -Execution halted - - ‘evals.Rmd’ using ‘UTF-8’... OK - ‘knitr.Rmd’ using ‘UTF-8’... failed - ‘pander.Rmd’ using ‘UTF-8’... OK - ‘pandoc_table.Rmd’ using ‘UTF-8’... failed -* checking re-building of vignette outputs ... OK -* DONE -Status: 1 ERROR, 1 NOTE - - - - - -``` -# parameters - -
- -* Version: 0.21.7 -* GitHub: https://github.com/easystats/parameters -* Source code: https://github.com/cran/parameters -* Date/Publication: 2024-05-14 08:13:17 UTC -* Number of recursive dependencies: 440 - -Run `revdepcheck::cloud_details(, "parameters")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/parameters/new/parameters.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘parameters/DESCRIPTION’ ... OK -... -* checking for unstated dependencies in ‘tests’ ... OK -* checking tests ... OK - Running ‘testthat.R’ -* checking for unstated dependencies in vignettes ... OK -* checking package vignettes in ‘inst/doc’ ... OK -* checking running R code from vignettes ... OK - ‘overview_of_vignettes.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: 1 NOTE - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/parameters/old/parameters.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘parameters/DESCRIPTION’ ... OK -... -* checking for unstated dependencies in ‘tests’ ... OK -* checking tests ... OK - Running ‘testthat.R’ -* checking for unstated dependencies in vignettes ... OK -* checking package vignettes in ‘inst/doc’ ... OK -* checking running R code from vignettes ... OK - ‘overview_of_vignettes.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: 1 NOTE - - - - - -``` -# PAsso - -
- -* Version: 0.1.10 -* GitHub: https://github.com/XiaoruiZhu/PAsso -* Source code: https://github.com/cran/PAsso -* Date/Publication: 2021-06-18 09:20:08 UTC -* Number of recursive dependencies: 179 - -Run `revdepcheck::cloud_details(, "PAsso")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/PAsso/new/PAsso.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘PAsso/DESCRIPTION’ ... OK -... -* checking LazyData ... OK -* checking data for ASCII and uncompressed saves ... OK -* checking line endings in C/C++/Fortran sources/headers ... OK -* checking compiled code ... OK -* checking examples ... OK -* checking for unstated dependencies in ‘tests’ ... OK -* checking tests ... OK - Running ‘testthat.R’ -* DONE -Status: 2 NOTEs - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/PAsso/old/PAsso.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘PAsso/DESCRIPTION’ ... OK -... -* checking LazyData ... OK -* checking data for ASCII and uncompressed saves ... OK -* checking line endings in C/C++/Fortran sources/headers ... OK -* checking compiled code ... OK -* checking examples ... OK -* checking for unstated dependencies in ‘tests’ ... OK -* checking tests ... OK - Running ‘testthat.R’ -* DONE -Status: 2 NOTEs - - - - - -``` -# paths - -
- -* Version: 0.1.1 -* GitHub: NA -* Source code: https://github.com/cran/paths -* Date/Publication: 2021-06-18 08:40:02 UTC -* Number of recursive dependencies: 103 - -Run `revdepcheck::cloud_details(, "paths")` for more info - -
- -## In both - -* checking whether package ‘paths’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/paths/new/paths.Rcheck/00install.out’ for details. - ``` - -## Installation - -### Devel - -``` -* installing *source* package ‘paths’ ... -** package ‘paths’ 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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘paths’ -* removing ‘/tmp/workdir/paths/new/paths.Rcheck/paths’ - - -``` -### CRAN - -``` -* installing *source* package ‘paths’ ... -** package ‘paths’ 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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘paths’ -* removing ‘/tmp/workdir/paths/old/paths.Rcheck/paths’ - - -``` -# pctax - -
- -* Version: 0.1.1 -* GitHub: https://github.com/Asa12138/pctax -* Source code: https://github.com/cran/pctax -* Date/Publication: 2024-04-10 17:10:05 UTC -* Number of recursive dependencies: 267 - -Run `revdepcheck::cloud_details(, "pctax")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/pctax/new/pctax.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘pctax/DESCRIPTION’ ... OK -... -1. ggpmisc -Calls: -> lib_ps -Execution halted -* checking for unstated dependencies in vignettes ... OK -* checking package vignettes in ‘inst/doc’ ... OK -* checking running R code from vignettes ... OK - ‘pctax.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: 1 ERROR, 1 NOTE - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/pctax/old/pctax.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘pctax/DESCRIPTION’ ... OK -... -1. ggpmisc -Calls: -> lib_ps -Execution halted -* checking for unstated dependencies in vignettes ... OK -* checking package vignettes in ‘inst/doc’ ... OK -* checking running R code from vignettes ... OK - ‘pctax.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: 1 ERROR, 1 NOTE - - - - - -``` -# pcutils - -
- -* Version: 0.2.5 -* GitHub: https://github.com/Asa12138/pcutils -* Source code: https://github.com/cran/pcutils -* Date/Publication: 2024-03-19 16:50:07 UTC -* Number of recursive dependencies: 277 - -Run `revdepcheck::cloud_details(, "pcutils")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/pcutils/new/pcutils.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘pcutils/DESCRIPTION’ ... OK -... - 1. ├─base (local) ``(x) - 2. └─ggplot2:::print.ggplot(x) - 3. ├─ggplot2::ggplot_gtable(data) - 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) - 5. └─ggplot2::calc_element("plot.margin", theme) - 6. └─cli::cli_abort(...) - 7. └─rlang::abort(...) -Execution halted -* DONE -Status: 1 ERROR, 1 NOTE - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/pcutils/old/pcutils.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘pcutils/DESCRIPTION’ ... OK -... -* checking for code/documentation mismatches ... OK -* checking Rd \usage sections ... OK -* checking Rd contents ... OK -* checking for unstated dependencies in examples ... OK -* checking contents of ‘data’ directory ... OK -* checking data for non-ASCII characters ... OK -* checking data for ASCII and uncompressed saves ... OK -* checking examples ... OK -* DONE -Status: 1 NOTE - - - - - -``` -# PLMIX - -
- -* Version: 2.1.1 -* GitHub: NA -* Source code: https://github.com/cran/PLMIX -* Date/Publication: 2019-09-04 11:50:02 UTC -* Number of recursive dependencies: 150 - -Run `revdepcheck::cloud_details(, "PLMIX")` for more info - -
- -## In both - -* checking whether package ‘PLMIX’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/PLMIX/new/PLMIX.Rcheck/00install.out’ for details. - ``` - -## Installation - -### Devel - -``` -* installing *source* package ‘PLMIX’ ... -** package ‘PLMIX’ successfully unpacked and MD5 sums checked -** using staged installation -** libs -using C++ compiler: ‘g++ (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c CompProbZpartial.cpp -o CompProbZpartial.o -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c CompRateP.cpp -o CompRateP.o -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c CompRateYpartial.cpp -o CompRateYpartial.o -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c Estep.cpp -o Estep.o -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c PLMIXsim.cpp -o PLMIXsim.o -... -** data -*** moving datasets to lazyload DB -** 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 ‘quantreg’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart -Execution halted -ERROR: lazy loading failed for package ‘PLMIX’ -* removing ‘/tmp/workdir/PLMIX/new/PLMIX.Rcheck/PLMIX’ - - -``` -### CRAN - -``` -* installing *source* package ‘PLMIX’ ... -** package ‘PLMIX’ successfully unpacked and MD5 sums checked -** using staged installation -** libs -using C++ compiler: ‘g++ (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c CompProbZpartial.cpp -o CompProbZpartial.o -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c CompRateP.cpp -o CompRateP.o -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c CompRateYpartial.cpp -o CompRateYpartial.o -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c Estep.cpp -o Estep.o -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c PLMIXsim.cpp -o PLMIXsim.o -... -** data -*** moving datasets to lazyload DB -** 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 ‘quantreg’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart -Execution halted -ERROR: lazy loading failed for package ‘PLMIX’ -* removing ‘/tmp/workdir/PLMIX/old/PLMIX.Rcheck/PLMIX’ - - -``` -# pmcalibration - -
- -* Version: 0.1.0 -* GitHub: https://github.com/stephenrho/pmcalibration -* Source code: https://github.com/cran/pmcalibration -* Date/Publication: 2023-09-06 17:50:02 UTC -* Number of recursive dependencies: 80 - -Run `revdepcheck::cloud_details(, "pmcalibration")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/pmcalibration/new/pmcalibration.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘pmcalibration/DESCRIPTION’ ... OK -... ---- finished re-building ‘internal-validation.Rmd’ - -SUMMARY: processing the following file failed: - ‘external-validation.Rmd’ - -Error: Vignette re-building failed. -Execution halted - -* DONE -Status: 1 WARNING, 2 NOTEs - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/pmcalibration/old/pmcalibration.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘pmcalibration/DESCRIPTION’ ... OK -... ---- finished re-building ‘internal-validation.Rmd’ - -SUMMARY: processing the following file failed: - ‘external-validation.Rmd’ - -Error: Vignette re-building failed. -Execution halted - -* DONE -Status: 1 WARNING, 2 NOTEs - - - - - -``` -# popstudy - -
- -* Version: 1.0.1 -* GitHub: NA -* Source code: https://github.com/cran/popstudy -* Date/Publication: 2023-10-17 23:50:02 UTC -* Number of recursive dependencies: 235 - -Run `revdepcheck::cloud_details(, "popstudy")` for more info - -
- -## In both - -* checking whether package ‘popstudy’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/popstudy/new/popstudy.Rcheck/00install.out’ for details. - ``` - -## Installation - -### Devel - -``` -* installing *source* package ‘popstudy’ ... -** package ‘popstudy’ 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 ‘quantreg’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart -Execution halted -ERROR: lazy loading failed for package ‘popstudy’ -* removing ‘/tmp/workdir/popstudy/new/popstudy.Rcheck/popstudy’ - - -``` -### CRAN - -``` -* installing *source* package ‘popstudy’ ... -** package ‘popstudy’ 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 ‘quantreg’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart -Execution halted -ERROR: lazy loading failed for package ‘popstudy’ -* removing ‘/tmp/workdir/popstudy/old/popstudy.Rcheck/popstudy’ - - -``` -# pould - -
- -* Version: 1.0.1 -* GitHub: NA -* Source code: https://github.com/cran/pould -* Date/Publication: 2020-10-16 13:50:03 UTC -* Number of recursive dependencies: 104 - -Run `revdepcheck::cloud_details(, "pould")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/pould/new/pould.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘pould/DESCRIPTION’ ... OK -... -* checking if there is a namespace ... OK -* checking for executable files ... OK -* checking for hidden files and directories ... OK -* checking for portable file names ... OK -* checking for sufficient/correct file permissions ... OK -* checking whether package ‘pould’ can be installed ... ERROR -Installation failed. -See ‘/tmp/workdir/pould/new/pould.Rcheck/00install.out’ for details. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/pould/old/pould.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘pould/DESCRIPTION’ ... OK -... -* checking if there is a namespace ... OK -* checking for executable files ... OK -* checking for hidden files and directories ... OK -* checking for portable file names ... OK -* checking for sufficient/correct file permissions ... OK -* checking whether package ‘pould’ can be installed ... ERROR -Installation failed. -See ‘/tmp/workdir/pould/old/pould.Rcheck/00install.out’ for details. -* DONE -Status: 1 ERROR - - - - - -``` -# powerly - -
- -* Version: 1.8.6 -* GitHub: https://github.com/mihaiconstantin/powerly -* Source code: https://github.com/cran/powerly -* Date/Publication: 2022-09-09 14:10:01 UTC -* Number of recursive dependencies: 175 - -Run `revdepcheck::cloud_details(, "powerly")` for more info - -
- -## In both - -* checking whether package ‘powerly’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/powerly/new/powerly.Rcheck/00install.out’ for details. - ``` - -## Installation - -### Devel - -``` -* installing *source* package ‘powerly’ ... -** package ‘powerly’ 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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.1 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘powerly’ -* removing ‘/tmp/workdir/powerly/new/powerly.Rcheck/powerly’ - - -``` -### CRAN - -``` -* installing *source* package ‘powerly’ ... -** package ‘powerly’ 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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.1 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘powerly’ -* removing ‘/tmp/workdir/powerly/old/powerly.Rcheck/powerly’ - - -``` -# pre - -
- -* Version: 1.0.7 -* GitHub: https://github.com/marjoleinF/pre -* Source code: https://github.com/cran/pre -* Date/Publication: 2024-01-12 19:30:02 UTC -* Number of recursive dependencies: 152 - -Run `revdepcheck::cloud_details(, "pre")` for more info - -
- -## In both - -* checking whether package ‘pre’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/pre/new/pre.Rcheck/00install.out’ for details. - ``` - -## Installation - -### Devel - -``` -* installing *source* package ‘pre’ ... -** package ‘pre’ 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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘pre’ -* removing ‘/tmp/workdir/pre/new/pre.Rcheck/pre’ - - -``` -### CRAN - -``` -* installing *source* package ‘pre’ ... -** package ‘pre’ 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]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required -Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace -Execution halted -ERROR: lazy loading failed for package ‘pre’ -* removing ‘/tmp/workdir/pre/old/pre.Rcheck/pre’ - - -``` -# PRECAST - -
- -* Version: 1.6.5 -* GitHub: https://github.com/feiyoung/PRECAST -* Source code: https://github.com/cran/PRECAST -* Date/Publication: 2024-03-19 08:30:02 UTC -* Number of recursive dependencies: 224 - -Run `revdepcheck::cloud_details(, "PRECAST")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/PRECAST/new/PRECAST.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘PRECAST/DESCRIPTION’ ... OK -... -* this is package ‘PRECAST’ version ‘1.6.5’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Packages required but not available: 'Seurat', 'DR.SC' - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/PRECAST/old/PRECAST.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘PRECAST/DESCRIPTION’ ... OK -... -* this is package ‘PRECAST’ version ‘1.6.5’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Packages required but not available: 'Seurat', 'DR.SC' - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# ProFAST - -
- -* Version: 1.4 -* GitHub: https://github.com/feiyoung/ProFAST -* Source code: https://github.com/cran/ProFAST -* Date/Publication: 2024-03-18 08:10:06 UTC -* Number of recursive dependencies: 252 - -Run `revdepcheck::cloud_details(, "ProFAST")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/ProFAST/new/ProFAST.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘ProFAST/DESCRIPTION’ ... OK -... -* this is package ‘ProFAST’ version ‘1.4’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Packages required but not available: 'DR.SC', 'PRECAST', 'Seurat' - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/ProFAST/old/ProFAST.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘ProFAST/DESCRIPTION’ ... OK -... -* this is package ‘ProFAST’ version ‘1.4’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Packages required but not available: 'DR.SC', 'PRECAST', 'Seurat' - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# psbcSpeedUp - -
- -* Version: 2.0.6 -* GitHub: https://github.com/ocbe-uio/psbcSpeedUp -* Source code: https://github.com/cran/psbcSpeedUp -* Date/Publication: 2024-03-21 18:00:02 UTC -* Number of recursive dependencies: 129 - -Run `revdepcheck::cloud_details(, "psbcSpeedUp")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/psbcSpeedUp/new/psbcSpeedUp.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘psbcSpeedUp/DESCRIPTION’ ... OK -... -* this is package ‘psbcSpeedUp’ version ‘2.0.6’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘riskRegression’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/psbcSpeedUp/old/psbcSpeedUp.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘psbcSpeedUp/DESCRIPTION’ ... OK -... -* this is package ‘psbcSpeedUp’ version ‘2.0.6’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘riskRegression’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# pscore - -
- -* Version: 0.4.0 -* GitHub: https://github.com/JWiley/score-project -* Source code: https://github.com/cran/pscore -* Date/Publication: 2022-05-13 22:30:02 UTC -* Number of recursive dependencies: 164 - -Run `revdepcheck::cloud_details(, "pscore")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/pscore/new/pscore.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘pscore/DESCRIPTION’ ... OK -... -* checking if there is a namespace ... OK -* checking for executable files ... OK -* checking for hidden files and directories ... OK -* checking for portable file names ... OK -* checking for sufficient/correct file permissions ... OK -* checking whether package ‘pscore’ can be installed ... ERROR -Installation failed. -See ‘/tmp/workdir/pscore/new/pscore.Rcheck/00install.out’ for details. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/pscore/old/pscore.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘pscore/DESCRIPTION’ ... OK -... -* checking if there is a namespace ... OK -* checking for executable files ... OK -* checking for hidden files and directories ... OK -* checking for portable file names ... OK -* checking for sufficient/correct file permissions ... OK -* checking whether package ‘pscore’ can be installed ... ERROR -Installation failed. -See ‘/tmp/workdir/pscore/old/pscore.Rcheck/00install.out’ for details. -* DONE -Status: 1 ERROR - - - - - -``` -# psfmi - -
- -* Version: 1.4.0 -* GitHub: https://github.com/mwheymans/psfmi -* Source code: https://github.com/cran/psfmi -* Date/Publication: 2023-06-17 22:40:02 UTC -* Number of recursive dependencies: 159 - -Run `revdepcheck::cloud_details(, "psfmi")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/psfmi/new/psfmi.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘psfmi/DESCRIPTION’ ... OK -... -* this is package ‘psfmi’ version ‘1.4.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘rms’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/psfmi/old/psfmi.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘psfmi/DESCRIPTION’ ... OK -... -* this is package ‘psfmi’ version ‘1.4.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘rms’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR +*** 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘paths’ +* removing ‘/tmp/workdir/paths/new/paths.Rcheck/paths’ +``` +### CRAN +``` +* installing *source* package ‘paths’ ... +** package ‘paths’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘paths’ +* removing ‘/tmp/workdir/paths/old/paths.Rcheck/paths’ ``` -# pubh +# PLMIX
-* Version: 1.3.2 -* GitHub: https://github.com/josie-athens/pubh -* Source code: https://github.com/cran/pubh -* Date/Publication: 2024-01-11 21:30:12 UTC -* Number of recursive dependencies: 229 +* Version: 2.1.1 +* GitHub: NA +* Source code: https://github.com/cran/PLMIX +* Date/Publication: 2019-09-04 11:50:02 UTC +* Number of recursive dependencies: 138 -Run `revdepcheck::cloud_details(, "pubh")` for more info +Run `revdepcheck::cloud_details(, "PLMIX")` for more info
-## Error before installation +## In both + +* checking whether package ‘PLMIX’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/PLMIX/new/PLMIX.Rcheck/00install.out’ for details. + ``` + +## Installation ### Devel ``` -* using log directory ‘/tmp/workdir/pubh/new/pubh.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘pubh/DESCRIPTION’ ... OK +* installing *source* package ‘PLMIX’ ... +** package ‘PLMIX’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C++ compiler: ‘g++ (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c CompProbZpartial.cpp -o CompProbZpartial.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c CompRateP.cpp -o CompRateP.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c CompRateYpartial.cpp -o CompRateYpartial.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c Estep.cpp -o Estep.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c PLMIXsim.cpp -o PLMIXsim.o ... -* checking files in ‘vignettes’ ... OK -* checking examples ... OK -* checking for unstated dependencies in vignettes ... OK -* checking package vignettes in ‘inst/doc’ ... OK -* checking running R code from vignettes ... OK - ‘introduction.Rmd’ using ‘UTF-8’... OK - ‘regression.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: 1 NOTE - - - +** 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘PLMIX’ +* removing ‘/tmp/workdir/PLMIX/new/PLMIX.Rcheck/PLMIX’ ``` ### CRAN ``` -* using log directory ‘/tmp/workdir/pubh/old/pubh.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘pubh/DESCRIPTION’ ... OK +* installing *source* package ‘PLMIX’ ... +** package ‘PLMIX’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C++ compiler: ‘g++ (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c CompProbZpartial.cpp -o CompProbZpartial.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c CompRateP.cpp -o CompRateP.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c CompRateYpartial.cpp -o CompRateYpartial.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c Estep.cpp -o Estep.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c PLMIXsim.cpp -o PLMIXsim.o ... -* checking files in ‘vignettes’ ... OK -* checking examples ... OK -* checking for unstated dependencies in vignettes ... OK -* checking package vignettes in ‘inst/doc’ ... OK -* checking running R code from vignettes ... OK - ‘introduction.Rmd’ using ‘UTF-8’... OK - ‘regression.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: 1 NOTE - - - +** 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘PLMIX’ +* removing ‘/tmp/workdir/PLMIX/old/PLMIX.Rcheck/PLMIX’ ``` -# qPCRtools +# popstudy
* Version: 1.0.1 -* GitHub: https://github.com/lixiang117423/qPCRtools -* Source code: https://github.com/cran/qPCRtools -* Date/Publication: 2023-11-02 13:10:05 UTC -* Number of recursive dependencies: 115 +* GitHub: NA +* Source code: https://github.com/cran/popstudy +* Date/Publication: 2023-10-17 23:50:02 UTC +* Number of recursive dependencies: 240 -Run `revdepcheck::cloud_details(, "qPCRtools")` for more info +Run `revdepcheck::cloud_details(, "popstudy")` for more info
-## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/qPCRtools/new/qPCRtools.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘qPCRtools/DESCRIPTION’ ... OK -* this is package ‘qPCRtools’ version ‘1.0.1’ -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘ggpmisc’ +## In both -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR +* checking whether package ‘popstudy’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/popstudy/new/popstudy.Rcheck/00install.out’ for details. + ``` +## Installation +### Devel +``` +* installing *source* package ‘popstudy’ ... +** package ‘popstudy’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘popstudy’ +* removing ‘/tmp/workdir/popstudy/new/popstudy.Rcheck/popstudy’ ``` ### CRAN ``` -* using log directory ‘/tmp/workdir/qPCRtools/old/qPCRtools.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘qPCRtools/DESCRIPTION’ ... OK -* this is package ‘qPCRtools’ version ‘1.0.1’ -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘ggpmisc’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - +* installing *source* package ‘popstudy’ ... +** package ‘popstudy’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘popstudy’ +* removing ‘/tmp/workdir/popstudy/old/popstudy.Rcheck/popstudy’ ``` -# qreport +# pould
-* Version: 1.0-1 +* Version: 1.0.1 * GitHub: NA -* Source code: https://github.com/cran/qreport -* Date/Publication: 2024-05-26 21:50:03 UTC -* Number of recursive dependencies: 77 +* Source code: https://github.com/cran/pould +* Date/Publication: 2020-10-16 13:50:03 UTC +* Number of recursive dependencies: 104 -Run `revdepcheck::cloud_details(, "qreport")` for more info +Run `revdepcheck::cloud_details(, "pould")` for more info
-## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/qreport/new/qreport.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘qreport/DESCRIPTION’ ... OK -... -* this is package ‘qreport’ version ‘1.0-1’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘rms’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - +## In both +* checking whether package ‘pould’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/pould/new/pould.Rcheck/00install.out’ for details. + ``` -``` -### CRAN +## Installation -``` -* using log directory ‘/tmp/workdir/qreport/old/qreport.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘qreport/DESCRIPTION’ ... OK -... -* this is package ‘qreport’ version ‘1.0-1’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘rms’ +### Devel -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR +``` +* installing *source* package ‘pould’ ... +** package ‘pould’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘pould’ +* removing ‘/tmp/workdir/pould/new/pould.Rcheck/pould’ +``` +### CRAN +``` +* installing *source* package ‘pould’ ... +** package ‘pould’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘pould’ +* removing ‘/tmp/workdir/pould/old/pould.Rcheck/pould’ ``` -# quid +# powerly
-* Version: 0.0.1 -* GitHub: NA -* Source code: https://github.com/cran/quid -* Date/Publication: 2021-12-09 09:00:02 UTC -* Number of recursive dependencies: 95 +* Version: 1.8.6 +* GitHub: https://github.com/mihaiconstantin/powerly +* Source code: https://github.com/cran/powerly +* Date/Publication: 2022-09-09 14:10:01 UTC +* Number of recursive dependencies: 181 -Run `revdepcheck::cloud_details(, "quid")` for more info +Run `revdepcheck::cloud_details(, "powerly")` for more info
## In both -* checking whether package ‘quid’ can be installed ... ERROR +* checking whether package ‘powerly’ can be installed ... ERROR ``` Installation failed. - See ‘/tmp/workdir/quid/new/quid.Rcheck/00install.out’ for details. + See ‘/tmp/workdir/powerly/new/powerly.Rcheck/00install.out’ for details. ``` ## Installation @@ -9674,63 +4979,69 @@ Run `revdepcheck::cloud_details(, "quid")` for more info ### Devel ``` -* installing *source* package ‘quid’ ... -** package ‘quid’ successfully unpacked and MD5 sums checked +* installing *source* package ‘powerly’ ... +** package ‘powerly’ 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 +Warning in check_dep_version() : + ABI version mismatch: +lme4 was built with Matrix ABI version 1 +Current Matrix ABI version is 0 +Please re-install lme4 from source or restore original ‘Matrix’ package Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.1 is required Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace Execution halted -ERROR: lazy loading failed for package ‘quid’ -* removing ‘/tmp/workdir/quid/new/quid.Rcheck/quid’ +ERROR: lazy loading failed for package ‘powerly’ +* removing ‘/tmp/workdir/powerly/new/powerly.Rcheck/powerly’ ``` ### CRAN ``` -* installing *source* package ‘quid’ ... -** package ‘quid’ successfully unpacked and MD5 sums checked +* installing *source* package ‘powerly’ ... +** package ‘powerly’ 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 +Warning in check_dep_version() : + ABI version mismatch: +lme4 was built with Matrix ABI version 1 +Current Matrix ABI version is 0 +Please re-install lme4 from source or restore original ‘Matrix’ package Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.1 is required Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace Execution halted -ERROR: lazy loading failed for package ‘quid’ -* removing ‘/tmp/workdir/quid/old/quid.Rcheck/quid’ +ERROR: lazy loading failed for package ‘powerly’ +* removing ‘/tmp/workdir/powerly/old/powerly.Rcheck/powerly’ ``` -# RcmdrPlugin.RiskDemo +# pre
-* Version: 3.2 -* GitHub: NA -* Source code: https://github.com/cran/RcmdrPlugin.RiskDemo -* Date/Publication: 2024-02-06 09:20:02 UTC -* Number of recursive dependencies: 207 +* Version: 1.0.7 +* GitHub: https://github.com/marjoleinF/pre +* Source code: https://github.com/cran/pre +* Date/Publication: 2024-01-12 19:30:02 UTC +* Number of recursive dependencies: 151 -Run `revdepcheck::cloud_details(, "RcmdrPlugin.RiskDemo")` for more info +Run `revdepcheck::cloud_details(, "pre")` for more info
## In both -* checking whether package ‘RcmdrPlugin.RiskDemo’ can be installed ... ERROR +* checking whether package ‘pre’ can be installed ... ERROR ``` Installation failed. - See ‘/tmp/workdir/RcmdrPlugin.RiskDemo/new/RcmdrPlugin.RiskDemo.Rcheck/00install.out’ for details. + See ‘/tmp/workdir/pre/new/pre.Rcheck/00install.out’ for details. ``` ## Installation @@ -9738,52 +5049,54 @@ Run `revdepcheck::cloud_details(, "RcmdrPlugin.RiskDemo")` for more info ### Devel ``` -* installing *source* package ‘RcmdrPlugin.RiskDemo’ ... -** package ‘RcmdrPlugin.RiskDemo’ successfully unpacked and MD5 sums checked +* installing *source* package ‘pre’ ... +** package ‘pre’ 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 ‘quantreg’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace Execution halted -ERROR: lazy loading failed for package ‘RcmdrPlugin.RiskDemo’ -* removing ‘/tmp/workdir/RcmdrPlugin.RiskDemo/new/RcmdrPlugin.RiskDemo.Rcheck/RcmdrPlugin.RiskDemo’ +ERROR: lazy loading failed for package ‘pre’ +* removing ‘/tmp/workdir/pre/new/pre.Rcheck/pre’ ``` ### CRAN ``` -* installing *source* package ‘RcmdrPlugin.RiskDemo’ ... -** package ‘RcmdrPlugin.RiskDemo’ successfully unpacked and MD5 sums checked +* installing *source* package ‘pre’ ... +** package ‘pre’ 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 ‘quantreg’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace Execution halted -ERROR: lazy loading failed for package ‘RcmdrPlugin.RiskDemo’ -* removing ‘/tmp/workdir/RcmdrPlugin.RiskDemo/old/RcmdrPlugin.RiskDemo.Rcheck/RcmdrPlugin.RiskDemo’ +ERROR: lazy loading failed for package ‘pre’ +* removing ‘/tmp/workdir/pre/old/pre.Rcheck/pre’ ``` -# rcssci +# ProFAST
-* Version: 0.4.0 -* GitHub: https://github.com/popnie/RCSsci -* Source code: https://github.com/cran/rcssci -* Date/Publication: 2023-02-15 21:20:02 UTC -* Number of recursive dependencies: 137 +* Version: 1.4 +* GitHub: https://github.com/feiyoung/ProFAST +* Source code: https://github.com/cran/ProFAST +* Date/Publication: 2024-03-18 08:10:06 UTC +* Number of recursive dependencies: 245 -Run `revdepcheck::cloud_details(, "rcssci")` for more info +Run `revdepcheck::cloud_details(, "ProFAST")` for more info
@@ -9792,7 +5105,7 @@ Run `revdepcheck::cloud_details(, "rcssci")` for more info ### Devel ``` -* using log directory ‘/tmp/workdir/rcssci/new/rcssci.Rcheck’ +* using log directory ‘/tmp/workdir/ProFAST/new/ProFAST.Rcheck’ * using R version 4.3.1 (2023-06-16) * using platform: x86_64-pc-linux-gnu (64-bit) * R was compiled by @@ -9801,13 +5114,13 @@ Run `revdepcheck::cloud_details(, "rcssci")` for more info * running under: Ubuntu 22.04.4 LTS * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘rcssci/DESCRIPTION’ ... OK +* checking for file ‘ProFAST/DESCRIPTION’ ... OK ... -* this is package ‘rcssci’ version ‘0.4.0’ +* this is package ‘ProFAST’ version ‘1.4’ * package encoding: UTF-8 * checking package namespace information ... OK * checking package dependencies ... ERROR -Package required but not available: ‘rms’ +Packages required but not available: 'DR.SC', 'PRECAST' See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ manual. @@ -9822,7 +5135,7 @@ Status: 1 ERROR ### CRAN ``` -* using log directory ‘/tmp/workdir/rcssci/old/rcssci.Rcheck’ +* using log directory ‘/tmp/workdir/ProFAST/old/ProFAST.Rcheck’ * using R version 4.3.1 (2023-06-16) * using platform: x86_64-pc-linux-gnu (64-bit) * R was compiled by @@ -9831,13 +5144,13 @@ Status: 1 ERROR * running under: Ubuntu 22.04.4 LTS * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘rcssci/DESCRIPTION’ ... OK +* checking for file ‘ProFAST/DESCRIPTION’ ... OK ... -* this is package ‘rcssci’ version ‘0.4.0’ +* this is package ‘ProFAST’ version ‘1.4’ * package encoding: UTF-8 * checking package namespace information ... OK * checking package dependencies ... ERROR -Package required but not available: ‘rms’ +Packages required but not available: 'DR.SC', 'PRECAST' See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ manual. @@ -9849,26 +5162,26 @@ Status: 1 ERROR ``` -# rddtools +# psbcSpeedUp
-* Version: 1.6.0 -* GitHub: https://github.com/bquast/rddtools -* Source code: https://github.com/cran/rddtools -* Date/Publication: 2022-01-10 12:42:49 UTC -* Number of recursive dependencies: 101 +* Version: 2.0.7 +* GitHub: https://github.com/ocbe-uio/psbcSpeedUp +* Source code: https://github.com/cran/psbcSpeedUp +* Date/Publication: 2024-07-01 09:00:02 UTC +* Number of recursive dependencies: 129 -Run `revdepcheck::cloud_details(, "rddtools")` for more info +Run `revdepcheck::cloud_details(, "psbcSpeedUp")` for more info
## In both -* checking whether package ‘rddtools’ can be installed ... ERROR +* checking whether package ‘psbcSpeedUp’ can be installed ... ERROR ``` Installation failed. - See ‘/tmp/workdir/rddtools/new/rddtools.Rcheck/00install.out’ for details. + See ‘/tmp/workdir/psbcSpeedUp/new/psbcSpeedUp.Rcheck/00install.out’ for details. ``` ## Installation @@ -9876,515 +5189,537 @@ Run `revdepcheck::cloud_details(, "rddtools")` for more info ### Devel ``` -* installing *source* package ‘rddtools’ ... -** package ‘rddtools’ successfully unpacked and MD5 sums checked +* installing *source* package ‘psbcSpeedUp’ ... +** package ‘psbcSpeedUp’ successfully unpacked and MD5 sums checked ** using staged installation -** R +checking whether the C++ compiler works... yes +checking for C++ compiler default output file name... a.out +checking for suffix of executables... +checking whether we are cross compiling... no +checking for suffix of object files... o +checking whether the compiler supports GNU C++... yes +checking whether g++ -std=gnu++17 accepts -g... yes +... ** data +*** moving datasets to lazyload DB ** inst ** byte-compile and prepare package for lazy loading -Error: package or namespace load failed for ‘np’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): - there is no package called ‘quantreg’ +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace Execution halted -ERROR: lazy loading failed for package ‘rddtools’ -* removing ‘/tmp/workdir/rddtools/new/rddtools.Rcheck/rddtools’ +ERROR: lazy loading failed for package ‘psbcSpeedUp’ +* removing ‘/tmp/workdir/psbcSpeedUp/new/psbcSpeedUp.Rcheck/psbcSpeedUp’ ``` ### CRAN ``` -* installing *source* package ‘rddtools’ ... -** package ‘rddtools’ successfully unpacked and MD5 sums checked +* installing *source* package ‘psbcSpeedUp’ ... +** package ‘psbcSpeedUp’ successfully unpacked and MD5 sums checked ** using staged installation -** R +checking whether the C++ compiler works... yes +checking for C++ compiler default output file name... a.out +checking for suffix of executables... +checking whether we are cross compiling... no +checking for suffix of object files... o +checking whether the compiler supports GNU C++... yes +checking whether g++ -std=gnu++17 accepts -g... yes +... ** data +*** moving datasets to lazyload DB ** inst ** byte-compile and prepare package for lazy loading -Error: package or namespace load failed for ‘np’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): - there is no package called ‘quantreg’ +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace Execution halted -ERROR: lazy loading failed for package ‘rddtools’ -* removing ‘/tmp/workdir/rddtools/old/rddtools.Rcheck/rddtools’ +ERROR: lazy loading failed for package ‘psbcSpeedUp’ +* removing ‘/tmp/workdir/psbcSpeedUp/old/psbcSpeedUp.Rcheck/psbcSpeedUp’ ``` -# relsurv +# pscore
-* Version: 2.2-9 -* GitHub: NA -* Source code: https://github.com/cran/relsurv -* Date/Publication: 2022-12-22 13:30:02 UTC -* Number of recursive dependencies: 113 +* Version: 0.4.0 +* GitHub: https://github.com/JWiley/score-project +* Source code: https://github.com/cran/pscore +* Date/Publication: 2022-05-13 22:30:02 UTC +* Number of recursive dependencies: 169 -Run `revdepcheck::cloud_details(, "relsurv")` for more info +Run `revdepcheck::cloud_details(, "pscore")` for more info
-## Error before installation +## In both + +* checking whether package ‘pscore’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/pscore/new/pscore.Rcheck/00install.out’ for details. + ``` + +## Installation ### Devel ``` -* using log directory ‘/tmp/workdir/relsurv/new/relsurv.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘relsurv/DESCRIPTION’ ... OK -... -* checking for unstated dependencies in examples ... OK -* checking contents of ‘data’ directory ... OK -* checking data for non-ASCII characters ... OK -* checking LazyData ... OK -* checking data for ASCII and uncompressed saves ... OK -* checking line endings in C/C++/Fortran sources/headers ... OK -* checking compiled code ... OK -* checking examples ... OK -* DONE -Status: OK +* installing *source* package ‘pscore’ ... +** package ‘pscore’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** data +** inst +** byte-compile and prepare package for lazy loading +Warning in check_dep_version() : + ABI version mismatch: +lme4 was built with Matrix ABI version 1 +Current Matrix ABI version is 0 +Please re-install lme4 from source or restore original ‘Matrix’ package +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘pscore’ +* removing ‘/tmp/workdir/pscore/new/pscore.Rcheck/pscore’ +``` +### CRAN +``` +* installing *source* package ‘pscore’ ... +** package ‘pscore’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** data +** inst +** byte-compile and prepare package for lazy loading +Warning in check_dep_version() : + ABI version mismatch: +lme4 was built with Matrix ABI version 1 +Current Matrix ABI version is 0 +Please re-install lme4 from source or restore original ‘Matrix’ package +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘pscore’ +* removing ‘/tmp/workdir/pscore/old/pscore.Rcheck/pscore’ ``` -### CRAN +# psfmi + +
+ +* Version: 1.4.0 +* GitHub: https://github.com/mwheymans/psfmi +* Source code: https://github.com/cran/psfmi +* Date/Publication: 2023-06-17 22:40:02 UTC +* Number of recursive dependencies: 164 + +Run `revdepcheck::cloud_details(, "psfmi")` for more info + +
+ +## In both + +* checking whether package ‘psfmi’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/psfmi/new/psfmi.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel ``` -* using log directory ‘/tmp/workdir/relsurv/old/relsurv.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘relsurv/DESCRIPTION’ ... OK -... -* checking for unstated dependencies in examples ... OK -* checking contents of ‘data’ directory ... OK -* checking data for non-ASCII characters ... OK -* checking LazyData ... OK -* checking data for ASCII and uncompressed saves ... OK -* checking line endings in C/C++/Fortran sources/headers ... OK -* checking compiled code ... OK -* checking examples ... OK -* DONE -Status: OK +* installing *source* package ‘psfmi’ ... +** package ‘psfmi’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘psfmi’ +* removing ‘/tmp/workdir/psfmi/new/psfmi.Rcheck/psfmi’ +``` +### CRAN +``` +* installing *source* package ‘psfmi’ ... +** package ‘psfmi’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘psfmi’ +* removing ‘/tmp/workdir/psfmi/old/psfmi.Rcheck/psfmi’ ``` -# riskRegression +# qPCRtools
-* Version: 2023.12.21 -* GitHub: https://github.com/tagteam/riskRegression -* Source code: https://github.com/cran/riskRegression -* Date/Publication: 2023-12-19 17:00:02 UTC -* Number of recursive dependencies: 186 +* Version: 1.0.1 +* GitHub: https://github.com/lixiang117423/qPCRtools +* Source code: https://github.com/cran/qPCRtools +* Date/Publication: 2023-11-02 13:10:05 UTC +* Number of recursive dependencies: 106 -Run `revdepcheck::cloud_details(, "riskRegression")` for more info +Run `revdepcheck::cloud_details(, "qPCRtools")` for more info
-## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/riskRegression/new/riskRegression.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘riskRegression/DESCRIPTION’ ... OK -... -* this is package ‘riskRegression’ version ‘2023.12.21’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘rms’ +## In both -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR +* checking whether package ‘qPCRtools’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/qPCRtools/new/qPCRtools.Rcheck/00install.out’ for details. + ``` +## Installation +### Devel +``` +* installing *source* package ‘qPCRtools’ ... +** package ‘qPCRtools’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘qPCRtools’ +* removing ‘/tmp/workdir/qPCRtools/new/qPCRtools.Rcheck/qPCRtools’ ``` ### CRAN ``` -* using log directory ‘/tmp/workdir/riskRegression/old/riskRegression.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘riskRegression/DESCRIPTION’ ... OK -... -* this is package ‘riskRegression’ version ‘2023.12.21’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘rms’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - +* installing *source* package ‘qPCRtools’ ... +** package ‘qPCRtools’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘qPCRtools’ +* removing ‘/tmp/workdir/qPCRtools/old/qPCRtools.Rcheck/qPCRtools’ ``` -# rliger +# qreport
-* Version: 2.0.1 -* GitHub: https://github.com/welch-lab/liger -* Source code: https://github.com/cran/rliger -* Date/Publication: 2024-04-04 23:20:02 UTC -* Number of recursive dependencies: 218 +* Version: 1.0-1 +* GitHub: NA +* Source code: https://github.com/cran/qreport +* Date/Publication: 2024-05-26 21:50:03 UTC +* Number of recursive dependencies: 77 -Run `revdepcheck::cloud_details(, "rliger")` for more info +Run `revdepcheck::cloud_details(, "qreport")` for more info
-## Error before installation - -### Devel +## In both -``` -* using log directory ‘/tmp/workdir/rliger/new/rliger.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘rliger/DESCRIPTION’ ... OK -... - [ FAIL 2 | WARN 0 | SKIP 5 | PASS 1233 ] - Error: Test failures - Execution halted -* checking for unstated dependencies in vignettes ... OK -* checking package vignettes in ‘inst/doc’ ... OK -* checking running R code from vignettes ... OK - ‘liger-vignette.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: 2 ERRORs, 2 NOTEs +* checking whether package ‘qreport’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/qreport/new/qreport.Rcheck/00install.out’ for details. + ``` +## Installation +### Devel +``` +* installing *source* package ‘qreport’ ... +** package ‘qreport’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘qreport’ +* removing ‘/tmp/workdir/qreport/new/qreport.Rcheck/qreport’ ``` ### CRAN ``` -* using log directory ‘/tmp/workdir/rliger/old/rliger.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘rliger/DESCRIPTION’ ... OK -... - [ FAIL 1 | WARN 0 | SKIP 5 | PASS 1234 ] - Error: Test failures - Execution halted -* checking for unstated dependencies in vignettes ... OK -* checking package vignettes in ‘inst/doc’ ... OK -* checking running R code from vignettes ... OK - ‘liger-vignette.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: 2 ERRORs, 2 NOTEs - - - +* installing *source* package ‘qreport’ ... +** package ‘qreport’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘qreport’ +* removing ‘/tmp/workdir/qreport/old/qreport.Rcheck/qreport’ ``` -# rms +# qris
-* Version: 6.8-1 -* GitHub: https://github.com/harrelfe/rms -* Source code: https://github.com/cran/rms -* Date/Publication: 2024-05-27 12:00:02 UTC -* Number of recursive dependencies: 153 +* Version: 1.1.1 +* GitHub: https://github.com/Kyuhyun07/qris +* Source code: https://github.com/cran/qris +* Date/Publication: 2024-03-05 14:40:03 UTC +* Number of recursive dependencies: 55 -Run `revdepcheck::cloud_details(, "rms")` for more info +Run `revdepcheck::cloud_details(, "qris")` for more info
-## Error before installation +## In both + +* checking whether package ‘qris’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/qris/new/qris.Rcheck/00install.out’ for details. + ``` + +## Installation ### Devel ``` -* using log directory ‘/tmp/workdir/rms/new/rms.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘rms/DESCRIPTION’ ... OK +* installing *source* package ‘qris’ ... +** package ‘qris’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C compiler: ‘gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ +using C++ compiler: ‘g++ (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ +using C++11 +g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c Amat.cpp -o Amat.o +g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c ghat.cpp -o ghat.o ... -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘quantreg’ - -Package suggested but not available for checking: ‘rmsb’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - +installing to /tmp/workdir/qris/new/qris.Rcheck/00LOCK-qris/00new/qris/libs +** R +** inst +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘qris’ +* removing ‘/tmp/workdir/qris/new/qris.Rcheck/qris’ ``` ### CRAN ``` -* using log directory ‘/tmp/workdir/rms/old/rms.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘rms/DESCRIPTION’ ... OK +* installing *source* package ‘qris’ ... +** package ‘qris’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C compiler: ‘gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ +using C++ compiler: ‘g++ (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ +using C++11 +g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c Amat.cpp -o Amat.o +g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +g++ -std=gnu++11 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fopenmp -fpic -g -O2 -c ghat.cpp -o ghat.o ... -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘quantreg’ - -Package suggested but not available for checking: ‘rmsb’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - +installing to /tmp/workdir/qris/old/qris.Rcheck/00LOCK-qris/00new/qris/libs +** R +** inst +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘qris’ +* removing ‘/tmp/workdir/qris/old/qris.Rcheck/qris’ ``` -# rmsb +# qte
-* Version: 1.1-0 +* Version: 1.3.1 * GitHub: NA -* Source code: https://github.com/cran/rmsb -* Date/Publication: 2024-03-12 15:50:02 UTC -* Number of recursive dependencies: 143 +* Source code: https://github.com/cran/qte +* Date/Publication: 2022-09-01 14:30:02 UTC +* Number of recursive dependencies: 87 -Run `revdepcheck::cloud_details(, "rmsb")` for more info +Run `revdepcheck::cloud_details(, "qte")` for more info
-## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/rmsb/new/rmsb.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘rmsb/DESCRIPTION’ ... OK -... -* this is package ‘rmsb’ version ‘1.1-0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘rms’ +## In both -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR +* checking whether package ‘qte’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/qte/new/qte.Rcheck/00install.out’ for details. + ``` +## Installation +### Devel +``` +* installing *source* package ‘qte’ ... +** package ‘qte’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘qte’ +* removing ‘/tmp/workdir/qte/new/qte.Rcheck/qte’ ``` ### CRAN ``` -* using log directory ‘/tmp/workdir/rmsb/old/rmsb.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘rmsb/DESCRIPTION’ ... OK -... -* this is package ‘rmsb’ version ‘1.1-0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘rms’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - +* installing *source* package ‘qte’ ... +** package ‘qte’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘qte’ +* removing ‘/tmp/workdir/qte/old/qte.Rcheck/qte’ ``` -# robber +# quid
-* Version: 0.2.4 -* GitHub: https://github.com/Chabert-Liddell/robber -* Source code: https://github.com/cran/robber -* Date/Publication: 2024-02-07 13:50:02 UTC -* Number of recursive dependencies: 144 +* Version: 0.0.1 +* GitHub: NA +* Source code: https://github.com/cran/quid +* Date/Publication: 2021-12-09 09:00:02 UTC +* Number of recursive dependencies: 95 -Run `revdepcheck::cloud_details(, "robber")` for more info +Run `revdepcheck::cloud_details(, "quid")` for more info
-## Error before installation - -### Devel +## In both -``` -* using log directory ‘/tmp/workdir/robber/new/robber.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘robber/DESCRIPTION’ ... OK -... -* checking tests ... OK - Running ‘spelling.R’ - Running ‘testthat.R’ -* checking for unstated dependencies in vignettes ... OK -* checking package vignettes in ‘inst/doc’ ... OK -* checking running R code from vignettes ... OK - ‘topological-analysis.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: OK +* checking whether package ‘quid’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/quid/new/quid.Rcheck/00install.out’ for details. + ``` +## Installation +### Devel +``` +* installing *source* package ‘quid’ ... +** package ‘quid’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘quid’ +* removing ‘/tmp/workdir/quid/new/quid.Rcheck/quid’ ``` ### CRAN ``` -* using log directory ‘/tmp/workdir/robber/old/robber.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘robber/DESCRIPTION’ ... OK -... -* checking tests ... OK - Running ‘spelling.R’ - Running ‘testthat.R’ -* checking for unstated dependencies in vignettes ... OK -* checking package vignettes in ‘inst/doc’ ... OK -* checking running R code from vignettes ... OK - ‘topological-analysis.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: OK - - - +* installing *source* package ‘quid’ ... +** package ‘quid’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘quid’ +* removing ‘/tmp/workdir/quid/old/quid.Rcheck/quid’ ``` -# robmedExtra +# RATest
-* Version: 0.1.0 -* GitHub: https://github.com/aalfons/robmedExtra -* Source code: https://github.com/cran/robmedExtra -* Date/Publication: 2023-06-02 14:40:02 UTC -* Number of recursive dependencies: 96 +* Version: 0.1.10 +* GitHub: https://github.com/ignaciomsarmiento/RATest +* Source code: https://github.com/cran/RATest +* Date/Publication: 2022-09-29 04:30:02 UTC +* Number of recursive dependencies: 54 -Run `revdepcheck::cloud_details(, "robmedExtra")` for more info +Run `revdepcheck::cloud_details(, "RATest")` for more info
## In both -* checking whether package ‘robmedExtra’ can be installed ... ERROR +* checking whether package ‘RATest’ can be installed ... ERROR ``` Installation failed. - See ‘/tmp/workdir/robmedExtra/new/robmedExtra.Rcheck/00install.out’ for details. + See ‘/tmp/workdir/RATest/new/RATest.Rcheck/00install.out’ for details. ``` ## Installation @@ -10392,209 +5727,195 @@ Run `revdepcheck::cloud_details(, "robmedExtra")` for more info ### Devel ``` -* installing *source* package ‘robmedExtra’ ... -** package ‘robmedExtra’ successfully unpacked and MD5 sums checked +* installing *source* package ‘RATest’ ... +** package ‘RATest’ 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: package or namespace load failed for ‘robmed’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): - there is no package called ‘quantreg’ +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace Execution halted -ERROR: lazy loading failed for package ‘robmedExtra’ -* removing ‘/tmp/workdir/robmedExtra/new/robmedExtra.Rcheck/robmedExtra’ +ERROR: lazy loading failed for package ‘RATest’ +* removing ‘/tmp/workdir/RATest/new/RATest.Rcheck/RATest’ ``` ### CRAN ``` -* installing *source* package ‘robmedExtra’ ... -** package ‘robmedExtra’ successfully unpacked and MD5 sums checked +* installing *source* package ‘RATest’ ... +** package ‘RATest’ 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: package or namespace load failed for ‘robmed’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): - there is no package called ‘quantreg’ +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace Execution halted -ERROR: lazy loading failed for package ‘robmedExtra’ -* removing ‘/tmp/workdir/robmedExtra/old/robmedExtra.Rcheck/robmedExtra’ +ERROR: lazy loading failed for package ‘RATest’ +* removing ‘/tmp/workdir/RATest/old/RATest.Rcheck/RATest’ ``` -# rprev +# RcmdrPlugin.RiskDemo
-* Version: 1.0.5 -* GitHub: https://github.com/stulacy/rprev-dev -* Source code: https://github.com/cran/rprev -* Date/Publication: 2021-05-04 16:40:03 UTC -* Number of recursive dependencies: 124 +* Version: 3.2 +* GitHub: NA +* Source code: https://github.com/cran/RcmdrPlugin.RiskDemo +* Date/Publication: 2024-02-06 09:20:02 UTC +* Number of recursive dependencies: 200 -Run `revdepcheck::cloud_details(, "rprev")` for more info +Run `revdepcheck::cloud_details(, "RcmdrPlugin.RiskDemo")` for more info
-## Error before installation +## In both -### Devel +* checking whether package ‘RcmdrPlugin.RiskDemo’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/RcmdrPlugin.RiskDemo/new/RcmdrPlugin.RiskDemo.Rcheck/00install.out’ for details. + ``` -``` -* using log directory ‘/tmp/workdir/rprev/new/rprev.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘rprev/DESCRIPTION’ ... OK -... ---- finished re-building ‘user_guide.Rmd’ +## Installation -SUMMARY: processing the following file failed: - ‘diagnostics.Rmd’ +### Devel -Error: Vignette re-building failed. +``` +* installing *source* package ‘RcmdrPlugin.RiskDemo’ ... +** package ‘RcmdrPlugin.RiskDemo’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** data +** inst +** byte-compile and prepare package for lazy loading +Warning in check_dep_version() : + ABI version mismatch: +lme4 was built with Matrix ABI version 1 +Current Matrix ABI version is 0 +Please re-install lme4 from source or restore original ‘Matrix’ package +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace Execution halted - -* DONE -Status: 1 WARNING, 2 NOTEs - - - +ERROR: lazy loading failed for package ‘RcmdrPlugin.RiskDemo’ +* removing ‘/tmp/workdir/RcmdrPlugin.RiskDemo/new/RcmdrPlugin.RiskDemo.Rcheck/RcmdrPlugin.RiskDemo’ ``` ### CRAN ``` -* using log directory ‘/tmp/workdir/rprev/old/rprev.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘rprev/DESCRIPTION’ ... OK -... ---- finished re-building ‘user_guide.Rmd’ - -SUMMARY: processing the following file failed: - ‘diagnostics.Rmd’ - -Error: Vignette re-building failed. +* installing *source* package ‘RcmdrPlugin.RiskDemo’ ... +** package ‘RcmdrPlugin.RiskDemo’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** data +** inst +** byte-compile and prepare package for lazy loading +Warning in check_dep_version() : + ABI version mismatch: +lme4 was built with Matrix ABI version 1 +Current Matrix ABI version is 0 +Please re-install lme4 from source or restore original ‘Matrix’ package +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace Execution halted - -* DONE -Status: 1 WARNING, 2 NOTEs - - - +ERROR: lazy loading failed for package ‘RcmdrPlugin.RiskDemo’ +* removing ‘/tmp/workdir/RcmdrPlugin.RiskDemo/old/RcmdrPlugin.RiskDemo.Rcheck/RcmdrPlugin.RiskDemo’ ``` -# RQdeltaCT +# rddtools
-* Version: 1.3.0 -* GitHub: NA -* Source code: https://github.com/cran/RQdeltaCT -* Date/Publication: 2024-04-17 15:50:02 UTC -* Number of recursive dependencies: 164 +* Version: 1.6.0 +* GitHub: https://github.com/bquast/rddtools +* Source code: https://github.com/cran/rddtools +* Date/Publication: 2022-01-10 12:42:49 UTC +* Number of recursive dependencies: 106 -Run `revdepcheck::cloud_details(, "RQdeltaCT")` for more info +Run `revdepcheck::cloud_details(, "rddtools")` for more info
-## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/RQdeltaCT/new/RQdeltaCT.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘RQdeltaCT/DESCRIPTION’ ... OK -... -* this is package ‘RQdeltaCT’ version ‘1.3.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘ggpmisc’ +## In both -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR +* checking whether package ‘rddtools’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/rddtools/new/rddtools.Rcheck/00install.out’ for details. + ``` +## Installation +### Devel +``` +* installing *source* package ‘rddtools’ ... +** package ‘rddtools’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** data +** inst +** byte-compile and prepare package for lazy loading +Error: package or namespace load failed for ‘np’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Execution halted +ERROR: lazy loading failed for package ‘rddtools’ +* removing ‘/tmp/workdir/rddtools/new/rddtools.Rcheck/rddtools’ ``` ### CRAN ``` -* using log directory ‘/tmp/workdir/RQdeltaCT/old/RQdeltaCT.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘RQdeltaCT/DESCRIPTION’ ... OK -... -* this is package ‘RQdeltaCT’ version ‘1.3.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘ggpmisc’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - +* installing *source* package ‘rddtools’ ... +** package ‘rddtools’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** data +** inst +** byte-compile and prepare package for lazy loading +Error: package or namespace load failed for ‘np’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Execution halted +ERROR: lazy loading failed for package ‘rddtools’ +* removing ‘/tmp/workdir/rddtools/old/rddtools.Rcheck/rddtools’ ``` -# rstanarm +# riskRegression
-* Version: 2.32.1 -* GitHub: https://github.com/stan-dev/rstanarm -* Source code: https://github.com/cran/rstanarm -* Date/Publication: 2024-01-18 23:00:03 UTC -* Number of recursive dependencies: 138 +* Version: 2023.12.21 +* GitHub: https://github.com/tagteam/riskRegression +* Source code: https://github.com/cran/riskRegression +* Date/Publication: 2023-12-19 17:00:02 UTC +* Number of recursive dependencies: 186 -Run `revdepcheck::cloud_details(, "rstanarm")` for more info +Run `revdepcheck::cloud_details(, "riskRegression")` for more info
## In both -* checking whether package ‘rstanarm’ can be installed ... ERROR +* checking whether package ‘riskRegression’ can be installed ... ERROR ``` Installation failed. - See ‘/tmp/workdir/rstanarm/new/rstanarm.Rcheck/00install.out’ for details. + See ‘/tmp/workdir/riskRegression/new/riskRegression.Rcheck/00install.out’ for details. ``` ## Installation @@ -10602,814 +5923,852 @@ Run `revdepcheck::cloud_details(, "rstanarm")` for more info ### Devel ``` -* installing *source* package ‘rstanarm’ ... -** package ‘rstanarm’ successfully unpacked and MD5 sums checked +* installing *source* package ‘riskRegression’ ... +** package ‘riskRegression’ successfully unpacked and MD5 sums checked ** using staged installation ** libs using C++ compiler: ‘g++ (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ -using C++17 -"/opt/R/4.3.1/lib/R/bin/Rscript" -e "source(file.path('..', 'tools', 'make_cc.R')); make_cc(commandArgs(TRUE))" stan_files/bernoulli.stan -Wrote C++ file "stan_files/bernoulli.cc" - - +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c IC-Nelson-Aalen-cens-time.cpp -o IC-Nelson-Aalen-cens-time.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c aucCVFun.cpp -o aucCVFun.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c baseHaz.cpp -o baseHaz.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c calcSeCSC.cpp -o calcSeCSC.o ... -/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src/stan/mcmc/hmc/hamiltonians/dense_e_metric.hpp:21:10: required from here -/opt/R/4.3.1/lib/R/site-library/RcppEigen/include/Eigen/src/Core/DenseCoeffsBase.h:654:74: warning: ignoring attributes on template argument ‘Eigen::internal::packet_traits::type’ {aka ‘__m128d’} [-Wignored-attributes] - 654 | return internal::first_aligned::alignment),Derived>(m); - | ^~~~~~~~~ -g++: fatal error: Killed signal terminated program cc1plus -compilation terminated. -make: *** [/opt/R/4.3.1/lib/R/etc/Makeconf:198: stan_files/bernoulli.o] Error 1 -rm stan_files/bernoulli.cc -ERROR: compilation failed for package ‘rstanarm’ -* removing ‘/tmp/workdir/rstanarm/new/rstanarm.Rcheck/rstanarm’ +** R +** data +** inst +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘riskRegression’ +* removing ‘/tmp/workdir/riskRegression/new/riskRegression.Rcheck/riskRegression’ ``` ### CRAN ``` -* installing *source* package ‘rstanarm’ ... -** package ‘rstanarm’ successfully unpacked and MD5 sums checked +* installing *source* package ‘riskRegression’ ... +** package ‘riskRegression’ successfully unpacked and MD5 sums checked ** using staged installation ** libs using C++ compiler: ‘g++ (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ -using C++17 -"/opt/R/4.3.1/lib/R/bin/Rscript" -e "source(file.path('..', 'tools', 'make_cc.R')); make_cc(commandArgs(TRUE))" stan_files/bernoulli.stan -Wrote C++ file "stan_files/bernoulli.cc" - - +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c IC-Nelson-Aalen-cens-time.cpp -o IC-Nelson-Aalen-cens-time.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c aucCVFun.cpp -o aucCVFun.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c baseHaz.cpp -o baseHaz.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c calcSeCSC.cpp -o calcSeCSC.o ... -/opt/R/4.3.1/lib/R/site-library/StanHeaders/include/src/stan/mcmc/hmc/hamiltonians/dense_e_metric.hpp:21:10: required from here -/opt/R/4.3.1/lib/R/site-library/RcppEigen/include/Eigen/src/Core/DenseCoeffsBase.h:654:74: warning: ignoring attributes on template argument ‘Eigen::internal::packet_traits::type’ {aka ‘__m128d’} [-Wignored-attributes] - 654 | return internal::first_aligned::alignment),Derived>(m); - | ^~~~~~~~~ -g++: fatal error: Killed signal terminated program cc1plus -compilation terminated. -make: *** [/opt/R/4.3.1/lib/R/etc/Makeconf:198: stan_files/bernoulli.o] Error 1 -rm stan_files/bernoulli.cc -ERROR: compilation failed for package ‘rstanarm’ -* removing ‘/tmp/workdir/rstanarm/old/rstanarm.Rcheck/rstanarm’ +** R +** data +** inst +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘riskRegression’ +* removing ‘/tmp/workdir/riskRegression/old/riskRegression.Rcheck/riskRegression’ ``` -# rTwig +# rms
-* Version: 1.0.2 -* GitHub: https://github.com/aidanmorales/rTwig -* Source code: https://github.com/cran/rTwig -* Date/Publication: 2024-04-08 15:00:02 UTC -* Number of recursive dependencies: 188 +* Version: 6.8-1 +* GitHub: https://github.com/harrelfe/rms +* Source code: https://github.com/cran/rms +* Date/Publication: 2024-05-27 12:00:02 UTC +* Number of recursive dependencies: 145 -Run `revdepcheck::cloud_details(, "rTwig")` for more info +Run `revdepcheck::cloud_details(, "rms")` for more info
-## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/rTwig/new/rTwig.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘rTwig/DESCRIPTION’ ... OK -... -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required and available but unsuitable version: ‘Matrix’ +## In both -Package suggested but not available for checking: ‘ggpmisc’ +* checking whether package ‘rms’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/rms/new/rms.Rcheck/00install.out’ for details. + ``` -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR +* checking package dependencies ... NOTE + ``` + Package suggested but not available for checking: ‘rmsb’ + ``` +## Installation +### Devel +``` +* installing *source* package ‘rms’ ... +** package ‘rms’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C compiler: ‘gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ +using Fortran compiler: ‘GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ +gcc -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I/usr/local/include -fpic -g -O2 -c init.c -o init.o +gfortran -fpic -g -O2 -c lrmfit.f -o lrmfit.o +gfortran -fpic -g -O2 -c mlmats.f -o mlmats.o +gfortran -fpic -g -O2 -c ormuv.f -o ormuv.o +... +** R +** demo +** inst +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘rms’ +* removing ‘/tmp/workdir/rms/new/rms.Rcheck/rms’ ``` ### CRAN ``` -* using log directory ‘/tmp/workdir/rTwig/old/rTwig.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘rTwig/DESCRIPTION’ ... OK +* installing *source* package ‘rms’ ... +** package ‘rms’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C compiler: ‘gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ +using Fortran compiler: ‘GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ +gcc -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I/usr/local/include -fpic -g -O2 -c init.c -o init.o +gfortran -fpic -g -O2 -c lrmfit.f -o lrmfit.o +gfortran -fpic -g -O2 -c mlmats.f -o mlmats.o +gfortran -fpic -g -O2 -c ormuv.f -o ormuv.o ... -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required and available but unsuitable version: ‘Matrix’ +** R +** demo +** inst +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘rms’ +* removing ‘/tmp/workdir/rms/old/rms.Rcheck/rms’ -Package suggested but not available for checking: ‘ggpmisc’ -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR +``` +# rmsb +
+* Version: 1.1-1 +* GitHub: NA +* Source code: https://github.com/cran/rmsb +* Date/Publication: 2024-07-08 11:10:03 UTC +* Number of recursive dependencies: 135 +Run `revdepcheck::cloud_details(, "rmsb")` for more info +
-``` -# scCustomize +## In both -
+* checking whether package ‘rmsb’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/rmsb/new/rmsb.Rcheck/00install.out’ for details. + ``` -* Version: 2.1.2 -* GitHub: https://github.com/samuel-marsh/scCustomize -* Source code: https://github.com/cran/scCustomize -* Date/Publication: 2024-02-28 19:40:02 UTC -* Number of recursive dependencies: 273 +## Installation -Run `revdepcheck::cloud_details(, "scCustomize")` for more info +### Devel -
+``` +* installing *source* package ‘rmsb’ ... +** package ‘rmsb’ successfully unpacked and MD5 sums checked +** using staged installation +Error in loadNamespace(x) : there is no package called ‘rstantools’ +Calls: loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Execution halted +ERROR: configuration failed for package ‘rmsb’ +* removing ‘/tmp/workdir/rmsb/new/rmsb.Rcheck/rmsb’ -## Error before installation -### Devel +``` +### CRAN ``` -* using log directory ‘/tmp/workdir/scCustomize/new/scCustomize.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘scCustomize/DESCRIPTION’ ... OK -... -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Packages required but not available: 'Seurat', 'SeuratObject' +* installing *source* package ‘rmsb’ ... +** package ‘rmsb’ successfully unpacked and MD5 sums checked +** using staged installation +Error in loadNamespace(x) : there is no package called ‘rstantools’ +Calls: loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Execution halted +ERROR: configuration failed for package ‘rmsb’ +* removing ‘/tmp/workdir/rmsb/old/rmsb.Rcheck/rmsb’ -Package suggested but not available for checking: ‘Nebulosa’ -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR +``` +# robmed +
+* Version: 1.0.2 +* GitHub: https://github.com/aalfons/robmed +* Source code: https://github.com/cran/robmed +* Date/Publication: 2023-06-16 23:00:02 UTC +* Number of recursive dependencies: 60 +Run `revdepcheck::cloud_details(, "robmed")` for more info +
-``` -### CRAN +## In both -``` -* using log directory ‘/tmp/workdir/scCustomize/old/scCustomize.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘scCustomize/DESCRIPTION’ ... OK -... -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Packages required but not available: 'Seurat', 'SeuratObject' +* checking whether package ‘robmed’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/robmed/new/robmed.Rcheck/00install.out’ for details. + ``` -Package suggested but not available for checking: ‘Nebulosa’ +## Installation -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR +### Devel + +``` +* installing *source* package ‘robmed’ ... +** package ‘robmed’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘robmed’ +* removing ‘/tmp/workdir/robmed/new/robmed.Rcheck/robmed’ +``` +### CRAN +``` +* installing *source* package ‘robmed’ ... +** package ‘robmed’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘robmed’ +* removing ‘/tmp/workdir/robmed/old/robmed.Rcheck/robmed’ ``` -# SCdeconR +# robmedExtra
-* Version: 1.0.0 -* GitHub: https://github.com/Liuy12/SCdeconR -* Source code: https://github.com/cran/SCdeconR -* Date/Publication: 2024-03-22 19:20:02 UTC -* Number of recursive dependencies: 235 +* Version: 0.1.0 +* GitHub: https://github.com/aalfons/robmedExtra +* Source code: https://github.com/cran/robmedExtra +* Date/Publication: 2023-06-02 14:40:02 UTC +* Number of recursive dependencies: 96 -Run `revdepcheck::cloud_details(, "SCdeconR")` for more info +Run `revdepcheck::cloud_details(, "robmedExtra")` for more info
-## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/SCdeconR/new/SCdeconR.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘SCdeconR/DESCRIPTION’ ... OK -... -* this is package ‘SCdeconR’ version ‘1.0.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘Seurat’ +## In both -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR +* checking whether package ‘robmedExtra’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/robmedExtra/new/robmedExtra.Rcheck/00install.out’ for details. + ``` +## Installation +### Devel +``` +* installing *source* package ‘robmedExtra’ ... +** package ‘robmedExtra’ 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 ‘robmed’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Execution halted +ERROR: lazy loading failed for package ‘robmedExtra’ +* removing ‘/tmp/workdir/robmedExtra/new/robmedExtra.Rcheck/robmedExtra’ ``` ### CRAN ``` -* using log directory ‘/tmp/workdir/SCdeconR/old/SCdeconR.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘SCdeconR/DESCRIPTION’ ... OK -... -* this is package ‘SCdeconR’ version ‘1.0.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘Seurat’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - +* installing *source* package ‘robmedExtra’ ... +** package ‘robmedExtra’ 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 ‘robmed’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Execution halted +ERROR: lazy loading failed for package ‘robmedExtra’ +* removing ‘/tmp/workdir/robmedExtra/old/robmedExtra.Rcheck/robmedExtra’ ``` -# scDiffCom +# RPPanalyzer
-* Version: 1.0.0 +* Version: 1.4.9 * GitHub: NA -* Source code: https://github.com/cran/scDiffCom -* Date/Publication: 2023-11-03 18:40:02 UTC -* Number of recursive dependencies: 259 +* Source code: https://github.com/cran/RPPanalyzer +* Date/Publication: 2024-01-25 11:00:02 UTC +* Number of recursive dependencies: 82 -Run `revdepcheck::cloud_details(, "scDiffCom")` for more info +Run `revdepcheck::cloud_details(, "RPPanalyzer")` for more info
-## Error before installation +## In both + +* checking whether package ‘RPPanalyzer’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/RPPanalyzer/new/RPPanalyzer.Rcheck/00install.out’ for details. + ``` + +## Installation ### Devel ``` -* using log directory ‘/tmp/workdir/scDiffCom/new/scDiffCom.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘scDiffCom/DESCRIPTION’ ... OK -... -* this is package ‘scDiffCom’ version ‘1.0.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘Seurat’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR +* installing *source* package ‘RPPanalyzer’ ... +** package ‘RPPanalyzer’ successfully unpacked and MD5 sums checked +** 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘RPPanalyzer’ +* removing ‘/tmp/workdir/RPPanalyzer/new/RPPanalyzer.Rcheck/RPPanalyzer’ +``` +### CRAN +``` +* installing *source* package ‘RPPanalyzer’ ... +** package ‘RPPanalyzer’ successfully unpacked and MD5 sums checked +** 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘RPPanalyzer’ +* removing ‘/tmp/workdir/RPPanalyzer/old/RPPanalyzer.Rcheck/RPPanalyzer’ ``` -### CRAN +# RQdeltaCT -``` -* using log directory ‘/tmp/workdir/scDiffCom/old/scDiffCom.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘scDiffCom/DESCRIPTION’ ... OK -... -* this is package ‘scDiffCom’ version ‘1.0.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘Seurat’ +
-See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR +* Version: 1.3.0 +* GitHub: NA +* Source code: https://github.com/cran/RQdeltaCT +* Date/Publication: 2024-04-17 15:50:02 UTC +* Number of recursive dependencies: 165 +Run `revdepcheck::cloud_details(, "RQdeltaCT")` for more info +
+## In both +* checking whether package ‘RQdeltaCT’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/RQdeltaCT/new/RQdeltaCT.Rcheck/00install.out’ for details. + ``` -``` -# scGate +## Installation -
+### Devel -* Version: 1.6.2 -* GitHub: https://github.com/carmonalab/scGate -* Source code: https://github.com/cran/scGate -* Date/Publication: 2024-04-23 08:50:02 UTC -* Number of recursive dependencies: 178 +``` +* installing *source* package ‘RQdeltaCT’ ... +** package ‘RQdeltaCT’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘RQdeltaCT’ +* removing ‘/tmp/workdir/RQdeltaCT/new/RQdeltaCT.Rcheck/RQdeltaCT’ -Run `revdepcheck::cloud_details(, "scGate")` for more info -
+``` +### CRAN -## Error before installation +``` +* installing *source* package ‘RQdeltaCT’ ... +** package ‘RQdeltaCT’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘RQdeltaCT’ +* removing ‘/tmp/workdir/RQdeltaCT/old/RQdeltaCT.Rcheck/RQdeltaCT’ -### Devel ``` -* using log directory ‘/tmp/workdir/scGate/new/scGate.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘scGate/DESCRIPTION’ ... OK -... -* this is package ‘scGate’ version ‘1.6.2’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘Seurat’ +# scCustomize -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR +
+* Version: 2.1.2 +* GitHub: https://github.com/samuel-marsh/scCustomize +* Source code: https://github.com/cran/scCustomize +* Date/Publication: 2024-02-28 19:40:02 UTC +* Number of recursive dependencies: 267 +Run `revdepcheck::cloud_details(, "scCustomize")` for more info +
+## In both -``` -### CRAN +* checking whether package ‘scCustomize’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/scCustomize/new/scCustomize.Rcheck/00install.out’ for details. + ``` -``` -* using log directory ‘/tmp/workdir/scGate/old/scGate.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘scGate/DESCRIPTION’ ... OK -... -* this is package ‘scGate’ version ‘1.6.2’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘Seurat’ +* checking package dependencies ... NOTE + ``` + Package suggested but not available for checking: ‘Nebulosa’ + ``` + +## Installation -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR +### Devel + +``` +* installing *source* package ‘scCustomize’ ... +** package ‘scCustomize’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** data +*** moving datasets to lazyload DB +** byte-compile and prepare package for lazy loading +Error: package or namespace load failed for ‘SeuratObject’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): + namespace ‘Matrix’ 1.5-4.1 is being loaded, but >= 1.6.4 is required +Execution halted +ERROR: lazy loading failed for package ‘scCustomize’ +* removing ‘/tmp/workdir/scCustomize/new/scCustomize.Rcheck/scCustomize’ +``` +### CRAN +``` +* installing *source* package ‘scCustomize’ ... +** package ‘scCustomize’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** data +*** moving datasets to lazyload DB +** byte-compile and prepare package for lazy loading +Error: package or namespace load failed for ‘SeuratObject’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): + namespace ‘Matrix’ 1.5-4.1 is being loaded, but >= 1.6.4 is required +Execution halted +ERROR: lazy loading failed for package ‘scCustomize’ +* removing ‘/tmp/workdir/scCustomize/old/scCustomize.Rcheck/scCustomize’ ``` -# scMappR +# SCdeconR
-* Version: 1.0.11 -* GitHub: NA -* Source code: https://github.com/cran/scMappR -* Date/Publication: 2023-06-30 08:40:08 UTC -* Number of recursive dependencies: 233 +* Version: 1.0.0 +* GitHub: https://github.com/Liuy12/SCdeconR +* Source code: https://github.com/cran/SCdeconR +* Date/Publication: 2024-03-22 19:20:02 UTC +* Number of recursive dependencies: 236 -Run `revdepcheck::cloud_details(, "scMappR")` for more info +Run `revdepcheck::cloud_details(, "SCdeconR")` for more info
-## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/scMappR/new/scMappR.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘scMappR/DESCRIPTION’ ... OK -... -* this is package ‘scMappR’ version ‘1.0.11’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘Seurat’ +## In both -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR +* checking whether package ‘SCdeconR’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/SCdeconR/new/SCdeconR.Rcheck/00install.out’ for details. + ``` +## Installation +### Devel +``` +* installing *source* package ‘SCdeconR’ ... +** package ‘SCdeconR’ 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 ‘SeuratObject’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): + namespace ‘Matrix’ 1.5-4.1 is being loaded, but >= 1.6.4 is required +Execution halted +ERROR: lazy loading failed for package ‘SCdeconR’ +* removing ‘/tmp/workdir/SCdeconR/new/SCdeconR.Rcheck/SCdeconR’ ``` ### CRAN ``` -* using log directory ‘/tmp/workdir/scMappR/old/scMappR.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘scMappR/DESCRIPTION’ ... OK -... -* this is package ‘scMappR’ version ‘1.0.11’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘Seurat’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - +* installing *source* package ‘SCdeconR’ ... +** package ‘SCdeconR’ 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 ‘SeuratObject’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): + namespace ‘Matrix’ 1.5-4.1 is being loaded, but >= 1.6.4 is required +Execution halted +ERROR: lazy loading failed for package ‘SCdeconR’ +* removing ‘/tmp/workdir/SCdeconR/old/SCdeconR.Rcheck/SCdeconR’ ``` -# SCORPIUS +# scGate
-* Version: 1.0.9 -* GitHub: https://github.com/rcannood/SCORPIUS -* Source code: https://github.com/cran/SCORPIUS -* Date/Publication: 2023-08-07 17:30:05 UTC -* Number of recursive dependencies: 202 +* Version: 1.6.2 +* GitHub: https://github.com/carmonalab/scGate +* Source code: https://github.com/cran/scGate +* Date/Publication: 2024-04-23 08:50:02 UTC +* Number of recursive dependencies: 179 -Run `revdepcheck::cloud_details(, "SCORPIUS")` for more info +Run `revdepcheck::cloud_details(, "scGate")` for more info
-## Error before installation +## In both + +* checking whether package ‘scGate’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/scGate/new/scGate.Rcheck/00install.out’ for details. + ``` + +## Installation ### Devel ``` -* using log directory ‘/tmp/workdir/SCORPIUS/new/SCORPIUS.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘SCORPIUS/DESCRIPTION’ ... OK -... -Run `reticulate::py_last_error()` for details. +* installing *source* package ‘scGate’ ... +** package ‘scGate’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** data +*** moving datasets to lazyload DB +Warning: namespace ‘Seurat’ is not available and has been replaced +by .GlobalEnv when processing object ‘query.seurat’ +Warning: namespace ‘Seurat’ is not available and has been replaced +by .GlobalEnv when processing object ‘query.seurat’ +** inst +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.4 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace Execution halted - - ‘anndata.Rmd’ using ‘UTF-8’... failed - ‘ginhoux.Rmd’ using ‘UTF-8’... OK - ‘simulated-data.Rmd’ using ‘UTF-8’... OK - ‘singlecellexperiment.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: 1 ERROR, 1 NOTE - - - +ERROR: lazy loading failed for package ‘scGate’ +* removing ‘/tmp/workdir/scGate/new/scGate.Rcheck/scGate’ ``` ### CRAN ``` -* using log directory ‘/tmp/workdir/SCORPIUS/old/SCORPIUS.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘SCORPIUS/DESCRIPTION’ ... OK -... -Run `reticulate::py_last_error()` for details. +* installing *source* package ‘scGate’ ... +** package ‘scGate’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** data +*** moving datasets to lazyload DB +Warning: namespace ‘Seurat’ is not available and has been replaced +by .GlobalEnv when processing object ‘query.seurat’ +Warning: namespace ‘Seurat’ is not available and has been replaced +by .GlobalEnv when processing object ‘query.seurat’ +** inst +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.4 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace Execution halted - - ‘anndata.Rmd’ using ‘UTF-8’... failed - ‘ginhoux.Rmd’ using ‘UTF-8’... OK - ‘simulated-data.Rmd’ using ‘UTF-8’... OK - ‘singlecellexperiment.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: 1 ERROR, 1 NOTE - - - +ERROR: lazy loading failed for package ‘scGate’ +* removing ‘/tmp/workdir/scGate/old/scGate.Rcheck/scGate’ ``` -# scpi +# SCIntRuler
-* Version: 2.2.5 -* GitHub: NA -* Source code: https://github.com/cran/scpi -* Date/Publication: 2023-11-01 06:10:07 UTC -* Number of recursive dependencies: 97 +* Version: 0.99.6 +* GitHub: https://github.com/yuelyu21/SCIntRuler +* Source code: https://github.com/cran/SCIntRuler +* Date/Publication: 2024-07-12 15:20:08 UTC +* Number of recursive dependencies: 202 -Run `revdepcheck::cloud_details(, "scpi")` for more info +Run `revdepcheck::cloud_details(, "SCIntRuler")` for more info
-## Error before installation +## In both + +* checking whether package ‘SCIntRuler’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/SCIntRuler/new/SCIntRuler.Rcheck/00install.out’ for details. + ``` + +## Installation ### Devel ``` -* using log directory ‘/tmp/workdir/scpi/new/scpi.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘scpi/DESCRIPTION’ ... OK +* installing *source* package ‘SCIntRuler’ ... +** package ‘SCIntRuler’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C++ compiler: ‘g++ (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c crossdist.cpp -o crossdist.o +g++ -std=gnu++17 -shared -L/opt/R/4.3.1/lib/R/lib -L/usr/local/lib -o SCIntRuler.so RcppExports.o crossdist.o -L/opt/R/4.3.1/lib/R/lib -lR +installing to /tmp/workdir/SCIntRuler/new/SCIntRuler.Rcheck/00LOCK-SCIntRuler/00new/SCIntRuler/libs +** R ... -* this is package ‘scpi’ version ‘2.2.5’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘Qtools’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - +** 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]]) : + namespace ‘Matrix’ 1.5-4.1 is being loaded, but >= 1.6.4 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘SCIntRuler’ +* removing ‘/tmp/workdir/SCIntRuler/new/SCIntRuler.Rcheck/SCIntRuler’ ``` ### CRAN ``` -* using log directory ‘/tmp/workdir/scpi/old/scpi.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘scpi/DESCRIPTION’ ... OK +* installing *source* package ‘SCIntRuler’ ... +** package ‘SCIntRuler’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C++ compiler: ‘g++ (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c crossdist.cpp -o crossdist.o +g++ -std=gnu++17 -shared -L/opt/R/4.3.1/lib/R/lib -L/usr/local/lib -o SCIntRuler.so RcppExports.o crossdist.o -L/opt/R/4.3.1/lib/R/lib -lR +installing to /tmp/workdir/SCIntRuler/old/SCIntRuler.Rcheck/00LOCK-SCIntRuler/00new/SCIntRuler/libs +** R ... -* this is package ‘scpi’ version ‘2.2.5’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘Qtools’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - +** 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]]) : + namespace ‘Matrix’ 1.5-4.1 is being loaded, but >= 1.6.4 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘SCIntRuler’ +* removing ‘/tmp/workdir/SCIntRuler/old/SCIntRuler.Rcheck/SCIntRuler’ ``` -# scpoisson +# scMappR
-* Version: 0.0.1 +* Version: 1.0.11 * GitHub: NA -* Source code: https://github.com/cran/scpoisson -* Date/Publication: 2022-08-17 06:50:02 UTC -* Number of recursive dependencies: 202 - -Run `revdepcheck::cloud_details(, "scpoisson")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/scpoisson/new/scpoisson.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘scpoisson/DESCRIPTION’ ... OK -... -* this is package ‘scpoisson’ version ‘0.0.1’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Packages required but not available: 'Seurat', 'SeuratObject' +* Source code: https://github.com/cran/scMappR +* Date/Publication: 2023-06-30 08:40:08 UTC +* Number of recursive dependencies: 234 -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR +Run `revdepcheck::cloud_details(, "scMappR")` for more info +
+## In both +* checking whether package ‘scMappR’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/scMappR/new/scMappR.Rcheck/00install.out’ for details. + ``` +## Installation -``` -### CRAN +### Devel ``` -* using log directory ‘/tmp/workdir/scpoisson/old/scpoisson.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘scpoisson/DESCRIPTION’ ... OK -... -* this is package ‘scpoisson’ version ‘0.0.1’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Packages required but not available: 'Seurat', 'SeuratObject' - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR +* installing *source* package ‘scMappR’ ... +** package ‘scMappR’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.4 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘scMappR’ +* removing ‘/tmp/workdir/scMappR/new/scMappR.Rcheck/scMappR’ +``` +### CRAN +``` +* installing *source* package ‘scMappR’ ... +** package ‘scMappR’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.4 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘scMappR’ +* removing ‘/tmp/workdir/scMappR/old/scMappR.Rcheck/scMappR’ ``` -# SCpubr +# scpi
-* Version: 2.0.2 -* GitHub: https://github.com/enblacar/SCpubr -* Source code: https://github.com/cran/SCpubr -* Date/Publication: 2023-10-11 09:50:02 UTC -* Number of recursive dependencies: 305 +* Version: 2.2.5 +* GitHub: NA +* Source code: https://github.com/cran/scpi +* Date/Publication: 2023-11-01 06:10:07 UTC +* Number of recursive dependencies: 98 -Run `revdepcheck::cloud_details(, "SCpubr")` for more info +Run `revdepcheck::cloud_details(, "scpi")` for more info
-## Error before installation - -### Devel +## In both -``` -* using log directory ‘/tmp/workdir/SCpubr/new/SCpubr.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘SCpubr/DESCRIPTION’ ... OK -... -* checking for unstated dependencies in ‘tests’ ... OK -* checking tests ... OK - Running ‘testthat.R’ -* checking for unstated dependencies in vignettes ... OK -* checking package vignettes in ‘inst/doc’ ... OK -* checking running R code from vignettes ... NONE - ‘reference_manual.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: 2 NOTEs +* checking whether package ‘scpi’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/scpi/new/scpi.Rcheck/00install.out’ for details. + ``` +## Installation +### Devel +``` +* installing *source* package ‘scpi’ ... +** package ‘scpi’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** data +*** moving datasets to lazyload DB +** byte-compile and prepare package for lazy loading +Warning in .recacheSubclasses(def@className, def, env) : + undefined subclass "pcorMatrix" of class "ConstVal"; definition not updated +Warning in .recacheSubclasses(def@className, def, env) : +... +Warning in .recacheSubclasses(def@className, def, env) : + undefined subclass "pcorMatrix" of class "ConstValORExpr"; definition not updated +Warning in .recacheSubclasses(def@className, def, env) : + undefined subclass "pcorMatrix" of class "ConstValORNULL"; definition not updated +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘scpi’ +* removing ‘/tmp/workdir/scpi/new/scpi.Rcheck/scpi’ ``` ### CRAN ``` -* using log directory ‘/tmp/workdir/SCpubr/old/SCpubr.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘SCpubr/DESCRIPTION’ ... OK -... -* checking for unstated dependencies in ‘tests’ ... OK -* checking tests ... OK - Running ‘testthat.R’ -* checking for unstated dependencies in vignettes ... OK -* checking package vignettes in ‘inst/doc’ ... OK -* checking running R code from vignettes ... NONE - ‘reference_manual.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: 2 NOTEs - - - +* installing *source* package ‘scpi’ ... +** package ‘scpi’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** data +*** moving datasets to lazyload DB +** byte-compile and prepare package for lazy loading +Warning in .recacheSubclasses(def@className, def, env) : + undefined subclass "pcorMatrix" of class "ConstVal"; definition not updated +Warning in .recacheSubclasses(def@className, def, env) : +... +Warning in .recacheSubclasses(def@className, def, env) : + undefined subclass "pcorMatrix" of class "ConstValORExpr"; definition not updated +Warning in .recacheSubclasses(def@className, def, env) : + undefined subclass "pcorMatrix" of class "ConstValORNULL"; definition not updated +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘scpi’ +* removing ‘/tmp/workdir/scpi/old/scpi.Rcheck/scpi’ ``` @@ -11421,71 +6780,73 @@ Status: 2 NOTEs * GitHub: NA * Source code: https://github.com/cran/scRNAstat * Date/Publication: 2021-09-22 08:10:02 UTC -* Number of recursive dependencies: 155 +* Number of recursive dependencies: 156 Run `revdepcheck::cloud_details(, "scRNAstat")` for more info
-## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/scRNAstat/new/scRNAstat.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘scRNAstat/DESCRIPTION’ ... OK -... -* this is package ‘scRNAstat’ version ‘0.1.1’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘Seurat’ +## In both -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR +* checking whether package ‘scRNAstat’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/scRNAstat/new/scRNAstat.Rcheck/00install.out’ for details. + ``` +## Installation +### Devel +``` +* installing *source* package ‘scRNAstat’ ... +** package ‘scRNAstat’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** data +*** moving datasets to lazyload DB +Warning: namespace ‘Seurat’ is not available and has been replaced +by .GlobalEnv when processing object ‘AJ064_small_last_sce’ +Warning: namespace ‘SeuratObject’ is not available and has been replaced +by .GlobalEnv when processing object ‘AJ064_small_last_sce’ +... +by .GlobalEnv when processing object ‘AJ064_small_last_sce’ +Warning: namespace ‘DBI’ is not available and has been replaced +by .GlobalEnv when processing object ‘AJ064_small_last_sce’ +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.4 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘scRNAstat’ +* removing ‘/tmp/workdir/scRNAstat/new/scRNAstat.Rcheck/scRNAstat’ ``` ### CRAN ``` -* using log directory ‘/tmp/workdir/scRNAstat/old/scRNAstat.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘scRNAstat/DESCRIPTION’ ... OK -... -* this is package ‘scRNAstat’ version ‘0.1.1’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘Seurat’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - +* installing *source* package ‘scRNAstat’ ... +** package ‘scRNAstat’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** data +*** moving datasets to lazyload DB +Warning: namespace ‘Seurat’ is not available and has been replaced +by .GlobalEnv when processing object ‘AJ064_small_last_sce’ +Warning: namespace ‘SeuratObject’ is not available and has been replaced +by .GlobalEnv when processing object ‘AJ064_small_last_sce’ +... +by .GlobalEnv when processing object ‘AJ064_small_last_sce’ +Warning: namespace ‘DBI’ is not available and has been replaced +by .GlobalEnv when processing object ‘AJ064_small_last_sce’ +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.4 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘scRNAstat’ +* removing ‘/tmp/workdir/scRNAstat/old/scRNAstat.Rcheck/scRNAstat’ ``` @@ -11524,9 +6885,9 @@ Run `revdepcheck::cloud_details(, "sectorgap")` for more info *** moving datasets to lazyload DB ** 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 ‘quantreg’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace Execution halted ERROR: lazy loading failed for package ‘sectorgap’ * removing ‘/tmp/workdir/sectorgap/new/sectorgap.Rcheck/sectorgap’ @@ -11544,9 +6905,9 @@ ERROR: lazy loading failed for package ‘sectorgap’ *** moving datasets to lazyload DB ** 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 ‘quantreg’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace Execution halted ERROR: lazy loading failed for package ‘sectorgap’ * removing ‘/tmp/workdir/sectorgap/old/sectorgap.Rcheck/sectorgap’ @@ -11561,7 +6922,7 @@ ERROR: lazy loading failed for package ‘sectorgap’ * GitHub: NA * Source code: https://github.com/cran/SEERaBomb * Date/Publication: 2019-12-12 18:50:03 UTC -* Number of recursive dependencies: 184 +* Number of recursive dependencies: 185 Run `revdepcheck::cloud_details(, "SEERaBomb")` for more info @@ -11597,7 +6958,7 @@ g++ -std=gnu++17 -shared -L/opt/R/4.3.1/lib/R/lib -L/usr/local/lib -o SEERaBomb. ** inst ** byte-compile and prepare package for lazy loading Error: package or namespace load failed for ‘demography’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): - there is no package called ‘quantreg’ + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required Execution halted ERROR: lazy loading failed for package ‘SEERaBomb’ * removing ‘/tmp/workdir/SEERaBomb/new/SEERaBomb.Rcheck/SEERaBomb’ @@ -11624,7 +6985,7 @@ g++ -std=gnu++17 -shared -L/opt/R/4.3.1/lib/R/lib -L/usr/local/lib -o SEERaBomb. ** inst ** byte-compile and prepare package for lazy loading Error: package or namespace load failed for ‘demography’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): - there is no package called ‘quantreg’ + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required Execution halted ERROR: lazy loading failed for package ‘SEERaBomb’ * removing ‘/tmp/workdir/SEERaBomb/old/SEERaBomb.Rcheck/SEERaBomb’ @@ -11724,9 +7085,9 @@ Run `revdepcheck::cloud_details(, "SensMap")` for more info *** moving datasets to lazyload DB ** 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 ‘quantreg’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace Execution halted ERROR: lazy loading failed for package ‘SensMap’ * removing ‘/tmp/workdir/SensMap/new/SensMap.Rcheck/SensMap’ @@ -11744,88 +7105,150 @@ ERROR: lazy loading failed for package ‘SensMap’ *** moving datasets to lazyload DB ** 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 ‘quantreg’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace Execution halted ERROR: lazy loading failed for package ‘SensMap’ * removing ‘/tmp/workdir/SensMap/old/SensMap.Rcheck/SensMap’ ``` -# shinyTempSignal +# Seurat
-* Version: 0.0.8 -* GitHub: https://github.com/YuLab-SMU/shinyTempSignal -* Source code: https://github.com/cran/shinyTempSignal -* Date/Publication: 2024-03-06 08:00:02 UTC -* Number of recursive dependencies: 137 +* Version: 5.1.0 +* GitHub: https://github.com/satijalab/seurat +* Source code: https://github.com/cran/Seurat +* Date/Publication: 2024-05-10 17:23:17 UTC +* Number of recursive dependencies: 266 -Run `revdepcheck::cloud_details(, "shinyTempSignal")` for more info +Run `revdepcheck::cloud_details(, "Seurat")` for more info
-## Error before installation +## In both + +* checking whether package ‘Seurat’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/Seurat/new/Seurat.Rcheck/00install.out’ for details. + ``` + +## Installation ### Devel ``` -* using log directory ‘/tmp/workdir/shinyTempSignal/new/shinyTempSignal.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘shinyTempSignal/DESCRIPTION’ ... OK +* installing *source* package ‘Seurat’ ... +** package ‘Seurat’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C compiler: ‘gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ +using C++ compiler: ‘g++ (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ +using C++17 +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppEigen/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppProgress/include' -I/usr/local/include -fpic -g -O2 -c ModularityOptimizer.cpp -o ModularityOptimizer.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppEigen/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppProgress/include' -I/usr/local/include -fpic -g -O2 -c RModularityOptimizer.cpp -o RModularityOptimizer.o +In file included from /opt/R/4.3.1/lib/R/site-library/RcppEigen/include/Eigen/Core:205, ... -* this is package ‘shinyTempSignal’ version ‘0.0.8’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘ggpmisc’ +** R +** data +*** moving datasets to lazyload DB +** inst +** byte-compile and prepare package for lazy loading +Error: package or namespace load failed for ‘SeuratObject’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): + namespace ‘Matrix’ 1.5-4.1 is being loaded, but >= 1.6.4 is required +Execution halted +ERROR: lazy loading failed for package ‘Seurat’ +* removing ‘/tmp/workdir/Seurat/new/Seurat.Rcheck/Seurat’ + + +``` +### CRAN + +``` +* installing *source* package ‘Seurat’ ... +** package ‘Seurat’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C compiler: ‘gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ +using C++ compiler: ‘g++ (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ +using C++17 +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppEigen/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppProgress/include' -I/usr/local/include -fpic -g -O2 -c ModularityOptimizer.cpp -o ModularityOptimizer.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppEigen/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppProgress/include' -I/usr/local/include -fpic -g -O2 -c RModularityOptimizer.cpp -o RModularityOptimizer.o +In file included from /opt/R/4.3.1/lib/R/site-library/RcppEigen/include/Eigen/Core:205, +... +** R +** data +*** moving datasets to lazyload DB +** inst +** byte-compile and prepare package for lazy loading +Error: package or namespace load failed for ‘SeuratObject’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): + namespace ‘Matrix’ 1.5-4.1 is being loaded, but >= 1.6.4 is required +Execution halted +ERROR: lazy loading failed for package ‘Seurat’ +* removing ‘/tmp/workdir/Seurat/old/Seurat.Rcheck/Seurat’ + + +``` +# shinyTempSignal + +
-See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR +* Version: 0.0.8 +* GitHub: https://github.com/YuLab-SMU/shinyTempSignal +* Source code: https://github.com/cran/shinyTempSignal +* Date/Publication: 2024-03-06 08:00:02 UTC +* Number of recursive dependencies: 137 +Run `revdepcheck::cloud_details(, "shinyTempSignal")` for more info +
+## In both +* checking whether package ‘shinyTempSignal’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/shinyTempSignal/new/shinyTempSignal.Rcheck/00install.out’ for details. + ``` -``` -### CRAN +## Installation -``` -* using log directory ‘/tmp/workdir/shinyTempSignal/old/shinyTempSignal.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘shinyTempSignal/DESCRIPTION’ ... OK -... -* this is package ‘shinyTempSignal’ version ‘0.0.8’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘ggpmisc’ +### Devel -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR +``` +* installing *source* package ‘shinyTempSignal’ ... +** package ‘shinyTempSignal’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘shinyTempSignal’ +* removing ‘/tmp/workdir/shinyTempSignal/new/shinyTempSignal.Rcheck/shinyTempSignal’ +``` +### CRAN +``` +* installing *source* package ‘shinyTempSignal’ ... +** package ‘shinyTempSignal’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘shinyTempSignal’ +* removing ‘/tmp/workdir/shinyTempSignal/old/shinyTempSignal.Rcheck/shinyTempSignal’ ``` @@ -11837,7 +7260,7 @@ Status: 1 ERROR * GitHub: https://github.com/mjuraska/sievePH * Source code: https://github.com/cran/sievePH * Date/Publication: 2024-05-17 23:40:02 UTC -* Number of recursive dependencies: 86 +* Number of recursive dependencies: 72 Run `revdepcheck::cloud_details(, "sievePH")` for more info @@ -11868,8 +7291,8 @@ installing to /tmp/workdir/sievePH/new/sievePH.Rcheck/00LOCK-sievePH/00new/sieve ** R ** 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 ‘quantreg’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace Execution halted ERROR: lazy loading failed for package ‘sievePH’ * removing ‘/tmp/workdir/sievePH/new/sievePH.Rcheck/sievePH’ @@ -11891,8 +7314,8 @@ installing to /tmp/workdir/sievePH/old/sievePH.Rcheck/00LOCK-sievePH/00new/sieve ** R ** 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 ‘quantreg’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace Execution halted ERROR: lazy loading failed for package ‘sievePH’ * removing ‘/tmp/workdir/sievePH/old/sievePH.Rcheck/sievePH’ @@ -11907,223 +7330,147 @@ ERROR: lazy loading failed for package ‘sievePH’ * GitHub: https://github.com/stuart-lab/signac * Source code: https://github.com/cran/Signac * Date/Publication: 2024-04-04 02:42:57 UTC -* Number of recursive dependencies: 249 +* Number of recursive dependencies: 250 Run `revdepcheck::cloud_details(, "Signac")` for more info
-## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/Signac/new/Signac.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘Signac/DESCRIPTION’ ... OK -... -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘SeuratObject’ - -Package suggested but not available for checking: ‘Seurat’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/Signac/old/Signac.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘Signac/DESCRIPTION’ ... OK -... -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘SeuratObject’ - -Package suggested but not available for checking: ‘Seurat’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# simET - -
- -* Version: 1.0.3 -* GitHub: NA -* Source code: https://github.com/cran/simET -* Date/Publication: 2023-08-19 14:40:02 UTC -* Number of recursive dependencies: 97 - -Run `revdepcheck::cloud_details(, "simET")` for more info +## In both -
+* checking whether package ‘Signac’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/Signac/new/Signac.Rcheck/00install.out’ for details. + ``` -## Error before installation +## Installation ### Devel ``` -* using log directory ‘/tmp/workdir/simET/new/simET.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘simET/DESCRIPTION’ ... OK +* installing *source* package ‘Signac’ ... +** package ‘Signac’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C++ compiler: ‘g++ (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c filter.cpp -o filter.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c group.cpp -o group.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c split.cpp -o split.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c validate.cpp -o validate.o ... -* this is package ‘simET’ version ‘1.0.3’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘ggpmisc’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - +** 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.4 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘Signac’ +* removing ‘/tmp/workdir/Signac/new/Signac.Rcheck/Signac’ ``` ### CRAN ``` -* using log directory ‘/tmp/workdir/simET/old/simET.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘simET/DESCRIPTION’ ... OK +* installing *source* package ‘Signac’ ... +** package ‘Signac’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C++ compiler: ‘g++ (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c filter.cpp -o filter.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c group.cpp -o group.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c split.cpp -o split.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c validate.cpp -o validate.o ... -* this is package ‘simET’ version ‘1.0.3’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘ggpmisc’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - +** 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.4 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘Signac’ +* removing ‘/tmp/workdir/Signac/old/Signac.Rcheck/Signac’ ``` -# simstudy +# SimplyAgree
-* Version: 0.8.0 -* GitHub: https://github.com/kgoldfeld/simstudy -* Source code: https://github.com/cran/simstudy -* Date/Publication: 2024-05-15 13:50:02 UTC -* Number of recursive dependencies: 176 +* Version: 0.2.0 +* GitHub: https://github.com/arcaldwell49/SimplyAgree +* Source code: https://github.com/cran/SimplyAgree +* Date/Publication: 2024-03-21 14:20:06 UTC +* Number of recursive dependencies: 115 -Run `revdepcheck::cloud_details(, "simstudy")` for more info +Run `revdepcheck::cloud_details(, "SimplyAgree")` for more info
-## Error before installation +## In both -### Devel +* checking whether package ‘SimplyAgree’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/SimplyAgree/new/SimplyAgree.Rcheck/00install.out’ for details. + ``` -``` -* using log directory ‘/tmp/workdir/simstudy/new/simstudy.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘simstudy/DESCRIPTION’ ... OK -... ---- finished re-building ‘treat_and_exposure.Rmd’ +## Installation -SUMMARY: processing the following file failed: - ‘logisticCoefs.Rmd’ +### Devel -Error: Vignette re-building failed. +``` +* installing *source* package ‘SimplyAgree’ ... +** package ‘SimplyAgree’ 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 +Warning in check_dep_version() : + ABI version mismatch: +lme4 was built with Matrix ABI version 1 +Current Matrix ABI version is 0 +Please re-install lme4 from source or restore original ‘Matrix’ package +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace Execution halted - -* DONE -Status: 1 WARNING, 2 NOTEs - - - +ERROR: lazy loading failed for package ‘SimplyAgree’ +* removing ‘/tmp/workdir/SimplyAgree/new/SimplyAgree.Rcheck/SimplyAgree’ ``` ### CRAN ``` -* using log directory ‘/tmp/workdir/simstudy/old/simstudy.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘simstudy/DESCRIPTION’ ... OK -... ---- finished re-building ‘treat_and_exposure.Rmd’ - -SUMMARY: processing the following file failed: - ‘logisticCoefs.Rmd’ - -Error: Vignette re-building failed. +* installing *source* package ‘SimplyAgree’ ... +** package ‘SimplyAgree’ 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 +Warning in check_dep_version() : + ABI version mismatch: +lme4 was built with Matrix ABI version 1 +Current Matrix ABI version is 0 +Please re-install lme4 from source or restore original ‘Matrix’ package +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace Execution halted - -* DONE -Status: 1 WARNING, 2 NOTEs - - - +ERROR: lazy loading failed for package ‘SimplyAgree’ +* removing ‘/tmp/workdir/SimplyAgree/old/SimplyAgree.Rcheck/SimplyAgree’ ``` @@ -12137,69 +7484,55 @@ Status: 1 WARNING, 2 NOTEs * Date/Publication: 2023-12-07 15:50:02 UTC * Number of recursive dependencies: 119 -Run `revdepcheck::cloud_details(, "sMSROC")` for more info - -
- -## Error before installation +Run `revdepcheck::cloud_details(, "sMSROC")` for more info -### Devel +
-``` -* using log directory ‘/tmp/workdir/sMSROC/new/sMSROC.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘sMSROC/DESCRIPTION’ ... OK -... -* this is package ‘sMSROC’ version ‘0.1.2’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘rms’ +## In both -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR +* checking whether package ‘sMSROC’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/sMSROC/new/sMSROC.Rcheck/00install.out’ for details. + ``` +## Installation +### Devel +``` +* installing *source* package ‘sMSROC’ ... +** package ‘sMSROC’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** data +*** moving datasets to lazyload DB +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘sMSROC’ +* removing ‘/tmp/workdir/sMSROC/new/sMSROC.Rcheck/sMSROC’ ``` ### CRAN ``` -* using log directory ‘/tmp/workdir/sMSROC/old/sMSROC.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘sMSROC/DESCRIPTION’ ... OK -... -* this is package ‘sMSROC’ version ‘0.1.2’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘rms’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - +* installing *source* package ‘sMSROC’ ... +** package ‘sMSROC’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** data +*** moving datasets to lazyload DB +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘sMSROC’ +* removing ‘/tmp/workdir/sMSROC/old/sMSROC.Rcheck/sMSROC’ ``` @@ -12217,65 +7550,51 @@ Run `revdepcheck::cloud_details(, "SNPassoc")` for more info
-## Error before installation - -### Devel +## In both -``` -* using log directory ‘/tmp/workdir/SNPassoc/new/SNPassoc.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘SNPassoc/DESCRIPTION’ ... OK -... -* checking if there is a namespace ... OK -* checking for executable files ... OK -* checking for hidden files and directories ... OK -* checking for portable file names ... OK -* checking for sufficient/correct file permissions ... OK -* checking whether package ‘SNPassoc’ can be installed ... ERROR -Installation failed. -See ‘/tmp/workdir/SNPassoc/new/SNPassoc.Rcheck/00install.out’ for details. -* DONE -Status: 1 ERROR +* checking whether package ‘SNPassoc’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/SNPassoc/new/SNPassoc.Rcheck/00install.out’ for details. + ``` +## Installation +### Devel +``` +* installing *source* package ‘SNPassoc’ ... +** package ‘SNPassoc’ successfully unpacked and MD5 sums checked +** 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘SNPassoc’ +* removing ‘/tmp/workdir/SNPassoc/new/SNPassoc.Rcheck/SNPassoc’ ``` ### CRAN ``` -* using log directory ‘/tmp/workdir/SNPassoc/old/SNPassoc.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘SNPassoc/DESCRIPTION’ ... OK -... -* checking if there is a namespace ... OK -* checking for executable files ... OK -* checking for hidden files and directories ... OK -* checking for portable file names ... OK -* checking for sufficient/correct file permissions ... OK -* checking whether package ‘SNPassoc’ can be installed ... ERROR -Installation failed. -See ‘/tmp/workdir/SNPassoc/old/SNPassoc.Rcheck/00install.out’ for details. -* DONE -Status: 1 ERROR - - - +* installing *source* package ‘SNPassoc’ ... +** package ‘SNPassoc’ successfully unpacked and MD5 sums checked +** 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘SNPassoc’ +* removing ‘/tmp/workdir/SNPassoc/old/SNPassoc.Rcheck/SNPassoc’ ``` @@ -12363,94 +7682,18 @@ Status: 1 ERROR * GitHub: https://github.com/constantAmateur/SoupX * Source code: https://github.com/cran/SoupX * Date/Publication: 2022-11-01 14:00:03 UTC -* Number of recursive dependencies: 200 +* Number of recursive dependencies: 201 Run `revdepcheck::cloud_details(, "SoupX")` for more info
-## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/SoupX/new/SoupX.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘SoupX/DESCRIPTION’ ... OK -... -* this is package ‘SoupX’ version ‘1.6.2’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘Seurat’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/SoupX/old/SoupX.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘SoupX/DESCRIPTION’ ... OK -... -* this is package ‘SoupX’ version ‘1.6.2’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘Seurat’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# sparsereg - -
- -* Version: 1.2 -* GitHub: NA -* Source code: https://github.com/cran/sparsereg -* Date/Publication: 2016-03-10 23:32:18 -* Number of recursive dependencies: 49 - -Run `revdepcheck::cloud_details(, "sparsereg")` for more info - -
- ## In both -* checking whether package ‘sparsereg’ can be installed ... ERROR +* checking whether package ‘SoupX’ can be installed ... ERROR ``` Installation failed. - See ‘/tmp/workdir/sparsereg/new/sparsereg.Rcheck/00install.out’ for details. + See ‘/tmp/workdir/SoupX/new/SoupX.Rcheck/00install.out’ for details. ``` ## Installation @@ -12458,126 +7701,114 @@ Run `revdepcheck::cloud_details(, "sparsereg")` for more info ### Devel ``` -* installing *source* package ‘sparsereg’ ... -** package ‘sparsereg’ successfully unpacked and MD5 sums checked +* installing *source* package ‘SoupX’ ... +** package ‘SoupX’ successfully unpacked and MD5 sums checked ** using staged installation -** libs -using C++ compiler: ‘g++ (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c makeinter.cpp -o makeinter.o -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c makethreeinter.cpp -o makethreeinter.o -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c subgroup.cpp -o subgroup.o -g++ -std=gnu++17 -shared -L/opt/R/4.3.1/lib/R/lib -L/usr/local/lib -o sparsereg.so RcppExports.o makeinter.o makethreeinter.o subgroup.o -llapack -lblas -lgfortran -lm -lquadmath -L/opt/R/4.3.1/lib/R/lib -lR -installing to /tmp/workdir/sparsereg/new/sparsereg.Rcheck/00LOCK-sparsereg/00new/sparsereg/libs ** R +** data +*** moving datasets to lazyload DB +** 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 ‘quantreg’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.4 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace Execution halted -ERROR: lazy loading failed for package ‘sparsereg’ -* removing ‘/tmp/workdir/sparsereg/new/sparsereg.Rcheck/sparsereg’ +ERROR: lazy loading failed for package ‘SoupX’ +* removing ‘/tmp/workdir/SoupX/new/SoupX.Rcheck/SoupX’ ``` ### CRAN ``` -* installing *source* package ‘sparsereg’ ... -** package ‘sparsereg’ successfully unpacked and MD5 sums checked +* installing *source* package ‘SoupX’ ... +** package ‘SoupX’ successfully unpacked and MD5 sums checked ** using staged installation -** libs -using C++ compiler: ‘g++ (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c makeinter.cpp -o makeinter.o -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c makethreeinter.cpp -o makethreeinter.o -g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c subgroup.cpp -o subgroup.o -g++ -std=gnu++17 -shared -L/opt/R/4.3.1/lib/R/lib -L/usr/local/lib -o sparsereg.so RcppExports.o makeinter.o makethreeinter.o subgroup.o -llapack -lblas -lgfortran -lm -lquadmath -L/opt/R/4.3.1/lib/R/lib -lR -installing to /tmp/workdir/sparsereg/old/sparsereg.Rcheck/00LOCK-sparsereg/00new/sparsereg/libs ** R +** data +*** moving datasets to lazyload DB +** 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 ‘quantreg’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.4 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace Execution halted -ERROR: lazy loading failed for package ‘sparsereg’ -* removing ‘/tmp/workdir/sparsereg/old/sparsereg.Rcheck/sparsereg’ +ERROR: lazy loading failed for package ‘SoupX’ +* removing ‘/tmp/workdir/SoupX/old/SoupX.Rcheck/SoupX’ ``` -# SPECK +# sparsereg
-* Version: 1.0.0 +* Version: 1.2 * GitHub: NA -* Source code: https://github.com/cran/SPECK -* Date/Publication: 2023-11-17 17:30:02 UTC -* Number of recursive dependencies: 161 +* Source code: https://github.com/cran/sparsereg +* Date/Publication: 2016-03-10 23:32:18 +* Number of recursive dependencies: 49 -Run `revdepcheck::cloud_details(, "SPECK")` for more info +Run `revdepcheck::cloud_details(, "sparsereg")` for more info
-## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/SPECK/new/SPECK.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘SPECK/DESCRIPTION’ ... OK -... -Package required but not available: ‘Seurat’ - -Package required and available but unsuitable version: ‘Matrix’ - -Package suggested but not available for checking: ‘SeuratObject’ +## In both -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR +* checking whether package ‘sparsereg’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/sparsereg/new/sparsereg.Rcheck/00install.out’ for details. + ``` +## Installation +### Devel +``` +* installing *source* package ‘sparsereg’ ... +** package ‘sparsereg’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C++ compiler: ‘g++ (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c makeinter.cpp -o makeinter.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c makethreeinter.cpp -o makethreeinter.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c subgroup.cpp -o subgroup.o +g++ -std=gnu++17 -shared -L/opt/R/4.3.1/lib/R/lib -L/usr/local/lib -o sparsereg.so RcppExports.o makeinter.o makethreeinter.o subgroup.o -llapack -lblas -lgfortran -lm -lquadmath -L/opt/R/4.3.1/lib/R/lib -lR +installing to /tmp/workdir/sparsereg/new/sparsereg.Rcheck/00LOCK-sparsereg/00new/sparsereg/libs +** R +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘sparsereg’ +* removing ‘/tmp/workdir/sparsereg/new/sparsereg.Rcheck/sparsereg’ ``` ### CRAN ``` -* using log directory ‘/tmp/workdir/SPECK/old/SPECK.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘SPECK/DESCRIPTION’ ... OK -... -Package required but not available: ‘Seurat’ - -Package required and available but unsuitable version: ‘Matrix’ - -Package suggested but not available for checking: ‘SeuratObject’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - +* installing *source* package ‘sparsereg’ ... +** package ‘sparsereg’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C++ compiler: ‘g++ (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c makeinter.cpp -o makeinter.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c makethreeinter.cpp -o makethreeinter.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.3.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c subgroup.cpp -o subgroup.o +g++ -std=gnu++17 -shared -L/opt/R/4.3.1/lib/R/lib -L/usr/local/lib -o sparsereg.so RcppExports.o makeinter.o makethreeinter.o subgroup.o -llapack -lblas -lgfortran -lm -lquadmath -L/opt/R/4.3.1/lib/R/lib -lR +installing to /tmp/workdir/sparsereg/old/sparsereg.Rcheck/00LOCK-sparsereg/00new/sparsereg/libs +** R +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘sparsereg’ +* removing ‘/tmp/workdir/sparsereg/old/sparsereg.Rcheck/sparsereg’ ``` @@ -12620,9 +7851,9 @@ installing to /tmp/workdir/spikeSlabGAM/new/spikeSlabGAM.Rcheck/00LOCK-spikeSlab ** R ** 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 ‘quantreg’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace Execution halted ERROR: lazy loading failed for package ‘spikeSlabGAM’ * removing ‘/tmp/workdir/spikeSlabGAM/new/spikeSlabGAM.Rcheck/spikeSlabGAM’ @@ -12644,9 +7875,9 @@ installing to /tmp/workdir/spikeSlabGAM/old/spikeSlabGAM.Rcheck/00LOCK-spikeSlab ** R ** 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 ‘quantreg’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace Execution halted ERROR: lazy loading failed for package ‘spikeSlabGAM’ * removing ‘/tmp/workdir/spikeSlabGAM/old/spikeSlabGAM.Rcheck/spikeSlabGAM’ @@ -12723,7 +7954,7 @@ ERROR: lazy loading failed for package ‘statsr’ * GitHub: NA * Source code: https://github.com/cran/streamDAG * Date/Publication: 2023-10-06 18:50:02 UTC -* Number of recursive dependencies: 133 +* Number of recursive dependencies: 132 Run `revdepcheck::cloud_details(, "streamDAG")` for more info @@ -12786,234 +8017,6 @@ Status: 1 ERROR -``` -# sure - -
- -* Version: 0.2.0 -* GitHub: https://github.com/AFIT-R/sure -* Source code: https://github.com/cran/sure -* Date/Publication: 2017-09-19 18:04:46 UTC -* Number of recursive dependencies: 96 - -Run `revdepcheck::cloud_details(, "sure")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/sure/new/sure.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘sure/DESCRIPTION’ ... OK -... -* checking contents of ‘data’ directory ... OK -* checking data for non-ASCII characters ... OK -* checking LazyData ... OK -* checking data for ASCII and uncompressed saves ... OK -* checking examples ... OK -* checking for unstated dependencies in ‘tests’ ... OK -* checking tests ... OK - Running ‘testthat.R’ -* DONE -Status: 2 NOTEs - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/sure/old/sure.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘sure/DESCRIPTION’ ... OK -... -* checking contents of ‘data’ directory ... OK -* checking data for non-ASCII characters ... OK -* checking LazyData ... OK -* checking data for ASCII and uncompressed saves ... OK -* checking examples ... OK -* checking for unstated dependencies in ‘tests’ ... OK -* checking tests ... OK - Running ‘testthat.R’ -* DONE -Status: 2 NOTEs - - - - - -``` -# Surrogate - -
- -* Version: 3.2.6 -* GitHub: https://github.com/florianstijven/Surrogate-development -* Source code: https://github.com/cran/Surrogate -* Date/Publication: 2024-05-27 12:30:02 UTC -* Number of recursive dependencies: 194 - -Run `revdepcheck::cloud_details(, "Surrogate")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/Surrogate/new/Surrogate.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘Surrogate/DESCRIPTION’ ... OK -... -* this is package ‘Surrogate’ version ‘3.2.6’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘rms’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/Surrogate/old/Surrogate.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘Surrogate/DESCRIPTION’ ... OK -... -* this is package ‘Surrogate’ version ‘3.2.6’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘rms’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# survex - -
- -* Version: 1.2.0 -* GitHub: https://github.com/ModelOriented/survex -* Source code: https://github.com/cran/survex -* Date/Publication: 2023-10-24 18:50:07 UTC -* Number of recursive dependencies: 182 - -Run `revdepcheck::cloud_details(, "survex")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/survex/new/survex.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘survex/DESCRIPTION’ ... OK -... -  A new explainer has been created!  -> -> y <- cph_exp$y -> times <- cph_exp$times -> surv <- cph_exp$predict_survival_function(cph, cph_exp$data, times) -Error in loadNamespace(x) : there is no package called ‘riskRegression’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart -Execution halted -* DONE -Status: 1 ERROR, 1 NOTE - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/survex/old/survex.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘survex/DESCRIPTION’ ... OK -... -  A new explainer has been created!  -> -> y <- cph_exp$y -> times <- cph_exp$times -> surv <- cph_exp$predict_survival_function(cph, cph_exp$data, times) -Error in loadNamespace(x) : there is no package called ‘riskRegression’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart -Execution halted -* DONE -Status: 1 ERROR, 1 NOTE - - - - - ``` # survHE @@ -13022,72 +8025,66 @@ Status: 1 ERROR, 1 NOTE * Version: 2.0.1 * GitHub: https://github.com/giabaio/survHE * Source code: https://github.com/cran/survHE -* Date/Publication: 2023-03-19 22:10:02 UTC -* Number of recursive dependencies: 130 - -Run `revdepcheck::cloud_details(, "survHE")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/survHE/new/survHE.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘survHE/DESCRIPTION’ ... OK -... -* checking package dependencies ... ERROR -Package required but not available: ‘rms’ - -Packages suggested but not available for checking: - 'survHEinla', 'survHEhmc' - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR +* Date/Publication: 2023-03-19 22:10:02 UTC +* Number of recursive dependencies: 130 +Run `revdepcheck::cloud_details(, "survHE")` for more info +
+## In both +* checking whether package ‘survHE’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/survHE/new/survHE.Rcheck/00install.out’ for details. + ``` -``` -### CRAN +* checking package dependencies ... NOTE + ``` + Packages suggested but not available for checking: + 'survHEinla', 'survHEhmc' + ``` -``` -* using log directory ‘/tmp/workdir/survHE/old/survHE.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘survHE/DESCRIPTION’ ... OK -... -* checking package dependencies ... ERROR -Package required but not available: ‘rms’ +## Installation -Packages suggested but not available for checking: - 'survHEinla', 'survHEhmc' +### Devel -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR +``` +* installing *source* package ‘survHE’ ... +** package ‘survHE’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘survHE’ +* removing ‘/tmp/workdir/survHE/new/survHE.Rcheck/survHE’ +``` +### CRAN +``` +* installing *source* package ‘survHE’ ... +** package ‘survHE’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘survHE’ +* removing ‘/tmp/workdir/survHE/old/survHE.Rcheck/survHE’ ``` @@ -13132,8 +8129,8 @@ installing to /tmp/workdir/survidm/new/survidm.Rcheck/00LOCK-survidm/00new/survi *** moving datasets to lazyload DB ** 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 ‘quantreg’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace Execution halted ERROR: lazy loading failed for package ‘survidm’ * removing ‘/tmp/workdir/survidm/new/survidm.Rcheck/survidm’ @@ -13157,89 +8154,13 @@ installing to /tmp/workdir/survidm/old/survidm.Rcheck/00LOCK-survidm/00new/survi *** moving datasets to lazyload DB ** 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 ‘quantreg’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace Execution halted ERROR: lazy loading failed for package ‘survidm’ * removing ‘/tmp/workdir/survidm/old/survidm.Rcheck/survidm’ -``` -# SurvMetrics - -
- -* Version: 0.5.0 -* GitHub: https://github.com/skyee1/SurvMetrics -* Source code: https://github.com/cran/SurvMetrics -* Date/Publication: 2022-09-03 21:40:23 UTC -* Number of recursive dependencies: 187 - -Run `revdepcheck::cloud_details(, "SurvMetrics")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/SurvMetrics/new/SurvMetrics.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘SurvMetrics/DESCRIPTION’ ... OK -... ---- failed re-building ‘SurvMetrics-vignette.Rmd’ - -SUMMARY: processing the following file failed: - ‘SurvMetrics-vignette.Rmd’ - -Error: Vignette re-building failed. -Execution halted - -* DONE -Status: 1 ERROR, 1 WARNING, 1 NOTE - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/SurvMetrics/old/SurvMetrics.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘SurvMetrics/DESCRIPTION’ ... OK -... ---- failed re-building ‘SurvMetrics-vignette.Rmd’ - -SUMMARY: processing the following file failed: - ‘SurvMetrics-vignette.Rmd’ - -Error: Vignette re-building failed. -Execution halted - -* DONE -Status: 1 ERROR, 1 WARNING, 1 NOTE - - - - - ``` # tempted @@ -13277,7 +8198,7 @@ Run `revdepcheck::cloud_details(, "tempted")` for more info ** inst ** byte-compile and prepare package for lazy loading Error: package or namespace load failed for ‘np’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): - there is no package called ‘quantreg’ + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required Execution halted ERROR: lazy loading failed for package ‘tempted’ * removing ‘/tmp/workdir/tempted/new/tempted.Rcheck/tempted’ @@ -13296,7 +8217,7 @@ ERROR: lazy loading failed for package ‘tempted’ ** inst ** byte-compile and prepare package for lazy loading Error: package or namespace load failed for ‘np’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): - there is no package called ‘quantreg’ + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required Execution halted ERROR: lazy loading failed for package ‘tempted’ * removing ‘/tmp/workdir/tempted/old/tempted.Rcheck/tempted’ @@ -13373,71 +8294,61 @@ ERROR: lazy loading failed for package ‘tidydr’ * GitHub: NA * Source code: https://github.com/cran/tidyEdSurvey * Date/Publication: 2024-05-14 20:20:03 UTC -* Number of recursive dependencies: 106 +* Number of recursive dependencies: 111 Run `revdepcheck::cloud_details(, "tidyEdSurvey")` for more info
-## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/tidyEdSurvey/new/tidyEdSurvey.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘tidyEdSurvey/DESCRIPTION’ ... OK -... -* this is package ‘tidyEdSurvey’ version ‘0.1.3’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘EdSurvey’ +## In both -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR +* checking whether package ‘tidyEdSurvey’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/tidyEdSurvey/new/tidyEdSurvey.Rcheck/00install.out’ for details. + ``` +## Installation +### Devel +``` +* installing *source* package ‘tidyEdSurvey’ ... +** package ‘tidyEdSurvey’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** byte-compile and prepare package for lazy loading +Error: package or namespace load failed for ‘EdSurvey’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +In addition: Warning message: +In check_dep_version() : ABI version mismatch: +lme4 was built with Matrix ABI version 1 +Current Matrix ABI version is 0 +Please re-install lme4 from source or restore original ‘Matrix’ package +Execution halted +ERROR: lazy loading failed for package ‘tidyEdSurvey’ +* removing ‘/tmp/workdir/tidyEdSurvey/new/tidyEdSurvey.Rcheck/tidyEdSurvey’ ``` ### CRAN ``` -* using log directory ‘/tmp/workdir/tidyEdSurvey/old/tidyEdSurvey.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘tidyEdSurvey/DESCRIPTION’ ... OK -... -* this is package ‘tidyEdSurvey’ version ‘0.1.3’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘EdSurvey’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - +* installing *source* package ‘tidyEdSurvey’ ... +** package ‘tidyEdSurvey’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** byte-compile and prepare package for lazy loading +Error: package or namespace load failed for ‘EdSurvey’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +In addition: Warning message: +In check_dep_version() : ABI version mismatch: +lme4 was built with Matrix ABI version 1 +Current Matrix ABI version is 0 +Please re-install lme4 from source or restore original ‘Matrix’ package +Execution halted +ERROR: lazy loading failed for package ‘tidyEdSurvey’ +* removing ‘/tmp/workdir/tidyEdSurvey/old/tidyEdSurvey.Rcheck/tidyEdSurvey’ ``` @@ -13449,147 +8360,121 @@ Status: 1 ERROR * GitHub: https://github.com/stemangiola/tidyseurat * Source code: https://github.com/cran/tidyseurat * Date/Publication: 2024-01-10 04:50:02 UTC -* Number of recursive dependencies: 206 +* Number of recursive dependencies: 207 Run `revdepcheck::cloud_details(, "tidyseurat")` for more info -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/tidyseurat/new/tidyseurat.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘tidyseurat/DESCRIPTION’ ... OK -... -* this is package ‘tidyseurat’ version ‘0.8.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Packages required but not available: 'SeuratObject', 'Seurat' +## In both -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR +* checking whether package ‘tidyseurat’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/tidyseurat/new/tidyseurat.Rcheck/00install.out’ for details. + ``` +## Installation +### Devel +``` +* installing *source* package ‘tidyseurat’ ... +** package ‘tidyseurat’ 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: package or namespace load failed for ‘SeuratObject’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.4 is required +Execution halted +ERROR: lazy loading failed for package ‘tidyseurat’ +* removing ‘/tmp/workdir/tidyseurat/new/tidyseurat.Rcheck/tidyseurat’ ``` ### CRAN ``` -* using log directory ‘/tmp/workdir/tidyseurat/old/tidyseurat.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘tidyseurat/DESCRIPTION’ ... OK -... -* this is package ‘tidyseurat’ version ‘0.8.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Packages required but not available: 'SeuratObject', 'Seurat' - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - +* installing *source* package ‘tidyseurat’ ... +** package ‘tidyseurat’ 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: package or namespace load failed for ‘SeuratObject’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.4 is required +Execution halted +ERROR: lazy loading failed for package ‘tidyseurat’ +* removing ‘/tmp/workdir/tidyseurat/old/tidyseurat.Rcheck/tidyseurat’ ``` -# treefit +# tidyvpc
-* Version: 1.0.2 -* GitHub: https://github.com/hayamizu-lab/treefit-r -* Source code: https://github.com/cran/treefit -* Date/Publication: 2022-01-18 07:50:02 UTC -* Number of recursive dependencies: 159 +* Version: 1.5.1 +* GitHub: https://github.com/certara/tidyvpc +* Source code: https://github.com/cran/tidyvpc +* Date/Publication: 2024-01-18 13:10:02 UTC +* Number of recursive dependencies: 176 -Run `revdepcheck::cloud_details(, "treefit")` for more info +Run `revdepcheck::cloud_details(, "tidyvpc")` for more info
-## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/treefit/new/treefit.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘treefit/DESCRIPTION’ ... OK -... - - When sourcing ‘working-with-seurat.R’: -Error: there is no package called ‘Seurat’ -Execution halted +## In both - ‘treefit.Rmd’ using ‘UTF-8’... OK - ‘working-with-seurat.Rmd’ using ‘UTF-8’... failed -* checking re-building of vignette outputs ... OK -* DONE -Status: 1 WARNING, 1 NOTE +* checking whether package ‘tidyvpc’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/tidyvpc/new/tidyvpc.Rcheck/00install.out’ for details. + ``` +## Installation +### Devel +``` +* installing *source* package ‘tidyvpc’ ... +** package ‘tidyvpc’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘tidyvpc’ +* removing ‘/tmp/workdir/tidyvpc/new/tidyvpc.Rcheck/tidyvpc’ ``` ### CRAN ``` -* using log directory ‘/tmp/workdir/treefit/old/treefit.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘treefit/DESCRIPTION’ ... OK -... - - When sourcing ‘working-with-seurat.R’: -Error: there is no package called ‘Seurat’ +* installing *source* package ‘tidyvpc’ ... +** package ‘tidyvpc’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace Execution halted - - ‘treefit.Rmd’ using ‘UTF-8’... OK - ‘working-with-seurat.Rmd’ using ‘UTF-8’... failed -* checking re-building of vignette outputs ... OK -* DONE -Status: 1 WARNING, 1 NOTE - - - +ERROR: lazy loading failed for package ‘tidyvpc’ +* removing ‘/tmp/workdir/tidyvpc/old/tidyvpc.Rcheck/tidyvpc’ ``` @@ -13644,6 +8529,84 @@ ERROR: configuration failed for package ‘TriDimRegression’ * removing ‘/tmp/workdir/TriDimRegression/old/TriDimRegression.Rcheck/TriDimRegression’ +``` +# TSrepr + +
+ +* Version: 1.1.0 +* GitHub: https://github.com/PetoLau/TSrepr +* Source code: https://github.com/cran/TSrepr +* Date/Publication: 2020-07-13 06:50:15 UTC +* Number of recursive dependencies: 72 + +Run `revdepcheck::cloud_details(, "TSrepr")` for more info + +
+ +## In both + +* checking whether package ‘TSrepr’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/TSrepr/new/TSrepr.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘TSrepr’ ... +** package ‘TSrepr’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C++ compiler: ‘g++ (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c FeatureClippingTrending.cpp -o FeatureClippingTrending.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c helpers.cpp -o helpers.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c measures.cpp -o measures.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c normalizations.cpp -o normalizations.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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘TSrepr’ +* removing ‘/tmp/workdir/TSrepr/new/TSrepr.Rcheck/TSrepr’ + + +``` +### CRAN + +``` +* installing *source* package ‘TSrepr’ ... +** package ‘TSrepr’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +using C++ compiler: ‘g++ (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c FeatureClippingTrending.cpp -o FeatureClippingTrending.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c helpers.cpp -o helpers.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c measures.cpp -o measures.o +g++ -std=gnu++17 -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I'/opt/R/4.3.1/lib/R/site-library/Rcpp/include' -I/usr/local/include -fpic -g -O2 -c normalizations.cpp -o normalizations.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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘TSrepr’ +* removing ‘/tmp/workdir/TSrepr/old/TSrepr.Rcheck/TSrepr’ + + ``` # twang @@ -13719,26 +8682,26 @@ ERROR: lazy loading failed for package ‘twang’ ``` -# valse +# vdg
-* Version: 0.1-0 +* Version: 1.2.3 * GitHub: NA -* Source code: https://github.com/cran/valse -* Date/Publication: 2021-05-31 08:00:02 UTC -* Number of recursive dependencies: 55 +* Source code: https://github.com/cran/vdg +* Date/Publication: 2024-04-23 13:00:02 UTC +* Number of recursive dependencies: 45 -Run `revdepcheck::cloud_details(, "valse")` for more info +Run `revdepcheck::cloud_details(, "vdg")` for more info
## In both -* checking whether package ‘valse’ can be installed ... ERROR +* checking whether package ‘vdg’ can be installed ... ERROR ``` Installation failed. - See ‘/tmp/workdir/valse/new/valse.Rcheck/00install.out’ for details. + See ‘/tmp/workdir/vdg/new/vdg.Rcheck/00install.out’ for details. ``` ## Installation @@ -13746,54 +8709,48 @@ Run `revdepcheck::cloud_details(, "valse")` for more info ### Devel ``` -* installing *source* package ‘valse’ ... -** package ‘valse’ successfully unpacked and MD5 sums checked +* installing *source* package ‘vdg’ ... +** package ‘vdg’ successfully unpacked and MD5 sums checked ** using staged installation ** libs -using C compiler: ‘gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ -gcc -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I/usr/local/include -fpic -g -O2 -c EMGLLF.c -o EMGLLF.o -gcc -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I/usr/local/include -fpic -g -O2 -c EMGrank.c -o EMGrank.o -gcc -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I/usr/local/include -fpic -g -O2 -c a.EMGLLF.c -o a.EMGLLF.o -gcc -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I/usr/local/include -fpic -g -O2 -c a.EMGrank.c -o a.EMGrank.o -gcc -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I/usr/local/include -fpic -g -O2 -c valse_init.c -o valse_init.o -... -*** installing help indices -** building package indices -** testing if installed package can be loaded from temporary location -Error: package or namespace load failed for ‘valse’ in dyn.load(file, DLLpath = DLLpath, ...): - unable to load shared object '/tmp/workdir/valse/new/valse.Rcheck/00LOCK-valse/00new/valse/libs/valse.so': - /tmp/workdir/valse/new/valse.Rcheck/00LOCK-valse/00new/valse/libs/valse.so: undefined symbol: gsl_permutation_free -Error: loading failed +using Fortran compiler: ‘GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ +gfortran -fpic -g -O2 -c FDS.f -o FDS.o +gcc -shared -L/opt/R/4.3.1/lib/R/lib -L/usr/local/lib -o vdg.so FDS.o -lgfortran -lm -lquadmath -L/opt/R/4.3.1/lib/R/lib -lR +installing to /tmp/workdir/vdg/new/vdg.Rcheck/00LOCK-vdg/00new/vdg/libs +** R +** data +*** moving datasets to lazyload DB +** inst +** byte-compile and prepare package for lazy loading +Error: package or namespace load failed for ‘quantreg’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required Execution halted -ERROR: loading failed -* removing ‘/tmp/workdir/valse/new/valse.Rcheck/valse’ +ERROR: lazy loading failed for package ‘vdg’ +* removing ‘/tmp/workdir/vdg/new/vdg.Rcheck/vdg’ ``` ### CRAN ``` -* installing *source* package ‘valse’ ... -** package ‘valse’ successfully unpacked and MD5 sums checked +* installing *source* package ‘vdg’ ... +** package ‘vdg’ successfully unpacked and MD5 sums checked ** using staged installation ** libs -using C compiler: ‘gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ -gcc -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I/usr/local/include -fpic -g -O2 -c EMGLLF.c -o EMGLLF.o -gcc -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I/usr/local/include -fpic -g -O2 -c EMGrank.c -o EMGrank.o -gcc -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I/usr/local/include -fpic -g -O2 -c a.EMGLLF.c -o a.EMGLLF.o -gcc -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I/usr/local/include -fpic -g -O2 -c a.EMGrank.c -o a.EMGrank.o -gcc -I"/opt/R/4.3.1/lib/R/include" -DNDEBUG -I/usr/local/include -fpic -g -O2 -c valse_init.c -o valse_init.o -... -*** installing help indices -** building package indices -** testing if installed package can be loaded from temporary location -Error: package or namespace load failed for ‘valse’ in dyn.load(file, DLLpath = DLLpath, ...): - unable to load shared object '/tmp/workdir/valse/old/valse.Rcheck/00LOCK-valse/00new/valse/libs/valse.so': - /tmp/workdir/valse/old/valse.Rcheck/00LOCK-valse/00new/valse/libs/valse.so: undefined symbol: gsl_permutation_free -Error: loading failed +using Fortran compiler: ‘GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0’ +gfortran -fpic -g -O2 -c FDS.f -o FDS.o +gcc -shared -L/opt/R/4.3.1/lib/R/lib -L/usr/local/lib -o vdg.so FDS.o -lgfortran -lm -lquadmath -L/opt/R/4.3.1/lib/R/lib -lR +installing to /tmp/workdir/vdg/old/vdg.Rcheck/00LOCK-vdg/00new/vdg/libs +** R +** data +*** moving datasets to lazyload DB +** inst +** byte-compile and prepare package for lazy loading +Error: package or namespace load failed for ‘quantreg’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required Execution halted -ERROR: loading failed -* removing ‘/tmp/workdir/valse/old/valse.Rcheck/valse’ +ERROR: lazy loading failed for package ‘vdg’ +* removing ‘/tmp/workdir/vdg/old/vdg.Rcheck/vdg’ ``` @@ -13805,147 +8762,123 @@ ERROR: loading failed * GitHub: https://github.com/kang-yu/visa * Source code: https://github.com/cran/visa * Date/Publication: 2021-04-20 07:20:02 UTC -* Number of recursive dependencies: 141 +* Number of recursive dependencies: 140 Run `revdepcheck::cloud_details(, "visa")` for more info -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/visa/new/visa.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘visa/DESCRIPTION’ ... OK -... -* this is package ‘visa’ version ‘0.1.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘ggpmisc’ +## In both -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR +* checking whether package ‘visa’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/visa/new/visa.Rcheck/00install.out’ for details. + ``` +## Installation +### Devel +``` +* installing *source* package ‘visa’ ... +** package ‘visa’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘visa’ +* removing ‘/tmp/workdir/visa/new/visa.Rcheck/visa’ ``` ### CRAN ``` -* using log directory ‘/tmp/workdir/visa/old/visa.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘visa/DESCRIPTION’ ... OK -... -* this is package ‘visa’ version ‘0.1.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘ggpmisc’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - +* installing *source* package ‘visa’ ... +** package ‘visa’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘visa’ +* removing ‘/tmp/workdir/visa/old/visa.Rcheck/visa’ ``` -# WpProj +# WRTDStidal
-* Version: 0.2.1 -* GitHub: https://github.com/ericdunipace/WpProj -* Source code: https://github.com/cran/WpProj -* Date/Publication: 2024-02-02 10:10:05 UTC -* Number of recursive dependencies: 100 +* Version: 1.1.4 +* GitHub: https://github.com/fawda123/WRTDStidal +* Source code: https://github.com/cran/WRTDStidal +* Date/Publication: 2023-10-20 09:00:11 UTC +* Number of recursive dependencies: 139 -Run `revdepcheck::cloud_details(, "WpProj")` for more info +Run `revdepcheck::cloud_details(, "WRTDStidal")` for more info
-## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/WpProj/new/WpProj.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘WpProj/DESCRIPTION’ ... OK -... -* this is package ‘WpProj’ version ‘0.2.1’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Packages required but not available: 'rqPen', 'quantreg' +## In both -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR +* checking whether package ‘WRTDStidal’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/WRTDStidal/new/WRTDStidal.Rcheck/00install.out’ for details. + ``` +## Installation +### Devel +``` +* installing *source* package ‘WRTDStidal’ ... +** package ‘WRTDStidal’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘WRTDStidal’ +* removing ‘/tmp/workdir/WRTDStidal/new/WRTDStidal.Rcheck/WRTDStidal’ ``` ### CRAN ``` -* using log directory ‘/tmp/workdir/WpProj/old/WpProj.Rcheck’ -* using R version 4.3.1 (2023-06-16) -* using platform: x86_64-pc-linux-gnu (64-bit) -* R was compiled by - gcc (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 - GNU Fortran (Ubuntu 11.4.0-1ubuntu1~22.04) 11.4.0 -* running under: Ubuntu 22.04.4 LTS -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘WpProj/DESCRIPTION’ ... OK -... -* this is package ‘WpProj’ version ‘0.2.1’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Packages required but not available: 'rqPen', 'quantreg' - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - +* installing *source* package ‘WRTDStidal’ ... +** package ‘WRTDStidal’ 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]]) : + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required +Calls: ... namespaceImportFrom -> asNamespace -> loadNamespace +Execution halted +ERROR: lazy loading failed for package ‘WRTDStidal’ +* removing ‘/tmp/workdir/WRTDStidal/old/WRTDStidal.Rcheck/WRTDStidal’ ``` diff --git a/revdep/problems.md b/revdep/problems.md index ac4d68ce5f..517f4be819 100644 --- a/revdep/problems.md +++ b/revdep/problems.md @@ -1,44 +1,3 @@ -# accSDA - -
- -* Version: 1.1.3 -* GitHub: https://github.com/gumeo/accSDA -* Source code: https://github.com/cran/accSDA -* Date/Publication: 2024-03-06 18:50:02 UTC -* Number of recursive dependencies: 29 - -Run `revdepcheck::cloud_details(, "accSDA")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘accSDA-Ex.R’ failed - The error most likely occurred in: - - > ### Name: ASDABarPlot - > ### Title: barplot for ASDA objects - > ### Aliases: ASDABarPlot - > - > ### ** Examples - > - > # Generate and ASDA object with your data, e.g. - ... - 3. ├─base::do.call(arrangeGrob, c(list(grobs = groups[[g]]), params)) - 4. └─gridExtra (local) ``(grobs = ``, layout_matrix = ``) - 5. └─base::lapply(grobs[toconv], ggplot2::ggplotGrob) - 6. └─ggplot2 (local) FUN(X[[i]], ...) - 7. ├─ggplot2::ggplot_gtable(ggplot_build(x)) - 8. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) - 9. └─ggplot2::calc_element("plot.margin", theme) - 10. └─cli::cli_abort(...) - 11. └─rlang::abort(...) - Execution halted - ``` - # activAnalyzer
@@ -47,7 +6,7 @@ Run `revdepcheck::cloud_details(, "accSDA")` for more info * GitHub: https://github.com/pydemull/activAnalyzer * Source code: https://github.com/cran/activAnalyzer * Date/Publication: 2024-05-05 22:40:03 UTC -* Number of recursive dependencies: 152 +* Number of recursive dependencies: 153 Run `revdepcheck::cloud_details(, "activAnalyzer")` for more info @@ -84,9 +43,9 @@ Run `revdepcheck::cloud_details(, "activAnalyzer")` for more info * checking installed package size ... NOTE ``` - installed size is 5.8Mb + installed size is 5.3Mb sub-directories of 1Mb or more: - R 1.5Mb + R 1.0Mb doc 1.0Mb extdata 2.0Mb ``` @@ -95,11 +54,11 @@ Run `revdepcheck::cloud_details(, "activAnalyzer")` for more info
-* Version: 1.4.0 +* Version: 1.5.0 * GitHub: https://github.com/mattheaphy/actxps * Source code: https://github.com/cran/actxps -* Date/Publication: 2023-11-26 16:10:02 UTC -* Number of recursive dependencies: 131 +* Date/Publication: 2024-06-25 12:40:02 UTC +* Number of recursive dependencies: 130 Run `revdepcheck::cloud_details(, "actxps")` for more info @@ -140,7 +99,7 @@ Run `revdepcheck::cloud_details(, "actxps")` for more info Warning: thematic was unable to resolve `fg='auto'`. Try providing an actual color (or `NA`) to the `fg` argument of `thematic_on()`. By the way, 'auto' is only officially supported in `shiny::renderPlot()`, some rmarkdown scenarios (specifically, `html_document()` with `theme!=NULL`), in RStudio, or if `auto_config_set()` is used. Warning: thematic was unable to resolve `accent='auto'`. Try providing an actual color (or `NA`) to the `accent` argument of `thematic_on()`. By the way, 'auto' is only officially supported in `shiny::renderPlot()`, some rmarkdown scenarios (specifically, `html_document()` with `theme!=NULL`), in RStudio, or if `auto_config_set()` is used. - Quitting from lines 131-132 [plot] (actxps.Rmd) + Quitting from lines 129-130 [plot] (actxps.Rmd) Error: processing vignette 'actxps.Rmd' failed with diagnostics: Internal error: adjust_color() expects an input of length 1 --- failed re-building ‘actxps.Rmd’ @@ -157,79 +116,6 @@ Run `revdepcheck::cloud_details(, "actxps")` for more info Execution halted ``` -# add2ggplot - -
- -* Version: 0.3.0 -* GitHub: https://github.com/JiaxiangBU/add2ggplot -* Source code: https://github.com/cran/add2ggplot -* Date/Publication: 2020-02-07 11:50:02 UTC -* Number of recursive dependencies: 53 - -Run `revdepcheck::cloud_details(, "add2ggplot")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘add2ggplot-Ex.R’ failed - The error most likely occurred in: - - > ### Name: theme_ilo - > ### Title: One ggplot theme - > ### Aliases: theme_ilo - > - > ### ** Examples - > - > datasets::mtcars %>% - ... - Backtrace: - ▆ - 1. ├─base (local) ``(x) - 2. └─ggplot2:::print.ggplot(x) - 3. ├─ggplot2::ggplot_gtable(data) - 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) - 5. └─ggplot2::calc_element("plot.margin", theme) - 6. └─cli::cli_abort(...) - 7. └─rlang::abort(...) - Execution halted - ``` - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘intro.Rmd’ - ... - - > mtcars %>% ggplot2::ggplot(ggplot2::aes(mpg, disp)) + - + ggplot2::geom_point() + theme_grey_and_red() - - > mtcars %>% ggplot2::ggplot(ggplot2::aes(mpg, disp)) + - + ggplot2::geom_point() + theme_ilo() - - When sourcing ‘intro.R’: - Error: Theme element `plot.margin` must have class . - Execution halted - - ‘intro.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘intro.Rmd’ using rmarkdown - ``` - -## In both - -* checking LazyData ... NOTE - ``` - 'LazyData' is specified without a 'data' directory - ``` - # AeRobiology
@@ -273,133 +159,45 @@ Run `revdepcheck::cloud_details(, "AeRobiology")` for more info ‘my-vignette.Rmd’ using ‘UTF-8’... failed ``` -# afex - -
- -* Version: 1.3-1 -* GitHub: https://github.com/singmann/afex -* Source code: https://github.com/cran/afex -* Date/Publication: 2024-02-25 14:40:02 UTC -* Number of recursive dependencies: 226 - -Run `revdepcheck::cloud_details(, "afex")` for more info - -
- -## Newly broken - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘afex_plot_supported_models.Rmd’ - ... - - > grid::grid.draw(b34) - - When sourcing ‘afex_plot_supported_models.R’: - Error: Problem while setting up geom aesthetics. - ℹ Error occurred in the 1st layer. - Caused by error in `compute_geom_2()`: - ... - 14, NULL, NULL, list(), 15.4, NULL, NULL, 7, NULL, NULL, NULL, NULL, 0.2, NULL, list(NULL, NULL, NULL, 0.857142857142857, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, NULL, NULL, NULL, TRUE), NULL, "none", NULL, NULL, NULL, "center", NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, c(0, 0, 0, 0), list(), 14, li - Execution halted - - ‘afex_analysing_accuracy_data.Rmd’ using ‘UTF-8’... OK - ‘afex_anova_example.Rmd’ using ‘UTF-8’... OK - ‘afex_mixed_example.Rmd’ using ‘UTF-8’... OK - ‘afex_plot_introduction.Rmd’ using ‘UTF-8’... OK - ‘afex_plot_supported_models.Rmd’ using ‘UTF-8’... failed - ‘assumptions_of_ANOVAs.Rmd’ using ‘UTF-8’... OK - ‘introduction-mixed-models.pdf.asis’ using ‘UTF-8’... OK - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘afex_analysing_accuracy_data.Rmd’ using rmarkdown - ``` - -# AgroR - -
- -* Version: 1.3.6 -* GitHub: NA -* Source code: https://github.com/cran/AgroR -* Date/Publication: 2024-04-24 02:20:18 UTC -* Number of recursive dependencies: 118 - -Run `revdepcheck::cloud_details(, "AgroR")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘AgroR-Ex.R’ failed - The error most likely occurred in: - - > ### Name: DBC - > ### Title: Analysis: Randomized block design - > ### Aliases: DBC - > ### Keywords: DBC Experimental - > - > ### ** Examples - > - ... - 12. │ └─base::withCallingHandlers(...) - 13. └─ggplot2 (local) f(l = layers[[i]], d = data[[i]]) - 14. └─l$compute_geom_2(d, theme = plot$theme) - 15. └─ggplot2 (local) compute_geom_2(..., self = self) - 16. └─self$geom$use_defaults(...) - 17. └─ggplot2 (local) use_defaults(..., self = self) - 18. └─ggplot2:::check_aesthetics(new_params, nrow(data)) - 19. └─cli::cli_abort(...) - 20. └─rlang::abort(...) - Execution halted - ``` - -# allMT +# agricolaeplotr
-* Version: 0.1.0 -* GitHub: https://github.com/tmungle/allMT -* Source code: https://github.com/cran/allMT -* Date/Publication: 2023-04-20 17:32:33 UTC +* Version: 0.5.0 +* GitHub: https://github.com/jensharbers/agricolaeplotr +* Source code: https://github.com/cran/agricolaeplotr +* Date/Publication: 2024-01-17 16:42:04 UTC * Number of recursive dependencies: 144 -Run `revdepcheck::cloud_details(, "allMT")` for more info +Run `revdepcheck::cloud_details(, "agricolaeplotr")` for more info
## Newly broken -* checking examples ... ERROR +* checking tests ... ERROR ``` - Running examples in ‘allMT-Ex.R’ failed - The error most likely occurred in: - - > ### Name: compare_cohorts - > ### Title: Plot summarized maintenance therapy (MT) data to compare two or - > ### more cohorts - > ### Aliases: compare_cohorts - > - > ### ** Examples - > + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(agricolaeplotr) + + Type 'citation("agricolaeplotr")' for citing this R package in publications. + + Attaching package: 'agricolaeplotr' + ... - Backtrace: - ▆ - 1. ├─base (local) ``(x) - 2. └─ggplot2:::print.ggplot(x) - 3. ├─ggplot2::ggplot_gtable(data) - 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) - 5. └─ggplot2::calc_element("plot.margin", theme) - 6. └─cli::cli_abort(...) - 7. └─rlang::abort(...) - Execution halted + `expected` is a character vector ('ROW') + ── Failure ('testall.R:847:3'): plot a plot design from FielDHub package shows COLUMN as x axis ── + p$labels$x (`actual`) not identical to "COLUMN" (`expected`). + + `actual` is NULL + `expected` is a character vector ('COLUMN') + + [ FAIL 30 | WARN 92 | SKIP 0 | PASS 107 ] + Error: Test failures + Execution halted ``` # AnalysisLin @@ -410,7 +208,7 @@ Run `revdepcheck::cloud_details(, "allMT")` for more info * GitHub: NA * Source code: https://github.com/cran/AnalysisLin * Date/Publication: 2024-01-30 00:10:10 UTC -* Number of recursive dependencies: 120 +* Number of recursive dependencies: 119 Run `revdepcheck::cloud_details(, "AnalysisLin")` for more info @@ -477,14 +275,75 @@ Run `revdepcheck::cloud_details(, "animbook")` for more info Execution halted ``` +# ANN2 + +
+ +* Version: 2.3.4 +* GitHub: https://github.com/bflammers/ANN2 +* Source code: https://github.com/cran/ANN2 +* Date/Publication: 2020-12-01 10:00:02 UTC +* Number of recursive dependencies: 52 + +Run `revdepcheck::cloud_details(, "ANN2")` for more info + +
+ +## Newly broken + +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(ANN2) + > + > # Only test if not on mac + > if (tolower(Sys.info()[["sysname"]]) != "darwin") { + + test_check("ANN2") + + } + ... + ── Failure ('test-plotting.R:59:3'): the reconstruction_plot.ANN() function works correctly ── + p_AE$labels$colour not equal to "col". + target is NULL, current is character + ── Failure ('test-plotting.R:77:3'): the compression_plot.ANN() function works correctly ── + p_AE$labels$colour not equal to "col". + target is NULL, current is character + + [ FAIL 5 | WARN 1 | SKIP 4 | PASS 143 ] + Error: Test failures + Execution halted + ``` + +## In both + +* checking C++ specification ... NOTE + ``` + Specified C++11: please drop specification unless essential + ``` + +* checking installed package size ... NOTE + ``` + installed size is 58.6Mb + sub-directories of 1Mb or more: + cereal 1.4Mb + libs 57.0Mb + ``` + +* checking LazyData ... NOTE + ``` + 'LazyData' is specified without a 'data' directory + ``` + # aplot
-* Version: 0.2.2 +* Version: 0.2.3 * GitHub: https://github.com/YuLab-SMU/aplot * Source code: https://github.com/cran/aplot -* Date/Publication: 2023-10-06 04:30:02 UTC +* Date/Publication: 2024-06-17 09:50:01 UTC * Number of recursive dependencies: 53 Run `revdepcheck::cloud_details(, "aplot")` for more info @@ -518,92 +377,58 @@ Run `revdepcheck::cloud_details(, "aplot")` for more info Execution halted ``` -# ASRgenomics +# applicable
-* Version: 1.1.4 -* GitHub: NA -* Source code: https://github.com/cran/ASRgenomics -* Date/Publication: 2024-01-29 21:20:02 UTC -* Number of recursive dependencies: 132 +* Version: 0.1.1 +* GitHub: https://github.com/tidymodels/applicable +* Source code: https://github.com/cran/applicable +* Date/Publication: 2024-04-25 00:00:04 UTC +* Number of recursive dependencies: 116 -Run `revdepcheck::cloud_details(, "ASRgenomics")` for more info +Run `revdepcheck::cloud_details(, "applicable")` for more info
## Newly broken -* checking examples ... ERROR - ``` - Running examples in ‘ASRgenomics-Ex.R’ failed - The error most likely occurred in: - - > ### Name: kinship.heatmap - > ### Title: Enhanced heatmap plot for a kinship matrix K - > ### Aliases: kinship.heatmap - > - > ### ** Examples - > - > # Get G matrix. - ... - 7. ├─gtable::gtable_filter(...) - 8. │ └─base::grepl(pattern, .subset2(x$layout, "name"), fixed = fixed) - 9. │ └─base::is.factor(x) - 10. └─ggplot2::ggplotGrob(gg.left) - 11. ├─ggplot2::ggplot_gtable(ggplot_build(x)) - 12. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) - 13. └─ggplot2::calc_element("plot.margin", theme) - 14. └─cli::cli_abort(...) - 15. └─rlang::abort(...) - Execution halted - ``` - * checking tests ... ERROR ``` Running ‘spelling.R’ Running ‘testthat.R’ Running the tests in ‘tests/testthat.R’ failed. Complete output: - > # This file is part of the standard setup for testthat. - > # It is recommended that you do not modify it. - > # - > # Where should you do additional test configuration? - > # Learn more about the roles of various files in: - > # * https://r-pkgs.org/tests.html + > library(testthat) + > library(applicable) + Loading required package: ggplot2 + > + > test_check("applicable") + Loading required package: dplyr ... + `expected` is a character vector ('percentile') + ── Failure ('test-plot.R:36:3'): output of autoplot.apd_pca is correct when options=distance are provided ── + ad_plot$labels$y (`actual`) not equal to "percentile" (`expected`). - ══ Failed tests ════════════════════════════════════════════════════════════════ - ── Failure ('test-kinshipheat.R:11:3'): kinship heatmap works ────────────────── - Expected `... <- NULL` to run without any errors. - i Actually got a with text: - Theme element `plot.margin` must have class . + `actual` is NULL + `expected` is a character vector ('percentile') - [ FAIL 1 | WARN 0 | SKIP 0 | PASS 263 ] + [ FAIL 3 | WARN 0 | SKIP 22 | PASS 90 ] Error: Test failures Execution halted ``` -## In both - -* checking installed package size ... NOTE - ``` - installed size is 8.9Mb - sub-directories of 1Mb or more: - data 8.5Mb - ``` - -# auditor +# ASRgenomics
-* Version: 1.3.5 -* GitHub: https://github.com/ModelOriented/auditor -* Source code: https://github.com/cran/auditor -* Date/Publication: 2023-10-30 15:40:07 UTC -* Number of recursive dependencies: 87 +* Version: 1.1.4 +* GitHub: NA +* Source code: https://github.com/cran/ASRgenomics +* Date/Publication: 2024-01-29 21:20:02 UTC +* Number of recursive dependencies: 136 -Run `revdepcheck::cloud_details(, "auditor")` for more info +Run `revdepcheck::cloud_details(, "ASRgenomics")` for more info
@@ -611,149 +436,36 @@ Run `revdepcheck::cloud_details(, "auditor")` for more info * checking examples ... ERROR ``` - Running examples in ‘auditor-Ex.R’ failed + Running examples in ‘ASRgenomics-Ex.R’ failed The error most likely occurred in: - > ### Name: plot_lift - > ### Title: LIFT Chart - > ### Aliases: plot_lift plotLIFT + > ### Name: kinship.pca + > ### Title: Performs a Principal Component Analysis (PCA) based on a kinship + > ### matrix K + > ### Aliases: kinship.pca > > ### ** Examples > - > data(titanic_imputed, package = "DALEX") ... - Backtrace: - ▆ - 1. ├─base (local) ``(x) - 2. └─ggplot2:::print.ggplot(x) - 3. ├─ggplot2::ggplot_gtable(data) - 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) - 5. └─ggplot2::calc_element("plot.margin", theme) - 6. └─cli::cli_abort(...) - 7. └─rlang::abort(...) + 11. │ └─base::withCallingHandlers(...) + 12. └─ggplot2 (local) f(l = layers[[i]], d = data[[i]]) + 13. └─l$compute_geom_2(d, theme = plot$theme) + 14. └─ggplot2 (local) compute_geom_2(..., self = self) + 15. └─self$geom$use_defaults(...) + 16. └─ggplot2 (local) use_defaults(..., self = self) + 17. └─ggplot2:::check_aesthetics(new_params, nrow(data)) + 18. └─cli::cli_abort(...) + 19. └─rlang::abort(...) Execution halted ``` -* checking running R code from vignettes ... ERROR +## In both + +* checking installed package size ... NOTE ``` - Errors in running code in vignettes: - when running code in ‘model_evaluation_audit.Rmd’ - ... - > plot(eva_glm, eva_rf, type = "lift") - Warning: The `guide` argument in `scale_*()` cannot be `FALSE`. This was deprecated in - ggplot2 3.3.4. - ℹ Please use "none" instead. - ℹ The deprecated feature was likely used in the auditor package. - Please report the issue at . - - When sourcing ‘model_evaluation_audit.R’: - Error: Theme element `plot.margin` must have class . - Execution halted - - ‘model_evaluation_audit.Rmd’ using ‘UTF-8’... failed - ‘model_fit_audit.Rmd’ using ‘UTF-8’... OK - ‘model_performance_audit.Rmd’ using ‘UTF-8’... OK - ‘model_residuals_audit.Rmd’ using ‘UTF-8’... OK - ‘observation_influence_audit.Rmd’ using ‘UTF-8’... OK - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘model_evaluation_audit.Rmd’ using knitr - ``` - -# augmentedRCBD - -
- -* Version: 0.1.7 -* GitHub: https://github.com/aravind-j/augmentedRCBD -* Source code: https://github.com/cran/augmentedRCBD -* Date/Publication: 2023-08-19 00:12:38 UTC -* Number of recursive dependencies: 128 - -Run `revdepcheck::cloud_details(, "augmentedRCBD")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘augmentedRCBD-Ex.R’ failed - The error most likely occurred in: - - > ### Name: augmentedRCBD.bulk - > ### Title: Analysis of Augmented Randomised Complete Block Design for - > ### Multiple Traits/Characters - > ### Aliases: augmentedRCBD.bulk - > - > ### ** Examples - > - ... - 2. ├─base::withCallingHandlers(...) - 3. └─augmentedRCBD::freqdist.augmentedRCBD(...) - 4. ├─base::rbind(ggplotGrob(G2), ggplotGrob(G1), size = "max") - 5. └─ggplot2::ggplotGrob(G2) - 6. ├─ggplot2::ggplot_gtable(ggplot_build(x)) - 7. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) - 8. └─ggplot2::calc_element("plot.margin", theme) - 9. └─cli::cli_abort(...) - 10. └─rlang::abort(...) - Execution halted - ``` - -* checking re-building of vignette outputs ... ERROR - ``` - Error(s) in re-building vignettes: - --- re-building ‘Data_Analysis_with_augmentedRCBD.Rmd’ using rmarkdown_notangle - trying URL 'https://www.r-project.org/logo/Rlogo.png' - Content type 'image/png' length 48148 bytes (47 KB) - ================================================== - downloaded 47 KB - - trying URL 'https://raw.githubusercontent.com/aravind-j/augmentedRCBD/master/vignettes/rbase.png' - Content type 'image/png' length 57299 bytes (55 KB) - ================================================== - ... - Quitting from lines 970-977 [unnamed-chunk-70] (Data_Analysis_with_augmentedRCBD.Rmd) - Error: processing vignette 'Data_Analysis_with_augmentedRCBD.Rmd' failed with diagnostics: - Theme element `plot.margin` must have class . - --- failed re-building ‘Data_Analysis_with_augmentedRCBD.Rmd’ - - SUMMARY: processing the following file failed: - ‘Data_Analysis_with_augmentedRCBD.Rmd’ - - Error: Vignette re-building failed. - Execution halted - ``` - -## Newly fixed - -* checking re-building of vignette outputs ... WARNING - ``` - Error(s) in re-building vignettes: - --- re-building ‘Data_Analysis_with_augmentedRCBD.Rmd’ using rmarkdown_notangle - trying URL 'https://www.r-project.org/logo/Rlogo.png' - Content type 'image/png' length 48148 bytes (47 KB) - ================================================== - downloaded 47 KB - - trying URL 'https://raw.githubusercontent.com/aravind-j/augmentedRCBD/master/vignettes/rbase.png' - Content type 'image/png' length 57299 bytes (55 KB) - ================================================== - ... - - Error: processing vignette 'Data_Analysis_with_augmentedRCBD.Rmd' failed with diagnostics: - LaTeX failed to compile /tmp/workdir/augmentedRCBD/old/augmentedRCBD.Rcheck/vign_test/augmentedRCBD/vignettes/Data_Analysis_with_augmentedRCBD.tex. See https://yihui.org/tinytex/r/#debugging for debugging tips. See Data_Analysis_with_augmentedRCBD.log for more info. - --- failed re-building ‘Data_Analysis_with_augmentedRCBD.Rmd’ - - SUMMARY: processing the following file failed: - ‘Data_Analysis_with_augmentedRCBD.Rmd’ - - Error: Vignette re-building failed. - Execution halted + installed size is 8.9Mb + sub-directories of 1Mb or more: + data 8.5Mb ``` # autoplotly @@ -817,17 +529,17 @@ Run `revdepcheck::cloud_details(, "autoplotly")` for more info Execution halted ``` -# baggr +# autoReg
-* Version: 0.7.8 -* GitHub: https://github.com/wwiecek/baggr -* Source code: https://github.com/cran/baggr -* Date/Publication: 2024-02-12 18:20:02 UTC -* Number of recursive dependencies: 104 +* Version: 0.3.3 +* GitHub: https://github.com/cardiomoon/autoReg +* Source code: https://github.com/cran/autoReg +* Date/Publication: 2023-11-14 05:53:27 UTC +* Number of recursive dependencies: 223 -Run `revdepcheck::cloud_details(, "baggr")` for more info +Run `revdepcheck::cloud_details(, "autoReg")` for more info
@@ -835,71 +547,72 @@ Run `revdepcheck::cloud_details(, "baggr")` for more info * checking examples ... ERROR ``` - Running examples in ‘baggr-Ex.R’ failed + Running examples in ‘autoReg-Ex.R’ failed The error most likely occurred in: - > ### Name: baggr_plot - > ### Title: Plotting method in baggr package - > ### Aliases: baggr_plot + > ### Name: modelPlot + > ### Title: Draw coefficients/odds ratio/hazard ratio plot + > ### Aliases: modelPlot > > ### ** Examples > - > fit <- baggr(schools, pooling = "none") - Automatically chose Rubin model with aggregate data based on input data. - Setting prior for mean in each group using 10 times the max effect : + > fit=lm(mpg~wt*hp+am,data=mtcars) + > modelPlot(fit,widths=c(1,0,2,3)) + > modelPlot(fit,uni=TRUE,threshold=1,widths=c(1,0,2,3)) + Error in identicalUnits(x) : object is not a unit + Calls: ... assemble_guides -> guides_build -> unit.c -> identicalUnits + Execution halted ``` * checking running R code from vignettes ... ERROR ``` Errors in running code in vignettes: - when running code in ‘baggr.Rmd’ + when running code in ‘Automatic_Regression_Modeling.Rmd’ ... - [1] -1.866291 + Species setosa (N=50) Mean ± SD 5.0 ± 0.4 + versicolor (N=50) Mean ± SD 5.9 ± 0.5 1.46 (1.24 to 1.68, p<.001) 1.49 (1.25 to 1.73, p<.001) 1.58 (1.36 to 1.80, p<.001) + virginica (N=50) Mean ± SD 6.6 ± 0.6 1.95 (1.75 to 2.14, p<.001) 2.11 (1.89 to 2.32, p<.001) 2.08 (1.88 to 2.29, p<.001) + ———————————————————————————————————————————————————————————————————————————————————————————————————————————————————————————————————————————————————————— - > my_baggr_comparison <- baggr_compare(schools) - There is no predicted effect when pooling = 'none'. + > modelPlot(fit1, imputed = TRUE) - > plot(my_baggr_comparison) + ggtitle("8 schools: model comparison") + ... - When sourcing ‘baggr.R’: - Error: Theme element `plot.margin` must have class . + When sourcing ‘Survival.R’: + Error: object is not a unit Execution halted - ‘baggr.Rmd’ using ‘UTF-8’... failed - ‘baggr_binary.Rmd’ using ‘UTF-8’... OK + ‘Automatic_Regression_Modeling.Rmd’ using ‘UTF-8’... failed + ‘Bootstrap_Prediction.Rmd’ using ‘UTF-8’... OK + ‘Getting_started.Rmd’ using ‘UTF-8’... failed + ‘Statiastical_test_in_gaze.Rmd’ using ‘UTF-8’... OK + ‘Survival.Rmd’ using ‘UTF-8’... failed ``` * checking re-building of vignette outputs ... NOTE ``` Error(s) in re-building vignettes: - --- re-building ‘baggr.Rmd’ using rmarkdown - ``` - -## In both - -* checking installed package size ... NOTE - ``` - installed size is 195.7Mb - sub-directories of 1Mb or more: - libs 193.9Mb - ``` - -* checking for GNU extensions in Makefiles ... NOTE - ``` - GNU make is a SystemRequirements. + --- re-building ‘Automatic_Regression_Modeling.Rmd’ using rmarkdown + + Quitting from lines 142-143 [unnamed-chunk-15] (Automatic_Regression_Modeling.Rmd) + Error: processing vignette 'Automatic_Regression_Modeling.Rmd' failed with diagnostics: + object is not a unit + --- failed re-building ‘Automatic_Regression_Modeling.Rmd’ + + --- re-building ‘Bootstrap_Prediction.Rmd’ using rmarkdown ``` -# bayefdr +# bartMan
-* Version: 0.2.1 -* GitHub: https://github.com/VallejosGroup/bayefdr -* Source code: https://github.com/cran/bayefdr -* Date/Publication: 2022-10-26 19:35:06 UTC -* Number of recursive dependencies: 96 +* Version: 0.1.0 +* GitHub: NA +* Source code: https://github.com/cran/bartMan +* Date/Publication: 2024-04-15 15:40:07 UTC +* Number of recursive dependencies: 135 -Run `revdepcheck::cloud_details(, "bayefdr")` for more info +Run `revdepcheck::cloud_details(, "bartMan")` for more info
@@ -907,50 +620,62 @@ Run `revdepcheck::cloud_details(, "bayefdr")` for more info * checking examples ... ERROR ``` - Running examples in ‘bayefdr-Ex.R’ failed + Running examples in ‘bartMan-Ex.R’ failed The error most likely occurred in: - > ### Name: traceplot - > ### Title: Trace, marginal density histogram, and autocorrelation plot of - > ### MCMC draws. - > ### Aliases: traceplot + > ### Name: plotTrees + > ### Title: Plot Trees with Customisations + > ### Aliases: plotTrees > > ### ** Examples > + > if (requireNamespace("dbarts", quietly = TRUE)) { ... - ▆ - 1. └─bayefdr::traceplot(x) - 2. └─ggExtra::ggMarginal(p1, type = "histogram", margins = "y") - 3. └─ggplot2::ggplotGrob(scatP) - 4. ├─ggplot2::ggplot_gtable(ggplot_build(x)) - 5. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) - 6. └─ggplot2::calc_element("plot.margin", theme) - 7. └─cli::cli_abort(...) - 8. └─rlang::abort(...) + | + |======================================================================| 99% + | + |======================================================================| 100% + Extracting Observation Data... + + Displaying All Trees. + Error in names(labels) <- `*vtmp*` : attempt to set an attribute on NULL + Calls: plotTrees ... ggplot_add -> ggplot_add.new_aes -> bump_aes_labels Execution halted ``` +# bayesAB + +
+ +* Version: 1.1.3 +* GitHub: https://github.com/FrankPortman/bayesAB +* Source code: https://github.com/cran/bayesAB +* Date/Publication: 2021-06-25 00:50:02 UTC +* Number of recursive dependencies: 74 + +Run `revdepcheck::cloud_details(, "bayesAB")` for more info + +
+ +## Newly broken + * checking tests ... ERROR ``` Running ‘testthat.R’ Running the tests in ‘tests/testthat.R’ failed. Complete output: > library(testthat) - > library(bayefdr) + > library(bayesAB) > - > test_check("bayefdr") - [ FAIL 1 | WARN 1 | SKIP 0 | PASS 14 ] + > test_check("bayesAB") + [ FAIL 1 | WARN 4 | SKIP 0 | PASS 140 ] ══ Failed tests ════════════════════════════════════════════════════════════════ - ... - 6. └─ggplot2::ggplotGrob(scatP) - 7. ├─ggplot2::ggplot_gtable(ggplot_build(x)) - 8. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) - 9. └─ggplot2::calc_element("plot.margin", theme) - 10. └─cli::cli_abort(...) - 11. └─rlang::abort(...) + ── Failure ('test-dists.R:34:3'): Success ────────────────────────────────────── + plotNormalInvGamma(3, 1, 1, 1)$labels$y not equal to "sig_sq". + target is NULL, current is character - [ FAIL 1 | WARN 1 | SKIP 0 | PASS 14 ] + [ FAIL 1 | WARN 4 | SKIP 0 | PASS 140 ] Error: Test failures Execution halted ``` @@ -983,8 +708,8 @@ Run `revdepcheck::cloud_details(, "BayesGrowth")` for more info ℹ Please use `linewidth` instead. When sourcing ‘MCMC-example.R’: - Error: unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, "black", TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 14, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, FALSE), NULL, list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), 5.5, c(5.5, 5.5, 5.5, 5.5), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.75, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, - NULL, NULL, NULL, 1, 90, NULL, c(0, 2.75, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 1, NULL, NULL, NULL, c(0, 2.2, 0, 0), NULL, TRUE), NULL, li + Error: unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, "black", TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 14, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, FALSE), list(NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), 5.5, c(5.5, 5.5, 5.5, 5.5), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.75, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, + NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, 90, NULL, c(0, 2.75, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, Execution halted ‘MCMC-example.Rmd’ using ‘UTF-8’... failed @@ -1027,6 +752,31 @@ Run `revdepcheck::cloud_details(, "BayesianReasoning")` for more info ## Newly broken +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(BayesianReasoning) + > + > test_check("BayesianReasoning") + + Plot created in: ./FP_10_sens_100_screening_1667_diagnostic_44.png + + ... + `expected` is a character vector ('PPV') + ── Failure ('test-PPV_heatmap.R:748:3'): NPV Plot ────────────────────────────── + p$result$labels$fill (`actual`) not identical to "NPV" (`expected`). + + `actual` is NULL + `expected` is a character vector ('NPV') + + [ FAIL 3 | WARN 56 | SKIP 4 | PASS 120 ] + Error: Test failures + Execution halted + ``` + * checking running R code from vignettes ... ERROR ``` Errors in running code in vignettes: @@ -1053,6 +803,129 @@ Run `revdepcheck::cloud_details(, "BayesianReasoning")` for more info --- re-building ‘PPV_NPV.Rmd’ using rmarkdown ``` +# BayesMallows + +
+ +* Version: 2.2.1 +* GitHub: https://github.com/ocbe-uio/BayesMallows +* Source code: https://github.com/cran/BayesMallows +* Date/Publication: 2024-04-22 20:20:02 UTC +* Number of recursive dependencies: 82 + +Run `revdepcheck::cloud_details(, "BayesMallows")` for more info + +
+ +## Newly broken + +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > # This file is part of the standard setup for testthat. + > # It is recommended that you do not modify it. + > # + > # Where should you do additional test configuration? + > # Learn more about the roles of various files in: + > # * https://r-pkgs.org/testing-design.html#sec-tests-files-overview + > # * https://testthat.r-lib.org/articles/special-files.html + ... + `expected` is a character vector ('interaction(chain, cluster)') + ── Failure ('test-assess_convergence.R:217:3'): assess_convergence.BayesMallowsMixtures works ── + p$labels$colour (`actual`) not equal to "cluster" (`expected`). + + `actual` is NULL + `expected` is a character vector ('cluster') + + [ FAIL 10 | WARN 0 | SKIP 6 | PASS 432 ] + Error: Test failures + Execution halted + ``` + +## In both + +* checking installed package size ... NOTE + ``` + installed size is 22.9Mb + sub-directories of 1Mb or more: + doc 2.7Mb + libs 19.3Mb + ``` + +# bayesplot + +
+ +* Version: 1.11.1 +* GitHub: https://github.com/stan-dev/bayesplot +* Source code: https://github.com/cran/bayesplot +* Date/Publication: 2024-02-15 05:30:11 UTC +* Number of recursive dependencies: 126 + +Run `revdepcheck::cloud_details(, "bayesplot")` for more info + +
+ +## Newly broken + +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(bayesplot) + This is bayesplot version 1.11.1 + - Online documentation and vignettes at mc-stan.org/bayesplot + - bayesplot theme set to bayesplot::theme_default() + * Does _not_ affect other ggplot2 plots + * See ?bayesplot_theme_set for details on theme setting + ... + ══ Failed tests ════════════════════════════════════════════════════════════════ + ── Failure ('test-mcmc-traces.R:55:3'): mcmc_trace options work ──────────────── + all(c("xmin", "xmax", "ymin", "ymax") %in% names(ll)) is not TRUE + + `actual`: FALSE + `expected`: TRUE + + [ FAIL 1 | WARN 1 | SKIP 73 | PASS 1024 ] + Error: Test failures + Execution halted + ``` + +## In both + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘visual-mcmc-diagnostics.Rmd’ + ... + + > schools_dat <- list(J = 8, y = c(28, 8, -3, 7, -1, + + 1, 18, 12), sigma = c(15, 10, 16, 11, 9, 11, 10, 18)) + + > fit_cp <- sampling(schools_mod_cp, data = schools_dat, + + seed = 803214055, control = list(adapt_delta = 0.9)) + + When sourcing ‘visual-mcmc-diagnostics.R’: + Error: error in evaluating the argument 'object' in selecting a method for function 'sampling': object 'schools_mod_cp' not found + Execution halted + + ‘graphical-ppcs.Rmd’ using ‘UTF-8’... OK + ‘plotting-mcmc-draws.Rmd’ using ‘UTF-8’... OK + ‘visual-mcmc-diagnostics.Rmd’ using ‘UTF-8’... failed + ``` + +* checking installed package size ... NOTE + ``` + installed size is 8.6Mb + sub-directories of 1Mb or more: + R 4.0Mb + doc 3.8Mb + ``` + # bayestestR
@@ -1106,7 +979,7 @@ Run `revdepcheck::cloud_details(, "bayestestR")` for more info > > test_check("bayestestR") Starting 2 test processes - [ FAIL 2 | WARN 3 | SKIP 75 | PASS 186 ] + [ FAIL 3 | WARN 5 | SKIP 75 | PASS 180 ] ... 14. └─brms:::eval2(call, envir = args, enclos = envir) @@ -1116,186 +989,100 @@ Run `revdepcheck::cloud_details(, "bayestestR")` for more info 18. └─rstan:::cxxfunctionplus(...) 19. └─base::sink(type = "output") - [ FAIL 2 | WARN 3 | SKIP 75 | PASS 186 ] + [ FAIL 3 | WARN 5 | SKIP 75 | PASS 180 ] Error: Test failures Execution halted ``` -# bdots +# beastt
-* Version: 1.2.5 -* GitHub: https://github.com/collinn/bdots -* Source code: https://github.com/cran/bdots -* Date/Publication: 2023-01-06 23:20:02 UTC -* Number of recursive dependencies: 53 +* Version: 0.0.1 +* GitHub: https://github.com/GSK-Biostatistics/beastt +* Source code: https://github.com/cran/beastt +* Date/Publication: 2024-06-20 15:50:16 UTC +* Number of recursive dependencies: 100 -Run `revdepcheck::cloud_details(, "bdots")` for more info +Run `revdepcheck::cloud_details(, "beastt")` for more info
## Newly broken -* checking running R code from vignettes ... ERROR +* checking examples ... ERROR ``` - Errors in running code in vignettes: - when running code in ‘bdots.Rmd’ - ... - Adjusted alpha: 0.01182815 - Significant Intervals at adjusted alpha: - [,1] [,2] - [1,] 556 940 - - > plot(boot1) + Running examples in ‘beastt-Ex.R’ failed + The error most likely occurred in: - When sourcing ‘bdots.R’: - Error: Theme element `plot.margin` must have class . + > ### Name: plot_dist + > ### Title: Plot Distribution + > ### Aliases: plot_dist + > + > ### ** Examples + > + > library(distributional) + ... + 12. │ └─ggplot2 (local) f(l = layers[[i]], d = data[[i]]) + 13. │ └─l$compute_geom_2(d, theme = plot$theme) + 14. │ └─ggplot2 (local) compute_geom_2(..., self = self) + 15. │ └─self$geom$use_defaults(...) + 16. └─base::.handleSimpleError(...) + 17. └─rlang (local) h(simpleError(msg, call)) + 18. └─handlers[[1L]](cnd) + 19. └─cli::cli_abort(...) + 20. └─rlang::abort(...) Execution halted - - ‘bdots.Rmd’ using ‘UTF-8’... failed - ‘correlations.Rmd’ using ‘UTF-8’... OK - ‘customCurves.Rmd’ using ‘UTF-8’... OK - ‘refitCoef.Rmd’ using ‘UTF-8’... OK - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘bdots.Rmd’ using rmarkdown ``` -# bdrc - -
- -* Version: 1.1.0 -* GitHub: https://github.com/sor16/bdrc -* Source code: https://github.com/cran/bdrc -* Date/Publication: 2023-03-19 17:10:03 UTC -* Number of recursive dependencies: 75 - -Run `revdepcheck::cloud_details(, "bdrc")` for more info - -
- -## Newly broken - * checking running R code from vignettes ... ERROR ``` Errors in running code in vignettes: - when running code in ‘tournament.Rmd’ + when running code in ‘binary.Rmd’ ... - 3 1 2 plm -8.903540 4.249257 26.305595 -0.3185195 FALSE - 4 1 2 plm0 -8.873488 4.120050 25.987075 NA TRUE - 5 2 3 gplm0 5.884914 6.692781 1.615733 24.3713418 TRUE - 6 2 3 plm0 -8.873488 4.120050 25.987075 NA FALSE - > plot(t_obj) + > plot_dist(pwr_prior) - When sourcing ‘tournament.R’: - Error: Theme element `plot.margin` must have class . + When sourcing ‘binary.R’: + Error: Problem while setting up geom aesthetics. + ℹ Error occurred in the 1st layer. + Caused by error in `use_defaults()`: + ... + When sourcing ‘continuous.R’: + Error: Problem while setting up geom aesthetics. + ℹ Error occurred in the 1st layer. + Caused by error in `use_defaults()`: + ! unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, "black", TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), list(NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), 5.5, c(5.5, 5.5, 5.5, 5.5), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.75, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, + NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, 90, NULL, c(0, 2.75, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL Execution halted - ‘background.Rmd’ using ‘UTF-8’... OK - ‘introduction.Rmd’ using ‘UTF-8’... OK - ‘tournament.Rmd’ using ‘UTF-8’... failed + ‘binary.Rmd’ using ‘UTF-8’... failed + ‘continuous.Rmd’ using ‘UTF-8’... failed ``` * checking re-building of vignette outputs ... NOTE ``` Error(s) in re-building vignettes: - --- re-building ‘background.Rmd’ using rmarkdown - --- finished re-building ‘background.Rmd’ - - --- re-building ‘introduction.Rmd’ using rmarkdown + --- re-building ‘binary.Rmd’ using rmarkdown ``` -# BeeBDC +# besthr
-* Version: 1.1.1 -* GitHub: https://github.com/jbdorey/BeeBDC -* Source code: https://github.com/cran/BeeBDC -* Date/Publication: 2024-04-03 23:53:03 UTC -* Number of recursive dependencies: 219 +* Version: 0.3.2 +* GitHub: NA +* Source code: https://github.com/cran/besthr +* Date/Publication: 2023-04-14 08:50:08 UTC +* Number of recursive dependencies: 67 -Run `revdepcheck::cloud_details(, "BeeBDC")` for more info +Run `revdepcheck::cloud_details(, "besthr")` for more info
## Newly broken -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > # This file is part of the standard setup for testthat. - > # It is recommended that you do not modify it. - > # - > # Where should you do additional test configuration? - > # Learn more about the roles of various files in: - > # * https://r-pkgs.org/tests.html - > # * https://testthat.r-lib.org/reference/test_package.html#special-files - ... - 8. └─ggplot2:::ggplot_gtable.ggplot_built(data) - 9. └─ggplot2::calc_element("plot.margin", theme) - 10. └─cli::cli_abort(...) - 11. └─rlang::abort(...) - - [ FAIL 1 | WARN 4 | SKIP 0 | PASS 235 ] - Error: Test failures - Execution halted - Warning message: - Connection is garbage-collected, use dbDisconnect() to avoid this. - ``` - -## In both - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘BeeBDC_main.Rmd’ - ... - - > rm(testChecklist) - - > check_space <- BeeBDC::countryOutlieRs(checklist = checklistFile, - + data = check_space, keepAdjacentCountry = TRUE, pointBuffer = 0.05, - + .... [TRUNCATED] - - When sourcing ‘BeeBDC_main.R’: - Error: object 'checklistFile' not found - Execution halted - - ‘BeeBDC_main.Rmd’ using ‘UTF-8’... failed - ‘basic_workflow.Rmd’ using ‘UTF-8’... OK - ``` - -* checking data for non-ASCII characters ... NOTE - ``` - Note: found 107 marked UTF-8 strings - ``` - -# besthr - -
- -* Version: 0.3.2 -* GitHub: NA -* Source code: https://github.com/cran/besthr -* Date/Publication: 2023-04-14 08:50:08 UTC -* Number of recursive dependencies: 67 - -Run `revdepcheck::cloud_details(, "besthr")` for more info - -
- -## Newly broken - -* checking examples ... ERROR +* checking examples ... ERROR ``` Running examples in ‘besthr-Ex.R’ failed The error most likely occurred in: @@ -1322,11 +1109,11 @@ Run `revdepcheck::cloud_details(, "besthr")` for more info when running code in ‘basic-use.Rmd’ ... Confidence Intervals (0.025, 0.975) - 4.07125, 8.62625 + 4.16875, 8.42625 100 bootstrap resamples. > plot(hr_est_1) - Picking joint bandwidth of 0.412 + Picking joint bandwidth of 0.418 When sourcing ‘basic-use.R’: Error: object is not coercible to a unit @@ -1353,293 +1140,94 @@ Run `revdepcheck::cloud_details(, "besthr")` for more info Execution halted ``` -# BetaPASS - -
- -* Version: 1.1-2 -* GitHub: NA -* Source code: https://github.com/cran/BetaPASS -* Date/Publication: 2023-10-18 21:00:08 UTC -* Number of recursive dependencies: 58 - -Run `revdepcheck::cloud_details(, "BetaPASS")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘BetaPASS-Ex.R’ failed - The error most likely occurred in: - - > ### Name: betapower - > ### Title: Find Power with Beta distribution - > ### Aliases: betapower - > - > ### ** Examples - > - > BPmat <- betapower(mu0 = 0.56, sd0 = 0.255, mu1.start = .70, mu1.end = .75, mu1.by = .05, - ... - Backtrace: - ▆ - 1. ├─base (local) ``(x) - 2. └─ggplot2:::print.ggplot(x) - 3. ├─ggplot2::ggplot_gtable(data) - 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) - 5. └─ggplot2::calc_element("plot.margin", theme) - 6. └─cli::cli_abort(...) - 7. └─rlang::abort(...) - Execution halted - ``` - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘BetaPASS.Rmd’ - ... - | 0.825| 0.775| 45| 0.70| - | 0.975| 0.975| 45| 0.75| - | 0.925| 0.875| 50| 0.70| - | 1.000| 0.975| 50| 0.75| - - > plot(Power.mat, link.type = "logit", by = "mu1") - - When sourcing ‘BetaPASS.R’: - Error: Theme element `plot.margin` must have class . - Execution halted - - ‘BetaPASS.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - ... - --- re-building ‘BetaPASS.Rmd’ using rmarkdown - - Quitting from lines 101-102 [unnamed-chunk-4] (BetaPASS.Rmd) - Error: processing vignette 'BetaPASS.Rmd' failed with diagnostics: - Theme element `plot.margin` must have class . - --- failed re-building ‘BetaPASS.Rmd’ - - SUMMARY: processing the following file failed: - ‘BetaPASS.Rmd’ - - Error: Vignette re-building failed. - Execution halted - ``` - -# biblioverlap - -
- -* Version: 1.0.2 -* GitHub: https://github.com/gavieira/biblioverlap -* Source code: https://github.com/cran/biblioverlap -* Date/Publication: 2023-11-07 19:50:02 UTC -* Number of recursive dependencies: 93 - -Run `revdepcheck::cloud_details(, "biblioverlap")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘biblioverlap-Ex.R’ failed - The error most likely occurred in: - - > ### Name: plot_upset - > ### Title: Plotting UpSet plot from biblioverlap results - > ### Aliases: plot_upset - > - > ### ** Examples - > - > #Running document-level matching procedure - ... - 3. ├─base::suppressMessages(...) - 4. │ └─base::withCallingHandlers(...) - 5. └─UpSetR:::Make_main_bar(...) - 6. └─ggplot2::ggplotGrob(Main_bar_plot) - 7. ├─ggplot2::ggplot_gtable(ggplot_build(x)) - 8. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) - 9. └─ggplot2::calc_element("plot.margin", theme) - 10. └─cli::cli_abort(...) - 11. └─rlang::abort(...) - Execution halted - ``` - -## In both - -* checking data for non-ASCII characters ... NOTE - ``` - Note: found 573 marked UTF-8 strings - ``` - -# biscale +# biclustermd
-* Version: 1.0.0 -* GitHub: https://github.com/chris-prener/biscale -* Source code: https://github.com/cran/biscale -* Date/Publication: 2022-05-27 08:40:09 UTC -* Number of recursive dependencies: 83 +* Version: 0.2.3 +* GitHub: https://github.com/jreisner/biclustermd +* Source code: https://github.com/cran/biclustermd +* Date/Publication: 2021-06-17 15:10:06 UTC +* Number of recursive dependencies: 84 -Run `revdepcheck::cloud_details(, "biscale")` for more info +Run `revdepcheck::cloud_details(, "biclustermd")` for more info
## Newly broken -* checking examples ... ERROR +* checking tests ... ERROR ``` - Running examples in ‘biscale-Ex.R’ failed - The error most likely occurred in: - - > ### Name: bi_legend - > ### Title: Create Object for Drawing Legend - > ### Aliases: bi_legend - > - > ### ** Examples - > - > # sample 3x3 legend + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(biclustermd) + Loading required package: ggplot2 + Loading required package: tidyr + + Attaching package: 'tidyr' + ... - Backtrace: - ▆ - 1. ├─base (local) ``(x) - 2. └─ggplot2:::print.ggplot(x) - 3. ├─ggplot2::ggplot_gtable(data) - 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) - 5. └─ggplot2::calc_element("plot.margin", theme) - 6. └─cli::cli_abort(...) - 7. └─rlang::abort(...) - Execution halted + ── Failure ('test-autoplot_biclustermd.R:6:3'): autoplot_biclustermd() correctly plots cluster lines ── + ap$data[[3]]$xintercept[-1] not equal to cumsum(colSums(sbc$P)) + 0.5. + Classes differ: 'mapped_discrete'/'numeric' is not 'numeric' + ── Failure ('test-autoplot_biclustermd.R:7:3'): autoplot_biclustermd() correctly plots cluster lines ── + ap$data[[4]]$yintercept[-1] not equal to cumsum(colSums(sbc$Q)) + 0.5. + Classes differ: 'mapped_discrete'/'numeric' is not 'numeric' + + [ FAIL 2 | WARN 0 | SKIP 0 | PASS 66 ] + Error: Test failures + Execution halted ``` ## In both -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘biscale.Rmd’ - ... - - > knitr::opts_chunk$set(collapse = TRUE, comment = "#>") - - > knitr::include_graphics("../man/figures/biscale.001.jpeg") - - When sourcing ‘biscale.R’: - Error: Cannot find the file(s): "../man/figures/biscale.001.jpeg" - ... - > knitr::include_graphics("../man/figures/raster.jpeg") - - When sourcing ‘rasters.R’: - Error: Cannot find the file(s): "../man/figures/raster.jpeg" - Execution halted - - ‘biscale.Rmd’ using ‘UTF-8’... failed - ‘bivariate_palettes.Rmd’ using ‘UTF-8’... failed - ‘breaks.Rmd’ using ‘UTF-8’... failed - ‘rasters.Rmd’ using ‘UTF-8’... failed - ``` - * checking dependencies in R code ... NOTE ``` - Namespaces in Imports field not imported from: - ‘stats’ ‘utils’ + Namespace in Imports field not imported from: ‘nycflights13’ All declared Imports should be used. ``` -# BlandAltmanLeh - -
- -* Version: 0.3.1 -* GitHub: NA -* Source code: https://github.com/cran/BlandAltmanLeh -* Date/Publication: 2015-12-23 23:32:17 -* Number of recursive dependencies: 63 - -Run `revdepcheck::cloud_details(, "BlandAltmanLeh")` for more info - -
- -## Newly broken - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘Intro.Rmd’ - ... - > b <- 0.02 * a + 0.3 * rnorm(150) - - > library(ggExtra) - - > print(ggMarginal(bland.altman.plot(a, b, graph.sys = "ggplot2"), - + type = "histogram", size = 4)) - - When sourcing ‘Intro.R’: - Error: Theme element `plot.margin` must have class . - Execution halted - - ‘Intro.Rmd’... failed - ``` - -# bnma +# biodosetools
-* Version: 1.6.0 -* GitHub: NA -* Source code: https://github.com/cran/bnma -* Date/Publication: 2024-02-11 01:10:02 UTC -* Number of recursive dependencies: 53 +* Version: 3.6.1 +* GitHub: https://github.com/biodosetools-team/biodosetools +* Source code: https://github.com/cran/biodosetools +* Date/Publication: 2022-11-16 16:00:02 UTC +* Number of recursive dependencies: 121 -Run `revdepcheck::cloud_details(, "bnma")` for more info +Run `revdepcheck::cloud_details(, "biodosetools")` for more info
## Newly broken -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘bnma.Rmd’ - ... - - > network.forest.plot(result, label.margin = 15) - Warning in geom_text(aes(label = "Median [95% Crl]"), y = xlim.range[2] + : - All aesthetics have length 1, but the data has 6 rows. - ℹ Please consider using `annotate()` or provide this layer with data containing - a single row. - - When sourcing ‘bnma.R’: - Error: Theme element `plot.margin` must have class . - Execution halted - - ‘bnma.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE +* checking tests ... ERROR ``` - Error(s) in re-building vignettes: - ... - --- re-building ‘bnma.Rmd’ using rmarkdown - - Quitting from lines 88-99 [unnamed-chunk-8] (bnma.Rmd) - Error: processing vignette 'bnma.Rmd' failed with diagnostics: - Theme element `plot.margin` must have class . - --- failed re-building ‘bnma.Rmd’ - - SUMMARY: processing the following file failed: - ‘bnma.Rmd’ - - Error: Vignette re-building failed. - Execution halted + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(biodosetools) + > + > test_check("biodosetools") + ! Problem with `glm()` -> constraint ML optimization will be used instead + ! Problem with `glm()` -> constraint ML optimization will be used instead + number of iterations= 43 + ... + actual | expected + [2] "Estimation" | "Estimation" [2] + [3] "Dose (Gy)" | "Dose (Gy)" [3] + [4] "Translocations/cells" | "Translocations/cells" [4] + - "yield_low" [5] + - "yield_upp" [6] + + [ FAIL 4 | WARN 0 | SKIP 1 | PASS 232 ] + Error: Test failures + Execution halted ``` # boxly @@ -1724,6 +1312,47 @@ Run `revdepcheck::cloud_details(, "braidReports")` for more info Execution halted ``` +# breathtestcore + +
+ +* Version: 0.8.7 +* GitHub: https://github.com/dmenne/breathtestcore +* Source code: https://github.com/cran/breathtestcore +* Date/Publication: 2024-01-24 15:02:47 UTC +* Number of recursive dependencies: 130 + +Run `revdepcheck::cloud_details(, "breathtestcore")` for more info + +
+ +## Newly broken + +* checking tests ... ERROR + ``` + Running ‘test-all.R’ + Running the tests in ‘tests/test-all.R’ failed. + Complete output: + > library(testthat) + > + > options(Ncpus = parallelly::availableCores(omit = 1)) + > test_check("breathtestcore") + Loading required package: breathtestcore + Starting 1 test process + [ FAIL 3 | WARN 11 | SKIP 4 | PASS 356 ] + ... + `expected`: 10 + ── Failure ('test_plot_breathtestfit.R:81:3'): Plot multiple groups data only (no fit) ── + length(p) (`actual`) not equal to length(ggplot()) (`expected`). + + `actual`: 11 + `expected`: 10 + + [ FAIL 3 | WARN 11 | SKIP 4 | PASS 356 ] + Error: Test failures + Execution halted + ``` + # brolgar
@@ -1763,6 +1392,8 @@ Run `revdepcheck::cloud_details(, "brolgar")` for more info Execution halted ``` +## In both + * checking running R code from vignettes ... ERROR ``` Errors in running code in vignettes: @@ -1804,17 +1435,17 @@ Run `revdepcheck::cloud_details(, "brolgar")` for more info --- re-building ‘finding-features.Rmd’ using rmarkdown ``` -# calendR +# cartograflow
-* Version: 1.2 -* GitHub: NA -* Source code: https://github.com/cran/calendR -* Date/Publication: 2023-10-05 17:30:02 UTC -* Number of recursive dependencies: 52 +* Version: 1.0.5 +* GitHub: https://github.com/fbahoken/cartogRaflow +* Source code: https://github.com/cran/cartograflow +* Date/Publication: 2023-10-17 22:40:21 UTC +* Number of recursive dependencies: 102 -Run `revdepcheck::cloud_details(, "calendR")` for more info +Run `revdepcheck::cloud_details(, "cartograflow")` for more info
@@ -1822,157 +1453,77 @@ Run `revdepcheck::cloud_details(, "calendR")` for more info * checking examples ... ERROR ``` - Running examples in ‘calendR-Ex.R’ failed + Running examples in ‘cartograflow-Ex.R’ failed The error most likely occurred in: - > ### Name: calendR - > ### Title: Monthly and yearly calendars - > ### Aliases: calendR + > ### Name: flowgini + > ### Title: Analysis of flow concentration (Gini coefficient) + > ### Aliases: flowgini > > ### ** Examples > - > # Calendar of the current year + > library(cartograflow) ... - Backtrace: - ▆ - 1. ├─base (local) ``(x) - 2. └─ggplot2:::print.ggplot(x) - 3. ├─ggplot2::ggplot_gtable(data) - 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) - 5. └─ggplot2::calc_element("plot.margin", theme) - 6. └─cli::cli_abort(...) - 7. └─rlang::abort(...) - Execution halted - ``` - -# calendRio - -
- -* Version: 0.2.0 -* GitHub: NA -* Source code: https://github.com/cran/calendRio -* Date/Publication: 2022-03-10 07:50:02 UTC -* Number of recursive dependencies: 52 - -Run `revdepcheck::cloud_details(, "calendRio")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘calendRio-Ex.R’ failed - The error most likely occurred in: - - > ### Name: calendR - > ### Title: Monthly and yearly calendars - > ### Aliases: calendR - > - > ### ** Examples - > - > # Calendar of the current year - ... - Backtrace: - ▆ - 1. ├─base (local) ``(x) - 2. └─ggplot2:::print.ggplot(x) - 3. ├─ggplot2::ggplot_gtable(data) - 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) - 5. └─ggplot2::calc_element("plot.margin", theme) - 6. └─cli::cli_abort(...) - 7. └─rlang::abort(...) + ℹ Use `flowcum` instead. + Warning: Use of `x$linkcum` is discouraged. + ℹ Use `linkcum` instead. + Warning: Use of `x$flowcum` is discouraged. + ℹ Use `flowcum` instead. + Warning: Use of `x$flowcum` is discouraged. + ℹ Use `flowcum` instead. + Error in pm[[2]] : subscript out of bounds + Calls: flowgini ... %>% -> layout -> ggplotly -> ggplotly.ggplot -> gg2list Execution halted ``` -# capm +# cartographr
-* Version: 0.14.0 -* GitHub: NA -* Source code: https://github.com/cran/capm -* Date/Publication: 2019-10-24 16:50:05 UTC -* Number of recursive dependencies: 61 +* Version: 0.2.2 +* GitHub: https://github.com/da-wi/cartographr +* Source code: https://github.com/cran/cartographr +* Date/Publication: 2024-06-28 14:50:09 UTC +* Number of recursive dependencies: 99 -Run `revdepcheck::cloud_details(, "capm")` for more info +Run `revdepcheck::cloud_details(, "cartographr")` for more info
## Newly broken -* checking examples ... ERROR +* checking tests ... ERROR ``` - Running examples in ‘capm-Ex.R’ failed - The error most likely occurred in: - - > ### Name: PlotPopPyramid - > ### Title: Population PlotPopPyramid - > ### Aliases: PlotPopPyramid - > - > ### ** Examples - > - > data(dogs) + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > # This file is part of the standard setup for testthat. + > # It is recommended that you do not modify it. + > # + > # Where should you do additional test configuration? + > # Learn more about the roles of various files in: + > # * https://r-pkgs.org/testing-design.html#sec-tests-files-overview + > # * https://testthat.r-lib.org/articles/special-files.html ... - Backtrace: - ▆ - 1. ├─base (local) ``(x) - 2. └─ggplot2:::print.ggplot(x) - 3. ├─ggplot2::ggplot_gtable(data) - 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) - 5. └─ggplot2::calc_element("plot.margin", theme) - 6. └─cli::cli_abort(...) - 7. └─rlang::abort(...) - Execution halted + 21. │ └─base::stop(...) + 22. └─base::.handleSimpleError(...) + 23. └─rlang (local) h(simpleError(msg, call)) + 24. └─handlers[[1L]](cnd) + 25. └─cli::cli_abort(...) + 26. └─rlang::abort(...) + + [ FAIL 1 | WARN 0 | SKIP 0 | PASS 106 ] + Error: Test failures + Execution halted ``` ## In both -* checking data for non-ASCII characters ... NOTE - ``` - Note: found 59 marked UTF-8 strings - ``` - -# cartograflow - -
- -* Version: 1.0.5 -* GitHub: https://github.com/fbahoken/cartogRaflow -* Source code: https://github.com/cran/cartograflow -* Date/Publication: 2023-10-17 22:40:21 UTC -* Number of recursive dependencies: 102 - -Run `revdepcheck::cloud_details(, "cartograflow")` for more info - -
- -## Newly broken - -* checking examples ... ERROR +* checking installed package size ... NOTE ``` - Running examples in ‘cartograflow-Ex.R’ failed - The error most likely occurred in: - - > ### Name: flowgini - > ### Title: Analysis of flow concentration (Gini coefficient) - > ### Aliases: flowgini - > - > ### ** Examples - > - > library(cartograflow) - ... - ℹ Use `flowcum` instead. - Warning: Use of `x$linkcum` is discouraged. - ℹ Use `linkcum` instead. - Warning: Use of `x$flowcum` is discouraged. - ℹ Use `flowcum` instead. - Warning: Use of `x$flowcum` is discouraged. - ℹ Use `flowcum` instead. - Error in pm[[2]] : subscript out of bounds - Calls: flowgini ... %>% -> layout -> ggplotly -> ggplotly.ggplot -> gg2list - Execution halted + installed size is 5.3Mb + sub-directories of 1Mb or more: + data 3.5Mb ``` # cats @@ -2033,7 +1584,7 @@ Run `revdepcheck::cloud_details(, "cats")` for more info * GitHub: https://github.com/nspyrison/cheem * Source code: https://github.com/cran/cheem * Date/Publication: 2023-11-08 21:30:02 UTC -* Number of recursive dependencies: 152 +* Number of recursive dependencies: 153 Run `revdepcheck::cloud_details(, "cheem")` for more info @@ -2209,60 +1760,17 @@ Run `revdepcheck::cloud_details(, "chronicle")` for more info All declared Imports should be used. ``` -# circumplex - -
- -* Version: 0.3.10 -* GitHub: https://github.com/jmgirard/circumplex -* Source code: https://github.com/cran/circumplex -* Date/Publication: 2023-08-22 07:20:05 UTC -* Number of recursive dependencies: 101 - -Run `revdepcheck::cloud_details(, "circumplex")` for more info - -
- -## Newly broken - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘introduction-to-ssm-analysis.Rmd’ - ... - + "BC", "DE", "FG", "HI", "JK", "LM", "NO"), levels = c("PA", - + "BC", "DE", "FG", "HI ..." ... [TRUNCATED] - - > ggplot2::ggplot(dat_r, ggplot2::aes(x = Angle, y = est)) + - + ggplot2::geom_hline(yintercept = 0, size = 1.25, color = "darkgray") + - + ggpl .... [TRUNCATED] - - When sourcing ‘introduction-to-ssm-analysis.R’: - Error: Theme element `plot.margin` must have class . - Execution halted - - ‘intermediate-ssm-analysis.Rmd’ using ‘UTF-8’... OK - ‘introduction-to-ssm-analysis.Rmd’ using ‘UTF-8’... failed - ‘using-instruments.Rmd’ using ‘UTF-8’... OK - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘intermediate-ssm-analysis.Rmd’ using rmarkdown - ``` - -# cities +# circhelp
-* Version: 0.1.3 -* GitHub: NA -* Source code: https://github.com/cran/cities -* Date/Publication: 2023-08-08 07:50:10 UTC -* Number of recursive dependencies: 85 +* Version: 1.1 +* GitHub: https://github.com/achetverikov/circhelp +* Source code: https://github.com/cran/circhelp +* Date/Publication: 2024-07-04 17:10:02 UTC +* Number of recursive dependencies: 106 -Run `revdepcheck::cloud_details(, "cities")` for more info +Run `revdepcheck::cloud_details(, "circhelp")` for more info
@@ -2270,103 +1778,100 @@ Run `revdepcheck::cloud_details(, "cities")` for more info * checking examples ... ERROR ``` - Running examples in ‘cities-Ex.R’ failed + Running examples in ‘circhelp-Ex.R’ failed The error most likely occurred in: - > ### Name: plot_dc - > ### Title: plot_dc - > ### Aliases: plot_dc + > ### Name: remove_cardinal_biases + > ### Title: Remove cardinal biases + > ### Aliases: remove_cardinal_biases > > ### ** Examples > - > total_data = 3 - ... - ▆ - 1. └─cities::plot_estimates(...) - 2. ├─base::print(p_estimands) - 3. └─ggplot2:::print.ggplot(p_estimands) - 4. ├─ggplot2::ggplot_gtable(data) - 5. └─ggplot2:::ggplot_gtable.ggplot_built(data) - 6. └─ggplot2::calc_element("plot.margin", theme) - 7. └─cli::cli_abort(...) - 8. └─rlang::abort(...) + > + > # Data in orientation domain from Pascucci et al. (2019, PLOS Bio), + > # https://doi.org/10.5281/zenodo.2544946 + > + > ex_data <- Pascucci_et_al_2019_data[observer == 4, ] + > remove_cardinal_biases(ex_data$err, ex_data$orientation, plots = "show") + Error in as.unit(value) : object is not coercible to a unit + Calls: remove_cardinal_biases ... assemble_guides -> guides_build -> [<- -> [<-.unit -> as.unit Execution halted ``` * checking running R code from vignettes ... ERROR ``` Errors in running code in vignettes: - when running code in ‘CITIES_demo.Rmd’ + when running code in ‘cardinal_biases.Rmd’ ... - | - |==================================================| 100% - > estimates_out = plot_estimates(data_out = data_out, - + total_data = total_data, timepoints = timepoints, reference_id = reference_id, - + IR_ .... [TRUNCATED] - Warning: Using shapes for an ordinal variable is not advised - - When sourcing ‘CITIES_demo.R’: - Error: Theme element `plot.margin` must have class . + + 90)) + .... [TRUNCATED] + + > ex_subj_data <- data[observer == 4, ] + + > res <- remove_cardinal_biases(ex_subj_data$err, ex_subj_data$orientation, + + plots = "show") + + When sourcing ‘cardinal_biases.R’: + Error: object is not coercible to a unit Execution halted - ‘CITIES_demo.Rmd’ using ‘UTF-8’... failed + ‘cardinal_biases.Rmd’ using ‘UTF-8’... failed ``` * checking re-building of vignette outputs ... NOTE ``` Error(s) in re-building vignettes: - --- re-building ‘CITIES_demo.Rmd’ using rmarkdown + --- re-building ‘cardinal_biases.Rmd’ using rmarkdown ``` -# CleaningValidation +# clifro
-* Version: 1.0 -* GitHub: https://github.com/ChandlerXiandeYang/CleaningValidation -* Source code: https://github.com/cran/CleaningValidation -* Date/Publication: 2024-05-17 09:10:21 UTC -* Number of recursive dependencies: 79 +* Version: 3.2-5 +* GitHub: https://github.com/ropensci/clifro +* Source code: https://github.com/cran/clifro +* Date/Publication: 2021-05-24 05:50:02 UTC +* Number of recursive dependencies: 84 -Run `revdepcheck::cloud_details(, "CleaningValidation")` for more info +Run `revdepcheck::cloud_details(, "clifro")` for more info
## Newly broken -* checking examples ... ERROR +* checking tests ... ERROR ``` - Running examples in ‘CleaningValidation-Ex.R’ failed - The error most likely occurred in: - - > ### Name: cv16_u_chart - > ### Title: Create a u-Chart for Poisson-distributed Data - > ### Aliases: cv16_u_chart - > - > ### ** Examples - > - > cv16_u_chart(data = Eq_Mic, residue_col = "Mic", cleaning_event_col = "CleaningEvent") + Running ‘spelling.R’ + Running ‘test-all.R’ + Running the tests in ‘tests/test-all.R’ failed. + Complete output: + > library(testthat) + > library(clifro) + > + > test_check("clifro") + [ FAIL 1 | WARN 1 | SKIP 4 | PASS 10 ] + ... - Backtrace: - ▆ - 1. ├─base (local) ``(x) - 2. └─ggplot2:::print.ggplot(x) - 3. ├─ggplot2::ggplot_gtable(data) - 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) - 5. └─ggplot2::calc_element("plot.margin", theme) - 6. └─cli::cli_abort(...) - 7. └─rlang::abort(...) - Execution halted + • On CRAN (4): 'test-cf_find_station.R:4:3', 'test-cf_last_query.R:4:3', + 'test-cf_query.R:4:3', 'test-cf_station.R:4:3' + + ══ Failed tests ════════════════════════════════════════════════════════════════ + ── Failure ('test-windrose.R:15:3'): windrose ────────────────────────────────── + tt$labels inherits from `'NULL'` not `'character'`. + + [ FAIL 1 | WARN 1 | SKIP 4 | PASS 10 ] + Error: Test failures + Execution halted ``` # clinDataReview
-* Version: 1.5.2 +* Version: 1.6.1 * GitHub: https://github.com/openanalytics/clinDataReview * Source code: https://github.com/cran/clinDataReview -* Date/Publication: 2024-05-17 16:30:05 UTC +* Date/Publication: 2024-06-18 09:10:05 UTC * Number of recursive dependencies: 130 Run `revdepcheck::cloud_details(, "clinDataReview")` for more info @@ -2410,17 +1915,17 @@ Run `revdepcheck::cloud_details(, "clinDataReview")` for more info > > test_check("clinDataReview") adding: report.html (deflated 63%) - adding: report_dependencies12051d006778/ (stored 0%) - adding: report_dependencies12051d006778/file12056baf983f.html (deflated 8%) + adding: report_dependencies13af6c90fb24/ (stored 0%) + adding: report_dependencies13af6c90fb24/file13af13ea2d3b.html (deflated 8%) ... Backtrace: ▆ - 1. └─clinDataReview::scatterplotClinData(...) at test_scatterplotClinData.R:851:3 + 1. └─clinDataReview::scatterplotClinData(...) at test_scatterplotClinData.R:1001:3 2. ├─plotly::ggplotly(p = gg, width = width, height = height, tooltip = if (!is.null(hoverVars)) "text") 3. └─plotly:::ggplotly.ggplot(...) 4. └─plotly::gg2list(...) - [ FAIL 25 | WARN 8 | SKIP 30 | PASS 450 ] + [ FAIL 31 | WARN 0 | SKIP 31 | PASS 466 ] Error: Test failures Execution halted ``` @@ -2454,7 +1959,7 @@ Run `revdepcheck::cloud_details(, "clinDataReview")` for more info * checking installed package size ... NOTE ``` - installed size is 5.7Mb + installed size is 5.8Mb sub-directories of 1Mb or more: doc 4.3Mb ``` @@ -2530,110 +2035,6 @@ Run `revdepcheck::cloud_details(, "clinUtils")` for more info doc 6.5Mb ``` -# ClustImpute - -
- -* Version: 0.2.4 -* GitHub: NA -* Source code: https://github.com/cran/ClustImpute -* Date/Publication: 2021-05-31 07:40:11 UTC -* Number of recursive dependencies: 121 - -Run `revdepcheck::cloud_details(, "ClustImpute")` for more info - -
- -## Newly broken - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘Example_on_simulated_data.Rmd’ - ... - > dat4plot$true_clust_fct <- factor(true_clust) - - > p_base <- ggplot(dat4plot, aes(x = x, y = y, color = true_clust_fct)) + - + geom_point() - - > ggExtra::ggMarginal(p_base, groupColour = TRUE, groupFill = TRUE) - - When sourcing ‘Example_on_simulated_data.R’: - Error: Theme element `plot.margin` must have class . - Execution halted - - ‘Example_on_simulated_data.Rmd’ using ‘UTF-8’... failed - ‘description_of_algorithm.Rnw’ using ‘UTF-8’... OK - ``` - -## In both - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘Example_on_simulated_data.Rmd’ using rmarkdown - - Quitting from lines 49-53 [unnamed-chunk-3] (Example_on_simulated_data.Rmd) - Error: processing vignette 'Example_on_simulated_data.Rmd' failed with diagnostics: - Theme element `plot.margin` must have class . - --- failed re-building ‘Example_on_simulated_data.Rmd’ - - --- re-building ‘description_of_algorithm.Rnw’ using Sweave - Error: processing vignette 'description_of_algorithm.Rnw' failed with diagnostics: - ... - l.6 \usepackage - {Sweave}^^M - ! ==> Fatal error occurred, no output PDF file produced! - --- failed re-building ‘description_of_algorithm.Rnw’ - - SUMMARY: processing the following files failed: - ‘Example_on_simulated_data.Rmd’ ‘description_of_algorithm.Rnw’ - - Error: Vignette re-building failed. - Execution halted - ``` - -# cogmapr - -
- -* Version: 0.9.3 -* GitHub: NA -* Source code: https://github.com/cran/cogmapr -* Date/Publication: 2022-01-04 15:40:07 UTC -* Number of recursive dependencies: 75 - -Run `revdepcheck::cloud_details(, "cogmapr")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘cogmapr-Ex.R’ failed - The error most likely occurred in: - - > ### Name: ggCMap - > ### Title: Plot a social cognitive map using ggplot2 - > ### Aliases: ggCMap - > - > ### ** Examples - > - > project_name <- "a_new_project" - ... - Backtrace: - ▆ - 1. ├─base (local) ``(x) - 2. └─ggplot2:::print.ggplot(x) - 3. ├─ggplot2::ggplot_gtable(data) - 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) - 5. └─ggplot2::calc_element("plot.margin", theme) - 6. └─cli::cli_abort(...) - 7. └─rlang::abort(...) - Execution halted - ``` - # CohortPlat
@@ -2712,17 +2113,17 @@ Run `revdepcheck::cloud_details(, "CohortPlat")` for more info Execution halted ``` -# CoMiRe +# CoreMicrobiomeR
-* Version: 0.8 +* Version: 0.1.0 * GitHub: NA -* Source code: https://github.com/cran/CoMiRe -* Date/Publication: 2023-08-23 09:10:06 UTC -* Number of recursive dependencies: 35 +* Source code: https://github.com/cran/CoreMicrobiomeR +* Date/Publication: 2024-04-03 20:03:02 UTC +* Number of recursive dependencies: 91 -Run `revdepcheck::cloud_details(, "CoMiRe")` for more info +Run `revdepcheck::cloud_details(, "CoreMicrobiomeR")` for more info
@@ -2730,242 +2131,38 @@ Run `revdepcheck::cloud_details(, "CoMiRe")` for more info * checking examples ... ERROR ``` - Running examples in ‘CoMiRe-Ex.R’ failed + Running examples in ‘CoreMicrobiomeR-Ex.R’ failed The error most likely occurred in: - > ### Name: BMD - > ### Title: Benchmark dose - > ### Aliases: BMD + > ### Name: group_bar_plots + > ### Title: Grouped Bar Plots Based on Sample Size + > ### Aliases: group_bar_plots > > ### ** Examples > - > { + > #To run input data ... - Backtrace: - ▆ - 1. ├─base (local) ``(x) - 2. └─ggplot2:::print.ggplot(x) - 3. ├─ggplot2::ggplot_gtable(data) - 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) - 5. └─ggplot2::calc_element("plot.margin", theme) - 6. └─cli::cli_abort(...) - 7. └─rlang::abort(...) + + top_percentage = 10 # Adjust the percentage as needed for core/non-core OTUs + + ) + Warning encountered during diversity analysis:you have empty rows: their dissimilarities may be + meaningless in method “bray” + > #To run grouped bar plot function + > plot_group_bar <- group_bar_plots(core_1$final_otu_table_bef_filter, + + core_1$final_otu_aft_filter, 10) + Error in pm[[2]] : subscript out of bounds + Calls: group_bar_plots -> -> ggplotly.ggplot -> gg2list Execution halted ``` -# CommKern +# correlationfunnel
-* Version: 1.0.1 -* GitHub: https://github.com/aljensen89/CommKern -* Source code: https://github.com/cran/CommKern -* Date/Publication: 2022-09-23 10:20:06 UTC -* Number of recursive dependencies: 58 - -Run `revdepcheck::cloud_details(, "CommKern")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘CommKern-Ex.R’ failed - The error most likely occurred in: - - > ### Name: hms - > ### Title: Hierarchical multimodal spinglass algorithm - > ### Aliases: hms - > - > ### ** Examples - > - > - ... - ▆ - 1. ├─CommKern::community_plot(hms_object) - 2. └─CommKern:::community_plot.spinglass_hms(hms_object) - 3. └─ggplot2::ggplotGrob(comm_plot) - 4. ├─ggplot2::ggplot_gtable(ggplot_build(x)) - 5. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) - 6. └─ggplot2::calc_element("plot.margin", theme) - 7. └─cli::cli_abort(...) - 8. └─rlang::abort(...) - Execution halted - ``` - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘CommKern.Rmd’ - ... - .. .. ..$ : chr [1:80] "1" "2" "3" "4" ... - ..- attr(*, "class")= chr "spinglass_net" - $ best_hamiltonian: num -286 - - attr(*, "class")= chr "spinglass_hms" - - > community_plot(hms_object) - - When sourcing ‘CommKern.R’: - Error: Theme element `plot.margin` must have class . - Execution halted - - ‘CommKern.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘CommKern.Rmd’ using rmarkdown - ``` - -## In both - -* checking installed package size ... NOTE - ``` - installed size is 7.2Mb - sub-directories of 1Mb or more: - data 6.5Mb - ``` - -# conText - -
- -* Version: 1.4.3 -* GitHub: https://github.com/prodriguezsosa/ConText -* Source code: https://github.com/cran/conText -* Date/Publication: 2023-02-09 21:10:02 UTC -* Number of recursive dependencies: 78 - -Run `revdepcheck::cloud_details(, "conText")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘conText-Ex.R’ failed - The error most likely occurred in: - - > ### Name: plot_nns_ratio - > ### Title: Plot output of 'get_nns_ratio()' - > ### Aliases: plot_nns_ratio - > ### Keywords: plot_nns_ratio - > - > ### ** Examples - > - ... - Backtrace: - ▆ - 1. ├─base (local) ``(x) - 2. └─ggplot2:::print.ggplot(x) - 3. ├─ggplot2::ggplot_gtable(data) - 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) - 5. └─ggplot2::calc_element("plot.margin", theme) - 6. └─cli::cli_abort(...) - 7. └─rlang::abort(...) - Execution halted - ``` - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘quickstart.Rmd’ - ... - 4 illegally 1.12 0.0290 1.08 1.18 0 shared - 5 laws 1.09 0.0351 1.03 1.15 0 R - 6 legal 1.03 0.0341 0.973 1.08 0.39 R - - > plot_nns_ratio(x = immig_nns_ratio, alpha = 0.01, - + horizontal = TRUE) - - When sourcing ‘quickstart.R’: - Error: Theme element `plot.margin` must have class . - Execution halted - - ‘quickstart.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - ... - --- re-building ‘quickstart.Rmd’ using rmarkdown - - Quitting from lines 342-343 [unnamed-chunk-21] (quickstart.Rmd) - Error: processing vignette 'quickstart.Rmd' failed with diagnostics: - Theme element `plot.margin` must have class . - --- failed re-building ‘quickstart.Rmd’ - - SUMMARY: processing the following file failed: - ‘quickstart.Rmd’ - - Error: Vignette re-building failed. - Execution halted - ``` - -## In both - -* checking installed package size ... NOTE - ``` - installed size is 5.4Mb - sub-directories of 1Mb or more: - data 3.5Mb - doc 1.5Mb - ``` - -# CoreMicrobiomeR - -
- -* Version: 0.1.0 -* GitHub: NA -* Source code: https://github.com/cran/CoreMicrobiomeR -* Date/Publication: 2024-04-03 20:03:02 UTC -* Number of recursive dependencies: 91 - -Run `revdepcheck::cloud_details(, "CoreMicrobiomeR")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘CoreMicrobiomeR-Ex.R’ failed - The error most likely occurred in: - - > ### Name: group_bar_plots - > ### Title: Grouped Bar Plots Based on Sample Size - > ### Aliases: group_bar_plots - > - > ### ** Examples - > - > #To run input data - ... - + top_percentage = 10 # Adjust the percentage as needed for core/non-core OTUs - + ) - Warning encountered during diversity analysis:you have empty rows: their dissimilarities may be - meaningless in method “bray” - > #To run grouped bar plot function - > plot_group_bar <- group_bar_plots(core_1$final_otu_table_bef_filter, - + core_1$final_otu_aft_filter, 10) - Error in pm[[2]] : subscript out of bounds - Calls: group_bar_plots -> -> ggplotly.ggplot -> gg2list - Execution halted - ``` - -# correlationfunnel - -
- -* Version: 0.2.0 -* GitHub: https://github.com/business-science/correlationfunnel -* Source code: https://github.com/cran/correlationfunnel -* Date/Publication: 2020-06-09 04:40:03 UTC -* Number of recursive dependencies: 117 +* Version: 0.2.0 +* GitHub: https://github.com/business-science/correlationfunnel +* Source code: https://github.com/cran/correlationfunnel +* Date/Publication: 2020-06-09 04:40:03 UTC +* Number of recursive dependencies: 116 Run `revdepcheck::cloud_details(, "correlationfunnel")` for more info @@ -3093,6 +2290,44 @@ Run `revdepcheck::cloud_details(, "corrViz")` for more info doc 6.7Mb ``` +# countfitteR + +
+ +* Version: 1.4 +* GitHub: https://github.com/BioGenies/countfitteR +* Source code: https://github.com/cran/countfitteR +* Date/Publication: 2020-09-30 21:30:02 UTC +* Number of recursive dependencies: 93 + +Run `revdepcheck::cloud_details(, "countfitteR")` for more info + +
+ +## Newly broken + +* checking tests ... ERROR + ``` + Running ‘spelling.R’ + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(countfitteR) + > + > test_check("countfitteR") + [ FAIL 1 | WARN 6 | SKIP 0 | PASS 34 ] + + ══ Failed tests ════════════════════════════════════════════════════════════════ + ── Failure ('testing.R:45:3'): plot_fit ──────────────────────────────────────── + p$labels[[1]] not equal to "x". + target is NULL, current is character + + [ FAIL 1 | WARN 6 | SKIP 0 | PASS 34 ] + Error: Test failures + Execution halted + ``` + # covidcast
@@ -3137,25 +2372,23 @@ Run `revdepcheck::cloud_details(, "covidcast")` for more info * checking running R code from vignettes ... ERROR ``` Errors in running code in vignettes: - when running code in ‘multi-signals.Rmd’ + when running code in ‘plotting-signals.Rmd’ ... + > knitr::opts_chunk$set(fig.width = 6, fig.height = 4) - > signals <- covidcast_signals(data_source = "jhu-csse", - + signal = c("confirmed_7dav_incidence_prop", "deaths_7dav_incidence_prop"), - + star .... [TRUNCATED] + > plot(dv) - When sourcing ‘multi-signals.R’: - Error: Rate limit exceeded when fetching data from API anonymously. See the "API keys" section of the `covidcast_signal()` documentation for information on registering for an API key. - ... - Error: Rate limit exceeded when fetching data from API anonymously. See the "API keys" section of the `covidcast_signal()` documentation for information on registering for an API key. - ℹ Message from server: - ℹ Rate limit exceeded for anonymous queries. To remove this limit, register a free API key at https://api.delphi.cmu.edu/epidata/admin/registration_form + When sourcing ‘plotting-signals.R’: + Error: Problem while setting up geom aesthetics. + ℹ Error occurred in the 6th layer. + Caused by error in `$<-.data.frame`: + ! replacement has 1 row, data has 0 Execution halted ‘correlation-utils.Rmd’ using ‘UTF-8’... OK ‘covidcast.Rmd’ using ‘UTF-8’... OK ‘external-data.Rmd’ using ‘UTF-8’... OK - ‘multi-signals.Rmd’ using ‘UTF-8’... failed + ‘multi-signals.Rmd’ using ‘UTF-8’... OK ‘plotting-signals.Rmd’ using ‘UTF-8’... failed ``` @@ -3166,15 +2399,6 @@ Run `revdepcheck::cloud_details(, "covidcast")` for more info --- finished re-building ‘correlation-utils.Rmd’ --- re-building ‘covidcast.Rmd’ using rmarkdown - - Quitting from lines 38-45 [unnamed-chunk-1] (covidcast.Rmd) - Error: processing vignette 'covidcast.Rmd' failed with diagnostics: - Rate limit exceeded when fetching data from API anonymously. See the "API keys" section of the `covidcast_signal()` documentation for information on registering for an API key. - ℹ Message from server: - ℹ Rate limit exceeded for anonymous queries. To remove this limit, register a free API key at https://api.delphi.cmu.edu/epidata/admin/registration_form - --- failed re-building ‘covidcast.Rmd’ - - --- re-building ‘external-data.Rmd’ using rmarkdown ``` ## In both @@ -3184,60 +2408,6 @@ Run `revdepcheck::cloud_details(, "covidcast")` for more info Note: found 20 marked UTF-8 strings ``` -# cricketdata - -
- -* Version: 0.2.3 -* GitHub: https://github.com/robjhyndman/cricketdata -* Source code: https://github.com/cran/cricketdata -* Date/Publication: 2023-08-29 10:30:09 UTC -* Number of recursive dependencies: 104 - -Run `revdepcheck::cloud_details(, "cricketdata")` for more info - -
- -## Newly broken - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘cricinfo.Rmd’ using rmarkdown - ``` - -## In both - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘cricinfo.Rmd’ - ... - - > library(ggplot2) - - > wt20 <- readRDS("../inst/extdata/wt20.rds") - Warning in gzfile(file, "rb") : - cannot open compressed file '../inst/extdata/wt20.rds', probable reason 'No such file or directory' - - ... - Warning in gzfile(file, "rb") : - cannot open compressed file '../inst/extdata/wbbl_bbb.rds', probable reason 'No such file or directory' - - When sourcing ‘cricsheet.R’: - Error: cannot open the connection - Execution halted - - ‘cricinfo.Rmd’ using ‘UTF-8’... failed - ‘cricketdata_R_pkg.Rmd’ using ‘UTF-8’... failed - ‘cricsheet.Rmd’ using ‘UTF-8’... failed - ``` - -* checking data for non-ASCII characters ... NOTE - ``` - Note: found 37 marked UTF-8 strings - ``` - # crosshap
@@ -3279,17 +2449,17 @@ Run `revdepcheck::cloud_details(, "crosshap")` for more info Execution halted ``` -# crplyr +# ctrialsgov
-* Version: 0.4.0 -* GitHub: https://github.com/Crunch-io/crplyr -* Source code: https://github.com/cran/crplyr -* Date/Publication: 2023-03-21 21:50:02 UTC -* Number of recursive dependencies: 88 +* Version: 0.2.5 +* GitHub: NA +* Source code: https://github.com/cran/ctrialsgov +* Date/Publication: 2021-10-18 16:00:02 UTC +* Number of recursive dependencies: 100 -Run `revdepcheck::cloud_details(, "crplyr")` for more info +Run `revdepcheck::cloud_details(, "ctrialsgov")` for more info
@@ -3297,122 +2467,44 @@ Run `revdepcheck::cloud_details(, "crplyr")` for more info * checking tests ... ERROR ``` - Running ‘spelling.R’ Running ‘testthat.R’ Running the tests in ‘tests/testthat.R’ failed. Complete output: - > library(httptest) - Loading required package: testthat - > test_check("crplyr") - Loading required package: crplyr - Loading required package: crunch - + > library(testthat) + > library(ctrialsgov) + > + > test_check("ctrialsgov") + [NCT04553939] ible Local Advanved |Bladder| Cancer + [NCT03517995] of Sulforaphane in |Bladder| Cancer Chemoprevent + [NCT04210479] Comparison of |Bladder| Filling vs. Non-Fil ... - 7. └─ggplot2:::print.ggplot(p) - 8. ├─ggplot2::ggplot_gtable(data) - 9. └─ggplot2:::ggplot_gtable.ggplot_built(data) - 10. └─ggplot2::calc_element("plot.margin", theme) - 11. └─cli::cli_abort(...) - 12. └─rlang::abort(...) + ▆ + 1. ├─ctrialsgov::ctgov_to_plotly(p) at test-plot.R:12:3 + 2. └─ctrialsgov:::ctgov_to_plotly.ctgov_bar_plot(p) + 3. ├─plotly::ggplotly(p, tooltip = "text") + 4. └─plotly:::ggplotly.ggplot(p, tooltip = "text") + 5. └─plotly::gg2list(...) - [ FAIL 1 | WARN 0 | SKIP 0 | PASS 172 ] + [ FAIL 1 | WARN 6 | SKIP 0 | PASS 43 ] Error: Test failures Execution halted ``` -* checking running R code from vignettes ... ERROR +## In both + +* checking data for non-ASCII characters ... NOTE ``` - Errors in running code in vignettes: - when running code in ‘plotting.Rmd’ - ... - equals, is_less_than, not - - - > ds <- loadDataset("https://app.crunch.io/api/datasets/5c9336/") - - > autoplot(ds$CompanySize) - - When sourcing ‘plotting.R’: - Error: Theme element `plot.margin` must have class . - Execution halted - - ‘plotting.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - ... - --- re-building ‘plotting.Rmd’ using rmarkdown - - Quitting from lines 35-36 [basic-card-plots] (plotting.Rmd) - Error: processing vignette 'plotting.Rmd' failed with diagnostics: - Theme element `plot.margin` must have class . - --- failed re-building ‘plotting.Rmd’ - - SUMMARY: processing the following file failed: - ‘plotting.Rmd’ - - Error: Vignette re-building failed. - Execution halted - ``` - -# ctrialsgov - -
- -* Version: 0.2.5 -* GitHub: NA -* Source code: https://github.com/cran/ctrialsgov -* Date/Publication: 2021-10-18 16:00:02 UTC -* Number of recursive dependencies: 100 - -Run `revdepcheck::cloud_details(, "ctrialsgov")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(ctrialsgov) - > - > test_check("ctrialsgov") - [NCT04553939] ible Local Advanved |Bladder| Cancer - [NCT03517995] of Sulforaphane in |Bladder| Cancer Chemoprevent - [NCT04210479] Comparison of |Bladder| Filling vs. Non-Fil - ... - ▆ - 1. ├─ctrialsgov::ctgov_to_plotly(p) at test-plot.R:12:3 - 2. └─ctrialsgov:::ctgov_to_plotly.ctgov_bar_plot(p) - 3. ├─plotly::ggplotly(p, tooltip = "text") - 4. └─plotly:::ggplotly.ggplot(p, tooltip = "text") - 5. └─plotly::gg2list(...) - - [ FAIL 1 | WARN 6 | SKIP 0 | PASS 43 ] - Error: Test failures - Execution halted - ``` - -## In both - -* checking data for non-ASCII characters ... NOTE - ``` - Note: found 1350 marked UTF-8 strings + Note: found 1350 marked UTF-8 strings ``` # cubble
-* Version: 0.3.0 +* Version: 0.3.1 * GitHub: https://github.com/huizezhang-sherry/cubble * Source code: https://github.com/cran/cubble -* Date/Publication: 2023-06-30 03:40:02 UTC +* Date/Publication: 2024-07-02 17:20:03 UTC * Number of recursive dependencies: 144 Run `revdepcheck::cloud_details(, "cubble")` for more info @@ -3426,15 +2518,14 @@ Run `revdepcheck::cloud_details(, "cubble")` for more info Errors in running code in vignettes: when running code in ‘cb5match.Rmd’ ... - > p2 <- res_tm_long %>% ggplot(aes(x = date, y = matched, + > p2 <- ggplot(res_tm_long, aes(x = date, y = matched, + group = type, color = type)) + geom_line() + facet_wrap(vars(group)) + - + scale_c .... [TRUNCATED] + + scale_colo .... [TRUNCATED] > (p1 | p2) + patchwork::plot_layout(guides = "collect") + + plot_annotation(tag_levels = "a") & theme(legend.position = "bottom") ... - When sourcing ‘cb6interactive.R’: Error: subscript out of bounds Execution halted @@ -3444,6 +2535,7 @@ Run `revdepcheck::cloud_details(, "cubble")` for more info ‘cb4glyph.Rmd’ using ‘UTF-8’... OK ‘cb5match.Rmd’ using ‘UTF-8’... failed ‘cb6interactive.Rmd’ using ‘UTF-8’... failed + ‘cb7misc.Rmd’ using ‘UTF-8’... OK ``` * checking re-building of vignette outputs ... NOTE @@ -3468,20 +2560,20 @@ Run `revdepcheck::cloud_details(, "cubble")` for more info installed size is 5.6Mb sub-directories of 1Mb or more: data 3.0Mb - doc 1.3Mb + doc 1.4Mb ``` -# dabestr +# deeptime
-* Version: 2023.9.12 -* GitHub: https://github.com/ACCLAB/dabestr -* Source code: https://github.com/cran/dabestr -* Date/Publication: 2023-10-13 11:50:06 UTC -* Number of recursive dependencies: 85 +* Version: 1.1.1 +* GitHub: https://github.com/willgearty/deeptime +* Source code: https://github.com/cran/deeptime +* Date/Publication: 2024-03-08 17:10:10 UTC +* Number of recursive dependencies: 182 -Run `revdepcheck::cloud_details(, "dabestr")` for more info +Run `revdepcheck::cloud_details(, "deeptime")` for more info
@@ -3489,197 +2581,188 @@ Run `revdepcheck::cloud_details(, "dabestr")` for more info * checking examples ... ERROR ``` - Running examples in ‘dabestr-Ex.R’ failed + Running examples in ‘deeptime-Ex.R’ failed The error most likely occurred in: - > ### Name: dabest_plot - > ### Title: Producing an estimation plot - > ### Aliases: dabest_plot + > ### Name: gggeo_scale_old + > ### Title: Add a geologic scale on top of ggplots + > ### Aliases: gggeo_scale_old + > ### Keywords: internal > > ### ** Examples > - > # Loading of the dataset ... - 7. └─cowplot:::as_gtable.default(x) - 8. ├─cowplot::as_grob(plot) - 9. └─cowplot:::as_grob.ggplot(plot) - 10. └─ggplot2::ggplotGrob(plot) - 11. ├─ggplot2::ggplot_gtable(ggplot_build(x)) - 12. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) - 13. └─ggplot2::calc_element("plot.margin", theme) - 14. └─cli::cli_abort(...) - 15. └─rlang::abort(...) + + geom_point(aes(y = runif(1000, .5, 8), x = runif(1000, 0, 1000))) + + + scale_x_reverse() + + + coord_cartesian(xlim = c(0, 1000), ylim = c(0, 8), expand = FALSE) + + + theme_classic() + > gggeo_scale_old(p) + Warning: `gggeo_scale_old()` was deprecated in deeptime 1.0.0. + ℹ Please use `coord_geo()` instead. + Error in names(labels) <- `*vtmp*` : attempt to set an attribute on NULL + Calls: gggeo_scale_old ... ggplot_add -> ggplot_add.new_aes -> bump_aes_labels Execution halted ``` -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > # This file is part of the standard setup for testthat. - > # It is recommended that you do not modify it. - > # - > # Where should you do additional test configuration? - > # Learn more about the roles of various files in: - > # * https://r-pkgs.org/tests.html - > # * https://testthat.r-lib.org/reference/test_package.html#special-files - ... - • 001_plotter/proportion-sequential-mean-diff.svg - • 001_plotter/proportion-unpaired-mean-diff-float-false.svg - • 001_plotter/proportion-unpaired-mean-diff-float-true.svg - • 001_plotter/proportion-unpaired-multigroup-mean-diff.svg - • 001_plotter/two-groups-unpaired-mean-diff-colour-float-false.svg - • 001_plotter/two-groups-unpaired-mean-diff-colour-float-true.svg - • 001_plotter/two-groups-unpaired-mean-diff-float-false.svg - • 001_plotter/two-groups-unpaired-mean-diff-float-true.svg - Error: Test failures - Execution halted - ``` +# distributional -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘plot_aesthetics.Rmd’ - ... - + x = Group, y = Success, idx = list(c("Control 1", "Test 1", - + "Test 2", "Te ..." ... [TRUNCATED] - - > dabest_plot(dabest_twogroup_obj.mean_diff, float_contrast = TRUE, - + swarm_x_text = 30, swarm_y_text = 1, contrast_x_text = 30, - + contrast_ .... [TRUNCATED] - - ... - Error: Theme element `plot.margin` must have class . - Execution halted - - ‘datasets.Rmd’ using ‘UTF-8’... OK - ‘plot_aesthetics.Rmd’ using ‘UTF-8’... failed - ‘tutorial_basics.Rmd’ using ‘UTF-8’... failed - ‘tutorial_deltadelta.Rmd’ using ‘UTF-8’... failed - ‘tutorial_minimeta.Rmd’ using ‘UTF-8’... failed - ‘tutorial_proportion_plots.Rmd’ using ‘UTF-8’... failed - ‘tutorial_repeated_measures.Rmd’ using ‘UTF-8’... failed - ``` +
-* checking re-building of vignette outputs ... NOTE +* Version: 0.4.0 +* GitHub: https://github.com/mitchelloharawild/distributional +* Source code: https://github.com/cran/distributional +* Date/Publication: 2024-02-07 13:30:02 UTC +* Number of recursive dependencies: 64 + +Run `revdepcheck::cloud_details(, "distributional")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR ``` - Error(s) in re-building vignettes: - --- re-building ‘datasets.Rmd’ using rmarkdown - --- finished re-building ‘datasets.Rmd’ - - --- re-building ‘plot_aesthetics.Rmd’ using rmarkdown + Running examples in ‘distributional-Ex.R’ failed + The error most likely occurred in: - Quitting from lines 81-89 [unnamed-chunk-3] (plot_aesthetics.Rmd) - Error: processing vignette 'plot_aesthetics.Rmd' failed with diagnostics: - Theme element `plot.margin` must have class . - --- failed re-building ‘plot_aesthetics.Rmd’ + > ### Name: dist_truncated + > ### Title: Truncate a distribution + > ### Aliases: dist_truncated + > + > ### ** Examples + > + > dist <- dist_truncated(dist_normal(2,1), lower = 0) ... - Theme element `plot.margin` must have class . - --- failed re-building ‘tutorial_repeated_measures.Rmd’ - - SUMMARY: processing the following files failed: - ‘plot_aesthetics.Rmd’ ‘tutorial_basics.Rmd’ ‘tutorial_deltadelta.Rmd’ - ‘tutorial_minimeta.Rmd’ ‘tutorial_proportion_plots.Rmd’ - ‘tutorial_repeated_measures.Rmd’ - - Error: Vignette re-building failed. + 12. │ └─ggplot2 (local) f(l = layers[[i]], d = data[[i]]) + 13. │ └─l$compute_geom_2(d, theme = plot$theme) + 14. │ └─ggplot2 (local) compute_geom_2(..., self = self) + 15. │ └─self$geom$use_defaults(...) + 16. └─base::.handleSimpleError(...) + 17. └─rlang (local) h(simpleError(msg, call)) + 18. └─handlers[[1L]](cnd) + 19. └─cli::cli_abort(...) + 20. └─rlang::abort(...) Execution halted ``` -# DAISIEprep +# dittoViz
-* Version: 0.4.0 -* GitHub: https://github.com/joshwlambert/DAISIEprep -* Source code: https://github.com/cran/DAISIEprep -* Date/Publication: 2024-04-02 11:30:06 UTC -* Number of recursive dependencies: 149 +* Version: 1.0.1 +* GitHub: https://github.com/dtm2451/dittoViz +* Source code: https://github.com/cran/dittoViz +* Date/Publication: 2024-02-02 00:00:12 UTC +* Number of recursive dependencies: 99 -Run `revdepcheck::cloud_details(, "DAISIEprep")` for more info +Run `revdepcheck::cloud_details(, "dittoViz")` for more info
## Newly broken +* checking examples ... ERROR + ``` + Running examples in ‘dittoViz-Ex.R’ failed + The error most likely occurred in: + + > ### Name: barPlot + > ### Title: Outputs a stacked bar plot to show the percent composition of + > ### samples, groups, clusters, or other groupings + > ### Aliases: barPlot + > + > ### ** Examples + > + ... + 15 3 D 12 32 0.3750000 + 16 4 D 8 32 0.2500000 + > # through hovering the cursor over the relevant parts of the plot + > if (requireNamespace("plotly", quietly = TRUE)) { + + barPlot(example_df, "clustering", group.by = "groups", + + do.hover = TRUE) + + } + Error in pm[[2]] : subscript out of bounds + Calls: barPlot -> -> ggplotly.ggplot -> gg2list + Execution halted + ``` + * checking tests ... ERROR ``` Running ‘testthat.R’ Running the tests in ‘tests/testthat.R’ failed. Complete output: > library(testthat) - > library(DAISIEprep) - > - > test_check("DAISIEprep") - [ FAIL 2 | WARN 2 | SKIP 14 | PASS 2213 ] + > library(dittoViz) + Loading required package: ggplot2 + > test_check("dittoViz") + [ FAIL 12 | WARN 12 | SKIP 0 | PASS 307 ] - ══ Skipped tests (14) ══════════════════════════════════════════════════════════ + ══ Failed tests ════════════════════════════════════════════════════════════════ ... - 23. └─ggplot2::ggplotGrob(plot) - 24. ├─ggplot2::ggplot_gtable(ggplot_build(x)) - 25. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) - 26. └─ggplot2::calc_element("plot.margin", theme) - 27. └─cli::cli_abort(...) - 28. └─rlang::abort(...) + 2. └─dittoViz::freqPlot(...) + 3. └─dittoViz::yPlot(...) + 4. └─dittoViz:::.warn_or_apply_plotly(p, plots) + 5. ├─plotly::ggplotly(p, tooltip = "text") + 6. └─plotly:::ggplotly.ggplot(p, tooltip = "text") + 7. └─plotly::gg2list(...) - [ FAIL 2 | WARN 2 | SKIP 14 | PASS 2213 ] + [ FAIL 12 | WARN 12 | SKIP 0 | PASS 307 ] Error: Test failures Execution halted ``` -# dataresqc +# EGM
-* Version: 1.1.1 -* GitHub: NA -* Source code: https://github.com/cran/dataresqc -* Date/Publication: 2023-04-02 22:00:02 UTC -* Number of recursive dependencies: 49 +* Version: 0.1.0 +* GitHub: https://github.com/shah-in-boots/EGM +* Source code: https://github.com/cran/EGM +* Date/Publication: 2024-05-23 16:10:05 UTC +* Number of recursive dependencies: 77 -Run `revdepcheck::cloud_details(, "dataresqc")` for more info +Run `revdepcheck::cloud_details(, "EGM")` for more info
## Newly broken -* checking examples ... ERROR +* checking tests ... ERROR ``` - Running examples in ‘dataresqc-Ex.R’ failed - The error most likely occurred in: - - > ### Name: plot_decimals - > ### Title: Plot decimals - > ### Aliases: plot_decimals - > - > ### ** Examples - > - > plot_decimals(Rosario$Tx, outfile = paste0(tempdir(),"/test.pdf")) + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(EGM) + Loading required package: vctrs + Loading required package: data.table + > EGM::set_wfdb_path("/usr/local/bin") + > + > test_check("EGM") ... - 1. └─dataresqc::plot_decimals(...) - 2. └─dataresqc:::multiplot(plotlist = plots) - 3. ├─base::print(plots[[1]]) - 4. └─ggplot2:::print.ggplot(plots[[1]]) - 5. ├─ggplot2::ggplot_gtable(data) - 6. └─ggplot2:::ggplot_gtable.ggplot_built(data) - 7. └─ggplot2::calc_element("plot.margin", theme) - 8. └─cli::cli_abort(...) - 9. └─rlang::abort(...) - Execution halted + ══ Failed tests ════════════════════════════════════════════════════════════════ + ── Failure ('test-ggm.R:63:2'): theming works ────────────────────────────────── + g$labels$x (`actual`) not equal to "sample" (`expected`). + + `actual` is NULL + `expected` is a character vector ('sample') + + [ FAIL 1 | WARN 0 | SKIP 19 | PASS 43 ] + Error: Test failures + Execution halted ``` -# ddtlcm +# entropart
-* Version: 0.2.1 -* GitHub: https://github.com/limengbinggz/ddtlcm -* Source code: https://github.com/cran/ddtlcm -* Date/Publication: 2024-04-04 02:32:57 UTC -* Number of recursive dependencies: 150 +* Version: 1.6-13 +* GitHub: https://github.com/EricMarcon/entropart +* Source code: https://github.com/cran/entropart +* Date/Publication: 2023-09-26 14:40:02 UTC +* Number of recursive dependencies: 125 -Run `revdepcheck::cloud_details(, "ddtlcm")` for more info +Run `revdepcheck::cloud_details(, "entropart")` for more info
@@ -3687,111 +2770,132 @@ Run `revdepcheck::cloud_details(, "ddtlcm")` for more info * checking examples ... ERROR ``` - Running examples in ‘ddtlcm-Ex.R’ failed + Running examples in ‘entropart-Ex.R’ failed The error most likely occurred in: - > ### Name: plot.summary.ddt_lcm - > ### Title: Plot the MAP tree and class profiles of summarized DDT-LCM - > ### results - > ### Aliases: plot.summary.ddt_lcm + > ### Name: Accumulation + > ### Title: Diversity accumulation. + > ### Aliases: DivAC EntAC as.AccumCurve is.AccumCurve autoplot.AccumCurve + > ### plot.AccumCurve > > ### ** Examples > ... - 15. └─cowplot:::as_gtable.default(x) - 16. ├─cowplot::as_grob(plot) - 17. └─cowplot:::as_grob.ggplot(plot) - 18. └─ggplot2::ggplotGrob(plot) - 19. ├─ggplot2::ggplot_gtable(ggplot_build(x)) - 20. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) - 21. └─ggplot2::calc_element("plot.margin", theme) - 22. └─cli::cli_abort(...) - 23. └─rlang::abort(...) + 11. │ └─base::withCallingHandlers(...) + 12. └─ggplot2 (local) f(l = layers[[i]], d = data[[i]]) + 13. └─l$compute_geom_2(d, theme = plot$theme) + 14. └─ggplot2 (local) compute_geom_2(..., self = self) + 15. └─self$geom$use_defaults(...) + 16. └─ggplot2 (local) use_defaults(..., self = self) + 17. └─ggplot2:::check_aesthetics(new_params, nrow(data)) + 18. └─cli::cli_abort(...) + 19. └─rlang::abort(...) Execution halted ``` -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > # This file is part of the standard setup for testthat. - > # It is recommended that you do not modify it. - > # - > # Where should you do additional test configuration? - > # Learn more about the roles of various files in: - > # * https://r-pkgs.org/tests.html - > # * https://testthat.r-lib.org/reference/test_package.html#special-files - ... - label_size = .lab$size, label_fontfamily = .lab$family, label_fontface = .lab$face, - label_colour = .lab$color, label_x = .lab$label.x, label_y = .lab$label.y, - hjust = .lab$hjust, vjust = .lab$vjust, align = align, rel_widths = widths, - rel_heights = heights, legend = legend, common.legend.grob = legend.grob)`: i In index: 1. - Caused by error in `ggplot_gtable()`: - ! Theme element `plot.margin` must have class . - - [ FAIL 1 | WARN 30 | SKIP 0 | PASS 62 ] - Error: Test failures - Execution halted - ``` - * checking running R code from vignettes ... ERROR ``` Errors in running code in vignettes: - when running code in ‘ddtlcm-demo.Rmd’ + when running code in ‘entropart.Rmd’ ... - > response_prob <- sim_data$response_prob - > tree_with_parameter <- sim_data$tree_with_parameter - - > plot_tree_with_heatmap(tree_with_parameter, response_prob, - + item_membership_list) + > autoplot(Abd18, Distribution = "lnorm") - When sourcing ‘ddtlcm-demo.R’: - Error: Theme element `plot.margin` must have class . + When sourcing ‘entropart.R’: + Error: Problem while setting up geom aesthetics. + ℹ Error occurred in the 1st layer. + Caused by error in `check_aesthetics()`: + ! Aesthetics must be either length 1 or the same as the data (149). + ✖ Fix the following mappings: `shape`, `colour`, and `size`. Execution halted - ‘ddtlcm-demo.Rmd’ using ‘UTF-8’... failed + ‘entropart.Rmd’ using ‘UTF-8’... failed ``` * checking re-building of vignette outputs ... NOTE ``` Error(s) in re-building vignettes: ... - --- re-building ‘ddtlcm-demo.Rmd’ using rmarkdown - - Quitting from lines 134-139 [unnamed-chunk-5] (ddtlcm-demo.Rmd) - Error: processing vignette 'ddtlcm-demo.Rmd' failed with diagnostics: - Theme element `plot.margin` must have class . - --- failed re-building ‘ddtlcm-demo.Rmd’ - - SUMMARY: processing the following file failed: - ‘ddtlcm-demo.Rmd’ + --- re-building ‘entropart.Rmd’ using rmarkdown - Error: Vignette re-building failed. - Execution halted - ``` + Quitting from lines 53-55 [PlotN18] (entropart.Rmd) + Error: processing vignette 'entropart.Rmd' failed with diagnostics: + Problem while setting up geom aesthetics. + ℹ Error occurred in the 1st layer. + Caused by error in `check_aesthetics()`: + ! Aesthetics must be either length 1 or the same as the data (149). + ✖ Fix the following mappings: `shape`, `colour`, and `size`. + --- failed re-building ‘entropart.Rmd’ + + SUMMARY: processing the following file failed: + ‘entropart.Rmd’ + + Error: Vignette re-building failed. + Execution halted + ``` + +# epiCleanr + +
+ +* Version: 0.2.0 +* GitHub: https://github.com/truenomad/epiCleanr +* Source code: https://github.com/cran/epiCleanr +* Date/Publication: 2023-09-28 12:20:05 UTC +* Number of recursive dependencies: 130 + +Run `revdepcheck::cloud_details(, "epiCleanr")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘epiCleanr-Ex.R’ failed + The error most likely occurred in: + + > ### Name: handle_outliers + > ### Title: Detect and Handle Outliers in Dataset + > ### Aliases: handle_outliers + > + > ### ** Examples + > + > + ... + 12. │ └─ggplot2 (local) f(l = layers[[i]], d = data[[i]]) + 13. │ └─l$compute_geom_2(d, theme = plot$theme) + 14. │ └─ggplot2 (local) compute_geom_2(..., self = self) + 15. │ └─self$geom$use_defaults(...) + 16. └─base::.handleSimpleError(...) + 17. └─rlang (local) h(simpleError(msg, call)) + 18. └─handlers[[1L]](cnd) + 19. └─cli::cli_abort(...) + 20. └─rlang::abort(...) + Execution halted + ``` ## In both * checking installed package size ... NOTE ``` - installed size is 9.3Mb + installed size is 5.6Mb sub-directories of 1Mb or more: - data 8.0Mb + doc 2.9Mb + help 2.5Mb ``` -# dfoliatR +# esci
-* Version: 0.3.0 -* GitHub: https://github.com/chguiterman/dfoliatR -* Source code: https://github.com/cran/dfoliatR -* Date/Publication: 2023-08-09 22:10:02 UTC -* Number of recursive dependencies: 109 +* Version: 1.0.3 +* GitHub: https://github.com/rcalinjageman/esci +* Source code: https://github.com/cran/esci +* Date/Publication: 2024-07-08 21:40:10 UTC +* Number of recursive dependencies: 93 -Run `revdepcheck::cloud_details(, "dfoliatR")` for more info +Run `revdepcheck::cloud_details(, "esci")` for more info
@@ -3799,26 +2903,26 @@ Run `revdepcheck::cloud_details(, "dfoliatR")` for more info * checking examples ... ERROR ``` - Running examples in ‘dfoliatR-Ex.R’ failed + Running examples in ‘esci-Ex.R’ failed The error most likely occurred in: - > ### Name: plot_outbreak - > ### Title: Produce a stacked plot to present composited, site-level insect - > ### outbreak chronologies - > ### Aliases: plot_outbreak + > ### Name: estimate_mdiff_2x2_between + > ### Title: Estimates for a 2x2 between-subjects design with a continuous + > ### outcome variable + > ### Aliases: estimate_mdiff_2x2_between > > ### ** Examples > ... - 14. └─cowplot:::as_gtable.default(x) - 15. ├─cowplot::as_grob(plot) - 16. └─cowplot:::as_grob.ggplot(plot) - 17. └─ggplot2::ggplotGrob(plot) - 18. ├─ggplot2::ggplot_gtable(ggplot_build(x)) - 19. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) - 20. └─ggplot2::calc_element("plot.margin", theme) - 21. └─cli::cli_abort(...) - 22. └─rlang::abort(...) + + estimates_from_summary$interaction, + + effect_size = "mean" + + ) + Warning: Using size for a discrete variable is not advised. + Warning: Using alpha for a discrete variable is not advised. + Error in use_defaults(..., self = self) : + unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, "black", TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), list(NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), 5.5, c(5.5, 5.5, 5.5, 5.5), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.75, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, + NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, 90, NULL, c(0, 2.75, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL + Calls: ... -> -> compute_geom_2 -> Execution halted ``` @@ -3828,102 +2932,133 @@ Run `revdepcheck::cloud_details(, "dfoliatR")` for more info Running the tests in ‘tests/testthat.R’ failed. Complete output: > library(testthat) - > library(dfoliatR) + > library(esci) > - > test_check("dfoliatR") - [ FAIL 1 | WARN 9 | SKIP 2 | PASS 12 ] - - ══ Skipped tests (2) ═══════════════════════════════════════════════════════════ + > test_check("esci") + Loading required package: Matrix + Loading required package: metadat + Loading required package: numDeriv ... - label_size = .lab$size, label_fontfamily = .lab$family, label_fontface = .lab$face, - label_colour = .lab$color, label_x = .lab$label.x, label_y = .lab$label.y, - hjust = .lab$hjust, vjust = .lab$vjust, align = align, rel_widths = widths, - rel_heights = heights, legend = legend, common.legend.grob = legend.grob)`: ℹ In index: 1. - Caused by error in `ggplot_gtable()`: - ! Theme element `plot.margin` must have class . + 17. │ └─self$geom$use_defaults(...) + 18. └─base::.handleSimpleError(...) + 19. └─rlang (local) h(simpleError(msg, call)) + 20. └─handlers[[1L]](cnd) + 21. └─cli::cli_abort(...) + 22. └─rlang::abort(...) - [ FAIL 1 | WARN 9 | SKIP 2 | PASS 12 ] + [ FAIL 14 | WARN 0 | SKIP 0 | PASS 3182 ] Error: Test failures Execution halted ``` +# evalITR + +
+ +* Version: 1.0.0 +* GitHub: https://github.com/MichaelLLi/evalITR +* Source code: https://github.com/cran/evalITR +* Date/Publication: 2023-08-25 23:10:06 UTC +* Number of recursive dependencies: 167 + +Run `revdepcheck::cloud_details(, "evalITR")` for more info + +
+ +## Newly broken + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘cv_multiple_alg.Rmd’ using rmarkdown + ``` + +## In both + * checking running R code from vignettes ... ERROR ``` Errors in running code in vignettes: - when running code in ‘intro-to-dfoliatR.Rmd’ + when running code in ‘cv_multiple_alg.Rmd’ ... - | 1683| 3| 2| 66.7| 1| 33.3| 0.3466| -1.7847|outbreak | - | 1684| 3| 2| 66.7| 0| 0.0| 0.6063| -1.0589|outbreak | + intersect, setdiff, setequal, union - > plot_outbreak(dmj_obr) - When sourcing ‘intro-to-dfoliatR.R’: - Error: ℹ In index: 1. - Caused by error in `ggplot_gtable()`: - ! Theme element `plot.margin` must have class . + > load("../data/star.rda") + Warning in readChar(con, 5L, useBytes = TRUE) : + cannot open compressed file '../data/star.rda', probable reason 'No such file or directory' + + ... Execution halted - ‘intro-to-dfoliatR.Rmd’ using ‘UTF-8’... failed + ‘cv_multiple_alg.Rmd’ using ‘UTF-8’... failed + ‘cv_single_alg.Rmd’ using ‘UTF-8’... failed + ‘install.Rmd’ using ‘UTF-8’... OK + ‘paper_alg1.Rmd’ using ‘UTF-8’... OK + ‘sample_split.Rmd’ using ‘UTF-8’... failed + ‘sample_split_caret.Rmd’ using ‘UTF-8’... failed + ‘user_itr.Rmd’ using ‘UTF-8’... failed + ‘user_itr_algs.Rmd’ using ‘UTF-8’... failed ``` -* checking re-building of vignette outputs ... NOTE +* checking dependencies in R code ... NOTE ``` - Error(s) in re-building vignettes: - --- re-building ‘intro-to-dfoliatR.Rmd’ using rmarkdown + Namespaces in Imports field not imported from: + ‘forcats’ ‘rqPen’ ‘utils’ + All declared Imports should be used. ``` -# directlabels +# eventstudyr
-* Version: 2024.1.21 -* GitHub: https://github.com/tdhock/directlabels -* Source code: https://github.com/cran/directlabels -* Date/Publication: 2024-01-24 19:20:07 UTC -* Number of recursive dependencies: 81 +* Version: 1.1.3 +* GitHub: https://github.com/JMSLab/eventstudyr +* Source code: https://github.com/cran/eventstudyr +* Date/Publication: 2024-03-04 15:00:02 UTC +* Number of recursive dependencies: 98 -Run `revdepcheck::cloud_details(, "directlabels")` for more info +Run `revdepcheck::cloud_details(, "eventstudyr")` for more info
## Newly broken -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘examples.Rmd’ - ... - 6 23 1669 aaa - 7 22 1315 aaa - 8 21 951 aaa - 9 20 610 aaa - 10 19 543 aaa - # ℹ 14 more rows - - When sourcing ‘examples.R’: - Error: Theme element `plot.margin` must have class . - Execution halted - - ‘examples.Rmd’... failed - ``` - -* checking re-building of vignette outputs ... NOTE +* checking tests ... ERROR ``` - Error(s) in re-building vignettes: - --- re-building ‘examples.Rmd’ using knitr + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(eventstudyr) + > + > test_check("eventstudyr") + Defaulting to strongest lead of differenced policy variable: proxyIV = z_fd_lead3. To specify a different proxyIV use the proxyIV argument. + Defaulting to strongest lead of differenced policy variable: proxyIV = z_fd_lead3. To specify a different proxyIV use the proxyIV argument. + Defaulting to strongest lead of differenced policy variable: proxyIV = z_fd_lead3. To specify a different proxyIV use the proxyIV argument. + ... + `expected` is a character vector ('ci_lower') + ── Failure ('test-EventStudyPlot.R:128:5'): confidence intervals are appropriately present or absent ── + p_ci$labels$ymax (`actual`) not equal to "ci_upper" (`expected`). + + `actual` is NULL + `expected` is a character vector ('ci_upper') + + [ FAIL 6 | WARN 0 | SKIP 0 | PASS 258 ] + Error: Test failures + Execution halted ``` -# disprofas +# EvoPhylo
-* Version: 0.1.3 -* GitHub: https://github.com/piusdahinden/disprofas -* Source code: https://github.com/cran/disprofas -* Date/Publication: 2021-12-08 12:40:02 UTC -* Number of recursive dependencies: 48 +* Version: 0.3.2 +* GitHub: https://github.com/tiago-simoes/EvoPhylo +* Source code: https://github.com/cran/EvoPhylo +* Date/Publication: 2022-11-03 17:00:02 UTC +* Number of recursive dependencies: 164 -Run `revdepcheck::cloud_details(, "disprofas")` for more info +Run `revdepcheck::cloud_details(, "EvoPhylo")` for more info
@@ -3931,65 +3066,123 @@ Run `revdepcheck::cloud_details(, "disprofas")` for more info * checking examples ... ERROR ``` - Running examples in ‘disprofas-Ex.R’ failed + Running examples in ‘EvoPhylo-Ex.R’ failed The error most likely occurred in: - > ### Name: plot.plot_mztia - > ### Title: Plot of the mztia simulation - > ### Aliases: plot.plot_mztia + > ### Name: make_clusters + > ### Title: Estimate and plot character partitions + > ### Aliases: make_clusters plot.cluster_df > > ### ** Examples > - > # Dissolution data of one reference batch and one test batch of n = 6 + > # See vignette("char-part") for how to use this ... - 1. ├─base::plot(gg1) - 2. └─disprofas:::plot.plot_mztia(gg1) - 3. ├─base::plot(x$Graph, ...) - 4. └─ggplot2:::plot.ggplot(x$Graph, ...) - 5. ├─ggplot2::ggplot_gtable(data) - 6. └─ggplot2:::ggplot_gtable.ggplot_built(data) - 7. └─ggplot2::calc_element("plot.margin", theme) - 8. └─cli::cli_abort(...) - 9. └─rlang::abort(...) + > # tSNE (3 dimensions; default is 2) + > cluster_df_tsne <- make_clusters(Dmatrix, k = 3, tsne = TRUE, + + tsne_dim = 2) + > + > # Plot clusters, plots divided into 2 rows, and increasing + > # overlap of text labels (default = 10) + > plot(cluster_df_tsne, nrow = 2, max.overlaps = 20) + Error in identicalUnits(x) : object is not a unit + Calls: ... assemble_guides -> guides_build -> unit.c -> identicalUnits + Execution halted + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘char-part.Rmd’ using rmarkdown + ``` + +## In both + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘char-part.Rmd’ + ... + + collapse = TRUE, dpi = 300) + + > devtools::load_all(".") + + When sourcing ‘char-part.R’: + Error: Could not find a root 'DESCRIPTION' file that starts with '^Package' in + '/tmp/Rtmp2nrOwZ/file1bed270c7be0/vignettes'. + ... + ℹ Are you in your project directory and does your project have a 'DESCRIPTION' + file? Execution halted + + ‘char-part.Rmd’ using ‘UTF-8’... failed + ‘data_treatment.Rmd’ using ‘UTF-8’... OK + ‘fbd-params.Rmd’ using ‘UTF-8’... failed + ‘offset_handling.Rmd’ using ‘UTF-8’... failed + ‘rates-selection_BEAST2.Rmd’ using ‘UTF-8’... failed + ‘rates-selection_MrBayes.Rmd’ using ‘UTF-8’... failed + ``` + +* checking installed package size ... NOTE + ``` + installed size is 6.8Mb + sub-directories of 1Mb or more: + data 2.5Mb + doc 1.6Mb + extdata 2.4Mb ``` +# expirest + +
+ +* Version: 0.1.6 +* GitHub: https://github.com/piusdahinden/expirest +* Source code: https://github.com/cran/expirest +* Date/Publication: 2024-03-25 16:30:02 UTC +* Number of recursive dependencies: 46 + +Run `revdepcheck::cloud_details(, "expirest")` for more info + +
+ +## Newly broken + * checking tests ... ERROR ``` Running ‘testthat.R’ Running the tests in ‘tests/testthat.R’ failed. Complete output: > library(testthat) - > library(disprofas) + > library(expirest) > - > test_check("disprofas") - [ FAIL 2 | WARN 3 | SKIP 0 | PASS 479 ] + > test_check("expirest") + [ FAIL 9 | WARN 0 | SKIP 0 | PASS 1122 ] ══ Failed tests ════════════════════════════════════════════════════════════════ ... - 8. └─ggplot2:::plot.ggplot(x$Graph, ...) - 9. ├─ggplot2::ggplot_gtable(data) - 10. └─ggplot2:::ggplot_gtable.ggplot_built(data) - 11. └─ggplot2::calc_element("plot.margin", theme) - 12. └─cli::cli_abort(...) - 13. └─rlang::abort(...) + ── Failure ('test-plot_expirest_wisle.R:260:3'): plot_expirest_wisle_succeeds ── + tmp4l2[["Graph"]]$labels has length 0, not length 8. + ── Failure ('test-plot_expirest_wisle.R:264:3'): plot_expirest_wisle_succeeds ── + tmp4b1[["Graph"]]$labels has length 0, not length 5. + ── Failure ('test-plot_expirest_wisle.R:269:3'): plot_expirest_wisle_succeeds ── + tmp4b2[["Graph"]]$labels has length 0, not length 5. - [ FAIL 2 | WARN 3 | SKIP 0 | PASS 479 ] + [ FAIL 9 | WARN 0 | SKIP 0 | PASS 1122 ] Error: Test failures Execution halted ``` -# distributional +# explainer
-* Version: 0.4.0 -* GitHub: https://github.com/mitchelloharawild/distributional -* Source code: https://github.com/cran/distributional -* Date/Publication: 2024-02-07 13:30:02 UTC -* Number of recursive dependencies: 64 +* Version: 1.0.1 +* GitHub: https://github.com/PERSIMUNE/explainer +* Source code: https://github.com/cran/explainer +* Date/Publication: 2024-04-18 09:00:02 UTC +* Number of recursive dependencies: 184 -Run `revdepcheck::cloud_details(, "distributional")` for more info +Run `revdepcheck::cloud_details(, "explainer")` for more info
@@ -3997,214 +3190,220 @@ Run `revdepcheck::cloud_details(, "distributional")` for more info * checking examples ... ERROR ``` - Running examples in ‘distributional-Ex.R’ failed + Running examples in ‘explainer-Ex.R’ failed The error most likely occurred in: - > ### Name: dist_truncated - > ### Title: Truncate a distribution - > ### Aliases: dist_truncated + > ### Name: eDecisionCurve + > ### Title: Decision Curve Plot + > ### Aliases: eDecisionCurve > > ### ** Examples > - > dist <- dist_truncated(dist_normal(2,1), lower = 0) + > library("explainer") ... - 12. │ └─ggplot2 (local) f(l = layers[[i]], d = data[[i]]) - 13. │ └─l$compute_geom_2(d, theme = plot$theme) - 14. │ └─ggplot2 (local) compute_geom_2(..., self = self) - 15. │ └─self$geom$use_defaults(...) - 16. └─base::.handleSimpleError(...) - 17. └─rlang (local) h(simpleError(msg, call)) - 18. └─handlers[[1L]](cnd) - 19. └─cli::cli_abort(...) - 20. └─rlang::abort(...) + > mylrn$train(maintask, splits$train) + > myplot <- eDecisionCurve( + + task = maintask, + + trained_model = mylrn, + + splits = splits, + + seed = seed + + ) + Error in pm[[2]] : subscript out of bounds + Calls: eDecisionCurve -> ggplotly -> ggplotly.ggplot -> gg2list Execution halted ``` -# dittoViz - -
+## In both -* Version: 1.0.1 -* GitHub: https://github.com/dtm2451/dittoViz -* Source code: https://github.com/cran/dittoViz -* Date/Publication: 2024-02-02 00:00:12 UTC -* Number of recursive dependencies: 99 +* checking dependencies in R code ... NOTE + ``` + Namespace in Imports field not imported from: ‘ggpmisc’ + All declared Imports should be used. + ``` -Run `revdepcheck::cloud_details(, "dittoViz")` for more info +# ezEDA + +
+ +* Version: 0.1.1 +* GitHub: https://github.com/kviswana/ezEDA +* Source code: https://github.com/cran/ezEDA +* Date/Publication: 2021-06-29 04:40:10 UTC +* Number of recursive dependencies: 91 + +Run `revdepcheck::cloud_details(, "ezEDA")` for more info
## Newly broken -* checking examples ... ERROR - ``` - Running examples in ‘dittoViz-Ex.R’ failed - The error most likely occurred in: - - > ### Name: barPlot - > ### Title: Outputs a stacked bar plot to show the percent composition of - > ### samples, groups, clusters, or other groupings - > ### Aliases: barPlot - > - > ### ** Examples - > - ... - 15 3 D 12 32 0.3750000 - 16 4 D 8 32 0.2500000 - > # through hovering the cursor over the relevant parts of the plot - > if (requireNamespace("plotly", quietly = TRUE)) { - + barPlot(example_df, "clustering", group.by = "groups", - + do.hover = TRUE) - + } - Error in pm[[2]] : subscript out of bounds - Calls: barPlot -> -> ggplotly.ggplot -> gg2list - Execution halted - ``` - * checking tests ... ERROR ``` Running ‘testthat.R’ Running the tests in ‘tests/testthat.R’ failed. Complete output: > library(testthat) - > library(dittoViz) - Loading required package: ggplot2 - > test_check("dittoViz") - [ FAIL 12 | WARN 12 | SKIP 0 | PASS 307 ] + > library(ezEDA) + > + > test_check("ezEDA") + [ FAIL 22 | WARN 0 | SKIP 0 | PASS 57 ] ══ Failed tests ════════════════════════════════════════════════════════════════ ... - 2. └─dittoViz::freqPlot(...) - 3. └─dittoViz::yPlot(...) - 4. └─dittoViz:::.warn_or_apply_plotly(p, plots) - 5. ├─plotly::ggplotly(p, tooltip = "text") - 6. └─plotly:::ggplotly.ggplot(p, tooltip = "text") - 7. └─plotly::gg2list(...) + ── Error ('test_two_measures_relationship.R:19:3'): y axis is labeled 'hwy' ──── + Error in `expect_match(p$labels$y, "hwy")`: is.character(act$val) is not TRUE + Backtrace: + ▆ + 1. └─testthat::expect_match(p$labels$y, "hwy") at test_two_measures_relationship.R:19:3 + 2. └─base::stopifnot(is.character(act$val)) - [ FAIL 12 | WARN 12 | SKIP 0 | PASS 307 ] + [ FAIL 22 | WARN 0 | SKIP 0 | PASS 57 ] Error: Test failures Execution halted ``` -# dobin +# ezplot
-* Version: 1.0.4 +* Version: 0.7.13 * GitHub: NA -* Source code: https://github.com/cran/dobin -* Date/Publication: 2022-08-25 22:52:33 UTC -* Number of recursive dependencies: 147 +* Source code: https://github.com/cran/ezplot +* Date/Publication: 2024-01-28 11:30:05 UTC +* Number of recursive dependencies: 109 -Run `revdepcheck::cloud_details(, "dobin")` for more info +Run `revdepcheck::cloud_details(, "ezplot")` for more info
## Newly broken +* checking examples ... ERROR + ``` + Running examples in ‘ezplot-Ex.R’ failed + The error most likely occurred in: + + > ### Name: bar_plot + > ### Title: bar_plot + > ### Aliases: bar_plot + > + > ### ** Examples + > + > library(tsibble) + ... + 11. │ └─base::withCallingHandlers(...) + 12. └─ggplot2 (local) f(l = layers[[i]], d = data[[i]]) + 13. └─l$compute_geom_2(d, theme = plot$theme) + 14. └─ggplot2 (local) compute_geom_2(..., self = self) + 15. └─self$geom$use_defaults(...) + 16. └─ggplot2 (local) use_defaults(..., self = self) + 17. └─ggplot2:::check_aesthetics(new_params, nrow(data)) + 18. └─cli::cli_abort(...) + 19. └─rlang::abort(...) + Execution halted + ``` + * checking running R code from vignettes ... ERROR ``` Errors in running code in vignettes: - when running code in ‘dobin.Rmd’ + when running code in ‘bar_plot.Rmd’ ... - + boxplotLimits = 10) - > pPx <- O3plotM(pPa) - - > pPx$gO3x + theme(plot.margin = unit(c(0, 2, 0, 0), - + "cm")) + > bar_plot(ansett, "year(Week)", "Passengers", size = 16) - When sourcing ‘dobin.R’: - Error: Theme element `plot.margin` must have class . + When sourcing ‘bar_plot.R’: + Error: Problem while setting up geom aesthetics. + ℹ Error occurred in the 1st layer. + Caused by error in `check_aesthetics()`: + ... + Caused by error in `check_aesthetics()`: + ! Aesthetics must be either length 1 or the same as the data (9). + ✖ Fix the following mappings: `width`. Execution halted - ‘dobin.Rmd’ using ‘UTF-8’... failed + ‘bar_plot.Rmd’ using ‘UTF-8’... failed + ‘basics.Rmd’ using ‘UTF-8’... failed + ‘line_plot.Rmd’ using ‘UTF-8’... OK + ‘overview.Rmd’ using ‘UTF-8’... failed + ‘variable_plot.Rmd’ using ‘UTF-8’... OK ``` * checking re-building of vignette outputs ... NOTE ``` Error(s) in re-building vignettes: - --- re-building ‘dobin.Rmd’ using rmarkdown + --- re-building ‘bar_plot.Rmd’ using rmarkdown + + Quitting from lines 28-29 [unnamed-chunk-2] (bar_plot.Rmd) + Error: processing vignette 'bar_plot.Rmd' failed with diagnostics: + Problem while setting up geom aesthetics. + ℹ Error occurred in the 1st layer. + Caused by error in `check_aesthetics()`: + ! Aesthetics must be either length 1 or the same as the data (6). + ✖ Fix the following mappings: `width`. + --- failed re-building ‘bar_plot.Rmd’ + + --- re-building ‘basics.Rmd’ using rmarkdown ``` -# dogesr +# fable.prophet
-* Version: 0.5.0 -* GitHub: NA -* Source code: https://github.com/cran/dogesr -* Date/Publication: 2023-08-21 11:40:05 UTC -* Number of recursive dependencies: 121 +* Version: 0.1.0 +* GitHub: https://github.com/mitchelloharawild/fable.prophet +* Source code: https://github.com/cran/fable.prophet +* Date/Publication: 2020-08-20 09:30:03 UTC +* Number of recursive dependencies: 114 -Run `revdepcheck::cloud_details(, "dogesr")` for more info +Run `revdepcheck::cloud_details(, "fable.prophet")` for more info
## Newly broken -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘counting-doge-families.Rmd’ using rmarkdown - --- finished re-building ‘counting-doge-families.Rmd’ - - --- re-building ‘doge-types.Rmd’ using rmarkdown - - Quitting from lines 48-51 [plot] (doge-types.Rmd) - Error: processing vignette 'doge-types.Rmd' failed with diagnostics: - Theme element `plot.margin` must have class . - --- failed re-building ‘doge-types.Rmd’ - - --- re-building ‘doges-family-types.Rmd’ using rmarkdown - --- finished re-building ‘doges-family-types.Rmd’ - - --- re-building ‘doges-social-network.Rmd’ using rmarkdown - ``` - -## In both - * checking running R code from vignettes ... ERROR ``` Errors in running code in vignettes: - when running code in ‘counting-doge-families.Rmd’ + when running code in ‘intro.Rmd’ ... - > knitr::opts_chunk$set(collapse = TRUE, comment = "#>") + 9 Domestic mdl 2019 Dec sample[5000] 5337907. + 10 Domestic mdl 2020 Jan sample[5000] 4887065. + # ℹ 62 more rows - > devtools::load_all(".") + > fc %>% autoplot(lax_passengers) - When sourcing ‘counting-doge-families.R’: - Error: Could not find a root 'DESCRIPTION' file that starts with '^Package' in - '/tmp/Rtmpt416E4/file12ff49ee8180/vignettes'. - ... - ℹ Are you in your project directory and does your project have a 'DESCRIPTION' - file? + When sourcing ‘intro.R’: + Error: unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, "black", TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), list(NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), 5.5, c(5.5, 5.5, 5.5, 5.5), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.75, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, + NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, 90, NULL, c(0, 2.75, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, Execution halted - ‘counting-doge-families.Rmd’ using ‘UTF-8’... failed - ‘doge-types.Rmd’ using ‘UTF-8’... failed - ‘doges-family-types.Rmd’ using ‘UTF-8’... failed - ‘doges-social-network.Rmd’ using ‘UTF-8’... OK - ‘doges-split-social-network.Rmd’ using ‘UTF-8’... OK - ‘doges-terms.Rmd’ using ‘UTF-8’... OK + ‘intro.Rmd’ using ‘UTF-8’... failed ``` -* checking data for non-ASCII characters ... NOTE +* checking re-building of vignette outputs ... NOTE ``` - Note: found 3 marked UTF-8 strings + Error(s) in re-building vignettes: + --- re-building ‘intro.Rmd’ using rmarkdown ``` -# dotsViolin +## In both + +* checking LazyData ... NOTE + ``` + 'LazyData' is specified without a 'data' directory + ``` + +# fabletools
-* Version: 0.0.1 -* GitHub: NA -* Source code: https://github.com/cran/dotsViolin -* Date/Publication: 2023-10-30 13:20:02 UTC -* Number of recursive dependencies: 39 +* Version: 0.4.2 +* GitHub: https://github.com/tidyverts/fabletools +* Source code: https://github.com/cran/fabletools +* Date/Publication: 2024-04-22 11:22:41 UTC +* Number of recursive dependencies: 106 -Run `revdepcheck::cloud_details(, "dotsViolin")` for more info +Run `revdepcheck::cloud_details(, "fabletools")` for more info
@@ -4212,47 +3411,65 @@ Run `revdepcheck::cloud_details(, "dotsViolin")` for more info * checking examples ... ERROR ``` - Running examples in ‘dotsViolin-Ex.R’ failed + Running examples in ‘fabletools-Ex.R’ failed The error most likely occurred in: - > ### Name: dots_and_violin - > ### Title: Makes a composite dot-plot and violin-plot - > ### Aliases: dots_and_violin - > ### Keywords: dot-plot violin-plot + > ### Name: autoplot.fbl_ts + > ### Title: Plot a set of forecasts + > ### Aliases: autoplot.fbl_ts autolayer.fbl_ts > > ### ** Examples > + > ## Don't show: ... - 3. │ └─gridExtra::arrangeGrob(...) - 4. └─gridExtra::arrangeGrob(...) - 5. └─base::lapply(grobs[toconv], ggplot2::ggplotGrob) - 6. └─ggplot2 (local) FUN(X[[i]], ...) - 7. ├─ggplot2::ggplot_gtable(ggplot_build(x)) - 8. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) - 9. └─ggplot2::calc_element("plot.margin", theme) - 10. └─cli::cli_abort(...) - 11. └─rlang::abort(...) + > library(fable) + > library(tsibbledata) + > fc <- aus_production %>% model(ets = ETS(log(Beer) ~ error("M") + trend("Ad") + + + season("A"))) %>% forecast(h = "3 years") + > fc %>% autoplot(aus_production) + Error in use_defaults(..., self = self) : + unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, "black", TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), list(NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), 5.5, c(5.5, 5.5, 5.5, 5.5), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.75, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, + NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, 90, NULL, c(0, 2.75, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL + Calls: ... -> -> compute_geom_2 -> Execution halted ``` -## In both - -* checking data for non-ASCII characters ... NOTE +* checking tests ... ERROR ``` - Note: found 2 marked UTF-8 strings + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(dplyr) + + Attaching package: 'dplyr' + + The following object is masked from 'package:testthat': + + ... + 24. └─base::Map(...) + 25. └─base::mapply(FUN = f, ..., SIMPLIFY = FALSE) + 26. └─ggplot2 (local) ``(layer = dots[[1L]][[1L]], df = dots[[2L]][[1L]]) + 27. └─layer$compute_geom_2(key, single_params, theme) + 28. └─ggplot2 (local) compute_geom_2(..., self = self) + 29. └─self$geom$use_defaults(...) + + [ FAIL 2 | WARN 0 | SKIP 1 | PASS 269 ] + Error: Test failures + Execution halted ``` -# ds4psy +# factoextra
-* Version: 1.0.0 -* GitHub: https://github.com/hneth/ds4psy -* Source code: https://github.com/cran/ds4psy -* Date/Publication: 2023-09-15 07:30:02 UTC -* Number of recursive dependencies: 55 +* Version: 1.0.7 +* GitHub: https://github.com/kassambara/factoextra +* Source code: https://github.com/cran/factoextra +* Date/Publication: 2020-04-01 21:20:02 UTC +* Number of recursive dependencies: 116 -Run `revdepcheck::cloud_details(, "ds4psy")` for more info +Run `revdepcheck::cloud_details(, "factoextra")` for more info
@@ -4260,260 +3477,171 @@ Run `revdepcheck::cloud_details(, "ds4psy")` for more info * checking examples ... ERROR ``` - Running examples in ‘ds4psy-Ex.R’ failed + Running examples in ‘factoextra-Ex.R’ failed The error most likely occurred in: - > ### Name: plot_charmap - > ### Title: Plot a character map as a tile plot with text labels. - > ### Aliases: plot_charmap + > ### Name: eigenvalue + > ### Title: Extract and visualize the eigenvalues/variances of dimensions + > ### Aliases: eigenvalue get_eig get_eigenvalue fviz_eig fviz_screeplot > > ### ** Examples > - > # (0) Prepare: + > # Principal Component Analysis ... - Backtrace: - ▆ - 1. ├─base (local) ``(x) - 2. └─ggplot2:::print.ggplot(x) - 3. ├─ggplot2::ggplot_gtable(data) - 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) - 5. └─ggplot2::calc_element("plot.margin", theme) - 6. └─cli::cli_abort(...) - 7. └─rlang::abort(...) + 11. │ └─base::withCallingHandlers(...) + 12. └─ggplot2 (local) f(l = layers[[i]], d = data[[i]]) + 13. └─l$compute_geom_2(d, theme = plot$theme) + 14. └─ggplot2 (local) compute_geom_2(..., self = self) + 15. └─self$geom$use_defaults(...) + 16. └─ggplot2 (local) use_defaults(..., self = self) + 17. └─ggplot2:::check_aesthetics(new_params, nrow(data)) + 18. └─cli::cli_abort(...) + 19. └─rlang::abort(...) Execution halted ``` -# edecob +# fairmodels
-* Version: 1.2.2 -* GitHub: NA -* Source code: https://github.com/cran/edecob -* Date/Publication: 2022-11-04 12:00:02 UTC -* Number of recursive dependencies: 29 +* Version: 1.2.1 +* GitHub: https://github.com/ModelOriented/fairmodels +* Source code: https://github.com/cran/fairmodels +* Date/Publication: 2022-08-23 19:50:06 UTC +* Number of recursive dependencies: 87 -Run `revdepcheck::cloud_details(, "edecob")` for more info +Run `revdepcheck::cloud_details(, "fairmodels")` for more info
## Newly broken -* checking examples ... ERROR +* checking tests ... ERROR ``` - Running examples in ‘edecob-Ex.R’ failed - The error most likely occurred in: - - > ### Name: edecob - > ### Title: Event DEtection using COnfidence Bounds - > ### Aliases: edecob - > - > ### ** Examples - > - > library(edecob) + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(fairmodels) + > + > + > test_check("fairmodels") + Welcome to DALEX (version: 2.4.3). + Find examples and detailed introduction at: http://ema.drwhy.ai/ ... - ▆ - 1. ├─base::plot(example_event$`Subject 1`) - 2. └─edecob:::plot.edecob(example_event$`Subject 1`) - 3. └─ggplot2::ggplotGrob(patient_plot) - 4. ├─ggplot2::ggplot_gtable(ggplot_build(x)) - 5. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) - 6. └─ggplot2::calc_element("plot.margin", theme) - 7. └─cli::cli_abort(...) - 8. └─rlang::abort(...) - Execution halted + [ FAIL 1 | WARN 1 | SKIP 0 | PASS 312 ] + + ══ Failed tests ════════════════════════════════════════════════════════════════ + ── Failure ('test_plot_density.R:14:3'): Test plot_density ───────────────────── + plt$labels$x not equal to "probability". + target is NULL, current is character + + [ FAIL 1 | WARN 1 | SKIP 0 | PASS 312 ] + Error: Test failures + Execution halted ``` -# entropart +# fddm
-* Version: 1.6-13 -* GitHub: https://github.com/EricMarcon/entropart -* Source code: https://github.com/cran/entropart -* Date/Publication: 2023-09-26 14:40:02 UTC -* Number of recursive dependencies: 121 +* Version: 1.0-2 +* GitHub: https://github.com/rtdists/fddm +* Source code: https://github.com/cran/fddm +* Date/Publication: 2024-07-02 16:00:07 UTC +* Number of recursive dependencies: 92 -Run `revdepcheck::cloud_details(, "entropart")` for more info +Run `revdepcheck::cloud_details(, "fddm")` for more info
## Newly broken -* checking examples ... ERROR - ``` - Running examples in ‘entropart-Ex.R’ failed - The error most likely occurred in: - - > ### Name: Accumulation - > ### Title: Diversity accumulation. - > ### Aliases: DivAC EntAC as.AccumCurve is.AccumCurve autoplot.AccumCurve - > ### plot.AccumCurve - > - > ### ** Examples - > - ... - 11. │ └─base::withCallingHandlers(...) - 12. └─ggplot2 (local) f(l = layers[[i]], d = data[[i]]) - 13. └─l$compute_geom_2(d, theme = plot$theme) - 14. └─ggplot2 (local) compute_geom_2(..., self = self) - 15. └─self$geom$use_defaults(...) - 16. └─ggplot2 (local) use_defaults(..., self = self) - 17. └─ggplot2:::check_aesthetics(new_params, nrow(data)) - 18. └─cli::cli_abort(...) - 19. └─rlang::abort(...) - Execution halted - ``` - * checking running R code from vignettes ... ERROR ``` Errors in running code in vignettes: - when running code in ‘entropart.Rmd’ + when running code in ‘benchmark.Rmd’ ... + > mi <- min(bm_vec[, -seq_len(t_idx)]) - > autoplot(Abd18, Distribution = "lnorm") + > ma <- max(bm_vec[, (t_idx + 1):(ncol(bm_vec) - 4)]) - When sourcing ‘entropart.R’: - Error: Problem while setting up geom aesthetics. - ℹ Error occurred in the 1st layer. - Caused by error in `check_aesthetics()`: - ! Aesthetics must be either length 1 or the same as the data (149). - ✖ Fix the following mappings: `shape`, `colour`, and `size`. + > ggplot(mbm_vec, aes(x = factor(FuncName, levels = Names_vec), + + y = time, color = factor(FuncName, levels = Names_vec), fill = factor(FuncName, .... [TRUNCATED] + + ... + + When sourcing ‘pfddm.R’: + Error: Not a unit object Execution halted - ‘entropart.Rmd’ using ‘UTF-8’... failed + ‘benchmark.Rmd’ using ‘UTF-8’... failed + ‘example.Rmd’ using ‘UTF-8’... OK + ‘math.Rmd’ using ‘UTF-8’... OK + ‘pfddm.Rmd’ using ‘UTF-8’... failed + ‘validity.Rmd’ using ‘UTF-8’... OK ``` -* checking re-building of vignette outputs ... NOTE +## In both + +* checking installed package size ... NOTE ``` - Error(s) in re-building vignettes: - ... - --- re-building ‘entropart.Rmd’ using rmarkdown - - Quitting from lines 53-55 [PlotN18] (entropart.Rmd) - Error: processing vignette 'entropart.Rmd' failed with diagnostics: - Problem while setting up geom aesthetics. - ℹ Error occurred in the 1st layer. - Caused by error in `check_aesthetics()`: - ! Aesthetics must be either length 1 or the same as the data (149). - ✖ Fix the following mappings: `shape`, `colour`, and `size`. - --- failed re-building ‘entropart.Rmd’ - - SUMMARY: processing the following file failed: - ‘entropart.Rmd’ - - Error: Vignette re-building failed. - Execution halted + installed size is 16.0Mb + sub-directories of 1Mb or more: + doc 1.6Mb + libs 13.5Mb ``` -# envalysis +# feasts
-* Version: 0.7.0 -* GitHub: https://github.com/zsteinmetz/envalysis -* Source code: https://github.com/cran/envalysis -* Date/Publication: 2024-03-20 15:10:02 UTC -* Number of recursive dependencies: 103 +* Version: 0.3.2 +* GitHub: https://github.com/tidyverts/feasts +* Source code: https://github.com/cran/feasts +* Date/Publication: 2024-03-15 09:10:02 UTC +* Number of recursive dependencies: 101 -Run `revdepcheck::cloud_details(, "envalysis")` for more info +Run `revdepcheck::cloud_details(, "feasts")` for more info
## Newly broken -* checking examples ... ERROR - ``` - Running examples in ‘envalysis-Ex.R’ failed - The error most likely occurred in: - - > ### Name: theme_publish - > ### Title: ggplot2 theme for scientific publications - > ### Aliases: theme_publish - > - > ### ** Examples - > - > library(ggplot2) - ... - Backtrace: - ▆ - 1. ├─base (local) ``(x) - 2. └─ggplot2:::print.ggplot(x) - 3. ├─ggplot2::ggplot_gtable(data) - 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) - 5. └─ggplot2::calc_element("plot.margin", theme) - 6. └─cli::cli_abort(...) - 7. └─rlang::abort(...) - Execution halted - ``` - * checking tests ... ERROR ``` Running ‘testthat.R’ Running the tests in ‘tests/testthat.R’ failed. Complete output: > library(testthat) - > library(envalysis) + > library(feasts) + Loading required package: fabletools > - > test_check("envalysis") - number of blank values <= 1; LOD is estimated from the calibration curve - number of blank values <= 1; LOD is estimated from the calibration curve - number of blank values <= 1; LOD is estimated from the calibration curve - ... - 13. └─ggplot2::calc_element("plot.margin", theme) - 14. └─cli::cli_abort(...) - 15. └─rlang::abort(...) + > test_check("feasts") + [ FAIL 1 | WARN 0 | SKIP 0 | PASS 108 ] - [ FAIL 1 | WARN 0 | SKIP 3 | PASS 139 ] - Deleting unused snapshots: - • calibration/plot.png - • texture/plot.png + ══ Failed tests ════════════════════════════════════════════════════════════════ + ── Failure ('test-graphics.R:273:3'): gg_arma() plots ────────────────────────── + p_built$plot$labels[c("x", "y")] not equivalent to list(x = "Re(1/root)", y = "Im(1/root)"). + Component "x": 1 string mismatch + Component "y": 1 string mismatch + + [ FAIL 1 | WARN 0 | SKIP 0 | PASS 108 ] Error: Test failures Execution halted ``` -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘calibration.Rmd’ - ... - > dt$sum <- dt$res[, .(Content = mean(Content, na.rm = T), - + CI = CI(Content, na.rm = T)), by = .(Compound, Treatment, - + Day)] - - > ggplot(dt$sum, aes(x = Day, y = Content)) + geom_errorbar(aes(ymin = Content - - + CI, ymax = Content + CI, group = Treatment), width = 1, positi .... [TRUNCATED] - - ... - - > p + theme_publish() - - When sourcing ‘theme_publish.R’: - Error: Theme element `plot.margin` must have class . - Execution halted - - ‘calibration.Rmd’ using ‘UTF-8’... failed - ‘texture.Rmd’ using ‘UTF-8’... OK - ‘theme_publish.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘calibration.Rmd’ using rmarkdown - ``` - -# epiCleanr +# ffp
-* Version: 0.2.0 -* GitHub: https://github.com/truenomad/epiCleanr -* Source code: https://github.com/cran/epiCleanr -* Date/Publication: 2023-09-28 12:20:05 UTC -* Number of recursive dependencies: 130 +* Version: 0.2.2 +* GitHub: https://github.com/Reckziegel/FFP +* Source code: https://github.com/cran/ffp +* Date/Publication: 2022-09-29 15:10:06 UTC +* Number of recursive dependencies: 107 -Run `revdepcheck::cloud_details(, "epiCleanr")` for more info +Run `revdepcheck::cloud_details(, "ffp")` for more info
@@ -4521,101 +3649,37 @@ Run `revdepcheck::cloud_details(, "epiCleanr")` for more info * checking examples ... ERROR ``` - Running examples in ‘epiCleanr-Ex.R’ failed + Running examples in ‘ffp-Ex.R’ failed The error most likely occurred in: - > ### Name: handle_outliers - > ### Title: Detect and Handle Outliers in Dataset - > ### Aliases: handle_outliers + > ### Name: scenario_density + > ### Title: Plot Scenarios + > ### Aliases: scenario_density scenario_histogram > > ### ** Examples > + > x <- diff(log(EuStockMarkets))[, 1] + > p <- exp_decay(x, 0.005) > - ... - 12. │ └─ggplot2 (local) f(l = layers[[i]], d = data[[i]]) - 13. │ └─l$compute_geom_2(d, theme = plot$theme) - 14. │ └─ggplot2 (local) compute_geom_2(..., self = self) - 15. │ └─self$geom$use_defaults(...) - 16. └─base::.handleSimpleError(...) - 17. └─rlang (local) h(simpleError(msg, call)) - 18. └─handlers[[1L]](cnd) - 19. └─cli::cli_abort(...) - 20. └─rlang::abort(...) - Execution halted - ``` - -## In both - -* checking installed package size ... NOTE - ``` - installed size is 5.6Mb - sub-directories of 1Mb or more: - doc 2.9Mb - help 2.5Mb - ``` - -# EpiInvert - -
- -* Version: 0.3.1 -* GitHub: https://github.com/lalvarezmat/EpiInvert -* Source code: https://github.com/cran/EpiInvert -* Date/Publication: 2022-12-14 14:40:03 UTC -* Number of recursive dependencies: 98 - -Run `revdepcheck::cloud_details(, "EpiInvert")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘EpiInvert-Ex.R’ failed - The error most likely occurred in: - - > ### Name: EpiInvert - > ### Title: 'EpiInvert' estimates the reproduction number Rt and a restored - > ### incidence curve from the original daily incidence curve and the - > ### serial interval distribution. EpiInvert also corrects the festive and - > ### weekly biases present in the registered daily incidence. - > ### Aliases: EpiInvert - > - ... - Backtrace: - ▆ - 1. └─EpiInvert::EpiInvert_plot(res) - 2. └─ggplot2::ggplotGrob(g1) - 3. ├─ggplot2::ggplot_gtable(ggplot_build(x)) - 4. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) - 5. └─ggplot2::calc_element("plot.margin", theme) - 6. └─cli::cli_abort(...) - 7. └─rlang::abort(...) + > scenario_density(x, p, 500) + Error in use_defaults(..., self = self) : + unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, "black", TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), list(NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), 5.5, c(5.5, 5.5, 5.5, 5.5), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.75, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, + NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, 90, NULL, c(0, 2.75, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(), NULL, list(NU + Calls: ... -> -> compute_geom_2 -> Execution halted ``` -## In both - -* checking installed package size ... NOTE - ``` - installed size is 7.7Mb - sub-directories of 1Mb or more: - data 3.2Mb - libs 4.3Mb - ``` - -# esci +# fido
-* Version: 1.0.2 -* GitHub: https://github.com/rcalinjageman/esci -* Source code: https://github.com/cran/esci -* Date/Publication: 2024-03-21 18:10:02 UTC -* Number of recursive dependencies: 93 +* Version: 1.1.1 +* GitHub: https://github.com/jsilve24/fido +* Source code: https://github.com/cran/fido +* Date/Publication: 2024-06-05 21:30:06 UTC +* Number of recursive dependencies: 130 -Run `revdepcheck::cloud_details(, "esci")` for more info +Run `revdepcheck::cloud_details(, "fido")` for more info
@@ -4623,25 +3687,23 @@ Run `revdepcheck::cloud_details(, "esci")` for more info * checking examples ... ERROR ``` - Running examples in ‘esci-Ex.R’ failed + Running examples in ‘fido-Ex.R’ failed The error most likely occurred in: - > ### Name: estimate_mdiff_2x2_between - > ### Title: Estimates for a 2x2 between-subjects design with a continuous - > ### outcome variable - > ### Aliases: estimate_mdiff_2x2_between + > ### Name: plot.pibblefit + > ### Title: Plot Summaries of Posterior Distribution of pibblefit Parameters + > ### Aliases: plot.pibblefit > > ### ** Examples > - ... - + estimates_from_summary$interaction, - + effect_size = "mean" - + ) - Warning: Using size for a discrete variable is not advised. - Warning: Using alpha for a discrete variable is not advised. + > sim <- pibble_sim(N=10, D=4, Q=3) + > fit <- pibble(sim$Y, sim$X) + > plot(fit, par="Lambda") + Scale for colour is already present. + Adding another scale for colour, which will replace the existing scale. Error in use_defaults(..., self = self) : - unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, "black", TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), NULL, list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), 5.5, c(5.5, 5.5, 5.5, 5.5), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.75, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, - NULL, NULL, NULL, 1, 90, NULL, c(0, 2.75, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 1, NULL, NULL, NULL, c(0, 2.2, 0, 0), NULL, TRUE), NULL, l + unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, "black", TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), list(NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), 5.5, c(5.5, 5.5, 5.5, 5.5), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.75, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, + NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 1, NULL, NULL, NULL, c(0, 2.2, 0, 0), NULL, TRUE), NULL, list(N Calls: ... -> -> compute_geom_2 -> Execution halted ``` @@ -4652,307 +3714,246 @@ Run `revdepcheck::cloud_details(, "esci")` for more info Running the tests in ‘tests/testthat.R’ failed. Complete output: > library(testthat) - > library(esci) + > library(fido) > - > test_check("esci") - Loading required package: Matrix - Loading required package: metadat - Loading required package: numDeriv + > #Sys.setenv(KMP_DUPLICATE_LIB_OK="TRUE") + > test_check("fido") + [1] 0.27980164 -0.69169550 -0.53205652 0.11488451 -0.42419872 2.20261388 + [7] -1.62190133 -0.90893172 0.07891428 0.75060681 0.43593605 0.26819442 ... - 17. │ └─self$geom$use_defaults(...) - 18. └─base::.handleSimpleError(...) - 19. └─rlang (local) h(simpleError(msg, call)) - 20. └─handlers[[1L]](cnd) - 21. └─cli::cli_abort(...) - 22. └─rlang::abort(...) + 21. └─base::Map(...) + 22. └─base::mapply(FUN = f, ..., SIMPLIFY = FALSE) + 23. └─ggplot2 (local) ``(layer = dots[[1L]][[1L]], df = dots[[2L]][[1L]]) + 24. └─layer$compute_geom_2(key, single_params, theme) + 25. └─ggplot2 (local) compute_geom_2(..., self = self) + 26. └─self$geom$use_defaults(...) - [ FAIL 14 | WARN 15 | SKIP 0 | PASS 3182 ] + [ FAIL 1 | WARN 0 | SKIP 0 | PASS 114 ] Error: Test failures Execution halted ``` -# EvidenceSynthesis - -
- -* Version: 0.5.0 -* GitHub: https://github.com/OHDSI/EvidenceSynthesis -* Source code: https://github.com/cran/EvidenceSynthesis -* Date/Publication: 2023-05-08 12:20:02 UTC -* Number of recursive dependencies: 117 - -Run `revdepcheck::cloud_details(, "EvidenceSynthesis")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘EvidenceSynthesis-Ex.R’ failed - The error most likely occurred in: - - > ### Name: plotCovariateBalances - > ### Title: Plot covariate balances - > ### Aliases: plotCovariateBalances - > - > ### ** Examples - > - > # Some example data: - ... - 2. └─gridExtra::grid.arrange(data_table, plot, ncol = 2) - 3. └─gridExtra::arrangeGrob(...) - 4. └─base::lapply(grobs[toconv], ggplot2::ggplotGrob) - 5. └─ggplot2 (local) FUN(X[[i]], ...) - 6. ├─ggplot2::ggplot_gtable(ggplot_build(x)) - 7. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) - 8. └─ggplot2::calc_element("plot.margin", theme) - 9. └─cli::cli_abort(...) - 10. └─rlang::abort(...) - Execution halted - ``` - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > test_check("EvidenceSynthesis") - Loading required package: EvidenceSynthesis - Loading required package: survival - - | | 0% - |=============================================================== | 90%df = 4.0 - ... - 5. └─ggplot2 (local) FUN(X[[i]], ...) - 6. ├─ggplot2::ggplot_gtable(ggplot_build(x)) - 7. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) - 8. └─ggplot2::calc_element("plot.margin", theme) - 9. └─cli::cli_abort(...) - 10. └─rlang::abort(...) - - [ FAIL 3 | WARN 8 | SKIP 0 | PASS 57 ] - Error: Test failures - Execution halted - ``` +## In both * checking running R code from vignettes ... ERROR ``` Errors in running code in vignettes: - when running code in ‘NonNormalEffectSynthesis.Rmd’ + when running code in ‘non-linear-models.Rmd’ ... - 1 2.097148 1.104696 3.783668 - > labels <- paste("Data site", LETTERS[1:length(populations)]) + The following object is masked from ‘package:dplyr’: - > plotMetaAnalysisForest(data = approximations, labels = labels, - + estimate = estimate, xLabel = "Hazard Ratio", showLikelihood = TRUE) + select - ... - > plotMetaAnalysisForest(data = normalApproximations, - + labels = paste("Site", 1:10), estimate = fixedFxNormal, xLabel = "Hazard Ratio") - When sourcing ‘VideoVignette.R’: - Error: Theme element `plot.margin` must have class . + When sourcing ‘non-linear-models.R’: + Error: package or namespace load failed for ‘MCMCpack’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): + namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required Execution halted - ‘BayesianBiasCorrection.Rmd’ using ‘UTF-8’... OK - ‘NonNormalEffectSynthesis.Rmd’ using ‘UTF-8’... failed - ‘VideoVignette.Rmd’ using ‘UTF-8’... failed + ‘introduction-to-fido.Rmd’ using ‘UTF-8’... OK + ‘mitigating-pcrbias.Rmd’ using ‘UTF-8’... OK + ‘non-linear-models.Rmd’ using ‘UTF-8’... failed + ‘orthus.Rmd’ using ‘UTF-8’... OK + ‘picking_priors.Rmd’ using ‘UTF-8’... OK + ``` + +* checking installed package size ... NOTE + ``` + installed size is 106.3Mb + sub-directories of 1Mb or more: + data 4.0Mb + libs 100.5Mb ``` * checking re-building of vignette outputs ... NOTE ``` Error(s) in re-building vignettes: - --- re-building ‘BayesianBiasCorrection.Rmd’ using rmarkdown - - | | 0% - |====== | 9% - |============ | 18% - |=================== | 27% - |========================= | 36% - |=============================== | 45% - |====================================== | 54% - ... - Quitting from lines 158-164 [unnamed-chunk-9] (VideoVignette.Rmd) - Error: processing vignette 'VideoVignette.Rmd' failed with diagnostics: - Theme element `plot.margin` must have class . - --- failed re-building ‘VideoVignette.Rmd’ + --- re-building ‘introduction-to-fido.Rmd’ using rmarkdown + --- finished re-building ‘introduction-to-fido.Rmd’ - SUMMARY: processing the following files failed: - ‘NonNormalEffectSynthesis.Rmd’ ‘VideoVignette.Rmd’ + --- re-building ‘mitigating-pcrbias.Rmd’ using rmarkdown + --- finished re-building ‘mitigating-pcrbias.Rmd’ - Error: Vignette re-building failed. - Execution halted + --- re-building ‘non-linear-models.Rmd’ using rmarkdown ``` -# EvolutionaryGames +# flipr
-* Version: 0.1.2 -* GitHub: NA -* Source code: https://github.com/cran/EvolutionaryGames -* Date/Publication: 2022-08-29 00:10:02 UTC -* Number of recursive dependencies: 66 +* Version: 0.3.3 +* GitHub: https://github.com/LMJL-Alea/flipr +* Source code: https://github.com/cran/flipr +* Date/Publication: 2023-08-23 09:00:02 UTC +* Number of recursive dependencies: 106 -Run `revdepcheck::cloud_details(, "EvolutionaryGames")` for more info +Run `revdepcheck::cloud_details(, "flipr")` for more info
## Newly broken -* checking examples ... ERROR +* checking re-building of vignette outputs ... NOTE ``` - Running examples in ‘EvolutionaryGames-Ex.R’ failed - The error most likely occurred in: + Error(s) in re-building vignettes: + --- re-building ‘alternative.Rmd’ using rmarkdown + --- finished re-building ‘alternative.Rmd’ - > ### Name: phaseDiagram2S - > ### Title: Phase Diagram for two-player games with two strategies - > ### Aliases: phaseDiagram2S - > - > ### ** Examples - > - > A <- matrix(c(-1, 4, 0, 2), 2, 2, byrow=TRUE) - ... - ▆ - 1. └─EvolutionaryGames::phaseDiagram2S(...) - 2. ├─base::print(p + vField) - 3. └─ggplot2:::print.ggplot(p + vField) - 4. ├─ggplot2::ggplot_gtable(data) - 5. └─ggplot2:::ggplot_gtable.ggplot_built(data) - 6. └─ggplot2::calc_element("plot.margin", theme) - 7. └─cli::cli_abort(...) - 8. └─rlang::abort(...) - Execution halted + --- re-building ‘exactness.Rmd’ using rmarkdown + + Quitting from lines 142-177 [unnamed-chunk-1] (exactness.Rmd) + Error: processing vignette 'exactness.Rmd' failed with diagnostics: + subscript out of bounds + --- failed re-building ‘exactness.Rmd’ + + --- re-building ‘flipr.Rmd’ using rmarkdown ``` +## In both + * checking running R code from vignettes ... ERROR ``` Errors in running code in vignettes: - when running code in ‘UsingEvolutionaryGames.Rmd’ + when running code in ‘exactness.Rmd’ ... - > library(EvolutionaryGames) - > A <- matrix(c(-1, 4, 0, 2), 2, byrow = TRUE) + > library(flipr) - > phaseDiagram2S(A, Replicator, strategies = c("Hawk", - + "Dove")) + > load("../R/sysdata.rda") + Warning in readChar(con, 5L, useBytes = TRUE) : + cannot open compressed file '../R/sysdata.rda', probable reason 'No such file or directory' ... + cannot open compressed file '../R/sysdata.rda', probable reason 'No such file or directory' - > phaseDiagram2S(A, Replicator, strategies = c("Hawk", - + "Dove")) - - When sourcing ‘UsingEvolutionaryGames_pdf.R’: - Error: Theme element `plot.margin` must have class . + When sourcing ‘plausibility.R’: + Error: cannot open the connection Execution halted - ‘UsingEvolutionaryGames.Rmd’ using ‘UTF-8’... failed - ‘UsingEvolutionaryGames_pdf.Rmd’ using ‘UTF-8’... failed + ‘alternative.Rmd’ using ‘UTF-8’... OK + ‘exactness.Rmd’ using ‘UTF-8’... failed + ‘flipr.Rmd’ using ‘UTF-8’... failed + ‘plausibility.Rmd’ using ‘UTF-8’... failed ``` -* checking re-building of vignette outputs ... NOTE +* checking installed package size ... NOTE ``` - Error(s) in re-building vignettes: - --- re-building ‘UsingEvolutionaryGames.Rmd’ using rmarkdown + installed size is 11.0Mb + sub-directories of 1Mb or more: + doc 9.1Mb + libs 1.2Mb ``` -# EvoPhylo +# foqat
-* Version: 0.3.2 -* GitHub: https://github.com/tiago-simoes/EvoPhylo -* Source code: https://github.com/cran/EvoPhylo -* Date/Publication: 2022-11-03 17:00:02 UTC -* Number of recursive dependencies: 164 +* Version: 2.0.8.2 +* GitHub: https://github.com/tianshu129/foqat +* Source code: https://github.com/cran/foqat +* Date/Publication: 2023-09-30 06:10:02 UTC +* Number of recursive dependencies: 75 -Run `revdepcheck::cloud_details(, "EvoPhylo")` for more info +Run `revdepcheck::cloud_details(, "foqat")` for more info
## Newly broken -* checking examples ... ERROR +* checking running R code from vignettes ... ERROR ``` - Running examples in ‘EvoPhylo-Ex.R’ failed - The error most likely occurred in: + Errors in running code in vignettes: + when running code in ‘Plot_Functions.Rmd’ + ... + > paged_table(aqids, options = list(max.print = 10000, + + rows.print = 10, cols.print = 6)) + + > geom_ts(df = aqids, yl = c(3, 2), yr = 6, alist = c(3, + + 2), llist = 6, yllab = bquote(NO[x] ~ " " ~ (ppbv)), yrlab = bquote(O[3] ~ + + " " .... [TRUNCATED] - > ### Name: make_clusters - > ### Title: Estimate and plot character partitions - > ### Aliases: make_clusters plot.cluster_df - > - > ### ** Examples - > - > # See vignette("char-part") for how to use this ... - > # tSNE (3 dimensions; default is 2) - > cluster_df_tsne <- make_clusters(Dmatrix, k = 3, tsne = TRUE, - + tsne_dim = 2) - > - > # Plot clusters, plots divided into 2 rows, and increasing - > # overlap of text labels (default = 10) - > plot(cluster_df_tsne, nrow = 2, max.overlaps = 20) - Error in identicalUnits(x) : object is not a unit - Calls: ... assemble_guides -> guides_build -> unit.c -> identicalUnits + When sourcing ‘Plot_Functions.R’: + Error: attempt to set an attribute on NULL Execution halted + + ‘Air_Quality.Rmd’ using ‘UTF-8’... OK + ‘Atmospheric_Radiation.Rmd’ using ‘UTF-8’... OK + ‘Basic_Functions.Rmd’ using ‘UTF-8’... OK + ‘Particle_Size_Distribution.Rmd’ using ‘UTF-8’... OK + ‘Plot_Functions.Rmd’ using ‘UTF-8’... failed + ‘Trace_Gas_Chemistry.Rmd’ using ‘UTF-8’... OK ``` * checking re-building of vignette outputs ... NOTE ``` Error(s) in re-building vignettes: - --- re-building ‘char-part.Rmd’ using rmarkdown + --- re-building ‘Air_Quality.Rmd’ using rmarkdown + --- finished re-building ‘Air_Quality.Rmd’ + + --- re-building ‘Atmospheric_Radiation.Rmd’ using rmarkdown + --- finished re-building ‘Atmospheric_Radiation.Rmd’ + + --- re-building ‘Basic_Functions.Rmd’ using rmarkdown + --- finished re-building ‘Basic_Functions.Rmd’ + + --- re-building ‘Particle_Size_Distribution.Rmd’ using rmarkdown ``` -## In both +# forestly + +
+ +* Version: 0.1.1 +* GitHub: https://github.com/Merck/forestly +* Source code: https://github.com/cran/forestly +* Date/Publication: 2024-07-08 19:40:02 UTC +* Number of recursive dependencies: 84 + +Run `revdepcheck::cloud_details(, "forestly")` for more info + +
+ +## Newly broken * checking running R code from vignettes ... ERROR ``` Errors in running code in vignettes: - when running code in ‘char-part.Rmd’ + when running code in ‘forest-plot-static.Rmd’ ... - + collapse = TRUE, dpi = 300) - - > devtools::load_all(".") + Warning in grid.Call(C_textBounds, as.graphicsAnnot(x$label), x$x, x$y, : + conversion failure on 'Treatment← Favor →Placebo' in 'mbcsToSbcs': dot substituted for + Warning in grid.Call(C_textBounds, as.graphicsAnnot(x$label), x$x, x$y, : + conversion failure on 'Treatment← Favor →Placebo' in 'mbcsToSbcs': dot substituted for <86> + Warning in grid.Call(C_textBounds, as.graphicsAnnot(x$label), x$x, x$y, : + conversion failure on 'Treatment← Favor →Placebo' in 'mbcsToSbcs': dot substituted for <92> - When sourcing ‘char-part.R’: - Error: Could not find a root 'DESCRIPTION' file that starts with '^Package' in - '/tmp/RtmpjL0Rwa/file19d43c89cd22/vignettes'. - ... - ℹ Are you in your project directory and does your project have a 'DESCRIPTION' - file? + When sourcing ‘forest-plot-static.R’: + Error: object is not a unit Execution halted - ‘char-part.Rmd’ using ‘UTF-8’... failed - ‘data_treatment.Rmd’ using ‘UTF-8’... OK - ‘fbd-params.Rmd’ using ‘UTF-8’... failed - ‘offset_handling.Rmd’ using ‘UTF-8’... failed - ‘rates-selection_BEAST2.Rmd’ using ‘UTF-8’... failed - ‘rates-selection_MrBayes.Rmd’ using ‘UTF-8’... failed + ‘forest-plot-static.Rmd’ using ‘UTF-8’... failed + ‘forestly-cran.Rmd’ using ‘UTF-8’... OK ``` -* checking installed package size ... NOTE +* checking re-building of vignette outputs ... NOTE ``` - installed size is 6.8Mb - sub-directories of 1Mb or more: - data 2.5Mb - doc 1.6Mb - extdata 2.4Mb + Error(s) in re-building vignettes: + --- re-building ‘forest-plot-static.Rmd’ using rmarkdown ``` -# evprof +# frailtyEM
-* Version: 1.1.2 -* GitHub: https://github.com/mcanigueral/evprof -* Source code: https://github.com/cran/evprof -* Date/Publication: 2024-03-14 14:50:05 UTC -* Number of recursive dependencies: 93 +* Version: 1.0.1 +* GitHub: https://github.com/tbalan/frailtyEM +* Source code: https://github.com/cran/frailtyEM +* Date/Publication: 2019-09-22 13:00:10 UTC +* Number of recursive dependencies: 78 -Run `revdepcheck::cloud_details(, "evprof")` for more info +Run `revdepcheck::cloud_details(, "frailtyEM")` for more info
@@ -4960,116 +3961,108 @@ Run `revdepcheck::cloud_details(, "evprof")` for more info * checking examples ... ERROR ``` - Running examples in ‘evprof-Ex.R’ failed + Running examples in ‘frailtyEM-Ex.R’ failed The error most likely occurred in: - > ### Name: plot_energy_models - > ### Title: Compare density of estimated energy with density of real energy - > ### vector - > ### Aliases: plot_energy_models + > ### Name: summary.emfrail + > ### Title: Summary for 'emfrail' objects + > ### Aliases: summary.emfrail > > ### ** Examples > + > data("bladder") ... - 7. └─cowplot:::as_gtable.default(x) - 8. ├─cowplot::as_grob(plot) - 9. └─cowplot:::as_grob.ggplot(plot) - 10. └─ggplot2::ggplotGrob(plot) - 11. ├─ggplot2::ggplot_gtable(ggplot_build(x)) - 12. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) - 13. └─ggplot2::calc_element("plot.margin", theme) - 14. └─cli::cli_abort(...) - 15. └─rlang::abort(...) + filter + + The following object is masked from ‘package:graphics’: + + layout + + > ggplotly(pl2) + Error in pm[[2]] : subscript out of bounds + Calls: ggplotly -> ggplotly.ggplot -> gg2list Execution halted ``` -* checking tests ... ERROR +## In both + +* checking LazyData ... NOTE ``` - Running ‘spelling.R’ - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > # This file is part of the standard setup for testthat. - > # It is recommended that you do not modify it. - > # - > # Where should you do additional test configuration? - > # Learn more about the roles of various files in: - > # * https://r-pkgs.org/tests.html - ... - 10. └─ggplot2::ggplotGrob(plot) - 11. ├─ggplot2::ggplot_gtable(ggplot_build(x)) - 12. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) - 13. └─ggplot2::calc_element("plot.margin", theme) - 14. └─cli::cli_abort(...) - 15. └─rlang::abort(...) - - [ FAIL 2 | WARN 0 | SKIP 4 | PASS 48 ] - Error: Test failures - Execution halted + 'LazyData' is specified without a 'data' directory ``` -## In both - -* checking installed package size ... NOTE +* checking re-building of vignette outputs ... NOTE ``` - installed size is 5.1Mb - sub-directories of 1Mb or more: - data 3.5Mb - doc 1.2Mb + Error(s) in re-building vignettes: + --- re-building ‘frailtyEM_manual.Rnw’ using Sweave + Loading required package: survival + Loading required package: gridExtra + Warning: The `` argument of `guides()` cannot be `FALSE`. Use + "none" instead as of ggplot2 3.3.4. + Warning: Removed 2 rows containing missing values or values outside + the scale range (`geom_path()`). + Warning in data("kidney") : data set ‘kidney’ not found + Warning in emfrail(Surv(time, status) ~ age + sex + cluster(id), data = kidney, : + ... + l.179 \RequirePackage{grfext}\relax + ^^M + ! ==> Fatal error occurred, no output PDF file produced! + --- failed re-building ‘frailtyEM_manual.Rnw’ + + SUMMARY: processing the following file failed: + ‘frailtyEM_manual.Rnw’ + + Error: Vignette re-building failed. + Execution halted ``` -# expirest +# funcharts
-* Version: 0.1.6 -* GitHub: https://github.com/piusdahinden/expirest -* Source code: https://github.com/cran/expirest -* Date/Publication: 2024-03-25 16:30:02 UTC -* Number of recursive dependencies: 46 +* Version: 1.4.1 +* GitHub: https://github.com/unina-sfere/funcharts +* Source code: https://github.com/cran/funcharts +* Date/Publication: 2024-02-22 08:50:02 UTC +* Number of recursive dependencies: 123 -Run `revdepcheck::cloud_details(, "expirest")` for more info +Run `revdepcheck::cloud_details(, "funcharts")` for more info
## Newly broken -* checking tests ... ERROR +* checking examples ... ERROR ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(expirest) - > - > test_check("expirest") - [ FAIL 2 | WARN 0 | SKIP 0 | PASS 1121 ] - - ══ Failed tests ════════════════════════════════════════════════════════════════ - ... - 9. └─ggplot2:::plot.ggplot(x = x$Graph, ...) - 10. ├─ggplot2::ggplot_gtable(data) - 11. └─ggplot2:::ggplot_gtable.ggplot_built(data) - 12. └─ggplot2::calc_element("plot.margin", theme) - 13. └─cli::cli_abort(...) - 14. └─rlang::abort(...) - - [ FAIL 2 | WARN 0 | SKIP 0 | PASS 1121 ] - Error: Test failures - Execution halted + Running examples in ‘funcharts-Ex.R’ failed + The error most likely occurred in: + + > ### Name: pca_mfd + > ### Title: Multivariate functional principal components analysis + > ### Aliases: pca_mfd + > + > ### ** Examples + > + > library(funcharts) + > mfdobj <- data_sim_mfd() + > pca_obj <- pca_mfd(mfdobj) + > plot_pca_mfd(pca_obj) + Error in identicalUnits(x) : object is not a unit + Calls: ... assemble_guides -> guides_build -> unit.c -> identicalUnits + Execution halted ``` -# explore +# geomtextpath
-* Version: 1.3.0 -* GitHub: https://github.com/rolkra/explore -* Source code: https://github.com/cran/explore -* Date/Publication: 2024-04-15 15:50:09 UTC -* Number of recursive dependencies: 97 +* Version: 0.1.4 +* GitHub: https://github.com/AllanCameron/geomtextpath +* Source code: https://github.com/cran/geomtextpath +* Date/Publication: 2024-06-13 06:40:02 UTC +* Number of recursive dependencies: 94 -Run `revdepcheck::cloud_details(, "explore")` for more info +Run `revdepcheck::cloud_details(, "geomtextpath")` for more info
@@ -5077,154 +4070,172 @@ Run `revdepcheck::cloud_details(, "explore")` for more info * checking examples ... ERROR ``` - Running examples in ‘explore-Ex.R’ failed + Running examples in ‘geomtextpath-Ex.R’ failed The error most likely occurred in: - > ### Name: explore_targetpct - > ### Title: Explore variable + binary target (values 0/1) - > ### Aliases: explore_targetpct + > ### Name: geom_textsf + > ### Title: Visualise sf objects with labels + > ### Aliases: geom_textsf geom_labelsf > > ### ** Examples > - > iris$target01 <- ifelse(iris$Species == "versicolor",1,0) + > ggplot(waterways) + ... - Backtrace: - ▆ - 1. ├─base (local) ``(x) - 2. └─ggplot2:::print.ggplot(x) - 3. ├─ggplot2::ggplot_gtable(data) - 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) - 5. └─ggplot2::calc_element("plot.margin", theme) - 6. └─cli::cli_abort(...) - 7. └─rlang::abort(...) + 19. │ ├─rlang::inject(self$draw_panel(data, panel_params, coord, !!!params)) + 20. │ └─self$draw_panel(data, panel_params, coord, na.rm = FALSE, legend = "other") + 21. │ └─geomtextpath (local) draw_panel(...) + 22. │ └─geomtextpath:::sf_textgrob(...) + 23. └─base::.handleSimpleError(...) + 24. └─rlang (local) h(simpleError(msg, call)) + 25. └─handlers[[1L]](cnd) + 26. └─cli::cli_abort(...) + 27. └─rlang::abort(...) Execution halted ``` -* checking running R code from vignettes ... ERROR +* checking tests ... ERROR ``` - Errors in running code in vignettes: - when running code in ‘explore-mtcars.Rmd’ - ... - > data %>% explain_tree(target = highmpg) - - > data %>% explore(wt, target = highmpg) - - > data %>% explore(wt, target = highmpg, split = FALSE) - Warning: `position_dodge()` requires non-overlapping x intervals. - + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(geomtextpath) + Loading required package: ggplot2 + > + > test_check("geomtextpath") + [ FAIL 1 | WARN 0 | SKIP 4 | PASS 463 ] + ... - ‘explain.Rmd’ using ‘UTF-8’... OK - ‘explore-mtcars.Rmd’ using ‘UTF-8’... failed - ‘explore-penguins.Rmd’ using ‘UTF-8’... OK - ‘explore-titanic.Rmd’ using ‘UTF-8’... OK - ‘explore.Rmd’ using ‘UTF-8’... failed - ‘predict.Rmd’ using ‘UTF-8’... OK - ‘report-target.Rmd’ using ‘UTF-8’... OK - ‘report-targetpct.Rmd’ using ‘UTF-8’... failed - ‘report.Rmd’ using ‘UTF-8’... OK - ‘tips-tricks.Rmd’ using ‘UTF-8’... OK + ══ Failed tests ════════════════════════════════════════════════════════════════ + ── Error ('test-sf.R:91:3'): We can make grobs from sf features ──────────────── + Error in `(x$boxlinewidth %||% defaults$linewidth[type_ind]) * 3.779528`: non-numeric argument to binary operator + Backtrace: + ▆ + 1. └─geomtextpath:::sf_textgrob(river, as_textbox = TRUE) at test-sf.R:91:3 + + [ FAIL 1 | WARN 0 | SKIP 4 | PASS 463 ] + Error: Test failures + Execution halted ``` -* checking re-building of vignette outputs ... NOTE +# GGally + +
+ +* Version: 2.2.1 +* GitHub: https://github.com/ggobi/ggally +* Source code: https://github.com/cran/GGally +* Date/Publication: 2024-02-14 00:53:32 UTC +* Number of recursive dependencies: 145 + +Run `revdepcheck::cloud_details(, "GGally")` for more info + +
+ +## Newly broken + +* checking tests ... ERROR ``` - Error(s) in re-building vignettes: - --- re-building ‘abtest.Rmd’ using rmarkdown + Running ‘spelling.R’ + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > if (requireNamespace("testthat", quietly = TRUE)) { + + library(testthat) + + library(GGally) + + + + test_check("GGally") + + } + ... + `expected` is a character vector ('tip') + ── Failure ('test-ggsurv.R:26:3'): multiple ──────────────────────────────────── + !is.null(a$labels$group) is not TRUE + + `actual`: FALSE + `expected`: TRUE + + [ FAIL 3 | WARN 1 | SKIP 26 | PASS 477 ] + Error: Test failures + Execution halted ``` -# ezplot +# gganimate
-* Version: 0.7.13 -* GitHub: NA -* Source code: https://github.com/cran/ezplot -* Date/Publication: 2024-01-28 11:30:05 UTC -* Number of recursive dependencies: 109 +* Version: 1.0.9 +* GitHub: https://github.com/thomasp85/gganimate +* Source code: https://github.com/cran/gganimate +* Date/Publication: 2024-02-27 14:00:03 UTC +* Number of recursive dependencies: 97 -Run `revdepcheck::cloud_details(, "ezplot")` for more info +Run `revdepcheck::cloud_details(, "gganimate")` for more info
## Newly broken -* checking examples ... ERROR +* checking tests ... ERROR ``` - Running examples in ‘ezplot-Ex.R’ failed - The error most likely occurred in: - - > ### Name: bar_plot - > ### Title: bar_plot - > ### Aliases: bar_plot - > - > ### ** Examples - > - > library(tsibble) + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(gganimate) + Loading required package: ggplot2 + > + > test_check("gganimate") + [ FAIL 1 | WARN 3 | SKIP 1 | PASS 5 ] + ... - 11. │ └─base::withCallingHandlers(...) - 12. └─ggplot2 (local) f(l = layers[[i]], d = data[[i]]) - 13. └─l$compute_geom_2(d, theme = plot$theme) - 14. └─ggplot2 (local) compute_geom_2(..., self = self) - 15. └─self$geom$use_defaults(...) - 16. └─ggplot2 (local) use_defaults(..., self = self) - 17. └─ggplot2:::check_aesthetics(new_params, nrow(data)) - 18. └─cli::cli_abort(...) - 19. └─rlang::abort(...) - Execution halted + 3. ├─gganimate::animate(p, nframes = 2) at test-anim_save.R:14:5 + 4. └─gganimate:::animate.gganim(p, nframes = 2) + 5. └─args$renderer(frames_vars$frame_source, args$fps) + 6. └─gganimate:::png_dim(frames[1]) + 7. └─cli::cli_abort("Provided file ({file}) does not exist") + 8. └─rlang::abort(...) + + [ FAIL 1 | WARN 3 | SKIP 1 | PASS 5 ] + Error: Test failures + Execution halted ``` * checking running R code from vignettes ... ERROR ``` Errors in running code in vignettes: - when running code in ‘bar_plot.Rmd’ + when running code in ‘gganimate.Rmd’ ... + Theme element `panel.grid.major.y` is missing + Theme element `panel.grid.major.x` is missing + Warning: Failed to plot frame + Caused by error in `UseMethod()`: + ! no applicable method for 'element_grob' applied to an object of class "NULL" - > bar_plot(ansett, "year(Week)", "Passengers", size = 16) - - When sourcing ‘bar_plot.R’: - Error: Problem while setting up geom aesthetics. - ℹ Error occurred in the 1st layer. - Caused by error in `check_aesthetics()`: - ... - Caused by error in `check_aesthetics()`: - ! Aesthetics must be either length 1 or the same as the data (9). - ✖ Fix the following mappings: `width`. + When sourcing ‘gganimate.R’: + Error: Provided file (/tmp/RtmpingcHf/165822e22fea/gganim_plot0001.png) does + not exist Execution halted - ‘bar_plot.Rmd’ using ‘UTF-8’... failed - ‘basics.Rmd’ using ‘UTF-8’... failed - ‘line_plot.Rmd’ using ‘UTF-8’... OK - ‘overview.Rmd’ using ‘UTF-8’... failed - ‘variable_plot.Rmd’ using ‘UTF-8’... OK + ‘gganimate.Rmd’ using ‘UTF-8’... failed ``` * checking re-building of vignette outputs ... NOTE ``` Error(s) in re-building vignettes: - --- re-building ‘bar_plot.Rmd’ using rmarkdown - - Quitting from lines 28-29 [unnamed-chunk-2] (bar_plot.Rmd) - Error: processing vignette 'bar_plot.Rmd' failed with diagnostics: - Problem while setting up geom aesthetics. - ℹ Error occurred in the 1st layer. - Caused by error in `check_aesthetics()`: - ! Aesthetics must be either length 1 or the same as the data (6). - ✖ Fix the following mappings: `width`. - --- failed re-building ‘bar_plot.Rmd’ - - --- re-building ‘basics.Rmd’ using rmarkdown + --- re-building ‘gganimate.Rmd’ using rmarkdown ``` -# fable.prophet +# ggbrain
-* Version: 0.1.0 -* GitHub: https://github.com/mitchelloharawild/fable.prophet -* Source code: https://github.com/cran/fable.prophet -* Date/Publication: 2020-08-20 09:30:03 UTC -* Number of recursive dependencies: 114 +* Version: 0.8.1 +* GitHub: https://github.com/michaelhallquist/ggbrain +* Source code: https://github.com/cran/ggbrain +* Date/Publication: 2023-03-21 18:00:05 UTC +* Number of recursive dependencies: 74 -Run `revdepcheck::cloud_details(, "fable.prophet")` for more info +Run `revdepcheck::cloud_details(, "ggbrain")` for more info
@@ -5233,46 +4244,75 @@ Run `revdepcheck::cloud_details(, "fable.prophet")` for more info * checking running R code from vignettes ... ERROR ``` Errors in running code in vignettes: - when running code in ‘intro.Rmd’ + when running code in ‘ggbrain_introduction.Rmd’ ... - 9 Domestic mdl 2019 Dec sample[5000] 5335212. - 10 Domestic mdl 2020 Jan sample[5000] 4888063. - # ℹ 62 more rows - > fc %>% autoplot(lax_passengers) + > gg_obj <- gg_base + geom_brain(definition = "underlay", + + fill_scale = scale_fill_gradient(low = "grey8", high = "grey62"), + + show_legend .... [TRUNCATED] - When sourcing ‘intro.R’: - Error: unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, "black", TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), NULL, list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), 5.5, c(5.5, 5.5, 5.5, 5.5), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.75, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, - NULL, NULL, NULL, 1, 90, NULL, c(0, 2.75, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 1, NULL, NULL, NULL, c(0, 2.2, 0, 0), NULL, TRUE), NULL, lis + > gg_obj$render() + + ... + + > plot(gg_obj) + + When sourcing ‘ggbrain_labels.R’: + Error: attempt to set an attribute on NULL Execution halted - ‘intro.Rmd’ using ‘UTF-8’... failed + ‘ggbrain_aesthetics.Rmd’ using ‘UTF-8’... OK + ‘ggbrain_introduction.Rmd’ using ‘UTF-8’... failed + ‘ggbrain_labels.Rmd’ using ‘UTF-8’... failed ``` * checking re-building of vignette outputs ... NOTE ``` Error(s) in re-building vignettes: - --- re-building ‘intro.Rmd’ using rmarkdown + ... + --- re-building ‘ggbrain_aesthetics.Rmd’ using rmarkdown + --- finished re-building ‘ggbrain_aesthetics.Rmd’ + + --- re-building ‘ggbrain_introduction.Rmd’ using rmarkdown + + Quitting from lines 238-239 [unnamed-chunk-16] (ggbrain_introduction.Rmd) + Error: processing vignette 'ggbrain_introduction.Rmd' failed with diagnostics: + attempt to set an attribute on NULL + ... + Quitting from lines 47-54 [unnamed-chunk-2] (ggbrain_labels.Rmd) + Error: processing vignette 'ggbrain_labels.Rmd' failed with diagnostics: + attempt to set an attribute on NULL + --- failed re-building ‘ggbrain_labels.Rmd’ + + SUMMARY: processing the following files failed: + ‘ggbrain_introduction.Rmd’ ‘ggbrain_labels.Rmd’ + + Error: Vignette re-building failed. + Execution halted ``` ## In both -* checking LazyData ... NOTE +* checking installed package size ... NOTE ``` - 'LazyData' is specified without a 'data' directory + installed size is 10.6Mb + sub-directories of 1Mb or more: + doc 3.0Mb + extdata 1.6Mb + libs 5.3Mb ``` -# fabletools +# ggbreak
-* Version: 0.4.2 -* GitHub: https://github.com/tidyverts/fabletools -* Source code: https://github.com/cran/fabletools -* Date/Publication: 2024-04-22 11:22:41 UTC -* Number of recursive dependencies: 106 +* Version: 0.1.2 +* GitHub: https://github.com/YuLab-SMU/ggbreak +* Source code: https://github.com/cran/ggbreak +* Date/Publication: 2023-06-26 05:40:02 UTC +* Number of recursive dependencies: 64 -Run `revdepcheck::cloud_details(, "fabletools")` for more info +Run `revdepcheck::cloud_details(, "ggbreak")` for more info
@@ -5280,65 +4320,61 @@ Run `revdepcheck::cloud_details(, "fabletools")` for more info * checking examples ... ERROR ``` - Running examples in ‘fabletools-Ex.R’ failed + Running examples in ‘ggbreak-Ex.R’ failed The error most likely occurred in: - > ### Name: autoplot.fbl_ts - > ### Title: Plot a set of forecasts - > ### Aliases: autoplot.fbl_ts autolayer.fbl_ts + > ### Name: scale_wrap + > ### Title: scale-wrap + > ### Aliases: scale_wrap > > ### ** Examples > - > ## Don't show: - ... - > library(fable) - > library(tsibbledata) - > fc <- aus_production %>% model(ets = ETS(log(Beer) ~ error("M") + trend("Ad") + - + season("A"))) %>% forecast(h = "3 years") - > fc %>% autoplot(aus_production) - Error in use_defaults(..., self = self) : - unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, "black", TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), NULL, list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), 5.5, c(5.5, 5.5, 5.5, 5.5), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.75, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, - NULL, NULL, NULL, 1, 90, NULL, c(0, 2.75, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 1, NULL, NULL, NULL, c(0, 2.2, 0, 0), NULL, TRUE), NULL, l - Calls: ... -> -> compute_geom_2 -> + > library(ggplot2) + > library(ggbreak) + > p <- ggplot(economics, aes(x=date, y = unemploy, colour = uempmed)) + + + geom_line() + > p + scale_wrap(n=4) + Error in identicalUnits(x) : object is not a unit + Calls: -> print.ggwrap Execution halted ``` -* checking tests ... ERROR +* checking running R code from vignettes ... ERROR ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(dplyr) - - Attaching package: 'dplyr' - - The following object is masked from 'package:testthat': - - ... - 24. └─base::Map(...) - 25. └─base::mapply(FUN = f, ..., SIMPLIFY = FALSE) - 26. └─ggplot2 (local) ``(layer = dots[[1L]][[1L]], df = dots[[2L]][[1L]]) - 27. └─layer$compute_geom_2(key, single_params, theme) - 28. └─ggplot2 (local) compute_geom_2(..., self = self) - 29. └─self$geom$use_defaults(...) - - [ FAIL 2 | WARN 0 | SKIP 1 | PASS 269 ] - Error: Test failures - Execution halted + Errors in running code in vignettes: + when running code in ‘ggbreak.Rmd’ + ... + > p1 + p2 + + > p2 + scale_x_break(c(18, 21)) + + > p1 + scale_x_break(c(7, 17), scales = 1.5) + scale_x_break(c(18, + + 21), scales = 2) + + When sourcing ‘ggbreak.R’: + Error: second argument must be a list + Execution halted + + ‘ggbreak.Rmd’ using ‘UTF-8’... failed ``` -# factoextra +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘ggbreak.Rmd’ using rmarkdown + ``` + +# ggdark
-* Version: 1.0.7 -* GitHub: https://github.com/kassambara/factoextra -* Source code: https://github.com/cran/factoextra -* Date/Publication: 2020-04-01 21:20:02 UTC -* Number of recursive dependencies: 126 +* Version: 0.2.1 +* GitHub: NA +* Source code: https://github.com/cran/ggdark +* Date/Publication: 2019-01-11 17:30:06 UTC +* Number of recursive dependencies: 46 -Run `revdepcheck::cloud_details(, "factoextra")` for more info +Run `revdepcheck::cloud_details(, "ggdark")` for more info
@@ -5346,40 +4382,72 @@ Run `revdepcheck::cloud_details(, "factoextra")` for more info * checking examples ... ERROR ``` - Running examples in ‘factoextra-Ex.R’ failed + Running examples in ‘ggdark-Ex.R’ failed The error most likely occurred in: - > ### Name: eigenvalue - > ### Title: Extract and visualize the eigenvalues/variances of dimensions - > ### Aliases: eigenvalue get_eig get_eigenvalue fviz_eig fviz_screeplot + > ### Name: dark_mode + > ### Title: Activate dark mode on a 'ggplot2' theme + > ### Aliases: dark_mode > > ### ** Examples > - > # Principal Component Analysis + > library(ggplot2) ... - 11. │ └─base::withCallingHandlers(...) - 12. └─ggplot2 (local) f(l = layers[[i]], d = data[[i]]) - 13. └─l$compute_geom_2(d, theme = plot$theme) - 14. └─ggplot2 (local) compute_geom_2(..., self = self) - 15. └─self$geom$use_defaults(...) - 16. └─ggplot2 (local) use_defaults(..., self = self) - 17. └─ggplot2:::check_aesthetics(new_params, nrow(data)) - 18. └─cli::cli_abort(...) - 19. └─rlang::abort(...) + > + > p1 <- ggplot(iris, aes(Sepal.Width, Sepal.Length, color = Species)) + + + geom_point() + > + > p1 # theme returned by theme_get() + > p1 + dark_mode() # activate dark mode on theme returned by theme_get() + Error in match(x, table, nomatch = 0L) : + 'match' requires vector arguments + Calls: dark_mode -> %in% Execution halted ``` -# faux +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(ggdark) + > + > test_check("ggdark") + [ FAIL 1 | WARN 0 | SKIP 0 | PASS 0 ] + + ══ Failed tests ════════════════════════════════════════════════════════════════ + ... + ── Error ('test_dark_mode.R:10:1'): (code run outside of `test_that()`) ──────── + Error in `match(x, table, nomatch = 0L)`: 'match' requires vector arguments + Backtrace: + ▆ + 1. └─ggdark::dark_mode(light_theme) at test_dark_mode.R:10:1 + 2. └─geoms[["GeomPoint"]]$default_aes$colour %in% ... + + [ FAIL 1 | WARN 0 | SKIP 0 | PASS 0 ] + Error: Test failures + Execution halted + ``` + +## In both + +* checking LazyData ... NOTE + ``` + 'LazyData' is specified without a 'data' directory + ``` + +# ggdist
-* Version: 1.2.1 -* GitHub: https://github.com/debruine/faux -* Source code: https://github.com/cran/faux -* Date/Publication: 2023-04-20 07:00:11 UTC -* Number of recursive dependencies: 131 +* Version: 3.3.2 +* GitHub: https://github.com/mjskay/ggdist +* Source code: https://github.com/cran/ggdist +* Date/Publication: 2024-03-05 05:30:23 UTC +* Number of recursive dependencies: 127 -Run `revdepcheck::cloud_details(, "faux")` for more info +Run `revdepcheck::cloud_details(, "ggdist")` for more info
@@ -5387,124 +4455,126 @@ Run `revdepcheck::cloud_details(, "faux")` for more info * checking examples ... ERROR ``` - Running examples in ‘faux-Ex.R’ failed + Running examples in ‘ggdist-Ex.R’ failed The error most likely occurred in: - > ### Name: beta2norm - > ### Title: Convert beta to normal - > ### Aliases: beta2norm + > ### Name: Pr_ + > ### Title: Probability expressions in ggdist aesthetics + > ### Aliases: Pr_ p_ > > ### ** Examples > - > + > library(ggplot2) ... - Backtrace: - ▆ - 1. └─ggExtra::ggMarginal(g, type = "histogram") - 2. └─ggplot2::ggplotGrob(scatP) - 3. ├─ggplot2::ggplot_gtable(ggplot_build(x)) - 4. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) - 5. └─ggplot2::calc_element("plot.margin", theme) - 6. └─cli::cli_abort(...) - 7. └─rlang::abort(...) + + ) + > + > # map density onto alpha of the fill + > ggplot(df, aes(y = name, xdist = d)) + + + stat_slabinterval(aes(alpha = !!p_(x))) + Error in use_defaults(..., self = self) : + unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, "black", TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), list(NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), 5.5, c(5.5, 5.5, 5.5, 5.5), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.75, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, + NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, 90, NULL, c(0, 2.75, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL + Calls: ... -> -> compute_geom_2 -> Execution halted ``` -* checking re-building of vignette outputs ... NOTE +* checking tests ... ERROR ``` - Error(s) in re-building vignettes: - --- re-building ‘codebook.Rmd’ using rmarkdown - --- finished re-building ‘codebook.Rmd’ - - --- re-building ‘continuous.Rmd’ using rmarkdown + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > # This file is part of the standard setup for testthat. + > # It is recommended that you do not modify it. + > # + > # Where should you do additional test configuration? + > # Learn more about the roles of various files in: + > # * https://r-pkgs.org/testing-design.html#sec-tests-files-overview + > # * https://testthat.r-lib.org/articles/special-files.html + ... + • test.stat_sample_slabinterval/nas-with-na-rm-true.svg + • test.subguide/dots-subguide-with-side-vertical.svg + • test.subguide/integer-subguide-with-zero-range.svg + • test.subguide/slab-subguide-with-inside-labels-vertical.svg + • test.subguide/slab-subguide-with-outside-labels-vert.svg + • test.subguide/slab-subguide-with-outside-labels.svg + • test.subguide/slab-subguide-with-side-vertical.svg + • test.theme_ggdist/facet-titles-on-left.svg + Error: Test failures + Execution halted ``` -## In both - -* checking running R code from vignettes ... ERROR +* checking re-building of vignette outputs ... NOTE ``` - Errors in running code in vignettes: - when running code in ‘norta.Rmd’ - ... - > p <- ggplot(dat, aes(uniform_var, poisson_var)) + - + geom_point() + geom_smooth() - - > ggMarginal(p, type = "histogram") - `geom_smooth()` using method = 'gam' and formula = 'y ~ s(x, bs = "cs")' - `geom_smooth()` using method = 'gam' and formula = 'y ~ s(x, bs = "cs")' + Error(s) in re-building vignettes: + --- re-building ‘dotsinterval.Rmd’ using rmarkdown + Warning in hook_png(..., cmd = "pngquant", post_process = function(x) { : + cannot find pngquant; please install and put it in PATH + Warning in hook_png(..., cmd = "pngquant", post_process = function(x) { : + cannot find pngquant; please install and put it in PATH + Quitting from lines 49-161 [dotsinterval_components] (dotsinterval.Rmd) + Error: processing vignette 'dotsinterval.Rmd' failed with diagnostics: + Problem while setting up geom aesthetics. ... - Error: Theme element `plot.margin` must have class . - Execution halted - ‘codebook.Rmd’ using ‘UTF-8’... OK - ‘continuous.Rmd’ using ‘UTF-8’... OK - ‘contrasts.Rmd’ using ‘UTF-8’... OK - ‘norta.Rmd’ using ‘UTF-8’... failed - ‘rnorm_multi.Rmd’ using ‘UTF-8’... OK - ‘sim_design.Rmd’ using ‘UTF-8’... OK - ‘sim_df.Rmd’ using ‘UTF-8’... OK + --- re-building ‘freq-uncertainty-vis.Rmd’ using rmarkdown + Warning in hook_png(..., cmd = "pngquant", post_process = function(x) { : + cannot find pngquant; please install and put it in PATH + Warning in hook_png(..., cmd = "pngquant", post_process = function(x) { : + cannot find pngquant; please install and put it in PATH + Warning in hook_png(..., cmd = "pngquant", post_process = function(x) { : + cannot find pngquant; please install and put it in PATH + Warning in hook_png(..., cmd = "pngquant", post_process = function(x) { : + cannot find pngquant; please install and put it in PATH ``` -# fddm - -
- -* Version: 0.5-2 -* GitHub: https://github.com/rtdists/fddm -* Source code: https://github.com/cran/fddm -* Date/Publication: 2022-09-09 19:02:54 UTC -* Number of recursive dependencies: 86 - -Run `revdepcheck::cloud_details(, "fddm")` for more info - -
- -## Newly broken +## In both * checking running R code from vignettes ... ERROR ``` Errors in running code in vignettes: - when running code in ‘benchmark.Rmd’ + when running code in ‘dotsinterval.Rmd’ ... - > ma <- max(bm_vec[, (t_idx + 1):(ncol(bm_vec) - 4)]) - - > ggplot(mbm_vec, aes(x = factor(FuncName, levels = Names_vec), - + y = time, color = factor(FuncName, levels = Names_vec), fill = factor(FuncName, .... [TRUNCATED] - Warning: The dot-dot notation (`..y..`) was deprecated in ggplot2 3.4.0. - ℹ Please use `after_stat(y)` instead. + + xdist = dist)) + geom_hline(yintercept = 0:1, color = "gray95") + + + stat_dotsin .... [TRUNCATED] + When sourcing ‘dotsinterval.R’: + Error: Problem while setting up geom aesthetics. + ℹ Error occurred in the 2nd layer. + Caused by error in `use_defaults()`: ... - - When sourcing ‘pfddm.R’: - Error: Not a unit object + ℹ Error occurred in the 1st layer. + Caused by error in `use_defaults()`: + ! unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, "black", TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), list(NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), 5.5, c(5.5, 5.5, 5.5, 5.5), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(7, 0, 0, 0), NULL, FALSE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, + NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, 90, NULL, c(0, 7, 0, 0), NULL, FALSE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TR Execution halted - ‘benchmark.Rmd’ using ‘UTF-8’... failed - ‘example.Rmd’ using ‘UTF-8’... OK - ‘math.Rmd’ using ‘UTF-8’... OK - ‘pfddm.Rmd’ using ‘UTF-8’... failed - ‘validity.Rmd’ using ‘UTF-8’... OK + ‘dotsinterval.Rmd’ using ‘UTF-8’... failed + ‘freq-uncertainty-vis.Rmd’ using ‘UTF-8’... failed + ‘lineribbon.Rmd’ using ‘UTF-8’... failed + ‘slabinterval.Rmd’ using ‘UTF-8’... failed ``` -## In both - -* checking C++ specification ... NOTE +* checking installed package size ... NOTE ``` - Specified C++11: please drop specification unless essential + installed size is 5.4Mb + sub-directories of 1Mb or more: + R 1.5Mb + doc 1.3Mb + help 1.5Mb ``` -# fdrci +# ggDoubleHeat
-* Version: 2.4 -* GitHub: NA -* Source code: https://github.com/cran/fdrci -* Date/Publication: 2022-10-18 02:12:32 UTC -* Number of recursive dependencies: 81 +* Version: 0.1.2 +* GitHub: https://github.com/PursuitOfDataScience/ggDoubleHeat +* Source code: https://github.com/cran/ggDoubleHeat +* Date/Publication: 2023-08-24 21:00:04 UTC +* Number of recursive dependencies: 58 -Run `revdepcheck::cloud_details(, "fdrci")` for more info +Run `revdepcheck::cloud_details(, "ggDoubleHeat")` for more info
@@ -5512,40 +4582,40 @@ Run `revdepcheck::cloud_details(, "fdrci")` for more info * checking examples ... ERROR ``` - Running examples in ‘fdrci-Ex.R’ failed + Running examples in ‘ggDoubleHeat-Ex.R’ failed The error most likely occurred in: - > ### Name: FDRplot - > ### Title: Plot results of FDR table generated by fdrTbl() - > ### Aliases: FDRplot + > ### Name: geom_heat_circle + > ### Title: Heatcircle + > ### Aliases: geom_heat_circle > > ### ** Examples > - > ss = 100 + > ... - Backtrace: - ▆ - 1. ├─base (local) ``(x) - 2. └─ggplot2:::print.ggplot(x) - 3. ├─ggplot2::ggplot_gtable(data) - 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) - 5. └─ggplot2::calc_element("plot.margin", theme) - 6. └─cli::cli_abort(...) - 7. └─rlang::abort(...) + + y = rep(c("d", "e", "f"), 3), + + outside_values = rep(c(1,5,7),3), + + inside_values = rep(c(2,3,4),3)) + > + > ggplot(data, aes(x,y)) + + + geom_heat_circle(outside = outside_values, + + inside = inside_values) + Error in names(labels) <- `*vtmp*` : attempt to set an attribute on NULL + Calls: +.gg ... ggplot_add -> ggplot_add.new_aes -> bump_aes_labels Execution halted ``` -# ffp +# ggeasy
-* Version: 0.2.2 -* GitHub: https://github.com/Reckziegel/FFP -* Source code: https://github.com/cran/ffp -* Date/Publication: 2022-09-29 15:10:06 UTC -* Number of recursive dependencies: 107 +* Version: 0.1.4 +* GitHub: https://github.com/jonocarroll/ggeasy +* Source code: https://github.com/cran/ggeasy +* Date/Publication: 2023-03-12 10:00:23 UTC +* Number of recursive dependencies: 94 -Run `revdepcheck::cloud_details(, "ffp")` for more info +Run `revdepcheck::cloud_details(, "ggeasy")` for more info
@@ -5553,62 +4623,26 @@ Run `revdepcheck::cloud_details(, "ffp")` for more info * checking examples ... ERROR ``` - Running examples in ‘ffp-Ex.R’ failed + Running examples in ‘ggeasy-Ex.R’ failed The error most likely occurred in: - > ### Name: scenario_density - > ### Title: Plot Scenarios - > ### Aliases: scenario_density scenario_histogram + > ### Name: easy_labs + > ### Title: Easily add ggplot labels using label attribute of 'data.frame' + > ### column + > ### Aliases: easy_labs > > ### ** Examples > - > x <- diff(log(EuStockMarkets))[, 1] - > p <- exp_decay(x, 0.005) - > - > scenario_density(x, p, 500) - Error in use_defaults(..., self = self) : - unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, "black", TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), NULL, list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), 5.5, c(5.5, 5.5, 5.5, 5.5), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.75, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, - NULL, NULL, NULL, 1, 90, NULL, c(0, 2.75, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, NULL, c(0, 0, 0, 2.2), NULL, - Calls: ... -> -> compute_geom_2 -> - Execution halted - ``` - -# fido - -
- -* Version: 1.1.0 -* GitHub: https://github.com/jsilve24/fido -* Source code: https://github.com/cran/fido -* Date/Publication: 2024-05-30 07:00:24 UTC -* Number of recursive dependencies: 130 - -Run `revdepcheck::cloud_details(, "fido")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘fido-Ex.R’ failed - The error most likely occurred in: - - > ### Name: plot.pibblefit - > ### Title: Plot Summaries of Posterior Distribution of pibblefit Parameters - > ### Aliases: plot.pibblefit + ... + + ggplot2::geom_line(ggplot2::aes(colour=Species)) > - > ### ** Examples + > p > - > sim <- pibble_sim(N=10, D=4, Q=3) - > fit <- pibble(sim$Y, sim$X) - > plot(fit, par="Lambda") - Scale for colour is already present. - Adding another scale for colour, which will replace the existing scale. - Error in use_defaults(..., self = self) : - unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, "black", TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), NULL, list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), 5.5, c(5.5, 5.5, 5.5, 5.5), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.75, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(), NULL, list( - NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 1, NULL, NULL, NULL, c(0, 2.2, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, NULL, c(0, 0, 0, 2.2), NULL, - Calls: ... -> -> compute_geom_2 -> + > p + easy_labs() + > p + easy_labs(title = "Plot Title", subtitle = 'Plot Subtitle', x = 'x axis label') + Error in utils::modifyList(p_labs, as.list(unlist(man_labs))) : + is.list(x) is not TRUE + Calls: +.gg ... ggplot_add.easy_labs -> easy_update_labs -> -> stopifnot Execution halted ``` @@ -5618,81 +4652,62 @@ Run `revdepcheck::cloud_details(, "fido")` for more info Running the tests in ‘tests/testthat.R’ failed. Complete output: > library(testthat) - > library(fido) + > library(ggeasy) > - > #Sys.setenv(KMP_DUPLICATE_LIB_OK="TRUE") - > test_check("fido") - [1] 0.27980164 -0.69169550 -0.53205652 0.11488451 -0.42419872 2.20261388 - [7] -1.62190133 -0.90893172 0.07891428 0.75060681 0.43593605 0.26819442 + > test_check("ggeasy") + [ FAIL 6 | WARN 0 | SKIP 1 | PASS 505 ] + + ══ Skipped tests (1) ═══════════════════════════════════════════════════════════ ... - 21. └─base::Map(...) - 22. └─base::mapply(FUN = f, ..., SIMPLIFY = FALSE) - 23. └─ggplot2 (local) ``(layer = dots[[1L]][[1L]], df = dots[[2L]][[1L]]) - 24. └─layer$compute_geom_2(key, single_params, theme) - 25. └─ggplot2 (local) compute_geom_2(..., self = self) - 26. └─self$geom$use_defaults(...) + 1. └─ggeasy (local) expect_eqNe(easy_res$labels[sort(names(easy_res$labels))], hard_res$labels[sort(names(hard_res$labels))]) at test-labs.R:76:3 + 2. └─testthat::expect_equal(..., check.environment = FALSE) at test-labs.R:6:16 - [ FAIL 1 | WARN 0 | SKIP 0 | PASS 114 ] + [ FAIL 6 | WARN 0 | SKIP 1 | PASS 505 ] + Deleting unused snapshots: + • labs/labels-attrib.svg + • labs/labels-manual.svg + • labs/labels-mytitle.svg Error: Test failures Execution halted ``` -## In both - -* checking running R code from vignettes ... WARNING +* checking running R code from vignettes ... ERROR ``` Errors in running code in vignettes: - when running code in ‘non-linear-models.Rmd’ + when running code in ‘shortcuts.Rmd’ ... - The following object is masked from ‘package:dplyr’: + > p1 <- p + labs(title = "default labels") - select + > p2 <- p + easy_labs() + labs(title = "Replace titles with column labels") + > p3 <- p + easy_labs(x = "My x axis") + labs(title = "Manually add x axis label") - When sourcing ‘non-linear-models.R’: - Error: package or namespace load failed for ‘MCMCpack’ in loadNamespace(i, c(lib.loc, .libPaths()), versionCheck = vI[[i]]): - there is no package called ‘quantreg’ + When sourcing ‘shortcuts.R’: + Error: is.list(x) is not TRUE Execution halted - ‘introduction-to-fido.Rmd’ using ‘UTF-8’... OK - ‘mitigating-pcrbias.Rmd’ using ‘UTF-8’... OK - ‘non-linear-models.Rmd’ using ‘UTF-8’... failed - ‘orthus.Rmd’ using ‘UTF-8’... OK - ‘picking_priors.Rmd’ using ‘UTF-8’... OK - ``` - -* checking installed package size ... NOTE - ``` - installed size is 106.2Mb - sub-directories of 1Mb or more: - data 4.0Mb - libs 100.5Mb + ‘shortcuts.Rmd’ using ‘UTF-8’... failed + ‘tests_and_coverage.Rmd’ using ‘UTF-8’... OK ``` * checking re-building of vignette outputs ... NOTE ``` Error(s) in re-building vignettes: - --- re-building ‘introduction-to-fido.Rmd’ using rmarkdown - --- finished re-building ‘introduction-to-fido.Rmd’ - - --- re-building ‘mitigating-pcrbias.Rmd’ using rmarkdown - --- finished re-building ‘mitigating-pcrbias.Rmd’ - - --- re-building ‘non-linear-models.Rmd’ using rmarkdown + --- re-building ‘shortcuts.Rmd’ using rmarkdown ``` -# figuRes2 +# ggedit
-* Version: 1.0.0 -* GitHub: https://github.com/gcicc/figures2 -* Source code: https://github.com/cran/figuRes2 -* Date/Publication: 2022-09-09 08:02:55 UTC -* Number of recursive dependencies: 112 +* Version: 0.4.1 +* GitHub: https://github.com/yonicd/ggedit +* Source code: https://github.com/cran/ggedit +* Date/Publication: 2024-03-04 14:40:02 UTC +* Number of recursive dependencies: 95 -Run `revdepcheck::cloud_details(, "figuRes2")` for more info +Run `revdepcheck::cloud_details(, "ggedit")` for more info
@@ -5700,84 +4715,105 @@ Run `revdepcheck::cloud_details(, "figuRes2")` for more info * checking examples ... ERROR ``` - Running examples in ‘figuRes2-Ex.R’ failed + Running examples in ‘ggedit-Ex.R’ failed The error most likely occurred in: - > ### Name: km.plot - > ### Title: km.plot - > ### Aliases: km.plot + > ### Name: dput.ggedit + > ### Title: Convert ggplot object to a string call + > ### Aliases: dput.ggedit > > ### ** Examples > - > { - ... - Backtrace: - ▆ - 1. ├─base::print(km.M[[2]]) - 2. └─ggplot2:::print.ggplot(km.M[[2]]) - 3. ├─ggplot2::ggplot_gtable(data) - 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) - 5. └─ggplot2::calc_element("plot.margin", theme) - 6. └─cli::cli_abort(...) - 7. └─rlang::abort(...) + > + > pList$pointSmooth #original compiled plot + `geom_smooth()` using formula = 'y ~ x' + Error in compute_geom_2(..., self = self) : + unused arguments (list(6), list(list("black", 0.5, 1, "butt", FALSE, "black", TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), list(NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), 5.5, c(5.5, 5.5, 5.5, 5.5), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.75, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, + NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, 90, NULL, c(0, 2.75, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(NULL, NULL, NU + Calls: ... get_layer_key -> Map -> mapply -> -> Execution halted ``` -* checking running R code from vignettes ... ERROR +# ggESDA + +
+ +* Version: 0.2.0 +* GitHub: https://github.com/kiangkiangkiang/ggESDA +* Source code: https://github.com/cran/ggESDA +* Date/Publication: 2022-08-19 08:40:10 UTC +* Number of recursive dependencies: 214 + +Run `revdepcheck::cloud_details(, "ggESDA")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR ``` - Errors in running code in vignettes: - when running code in ‘basics.Rmd’ - ... - - > ex.bar <- ggplot(data = working.df, aes(x = group, - + fill = group)) + geom_bar() + labs(x = "Group", y = "Frequency", - + title = "", fill = .... [TRUNCATED] - - > print(ex.bar) + Running examples in ‘ggESDA-Ex.R’ failed + The error most likely occurred in: + > ### Name: ggInterval_2DhistMatrix + > ### Title: 2-Dimension histogram matrix + > ### Aliases: ggInterval_2DhistMatrix + > + > ### ** Examples + > + > ggInterval_2DhistMatrix(oils, xBins = 5, yBins = 5) ... - > km.M[[2]] - - When sourcing ‘km.R’: - Error: Theme element `plot.margin` must have class . + 11. │ └─base::withCallingHandlers(...) + 12. └─ggplot2 (local) f(l = layers[[i]], d = data[[i]]) + 13. └─l$compute_geom_2(d, theme = plot$theme) + 14. └─ggplot2 (local) compute_geom_2(..., self = self) + 15. └─self$geom$use_defaults(...) + 16. └─ggplot2 (local) use_defaults(..., self = self) + 17. └─ggplot2:::check_aesthetics(new_params, nrow(data)) + 18. └─cli::cli_abort(...) + 19. └─rlang::abort(...) Execution halted - - ‘basics.Rmd’ using ‘UTF-8’... failed - ‘forest-plots.Rmd’ using ‘UTF-8’... OK - ‘km.Rmd’ using ‘UTF-8’... failed - ‘large-scale.Rmd’ using ‘UTF-8’... OK ``` -# flipr +# ggfixest
-* Version: 0.3.3 -* GitHub: https://github.com/LMJL-Alea/flipr -* Source code: https://github.com/cran/flipr -* Date/Publication: 2023-08-23 09:00:02 UTC -* Number of recursive dependencies: 106 +* Version: 0.1.0 +* GitHub: https://github.com/grantmcdermott/ggfixest +* Source code: https://github.com/cran/ggfixest +* Date/Publication: 2023-12-14 08:00:06 UTC +* Number of recursive dependencies: 78 -Run `revdepcheck::cloud_details(, "flipr")` for more info +Run `revdepcheck::cloud_details(, "ggfixest")` for more info
## Newly broken -* checking re-building of vignette outputs ... NOTE +* checking tests ... ERROR ``` - Error(s) in re-building vignettes: - --- re-building ‘alternative.Rmd’ using rmarkdown - --- finished re-building ‘alternative.Rmd’ - - --- re-building ‘exactness.Rmd’ using rmarkdown - - Quitting from lines 142-177 [unnamed-chunk-1] (exactness.Rmd) - Error: processing vignette 'exactness.Rmd' failed with diagnostics: - subscript out of bounds - --- failed re-building ‘exactness.Rmd’ - - --- re-building ‘flipr.Rmd’ using rmarkdown + Running ‘tinytest.R’ + Running the tests in ‘tests/tinytest.R’ failed. + Complete output: + > ## Throttle CPU threads if R CMD check (for CRAN) + > + > if (any(grepl("_R_CHECK", names(Sys.getenv()), fixed = TRUE))) { + + # fixest + + if (requireNamespace("fixest", quietly = TRUE)) { + + library(fixest) + + setFixest_nthreads(1) + ... + ----- FAILED[]: test_ggiplot.R<52--52> + call| expect_snapshot_plot(p3, label = "ggiplot_simple_ribbon") + diff| 54503 + info| Diff plot saved to: _tinysnapshot_review/ggiplot_simple_ribbon.png + ----- FAILED[]: test_ggiplot.R<54--54> + call| expect_snapshot_plot(p5, label = "ggiplot_simple_mci_ribbon") + diff| 54400 + info| Diff plot saved to: _tinysnapshot_review/ggiplot_simple_mci_ribbon.png + Error: 14 out of 101 tests failed + Execution halted ``` ## In both @@ -5785,194 +4821,169 @@ Run `revdepcheck::cloud_details(, "flipr")` for more info * checking running R code from vignettes ... ERROR ``` Errors in running code in vignettes: - when running code in ‘exactness.Rmd’ + when running code in ‘ggiplot.Rmd’ ... + > iplot(list(TWFE = est_twfe_grp, `Sun & Abraham (2020)` = est_sa20_grp), + + ref.line = -1, main = "Staggered treatment: Split mutli-sample") + The degrees of freedom for the t distribution could not be deduced. Using a Normal distribution instead. + Note that you can provide the argument `df.t` directly. - > library(flipr) - - > load("../R/sysdata.rda") - Warning in readChar(con, 5L, useBytes = TRUE) : - cannot open compressed file '../R/sysdata.rda', probable reason 'No such file or directory' - - ... - cannot open compressed file '../R/sysdata.rda', probable reason 'No such file or directory' - - When sourcing ‘plausibility.R’: - Error: cannot open the connection + When sourcing ‘ggiplot.R’: + Error: in iplot(list(TWFE = est_twfe_grp, `Sun & Abraham (2...: + The 1st element of 'object' raises and error: + Error in nb * sd : non-numeric argument to binary operator Execution halted - ‘alternative.Rmd’ using ‘UTF-8’... OK - ‘exactness.Rmd’ using ‘UTF-8’... failed - ‘flipr.Rmd’ using ‘UTF-8’... failed - ‘plausibility.Rmd’ using ‘UTF-8’... failed - ``` - -* checking installed package size ... NOTE - ``` - installed size is 11.0Mb - sub-directories of 1Mb or more: - doc 9.1Mb - libs 1.2Mb + ‘ggiplot.Rmd’ using ‘UTF-8’... failed ``` -# FMM +# ggforce
-* Version: 0.3.1 -* GitHub: https://github.com/alexARC26/FMM -* Source code: https://github.com/cran/FMM -* Date/Publication: 2021-12-17 12:52:03 UTC -* Number of recursive dependencies: 68 +* Version: 0.4.2 +* GitHub: https://github.com/thomasp85/ggforce +* Source code: https://github.com/cran/ggforce +* Date/Publication: 2024-02-19 11:00:02 UTC +* Number of recursive dependencies: 69 -Run `revdepcheck::cloud_details(, "FMM")` for more info +Run `revdepcheck::cloud_details(, "ggforce")` for more info
## Newly broken -* checking running R code from vignettes ... ERROR +* checking examples ... ERROR ``` - Errors in running code in vignettes: - when running code in ‘FMMVignette.Rmd’ - ... - + 0.25, 0, 1), "cm")) + ylim(-5, 6) + scale_color_manual(values = brewer.pal("Set1", - + .... [TRUNCATED] - Scale for colour is already present. - Adding another scale for colour, which will replace the existing scale. - - > grid.arrange(defaultrFMM2, comprFMM2, nrow = 1) + Running examples in ‘ggforce-Ex.R’ failed + The error most likely occurred in: - When sourcing ‘FMMVignette.R’: - Error: Theme element `plot.margin` must have class . + > ### Name: facet_row + > ### Title: One-dimensional facets + > ### Aliases: facet_row facet_col + > + > ### ** Examples + > + > # Standard use + > ggplot(mtcars) + + + geom_point(aes(disp, mpg)) + + + facet_col(~gear) + Error in space$x : $ operator is invalid for atomic vectors + Calls: ... -> draw_panels -> -> init_gtable Execution halted - - ‘FMMVignette.Rmd’ using ‘UTF-8’... failed ``` -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘FMMVignette.Rmd’ using rmarkdown - ``` +## In both -# fmriqa +* checking installed package size ... NOTE + ``` + installed size is 27.7Mb + sub-directories of 1Mb or more: + R 1.5Mb + help 1.2Mb + libs 24.9Mb + ``` + +# ggformula
-* Version: 0.3.0 -* GitHub: https://github.com/martin3141/fmriqa -* Source code: https://github.com/cran/fmriqa -* Date/Publication: 2018-02-19 15:59:01 UTC -* Number of recursive dependencies: 96 +* Version: 0.12.0 +* GitHub: https://github.com/ProjectMOSAIC/ggformula +* Source code: https://github.com/cran/ggformula +* Date/Publication: 2023-11-09 12:30:07 UTC +* Number of recursive dependencies: 123 -Run `revdepcheck::cloud_details(, "fmriqa")` for more info +Run `revdepcheck::cloud_details(, "ggformula")` for more info
## Newly broken -* checking tests ... ERROR +* checking for code/documentation mismatches ... WARNING ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(fmriqa) - > - > test_check("fmriqa") - Reading data : /tmp/workdir/fmriqa/new/fmriqa.Rcheck/fmriqa/extdata/qa_data.nii.gz - - Basic analysis parameters - ... - 5. └─ggplot2 (local) FUN(X[[i]], ...) - 6. ├─ggplot2::ggplot_gtable(ggplot_build(x)) - 7. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) - 8. └─ggplot2::calc_element("plot.margin", theme) - 9. └─cli::cli_abort(...) - 10. └─rlang::abort(...) - - [ FAIL 2 | WARN 2 | SKIP 1 | PASS 0 ] - Error: Test failures - Execution halted + Codoc mismatches from documentation object 'gf_abline': + gf_hline + Code: function(object = NULL, gformula = NULL, data = NULL, ..., + yintercept, color, linetype, linewidth, alpha, xlab, + ylab, title, subtitle, caption, position = "identity", + show.legend = NA, show.help = NULL, inherit = FALSE, + environment = parent.frame()) + Docs: function(object = NULL, gformula = NULL, data = NULL, ..., + yintercept, color, linetype, linewidth, alpha, xlab, + ylab, title, subtitle, caption, show.legend = NA, + ... + xintercept, color, linetype, linewidth, alpha, xlab, + ylab, title, subtitle, caption, show.legend = NA, + show.help = NULL, inherit = FALSE, environment = + parent.frame()) + Argument names in code not in docs: + position + Mismatches in argument names (first 3): + Position: 15 Code: position Docs: show.legend + Position: 16 Code: show.legend Docs: show.help + Position: 17 Code: show.help Docs: inherit ``` ## In both -* checking LazyData ... NOTE +* checking Rd cross-references ... NOTE ``` - 'LazyData' is specified without a 'data' directory + Packages unavailable to check Rd xrefs: ‘akima’, ‘ggforce’ ``` -# foreSIGHT +# ggfortify
-* Version: 1.2.0 -* GitHub: https://github.com/ClimateAnalytics/foreSIGHT -* Source code: https://github.com/cran/foreSIGHT -* Date/Publication: 2023-10-19 07:00:08 UTC -* Number of recursive dependencies: 92 +* Version: 0.4.17 +* GitHub: https://github.com/sinhrks/ggfortify +* Source code: https://github.com/cran/ggfortify +* Date/Publication: 2024-04-17 04:30:04 UTC +* Number of recursive dependencies: 125 -Run `revdepcheck::cloud_details(, "foreSIGHT")` for more info +Run `revdepcheck::cloud_details(, "ggfortify")` for more info
## Newly broken -* checking examples ... ERROR +* checking tests ... ERROR ``` - Running examples in ‘foreSIGHT-Ex.R’ failed - The error most likely occurred in: - - > ### Name: plotOptions - > ### Title: Plots the differences in performance metrics from two system - > ### options - > ### Aliases: plotOptions - > - > ### ** Examples - > + Running ‘test-all.R’ + Running the tests in ‘tests/test-all.R’ failed. + Complete output: + > library(testthat) + > + > suppressWarnings(RNGversion("3.5.0")) + > set.seed(1, sample.kind = "Rejection") + > + > test_check('ggfortify') + Loading required package: ggfortify ... - 1. └─foreSIGHT::plotOptions(...) - 2. ├─base::print(p1) - 3. ├─base::print(p1) - 4. └─ggplot2:::print.ggplot(p1) - 5. ├─ggplot2::ggplot_gtable(data) - 6. └─ggplot2:::ggplot_gtable.ggplot_built(data) - 7. └─ggplot2::calc_element("plot.margin", theme) - 8. └─cli::cli_abort(...) - 9. └─rlang::abort(...) - Execution halted - ``` - -* checking re-building of vignette outputs ... ERROR - ``` - Error(s) in re-building vignettes: - --- re-building ‘Vignette_QuickStart_simpleScal.Rmd’ using rmarkdown_notangle - ``` - -## In both - -* checking installed package size ... NOTE - ``` - installed size is 5.7Mb - sub-directories of 1Mb or more: - data 2.0Mb - doc 1.3Mb - libs 1.7Mb + + x[3]: "#595959FF" + y[3]: "grey35" + + x[4]: "#595959FF" + y[4]: "grey35" + + [ FAIL 5 | WARN 12 | SKIP 48 | PASS 734 ] + Error: Test failures + Execution halted ``` -# frailtyEM +# gggenomes
-* Version: 1.0.1 -* GitHub: https://github.com/tbalan/frailtyEM -* Source code: https://github.com/cran/frailtyEM -* Date/Publication: 2019-09-22 13:00:10 UTC -* Number of recursive dependencies: 78 +* Version: 1.0.0 +* GitHub: https://github.com/thackl/gggenomes +* Source code: https://github.com/cran/gggenomes +* Date/Publication: 2024-06-28 09:30:06 UTC +* Number of recursive dependencies: 112 -Run `revdepcheck::cloud_details(, "frailtyEM")` for more info +Run `revdepcheck::cloud_details(, "gggenomes")` for more info
@@ -5980,72 +4991,86 @@ Run `revdepcheck::cloud_details(, "frailtyEM")` for more info * checking examples ... ERROR ``` - Running examples in ‘frailtyEM-Ex.R’ failed + Running examples in ‘gggenomes-Ex.R’ failed The error most likely occurred in: - > ### Name: summary.emfrail - > ### Title: Summary for 'emfrail' objects - > ### Aliases: summary.emfrail + > ### Name: flip + > ### Title: Flip bins and sequences + > ### Aliases: flip flip_seqs sync > > ### ** Examples > - > data("bladder") + > library(patchwork) ... - filter - - The following object is masked from ‘package:graphics’: - - layout - - > ggplotly(pl2) - Error in pm[[2]] : subscript out of bounds - Calls: ggplotly -> ggplotly.ggplot -> gg2list + > p4 <- p %>% + + add_clusters(emale_cogs) %>% + + sync() + labs(caption = "shared orthologs") + Joining with `by = join_by(feat_id)` + Flipping: E4-10_086,E4-10_112,RCC970_016B + > + > p0 + p1 + p2 + p3 + p4 + plot_layout(nrow = 1, guides = "collect") + Error in as.unit(value) : object is not coercible to a unit + Calls: ... assemble_guides -> guides_build -> [<- -> [<-.unit -> as.unit Execution halted ``` -## In both - -* checking LazyData ... NOTE +* checking running R code from vignettes ... ERROR ``` - 'LazyData' is specified without a 'data' directory + Errors in running code in vignettes: + when running code in ‘flip.Rmd’ + ... + > p4 <- p %>% add_clusters(emale_cogs) %>% sync() + + + labs(caption = "shared orthologs") + Joining with `by = join_by(feat_id)` + Flipping: E4-10_086,E4-10_112,RCC970_016B + + > p0 + p1 + p2 + p3 + p4 + plot_layout(nrow = 1, guides = "collect") + + When sourcing ‘flip.R’: + Error: object is not coercible to a unit + Execution halted + + ‘emales.Rmd’ using ‘UTF-8’... OK + ‘flip.Rmd’ using ‘UTF-8’... failed + ‘gggenomes.Rmd’ using ‘UTF-8’... OK ``` * checking re-building of vignette outputs ... NOTE ``` Error(s) in re-building vignettes: - --- re-building ‘frailtyEM_manual.Rnw’ using Sweave - Loading required package: survival - Loading required package: gridExtra - Warning: The `` argument of `guides()` cannot be `FALSE`. Use - "none" instead as of ggplot2 3.3.4. - Warning: Removed 2 rows containing missing values or values outside - the scale range (`geom_path()`). - Warning in data("kidney") : data set ‘kidney’ not found - Warning in emfrail(Surv(time, status) ~ age + sex + cluster(id), data = kidney, : + --- re-building ‘emales.Rmd’ using rmarkdown + --- finished re-building ‘emales.Rmd’ + + --- re-building ‘flip.Rmd’ using rmarkdown + + Quitting from lines 17-44 [unnamed-chunk-2] (flip.Rmd) + Error: processing vignette 'flip.Rmd' failed with diagnostics: + object is not coercible to a unit + --- failed re-building ‘flip.Rmd’ ... - l.179 \RequirePackage{grfext}\relax - ^^M - ! ==> Fatal error occurred, no output PDF file produced! - --- failed re-building ‘frailtyEM_manual.Rnw’ + virophages) + emale_tirs Terminal inverted repeats of 6 EMALE genomes + + --- finished re-building ‘gggenomes.Rmd’ SUMMARY: processing the following file failed: - ‘frailtyEM_manual.Rnw’ + ‘flip.Rmd’ Error: Vignette re-building failed. Execution halted ``` -# funcharts +# ggh4x
-* Version: 1.4.1 -* GitHub: https://github.com/unina-sfere/funcharts -* Source code: https://github.com/cran/funcharts -* Date/Publication: 2024-02-22 08:50:02 UTC -* Number of recursive dependencies: 123 +* Version: 0.2.8 +* GitHub: https://github.com/teunbrand/ggh4x +* Source code: https://github.com/cran/ggh4x +* Date/Publication: 2024-01-23 21:00:02 UTC +* Number of recursive dependencies: 77 -Run `revdepcheck::cloud_details(, "funcharts")` for more info +Run `revdepcheck::cloud_details(, "ggh4x")` for more info
@@ -6053,126 +5078,95 @@ Run `revdepcheck::cloud_details(, "funcharts")` for more info * checking examples ... ERROR ``` - Running examples in ‘funcharts-Ex.R’ failed + Running examples in ‘ggh4x-Ex.R’ failed The error most likely occurred in: - > ### Name: pca_mfd - > ### Title: Multivariate functional principal components analysis - > ### Aliases: pca_mfd + > ### Name: guide_stringlegend + > ### Title: String legend + > ### Aliases: guide_stringlegend > > ### ** Examples > - > library(funcharts) - > mfdobj <- data_sim_mfd() - > pca_obj <- pca_mfd(mfdobj) - > plot_pca_mfd(pca_obj) - Error in identicalUnits(x) : object is not a unit - Calls: ... assemble_guides -> guides_build -> unit.c -> identicalUnits - Execution halted - ``` - -# gapmap - -
- -* Version: 1.0.0 -* GitHub: https://github.com/evanbiederstedt/gapmap -* Source code: https://github.com/cran/gapmap -* Date/Publication: 2024-01-22 20:50:02 UTC -* Number of recursive dependencies: 55 - -Run `revdepcheck::cloud_details(, "gapmap")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘gapmap-Ex.R’ failed - The error most likely occurred in: - - > ### Name: gapmap - > ### Title: Function to draw a gapped cluster heatmap - > ### Aliases: gapmap - > - > ### ** Examples + > p <- ggplot(mpg, aes(displ, hwy)) + + + geom_point(aes(colour = manufacturer)) > - > set.seed(1234) - ... - ! Theme element `plot.margin` must have class . - Backtrace: - ▆ - 1. └─gapmap::gapmap(m = as.matrix(distxy), d_row = rev(dend), d_col = dend) - 2. ├─ggplot2::ggplot_gtable(ggplot2::ggplot_build(hm)) - 3. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot2::ggplot_build(hm)) - 4. └─ggplot2::calc_element("plot.margin", theme) - 5. └─cli::cli_abort(...) - 6. └─rlang::abort(...) + > # String legend can be set in the `guides()` function + > p + guides(colour = guide_stringlegend(ncol = 2)) + Error in (function (layer, df) : + argument "theme" is missing, with no default + Calls: ... use_defaults -> eval_from_theme -> %||% -> calc_element Execution halted ``` -* checking running R code from vignettes ... ERROR +* checking tests ... ERROR ``` - Errors in running code in vignettes: - when running code in ‘simple_example.Rmd’ - ... - + col = grey_scale) - Warning: The `panel.margin` argument of `theme()` is deprecated as of ggplot2 2.2.0. - ℹ Please use the `panel.spacing` argument instead. - ℹ The deprecated feature was likely used in the gapmap package. - Please report the issue at - . - + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(ggh4x) + Loading required package: ggplot2 + > + > test_check("ggh4x") + [ FAIL 2 | WARN 20 | SKIP 18 | PASS 753 ] + ... - ℹ The deprecated feature was likely used in the gapmap package. - Please report the issue at - . - - When sourcing ‘tcga_example.R’: - Error: Theme element `plot.margin` must have class . - Execution halted - - ‘simple_example.Rmd’ using ‘UTF-8’... failed - ‘tcga_example.Rmd’ using ‘UTF-8’... failed + 25. └─ggplot2 (local) compute_geom_2(..., self = self) + 26. └─self$geom$use_defaults(...) + 27. └─ggplot2 (local) use_defaults(..., self = self) + 28. └─ggplot2:::eval_from_theme(default_aes, theme) + 29. ├─calc_element("geom", theme) %||% .default_geom_element + 30. └─ggplot2::calc_element("geom", theme) + + [ FAIL 2 | WARN 20 | SKIP 18 | PASS 753 ] + Error: Test failures + Execution halted ``` * checking re-building of vignette outputs ... NOTE ``` Error(s) in re-building vignettes: + --- re-building ‘Facets.Rmd’ using rmarkdown + ``` + +## In both + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘Miscellaneous.Rmd’ ... - --- re-building ‘simple_example.Rmd’ using rmarkdown - Quitting from lines 36-38 [unnamed-chunk-3] (simple_example.Rmd) - Error: processing vignette 'simple_example.Rmd' failed with diagnostics: - Theme element `plot.margin` must have class . - --- failed re-building ‘simple_example.Rmd’ + > ggplot(diamonds, aes(price, carat, colour = clarity)) + + + geom_point(shape = ".") + scale_colour_brewer(palette = "Dark2", + + guide = "stri ..." ... [TRUNCATED] + Warning: The S3 guide system was deprecated in ggplot2 3.5.0. + ℹ It has been replaced by a ggproto system that can be extended. - --- re-building ‘tcga_example.Rmd’ using rmarkdown ... - Quitting from lines 43-45 [unnamed-chunk-3] (tcga_example.Rmd) - Error: processing vignette 'tcga_example.Rmd' failed with diagnostics: - Theme element `plot.margin` must have class . - --- failed re-building ‘tcga_example.Rmd’ - - SUMMARY: processing the following files failed: - ‘simple_example.Rmd’ ‘tcga_example.Rmd’ - - Error: Vignette re-building failed. + ℹ Error occurred in the 1st layer. + Caused by error in `setup_params()`: + ! A discrete 'nbinom' distribution cannot be fitted to continuous data. Execution halted + + ‘Facets.Rmd’ using ‘UTF-8’... OK + ‘Miscellaneous.Rmd’ using ‘UTF-8’... failed + ‘PositionGuides.Rmd’ using ‘UTF-8’... OK + ‘Statistics.Rmd’ using ‘UTF-8’... failed + ‘ggh4x.Rmd’ using ‘UTF-8’... OK ``` -# gasper +# gghighlight
-* Version: 1.1.6 -* GitHub: https://github.com/fabnavarro/gasper -* Source code: https://github.com/cran/gasper -* Date/Publication: 2024-02-28 11:10:02 UTC -* Number of recursive dependencies: 68 +* Version: 0.4.1 +* GitHub: https://github.com/yutannihilation/gghighlight +* Source code: https://github.com/cran/gghighlight +* Date/Publication: 2023-12-16 01:00:02 UTC +* Number of recursive dependencies: 85 -Run `revdepcheck::cloud_details(, "gasper")` for more info +Run `revdepcheck::cloud_details(, "gghighlight")` for more info
@@ -6180,79 +5174,90 @@ Run `revdepcheck::cloud_details(, "gasper")` for more info * checking examples ... ERROR ``` - Running examples in ‘gasper-Ex.R’ failed + Running examples in ‘gghighlight-Ex.R’ failed The error most likely occurred in: - > ### Name: plot_signal - > ### Title: Plot a Signal on Top of a Given Graph - > ### Aliases: plot_signal + > ### Name: gghighlight + > ### Title: Highlight Data With Predicate + > ### Aliases: gghighlight > > ### ** Examples > - > f <- rnorm(length(grid1$xy[,1])) + > d <- data.frame( ... - ▆ - 1. └─gasper::plot_signal(grid1, f) - 2. ├─base::print(p2) - 3. └─ggplot2:::print.ggplot(p2) - 4. ├─ggplot2::ggplot_gtable(data) - 5. └─ggplot2:::ggplot_gtable.ggplot_built(data) - 6. └─ggplot2::calc_element("plot.margin", theme) - 7. └─cli::cli_abort(...) - 8. └─rlang::abort(...) + 8. │ ├─purrr:::with_indexed_errors(...) + 9. │ │ └─base::withCallingHandlers(...) + 10. │ ├─purrr:::call_with_cleanup(...) + 11. │ └─gghighlight (local) .f(.x[[i]], .y[[i]], ...) + 12. │ └─gghighlight:::get_default_aes_param(nm, layer$geom, layer$mapping) + 13. └─base::.handleSimpleError(...) + 14. └─purrr (local) h(simpleError(msg, call)) + 15. └─cli::cli_abort(...) + 16. └─rlang::abort(...) Execution halted ``` -* checking running R code from vignettes ... ERROR +* checking tests ... ERROR ``` - Errors in running code in vignettes: - when running code in ‘gasper_vignette.rmd’ - ... - - > f <- rnorm(nrow(grid1$sA)) - - > plot_graph(grid1) - - > plot_signal(grid1, f, size = 2) + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(gghighlight) + Loading required package: ggplot2 + > + > test_check("gghighlight") + label_key: type + label_key: type + ... + 15. └─cli::cli_abort(...) + 16. └─rlang::abort(...) + + [ FAIL 2 | WARN 2 | SKIP 1 | PASS 178 ] + Deleting unused snapshots: + • vdiffr/simple-bar-chart-with-facet.svg + • vdiffr/simple-line-chart.svg + • vdiffr/simple-point-chart.svg + Error: Test failures + Execution halted + ``` + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘gghighlight.Rmd’ + ... + + 0, label_key = type) + Warning in is.na(non_null_default_aes[[aes_param_name]]) : + is.na() applied to non-(list or vector) of type 'language' - When sourcing ‘gasper_vignette.R’: - Error: Theme element `plot.margin` must have class . + When sourcing ‘gghighlight.R’: + Error: ℹ In index: 1. + Caused by error in `aes_param_name %in% names(non_null_default_aes) && is.na(non_null_default_aes[[ + aes_param_name]])`: + ! 'length = 2' in coercion to 'logical(1)' Execution halted - ‘gasper_vignette.rmd’ using ‘UTF-8’... failed + ‘gghighlight.Rmd’ using ‘UTF-8’... failed ``` -## In both - * checking re-building of vignette outputs ... NOTE ``` Error(s) in re-building vignettes: - ... - --- re-building ‘gasper_vignette.rmd’ using rmarkdown - - Quitting from lines 173-176 [unnamed-chunk-17] (gasper_vignette.rmd) - Error: processing vignette 'gasper_vignette.rmd' failed with diagnostics: - Theme element `plot.margin` must have class . - --- failed re-building ‘gasper_vignette.rmd’ - - SUMMARY: processing the following file failed: - ‘gasper_vignette.rmd’ - - Error: Vignette re-building failed. - Execution halted + --- re-building ‘gghighlight.Rmd’ using rmarkdown ``` -# gaussplotR +# ggHoriPlot
-* Version: 0.2.5 -* GitHub: https://github.com/vbaliga/gaussplotR -* Source code: https://github.com/cran/gaussplotR -* Date/Publication: 2021-05-02 20:10:02 UTC -* Number of recursive dependencies: 91 +* Version: 1.0.1 +* GitHub: https://github.com/rivasiker/ggHoriPlot +* Source code: https://github.com/cran/ggHoriPlot +* Date/Publication: 2022-10-11 16:22:33 UTC +* Number of recursive dependencies: 117 -Run `revdepcheck::cloud_details(, "gaussplotR")` for more info +Run `revdepcheck::cloud_details(, "ggHoriPlot")` for more info
@@ -6261,41 +5266,40 @@ Run `revdepcheck::cloud_details(, "gaussplotR")` for more info * checking running R code from vignettes ... ERROR ``` Errors in running code in vignettes: - when running code in ‘fit_gaussian_2D.Rmd’ + when running code in ‘ggHoriPlot.Rmd’ ... - + by = 0.1), Y_values = seq(from = -1, to = 4, by = 0.1)) + > mid <- sum(range(dat_tab$y, na.rm = T))/2 - > gauss_data_ue <- predict_gaussian_2D(fit_object = gauss_fit_ue, - + X_values = grid$X_values, Y_values = grid$Y_values, ) + > b <- plotAllLayers(dat_tab, mid, cutpoints$cuts, cutpoints$color) - > ggplot_gaussian_2D(gauss_data_ue) + > b/a + plot_layout(guides = "collect", heights = c(6, + + 1)) - When sourcing ‘fit_gaussian_2D.R’: - Error: Theme element `plot.margin` must have class . + When sourcing ‘ggHoriPlot.R’: + Error: object is not a unit Execution halted - ‘fit_gaussian_2D.Rmd’ using ‘UTF-8’... failed - ‘formulas-used-by-fit-gaussian-2D.Rmd’ using ‘UTF-8’... OK - ‘troubleshooting-model-fits.Rmd’ using ‘UTF-8’... OK + ‘examples.Rmd’ using ‘UTF-8’... OK + ‘ggHoriPlot.Rmd’ using ‘UTF-8’... failed ``` * checking re-building of vignette outputs ... NOTE ``` Error(s) in re-building vignettes: - --- re-building ‘fit_gaussian_2D.Rmd’ using rmarkdown + --- re-building ‘examples.Rmd’ using rmarkdown ``` -# gg.gap +# ggiraph
-* Version: 1.3 -* GitHub: https://github.com/ChrisLou-bioinfo/gg.gap -* Source code: https://github.com/cran/gg.gap -* Date/Publication: 2019-09-30 16:10:02 UTC -* Number of recursive dependencies: 29 +* Version: 0.8.10 +* GitHub: https://github.com/davidgohel/ggiraph +* Source code: https://github.com/cran/ggiraph +* Date/Publication: 2024-05-17 12:10:02 UTC +* Number of recursive dependencies: 95 -Run `revdepcheck::cloud_details(, "gg.gap")` for more info +Run `revdepcheck::cloud_details(, "ggiraph")` for more info
@@ -6303,205 +5307,235 @@ Run `revdepcheck::cloud_details(, "gg.gap")` for more info * checking examples ... ERROR ``` - Running examples in ‘gg.gap-Ex.R’ failed + Running examples in ‘ggiraph-Ex.R’ failed The error most likely occurred in: - > ### Name: add.legend - > ### Title: Add Legend to gg.gap() - > ### Aliases: add.legend + > ### Name: geom_path_interactive + > ### Title: Create interactive observations connections + > ### Aliases: geom_path_interactive geom_line_interactive + > ### geom_step_interactive > > ### ** Examples > - > library(ggplot2) ... - Backtrace: - ▆ - 1. ├─base (local) ``(x) - 2. └─ggplot2:::print.ggplot(x) - 3. ├─ggplot2::ggplot_gtable(data) - 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) - 5. └─ggplot2::calc_element("plot.margin", theme) - 6. └─cli::cli_abort(...) - 7. └─rlang::abort(...) + 20. │ └─base::lapply(...) + 21. │ └─ggplot2 (local) FUN(X[[i]], ...) + 22. │ ├─rlang::inject(self$draw_panel(data, panel_params, coord, !!!params)) + 23. │ └─self$draw_panel(...) + 24. └─base::.handleSimpleError(...) + 25. └─rlang (local) h(simpleError(msg, call)) + 26. └─handlers[[1L]](cnd) + 27. └─cli::cli_abort(...) + 28. └─rlang::abort(...) Execution halted ``` +* checking tests ... ERROR + ``` + Running ‘tinytest.R’ + Running the tests in ‘tests/tinytest.R’ failed. + Complete output: + > if (requireNamespace("tinytest", quietly = TRUE)) { + + tinytest::test_package("ggiraph") + + } + + test-annotate_interactive.R... 0 tests + test-annotate_interactive.R... 0 tests + test-annotate_interactive.R... 0 tests + ... + 30. │ └─base::lapply(...) + 31. │ └─ggplot2 (local) FUN(X[[i]], ...) + 32. │ ├─rlang::inject(self$draw_panel(data, panel_params, coord, !!!params)) + 33. │ └─self$draw_panel(...) + 34. └─base::.handleSimpleError(...) + 35. └─rlang (local) h(simpleError(msg, call)) + 36. └─handlers[[1L]](cnd) + 37. └─cli::cli_abort(...) + 38. └─rlang::abort(...) + Execution halted + ``` + ## In both -* checking LazyData ... NOTE +* checking installed package size ... NOTE ``` - 'LazyData' is specified without a 'data' directory + installed size is 9.7Mb + sub-directories of 1Mb or more: + R 1.5Mb + libs 6.9Mb ``` -# ggalignment +# ggiraphExtra
-* Version: 1.0.1 -* GitHub: NA -* Source code: https://github.com/cran/ggalignment -* Date/Publication: 2022-11-04 10:20:02 UTC -* Number of recursive dependencies: 83 +* Version: 0.3.0 +* GitHub: https://github.com/cardiomoon/ggiraphExtra +* Source code: https://github.com/cran/ggiraphExtra +* Date/Publication: 2020-10-06 07:00:02 UTC +* Number of recursive dependencies: 124 -Run `revdepcheck::cloud_details(, "ggalignment")` for more info +Run `revdepcheck::cloud_details(, "ggiraphExtra")` for more info
## Newly broken -* checking tests ... ERROR +* checking examples ... ERROR ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(ggalignment) - > - > test_check("ggalignment") - [ FAIL 1 | WARN 0 | SKIP 0 | PASS 8 ] - - ══ Failed tests ════════════════════════════════════════════════════════════════ + Running examples in ‘ggiraphExtra-Ex.R’ failed + The error most likely occurred in: + + > ### Name: ggAncova + > ### Title: Make an interactive plot for an ANCOVA model + > ### Aliases: ggAncova ggAncova.default ggAncova.formula ggAncova.lm + > + > ### ** Examples + > + > require(moonBook) ... - 6. └─ggplot2:::print.ggplot(p) - 7. ├─ggplot2::ggplot_gtable(data) - 8. └─ggplot2:::ggplot_gtable.ggplot_built(data) - 9. └─ggplot2::calc_element("plot.margin", theme) - 10. └─cli::cli_abort(...) - 11. └─rlang::abort(...) - - [ FAIL 1 | WARN 0 | SKIP 0 | PASS 8 ] - Error: Test failures - Execution halted + 24. │ └─base::lapply(...) + 25. │ └─ggplot2 (local) FUN(X[[i]], ...) + 26. │ ├─rlang::inject(self$draw_panel(data, panel_params, coord, !!!params)) + 27. │ └─self$draw_panel(...) + 28. └─base::.handleSimpleError(...) + 29. └─rlang (local) h(simpleError(msg, call)) + 30. └─handlers[[1L]](cnd) + 31. └─cli::cli_abort(...) + 32. └─rlang::abort(...) + Execution halted ``` * checking running R code from vignettes ... ERROR ``` Errors in running code in vignettes: - when running code in ‘ggalignment.Rmd’ + when running code in ‘introduction.Rmd’ ... - intersect, setdiff, setequal, union - - - > ggalignment(alignment = data.frame(img = character(), - + alignment = character()), font_size = 3) + > ggPoints(aes(x = wt, y = mpg, color = am), data = mtcars, + + method = "lm", interactive = TRUE) - When sourcing ‘ggalignment.R’: - Error: Theme element `plot.margin` must have class . + When sourcing ‘introduction.R’: + Error: Problem while converting geom to grob. + ℹ Error occurred in the 3rd layer. + Caused by error in `draw_panel()`: + ! unused argument (arrow.fill = NULL) Execution halted - ‘ggalignment.Rmd’ using ‘UTF-8’... failed + ‘ggPredict.Rmd’ using ‘UTF-8’... OK + ‘introduction.Rmd’ using ‘UTF-8’... failed ``` * checking re-building of vignette outputs ... NOTE ``` Error(s) in re-building vignettes: - ... - --- re-building ‘ggalignment.Rmd’ using rmarkdown - - Quitting from lines 27-33 [example-alignment-plot] (ggalignment.Rmd) - Error: processing vignette 'ggalignment.Rmd' failed with diagnostics: - Theme element `plot.margin` must have class . - --- failed re-building ‘ggalignment.Rmd’ - - SUMMARY: processing the following file failed: - ‘ggalignment.Rmd’ - - Error: Vignette re-building failed. - Execution halted + --- re-building ‘ggPredict.Rmd’ using rmarkdown ``` -# ggalt +# ggmice
-* Version: 0.4.0 -* GitHub: https://github.com/hrbrmstr/ggalt -* Source code: https://github.com/cran/ggalt -* Date/Publication: 2017-02-15 18:16:00 -* Number of recursive dependencies: 95 +* Version: 0.1.0 +* GitHub: https://github.com/amices/ggmice +* Source code: https://github.com/cran/ggmice +* Date/Publication: 2023-08-07 14:20:02 UTC +* Number of recursive dependencies: 120 -Run `revdepcheck::cloud_details(, "ggalt")` for more info +Run `revdepcheck::cloud_details(, "ggmice")` for more info
## Newly broken -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘ggalt_examples.Rmd’ using rmarkdown - ``` - -## In both - * checking running R code from vignettes ... ERROR ``` Errors in running code in vignettes: - when running code in ‘ggalt_examples.Rmd’ + when running code in ‘old_friends.Rmd’ ... - Warning in grid.Call.graphics(C_text, as.graphicsAnnot(x$label), x$x, x$y, : - font family 'StateFace' not found in PostScript font database - Warning in grid.Call.graphics(C_text, as.graphicsAnnot(x$label), x$x, x$y, : - font family 'StateFace' not found in PostScript font database - Warning in grid.Call.graphics(C_text, as.graphicsAnnot(x$label), x$x, x$y, : - font family 'StateFace' not found in PostScript font database + layout - When sourcing ‘ggalt_examples.R’: - Error: invalid font type + + > p <- plot_flux(dat) + + > ggplotly(p) + + When sourcing ‘old_friends.R’: + Error: subscript out of bounds Execution halted - ‘ggalt_examples.Rmd’ using ‘UTF-8’... failed - ``` - -* checking dependencies in R code ... NOTE - ``` - Namespace in Imports field not imported from: ‘plotly’ - All declared Imports should be used. + ‘ggmice.Rmd’ using ‘UTF-8’... OK + ‘old_friends.Rmd’ using ‘UTF-8’... failed ``` -* checking LazyData ... NOTE +* checking re-building of vignette outputs ... NOTE ``` - 'LazyData' is specified without a 'data' directory + Error(s) in re-building vignettes: + --- re-building ‘ggmice.Rmd’ using rmarkdown ``` -# gganimate +# ggmulti
-* Version: 1.0.9 -* GitHub: https://github.com/thomasp85/gganimate -* Source code: https://github.com/cran/gganimate -* Date/Publication: 2024-02-27 14:00:03 UTC -* Number of recursive dependencies: 97 +* Version: 1.0.7 +* GitHub: NA +* Source code: https://github.com/cran/ggmulti +* Date/Publication: 2024-04-09 09:40:05 UTC +* Number of recursive dependencies: 125 -Run `revdepcheck::cloud_details(, "gganimate")` for more info +Run `revdepcheck::cloud_details(, "ggmulti")` for more info
## Newly broken -* checking tests ... ERROR +* checking examples ... ERROR ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(gganimate) - Loading required package: ggplot2 - > - > test_check("gganimate") - [ FAIL 1 | WARN 3 | SKIP 1 | PASS 5 ] - - ... - 3. ├─gganimate::animate(p, nframes = 2) at test-anim_save.R:14:5 - 4. └─gganimate:::animate.gganim(p, nframes = 2) - 5. └─args$renderer(frames_vars$frame_source, args$fps) - 6. └─gganimate:::png_dim(frames[1]) - 7. └─cli::cli_abort("Provided file ({file}) does not exist") - 8. └─rlang::abort(...) + Running examples in ‘ggmulti-Ex.R’ failed + The error most likely occurred in: + + > ### Name: coord_radial + > ### Title: Radial axes + > ### Aliases: coord_radial + > + > ### ** Examples + > + > if(require("dplyr")) { + ... + + The following objects are masked from ‘package:base’: + + intersect, setdiff, setequal, union + + Error in use_defaults(..., self = self) : + unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, "black", TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), list(NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), 5.5, c(5.5, 5.5, 5.5, 5.5), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.75, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, + NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, 90, NULL, c(0, 2.75, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL + Calls: ... -> -> compute_geom_2 -> + Execution halted + ``` + +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > + > + > library(testthat) + > library(ggmulti) + Loading required package: ggplot2 - [ FAIL 1 | WARN 3 | SKIP 1 | PASS 5 ] + Attaching package: 'ggmulti' + ... + ── Error ('test_stat.R:18:3'): test stat ─────────────────────────────────────── + Error in `stat_hist_(prop = 0.5)`: Problem while setting up geom aesthetics. + ℹ Error occurred in the 1st layer. + Caused by error in `check_aesthetics()`: + ! Aesthetics must be either length 1 or the same as the data (83). + ✖ Fix the following mappings: `width`. + + [ FAIL 5 | WARN 1 | SKIP 0 | PASS 21 ] Error: Test failures Execution halted ``` @@ -6509,39 +5543,45 @@ Run `revdepcheck::cloud_details(, "gganimate")` for more info * checking running R code from vignettes ... ERROR ``` Errors in running code in vignettes: - when running code in ‘gganimate.Rmd’ + when running code in ‘glyph.Rmd’ ... - Theme element `panel.grid.major.y` is missing - Theme element `panel.grid.major.x` is missing - Warning: Failed to plot frame - Caused by error in `UseMethod()`: - ! no applicable method for 'element_grob' applied to an object of class "NULL" + + Sepal.Width, colour = Species), serialaxes.data = iris, axes.layout = "radia ..." ... [TRUNCATED] - When sourcing ‘gganimate.R’: - Error: Provided file (/tmp/RtmpEoDH6s/16eb8d7241d/gganim_plot0001.png) does not - exist + When sourcing ‘glyph.R’: + Error: Base operators are not defined for quosures. Do you need to unquote the + quosure? + + # Bad: myquosure / rhs + ... + > p + + When sourcing ‘highDim.R’: + Error: unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, "black", TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), list(NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), 5.5, c(5.5, 5.5, 5.5, 5.5), NULL, NULL, list(), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(), NULL, list(NULL, + NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, NULL, c(0, 0, 0, 2.2), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0.5, NULL, NULL, NULL, c(0, 2.2, 0, 2. Execution halted - ‘gganimate.Rmd’ using ‘UTF-8’... failed + ‘glyph.Rmd’ using ‘UTF-8’... failed + ‘highDim.Rmd’ using ‘UTF-8’... failed + ‘histogram-density-.Rmd’ using ‘UTF-8’... OK ``` * checking re-building of vignette outputs ... NOTE ``` Error(s) in re-building vignettes: - --- re-building ‘gganimate.Rmd’ using rmarkdown + --- re-building ‘glyph.Rmd’ using rmarkdown ``` -# ggbrace +# ggnewscale
-* Version: 0.1.1 -* GitHub: NA -* Source code: https://github.com/cran/ggbrace -* Date/Publication: 2024-02-20 20:30:02 UTC -* Number of recursive dependencies: 49 +* Version: 0.4.10 +* GitHub: https://github.com/eliocamp/ggnewscale +* Source code: https://github.com/cran/ggnewscale +* Date/Publication: 2024-02-08 23:50:02 UTC +* Number of recursive dependencies: 62 -Run `revdepcheck::cloud_details(, "ggbrace")` for more info +Run `revdepcheck::cloud_details(, "ggnewscale")` for more info
@@ -6549,92 +5589,133 @@ Run `revdepcheck::cloud_details(, "ggbrace")` for more info * checking examples ... ERROR ``` - Running examples in ‘ggbrace-Ex.R’ failed + Running examples in ‘ggnewscale-Ex.R’ failed The error most likely occurred in: - > ### Name: stat_brace - > ### Title: create curly braces as a layer in ggplot - > ### Aliases: stat_brace + > ### Name: new_scale + > ### Title: Adds a new scale to a plot + > ### Aliases: new_scale new_scale_fill new_scale_color new_scale_colour > > ### ** Examples > - > library(ggbrace) + > library(ggplot2) ... - Backtrace: - ▆ - 1. ├─base (local) ``(x) - 2. └─ggplot2:::print.ggplot(x) - 3. ├─ggplot2::ggplot_gtable(data) - 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) - 5. └─ggplot2::calc_element("plot.margin", theme) - 6. └─cli::cli_abort(...) - 7. └─rlang::abort(...) + + # Color scale for topography + + scale_color_viridis_c(option = "D") + + + # geoms below will use another color scale + + new_scale_color() + + + geom_point(data = measurements, size = 3, aes(color = thing)) + + + # Color scale applied to geoms added after new_scale_color() + + scale_color_viridis_c(option = "A") + Error in names(labels) <- `*vtmp*` : attempt to set an attribute on NULL + Calls: +.gg ... ggplot_add -> ggplot_add.new_aes -> bump_aes_labels Execution halted ``` -# ggbrain +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(ggnewscale) + > + > test_check("ggnewscale") + [ FAIL 7 | WARN 0 | SKIP 0 | PASS 0 ] + + ══ Failed tests ════════════════════════════════════════════════════════════════ + ... + [ FAIL 7 | WARN 0 | SKIP 0 | PASS 0 ] + Deleting unused snapshots: + • newscale/guides-outisde-of-scales.svg + • newscale/guides.svg + • newscale/guides2.svg + • newscale/implicit-mapping.svg + • newscale/many-layers.svg + • newscale/respects-override-aes-2.svg + Error: Test failures + Execution halted + ``` + +# ggparallel
-* Version: 0.8.1 -* GitHub: https://github.com/michaelhallquist/ggbrain -* Source code: https://github.com/cran/ggbrain -* Date/Publication: 2023-03-21 18:00:05 UTC -* Number of recursive dependencies: 74 +* Version: 0.4.0 +* GitHub: https://github.com/heike/ggparallel +* Source code: https://github.com/cran/ggparallel +* Date/Publication: 2024-03-09 22:00:02 UTC +* Number of recursive dependencies: 51 -Run `revdepcheck::cloud_details(, "ggbrain")` for more info +Run `revdepcheck::cloud_details(, "ggparallel")` for more info
## Newly broken -* checking running R code from vignettes ... ERROR +* checking tests ... ERROR ``` - Errors in running code in vignettes: - when running code in ‘ggbrain_introduction.Rmd’ - ... - - > gg_obj <- gg_base + geom_brain(definition = "underlay", - + fill_scale = scale_fill_gradient(low = "grey8", high = "grey62"), - + show_legend .... [TRUNCATED] - - > gg_obj$render() - + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > # This file is part of the standard setup for testthat. + > # It is recommended that you do not modify it. + > # + > # Where should you do additional test configuration? + > # Learn more about the roles of various files in: + > # * https://r-pkgs.org/testing-design.html#sec-tests-files-overview + > # * https://testthat.r-lib.org/articles/special-files.html ... - - > plot(gg_obj) - - When sourcing ‘ggbrain_labels.R’: - Error: Theme element `plot.margin` must have class . - Execution halted - - ‘ggbrain_aesthetics.Rmd’ using ‘UTF-8’... OK - ‘ggbrain_introduction.Rmd’ using ‘UTF-8’... failed - ‘ggbrain_labels.Rmd’ using ‘UTF-8’... failed + 12. └─self$get_layer_key(params, layers[include], data[include], theme) + 13. └─ggplot2 (local) get_layer_key(...) + 14. └─base::Map(...) + 15. └─base::mapply(FUN = f, ..., SIMPLIFY = FALSE) + 16. └─ggplot2 (local) ``(layer = dots[[1L]][[1L]], df = dots[[2L]][[1L]]) + 17. └─layer$compute_geom_2(key, single_params, theme) + + [ FAIL 1 | WARN 0 | SKIP 0 | PASS 0 ] + Error: Test failures + Execution halted ``` -* checking re-building of vignette outputs ... NOTE +# ggpicrust2 + +
+ +* Version: 1.7.3 +* GitHub: https://github.com/cafferychen777/ggpicrust2 +* Source code: https://github.com/cran/ggpicrust2 +* Date/Publication: 2023-11-08 16:10:02 UTC +* Number of recursive dependencies: 230 + +Run `revdepcheck::cloud_details(, "ggpicrust2")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR ``` - Error(s) in re-building vignettes: - ... - --- re-building ‘ggbrain_aesthetics.Rmd’ using rmarkdown - --- finished re-building ‘ggbrain_aesthetics.Rmd’ - - --- re-building ‘ggbrain_introduction.Rmd’ using rmarkdown + Running examples in ‘ggpicrust2-Ex.R’ failed + The error most likely occurred in: - Quitting from lines 238-239 [unnamed-chunk-16] (ggbrain_introduction.Rmd) - Error: processing vignette 'ggbrain_introduction.Rmd' failed with diagnostics: - Theme element `plot.margin` must have class . + > ### Name: pathway_pca + > ### Title: Perform Principal Component Analysis (PCA) on functional pathway + > ### abundance data and create visualizations of the PCA results. + > ### Aliases: pathway_pca + > + > ### ** Examples + > ... - Quitting from lines 47-54 [unnamed-chunk-2] (ggbrain_labels.Rmd) - Error: processing vignette 'ggbrain_labels.Rmd' failed with diagnostics: - Theme element `plot.margin` must have class . - --- failed re-building ‘ggbrain_labels.Rmd’ - - SUMMARY: processing the following files failed: - ‘ggbrain_introduction.Rmd’ ‘ggbrain_labels.Rmd’ - - Error: Vignette re-building failed. + > + > # Create example metadata + > # Please ensure the sample IDs in the metadata have the column name "sample_name" + > metadata_example <- data.frame(sample_name = colnames(kegg_abundance_example), + + group = factor(rep(c("Control", "Treatment"), each = 5))) + > + > pca_plot <- pathway_pca(kegg_abundance_example, metadata_example, "group") + Error in identicalUnits(x) : object is not a unit + Calls: pathway_pca ... assemble_guides -> guides_build -> unit.c -> identicalUnits Execution halted ``` @@ -6642,24 +5723,23 @@ Run `revdepcheck::cloud_details(, "ggbrain")` for more info * checking installed package size ... NOTE ``` - installed size is 10.5Mb + installed size is 5.5Mb sub-directories of 1Mb or more: - doc 3.0Mb - extdata 1.6Mb - libs 5.2Mb + R 2.1Mb + data 2.0Mb ``` -# ggbreak +# ggpie
-* Version: 0.1.2 -* GitHub: https://github.com/YuLab-SMU/ggbreak -* Source code: https://github.com/cran/ggbreak -* Date/Publication: 2023-06-26 05:40:02 UTC -* Number of recursive dependencies: 64 +* Version: 0.2.5 +* GitHub: https://github.com/showteeth/ggpie +* Source code: https://github.com/cran/ggpie +* Date/Publication: 2022-11-16 07:40:06 UTC +* Number of recursive dependencies: 59 -Run `revdepcheck::cloud_details(, "ggbreak")` for more info +Run `revdepcheck::cloud_details(, "ggpie")` for more info
@@ -6667,61 +5747,65 @@ Run `revdepcheck::cloud_details(, "ggbreak")` for more info * checking examples ... ERROR ``` - Running examples in ‘ggbreak-Ex.R’ failed + Running examples in ‘ggpie-Ex.R’ failed The error most likely occurred in: - > ### Name: scale_wrap - > ### Title: scale-wrap - > ### Aliases: scale_wrap + > ### Name: ggnestedpie + > ### Title: Create nested pie plot. + > ### Aliases: ggnestedpie > > ### ** Examples > - > library(ggplot2) - > library(ggbreak) - > p <- ggplot(economics, aes(x=date, y = unemploy, colour = uempmed)) + - + geom_line() - > p + scale_wrap(n=4) - Error in identicalUnits(x) : object is not a unit - Calls: -> print.ggwrap + > library(ggpie) + ... + > data(diamonds) + > # inner circle label, outer circle label and in pie plot + > ggnestedpie( + + data = diamonds, group_key = c("cut", "color"), count_type = "full", + + inner_label_info = "all", inner_label_split = NULL, + + outer_label_type = "circle", outer_label_pos = "in", outer_label_info = "all" + + ) + Error in names(labels) <- `*vtmp*` : attempt to set an attribute on NULL + Calls: ggnestedpie ... ggplot_add -> ggplot_add.new_aes -> bump_aes_labels Execution halted ``` * checking running R code from vignettes ... ERROR ``` Errors in running code in vignettes: - when running code in ‘ggbreak.Rmd’ + when running code in ‘ggpie.Rmd’ ... - > print(pg) - - > pg <- pg + aes(fill = group) + theme(legend.position = "bottom") + > cowplot::plot_grid(p1, p2, p3, p4, ncol = 2) - > print(pg) + > ggnestedpie(data = diamonds, group_key = c("cut", + + "color"), count_type = "full", inner_label_info = "all", + + inner_label_split = NULL, i .... [TRUNCATED] - When sourcing ‘ggbreak.R’: - Error: object is not a unit + When sourcing ‘ggpie.R’: + Error: attempt to set an attribute on NULL Execution halted - ‘ggbreak.Rmd’ using ‘UTF-8’... failed + ‘ggpie.Rmd’ using ‘UTF-8’... failed ``` * checking re-building of vignette outputs ... NOTE ``` Error(s) in re-building vignettes: - --- re-building ‘ggbreak.Rmd’ using rmarkdown + --- re-building ‘ggpie.Rmd’ using rmarkdown ``` -# ggdark +# ggplotlyExtra
-* Version: 0.2.1 +* Version: 0.0.1 * GitHub: NA -* Source code: https://github.com/cran/ggdark -* Date/Publication: 2019-01-11 17:30:06 UTC -* Number of recursive dependencies: 46 +* Source code: https://github.com/cran/ggplotlyExtra +* Date/Publication: 2019-12-02 16:20:06 UTC +* Number of recursive dependencies: 70 -Run `revdepcheck::cloud_details(, "ggdark")` for more info +Run `revdepcheck::cloud_details(, "ggplotlyExtra")` for more info
@@ -6729,54 +5813,29 @@ Run `revdepcheck::cloud_details(, "ggdark")` for more info * checking examples ... ERROR ``` - Running examples in ‘ggdark-Ex.R’ failed + Running examples in ‘ggplotlyExtra-Ex.R’ failed The error most likely occurred in: - > ### Name: dark_mode - > ### Title: Activate dark mode on a 'ggplot2' theme - > ### Aliases: dark_mode + > ### Name: ggplotly_histogram + > ### Title: Clean 'ggplot2' Histogram to be Converted to 'Plotly' + > ### Aliases: ggplotly_histogram > > ### ** Examples > - > library(ggplot2) - ... > - > p1 <- ggplot(iris, aes(Sepal.Width, Sepal.Length, color = Species)) + - + geom_point() + ... + + xlab("len") + `stat_bin()` using `bins = 30`. Pick better value with `binwidth`. + Warning in geom_bar(data = layerdata, mapping = aes(x = .data$x, y = .data$count, : + Ignoring unknown aesthetics: label1, label2, and label3 > - > p1 # theme returned by theme_get() - > p1 + dark_mode() # activate dark mode on theme returned by theme_get() - Error in match(x, table, nomatch = 0L) : - 'match' requires vector arguments - Calls: dark_mode -> %in% + > # convert `ggplot` object to `plotly` object + > ggplotly(p, tooltip = c("Range", "count", "density")) + Error in pm[[2]] : subscript out of bounds + Calls: ggplotly -> ggplotly.ggplot -> gg2list Execution halted ``` -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(ggdark) - > - > test_check("ggdark") - [ FAIL 1 | WARN 0 | SKIP 0 | PASS 0 ] - - ══ Failed tests ════════════════════════════════════════════════════════════════ - ... - ── Error ('test_dark_mode.R:10:1'): (code run outside of `test_that()`) ──────── - Error in `match(x, table, nomatch = 0L)`: 'match' requires vector arguments - Backtrace: - ▆ - 1. └─ggdark::dark_mode(light_theme) at test_dark_mode.R:10:1 - 2. └─geoms[["GeomPoint"]]$default_aes$colour %in% ... - - [ FAIL 1 | WARN 0 | SKIP 0 | PASS 0 ] - Error: Test failures - Execution halted - ``` - ## In both * checking LazyData ... NOTE @@ -6784,17 +5843,17 @@ Run `revdepcheck::cloud_details(, "ggdark")` for more info 'LazyData' is specified without a 'data' directory ``` -# ggdist +# ggpol
-* Version: 3.3.2 -* GitHub: https://github.com/mjskay/ggdist -* Source code: https://github.com/cran/ggdist -* Date/Publication: 2024-03-05 05:30:23 UTC -* Number of recursive dependencies: 126 +* Version: 0.0.7 +* GitHub: https://github.com/erocoar/ggpol +* Source code: https://github.com/cran/ggpol +* Date/Publication: 2020-11-08 13:40:02 UTC +* Number of recursive dependencies: 54 -Run `revdepcheck::cloud_details(, "ggdist")` for more info +Run `revdepcheck::cloud_details(, "ggpol")` for more info
@@ -6802,77 +5861,129 @@ Run `revdepcheck::cloud_details(, "ggdist")` for more info * checking examples ... ERROR ``` - Running examples in ‘ggdist-Ex.R’ failed + Running examples in ‘ggpol-Ex.R’ failed The error most likely occurred in: - > ### Name: Pr_ - > ### Title: Probability expressions in ggdist aesthetics - > ### Aliases: Pr_ p_ + > ### Name: GeomConfmat + > ### Title: Confusion Matrix + > ### Aliases: GeomConfmat geom_confmat stat_confmat > > ### ** Examples > - > library(ggplot2) + > x <- sample(LETTERS[seq(4)], 50, replace = TRUE) ... - + ) - > - > # map density onto alpha of the fill - > ggplot(df, aes(y = name, xdist = d)) + - + stat_slabinterval(aes(alpha = !!p_(x))) - Error in use_defaults(..., self = self) : - unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, "black", TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), NULL, list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), 5.5, c(5.5, 5.5, 5.5, 5.5), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.75, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, - NULL, NULL, NULL, 1, 90, NULL, c(0, 2.75, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 1, NULL, NULL, NULL, c(0, 2.2, 0, 0), NULL, TRUE), NULL, l - Calls: ... -> -> compute_geom_2 -> + 21. │ └─ggpol (local) draw_panel(...) + 22. │ └─base::lapply(GeomText$default_aes[missing_aes], rlang::eval_tidy) + 23. │ └─rlang (local) FUN(X[[i]], ...) + 24. ├─ggplot2::from_theme(fontsize) + 25. └─base::.handleSimpleError(...) + 26. └─rlang (local) h(simpleError(msg, call)) + 27. └─handlers[[1L]](cnd) + 28. └─cli::cli_abort(...) + 29. └─rlang::abort(...) Execution halted ``` +## In both + +* checking dependencies in R code ... NOTE + ``` + Namespaces in Imports field not imported from: + ‘dplyr’ ‘grDevices’ + All declared Imports should be used. + ``` + +* checking LazyData ... NOTE + ``` + 'LazyData' is specified without a 'data' directory + ``` + +# ggpubr + +
+ +* Version: 0.6.0 +* GitHub: https://github.com/kassambara/ggpubr +* Source code: https://github.com/cran/ggpubr +* Date/Publication: 2023-02-10 16:20:02 UTC +* Number of recursive dependencies: 88 + +Run `revdepcheck::cloud_details(, "ggpubr")` for more info + +
+ +## Newly broken + * checking tests ... ERROR ``` Running ‘testthat.R’ Running the tests in ‘tests/testthat.R’ failed. Complete output: - > # This file is part of the standard setup for testthat. - > # It is recommended that you do not modify it. - > # - > # Where should you do additional test configuration? - > # Learn more about the roles of various files in: - > # * https://r-pkgs.org/testing-design.html#sec-tests-files-overview - > # * https://testthat.r-lib.org/articles/special-files.html + > library(testthat) + > library(ggpubr) + Loading required package: ggplot2 + > + > test_check("ggpubr") + [ FAIL 2 | WARN 5 | SKIP 0 | PASS 183 ] + ... - • test.stat_sample_slabinterval/nas-with-na-rm-true.svg - • test.subguide/dots-subguide-with-side-vertical.svg - • test.subguide/integer-subguide-with-zero-range.svg - • test.subguide/slab-subguide-with-inside-labels-vertical.svg - • test.subguide/slab-subguide-with-outside-labels-vert.svg - • test.subguide/slab-subguide-with-outside-labels.svg - • test.subguide/slab-subguide-with-side-vertical.svg - • test.theme_ggdist/facet-titles-on-left.svg + [6] 6 - 10 == -4 + [7] 19 - 9 == 10 + [9] 1 - 7 == -6 + [10] 6 - 7 == -1 + [11] 13 - 6 == 7 + ... + + [ FAIL 2 | WARN 5 | SKIP 0 | PASS 183 ] Error: Test failures Execution halted ``` -* checking re-building of vignette outputs ... NOTE +# ggraph + +
+ +* Version: 2.2.1 +* GitHub: https://github.com/thomasp85/ggraph +* Source code: https://github.com/cran/ggraph +* Date/Publication: 2024-03-07 12:40:02 UTC +* Number of recursive dependencies: 115 + +Run `revdepcheck::cloud_details(, "ggraph")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR ``` - Error(s) in re-building vignettes: - --- re-building ‘dotsinterval.Rmd’ using rmarkdown - Warning in hook_png(..., cmd = "pngquant", post_process = function(x) { : - cannot find pngquant; please install and put it in PATH - Warning in hook_png(..., cmd = "pngquant", post_process = function(x) { : - cannot find pngquant; please install and put it in PATH + Running examples in ‘ggraph-Ex.R’ failed + The error most likely occurred in: - Quitting from lines 49-161 [dotsinterval_components] (dotsinterval.Rmd) - Error: processing vignette 'dotsinterval.Rmd' failed with diagnostics: - Problem while setting up geom aesthetics. + > ### Name: geom_conn_bundle + > ### Title: Create hierarchical edge bundles between node connections + > ### Aliases: geom_conn_bundle geom_conn_bundle2 geom_conn_bundle0 + > + > ### ** Examples + > + > # Create a graph of the flare class system ... - - --- re-building ‘freq-uncertainty-vis.Rmd’ using rmarkdown - Warning in hook_png(..., cmd = "pngquant", post_process = function(x) { : - cannot find pngquant; please install and put it in PATH - Warning in hook_png(..., cmd = "pngquant", post_process = function(x) { : - cannot find pngquant; please install and put it in PATH - Warning in hook_png(..., cmd = "pngquant", post_process = function(x) { : - cannot find pngquant; please install and put it in PATH - Warning in hook_png(..., cmd = "pngquant", post_process = function(x) { : - cannot find pngquant; please install and put it in PATH + + ) + + + geom_node_point(aes(filter = leaf, colour = class)) + + + scale_edge_colour_distiller('', direction = 1, guide = 'edge_direction') + + + coord_fixed() + + + ggforce::theme_no_axes() + Error in get_layer_key(...) : + unused argument (list(list("black", 0.5, 1, "butt", FALSE, "black", TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), list(NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), 5.5, c(5.5, 5.5, 5.5, 5.5), NULL, list(), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.75, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, + NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, 90, NULL, c(0, 2.75, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 1, NULL, NULL, NULL, c(0, 2.2, 0, 0), NULL, TRUE), NULL, list(NUL + Calls: ... -> -> process_layers -> + Execution halted + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘Edges.Rmd’ using rmarkdown ``` ## In both @@ -6880,48 +5991,48 @@ Run `revdepcheck::cloud_details(, "ggdist")` for more info * checking running R code from vignettes ... ERROR ``` Errors in running code in vignettes: - when running code in ‘dotsinterval.Rmd’ + when running code in ‘Edges.Rmd’ ... - + xdist = dist)) + geom_hline(yintercept = 0:1, color = "gray95") + - + stat_dotsin .... [TRUNCATED] + Warning in grid.Call.graphics(C_text, as.graphicsAnnot(x$label), x$x, x$y, : + font family 'Arial Narrow' not found in PostScript font database + Warning in grid.Call.graphics(C_text, as.graphicsAnnot(x$label), x$x, x$y, : + font family 'Arial Narrow' not found in PostScript font database + Warning in grid.Call.graphics(C_text, as.graphicsAnnot(x$label), x$x, x$y, : + font family 'Arial Narrow' not found in PostScript font database - When sourcing ‘dotsinterval.R’: - Error: Problem while setting up geom aesthetics. - ℹ Error occurred in the 2nd layer. - Caused by error in `use_defaults()`: ... - ℹ Error occurred in the 1st layer. - Caused by error in `use_defaults()`: - ! unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, "black", TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), NULL, list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), 5.5, c(5.5, 5.5, 5.5, 5.5), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(7, 0, 0, 0), NULL, FALSE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, - NULL, NULL, 1, 90, NULL, c(0, 7, 0, 0), NULL, FALSE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2 + font family 'Arial' not found in PostScript font database + + When sourcing ‘tidygraph.R’: + Error: invalid font type Execution halted - ‘dotsinterval.Rmd’ using ‘UTF-8’... failed - ‘freq-uncertainty-vis.Rmd’ using ‘UTF-8’... failed - ‘lineribbon.Rmd’ using ‘UTF-8’... failed - ‘slabinterval.Rmd’ using ‘UTF-8’... failed + ‘Edges.Rmd’ using ‘UTF-8’... failed + ‘Layouts.Rmd’ using ‘UTF-8’... failed + ‘Nodes.Rmd’ using ‘UTF-8’... failed + ‘tidygraph.Rmd’ using ‘UTF-8’... failed ``` * checking installed package size ... NOTE ``` - installed size is 5.4Mb + installed size is 9.0Mb sub-directories of 1Mb or more: R 1.5Mb - doc 1.3Mb - help 1.5Mb + doc 3.9Mb + libs 2.9Mb ``` -# ggedit +# ggredist
-* Version: 0.4.1 -* GitHub: https://github.com/yonicd/ggedit -* Source code: https://github.com/cran/ggedit -* Date/Publication: 2024-03-04 14:40:02 UTC -* Number of recursive dependencies: 95 +* Version: 0.0.2 +* GitHub: https://github.com/alarm-redist/ggredist +* Source code: https://github.com/cran/ggredist +* Date/Publication: 2022-11-23 11:20:02 UTC +* Number of recursive dependencies: 67 -Run `revdepcheck::cloud_details(, "ggedit")` for more info +Run `revdepcheck::cloud_details(, "ggredist")` for more info
@@ -6929,239 +6040,284 @@ Run `revdepcheck::cloud_details(, "ggedit")` for more info * checking examples ... ERROR ``` - Running examples in ‘ggedit-Ex.R’ failed + Running examples in ‘ggredist-Ex.R’ failed The error most likely occurred in: - > ### Name: dput.ggedit - > ### Title: Convert ggplot object to a string call - > ### Aliases: dput.ggedit + > ### Name: geom_district_text + > ### Title: Label Map Regions + > ### Aliases: geom_district_text geom_district_label + > ### stat_district_coordinates StatDistrictCoordinates GeomDistrictText + > ### Keywords: datasets > > ### ** Examples - > - > - > pList$pointSmooth #original compiled plot - `geom_smooth()` using formula = 'y ~ x' - Error in compute_geom_2(..., self = self) : - unused arguments (list(6), list(list("black", 0.5, 1, "butt", FALSE, "black", TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), NULL, list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), 5.5, c(5.5, 5.5, 5.5, 5.5), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.75, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, - NULL, NULL, NULL, 1, 90, NULL, c(0, 2.75, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 1, NULL, NULL, NULL, c(0, 2.2, 0, 0), NULL, TRUE), NULL, - Calls: ... get_layer_key -> Map -> mapply -> -> + ... + 22. │ └─coord$transform(data, panel_params) + 23. │ └─ggplot2 (local) transform(..., self = self) + 24. │ └─ggplot2:::sf_rescale01(...) + 25. │ └─sf::st_normalize(x, c(x_range[1], y_range[1], x_range[2], y_range[2])) + 26. └─base::.handleSimpleError(...) + 27. └─rlang (local) h(simpleError(msg, call)) + 28. └─handlers[[1L]](cnd) + 29. └─cli::cli_abort(...) + 30. └─rlang::abort(...) Execution halted ``` -# ggExtra +# ggRtsy
-* Version: 0.10.1 -* GitHub: https://github.com/daattali/ggExtra -* Source code: https://github.com/cran/ggExtra -* Date/Publication: 2023-08-21 14:40:02 UTC -* Number of recursive dependencies: 118 +* Version: 0.1.0 +* GitHub: NA +* Source code: https://github.com/cran/ggRtsy +* Date/Publication: 2023-09-15 19:12:05 UTC +* Number of recursive dependencies: 69 -Run `revdepcheck::cloud_details(, "ggExtra")` for more info +Run `revdepcheck::cloud_details(, "ggRtsy")` for more info
## Newly broken +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(ggplot2) + > library(dplyr) + + Attaching package: 'dplyr' + + The following object is masked from 'package:testthat': + ... + 13. │ │ └─base (local) doTryCatch(return(expr), name, parentenv, handler) + 14. │ └─vctrs::vec_as_location(i, n, names = names, arg = arg, call = call) + 15. └─vctrs (local) ``() + 16. └─vctrs:::stop_subscript_oob(...) + 17. └─vctrs:::stop_subscript(...) + 18. └─rlang::abort(...) + + [ FAIL 1 | WARN 0 | SKIP 0 | PASS 3 ] + Error: Test failures + Execution halted + ``` + * checking running R code from vignettes ... ERROR ``` Errors in running code in vignettes: - when running code in ‘ggExtra.Rmd’ + when running code in ‘Vignette.Rmd’ ... + |Antique White |(238, 223, 204) |#eedfcc | - > p1 <- ggplot(df1, aes(x, y)) + geom_point() + theme_bw() + > RectangleFiller(plotExample, c("#e32636", "#9966cc", + + "#f4c2c2", "#e16827")) - > p1 - - > ggMarginal(p1) - - When sourcing ‘ggExtra.R’: - Error: Theme element `plot.margin` must have class . + When sourcing ‘Vignette.R’: + Error: Can't extract rows past the end. + ℹ Location 1 doesn't exist. + ℹ There are only 0 rows. Execution halted - ‘ggExtra.Rmd’... failed + ‘Vignette.Rmd’ using ‘UTF-8’... failed ``` * checking re-building of vignette outputs ... NOTE ``` Error(s) in re-building vignettes: - --- re-building ‘ggExtra.Rmd’ using rmarkdown + ... + --- re-building ‘Vignette.Rmd’ using rmarkdown + + Quitting from lines 48-49 [unnamed-chunk-2] (Vignette.Rmd) + Error: processing vignette 'Vignette.Rmd' failed with diagnostics: + Can't extract rows past the end. + ℹ Location 1 doesn't exist. + ℹ There are only 0 rows. + --- failed re-building ‘Vignette.Rmd’ + + SUMMARY: processing the following file failed: + ‘Vignette.Rmd’ + + Error: Vignette re-building failed. + Execution halted ``` ## In both -* checking dependencies in R code ... NOTE +* checking data for non-ASCII characters ... NOTE ``` - Namespaces in Imports field not imported from: - ‘R6’ ‘scales’ ‘utils’ - All declared Imports should be used. + Note: found 19 marked UTF-8 strings ``` -# ggfixest +# ggseqplot
-* Version: 0.1.0 -* GitHub: https://github.com/grantmcdermott/ggfixest -* Source code: https://github.com/cran/ggfixest -* Date/Publication: 2023-12-14 08:00:06 UTC -* Number of recursive dependencies: 78 +* Version: 0.8.4 +* GitHub: https://github.com/maraab23/ggseqplot +* Source code: https://github.com/cran/ggseqplot +* Date/Publication: 2024-05-17 21:40:03 UTC +* Number of recursive dependencies: 139 -Run `revdepcheck::cloud_details(, "ggfixest")` for more info +Run `revdepcheck::cloud_details(, "ggseqplot")` for more info
## Newly broken +* checking examples ... ERROR + ``` + Running examples in ‘ggseqplot-Ex.R’ failed + The error most likely occurred in: + + > ### Name: ggseqmsplot + > ### Title: Modal State Sequence Plot + > ### Aliases: ggseqmsplot + > + > ### ** Examples + > + > # Use example data from TraMineR: actcal data set + ... + 11. │ └─base::withCallingHandlers(...) + 12. └─ggplot2 (local) f(l = layers[[i]], d = data[[i]]) + 13. └─l$compute_geom_2(d, theme = plot$theme) + 14. └─ggplot2 (local) compute_geom_2(..., self = self) + 15. └─self$geom$use_defaults(...) + 16. └─ggplot2 (local) use_defaults(..., self = self) + 17. └─ggplot2:::check_aesthetics(new_params, nrow(data)) + 18. └─cli::cli_abort(...) + 19. └─rlang::abort(...) + Execution halted + ``` + * checking tests ... ERROR ``` - Running ‘tinytest.R’ - Running the tests in ‘tests/tinytest.R’ failed. + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. Complete output: - > ## Throttle CPU threads if R CMD check (for CRAN) - > - > if (any(grepl("_R_CHECK", names(Sys.getenv()), fixed = TRUE))) { - + # fixest - + if (requireNamespace("fixest", quietly = TRUE)) { - + library(fixest) - + setFixest_nthreads(1) + > library(testthat) + > library(ggseqplot) + Loading required package: TraMineR + + TraMineR stable version 2.2-10 (Built: 2024-05-22) + Website: http://traminer.unige.ch + Please type 'citation("TraMineR")' for citation information. ... - test_nthreads.R............... 0 tests ----- FAILED[]: test_ggiplot.R<52--52> - call| expect_snapshot_plot(p3, label = "ggiplot_simple_ribbon") - diff| 54503 - info| Diff plot saved to: _tinysnapshot_review/ggiplot_simple_ribbon.png - ----- FAILED[]: test_ggiplot.R<54--54> - call| expect_snapshot_plot(p5, label = "ggiplot_simple_mci_ribbon") - diff| 54400 - info| Diff plot saved to: _tinysnapshot_review/ggiplot_simple_mci_ribbon.png - Error: 2 out of 101 tests failed + Backtrace: + ▆ + 1. ├─testthat::expect_s3_class(ggseqtrplot(biofam.seq), "ggplot") at test-ggseqtrplot.R:35:3 + 2. │ └─testthat::quasi_label(enquo(object), arg = "object") + 3. │ └─rlang::eval_bare(expr, quo_get_env(quo)) + 4. └─ggseqplot::ggseqtrplot(biofam.seq) + + [ FAIL 1 | WARN 1036 | SKIP 0 | PASS 131 ] + Error: Test failures Execution halted ``` -## In both - * checking running R code from vignettes ... ERROR ``` Errors in running code in vignettes: - when running code in ‘ggiplot.Rmd’ + when running code in ‘ggseqplot.Rmd’ ... - > iplot(list(TWFE = est_twfe_grp, `Sun & Abraham (2020)` = est_sa20_grp), - + ref.line = -1, main = "Staggered treatment: Split mutli-sample") - The degrees of freedom for the t distribution could not be deduced. Using a Normal distribution instead. - Note that you can provide the argument `df.t` directly. + > p1 + p2 + plot_layout(guides = "collect") & scale_fill_manual(values = canva_palettes$`Fun and tropical`[1:4]) & + + theme_ipsum(base_family = "" .... [TRUNCATED] + Scale for fill is already present. + Adding another scale for fill, which will replace the existing scale. + Scale for fill is already present. + Adding another scale for fill, which will replace the existing scale. - When sourcing ‘ggiplot.R’: - Error: in iplot(list(TWFE = est_twfe_grp, `Sun & Abraham (2...: - The 1st element of 'object' raises and error: - Error in nb * sd : non-numeric argument to binary operator + When sourcing ‘ggseqplot.R’: + Error: object is not coercible to a unit Execution halted - ‘ggiplot.Rmd’ using ‘UTF-8’... failed + ‘ggseqplot.Rmd’ using ‘UTF-8’... failed + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘ggseqplot.Rmd’ using rmarkdown ``` -# ggflowchart +# ggside
-* Version: 1.0.0 -* GitHub: NA -* Source code: https://github.com/cran/ggflowchart -* Date/Publication: 2023-05-11 10:10:05 UTC -* Number of recursive dependencies: 59 +* Version: 0.3.1 +* GitHub: https://github.com/jtlandis/ggside +* Source code: https://github.com/cran/ggside +* Date/Publication: 2024-03-01 09:12:37 UTC +* Number of recursive dependencies: 76 -Run `revdepcheck::cloud_details(, "ggflowchart")` for more info +Run `revdepcheck::cloud_details(, "ggside")` for more info
## Newly broken -* checking examples ... ERROR - ``` - Running examples in ‘ggflowchart-Ex.R’ failed - The error most likely occurred in: - - > ### Name: ggflowchart - > ### Title: Generate a flowchart in ggplot2 - > ### Aliases: ggflowchart - > - > ### ** Examples - > - > data <- tibble::tibble(from = c("A", "A", "A", "B", "C", "F"), to = c("B", "C", "D", "E", "F", "G")) - ... - Backtrace: - ▆ - 1. ├─base (local) ``(x) - 2. └─ggplot2:::print.ggplot(x) - 3. ├─ggplot2::ggplot_gtable(data) - 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) - 5. └─ggplot2::calc_element("plot.margin", theme) - 6. └─cli::cli_abort(...) - 7. └─rlang::abort(...) - Execution halted - ``` - -* checking running R code from vignettes ... ERROR +* checking tests ... ERROR ``` - Errors in running code in vignettes: - when running code in ‘decision-tree-example.Rmd’ - ... - - > node_data <- tibble::tibble(name = c("Goldilocks", - + "Porridge", "Just right", "Chairs", "Just right2", "Beds", - + "Just right3", "Too cold ..." ... [TRUNCATED] - - > ggflowchart(goldilocks, node_data) - + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(ggplot2) + > library(ggside) + Registered S3 method overwritten by 'ggside': + method from + +.gg ggplot2 + > ... - + "C", "F"), to = c("B", "C", "D", "E", "F", "G")) - - > ggflowchart(data) - - When sourcing ‘minimal-example.R’: - Error: Theme element `plot.margin` must have class . - Execution halted - - ‘decision-tree-example.Rmd’ using ‘UTF-8’... failed - ‘minimal-example.Rmd’ using ‘UTF-8’... failed + • ops_meaningful/alpha-0-5-from-function.svg + • side_layers/boxplot2.svg + • vdiff_irisScatter/collapsed-histo.svg + • vdiff_irisScatter/facetgrid-collapsed-density.svg + • vdiff_irisScatter/facetgrid-histo.svg + • vdiff_irisScatter/facetgrid-side-density.svg + • vdiff_irisScatter/stacked-side-density.svg + • vdiff_irisScatter/yside-histo.svg + Error: Test failures + Execution halted ``` -* checking re-building of vignette outputs ... NOTE +* checking for code/documentation mismatches ... WARNING ``` - Error(s) in re-building vignettes: - ... - --- re-building ‘decision-tree-example.Rmd’ using rmarkdown - - Quitting from lines 64-65 [flowchart] (decision-tree-example.Rmd) - Error: processing vignette 'decision-tree-example.Rmd' failed with diagnostics: - Theme element `plot.margin` must have class . - --- failed re-building ‘decision-tree-example.Rmd’ - - --- re-building ‘minimal-example.Rmd’ using rmarkdown + Codoc mismatches from documentation object 'geom_xsideabline': + geom_xsidehline + Code: function(mapping = NULL, data = NULL, position = "identity", + ..., yintercept, na.rm = FALSE, show.legend = NA) + Docs: function(mapping = NULL, data = NULL, ..., yintercept, na.rm = + FALSE, show.legend = NA) + Argument names in code not in docs: + position + Mismatches in argument names (first 3): + Position: 3 Code: position Docs: ... ... - Quitting from lines 31-32 [flowchart] (minimal-example.Rmd) - Error: processing vignette 'minimal-example.Rmd' failed with diagnostics: - Theme element `plot.margin` must have class . - --- failed re-building ‘minimal-example.Rmd’ - - SUMMARY: processing the following files failed: - ‘decision-tree-example.Rmd’ ‘minimal-example.Rmd’ - - Error: Vignette re-building failed. - Execution halted + Docs: function(mapping = NULL, data = NULL, stat = "identity", + position = "identity", ..., lineend = "butt", linejoin + = "round", linemitre = 10, arrow = NULL, na.rm = + FALSE, show.legend = NA, inherit.aes = TRUE) + Argument names in code not in docs: + arrow.fill + Mismatches in argument names: + Position: 10 Code: arrow.fill Docs: na.rm + Position: 11 Code: na.rm Docs: show.legend + Position: 12 Code: show.legend Docs: inherit.aes ``` -# ggforce +# ggspatial
-* Version: 0.4.2 -* GitHub: https://github.com/thomasp85/ggforce -* Source code: https://github.com/cran/ggforce -* Date/Publication: 2024-02-19 11:00:02 UTC -* Number of recursive dependencies: 69 +* Version: 1.1.9 +* GitHub: https://github.com/paleolimbot/ggspatial +* Source code: https://github.com/cran/ggspatial +* Date/Publication: 2023-08-17 15:32:38 UTC +* Number of recursive dependencies: 108 -Run `revdepcheck::cloud_details(, "ggforce")` for more info +Run `revdepcheck::cloud_details(, "ggspatial")` for more info
@@ -7169,140 +6325,118 @@ Run `revdepcheck::cloud_details(, "ggforce")` for more info * checking examples ... ERROR ``` - Running examples in ‘ggforce-Ex.R’ failed + Running examples in ‘ggspatial-Ex.R’ failed The error most likely occurred in: - > ### Name: facet_zoom - > ### Title: Facet data for zoom with context - > ### Aliases: facet_zoom + > ### Name: annotation_spatial_hline + > ### Title: Projected horizontal and vertical lines + > ### Aliases: annotation_spatial_hline annotation_spatial_vline + > ### GeomSpatialXline + > ### Keywords: datasets > > ### ** Examples - > - > # Zoom in on the versicolor species on the x-axis - > ggplot(iris, aes(Petal.Length, Petal.Width, colour = Species)) + - + geom_point() + - + facet_zoom(x = Species == 'versicolor') - Error in upgradeUnit.default(x) : Not a unit object - Calls: ... is.unit -> convertUnit -> upgradeUnit -> upgradeUnit.default + ... + 25. │ └─grid:::validGP(list(...)) + 26. │ └─grid (local) numnotnull("fontsize") + 27. │ └─grid (local) check.length(gparname) + 28. │ └─base::stop(...) + 29. └─base::.handleSimpleError(...) + 30. └─rlang (local) h(simpleError(msg, call)) + 31. └─handlers[[1L]](cnd) + 32. └─cli::cli_abort(...) + 33. └─rlang::abort(...) Execution halted ``` -## In both - -* checking installed package size ... NOTE +* checking tests ... ERROR ``` - installed size is 27.7Mb - sub-directories of 1Mb or more: - R 1.5Mb - help 1.2Mb - libs 24.9Mb - ``` - -# ggfortify - -
- -* Version: 0.4.17 -* GitHub: https://github.com/sinhrks/ggfortify -* Source code: https://github.com/cran/ggfortify -* Date/Publication: 2024-04-17 04:30:04 UTC -* Number of recursive dependencies: 125 - -Run `revdepcheck::cloud_details(, "ggfortify")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘test-all.R’ - Running the tests in ‘tests/test-all.R’ failed. + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. Complete output: > library(testthat) + > library(ggspatial) > - > suppressWarnings(RNGversion("3.5.0")) - > set.seed(1, sample.kind = "Rejection") - > - > test_check('ggfortify') - Loading required package: ggfortify - ... - - x[3]: "#595959FF" - y[3]: "grey35" + > test_check("ggspatial") + Linking to GEOS 3.10.2, GDAL 3.4.1, PROJ 8.2.1; sf_use_s2() is TRUE + [ FAIL 1 | WARN 1 | SKIP 22 | PASS 195 ] - x[4]: "#595959FF" - y[4]: "grey35" + ... + 33. │ └─base::stop(...) + 34. └─base::.handleSimpleError(...) + 35. └─rlang (local) h(simpleError(msg, call)) + 36. └─handlers[[1L]](cnd) + 37. └─cli::cli_abort(...) + 38. └─rlang::abort(...) - [ FAIL 5 | WARN 12 | SKIP 48 | PASS 734 ] + [ FAIL 1 | WARN 1 | SKIP 22 | PASS 195 ] Error: Test failures Execution halted ``` -# ggfoundry +# ggtern
-* Version: 0.1.1 -* GitHub: https://github.com/cgoo4/ggfoundry -* Source code: https://github.com/cran/ggfoundry -* Date/Publication: 2024-05-28 11:40:02 UTC -* Number of recursive dependencies: 107 +* Version: 3.5.0 +* GitHub: NA +* Source code: https://github.com/cran/ggtern +* Date/Publication: 2024-03-24 21:50:02 UTC +* Number of recursive dependencies: 42 -Run `revdepcheck::cloud_details(, "ggfoundry")` for more info +Run `revdepcheck::cloud_details(, "ggtern")` for more info
## Newly broken -* checking running R code from vignettes ... ERROR +* checking examples ... ERROR ``` - Errors in running code in vignettes: - when running code in ‘ggfoundry.Rmd’ - ... - - > p2 <- p + geom_point(size = 4) + scale_shape_manual(values = c("▼", - + "●", "▲")) + labs(title = "geom_point with unicodes", - + subtitle = " ..." ... [TRUNCATED] - - > p1 + p2 + plot_layout(guides = "collect", axes = "collect") + Running examples in ‘ggtern-Ex.R’ failed + The error most likely occurred in: - When sourcing ‘ggfoundry.R’: - Error: object is not coercible to a unit + > ### Name: annotate + > ### Title: Create an annotation layer (ggtern version). + > ### Aliases: annotate + > + > ### ** Examples + > + > ggtern() + + ... + 3. ├─ggtern::ggplot_build(x) + 4. └─ggtern:::ggplot_build.ggplot(x) + 5. └─ggtern:::layers_add_or_remove_mask(plot) + 6. └─ggint$plot_theme(plot) + 7. └─ggplot2:::validate_theme(theme) + 8. └─base::mapply(...) + 9. └─ggplot2 (local) ``(...) + 10. └─cli::cli_abort(...) + 11. └─rlang::abort(...) Execution halted - - ‘ggfoundry.Rmd’ using ‘UTF-8’... failed ``` -* checking re-building of vignette outputs ... NOTE +## In both + +* checking package dependencies ... NOTE ``` - Error(s) in re-building vignettes: - ... - --- re-building ‘ggfoundry.Rmd’ using rmarkdown - - Quitting from lines 50-94 [unicodes] (ggfoundry.Rmd) - Error: processing vignette 'ggfoundry.Rmd' failed with diagnostics: - object is not coercible to a unit - --- failed re-building ‘ggfoundry.Rmd’ - - SUMMARY: processing the following file failed: - ‘ggfoundry.Rmd’ - - Error: Vignette re-building failed. - Execution halted + Package which this enhances but not available for checking: ‘sp’ + ``` + +* checking Rd cross-references ... NOTE + ``` + Package unavailable to check Rd xrefs: ‘chemometrics’ ``` -# gggap +# ggupset
-* Version: 1.0.1 -* GitHub: https://github.com/cmoralesmx/gggap -* Source code: https://github.com/cran/gggap -* Date/Publication: 2020-11-20 09:20:02 UTC -* Number of recursive dependencies: 29 +* Version: 0.4.0 +* GitHub: https://github.com/const-ae/ggupset +* Source code: https://github.com/cran/ggupset +* Date/Publication: 2024-06-24 10:10:04 UTC +* Number of recursive dependencies: 46 -Run `revdepcheck::cloud_details(, "gggap")` for more info +Run `revdepcheck::cloud_details(, "ggupset")` for more info
@@ -7310,214 +6444,163 @@ Run `revdepcheck::cloud_details(, "gggap")` for more info * checking examples ... ERROR ``` - Running examples in ‘gggap-Ex.R’ failed + Running examples in ‘ggupset-Ex.R’ failed The error most likely occurred in: - > ### Name: gggap - > ### Title: Define Segments in y-Axis for 'ggplot2' - > ### Aliases: gggap + > ### Name: axis_combmatrix + > ### Title: Convert delimited text labels into a combination matrix axis + > ### Aliases: axis_combmatrix > > ### ** Examples > - > data(mtcars) + > library(ggplot2) ... - Backtrace: - ▆ - 1. ├─base (local) ``(x) - 2. └─ggplot2:::print.ggplot(x) - 3. ├─ggplot2::ggplot_gtable(data) - 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) - 5. └─ggplot2::calc_element("plot.margin", theme) - 6. └─cli::cli_abort(...) - 7. └─rlang::abort(...) + Datsun 710 Cyl: 4_Gears: 4 + Hornet 4 Drive Cyl: 6_Gears: 3 + Hornet Sportabout Cyl: 8_Gears: 3 + Valiant Cyl: 6_Gears: 3 + > ggplot(mtcars, aes(x=combined)) + + + geom_bar() + + + axis_combmatrix(sep = "_") + Error in as.unit(e2) : object is not coercible to a unit + Calls: ... polylineGrob -> is.unit -> unit.c -> Ops.unit -> as.unit Execution halted ``` -## In both - -* checking LazyData ... NOTE - ``` - 'LazyData' is specified without a 'data' directory - ``` - -# ggh4x +# ggVennDiagram
-* Version: 0.2.8 -* GitHub: https://github.com/teunbrand/ggh4x -* Source code: https://github.com/cran/ggh4x -* Date/Publication: 2024-01-23 21:00:02 UTC -* Number of recursive dependencies: 77 +* Version: 1.5.2 +* GitHub: https://github.com/gaospecial/ggVennDiagram +* Source code: https://github.com/cran/ggVennDiagram +* Date/Publication: 2024-02-20 08:10:02 UTC +* Number of recursive dependencies: 98 -Run `revdepcheck::cloud_details(, "ggh4x")` for more info +Run `revdepcheck::cloud_details(, "ggVennDiagram")` for more info
## Newly broken -* checking examples ... ERROR +* checking running R code from vignettes ... ERROR ``` - Running examples in ‘ggh4x-Ex.R’ failed - The error most likely occurred in: + Errors in running code in vignettes: + when running code in ‘fully-customed.Rmd’ + ... + [1] "b" "c" "e" "h" "k" "q" "s" "y" + + + > ggVennDiagram(y, show_intersect = TRUE, set_color = "black") + Warning in geom_text(aes(label = .data$count, text = .data$item), data = region_label) : + Ignoring unknown aesthetics: text - > ### Name: guide_dendro - > ### Title: Dendrogram guide - > ### Aliases: guide_dendro - > - > ### ** Examples - > - > clust <- hclust(dist(USArrests), "ave") ... - 9. └─ggplot2:::scale_apply(layer_data, y_vars, "map", SCALE_Y, self$panel_scales_y) - 10. └─base::lapply(...) - 11. └─ggplot2 (local) FUN(X[[i]], ...) - 12. └─base::lapply(...) - 13. └─ggplot2 (local) FUN(X[[i]], ...) - 14. └─scales[[i]][[method]](data[[var]][scale_index[[i]]]) - 15. └─ggplot2 (local) map(..., self = self) - 16. └─cli::cli_abort(...) - 17. └─rlang::abort(...) + Ignoring unknown aesthetics: text + + When sourcing ‘using-ggVennDiagram.R’: + Error: subscript out of bounds Execution halted - ``` - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(ggh4x) - Loading required package: ggplot2 - > - > test_check("ggh4x") - [ FAIL 7 | WARN 20 | SKIP 18 | PASS 740 ] - - ... - 14. └─base::lapply(...) - 15. └─ggplot2 (local) FUN(X[[i]], ...) - 16. └─scales[[i]][[method]](data[[var]][scale_index[[i]]]) - 17. └─ggplot2 (local) map(..., self = self) - 18. └─cli::cli_abort(...) - 19. └─rlang::abort(...) - - [ FAIL 7 | WARN 20 | SKIP 18 | PASS 740 ] - Error: Test failures - Execution halted + + ‘VennCalculator.Rmd’ using ‘UTF-8’... OK + ‘fully-customed.Rmd’ using ‘UTF-8’... failed + ‘using-ggVennDiagram.Rmd’ using ‘UTF-8’... failed + ‘using-new-shapes.Rmd’ using ‘UTF-8’... OK ``` * checking re-building of vignette outputs ... NOTE ``` Error(s) in re-building vignettes: - --- re-building ‘Facets.Rmd’ using rmarkdown + --- re-building ‘VennCalculator.Rmd’ using rmarkdown + --- finished re-building ‘VennCalculator.Rmd’ + + --- re-building ‘fully-customed.Rmd’ using rmarkdown ``` ## In both -* checking running R code from vignettes ... ERROR +* checking installed package size ... NOTE ``` - Errors in running code in vignettes: - when running code in ‘Miscellaneous.Rmd’ - ... - - > ggplot(diamonds, aes(price, carat, colour = clarity)) + - + geom_point(shape = ".") + scale_colour_brewer(palette = "Dark2", - + guide = "stri ..." ... [TRUNCATED] - Warning: The S3 guide system was deprecated in ggplot2 3.5.0. - ℹ It has been replaced by a ggproto system that can be extended. - - ... - ℹ Error occurred in the 1st layer. - Caused by error in `setup_params()`: - ! A discrete 'nbinom' distribution cannot be fitted to continuous data. - Execution halted - - ‘Facets.Rmd’ using ‘UTF-8’... OK - ‘Miscellaneous.Rmd’ using ‘UTF-8’... failed - ‘PositionGuides.Rmd’ using ‘UTF-8’... failed - ‘Statistics.Rmd’ using ‘UTF-8’... failed - ‘ggh4x.Rmd’ using ‘UTF-8’... OK + installed size is 11.1Mb + sub-directories of 1Mb or more: + doc 9.5Mb + help 1.1Mb ``` -# gghdx +# greatR
-* Version: 0.1.3 -* GitHub: https://github.com/OCHA-DAP/gghdx -* Source code: https://github.com/cran/gghdx -* Date/Publication: 2024-05-14 19:50:02 UTC -* Number of recursive dependencies: 82 +* Version: 2.0.0 +* GitHub: https://github.com/ruthkr/greatR +* Source code: https://github.com/cran/greatR +* Date/Publication: 2024-04-09 22:40:07 UTC +* Number of recursive dependencies: 77 -Run `revdepcheck::cloud_details(, "gghdx")` for more info +Run `revdepcheck::cloud_details(, "greatR")` for more info
## Newly broken -* checking examples ... ERROR - ``` - Running examples in ‘gghdx-Ex.R’ failed - The error most likely occurred in: - - > ### Name: gghdx - > ### Title: Set HDX theme and aesthetics - > ### Aliases: gghdx gghdx_reset - > - > ### ** Examples - > - > - ... - Backtrace: - ▆ - 1. ├─base (local) ``(x) - 2. └─ggplot2:::print.ggplot(x) - 3. ├─ggplot2::ggplot_gtable(data) - 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) - 5. └─ggplot2::calc_element("plot.margin", theme) - 6. └─cli::cli_abort(...) - 7. └─rlang::abort(...) - Execution halted - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘gghdx.Rmd’ using rmarkdown - ``` - -## In both - * checking running R code from vignettes ... ERROR ``` Errors in running code in vignettes: - when running code in ‘gghdx.Rmd’ + when running code in ‘process-results.Rmd’ ... - > p - - > library(gghdx) + > reg_summary$non_registered_genes + [1] "BRAA02G018970.3C" - > p + theme_hdx(base_family = "sans") + > plot(reg_summary, type = "registered", scatterplot_size = c(4, + + 3.5)) - When sourcing ‘gghdx.R’: - Error: Theme element `plot.margin` must have class . + When sourcing ‘process-results.R’: + Error: object is not a unit Execution halted - ‘gghdx.Rmd’ using ‘UTF-8’... failed + ‘data-requirement.Rmd’ using ‘UTF-8’... OK + ‘process-results.Rmd’ using ‘UTF-8’... failed + ‘register-data-manually.Rmd’ using ‘UTF-8’... OK + ‘register-data.Rmd’ using ‘UTF-8’... OK ``` -# gghighlight +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + ... + --- re-building ‘data-requirement.Rmd’ using rmarkdown + --- finished re-building ‘data-requirement.Rmd’ + + --- re-building ‘process-results.Rmd’ using rmarkdown + + Quitting from lines 76-81 [plot-summary-results] (process-results.Rmd) + Error: processing vignette 'process-results.Rmd' failed with diagnostics: + object is not a unit + ... + --- finished re-building ‘register-data-manually.Rmd’ + + --- re-building ‘register-data.Rmd’ using rmarkdown + --- finished re-building ‘register-data.Rmd’ + + SUMMARY: processing the following file failed: + ‘process-results.Rmd’ + + Error: Vignette re-building failed. + Execution halted + ``` + +# Greymodels
-* Version: 0.4.1 -* GitHub: https://github.com/yutannihilation/gghighlight -* Source code: https://github.com/cran/gghighlight -* Date/Publication: 2023-12-16 01:00:02 UTC -* Number of recursive dependencies: 85 +* Version: 2.0.1 +* GitHub: https://github.com/havishaJ/Greymodels +* Source code: https://github.com/cran/Greymodels +* Date/Publication: 2022-12-05 12:42:35 UTC +* Number of recursive dependencies: 91 -Run `revdepcheck::cloud_details(, "gghighlight")` for more info +Run `revdepcheck::cloud_details(, "Greymodels")` for more info
@@ -7525,92 +6608,134 @@ Run `revdepcheck::cloud_details(, "gghighlight")` for more info * checking examples ... ERROR ``` - Running examples in ‘gghighlight-Ex.R’ failed + Running examples in ‘Greymodels-Ex.R’ failed The error most likely occurred in: - > ### Name: gghighlight - > ### Title: Highlight Data With Predicate - > ### Aliases: gghighlight + > ### Name: Plots + > ### Title: plots + > ### Aliases: plots plotrm plotsmv1 plotsmv2 plotsigndgm plots_mdbgm12 > > ### ** Examples > - > d <- data.frame( + > # Plots - EPGM (1, 1) model ... - 8. │ ├─purrr:::with_indexed_errors(...) - 9. │ │ └─base::withCallingHandlers(...) - 10. │ ├─purrr:::call_with_cleanup(...) - 11. │ └─gghighlight (local) .f(.x[[i]], .y[[i]], ...) - 12. │ └─gghighlight:::get_default_aes_param(nm, layer$geom, layer$mapping) - 13. └─base::.handleSimpleError(...) - 14. └─purrr (local) h(simpleError(msg, call)) - 15. └─cli::cli_abort(...) - 16. └─rlang::abort(...) + + geom_point(data = set4, aes(x = CI, y = y), shape = 23, color = "black") + + + geom_line(data = xy1, aes(x = x, y = y,color = "Raw Data")) + + + geom_line(data = xy2, aes(x = x, y = y,color = "Fitted&Forecasts")) + + + geom_line(data = set3, aes(x = CI, y = y,color = "LowerBound"), linetype=2) + + + geom_line(data = set4, aes(x = CI, y = y,color = "UpperBound"), linetype=2) + + + scale_color_manual(name = "Label",values = colors) + > r <- ggplotly(p) + Error in pm[[2]] : subscript out of bounds + Calls: ggplotly -> ggplotly.ggplot -> gg2list Execution halted ``` +# gtExtras + +
+ +* Version: 0.5.0 +* GitHub: https://github.com/jthomasmock/gtExtras +* Source code: https://github.com/cran/gtExtras +* Date/Publication: 2023-09-15 22:32:06 UTC +* Number of recursive dependencies: 105 + +Run `revdepcheck::cloud_details(, "gtExtras")` for more info + +
+ +## Newly broken + * checking tests ... ERROR ``` Running ‘testthat.R’ Running the tests in ‘tests/testthat.R’ failed. Complete output: > library(testthat) - > library(gghighlight) - Loading required package: ggplot2 - > - > test_check("gghighlight") - label_key: type - label_key: type + > library(gtExtras) + Loading required package: gt + + Attaching package: 'gt' + + The following object is masked from 'package:testthat': ... - 15. └─cli::cli_abort(...) - 16. └─rlang::abort(...) + ══ Failed tests ════════════════════════════════════════════════════════════════ + ── Failure ('test-gt_plt_bar.R:44:3'): gt_plt_bar svg is created and has specific values ── + `bar_neg_vals` (`actual`) not equal to c("49.19", "32.79", "16.40", "16.40", "32.79", "49.19") (`expected`). - [ FAIL 2 | WARN 2 | SKIP 1 | PASS 178 ] - Deleting unused snapshots: - • vdiffr/simple-bar-chart-with-facet.svg - • vdiffr/simple-line-chart.svg - • vdiffr/simple-point-chart.svg + `actual`: "49.19" "32.79" "16.40" "0.00" "0.00" "0.00" + `expected`: "49.19" "32.79" "16.40" "16.40" "32.79" "49.19" + + [ FAIL 1 | WARN 14 | SKIP 23 | PASS 115 ] Error: Test failures Execution halted ``` -## In both +# HaploCatcher + +
+ +* Version: 1.0.4 +* GitHub: NA +* Source code: https://github.com/cran/HaploCatcher +* Date/Publication: 2023-04-21 23:32:39 UTC +* Number of recursive dependencies: 112 + +Run `revdepcheck::cloud_details(, "HaploCatcher")` for more info + +
+ +## Newly broken * checking running R code from vignettes ... ERROR ``` Errors in running code in vignettes: - when running code in ‘gghighlight.Rmd’ + when running code in ‘An_Intro_to_HaploCatcher.Rmd’ ... - + 0, label_key = type) - Warning in is.na(non_null_default_aes[[aes_param_name]]) : - is.na() applied to non-(list or vector) of type 'language' + > set.seed(NULL) - When sourcing ‘gghighlight.R’: - Error: ℹ In index: 1. - Caused by error in `aes_param_name %in% names(non_null_default_aes) && is.na(non_null_default_aes[[ - aes_param_name]])`: - ! 'length = 2' in coercion to 'logical(1)' + > results1 <- auto_locus(geno_mat = geno_mat, gene_file = gene_comp, + + gene_name = "sst1_solid_stem", marker_info = marker_info, + + chromosom .... [TRUNCATED] + Loading required package: lattice + + When sourcing ‘An_Intro_to_HaploCatcher.R’: + Error: object is not a unit Execution halted - ‘gghighlight.Rmd’ using ‘UTF-8’... failed + ‘An_Intro_to_HaploCatcher.Rmd’ using ‘UTF-8’... failed ``` * checking re-building of vignette outputs ... NOTE ``` Error(s) in re-building vignettes: - --- re-building ‘gghighlight.Rmd’ using rmarkdown + ... + --- re-building ‘An_Intro_to_HaploCatcher.Rmd’ using rmarkdown + + Quitting from lines 242-253 [example_models_1] (An_Intro_to_HaploCatcher.Rmd) + Error: processing vignette 'An_Intro_to_HaploCatcher.Rmd' failed with diagnostics: + object is not a unit + --- failed re-building ‘An_Intro_to_HaploCatcher.Rmd’ + + SUMMARY: processing the following file failed: + ‘An_Intro_to_HaploCatcher.Rmd’ + + Error: Vignette re-building failed. + Execution halted ``` -# ggHoriPlot +# healthyR
-* Version: 1.0.1 -* GitHub: https://github.com/rivasiker/ggHoriPlot -* Source code: https://github.com/cran/ggHoriPlot -* Date/Publication: 2022-10-11 16:22:33 UTC -* Number of recursive dependencies: 117 +* Version: 0.2.2 +* GitHub: https://github.com/spsanderson/healthyR +* Source code: https://github.com/cran/healthyR +* Date/Publication: 2024-07-01 13:20:02 UTC +* Number of recursive dependencies: 146 -Run `revdepcheck::cloud_details(, "ggHoriPlot")` for more info +Run `revdepcheck::cloud_details(, "healthyR")` for more info
@@ -7619,40 +6744,49 @@ Run `revdepcheck::cloud_details(, "ggHoriPlot")` for more info * checking running R code from vignettes ... ERROR ``` Errors in running code in vignettes: - when running code in ‘ggHoriPlot.Rmd’ + when running code in ‘getting-started.Rmd’ ... - > mid <- sum(range(dat_tab$y, na.rm = T))/2 - > b <- plotAllLayers(dat_tab, mid, cutpoints$cuts, cutpoints$color) + > ts_alos_plt(.data = df_tbl, .date_col = Date, .value_col = Values, + + .by = "month", .interactive = FALSE) - > b/a + plot_layout(guides = "collect", heights = c(6, - + 1)) + > ts_alos_plt(.data = df_tbl, .date_col = Date, .value_col = Values, + + .by = "month", .interactive = TRUE) - When sourcing ‘ggHoriPlot.R’: - Error: object is not a unit + When sourcing ‘getting-started.R’: + Error: subscript out of bounds Execution halted - ‘examples.Rmd’ using ‘UTF-8’... OK - ‘ggHoriPlot.Rmd’ using ‘UTF-8’... failed + ‘getting-started.Rmd’ using ‘UTF-8’... failed ``` * checking re-building of vignette outputs ... NOTE ``` Error(s) in re-building vignettes: - --- re-building ‘examples.Rmd’ using rmarkdown + --- re-building ‘getting-started.Rmd’ using rmarkdown ``` -# ggiraph +## In both + +* checking installed package size ... NOTE + ``` + installed size is 6.6Mb + sub-directories of 1Mb or more: + data 2.5Mb + doc 3.7Mb + ``` + +# healthyR.ts
-* Version: 0.8.10 -* GitHub: https://github.com/davidgohel/ggiraph -* Source code: https://github.com/cran/ggiraph -* Date/Publication: 2024-05-17 12:10:02 UTC -* Number of recursive dependencies: 95 +* Version: 0.3.0 +* GitHub: https://github.com/spsanderson/healthyR.ts +* Source code: https://github.com/cran/healthyR.ts +* Date/Publication: 2023-11-15 06:00:05 UTC +* Number of recursive dependencies: 221 -Run `revdepcheck::cloud_details(, "ggiraph")` for more info +Run `revdepcheck::cloud_details(, "healthyR.ts")` for more info
@@ -7660,174 +6794,139 @@ Run `revdepcheck::cloud_details(, "ggiraph")` for more info * checking examples ... ERROR ``` - Running examples in ‘ggiraph-Ex.R’ failed + Running examples in ‘healthyR.ts-Ex.R’ failed The error most likely occurred in: - > ### Name: geom_path_interactive - > ### Title: Create interactive observations connections - > ### Aliases: geom_path_interactive geom_line_interactive - > ### geom_step_interactive + > ### Name: tidy_fft + > ### Title: Tidy Style FFT + > ### Aliases: tidy_fft > > ### ** Examples > + > suppressPackageStartupMessages(library(dplyr)) ... - 20. │ └─base::lapply(...) - 21. │ └─ggplot2 (local) FUN(X[[i]], ...) - 22. │ ├─rlang::inject(self$draw_panel(data, panel_params, coord, !!!params)) - 23. │ └─self$draw_panel(...) - 24. └─base::.handleSimpleError(...) - 25. └─rlang (local) h(simpleError(msg, call)) - 26. └─handlers[[1L]](cnd) - 27. └─cli::cli_abort(...) - 28. └─rlang::abort(...) + > a <- tidy_fft( + + .data = data_tbl, + + .value_col = value, + + .date_col = date_col, + + .harmonics = 3, + + .frequency = 12 + + ) + Error in pm[[2]] : subscript out of bounds + Calls: tidy_fft -> -> ggplotly.ggplot -> gg2list Execution halted ``` -* checking tests ... ERROR +* checking running R code from vignettes ... ERROR ``` - Running ‘tinytest.R’ - Running the tests in ‘tests/tinytest.R’ failed. - Complete output: - > if (requireNamespace("tinytest", quietly = TRUE)) { - + tinytest::test_package("ggiraph") - + } - - test-annotate_interactive.R... 0 tests - test-annotate_interactive.R... 0 tests - test-annotate_interactive.R... 0 tests - ... - 30. │ └─base::lapply(...) - 31. │ └─ggplot2 (local) FUN(X[[i]], ...) - 32. │ ├─rlang::inject(self$draw_panel(data, panel_params, coord, !!!params)) - 33. │ └─self$draw_panel(...) - 34. └─base::.handleSimpleError(...) - 35. └─rlang (local) h(simpleError(msg, call)) - 36. └─handlers[[1L]](cnd) - 37. └─cli::cli_abort(...) - 38. └─rlang::abort(...) - Execution halted + Errors in running code in vignettes: + when running code in ‘using-tidy-fft.Rmd’ + ... + $ value 112, 118, 132, 129, 121, 135, 148, 148, 136, 119, 104, 118, 1… + + > suppressPackageStartupMessages(library(timetk)) + + > data_tbl %>% plot_time_series(.date_var = date_col, + + .value = value) + + When sourcing ‘using-tidy-fft.R’: + Error: subscript out of bounds + Execution halted + + ‘getting-started.Rmd’ using ‘UTF-8’... OK + ‘using-tidy-fft.Rmd’ using ‘UTF-8’... failed ``` -## In both - -* checking package dependencies ... NOTE +* checking re-building of vignette outputs ... NOTE ``` - Package suggested but not available for checking: ‘quantreg’ + Error(s) in re-building vignettes: + --- re-building ‘getting-started.Rmd’ using rmarkdown ``` +## In both + * checking installed package size ... NOTE ``` - installed size is 9.7Mb + installed size is 6.3Mb sub-directories of 1Mb or more: - R 1.5Mb - libs 6.9Mb + doc 5.2Mb ``` -# ggiraphExtra +# heatmaply
-* Version: 0.3.0 -* GitHub: https://github.com/cardiomoon/ggiraphExtra -* Source code: https://github.com/cran/ggiraphExtra -* Date/Publication: 2020-10-06 07:00:02 UTC -* Number of recursive dependencies: 124 +* Version: 1.5.0 +* GitHub: https://github.com/talgalili/heatmaply +* Source code: https://github.com/cran/heatmaply +* Date/Publication: 2023-10-06 20:50:02 UTC +* Number of recursive dependencies: 111 -Run `revdepcheck::cloud_details(, "ggiraphExtra")` for more info +Run `revdepcheck::cloud_details(, "heatmaply")` for more info
## Newly broken -* checking examples ... ERROR +* checking tests ... ERROR ``` - Running examples in ‘ggiraphExtra-Ex.R’ failed - The error most likely occurred in: - - > ### Name: ggAncova - > ### Title: Make an interactive plot for an ANCOVA model - > ### Aliases: ggAncova ggAncova.default ggAncova.formula ggAncova.lm - > - > ### ** Examples - > - > require(moonBook) + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(heatmaply) + Loading required package: plotly + Loading required package: ggplot2 + + Attaching package: 'plotly' + ... - 24. │ └─base::lapply(...) - 25. │ └─ggplot2 (local) FUN(X[[i]], ...) - 26. │ ├─rlang::inject(self$draw_panel(data, panel_params, coord, !!!params)) - 27. │ └─self$draw_panel(...) - 28. └─base::.handleSimpleError(...) - 29. └─rlang (local) h(simpleError(msg, call)) - 30. └─handlers[[1L]](cnd) - 31. └─cli::cli_abort(...) - 32. └─rlang::abort(...) - Execution halted + 4. │ │ └─base::withCallingHandlers(...) + 5. │ └─rlang::eval_bare(quo_get_expr(.quo), quo_get_env(.quo)) + 6. ├─heatmaply:::predict_colors(ggplotly(g), plot_method = "ggplot") + 7. ├─plotly::ggplotly(g) + 8. └─plotly:::ggplotly.ggplot(g) + 9. └─plotly::gg2list(...) + + [ FAIL 58 | WARN 0 | SKIP 0 | PASS 193 ] + Error: Test failures + Execution halted ``` * checking running R code from vignettes ... ERROR ``` Errors in running code in vignettes: - when running code in ‘introduction.Rmd’ + when running code in ‘heatmaply.Rmd’ ... - > ggPoints(aes(x = wt, y = mpg, color = am), data = mtcars, - + method = "lm", interactive = TRUE) + > library("heatmaply") - When sourcing ‘introduction.R’: - Error: Problem while converting geom to grob. - ℹ Error occurred in the 3rd layer. - Caused by error in `draw_panel()`: - ! unused argument (arrow.fill = NULL) + > library("heatmaply") + + > heatmaply(mtcars) + + When sourcing ‘heatmaply.R’: + Error: subscript out of bounds Execution halted - ‘ggPredict.Rmd’ using ‘UTF-8’... OK - ‘introduction.Rmd’ using ‘UTF-8’... failed + ‘heatmaply.Rmd’ using ‘UTF-8’... failed ``` * checking re-building of vignette outputs ... NOTE ``` Error(s) in re-building vignettes: - --- re-building ‘ggPredict.Rmd’ using rmarkdown - ``` - -# ggmap - -
- -* Version: 4.0.0 -* GitHub: https://github.com/dkahle/ggmap -* Source code: https://github.com/cran/ggmap -* Date/Publication: 2023-11-19 08:10:02 UTC -* Number of recursive dependencies: 66 - -Run `revdepcheck::cloud_details(, "ggmap")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘ggmap-Ex.R’ failed - The error most likely occurred in: + ... + --- re-building ‘heatmaply.Rmd’ using rmarkdown - > ### Name: theme_nothing - > ### Title: Make a blank ggplot2 theme. - > ### Aliases: theme_nothing - > - > ### ** Examples - > - > - ... - Backtrace: - ▆ - 1. ├─base (local) ``(x) - 2. └─ggplot2:::print.ggplot(x) - 3. ├─ggplot2::ggplot_gtable(data) - 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) - 5. └─ggplot2::calc_element("plot.margin", theme) - 6. └─cli::cli_abort(...) - 7. └─rlang::abort(...) + Quitting from lines 109-111 [unnamed-chunk-5] (heatmaply.Rmd) + Error: processing vignette 'heatmaply.Rmd' failed with diagnostics: + subscript out of bounds + --- failed re-building ‘heatmaply.Rmd’ + + SUMMARY: processing the following file failed: + ‘heatmaply.Rmd’ + + Error: Vignette re-building failed. Execution halted ``` @@ -7835,22 +6934,22 @@ Run `revdepcheck::cloud_details(, "ggmap")` for more info * checking installed package size ... NOTE ``` - installed size is 7.4Mb + installed size is 5.5Mb sub-directories of 1Mb or more: - data 7.0Mb + doc 5.1Mb ``` -# ggmice +# hermiter
-* Version: 0.1.0 -* GitHub: https://github.com/amices/ggmice -* Source code: https://github.com/cran/ggmice -* Date/Publication: 2023-08-07 14:20:02 UTC -* Number of recursive dependencies: 120 +* Version: 2.3.1 +* GitHub: https://github.com/MikeJaredS/hermiter +* Source code: https://github.com/cran/hermiter +* Date/Publication: 2024-03-06 23:50:02 UTC +* Number of recursive dependencies: 79 -Run `revdepcheck::cloud_details(, "ggmice")` for more info +Run `revdepcheck::cloud_details(, "hermiter")` for more info
@@ -7859,137 +6958,114 @@ Run `revdepcheck::cloud_details(, "ggmice")` for more info * checking running R code from vignettes ... ERROR ``` Errors in running code in vignettes: - when running code in ‘old_friends.Rmd’ + when running code in ‘hermiter.Rmd’ ... - layout - - - > p <- plot_flux(dat) + > p2 <- ggplot(df_pdf_cdf) + geom_tile(aes(X, Y, fill = pdf_est)) + + + scale_fill_continuous_sequential(palette = "Oslo", breaks = seq(0, + + .... [TRUNCATED] - > ggplotly(p) + > p1 + ggtitle("Actual PDF") + theme(legend.title = element_blank()) + + + p2 + ggtitle("Estimated PDF") + theme(legend.title = element_blank()) + .... [TRUNCATED] - When sourcing ‘old_friends.R’: - Error: subscript out of bounds + When sourcing ‘hermiter.R’: + Error: object is not a unit Execution halted - ‘ggmice.Rmd’ using ‘UTF-8’... OK - ‘old_friends.Rmd’ using ‘UTF-8’... failed + ‘hermiter.Rmd’ using ‘UTF-8’... failed ``` * checking re-building of vignette outputs ... NOTE ``` Error(s) in re-building vignettes: - --- re-building ‘ggmice.Rmd’ using rmarkdown + --- re-building ‘hermiter.Rmd’ using rmarkdown ``` -# ggmulti +## In both + +* checking installed package size ... NOTE + ``` + installed size is 6.5Mb + sub-directories of 1Mb or more: + R 2.6Mb + doc 1.9Mb + libs 1.8Mb + ``` + +* checking for GNU extensions in Makefiles ... NOTE + ``` + GNU make is a SystemRequirements. + ``` + +# hesim
-* Version: 1.0.7 -* GitHub: NA -* Source code: https://github.com/cran/ggmulti -* Date/Publication: 2024-04-09 09:40:05 UTC -* Number of recursive dependencies: 125 +* Version: 0.5.4 +* GitHub: https://github.com/hesim-dev/hesim +* Source code: https://github.com/cran/hesim +* Date/Publication: 2024-02-12 01:10:03 UTC +* Number of recursive dependencies: 107 -Run `revdepcheck::cloud_details(, "ggmulti")` for more info +Run `revdepcheck::cloud_details(, "hesim")` for more info
## Newly broken -* checking examples ... ERROR - ``` - Running examples in ‘ggmulti-Ex.R’ failed - The error most likely occurred in: - - > ### Name: coord_radial - > ### Title: Radial axes - > ### Aliases: coord_radial - > - > ### ** Examples - > - > if(require("dplyr")) { - ... - - The following objects are masked from ‘package:base’: - - intersect, setdiff, setequal, union - - Error in use_defaults(..., self = self) : - unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, "black", TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), NULL, list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), 5.5, c(5.5, 5.5, 5.5, 5.5), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.75, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, - NULL, NULL, NULL, 1, 90, NULL, c(0, 2.75, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 1, NULL, NULL, NULL, c(0, 2.2, 0, 0), NULL, TRUE), NULL, l - Calls: ... -> -> compute_geom_2 -> - Execution halted - ``` - * checking tests ... ERROR ``` Running ‘testthat.R’ Running the tests in ‘tests/testthat.R’ failed. Complete output: - > - > > library(testthat) - > library(ggmulti) - Loading required package: ggplot2 - - Attaching package: 'ggmulti' - ... - ── Error ('test_stat.R:18:3'): test stat ─────────────────────────────────────── - Error in `stat_hist_(prop = 0.5)`: Problem while setting up geom aesthetics. - ℹ Error occurred in the 1st layer. - Caused by error in `check_aesthetics()`: - ! Aesthetics must be either length 1 or the same as the data (83). - ✖ Fix the following mappings: `width`. - - [ FAIL 5 | WARN 1 | SKIP 0 | PASS 21 ] + > library(hesim) + > + > test_check("hesim") + sample = 1 + sample = 2 + [ FAIL 4 | WARN 0 | SKIP 0 | PASS 1121 ] + ... + ── Failure ('test-plot.R:95:3'): autoplot.stateprobs() allows confidence intervals ── + p$labels$fill not equal to "strategy_id". + target is NULL, current is character + ── Failure ('test-plot.R:99:3'): autoplot.stateprobs() allows confidence intervals ── + p$labels$fill not equal to "strategy_id". + target is NULL, current is character + + [ FAIL 4 | WARN 0 | SKIP 0 | PASS 1121 ] Error: Test failures Execution halted ``` -* checking running R code from vignettes ... ERROR +## In both + +* checking installed package size ... NOTE ``` - Errors in running code in vignettes: - when running code in ‘glyph.Rmd’ - ... - + Sepal.Width, colour = Species), serialaxes.data = iris, axes.layout = "radia ..." ... [TRUNCATED] - - When sourcing ‘glyph.R’: - Error: Base operators are not defined for quosures. Do you need to unquote the - quosure? - - # Bad: myquosure / rhs - ... - > p - - When sourcing ‘highDim.R’: - Error: unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, "black", TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), NULL, list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), 5.5, c(5.5, 5.5, 5.5, 5.5), NULL, NULL, list(), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), - list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, NULL, c(0, 0, 0, 2.2), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0.5, NULL, NULL, NULL, c(0, 2.2, 0, 2.2), NULL, TRUE), list("grey20", NULL, NULL, NULL, FALSE, "grey20", - Execution halted - - ‘glyph.Rmd’ using ‘UTF-8’... failed - ‘highDim.Rmd’ using ‘UTF-8’... failed - ‘histogram-density-.Rmd’ using ‘UTF-8’... OK + installed size is 37.4Mb + sub-directories of 1Mb or more: + R 1.5Mb + data 1.5Mb + doc 2.2Mb + libs 31.4Mb ``` -* checking re-building of vignette outputs ... NOTE +* checking dependencies in R code ... NOTE ``` - Error(s) in re-building vignettes: - --- re-building ‘glyph.Rmd’ using rmarkdown + Namespace in Imports field not imported from: ‘R6’ + All declared Imports should be used. ``` -# ggparallel +# hidecan
-* Version: 0.4.0 -* GitHub: https://github.com/heike/ggparallel -* Source code: https://github.com/cran/ggparallel -* Date/Publication: 2024-03-09 22:00:02 UTC -* Number of recursive dependencies: 51 +* Version: 1.1.0 +* GitHub: https://github.com/PlantandFoodResearch/hidecan +* Source code: https://github.com/cran/hidecan +* Date/Publication: 2023-02-10 09:40:02 UTC +* Number of recursive dependencies: 90 -Run `revdepcheck::cloud_details(, "ggparallel")` for more info +Run `revdepcheck::cloud_details(, "hidecan")` for more info
@@ -8005,32 +7081,84 @@ Run `revdepcheck::cloud_details(, "ggparallel")` for more info > # > # Where should you do additional test configuration? > # Learn more about the roles of various files in: - > # * https://r-pkgs.org/testing-design.html#sec-tests-files-overview - > # * https://testthat.r-lib.org/articles/special-files.html + > # * https://r-pkgs.org/tests.html + > # * https://testthat.r-lib.org/reference/test_package.html#special-files ... - 12. └─self$get_layer_key(params, layers[include], data[include], theme) - 13. └─ggplot2 (local) get_layer_key(...) - 14. └─base::Map(...) - 15. └─base::mapply(FUN = f, ..., SIMPLIFY = FALSE) - 16. └─ggplot2 (local) ``(layer = dots[[1L]][[1L]], df = dots[[2L]][[1L]]) - 17. └─layer$compute_geom_2(key, single_params, theme) + 8. └─hidecan::create_hidecan_plot(...) + 9. └─ggplot2:::`+.gg`(p, ggnewscale::new_scale_fill()) + 10. └─ggplot2:::add_ggplot(e1, e2, e2name) + 11. ├─ggplot2::ggplot_add(object, p, objectname) + 12. └─ggnewscale:::ggplot_add.new_aes(object, p, objectname) + 13. └─ggnewscale:::bump_aes_labels(plot$labels, new_aes = object) - [ FAIL 1 | WARN 0 | SKIP 0 | PASS 0 ] + [ FAIL 4 | WARN 0 | SKIP 1 | PASS 89 ] Error: Test failures Execution halted ``` -# ggpicrust2 +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + ... + --- re-building ‘hidecan-step-by-step.Rmd’ using rmarkdown + + Quitting from lines 168-174 [create-hidecan-plot] (hidecan-step-by-step.Rmd) + Error: processing vignette 'hidecan-step-by-step.Rmd' failed with diagnostics: + attempt to set an attribute on NULL + --- failed re-building ‘hidecan-step-by-step.Rmd’ + + --- re-building ‘hidecan.Rmd’ using rmarkdown + ... + Quitting from lines 97-105 [hidecan-plot] (hidecan.Rmd) + Error: processing vignette 'hidecan.Rmd' failed with diagnostics: + attempt to set an attribute on NULL + --- failed re-building ‘hidecan.Rmd’ + + SUMMARY: processing the following files failed: + ‘hidecan-step-by-step.Rmd’ ‘hidecan.Rmd’ + + Error: Vignette re-building failed. + Execution halted + ``` + +## In both + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘hidecan-step-by-step.Rmd’ + ... + 5 PGSC0003DMG400005279 ST4.03ch05 42523943 42525912 peroxida… peroxida… 4.25e7 + 6 PGSC0003DMG400007782 ST4.03ch03 38537202 38540209 PHO1A PHO1A 3.85e7 + + > gwas_wrong_input <- select(x[["GWAS"]], -chromosome) + + > GWAS_data(gwas_wrong_input) + + ... + + > hidecan_plot(gwas_list = x[["GWAS"]], de_list = x[["DE"]], + + can_list = x[["CAN"]], score_thr_gwas = -log10(1e-04), score_thr_de = -log10(0.05) .... [TRUNCATED] + + When sourcing ‘hidecan.R’: + Error: attempt to set an attribute on NULL + Execution halted + + ‘hidecan-step-by-step.Rmd’ using ‘UTF-8’... failed + ‘hidecan.Rmd’ using ‘UTF-8’... failed + ``` + +# HVT
-* Version: 1.7.3 -* GitHub: https://github.com/cafferychen777/ggpicrust2 -* Source code: https://github.com/cran/ggpicrust2 -* Date/Publication: 2023-11-08 16:10:02 UTC -* Number of recursive dependencies: 238 +* Version: 24.5.2 +* GitHub: https://github.com/Mu-Sigma/HVT +* Source code: https://github.com/cran/HVT +* Date/Publication: 2024-05-15 08:50:21 UTC +* Number of recursive dependencies: 200 -Run `revdepcheck::cloud_details(, "ggpicrust2")` for more info +Run `revdepcheck::cloud_details(, "HVT")` for more info
@@ -8038,128 +7166,145 @@ Run `revdepcheck::cloud_details(, "ggpicrust2")` for more info * checking examples ... ERROR ``` - Running examples in ‘ggpicrust2-Ex.R’ failed + Running examples in ‘HVT-Ex.R’ failed The error most likely occurred in: - > ### Name: pathway_pca - > ### Title: Perform Principal Component Analysis (PCA) on functional pathway - > ### abundance data and create visualizations of the PCA results. - > ### Aliases: pathway_pca + > ### Name: getTransitionProbability + > ### Title: Creating Transition Probabilities list + > ### Aliases: getTransitionProbability + > ### Keywords: Transition_or_Prediction > > ### ** Examples > ... - > - > # Create example metadata - > # Please ensure the sample IDs in the metadata have the column name "sample_name" - > metadata_example <- data.frame(sample_name = colnames(kegg_abundance_example), - + group = factor(rep(c("Control", "Treatment"), each = 5))) - > - > pca_plot <- pathway_pca(kegg_abundance_example, metadata_example, "group") - Error in identicalUnits(x) : object is not a unit - Calls: pathway_pca ... assemble_guides -> guides_build -> unit.c -> identicalUnits + Ignoring unknown parameters: `check_overlap` + Scale for x is already present. + Adding another scale for x, which will replace the existing scale. + Scale for y is already present. + Adding another scale for y, which will replace the existing scale. + Warning in geom_polygon(data = boundaryCoords2, aes(x = bp.x, y = bp.y, : + Ignoring unknown aesthetics: text + Error in pm[[2]] : subscript out of bounds + Calls: scoreHVT -> -> ggplotly.ggplot -> gg2list Execution halted ``` -## In both +# hypsoLoop -* checking installed package size ... NOTE +
+ +* Version: 0.2.0 +* GitHub: NA +* Source code: https://github.com/cran/hypsoLoop +* Date/Publication: 2022-02-08 09:00:02 UTC +* Number of recursive dependencies: 97 + +Run `revdepcheck::cloud_details(, "hypsoLoop")` for more info + +
+ +## Newly broken + +* checking whether package ‘hypsoLoop’ can be installed ... WARNING ``` - installed size is 5.5Mb - sub-directories of 1Mb or more: - R 2.1Mb - data 2.0Mb + Found the following significant warnings: + Warning: replacing previous import ‘ggplot2::set_theme’ by ‘sjPlot::set_theme’ when loading ‘hypsoLoop’ + See ‘/tmp/workdir/hypsoLoop/new/hypsoLoop.Rcheck/00install.out’ for details. ``` -# ggpie +# ICvectorfields
-* Version: 0.2.5 -* GitHub: https://github.com/showteeth/ggpie -* Source code: https://github.com/cran/ggpie -* Date/Publication: 2022-11-16 07:40:06 UTC -* Number of recursive dependencies: 59 +* Version: 0.1.2 +* GitHub: https://github.com/goodsman/ICvectorfields +* Source code: https://github.com/cran/ICvectorfields +* Date/Publication: 2022-02-26 22:30:02 UTC +* Number of recursive dependencies: 93 -Run `revdepcheck::cloud_details(, "ggpie")` for more info +Run `revdepcheck::cloud_details(, "ICvectorfields")` for more info
## Newly broken -* checking examples ... ERROR - ``` - Running examples in ‘ggpie-Ex.R’ failed - The error most likely occurred in: - - > ### Name: ggdonut - > ### Title: Create donut plot. - > ### Aliases: ggdonut - > - > ### ** Examples - > - > library(ggpie) - ... - Backtrace: - ▆ - 1. ├─base (local) ``(x) - 2. └─ggplot2:::print.ggplot(x) - 3. ├─ggplot2::ggplot_gtable(data) - 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) - 5. └─ggplot2::calc_element("plot.margin", theme) - 6. └─cli::cli_abort(...) - 7. └─rlang::abort(...) - Execution halted - ``` - * checking running R code from vignettes ... ERROR ``` Errors in running code in vignettes: - when running code in ‘ggpie.Rmd’ + when running code in ‘Using_ICvectorfields.Rmd’ ... - $ x : num [1:53940] 3.95 3.89 4.05 4.2 4.34 3.94 3.95 4.07 3.87 4 ... - $ y : num [1:53940] 3.98 3.84 4.07 4.23 4.35 3.96 3.98 4.11 3.78 4.05 ... - $ z : num [1:53940] 2.43 2.31 2.31 2.63 2.75 2.48 2.47 2.53 2.49 2.39 ... + 3 -3.89153024 -0.09851975 + 4 -0.09851975 3.89153024 - > ggpie(data = diamonds, group_key = "cut", count_type = "full", - + label_type = "none") + > SimVF = ggplot() + xlim(c(-5, 5)) + ylim(c(-5, 5)) + + + geom_raster(data = SimData, aes(x = xcoord, y = ycoord, fill = t1)) + + + scale_fill_ .... [TRUNCATED] - When sourcing ‘ggpie.R’: - Error: Theme element `plot.margin` must have class . + When sourcing ‘Using_ICvectorfields.R’: + Error: attempt to set an attribute on NULL Execution halted - ‘ggpie.Rmd’ using ‘UTF-8’... failed + ‘Using_ICvectorfields.Rmd’ using ‘UTF-8’... failed ``` * checking re-building of vignette outputs ... NOTE ``` Error(s) in re-building vignettes: + --- re-building ‘Using_ICvectorfields.Rmd’ using rmarkdown + ``` + +# idopNetwork + +
+ +* Version: 0.1.2 +* GitHub: https://github.com/cxzdsa2332/idopNetwork +* Source code: https://github.com/cran/idopNetwork +* Date/Publication: 2023-04-18 06:50:02 UTC +* Number of recursive dependencies: 77 + +Run `revdepcheck::cloud_details(, "idopNetwork")` for more info + +
+ +## Newly broken + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘idopNetwork_vignette.Rmd’ ... - --- re-building ‘ggpie.Rmd’ using rmarkdown - Quitting from lines 73-75 [pie_basic_no_label] (ggpie.Rmd) - Error: processing vignette 'ggpie.Rmd' failed with diagnostics: - Theme element `plot.margin` must have class . - --- failed re-building ‘ggpie.Rmd’ + > qdODE_plot_base(ode.test) - SUMMARY: processing the following file failed: - ‘ggpie.Rmd’ + > ode.module = test_result$d1_module - Error: Vignette re-building failed. + > qdODE_plot_all(ode.module) + + When sourcing ‘idopNetwork_vignette.R’: + Error: object is not a unit Execution halted + + ‘idopNetwork_vignette.Rmd’ using ‘UTF-8’... failed ``` -# ggplotlyExtra +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘idopNetwork_vignette.Rmd’ using rmarkdown + ``` + +# inferCSN
-* Version: 0.0.1 -* GitHub: NA -* Source code: https://github.com/cran/ggplotlyExtra -* Date/Publication: 2019-12-02 16:20:06 UTC -* Number of recursive dependencies: 70 +* Version: 1.0.5 +* GitHub: https://github.com/mengxu98/inferCSN +* Source code: https://github.com/cran/inferCSN +* Date/Publication: 2024-06-26 12:10:02 UTC +* Number of recursive dependencies: 185 -Run `revdepcheck::cloud_details(, "ggplotlyExtra")` for more info +Run `revdepcheck::cloud_details(, "inferCSN")` for more info
@@ -8167,47 +7312,50 @@ Run `revdepcheck::cloud_details(, "ggplotlyExtra")` for more info * checking examples ... ERROR ``` - Running examples in ‘ggplotlyExtra-Ex.R’ failed + Running examples in ‘inferCSN-Ex.R’ failed The error most likely occurred in: - > ### Name: ggplotly_histogram - > ### Title: Clean 'ggplot2' Histogram to be Converted to 'Plotly' - > ### Aliases: ggplotly_histogram + > ### Name: plot_dynamic_networks + > ### Title: plot_dynamic_networks + > ### Aliases: plot_dynamic_networks > > ### ** Examples > - > + > data("example_matrix") ... - + xlab("len") - `stat_bin()` using `bins = 30`. Pick better value with `binwidth`. - Warning in geom_bar(data = layerdata, mapping = aes(x = .data$x, y = .data$count, : - Ignoring unknown aesthetics: label1, label2, and label3 + > ## End(Not run) > - > # convert `ggplot` object to `plotly` object - > ggplotly(p, tooltip = c("Range", "count", "density")) + > plot_dynamic_networks( + + network, + + celltypes_order = celltypes_order, + + plot_type = "ggplotly" + + ) Error in pm[[2]] : subscript out of bounds - Calls: ggplotly -> ggplotly.ggplot -> gg2list + Calls: plot_dynamic_networks -> -> ggplotly.ggplot -> gg2list Execution halted ``` ## In both -* checking LazyData ... NOTE +* checking installed package size ... NOTE ``` - 'LazyData' is specified without a 'data' directory + installed size is 22.5Mb + sub-directories of 1Mb or more: + data 2.0Mb + libs 20.0Mb ``` -# ggpol +# insurancerating
-* Version: 0.0.7 -* GitHub: https://github.com/erocoar/ggpol -* Source code: https://github.com/cran/ggpol -* Date/Publication: 2020-11-08 13:40:02 UTC -* Number of recursive dependencies: 54 +* Version: 0.7.4 +* GitHub: https://github.com/mharinga/insurancerating +* Source code: https://github.com/cran/insurancerating +* Date/Publication: 2024-05-20 11:30:03 UTC +* Number of recursive dependencies: 133 -Run `revdepcheck::cloud_details(, "ggpol")` for more info +Run `revdepcheck::cloud_details(, "insurancerating")` for more info
@@ -8215,95 +7363,200 @@ Run `revdepcheck::cloud_details(, "ggpol")` for more info * checking examples ... ERROR ``` - Running examples in ‘ggpol-Ex.R’ failed + Running examples in ‘insurancerating-Ex.R’ failed The error most likely occurred in: - > ### Name: GeomConfmat - > ### Title: Confusion Matrix - > ### Aliases: GeomConfmat geom_confmat stat_confmat + > ### Name: autoplot.univariate + > ### Title: Automatically create a ggplot for objects obtained from + > ### univariate() + > ### Aliases: autoplot.univariate > > ### ** Examples > - > x <- sample(LETTERS[seq(4)], 50, replace = TRUE) ... - 21. │ └─ggpol (local) draw_panel(...) - 22. │ └─base::lapply(GeomText$default_aes[missing_aes], rlang::eval_tidy) - 23. │ └─rlang (local) FUN(X[[i]], ...) - 24. ├─ggplot2::from_theme(fontsize) - 25. └─base::.handleSimpleError(...) - 26. └─rlang (local) h(simpleError(msg, call)) - 27. └─handlers[[1L]](cnd) - 28. └─cli::cli_abort(...) - 29. └─rlang::abort(...) + > xzip <- univariate(MTPL, x = bm, severity = amount, nclaims = nclaims, + + exposure = exposure, by = zip) + > autoplot(xzip, show_plots = 1:2) + Warning: Removed 16 rows containing missing values or values outside the scale range + (`geom_point()`). + Warning: Removed 5 rows containing missing values or values outside the scale range + (`geom_line()`). + Error in identicalUnits(x) : object is not a unit + Calls: ... assemble_guides -> guides_build -> unit.c -> identicalUnits Execution halted ``` -## In both +# inTextSummaryTable -* checking dependencies in R code ... NOTE +
+ +* Version: 3.3.3 +* GitHub: https://github.com/openanalytics/inTextSummaryTable +* Source code: https://github.com/cran/inTextSummaryTable +* Date/Publication: 2024-06-12 18:30:02 UTC +* Number of recursive dependencies: 123 + +Run `revdepcheck::cloud_details(, "inTextSummaryTable")` for more info + +
+ +## Newly broken + +* checking tests ... ERROR ``` - Namespaces in Imports field not imported from: - ‘dplyr’ ‘grDevices’ - All declared Imports should be used. + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(inTextSummaryTable) + > + > test_check("inTextSummaryTable") + [ FAIL 59 | WARN 0 | SKIP 0 | PASS 881 ] + + ══ Failed tests ════════════════════════════════════════════════════════════════ + ... + 5. │ └─rlang::eval_bare(quo_get_expr(.quo), quo_get_env(.quo)) + 6. └─inTextSummaryTable::subjectProfileSummaryPlot(...) + 7. ├─base::do.call(plyr::rbind.fill, ggplot_build(gg)$data) + 8. └─plyr (local) ``(``, ``) + 9. └─plyr:::output_template(dfs, nrows) + 10. └─plyr:::allocate_column(df[[var]], nrows, dfs, var) + + [ FAIL 59 | WARN 0 | SKIP 0 | PASS 881 ] + Error: Test failures + Execution halted ``` -* checking LazyData ... NOTE +* checking running R code from vignettes ... ERROR ``` - 'LazyData' is specified without a 'data' directory + Errors in running code in vignettes: + when running code in ‘inTextSummaryTable-aesthetics.Rmd’ + ... + > subjectProfileSummaryPlot(data = summaryTable, xVar = "visit", + + colorVar = "TRT") + + When sourcing ‘inTextSummaryTable-aesthetics.R’: + Error: Problem while setting up geom aesthetics. + ℹ Error occurred in the 2nd layer. + Caused by error in `check_aesthetics()`: + ... + ✖ Fix the following mappings: `size`. + Execution halted + + ‘inTextSummaryTable-advanced.Rmd’ using ‘UTF-8’... OK + ‘inTextSummaryTable-aesthetics.Rmd’ using ‘UTF-8’... failed + ‘inTextSummaryTable-createTables.Rmd’ using ‘UTF-8’... OK + ‘inTextSummaryTable-exportTables.Rmd’ using ‘UTF-8’... OK + ‘inTextSummaryTable-introduction.Rmd’ using ‘UTF-8’... OK + ‘inTextSummaryTable-standardTables.Rmd’ using ‘UTF-8’... OK + ‘inTextSummaryTable-visualization.Rmd’ using ‘UTF-8’... failed + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘inTextSummaryTable-advanced.Rmd’ using rmarkdown + --- finished re-building ‘inTextSummaryTable-advanced.Rmd’ + + --- re-building ‘inTextSummaryTable-aesthetics.Rmd’ using rmarkdown + + Quitting from lines 211-224 [aesthetics-defaultsVisualization] (inTextSummaryTable-aesthetics.Rmd) + Error: processing vignette 'inTextSummaryTable-aesthetics.Rmd' failed with diagnostics: + Problem while setting up geom aesthetics. + ℹ Error occurred in the 2nd layer. + ... + ! Aesthetics must be either length 1 or the same as the data (28). + ✖ Fix the following mappings: `size`. + --- failed re-building ‘inTextSummaryTable-visualization.Rmd’ + + SUMMARY: processing the following files failed: + ‘inTextSummaryTable-aesthetics.Rmd’ + ‘inTextSummaryTable-visualization.Rmd’ + + Error: Vignette re-building failed. + Execution halted + ``` + +## In both + +* checking installed package size ... NOTE + ``` + installed size is 10.3Mb + sub-directories of 1Mb or more: + doc 9.7Mb ``` -# ggprism +# inventorize
-* Version: 1.0.5 -* GitHub: https://github.com/csdaw/ggprism -* Source code: https://github.com/cran/ggprism -* Date/Publication: 2024-03-21 10:50:02 UTC -* Number of recursive dependencies: 105 +* Version: 1.1.1 +* GitHub: NA +* Source code: https://github.com/cran/inventorize +* Date/Publication: 2022-05-31 22:20:09 UTC +* Number of recursive dependencies: 71 -Run `revdepcheck::cloud_details(, "ggprism")` for more info +Run `revdepcheck::cloud_details(, "inventorize")` for more info
## Newly broken -* checking examples ... ERROR +* checking whether package ‘inventorize’ can be installed ... ERROR ``` - Running examples in ‘ggprism-Ex.R’ failed - The error most likely occurred in: - - > ### Name: annotation_ticks - > ### Title: Add ticks as ggplot annotation - > ### Aliases: annotation_ticks - > - > ### ** Examples - > - > ## Generally it is better to use the guide_prism_minor function. - ... - Backtrace: - ▆ - 1. ├─base (local) ``(x) - 2. └─ggplot2:::print.ggplot(x) - 3. ├─ggplot2::ggplot_gtable(data) - 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) - 5. └─ggplot2::calc_element("plot.margin", theme) - 6. └─cli::cli_abort(...) - 7. └─rlang::abort(...) - Execution halted + Installation failed. + See ‘/tmp/workdir/inventorize/new/inventorize.Rcheck/00install.out’ for details. ``` -# ggpubr +## Installation + +### Devel + +``` +* installing *source* package ‘inventorize’ ... +** package ‘inventorize’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** byte-compile and prepare package for lazy loading +Error in pm[[2]] : subscript out of bounds +Error: unable to load R code in package ‘inventorize’ +Execution halted +ERROR: lazy loading failed for package ‘inventorize’ +* removing ‘/tmp/workdir/inventorize/new/inventorize.Rcheck/inventorize’ + + +``` +### CRAN + +``` +* installing *source* package ‘inventorize’ ... +** package ‘inventorize’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** byte-compile and prepare package for lazy loading +Warning in qgamma(service_level, alpha, beta) : NaNs produced +Warning in qgamma(service_level, alpha, beta) : NaNs produced +** help +*** installing help indices +** building package indices +** testing if installed package can be loaded from temporary location +** testing if installed package can be loaded from final location +** testing if installed package keeps a record of temporary installation path +* DONE (inventorize) + + +``` +# karel
-* Version: 0.6.0 -* GitHub: https://github.com/kassambara/ggpubr -* Source code: https://github.com/cran/ggpubr -* Date/Publication: 2023-02-10 16:20:02 UTC -* Number of recursive dependencies: 84 +* Version: 0.1.1 +* GitHub: https://github.com/mpru/karel +* Source code: https://github.com/cran/karel +* Date/Publication: 2022-03-26 21:50:02 UTC +* Number of recursive dependencies: 90 -Run `revdepcheck::cloud_details(, "ggpubr")` for more info +Run `revdepcheck::cloud_details(, "karel")` for more info
@@ -8311,26 +7564,26 @@ Run `revdepcheck::cloud_details(, "ggpubr")` for more info * checking examples ... ERROR ``` - Running examples in ‘ggpubr-Ex.R’ failed + Running examples in ‘karel-Ex.R’ failed The error most likely occurred in: - > ### Name: ggpie - > ### Title: Pie chart - > ### Aliases: ggpie + > ### Name: acciones + > ### Title: Acciones que Karel puede realizar + > ### Aliases: acciones avanzar girar_izquierda poner_coso juntar_coso + > ### girar_derecha darse_vuelta > > ### ** Examples > - > ... - Backtrace: - ▆ - 1. ├─base (local) ``(x) - 2. └─ggplot2:::print.ggplot(x) - 3. ├─ggplot2::ggplot_gtable(data) - 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) - 5. └─ggplot2::calc_element("plot.margin", theme) - 6. └─cli::cli_abort(...) - 7. └─rlang::abort(...) + 1. └─karel::ejecutar_acciones() + 2. ├─base::suppressWarnings(...) + 3. │ └─base::withCallingHandlers(...) + 4. ├─gganimate::animate(...) + 5. └─gganimate:::animate.gganim(...) + 6. └─args$renderer(frames_vars$frame_source, args$fps) + 7. └─gganimate:::png_dim(frames[1]) + 8. └─cli::cli_abort("Provided file ({file}) does not exist") + 9. └─rlang::abort(...) Execution halted ``` @@ -8340,36 +7593,44 @@ Run `revdepcheck::cloud_details(, "ggpubr")` for more info Running the tests in ‘tests/testthat.R’ failed. Complete output: > library(testthat) - > library(ggpubr) - Loading required package: ggplot2 + > library(karel) > - > test_check("ggpubr") - [ FAIL 2 | WARN 5 | SKIP 0 | PASS 183 ] + > test_check("karel") + [ FAIL 2 | WARN 2 | SKIP 0 | PASS 78 ] + ══ Failed tests ════════════════════════════════════════════════════════════════ ... - [6] 6 - 10 == -4 - [7] 19 - 9 == 10 - [9] 1 - 7 == -6 - [10] 6 - 7 == -1 - [11] 13 - 6 == 7 - ... + 5. ├─gganimate::animate(...) + 6. └─gganimate:::animate.gganim(...) + 7. └─args$renderer(frames_vars$frame_source, args$fps) + 8. └─gganimate:::png_dim(frames[1]) + 9. └─cli::cli_abort("Provided file ({file}) does not exist") + 10. └─rlang::abort(...) - [ FAIL 2 | WARN 5 | SKIP 0 | PASS 183 ] + [ FAIL 2 | WARN 2 | SKIP 0 | PASS 78 ] Error: Test failures Execution halted ``` -# ggraph +## In both + +* checking dependencies in R code ... NOTE + ``` + Namespace in Imports field not imported from: ‘gifski’ + All declared Imports should be used. + ``` + +# kDGLM
-* Version: 2.2.1 -* GitHub: https://github.com/thomasp85/ggraph -* Source code: https://github.com/cran/ggraph -* Date/Publication: 2024-03-07 12:40:02 UTC -* Number of recursive dependencies: 115 +* Version: 1.2.0 +* GitHub: https://github.com/silvaneojunior/kDGLM +* Source code: https://github.com/cran/kDGLM +* Date/Publication: 2024-05-25 09:50:03 UTC +* Number of recursive dependencies: 136 -Run `revdepcheck::cloud_details(, "ggraph")` for more info +Run `revdepcheck::cloud_details(, "kDGLM")` for more info
@@ -8377,82 +7638,65 @@ Run `revdepcheck::cloud_details(, "ggraph")` for more info * checking examples ... ERROR ``` - Running examples in ‘ggraph-Ex.R’ failed + Running examples in ‘kDGLM-Ex.R’ failed The error most likely occurred in: - > ### Name: geom_conn_bundle - > ### Title: Create hierarchical edge bundles between node connections - > ### Aliases: geom_conn_bundle geom_conn_bundle2 geom_conn_bundle0 + > ### Name: forecast.fitted_dlm + > ### Title: Auxiliary function for forecasting + > ### Aliases: forecast.fitted_dlm > > ### ** Examples > - > # Create a graph of the flare class system + > ... - + ) + - + geom_node_point(aes(filter = leaf, colour = class)) + - + scale_edge_colour_distiller('', direction = 1, guide = 'edge_direction') + - + coord_fixed() + - + ggforce::theme_no_axes() - Error in get_layer_key(...) : - unused argument (list(list("black", 0.5, 1, "butt", FALSE, "black", TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), NULL, list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), 5.5, c(5.5, 5.5, 5.5, 5.5), NULL, list(), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.75, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, - NULL, NULL, 1, 90, NULL, c(0, 2.75, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 1, NULL, NULL, NULL, c(0, 2.2, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, NULL, c(0, 0, 0, 2.2), NULL, T - Calls: ... -> -> process_layers -> + > forecast(fitted.data, 24, + + chickenPox = list(Total = rep(175, 24)), # Optional + + Vaccine.1.Covariate = rep(TRUE, 24), + + Vaccine.2.Covariate = rep(TRUE, 24) + + ) + Scale for y is already present. + Adding another scale for y, which will replace the existing scale. + Error in pm[[2]] : subscript out of bounds + Calls: forecast ... lapply -> -> ggplotly.ggplot -> gg2list Execution halted ``` -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘Edges.Rmd’ using rmarkdown - ``` - ## In both * checking running R code from vignettes ... ERROR ``` Errors in running code in vignettes: - when running code in ‘Edges.Rmd’ + when running code in ‘fitting.Rmd’ ... - Warning in grid.Call.graphics(C_text, as.graphicsAnnot(x$label), x$x, x$y, : - font family 'Arial Narrow' not found in PostScript font database - Warning in grid.Call.graphics(C_text, as.graphicsAnnot(x$label), x$x, x$y, : - font family 'Arial Narrow' not found in PostScript font database - Warning in grid.Call.graphics(C_text, as.graphicsAnnot(x$label), x$x, x$y, : - font family 'Arial Narrow' not found in PostScript font database + > outcome <- Multinom(p = c("p.1", "p.2"), data = chickenPox[, + + c(2, 3, 5)]) - ... - font family 'Arial' not found in PostScript font database + > fitted.model <- fit_model(structure * 2, chickenPox = outcome) - When sourcing ‘tidygraph.R’: - Error: invalid font type + > forecast(fitted.model, t = 24, plot = "base") + + When sourcing ‘fitting.R’: + Error: Error: Missing extra argument: Vaccine.1.Covariate Execution halted - ‘Edges.Rmd’ using ‘UTF-8’... failed - ‘Layouts.Rmd’ using ‘UTF-8’... failed - ‘Nodes.Rmd’ using ‘UTF-8’... failed - ‘tidygraph.Rmd’ using ‘UTF-8’... failed - ``` - -* checking installed package size ... NOTE - ``` - installed size is 9.0Mb - sub-directories of 1Mb or more: - R 1.5Mb - doc 3.9Mb - libs 2.9Mb + ‘example1.Rmd’ using ‘UTF-8’... OK + ‘fitting.Rmd’ using ‘UTF-8’... failed + ‘intro.Rmd’ using ‘UTF-8’... OK + ‘outcomes.Rmd’ using ‘UTF-8’... OK + ‘structures.Rmd’ using ‘UTF-8’... OK ``` -# ggredist +# latentcor
-* Version: 0.0.2 -* GitHub: https://github.com/alarm-redist/ggredist -* Source code: https://github.com/cran/ggredist -* Date/Publication: 2022-11-23 11:20:02 UTC -* Number of recursive dependencies: 67 +* Version: 2.0.1 +* GitHub: NA +* Source code: https://github.com/cran/latentcor +* Date/Publication: 2022-09-05 20:50:02 UTC +* Number of recursive dependencies: 143 -Run `revdepcheck::cloud_details(, "ggredist")` for more info +Run `revdepcheck::cloud_details(, "latentcor")` for more info
@@ -8460,40 +7704,40 @@ Run `revdepcheck::cloud_details(, "ggredist")` for more info * checking examples ... ERROR ``` - Running examples in ‘ggredist-Ex.R’ failed + Running examples in ‘latentcor-Ex.R’ failed The error most likely occurred in: - > ### Name: geom_district_text - > ### Title: Label Map Regions - > ### Aliases: geom_district_text geom_district_label - > ### stat_district_coordinates StatDistrictCoordinates GeomDistrictText - > ### Keywords: datasets + > ### Name: latentcor + > ### Title: Estimate latent correlation for mixed types. + > ### Aliases: latentcor > > ### ** Examples + > + > # Example 1 - truncated data type, same type for all variables ... - 22. │ └─coord$transform(data, panel_params) - 23. │ └─ggplot2 (local) transform(..., self = self) - 24. │ └─ggplot2:::sf_rescale01(...) - 25. │ └─sf::st_normalize(x, c(x_range[1], y_range[1], x_range[2], y_range[2])) - 26. └─base::.handleSimpleError(...) - 27. └─rlang (local) h(simpleError(msg, call)) - 28. └─handlers[[1L]](cnd) - 29. └─cli::cli_abort(...) - 30. └─rlang::abort(...) + > R_approx = latentcor(X = X, types = "tru", method = "approx")$R + > proc.time() - start_time + user system elapsed + 0.021 0.000 0.021 + > # Heatmap for latent correlation matrix. + > Heatmap_R_approx = latentcor(X = X, types = "tru", method = "approx", + + showplot = TRUE)$plotR + Error in pm[[2]] : subscript out of bounds + Calls: latentcor ... %>% -> layout -> ggplotly -> ggplotly.ggplot -> gg2list Execution halted ``` -# ggResidpanel +# lcars
-* Version: 0.3.0 -* GitHub: NA -* Source code: https://github.com/cran/ggResidpanel -* Date/Publication: 2019-05-31 23:20:04 UTC -* Number of recursive dependencies: 112 +* Version: 0.3.8 +* GitHub: https://github.com/leonawicz/lcars +* Source code: https://github.com/cran/lcars +* Date/Publication: 2023-09-10 04:10:02 UTC +* Number of recursive dependencies: 88 -Run `revdepcheck::cloud_details(, "ggResidpanel")` for more info +Run `revdepcheck::cloud_details(, "lcars")` for more info
@@ -8501,62 +7745,59 @@ Run `revdepcheck::cloud_details(, "ggResidpanel")` for more info * checking examples ... ERROR ``` - Running examples in ‘ggResidpanel-Ex.R’ failed + Running examples in ‘lcars-Ex.R’ failed The error most likely occurred in: - > ### Name: resid_interact - > ### Title: Panel of Interactive Versions of Diagnostic Residual Plots. - > ### Aliases: resid_interact + > ### Name: lcars_border + > ### Title: LCARS border plot + > ### Aliases: lcars_border > > ### ** Examples > - > - > # Fit a model to the penguin data - > penguin_model <- lme4::lmer(heartrate ~ depth + duration + (1|bird), data = penguins) - > - > # Create the default interactive panel - > resid_interact(penguin_model) - Error in pm[[2]] : subscript out of bounds - Calls: resid_interact ... %>% -> layout -> ggplotly -> ggplotly.ggplot -> gg2list + > lcars_border() + ... + Warning in grid.Call.graphics(C_text, as.graphicsAnnot(x$label), x$x, x$y, : + font family '0.5' not found in PostScript font database + Warning in grid.Call.graphics(C_text, as.graphicsAnnot(x$label), x$x, x$y, : + font family '0.5' not found in PostScript font database + Warning in grid.Call.graphics(C_text, as.graphicsAnnot(x$label), x$x, x$y, : + font family '0.5' not found in PostScript font database + Error in grid.Call.graphics(C_text, as.graphicsAnnot(x$label), x$x, x$y, : + invalid font type + Calls: lcars_border ... drawDetails -> drawDetails.text -> grid.Call.graphics Execution halted ``` * checking running R code from vignettes ... ERROR ``` Errors in running code in vignettes: - when running code in ‘introduction.Rmd’ + when running code in ‘lcars.Rmd’ ... - > resid_interact(penguin_model, plots = c("resid", "qq")) - Warning: The following aesthetics were dropped during statistical transformation: label. - ℹ This can happen when ggplot fails to infer the correct grouping structure in - the data. - ℹ Did you forget to specify a `group` aesthetic or to convert a numerical - variable into a factor? + Warning in grid.Call.graphics(C_text, as.graphicsAnnot(x$label), x$x, x$y, : + font family '0.5' not found in PostScript font database + Warning in grid.Call.graphics(C_text, as.graphicsAnnot(x$label), x$x, x$y, : + font family '0.5' not found in PostScript font database + Warning in grid.Call.graphics(C_text, as.graphicsAnnot(x$label), x$x, x$y, : + font family '0.5' not found in PostScript font database - When sourcing ‘introduction.R’: - Error: subscript out of bounds + When sourcing ‘lcars.R’: + Error: invalid font type Execution halted - ‘introduction.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘introduction.Rmd’ using rmarkdown + ‘lcars.Rmd’ using ‘UTF-8’... failed ``` -# ggseqplot +# lemon
-* Version: 0.8.4 -* GitHub: https://github.com/maraab23/ggseqplot -* Source code: https://github.com/cran/ggseqplot -* Date/Publication: 2024-05-17 21:40:03 UTC -* Number of recursive dependencies: 139 +* Version: 0.4.9 +* GitHub: https://github.com/stefanedwards/lemon +* Source code: https://github.com/cran/lemon +* Date/Publication: 2024-02-08 08:00:08 UTC +* Number of recursive dependencies: 76 -Run `revdepcheck::cloud_details(, "ggseqplot")` for more info +Run `revdepcheck::cloud_details(, "lemon")` for more info
@@ -8564,26 +7805,23 @@ Run `revdepcheck::cloud_details(, "ggseqplot")` for more info * checking examples ... ERROR ``` - Running examples in ‘ggseqplot-Ex.R’ failed + Running examples in ‘lemon-Ex.R’ failed The error most likely occurred in: - > ### Name: ggseqmsplot - > ### Title: Modal State Sequence Plot - > ### Aliases: ggseqmsplot + > ### Name: annotate_y_axis + > ### Title: Annotations on the axis + > ### Aliases: annotate_y_axis annotate_x_axis > > ### ** Examples > - > # Use example data from TraMineR: actcal data set - ... - 11. │ └─base::withCallingHandlers(...) - 12. └─ggplot2 (local) f(l = layers[[i]], d = data[[i]]) - 13. └─l$compute_geom_2(d, theme = plot$theme) - 14. └─ggplot2 (local) compute_geom_2(..., self = self) - 15. └─self$geom$use_defaults(...) - 16. └─ggplot2 (local) use_defaults(..., self = self) - 17. └─ggplot2:::check_aesthetics(new_params, nrow(data)) - 18. └─cli::cli_abort(...) - 19. └─rlang::abort(...) + > library(ggplot2) + > + > p <- ggplot(mtcars, aes(mpg, hp, colour=disp)) + geom_point() + > + > l <- p + annotate_y_axis('mark at', y=200, tick=TRUE) + > l + Error in identicalUnits(x) : object is not a unit + Calls: ... polylineGrob -> is.unit -> unit.c -> identicalUnits Execution halted ``` @@ -8593,21 +7831,21 @@ Run `revdepcheck::cloud_details(, "ggseqplot")` for more info Running the tests in ‘tests/testthat.R’ failed. Complete output: > library(testthat) - > library(ggseqplot) - Loading required package: TraMineR - - TraMineR stable version 2.2-10 (Built: 2024-05-22) - Website: http://traminer.unige.ch - Please type 'citation("TraMineR")' for citation information. + > library(lemon) + > + > + > if (TRUE) { + + test_check("lemon") + + } #else { ... - Backtrace: - ▆ - 1. ├─testthat::expect_s3_class(ggseqtrplot(biofam.seq), "ggplot") at test-ggseqtrplot.R:35:3 - 2. │ └─testthat::quasi_label(enquo(object), arg = "object") - 3. │ └─rlang::eval_bare(expr, quo_get_env(quo)) - 4. └─ggseqplot::ggseqtrplot(biofam.seq) + 17. ├─grid::unit.c(unit(1, "npc"), unit(1, "npc") - tick.length) + 18. └─grid:::Ops.unit(unit(1, "npc"), tick.length) + 19. └─grid:::as.unit(e2) - [ FAIL 1 | WARN 1036 | SKIP 0 | PASS 131 ] + [ FAIL 1 | WARN 0 | SKIP 3 | PASS 138 ] + Deleting unused snapshots: + • facet/facet-rep-wrap-spacing.svg + • facet_aux/facet-rep-wrap.svg Error: Test failures Execution halted ``` @@ -8615,274 +7853,244 @@ Run `revdepcheck::cloud_details(, "ggseqplot")` for more info * checking running R code from vignettes ... ERROR ``` Errors in running code in vignettes: - when running code in ‘ggseqplot.Rmd’ + when running code in ‘capped-axes.Rmd’ ... - > p1 + p2 + plot_layout(guides = "collect") & scale_fill_manual(values = canva_palettes$`Fun and tropical`[1:4]) & - + theme_ipsum(base_family = "" .... [TRUNCATED] - Scale for fill is already present. - Adding another scale for fill, which will replace the existing scale. - Scale for fill is already present. - Adding another scale for fill, which will replace the existing scale. + > p + coord_capped_cart(bottom = "right") - When sourcing ‘ggseqplot.R’: - Error: object is not coercible to a unit + > p + coord_capped_cart(bottom = "right", left = "none") + + > ggplot(dat1, aes(gp, y)) + geom_point(position = position_jitter(width = 0.2, + + height = 0)) + coord_capped_cart(left = "none", bottom = bracke .... [TRUNCATED] + + ... + When sourcing ‘legends.R’: + Error: Could not find panel named `panel-1-5`. Execution halted - ‘ggseqplot.Rmd’ using ‘UTF-8’... failed + ‘capped-axes.Rmd’ using ‘UTF-8’... failed + ‘facet-rep-labels.Rmd’ using ‘UTF-8’... failed + ‘geoms.Rmd’ using ‘UTF-8’... OK + ‘gtable_show_lemonade.Rmd’ using ‘UTF-8’... OK + ‘legends.Rmd’ using ‘UTF-8’... failed + ‘lemon_print.Rmd’ using ‘UTF-8’... OK ``` * checking re-building of vignette outputs ... NOTE ``` Error(s) in re-building vignettes: - --- re-building ‘ggseqplot.Rmd’ using rmarkdown + --- re-building ‘capped-axes.Rmd’ using rmarkdown ``` -# ggside +# lfproQC
-* Version: 0.3.1 -* GitHub: https://github.com/jtlandis/ggside -* Source code: https://github.com/cran/ggside -* Date/Publication: 2024-03-01 09:12:37 UTC -* Number of recursive dependencies: 76 +* Version: 0.1.0 +* GitHub: NA +* Source code: https://github.com/cran/lfproQC +* Date/Publication: 2024-05-23 16:10:02 UTC +* Number of recursive dependencies: 143 -Run `revdepcheck::cloud_details(, "ggside")` for more info +Run `revdepcheck::cloud_details(, "lfproQC")` for more info
## Newly broken -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(ggplot2) - > library(ggside) - Registered S3 method overwritten by 'ggside': - method from - +.gg ggplot2 - > - ... - • ops_meaningful/alpha-0-5-from-function.svg - • side_layers/boxplot2.svg - • vdiff_irisScatter/collapsed-histo.svg - • vdiff_irisScatter/facetgrid-collapsed-density.svg - • vdiff_irisScatter/facetgrid-histo.svg - • vdiff_irisScatter/facetgrid-side-density.svg - • vdiff_irisScatter/stacked-side-density.svg - • vdiff_irisScatter/yside-histo.svg - Error: Test failures - Execution halted - ``` - -* checking for code/documentation mismatches ... WARNING +* checking examples ... ERROR ``` - Codoc mismatches from documentation object 'geom_xsidebar': - geom_xsidebar - Code: function(mapping = NULL, data = NULL, stat = "count", position - = "stack", ..., just = 0.5, na.rm = FALSE, orientation - = "x", show.legend = NA, inherit.aes = TRUE) - Docs: function(mapping = NULL, data = NULL, stat = "count", position - = "stack", ..., just = 0.5, width = NULL, na.rm = - FALSE, orientation = "x", show.legend = NA, - inherit.aes = TRUE) - Argument names in docs not in code: - ... - Docs: function(mapping = NULL, data = NULL, stat = "identity", - position = "identity", ..., lineend = "butt", linejoin - = "round", linemitre = 10, arrow = NULL, na.rm = - FALSE, show.legend = NA, inherit.aes = TRUE) - Argument names in code not in docs: - arrow.fill - Mismatches in argument names: - Position: 10 Code: arrow.fill Docs: na.rm - Position: 11 Code: na.rm Docs: show.legend - Position: 12 Code: show.legend Docs: inherit.aes + Running examples in ‘lfproQC-Ex.R’ failed + The error most likely occurred in: + + > ### Name: Boxplot_data + > ### Title: Creating Boxplot for a dataset + > ### Aliases: Boxplot_data + > + > ### ** Examples + > + > Boxplot_data(yeast_data) + Using Majority protein IDs as id variables + Warning: Removed 266 rows containing non-finite outside the scale range + (`stat_boxplot()`). + Error in pm[[2]] : subscript out of bounds + Calls: Boxplot_data -> -> ggplotly.ggplot -> gg2list + Execution halted ``` -# ggstatsplot - -
- -* Version: 0.12.3 -* GitHub: https://github.com/IndrajeetPatil/ggstatsplot -* Source code: https://github.com/cran/ggstatsplot -* Date/Publication: 2024-04-06 17:42:59 UTC -* Number of recursive dependencies: 168 - -Run `revdepcheck::cloud_details(, "ggstatsplot")` for more info - -
- -## Newly broken - -* checking tests ... ERROR +* checking running R code from vignettes ... ERROR ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > # graphics engine changed in this version, and so snapshots generated on - > # previous R version won't work - > if (getRversion() < "4.4.0") { - + library(testthat) - + suppressPackageStartupMessages(library(ggstatsplot)) - + - + test_check("ggstatsplot") - ... - • pairwise-ggsignif/within-non-parametric-all.svg - • pairwise-ggsignif/within-non-parametric-only-non-significant.svg - • pairwise-ggsignif/within-non-parametric-only-significant.svg - • pairwise-ggsignif/within-parametric-all.svg - • pairwise-ggsignif/within-parametric-only-significant.svg - • pairwise-ggsignif/within-robust-all.svg - • pairwise-ggsignif/within-robust-only-non-significant.svg - • pairwise-ggsignif/within-robust-only-significant.svg - Error: Test failures - Execution halted + Errors in running code in vignettes: + when running code in ‘user_guide.Rmd’ + ... + > yeast$`Best combinations` + PCV_best_combination PEV_best_combination PMAD_best_combination + 1 knn_rlr lls_loess lls_rlr + + > Boxplot_data(yeast$knn_rlr_data) + Using Majority protein IDs as id variables + + When sourcing ‘user_guide.R’: + Error: subscript out of bounds + Execution halted + + ‘user_guide.Rmd’ using ‘UTF-8’... failed ``` -## In both - -* checking running R code from vignettes ... ERROR +* checking re-building of vignette outputs ... NOTE ``` - Errors in running code in vignettes: - when running code in ‘ggstatsplot.Rmd’ + Error(s) in re-building vignettes: ... - journal = {{Journal of Open Source Software}}, - } + --- re-building ‘user_guide.Rmd’ using rmarkdown - > ggbetweenstats(iris, Species, Sepal.Length) + Quitting from lines 53-54 [unnamed-chunk-8] (user_guide.Rmd) + Error: processing vignette 'user_guide.Rmd' failed with diagnostics: + subscript out of bounds + --- failed re-building ‘user_guide.Rmd’ - > knitr::include_graphics("../man/figures/stats_reporting_format.png") + SUMMARY: processing the following file failed: + ‘user_guide.Rmd’ - When sourcing ‘ggstatsplot.R’: - Error: Cannot find the file(s): "../man/figures/stats_reporting_format.png" + Error: Vignette re-building failed. Execution halted - - ‘additional.Rmd’ using ‘UTF-8’... OK - ‘ggstatsplot.Rmd’ using ‘UTF-8’... failed ``` -# ggtern +## In both + +* checking installed package size ... NOTE + ``` + installed size is 6.2Mb + sub-directories of 1Mb or more: + doc 5.9Mb + ``` + +# LMoFit
-* Version: 3.5.0 +* Version: 0.1.7 * GitHub: NA -* Source code: https://github.com/cran/ggtern -* Date/Publication: 2024-03-24 21:50:02 UTC -* Number of recursive dependencies: 42 +* Source code: https://github.com/cran/LMoFit +* Date/Publication: 2024-05-14 07:33:23 UTC +* Number of recursive dependencies: 62 -Run `revdepcheck::cloud_details(, "ggtern")` for more info +Run `revdepcheck::cloud_details(, "LMoFit")` for more info
## Newly broken -* checking examples ... ERROR +* checking running R code from vignettes ... ERROR ``` - Running examples in ‘ggtern-Ex.R’ failed - The error most likely occurred in: + Errors in running code in vignettes: + when running code in ‘LMoFit.Rmd’ + ... - > ### Name: annotate - > ### Title: Create an annotation layer (ggtern version). - > ### Aliases: annotate - > - > ### ** Examples - > - > ggtern() + - ... - 3. ├─ggtern::ggplot_build(x) - 4. └─ggtern:::ggplot_build.ggplot(x) - 5. └─ggtern:::layers_add_or_remove_mask(plot) - 6. └─ggint$plot_theme(plot) - 7. └─ggplot2:::validate_theme(theme) - 8. └─base::mapply(...) - 9. └─ggplot2 (local) ``(...) - 10. └─cli::cli_abort(...) - 11. └─rlang::abort(...) + > lspace_BrIII + + When sourcing ‘LMoFit.R’: + Error: Problem while setting up geom aesthetics. + ℹ Error occurred in the 1st layer. + Caused by error in `compute_geom_2()`: + ! unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), NULL, NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.75, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, 90, NULL, c(0, 2.75, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, + c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 1, NULL, NULL, NULL, c(0, 2.2, 0, 0), NULL, TRUE), NULL, Execution halted + + ‘LMoFit.Rmd’ using ‘UTF-8’... failed ``` -## In both - -* checking package dependencies ... NOTE +* checking re-building of vignette outputs ... NOTE ``` - Package which this enhances but not available for checking: ‘sp’ + Error(s) in re-building vignettes: + ... + --- re-building ‘LMoFit.Rmd’ using rmarkdown + + Quitting from lines 236-237 [unnamed-chunk-15] (LMoFit.Rmd) + Error: processing vignette 'LMoFit.Rmd' failed with diagnostics: + Problem while setting up geom aesthetics. + ℹ Error occurred in the 1st layer. + Caused by error in `compute_geom_2()`: + ! unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), NULL, NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.75, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, 90, NULL, c(0, 2.75, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, + ... + NULL, NULL, 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, NULL, NULL, NULL, TRUE), NULL, "right", NULL, NULL, NULL, "center", NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, c(0, 0, 0, 0), list(), 11, list("white", NA, NULL, NULL, TRUE), list(), 5.5, NULL, NULL, list("grey92", NULL, NULL, NULL, FALSE, TRUE), list(), list(), NULL, NULL, NULL, NULL, FALSE, list(NULL, "white", NULL, NULL, TRUE), list(NULL, NULL, NULL, 1.2, 0, 1, NULL, NULL, c(0, + 0, 5.5, 0), NULL, TRUE), "panel", list(NULL, NULL, NULL, NULL, 0, 1, NULL, NULL, c(0, 0, 5.5, 0), NULL, TRUE), list(NULL, NULL, NULL, 0.8, 1, 1, NULL, NULL, c(5.5, 0, 0, 0), NULL, TRUE), "panel", list(NULL, NULL, NULL, 1.2, 0.5, 0.5, NULL, NULL, NULL, NULL, TRUE), "topleft", NULL, c(5.5, 5.5, 5.5, 5.5), list("white", "black", 2, NULL, TRUE), NULL, NULL, "inherit", "inside", list(NULL, NULL, "grey10", 0.8, NULL, NULL, NULL, NULL, c(4.4, 4.4, 4.4, 4.4), NULL, TRUE), NULL, NULL, NULL, list(NULL, NULL, + NULL, NULL, NULL, NULL, -90, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, NULL, 90, NULL, NULL, NULL, TRUE), NULL, 2.75, 2.75, list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), 5.5, c(5.5, 5.5, 5.5, 5.5))) + --- failed re-building ‘LMoFit.Rmd’ + + SUMMARY: processing the following file failed: + ‘LMoFit.Rmd’ + + Error: Vignette re-building failed. + Execution halted ``` -* checking Rd cross-references ... NOTE +## In both + +* checking installed package size ... NOTE ``` - Package unavailable to check Rd xrefs: ‘chemometrics’ + installed size is 7.0Mb + sub-directories of 1Mb or more: + data 6.5Mb ``` -# ggthemes +# manydata
-* Version: 5.1.0 -* GitHub: https://github.com/jrnold/ggthemes -* Source code: https://github.com/cran/ggthemes -* Date/Publication: 2024-02-10 00:30:02 UTC -* Number of recursive dependencies: 101 +* Version: 0.9.3 +* GitHub: https://github.com/globalgov/manydata +* Source code: https://github.com/cran/manydata +* Date/Publication: 2024-05-06 19:00:02 UTC +* Number of recursive dependencies: 129 -Run `revdepcheck::cloud_details(, "ggthemes")` for more info +Run `revdepcheck::cloud_details(, "manydata")` for more info
## Newly broken -* checking examples ... ERROR +* checking tests ... ERROR ``` - Running examples in ‘ggthemes-Ex.R’ failed - The error most likely occurred in: - - > ### Name: theme_economist - > ### Title: ggplot color theme based on the Economist - > ### Aliases: theme_economist theme_economist_white - > - > ### ** Examples - > - > library("ggplot2") + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(manydata) + manydata 0.9.3 + Please see manydata.ch for more information. + Type 'citation("manydata")' for citing this R package in publications. + > + > test_check("manydata") ... - Backtrace: - ▆ - 1. ├─base (local) ``(x) - 2. └─ggplot2:::print.ggplot(x) - 3. ├─ggplot2::ggplot_gtable(data) - 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) - 5. └─ggplot2::calc_element("plot.margin", theme) - 6. └─cli::cli_abort(...) - 7. └─rlang::abort(...) - Execution halted + ── Failure ('test_compare.R:8:3'): plot for compare_categories returns the correct output format ── + Names of `db` ('data', 'layers', 'scales', 'guides', 'mapping', 'theme', 'coordinates', 'facet', 'plot_env', 'layout', 'labels') don't match 'data', 'layers', 'scales', 'guides', 'mapping', 'theme', 'coordinates', 'facet', 'plot_env', 'layout' + ── Failure ('test_compare.R:74:3'): compare_missing() and plot_missing() returns the correct output format ── + `pl` has length 11, not length 10. + ── Failure ('test_compare.R:76:3'): compare_missing() and plot_missing() returns the correct output format ── + Names of `pl` ('data', 'layers', 'scales', 'guides', 'mapping', 'theme', 'coordinates', 'facet', 'plot_env', 'layout', 'labels') don't match 'data', 'layers', 'scales', 'guides', 'mapping', 'theme', 'coordinates', 'facet', 'plot_env', 'layout' + + [ FAIL 4 | WARN 0 | SKIP 3 | PASS 121 ] + Error: Test failures + Execution halted ``` ## In both -* checking package dependencies ... NOTE - ``` - Package suggested but not available for checking: ‘quantreg’ - ``` - * checking data for non-ASCII characters ... NOTE ``` - Note: found 138 marked UTF-8 strings + Note: found 3 marked UTF-8 strings ``` -# ggupset +# MARVEL
-* Version: 0.3.0 -* GitHub: https://github.com/const-ae/ggupset -* Source code: https://github.com/cran/ggupset -* Date/Publication: 2020-05-05 10:40:03 UTC -* Number of recursive dependencies: 46 +* Version: 1.4.0 +* GitHub: NA +* Source code: https://github.com/cran/MARVEL +* Date/Publication: 2022-10-31 10:22:50 UTC +* Number of recursive dependencies: 227 -Run `revdepcheck::cloud_details(, "ggupset")` for more info +Run `revdepcheck::cloud_details(, "MARVEL")` for more info
@@ -8890,204 +8098,180 @@ Run `revdepcheck::cloud_details(, "ggupset")` for more info * checking examples ... ERROR ``` - Running examples in ‘ggupset-Ex.R’ failed + Running examples in ‘MARVEL-Ex.R’ failed The error most likely occurred in: - > ### Name: axis_combmatrix - > ### Title: Convert delimited text labels into a combination matrix axis - > ### Aliases: axis_combmatrix + > ### Name: PlotValues.PSI + > ### Title: Plot percent spliced-in (PSI) values + > ### Aliases: PlotValues.PSI > > ### ** Examples > - > library(ggplot2) + > marvel.demo <- readRDS(system.file("extdata/data", "marvel.demo.rds", package="MARVEL")) ... - Datsun 710 Cyl: 4_Gears: 4 - Hornet 4 Drive Cyl: 6_Gears: 3 - Hornet Sportabout Cyl: 8_Gears: 3 - Valiant Cyl: 6_Gears: 3 - > ggplot(mtcars, aes(x=combined)) + - + geom_bar() + - + axis_combmatrix(sep = "_") - Error in as.unit(e2) : object is not coercible to a unit - Calls: ... polylineGrob -> is.unit -> unit.c -> Ops.unit -> as.unit + > # Plot + > marvel.demo <- PlotValues.PSI(MarvelObject=marvel.demo, + + cell.group.list=cell.group.list, + + feature="chr17:8383254:8382781|8383157:-@chr17:8382143:8382315", + + min.cells=5, + + xlabels.size=5 + + ) + Error in names(labels) <- `*vtmp*` : attempt to set an attribute on NULL + Calls: PlotValues.PSI ... ggplot_add -> ggplot_add.new_aes -> bump_aes_labels Execution halted ``` -# ggVennDiagram - -
- -* Version: 1.5.2 -* GitHub: https://github.com/gaospecial/ggVennDiagram -* Source code: https://github.com/cran/ggVennDiagram -* Date/Publication: 2024-02-20 08:10:02 UTC -* Number of recursive dependencies: 98 - -Run `revdepcheck::cloud_details(, "ggVennDiagram")` for more info - -
- -## Newly broken - * checking running R code from vignettes ... ERROR ``` Errors in running code in vignettes: - when running code in ‘fully-customed.Rmd’ + when running code in ‘MARVEL.Rmd’ ... - [1] "b" "c" "e" "h" "k" "q" "s" "y" - - > ggVennDiagram(y, show_intersect = TRUE, set_color = "black") - Warning in geom_text(aes(label = .data$count, text = .data$item), data = region_label) : - Ignoring unknown aesthetics: text + > tran_id <- "chr4:108620569:108620600|108620656:108620712:+@chr4:108621951:108622024" - ... - Ignoring unknown aesthetics: text + > marvel.demo <- PlotValues(MarvelObject = marvel.demo, + + cell.group.list = cell.group.list, feature = tran_id, xlabels.size = 5, + + level = .... [TRUNCATED] - When sourcing ‘using-ggVennDiagram.R’: - Error: subscript out of bounds + When sourcing ‘MARVEL.R’: + Error: attempt to set an attribute on NULL Execution halted - ‘VennCalculator.Rmd’ using ‘UTF-8’... OK - ‘fully-customed.Rmd’ using ‘UTF-8’... failed - ‘using-ggVennDiagram.Rmd’ using ‘UTF-8’... failed - ‘using-new-shapes.Rmd’ using ‘UTF-8’... OK + ‘MARVEL.Rmd’ using ‘UTF-8’... failed ``` * checking re-building of vignette outputs ... NOTE ``` Error(s) in re-building vignettes: - --- re-building ‘VennCalculator.Rmd’ using rmarkdown - --- finished re-building ‘VennCalculator.Rmd’ - - --- re-building ‘fully-customed.Rmd’ using rmarkdown - ``` - -## In both - -* checking installed package size ... NOTE - ``` - installed size is 11.1Mb - sub-directories of 1Mb or more: - doc 9.5Mb - help 1.1Mb + --- re-building ‘MARVEL.Rmd’ using rmarkdown ``` -# graphPAF +# MBNMAdose
-* Version: 2.0.0 -* GitHub: https://github.com/johnfergusonNUIG/graphPAF -* Source code: https://github.com/cran/graphPAF -* Date/Publication: 2023-12-21 00:50:06 UTC -* Number of recursive dependencies: 50 +* Version: 0.4.3 +* GitHub: NA +* Source code: https://github.com/cran/MBNMAdose +* Date/Publication: 2024-04-18 12:42:47 UTC +* Number of recursive dependencies: 118 -Run `revdepcheck::cloud_details(, "graphPAF")` for more info +Run `revdepcheck::cloud_details(, "MBNMAdose")` for more info
## Newly broken -* checking examples ... ERROR +* checking running R code from vignettes ... ERROR ``` - Running examples in ‘graphPAF-Ex.R’ failed - The error most likely occurred in: + Errors in running code in vignettes: + when running code in ‘outputs-4.Rmd’ + ... - > ### Name: plot.rf.data.frame - > ### Title: Create a fan_plot of a rf.data.frame object - > ### Aliases: plot.rf.data.frame - > - > ### ** Examples - > - > library(ggplot2) + > plot(trip.emax) + + When sourcing ‘outputs-4.R’: + Error: Problem while setting up geom aesthetics. + ℹ Error occurred in the 1st layer. + Caused by error in `use_defaults()`: ... - Backtrace: - ▆ - 1. ├─base (local) ``(x) - 2. └─ggplot2:::print.ggplot(x) - 3. ├─ggplot2::ggplot_gtable(data) - 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) - 5. └─ggplot2::calc_element("plot.margin", theme) - 6. └─cli::cli_abort(...) - 7. └─rlang::abort(...) Execution halted + + ‘consistencychecking-3.Rmd’ using ‘UTF-8’... OK + ‘dataexploration-1.Rmd’ using ‘UTF-8’... OK + ‘mbnmadose-overview.Rmd’ using ‘UTF-8’... OK + ‘metaregression-6.Rmd’ using ‘UTF-8’... OK + ‘nma_in_mbnmadose.Rmd’ using ‘UTF-8’... OK + ‘outputs-4.Rmd’ using ‘UTF-8’... failed + ‘predictions-5.Rmd’ using ‘UTF-8’... OK + ‘runmbnmadose-2.Rmd’ using ‘UTF-8’... OK ``` -# greatR +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘consistencychecking-3.Rmd’ using rmarkdown + ``` + +## In both + +* checking data for non-ASCII characters ... NOTE + ``` + Note: found 6 marked Latin-1 strings + ``` + +# MBNMAtime
-* Version: 2.0.0 -* GitHub: https://github.com/ruthkr/greatR -* Source code: https://github.com/cran/greatR -* Date/Publication: 2024-04-09 22:40:07 UTC -* Number of recursive dependencies: 77 +* Version: 0.2.4 +* GitHub: NA +* Source code: https://github.com/cran/MBNMAtime +* Date/Publication: 2023-10-14 15:20:02 UTC +* Number of recursive dependencies: 106 -Run `revdepcheck::cloud_details(, "greatR")` for more info +Run `revdepcheck::cloud_details(, "MBNMAtime")` for more info
## Newly broken -* checking running R code from vignettes ... ERROR +* checking re-building of vignette outputs ... NOTE ``` - Errors in running code in vignettes: - when running code in ‘process-results.Rmd’ - ... - - > reg_summary$non_registered_genes - [1] "BRAA02G018970.3C" - - > plot(reg_summary, type = "registered", scatterplot_size = c(4, - + 3.5)) + Error(s) in re-building vignettes: + --- re-building ‘consistencychecking-3.Rmd’ using rmarkdown - When sourcing ‘process-results.R’: - Error: object is not a unit - Execution halted + Quitting from lines 141-146 [unnamed-chunk-8] (consistencychecking-3.Rmd) + Error: processing vignette 'consistencychecking-3.Rmd' failed with diagnostics: + unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, "black", TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), list(NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), 5.5, c(5.5, 5.5, 5.5, 5.5), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.75, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, + NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, 90, NULL, c(0, 2.75, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 1, NULL, NULL, + NULL, c(0, 2.2, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, NULL, c(0, 0, 0, 2.2), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0.5, NULL, NULL, NULL, c(0, 2.2, 0, 2.2), NULL, TRUE), list("grey20", NULL, NULL, NULL, FALSE, "grey20", TRUE), NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 0.5, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 0.75, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, list(), NULL, NULL, NULL, NULL, NULL, + NULL, NULL, NULL, list("transparent", NA, NULL, NULL, FALSE), NULL, 2, NULL, NULL, list("transparent", NA, NULL, NULL, FALSE), 1.2, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 0.2, NULL, list(NULL, NULL, NULL, 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, NULL, NULL, NULL, TRUE), NULL, "right", NULL, NULL, NULL, "center", NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 0, list(), 2, list(), list(NULL, "grey20", NULL, NULL, TRUE), NULL, NULL, NULL, + list("grey92", NULL, NULL, NULL, FALSE, "grey92", TRUE), list("grey95", NULL, NULL, NULL, FALSE, "grey95", FALSE), list("grey95", 0.5, NULL, NULL, FALSE, "grey95", FALSE), NULL, NULL, NULL, NULL, FALSE, list("white", NA, NULL, NULL, FALSE), list(NULL, NULL, NULL, 1.2, 0, 1, NULL, NULL, c(0, 0, 5.5, 0), NULL, TRUE), "panel", list(NULL, NULL, NULL, NULL, 0, 1, NULL, NULL, c(0, 0, 5.5, 0), NULL, TRUE), list(NULL, NULL, NULL, 0.8, 1, 1, NULL, NULL, c(5.5, 0, 0, 0), NULL, TRUE), "panel", list(NULL, + NULL, NULL, 1.2, 0.5, 0.5, NULL, NULL, NULL, NULL, TRUE), "topleft", NULL, NULL, list("lightsteelblue1", "black", NULL, NULL, FALSE), NULL, NULL, "inherit", "inside", list(NULL, NULL, "black", 0.8, NULL, NULL, NULL, NULL, c(4.4, 4.4, 4.4, 4.4), NULL, FALSE), NULL, NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, NULL, -90, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, NULL, 90, NULL, NULL, NULL, TRUE), NULL, 2.75, 2.75)) + --- failed re-building ‘consistencychecking-3.Rmd’ - ‘data-requirement.Rmd’ using ‘UTF-8’... OK - ‘process-results.Rmd’ using ‘UTF-8’... failed - ‘register-data-manually.Rmd’ using ‘UTF-8’... OK - ‘register-data.Rmd’ using ‘UTF-8’... OK + --- re-building ‘dataexploration-1.Rmd’ using rmarkdown ``` -* checking re-building of vignette outputs ... NOTE +## In both + +* checking running R code from vignettes ... ERROR ``` - Error(s) in re-building vignettes: + Errors in running code in vignettes: + when running code in ‘consistencychecking-3.Rmd’ ... - --- re-building ‘data-requirement.Rmd’ using rmarkdown - --- finished re-building ‘data-requirement.Rmd’ + |-> direct | | 0.228| -0.213| 0.684| + |-> indirect | | -0.515| -0.891| -0.137| + | | | | | | - --- re-building ‘process-results.Rmd’ using rmarkdown + > plot(nodesplit, plot.type = "forest") - Quitting from lines 76-81 [plot-summary-results] (process-results.Rmd) - Error: processing vignette 'process-results.Rmd' failed with diagnostics: - object is not a unit + When sourcing ‘consistencychecking-3.R’: ... - --- finished re-building ‘register-data-manually.Rmd’ - - --- re-building ‘register-data.Rmd’ using rmarkdown - --- finished re-building ‘register-data.Rmd’ - - SUMMARY: processing the following file failed: - ‘process-results.Rmd’ - - Error: Vignette re-building failed. + ! unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, "black", TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), list(NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), 5.5, c(5.5, 5.5, 5.5, 5.5), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.75, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, + NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, 90, NULL, c(0, 2.75, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL Execution halted + + ‘consistencychecking-3.Rmd’ using ‘UTF-8’... failed + ‘dataexploration-1.Rmd’ using ‘UTF-8’... failed + ‘mbnmatime-overview.Rmd’ using ‘UTF-8’... OK + ‘outputs-4.Rmd’ using ‘UTF-8’... failed + ‘predictions-5.Rmd’ using ‘UTF-8’... OK + ‘runmbnmatime-2.Rmd’ using ‘UTF-8’... OK ``` -# Greymodels +# MetaNet
-* Version: 2.0.1 -* GitHub: https://github.com/havishaJ/Greymodels -* Source code: https://github.com/cran/Greymodels -* Date/Publication: 2022-12-05 12:42:35 UTC -* Number of recursive dependencies: 91 +* Version: 0.1.2 +* GitHub: https://github.com/Asa12138/MetaNet +* Source code: https://github.com/cran/MetaNet +* Date/Publication: 2024-03-25 20:40:07 UTC +* Number of recursive dependencies: 151 -Run `revdepcheck::cloud_details(, "Greymodels")` for more info +Run `revdepcheck::cloud_details(, "MetaNet")` for more info
@@ -9095,133 +8279,135 @@ Run `revdepcheck::cloud_details(, "Greymodels")` for more info * checking examples ... ERROR ``` - Running examples in ‘Greymodels-Ex.R’ failed + Running examples in ‘MetaNet-Ex.R’ failed The error most likely occurred in: - > ### Name: Plots - > ### Title: plots - > ### Aliases: plots plotrm plotsmv1 plotsmv2 plotsigndgm plots_mdbgm12 + > ### Name: as.ggig + > ### Title: Transfer an igraph object to a ggig + > ### Aliases: as.ggig > > ### ** Examples > - > # Plots - EPGM (1, 1) model - ... - + geom_point(data = set4, aes(x = CI, y = y), shape = 23, color = "black") + - + geom_line(data = xy1, aes(x = x, y = y,color = "Raw Data")) + - + geom_line(data = xy2, aes(x = x, y = y,color = "Fitted&Forecasts")) + - + geom_line(data = set3, aes(x = CI, y = y,color = "LowerBound"), linetype=2) + - + geom_line(data = set4, aes(x = CI, y = y,color = "UpperBound"), linetype=2) + - + scale_color_manual(name = "Label",values = colors) - > r <- ggplotly(p) - Error in pm[[2]] : subscript out of bounds - Calls: ggplotly -> ggplotly.ggplot -> gg2list + > as.ggig(co_net, coors = c_net_layout(co_net)) -> ggig + > plot(ggig) + Error in names(labels) <- `*vtmp*` : attempt to set an attribute on NULL + Calls: plot ... ggplot_add -> ggplot_add.new_aes -> bump_aes_labels Execution halted ``` -# groupdata2 +# metR
-* Version: 2.0.3 -* GitHub: https://github.com/ludvigolsen/groupdata2 -* Source code: https://github.com/cran/groupdata2 -* Date/Publication: 2023-06-18 12:30:02 UTC -* Number of recursive dependencies: 96 +* Version: 0.15.0 +* GitHub: https://github.com/eliocamp/metR +* Source code: https://github.com/cran/metR +* Date/Publication: 2024-02-09 00:40:02 UTC +* Number of recursive dependencies: 121 -Run `revdepcheck::cloud_details(, "groupdata2")` for more info +Run `revdepcheck::cloud_details(, "metR")` for more info
## Newly broken +* checking examples ... ERROR + ``` + Running examples in ‘metR-Ex.R’ failed + The error most likely occurred in: + + > ### Name: GeostrophicWind + > ### Title: Calculate geostrophic winds + > ### Aliases: GeostrophicWind + > + > ### ** Examples + > + > data(geopotential) + ... + > ggplot(geopotential[date == date[1]], aes(lon, lat)) + + + geom_contour(aes(z = gh)) + + + geom_vector(aes(dx = u, dy = v), skip = 2) + + + scale_mag() + Warning: The S3 guide system was deprecated in ggplot2 3.5.0. + ℹ It has been replaced by a ggproto system that can be extended. + Error in (function (layer, df) : + argument "theme" is missing, with no default + Calls: ... use_defaults -> eval_from_theme -> %||% -> calc_element + Execution halted + ``` + * checking running R code from vignettes ... ERROR ``` Errors in running code in vignettes: - when running code in ‘description_of_groupdata2.Rmd’ + when running code in ‘Visualization-tools.Rmd’ ... - > greedy_plot <- ggplot(greedy_data, aes(x, freq, color = Size)) + > (g <- ggplot(temperature[lev == 500], aes(lon, lat)) + + + geom_contour_fill(aes(z = air.z)) + geom_vector(aes(dx = t.dx, + + dy = t.dy), skip .... [TRUNCATED] + Warning: The S3 guide system was deprecated in ggplot2 3.5.0. + ℹ It has been replaced by a ggproto system that can be extended. - > greedy_plot + geom_point() + labs(x = "group", y = "group Size", - + title = "Greedy Distribution of Elements in groups", color = "Size") + - + .... [TRUNCATED] + ... + + dy = gh.dlat), s .... [TRUNCATED] + Warning: The S3 guide system was deprecated in ggplot2 3.5.0. + ℹ It has been replaced by a ggproto system that can be extended. - When sourcing ‘description_of_groupdata2.R’: - Error: Theme element `plot.margin` must have class . + When sourcing ‘Working-with-data.R’: + Error: argument "theme" is missing, with no default Execution halted - ‘automatic_groups_with_groupdata2.Rmd’ using ‘UTF-8’... OK - ‘cross-validation_with_groupdata2.Rmd’ using ‘UTF-8’... OK - ‘description_of_groupdata2.Rmd’ using ‘UTF-8’... failed - ‘introduction_to_groupdata2.Rmd’ using ‘UTF-8’... OK - ‘time_series_with_groupdata2.Rmd’ using ‘UTF-8’... OK + ‘Visualization-tools.Rmd’ using ‘UTF-8’... failed + ‘Working-with-data.Rmd’ using ‘UTF-8’... failed ``` * checking re-building of vignette outputs ... NOTE ``` Error(s) in re-building vignettes: - --- re-building ‘automatic_groups_with_groupdata2.Rmd’ using rmarkdown - --- finished re-building ‘automatic_groups_with_groupdata2.Rmd’ + ... + --- re-building ‘Visualization-tools.Rmd’ using knitr + + Quitting from lines 284-293 [unnamed-chunk-19] (Visualization-tools.Rmd) + Error: processing vignette 'Visualization-tools.Rmd' failed with diagnostics: + argument "theme" is missing, with no default + --- failed re-building ‘Visualization-tools.Rmd’ + + --- re-building ‘Working-with-data.Rmd’ using knitr + ... + Quitting from lines 199-210 [unnamed-chunk-13] (Working-with-data.Rmd) + Error: processing vignette 'Working-with-data.Rmd' failed with diagnostics: + argument "theme" is missing, with no default + --- failed re-building ‘Working-with-data.Rmd’ - --- re-building ‘cross-validation_with_groupdata2.Rmd’ using rmarkdown - Loading required namespace: broom - --- finished re-building ‘cross-validation_with_groupdata2.Rmd’ + SUMMARY: processing the following files failed: + ‘Visualization-tools.Rmd’ ‘Working-with-data.Rmd’ - --- re-building ‘description_of_groupdata2.Rmd’ using rmarkdown + Error: Vignette re-building failed. + Execution halted ``` -# GSD - -
- -* Version: 1.0.0 -* GitHub: NA -* Source code: https://github.com/cran/GSD -* Date/Publication: 2024-02-05 20:40:13 UTC -* Number of recursive dependencies: 32 - -Run `revdepcheck::cloud_details(, "GSD")` for more info - -
- -## Newly broken +## In both -* checking examples ... ERROR +* checking installed package size ... NOTE ``` - Running examples in ‘GSD-Ex.R’ failed - The error most likely occurred in: - - > ### Name: gfdecomp - > ### Title: Graph Fourier Decomposition - > ### Aliases: gfdecomp - > ### Keywords: nonparametric - > - > ### ** Examples - > - ... - Backtrace: - ▆ - 1. ├─base (local) ``(x) - 2. └─ggplot2:::print.ggplot(x) - 3. ├─ggplot2::ggplot_gtable(data) - 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) - 5. └─ggplot2::calc_element("plot.margin", theme) - 6. └─cli::cli_abort(...) - 7. └─rlang::abort(...) - Execution halted + installed size is 6.6Mb + sub-directories of 1Mb or more: + R 1.5Mb + data 2.0Mb + doc 1.8Mb ``` -# gtExtras +# migraph
-* Version: 0.5.0 -* GitHub: https://github.com/jthomasmock/gtExtras -* Source code: https://github.com/cran/gtExtras -* Date/Publication: 2023-09-15 22:32:06 UTC -* Number of recursive dependencies: 105 +* Version: 1.3.4 +* GitHub: https://github.com/stocnet/migraph +* Source code: https://github.com/cran/migraph +* Date/Publication: 2024-03-07 11:50:02 UTC +* Number of recursive dependencies: 120 -Run `revdepcheck::cloud_details(, "gtExtras")` for more info +Run `revdepcheck::cloud_details(, "migraph")` for more info
@@ -9233,89 +8419,118 @@ Run `revdepcheck::cloud_details(, "gtExtras")` for more info Running the tests in ‘tests/testthat.R’ failed. Complete output: > library(testthat) - > library(gtExtras) - Loading required package: gt - - Attaching package: 'gt' + > library(manynet) + > library(migraph) + > + > test_check("migraph") + [ FAIL 2 | WARN 0 | SKIP 0 | PASS 266 ] - The following object is masked from 'package:testthat': ... - 18. └─ggplot2:::print.ggplot(x) - 19. ├─ggplot2::ggplot_gtable(data) - 20. └─ggplot2:::ggplot_gtable.ggplot_built(data) - 21. └─ggplot2::calc_element("plot.margin", theme) - 22. └─cli::cli_abort(...) - 23. └─rlang::abort(...) + ── Failure ('test-model_tests.R:63:3'): cug plot works ───────────────────────── + cugplot$labels$x not identical to "Statistic". + target is NULL, current is character + ── Failure ('test-model_tests.R:73:3'): qap plot works ───────────────────────── + qapplot$labels$x not identical to "Statistic". + target is NULL, current is character - [ FAIL 1 | WARN 14 | SKIP 23 | PASS 112 ] + [ FAIL 2 | WARN 0 | SKIP 0 | PASS 266 ] Error: Test failures Execution halted ``` -# HaploCatcher +# MiMIR
-* Version: 1.0.4 +* Version: 1.5 * GitHub: NA -* Source code: https://github.com/cran/HaploCatcher -* Date/Publication: 2023-04-21 23:32:39 UTC -* Number of recursive dependencies: 113 +* Source code: https://github.com/cran/MiMIR +* Date/Publication: 2024-02-01 08:50:02 UTC +* Number of recursive dependencies: 191 -Run `revdepcheck::cloud_details(, "HaploCatcher")` for more info +Run `revdepcheck::cloud_details(, "MiMIR")` for more info
## Newly broken -* checking running R code from vignettes ... ERROR +* checking examples ... ERROR ``` - Errors in running code in vignettes: - when running code in ‘An_Intro_to_HaploCatcher.Rmd’ - ... - > set.seed(NULL) - - > results1 <- auto_locus(geno_mat = geno_mat, gene_file = gene_comp, - + gene_name = "sst1_solid_stem", marker_info = marker_info, - + chromosom .... [TRUNCATED] - Loading required package: lattice + Running examples in ‘MiMIR-Ex.R’ failed + The error most likely occurred in: - When sourcing ‘An_Intro_to_HaploCatcher.R’: - Error: object is not a unit + > ### Name: LOBOV_accuracies + > ### Title: LOBOV_accuracies + > ### Aliases: LOBOV_accuracies + > + > ### ** Examples + > + > require(pROC) + ... + 56 metabolites x 500 samples + | Pruning samples on5SD: + 56 metabolites x 500 samples + | Performing scaling ... DONE! + | Imputation ... DONE! + > p_avail<-colnames(b_p)[c(1:5)] + > LOBOV_accuracies(sur$surrogates, b_p, p_avail, MiMIR::acc_LOBOV) + Error in pm[[2]] : subscript out of bounds + Calls: LOBOV_accuracies -> -> ggplotly.ggplot -> gg2list Execution halted - - ‘An_Intro_to_HaploCatcher.Rmd’ using ‘UTF-8’... failed ``` -* checking re-building of vignette outputs ... NOTE +# miRetrieve + +
+ +* Version: 1.3.4 +* GitHub: NA +* Source code: https://github.com/cran/miRetrieve +* Date/Publication: 2021-09-18 17:30:02 UTC +* Number of recursive dependencies: 126 + +Run `revdepcheck::cloud_details(, "miRetrieve")` for more info + +
+ +## Newly broken + +* checking tests ... ERROR ``` - Error(s) in re-building vignettes: - ... - --- re-building ‘An_Intro_to_HaploCatcher.Rmd’ using rmarkdown - - Quitting from lines 242-253 [example_models_1] (An_Intro_to_HaploCatcher.Rmd) - Error: processing vignette 'An_Intro_to_HaploCatcher.Rmd' failed with diagnostics: - object is not a unit - --- failed re-building ‘An_Intro_to_HaploCatcher.Rmd’ - - SUMMARY: processing the following file failed: - ‘An_Intro_to_HaploCatcher.Rmd’ - - Error: Vignette re-building failed. - Execution halted + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(miRetrieve) + > + > test_check("miRetrieve") + [ FAIL 1 | WARN 11 | SKIP 0 | PASS 202 ] + + ══ Failed tests ════════════════════════════════════════════════════════════════ + ... + Backtrace: + ▆ + 1. └─miRetrieve::compare_mir_terms_scatter(df_merged, "miR-21", title = "Test_title") at test-comparemirterms.R:56:1 + 2. ├─plotly::ggplotly(plot) + 3. └─plotly:::ggplotly.ggplot(plot) + 4. └─plotly::gg2list(...) + + [ FAIL 1 | WARN 11 | SKIP 0 | PASS 202 ] + Error: Test failures + Execution halted ``` -# hdnom +# misspi
-* Version: 6.0.3 -* GitHub: https://github.com/nanxstats/hdnom -* Source code: https://github.com/cran/hdnom -* Date/Publication: 2024-03-03 03:20:02 UTC -* Number of recursive dependencies: 66 +* Version: 0.1.0 +* GitHub: NA +* Source code: https://github.com/cran/misspi +* Date/Publication: 2023-10-17 09:50:02 UTC +* Number of recursive dependencies: 88 -Run `revdepcheck::cloud_details(, "hdnom")` for more info +Run `revdepcheck::cloud_details(, "misspi")` for more info
@@ -9323,116 +8538,91 @@ Run `revdepcheck::cloud_details(, "hdnom")` for more info * checking examples ... ERROR ``` - Running examples in ‘hdnom-Ex.R’ failed + Running examples in ‘misspi-Ex.R’ failed The error most likely occurred in: - > ### Name: calibrate - > ### Title: Calibrate high-dimensional Cox models - > ### Aliases: calibrate + > ### Name: evaliq + > ### Title: Evaluate the Imputation Quality + > ### Aliases: evaliq > > ### ** Examples > - > data("smart") + > # A very quick example ... - Backtrace: - ▆ - 1. ├─base (local) ``(x) - 2. └─ggplot2:::print.ggplot(x) - 3. ├─ggplot2::ggplot_gtable(data) - 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) - 5. └─ggplot2::calc_element("plot.margin", theme) - 6. └─cli::cli_abort(...) - 7. └─rlang::abort(...) - Execution halted - ``` - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘hdnom.Rmd’ - ... - Mean 0.6841580 0.6935303 - Min 0.6770945 0.6800316 - 0.25 Qt. 0.6821133 0.6924729 - Median 0.6831368 0.6956285 - 0.75 Qt. 0.6864527 0.6966638 - Max 0.6939574 0.6997908 - - When sourcing ‘hdnom.R’: - Error: Theme element `plot.margin` must have class . + > # Default plot + > er.eval <- evaliq(x.true[na.idx], x.est[na.idx]) + `geom_smooth()` using formula = 'y ~ x' + > + > # Interactive plot + > er.eval <- evaliq(x.true[na.idx], x.est[na.idx], interactive = TRUE) + `geom_smooth()` using formula = 'y ~ x' + Error in pm[[2]] : subscript out of bounds + Calls: evaliq -> print -> ggplotly -> ggplotly.ggplot -> gg2list Execution halted - - ‘hdnom.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘hdnom.Rmd’ using rmarkdown ``` -# healthyR +# mizer
-* Version: 0.2.1 -* GitHub: https://github.com/spsanderson/healthyR -* Source code: https://github.com/cran/healthyR -* Date/Publication: 2023-04-06 22:20:03 UTC -* Number of recursive dependencies: 158 +* Version: 2.5.1 +* GitHub: https://github.com/sizespectrum/mizer +* Source code: https://github.com/cran/mizer +* Date/Publication: 2024-03-08 23:10:02 UTC +* Number of recursive dependencies: 110 -Run `revdepcheck::cloud_details(, "healthyR")` for more info +Run `revdepcheck::cloud_details(, "mizer")` for more info
## Newly broken -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘getting-started.Rmd’ - ... - - > ts_alos_plt(.data = df_tbl, .date_col = Date, .value_col = Values, - + .by = "month", .interactive = FALSE) - - > ts_alos_plt(.data = df_tbl, .date_col = Date, .value_col = Values, - + .by = "month", .interactive = TRUE) - - When sourcing ‘getting-started.R’: - Error: subscript out of bounds - Execution halted - - ‘getting-started.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE +* checking tests ... ERROR ``` - Error(s) in re-building vignettes: - --- re-building ‘getting-started.Rmd’ using rmarkdown + Running ‘spelling.R’ + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(mizer) + > + > test_check("mizer") + [ FAIL 10 | WARN 0 | SKIP 5 | PASS 1251 ] + + ... + • plots/plot-spectra.svg + • plots/plot-yield-by-gear.svg + • plots/plot-yield.svg + • plots/plotfishing-mortality.svg + • plots/plotfmort-truncated.svg + • plots/plotpredation-mortality.svg + • plots/plotpredmort-truncated.new.svg + • plots/plotpredmort-truncated.svg + Error: Test failures + Execution halted ``` ## In both * checking installed package size ... NOTE ``` - installed size is 6.6Mb + installed size is 6.1Mb sub-directories of 1Mb or more: - data 2.5Mb - doc 3.7Mb + doc 1.5Mb + help 1.8Mb ``` -# healthyR.ai +# mlr3spatiotempcv
-* Version: 0.0.13 -* GitHub: https://github.com/spsanderson/healthyR.ai -* Source code: https://github.com/cran/healthyR.ai -* Date/Publication: 2023-04-03 00:20:02 UTC -* Number of recursive dependencies: 229 +* Version: 2.3.1 +* GitHub: https://github.com/mlr-org/mlr3spatiotempcv +* Source code: https://github.com/cran/mlr3spatiotempcv +* Date/Publication: 2024-04-17 12:10:05 UTC +* Number of recursive dependencies: 168 -Run `revdepcheck::cloud_details(, "healthyR.ai")` for more info +Run `revdepcheck::cloud_details(, "mlr3spatiotempcv")` for more info
@@ -9440,77 +8630,67 @@ Run `revdepcheck::cloud_details(, "healthyR.ai")` for more info * checking examples ... ERROR ``` - Running examples in ‘healthyR.ai-Ex.R’ failed + Running examples in ‘mlr3spatiotempcv-Ex.R’ failed The error most likely occurred in: - > ### Name: pca_your_recipe - > ### Title: Perform PCA - > ### Aliases: pca_your_recipe + > ### Name: autoplot.ResamplingCustomCV + > ### Title: Visualization Functions for Non-Spatial CV Methods. + > ### Aliases: autoplot.ResamplingCustomCV plot.ResamplingCustomCV > > ### ** Examples > - > suppressPackageStartupMessages(library(timetk)) + > if (mlr3misc::require_namespaces(c("sf", "patchwork"), quietly = TRUE)) { ... - + step_rm(matches("(iso$)|(xts$)|(hour)|(min)|(sec)|(am.pm)")) - > - > output_list <- pca_your_recipe(rec_obj, .data = data_tbl) - Warning: ! The following columns have zero variance so scaling cannot be used: - date_col_day, date_col_mday, date_col_mweek, and date_col_mday7. - ℹ Consider using ?step_zv (`?recipes::step_zv()`) to remove those columns - before normalizing. - Error in pm[[2]] : subscript out of bounds - Calls: pca_your_recipe -> -> ggplotly.ggplot -> gg2list + + + + autoplot(resampling, task) + + + ggplot2::scale_x_continuous(breaks = seq(-79.085, -79.055, 0.01)) + + autoplot(resampling, task, fold_id = 1) + + autoplot(resampling, task, fold_id = c(1, 2)) * + + ggplot2::scale_x_continuous(breaks = seq(-79.085, -79.055, 0.01)) + + } + Error in identicalUnits(x) : object is not a unit + Calls: ... assemble_guides -> guides_build -> unit.c -> identicalUnits Execution halted ``` +## In both + * checking running R code from vignettes ... ERROR ``` Errors in running code in vignettes: - when running code in ‘getting-started.Rmd’ + when running code in ‘spatiotemp-viz.Rmd’ ... - > pca_list <- pca_your_recipe(.recipe_object = rec_obj, - + .data = data_tbl, .threshold = 0.8, .top_n = 5) - Warning: ! The following columns have zero variance so scaling cannot be used: - date_col_day, date_col_mday, date_col_mweek, and date_col_mday7. - ℹ Consider using ?step_zv (`?recipes::step_zv()`) to remove those columns - before normalizing. - When sourcing ‘getting-started.R’: - Error: subscript out of bounds + > knitr::opts_chunk$set(collapse = TRUE, comment = "#>") + + > knitr::include_graphics("../man/figures/sptcv_cstf_multiplot.png") + + When sourcing ‘spatiotemp-viz.R’: + Error: Cannot find the file(s): "../man/figures/sptcv_cstf_multiplot.png" Execution halted - ‘auto-kmeans.Rmd’ using ‘UTF-8’... OK - ‘getting-started.Rmd’ using ‘UTF-8’... failed - ‘kmeans-umap.Rmd’ using ‘UTF-8’... OK + ‘mlr3spatiotempcv.Rmd’ using ‘UTF-8’... OK + ‘spatiotemp-viz.Rmd’ using ‘UTF-8’... failed ``` -* checking re-building of vignette outputs ... NOTE +* checking installed package size ... NOTE ``` - Error(s) in re-building vignettes: - --- re-building ‘auto-kmeans.Rmd’ using rmarkdown - --- finished re-building ‘auto-kmeans.Rmd’ - - --- re-building ‘getting-started.Rmd’ using rmarkdown - - Quitting from lines 107-113 [pca_your_rec] (getting-started.Rmd) - Error: processing vignette 'getting-started.Rmd' failed with diagnostics: - subscript out of bounds - --- failed re-building ‘getting-started.Rmd’ - - --- re-building ‘kmeans-umap.Rmd’ using rmarkdown + installed size is 5.9Mb + sub-directories of 1Mb or more: + data 3.5Mb ``` -# healthyR.ts +# mlr3viz
-* Version: 0.3.0 -* GitHub: https://github.com/spsanderson/healthyR.ts -* Source code: https://github.com/cran/healthyR.ts -* Date/Publication: 2023-11-15 06:00:05 UTC -* Number of recursive dependencies: 222 +* Version: 0.9.0 +* GitHub: https://github.com/mlr-org/mlr3viz +* Source code: https://github.com/cran/mlr3viz +* Date/Publication: 2024-07-01 12:30:02 UTC +* Number of recursive dependencies: 142 -Run `revdepcheck::cloud_details(, "healthyR.ts")` for more info +Run `revdepcheck::cloud_details(, "mlr3viz")` for more info
@@ -9518,321 +8698,176 @@ Run `revdepcheck::cloud_details(, "healthyR.ts")` for more info * checking examples ... ERROR ``` - Running examples in ‘healthyR.ts-Ex.R’ failed + Running examples in ‘mlr3viz-Ex.R’ failed The error most likely occurred in: - > ### Name: tidy_fft - > ### Title: Tidy Style FFT - > ### Aliases: tidy_fft + > ### Name: autoplot.OptimInstanceBatchSingleCrit + > ### Title: Plots for Optimization Instances + > ### Aliases: autoplot.OptimInstanceBatchSingleCrit > > ### ** Examples > - > suppressPackageStartupMessages(library(dplyr)) + > if (requireNamespace("mlr3") && requireNamespace("bbotk") && requireNamespace("patchwork")) { ... - > a <- tidy_fft( - + .data = data_tbl, - + .value_col = value, - + .date_col = date_col, - + .harmonics = 3, - + .frequency = 12 - + ) - Error in pm[[2]] : subscript out of bounds - Calls: tidy_fft -> -> ggplotly.ggplot -> gg2list - Execution halted - ``` - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘using-tidy-fft.Rmd’ - ... - $ value 112, 118, 132, 129, 121, 135, 148, 148, 136, 119, 104, 118, 1… - - > suppressPackageStartupMessages(library(timetk)) - - > data_tbl %>% plot_time_series(.date_var = date_col, - + .value = value) - - When sourcing ‘using-tidy-fft.R’: - Error: subscript out of bounds + INFO [09:19:55.573] [bbotk] 5.884797 2.2371095 -32.51896 + INFO [09:19:55.573] [bbotk] -7.841127 -0.8872557 -91.31148 + INFO [09:19:55.608] [bbotk] Finished optimizing after 20 evaluation(s) + INFO [09:19:55.609] [bbotk] Result: + INFO [09:19:55.613] [bbotk] x1 x2 x_domain y + INFO [09:19:55.613] [bbotk] + INFO [09:19:55.613] [bbotk] 2.582281 -2.940254 9.657379 + Error in identicalUnits(x) : object is not a unit + Calls: print ... assemble_guides -> guides_build -> unit.c -> identicalUnits Execution halted - - ‘getting-started.Rmd’ using ‘UTF-8’... OK - ‘using-tidy-fft.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘getting-started.Rmd’ using rmarkdown - ``` - -## In both - -* checking installed package size ... NOTE - ``` - installed size is 6.3Mb - sub-directories of 1Mb or more: - doc 5.2Mb ``` -# heatmaply +# modeltime.resample
-* Version: 1.5.0 -* GitHub: https://github.com/talgalili/heatmaply -* Source code: https://github.com/cran/heatmaply -* Date/Publication: 2023-10-06 20:50:02 UTC -* Number of recursive dependencies: 111 +* Version: 0.2.3 +* GitHub: https://github.com/business-science/modeltime.resample +* Source code: https://github.com/cran/modeltime.resample +* Date/Publication: 2023-04-12 15:50:02 UTC +* Number of recursive dependencies: 228 -Run `revdepcheck::cloud_details(, "heatmaply")` for more info +Run `revdepcheck::cloud_details(, "modeltime.resample")` for more info
## Newly broken -* checking examples ... ERROR - ``` - Running examples in ‘heatmaply-Ex.R’ failed - The error most likely occurred in: - - > ### Name: ggheatmap - > ### Title: ggplot heatmap equivalent to heatmaply - > ### Aliases: ggheatmap - > - > ### ** Examples - > - > ggheatmap(mtcars) - ... - 2. └─heatmaply:::arrange_plots(...) - 3. └─egg::ggarrange(...) - 4. └─base::lapply(plots, ggplot2::ggplotGrob) - 5. └─ggplot2 (local) FUN(X[[i]], ...) - 6. ├─ggplot2::ggplot_gtable(ggplot_build(x)) - 7. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) - 8. └─ggplot2::calc_element("plot.margin", theme) - 9. └─cli::cli_abort(...) - 10. └─rlang::abort(...) - Execution halted - ``` - * checking tests ... ERROR ``` Running ‘testthat.R’ Running the tests in ‘tests/testthat.R’ failed. Complete output: > library(testthat) - > library(heatmaply) - Loading required package: plotly - Loading required package: ggplot2 - - Attaching package: 'plotly' - + > + > # Machine Learning + > library(tidymodels) + ── Attaching packages ────────────────────────────────────── tidymodels 1.2.0 ── + ✔ broom 1.0.6 ✔ recipes 1.1.0 + ✔ dials 1.2.1 ✔ rsample 1.2.1 ... - 4. │ │ └─base::withCallingHandlers(...) - 5. │ └─rlang::eval_bare(quo_get_expr(.quo), quo_get_env(.quo)) - 6. ├─heatmaply:::predict_colors(ggplotly(g), plot_method = "ggplot") - 7. ├─plotly::ggplotly(g) - 8. └─plotly:::ggplotly.ggplot(g) - 9. └─plotly::gg2list(...) + ▆ + 1. ├─m750_models_resample %>% ... at test-modeltime_fit_resamples.R:116:5 + 2. └─modeltime.resample::plot_modeltime_resamples(., .interactive = TRUE) + 3. ├─plotly::ggplotly(g) + 4. └─plotly:::ggplotly.ggplot(g) + 5. └─plotly::gg2list(...) - [ FAIL 59 | WARN 0 | SKIP 0 | PASS 185 ] + [ FAIL 1 | WARN 4 | SKIP 0 | PASS 16 ] Error: Test failures Execution halted ``` -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘heatmaply.Rmd’ - ... - - > library("heatmaply") - - > library("heatmaply") - - > heatmaply(mtcars) - - When sourcing ‘heatmaply.R’: - Error: subscript out of bounds - Execution halted - - ‘heatmaply.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - ... - --- re-building ‘heatmaply.Rmd’ using rmarkdown - - Quitting from lines 109-111 [unnamed-chunk-5] (heatmaply.Rmd) - Error: processing vignette 'heatmaply.Rmd' failed with diagnostics: - subscript out of bounds - --- failed re-building ‘heatmaply.Rmd’ - - SUMMARY: processing the following file failed: - ‘heatmaply.Rmd’ - - Error: Vignette re-building failed. - Execution halted - ``` - ## In both -* checking installed package size ... NOTE +* checking dependencies in R code ... NOTE ``` - installed size is 5.5Mb - sub-directories of 1Mb or more: - doc 5.1Mb + Namespaces in Imports field not imported from: + ‘crayon’ ‘dials’ ‘glue’ ‘parsnip’ + All declared Imports should be used. ``` -# hermiter +# move
-* Version: 2.3.1 -* GitHub: https://github.com/MikeJaredS/hermiter -* Source code: https://github.com/cran/hermiter -* Date/Publication: 2024-03-06 23:50:02 UTC -* Number of recursive dependencies: 79 +* Version: 4.2.4 +* GitHub: NA +* Source code: https://github.com/cran/move +* Date/Publication: 2023-07-06 23:10:02 UTC +* Number of recursive dependencies: 153 -Run `revdepcheck::cloud_details(, "hermiter")` for more info +Run `revdepcheck::cloud_details(, "move")` for more info
## Newly broken -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘hermiter.Rmd’ - ... - > p2 <- ggplot(df_pdf_cdf) + geom_tile(aes(X, Y, fill = pdf_est)) + - + scale_fill_continuous_sequential(palette = "Oslo", breaks = seq(0, - + .... [TRUNCATED] - - > p1 + ggtitle("Actual PDF") + theme(legend.title = element_blank()) + - + p2 + ggtitle("Estimated PDF") + theme(legend.title = element_blank()) + .... [TRUNCATED] - - When sourcing ‘hermiter.R’: - Error: object is not a unit - Execution halted - - ‘hermiter.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘hermiter.Rmd’ using rmarkdown - ``` - -## In both - * checking installed package size ... NOTE ``` - installed size is 6.5Mb + installed size is 5.4Mb sub-directories of 1Mb or more: - R 2.6Mb - doc 1.9Mb - libs 1.8Mb + R 2.0Mb ``` -* checking for GNU extensions in Makefiles ... NOTE - ``` - GNU make is a SystemRequirements. - ``` - -# heumilkr - -
- -* Version: 0.2.0 -* GitHub: https://github.com/lschneiderbauer/heumilkr -* Source code: https://github.com/cran/heumilkr -* Date/Publication: 2024-04-01 13:50:06 UTC -* Number of recursive dependencies: 80 - -Run `revdepcheck::cloud_details(, "heumilkr")` for more info - -
- -## Newly broken +## In both * checking running R code from vignettes ... ERROR ``` Errors in running code in vignettes: - when running code in ‘clarke_wright_performance.Rmd’ + when running code in ‘move.Rmd’ ... - + "F", "tai"), group_desc = c("Augerat A, 1995", "Augerat B, 1995", - + "Christofides and ..." ... [TRUNCATED] - > ggMarginal(ggplot(merge(result, description, by = "group"), - + aes(x = n_site, y = clarke_wright_perf_xi, color = group_desc)) + - + geom_poi .... [TRUNCATED] + > leroyWithGap_p <- spTransform(leroyWithGap, center = TRUE) - When sourcing ‘clarke_wright_performance.R’: - Error: Theme element `plot.margin` must have class . - Execution halted - - ‘clarke_wright_performance.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - ... - --- re-building ‘clarke_wright_performance.Rmd’ using rmarkdown + > dbb <- brownian.bridge.dyn(leroyWithGap_p, raster = 100, + + location.error = 20) + Computational size: 7.0e+07 - Quitting from lines 69-97 [perf_scale_based_graph] (clarke_wright_performance.Rmd) - Error: processing vignette 'clarke_wright_performance.Rmd' failed with diagnostics: - Theme element `plot.margin` must have class . - --- failed re-building ‘clarke_wright_performance.Rmd’ - - SUMMARY: processing the following file failed: - ‘clarke_wright_performance.Rmd’ - - Error: Vignette re-building failed. + When sourcing ‘move.R’: + Error: Lower x grid not large enough, consider extending the raster in that direction or enlarging the ext argument Execution halted + + ‘browseMovebank.Rmd’ using ‘UTF-8’... OK + ‘move.Rmd’ using ‘UTF-8’... failed ``` -# heuristicsmineR +# mtb
-* Version: 0.3.0 -* GitHub: https://github.com/bupaverse/heuristicsmineR -* Source code: https://github.com/cran/heuristicsmineR -* Date/Publication: 2023-04-04 13:20:06 UTC -* Number of recursive dependencies: 106 +* Version: 0.1.8 +* GitHub: https://github.com/yh202109/mtb +* Source code: https://github.com/cran/mtb +* Date/Publication: 2022-10-20 17:22:35 UTC +* Number of recursive dependencies: 64 -Run `revdepcheck::cloud_details(, "heuristicsmineR")` for more info +Run `revdepcheck::cloud_details(, "mtb")` for more info
## Newly broken -* checking installed package size ... NOTE +* checking tests ... ERROR ``` - installed size is 5.4Mb - sub-directories of 1Mb or more: - data 2.0Mb - libs 3.1Mb + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(mtb) + > + > test_check("mtb") + [ FAIL 2 | WARN 13 | SKIP 0 | PASS 56 ] + + ══ Failed tests ════════════════════════════════════════════════════════════════ + ... + - "yend" [6] + - "xmin" [7] + - "xmax" [8] + - "ymin" [9] + - "ymax" [10] + ... ... ... and 3 more ... + + [ FAIL 2 | WARN 13 | SKIP 0 | PASS 56 ] + Error: Test failures + Execution halted ``` -# HistDAWass +# neatmaps
-* Version: 1.0.8 -* GitHub: NA -* Source code: https://github.com/cran/HistDAWass -* Date/Publication: 2024-01-24 17:42:31 UTC -* Number of recursive dependencies: 111 +* Version: 2.1.0 +* GitHub: https://github.com/PhilBoileau/neatmaps +* Source code: https://github.com/cran/neatmaps +* Date/Publication: 2019-05-12 19:10:03 UTC +* Number of recursive dependencies: 99 -Run `revdepcheck::cloud_details(, "HistDAWass")` for more info +Run `revdepcheck::cloud_details(, "neatmaps")` for more info
@@ -9840,26 +8875,26 @@ Run `revdepcheck::cloud_details(, "HistDAWass")` for more info * checking examples ... ERROR ``` - Running examples in ‘HistDAWass-Ex.R’ failed + Running examples in ‘neatmaps-Ex.R’ failed The error most likely occurred in: - > ### Name: plot-HTS - > ### Title: Method plot for a histogram time series - > ### Aliases: plot-HTS plot,HTS-method + > ### Name: consClustResTable + > ### Title: Consensus Cluster Results in a Table + > ### Aliases: consClustResTable > > ### ** Examples > - > plot(subsetHTS(RetHTS, from = 1, to = 10)) # plots RetHTS dataset + > # create the data frame using the network, node and edge attributes ... - 4. └─HistDAWass:::plot.HTS.1v(x, type = type, border = border, maxno.perplot = maxno.perplot) - 5. └─HistDAWass:::multiplot(listofP) - 6. ├─base::print(plots[[1]]) - 7. └─ggplot2:::print.ggplot(plots[[1]]) - 8. ├─ggplot2::ggplot_gtable(data) - 9. └─ggplot2:::ggplot_gtable.ggplot_built(data) - 10. └─ggplot2::calc_element("plot.margin", theme) - 11. └─cli::cli_abort(...) - 12. └─rlang::abort(...) + > df <- netsDataFrame(network_attr_df, + + node_attr_df, + + edge_df) + > + > # run the neatmap code on df + > neat_res <- neatmap(df, scale_df = "ecdf", max_k = 3, reps = 100, + + xlab = "vars", ylab = "nets", xlab_cex = 1, ylab_cex = 1) + Error in pm[[2]] : subscript out of bounds + Calls: neatmap ... %>% -> layout -> ggplotly -> ggplotly.ggplot -> gg2list Execution halted ``` @@ -9867,117 +8902,80 @@ Run `revdepcheck::cloud_details(, "HistDAWass")` for more info * checking installed package size ... NOTE ``` - installed size is 9.3Mb - sub-directories of 1Mb or more: - R 1.5Mb - data 2.0Mb - libs 5.6Mb + installed size is 6.3Mb ``` -# huito +# NetFACS
-* Version: 0.2.4 -* GitHub: https://github.com/flavjack/huito -* Source code: https://github.com/cran/huito -* Date/Publication: 2023-10-25 16:30:02 UTC -* Number of recursive dependencies: 137 - -Run `revdepcheck::cloud_details(, "huito")` for more info - -
+* Version: 0.5.0 +* GitHub: NA +* Source code: https://github.com/cran/NetFACS +* Date/Publication: 2022-12-06 17:32:35 UTC +* Number of recursive dependencies: 101 + +Run `revdepcheck::cloud_details(, "NetFACS")` for more info + +
## Newly broken * checking examples ... ERROR ``` - Running examples in ‘huito-Ex.R’ failed + Running examples in ‘NetFACS-Ex.R’ failed The error most likely occurred in: - > ### Name: include_shape - > ### Title: Shape layer - > ### Aliases: include_shape + > ### Name: network_conditional + > ### Title: Create a network based on conditional probabilities of dyads of + > ### elements + > ### Aliases: network_conditional > > ### ** Examples > - > - ... - 5. └─cowplot::draw_plot(...) - 6. ├─cowplot::as_grob(plot) - 7. └─cowplot:::as_grob.ggplot(plot) - 8. └─ggplot2::ggplotGrob(plot) - 9. ├─ggplot2::ggplot_gtable(ggplot_build(x)) - 10. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) - 11. └─ggplot2::calc_element("plot.margin", theme) - 12. └─cli::cli_abort(...) - 13. └─rlang::abort(...) - Execution halted - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘germinar.Rmd’ using rmarkdown - - Quitting from lines 67-69 [unnamed-chunk-2] (germinar.Rmd) - Error: processing vignette 'germinar.Rmd' failed with diagnostics: - Theme element `plot.margin` must have class . - --- failed re-building ‘germinar.Rmd’ - - --- re-building ‘huito.Rmd’ using rmarkdown - --- finished re-building ‘huito.Rmd’ ... - Quitting from lines 68-70 [unnamed-chunk-2] (stickers.Rmd) - Error: processing vignette 'stickers.Rmd' failed with diagnostics: - Theme element `plot.margin` must have class . - --- failed re-building ‘stickers.Rmd’ - - SUMMARY: processing the following files failed: - ‘germinar.Rmd’ ‘labels.Rmd’ ‘stickers.Rmd’ - - Error: Vignette re-building failed. + Warning in grid.Call.graphics(C_text, as.graphicsAnnot(x$label), x$x, x$y, : + font family 'Arial Narrow' not found in PostScript font database + Warning in grid.Call.graphics(C_text, as.graphicsAnnot(x$label), x$x, x$y, : + font family 'Arial Narrow' not found in PostScript font database + Warning in grid.Call.graphics(C_text, as.graphicsAnnot(x$label), x$x, x$y, : + font family 'Arial Narrow' not found in PostScript font database + Error in grid.Call.graphics(C_text, as.graphicsAnnot(x$label), x$x, x$y, : + invalid font type + Calls: ... drawDetails -> drawDetails.text -> grid.Call.graphics Execution halted ``` -## In both - * checking running R code from vignettes ... ERROR ``` Errors in running code in vignettes: - when running code in ‘germinar.Rmd’ + when running code in ‘netfacs_tutorial.Rmd’ ... - > huito_fonts(font) - - > label <- label_layout(size = c(5.08, 5.08), border_width = 0, - + background = "#b1d842") %>% include_image(value = "https://germinar.inkaverse.c ..." ... [TRUNCATED] - - > label %>% label_print(mode = "preview") - - ... - > label %>% label_print(mode = "preview") + Warning in grid.Call.graphics(C_text, as.graphicsAnnot(x$label), x$x, x$y, : + font family 'Arial Narrow' not found in PostScript font database + Warning in grid.Call.graphics(C_text, as.graphicsAnnot(x$label), x$x, x$y, : + font family 'Arial Narrow' not found in PostScript font database + Warning in grid.Call.graphics(C_text, as.graphicsAnnot(x$label), x$x, x$y, : + font family 'Arial Narrow' not found in PostScript font database - When sourcing ‘stickers.R’: - Error: Theme element `plot.margin` must have class . + When sourcing ‘netfacs_tutorial.R’: + Error: invalid font type Execution halted - ‘germinar.Rmd’ using ‘UTF-8’... failed - ‘huito.Rmd’ using ‘UTF-8’... failed - ‘labels.Rmd’ using ‘UTF-8’... failed - ‘stickers.Rmd’ using ‘UTF-8’... failed + ‘netfacs_tutorial.Rmd’ using ‘UTF-8’... failed ``` -# hurricaneexposure +# NeuralSens
-* Version: 0.1.1 -* GitHub: https://github.com/geanders/hurricaneexposure -* Source code: https://github.com/cran/hurricaneexposure -* Date/Publication: 2020-02-13 14:30:02 UTC -* Number of recursive dependencies: 77 +* Version: 1.1.3 +* GitHub: https://github.com/JaiPizGon/NeuralSens +* Source code: https://github.com/cran/NeuralSens +* Date/Publication: 2024-05-11 19:43:03 UTC +* Number of recursive dependencies: 138 -Run `revdepcheck::cloud_details(, "hurricaneexposure")` for more info +Run `revdepcheck::cloud_details(, "NeuralSens")` for more info
@@ -9985,78 +8983,90 @@ Run `revdepcheck::cloud_details(, "hurricaneexposure")` for more info * checking examples ... ERROR ``` - Running examples in ‘hurricaneexposure-Ex.R’ failed + Running examples in ‘NeuralSens-Ex.R’ failed The error most likely occurred in: - > ### Name: default_map - > ### Title: Create a default map with eastern US states - > ### Aliases: default_map + > ### Name: SensMatPlot + > ### Title: Plot sensitivities of a neural network model + > ### Aliases: SensMatPlot > > ### ** Examples > - > default_map() + > ## Load data ------------------------------------------------------------------- ... - Backtrace: - ▆ - 1. ├─base (local) ``(x) - 2. └─ggplot2:::print.ggplot(x) - 3. ├─ggplot2::ggplot_gtable(data) - 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) - 5. └─ggplot2::calc_element("plot.margin", theme) - 6. └─cli::cli_abort(...) - 7. └─rlang::abort(...) + final value 1321.996301 + converged + > # Try HessianMLP + > H <- NeuralSens::HessianMLP(nnetmod, trData = nntrData, plot = FALSE) + > NeuralSens::SensMatPlot(H) + > S <- NeuralSens::SensAnalysisMLP(nnetmod, trData = nntrData, plot = FALSE) + > NeuralSens::SensMatPlot(H, S, senstype = "interactions") + Error in names(labels) <- `*vtmp*` : attempt to set an attribute on NULL + Calls: ... ggplot_add -> ggplot_add.new_aes -> bump_aes_labels Execution halted ``` -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘hurricaneexposure.Rmd’ - ... - - > map_event_exposure(storm = "Floyd-1999", event_type = "flood") - - > map_event_exposure(storm = "Ivan-2004", event_type = "tornado") - - > map_tracks(storms = "Floyd-1999") - - When sourcing ‘hurricaneexposure.R’: - Error: Theme element `plot.margin` must have class . - Execution halted - - ‘hurricaneexposure.Rmd’ using ‘UTF-8’... failed - ``` +# NHSRplotthedots -* checking re-building of vignette outputs ... NOTE +
+ +* Version: 0.1.0 +* GitHub: NA +* Source code: https://github.com/cran/NHSRplotthedots +* Date/Publication: 2021-11-03 20:20:10 UTC +* Number of recursive dependencies: 88 + +Run `revdepcheck::cloud_details(, "NHSRplotthedots")` for more info + +
+ +## Newly broken + +* checking tests ... ERROR ``` - Error(s) in re-building vignettes: - --- re-building ‘hurricaneexposure.Rmd’ using rmarkdown + Running ‘spelling.R’ + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(NHSRplotthedots) + > + > test_check("NHSRplotthedots") + [ FAIL 1 | WARN 733 | SKIP 3 | PASS 431 ] + + ... + + `actual$type` is absent + `expected$type` is a character vector ('type') + + `actual$text` is absent + `expected$text` is a character vector ('text') + + [ FAIL 1 | WARN 733 | SKIP 3 | PASS 431 ] + Error: Test failures + Execution halted ``` ## In both * checking dependencies in R code ... NOTE ``` - Namespace in Imports field not imported from: ‘mapproj’ + Namespaces in Imports field not imported from: + ‘NHSRdatasets’ ‘grid’ ‘utils’ All declared Imports should be used. ``` -* checking LazyData ... NOTE - ``` - 'LazyData' is specified without a 'data' directory - ``` - -# HVT +# NIMAA
-* Version: 24.5.2 -* GitHub: https://github.com/Mu-Sigma/HVT -* Source code: https://github.com/cran/HVT -* Date/Publication: 2024-05-15 08:50:21 UTC -* Number of recursive dependencies: 200 +* Version: 0.2.1 +* GitHub: https://github.com/jafarilab/NIMAA +* Source code: https://github.com/cran/NIMAA +* Date/Publication: 2022-04-11 14:12:45 UTC +* Number of recursive dependencies: 177 -Run `revdepcheck::cloud_details(, "HVT")` for more info +Run `revdepcheck::cloud_details(, "NIMAA")` for more info
@@ -10064,170 +9074,117 @@ Run `revdepcheck::cloud_details(, "HVT")` for more info * checking examples ... ERROR ``` - Running examples in ‘HVT-Ex.R’ failed + Running examples in ‘NIMAA-Ex.R’ failed The error most likely occurred in: - > ### Name: getTransitionProbability - > ### Title: Creating Transition Probabilities list - > ### Aliases: getTransitionProbability - > ### Keywords: Transition_or_Prediction + > ### Name: extractSubMatrix + > ### Title: Extract the non-missing submatrices from a given matrix. + > ### Aliases: extractSubMatrix > > ### ** Examples > + > # load part of the beatAML data ... - Ignoring unknown parameters: `check_overlap` - Scale for x is already present. - Adding another scale for x, which will replace the existing scale. - Scale for y is already present. - Adding another scale for y, which will replace the existing scale. - Warning in geom_polygon(data = boundaryCoords2, aes(x = bp.x, y = bp.y, : - Ignoring unknown aesthetics: text + + row.vars = "inhibitor") + binmatnest.temperature + 13.21221 + Size of Square: 66 rows x 66 columns + Size of Rectangular_row: 6 rows x 105 columns + Size of Rectangular_col: 99 rows x 2 columns + Size of Rectangular_element_max: 59 rows x 79 columns Error in pm[[2]] : subscript out of bounds - Calls: scoreHVT -> -> ggplotly.ggplot -> gg2list + Calls: extractSubMatrix ... plotSubmatrix -> print -> -> ggplotly.ggplot -> gg2list Execution halted ``` -# hydraulics - -
- -* Version: 0.7.0 -* GitHub: https://github.com/EdM44/hydraulics -* Source code: https://github.com/cran/hydraulics -* Date/Publication: 2024-03-06 13:10:08 UTC -* Number of recursive dependencies: 70 - -Run `revdepcheck::cloud_details(, "hydraulics")` for more info - -
- -## Newly broken - -* checking examples ... ERROR +* checking tests ... ERROR ``` - Running examples in ‘hydraulics-Ex.R’ failed - The error most likely occurred in: - - > ### Name: moody - > ### Title: Creates a Moody diagram with optional manually added points - > ### Aliases: moody - > - > ### ** Examples - > - > + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(NIMAA) + Warning message: + In check_dep_version() : ABI version mismatch: + lme4 was built with Matrix ABI version 1 + Current Matrix ABI version is 0 + Please re-install lme4 from source or restore original 'Matrix' package ... - Backtrace: - ▆ - 1. └─hydraulics::moody() - 2. └─ggplot2::ggplotGrob(p4) - 3. ├─ggplot2::ggplot_gtable(ggplot_build(x)) - 4. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) - 5. └─ggplot2::calc_element("plot.margin", theme) - 6. └─cli::cli_abort(...) - 7. └─rlang::abort(...) - Execution halted + 1. └─NIMAA::extractSubMatrix(...) at test-extract-nonmissing-submatrix.R:5:3 + 2. └─NIMAA:::plotSubmatrix(...) + 3. ├─base::print(plotly::ggplotly(p)) + 4. ├─plotly::ggplotly(p) + 5. └─plotly:::ggplotly.ggplot(p) + 6. └─plotly::gg2list(...) + + [ FAIL 1 | WARN 4 | SKIP 0 | PASS 7 ] + Error: Test failures + Execution halted ``` * checking running R code from vignettes ... ERROR ``` Errors in running code in vignettes: - when running code in ‘hydraulics_vignette.Rmd’ + when running code in ‘NIMAA-vignette.Rmd’ ... - Mean Roughness, ks = 0.000434 m - > Re_values <- unlist((as.data.frame(t(ans)))$Re) - > f_values <- unlist((as.data.frame(t(ans)))$f) + > beatAML_incidence_matrix <- plotIncMatrix(x = beatAML_data, + + index_nominal = c(2, 1), index_numeric = 3, print_skim = FALSE, + + plot_weigh .... [TRUNCATED] - > moody(Re = Re_values, f = f_values) + Na/missing values Proportion: 0.2603 - When sourcing ‘hydraulics_vignette.R’: - Error: Theme element `plot.margin` must have class . + When sourcing ‘NIMAA-vignette.R’: + Error: subscript out of bounds Execution halted - ‘hydraulics_vignette.Rmd’ using ‘UTF-8’... failed + ‘NIMAA-vignette.Rmd’ using ‘UTF-8’... failed ``` * checking re-building of vignette outputs ... NOTE ``` Error(s) in re-building vignettes: - --- re-building ‘hydraulics_vignette.Rmd’ using rmarkdown - ``` - -# hyperSpec - -
- -* Version: 0.100.2 -* GitHub: https://github.com/r-hyperspec/hyperSpec -* Source code: https://github.com/cran/hyperSpec -* Date/Publication: 2024-05-01 16:02:11 UTC -* Number of recursive dependencies: 141 - -Run `revdepcheck::cloud_details(, "hyperSpec")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘hyperSpec-Ex.R’ failed - The error most likely occurred in: + ... + --- re-building ‘NIMAA-vignette.Rmd’ using rmarkdown - > ### Name: qplotmixmap - > ### Title: qplotmap with colour mixing for multivariate overlay - > ### Aliases: qplotmixmap - > - > ### ** Examples - > - > chondro <- chondro - spc.fit.poly.below (chondro) - ... - 2. └─hyperSpec::legendright(p, l) - 3. ├─base::print(l, viewport(layout.pos.col = 2), newpage = FALSE) - 4. ├─base::print(l, viewport(layout.pos.col = 2), newpage = FALSE) - 5. └─ggplot2:::print.ggplot(l, viewport(layout.pos.col = 2), newpage = FALSE) - 6. ├─ggplot2::ggplot_gtable(data) - 7. └─ggplot2:::ggplot_gtable.ggplot_built(data) - 8. └─ggplot2::calc_element("plot.margin", theme) - 9. └─cli::cli_abort(...) - 10. └─rlang::abort(...) + Quitting from lines 49-57 [plotIncMatrix function] (NIMAA-vignette.Rmd) + Error: processing vignette 'NIMAA-vignette.Rmd' failed with diagnostics: + subscript out of bounds + --- failed re-building ‘NIMAA-vignette.Rmd’ + + SUMMARY: processing the following file failed: + ‘NIMAA-vignette.Rmd’ + + Error: Vignette re-building failed. Execution halted ``` -# hypsoLoop - -
- -* Version: 0.2.0 -* GitHub: NA -* Source code: https://github.com/cran/hypsoLoop -* Date/Publication: 2022-02-08 09:00:02 UTC -* Number of recursive dependencies: 97 - -Run `revdepcheck::cloud_details(, "hypsoLoop")` for more info - -
+## In both -## Newly broken +* checking installed package size ... NOTE + ``` + installed size is 6.5Mb + sub-directories of 1Mb or more: + data 2.0Mb + doc 4.0Mb + ``` -* checking whether package ‘hypsoLoop’ can be installed ... WARNING +* checking data for non-ASCII characters ... NOTE ``` - Found the following significant warnings: - Warning: replacing previous import ‘ggplot2::set_theme’ by ‘sjPlot::set_theme’ when loading ‘hypsoLoop’ - See ‘/tmp/workdir/hypsoLoop/new/hypsoLoop.Rcheck/00install.out’ for details. + Note: found 24 marked UTF-8 strings ``` -# ICvectorfields +# OBIC
-* Version: 0.1.2 -* GitHub: https://github.com/goodsman/ICvectorfields -* Source code: https://github.com/cran/ICvectorfields -* Date/Publication: 2022-02-26 22:30:02 UTC -* Number of recursive dependencies: 93 +* Version: 3.0.2 +* GitHub: https://github.com/AgroCares/Open-Bodem-Index-Calculator +* Source code: https://github.com/cran/OBIC +* Date/Publication: 2024-03-05 12:40:08 UTC +* Number of recursive dependencies: 75 -Run `revdepcheck::cloud_details(, "ICvectorfields")` for more info +Run `revdepcheck::cloud_details(, "OBIC")` for more info
@@ -10236,331 +9193,273 @@ Run `revdepcheck::cloud_details(, "ICvectorfields")` for more info * checking running R code from vignettes ... ERROR ``` Errors in running code in vignettes: - when running code in ‘Using_ICvectorfields.Rmd’ + when running code in ‘obic_workability.Rmd’ ... + > gg2 <- ggplot(data = dt, aes(x = field, fill = field)) + + + geom_col(aes(y = I_P_WO)) + theme_bw() + theme(axis.text = element_text(size = 10, + .... [TRUNCATED] - > SimVF - Warning: The `scale_name` argument of `continuous_scale()` is deprecated as of ggplot2 - 3.5.0. - Warning: The S3 guide system was deprecated in ggplot2 3.5.0. - ℹ It has been replaced by a ggproto system that can be extended. - - When sourcing ‘Using_ICvectorfields.R’: - Error: argument "theme" is missing, with no default + > (gg | gg2) + plot_layout(guides = "collect") + plot_annotation(caption = "Baseline workability scores.", + + theme = theme(plot.caption = element .... [TRUNCATED] + + When sourcing ‘obic_workability.R’: + Error: object is not a unit Execution halted - ‘Using_ICvectorfields.Rmd’ using ‘UTF-8’... failed + ‘description-of-the-columns.Rmd’ using ‘UTF-8’... OK + ‘obic_introduction.Rmd’ using ‘UTF-8’... OK + ‘obic_score_aggregation.Rmd’ using ‘UTF-8’... OK + ‘obic_water_functions.Rmd’ using ‘UTF-8’... OK + ‘obic_workability.Rmd’ using ‘UTF-8’... failed ``` * checking re-building of vignette outputs ... NOTE ``` Error(s) in re-building vignettes: - --- re-building ‘Using_ICvectorfields.Rmd’ using rmarkdown + --- re-building ‘description-of-the-columns.Rmd’ using rmarkdown + --- finished re-building ‘description-of-the-columns.Rmd’ + + --- re-building ‘obic_introduction.Rmd’ using rmarkdown ``` -# idiogramFISH - -
- -* Version: 2.0.13 -* GitHub: NA -* Source code: https://github.com/cran/idiogramFISH -* Date/Publication: 2023-08-22 16:50:02 UTC -* Number of recursive dependencies: 170 - -Run `revdepcheck::cloud_details(, "idiogramFISH")` for more info - -
- -## Newly broken +## In both * checking installed package size ... NOTE ``` - installed size is 5.1Mb + installed size is 6.0Mb sub-directories of 1Mb or more: - R 1.5Mb - doc 2.0Mb - ``` - -## In both - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘index.Rmd’ - ... - > if (requireNamespace("RCurl", quietly = TRUE)) { - + v <- sub("Version: ", "", readLines("../DESCRIPTION")[3]) - + pkg <- "idiogramFISH" - + l .... [TRUNCATED] - Warning in file(con, "r") : - cannot open file '../DESCRIPTION': No such file or directory - - When sourcing ‘index.R’: - Error: cannot open the connection - Execution halted - - ‘AVignette.Rmd’ using ‘UTF-8’... OK - ‘index.Rmd’ using ‘UTF-8’... failed + data 4.0Mb + doc 1.4Mb ``` -# idopNetwork +# OmicNavigator
-* Version: 0.1.2 -* GitHub: https://github.com/cxzdsa2332/idopNetwork -* Source code: https://github.com/cran/idopNetwork -* Date/Publication: 2023-04-18 06:50:02 UTC -* Number of recursive dependencies: 77 +* Version: 1.13.13 +* GitHub: https://github.com/abbvie-external/OmicNavigator +* Source code: https://github.com/cran/OmicNavigator +* Date/Publication: 2023-08-25 20:40:02 UTC +* Number of recursive dependencies: 86 -Run `revdepcheck::cloud_details(, "idopNetwork")` for more info +Run `revdepcheck::cloud_details(, "OmicNavigator")` for more info
## Newly broken -* checking running R code from vignettes ... ERROR +* checking tests ... ERROR ``` - Errors in running code in vignettes: - when running code in ‘idopNetwork_vignette.Rmd’ - ... - - > df = data_cleaning(gut_microbe) - - > result1 = test_result$d1_power_fitting - - > power_equation_plot(result1) - - When sourcing ‘idopNetwork_vignette.R’: - Error: Theme element `plot.margin` must have class . - Execution halted - - ‘idopNetwork_vignette.Rmd’ using ‘UTF-8’... failed + Running ‘tinytest.R’ + Running the tests in ‘tests/tinytest.R’ failed. + Complete output: + > # Test files in inst/tinytest/ + > if (requireNamespace("tinytest", quietly = TRUE)) { + + suppressMessages(tinytest::test_package("OmicNavigator")) + + } + + testAdd.R..................... 0 tests + testAdd.R..................... 0 tests + ... + testPlot.R.................... 140 tests OK + testPlot.R.................... 140 tests OK + testPlot.R.................... 141 tests OK + testPlot.R.................... 141 tests OK + testPlot.R.................... 141 tests OK + testPlot.R.................... 142 tests OK + testPlot.R.................... 142 tests OK + testPlot.R.................... 143 tests OK Error in pm[[2]] : subscript out of bounds + Calls: suppressMessages ... plotStudy -> f -> -> ggplotly.ggplot -> gg2list + Execution halted ``` +## In both + * checking re-building of vignette outputs ... NOTE ``` Error(s) in re-building vignettes: - ... - --- re-building ‘idopNetwork_vignette.Rmd’ using rmarkdown - - Quitting from lines 86-87 [unnamed-chunk-9] (idopNetwork_vignette.Rmd) - Error: processing vignette 'idopNetwork_vignette.Rmd' failed with diagnostics: - Theme element `plot.margin` must have class . - --- failed re-building ‘idopNetwork_vignette.Rmd’ + --- re-building ‘OmicNavigatorAPI.Rnw’ using Sweave + OmicNavigator R package version: 1.13.13 + The app is not installed. Install it with installApp() + Installing study "ABC" in /tmp/Rtmpd2oXDy/file1d222df82584 + Exporting study "ABC" as an R package + Note: No maintainer email was specified. Using the placeholder: Unknown + Calculating pairwise overlaps. This may take a while... + Exported study to /tmp/Rtmpd2oXDy/ONstudyABC + Success! + ... + l.14 ^^M + + ! ==> Fatal error occurred, no output PDF file produced! + --- failed re-building ‘OmicNavigatorUsersGuide.Rnw’ - SUMMARY: processing the following file failed: - ‘idopNetwork_vignette.Rmd’ + SUMMARY: processing the following files failed: + ‘OmicNavigatorAPI.Rnw’ ‘OmicNavigatorUsersGuide.Rnw’ Error: Vignette re-building failed. Execution halted ``` -# iglu +# oncomsm
-* Version: 4.0.0 -* GitHub: https://github.com/irinagain/iglu -* Source code: https://github.com/cran/iglu -* Date/Publication: 2024-02-23 17:50:02 UTC -* Number of recursive dependencies: 124 +* Version: 0.1.4 +* GitHub: https://github.com/Boehringer-Ingelheim/oncomsm +* Source code: https://github.com/cran/oncomsm +* Date/Publication: 2023-04-17 07:00:02 UTC +* Number of recursive dependencies: 126 -Run `revdepcheck::cloud_details(, "iglu")` for more info +Run `revdepcheck::cloud_details(, "oncomsm")` for more info
## Newly broken -* checking examples ... ERROR +* checking tests ... ERROR ``` - Running examples in ‘iglu-Ex.R’ failed - The error most likely occurred in: - - > ### Name: agp - > ### Title: Display Ambulatory Glucose Profile (AGP) statistics for selected - > ### subject - > ### Aliases: agp - > - > ### ** Examples - > + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(dplyr) + + Attaching package: 'dplyr' + + The following objects are masked from 'package:stats': + + filter, lag ... - 4. └─base::lapply(x$plots, plot_table, guides = guides) - 5. ├─patchwork (local) FUN(X[[i]], ...) - 6. └─patchwork:::plot_table.ggplot(X[[i]], ...) - 7. └─ggplot2::ggplotGrob(x) - 8. ├─ggplot2::ggplot_gtable(ggplot_build(x)) - 9. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) - 10. └─ggplot2::calc_element("plot.margin", theme) - 11. └─cli::cli_abort(...) - 12. └─rlang::abort(...) - Execution halted + 10. └─grid::unit.c(legend.box.margin[4], widths, legend.box.margin[2]) + 11. └─grid:::identicalUnits(x) + + [ FAIL 1 | WARN 0 | SKIP 2 | PASS 59 ] + Deleting unused snapshots: + • plots/plot-mstate-srp-model-2.svg + • plots/plot-mstate-srp-model-3.svg + • plots/plot-srp-model-2.svg + Error: Test failures + Execution halted ``` * checking running R code from vignettes ... ERROR ``` Errors in running code in vignettes: - when running code in ‘AGP_and_Episodes.Rmd’ + when running code in ‘avoiding-bias.Rmd’ ... - > knitr::opts_chunk$set(collapse = TRUE, comment = "#>") - - > library(iglu) - - > agp(example_data_1_subject) - - When sourcing ‘AGP_and_Episodes.R’: - Error: Theme element `plot.margin` must have class . - Execution halted - - ‘AGP_and_Episodes.Rmd’ using ‘UTF-8’... failed - ‘MAGE.Rmd’ using ‘UTF-8’... OK - ‘iglu.Rmd’ using ‘UTF-8’... OK - ‘lasagna_plots.Rmd’ using ‘UTF-8’... OK - ‘metrics_list.Rmd’ using ‘UTF-8’... OK - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘AGP_and_Episodes.Rmd’ using rmarkdown + > mdl <- create_srpmodel(A = define_srp_prior(median_t_q05 = c(1, + + 4, 12), median_t_q95 = c(6, 8, 36), shape_q05 = c(0.99, 0.99, + + 0.99), s .... [TRUNCATED] - Quitting from lines 24-25 [unnamed-chunk-1] (AGP_and_Episodes.Rmd) - Error: processing vignette 'AGP_and_Episodes.Rmd' failed with diagnostics: - Theme element `plot.margin` must have class . - --- failed re-building ‘AGP_and_Episodes.Rmd’ + > plot(mdl, confidence = 0.9) - --- re-building ‘MAGE.Rmd’ using rmarkdown - ``` - -# igoR - -
- -* Version: 0.2.0 -* GitHub: https://github.com/dieghernan/igoR -* Source code: https://github.com/cran/igoR -* Date/Publication: 2024-02-05 15:30:02 UTC -* Number of recursive dependencies: 67 - -Run `revdepcheck::cloud_details(, "igoR")` for more info - -
- -## Newly broken - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘igoR.Rmd’ - ... - + mutate(variable = factor(variable, levels = c("Total IGOs", - + "Numb ..." ... [TRUNCATED] + ... - > ggplot(all_by_year, aes(x = year, y = value)) + geom_line(color = "black", - + aes(linetype = variable)) + scale_x_continuous(limits = c(1800, - + .... [TRUNCATED] + > plot(mdl, parameter_sample = smpl_prior, confidence = 0.75) - When sourcing ‘igoR.R’: - Error: Theme element `plot.margin` must have class . + When sourcing ‘oncomsm.R’: + Error: object is not a unit Execution halted - ‘igoR.Rmd’ using ‘UTF-8’... failed - ‘mapping.Rmd’ using ‘UTF-8’... OK + ‘avoiding-bias.Rmd’ using ‘UTF-8’... failed + ‘oncomsm.Rmd’ using ‘UTF-8’... failed + ‘prior-choice.Rmd’ using ‘UTF-8’... OK ``` * checking re-building of vignette outputs ... NOTE ``` Error(s) in re-building vignettes: - ... - --- re-building ‘igoR.Rmd’ using rmarkdown + --- re-building ‘avoiding-bias.Rmd’ using rmarkdown - Quitting from lines 123-150 [Fig1] (igoR.Rmd) - Error: processing vignette 'igoR.Rmd' failed with diagnostics: - Theme element `plot.margin` must have class . - --- failed re-building ‘igoR.Rmd’ + Quitting from lines 35-46 [unnamed-chunk-2] (avoiding-bias.Rmd) + Error: processing vignette 'avoiding-bias.Rmd' failed with diagnostics: + object is not a unit + --- failed re-building ‘avoiding-bias.Rmd’ - --- re-building ‘mapping.Rmd’ using rmarkdown - --- finished re-building ‘mapping.Rmd’ + --- re-building ‘oncomsm.Rmd’ using rmarkdown - SUMMARY: processing the following file failed: - ‘igoR.Rmd’ + Quitting from lines 211-215 [plotting-the-prior] (oncomsm.Rmd) + Error: processing vignette 'oncomsm.Rmd' failed with diagnostics: + object is not a unit + --- failed re-building ‘oncomsm.Rmd’ - Error: Vignette re-building failed. - Execution halted + --- re-building ‘prior-choice.Rmd’ using rmarkdown ``` ## In both -* checking data for non-ASCII characters ... NOTE +* checking installed package size ... NOTE ``` - Note: found 160 marked UTF-8 strings + installed size is 59.1Mb + sub-directories of 1Mb or more: + doc 1.1Mb + libs 56.9Mb + ``` + +* checking for GNU extensions in Makefiles ... NOTE + ``` + GNU make is a SystemRequirements. ``` -# immunarch +# pafr
-* Version: 0.9.1 -* GitHub: https://github.com/immunomind/immunarch -* Source code: https://github.com/cran/immunarch -* Date/Publication: 2024-03-18 19:10:06 UTC -* Number of recursive dependencies: 194 +* Version: 0.0.2 +* GitHub: https://github.com/dwinter/pafr +* Source code: https://github.com/cran/pafr +* Date/Publication: 2020-12-08 10:20:12 UTC +* Number of recursive dependencies: 110 -Run `revdepcheck::cloud_details(, "immunarch")` for more info +Run `revdepcheck::cloud_details(, "pafr")` for more info
## Newly broken -* checking examples ... ERROR +* checking tests ... ERROR ``` - Running examples in ‘immunarch-Ex.R’ failed - The error most likely occurred in: - - > ### Name: pubRepStatistics - > ### Title: Statistics of number of public clonotypes for each possible - > ### combinations of repertoires - > ### Aliases: pubRepStatistics - > - > ### ** Examples - > + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(pafr) + Loading required package: ggplot2 + > + > test_check("pafr") + [ FAIL 6 | WARN 2 | SKIP 0 | PASS 70 ] + ... - 5. ├─base::suppressMessages(...) - 6. │ └─base::withCallingHandlers(...) - 7. └─UpSetR:::Make_main_bar(...) - 8. └─ggplot2::ggplotGrob(Main_bar_plot) - 9. ├─ggplot2::ggplot_gtable(ggplot_build(x)) - 10. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) - 11. └─ggplot2::calc_element("plot.margin", theme) - 12. └─cli::cli_abort(...) - 13. └─rlang::abort(...) - Execution halted + ── Failure ('test_plot.r:11:5'): dotplot works produces a plot ───────────────── + unname(labs["xintercept"]) not equal to "xintercept". + target is NULL, current is character + ── Failure ('test_plot.r:12:5'): dotplot works produces a plot ───────────────── + unname(labs["yintercept"]) not equal to "yintercept". + target is NULL, current is character + + [ FAIL 6 | WARN 2 | SKIP 0 | PASS 70 ] + Error: Test failures + Execution halted ``` ## In both -* checking installed package size ... NOTE +* checking LazyData ... NOTE ``` - installed size is 10.5Mb - sub-directories of 1Mb or more: - R 1.5Mb - data 5.5Mb - doc 1.6Mb + 'LazyData' is specified without a 'data' directory ``` -# immuneSIM +# patchwork
-* Version: 0.8.7 -* GitHub: https://github.com/GreiffLab/immuneSIM -* Source code: https://github.com/cran/immuneSIM -* Date/Publication: 2019-09-27 10:30:06 UTC -* Number of recursive dependencies: 66 +* Version: 1.2.0 +* GitHub: https://github.com/thomasp85/patchwork +* Source code: https://github.com/cran/patchwork +* Date/Publication: 2024-01-08 14:40:02 UTC +* Number of recursive dependencies: 80 -Run `revdepcheck::cloud_details(, "immuneSIM")` for more info +Run `revdepcheck::cloud_details(, "patchwork")` for more info
@@ -10568,54 +9467,81 @@ Run `revdepcheck::cloud_details(, "immuneSIM")` for more info * checking examples ... ERROR ``` - Running examples in ‘immuneSIM-Ex.R’ failed + Running examples in ‘patchwork-Ex.R’ failed The error most likely occurred in: - > ### Name: plot_repertoire_A_vs_B - > ### Title: Comparative plots of main repertoire features of two input - > ### repertoires (length distribution, amino acid frequency, VDJ usage, - > ### kmer occurrence) - > ### Aliases: plot_repertoire_A_vs_B + > ### Name: free + > ### Title: Free a plot from alignment + > ### Aliases: free > > ### ** Examples - ... - ▆ - 1. └─immuneSIM::plot_repertoire_A_vs_B(...) - 2. ├─base::print(plots_aa_freq_list_imgt[[1]], vp = vplayout(1, 1)) - 3. └─ggplot2:::print.ggplot(...) - 4. ├─ggplot2::ggplot_gtable(data) - 5. └─ggplot2:::ggplot_gtable.ggplot_built(data) - 6. └─ggplot2::calc_element("plot.margin", theme) - 7. └─cli::cli_abort(...) - 8. └─rlang::abort(...) + > + > # Sometimes you have a plot that defies good composition alginment, e.g. due + ... + > p1 / p2 + > + > # We can fix this be using free + > free(p1) / p2 + > + > # We can still collect guides like before + > free(p1) / p2 + plot_layout(guides = "collect") + Error in identicalUnits(x) : object is not a unit + Calls: ... assemble_guides -> guides_build -> unit.c -> identicalUnits Execution halted ``` -## In both +# pathviewr -* checking installed package size ... NOTE - ``` - installed size is 8.2Mb - sub-directories of 1Mb or more: - R 8.1Mb - ``` +
-* checking LazyData ... NOTE +* Version: 1.1.7 +* GitHub: https://github.com/ropensci/pathviewr +* Source code: https://github.com/cran/pathviewr +* Date/Publication: 2023-03-08 08:10:05 UTC +* Number of recursive dependencies: 184 + +Run `revdepcheck::cloud_details(, "pathviewr")` for more info + +
+ +## Newly broken + +* checking tests ... ERROR ``` - 'LazyData' is specified without a 'data' directory + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(pathviewr) + > #library(vdiffr) + > + > test_check("pathviewr") + [ FAIL 2 | WARN 1 | SKIP 0 | PASS 286 ] + + ... + ── Error ('test-plot_by_subject.R:168:3'): elev views wrangled correctly via tidyverse ── + Error in `expect_match(elev_all_plots[[3]][[4]][["labels"]][["x"]], "position_height")`: is.character(act$val) is not TRUE + Backtrace: + ▆ + 1. └─testthat::expect_match(...) at test-plot_by_subject.R:168:3 + 2. └─base::stopifnot(is.character(act$val)) + + [ FAIL 2 | WARN 1 | SKIP 0 | PASS 286 ] + Error: Test failures + Execution halted ``` -# iNEXT.4steps +# pcutils
-* Version: 1.0.0 -* GitHub: https://github.com/KaiHsiangHu/iNEXT.4steps -* Source code: https://github.com/cran/iNEXT.4steps -* Date/Publication: 2024-04-10 20:00:05 UTC -* Number of recursive dependencies: 106 +* Version: 0.2.6 +* GitHub: https://github.com/Asa12138/pcutils +* Source code: https://github.com/cran/pcutils +* Date/Publication: 2024-06-25 21:20:05 UTC +* Number of recursive dependencies: 281 -Run `revdepcheck::cloud_details(, "iNEXT.4steps")` for more info +Run `revdepcheck::cloud_details(, "pcutils")` for more info
@@ -10623,102 +9549,170 @@ Run `revdepcheck::cloud_details(, "iNEXT.4steps")` for more info * checking examples ... ERROR ``` - Running examples in ‘iNEXT.4steps-Ex.R’ failed + Running examples in ‘pcutils-Ex.R’ failed The error most likely occurred in: - > ### Name: ggCompleteness - > ### Title: ggplot for depicting sample completeness profiles - > ### Aliases: ggCompleteness + > ### Name: multireg + > ### Title: Multiple regression/ variance decomposition analysis + > ### Aliases: multireg > > ### ** Examples > - > + > if (requireNamespace("relaimpo") && requireNamespace("aplot")) { ... - Backtrace: - ▆ - 1. ├─base (local) ``(x) - 2. └─ggplot2:::print.ggplot(x) - 3. ├─ggplot2::ggplot_gtable(data) - 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) - 5. └─ggplot2::calc_element("plot.margin", theme) - 6. └─cli::cli_abort(...) - 7. └─rlang::abort(...) + + } + Loading required namespace: relaimpo + Loading required namespace: aplot + [1] "NS" + [1] "WS" + [1] "CS" + Selecting by value + Error in as.unit(value) : object is not coercible to a unit + Calls: ... assemble_guides -> guides_build -> [<- -> [<-.unit -> as.unit + Execution halted + ``` + +# pdxTrees + +
+ +* Version: 0.4.0 +* GitHub: https://github.com/mcconvil/pdxTrees +* Source code: https://github.com/cran/pdxTrees +* Date/Publication: 2020-08-17 14:00:02 UTC +* Number of recursive dependencies: 105 + +Run `revdepcheck::cloud_details(, "pdxTrees")` for more info + +
+ +## Newly broken + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘pdxTrees-vignette.Rmd’ + ... + + y = Pollution_Removal_value, color = Mature_Size)) + geom_point(size = 2, + + .... [TRUNCATED] + + > berkeley_graph + transition_states(states = Mature_Size, + + transition_length = 10, state_length = 8) + enter_grow() + + + exit_shrink() + + When sourcing ‘pdxTrees-vignette.R’: + Error: argument "theme" is missing, with no default Execution halted + + ‘pdxTrees-vignette.Rmd’ using ‘UTF-8’... failed + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘pdxTrees-vignette.Rmd’ using rmarkdown + ``` + +## In both + +* checking LazyData ... NOTE ``` + 'LazyData' is specified without a 'data' directory + ``` + +# personalized + +
+ +* Version: 0.2.7 +* GitHub: https://github.com/jaredhuling/personalized +* Source code: https://github.com/cran/personalized +* Date/Publication: 2022-06-27 20:20:03 UTC +* Number of recursive dependencies: 94 + +Run `revdepcheck::cloud_details(, "personalized")` for more info + +
+ +## Newly broken * checking tests ... ERROR ``` Running ‘testthat.R’ Running the tests in ‘tests/testthat.R’ failed. Complete output: + > Sys.setenv("R_TESTS" = "") > library(testthat) - > library(iNEXT.4steps) - > - > test_check("iNEXT.4steps") - [ FAIL 2 | WARN 5 | SKIP 0 | PASS 10 ] - - ══ Failed tests ════════════════════════════════════════════════════════════════ + > library(personalized) + Loading required package: glmnet + Loading required package: Matrix + Loaded glmnet 4.1-8 + Loading required package: mgcv ... - 3. └─ggpubr:::.get_legend(p, position = position) - 4. ├─ggplot2::ggplot_gtable(ggplot_build(p)) - 5. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(p)) - 6. └─ggplot2::calc_element("plot.margin", theme) - 7. └─cli::cli_abort(...) - 8. └─rlang::abort(...) + 4. └─personalized:::plot.subgroup_validated(subgrp.val, type = "stability") + 5. ├─plotly::subplot(...) + 6. │ └─plotly:::dots2plots(...) + 7. ├─plotly::ggplotly(p.primary, tooltip = paste0("tooltip", 1:4)) + 8. └─plotly:::ggplotly.ggplot(...) + 9. └─plotly::gg2list(...) - [ FAIL 2 | WARN 5 | SKIP 0 | PASS 10 ] + [ FAIL 1 | WARN 2 | SKIP 0 | PASS 215 ] Error: Test failures Execution halted ``` +# phylepic + +
+ +* Version: 0.2.0 +* GitHub: https://github.com/cidm-ph/phylepic +* Source code: https://github.com/cran/phylepic +* Date/Publication: 2024-05-31 19:10:02 UTC +* Number of recursive dependencies: 89 + +Run `revdepcheck::cloud_details(, "phylepic")` for more info + +
+ +## Newly broken + * checking running R code from vignettes ... ERROR ``` Errors in running code in vignettes: - when running code in ‘Vignette-iNEXT.4steps-April10.Rmd’ + when running code in ‘phylepic.Rmd’ ... + > clade <- ape::extract.clade(tree, clade.parent) - > data(Data_spider) + > plot(clade) - > Four_Steps_out1 <- iNEXT4steps(data = Data_spider, - + datatype = "abundance") + > plot(phylepic(clade, metadata, name, collection_date)) - When sourcing ‘Vignette-iNEXT.4steps-April10.R’: - Error: Theme element `plot.margin` must have class . + When sourcing ‘phylepic.R’: + Error: attempt to set an attribute on NULL Execution halted - ‘Vignette-iNEXT.4steps-April10.Rmd’ using ‘UTF-8’... failed + ‘phylepic.Rmd’ using ‘UTF-8’... failed ``` * checking re-building of vignette outputs ... NOTE ``` Error(s) in re-building vignettes: - ... - --- re-building ‘Vignette-iNEXT.4steps-April10.Rmd’ using rmarkdown - - Quitting from lines 209-213 [unnamed-chunk-8] (Vignette-iNEXT.4steps-April10.Rmd) - Error: processing vignette 'Vignette-iNEXT.4steps-April10.Rmd' failed with diagnostics: - Theme element `plot.margin` must have class . - --- failed re-building ‘Vignette-iNEXT.4steps-April10.Rmd’ - - SUMMARY: processing the following file failed: - ‘Vignette-iNEXT.4steps-April10.Rmd’ - - Error: Vignette re-building failed. - Execution halted + --- re-building ‘phylepic.Rmd’ using rmarkdown ``` -# iNEXT.beta3D +# Plasmidprofiler
-* Version: 1.0.2 -* GitHub: https://github.com/AnneChao/iNEXT.beta3D -* Source code: https://github.com/cran/iNEXT.beta3D -* Date/Publication: 2024-04-17 19:40:11 UTC -* Number of recursive dependencies: 88 +* Version: 0.1.6 +* GitHub: NA +* Source code: https://github.com/cran/Plasmidprofiler +* Date/Publication: 2017-01-06 01:10:47 +* Number of recursive dependencies: 90 -Run `revdepcheck::cloud_details(, "iNEXT.beta3D")` for more info +Run `revdepcheck::cloud_details(, "Plasmidprofiler")` for more info
@@ -10726,108 +9720,81 @@ Run `revdepcheck::cloud_details(, "iNEXT.beta3D")` for more info * checking examples ... ERROR ``` - Running examples in ‘iNEXT.beta3D-Ex.R’ failed + Running examples in ‘Plasmidprofiler-Ex.R’ failed The error most likely occurred in: - > ### Name: ggiNEXTbeta3D - > ### Title: ggplot2 extension for the iNEXTbeta3D object - > ### Aliases: ggiNEXTbeta3D + > ### Name: main + > ### Title: Main: Run everything + > ### Aliases: main > > ### ** Examples > - > - ... - Backtrace: - ▆ - 1. ├─base (local) ``(x) - 2. └─ggplot2:::print.ggplot(x) - 3. ├─ggplot2::ggplot_gtable(data) - 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) - 5. └─ggplot2::calc_element("plot.margin", theme) - 6. └─cli::cli_abort(...) - 7. └─rlang::abort(...) - Execution halted - ``` - -## In both - -* checking re-building of vignette outputs ... WARNING - ``` - Error(s) in re-building vignettes: - ... - --- re-building ‘Introduction.Rnw’ using Sweave - Error: processing vignette 'Introduction.Rnw' failed with diagnostics: - Running 'texi2dvi' on 'Introduction.tex' failed. - LaTeX errors: - ! LaTeX Error: File `pdfpages.sty' not found. - - Type X to quit or to proceed, - or enter new name. (Default extension: sty) + > main(blastdata, ... - l.4 ^^M - - ! ==> Fatal error occurred, no output PDF file produced! - --- failed re-building ‘Introduction.Rnw’ - - SUMMARY: processing the following file failed: - ‘Introduction.Rnw’ - - Error: Vignette re-building failed. + Saving 12 x 7 in image + Warning: Vectorized input to `element_text()` is not officially supported. + ℹ Results may be unexpected or may change in future versions of ggplot2. + Warning in geom_tile(aes(x = Plasmid, y = Sample, label = AMR_gene, fill = Inc_group, : + Ignoring unknown aesthetics: label and text + Warning: Use of `report$Sureness` is discouraged. + ℹ Use `Sureness` instead. + Error in pm[[2]] : subscript out of bounds + Calls: main ... -> ggplotly -> ggplotly.ggplot -> gg2list Execution halted ``` -# insurancerating +# platetools
-* Version: 0.7.4 -* GitHub: https://github.com/mharinga/insurancerating -* Source code: https://github.com/cran/insurancerating -* Date/Publication: 2024-05-20 11:30:03 UTC -* Number of recursive dependencies: 133 +* Version: 0.1.7 +* GitHub: https://github.com/swarchal/platetools +* Source code: https://github.com/cran/platetools +* Date/Publication: 2024-03-07 16:50:02 UTC +* Number of recursive dependencies: 48 -Run `revdepcheck::cloud_details(, "insurancerating")` for more info +Run `revdepcheck::cloud_details(, "platetools")` for more info
## Newly broken -* checking examples ... ERROR +* checking tests ... ERROR ``` - Running examples in ‘insurancerating-Ex.R’ failed - The error most likely occurred in: - - > ### Name: autoplot.univariate - > ### Title: Automatically create a ggplot for objects obtained from - > ### univariate() - > ### Aliases: autoplot.univariate - > - > ### ** Examples - > + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(platetools) + > + > test_check("platetools") + [ FAIL 2 | WARN 1 | SKIP 4 | PASS 187 ] + + ══ Skipped tests (4) ═══════════════════════════════════════════════════════════ ... - > xzip <- univariate(MTPL, x = bm, severity = amount, nclaims = nclaims, - + exposure = exposure, by = zip) - > autoplot(xzip, show_plots = 1:2) - Warning: Removed 16 rows containing missing values or values outside the scale range - (`geom_point()`). - Warning: Removed 5 rows containing missing values or values outside the scale range - (`geom_line()`). - Error in identicalUnits(x) : object is not a unit - Calls: ... assemble_guides -> guides_build -> unit.c -> identicalUnits - Execution halted + length(out96) not equal to length(ggplot()). + 1/1 mismatches + [1] 11 - 10 == 1 + ── Failure ('test-plot_wrapper.R:34:5'): returns expected ggplot object ──────── + names(out96) not equal to names(ggplot()). + Lengths differ: 11 is not 10 + + [ FAIL 2 | WARN 1 | SKIP 4 | PASS 187 ] + Error: Test failures + Execution halted ``` -# inTextSummaryTable +# plotDK
-* Version: 3.3.2 -* GitHub: https://github.com/openanalytics/inTextSummaryTable -* Source code: https://github.com/cran/inTextSummaryTable -* Date/Publication: 2024-03-09 16:20:02 UTC -* Number of recursive dependencies: 120 +* Version: 0.1.0 +* GitHub: NA +* Source code: https://github.com/cran/plotDK +* Date/Publication: 2021-10-01 08:00:02 UTC +* Number of recursive dependencies: 86 -Run `revdepcheck::cloud_details(, "inTextSummaryTable")` for more info +Run `revdepcheck::cloud_details(, "plotDK")` for more info
@@ -10839,155 +9806,49 @@ Run `revdepcheck::cloud_details(, "inTextSummaryTable")` for more info Running the tests in ‘tests/testthat.R’ failed. Complete output: > library(testthat) - > library(inTextSummaryTable) + > library(plotDK) > - > test_check("inTextSummaryTable") - [ FAIL 59 | WARN 1 | SKIP 0 | PASS 881 ] + > test_check("plotDK") + [ FAIL 2 | WARN 0 | SKIP 0 | PASS 46 ] ══ Failed tests ════════════════════════════════════════════════════════════════ ... - 5. │ └─rlang::eval_bare(quo_get_expr(.quo), quo_get_env(.quo)) - 6. └─inTextSummaryTable::subjectProfileSummaryPlot(...) - 7. ├─base::do.call(plyr::rbind.fill, ggplot_build(gg)$data) - 8. └─plyr (local) ``(``, ``) - 9. └─plyr:::output_template(dfs, nrows) - 10. └─plyr:::allocate_column(df[[var]], nrows, dfs, var) + Error in `expect_setequal(c("x", "y", "group", "subgroup", "text", "fill"), + names(labels))`: `object` and `expected` must both be vectors + Backtrace: + ▆ + 1. └─testthat::expect_setequal(c("x", "y", "group", "subgroup", "text", "fill"), names(labels)) at test-plotDK.R:67:5 + 2. └─rlang::abort("`object` and `expected` must both be vectors") - [ FAIL 59 | WARN 1 | SKIP 0 | PASS 881 ] + [ FAIL 2 | WARN 0 | SKIP 0 | PASS 46 ] Error: Test failures Execution halted ``` -* checking re-building of vignette outputs ... NOTE +## In both + +* checking dependencies in R code ... NOTE ``` - Error(s) in re-building vignettes: - --- re-building ‘inTextSummaryTable-advanced.Rmd’ using rmarkdown - --- finished re-building ‘inTextSummaryTable-advanced.Rmd’ - - --- re-building ‘inTextSummaryTable-aesthetics.Rmd’ using rmarkdown - - Quitting from lines 211-224 [aesthetics-defaultsVisualization] (inTextSummaryTable-aesthetics.Rmd) - Error: processing vignette 'inTextSummaryTable-aesthetics.Rmd' failed with diagnostics: - Problem while setting up geom aesthetics. - ℹ Error occurred in the 2nd layer. - ... - ! Aesthetics must be either length 1 or the same as the data (28). - ✖ Fix the following mappings: `size`. - --- failed re-building ‘inTextSummaryTable-visualization.Rmd’ - - SUMMARY: processing the following files failed: - ‘inTextSummaryTable-aesthetics.Rmd’ - ‘inTextSummaryTable-visualization.Rmd’ - - Error: Vignette re-building failed. - Execution halted - ``` - -## In both - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘inTextSummaryTable-aesthetics.Rmd’ - ... - > subjectProfileSummaryPlot(data = summaryTable, xVar = "visit", - + colorVar = "TRT") - - When sourcing ‘inTextSummaryTable-aesthetics.R’: - Error: Problem while setting up geom aesthetics. - ℹ Error occurred in the 2nd layer. - Caused by error in `check_aesthetics()`: - ... - ✖ Fix the following mappings: `size`. - Execution halted - - ‘inTextSummaryTable-advanced.Rmd’ using ‘UTF-8’... OK - ‘inTextSummaryTable-aesthetics.Rmd’ using ‘UTF-8’... failed - ‘inTextSummaryTable-createTables.Rmd’ using ‘UTF-8’... OK - ‘inTextSummaryTable-exportTables.Rmd’ using ‘UTF-8’... OK - ‘inTextSummaryTable-introduction.Rmd’ using ‘UTF-8’... OK - ‘inTextSummaryTable-standardTables.Rmd’ using ‘UTF-8’... OK - ‘inTextSummaryTable-visualization.Rmd’ using ‘UTF-8’... failed - ``` - -* checking installed package size ... NOTE - ``` - installed size is 10.5Mb - sub-directories of 1Mb or more: - doc 9.9Mb + Namespace in Imports field not imported from: ‘mapproj’ + All declared Imports should be used. ``` -# inventorize - -
- -* Version: 1.1.1 -* GitHub: NA -* Source code: https://github.com/cran/inventorize -* Date/Publication: 2022-05-31 22:20:09 UTC -* Number of recursive dependencies: 71 - -Run `revdepcheck::cloud_details(, "inventorize")` for more info - -
- -## Newly broken - -* checking whether package ‘inventorize’ can be installed ... ERROR +* checking data for non-ASCII characters ... NOTE ``` - Installation failed. - See ‘/tmp/workdir/inventorize/new/inventorize.Rcheck/00install.out’ for details. + Note: found 12992 marked UTF-8 strings ``` -## Installation - -### Devel - -``` -* installing *source* package ‘inventorize’ ... -** package ‘inventorize’ successfully unpacked and MD5 sums checked -** using staged installation -** R -** byte-compile and prepare package for lazy loading -Error in pm[[2]] : subscript out of bounds -Error: unable to load R code in package ‘inventorize’ -Execution halted -ERROR: lazy loading failed for package ‘inventorize’ -* removing ‘/tmp/workdir/inventorize/new/inventorize.Rcheck/inventorize’ - - -``` -### CRAN - -``` -* installing *source* package ‘inventorize’ ... -** package ‘inventorize’ successfully unpacked and MD5 sums checked -** using staged installation -** R -** byte-compile and prepare package for lazy loading -Warning in qgamma(service_level, alpha, beta) : NaNs produced -Warning in qgamma(service_level, alpha, beta) : NaNs produced -** help -*** installing help indices -** building package indices -** testing if installed package can be loaded from temporary location -** testing if installed package can be loaded from final location -** testing if installed package keeps a record of temporary installation path -* DONE (inventorize) - - -``` -# jskm +# plotly
-* Version: 0.5.3 -* GitHub: https://github.com/jinseob2kim/jstable -* Source code: https://github.com/cran/jskm -* Date/Publication: 2024-01-26 06:20:08 UTC -* Number of recursive dependencies: 103 +* Version: 4.10.4 +* GitHub: https://github.com/plotly/plotly.R +* Source code: https://github.com/cran/plotly +* Date/Publication: 2024-01-13 22:40:02 UTC +* Number of recursive dependencies: 147 -Run `revdepcheck::cloud_details(, "jskm")` for more info +Run `revdepcheck::cloud_details(, "plotly")` for more info
@@ -10995,26 +9856,26 @@ Run `revdepcheck::cloud_details(, "jskm")` for more info * checking examples ... ERROR ``` - Running examples in ‘jskm-Ex.R’ failed + Running examples in ‘plotly-Ex.R’ failed The error most likely occurred in: - > ### Name: jskm - > ### Title: Creates a Kaplan-Meier plot for survfit object. - > ### Aliases: jskm + > ### Name: style + > ### Title: Modify trace(s) + > ### Aliases: style > > ### ** Examples > - > library(survival) + > ## Don't show: ... - Backtrace: - ▆ - 1. ├─base (local) ``(x) - 2. └─ggplot2:::print.ggplot(x) - 3. ├─ggplot2::ggplot_gtable(data) - 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) - 5. └─ggplot2::calc_element("plot.margin", theme) - 6. └─cli::cli_abort(...) - 7. └─rlang::abort(...) + + # this clobbers the previously supplied marker.line.color + + style(p, marker.line = list(width = 2.5), marker.size = 10) + + ## Don't show: + + }) # examplesIf + > (p <- ggplotly(qplot(data = mtcars, wt, mpg, geom = c("point", "smooth")))) + Warning: `qplot()` was deprecated in ggplot2 3.4.0. + `geom_smooth()` using method = 'loess' and formula = 'y ~ x' + Error in pm[[2]] : subscript out of bounds + Calls: ... eval -> eval -> ggplotly -> ggplotly.ggplot -> gg2list Execution halted ``` @@ -11023,6980 +9884,394 @@ Run `revdepcheck::cloud_details(, "jskm")` for more info Running ‘testthat.R’ Running the tests in ‘tests/testthat.R’ failed. Complete output: - > library(testthat) - > library(jskm) - > - > test_check("jskm") - [ FAIL 2 | WARN 1 | SKIP 0 | PASS 2 ] + > library("testthat") + > library("plotly") + Loading required package: ggplot2 - ══ Failed tests ════════════════════════════════════════════════════════════════ - ... - label_size = .lab$size, label_fontfamily = .lab$family, label_fontface = .lab$face, - label_colour = .lab$color, label_x = .lab$label.x, label_y = .lab$label.y, - hjust = .lab$hjust, vjust = .lab$vjust, align = align, rel_widths = widths, - rel_heights = heights, legend = legend, common.legend.grob = legend.grob)`: ℹ In index: 1. - Caused by error in `ggplot_gtable()`: - ! Theme element `plot.margin` must have class . + Attaching package: 'plotly' - [ FAIL 2 | WARN 1 | SKIP 0 | PASS 2 ] + The following object is masked from 'package:ggplot2': + ... + • plotly-subplot/subplot-bump-axis-annotation.svg + • plotly-subplot/subplot-bump-axis-image.svg + • plotly-subplot/subplot-bump-axis-shape-shared.svg + • plotly-subplot/subplot-bump-axis-shape.svg + • plotly-subplot/subplot-reposition-annotation.svg + • plotly-subplot/subplot-reposition-image.svg + • plotly-subplot/subplot-reposition-shape-fixed.svg + • plotly-subplot/subplot-reposition-shape.svg Error: Test failures Execution halted ``` -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘jskm.Rmd’ - ... - > data(colon) - Warning in data(colon) : data set ‘colon’ not found - - > fit <- survfit(Surv(time, status) ~ rx, data = colon) - - > jskm(fit) - - When sourcing ‘jskm.R’: - Error: Theme element `plot.margin` must have class . - Execution halted - - ‘jskm.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - ... - --- re-building ‘jskm.Rmd’ using rmarkdown - - Quitting from lines 35-47 [unnamed-chunk-1] (jskm.Rmd) - Error: processing vignette 'jskm.Rmd' failed with diagnostics: - Theme element `plot.margin` must have class . - --- failed re-building ‘jskm.Rmd’ - - SUMMARY: processing the following file failed: - ‘jskm.Rmd’ - - Error: Vignette re-building failed. - Execution halted - ``` - -# KaradaColor - -
- -* Version: 0.1.5 -* GitHub: https://github.com/KaradaGood/KaradaColor -* Source code: https://github.com/cran/KaradaColor -* Date/Publication: 2023-04-21 08:02:37 UTC -* Number of recursive dependencies: 40 - -Run `revdepcheck::cloud_details(, "KaradaColor")` for more info - -
- -## Newly broken +## In both -* checking examples ... ERROR +* checking installed package size ... NOTE ``` - Running examples in ‘KaradaColor-Ex.R’ failed - The error most likely occurred in: - - > ### Name: kg_get_color - > ### Title: Get color palette data - > ### Aliases: kg_get_color kg_get_palette - > - > ### ** Examples - > - > library("scales") - ... - Backtrace: - ▆ - 1. ├─base (local) ``(x) - 2. └─ggplot2:::print.ggplot(x) - 3. ├─ggplot2::ggplot_gtable(data) - 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) - 5. └─ggplot2::calc_element("plot.margin", theme) - 6. └─cli::cli_abort(...) - 7. └─rlang::abort(...) - Execution halted + installed size is 7.1Mb + sub-directories of 1Mb or more: + R 1.0Mb + htmlwidgets 4.0Mb ``` -# karel +# pmartR
-* Version: 0.1.1 -* GitHub: https://github.com/mpru/karel -* Source code: https://github.com/cran/karel -* Date/Publication: 2022-03-26 21:50:02 UTC -* Number of recursive dependencies: 90 +* Version: 2.4.5 +* GitHub: https://github.com/pmartR/pmartR +* Source code: https://github.com/cran/pmartR +* Date/Publication: 2024-05-21 15:50:02 UTC +* Number of recursive dependencies: 149 -Run `revdepcheck::cloud_details(, "karel")` for more info +Run `revdepcheck::cloud_details(, "pmartR")` for more info
## Newly broken -* checking examples ... ERROR - ``` - Running examples in ‘karel-Ex.R’ failed - The error most likely occurred in: - - > ### Name: acciones - > ### Title: Acciones que Karel puede realizar - > ### Aliases: acciones avanzar girar_izquierda poner_coso juntar_coso - > ### girar_derecha darse_vuelta - > - > ### ** Examples - > - ... - 1. └─karel::ejecutar_acciones() - 2. ├─base::suppressWarnings(...) - 3. │ └─base::withCallingHandlers(...) - 4. ├─gganimate::animate(...) - 5. └─gganimate:::animate.gganim(...) - 6. └─args$renderer(frames_vars$frame_source, args$fps) - 7. └─gganimate:::png_dim(frames[1]) - 8. └─cli::cli_abort("Provided file ({file}) does not exist") - 9. └─rlang::abort(...) - Execution halted - ``` - * checking tests ... ERROR ``` Running ‘testthat.R’ Running the tests in ‘tests/testthat.R’ failed. Complete output: > library(testthat) - > library(karel) + > library(pmartR) > - > test_check("karel") - [ FAIL 2 | WARN 2 | SKIP 0 | PASS 78 ] + > test_check("pmartR") + [ FAIL 1 | WARN 1 | SKIP 11 | PASS 2375 ] - ══ Failed tests ════════════════════════════════════════════════════════════════ + ══ Skipped tests (11) ══════════════════════════════════════════════════════════ ... - 5. ├─gganimate::animate(...) - 6. └─gganimate:::animate.gganim(...) - 7. └─args$renderer(frames_vars$frame_source, args$fps) - 8. └─gganimate:::png_dim(frames[1]) - 9. └─cli::cli_abort("Provided file ({file}) does not exist") - 10. └─rlang::abort(...) - - [ FAIL 2 | WARN 2 | SKIP 0 | PASS 78 ] - Error: Test failures - Execution halted - ``` - -## In both - -* checking dependencies in R code ... NOTE - ``` - Namespace in Imports field not imported from: ‘gifski’ - All declared Imports should be used. - ``` - -# kDGLM - -
- -* Version: 1.2.0 -* GitHub: https://github.com/silvaneojunior/kDGLM -* Source code: https://github.com/cran/kDGLM -* Date/Publication: 2024-05-25 09:50:03 UTC -* Number of recursive dependencies: 136 - -Run `revdepcheck::cloud_details(, "kDGLM")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘kDGLM-Ex.R’ failed - The error most likely occurred in: - - > ### Name: forecast.fitted_dlm - > ### Title: Auxiliary function for forecasting - > ### Aliases: forecast.fitted_dlm - > - > ### ** Examples - > - > - ... - > forecast(fitted.data, 24, - + chickenPox = list(Total = rep(175, 24)), # Optional - + Vaccine.1.Covariate = rep(TRUE, 24), - + Vaccine.2.Covariate = rep(TRUE, 24) - + ) - Scale for y is already present. - Adding another scale for y, which will replace the existing scale. - Error in pm[[2]] : subscript out of bounds - Calls: forecast ... lapply -> -> ggplotly.ggplot -> gg2list - Execution halted - ``` - -## In both - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘fitting.Rmd’ - ... - > outcome <- Multinom(p = c("p.1", "p.2"), data = chickenPox[, - + c(2, 3, 5)]) - - > fitted.model <- fit_model(structure * 2, chickenPox = outcome) - - > forecast(fitted.model, t = 24, plot = "base") - - When sourcing ‘fitting.R’: - Error: Error: Missing extra argument: Vaccine.1.Covariate - Execution halted - - ‘example1.Rmd’ using ‘UTF-8’... OK - ‘fitting.Rmd’ using ‘UTF-8’... failed - ‘intro.Rmd’ using ‘UTF-8’... OK - ‘outcomes.Rmd’ using ‘UTF-8’... OK - ‘structures.Rmd’ using ‘UTF-8’... OK - ``` - -# labsimplex - -
- -* Version: 0.1.2 -* GitHub: NA -* Source code: https://github.com/cran/labsimplex -* Date/Publication: 2020-06-03 16:10:06 UTC -* Number of recursive dependencies: 68 - -Run `revdepcheck::cloud_details(, "labsimplex")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘labsimplex-Ex.R’ failed - The error most likely occurred in: - - > ### Name: addSimplex2Surface - > ### Title: Adds the simplex movements to a response surface contour - > ### Aliases: addSimplex2Surface - > - > ### ** Examples - > - > simplex <- exampleOptimization(surface = exampleSurfaceR2, - ... - Backtrace: - ▆ - 1. ├─base::print(p) - 2. └─ggplot2:::print.ggplot(p) - 3. ├─ggplot2::ggplot_gtable(data) - 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) - 5. └─ggplot2::calc_element("plot.margin", theme) - 6. └─cli::cli_abort(...) - 7. └─rlang::abort(...) - Execution halted - ``` - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘labsimplex.Rmd’ - ... - + 0.6, 0, 0)), phi = 30, theta = 30, ltheta = -120, expand = 0.6, - + xlab = "Te ..." ... [TRUNCATED] - - > (cont.surf <- cntr(surface = exampleSurfaceR2, length = 200)) - Warning: Removed 796 rows containing missing values or values outside the scale range - (`geom_tile()`). - - When sourcing ‘labsimplex.R’: - Error: Theme element `plot.margin` must have class . - Execution halted - - ‘labsimplex.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - ... - --- re-building ‘labsimplex.Rmd’ using rmarkdown - - Quitting from lines 66-69 [surfaces1] (labsimplex.Rmd) - Error: processing vignette 'labsimplex.Rmd' failed with diagnostics: - Theme element `plot.margin` must have class . - --- failed re-building ‘labsimplex.Rmd’ - - SUMMARY: processing the following file failed: - ‘labsimplex.Rmd’ - - Error: Vignette re-building failed. - Execution halted - ``` - -# landscapemetrics - -
- -* Version: 2.1.2 -* GitHub: https://github.com/r-spatialecology/landscapemetrics -* Source code: https://github.com/cran/landscapemetrics -* Date/Publication: 2024-05-02 12:52:46 UTC -* Number of recursive dependencies: 96 - -Run `revdepcheck::cloud_details(, "landscapemetrics")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘landscapemetrics-Ex.R’ failed - The error most likely occurred in: - - > ### Name: show_cores - > ### Title: Show core area - > ### Aliases: show_cores - > - > ### ** Examples - > - > landscape <- terra::rast(landscapemetrics::landscape) - ... - Backtrace: - ▆ - 1. ├─base (local) ``(x) - 2. └─ggplot2:::print.ggplot(x) - 3. ├─ggplot2::ggplot_gtable(data) - 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) - 5. └─ggplot2::calc_element("plot.margin", theme) - 6. └─cli::cli_abort(...) - 7. └─rlang::abort(...) - Execution halted - ``` - -## In both - -* checking installed package size ... NOTE - ``` - installed size is 7.9Mb - sub-directories of 1Mb or more: - libs 6.3Mb - ``` - -# landscapetools - -
- -* Version: 0.5.0 -* GitHub: https://github.com/ropensci/landscapetools -* Source code: https://github.com/cran/landscapetools -* Date/Publication: 2019-02-25 22:40:03 UTC -* Number of recursive dependencies: 75 - -Run `revdepcheck::cloud_details(, "landscapetools")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘landscapetools-Ex.R’ failed - The error most likely occurred in: - - > ### Name: util_merge - > ### Title: util_merge - > ### Aliases: util_merge util_merge.RasterLayer - > - > ### ** Examples - > - > x <- util_merge(gradient_landscape, random_landscape) - ... - Backtrace: - ▆ - 1. ├─base (local) ``(x) - 2. └─ggplot2:::print.ggplot(x) - 3. ├─ggplot2::ggplot_gtable(data) - 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) - 5. └─ggplot2::calc_element("plot.margin", theme) - 6. └─cli::cli_abort(...) - 7. └─rlang::abort(...) - Execution halted - ``` - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘overview.Rmd’ - ... - - > library(landscapetools) - - > show_landscape(gradient_landscape) - Loading required package: raster - Loading required package: sp - - When sourcing ‘overview.R’: - Error: Theme element `plot.margin` must have class . - Execution halted - - ‘overview.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - ... - --- re-building ‘overview.Rmd’ using rmarkdown - - Quitting from lines 31-46 [unnamed-chunk-1] (overview.Rmd) - Error: processing vignette 'overview.Rmd' failed with diagnostics: - Theme element `plot.margin` must have class . - --- failed re-building ‘overview.Rmd’ - - SUMMARY: processing the following file failed: - ‘overview.Rmd’ - - Error: Vignette re-building failed. - Execution halted - ``` - -# latentcor - -
- -* Version: 2.0.1 -* GitHub: NA -* Source code: https://github.com/cran/latentcor -* Date/Publication: 2022-09-05 20:50:02 UTC -* Number of recursive dependencies: 143 - -Run `revdepcheck::cloud_details(, "latentcor")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘latentcor-Ex.R’ failed - The error most likely occurred in: - - > ### Name: latentcor - > ### Title: Estimate latent correlation for mixed types. - > ### Aliases: latentcor - > - > ### ** Examples - > - > # Example 1 - truncated data type, same type for all variables - ... - > R_approx = latentcor(X = X, types = "tru", method = "approx")$R - > proc.time() - start_time - user system elapsed - 0.020 0.000 0.021 - > # Heatmap for latent correlation matrix. - > Heatmap_R_approx = latentcor(X = X, types = "tru", method = "approx", - + showplot = TRUE)$plotR - Error in pm[[2]] : subscript out of bounds - Calls: latentcor ... %>% -> layout -> ggplotly -> ggplotly.ggplot -> gg2list - Execution halted - ``` - -# latte - -
- -* Version: 0.2.1 -* GitHub: https://github.com/dkahle/latte -* Source code: https://github.com/cran/latte -* Date/Publication: 2019-03-25 10:50:03 UTC -* Number of recursive dependencies: 86 - -Run `revdepcheck::cloud_details(, "latte")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘latte-Ex.R’ failed - The error most likely occurred in: - - > ### Name: plot-matrix - > ### Title: Plot a matrix - > ### Aliases: plot-matrix plot_matrix - > - > ### ** Examples - > - > - ... - Backtrace: - ▆ - 1. ├─base (local) ``(x) - 2. └─ggplot2:::print.ggplot(x) - 3. ├─ggplot2::ggplot_gtable(data) - 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) - 5. └─ggplot2::calc_element("plot.margin", theme) - 6. └─cli::cli_abort(...) - 7. └─rlang::abort(...) - Execution halted - ``` - -## In both - -* checking LazyData ... NOTE - ``` - 'LazyData' is specified without a 'data' directory - ``` - -# lemon - -
- -* Version: 0.4.9 -* GitHub: https://github.com/stefanedwards/lemon -* Source code: https://github.com/cran/lemon -* Date/Publication: 2024-02-08 08:00:08 UTC -* Number of recursive dependencies: 76 - -Run `revdepcheck::cloud_details(, "lemon")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘lemon-Ex.R’ failed - The error most likely occurred in: - - > ### Name: annotate_y_axis - > ### Title: Annotations on the axis - > ### Aliases: annotate_y_axis annotate_x_axis - > - > ### ** Examples - > - > library(ggplot2) - > - > p <- ggplot(mtcars, aes(mpg, hp, colour=disp)) + geom_point() - > - > l <- p + annotate_y_axis('mark at', y=200, tick=TRUE) - > l - Error in identicalUnits(x) : object is not a unit - Calls: ... polylineGrob -> is.unit -> unit.c -> identicalUnits - Execution halted - ``` - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(lemon) - > - > - > if (TRUE) { - + test_check("lemon") - + } #else { - ... - 17. ├─grid::unit.c(unit(1, "npc"), unit(1, "npc") - tick.length) - 18. └─grid:::Ops.unit(unit(1, "npc"), tick.length) - 19. └─grid:::as.unit(e2) - - [ FAIL 1 | WARN 0 | SKIP 3 | PASS 138 ] - Deleting unused snapshots: - • facet/facet-rep-wrap-spacing.svg - • facet_aux/facet-rep-wrap.svg - Error: Test failures - Execution halted - ``` - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘capped-axes.Rmd’ - ... - > p + coord_capped_cart(bottom = "right") - - > p + coord_capped_cart(bottom = "right", left = "none") - - > ggplot(dat1, aes(gp, y)) + geom_point(position = position_jitter(width = 0.2, - + height = 0)) + coord_capped_cart(left = "none", bottom = bracke .... [TRUNCATED] - - ... - When sourcing ‘legends.R’: - Error: object is not coercible to a unit - Execution halted - - ‘capped-axes.Rmd’ using ‘UTF-8’... failed - ‘facet-rep-labels.Rmd’ using ‘UTF-8’... failed - ‘geoms.Rmd’ using ‘UTF-8’... OK - ‘gtable_show_lemonade.Rmd’ using ‘UTF-8’... OK - ‘legends.Rmd’ using ‘UTF-8’... failed - ‘lemon_print.Rmd’ using ‘UTF-8’... OK - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘capped-axes.Rmd’ using rmarkdown - ``` - -# lfproQC - -
- -* Version: 0.1.0 -* GitHub: NA -* Source code: https://github.com/cran/lfproQC -* Date/Publication: 2024-05-23 16:10:02 UTC -* Number of recursive dependencies: 138 - -Run `revdepcheck::cloud_details(, "lfproQC")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘lfproQC-Ex.R’ failed - The error most likely occurred in: - - > ### Name: Boxplot_data - > ### Title: Creating Boxplot for a dataset - > ### Aliases: Boxplot_data - > - > ### ** Examples - > - > Boxplot_data(yeast_data) - Using Majority protein IDs as id variables - Warning: Removed 266 rows containing non-finite outside the scale range - (`stat_boxplot()`). - Error in pm[[2]] : subscript out of bounds - Calls: Boxplot_data -> -> ggplotly.ggplot -> gg2list - Execution halted - ``` - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘user_guide.Rmd’ - ... - > yeast$`Best combinations` - PCV_best_combination PEV_best_combination PMAD_best_combination - 1 knn_rlr lls_loess lls_rlr - - > Boxplot_data(yeast$knn_rlr_data) - Using Majority protein IDs as id variables - - When sourcing ‘user_guide.R’: - Error: subscript out of bounds - Execution halted - - ‘user_guide.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - ... - --- re-building ‘user_guide.Rmd’ using rmarkdown - - Quitting from lines 53-54 [unnamed-chunk-8] (user_guide.Rmd) - Error: processing vignette 'user_guide.Rmd' failed with diagnostics: - subscript out of bounds - --- failed re-building ‘user_guide.Rmd’ - - SUMMARY: processing the following file failed: - ‘user_guide.Rmd’ - - Error: Vignette re-building failed. - Execution halted - ``` - -## In both - -* checking installed package size ... NOTE - ``` - installed size is 6.2Mb - sub-directories of 1Mb or more: - doc 5.9Mb - ``` - -# LLSR - -
- -* Version: 0.0.3.1 -* GitHub: https://github.com/diegofcoelho/LLSR -* Source code: https://github.com/cran/LLSR -* Date/Publication: 2021-02-17 18:20:02 UTC -* Number of recursive dependencies: 62 - -Run `revdepcheck::cloud_details(, "LLSR")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘LLSR-Ex.R’ failed - The error most likely occurred in: - - > ### Name: AQSys.plot - > ### Title: Dataset and Fitted Function plot - > ### Aliases: AQSys.plot - > - > ### ** Examples - > - > #Populating variable dataSET with binodal data - ... - ▆ - 1. └─LLSR::AQSys.plot(dataSET) - 2. ├─base::print(plot_image) - 3. └─ggplot2:::print.ggplot(plot_image) - 4. ├─ggplot2::ggplot_gtable(data) - 5. └─ggplot2:::ggplot_gtable.ggplot_built(data) - 6. └─ggplot2::calc_element("plot.margin", theme) - 7. └─cli::cli_abort(...) - 8. └─rlang::abort(...) - Execution halted - ``` - -# LMoFit - -
- -* Version: 0.1.7 -* GitHub: NA -* Source code: https://github.com/cran/LMoFit -* Date/Publication: 2024-05-14 07:33:23 UTC -* Number of recursive dependencies: 62 - -Run `revdepcheck::cloud_details(, "LMoFit")` for more info - -
- -## Newly broken - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘LMoFit.Rmd’ - ... - - > lspace_BrIII - - When sourcing ‘LMoFit.R’: - Error: Problem while setting up geom aesthetics. - ℹ Error occurred in the 1st layer. - Caused by error in `compute_geom_2()`: - ! unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), NULL, NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.75, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, 90, NULL, c(0, 2.75, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, - c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 1, NULL, NULL, NULL, c(0, 2.2, 0, 0), NULL, TRUE), NULL, - Execution halted - - ‘LMoFit.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - ... - --- re-building ‘LMoFit.Rmd’ using rmarkdown - - Quitting from lines 236-237 [unnamed-chunk-15] (LMoFit.Rmd) - Error: processing vignette 'LMoFit.Rmd' failed with diagnostics: - Problem while setting up geom aesthetics. - ℹ Error occurred in the 1st layer. - Caused by error in `compute_geom_2()`: - ! unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), NULL, NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.75, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, 90, NULL, c(0, 2.75, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, - ... - NULL, NULL, 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, NULL, NULL, NULL, TRUE), NULL, "right", NULL, NULL, NULL, "center", NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, c(0, 0, 0, 0), list(), 11, list("white", NA, NULL, NULL, TRUE), list(), 5.5, NULL, NULL, list("grey92", NULL, NULL, NULL, FALSE, TRUE), list(), list(), NULL, NULL, NULL, NULL, FALSE, list(NULL, "white", NULL, NULL, TRUE), list(NULL, NULL, NULL, 1.2, 0, 1, NULL, NULL, c(0, - 0, 5.5, 0), NULL, TRUE), "panel", list(NULL, NULL, NULL, NULL, 0, 1, NULL, NULL, c(0, 0, 5.5, 0), NULL, TRUE), list(NULL, NULL, NULL, 0.8, 1, 1, NULL, NULL, c(5.5, 0, 0, 0), NULL, TRUE), "panel", list(NULL, NULL, NULL, 1.2, 0.5, 0.5, NULL, NULL, NULL, NULL, TRUE), "topleft", NULL, c(5.5, 5.5, 5.5, 5.5), list("white", "black", 2, NULL, TRUE), NULL, NULL, "inherit", "inside", list(NULL, NULL, "grey10", 0.8, NULL, NULL, NULL, NULL, c(4.4, 4.4, 4.4, 4.4), NULL, TRUE), NULL, NULL, NULL, list(NULL, NULL, - NULL, NULL, NULL, NULL, -90, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, NULL, 90, NULL, NULL, NULL, TRUE), NULL, 2.75, 2.75, list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), 5.5, c(5.5, 5.5, 5.5, 5.5))) - --- failed re-building ‘LMoFit.Rmd’ - - SUMMARY: processing the following file failed: - ‘LMoFit.Rmd’ - - Error: Vignette re-building failed. - Execution halted - ``` - -## In both - -* checking installed package size ... NOTE - ``` - installed size is 7.0Mb - sub-directories of 1Mb or more: - data 6.5Mb - ``` - -# lomb - -
- -* Version: 2.5.0 -* GitHub: NA -* Source code: https://github.com/cran/lomb -* Date/Publication: 2024-03-26 15:10:05 UTC -* Number of recursive dependencies: 86 - -Run `revdepcheck::cloud_details(, "lomb")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘lomb-Ex.R’ failed - The error most likely occurred in: - - > ### Name: getpeaks - > ### Title: Retrieve periodogram peaks - > ### Aliases: getpeaks - > ### Keywords: ts - > - > ### ** Examples - > - ... - 2. ├─base::plot(sp.out, ...) - 3. └─lomb::plot.lsp(sp.out, ...) - 4. ├─base::print(p) - 5. └─ggplot2:::print.ggplot(p) - 6. ├─ggplot2::ggplot_gtable(data) - 7. └─ggplot2:::ggplot_gtable.ggplot_built(data) - 8. └─ggplot2::calc_element("plot.margin", theme) - 9. └─cli::cli_abort(...) - 10. └─rlang::abort(...) - Execution halted - ``` - -## In both - -* checking installed package size ... NOTE - ``` - installed size is 7.0Mb - sub-directories of 1Mb or more: - data 6.5Mb - ``` - -# LongDat - -
- -* Version: 1.1.2 -* GitHub: https://github.com/CCY-dev/LongDat -* Source code: https://github.com/cran/LongDat -* Date/Publication: 2023-07-17 05:40:02 UTC -* Number of recursive dependencies: 144 - -Run `revdepcheck::cloud_details(, "LongDat")` for more info - -
- -## Newly broken - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘LongDat_cont_tutorial.Rmd’ - ... - - > test_plot <- cuneiform_plot(result_table = test_cont[[1]], - + title_size = 15) - [1] "Finished plotting successfully!" - - > test_plot - - ... - [1] "Finished plotting successfully!" - - > test_plot - - When sourcing ‘LongDat_disc_tutorial.R’: - Error: object is not coercible to a unit - Execution halted - - ‘LongDat_cont_tutorial.Rmd’ using ‘UTF-8’... failed - ‘LongDat_disc_tutorial.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘LongDat_cont_tutorial.Rmd’ using rmarkdown - Warning in eng_r(options) : - Failed to tidy R code in chunk 'unnamed-chunk-3'. Reason: - Error : The formatR package is required by the chunk option tidy = TRUE but not installed; tidy = TRUE will be ignored. - - Warning in eng_r(options) : - Failed to tidy R code in chunk 'unnamed-chunk-4'. Reason: - Error : The formatR package is required by the chunk option tidy = TRUE but not installed; tidy = TRUE will be ignored. - - ... - Quitting from lines 181-182 [unnamed-chunk-11] (LongDat_disc_tutorial.Rmd) - Error: processing vignette 'LongDat_disc_tutorial.Rmd' failed with diagnostics: - object is not coercible to a unit - --- failed re-building ‘LongDat_disc_tutorial.Rmd’ - - SUMMARY: processing the following files failed: - ‘LongDat_cont_tutorial.Rmd’ ‘LongDat_disc_tutorial.Rmd’ - - Error: Vignette re-building failed. - Execution halted - ``` - -# longitudinalcascade - -
- -* Version: 0.3.2.6 -* GitHub: NA -* Source code: https://github.com/cran/longitudinalcascade -* Date/Publication: 2023-05-02 20:50:02 UTC -* Number of recursive dependencies: 40 - -Run `revdepcheck::cloud_details(, "longitudinalcascade")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘longitudinalcascade-Ex.R’ failed - The error most likely occurred in: - - > ### Name: longitudinalcascade - > ### Title: Longitudinal cascade statistics and charts - > ### Aliases: longitudinalcascade - > ### Keywords: cascade longitudinal survival - > - > ### ** Examples - > - ... - Backtrace: - ▆ - 1. ├─base (local) ``(x) - 2. └─ggplot2:::print.ggplot(x) - 3. ├─ggplot2::ggplot_gtable(data) - 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) - 5. └─ggplot2::calc_element("plot.margin", theme) - 6. └─cli::cli_abort(...) - 7. └─rlang::abort(...) - Execution halted - ``` - -# longmixr - -
- -* Version: 1.0.0 -* GitHub: https://github.com/cellmapslab/longmixr -* Source code: https://github.com/cran/longmixr -* Date/Publication: 2022-01-13 20:32:42 UTC -* Number of recursive dependencies: 135 - -Run `revdepcheck::cloud_details(, "longmixr")` for more info - -
- -## Newly broken - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘analysis_workflow.Rmd’ - ... - - > fviz_screeplot(quest_A_dim, main = "Questionnaire A") - - When sourcing ‘analysis_workflow.R’: - Error: Problem while setting up geom aesthetics. - ℹ Error occurred in the 1st layer. - Caused by error in `check_aesthetics()`: - ! Aesthetics must be either length 1 or the same as the data (5). - ✖ Fix the following mappings: `width`. - Execution halted - - ‘analysis_workflow.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘analysis_workflow.Rmd’ using rmarkdown - ``` - -# manhplot - -
- -* Version: 1.1 -* GitHub: https://github.com/cgrace1978/manhplot -* Source code: https://github.com/cran/manhplot -* Date/Publication: 2019-11-25 16:40:03 UTC -* Number of recursive dependencies: 56 - -Run `revdepcheck::cloud_details(, "manhplot")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(manhplot) - > - > test_check("manhplot") - [ FAIL 2 | WARN 3 | SKIP 0 | PASS 0 ] - - ══ Failed tests ════════════════════════════════════════════════════════════════ - ... - 1. └─manhplot::manhplusplot(...) at testmanhplusplot.R:17:3 - 2. ├─ggplot2::ggplot_gtable(ggplot_build(final.table.plot)) - 3. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(final.table.plot)) - 4. └─ggplot2::calc_element("plot.margin", theme) - 5. └─cli::cli_abort(...) - 6. └─rlang::abort(...) - - [ FAIL 2 | WARN 3 | SKIP 0 | PASS 0 ] - Error: Test failures - Execution halted - ``` - -# mau - -
- -* Version: 0.1.2 -* GitHub: https://github.com/pedroguarderas/mau -* Source code: https://github.com/cran/mau -* Date/Publication: 2018-01-17 05:35:14 UTC -* Number of recursive dependencies: 57 - -Run `revdepcheck::cloud_details(, "mau")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘mau-Ex.R’ failed - The error most likely occurred in: - - > ### Name: Spider.Plot - > ### Title: Spider plot - > ### Aliases: Spider.Plot - > - > ### ** Examples - > - > # Preparing data - ... - Backtrace: - ▆ - 1. ├─base::plot(p) - 2. └─ggplot2:::plot.ggplot(p) - 3. ├─ggplot2::ggplot_gtable(data) - 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) - 5. └─ggplot2::calc_element("plot.margin", theme) - 6. └─cli::cli_abort(...) - 7. └─rlang::abort(...) - Execution halted - ``` - -# MBNMAdose - -
- -* Version: 0.4.3 -* GitHub: NA -* Source code: https://github.com/cran/MBNMAdose -* Date/Publication: 2024-04-18 12:42:47 UTC -* Number of recursive dependencies: 118 - -Run `revdepcheck::cloud_details(, "MBNMAdose")` for more info - -
- -## Newly broken - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘outputs-4.Rmd’ - ... - - > plot(trip.emax) - - When sourcing ‘outputs-4.R’: - Error: Problem while setting up geom aesthetics. - ℹ Error occurred in the 1st layer. - Caused by error in `use_defaults()`: - ... - Execution halted - - ‘consistencychecking-3.Rmd’ using ‘UTF-8’... OK - ‘dataexploration-1.Rmd’ using ‘UTF-8’... OK - ‘mbnmadose-overview.Rmd’ using ‘UTF-8’... OK - ‘metaregression-6.Rmd’ using ‘UTF-8’... OK - ‘nma_in_mbnmadose.Rmd’ using ‘UTF-8’... OK - ‘outputs-4.Rmd’ using ‘UTF-8’... failed - ‘predictions-5.Rmd’ using ‘UTF-8’... OK - ‘runmbnmadose-2.Rmd’ using ‘UTF-8’... OK - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘consistencychecking-3.Rmd’ using rmarkdown - ``` - -## In both - -* checking data for non-ASCII characters ... NOTE - ``` - Note: found 6 marked Latin-1 strings - ``` - -# MBNMAtime - -
- -* Version: 0.2.4 -* GitHub: NA -* Source code: https://github.com/cran/MBNMAtime -* Date/Publication: 2023-10-14 15:20:02 UTC -* Number of recursive dependencies: 106 - -Run `revdepcheck::cloud_details(, "MBNMAtime")` for more info - -
- -## Newly broken - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘consistencychecking-3.Rmd’ using rmarkdown - - Quitting from lines 141-146 [unnamed-chunk-8] (consistencychecking-3.Rmd) - Error: processing vignette 'consistencychecking-3.Rmd' failed with diagnostics: - unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, "black", TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), NULL, list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), 5.5, c(5.5, 5.5, 5.5, 5.5), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.75, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, - NULL, NULL, NULL, 1, 90, NULL, c(0, 2.75, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 1, NULL, NULL, NULL, c(0, 2.2, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, - NULL, 0, NULL, NULL, NULL, c(0, 0, 0, 2.2), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0.5, NULL, NULL, NULL, c(0, 2.2, 0, 2.2), NULL, TRUE), list("grey20", NULL, NULL, NULL, FALSE, "grey20", TRUE), NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 0.5, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 0.75, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, list(), NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, list("transparent", NA, NULL, NULL, FALSE), NULL, - 2, NULL, NULL, list("transparent", NA, NULL, NULL, FALSE), 1.2, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 0.2, NULL, list(NULL, NULL, NULL, 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, NULL, NULL, NULL, TRUE), NULL, "right", NULL, NULL, NULL, "center", NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 0, list(), 2, list(), list(NULL, "grey20", NULL, NULL, TRUE), NULL, NULL, NULL, list("grey92", NULL, NULL, NULL, FALSE, "grey92", TRUE), list("grey95", - NULL, NULL, NULL, FALSE, "grey95", FALSE), list("grey95", 0.5, NULL, NULL, FALSE, "grey95", FALSE), NULL, NULL, NULL, NULL, FALSE, list("white", NA, NULL, NULL, FALSE), list(NULL, NULL, NULL, 1.2, 0, 1, NULL, NULL, c(0, 0, 5.5, 0), NULL, TRUE), "panel", list(NULL, NULL, NULL, NULL, 0, 1, NULL, NULL, c(0, 0, 5.5, 0), NULL, TRUE), list(NULL, NULL, NULL, 0.8, 1, 1, NULL, NULL, c(5.5, 0, 0, 0), NULL, TRUE), "panel", list(NULL, NULL, NULL, 1.2, 0.5, 0.5, NULL, NULL, NULL, NULL, TRUE), "topleft", - NULL, NULL, list("lightsteelblue1", "black", NULL, NULL, FALSE), NULL, NULL, "inherit", "inside", list(NULL, NULL, "black", 0.8, NULL, NULL, NULL, NULL, c(4.4, 4.4, 4.4, 4.4), NULL, FALSE), NULL, NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, NULL, -90, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, NULL, 90, NULL, NULL, NULL, TRUE), NULL, 2.75, 2.75)) - --- failed re-building ‘consistencychecking-3.Rmd’ - - --- re-building ‘dataexploration-1.Rmd’ using rmarkdown - ``` - -## In both - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘consistencychecking-3.Rmd’ - ... - |-> direct | | 0.228| -0.213| 0.684| - |-> indirect | | -0.515| -0.891| -0.137| - | | | | | | - - > plot(nodesplit, plot.type = "forest") - - When sourcing ‘consistencychecking-3.R’: - ... - ! unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, "black", TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), NULL, list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), 5.5, c(5.5, 5.5, 5.5, 5.5), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.75, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, - NULL, NULL, NULL, 1, 90, NULL, c(0, 2.75, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, - Execution halted - - ‘consistencychecking-3.Rmd’ using ‘UTF-8’... failed - ‘dataexploration-1.Rmd’ using ‘UTF-8’... failed - ‘mbnmatime-overview.Rmd’ using ‘UTF-8’... OK - ‘outputs-4.Rmd’ using ‘UTF-8’... failed - ‘predictions-5.Rmd’ using ‘UTF-8’... OK - ‘runmbnmatime-2.Rmd’ using ‘UTF-8’... OK - ``` - -# metaforest - -
- -* Version: 0.1.4 -* GitHub: NA -* Source code: https://github.com/cran/metaforest -* Date/Publication: 2024-01-26 09:40:05 UTC -* Number of recursive dependencies: 124 - -Run `revdepcheck::cloud_details(, "metaforest")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > rm(list=ls()) - > library(testthat) - > library(caret) - Loading required package: ggplot2 - Loading required package: lattice - > library(metaforest) - Loading required package: metafor - ... - 6. └─ggplot2::ggplotGrob(plots[[x]] + theme(axis.title.y = element_blank())) - 7. ├─ggplot2::ggplot_gtable(ggplot_build(x)) - 8. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) - 9. └─ggplot2::calc_element("plot.margin", theme) - 10. └─cli::cli_abort(...) - 11. └─rlang::abort(...) - - [ FAIL 1 | WARN 3 | SKIP 0 | PASS 18 ] - Error: Test failures - Execution halted - ``` - -## In both - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘Introduction_to_metaforest.Rmd’ - ... - - > set.seed(62) - - > check_conv <- readRDS("C:/Git_Repositories/S4_meta-analysis/check_conv.RData") - Warning in gzfile(file, "rb") : - cannot open compressed file 'C:/Git_Repositories/S4_meta-analysis/check_conv.RData', probable reason 'No such file or directory' - - When sourcing ‘Introduction_to_metaforest.R’: - Error: cannot open the connection - Execution halted - - ‘Introduction_to_metaforest.Rmd’ using ‘UTF-8’... failed - ``` - -# metan - -
- -* Version: 1.18.0 -* GitHub: https://github.com/TiagoOlivoto/metan -* Source code: https://github.com/cran/metan -* Date/Publication: 2023-03-05 22:00:15 UTC -* Number of recursive dependencies: 116 - -Run `revdepcheck::cloud_details(, "metan")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘metan-Ex.R’ failed - The error most likely occurred in: - - > ### Name: network_plot - > ### Title: Network plot of a correlation matrix - > ### Aliases: network_plot - > - > ### ** Examples - > - > cor <- corr_coef(iris) - ... - Backtrace: - ▆ - 1. ├─base (local) ``(x) - 2. └─ggplot2:::print.ggplot(x) - 3. ├─ggplot2::ggplot_gtable(data) - 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) - 5. └─ggplot2::calc_element("plot.margin", theme) - 6. └─cli::cli_abort(...) - 7. └─rlang::abort(...) - Execution halted - ``` - -# metaplot - -
- -* Version: 0.8.4 -* GitHub: NA -* Source code: https://github.com/cran/metaplot -* Date/Publication: 2024-02-18 05:30:10 UTC -* Number of recursive dependencies: 40 - -Run `revdepcheck::cloud_details(, "metaplot")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘metaplot-Ex.R’ failed - The error most likely occurred in: - - > ### Name: boxplot.data.frame - > ### Title: Boxplot Method for Data Frame - > ### Aliases: boxplot.data.frame - > - > ### ** Examples - > - > library(dplyr) - ... - Backtrace: - ▆ - 1. ├─base (local) ``(x) - 2. └─ggplot2:::print.ggplot(x) - 3. ├─ggplot2::ggplot_gtable(data) - 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) - 5. └─ggplot2::calc_element("plot.margin", theme) - 6. └─cli::cli_abort(...) - 7. └─rlang::abort(...) - Execution halted - ``` - -# metR - -
- -* Version: 0.15.0 -* GitHub: https://github.com/eliocamp/metR -* Source code: https://github.com/cran/metR -* Date/Publication: 2024-02-09 00:40:02 UTC -* Number of recursive dependencies: 120 - -Run `revdepcheck::cloud_details(, "metR")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘metR-Ex.R’ failed - The error most likely occurred in: - - > ### Name: GeostrophicWind - > ### Title: Calculate geostrophic winds - > ### Aliases: GeostrophicWind - > - > ### ** Examples - > - > data(geopotential) - ... - > ggplot(geopotential[date == date[1]], aes(lon, lat)) + - + geom_contour(aes(z = gh)) + - + geom_vector(aes(dx = u, dy = v), skip = 2) + - + scale_mag() - Warning: The S3 guide system was deprecated in ggplot2 3.5.0. - ℹ It has been replaced by a ggproto system that can be extended. - Error in (function (layer, df) : - argument "theme" is missing, with no default - Calls: ... use_defaults -> eval_from_theme -> %||% -> calc_element - Execution halted - ``` - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘Visualization-tools.Rmd’ - ... - - > (g <- ggplot(temperature[lev == 500], aes(lon, lat)) + - + geom_contour_fill(aes(z = air.z)) + geom_vector(aes(dx = t.dx, - + dy = t.dy), skip .... [TRUNCATED] - Warning: The S3 guide system was deprecated in ggplot2 3.5.0. - ℹ It has been replaced by a ggproto system that can be extended. - - ... - + dy = gh.dlat), s .... [TRUNCATED] - Warning: The S3 guide system was deprecated in ggplot2 3.5.0. - ℹ It has been replaced by a ggproto system that can be extended. - - When sourcing ‘Working-with-data.R’: - Error: argument "theme" is missing, with no default - Execution halted - - ‘Visualization-tools.Rmd’ using ‘UTF-8’... failed - ‘Working-with-data.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - ... - --- re-building ‘Visualization-tools.Rmd’ using knitr - - Quitting from lines 284-293 [unnamed-chunk-19] (Visualization-tools.Rmd) - Error: processing vignette 'Visualization-tools.Rmd' failed with diagnostics: - argument "theme" is missing, with no default - --- failed re-building ‘Visualization-tools.Rmd’ - - --- re-building ‘Working-with-data.Rmd’ using knitr - ... - Quitting from lines 199-210 [unnamed-chunk-13] (Working-with-data.Rmd) - Error: processing vignette 'Working-with-data.Rmd' failed with diagnostics: - argument "theme" is missing, with no default - --- failed re-building ‘Working-with-data.Rmd’ - - SUMMARY: processing the following files failed: - ‘Visualization-tools.Rmd’ ‘Working-with-data.Rmd’ - - Error: Vignette re-building failed. - Execution halted - ``` - -## In both - -* checking installed package size ... NOTE - ``` - installed size is 6.6Mb - sub-directories of 1Mb or more: - R 1.5Mb - data 2.0Mb - doc 1.8Mb - ``` - -# miceFast - -
- -* Version: 0.8.2 -* GitHub: https://github.com/Polkas/miceFast -* Source code: https://github.com/cran/miceFast -* Date/Publication: 2022-11-17 21:10:02 UTC -* Number of recursive dependencies: 112 - -Run `revdepcheck::cloud_details(, "miceFast")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘miceFast-Ex.R’ failed - The error most likely occurred in: - - > ### Name: upset_NA - > ### Title: upset plot for NA values - > ### Aliases: upset_NA - > - > ### ** Examples - > - > library(miceFast) - ... - 4. ├─base::suppressMessages(...) - 5. │ └─base::withCallingHandlers(...) - 6. └─UpSetR:::Make_main_bar(...) - 7. └─ggplot2::ggplotGrob(Main_bar_plot) - 8. ├─ggplot2::ggplot_gtable(ggplot_build(x)) - 9. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) - 10. └─ggplot2::calc_element("plot.margin", theme) - 11. └─cli::cli_abort(...) - 12. └─rlang::abort(...) - Execution halted - ``` - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(miceFast) - > library(data.table) - > library(dplyr) - - Attaching package: 'dplyr' - - ... - 15. └─ggplot2::ggplotGrob(Main_bar_plot) - 16. ├─ggplot2::ggplot_gtable(ggplot_build(x)) - 17. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) - 18. └─ggplot2::calc_element("plot.margin", theme) - 19. └─cli::cli_abort(...) - 20. └─rlang::abort(...) - - [ FAIL 1 | WARN 0 | SKIP 0 | PASS 103 ] - Error: Test failures - Execution halted - ``` - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘miceFast-intro.Rmd’ - ... - - > set.seed(123456) - - > data(air_miss) - - > upset_NA(air_miss, 6) - - When sourcing ‘miceFast-intro.R’: - Error: Theme element `plot.margin` must have class . - Execution halted - - ‘miceFast-intro.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - ... - --- re-building ‘miceFast-intro.Rmd’ using rmarkdown - - Quitting from lines 84-85 [unnamed-chunk-6] (miceFast-intro.Rmd) - Error: processing vignette 'miceFast-intro.Rmd' failed with diagnostics: - Theme element `plot.margin` must have class . - --- failed re-building ‘miceFast-intro.Rmd’ - - SUMMARY: processing the following file failed: - ‘miceFast-intro.Rmd’ - - Error: Vignette re-building failed. - Execution halted - ``` - -## In both - -* checking C++ specification ... NOTE - ``` - Specified C++11: please drop specification unless essential - ``` - -* checking installed package size ... NOTE - ``` - installed size is 12.1Mb - sub-directories of 1Mb or more: - libs 10.9Mb - ``` - -# MicrobiomeStat - -
- -* Version: 1.2 -* GitHub: NA -* Source code: https://github.com/cran/MicrobiomeStat -* Date/Publication: 2024-04-01 22:30:02 UTC -* Number of recursive dependencies: 73 - -Run `revdepcheck::cloud_details(, "MicrobiomeStat")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘MicrobiomeStat-Ex.R’ failed - The error most likely occurred in: - - > ### Name: linda - > ### Title: Linear (Lin) Model for Differential Abundance (DA) Analysis of - > ### High-dimensional Compositional Data - > ### Aliases: linda - > - > ### ** Examples - > - ... - Backtrace: - ▆ - 1. ├─base (local) ``(x) - 2. └─ggplot2:::print.ggplot(x) - 3. ├─ggplot2::ggplot_gtable(data) - 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) - 5. └─ggplot2::calc_element("plot.margin", theme) - 6. └─cli::cli_abort(...) - 7. └─rlang::abort(...) - Execution halted - ``` - -# micromap - -
- -* Version: 1.9.8 -* GitHub: https://github.com/USEPA/micromap -* Source code: https://github.com/cran/micromap -* Date/Publication: 2024-02-06 14:00:02 UTC -* Number of recursive dependencies: 45 - -Run `revdepcheck::cloud_details(, "micromap")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘micromap-Ex.R’ failed - The error most likely occurred in: - - > ### Name: lmgroupedplot - > ### Title: Linked Micromaps - > ### Aliases: lmgroupedplot lmplot mmgroupedplot mmplot - > ### mmplot.SpatialPolygonsDataFrame mmplot.sf mmplot.default - > ### Keywords: hplot - > - > ### ** Examples - ... - 6. ├─base::suppressWarnings(...) - 7. │ └─base::withCallingHandlers(...) - 8. ├─base::print(plobject[[p]], vp = subplot(1, p * 2)) - 9. └─ggplot2:::print.ggplot(plobject[[p]], vp = subplot(1, p * 2)) - 10. ├─ggplot2::ggplot_gtable(data) - 11. └─ggplot2:::ggplot_gtable.ggplot_built(data) - 12. └─ggplot2::calc_element("plot.margin", theme) - 13. └─cli::cli_abort(...) - 14. └─rlang::abort(...) - Execution halted - ``` - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘Introduction_Guide.Rnw’ - ... - 6 AK 1 1 4 17 0 1 0 - - > mmplot(stat.data = edPov, map.data = statePolys, panel.types = c("labels", - + "dot", "dot", "map"), panel.data = list("state", "pov", "ed", - + .... [TRUNCATED] - - When sourcing ‘Introduction_Guide.R’: - Error: Theme element `plot.margin` must have class - . - Execution halted - - ‘Introduction_Guide.Rnw’ using ‘UTF-8’... failed - ``` - -## In both - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - ... - --- re-building ‘Introduction_Guide.Rnw’ using Sweave - Loading required package: RColorBrewer - Loading required package: sp - Loading required package: sf - Linking to GEOS 3.10.2, GDAL 3.4.1, PROJ 8.2.1; sf_use_s2() - is TRUE - - Error: processing vignette 'Introduction_Guide.Rnw' failed with diagnostics: - ... - Theme element `plot.margin` must have class - . - - --- failed re-building ‘Introduction_Guide.Rnw’ - - SUMMARY: processing the following file failed: - ‘Introduction_Guide.Rnw’ - - Error: Vignette re-building failed. - Execution halted - ``` - -# MiMIR - -
- -* Version: 1.5 -* GitHub: NA -* Source code: https://github.com/cran/MiMIR -* Date/Publication: 2024-02-01 08:50:02 UTC -* Number of recursive dependencies: 188 - -Run `revdepcheck::cloud_details(, "MiMIR")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘MiMIR-Ex.R’ failed - The error most likely occurred in: - - > ### Name: LOBOV_accuracies - > ### Title: LOBOV_accuracies - > ### Aliases: LOBOV_accuracies - > - > ### ** Examples - > - > require(pROC) - ... - 56 metabolites x 500 samples - | Pruning samples on5SD: - 56 metabolites x 500 samples - | Performing scaling ... DONE! - | Imputation ... DONE! - > p_avail<-colnames(b_p)[c(1:5)] - > LOBOV_accuracies(sur$surrogates, b_p, p_avail, MiMIR::acc_LOBOV) - Error in pm[[2]] : subscript out of bounds - Calls: LOBOV_accuracies -> -> ggplotly.ggplot -> gg2list - Execution halted - ``` - -# MIMSunit - -
- -* Version: 0.11.2 -* GitHub: https://github.com/mhealthgroup/MIMSunit -* Source code: https://github.com/cran/MIMSunit -* Date/Publication: 2022-06-21 11:00:09 UTC -* Number of recursive dependencies: 114 - -Run `revdepcheck::cloud_details(, "MIMSunit")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘MIMSunit-Ex.R’ failed - The error most likely occurred in: - - > ### Name: bandlimited_interp - > ### Title: Apply a bandlimited interpolation filter to the signal to change - > ### the sampling rate - > ### Aliases: bandlimited_interp - > - > ### ** Examples - > - ... - Backtrace: - ▆ - 1. ├─base (local) ``(x) - 2. └─ggplot2:::print.ggplot(x) - 3. ├─ggplot2::ggplot_gtable(data) - 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) - 5. └─ggplot2::calc_element("plot.margin", theme) - 6. └─cli::cli_abort(...) - 7. └─rlang::abort(...) - Execution halted - ``` - -# miRetrieve - -
- -* Version: 1.3.4 -* GitHub: NA -* Source code: https://github.com/cran/miRetrieve -* Date/Publication: 2021-09-18 17:30:02 UTC -* Number of recursive dependencies: 126 - -Run `revdepcheck::cloud_details(, "miRetrieve")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(miRetrieve) - > - > test_check("miRetrieve") - [ FAIL 1 | WARN 11 | SKIP 0 | PASS 202 ] - - ══ Failed tests ════════════════════════════════════════════════════════════════ - ... - Backtrace: - ▆ - 1. └─miRetrieve::compare_mir_terms_scatter(df_merged, "miR-21", title = "Test_title") at test-comparemirterms.R:56:1 - 2. ├─plotly::ggplotly(plot) - 3. └─plotly:::ggplotly.ggplot(plot) - 4. └─plotly::gg2list(...) - - [ FAIL 1 | WARN 11 | SKIP 0 | PASS 202 ] - Error: Test failures - Execution halted - ``` - -# misspi - -
- -* Version: 0.1.0 -* GitHub: NA -* Source code: https://github.com/cran/misspi -* Date/Publication: 2023-10-17 09:50:02 UTC -* Number of recursive dependencies: 88 - -Run `revdepcheck::cloud_details(, "misspi")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘misspi-Ex.R’ failed - The error most likely occurred in: - - > ### Name: evaliq - > ### Title: Evaluate the Imputation Quality - > ### Aliases: evaliq - > - > ### ** Examples - > - > # A very quick example - ... - > # Default plot - > er.eval <- evaliq(x.true[na.idx], x.est[na.idx]) - `geom_smooth()` using formula = 'y ~ x' - > - > # Interactive plot - > er.eval <- evaliq(x.true[na.idx], x.est[na.idx], interactive = TRUE) - `geom_smooth()` using formula = 'y ~ x' - Error in pm[[2]] : subscript out of bounds - Calls: evaliq -> print -> ggplotly -> ggplotly.ggplot -> gg2list - Execution halted - ``` - -# mizer - -
- -* Version: 2.5.1 -* GitHub: https://github.com/sizespectrum/mizer -* Source code: https://github.com/cran/mizer -* Date/Publication: 2024-03-08 23:10:02 UTC -* Number of recursive dependencies: 109 - -Run `revdepcheck::cloud_details(, "mizer")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘spelling.R’ - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(mizer) - > - > test_check("mizer") - [ FAIL 10 | WARN 0 | SKIP 5 | PASS 1251 ] - - ... - • plots/plot-spectra.svg - • plots/plot-yield-by-gear.svg - • plots/plot-yield.svg - • plots/plotfishing-mortality.svg - • plots/plotfmort-truncated.svg - • plots/plotpredation-mortality.svg - • plots/plotpredmort-truncated.new.svg - • plots/plotpredmort-truncated.svg - Error: Test failures - Execution halted - ``` - -## In both - -* checking installed package size ... NOTE - ``` - installed size is 6.1Mb - sub-directories of 1Mb or more: - doc 1.5Mb - help 1.8Mb - ``` - -# mlr3spatiotempcv - -
- -* Version: 2.3.1 -* GitHub: https://github.com/mlr-org/mlr3spatiotempcv -* Source code: https://github.com/cran/mlr3spatiotempcv -* Date/Publication: 2024-04-17 12:10:05 UTC -* Number of recursive dependencies: 168 - -Run `revdepcheck::cloud_details(, "mlr3spatiotempcv")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘mlr3spatiotempcv-Ex.R’ failed - The error most likely occurred in: - - > ### Name: autoplot.ResamplingCustomCV - > ### Title: Visualization Functions for Non-Spatial CV Methods. - > ### Aliases: autoplot.ResamplingCustomCV plot.ResamplingCustomCV - > - > ### ** Examples - > - > if (mlr3misc::require_namespaces(c("sf", "patchwork"), quietly = TRUE)) { - ... - + - + autoplot(resampling, task) + - + ggplot2::scale_x_continuous(breaks = seq(-79.085, -79.055, 0.01)) - + autoplot(resampling, task, fold_id = 1) - + autoplot(resampling, task, fold_id = c(1, 2)) * - + ggplot2::scale_x_continuous(breaks = seq(-79.085, -79.055, 0.01)) - + } - Error in identicalUnits(x) : object is not a unit - Calls: ... assemble_guides -> guides_build -> unit.c -> identicalUnits - Execution halted - ``` - -## In both - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘spatiotemp-viz.Rmd’ - ... - - > knitr::opts_chunk$set(collapse = TRUE, comment = "#>") - - > knitr::include_graphics("../man/figures/sptcv_cstf_multiplot.png") - - When sourcing ‘spatiotemp-viz.R’: - Error: Cannot find the file(s): "../man/figures/sptcv_cstf_multiplot.png" - Execution halted - - ‘mlr3spatiotempcv.Rmd’ using ‘UTF-8’... OK - ‘spatiotemp-viz.Rmd’ using ‘UTF-8’... failed - ``` - -* checking installed package size ... NOTE - ``` - installed size is 5.9Mb - sub-directories of 1Mb or more: - data 3.5Mb - ``` - -# mlr3viz - -
- -* Version: 0.8.0 -* GitHub: https://github.com/mlr-org/mlr3viz -* Source code: https://github.com/cran/mlr3viz -* Date/Publication: 2024-03-05 12:50:03 UTC -* Number of recursive dependencies: 140 - -Run `revdepcheck::cloud_details(, "mlr3viz")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘mlr3viz-Ex.R’ failed - The error most likely occurred in: - - > ### Name: autoplot.OptimInstanceSingleCrit - > ### Title: Plots for Optimization Instances - > ### Aliases: autoplot.OptimInstanceSingleCrit - > - > ### ** Examples - > - > if (requireNamespace("mlr3") && requireNamespace("bbotk") && requireNamespace("patchwork")) { - ... - INFO [11:58:58.325] [bbotk] 5.884797 2.2371095 -32.51896 - INFO [11:58:58.325] [bbotk] -7.841127 -0.8872557 -91.31148 - INFO [11:58:58.334] [bbotk] Finished optimizing after 20 evaluation(s) - INFO [11:58:58.335] [bbotk] Result: - INFO [11:58:58.338] [bbotk] x1 x2 x_domain y - INFO [11:58:58.338] [bbotk] - INFO [11:58:58.338] [bbotk] 2.582281 -2.940254 9.657379 - Error in identicalUnits(x) : object is not a unit - Calls: print ... assemble_guides -> guides_build -> unit.c -> identicalUnits - Execution halted - ``` - -# modeltime.resample - -
- -* Version: 0.2.3 -* GitHub: https://github.com/business-science/modeltime.resample -* Source code: https://github.com/cran/modeltime.resample -* Date/Publication: 2023-04-12 15:50:02 UTC -* Number of recursive dependencies: 229 - -Run `revdepcheck::cloud_details(, "modeltime.resample")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > - > # Machine Learning - > library(tidymodels) - ── Attaching packages ────────────────────────────────────── tidymodels 1.2.0 ── - ✔ broom 1.0.6 ✔ recipes 1.0.10 - ✔ dials 1.2.1 ✔ rsample 1.2.1 - ... - ▆ - 1. ├─m750_models_resample %>% ... at test-modeltime_fit_resamples.R:116:5 - 2. └─modeltime.resample::plot_modeltime_resamples(., .interactive = TRUE) - 3. ├─plotly::ggplotly(g) - 4. └─plotly:::ggplotly.ggplot(g) - 5. └─plotly::gg2list(...) - - [ FAIL 1 | WARN 4 | SKIP 0 | PASS 16 ] - Error: Test failures - Execution halted - ``` - -## In both - -* checking dependencies in R code ... NOTE - ``` - Namespaces in Imports field not imported from: - ‘crayon’ ‘dials’ ‘glue’ ‘parsnip’ - All declared Imports should be used. - ``` - -# mosaic - -
- -* Version: 1.9.1 -* GitHub: https://github.com/ProjectMOSAIC/mosaic -* Source code: https://github.com/cran/mosaic -* Date/Publication: 2024-02-23 14:30:06 UTC -* Number of recursive dependencies: 131 - -Run `revdepcheck::cloud_details(, "mosaic")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘mosaic-Ex.R’ failed - The error most likely occurred in: - - > ### Name: mUSMap - > ### Title: Make a US map with 'ggplot2' - > ### Aliases: mUSMap - > - > ### ** Examples - > - > USArrests2 <- USArrests |> tibble::rownames_to_column("state") - ... - Backtrace: - ▆ - 1. ├─base (local) ``(x) - 2. └─ggplot2:::print.ggplot(x) - 3. ├─ggplot2::ggplot_gtable(data) - 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) - 5. └─ggplot2::calc_element("plot.margin", theme) - 6. └─cli::cli_abort(...) - 7. └─rlang::abort(...) - Execution halted - ``` - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(mosaic) - Registered S3 method overwritten by 'mosaic': - method from - fortify.SpatialPolygonsDataFrame ggplot2 - - The 'mosaic' package masks several functions from core packages in order to add - ... - • plotModel/plotmodel2.svg - • plotModel/plotmodel3.svg - • plotPoints/plotpoints2.svg - • plotPoints/plotpoints3.svg - • rfun/rfun2.svg - • statTally/stattally2.svg - • statTally/stattally3.svg - • xpnorm/xpnorm2.svg - Error: Test failures - Execution halted - ``` - -## In both - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘MinimalRgg.Rnw’ - ... - > set.seed(123) - - > knitr::opts_chunk$set(dev = "pdf", eval = FALSE, tidy = FALSE, - + fig.align = "center", fig.show = "hold", message = FALSE) - - > apropos() - - When sourcing ‘MinimalRgg.R’: - Error: argument "what" is missing, with no default - Execution halted - - ‘Resampling.Rmd’ using ‘UTF-8’... OK - ‘mosaic-resources.Rmd’ using ‘UTF-8’... OK - ‘MinimalRgg.Rnw’ using ‘UTF-8’... failed - ``` - -* checking package dependencies ... NOTE - ``` - Package which this enhances but not available for checking: ‘manipulate’ - ``` - -* checking installed package size ... NOTE - ``` - installed size is 6.8Mb - sub-directories of 1Mb or more: - R 5.0Mb - doc 1.2Mb - ``` - -* checking Rd cross-references ... NOTE - ``` - Package unavailable to check Rd xrefs: ‘cubature’ - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘Resampling.Rmd’ using rmarkdown - ``` - -# motifr - -
- -* Version: 1.0.0 -* GitHub: https://github.com/marioangst/motifr -* Source code: https://github.com/cran/motifr -* Date/Publication: 2020-12-10 15:40:02 UTC -* Number of recursive dependencies: 121 - -Run `revdepcheck::cloud_details(, "motifr")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘motifr-Ex.R’ failed - The error most likely occurred in: - - > ### Name: directed_dummy_net - > ### Title: Two-level directed network dummy example - > ### Aliases: directed_dummy_net - > ### Keywords: datasets - > - > ### ** Examples - > - ... - Backtrace: - ▆ - 1. ├─base (local) ``(x) - 2. └─ggplot2:::print.ggplot(x) - 3. ├─ggplot2::ggplot_gtable(data) - 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) - 5. └─ggplot2::calc_element("plot.margin", theme) - 6. └─cli::cli_abort(...) - 7. └─rlang::abort(...) - Execution halted - ``` - -# mpwR - -
- -* Version: 0.1.5 -* GitHub: NA -* Source code: https://github.com/cran/mpwR -* Date/Publication: 2023-11-13 23:33:26 UTC -* Number of recursive dependencies: 112 - -Run `revdepcheck::cloud_details(, "mpwR")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘mpwR-Ex.R’ failed - The error most likely occurred in: - - > ### Name: plot_Upset - > ### Title: Upset Plot - > ### Aliases: plot_Upset - > - > ### ** Examples - > - > # Load libraries - ... - 3. ├─base::suppressMessages(...) - 4. │ └─base::withCallingHandlers(...) - 5. └─UpSetR:::Make_main_bar(...) - 6. └─ggplot2::ggplotGrob(Main_bar_plot) - 7. ├─ggplot2::ggplot_gtable(ggplot_build(x)) - 8. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) - 9. └─ggplot2::calc_element("plot.margin", theme) - 10. └─cli::cli_abort(...) - 11. └─rlang::abort(...) - Execution halted - ``` - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(mpwR) - > - > test_check("mpwR") - For DIA-NN no quantitative LFQ data on peptide-level. - For PD no quantitative LFQ data on peptide-level. - For DIA-NN no quantitative LFQ data on peptide-level. - ... - 6. └─ggplot2::ggplotGrob(Main_bar_plot) - 7. ├─ggplot2::ggplot_gtable(ggplot_build(x)) - 8. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) - 9. └─ggplot2::calc_element("plot.margin", theme) - 10. └─cli::cli_abort(...) - 11. └─rlang::abort(...) - - [ FAIL 1 | WARN 123 | SKIP 0 | PASS 658 ] - Error: Test failures - Execution halted - ``` - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘Workflow.Rmd’ - ... - > plot_CV_density(input_list = CV_LFQ_PG, cv_col = "PG_quant") - - > Upset_prepared <- get_Upset_list(input_list = files, - + level = "ProteinGroup.IDs") - - > plot_Upset(input_list = Upset_prepared, label = "ProteinGroup.IDs") - - When sourcing ‘Workflow.R’: - Error: Theme element `plot.margin` must have class . - Execution halted - - ‘Import.Rmd’ using ‘UTF-8’... OK - ‘Output_Explanations.Rmd’ using ‘UTF-8’... OK - ‘Requirements.Rmd’ using ‘UTF-8’... OK - ‘Workflow.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘Import.Rmd’ using rmarkdown - --- finished re-building ‘Import.Rmd’ - - --- re-building ‘Output_Explanations.Rmd’ using rmarkdown - --- finished re-building ‘Output_Explanations.Rmd’ - - --- re-building ‘Requirements.Rmd’ using rmarkdown - --- finished re-building ‘Requirements.Rmd’ - - --- re-building ‘Workflow.Rmd’ using rmarkdown - ``` - -# mrfDepth - -
- -* Version: 1.0.17 -* GitHub: NA -* Source code: https://github.com/cran/mrfDepth -* Date/Publication: 2024-05-24 21:20:02 UTC -* Number of recursive dependencies: 44 - -Run `revdepcheck::cloud_details(, "mrfDepth")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘mrfDepth-Ex.R’ failed - The error most likely occurred in: - - > ### Name: bagplot - > ### Title: Draws a bagplot, a bivariate boxplot - > ### Aliases: bagplot - > ### Keywords: Graphical - > - > ### ** Examples - > - ... - Backtrace: - ▆ - 1. ├─base (local) ``(x) - 2. └─ggplot2:::print.ggplot(x) - 3. ├─ggplot2::ggplot_gtable(data) - 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) - 5. └─ggplot2::calc_element("plot.margin", theme) - 6. └─cli::cli_abort(...) - 7. └─rlang::abort(...) - Execution halted - ``` - -## In both - -* checking installed package size ... NOTE - ``` - installed size is 20.2Mb - sub-directories of 1Mb or more: - data 1.6Mb - libs 18.1Mb - ``` - -# musclesyneRgies - -
- -* Version: 1.2.5 -* GitHub: https://github.com/alesantuz/musclesyneRgies -* Source code: https://github.com/cran/musclesyneRgies -* Date/Publication: 2022-07-19 17:10:02 UTC -* Number of recursive dependencies: 82 - -Run `revdepcheck::cloud_details(, "musclesyneRgies")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘musclesyneRgies-Ex.R’ failed - The error most likely occurred in: - - > ### Name: plot_classified_syns - > ### Title: Plot muscle synergies - > ### Aliases: plot_classified_syns - > - > ### ** Examples - > - > # Load some data - ... - 3. │ └─base::withCallingHandlers(...) - 4. └─gridExtra::arrangeGrob(...) - 5. └─base::lapply(grobs[toconv], ggplot2::ggplotGrob) - 6. └─ggplot2 (local) FUN(X[[i]], ...) - 7. ├─ggplot2::ggplot_gtable(ggplot_build(x)) - 8. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) - 9. └─ggplot2::calc_element("plot.margin", theme) - 10. └─cli::cli_abort(...) - 11. └─rlang::abort(...) - Execution halted - ``` - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(musclesyneRgies) - > - > test_check("musclesyneRgies") - [ FAIL 1 | WARN 13 | SKIP 0 | PASS 45 ] - - ══ Failed tests ════════════════════════════════════════════════════════════════ - ... - 4. └─ggplot2 (local) FUN(X[[i]], ...) - 5. ├─ggplot2::ggplot_gtable(ggplot_build(x)) - 6. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) - 7. └─ggplot2::calc_element("plot.margin", theme) - 8. └─cli::cli_abort(...) - 9. └─rlang::abort(...) - - [ FAIL 1 | WARN 13 | SKIP 0 | PASS 45 ] - Error: Test failures - Execution halted - ``` - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘plots.Rmd’ - ... - > library(musclesyneRgies) - - > data("RAW_DATA") - - > pp <- plot_rawEMG(RAW_DATA[[1]], trial = names(RAW_DATA)[1], - + row_number = 4, col_number = 4, line_col = "tomato3") - - When sourcing ‘plots.R’: - Error: Theme element `plot.margin` must have class . - Execution halted - - ‘analysis.Rmd’ using ‘UTF-8’... OK - ‘plots.Rmd’ using ‘UTF-8’... failed - ‘pro_tips.Rmd’ using ‘UTF-8’... OK - ‘workflow.Rmd’ using ‘UTF-8’... OK - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘analysis.Rmd’ using rmarkdown - ``` - -# naniar - -
- -* Version: 1.1.0 -* GitHub: https://github.com/njtierney/naniar -* Source code: https://github.com/cran/naniar -* Date/Publication: 2024-03-05 10:10:02 UTC -* Number of recursive dependencies: 173 - -Run `revdepcheck::cloud_details(, "naniar")` for more info - -
- -## Newly broken - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘naniar-visualisation.Rmd’ - ... - - > library(naniar) - - > vis_miss(airquality) - - > gg_miss_upset(airquality) - - When sourcing ‘naniar-visualisation.R’: - Error: Theme element `plot.margin` must have class . - Execution halted - - ‘exploring-imputed-values.Rmd’ using ‘UTF-8’... OK - ‘getting-started-w-naniar.Rmd’ using ‘UTF-8’... OK - ‘naniar-visualisation.Rmd’ using ‘UTF-8’... failed - ‘replace-with-na.Rmd’ using ‘UTF-8’... OK - ‘special-missing-values.Rmd’ using ‘UTF-8’... OK - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘exploring-imputed-values.Rmd’ using rmarkdown - ``` - -# neatmaps - -
- -* Version: 2.1.0 -* GitHub: https://github.com/PhilBoileau/neatmaps -* Source code: https://github.com/cran/neatmaps -* Date/Publication: 2019-05-12 19:10:03 UTC -* Number of recursive dependencies: 99 - -Run `revdepcheck::cloud_details(, "neatmaps")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘neatmaps-Ex.R’ failed - The error most likely occurred in: - - > ### Name: consClustResTable - > ### Title: Consensus Cluster Results in a Table - > ### Aliases: consClustResTable - > - > ### ** Examples - > - > # create the data frame using the network, node and edge attributes - ... - > df <- netsDataFrame(network_attr_df, - + node_attr_df, - + edge_df) - > - > # run the neatmap code on df - > neat_res <- neatmap(df, scale_df = "ecdf", max_k = 3, reps = 100, - + xlab = "vars", ylab = "nets", xlab_cex = 1, ylab_cex = 1) - Error in pm[[2]] : subscript out of bounds - Calls: neatmap ... %>% -> layout -> ggplotly -> ggplotly.ggplot -> gg2list - Execution halted - ``` - -## In both - -* checking installed package size ... NOTE - ``` - installed size is 6.3Mb - ``` - -# NetFACS - -
- -* Version: 0.5.0 -* GitHub: NA -* Source code: https://github.com/cran/NetFACS -* Date/Publication: 2022-12-06 17:32:35 UTC -* Number of recursive dependencies: 101 - -Run `revdepcheck::cloud_details(, "NetFACS")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘NetFACS-Ex.R’ failed - The error most likely occurred in: - - > ### Name: multiple_network_plot - > ### Title: Plots networks for multiple conditions - > ### Aliases: multiple_network_plot multiple.network.plot - > - > ### ** Examples - > - > data(emotions_set) - ... - 4. └─base::lapply(x$plots, plot_table, guides = guides) - 5. ├─patchwork (local) FUN(X[[i]], ...) - 6. └─patchwork:::plot_table.ggplot(X[[i]], ...) - 7. └─ggplot2::ggplotGrob(x) - 8. ├─ggplot2::ggplot_gtable(ggplot_build(x)) - 9. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) - 10. └─ggplot2::calc_element("plot.margin", theme) - 11. └─cli::cli_abort(...) - 12. └─rlang::abort(...) - Execution halted - ``` - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘netfacs_tutorial.Rmd’ - ... - Warning in grid.Call.graphics(C_text, as.graphicsAnnot(x$label), x$x, x$y, : - font family 'Arial Narrow' not found in PostScript font database - Warning in grid.Call.graphics(C_text, as.graphicsAnnot(x$label), x$x, x$y, : - font family 'Arial Narrow' not found in PostScript font database - Warning in grid.Call.graphics(C_text, as.graphicsAnnot(x$label), x$x, x$y, : - font family 'Arial Narrow' not found in PostScript font database - - When sourcing ‘netfacs_tutorial.R’: - Error: invalid font type - Execution halted - - ‘netfacs_tutorial.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘netfacs_tutorial.Rmd’ using rmarkdown - ``` - -# NHSRplotthedots - -
- -* Version: 0.1.0 -* GitHub: NA -* Source code: https://github.com/cran/NHSRplotthedots -* Date/Publication: 2021-11-03 20:20:10 UTC -* Number of recursive dependencies: 88 - -Run `revdepcheck::cloud_details(, "NHSRplotthedots")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘NHSRplotthedots-Ex.R’ failed - The error most likely occurred in: - - > ### Name: ptd_spc - > ### Title: SPC Plotting Function - > ### Aliases: ptd_spc - > - > ### ** Examples - > - > library(NHSRdatasets) - ... - 1. ├─base (local) ``(x) - 2. └─NHSRplotthedots:::print.ptd_spc_df(x) - 3. ├─base::print(p) - 4. └─ggplot2:::print.ggplot(p) - 5. ├─ggplot2::ggplot_gtable(data) - 6. └─ggplot2:::ggplot_gtable.ggplot_built(data) - 7. └─ggplot2::calc_element("plot.margin", theme) - 8. └─cli::cli_abort(...) - 9. └─rlang::abort(...) - Execution halted - ``` - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘deviations.Rmd’ - ... - - > spc_data <- ptd_spc(df, value_field = data, date_field = date) - - > spc_data %>% plot() + labs(caption = paste("UPL = ", - + round(spc_data$upl[1], 2), ", Mean = ", round(spc_data$mean[1], - + 2), ", LPL = ..." ... [TRUNCATED] - - ... - > ptd_spc(stable_set, value_field = breaches, date_field = period, - + improvement_direction = "decrease") - - When sourcing ‘intro.R’: - Error: Theme element `plot.margin` must have class . - Execution halted - - ‘deviations.Rmd’ using ‘UTF-8’... failed - ‘intro.Rmd’ using ‘UTF-8’... failed - ‘number-of-points-required.Rmd’ using ‘UTF-8’... OK - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘deviations.Rmd’ using rmarkdown - - Quitting from lines 60-74 [unnamed-chunk-1] (deviations.Rmd) - Error: processing vignette 'deviations.Rmd' failed with diagnostics: - Theme element `plot.margin` must have class . - --- failed re-building ‘deviations.Rmd’ - - --- re-building ‘intro.Rmd’ using rmarkdown - ``` - -## In both - -* checking dependencies in R code ... NOTE - ``` - Namespaces in Imports field not imported from: - ‘NHSRdatasets’ ‘grid’ ‘utils’ - All declared Imports should be used. - ``` - -# nima - -
- -* Version: 0.6.2 -* GitHub: https://github.com/nhejazi/nima -* Source code: https://github.com/cran/nima -* Date/Publication: 2020-03-06 06:10:03 UTC -* Number of recursive dependencies: 65 - -Run `revdepcheck::cloud_details(, "nima")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘nima-Ex.R’ failed - The error most likely occurred in: - - > ### Name: theme_jetblack - > ### Title: A jet black theme with inverted colors - > ### Aliases: theme_jetblack - > - > ### ** Examples - > - > library(ggplot2) - ... - Backtrace: - ▆ - 1. ├─base (local) ``(x) - 2. └─ggplot2:::print.ggplot(x) - 3. ├─ggplot2::ggplot_gtable(data) - 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) - 5. └─ggplot2::calc_element("plot.margin", theme) - 6. └─cli::cli_abort(...) - 7. └─rlang::abort(...) - Execution halted - ``` - -## In both - -* checking LazyData ... NOTE - ``` - 'LazyData' is specified without a 'data' directory - ``` - -# NIMAA - -
- -* Version: 0.2.1 -* GitHub: https://github.com/jafarilab/NIMAA -* Source code: https://github.com/cran/NIMAA -* Date/Publication: 2022-04-11 14:12:45 UTC -* Number of recursive dependencies: 172 - -Run `revdepcheck::cloud_details(, "NIMAA")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘NIMAA-Ex.R’ failed - The error most likely occurred in: - - > ### Name: extractSubMatrix - > ### Title: Extract the non-missing submatrices from a given matrix. - > ### Aliases: extractSubMatrix - > - > ### ** Examples - > - > # load part of the beatAML data - ... - + row.vars = "inhibitor") - binmatnest.temperature - 13.21221 - Size of Square: 66 rows x 66 columns - Size of Rectangular_row: 6 rows x 105 columns - Size of Rectangular_col: 99 rows x 2 columns - Size of Rectangular_element_max: 59 rows x 79 columns - Error in pm[[2]] : subscript out of bounds - Calls: extractSubMatrix ... plotSubmatrix -> print -> -> ggplotly.ggplot -> gg2list - Execution halted - ``` - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(NIMAA) - > - > test_check("NIMAA") - binmatnest.temperature - 13.21249 - Size of Square: 66 rows x 66 columns - ... - 1. └─NIMAA::extractSubMatrix(...) at test-extract-nonmissing-submatrix.R:5:3 - 2. └─NIMAA:::plotSubmatrix(...) - 3. ├─base::print(plotly::ggplotly(p)) - 4. ├─plotly::ggplotly(p) - 5. └─plotly:::ggplotly.ggplot(p) - 6. └─plotly::gg2list(...) - - [ FAIL 1 | WARN 4 | SKIP 0 | PASS 7 ] - Error: Test failures - Execution halted - ``` - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘NIMAA-vignette.Rmd’ - ... - - > beatAML_incidence_matrix <- plotIncMatrix(x = beatAML_data, - + index_nominal = c(2, 1), index_numeric = 3, print_skim = FALSE, - + plot_weigh .... [TRUNCATED] - - Na/missing values Proportion: 0.2603 - - When sourcing ‘NIMAA-vignette.R’: - Error: subscript out of bounds - Execution halted - - ‘NIMAA-vignette.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - ... - --- re-building ‘NIMAA-vignette.Rmd’ using rmarkdown - - Quitting from lines 49-57 [plotIncMatrix function] (NIMAA-vignette.Rmd) - Error: processing vignette 'NIMAA-vignette.Rmd' failed with diagnostics: - subscript out of bounds - --- failed re-building ‘NIMAA-vignette.Rmd’ - - SUMMARY: processing the following file failed: - ‘NIMAA-vignette.Rmd’ - - Error: Vignette re-building failed. - Execution halted - ``` - -## In both - -* checking installed package size ... NOTE - ``` - installed size is 6.5Mb - sub-directories of 1Mb or more: - data 2.0Mb - doc 4.0Mb - ``` - -* checking data for non-ASCII characters ... NOTE - ``` - Note: found 24 marked UTF-8 strings - ``` - -# nparACT - -
- -* Version: 0.8 -* GitHub: NA -* Source code: https://github.com/cran/nparACT -* Date/Publication: 2017-12-20 14:25:17 UTC -* Number of recursive dependencies: 31 - -Run `revdepcheck::cloud_details(, "nparACT")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘nparACT-Ex.R’ failed - The error most likely occurred in: - - > ### Name: nparACT-package - > ### Title: Non-Parametric Measures of Actigraphy Data - > ### Aliases: nparACT-package nparACT - > ### Keywords: package - > - > ### ** Examples - > - ... - 1. └─nparACT::nparACT_base("sleepstudy", SR = 4/60) - 2. └─nparACT_auxfunctions2$nparACT_plot_hourly(data, data_hrs, SR) - 3. ├─base::print(p) - 4. └─ggplot2:::print.ggplot(p) - 5. ├─ggplot2::ggplot_gtable(data) - 6. └─ggplot2:::ggplot_gtable.ggplot_built(data) - 7. └─ggplot2::calc_element("plot.margin", theme) - 8. └─cli::cli_abort(...) - 9. └─rlang::abort(...) - Execution halted - ``` - -# nullabor - -
- -* Version: 0.3.9 -* GitHub: https://github.com/dicook/nullabor -* Source code: https://github.com/cran/nullabor -* Date/Publication: 2020-02-25 21:50:02 UTC -* Number of recursive dependencies: 79 - -Run `revdepcheck::cloud_details(, "nullabor")` for more info - -
- -## Newly broken - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘nullabor-examples.Rmd’ - ... - + data = dframe) + scale_colour_manual(values = c("red", "blue"), - + guide = "n ..." ... [TRUNCATED] - Warning: Using `size` aesthetic for lines was deprecated in ggplot2 3.4.0. - ℹ Please use `linewidth` instead. - Warning: Removed 20 rows containing missing values or values outside the scale range - (`geom_rect()`). - - When sourcing ‘nullabor-examples.R’: - Error: Theme element `plot.margin` must have class . - Execution halted - - ‘distances.Rmd’ using ‘UTF-8’... OK - ‘nullabor-examples.Rmd’ using ‘UTF-8’... failed - ‘nullabor.Rmd’ using ‘UTF-8’... OK - ``` - -## In both - -* checking dependencies in R code ... NOTE - ``` - Namespaces in Imports field not imported from: - ‘forecast’ ‘rlang’ ‘tsibble’ ‘viridis’ - All declared Imports should be used. - ``` - -# OBIC - -
- -* Version: 3.0.2 -* GitHub: https://github.com/AgroCares/Open-Bodem-Index-Calculator -* Source code: https://github.com/cran/OBIC -* Date/Publication: 2024-03-05 12:40:08 UTC -* Number of recursive dependencies: 75 - -Run `revdepcheck::cloud_details(, "OBIC")` for more info - -
- -## Newly broken - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘obic_workability.Rmd’ - ... - > gg2 <- ggplot(data = dt, aes(x = field, fill = field)) + - + geom_col(aes(y = I_P_WO)) + theme_bw() + theme(axis.text = element_text(size = 10, - .... [TRUNCATED] - - > (gg | gg2) + plot_layout(guides = "collect") + plot_annotation(caption = "Baseline workability scores.", - + theme = theme(plot.caption = element .... [TRUNCATED] - - When sourcing ‘obic_workability.R’: - Error: object is not a unit - Execution halted - - ‘description-of-the-columns.Rmd’ using ‘UTF-8’... OK - ‘obic_introduction.Rmd’ using ‘UTF-8’... OK - ‘obic_score_aggregation.Rmd’ using ‘UTF-8’... OK - ‘obic_water_functions.Rmd’ using ‘UTF-8’... OK - ‘obic_workability.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘description-of-the-columns.Rmd’ using rmarkdown - --- finished re-building ‘description-of-the-columns.Rmd’ - - --- re-building ‘obic_introduction.Rmd’ using rmarkdown - ``` - -## In both - -* checking installed package size ... NOTE - ``` - installed size is 6.0Mb - sub-directories of 1Mb or more: - data 4.0Mb - doc 1.4Mb - ``` - -# OddsPlotty - -
- -* Version: 1.0.2 -* GitHub: https://github.com/StatsGary/OddsPlotty -* Source code: https://github.com/cran/OddsPlotty -* Date/Publication: 2021-11-13 14:40:02 UTC -* Number of recursive dependencies: 146 - -Run `revdepcheck::cloud_details(, "OddsPlotty")` for more info - -
- -## Newly broken - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘introduction.Rmd’ - ... - > plot <- plotty$odds_plot - - > plot <- plot + ggthemes::theme_economist() + theme(legend.position = "NULL") - - > plot + geom_text(label = round(plotty$odds_plot$data$OR, - + digits = 2), hjust = 0.1, vjust = 1, color = "navy") - - When sourcing ‘introduction.R’: - Error: Theme element `plot.margin` must have class . - Execution halted - - ‘introduction.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘introduction.Rmd’ using rmarkdown - ``` - -## In both - -* checking dependencies in R code ... NOTE - ``` - Namespaces in Imports field not imported from: - ‘caret’ ‘e1071’ ‘ggthemes’ ‘mlbench’ ‘rmarkdown’ ‘tidymodels’ - All declared Imports should be used. - ``` - -# ofpetrial - -
- -* Version: 0.1.1 -* GitHub: https://github.com/DIFM-Brain/ofpetrial -* Source code: https://github.com/cran/ofpetrial -* Date/Publication: 2024-05-15 08:50:03 UTC -* Number of recursive dependencies: 145 - -Run `revdepcheck::cloud_details(, "ofpetrial")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘ofpetrial-Ex.R’ failed - The error most likely occurred in: - - > ### Name: check_ortho_with_chars - > ### Title: Check the orthogonality with field/topographic characteristics - > ### Aliases: check_ortho_with_chars - > - > ### ** Examples - > - > data(td_single_input) - ... - 27. ├─dplyr::bind_rows(.) - 28. │ └─rlang::list2(...) - 29. └─ggExtra::ggMarginal(., type = "histogram") - 30. └─ggplot2::ggplotGrob(scatP) - 31. ├─ggplot2::ggplot_gtable(ggplot_build(x)) - 32. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) - 33. └─ggplot2::calc_element("plot.margin", theme) - 34. └─cli::cli_abort(...) - 35. └─rlang::abort(...) - Execution halted - ``` - -# OmicNavigator - -
- -* Version: 1.13.13 -* GitHub: https://github.com/abbvie-external/OmicNavigator -* Source code: https://github.com/cran/OmicNavigator -* Date/Publication: 2023-08-25 20:40:02 UTC -* Number of recursive dependencies: 86 - -Run `revdepcheck::cloud_details(, "OmicNavigator")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘tinytest.R’ - Running the tests in ‘tests/tinytest.R’ failed. - Complete output: - > # Test files in inst/tinytest/ - > if (requireNamespace("tinytest", quietly = TRUE)) { - + suppressMessages(tinytest::test_package("OmicNavigator")) - + } - - testAdd.R..................... 0 tests - testAdd.R..................... 0 tests - ... - testPlot.R.................... 140 tests OK - testPlot.R.................... 140 tests OK - testPlot.R.................... 141 tests OK - testPlot.R.................... 141 tests OK - testPlot.R.................... 141 tests OK - testPlot.R.................... 142 tests OK - testPlot.R.................... 142 tests OK - testPlot.R.................... 143 tests OK Error in pm[[2]] : subscript out of bounds - Calls: suppressMessages ... plotStudy -> f -> -> ggplotly.ggplot -> gg2list - Execution halted - ``` - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘OmicNavigatorAPI.Rnw’ - ... - "test_02": 0.07 - } - ] - - > resultsUpset <- getResultsUpset(study = "ABC", modelID = "model_01", - + sigValue = 0.5, operator = "<", column = "p_val") - - When sourcing ‘OmicNavigatorAPI.R’: - Error: Theme element `plot.margin` must have class . - Execution halted - - ‘OmicNavigatorAPI.Rnw’ using ‘UTF-8’... failed - ‘OmicNavigatorUsersGuide.Rnw’ using ‘UTF-8’... OK - ``` - -## In both - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘OmicNavigatorAPI.Rnw’ using Sweave - OmicNavigator R package version: 1.13.13 - The app is not installed. Install it with installApp() - Installing study "ABC" in /tmp/RtmpZpDw4T/file231e3ed1b448 - Exporting study "ABC" as an R package - Note: No maintainer email was specified. Using the placeholder: Unknown - Calculating pairwise overlaps. This may take a while... - Exported study to /tmp/RtmpZpDw4T/ONstudyABC - Success! - ... - write - l.14 - - --- failed re-building ‘OmicNavigatorUsersGuide.Rnw’ - - SUMMARY: processing the following files failed: - ‘OmicNavigatorAPI.Rnw’ ‘OmicNavigatorUsersGuide.Rnw’ - - Error: Vignette re-building failed. - Execution halted - ``` - -# oncomsm - -
- -* Version: 0.1.4 -* GitHub: https://github.com/Boehringer-Ingelheim/oncomsm -* Source code: https://github.com/cran/oncomsm -* Date/Publication: 2023-04-17 07:00:02 UTC -* Number of recursive dependencies: 126 - -Run `revdepcheck::cloud_details(, "oncomsm")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(dplyr) - - Attaching package: 'dplyr' - - The following objects are masked from 'package:stats': - - filter, lag - ... - 10. └─grid::unit.c(legend.box.margin[4], widths, legend.box.margin[2]) - 11. └─grid:::identicalUnits(x) - - [ FAIL 1 | WARN 0 | SKIP 2 | PASS 59 ] - Deleting unused snapshots: - • plots/plot-mstate-srp-model-2.svg - • plots/plot-mstate-srp-model-3.svg - • plots/plot-srp-model-2.svg - Error: Test failures - Execution halted - ``` - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘avoiding-bias.Rmd’ - ... - - > mdl <- create_srpmodel(A = define_srp_prior(median_t_q05 = c(1, - + 4, 12), median_t_q95 = c(6, 8, 36), shape_q05 = c(0.99, 0.99, - + 0.99), s .... [TRUNCATED] - - > plot(mdl, confidence = 0.9) - - ... - - > plot(mdl, parameter_sample = smpl_prior, confidence = 0.75) - - When sourcing ‘oncomsm.R’: - Error: object is not a unit - Execution halted - - ‘avoiding-bias.Rmd’ using ‘UTF-8’... failed - ‘oncomsm.Rmd’ using ‘UTF-8’... failed - ‘prior-choice.Rmd’ using ‘UTF-8’... OK - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘avoiding-bias.Rmd’ using rmarkdown - - Quitting from lines 35-46 [unnamed-chunk-2] (avoiding-bias.Rmd) - Error: processing vignette 'avoiding-bias.Rmd' failed with diagnostics: - object is not a unit - --- failed re-building ‘avoiding-bias.Rmd’ - - --- re-building ‘oncomsm.Rmd’ using rmarkdown - - Quitting from lines 211-215 [plotting-the-prior] (oncomsm.Rmd) - Error: processing vignette 'oncomsm.Rmd' failed with diagnostics: - object is not a unit - --- failed re-building ‘oncomsm.Rmd’ - - --- re-building ‘prior-choice.Rmd’ using rmarkdown - ``` - -## In both - -* checking installed package size ... NOTE - ``` - installed size is 59.1Mb - sub-directories of 1Mb or more: - doc 1.1Mb - libs 56.9Mb - ``` - -* checking for GNU extensions in Makefiles ... NOTE - ``` - GNU make is a SystemRequirements. - ``` - -# ontophylo - -
- -* Version: 1.1.3 -* GitHub: https://github.com/diegosasso/ontophylo -* Source code: https://github.com/cran/ontophylo -* Date/Publication: 2024-01-10 10:33:17 UTC -* Number of recursive dependencies: 101 - -Run `revdepcheck::cloud_details(, "ontophylo")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘ontophylo-Ex.R’ failed - The error most likely occurred in: - - > ### Name: edgeplot - > ### Title: Plot edge profiles and contMap - > ### Aliases: edgeplot - > - > ### ** Examples - > - > data("hym_tree", "hym_kde") - ... - 2. │ └─base::withCallingHandlers(...) - 3. └─ontophylo::edgeplot(map_stat, prof_stat) - 4. ├─base::print(plot_edgeprof, vp = vp) - 5. └─ggplot2:::print.ggplot(plot_edgeprof, vp = vp) - 6. ├─ggplot2::ggplot_gtable(data) - 7. └─ggplot2:::ggplot_gtable.ggplot_built(data) - 8. └─ggplot2::calc_element("plot.margin", theme) - 9. └─cli::cli_abort(...) - 10. └─rlang::abort(...) - Execution halted - ``` - -## In both - -* checking installed package size ... NOTE - ``` - installed size is 7.3Mb - sub-directories of 1Mb or more: - data 7.0Mb - ``` - -* checking data for non-ASCII characters ... NOTE - ``` - Note: found 42 marked UTF-8 strings - ``` - -# OpenLand - -
- -* Version: 1.0.3 -* GitHub: https://github.com/reginalexavier/OpenLand -* Source code: https://github.com/cran/OpenLand -* Date/Publication: 2024-05-03 13:40:02 UTC -* Number of recursive dependencies: 119 - -Run `revdepcheck::cloud_details(, "OpenLand")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(OpenLand) - > - > test_check("OpenLand") - [ FAIL 1 | WARN 0 | SKIP 0 | PASS 103 ] - - ══ Failed tests ════════════════════════════════════════════════════════════════ - ... - 9. └─ggplot2 (local) FUN(X[[i]], ...) - 10. ├─ggplot2::ggplot_gtable(ggplot_build(x)) - 11. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) - 12. └─ggplot2::calc_element("plot.margin", theme) - 13. └─cli::cli_abort(...) - 14. └─rlang::abort(...) - - [ FAIL 1 | WARN 0 | SKIP 0 | PASS 103 ] - Error: Test failures - Execution halted - ``` - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘openland_vignette.Rmd’ - ... - - - - > plot(testSL$interval_lvl, labels = c(leftlabel = "Interval Change Area (%)", - + rightlabel = "Annual Change Area (%)"), marginplot = c(-8, - + .... [TRUNCATED] - - When sourcing ‘openland_vignette.R’: - Error: Theme element `plot.margin` must have class . - Execution halted - - ‘openland_vignette.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - ... - --- re-building ‘openland_vignette.Rmd’ using rmarkdown - trying URL 'https://zenodo.org/record/3685230/files/SaoLourencoBasin.rda?download=1' - Content type 'application/octet-stream' length 5309066 bytes (5.1 MB) - ================================================== - downloaded 5.1 MB - - - Quitting from lines 184-191 [unnamed-chunk-10] (openland_vignette.Rmd) - Error: processing vignette 'openland_vignette.Rmd' failed with diagnostics: - Theme element `plot.margin` must have class . - --- failed re-building ‘openland_vignette.Rmd’ - - SUMMARY: processing the following file failed: - ‘openland_vignette.Rmd’ - - Error: Vignette re-building failed. - Execution halted - ``` - -# ordbetareg - -
- -* Version: 0.7.2 -* GitHub: https://github.com/saudiwin/ordbetareg_pack -* Source code: https://github.com/cran/ordbetareg -* Date/Publication: 2023-08-10 07:30:02 UTC -* Number of recursive dependencies: 182 - -Run `revdepcheck::cloud_details(, "ordbetareg")` for more info - -
- -## Newly broken - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘package_introduction.Rmd’ - ... - + theme_minimal() + theme(panel.grid = element_blank()) + scale_x_continuous(brea .... [TRUNCATED] - - > plots <- pp_check_ordbeta(ord_fit_mean, ndraws = 100, - + outcome_label = "Thermometer Rating", new_theme = ggthemes::theme_economist()) - - > plots$discrete - - When sourcing ‘package_introduction.R’: - Error: Theme element `plot.margin` must have class . - Execution halted - - ‘package_introduction.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘package_introduction.Rmd’ using rmarkdown - ``` - -## In both - -* checking installed package size ... NOTE - ``` - installed size is 8.1Mb - sub-directories of 1Mb or more: - data 7.5Mb - ``` - -* checking data for non-ASCII characters ... NOTE - ``` - Note: found 36 marked UTF-8 strings - ``` - -# otsad - -
- -* Version: 0.2.0 -* GitHub: https://github.com/alaineiturria/otsad -* Source code: https://github.com/cran/otsad -* Date/Publication: 2019-09-06 09:50:02 UTC -* Number of recursive dependencies: 109 - -Run `revdepcheck::cloud_details(, "otsad")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘otsad-Ex.R’ failed - The error most likely occurred in: - - > ### Name: CpKnnCad - > ### Title: Classic processing KNN based Conformal Anomaly Detector - > ### (KNN-CAD) - > ### Aliases: CpKnnCad - > - > ### ** Examples - > - ... - + ncm.type = "ICAD", - + reducefp = TRUE - + ) - > - > ## Plot results - > res <- cbind(df, result) - > PlotDetections(res, title = "KNN-CAD ANOMALY DETECTOR") - Error in pm[[2]] : subscript out of bounds - Calls: PlotDetections -> -> ggplotly.ggplot -> gg2list - Execution halted - ``` - -## In both - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - ... - --- re-building ‘otsad.Rnw’ using knitr - Error: processing vignette 'otsad.Rnw' failed with diagnostics: - Running 'texi2dvi' on 'otsad.tex' failed. - LaTeX errors: - ! LaTeX Error: File `colortbl.sty' not found. - - Type X to quit or to proceed, - or enter new name. (Default extension: sty) - ... - l.12 \makeatletter - ^^M - ! ==> Fatal error occurred, no output PDF file produced! - --- failed re-building ‘otsad.Rnw’ - - SUMMARY: processing the following file failed: - ‘otsad.Rnw’ - - Error: Vignette re-building failed. - Execution halted - ``` - -# OutliersO3 - -
- -* Version: 0.6.3 -* GitHub: NA -* Source code: https://github.com/cran/OutliersO3 -* Date/Publication: 2020-04-25 00:10:02 UTC -* Number of recursive dependencies: 145 - -Run `revdepcheck::cloud_details(, "OutliersO3")` for more info - -
- -## Newly broken - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘DrawingO3plots.Rmd’ - ... - > O3s <- O3prep(data, method = "HDo", tols = 0.05, boxplotLimits = 6) - - > O3s1 <- O3plotT(O3s, caseNames = Election2005$Name) - - > O3s1$gO3 + theme(plot.margin = unit(c(0, 2, 0, 0), - + "cm")) - - ... - + 1, 0, 0), "cm")), O3r1$gpcp, ncol = 1, heights = c(2, 1)) - - When sourcing ‘MultTolLevels.R’: - Error: Theme element `plot.margin` must have class . - Execution halted - - ‘DrawingO3plots.Rmd’ using ‘UTF-8’... failed - ‘MultTolLevels.Rmd’ using ‘UTF-8’... failed - ‘PCPsO3.Rmd’ using ‘UTF-8’... OK - ‘xtraO3methods.Rmd’ using ‘UTF-8’... OK - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘DrawingO3plots.Rmd’ using rmarkdown - - Quitting from lines 25-32 [unnamed-chunk-1] (DrawingO3plots.Rmd) - Error: processing vignette 'DrawingO3plots.Rmd' failed with diagnostics: - Theme element `plot.margin` must have class . - --- failed re-building ‘DrawingO3plots.Rmd’ - - --- re-building ‘MultTolLevels.Rmd’ using rmarkdown - ``` - -# palettes - -
- -* Version: 0.2.0 -* GitHub: https://github.com/mccarthy-m-g/palettes -* Source code: https://github.com/cran/palettes -* Date/Publication: 2024-02-05 11:50:02 UTC -* Number of recursive dependencies: 110 - -Run `revdepcheck::cloud_details(, "palettes")` for more info - -
- -## Newly broken - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘biscale.Rmd’ - ... - + "2-2") - - > names(unnamed_colour_vector) - [1] "1-1" "2-1" "1-2" "2-2" - - > bi_pal(named_colour_vector, dim = 2) - - ... - When sourcing ‘biscale.R’: - Error: Theme element `plot.margin` must have class . - Execution halted - - ‘biscale.Rmd’ using ‘UTF-8’... failed - ‘compatibility.Rmd’ using ‘UTF-8’... OK - ‘creating-packages.Rmd’ using ‘UTF-8’... OK - ‘ggplot2.Rmd’ using ‘UTF-8’... OK - ‘gt.Rmd’ using ‘UTF-8’... OK - ‘palettes.Rmd’ using ‘UTF-8’... OK - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘biscale.Rmd’ using rmarkdown - - Quitting from lines 66-67 [unnamed-chunk-4] (biscale.Rmd) - Error: processing vignette 'biscale.Rmd' failed with diagnostics: - Theme element `plot.margin` must have class . - --- failed re-building ‘biscale.Rmd’ - - --- re-building ‘compatibility.Rmd’ using rmarkdown - --- finished re-building ‘compatibility.Rmd’ - - --- re-building ‘creating-packages.Rmd’ using rmarkdown - --- finished re-building ‘creating-packages.Rmd’ - - --- re-building ‘ggplot2.Rmd’ using rmarkdown - ``` - -# ParBayesianOptimization - -
- -* Version: 1.2.6 -* GitHub: https://github.com/AnotherSamWilson/ParBayesianOptimization -* Source code: https://github.com/cran/ParBayesianOptimization -* Date/Publication: 2022-10-18 14:47:54 UTC -* Number of recursive dependencies: 107 - -Run `revdepcheck::cloud_details(, "ParBayesianOptimization")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘ParBayesianOptimization-Ex.R’ failed - The error most likely occurred in: - - > ### Name: plot.bayesOpt - > ### Title: Plot a 'bayesOpt' object - > ### Aliases: plot.bayesOpt - > - > ### ** Examples - > - > scoringFunction <- function(x) { - ... - 3. └─ParBayesianOptimization:::plot.bayesOpt(Results) - 4. └─ggpubr::ggarrange(...) - 5. └─ggpubr::get_legend(plots) - 6. └─ggpubr:::.get_legend(p[[i]], position = position) - 7. ├─ggplot2::ggplot_gtable(ggplot_build(p)) - 8. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(p)) - 9. └─ggplot2::calc_element("plot.margin", theme) - 10. └─cli::cli_abort(...) - 11. └─rlang::abort(...) - Execution halted - ``` - -# patchwork - -
- -* Version: 1.2.0 -* GitHub: https://github.com/thomasp85/patchwork -* Source code: https://github.com/cran/patchwork -* Date/Publication: 2024-01-08 14:40:02 UTC -* Number of recursive dependencies: 80 - -Run `revdepcheck::cloud_details(, "patchwork")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘patchwork-Ex.R’ failed - The error most likely occurred in: - - > ### Name: free - > ### Title: Free a plot from alignment - > ### Aliases: free - > - > ### ** Examples - > - > # Sometimes you have a plot that defies good composition alginment, e.g. due - ... - > p1 / p2 - > - > # We can fix this be using free - > free(p1) / p2 - > - > # We can still collect guides like before - > free(p1) / p2 + plot_layout(guides = "collect") - Error in identicalUnits(x) : object is not a unit - Calls: ... assemble_guides -> guides_build -> unit.c -> identicalUnits - Execution halted - ``` - -# pathfindR - -
- -* Version: 2.4.1 -* GitHub: https://github.com/egeulgen/pathfindR -* Source code: https://github.com/cran/pathfindR -* Date/Publication: 2024-05-04 15:30:05 UTC -* Number of recursive dependencies: 150 - -Run `revdepcheck::cloud_details(, "pathfindR")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘pathfindR-Ex.R’ failed - The error most likely occurred in: - - > ### Name: UpSet_plot - > ### Title: Create UpSet Plot of Enriched Terms - > ### Aliases: UpSet_plot - > - > ### ** Examples - > - > UpSet_plot(example_pathfindR_output) - ... - 9. └─ggplot2:::scale_apply(layer_data, x_vars, "map", SCALE_X, self$panel_scales_x) - 10. └─base::lapply(...) - 11. └─ggplot2 (local) FUN(X[[i]], ...) - 12. └─base::lapply(...) - 13. └─ggplot2 (local) FUN(X[[i]], ...) - 14. └─scales[[i]][[method]](data[[var]][scale_index[[i]]]) - 15. └─ggplot2 (local) map(..., self = self) - 16. └─cli::cli_abort(...) - 17. └─rlang::abort(...) - Execution halted - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘comparing_results.Rmd’ using rmarkdown - ``` - -## In both - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘intro_vignette.Rmd’ - ... - - - - > output_df <- run_pathfindR(example_pathfindR_input, - + pin_name_path = "/path/to/myPIN.sif") - - When sourcing ‘intro_vignette.R’: - ... - When sourcing ‘visualization_vignette.R’: - Error: The `palette` function must return at least 21 values. - Execution halted - - ‘comparing_results.Rmd’ using ‘UTF-8’... OK - ‘intro_vignette.Rmd’ using ‘UTF-8’... failed - ‘manual_execution.Rmd’ using ‘UTF-8’... failed - ‘non_hs_analysis.Rmd’ using ‘UTF-8’... failed - ‘obtain_data.Rmd’ using ‘UTF-8’... failed - ‘visualization_vignette.Rmd’ using ‘UTF-8’... failed - ``` - -# pdSpecEst - -
- -* Version: 1.2.4 -* GitHub: https://github.com/JorisChau/pdSpecEst -* Source code: https://github.com/cran/pdSpecEst -* Date/Publication: 2020-01-08 09:10:07 UTC -* Number of recursive dependencies: 88 - -Run `revdepcheck::cloud_details(, "pdSpecEst")` for more info - -
- -## Newly broken - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘wavelet_est_clust.Rmd’ - ... - Warning: Use of `longdata$Var1` is discouraged. - ℹ Use `Var1` instead. - Warning: Use of `longdata$Var2` is discouraged. - ℹ Use `Var2` instead. - Warning: Use of `longdata$value` is discouraged. - ℹ Use `value` instead. - - When sourcing ‘wavelet_est_clust.R’: - Error: Theme element `plot.margin` must have class . - Execution halted - - ‘depth_ranktests.Rmd’ using ‘UTF-8’... OK - ‘wavelet_est_clust.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘depth_ranktests.Rmd’ using rmarkdown - - warning: logmat_sympd(): imaginary components on diagonal are non-zero - - warning: logmat_sympd(): given matrix is not hermitian - --- finished re-building ‘depth_ranktests.Rmd’ - - --- re-building ‘wavelet_est_clust.Rmd’ using rmarkdown - ``` - -## In both - -* checking C++ specification ... NOTE - ``` - Specified C++11: please drop specification unless essential - ``` - -* checking installed package size ... NOTE - ``` - installed size is 9.1Mb - sub-directories of 1Mb or more: - libs 8.0Mb - ``` - -* checking LazyData ... NOTE - ``` - 'LazyData' is specified without a 'data' directory - ``` - -# pdxTrees - -
- -* Version: 0.4.0 -* GitHub: https://github.com/mcconvil/pdxTrees -* Source code: https://github.com/cran/pdxTrees -* Date/Publication: 2020-08-17 14:00:02 UTC -* Number of recursive dependencies: 105 - -Run `revdepcheck::cloud_details(, "pdxTrees")` for more info - -
- -## Newly broken - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘pdxTrees-vignette.Rmd’ - ... - + y = Pollution_Removal_value, color = Mature_Size)) + geom_point(size = 2, - + .... [TRUNCATED] - - > berkeley_graph + transition_states(states = Mature_Size, - + transition_length = 10, state_length = 8) + enter_grow() + - + exit_shrink() - - When sourcing ‘pdxTrees-vignette.R’: - Error: argument "theme" is missing, with no default - Execution halted - - ‘pdxTrees-vignette.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘pdxTrees-vignette.Rmd’ using rmarkdown - ``` - -## In both - -* checking LazyData ... NOTE - ``` - 'LazyData' is specified without a 'data' directory - ``` - -# personalized - -
- -* Version: 0.2.7 -* GitHub: https://github.com/jaredhuling/personalized -* Source code: https://github.com/cran/personalized -* Date/Publication: 2022-06-27 20:20:03 UTC -* Number of recursive dependencies: 94 - -Run `revdepcheck::cloud_details(, "personalized")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > Sys.setenv("R_TESTS" = "") - > library(testthat) - > library(personalized) - Loading required package: glmnet - Loading required package: Matrix - Loaded glmnet 4.1-8 - Loading required package: mgcv - ... - 4. └─personalized:::plot.subgroup_validated(subgrp.val, type = "stability") - 5. ├─plotly::subplot(...) - 6. │ └─plotly:::dots2plots(...) - 7. ├─plotly::ggplotly(p.primary, tooltip = paste0("tooltip", 1:4)) - 8. └─plotly:::ggplotly.ggplot(...) - 9. └─plotly::gg2list(...) - - [ FAIL 1 | WARN 2 | SKIP 0 | PASS 215 ] - Error: Test failures - Execution halted - ``` - -# PGRdup - -
- -* Version: 0.2.3.9 -* GitHub: https://github.com/aravind-j/PGRdup -* Source code: https://github.com/cran/PGRdup -* Date/Publication: 2023-08-31 22:10:16 UTC -* Number of recursive dependencies: 69 - -Run `revdepcheck::cloud_details(, "PGRdup")` for more info - -
- -## Newly broken - -* checking re-building of vignette outputs ... ERROR - ``` - Error(s) in re-building vignettes: - ... - --- re-building ‘Introduction.Rmd’ using rmarkdown_notangle - - Quitting from lines 1195-1203 [unnamed-chunk-59] (Introduction.Rmd) - Error: processing vignette 'Introduction.Rmd' failed with diagnostics: - Theme element `plot.margin` must have class . - --- failed re-building ‘Introduction.Rmd’ - - SUMMARY: processing the following file failed: - ‘Introduction.Rmd’ - - Error: Vignette re-building failed. - Execution halted - ``` - -## Newly fixed - -* checking re-building of vignette outputs ... WARNING - ``` - Error(s) in re-building vignettes: - --- re-building ‘Introduction.Rmd’ using rmarkdown_notangle - tlmgr: package repository https://mirrors.rit.edu/CTAN/systems/texlive/tlnet (verified) - [1/1, ??:??/??:??] install: colortbl [4k] - running mktexlsr ... - done running mktexlsr. - tlmgr: package log updated: /opt/TinyTeX/texmf-var/web2c/tlmgr.log - tlmgr: command log updated: /opt/TinyTeX/texmf-var/web2c/tlmgr-commands.log - - tlmgr: Remote database (revision 71410 of the texlive-scripts package) - ... - - Error: processing vignette 'Introduction.Rmd' failed with diagnostics: - LaTeX failed to compile /tmp/workdir/PGRdup/old/PGRdup.Rcheck/vign_test/PGRdup/vignettes/Introduction.tex. See https://yihui.org/tinytex/r/#debugging for debugging tips. See Introduction.log for more info. - --- failed re-building ‘Introduction.Rmd’ - - SUMMARY: processing the following file failed: - ‘Introduction.Rmd’ - - Error: Vignette re-building failed. - Execution halted - ``` - -# Plasmidprofiler - -
- -* Version: 0.1.6 -* GitHub: NA -* Source code: https://github.com/cran/Plasmidprofiler -* Date/Publication: 2017-01-06 01:10:47 -* Number of recursive dependencies: 90 - -Run `revdepcheck::cloud_details(, "Plasmidprofiler")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘Plasmidprofiler-Ex.R’ failed - The error most likely occurred in: - - > ### Name: main - > ### Title: Main: Run everything - > ### Aliases: main - > - > ### ** Examples - > - > main(blastdata, - ... - Saving 12 x 7 in image - Warning: Vectorized input to `element_text()` is not officially supported. - ℹ Results may be unexpected or may change in future versions of ggplot2. - Warning in geom_tile(aes(x = Plasmid, y = Sample, label = AMR_gene, fill = Inc_group, : - Ignoring unknown aesthetics: label and text - Warning: Use of `report$Sureness` is discouraged. - ℹ Use `Sureness` instead. - Error in pm[[2]] : subscript out of bounds - Calls: main ... -> ggplotly -> ggplotly.ggplot -> gg2list - Execution halted - ``` - -# plotDK - -
- -* Version: 0.1.0 -* GitHub: NA -* Source code: https://github.com/cran/plotDK -* Date/Publication: 2021-10-01 08:00:02 UTC -* Number of recursive dependencies: 86 - -Run `revdepcheck::cloud_details(, "plotDK")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(plotDK) - > - > test_check("plotDK") - [ FAIL 1 | WARN 0 | SKIP 0 | PASS 49 ] - - ══ Failed tests ════════════════════════════════════════════════════════════════ - ... - Backtrace: - ▆ - 1. └─plotDK::plotDK(...) at test-plotDK.R:32:5 - 2. ├─plotly::ggplotly(p, tooltip = c("text", "fill")) - 3. └─plotly:::ggplotly.ggplot(p, tooltip = c("text", "fill")) - 4. └─plotly::gg2list(...) - - [ FAIL 1 | WARN 0 | SKIP 0 | PASS 49 ] - Error: Test failures - Execution halted - ``` - -## In both - -* checking dependencies in R code ... NOTE - ``` - Namespace in Imports field not imported from: ‘mapproj’ - All declared Imports should be used. - ``` - -* checking data for non-ASCII characters ... NOTE - ``` - Note: found 12992 marked UTF-8 strings - ``` - -# plotly - -
- -* Version: 4.10.4 -* GitHub: https://github.com/plotly/plotly.R -* Source code: https://github.com/cran/plotly -* Date/Publication: 2024-01-13 22:40:02 UTC -* Number of recursive dependencies: 147 - -Run `revdepcheck::cloud_details(, "plotly")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘plotly-Ex.R’ failed - The error most likely occurred in: - - > ### Name: style - > ### Title: Modify trace(s) - > ### Aliases: style - > - > ### ** Examples - > - > ## Don't show: - ... - + # this clobbers the previously supplied marker.line.color - + style(p, marker.line = list(width = 2.5), marker.size = 10) - + ## Don't show: - + }) # examplesIf - > (p <- ggplotly(qplot(data = mtcars, wt, mpg, geom = c("point", "smooth")))) - Warning: `qplot()` was deprecated in ggplot2 3.4.0. - `geom_smooth()` using method = 'loess' and formula = 'y ~ x' - Error in pm[[2]] : subscript out of bounds - Calls: ... eval -> eval -> ggplotly -> ggplotly.ggplot -> gg2list - Execution halted - ``` - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library("testthat") - > library("plotly") - Loading required package: ggplot2 - - Attaching package: 'plotly' - - The following object is masked from 'package:ggplot2': - ... - • plotly-subplot/subplot-bump-axis-annotation.svg - • plotly-subplot/subplot-bump-axis-image.svg - • plotly-subplot/subplot-bump-axis-shape-shared.svg - • plotly-subplot/subplot-bump-axis-shape.svg - • plotly-subplot/subplot-reposition-annotation.svg - • plotly-subplot/subplot-reposition-image.svg - • plotly-subplot/subplot-reposition-shape-fixed.svg - • plotly-subplot/subplot-reposition-shape.svg - Error: Test failures - Execution halted - ``` - -## In both - -* checking installed package size ... NOTE - ``` - installed size is 7.1Mb - sub-directories of 1Mb or more: - R 1.0Mb - htmlwidgets 4.0Mb - ``` - -# pmartR - -
- -* Version: 2.4.5 -* GitHub: https://github.com/pmartR/pmartR -* Source code: https://github.com/cran/pmartR -* Date/Publication: 2024-05-21 15:50:02 UTC -* Number of recursive dependencies: 149 - -Run `revdepcheck::cloud_details(, "pmartR")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(pmartR) - > - > test_check("pmartR") - [ FAIL 1 | WARN 1 | SKIP 11 | PASS 2375 ] - - ══ Skipped tests (11) ══════════════════════════════════════════════════════════ - ... - • plots/plot-spansres-color-high-color-low.svg - • plots/plot-spansres.svg - • plots/plot-statres-anova-volcano.svg - • plots/plot-statres-anova.svg - • plots/plot-statres-combined-volcano.svg - • plots/plot-statres-combined.svg - • plots/plot-statres-gtest.svg - • plots/plot-totalcountfilt.svg - Error: Test failures - Execution halted - ``` - -## In both - -* checking installed package size ... NOTE - ``` - installed size is 10.4Mb - sub-directories of 1Mb or more: - R 1.5Mb - help 1.5Mb - libs 6.3Mb - ``` - -# pmxTools - -
- -* Version: 1.3 -* GitHub: https://github.com/kestrel99/pmxTools -* Source code: https://github.com/cran/pmxTools -* Date/Publication: 2023-02-21 16:00:08 UTC -* Number of recursive dependencies: 85 - -Run `revdepcheck::cloud_details(, "pmxTools")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(pmxTools) - Loading required package: patchwork - > - > test_check("pmxTools") - [ FAIL 1 | WARN 1 | SKIP 12 | PASS 110 ] - - ... - 24. └─handlers[[1L]](cnd) - 25. └─cli::cli_abort(...) - 26. └─rlang::abort(...) - - [ FAIL 1 | WARN 1 | SKIP 12 | PASS 110 ] - Deleting unused snapshots: - • plot/conditioned-distplot.svg - • plot/perc.svg - Error: Test failures - Execution halted - ``` - -## In both - -* checking Rd cross-references ... NOTE - ``` - Package unavailable to check Rd xrefs: ‘DiagrammeR’ - ``` - -# politeness - -
- -* Version: 0.9.3 -* GitHub: NA -* Source code: https://github.com/cran/politeness -* Date/Publication: 2023-11-12 13:13:26 UTC -* Number of recursive dependencies: 93 - -Run `revdepcheck::cloud_details(, "politeness")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘politeness-Ex.R’ failed - The error most likely occurred in: - - > ### Name: politenessPlot - > ### Title: Politeness plot - > ### Aliases: politenessPlot - > - > ### ** Examples - > - > - ... - Backtrace: - ▆ - 1. ├─base (local) ``(x) - 2. └─ggplot2:::print.ggplot(x) - 3. ├─ggplot2::ggplot_gtable(data) - 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) - 5. └─ggplot2::calc_element("plot.margin", theme) - 6. └─cli::cli_abort(...) - 7. └─rlang::abort(...) - Execution halted - ``` - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘politeness.Rmd’ - ... - 28 0 0 0 0 0 - 29 0 1 0 0 0 - 30 0 1 0 1 0 - - > politeness::politenessPlot(df_politeness, split = phone_offers$condition, - + split_levels = c("Tough", "Warm"), split_name = "Condition") - - When sourcing ‘politeness.R’: - Error: Theme element `plot.margin` must have class . - Execution halted - - ‘politeness.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - ... - --- re-building ‘politeness.Rmd’ using rmarkdown - - Quitting from lines 119-123 [unnamed-chunk-8] (politeness.Rmd) - Error: processing vignette 'politeness.Rmd' failed with diagnostics: - Theme element `plot.margin` must have class . - --- failed re-building ‘politeness.Rmd’ - - SUMMARY: processing the following file failed: - ‘politeness.Rmd’ - - Error: Vignette re-building failed. - Execution halted - ``` - -## In both - -* checking data for non-ASCII characters ... NOTE - ``` - Note: found 52 marked UTF-8 strings - ``` - -# posterior - -
- -* Version: 1.5.0 -* GitHub: https://github.com/stan-dev/posterior -* Source code: https://github.com/cran/posterior -* Date/Publication: 2023-10-31 08:30:02 UTC -* Number of recursive dependencies: 120 - -Run `revdepcheck::cloud_details(, "posterior")` for more info - -
- -## Newly broken - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - ... - --- re-building ‘posterior.Rmd’ using rmarkdown - --- finished re-building ‘posterior.Rmd’ - - --- re-building ‘rvar.Rmd’ using rmarkdown - - Quitting from lines 526-529 [mixture] (rvar.Rmd) - Error: processing vignette 'rvar.Rmd' failed with diagnostics: - Problem while setting up geom aesthetics. - ... - NULL, NULL, 1.2, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 0.2, NULL, list(NULL, NULL, NULL, 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, NULL, NULL, NULL, TRUE), NULL, "right", NULL, NULL, NULL, "center", NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 0, list(), 2, list("grey92", NA, NULL, NULL, TRUE), list(), NULL, NULL, NULL, list("white", NULL, NULL, NULL, FALSE, "white", TRUE), NULL, list(NULL, 0.5, NULL, NULL, FALSE, NULL, TRUE), NULL, - NULL, NULL, NULL, FALSE, list(NULL, "white", NULL, NULL, TRUE), list(NULL, NULL, NULL, 1.2, 0, 1, NULL, NULL, c(0, 0, 5.5, 0), NULL, TRUE), "panel", list(NULL, NULL, NULL, NULL, 0, 1, NULL, NULL, c(0, 0, 5.5, 0), NULL, TRUE), list(NULL, NULL, NULL, 0.8, 1, 1, NULL, NULL, c(5.5, 0, 0, 0), NULL, TRUE), "panel", list(NULL, NULL, NULL, 1.2, 0.5, 0.5, NULL, NULL, NULL, NULL, TRUE), "topleft", NULL, NULL, list("grey85", NA, NULL, NULL, TRUE), NULL, NULL, "inherit", "inside", list(NULL, NULL, "grey10", - 0.8, NULL, NULL, NULL, NULL, c(4.4, 4.4, 4.4, 4.4), NULL, TRUE), NULL, NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, NULL, -90, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, NULL, 90, NULL, NULL, NULL, TRUE), NULL, 2.75, 2.75)) - --- failed re-building ‘rvar.Rmd’ - - SUMMARY: processing the following file failed: - ‘rvar.Rmd’ - - Error: Vignette re-building failed. - Execution halted - ``` - -## In both - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘rvar.Rmd’ - ... - > y - rvar<4000>[3] mean ± sd: - [1] 3.00 ± 1.00 2.02 ± 0.99 0.96 ± 0.99 - - > X + y - - When sourcing ‘rvar.R’: - Error: Cannot broadcast array of shape [4000,3,1] to array of shape [4000,4,3]: - All dimensions must be 1 or equal. - Execution halted - - ‘posterior.Rmd’ using ‘UTF-8’... OK - ‘rvar.Rmd’ using ‘UTF-8’... failed - ``` - -# PPQplan - -
- -* Version: 1.1.0 -* GitHub: https://github.com/allenzhuaz/PPQplan -* Source code: https://github.com/cran/PPQplan -* Date/Publication: 2020-10-08 04:30:06 UTC -* Number of recursive dependencies: 119 - -Run `revdepcheck::cloud_details(, "PPQplan")` for more info - -
- -## Newly broken - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘PPQnote.Rmd’ using rmarkdown - --- finished re-building ‘PPQnote.Rmd’ - - --- re-building ‘PPQplan-vignette.Rmd’ using rmarkdown - ``` - -## In both - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘PPQplan-vignette.Rmd’ - ... - - > devtools::load_all() - - When sourcing ‘PPQplan-vignette.R’: - Error: Could not find a root 'DESCRIPTION' file that starts with '^Package' in - '/tmp/RtmpklfDYr/file150247a66b97/vignettes'. - ℹ Are you in your project directory and does your project have a 'DESCRIPTION' - file? - Execution halted - - ‘PPQnote.Rmd’ using ‘UTF-8’... OK - ‘PPQplan-vignette.Rmd’ using ‘UTF-8’... failed - ``` - -* checking installed package size ... NOTE - ``` - installed size is 12.1Mb - sub-directories of 1Mb or more: - doc 12.0Mb - ``` - -* checking LazyData ... NOTE - ``` - 'LazyData' is specified without a 'data' directory - ``` - -# ppseq - -
- -* Version: 0.2.4 -* GitHub: https://github.com/zabore/ppseq -* Source code: https://github.com/cran/ppseq -* Date/Publication: 2024-04-04 18:20:02 UTC -* Number of recursive dependencies: 106 - -Run `revdepcheck::cloud_details(, "ppseq")` for more info - -
- -## Newly broken - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘one_sample_expansion.Rmd’ - ... - - - - - > ptest <- plot(one_sample_cal_tbl, type1_range = c(0.05, - + 0.1), minimum_power = 0.7, plotly = TRUE) - - ... - - > ptest <- plot(two_sample_cal_tbl, type1_range = c(0.05, - + 0.1), minimum_power = 0.7, plotly = TRUE) - - When sourcing ‘two_sample_randomized.R’: - Error: subscript out of bounds - Execution halted - - ‘one_sample_expansion.Rmd’ using ‘UTF-8’... failed - ‘two_sample_randomized.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - ... - --- re-building ‘one_sample_expansion.Rmd’ using rmarkdown - - Quitting from lines 183-188 [unnamed-chunk-13] (one_sample_expansion.Rmd) - Error: processing vignette 'one_sample_expansion.Rmd' failed with diagnostics: - subscript out of bounds - --- failed re-building ‘one_sample_expansion.Rmd’ - - --- re-building ‘two_sample_randomized.Rmd’ using rmarkdown - ... - Quitting from lines 179-184 [unnamed-chunk-13] (two_sample_randomized.Rmd) - Error: processing vignette 'two_sample_randomized.Rmd' failed with diagnostics: - subscript out of bounds - --- failed re-building ‘two_sample_randomized.Rmd’ - - SUMMARY: processing the following files failed: - ‘one_sample_expansion.Rmd’ ‘two_sample_randomized.Rmd’ - - Error: Vignette re-building failed. - Execution halted - ``` - -## In both - -* checking installed package size ... NOTE - ``` - installed size is 11.0Mb - sub-directories of 1Mb or more: - doc 10.5Mb - ``` - -# PPtreeregViz - -
- -* Version: 2.0.5 -* GitHub: https://github.com/sunsmiling/PPtreeregViz -* Source code: https://github.com/cran/PPtreeregViz -* Date/Publication: 2022-12-23 19:20:05 UTC -* Number of recursive dependencies: 125 - -Run `revdepcheck::cloud_details(, "PPtreeregViz")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘PPtreeregViz-Ex.R’ failed - The error most likely occurred in: - - > ### Name: PPregNodeViz - > ### Title: Node visualization - > ### Aliases: PPregNodeViz - > ### Keywords: tree - > - > ### ** Examples - > - ... - ▆ - 1. └─PPtreeregViz::PPregNodeViz(Model, node.id = 1) - 2. └─ggExtra::ggMarginal(...) - 3. └─ggplot2::ggplotGrob(scatP) - 4. ├─ggplot2::ggplot_gtable(ggplot_build(x)) - 5. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) - 6. └─ggplot2::calc_element("plot.margin", theme) - 7. └─cli::cli_abort(...) - 8. └─rlang::abort(...) - Execution halted - ``` - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘PPtreeregViz.Rmd’ - ... - - > plot(Tree.Imp) - - > plot(Tree.Imp, marginal = TRUE, num_var = 5) - - > PPregNodeViz(Model, node.id = 1) - - When sourcing ‘PPtreeregViz.R’: - Error: Theme element `plot.margin` must have class . - Execution halted - - ‘PPtreeregViz.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘PPtreeregViz.Rmd’ using rmarkdown - ``` - -## In both - -* checking C++ specification ... NOTE - ``` - Specified C++11: please drop specification unless essential - ``` - -# precrec - -
- -* Version: 0.14.4 -* GitHub: https://github.com/evalclass/precrec -* Source code: https://github.com/cran/precrec -* Date/Publication: 2023-10-11 22:10:02 UTC -* Number of recursive dependencies: 71 - -Run `revdepcheck::cloud_details(, "precrec")` for more info - -
- -## Newly broken - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘introduction.Rmd’ - ... - > msmdat3 <- mmdata(samps2[["scores"]], samps2[["labels"]], - + modnames = samps2[["modnames"]]) - - > mscurves <- evalmod(msmdat3) - - > autoplot(mscurves) - - When sourcing ‘introduction.R’: - Error: object is not a unit - Execution halted - - ‘introduction.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘introduction.Rmd’ using rmarkdown - ``` - -## In both - -* checking installed package size ... NOTE - ``` - installed size is 6.5Mb - sub-directories of 1Mb or more: - libs 4.2Mb - ``` - -# prevR - -
- -* Version: 5.0.0 -* GitHub: https://github.com/larmarange/prevR -* Source code: https://github.com/cran/prevR -* Date/Publication: 2023-05-15 18:50:03 UTC -* Number of recursive dependencies: 82 - -Run `revdepcheck::cloud_details(, "prevR")` for more info - -
- -## Newly broken - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘intro_prevR.Rmd’ - ... - > plot(dhs, axes = TRUE) - - > qa <- quick.prevR(fdhs, return.results = TRUE, return.plot = TRUE, - + plot.results = FALSE, progression = FALSE) - - > qa$plot - - When sourcing ‘intro_prevR.R’: - Error: Theme element `plot.margin` must have class . - Execution halted - - ‘intro_prevR.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘intro_prevR.Rmd’ using rmarkdown - ``` - -## In both - -* checking installed package size ... NOTE - ``` - installed size is 8.4Mb - sub-directories of 1Mb or more: - data 7.5Mb - ``` - -# primerTree - -
- -* Version: 1.0.6 -* GitHub: NA -* Source code: https://github.com/cran/primerTree -* Date/Publication: 2022-04-05 14:30:02 UTC -* Number of recursive dependencies: 53 - -Run `revdepcheck::cloud_details(, "primerTree")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘primerTree-Ex.R’ failed - The error most likely occurred in: - - > ### Name: plot.primerTree - > ### Title: plot function for a primerTree object, calls plot_tree_ranks - > ### Aliases: plot.primerTree - > - > ### ** Examples - > - > library(gridExtra) - ... - 4. ├─base::do.call(arrangeGrob, plots) - 5. └─gridExtra (local) ``(...) - 6. └─base::lapply(grobs[toconv], ggplot2::ggplotGrob) - 7. └─ggplot2 (local) FUN(X[[i]], ...) - 8. ├─ggplot2::ggplot_gtable(ggplot_build(x)) - 9. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) - 10. └─ggplot2::calc_element("plot.margin", theme) - 11. └─cli::cli_abort(...) - 12. └─rlang::abort(...) - Execution halted - ``` - -# processmapR - -
- -* Version: 0.5.3 -* GitHub: https://github.com/bupaverse/processmapr -* Source code: https://github.com/cran/processmapR -* Date/Publication: 2023-04-06 12:50:02 UTC -* Number of recursive dependencies: 118 - -Run `revdepcheck::cloud_details(, "processmapR")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(processmapR) - - Attaching package: 'processmapR' - - The following object is masked from 'package:stats': - - ... - 10. └─processmapR:::return_plotly(p, plotly) - 11. ├─plotly::ggplotly(p) - 12. └─plotly:::ggplotly.ggplot(p) - 13. └─plotly::gg2list(...) - ── Failure ('test_trace_explorer.R:240:3'): test trace_explorer on eventlog with param `plotly` ── - `chart` inherits from 'gg'/'ggplot' not 'plotly'. - - [ FAIL 6 | WARN 0 | SKIP 10 | PASS 107 ] - Error: Test failures - Execution halted - ``` - -# PTXQC - -
- -* Version: 1.1.1 -* GitHub: https://github.com/cbielow/PTXQC -* Source code: https://github.com/cran/PTXQC -* Date/Publication: 2024-03-11 19:50:02 UTC -* Number of recursive dependencies: 97 - -Run `revdepcheck::cloud_details(, "PTXQC")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(PTXQC) - Loading package PTXQC (version 1.1.1) - > - > ## - > ## calls all code in PTXQC/tests/testthat/test*.R - > ## - ... - 8. └─ggplot2::ggplotGrob(Main_bar_plot) - 9. ├─ggplot2::ggplot_gtable(ggplot_build(x)) - 10. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) - 11. └─ggplot2::calc_element("plot.margin", theme) - 12. └─cli::cli_abort(...) - 13. └─rlang::abort(...) - - [ FAIL 1 | WARN 20 | SKIP 0 | PASS 131 ] - Error: Test failures - Execution halted - ``` - -## In both - -* checking installed package size ... NOTE - ``` - installed size is 8.5Mb - sub-directories of 1Mb or more: - R 1.5Mb - doc 4.0Mb - examples 2.6Mb - ``` - -# qacBase - -
- -* Version: 1.0.3 -* GitHub: https://github.com/rkabacoff/qacBase -* Source code: https://github.com/cran/qacBase -* Date/Publication: 2022-02-09 22:20:02 UTC -* Number of recursive dependencies: 99 - -Run `revdepcheck::cloud_details(, "qacBase")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘qacBase-Ex.R’ failed - The error most likely occurred in: - - > ### Name: scatter - > ### Title: Scatterplot - > ### Aliases: scatter - > - > ### ** Examples - > - > scatter(cars74, hp, mpg) - ... - ▆ - 1. └─qacBase::scatter(...) - 2. └─ggExtra::ggMarginal(p, size = 8, type = margin, fill = margin_color) - 3. └─ggplot2::ggplotGrob(scatP) - 4. ├─ggplot2::ggplot_gtable(ggplot_build(x)) - 5. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) - 6. └─ggplot2::calc_element("plot.margin", theme) - 7. └─cli::cli_abort(...) - 8. └─rlang::abort(...) - Execution halted - ``` - -# qgcomp - -
- -* Version: 2.15.2 -* GitHub: https://github.com/alexpkeil1/qgcomp -* Source code: https://github.com/cran/qgcomp -* Date/Publication: 2023-08-10 09:10:06 UTC -* Number of recursive dependencies: 157 - -Run `revdepcheck::cloud_details(, "qgcomp")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘qgcomp-Ex.R’ failed - The error most likely occurred in: - - > ### Name: plot.qgcompfit - > ### Title: Default plotting method for a qgcompfit object - > ### Aliases: plot.qgcompfit plot.qgcompmultfit - > - > ### ** Examples - > - > set.seed(12) - ... - 3. └─qgcomp:::.plot_noboot_base(x, nms, theme_butterfly_r, theme_butterfly_l) - 4. └─gridExtra::arrangeGrob(...) - 5. └─base::lapply(grobs[toconv], ggplot2::ggplotGrob) - 6. └─ggplot2 (local) FUN(X[[i]], ...) - 7. ├─ggplot2::ggplot_gtable(ggplot_build(x)) - 8. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) - 9. └─ggplot2::calc_element("plot.margin", theme) - 10. └─cli::cli_abort(...) - 11. └─rlang::abort(...) - Execution halted - ``` - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘qgcomp-vignette.Rmd’ - ... - - Estimate Std. Error Lower CI Upper CI t value Pr(>|t|) - (Intercept) -0.348084 0.108037 -0.55983 -0.13634 -3.2219 0.0013688 - psi1 0.256969 0.071459 0.11691 0.39703 3.5960 0.0003601 - - > plot(qc.fit3) - - When sourcing ‘qgcomp-vignette.R’: - Error: Theme element `plot.margin` must have class . - Execution halted - - ‘qgcomp-vignette.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - ... - --- re-building ‘qgcomp-vignette.Rmd’ using knitr - - Quitting from lines 234-242 [adjusting for covariates a] (qgcomp-vignette.Rmd) - Error: processing vignette 'qgcomp-vignette.Rmd' failed with diagnostics: - Theme element `plot.margin` must have class . - --- failed re-building ‘qgcomp-vignette.Rmd’ - - SUMMARY: processing the following file failed: - ‘qgcomp-vignette.Rmd’ - - Error: Vignette re-building failed. - Execution halted - ``` - -# qgcompint - -
- -* Version: 0.7.0 -* GitHub: https://github.com/alexpkeil1/qgcomp -* Source code: https://github.com/cran/qgcompint -* Date/Publication: 2022-03-22 16:00:02 UTC -* Number of recursive dependencies: 132 - -Run `revdepcheck::cloud_details(, "qgcompint")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘qgcompint-Ex.R’ failed - The error most likely occurred in: - - > ### Name: plot.qgcompemmfit - > ### Title: Default plotting method for a qgcompfit object - > ### Aliases: plot.qgcompemmfit - > - > ### ** Examples - > - > set.seed(50) - ... - 5. └─qgcomp:::.plot_noboot_base(x, nms, theme_butterfly_r, theme_butterfly_l) - 6. └─gridExtra::arrangeGrob(...) - 7. └─base::lapply(grobs[toconv], ggplot2::ggplotGrob) - 8. └─ggplot2 (local) FUN(X[[i]], ...) - 9. ├─ggplot2::ggplot_gtable(ggplot_build(x)) - 10. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) - 11. └─ggplot2::calc_element("plot.margin", theme) - 12. └─cli::cli_abort(...) - 13. └─rlang::abort(...) - Execution halted - ``` - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘qgcompint-vignette.Rmd’ - ... - 1 1 - 2 1 - 3 1 - 4 1 - - > plot(qfit1, emmval = 0) - - When sourcing ‘qgcompint-vignette.R’: - Error: Theme element `plot.margin` must have class . - Execution halted - - ‘qgcompint-vignette.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - ... - --- re-building ‘qgcompint-vignette.Rmd’ using knitr - - Quitting from lines 119-121 [first_step_plot] (qgcompint-vignette.Rmd) - Error: processing vignette 'qgcompint-vignette.Rmd' failed with diagnostics: - Theme element `plot.margin` must have class . - --- failed re-building ‘qgcompint-vignette.Rmd’ - - SUMMARY: processing the following file failed: - ‘qgcompint-vignette.Rmd’ - - Error: Vignette re-building failed. - Execution halted - ``` - -# qpNCA - -
- -* Version: 1.1.6 -* GitHub: NA -* Source code: https://github.com/cran/qpNCA -* Date/Publication: 2021-08-16 12:50:02 UTC -* Number of recursive dependencies: 81 - -Run `revdepcheck::cloud_details(, "qpNCA")` for more info - -
- -## Newly broken - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘Example-full-nca-analysis.rmd’ - ... - - Performing Thalf estimation... - - Creating regression plots in standard output... - - [[1]] - - ... - [[1]] - - When sourcing ‘Example-stepwise-nca-analysis.R’: - Error: Theme element `plot.margin` must have class . - Execution halted - - ‘Parameter_Guidelines.rmd’ using ‘UTF-8’... OK - ‘User_Guide.rmd’ using ‘UTF-8’... OK - ‘Example-full-nca-analysis.rmd’ using ‘UTF-8’... failed - ‘Example-stepwise-nca-analysis.rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘Parameter_Guidelines.rmd’ using rmarkdown - --- finished re-building ‘Parameter_Guidelines.rmd’ - - --- re-building ‘User_Guide.rmd’ using rmarkdown - --- finished re-building ‘User_Guide.rmd’ - - --- re-building ‘Example-full-nca-analysis.rmd’ using knitr - - Quitting from lines 81-114 [unnamed-chunk-4] (Example-full-nca-analysis.rmd) - ... - Quitting from lines 121-135 [unnamed-chunk-6] (Example-stepwise-nca-analysis.rmd) - Error: processing vignette 'Example-stepwise-nca-analysis.rmd' failed with diagnostics: - Theme element `plot.margin` must have class . - --- failed re-building ‘Example-stepwise-nca-analysis.rmd’ - - SUMMARY: processing the following files failed: - ‘Example-full-nca-analysis.rmd’ ‘Example-stepwise-nca-analysis.rmd’ - - Error: Vignette re-building failed. - Execution halted - ``` - -# QurvE - -
- -* Version: 1.1.1 -* GitHub: https://github.com/NicWir/QurvE -* Source code: https://github.com/cran/QurvE -* Date/Publication: 2024-01-26 12:40:14 UTC -* Number of recursive dependencies: 145 - -Run `revdepcheck::cloud_details(, "QurvE")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘QurvE-Ex.R’ failed - The error most likely occurred in: - - > ### Name: flFitSpline - > ### Title: Perform a smooth spline fit on fluorescence data - > ### Aliases: flFitSpline - > - > ### ** Examples - > - > # load example dataset - ... - 17. └─cowplot:::as_gtable.default(x) - 18. ├─cowplot::as_grob(plot) - 19. └─cowplot:::as_grob.ggplot(plot) - 20. └─ggplot2::ggplotGrob(plot) - 21. ├─ggplot2::ggplot_gtable(ggplot_build(x)) - 22. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) - 23. └─ggplot2::calc_element("plot.margin", theme) - 24. └─cli::cli_abort(...) - 25. └─rlang::abort(...) - Execution halted - ``` - -## In both - -* checking installed package size ... NOTE - ``` - installed size is 5.9Mb - sub-directories of 1Mb or more: - R 1.5Mb - doc 2.1Mb - shiny_app 1.2Mb - ``` - -# r2dii.plot - -
- -* Version: 0.4.0 -* GitHub: https://github.com/RMI-PACTA/r2dii.plot -* Source code: https://github.com/cran/r2dii.plot -* Date/Publication: 2024-02-29 16:40:02 UTC -* Number of recursive dependencies: 91 - -Run `revdepcheck::cloud_details(, "r2dii.plot")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘r2dii.plot-Ex.R’ failed - The error most likely occurred in: - - > ### Name: plot_emission_intensity - > ### Title: Create an emission intensity plot - > ### Aliases: plot_emission_intensity - > - > ### ** Examples - > - > # plot with `qplot_emission_intensity()` parameters - ... - Backtrace: - ▆ - 1. ├─base (local) ``(x) - 2. └─ggplot2:::print.ggplot(x) - 3. ├─ggplot2::ggplot_gtable(data) - 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) - 5. └─ggplot2::calc_element("plot.margin", theme) - 6. └─cli::cli_abort(...) - 7. └─rlang::abort(...) - Execution halted - ``` - -* checking tests ... ERROR - ``` - Running ‘spelling.R’ - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(r2dii.plot) - > - > test_check("r2dii.plot") - Scale for colour is already present. - Adding another scale for colour, which will replace the existing scale. - ... - 10. └─ggplot2:::print.ggplot(x) - 11. ├─ggplot2::ggplot_gtable(data) - 12. └─ggplot2:::ggplot_gtable.ggplot_built(data) - 13. └─ggplot2::calc_element("plot.margin", theme) - 14. └─cli::cli_abort(...) - 15. └─rlang::abort(...) - - [ FAIL 1 | WARN 2 | SKIP 39 | PASS 124 ] - Error: Test failures - Execution halted - ``` - -# Radviz - -
- -* Version: 0.9.3 -* GitHub: https://github.com/yannabraham/Radviz -* Source code: https://github.com/cran/Radviz -* Date/Publication: 2022-03-25 18:10:02 UTC -* Number of recursive dependencies: 64 - -Run `revdepcheck::cloud_details(, "Radviz")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘Radviz-Ex.R’ failed - The error most likely occurred in: - - > ### Name: Radviz - > ### Title: Radviz Projection of Multidimensional Data - > ### Aliases: Radviz - > - > ### ** Examples - > - > data(iris) - > das <- c('Sepal.Length','Sepal.Width','Petal.Length','Petal.Width') - > S <- make.S(das) - > rv <- do.radviz(iris,S) - > plot(rv,anchors.only=FALSE) - Error in plot.radviz(rv, anchors.only = FALSE) : - 'language' object cannot be coerced to type 'double' - Calls: plot -> plot.radviz - Execution halted - ``` - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘multivariate_analysis.Rmd’ - ... - - > classic.S <- make.S(get.optim(classic.optim)) - - > btcells.rv <- do.radviz(btcells.df, classic.S) - - > plot(btcells.rv) + geom_point(aes(color = Treatment)) - - ... - [1] 15792 18 - - > ct.rv - - When sourcing ‘single_cell_projections.R’: - Error: 'language' object cannot be coerced to type 'double' - Execution halted - - ‘multivariate_analysis.Rmd’ using ‘UTF-8’... failed - ‘single_cell_projections.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘multivariate_analysis.Rmd’ using rmarkdown - ``` - -# rainette - -
- -* Version: 0.3.1.1 -* GitHub: https://github.com/juba/rainette -* Source code: https://github.com/cran/rainette -* Date/Publication: 2023-03-28 16:50:02 UTC -* Number of recursive dependencies: 117 - -Run `revdepcheck::cloud_details(, "rainette")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(rainette) - - Attaching package: 'rainette' - - The following object is masked from 'package:stats': - - ... - • plots/base-rainette2-plot-measure-frequency.svg - • plots/base-rainette2-plot-measure-lr.svg - • plots/base-rainette2-plot-with-complete-groups.svg - • plots/base-rainette2-plot-with-free-scales.svg - • plots/base-rainette2-plot-with-k-5.svg - • plots/base-rainette2-plot-with-k-and-without-negative.svg - • plots/base-rainette2-plot-with-k-n-terms-and-font-size.svg - • plots/base-rainette2-plot.svg - Error: Test failures - Execution halted - ``` - -# rassta - -
- -* Version: 1.0.5 -* GitHub: https://github.com/bafuentes/rassta -* Source code: https://github.com/cran/rassta -* Date/Publication: 2022-08-30 22:30:02 UTC -* Number of recursive dependencies: 120 - -Run `revdepcheck::cloud_details(, "rassta")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘rassta-Ex.R’ failed - The error most likely occurred in: - - > ### Name: select_functions - > ### Title: Select Constrained Univariate Distribution Functions - > ### Aliases: select_functions - > - > ### ** Examples - > - > require(terra) - ... - > tvars <- terra::rast(tf) - > # Single-layer SpatRaster of topographic classification units - > ## 5 classification units - > tcf <- list.files(path = p, pattern = "topography.tif", full.names = TRUE) - > tcu <- terra::rast(tcf) - > # Automatic selection of distribution functions - > tdif <- select_functions(cu.rast = tcu, var.rast = tvars, fun = mean) - Error in pm[[2]] : subscript out of bounds - Calls: select_functions -> -> ggplotly.ggplot -> gg2list - Execution halted - ``` - -* checking tests ... ERROR - ``` - Running ‘tinytest.R’ - Running the tests in ‘tests/tinytest.R’ failed. - Complete output: - > - > if ( requireNamespace("tinytest", quietly=TRUE) ){ - + tinytest::test_package("rassta") - + } - - Attaching package: 'rassta' - - ... - test_select_functions.R....... 0 tests - test_select_functions.R....... 0 tests - test_select_functions.R....... 0 tests - test_select_functions.R....... 0 tests - test_select_functions.R....... 0 tests - test_select_functions.R....... 0 tests - test_select_functions.R....... 0 tests - test_select_functions.R....... 0 tests Error in pm[[2]] : subscript out of bounds - Calls: ... select_functions -> -> ggplotly.ggplot -> gg2list - Execution halted - ``` - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘signature.Rmd’ - ... - > clim.var <- rast(vardir) - - > clim.cu <- rast(paste(d, "/climate.tif", sep = "")) - - > clim.difun <- select_functions(cu.rast = clim.cu, - + var.rast = clim.var, mode = "auto") - - ... - When sourcing ‘signature.R’: - Error: subscript out of bounds - Execution halted - - ‘classunits.Rmd’ using ‘UTF-8’... OK - ‘modeling.Rmd’ using ‘UTF-8’... OK - ‘sampling.Rmd’ using ‘UTF-8’... OK - ‘signature.Rmd’ using ‘UTF-8’... failed - ‘similarity.Rmd’ using ‘UTF-8’... OK - ‘stratunits.Rmd’ using ‘UTF-8’... OK - ``` - -# RAT - -
- -* Version: 0.3.1 -* GitHub: NA -* Source code: https://github.com/cran/RAT -* Date/Publication: 2022-08-24 07:00:23 UTC -* Number of recursive dependencies: 32 - -Run `revdepcheck::cloud_details(, "RAT")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘RAT-Ex.R’ failed - The error most likely occurred in: - - > ### Name: i.map - > ### Title: Map of international collaboration. - > ### Aliases: i.map - > - > ### ** Examples - > - > data(biblio) - ... - Backtrace: - ▆ - 1. ├─base (local) ``(x) - 2. └─ggplot2:::print.ggplot(x) - 3. ├─ggplot2::ggplot_gtable(data) - 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) - 5. └─ggplot2::calc_element("plot.margin", theme) - 6. └─cli::cli_abort(...) - 7. └─rlang::abort(...) - Execution halted - ``` - -# Rcan - -
- -* Version: 1.3.82 -* GitHub: https://github.com/timat35/Rcan -* Source code: https://github.com/cran/Rcan -* Date/Publication: 2020-05-19 11:40:07 UTC -* Number of recursive dependencies: 47 - -Run `revdepcheck::cloud_details(, "Rcan")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘Rcan-Ex.R’ failed - The error most likely occurred in: - - > ### Name: csu_trendCohortPeriod - > ### Title: csu_trendCohortPeriod - > ### Aliases: csu_trendCohortPeriod - > - > ### ** Examples - > - > - ... - ! Theme element `plot.margin` must have class . - Backtrace: - ▆ - 1. └─Rcan::csu_trendCohortPeriod(...) - 2. ├─ggplot2::ggplot_gtable(gb_plot) - 3. └─ggplot2:::ggplot_gtable.ggplot_built(gb_plot) - 4. └─ggplot2::calc_element("plot.margin", theme) - 5. └─cli::cli_abort(...) - 6. └─rlang::abort(...) - Execution halted - ``` - -## In both - -* checking data for non-ASCII characters ... NOTE - ``` - Note: found 26334 marked UTF-8 strings - ``` - -# redist - -
- -* Version: 4.2.0 -* GitHub: https://github.com/alarm-redist/redist -* Source code: https://github.com/cran/redist -* Date/Publication: 2024-01-13 13:20:02 UTC -* Number of recursive dependencies: 132 - -Run `revdepcheck::cloud_details(, "redist")` for more info - -
- -## Newly broken - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘redist.Rmd’ - ... - # ℹ 991 more rows - - > library(patchwork) - - > hist(plan_sum, max_dev) + hist(iowa_plans, comp) + - + plot_layout(guides = "collect") - - When sourcing ‘redist.R’: - Error: object is not a unit - Execution halted - - ‘common_args.Rmd’ using ‘UTF-8’... OK - ‘flip.Rmd’ using ‘UTF-8’... OK - ‘map-preproc.Rmd’ using ‘UTF-8’... OK - ‘redist.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘common_args.Rmd’ using rmarkdown - ``` - -## In both - -* checking installed package size ... NOTE - ``` - installed size is 27.4Mb - sub-directories of 1Mb or more: - data 1.2Mb - libs 23.4Mb - ``` - -# Relectoral - -
- -* Version: 0.1.0 -* GitHub: NA -* Source code: https://github.com/cran/Relectoral -* Date/Publication: 2020-06-14 14:20:02 UTC -* Number of recursive dependencies: 79 - -Run `revdepcheck::cloud_details(, "Relectoral")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘Relectoral-Ex.R’ failed - The error most likely occurred in: - - > ### Name: mapa - > ### Title: Graphs. Representation on maps. Choropleth map - > ### Aliases: mapa - > - > ### ** Examples - > - > - ... - Backtrace: - ▆ - 1. ├─base (local) ``(x) - 2. └─ggplot2:::print.ggplot(x) - 3. ├─ggplot2::ggplot_gtable(data) - 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) - 5. └─ggplot2::calc_element("plot.margin", theme) - 6. └─cli::cli_abort(...) - 7. └─rlang::abort(...) - Execution halted - ``` - -## In both - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘Volatilidad.Rmd’ - ... - Loading required package: readxl - - > require("readxl") - - > dat1 <- read_xlsx("../inst/data_raw/volatilidad/abril_19.xlsx", - + col_names = TRUE) - - When sourcing ‘Volatilidad.R’: - Error: `path` does not exist: ‘../inst/data_raw/volatilidad/abril_19.xlsx’ - Execution halted - - ‘Volatilidad.Rmd’ using ‘UTF-8’... failed - ``` - -* checking dependencies in R code ... NOTE - ``` - Namespace in Imports field not imported from: ‘rmarkdown’ - All declared Imports should be used. - ``` - -* checking LazyData ... NOTE - ``` - 'LazyData' is specified without a 'data' directory - ``` - -# reliabilitydiag - -
- -* Version: 0.2.1 -* GitHub: https://github.com/aijordan/reliabilitydiag -* Source code: https://github.com/cran/reliabilitydiag -* Date/Publication: 2022-06-29 00:20:06 UTC -* Number of recursive dependencies: 73 - -Run `revdepcheck::cloud_details(, "reliabilitydiag")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘reliabilitydiag-Ex.R’ failed - The error most likely occurred in: - - > ### Name: plot.reliabilitydiag - > ### Title: Plotting reliability diagram objects - > ### Aliases: plot.reliabilitydiag autoplot.reliabilitydiag - > ### autolayer.reliabilitydiag - > - > ### ** Examples - > - ... - 2. └─reliabilitydiag:::autoplot.reliabilitydiag(r["EMOS"], type = "discrimination") - 3. ├─base::do.call(...) - 4. └─ggExtra (local) ``(...) - 5. └─ggplot2::ggplotGrob(scatP) - 6. ├─ggplot2::ggplot_gtable(ggplot_build(x)) - 7. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) - 8. └─ggplot2::calc_element("plot.margin", theme) - 9. └─cli::cli_abort(...) - 10. └─rlang::abort(...) - Execution halted - ``` - -# relliptical - -
- -* Version: 1.3.0 -* GitHub: NA -* Source code: https://github.com/cran/relliptical -* Date/Publication: 2024-02-07 12:50:02 UTC -* Number of recursive dependencies: 73 - -Run `revdepcheck::cloud_details(, "relliptical")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘relliptical-Ex.R’ failed - The error most likely occurred in: - - > ### Name: rtelliptical - > ### Title: Sampling Random Numbers from Truncated Multivariate Elliptical - > ### Distributions - > ### Aliases: rtelliptical - > - > ### ** Examples - > - ... - Backtrace: - ▆ - 1. └─ggExtra::ggMarginal(f1, type = "histogram", fill = "grey") - 2. └─ggplot2::ggplotGrob(scatP) - 3. ├─ggplot2::ggplot_gtable(ggplot_build(x)) - 4. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) - 5. └─ggplot2::calc_element("plot.margin", theme) - 6. └─cli::cli_abort(...) - 7. └─rlang::abort(...) - Execution halted - ``` - -## In both - -* checking installed package size ... NOTE - ``` - installed size is 6.5Mb - sub-directories of 1Mb or more: - libs 6.4Mb - ``` - -# Repliscope - -
- -* Version: 1.1.1 -* GitHub: NA -* Source code: https://github.com/cran/Repliscope -* Date/Publication: 2022-09-13 07:20:02 UTC -* Number of recursive dependencies: 62 - -Run `revdepcheck::cloud_details(, "Repliscope")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘Repliscope-Ex.R’ failed - The error most likely occurred in: - - > ### Name: plotBed - > ### Title: A function to boxplot 'score' column of a BED dataframe, per - > ### unique chromosome name in the 'chrom' column. The resulting plot also - > ### highlights outliers based on the inter quartile range (IQR). The - > ### genome wide median is plotted as a pink line through the boxplots. - > ### Aliases: plotBed - > ### Keywords: BED bioinformatics boxplot genomics - ... - Backtrace: - ▆ - 1. ├─base (local) ``(x) - 2. └─ggplot2:::print.ggplot(x) - 3. ├─ggplot2::ggplot_gtable(data) - 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) - 5. └─ggplot2::calc_element("plot.margin", theme) - 6. └─cli::cli_abort(...) - 7. └─rlang::abort(...) - Execution halted - ``` - -# reportRmd - -
- -* Version: 0.1.0 -* GitHub: NA -* Source code: https://github.com/cran/reportRmd -* Date/Publication: 2023-11-16 17:00:03 UTC -* Number of recursive dependencies: 108 - -Run `revdepcheck::cloud_details(, "reportRmd")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘reportRmd-Ex.R’ failed - The error most likely occurred in: - - > ### Name: ggkmcif - > ### Title: Plot KM and CIF curves with ggplot - > ### Aliases: ggkmcif - > - > ### ** Examples - > - > data("pembrolizumab") - ... - Backtrace: - ▆ - 1. └─reportRmd::ggkmcif(...) - 2. └─ggplot2::ggplotGrob(data.table) - 3. ├─ggplot2::ggplot_gtable(ggplot_build(x)) - 4. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) - 5. └─ggplot2::calc_element("plot.margin", theme) - 6. └─cli::cli_abort(...) - 7. └─rlang::abort(...) - Execution halted - ``` - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘reportRmd.Rmd’ - ... - > ctDNA <- clear_labels(ctDNA) - - > plotuv(data = pembrolizumab, response = "orr", covs = c("age", - + "cohort", "pdl1", "change_ctdna_group")) - Boxplots not shown for categories with fewer than 20 observations. - Boxplots not shown for categories with fewer than 20 observations. - - When sourcing ‘reportRmd.R’: - Error: Theme element `plot.margin` must have class . - Execution halted - - ‘reportRmd.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - ... - --- re-building ‘reportRmd.Rmd’ using rmarkdown - - Quitting from lines 380-383 [unnamed-chunk-30] (reportRmd.Rmd) - Error: processing vignette 'reportRmd.Rmd' failed with diagnostics: - Theme element `plot.margin` must have class . - --- failed re-building ‘reportRmd.Rmd’ - - SUMMARY: processing the following file failed: - ‘reportRmd.Rmd’ - - Error: Vignette re-building failed. - Execution halted - ``` - -# reReg - -
- -* Version: 1.4.6 -* GitHub: https://github.com/stc04003/reReg -* Source code: https://github.com/cran/reReg -* Date/Publication: 2023-09-20 08:00:02 UTC -* Number of recursive dependencies: 63 - -Run `revdepcheck::cloud_details(, "reReg")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘reReg-Ex.R’ failed - The error most likely occurred in: - - > ### Name: plot.Recur - > ### Title: Produce Event Plot or Mean Cumulative Function Plot - > ### Aliases: plot.Recur - > ### Keywords: Plots - > - > ### ** Examples - > - ... - 11. │ └─base::withCallingHandlers(...) - 12. └─ggplot2 (local) f(l = layers[[i]], d = data[[i]]) - 13. └─l$compute_geom_2(d, theme = plot$theme) - 14. └─ggplot2 (local) compute_geom_2(..., self = self) - 15. └─self$geom$use_defaults(...) - 16. └─ggplot2 (local) use_defaults(..., self = self) - 17. └─ggplot2:::check_aesthetics(new_params, nrow(data)) - 18. └─cli::cli_abort(...) - 19. └─rlang::abort(...) - Execution halted - ``` - -# reservr - -
- -* Version: 0.0.2 -* GitHub: https://github.com/AshesITR/reservr -* Source code: https://github.com/cran/reservr -* Date/Publication: 2023-10-18 20:50:05 UTC -* Number of recursive dependencies: 142 - -Run `revdepcheck::cloud_details(, "reservr")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘reservr-Ex.R’ failed - The error most likely occurred in: - - > ### Name: dist_bdegp - > ### Title: Construct a BDEGP-Family - > ### Aliases: dist_bdegp - > - > ### ** Examples - > - > dist <- dist_bdegp(n = 1, m = 2, u = 10, epsilon = 3) - ... - + theoretical = dist, - + empirical = dist_empirical(x), - + .x = seq(0, 20, length.out = 101), - + with_params = list(theoretical = params) - + ) - Warning: Removed 9 rows containing missing values or values outside the scale range - (`geom_line()`). - Error in as.unit(value) : object is not coercible to a unit - Calls: ... assemble_guides -> guides_build -> [<- -> [<-.unit -> as.unit - Execution halted - ``` - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘distributions.Rmd’ - ... - - > attr(trunc_fit$logLik, "nobs") - [1] 62 - - > plot_distributions(true = norm, fit1 = norm, fit2 = norm2, - + fit3 = dist_normal(3), .x = seq(-2, 7, 0.01), with_params = list(true = list(mean .... [TRUNCATED] - - When sourcing ‘distributions.R’: - Error: object is not a unit - Execution halted - - ‘distributions.Rmd’ using ‘UTF-8’... failed - ‘tensorflow.Rmd’ using ‘UTF-8’... OK - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - ... - --- re-building ‘distributions.Rmd’ using rmarkdown - - Quitting from lines 170-227 [unnamed-chunk-10] (distributions.Rmd) - Error: processing vignette 'distributions.Rmd' failed with diagnostics: - object is not a unit - --- failed re-building ‘distributions.Rmd’ - - --- re-building ‘tensorflow.Rmd’ using rmarkdown - --- finished re-building ‘tensorflow.Rmd’ - - SUMMARY: processing the following file failed: - ‘distributions.Rmd’ - - Error: Vignette re-building failed. - Execution halted - ``` - -## In both - -* checking installed package size ... NOTE - ``` - installed size is 16.5Mb - sub-directories of 1Mb or more: - R 3.5Mb - libs 12.4Mb - ``` - -* checking for GNU extensions in Makefiles ... NOTE - ``` - GNU make is a SystemRequirements. - ``` - -# restriktor - -
- -* Version: 0.5-60 -* GitHub: NA -* Source code: https://github.com/cran/restriktor -* Date/Publication: 2024-05-24 11:00:03 UTC -* Number of recursive dependencies: 81 - -Run `revdepcheck::cloud_details(, "restriktor")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘restriktor-Ex.R’ failed - The error most likely occurred in: - - > ### Name: evSyn - > ### Title: GORIC(A) Evidence synthesis - > ### Aliases: evSyn evsyn evSyn_est.list evSyn_ICweights.list - > ### evSyn_ICvalues.list evSyn_LL.list print.evSyn print.summary.evSyn - > ### summary.evSyn plot.evSyn - > - > ### ** Examples - ... - Backtrace: - ▆ - 1. ├─base (local) ``(x) - 2. └─ggplot2:::print.ggplot(x) - 3. ├─ggplot2::ggplot_gtable(data) - 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) - 5. └─ggplot2::calc_element("plot.margin", theme) - 6. └─cli::cli_abort(...) - 7. └─rlang::abort(...) - Execution halted - ``` - -# RevGadgets - -
- -* Version: 1.2.1 -* GitHub: https://github.com/revbayes/RevGadgets -* Source code: https://github.com/cran/RevGadgets -* Date/Publication: 2023-11-29 20:30:02 UTC -* Number of recursive dependencies: 131 - -Run `revdepcheck::cloud_details(, "RevGadgets")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(RevGadgets) - > - > test_check("RevGadgets") - - | - | | 0% - ... - 6. └─ggplot2:::print.ggplot(x) - 7. ├─ggplot2::ggplot_gtable(data) - 8. └─ggplot2:::ggplot_gtable.ggplot_built(data) - 9. └─ggplot2::calc_element("plot.margin", theme) - 10. └─cli::cli_abort(...) - 11. └─rlang::abort(...) - - [ FAIL 1 | WARN 44 | SKIP 0 | PASS 138 ] - Error: Test failures - Execution halted - ``` - -# rimu - -
- -* Version: 0.6 -* GitHub: NA -* Source code: https://github.com/cran/rimu -* Date/Publication: 2022-10-06 04:50:02 UTC -* Number of recursive dependencies: 53 - -Run `revdepcheck::cloud_details(, "rimu")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘rimu-Ex.R’ failed - The error most likely occurred in: - - > ### Name: plot.mr - > ### Title: Plot multiple-response objects - > ### Aliases: plot.mr image.mr - > - > ### ** Examples - > - > data(rstudiosurvey) - ... - 4. ├─base::suppressMessages(...) - 5. │ └─base::withCallingHandlers(...) - 6. └─UpSetR:::Make_main_bar(...) - 7. └─ggplot2::ggplotGrob(Main_bar_plot) - 8. ├─ggplot2::ggplot_gtable(ggplot_build(x)) - 9. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) - 10. └─ggplot2::calc_element("plot.margin", theme) - 11. └─cli::cli_abort(...) - 12. └─rlang::abort(...) - Execution halted - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - ... - --- re-building ‘backyard-birds.Rmd’ using rmarkdown - - Quitting from lines 63-64 [unnamed-chunk-6] (backyard-birds.Rmd) - Error: processing vignette 'backyard-birds.Rmd' failed with diagnostics: - Theme element `plot.margin` must have class . - --- failed re-building ‘backyard-birds.Rmd’ - - --- re-building ‘ethnicity.Rmd’ using rmarkdown - ... - --- failed re-building ‘ethnicity.Rmd’ - - --- re-building ‘internals.Rmd’ using rmarkdown - --- finished re-building ‘internals.Rmd’ - - SUMMARY: processing the following files failed: - ‘backyard-birds.Rmd’ ‘ethnicity.Rmd’ - - Error: Vignette re-building failed. - Execution halted - ``` - -## In both - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘backyard-birds.Rmd’ - ... - Aythya collaris Xanthocephalus xanthocephalus Gracula religiosa - 1090 80 1 - Icterus parisorum Coccyzus erythropthalmus - 8 1 - - > plot(bird_presence, nsets = 12) - - ... - - > plot(ethnicity, nsets = 6) - - When sourcing ‘ethnicity.R’: - Error: Theme element `plot.margin` must have class . - Execution halted - - ‘backyard-birds.Rmd’ using ‘UTF-8’... failed - ‘ethnicity.Rmd’ using ‘UTF-8’... failed - ‘internals.Rmd’ using ‘UTF-8’... OK - ``` - -# rKOMICS - -
- -* Version: 1.3 -* GitHub: NA -* Source code: https://github.com/cran/rKOMICS -* Date/Publication: 2023-06-29 22:40:03 UTC -* Number of recursive dependencies: 137 - -Run `revdepcheck::cloud_details(, "rKOMICS")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘rKOMICS-Ex.R’ failed - The error most likely occurred in: - - > ### Name: msc.pca - > ### Title: Prinicple Component Analysis based on MSC - > ### Aliases: msc.pca - > - > ### ** Examples - > - > data(matrices) - ... - 11. │ └─base::withCallingHandlers(...) - 12. └─ggplot2 (local) f(l = layers[[i]], d = data[[i]]) - 13. └─l$compute_geom_2(d, theme = plot$theme) - 14. └─ggplot2 (local) compute_geom_2(..., self = self) - 15. └─self$geom$use_defaults(...) - 16. └─ggplot2 (local) use_defaults(..., self = self) - 17. └─ggplot2:::check_aesthetics(new_params, nrow(data)) - 18. └─cli::cli_abort(...) - 19. └─rlang::abort(...) - Execution halted - ``` - -## In both - -* checking installed package size ... NOTE - ``` - installed size is 24.8Mb - sub-directories of 1Mb or more: - extdata 24.0Mb - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘example.Rnw’ using Sweave - Loading required package: viridisLite - Warning: Removed 95 rows containing non-finite outside the scale range - (`stat_boxplot()`). - Warning: Removed 89 rows containing non-finite outside the scale range - (`stat_boxplot()`). - Warning: Removed 149 rows containing non-finite outside the scale range - (`stat_boxplot()`). - Warning: Removed 286 rows containing non-finite outside the scale range - ... - l.5 \usepackage - {xcolor}^^M - ! ==> Fatal error occurred, no output PDF file produced! - --- failed re-building ‘example.Rnw’ - - SUMMARY: processing the following file failed: - ‘example.Rnw’ - - Error: Vignette re-building failed. - Execution halted - ``` - -# rmcorr - -
- -* Version: 0.6.0 -* GitHub: https://github.com/lmarusich/rmcorr -* Source code: https://github.com/cran/rmcorr -* Date/Publication: 2023-08-09 16:40:10 UTC -* Number of recursive dependencies: 140 - -Run `revdepcheck::cloud_details(, "rmcorr")` for more info - -
- -## Newly broken - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘CI_fix.Rmd’ using rmarkdown - --- finished re-building ‘CI_fix.Rmd’ - - --- re-building ‘FAQ_and_limitations.Rmd’ using rmarkdown - --- finished re-building ‘FAQ_and_limitations.Rmd’ - - --- re-building ‘New_rmcorr_paper_analyses_figures.Rmd’ using rmarkdown - ``` - -## In both - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘estimates_w_NaN.Rmd’ - ... - - > library(ggExtra) - - > load(file = "../man/data/ghosh_synth.rda") - Warning in readChar(con, 5L, useBytes = TRUE) : - cannot open compressed file '../man/data/ghosh_synth.rda', probable reason 'No such file or directory' - - ... - Execution halted - - ‘CI_fix.Rmd’ using ‘UTF-8’... OK - ‘FAQ_and_limitations.Rmd’ using ‘UTF-8’... OK - ‘New_rmcorr_paper_analyses_figures.Rmd’ using ‘UTF-8’... OK - ‘compcor.Rmd’ using ‘UTF-8’... OK - ‘estimates_w_NaN.Rmd’ using ‘UTF-8’... failed - ‘model_diag.Rmd’ using ‘UTF-8’... OK - ‘repro_bootstrapping.Rmd’ using ‘UTF-8’... OK - ‘rmcorr_mat.Rmd’ using ‘UTF-8’... OK - ``` - -# RNAseqQC - -
- -* Version: 0.1.4 -* GitHub: NA -* Source code: https://github.com/cran/RNAseqQC -* Date/Publication: 2022-06-15 09:50:06 UTC -* Number of recursive dependencies: 176 - -Run `revdepcheck::cloud_details(, "RNAseqQC")` for more info - -
- -## Newly broken - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘introduction.Rmd’ - ... - + show_plot = F)$plot + theme(legend.position = "bottom") - - > plot_loadings(pca_res, PC = 2, color_by = "gc_content") - - > plot_pca_scatters(vsd, n_PCs = 5, color_by = "treatment", - + shape_by = "mutation") - - When sourcing 'introduction.R': - Error: object is not coercible to a unit - Execution halted - - ‘data.Rmd’ using ‘UTF-8’... OK - ‘introduction.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘data.Rmd’ using rmarkdown - --- finished re-building ‘data.Rmd’ - - --- re-building ‘introduction.Rmd’ using rmarkdown - ``` - -## In both - -* checking installed package size ... NOTE - ``` - installed size is 9.9Mb - sub-directories of 1Mb or more: - data 7.5Mb - doc 2.2Mb - ``` - -# roahd - -
- -* Version: 1.4.3 -* GitHub: https://github.com/astamm/roahd -* Source code: https://github.com/cran/roahd -* Date/Publication: 2021-11-04 00:10:02 UTC -* Number of recursive dependencies: 88 - -Run `revdepcheck::cloud_details(, "roahd")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘roahd-Ex.R’ failed - The error most likely occurred in: - - > ### Name: plot.depthgram - > ### Title: Specialized method to plot 'depthgram' objects - > ### Aliases: plot.depthgram - > - > ### ** Examples - > - > N <- 50 - ... - + N, - + centerline = sin(2 * pi * grid), - + Cov = Cov - + ) - > names <- paste0("id_", 1:nrow(Data[[1]])) - > DG <- depthgram(Data, marginal_outliers = TRUE, ids = names) - > plot(DG) - Error in pm[[2]] : subscript out of bounds - Calls: plot ... plotly_build -> ggplotly -> ggplotly.ggplot -> gg2list - Execution halted + • plots/plot-spansres-color-high-color-low.svg + • plots/plot-spansres.svg + • plots/plot-statres-anova-volcano.svg + • plots/plot-statres-anova.svg + • plots/plot-statres-combined-volcano.svg + • plots/plot-statres-combined.svg + • plots/plot-statres-gtest.svg + • plots/plot-totalcountfilt.svg + Error: Test failures + Execution halted ``` ## In both * checking installed package size ... NOTE ``` - installed size is 7.4Mb - sub-directories of 1Mb or more: - data 5.0Mb - doc 1.7Mb - ``` - -# robustbase - -
- -* Version: 0.99-2 -* GitHub: NA -* Source code: https://github.com/cran/robustbase -* Date/Publication: 2024-01-27 16:30:02 UTC -* Number of recursive dependencies: 77 - -Run `revdepcheck::cloud_details(, "robustbase")` for more info - -
- -## Newly broken - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘lmrob_simulation.Rnw’ - ... - + d.x_psi(x, "lqq"), d.x_psi(x, "hampel")) - - > print(ggplot(tmp, aes(x, value, color = psi)) + geom_line(lwd = 1.25) + - + ylab(quote(psi(x))) + scale_color_discrete(name = quote(psi ~ - + .... [TRUNCATED] - - When sourcing ‘lmrob_simulation.R’: - Error: Theme element `plot.margin` must have class - . - Execution halted - - ‘fastMcd-kmini.Rnw’ using ‘UTF-8’... OK - ‘lmrob_simulation.Rnw’ using ‘UTF-8’... failed - ‘psi_functions.Rnw’ using ‘UTF-8’... OK - ``` - -## In both - -* checking package dependencies ... NOTE - ``` - Packages which this enhances but not available for checking: - 'robustX', 'matrixStats', 'quantreg', 'Hmisc' - ``` - -* checking Rd cross-references ... NOTE - ``` - Packages unavailable to check Rd xrefs: ‘matrixStats’, ‘robustX’, ‘quantreg’, ‘Hmisc’ - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘fastMcd-kmini.Rnw’ using Sweave - Loading required package: robustbase - Error: processing vignette 'fastMcd-kmini.Rnw' failed with diagnostics: - Running 'texi2dvi' on 'fastMcd-kmini.tex' failed. - LaTeX errors: - ! LaTeX Error: File `mathtools.sty' not found. - - Type X to quit or to proceed, - or enter new name. (Default extension: sty) - ... - l.179 \RequirePackage{grfext}\relax - ^^M - ! ==> Fatal error occurred, no output PDF file produced! - --- failed re-building ‘psi_functions.Rnw’ - - SUMMARY: processing the following files failed: - ‘fastMcd-kmini.Rnw’ ‘lmrob_simulation.Rnw’ ‘psi_functions.Rnw’ - - Error: Vignette re-building failed. - Execution halted - ``` - -# romic - -
- -* Version: 1.1.3 -* GitHub: NA -* Source code: https://github.com/cran/romic -* Date/Publication: 2023-09-21 05:40:02 UTC -* Number of recursive dependencies: 113 - -Run `revdepcheck::cloud_details(, "romic")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > # This file is part of the standard setup for testthat. - > # It is recommended that you do not modify it. - > # - > # Where should you do additional test configuration? - > # Learn more about the roles of various files in: - > # * https://r-pkgs.org/testing-design.html#sec-tests-files-overview - > # * https://testthat.r-lib.org/articles/special-files.html - ... - 3. │ │ └─base::withCallingHandlers(...) - 4. │ ├─plotly::ggplotly(heatmap_plot) %>% plotly::layout(margin = 0) - 5. │ ├─plotly::ggplotly(heatmap_plot) - 6. │ └─plotly:::ggplotly.ggplot(heatmap_plot) - 7. │ └─plotly::gg2list(...) - 8. └─plotly::layout(., margin = 0) - - [ FAIL 1 | WARN 0 | SKIP 7 | PASS 66 ] - Error: Test failures - Execution halted - ``` + installed size is 10.4Mb + sub-directories of 1Mb or more: + R 1.5Mb + help 1.5Mb + libs 6.3Mb + ``` -# roptions +# pmxTools
-* Version: 1.0.3 -* GitHub: NA -* Source code: https://github.com/cran/roptions -* Date/Publication: 2020-05-11 11:10:06 UTC -* Number of recursive dependencies: 70 +* Version: 1.3 +* GitHub: https://github.com/kestrel99/pmxTools +* Source code: https://github.com/cran/pmxTools +* Date/Publication: 2023-02-21 16:00:08 UTC +* Number of recursive dependencies: 85 -Run `revdepcheck::cloud_details(, "roptions")` for more info +Run `revdepcheck::cloud_details(, "pmxTools")` for more info
## Newly broken -* checking examples ... ERROR +* checking tests ... ERROR ``` - Running examples in ‘roptions-Ex.R’ failed - The error most likely occurred in: - - > ### Name: box.spread - > ### Title: Box Spread Strategy Function - > ### Aliases: box.spread - > - > ### ** Examples - > - > box.spread(100, 105, 95, 110, 3.2, 2.6, 1.1, 2.4) + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(pmxTools) + Loading required package: patchwork + > + > test_check("pmxTools") + [ FAIL 1 | WARN 1 | SKIP 12 | PASS 110 ] + ... - 35 5.7 - 36 5.7 - 37 5.7 - 38 5.7 - 39 5.7 - 40 5.7 - 41 5.7 - Error in pm[[2]] : subscript out of bounds - Calls: box.spread -> print -> ggplotly -> ggplotly.ggplot -> gg2list - Execution halted + 24. └─handlers[[1L]](cnd) + 25. └─cli::cli_abort(...) + 26. └─rlang::abort(...) + + [ FAIL 1 | WARN 1 | SKIP 12 | PASS 110 ] + Deleting unused snapshots: + • plot/conditioned-distplot.svg + • plot/perc.svg + Error: Test failures + Execution halted ``` ## In both -* checking LazyData ... NOTE +* checking Rd cross-references ... NOTE ``` - 'LazyData' is specified without a 'data' directory + Package unavailable to check Rd xrefs: ‘DiagrammeR’ ``` -# rotations +# posterior
-* Version: 1.6.5 -* GitHub: https://github.com/stanfill/rotationsC -* Source code: https://github.com/cran/rotations -* Date/Publication: 2023-12-08 00:10:02 UTC -* Number of recursive dependencies: 79 +* Version: 1.6.0 +* GitHub: https://github.com/stan-dev/posterior +* Source code: https://github.com/cran/posterior +* Date/Publication: 2024-07-03 23:00:02 UTC +* Number of recursive dependencies: 119 -Run `revdepcheck::cloud_details(, "rotations")` for more info +Run `revdepcheck::cloud_details(, "posterior")` for more info
## Newly broken -* checking examples ... ERROR +* checking re-building of vignette outputs ... NOTE ``` - Running examples in ‘rotations-Ex.R’ failed - The error most likely occurred in: + Error(s) in re-building vignettes: + --- re-building ‘pareto_diagnostics.Rmd’ using rmarkdown + --- finished re-building ‘pareto_diagnostics.Rmd’ - > ### Name: plot - > ### Title: Visualizing random rotations - > ### Aliases: plot plot.SO3 plot.Q4 - > - > ### ** Examples - > - > r <- rvmises(200, kappa = 1.0) - ... - Backtrace: - ▆ - 1. ├─base (local) ``(x) - 2. └─ggplot2:::print.ggplot(x) - 3. ├─ggplot2::ggplot_gtable(data) - 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) - 5. └─ggplot2::calc_element("plot.margin", theme) - 6. └─cli::cli_abort(...) - 7. └─rlang::abort(...) - Execution halted - ``` - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘rotations-intro.Rnw’ - ... + --- re-building ‘posterior.Rmd’ using rmarkdown + --- finished re-building ‘posterior.Rmd’ - > region(x = Rs, method = "direct", type = "bootstrap", - + estimator = "median", alp = 0.05, m = 300) - [1] 0.238 + --- re-building ‘rvar.Rmd’ using rmarkdown - > plot(x = Rs, center = mean(Rs), show_estimates = "all") + Quitting from lines 530-533 [mixture] (rvar.Rmd) + ... + NULL, NULL, NULL, list(NULL, NA, NULL, NULL, TRUE), NULL, 2, NULL, NULL, NULL, 1.2, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 0.2, NULL, list(NULL, NULL, NULL, 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, NULL, NULL, NULL, TRUE), NULL, "right", NULL, NULL, NULL, "center", NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 0, list(), 2, list("grey92", NA, NULL, NULL, TRUE), list(), NULL, NULL, NULL, list("white", NULL, NULL, NULL, FALSE, "white", + TRUE), NULL, list(NULL, 0.5, NULL, NULL, FALSE, NULL, TRUE), NULL, NULL, NULL, NULL, FALSE, list(NULL, "white", NULL, NULL, TRUE), list(NULL, NULL, NULL, 1.2, 0, 1, NULL, NULL, c(0, 0, 5.5, 0), NULL, TRUE), "panel", list(NULL, NULL, NULL, NULL, 0, 1, NULL, NULL, c(0, 0, 5.5, 0), NULL, TRUE), list(NULL, NULL, NULL, 0.8, 1, 1, NULL, NULL, c(5.5, 0, 0, 0), NULL, TRUE), "panel", list(NULL, NULL, NULL, 1.2, 0.5, 0.5, NULL, NULL, NULL, NULL, TRUE), "topleft", NULL, NULL, list("grey85", NA, NULL, + NULL, TRUE), NULL, NULL, "inherit", "inside", list(NULL, NULL, "grey10", 0.8, NULL, NULL, NULL, NULL, c(4.4, 4.4, 4.4, 4.4), NULL, TRUE), NULL, NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, NULL, -90, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, NULL, 90, NULL, NULL, NULL, TRUE), NULL, 2.75, 2.75)) + --- failed re-building ‘rvar.Rmd’ - When sourcing ‘rotations-intro.R’: - Error: Theme element `plot.margin` must have class . - Execution halted + SUMMARY: processing the following file failed: + ‘rvar.Rmd’ - ‘rotations-intro.Rnw’ using ‘UTF-8’... failed + Error: Vignette re-building failed. + Execution halted ``` ## In both -* checking C++ specification ... NOTE - ``` - Specified C++11: please drop specification unless essential - ``` - -* checking installed package size ... NOTE - ``` - installed size is 19.1Mb - sub-directories of 1Mb or more: - R 3.5Mb - data 7.0Mb - libs 8.0Mb - ``` - -* checking re-building of vignette outputs ... NOTE +* checking running R code from vignettes ... ERROR ``` - Error(s) in re-building vignettes: + Errors in running code in vignettes: + when running code in ‘rvar.Rmd’ ... - --- re-building ‘rotations-intro.Rnw’ using knitr - - Quitting from lines 324-336 [ex7] (rotations-intro.Rnw) - Error: processing vignette 'rotations-intro.Rnw' failed with diagnostics: - Theme element `plot.margin` must have class . - --- failed re-building ‘rotations-intro.Rnw’ + > y + rvar<4000>[3] mean ± sd: + [1] 3.00 ± 1.00 2.02 ± 0.99 0.96 ± 0.99 - SUMMARY: processing the following file failed: - ‘rotations-intro.Rnw’ + > X + y - Error: Vignette re-building failed. + When sourcing ‘rvar.R’: + Error: Cannot broadcast array of shape [4000,3,1] to array of shape [4000,4,3]: + All dimensions must be 1 or equal. Execution halted + + ‘pareto_diagnostics.Rmd’ using ‘UTF-8’... OK + ‘posterior.Rmd’ using ‘UTF-8’... OK + ‘rvar.Rmd’ using ‘UTF-8’... failed ``` -# rreg +# PPQplan
-* Version: 0.2.1 -* GitHub: NA -* Source code: https://github.com/cran/rreg -* Date/Publication: 2018-03-22 14:11:31 UTC -* Number of recursive dependencies: 50 +* Version: 1.1.0 +* GitHub: https://github.com/allenzhuaz/PPQplan +* Source code: https://github.com/cran/PPQplan +* Date/Publication: 2020-10-08 04:30:06 UTC +* Number of recursive dependencies: 119 -Run `revdepcheck::cloud_details(, "rreg")` for more info +Run `revdepcheck::cloud_details(, "PPQplan")` for more info
## Newly broken -* checking examples ... ERROR +* checking re-building of vignette outputs ... NOTE ``` - Running examples in ‘rreg-Ex.R’ failed - The error most likely occurred in: + Error(s) in re-building vignettes: + --- re-building ‘PPQnote.Rmd’ using rmarkdown + --- finished re-building ‘PPQnote.Rmd’ - > ### Name: regbar - > ### Title: Barplot with explicit data comparison - > ### Aliases: regbar - > - > ### ** Examples - > - > # basic usage - ... - Backtrace: - ▆ - 1. ├─base (local) ``(x) - 2. └─ggplot2:::print.ggplot(x) - 3. ├─ggplot2::ggplot_gtable(data) - 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) - 5. └─ggplot2::calc_element("plot.margin", theme) - 6. └─cli::cli_abort(...) - 7. └─rlang::abort(...) - Execution halted + --- re-building ‘PPQplan-vignette.Rmd’ using rmarkdown ``` -# rSDI - -
- -* Version: 0.2.1 -* GitHub: https://github.com/ehengirmen/rSDI -* Source code: https://github.com/cran/rSDI -* Date/Publication: 2024-05-30 07:40:02 UTC -* Number of recursive dependencies: 93 - -Run `revdepcheck::cloud_details(, "rSDI")` for more info - -
- -## Newly broken +## In both * checking running R code from vignettes ... ERROR ``` Errors in running code in vignettes: - when running code in ‘rSDI.Rmd’ + when running code in ‘PPQplan-vignette.Rmd’ ... - |A | 0| 3| - |B | 4| 0| - |C | 0| 0| - |D | 4| 3| - > p + > devtools::load_all() - When sourcing ‘rSDI.R’: - Error: Theme element `plot.margin` must have class . + When sourcing ‘PPQplan-vignette.R’: + Error: Could not find a root 'DESCRIPTION' file that starts with '^Package' in + '/tmp/RtmpjusJAT/filef521ca1f964/vignettes'. + ℹ Are you in your project directory and does your project have a 'DESCRIPTION' + file? Execution halted - ‘rSDI.Rmd’ using ‘UTF-8’... failed + ‘PPQnote.Rmd’ using ‘UTF-8’... OK + ‘PPQplan-vignette.Rmd’ using ‘UTF-8’... failed ``` -* checking re-building of vignette outputs ... NOTE +* checking installed package size ... NOTE ``` - Error(s) in re-building vignettes: - ... - --- re-building ‘rSDI.Rmd’ using rmarkdown - - Quitting from lines 82-83 [unnamed-chunk-5] (rSDI.Rmd) - Error: processing vignette 'rSDI.Rmd' failed with diagnostics: - Theme element `plot.margin` must have class . - --- failed re-building ‘rSDI.Rmd’ - - SUMMARY: processing the following file failed: - ‘rSDI.Rmd’ - - Error: Vignette re-building failed. - Execution halted + installed size is 12.1Mb + sub-directories of 1Mb or more: + doc 12.0Mb + ``` + +* checking LazyData ... NOTE + ``` + 'LazyData' is specified without a 'data' directory ``` -# SangerTools +# ppseq
-* Version: 1.0.2 -* GitHub: NA -* Source code: https://github.com/cran/SangerTools -* Date/Publication: 2022-02-20 13:10:02 UTC -* Number of recursive dependencies: 104 +* Version: 0.2.4 +* GitHub: https://github.com/zabore/ppseq +* Source code: https://github.com/cran/ppseq +* Date/Publication: 2024-04-04 18:20:02 UTC +* Number of recursive dependencies: 106 -Run `revdepcheck::cloud_details(, "SangerTools")` for more info +Run `revdepcheck::cloud_details(, "ppseq")` for more info
## Newly broken -* checking examples ... ERROR - ``` - Running examples in ‘SangerTools-Ex.R’ failed - The error most likely occurred in: - - > ### Name: categorical_col_chart - > ### Title: Plot Counts of Categorical Variables - > ### Aliases: categorical_col_chart - > - > ### ** Examples - > - > library(SangerTools) - ... - Backtrace: - ▆ - 1. ├─base (local) ``(x) - 2. └─ggplot2:::print.ggplot(x) - 3. ├─ggplot2::ggplot_gtable(data) - 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) - 5. └─ggplot2::calc_element("plot.margin", theme) - 6. └─cli::cli_abort(...) - 7. └─rlang::abort(...) - Execution halted - ``` - * checking running R code from vignettes ... ERROR ``` Errors in running code in vignettes: - when running code in ‘SangerTools_Vignette.Rmd’ + when running code in ‘one_sample_expansion.Rmd’ ... + - > diabetes_df <- health_data %>% dplyr::filter(Diabetes == - + 1) + + + > ptest <- plot(one_sample_cal_tbl, type1_range = c(0.05, + + 0.1), minimum_power = 0.7, plotly = TRUE) - > SangerTools::categorical_col_chart(df = diabetes_df, - + grouping_var = Ethnicity) + scale_fill_sanger() + labs(title = "Diabetic Patients by Eth ..." ... [TRUNCATED] + ... + + > ptest <- plot(two_sample_cal_tbl, type1_range = c(0.05, + + 0.1), minimum_power = 0.7, plotly = TRUE) - When sourcing ‘SangerTools_Vignette.R’: - Error: Theme element `plot.margin` must have class . + When sourcing ‘two_sample_randomized.R’: + Error: subscript out of bounds Execution halted - ‘SangerTools_Vignette.Rmd’ using ‘UTF-8’... failed + ‘one_sample_expansion.Rmd’ using ‘UTF-8’... failed + ‘two_sample_randomized.Rmd’ using ‘UTF-8’... failed ``` * checking re-building of vignette outputs ... NOTE ``` Error(s) in re-building vignettes: ... - --- re-building ‘SangerTools_Vignette.Rmd’ using rmarkdown + --- re-building ‘one_sample_expansion.Rmd’ using rmarkdown + + Quitting from lines 183-188 [unnamed-chunk-13] (one_sample_expansion.Rmd) + Error: processing vignette 'one_sample_expansion.Rmd' failed with diagnostics: + subscript out of bounds + --- failed re-building ‘one_sample_expansion.Rmd’ - Quitting from lines 119-140 [categorical_column_chart] (SangerTools_Vignette.Rmd) - Error: processing vignette 'SangerTools_Vignette.Rmd' failed with diagnostics: - Theme element `plot.margin` must have class . - --- failed re-building ‘SangerTools_Vignette.Rmd’ + --- re-building ‘two_sample_randomized.Rmd’ using rmarkdown + ... + Quitting from lines 179-184 [unnamed-chunk-13] (two_sample_randomized.Rmd) + Error: processing vignette 'two_sample_randomized.Rmd' failed with diagnostics: + subscript out of bounds + --- failed re-building ‘two_sample_randomized.Rmd’ - SUMMARY: processing the following file failed: - ‘SangerTools_Vignette.Rmd’ + SUMMARY: processing the following files failed: + ‘one_sample_expansion.Rmd’ ‘two_sample_randomized.Rmd’ Error: Vignette re-building failed. Execution halted ``` -# santaR +## In both + +* checking installed package size ... NOTE + ``` + installed size is 11.0Mb + sub-directories of 1Mb or more: + doc 10.5Mb + ``` + +# precrec
-* Version: 1.2.4 -* GitHub: https://github.com/adwolfer/santaR -* Source code: https://github.com/cran/santaR -* Date/Publication: 2024-03-07 00:30:02 UTC -* Number of recursive dependencies: 93 +* Version: 0.14.4 +* GitHub: https://github.com/evalclass/precrec +* Source code: https://github.com/cran/precrec +* Date/Publication: 2023-10-11 22:10:02 UTC +* Number of recursive dependencies: 71 -Run `revdepcheck::cloud_details(, "santaR")` for more info +Run `revdepcheck::cloud_details(, "precrec")` for more info
## Newly broken -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘advanced-command-line-functions.Rmd’ using rmarkdown - ``` - -## In both - * checking running R code from vignettes ... ERROR ``` Errors in running code in vignettes: - when running code in ‘getting-started.Rmd’ + when running code in ‘introduction.Rmd’ ... + > msmdat3 <- mmdata(samps2[["scores"]], samps2[["labels"]], + + modnames = samps2[["modnames"]]) - > knitr::include_graphics("../man/figures/santaR-approach.jpg") + > mscurves <- evalmod(msmdat3) - When sourcing ‘getting-started.R’: - Error: Cannot find the file(s): "../man/figures/santaR-approach.jpg" - Execution halted - when running code in ‘selecting-optimal-df.Rmd’ - ... + > autoplot(mscurves) + + When sourcing ‘introduction.R’: + Error: object is not a unit Execution halted - ‘advanced-command-line-functions.Rmd’ using ‘UTF-8’... OK - ‘automated-command-line.Rmd’ using ‘UTF-8’... OK - ‘getting-started.Rmd’ using ‘UTF-8’... failed - ‘plotting-options.Rmd’ using ‘UTF-8’... OK - ‘prepare-input-data.Rmd’ using ‘UTF-8’... OK - ‘selecting-optimal-df.Rmd’ using ‘UTF-8’... failed - ‘theoretical-background.Rmd’ using ‘UTF-8’... failed - ‘santaR-GUI.pdf.asis’ using ‘UTF-8’... OK + ‘introduction.Rmd’ using ‘UTF-8’... failed ``` -# scoringutils +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘introduction.Rmd’ using rmarkdown + ``` + +## In both + +* checking installed package size ... NOTE + ``` + installed size is 6.5Mb + sub-directories of 1Mb or more: + libs 4.2Mb + ``` + +# priorsense
-* Version: 1.2.2 -* GitHub: https://github.com/epiforecasts/scoringutils -* Source code: https://github.com/cran/scoringutils -* Date/Publication: 2023-11-29 15:50:10 UTC -* Number of recursive dependencies: 81 +* Version: 1.0.1 +* GitHub: NA +* Source code: https://github.com/cran/priorsense +* Date/Publication: 2024-06-24 14:40:02 UTC +* Number of recursive dependencies: 113 -Run `revdepcheck::cloud_details(, "scoringutils")` for more info +Run `revdepcheck::cloud_details(, "priorsense")` for more info
@@ -18004,387 +10279,287 @@ Run `revdepcheck::cloud_details(, "scoringutils")` for more info * checking examples ... ERROR ``` - Running examples in ‘scoringutils-Ex.R’ failed + Running examples in ‘priorsense-Ex.R’ failed The error most likely occurred in: - > ### Name: plot_predictions - > ### Title: Plot Predictions vs True Values - > ### Aliases: plot_predictions + > ### Name: powerscale_plots + > ### Title: Diagnostic plots for power-scaling sensitivity + > ### Aliases: powerscale_plots powerscale_plot_dens powerscale_plot_ecdf + > ### powerscale_plot_ecdf.powerscaled_sequence powerscale_plot_quantities + > ### powerscale_plot_quantities.powerscaled_sequence > > ### ** Examples > - > library(ggplot2) - ... - + by = c("target_type", "location"), - + range = c(0, 50, 90, 95) - + ) + - + facet_wrap(~ location + target_type, scales = "free_y") + - + aes(fill = model, color = model) + > ex <- example_powerscale_model() + > + > powerscale_plot_dens(ex$draws) Error in use_defaults(..., self = self) : - unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, "black", TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), NULL, list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), 5.5, c(5.5, 5.5, 5.5, 5.5), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.75, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, - NULL, NULL, NULL, 1, 90, NULL, c(0, 2.75, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 1, NULL, NULL, NULL, c(0, 2.2, 0, 0), NULL, TRUE), NULL, l + unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, "black", TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), list(NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), 5.5, c(5.5, 5.5, 5.5, 5.5), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.75, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, + NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, 90, NULL, c(0, 2.75, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(), NULL, list(NU Calls: ... -> -> compute_geom_2 -> Execution halted ``` -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘metric-details.Rmd’ using rmarkdown - --- finished re-building ‘metric-details.Rmd’ - - --- re-building ‘scoring-forecasts-directly.Rmd’ using rmarkdown - --- finished re-building ‘scoring-forecasts-directly.Rmd’ - - --- re-building ‘scoringutils.Rmd’ using rmarkdown - ``` - -## In both - * checking running R code from vignettes ... ERROR ``` Errors in running code in vignettes: - when running code in ‘scoringutils.Rmd’ + when running code in ‘powerscaling.Rmd’ ... - The following messages were produced when checking inputs: - 1. 144 values for `prediction` are NA in the data provided and the corresponding rows were removed. This may indicate a problem if unexpected. + + 1 mu 0.393 0.563 prior-data conflict + 2 sigma 0.291 0.532 prior-data conflict - > example_quantile %>% make_NA(what = "truth", target_end_date >= - + "2021-07-15", target_end_date < "2021-05-22") %>% make_NA(what = "forecast", .... [TRUNCATED] + > powerscale_plot_dens(fit, variable = "mu") - When sourcing ‘scoringutils.R’: - Error: unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, "black", TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), NULL, list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), 5.5, c(5.5, 5.5, 5.5, 5.5), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.75, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, - NULL, NULL, NULL, 1, 90, NULL, c(0, 2.75, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 1, NULL, NULL, NULL, c(0, 2.2, 0, 0), NULL, TRUE), NULL, lis + When sourcing ‘powerscaling.R’: + Error: unused argument (theme = list(list("black", 0.545454545454545, 1, "butt", FALSE, "black", TRUE), list("white", "black", 0.545454545454545, 1, TRUE), list("sans", "plain", "black", 12, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), list(NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list("black", "white", "#3366FF", 0.545454545454545, 1.09090909090909, "sans", 4.21751764217518, 1.63636363636364, 19, TRUE), 6, c(6, 6, 6, 6), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, + c(3, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 3, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, 90, NULL, c(0, 3, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 3), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.4, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0 Execution halted - ‘metric-details.Rmd’ using ‘UTF-8’... OK - ‘scoring-forecasts-directly.Rmd’ using ‘UTF-8’... OK - ‘scoringutils.Rmd’ using ‘UTF-8’... failed + ‘powerscaling.Rmd’ using ‘UTF-8’... failed ``` -# SCVA - -
- -* Version: 1.3.1 -* GitHub: NA -* Source code: https://github.com/cran/SCVA -* Date/Publication: 2020-01-09 22:50:10 UTC -* Number of recursive dependencies: 80 - -Run `revdepcheck::cloud_details(, "SCVA")` for more info - -
- -## Newly broken - -* checking examples ... ERROR +* checking re-building of vignette outputs ... NOTE ``` - Running examples in ‘SCVA-Ex.R’ failed - The error most likely occurred in: + Error(s) in re-building vignettes: + ... + --- re-building ‘powerscaling.Rmd’ using rmarkdown - > ### Name: graphly - > ### Title: Interactive plot of single-case data - > ### Aliases: graphly - > ### Keywords: Single-case design Graph - > - > ### ** Examples - > - > data(AB) - > graphly(design = "AB", data = AB) - Error in pm[[2]] : subscript out of bounds - Calls: graphly -> ggplotly -> ggplotly.ggplot -> gg2list + Quitting from lines 118-119 [unnamed-chunk-6] (powerscaling.Rmd) + Error: processing vignette 'powerscaling.Rmd' failed with diagnostics: + unused argument (theme = list(list("black", 0.545454545454545, 1, "butt", FALSE, "black", TRUE), list("white", "black", 0.545454545454545, 1, TRUE), list("sans", "plain", "black", 12, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), list(NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list("black", "white", "#3366FF", 0.545454545454545, 1.09090909090909, "sans", 4.21751764217518, 1.63636363636364, 19, TRUE), 6, c(6, 6, 6, 6), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, + c(3, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 3, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, 90, NULL, c(0, 3, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 3), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.4, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.4, 0), NULL, + TRUE), NULL, list(), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, NULL, c(0, 0, 0, 2.4), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0.5, NULL, NULL, NULL, c(0, 2.4, 0, 2.4), NULL, TRUE), list("grey20", 0.3, NULL, NULL, FALSE, "grey20", FALSE), NULL, NULL, NULL, list(), NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 0.5, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 0.75, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, list(NULL, 0.4, NULL, NULL, FALSE, NULL, FALSE), NULL, + NULL, NULL, list(), NULL, NULL, NULL, NULL, list(), NULL, 2, NULL, NULL, list(), 1.2, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 0.2, NULL, list(NULL, NULL, NULL, 13, 0, NULL, NULL, NULL, NULL, NULL, FALSE), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, NULL, NULL, NULL, TRUE), NULL, "bottom", NULL, NULL, NULL, "center", NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 0, list(), 2, list(), list(), 1.5, NULL, NULL, list(), NULL, list(NULL, 0.5, NULL, NULL, FALSE, NULL, TRUE), NULL, NULL, NULL, + NULL, FALSE, list(), list(NULL, NULL, NULL, 1.2, 0, 1, NULL, NULL, c(0, 0, 6, 0), NULL, TRUE), "panel", list(NULL, NULL, NULL, NULL, 0, 1, NULL, NULL, c(0, 0, 6, 0), NULL, TRUE), list(NULL, NULL, NULL, 0.8, 1, 1, NULL, NULL, c(6, 0, 0, 0), NULL, TRUE), "panel", list(NULL, NULL, NULL, 1.2, 0.5, 0.5, NULL, NULL, NULL, NULL, TRUE), "topleft", NULL, NULL, list(), NULL, NULL, "inherit", "outside", list(NULL, NULL, "grey10", 0.9, NULL, NULL, NULL, NULL, c(4.8, 4.8, 4.8, 4.8), NULL, FALSE), NULL, NULL, + NULL, list(NULL, NULL, NULL, NULL, NULL, NULL, -90, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, NULL, 90, NULL, NULL, NULL, TRUE), NULL, 3, 3, list(), list(NULL, NULL, NULL, NULL, FALSE, NULL, TRUE), list(NULL, NULL, NULL, NULL, FALSE, NULL, TRUE), list(NULL, NULL, NULL, NULL, FALSE, NULL, TRUE), list(NULL, NULL, NULL, NULL, 0.5, 0.5, 0, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), 0.666666666666667, 0.333333333333333)) + --- failed re-building ‘powerscaling.Rmd’ + + SUMMARY: processing the following file failed: + ‘powerscaling.Rmd’ + + Error: Vignette re-building failed. Execution halted ``` -# SDLfilter +# ProAE
-* Version: 2.3.3 -* GitHub: https://github.com/TakahiroShimada/SDLfilter -* Source code: https://github.com/cran/SDLfilter -* Date/Publication: 2023-11-10 00:00:11 UTC -* Number of recursive dependencies: 80 +* Version: 1.0.1 +* GitHub: NA +* Source code: https://github.com/cran/ProAE +* Date/Publication: 2024-06-17 23:30:03 UTC +* Number of recursive dependencies: 126 -Run `revdepcheck::cloud_details(, "SDLfilter")` for more info +Run `revdepcheck::cloud_details(, "ProAE")` for more info
## Newly broken -* checking examples ... ERROR +* checking running R code from vignettes ... ERROR ``` - Running examples in ‘SDLfilter-Ex.R’ failed - The error most likely occurred in: + Errors in running code in vignettes: + when running code in ‘toxFigures.Rmd’ + ... + $ PROCTCAE_9B_SCL: num 0 2 3 3 0 1 0 0 0 0 ... + $ PROCTCAE_9_COMP: num 0 2 3 0 0 0 0 0 0 0 ... + $ time : chr "Cycle 1" "Cycle 2" "Cycle 3" "Cycle 4" ... - > ### Name: ddfilter - > ### Title: Filter locations using a data driven filter - > ### Aliases: ddfilter - > - > ### ** Examples - > - > #### Load data sets - ... - 2. ├─base::do.call(arrangeGrob, c(list(grobs = groups[[g]]), params)) - 3. └─gridExtra (local) ``(grobs = ``, top = "page 1 of 1", layout_matrix = ``) - 4. └─base::lapply(grobs[toconv], ggplot2::ggplotGrob) - 5. └─ggplot2 (local) FUN(X[[i]], ...) - 6. ├─ggplot2::ggplot_gtable(ggplot_build(x)) - 7. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) - 8. └─ggplot2::calc_element("plot.margin", theme) - 9. └─cli::cli_abort(...) - 10. └─rlang::abort(...) + > figure_1 <- toxFigures(dsn = acute, cycle_var = "Cycle", + + baseline_val = 1, arm_var = "arm", id_var = "id") + + When sourcing ‘toxFigures.R’: + Error: attempt to set an attribute on NULL Execution halted + + ‘toxAUC.Rmd’ using ‘UTF-8’... OK + ‘toxFigures.Rmd’ using ‘UTF-8’... failed + ‘toxTables.Rmd’ using ‘UTF-8’... OK ``` -# see - -
- -* Version: 0.8.4 -* GitHub: https://github.com/easystats/see -* Source code: https://github.com/cran/see -* Date/Publication: 2024-04-29 04:40:03 UTC -* Number of recursive dependencies: 233 - -Run `revdepcheck::cloud_details(, "see")` for more info - -
- -## Newly broken - -* checking examples ... ERROR +* checking re-building of vignette outputs ... NOTE ``` - Running examples in ‘see-Ex.R’ failed - The error most likely occurred in: - - > ### Name: geom_binomdensity - > ### Title: Add dot-densities for binary 'y' variables - > ### Aliases: geom_binomdensity - > - > ### ** Examples - > - > ## Don't show: - ... - 14. │ └─ggplot2 (local) f(l = layers[[i]], d = data[[i]]) - 15. │ └─l$compute_geom_2(d, theme = plot$theme) - 16. │ └─ggplot2 (local) compute_geom_2(..., self = self) - 17. │ └─self$geom$use_defaults(...) - 18. └─base::.handleSimpleError(...) - 19. └─rlang (local) h(simpleError(msg, call)) - 20. └─handlers[[1L]](cnd) - 21. └─cli::cli_abort(...) - 22. └─rlang::abort(...) - Execution halted + Error(s) in re-building vignettes: + --- re-building ‘toxAUC.Rmd’ using rmarkdown ``` -# sentimentr +# probably
-* Version: 2.9.0 -* GitHub: https://github.com/trinker/sentimentr -* Source code: https://github.com/cran/sentimentr -* Date/Publication: 2021-10-12 08:30:02 UTC -* Number of recursive dependencies: 66 +* Version: 1.0.3 +* GitHub: https://github.com/tidymodels/probably +* Source code: https://github.com/cran/probably +* Date/Publication: 2024-02-23 03:20:02 UTC +* Number of recursive dependencies: 131 -Run `revdepcheck::cloud_details(, "sentimentr")` for more info +Run `revdepcheck::cloud_details(, "probably")` for more info
## Newly broken -* checking examples ... ERROR +* checking tests ... ERROR ``` - Running examples in ‘sentimentr-Ex.R’ failed - The error most likely occurred in: - - > ### Name: sentiment - > ### Title: Polarity Score (Sentiment Analysis) - > ### Aliases: sentiment - > - > ### ** Examples - > - > mytext <- c( + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > # This file is part of the standard setup for testthat. + > # It is recommended that you do not modify it. + > # + > # Where should you do additional test configuration? + > # Learn more about the roles of various files in: + > # * https://r-pkgs.org/tests.html + > # * https://testthat.r-lib.org/reference/test_package.html#special-files ... - Backtrace: - ▆ - 1. ├─base (local) ``(x) - 2. └─ggplot2:::print.ggplot(x) - 3. ├─ggplot2::ggplot_gtable(data) - 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) - 5. └─ggplot2::calc_element("plot.margin", theme) - 6. └─cli::cli_abort(...) - 7. └─rlang::abort(...) - Execution halted - ``` - -## In both - -* checking installed package size ... NOTE - ``` - installed size is 5.5Mb - sub-directories of 1Mb or more: - data 5.0Mb + + `actual$ymin` is absent + `expected$ymin` is a character vector ('lower') + + `actual$ymax` is absent + `expected$ymax` is a character vector ('upper') + + [ FAIL 2 | WARN 0 | SKIP 46 | PASS 466 ] + Error: Test failures + Execution halted ``` -# sentometrics +# processmapR
-* Version: 1.0.0 -* GitHub: https://github.com/SentometricsResearch/sentometrics -* Source code: https://github.com/cran/sentometrics -* Date/Publication: 2021-08-18 07:50:02 UTC -* Number of recursive dependencies: 127 +* Version: 0.5.4 +* GitHub: https://github.com/bupaverse/processmapr +* Source code: https://github.com/cran/processmapR +* Date/Publication: 2024-07-15 13:10:01 UTC +* Number of recursive dependencies: 118 -Run `revdepcheck::cloud_details(, "sentometrics")` for more info +Run `revdepcheck::cloud_details(, "processmapR")` for more info
## Newly broken -* checking examples ... ERROR +* checking tests ... ERROR ``` - Running examples in ‘sentometrics-Ex.R’ failed - The error most likely occurred in: - - > ### Name: plot.sento_measures - > ### Title: Plot sentiment measures - > ### Aliases: plot.sento_measures - > - > ### ** Examples - > - > # construct a sento_measures object to start with + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(processmapR) + + Attaching package: 'processmapR' + + The following object is masked from 'package:stats': + ... - Backtrace: - ▆ - 1. ├─base (local) ``(x) - 2. └─ggplot2:::print.ggplot(x) - 3. ├─ggplot2::ggplot_gtable(data) - 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) - 5. └─ggplot2::calc_element("plot.margin", theme) - 6. └─cli::cli_abort(...) - 7. └─rlang::abort(...) - Execution halted - ``` - -## In both - -* checking C++ specification ... NOTE - ``` - Specified C++11: please drop specification unless essential - ``` - -* checking installed package size ... NOTE - ``` - installed size is 9.7Mb - sub-directories of 1Mb or more: - data 2.3Mb - libs 6.2Mb - ``` - -* checking data for non-ASCII characters ... NOTE - ``` - Note: found 4436 marked UTF-8 strings - ``` - -* checking for GNU extensions in Makefiles ... NOTE - ``` - GNU make is a SystemRequirements. + 10. └─processmapR:::return_plotly(p, plotly) + 11. ├─plotly::ggplotly(p) + 12. └─plotly:::ggplotly.ggplot(p) + 13. └─plotly::gg2list(...) + ── Failure ('test_trace_explorer.R:240:3'): test trace_explorer on eventlog with param `plotly` ── + `chart` inherits from 'gg'/'ggplot' not 'plotly'. + + [ FAIL 6 | WARN 0 | SKIP 10 | PASS 107 ] + Error: Test failures + Execution halted ``` -# sglg +# psborrow
-* Version: 0.2.2 +* Version: 0.2.1 * GitHub: NA -* Source code: https://github.com/cran/sglg -* Date/Publication: 2022-09-04 03:50:01 UTC -* Number of recursive dependencies: 96 +* Source code: https://github.com/cran/psborrow +* Date/Publication: 2023-03-03 10:30:07 UTC +* Number of recursive dependencies: 108 -Run `revdepcheck::cloud_details(, "sglg")` for more info +Run `revdepcheck::cloud_details(, "psborrow")` for more info
## Newly broken -* checking examples ... ERROR +* checking tests ... ERROR ``` - Running examples in ‘sglg-Ex.R’ failed - The error most likely occurred in: - - > ### Name: deviance_residuals - > ### Title: Deviance Residuals for a Generalized Log-gamma Regression Model - > ### Aliases: deviance_residuals - > - > ### ** Examples - > - > # Example 1 - > n <- 300 - > error <- rglg(n,0,1,1) - > y <- 0.5 + error - > fit <- glg(y~1,data=as.data.frame(y)) - > deviance_residuals(fit) - Error in pm[[2]] : subscript out of bounds - Calls: deviance_residuals ... dots2plots -> ggplotly -> ggplotly.ggplot -> gg2list - Execution halted + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(psborrow) + > + > test_check("psborrow") + [ FAIL 10 | WARN 0 | SKIP 1 | PASS 142 ] + + ══ Skipped tests (1) ═══════════════════════════════════════════════════════════ + ... + `expected` is a character vector ('ref') + ── Failure ('test-plots.R:126:5'): Ensure output is producing a ggplot2 object with appropriate parameters ── + p1$labels$yintercept (`actual`) not equal to "ref" (`expected`). + + `actual` is NULL + `expected` is a character vector ('ref') + + [ FAIL 10 | WARN 0 | SKIP 1 | PASS 142 ] + Error: Test failures + Execution halted ``` -# SHAPforxgboost +# r2dii.plot
-* Version: 0.1.3 -* GitHub: https://github.com/liuyanguu/SHAPforxgboost -* Source code: https://github.com/cran/SHAPforxgboost -* Date/Publication: 2023-05-29 17:20:07 UTC -* Number of recursive dependencies: 120 +* Version: 0.4.0 +* GitHub: https://github.com/RMI-PACTA/r2dii.plot +* Source code: https://github.com/cran/r2dii.plot +* Date/Publication: 2024-02-29 16:40:02 UTC +* Number of recursive dependencies: 91 -Run `revdepcheck::cloud_details(, "SHAPforxgboost")` for more info +Run `revdepcheck::cloud_details(, "r2dii.plot")` for more info
## Newly broken -* checking examples ... ERROR +* checking tests ... ERROR ``` - Running examples in ‘SHAPforxgboost-Ex.R’ failed - The error most likely occurred in: - - > ### Name: scatter.plot.diagonal - > ### Title: Make customized scatter plot with diagonal line and R2 printed. - > ### Aliases: scatter.plot.diagonal - > - > ### ** Examples - > - > scatter.plot.diagonal(data = iris, x = "Sepal.Length", y = "Petal.Length") + Running ‘spelling.R’ + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(r2dii.plot) + > + > test_check("r2dii.plot") + Scale for colour is already present. + Adding another scale for colour, which will replace the existing scale. ... - ▆ - 1. └─SHAPforxgboost::scatter.plot.diagonal(...) - 2. └─ggExtra::ggMarginal(...) - 3. └─ggplot2::ggplotGrob(scatP) - 4. ├─ggplot2::ggplot_gtable(ggplot_build(x)) - 5. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) - 6. └─ggplot2::calc_element("plot.margin", theme) - 7. └─cli::cli_abort(...) - 8. └─rlang::abort(...) - Execution halted + `expected` is a character vector ('year') + ── Failure ('test-plot_trajectory.R:41:3'): outputs default axis labels ──────── + p$labels$y (`actual`) not equal to "value" (`expected`). + + `actual` is NULL + `expected` is a character vector ('value') + + [ FAIL 2 | WARN 2 | SKIP 40 | PASS 122 ] + Error: Test failures + Execution halted ``` -# shazam +# Radviz
-* Version: 1.2.0 -* GitHub: NA -* Source code: https://github.com/cran/shazam -* Date/Publication: 2023-10-02 18:50:02 UTC -* Number of recursive dependencies: 127 +* Version: 0.9.3 +* GitHub: https://github.com/yannabraham/Radviz +* Source code: https://github.com/cran/Radviz +* Date/Publication: 2022-03-25 18:10:02 UTC +* Number of recursive dependencies: 64 -Run `revdepcheck::cloud_details(, "shazam")` for more info +Run `revdepcheck::cloud_details(, "Radviz")` for more info
@@ -18392,88 +10567,68 @@ Run `revdepcheck::cloud_details(, "shazam")` for more info * checking examples ... ERROR ``` - Running examples in ‘shazam-Ex.R’ failed + Running examples in ‘Radviz-Ex.R’ failed The error most likely occurred in: - > ### Name: plotMutability - > ### Title: Plot mutability probabilities - > ### Aliases: plotMutability + > ### Name: Radviz + > ### Title: Radviz Projection of Multidimensional Data + > ### Aliases: Radviz > > ### ** Examples > - > # Plot one nucleotide in circular style - ... - 3. └─alakazam (local) ``(C = ``, ncol = 1L) - 4. ├─base::plot(p[[1]]) - 5. ├─base::plot(p[[1]]) - 6. └─ggplot2:::plot.ggplot(p[[1]]) - 7. ├─ggplot2::ggplot_gtable(data) - 8. └─ggplot2:::ggplot_gtable.ggplot_built(data) - 9. └─ggplot2::calc_element("plot.margin", theme) - 10. └─cli::cli_abort(...) - 11. └─rlang::abort(...) + > data(iris) + > das <- c('Sepal.Length','Sepal.Width','Petal.Length','Petal.Width') + > S <- make.S(das) + > rv <- do.radviz(iris,S) + > plot(rv,anchors.only=FALSE) + Error in plot.radviz(rv, anchors.only = FALSE) : + 'language' object cannot be coerced to type 'double' + Calls: plot -> plot.radviz Execution halted ``` * checking running R code from vignettes ... ERROR ``` Errors in running code in vignettes: - when running code in ‘Targeting-Vignette.Rmd’ + when running code in ‘multivariate_analysis.Rmd’ ... - + sequenceColumn = "clonal_sequence", germlineColumn = "clonal_germline", - + vCallColu .... [TRUNCATED] - Warning in createMutabilityMatrix(db, sub_mat, model = model, sequenceColumn = sequenceColumn, : - Insufficient number of mutations to infer some 5-mers. Filled with 0. - > plotMutability(model, nucleotides = "A", style = "hedgehog") + > classic.S <- make.S(get.optim(classic.optim)) + + > btcells.rv <- do.radviz(btcells.df, classic.S) + + > plot(btcells.rv) + geom_point(aes(color = Treatment)) + + ... + [1] 15792 18 + + > ct.rv - When sourcing ‘Targeting-Vignette.R’: - Error: Theme element `plot.margin` must have class . + When sourcing ‘single_cell_projections.R’: + Error: 'language' object cannot be coerced to type 'double' Execution halted - ‘Baseline-Vignette.Rmd’ using ‘UTF-8’... OK - ‘DistToNearest-Vignette.Rmd’ using ‘UTF-8’... OK - ‘Mutation-Vignette.Rmd’ using ‘UTF-8’... OK - ‘Shmulate-Vignette.Rmd’ using ‘UTF-8’... OK - ‘Targeting-Vignette.Rmd’ using ‘UTF-8’... failed + ‘multivariate_analysis.Rmd’ using ‘UTF-8’... failed + ‘single_cell_projections.Rmd’ using ‘UTF-8’... failed ``` * checking re-building of vignette outputs ... NOTE ``` Error(s) in re-building vignettes: - ... - --- re-building ‘Baseline-Vignette.Rmd’ using rmarkdown - --- finished re-building ‘Baseline-Vignette.Rmd’ - - --- re-building ‘DistToNearest-Vignette.Rmd’ using rmarkdown - --- finished re-building ‘DistToNearest-Vignette.Rmd’ - - --- re-building ‘Mutation-Vignette.Rmd’ using rmarkdown - --- finished re-building ‘Mutation-Vignette.Rmd’ - ... - Quitting from lines 167-170 [unnamed-chunk-8] (Targeting-Vignette.Rmd) - Error: processing vignette 'Targeting-Vignette.Rmd' failed with diagnostics: - Theme element `plot.margin` must have class . - --- failed re-building ‘Targeting-Vignette.Rmd’ - - SUMMARY: processing the following file failed: - ‘Targeting-Vignette.Rmd’ - - Error: Vignette re-building failed. - Execution halted + --- re-building ‘multivariate_analysis.Rmd’ using rmarkdown ``` -# simulariatools +# rassta
-* Version: 2.5.1 -* GitHub: https://github.com/Simularia/simulariatools -* Source code: https://github.com/cran/simulariatools -* Date/Publication: 2023-11-08 14:10:02 UTC -* Number of recursive dependencies: 96 +* Version: 1.0.5 +* GitHub: https://github.com/bafuentes/rassta +* Source code: https://github.com/cran/rassta +* Date/Publication: 2022-08-30 22:30:02 UTC +* Number of recursive dependencies: 120 -Run `revdepcheck::cloud_details(, "simulariatools")` for more info +Run `revdepcheck::cloud_details(, "rassta")` for more info
@@ -18481,112 +10636,169 @@ Run `revdepcheck::cloud_details(, "simulariatools")` for more info * checking examples ... ERROR ``` - Running examples in ‘simulariatools-Ex.R’ failed + Running examples in ‘rassta-Ex.R’ failed The error most likely occurred in: - > ### Name: plotAvgTemp - > ### Title: Plot average temperature - > ### Aliases: plotAvgTemp + > ### Name: select_functions + > ### Title: Select Constrained Univariate Distribution Functions + > ### Aliases: select_functions > > ### ** Examples > - > # Plot histogram with monthly averages together with maxima and minima + > require(terra) + ... + > tvars <- terra::rast(tf) + > # Single-layer SpatRaster of topographic classification units + > ## 5 classification units + > tcf <- list.files(path = p, pattern = "topography.tif", full.names = TRUE) + > tcu <- terra::rast(tcf) + > # Automatic selection of distribution functions + > tdif <- select_functions(cu.rast = tcu, var.rast = tvars, fun = mean) + Error in pm[[2]] : subscript out of bounds + Calls: select_functions -> -> ggplotly.ggplot -> gg2list + Execution halted + ``` + +* checking tests ... ERROR + ``` + Running ‘tinytest.R’ + Running the tests in ‘tests/tinytest.R’ failed. + Complete output: + > + > if ( requireNamespace("tinytest", quietly=TRUE) ){ + + tinytest::test_package("rassta") + + } + + Attaching package: 'rassta' + + ... + test_select_functions.R....... 0 tests + test_select_functions.R....... 0 tests + test_select_functions.R....... 0 tests + test_select_functions.R....... 0 tests + test_select_functions.R....... 0 tests + test_select_functions.R....... 0 tests + test_select_functions.R....... 0 tests + test_select_functions.R....... 0 tests Error in pm[[2]] : subscript out of bounds + Calls: ... select_functions -> -> ggplotly.ggplot -> gg2list + Execution halted + ``` + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘signature.Rmd’ + ... + > clim.var <- rast(vardir) + + > clim.cu <- rast(paste(d, "/climate.tif", sep = "")) + + > clim.difun <- select_functions(cu.rast = clim.cu, + + var.rast = clim.var, mode = "auto") + ... - 1. └─simulariatools::plotAvgTemp(stMeteo) - 2. └─simulariatools (local) mmplot(v, data_table) - 3. ├─base::print(b, vp = subplot(2, 1)) - 4. └─ggplot2:::print.ggplot(b, vp = subplot(2, 1)) - 5. ├─ggplot2::ggplot_gtable(data) - 6. └─ggplot2:::ggplot_gtable.ggplot_built(data) - 7. └─ggplot2::calc_element("plot.margin", theme) - 8. └─cli::cli_abort(...) - 9. └─rlang::abort(...) + When sourcing ‘signature.R’: + Error: subscript out of bounds Execution halted + + ‘classunits.Rmd’ using ‘UTF-8’... OK + ‘modeling.Rmd’ using ‘UTF-8’... OK + ‘sampling.Rmd’ using ‘UTF-8’... OK + ‘signature.Rmd’ using ‘UTF-8’... failed + ‘similarity.Rmd’ using ‘UTF-8’... OK + ‘stratunits.Rmd’ using ‘UTF-8’... OK ``` -# sjPlot +# REddyProc
-* Version: 2.8.16 -* GitHub: https://github.com/strengejacke/sjPlot -* Source code: https://github.com/cran/sjPlot -* Date/Publication: 2024-05-13 17:50:02 UTC -* Number of recursive dependencies: 187 +* Version: 1.3.3 +* GitHub: https://github.com/bgctw/REddyProc +* Source code: https://github.com/cran/REddyProc +* Date/Publication: 2024-01-25 15:30:02 UTC +* Number of recursive dependencies: 93 -Run `revdepcheck::cloud_details(, "sjPlot")` for more info +Run `revdepcheck::cloud_details(, "REddyProc")` for more info
## Newly broken -* checking examples ... ERROR +* checking installed package size ... NOTE ``` - Running examples in ‘sjPlot-Ex.R’ failed - The error most likely occurred in: - - > ### Name: plot_frq - > ### Title: Plot frequencies of variables - > ### Aliases: plot_frq - > - > ### ** Examples - > - > library(sjlabelled) - ... - 4. └─gridExtra (local) ``(``, ``, ``, ``, nrow = 2, ncol = 2) - 5. └─gridExtra::arrangeGrob(...) - 6. └─base::lapply(grobs[toconv], ggplot2::ggplotGrob) - 7. └─ggplot2 (local) FUN(X[[i]], ...) - 8. ├─ggplot2::ggplot_gtable(ggplot_build(x)) - 9. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) - 10. └─ggplot2::calc_element("plot.margin", theme) - 11. └─cli::cli_abort(...) - 12. └─rlang::abort(...) - Execution halted + installed size is 5.7Mb + sub-directories of 1Mb or more: + R 1.5Mb + data 2.0Mb + libs 1.1Mb ``` +# redist + +
+ +* Version: 4.2.0 +* GitHub: https://github.com/alarm-redist/redist +* Source code: https://github.com/cran/redist +* Date/Publication: 2024-01-13 13:20:02 UTC +* Number of recursive dependencies: 132 + +Run `revdepcheck::cloud_details(, "redist")` for more info + +
+ +## Newly broken + * checking running R code from vignettes ... ERROR ``` Errors in running code in vignettes: - when running code in ‘custplot.Rmd’ + when running code in ‘redist.Rmd’ ... + # ℹ 991 more rows + > library(patchwork) - > data(efc) + > hist(plan_sum, max_dev) + hist(iowa_plans, comp) + + + plot_layout(guides = "collect") - > set_theme(geom.outline.color = "antiquewhite4", geom.outline.size = 1, - + geom.label.size = 2, geom.label.color = "grey50", title.color = "red", .... [TRUNCATED] + When sourcing ‘redist.R’: + Error: object is not a unit + Execution halted - ... - ‘plot_interactions.Rmd’ using ‘UTF-8’... OK - ‘plot_likert_scales.Rmd’ using ‘UTF-8’... OK - ‘plot_marginal_effects.Rmd’ using ‘UTF-8’... OK - ‘plot_model_estimates.Rmd’ using ‘UTF-8’... OK - ‘sjtitemanalysis.Rmd’ using ‘UTF-8’... OK - ‘tab_bayes.Rmd’ using ‘UTF-8’... OK - ‘tab_mixed.Rmd’ using ‘UTF-8’... OK - ‘tab_model_estimates.Rmd’ using ‘UTF-8’... OK - ‘tab_model_robust.Rmd’ using ‘UTF-8’... OK - ‘table_css.Rmd’ using ‘UTF-8’... OK + ‘common_args.Rmd’ using ‘UTF-8’... OK + ‘flip.Rmd’ using ‘UTF-8’... OK + ‘map-preproc.Rmd’ using ‘UTF-8’... OK + ‘redist.Rmd’ using ‘UTF-8’... failed ``` * checking re-building of vignette outputs ... NOTE ``` Error(s) in re-building vignettes: - --- re-building ‘blackwhitefigures.Rmd’ using rmarkdown + --- re-building ‘common_args.Rmd’ using rmarkdown + ``` + +## In both + +* checking installed package size ... NOTE + ``` + installed size is 27.7Mb + sub-directories of 1Mb or more: + data 1.2Mb + libs 23.7Mb ``` -# SleepCycles +# reReg
-* Version: 1.1.4 -* GitHub: NA -* Source code: https://github.com/cran/SleepCycles -* Date/Publication: 2021-09-27 13:50:10 UTC -* Number of recursive dependencies: 56 +* Version: 1.4.6 +* GitHub: https://github.com/stc04003/reReg +* Source code: https://github.com/cran/reReg +* Date/Publication: 2023-09-20 08:00:02 UTC +* Number of recursive dependencies: 45 -Run `revdepcheck::cloud_details(, "SleepCycles")` for more info +Run `revdepcheck::cloud_details(, "reReg")` for more info
@@ -18594,40 +10806,40 @@ Run `revdepcheck::cloud_details(, "SleepCycles")` for more info * checking examples ... ERROR ``` - Running examples in ‘SleepCycles-Ex.R’ failed + Running examples in ‘reReg-Ex.R’ failed The error most likely occurred in: - > ### Name: SleepCycles - > ### Title: Sleep Cycle Detection - > ### Aliases: SleepCycles + > ### Name: plot.Recur + > ### Title: Produce Event Plot or Mean Cumulative Function Plot + > ### Aliases: plot.Recur + > ### Keywords: Plots > > ### ** Examples > - > data(sleepstages) ... - 4. ├─grid::grid.draw(plot) - 5. └─ggplot2:::grid.draw.ggplot(plot) - 6. ├─base::print(x) - 7. └─ggplot2:::print.ggplot(x) - 8. ├─ggplot2::ggplot_gtable(data) - 9. └─ggplot2:::ggplot_gtable.ggplot_built(data) - 10. └─ggplot2::calc_element("plot.margin", theme) - 11. └─cli::cli_abort(...) - 12. └─rlang::abort(...) + 11. │ └─base::withCallingHandlers(...) + 12. └─ggplot2 (local) f(l = layers[[i]], d = data[[i]]) + 13. └─l$compute_geom_2(d, theme = plot$theme) + 14. └─ggplot2 (local) compute_geom_2(..., self = self) + 15. └─self$geom$use_defaults(...) + 16. └─ggplot2 (local) use_defaults(..., self = self) + 17. └─ggplot2:::check_aesthetics(new_params, nrow(data)) + 18. └─cli::cli_abort(...) + 19. └─rlang::abort(...) Execution halted ``` -# smallsets +# reservr
-* Version: 2.0.0 -* GitHub: https://github.com/lydialucchesi/smallsets -* Source code: https://github.com/cran/smallsets -* Date/Publication: 2023-12-05 00:00:02 UTC -* Number of recursive dependencies: 107 +* Version: 0.0.3 +* GitHub: https://github.com/AshesITR/reservr +* Source code: https://github.com/cran/reservr +* Date/Publication: 2024-06-24 16:40:02 UTC +* Number of recursive dependencies: 146 -Run `revdepcheck::cloud_details(, "smallsets")` for more info +Run `revdepcheck::cloud_details(, "reservr")` for more info
@@ -18635,185 +10847,210 @@ Run `revdepcheck::cloud_details(, "smallsets")` for more info * checking examples ... ERROR ``` - Running examples in ‘smallsets-Ex.R’ failed + Running examples in ‘reservr-Ex.R’ failed The error most likely occurred in: - > ### Name: Smallset_Timeline - > ### Title: Smallset Timeline - > ### Aliases: Smallset_Timeline + > ### Name: dist_bdegp + > ### Title: Construct a BDEGP-Family + > ### Aliases: dist_bdegp > > ### ** Examples > - > set.seed(145) - > - > Smallset_Timeline( - + data = s_data, - + code = system.file("s_data_preprocess.R", package = "smallsets") + > dist <- dist_bdegp(n = 1, m = 2, u = 10, epsilon = 3) + ... + + theoretical = dist, + + empirical = dist_empirical(x), + + .x = seq(0, 20, length.out = 101), + + with_params = list(theoretical = params) + ) + Warning: Removed 9 rows containing missing values or values outside the scale range + (`geom_line()`). Error in as.unit(value) : object is not coercible to a unit Calls: ... assemble_guides -> guides_build -> [<- -> [<-.unit -> as.unit Execution halted ``` -* checking running R code from vignettes ... ERROR +* checking re-building of vignette outputs ... NOTE ``` - Errors in running code in vignettes: - when running code in ‘smallsets.Rmd’ - ... - > library(smallsets) - - > set.seed(145) - - > Smallset_Timeline(data = s_data, code = system.file("s_data_preprocess.R", - + package = "smallsets")) + Error(s) in re-building vignettes: + --- re-building ‘distributions.Rmd’ using rmarkdown - When sourcing ‘smallsets.R’: - Error: object is not coercible to a unit - Execution halted + Quitting from lines 170-227 [unnamed-chunk-10] (distributions.Rmd) + Error: processing vignette 'distributions.Rmd' failed with diagnostics: + object is not a unit + --- failed re-building ‘distributions.Rmd’ - ‘smallsets.Rmd’ using ‘UTF-8’... failed + --- re-building ‘jss_paper.Rmd’ using rmarkdown ``` -* checking re-building of vignette outputs ... NOTE +## In both + +* checking running R code from vignettes ... ERROR ``` - Error(s) in re-building vignettes: + Errors in running code in vignettes: + when running code in ‘distributions.Rmd’ ... - --- re-building ‘smallsets.Rmd’ using rmarkdown - Quitting from lines 36-42 [timeline1] (smallsets.Rmd) - Error: processing vignette 'smallsets.Rmd' failed with diagnostics: - object is not coercible to a unit - --- failed re-building ‘smallsets.Rmd’ + > attr(trunc_fit$logLik, "nobs") + [1] 62 - SUMMARY: processing the following file failed: - ‘smallsets.Rmd’ + > plot_distributions(true = norm, fit1 = norm, fit2 = norm2, + + fit3 = dist_normal(3), .x = seq(-2, 7, 0.01), with_params = list(true = list(mean .... [TRUNCATED] - Error: Vignette re-building failed. + ... + + > dist$sample(1) + + When sourcing ‘jss_paper.R’: + Error: invalid arguments Execution halted + + ‘distributions.Rmd’ using ‘UTF-8’... failed + ‘jss_paper.Rmd’ using ‘UTF-8’... failed + ‘tensorflow.Rmd’ using ‘UTF-8’... OK ``` -## In both +* checking installed package size ... NOTE + ``` + installed size is 15.7Mb + sub-directories of 1Mb or more: + R 1.5Mb + doc 1.2Mb + libs 12.7Mb + ``` -* checking package dependencies ... NOTE +* checking for GNU extensions in Makefiles ... NOTE ``` - Package suggested but not available for checking: ‘gurobi’ + GNU make is a SystemRequirements. ``` -# smdi +# rKOMICS
-* Version: 0.2.2 +* Version: 1.3 * GitHub: NA -* Source code: https://github.com/cran/smdi -* Date/Publication: 2023-07-17 14:20:02 UTC -* Number of recursive dependencies: 188 +* Source code: https://github.com/cran/rKOMICS +* Date/Publication: 2023-06-29 22:40:03 UTC +* Number of recursive dependencies: 128 -Run `revdepcheck::cloud_details(, "smdi")` for more info +Run `revdepcheck::cloud_details(, "rKOMICS")` for more info
## Newly broken -* checking re-building of vignette outputs ... NOTE +* checking examples ... ERROR ``` - Error(s) in re-building vignettes: - --- re-building ‘a_data_generation.Rmd’ using rmarkdown + Running examples in ‘rKOMICS-Ex.R’ failed + The error most likely occurred in: + + > ### Name: msc.pca + > ### Title: Prinicple Component Analysis based on MSC + > ### Aliases: msc.pca + > + > ### ** Examples + > + > data(matrices) + ... + 11. │ └─base::withCallingHandlers(...) + 12. └─ggplot2 (local) f(l = layers[[i]], d = data[[i]]) + 13. └─l$compute_geom_2(d, theme = plot$theme) + 14. └─ggplot2 (local) compute_geom_2(..., self = self) + 15. └─self$geom$use_defaults(...) + 16. └─ggplot2 (local) use_defaults(..., self = self) + 17. └─ggplot2:::check_aesthetics(new_params, nrow(data)) + 18. └─cli::cli_abort(...) + 19. └─rlang::abort(...) + Execution halted ``` ## In both -* checking running R code from vignettes ... ERROR +* checking installed package size ... NOTE ``` - Errors in running code in vignettes: - when running code in ‘a_data_generation.Rmd’ - ... - > usethis::use_data(smdi_data_complete, overwrite = TRUE) - Warning in path_file(base_path) : - restarting interrupted promise evaluation - - When sourcing ‘a_data_generation.R’: - Error: Failed to evaluate glue component {ui_value(project_name())} - Caused by error: + installed size is 24.8Mb + sub-directories of 1Mb or more: + extdata 24.0Mb + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘example.Rnw’ using Sweave + Loading required package: viridisLite + Warning: Removed 95 rows containing non-finite outside the scale range + (`stat_boxplot()`). + Warning: Removed 89 rows containing non-finite outside the scale range + (`stat_boxplot()`). + Warning: Removed 149 rows containing non-finite outside the scale range + (`stat_boxplot()`). + Warning: Removed 286 rows containing non-finite outside the scale range ... + l.5 \usepackage + {xcolor}^^M + ! ==> Fatal error occurred, no output PDF file produced! + --- failed re-building ‘example.Rnw’ - When sourcing ‘c_multivariate_missingness.R’: - Error: Theme element `plot.margin` must have class . - Execution halted + SUMMARY: processing the following file failed: + ‘example.Rnw’ - ‘a_data_generation.Rmd’ using ‘UTF-8’... failed - ‘b_routine_diagnostics.Rmd’ using ‘UTF-8’... failed - ‘c_multivariate_missingness.Rmd’ using ‘UTF-8’... failed - ‘d_narfcs_sensitivity_analysis.Rmd’ using ‘UTF-8’... OK - ‘smdi.Rmd’ using ‘UTF-8’... OK + Error: Vignette re-building failed. + Execution halted ``` -# soc.ca +# RKorAPClient
-* Version: 0.8.0 -* GitHub: https://github.com/Rsoc/soc.ca -* Source code: https://github.com/cran/soc.ca -* Date/Publication: 2021-09-02 22:50:02 UTC -* Number of recursive dependencies: 140 +* Version: 0.8.1 +* GitHub: https://github.com/KorAP/RKorAPClient +* Source code: https://github.com/cran/RKorAPClient +* Date/Publication: 2024-05-02 11:42:54 UTC +* Number of recursive dependencies: 124 -Run `revdepcheck::cloud_details(, "soc.ca")` for more info +Run `revdepcheck::cloud_details(, "RKorAPClient")` for more info
## Newly broken -* checking examples ... ERROR +* checking tests ... ERROR ``` - Running examples in ‘soc.ca-Ex.R’ failed - The error most likely occurred in: - - > ### Name: add.to.label - > ### Title: Add values to label - > ### Aliases: add.to.label - > - > ### ** Examples - > - > example(soc.ca) + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library("testthat") + > library("RKorAPClient") + > + > test_check("RKorAPClient") + + apiUrl: https://korap.ids-mannheim.de/api/v1.0/ + [ FAIL 1 | WARN 0 | SKIP 30 | PASS 25 ] ... - Backtrace: - ▆ - 1. ├─base (local) ``(x) - 2. └─ggplot2:::print.ggplot(x) - 3. ├─ggplot2::ggplot_gtable(data) - 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) - 5. └─ggplot2::calc_element("plot.margin", theme) - 6. └─cli::cli_abort(...) - 7. └─rlang::abort(...) - Execution halted - ``` - -## In both - -* checking dependencies in R code ... NOTE - ``` - Namespaces in Imports field not imported from: - ‘FactoMineR’ ‘flextable’ ‘htmlTable’ ‘stringr’ - All declared Imports should be used. - ``` - -* checking data for non-ASCII characters ... NOTE - ``` - Note: found 938 marked UTF-8 strings + 'test-demos.R:129:3', 'test-textMetadata.R:2:3', 'test-textMetadata.R:9:3' + + ══ Failed tests ════════════════════════════════════════════════════════════════ + ── Failure ('test-misc.R:224:5'): geom_freq_by_year_ci works correctly ───────── + gpt[["labels"]][["url"]] not equal to "webUIRequestUrl". + target is NULL, current is character + + [ FAIL 1 | WARN 0 | SKIP 30 | PASS 25 ] + Error: Test failures + Execution halted ``` -# spbal +# RNAseqQC
-* Version: 1.0.0 -* GitHub: NA -* Source code: https://github.com/cran/spbal -* Date/Publication: 2024-05-17 16:00:02 UTC -* Number of recursive dependencies: 77 +* Version: 0.2.1 +* GitHub: https://github.com/frederikziebell/RNAseqQC +* Source code: https://github.com/cran/RNAseqQC +* Date/Publication: 2024-07-15 14:40:02 UTC +* Number of recursive dependencies: 177 -Run `revdepcheck::cloud_details(, "spbal")` for more info +Run `revdepcheck::cloud_details(, "RNAseqQC")` for more info
@@ -18822,54 +11059,53 @@ Run `revdepcheck::cloud_details(, "spbal")` for more info * checking running R code from vignettes ... ERROR ``` Errors in running code in vignettes: - when running code in ‘spbal.Rmd’ + when running code in ‘introduction.Rmd’ ... - st_point_on_surface may not give correct results for longitude/latitude data - Warning in st_point_on_surface.sfc(sf::st_zm(x)) : - st_point_on_surface may not give correct results for longitude/latitude data + + show_plot = F)$plot + theme(legend.position = "bottom") - When sourcing ‘spbal.R’: - Error: Problem while setting up geom aesthetics. - ℹ Error occurred in the 1st layer. - Caused by error in `$<-.data.frame`: - ! replacement has 1 row, data has 0 + > plot_loadings(pca_res, PC = 2, color_by = "gc_content") + + > plot_pca_scatters(vsd, n_PCs = 5, color_by = "treatment", + + shape_by = "mutation") + + When sourcing 'introduction.R': + Error: object is not coercible to a unit Execution halted - ‘spbal.Rmd’ using ‘UTF-8’... failed + ‘data.Rmd’ using ‘UTF-8’... OK + ‘introduction.Rmd’ using ‘UTF-8’... failed ``` * checking re-building of vignette outputs ... NOTE ``` Error(s) in re-building vignettes: - ... - --- re-building ‘spbal.Rmd’ using rmarkdown - - Quitting from lines 159-187 [BASex1c] (spbal.Rmd) - Error: processing vignette 'spbal.Rmd' failed with diagnostics: - Problem while setting up geom aesthetics. - ℹ Error occurred in the 1st layer. - Caused by error in `$<-.data.frame`: - ! replacement has 1 row, data has 0 - --- failed re-building ‘spbal.Rmd’ - - SUMMARY: processing the following file failed: - ‘spbal.Rmd’ + --- re-building ‘data.Rmd’ using rmarkdown + --- finished re-building ‘data.Rmd’ - Error: Vignette re-building failed. - Execution halted + --- re-building ‘introduction.Rmd’ using rmarkdown + ``` + +## In both + +* checking installed package size ... NOTE + ``` + installed size is 7.0Mb + sub-directories of 1Mb or more: + data 4.5Mb + doc 2.3Mb ``` -# speccurvieR +# roahd
-* Version: 0.3.0 -* GitHub: https://github.com/zaynesember/speccurvieR -* Source code: https://github.com/cran/speccurvieR -* Date/Publication: 2024-01-24 19:40:02 UTC -* Number of recursive dependencies: 46 +* Version: 1.4.3 +* GitHub: https://github.com/astamm/roahd +* Source code: https://github.com/cran/roahd +* Date/Publication: 2021-11-04 00:10:02 UTC +* Number of recursive dependencies: 88 -Run `revdepcheck::cloud_details(, "speccurvieR")` for more info +Run `revdepcheck::cloud_details(, "roahd")` for more info
@@ -18877,47 +11113,50 @@ Run `revdepcheck::cloud_details(, "speccurvieR")` for more info * checking examples ... ERROR ``` - Running examples in ‘speccurvieR-Ex.R’ failed + Running examples in ‘roahd-Ex.R’ failed The error most likely occurred in: - > ### Name: plotCurve - > ### Title: Plots a specification curve. - > ### Aliases: plotCurve + > ### Name: plot.depthgram + > ### Title: Specialized method to plot 'depthgram' objects + > ### Aliases: plot.depthgram > > ### ** Examples > - > plotCurve(sca_data = sca(y="Salnty", x="T_degC", c("ChlorA", "O2Sat"), + > N <- 50 ... - 1. └─speccurvieR::plotCurve(...) - 2. ├─grid::grid.draw(rbind(ggplotGrob(sc1), ggplotGrob(sc2))) - 3. ├─base::rbind(ggplotGrob(sc1), ggplotGrob(sc2)) - 4. └─ggplot2::ggplotGrob(sc1) - 5. ├─ggplot2::ggplot_gtable(ggplot_build(x)) - 6. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) - 7. └─ggplot2::calc_element("plot.margin", theme) - 8. └─cli::cli_abort(...) - 9. └─rlang::abort(...) + + N, + + centerline = sin(2 * pi * grid), + + Cov = Cov + + ) + > names <- paste0("id_", 1:nrow(Data[[1]])) + > DG <- depthgram(Data, marginal_outliers = TRUE, ids = names) + > plot(DG) + Error in pm[[2]] : subscript out of bounds + Calls: plot ... plotly_build -> ggplotly -> ggplotly.ggplot -> gg2list Execution halted ``` ## In both -* checking data for non-ASCII characters ... NOTE +* checking installed package size ... NOTE ``` - Note: found 2 marked UTF-8 strings + installed size is 7.4Mb + sub-directories of 1Mb or more: + data 5.0Mb + doc 1.7Mb ``` -# spinifex +# romic
-* Version: 0.3.7.0 -* GitHub: https://github.com/nspyrison/spinifex -* Source code: https://github.com/cran/spinifex -* Date/Publication: 2024-01-29 14:40:02 UTC -* Number of recursive dependencies: 163 +* Version: 1.1.3 +* GitHub: NA +* Source code: https://github.com/cran/romic +* Date/Publication: 2023-09-21 05:40:02 UTC +* Number of recursive dependencies: 113 -Run `revdepcheck::cloud_details(, "spinifex")` for more info +Run `revdepcheck::cloud_details(, "romic")` for more info
@@ -18925,40 +11164,88 @@ Run `revdepcheck::cloud_details(, "spinifex")` for more info * checking tests ... ERROR ``` - Running ‘spelling.R’ Running ‘testthat.R’ Running the tests in ‘tests/testthat.R’ failed. Complete output: - > library(testthat) - > library(spinifex) - Loading required package: tourr - -------------------------------------------------------- - spinifex --- version 0.3.7.0 - Please share bugs, suggestions, and feature requests at: + > # This file is part of the standard setup for testthat. + > # It is recommended that you do not modify it. + > # + > # Where should you do additional test configuration? + > # Learn more about the roles of various files in: + > # * https://r-pkgs.org/testing-design.html#sec-tests-files-overview + > # * https://testthat.r-lib.org/articles/special-files.html ... - 2. │ └─base::withCallingHandlers(...) - 3. └─spinifex::play_tour_path(tour_path = tpath, data = dat_std, angle = 1) - 4. └─spinifex (local) render_type(frames = tour_df, ...) - 5. ├─plotly::ggplotly(p = gg, tooltip = "tooltip") - 6. └─plotly:::ggplotly.ggplot(p = gg, tooltip = "tooltip") - 7. └─plotly::gg2list(...) + 3. │ │ └─base::withCallingHandlers(...) + 4. │ ├─plotly::ggplotly(heatmap_plot) %>% plotly::layout(margin = 0) + 5. │ ├─plotly::ggplotly(heatmap_plot) + 6. │ └─plotly:::ggplotly.ggplot(heatmap_plot) + 7. │ └─plotly::gg2list(...) + 8. └─plotly::layout(., margin = 0) - [ FAIL 3 | WARN 0 | SKIP 0 | PASS 80 ] + [ FAIL 1 | WARN 0 | SKIP 7 | PASS 66 ] Error: Test failures Execution halted ``` -# spotoroo +# roptions
-* Version: 0.1.4 -* GitHub: https://github.com/TengMCing/spotoroo -* Source code: https://github.com/cran/spotoroo -* Date/Publication: 2023-08-21 05:50:02 UTC -* Number of recursive dependencies: 107 +* Version: 1.0.3 +* GitHub: NA +* Source code: https://github.com/cran/roptions +* Date/Publication: 2020-05-11 11:10:06 UTC +* Number of recursive dependencies: 70 + +Run `revdepcheck::cloud_details(, "roptions")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘roptions-Ex.R’ failed + The error most likely occurred in: + + > ### Name: box.spread + > ### Title: Box Spread Strategy Function + > ### Aliases: box.spread + > + > ### ** Examples + > + > box.spread(100, 105, 95, 110, 3.2, 2.6, 1.1, 2.4) + ... + 35 5.7 + 36 5.7 + 37 5.7 + 38 5.7 + 39 5.7 + 40 5.7 + 41 5.7 + Error in pm[[2]] : subscript out of bounds + Calls: box.spread -> print -> ggplotly -> ggplotly.ggplot -> gg2list + Execution halted + ``` + +## In both + +* checking LazyData ... NOTE + ``` + 'LazyData' is specified without a 'data' directory + ``` + +# santaR + +
+ +* Version: 1.2.4 +* GitHub: https://github.com/adwolfer/santaR +* Source code: https://github.com/cran/santaR +* Date/Publication: 2024-03-07 00:30:02 UTC +* Number of recursive dependencies: 93 -Run `revdepcheck::cloud_details(, "spotoroo")` for more info +Run `revdepcheck::cloud_details(, "santaR")` for more info
@@ -18970,78 +11257,144 @@ Run `revdepcheck::cloud_details(, "spotoroo")` for more info Running the tests in ‘tests/testthat.R’ failed. Complete output: > library(testthat) - > library(spotoroo) - > - > test_check("spotoroo") + > library(santaR) - -------------------------------- SPOTOROO 0.1.4 -------------------------------- + This is santaR version 1.2.4 + > + > test_check("santaR") ... - i Actually got a with text: - Theme element `plot.margin` must have class . - ── Failure ('test-plot_spotoroo.R:64:3'): plot_spotoroo() works ──────────────── - Expected `plot_spotoroo(result, type = "timeline")` to run without any errors. - i Actually got a with text: - Theme element `plot.margin` must have class . + 1/1 mismatches + [1] 11 - 10 == 1 + ── Failure ('test_dfSearch-plot_nbTP_histogram.R:69:3'): change dfCuttOff ────── + length(result_nbTPHisto) not equal to length(ggplot2::ggplot()). + 1/1 mismatches + [1] 11 - 10 == 1 - [ FAIL 2 | WARN 5 | SKIP 0 | PASS 65 ] + [ FAIL 8 | WARN 1 | SKIP 0 | PASS 681 ] Error: Test failures Execution halted ``` +## In both + * checking running R code from vignettes ... ERROR ``` Errors in running code in vignettes: - when running code in ‘Clustering-hot-spots.Rmd’ + when running code in ‘getting-started.Rmd’ ... - ──────────────────────────────────────────────────────────────────────────────── - - > plot_spotoroo(result, type = "def") - - > plot_spotoroo(result, type = "timeline") + > knitr::include_graphics("../man/figures/santaR-approach.jpg") - When sourcing ‘Clustering-hot-spots.R’: - Error: Theme element `plot.margin` must have class . + When sourcing ‘getting-started.R’: + Error: Cannot find the file(s): "../man/figures/santaR-approach.jpg" + Execution halted + when running code in ‘selecting-optimal-df.Rmd’ + ... Execution halted - ‘Clustering-hot-spots.Rmd’ using ‘UTF-8’... failed + ‘advanced-command-line-functions.Rmd’ using ‘UTF-8’... OK + ‘automated-command-line.Rmd’ using ‘UTF-8’... OK + ‘getting-started.Rmd’ using ‘UTF-8’... failed + ‘plotting-options.Rmd’ using ‘UTF-8’... OK + ‘prepare-input-data.Rmd’ using ‘UTF-8’... OK + ‘selecting-optimal-df.Rmd’ using ‘UTF-8’... failed + ‘theoretical-background.Rmd’ using ‘UTF-8’... OK + ‘santaR-GUI.pdf.asis’ using ‘UTF-8’... OK ``` -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘Clustering-hot-spots.Rmd’ using rmarkdown - ``` +# scdtb -## In both +
-* checking dependencies in R code ... NOTE +* Version: 0.1.0 +* GitHub: https://github.com/mightymetrika/scdtb +* Source code: https://github.com/cran/scdtb +* Date/Publication: 2024-04-30 08:50:02 UTC +* Number of recursive dependencies: 96 + +Run `revdepcheck::cloud_details(, "scdtb")` for more info + +
+ +## Newly broken + +* checking tests ... ERROR ``` - Namespace in Imports field not imported from: ‘utils’ - All declared Imports should be used. + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > # This file is part of the standard setup for testthat. + > # It is recommended that you do not modify it. + > # + > # Where should you do additional test configuration? + > # Learn more about the roles of various files in: + > # * https://r-pkgs.org/testing-design.html#sec-tests-files-overview + > # * https://testthat.r-lib.org/articles/special-files.html + ... + ── Failure ('test-mixed_model_analysis.R:119:3'): mixed_model_analysis uses the .participant variable to label data points + when .participant is not NULL ── + res$plot$labels$shape (`actual`) not equal to "factor(part)" (`expected`). + + `actual` is NULL + `expected` is a character vector ('factor(part)') + + [ FAIL 1 | WARN 0 | SKIP 0 | PASS 45 ] + Error: Test failures + Execution halted ``` -# SqueakR +# scoringutils
-* Version: 1.3.0 -* GitHub: https://github.com/osimon81/SqueakR -* Source code: https://github.com/cran/SqueakR -* Date/Publication: 2022-06-28 09:20:04 UTC -* Number of recursive dependencies: 141 +* Version: 1.2.2 +* GitHub: https://github.com/epiforecasts/scoringutils +* Source code: https://github.com/cran/scoringutils +* Date/Publication: 2023-11-29 15:50:10 UTC +* Number of recursive dependencies: 81 -Run `revdepcheck::cloud_details(, "SqueakR")` for more info +Run `revdepcheck::cloud_details(, "scoringutils")` for more info
## Newly broken +* checking examples ... ERROR + ``` + Running examples in ‘scoringutils-Ex.R’ failed + The error most likely occurred in: + + > ### Name: plot_predictions + > ### Title: Plot Predictions vs True Values + > ### Aliases: plot_predictions + > + > ### ** Examples + > + > library(ggplot2) + ... + + by = c("target_type", "location"), + + range = c(0, 50, 90, 95) + + ) + + + facet_wrap(~ location + target_type, scales = "free_y") + + + aes(fill = model, color = model) + Error in use_defaults(..., self = self) : + unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, "black", TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), list(NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), 5.5, c(5.5, 5.5, 5.5, 5.5), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.75, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, + NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, 90, NULL, c(0, 2.75, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL + Calls: ... -> -> compute_geom_2 -> + Execution halted + ``` + * checking re-building of vignette outputs ... NOTE ``` Error(s) in re-building vignettes: - --- re-building ‘SqueakR.Rmd’ using rmarkdown + --- re-building ‘metric-details.Rmd’ using rmarkdown + --- finished re-building ‘metric-details.Rmd’ + + --- re-building ‘scoring-forecasts-directly.Rmd’ using rmarkdown + --- finished re-building ‘scoring-forecasts-directly.Rmd’ + + --- re-building ‘scoringutils.Rmd’ using rmarkdown ``` ## In both @@ -19049,143 +11402,79 @@ Run `revdepcheck::cloud_details(, "SqueakR")` for more info * checking running R code from vignettes ... ERROR ``` Errors in running code in vignettes: - when running code in ‘SqueakR.Rmd’ + when running code in ‘scoringutils.Rmd’ ... - $ experimenters : NULL - $ experimental_data: list() + The following messages were produced when checking inputs: + 1. 144 values for `prediction` are NA in the data provided and the corresponding rows were removed. This may indicate a problem if unexpected. - > my_new_data <- add_timepoint_data(data_path = "../inst/extdata/Example_Mouse_Data.xlsx", - + t1 = 5, t2 = 25) - Adding call features Excel file to workspace... + > example_quantile %>% make_NA(what = "truth", target_end_date >= + + "2021-07-15", target_end_date < "2021-05-22") %>% make_NA(what = "forecast", .... [TRUNCATED] - When sourcing ‘SqueakR.R’: - Error: `path` does not exist: ‘../inst/extdata/Example_Mouse_Data.xlsx’ + When sourcing ‘scoringutils.R’: + Error: unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, "black", TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), list(NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), 5.5, c(5.5, 5.5, 5.5, 5.5), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.75, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, + NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, 90, NULL, c(0, 2.75, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, Execution halted - ‘SqueakR.Rmd’ using ‘UTF-8’... failed - ``` - -* checking installed package size ... NOTE - ``` - installed size is 8.8Mb - sub-directories of 1Mb or more: - doc 8.2Mb + ‘metric-details.Rmd’ using ‘UTF-8’... OK + ‘scoring-forecasts-directly.Rmd’ using ‘UTF-8’... OK + ‘scoringutils.Rmd’ using ‘UTF-8’... failed ``` -# stabm +# scUtils
-* Version: 1.2.2 -* GitHub: https://github.com/bommert/stabm -* Source code: https://github.com/cran/stabm -* Date/Publication: 2023-04-04 13:20:02 UTC -* Number of recursive dependencies: 71 +* Version: 0.1.0 +* GitHub: NA +* Source code: https://github.com/cran/scUtils +* Date/Publication: 2020-06-25 16:20:02 UTC +* Number of recursive dependencies: 52 -Run `revdepcheck::cloud_details(, "stabm")` for more info +Run `revdepcheck::cloud_details(, "scUtils")` for more info
## Newly broken -* checking examples ... ERROR - ``` - Running examples in ‘stabm-Ex.R’ failed - The error most likely occurred in: - - > ### Name: plotFeatures - > ### Title: Plot Selected Features - > ### Aliases: plotFeatures - > - > ### ** Examples - > - > feats = list(1:3, 1:4, 1:5) - ... - 5. └─cowplot:::as_gtable.default(plot) - 6. ├─cowplot::as_grob(plot) - 7. └─cowplot:::as_grob.ggplot(plot) - 8. └─ggplot2::ggplotGrob(plot) - 9. ├─ggplot2::ggplot_gtable(ggplot_build(x)) - 10. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) - 11. └─ggplot2::calc_element("plot.margin", theme) - 12. └─cli::cli_abort(...) - 13. └─rlang::abort(...) - Execution halted - ``` - * checking tests ... ERROR ``` Running ‘testthat.R’ Running the tests in ‘tests/testthat.R’ failed. Complete output: > library(testthat) - > library(stabm) + > library(scUtils) > - > test_check("stabm") - [ FAIL 10 | WARN 3 | SKIP 0 | PASS 290 ] + > test_check("scUtils") + [ FAIL 1 | WARN 0 | SKIP 0 | PASS 32 ] ══ Failed tests ════════════════════════════════════════════════════════════════ - ... - 10. └─ggplot2::ggplotGrob(plot) - 11. ├─ggplot2::ggplot_gtable(ggplot_build(x)) - 12. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) - 13. └─ggplot2::calc_element("plot.margin", theme) - 14. └─cli::cli_abort(...) - 15. └─rlang::abort(...) + ── Failure ('test-plots.R:59:3'): all kinds of colnames are allowed ──────────── + p$labels not equal to list(y = "Dim2", x = "Dim1", colour = "expression"). + Length mismatch: comparison on first 2 components - [ FAIL 10 | WARN 3 | SKIP 0 | PASS 290 ] + [ FAIL 1 | WARN 0 | SKIP 0 | PASS 32 ] Error: Test failures Execution halted ``` -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘stabm.Rmd’ - ... - [1] 0.4353893 - - > plotFeatures(feats) - Loading required namespace: ggplot2 - Loading required namespace: cowplot - Loading required namespace: ggdendro - - When sourcing ‘stabm.R’: - Error: Theme element `plot.margin` must have class . - Execution halted - - ‘stabm.Rmd’ using ‘UTF-8’... failed - ``` +## In both -* checking re-building of vignette outputs ... NOTE +* checking LazyData ... NOTE ``` - Error(s) in re-building vignettes: - ... - --- re-building ‘stabm.Rmd’ using rmarkdown - - Quitting from lines 65-66 [unnamed-chunk-5] (stabm.Rmd) - Error: processing vignette 'stabm.Rmd' failed with diagnostics: - Theme element `plot.margin` must have class . - --- failed re-building ‘stabm.Rmd’ - - SUMMARY: processing the following file failed: - ‘stabm.Rmd’ - - Error: Vignette re-building failed. - Execution halted + 'LazyData' is specified without a 'data' directory ``` -# starvz +# SCVA
-* Version: 0.8.0 -* GitHub: https://github.com/schnorr/starvz -* Source code: https://github.com/cran/starvz -* Date/Publication: 2024-02-23 23:50:02 UTC -* Number of recursive dependencies: 96 +* Version: 1.3.1 +* GitHub: NA +* Source code: https://github.com/cran/SCVA +* Date/Publication: 2020-01-09 22:50:10 UTC +* Number of recursive dependencies: 80 -Run `revdepcheck::cloud_details(, "starvz")` for more info +Run `revdepcheck::cloud_details(, "SCVA")` for more info
@@ -19193,40 +11482,34 @@ Run `revdepcheck::cloud_details(, "starvz")` for more info * checking examples ... ERROR ``` - Running examples in ‘starvz-Ex.R’ failed + Running examples in ‘SCVA-Ex.R’ failed The error most likely occurred in: - > ### Name: panel_gpubandwidth - > ### Title: Create a line chart panel with GPU bandwidth - > ### Aliases: panel_gpubandwidth + > ### Name: graphly + > ### Title: Interactive plot of single-case data + > ### Aliases: graphly + > ### Keywords: Single-case design Graph > > ### ** Examples > - > panel_gpubandwidth(data = starvz_sample_lu) - ... - Backtrace: - ▆ - 1. ├─base (local) ``(x) - 2. └─ggplot2:::print.ggplot(x) - 3. ├─ggplot2::ggplot_gtable(data) - 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) - 5. └─ggplot2::calc_element("plot.margin", theme) - 6. └─cli::cli_abort(...) - 7. └─rlang::abort(...) + > data(AB) + > graphly(design = "AB", data = AB) + Error in pm[[2]] : subscript out of bounds + Calls: graphly -> ggplotly -> ggplotly.ggplot -> gg2list Execution halted ``` -# statgenMPP +# SDMtune
-* Version: 1.0.2 -* GitHub: NA -* Source code: https://github.com/cran/statgenMPP -* Date/Publication: 2022-12-02 22:00:02 UTC -* Number of recursive dependencies: 78 +* Version: 1.3.1 +* GitHub: https://github.com/ConsBiol-unibern/SDMtune +* Source code: https://github.com/cran/SDMtune +* Date/Publication: 2023-07-03 12:20:02 UTC +* Number of recursive dependencies: 125 -Run `revdepcheck::cloud_details(, "statgenMPP")` for more info +Run `revdepcheck::cloud_details(, "SDMtune")` for more info
@@ -19234,140 +11517,71 @@ Run `revdepcheck::cloud_details(, "statgenMPP")` for more info * checking tests ... ERROR ``` - Running ‘tinytest.R’ - Running the tests in ‘tests/tinytest.R’ failed. + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. Complete output: - > - > if ( requireNamespace("tinytest", quietly=TRUE) ){ - + tinytest::test_package("statgenMPP") - + } - Loading required package: statgenGWAS + > library(testthat) + > library(SDMtune) - test_calcIBDmpp.R............. 0 tests + _____ ____ __ ___ __ + / ___/ / __ \ / |/ // /_ __ __ ____ ___ + \__ \ / / / // /|_/ // __// / / // __ \ / _ \ + ___/ // /_/ // / / // /_ / /_/ // / / // __/ ... - 7. ├─base::plot(ABC_MQM, plotType = "QTLProfileExt") - 8. └─statgenMPP:::plot.QTLMPP(ABC_MQM, plotType = "QTLProfileExt") - 9. └─ggplot2::ggplotGrob(p1) - 10. ├─ggplot2::ggplot_gtable(ggplot_build(x)) - 11. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) - 12. └─ggplot2::calc_element("plot.margin", theme) - 13. └─cli::cli_abort(...) - 14. └─rlang::abort(...) - There were 50 or more warnings (use warnings() to see the first 50) + `expected` is a character vector ('Var2') + ── Failure ('test-plotCor.R:6:3'): The plot has the correct labels and text size ── + p$labels$y (`actual`) not equal to "Var1" (`expected`). + + `actual` is NULL + `expected` is a character vector ('Var1') + + [ FAIL 2 | WARN 0 | SKIP 55 | PASS 315 ] + Error: Test failures Execution halted ``` -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘QTLMapping_in_MultiParentPopulations.Rmd’ - ... - - > plot(ABCMQM, plotType = "QTLProfile") - - > plot(ABCMQM, plotType = "parEffs") - - > plot(ABCMQM, plotType = "QTLProfileExt") - - When sourcing ‘QTLMapping_in_MultiParentPopulations.R’: - Error: Theme element `plot.margin` must have class . - Execution halted - - ‘QTLMapping_in_MultiParentPopulations.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘QTLMapping_in_MultiParentPopulations.Rmd’ using rmarkdown - ``` - -# statVisual - -
- -* Version: 1.2.1 -* GitHub: NA -* Source code: https://github.com/cran/statVisual -* Date/Publication: 2020-02-20 19:30:02 UTC -* Number of recursive dependencies: 193 - -Run `revdepcheck::cloud_details(, "statVisual")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘statVisual-Ex.R’ failed - The error most likely occurred in: - - > ### Name: PCA_score - > ### Title: Scatter Plot of 2 Specified Principal Components - > ### Aliases: PCA_score - > ### Keywords: method - > - > ### ** Examples - > - ... - 11. │ └─base::withCallingHandlers(...) - 12. └─ggplot2 (local) f(l = layers[[i]], d = data[[i]]) - 13. └─l$compute_geom_2(d, theme = plot$theme) - 14. └─ggplot2 (local) compute_geom_2(..., self = self) - 15. └─self$geom$use_defaults(...) - 16. └─ggplot2 (local) use_defaults(..., self = self) - 17. └─ggplot2:::check_aesthetics(new_params, nrow(data)) - 18. └─cli::cli_abort(...) - 19. └─rlang::abort(...) - Execution halted - ``` +## In both * checking running R code from vignettes ... ERROR ``` Errors in running code in vignettes: - when running code in ‘statVisual.Rmd’ + when running code in ‘basic-use.Rmd’ ... + [1] 0.8336850 0.8672387 - > factoextra::fviz_eig(pca.obj, addlabels = TRUE) + > folds <- randomFolds(data, k = 4, only_presence = TRUE, + + seed = 25) - When sourcing ‘statVisual.R’: - Error: Problem while setting up geom aesthetics. - ℹ Error occurred in the 1st layer. - Caused by error in `check_aesthetics()`: - ! Aesthetics must be either length 1 or the same as the data (6). - ✖ Fix the following mappings: `width`. + > auc(cv_model) + + When sourcing ‘basic-use.R’: + Error: object 'cv_model' not found Execution halted - ‘statVisual.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘statVisual.Rmd’ using rmarkdown + ‘basic-use.Rmd’ using ‘UTF-8’... failed + ‘hyper-tuning.Rmd’ using ‘UTF-8’... OK + ‘presence-absence.Rmd’ using ‘UTF-8’... OK + ‘var-selection.Rmd’ using ‘UTF-8’... OK ``` -## In both - -* checking dependencies in R code ... NOTE +* checking installed package size ... NOTE ``` - Namespaces in Imports field not imported from: - ‘gbm’ ‘ggfortify’ ‘tibble’ ‘tidyverse’ - All declared Imports should be used. + installed size is 5.2Mb + sub-directories of 1Mb or more: + R 3.0Mb ``` -# superheat +# SeaVal
-* Version: 0.1.0 -* GitHub: NA -* Source code: https://github.com/cran/superheat -* Date/Publication: 2017-02-04 23:35:29 -* Number of recursive dependencies: 69 +* Version: 1.2.0 +* GitHub: https://github.com/SeasonalForecastingEngine/SeaVal +* Source code: https://github.com/cran/SeaVal +* Date/Publication: 2024-06-14 15:20:05 UTC +* Number of recursive dependencies: 43 -Run `revdepcheck::cloud_details(, "superheat")` for more info +Run `revdepcheck::cloud_details(, "SeaVal")` for more info
@@ -19375,72 +11589,43 @@ Run `revdepcheck::cloud_details(, "superheat")` for more info * checking examples ... ERROR ``` - Running examples in ‘superheat-Ex.R’ failed + Running examples in ‘SeaVal-Ex.R’ failed The error most likely occurred in: - > ### Name: superheat - > ### Title: Generate supervised heatmaps. - > ### Aliases: superheat + > ### Name: tfc_gha_plot + > ### Title: Plotting function with different map for Greater Horn of Africa + > ### Aliases: tfc_gha_plot > > ### ** Examples > - > # plot a heatmap of the numerical iris variables - ... - 6. ├─gtable::gtable_filter(...) - 7. │ └─base::grepl(pattern, .subset2(x$layout, "name"), fixed = fixed) - 8. │ └─base::is.factor(x) - 9. └─ggplot2::ggplotGrob(gg.right) - 10. ├─ggplot2::ggplot_gtable(ggplot_build(x)) - 11. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) - 12. └─ggplot2::calc_element("plot.margin", theme) - 13. └─cli::cli_abort(...) - 14. └─rlang::abort(...) + > dt = tfc_from_efc(ecmwf_monthly[month == 11 & lat < 0]) + > pp = tfc_gha_plot(dt[year == 2018], expand.y = c(0.5,0.5)) + Error in names(labels) <- `*vtmp*` : attempt to set an attribute on NULL + Calls: tfc_gha_plot ... ggplot_add -> ggplot_add.new_aes -> bump_aes_labels Execution halted ``` -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(superheat) - > - > test_check("superheat") - [ FAIL 58 | WARN 256 | SKIP 0 | PASS 0 ] - - ══ Failed tests ════════════════════════════════════════════════════════════════ - ... - 9. └─ggplot2::ggplotGrob(gg.top) - 10. ├─ggplot2::ggplot_gtable(ggplot_build(x)) - 11. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) - 12. └─ggplot2::calc_element("plot.margin", theme) - 13. └─cli::cli_abort(...) - 14. └─rlang::abort(...) - - [ FAIL 58 | WARN 256 | SKIP 0 | PASS 0 ] - Error: Test failures - Execution halted - ``` - ## In both -* checking LazyData ... NOTE +* checking installed package size ... NOTE ``` - 'LazyData' is specified without a 'data' directory + installed size is 20.6Mb + sub-directories of 1Mb or more: + data 2.0Mb + extdata 18.0Mb ``` -# surveyexplorer +# sglg
-* Version: 0.1.0 +* Version: 0.2.2 * GitHub: NA -* Source code: https://github.com/cran/surveyexplorer -* Date/Publication: 2023-12-21 16:40:02 UTC -* Number of recursive dependencies: 87 +* Source code: https://github.com/cran/sglg +* Date/Publication: 2022-09-04 03:50:01 UTC +* Number of recursive dependencies: 96 -Run `revdepcheck::cloud_details(, "surveyexplorer")` for more info +Run `revdepcheck::cloud_details(, "sglg")` for more info
@@ -19448,121 +11633,78 @@ Run `revdepcheck::cloud_details(, "surveyexplorer")` for more info * checking examples ... ERROR ``` - Running examples in ‘surveyexplorer-Ex.R’ failed + Running examples in ‘sglg-Ex.R’ failed The error most likely occurred in: - > ### Name: multi_freq - > ### Title: Generate an UpSet plot for multiple-choice questions - > ### Aliases: multi_freq + > ### Name: deviance_residuals + > ### Title: Deviance Residuals for a Generalized Log-gamma Regression Model + > ### Aliases: deviance_residuals > > ### ** Examples > - > - ... - 9. └─ggplot2:::scale_apply(layer_data, x_vars, "map", SCALE_X, self$panel_scales_x) - 10. └─base::lapply(...) - 11. └─ggplot2 (local) FUN(X[[i]], ...) - 12. └─base::lapply(...) - 13. └─ggplot2 (local) FUN(X[[i]], ...) - 14. └─scales[[i]][[method]](data[[var]][scale_index[[i]]]) - 15. └─ggplot2 (local) map(..., self = self) - 16. └─cli::cli_abort(...) - 17. └─rlang::abort(...) + > # Example 1 + > n <- 300 + > error <- rglg(n,0,1,1) + > y <- 0.5 + error + > fit <- glg(y~1,data=as.data.frame(y)) + > deviance_residuals(fit) + Error in pm[[2]] : subscript out of bounds + Calls: deviance_residuals ... dots2plots -> ggplotly -> ggplotly.ggplot -> gg2list Execution halted ``` -# survivalAnalysis +# sgsR
-* Version: 0.3.0 -* GitHub: NA -* Source code: https://github.com/cran/survivalAnalysis -* Date/Publication: 2022-02-11 14:00:02 UTC -* Number of recursive dependencies: 159 +* Version: 1.4.5 +* GitHub: https://github.com/tgoodbody/sgsR +* Source code: https://github.com/cran/sgsR +* Date/Publication: 2024-03-03 15:10:02 UTC +* Number of recursive dependencies: 124 -Run `revdepcheck::cloud_details(, "survivalAnalysis")` for more info +Run `revdepcheck::cloud_details(, "sgsR")` for more info
## Newly broken -* checking examples ... ERROR - ``` - Running examples in ‘survivalAnalysis-Ex.R’ failed - The error most likely occurred in: - - > ### Name: forest_plot - > ### Title: Forest plots for survival analysis. - > ### Aliases: forest_plot forest_plot.df - > - > ### ** Examples - > - > library(magrittr) - ... - 10. └─cowplot:::as_gtable.default(x) - 11. ├─cowplot::as_grob(plot) - 12. └─cowplot:::as_grob.ggplot(plot) - 13. └─ggplot2::ggplotGrob(plot) - 14. ├─ggplot2::ggplot_gtable(ggplot_build(x)) - 15. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) - 16. └─ggplot2::calc_element("plot.margin", theme) - 17. └─cli::cli_abort(...) - 18. └─rlang::abort(...) - Execution halted - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘multivariate.Rmd’ using rmarkdown - - Quitting from lines 88-89 [unnamed-chunk-6] (multivariate.Rmd) - Error: processing vignette 'multivariate.Rmd' failed with diagnostics: - Theme element `plot.margin` must have class . - --- failed re-building ‘multivariate.Rmd’ - - --- re-building ‘univariate.Rmd’ using rmarkdown - ``` - -## In both - -* checking running R code from vignettes ... ERROR +* checking tests ... ERROR ``` - Errors in running code in vignettes: - when running code in ‘multivariate.Rmd’ - ... - Warning in strwidth(., family = ggtheme$text$family, units = "in") : - conversion failure on '(0.98–1.00)' in 'mbcsToSbcs': dot substituted for - Warning in strwidth(., family = ggtheme$text$family, units = "in") : - conversion failure on '(0.98–1.00)' in 'mbcsToSbcs': dot substituted for <80> - Warning in strwidth(., family = ggtheme$text$family, units = "in") : - conversion failure on '(0.98–1.00)' in 'mbcsToSbcs': dot substituted for <93> - + Running ‘spelling.R’ + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > # This file is part of the standard setup for testthat. + > # It is recommended that you do not modify it. + > # + > # Where should you do additional test configuration? + > # Learn more about the roles of various files in: + > # * https://r-pkgs.org/tests.html ... - font family 'Arial' not found in PostScript font database - Warning in grid.Call.graphics(C_text, as.graphicsAnnot(x$label), x$x, x$y, : - font family 'Arial' not found in PostScript font database - - When sourcing ‘univariate.R’: - Error: invalid font type - Execution halted - - ‘multivariate.Rmd’ using ‘UTF-8’... failed - ‘univariate.Rmd’ using ‘UTF-8’... failed + `expected` is a character vector ('zq90') + ── Failure ('test-utils-plot.R:19:3'): scatter messages ──────────────────────── + o1$labels$x (`actual`) not equal to "pzabove2" (`expected`). + + `actual` is NULL + `expected` is a character vector ('pzabove2') + + [ FAIL 2 | WARN 115 | SKIP 19 | PASS 508 ] + Error: Test failures + Execution halted ``` -# Sysrecon +# SHAPforxgboost
* Version: 0.1.3 -* GitHub: NA -* Source code: https://github.com/cran/Sysrecon -* Date/Publication: 2023-02-20 08:50:02 UTC -* Number of recursive dependencies: 61 +* GitHub: https://github.com/liuyanguu/SHAPforxgboost +* Source code: https://github.com/cran/SHAPforxgboost +* Date/Publication: 2023-05-29 17:20:07 UTC +* Number of recursive dependencies: 112 -Run `revdepcheck::cloud_details(, "Sysrecon")` for more info +Run `revdepcheck::cloud_details(, "SHAPforxgboost")` for more info
@@ -19570,171 +11712,144 @@ Run `revdepcheck::cloud_details(, "Sysrecon")` for more info * checking examples ... ERROR ``` - Running examples in ‘Sysrecon-Ex.R’ failed + Running examples in ‘SHAPforxgboost-Ex.R’ failed The error most likely occurred in: - > ### Name: Sysrecon - > ### Title: Sysrecon - > ### Aliases: Sysrecon + > ### Name: shap.plot.force_plot + > ### Title: Make the SHAP force plot + > ### Aliases: shap.plot.force_plot > > ### ** Examples > > ... - no non-missing arguments to min; returning Inf - Warning in min(freq[grepl(i, allwords, ignore.case = T)]) : - no non-missing arguments to min; returning Inf - Warning in min(freq[grepl(i, allwords, ignore.case = T)]) : - no non-missing arguments to min; returning Inf - Warning in min(freq[grepl(i, allwords, ignore.case = T)]) : - no non-missing arguments to min; returning Inf - Error in as.unit(value) : object is not coercible to a unit - Calls: Sysrecon ... assemble_guides -> guides_build -> [<- -> [<-.unit -> as.unit + > plot_data <- shap.prep.stack.data(shap_contrib = shap_values_iris, + + n_groups = 4) + All the features will be used. + + > shap.plot.force_plot(plot_data) + Data has N = 150 | zoom in length is 50 at location 90. + + Error in upgradeUnit.default(x) : Not a unit object + Calls: ... is.unit -> convertUnit -> upgradeUnit -> upgradeUnit.default Execution halted ``` -## In both - -* checking data for non-ASCII characters ... NOTE - ``` - Note: found 38 marked UTF-8 strings - ``` - -# tabledown +# SHELF
-* Version: 1.0.0 -* GitHub: https://github.com/masiraji/tabledown -* Source code: https://github.com/cran/tabledown -* Date/Publication: 2024-05-02 13:40:03 UTC -* Number of recursive dependencies: 144 +* Version: 1.10.0 +* GitHub: https://github.com/OakleyJ/SHELF +* Source code: https://github.com/cran/SHELF +* Date/Publication: 2024-05-07 14:20:03 UTC +* Number of recursive dependencies: 126 -Run `revdepcheck::cloud_details(, "tabledown")` for more info +Run `revdepcheck::cloud_details(, "SHELF")` for more info
## Newly broken -* checking examples ... ERROR - ``` - Running examples in ‘tabledown-Ex.R’ failed - The error most likely occurred in: - - > ### Name: ggreliability_plotly - > ### Title: A Function for Creating Item Response Theory based reliability - > ### plot based on plotly. - > ### Aliases: ggreliability_plotly - > - > ### ** Examples - > - ... - Iteration: 17, Log-Lik: -5351.363, Max-Change: 0.00011 - Iteration: 18, Log-Lik: -5351.363, Max-Change: 0.00054 - Iteration: 19, Log-Lik: -5351.363, Max-Change: 0.00012 - Iteration: 20, Log-Lik: -5351.363, Max-Change: 0.00035 - Iteration: 21, Log-Lik: -5351.363, Max-Change: 0.00010 - > - > plot <- ggreliability_plotly(data, model) - Error in pm[[2]] : subscript out of bounds - Calls: ggreliability_plotly -> -> ggplotly.ggplot -> gg2list - Execution halted - ``` - -## In both - -* checking data for non-ASCII characters ... NOTE +* checking re-building of vignette outputs ... NOTE ``` - Note: found 551 marked UTF-8 strings + Error(s) in re-building vignettes: + --- re-building ‘Dirichlet-elicitation.Rmd’ using rmarkdown ``` -# tabr +# shinipsum
-* Version: 0.4.9 -* GitHub: https://github.com/leonawicz/tabr -* Source code: https://github.com/cran/tabr -* Date/Publication: 2023-09-21 16:50:02 UTC -* Number of recursive dependencies: 80 +* Version: 0.1.1 +* GitHub: https://github.com/Thinkr-open/shinipsum +* Source code: https://github.com/cran/shinipsum +* Date/Publication: 2024-02-09 15:50:05 UTC +* Number of recursive dependencies: 90 -Run `revdepcheck::cloud_details(, "tabr")` for more info +Run `revdepcheck::cloud_details(, "shinipsum")` for more info
## Newly broken -* checking examples ... ERROR +* checking tests ... ERROR ``` - Running examples in ‘tabr-Ex.R’ failed - The error most likely occurred in: - - > ### Name: plot_fretboard - > ### Title: Chord and fretboard diagram plots - > ### Aliases: plot_fretboard plot_chord - > - > ### ** Examples - > - > # General patterns: scale shifting exercise + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(shinipsum) + > + > test_check("shinipsum") + [ FAIL 2 | WARN 1 | SKIP 0 | PASS 3150 ] + + ══ Failed tests ════════════════════════════════════════════════════════════════ ... - Backtrace: - ▆ - 1. ├─base (local) ``(x) - 2. └─ggplot2:::print.ggplot(x) - 3. ├─ggplot2::ggplot_gtable(data) - 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) - 5. └─ggplot2::calc_element("plot.margin", theme) - 6. └─cli::cli_abort(...) - 7. └─rlang::abort(...) - Execution halted + `a` has length 11, not length 10. + Backtrace: + ▆ + 1. └─base::lapply(...) at test-ggplot.R:3:3 + 2. └─shinipsum (local) FUN(X[[i]], ...) + 3. └─testthat::expect_length(a, expected_length) at test-ggplot.R:8:7 + + [ FAIL 2 | WARN 1 | SKIP 0 | PASS 3150 ] + Error: Test failures + Execution halted ``` -# TcGSA +# SimNPH
-* Version: 0.12.10 -* GitHub: https://github.com/sistm/TcGSA -* Source code: https://github.com/cran/TcGSA -* Date/Publication: 2022-02-28 21:40:02 UTC -* Number of recursive dependencies: 122 +* Version: 0.5.5 +* GitHub: https://github.com/SimNPH/SimNPH +* Source code: https://github.com/cran/SimNPH +* Date/Publication: 2024-03-04 10:10:02 UTC +* Number of recursive dependencies: 133 -Run `revdepcheck::cloud_details(, "TcGSA")` for more info +Run `revdepcheck::cloud_details(, "SimNPH")` for more info
## Newly broken -* checking running R code from vignettes ... ERROR +* checking tests ... ERROR ``` - Errors in running code in vignettes: - when running code in ‘TcGSA_userguide.Rmd’ - ... - Optimally clustering... - - DONE - - Scale for y is already present. - Adding another scale for y, which will replace the existing scale. - - When sourcing ‘TcGSA_userguide.R’: - Error: Theme element `plot.margin` must have class . - Execution halted - - ‘TcGSA_userguide.Rmd’ using ‘UTF-8’... failed + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(SimNPH) + Loading required package: SimDesign + Loading required package: survival + > + > test_check("SimNPH") + [ FAIL 2 | WARN 0 | SKIP 0 | PASS 343 ] + ... + + `names(actual)`: "x" + `names(expected)`: "x" "y" + + `actual$y` is absent + `expected$y` is a character vector ('mpg') + + [ FAIL 2 | WARN 0 | SKIP 0 | PASS 343 ] + Error: Test failures + Execution halted ``` -# TCIU +# smallsets
-* Version: 1.2.6 -* GitHub: https://github.com/SOCR/TCIU -* Source code: https://github.com/cran/TCIU -* Date/Publication: 2024-05-17 23:40:21 UTC -* Number of recursive dependencies: 172 +* Version: 2.0.0 +* GitHub: https://github.com/lydialucchesi/smallsets +* Source code: https://github.com/cran/smallsets +* Date/Publication: 2023-12-05 00:00:02 UTC +* Number of recursive dependencies: 107 -Run `revdepcheck::cloud_details(, "TCIU")` for more info +Run `revdepcheck::cloud_details(, "smallsets")` for more info
@@ -19742,67 +11857,58 @@ Run `revdepcheck::cloud_details(, "TCIU")` for more info * checking examples ... ERROR ``` - Running examples in ‘TCIU-Ex.R’ failed + Running examples in ‘smallsets-Ex.R’ failed The error most likely occurred in: - > ### Name: fmri_image - > ### Title: interactive graph object of the fMRI image - > ### Aliases: fmri_image + > ### Name: Smallset_Timeline + > ### Title: Smallset Timeline + > ### Aliases: Smallset_Timeline > > ### ** Examples > - > fmri_generate = fmri_simulate_func(dim_data = c(64, 64, 40), mask = mask) - > fmri_image(fmri_generate$fmri_data, option='manually', voxel_location = c(40,22,33), time = 4) - Error in pm[[2]] : subscript out of bounds - Calls: fmri_image ... add_trace -> add_data -> ggplotly -> ggplotly.ggplot -> gg2list + > set.seed(145) + > + > Smallset_Timeline( + + data = s_data, + + code = system.file("s_data_preprocess.R", package = "smallsets") + + ) + Error in as.unit(value) : object is not coercible to a unit + Calls: ... assemble_guides -> guides_build -> [<- -> [<-.unit -> as.unit Execution halted ``` * checking running R code from vignettes ... ERROR ``` Errors in running code in vignettes: - when running code in ‘tciu-LT-kimesurface.Rmd’ + when running code in ‘smallsets.Rmd’ ... - > require(ggplot2) - - > sample_save[[1]] - - > sample_save[[2]] + > library(smallsets) - When sourcing ‘tciu-LT-kimesurface.R’: - ... + > set.seed(145) - > fmri_image(fmri_generate$fmri_data, option = "manually", - + voxel_location = c(40, 22, 33), time = 4) + > Smallset_Timeline(data = s_data, code = system.file("s_data_preprocess.R", + + package = "smallsets")) - When sourcing ‘tciu-fMRI-analytics.R’: - Error: subscript out of bounds + When sourcing ‘smallsets.R’: + Error: object is not coercible to a unit Execution halted - ‘tciu-LT-kimesurface.Rmd’ using ‘UTF-8’... failed - ‘tciu-fMRI-analytics.Rmd’ using ‘UTF-8’... failed + ‘smallsets.Rmd’ using ‘UTF-8’... failed ``` * checking re-building of vignette outputs ... NOTE ``` Error(s) in re-building vignettes: ... - --- re-building ‘tciu-LT-kimesurface.Rmd’ using rmarkdown + --- re-building ‘smallsets.Rmd’ using rmarkdown - Quitting from lines 159-160 [unnamed-chunk-5] (tciu-LT-kimesurface.Rmd) - Error: processing vignette 'tciu-LT-kimesurface.Rmd' failed with diagnostics: - unused arguments (list(1, 2), list(list("black", 0.727272727272727, 1, "butt", FALSE, TRUE), list("white", "black", 0.727272727272727, 1, TRUE), list("", "plain", "black", 16, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), NULL, NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(4, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 4, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, 90, NULL, c(0, 4, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, - NULL, 1, -90, NULL, c(0, 0, 0, 4), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(3.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 3.2, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 1, NULL, NULL, NULL, c(0, 3.2, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, NULL, c(0, 0, 0, 3.2), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0.5, NULL, - NULL, NULL, c(0, 3.2, 0, 3.2), NULL, TRUE), list("grey20", NULL, NULL, NULL, FALSE, TRUE), NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 4, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 0.75, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, list(), NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, list(NULL, NA, NULL, NULL, TRUE), c(8, 8, 8, 8), 16, NULL, NULL, NULL, 1.2, NULL, NULL, 8, NULL, NULL, NULL, NULL, 0.2, NULL, list(NULL, NULL, NULL, 0.8, NULL, NULL, - NULL, NULL, NULL, NULL, TRUE), NULL, list(NULL, "bold", "black", 14, 0, NULL, NULL, NULL, NULL, NULL, FALSE), NULL, "right", NULL, NULL, NULL, "center", NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, c(0, 0, 0, 0), list(), 16, list("grey92", NA, NULL, NULL, TRUE), list(), 8, NULL, NULL, list("white", NULL, NULL, NULL, FALSE, TRUE), NULL, list(NULL, 0.5, NULL, NULL, FALSE, TRUE), NULL, list(), NULL, list(), FALSE, list(NULL, "white", NULL, NULL, TRUE), list(NULL, NULL, NULL, 1.2, 0.5, 1, NULL, - ... - Quitting from lines 184-185 [unnamed-chunk-5] (tciu-fMRI-analytics.Rmd) - Error: processing vignette 'tciu-fMRI-analytics.Rmd' failed with diagnostics: - subscript out of bounds - --- failed re-building ‘tciu-fMRI-analytics.Rmd’ + Quitting from lines 36-42 [timeline1] (smallsets.Rmd) + Error: processing vignette 'smallsets.Rmd' failed with diagnostics: + object is not coercible to a unit + --- failed re-building ‘smallsets.Rmd’ - SUMMARY: processing the following files failed: - ‘tciu-LT-kimesurface.Rmd’ ‘tciu-fMRI-analytics.Rmd’ + SUMMARY: processing the following file failed: + ‘smallsets.Rmd’ Error: Vignette re-building failed. Execution halted @@ -19810,460 +11916,406 @@ Run `revdepcheck::cloud_details(, "TCIU")` for more info ## In both -* checking installed package size ... NOTE +* checking package dependencies ... NOTE ``` - installed size is 14.1Mb - sub-directories of 1Mb or more: - data 1.5Mb - doc 12.0Mb + Package suggested but not available for checking: ‘gurobi’ ``` -# thematic +# spbal
-* Version: 0.1.5 -* GitHub: https://github.com/rstudio/thematic -* Source code: https://github.com/cran/thematic -* Date/Publication: 2024-02-14 00:20:03 UTC -* Number of recursive dependencies: 106 +* Version: 1.0.0 +* GitHub: NA +* Source code: https://github.com/cran/spbal +* Date/Publication: 2024-05-17 16:00:02 UTC +* Number of recursive dependencies: 77 + +Run `revdepcheck::cloud_details(, "spbal")` for more info + +
+ +## Newly broken + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘spbal.Rmd’ + ... + st_point_on_surface may not give correct results for longitude/latitude data + Warning in st_point_on_surface.sfc(sf::st_zm(x)) : + st_point_on_surface may not give correct results for longitude/latitude data + + When sourcing ‘spbal.R’: + Error: Problem while setting up geom aesthetics. + ℹ Error occurred in the 1st layer. + Caused by error in `$<-.data.frame`: + ! replacement has 1 row, data has 0 + Execution halted + + ‘spbal.Rmd’ using ‘UTF-8’... failed + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + ... + --- re-building ‘spbal.Rmd’ using rmarkdown + + Quitting from lines 159-187 [BASex1c] (spbal.Rmd) + Error: processing vignette 'spbal.Rmd' failed with diagnostics: + Problem while setting up geom aesthetics. + ℹ Error occurred in the 1st layer. + Caused by error in `$<-.data.frame`: + ! replacement has 1 row, data has 0 + --- failed re-building ‘spbal.Rmd’ + + SUMMARY: processing the following file failed: + ‘spbal.Rmd’ + + Error: Vignette re-building failed. + Execution halted + ``` + +# spinifex -Run `revdepcheck::cloud_details(, "thematic")` for more info +
+ +* Version: 0.3.7.0 +* GitHub: https://github.com/nspyrison/spinifex +* Source code: https://github.com/cran/spinifex +* Date/Publication: 2024-01-29 14:40:02 UTC +* Number of recursive dependencies: 164 + +Run `revdepcheck::cloud_details(, "spinifex")` for more info
## Newly broken -* checking examples ... ERROR - ``` - Running examples in ‘thematic-Ex.R’ failed - The error most likely occurred in: - - > ### Name: sequential_gradient - > ### Title: Control parameters of the sequential colorscale - > ### Aliases: sequential_gradient - > - > ### ** Examples - > - > - > # Gradient from fg to accent - > fg <- sequential_gradient(1, 0) - > thematic_on("black", "white", "salmon", sequential = fg) - > ggplot2::qplot(1:10, 1:10, color = 1:10) - Warning: `qplot()` was deprecated in ggplot2 3.4.0. - Error in adjust_color(user_default$colour, bg, fg, accent) : - Internal error: adjust_color() expects an input of length 1 - Calls: ... -> -> update_defaults -> adjust_color - Execution halted - ``` - * checking tests ... ERROR ``` + Running ‘spelling.R’ Running ‘testthat.R’ Running the tests in ‘tests/testthat.R’ failed. Complete output: > library(testthat) - > library(thematic) - > - > test_check("thematic") - [ FAIL 9 | WARN 1 | SKIP 7 | PASS 27 ] - - ══ Skipped tests (7) ═══════════════════════════════════════════════════════════ + > library(spinifex) + Loading required package: tourr + -------------------------------------------------------- + spinifex --- version 0.3.7.0 + Please share bugs, suggestions, and feature requests at: ... - 10. └─base::Map(...) - 11. └─base::mapply(FUN = f, ..., SIMPLIFY = FALSE) - 12. └─thematic (local) ``(dots[[1L]][[1L]], dots[[2L]][[1L]]) - 13. ├─ggplot2::update_geom_defaults(...) - 14. │ └─ggplot2:::update_defaults(geom, "Geom", new, env = parent.frame()) - 15. └─thematic:::adjust_color(user_default$colour, bg, fg, accent) + 2. │ └─base::withCallingHandlers(...) + 3. └─spinifex::play_tour_path(tour_path = tpath, data = dat_std, angle = 1) + 4. └─spinifex (local) render_type(frames = tour_df, ...) + 5. ├─plotly::ggplotly(p = gg, tooltip = "tooltip") + 6. └─plotly:::ggplotly.ggplot(p = gg, tooltip = "tooltip") + 7. └─plotly::gg2list(...) - [ FAIL 9 | WARN 1 | SKIP 7 | PASS 27 ] + [ FAIL 3 | WARN 4 | SKIP 0 | PASS 80 ] Error: Test failures Execution halted ``` -# tidybayes +# sport
-* Version: 3.0.6 -* GitHub: https://github.com/mjskay/tidybayes -* Source code: https://github.com/cran/tidybayes -* Date/Publication: 2023-08-12 23:30:02 UTC -* Number of recursive dependencies: 192 +* Version: 0.2.1 +* GitHub: https://github.com/gogonzo/sport +* Source code: https://github.com/cran/sport +* Date/Publication: 2024-01-08 23:50:02 UTC +* Number of recursive dependencies: 71 -Run `revdepcheck::cloud_details(, "tidybayes")` for more info +Run `revdepcheck::cloud_details(, "sport")` for more info
## Newly broken -* checking examples ... ERROR - ``` - Running examples in ‘tidybayes-Ex.R’ failed - The error most likely occurred in: - - > ### Name: compare_levels - > ### Title: Compare the value of draws of some variable from a Bayesian - > ### model for different levels of a factor - > ### Aliases: compare_levels - > ### Keywords: manip - > - > ### ** Examples - ... - 12. │ └─ggplot2 (local) f(l = layers[[i]], d = data[[i]]) - 13. │ └─l$compute_geom_2(d, theme = plot$theme) - 14. │ └─ggplot2 (local) compute_geom_2(..., self = self) - 15. │ └─self$geom$use_defaults(...) - 16. └─base::.handleSimpleError(...) - 17. └─rlang (local) h(simpleError(msg, call)) - 18. └─handlers[[1L]](cnd) - 19. └─cli::cli_abort(...) - 20. └─rlang::abort(...) - Execution halted - ``` - * checking tests ... ERROR ``` Running ‘testthat.R’ Running the tests in ‘tests/testthat.R’ failed. Complete output: - > # This is necessary because some tests fail otherwise; see https://github.com/hadley/testthat/issues/144 - > Sys.setenv("R_TESTS" = "") - > > library(testthat) - > library(tidybayes) > - > test_check("tidybayes") - ... - • test.geom_interval/grouped-intervals-h-stat.svg - • test.geom_pointinterval/grouped-pointintervals-h-stat.svg - • test.stat_dist_slabinterval/ccdfintervalh-using-args.svg - • test.stat_eye/one-parameter-horizontal-eye-mode-hdi.svg - • test.stat_eye/one-parameter-horizontal-half-eye.svg - • test.stat_eye/one-parameter-vertical-eye.svg - • test.stat_eye/one-parameter-vertical-halfeye.svg - • test.stat_eye/two-parameter-factor-horizontal-eye-fill.svg + > test_check("sport") + Loading required package: sport + [ FAIL 1 | WARN 0 | SKIP 0 | PASS 238 ] + + ══ Failed tests ════════════════════════════════════════════════════════════════ + ── Failure ('test_output.R:30:3'): Scale is labelled 'r' ─────────────────────── + p$labels$y not identical to "r". + target is NULL, current is character + + [ FAIL 1 | WARN 0 | SKIP 0 | PASS 238 ] Error: Test failures Execution halted ``` ## In both -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘tidy-brms.Rmd’ - ... - + ]) %>% median_qi(condition_mean = b_Intercept + r_condition, - + .width = c(0.95, 0 .... [TRUNCATED] - - When sourcing ‘tidy-brms.R’: - Error: Problem while setting up geom aesthetics. - ℹ Error occurred in the 1st layer. - Caused by error in `use_defaults()`: - ... - - When sourcing ‘tidybayes.R’: - Error: error in evaluating the argument 'object' in selecting a method for function 'sampling': object 'ABC_stan' not found - Execution halted - - ‘tidy-brms.Rmd’ using ‘UTF-8’... failed - ‘tidy-posterior.Rmd’ using ‘UTF-8’... failed - ‘tidy-rstanarm.Rmd’ using ‘UTF-8’... failed - ‘tidybayes-residuals.Rmd’ using ‘UTF-8’... failed - ‘tidybayes.Rmd’ using ‘UTF-8’... failed - ``` - -* checking package dependencies ... NOTE +* checking data for non-ASCII characters ... NOTE ``` - Package suggested but not available for checking: ‘dotwhisker’ + Note: found 7504 marked UTF-8 strings ``` -# tidyCDISC +# SqueakR
-* Version: 0.2.1 -* GitHub: https://github.com/Biogen-Inc/tidyCDISC -* Source code: https://github.com/cran/tidyCDISC -* Date/Publication: 2023-03-16 14:20:02 UTC -* Number of recursive dependencies: 140 +* Version: 1.3.0 +* GitHub: https://github.com/osimon81/SqueakR +* Source code: https://github.com/cran/SqueakR +* Date/Publication: 2022-06-28 09:20:04 UTC +* Number of recursive dependencies: 145 -Run `revdepcheck::cloud_details(, "tidyCDISC")` for more info +Run `revdepcheck::cloud_details(, "SqueakR")` for more info
## Newly broken -* checking tests ... ERROR +* checking re-building of vignette outputs ... NOTE ``` - Running ‘spelling.R’ - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(tidyCDISC) - > library(shinyjs) - - Attaching package: 'shinyjs' - - ... - 6. ├─plotly::config(...) - 7. │ └─plotly:::modify_list(p$x$config, args) - 8. │ ├─utils::modifyList(x %||% list(), y %||% list(), ...) - 9. │ │ └─base::stopifnot(is.list(x), is.list(val)) - 10. │ └─x %||% list() - 11. └─plotly::layout(...) - - [ FAIL 1 | WARN 1 | SKIP 15 | PASS 91 ] - Error: Test failures - Execution halted + Error(s) in re-building vignettes: + --- re-building ‘SqueakR.Rmd’ using rmarkdown ``` ## In both +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘SqueakR.Rmd’ + ... + $ experimenters : NULL + $ experimental_data: list() + + > my_new_data <- add_timepoint_data(data_path = "../inst/extdata/Example_Mouse_Data.xlsx", + + t1 = 5, t2 = 25) + Adding call features Excel file to workspace... + + When sourcing ‘SqueakR.R’: + Error: `path` does not exist: ‘../inst/extdata/Example_Mouse_Data.xlsx’ + Execution halted + + ‘SqueakR.Rmd’ using ‘UTF-8’... failed + ``` + * checking installed package size ... NOTE ``` - installed size is 6.0Mb + installed size is 8.8Mb sub-directories of 1Mb or more: - R 1.0Mb - data 2.0Mb - doc 1.8Mb + doc 8.2Mb ``` -# tidydr +# statgenGWAS
-* Version: 0.0.5 -* GitHub: https://github.com/YuLab-SMU/tidydr -* Source code: https://github.com/cran/tidydr -* Date/Publication: 2023-03-08 09:20:02 UTC -* Number of recursive dependencies: 74 +* Version: 1.0.9 +* GitHub: https://github.com/Biometris/statgenGWAS +* Source code: https://github.com/cran/statgenGWAS +* Date/Publication: 2022-10-13 15:30:43 UTC +* Number of recursive dependencies: 71 -Run `revdepcheck::cloud_details(, "tidydr")` for more info +Run `revdepcheck::cloud_details(, "statgenGWAS")` for more info
## Newly broken -* checking whether package ‘tidydr’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/tidydr/new/tidydr.Rcheck/00install.out’ for details. +* checking tests ... ERROR + ``` + Running ‘tinytest.R’ + Running the tests in ‘tests/tinytest.R’ failed. + Complete output: + > + > if ( requireNamespace("tinytest", quietly=TRUE) ){ + + tinytest::test_package("statgenGWAS") + + } + + test_GWAS.R................... 0 tests + test_GWAS.R................... 0 tests + ... + conversion failure on '← 2@3' in 'mbcsToSbcs': dot substituted for <86> + 3: In grid.Call.graphics(C_text, as.graphicsAnnot(x$label), x$x, x$y, : + conversion failure on '← 2@3' in 'mbcsToSbcs': dot substituted for <90> + 4: In grid.Call.graphics(C_text, as.graphicsAnnot(x$label), x$x, x$y, : + conversion failure on '← 2@3' in 'mbcsToSbcs': dot substituted for + 5: In grid.Call.graphics(C_text, as.graphicsAnnot(x$label), x$x, x$y, : + conversion failure on '← 2@3' in 'mbcsToSbcs': dot substituted for <86> + 6: In grid.Call.graphics(C_text, as.graphicsAnnot(x$label), x$x, x$y, : + conversion failure on '← 2@3' in 'mbcsToSbcs': dot substituted for <90> + Execution halted ``` -## Installation - -### Devel - -``` -* installing *source* package ‘tidydr’ ... -** package ‘tidydr’ successfully unpacked and MD5 sums checked -** using staged installation -** R -** inst -** byte-compile and prepare package for lazy loading -Error in get(x, envir = ns, inherits = FALSE) : - object 'len0_null' not found -Error: unable to load R code in package ‘tidydr’ -Execution halted -ERROR: lazy loading failed for package ‘tidydr’ -* removing ‘/tmp/workdir/tidydr/new/tidydr.Rcheck/tidydr’ - - -``` -### CRAN - -``` -* installing *source* package ‘tidydr’ ... -** package ‘tidydr’ successfully unpacked and MD5 sums checked -** using staged installation -** R -** inst -** byte-compile and prepare package for lazy loading -** help -*** installing help indices -** building package indices -** installing vignettes -** testing if installed package can be loaded from temporary location -** testing if installed package can be loaded from final location -** testing if installed package keeps a record of temporary installation path -* DONE (tidydr) - +## In both -``` -# tidysdm +* checking C++ specification ... NOTE + ``` + Specified C++11: please drop specification unless essential + ``` + +* checking installed package size ... NOTE + ``` + installed size is 15.2Mb + sub-directories of 1Mb or more: + data 7.0Mb + libs 7.1Mb + ``` + +# surveyexplorer
-* Version: 0.9.4 -* GitHub: https://github.com/EvolEcolGroup/tidysdm -* Source code: https://github.com/cran/tidysdm -* Date/Publication: 2024-03-05 20:30:02 UTC -* Number of recursive dependencies: 167 +* Version: 0.2.0 +* GitHub: NA +* Source code: https://github.com/cran/surveyexplorer +* Date/Publication: 2024-06-07 09:50:02 UTC +* Number of recursive dependencies: 87 -Run `revdepcheck::cloud_details(, "tidysdm")` for more info +Run `revdepcheck::cloud_details(, "surveyexplorer")` for more info
## Newly broken -* checking running R code from vignettes ... ERROR +* checking examples ... ERROR ``` - Errors in running code in vignettes: - when running code in ‘a0_tidysdm_overview.Rmd’ - ... - > climate_vars <- names(climate_present) - - > lacerta_thin <- lacerta_thin %>% bind_cols(terra::extract(climate_present, - + lacerta_thin, ID = FALSE)) + Running examples in ‘surveyexplorer-Ex.R’ failed + The error most likely occurred in: - > lacerta_thin %>% plot_pres_vs_bg(class) + > ### Name: multi_freq + > ### Title: Generate an UpSet plot for multiple-choice questions + > ### Aliases: multi_freq + > + > ### ** Examples + > + > + ... - When sourcing ‘a0_tidysdm_overview.R’: - Error: object is not a unit + > + > #Basic Upset plot + > + > #Use `group_by` to partition the question into several groups + > multi_freq(berlinbears, question = dplyr::starts_with('will_eat'), group_by + + = gender) + Error in as.unit(e2) : object is not coercible to a unit + Calls: ... polylineGrob -> is.unit -> unit.c -> Ops.unit -> as.unit Execution halted - - ‘a0_tidysdm_overview.Rmd’ using ‘UTF-8’... failed - ‘a1_palaeodata_application.Rmd’ using ‘UTF-8’... OK - ‘a2_tidymodels_additions.Rmd’ using ‘UTF-8’... OK - ‘a3_troubleshooting.Rmd’ using ‘UTF-8’... OK - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘a0_tidysdm_overview.Rmd’ using rmarkdown ``` -# tidytreatment +# Sysrecon
-* Version: 0.2.2 -* GitHub: https://github.com/bonStats/tidytreatment -* Source code: https://github.com/cran/tidytreatment -* Date/Publication: 2022-02-21 09:00:07 UTC -* Number of recursive dependencies: 98 +* Version: 0.1.3 +* GitHub: NA +* Source code: https://github.com/cran/Sysrecon +* Date/Publication: 2023-02-20 08:50:02 UTC +* Number of recursive dependencies: 61 -Run `revdepcheck::cloud_details(, "tidytreatment")` for more info +Run `revdepcheck::cloud_details(, "Sysrecon")` for more info
## Newly broken -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘use-tidytreatment-BART.Rmd’ - ... - + by = ".row") %>% ggplot() + stat_halfeye(aes(x = z, y = fit)) + - + facet_wrap(~c1, l .... [TRUNCATED] - - When sourcing ‘use-tidytreatment-BART.R’: - Error: Problem while setting up geom aesthetics. - ℹ Error occurred in the 1st layer. - Caused by error in `use_defaults()`: - ! unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, "black", TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), NULL, list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), 5.5, c(5.5, 5.5, 5.5, 5.5), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.75, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, - NULL, NULL, NULL, 1, 90, NULL, c(0, 2.75, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, - Execution halted - - ‘use-tidytreatment-BART.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE +* checking examples ... ERROR ``` - Error(s) in re-building vignettes: - ... - --- re-building ‘use-tidytreatment-BART.Rmd’ using rmarkdown + Running examples in ‘Sysrecon-Ex.R’ failed + The error most likely occurred in: - Quitting from lines 163-177 [plot-tidy-bart] (use-tidytreatment-BART.Rmd) - Error: processing vignette 'use-tidytreatment-BART.Rmd' failed with diagnostics: - Problem while setting up geom aesthetics. - ℹ Error occurred in the 1st layer. - Caused by error in `use_defaults()`: - ! unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, "black", TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), NULL, list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), 5.5, c(5.5, 5.5, 5.5, 5.5), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.75, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, + > ### Name: Sysrecon + > ### Title: Sysrecon + > ### Aliases: Sysrecon + > + > ### ** Examples + > + > ... - NULL, NULL, 1.2, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 0.2, NULL, list(NULL, NULL, NULL, 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, NULL, NULL, NULL, TRUE), NULL, "right", NULL, NULL, NULL, "center", NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 0, list(), 2, list("white", NA, NULL, NULL, TRUE), list(NULL, "grey20", NULL, NULL, TRUE), NULL, NULL, NULL, list("grey92", NULL, NULL, NULL, FALSE, "grey92", TRUE), NULL, list(NULL, 0.5, NULL, - NULL, FALSE, NULL, TRUE), NULL, NULL, NULL, NULL, FALSE, list(NULL, "white", NULL, NULL, TRUE), list(NULL, NULL, NULL, 1.2, 0, 1, NULL, NULL, c(0, 0, 5.5, 0), NULL, TRUE), "panel", list(NULL, NULL, NULL, NULL, 0, 1, NULL, NULL, c(0, 0, 5.5, 0), NULL, TRUE), list(NULL, NULL, NULL, 0.8, 1, 1, NULL, NULL, c(5.5, 0, 0, 0), NULL, TRUE), "panel", list(NULL, NULL, NULL, 1.2, 0.5, 0.5, NULL, NULL, NULL, NULL, TRUE), "topleft", NULL, NULL, list("grey85", "grey20", NULL, NULL, TRUE), NULL, NULL, "inherit", - "inside", list(NULL, NULL, "grey10", 0.8, NULL, NULL, NULL, NULL, c(4.4, 4.4, 4.4, 4.4), NULL, TRUE), NULL, NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, NULL, -90, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, NULL, 90, NULL, NULL, NULL, TRUE), NULL, 2.75, 2.75)) - --- failed re-building ‘use-tidytreatment-BART.Rmd’ - - SUMMARY: processing the following file failed: - ‘use-tidytreatment-BART.Rmd’ - - Error: Vignette re-building failed. + no non-missing arguments to min; returning Inf + Warning in min(freq[grepl(i, allwords, ignore.case = T)]) : + no non-missing arguments to min; returning Inf + Warning in min(freq[grepl(i, allwords, ignore.case = T)]) : + no non-missing arguments to min; returning Inf + Warning in min(freq[grepl(i, allwords, ignore.case = T)]) : + no non-missing arguments to min; returning Inf + Error in as.unit(value) : object is not coercible to a unit + Calls: Sysrecon ... assemble_guides -> guides_build -> [<- -> [<-.unit -> as.unit Execution halted ``` ## In both -* checking package dependencies ... NOTE +* checking data for non-ASCII characters ... NOTE ``` - Package which this enhances but not available for checking: ‘bartMachine’ + Note: found 38 marked UTF-8 strings ``` -# timetk +# tabledown
-* Version: 2.9.0 -* GitHub: https://github.com/business-science/timetk -* Source code: https://github.com/cran/timetk -* Date/Publication: 2023-10-31 22:30:02 UTC -* Number of recursive dependencies: 226 +* Version: 1.0.0 +* GitHub: https://github.com/masiraji/tabledown +* Source code: https://github.com/cran/tabledown +* Date/Publication: 2024-05-02 13:40:03 UTC +* Number of recursive dependencies: 163 -Run `revdepcheck::cloud_details(, "timetk")` for more info +Run `revdepcheck::cloud_details(, "tabledown")` for more info
## Newly broken -* checking tests ... ERROR +* checking examples ... ERROR ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > # This file is part of the standard setup for testthat. - > # It is recommended that you do not modify it. - > # - > # Where should you do additional test configuration? - > # Learn more about the roles of various files in: - > # * https://r-pkgs.org/testing-design.html#sec-tests-files-overview - > # * https://testthat.r-lib.org/articles/special-files.html + Running examples in ‘tabledown-Ex.R’ failed + The error most likely occurred in: + + > ### Name: ggreliability_plotly + > ### Title: A Function for Creating Item Response Theory based reliability + > ### plot based on plotly. + > ### Aliases: ggreliability_plotly + > + > ### ** Examples + > ... - 7. └─timetk:::plot_time_series.grouped_df(...) - 8. ├─timetk::plot_time_series(...) - 9. └─timetk:::plot_time_series.data.frame(...) - 10. ├─plotly::ggplotly(g, dynamicTicks = TRUE) - 11. └─plotly:::ggplotly.ggplot(g, dynamicTicks = TRUE) - 12. └─plotly::gg2list(...) - - [ FAIL 1 | WARN 0 | SKIP 0 | PASS 406 ] - Error: Test failures - Execution halted + Iteration: 17, Log-Lik: -5351.363, Max-Change: 0.00011 + Iteration: 18, Log-Lik: -5351.363, Max-Change: 0.00054 + Iteration: 19, Log-Lik: -5351.363, Max-Change: 0.00012 + Iteration: 20, Log-Lik: -5351.363, Max-Change: 0.00035 + Iteration: 21, Log-Lik: -5351.363, Max-Change: 0.00010 + > + > plot <- ggreliability_plotly(data, model) + Error in pm[[2]] : subscript out of bounds + Calls: ggreliability_plotly -> -> ggplotly.ggplot -> gg2list + Execution halted ``` ## In both * checking data for non-ASCII characters ... NOTE ``` - Note: found 2750 marked UTF-8 strings + Note: found 551 marked UTF-8 strings ``` -# tinyarray +# TCIU
-* Version: 2.4.1 -* GitHub: https://github.com/xjsun1221/tinyarray -* Source code: https://github.com/cran/tinyarray -* Date/Publication: 2024-06-04 09:45:15 UTC -* Number of recursive dependencies: 240 +* Version: 1.2.6 +* GitHub: https://github.com/SOCR/TCIU +* Source code: https://github.com/cran/TCIU +* Date/Publication: 2024-05-17 23:40:21 UTC +* Number of recursive dependencies: 163 -Run `revdepcheck::cloud_details(, "tinyarray")` for more info +Run `revdepcheck::cloud_details(, "TCIU")` for more info
@@ -20271,159 +12323,146 @@ Run `revdepcheck::cloud_details(, "tinyarray")` for more info * checking examples ... ERROR ``` - Running examples in ‘tinyarray-Ex.R’ failed + Running examples in ‘TCIU-Ex.R’ failed The error most likely occurred in: - > ### Name: exp_surv - > ### Title: exp_surv - > ### Aliases: exp_surv - > - > ### ** Examples - > - > tmp = exp_surv(exprSet_hub1,meta1) - > patchwork::wrap_plots(tmp)+patchwork::plot_layout(guides = "collect") - Error in identicalUnits(x) : object is not a unit - Calls: ... assemble_guides -> guides_build -> unit.c -> identicalUnits + > ### Name: fmri_image + > ### Title: interactive graph object of the fMRI image + > ### Aliases: fmri_image + > + > ### ** Examples + > + > fmri_generate = fmri_simulate_func(dim_data = c(64, 64, 40), mask = mask) + > fmri_image(fmri_generate$fmri_data, option='manually', voxel_location = c(40,22,33), time = 4) + Error in pm[[2]] : subscript out of bounds + Calls: fmri_image ... add_trace -> add_data -> ggplotly -> ggplotly.ggplot -> gg2list + Execution halted + ``` + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘tciu-LT-kimesurface.Rmd’ + ... + > require(ggplot2) + + > sample_save[[1]] + + > sample_save[[2]] + + When sourcing ‘tciu-LT-kimesurface.R’: + ... + + > fmri_image(fmri_generate$fmri_data, option = "manually", + + voxel_location = c(40, 22, 33), time = 4) + + When sourcing ‘tciu-fMRI-analytics.R’: + Error: subscript out of bounds + Execution halted + + ‘tciu-LT-kimesurface.Rmd’ using ‘UTF-8’... failed + ‘tciu-fMRI-analytics.Rmd’ using ‘UTF-8’... failed + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + ... + --- re-building ‘tciu-LT-kimesurface.Rmd’ using rmarkdown + + Quitting from lines 159-160 [unnamed-chunk-5] (tciu-LT-kimesurface.Rmd) + Error: processing vignette 'tciu-LT-kimesurface.Rmd' failed with diagnostics: + unused arguments (list(1, 2), list(list("black", 0.727272727272727, 1, "butt", FALSE, TRUE), list("white", "black", 0.727272727272727, 1, TRUE), list("", "plain", "black", 16, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), NULL, NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(4, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 4, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, 90, NULL, c(0, 4, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, + NULL, 1, -90, NULL, c(0, 0, 0, 4), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(3.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 3.2, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 1, NULL, NULL, NULL, c(0, 3.2, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, NULL, c(0, 0, 0, 3.2), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0.5, NULL, + NULL, NULL, c(0, 3.2, 0, 3.2), NULL, TRUE), list("grey20", NULL, NULL, NULL, FALSE, TRUE), NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 4, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 0.75, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, list(), NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, list(NULL, NA, NULL, NULL, TRUE), c(8, 8, 8, 8), 16, NULL, NULL, NULL, 1.2, NULL, NULL, 8, NULL, NULL, NULL, NULL, 0.2, NULL, list(NULL, NULL, NULL, 0.8, NULL, NULL, + NULL, NULL, NULL, NULL, TRUE), NULL, list(NULL, "bold", "black", 14, 0, NULL, NULL, NULL, NULL, NULL, FALSE), NULL, "right", NULL, NULL, NULL, "center", NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, c(0, 0, 0, 0), list(), 16, list("grey92", NA, NULL, NULL, TRUE), list(), 8, NULL, NULL, list("white", NULL, NULL, NULL, FALSE, TRUE), NULL, list(NULL, 0.5, NULL, NULL, FALSE, TRUE), NULL, list(), NULL, list(), FALSE, list(NULL, "white", NULL, NULL, TRUE), list(NULL, NULL, NULL, 1.2, 0.5, 1, NULL, + ... + Quitting from lines 184-185 [unnamed-chunk-5] (tciu-fMRI-analytics.Rmd) + Error: processing vignette 'tciu-fMRI-analytics.Rmd' failed with diagnostics: + subscript out of bounds + --- failed re-building ‘tciu-fMRI-analytics.Rmd’ + + SUMMARY: processing the following files failed: + ‘tciu-LT-kimesurface.Rmd’ ‘tciu-fMRI-analytics.Rmd’ + + Error: Vignette re-building failed. Execution halted ``` ## In both -* checking data for non-ASCII characters ... NOTE - ``` - Note: found 2 marked UTF-8 strings - ``` - -# tmap - -
- -* Version: 3.3-4 -* GitHub: https://github.com/r-tmap/tmap -* Source code: https://github.com/cran/tmap -* Date/Publication: 2023-09-12 21:20:02 UTC -* Number of recursive dependencies: 145 - -Run `revdepcheck::cloud_details(, "tmap")` for more info - -
- -## Newly broken - -* checking examples ... ERROR +* checking installed package size ... NOTE ``` - Running examples in ‘tmap-Ex.R’ failed - The error most likely occurred in: - - > ### Name: tm_symbols - > ### Title: Draw symbols - > ### Aliases: tm_symbols tm_squares tm_bubbles tm_dots tm_markers - > - > ### ** Examples - > - > data(World, metro) - ... - ▆ - 1. └─base::lapply(...) - 2. └─global FUN(X[[i]], ...) - 3. └─ggplot2::ggplotGrob(...) - 4. ├─ggplot2::ggplot_gtable(ggplot_build(x)) - 5. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) - 6. └─ggplot2::calc_element("plot.margin", theme) - 7. └─cli::cli_abort(...) - 8. └─rlang::abort(...) - Execution halted + installed size is 14.1Mb + sub-directories of 1Mb or more: + data 1.5Mb + doc 12.0Mb ``` -# TOmicsVis +# tensorEVD
-* Version: 2.0.0 -* GitHub: https://github.com/benben-miao/TOmicsVis -* Source code: https://github.com/cran/TOmicsVis -* Date/Publication: 2023-08-28 18:30:02 UTC -* Number of recursive dependencies: 264 +* Version: 0.1.3 +* GitHub: https://github.com/MarcooLopez/tensorEVD +* Source code: https://github.com/cran/tensorEVD +* Date/Publication: 2024-05-30 07:10:02 UTC +* Number of recursive dependencies: 61 -Run `revdepcheck::cloud_details(, "TOmicsVis")` for more info +Run `revdepcheck::cloud_details(, "tensorEVD")` for more info
## Newly broken -* checking examples ... ERROR - ``` - Running examples in ‘TOmicsVis-Ex.R’ failed - The error most likely occurred in: - - > ### Name: upsetr_plot - > ### Title: UpSet plot for stat common and unique gene among multiple sets. - > ### Aliases: upsetr_plot - > - > ### ** Examples - > - > # 1. Library TOmicsVis package - ... - 3. ├─base::suppressMessages(...) - 4. │ └─base::withCallingHandlers(...) - 5. └─UpSetR:::Make_main_bar(...) - 6. └─ggplot2::ggplotGrob(Main_bar_plot) - 7. ├─ggplot2::ggplot_gtable(ggplot_build(x)) - 8. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) - 9. └─ggplot2::calc_element("plot.margin", theme) - 10. └─cli::cli_abort(...) - 11. └─rlang::abort(...) - Execution halted - ``` - * checking running R code from vignettes ... ERROR ``` Errors in running code in vignettes: - when running code in ‘Tutorials.Rmd’ + when running code in ‘tensorEVD-documentation.Rmd’ ... - 5 transcript_8832 transcript_3069 transcript_10224 transcript_9881 - 6 transcript_74 transcript_9809 transcript_3151 transcript_8836 - > upsetr_plot(data = degs_lists, sets_num = 4, keep_order = FALSE, - + order_by = "freq", decrease = TRUE, mainbar_color = "#006600", - + number .... [TRUNCATED] + > dat0$alpha <- factor(as.character(dat0$alpha)) + + > figure2 <- make_plot(dat0, x = "alpha", y = "Frobenius", + + group = "method", by = "n", facet = "nG", facet2 = "nE", + + facet.type = "grid", .... [TRUNCATED] - When sourcing ‘Tutorials.R’: - Error: Theme element `plot.margin` must have class . + When sourcing ‘tensorEVD-documentation.R’: + Error: attempt to set an attribute on NULL Execution halted - ‘Tutorials.Rmd’ using ‘UTF-8’... failed + ‘tensorEVD-documentation.Rmd’ using ‘UTF-8’... failed ``` * checking re-building of vignette outputs ... NOTE ``` Error(s) in re-building vignettes: - --- re-building ‘Tutorials.Rmd’ using rmarkdown - ``` - -## In both - -* checking installed package size ... NOTE - ``` - installed size is 7.3Mb - sub-directories of 1Mb or more: - data 1.5Mb - data-tables 1.5Mb - doc 1.9Mb - help 1.2Mb + ... + --- re-building ‘tensorEVD-documentation.Rmd’ using rmarkdown + + Quitting from lines 253-265 [unnamed-chunk-6] (tensorEVD-documentation.Rmd) + Error: processing vignette 'tensorEVD-documentation.Rmd' failed with diagnostics: + attempt to set an attribute on NULL + --- failed re-building ‘tensorEVD-documentation.Rmd’ + + SUMMARY: processing the following file failed: + ‘tensorEVD-documentation.Rmd’ + + Error: Vignette re-building failed. + Execution halted ``` -# tornado +# thematic
-* Version: 0.1.3 -* GitHub: https://github.com/bertcarnell/tornado -* Source code: https://github.com/cran/tornado -* Date/Publication: 2024-01-21 17:30:02 UTC -* Number of recursive dependencies: 115 +* Version: 0.1.5 +* GitHub: https://github.com/rstudio/thematic +* Source code: https://github.com/cran/thematic +* Date/Publication: 2024-02-14 00:20:03 UTC +* Number of recursive dependencies: 106 -Run `revdepcheck::cloud_details(, "tornado")` for more info +Run `revdepcheck::cloud_details(, "thematic")` for more info
@@ -20431,26 +12470,24 @@ Run `revdepcheck::cloud_details(, "tornado")` for more info * checking examples ... ERROR ``` - Running examples in ‘tornado-Ex.R’ failed + Running examples in ‘thematic-Ex.R’ failed The error most likely occurred in: - > ### Name: plot.tornado_plot - > ### Title: Plot a Tornado Plot object - > ### Aliases: plot.tornado_plot + > ### Name: sequential_gradient + > ### Title: Control parameters of the sequential colorscale + > ### Aliases: sequential_gradient > > ### ** Examples > - > gtest <- lm(mpg ~ cyl*wt*hp, data = mtcars) - ... - 13. │ └─base::withCallingHandlers(...) - 14. └─ggplot2 (local) f(l = layers[[i]], d = data[[i]]) - 15. └─l$compute_geom_2(d, theme = plot$theme) - 16. └─ggplot2 (local) compute_geom_2(..., self = self) - 17. └─self$geom$use_defaults(...) - 18. └─ggplot2 (local) use_defaults(..., self = self) - 19. └─ggplot2:::check_aesthetics(new_params, nrow(data)) - 20. └─cli::cli_abort(...) - 21. └─rlang::abort(...) + > + > # Gradient from fg to accent + > fg <- sequential_gradient(1, 0) + > thematic_on("black", "white", "salmon", sequential = fg) + > ggplot2::qplot(1:10, 1:10, color = 1:10) + Warning: `qplot()` was deprecated in ggplot2 3.4.0. + Error in adjust_color(user_default$colour, bg, fg, accent) : + Internal error: adjust_color() expects an input of length 1 + Calls: ... -> -> update_defaults -> adjust_color Execution halted ``` @@ -20459,62 +12496,37 @@ Run `revdepcheck::cloud_details(, "tornado")` for more info Running ‘testthat.R’ Running the tests in ‘tests/testthat.R’ failed. Complete output: - > if (require(testthat)) - + { - + library(tornado) - + - + test_check("tornado") - + } - Loading required package: testthat + > library(testthat) + > library(thematic) + > + > test_check("thematic") + [ FAIL 9 | WARN 1 | SKIP 7 | PASS 27 ] + + ══ Skipped tests (7) ═══════════════════════════════════════════════════════════ ... - ...)) - })(position = "identity", stat = "identity", width = NULL)`: Problem while setting up geom aesthetics. - ℹ Error occurred in the 1st layer. - Caused by error in `check_aesthetics()`: - ! Aesthetics must be either length 1 or the same as the data (20). - ✖ Fix the following mappings: `width`. + 10. └─base::Map(...) + 11. └─base::mapply(FUN = f, ..., SIMPLIFY = FALSE) + 12. └─thematic (local) ``(dots[[1L]][[1L]], dots[[2L]][[1L]]) + 13. ├─ggplot2::update_geom_defaults(...) + 14. │ └─ggplot2:::update_defaults(geom, "Geom", new, env = parent.frame()) + 15. └─thematic:::adjust_color(user_default$colour, bg, fg, accent) - [ FAIL 14 | WARN 0 | SKIP 0 | PASS 101 ] + [ FAIL 9 | WARN 1 | SKIP 7 | PASS 27 ] Error: Test failures Execution halted ``` -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘tornadoVignette.Rmd’ - ... - + .... [TRUNCATED] - Loading required package: lattice - - When sourcing ‘tornadoVignette.R’: - Error: Problem while setting up geom aesthetics. - ℹ Error occurred in the 1st layer. - Caused by error in `check_aesthetics()`: - ! Aesthetics must be either length 1 or the same as the data (20). - ✖ Fix the following mappings: `width`. - Execution halted - - ‘tornadoVignette.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘tornadoVignette.Rmd’ using rmarkdown - ``` - -# TOSTER +# tidybayes
-* Version: 0.8.3 -* GitHub: NA -* Source code: https://github.com/cran/TOSTER -* Date/Publication: 2024-05-08 16:40:02 UTC -* Number of recursive dependencies: 102 +* Version: 3.0.6 +* GitHub: https://github.com/mjskay/tidybayes +* Source code: https://github.com/cran/tidybayes +* Date/Publication: 2023-08-12 23:30:02 UTC +* Number of recursive dependencies: 200 -Run `revdepcheck::cloud_details(, "TOSTER")` for more info +Run `revdepcheck::cloud_details(, "tidybayes")` for more info
@@ -20522,50 +12534,52 @@ Run `revdepcheck::cloud_details(, "TOSTER")` for more info * checking examples ... ERROR ``` - Running examples in ‘TOSTER-Ex.R’ failed + Running examples in ‘tidybayes-Ex.R’ failed The error most likely occurred in: - > ### Name: dataTOSTone - > ### Title: TOST One Sample T-Test - > ### Aliases: dataTOSTone + > ### Name: compare_levels + > ### Title: Compare the value of draws of some variable from a Bayesian + > ### model for different levels of a factor + > ### Aliases: compare_levels + > ### Keywords: manip > > ### ** Examples - > - > library("TOSTER") ... - N Mean Median SD SE - ───────────────────────────────────────────────────────────────────────── - Sepal.Width 150 3.057333 3.000000 0.4358663 0.03558833 - ───────────────────────────────────────────────────────────────────────── - - Error in use_defaults(..., self = self) : - unused argument (theme = list(list("black", 0.727272727272727, 1, "butt", FALSE, "black", TRUE), list("white", "black", 0.727272727272727, 1, TRUE), list("", "plain", "black", 16, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), NULL, list("black", "white", "#3366FF", 0.727272727272727, 1.45454545454545, "", 5.62335685623357, 2.18181818181818, 19, TRUE), 8, c(8, 8, 8, 8), NULL, NULL, list(NULL, NULL, "#333333", NULL, NULL, NULL, NULL, NULL, c(10, 0, 0, 0), NULL, FALSE), list(NULL, NULL, NULL, NULL, NULL, 0, - NULL, NULL, c(0, 0, 4, 0), NULL, TRUE), NULL, list(NULL, NULL, "#333333", NULL, NULL, NULL, 90, NULL, c(0, 10, 0, 0), NULL, FALSE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 4), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, "#333333", NULL, NULL, NULL, NULL, NULL, c(5, 0, 0, 0), NULL, FALSE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 3.2, 0), NULL, TRUE), NULL, list(), NULL - Calls: ... -> -> -> + 12. │ └─ggplot2 (local) f(l = layers[[i]], d = data[[i]]) + 13. │ └─l$compute_geom_2(d, theme = plot$theme) + 14. │ └─ggplot2 (local) compute_geom_2(..., self = self) + 15. │ └─self$geom$use_defaults(...) + 16. └─base::.handleSimpleError(...) + 17. └─rlang (local) h(simpleError(msg, call)) + 18. └─handlers[[1L]](cnd) + 19. └─cli::cli_abort(...) + 20. └─rlang::abort(...) Execution halted ``` +## In both + * checking tests ... ERROR ``` - Running ‘spelling.R’ Running ‘testthat.R’ Running the tests in ‘tests/testthat.R’ failed. Complete output: + > # This is necessary because some tests fail otherwise; see https://github.com/hadley/testthat/issues/144 + > Sys.setenv("R_TESTS" = "") + > > library(testthat) - > library(TOSTER) - - Attaching package: 'TOSTER' - - The following object is masked from 'package:testthat': + > library(tidybayes) + > + > test_check("tidybayes") ... - 26. └─base::Map(...) - 27. └─base::mapply(FUN = f, ..., SIMPLIFY = FALSE) - 28. └─ggplot2 (local) ``(layer = dots[[1L]][[1L]], df = dots[[2L]][[1L]]) - 29. └─layer$compute_geom_2(key, single_params, theme) - 30. └─ggplot2 (local) compute_geom_2(..., self = self) - 31. └─self$geom$use_defaults(...) - - [ FAIL 8 | WARN 0 | SKIP 0 | PASS 1034 ] + • test.geom_interval/grouped-intervals-h-stat.svg + • test.geom_pointinterval/grouped-pointintervals-h-stat.svg + • test.stat_dist_slabinterval/ccdfintervalh-using-args.svg + • test.stat_eye/one-parameter-horizontal-eye-mode-hdi.svg + • test.stat_eye/one-parameter-horizontal-half-eye.svg + • test.stat_eye/one-parameter-vertical-eye.svg + • test.stat_eye/one-parameter-vertical-halfeye.svg + • test.stat_eye/two-parameter-factor-horizontal-eye-fill.svg Error: Test failures Execution halted ``` @@ -20573,45 +12587,39 @@ Run `revdepcheck::cloud_details(, "TOSTER")` for more info * checking running R code from vignettes ... ERROR ``` Errors in running code in vignettes: - when running code in ‘IntroTOSTt.Rmd’ + when running code in ‘tidy-brms.Rmd’ ... - mean of x mean of y - 0.75 2.33 - - - > plot(res1, type = "cd") + + ]) %>% median_qi(condition_mean = b_Intercept + r_condition, + + .width = c(0.95, 0 .... [TRUNCATED] - When sourcing ‘IntroTOSTt.R’: + When sourcing ‘tidy-brms.R’: + Error: Problem while setting up geom aesthetics. + ℹ Error occurred in the 1st layer. + Caused by error in `use_defaults()`: ... - Error: unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, "black", TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), NULL, list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), 5.5, c(5.5, 5.5, 5.5, 5.5), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(7, 0, 0, 0), NULL, FALSE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, - NULL, NULL, 1, 90, NULL, c(0, 7, 0, 0), NULL, FALSE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, "bold", NULL, 11, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, FALSE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, NULL, c(0, 0, 0, 2.2), NULL, TRUE) + + When sourcing ‘tidybayes.R’: + Error: error in evaluating the argument 'object' in selecting a method for function 'sampling': object 'ABC_stan' not found Execution halted - ‘IntroTOSTt.Rmd’ using ‘UTF-8’... failed - ‘IntroductionToTOSTER.Rmd’ using ‘UTF-8’... OK - ‘SMD_calcs.Rmd’ using ‘UTF-8’... OK - ‘correlations.Rmd’ using ‘UTF-8’... OK - ‘robustTOST.Rmd’ using ‘UTF-8’... failed - ‘the_ftestTOSTER.Rmd’ using ‘UTF-8’... OK - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘IntroTOSTt.Rmd’ using rmarkdown + ‘tidy-brms.Rmd’ using ‘UTF-8’... failed + ‘tidy-posterior.Rmd’ using ‘UTF-8’... failed + ‘tidy-rstanarm.Rmd’ using ‘UTF-8’... failed + ‘tidybayes-residuals.Rmd’ using ‘UTF-8’... failed + ‘tidybayes.Rmd’ using ‘UTF-8’... failed ``` -# toxEval +# tidycat
-* Version: 1.3.2 -* GitHub: https://github.com/DOI-USGS/toxEval -* Source code: https://github.com/cran/toxEval -* Date/Publication: 2024-02-08 07:30:02 UTC -* Number of recursive dependencies: 127 +* Version: 0.1.2 +* GitHub: https://github.com/guyabel/tidycat +* Source code: https://github.com/cran/tidycat +* Date/Publication: 2021-08-02 04:20:01 UTC +* Number of recursive dependencies: 70 -Run `revdepcheck::cloud_details(, "toxEval")` for more info +Run `revdepcheck::cloud_details(, "tidycat")` for more info
@@ -20619,49 +12627,73 @@ Run `revdepcheck::cloud_details(, "toxEval")` for more info * checking examples ... ERROR ``` - Running examples in ‘toxEval-Ex.R’ failed + Running examples in ‘tidycat-Ex.R’ failed The error most likely occurred in: - > ### Name: plot_tox_stacks - > ### Title: Plot stacked bar charts - > ### Aliases: plot_tox_stacks + > ### Name: tidy_categorical + > ### Title: Expand broom::tidy() Outputs for Categorical Parameter Estimates + > ### Aliases: tidy_categorical > > ### ** Examples > - > # This is the example workflow: + > # strip ordering in factors (currently ordered factor not supported) ... - Backtrace: - ▆ - 1. ├─base (local) ``(x) - 2. └─ggplot2:::print.ggplot(x) - 3. ├─ggplot2::ggplot_gtable(data) - 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) - 5. └─ggplot2::calc_element("plot.margin", theme) - 6. └─cli::cli_abort(...) - 7. └─rlang::abort(...) + > ggplot(data = d0, + + mapping = aes(x = level, colour = reference, + + y = estimate, ymin = conf.low, ymax = conf.high)) + + + facet_row(facets = vars(variable), scales = "free_x", space = "free") + + + geom_hline(yintercept = 0, linetype = "dashed") + + + geom_pointrange() + + + theme(axis.text.x = element_text(angle = 45, hjust = 1)) + Error in space$x : $ operator is invalid for atomic vectors + Calls: ... -> draw_panels -> -> init_gtable + Execution halted + ``` + +* checking running R code from vignettes ... ERROR + ``` + Errors in running code in vignettes: + when running code in ‘intro.Rmd’ + ... + + > library(ggforce) + + > ggplot(data = d0, mapping = aes(x = level, y = estimate, + + colour = reference, ymin = conf.low, ymax = conf.high)) + + + facet_col(facets = .... [TRUNCATED] + + When sourcing ‘intro.R’: + Error: $ operator is invalid for atomic vectors Execution halted + + ‘intro.Rmd’ using ‘UTF-8’... failed + ``` + +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘intro.Rmd’ using rmarkdown ``` ## In both -* checking installed package size ... NOTE +* checking dependencies in R code ... NOTE ``` - installed size is 8.1Mb - sub-directories of 1Mb or more: - R 7.2Mb + Namespace in Imports field not imported from: ‘tidyr’ + All declared Imports should be used. ``` -# TreatmentPatterns +# tidyCDISC
-* Version: 2.6.7 -* GitHub: https://github.com/darwin-eu/TreatmentPatterns -* Source code: https://github.com/cran/TreatmentPatterns -* Date/Publication: 2024-05-24 08:30:32 UTC -* Number of recursive dependencies: 142 +* Version: 0.2.1 +* GitHub: https://github.com/Biogen-Inc/tidyCDISC +* Source code: https://github.com/cran/tidyCDISC +* Date/Publication: 2023-03-16 14:20:02 UTC +* Number of recursive dependencies: 140 -Run `revdepcheck::cloud_details(, "TreatmentPatterns")` for more info +Run `revdepcheck::cloud_details(, "tidyCDISC")` for more info
@@ -20669,386 +12701,211 @@ Run `revdepcheck::cloud_details(, "TreatmentPatterns")` for more info * checking tests ... ERROR ``` + Running ‘spelling.R’ Running ‘testthat.R’ Running the tests in ‘tests/testthat.R’ failed. Complete output: - > # This file is part of the standard setup for testthat. - > # It is recommended that you do not modify it. - > # - > # Where should you do additional test configuration? - > # Learn more about the roles of various files in: - > # * https://r-pkgs.org/tests.html - > # * https://testthat.r-lib.org/reference/test_package.html#special-files + > library(testthat) + > library(tidyCDISC) + > library(shinyjs) + + Attaching package: 'shinyjs' + ... - 22. ├─testthat::expect_s3_class(output$charAgePlot$html, "html") at test-CharacterizationPlots.R:47:9 - 23. │ └─testthat::quasi_label(enquo(object), arg = "object") - 24. │ └─rlang::eval_bare(expr, quo_get_env(quo)) - 25. ├─output$charAgePlot - 26. └─shiny:::`$.shinyoutput`(output, charAgePlot) - 27. └─.subset2(x, "impl")$getOutput(name) + 6. ├─plotly::config(...) + 7. │ └─plotly:::modify_list(p$x$config, args) + 8. │ ├─utils::modifyList(x %||% list(), y %||% list(), ...) + 9. │ │ └─base::stopifnot(is.list(x), is.list(val)) + 10. │ └─x %||% list() + 11. └─plotly::layout(...) - [ FAIL 1 | WARN 0 | SKIP 21 | PASS 134 ] + [ FAIL 1 | WARN 1 | SKIP 15 | PASS 91 ] Error: Test failures Execution halted ``` -# TreatmentSelection - -
- -* Version: 2.1.1 -* GitHub: NA -* Source code: https://github.com/cran/TreatmentSelection -* Date/Publication: 2017-08-11 18:55:47 UTC -* Number of recursive dependencies: 30 - -Run `revdepcheck::cloud_details(, "TreatmentSelection")` for more info - -
- -## Newly broken +## In both -* checking examples ... ERROR +* checking installed package size ... NOTE ``` - Running examples in ‘TreatmentSelection-Ex.R’ failed - The error most likely occurred in: - - > ### Name: plot.trtsel - > ### Title: plot risk curves, treatment effect curves or cdf of risk for a - > ### trtsel object. - > ### Aliases: plot.trtsel plot - > - > ### ** Examples - > - ... - 1. ├─base::plot(...) - 2. └─TreatmentSelection:::plot.trtsel(...) - 3. └─TreatmentSelection (local) tmp.plotfun(...) - 4. └─ggplot2::ggplotGrob((p)) - 5. ├─ggplot2::ggplot_gtable(ggplot_build(x)) - 6. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) - 7. └─ggplot2::calc_element("plot.margin", theme) - 8. └─cli::cli_abort(...) - 9. └─rlang::abort(...) - Execution halted + installed size is 6.5Mb + sub-directories of 1Mb or more: + R 1.5Mb + data 2.0Mb + doc 1.8Mb ``` -# TreeDep +# tidydr
-* Version: 0.1.3 -* GitHub: NA -* Source code: https://github.com/cran/TreeDep -* Date/Publication: 2018-12-02 17:50:03 UTC -* Number of recursive dependencies: 32 +* Version: 0.0.5 +* GitHub: https://github.com/YuLab-SMU/tidydr +* Source code: https://github.com/cran/tidydr +* Date/Publication: 2023-03-08 09:20:02 UTC +* Number of recursive dependencies: 74 -Run `revdepcheck::cloud_details(, "TreeDep")` for more info +Run `revdepcheck::cloud_details(, "tidydr")` for more info
## Newly broken -* checking examples ... ERROR +* checking whether package ‘tidydr’ can be installed ... ERROR ``` - Running examples in ‘TreeDep-Ex.R’ failed - The error most likely occurred in: - - > ### Name: TreeDep_plot - > ### Title: TreeDep_plot - Generates a plot for selected variables and - > ### dates. - > ### Aliases: TreeDep_plot - > - > ### ** Examples - > - ... - Backtrace: - ▆ - 1. ├─base (local) ``(x) - 2. └─ggplot2:::print.ggplot(x) - 3. ├─ggplot2::ggplot_gtable(data) - 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) - 5. └─ggplot2::calc_element("plot.margin", theme) - 6. └─cli::cli_abort(...) - 7. └─rlang::abort(...) - Execution halted + Installation failed. + See ‘/tmp/workdir/tidydr/new/tidydr.Rcheck/00install.out’ for details. ``` -# TreeDist - -
- -* Version: 2.7.0 -* GitHub: https://github.com/ms609/TreeDist -* Source code: https://github.com/cran/TreeDist -* Date/Publication: 2023-10-25 22:10:02 UTC -* Number of recursive dependencies: 230 - -Run `revdepcheck::cloud_details(, "TreeDist")` for more info +## Installation -
+### Devel -## Newly broken +``` +* installing *source* package ‘tidydr’ ... +** package ‘tidydr’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** inst +** byte-compile and prepare package for lazy loading +Error in get(x, envir = ns, inherits = FALSE) : + object 'len0_null' not found +Error: unable to load R code in package ‘tidydr’ +Execution halted +ERROR: lazy loading failed for package ‘tidydr’ +* removing ‘/tmp/workdir/tidydr/new/tidydr.Rcheck/tidydr’ -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘treespace.Rmd’ - ... - [1] "Epoch: 3 finished. 212 datapoints changed bestmatch" - [1] "Epoch: 4 started" - [1] "Epoch: 4 finished. 203 datapoints changed bestmatch" - [1] "Epoch: 5 started" - [1] "Epoch: 5 finished. 165 datapoints changed bestmatch" - [1] "---- Esom Training Finished ----" - - ... - - ‘Generalized-RF.Rmd’ using ‘UTF-8’... OK - ‘Robinson-Foulds.Rmd’ using ‘UTF-8’... OK - ‘Using-TreeDist.Rmd’ using ‘UTF-8’... OK - ‘compare-treesets.Rmd’ using ‘UTF-8’... OK - ‘different-leaves.Rmd’ using ‘UTF-8’... OK - ‘information.Rmd’ using ‘UTF-8’... OK - ‘landscapes.Rmd’ using ‘UTF-8’... OK - ‘treespace.Rmd’ using ‘UTF-8’... failed - ‘using-distances.Rmd’ using ‘UTF-8’... OK - ``` -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘Generalized-RF.Rmd’ using rmarkdown - ``` +``` +### CRAN -## In both +``` +* installing *source* package ‘tidydr’ ... +** package ‘tidydr’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** inst +** byte-compile and prepare package for lazy loading +** help +*** installing help indices +** building package indices +** installing vignettes +** testing if installed package can be loaded from temporary location +** testing if installed package can be loaded from final location +** testing if installed package keeps a record of temporary installation path +* DONE (tidydr) -* checking installed package size ... NOTE - ``` - installed size is 9.2Mb - sub-directories of 1Mb or more: - doc 5.0Mb - libs 3.6Mb - ``` -# treeheatr +``` +# tidysdm
-* Version: 0.2.1 -* GitHub: https://github.com/trang1618/treeheatr -* Source code: https://github.com/cran/treeheatr -* Date/Publication: 2020-11-19 21:00:03 UTC -* Number of recursive dependencies: 97 +* Version: 0.9.5 +* GitHub: https://github.com/EvolEcolGroup/tidysdm +* Source code: https://github.com/cran/tidysdm +* Date/Publication: 2024-06-23 19:40:02 UTC +* Number of recursive dependencies: 179 -Run `revdepcheck::cloud_details(, "treeheatr")` for more info +Run `revdepcheck::cloud_details(, "tidysdm")` for more info
## Newly broken -* checking examples ... ERROR - ``` - Running examples in ‘treeheatr-Ex.R’ failed - The error most likely occurred in: - - > ### Name: draw_heat - > ### Title: Draws the heatmap. - > ### Aliases: draw_heat - > - > ### ** Examples - > - > x <- compute_tree(penguins, target_lab = 'species') - ... - Backtrace: - ▆ - 1. ├─base (local) ``(x) - 2. └─ggplot2:::print.ggplot(x) - 3. ├─ggplot2::ggplot_gtable(data) - 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) - 5. └─ggplot2::calc_element("plot.margin", theme) - 6. └─cli::cli_abort(...) - 7. └─rlang::abort(...) - Execution halted - ``` - * checking running R code from vignettes ... ERROR ``` Errors in running code in vignettes: - when running code in ‘explore.Rmd’ - ... - Please report the issue at . - Warning: The `guide` argument in `scale_*()` cannot be `FALSE`. This was deprecated in - ggplot2 3.3.4. - ℹ Please use "none" instead. - ℹ The deprecated feature was likely used in the treeheatr package. - Please report the issue at . - - When sourcing ‘explore.R’: - Error: Theme element `plot.margin` must have class . - Execution halted - - ‘explore.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: + when running code in ‘a0_tidysdm_overview.Rmd’ ... - --- re-building ‘explore.Rmd’ using rmarkdown + > climate_vars <- names(climate_present) - Quitting from lines 33-36 [unnamed-chunk-2] (explore.Rmd) - Error: processing vignette 'explore.Rmd' failed with diagnostics: - Theme element `plot.margin` must have class . - --- failed re-building ‘explore.Rmd’ + > lacerta_thin <- lacerta_thin %>% bind_cols(terra::extract(climate_present, + + lacerta_thin, ID = FALSE)) - SUMMARY: processing the following file failed: - ‘explore.Rmd’ + > lacerta_thin %>% plot_pres_vs_bg(class) - Error: Vignette re-building failed. + When sourcing ‘a0_tidysdm_overview.R’: + Error: object is not a unit Execution halted + + ‘a0_tidysdm_overview.Rmd’ using ‘UTF-8’... failed + ‘a1_palaeodata_application.Rmd’ using ‘UTF-8’... OK + ‘a2_tidymodels_additions.Rmd’ using ‘UTF-8’... OK + ‘a3_troubleshooting.Rmd’ using ‘UTF-8’... OK ``` -# trelliscopejs - -
- -* Version: 0.2.6 -* GitHub: https://github.com/hafen/trelliscopejs -* Source code: https://github.com/cran/trelliscopejs -* Date/Publication: 2021-02-01 08:00:02 UTC -* Number of recursive dependencies: 106 - -Run `revdepcheck::cloud_details(, "trelliscopejs")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘trelliscopejs-Ex.R’ failed - The error most likely occurred in: - - > ### Name: cog - > ### Title: Cast Column as a Cognostic - > ### Aliases: cog - > - > ### ** Examples - > - > library(dplyr) - ... - 8. ├─base::tryCatch(...) - 9. │ └─base (local) tryCatchList(expr, classes, parentenv, handlers) - 10. ├─base::print(p) - 11. └─ggplot2:::print.ggplot(p) - 12. ├─ggplot2::ggplot_gtable(data) - 13. └─ggplot2:::ggplot_gtable.ggplot_built(data) - 14. └─ggplot2::calc_element("plot.margin", theme) - 15. └─cli::cli_abort(...) - 16. └─rlang::abort(...) - Execution halted +* checking re-building of vignette outputs ... NOTE + ``` + Error(s) in re-building vignettes: + --- re-building ‘a0_tidysdm_overview.Rmd’ using rmarkdown ``` -* checking tests ... ERROR +## In both + +* checking installed package size ... NOTE ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(trelliscopejs) - > - > test_check("trelliscopejs") - [ FAIL 1 | WARN 0 | SKIP 0 | PASS 0 ] - - ══ Failed tests ════════════════════════════════════════════════════════════════ - ... - 12. └─ggplot2:::print.ggplot(p) - 13. ├─ggplot2::ggplot_gtable(data) - 14. └─ggplot2:::ggplot_gtable.ggplot_built(data) - 15. └─ggplot2::calc_element("plot.margin", theme) - 16. └─cli::cli_abort(...) - 17. └─rlang::abort(...) - - [ FAIL 1 | WARN 0 | SKIP 0 | PASS 0 ] - Error: Test failures - Execution halted + installed size is 5.4Mb + sub-directories of 1Mb or more: + data 2.5Mb + doc 2.0Mb ``` -# tricolore +# tidytreatment
-* Version: 1.2.4 -* GitHub: https://github.com/jschoeley/tricolore -* Source code: https://github.com/cran/tricolore -* Date/Publication: 2024-05-15 15:00:02 UTC -* Number of recursive dependencies: 108 +* Version: 0.2.2 +* GitHub: https://github.com/bonStats/tidytreatment +* Source code: https://github.com/cran/tidytreatment +* Date/Publication: 2022-02-21 09:00:07 UTC +* Number of recursive dependencies: 97 -Run `revdepcheck::cloud_details(, "tricolore")` for more info +Run `revdepcheck::cloud_details(, "tidytreatment")` for more info
## Newly broken -* checking examples ... ERROR - ``` - Running examples in ‘tricolore-Ex.R’ failed - The error most likely occurred in: - - > ### Name: ColorKeySextant - > ### Title: Sextant Scheme Legend - > ### Aliases: ColorKeySextant - > ### Keywords: internal - > - > ### ** Examples - > - ... - 3. ├─ggtern::ggplot_build(x) - 4. └─ggtern:::ggplot_build.ggplot(x) - 5. └─ggtern:::layers_add_or_remove_mask(plot) - 6. └─ggint$plot_theme(plot) - 7. └─ggplot2:::validate_theme(theme) - 8. └─base::mapply(...) - 9. └─ggplot2 (local) ``(...) - 10. └─cli::cli_abort(...) - 11. └─rlang::abort(...) - Execution halted - ``` - * checking running R code from vignettes ... ERROR ``` Errors in running code in vignettes: - when running code in ‘choropleth_maps_with_tricolore.Rmd’ + when running code in ‘use-tidytreatment-BART.Rmd’ ... + + by = ".row") %>% ggplot() + stat_halfeye(aes(x = z, y = fit)) + + + facet_wrap(~c1, l .... [TRUNCATED] - > plot_educ <- ggplot(euro_example) + geom_sf(aes(fill = rgb, - + geometry = geometry), size = 0.1) + scale_fill_identity() - - > plot_educ - - When sourcing ‘choropleth_maps_with_tricolore.R’: - Error: The `tern.axis.ticks.length.major` theme element must be a - object. + When sourcing ‘use-tidytreatment-BART.R’: + Error: Problem while setting up geom aesthetics. + ℹ Error occurred in the 1st layer. + Caused by error in `use_defaults()`: + ! unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, "black", TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), list(NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), 5.5, c(5.5, 5.5, 5.5, 5.5), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.75, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, + NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, 90, NULL, c(0, 2.75, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL Execution halted - ‘choropleth_maps_with_tricolore.Rmd’ using ‘UTF-8’... failed + ‘use-tidytreatment-BART.Rmd’ using ‘UTF-8’... failed ``` * checking re-building of vignette outputs ... NOTE ``` Error(s) in re-building vignettes: ... - --- re-building ‘choropleth_maps_with_tricolore.Rmd’ using rmarkdown + --- re-building ‘use-tidytreatment-BART.Rmd’ using rmarkdown - Quitting from lines 61-72 [unnamed-chunk-4] (choropleth_maps_with_tricolore.Rmd) - Error: processing vignette 'choropleth_maps_with_tricolore.Rmd' failed with diagnostics: - The `tern.axis.ticks.length.major` theme element must be a - object. - --- failed re-building ‘choropleth_maps_with_tricolore.Rmd’ + Quitting from lines 163-177 [plot-tidy-bart] (use-tidytreatment-BART.Rmd) + Error: processing vignette 'use-tidytreatment-BART.Rmd' failed with diagnostics: + Problem while setting up geom aesthetics. + ℹ Error occurred in the 1st layer. + Caused by error in `use_defaults()`: + ! unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, "black", TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), list(NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), 5.5, c(5.5, 5.5, 5.5, 5.5), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.75, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, + ... + NULL, NULL, NULL, list(NULL, NA, NULL, NULL, TRUE), NULL, 2, NULL, NULL, NULL, 1.2, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 0.2, NULL, list(NULL, NULL, NULL, 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, NULL, NULL, NULL, TRUE), NULL, "right", NULL, NULL, NULL, "center", NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 0, list(), 2, list("white", NA, NULL, NULL, TRUE), list(NULL, "grey20", NULL, NULL, TRUE), NULL, NULL, NULL, list("grey92", + NULL, NULL, NULL, FALSE, "grey92", TRUE), NULL, list(NULL, 0.5, NULL, NULL, FALSE, NULL, TRUE), NULL, NULL, NULL, NULL, FALSE, list(NULL, "white", NULL, NULL, TRUE), list(NULL, NULL, NULL, 1.2, 0, 1, NULL, NULL, c(0, 0, 5.5, 0), NULL, TRUE), "panel", list(NULL, NULL, NULL, NULL, 0, 1, NULL, NULL, c(0, 0, 5.5, 0), NULL, TRUE), list(NULL, NULL, NULL, 0.8, 1, 1, NULL, NULL, c(5.5, 0, 0, 0), NULL, TRUE), "panel", list(NULL, NULL, NULL, 1.2, 0.5, 0.5, NULL, NULL, NULL, NULL, TRUE), "topleft", + NULL, NULL, list("grey85", "grey20", NULL, NULL, TRUE), NULL, NULL, "inherit", "inside", list(NULL, NULL, "grey10", 0.8, NULL, NULL, NULL, NULL, c(4.4, 4.4, 4.4, 4.4), NULL, TRUE), NULL, NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, NULL, -90, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, NULL, 90, NULL, NULL, NULL, TRUE), NULL, 2.75, 2.75)) + --- failed re-building ‘use-tidytreatment-BART.Rmd’ SUMMARY: processing the following file failed: - ‘choropleth_maps_with_tricolore.Rmd’ + ‘use-tidytreatment-BART.Rmd’ Error: Vignette re-building failed. Execution halted @@ -21056,22 +12913,22 @@ Run `revdepcheck::cloud_details(, "tricolore")` for more info ## In both -* checking data for non-ASCII characters ... NOTE +* checking package dependencies ... NOTE ``` - Note: found 2 marked UTF-8 strings + Package which this enhances but not available for checking: ‘bartMachine’ ``` -# tsnet +# timetk
-* Version: 0.1.0 -* GitHub: https://github.com/bsiepe/tsnet -* Source code: https://github.com/cran/tsnet -* Date/Publication: 2024-02-28 11:30:02 UTC -* Number of recursive dependencies: 77 +* Version: 2.9.0 +* GitHub: https://github.com/business-science/timetk +* Source code: https://github.com/cran/timetk +* Date/Publication: 2023-10-31 22:30:02 UTC +* Number of recursive dependencies: 225 -Run `revdepcheck::cloud_details(, "tsnet")` for more info +Run `revdepcheck::cloud_details(, "timetk")` for more info
@@ -21087,46 +12944,39 @@ Run `revdepcheck::cloud_details(, "tsnet")` for more info > # > # Where should you do additional test configuration? > # Learn more about the roles of various files in: - > # * https://r-pkgs.org/tests.html - > # * https://testthat.r-lib.org/reference/test_package.html#special-files + > # * https://r-pkgs.org/testing-design.html#sec-tests-files-overview + > # * https://testthat.r-lib.org/articles/special-files.html ... - unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, "black", TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), NULL, list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), 5.5, c(5.5, 5.5, 5.5, 5.5), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(7, 0, 0, 0), NULL, FALSE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, - NULL, NULL, 1, 90, NULL, c(0, 7, 0, 0), NULL, FALSE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 1, NULL, NULL, NULL, c(0, 2.2, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0, - NULL, NULL, NULL, c(0, 0, 0, 2.2), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0.5, NULL, NULL, NULL, c(0, 2.2, 0, 2.2), NULL, TRUE), list("grey70", 0.5, NULL, NULL, FALSE, "grey70", TRUE), NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 0.5, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 0.75, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, list(), list("gray70", 0.5, NULL, NULL, FALSE, "gray70", FALSE), NULL, NULL, list("gray70", 0.5, NULL, NULL, FALSE, - "gray70", FALSE), NULL, NULL, NULL, NULL, list(NULL, NA, NULL, NULL, TRUE), NULL, 2, NULL, NULL, NULL, 1.2, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 0.2, NULL, list(NULL, NULL, NULL, 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, NULL, NULL, NULL, TRUE), NULL, "right", NULL, NULL, NULL, "center", NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 0, list(), 2, list("white", NA, NULL, NULL, TRUE), list(), NULL, NULL, NULL, list("grey87", NULL, NULL, - NULL, FALSE, "grey87", TRUE), list(), list(), NULL, NULL, NULL, NULL, FALSE, list(NULL, "white", NULL, NULL, TRUE), list(NULL, NULL, NULL, 1.2, 0, 1, NULL, NULL, c(0, 0, 5.5, 0), NULL, TRUE), "panel", list(NULL, NULL, NULL, NULL, 0, 1, NULL, NULL, c(0, 0, 5.5, 0), NULL, TRUE), list(NULL, NULL, NULL, 0.8, 1, 1, NULL, NULL, c(5.5, 0, 0, 0), NULL, TRUE), "panel", list(NULL, NULL, NULL, 1.2, 0.5, 0.5, NULL, NULL, NULL, NULL, TRUE), "topleft", NULL, NULL, list("gray90", NA, NULL, NULL, FALSE), NULL, - NULL, "inherit", "inside", list(NULL, NULL, "black", 0.8, NULL, NULL, NULL, NULL, c(6, 6, 6, 6), NULL, FALSE), NULL, NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, NULL, -90, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, NULL, 90, NULL, NULL, NULL, TRUE), NULL, 2.75, 2.75)) + 7. └─timetk:::plot_time_series.grouped_df(...) + 8. ├─timetk::plot_time_series(...) + 9. └─timetk:::plot_time_series.data.frame(...) + 10. ├─plotly::ggplotly(g, dynamicTicks = TRUE) + 11. └─plotly:::ggplotly.ggplot(g, dynamicTicks = TRUE) + 12. └─plotly::gg2list(...) - [ FAIL 1 | WARN 14 | SKIP 0 | PASS 108 ] + [ FAIL 1 | WARN 0 | SKIP 0 | PASS 406 ] Error: Test failures Execution halted ``` ## In both -* checking installed package size ... NOTE - ``` - installed size is 163.0Mb - sub-directories of 1Mb or more: - libs 162.0Mb - ``` - -* checking for GNU extensions in Makefiles ... NOTE +* checking data for non-ASCII characters ... NOTE ``` - GNU make is a SystemRequirements. + Note: found 2750 marked UTF-8 strings ``` -# umiAnalyzer +# tinyarray
-* Version: 1.0.0 -* GitHub: https://github.com/sfilges/umiAnalyzer -* Source code: https://github.com/cran/umiAnalyzer -* Date/Publication: 2021-11-25 08:40:02 UTC -* Number of recursive dependencies: 116 +* Version: 2.4.2 +* GitHub: https://github.com/xjsun1221/tinyarray +* Source code: https://github.com/cran/tinyarray +* Date/Publication: 2024-06-13 14:20:02 UTC +* Number of recursive dependencies: 244 -Run `revdepcheck::cloud_details(, "umiAnalyzer")` for more info +Run `revdepcheck::cloud_details(, "tinyarray")` for more info
@@ -21134,40 +12984,33 @@ Run `revdepcheck::cloud_details(, "umiAnalyzer")` for more info * checking examples ... ERROR ``` - Running examples in ‘umiAnalyzer-Ex.R’ failed + Running examples in ‘tinyarray-Ex.R’ failed The error most likely occurred in: - > ### Name: AmpliconPlot - > ### Title: Generate Amplicon plots - > ### Aliases: AmpliconPlot + > ### Name: exp_surv + > ### Title: exp_surv + > ### Aliases: exp_surv > > ### ** Examples > - > library(umiAnalyzer) - ... - > - > main = system.file('extdata', package = 'umiAnalyzer') - > samples <- list.dirs(path = main, full.names = FALSE, recursive = FALSE) - > simsen <- createUmiExperiment(experimentName = 'example',mainDir = main,sampleNames = samples) - > simsen <- filterUmiObject(simsen) - > - > amplicon_plot <- AmpliconPlot(simsen) - Error in pm[[2]] : subscript out of bounds - Calls: AmpliconPlot -> -> ggplotly.ggplot -> gg2list + > tmp = exp_surv(exprSet_hub1,meta1) + > patchwork::wrap_plots(tmp)+patchwork::plot_layout(guides = "collect") + Error in identicalUnits(x) : object is not a unit + Calls: ... assemble_guides -> guides_build -> unit.c -> identicalUnits Execution halted ``` -# UnalR +# tornado
-* Version: 1.0.0 -* GitHub: https://github.com/estadisticaun/UnalR -* Source code: https://github.com/cran/UnalR -* Date/Publication: 2024-05-25 17:20:05 UTC -* Number of recursive dependencies: 168 +* Version: 0.1.3 +* GitHub: https://github.com/bertcarnell/tornado +* Source code: https://github.com/cran/tornado +* Date/Publication: 2024-01-21 17:30:02 UTC +* Number of recursive dependencies: 114 -Run `revdepcheck::cloud_details(, "UnalR")` for more info +Run `revdepcheck::cloud_details(, "tornado")` for more info
@@ -21175,56 +13018,90 @@ Run `revdepcheck::cloud_details(, "UnalR")` for more info * checking examples ... ERROR ``` - Running examples in ‘UnalR-Ex.R’ failed + Running examples in ‘tornado-Ex.R’ failed The error most likely occurred in: - > ### Name: Plot.Barras - > ### Title: Cree un gráfico de barras que muestre la información de forma - > ### horizontal o vertical, para variables nominales u ordinales con dos - > ### diferentes paquetes - > ### Aliases: Plot.Barras + > ### Name: plot.tornado_plot + > ### Title: Plot a Tornado Plot object + > ### Aliases: plot.tornado_plot > > ### ** Examples + > + > gtest <- lm(mpg ~ cyl*wt*hp, data = mtcars) ... - 1. └─(if (getRversion() >= "3.4") withAutoprint else force)(...) - 2. └─base::source(...) - 3. ├─base::print(yy$value) - 4. └─ggplot2:::print.ggplot(yy$value) - 5. ├─ggplot2::ggplot_gtable(data) - 6. └─ggplot2:::ggplot_gtable.ggplot_built(data) - 7. └─ggplot2::calc_element("plot.margin", theme) - 8. └─cli::cli_abort(...) - 9. └─rlang::abort(...) + 13. │ └─base::withCallingHandlers(...) + 14. └─ggplot2 (local) f(l = layers[[i]], d = data[[i]]) + 15. └─l$compute_geom_2(d, theme = plot$theme) + 16. └─ggplot2 (local) compute_geom_2(..., self = self) + 17. └─self$geom$use_defaults(...) + 18. └─ggplot2 (local) use_defaults(..., self = self) + 19. └─ggplot2:::check_aesthetics(new_params, nrow(data)) + 20. └─cli::cli_abort(...) + 21. └─rlang::abort(...) Execution halted ``` -## In both +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > if (require(testthat)) + + { + + library(tornado) + + + + test_check("tornado") + + } + Loading required package: testthat + ... + ...)) + })(position = "identity", stat = "identity", width = NULL)`: Problem while setting up geom aesthetics. + ℹ Error occurred in the 1st layer. + Caused by error in `check_aesthetics()`: + ! Aesthetics must be either length 1 or the same as the data (20). + ✖ Fix the following mappings: `width`. + + [ FAIL 14 | WARN 0 | SKIP 0 | PASS 101 ] + Error: Test failures + Execution halted + ``` -* checking installed package size ... NOTE +* checking running R code from vignettes ... ERROR ``` - installed size is 7.0Mb - sub-directories of 1Mb or more: - R 2.3Mb - data 2.0Mb - help 2.6Mb + Errors in running code in vignettes: + when running code in ‘tornadoVignette.Rmd’ + ... + + .... [TRUNCATED] + Loading required package: lattice + + When sourcing ‘tornadoVignette.R’: + Error: Problem while setting up geom aesthetics. + ℹ Error occurred in the 1st layer. + Caused by error in `check_aesthetics()`: + ! Aesthetics must be either length 1 or the same as the data (20). + ✖ Fix the following mappings: `width`. + Execution halted + + ‘tornadoVignette.Rmd’ using ‘UTF-8’... failed ``` -* checking data for non-ASCII characters ... NOTE +* checking re-building of vignette outputs ... NOTE ``` - Note: found 312859 marked UTF-8 strings + Error(s) in re-building vignettes: + --- re-building ‘tornadoVignette.Rmd’ using rmarkdown ``` -# UpSetR +# TOSTER
-* Version: 1.4.0 -* GitHub: https://github.com/hms-dbmi/UpSetR -* Source code: https://github.com/cran/UpSetR -* Date/Publication: 2019-05-22 23:30:03 UTC -* Number of recursive dependencies: 36 +* Version: 0.8.3 +* GitHub: NA +* Source code: https://github.com/cran/TOSTER +* Date/Publication: 2024-05-08 16:40:02 UTC +* Number of recursive dependencies: 106 -Run `revdepcheck::cloud_details(, "UpSetR")` for more info +Run `revdepcheck::cloud_details(, "TOSTER")` for more info
@@ -21232,195 +13109,178 @@ Run `revdepcheck::cloud_details(, "UpSetR")` for more info * checking examples ... ERROR ``` - Running examples in ‘UpSetR-Ex.R’ failed + Running examples in ‘TOSTER-Ex.R’ failed The error most likely occurred in: - > ### Name: upset - > ### Title: UpSetR Plot - > ### Aliases: upset + > ### Name: dataTOSTone + > ### Title: TOST One Sample T-Test + > ### Aliases: dataTOSTone > > ### ** Examples > - > movies <- read.csv( system.file("extdata", "movies.csv", package = "UpSetR"), header=TRUE, sep=";" ) + > library("TOSTER") ... - 2. ├─base::suppressMessages(...) - 3. │ └─base::withCallingHandlers(...) - 4. └─UpSetR:::Make_main_bar(...) - 5. └─ggplot2::ggplotGrob(Main_bar_plot) - 6. ├─ggplot2::ggplot_gtable(ggplot_build(x)) - 7. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) - 8. └─ggplot2::calc_element("plot.margin", theme) - 9. └─cli::cli_abort(...) - 10. └─rlang::abort(...) + N Mean Median SD SE + ───────────────────────────────────────────────────────────────────────── + Sepal.Width 150 3.057333 3.000000 0.4358663 0.03558833 + ───────────────────────────────────────────────────────────────────────── + + Error in use_defaults(..., self = self) : + unused argument (theme = list(list("black", 0.727272727272727, 1, "butt", FALSE, "black", TRUE), list("white", "black", 0.727272727272727, 1, TRUE), list("", "plain", "black", 16, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), list(NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list("black", "white", "#3366FF", 0.727272727272727, 1.45454545454545, "", 5.62335685623357, 2.18181818181818, 19, TRUE), 8, c(8, 8, 8, 8), NULL, NULL, list(NULL, NULL, "#333333", NULL, NULL, NULL, NULL, NULL, + c(10, 0, 0, 0), NULL, FALSE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 4, 0), NULL, TRUE), NULL, list(NULL, NULL, "#333333", NULL, NULL, NULL, 90, NULL, c(0, 10, 0, 0), NULL, FALSE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 4), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, "#333333", NULL, NULL, NULL, NULL, NULL, c(5, 0, 0, 0), NULL, FALSE), list(NULL, NULL, NULL, NULL, NUL + Calls: ... -> -> -> Execution halted ``` +* checking tests ... ERROR + ``` + Running ‘spelling.R’ + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > library(testthat) + > library(TOSTER) + + Attaching package: 'TOSTER' + + The following object is masked from 'package:testthat': + ... + 26. └─base::Map(...) + 27. └─base::mapply(FUN = f, ..., SIMPLIFY = FALSE) + 28. └─ggplot2 (local) ``(layer = dots[[1L]][[1L]], df = dots[[2L]][[1L]]) + 29. └─layer$compute_geom_2(key, single_params, theme) + 30. └─ggplot2 (local) compute_geom_2(..., self = self) + 31. └─self$geom$use_defaults(...) + + [ FAIL 8 | WARN 0 | SKIP 0 | PASS 1034 ] + Error: Test failures + Execution halted + ``` + * checking running R code from vignettes ... ERROR ``` Errors in running code in vignettes: - when running code in ‘attribute.plots.Rmd’ + when running code in ‘IntroTOSTt.Rmd’ ... + mean of x mean of y + 0.75 2.33 - > movies <- read.csv(system.file("extdata", "movies.csv", - + package = "UpSetR"), header = T, sep = ";") - > upset(movies, main.bar.color = "black", queries = list(list(query = intersects, - + params = list("Drama"), active = T)), attribute.plots = list( .... [TRUNCATED] + > plot(res1, type = "cd") + When sourcing ‘IntroTOSTt.R’: ... - + assign = 20 .... [TRUNCATED] - - When sourcing ‘set.metadata.plots.R’: - Error: Theme element `plot.margin` must have class . + Error: unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, "black", TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), list(NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), 5.5, c(5.5, 5.5, 5.5, 5.5), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(7, 0, 0, 0), NULL, FALSE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, + NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, 90, NULL, c(0, 7, 0, 0), NULL, FALSE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, "bold", NULL, 11, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, FALSE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(), NULL, list(NULL, N Execution halted - ‘attribute.plots.Rmd’ using ‘UTF-8’... failed - ‘basic.usage.Rmd’ using ‘UTF-8’... failed - ‘queries.Rmd’ using ‘UTF-8’... failed - ‘set.metadata.plots.Rmd’ using ‘UTF-8’... failed - ``` - -## In both - -* checking installed package size ... NOTE - ``` - installed size is 8.1Mb - sub-directories of 1Mb or more: - doc 7.6Mb + ‘IntroTOSTt.Rmd’ using ‘UTF-8’... failed + ‘IntroductionToTOSTER.Rmd’ using ‘UTF-8’... OK + ‘SMD_calcs.Rmd’ using ‘UTF-8’... OK + ‘correlations.Rmd’ using ‘UTF-8’... OK + ‘robustTOST.Rmd’ using ‘UTF-8’... failed + ‘the_ftestTOSTER.Rmd’ using ‘UTF-8’... OK ``` -* checking LazyData ... NOTE +* checking re-building of vignette outputs ... NOTE ``` - 'LazyData' is specified without a 'data' directory + Error(s) in re-building vignettes: + --- re-building ‘IntroTOSTt.Rmd’ using rmarkdown ``` -# vDiveR +# TreatmentPatterns
-* Version: 1.2.1 -* GitHub: NA -* Source code: https://github.com/cran/vDiveR -* Date/Publication: 2024-01-09 20:20:02 UTC -* Number of recursive dependencies: 131 +* Version: 2.6.7 +* GitHub: https://github.com/darwin-eu/TreatmentPatterns +* Source code: https://github.com/cran/TreatmentPatterns +* Date/Publication: 2024-05-24 08:30:32 UTC +* Number of recursive dependencies: 142 -Run `revdepcheck::cloud_details(, "vDiveR")` for more info +Run `revdepcheck::cloud_details(, "TreatmentPatterns")` for more info
## Newly broken -* checking examples ... ERROR +* checking tests ... ERROR ``` - Running examples in ‘vDiveR-Ex.R’ failed - The error most likely occurred in: - - > ### Name: plot_conservationLevel - > ### Title: Conservation Levels Distribution Plot - > ### Aliases: plot_conservationLevel - > - > ### ** Examples - > - > plot_conservationLevel(proteins_1host, conservation_label = 1,alpha=0.8, base_size = 15) + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > # This file is part of the standard setup for testthat. + > # It is recommended that you do not modify it. + > # + > # Where should you do additional test configuration? + > # Learn more about the roles of various files in: + > # * https://r-pkgs.org/tests.html + > # * https://testthat.r-lib.org/reference/test_package.html#special-files ... - Backtrace: - ▆ - 1. ├─base (local) ``(x) - 2. └─ggplot2:::print.ggplot(x) - 3. ├─ggplot2::ggplot_gtable(data) - 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) - 5. └─ggplot2::calc_element("plot.margin", theme) - 6. └─cli::cli_abort(...) - 7. └─rlang::abort(...) - Execution halted - ``` - -## In both - -* checking dependencies in R code ... NOTE - ``` - Namespaces in Imports field not imported from: - ‘DT’ ‘maps’ ‘readr’ - All declared Imports should be used. + 22. ├─testthat::expect_s3_class(output$charAgePlot$html, "html") at test-CharacterizationPlots.R:47:9 + 23. │ └─testthat::quasi_label(enquo(object), arg = "object") + 24. │ └─rlang::eval_bare(expr, quo_get_env(quo)) + 25. ├─output$charAgePlot + 26. └─shiny:::`$.shinyoutput`(output, charAgePlot) + 27. └─.subset2(x, "impl")$getOutput(name) + + [ FAIL 1 | WARN 0 | SKIP 21 | PASS 134 ] + Error: Test failures + Execution halted ``` -# VDSM +# trelliscopejs
-* Version: 0.1.1 -* GitHub: NA -* Source code: https://github.com/cran/VDSM -* Date/Publication: 2021-04-16 09:00:02 UTC -* Number of recursive dependencies: 57 +* Version: 0.2.6 +* GitHub: https://github.com/hafen/trelliscopejs +* Source code: https://github.com/cran/trelliscopejs +* Date/Publication: 2021-02-01 08:00:02 UTC +* Number of recursive dependencies: 106 -Run `revdepcheck::cloud_details(, "VDSM")` for more info +Run `revdepcheck::cloud_details(, "trelliscopejs")` for more info
## Newly broken -* checking examples ... ERROR - ``` - Running examples in ‘VDSM-Ex.R’ failed - The error most likely occurred in: - - > ### Name: Gplot - > ### Title: Gplot. - > ### Aliases: Gplot - > - > ### ** Examples - > - > data(exampleX) - ... - ▆ - 1. └─VDSM::Gplot(X, f, p) - 2. ├─base::suppressWarnings(ggplot_gtable(ggplot_build(p1.common.y))) - 3. │ └─base::withCallingHandlers(...) - 4. ├─ggplot2::ggplot_gtable(ggplot_build(p1.common.y)) - 5. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(p1.common.y)) - 6. └─ggplot2::calc_element("plot.margin", theme) - 7. └─cli::cli_abort(...) - 8. └─rlang::abort(...) - Execution halted - ``` - * checking tests ... ERROR ``` Running ‘testthat.R’ Running the tests in ‘tests/testthat.R’ failed. Complete output: > library(testthat) - > library(VDSM) + > library(trelliscopejs) > - > test_check("VDSM") - [ FAIL 1 | WARN 1 | SKIP 0 | PASS 0 ] + > test_check("trelliscopejs") + [ FAIL 1 | WARN 2 | SKIP 0 | PASS 0 ] ══ Failed tests ════════════════════════════════════════════════════════════════ ... - 3. │ └─base::withCallingHandlers(...) - 4. ├─ggplot2::ggplot_gtable(ggplot_build(p1.common.y)) - 5. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(p1.common.y)) - 6. └─ggplot2::calc_element("plot.margin", theme) - 7. └─cli::cli_abort(...) - 8. └─rlang::abort(...) + 4. └─base::lapply(...) + 5. └─trelliscopejs (local) FUN(X[[i]], ...) + 6. ├─base::do.call(plotly::ggplotly, c(list(p = q), plotly_args)) + 7. ├─plotly (local) ``(p = ``) + 8. └─plotly:::ggplotly.ggplot(p = ``) + 9. └─plotly::gg2list(...) - [ FAIL 1 | WARN 1 | SKIP 0 | PASS 0 ] + [ FAIL 1 | WARN 2 | SKIP 0 | PASS 0 ] Error: Test failures Execution halted ``` -# virtualPollen +# tricolore
-* Version: 1.0.1 -* GitHub: https://github.com/BlasBenito/virtualPollen -* Source code: https://github.com/cran/virtualPollen -* Date/Publication: 2022-02-13 13:00:02 UTC -* Number of recursive dependencies: 122 +* Version: 1.2.4 +* GitHub: https://github.com/jschoeley/tricolore +* Source code: https://github.com/cran/tricolore +* Date/Publication: 2024-05-15 15:00:02 UTC +* Number of recursive dependencies: 108 -Run `revdepcheck::cloud_details(, "virtualPollen")` for more info +Run `revdepcheck::cloud_details(, "tricolore")` for more info
@@ -21428,65 +13288,85 @@ Run `revdepcheck::cloud_details(, "virtualPollen")` for more info * checking examples ... ERROR ``` - Running examples in ‘virtualPollen-Ex.R’ failed + Running examples in ‘tricolore-Ex.R’ failed The error most likely occurred in: - > ### Name: simulateDriverS - > ### Title: Generates drivers for 'simulatePopulation'. - > ### Aliases: simulateDriverS + > ### Name: ColorKeySextant + > ### Title: Sextant Scheme Legend + > ### Aliases: ColorKeySextant + > ### Keywords: internal > > ### ** Examples > - > ... - 8. └─cowplot:::as_gtable.default(x) - 9. ├─cowplot::as_grob(plot) - 10. └─cowplot:::as_grob.ggplot(plot) - 11. └─ggplot2::ggplotGrob(plot) - 12. ├─ggplot2::ggplot_gtable(ggplot_build(x)) - 13. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) - 14. └─ggplot2::calc_element("plot.margin", theme) - 15. └─cli::cli_abort(...) - 16. └─rlang::abort(...) + 3. ├─ggtern::ggplot_build(x) + 4. └─ggtern:::ggplot_build.ggplot(x) + 5. └─ggtern:::layers_add_or_remove_mask(plot) + 6. └─ggint$plot_theme(plot) + 7. └─ggplot2:::validate_theme(theme) + 8. └─base::mapply(...) + 9. └─ggplot2 (local) ``(...) + 10. └─cli::cli_abort(...) + 11. └─rlang::abort(...) Execution halted ``` * checking running R code from vignettes ... ERROR ``` Errors in running code in vignettes: - when running code in ‘using_virtualPollen.Rmd’ + when running code in ‘choropleth_maps_with_tricolore.Rmd’ ... - > p7 <- ggplot(data = acfToDf(moves.100, 200, 50), aes(x = lag, - + y = acf)) + geom_hline(aes(yintercept = 0)) + geom_hline(aes(yintercept = ci.ma .... [TRUNCATED] + > plot_educ <- ggplot(euro_example) + geom_sf(aes(fill = rgb, + + geometry = geometry), size = 0.1) + scale_fill_identity() - > plot_grid(p4, p5, p6, p7, labels = c("a", "b", "c", - + "d"), align = "v", nrow = 2) + > plot_educ - When sourcing ‘using_virtualPollen.R’: - Error: Theme element `plot.margin` must have class . + When sourcing ‘choropleth_maps_with_tricolore.R’: + Error: The `tern.axis.ticks.length.major` theme element must be a + object. Execution halted - ‘using_virtualPollen.Rmd’ using ‘UTF-8’... failed + ‘choropleth_maps_with_tricolore.Rmd’ using ‘UTF-8’... failed ``` * checking re-building of vignette outputs ... NOTE ``` Error(s) in re-building vignettes: - --- re-building ‘using_virtualPollen.Rmd’ using rmarkdown + ... + --- re-building ‘choropleth_maps_with_tricolore.Rmd’ using rmarkdown + + Quitting from lines 61-72 [unnamed-chunk-4] (choropleth_maps_with_tricolore.Rmd) + Error: processing vignette 'choropleth_maps_with_tricolore.Rmd' failed with diagnostics: + The `tern.axis.ticks.length.major` theme element must be a + object. + --- failed re-building ‘choropleth_maps_with_tricolore.Rmd’ + + SUMMARY: processing the following file failed: + ‘choropleth_maps_with_tricolore.Rmd’ + + Error: Vignette re-building failed. + Execution halted + ``` + +## In both + +* checking data for non-ASCII characters ... NOTE + ``` + Note: found 2 marked UTF-8 strings ``` -# viscomp +# triptych
-* Version: 1.0.0 -* GitHub: https://github.com/georgiosseitidis/viscomp -* Source code: https://github.com/cran/viscomp -* Date/Publication: 2023-01-16 09:50:02 UTC -* Number of recursive dependencies: 149 +* Version: 0.1.3 +* GitHub: https://github.com/aijordan/triptych +* Source code: https://github.com/cran/triptych +* Date/Publication: 2024-06-13 15:50:02 UTC +* Number of recursive dependencies: 64 -Run `revdepcheck::cloud_details(, "viscomp")` for more info +Run `revdepcheck::cloud_details(, "triptych")` for more info
@@ -21494,172 +13374,171 @@ Run `revdepcheck::cloud_details(, "viscomp")` for more info * checking examples ... ERROR ``` - Running examples in ‘viscomp-Ex.R’ failed + Running examples in ‘triptych-Ex.R’ failed The error most likely occurred in: - > ### Name: loccos - > ### Title: Leaving One Component Combination Out Scatter plot - > ### Aliases: loccos + > ### Name: plot.triptych + > ### Title: Plot methods for the triptych classes + > ### Aliases: plot.triptych autoplot.triptych plot.triptych_murphy + > ### autoplot.triptych_murphy plot.triptych_reliability + > ### autoplot.triptych_reliability plot.triptych_roc autoplot.triptych_roc + > ### plot.triptych_mcbdsc autoplot.triptych_mcbdsc > > ### ** Examples > - > data(nmaMACE) - ... - ▆ - 1. └─viscomp::loccos(model = nmaMACE, combination = c("B")) - 2. └─ggExtra::ggMarginal(p, type = "histogram", fill = histogram.color) - 3. └─ggplot2::ggplotGrob(scatP) - 4. ├─ggplot2::ggplot_gtable(ggplot_build(x)) - 5. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) - 6. └─ggplot2::calc_element("plot.margin", theme) - 7. └─cli::cli_abort(...) - 8. └─rlang::abort(...) + > data(ex_binary, package = "triptych") + > tr <- triptych(ex_binary) + > + > dplyr::slice(tr, 1, 3, 6, 9) |> autoplot() + Error in identicalUnits(x) : object is not a unit + Calls: ... assemble_guides -> guides_build -> unit.c -> identicalUnits Execution halted ``` -# visR +# tsnet
-* Version: 0.4.1 -* GitHub: https://github.com/openpharma/visR -* Source code: https://github.com/cran/visR -* Date/Publication: 2024-03-15 21:50:02 UTC -* Number of recursive dependencies: 148 +* Version: 0.1.0 +* GitHub: https://github.com/bsiepe/tsnet +* Source code: https://github.com/cran/tsnet +* Date/Publication: 2024-02-28 11:30:02 UTC +* Number of recursive dependencies: 77 -Run `revdepcheck::cloud_details(, "visR")` for more info +Run `revdepcheck::cloud_details(, "tsnet")` for more info
## Newly broken -* checking examples ... ERROR - ``` - Running examples in ‘visR-Ex.R’ failed - The error most likely occurred in: - - > ### Name: add_risktable - > ### Title: Add risk tables to visR plots through an S3 method - > ### Aliases: add_risktable add_risktable.ggsurvfit - > ### add_risktable.ggtidycuminc - > - > ### ** Examples - > - ... - 4. │ └─gglist %>% align_plots() - 5. └─visR::align_plots(.) - 6. └─base::lapply(pltlist, ggplot2::ggplotGrob) - 7. └─ggplot2 (local) FUN(X[[i]], ...) - 8. ├─ggplot2::ggplot_gtable(ggplot_build(x)) - 9. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) - 10. └─ggplot2::calc_element("plot.margin", theme) - 11. └─cli::cli_abort(...) - 12. └─rlang::abort(...) - Execution halted - ``` - * checking tests ... ERROR ``` - Running ‘spelling.R’ Running ‘testthat.R’ Running the tests in ‘tests/testthat.R’ failed. Complete output: - > library(testthat) - > library(visR) - > library(vdiffr) - > library(survival) - > - > test_check("visR") + > # This file is part of the standard setup for testthat. + > # It is recommended that you do not modify it. + > # + > # Where should you do additional test configuration? + > # Learn more about the roles of various files in: + > # * https://r-pkgs.org/tests.html + > # * https://testthat.r-lib.org/reference/test_package.html#special-files ... - 10. └─ggplot2::calc_element("plot.margin", theme) - 11. └─cli::cli_abort(...) - 12. └─rlang::abort(...) + unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, "black", TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), list(NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), 5.5, c(5.5, 5.5, 5.5, 5.5), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(7, 0, 0, 0), NULL, FALSE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, + NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, 90, NULL, c(0, 7, 0, 0), NULL, FALSE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 1, NULL, NULL, NULL, + c(0, 2.2, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, NULL, c(0, 0, 0, 2.2), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0.5, NULL, NULL, NULL, c(0, 2.2, 0, 2.2), NULL, TRUE), list("grey70", 0.5, NULL, NULL, FALSE, "grey70", TRUE), NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 0.5, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 0.75, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, list(), list("gray70", 0.5, NULL, NULL, FALSE, + "gray70", FALSE), NULL, NULL, list("gray70", 0.5, NULL, NULL, FALSE, "gray70", FALSE), NULL, NULL, NULL, NULL, list(NULL, NA, NULL, NULL, TRUE), NULL, 2, NULL, NULL, NULL, 1.2, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 0.2, NULL, list(NULL, NULL, NULL, 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, NULL, NULL, NULL, TRUE), NULL, "right", NULL, NULL, NULL, "center", NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 0, list(), 2, list("white", NA, + NULL, NULL, TRUE), list(), NULL, NULL, NULL, list("grey87", NULL, NULL, NULL, FALSE, "grey87", TRUE), list(), list(), NULL, NULL, NULL, NULL, FALSE, list(NULL, "white", NULL, NULL, TRUE), list(NULL, NULL, NULL, 1.2, 0, 1, NULL, NULL, c(0, 0, 5.5, 0), NULL, TRUE), "panel", list(NULL, NULL, NULL, NULL, 0, 1, NULL, NULL, c(0, 0, 5.5, 0), NULL, TRUE), list(NULL, NULL, NULL, 0.8, 1, 1, NULL, NULL, c(5.5, 0, 0, 0), NULL, TRUE), "panel", list(NULL, NULL, NULL, 1.2, 0.5, 0.5, NULL, NULL, NULL, NULL, + TRUE), "topleft", NULL, NULL, list("gray90", NA, NULL, NULL, FALSE), NULL, NULL, "inherit", "inside", list(NULL, NULL, "black", 0.8, NULL, NULL, NULL, NULL, c(6, 6, 6, 6), NULL, FALSE), NULL, NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, NULL, -90, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, NULL, 90, NULL, NULL, NULL, TRUE), NULL, 2.75, 2.75)) - [ FAIL 14 | WARN 28 | SKIP 24 | PASS 991 ] + [ FAIL 1 | WARN 14 | SKIP 0 | PASS 108 ] Error: Test failures - In addition: Warning message: - In .Internal(delayedAssign(x, substitute(value), eval.env, assign.env)) : - closing unused connection 4 (https://raw.githubusercontent.com/vntkumar8/covid-survival/main/data/final.csv) Execution halted ``` -* checking running R code from vignettes ... ERROR +## In both + +* checking installed package size ... NOTE ``` - Errors in running code in vignettes: - when running code in ‘CDISC_ADaM.Rmd’ - ... - - - - > visr(survfit_object) %>% visR::add_CI() %>% visR::add_risktable() - Warning: `visr.survfit()` was deprecated in visR 0.4.0. - ℹ Please use `ggsurvfit::ggsurvfit()` instead. - - ... - + size = 2) %>% visR::add_risktable() - - When sourcing ‘Time_to_event_analysis.R’: - Error: Theme element `plot.margin` must have class . - Execution halted - - ‘CDISC_ADaM.Rmd’ using ‘UTF-8’... failed - ‘Consort_flow_diagram.Rmd’ using ‘UTF-8’... OK - ‘Styling_KM_plots.Rmd’ using ‘UTF-8’... OK - ‘Time_to_event_analysis.Rmd’ using ‘UTF-8’... failed + installed size is 163.0Mb + sub-directories of 1Mb or more: + libs 162.0Mb + ``` + +* checking for GNU extensions in Makefiles ... NOTE + ``` + GNU make is a SystemRequirements. ``` -* checking re-building of vignette outputs ... NOTE +# umiAnalyzer + +
+ +* Version: 1.0.0 +* GitHub: https://github.com/sfilges/umiAnalyzer +* Source code: https://github.com/cran/umiAnalyzer +* Date/Publication: 2021-11-25 08:40:02 UTC +* Number of recursive dependencies: 116 + +Run `revdepcheck::cloud_details(, "umiAnalyzer")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR ``` - Error(s) in re-building vignettes: - --- re-building ‘CDISC_ADaM.Rmd’ using rmarkdown - - Quitting from lines 86-90 [km_plot_1] (CDISC_ADaM.Rmd) - Error: processing vignette 'CDISC_ADaM.Rmd' failed with diagnostics: - Theme element `plot.margin` must have class . - --- failed re-building ‘CDISC_ADaM.Rmd’ + Running examples in ‘umiAnalyzer-Ex.R’ failed + The error most likely occurred in: - --- re-building ‘Consort_flow_diagram.Rmd’ using rmarkdown + > ### Name: AmpliconPlot + > ### Title: Generate Amplicon plots + > ### Aliases: AmpliconPlot + > + > ### ** Examples + > + > library(umiAnalyzer) + ... + > + > main = system.file('extdata', package = 'umiAnalyzer') + > samples <- list.dirs(path = main, full.names = FALSE, recursive = FALSE) + > simsen <- createUmiExperiment(experimentName = 'example',mainDir = main,sampleNames = samples) + > simsen <- filterUmiObject(simsen) + > + > amplicon_plot <- AmpliconPlot(simsen) + Error in pm[[2]] : subscript out of bounds + Calls: AmpliconPlot -> -> ggplotly.ggplot -> gg2list + Execution halted ``` -# vivainsights +# valr
-* Version: 0.5.2 -* GitHub: https://github.com/microsoft/vivainsights -* Source code: https://github.com/cran/vivainsights -* Date/Publication: 2024-03-14 17:40:02 UTC -* Number of recursive dependencies: 114 +* Version: 0.8.1 +* GitHub: https://github.com/rnabioco/valr +* Source code: https://github.com/cran/valr +* Date/Publication: 2024-04-22 18:30:03 UTC +* Number of recursive dependencies: 175 -Run `revdepcheck::cloud_details(, "vivainsights")` for more info +Run `revdepcheck::cloud_details(, "valr")` for more info
## Newly broken -* checking examples ... ERROR +* checking tests ... ERROR ``` - Running examples in ‘vivainsights-Ex.R’ failed - The error most likely occurred in: - - > ### Name: tm_freq - > ### Title: Perform a Word or Ngram Frequency Analysis and return a Circular - > ### Bar Plot - > ### Aliases: tm_freq - > - > ### ** Examples - > + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Complete output: + > # This file is part of the standard setup for testthat. + > # It is recommended that you do not modify it. + > # + > # Where should you do additional test configuration? + > # Learn more about the roles of various files in: + > # * https://r-pkgs.org/tests.html + > # * https://testthat.r-lib.org/reference/test_package.html#special-files ... - Backtrace: - ▆ - 1. ├─base (local) ``(x) - 2. └─ggplot2:::print.ggplot(x) - 3. ├─ggplot2::ggplot_gtable(data) - 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) - 5. └─ggplot2::calc_element("plot.margin", theme) - 6. └─cli::cli_abort(...) - 7. └─rlang::abort(...) - Execution halted + ══ Failed tests ════════════════════════════════════════════════════════════════ + ── Failure ('test_glyph.r:13:3'): glyph labels are applied ───────────────────── + res$labels$label (`actual`) not equal to "id" (`expected`). + + `actual` is NULL + `expected` is a character vector ('id') + + [ FAIL 1 | WARN 0 | SKIP 4 | PASS 479 ] + Error: Test failures + Execution halted + ``` + +## In both + +* checking installed package size ... NOTE + ``` + installed size is 15.1Mb + sub-directories of 1Mb or more: + libs 13.9Mb ``` # vivaldi @@ -21763,6 +13642,45 @@ Run `revdepcheck::cloud_details(, "vivaldi")` for more info extdata 1.1Mb ``` +# vivid + +
+ +* Version: 0.2.8 +* GitHub: NA +* Source code: https://github.com/cran/vivid +* Date/Publication: 2023-07-10 22:20:02 UTC +* Number of recursive dependencies: 220 + +Run `revdepcheck::cloud_details(, "vivid")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘vivid-Ex.R’ failed + The error most likely occurred in: + + > ### Name: vivi + > ### Title: vivi + > ### Aliases: vivi + > + > ### ** Examples + > + > + > aq <- na.omit(airquality) + > f <- lm(Ozone ~ ., data = aq) + > m <- vivi(fit = f, data = aq, response = "Ozone") # as expected all interactions are zero + Agnostic variable importance method used. + Calculating interactions... + > viviHeatmap(m) + Error in names(labels) <- `*vtmp*` : attempt to set an attribute on NULL + Calls: viviHeatmap ... ggplot_add -> ggplot_add.new_aes -> bump_aes_labels + Execution halted + ``` + # vvshiny
@@ -21771,7 +13689,7 @@ Run `revdepcheck::cloud_details(, "vivaldi")` for more info * GitHub: NA * Source code: https://github.com/cran/vvshiny * Date/Publication: 2023-07-19 15:30:02 UTC -* Number of recursive dependencies: 131 +* Number of recursive dependencies: 135 Run `revdepcheck::cloud_details(, "vvshiny")` for more info @@ -21804,164 +13722,6 @@ Run `revdepcheck::cloud_details(, "vvshiny")` for more info Execution halted ``` -# WASP - -
- -* Version: 1.4.3 -* GitHub: https://github.com/zejiang-unsw/WASP -* Source code: https://github.com/cran/WASP -* Date/Publication: 2022-08-22 07:50:24 UTC -* Number of recursive dependencies: 153 - -Run `revdepcheck::cloud_details(, "WASP")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘WASP-Ex.R’ failed - The error most likely occurred in: - - > ### Name: fig.dwt.vt - > ### Title: Plot function: Variance structure before and after variance - > ### transformation - > ### Aliases: fig.dwt.vt - > - > ### ** Examples - > - ... - Backtrace: - ▆ - 1. ├─base (local) ``(x) - 2. └─ggplot2:::print.ggplot(x) - 3. ├─ggplot2::ggplot_gtable(data) - 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) - 5. └─ggplot2::calc_element("plot.margin", theme) - 6. └─cli::cli_abort(...) - 7. └─rlang::abort(...) - Execution halted - ``` - -## In both - -* checking dependencies in R code ... NOTE - ``` - Namespace in Imports field not imported from: ‘rlang’ - All declared Imports should be used. - ``` - -# Wats - -
- -* Version: 1.0.1 -* GitHub: https://github.com/OuhscBbmc/Wats -* Source code: https://github.com/cran/Wats -* Date/Publication: 2023-03-10 22:50:05 UTC -* Number of recursive dependencies: 122 - -Run `revdepcheck::cloud_details(, "Wats")` for more info - -
- -## Newly broken - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘mbr-figures.Rmd’ - ... - > grid::grid.newpage() - - > grid::pushViewport(grid::viewport(layout = grid::grid.layout(3, - + 1))) - - > print(top_panel, vp = vp_layout(1, 1)) - - When sourcing ‘mbr-figures.R’: - Error: Theme element `plot.margin` must have class . - Execution halted - - ‘mbr-figures.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘mbr-figures.Rmd’ using rmarkdown - ``` - -# whomds - -
- -* Version: 1.1.1 -* GitHub: https://github.com/lindsayevanslee/whomds -* Source code: https://github.com/cran/whomds -* Date/Publication: 2023-09-08 04:30:02 UTC -* Number of recursive dependencies: 123 - -Run `revdepcheck::cloud_details(, "whomds")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘whomds-Ex.R’ failed - The error most likely occurred in: - - > ### Name: fig_density - > ### Title: Plot a density of a score - > ### Aliases: fig_density - > - > ### ** Examples - > - > fig_density(df_adults, score = "disability_score", cutoffs = c(19.1, 34.4, 49.6), - ... - Backtrace: - ▆ - 1. ├─base (local) ``(x) - 2. └─ggplot2:::print.ggplot(x) - 3. ├─ggplot2::ggplot_gtable(data) - 4. └─ggplot2:::ggplot_gtable.ggplot_built(data) - 5. └─ggplot2::calc_element("plot.margin", theme) - 6. └─cli::cli_abort(...) - 7. └─rlang::abort(...) - Execution halted - ``` - -## In both - -* checking running R code from vignettes ... WARNING - ``` - Errors in running code in vignettes: - when running code in ‘c2_getting_started_EN.Rmd’ - ... - + out.width = "80%", fig.align = "center", collapse = TRUE, - + comment = "#> ..." ... [TRUNCATED] - - > install.packages("whomds") - Installing package into ‘/tmp/workdir/whomds/new/whomds.Rcheck’ - (as ‘lib’ is unspecified) - - ... - ‘c2_getting_started_EN.Rmd’ using ‘UTF-8’... failed - ‘c2_getting_started_ES.Rmd’ using ‘UTF-8’... failed - ‘c3_rasch_adults_EN.Rmd’ using ‘UTF-8’... failed - ‘c3_rasch_adults_ES.Rmd’ using ‘UTF-8’... failed - ‘c4_rasch_children_EN.Rmd’ using ‘UTF-8’... failed - ‘c4_rasch_children_ES.Rmd’ using ‘UTF-8’... failed - ‘c5_best_practices_EN.Rmd’ using ‘UTF-8’... OK - ‘c5_best_practices_ES.Rmd’ using ‘UTF-8’... OK - ‘c6_after_rasch_EN.Rmd’ using ‘UTF-8’... failed - ‘c6_after_rasch_ES.Rmd’ using ‘UTF-8’... failed - ``` - # wilson
@@ -21970,7 +13730,7 @@ Run `revdepcheck::cloud_details(, "whomds")` for more info * GitHub: https://github.com/loosolab/wilson * Source code: https://github.com/cran/wilson * Date/Publication: 2021-04-19 09:40:02 UTC -* Number of recursive dependencies: 199 +* Number of recursive dependencies: 203 Run `revdepcheck::cloud_details(, "wilson")` for more info @@ -22003,103 +13763,6 @@ Run `revdepcheck::cloud_details(, "wilson")` for more info Execution halted ``` -# WVPlots - -
- -* Version: 1.3.8 -* GitHub: https://github.com/WinVector/WVPlots -* Source code: https://github.com/cran/WVPlots -* Date/Publication: 2024-04-22 20:40:07 UTC -* Number of recursive dependencies: 78 - -Run `revdepcheck::cloud_details(, "WVPlots")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘WVPlots-Ex.R’ failed - The error most likely occurred in: - - > ### Name: ScatterHist - > ### Title: Plot a scatter plot with marginals. - > ### Aliases: ScatterHist - > - > ### ** Examples - > - > - ... - 2. └─gridExtra::grid.arrange(...) - 3. └─gridExtra::arrangeGrob(...) - 4. └─base::lapply(grobs[toconv], ggplot2::ggplotGrob) - 5. └─ggplot2 (local) FUN(X[[i]], ...) - 6. ├─ggplot2::ggplot_gtable(ggplot_build(x)) - 7. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) - 8. └─ggplot2::calc_element("plot.margin", theme) - 9. └─cli::cli_abort(...) - 10. └─rlang::abort(...) - Execution halted - ``` - -* checking tests ... ERROR - ``` - Running ‘tinytest.R’ - Running the tests in ‘tests/tinytest.R’ failed. - Complete output: - > - > if (requireNamespace("tinytest", quietly=TRUE) ) { - + if (requireNamespace('data.table', quietly = TRUE)) { - + # don't multi-thread during CRAN checks - + data.table::setDTthreads(1) - + } - + tinytest::test_package("WVPlots") - ... - 10. └─gridExtra::grid.arrange(...) - 11. └─gridExtra::arrangeGrob(...) - 12. └─base::lapply(grobs[toconv], ggplot2::ggplotGrob) - 13. └─ggplot2 (local) FUN(X[[i]], ...) - 14. ├─ggplot2::ggplot_gtable(ggplot_build(x)) - 15. └─ggplot2:::ggplot_gtable.ggplot_built(ggplot_build(x)) - 16. └─ggplot2::calc_element("plot.margin", theme) - 17. └─cli::cli_abort(...) - 18. └─rlang::abort(...) - Execution halted - ``` - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘WVPlots_concept.Rmd’ - ... - > frm$absY <- abs(frm$y) - - > frm$posY = frm$y > 0 - - > WVPlots::ScatterHist(frm, "x", "y", smoothmethod = "lm", - + title = "Example Linear Fit") - - ... - > frm$posY = frm$y > 0 - - > WVPlots::ScatterHist(frm, "x", "y", title = "Example Fit") - - When sourcing ‘WVPlots_examples.R’: - Error: Theme element `plot.margin` must have class . - Execution halted - - ‘WVPlots_concept.Rmd’ using ‘UTF-8’... failed - ‘WVPlots_examples.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘WVPlots_concept.Rmd’ using rmarkdown - ``` - # xaringanthemer
@@ -22162,17 +13825,17 @@ Run `revdepcheck::cloud_details(, "xaringanthemer")` for more info ‘xaringanthemer.Rmd’ using ‘UTF-8’... failed ``` -# xpose +# yamlet
-* Version: 0.4.18 -* GitHub: https://github.com/UUPharmacometrics/xpose -* Source code: https://github.com/cran/xpose -* Date/Publication: 2024-02-01 16:20:02 UTC -* Number of recursive dependencies: 109 +* Version: 1.0.3 +* GitHub: https://github.com/bergsmat/yamlet +* Source code: https://github.com/cran/yamlet +* Date/Publication: 2024-03-29 13:30:02 UTC +* Number of recursive dependencies: 103 -Run `revdepcheck::cloud_details(, "xpose")` for more info +Run `revdepcheck::cloud_details(, "yamlet")` for more info
@@ -22180,26 +13843,26 @@ Run `revdepcheck::cloud_details(, "xpose")` for more info * checking examples ... ERROR ``` - Running examples in ‘xpose-Ex.R’ failed + Running examples in ‘yamlet-Ex.R’ failed The error most likely occurred in: - > ### Name: amt_vs_idv - > ### Title: Compartment kinetics - > ### Aliases: amt_vs_idv + > ### Name: ggplot_add.ggplot_isometric + > ### Title: Add Isometry to Plot Object + > ### Aliases: ggplot_add.ggplot_isometric + > ### Keywords: internal > > ### ** Examples > - > amt_vs_idv(xpdb_ex_pk, nrow = 2, ncol = 1) ... - 1. ├─base (local) ``(x) - 2. ├─xpose:::print.xpose_plot(x) - 3. │ └─x %>% paginate(page_2_draw, page_tot) %>% print.ggplot(...) - 4. └─ggplot2:::print.ggplot(., ...) - 5. ├─ggplot2::ggplot_gtable(data) - 6. └─ggplot2:::ggplot_gtable.ggplot_built(data) - 7. └─ggplot2::calc_element("plot.margin", theme) - 8. └─cli::cli_abort(...) - 9. └─rlang::abort(...) + ismtrc> library(magrittr) + + ismtrc> library(ggplot2) + + ismtrc> data.frame(x = 1:5, y = 3:7) %>% + ismtrc+ ggplot(aes(x, y)) + geom_point() + isometric() + Error in ggplot_add.ggplot_isometric(object, p, objectname) : + "x" %in% names(plot$labels) is not TRUE + Calls: example ... ggplot_add -> ggplot_add.ggplot_isometric -> stopifnot Execution halted ``` @@ -22209,72 +13872,22 @@ Run `revdepcheck::cloud_details(, "xpose")` for more info Running the tests in ‘tests/testthat.R’ failed. Complete output: > library(testthat) - > library(xpose) - Loading required package: ggplot2 + > library(yamlet) - Attaching package: 'xpose' + Attaching package: 'yamlet' The following object is masked from 'package:stats': + ... - 8. └─ggplot2:::print.ggplot(., ...) - 9. ├─ggplot2::ggplot_gtable(data) - 10. └─ggplot2:::ggplot_gtable.ggplot_built(data) - 11. └─ggplot2::calc_element("plot.margin", theme) - 12. └─cli::cli_abort(...) - 13. └─rlang::abort(...) + ══ Skipped tests (2) ═══════════════════════════════════════════════════════════ + • empty test (2): 'test-yamlet.R:1346:1', 'test-yamlet.R:1351:1' + + ══ Failed tests ════════════════════════════════════════════════════════════════ + ── Failure ('test-yamlet.R:843:1'): ggplot.resolved is stable ────────────────── + `print(x %>% ggplot(map) + geom_point())` did not produce any warnings. - [ FAIL 4 | WARN 0 | SKIP 8 | PASS 510 ] + [ FAIL 1 | WARN 0 | SKIP 2 | PASS 516 ] Error: Test failures Execution halted ``` -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘customize_plots.Rmd’ - ... - Using data from $prob no.1 - Filtering data by EVID == 0 - Using data from $prob no.1 - Filtering data by EVID == 0 - Using data from $prob no.1 - Filtering data by EVID == 0 - - ... - When sourcing ‘vpc.R’: - Error: Theme element `plot.margin` must have class . - Execution halted - - ‘access_xpdb_data.Rmd’ using ‘UTF-8’... OK - ‘customize_plots.Rmd’ using ‘UTF-8’... failed - ‘import_model_outputs.Rmd’ using ‘UTF-8’... OK - ‘introduction.Rmd’ using ‘UTF-8’... failed - ‘multiple_pages.Rmd’ using ‘UTF-8’... failed - ‘vpc.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘access_xpdb_data.Rmd’ using rmarkdown - --- finished re-building ‘access_xpdb_data.Rmd’ - - --- re-building ‘customize_plots.Rmd’ using rmarkdown - - Quitting from lines 36-42 [demo type scatter] (customize_plots.Rmd) - Error: processing vignette 'customize_plots.Rmd' failed with diagnostics: - Theme element `plot.margin` must have class . - --- failed re-building ‘customize_plots.Rmd’ - ... - Error: processing vignette 'vpc.Rmd' failed with diagnostics: - Theme element `plot.margin` must have class . - --- failed re-building ‘vpc.Rmd’ - - SUMMARY: processing the following files failed: - ‘customize_plots.Rmd’ ‘introduction.Rmd’ ‘multiple_pages.Rmd’ - ‘vpc.Rmd’ - - Error: Vignette re-building failed. - Execution halted - ``` - From 789ec08da50c5c6bb96a2ef2a3ecd6447d53d544 Mon Sep 17 00:00:00 2001 From: Teun van den Brand Date: Fri, 19 Jul 2024 15:28:12 +0200 Subject: [PATCH 31/41] protect against missing `theme` --- R/guide-legend.R | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/R/guide-legend.R b/R/guide-legend.R index e665b76d54..b355af9287 100644 --- a/R/guide-legend.R +++ b/R/guide-legend.R @@ -223,7 +223,7 @@ GuideLegend <- ggproto( self$get_layer_key(params, layers[include], data[include], theme) }, - get_layer_key = function(params, layers, data, theme) { + get_layer_key = function(params, layers, data, theme = NULL) { # Return empty guides as-is if (nrow(params$key) < 1) { From 0d682f1ab399402ecb230d17aaca0c495569e740 Mon Sep 17 00:00:00 2001 From: Teun van den Brand Date: Fri, 19 Jul 2024 16:09:16 +0200 Subject: [PATCH 32/41] skip empty sf layers --- R/layer-sf.R | 1 + 1 file changed, 1 insertion(+) diff --git a/R/layer-sf.R b/R/layer-sf.R index 437ecef3df..3a282e734f 100644 --- a/R/layer-sf.R +++ b/R/layer-sf.R @@ -72,6 +72,7 @@ LayerSf <- ggproto("LayerSf", Layer, }, compute_geom_2 = function(self, data, params = self$aes_params, ...) { + if (empty(data)) return(data) data$geometry <- data$geometry %||% self$computed_geom_params$legend ggproto_parent(Layer, self)$compute_geom_2(data, params, ...) } From e6afd5c590f968d3860e71372e5a3525b4929af5 Mon Sep 17 00:00:00 2001 From: Teun van den Brand Date: Tue, 23 Jul 2024 10:22:07 +0200 Subject: [PATCH 33/41] getter for geom defaults --- DESCRIPTION | 2 +- NAMESPACE | 1 + R/geom-defaults.R | 52 ++++++++++++++++++++++++++++++++++++++++ man/get_geom_defaults.Rd | 43 +++++++++++++++++++++++++++++++++ 4 files changed, 97 insertions(+), 1 deletion(-) create mode 100644 man/get_geom_defaults.Rd diff --git a/DESCRIPTION b/DESCRIPTION index 3f34454b36..d97ce7e689 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -78,7 +78,7 @@ Config/testthat/edition: 3 Encoding: UTF-8 LazyData: true Roxygen: list(markdown = TRUE) -RoxygenNote: 7.3.1 +RoxygenNote: 7.3.2 Collate: 'ggproto.R' 'ggplot-global.R' diff --git a/NAMESPACE b/NAMESPACE index c71207ce97..62adb9cb44 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -424,6 +424,7 @@ export(geom_violin) export(geom_vline) export(get_alt_text) export(get_element_tree) +export(get_geom_defaults) export(get_guide_data) export(get_last_plot) export(get_layer_data) diff --git a/R/geom-defaults.R b/R/geom-defaults.R index 55d019b886..9bf1689a1e 100644 --- a/R/geom-defaults.R +++ b/R/geom-defaults.R @@ -47,6 +47,58 @@ update_stat_defaults <- function(stat, new) { update_defaults(stat, "Stat", new, env = parent.frame()) } +#' Resolve and get geom defaults +#' +#' @param geom Some definition of a geom: +#' * A `function` that creates a layer, e.g. `geom_path()`. +#' * A layer created by such function +#' * A string naming a geom class in snake case without the `geom_`-prefix, +#' e.g. `"contour_filled"`. +#' * A geom class object. +#' @param theme A [`theme`] object. Defaults to the current global theme. +#' +#' @return A list of aesthetics +#' @export +#' @keywords internal +#' +#' @examples +#' # Using a function +#' get_geom_defaults(geom_raster) +#' +#' # Using a layer includes static aesthetics as default +#' get_geom_defaults(geom_tile(fill = "white")) +#' +#' # Using a class name +#' get_geom_defaults("density_2d") +#' +#' # Using a class +#' get_geom_defaults(GeomPoint) +#' +#' # Changed theme +#' get_geom_defaults("point", theme(geom = element_geom(ink = "purple"))) +get_geom_defaults <- function(geom, theme = theme_get()) { + theme <- theme %||% list(geom = .default_geom_element) + + if (is.function(geom)) { + geom <- geom() + } + if (is.layer(geom)) { + data <- data_frame0(.id = 1L) + data <- geom$compute_geom_2(data = data, theme = theme) + data$.id <- NULL + return(data) + } + if (is.character(geom)) { + geom <- check_subclass(geom, "Geom") + } + if (inherits(geom, "Geom")) { + out <- geom$use_defaults(data = NULL, theme = theme) + return(out) + } + stop_input_type(geom, as_cli("a layer function, string or {.cls Geom} object")) +} + + cache_defaults <- new_environment() update_defaults <- function(name, subclass, new, env = parent.frame()) { diff --git a/man/get_geom_defaults.Rd b/man/get_geom_defaults.Rd new file mode 100644 index 0000000000..a39f80d720 --- /dev/null +++ b/man/get_geom_defaults.Rd @@ -0,0 +1,43 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/geom-defaults.R +\name{get_geom_defaults} +\alias{get_geom_defaults} +\title{Resolve and get geom defaults} +\usage{ +get_geom_defaults(geom, theme = theme_get()) +} +\arguments{ +\item{geom}{Some definition of a geom: +\itemize{ +\item A \code{function} that creates a layer, e.g. \code{geom_path()}. +\item A layer created by such function +\item A string naming a geom class in snake case without the \code{geom_}-prefix, +e.g. \code{"contour_filled"}. +\item A geom class object. +}} + +\item{theme}{A \code{\link{theme}} object. Defaults to the current global theme.} +} +\value{ +A list of aesthetics +} +\description{ +Resolve and get geom defaults +} +\examples{ +# Using a function +get_geom_defaults(geom_raster) + +# Using a layer includes static aesthetics as default +get_geom_defaults(geom_tile(fill = "white")) + +# Using a class name +get_geom_defaults("density_2d") + +# Using a class +get_geom_defaults(GeomPoint) + +# Changed theme +get_geom_defaults("point", theme(geom = element_geom(ink = "purple"))) +} +\keyword{internal} From 6a08f2d947cabc867da3717538a414a4742701e7 Mon Sep 17 00:00:00 2001 From: Teun van den Brand Date: Tue, 23 Jul 2024 10:26:40 +0200 Subject: [PATCH 34/41] add test --- tests/testthat/test-geom-.R | 21 ++++++++++++++++++--- 1 file changed, 18 insertions(+), 3 deletions(-) diff --git a/tests/testthat/test-geom-.R b/tests/testthat/test-geom-.R index f13236416e..e6f952ec14 100644 --- a/tests/testthat/test-geom-.R +++ b/tests/testthat/test-geom-.R @@ -6,19 +6,34 @@ test_that("aesthetic checking in geom throws correct errors", { expect_snapshot_error(check_aesthetics(aes, 4)) }) +test_that("get_geom_defaults can use various sources", { + + test <- get_geom_defaults(geom_point) + expect_equal(test$colour, "black") + + test <- get_geom_defaults(geom_point(colour = "red")) + expect_equal(test$colour, "red") + + test <- get_geom_defaults("point") + expect_equal(test$colour, "black") + + test <- get_geom_defaults(GeomPoint, theme(geom = element_geom("red"))) + expect_equal(test$colour, "red") +}) + test_that("geom defaults can be set and reset", { l <- geom_point() orig <- l$geom$default_aes$colour - test <- l$geom$use_defaults(data_frame0()) + test <- get_geom_defaults(l) expect_equal(test$colour, "black") inv <- update_geom_defaults("point", list(colour = "red")) - test <- l$geom$use_defaults(data_frame0()) + test <- get_geom_defaults(l) expect_equal(test$colour, "red") expect_equal(inv$colour, orig) inv <- update_geom_defaults("point", NULL) - test <- l$geom$use_defaults(data_frame0()) + test <- get_geom_defaults(l) expect_equal(test$colour, "black") expect_equal(inv$colour, "red") }) From f1fae8e6c22a680d3f13ac569ff7da43b764dba0 Mon Sep 17 00:00:00 2001 From: Teun van den Brand Date: Tue, 23 Jul 2024 14:02:29 +0200 Subject: [PATCH 35/41] tmp --- revdep/problems.md | 15168 ++++--------------------------------------- 1 file changed, 1296 insertions(+), 13872 deletions(-) diff --git a/revdep/problems.md b/revdep/problems.md index 517f4be819..8e2e437056 100644 --- a/revdep/problems.md +++ b/revdep/problems.md @@ -1,13893 +1,1317 @@ -# activAnalyzer - -
- -* Version: 2.1.1 -* GitHub: https://github.com/pydemull/activAnalyzer -* Source code: https://github.com/cran/activAnalyzer -* Date/Publication: 2024-05-05 22:40:03 UTC -* Number of recursive dependencies: 153 - -Run `revdepcheck::cloud_details(, "activAnalyzer")` for more info - -
- -## Newly broken - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘activAnalyzer.Rmd’ - ... - > p3 <- accum_metrics_sed$p_UBD - - > p4 <- accum_metrics_sed$p_gini - - > (p1 | p2)/(p3 | p4) + plot_layout(guides = "collect") & - + theme(legend.position = "bottom") - - When sourcing ‘activAnalyzer.R’: - Error: object is not a unit - Execution halted - - ‘activAnalyzer.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘activAnalyzer.Rmd’ using rmarkdown - ``` - -## In both - -* checking installed package size ... NOTE - ``` - installed size is 5.3Mb - sub-directories of 1Mb or more: - R 1.0Mb - doc 1.0Mb - extdata 2.0Mb - ``` - -# actxps - -
- -* Version: 1.5.0 -* GitHub: https://github.com/mattheaphy/actxps -* Source code: https://github.com/cran/actxps -* Date/Publication: 2024-06-25 12:40:02 UTC -* Number of recursive dependencies: 130 - -Run `revdepcheck::cloud_details(, "actxps")` for more info - -
- -## Newly broken - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘actxps.Rmd’ - ... - # ℹ 2 more variables: ae_expected_1 , ae_expected_2 - - > autoplot(exp_res) - Warning: thematic was unable to resolve `bg='auto'`. Try providing an actual color (or `NA`) to the `bg` argument of `thematic_on()`. By the way, 'auto' is only officially supported in `shiny::renderPlot()`, some rmarkdown scenarios (specifically, `html_document()` with `theme!=NULL`), in RStudio, or if `auto_config_set()` is used. - Warning: thematic was unable to resolve `fg='auto'`. Try providing an actual color (or `NA`) to the `fg` argument of `thematic_on()`. By the way, 'auto' is only officially supported in `shiny::renderPlot()`, some rmarkdown scenarios (specifically, `html_document()` with `theme!=NULL`), in RStudio, or if `auto_config_set()` is used. - Warning: thematic was unable to resolve `accent='auto'`. Try providing an actual color (or `NA`) to the `accent` argument of `thematic_on()`. By the way, 'auto' is only officially supported in `shiny::renderPlot()`, some rmarkdown scenarios (specifically, `html_document()` with `theme!=NULL`), in RStudio, or if `auto_config_set()` is used. - - ... - - When sourcing ‘transactions.R’: - Error: Internal error: adjust_color() expects an input of length 1 - Execution halted - - ‘actxps.Rmd’ using ‘UTF-8’... failed - ‘exp_summary.Rmd’ using ‘UTF-8’... OK - ‘exposures.Rmd’ using ‘UTF-8’... OK - ‘misc.Rmd’ using ‘UTF-8’... failed - ‘transactions.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘actxps.Rmd’ using rmarkdown - Warning: thematic was unable to resolve `bg='auto'`. Try providing an actual color (or `NA`) to the `bg` argument of `thematic_on()`. By the way, 'auto' is only officially supported in `shiny::renderPlot()`, some rmarkdown scenarios (specifically, `html_document()` with `theme!=NULL`), in RStudio, or if `auto_config_set()` is used. - Warning: thematic was unable to resolve `fg='auto'`. Try providing an actual color (or `NA`) to the `fg` argument of `thematic_on()`. By the way, 'auto' is only officially supported in `shiny::renderPlot()`, some rmarkdown scenarios (specifically, `html_document()` with `theme!=NULL`), in RStudio, or if `auto_config_set()` is used. - Warning: thematic was unable to resolve `accent='auto'`. Try providing an actual color (or `NA`) to the `accent` argument of `thematic_on()`. By the way, 'auto' is only officially supported in `shiny::renderPlot()`, some rmarkdown scenarios (specifically, `html_document()` with `theme!=NULL`), in RStudio, or if `auto_config_set()` is used. - - Quitting from lines 129-130 [plot] (actxps.Rmd) - Error: processing vignette 'actxps.Rmd' failed with diagnostics: - Internal error: adjust_color() expects an input of length 1 - --- failed re-building ‘actxps.Rmd’ - ... - Quitting from lines 205-211 [trx-plot] (transactions.Rmd) - Error: processing vignette 'transactions.Rmd' failed with diagnostics: - Internal error: adjust_color() expects an input of length 1 - --- failed re-building ‘transactions.Rmd’ - - SUMMARY: processing the following files failed: - ‘actxps.Rmd’ ‘misc.Rmd’ ‘transactions.Rmd’ - - Error: Vignette re-building failed. - Execution halted - ``` - -# AeRobiology - -
- -* Version: 2.0.1 -* GitHub: NA -* Source code: https://github.com/cran/AeRobiology -* Date/Publication: 2019-06-03 06:20:03 UTC -* Number of recursive dependencies: 98 - -Run `revdepcheck::cloud_details(, "AeRobiology")` for more info - -
- -## Newly broken - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘my-vignette.Rmd’ using rmarkdown - ``` - -## In both - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘my-vignette.Rmd’ - ... - + export.plot = FALSE, export.result = FALSE, n.types = 3, - + y.start = 2011, y.end = .... [TRUNCATED] - - > iplot_abundance(munich_pollen, interpolation = FALSE, - + export.plot = FALSE, export.result = FALSE, n.types = 3, - + y.start = 2011, y.end = .... [TRUNCATED] - - When sourcing ‘my-vignette.R’: - Error: subscript out of bounds - Execution halted - - ‘my-vignette.Rmd’ using ‘UTF-8’... failed - ``` - -# agricolaeplotr - -
- -* Version: 0.5.0 -* GitHub: https://github.com/jensharbers/agricolaeplotr -* Source code: https://github.com/cran/agricolaeplotr -* Date/Publication: 2024-01-17 16:42:04 UTC -* Number of recursive dependencies: 144 - -Run `revdepcheck::cloud_details(, "agricolaeplotr")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(agricolaeplotr) - - Type 'citation("agricolaeplotr")' for citing this R package in publications. - - Attaching package: 'agricolaeplotr' - - ... - `expected` is a character vector ('ROW') - ── Failure ('testall.R:847:3'): plot a plot design from FielDHub package shows COLUMN as x axis ── - p$labels$x (`actual`) not identical to "COLUMN" (`expected`). - - `actual` is NULL - `expected` is a character vector ('COLUMN') - - [ FAIL 30 | WARN 92 | SKIP 0 | PASS 107 ] - Error: Test failures - Execution halted - ``` - -# AnalysisLin - -
- -* Version: 0.1.2 -* GitHub: NA -* Source code: https://github.com/cran/AnalysisLin -* Date/Publication: 2024-01-30 00:10:10 UTC -* Number of recursive dependencies: 119 - -Run `revdepcheck::cloud_details(, "AnalysisLin")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘AnalysisLin-Ex.R’ failed - The error most likely occurred in: - - > ### Name: bar_plot - > ### Title: Bar Plots for Categorical Variables - > ### Aliases: bar_plot - > - > ### ** Examples - > - > data(iris) - > bar_plot(iris) - Error in pm[[2]] : subscript out of bounds - Calls: bar_plot ... plotly_build -> ggplotly -> ggplotly.ggplot -> gg2list - Execution halted - ``` - -# animbook - -
- -* Version: 1.0.0 -* GitHub: https://github.com/KrisanatA/animbook -* Source code: https://github.com/cran/animbook -* Date/Publication: 2023-12-05 17:50:07 UTC -* Number of recursive dependencies: 88 - -Run `revdepcheck::cloud_details(, "animbook")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘animbook-Ex.R’ failed - The error most likely occurred in: - - > ### Name: anim_animate - > ### Title: Modified the ggplot object - > ### Aliases: anim_animate - > - > ### ** Examples - > - > animbook <- anim_prep(data = osiris, id = ID, values = sales, time = year, group = japan) - ... - transform it into an animated object - > - > animate <- anim_animate(plot) - You can now pass it to gganimate::animate(). - The recommended setting is nframes = 89 - > - > plotly::ggplotly(animate) - Error in pm[[2]] : subscript out of bounds - Calls: -> ggplotly.ggplot -> gg2list - Execution halted - ``` - -# ANN2 - -
- -* Version: 2.3.4 -* GitHub: https://github.com/bflammers/ANN2 -* Source code: https://github.com/cran/ANN2 -* Date/Publication: 2020-12-01 10:00:02 UTC -* Number of recursive dependencies: 52 - -Run `revdepcheck::cloud_details(, "ANN2")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(ANN2) - > - > # Only test if not on mac - > if (tolower(Sys.info()[["sysname"]]) != "darwin") { - + test_check("ANN2") - + } - ... - ── Failure ('test-plotting.R:59:3'): the reconstruction_plot.ANN() function works correctly ── - p_AE$labels$colour not equal to "col". - target is NULL, current is character - ── Failure ('test-plotting.R:77:3'): the compression_plot.ANN() function works correctly ── - p_AE$labels$colour not equal to "col". - target is NULL, current is character - - [ FAIL 5 | WARN 1 | SKIP 4 | PASS 143 ] - Error: Test failures - Execution halted - ``` - -## In both - -* checking C++ specification ... NOTE - ``` - Specified C++11: please drop specification unless essential - ``` - -* checking installed package size ... NOTE - ``` - installed size is 58.6Mb - sub-directories of 1Mb or more: - cereal 1.4Mb - libs 57.0Mb - ``` - -* checking LazyData ... NOTE - ``` - 'LazyData' is specified without a 'data' directory - ``` - -# aplot - -
- -* Version: 0.2.3 -* GitHub: https://github.com/YuLab-SMU/aplot -* Source code: https://github.com/cran/aplot -* Date/Publication: 2024-06-17 09:50:01 UTC -* Number of recursive dependencies: 53 - -Run `revdepcheck::cloud_details(, "aplot")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘aplot-Ex.R’ failed - The error most likely occurred in: - - > ### Name: insert_left - > ### Title: plot-insertion - > ### Aliases: insert_left insert_right insert_top insert_bottom - > - > ### ** Examples - > - > library(ggplot2) - ... - > ap - > ap[2, 1] <- ap[2, 1] + theme_bw() - > ap[2, 1] <- ap[2, 1] + - + aes(color = as.factor(am)) + - + scale_color_manual(values = c('steelblue', 'darkgreen')) - > ap[1, 1] <- ap[1, 1] + theme(axis.line.x.bottom=element_line()) - > ap - Error in identicalUnits(x) : object is not a unit - Calls: ... assemble_guides -> guides_build -> unit.c -> identicalUnits - Execution halted - ``` - -# applicable - -
- -* Version: 0.1.1 -* GitHub: https://github.com/tidymodels/applicable -* Source code: https://github.com/cran/applicable -* Date/Publication: 2024-04-25 00:00:04 UTC -* Number of recursive dependencies: 116 - -Run `revdepcheck::cloud_details(, "applicable")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘spelling.R’ - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(applicable) - Loading required package: ggplot2 - > - > test_check("applicable") - Loading required package: dplyr - ... - `expected` is a character vector ('percentile') - ── Failure ('test-plot.R:36:3'): output of autoplot.apd_pca is correct when options=distance are provided ── - ad_plot$labels$y (`actual`) not equal to "percentile" (`expected`). - - `actual` is NULL - `expected` is a character vector ('percentile') - - [ FAIL 3 | WARN 0 | SKIP 22 | PASS 90 ] - Error: Test failures - Execution halted - ``` - -# ASRgenomics - -
- -* Version: 1.1.4 -* GitHub: NA -* Source code: https://github.com/cran/ASRgenomics -* Date/Publication: 2024-01-29 21:20:02 UTC -* Number of recursive dependencies: 136 - -Run `revdepcheck::cloud_details(, "ASRgenomics")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘ASRgenomics-Ex.R’ failed - The error most likely occurred in: - - > ### Name: kinship.pca - > ### Title: Performs a Principal Component Analysis (PCA) based on a kinship - > ### matrix K - > ### Aliases: kinship.pca - > - > ### ** Examples - > - ... - 11. │ └─base::withCallingHandlers(...) - 12. └─ggplot2 (local) f(l = layers[[i]], d = data[[i]]) - 13. └─l$compute_geom_2(d, theme = plot$theme) - 14. └─ggplot2 (local) compute_geom_2(..., self = self) - 15. └─self$geom$use_defaults(...) - 16. └─ggplot2 (local) use_defaults(..., self = self) - 17. └─ggplot2:::check_aesthetics(new_params, nrow(data)) - 18. └─cli::cli_abort(...) - 19. └─rlang::abort(...) - Execution halted - ``` - -## In both - -* checking installed package size ... NOTE - ``` - installed size is 8.9Mb - sub-directories of 1Mb or more: - data 8.5Mb - ``` - -# autoplotly - -
- -* Version: 0.1.4 -* GitHub: https://github.com/terrytangyuan/autoplotly -* Source code: https://github.com/cran/autoplotly -* Date/Publication: 2021-04-18 06:50:11 UTC -* Number of recursive dependencies: 88 - -Run `revdepcheck::cloud_details(, "autoplotly")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘autoplotly-Ex.R’ failed - The error most likely occurred in: - - > ### Name: autoplotly - > ### Title: Automatic Visualization of Popular Statistical Results Using - > ### 'plotly.js' and 'ggplot2' - > ### Aliases: autoplotly - > - > ### ** Examples - > - > # Automatically generate interactive plot for results produced by `stats::prcomp` - > p <- autoplotly(prcomp(iris[c(1, 2, 3, 4)]), data = iris, - + colour = 'Species', label = TRUE, label.size = 3, frame = TRUE) - Error in pm[[2]] : subscript out of bounds - Calls: autoplotly ... autoplotly.default -> ggplotly -> ggplotly.ggplot -> gg2list - Execution halted - ``` - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(autoplotly) - > - > test_check("autoplotly") - [ FAIL 3 | WARN 0 | SKIP 0 | PASS 1 ] - - ══ Failed tests ════════════════════════════════════════════════════════════════ - ... - ▆ - 1. ├─autoplotly::autoplotly(...) at test_all.R:26:3 - 2. └─autoplotly:::autoplotly.default(...) - 3. ├─plotly::ggplotly(...) - 4. └─plotly:::ggplotly.ggplot(...) - 5. └─plotly::gg2list(...) - - [ FAIL 3 | WARN 0 | SKIP 0 | PASS 1 ] - Error: Test failures - Execution halted - ``` - -# autoReg - -
- -* Version: 0.3.3 -* GitHub: https://github.com/cardiomoon/autoReg -* Source code: https://github.com/cran/autoReg -* Date/Publication: 2023-11-14 05:53:27 UTC -* Number of recursive dependencies: 223 - -Run `revdepcheck::cloud_details(, "autoReg")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘autoReg-Ex.R’ failed - The error most likely occurred in: - - > ### Name: modelPlot - > ### Title: Draw coefficients/odds ratio/hazard ratio plot - > ### Aliases: modelPlot - > - > ### ** Examples - > - > fit=lm(mpg~wt*hp+am,data=mtcars) - > modelPlot(fit,widths=c(1,0,2,3)) - > modelPlot(fit,uni=TRUE,threshold=1,widths=c(1,0,2,3)) - Error in identicalUnits(x) : object is not a unit - Calls: ... assemble_guides -> guides_build -> unit.c -> identicalUnits - Execution halted - ``` - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘Automatic_Regression_Modeling.Rmd’ - ... - Species setosa (N=50) Mean ± SD 5.0 ± 0.4 - versicolor (N=50) Mean ± SD 5.9 ± 0.5 1.46 (1.24 to 1.68, p<.001) 1.49 (1.25 to 1.73, p<.001) 1.58 (1.36 to 1.80, p<.001) - virginica (N=50) Mean ± SD 6.6 ± 0.6 1.95 (1.75 to 2.14, p<.001) 2.11 (1.89 to 2.32, p<.001) 2.08 (1.88 to 2.29, p<.001) - ———————————————————————————————————————————————————————————————————————————————————————————————————————————————————————————————————————————————————————— - - > modelPlot(fit1, imputed = TRUE) - - ... - - When sourcing ‘Survival.R’: - Error: object is not a unit - Execution halted - - ‘Automatic_Regression_Modeling.Rmd’ using ‘UTF-8’... failed - ‘Bootstrap_Prediction.Rmd’ using ‘UTF-8’... OK - ‘Getting_started.Rmd’ using ‘UTF-8’... failed - ‘Statiastical_test_in_gaze.Rmd’ using ‘UTF-8’... OK - ‘Survival.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘Automatic_Regression_Modeling.Rmd’ using rmarkdown - - Quitting from lines 142-143 [unnamed-chunk-15] (Automatic_Regression_Modeling.Rmd) - Error: processing vignette 'Automatic_Regression_Modeling.Rmd' failed with diagnostics: - object is not a unit - --- failed re-building ‘Automatic_Regression_Modeling.Rmd’ - - --- re-building ‘Bootstrap_Prediction.Rmd’ using rmarkdown - ``` - -# bartMan - -
- -* Version: 0.1.0 -* GitHub: NA -* Source code: https://github.com/cran/bartMan -* Date/Publication: 2024-04-15 15:40:07 UTC -* Number of recursive dependencies: 135 - -Run `revdepcheck::cloud_details(, "bartMan")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘bartMan-Ex.R’ failed - The error most likely occurred in: - - > ### Name: plotTrees - > ### Title: Plot Trees with Customisations - > ### Aliases: plotTrees - > - > ### ** Examples - > - > if (requireNamespace("dbarts", quietly = TRUE)) { - ... - | - |======================================================================| 99% - | - |======================================================================| 100% - Extracting Observation Data... - - Displaying All Trees. - Error in names(labels) <- `*vtmp*` : attempt to set an attribute on NULL - Calls: plotTrees ... ggplot_add -> ggplot_add.new_aes -> bump_aes_labels - Execution halted - ``` - -# bayesAB - -
- -* Version: 1.1.3 -* GitHub: https://github.com/FrankPortman/bayesAB -* Source code: https://github.com/cran/bayesAB -* Date/Publication: 2021-06-25 00:50:02 UTC -* Number of recursive dependencies: 74 - -Run `revdepcheck::cloud_details(, "bayesAB")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(bayesAB) - > - > test_check("bayesAB") - [ FAIL 1 | WARN 4 | SKIP 0 | PASS 140 ] - - ══ Failed tests ════════════════════════════════════════════════════════════════ - ── Failure ('test-dists.R:34:3'): Success ────────────────────────────────────── - plotNormalInvGamma(3, 1, 1, 1)$labels$y not equal to "sig_sq". - target is NULL, current is character - - [ FAIL 1 | WARN 4 | SKIP 0 | PASS 140 ] - Error: Test failures - Execution halted - ``` - -# BayesGrowth - -
- -* Version: 1.0.0 -* GitHub: https://github.com/jonathansmart/BayesGrowth -* Source code: https://github.com/cran/BayesGrowth -* Date/Publication: 2023-11-21 18:10:08 UTC -* Number of recursive dependencies: 109 - -Run `revdepcheck::cloud_details(, "BayesGrowth")` for more info - -
- -## Newly broken - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘MCMC-example.Rmd’ - ... - > ggplot(growth_curve, aes(Age, LAA)) + geom_point(data = example_data, - + aes(Age, Length), alpha = 0.3) + geom_lineribbon(aes(ymin = .lower, - + .... [TRUNCATED] - Warning: Using `size` aesthetic for lines was deprecated in ggplot2 3.4.0. - ℹ Please use `linewidth` instead. - - When sourcing ‘MCMC-example.R’: - Error: unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, "black", TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 14, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, FALSE), list(NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), 5.5, c(5.5, 5.5, 5.5, 5.5), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.75, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, - NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, 90, NULL, c(0, 2.75, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, - Execution halted - - ‘MCMC-example.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘MCMC-example.Rmd’ using rmarkdown - ``` - -## In both - -* checking installed package size ... NOTE - ``` - installed size is 84.5Mb - sub-directories of 1Mb or more: - data 1.5Mb - libs 82.3Mb - ``` - -* checking for GNU extensions in Makefiles ... NOTE - ``` - GNU make is a SystemRequirements. - ``` - -# BayesianReasoning - -
- -* Version: 0.4.2 -* GitHub: https://github.com/gorkang/BayesianReasoning -* Source code: https://github.com/cran/BayesianReasoning -* Date/Publication: 2023-11-14 11:33:20 UTC -* Number of recursive dependencies: 107 - -Run `revdepcheck::cloud_details(, "BayesianReasoning")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(BayesianReasoning) - > - > test_check("BayesianReasoning") - - Plot created in: ./FP_10_sens_100_screening_1667_diagnostic_44.png - - ... - `expected` is a character vector ('PPV') - ── Failure ('test-PPV_heatmap.R:748:3'): NPV Plot ────────────────────────────── - p$result$labels$fill (`actual`) not identical to "NPV" (`expected`). - - `actual` is NULL - `expected` is a character vector ('NPV') - - [ FAIL 3 | WARN 56 | SKIP 4 | PASS 120 ] - Error: Test failures - Execution halted - ``` - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘PPV_NPV.Rmd’ - ... - ℹ Please consider using `annotate()` or provide this layer with data containing - a single row. - Warning in ggforce::geom_mark_rect(aes(label = paste0(translated_labels$label_PPV_NPV, : - All aesthetics have length 1, but the data has 10201 rows. - ℹ Please consider using `annotate()` or provide this layer with data containing - a single row. - - When sourcing ‘PPV_NPV.R’: - Error: object is not coercible to a unit - Execution halted - - ‘PPV_NPV.Rmd’ using ‘UTF-8’... failed - ‘introduction.Rmd’ using ‘UTF-8’... OK - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘PPV_NPV.Rmd’ using rmarkdown - ``` - -# BayesMallows - -
- -* Version: 2.2.1 -* GitHub: https://github.com/ocbe-uio/BayesMallows -* Source code: https://github.com/cran/BayesMallows -* Date/Publication: 2024-04-22 20:20:02 UTC -* Number of recursive dependencies: 82 - -Run `revdepcheck::cloud_details(, "BayesMallows")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > # This file is part of the standard setup for testthat. - > # It is recommended that you do not modify it. - > # - > # Where should you do additional test configuration? - > # Learn more about the roles of various files in: - > # * https://r-pkgs.org/testing-design.html#sec-tests-files-overview - > # * https://testthat.r-lib.org/articles/special-files.html - ... - `expected` is a character vector ('interaction(chain, cluster)') - ── Failure ('test-assess_convergence.R:217:3'): assess_convergence.BayesMallowsMixtures works ── - p$labels$colour (`actual`) not equal to "cluster" (`expected`). - - `actual` is NULL - `expected` is a character vector ('cluster') - - [ FAIL 10 | WARN 0 | SKIP 6 | PASS 432 ] - Error: Test failures - Execution halted - ``` - -## In both - -* checking installed package size ... NOTE - ``` - installed size is 22.9Mb - sub-directories of 1Mb or more: - doc 2.7Mb - libs 19.3Mb - ``` - -# bayesplot - -
- -* Version: 1.11.1 -* GitHub: https://github.com/stan-dev/bayesplot -* Source code: https://github.com/cran/bayesplot -* Date/Publication: 2024-02-15 05:30:11 UTC -* Number of recursive dependencies: 126 - -Run `revdepcheck::cloud_details(, "bayesplot")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(bayesplot) - This is bayesplot version 1.11.1 - - Online documentation and vignettes at mc-stan.org/bayesplot - - bayesplot theme set to bayesplot::theme_default() - * Does _not_ affect other ggplot2 plots - * See ?bayesplot_theme_set for details on theme setting - ... - ══ Failed tests ════════════════════════════════════════════════════════════════ - ── Failure ('test-mcmc-traces.R:55:3'): mcmc_trace options work ──────────────── - all(c("xmin", "xmax", "ymin", "ymax") %in% names(ll)) is not TRUE - - `actual`: FALSE - `expected`: TRUE - - [ FAIL 1 | WARN 1 | SKIP 73 | PASS 1024 ] - Error: Test failures - Execution halted - ``` - -## In both - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘visual-mcmc-diagnostics.Rmd’ - ... - - > schools_dat <- list(J = 8, y = c(28, 8, -3, 7, -1, - + 1, 18, 12), sigma = c(15, 10, 16, 11, 9, 11, 10, 18)) - - > fit_cp <- sampling(schools_mod_cp, data = schools_dat, - + seed = 803214055, control = list(adapt_delta = 0.9)) - - When sourcing ‘visual-mcmc-diagnostics.R’: - Error: error in evaluating the argument 'object' in selecting a method for function 'sampling': object 'schools_mod_cp' not found - Execution halted - - ‘graphical-ppcs.Rmd’ using ‘UTF-8’... OK - ‘plotting-mcmc-draws.Rmd’ using ‘UTF-8’... OK - ‘visual-mcmc-diagnostics.Rmd’ using ‘UTF-8’... failed - ``` - -* checking installed package size ... NOTE - ``` - installed size is 8.6Mb - sub-directories of 1Mb or more: - R 4.0Mb - doc 3.8Mb - ``` - -# bayestestR - -
- -* Version: 0.13.2 -* GitHub: https://github.com/easystats/bayestestR -* Source code: https://github.com/cran/bayestestR -* Date/Publication: 2024-02-12 11:40:02 UTC -* Number of recursive dependencies: 186 - -Run `revdepcheck::cloud_details(, "bayestestR")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘bayestestR-Ex.R’ failed - The error most likely occurred in: - - > ### Name: bayesfactor_restricted - > ### Title: Bayes Factors (BF) for Order Restricted Models - > ### Aliases: bayesfactor_restricted bf_restricted - > ### bayesfactor_restricted.stanreg bayesfactor_restricted.brmsfit - > ### bayesfactor_restricted.blavaan bayesfactor_restricted.emmGrid - > ### as.logical.bayesfactor_restricted - > - ... - + ) - > - > - > (b <- bayesfactor_restricted(posterior, hypothesis = hyps, prior = prior)) - Bayes Factor (Order-Restriction) - - Hypothesis P(Prior) P(Posterior) BF - A > B & B > C 0.16 0.23 1.39 - A > B & A > C 0.36 0.59 1.61 - C > A 0.46 0.34 0.742 - ``` - -## In both - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(bayestestR) - > - > test_check("bayestestR") - Starting 2 test processes - [ FAIL 3 | WARN 5 | SKIP 75 | PASS 180 ] - - ... - 14. └─brms:::eval2(call, envir = args, enclos = envir) - 15. └─base::eval(expr, envir, ...) - 16. └─base::eval(expr, envir, ...) - 17. └─rstan (local) .fun(model_code = .x1) - 18. └─rstan:::cxxfunctionplus(...) - 19. └─base::sink(type = "output") - - [ FAIL 3 | WARN 5 | SKIP 75 | PASS 180 ] - Error: Test failures - Execution halted - ``` - -# beastt - -
- -* Version: 0.0.1 -* GitHub: https://github.com/GSK-Biostatistics/beastt -* Source code: https://github.com/cran/beastt -* Date/Publication: 2024-06-20 15:50:16 UTC -* Number of recursive dependencies: 100 - -Run `revdepcheck::cloud_details(, "beastt")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘beastt-Ex.R’ failed - The error most likely occurred in: - - > ### Name: plot_dist - > ### Title: Plot Distribution - > ### Aliases: plot_dist - > - > ### ** Examples - > - > library(distributional) - ... - 12. │ └─ggplot2 (local) f(l = layers[[i]], d = data[[i]]) - 13. │ └─l$compute_geom_2(d, theme = plot$theme) - 14. │ └─ggplot2 (local) compute_geom_2(..., self = self) - 15. │ └─self$geom$use_defaults(...) - 16. └─base::.handleSimpleError(...) - 17. └─rlang (local) h(simpleError(msg, call)) - 18. └─handlers[[1L]](cnd) - 19. └─cli::cli_abort(...) - 20. └─rlang::abort(...) - Execution halted - ``` - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘binary.Rmd’ - ... - - > plot_dist(pwr_prior) - - When sourcing ‘binary.R’: - Error: Problem while setting up geom aesthetics. - ℹ Error occurred in the 1st layer. - Caused by error in `use_defaults()`: - ... - When sourcing ‘continuous.R’: - Error: Problem while setting up geom aesthetics. - ℹ Error occurred in the 1st layer. - Caused by error in `use_defaults()`: - ! unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, "black", TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), list(NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), 5.5, c(5.5, 5.5, 5.5, 5.5), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.75, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, - NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, 90, NULL, c(0, 2.75, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL - Execution halted - - ‘binary.Rmd’ using ‘UTF-8’... failed - ‘continuous.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘binary.Rmd’ using rmarkdown - ``` - -# besthr - -
- -* Version: 0.3.2 -* GitHub: NA -* Source code: https://github.com/cran/besthr -* Date/Publication: 2023-04-14 08:50:08 UTC -* Number of recursive dependencies: 67 - -Run `revdepcheck::cloud_details(, "besthr")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘besthr-Ex.R’ failed - The error most likely occurred in: - - > ### Name: plot.hrest - > ### Title: plots the 'hrest' object - > ### Aliases: plot.hrest - > - > ### ** Examples - > - > - > d1 <- make_data() - > hr_est <- estimate(d1, score, group) - > plot(hr_est) - Picking joint bandwidth of 0.68 - Error in as.unit(value) : object is not coercible to a unit - Calls: ... assemble_guides -> guides_build -> [<- -> [<-.unit -> as.unit - Execution halted - ``` - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘basic-use.Rmd’ - ... - Confidence Intervals (0.025, 0.975) - 4.16875, 8.42625 - - 100 bootstrap resamples. - > plot(hr_est_1) - Picking joint bandwidth of 0.418 - - When sourcing ‘basic-use.R’: - Error: object is not coercible to a unit - Execution halted - - ‘basic-use.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - ... - --- re-building ‘basic-use.Rmd’ using rmarkdown - - Quitting from lines 34-44 [unnamed-chunk-2] (basic-use.Rmd) - Error: processing vignette 'basic-use.Rmd' failed with diagnostics: - object is not coercible to a unit - --- failed re-building ‘basic-use.Rmd’ - - SUMMARY: processing the following file failed: - ‘basic-use.Rmd’ - - Error: Vignette re-building failed. - Execution halted - ``` - -# biclustermd - -
- -* Version: 0.2.3 -* GitHub: https://github.com/jreisner/biclustermd -* Source code: https://github.com/cran/biclustermd -* Date/Publication: 2021-06-17 15:10:06 UTC -* Number of recursive dependencies: 84 - -Run `revdepcheck::cloud_details(, "biclustermd")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(biclustermd) - Loading required package: ggplot2 - Loading required package: tidyr - - Attaching package: 'tidyr' - - ... - ── Failure ('test-autoplot_biclustermd.R:6:3'): autoplot_biclustermd() correctly plots cluster lines ── - ap$data[[3]]$xintercept[-1] not equal to cumsum(colSums(sbc$P)) + 0.5. - Classes differ: 'mapped_discrete'/'numeric' is not 'numeric' - ── Failure ('test-autoplot_biclustermd.R:7:3'): autoplot_biclustermd() correctly plots cluster lines ── - ap$data[[4]]$yintercept[-1] not equal to cumsum(colSums(sbc$Q)) + 0.5. - Classes differ: 'mapped_discrete'/'numeric' is not 'numeric' - - [ FAIL 2 | WARN 0 | SKIP 0 | PASS 66 ] - Error: Test failures - Execution halted - ``` - -## In both - -* checking dependencies in R code ... NOTE - ``` - Namespace in Imports field not imported from: ‘nycflights13’ - All declared Imports should be used. - ``` - -# biodosetools - -
- -* Version: 3.6.1 -* GitHub: https://github.com/biodosetools-team/biodosetools -* Source code: https://github.com/cran/biodosetools -* Date/Publication: 2022-11-16 16:00:02 UTC -* Number of recursive dependencies: 121 - -Run `revdepcheck::cloud_details(, "biodosetools")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(biodosetools) - > - > test_check("biodosetools") - ! Problem with `glm()` -> constraint ML optimization will be used instead - ! Problem with `glm()` -> constraint ML optimization will be used instead - number of iterations= 43 - ... - actual | expected - [2] "Estimation" | "Estimation" [2] - [3] "Dose (Gy)" | "Dose (Gy)" [3] - [4] "Translocations/cells" | "Translocations/cells" [4] - - "yield_low" [5] - - "yield_upp" [6] - - [ FAIL 4 | WARN 0 | SKIP 1 | PASS 232 ] - Error: Test failures - Execution halted - ``` - -# boxly - -
- -* Version: 0.1.1 -* GitHub: https://github.com/Merck/boxly -* Source code: https://github.com/cran/boxly -* Date/Publication: 2023-10-24 02:40:02 UTC -* Number of recursive dependencies: 91 - -Run `revdepcheck::cloud_details(, "boxly")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > # This file is part of the standard setup for testthat. - > # It is recommended that you do not modify it. - > # - > # Where should you do additional test configuration? - > # Learn more about the roles of various files in: - > # * https://r-pkgs.org/tests.html - > # * https://testthat.r-lib.org/reference/test_package.html#special-files - ... - 16. ├─plotly::add_trace(...) - 17. │ └─plotly::add_data(p, data) - 18. │ └─plotly:::is.plotly(p) - 19. ├─plotly::ggplotly(p, tooltip = "text", dynamicTicks = TRUE) - 20. └─plotly:::ggplotly.ggplot(p, tooltip = "text", dynamicTicks = TRUE) - 21. └─plotly::gg2list(...) - - [ FAIL 2 | WARN 0 | SKIP 0 | PASS 25 ] - Error: Test failures - Execution halted - ``` - -# braidReports - -
- -* Version: 0.5.4 -* GitHub: NA -* Source code: https://github.com/cran/braidReports -* Date/Publication: 2021-01-05 18:20:09 UTC -* Number of recursive dependencies: 30 - -Run `revdepcheck::cloud_details(, "braidReports")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘braidReports-Ex.R’ failed - The error most likely occurred in: - - > ### Name: makeBRAIDreport - > ### Title: Make a BRAID Report Page - > ### Aliases: makeBRAIDreport - > ### Keywords: hplot - > - > ### ** Examples - > - ... - 22. │ └─grid::convertUnit(short, "cm", valueOnly = TRUE) - 23. │ ├─grid:::upgradeUnit(x) - 24. │ └─grid:::upgradeUnit.default(x) - 25. │ └─base::stop("Not a unit object") - 26. └─base::.handleSimpleError(``, "Not a unit object", base::quote(upgradeUnit.default(x))) - 27. └─rlang (local) h(simpleError(msg, call)) - 28. └─handlers[[1L]](cnd) - 29. └─cli::cli_abort(...) - 30. └─rlang::abort(...) - Execution halted - ``` - -# breathtestcore - -
- -* Version: 0.8.7 -* GitHub: https://github.com/dmenne/breathtestcore -* Source code: https://github.com/cran/breathtestcore -* Date/Publication: 2024-01-24 15:02:47 UTC -* Number of recursive dependencies: 130 - -Run `revdepcheck::cloud_details(, "breathtestcore")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘test-all.R’ - Running the tests in ‘tests/test-all.R’ failed. - Complete output: - > library(testthat) - > - > options(Ncpus = parallelly::availableCores(omit = 1)) - > test_check("breathtestcore") - Loading required package: breathtestcore - Starting 1 test process - [ FAIL 3 | WARN 11 | SKIP 4 | PASS 356 ] - ... - `expected`: 10 - ── Failure ('test_plot_breathtestfit.R:81:3'): Plot multiple groups data only (no fit) ── - length(p) (`actual`) not equal to length(ggplot()) (`expected`). - - `actual`: 11 - `expected`: 10 - - [ FAIL 3 | WARN 11 | SKIP 4 | PASS 356 ] - Error: Test failures - Execution halted - ``` - -# brolgar - -
- -* Version: 1.0.1 -* GitHub: https://github.com/njtierney/brolgar -* Source code: https://github.com/cran/brolgar -* Date/Publication: 2024-05-10 14:50:34 UTC -* Number of recursive dependencies: 101 - -Run `revdepcheck::cloud_details(, "brolgar")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘brolgar-Ex.R’ failed - The error most likely occurred in: - - > ### Name: facet_sample - > ### Title: Facet data into groups to facilitate exploration - > ### Aliases: facet_sample - > - > ### ** Examples - > - > library(ggplot2) - > ggplot(heights, - + aes(x = year, - + y = height_cm, - + group = country)) + - + geom_line() + - + facet_sample() - Error in if (params$as.table) { : argument is of length zero - Calls: ... -> setup -> -> compute_layout - Execution halted - ``` - -## In both - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘exploratory-modelling.Rmd’ - ... - + 0) - Warning in is.na(non_null_default_aes[[aes_param_name]]) : - is.na() applied to non-(list or vector) of type 'language' - - When sourcing ‘exploratory-modelling.R’: - Error: ℹ In index: 1. - Caused by error in `aes_param_name %in% names(non_null_default_aes) && is.na(non_null_default_aes[[ - ... - Error: argument is of length zero - Execution halted - - ‘exploratory-modelling.Rmd’ using ‘UTF-8’... failed - ‘finding-features.Rmd’ using ‘UTF-8’... failed - ‘getting-started.Rmd’ using ‘UTF-8’... failed - ‘id-interesting-obs.Rmd’ using ‘UTF-8’... OK - ‘longitudinal-data-structures.Rmd’ using ‘UTF-8’... OK - ‘mixed-effects-models.Rmd’ using ‘UTF-8’... failed - ‘visualisation-gallery.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘exploratory-modelling.Rmd’ using rmarkdown - - Quitting from lines 47-56 [use-gg-highlight] (exploratory-modelling.Rmd) - Error: processing vignette 'exploratory-modelling.Rmd' failed with diagnostics: - ℹ In index: 1. - Caused by error in `aes_param_name %in% names(non_null_default_aes) && is.na(non_null_default_aes[[ - aes_param_name]])`: - ! 'length = 2' in coercion to 'logical(1)' - --- failed re-building ‘exploratory-modelling.Rmd’ - - --- re-building ‘finding-features.Rmd’ using rmarkdown - ``` - -# cartograflow - -
- -* Version: 1.0.5 -* GitHub: https://github.com/fbahoken/cartogRaflow -* Source code: https://github.com/cran/cartograflow -* Date/Publication: 2023-10-17 22:40:21 UTC -* Number of recursive dependencies: 102 - -Run `revdepcheck::cloud_details(, "cartograflow")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘cartograflow-Ex.R’ failed - The error most likely occurred in: - - > ### Name: flowgini - > ### Title: Analysis of flow concentration (Gini coefficient) - > ### Aliases: flowgini - > - > ### ** Examples - > - > library(cartograflow) - ... - ℹ Use `flowcum` instead. - Warning: Use of `x$linkcum` is discouraged. - ℹ Use `linkcum` instead. - Warning: Use of `x$flowcum` is discouraged. - ℹ Use `flowcum` instead. - Warning: Use of `x$flowcum` is discouraged. - ℹ Use `flowcum` instead. - Error in pm[[2]] : subscript out of bounds - Calls: flowgini ... %>% -> layout -> ggplotly -> ggplotly.ggplot -> gg2list - Execution halted - ``` - -# cartographr - -
- -* Version: 0.2.2 -* GitHub: https://github.com/da-wi/cartographr -* Source code: https://github.com/cran/cartographr -* Date/Publication: 2024-06-28 14:50:09 UTC -* Number of recursive dependencies: 99 - -Run `revdepcheck::cloud_details(, "cartographr")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > # This file is part of the standard setup for testthat. - > # It is recommended that you do not modify it. - > # - > # Where should you do additional test configuration? - > # Learn more about the roles of various files in: - > # * https://r-pkgs.org/testing-design.html#sec-tests-files-overview - > # * https://testthat.r-lib.org/articles/special-files.html - ... - 21. │ └─base::stop(...) - 22. └─base::.handleSimpleError(...) - 23. └─rlang (local) h(simpleError(msg, call)) - 24. └─handlers[[1L]](cnd) - 25. └─cli::cli_abort(...) - 26. └─rlang::abort(...) - - [ FAIL 1 | WARN 0 | SKIP 0 | PASS 106 ] - Error: Test failures - Execution halted - ``` - -## In both - -* checking installed package size ... NOTE - ``` - installed size is 5.3Mb - sub-directories of 1Mb or more: - data 3.5Mb - ``` - -# cats - -
- -* Version: 1.0.2 -* GitHub: NA -* Source code: https://github.com/cran/cats -* Date/Publication: 2022-03-11 10:20:07 UTC -* Number of recursive dependencies: 83 - -Run `revdepcheck::cloud_details(, "cats")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘cats-Ex.R’ failed - The error most likely occurred in: - - > ### Name: trial_ocs - > ### Title: Calculates the operating characteristics of the cohort trial - > ### Aliases: trial_ocs - > - > ### ** Examples - > - > - ... - + safety_prob = safety_prob, Bayes_Sup1 = Bayes_Sup1, Bayes_Sup2 = Bayes_Sup2, - + cohort_offset = cohort_offset, sr_first_pos = sr_first_pos, - + missing_prob = missing_prob, cohort_fixed = cohort_fixed, accrual_type = accrual_type, - + accrual_param = accrual_param, hist_lag = hist_lag, analysis_times = analysis_times, - + time_trend = time_trend, cohorts_start = cohorts_start, cohorts_sim = cohorts_sim, - + iter = 2, coresnum = 1, save = FALSE, ret_list = TRUE, plot_ocs = TRUE - + ) - Error in pm[[2]] : subscript out of bounds - Calls: trial_ocs -> -> ggplotly.ggplot -> gg2list - Execution halted - ``` - -## In both - -* checking dependencies in R code ... NOTE - ``` - Namespaces in Imports field not imported from: - ‘epitools’ ‘forcats’ ‘purrr’ - All declared Imports should be used. - ``` - -# cheem - -
- -* Version: 0.4.0.0 -* GitHub: https://github.com/nspyrison/cheem -* Source code: https://github.com/cran/cheem -* Date/Publication: 2023-11-08 21:30:02 UTC -* Number of recursive dependencies: 153 - -Run `revdepcheck::cloud_details(, "cheem")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(cheem) - -------------------------------------------------------- - cheem --- version 0.4.0.0 - Please share bugs, suggestions, and feature requests at: - https://github.com/nspyrison/cheem/issues/ - -------------------------------------------------------- - ... - 13. │ ├─utils::modifyList(x %||% list(), y %||% list(), ...) - 14. │ │ └─base::stopifnot(is.list(x), is.list(val)) - 15. │ └─x %||% list() - 16. ├─plotly::ggplotly(...) - 17. └─plotly:::ggplotly.ggplot(...) - 18. └─plotly::gg2list(...) - - [ FAIL 1 | WARN 0 | SKIP 0 | PASS 10 ] - Error: Test failures - Execution halted - ``` - -## In both - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘getting-started-with-cheem.Rmd’ - ... - - > knitr::opts_chunk$set(echo = TRUE, include = TRUE, - + results = "show", eval = FALSE, message = FALSE, warning = FALSE, - + error = FALSE, co .... [TRUNCATED] - - > knitr::include_graphics("../inst/shiny_apps/cheem/www/lime_nonlinear.png") - - When sourcing ‘getting-started-with-cheem.R’: - Error: Cannot find the file(s): "../inst/shiny_apps/cheem/www/lime_nonlinear.png" - Execution halted - - ‘getting-started-with-cheem.Rmd’ using ‘UTF-8’... failed - ``` - -# chillR - -
- -* Version: 0.75 -* GitHub: NA -* Source code: https://github.com/cran/chillR -* Date/Publication: 2023-11-27 22:20:02 UTC -* Number of recursive dependencies: 139 - -Run `revdepcheck::cloud_details(, "chillR")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘chillR-Ex.R’ failed - The error most likely occurred in: - - > ### Name: plot_scenarios - > ### Title: Plot historic and future scenarios for climate-related metrics - > ### ('ggplot2' version) - > ### Aliases: plot_scenarios - > - > ### ** Examples - > - ... - > - > # Plot the climate scenarios - > - > plot_scenarios(climate_scenario_list, metric = 'Chill_Portions', - + add_historic = TRUE, size = 2, shape = 3, color = 'blue', - + outlier_shape = 12, historic_color = 'skyblue', - + group_by = c("Year", "Scenario")) - Error in identicalUnits(x) : object is not a unit - Calls: ... assemble_guides -> guides_build -> unit.c -> identicalUnits - Execution halted - ``` - -# chronicle - -
- -* Version: 0.3 -* GitHub: NA -* Source code: https://github.com/cran/chronicle -* Date/Publication: 2021-06-25 05:00:02 UTC -* Number of recursive dependencies: 146 - -Run `revdepcheck::cloud_details(, "chronicle")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘chronicle-Ex.R’ failed - The error most likely occurred in: - - > ### Name: make_barplot - > ### Title: Create a bar plot from a data frame through ggplotly - > ### Aliases: make_barplot - > - > ### ** Examples - > - > make_barplot(dt = iris, bars = 'Species', value = 'Sepal.Length') - Error in pm[[2]] : subscript out of bounds - Calls: make_barplot -> -> ggplotly.ggplot -> gg2list - Execution halted - ``` - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘chronicle.Rmd’ - ... - + filename = "quick_demo", title = "A quick chronicle demo", - + author = .... [TRUNCATED] - - Quitting from lines 34-46 [unnamed-chunk-3] (quick_demo.Rmd) - - When sourcing ‘chronicle.R’: - Error: ℹ In index: 1. - Caused by error in `pm[[2]]`: - ! subscript out of bounds - Execution halted - - ‘chronicle.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - ... - --- re-building ‘chronicle.Rmd’ using rmarkdown - - Quitting from lines 38-67 [unnamed-chunk-3] (chronicle.Rmd) - Error: processing vignette 'chronicle.Rmd' failed with diagnostics: - ℹ In index: 1. - Caused by error in `pm[[2]]`: - ! subscript out of bounds - --- failed re-building ‘chronicle.Rmd’ - - SUMMARY: processing the following file failed: - ‘chronicle.Rmd’ - - Error: Vignette re-building failed. - Execution halted - ``` - -## In both - -* checking dependencies in R code ... NOTE - ``` - Namespaces in Imports field not imported from: - ‘DT’ ‘dplyr’ ‘prettydoc’ ‘rmdformats’ ‘skimr’ - All declared Imports should be used. - ``` - -# circhelp - -
- -* Version: 1.1 -* GitHub: https://github.com/achetverikov/circhelp -* Source code: https://github.com/cran/circhelp -* Date/Publication: 2024-07-04 17:10:02 UTC -* Number of recursive dependencies: 106 - -Run `revdepcheck::cloud_details(, "circhelp")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘circhelp-Ex.R’ failed - The error most likely occurred in: - - > ### Name: remove_cardinal_biases - > ### Title: Remove cardinal biases - > ### Aliases: remove_cardinal_biases - > - > ### ** Examples - > - > - > # Data in orientation domain from Pascucci et al. (2019, PLOS Bio), - > # https://doi.org/10.5281/zenodo.2544946 - > - > ex_data <- Pascucci_et_al_2019_data[observer == 4, ] - > remove_cardinal_biases(ex_data$err, ex_data$orientation, plots = "show") - Error in as.unit(value) : object is not coercible to a unit - Calls: remove_cardinal_biases ... assemble_guides -> guides_build -> [<- -> [<-.unit -> as.unit - Execution halted - ``` - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘cardinal_biases.Rmd’ - ... - + 90)) + .... [TRUNCATED] - - > ex_subj_data <- data[observer == 4, ] - - > res <- remove_cardinal_biases(ex_subj_data$err, ex_subj_data$orientation, - + plots = "show") - - When sourcing ‘cardinal_biases.R’: - Error: object is not coercible to a unit - Execution halted - - ‘cardinal_biases.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘cardinal_biases.Rmd’ using rmarkdown - ``` - -# clifro - -
- -* Version: 3.2-5 -* GitHub: https://github.com/ropensci/clifro -* Source code: https://github.com/cran/clifro -* Date/Publication: 2021-05-24 05:50:02 UTC -* Number of recursive dependencies: 84 - -Run `revdepcheck::cloud_details(, "clifro")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘spelling.R’ - Running ‘test-all.R’ - Running the tests in ‘tests/test-all.R’ failed. - Complete output: - > library(testthat) - > library(clifro) - > - > test_check("clifro") - [ FAIL 1 | WARN 1 | SKIP 4 | PASS 10 ] - - ... - • On CRAN (4): 'test-cf_find_station.R:4:3', 'test-cf_last_query.R:4:3', - 'test-cf_query.R:4:3', 'test-cf_station.R:4:3' - - ══ Failed tests ════════════════════════════════════════════════════════════════ - ── Failure ('test-windrose.R:15:3'): windrose ────────────────────────────────── - tt$labels inherits from `'NULL'` not `'character'`. - - [ FAIL 1 | WARN 1 | SKIP 4 | PASS 10 ] - Error: Test failures - Execution halted - ``` - -# clinDataReview - -
- -* Version: 1.6.1 -* GitHub: https://github.com/openanalytics/clinDataReview -* Source code: https://github.com/cran/clinDataReview -* Date/Publication: 2024-06-18 09:10:05 UTC -* Number of recursive dependencies: 130 - -Run `revdepcheck::cloud_details(, "clinDataReview")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘clinDataReview-Ex.R’ failed - The error most likely occurred in: - - > ### Name: scatterplotClinData - > ### Title: Scatterplot of variables of interest for clinical data - > ### visualization. - > ### Aliases: scatterplotClinData - > - > ### ** Examples - > - ... - + data = dataPlot, - + xVar = "ADY", - + yVar = "LBSTRESN", - + aesPointVar = list(color = "TRTP", fill = "TRTP"), - + aesLineVar = list(group = "USUBJID", color = "TRTP"), - + labelVars = labelVars - + ) - Error in pm[[2]] : subscript out of bounds - Calls: scatterplotClinData -> ggplotly -> ggplotly.ggplot -> gg2list - Execution halted - ``` - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(clinDataReview) - > - > test_check("clinDataReview") - adding: report.html (deflated 63%) - adding: report_dependencies13af6c90fb24/ (stored 0%) - adding: report_dependencies13af6c90fb24/file13af13ea2d3b.html (deflated 8%) - ... - Backtrace: - ▆ - 1. └─clinDataReview::scatterplotClinData(...) at test_scatterplotClinData.R:1001:3 - 2. ├─plotly::ggplotly(p = gg, width = width, height = height, tooltip = if (!is.null(hoverVars)) "text") - 3. └─plotly:::ggplotly.ggplot(...) - 4. └─plotly::gg2list(...) - - [ FAIL 31 | WARN 0 | SKIP 31 | PASS 466 ] - Error: Test failures - Execution halted - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - ... - --- re-building ‘clinDataReview-dataPreprocessing.Rmd’ using rmarkdown - --- finished re-building ‘clinDataReview-dataPreprocessing.Rmd’ - - --- re-building ‘clinDataReview-dataVisualization.Rmd’ using rmarkdown - - Quitting from lines 167-208 [timeProfiles] (clinDataReview-dataVisualization.Rmd) - Error: processing vignette 'clinDataReview-dataVisualization.Rmd' failed with diagnostics: - subscript out of bounds - ... - --- failed re-building ‘clinDataReview-dataVisualization.Rmd’ - - --- re-building ‘clinDataReview-reporting.Rmd’ using rmarkdown - --- finished re-building ‘clinDataReview-reporting.Rmd’ - - SUMMARY: processing the following file failed: - ‘clinDataReview-dataVisualization.Rmd’ - - Error: Vignette re-building failed. - Execution halted - ``` - -## In both - -* checking installed package size ... NOTE - ``` - installed size is 5.8Mb - sub-directories of 1Mb or more: - doc 4.3Mb - ``` - -# clinUtils - -
- -* Version: 0.2.0 -* GitHub: https://github.com/openanalytics/clinUtils -* Source code: https://github.com/cran/clinUtils -* Date/Publication: 2024-05-17 14:50:06 UTC -* Number of recursive dependencies: 120 - -Run `revdepcheck::cloud_details(, "clinUtils")` for more info - -
- -## Newly broken - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘clinUtils-vignette.Rmd’ - ... - - layout - - - > listPlotsInteractiveLB <- sapply(listPlotsLB, function(ggplot) ggplotly(ggplot) %>% - + partial_bundle(), simplify = FALSE) - - When sourcing ‘clinUtils-vignette.R’: - Error: subscript out of bounds - Execution halted - - ‘clinUtils-vignette.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘clinUtils-vignette.Rmd’ using rmarkdown - ``` - -## Newly fixed - -* checking running R code from vignettes ... WARNING - ``` - Errors in running code in vignettes: - when running code in ‘clinUtils-vignette.Rmd’ - ... - - - - - - Quitting from lines 2-4 [lab-hist-interactive1] - - When sourcing ‘clinUtils-vignette.R’: - Error: there is no package called 'webshot' - Execution halted - - ‘clinUtils-vignette.Rmd’ using ‘UTF-8’... failed - ``` - -## In both - -* checking installed package size ... NOTE - ``` - installed size is 7.7Mb - sub-directories of 1Mb or more: - doc 6.5Mb - ``` - -# CohortPlat - -
- -* Version: 1.0.5 -* GitHub: NA -* Source code: https://github.com/cran/CohortPlat -* Date/Publication: 2022-02-14 09:30:02 UTC -* Number of recursive dependencies: 82 - -Run `revdepcheck::cloud_details(, "CohortPlat")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘CohortPlat-Ex.R’ failed - The error most likely occurred in: - - > ### Name: plot_trial - > ### Title: Plots the cohort trial study overview given stage data. - > ### Aliases: plot_trial - > - > ### ** Examples - > - > - ... - + stage_data = stage_data, cohort_random = cohort_random, cohorts_max = cohorts_max, - + sr_drugs_pos = sr_drugs_pos, target_rr = target_rr, sharing_type = sharing_type, - + safety_prob = safety_prob, Bayes_Sup = Bayes_Sup, prob_rr_transform = prob_rr_transform, - + cohort_offset = cohort_offset, Bayes_Fut = Bayes_Fut, sr_first_pos = sr_first_pos - + ) - > - > plot_trial(res_list, unit = "n") - Error in pm[[2]] : subscript out of bounds - Calls: plot_trial -> -> ggplotly.ggplot -> gg2list - Execution halted - ``` - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘my-vignette.Rmd’ - ... - - > set.seed(50) - - > ocs1 <- trial_ocs(n_int = n_int, n_fin = n_fin, rr_comb = rr_comb, - + rr_mono = rr_mono, rr_back = rr_back, rr_plac = rr_plac, - + rr_transfo .... [TRUNCATED] - - When sourcing ‘my-vignette.R’: - Error: subscript out of bounds - Execution halted - - ‘my-vignette.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - ... - --- re-building ‘my-vignette.Rmd’ using rmarkdown - - Quitting from lines 1043-1073 [unnamed-chunk-20] (my-vignette.Rmd) - Error: processing vignette 'my-vignette.Rmd' failed with diagnostics: - subscript out of bounds - --- failed re-building ‘my-vignette.Rmd’ - - SUMMARY: processing the following file failed: - ‘my-vignette.Rmd’ - - Error: Vignette re-building failed. - Execution halted - ``` - -# CoreMicrobiomeR - -
- -* Version: 0.1.0 -* GitHub: NA -* Source code: https://github.com/cran/CoreMicrobiomeR -* Date/Publication: 2024-04-03 20:03:02 UTC -* Number of recursive dependencies: 91 - -Run `revdepcheck::cloud_details(, "CoreMicrobiomeR")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘CoreMicrobiomeR-Ex.R’ failed - The error most likely occurred in: - - > ### Name: group_bar_plots - > ### Title: Grouped Bar Plots Based on Sample Size - > ### Aliases: group_bar_plots - > - > ### ** Examples - > - > #To run input data - ... - + top_percentage = 10 # Adjust the percentage as needed for core/non-core OTUs - + ) - Warning encountered during diversity analysis:you have empty rows: their dissimilarities may be - meaningless in method “bray” - > #To run grouped bar plot function - > plot_group_bar <- group_bar_plots(core_1$final_otu_table_bef_filter, - + core_1$final_otu_aft_filter, 10) - Error in pm[[2]] : subscript out of bounds - Calls: group_bar_plots -> -> ggplotly.ggplot -> gg2list - Execution halted - ``` - -# correlationfunnel - -
- -* Version: 0.2.0 -* GitHub: https://github.com/business-science/correlationfunnel -* Source code: https://github.com/cran/correlationfunnel -* Date/Publication: 2020-06-09 04:40:03 UTC -* Number of recursive dependencies: 116 - -Run `revdepcheck::cloud_details(, "correlationfunnel")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(dplyr) - - Attaching package: 'dplyr' - - The following object is masked from 'package:testthat': - - ... - ▆ - 1. ├─correlationfunnel::plot_correlation_funnel(...) at test-plot_correlation_funnel.R:23:1 - 2. └─correlationfunnel:::plot_correlation_funnel.data.frame(...) - 3. ├─plotly::ggplotly(g, tooltip = "text") - 4. └─plotly:::ggplotly.ggplot(g, tooltip = "text") - 5. └─plotly::gg2list(...) - - [ FAIL 1 | WARN 3 | SKIP 0 | PASS 17 ] - Error: Test failures - Execution halted - ``` - -## In both - -* checking dependencies in R code ... NOTE - ``` - Namespace in Imports field not imported from: ‘utils’ - All declared Imports should be used. - ``` - -# corrViz - -
- -* Version: 0.1.0 -* GitHub: NA -* Source code: https://github.com/cran/corrViz -* Date/Publication: 2023-06-30 11:40:07 UTC -* Number of recursive dependencies: 139 - -Run `revdepcheck::cloud_details(, "corrViz")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘corrViz-Ex.R’ failed - The error most likely occurred in: - - > ### Name: animSolar - > ### Title: animSolar - > ### Aliases: animSolar - > - > ### ** Examples - > - > cm <- cor(mtcars) - ... - All aesthetics have length 1, but the data has 250 rows. - ℹ Please consider using `annotate()` or provide this layer with data containing - a single row. - Warning in geom_text(data = solar_system, aes(x = 0, y = 0, label = sun), : - All aesthetics have length 1, but the data has 250 rows. - ℹ Please consider using `annotate()` or provide this layer with data containing - a single row. - Error in pm[[2]] : subscript out of bounds - Calls: animSolar -> ggplotly -> ggplotly.ggplot -> gg2list - Execution halted - ``` - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘corrViz.Rmd’ - ... - > library(corrViz) - - > cm <- cor(mtcars) - - > corrHeatmap(mat = cm, display = "all", reorder = TRUE, - + pal = colorRampPalette(c("darkblue", "white", "darkred"))(100)) - - When sourcing ‘corrViz.R’: - Error: subscript out of bounds - Execution halted - - ‘corrViz.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - ... - --- re-building ‘corrViz.Rmd’ using rmarkdown - - Quitting from lines 76-81 [heatmap] (corrViz.Rmd) - Error: processing vignette 'corrViz.Rmd' failed with diagnostics: - subscript out of bounds - --- failed re-building ‘corrViz.Rmd’ - - SUMMARY: processing the following file failed: - ‘corrViz.Rmd’ - - Error: Vignette re-building failed. - Execution halted - ``` - -## In both - -* checking installed package size ... NOTE - ``` - installed size is 7.2Mb - sub-directories of 1Mb or more: - doc 6.7Mb - ``` - -# countfitteR - -
- -* Version: 1.4 -* GitHub: https://github.com/BioGenies/countfitteR -* Source code: https://github.com/cran/countfitteR -* Date/Publication: 2020-09-30 21:30:02 UTC -* Number of recursive dependencies: 93 - -Run `revdepcheck::cloud_details(, "countfitteR")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘spelling.R’ - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(countfitteR) - > - > test_check("countfitteR") - [ FAIL 1 | WARN 6 | SKIP 0 | PASS 34 ] - - ══ Failed tests ════════════════════════════════════════════════════════════════ - ── Failure ('testing.R:45:3'): plot_fit ──────────────────────────────────────── - p$labels[[1]] not equal to "x". - target is NULL, current is character - - [ FAIL 1 | WARN 6 | SKIP 0 | PASS 34 ] - Error: Test failures - Execution halted - ``` - -# covidcast - -
- -* Version: 0.5.2 -* GitHub: https://github.com/cmu-delphi/covidcast -* Source code: https://github.com/cran/covidcast -* Date/Publication: 2023-07-12 23:40:06 UTC -* Number of recursive dependencies: 93 - -Run `revdepcheck::cloud_details(, "covidcast")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(covidcast) - We encourage COVIDcast API users to register on our mailing list: - https://lists.andrew.cmu.edu/mailman/listinfo/delphi-covidcast-api - We'll send announcements about new data sources, package updates, - server maintenance, and new features. - > - ... - • plot/default-county-choropleth.svg - • plot/default-hrr-choropleth-with-include.svg - • plot/default-msa-choropleth-with-include.svg - • plot/default-state-choropleth-with-include.svg - • plot/default-state-choropleth-with-range.svg - • plot/state-choropleth-with-no-metadata.svg - • plot/state-line-graph-with-range.svg - • plot/state-line-graph-with-stderrs.svg - Error: Test failures - Execution halted - ``` - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘plotting-signals.Rmd’ - ... - > knitr::opts_chunk$set(fig.width = 6, fig.height = 4) - - > plot(dv) - - When sourcing ‘plotting-signals.R’: - Error: Problem while setting up geom aesthetics. - ℹ Error occurred in the 6th layer. - Caused by error in `$<-.data.frame`: - ! replacement has 1 row, data has 0 - Execution halted - - ‘correlation-utils.Rmd’ using ‘UTF-8’... OK - ‘covidcast.Rmd’ using ‘UTF-8’... OK - ‘external-data.Rmd’ using ‘UTF-8’... OK - ‘multi-signals.Rmd’ using ‘UTF-8’... OK - ‘plotting-signals.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘correlation-utils.Rmd’ using rmarkdown - --- finished re-building ‘correlation-utils.Rmd’ - - --- re-building ‘covidcast.Rmd’ using rmarkdown - ``` - -## In both - -* checking data for non-ASCII characters ... NOTE - ``` - Note: found 20 marked UTF-8 strings - ``` - -# crosshap - -
- -* Version: 1.4.0 -* GitHub: https://github.com/jacobimarsh/crosshap -* Source code: https://github.com/cran/crosshap -* Date/Publication: 2024-03-31 15:40:02 UTC -* Number of recursive dependencies: 117 - -Run `revdepcheck::cloud_details(, "crosshap")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘crosshap-Ex.R’ failed - The error most likely occurred in: - - > ### Name: build_bot_halfeyeplot - > ### Title: Bot hap-pheno raincloud plot - > ### Aliases: build_bot_halfeyeplot - > - > ### ** Examples - > - > - ... - 12. │ └─ggplot2 (local) f(l = layers[[i]], d = data[[i]]) - 13. │ └─l$compute_geom_2(d, theme = plot$theme) - 14. │ └─ggplot2 (local) compute_geom_2(..., self = self) - 15. │ └─self$geom$use_defaults(...) - 16. └─base::.handleSimpleError(...) - 17. └─rlang (local) h(simpleError(msg, call)) - 18. └─handlers[[1L]](cnd) - 19. └─cli::cli_abort(...) - 20. └─rlang::abort(...) - Execution halted - ``` - -# ctrialsgov - -
- -* Version: 0.2.5 -* GitHub: NA -* Source code: https://github.com/cran/ctrialsgov -* Date/Publication: 2021-10-18 16:00:02 UTC -* Number of recursive dependencies: 100 - -Run `revdepcheck::cloud_details(, "ctrialsgov")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(ctrialsgov) - > - > test_check("ctrialsgov") - [NCT04553939] ible Local Advanved |Bladder| Cancer - [NCT03517995] of Sulforaphane in |Bladder| Cancer Chemoprevent - [NCT04210479] Comparison of |Bladder| Filling vs. Non-Fil - ... - ▆ - 1. ├─ctrialsgov::ctgov_to_plotly(p) at test-plot.R:12:3 - 2. └─ctrialsgov:::ctgov_to_plotly.ctgov_bar_plot(p) - 3. ├─plotly::ggplotly(p, tooltip = "text") - 4. └─plotly:::ggplotly.ggplot(p, tooltip = "text") - 5. └─plotly::gg2list(...) - - [ FAIL 1 | WARN 6 | SKIP 0 | PASS 43 ] - Error: Test failures - Execution halted - ``` - -## In both - -* checking data for non-ASCII characters ... NOTE - ``` - Note: found 1350 marked UTF-8 strings - ``` - -# cubble - -
- -* Version: 0.3.1 -* GitHub: https://github.com/huizezhang-sherry/cubble -* Source code: https://github.com/cran/cubble -* Date/Publication: 2024-07-02 17:20:03 UTC -* Number of recursive dependencies: 144 - -Run `revdepcheck::cloud_details(, "cubble")` for more info - -
- -## Newly broken - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘cb5match.Rmd’ - ... - > p2 <- ggplot(res_tm_long, aes(x = date, y = matched, - + group = type, color = type)) + geom_line() + facet_wrap(vars(group)) + - + scale_colo .... [TRUNCATED] - - > (p1 | p2) + patchwork::plot_layout(guides = "collect") + - + plot_annotation(tag_levels = "a") & theme(legend.position = "bottom") - - ... - Error: subscript out of bounds - Execution halted - - ‘cb1class.Rmd’ using ‘UTF-8’... OK - ‘cb2create.Rmd’ using ‘UTF-8’... OK - ‘cb3tsibblesf.Rmd’ using ‘UTF-8’... OK - ‘cb4glyph.Rmd’ using ‘UTF-8’... OK - ‘cb5match.Rmd’ using ‘UTF-8’... failed - ‘cb6interactive.Rmd’ using ‘UTF-8’... failed - ‘cb7misc.Rmd’ using ‘UTF-8’... OK - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘cb1class.Rmd’ using rmarkdown - --- finished re-building ‘cb1class.Rmd’ - - --- re-building ‘cb2create.Rmd’ using rmarkdown - --- finished re-building ‘cb2create.Rmd’ - - --- re-building ‘cb3tsibblesf.Rmd’ using rmarkdown - --- finished re-building ‘cb3tsibblesf.Rmd’ - - --- re-building ‘cb4glyph.Rmd’ using rmarkdown - ``` - -## In both - -* checking installed package size ... NOTE - ``` - installed size is 5.6Mb - sub-directories of 1Mb or more: - data 3.0Mb - doc 1.4Mb - ``` - -# deeptime - -
- -* Version: 1.1.1 -* GitHub: https://github.com/willgearty/deeptime -* Source code: https://github.com/cran/deeptime -* Date/Publication: 2024-03-08 17:10:10 UTC -* Number of recursive dependencies: 182 - -Run `revdepcheck::cloud_details(, "deeptime")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘deeptime-Ex.R’ failed - The error most likely occurred in: - - > ### Name: gggeo_scale_old - > ### Title: Add a geologic scale on top of ggplots - > ### Aliases: gggeo_scale_old - > ### Keywords: internal - > - > ### ** Examples - > - ... - + geom_point(aes(y = runif(1000, .5, 8), x = runif(1000, 0, 1000))) + - + scale_x_reverse() + - + coord_cartesian(xlim = c(0, 1000), ylim = c(0, 8), expand = FALSE) + - + theme_classic() - > gggeo_scale_old(p) - Warning: `gggeo_scale_old()` was deprecated in deeptime 1.0.0. - ℹ Please use `coord_geo()` instead. - Error in names(labels) <- `*vtmp*` : attempt to set an attribute on NULL - Calls: gggeo_scale_old ... ggplot_add -> ggplot_add.new_aes -> bump_aes_labels - Execution halted - ``` - -# distributional - -
- -* Version: 0.4.0 -* GitHub: https://github.com/mitchelloharawild/distributional -* Source code: https://github.com/cran/distributional -* Date/Publication: 2024-02-07 13:30:02 UTC -* Number of recursive dependencies: 64 - -Run `revdepcheck::cloud_details(, "distributional")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘distributional-Ex.R’ failed - The error most likely occurred in: - - > ### Name: dist_truncated - > ### Title: Truncate a distribution - > ### Aliases: dist_truncated - > - > ### ** Examples - > - > dist <- dist_truncated(dist_normal(2,1), lower = 0) - ... - 12. │ └─ggplot2 (local) f(l = layers[[i]], d = data[[i]]) - 13. │ └─l$compute_geom_2(d, theme = plot$theme) - 14. │ └─ggplot2 (local) compute_geom_2(..., self = self) - 15. │ └─self$geom$use_defaults(...) - 16. └─base::.handleSimpleError(...) - 17. └─rlang (local) h(simpleError(msg, call)) - 18. └─handlers[[1L]](cnd) - 19. └─cli::cli_abort(...) - 20. └─rlang::abort(...) - Execution halted - ``` - -# dittoViz - -
- -* Version: 1.0.1 -* GitHub: https://github.com/dtm2451/dittoViz -* Source code: https://github.com/cran/dittoViz -* Date/Publication: 2024-02-02 00:00:12 UTC -* Number of recursive dependencies: 99 - -Run `revdepcheck::cloud_details(, "dittoViz")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘dittoViz-Ex.R’ failed - The error most likely occurred in: - - > ### Name: barPlot - > ### Title: Outputs a stacked bar plot to show the percent composition of - > ### samples, groups, clusters, or other groupings - > ### Aliases: barPlot - > - > ### ** Examples - > - ... - 15 3 D 12 32 0.3750000 - 16 4 D 8 32 0.2500000 - > # through hovering the cursor over the relevant parts of the plot - > if (requireNamespace("plotly", quietly = TRUE)) { - + barPlot(example_df, "clustering", group.by = "groups", - + do.hover = TRUE) - + } - Error in pm[[2]] : subscript out of bounds - Calls: barPlot -> -> ggplotly.ggplot -> gg2list - Execution halted - ``` - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(dittoViz) - Loading required package: ggplot2 - > test_check("dittoViz") - [ FAIL 12 | WARN 12 | SKIP 0 | PASS 307 ] - - ══ Failed tests ════════════════════════════════════════════════════════════════ - ... - 2. └─dittoViz::freqPlot(...) - 3. └─dittoViz::yPlot(...) - 4. └─dittoViz:::.warn_or_apply_plotly(p, plots) - 5. ├─plotly::ggplotly(p, tooltip = "text") - 6. └─plotly:::ggplotly.ggplot(p, tooltip = "text") - 7. └─plotly::gg2list(...) - - [ FAIL 12 | WARN 12 | SKIP 0 | PASS 307 ] - Error: Test failures - Execution halted - ``` - -# EGM - -
- -* Version: 0.1.0 -* GitHub: https://github.com/shah-in-boots/EGM -* Source code: https://github.com/cran/EGM -* Date/Publication: 2024-05-23 16:10:05 UTC -* Number of recursive dependencies: 77 - -Run `revdepcheck::cloud_details(, "EGM")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(EGM) - Loading required package: vctrs - Loading required package: data.table - > EGM::set_wfdb_path("/usr/local/bin") - > - > test_check("EGM") - ... - ══ Failed tests ════════════════════════════════════════════════════════════════ - ── Failure ('test-ggm.R:63:2'): theming works ────────────────────────────────── - g$labels$x (`actual`) not equal to "sample" (`expected`). - - `actual` is NULL - `expected` is a character vector ('sample') - - [ FAIL 1 | WARN 0 | SKIP 19 | PASS 43 ] - Error: Test failures - Execution halted - ``` - -# entropart - -
- -* Version: 1.6-13 -* GitHub: https://github.com/EricMarcon/entropart -* Source code: https://github.com/cran/entropart -* Date/Publication: 2023-09-26 14:40:02 UTC -* Number of recursive dependencies: 125 - -Run `revdepcheck::cloud_details(, "entropart")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘entropart-Ex.R’ failed - The error most likely occurred in: - - > ### Name: Accumulation - > ### Title: Diversity accumulation. - > ### Aliases: DivAC EntAC as.AccumCurve is.AccumCurve autoplot.AccumCurve - > ### plot.AccumCurve - > - > ### ** Examples - > - ... - 11. │ └─base::withCallingHandlers(...) - 12. └─ggplot2 (local) f(l = layers[[i]], d = data[[i]]) - 13. └─l$compute_geom_2(d, theme = plot$theme) - 14. └─ggplot2 (local) compute_geom_2(..., self = self) - 15. └─self$geom$use_defaults(...) - 16. └─ggplot2 (local) use_defaults(..., self = self) - 17. └─ggplot2:::check_aesthetics(new_params, nrow(data)) - 18. └─cli::cli_abort(...) - 19. └─rlang::abort(...) - Execution halted - ``` - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘entropart.Rmd’ - ... - - > autoplot(Abd18, Distribution = "lnorm") - - When sourcing ‘entropart.R’: - Error: Problem while setting up geom aesthetics. - ℹ Error occurred in the 1st layer. - Caused by error in `check_aesthetics()`: - ! Aesthetics must be either length 1 or the same as the data (149). - ✖ Fix the following mappings: `shape`, `colour`, and `size`. - Execution halted - - ‘entropart.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - ... - --- re-building ‘entropart.Rmd’ using rmarkdown - - Quitting from lines 53-55 [PlotN18] (entropart.Rmd) - Error: processing vignette 'entropart.Rmd' failed with diagnostics: - Problem while setting up geom aesthetics. - ℹ Error occurred in the 1st layer. - Caused by error in `check_aesthetics()`: - ! Aesthetics must be either length 1 or the same as the data (149). - ✖ Fix the following mappings: `shape`, `colour`, and `size`. - --- failed re-building ‘entropart.Rmd’ - - SUMMARY: processing the following file failed: - ‘entropart.Rmd’ - - Error: Vignette re-building failed. - Execution halted - ``` - -# epiCleanr - -
- -* Version: 0.2.0 -* GitHub: https://github.com/truenomad/epiCleanr -* Source code: https://github.com/cran/epiCleanr -* Date/Publication: 2023-09-28 12:20:05 UTC -* Number of recursive dependencies: 130 - -Run `revdepcheck::cloud_details(, "epiCleanr")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘epiCleanr-Ex.R’ failed - The error most likely occurred in: - - > ### Name: handle_outliers - > ### Title: Detect and Handle Outliers in Dataset - > ### Aliases: handle_outliers - > - > ### ** Examples - > - > - ... - 12. │ └─ggplot2 (local) f(l = layers[[i]], d = data[[i]]) - 13. │ └─l$compute_geom_2(d, theme = plot$theme) - 14. │ └─ggplot2 (local) compute_geom_2(..., self = self) - 15. │ └─self$geom$use_defaults(...) - 16. └─base::.handleSimpleError(...) - 17. └─rlang (local) h(simpleError(msg, call)) - 18. └─handlers[[1L]](cnd) - 19. └─cli::cli_abort(...) - 20. └─rlang::abort(...) - Execution halted - ``` - -## In both - -* checking installed package size ... NOTE - ``` - installed size is 5.6Mb - sub-directories of 1Mb or more: - doc 2.9Mb - help 2.5Mb - ``` - -# esci - -
- -* Version: 1.0.3 -* GitHub: https://github.com/rcalinjageman/esci -* Source code: https://github.com/cran/esci -* Date/Publication: 2024-07-08 21:40:10 UTC -* Number of recursive dependencies: 93 - -Run `revdepcheck::cloud_details(, "esci")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘esci-Ex.R’ failed - The error most likely occurred in: - - > ### Name: estimate_mdiff_2x2_between - > ### Title: Estimates for a 2x2 between-subjects design with a continuous - > ### outcome variable - > ### Aliases: estimate_mdiff_2x2_between - > - > ### ** Examples - > - ... - + estimates_from_summary$interaction, - + effect_size = "mean" - + ) - Warning: Using size for a discrete variable is not advised. - Warning: Using alpha for a discrete variable is not advised. - Error in use_defaults(..., self = self) : - unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, "black", TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), list(NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), 5.5, c(5.5, 5.5, 5.5, 5.5), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.75, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, - NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, 90, NULL, c(0, 2.75, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL - Calls: ... -> -> compute_geom_2 -> - Execution halted - ``` - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(esci) - > - > test_check("esci") - Loading required package: Matrix - Loading required package: metadat - Loading required package: numDeriv - ... - 17. │ └─self$geom$use_defaults(...) - 18. └─base::.handleSimpleError(...) - 19. └─rlang (local) h(simpleError(msg, call)) - 20. └─handlers[[1L]](cnd) - 21. └─cli::cli_abort(...) - 22. └─rlang::abort(...) - - [ FAIL 14 | WARN 0 | SKIP 0 | PASS 3182 ] - Error: Test failures - Execution halted - ``` - -# evalITR - -
- -* Version: 1.0.0 -* GitHub: https://github.com/MichaelLLi/evalITR -* Source code: https://github.com/cran/evalITR -* Date/Publication: 2023-08-25 23:10:06 UTC -* Number of recursive dependencies: 167 - -Run `revdepcheck::cloud_details(, "evalITR")` for more info - -
- -## Newly broken - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘cv_multiple_alg.Rmd’ using rmarkdown - ``` - -## In both - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘cv_multiple_alg.Rmd’ - ... - intersect, setdiff, setequal, union - - - > load("../data/star.rda") - Warning in readChar(con, 5L, useBytes = TRUE) : - cannot open compressed file '../data/star.rda', probable reason 'No such file or directory' - - ... - Execution halted - - ‘cv_multiple_alg.Rmd’ using ‘UTF-8’... failed - ‘cv_single_alg.Rmd’ using ‘UTF-8’... failed - ‘install.Rmd’ using ‘UTF-8’... OK - ‘paper_alg1.Rmd’ using ‘UTF-8’... OK - ‘sample_split.Rmd’ using ‘UTF-8’... failed - ‘sample_split_caret.Rmd’ using ‘UTF-8’... failed - ‘user_itr.Rmd’ using ‘UTF-8’... failed - ‘user_itr_algs.Rmd’ using ‘UTF-8’... failed - ``` - -* checking dependencies in R code ... NOTE - ``` - Namespaces in Imports field not imported from: - ‘forcats’ ‘rqPen’ ‘utils’ - All declared Imports should be used. - ``` - -# eventstudyr - -
- -* Version: 1.1.3 -* GitHub: https://github.com/JMSLab/eventstudyr -* Source code: https://github.com/cran/eventstudyr -* Date/Publication: 2024-03-04 15:00:02 UTC -* Number of recursive dependencies: 98 - -Run `revdepcheck::cloud_details(, "eventstudyr")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(eventstudyr) - > - > test_check("eventstudyr") - Defaulting to strongest lead of differenced policy variable: proxyIV = z_fd_lead3. To specify a different proxyIV use the proxyIV argument. - Defaulting to strongest lead of differenced policy variable: proxyIV = z_fd_lead3. To specify a different proxyIV use the proxyIV argument. - Defaulting to strongest lead of differenced policy variable: proxyIV = z_fd_lead3. To specify a different proxyIV use the proxyIV argument. - ... - `expected` is a character vector ('ci_lower') - ── Failure ('test-EventStudyPlot.R:128:5'): confidence intervals are appropriately present or absent ── - p_ci$labels$ymax (`actual`) not equal to "ci_upper" (`expected`). - - `actual` is NULL - `expected` is a character vector ('ci_upper') - - [ FAIL 6 | WARN 0 | SKIP 0 | PASS 258 ] - Error: Test failures - Execution halted - ``` - -# EvoPhylo - -
- -* Version: 0.3.2 -* GitHub: https://github.com/tiago-simoes/EvoPhylo -* Source code: https://github.com/cran/EvoPhylo -* Date/Publication: 2022-11-03 17:00:02 UTC -* Number of recursive dependencies: 164 - -Run `revdepcheck::cloud_details(, "EvoPhylo")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘EvoPhylo-Ex.R’ failed - The error most likely occurred in: - - > ### Name: make_clusters - > ### Title: Estimate and plot character partitions - > ### Aliases: make_clusters plot.cluster_df - > - > ### ** Examples - > - > # See vignette("char-part") for how to use this - ... - > # tSNE (3 dimensions; default is 2) - > cluster_df_tsne <- make_clusters(Dmatrix, k = 3, tsne = TRUE, - + tsne_dim = 2) - > - > # Plot clusters, plots divided into 2 rows, and increasing - > # overlap of text labels (default = 10) - > plot(cluster_df_tsne, nrow = 2, max.overlaps = 20) - Error in identicalUnits(x) : object is not a unit - Calls: ... assemble_guides -> guides_build -> unit.c -> identicalUnits - Execution halted - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘char-part.Rmd’ using rmarkdown - ``` - -## In both - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘char-part.Rmd’ - ... - + collapse = TRUE, dpi = 300) - - > devtools::load_all(".") - - When sourcing ‘char-part.R’: - Error: Could not find a root 'DESCRIPTION' file that starts with '^Package' in - '/tmp/Rtmp2nrOwZ/file1bed270c7be0/vignettes'. - ... - ℹ Are you in your project directory and does your project have a 'DESCRIPTION' - file? - Execution halted - - ‘char-part.Rmd’ using ‘UTF-8’... failed - ‘data_treatment.Rmd’ using ‘UTF-8’... OK - ‘fbd-params.Rmd’ using ‘UTF-8’... failed - ‘offset_handling.Rmd’ using ‘UTF-8’... failed - ‘rates-selection_BEAST2.Rmd’ using ‘UTF-8’... failed - ‘rates-selection_MrBayes.Rmd’ using ‘UTF-8’... failed - ``` - -* checking installed package size ... NOTE - ``` - installed size is 6.8Mb - sub-directories of 1Mb or more: - data 2.5Mb - doc 1.6Mb - extdata 2.4Mb - ``` - -# expirest - -
- -* Version: 0.1.6 -* GitHub: https://github.com/piusdahinden/expirest -* Source code: https://github.com/cran/expirest -* Date/Publication: 2024-03-25 16:30:02 UTC -* Number of recursive dependencies: 46 - -Run `revdepcheck::cloud_details(, "expirest")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(expirest) - > - > test_check("expirest") - [ FAIL 9 | WARN 0 | SKIP 0 | PASS 1122 ] - - ══ Failed tests ════════════════════════════════════════════════════════════════ - ... - ── Failure ('test-plot_expirest_wisle.R:260:3'): plot_expirest_wisle_succeeds ── - tmp4l2[["Graph"]]$labels has length 0, not length 8. - ── Failure ('test-plot_expirest_wisle.R:264:3'): plot_expirest_wisle_succeeds ── - tmp4b1[["Graph"]]$labels has length 0, not length 5. - ── Failure ('test-plot_expirest_wisle.R:269:3'): plot_expirest_wisle_succeeds ── - tmp4b2[["Graph"]]$labels has length 0, not length 5. - - [ FAIL 9 | WARN 0 | SKIP 0 | PASS 1122 ] - Error: Test failures - Execution halted - ``` - -# explainer - -
- -* Version: 1.0.1 -* GitHub: https://github.com/PERSIMUNE/explainer -* Source code: https://github.com/cran/explainer -* Date/Publication: 2024-04-18 09:00:02 UTC -* Number of recursive dependencies: 184 - -Run `revdepcheck::cloud_details(, "explainer")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘explainer-Ex.R’ failed - The error most likely occurred in: - - > ### Name: eDecisionCurve - > ### Title: Decision Curve Plot - > ### Aliases: eDecisionCurve - > - > ### ** Examples - > - > library("explainer") - ... - > mylrn$train(maintask, splits$train) - > myplot <- eDecisionCurve( - + task = maintask, - + trained_model = mylrn, - + splits = splits, - + seed = seed - + ) - Error in pm[[2]] : subscript out of bounds - Calls: eDecisionCurve -> ggplotly -> ggplotly.ggplot -> gg2list - Execution halted - ``` - -## In both - -* checking dependencies in R code ... NOTE - ``` - Namespace in Imports field not imported from: ‘ggpmisc’ - All declared Imports should be used. - ``` - -# ezEDA - -
- -* Version: 0.1.1 -* GitHub: https://github.com/kviswana/ezEDA -* Source code: https://github.com/cran/ezEDA -* Date/Publication: 2021-06-29 04:40:10 UTC -* Number of recursive dependencies: 91 - -Run `revdepcheck::cloud_details(, "ezEDA")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(ezEDA) - > - > test_check("ezEDA") - [ FAIL 22 | WARN 0 | SKIP 0 | PASS 57 ] - - ══ Failed tests ════════════════════════════════════════════════════════════════ - ... - ── Error ('test_two_measures_relationship.R:19:3'): y axis is labeled 'hwy' ──── - Error in `expect_match(p$labels$y, "hwy")`: is.character(act$val) is not TRUE - Backtrace: - ▆ - 1. └─testthat::expect_match(p$labels$y, "hwy") at test_two_measures_relationship.R:19:3 - 2. └─base::stopifnot(is.character(act$val)) - - [ FAIL 22 | WARN 0 | SKIP 0 | PASS 57 ] - Error: Test failures - Execution halted - ``` - -# ezplot - -
- -* Version: 0.7.13 -* GitHub: NA -* Source code: https://github.com/cran/ezplot -* Date/Publication: 2024-01-28 11:30:05 UTC -* Number of recursive dependencies: 109 - -Run `revdepcheck::cloud_details(, "ezplot")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘ezplot-Ex.R’ failed - The error most likely occurred in: - - > ### Name: bar_plot - > ### Title: bar_plot - > ### Aliases: bar_plot - > - > ### ** Examples - > - > library(tsibble) - ... - 11. │ └─base::withCallingHandlers(...) - 12. └─ggplot2 (local) f(l = layers[[i]], d = data[[i]]) - 13. └─l$compute_geom_2(d, theme = plot$theme) - 14. └─ggplot2 (local) compute_geom_2(..., self = self) - 15. └─self$geom$use_defaults(...) - 16. └─ggplot2 (local) use_defaults(..., self = self) - 17. └─ggplot2:::check_aesthetics(new_params, nrow(data)) - 18. └─cli::cli_abort(...) - 19. └─rlang::abort(...) - Execution halted - ``` - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘bar_plot.Rmd’ - ... - - > bar_plot(ansett, "year(Week)", "Passengers", size = 16) - - When sourcing ‘bar_plot.R’: - Error: Problem while setting up geom aesthetics. - ℹ Error occurred in the 1st layer. - Caused by error in `check_aesthetics()`: - ... - Caused by error in `check_aesthetics()`: - ! Aesthetics must be either length 1 or the same as the data (9). - ✖ Fix the following mappings: `width`. - Execution halted - - ‘bar_plot.Rmd’ using ‘UTF-8’... failed - ‘basics.Rmd’ using ‘UTF-8’... failed - ‘line_plot.Rmd’ using ‘UTF-8’... OK - ‘overview.Rmd’ using ‘UTF-8’... failed - ‘variable_plot.Rmd’ using ‘UTF-8’... OK - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘bar_plot.Rmd’ using rmarkdown - - Quitting from lines 28-29 [unnamed-chunk-2] (bar_plot.Rmd) - Error: processing vignette 'bar_plot.Rmd' failed with diagnostics: - Problem while setting up geom aesthetics. - ℹ Error occurred in the 1st layer. - Caused by error in `check_aesthetics()`: - ! Aesthetics must be either length 1 or the same as the data (6). - ✖ Fix the following mappings: `width`. - --- failed re-building ‘bar_plot.Rmd’ - - --- re-building ‘basics.Rmd’ using rmarkdown - ``` - -# fable.prophet - -
- -* Version: 0.1.0 -* GitHub: https://github.com/mitchelloharawild/fable.prophet -* Source code: https://github.com/cran/fable.prophet -* Date/Publication: 2020-08-20 09:30:03 UTC -* Number of recursive dependencies: 114 - -Run `revdepcheck::cloud_details(, "fable.prophet")` for more info - -
- -## Newly broken - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘intro.Rmd’ - ... - 9 Domestic mdl 2019 Dec sample[5000] 5337907. - 10 Domestic mdl 2020 Jan sample[5000] 4887065. - # ℹ 62 more rows - - > fc %>% autoplot(lax_passengers) - - When sourcing ‘intro.R’: - Error: unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, "black", TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), list(NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), 5.5, c(5.5, 5.5, 5.5, 5.5), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.75, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, - NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, 90, NULL, c(0, 2.75, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, - Execution halted - - ‘intro.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘intro.Rmd’ using rmarkdown - ``` - -## In both - -* checking LazyData ... NOTE - ``` - 'LazyData' is specified without a 'data' directory - ``` - -# fabletools - -
- -* Version: 0.4.2 -* GitHub: https://github.com/tidyverts/fabletools -* Source code: https://github.com/cran/fabletools -* Date/Publication: 2024-04-22 11:22:41 UTC -* Number of recursive dependencies: 106 - -Run `revdepcheck::cloud_details(, "fabletools")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘fabletools-Ex.R’ failed - The error most likely occurred in: - - > ### Name: autoplot.fbl_ts - > ### Title: Plot a set of forecasts - > ### Aliases: autoplot.fbl_ts autolayer.fbl_ts - > - > ### ** Examples - > - > ## Don't show: - ... - > library(fable) - > library(tsibbledata) - > fc <- aus_production %>% model(ets = ETS(log(Beer) ~ error("M") + trend("Ad") + - + season("A"))) %>% forecast(h = "3 years") - > fc %>% autoplot(aus_production) - Error in use_defaults(..., self = self) : - unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, "black", TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), list(NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), 5.5, c(5.5, 5.5, 5.5, 5.5), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.75, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, - NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, 90, NULL, c(0, 2.75, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL - Calls: ... -> -> compute_geom_2 -> - Execution halted - ``` - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(dplyr) - - Attaching package: 'dplyr' - - The following object is masked from 'package:testthat': - - ... - 24. └─base::Map(...) - 25. └─base::mapply(FUN = f, ..., SIMPLIFY = FALSE) - 26. └─ggplot2 (local) ``(layer = dots[[1L]][[1L]], df = dots[[2L]][[1L]]) - 27. └─layer$compute_geom_2(key, single_params, theme) - 28. └─ggplot2 (local) compute_geom_2(..., self = self) - 29. └─self$geom$use_defaults(...) - - [ FAIL 2 | WARN 0 | SKIP 1 | PASS 269 ] - Error: Test failures - Execution halted - ``` - -# factoextra - -
- -* Version: 1.0.7 -* GitHub: https://github.com/kassambara/factoextra -* Source code: https://github.com/cran/factoextra -* Date/Publication: 2020-04-01 21:20:02 UTC -* Number of recursive dependencies: 116 - -Run `revdepcheck::cloud_details(, "factoextra")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘factoextra-Ex.R’ failed - The error most likely occurred in: - - > ### Name: eigenvalue - > ### Title: Extract and visualize the eigenvalues/variances of dimensions - > ### Aliases: eigenvalue get_eig get_eigenvalue fviz_eig fviz_screeplot - > - > ### ** Examples - > - > # Principal Component Analysis - ... - 11. │ └─base::withCallingHandlers(...) - 12. └─ggplot2 (local) f(l = layers[[i]], d = data[[i]]) - 13. └─l$compute_geom_2(d, theme = plot$theme) - 14. └─ggplot2 (local) compute_geom_2(..., self = self) - 15. └─self$geom$use_defaults(...) - 16. └─ggplot2 (local) use_defaults(..., self = self) - 17. └─ggplot2:::check_aesthetics(new_params, nrow(data)) - 18. └─cli::cli_abort(...) - 19. └─rlang::abort(...) - Execution halted - ``` - -# fairmodels - -
- -* Version: 1.2.1 -* GitHub: https://github.com/ModelOriented/fairmodels -* Source code: https://github.com/cran/fairmodels -* Date/Publication: 2022-08-23 19:50:06 UTC -* Number of recursive dependencies: 87 - -Run `revdepcheck::cloud_details(, "fairmodels")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(fairmodels) - > - > - > test_check("fairmodels") - Welcome to DALEX (version: 2.4.3). - Find examples and detailed introduction at: http://ema.drwhy.ai/ - ... - [ FAIL 1 | WARN 1 | SKIP 0 | PASS 312 ] - - ══ Failed tests ════════════════════════════════════════════════════════════════ - ── Failure ('test_plot_density.R:14:3'): Test plot_density ───────────────────── - plt$labels$x not equal to "probability". - target is NULL, current is character - - [ FAIL 1 | WARN 1 | SKIP 0 | PASS 312 ] - Error: Test failures - Execution halted - ``` - -# fddm - -
- -* Version: 1.0-2 -* GitHub: https://github.com/rtdists/fddm -* Source code: https://github.com/cran/fddm -* Date/Publication: 2024-07-02 16:00:07 UTC -* Number of recursive dependencies: 92 - -Run `revdepcheck::cloud_details(, "fddm")` for more info - -
- -## Newly broken - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘benchmark.Rmd’ - ... - > mi <- min(bm_vec[, -seq_len(t_idx)]) - - > ma <- max(bm_vec[, (t_idx + 1):(ncol(bm_vec) - 4)]) - - > ggplot(mbm_vec, aes(x = factor(FuncName, levels = Names_vec), - + y = time, color = factor(FuncName, levels = Names_vec), fill = factor(FuncName, .... [TRUNCATED] - - ... - - When sourcing ‘pfddm.R’: - Error: Not a unit object - Execution halted - - ‘benchmark.Rmd’ using ‘UTF-8’... failed - ‘example.Rmd’ using ‘UTF-8’... OK - ‘math.Rmd’ using ‘UTF-8’... OK - ‘pfddm.Rmd’ using ‘UTF-8’... failed - ‘validity.Rmd’ using ‘UTF-8’... OK - ``` - -## In both - -* checking installed package size ... NOTE - ``` - installed size is 16.0Mb - sub-directories of 1Mb or more: - doc 1.6Mb - libs 13.5Mb - ``` - -# feasts - -
- -* Version: 0.3.2 -* GitHub: https://github.com/tidyverts/feasts -* Source code: https://github.com/cran/feasts -* Date/Publication: 2024-03-15 09:10:02 UTC -* Number of recursive dependencies: 101 - -Run `revdepcheck::cloud_details(, "feasts")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(feasts) - Loading required package: fabletools - > - > test_check("feasts") - [ FAIL 1 | WARN 0 | SKIP 0 | PASS 108 ] - - ══ Failed tests ════════════════════════════════════════════════════════════════ - ── Failure ('test-graphics.R:273:3'): gg_arma() plots ────────────────────────── - p_built$plot$labels[c("x", "y")] not equivalent to list(x = "Re(1/root)", y = "Im(1/root)"). - Component "x": 1 string mismatch - Component "y": 1 string mismatch - - [ FAIL 1 | WARN 0 | SKIP 0 | PASS 108 ] - Error: Test failures - Execution halted - ``` - -# ffp - -
- -* Version: 0.2.2 -* GitHub: https://github.com/Reckziegel/FFP -* Source code: https://github.com/cran/ffp -* Date/Publication: 2022-09-29 15:10:06 UTC -* Number of recursive dependencies: 107 - -Run `revdepcheck::cloud_details(, "ffp")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘ffp-Ex.R’ failed - The error most likely occurred in: - - > ### Name: scenario_density - > ### Title: Plot Scenarios - > ### Aliases: scenario_density scenario_histogram - > - > ### ** Examples - > - > x <- diff(log(EuStockMarkets))[, 1] - > p <- exp_decay(x, 0.005) - > - > scenario_density(x, p, 500) - Error in use_defaults(..., self = self) : - unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, "black", TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), list(NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), 5.5, c(5.5, 5.5, 5.5, 5.5), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.75, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, - NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, 90, NULL, c(0, 2.75, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(), NULL, list(NU - Calls: ... -> -> compute_geom_2 -> - Execution halted - ``` - -# fido - -
- -* Version: 1.1.1 -* GitHub: https://github.com/jsilve24/fido -* Source code: https://github.com/cran/fido -* Date/Publication: 2024-06-05 21:30:06 UTC -* Number of recursive dependencies: 130 - -Run `revdepcheck::cloud_details(, "fido")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘fido-Ex.R’ failed - The error most likely occurred in: - - > ### Name: plot.pibblefit - > ### Title: Plot Summaries of Posterior Distribution of pibblefit Parameters - > ### Aliases: plot.pibblefit - > - > ### ** Examples - > - > sim <- pibble_sim(N=10, D=4, Q=3) - > fit <- pibble(sim$Y, sim$X) - > plot(fit, par="Lambda") - Scale for colour is already present. - Adding another scale for colour, which will replace the existing scale. - Error in use_defaults(..., self = self) : - unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, "black", TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), list(NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), 5.5, c(5.5, 5.5, 5.5, 5.5), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.75, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, - NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 1, NULL, NULL, NULL, c(0, 2.2, 0, 0), NULL, TRUE), NULL, list(N - Calls: ... -> -> compute_geom_2 -> - Execution halted - ``` - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(fido) - > - > #Sys.setenv(KMP_DUPLICATE_LIB_OK="TRUE") - > test_check("fido") - [1] 0.27980164 -0.69169550 -0.53205652 0.11488451 -0.42419872 2.20261388 - [7] -1.62190133 -0.90893172 0.07891428 0.75060681 0.43593605 0.26819442 - ... - 21. └─base::Map(...) - 22. └─base::mapply(FUN = f, ..., SIMPLIFY = FALSE) - 23. └─ggplot2 (local) ``(layer = dots[[1L]][[1L]], df = dots[[2L]][[1L]]) - 24. └─layer$compute_geom_2(key, single_params, theme) - 25. └─ggplot2 (local) compute_geom_2(..., self = self) - 26. └─self$geom$use_defaults(...) - - [ FAIL 1 | WARN 0 | SKIP 0 | PASS 114 ] - Error: Test failures - Execution halted - ``` - -## In both - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘non-linear-models.Rmd’ - ... - - The following object is masked from ‘package:dplyr’: - - select - - - When sourcing ‘non-linear-models.R’: - Error: package or namespace load failed for ‘MCMCpack’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): - namespace ‘Matrix’ 1.5-4.1 is already loaded, but >= 1.6.0 is required - Execution halted - - ‘introduction-to-fido.Rmd’ using ‘UTF-8’... OK - ‘mitigating-pcrbias.Rmd’ using ‘UTF-8’... OK - ‘non-linear-models.Rmd’ using ‘UTF-8’... failed - ‘orthus.Rmd’ using ‘UTF-8’... OK - ‘picking_priors.Rmd’ using ‘UTF-8’... OK - ``` - -* checking installed package size ... NOTE - ``` - installed size is 106.3Mb - sub-directories of 1Mb or more: - data 4.0Mb - libs 100.5Mb - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘introduction-to-fido.Rmd’ using rmarkdown - --- finished re-building ‘introduction-to-fido.Rmd’ - - --- re-building ‘mitigating-pcrbias.Rmd’ using rmarkdown - --- finished re-building ‘mitigating-pcrbias.Rmd’ - - --- re-building ‘non-linear-models.Rmd’ using rmarkdown - ``` - -# flipr - -
- -* Version: 0.3.3 -* GitHub: https://github.com/LMJL-Alea/flipr -* Source code: https://github.com/cran/flipr -* Date/Publication: 2023-08-23 09:00:02 UTC -* Number of recursive dependencies: 106 - -Run `revdepcheck::cloud_details(, "flipr")` for more info - -
- -## Newly broken - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘alternative.Rmd’ using rmarkdown - --- finished re-building ‘alternative.Rmd’ - - --- re-building ‘exactness.Rmd’ using rmarkdown - - Quitting from lines 142-177 [unnamed-chunk-1] (exactness.Rmd) - Error: processing vignette 'exactness.Rmd' failed with diagnostics: - subscript out of bounds - --- failed re-building ‘exactness.Rmd’ - - --- re-building ‘flipr.Rmd’ using rmarkdown - ``` - -## In both - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘exactness.Rmd’ - ... - - > library(flipr) - - > load("../R/sysdata.rda") - Warning in readChar(con, 5L, useBytes = TRUE) : - cannot open compressed file '../R/sysdata.rda', probable reason 'No such file or directory' - - ... - cannot open compressed file '../R/sysdata.rda', probable reason 'No such file or directory' - - When sourcing ‘plausibility.R’: - Error: cannot open the connection - Execution halted - - ‘alternative.Rmd’ using ‘UTF-8’... OK - ‘exactness.Rmd’ using ‘UTF-8’... failed - ‘flipr.Rmd’ using ‘UTF-8’... failed - ‘plausibility.Rmd’ using ‘UTF-8’... failed - ``` - -* checking installed package size ... NOTE - ``` - installed size is 11.0Mb - sub-directories of 1Mb or more: - doc 9.1Mb - libs 1.2Mb - ``` - -# foqat - -
- -* Version: 2.0.8.2 -* GitHub: https://github.com/tianshu129/foqat -* Source code: https://github.com/cran/foqat -* Date/Publication: 2023-09-30 06:10:02 UTC -* Number of recursive dependencies: 75 - -Run `revdepcheck::cloud_details(, "foqat")` for more info - -
- -## Newly broken - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘Plot_Functions.Rmd’ - ... - > paged_table(aqids, options = list(max.print = 10000, - + rows.print = 10, cols.print = 6)) - - > geom_ts(df = aqids, yl = c(3, 2), yr = 6, alist = c(3, - + 2), llist = 6, yllab = bquote(NO[x] ~ " " ~ (ppbv)), yrlab = bquote(O[3] ~ - + " " .... [TRUNCATED] - - ... - When sourcing ‘Plot_Functions.R’: - Error: attempt to set an attribute on NULL - Execution halted - - ‘Air_Quality.Rmd’ using ‘UTF-8’... OK - ‘Atmospheric_Radiation.Rmd’ using ‘UTF-8’... OK - ‘Basic_Functions.Rmd’ using ‘UTF-8’... OK - ‘Particle_Size_Distribution.Rmd’ using ‘UTF-8’... OK - ‘Plot_Functions.Rmd’ using ‘UTF-8’... failed - ‘Trace_Gas_Chemistry.Rmd’ using ‘UTF-8’... OK - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘Air_Quality.Rmd’ using rmarkdown - --- finished re-building ‘Air_Quality.Rmd’ - - --- re-building ‘Atmospheric_Radiation.Rmd’ using rmarkdown - --- finished re-building ‘Atmospheric_Radiation.Rmd’ - - --- re-building ‘Basic_Functions.Rmd’ using rmarkdown - --- finished re-building ‘Basic_Functions.Rmd’ - - --- re-building ‘Particle_Size_Distribution.Rmd’ using rmarkdown - ``` - -# forestly - -
- -* Version: 0.1.1 -* GitHub: https://github.com/Merck/forestly -* Source code: https://github.com/cran/forestly -* Date/Publication: 2024-07-08 19:40:02 UTC -* Number of recursive dependencies: 84 - -Run `revdepcheck::cloud_details(, "forestly")` for more info - -
- -## Newly broken - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘forest-plot-static.Rmd’ - ... - Warning in grid.Call(C_textBounds, as.graphicsAnnot(x$label), x$x, x$y, : - conversion failure on 'Treatment← Favor →Placebo' in 'mbcsToSbcs': dot substituted for - Warning in grid.Call(C_textBounds, as.graphicsAnnot(x$label), x$x, x$y, : - conversion failure on 'Treatment← Favor →Placebo' in 'mbcsToSbcs': dot substituted for <86> - Warning in grid.Call(C_textBounds, as.graphicsAnnot(x$label), x$x, x$y, : - conversion failure on 'Treatment← Favor →Placebo' in 'mbcsToSbcs': dot substituted for <92> - - When sourcing ‘forest-plot-static.R’: - Error: object is not a unit - Execution halted - - ‘forest-plot-static.Rmd’ using ‘UTF-8’... failed - ‘forestly-cran.Rmd’ using ‘UTF-8’... OK - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘forest-plot-static.Rmd’ using rmarkdown - ``` - -# frailtyEM - -
- -* Version: 1.0.1 -* GitHub: https://github.com/tbalan/frailtyEM -* Source code: https://github.com/cran/frailtyEM -* Date/Publication: 2019-09-22 13:00:10 UTC -* Number of recursive dependencies: 78 - -Run `revdepcheck::cloud_details(, "frailtyEM")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘frailtyEM-Ex.R’ failed - The error most likely occurred in: - - > ### Name: summary.emfrail - > ### Title: Summary for 'emfrail' objects - > ### Aliases: summary.emfrail - > - > ### ** Examples - > - > data("bladder") - ... - filter - - The following object is masked from ‘package:graphics’: - - layout - - > ggplotly(pl2) - Error in pm[[2]] : subscript out of bounds - Calls: ggplotly -> ggplotly.ggplot -> gg2list - Execution halted - ``` - -## In both - -* checking LazyData ... NOTE - ``` - 'LazyData' is specified without a 'data' directory - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘frailtyEM_manual.Rnw’ using Sweave - Loading required package: survival - Loading required package: gridExtra - Warning: The `` argument of `guides()` cannot be `FALSE`. Use - "none" instead as of ggplot2 3.3.4. - Warning: Removed 2 rows containing missing values or values outside - the scale range (`geom_path()`). - Warning in data("kidney") : data set ‘kidney’ not found - Warning in emfrail(Surv(time, status) ~ age + sex + cluster(id), data = kidney, : - ... - l.179 \RequirePackage{grfext}\relax - ^^M - ! ==> Fatal error occurred, no output PDF file produced! - --- failed re-building ‘frailtyEM_manual.Rnw’ - - SUMMARY: processing the following file failed: - ‘frailtyEM_manual.Rnw’ - - Error: Vignette re-building failed. - Execution halted - ``` - -# funcharts - -
- -* Version: 1.4.1 -* GitHub: https://github.com/unina-sfere/funcharts -* Source code: https://github.com/cran/funcharts -* Date/Publication: 2024-02-22 08:50:02 UTC -* Number of recursive dependencies: 123 - -Run `revdepcheck::cloud_details(, "funcharts")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘funcharts-Ex.R’ failed - The error most likely occurred in: - - > ### Name: pca_mfd - > ### Title: Multivariate functional principal components analysis - > ### Aliases: pca_mfd - > - > ### ** Examples - > - > library(funcharts) - > mfdobj <- data_sim_mfd() - > pca_obj <- pca_mfd(mfdobj) - > plot_pca_mfd(pca_obj) - Error in identicalUnits(x) : object is not a unit - Calls: ... assemble_guides -> guides_build -> unit.c -> identicalUnits - Execution halted - ``` - -# geomtextpath - -
- -* Version: 0.1.4 -* GitHub: https://github.com/AllanCameron/geomtextpath -* Source code: https://github.com/cran/geomtextpath -* Date/Publication: 2024-06-13 06:40:02 UTC -* Number of recursive dependencies: 94 - -Run `revdepcheck::cloud_details(, "geomtextpath")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘geomtextpath-Ex.R’ failed - The error most likely occurred in: - - > ### Name: geom_textsf - > ### Title: Visualise sf objects with labels - > ### Aliases: geom_textsf geom_labelsf - > - > ### ** Examples - > - > ggplot(waterways) + - ... - 19. │ ├─rlang::inject(self$draw_panel(data, panel_params, coord, !!!params)) - 20. │ └─self$draw_panel(data, panel_params, coord, na.rm = FALSE, legend = "other") - 21. │ └─geomtextpath (local) draw_panel(...) - 22. │ └─geomtextpath:::sf_textgrob(...) - 23. └─base::.handleSimpleError(...) - 24. └─rlang (local) h(simpleError(msg, call)) - 25. └─handlers[[1L]](cnd) - 26. └─cli::cli_abort(...) - 27. └─rlang::abort(...) - Execution halted - ``` - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(geomtextpath) - Loading required package: ggplot2 - > - > test_check("geomtextpath") - [ FAIL 1 | WARN 0 | SKIP 4 | PASS 463 ] - - ... - ══ Failed tests ════════════════════════════════════════════════════════════════ - ── Error ('test-sf.R:91:3'): We can make grobs from sf features ──────────────── - Error in `(x$boxlinewidth %||% defaults$linewidth[type_ind]) * 3.779528`: non-numeric argument to binary operator - Backtrace: - ▆ - 1. └─geomtextpath:::sf_textgrob(river, as_textbox = TRUE) at test-sf.R:91:3 - - [ FAIL 1 | WARN 0 | SKIP 4 | PASS 463 ] - Error: Test failures - Execution halted - ``` - -# GGally - -
- -* Version: 2.2.1 -* GitHub: https://github.com/ggobi/ggally -* Source code: https://github.com/cran/GGally -* Date/Publication: 2024-02-14 00:53:32 UTC -* Number of recursive dependencies: 145 - -Run `revdepcheck::cloud_details(, "GGally")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘spelling.R’ - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > if (requireNamespace("testthat", quietly = TRUE)) { - + library(testthat) - + library(GGally) - + - + test_check("GGally") - + } - ... - `expected` is a character vector ('tip') - ── Failure ('test-ggsurv.R:26:3'): multiple ──────────────────────────────────── - !is.null(a$labels$group) is not TRUE - - `actual`: FALSE - `expected`: TRUE - - [ FAIL 3 | WARN 1 | SKIP 26 | PASS 477 ] - Error: Test failures - Execution halted - ``` - -# gganimate - -
- -* Version: 1.0.9 -* GitHub: https://github.com/thomasp85/gganimate -* Source code: https://github.com/cran/gganimate -* Date/Publication: 2024-02-27 14:00:03 UTC -* Number of recursive dependencies: 97 - -Run `revdepcheck::cloud_details(, "gganimate")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(gganimate) - Loading required package: ggplot2 - > - > test_check("gganimate") - [ FAIL 1 | WARN 3 | SKIP 1 | PASS 5 ] - - ... - 3. ├─gganimate::animate(p, nframes = 2) at test-anim_save.R:14:5 - 4. └─gganimate:::animate.gganim(p, nframes = 2) - 5. └─args$renderer(frames_vars$frame_source, args$fps) - 6. └─gganimate:::png_dim(frames[1]) - 7. └─cli::cli_abort("Provided file ({file}) does not exist") - 8. └─rlang::abort(...) - - [ FAIL 1 | WARN 3 | SKIP 1 | PASS 5 ] - Error: Test failures - Execution halted - ``` - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘gganimate.Rmd’ - ... - Theme element `panel.grid.major.y` is missing - Theme element `panel.grid.major.x` is missing - Warning: Failed to plot frame - Caused by error in `UseMethod()`: - ! no applicable method for 'element_grob' applied to an object of class "NULL" - - When sourcing ‘gganimate.R’: - Error: Provided file (/tmp/RtmpingcHf/165822e22fea/gganim_plot0001.png) does - not exist - Execution halted - - ‘gganimate.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘gganimate.Rmd’ using rmarkdown - ``` - -# ggbrain - -
- -* Version: 0.8.1 -* GitHub: https://github.com/michaelhallquist/ggbrain -* Source code: https://github.com/cran/ggbrain -* Date/Publication: 2023-03-21 18:00:05 UTC -* Number of recursive dependencies: 74 - -Run `revdepcheck::cloud_details(, "ggbrain")` for more info - -
- -## Newly broken - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘ggbrain_introduction.Rmd’ - ... - - > gg_obj <- gg_base + geom_brain(definition = "underlay", - + fill_scale = scale_fill_gradient(low = "grey8", high = "grey62"), - + show_legend .... [TRUNCATED] - - > gg_obj$render() - - ... - - > plot(gg_obj) - - When sourcing ‘ggbrain_labels.R’: - Error: attempt to set an attribute on NULL - Execution halted - - ‘ggbrain_aesthetics.Rmd’ using ‘UTF-8’... OK - ‘ggbrain_introduction.Rmd’ using ‘UTF-8’... failed - ‘ggbrain_labels.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - ... - --- re-building ‘ggbrain_aesthetics.Rmd’ using rmarkdown - --- finished re-building ‘ggbrain_aesthetics.Rmd’ - - --- re-building ‘ggbrain_introduction.Rmd’ using rmarkdown - - Quitting from lines 238-239 [unnamed-chunk-16] (ggbrain_introduction.Rmd) - Error: processing vignette 'ggbrain_introduction.Rmd' failed with diagnostics: - attempt to set an attribute on NULL - ... - Quitting from lines 47-54 [unnamed-chunk-2] (ggbrain_labels.Rmd) - Error: processing vignette 'ggbrain_labels.Rmd' failed with diagnostics: - attempt to set an attribute on NULL - --- failed re-building ‘ggbrain_labels.Rmd’ - - SUMMARY: processing the following files failed: - ‘ggbrain_introduction.Rmd’ ‘ggbrain_labels.Rmd’ - - Error: Vignette re-building failed. - Execution halted - ``` - -## In both - -* checking installed package size ... NOTE - ``` - installed size is 10.6Mb - sub-directories of 1Mb or more: - doc 3.0Mb - extdata 1.6Mb - libs 5.3Mb - ``` - -# ggbreak - -
- -* Version: 0.1.2 -* GitHub: https://github.com/YuLab-SMU/ggbreak -* Source code: https://github.com/cran/ggbreak -* Date/Publication: 2023-06-26 05:40:02 UTC -* Number of recursive dependencies: 64 - -Run `revdepcheck::cloud_details(, "ggbreak")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘ggbreak-Ex.R’ failed - The error most likely occurred in: - - > ### Name: scale_wrap - > ### Title: scale-wrap - > ### Aliases: scale_wrap - > - > ### ** Examples - > - > library(ggplot2) - > library(ggbreak) - > p <- ggplot(economics, aes(x=date, y = unemploy, colour = uempmed)) + - + geom_line() - > p + scale_wrap(n=4) - Error in identicalUnits(x) : object is not a unit - Calls: -> print.ggwrap - Execution halted - ``` - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘ggbreak.Rmd’ - ... - > p1 + p2 - - > p2 + scale_x_break(c(18, 21)) - - > p1 + scale_x_break(c(7, 17), scales = 1.5) + scale_x_break(c(18, - + 21), scales = 2) - - When sourcing ‘ggbreak.R’: - Error: second argument must be a list - Execution halted - - ‘ggbreak.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘ggbreak.Rmd’ using rmarkdown - ``` - -# ggdark - -
- -* Version: 0.2.1 -* GitHub: NA -* Source code: https://github.com/cran/ggdark -* Date/Publication: 2019-01-11 17:30:06 UTC -* Number of recursive dependencies: 46 - -Run `revdepcheck::cloud_details(, "ggdark")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘ggdark-Ex.R’ failed - The error most likely occurred in: - - > ### Name: dark_mode - > ### Title: Activate dark mode on a 'ggplot2' theme - > ### Aliases: dark_mode - > - > ### ** Examples - > - > library(ggplot2) - ... - > - > p1 <- ggplot(iris, aes(Sepal.Width, Sepal.Length, color = Species)) + - + geom_point() - > - > p1 # theme returned by theme_get() - > p1 + dark_mode() # activate dark mode on theme returned by theme_get() - Error in match(x, table, nomatch = 0L) : - 'match' requires vector arguments - Calls: dark_mode -> %in% - Execution halted - ``` - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(ggdark) - > - > test_check("ggdark") - [ FAIL 1 | WARN 0 | SKIP 0 | PASS 0 ] - - ══ Failed tests ════════════════════════════════════════════════════════════════ - ... - ── Error ('test_dark_mode.R:10:1'): (code run outside of `test_that()`) ──────── - Error in `match(x, table, nomatch = 0L)`: 'match' requires vector arguments - Backtrace: - ▆ - 1. └─ggdark::dark_mode(light_theme) at test_dark_mode.R:10:1 - 2. └─geoms[["GeomPoint"]]$default_aes$colour %in% ... - - [ FAIL 1 | WARN 0 | SKIP 0 | PASS 0 ] - Error: Test failures - Execution halted - ``` - -## In both - -* checking LazyData ... NOTE - ``` - 'LazyData' is specified without a 'data' directory - ``` - -# ggdist - -
- -* Version: 3.3.2 -* GitHub: https://github.com/mjskay/ggdist -* Source code: https://github.com/cran/ggdist -* Date/Publication: 2024-03-05 05:30:23 UTC -* Number of recursive dependencies: 127 - -Run `revdepcheck::cloud_details(, "ggdist")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘ggdist-Ex.R’ failed - The error most likely occurred in: - - > ### Name: Pr_ - > ### Title: Probability expressions in ggdist aesthetics - > ### Aliases: Pr_ p_ - > - > ### ** Examples - > - > library(ggplot2) - ... - + ) - > - > # map density onto alpha of the fill - > ggplot(df, aes(y = name, xdist = d)) + - + stat_slabinterval(aes(alpha = !!p_(x))) - Error in use_defaults(..., self = self) : - unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, "black", TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), list(NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), 5.5, c(5.5, 5.5, 5.5, 5.5), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.75, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, - NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, 90, NULL, c(0, 2.75, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL - Calls: ... -> -> compute_geom_2 -> - Execution halted - ``` - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > # This file is part of the standard setup for testthat. - > # It is recommended that you do not modify it. - > # - > # Where should you do additional test configuration? - > # Learn more about the roles of various files in: - > # * https://r-pkgs.org/testing-design.html#sec-tests-files-overview - > # * https://testthat.r-lib.org/articles/special-files.html - ... - • test.stat_sample_slabinterval/nas-with-na-rm-true.svg - • test.subguide/dots-subguide-with-side-vertical.svg - • test.subguide/integer-subguide-with-zero-range.svg - • test.subguide/slab-subguide-with-inside-labels-vertical.svg - • test.subguide/slab-subguide-with-outside-labels-vert.svg - • test.subguide/slab-subguide-with-outside-labels.svg - • test.subguide/slab-subguide-with-side-vertical.svg - • test.theme_ggdist/facet-titles-on-left.svg - Error: Test failures - Execution halted - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘dotsinterval.Rmd’ using rmarkdown - Warning in hook_png(..., cmd = "pngquant", post_process = function(x) { : - cannot find pngquant; please install and put it in PATH - Warning in hook_png(..., cmd = "pngquant", post_process = function(x) { : - cannot find pngquant; please install and put it in PATH - - Quitting from lines 49-161 [dotsinterval_components] (dotsinterval.Rmd) - Error: processing vignette 'dotsinterval.Rmd' failed with diagnostics: - Problem while setting up geom aesthetics. - ... - - --- re-building ‘freq-uncertainty-vis.Rmd’ using rmarkdown - Warning in hook_png(..., cmd = "pngquant", post_process = function(x) { : - cannot find pngquant; please install and put it in PATH - Warning in hook_png(..., cmd = "pngquant", post_process = function(x) { : - cannot find pngquant; please install and put it in PATH - Warning in hook_png(..., cmd = "pngquant", post_process = function(x) { : - cannot find pngquant; please install and put it in PATH - Warning in hook_png(..., cmd = "pngquant", post_process = function(x) { : - cannot find pngquant; please install and put it in PATH - ``` - -## In both - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘dotsinterval.Rmd’ - ... - + xdist = dist)) + geom_hline(yintercept = 0:1, color = "gray95") + - + stat_dotsin .... [TRUNCATED] - - When sourcing ‘dotsinterval.R’: - Error: Problem while setting up geom aesthetics. - ℹ Error occurred in the 2nd layer. - Caused by error in `use_defaults()`: - ... - ℹ Error occurred in the 1st layer. - Caused by error in `use_defaults()`: - ! unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, "black", TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), list(NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), 5.5, c(5.5, 5.5, 5.5, 5.5), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(7, 0, 0, 0), NULL, FALSE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, - NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, 90, NULL, c(0, 7, 0, 0), NULL, FALSE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TR - Execution halted - - ‘dotsinterval.Rmd’ using ‘UTF-8’... failed - ‘freq-uncertainty-vis.Rmd’ using ‘UTF-8’... failed - ‘lineribbon.Rmd’ using ‘UTF-8’... failed - ‘slabinterval.Rmd’ using ‘UTF-8’... failed - ``` - -* checking installed package size ... NOTE - ``` - installed size is 5.4Mb - sub-directories of 1Mb or more: - R 1.5Mb - doc 1.3Mb - help 1.5Mb - ``` - -# ggDoubleHeat - -
- -* Version: 0.1.2 -* GitHub: https://github.com/PursuitOfDataScience/ggDoubleHeat -* Source code: https://github.com/cran/ggDoubleHeat -* Date/Publication: 2023-08-24 21:00:04 UTC -* Number of recursive dependencies: 58 - -Run `revdepcheck::cloud_details(, "ggDoubleHeat")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘ggDoubleHeat-Ex.R’ failed - The error most likely occurred in: - - > ### Name: geom_heat_circle - > ### Title: Heatcircle - > ### Aliases: geom_heat_circle - > - > ### ** Examples - > - > - ... - + y = rep(c("d", "e", "f"), 3), - + outside_values = rep(c(1,5,7),3), - + inside_values = rep(c(2,3,4),3)) - > - > ggplot(data, aes(x,y)) + - + geom_heat_circle(outside = outside_values, - + inside = inside_values) - Error in names(labels) <- `*vtmp*` : attempt to set an attribute on NULL - Calls: +.gg ... ggplot_add -> ggplot_add.new_aes -> bump_aes_labels - Execution halted - ``` - -# ggeasy - -
- -* Version: 0.1.4 -* GitHub: https://github.com/jonocarroll/ggeasy -* Source code: https://github.com/cran/ggeasy -* Date/Publication: 2023-03-12 10:00:23 UTC -* Number of recursive dependencies: 94 - -Run `revdepcheck::cloud_details(, "ggeasy")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘ggeasy-Ex.R’ failed - The error most likely occurred in: - - > ### Name: easy_labs - > ### Title: Easily add ggplot labels using label attribute of 'data.frame' - > ### column - > ### Aliases: easy_labs - > - > ### ** Examples - > - ... - + ggplot2::geom_line(ggplot2::aes(colour=Species)) - > - > p - > - > p + easy_labs() - > p + easy_labs(title = "Plot Title", subtitle = 'Plot Subtitle', x = 'x axis label') - Error in utils::modifyList(p_labs, as.list(unlist(man_labs))) : - is.list(x) is not TRUE - Calls: +.gg ... ggplot_add.easy_labs -> easy_update_labs -> -> stopifnot - Execution halted - ``` - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(ggeasy) - > - > test_check("ggeasy") - [ FAIL 6 | WARN 0 | SKIP 1 | PASS 505 ] - - ══ Skipped tests (1) ═══════════════════════════════════════════════════════════ - ... - 1. └─ggeasy (local) expect_eqNe(easy_res$labels[sort(names(easy_res$labels))], hard_res$labels[sort(names(hard_res$labels))]) at test-labs.R:76:3 - 2. └─testthat::expect_equal(..., check.environment = FALSE) at test-labs.R:6:16 - - [ FAIL 6 | WARN 0 | SKIP 1 | PASS 505 ] - Deleting unused snapshots: - • labs/labels-attrib.svg - • labs/labels-manual.svg - • labs/labels-mytitle.svg - Error: Test failures - Execution halted - ``` - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘shortcuts.Rmd’ - ... - - > p1 <- p + labs(title = "default labels") - - > p2 <- p + easy_labs() + labs(title = "Replace titles with column labels") - - > p3 <- p + easy_labs(x = "My x axis") + labs(title = "Manually add x axis label") - - When sourcing ‘shortcuts.R’: - Error: is.list(x) is not TRUE - Execution halted - - ‘shortcuts.Rmd’ using ‘UTF-8’... failed - ‘tests_and_coverage.Rmd’ using ‘UTF-8’... OK - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘shortcuts.Rmd’ using rmarkdown - ``` - -# ggedit - -
- -* Version: 0.4.1 -* GitHub: https://github.com/yonicd/ggedit -* Source code: https://github.com/cran/ggedit -* Date/Publication: 2024-03-04 14:40:02 UTC -* Number of recursive dependencies: 95 - -Run `revdepcheck::cloud_details(, "ggedit")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘ggedit-Ex.R’ failed - The error most likely occurred in: - - > ### Name: dput.ggedit - > ### Title: Convert ggplot object to a string call - > ### Aliases: dput.ggedit - > - > ### ** Examples - > - > - > pList$pointSmooth #original compiled plot - `geom_smooth()` using formula = 'y ~ x' - Error in compute_geom_2(..., self = self) : - unused arguments (list(6), list(list("black", 0.5, 1, "butt", FALSE, "black", TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), list(NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), 5.5, c(5.5, 5.5, 5.5, 5.5), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.75, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, - NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, 90, NULL, c(0, 2.75, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(NULL, NULL, NU - Calls: ... get_layer_key -> Map -> mapply -> -> - Execution halted - ``` - -# ggESDA - -
- -* Version: 0.2.0 -* GitHub: https://github.com/kiangkiangkiang/ggESDA -* Source code: https://github.com/cran/ggESDA -* Date/Publication: 2022-08-19 08:40:10 UTC -* Number of recursive dependencies: 214 - -Run `revdepcheck::cloud_details(, "ggESDA")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘ggESDA-Ex.R’ failed - The error most likely occurred in: - - > ### Name: ggInterval_2DhistMatrix - > ### Title: 2-Dimension histogram matrix - > ### Aliases: ggInterval_2DhistMatrix - > - > ### ** Examples - > - > ggInterval_2DhistMatrix(oils, xBins = 5, yBins = 5) - ... - 11. │ └─base::withCallingHandlers(...) - 12. └─ggplot2 (local) f(l = layers[[i]], d = data[[i]]) - 13. └─l$compute_geom_2(d, theme = plot$theme) - 14. └─ggplot2 (local) compute_geom_2(..., self = self) - 15. └─self$geom$use_defaults(...) - 16. └─ggplot2 (local) use_defaults(..., self = self) - 17. └─ggplot2:::check_aesthetics(new_params, nrow(data)) - 18. └─cli::cli_abort(...) - 19. └─rlang::abort(...) - Execution halted - ``` - -# ggfixest - -
- -* Version: 0.1.0 -* GitHub: https://github.com/grantmcdermott/ggfixest -* Source code: https://github.com/cran/ggfixest -* Date/Publication: 2023-12-14 08:00:06 UTC -* Number of recursive dependencies: 78 - -Run `revdepcheck::cloud_details(, "ggfixest")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘tinytest.R’ - Running the tests in ‘tests/tinytest.R’ failed. - Complete output: - > ## Throttle CPU threads if R CMD check (for CRAN) - > - > if (any(grepl("_R_CHECK", names(Sys.getenv()), fixed = TRUE))) { - + # fixest - + if (requireNamespace("fixest", quietly = TRUE)) { - + library(fixest) - + setFixest_nthreads(1) - ... - ----- FAILED[]: test_ggiplot.R<52--52> - call| expect_snapshot_plot(p3, label = "ggiplot_simple_ribbon") - diff| 54503 - info| Diff plot saved to: _tinysnapshot_review/ggiplot_simple_ribbon.png - ----- FAILED[]: test_ggiplot.R<54--54> - call| expect_snapshot_plot(p5, label = "ggiplot_simple_mci_ribbon") - diff| 54400 - info| Diff plot saved to: _tinysnapshot_review/ggiplot_simple_mci_ribbon.png - Error: 14 out of 101 tests failed - Execution halted - ``` - -## In both - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘ggiplot.Rmd’ - ... - > iplot(list(TWFE = est_twfe_grp, `Sun & Abraham (2020)` = est_sa20_grp), - + ref.line = -1, main = "Staggered treatment: Split mutli-sample") - The degrees of freedom for the t distribution could not be deduced. Using a Normal distribution instead. - Note that you can provide the argument `df.t` directly. - - When sourcing ‘ggiplot.R’: - Error: in iplot(list(TWFE = est_twfe_grp, `Sun & Abraham (2...: - The 1st element of 'object' raises and error: - Error in nb * sd : non-numeric argument to binary operator - Execution halted - - ‘ggiplot.Rmd’ using ‘UTF-8’... failed - ``` - -# ggforce - -
- -* Version: 0.4.2 -* GitHub: https://github.com/thomasp85/ggforce -* Source code: https://github.com/cran/ggforce -* Date/Publication: 2024-02-19 11:00:02 UTC -* Number of recursive dependencies: 69 - -Run `revdepcheck::cloud_details(, "ggforce")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘ggforce-Ex.R’ failed - The error most likely occurred in: - - > ### Name: facet_row - > ### Title: One-dimensional facets - > ### Aliases: facet_row facet_col - > - > ### ** Examples - > - > # Standard use - > ggplot(mtcars) + - + geom_point(aes(disp, mpg)) + - + facet_col(~gear) - Error in space$x : $ operator is invalid for atomic vectors - Calls: ... -> draw_panels -> -> init_gtable - Execution halted - ``` - -## In both - -* checking installed package size ... NOTE - ``` - installed size is 27.7Mb - sub-directories of 1Mb or more: - R 1.5Mb - help 1.2Mb - libs 24.9Mb - ``` - -# ggformula - -
- -* Version: 0.12.0 -* GitHub: https://github.com/ProjectMOSAIC/ggformula -* Source code: https://github.com/cran/ggformula -* Date/Publication: 2023-11-09 12:30:07 UTC -* Number of recursive dependencies: 123 - -Run `revdepcheck::cloud_details(, "ggformula")` for more info - -
- -## Newly broken - -* checking for code/documentation mismatches ... WARNING - ``` - Codoc mismatches from documentation object 'gf_abline': - gf_hline - Code: function(object = NULL, gformula = NULL, data = NULL, ..., - yintercept, color, linetype, linewidth, alpha, xlab, - ylab, title, subtitle, caption, position = "identity", - show.legend = NA, show.help = NULL, inherit = FALSE, - environment = parent.frame()) - Docs: function(object = NULL, gformula = NULL, data = NULL, ..., - yintercept, color, linetype, linewidth, alpha, xlab, - ylab, title, subtitle, caption, show.legend = NA, - ... - xintercept, color, linetype, linewidth, alpha, xlab, - ylab, title, subtitle, caption, show.legend = NA, - show.help = NULL, inherit = FALSE, environment = - parent.frame()) - Argument names in code not in docs: - position - Mismatches in argument names (first 3): - Position: 15 Code: position Docs: show.legend - Position: 16 Code: show.legend Docs: show.help - Position: 17 Code: show.help Docs: inherit - ``` - -## In both - -* checking Rd cross-references ... NOTE - ``` - Packages unavailable to check Rd xrefs: ‘akima’, ‘ggforce’ - ``` - -# ggfortify - -
- -* Version: 0.4.17 -* GitHub: https://github.com/sinhrks/ggfortify -* Source code: https://github.com/cran/ggfortify -* Date/Publication: 2024-04-17 04:30:04 UTC -* Number of recursive dependencies: 125 - -Run `revdepcheck::cloud_details(, "ggfortify")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘test-all.R’ - Running the tests in ‘tests/test-all.R’ failed. - Complete output: - > library(testthat) - > - > suppressWarnings(RNGversion("3.5.0")) - > set.seed(1, sample.kind = "Rejection") - > - > test_check('ggfortify') - Loading required package: ggfortify - ... - - x[3]: "#595959FF" - y[3]: "grey35" - - x[4]: "#595959FF" - y[4]: "grey35" - - [ FAIL 5 | WARN 12 | SKIP 48 | PASS 734 ] - Error: Test failures - Execution halted - ``` - -# gggenomes - -
- -* Version: 1.0.0 -* GitHub: https://github.com/thackl/gggenomes -* Source code: https://github.com/cran/gggenomes -* Date/Publication: 2024-06-28 09:30:06 UTC -* Number of recursive dependencies: 112 - -Run `revdepcheck::cloud_details(, "gggenomes")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘gggenomes-Ex.R’ failed - The error most likely occurred in: - - > ### Name: flip - > ### Title: Flip bins and sequences - > ### Aliases: flip flip_seqs sync - > - > ### ** Examples - > - > library(patchwork) - ... - > p4 <- p %>% - + add_clusters(emale_cogs) %>% - + sync() + labs(caption = "shared orthologs") - Joining with `by = join_by(feat_id)` - Flipping: E4-10_086,E4-10_112,RCC970_016B - > - > p0 + p1 + p2 + p3 + p4 + plot_layout(nrow = 1, guides = "collect") - Error in as.unit(value) : object is not coercible to a unit - Calls: ... assemble_guides -> guides_build -> [<- -> [<-.unit -> as.unit - Execution halted - ``` - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘flip.Rmd’ - ... - > p4 <- p %>% add_clusters(emale_cogs) %>% sync() + - + labs(caption = "shared orthologs") - Joining with `by = join_by(feat_id)` - Flipping: E4-10_086,E4-10_112,RCC970_016B - - > p0 + p1 + p2 + p3 + p4 + plot_layout(nrow = 1, guides = "collect") - - When sourcing ‘flip.R’: - Error: object is not coercible to a unit - Execution halted - - ‘emales.Rmd’ using ‘UTF-8’... OK - ‘flip.Rmd’ using ‘UTF-8’... failed - ‘gggenomes.Rmd’ using ‘UTF-8’... OK - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘emales.Rmd’ using rmarkdown - --- finished re-building ‘emales.Rmd’ - - --- re-building ‘flip.Rmd’ using rmarkdown - - Quitting from lines 17-44 [unnamed-chunk-2] (flip.Rmd) - Error: processing vignette 'flip.Rmd' failed with diagnostics: - object is not coercible to a unit - --- failed re-building ‘flip.Rmd’ - ... - virophages) - emale_tirs Terminal inverted repeats of 6 EMALE genomes - - --- finished re-building ‘gggenomes.Rmd’ - - SUMMARY: processing the following file failed: - ‘flip.Rmd’ - - Error: Vignette re-building failed. - Execution halted - ``` - -# ggh4x - -
- -* Version: 0.2.8 -* GitHub: https://github.com/teunbrand/ggh4x -* Source code: https://github.com/cran/ggh4x -* Date/Publication: 2024-01-23 21:00:02 UTC -* Number of recursive dependencies: 77 - -Run `revdepcheck::cloud_details(, "ggh4x")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘ggh4x-Ex.R’ failed - The error most likely occurred in: - - > ### Name: guide_stringlegend - > ### Title: String legend - > ### Aliases: guide_stringlegend - > - > ### ** Examples - > - > p <- ggplot(mpg, aes(displ, hwy)) + - + geom_point(aes(colour = manufacturer)) - > - > # String legend can be set in the `guides()` function - > p + guides(colour = guide_stringlegend(ncol = 2)) - Error in (function (layer, df) : - argument "theme" is missing, with no default - Calls: ... use_defaults -> eval_from_theme -> %||% -> calc_element - Execution halted - ``` - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(ggh4x) - Loading required package: ggplot2 - > - > test_check("ggh4x") - [ FAIL 2 | WARN 20 | SKIP 18 | PASS 753 ] - - ... - 25. └─ggplot2 (local) compute_geom_2(..., self = self) - 26. └─self$geom$use_defaults(...) - 27. └─ggplot2 (local) use_defaults(..., self = self) - 28. └─ggplot2:::eval_from_theme(default_aes, theme) - 29. ├─calc_element("geom", theme) %||% .default_geom_element - 30. └─ggplot2::calc_element("geom", theme) - - [ FAIL 2 | WARN 20 | SKIP 18 | PASS 753 ] - Error: Test failures - Execution halted - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘Facets.Rmd’ using rmarkdown - ``` - -## In both - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘Miscellaneous.Rmd’ - ... - - > ggplot(diamonds, aes(price, carat, colour = clarity)) + - + geom_point(shape = ".") + scale_colour_brewer(palette = "Dark2", - + guide = "stri ..." ... [TRUNCATED] - Warning: The S3 guide system was deprecated in ggplot2 3.5.0. - ℹ It has been replaced by a ggproto system that can be extended. - - ... - ℹ Error occurred in the 1st layer. - Caused by error in `setup_params()`: - ! A discrete 'nbinom' distribution cannot be fitted to continuous data. - Execution halted - - ‘Facets.Rmd’ using ‘UTF-8’... OK - ‘Miscellaneous.Rmd’ using ‘UTF-8’... failed - ‘PositionGuides.Rmd’ using ‘UTF-8’... OK - ‘Statistics.Rmd’ using ‘UTF-8’... failed - ‘ggh4x.Rmd’ using ‘UTF-8’... OK - ``` - -# gghighlight - -
- -* Version: 0.4.1 -* GitHub: https://github.com/yutannihilation/gghighlight -* Source code: https://github.com/cran/gghighlight -* Date/Publication: 2023-12-16 01:00:02 UTC -* Number of recursive dependencies: 85 - -Run `revdepcheck::cloud_details(, "gghighlight")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘gghighlight-Ex.R’ failed - The error most likely occurred in: - - > ### Name: gghighlight - > ### Title: Highlight Data With Predicate - > ### Aliases: gghighlight - > - > ### ** Examples - > - > d <- data.frame( - ... - 8. │ ├─purrr:::with_indexed_errors(...) - 9. │ │ └─base::withCallingHandlers(...) - 10. │ ├─purrr:::call_with_cleanup(...) - 11. │ └─gghighlight (local) .f(.x[[i]], .y[[i]], ...) - 12. │ └─gghighlight:::get_default_aes_param(nm, layer$geom, layer$mapping) - 13. └─base::.handleSimpleError(...) - 14. └─purrr (local) h(simpleError(msg, call)) - 15. └─cli::cli_abort(...) - 16. └─rlang::abort(...) - Execution halted - ``` - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(gghighlight) - Loading required package: ggplot2 - > - > test_check("gghighlight") - label_key: type - label_key: type - ... - 15. └─cli::cli_abort(...) - 16. └─rlang::abort(...) - - [ FAIL 2 | WARN 2 | SKIP 1 | PASS 178 ] - Deleting unused snapshots: - • vdiffr/simple-bar-chart-with-facet.svg - • vdiffr/simple-line-chart.svg - • vdiffr/simple-point-chart.svg - Error: Test failures - Execution halted - ``` - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘gghighlight.Rmd’ - ... - + 0, label_key = type) - Warning in is.na(non_null_default_aes[[aes_param_name]]) : - is.na() applied to non-(list or vector) of type 'language' - - When sourcing ‘gghighlight.R’: - Error: ℹ In index: 1. - Caused by error in `aes_param_name %in% names(non_null_default_aes) && is.na(non_null_default_aes[[ - aes_param_name]])`: - ! 'length = 2' in coercion to 'logical(1)' - Execution halted - - ‘gghighlight.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘gghighlight.Rmd’ using rmarkdown - ``` - -# ggHoriPlot - -
- -* Version: 1.0.1 -* GitHub: https://github.com/rivasiker/ggHoriPlot -* Source code: https://github.com/cran/ggHoriPlot -* Date/Publication: 2022-10-11 16:22:33 UTC -* Number of recursive dependencies: 117 - -Run `revdepcheck::cloud_details(, "ggHoriPlot")` for more info - -
- -## Newly broken - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘ggHoriPlot.Rmd’ - ... - > mid <- sum(range(dat_tab$y, na.rm = T))/2 - - > b <- plotAllLayers(dat_tab, mid, cutpoints$cuts, cutpoints$color) - - > b/a + plot_layout(guides = "collect", heights = c(6, - + 1)) - - When sourcing ‘ggHoriPlot.R’: - Error: object is not a unit - Execution halted - - ‘examples.Rmd’ using ‘UTF-8’... OK - ‘ggHoriPlot.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘examples.Rmd’ using rmarkdown - ``` - -# ggiraph - -
- -* Version: 0.8.10 -* GitHub: https://github.com/davidgohel/ggiraph -* Source code: https://github.com/cran/ggiraph -* Date/Publication: 2024-05-17 12:10:02 UTC -* Number of recursive dependencies: 95 - -Run `revdepcheck::cloud_details(, "ggiraph")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘ggiraph-Ex.R’ failed - The error most likely occurred in: - - > ### Name: geom_path_interactive - > ### Title: Create interactive observations connections - > ### Aliases: geom_path_interactive geom_line_interactive - > ### geom_step_interactive - > - > ### ** Examples - > - ... - 20. │ └─base::lapply(...) - 21. │ └─ggplot2 (local) FUN(X[[i]], ...) - 22. │ ├─rlang::inject(self$draw_panel(data, panel_params, coord, !!!params)) - 23. │ └─self$draw_panel(...) - 24. └─base::.handleSimpleError(...) - 25. └─rlang (local) h(simpleError(msg, call)) - 26. └─handlers[[1L]](cnd) - 27. └─cli::cli_abort(...) - 28. └─rlang::abort(...) - Execution halted - ``` - -* checking tests ... ERROR - ``` - Running ‘tinytest.R’ - Running the tests in ‘tests/tinytest.R’ failed. - Complete output: - > if (requireNamespace("tinytest", quietly = TRUE)) { - + tinytest::test_package("ggiraph") - + } - - test-annotate_interactive.R... 0 tests - test-annotate_interactive.R... 0 tests - test-annotate_interactive.R... 0 tests - ... - 30. │ └─base::lapply(...) - 31. │ └─ggplot2 (local) FUN(X[[i]], ...) - 32. │ ├─rlang::inject(self$draw_panel(data, panel_params, coord, !!!params)) - 33. │ └─self$draw_panel(...) - 34. └─base::.handleSimpleError(...) - 35. └─rlang (local) h(simpleError(msg, call)) - 36. └─handlers[[1L]](cnd) - 37. └─cli::cli_abort(...) - 38. └─rlang::abort(...) - Execution halted - ``` - -## In both - -* checking installed package size ... NOTE - ``` - installed size is 9.7Mb - sub-directories of 1Mb or more: - R 1.5Mb - libs 6.9Mb - ``` - -# ggiraphExtra - -
- -* Version: 0.3.0 -* GitHub: https://github.com/cardiomoon/ggiraphExtra -* Source code: https://github.com/cran/ggiraphExtra -* Date/Publication: 2020-10-06 07:00:02 UTC -* Number of recursive dependencies: 124 - -Run `revdepcheck::cloud_details(, "ggiraphExtra")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘ggiraphExtra-Ex.R’ failed - The error most likely occurred in: - - > ### Name: ggAncova - > ### Title: Make an interactive plot for an ANCOVA model - > ### Aliases: ggAncova ggAncova.default ggAncova.formula ggAncova.lm - > - > ### ** Examples - > - > require(moonBook) - ... - 24. │ └─base::lapply(...) - 25. │ └─ggplot2 (local) FUN(X[[i]], ...) - 26. │ ├─rlang::inject(self$draw_panel(data, panel_params, coord, !!!params)) - 27. │ └─self$draw_panel(...) - 28. └─base::.handleSimpleError(...) - 29. └─rlang (local) h(simpleError(msg, call)) - 30. └─handlers[[1L]](cnd) - 31. └─cli::cli_abort(...) - 32. └─rlang::abort(...) - Execution halted - ``` - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘introduction.Rmd’ - ... - - > ggPoints(aes(x = wt, y = mpg, color = am), data = mtcars, - + method = "lm", interactive = TRUE) - - When sourcing ‘introduction.R’: - Error: Problem while converting geom to grob. - ℹ Error occurred in the 3rd layer. - Caused by error in `draw_panel()`: - ! unused argument (arrow.fill = NULL) - Execution halted - - ‘ggPredict.Rmd’ using ‘UTF-8’... OK - ‘introduction.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘ggPredict.Rmd’ using rmarkdown - ``` - -# ggmice - -
- -* Version: 0.1.0 -* GitHub: https://github.com/amices/ggmice -* Source code: https://github.com/cran/ggmice -* Date/Publication: 2023-08-07 14:20:02 UTC -* Number of recursive dependencies: 120 - -Run `revdepcheck::cloud_details(, "ggmice")` for more info - -
- -## Newly broken - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘old_friends.Rmd’ - ... - layout - - - > p <- plot_flux(dat) - - > ggplotly(p) - - When sourcing ‘old_friends.R’: - Error: subscript out of bounds - Execution halted - - ‘ggmice.Rmd’ using ‘UTF-8’... OK - ‘old_friends.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘ggmice.Rmd’ using rmarkdown - ``` - -# ggmulti - -
- -* Version: 1.0.7 -* GitHub: NA -* Source code: https://github.com/cran/ggmulti -* Date/Publication: 2024-04-09 09:40:05 UTC -* Number of recursive dependencies: 125 - -Run `revdepcheck::cloud_details(, "ggmulti")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘ggmulti-Ex.R’ failed - The error most likely occurred in: - - > ### Name: coord_radial - > ### Title: Radial axes - > ### Aliases: coord_radial - > - > ### ** Examples - > - > if(require("dplyr")) { - ... - - The following objects are masked from ‘package:base’: - - intersect, setdiff, setequal, union - - Error in use_defaults(..., self = self) : - unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, "black", TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), list(NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), 5.5, c(5.5, 5.5, 5.5, 5.5), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.75, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, - NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, 90, NULL, c(0, 2.75, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL - Calls: ... -> -> compute_geom_2 -> - Execution halted - ``` - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > - > - > library(testthat) - > library(ggmulti) - Loading required package: ggplot2 - - Attaching package: 'ggmulti' - ... - ── Error ('test_stat.R:18:3'): test stat ─────────────────────────────────────── - Error in `stat_hist_(prop = 0.5)`: Problem while setting up geom aesthetics. - ℹ Error occurred in the 1st layer. - Caused by error in `check_aesthetics()`: - ! Aesthetics must be either length 1 or the same as the data (83). - ✖ Fix the following mappings: `width`. - - [ FAIL 5 | WARN 1 | SKIP 0 | PASS 21 ] - Error: Test failures - Execution halted - ``` - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘glyph.Rmd’ - ... - + Sepal.Width, colour = Species), serialaxes.data = iris, axes.layout = "radia ..." ... [TRUNCATED] - - When sourcing ‘glyph.R’: - Error: Base operators are not defined for quosures. Do you need to unquote the - quosure? - - # Bad: myquosure / rhs - ... - > p - - When sourcing ‘highDim.R’: - Error: unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, "black", TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), list(NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), 5.5, c(5.5, 5.5, 5.5, 5.5), NULL, NULL, list(), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(), NULL, list(NULL, - NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, NULL, c(0, 0, 0, 2.2), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0.5, NULL, NULL, NULL, c(0, 2.2, 0, 2. - Execution halted - - ‘glyph.Rmd’ using ‘UTF-8’... failed - ‘highDim.Rmd’ using ‘UTF-8’... failed - ‘histogram-density-.Rmd’ using ‘UTF-8’... OK - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘glyph.Rmd’ using rmarkdown - ``` - -# ggnewscale - -
- -* Version: 0.4.10 -* GitHub: https://github.com/eliocamp/ggnewscale -* Source code: https://github.com/cran/ggnewscale -* Date/Publication: 2024-02-08 23:50:02 UTC -* Number of recursive dependencies: 62 - -Run `revdepcheck::cloud_details(, "ggnewscale")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘ggnewscale-Ex.R’ failed - The error most likely occurred in: - - > ### Name: new_scale - > ### Title: Adds a new scale to a plot - > ### Aliases: new_scale new_scale_fill new_scale_color new_scale_colour - > - > ### ** Examples - > - > library(ggplot2) - ... - + # Color scale for topography - + scale_color_viridis_c(option = "D") + - + # geoms below will use another color scale - + new_scale_color() + - + geom_point(data = measurements, size = 3, aes(color = thing)) + - + # Color scale applied to geoms added after new_scale_color() - + scale_color_viridis_c(option = "A") - Error in names(labels) <- `*vtmp*` : attempt to set an attribute on NULL - Calls: +.gg ... ggplot_add -> ggplot_add.new_aes -> bump_aes_labels - Execution halted - ``` - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(ggnewscale) - > - > test_check("ggnewscale") - [ FAIL 7 | WARN 0 | SKIP 0 | PASS 0 ] - - ══ Failed tests ════════════════════════════════════════════════════════════════ - ... - [ FAIL 7 | WARN 0 | SKIP 0 | PASS 0 ] - Deleting unused snapshots: - • newscale/guides-outisde-of-scales.svg - • newscale/guides.svg - • newscale/guides2.svg - • newscale/implicit-mapping.svg - • newscale/many-layers.svg - • newscale/respects-override-aes-2.svg - Error: Test failures - Execution halted - ``` - -# ggparallel - -
- -* Version: 0.4.0 -* GitHub: https://github.com/heike/ggparallel -* Source code: https://github.com/cran/ggparallel -* Date/Publication: 2024-03-09 22:00:02 UTC -* Number of recursive dependencies: 51 - -Run `revdepcheck::cloud_details(, "ggparallel")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > # This file is part of the standard setup for testthat. - > # It is recommended that you do not modify it. - > # - > # Where should you do additional test configuration? - > # Learn more about the roles of various files in: - > # * https://r-pkgs.org/testing-design.html#sec-tests-files-overview - > # * https://testthat.r-lib.org/articles/special-files.html - ... - 12. └─self$get_layer_key(params, layers[include], data[include], theme) - 13. └─ggplot2 (local) get_layer_key(...) - 14. └─base::Map(...) - 15. └─base::mapply(FUN = f, ..., SIMPLIFY = FALSE) - 16. └─ggplot2 (local) ``(layer = dots[[1L]][[1L]], df = dots[[2L]][[1L]]) - 17. └─layer$compute_geom_2(key, single_params, theme) - - [ FAIL 1 | WARN 0 | SKIP 0 | PASS 0 ] - Error: Test failures - Execution halted - ``` - -# ggpicrust2 - -
- -* Version: 1.7.3 -* GitHub: https://github.com/cafferychen777/ggpicrust2 -* Source code: https://github.com/cran/ggpicrust2 -* Date/Publication: 2023-11-08 16:10:02 UTC -* Number of recursive dependencies: 230 - -Run `revdepcheck::cloud_details(, "ggpicrust2")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘ggpicrust2-Ex.R’ failed - The error most likely occurred in: - - > ### Name: pathway_pca - > ### Title: Perform Principal Component Analysis (PCA) on functional pathway - > ### abundance data and create visualizations of the PCA results. - > ### Aliases: pathway_pca - > - > ### ** Examples - > - ... - > - > # Create example metadata - > # Please ensure the sample IDs in the metadata have the column name "sample_name" - > metadata_example <- data.frame(sample_name = colnames(kegg_abundance_example), - + group = factor(rep(c("Control", "Treatment"), each = 5))) - > - > pca_plot <- pathway_pca(kegg_abundance_example, metadata_example, "group") - Error in identicalUnits(x) : object is not a unit - Calls: pathway_pca ... assemble_guides -> guides_build -> unit.c -> identicalUnits - Execution halted - ``` - -## In both - -* checking installed package size ... NOTE - ``` - installed size is 5.5Mb - sub-directories of 1Mb or more: - R 2.1Mb - data 2.0Mb - ``` - -# ggpie - -
- -* Version: 0.2.5 -* GitHub: https://github.com/showteeth/ggpie -* Source code: https://github.com/cran/ggpie -* Date/Publication: 2022-11-16 07:40:06 UTC -* Number of recursive dependencies: 59 - -Run `revdepcheck::cloud_details(, "ggpie")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘ggpie-Ex.R’ failed - The error most likely occurred in: - - > ### Name: ggnestedpie - > ### Title: Create nested pie plot. - > ### Aliases: ggnestedpie - > - > ### ** Examples - > - > library(ggpie) - ... - > data(diamonds) - > # inner circle label, outer circle label and in pie plot - > ggnestedpie( - + data = diamonds, group_key = c("cut", "color"), count_type = "full", - + inner_label_info = "all", inner_label_split = NULL, - + outer_label_type = "circle", outer_label_pos = "in", outer_label_info = "all" - + ) - Error in names(labels) <- `*vtmp*` : attempt to set an attribute on NULL - Calls: ggnestedpie ... ggplot_add -> ggplot_add.new_aes -> bump_aes_labels - Execution halted - ``` - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘ggpie.Rmd’ - ... - - > cowplot::plot_grid(p1, p2, p3, p4, ncol = 2) - - > ggnestedpie(data = diamonds, group_key = c("cut", - + "color"), count_type = "full", inner_label_info = "all", - + inner_label_split = NULL, i .... [TRUNCATED] - - When sourcing ‘ggpie.R’: - Error: attempt to set an attribute on NULL - Execution halted - - ‘ggpie.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘ggpie.Rmd’ using rmarkdown - ``` - -# ggplotlyExtra - -
- -* Version: 0.0.1 -* GitHub: NA -* Source code: https://github.com/cran/ggplotlyExtra -* Date/Publication: 2019-12-02 16:20:06 UTC -* Number of recursive dependencies: 70 - -Run `revdepcheck::cloud_details(, "ggplotlyExtra")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘ggplotlyExtra-Ex.R’ failed - The error most likely occurred in: - - > ### Name: ggplotly_histogram - > ### Title: Clean 'ggplot2' Histogram to be Converted to 'Plotly' - > ### Aliases: ggplotly_histogram - > - > ### ** Examples - > - > - ... - + xlab("len") - `stat_bin()` using `bins = 30`. Pick better value with `binwidth`. - Warning in geom_bar(data = layerdata, mapping = aes(x = .data$x, y = .data$count, : - Ignoring unknown aesthetics: label1, label2, and label3 - > - > # convert `ggplot` object to `plotly` object - > ggplotly(p, tooltip = c("Range", "count", "density")) - Error in pm[[2]] : subscript out of bounds - Calls: ggplotly -> ggplotly.ggplot -> gg2list - Execution halted - ``` - -## In both - -* checking LazyData ... NOTE - ``` - 'LazyData' is specified without a 'data' directory - ``` - -# ggpol - -
- -* Version: 0.0.7 -* GitHub: https://github.com/erocoar/ggpol -* Source code: https://github.com/cran/ggpol -* Date/Publication: 2020-11-08 13:40:02 UTC -* Number of recursive dependencies: 54 - -Run `revdepcheck::cloud_details(, "ggpol")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘ggpol-Ex.R’ failed - The error most likely occurred in: - - > ### Name: GeomConfmat - > ### Title: Confusion Matrix - > ### Aliases: GeomConfmat geom_confmat stat_confmat - > - > ### ** Examples - > - > x <- sample(LETTERS[seq(4)], 50, replace = TRUE) - ... - 21. │ └─ggpol (local) draw_panel(...) - 22. │ └─base::lapply(GeomText$default_aes[missing_aes], rlang::eval_tidy) - 23. │ └─rlang (local) FUN(X[[i]], ...) - 24. ├─ggplot2::from_theme(fontsize) - 25. └─base::.handleSimpleError(...) - 26. └─rlang (local) h(simpleError(msg, call)) - 27. └─handlers[[1L]](cnd) - 28. └─cli::cli_abort(...) - 29. └─rlang::abort(...) - Execution halted - ``` - -## In both - -* checking dependencies in R code ... NOTE - ``` - Namespaces in Imports field not imported from: - ‘dplyr’ ‘grDevices’ - All declared Imports should be used. - ``` - -* checking LazyData ... NOTE - ``` - 'LazyData' is specified without a 'data' directory - ``` - -# ggpubr - -
- -* Version: 0.6.0 -* GitHub: https://github.com/kassambara/ggpubr -* Source code: https://github.com/cran/ggpubr -* Date/Publication: 2023-02-10 16:20:02 UTC -* Number of recursive dependencies: 88 - -Run `revdepcheck::cloud_details(, "ggpubr")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(ggpubr) - Loading required package: ggplot2 - > - > test_check("ggpubr") - [ FAIL 2 | WARN 5 | SKIP 0 | PASS 183 ] - - ... - [6] 6 - 10 == -4 - [7] 19 - 9 == 10 - [9] 1 - 7 == -6 - [10] 6 - 7 == -1 - [11] 13 - 6 == 7 - ... - - [ FAIL 2 | WARN 5 | SKIP 0 | PASS 183 ] - Error: Test failures - Execution halted - ``` - -# ggraph - -
- -* Version: 2.2.1 -* GitHub: https://github.com/thomasp85/ggraph -* Source code: https://github.com/cran/ggraph -* Date/Publication: 2024-03-07 12:40:02 UTC -* Number of recursive dependencies: 115 - -Run `revdepcheck::cloud_details(, "ggraph")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘ggraph-Ex.R’ failed - The error most likely occurred in: - - > ### Name: geom_conn_bundle - > ### Title: Create hierarchical edge bundles between node connections - > ### Aliases: geom_conn_bundle geom_conn_bundle2 geom_conn_bundle0 - > - > ### ** Examples - > - > # Create a graph of the flare class system - ... - + ) + - + geom_node_point(aes(filter = leaf, colour = class)) + - + scale_edge_colour_distiller('', direction = 1, guide = 'edge_direction') + - + coord_fixed() + - + ggforce::theme_no_axes() - Error in get_layer_key(...) : - unused argument (list(list("black", 0.5, 1, "butt", FALSE, "black", TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), list(NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), 5.5, c(5.5, 5.5, 5.5, 5.5), NULL, list(), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.75, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, - NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, 90, NULL, c(0, 2.75, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 1, NULL, NULL, NULL, c(0, 2.2, 0, 0), NULL, TRUE), NULL, list(NUL - Calls: ... -> -> process_layers -> - Execution halted - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘Edges.Rmd’ using rmarkdown - ``` - -## In both - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘Edges.Rmd’ - ... - Warning in grid.Call.graphics(C_text, as.graphicsAnnot(x$label), x$x, x$y, : - font family 'Arial Narrow' not found in PostScript font database - Warning in grid.Call.graphics(C_text, as.graphicsAnnot(x$label), x$x, x$y, : - font family 'Arial Narrow' not found in PostScript font database - Warning in grid.Call.graphics(C_text, as.graphicsAnnot(x$label), x$x, x$y, : - font family 'Arial Narrow' not found in PostScript font database - - ... - font family 'Arial' not found in PostScript font database - - When sourcing ‘tidygraph.R’: - Error: invalid font type - Execution halted - - ‘Edges.Rmd’ using ‘UTF-8’... failed - ‘Layouts.Rmd’ using ‘UTF-8’... failed - ‘Nodes.Rmd’ using ‘UTF-8’... failed - ‘tidygraph.Rmd’ using ‘UTF-8’... failed - ``` - -* checking installed package size ... NOTE - ``` - installed size is 9.0Mb - sub-directories of 1Mb or more: - R 1.5Mb - doc 3.9Mb - libs 2.9Mb - ``` - -# ggredist - -
- -* Version: 0.0.2 -* GitHub: https://github.com/alarm-redist/ggredist -* Source code: https://github.com/cran/ggredist -* Date/Publication: 2022-11-23 11:20:02 UTC -* Number of recursive dependencies: 67 - -Run `revdepcheck::cloud_details(, "ggredist")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘ggredist-Ex.R’ failed - The error most likely occurred in: - - > ### Name: geom_district_text - > ### Title: Label Map Regions - > ### Aliases: geom_district_text geom_district_label - > ### stat_district_coordinates StatDistrictCoordinates GeomDistrictText - > ### Keywords: datasets - > - > ### ** Examples - ... - 22. │ └─coord$transform(data, panel_params) - 23. │ └─ggplot2 (local) transform(..., self = self) - 24. │ └─ggplot2:::sf_rescale01(...) - 25. │ └─sf::st_normalize(x, c(x_range[1], y_range[1], x_range[2], y_range[2])) - 26. └─base::.handleSimpleError(...) - 27. └─rlang (local) h(simpleError(msg, call)) - 28. └─handlers[[1L]](cnd) - 29. └─cli::cli_abort(...) - 30. └─rlang::abort(...) - Execution halted - ``` - -# ggRtsy - -
- -* Version: 0.1.0 -* GitHub: NA -* Source code: https://github.com/cran/ggRtsy -* Date/Publication: 2023-09-15 19:12:05 UTC -* Number of recursive dependencies: 69 - -Run `revdepcheck::cloud_details(, "ggRtsy")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(ggplot2) - > library(dplyr) - - Attaching package: 'dplyr' - - The following object is masked from 'package:testthat': - ... - 13. │ │ └─base (local) doTryCatch(return(expr), name, parentenv, handler) - 14. │ └─vctrs::vec_as_location(i, n, names = names, arg = arg, call = call) - 15. └─vctrs (local) ``() - 16. └─vctrs:::stop_subscript_oob(...) - 17. └─vctrs:::stop_subscript(...) - 18. └─rlang::abort(...) - - [ FAIL 1 | WARN 0 | SKIP 0 | PASS 3 ] - Error: Test failures - Execution halted - ``` - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘Vignette.Rmd’ - ... - |Antique White |(238, 223, 204) |#eedfcc | - - > RectangleFiller(plotExample, c("#e32636", "#9966cc", - + "#f4c2c2", "#e16827")) - - When sourcing ‘Vignette.R’: - Error: Can't extract rows past the end. - ℹ Location 1 doesn't exist. - ℹ There are only 0 rows. - Execution halted - - ‘Vignette.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - ... - --- re-building ‘Vignette.Rmd’ using rmarkdown - - Quitting from lines 48-49 [unnamed-chunk-2] (Vignette.Rmd) - Error: processing vignette 'Vignette.Rmd' failed with diagnostics: - Can't extract rows past the end. - ℹ Location 1 doesn't exist. - ℹ There are only 0 rows. - --- failed re-building ‘Vignette.Rmd’ - - SUMMARY: processing the following file failed: - ‘Vignette.Rmd’ - - Error: Vignette re-building failed. - Execution halted - ``` - -## In both - -* checking data for non-ASCII characters ... NOTE - ``` - Note: found 19 marked UTF-8 strings - ``` - -# ggseqplot - -
- -* Version: 0.8.4 -* GitHub: https://github.com/maraab23/ggseqplot -* Source code: https://github.com/cran/ggseqplot -* Date/Publication: 2024-05-17 21:40:03 UTC -* Number of recursive dependencies: 139 - -Run `revdepcheck::cloud_details(, "ggseqplot")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘ggseqplot-Ex.R’ failed - The error most likely occurred in: - - > ### Name: ggseqmsplot - > ### Title: Modal State Sequence Plot - > ### Aliases: ggseqmsplot - > - > ### ** Examples - > - > # Use example data from TraMineR: actcal data set - ... - 11. │ └─base::withCallingHandlers(...) - 12. └─ggplot2 (local) f(l = layers[[i]], d = data[[i]]) - 13. └─l$compute_geom_2(d, theme = plot$theme) - 14. └─ggplot2 (local) compute_geom_2(..., self = self) - 15. └─self$geom$use_defaults(...) - 16. └─ggplot2 (local) use_defaults(..., self = self) - 17. └─ggplot2:::check_aesthetics(new_params, nrow(data)) - 18. └─cli::cli_abort(...) - 19. └─rlang::abort(...) - Execution halted - ``` - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(ggseqplot) - Loading required package: TraMineR - - TraMineR stable version 2.2-10 (Built: 2024-05-22) - Website: http://traminer.unige.ch - Please type 'citation("TraMineR")' for citation information. - ... - Backtrace: - ▆ - 1. ├─testthat::expect_s3_class(ggseqtrplot(biofam.seq), "ggplot") at test-ggseqtrplot.R:35:3 - 2. │ └─testthat::quasi_label(enquo(object), arg = "object") - 3. │ └─rlang::eval_bare(expr, quo_get_env(quo)) - 4. └─ggseqplot::ggseqtrplot(biofam.seq) - - [ FAIL 1 | WARN 1036 | SKIP 0 | PASS 131 ] - Error: Test failures - Execution halted - ``` - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘ggseqplot.Rmd’ - ... - > p1 + p2 + plot_layout(guides = "collect") & scale_fill_manual(values = canva_palettes$`Fun and tropical`[1:4]) & - + theme_ipsum(base_family = "" .... [TRUNCATED] - Scale for fill is already present. - Adding another scale for fill, which will replace the existing scale. - Scale for fill is already present. - Adding another scale for fill, which will replace the existing scale. - - When sourcing ‘ggseqplot.R’: - Error: object is not coercible to a unit - Execution halted - - ‘ggseqplot.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘ggseqplot.Rmd’ using rmarkdown - ``` - -# ggside - -
- -* Version: 0.3.1 -* GitHub: https://github.com/jtlandis/ggside -* Source code: https://github.com/cran/ggside -* Date/Publication: 2024-03-01 09:12:37 UTC -* Number of recursive dependencies: 76 - -Run `revdepcheck::cloud_details(, "ggside")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(ggplot2) - > library(ggside) - Registered S3 method overwritten by 'ggside': - method from - +.gg ggplot2 - > - ... - • ops_meaningful/alpha-0-5-from-function.svg - • side_layers/boxplot2.svg - • vdiff_irisScatter/collapsed-histo.svg - • vdiff_irisScatter/facetgrid-collapsed-density.svg - • vdiff_irisScatter/facetgrid-histo.svg - • vdiff_irisScatter/facetgrid-side-density.svg - • vdiff_irisScatter/stacked-side-density.svg - • vdiff_irisScatter/yside-histo.svg - Error: Test failures - Execution halted - ``` - -* checking for code/documentation mismatches ... WARNING - ``` - Codoc mismatches from documentation object 'geom_xsideabline': - geom_xsidehline - Code: function(mapping = NULL, data = NULL, position = "identity", - ..., yintercept, na.rm = FALSE, show.legend = NA) - Docs: function(mapping = NULL, data = NULL, ..., yintercept, na.rm = - FALSE, show.legend = NA) - Argument names in code not in docs: - position - Mismatches in argument names (first 3): - Position: 3 Code: position Docs: ... - ... - Docs: function(mapping = NULL, data = NULL, stat = "identity", - position = "identity", ..., lineend = "butt", linejoin - = "round", linemitre = 10, arrow = NULL, na.rm = - FALSE, show.legend = NA, inherit.aes = TRUE) - Argument names in code not in docs: - arrow.fill - Mismatches in argument names: - Position: 10 Code: arrow.fill Docs: na.rm - Position: 11 Code: na.rm Docs: show.legend - Position: 12 Code: show.legend Docs: inherit.aes - ``` - -# ggspatial - -
- -* Version: 1.1.9 -* GitHub: https://github.com/paleolimbot/ggspatial -* Source code: https://github.com/cran/ggspatial -* Date/Publication: 2023-08-17 15:32:38 UTC -* Number of recursive dependencies: 108 - -Run `revdepcheck::cloud_details(, "ggspatial")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘ggspatial-Ex.R’ failed - The error most likely occurred in: - - > ### Name: annotation_spatial_hline - > ### Title: Projected horizontal and vertical lines - > ### Aliases: annotation_spatial_hline annotation_spatial_vline - > ### GeomSpatialXline - > ### Keywords: datasets - > - > ### ** Examples - ... - 25. │ └─grid:::validGP(list(...)) - 26. │ └─grid (local) numnotnull("fontsize") - 27. │ └─grid (local) check.length(gparname) - 28. │ └─base::stop(...) - 29. └─base::.handleSimpleError(...) - 30. └─rlang (local) h(simpleError(msg, call)) - 31. └─handlers[[1L]](cnd) - 32. └─cli::cli_abort(...) - 33. └─rlang::abort(...) - Execution halted - ``` - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(ggspatial) - > - > test_check("ggspatial") - Linking to GEOS 3.10.2, GDAL 3.4.1, PROJ 8.2.1; sf_use_s2() is TRUE - [ FAIL 1 | WARN 1 | SKIP 22 | PASS 195 ] - - ... - 33. │ └─base::stop(...) - 34. └─base::.handleSimpleError(...) - 35. └─rlang (local) h(simpleError(msg, call)) - 36. └─handlers[[1L]](cnd) - 37. └─cli::cli_abort(...) - 38. └─rlang::abort(...) - - [ FAIL 1 | WARN 1 | SKIP 22 | PASS 195 ] - Error: Test failures - Execution halted - ``` - -# ggtern - -
- -* Version: 3.5.0 -* GitHub: NA -* Source code: https://github.com/cran/ggtern -* Date/Publication: 2024-03-24 21:50:02 UTC -* Number of recursive dependencies: 42 - -Run `revdepcheck::cloud_details(, "ggtern")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘ggtern-Ex.R’ failed - The error most likely occurred in: - - > ### Name: annotate - > ### Title: Create an annotation layer (ggtern version). - > ### Aliases: annotate - > - > ### ** Examples - > - > ggtern() + - ... - 3. ├─ggtern::ggplot_build(x) - 4. └─ggtern:::ggplot_build.ggplot(x) - 5. └─ggtern:::layers_add_or_remove_mask(plot) - 6. └─ggint$plot_theme(plot) - 7. └─ggplot2:::validate_theme(theme) - 8. └─base::mapply(...) - 9. └─ggplot2 (local) ``(...) - 10. └─cli::cli_abort(...) - 11. └─rlang::abort(...) - Execution halted - ``` - -## In both - -* checking package dependencies ... NOTE - ``` - Package which this enhances but not available for checking: ‘sp’ - ``` - -* checking Rd cross-references ... NOTE - ``` - Package unavailable to check Rd xrefs: ‘chemometrics’ - ``` - -# ggupset - -
- -* Version: 0.4.0 -* GitHub: https://github.com/const-ae/ggupset -* Source code: https://github.com/cran/ggupset -* Date/Publication: 2024-06-24 10:10:04 UTC -* Number of recursive dependencies: 46 - -Run `revdepcheck::cloud_details(, "ggupset")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘ggupset-Ex.R’ failed - The error most likely occurred in: - - > ### Name: axis_combmatrix - > ### Title: Convert delimited text labels into a combination matrix axis - > ### Aliases: axis_combmatrix - > - > ### ** Examples - > - > library(ggplot2) - ... - Datsun 710 Cyl: 4_Gears: 4 - Hornet 4 Drive Cyl: 6_Gears: 3 - Hornet Sportabout Cyl: 8_Gears: 3 - Valiant Cyl: 6_Gears: 3 - > ggplot(mtcars, aes(x=combined)) + - + geom_bar() + - + axis_combmatrix(sep = "_") - Error in as.unit(e2) : object is not coercible to a unit - Calls: ... polylineGrob -> is.unit -> unit.c -> Ops.unit -> as.unit - Execution halted - ``` - -# ggVennDiagram - -
- -* Version: 1.5.2 -* GitHub: https://github.com/gaospecial/ggVennDiagram -* Source code: https://github.com/cran/ggVennDiagram -* Date/Publication: 2024-02-20 08:10:02 UTC -* Number of recursive dependencies: 98 - -Run `revdepcheck::cloud_details(, "ggVennDiagram")` for more info - -
- -## Newly broken - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘fully-customed.Rmd’ - ... - [1] "b" "c" "e" "h" "k" "q" "s" "y" - - - > ggVennDiagram(y, show_intersect = TRUE, set_color = "black") - Warning in geom_text(aes(label = .data$count, text = .data$item), data = region_label) : - Ignoring unknown aesthetics: text - - ... - Ignoring unknown aesthetics: text - - When sourcing ‘using-ggVennDiagram.R’: - Error: subscript out of bounds - Execution halted - - ‘VennCalculator.Rmd’ using ‘UTF-8’... OK - ‘fully-customed.Rmd’ using ‘UTF-8’... failed - ‘using-ggVennDiagram.Rmd’ using ‘UTF-8’... failed - ‘using-new-shapes.Rmd’ using ‘UTF-8’... OK - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘VennCalculator.Rmd’ using rmarkdown - --- finished re-building ‘VennCalculator.Rmd’ - - --- re-building ‘fully-customed.Rmd’ using rmarkdown - ``` - -## In both - -* checking installed package size ... NOTE - ``` - installed size is 11.1Mb - sub-directories of 1Mb or more: - doc 9.5Mb - help 1.1Mb - ``` - -# greatR - -
- -* Version: 2.0.0 -* GitHub: https://github.com/ruthkr/greatR -* Source code: https://github.com/cran/greatR -* Date/Publication: 2024-04-09 22:40:07 UTC -* Number of recursive dependencies: 77 - -Run `revdepcheck::cloud_details(, "greatR")` for more info - -
- -## Newly broken - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘process-results.Rmd’ - ... - - > reg_summary$non_registered_genes - [1] "BRAA02G018970.3C" - - > plot(reg_summary, type = "registered", scatterplot_size = c(4, - + 3.5)) - - When sourcing ‘process-results.R’: - Error: object is not a unit - Execution halted - - ‘data-requirement.Rmd’ using ‘UTF-8’... OK - ‘process-results.Rmd’ using ‘UTF-8’... failed - ‘register-data-manually.Rmd’ using ‘UTF-8’... OK - ‘register-data.Rmd’ using ‘UTF-8’... OK - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - ... - --- re-building ‘data-requirement.Rmd’ using rmarkdown - --- finished re-building ‘data-requirement.Rmd’ - - --- re-building ‘process-results.Rmd’ using rmarkdown - - Quitting from lines 76-81 [plot-summary-results] (process-results.Rmd) - Error: processing vignette 'process-results.Rmd' failed with diagnostics: - object is not a unit - ... - --- finished re-building ‘register-data-manually.Rmd’ - - --- re-building ‘register-data.Rmd’ using rmarkdown - --- finished re-building ‘register-data.Rmd’ - - SUMMARY: processing the following file failed: - ‘process-results.Rmd’ - - Error: Vignette re-building failed. - Execution halted - ``` - -# Greymodels - -
- -* Version: 2.0.1 -* GitHub: https://github.com/havishaJ/Greymodels -* Source code: https://github.com/cran/Greymodels -* Date/Publication: 2022-12-05 12:42:35 UTC -* Number of recursive dependencies: 91 - -Run `revdepcheck::cloud_details(, "Greymodels")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘Greymodels-Ex.R’ failed - The error most likely occurred in: - - > ### Name: Plots - > ### Title: plots - > ### Aliases: plots plotrm plotsmv1 plotsmv2 plotsigndgm plots_mdbgm12 - > - > ### ** Examples - > - > # Plots - EPGM (1, 1) model - ... - + geom_point(data = set4, aes(x = CI, y = y), shape = 23, color = "black") + - + geom_line(data = xy1, aes(x = x, y = y,color = "Raw Data")) + - + geom_line(data = xy2, aes(x = x, y = y,color = "Fitted&Forecasts")) + - + geom_line(data = set3, aes(x = CI, y = y,color = "LowerBound"), linetype=2) + - + geom_line(data = set4, aes(x = CI, y = y,color = "UpperBound"), linetype=2) + - + scale_color_manual(name = "Label",values = colors) - > r <- ggplotly(p) - Error in pm[[2]] : subscript out of bounds - Calls: ggplotly -> ggplotly.ggplot -> gg2list - Execution halted - ``` - -# gtExtras - -
- -* Version: 0.5.0 -* GitHub: https://github.com/jthomasmock/gtExtras -* Source code: https://github.com/cran/gtExtras -* Date/Publication: 2023-09-15 22:32:06 UTC -* Number of recursive dependencies: 105 - -Run `revdepcheck::cloud_details(, "gtExtras")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(gtExtras) - Loading required package: gt - - Attaching package: 'gt' - - The following object is masked from 'package:testthat': - ... - ══ Failed tests ════════════════════════════════════════════════════════════════ - ── Failure ('test-gt_plt_bar.R:44:3'): gt_plt_bar svg is created and has specific values ── - `bar_neg_vals` (`actual`) not equal to c("49.19", "32.79", "16.40", "16.40", "32.79", "49.19") (`expected`). - - `actual`: "49.19" "32.79" "16.40" "0.00" "0.00" "0.00" - `expected`: "49.19" "32.79" "16.40" "16.40" "32.79" "49.19" - - [ FAIL 1 | WARN 14 | SKIP 23 | PASS 115 ] - Error: Test failures - Execution halted - ``` - -# HaploCatcher - -
- -* Version: 1.0.4 -* GitHub: NA -* Source code: https://github.com/cran/HaploCatcher -* Date/Publication: 2023-04-21 23:32:39 UTC -* Number of recursive dependencies: 112 - -Run `revdepcheck::cloud_details(, "HaploCatcher")` for more info - -
- -## Newly broken - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘An_Intro_to_HaploCatcher.Rmd’ - ... - > set.seed(NULL) - - > results1 <- auto_locus(geno_mat = geno_mat, gene_file = gene_comp, - + gene_name = "sst1_solid_stem", marker_info = marker_info, - + chromosom .... [TRUNCATED] - Loading required package: lattice - - When sourcing ‘An_Intro_to_HaploCatcher.R’: - Error: object is not a unit - Execution halted - - ‘An_Intro_to_HaploCatcher.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - ... - --- re-building ‘An_Intro_to_HaploCatcher.Rmd’ using rmarkdown - - Quitting from lines 242-253 [example_models_1] (An_Intro_to_HaploCatcher.Rmd) - Error: processing vignette 'An_Intro_to_HaploCatcher.Rmd' failed with diagnostics: - object is not a unit - --- failed re-building ‘An_Intro_to_HaploCatcher.Rmd’ - - SUMMARY: processing the following file failed: - ‘An_Intro_to_HaploCatcher.Rmd’ - - Error: Vignette re-building failed. - Execution halted - ``` - -# healthyR - -
- -* Version: 0.2.2 -* GitHub: https://github.com/spsanderson/healthyR -* Source code: https://github.com/cran/healthyR -* Date/Publication: 2024-07-01 13:20:02 UTC -* Number of recursive dependencies: 146 - -Run `revdepcheck::cloud_details(, "healthyR")` for more info - -
- -## Newly broken - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘getting-started.Rmd’ - ... - - > ts_alos_plt(.data = df_tbl, .date_col = Date, .value_col = Values, - + .by = "month", .interactive = FALSE) - - > ts_alos_plt(.data = df_tbl, .date_col = Date, .value_col = Values, - + .by = "month", .interactive = TRUE) - - When sourcing ‘getting-started.R’: - Error: subscript out of bounds - Execution halted - - ‘getting-started.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘getting-started.Rmd’ using rmarkdown - ``` - -## In both - -* checking installed package size ... NOTE - ``` - installed size is 6.6Mb - sub-directories of 1Mb or more: - data 2.5Mb - doc 3.7Mb - ``` - -# healthyR.ts - -
- -* Version: 0.3.0 -* GitHub: https://github.com/spsanderson/healthyR.ts -* Source code: https://github.com/cran/healthyR.ts -* Date/Publication: 2023-11-15 06:00:05 UTC -* Number of recursive dependencies: 221 - -Run `revdepcheck::cloud_details(, "healthyR.ts")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘healthyR.ts-Ex.R’ failed - The error most likely occurred in: - - > ### Name: tidy_fft - > ### Title: Tidy Style FFT - > ### Aliases: tidy_fft - > - > ### ** Examples - > - > suppressPackageStartupMessages(library(dplyr)) - ... - > a <- tidy_fft( - + .data = data_tbl, - + .value_col = value, - + .date_col = date_col, - + .harmonics = 3, - + .frequency = 12 - + ) - Error in pm[[2]] : subscript out of bounds - Calls: tidy_fft -> -> ggplotly.ggplot -> gg2list - Execution halted - ``` - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘using-tidy-fft.Rmd’ - ... - $ value 112, 118, 132, 129, 121, 135, 148, 148, 136, 119, 104, 118, 1… - - > suppressPackageStartupMessages(library(timetk)) - - > data_tbl %>% plot_time_series(.date_var = date_col, - + .value = value) - - When sourcing ‘using-tidy-fft.R’: - Error: subscript out of bounds - Execution halted - - ‘getting-started.Rmd’ using ‘UTF-8’... OK - ‘using-tidy-fft.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘getting-started.Rmd’ using rmarkdown - ``` - -## In both - -* checking installed package size ... NOTE - ``` - installed size is 6.3Mb - sub-directories of 1Mb or more: - doc 5.2Mb - ``` - -# heatmaply - -
- -* Version: 1.5.0 -* GitHub: https://github.com/talgalili/heatmaply -* Source code: https://github.com/cran/heatmaply -* Date/Publication: 2023-10-06 20:50:02 UTC -* Number of recursive dependencies: 111 - -Run `revdepcheck::cloud_details(, "heatmaply")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(heatmaply) - Loading required package: plotly - Loading required package: ggplot2 - - Attaching package: 'plotly' - - ... - 4. │ │ └─base::withCallingHandlers(...) - 5. │ └─rlang::eval_bare(quo_get_expr(.quo), quo_get_env(.quo)) - 6. ├─heatmaply:::predict_colors(ggplotly(g), plot_method = "ggplot") - 7. ├─plotly::ggplotly(g) - 8. └─plotly:::ggplotly.ggplot(g) - 9. └─plotly::gg2list(...) - - [ FAIL 58 | WARN 0 | SKIP 0 | PASS 193 ] - Error: Test failures - Execution halted - ``` - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘heatmaply.Rmd’ - ... - - > library("heatmaply") - - > library("heatmaply") - - > heatmaply(mtcars) - - When sourcing ‘heatmaply.R’: - Error: subscript out of bounds - Execution halted - - ‘heatmaply.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - ... - --- re-building ‘heatmaply.Rmd’ using rmarkdown - - Quitting from lines 109-111 [unnamed-chunk-5] (heatmaply.Rmd) - Error: processing vignette 'heatmaply.Rmd' failed with diagnostics: - subscript out of bounds - --- failed re-building ‘heatmaply.Rmd’ - - SUMMARY: processing the following file failed: - ‘heatmaply.Rmd’ - - Error: Vignette re-building failed. - Execution halted - ``` - -## In both - -* checking installed package size ... NOTE - ``` - installed size is 5.5Mb - sub-directories of 1Mb or more: - doc 5.1Mb - ``` - -# hermiter - -
- -* Version: 2.3.1 -* GitHub: https://github.com/MikeJaredS/hermiter -* Source code: https://github.com/cran/hermiter -* Date/Publication: 2024-03-06 23:50:02 UTC -* Number of recursive dependencies: 79 - -Run `revdepcheck::cloud_details(, "hermiter")` for more info - -
- -## Newly broken - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘hermiter.Rmd’ - ... - > p2 <- ggplot(df_pdf_cdf) + geom_tile(aes(X, Y, fill = pdf_est)) + - + scale_fill_continuous_sequential(palette = "Oslo", breaks = seq(0, - + .... [TRUNCATED] - - > p1 + ggtitle("Actual PDF") + theme(legend.title = element_blank()) + - + p2 + ggtitle("Estimated PDF") + theme(legend.title = element_blank()) + .... [TRUNCATED] - - When sourcing ‘hermiter.R’: - Error: object is not a unit - Execution halted - - ‘hermiter.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘hermiter.Rmd’ using rmarkdown - ``` - -## In both - -* checking installed package size ... NOTE - ``` - installed size is 6.5Mb - sub-directories of 1Mb or more: - R 2.6Mb - doc 1.9Mb - libs 1.8Mb - ``` - -* checking for GNU extensions in Makefiles ... NOTE - ``` - GNU make is a SystemRequirements. - ``` - -# hesim - -
- -* Version: 0.5.4 -* GitHub: https://github.com/hesim-dev/hesim -* Source code: https://github.com/cran/hesim -* Date/Publication: 2024-02-12 01:10:03 UTC -* Number of recursive dependencies: 107 - -Run `revdepcheck::cloud_details(, "hesim")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(hesim) - > - > test_check("hesim") - sample = 1 - sample = 2 - [ FAIL 4 | WARN 0 | SKIP 0 | PASS 1121 ] - ... - ── Failure ('test-plot.R:95:3'): autoplot.stateprobs() allows confidence intervals ── - p$labels$fill not equal to "strategy_id". - target is NULL, current is character - ── Failure ('test-plot.R:99:3'): autoplot.stateprobs() allows confidence intervals ── - p$labels$fill not equal to "strategy_id". - target is NULL, current is character - - [ FAIL 4 | WARN 0 | SKIP 0 | PASS 1121 ] - Error: Test failures - Execution halted - ``` - -## In both - -* checking installed package size ... NOTE - ``` - installed size is 37.4Mb - sub-directories of 1Mb or more: - R 1.5Mb - data 1.5Mb - doc 2.2Mb - libs 31.4Mb - ``` - -* checking dependencies in R code ... NOTE - ``` - Namespace in Imports field not imported from: ‘R6’ - All declared Imports should be used. - ``` - -# hidecan - -
- -* Version: 1.1.0 -* GitHub: https://github.com/PlantandFoodResearch/hidecan -* Source code: https://github.com/cran/hidecan -* Date/Publication: 2023-02-10 09:40:02 UTC -* Number of recursive dependencies: 90 - -Run `revdepcheck::cloud_details(, "hidecan")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > # This file is part of the standard setup for testthat. - > # It is recommended that you do not modify it. - > # - > # Where should you do additional test configuration? - > # Learn more about the roles of various files in: - > # * https://r-pkgs.org/tests.html - > # * https://testthat.r-lib.org/reference/test_package.html#special-files - ... - 8. └─hidecan::create_hidecan_plot(...) - 9. └─ggplot2:::`+.gg`(p, ggnewscale::new_scale_fill()) - 10. └─ggplot2:::add_ggplot(e1, e2, e2name) - 11. ├─ggplot2::ggplot_add(object, p, objectname) - 12. └─ggnewscale:::ggplot_add.new_aes(object, p, objectname) - 13. └─ggnewscale:::bump_aes_labels(plot$labels, new_aes = object) - - [ FAIL 4 | WARN 0 | SKIP 1 | PASS 89 ] - Error: Test failures - Execution halted - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - ... - --- re-building ‘hidecan-step-by-step.Rmd’ using rmarkdown - - Quitting from lines 168-174 [create-hidecan-plot] (hidecan-step-by-step.Rmd) - Error: processing vignette 'hidecan-step-by-step.Rmd' failed with diagnostics: - attempt to set an attribute on NULL - --- failed re-building ‘hidecan-step-by-step.Rmd’ - - --- re-building ‘hidecan.Rmd’ using rmarkdown - ... - Quitting from lines 97-105 [hidecan-plot] (hidecan.Rmd) - Error: processing vignette 'hidecan.Rmd' failed with diagnostics: - attempt to set an attribute on NULL - --- failed re-building ‘hidecan.Rmd’ - - SUMMARY: processing the following files failed: - ‘hidecan-step-by-step.Rmd’ ‘hidecan.Rmd’ - - Error: Vignette re-building failed. - Execution halted - ``` - -## In both - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘hidecan-step-by-step.Rmd’ - ... - 5 PGSC0003DMG400005279 ST4.03ch05 42523943 42525912 peroxida… peroxida… 4.25e7 - 6 PGSC0003DMG400007782 ST4.03ch03 38537202 38540209 PHO1A PHO1A 3.85e7 - - > gwas_wrong_input <- select(x[["GWAS"]], -chromosome) - - > GWAS_data(gwas_wrong_input) - - ... - - > hidecan_plot(gwas_list = x[["GWAS"]], de_list = x[["DE"]], - + can_list = x[["CAN"]], score_thr_gwas = -log10(1e-04), score_thr_de = -log10(0.05) .... [TRUNCATED] - - When sourcing ‘hidecan.R’: - Error: attempt to set an attribute on NULL - Execution halted - - ‘hidecan-step-by-step.Rmd’ using ‘UTF-8’... failed - ‘hidecan.Rmd’ using ‘UTF-8’... failed - ``` - -# HVT - -
- -* Version: 24.5.2 -* GitHub: https://github.com/Mu-Sigma/HVT -* Source code: https://github.com/cran/HVT -* Date/Publication: 2024-05-15 08:50:21 UTC -* Number of recursive dependencies: 200 - -Run `revdepcheck::cloud_details(, "HVT")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘HVT-Ex.R’ failed - The error most likely occurred in: - - > ### Name: getTransitionProbability - > ### Title: Creating Transition Probabilities list - > ### Aliases: getTransitionProbability - > ### Keywords: Transition_or_Prediction - > - > ### ** Examples - > - ... - Ignoring unknown parameters: `check_overlap` - Scale for x is already present. - Adding another scale for x, which will replace the existing scale. - Scale for y is already present. - Adding another scale for y, which will replace the existing scale. - Warning in geom_polygon(data = boundaryCoords2, aes(x = bp.x, y = bp.y, : - Ignoring unknown aesthetics: text - Error in pm[[2]] : subscript out of bounds - Calls: scoreHVT -> -> ggplotly.ggplot -> gg2list - Execution halted - ``` - -# hypsoLoop - -
- -* Version: 0.2.0 -* GitHub: NA -* Source code: https://github.com/cran/hypsoLoop -* Date/Publication: 2022-02-08 09:00:02 UTC -* Number of recursive dependencies: 97 - -Run `revdepcheck::cloud_details(, "hypsoLoop")` for more info - -
- -## Newly broken - -* checking whether package ‘hypsoLoop’ can be installed ... WARNING - ``` - Found the following significant warnings: - Warning: replacing previous import ‘ggplot2::set_theme’ by ‘sjPlot::set_theme’ when loading ‘hypsoLoop’ - See ‘/tmp/workdir/hypsoLoop/new/hypsoLoop.Rcheck/00install.out’ for details. - ``` - -# ICvectorfields - -
- -* Version: 0.1.2 -* GitHub: https://github.com/goodsman/ICvectorfields -* Source code: https://github.com/cran/ICvectorfields -* Date/Publication: 2022-02-26 22:30:02 UTC -* Number of recursive dependencies: 93 - -Run `revdepcheck::cloud_details(, "ICvectorfields")` for more info - -
- -## Newly broken - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘Using_ICvectorfields.Rmd’ - ... - 3 -3.89153024 -0.09851975 - 4 -0.09851975 3.89153024 - - > SimVF = ggplot() + xlim(c(-5, 5)) + ylim(c(-5, 5)) + - + geom_raster(data = SimData, aes(x = xcoord, y = ycoord, fill = t1)) + - + scale_fill_ .... [TRUNCATED] - - When sourcing ‘Using_ICvectorfields.R’: - Error: attempt to set an attribute on NULL - Execution halted - - ‘Using_ICvectorfields.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘Using_ICvectorfields.Rmd’ using rmarkdown - ``` - -# idopNetwork - -
- -* Version: 0.1.2 -* GitHub: https://github.com/cxzdsa2332/idopNetwork -* Source code: https://github.com/cran/idopNetwork -* Date/Publication: 2023-04-18 06:50:02 UTC -* Number of recursive dependencies: 77 - -Run `revdepcheck::cloud_details(, "idopNetwork")` for more info - -
- -## Newly broken - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘idopNetwork_vignette.Rmd’ - ... - - > qdODE_plot_base(ode.test) - - > ode.module = test_result$d1_module - - > qdODE_plot_all(ode.module) - - When sourcing ‘idopNetwork_vignette.R’: - Error: object is not a unit - Execution halted - - ‘idopNetwork_vignette.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘idopNetwork_vignette.Rmd’ using rmarkdown - ``` - -# inferCSN - -
- -* Version: 1.0.5 -* GitHub: https://github.com/mengxu98/inferCSN -* Source code: https://github.com/cran/inferCSN -* Date/Publication: 2024-06-26 12:10:02 UTC -* Number of recursive dependencies: 185 - -Run `revdepcheck::cloud_details(, "inferCSN")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘inferCSN-Ex.R’ failed - The error most likely occurred in: - - > ### Name: plot_dynamic_networks - > ### Title: plot_dynamic_networks - > ### Aliases: plot_dynamic_networks - > - > ### ** Examples - > - > data("example_matrix") - ... - > ## End(Not run) - > - > plot_dynamic_networks( - + network, - + celltypes_order = celltypes_order, - + plot_type = "ggplotly" - + ) - Error in pm[[2]] : subscript out of bounds - Calls: plot_dynamic_networks -> -> ggplotly.ggplot -> gg2list - Execution halted - ``` - -## In both - -* checking installed package size ... NOTE - ``` - installed size is 22.5Mb - sub-directories of 1Mb or more: - data 2.0Mb - libs 20.0Mb - ``` - -# insurancerating - -
- -* Version: 0.7.4 -* GitHub: https://github.com/mharinga/insurancerating -* Source code: https://github.com/cran/insurancerating -* Date/Publication: 2024-05-20 11:30:03 UTC -* Number of recursive dependencies: 133 - -Run `revdepcheck::cloud_details(, "insurancerating")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘insurancerating-Ex.R’ failed - The error most likely occurred in: - - > ### Name: autoplot.univariate - > ### Title: Automatically create a ggplot for objects obtained from - > ### univariate() - > ### Aliases: autoplot.univariate - > - > ### ** Examples - > - ... - > xzip <- univariate(MTPL, x = bm, severity = amount, nclaims = nclaims, - + exposure = exposure, by = zip) - > autoplot(xzip, show_plots = 1:2) - Warning: Removed 16 rows containing missing values or values outside the scale range - (`geom_point()`). - Warning: Removed 5 rows containing missing values or values outside the scale range - (`geom_line()`). - Error in identicalUnits(x) : object is not a unit - Calls: ... assemble_guides -> guides_build -> unit.c -> identicalUnits - Execution halted - ``` - -# inTextSummaryTable - -
- -* Version: 3.3.3 -* GitHub: https://github.com/openanalytics/inTextSummaryTable -* Source code: https://github.com/cran/inTextSummaryTable -* Date/Publication: 2024-06-12 18:30:02 UTC -* Number of recursive dependencies: 123 - -Run `revdepcheck::cloud_details(, "inTextSummaryTable")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(inTextSummaryTable) - > - > test_check("inTextSummaryTable") - [ FAIL 59 | WARN 0 | SKIP 0 | PASS 881 ] - - ══ Failed tests ════════════════════════════════════════════════════════════════ - ... - 5. │ └─rlang::eval_bare(quo_get_expr(.quo), quo_get_env(.quo)) - 6. └─inTextSummaryTable::subjectProfileSummaryPlot(...) - 7. ├─base::do.call(plyr::rbind.fill, ggplot_build(gg)$data) - 8. └─plyr (local) ``(``, ``) - 9. └─plyr:::output_template(dfs, nrows) - 10. └─plyr:::allocate_column(df[[var]], nrows, dfs, var) - - [ FAIL 59 | WARN 0 | SKIP 0 | PASS 881 ] - Error: Test failures - Execution halted - ``` - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘inTextSummaryTable-aesthetics.Rmd’ - ... - > subjectProfileSummaryPlot(data = summaryTable, xVar = "visit", - + colorVar = "TRT") - - When sourcing ‘inTextSummaryTable-aesthetics.R’: - Error: Problem while setting up geom aesthetics. - ℹ Error occurred in the 2nd layer. - Caused by error in `check_aesthetics()`: - ... - ✖ Fix the following mappings: `size`. - Execution halted - - ‘inTextSummaryTable-advanced.Rmd’ using ‘UTF-8’... OK - ‘inTextSummaryTable-aesthetics.Rmd’ using ‘UTF-8’... failed - ‘inTextSummaryTable-createTables.Rmd’ using ‘UTF-8’... OK - ‘inTextSummaryTable-exportTables.Rmd’ using ‘UTF-8’... OK - ‘inTextSummaryTable-introduction.Rmd’ using ‘UTF-8’... OK - ‘inTextSummaryTable-standardTables.Rmd’ using ‘UTF-8’... OK - ‘inTextSummaryTable-visualization.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘inTextSummaryTable-advanced.Rmd’ using rmarkdown - --- finished re-building ‘inTextSummaryTable-advanced.Rmd’ - - --- re-building ‘inTextSummaryTable-aesthetics.Rmd’ using rmarkdown - - Quitting from lines 211-224 [aesthetics-defaultsVisualization] (inTextSummaryTable-aesthetics.Rmd) - Error: processing vignette 'inTextSummaryTable-aesthetics.Rmd' failed with diagnostics: - Problem while setting up geom aesthetics. - ℹ Error occurred in the 2nd layer. - ... - ! Aesthetics must be either length 1 or the same as the data (28). - ✖ Fix the following mappings: `size`. - --- failed re-building ‘inTextSummaryTable-visualization.Rmd’ - - SUMMARY: processing the following files failed: - ‘inTextSummaryTable-aesthetics.Rmd’ - ‘inTextSummaryTable-visualization.Rmd’ - - Error: Vignette re-building failed. - Execution halted - ``` - -## In both - -* checking installed package size ... NOTE - ``` - installed size is 10.3Mb - sub-directories of 1Mb or more: - doc 9.7Mb - ``` - -# inventorize - -
- -* Version: 1.1.1 -* GitHub: NA -* Source code: https://github.com/cran/inventorize -* Date/Publication: 2022-05-31 22:20:09 UTC -* Number of recursive dependencies: 71 - -Run `revdepcheck::cloud_details(, "inventorize")` for more info - -
- -## Newly broken - -* checking whether package ‘inventorize’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/inventorize/new/inventorize.Rcheck/00install.out’ for details. - ``` - -## Installation - -### Devel +# activAnalyzer (patchwork) +# actxps (thematic) + +# AeRobiology (unknown) + +``` +#
+# +# * Version: 2.0.1 +# * GitHub: NA +# * Source code: https://github.com/cran/AeRobiology +# * Date/Publication: 2019-06-03 06:20:03 UTC +# * Number of recursive dependencies: 98 +# +# Run `revdepcheck::cloud_details(, "AeRobiology")` for more info +# +#
+# +# ## Newly broken +# +# * checking re-building of vignette outputs ... NOTE +# ``` +# Error(s) in re-building vignettes: +# --- re-building ‘my-vignette.Rmd’ using rmarkdown +# ``` +# +# ## In both +# +# * checking running R code from vignettes ... ERROR +# ``` +# Errors in running code in vignettes: +# when running code in ‘my-vignette.Rmd’ +# ... +# + export.plot = FALSE, export.result = FALSE, n.types = 3, +# + y.start = 2011, y.end = .... [TRUNCATED] +# +# > iplot_abundance(munich_pollen, interpolation = FALSE, +# + export.plot = FALSE, export.result = FALSE, n.types = 3, +# + y.start = 2011, y.end = .... [TRUNCATED] +# +# When sourcing ‘my-vignette.R’: +# Error: subscript out of bounds +# Execution halted +# +# ‘my-vignette.Rmd’ using ‘UTF-8’... failed +# ``` ``` -* installing *source* package ‘inventorize’ ... -** package ‘inventorize’ successfully unpacked and MD5 sums checked -** using staged installation -** R -** byte-compile and prepare package for lazy loading -Error in pm[[2]] : subscript out of bounds -Error: unable to load R code in package ‘inventorize’ -Execution halted -ERROR: lazy loading failed for package ‘inventorize’ -* removing ‘/tmp/workdir/inventorize/new/inventorize.Rcheck/inventorize’ +# agricolaeplotr (missing labels) + +# AnalysisLin (plotly) + +# animbook (plotly) + +# ANN2 (missing labels) + +# aplot (patchwork) + +# applicable (missing labels) + +# ASRgenomics (factoextra) + +# autoplotly (plotly) + +# autoReg (patchwork) + +# bartMan (ggnewscale) + +# bayesAB (missing labels) + +# BayesGrowth (ggdist) + +# BayesianReasoning (missing labels) + +# BayesMallows (missing labels) + +# bayesplot (missing labels) + +# bayestestR (patchwork) + +# beastt (ggdist) + +# besthr (patchwork) + +# biclustermd (xintercept/yintercept class) + +# biodosetools (missing labels) + +# boxly (plotly) + +# braidReports (annotation_logticks) + +# breathtestcore (plot slots) + +# brolgar (facet params: as.table) + +# cartograflow (plotly) + +# cartographr (unknown) ``` -### CRAN +#
+# +# * Version: 0.2.2 +# * GitHub: https://github.com/da-wi/cartographr +# * Source code: https://github.com/cran/cartographr +# * Date/Publication: 2024-06-28 14:50:09 UTC +# * Number of recursive dependencies: 99 +# +# Run `revdepcheck::cloud_details(, "cartographr")` for more info +# +#
+# +# ## Newly broken +# +# * checking tests ... ERROR +# ``` +# Running ‘testthat.R’ +# Running the tests in ‘tests/testthat.R’ failed. +# Complete output: +# > # This file is part of the standard setup for testthat. +# > # It is recommended that you do not modify it. +# > # +# > # Where should you do additional test configuration? +# > # Learn more about the roles of various files in: +# > # * https://r-pkgs.org/testing-design.html#sec-tests-files-overview +# > # * https://testthat.r-lib.org/articles/special-files.html +# ... +# 21. │ └─base::stop(...) +# 22. └─base::.handleSimpleError(...) +# 23. └─rlang (local) h(simpleError(msg, call)) +# 24. └─handlers[[1L]](cnd) +# 25. └─cli::cli_abort(...) +# 26. └─rlang::abort(...) +# +# [ FAIL 1 | WARN 0 | SKIP 0 | PASS 106 ] +# Error: Test failures +# Execution halted +# ``` +# +# ## In both +# +# * checking installed package size ... NOTE +# ``` +# installed size is 5.3Mb +# sub-directories of 1Mb or more: +# data 3.5Mb +# ``` +``` + +# cats (plotly) + +# cheem (plotly) + +# chillR (patchwork) + +# chronicle (plotly) + +# circhelp (patchwork) + +# clifro (missing labels) + +# clinDataReview (plotly) + +# clinUtils (plotly) + +# CohortPlat (plotly) + +# CoreMicrobiomeR (plotly) + +# correlationfunnel (plotly) + +# corrViz (plotly) + +# countfitteR (missing labels) + +# covidcast (unknown) + +``` +#
+# +# * Version: 0.5.2 +# * GitHub: https://github.com/cmu-delphi/covidcast +# * Source code: https://github.com/cran/covidcast +# * Date/Publication: 2023-07-12 23:40:06 UTC +# * Number of recursive dependencies: 93 +# +# Run `revdepcheck::cloud_details(, "covidcast")` for more info +# +#
+# +# ## Newly broken +# +# * checking tests ... ERROR +# ``` +# Running ‘testthat.R’ +# Running the tests in ‘tests/testthat.R’ failed. +# Complete output: +# > library(testthat) +# > library(covidcast) +# We encourage COVIDcast API users to register on our mailing list: +# https://lists.andrew.cmu.edu/mailman/listinfo/delphi-covidcast-api +# We'll send announcements about new data sources, package updates, +# server maintenance, and new features. +# > +# ... +# • plot/default-county-choropleth.svg +# • plot/default-hrr-choropleth-with-include.svg +# • plot/default-msa-choropleth-with-include.svg +# • plot/default-state-choropleth-with-include.svg +# • plot/default-state-choropleth-with-range.svg +# • plot/state-choropleth-with-no-metadata.svg +# • plot/state-line-graph-with-range.svg +# • plot/state-line-graph-with-stderrs.svg +# Error: Test failures +# Execution halted +# ``` +# +# * checking running R code from vignettes ... ERROR +# ``` +# Errors in running code in vignettes: +# when running code in ‘plotting-signals.Rmd’ +# ... +# > knitr::opts_chunk$set(fig.width = 6, fig.height = 4) +# +# > plot(dv) +# +# When sourcing ‘plotting-signals.R’: +# Error: Problem while setting up geom aesthetics. +# ℹ Error occurred in the 6th layer. +# Caused by error in `$<-.data.frame`: +# ! replacement has 1 row, data has 0 +# Execution halted +# +# ‘correlation-utils.Rmd’ using ‘UTF-8’... OK +# ‘covidcast.Rmd’ using ‘UTF-8’... OK +# ‘external-data.Rmd’ using ‘UTF-8’... OK +# ‘multi-signals.Rmd’ using ‘UTF-8’... OK +# ‘plotting-signals.Rmd’ using ‘UTF-8’... failed +# ``` +# +# * checking re-building of vignette outputs ... NOTE +# ``` +# Error(s) in re-building vignettes: +# --- re-building ‘correlation-utils.Rmd’ using rmarkdown +# --- finished re-building ‘correlation-utils.Rmd’ +# +# --- re-building ‘covidcast.Rmd’ using rmarkdown +# ``` +# +# ## In both +# +# * checking data for non-ASCII characters ... NOTE +# ``` +# Note: found 20 marked UTF-8 strings +# ``` +``` + +# crosshap (plotly) + +# cubble (patchwork) + +# deeptime (ggnewscale) + +# distributional (ggdist) + +# dittoViz (plotly) + +# EGM (missing labels) + +# entropart (default access) + +# epiCleanr (ggdist) + +# esci (ggdist) + +# evalITR (unknown) + +``` +#
+# +# * Version: 1.0.0 +# * GitHub: https://github.com/MichaelLLi/evalITR +# * Source code: https://github.com/cran/evalITR +# * Date/Publication: 2023-08-25 23:10:06 UTC +# * Number of recursive dependencies: 167 +# +# Run `revdepcheck::cloud_details(, "evalITR")` for more info +# +#
+# +# ## Newly broken +# +# * checking re-building of vignette outputs ... NOTE +# ``` +# Error(s) in re-building vignettes: +# --- re-building ‘cv_multiple_alg.Rmd’ using rmarkdown +# ``` +# +# ## In both +# +# * checking running R code from vignettes ... ERROR +# ``` +# Errors in running code in vignettes: +# when running code in ‘cv_multiple_alg.Rmd’ +# ... +# intersect, setdiff, setequal, union +# +# +# > load("../data/star.rda") +# Warning in readChar(con, 5L, useBytes = TRUE) : +# cannot open compressed file '../data/star.rda', probable reason 'No such file or directory' +# +# ... +# Execution halted +# +# ‘cv_multiple_alg.Rmd’ using ‘UTF-8’... failed +# ‘cv_single_alg.Rmd’ using ‘UTF-8’... failed +# ‘install.Rmd’ using ‘UTF-8’... OK +# ‘paper_alg1.Rmd’ using ‘UTF-8’... OK +# ‘sample_split.Rmd’ using ‘UTF-8’... failed +# ‘sample_split_caret.Rmd’ using ‘UTF-8’... failed +# ‘user_itr.Rmd’ using ‘UTF-8’... failed +# ‘user_itr_algs.Rmd’ using ‘UTF-8’... failed +# ``` +# +# * checking dependencies in R code ... NOTE +# ``` +# Namespaces in Imports field not imported from: +# ‘forcats’ ‘rqPen’ ‘utils’ +# All declared Imports should be used. +# ``` +``` + +# eventstudyr (missing labels) + +# EvoPhylo (patchwork) + +# expirest (missing labels) + +# explainer (plotly) + +# ezEDA (missing labels) + +# ezplot (0-length width) + +# fable.prophet (ggdist) + +# fabletools (ggdist) +# factoextra (0-length width) + +# fairmodels (missing labels) + +# fddm (ggforce) + +# feasts (missing labels) + +# ffp (ggdist) + +# fido (ggdist) + +# flipr (unknown) + +``` +#
+# +# * Version: 0.3.3 +# * GitHub: https://github.com/LMJL-Alea/flipr +# * Source code: https://github.com/cran/flipr +# * Date/Publication: 2023-08-23 09:00:02 UTC +# * Number of recursive dependencies: 106 +# +# Run `revdepcheck::cloud_details(, "flipr")` for more info +# +#
+# +# ## Newly broken +# +# * checking re-building of vignette outputs ... NOTE +# ``` +# Error(s) in re-building vignettes: +# --- re-building ‘alternative.Rmd’ using rmarkdown +# --- finished re-building ‘alternative.Rmd’ +# +# --- re-building ‘exactness.Rmd’ using rmarkdown +# +# Quitting from lines 142-177 [unnamed-chunk-1] (exactness.Rmd) +# Error: processing vignette 'exactness.Rmd' failed with diagnostics: +# subscript out of bounds +# --- failed re-building ‘exactness.Rmd’ +# +# --- re-building ‘flipr.Rmd’ using rmarkdown +# ``` +# +# ## In both +# +# * checking running R code from vignettes ... ERROR +# ``` +# Errors in running code in vignettes: +# when running code in ‘exactness.Rmd’ +# ... +# +# > library(flipr) +# +# > load("../R/sysdata.rda") +# Warning in readChar(con, 5L, useBytes = TRUE) : +# cannot open compressed file '../R/sysdata.rda', probable reason 'No such file or directory' +# +# ... +# cannot open compressed file '../R/sysdata.rda', probable reason 'No such file or directory' +# +# When sourcing ‘plausibility.R’: +# Error: cannot open the connection +# Execution halted +# +# ‘alternative.Rmd’ using ‘UTF-8’... OK +# ‘exactness.Rmd’ using ‘UTF-8’... failed +# ‘flipr.Rmd’ using ‘UTF-8’... failed +# ‘plausibility.Rmd’ using ‘UTF-8’... failed +# ``` +# +# * checking installed package size ... NOTE +# ``` +# installed size is 11.0Mb +# sub-directories of 1Mb or more: +# doc 9.1Mb +# libs 1.2Mb +# ``` +``` + +# foqat (ggnewscale) + +# forestly (patchwork) + +# frailtyEM (plotly) + +# funcharts (patchwork) + +# geomtextpath (default access) + +# GGally (missing labels) + +# gganimate (gganimate) + +# ggbrain (ggnewscale) + +# ggbreak (patchwork) + +# ggdark (default access) + +# ggdist (ggdist) + +# ggDoubleHeat (ggnewscale) + +# ggeasy (missing labels) + +# ggedit (saved to disk) + +# ggESDA (passing NULL aesthetic mapping) + +# ggfixest (visual differences) + +# ggforce (ggforce) + +Note: facet_zoom/facet_col/facet_row + +# ggformula (docs) + +# ggfortify (tests) + +# gggenomes (patchwork) + +# ggh4x (unknown) + +``` +#
+# +# * Version: 0.2.8 +# * GitHub: https://github.com/teunbrand/ggh4x +# * Source code: https://github.com/cran/ggh4x +# * Date/Publication: 2024-01-23 21:00:02 UTC +# * Number of recursive dependencies: 77 +# +# Run `revdepcheck::cloud_details(, "ggh4x")` for more info +# +#
+# +# ## Newly broken +# +# * checking examples ... ERROR +# ``` +# Running examples in ‘ggh4x-Ex.R’ failed +# The error most likely occurred in: +# +# > ### Name: guide_stringlegend +# > ### Title: String legend +# > ### Aliases: guide_stringlegend +# > +# > ### ** Examples +# > +# > p <- ggplot(mpg, aes(displ, hwy)) + +# + geom_point(aes(colour = manufacturer)) +# > +# > # String legend can be set in the `guides()` function +# > p + guides(colour = guide_stringlegend(ncol = 2)) +# Error in (function (layer, df) : +# argument "theme" is missing, with no default +# Calls: ... use_defaults -> eval_from_theme -> %||% -> calc_element +# Execution halted +# ``` +# +# * checking tests ... ERROR +# ``` +# Running ‘testthat.R’ +# Running the tests in ‘tests/testthat.R’ failed. +# Complete output: +# > library(testthat) +# > library(ggh4x) +# Loading required package: ggplot2 +# > +# > test_check("ggh4x") +# [ FAIL 2 | WARN 20 | SKIP 18 | PASS 753 ] +# +# ... +# 25. └─ggplot2 (local) compute_geom_2(..., self = self) +# 26. └─self$geom$use_defaults(...) +# 27. └─ggplot2 (local) use_defaults(..., self = self) +# 28. └─ggplot2:::eval_from_theme(default_aes, theme) +# 29. ├─calc_element("geom", theme) %||% .default_geom_element +# 30. └─ggplot2::calc_element("geom", theme) +# +# [ FAIL 2 | WARN 20 | SKIP 18 | PASS 753 ] +# Error: Test failures +# Execution halted +# ``` +# +# * checking re-building of vignette outputs ... NOTE +# ``` +# Error(s) in re-building vignettes: +# --- re-building ‘Facets.Rmd’ using rmarkdown +# ``` +# +# ## In both +# +# * checking running R code from vignettes ... ERROR +# ``` +# Errors in running code in vignettes: +# when running code in ‘Miscellaneous.Rmd’ +# ... +# +# > ggplot(diamonds, aes(price, carat, colour = clarity)) + +# + geom_point(shape = ".") + scale_colour_brewer(palette = "Dark2", +# + guide = "stri ..." ... [TRUNCATED] +# Warning: The S3 guide system was deprecated in ggplot2 3.5.0. +# ℹ It has been replaced by a ggproto system that can be extended. +# +# ... +# ℹ Error occurred in the 1st layer. +# Caused by error in `setup_params()`: +# ! A discrete 'nbinom' distribution cannot be fitted to continuous data. +# Execution halted +# +# ‘Facets.Rmd’ using ‘UTF-8’... OK +# ‘Miscellaneous.Rmd’ using ‘UTF-8’... failed +# ‘PositionGuides.Rmd’ using ‘UTF-8’... OK +# ‘Statistics.Rmd’ using ‘UTF-8’... failed +# ‘ggh4x.Rmd’ using ‘UTF-8’... OK +# ``` +``` + +# gghighlight (default access) + +# ggHoriPlot (patchwork) + +# ggiraph (additional params) + +# ggiraphExtra (additional params) + +# ggmice (plotly) + +# ggmulti (custom use_defaults) + +# ggnewscale (ggnewscale) + +# ggparallel (unknown) + +``` +#
+# +# * Version: 0.4.0 +# * GitHub: https://github.com/heike/ggparallel +# * Source code: https://github.com/cran/ggparallel +# * Date/Publication: 2024-03-09 22:00:02 UTC +# * Number of recursive dependencies: 51 +# +# Run `revdepcheck::cloud_details(, "ggparallel")` for more info +# +#
+# +# ## Newly broken +# +# * checking tests ... ERROR +# ``` +# Running ‘testthat.R’ +# Running the tests in ‘tests/testthat.R’ failed. +# Complete output: +# > # This file is part of the standard setup for testthat. +# > # It is recommended that you do not modify it. +# > # +# > # Where should you do additional test configuration? +# > # Learn more about the roles of various files in: +# > # * https://r-pkgs.org/testing-design.html#sec-tests-files-overview +# > # * https://testthat.r-lib.org/articles/special-files.html +# ... +# 12. └─self$get_layer_key(params, layers[include], data[include], theme) +# 13. └─ggplot2 (local) get_layer_key(...) +# 14. └─base::Map(...) +# 15. └─base::mapply(FUN = f, ..., SIMPLIFY = FALSE) +# 16. └─ggplot2 (local) ``(layer = dots[[1L]][[1L]], df = dots[[2L]][[1L]]) +# 17. └─layer$compute_geom_2(key, single_params, theme) +# +# [ FAIL 1 | WARN 0 | SKIP 0 | PASS 0 ] +# Error: Test failures +# Execution halted +# ``` +``` + +# ggpicrust2 (patchwork) + +# ggpie (ggnewscale) + +# ggplotlyExtra (plotly) + +# ggpol (default access) + +# ggpubr (update tests) + +# ggraph (guide theme passing) + +# ggredist (unknown) + +``` +#
+# +# * Version: 0.0.2 +# * GitHub: https://github.com/alarm-redist/ggredist +# * Source code: https://github.com/cran/ggredist +# * Date/Publication: 2022-11-23 11:20:02 UTC +# * Number of recursive dependencies: 67 +# +# Run `revdepcheck::cloud_details(, "ggredist")` for more info +# +#
+# +# ## Newly broken +# +# * checking examples ... ERROR +# ``` +# Running examples in ‘ggredist-Ex.R’ failed +# The error most likely occurred in: +# +# > ### Name: geom_district_text +# > ### Title: Label Map Regions +# > ### Aliases: geom_district_text geom_district_label +# > ### stat_district_coordinates StatDistrictCoordinates GeomDistrictText +# > ### Keywords: datasets +# > +# > ### ** Examples +# ... +# 22. │ └─coord$transform(data, panel_params) +# 23. │ └─ggplot2 (local) transform(..., self = self) +# 24. │ └─ggplot2:::sf_rescale01(...) +# 25. │ └─sf::st_normalize(x, c(x_range[1], y_range[1], x_range[2], y_range[2])) +# 26. └─base::.handleSimpleError(...) +# 27. └─rlang (local) h(simpleError(msg, call)) +# 28. └─handlers[[1L]](cnd) +# 29. └─cli::cli_abort(...) +# 30. └─rlang::abort(...) +# Execution halted +# ``` +``` + +# ggRtsy (missing labels) + +# ggseqplot (length 0 width) + +# ggside (unknown) + +``` +#
+# +# * Version: 0.3.1 +# * GitHub: https://github.com/jtlandis/ggside +# * Source code: https://github.com/cran/ggside +# * Date/Publication: 2024-03-01 09:12:37 UTC +# * Number of recursive dependencies: 76 +# +# Run `revdepcheck::cloud_details(, "ggside")` for more info +# +#
+# +# ## Newly broken +# +# * checking tests ... ERROR +# ``` +# Running ‘testthat.R’ +# Running the tests in ‘tests/testthat.R’ failed. +# Complete output: +# > library(testthat) +# > library(ggplot2) +# > library(ggside) +# Registered S3 method overwritten by 'ggside': +# method from +# +.gg ggplot2 +# > +# ... +# • ops_meaningful/alpha-0-5-from-function.svg +# • side_layers/boxplot2.svg +# • vdiff_irisScatter/collapsed-histo.svg +# • vdiff_irisScatter/facetgrid-collapsed-density.svg +# • vdiff_irisScatter/facetgrid-histo.svg +# • vdiff_irisScatter/facetgrid-side-density.svg +# • vdiff_irisScatter/stacked-side-density.svg +# • vdiff_irisScatter/yside-histo.svg +# Error: Test failures +# Execution halted +# ``` +# +# * checking for code/documentation mismatches ... WARNING +# ``` +# Codoc mismatches from documentation object 'geom_xsideabline': +# geom_xsidehline +# Code: function(mapping = NULL, data = NULL, position = "identity", +# ..., yintercept, na.rm = FALSE, show.legend = NA) +# Docs: function(mapping = NULL, data = NULL, ..., yintercept, na.rm = +# FALSE, show.legend = NA) +# Argument names in code not in docs: +# position +# Mismatches in argument names (first 3): +# Position: 3 Code: position Docs: ... +# ... +# Docs: function(mapping = NULL, data = NULL, stat = "identity", +# position = "identity", ..., lineend = "butt", linejoin +# = "round", linemitre = 10, arrow = NULL, na.rm = +# FALSE, show.legend = NA, inherit.aes = TRUE) +# Argument names in code not in docs: +# arrow.fill +# Mismatches in argument names: +# Position: 10 Code: arrow.fill Docs: na.rm +# Position: 11 Code: na.rm Docs: show.legend +# Position: 12 Code: show.legend Docs: inherit.aes +# ``` +``` + +# ggspatial (missing defaults) + +# ggtern (ggtern) + +# ggupset (unknown) + +``` +#
+# +# * Version: 0.4.0 +# * GitHub: https://github.com/const-ae/ggupset +# * Source code: https://github.com/cran/ggupset +# * Date/Publication: 2024-06-24 10:10:04 UTC +# * Number of recursive dependencies: 46 +# +# Run `revdepcheck::cloud_details(, "ggupset")` for more info +# +#
+# +# ## Newly broken +# +# * checking examples ... ERROR +# ``` +# Running examples in ‘ggupset-Ex.R’ failed +# The error most likely occurred in: +# +# > ### Name: axis_combmatrix +# > ### Title: Convert delimited text labels into a combination matrix axis +# > ### Aliases: axis_combmatrix +# > +# > ### ** Examples +# > +# > library(ggplot2) +# ... +# Datsun 710 Cyl: 4_Gears: 4 +# Hornet 4 Drive Cyl: 6_Gears: 3 +# Hornet Sportabout Cyl: 8_Gears: 3 +# Valiant Cyl: 6_Gears: 3 +# > ggplot(mtcars, aes(x=combined)) + +# + geom_bar() + +# + axis_combmatrix(sep = "_") +# Error in as.unit(e2) : object is not coercible to a unit +# Calls: ... polylineGrob -> is.unit -> unit.c -> Ops.unit -> as.unit +# Execution halted +# ``` ``` -* installing *source* package ‘inventorize’ ... -** package ‘inventorize’ successfully unpacked and MD5 sums checked -** using staged installation -** R -** byte-compile and prepare package for lazy loading -Warning in qgamma(service_level, alpha, beta) : NaNs produced -Warning in qgamma(service_level, alpha, beta) : NaNs produced -** help -*** installing help indices -** building package indices -** testing if installed package can be loaded from temporary location -** testing if installed package can be loaded from final location -** testing if installed package keeps a record of temporary installation path -* DONE (inventorize) +# ggVennDiagram (plotly) + +# greatR (patchwork) + +# Greymodels (plotly) + +# gtExtras (unknown) ``` -# karel - -
- -* Version: 0.1.1 -* GitHub: https://github.com/mpru/karel -* Source code: https://github.com/cran/karel -* Date/Publication: 2022-03-26 21:50:02 UTC -* Number of recursive dependencies: 90 - -Run `revdepcheck::cloud_details(, "karel")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘karel-Ex.R’ failed - The error most likely occurred in: - - > ### Name: acciones - > ### Title: Acciones que Karel puede realizar - > ### Aliases: acciones avanzar girar_izquierda poner_coso juntar_coso - > ### girar_derecha darse_vuelta - > - > ### ** Examples - > - ... - 1. └─karel::ejecutar_acciones() - 2. ├─base::suppressWarnings(...) - 3. │ └─base::withCallingHandlers(...) - 4. ├─gganimate::animate(...) - 5. └─gganimate:::animate.gganim(...) - 6. └─args$renderer(frames_vars$frame_source, args$fps) - 7. └─gganimate:::png_dim(frames[1]) - 8. └─cli::cli_abort("Provided file ({file}) does not exist") - 9. └─rlang::abort(...) - Execution halted - ``` - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(karel) - > - > test_check("karel") - [ FAIL 2 | WARN 2 | SKIP 0 | PASS 78 ] - - ══ Failed tests ════════════════════════════════════════════════════════════════ - ... - 5. ├─gganimate::animate(...) - 6. └─gganimate:::animate.gganim(...) - 7. └─args$renderer(frames_vars$frame_source, args$fps) - 8. └─gganimate:::png_dim(frames[1]) - 9. └─cli::cli_abort("Provided file ({file}) does not exist") - 10. └─rlang::abort(...) - - [ FAIL 2 | WARN 2 | SKIP 0 | PASS 78 ] - Error: Test failures - Execution halted - ``` - -## In both - -* checking dependencies in R code ... NOTE - ``` - Namespace in Imports field not imported from: ‘gifski’ - All declared Imports should be used. - ``` - -# kDGLM - -
- -* Version: 1.2.0 -* GitHub: https://github.com/silvaneojunior/kDGLM -* Source code: https://github.com/cran/kDGLM -* Date/Publication: 2024-05-25 09:50:03 UTC -* Number of recursive dependencies: 136 - -Run `revdepcheck::cloud_details(, "kDGLM")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘kDGLM-Ex.R’ failed - The error most likely occurred in: - - > ### Name: forecast.fitted_dlm - > ### Title: Auxiliary function for forecasting - > ### Aliases: forecast.fitted_dlm - > - > ### ** Examples - > - > - ... - > forecast(fitted.data, 24, - + chickenPox = list(Total = rep(175, 24)), # Optional - + Vaccine.1.Covariate = rep(TRUE, 24), - + Vaccine.2.Covariate = rep(TRUE, 24) - + ) - Scale for y is already present. - Adding another scale for y, which will replace the existing scale. - Error in pm[[2]] : subscript out of bounds - Calls: forecast ... lapply -> -> ggplotly.ggplot -> gg2list - Execution halted - ``` - -## In both - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘fitting.Rmd’ - ... - > outcome <- Multinom(p = c("p.1", "p.2"), data = chickenPox[, - + c(2, 3, 5)]) - - > fitted.model <- fit_model(structure * 2, chickenPox = outcome) - - > forecast(fitted.model, t = 24, plot = "base") - - When sourcing ‘fitting.R’: - Error: Error: Missing extra argument: Vaccine.1.Covariate - Execution halted - - ‘example1.Rmd’ using ‘UTF-8’... OK - ‘fitting.Rmd’ using ‘UTF-8’... failed - ‘intro.Rmd’ using ‘UTF-8’... OK - ‘outcomes.Rmd’ using ‘UTF-8’... OK - ‘structures.Rmd’ using ‘UTF-8’... OK - ``` - -# latentcor - -
- -* Version: 2.0.1 -* GitHub: NA -* Source code: https://github.com/cran/latentcor -* Date/Publication: 2022-09-05 20:50:02 UTC -* Number of recursive dependencies: 143 - -Run `revdepcheck::cloud_details(, "latentcor")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘latentcor-Ex.R’ failed - The error most likely occurred in: - - > ### Name: latentcor - > ### Title: Estimate latent correlation for mixed types. - > ### Aliases: latentcor - > - > ### ** Examples - > - > # Example 1 - truncated data type, same type for all variables - ... - > R_approx = latentcor(X = X, types = "tru", method = "approx")$R - > proc.time() - start_time - user system elapsed - 0.021 0.000 0.021 - > # Heatmap for latent correlation matrix. - > Heatmap_R_approx = latentcor(X = X, types = "tru", method = "approx", - + showplot = TRUE)$plotR - Error in pm[[2]] : subscript out of bounds - Calls: latentcor ... %>% -> layout -> ggplotly -> ggplotly.ggplot -> gg2list - Execution halted - ``` - -# lcars - -
- -* Version: 0.3.8 -* GitHub: https://github.com/leonawicz/lcars -* Source code: https://github.com/cran/lcars -* Date/Publication: 2023-09-10 04:10:02 UTC -* Number of recursive dependencies: 88 - -Run `revdepcheck::cloud_details(, "lcars")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘lcars-Ex.R’ failed - The error most likely occurred in: - - > ### Name: lcars_border - > ### Title: LCARS border plot - > ### Aliases: lcars_border - > - > ### ** Examples - > - > lcars_border() - ... - Warning in grid.Call.graphics(C_text, as.graphicsAnnot(x$label), x$x, x$y, : - font family '0.5' not found in PostScript font database - Warning in grid.Call.graphics(C_text, as.graphicsAnnot(x$label), x$x, x$y, : - font family '0.5' not found in PostScript font database - Warning in grid.Call.graphics(C_text, as.graphicsAnnot(x$label), x$x, x$y, : - font family '0.5' not found in PostScript font database - Error in grid.Call.graphics(C_text, as.graphicsAnnot(x$label), x$x, x$y, : - invalid font type - Calls: lcars_border ... drawDetails -> drawDetails.text -> grid.Call.graphics - Execution halted - ``` - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘lcars.Rmd’ - ... - Warning in grid.Call.graphics(C_text, as.graphicsAnnot(x$label), x$x, x$y, : - font family '0.5' not found in PostScript font database - Warning in grid.Call.graphics(C_text, as.graphicsAnnot(x$label), x$x, x$y, : - font family '0.5' not found in PostScript font database - Warning in grid.Call.graphics(C_text, as.graphicsAnnot(x$label), x$x, x$y, : - font family '0.5' not found in PostScript font database - - When sourcing ‘lcars.R’: - Error: invalid font type - Execution halted - - ‘lcars.Rmd’ using ‘UTF-8’... failed - ``` - -# lemon - -
- -* Version: 0.4.9 -* GitHub: https://github.com/stefanedwards/lemon -* Source code: https://github.com/cran/lemon -* Date/Publication: 2024-02-08 08:00:08 UTC -* Number of recursive dependencies: 76 - -Run `revdepcheck::cloud_details(, "lemon")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘lemon-Ex.R’ failed - The error most likely occurred in: - - > ### Name: annotate_y_axis - > ### Title: Annotations on the axis - > ### Aliases: annotate_y_axis annotate_x_axis - > - > ### ** Examples - > - > library(ggplot2) - > - > p <- ggplot(mtcars, aes(mpg, hp, colour=disp)) + geom_point() - > - > l <- p + annotate_y_axis('mark at', y=200, tick=TRUE) - > l - Error in identicalUnits(x) : object is not a unit - Calls: ... polylineGrob -> is.unit -> unit.c -> identicalUnits - Execution halted - ``` - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(lemon) - > - > - > if (TRUE) { - + test_check("lemon") - + } #else { - ... - 17. ├─grid::unit.c(unit(1, "npc"), unit(1, "npc") - tick.length) - 18. └─grid:::Ops.unit(unit(1, "npc"), tick.length) - 19. └─grid:::as.unit(e2) - - [ FAIL 1 | WARN 0 | SKIP 3 | PASS 138 ] - Deleting unused snapshots: - • facet/facet-rep-wrap-spacing.svg - • facet_aux/facet-rep-wrap.svg - Error: Test failures - Execution halted - ``` - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘capped-axes.Rmd’ - ... - > p + coord_capped_cart(bottom = "right") - - > p + coord_capped_cart(bottom = "right", left = "none") - - > ggplot(dat1, aes(gp, y)) + geom_point(position = position_jitter(width = 0.2, - + height = 0)) + coord_capped_cart(left = "none", bottom = bracke .... [TRUNCATED] - - ... - When sourcing ‘legends.R’: - Error: Could not find panel named `panel-1-5`. - Execution halted - - ‘capped-axes.Rmd’ using ‘UTF-8’... failed - ‘facet-rep-labels.Rmd’ using ‘UTF-8’... failed - ‘geoms.Rmd’ using ‘UTF-8’... OK - ‘gtable_show_lemonade.Rmd’ using ‘UTF-8’... OK - ‘legends.Rmd’ using ‘UTF-8’... failed - ‘lemon_print.Rmd’ using ‘UTF-8’... OK - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘capped-axes.Rmd’ using rmarkdown - ``` - -# lfproQC - -
- -* Version: 0.1.0 -* GitHub: NA -* Source code: https://github.com/cran/lfproQC -* Date/Publication: 2024-05-23 16:10:02 UTC -* Number of recursive dependencies: 143 - -Run `revdepcheck::cloud_details(, "lfproQC")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘lfproQC-Ex.R’ failed - The error most likely occurred in: - - > ### Name: Boxplot_data - > ### Title: Creating Boxplot for a dataset - > ### Aliases: Boxplot_data - > - > ### ** Examples - > - > Boxplot_data(yeast_data) - Using Majority protein IDs as id variables - Warning: Removed 266 rows containing non-finite outside the scale range - (`stat_boxplot()`). - Error in pm[[2]] : subscript out of bounds - Calls: Boxplot_data -> -> ggplotly.ggplot -> gg2list - Execution halted - ``` - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘user_guide.Rmd’ - ... - > yeast$`Best combinations` - PCV_best_combination PEV_best_combination PMAD_best_combination - 1 knn_rlr lls_loess lls_rlr - - > Boxplot_data(yeast$knn_rlr_data) - Using Majority protein IDs as id variables - - When sourcing ‘user_guide.R’: - Error: subscript out of bounds - Execution halted - - ‘user_guide.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - ... - --- re-building ‘user_guide.Rmd’ using rmarkdown - - Quitting from lines 53-54 [unnamed-chunk-8] (user_guide.Rmd) - Error: processing vignette 'user_guide.Rmd' failed with diagnostics: - subscript out of bounds - --- failed re-building ‘user_guide.Rmd’ - - SUMMARY: processing the following file failed: - ‘user_guide.Rmd’ - - Error: Vignette re-building failed. - Execution halted - ``` - -## In both - -* checking installed package size ... NOTE - ``` - installed size is 6.2Mb - sub-directories of 1Mb or more: - doc 5.9Mb - ``` - -# LMoFit - -
- -* Version: 0.1.7 -* GitHub: NA -* Source code: https://github.com/cran/LMoFit -* Date/Publication: 2024-05-14 07:33:23 UTC -* Number of recursive dependencies: 62 - -Run `revdepcheck::cloud_details(, "LMoFit")` for more info - -
- -## Newly broken - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘LMoFit.Rmd’ - ... - - > lspace_BrIII - - When sourcing ‘LMoFit.R’: - Error: Problem while setting up geom aesthetics. - ℹ Error occurred in the 1st layer. - Caused by error in `compute_geom_2()`: - ! unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), NULL, NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.75, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, 90, NULL, c(0, 2.75, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, - c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 1, NULL, NULL, NULL, c(0, 2.2, 0, 0), NULL, TRUE), NULL, - Execution halted - - ‘LMoFit.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - ... - --- re-building ‘LMoFit.Rmd’ using rmarkdown - - Quitting from lines 236-237 [unnamed-chunk-15] (LMoFit.Rmd) - Error: processing vignette 'LMoFit.Rmd' failed with diagnostics: - Problem while setting up geom aesthetics. - ℹ Error occurred in the 1st layer. - Caused by error in `compute_geom_2()`: - ! unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), NULL, NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.75, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, 90, NULL, c(0, 2.75, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, - ... - NULL, NULL, 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, NULL, NULL, NULL, TRUE), NULL, "right", NULL, NULL, NULL, "center", NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, c(0, 0, 0, 0), list(), 11, list("white", NA, NULL, NULL, TRUE), list(), 5.5, NULL, NULL, list("grey92", NULL, NULL, NULL, FALSE, TRUE), list(), list(), NULL, NULL, NULL, NULL, FALSE, list(NULL, "white", NULL, NULL, TRUE), list(NULL, NULL, NULL, 1.2, 0, 1, NULL, NULL, c(0, - 0, 5.5, 0), NULL, TRUE), "panel", list(NULL, NULL, NULL, NULL, 0, 1, NULL, NULL, c(0, 0, 5.5, 0), NULL, TRUE), list(NULL, NULL, NULL, 0.8, 1, 1, NULL, NULL, c(5.5, 0, 0, 0), NULL, TRUE), "panel", list(NULL, NULL, NULL, 1.2, 0.5, 0.5, NULL, NULL, NULL, NULL, TRUE), "topleft", NULL, c(5.5, 5.5, 5.5, 5.5), list("white", "black", 2, NULL, TRUE), NULL, NULL, "inherit", "inside", list(NULL, NULL, "grey10", 0.8, NULL, NULL, NULL, NULL, c(4.4, 4.4, 4.4, 4.4), NULL, TRUE), NULL, NULL, NULL, list(NULL, NULL, - NULL, NULL, NULL, NULL, -90, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, NULL, 90, NULL, NULL, NULL, TRUE), NULL, 2.75, 2.75, list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), 5.5, c(5.5, 5.5, 5.5, 5.5))) - --- failed re-building ‘LMoFit.Rmd’ - - SUMMARY: processing the following file failed: - ‘LMoFit.Rmd’ - - Error: Vignette re-building failed. - Execution halted - ``` - -## In both - -* checking installed package size ... NOTE - ``` - installed size is 7.0Mb - sub-directories of 1Mb or more: - data 6.5Mb - ``` - -# manydata - -
- -* Version: 0.9.3 -* GitHub: https://github.com/globalgov/manydata -* Source code: https://github.com/cran/manydata -* Date/Publication: 2024-05-06 19:00:02 UTC -* Number of recursive dependencies: 129 - -Run `revdepcheck::cloud_details(, "manydata")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(manydata) - manydata 0.9.3 - Please see manydata.ch for more information. - Type 'citation("manydata")' for citing this R package in publications. - > - > test_check("manydata") - ... - ── Failure ('test_compare.R:8:3'): plot for compare_categories returns the correct output format ── - Names of `db` ('data', 'layers', 'scales', 'guides', 'mapping', 'theme', 'coordinates', 'facet', 'plot_env', 'layout', 'labels') don't match 'data', 'layers', 'scales', 'guides', 'mapping', 'theme', 'coordinates', 'facet', 'plot_env', 'layout' - ── Failure ('test_compare.R:74:3'): compare_missing() and plot_missing() returns the correct output format ── - `pl` has length 11, not length 10. - ── Failure ('test_compare.R:76:3'): compare_missing() and plot_missing() returns the correct output format ── - Names of `pl` ('data', 'layers', 'scales', 'guides', 'mapping', 'theme', 'coordinates', 'facet', 'plot_env', 'layout', 'labels') don't match 'data', 'layers', 'scales', 'guides', 'mapping', 'theme', 'coordinates', 'facet', 'plot_env', 'layout' - - [ FAIL 4 | WARN 0 | SKIP 3 | PASS 121 ] - Error: Test failures - Execution halted - ``` - -## In both - -* checking data for non-ASCII characters ... NOTE - ``` - Note: found 3 marked UTF-8 strings - ``` - -# MARVEL - -
- -* Version: 1.4.0 -* GitHub: NA -* Source code: https://github.com/cran/MARVEL -* Date/Publication: 2022-10-31 10:22:50 UTC -* Number of recursive dependencies: 227 - -Run `revdepcheck::cloud_details(, "MARVEL")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘MARVEL-Ex.R’ failed - The error most likely occurred in: - - > ### Name: PlotValues.PSI - > ### Title: Plot percent spliced-in (PSI) values - > ### Aliases: PlotValues.PSI - > - > ### ** Examples - > - > marvel.demo <- readRDS(system.file("extdata/data", "marvel.demo.rds", package="MARVEL")) - ... - > # Plot - > marvel.demo <- PlotValues.PSI(MarvelObject=marvel.demo, - + cell.group.list=cell.group.list, - + feature="chr17:8383254:8382781|8383157:-@chr17:8382143:8382315", - + min.cells=5, - + xlabels.size=5 - + ) - Error in names(labels) <- `*vtmp*` : attempt to set an attribute on NULL - Calls: PlotValues.PSI ... ggplot_add -> ggplot_add.new_aes -> bump_aes_labels - Execution halted - ``` - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘MARVEL.Rmd’ - ... - - > tran_id <- "chr4:108620569:108620600|108620656:108620712:+@chr4:108621951:108622024" - - > marvel.demo <- PlotValues(MarvelObject = marvel.demo, - + cell.group.list = cell.group.list, feature = tran_id, xlabels.size = 5, - + level = .... [TRUNCATED] - - When sourcing ‘MARVEL.R’: - Error: attempt to set an attribute on NULL - Execution halted - - ‘MARVEL.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘MARVEL.Rmd’ using rmarkdown - ``` - -# MBNMAdose - -
- -* Version: 0.4.3 -* GitHub: NA -* Source code: https://github.com/cran/MBNMAdose -* Date/Publication: 2024-04-18 12:42:47 UTC -* Number of recursive dependencies: 118 - -Run `revdepcheck::cloud_details(, "MBNMAdose")` for more info - -
- -## Newly broken - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘outputs-4.Rmd’ - ... - - > plot(trip.emax) - - When sourcing ‘outputs-4.R’: - Error: Problem while setting up geom aesthetics. - ℹ Error occurred in the 1st layer. - Caused by error in `use_defaults()`: - ... - Execution halted - - ‘consistencychecking-3.Rmd’ using ‘UTF-8’... OK - ‘dataexploration-1.Rmd’ using ‘UTF-8’... OK - ‘mbnmadose-overview.Rmd’ using ‘UTF-8’... OK - ‘metaregression-6.Rmd’ using ‘UTF-8’... OK - ‘nma_in_mbnmadose.Rmd’ using ‘UTF-8’... OK - ‘outputs-4.Rmd’ using ‘UTF-8’... failed - ‘predictions-5.Rmd’ using ‘UTF-8’... OK - ‘runmbnmadose-2.Rmd’ using ‘UTF-8’... OK - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘consistencychecking-3.Rmd’ using rmarkdown - ``` - -## In both - -* checking data for non-ASCII characters ... NOTE - ``` - Note: found 6 marked Latin-1 strings - ``` - -# MBNMAtime - -
- -* Version: 0.2.4 -* GitHub: NA -* Source code: https://github.com/cran/MBNMAtime -* Date/Publication: 2023-10-14 15:20:02 UTC -* Number of recursive dependencies: 106 - -Run `revdepcheck::cloud_details(, "MBNMAtime")` for more info - -
- -## Newly broken - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘consistencychecking-3.Rmd’ using rmarkdown - - Quitting from lines 141-146 [unnamed-chunk-8] (consistencychecking-3.Rmd) - Error: processing vignette 'consistencychecking-3.Rmd' failed with diagnostics: - unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, "black", TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), list(NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), 5.5, c(5.5, 5.5, 5.5, 5.5), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.75, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, - NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, 90, NULL, c(0, 2.75, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 1, NULL, NULL, - NULL, c(0, 2.2, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, NULL, c(0, 0, 0, 2.2), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0.5, NULL, NULL, NULL, c(0, 2.2, 0, 2.2), NULL, TRUE), list("grey20", NULL, NULL, NULL, FALSE, "grey20", TRUE), NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 0.5, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 0.75, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, list(), NULL, NULL, NULL, NULL, NULL, - NULL, NULL, NULL, list("transparent", NA, NULL, NULL, FALSE), NULL, 2, NULL, NULL, list("transparent", NA, NULL, NULL, FALSE), 1.2, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 0.2, NULL, list(NULL, NULL, NULL, 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, NULL, NULL, NULL, TRUE), NULL, "right", NULL, NULL, NULL, "center", NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 0, list(), 2, list(), list(NULL, "grey20", NULL, NULL, TRUE), NULL, NULL, NULL, - list("grey92", NULL, NULL, NULL, FALSE, "grey92", TRUE), list("grey95", NULL, NULL, NULL, FALSE, "grey95", FALSE), list("grey95", 0.5, NULL, NULL, FALSE, "grey95", FALSE), NULL, NULL, NULL, NULL, FALSE, list("white", NA, NULL, NULL, FALSE), list(NULL, NULL, NULL, 1.2, 0, 1, NULL, NULL, c(0, 0, 5.5, 0), NULL, TRUE), "panel", list(NULL, NULL, NULL, NULL, 0, 1, NULL, NULL, c(0, 0, 5.5, 0), NULL, TRUE), list(NULL, NULL, NULL, 0.8, 1, 1, NULL, NULL, c(5.5, 0, 0, 0), NULL, TRUE), "panel", list(NULL, - NULL, NULL, 1.2, 0.5, 0.5, NULL, NULL, NULL, NULL, TRUE), "topleft", NULL, NULL, list("lightsteelblue1", "black", NULL, NULL, FALSE), NULL, NULL, "inherit", "inside", list(NULL, NULL, "black", 0.8, NULL, NULL, NULL, NULL, c(4.4, 4.4, 4.4, 4.4), NULL, FALSE), NULL, NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, NULL, -90, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, NULL, 90, NULL, NULL, NULL, TRUE), NULL, 2.75, 2.75)) - --- failed re-building ‘consistencychecking-3.Rmd’ - - --- re-building ‘dataexploration-1.Rmd’ using rmarkdown - ``` - -## In both - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘consistencychecking-3.Rmd’ - ... - |-> direct | | 0.228| -0.213| 0.684| - |-> indirect | | -0.515| -0.891| -0.137| - | | | | | | - - > plot(nodesplit, plot.type = "forest") - - When sourcing ‘consistencychecking-3.R’: - ... - ! unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, "black", TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), list(NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), 5.5, c(5.5, 5.5, 5.5, 5.5), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.75, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, - NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, 90, NULL, c(0, 2.75, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL - Execution halted - - ‘consistencychecking-3.Rmd’ using ‘UTF-8’... failed - ‘dataexploration-1.Rmd’ using ‘UTF-8’... failed - ‘mbnmatime-overview.Rmd’ using ‘UTF-8’... OK - ‘outputs-4.Rmd’ using ‘UTF-8’... failed - ‘predictions-5.Rmd’ using ‘UTF-8’... OK - ‘runmbnmatime-2.Rmd’ using ‘UTF-8’... OK - ``` - -# MetaNet - -
- -* Version: 0.1.2 -* GitHub: https://github.com/Asa12138/MetaNet -* Source code: https://github.com/cran/MetaNet -* Date/Publication: 2024-03-25 20:40:07 UTC -* Number of recursive dependencies: 151 - -Run `revdepcheck::cloud_details(, "MetaNet")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘MetaNet-Ex.R’ failed - The error most likely occurred in: - - > ### Name: as.ggig - > ### Title: Transfer an igraph object to a ggig - > ### Aliases: as.ggig - > - > ### ** Examples - > - > as.ggig(co_net, coors = c_net_layout(co_net)) -> ggig - > plot(ggig) - Error in names(labels) <- `*vtmp*` : attempt to set an attribute on NULL - Calls: plot ... ggplot_add -> ggplot_add.new_aes -> bump_aes_labels - Execution halted - ``` - -# metR - -
- -* Version: 0.15.0 -* GitHub: https://github.com/eliocamp/metR -* Source code: https://github.com/cran/metR -* Date/Publication: 2024-02-09 00:40:02 UTC -* Number of recursive dependencies: 121 - -Run `revdepcheck::cloud_details(, "metR")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘metR-Ex.R’ failed - The error most likely occurred in: - - > ### Name: GeostrophicWind - > ### Title: Calculate geostrophic winds - > ### Aliases: GeostrophicWind - > - > ### ** Examples - > - > data(geopotential) - ... - > ggplot(geopotential[date == date[1]], aes(lon, lat)) + - + geom_contour(aes(z = gh)) + - + geom_vector(aes(dx = u, dy = v), skip = 2) + - + scale_mag() - Warning: The S3 guide system was deprecated in ggplot2 3.5.0. - ℹ It has been replaced by a ggproto system that can be extended. - Error in (function (layer, df) : - argument "theme" is missing, with no default - Calls: ... use_defaults -> eval_from_theme -> %||% -> calc_element - Execution halted - ``` - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘Visualization-tools.Rmd’ - ... - - > (g <- ggplot(temperature[lev == 500], aes(lon, lat)) + - + geom_contour_fill(aes(z = air.z)) + geom_vector(aes(dx = t.dx, - + dy = t.dy), skip .... [TRUNCATED] - Warning: The S3 guide system was deprecated in ggplot2 3.5.0. - ℹ It has been replaced by a ggproto system that can be extended. - - ... - + dy = gh.dlat), s .... [TRUNCATED] - Warning: The S3 guide system was deprecated in ggplot2 3.5.0. - ℹ It has been replaced by a ggproto system that can be extended. - - When sourcing ‘Working-with-data.R’: - Error: argument "theme" is missing, with no default - Execution halted - - ‘Visualization-tools.Rmd’ using ‘UTF-8’... failed - ‘Working-with-data.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - ... - --- re-building ‘Visualization-tools.Rmd’ using knitr - - Quitting from lines 284-293 [unnamed-chunk-19] (Visualization-tools.Rmd) - Error: processing vignette 'Visualization-tools.Rmd' failed with diagnostics: - argument "theme" is missing, with no default - --- failed re-building ‘Visualization-tools.Rmd’ - - --- re-building ‘Working-with-data.Rmd’ using knitr - ... - Quitting from lines 199-210 [unnamed-chunk-13] (Working-with-data.Rmd) - Error: processing vignette 'Working-with-data.Rmd' failed with diagnostics: - argument "theme" is missing, with no default - --- failed re-building ‘Working-with-data.Rmd’ - - SUMMARY: processing the following files failed: - ‘Visualization-tools.Rmd’ ‘Working-with-data.Rmd’ - - Error: Vignette re-building failed. - Execution halted - ``` - -## In both - -* checking installed package size ... NOTE - ``` - installed size is 6.6Mb - sub-directories of 1Mb or more: - R 1.5Mb - data 2.0Mb - doc 1.8Mb - ``` - -# migraph - -
- -* Version: 1.3.4 -* GitHub: https://github.com/stocnet/migraph -* Source code: https://github.com/cran/migraph -* Date/Publication: 2024-03-07 11:50:02 UTC -* Number of recursive dependencies: 120 - -Run `revdepcheck::cloud_details(, "migraph")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(manynet) - > library(migraph) - > - > test_check("migraph") - [ FAIL 2 | WARN 0 | SKIP 0 | PASS 266 ] - - ... - ── Failure ('test-model_tests.R:63:3'): cug plot works ───────────────────────── - cugplot$labels$x not identical to "Statistic". - target is NULL, current is character - ── Failure ('test-model_tests.R:73:3'): qap plot works ───────────────────────── - qapplot$labels$x not identical to "Statistic". - target is NULL, current is character - - [ FAIL 2 | WARN 0 | SKIP 0 | PASS 266 ] - Error: Test failures - Execution halted - ``` - -# MiMIR - -
- -* Version: 1.5 -* GitHub: NA -* Source code: https://github.com/cran/MiMIR -* Date/Publication: 2024-02-01 08:50:02 UTC -* Number of recursive dependencies: 191 - -Run `revdepcheck::cloud_details(, "MiMIR")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘MiMIR-Ex.R’ failed - The error most likely occurred in: - - > ### Name: LOBOV_accuracies - > ### Title: LOBOV_accuracies - > ### Aliases: LOBOV_accuracies - > - > ### ** Examples - > - > require(pROC) - ... - 56 metabolites x 500 samples - | Pruning samples on5SD: - 56 metabolites x 500 samples - | Performing scaling ... DONE! - | Imputation ... DONE! - > p_avail<-colnames(b_p)[c(1:5)] - > LOBOV_accuracies(sur$surrogates, b_p, p_avail, MiMIR::acc_LOBOV) - Error in pm[[2]] : subscript out of bounds - Calls: LOBOV_accuracies -> -> ggplotly.ggplot -> gg2list - Execution halted - ``` - -# miRetrieve - -
- -* Version: 1.3.4 -* GitHub: NA -* Source code: https://github.com/cran/miRetrieve -* Date/Publication: 2021-09-18 17:30:02 UTC -* Number of recursive dependencies: 126 - -Run `revdepcheck::cloud_details(, "miRetrieve")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(miRetrieve) - > - > test_check("miRetrieve") - [ FAIL 1 | WARN 11 | SKIP 0 | PASS 202 ] - - ══ Failed tests ════════════════════════════════════════════════════════════════ - ... - Backtrace: - ▆ - 1. └─miRetrieve::compare_mir_terms_scatter(df_merged, "miR-21", title = "Test_title") at test-comparemirterms.R:56:1 - 2. ├─plotly::ggplotly(plot) - 3. └─plotly:::ggplotly.ggplot(plot) - 4. └─plotly::gg2list(...) - - [ FAIL 1 | WARN 11 | SKIP 0 | PASS 202 ] - Error: Test failures - Execution halted - ``` - -# misspi - -
- -* Version: 0.1.0 -* GitHub: NA -* Source code: https://github.com/cran/misspi -* Date/Publication: 2023-10-17 09:50:02 UTC -* Number of recursive dependencies: 88 - -Run `revdepcheck::cloud_details(, "misspi")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘misspi-Ex.R’ failed - The error most likely occurred in: - - > ### Name: evaliq - > ### Title: Evaluate the Imputation Quality - > ### Aliases: evaliq - > - > ### ** Examples - > - > # A very quick example - ... - > # Default plot - > er.eval <- evaliq(x.true[na.idx], x.est[na.idx]) - `geom_smooth()` using formula = 'y ~ x' - > - > # Interactive plot - > er.eval <- evaliq(x.true[na.idx], x.est[na.idx], interactive = TRUE) - `geom_smooth()` using formula = 'y ~ x' - Error in pm[[2]] : subscript out of bounds - Calls: evaliq -> print -> ggplotly -> ggplotly.ggplot -> gg2list - Execution halted - ``` - -# mizer - -
- -* Version: 2.5.1 -* GitHub: https://github.com/sizespectrum/mizer -* Source code: https://github.com/cran/mizer -* Date/Publication: 2024-03-08 23:10:02 UTC -* Number of recursive dependencies: 110 - -Run `revdepcheck::cloud_details(, "mizer")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘spelling.R’ - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(mizer) - > - > test_check("mizer") - [ FAIL 10 | WARN 0 | SKIP 5 | PASS 1251 ] - - ... - • plots/plot-spectra.svg - • plots/plot-yield-by-gear.svg - • plots/plot-yield.svg - • plots/plotfishing-mortality.svg - • plots/plotfmort-truncated.svg - • plots/plotpredation-mortality.svg - • plots/plotpredmort-truncated.new.svg - • plots/plotpredmort-truncated.svg - Error: Test failures - Execution halted - ``` - -## In both - -* checking installed package size ... NOTE - ``` - installed size is 6.1Mb - sub-directories of 1Mb or more: - doc 1.5Mb - help 1.8Mb - ``` - -# mlr3spatiotempcv - -
- -* Version: 2.3.1 -* GitHub: https://github.com/mlr-org/mlr3spatiotempcv -* Source code: https://github.com/cran/mlr3spatiotempcv -* Date/Publication: 2024-04-17 12:10:05 UTC -* Number of recursive dependencies: 168 - -Run `revdepcheck::cloud_details(, "mlr3spatiotempcv")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘mlr3spatiotempcv-Ex.R’ failed - The error most likely occurred in: - - > ### Name: autoplot.ResamplingCustomCV - > ### Title: Visualization Functions for Non-Spatial CV Methods. - > ### Aliases: autoplot.ResamplingCustomCV plot.ResamplingCustomCV - > - > ### ** Examples - > - > if (mlr3misc::require_namespaces(c("sf", "patchwork"), quietly = TRUE)) { - ... - + - + autoplot(resampling, task) + - + ggplot2::scale_x_continuous(breaks = seq(-79.085, -79.055, 0.01)) - + autoplot(resampling, task, fold_id = 1) - + autoplot(resampling, task, fold_id = c(1, 2)) * - + ggplot2::scale_x_continuous(breaks = seq(-79.085, -79.055, 0.01)) - + } - Error in identicalUnits(x) : object is not a unit - Calls: ... assemble_guides -> guides_build -> unit.c -> identicalUnits - Execution halted - ``` - -## In both - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘spatiotemp-viz.Rmd’ - ... - - > knitr::opts_chunk$set(collapse = TRUE, comment = "#>") - - > knitr::include_graphics("../man/figures/sptcv_cstf_multiplot.png") - - When sourcing ‘spatiotemp-viz.R’: - Error: Cannot find the file(s): "../man/figures/sptcv_cstf_multiplot.png" - Execution halted - - ‘mlr3spatiotempcv.Rmd’ using ‘UTF-8’... OK - ‘spatiotemp-viz.Rmd’ using ‘UTF-8’... failed - ``` - -* checking installed package size ... NOTE - ``` - installed size is 5.9Mb - sub-directories of 1Mb or more: - data 3.5Mb - ``` - -# mlr3viz - -
- -* Version: 0.9.0 -* GitHub: https://github.com/mlr-org/mlr3viz -* Source code: https://github.com/cran/mlr3viz -* Date/Publication: 2024-07-01 12:30:02 UTC -* Number of recursive dependencies: 142 - -Run `revdepcheck::cloud_details(, "mlr3viz")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘mlr3viz-Ex.R’ failed - The error most likely occurred in: - - > ### Name: autoplot.OptimInstanceBatchSingleCrit - > ### Title: Plots for Optimization Instances - > ### Aliases: autoplot.OptimInstanceBatchSingleCrit - > - > ### ** Examples - > - > if (requireNamespace("mlr3") && requireNamespace("bbotk") && requireNamespace("patchwork")) { - ... - INFO [09:19:55.573] [bbotk] 5.884797 2.2371095 -32.51896 - INFO [09:19:55.573] [bbotk] -7.841127 -0.8872557 -91.31148 - INFO [09:19:55.608] [bbotk] Finished optimizing after 20 evaluation(s) - INFO [09:19:55.609] [bbotk] Result: - INFO [09:19:55.613] [bbotk] x1 x2 x_domain y - INFO [09:19:55.613] [bbotk] - INFO [09:19:55.613] [bbotk] 2.582281 -2.940254 9.657379 - Error in identicalUnits(x) : object is not a unit - Calls: print ... assemble_guides -> guides_build -> unit.c -> identicalUnits - Execution halted - ``` - -# modeltime.resample - -
- -* Version: 0.2.3 -* GitHub: https://github.com/business-science/modeltime.resample -* Source code: https://github.com/cran/modeltime.resample -* Date/Publication: 2023-04-12 15:50:02 UTC -* Number of recursive dependencies: 228 - -Run `revdepcheck::cloud_details(, "modeltime.resample")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > - > # Machine Learning - > library(tidymodels) - ── Attaching packages ────────────────────────────────────── tidymodels 1.2.0 ── - ✔ broom 1.0.6 ✔ recipes 1.1.0 - ✔ dials 1.2.1 ✔ rsample 1.2.1 - ... - ▆ - 1. ├─m750_models_resample %>% ... at test-modeltime_fit_resamples.R:116:5 - 2. └─modeltime.resample::plot_modeltime_resamples(., .interactive = TRUE) - 3. ├─plotly::ggplotly(g) - 4. └─plotly:::ggplotly.ggplot(g) - 5. └─plotly::gg2list(...) - - [ FAIL 1 | WARN 4 | SKIP 0 | PASS 16 ] - Error: Test failures - Execution halted - ``` - -## In both - -* checking dependencies in R code ... NOTE - ``` - Namespaces in Imports field not imported from: - ‘crayon’ ‘dials’ ‘glue’ ‘parsnip’ - All declared Imports should be used. - ``` - -# move - -
- -* Version: 4.2.4 -* GitHub: NA -* Source code: https://github.com/cran/move -* Date/Publication: 2023-07-06 23:10:02 UTC -* Number of recursive dependencies: 153 - -Run `revdepcheck::cloud_details(, "move")` for more info - -
- -## Newly broken - -* checking installed package size ... NOTE - ``` - installed size is 5.4Mb - sub-directories of 1Mb or more: - R 2.0Mb - ``` - -## In both - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘move.Rmd’ - ... - - > leroyWithGap_p <- spTransform(leroyWithGap, center = TRUE) - - > dbb <- brownian.bridge.dyn(leroyWithGap_p, raster = 100, - + location.error = 20) - Computational size: 7.0e+07 - - When sourcing ‘move.R’: - Error: Lower x grid not large enough, consider extending the raster in that direction or enlarging the ext argument - Execution halted - - ‘browseMovebank.Rmd’ using ‘UTF-8’... OK - ‘move.Rmd’ using ‘UTF-8’... failed - ``` - -# mtb - -
- -* Version: 0.1.8 -* GitHub: https://github.com/yh202109/mtb -* Source code: https://github.com/cran/mtb -* Date/Publication: 2022-10-20 17:22:35 UTC -* Number of recursive dependencies: 64 - -Run `revdepcheck::cloud_details(, "mtb")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(mtb) - > - > test_check("mtb") - [ FAIL 2 | WARN 13 | SKIP 0 | PASS 56 ] - - ══ Failed tests ════════════════════════════════════════════════════════════════ - ... - - "yend" [6] - - "xmin" [7] - - "xmax" [8] - - "ymin" [9] - - "ymax" [10] - ... ... ... and 3 more ... - - [ FAIL 2 | WARN 13 | SKIP 0 | PASS 56 ] - Error: Test failures - Execution halted - ``` - -# neatmaps - -
- -* Version: 2.1.0 -* GitHub: https://github.com/PhilBoileau/neatmaps -* Source code: https://github.com/cran/neatmaps -* Date/Publication: 2019-05-12 19:10:03 UTC -* Number of recursive dependencies: 99 - -Run `revdepcheck::cloud_details(, "neatmaps")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘neatmaps-Ex.R’ failed - The error most likely occurred in: - - > ### Name: consClustResTable - > ### Title: Consensus Cluster Results in a Table - > ### Aliases: consClustResTable - > - > ### ** Examples - > - > # create the data frame using the network, node and edge attributes - ... - > df <- netsDataFrame(network_attr_df, - + node_attr_df, - + edge_df) - > - > # run the neatmap code on df - > neat_res <- neatmap(df, scale_df = "ecdf", max_k = 3, reps = 100, - + xlab = "vars", ylab = "nets", xlab_cex = 1, ylab_cex = 1) - Error in pm[[2]] : subscript out of bounds - Calls: neatmap ... %>% -> layout -> ggplotly -> ggplotly.ggplot -> gg2list - Execution halted - ``` - -## In both - -* checking installed package size ... NOTE - ``` - installed size is 6.3Mb - ``` - -# NetFACS - -
- -* Version: 0.5.0 -* GitHub: NA -* Source code: https://github.com/cran/NetFACS -* Date/Publication: 2022-12-06 17:32:35 UTC -* Number of recursive dependencies: 101 - -Run `revdepcheck::cloud_details(, "NetFACS")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘NetFACS-Ex.R’ failed - The error most likely occurred in: - - > ### Name: network_conditional - > ### Title: Create a network based on conditional probabilities of dyads of - > ### elements - > ### Aliases: network_conditional - > - > ### ** Examples - > - ... - Warning in grid.Call.graphics(C_text, as.graphicsAnnot(x$label), x$x, x$y, : - font family 'Arial Narrow' not found in PostScript font database - Warning in grid.Call.graphics(C_text, as.graphicsAnnot(x$label), x$x, x$y, : - font family 'Arial Narrow' not found in PostScript font database - Warning in grid.Call.graphics(C_text, as.graphicsAnnot(x$label), x$x, x$y, : - font family 'Arial Narrow' not found in PostScript font database - Error in grid.Call.graphics(C_text, as.graphicsAnnot(x$label), x$x, x$y, : - invalid font type - Calls: ... drawDetails -> drawDetails.text -> grid.Call.graphics - Execution halted - ``` - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘netfacs_tutorial.Rmd’ - ... - Warning in grid.Call.graphics(C_text, as.graphicsAnnot(x$label), x$x, x$y, : - font family 'Arial Narrow' not found in PostScript font database - Warning in grid.Call.graphics(C_text, as.graphicsAnnot(x$label), x$x, x$y, : - font family 'Arial Narrow' not found in PostScript font database - Warning in grid.Call.graphics(C_text, as.graphicsAnnot(x$label), x$x, x$y, : - font family 'Arial Narrow' not found in PostScript font database - - When sourcing ‘netfacs_tutorial.R’: - Error: invalid font type - Execution halted - - ‘netfacs_tutorial.Rmd’ using ‘UTF-8’... failed - ``` - -# NeuralSens - -
- -* Version: 1.1.3 -* GitHub: https://github.com/JaiPizGon/NeuralSens -* Source code: https://github.com/cran/NeuralSens -* Date/Publication: 2024-05-11 19:43:03 UTC -* Number of recursive dependencies: 138 - -Run `revdepcheck::cloud_details(, "NeuralSens")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘NeuralSens-Ex.R’ failed - The error most likely occurred in: - - > ### Name: SensMatPlot - > ### Title: Plot sensitivities of a neural network model - > ### Aliases: SensMatPlot - > - > ### ** Examples - > - > ## Load data ------------------------------------------------------------------- - ... - final value 1321.996301 - converged - > # Try HessianMLP - > H <- NeuralSens::HessianMLP(nnetmod, trData = nntrData, plot = FALSE) - > NeuralSens::SensMatPlot(H) - > S <- NeuralSens::SensAnalysisMLP(nnetmod, trData = nntrData, plot = FALSE) - > NeuralSens::SensMatPlot(H, S, senstype = "interactions") - Error in names(labels) <- `*vtmp*` : attempt to set an attribute on NULL - Calls: ... ggplot_add -> ggplot_add.new_aes -> bump_aes_labels - Execution halted - ``` - -# NHSRplotthedots - -
- -* Version: 0.1.0 -* GitHub: NA -* Source code: https://github.com/cran/NHSRplotthedots -* Date/Publication: 2021-11-03 20:20:10 UTC -* Number of recursive dependencies: 88 - -Run `revdepcheck::cloud_details(, "NHSRplotthedots")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘spelling.R’ - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(NHSRplotthedots) - > - > test_check("NHSRplotthedots") - [ FAIL 1 | WARN 733 | SKIP 3 | PASS 431 ] - - ... - - `actual$type` is absent - `expected$type` is a character vector ('type') - - `actual$text` is absent - `expected$text` is a character vector ('text') - - [ FAIL 1 | WARN 733 | SKIP 3 | PASS 431 ] - Error: Test failures - Execution halted - ``` - -## In both - -* checking dependencies in R code ... NOTE - ``` - Namespaces in Imports field not imported from: - ‘NHSRdatasets’ ‘grid’ ‘utils’ - All declared Imports should be used. - ``` - -# NIMAA - -
- -* Version: 0.2.1 -* GitHub: https://github.com/jafarilab/NIMAA -* Source code: https://github.com/cran/NIMAA -* Date/Publication: 2022-04-11 14:12:45 UTC -* Number of recursive dependencies: 177 - -Run `revdepcheck::cloud_details(, "NIMAA")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘NIMAA-Ex.R’ failed - The error most likely occurred in: - - > ### Name: extractSubMatrix - > ### Title: Extract the non-missing submatrices from a given matrix. - > ### Aliases: extractSubMatrix - > - > ### ** Examples - > - > # load part of the beatAML data - ... - + row.vars = "inhibitor") - binmatnest.temperature - 13.21221 - Size of Square: 66 rows x 66 columns - Size of Rectangular_row: 6 rows x 105 columns - Size of Rectangular_col: 99 rows x 2 columns - Size of Rectangular_element_max: 59 rows x 79 columns - Error in pm[[2]] : subscript out of bounds - Calls: extractSubMatrix ... plotSubmatrix -> print -> -> ggplotly.ggplot -> gg2list - Execution halted - ``` - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(NIMAA) - Warning message: - In check_dep_version() : ABI version mismatch: - lme4 was built with Matrix ABI version 1 - Current Matrix ABI version is 0 - Please re-install lme4 from source or restore original 'Matrix' package - ... - 1. └─NIMAA::extractSubMatrix(...) at test-extract-nonmissing-submatrix.R:5:3 - 2. └─NIMAA:::plotSubmatrix(...) - 3. ├─base::print(plotly::ggplotly(p)) - 4. ├─plotly::ggplotly(p) - 5. └─plotly:::ggplotly.ggplot(p) - 6. └─plotly::gg2list(...) - - [ FAIL 1 | WARN 4 | SKIP 0 | PASS 7 ] - Error: Test failures - Execution halted - ``` - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘NIMAA-vignette.Rmd’ - ... - - > beatAML_incidence_matrix <- plotIncMatrix(x = beatAML_data, - + index_nominal = c(2, 1), index_numeric = 3, print_skim = FALSE, - + plot_weigh .... [TRUNCATED] - - Na/missing values Proportion: 0.2603 - - When sourcing ‘NIMAA-vignette.R’: - Error: subscript out of bounds - Execution halted - - ‘NIMAA-vignette.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - ... - --- re-building ‘NIMAA-vignette.Rmd’ using rmarkdown - - Quitting from lines 49-57 [plotIncMatrix function] (NIMAA-vignette.Rmd) - Error: processing vignette 'NIMAA-vignette.Rmd' failed with diagnostics: - subscript out of bounds - --- failed re-building ‘NIMAA-vignette.Rmd’ - - SUMMARY: processing the following file failed: - ‘NIMAA-vignette.Rmd’ - - Error: Vignette re-building failed. - Execution halted - ``` - -## In both - -* checking installed package size ... NOTE - ``` - installed size is 6.5Mb - sub-directories of 1Mb or more: - data 2.0Mb - doc 4.0Mb - ``` - -* checking data for non-ASCII characters ... NOTE - ``` - Note: found 24 marked UTF-8 strings - ``` - -# OBIC - -
- -* Version: 3.0.2 -* GitHub: https://github.com/AgroCares/Open-Bodem-Index-Calculator -* Source code: https://github.com/cran/OBIC -* Date/Publication: 2024-03-05 12:40:08 UTC -* Number of recursive dependencies: 75 - -Run `revdepcheck::cloud_details(, "OBIC")` for more info - -
- -## Newly broken - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘obic_workability.Rmd’ - ... - > gg2 <- ggplot(data = dt, aes(x = field, fill = field)) + - + geom_col(aes(y = I_P_WO)) + theme_bw() + theme(axis.text = element_text(size = 10, - .... [TRUNCATED] - - > (gg | gg2) + plot_layout(guides = "collect") + plot_annotation(caption = "Baseline workability scores.", - + theme = theme(plot.caption = element .... [TRUNCATED] - - When sourcing ‘obic_workability.R’: - Error: object is not a unit - Execution halted - - ‘description-of-the-columns.Rmd’ using ‘UTF-8’... OK - ‘obic_introduction.Rmd’ using ‘UTF-8’... OK - ‘obic_score_aggregation.Rmd’ using ‘UTF-8’... OK - ‘obic_water_functions.Rmd’ using ‘UTF-8’... OK - ‘obic_workability.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘description-of-the-columns.Rmd’ using rmarkdown - --- finished re-building ‘description-of-the-columns.Rmd’ - - --- re-building ‘obic_introduction.Rmd’ using rmarkdown - ``` - -## In both - -* checking installed package size ... NOTE - ``` - installed size is 6.0Mb - sub-directories of 1Mb or more: - data 4.0Mb - doc 1.4Mb - ``` - -# OmicNavigator - -
- -* Version: 1.13.13 -* GitHub: https://github.com/abbvie-external/OmicNavigator -* Source code: https://github.com/cran/OmicNavigator -* Date/Publication: 2023-08-25 20:40:02 UTC -* Number of recursive dependencies: 86 - -Run `revdepcheck::cloud_details(, "OmicNavigator")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘tinytest.R’ - Running the tests in ‘tests/tinytest.R’ failed. - Complete output: - > # Test files in inst/tinytest/ - > if (requireNamespace("tinytest", quietly = TRUE)) { - + suppressMessages(tinytest::test_package("OmicNavigator")) - + } - - testAdd.R..................... 0 tests - testAdd.R..................... 0 tests - ... - testPlot.R.................... 140 tests OK - testPlot.R.................... 140 tests OK - testPlot.R.................... 141 tests OK - testPlot.R.................... 141 tests OK - testPlot.R.................... 141 tests OK - testPlot.R.................... 142 tests OK - testPlot.R.................... 142 tests OK - testPlot.R.................... 143 tests OK Error in pm[[2]] : subscript out of bounds - Calls: suppressMessages ... plotStudy -> f -> -> ggplotly.ggplot -> gg2list - Execution halted - ``` - -## In both - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘OmicNavigatorAPI.Rnw’ using Sweave - OmicNavigator R package version: 1.13.13 - The app is not installed. Install it with installApp() - Installing study "ABC" in /tmp/Rtmpd2oXDy/file1d222df82584 - Exporting study "ABC" as an R package - Note: No maintainer email was specified. Using the placeholder: Unknown - Calculating pairwise overlaps. This may take a while... - Exported study to /tmp/Rtmpd2oXDy/ONstudyABC - Success! - ... - l.14 ^^M - - ! ==> Fatal error occurred, no output PDF file produced! - --- failed re-building ‘OmicNavigatorUsersGuide.Rnw’ - - SUMMARY: processing the following files failed: - ‘OmicNavigatorAPI.Rnw’ ‘OmicNavigatorUsersGuide.Rnw’ - - Error: Vignette re-building failed. - Execution halted - ``` - -# oncomsm - -
- -* Version: 0.1.4 -* GitHub: https://github.com/Boehringer-Ingelheim/oncomsm -* Source code: https://github.com/cran/oncomsm -* Date/Publication: 2023-04-17 07:00:02 UTC -* Number of recursive dependencies: 126 - -Run `revdepcheck::cloud_details(, "oncomsm")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(dplyr) - - Attaching package: 'dplyr' - - The following objects are masked from 'package:stats': - - filter, lag - ... - 10. └─grid::unit.c(legend.box.margin[4], widths, legend.box.margin[2]) - 11. └─grid:::identicalUnits(x) - - [ FAIL 1 | WARN 0 | SKIP 2 | PASS 59 ] - Deleting unused snapshots: - • plots/plot-mstate-srp-model-2.svg - • plots/plot-mstate-srp-model-3.svg - • plots/plot-srp-model-2.svg - Error: Test failures - Execution halted - ``` - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘avoiding-bias.Rmd’ - ... - - > mdl <- create_srpmodel(A = define_srp_prior(median_t_q05 = c(1, - + 4, 12), median_t_q95 = c(6, 8, 36), shape_q05 = c(0.99, 0.99, - + 0.99), s .... [TRUNCATED] - - > plot(mdl, confidence = 0.9) - - ... - - > plot(mdl, parameter_sample = smpl_prior, confidence = 0.75) - - When sourcing ‘oncomsm.R’: - Error: object is not a unit - Execution halted - - ‘avoiding-bias.Rmd’ using ‘UTF-8’... failed - ‘oncomsm.Rmd’ using ‘UTF-8’... failed - ‘prior-choice.Rmd’ using ‘UTF-8’... OK - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘avoiding-bias.Rmd’ using rmarkdown - - Quitting from lines 35-46 [unnamed-chunk-2] (avoiding-bias.Rmd) - Error: processing vignette 'avoiding-bias.Rmd' failed with diagnostics: - object is not a unit - --- failed re-building ‘avoiding-bias.Rmd’ - - --- re-building ‘oncomsm.Rmd’ using rmarkdown - - Quitting from lines 211-215 [plotting-the-prior] (oncomsm.Rmd) - Error: processing vignette 'oncomsm.Rmd' failed with diagnostics: - object is not a unit - --- failed re-building ‘oncomsm.Rmd’ - - --- re-building ‘prior-choice.Rmd’ using rmarkdown - ``` - -## In both - -* checking installed package size ... NOTE - ``` - installed size is 59.1Mb - sub-directories of 1Mb or more: - doc 1.1Mb - libs 56.9Mb - ``` - -* checking for GNU extensions in Makefiles ... NOTE - ``` - GNU make is a SystemRequirements. - ``` - -# pafr - -
- -* Version: 0.0.2 -* GitHub: https://github.com/dwinter/pafr -* Source code: https://github.com/cran/pafr -* Date/Publication: 2020-12-08 10:20:12 UTC -* Number of recursive dependencies: 110 - -Run `revdepcheck::cloud_details(, "pafr")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(pafr) - Loading required package: ggplot2 - > - > test_check("pafr") - [ FAIL 6 | WARN 2 | SKIP 0 | PASS 70 ] - - ... - ── Failure ('test_plot.r:11:5'): dotplot works produces a plot ───────────────── - unname(labs["xintercept"]) not equal to "xintercept". - target is NULL, current is character - ── Failure ('test_plot.r:12:5'): dotplot works produces a plot ───────────────── - unname(labs["yintercept"]) not equal to "yintercept". - target is NULL, current is character - - [ FAIL 6 | WARN 2 | SKIP 0 | PASS 70 ] - Error: Test failures - Execution halted - ``` - -## In both - -* checking LazyData ... NOTE - ``` - 'LazyData' is specified without a 'data' directory - ``` - -# patchwork - -
- -* Version: 1.2.0 -* GitHub: https://github.com/thomasp85/patchwork -* Source code: https://github.com/cran/patchwork -* Date/Publication: 2024-01-08 14:40:02 UTC -* Number of recursive dependencies: 80 - -Run `revdepcheck::cloud_details(, "patchwork")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘patchwork-Ex.R’ failed - The error most likely occurred in: - - > ### Name: free - > ### Title: Free a plot from alignment - > ### Aliases: free - > - > ### ** Examples - > - > # Sometimes you have a plot that defies good composition alginment, e.g. due - ... - > p1 / p2 - > - > # We can fix this be using free - > free(p1) / p2 - > - > # We can still collect guides like before - > free(p1) / p2 + plot_layout(guides = "collect") - Error in identicalUnits(x) : object is not a unit - Calls: ... assemble_guides -> guides_build -> unit.c -> identicalUnits - Execution halted - ``` - -# pathviewr - -
- -* Version: 1.1.7 -* GitHub: https://github.com/ropensci/pathviewr -* Source code: https://github.com/cran/pathviewr -* Date/Publication: 2023-03-08 08:10:05 UTC -* Number of recursive dependencies: 184 - -Run `revdepcheck::cloud_details(, "pathviewr")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(pathviewr) - > #library(vdiffr) - > - > test_check("pathviewr") - [ FAIL 2 | WARN 1 | SKIP 0 | PASS 286 ] - - ... - ── Error ('test-plot_by_subject.R:168:3'): elev views wrangled correctly via tidyverse ── - Error in `expect_match(elev_all_plots[[3]][[4]][["labels"]][["x"]], "position_height")`: is.character(act$val) is not TRUE - Backtrace: - ▆ - 1. └─testthat::expect_match(...) at test-plot_by_subject.R:168:3 - 2. └─base::stopifnot(is.character(act$val)) - - [ FAIL 2 | WARN 1 | SKIP 0 | PASS 286 ] - Error: Test failures - Execution halted - ``` - -# pcutils - -
- -* Version: 0.2.6 -* GitHub: https://github.com/Asa12138/pcutils -* Source code: https://github.com/cran/pcutils -* Date/Publication: 2024-06-25 21:20:05 UTC -* Number of recursive dependencies: 281 - -Run `revdepcheck::cloud_details(, "pcutils")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘pcutils-Ex.R’ failed - The error most likely occurred in: - - > ### Name: multireg - > ### Title: Multiple regression/ variance decomposition analysis - > ### Aliases: multireg - > - > ### ** Examples - > - > if (requireNamespace("relaimpo") && requireNamespace("aplot")) { - ... - + } - Loading required namespace: relaimpo - Loading required namespace: aplot - [1] "NS" - [1] "WS" - [1] "CS" - Selecting by value - Error in as.unit(value) : object is not coercible to a unit - Calls: ... assemble_guides -> guides_build -> [<- -> [<-.unit -> as.unit - Execution halted - ``` - -# pdxTrees - -
- -* Version: 0.4.0 -* GitHub: https://github.com/mcconvil/pdxTrees -* Source code: https://github.com/cran/pdxTrees -* Date/Publication: 2020-08-17 14:00:02 UTC -* Number of recursive dependencies: 105 - -Run `revdepcheck::cloud_details(, "pdxTrees")` for more info - -
- -## Newly broken - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘pdxTrees-vignette.Rmd’ - ... - + y = Pollution_Removal_value, color = Mature_Size)) + geom_point(size = 2, - + .... [TRUNCATED] - - > berkeley_graph + transition_states(states = Mature_Size, - + transition_length = 10, state_length = 8) + enter_grow() + - + exit_shrink() - - When sourcing ‘pdxTrees-vignette.R’: - Error: argument "theme" is missing, with no default - Execution halted - - ‘pdxTrees-vignette.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘pdxTrees-vignette.Rmd’ using rmarkdown - ``` - -## In both - -* checking LazyData ... NOTE - ``` - 'LazyData' is specified without a 'data' directory - ``` - -# personalized - -
- -* Version: 0.2.7 -* GitHub: https://github.com/jaredhuling/personalized -* Source code: https://github.com/cran/personalized -* Date/Publication: 2022-06-27 20:20:03 UTC -* Number of recursive dependencies: 94 - -Run `revdepcheck::cloud_details(, "personalized")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > Sys.setenv("R_TESTS" = "") - > library(testthat) - > library(personalized) - Loading required package: glmnet - Loading required package: Matrix - Loaded glmnet 4.1-8 - Loading required package: mgcv - ... - 4. └─personalized:::plot.subgroup_validated(subgrp.val, type = "stability") - 5. ├─plotly::subplot(...) - 6. │ └─plotly:::dots2plots(...) - 7. ├─plotly::ggplotly(p.primary, tooltip = paste0("tooltip", 1:4)) - 8. └─plotly:::ggplotly.ggplot(...) - 9. └─plotly::gg2list(...) - - [ FAIL 1 | WARN 2 | SKIP 0 | PASS 215 ] - Error: Test failures - Execution halted - ``` - -# phylepic - -
- -* Version: 0.2.0 -* GitHub: https://github.com/cidm-ph/phylepic -* Source code: https://github.com/cran/phylepic -* Date/Publication: 2024-05-31 19:10:02 UTC -* Number of recursive dependencies: 89 - -Run `revdepcheck::cloud_details(, "phylepic")` for more info - -
- -## Newly broken - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘phylepic.Rmd’ - ... - - > clade <- ape::extract.clade(tree, clade.parent) - - > plot(clade) - - > plot(phylepic(clade, metadata, name, collection_date)) - - When sourcing ‘phylepic.R’: - Error: attempt to set an attribute on NULL - Execution halted - - ‘phylepic.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘phylepic.Rmd’ using rmarkdown - ``` - -# Plasmidprofiler - -
- -* Version: 0.1.6 -* GitHub: NA -* Source code: https://github.com/cran/Plasmidprofiler -* Date/Publication: 2017-01-06 01:10:47 -* Number of recursive dependencies: 90 - -Run `revdepcheck::cloud_details(, "Plasmidprofiler")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘Plasmidprofiler-Ex.R’ failed - The error most likely occurred in: - - > ### Name: main - > ### Title: Main: Run everything - > ### Aliases: main - > - > ### ** Examples - > - > main(blastdata, - ... - Saving 12 x 7 in image - Warning: Vectorized input to `element_text()` is not officially supported. - ℹ Results may be unexpected or may change in future versions of ggplot2. - Warning in geom_tile(aes(x = Plasmid, y = Sample, label = AMR_gene, fill = Inc_group, : - Ignoring unknown aesthetics: label and text - Warning: Use of `report$Sureness` is discouraged. - ℹ Use `Sureness` instead. - Error in pm[[2]] : subscript out of bounds - Calls: main ... -> ggplotly -> ggplotly.ggplot -> gg2list - Execution halted - ``` - -# platetools - -
- -* Version: 0.1.7 -* GitHub: https://github.com/swarchal/platetools -* Source code: https://github.com/cran/platetools -* Date/Publication: 2024-03-07 16:50:02 UTC -* Number of recursive dependencies: 48 - -Run `revdepcheck::cloud_details(, "platetools")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(platetools) - > - > test_check("platetools") - [ FAIL 2 | WARN 1 | SKIP 4 | PASS 187 ] - - ══ Skipped tests (4) ═══════════════════════════════════════════════════════════ - ... - length(out96) not equal to length(ggplot()). - 1/1 mismatches - [1] 11 - 10 == 1 - ── Failure ('test-plot_wrapper.R:34:5'): returns expected ggplot object ──────── - names(out96) not equal to names(ggplot()). - Lengths differ: 11 is not 10 - - [ FAIL 2 | WARN 1 | SKIP 4 | PASS 187 ] - Error: Test failures - Execution halted - ``` - -# plotDK - -
- -* Version: 0.1.0 -* GitHub: NA -* Source code: https://github.com/cran/plotDK -* Date/Publication: 2021-10-01 08:00:02 UTC -* Number of recursive dependencies: 86 - -Run `revdepcheck::cloud_details(, "plotDK")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(plotDK) - > - > test_check("plotDK") - [ FAIL 2 | WARN 0 | SKIP 0 | PASS 46 ] - - ══ Failed tests ════════════════════════════════════════════════════════════════ - ... - Error in `expect_setequal(c("x", "y", "group", "subgroup", "text", "fill"), - names(labels))`: `object` and `expected` must both be vectors - Backtrace: - ▆ - 1. └─testthat::expect_setequal(c("x", "y", "group", "subgroup", "text", "fill"), names(labels)) at test-plotDK.R:67:5 - 2. └─rlang::abort("`object` and `expected` must both be vectors") - - [ FAIL 2 | WARN 0 | SKIP 0 | PASS 46 ] - Error: Test failures - Execution halted - ``` - -## In both - -* checking dependencies in R code ... NOTE - ``` - Namespace in Imports field not imported from: ‘mapproj’ - All declared Imports should be used. - ``` - -* checking data for non-ASCII characters ... NOTE - ``` - Note: found 12992 marked UTF-8 strings - ``` - -# plotly - -
- -* Version: 4.10.4 -* GitHub: https://github.com/plotly/plotly.R -* Source code: https://github.com/cran/plotly -* Date/Publication: 2024-01-13 22:40:02 UTC -* Number of recursive dependencies: 147 - -Run `revdepcheck::cloud_details(, "plotly")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘plotly-Ex.R’ failed - The error most likely occurred in: - - > ### Name: style - > ### Title: Modify trace(s) - > ### Aliases: style - > - > ### ** Examples - > - > ## Don't show: - ... - + # this clobbers the previously supplied marker.line.color - + style(p, marker.line = list(width = 2.5), marker.size = 10) - + ## Don't show: - + }) # examplesIf - > (p <- ggplotly(qplot(data = mtcars, wt, mpg, geom = c("point", "smooth")))) - Warning: `qplot()` was deprecated in ggplot2 3.4.0. - `geom_smooth()` using method = 'loess' and formula = 'y ~ x' - Error in pm[[2]] : subscript out of bounds - Calls: ... eval -> eval -> ggplotly -> ggplotly.ggplot -> gg2list - Execution halted - ``` - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library("testthat") - > library("plotly") - Loading required package: ggplot2 - - Attaching package: 'plotly' - - The following object is masked from 'package:ggplot2': - ... - • plotly-subplot/subplot-bump-axis-annotation.svg - • plotly-subplot/subplot-bump-axis-image.svg - • plotly-subplot/subplot-bump-axis-shape-shared.svg - • plotly-subplot/subplot-bump-axis-shape.svg - • plotly-subplot/subplot-reposition-annotation.svg - • plotly-subplot/subplot-reposition-image.svg - • plotly-subplot/subplot-reposition-shape-fixed.svg - • plotly-subplot/subplot-reposition-shape.svg - Error: Test failures - Execution halted - ``` - -## In both - -* checking installed package size ... NOTE - ``` - installed size is 7.1Mb - sub-directories of 1Mb or more: - R 1.0Mb - htmlwidgets 4.0Mb - ``` - -# pmartR - -
- -* Version: 2.4.5 -* GitHub: https://github.com/pmartR/pmartR -* Source code: https://github.com/cran/pmartR -* Date/Publication: 2024-05-21 15:50:02 UTC -* Number of recursive dependencies: 149 - -Run `revdepcheck::cloud_details(, "pmartR")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(pmartR) - > - > test_check("pmartR") - [ FAIL 1 | WARN 1 | SKIP 11 | PASS 2375 ] - - ══ Skipped tests (11) ══════════════════════════════════════════════════════════ - ... - • plots/plot-spansres-color-high-color-low.svg - • plots/plot-spansres.svg - • plots/plot-statres-anova-volcano.svg - • plots/plot-statres-anova.svg - • plots/plot-statres-combined-volcano.svg - • plots/plot-statres-combined.svg - • plots/plot-statres-gtest.svg - • plots/plot-totalcountfilt.svg - Error: Test failures - Execution halted - ``` - -## In both - -* checking installed package size ... NOTE - ``` - installed size is 10.4Mb - sub-directories of 1Mb or more: - R 1.5Mb - help 1.5Mb - libs 6.3Mb - ``` - -# pmxTools - -
- -* Version: 1.3 -* GitHub: https://github.com/kestrel99/pmxTools -* Source code: https://github.com/cran/pmxTools -* Date/Publication: 2023-02-21 16:00:08 UTC -* Number of recursive dependencies: 85 - -Run `revdepcheck::cloud_details(, "pmxTools")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(pmxTools) - Loading required package: patchwork - > - > test_check("pmxTools") - [ FAIL 1 | WARN 1 | SKIP 12 | PASS 110 ] - - ... - 24. └─handlers[[1L]](cnd) - 25. └─cli::cli_abort(...) - 26. └─rlang::abort(...) - - [ FAIL 1 | WARN 1 | SKIP 12 | PASS 110 ] - Deleting unused snapshots: - • plot/conditioned-distplot.svg - • plot/perc.svg - Error: Test failures - Execution halted - ``` - -## In both - -* checking Rd cross-references ... NOTE - ``` - Package unavailable to check Rd xrefs: ‘DiagrammeR’ - ``` - -# posterior - -
- -* Version: 1.6.0 -* GitHub: https://github.com/stan-dev/posterior -* Source code: https://github.com/cran/posterior -* Date/Publication: 2024-07-03 23:00:02 UTC -* Number of recursive dependencies: 119 - -Run `revdepcheck::cloud_details(, "posterior")` for more info - -
- -## Newly broken - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘pareto_diagnostics.Rmd’ using rmarkdown - --- finished re-building ‘pareto_diagnostics.Rmd’ - - --- re-building ‘posterior.Rmd’ using rmarkdown - --- finished re-building ‘posterior.Rmd’ - - --- re-building ‘rvar.Rmd’ using rmarkdown - - Quitting from lines 530-533 [mixture] (rvar.Rmd) - ... - NULL, NULL, NULL, list(NULL, NA, NULL, NULL, TRUE), NULL, 2, NULL, NULL, NULL, 1.2, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 0.2, NULL, list(NULL, NULL, NULL, 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, NULL, NULL, NULL, TRUE), NULL, "right", NULL, NULL, NULL, "center", NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 0, list(), 2, list("grey92", NA, NULL, NULL, TRUE), list(), NULL, NULL, NULL, list("white", NULL, NULL, NULL, FALSE, "white", - TRUE), NULL, list(NULL, 0.5, NULL, NULL, FALSE, NULL, TRUE), NULL, NULL, NULL, NULL, FALSE, list(NULL, "white", NULL, NULL, TRUE), list(NULL, NULL, NULL, 1.2, 0, 1, NULL, NULL, c(0, 0, 5.5, 0), NULL, TRUE), "panel", list(NULL, NULL, NULL, NULL, 0, 1, NULL, NULL, c(0, 0, 5.5, 0), NULL, TRUE), list(NULL, NULL, NULL, 0.8, 1, 1, NULL, NULL, c(5.5, 0, 0, 0), NULL, TRUE), "panel", list(NULL, NULL, NULL, 1.2, 0.5, 0.5, NULL, NULL, NULL, NULL, TRUE), "topleft", NULL, NULL, list("grey85", NA, NULL, - NULL, TRUE), NULL, NULL, "inherit", "inside", list(NULL, NULL, "grey10", 0.8, NULL, NULL, NULL, NULL, c(4.4, 4.4, 4.4, 4.4), NULL, TRUE), NULL, NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, NULL, -90, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, NULL, 90, NULL, NULL, NULL, TRUE), NULL, 2.75, 2.75)) - --- failed re-building ‘rvar.Rmd’ - - SUMMARY: processing the following file failed: - ‘rvar.Rmd’ - - Error: Vignette re-building failed. - Execution halted - ``` - -## In both - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘rvar.Rmd’ - ... - > y - rvar<4000>[3] mean ± sd: - [1] 3.00 ± 1.00 2.02 ± 0.99 0.96 ± 0.99 - - > X + y - - When sourcing ‘rvar.R’: - Error: Cannot broadcast array of shape [4000,3,1] to array of shape [4000,4,3]: - All dimensions must be 1 or equal. - Execution halted - - ‘pareto_diagnostics.Rmd’ using ‘UTF-8’... OK - ‘posterior.Rmd’ using ‘UTF-8’... OK - ‘rvar.Rmd’ using ‘UTF-8’... failed - ``` - -# PPQplan - -
- -* Version: 1.1.0 -* GitHub: https://github.com/allenzhuaz/PPQplan -* Source code: https://github.com/cran/PPQplan -* Date/Publication: 2020-10-08 04:30:06 UTC -* Number of recursive dependencies: 119 - -Run `revdepcheck::cloud_details(, "PPQplan")` for more info - -
- -## Newly broken - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘PPQnote.Rmd’ using rmarkdown - --- finished re-building ‘PPQnote.Rmd’ - - --- re-building ‘PPQplan-vignette.Rmd’ using rmarkdown - ``` - -## In both - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘PPQplan-vignette.Rmd’ - ... - - > devtools::load_all() - - When sourcing ‘PPQplan-vignette.R’: - Error: Could not find a root 'DESCRIPTION' file that starts with '^Package' in - '/tmp/RtmpjusJAT/filef521ca1f964/vignettes'. - ℹ Are you in your project directory and does your project have a 'DESCRIPTION' - file? - Execution halted - - ‘PPQnote.Rmd’ using ‘UTF-8’... OK - ‘PPQplan-vignette.Rmd’ using ‘UTF-8’... failed - ``` - -* checking installed package size ... NOTE - ``` - installed size is 12.1Mb - sub-directories of 1Mb or more: - doc 12.0Mb - ``` - -* checking LazyData ... NOTE - ``` - 'LazyData' is specified without a 'data' directory - ``` - -# ppseq - -
- -* Version: 0.2.4 -* GitHub: https://github.com/zabore/ppseq -* Source code: https://github.com/cran/ppseq -* Date/Publication: 2024-04-04 18:20:02 UTC -* Number of recursive dependencies: 106 - -Run `revdepcheck::cloud_details(, "ppseq")` for more info - -
- -## Newly broken - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘one_sample_expansion.Rmd’ - ... - - - - - > ptest <- plot(one_sample_cal_tbl, type1_range = c(0.05, - + 0.1), minimum_power = 0.7, plotly = TRUE) - - ... - - > ptest <- plot(two_sample_cal_tbl, type1_range = c(0.05, - + 0.1), minimum_power = 0.7, plotly = TRUE) - - When sourcing ‘two_sample_randomized.R’: - Error: subscript out of bounds - Execution halted - - ‘one_sample_expansion.Rmd’ using ‘UTF-8’... failed - ‘two_sample_randomized.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - ... - --- re-building ‘one_sample_expansion.Rmd’ using rmarkdown - - Quitting from lines 183-188 [unnamed-chunk-13] (one_sample_expansion.Rmd) - Error: processing vignette 'one_sample_expansion.Rmd' failed with diagnostics: - subscript out of bounds - --- failed re-building ‘one_sample_expansion.Rmd’ - - --- re-building ‘two_sample_randomized.Rmd’ using rmarkdown - ... - Quitting from lines 179-184 [unnamed-chunk-13] (two_sample_randomized.Rmd) - Error: processing vignette 'two_sample_randomized.Rmd' failed with diagnostics: - subscript out of bounds - --- failed re-building ‘two_sample_randomized.Rmd’ - - SUMMARY: processing the following files failed: - ‘one_sample_expansion.Rmd’ ‘two_sample_randomized.Rmd’ - - Error: Vignette re-building failed. - Execution halted - ``` - -## In both - -* checking installed package size ... NOTE - ``` - installed size is 11.0Mb - sub-directories of 1Mb or more: - doc 10.5Mb - ``` - -# precrec - -
- -* Version: 0.14.4 -* GitHub: https://github.com/evalclass/precrec -* Source code: https://github.com/cran/precrec -* Date/Publication: 2023-10-11 22:10:02 UTC -* Number of recursive dependencies: 71 - -Run `revdepcheck::cloud_details(, "precrec")` for more info - -
- -## Newly broken - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘introduction.Rmd’ - ... - > msmdat3 <- mmdata(samps2[["scores"]], samps2[["labels"]], - + modnames = samps2[["modnames"]]) - - > mscurves <- evalmod(msmdat3) - - > autoplot(mscurves) - - When sourcing ‘introduction.R’: - Error: object is not a unit - Execution halted - - ‘introduction.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘introduction.Rmd’ using rmarkdown - ``` - -## In both - -* checking installed package size ... NOTE - ``` - installed size is 6.5Mb - sub-directories of 1Mb or more: - libs 4.2Mb - ``` - -# priorsense - -
- -* Version: 1.0.1 -* GitHub: NA -* Source code: https://github.com/cran/priorsense -* Date/Publication: 2024-06-24 14:40:02 UTC -* Number of recursive dependencies: 113 - -Run `revdepcheck::cloud_details(, "priorsense")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘priorsense-Ex.R’ failed - The error most likely occurred in: - - > ### Name: powerscale_plots - > ### Title: Diagnostic plots for power-scaling sensitivity - > ### Aliases: powerscale_plots powerscale_plot_dens powerscale_plot_ecdf - > ### powerscale_plot_ecdf.powerscaled_sequence powerscale_plot_quantities - > ### powerscale_plot_quantities.powerscaled_sequence - > - > ### ** Examples - > - > ex <- example_powerscale_model() - > - > powerscale_plot_dens(ex$draws) - Error in use_defaults(..., self = self) : - unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, "black", TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), list(NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), 5.5, c(5.5, 5.5, 5.5, 5.5), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.75, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, - NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, 90, NULL, c(0, 2.75, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(), NULL, list(NU - Calls: ... -> -> compute_geom_2 -> - Execution halted - ``` - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘powerscaling.Rmd’ - ... - - 1 mu 0.393 0.563 prior-data conflict - 2 sigma 0.291 0.532 prior-data conflict - - > powerscale_plot_dens(fit, variable = "mu") - - When sourcing ‘powerscaling.R’: - Error: unused argument (theme = list(list("black", 0.545454545454545, 1, "butt", FALSE, "black", TRUE), list("white", "black", 0.545454545454545, 1, TRUE), list("sans", "plain", "black", 12, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), list(NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list("black", "white", "#3366FF", 0.545454545454545, 1.09090909090909, "sans", 4.21751764217518, 1.63636363636364, 19, TRUE), 6, c(6, 6, 6, 6), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, - c(3, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 3, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, 90, NULL, c(0, 3, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 3), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.4, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0 - Execution halted - - ‘powerscaling.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - ... - --- re-building ‘powerscaling.Rmd’ using rmarkdown - - Quitting from lines 118-119 [unnamed-chunk-6] (powerscaling.Rmd) - Error: processing vignette 'powerscaling.Rmd' failed with diagnostics: - unused argument (theme = list(list("black", 0.545454545454545, 1, "butt", FALSE, "black", TRUE), list("white", "black", 0.545454545454545, 1, TRUE), list("sans", "plain", "black", 12, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), list(NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list("black", "white", "#3366FF", 0.545454545454545, 1.09090909090909, "sans", 4.21751764217518, 1.63636363636364, 19, TRUE), 6, c(6, 6, 6, 6), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, - c(3, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 3, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, 90, NULL, c(0, 3, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 3), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.4, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.4, 0), NULL, - TRUE), NULL, list(), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, NULL, c(0, 0, 0, 2.4), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0.5, NULL, NULL, NULL, c(0, 2.4, 0, 2.4), NULL, TRUE), list("grey20", 0.3, NULL, NULL, FALSE, "grey20", FALSE), NULL, NULL, NULL, list(), NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 0.5, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 0.75, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, list(NULL, 0.4, NULL, NULL, FALSE, NULL, FALSE), NULL, - NULL, NULL, list(), NULL, NULL, NULL, NULL, list(), NULL, 2, NULL, NULL, list(), 1.2, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 0.2, NULL, list(NULL, NULL, NULL, 13, 0, NULL, NULL, NULL, NULL, NULL, FALSE), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, NULL, NULL, NULL, TRUE), NULL, "bottom", NULL, NULL, NULL, "center", NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 0, list(), 2, list(), list(), 1.5, NULL, NULL, list(), NULL, list(NULL, 0.5, NULL, NULL, FALSE, NULL, TRUE), NULL, NULL, NULL, - NULL, FALSE, list(), list(NULL, NULL, NULL, 1.2, 0, 1, NULL, NULL, c(0, 0, 6, 0), NULL, TRUE), "panel", list(NULL, NULL, NULL, NULL, 0, 1, NULL, NULL, c(0, 0, 6, 0), NULL, TRUE), list(NULL, NULL, NULL, 0.8, 1, 1, NULL, NULL, c(6, 0, 0, 0), NULL, TRUE), "panel", list(NULL, NULL, NULL, 1.2, 0.5, 0.5, NULL, NULL, NULL, NULL, TRUE), "topleft", NULL, NULL, list(), NULL, NULL, "inherit", "outside", list(NULL, NULL, "grey10", 0.9, NULL, NULL, NULL, NULL, c(4.8, 4.8, 4.8, 4.8), NULL, FALSE), NULL, NULL, - NULL, list(NULL, NULL, NULL, NULL, NULL, NULL, -90, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, NULL, 90, NULL, NULL, NULL, TRUE), NULL, 3, 3, list(), list(NULL, NULL, NULL, NULL, FALSE, NULL, TRUE), list(NULL, NULL, NULL, NULL, FALSE, NULL, TRUE), list(NULL, NULL, NULL, NULL, FALSE, NULL, TRUE), list(NULL, NULL, NULL, NULL, 0.5, 0.5, 0, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), 0.666666666666667, 0.333333333333333)) - --- failed re-building ‘powerscaling.Rmd’ - - SUMMARY: processing the following file failed: - ‘powerscaling.Rmd’ - - Error: Vignette re-building failed. - Execution halted - ``` - -# ProAE - -
- -* Version: 1.0.1 -* GitHub: NA -* Source code: https://github.com/cran/ProAE -* Date/Publication: 2024-06-17 23:30:03 UTC -* Number of recursive dependencies: 126 - -Run `revdepcheck::cloud_details(, "ProAE")` for more info - -
- -## Newly broken - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘toxFigures.Rmd’ - ... - $ PROCTCAE_9B_SCL: num 0 2 3 3 0 1 0 0 0 0 ... - $ PROCTCAE_9_COMP: num 0 2 3 0 0 0 0 0 0 0 ... - $ time : chr "Cycle 1" "Cycle 2" "Cycle 3" "Cycle 4" ... - - > figure_1 <- toxFigures(dsn = acute, cycle_var = "Cycle", - + baseline_val = 1, arm_var = "arm", id_var = "id") - - When sourcing ‘toxFigures.R’: - Error: attempt to set an attribute on NULL - Execution halted - - ‘toxAUC.Rmd’ using ‘UTF-8’... OK - ‘toxFigures.Rmd’ using ‘UTF-8’... failed - ‘toxTables.Rmd’ using ‘UTF-8’... OK - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘toxAUC.Rmd’ using rmarkdown - ``` - -# probably - -
- -* Version: 1.0.3 -* GitHub: https://github.com/tidymodels/probably -* Source code: https://github.com/cran/probably -* Date/Publication: 2024-02-23 03:20:02 UTC -* Number of recursive dependencies: 131 - -Run `revdepcheck::cloud_details(, "probably")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > # This file is part of the standard setup for testthat. - > # It is recommended that you do not modify it. - > # - > # Where should you do additional test configuration? - > # Learn more about the roles of various files in: - > # * https://r-pkgs.org/tests.html - > # * https://testthat.r-lib.org/reference/test_package.html#special-files - ... - - `actual$ymin` is absent - `expected$ymin` is a character vector ('lower') - - `actual$ymax` is absent - `expected$ymax` is a character vector ('upper') - - [ FAIL 2 | WARN 0 | SKIP 46 | PASS 466 ] - Error: Test failures - Execution halted - ``` - -# processmapR - -
- -* Version: 0.5.4 -* GitHub: https://github.com/bupaverse/processmapr -* Source code: https://github.com/cran/processmapR -* Date/Publication: 2024-07-15 13:10:01 UTC -* Number of recursive dependencies: 118 - -Run `revdepcheck::cloud_details(, "processmapR")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(processmapR) - - Attaching package: 'processmapR' - - The following object is masked from 'package:stats': - - ... - 10. └─processmapR:::return_plotly(p, plotly) - 11. ├─plotly::ggplotly(p) - 12. └─plotly:::ggplotly.ggplot(p) - 13. └─plotly::gg2list(...) - ── Failure ('test_trace_explorer.R:240:3'): test trace_explorer on eventlog with param `plotly` ── - `chart` inherits from 'gg'/'ggplot' not 'plotly'. - - [ FAIL 6 | WARN 0 | SKIP 10 | PASS 107 ] - Error: Test failures - Execution halted - ``` - -# psborrow - -
- -* Version: 0.2.1 -* GitHub: NA -* Source code: https://github.com/cran/psborrow -* Date/Publication: 2023-03-03 10:30:07 UTC -* Number of recursive dependencies: 108 - -Run `revdepcheck::cloud_details(, "psborrow")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(psborrow) - > - > test_check("psborrow") - [ FAIL 10 | WARN 0 | SKIP 1 | PASS 142 ] - - ══ Skipped tests (1) ═══════════════════════════════════════════════════════════ - ... - `expected` is a character vector ('ref') - ── Failure ('test-plots.R:126:5'): Ensure output is producing a ggplot2 object with appropriate parameters ── - p1$labels$yintercept (`actual`) not equal to "ref" (`expected`). - - `actual` is NULL - `expected` is a character vector ('ref') - - [ FAIL 10 | WARN 0 | SKIP 1 | PASS 142 ] - Error: Test failures - Execution halted - ``` - -# r2dii.plot - -
- -* Version: 0.4.0 -* GitHub: https://github.com/RMI-PACTA/r2dii.plot -* Source code: https://github.com/cran/r2dii.plot -* Date/Publication: 2024-02-29 16:40:02 UTC -* Number of recursive dependencies: 91 - -Run `revdepcheck::cloud_details(, "r2dii.plot")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘spelling.R’ - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(r2dii.plot) - > - > test_check("r2dii.plot") - Scale for colour is already present. - Adding another scale for colour, which will replace the existing scale. - ... - `expected` is a character vector ('year') - ── Failure ('test-plot_trajectory.R:41:3'): outputs default axis labels ──────── - p$labels$y (`actual`) not equal to "value" (`expected`). - - `actual` is NULL - `expected` is a character vector ('value') - - [ FAIL 2 | WARN 2 | SKIP 40 | PASS 122 ] - Error: Test failures - Execution halted - ``` - -# Radviz - -
- -* Version: 0.9.3 -* GitHub: https://github.com/yannabraham/Radviz -* Source code: https://github.com/cran/Radviz -* Date/Publication: 2022-03-25 18:10:02 UTC -* Number of recursive dependencies: 64 - -Run `revdepcheck::cloud_details(, "Radviz")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘Radviz-Ex.R’ failed - The error most likely occurred in: - - > ### Name: Radviz - > ### Title: Radviz Projection of Multidimensional Data - > ### Aliases: Radviz - > - > ### ** Examples - > - > data(iris) - > das <- c('Sepal.Length','Sepal.Width','Petal.Length','Petal.Width') - > S <- make.S(das) - > rv <- do.radviz(iris,S) - > plot(rv,anchors.only=FALSE) - Error in plot.radviz(rv, anchors.only = FALSE) : - 'language' object cannot be coerced to type 'double' - Calls: plot -> plot.radviz - Execution halted - ``` - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘multivariate_analysis.Rmd’ - ... - - > classic.S <- make.S(get.optim(classic.optim)) - - > btcells.rv <- do.radviz(btcells.df, classic.S) - - > plot(btcells.rv) + geom_point(aes(color = Treatment)) - - ... - [1] 15792 18 - - > ct.rv - - When sourcing ‘single_cell_projections.R’: - Error: 'language' object cannot be coerced to type 'double' - Execution halted - - ‘multivariate_analysis.Rmd’ using ‘UTF-8’... failed - ‘single_cell_projections.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘multivariate_analysis.Rmd’ using rmarkdown - ``` - -# rassta - -
- -* Version: 1.0.5 -* GitHub: https://github.com/bafuentes/rassta -* Source code: https://github.com/cran/rassta -* Date/Publication: 2022-08-30 22:30:02 UTC -* Number of recursive dependencies: 120 - -Run `revdepcheck::cloud_details(, "rassta")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘rassta-Ex.R’ failed - The error most likely occurred in: - - > ### Name: select_functions - > ### Title: Select Constrained Univariate Distribution Functions - > ### Aliases: select_functions - > - > ### ** Examples - > - > require(terra) - ... - > tvars <- terra::rast(tf) - > # Single-layer SpatRaster of topographic classification units - > ## 5 classification units - > tcf <- list.files(path = p, pattern = "topography.tif", full.names = TRUE) - > tcu <- terra::rast(tcf) - > # Automatic selection of distribution functions - > tdif <- select_functions(cu.rast = tcu, var.rast = tvars, fun = mean) - Error in pm[[2]] : subscript out of bounds - Calls: select_functions -> -> ggplotly.ggplot -> gg2list - Execution halted - ``` - -* checking tests ... ERROR - ``` - Running ‘tinytest.R’ - Running the tests in ‘tests/tinytest.R’ failed. - Complete output: - > - > if ( requireNamespace("tinytest", quietly=TRUE) ){ - + tinytest::test_package("rassta") - + } - - Attaching package: 'rassta' - - ... - test_select_functions.R....... 0 tests - test_select_functions.R....... 0 tests - test_select_functions.R....... 0 tests - test_select_functions.R....... 0 tests - test_select_functions.R....... 0 tests - test_select_functions.R....... 0 tests - test_select_functions.R....... 0 tests - test_select_functions.R....... 0 tests Error in pm[[2]] : subscript out of bounds - Calls: ... select_functions -> -> ggplotly.ggplot -> gg2list - Execution halted - ``` - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘signature.Rmd’ - ... - > clim.var <- rast(vardir) - - > clim.cu <- rast(paste(d, "/climate.tif", sep = "")) - - > clim.difun <- select_functions(cu.rast = clim.cu, - + var.rast = clim.var, mode = "auto") - - ... - When sourcing ‘signature.R’: - Error: subscript out of bounds - Execution halted - - ‘classunits.Rmd’ using ‘UTF-8’... OK - ‘modeling.Rmd’ using ‘UTF-8’... OK - ‘sampling.Rmd’ using ‘UTF-8’... OK - ‘signature.Rmd’ using ‘UTF-8’... failed - ‘similarity.Rmd’ using ‘UTF-8’... OK - ‘stratunits.Rmd’ using ‘UTF-8’... OK - ``` - -# REddyProc - -
- -* Version: 1.3.3 -* GitHub: https://github.com/bgctw/REddyProc -* Source code: https://github.com/cran/REddyProc -* Date/Publication: 2024-01-25 15:30:02 UTC -* Number of recursive dependencies: 93 - -Run `revdepcheck::cloud_details(, "REddyProc")` for more info - -
- -## Newly broken - -* checking installed package size ... NOTE - ``` - installed size is 5.7Mb - sub-directories of 1Mb or more: - R 1.5Mb - data 2.0Mb - libs 1.1Mb - ``` - -# redist - -
- -* Version: 4.2.0 -* GitHub: https://github.com/alarm-redist/redist -* Source code: https://github.com/cran/redist -* Date/Publication: 2024-01-13 13:20:02 UTC -* Number of recursive dependencies: 132 - -Run `revdepcheck::cloud_details(, "redist")` for more info - -
- -## Newly broken - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘redist.Rmd’ - ... - # ℹ 991 more rows - - > library(patchwork) - - > hist(plan_sum, max_dev) + hist(iowa_plans, comp) + - + plot_layout(guides = "collect") - - When sourcing ‘redist.R’: - Error: object is not a unit - Execution halted - - ‘common_args.Rmd’ using ‘UTF-8’... OK - ‘flip.Rmd’ using ‘UTF-8’... OK - ‘map-preproc.Rmd’ using ‘UTF-8’... OK - ‘redist.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘common_args.Rmd’ using rmarkdown - ``` - -## In both - -* checking installed package size ... NOTE - ``` - installed size is 27.7Mb - sub-directories of 1Mb or more: - data 1.2Mb - libs 23.7Mb - ``` - -# reReg - -
- -* Version: 1.4.6 -* GitHub: https://github.com/stc04003/reReg -* Source code: https://github.com/cran/reReg -* Date/Publication: 2023-09-20 08:00:02 UTC -* Number of recursive dependencies: 45 - -Run `revdepcheck::cloud_details(, "reReg")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘reReg-Ex.R’ failed - The error most likely occurred in: - - > ### Name: plot.Recur - > ### Title: Produce Event Plot or Mean Cumulative Function Plot - > ### Aliases: plot.Recur - > ### Keywords: Plots - > - > ### ** Examples - > - ... - 11. │ └─base::withCallingHandlers(...) - 12. └─ggplot2 (local) f(l = layers[[i]], d = data[[i]]) - 13. └─l$compute_geom_2(d, theme = plot$theme) - 14. └─ggplot2 (local) compute_geom_2(..., self = self) - 15. └─self$geom$use_defaults(...) - 16. └─ggplot2 (local) use_defaults(..., self = self) - 17. └─ggplot2:::check_aesthetics(new_params, nrow(data)) - 18. └─cli::cli_abort(...) - 19. └─rlang::abort(...) - Execution halted - ``` - -# reservr - -
- -* Version: 0.0.3 -* GitHub: https://github.com/AshesITR/reservr -* Source code: https://github.com/cran/reservr -* Date/Publication: 2024-06-24 16:40:02 UTC -* Number of recursive dependencies: 146 - -Run `revdepcheck::cloud_details(, "reservr")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘reservr-Ex.R’ failed - The error most likely occurred in: - - > ### Name: dist_bdegp - > ### Title: Construct a BDEGP-Family - > ### Aliases: dist_bdegp - > - > ### ** Examples - > - > dist <- dist_bdegp(n = 1, m = 2, u = 10, epsilon = 3) - ... - + theoretical = dist, - + empirical = dist_empirical(x), - + .x = seq(0, 20, length.out = 101), - + with_params = list(theoretical = params) - + ) - Warning: Removed 9 rows containing missing values or values outside the scale range - (`geom_line()`). - Error in as.unit(value) : object is not coercible to a unit - Calls: ... assemble_guides -> guides_build -> [<- -> [<-.unit -> as.unit - Execution halted - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘distributions.Rmd’ using rmarkdown - - Quitting from lines 170-227 [unnamed-chunk-10] (distributions.Rmd) - Error: processing vignette 'distributions.Rmd' failed with diagnostics: - object is not a unit - --- failed re-building ‘distributions.Rmd’ - - --- re-building ‘jss_paper.Rmd’ using rmarkdown - ``` - -## In both - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘distributions.Rmd’ - ... - - > attr(trunc_fit$logLik, "nobs") - [1] 62 - - > plot_distributions(true = norm, fit1 = norm, fit2 = norm2, - + fit3 = dist_normal(3), .x = seq(-2, 7, 0.01), with_params = list(true = list(mean .... [TRUNCATED] - - ... - - > dist$sample(1) - - When sourcing ‘jss_paper.R’: - Error: invalid arguments - Execution halted - - ‘distributions.Rmd’ using ‘UTF-8’... failed - ‘jss_paper.Rmd’ using ‘UTF-8’... failed - ‘tensorflow.Rmd’ using ‘UTF-8’... OK - ``` - -* checking installed package size ... NOTE - ``` - installed size is 15.7Mb - sub-directories of 1Mb or more: - R 1.5Mb - doc 1.2Mb - libs 12.7Mb - ``` - -* checking for GNU extensions in Makefiles ... NOTE - ``` - GNU make is a SystemRequirements. - ``` - -# rKOMICS - -
- -* Version: 1.3 -* GitHub: NA -* Source code: https://github.com/cran/rKOMICS -* Date/Publication: 2023-06-29 22:40:03 UTC -* Number of recursive dependencies: 128 - -Run `revdepcheck::cloud_details(, "rKOMICS")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘rKOMICS-Ex.R’ failed - The error most likely occurred in: - - > ### Name: msc.pca - > ### Title: Prinicple Component Analysis based on MSC - > ### Aliases: msc.pca - > - > ### ** Examples - > - > data(matrices) - ... - 11. │ └─base::withCallingHandlers(...) - 12. └─ggplot2 (local) f(l = layers[[i]], d = data[[i]]) - 13. └─l$compute_geom_2(d, theme = plot$theme) - 14. └─ggplot2 (local) compute_geom_2(..., self = self) - 15. └─self$geom$use_defaults(...) - 16. └─ggplot2 (local) use_defaults(..., self = self) - 17. └─ggplot2:::check_aesthetics(new_params, nrow(data)) - 18. └─cli::cli_abort(...) - 19. └─rlang::abort(...) - Execution halted - ``` - -## In both - -* checking installed package size ... NOTE - ``` - installed size is 24.8Mb - sub-directories of 1Mb or more: - extdata 24.0Mb - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘example.Rnw’ using Sweave - Loading required package: viridisLite - Warning: Removed 95 rows containing non-finite outside the scale range - (`stat_boxplot()`). - Warning: Removed 89 rows containing non-finite outside the scale range - (`stat_boxplot()`). - Warning: Removed 149 rows containing non-finite outside the scale range - (`stat_boxplot()`). - Warning: Removed 286 rows containing non-finite outside the scale range - ... - l.5 \usepackage - {xcolor}^^M - ! ==> Fatal error occurred, no output PDF file produced! - --- failed re-building ‘example.Rnw’ - - SUMMARY: processing the following file failed: - ‘example.Rnw’ - - Error: Vignette re-building failed. - Execution halted - ``` - -# RKorAPClient - -
- -* Version: 0.8.1 -* GitHub: https://github.com/KorAP/RKorAPClient -* Source code: https://github.com/cran/RKorAPClient -* Date/Publication: 2024-05-02 11:42:54 UTC -* Number of recursive dependencies: 124 - -Run `revdepcheck::cloud_details(, "RKorAPClient")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library("testthat") - > library("RKorAPClient") - > - > test_check("RKorAPClient") - - apiUrl: https://korap.ids-mannheim.de/api/v1.0/ - [ FAIL 1 | WARN 0 | SKIP 30 | PASS 25 ] - ... - 'test-demos.R:129:3', 'test-textMetadata.R:2:3', 'test-textMetadata.R:9:3' - - ══ Failed tests ════════════════════════════════════════════════════════════════ - ── Failure ('test-misc.R:224:5'): geom_freq_by_year_ci works correctly ───────── - gpt[["labels"]][["url"]] not equal to "webUIRequestUrl". - target is NULL, current is character - - [ FAIL 1 | WARN 0 | SKIP 30 | PASS 25 ] - Error: Test failures - Execution halted - ``` - -# RNAseqQC - -
- -* Version: 0.2.1 -* GitHub: https://github.com/frederikziebell/RNAseqQC -* Source code: https://github.com/cran/RNAseqQC -* Date/Publication: 2024-07-15 14:40:02 UTC -* Number of recursive dependencies: 177 - -Run `revdepcheck::cloud_details(, "RNAseqQC")` for more info - -
- -## Newly broken - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘introduction.Rmd’ - ... - + show_plot = F)$plot + theme(legend.position = "bottom") - - > plot_loadings(pca_res, PC = 2, color_by = "gc_content") - - > plot_pca_scatters(vsd, n_PCs = 5, color_by = "treatment", - + shape_by = "mutation") - - When sourcing 'introduction.R': - Error: object is not coercible to a unit - Execution halted - - ‘data.Rmd’ using ‘UTF-8’... OK - ‘introduction.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘data.Rmd’ using rmarkdown - --- finished re-building ‘data.Rmd’ - - --- re-building ‘introduction.Rmd’ using rmarkdown - ``` - -## In both - -* checking installed package size ... NOTE - ``` - installed size is 7.0Mb - sub-directories of 1Mb or more: - data 4.5Mb - doc 2.3Mb - ``` - -# roahd - -
- -* Version: 1.4.3 -* GitHub: https://github.com/astamm/roahd -* Source code: https://github.com/cran/roahd -* Date/Publication: 2021-11-04 00:10:02 UTC -* Number of recursive dependencies: 88 - -Run `revdepcheck::cloud_details(, "roahd")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘roahd-Ex.R’ failed - The error most likely occurred in: - - > ### Name: plot.depthgram - > ### Title: Specialized method to plot 'depthgram' objects - > ### Aliases: plot.depthgram - > - > ### ** Examples - > - > N <- 50 - ... - + N, - + centerline = sin(2 * pi * grid), - + Cov = Cov - + ) - > names <- paste0("id_", 1:nrow(Data[[1]])) - > DG <- depthgram(Data, marginal_outliers = TRUE, ids = names) - > plot(DG) - Error in pm[[2]] : subscript out of bounds - Calls: plot ... plotly_build -> ggplotly -> ggplotly.ggplot -> gg2list - Execution halted - ``` - -## In both - -* checking installed package size ... NOTE - ``` - installed size is 7.4Mb - sub-directories of 1Mb or more: - data 5.0Mb - doc 1.7Mb - ``` - -# romic - -
- -* Version: 1.1.3 -* GitHub: NA -* Source code: https://github.com/cran/romic -* Date/Publication: 2023-09-21 05:40:02 UTC -* Number of recursive dependencies: 113 - -Run `revdepcheck::cloud_details(, "romic")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > # This file is part of the standard setup for testthat. - > # It is recommended that you do not modify it. - > # - > # Where should you do additional test configuration? - > # Learn more about the roles of various files in: - > # * https://r-pkgs.org/testing-design.html#sec-tests-files-overview - > # * https://testthat.r-lib.org/articles/special-files.html - ... - 3. │ │ └─base::withCallingHandlers(...) - 4. │ ├─plotly::ggplotly(heatmap_plot) %>% plotly::layout(margin = 0) - 5. │ ├─plotly::ggplotly(heatmap_plot) - 6. │ └─plotly:::ggplotly.ggplot(heatmap_plot) - 7. │ └─plotly::gg2list(...) - 8. └─plotly::layout(., margin = 0) - - [ FAIL 1 | WARN 0 | SKIP 7 | PASS 66 ] - Error: Test failures - Execution halted - ``` - -# roptions - -
- -* Version: 1.0.3 -* GitHub: NA -* Source code: https://github.com/cran/roptions -* Date/Publication: 2020-05-11 11:10:06 UTC -* Number of recursive dependencies: 70 - -Run `revdepcheck::cloud_details(, "roptions")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘roptions-Ex.R’ failed - The error most likely occurred in: - - > ### Name: box.spread - > ### Title: Box Spread Strategy Function - > ### Aliases: box.spread - > - > ### ** Examples - > - > box.spread(100, 105, 95, 110, 3.2, 2.6, 1.1, 2.4) - ... - 35 5.7 - 36 5.7 - 37 5.7 - 38 5.7 - 39 5.7 - 40 5.7 - 41 5.7 - Error in pm[[2]] : subscript out of bounds - Calls: box.spread -> print -> ggplotly -> ggplotly.ggplot -> gg2list - Execution halted - ``` - -## In both - -* checking LazyData ... NOTE - ``` - 'LazyData' is specified without a 'data' directory - ``` - -# santaR - -
- -* Version: 1.2.4 -* GitHub: https://github.com/adwolfer/santaR -* Source code: https://github.com/cran/santaR -* Date/Publication: 2024-03-07 00:30:02 UTC -* Number of recursive dependencies: 93 - -Run `revdepcheck::cloud_details(, "santaR")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(santaR) - - This is santaR version 1.2.4 - - > - > test_check("santaR") - ... - 1/1 mismatches - [1] 11 - 10 == 1 - ── Failure ('test_dfSearch-plot_nbTP_histogram.R:69:3'): change dfCuttOff ────── - length(result_nbTPHisto) not equal to length(ggplot2::ggplot()). - 1/1 mismatches - [1] 11 - 10 == 1 - - [ FAIL 8 | WARN 1 | SKIP 0 | PASS 681 ] - Error: Test failures - Execution halted - ``` - -## In both - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘getting-started.Rmd’ - ... - - > knitr::include_graphics("../man/figures/santaR-approach.jpg") - - When sourcing ‘getting-started.R’: - Error: Cannot find the file(s): "../man/figures/santaR-approach.jpg" - Execution halted - when running code in ‘selecting-optimal-df.Rmd’ - ... - Execution halted - - ‘advanced-command-line-functions.Rmd’ using ‘UTF-8’... OK - ‘automated-command-line.Rmd’ using ‘UTF-8’... OK - ‘getting-started.Rmd’ using ‘UTF-8’... failed - ‘plotting-options.Rmd’ using ‘UTF-8’... OK - ‘prepare-input-data.Rmd’ using ‘UTF-8’... OK - ‘selecting-optimal-df.Rmd’ using ‘UTF-8’... failed - ‘theoretical-background.Rmd’ using ‘UTF-8’... OK - ‘santaR-GUI.pdf.asis’ using ‘UTF-8’... OK - ``` - -# scdtb - -
- -* Version: 0.1.0 -* GitHub: https://github.com/mightymetrika/scdtb -* Source code: https://github.com/cran/scdtb -* Date/Publication: 2024-04-30 08:50:02 UTC -* Number of recursive dependencies: 96 - -Run `revdepcheck::cloud_details(, "scdtb")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > # This file is part of the standard setup for testthat. - > # It is recommended that you do not modify it. - > # - > # Where should you do additional test configuration? - > # Learn more about the roles of various files in: - > # * https://r-pkgs.org/testing-design.html#sec-tests-files-overview - > # * https://testthat.r-lib.org/articles/special-files.html - ... - ── Failure ('test-mixed_model_analysis.R:119:3'): mixed_model_analysis uses the .participant variable to label data points - when .participant is not NULL ── - res$plot$labels$shape (`actual`) not equal to "factor(part)" (`expected`). - - `actual` is NULL - `expected` is a character vector ('factor(part)') - - [ FAIL 1 | WARN 0 | SKIP 0 | PASS 45 ] - Error: Test failures - Execution halted - ``` - -# scoringutils - -
- -* Version: 1.2.2 -* GitHub: https://github.com/epiforecasts/scoringutils -* Source code: https://github.com/cran/scoringutils -* Date/Publication: 2023-11-29 15:50:10 UTC -* Number of recursive dependencies: 81 - -Run `revdepcheck::cloud_details(, "scoringutils")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘scoringutils-Ex.R’ failed - The error most likely occurred in: - - > ### Name: plot_predictions - > ### Title: Plot Predictions vs True Values - > ### Aliases: plot_predictions - > - > ### ** Examples - > - > library(ggplot2) - ... - + by = c("target_type", "location"), - + range = c(0, 50, 90, 95) - + ) + - + facet_wrap(~ location + target_type, scales = "free_y") + - + aes(fill = model, color = model) - Error in use_defaults(..., self = self) : - unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, "black", TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), list(NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), 5.5, c(5.5, 5.5, 5.5, 5.5), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.75, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, - NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, 90, NULL, c(0, 2.75, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL - Calls: ... -> -> compute_geom_2 -> - Execution halted - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘metric-details.Rmd’ using rmarkdown - --- finished re-building ‘metric-details.Rmd’ - - --- re-building ‘scoring-forecasts-directly.Rmd’ using rmarkdown - --- finished re-building ‘scoring-forecasts-directly.Rmd’ - - --- re-building ‘scoringutils.Rmd’ using rmarkdown - ``` - -## In both - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘scoringutils.Rmd’ - ... - The following messages were produced when checking inputs: - 1. 144 values for `prediction` are NA in the data provided and the corresponding rows were removed. This may indicate a problem if unexpected. - - > example_quantile %>% make_NA(what = "truth", target_end_date >= - + "2021-07-15", target_end_date < "2021-05-22") %>% make_NA(what = "forecast", .... [TRUNCATED] - - When sourcing ‘scoringutils.R’: - Error: unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, "black", TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), list(NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), 5.5, c(5.5, 5.5, 5.5, 5.5), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.75, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, - NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, 90, NULL, c(0, 2.75, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, - Execution halted - - ‘metric-details.Rmd’ using ‘UTF-8’... OK - ‘scoring-forecasts-directly.Rmd’ using ‘UTF-8’... OK - ‘scoringutils.Rmd’ using ‘UTF-8’... failed - ``` - -# scUtils - -
- -* Version: 0.1.0 -* GitHub: NA -* Source code: https://github.com/cran/scUtils -* Date/Publication: 2020-06-25 16:20:02 UTC -* Number of recursive dependencies: 52 - -Run `revdepcheck::cloud_details(, "scUtils")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(scUtils) - > - > test_check("scUtils") - [ FAIL 1 | WARN 0 | SKIP 0 | PASS 32 ] - - ══ Failed tests ════════════════════════════════════════════════════════════════ - ── Failure ('test-plots.R:59:3'): all kinds of colnames are allowed ──────────── - p$labels not equal to list(y = "Dim2", x = "Dim1", colour = "expression"). - Length mismatch: comparison on first 2 components - - [ FAIL 1 | WARN 0 | SKIP 0 | PASS 32 ] - Error: Test failures - Execution halted - ``` - -## In both - -* checking LazyData ... NOTE - ``` - 'LazyData' is specified without a 'data' directory - ``` - -# SCVA - -
- -* Version: 1.3.1 -* GitHub: NA -* Source code: https://github.com/cran/SCVA -* Date/Publication: 2020-01-09 22:50:10 UTC -* Number of recursive dependencies: 80 - -Run `revdepcheck::cloud_details(, "SCVA")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘SCVA-Ex.R’ failed - The error most likely occurred in: - - > ### Name: graphly - > ### Title: Interactive plot of single-case data - > ### Aliases: graphly - > ### Keywords: Single-case design Graph - > - > ### ** Examples - > - > data(AB) - > graphly(design = "AB", data = AB) - Error in pm[[2]] : subscript out of bounds - Calls: graphly -> ggplotly -> ggplotly.ggplot -> gg2list - Execution halted - ``` - -# SDMtune - -
- -* Version: 1.3.1 -* GitHub: https://github.com/ConsBiol-unibern/SDMtune -* Source code: https://github.com/cran/SDMtune -* Date/Publication: 2023-07-03 12:20:02 UTC -* Number of recursive dependencies: 125 - -Run `revdepcheck::cloud_details(, "SDMtune")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(SDMtune) - - _____ ____ __ ___ __ - / ___/ / __ \ / |/ // /_ __ __ ____ ___ - \__ \ / / / // /|_/ // __// / / // __ \ / _ \ - ___/ // /_/ // / / // /_ / /_/ // / / // __/ - ... - `expected` is a character vector ('Var2') - ── Failure ('test-plotCor.R:6:3'): The plot has the correct labels and text size ── - p$labels$y (`actual`) not equal to "Var1" (`expected`). - - `actual` is NULL - `expected` is a character vector ('Var1') - - [ FAIL 2 | WARN 0 | SKIP 55 | PASS 315 ] - Error: Test failures - Execution halted - ``` - -## In both - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘basic-use.Rmd’ - ... - [1] 0.8336850 0.8672387 - - > folds <- randomFolds(data, k = 4, only_presence = TRUE, - + seed = 25) - - > auc(cv_model) - - When sourcing ‘basic-use.R’: - Error: object 'cv_model' not found - Execution halted - - ‘basic-use.Rmd’ using ‘UTF-8’... failed - ‘hyper-tuning.Rmd’ using ‘UTF-8’... OK - ‘presence-absence.Rmd’ using ‘UTF-8’... OK - ‘var-selection.Rmd’ using ‘UTF-8’... OK - ``` - -* checking installed package size ... NOTE - ``` - installed size is 5.2Mb - sub-directories of 1Mb or more: - R 3.0Mb - ``` - -# SeaVal - -
- -* Version: 1.2.0 -* GitHub: https://github.com/SeasonalForecastingEngine/SeaVal -* Source code: https://github.com/cran/SeaVal -* Date/Publication: 2024-06-14 15:20:05 UTC -* Number of recursive dependencies: 43 - -Run `revdepcheck::cloud_details(, "SeaVal")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘SeaVal-Ex.R’ failed - The error most likely occurred in: - - > ### Name: tfc_gha_plot - > ### Title: Plotting function with different map for Greater Horn of Africa - > ### Aliases: tfc_gha_plot - > - > ### ** Examples - > - > dt = tfc_from_efc(ecmwf_monthly[month == 11 & lat < 0]) - > pp = tfc_gha_plot(dt[year == 2018], expand.y = c(0.5,0.5)) - Error in names(labels) <- `*vtmp*` : attempt to set an attribute on NULL - Calls: tfc_gha_plot ... ggplot_add -> ggplot_add.new_aes -> bump_aes_labels - Execution halted - ``` - -## In both - -* checking installed package size ... NOTE - ``` - installed size is 20.6Mb - sub-directories of 1Mb or more: - data 2.0Mb - extdata 18.0Mb - ``` - -# sglg - -
- -* Version: 0.2.2 -* GitHub: NA -* Source code: https://github.com/cran/sglg -* Date/Publication: 2022-09-04 03:50:01 UTC -* Number of recursive dependencies: 96 - -Run `revdepcheck::cloud_details(, "sglg")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘sglg-Ex.R’ failed - The error most likely occurred in: - - > ### Name: deviance_residuals - > ### Title: Deviance Residuals for a Generalized Log-gamma Regression Model - > ### Aliases: deviance_residuals - > - > ### ** Examples - > - > # Example 1 - > n <- 300 - > error <- rglg(n,0,1,1) - > y <- 0.5 + error - > fit <- glg(y~1,data=as.data.frame(y)) - > deviance_residuals(fit) - Error in pm[[2]] : subscript out of bounds - Calls: deviance_residuals ... dots2plots -> ggplotly -> ggplotly.ggplot -> gg2list - Execution halted - ``` - -# sgsR - -
- -* Version: 1.4.5 -* GitHub: https://github.com/tgoodbody/sgsR -* Source code: https://github.com/cran/sgsR -* Date/Publication: 2024-03-03 15:10:02 UTC -* Number of recursive dependencies: 124 - -Run `revdepcheck::cloud_details(, "sgsR")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘spelling.R’ - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > # This file is part of the standard setup for testthat. - > # It is recommended that you do not modify it. - > # - > # Where should you do additional test configuration? - > # Learn more about the roles of various files in: - > # * https://r-pkgs.org/tests.html - ... - `expected` is a character vector ('zq90') - ── Failure ('test-utils-plot.R:19:3'): scatter messages ──────────────────────── - o1$labels$x (`actual`) not equal to "pzabove2" (`expected`). - - `actual` is NULL - `expected` is a character vector ('pzabove2') - - [ FAIL 2 | WARN 115 | SKIP 19 | PASS 508 ] - Error: Test failures - Execution halted - ``` - -# SHAPforxgboost - -
- -* Version: 0.1.3 -* GitHub: https://github.com/liuyanguu/SHAPforxgboost -* Source code: https://github.com/cran/SHAPforxgboost -* Date/Publication: 2023-05-29 17:20:07 UTC -* Number of recursive dependencies: 112 - -Run `revdepcheck::cloud_details(, "SHAPforxgboost")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘SHAPforxgboost-Ex.R’ failed - The error most likely occurred in: - - > ### Name: shap.plot.force_plot - > ### Title: Make the SHAP force plot - > ### Aliases: shap.plot.force_plot - > - > ### ** Examples - > - > - ... - > plot_data <- shap.prep.stack.data(shap_contrib = shap_values_iris, - + n_groups = 4) - All the features will be used. - - > shap.plot.force_plot(plot_data) - Data has N = 150 | zoom in length is 50 at location 90. - - Error in upgradeUnit.default(x) : Not a unit object - Calls: ... is.unit -> convertUnit -> upgradeUnit -> upgradeUnit.default - Execution halted - ``` - -# SHELF - -
- -* Version: 1.10.0 -* GitHub: https://github.com/OakleyJ/SHELF -* Source code: https://github.com/cran/SHELF -* Date/Publication: 2024-05-07 14:20:03 UTC -* Number of recursive dependencies: 126 - -Run `revdepcheck::cloud_details(, "SHELF")` for more info - -
- -## Newly broken - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘Dirichlet-elicitation.Rmd’ using rmarkdown - ``` - -# shinipsum - -
- -* Version: 0.1.1 -* GitHub: https://github.com/Thinkr-open/shinipsum -* Source code: https://github.com/cran/shinipsum -* Date/Publication: 2024-02-09 15:50:05 UTC -* Number of recursive dependencies: 90 - -Run `revdepcheck::cloud_details(, "shinipsum")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(shinipsum) - > - > test_check("shinipsum") - [ FAIL 2 | WARN 1 | SKIP 0 | PASS 3150 ] - - ══ Failed tests ════════════════════════════════════════════════════════════════ - ... - `a` has length 11, not length 10. - Backtrace: - ▆ - 1. └─base::lapply(...) at test-ggplot.R:3:3 - 2. └─shinipsum (local) FUN(X[[i]], ...) - 3. └─testthat::expect_length(a, expected_length) at test-ggplot.R:8:7 - - [ FAIL 2 | WARN 1 | SKIP 0 | PASS 3150 ] - Error: Test failures - Execution halted - ``` - -# SimNPH - -
- -* Version: 0.5.5 -* GitHub: https://github.com/SimNPH/SimNPH -* Source code: https://github.com/cran/SimNPH -* Date/Publication: 2024-03-04 10:10:02 UTC -* Number of recursive dependencies: 133 - -Run `revdepcheck::cloud_details(, "SimNPH")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(SimNPH) - Loading required package: SimDesign - Loading required package: survival - > - > test_check("SimNPH") - [ FAIL 2 | WARN 0 | SKIP 0 | PASS 343 ] - ... - - `names(actual)`: "x" - `names(expected)`: "x" "y" - - `actual$y` is absent - `expected$y` is a character vector ('mpg') - - [ FAIL 2 | WARN 0 | SKIP 0 | PASS 343 ] - Error: Test failures - Execution halted - ``` - -# smallsets - -
- -* Version: 2.0.0 -* GitHub: https://github.com/lydialucchesi/smallsets -* Source code: https://github.com/cran/smallsets -* Date/Publication: 2023-12-05 00:00:02 UTC -* Number of recursive dependencies: 107 - -Run `revdepcheck::cloud_details(, "smallsets")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘smallsets-Ex.R’ failed - The error most likely occurred in: - - > ### Name: Smallset_Timeline - > ### Title: Smallset Timeline - > ### Aliases: Smallset_Timeline - > - > ### ** Examples - > - > set.seed(145) - > - > Smallset_Timeline( - + data = s_data, - + code = system.file("s_data_preprocess.R", package = "smallsets") - + ) - Error in as.unit(value) : object is not coercible to a unit - Calls: ... assemble_guides -> guides_build -> [<- -> [<-.unit -> as.unit - Execution halted - ``` - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘smallsets.Rmd’ - ... - > library(smallsets) - - > set.seed(145) - - > Smallset_Timeline(data = s_data, code = system.file("s_data_preprocess.R", - + package = "smallsets")) - - When sourcing ‘smallsets.R’: - Error: object is not coercible to a unit - Execution halted - - ‘smallsets.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - ... - --- re-building ‘smallsets.Rmd’ using rmarkdown - - Quitting from lines 36-42 [timeline1] (smallsets.Rmd) - Error: processing vignette 'smallsets.Rmd' failed with diagnostics: - object is not coercible to a unit - --- failed re-building ‘smallsets.Rmd’ - - SUMMARY: processing the following file failed: - ‘smallsets.Rmd’ - - Error: Vignette re-building failed. - Execution halted - ``` - -## In both - -* checking package dependencies ... NOTE - ``` - Package suggested but not available for checking: ‘gurobi’ - ``` - -# spbal - -
- -* Version: 1.0.0 -* GitHub: NA -* Source code: https://github.com/cran/spbal -* Date/Publication: 2024-05-17 16:00:02 UTC -* Number of recursive dependencies: 77 - -Run `revdepcheck::cloud_details(, "spbal")` for more info - -
- -## Newly broken - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘spbal.Rmd’ - ... - st_point_on_surface may not give correct results for longitude/latitude data - Warning in st_point_on_surface.sfc(sf::st_zm(x)) : - st_point_on_surface may not give correct results for longitude/latitude data - - When sourcing ‘spbal.R’: - Error: Problem while setting up geom aesthetics. - ℹ Error occurred in the 1st layer. - Caused by error in `$<-.data.frame`: - ! replacement has 1 row, data has 0 - Execution halted - - ‘spbal.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - ... - --- re-building ‘spbal.Rmd’ using rmarkdown - - Quitting from lines 159-187 [BASex1c] (spbal.Rmd) - Error: processing vignette 'spbal.Rmd' failed with diagnostics: - Problem while setting up geom aesthetics. - ℹ Error occurred in the 1st layer. - Caused by error in `$<-.data.frame`: - ! replacement has 1 row, data has 0 - --- failed re-building ‘spbal.Rmd’ - - SUMMARY: processing the following file failed: - ‘spbal.Rmd’ - - Error: Vignette re-building failed. - Execution halted - ``` - -# spinifex - -
- -* Version: 0.3.7.0 -* GitHub: https://github.com/nspyrison/spinifex -* Source code: https://github.com/cran/spinifex -* Date/Publication: 2024-01-29 14:40:02 UTC -* Number of recursive dependencies: 164 - -Run `revdepcheck::cloud_details(, "spinifex")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘spelling.R’ - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(spinifex) - Loading required package: tourr - -------------------------------------------------------- - spinifex --- version 0.3.7.0 - Please share bugs, suggestions, and feature requests at: - ... - 2. │ └─base::withCallingHandlers(...) - 3. └─spinifex::play_tour_path(tour_path = tpath, data = dat_std, angle = 1) - 4. └─spinifex (local) render_type(frames = tour_df, ...) - 5. ├─plotly::ggplotly(p = gg, tooltip = "tooltip") - 6. └─plotly:::ggplotly.ggplot(p = gg, tooltip = "tooltip") - 7. └─plotly::gg2list(...) - - [ FAIL 3 | WARN 4 | SKIP 0 | PASS 80 ] - Error: Test failures - Execution halted - ``` - -# sport - -
- -* Version: 0.2.1 -* GitHub: https://github.com/gogonzo/sport -* Source code: https://github.com/cran/sport -* Date/Publication: 2024-01-08 23:50:02 UTC -* Number of recursive dependencies: 71 - -Run `revdepcheck::cloud_details(, "sport")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > - > test_check("sport") - Loading required package: sport - [ FAIL 1 | WARN 0 | SKIP 0 | PASS 238 ] - - ══ Failed tests ════════════════════════════════════════════════════════════════ - ── Failure ('test_output.R:30:3'): Scale is labelled 'r' ─────────────────────── - p$labels$y not identical to "r". - target is NULL, current is character - - [ FAIL 1 | WARN 0 | SKIP 0 | PASS 238 ] - Error: Test failures - Execution halted - ``` - -## In both - -* checking data for non-ASCII characters ... NOTE - ``` - Note: found 7504 marked UTF-8 strings - ``` - -# SqueakR - -
- -* Version: 1.3.0 -* GitHub: https://github.com/osimon81/SqueakR -* Source code: https://github.com/cran/SqueakR -* Date/Publication: 2022-06-28 09:20:04 UTC -* Number of recursive dependencies: 145 - -Run `revdepcheck::cloud_details(, "SqueakR")` for more info - -
- -## Newly broken - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘SqueakR.Rmd’ using rmarkdown - ``` - -## In both - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘SqueakR.Rmd’ - ... - $ experimenters : NULL - $ experimental_data: list() - - > my_new_data <- add_timepoint_data(data_path = "../inst/extdata/Example_Mouse_Data.xlsx", - + t1 = 5, t2 = 25) - Adding call features Excel file to workspace... - - When sourcing ‘SqueakR.R’: - Error: `path` does not exist: ‘../inst/extdata/Example_Mouse_Data.xlsx’ - Execution halted - - ‘SqueakR.Rmd’ using ‘UTF-8’... failed - ``` - -* checking installed package size ... NOTE - ``` - installed size is 8.8Mb - sub-directories of 1Mb or more: - doc 8.2Mb - ``` - -# statgenGWAS - -
- -* Version: 1.0.9 -* GitHub: https://github.com/Biometris/statgenGWAS -* Source code: https://github.com/cran/statgenGWAS -* Date/Publication: 2022-10-13 15:30:43 UTC -* Number of recursive dependencies: 71 - -Run `revdepcheck::cloud_details(, "statgenGWAS")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘tinytest.R’ - Running the tests in ‘tests/tinytest.R’ failed. - Complete output: - > - > if ( requireNamespace("tinytest", quietly=TRUE) ){ - + tinytest::test_package("statgenGWAS") - + } - - test_GWAS.R................... 0 tests - test_GWAS.R................... 0 tests - ... - conversion failure on '← 2@3' in 'mbcsToSbcs': dot substituted for <86> - 3: In grid.Call.graphics(C_text, as.graphicsAnnot(x$label), x$x, x$y, : - conversion failure on '← 2@3' in 'mbcsToSbcs': dot substituted for <90> - 4: In grid.Call.graphics(C_text, as.graphicsAnnot(x$label), x$x, x$y, : - conversion failure on '← 2@3' in 'mbcsToSbcs': dot substituted for - 5: In grid.Call.graphics(C_text, as.graphicsAnnot(x$label), x$x, x$y, : - conversion failure on '← 2@3' in 'mbcsToSbcs': dot substituted for <86> - 6: In grid.Call.graphics(C_text, as.graphicsAnnot(x$label), x$x, x$y, : - conversion failure on '← 2@3' in 'mbcsToSbcs': dot substituted for <90> - Execution halted - ``` - -## In both - -* checking C++ specification ... NOTE - ``` - Specified C++11: please drop specification unless essential - ``` - -* checking installed package size ... NOTE - ``` - installed size is 15.2Mb - sub-directories of 1Mb or more: - data 7.0Mb - libs 7.1Mb - ``` - -# surveyexplorer - -
- -* Version: 0.2.0 -* GitHub: NA -* Source code: https://github.com/cran/surveyexplorer -* Date/Publication: 2024-06-07 09:50:02 UTC -* Number of recursive dependencies: 87 - -Run `revdepcheck::cloud_details(, "surveyexplorer")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘surveyexplorer-Ex.R’ failed - The error most likely occurred in: - - > ### Name: multi_freq - > ### Title: Generate an UpSet plot for multiple-choice questions - > ### Aliases: multi_freq - > - > ### ** Examples - > - > - ... - - > - > #Basic Upset plot - > - > #Use `group_by` to partition the question into several groups - > multi_freq(berlinbears, question = dplyr::starts_with('will_eat'), group_by - + = gender) - Error in as.unit(e2) : object is not coercible to a unit - Calls: ... polylineGrob -> is.unit -> unit.c -> Ops.unit -> as.unit - Execution halted - ``` - -# Sysrecon - -
- -* Version: 0.1.3 -* GitHub: NA -* Source code: https://github.com/cran/Sysrecon -* Date/Publication: 2023-02-20 08:50:02 UTC -* Number of recursive dependencies: 61 - -Run `revdepcheck::cloud_details(, "Sysrecon")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘Sysrecon-Ex.R’ failed - The error most likely occurred in: - - > ### Name: Sysrecon - > ### Title: Sysrecon - > ### Aliases: Sysrecon - > - > ### ** Examples - > - > - ... - no non-missing arguments to min; returning Inf - Warning in min(freq[grepl(i, allwords, ignore.case = T)]) : - no non-missing arguments to min; returning Inf - Warning in min(freq[grepl(i, allwords, ignore.case = T)]) : - no non-missing arguments to min; returning Inf - Warning in min(freq[grepl(i, allwords, ignore.case = T)]) : - no non-missing arguments to min; returning Inf - Error in as.unit(value) : object is not coercible to a unit - Calls: Sysrecon ... assemble_guides -> guides_build -> [<- -> [<-.unit -> as.unit - Execution halted - ``` - -## In both - -* checking data for non-ASCII characters ... NOTE - ``` - Note: found 38 marked UTF-8 strings - ``` - -# tabledown - -
- -* Version: 1.0.0 -* GitHub: https://github.com/masiraji/tabledown -* Source code: https://github.com/cran/tabledown -* Date/Publication: 2024-05-02 13:40:03 UTC -* Number of recursive dependencies: 163 - -Run `revdepcheck::cloud_details(, "tabledown")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘tabledown-Ex.R’ failed - The error most likely occurred in: - - > ### Name: ggreliability_plotly - > ### Title: A Function for Creating Item Response Theory based reliability - > ### plot based on plotly. - > ### Aliases: ggreliability_plotly - > - > ### ** Examples - > - ... - Iteration: 17, Log-Lik: -5351.363, Max-Change: 0.00011 - Iteration: 18, Log-Lik: -5351.363, Max-Change: 0.00054 - Iteration: 19, Log-Lik: -5351.363, Max-Change: 0.00012 - Iteration: 20, Log-Lik: -5351.363, Max-Change: 0.00035 - Iteration: 21, Log-Lik: -5351.363, Max-Change: 0.00010 - > - > plot <- ggreliability_plotly(data, model) - Error in pm[[2]] : subscript out of bounds - Calls: ggreliability_plotly -> -> ggplotly.ggplot -> gg2list - Execution halted - ``` - -## In both - -* checking data for non-ASCII characters ... NOTE - ``` - Note: found 551 marked UTF-8 strings - ``` - -# TCIU - -
- -* Version: 1.2.6 -* GitHub: https://github.com/SOCR/TCIU -* Source code: https://github.com/cran/TCIU -* Date/Publication: 2024-05-17 23:40:21 UTC -* Number of recursive dependencies: 163 - -Run `revdepcheck::cloud_details(, "TCIU")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘TCIU-Ex.R’ failed - The error most likely occurred in: - - > ### Name: fmri_image - > ### Title: interactive graph object of the fMRI image - > ### Aliases: fmri_image - > - > ### ** Examples - > - > fmri_generate = fmri_simulate_func(dim_data = c(64, 64, 40), mask = mask) - > fmri_image(fmri_generate$fmri_data, option='manually', voxel_location = c(40,22,33), time = 4) - Error in pm[[2]] : subscript out of bounds - Calls: fmri_image ... add_trace -> add_data -> ggplotly -> ggplotly.ggplot -> gg2list - Execution halted - ``` - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘tciu-LT-kimesurface.Rmd’ - ... - > require(ggplot2) - - > sample_save[[1]] - - > sample_save[[2]] - - When sourcing ‘tciu-LT-kimesurface.R’: - ... - - > fmri_image(fmri_generate$fmri_data, option = "manually", - + voxel_location = c(40, 22, 33), time = 4) - - When sourcing ‘tciu-fMRI-analytics.R’: - Error: subscript out of bounds - Execution halted - - ‘tciu-LT-kimesurface.Rmd’ using ‘UTF-8’... failed - ‘tciu-fMRI-analytics.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - ... - --- re-building ‘tciu-LT-kimesurface.Rmd’ using rmarkdown - - Quitting from lines 159-160 [unnamed-chunk-5] (tciu-LT-kimesurface.Rmd) - Error: processing vignette 'tciu-LT-kimesurface.Rmd' failed with diagnostics: - unused arguments (list(1, 2), list(list("black", 0.727272727272727, 1, "butt", FALSE, TRUE), list("white", "black", 0.727272727272727, 1, TRUE), list("", "plain", "black", 16, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), NULL, NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(4, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 4, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, 90, NULL, c(0, 4, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, - NULL, 1, -90, NULL, c(0, 0, 0, 4), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(3.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 3.2, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 1, NULL, NULL, NULL, c(0, 3.2, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, NULL, c(0, 0, 0, 3.2), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0.5, NULL, - NULL, NULL, c(0, 3.2, 0, 3.2), NULL, TRUE), list("grey20", NULL, NULL, NULL, FALSE, TRUE), NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 4, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 0.75, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, list(), NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, list(NULL, NA, NULL, NULL, TRUE), c(8, 8, 8, 8), 16, NULL, NULL, NULL, 1.2, NULL, NULL, 8, NULL, NULL, NULL, NULL, 0.2, NULL, list(NULL, NULL, NULL, 0.8, NULL, NULL, - NULL, NULL, NULL, NULL, TRUE), NULL, list(NULL, "bold", "black", 14, 0, NULL, NULL, NULL, NULL, NULL, FALSE), NULL, "right", NULL, NULL, NULL, "center", NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, c(0, 0, 0, 0), list(), 16, list("grey92", NA, NULL, NULL, TRUE), list(), 8, NULL, NULL, list("white", NULL, NULL, NULL, FALSE, TRUE), NULL, list(NULL, 0.5, NULL, NULL, FALSE, TRUE), NULL, list(), NULL, list(), FALSE, list(NULL, "white", NULL, NULL, TRUE), list(NULL, NULL, NULL, 1.2, 0.5, 1, NULL, - ... - Quitting from lines 184-185 [unnamed-chunk-5] (tciu-fMRI-analytics.Rmd) - Error: processing vignette 'tciu-fMRI-analytics.Rmd' failed with diagnostics: - subscript out of bounds - --- failed re-building ‘tciu-fMRI-analytics.Rmd’ - - SUMMARY: processing the following files failed: - ‘tciu-LT-kimesurface.Rmd’ ‘tciu-fMRI-analytics.Rmd’ - - Error: Vignette re-building failed. - Execution halted - ``` - -## In both - -* checking installed package size ... NOTE - ``` - installed size is 14.1Mb - sub-directories of 1Mb or more: - data 1.5Mb - doc 12.0Mb - ``` - -# tensorEVD - -
- -* Version: 0.1.3 -* GitHub: https://github.com/MarcooLopez/tensorEVD -* Source code: https://github.com/cran/tensorEVD -* Date/Publication: 2024-05-30 07:10:02 UTC -* Number of recursive dependencies: 61 - -Run `revdepcheck::cloud_details(, "tensorEVD")` for more info - -
- -## Newly broken - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘tensorEVD-documentation.Rmd’ - ... - - > dat0$alpha <- factor(as.character(dat0$alpha)) - - > figure2 <- make_plot(dat0, x = "alpha", y = "Frobenius", - + group = "method", by = "n", facet = "nG", facet2 = "nE", - + facet.type = "grid", .... [TRUNCATED] - - When sourcing ‘tensorEVD-documentation.R’: - Error: attempt to set an attribute on NULL - Execution halted - - ‘tensorEVD-documentation.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - ... - --- re-building ‘tensorEVD-documentation.Rmd’ using rmarkdown - - Quitting from lines 253-265 [unnamed-chunk-6] (tensorEVD-documentation.Rmd) - Error: processing vignette 'tensorEVD-documentation.Rmd' failed with diagnostics: - attempt to set an attribute on NULL - --- failed re-building ‘tensorEVD-documentation.Rmd’ - - SUMMARY: processing the following file failed: - ‘tensorEVD-documentation.Rmd’ - - Error: Vignette re-building failed. - Execution halted - ``` - -# thematic - -
- -* Version: 0.1.5 -* GitHub: https://github.com/rstudio/thematic -* Source code: https://github.com/cran/thematic -* Date/Publication: 2024-02-14 00:20:03 UTC -* Number of recursive dependencies: 106 - -Run `revdepcheck::cloud_details(, "thematic")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘thematic-Ex.R’ failed - The error most likely occurred in: - - > ### Name: sequential_gradient - > ### Title: Control parameters of the sequential colorscale - > ### Aliases: sequential_gradient - > - > ### ** Examples - > - > - > # Gradient from fg to accent - > fg <- sequential_gradient(1, 0) - > thematic_on("black", "white", "salmon", sequential = fg) - > ggplot2::qplot(1:10, 1:10, color = 1:10) - Warning: `qplot()` was deprecated in ggplot2 3.4.0. - Error in adjust_color(user_default$colour, bg, fg, accent) : - Internal error: adjust_color() expects an input of length 1 - Calls: ... -> -> update_defaults -> adjust_color - Execution halted - ``` - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(thematic) - > - > test_check("thematic") - [ FAIL 9 | WARN 1 | SKIP 7 | PASS 27 ] - - ══ Skipped tests (7) ═══════════════════════════════════════════════════════════ - ... - 10. └─base::Map(...) - 11. └─base::mapply(FUN = f, ..., SIMPLIFY = FALSE) - 12. └─thematic (local) ``(dots[[1L]][[1L]], dots[[2L]][[1L]]) - 13. ├─ggplot2::update_geom_defaults(...) - 14. │ └─ggplot2:::update_defaults(geom, "Geom", new, env = parent.frame()) - 15. └─thematic:::adjust_color(user_default$colour, bg, fg, accent) - - [ FAIL 9 | WARN 1 | SKIP 7 | PASS 27 ] - Error: Test failures - Execution halted - ``` - -# tidybayes - -
- -* Version: 3.0.6 -* GitHub: https://github.com/mjskay/tidybayes -* Source code: https://github.com/cran/tidybayes -* Date/Publication: 2023-08-12 23:30:02 UTC -* Number of recursive dependencies: 200 - -Run `revdepcheck::cloud_details(, "tidybayes")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘tidybayes-Ex.R’ failed - The error most likely occurred in: - - > ### Name: compare_levels - > ### Title: Compare the value of draws of some variable from a Bayesian - > ### model for different levels of a factor - > ### Aliases: compare_levels - > ### Keywords: manip - > - > ### ** Examples - ... - 12. │ └─ggplot2 (local) f(l = layers[[i]], d = data[[i]]) - 13. │ └─l$compute_geom_2(d, theme = plot$theme) - 14. │ └─ggplot2 (local) compute_geom_2(..., self = self) - 15. │ └─self$geom$use_defaults(...) - 16. └─base::.handleSimpleError(...) - 17. └─rlang (local) h(simpleError(msg, call)) - 18. └─handlers[[1L]](cnd) - 19. └─cli::cli_abort(...) - 20. └─rlang::abort(...) - Execution halted - ``` - -## In both - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > # This is necessary because some tests fail otherwise; see https://github.com/hadley/testthat/issues/144 - > Sys.setenv("R_TESTS" = "") - > - > library(testthat) - > library(tidybayes) - > - > test_check("tidybayes") - ... - • test.geom_interval/grouped-intervals-h-stat.svg - • test.geom_pointinterval/grouped-pointintervals-h-stat.svg - • test.stat_dist_slabinterval/ccdfintervalh-using-args.svg - • test.stat_eye/one-parameter-horizontal-eye-mode-hdi.svg - • test.stat_eye/one-parameter-horizontal-half-eye.svg - • test.stat_eye/one-parameter-vertical-eye.svg - • test.stat_eye/one-parameter-vertical-halfeye.svg - • test.stat_eye/two-parameter-factor-horizontal-eye-fill.svg - Error: Test failures - Execution halted - ``` - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘tidy-brms.Rmd’ - ... - + ]) %>% median_qi(condition_mean = b_Intercept + r_condition, - + .width = c(0.95, 0 .... [TRUNCATED] - - When sourcing ‘tidy-brms.R’: - Error: Problem while setting up geom aesthetics. - ℹ Error occurred in the 1st layer. - Caused by error in `use_defaults()`: - ... - - When sourcing ‘tidybayes.R’: - Error: error in evaluating the argument 'object' in selecting a method for function 'sampling': object 'ABC_stan' not found - Execution halted - - ‘tidy-brms.Rmd’ using ‘UTF-8’... failed - ‘tidy-posterior.Rmd’ using ‘UTF-8’... failed - ‘tidy-rstanarm.Rmd’ using ‘UTF-8’... failed - ‘tidybayes-residuals.Rmd’ using ‘UTF-8’... failed - ‘tidybayes.Rmd’ using ‘UTF-8’... failed - ``` - -# tidycat - -
- -* Version: 0.1.2 -* GitHub: https://github.com/guyabel/tidycat -* Source code: https://github.com/cran/tidycat -* Date/Publication: 2021-08-02 04:20:01 UTC -* Number of recursive dependencies: 70 - -Run `revdepcheck::cloud_details(, "tidycat")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘tidycat-Ex.R’ failed - The error most likely occurred in: - - > ### Name: tidy_categorical - > ### Title: Expand broom::tidy() Outputs for Categorical Parameter Estimates - > ### Aliases: tidy_categorical - > - > ### ** Examples - > - > # strip ordering in factors (currently ordered factor not supported) - ... - > ggplot(data = d0, - + mapping = aes(x = level, colour = reference, - + y = estimate, ymin = conf.low, ymax = conf.high)) + - + facet_row(facets = vars(variable), scales = "free_x", space = "free") + - + geom_hline(yintercept = 0, linetype = "dashed") + - + geom_pointrange() + - + theme(axis.text.x = element_text(angle = 45, hjust = 1)) - Error in space$x : $ operator is invalid for atomic vectors - Calls: ... -> draw_panels -> -> init_gtable - Execution halted - ``` - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘intro.Rmd’ - ... - - > library(ggforce) - - > ggplot(data = d0, mapping = aes(x = level, y = estimate, - + colour = reference, ymin = conf.low, ymax = conf.high)) + - + facet_col(facets = .... [TRUNCATED] - - When sourcing ‘intro.R’: - Error: $ operator is invalid for atomic vectors - Execution halted - - ‘intro.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘intro.Rmd’ using rmarkdown - ``` - -## In both - -* checking dependencies in R code ... NOTE - ``` - Namespace in Imports field not imported from: ‘tidyr’ - All declared Imports should be used. - ``` - -# tidyCDISC - -
- -* Version: 0.2.1 -* GitHub: https://github.com/Biogen-Inc/tidyCDISC -* Source code: https://github.com/cran/tidyCDISC -* Date/Publication: 2023-03-16 14:20:02 UTC -* Number of recursive dependencies: 140 - -Run `revdepcheck::cloud_details(, "tidyCDISC")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘spelling.R’ - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(tidyCDISC) - > library(shinyjs) - - Attaching package: 'shinyjs' - - ... - 6. ├─plotly::config(...) - 7. │ └─plotly:::modify_list(p$x$config, args) - 8. │ ├─utils::modifyList(x %||% list(), y %||% list(), ...) - 9. │ │ └─base::stopifnot(is.list(x), is.list(val)) - 10. │ └─x %||% list() - 11. └─plotly::layout(...) - - [ FAIL 1 | WARN 1 | SKIP 15 | PASS 91 ] - Error: Test failures - Execution halted - ``` - -## In both - -* checking installed package size ... NOTE - ``` - installed size is 6.5Mb - sub-directories of 1Mb or more: - R 1.5Mb - data 2.0Mb - doc 1.8Mb - ``` - -# tidydr - -
- -* Version: 0.0.5 -* GitHub: https://github.com/YuLab-SMU/tidydr -* Source code: https://github.com/cran/tidydr -* Date/Publication: 2023-03-08 09:20:02 UTC -* Number of recursive dependencies: 74 - -Run `revdepcheck::cloud_details(, "tidydr")` for more info - -
- -## Newly broken - -* checking whether package ‘tidydr’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/tidydr/new/tidydr.Rcheck/00install.out’ for details. - ``` - -## Installation - -### Devel +#
+# +# * Version: 0.5.0 +# * GitHub: https://github.com/jthomasmock/gtExtras +# * Source code: https://github.com/cran/gtExtras +# * Date/Publication: 2023-09-15 22:32:06 UTC +# * Number of recursive dependencies: 105 +# +# Run `revdepcheck::cloud_details(, "gtExtras")` for more info +# +#
+# +# ## Newly broken +# +# * checking tests ... ERROR +# ``` +# Running ‘testthat.R’ +# Running the tests in ‘tests/testthat.R’ failed. +# Complete output: +# > library(testthat) +# > library(gtExtras) +# Loading required package: gt +# +# Attaching package: 'gt' +# +# The following object is masked from 'package:testthat': +# ... +# ══ Failed tests ════════════════════════════════════════════════════════════════ +# ── Failure ('test-gt_plt_bar.R:44:3'): gt_plt_bar svg is created and has specific values ── +# `bar_neg_vals` (`actual`) not equal to c("49.19", "32.79", "16.40", "16.40", "32.79", "49.19") (`expected`). +# +# `actual`: "49.19" "32.79" "16.40" "0.00" "0.00" "0.00" +# `expected`: "49.19" "32.79" "16.40" "16.40" "32.79" "49.19" +# +# [ FAIL 1 | WARN 14 | SKIP 23 | PASS 115 ] +# Error: Test failures +# Execution halted +# ``` +``` + +# HaploCatcher (patchwork) + +# healthyR (plotly) + +# healthyR.ts (plotly) + +# heatmaply (plotly) + +# hermiter (patchwork) + +# hesim (missing labels) + +# hidecan (ggnewscale) + +# HVT (plotly) + +# hypsoLoop (namespace conflict) + +# ICvectorfields (ggnewscale) + +# idopNetwork (patchwork) + +# inferCSN (plotly) + +# insurancerating (patchwork) +# inTextSummaryTable (default access) + +# inventorize (unknown) + +``` +#
+# +# * Version: 1.1.1 +# * GitHub: NA +# * Source code: https://github.com/cran/inventorize +# * Date/Publication: 2022-05-31 22:20:09 UTC +# * Number of recursive dependencies: 71 +# +# Run `revdepcheck::cloud_details(, "inventorize")` for more info +# +#
+# +# ## Newly broken +# +# * checking whether package ‘inventorize’ can be installed ... ERROR +# ``` +# Installation failed. +# See ‘/tmp/workdir/inventorize/new/inventorize.Rcheck/00install.out’ for details. +# ``` +# +# ## Installation +# +# ### Devel +# +# ``` +# * installing *source* package ‘inventorize’ ... +# ** package ‘inventorize’ successfully unpacked and MD5 sums checked +# ** using staged installation +# ** R +# ** byte-compile and prepare package for lazy loading +# Error in pm[[2]] : subscript out of bounds +# Error: unable to load R code in package ‘inventorize’ +# Execution halted +# ERROR: lazy loading failed for package ‘inventorize’ +# * removing ‘/tmp/workdir/inventorize/new/inventorize.Rcheck/inventorize’ +# +# +# ``` +# ### CRAN +# +# ``` +# * installing *source* package ‘inventorize’ ... +# ** package ‘inventorize’ successfully unpacked and MD5 sums checked +# ** using staged installation +# ** R +# ** byte-compile and prepare package for lazy loading +# Warning in qgamma(service_level, alpha, beta) : NaNs produced +# Warning in qgamma(service_level, alpha, beta) : NaNs produced +# ** help +# *** installing help indices +# ** building package indices +# ** testing if installed package can be loaded from temporary location +# ** testing if installed package can be loaded from final location +# ** testing if installed package keeps a record of temporary installation path +# * DONE (inventorize) +# +# +# ``` ``` -* installing *source* package ‘tidydr’ ... -** package ‘tidydr’ successfully unpacked and MD5 sums checked -** using staged installation -** R -** inst -** byte-compile and prepare package for lazy loading -Error in get(x, envir = ns, inherits = FALSE) : - object 'len0_null' not found -Error: unable to load R code in package ‘tidydr’ -Execution halted -ERROR: lazy loading failed for package ‘tidydr’ -* removing ‘/tmp/workdir/tidydr/new/tidydr.Rcheck/tidydr’ +# karel (gganimate) + +# kDGLM (plotly) + +# latentcor (plotly) + +# lcars (device issue) + +# lemon (resolve theme) + +# lfproQC (plotly) + +# LMoFit (saved to disk) + +# manydata (plot slots) + +# MARVEL (ggnewscale) + +# MBNMAdose (cannot reproduce) + +# MBNMAtime (ggdist) + +# MetaNet (ggnewscale) + +# metR (fixed in dev) + +# migraph (missing labels) + +# MiMIR (plotly) +# miRetrieve (plotly) + +# misspi (plotly) + +# mizer (cannot reproduce) + +# mlr3spatiotempcv (patchwork) + +# mlr3viz (patchwork) + +# modeltime.resample (plotly) + +# move (false positive) + +# mtb (missing labels) + +# neatmaps (plotly) + +# NetFACS (false positive) + +# NeuralSens (ggnewscale) + +# NHSRplotthedots (missing labels) + +# NIMAA (plotly) + +# OBIC (patchwork) + +# OmicNavigator (plotly) + +# oncomsm (patchwork) + +# pafr (missing labels) + +# patchwork (patchwork) + +# pathviewr (missing labels) + +# pcutils (patchwork) + +# pdxTrees (gganimate) + +# personalized (plotly) + +# phylepic (ggnewscale) + +# Plasmidprofiler (plotly) + +# platetools (faulty tests) + +# plotDK (missing labels) + +# plotly (plotly) + +# pmartR (unknown) ``` -### CRAN +#
+# +# * Version: 2.4.5 +# * GitHub: https://github.com/pmartR/pmartR +# * Source code: https://github.com/cran/pmartR +# * Date/Publication: 2024-05-21 15:50:02 UTC +# * Number of recursive dependencies: 149 +# +# Run `revdepcheck::cloud_details(, "pmartR")` for more info +# +#
+# +# ## Newly broken +# +# * checking tests ... ERROR +# ``` +# Running ‘testthat.R’ +# Running the tests in ‘tests/testthat.R’ failed. +# Complete output: +# > library(testthat) +# > library(pmartR) +# > +# > test_check("pmartR") +# [ FAIL 1 | WARN 1 | SKIP 11 | PASS 2375 ] +# +# ══ Skipped tests (11) ══════════════════════════════════════════════════════════ +# ... +# • plots/plot-spansres-color-high-color-low.svg +# • plots/plot-spansres.svg +# • plots/plot-statres-anova-volcano.svg +# • plots/plot-statres-anova.svg +# • plots/plot-statres-combined-volcano.svg +# • plots/plot-statres-combined.svg +# • plots/plot-statres-gtest.svg +# • plots/plot-totalcountfilt.svg +# Error: Test failures +# Execution halted +# ``` +# +# ## In both +# +# * checking installed package size ... NOTE +# ``` +# installed size is 10.4Mb +# sub-directories of 1Mb or more: +# R 1.5Mb +# help 1.5Mb +# libs 6.3Mb +# ``` +``` + +# pmxTools (ggdist) + +# posterior (ggdist) + +# PPQplan (plotly) + +# ppseq (plotly) + +# precrec (patchwork) + +# priorsense (ggdist) + +# ProAE (ggnewscale) + +# probably (missing labels) + +# processmapR (plotly) + +# psborrow (missing labels) + +# r2dii.plot (missing labels) + +# Radviz (accessing defaults) + +# rassta (plotly) + +# REddyProc (false positive) + +# redist (patchwork) + +# reReg (length 0 width) + +# reservr (patchwork) + +# rKOMICS (unknown) ``` -* installing *source* package ‘tidydr’ ... -** package ‘tidydr’ successfully unpacked and MD5 sums checked -** using staged installation -** R -** inst -** byte-compile and prepare package for lazy loading -** help -*** installing help indices -** building package indices -** installing vignettes -** testing if installed package can be loaded from temporary location -** testing if installed package can be loaded from final location -** testing if installed package keeps a record of temporary installation path -* DONE (tidydr) +#
+# +# * Version: 1.3 +# * GitHub: NA +# * Source code: https://github.com/cran/rKOMICS +# * Date/Publication: 2023-06-29 22:40:03 UTC +# * Number of recursive dependencies: 128 +# +# Run `revdepcheck::cloud_details(, "rKOMICS")` for more info +# +#
+# +# ## Newly broken +# +# * checking examples ... ERROR +# ``` +# Running examples in ‘rKOMICS-Ex.R’ failed +# The error most likely occurred in: +# +# > ### Name: msc.pca +# > ### Title: Prinicple Component Analysis based on MSC +# > ### Aliases: msc.pca +# > +# > ### ** Examples +# > +# > data(matrices) +# ... +# 11. │ └─base::withCallingHandlers(...) +# 12. └─ggplot2 (local) f(l = layers[[i]], d = data[[i]]) +# 13. └─l$compute_geom_2(d, theme = plot$theme) +# 14. └─ggplot2 (local) compute_geom_2(..., self = self) +# 15. └─self$geom$use_defaults(...) +# 16. └─ggplot2 (local) use_defaults(..., self = self) +# 17. └─ggplot2:::check_aesthetics(new_params, nrow(data)) +# 18. └─cli::cli_abort(...) +# 19. └─rlang::abort(...) +# Execution halted +# ``` +# +# ## In both +# +# * checking installed package size ... NOTE +# ``` +# installed size is 24.8Mb +# sub-directories of 1Mb or more: +# extdata 24.0Mb +# ``` +# +# * checking re-building of vignette outputs ... NOTE +# ``` +# Error(s) in re-building vignettes: +# --- re-building ‘example.Rnw’ using Sweave +# Loading required package: viridisLite +# Warning: Removed 95 rows containing non-finite outside the scale range +# (`stat_boxplot()`). +# Warning: Removed 89 rows containing non-finite outside the scale range +# (`stat_boxplot()`). +# Warning: Removed 149 rows containing non-finite outside the scale range +# (`stat_boxplot()`). +# Warning: Removed 286 rows containing non-finite outside the scale range +# ... +# l.5 \usepackage +# {xcolor}^^M +# ! ==> Fatal error occurred, no output PDF file produced! +# --- failed re-building ‘example.Rnw’ +# +# SUMMARY: processing the following file failed: +# ‘example.Rnw’ +# +# Error: Vignette re-building failed. +# Execution halted +# ``` +``` + +# RKorAPClient (missing labels) + +# RNAseqQC (patchwork) + +# roahd (plotly) +# romic (plotly) +# roptions (plotly) + +# santaR (plot slots) + +# scdtb (missing labels) + +# scoringutils (ggdist) + +# scUtils (missing labels) + +# SCVA (plotly) + +# SDMtune (missing labels) + +# SeaVal (plotly) + +# sgsR (missing labels) + +# SHAPforxgboost (ggforce) + +# SHELF (unknown) + +``` +#
+# +# * Version: 1.10.0 +# * GitHub: https://github.com/OakleyJ/SHELF +# * Source code: https://github.com/cran/SHELF +# * Date/Publication: 2024-05-07 14:20:03 UTC +# * Number of recursive dependencies: 126 +# +# Run `revdepcheck::cloud_details(, "SHELF")` for more info +# +#
+# +# ## Newly broken +# +# * checking re-building of vignette outputs ... NOTE +# ``` +# Error(s) in re-building vignettes: +# --- re-building ‘Dirichlet-elicitation.Rmd’ using rmarkdown +# ``` ``` -# tidysdm - -
- -* Version: 0.9.5 -* GitHub: https://github.com/EvolEcolGroup/tidysdm -* Source code: https://github.com/cran/tidysdm -* Date/Publication: 2024-06-23 19:40:02 UTC -* Number of recursive dependencies: 179 - -Run `revdepcheck::cloud_details(, "tidysdm")` for more info - -
- -## Newly broken - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘a0_tidysdm_overview.Rmd’ - ... - > climate_vars <- names(climate_present) - - > lacerta_thin <- lacerta_thin %>% bind_cols(terra::extract(climate_present, - + lacerta_thin, ID = FALSE)) - - > lacerta_thin %>% plot_pres_vs_bg(class) - - When sourcing ‘a0_tidysdm_overview.R’: - Error: object is not a unit - Execution halted - - ‘a0_tidysdm_overview.Rmd’ using ‘UTF-8’... failed - ‘a1_palaeodata_application.Rmd’ using ‘UTF-8’... OK - ‘a2_tidymodels_additions.Rmd’ using ‘UTF-8’... OK - ‘a3_troubleshooting.Rmd’ using ‘UTF-8’... OK - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘a0_tidysdm_overview.Rmd’ using rmarkdown - ``` - -## In both - -* checking installed package size ... NOTE - ``` - installed size is 5.4Mb - sub-directories of 1Mb or more: - data 2.5Mb - doc 2.0Mb - ``` - -# tidytreatment - -
- -* Version: 0.2.2 -* GitHub: https://github.com/bonStats/tidytreatment -* Source code: https://github.com/cran/tidytreatment -* Date/Publication: 2022-02-21 09:00:07 UTC -* Number of recursive dependencies: 97 - -Run `revdepcheck::cloud_details(, "tidytreatment")` for more info - -
- -## Newly broken - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘use-tidytreatment-BART.Rmd’ - ... - + by = ".row") %>% ggplot() + stat_halfeye(aes(x = z, y = fit)) + - + facet_wrap(~c1, l .... [TRUNCATED] - - When sourcing ‘use-tidytreatment-BART.R’: - Error: Problem while setting up geom aesthetics. - ℹ Error occurred in the 1st layer. - Caused by error in `use_defaults()`: - ! unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, "black", TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), list(NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), 5.5, c(5.5, 5.5, 5.5, 5.5), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.75, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, - NULL, NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, 90, NULL, c(0, 2.75, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL - Execution halted - - ‘use-tidytreatment-BART.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - ... - --- re-building ‘use-tidytreatment-BART.Rmd’ using rmarkdown - - Quitting from lines 163-177 [plot-tidy-bart] (use-tidytreatment-BART.Rmd) - Error: processing vignette 'use-tidytreatment-BART.Rmd' failed with diagnostics: - Problem while setting up geom aesthetics. - ℹ Error occurred in the 1st layer. - Caused by error in `use_defaults()`: - ! unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, "black", TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), list(NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), 5.5, c(5.5, 5.5, 5.5, 5.5), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.75, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, - ... - NULL, NULL, NULL, list(NULL, NA, NULL, NULL, TRUE), NULL, 2, NULL, NULL, NULL, 1.2, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 0.2, NULL, list(NULL, NULL, NULL, 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, NULL, NULL, NULL, TRUE), NULL, "right", NULL, NULL, NULL, "center", NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 0, list(), 2, list("white", NA, NULL, NULL, TRUE), list(NULL, "grey20", NULL, NULL, TRUE), NULL, NULL, NULL, list("grey92", - NULL, NULL, NULL, FALSE, "grey92", TRUE), NULL, list(NULL, 0.5, NULL, NULL, FALSE, NULL, TRUE), NULL, NULL, NULL, NULL, FALSE, list(NULL, "white", NULL, NULL, TRUE), list(NULL, NULL, NULL, 1.2, 0, 1, NULL, NULL, c(0, 0, 5.5, 0), NULL, TRUE), "panel", list(NULL, NULL, NULL, NULL, 0, 1, NULL, NULL, c(0, 0, 5.5, 0), NULL, TRUE), list(NULL, NULL, NULL, 0.8, 1, 1, NULL, NULL, c(5.5, 0, 0, 0), NULL, TRUE), "panel", list(NULL, NULL, NULL, 1.2, 0.5, 0.5, NULL, NULL, NULL, NULL, TRUE), "topleft", - NULL, NULL, list("grey85", "grey20", NULL, NULL, TRUE), NULL, NULL, "inherit", "inside", list(NULL, NULL, "grey10", 0.8, NULL, NULL, NULL, NULL, c(4.4, 4.4, 4.4, 4.4), NULL, TRUE), NULL, NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, NULL, -90, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, NULL, 90, NULL, NULL, NULL, TRUE), NULL, 2.75, 2.75)) - --- failed re-building ‘use-tidytreatment-BART.Rmd’ - - SUMMARY: processing the following file failed: - ‘use-tidytreatment-BART.Rmd’ - - Error: Vignette re-building failed. - Execution halted - ``` - -## In both - -* checking package dependencies ... NOTE - ``` - Package which this enhances but not available for checking: ‘bartMachine’ - ``` - -# timetk - -
- -* Version: 2.9.0 -* GitHub: https://github.com/business-science/timetk -* Source code: https://github.com/cran/timetk -* Date/Publication: 2023-10-31 22:30:02 UTC -* Number of recursive dependencies: 225 - -Run `revdepcheck::cloud_details(, "timetk")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > # This file is part of the standard setup for testthat. - > # It is recommended that you do not modify it. - > # - > # Where should you do additional test configuration? - > # Learn more about the roles of various files in: - > # * https://r-pkgs.org/testing-design.html#sec-tests-files-overview - > # * https://testthat.r-lib.org/articles/special-files.html - ... - 7. └─timetk:::plot_time_series.grouped_df(...) - 8. ├─timetk::plot_time_series(...) - 9. └─timetk:::plot_time_series.data.frame(...) - 10. ├─plotly::ggplotly(g, dynamicTicks = TRUE) - 11. └─plotly:::ggplotly.ggplot(g, dynamicTicks = TRUE) - 12. └─plotly::gg2list(...) - - [ FAIL 1 | WARN 0 | SKIP 0 | PASS 406 ] - Error: Test failures - Execution halted - ``` - -## In both - -* checking data for non-ASCII characters ... NOTE - ``` - Note: found 2750 marked UTF-8 strings - ``` - -# tinyarray - -
- -* Version: 2.4.2 -* GitHub: https://github.com/xjsun1221/tinyarray -* Source code: https://github.com/cran/tinyarray -* Date/Publication: 2024-06-13 14:20:02 UTC -* Number of recursive dependencies: 244 - -Run `revdepcheck::cloud_details(, "tinyarray")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘tinyarray-Ex.R’ failed - The error most likely occurred in: - - > ### Name: exp_surv - > ### Title: exp_surv - > ### Aliases: exp_surv - > - > ### ** Examples - > - > tmp = exp_surv(exprSet_hub1,meta1) - > patchwork::wrap_plots(tmp)+patchwork::plot_layout(guides = "collect") - Error in identicalUnits(x) : object is not a unit - Calls: ... assemble_guides -> guides_build -> unit.c -> identicalUnits - Execution halted - ``` - -# tornado - -
- -* Version: 0.1.3 -* GitHub: https://github.com/bertcarnell/tornado -* Source code: https://github.com/cran/tornado -* Date/Publication: 2024-01-21 17:30:02 UTC -* Number of recursive dependencies: 114 - -Run `revdepcheck::cloud_details(, "tornado")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘tornado-Ex.R’ failed - The error most likely occurred in: - - > ### Name: plot.tornado_plot - > ### Title: Plot a Tornado Plot object - > ### Aliases: plot.tornado_plot - > - > ### ** Examples - > - > gtest <- lm(mpg ~ cyl*wt*hp, data = mtcars) - ... - 13. │ └─base::withCallingHandlers(...) - 14. └─ggplot2 (local) f(l = layers[[i]], d = data[[i]]) - 15. └─l$compute_geom_2(d, theme = plot$theme) - 16. └─ggplot2 (local) compute_geom_2(..., self = self) - 17. └─self$geom$use_defaults(...) - 18. └─ggplot2 (local) use_defaults(..., self = self) - 19. └─ggplot2:::check_aesthetics(new_params, nrow(data)) - 20. └─cli::cli_abort(...) - 21. └─rlang::abort(...) - Execution halted - ``` - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > if (require(testthat)) - + { - + library(tornado) - + - + test_check("tornado") - + } - Loading required package: testthat - ... - ...)) - })(position = "identity", stat = "identity", width = NULL)`: Problem while setting up geom aesthetics. - ℹ Error occurred in the 1st layer. - Caused by error in `check_aesthetics()`: - ! Aesthetics must be either length 1 or the same as the data (20). - ✖ Fix the following mappings: `width`. - - [ FAIL 14 | WARN 0 | SKIP 0 | PASS 101 ] - Error: Test failures - Execution halted - ``` - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘tornadoVignette.Rmd’ - ... - + .... [TRUNCATED] - Loading required package: lattice - - When sourcing ‘tornadoVignette.R’: - Error: Problem while setting up geom aesthetics. - ℹ Error occurred in the 1st layer. - Caused by error in `check_aesthetics()`: - ! Aesthetics must be either length 1 or the same as the data (20). - ✖ Fix the following mappings: `width`. - Execution halted - - ‘tornadoVignette.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘tornadoVignette.Rmd’ using rmarkdown - ``` - -# TOSTER - -
- -* Version: 0.8.3 -* GitHub: NA -* Source code: https://github.com/cran/TOSTER -* Date/Publication: 2024-05-08 16:40:02 UTC -* Number of recursive dependencies: 106 - -Run `revdepcheck::cloud_details(, "TOSTER")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘TOSTER-Ex.R’ failed - The error most likely occurred in: - - > ### Name: dataTOSTone - > ### Title: TOST One Sample T-Test - > ### Aliases: dataTOSTone - > - > ### ** Examples - > - > library("TOSTER") - ... - N Mean Median SD SE - ───────────────────────────────────────────────────────────────────────── - Sepal.Width 150 3.057333 3.000000 0.4358663 0.03558833 - ───────────────────────────────────────────────────────────────────────── - - Error in use_defaults(..., self = self) : - unused argument (theme = list(list("black", 0.727272727272727, 1, "butt", FALSE, "black", TRUE), list("white", "black", 0.727272727272727, 1, TRUE), list("", "plain", "black", 16, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), list(NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list("black", "white", "#3366FF", 0.727272727272727, 1.45454545454545, "", 5.62335685623357, 2.18181818181818, 19, TRUE), 8, c(8, 8, 8, 8), NULL, NULL, list(NULL, NULL, "#333333", NULL, NULL, NULL, NULL, NULL, - c(10, 0, 0, 0), NULL, FALSE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 4, 0), NULL, TRUE), NULL, list(NULL, NULL, "#333333", NULL, NULL, NULL, 90, NULL, c(0, 10, 0, 0), NULL, FALSE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 4), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, "#333333", NULL, NULL, NULL, NULL, NULL, c(5, 0, 0, 0), NULL, FALSE), list(NULL, NULL, NULL, NULL, NUL - Calls: ... -> -> -> - Execution halted - ``` - -* checking tests ... ERROR - ``` - Running ‘spelling.R’ - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(TOSTER) - - Attaching package: 'TOSTER' - - The following object is masked from 'package:testthat': - ... - 26. └─base::Map(...) - 27. └─base::mapply(FUN = f, ..., SIMPLIFY = FALSE) - 28. └─ggplot2 (local) ``(layer = dots[[1L]][[1L]], df = dots[[2L]][[1L]]) - 29. └─layer$compute_geom_2(key, single_params, theme) - 30. └─ggplot2 (local) compute_geom_2(..., self = self) - 31. └─self$geom$use_defaults(...) - - [ FAIL 8 | WARN 0 | SKIP 0 | PASS 1034 ] - Error: Test failures - Execution halted - ``` - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘IntroTOSTt.Rmd’ - ... - mean of x mean of y - 0.75 2.33 - - - > plot(res1, type = "cd") - - When sourcing ‘IntroTOSTt.R’: - ... - Error: unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, "black", TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), list(NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), 5.5, c(5.5, 5.5, 5.5, 5.5), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(7, 0, 0, 0), NULL, FALSE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, - NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, 90, NULL, c(0, 7, 0, 0), NULL, FALSE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, "bold", NULL, 11, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, FALSE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(), NULL, list(NULL, N - Execution halted - - ‘IntroTOSTt.Rmd’ using ‘UTF-8’... failed - ‘IntroductionToTOSTER.Rmd’ using ‘UTF-8’... OK - ‘SMD_calcs.Rmd’ using ‘UTF-8’... OK - ‘correlations.Rmd’ using ‘UTF-8’... OK - ‘robustTOST.Rmd’ using ‘UTF-8’... failed - ‘the_ftestTOSTER.Rmd’ using ‘UTF-8’... OK - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘IntroTOSTt.Rmd’ using rmarkdown - ``` - -# TreatmentPatterns - -
- -* Version: 2.6.7 -* GitHub: https://github.com/darwin-eu/TreatmentPatterns -* Source code: https://github.com/cran/TreatmentPatterns -* Date/Publication: 2024-05-24 08:30:32 UTC -* Number of recursive dependencies: 142 - -Run `revdepcheck::cloud_details(, "TreatmentPatterns")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > # This file is part of the standard setup for testthat. - > # It is recommended that you do not modify it. - > # - > # Where should you do additional test configuration? - > # Learn more about the roles of various files in: - > # * https://r-pkgs.org/tests.html - > # * https://testthat.r-lib.org/reference/test_package.html#special-files - ... - 22. ├─testthat::expect_s3_class(output$charAgePlot$html, "html") at test-CharacterizationPlots.R:47:9 - 23. │ └─testthat::quasi_label(enquo(object), arg = "object") - 24. │ └─rlang::eval_bare(expr, quo_get_env(quo)) - 25. ├─output$charAgePlot - 26. └─shiny:::`$.shinyoutput`(output, charAgePlot) - 27. └─.subset2(x, "impl")$getOutput(name) - - [ FAIL 1 | WARN 0 | SKIP 21 | PASS 134 ] - Error: Test failures - Execution halted - ``` - -# trelliscopejs - -
- -* Version: 0.2.6 -* GitHub: https://github.com/hafen/trelliscopejs -* Source code: https://github.com/cran/trelliscopejs -* Date/Publication: 2021-02-01 08:00:02 UTC -* Number of recursive dependencies: 106 - -Run `revdepcheck::cloud_details(, "trelliscopejs")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(trelliscopejs) - > - > test_check("trelliscopejs") - [ FAIL 1 | WARN 2 | SKIP 0 | PASS 0 ] - - ══ Failed tests ════════════════════════════════════════════════════════════════ - ... - 4. └─base::lapply(...) - 5. └─trelliscopejs (local) FUN(X[[i]], ...) - 6. ├─base::do.call(plotly::ggplotly, c(list(p = q), plotly_args)) - 7. ├─plotly (local) ``(p = ``) - 8. └─plotly:::ggplotly.ggplot(p = ``) - 9. └─plotly::gg2list(...) - - [ FAIL 1 | WARN 2 | SKIP 0 | PASS 0 ] - Error: Test failures - Execution halted - ``` - -# tricolore - -
- -* Version: 1.2.4 -* GitHub: https://github.com/jschoeley/tricolore -* Source code: https://github.com/cran/tricolore -* Date/Publication: 2024-05-15 15:00:02 UTC -* Number of recursive dependencies: 108 - -Run `revdepcheck::cloud_details(, "tricolore")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘tricolore-Ex.R’ failed - The error most likely occurred in: - - > ### Name: ColorKeySextant - > ### Title: Sextant Scheme Legend - > ### Aliases: ColorKeySextant - > ### Keywords: internal - > - > ### ** Examples - > - ... - 3. ├─ggtern::ggplot_build(x) - 4. └─ggtern:::ggplot_build.ggplot(x) - 5. └─ggtern:::layers_add_or_remove_mask(plot) - 6. └─ggint$plot_theme(plot) - 7. └─ggplot2:::validate_theme(theme) - 8. └─base::mapply(...) - 9. └─ggplot2 (local) ``(...) - 10. └─cli::cli_abort(...) - 11. └─rlang::abort(...) - Execution halted - ``` - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘choropleth_maps_with_tricolore.Rmd’ - ... - - > plot_educ <- ggplot(euro_example) + geom_sf(aes(fill = rgb, - + geometry = geometry), size = 0.1) + scale_fill_identity() - - > plot_educ - - When sourcing ‘choropleth_maps_with_tricolore.R’: - Error: The `tern.axis.ticks.length.major` theme element must be a - object. - Execution halted - - ‘choropleth_maps_with_tricolore.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - ... - --- re-building ‘choropleth_maps_with_tricolore.Rmd’ using rmarkdown - - Quitting from lines 61-72 [unnamed-chunk-4] (choropleth_maps_with_tricolore.Rmd) - Error: processing vignette 'choropleth_maps_with_tricolore.Rmd' failed with diagnostics: - The `tern.axis.ticks.length.major` theme element must be a - object. - --- failed re-building ‘choropleth_maps_with_tricolore.Rmd’ - - SUMMARY: processing the following file failed: - ‘choropleth_maps_with_tricolore.Rmd’ - - Error: Vignette re-building failed. - Execution halted - ``` - -## In both - -* checking data for non-ASCII characters ... NOTE - ``` - Note: found 2 marked UTF-8 strings - ``` - -# triptych - -
- -* Version: 0.1.3 -* GitHub: https://github.com/aijordan/triptych -* Source code: https://github.com/cran/triptych -* Date/Publication: 2024-06-13 15:50:02 UTC -* Number of recursive dependencies: 64 - -Run `revdepcheck::cloud_details(, "triptych")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘triptych-Ex.R’ failed - The error most likely occurred in: - - > ### Name: plot.triptych - > ### Title: Plot methods for the triptych classes - > ### Aliases: plot.triptych autoplot.triptych plot.triptych_murphy - > ### autoplot.triptych_murphy plot.triptych_reliability - > ### autoplot.triptych_reliability plot.triptych_roc autoplot.triptych_roc - > ### plot.triptych_mcbdsc autoplot.triptych_mcbdsc - > - > ### ** Examples - > - > data(ex_binary, package = "triptych") - > tr <- triptych(ex_binary) - > - > dplyr::slice(tr, 1, 3, 6, 9) |> autoplot() - Error in identicalUnits(x) : object is not a unit - Calls: ... assemble_guides -> guides_build -> unit.c -> identicalUnits - Execution halted - ``` - -# tsnet - -
- -* Version: 0.1.0 -* GitHub: https://github.com/bsiepe/tsnet -* Source code: https://github.com/cran/tsnet -* Date/Publication: 2024-02-28 11:30:02 UTC -* Number of recursive dependencies: 77 - -Run `revdepcheck::cloud_details(, "tsnet")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > # This file is part of the standard setup for testthat. - > # It is recommended that you do not modify it. - > # - > # Where should you do additional test configuration? - > # Learn more about the roles of various files in: - > # * https://r-pkgs.org/tests.html - > # * https://testthat.r-lib.org/reference/test_package.html#special-files - ... - unused argument (theme = list(list("black", 0.5, 1, "butt", FALSE, "black", TRUE), list("white", "black", 0.5, 1, TRUE), list("", "plain", "black", 11, 0.5, 0.5, 0, 0.9, c(0, 0, 0, 0), FALSE, TRUE), list(NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list("black", "white", "#3366FF", 0.5, 1, "", 3.86605783866058, 1.5, 19, TRUE), 5.5, c(5.5, 5.5, 5.5, 5.5), NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(7, 0, 0, 0), NULL, FALSE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, - NULL, c(0, 0, 2.75, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, 90, NULL, c(0, 7, 0, 0), NULL, FALSE), NULL, list(NULL, NULL, NULL, NULL, NULL, 1, -90, NULL, c(0, 0, 0, 2.75), NULL, TRUE), list(NULL, NULL, "grey30", 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 1, NULL, NULL, c(2.2, 0, 0, 0), NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, 0, NULL, NULL, c(0, 0, 2.2, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 1, NULL, NULL, NULL, - c(0, 2.2, 0, 0), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, NULL, c(0, 0, 0, 2.2), NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0.5, NULL, NULL, NULL, c(0, 2.2, 0, 2.2), NULL, TRUE), list("grey70", 0.5, NULL, NULL, FALSE, "grey70", TRUE), NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 0.5, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 0.75, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, list(), list("gray70", 0.5, NULL, NULL, FALSE, - "gray70", FALSE), NULL, NULL, list("gray70", 0.5, NULL, NULL, FALSE, "gray70", FALSE), NULL, NULL, NULL, NULL, list(NULL, NA, NULL, NULL, TRUE), NULL, 2, NULL, NULL, NULL, 1.2, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 0.2, NULL, list(NULL, NULL, NULL, 0.8, NULL, NULL, NULL, NULL, NULL, NULL, TRUE), NULL, list(NULL, NULL, NULL, NULL, 0, NULL, NULL, NULL, NULL, NULL, TRUE), NULL, "right", NULL, NULL, NULL, "center", NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, 0, list(), 2, list("white", NA, - NULL, NULL, TRUE), list(), NULL, NULL, NULL, list("grey87", NULL, NULL, NULL, FALSE, "grey87", TRUE), list(), list(), NULL, NULL, NULL, NULL, FALSE, list(NULL, "white", NULL, NULL, TRUE), list(NULL, NULL, NULL, 1.2, 0, 1, NULL, NULL, c(0, 0, 5.5, 0), NULL, TRUE), "panel", list(NULL, NULL, NULL, NULL, 0, 1, NULL, NULL, c(0, 0, 5.5, 0), NULL, TRUE), list(NULL, NULL, NULL, 0.8, 1, 1, NULL, NULL, c(5.5, 0, 0, 0), NULL, TRUE), "panel", list(NULL, NULL, NULL, 1.2, 0.5, 0.5, NULL, NULL, NULL, NULL, - TRUE), "topleft", NULL, NULL, list("gray90", NA, NULL, NULL, FALSE), NULL, NULL, "inherit", "inside", list(NULL, NULL, "black", 0.8, NULL, NULL, NULL, NULL, c(6, 6, 6, 6), NULL, FALSE), NULL, NULL, NULL, list(NULL, NULL, NULL, NULL, NULL, NULL, -90, NULL, NULL, NULL, TRUE), list(NULL, NULL, NULL, NULL, NULL, NULL, 90, NULL, NULL, NULL, TRUE), NULL, 2.75, 2.75)) - - [ FAIL 1 | WARN 14 | SKIP 0 | PASS 108 ] - Error: Test failures - Execution halted - ``` - -## In both - -* checking installed package size ... NOTE - ``` - installed size is 163.0Mb - sub-directories of 1Mb or more: - libs 162.0Mb - ``` - -* checking for GNU extensions in Makefiles ... NOTE - ``` - GNU make is a SystemRequirements. - ``` - -# umiAnalyzer - -
- -* Version: 1.0.0 -* GitHub: https://github.com/sfilges/umiAnalyzer -* Source code: https://github.com/cran/umiAnalyzer -* Date/Publication: 2021-11-25 08:40:02 UTC -* Number of recursive dependencies: 116 - -Run `revdepcheck::cloud_details(, "umiAnalyzer")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘umiAnalyzer-Ex.R’ failed - The error most likely occurred in: - - > ### Name: AmpliconPlot - > ### Title: Generate Amplicon plots - > ### Aliases: AmpliconPlot - > - > ### ** Examples - > - > library(umiAnalyzer) - ... - > - > main = system.file('extdata', package = 'umiAnalyzer') - > samples <- list.dirs(path = main, full.names = FALSE, recursive = FALSE) - > simsen <- createUmiExperiment(experimentName = 'example',mainDir = main,sampleNames = samples) - > simsen <- filterUmiObject(simsen) - > - > amplicon_plot <- AmpliconPlot(simsen) - Error in pm[[2]] : subscript out of bounds - Calls: AmpliconPlot -> -> ggplotly.ggplot -> gg2list - Execution halted - ``` - -# valr - -
- -* Version: 0.8.1 -* GitHub: https://github.com/rnabioco/valr -* Source code: https://github.com/cran/valr -* Date/Publication: 2024-04-22 18:30:03 UTC -* Number of recursive dependencies: 175 - -Run `revdepcheck::cloud_details(, "valr")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > # This file is part of the standard setup for testthat. - > # It is recommended that you do not modify it. - > # - > # Where should you do additional test configuration? - > # Learn more about the roles of various files in: - > # * https://r-pkgs.org/tests.html - > # * https://testthat.r-lib.org/reference/test_package.html#special-files - ... - ══ Failed tests ════════════════════════════════════════════════════════════════ - ── Failure ('test_glyph.r:13:3'): glyph labels are applied ───────────────────── - res$labels$label (`actual`) not equal to "id" (`expected`). - - `actual` is NULL - `expected` is a character vector ('id') - - [ FAIL 1 | WARN 0 | SKIP 4 | PASS 479 ] - Error: Test failures - Execution halted - ``` - -## In both - -* checking installed package size ... NOTE - ``` - installed size is 15.1Mb - sub-directories of 1Mb or more: - libs 13.9Mb - ``` - -# vivaldi - -
- -* Version: 1.0.1 -* GitHub: https://github.com/GreshamLab/vivaldi -* Source code: https://github.com/cran/vivaldi -* Date/Publication: 2023-03-21 20:10:02 UTC -* Number of recursive dependencies: 102 - -Run `revdepcheck::cloud_details(, "vivaldi")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘vivaldi-Ex.R’ failed - The error most likely occurred in: - - > ### Name: snv_location - > ### Title: snv_location - > ### Aliases: snv_location - > - > ### ** Examples - > - > # Example 1: - ... - 6 m2 PB1 234 G A minor 0.010 0.990 - 7 m2 PB1 266 G A minor 0.022 0.978 - 8 m2 PB2 199 A G minor 0.043 0.957 - 9 m2 PB2 88 G A major 0.055 0.945 - 10 m2 PB2 180 C T minor 0.011 0.989 - > - > snv_location(df) - Error in pm[[2]] : subscript out of bounds - Calls: snv_location -> -> ggplotly.ggplot -> gg2list - Execution halted - ``` - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > # This file is part of the standard setup for testthat. - > # It is recommended that you do not modify it. - > # - > # Where should you do additional test configuration? - > # Learn more about the roles of various files in: - > # * https://r-pkgs.org/tests.html - > # * https://testthat.r-lib.org/reference/test_package.html#special-files - ... - - ══ Failed tests ════════════════════════════════════════════════════════════════ - ── Failure ('test-snv_location.R:13:3'): expect output ───────────────────────── - Expected `snv_location(df)` to run without any errors. - i Actually got a with text: - subscript out of bounds - - [ FAIL 1 | WARN 2 | SKIP 0 | PASS 29 ] - Error: Test failures - Execution halted - ``` - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘vignette.Rmd’ - ... - |a_3_fb | 96| - |a_3_iv | 94| - |b_1_fb | 82| - |b_1_iv | 91| - - > snv_location(DF_filt_SNVs) - - When sourcing ‘vignette.R’: - Error: subscript out of bounds - Execution halted - - ‘vignette.Rmd’ using ‘UTF-8’... failed - ``` - -* checking re-building of vignette outputs ... NOTE - ``` - Error(s) in re-building vignettes: - --- re-building ‘vignette.Rmd’ using rmarkdown - ``` - -## In both - -* checking installed package size ... NOTE - ``` - installed size is 6.8Mb - sub-directories of 1Mb or more: - doc 5.4Mb - extdata 1.1Mb - ``` - -# vivid - -
- -* Version: 0.2.8 -* GitHub: NA -* Source code: https://github.com/cran/vivid -* Date/Publication: 2023-07-10 22:20:02 UTC -* Number of recursive dependencies: 220 - -Run `revdepcheck::cloud_details(, "vivid")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘vivid-Ex.R’ failed - The error most likely occurred in: - - > ### Name: vivi - > ### Title: vivi - > ### Aliases: vivi - > - > ### ** Examples - > - > - > aq <- na.omit(airquality) - > f <- lm(Ozone ~ ., data = aq) - > m <- vivi(fit = f, data = aq, response = "Ozone") # as expected all interactions are zero - Agnostic variable importance method used. - Calculating interactions... - > viviHeatmap(m) - Error in names(labels) <- `*vtmp*` : attempt to set an attribute on NULL - Calls: viviHeatmap ... ggplot_add -> ggplot_add.new_aes -> bump_aes_labels - Execution halted - ``` - -# vvshiny - -
- -* Version: 0.1.1 -* GitHub: NA -* Source code: https://github.com/cran/vvshiny -* Date/Publication: 2023-07-19 15:30:02 UTC -* Number of recursive dependencies: 135 - -Run `revdepcheck::cloud_details(, "vvshiny")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > # This file is part of the standard setup for testthat. - > # It is recommended that you do not modify it. - > # - > # Where should you do additional test configuration? - > # Learn more about the roles of various files in: - > # * https://r-pkgs.org/testing-design.html#sec-tests-files-overview - > # * https://testthat.r-lib.org/articles/special-files.html - ... - 1. ├─vvshiny::ggplotly_with_legend(p, color = "grp", mapping_table = list(grp = "Group")) at test-ggplotly_with_legend.R:15:3 - 2. │ ├─plotly::ggplotly(plot) %>% ... - 3. │ ├─plotly::ggplotly(plot) - 4. │ └─plotly:::ggplotly.ggplot(plot) - 5. │ └─plotly::gg2list(...) - 6. └─plotly::layout(...) - - [ FAIL 1 | WARN 2 | SKIP 0 | PASS 60 ] - Error: Test failures - Execution halted - ``` - -# wilson - -
- -* Version: 2.4.2 -* GitHub: https://github.com/loosolab/wilson -* Source code: https://github.com/cran/wilson -* Date/Publication: 2021-04-19 09:40:02 UTC -* Number of recursive dependencies: 203 - -Run `revdepcheck::cloud_details(, "wilson")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(wilson) - - Attaching package: 'wilson' - - The following object is masked from 'package:stats': - - ... - Backtrace: - ▆ - 1. └─wilson::create_geneview(...) at test-interactive-plots.R:21:3 - 2. ├─plotly::ggplotly(...) - 3. └─plotly:::ggplotly.ggplot(...) - 4. └─plotly::gg2list(...) - - [ FAIL 3 | WARN 11 | SKIP 1 | PASS 74 ] - Error: Test failures - Execution halted - ``` - -# xaringanthemer - -
- -* Version: 0.4.2 -* GitHub: https://github.com/gadenbuie/xaringanthemer -* Source code: https://github.com/cran/xaringanthemer -* Date/Publication: 2022-08-20 18:40:02 UTC -* Number of recursive dependencies: 75 - -Run `revdepcheck::cloud_details(, "xaringanthemer")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(xaringanthemer) - > - > test_check("xaringanthemer") - [ FAIL 1 | WARN 18 | SKIP 1 | PASS 308 ] - - ══ Skipped tests (1) ═══════════════════════════════════════════════════════════ - ... - ══ Failed tests ════════════════════════════════════════════════════════════════ - ── Failure ('test-ggplot2.R:267:3'): theme_xaringan_restore_defaults() restores defaults ── - res$after_restore$line_colour (`actual`) not equal to res$original$colour (`expected`). - - `actual` is a character vector ('#0088ff') - `expected` is an S3 object of class , a call - - [ FAIL 1 | WARN 18 | SKIP 1 | PASS 308 ] - Error: Test failures - Execution halted - ``` - -## In both - -* checking running R code from vignettes ... ERROR - ``` - Errors in running code in vignettes: - when running code in ‘xaringanthemer.Rmd’ - ... - Warning in file(con, "r") : - cannot open file './../man/fragments/_quick-intro.Rmd': No such file or directory - - Quitting from lines 43-43 [unnamed-chunk-2] (xaringanthemer.Rmd) - - When tangling ‘xaringanthemer.Rmd’: - Error: cannot open the connection - Execution halted - - ‘ggplot2-themes.Rmd’ using ‘UTF-8’... OK - ‘template-variables.Rmd’ using ‘UTF-8’... OK - ‘xaringanthemer.Rmd’ using ‘UTF-8’... failed - ``` - -# yamlet - -
- -* Version: 1.0.3 -* GitHub: https://github.com/bergsmat/yamlet -* Source code: https://github.com/cran/yamlet -* Date/Publication: 2024-03-29 13:30:02 UTC -* Number of recursive dependencies: 103 - -Run `revdepcheck::cloud_details(, "yamlet")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘yamlet-Ex.R’ failed - The error most likely occurred in: - - > ### Name: ggplot_add.ggplot_isometric - > ### Title: Add Isometry to Plot Object - > ### Aliases: ggplot_add.ggplot_isometric - > ### Keywords: internal - > - > ### ** Examples - > - ... - ismtrc> library(magrittr) - - ismtrc> library(ggplot2) - - ismtrc> data.frame(x = 1:5, y = 3:7) %>% - ismtrc+ ggplot(aes(x, y)) + geom_point() + isometric() - Error in ggplot_add.ggplot_isometric(object, p, objectname) : - "x" %in% names(plot$labels) is not TRUE - Calls: example ... ggplot_add -> ggplot_add.ggplot_isometric -> stopifnot - Execution halted - ``` - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Complete output: - > library(testthat) - > library(yamlet) - - Attaching package: 'yamlet' - - The following object is masked from 'package:stats': - - ... - ══ Skipped tests (2) ═══════════════════════════════════════════════════════════ - • empty test (2): 'test-yamlet.R:1346:1', 'test-yamlet.R:1351:1' - - ══ Failed tests ════════════════════════════════════════════════════════════════ - ── Failure ('test-yamlet.R:843:1'): ggplot.resolved is stable ────────────────── - `print(x %>% ggplot(map) + geom_point())` did not produce any warnings. - - [ FAIL 1 | WARN 0 | SKIP 2 | PASS 516 ] - Error: Test failures - Execution halted - ``` + +# shinipsum (plot slots) + +# SimNPH (missing labels) + +# smallsets (patchwork) + +# spbal (empty sf) + +# spinifex (plotly) + +# sport (missing labels) + +# SqueakR (false positive) + +# statgenGWAS (device issue) + +# surveyexplorer (ggupset) + +# Sysrecon (patchwork) + +# tabledown (plotly) + +# TCIU (plotly) + +# tensorEVD (ggnewscale) + +# thematic (thematic) + +# tidybayes (ggdist) + +# tidycat (ggforce) + +# tidyCDISC (plotly) + +# tidydr (uses internals) + +# tidysdm (patchwork) + +# tidytreatment (ggdist) + +# timetk (plotly) + +# tinyarray (patchwork) + +# tornado (length 0 width) + +# TOSTER (ggdist) + +# TreatmentPatterns (plotly) + +# trelliscopejs (plotly) + +# tricolore (ggtern) + +# triptych (patchwork) + +# tsnet (ggdist) + +# umiAnalyzer (plotly) + +# valr (missing labels) + +# vivaldi (plotly) + +# vivid (ggnewscale) + +# vvshiny (plotly) + +# wilson (plotly) + +# xaringanthemer (default access) + +# yamlet (missing labels) From b73f1d2d791ee7ca91046e4ebbc8b1ca0e476732 Mon Sep 17 00:00:00 2001 From: Teun van den Brand Date: Tue, 20 Aug 2024 09:41:08 +0200 Subject: [PATCH 36/41] add `linetype` to `element_geom()` --- R/theme-defaults.R | 2 ++ R/theme-elements.R | 10 +++++++--- man/element.Rd | 1 + 3 files changed, 10 insertions(+), 3 deletions(-) diff --git a/R/theme-defaults.R b/R/theme-defaults.R index ba2f5083c7..3ed29f7b5c 100644 --- a/R/theme-defaults.R +++ b/R/theme-defaults.R @@ -146,6 +146,7 @@ theme_grey <- function(base_size = 11, base_family = "", geom = element_geom( ink = "black", paper = "white", accent = "#3366FF", thin = base_line_size, thick = base_line_size * 2, + linetype = 1L, family = base_family, fontsize = base_size, pointsize = (base_size / 11) * 1.5, pointshape = 19 ), @@ -585,6 +586,7 @@ theme_test <- function(base_size = 11, base_family = "", ink = "black", paper = "white", accent = "#3366FF", thin = base_line_size, thick = base_line_size * 2, family = base_family, fontsize = base_size, + linetype = 1L, pointsize = (base_size / 11) * 1.5, pointshape = 19 ), diff --git a/R/theme-elements.R b/R/theme-elements.R index 54e630b345..aaa72fc320 100644 --- a/R/theme-elements.R +++ b/R/theme-elements.R @@ -161,6 +161,10 @@ element_text <- function(family = NULL, face = NULL, colour = NULL, #' @param paper Background colour. #' @param accent Accent colour. #' @param thin,thick Linewidth for thin and thick lines in mm. +#' @param linetype Line type. An integer (0:8), a name (blank, solid, +#' dashed, dotted, dotdash, longdash, twodash), or a string with +#' an even number (up to eight) of hexadecimal digits which give the +#' lengths in consecutive positions in the string. #' @param pointsize Size for points in mm. #' @param pointshape Shape for points (1-25). #' @export @@ -169,7 +173,7 @@ element_geom <- function( # colours ink = NULL, paper = NULL, accent = NULL, # linewidth - thin = NULL, thick = NULL, + thin = NULL, thick = NULL, linetype = NULL, # text family = NULL, fontsize = NULL, # points @@ -185,7 +189,7 @@ element_geom <- function( ink = ink, paper = paper, accent = accent, - thin = thin, thick = thick, + thin = thin, thick = thick, linetype = linetype, family = family, fontsize = fontsize, pointsize = pointsize, pointshape = pointshape ), @@ -195,7 +199,7 @@ element_geom <- function( .default_geom_element <- element_geom( ink = "black", paper = "white", accent = "#3366FF", - thin = 0.5, thick = 2, + thin = 0.5, thick = 2, linetype = 1L, family = "", fontsize = 11, pointsize = 1.5, pointshape = 19 ) diff --git a/man/element.Rd b/man/element.Rd index d1d3b4895e..d3e963b3a7 100644 --- a/man/element.Rd +++ b/man/element.Rd @@ -55,6 +55,7 @@ element_geom( accent = NULL, thin = NULL, thick = NULL, + linetype = NULL, family = NULL, fontsize = NULL, pointsize = NULL, From c511902c104c030cdc3f4289f693e6e067b82056 Mon Sep 17 00:00:00 2001 From: Teun van den Brand Date: Tue, 20 Aug 2024 10:12:17 +0200 Subject: [PATCH 37/41] `geom_path()` treats integer `1L` as solid (in addition to numeric `1`) --- R/geom-path.R | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/R/geom-path.R b/R/geom-path.R index 99e3d5c0c5..80d2687b9f 100644 --- a/R/geom-path.R +++ b/R/geom-path.R @@ -180,7 +180,7 @@ GeomPath <- ggproto("GeomPath", Geom, attr <- dapply(munched, "group", function(df) { linetype <- unique0(df$linetype) data_frame0( - solid = identical(linetype, 1) || identical(linetype, "solid"), + solid = length(linetype) == 1 && (identical(linetype, "solid") || linetype == 1), constant = nrow(unique0(df[, names(df) %in% c("alpha", "colour", "linewidth", "linetype")])) == 1, .size = 1 ) From 7ffab68e8da83a5e723040c996d99bb3ecd11c55 Mon Sep 17 00:00:00 2001 From: Teun van den Brand Date: Tue, 20 Aug 2024 10:12:45 +0200 Subject: [PATCH 38/41] get linetype from theme --- R/annotation-logticks.R | 7 ++++++- R/geom-abline.R | 8 +++++++- R/geom-boxplot.R | 2 +- R/geom-contour.R | 2 +- R/geom-crossbar.R | 9 +++++++-- R/geom-curve.R | 9 ++++++++- R/geom-density2d.R | 7 ++++++- R/geom-dotplot.R | 10 ++++++++-- R/geom-errorbar.R | 10 ++++++++-- R/geom-errorbarh.R | 10 ++++++++-- R/geom-hex.R | 2 +- R/geom-hline.R | 7 ++++++- R/geom-linerange.R | 8 +++++++- R/geom-path.R | 7 ++++++- R/geom-pointrange.R | 2 +- R/geom-polygon.R | 3 ++- R/geom-rect.R | 2 +- R/geom-ribbon.R | 13 +++++++++---- R/geom-rug.R | 7 ++++++- R/geom-segment.R | 9 ++++++++- R/geom-sf.R | 2 +- R/geom-smooth.R | 3 ++- R/geom-tile.R | 5 +++-- R/geom-violin.R | 4 +++- R/geom-vline.R | 8 +++++++- 25 files changed, 123 insertions(+), 33 deletions(-) diff --git a/R/annotation-logticks.R b/R/annotation-logticks.R index 6696a3656a..975a49492c 100644 --- a/R/annotation-logticks.R +++ b/R/annotation-logticks.R @@ -228,7 +228,12 @@ GeomLogticks <- ggproto("GeomLogticks", Geom, gTree(children = inject(gList(!!!ticks))) }, - default_aes = aes(colour = from_theme(ink), linewidth = from_theme(thin), linetype = 1, alpha = 1) + default_aes = aes( + colour = from_theme(ink), + linewidth = from_theme(thin), + linetype = from_theme(linetype), + alpha = 1 + ) ) diff --git a/R/geom-abline.R b/R/geom-abline.R index 4bd215ff94..bc2b1171b2 100644 --- a/R/geom-abline.R +++ b/R/geom-abline.R @@ -142,7 +142,13 @@ GeomAbline <- ggproto("GeomAbline", Geom, GeomSegment$draw_panel(unique0(data), panel_params, coord, lineend = lineend) }, - default_aes = aes(colour = from_theme(ink), linewidth = from_theme(thin), linetype = 1, alpha = NA), + default_aes = aes( + colour = from_theme(ink), + linewidth = from_theme(thin), + linetype = from_theme(linetype), + alpha = NA + ), + required_aes = c("slope", "intercept"), draw_key = draw_key_abline, diff --git a/R/geom-boxplot.R b/R/geom-boxplot.R index 30262cbf92..f00fa8d3f5 100644 --- a/R/geom-boxplot.R +++ b/R/geom-boxplot.R @@ -330,7 +330,7 @@ GeomBoxplot <- ggproto("GeomBoxplot", Geom, default_aes = aes( weight = 1, colour = from_theme(col_mix(ink, paper, 0.2)), fill = from_theme(paper), size = from_theme(pointsize), - alpha = NA, shape = from_theme(pointshape), linetype = "solid", + alpha = NA, shape = from_theme(pointshape), linetype = from_theme(linetype), linewidth = from_theme(thin) ), diff --git a/R/geom-contour.R b/R/geom-contour.R index 945375dca2..94b1e84abc 100644 --- a/R/geom-contour.R +++ b/R/geom-contour.R @@ -128,7 +128,7 @@ GeomContour <- ggproto("GeomContour", GeomPath, weight = 1, colour = from_theme(accent), linewidth = from_theme(thin), - linetype = 1, + linetype = from_theme(linetype), alpha = NA ) ) diff --git a/R/geom-crossbar.R b/R/geom-crossbar.R index ffcc58785f..8c760a0bb8 100644 --- a/R/geom-crossbar.R +++ b/R/geom-crossbar.R @@ -40,8 +40,13 @@ GeomCrossbar <- ggproto("GeomCrossbar", Geom, GeomErrorbar$setup_data(data, params) }, - default_aes = aes(colour = from_theme(ink), fill = NA, linewidth = from_theme(thin), linetype = 1, - alpha = NA), + default_aes = aes( + colour = from_theme(ink), + fill = NA, + linewidth = from_theme(thin), + linetype = from_theme(linetype), + alpha = NA + ), required_aes = c("x", "y", "ymin|xmin", "ymax|xmax"), diff --git a/R/geom-curve.R b/R/geom-curve.R index dbcb8848dd..6f62051332 100644 --- a/R/geom-curve.R +++ b/R/geom-curve.R @@ -40,7 +40,14 @@ geom_curve <- function(mapping = NULL, data = NULL, #' @usage NULL #' @export GeomCurve <- ggproto("GeomCurve", GeomSegment, - default_aes = aes(colour = from_theme(ink), linewidth = from_theme(thin), linetype = 1, alpha = NA), + + default_aes = aes( + colour = from_theme(ink), + linewidth = from_theme(thin), + linetype = from_theme(linetype), + alpha = NA + ), + draw_panel = function(data, panel_params, coord, curvature = 0.5, angle = 90, ncp = 5, arrow = NULL, arrow.fill = NULL, lineend = "butt", na.rm = FALSE) { diff --git a/R/geom-density2d.R b/R/geom-density2d.R index 8d0e9fbff9..531505d671 100644 --- a/R/geom-density2d.R +++ b/R/geom-density2d.R @@ -106,7 +106,12 @@ geom_density2d <- geom_density_2d #' @usage NULL #' @export GeomDensity2d <- ggproto("GeomDensity2d", GeomPath, - default_aes = aes(colour = from_theme(accent), linewidth = from_theme(thin), linetype = 1, alpha = NA) + default_aes = aes( + colour = from_theme(accent), + linewidth = from_theme(thin), + linetype = from_theme(linetype), + alpha = NA + ) ) #' @export diff --git a/R/geom-dotplot.R b/R/geom-dotplot.R index 24204776fd..6c5305964d 100644 --- a/R/geom-dotplot.R +++ b/R/geom-dotplot.R @@ -188,8 +188,14 @@ GeomDotplot <- ggproto("GeomDotplot", Geom, required_aes = c("x", "y"), non_missing_aes = c("size", "shape"), - default_aes = aes(colour = from_theme(ink), fill = from_theme(ink), alpha = NA, - stroke = 1, linetype = "solid", weight = 1), + default_aes = aes( + colour = from_theme(ink), + fill = from_theme(ink), + alpha = NA, + stroke = 1, + linetype = from_theme(linetype), + weight = 1 + ), setup_data = function(data, params) { data$width <- data$width %||% diff --git a/R/geom-errorbar.R b/R/geom-errorbar.R index 93ef1d9b18..4b8f029822 100644 --- a/R/geom-errorbar.R +++ b/R/geom-errorbar.R @@ -28,8 +28,14 @@ geom_errorbar <- function(mapping = NULL, data = NULL, #' @usage NULL #' @export GeomErrorbar <- ggproto("GeomErrorbar", Geom, - default_aes = aes(colour = from_theme(ink), linewidth = from_theme(thin), linetype = 1, width = 0.5, - alpha = NA), + + default_aes = aes( + colour = from_theme(ink), + linewidth = from_theme(thin), + linetype = from_theme(linetype), + width = 0.5, + alpha = NA + ), draw_key = draw_key_path, diff --git a/R/geom-errorbarh.R b/R/geom-errorbarh.R index 5db06ec04d..4f040c9f88 100644 --- a/R/geom-errorbarh.R +++ b/R/geom-errorbarh.R @@ -51,8 +51,14 @@ geom_errorbarh <- function(mapping = NULL, data = NULL, #' @usage NULL #' @export GeomErrorbarh <- ggproto("GeomErrorbarh", Geom, - default_aes = aes(colour = from_theme(ink), linewidth = from_theme(thin), linetype = 1, height = 0.5, - alpha = NA), + + default_aes = aes( + colour = from_theme(ink), + linewidth = from_theme(thin), + linetype = from_theme(linetype), + height = 0.5, + alpha = NA + ), draw_key = draw_key_path, diff --git a/R/geom-hex.R b/R/geom-hex.R index 39f270db7e..2c4291af1a 100644 --- a/R/geom-hex.R +++ b/R/geom-hex.R @@ -109,7 +109,7 @@ GeomHex <- ggproto("GeomHex", Geom, colour = NA, fill = from_theme(col_mix(ink, paper)), linewidth = from_theme(thin), - linetype = 1, + linetype = from_theme(linetype), alpha = NA ), diff --git a/R/geom-hline.R b/R/geom-hline.R index 9540c80d21..95720c7707 100644 --- a/R/geom-hline.R +++ b/R/geom-hline.R @@ -56,7 +56,12 @@ GeomHline <- ggproto("GeomHline", Geom, GeomSegment$draw_panel(unique0(data), panel_params, coord, lineend = lineend) }, - default_aes = aes(colour = from_theme(ink), linewidth = from_theme(thin), linetype = 1, alpha = NA), + default_aes = aes( + colour = from_theme(ink), + linewidth = from_theme(thin), + linetype = from_theme(linetype), + alpha = NA + ), required_aes = "yintercept", draw_key = draw_key_path, diff --git a/R/geom-linerange.R b/R/geom-linerange.R index 819e3c1000..3c56bc3dc2 100644 --- a/R/geom-linerange.R +++ b/R/geom-linerange.R @@ -91,7 +91,13 @@ geom_linerange <- function(mapping = NULL, data = NULL, #' @usage NULL #' @export GeomLinerange <- ggproto("GeomLinerange", Geom, - default_aes = aes(colour = from_theme(ink), linewidth = from_theme(thin), linetype = 1, alpha = NA), + + default_aes = aes( + colour = from_theme(ink), + linewidth = from_theme(thin), + linetype = from_theme(linetype), + alpha = NA + ), draw_key = draw_key_linerange, diff --git a/R/geom-path.R b/R/geom-path.R index 80d2687b9f..3b595ed0fc 100644 --- a/R/geom-path.R +++ b/R/geom-path.R @@ -134,7 +134,12 @@ geom_path <- function(mapping = NULL, data = NULL, GeomPath <- ggproto("GeomPath", Geom, required_aes = c("x", "y"), - default_aes = aes(colour = from_theme(ink), linewidth = from_theme(thin), linetype = 1, alpha = NA), + default_aes = aes( + colour = from_theme(ink), + linewidth = from_theme(thin), + linetype = from_theme(linetype), + alpha = NA + ), non_missing_aes = c("linewidth", "colour", "linetype"), diff --git a/R/geom-pointrange.R b/R/geom-pointrange.R index 649928d2e6..cb43768a78 100644 --- a/R/geom-pointrange.R +++ b/R/geom-pointrange.R @@ -32,7 +32,7 @@ geom_pointrange <- function(mapping = NULL, data = NULL, GeomPointrange <- ggproto("GeomPointrange", Geom, default_aes = aes( colour = from_theme(ink), size = from_theme(pointsize / 3), - linewidth = from_theme(thin), linetype = 1, + linewidth = from_theme(thin), linetype = from_theme(linetype), shape = from_theme(pointshape), fill = NA, alpha = NA, stroke = 1 ), diff --git a/R/geom-polygon.R b/R/geom-polygon.R index f316d2d437..2f6a08b005 100644 --- a/R/geom-polygon.R +++ b/R/geom-polygon.R @@ -178,7 +178,8 @@ GeomPolygon <- ggproto("GeomPolygon", Geom, default_aes = aes( colour = NA, fill = from_theme(col_mix(ink, paper, 0.2)), - linewidth = from_theme(thin), linetype = 1, + linewidth = from_theme(thin), + linetype = from_theme(linetype), alpha = NA, subgroup = NULL ), diff --git a/R/geom-rect.R b/R/geom-rect.R index fc62b1194f..226cf1852e 100644 --- a/R/geom-rect.R +++ b/R/geom-rect.R @@ -30,7 +30,7 @@ geom_rect <- function(mapping = NULL, data = NULL, GeomRect <- ggproto("GeomRect", Geom, default_aes = aes( colour = NA, fill = from_theme(col_mix(ink, paper, 0.35)), - linewidth = from_theme(thin), linetype = 1, + linewidth = from_theme(thin), linetype = from_theme(linetype), alpha = NA ), diff --git a/R/geom-ribbon.R b/R/geom-ribbon.R index 9586f744ec..e0a015b539 100644 --- a/R/geom-ribbon.R +++ b/R/geom-ribbon.R @@ -97,8 +97,10 @@ geom_ribbon <- function(mapping = NULL, data = NULL, #' @export GeomRibbon <- ggproto("GeomRibbon", Geom, default_aes = aes( - colour = NA, fill = from_theme(col_mix(ink, paper, 0.799)), - linewidth = from_theme(thin), linetype = 1, + colour = NA, + fill = from_theme(col_mix(ink, paper, 0.799)), + linewidth = from_theme(thin), + linetype = from_theme(linetype), alpha = NA), required_aes = c("x|y", "ymin|xmin", "ymax|xmax"), @@ -294,9 +296,12 @@ geom_area <- function(mapping = NULL, data = NULL, stat = "align", #' @usage NULL #' @export GeomArea <- ggproto("GeomArea", GeomRibbon, + default_aes = aes( - colour = NA, fill = from_theme(col_mix(ink, paper, 0.2)), - linewidth = from_theme(thin), linetype = 1, + colour = NA, + fill = from_theme(col_mix(ink, paper, 0.2)), + linewidth = from_theme(thin), + linetype = from_theme(linetype), alpha = NA ), diff --git a/R/geom-rug.R b/R/geom-rug.R index 323b306e4f..575d897ccb 100644 --- a/R/geom-rug.R +++ b/R/geom-rug.R @@ -153,7 +153,12 @@ GeomRug <- ggproto("GeomRug", Geom, gTree(children = inject(gList(!!!rugs))) }, - default_aes = aes(colour = from_theme(ink), linewidth = from_theme(thin), linetype = 1, alpha = NA), + default_aes = aes( + colour = from_theme(ink), + linewidth = from_theme(thin), + linetype = from_theme(linetype), + alpha = NA + ), draw_key = draw_key_path, diff --git a/R/geom-segment.R b/R/geom-segment.R index 285097164f..49fde7399d 100644 --- a/R/geom-segment.R +++ b/R/geom-segment.R @@ -104,7 +104,14 @@ geom_segment <- function(mapping = NULL, data = NULL, GeomSegment <- ggproto("GeomSegment", Geom, required_aes = c("x", "y", "xend|yend"), non_missing_aes = c("linetype", "linewidth"), - default_aes = aes(colour = from_theme(ink), linewidth = from_theme(thin), linetype = 1, alpha = NA), + + default_aes = aes( + colour = from_theme(ink), + linewidth = from_theme(thin), + linetype = from_theme(linetype), + alpha = NA + ), + draw_panel = function(self, data, panel_params, coord, arrow = NULL, arrow.fill = NULL, lineend = "butt", linejoin = "round", na.rm = FALSE) { data$xend <- data$xend %||% data$x diff --git a/R/geom-sf.R b/R/geom-sf.R index 603e1eaf82..240eb0289c 100644 --- a/R/geom-sf.R +++ b/R/geom-sf.R @@ -126,7 +126,7 @@ GeomSf <- ggproto("GeomSf", Geom, fill = NULL, size = NULL, linewidth = NULL, - linetype = 1, + linetype = from_theme(linetype), alpha = NA, stroke = 0.5 ), diff --git a/R/geom-smooth.R b/R/geom-smooth.R index a40ab35aa5..21a343ffe7 100644 --- a/R/geom-smooth.R +++ b/R/geom-smooth.R @@ -172,7 +172,8 @@ GeomSmooth <- ggproto("GeomSmooth", Geom, colour = from_theme(accent), fill = from_theme(col_mix(ink, paper, 0.6)), linewidth = from_theme(thick), - linetype = 1, weight = 1, alpha = 0.4 + linetype = from_theme(linetype), + weight = 1, alpha = 0.4 ), rename_size = TRUE diff --git a/R/geom-tile.R b/R/geom-tile.R index fd609407fa..270d679b5e 100644 --- a/R/geom-tile.R +++ b/R/geom-tile.R @@ -110,7 +110,7 @@ GeomTile <- ggproto("GeomTile", GeomRect, extra_params = c("na.rm"), setup_data = function(data, params) { - + data$width <- data$width %||% params$width %||% stats::ave(data$x, data$PANEL, FUN = function(x) resolution(x, FALSE, TRUE)) data$height <- data$height %||% params$height %||% @@ -126,7 +126,8 @@ GeomTile <- ggproto("GeomTile", GeomRect, fill = from_theme(col_mix(ink, paper, 0.2)), colour = NA, linewidth = from_theme(thick / 10), - linetype = 1, alpha = NA, width = NA, height = NA + linetype = from_theme(linetype), + alpha = NA, width = NA, height = NA ), required_aes = c("x", "y"), diff --git a/R/geom-violin.R b/R/geom-violin.R index 3c9e6a4345..9b3d479983 100644 --- a/R/geom-violin.R +++ b/R/geom-violin.R @@ -202,7 +202,9 @@ GeomViolin <- ggproto("GeomViolin", Geom, colour = from_theme(col_mix(ink, paper, 0.2)), fill = from_theme(paper), linewidth = from_theme(thin), - alpha = NA, linetype = "solid"), + linetype = from_theme(linetype), + alpha = NA + ), required_aes = c("x", "y"), diff --git a/R/geom-vline.R b/R/geom-vline.R index ee1e2713cf..d26b900e51 100644 --- a/R/geom-vline.R +++ b/R/geom-vline.R @@ -56,7 +56,13 @@ GeomVline <- ggproto("GeomVline", Geom, GeomSegment$draw_panel(unique0(data), panel_params, coord, lineend = lineend) }, - default_aes = aes(colour = from_theme(ink), linewidth = from_theme(thin), linetype = 1, alpha = NA), + default_aes = aes( + colour = from_theme(ink), + linewidth = from_theme(thin), + linetype = from_theme(linetype), + alpha = NA + ), + required_aes = "xintercept", draw_key = draw_key_vline, From e17010ffbf8ee4d6261a1465606f8fa545d9ef1e Mon Sep 17 00:00:00 2001 From: Teun van den Brand Date: Mon, 26 Aug 2024 16:49:55 +0200 Subject: [PATCH 39/41] abstract away theme colours --- R/theme-defaults.R | 145 ++++++++++++++++++++++++++------------------- 1 file changed, 84 insertions(+), 61 deletions(-) diff --git a/R/theme-defaults.R b/R/theme-defaults.R index 86a11dbea8..021a57fe37 100644 --- a/R/theme-defaults.R +++ b/R/theme-defaults.R @@ -106,7 +106,8 @@ NULL theme_grey <- function(base_size = 11, base_family = "", header_family = NULL, base_line_size = base_size / 22, - base_rect_size = base_size / 22) { + base_rect_size = base_size / 22, + ink = "black", paper = "white") { # The half-line (base-fontsize / 2) sets up the basic vertical # rhythm of the theme. Most margins will be set to this value. @@ -124,16 +125,16 @@ theme_grey <- function(base_size = 11, base_family = "", # Elements in this first block aren't used directly, but are inherited # by others line = element_line( - colour = "black", linewidth = base_line_size, + colour = ink, linewidth = base_line_size, linetype = 1, lineend = "butt" ), rect = element_rect( - fill = "white", colour = "black", + fill = paper, colour = ink, linewidth = base_rect_size, linetype = 1 ), text = element_text( family = base_family, face = "plain", - colour = "black", size = base_size, + colour = ink, size = base_size, lineheight = 0.9, hjust = 0.5, vjust = 0.5, angle = 0, margin = margin(), debug = FALSE ), @@ -144,7 +145,7 @@ theme_grey <- function(base_size = 11, base_family = "", margins = margin(half_line, half_line, half_line, half_line), geom = element_geom( - ink = "black", paper = "white", accent = "#3366FF", + ink = ink, paper = paper, accent = "#3366FF", thin = base_line_size, thick = base_line_size * 2, linetype = 1L, family = base_family, fontsize = base_size, @@ -154,14 +155,14 @@ theme_grey <- function(base_size = 11, base_family = "", axis.line = element_blank(), axis.line.x = NULL, axis.line.y = NULL, - axis.text = element_text(size = rel(0.8), colour = "grey30"), + axis.text = element_text(size = rel(0.8), colour = col_mix(ink, paper, 0.305)), axis.text.x = element_text(margin = margin(t = 0.8 * half_line / 2), vjust = 1), axis.text.x.top = element_text(margin = margin(b = 0.8 * half_line / 2), vjust = 0), axis.text.y = element_text(margin = margin(r = 0.8 * half_line / 2), hjust = 1), axis.text.y.right = element_text(margin = margin(l = 0.8 * half_line / 2), hjust = 0), axis.text.r = element_text(margin = margin(l = 0.8 * half_line / 2, r = 0.8 * half_line / 2), hjust = 0.5), - axis.ticks = element_line(colour = "grey20"), + axis.ticks = element_line(colour = col_mix(ink, paper, 0.2)), axis.ticks.length = rel(0.5), axis.ticks.length.x = NULL, axis.ticks.length.x.top = NULL, @@ -210,19 +211,19 @@ theme_grey <- function(base_size = 11, base_family = "", legend.box.background = element_blank(), legend.box.spacing = rel(2), - panel.background = element_rect(fill = "grey92", colour = NA), + panel.background = element_rect(fill = col_mix(ink, paper, 0.925), colour = NA), panel.border = element_blank(), - panel.grid = element_line(colour = "white"), + panel.grid = element_line(colour = paper), panel.grid.minor = element_line(linewidth = rel(0.5)), panel.spacing = NULL, panel.spacing.x = NULL, panel.spacing.y = NULL, panel.ontop = FALSE, - strip.background = element_rect(fill = "grey85", colour = NA), + strip.background = element_rect(fill = col_mix(ink, paper, 0.854), colour = NA), strip.clip = "on", strip.text = element_text( - colour = "grey10", + colour = col_mix(ink, paper, 0.105), size = rel(0.8), margin = margin(0.8 * half_line, 0.8 * half_line, 0.8 * half_line, 0.8 * half_line) ), @@ -235,7 +236,7 @@ theme_grey <- function(base_size = 11, base_family = "", strip.switch.pad.grid = unit(half_line / 2, "pt"), strip.switch.pad.wrap = unit(half_line / 2, "pt"), - plot.background = element_rect(colour = "white"), + plot.background = element_rect(colour = paper), plot.title = element_text( # font size "large" size = rel(1.2), hjust = 0, vjust = 1, @@ -274,24 +275,30 @@ theme_gray <- theme_grey theme_bw <- function(base_size = 11, base_family = "", header_family = NULL, base_line_size = base_size / 22, - base_rect_size = base_size / 22) { + base_rect_size = base_size / 22, + ink = "black", paper = "white") { # Starts with theme_grey and then modify some parts theme_grey( base_size = base_size, base_family = base_family, header_family = header_family, base_line_size = base_line_size, - base_rect_size = base_rect_size + base_rect_size = base_rect_size, + ink = ink, + paper = paper ) %+replace% theme( # white background and dark border - panel.background = element_rect(fill = "white", colour = NA), - panel.border = element_rect(colour = "grey20"), + panel.background = element_rect(fill = paper, colour = NA), + panel.border = element_rect(colour = col_mix(ink, paper, 0.2)), # make gridlines dark, same contrast with white as in theme_grey - panel.grid = element_line(colour = "grey92"), + panel.grid = element_line(colour = col_mix(ink, paper, 0.925)), panel.grid.minor = element_line(linewidth = rel(0.5)), # contour strips to match panel contour - strip.background = element_rect(fill = "grey85", colour = "grey20"), + strip.background = element_rect( + fill = col_mix(ink, paper, 0.851), + colour = col_mix(ink, paper, 0.2) + ), complete = TRUE ) @@ -302,7 +309,8 @@ theme_bw <- function(base_size = 11, base_family = "", theme_linedraw <- function(base_size = 11, base_family = "", header_family = NULL, base_line_size = base_size / 22, - base_rect_size = base_size / 22) { + base_rect_size = base_size / 22, + ink = "black", paper = "white") { half_line <- base_size / 2 # Starts with theme_bw and then modify some parts @@ -312,25 +320,27 @@ theme_linedraw <- function(base_size = 11, base_family = "", base_family = base_family, header_family = header_family, base_line_size = base_line_size, - base_rect_size = base_rect_size + base_rect_size = base_rect_size, + ink = ink, + paper = paper ) %+replace% theme( # black text and ticks on the axes - axis.text = element_text(colour = "black", size = rel(0.8)), - axis.ticks = element_line(colour = "black", linewidth = rel(0.5)), + axis.text = element_text(colour = ink, size = rel(0.8)), + axis.ticks = element_line(colour = ink, linewidth = rel(0.5)), # NB: match the *visual* thickness of axis ticks to the panel border # 0.5 clipped looks like 0.25 # pure black panel border and grid lines, but thinner - panel.border = element_rect(colour = "black", linewidth = rel(1)), - panel.grid = element_line(colour = "black"), + panel.border = element_rect(colour = ink, linewidth = rel(1)), + panel.grid = element_line(colour = ink), panel.grid.major = element_line(linewidth = rel(0.1)), panel.grid.minor = element_line(linewidth = rel(0.05)), # strips with black background and white text - strip.background = element_rect(fill = "black"), + strip.background = element_rect(fill = ink), strip.text = element_text( - colour = "white", + colour = paper, size = rel(0.8), margin = margin(0.8 * half_line, 0.8 * half_line, 0.8 * half_line, 0.8 * half_line) ), @@ -344,7 +354,8 @@ theme_linedraw <- function(base_size = 11, base_family = "", theme_light <- function(base_size = 11, base_family = "", header_family = NULL, base_line_size = base_size / 22, - base_rect_size = base_size / 22) { + base_rect_size = base_size / 22, + ink = "black", paper = "white") { half_line <- base_size / 2 # Starts with theme_grey and then modify some parts @@ -353,25 +364,27 @@ theme_light <- function(base_size = 11, base_family = "", base_family = base_family, header_family = header_family, base_line_size = base_line_size, - base_rect_size = base_rect_size + base_rect_size = base_rect_size, + ink = ink, + paper = paper ) %+replace% theme( # white panel with light grey border - panel.background = element_rect(fill = "white", colour = NA), - panel.border = element_rect(colour = "grey70", linewidth = rel(1)), + panel.background = element_rect(fill = paper, colour = NA), + panel.border = element_rect(colour = col_mix(ink, paper, 0.705), linewidth = rel(1)), # light grey, thinner gridlines # => make them slightly darker to keep acceptable contrast - panel.grid = element_line(colour = "grey87"), + panel.grid = element_line(colour = col_mix(ink, paper, 0.871)), panel.grid.major = element_line(linewidth = rel(0.5)), panel.grid.minor = element_line(linewidth = rel(0.25)), # match axes ticks thickness to gridlines and colour to panel border - axis.ticks = element_line(colour = "grey70", linewidth = rel(0.5)), + axis.ticks = element_line(colour = col_mix(ink, paper, 0.705), linewidth = rel(0.5)), # dark strips with light text (inverse contrast compared to theme_grey) - strip.background = element_rect(fill = "grey70", colour = NA), + strip.background = element_rect(fill = col_mix(ink, paper, 0.705), colour = NA), strip.text = element_text( - colour = "white", + colour = paper, size = rel(0.8), margin = margin(0.8 * half_line, 0.8 * half_line, 0.8 * half_line, 0.8 * half_line) ), @@ -386,7 +399,8 @@ theme_light <- function(base_size = 11, base_family = "", theme_dark <- function(base_size = 11, base_family = "", header_family = NULL, base_line_size = base_size / 22, - base_rect_size = base_size / 22) { + base_rect_size = base_size / 22, + ink = "black", paper = "white") { half_line <- base_size / 2 # Starts with theme_grey and then modify some parts @@ -395,24 +409,25 @@ theme_dark <- function(base_size = 11, base_family = "", base_family = base_family, header_family = header_family, base_line_size = base_line_size, - base_rect_size = base_rect_size + base_rect_size = base_rect_size, + ink = ink, paper = paper ) %+replace% theme( # dark panel - panel.background = element_rect(fill = "grey50", colour = NA), + panel.background = element_rect(fill = col_mix(ink, paper, 0.5), colour = NA), # inverse grid lines contrast compared to theme_grey # make them thinner and try to keep the same visual contrast as in theme_light - panel.grid = element_line(colour = "grey42"), + panel.grid = element_line(colour = col_mix(ink, paper, 0.42)), panel.grid.major = element_line(linewidth = rel(0.5)), panel.grid.minor = element_line(linewidth = rel(0.25)), # match axes ticks thickness to gridlines - axis.ticks = element_line(colour = "grey20", linewidth = rel(0.5)), + axis.ticks = element_line(colour = col_mix(ink, paper, 0.2), linewidth = rel(0.5)), # dark strips with light text (inverse contrast compared to theme_grey) - strip.background = element_rect(fill = "grey15", colour = NA), + strip.background = element_rect(fill = col_mix(ink, paper, 0.15), colour = NA), strip.text = element_text( - colour = "grey90", + colour = col_mix(ink, paper, 0.9), size = rel(0.8), margin = margin(0.8 * half_line, 0.8 * half_line, 0.8 * half_line, 0.8 * half_line) ), @@ -426,14 +441,17 @@ theme_dark <- function(base_size = 11, base_family = "", theme_minimal <- function(base_size = 11, base_family = "", header_family = NULL, base_line_size = base_size / 22, - base_rect_size = base_size / 22) { + base_rect_size = base_size / 22, + ink = "black", paper = "white") { # Starts with theme_bw and remove most parts theme_bw( base_size = base_size, base_family = base_family, header_family = header_family, base_line_size = base_line_size, - base_rect_size = base_rect_size + base_rect_size = base_rect_size, + ink = ink, + paper = paper ) %+replace% theme( axis.ticks = element_blank(), @@ -453,13 +471,16 @@ theme_minimal <- function(base_size = 11, base_family = "", theme_classic <- function(base_size = 11, base_family = "", header_family = NULL, base_line_size = base_size / 22, - base_rect_size = base_size / 22) { + base_rect_size = base_size / 22, + ink = "black", paper = "white") { theme_bw( base_size = base_size, base_family = base_family, header_family = header_family, base_line_size = base_line_size, - base_rect_size = base_rect_size + base_rect_size = base_rect_size, + ink = ink, + paper = paper ) %+replace% theme( # no background and no grid @@ -468,10 +489,10 @@ theme_classic <- function(base_size = 11, base_family = "", panel.grid.minor = element_blank(), # show axes - axis.line = element_line(colour = "black", linewidth = rel(1)), + axis.line = element_line(colour = ink, linewidth = rel(1)), # simple, black and white strips - strip.background = element_rect(fill = "white", colour = "black", linewidth = rel(2)), + strip.background = element_rect(fill = paper, colour = ink, linewidth = rel(2)), # NB: size is 1 but clipped, it looks like the 0.5 of the axes complete = TRUE @@ -483,7 +504,8 @@ theme_classic <- function(base_size = 11, base_family = "", theme_void <- function(base_size = 11, base_family = "", header_family = NULL, base_line_size = base_size / 22, - base_rect_size = base_size / 22) { + base_rect_size = base_size / 22, + ink = "black", paper = "white") { half_line <- base_size / 2 # Only keep indispensable text: legend and plot titles @@ -492,7 +514,7 @@ theme_void <- function(base_size = 11, base_family = "", rect = element_blank(), text = element_text( family = base_family, face = "plain", - colour = "black", size = base_size, + colour = ink, size = base_size, lineheight = 0.9, hjust = 0.5, vjust = 0.5, angle = 0, margin = margin(), debug = FALSE ), @@ -561,21 +583,22 @@ theme_void <- function(base_size = 11, base_family = "", theme_test <- function(base_size = 11, base_family = "", header_family = NULL, base_line_size = base_size / 22, - base_rect_size = base_size / 22) { + base_rect_size = base_size / 22, + ink = "black", paper = "white") { half_line <- base_size / 2 t <- theme( line = element_line( - colour = "black", linewidth = base_line_size, + colour = ink, linewidth = base_line_size, linetype = 1, lineend = "butt" ), rect = element_rect( - fill = "white", colour = "black", + fill = paper, colour = ink, linewidth = base_rect_size, linetype = 1 ), text = element_text( family = base_family, face = "plain", - colour = "black", size = base_size, + colour = ink, size = base_size, lineheight = 0.9, hjust = 0.5, vjust = 0.5, angle = 0, margin = margin(), debug = FALSE ), @@ -583,7 +606,7 @@ theme_test <- function(base_size = 11, base_family = "", spacing = unit(half_line, "pt"), margins = margin(half_line, half_line, half_line, half_line), geom = element_geom( - ink = "black", paper = "white", accent = "#3366FF", + ink = ink, paper = paper, accent = "#3366FF", thin = base_line_size, thick = base_line_size * 2, family = base_family, fontsize = base_size, linetype = 1L, @@ -593,12 +616,12 @@ theme_test <- function(base_size = 11, base_family = "", axis.line = element_blank(), axis.line.x = NULL, axis.line.y = NULL, - axis.text = element_text(size = rel(0.8), colour = "grey30"), + axis.text = element_text(size = rel(0.8), colour = col_mix(ink, paper, 0.305)), axis.text.x = element_text(margin = margin(t = 0.8 * half_line / 2), vjust = 1), axis.text.x.top = element_text(margin = margin(b = 0.8 * half_line / 2), vjust = 0), axis.text.y = element_text(margin = margin(r = 0.8 * half_line / 2), hjust = 1), axis.text.y.right = element_text(margin = margin(l = 0.8 * half_line / 2), hjust = 0), - axis.ticks = element_line(colour = "grey20"), + axis.ticks = element_line(colour = col_mix(ink, paper, 0.2)), axis.ticks.length = rel(0.5), axis.ticks.length.x = NULL, axis.ticks.length.x.top = NULL, @@ -649,8 +672,8 @@ theme_test <- function(base_size = 11, base_family = "", legend.box.background = element_blank(), legend.box.spacing = rel(2), - panel.background = element_rect(fill = "white", colour = NA), - panel.border = element_rect(colour = "grey20"), + panel.background = element_rect(fill = paper, colour = NA), + panel.border = element_rect(colour = col_mix(ink, paper, 0.2)), panel.grid.major = element_blank(), panel.grid.minor = element_blank(), panel.spacing = NULL, @@ -658,10 +681,10 @@ theme_test <- function(base_size = 11, base_family = "", panel.spacing.y = NULL, panel.ontop = FALSE, - strip.background = element_rect(fill = "grey85", colour = "grey20"), + strip.background = element_rect(fill = col_mix(ink, paper, 0.851), colour = col_mix(ink, paper, 0.2)), strip.clip = "on", strip.text = element_text( - colour = "grey10", + colour = col_mix(ink, paper, 0.105), size = rel(0.8), margin = margin(0.8 * half_line, 0.8 * half_line, 0.8 * half_line, 0.8 * half_line) ), @@ -674,7 +697,7 @@ theme_test <- function(base_size = 11, base_family = "", strip.switch.pad.grid = rel(0.5), strip.switch.pad.wrap = rel(0.5), - plot.background = element_rect(colour = "white"), + plot.background = element_rect(colour = paper), plot.title = element_text( size = rel(1.2), hjust = 0, vjust = 1, From 1d3d87bf8ac0ba61d1fa6db85e91a961812171e0 Mon Sep 17 00:00:00 2001 From: Teun van den Brand Date: Mon, 26 Aug 2024 16:52:38 +0200 Subject: [PATCH 40/41] document --- R/theme-defaults.R | 2 ++ man/ggtheme.Rd | 44 ++++++++++++++++++++++++++++++++++---------- 2 files changed, 36 insertions(+), 10 deletions(-) diff --git a/R/theme-defaults.R b/R/theme-defaults.R index 021a57fe37..7fca93a955 100644 --- a/R/theme-defaults.R +++ b/R/theme-defaults.R @@ -11,6 +11,8 @@ #' legend titles, the plot title and tag text. #' @param base_line_size base size for line elements #' @param base_rect_size base size for rect elements +#' @param ink colour for foreground elements +#' @param paper colour for background elements #' #' @details #' \describe{ diff --git a/man/ggtheme.Rd b/man/ggtheme.Rd index 642319bcc9..76b204a212 100644 --- a/man/ggtheme.Rd +++ b/man/ggtheme.Rd @@ -18,7 +18,9 @@ theme_grey( base_family = "", header_family = NULL, base_line_size = base_size/22, - base_rect_size = base_size/22 + base_rect_size = base_size/22, + ink = "black", + paper = "white" ) theme_gray( @@ -26,7 +28,9 @@ theme_gray( base_family = "", header_family = NULL, base_line_size = base_size/22, - base_rect_size = base_size/22 + base_rect_size = base_size/22, + ink = "black", + paper = "white" ) theme_bw( @@ -34,7 +38,9 @@ theme_bw( base_family = "", header_family = NULL, base_line_size = base_size/22, - base_rect_size = base_size/22 + base_rect_size = base_size/22, + ink = "black", + paper = "white" ) theme_linedraw( @@ -42,7 +48,9 @@ theme_linedraw( base_family = "", header_family = NULL, base_line_size = base_size/22, - base_rect_size = base_size/22 + base_rect_size = base_size/22, + ink = "black", + paper = "white" ) theme_light( @@ -50,7 +58,9 @@ theme_light( base_family = "", header_family = NULL, base_line_size = base_size/22, - base_rect_size = base_size/22 + base_rect_size = base_size/22, + ink = "black", + paper = "white" ) theme_dark( @@ -58,7 +68,9 @@ theme_dark( base_family = "", header_family = NULL, base_line_size = base_size/22, - base_rect_size = base_size/22 + base_rect_size = base_size/22, + ink = "black", + paper = "white" ) theme_minimal( @@ -66,7 +78,9 @@ theme_minimal( base_family = "", header_family = NULL, base_line_size = base_size/22, - base_rect_size = base_size/22 + base_rect_size = base_size/22, + ink = "black", + paper = "white" ) theme_classic( @@ -74,7 +88,9 @@ theme_classic( base_family = "", header_family = NULL, base_line_size = base_size/22, - base_rect_size = base_size/22 + base_rect_size = base_size/22, + ink = "black", + paper = "white" ) theme_void( @@ -82,7 +98,9 @@ theme_void( base_family = "", header_family = NULL, base_line_size = base_size/22, - base_rect_size = base_size/22 + base_rect_size = base_size/22, + ink = "black", + paper = "white" ) theme_test( @@ -90,7 +108,9 @@ theme_test( base_family = "", header_family = NULL, base_line_size = base_size/22, - base_rect_size = base_size/22 + base_rect_size = base_size/22, + ink = "black", + paper = "white" ) } \arguments{ @@ -105,6 +125,10 @@ legend titles, the plot title and tag text.} \item{base_line_size}{base size for line elements} \item{base_rect_size}{base size for rect elements} + +\item{ink}{colour for foreground elements} + +\item{paper}{colour for background elements} } \description{ These are complete themes which control all non-data display. Use From f7d8a764b2fe7d864cd399b01187c0440a726982 Mon Sep 17 00:00:00 2001 From: Teun van den Brand Date: Mon, 26 Aug 2024 16:53:34 +0200 Subject: [PATCH 41/41] add news bullet --- NEWS.md | 2 ++ 1 file changed, 2 insertions(+) diff --git a/NEWS.md b/NEWS.md index 37e646f710..2f58835c89 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,5 +1,7 @@ # ggplot2 (development version) +* built-in themes now have `ink` and `paper` arguments to set foreground and + background colours in one go (@teunbrand) * (Breaking) The defaults for all geoms can be set at one in the theme. (@teunbrand based on pioneering work by @dpseidel, #2239) * A new `theme(geom)` argument is used to track these defaults.