From 5bfb8bfb53997e5b226e7ba88a8e5b6718573f92 Mon Sep 17 00:00:00 2001 From: Davis Vaughan Date: Mon, 29 Aug 2022 10:21:14 -0400 Subject: [PATCH 001/312] Add `call` argument to `vec_locate_matches()` (#1626) * Initial pass through of `call` from R to C * Pass `call` through ptype2 and cast infrastructure Had to add `call` to `vec_ptype2_params()` and `vec_cast_params()`, but I'm pretty sure it was just missing from those * Use `r_stop_internal()` * Pass call through `stop_matches_nothing()` And remove unused `haystack_arg` from `compute_nesting_container_info()` * Pass the call through `stop_matches_remaining()` * Pass the call through `stop_matches_incomplete()` * Pass the call through `stop_matches_multiple()` * Pass the call through `warn_matches_multiple()` * Add explicit `call` argument in `stop_matches()` and `warn_matches()` * Use internal call in `parse_incomplete()` * Use internal call in `parse_no_match()` * Use internal call in `parse_remaining()` * Use internal call in `parse_multiple()` * NEWS bullet * Use `transform` argument of `expect_snapshot()` --- NEWS.md | 2 + R/match.R | 43 +++--- man/vec_locate_matches.Rd | 8 +- src/cast.h | 2 + src/decl/match-decl.h | 40 ++++-- src/dictionary.c | 16 ++- src/init.c | 4 +- src/interval.c | 8 ++ src/match.c | 205 ++++++++++++++++++--------- src/ptype2.h | 2 + src/vctrs.h | 10 +- tests/testthat/_snaps/dictionary.md | 8 +- tests/testthat/_snaps/match.md | 157 +++++++++++++++++--- tests/testthat/helper-expectations.R | 5 + tests/testthat/test-match.R | 47 +++++- 15 files changed, 424 insertions(+), 133 deletions(-) diff --git a/NEWS.md b/NEWS.md index d3a4ce895..cc5d7de75 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,5 +1,7 @@ # vctrs (development version) +* `vec_locate_matches()` has gained a `call` argument (#1611). + * `"select"` and `"relocate"` have been added as valid subscript actions to support tidyselect and dplyr (#1596). diff --git a/R/match.R b/R/match.R index 576937116..537ebd92b 100644 --- a/R/match.R +++ b/R/match.R @@ -34,6 +34,7 @@ #' * [vec_detect_complete()] #' #' @inheritParams rlang::args_dots_empty +#' @inheritParams rlang::args_error_context #' @inheritParams order-radix #' #' @param needles,haystack Vectors used for matching. @@ -241,8 +242,10 @@ vec_locate_matches <- function(needles, nan_distinct = FALSE, chr_proxy_collate = NULL, needles_arg = "", - haystack_arg = "") { + haystack_arg = "", + call = current_env()) { check_dots_empty0(...) + frame <- environment() .Call( ffi_locate_matches, @@ -257,7 +260,8 @@ vec_locate_matches <- function(needles, nan_distinct, chr_proxy_collate, needles_arg, - haystack_arg + haystack_arg, + frame ) } @@ -281,29 +285,32 @@ compute_nesting_container_info <- function(x, condition) { # ------------------------------------------------------------------------------ -stop_matches <- function(class = NULL, ...) { +stop_matches <- function(class = NULL, ..., call = caller_env()) { stop_vctrs( class = c(class, "vctrs_error_matches"), - ... + ..., + call = call ) } -warn_matches <- function(message, class = NULL, ...) { +warn_matches <- function(message, class = NULL, ..., call = caller_env()) { warn_vctrs( message = message, class = c(class, "vctrs_warning_matches"), - ... + ..., + call = call ) } # ------------------------------------------------------------------------------ -stop_matches_nothing <- function(i, needles_arg, haystack_arg) { +stop_matches_nothing <- function(i, needles_arg, haystack_arg, call) { stop_matches( class = "vctrs_error_matches_nothing", i = i, needles_arg = needles_arg, - haystack_arg = haystack_arg + haystack_arg = haystack_arg, + call = call ) } @@ -333,12 +340,13 @@ cnd_body.vctrs_error_matches_nothing <- function(cnd, ...) { # ------------------------------------------------------------------------------ -stop_matches_remaining <- function(i, needles_arg, haystack_arg) { +stop_matches_remaining <- function(i, needles_arg, haystack_arg, call) { stop_matches( class = "vctrs_error_matches_remaining", i = i, needles_arg = needles_arg, - haystack_arg = haystack_arg + haystack_arg = haystack_arg, + call = call ) } @@ -368,11 +376,12 @@ cnd_body.vctrs_error_matches_remaining <- function(cnd, ...) { # ------------------------------------------------------------------------------ -stop_matches_incomplete <- function(i, needles_arg) { +stop_matches_incomplete <- function(i, needles_arg, call) { stop_matches( class = "vctrs_error_matches_incomplete", i = i, - needles_arg = needles_arg + needles_arg = needles_arg, + call = call ) } @@ -396,12 +405,13 @@ cnd_body.vctrs_error_matches_incomplete <- function(cnd, ...) { # ------------------------------------------------------------------------------ -stop_matches_multiple <- function(i, needles_arg, haystack_arg) { +stop_matches_multiple <- function(i, needles_arg, haystack_arg, call) { stop_matches( class = "vctrs_error_matches_multiple", i = i, needles_arg = needles_arg, - haystack_arg = haystack_arg + haystack_arg = haystack_arg, + call = call ) } @@ -437,7 +447,7 @@ cnd_matches_multiple_body <- function(i) { # ------------------------------------------------------------------------------ -warn_matches_multiple <- function(i, needles_arg, haystack_arg) { +warn_matches_multiple <- function(i, needles_arg, haystack_arg, call) { message <- paste( cnd_matches_multiple_header(needles_arg, haystack_arg), cnd_matches_multiple_body(i), @@ -449,6 +459,7 @@ warn_matches_multiple <- function(i, needles_arg, haystack_arg) { class = "vctrs_warning_matches_multiple", i = i, needles_arg = needles_arg, - haystack_arg = haystack_arg + haystack_arg = haystack_arg, + call = call ) } diff --git a/man/vec_locate_matches.Rd b/man/vec_locate_matches.Rd index 74665703e..05dbe929e 100644 --- a/man/vec_locate_matches.Rd +++ b/man/vec_locate_matches.Rd @@ -17,7 +17,8 @@ vec_locate_matches( nan_distinct = FALSE, chr_proxy_collate = NULL, needles_arg = "", - haystack_arg = "" + haystack_arg = "", + call = current_env() ) } \arguments{ @@ -136,6 +137,11 @@ ordering and \code{stringi::stri_sort_key()} for locale-aware ordering.} \item{needles_arg, haystack_arg}{Argument tags for \code{needles} and \code{haystack} used in error messages.} + +\item{call}{The execution environment of a currently +running function, e.g. \code{caller_env()}. The function will be +mentioned in error messages as the source of the error. See the +\code{call} argument of \code{\link[rlang:abort]{abort()}} for more information.} } \value{ A two column data frame containing the locations of the matches. diff --git a/src/cast.h b/src/cast.h index be190a5c4..440e832df 100644 --- a/src/cast.h +++ b/src/cast.h @@ -42,6 +42,7 @@ r_obj* vec_cast_params(r_obj* x, r_obj* to, struct vctrs_arg* p_x_arg, struct vctrs_arg* p_to_arg, + struct r_lazy call, enum df_fallback df_fallback, enum s3_fallback s3_fallback) { const struct cast_opts opts = { @@ -49,6 +50,7 @@ r_obj* vec_cast_params(r_obj* x, .to = to, .p_x_arg = p_x_arg, .p_to_arg = p_to_arg, + .call = call, .fallback = { .df = df_fallback, .s3 = s3_fallback diff --git a/src/decl/match-decl.h b/src/decl/match-decl.h index 0f00718dc..ab2580d78 100644 --- a/src/decl/match-decl.h +++ b/src/decl/match-decl.h @@ -21,7 +21,8 @@ r_obj* vec_locate_matches(r_obj* needles, bool nan_distinct, r_obj* chr_proxy_collate, struct vctrs_arg* needles_arg, - struct vctrs_arg* haystack_arg); + struct vctrs_arg* haystack_arg, + struct r_lazy call); static r_obj* df_locate_matches(r_obj* needles, @@ -38,7 +39,8 @@ r_obj* df_locate_matches(r_obj* needles, const enum vctrs_filter* v_filters, const enum vctrs_ops* v_ops, struct vctrs_arg* needles_arg, - struct vctrs_arg* haystack_arg); + struct vctrs_arg* haystack_arg, + struct r_lazy call); static void df_locate_matches_recurse(r_ssize col, @@ -127,16 +129,20 @@ static inline void parse_condition(r_obj* condition, r_ssize n_cols, enum vctrs_ops* v_ops); static inline -struct vctrs_no_match parse_no_match(r_obj* no_match); +struct vctrs_no_match parse_no_match(r_obj* no_match, + struct r_lazy call); static inline -struct vctrs_remaining parse_remaining(r_obj* remaining); +struct vctrs_remaining parse_remaining(r_obj* remaining, + struct r_lazy call); static inline -struct vctrs_incomplete parse_incomplete(r_obj* incomplete); +struct vctrs_incomplete parse_incomplete(r_obj* incomplete, + struct r_lazy call); static inline -enum vctrs_multiple parse_multiple(r_obj* multiple); +enum vctrs_multiple parse_multiple(r_obj* multiple, + struct r_lazy call); static inline void parse_filter(r_obj* filter, r_ssize n_cols, enum vctrs_filter* v_filters); @@ -160,13 +166,13 @@ r_obj* expand_compact_indices(const int* v_o_haystack, const int* v_loc_filter_match_o_haystack, const struct poly_df_data* p_haystack, struct vctrs_arg* needles_arg, - struct vctrs_arg* haystack_arg); + struct vctrs_arg* haystack_arg, + struct r_lazy call); static r_obj* compute_nesting_container_info(r_obj* haystack, r_ssize size_haystack, - const enum vctrs_ops* v_ops, - struct vctrs_arg* haystack_arg); + const enum vctrs_ops* v_ops); static r_obj* compute_nesting_container_ids(r_obj* x, @@ -206,22 +212,28 @@ void stop_matches_overflow(double size); static inline void stop_matches_nothing(r_ssize i, struct vctrs_arg* needles_arg, - struct vctrs_arg* haystack_arg); + struct vctrs_arg* haystack_arg, + struct r_lazy call); static inline void stop_matches_remaining(r_ssize i, struct vctrs_arg* needles_arg, - struct vctrs_arg* haystack_arg); + struct vctrs_arg* haystack_arg, + struct r_lazy call); static inline -void stop_matches_incomplete(r_ssize i, struct vctrs_arg* needles_arg); +void stop_matches_incomplete(r_ssize i, + struct vctrs_arg* needles_arg, + struct r_lazy call); static inline void stop_matches_multiple(r_ssize i, struct vctrs_arg* needles_arg, - struct vctrs_arg* haystack_arg); + struct vctrs_arg* haystack_arg, + struct r_lazy call); static inline void warn_matches_multiple(r_ssize i, struct vctrs_arg* needles_arg, - struct vctrs_arg* haystack_arg); + struct vctrs_arg* haystack_arg, + struct r_lazy call); diff --git a/src/dictionary.c b/src/dictionary.c index eddec1106..ea5aae24e 100644 --- a/src/dictionary.c +++ b/src/dictionary.c @@ -330,6 +330,8 @@ SEXP vctrs_id(SEXP x) { // [[ register() ]] SEXP vctrs_match(SEXP needles, SEXP haystack, SEXP na_equal, SEXP frame) { + struct r_lazy call = { .x = frame, .env = r_null }; + struct r_lazy needles_arg_ = { .x = syms.needles_arg, .env = frame }; struct vctrs_arg needles_arg = new_lazy_arg(&needles_arg_); @@ -340,7 +342,8 @@ SEXP vctrs_match(SEXP needles, SEXP haystack, SEXP na_equal, haystack, r_bool_as_int(na_equal), &needles_arg, - &haystack_arg); + &haystack_arg, + call); } static inline void vec_match_loop(int* p_out, @@ -356,23 +359,27 @@ SEXP vec_match_params(SEXP needles, SEXP haystack, bool na_equal, struct vctrs_arg* needles_arg, - struct vctrs_arg* haystack_arg) { + struct vctrs_arg* haystack_arg, + struct r_lazy call) { int nprot = 0; int _; SEXP type = vec_ptype2_params(needles, haystack, needles_arg, haystack_arg, + call, DF_FALLBACK_quiet, &_); PROTECT_N(type, &nprot); needles = vec_cast_params(needles, type, needles_arg, vec_args.empty, + call, DF_FALLBACK_quiet, S3_FALLBACK_false); PROTECT_N(needles, &nprot); haystack = vec_cast_params(haystack, type, haystack_arg, vec_args.empty, + call, DF_FALLBACK_quiet, S3_FALLBACK_false); PROTECT_N(haystack, &nprot); @@ -453,6 +460,8 @@ static inline void vec_match_loop_propagate(int* p_out, // [[ register() ]] SEXP vctrs_in(SEXP needles, SEXP haystack, SEXP na_equal_, SEXP frame) { + struct r_lazy call = { .x = frame, .env = r_null }; + int nprot = 0; bool na_equal = r_bool_as_int(na_equal_); @@ -466,18 +475,21 @@ SEXP vctrs_in(SEXP needles, SEXP haystack, SEXP na_equal_, SEXP frame) { SEXP type = vec_ptype2_params(needles, haystack, &needles_arg, &haystack_arg, + call, DF_FALLBACK_quiet, &_); PROTECT_N(type, &nprot); needles = vec_cast_params(needles, type, &needles_arg, vec_args.empty, + call, DF_FALLBACK_quiet, S3_FALLBACK_false); PROTECT_N(needles, &nprot); haystack = vec_cast_params(haystack, type, &haystack_arg, vec_args.empty, + call, DF_FALLBACK_quiet, S3_FALLBACK_false); PROTECT_N(haystack, &nprot); diff --git a/src/init.c b/src/init.c index 013ee7876..6ddfca53d 100644 --- a/src/init.c +++ b/src/init.c @@ -140,7 +140,7 @@ extern r_obj* vctrs_list_drop_empty(r_obj*); extern r_obj* vctrs_is_altrep(r_obj* x); extern r_obj* ffi_interleave_indices(r_obj*, r_obj*); extern r_obj* ffi_compute_nesting_container_info(r_obj*, r_obj*); -extern r_obj* ffi_locate_matches(r_obj*, r_obj*, r_obj*, r_obj*, r_obj*, r_obj*, r_obj*, r_obj*, r_obj*, r_obj*, r_obj*, r_obj*); +extern r_obj* ffi_locate_matches(r_obj*, r_obj*, r_obj*, r_obj*, r_obj*, r_obj*, r_obj*, r_obj*, r_obj*, r_obj*, r_obj*, r_obj*, r_obj*); extern r_obj* ffi_interval_groups(r_obj*, r_obj*, r_obj*, r_obj*); extern r_obj* ffi_interval_locate_groups(r_obj*, r_obj*, r_obj*, r_obj*); extern r_obj* ffi_interval_complement(r_obj*, r_obj*, r_obj*, r_obj*); @@ -310,7 +310,7 @@ static const R_CallMethodDef CallEntries[] = { {"vctrs_is_altrep", (DL_FUNC) &vctrs_is_altrep, 1}, {"ffi_interleave_indices", (DL_FUNC) &ffi_interleave_indices, 2}, {"ffi_compute_nesting_container_info", (DL_FUNC) &ffi_compute_nesting_container_info, 2}, - {"ffi_locate_matches", (DL_FUNC) &ffi_locate_matches, 12}, + {"ffi_locate_matches", (DL_FUNC) &ffi_locate_matches, 13}, {"ffi_interval_groups", (DL_FUNC) &ffi_interval_groups, 4}, {"ffi_interval_locate_groups", (DL_FUNC) &ffi_interval_locate_groups, 4}, {"ffi_interval_complement", (DL_FUNC) &ffi_interval_complement, 4}, diff --git a/src/interval.c b/src/interval.c index 59b42a993..e9895f601 100644 --- a/src/interval.c +++ b/src/interval.c @@ -80,6 +80,7 @@ r_obj* vec_interval_group_info(r_obj* start, end, args_start, args_end, + r_lazy_null, DF_FALLBACK_quiet, &_ ); @@ -90,6 +91,7 @@ r_obj* vec_interval_group_info(r_obj* start, ptype, args_start, vec_args.empty, + r_lazy_null, DF_FALLBACK_quiet, S3_FALLBACK_false ); @@ -100,6 +102,7 @@ r_obj* vec_interval_group_info(r_obj* start, ptype, args_end, vec_args.empty, + r_lazy_null, DF_FALLBACK_quiet, S3_FALLBACK_false ); @@ -316,6 +319,7 @@ r_obj* vec_interval_complement(r_obj* start, end, args_start, args_end, + r_lazy_null, DF_FALLBACK_quiet, &_ ); @@ -326,6 +330,7 @@ r_obj* vec_interval_complement(r_obj* start, ptype, args_start, vec_args.empty, + r_lazy_null, DF_FALLBACK_quiet, S3_FALLBACK_false ); @@ -336,6 +341,7 @@ r_obj* vec_interval_complement(r_obj* start, ptype, args_end, vec_args.empty, + r_lazy_null, DF_FALLBACK_quiet, S3_FALLBACK_false ); @@ -376,6 +382,7 @@ r_obj* vec_interval_complement(r_obj* start, ptype, args_lower, vec_args.empty, + r_lazy_null, DF_FALLBACK_quiet, S3_FALLBACK_false ); @@ -405,6 +412,7 @@ r_obj* vec_interval_complement(r_obj* start, ptype, args_upper, vec_args.empty, + r_lazy_null, DF_FALLBACK_quiet, S3_FALLBACK_false ); diff --git a/src/match.c b/src/match.c index 166773c60..a346a9e22 100644 --- a/src/match.c +++ b/src/match.c @@ -83,11 +83,15 @@ r_obj* ffi_locate_matches(r_obj* needles, r_obj* nan_distinct, r_obj* chr_proxy_collate, r_obj* needles_arg, - r_obj* haystack_arg) { - const struct vctrs_incomplete c_incomplete = parse_incomplete(incomplete); - const struct vctrs_no_match c_no_match = parse_no_match(no_match); - const struct vctrs_remaining c_remaining = parse_remaining(remaining); - const enum vctrs_multiple c_multiple = parse_multiple(multiple); + r_obj* haystack_arg, + r_obj* frame) { + struct r_lazy call = { .x = syms_call, .env = frame }; + struct r_lazy internal_call = { .x = frame, .env = r_null }; + + const struct vctrs_incomplete c_incomplete = parse_incomplete(incomplete, internal_call); + const struct vctrs_no_match c_no_match = parse_no_match(no_match, internal_call); + const struct vctrs_remaining c_remaining = parse_remaining(remaining, internal_call); + const enum vctrs_multiple c_multiple = parse_multiple(multiple, internal_call); const bool c_nan_distinct = r_arg_as_bool(nan_distinct, "nan_distinct"); struct vctrs_arg c_needles_arg = vec_as_arg(needles_arg); @@ -105,7 +109,8 @@ r_obj* ffi_locate_matches(r_obj* needles, c_nan_distinct, chr_proxy_collate, &c_needles_arg, - &c_haystack_arg + &c_haystack_arg, + call ); } @@ -121,7 +126,8 @@ r_obj* vec_locate_matches(r_obj* needles, bool nan_distinct, r_obj* chr_proxy_collate, struct vctrs_arg* needles_arg, - struct vctrs_arg* haystack_arg) { + struct vctrs_arg* haystack_arg, + struct r_lazy call) { int n_prot = 0; int _; @@ -130,6 +136,7 @@ r_obj* vec_locate_matches(r_obj* needles, haystack, needles_arg, haystack_arg, + call, DF_FALLBACK_quiet, &_ ), &n_prot); @@ -139,6 +146,7 @@ r_obj* vec_locate_matches(r_obj* needles, ptype, needles_arg, vec_args.empty, + call, DF_FALLBACK_quiet, S3_FALLBACK_false ), &n_prot); @@ -148,6 +156,7 @@ r_obj* vec_locate_matches(r_obj* needles, ptype, haystack_arg, vec_args.empty, + call, DF_FALLBACK_quiet, S3_FALLBACK_false ), &n_prot); @@ -186,7 +195,7 @@ r_obj* vec_locate_matches(r_obj* needles, if (n_cols == 0) { // If there are no columns, this operation isn't well defined. - r_abort("Must have at least 1 column to match on."); + r_abort_lazy_call(call, "Must have at least 1 column to match on."); } // Compute the locations of incomplete values per column since computing @@ -226,7 +235,8 @@ r_obj* vec_locate_matches(r_obj* needles, v_filters, v_ops, needles_arg, - haystack_arg + haystack_arg, + call ); FREE(n_prot); @@ -250,7 +260,8 @@ r_obj* df_locate_matches(r_obj* needles, const enum vctrs_filter* v_filters, const enum vctrs_ops* v_ops, struct vctrs_arg* needles_arg, - struct vctrs_arg* haystack_arg) { + struct vctrs_arg* haystack_arg, + struct r_lazy call) { int n_prot = 0; r_obj* o_needles = KEEP_N(vec_order( @@ -265,8 +276,7 @@ r_obj* df_locate_matches(r_obj* needles, r_obj* container_info = KEEP_N(compute_nesting_container_info( haystack, size_haystack, - v_ops, - haystack_arg + v_ops ), &n_prot); r_obj* o_haystack = r_list_get(container_info, 0); @@ -449,7 +459,8 @@ r_obj* df_locate_matches(r_obj* needles, v_loc_filter_match_o_haystack, p_haystack, needles_arg, - haystack_arg + haystack_arg, + call ), &n_prot); FREE(n_prot); @@ -1281,9 +1292,14 @@ void parse_condition(r_obj* condition, r_ssize n_cols, enum vctrs_ops* v_ops) { // ----------------------------------------------------------------------------- static inline -struct vctrs_incomplete parse_incomplete(r_obj* incomplete) { +struct vctrs_incomplete parse_incomplete(r_obj* incomplete, + struct r_lazy call) { if (r_length(incomplete) != 1) { - r_abort("`incomplete` must be length 1, not length %i.", r_length(incomplete)); + r_abort_lazy_call( + call, + "`incomplete` must be length 1, not length %i.", + r_length(incomplete) + ); } if (r_is_string(incomplete)) { @@ -1317,10 +1333,19 @@ struct vctrs_incomplete parse_incomplete(r_obj* incomplete) { }; } - r_abort("`incomplete` must be one of: \"compare\", \"match\", \"drop\", or \"error\"."); + r_abort_lazy_call( + call, + "`incomplete` must be one of: \"compare\", \"match\", \"drop\", or \"error\"." + ); } - incomplete = vec_cast(incomplete, vctrs_shared_empty_int, args_incomplete, vec_args.empty, r_lazy_null); + incomplete = vec_cast( + incomplete, + vctrs_shared_empty_int, + args_incomplete, + vec_args.empty, + call + ); int c_incomplete = r_int_get(incomplete, 0); return (struct vctrs_incomplete) { @@ -1332,9 +1357,9 @@ struct vctrs_incomplete parse_incomplete(r_obj* incomplete) { // ----------------------------------------------------------------------------- static inline -enum vctrs_multiple parse_multiple(r_obj* multiple) { +enum vctrs_multiple parse_multiple(r_obj* multiple, struct r_lazy call) { if (!r_is_string(multiple)) { - r_abort("`multiple` must be a string."); + r_abort_lazy_call(call, "`multiple` must be a string."); } const char* c_multiple = r_chr_get_c_string(multiple, 0); @@ -1346,7 +1371,10 @@ enum vctrs_multiple parse_multiple(r_obj* multiple) { if (!strcmp(c_multiple, "warning")) return VCTRS_MULTIPLE_warning; if (!strcmp(c_multiple, "error")) return VCTRS_MULTIPLE_error; - r_abort("`multiple` must be one of \"all\", \"any\", \"first\", \"last\", \"warning\", or \"error\"."); + r_abort_lazy_call( + call, + "`multiple` must be one of \"all\", \"any\", \"first\", \"last\", \"warning\", or \"error\"." + ); } // ----------------------------------------------------------------------------- @@ -1398,9 +1426,14 @@ void parse_filter(r_obj* filter, r_ssize n_cols, enum vctrs_filter* v_filters) { // ----------------------------------------------------------------------------- static inline -struct vctrs_no_match parse_no_match(r_obj* no_match) { +struct vctrs_no_match parse_no_match(r_obj* no_match, + struct r_lazy call) { if (r_length(no_match) != 1) { - r_abort("`no_match` must be length 1, not length %i.", r_length(no_match)); + r_abort_lazy_call( + call, + "`no_match` must be length 1, not length %i.", + r_length(no_match) + ); } if (r_is_string(no_match)) { @@ -1420,10 +1453,19 @@ struct vctrs_no_match parse_no_match(r_obj* no_match) { }; } - r_abort("`no_match` must be either \"drop\" or \"error\"."); + r_abort_lazy_call( + call, + "`no_match` must be either \"drop\" or \"error\"." + ); } - no_match = vec_cast(no_match, vctrs_shared_empty_int, args_no_match, vec_args.empty, r_lazy_null); + no_match = vec_cast( + no_match, + vctrs_shared_empty_int, + args_no_match, + vec_args.empty, + call + ); int c_no_match = r_int_get(no_match, 0); return (struct vctrs_no_match) { @@ -1435,9 +1477,14 @@ struct vctrs_no_match parse_no_match(r_obj* no_match) { // ----------------------------------------------------------------------------- static inline -struct vctrs_remaining parse_remaining(r_obj* remaining) { +struct vctrs_remaining parse_remaining(r_obj* remaining, + struct r_lazy call) { if (r_length(remaining) != 1) { - r_abort("`remaining` must be length 1, not length %i.", r_length(remaining)); + r_abort_lazy_call( + call, + "`remaining` must be length 1, not length %i.", + r_length(remaining) + ); } if (r_is_string(remaining)) { @@ -1457,10 +1504,19 @@ struct vctrs_remaining parse_remaining(r_obj* remaining) { }; } - r_abort("`remaining` must be either \"drop\" or \"error\"."); + r_abort_lazy_call( + call, + "`remaining` must be either \"drop\" or \"error\"." + ); } - remaining = vec_cast(remaining, vctrs_shared_empty_int, args_remaining, vec_args.empty, r_lazy_null); + remaining = vec_cast( + remaining, + vctrs_shared_empty_int, + args_remaining, + vec_args.empty, + call + ); int c_remaining = r_int_get(remaining, 0); return (struct vctrs_remaining) { @@ -1511,7 +1567,8 @@ r_obj* expand_compact_indices(const int* v_o_haystack, const int* v_loc_filter_match_o_haystack, const struct poly_df_data* p_haystack, struct vctrs_arg* needles_arg, - struct vctrs_arg* haystack_arg) { + struct vctrs_arg* haystack_arg, + struct r_lazy call) { int n_prot = 0; const r_ssize n_used = p_loc_first_match_o_haystack->count; @@ -1621,7 +1678,7 @@ r_obj* expand_compact_indices(const int* v_o_haystack, continue; } case VCTRS_INCOMPLETE_ACTION_error: { - stop_matches_incomplete(loc_needles, needles_arg); + stop_matches_incomplete(loc_needles, needles_arg, call); } case VCTRS_INCOMPLETE_ACTION_compare: case VCTRS_INCOMPLETE_ACTION_match: { @@ -1654,7 +1711,7 @@ r_obj* expand_compact_indices(const int* v_o_haystack, continue; } case VCTRS_NO_MATCH_ACTION_error: { - stop_matches_nothing(loc_needles, needles_arg, haystack_arg); + stop_matches_nothing(loc_needles, needles_arg, haystack_arg, call); } default: { r_stop_internal("Unknown `no_match->action`."); @@ -1703,9 +1760,9 @@ r_obj* expand_compact_indices(const int* v_o_haystack, if (any_multiple) { if (multiple == VCTRS_MULTIPLE_error) { - stop_matches_multiple(loc_needles, needles_arg, haystack_arg); + stop_matches_multiple(loc_needles, needles_arg, haystack_arg, call); } else if (multiple == VCTRS_MULTIPLE_warning) { - warn_matches_multiple(loc_needles, needles_arg, haystack_arg); + warn_matches_multiple(loc_needles, needles_arg, haystack_arg, call); } // We know there are multiple and don't need to continue checking @@ -1866,7 +1923,7 @@ r_obj* expand_compact_indices(const int* v_o_haystack, } if (remaining->action == VCTRS_REMAINING_ACTION_error) { - stop_matches_remaining(i, needles_arg, haystack_arg); + stop_matches_remaining(i, needles_arg, haystack_arg, call); } // Overwrite with location, this moves all "remaining" locations to the @@ -1912,15 +1969,13 @@ r_obj* ffi_compute_nesting_container_info(r_obj* haystack, r_obj* condition) { enum vctrs_ops* v_ops = (enum vctrs_ops*) R_alloc(n_cols, sizeof(enum vctrs_ops)); parse_condition(condition, n_cols, v_ops); const r_ssize size_haystack = vec_size(haystack); - struct vctrs_arg haystack_arg = new_wrapper_arg(NULL, "haystack"); - return compute_nesting_container_info(haystack, size_haystack, v_ops, &haystack_arg); + return compute_nesting_container_info(haystack, size_haystack, v_ops); } static r_obj* compute_nesting_container_info(r_obj* haystack, r_ssize size_haystack, - const enum vctrs_ops* v_ops, - struct vctrs_arg* haystack_arg) { + const enum vctrs_ops* v_ops) { int n_prot = 0; const r_ssize n_cols = r_length(haystack); @@ -2352,11 +2407,9 @@ r_ssize midpoint(r_ssize lhs, r_ssize rhs) { static inline void stop_matches_overflow(double size) { - r_abort( + r_stop_internal( "Match procedure results in an allocation larger than 2^31-1 elements. " - "Attempted allocation size was %.0lf. " - "Please report this to the vctrs maintainers at " - ".", + "Attempted allocation size was %.0lf.", size ); } @@ -2364,22 +2417,25 @@ void stop_matches_overflow(double size) { static inline void stop_matches_nothing(r_ssize i, struct vctrs_arg* needles_arg, - struct vctrs_arg* haystack_arg) { - r_obj* syms[4] = { + struct vctrs_arg* haystack_arg, + struct r_lazy call) { + r_obj* syms[5] = { syms_i, syms_needles_arg, syms_haystack_arg, + syms_call, NULL }; - r_obj* args[4] = { + r_obj* args[5] = { KEEP(r_int((int)i + 1)), KEEP(vctrs_arg(needles_arg)), KEEP(vctrs_arg(haystack_arg)), + KEEP(r_lazy_eval_protect(call)), NULL }; - r_obj* call = KEEP(r_call_n(syms_stop_matches_nothing, syms, args)); - Rf_eval(call, vctrs_ns_env); + r_obj* ffi_call = KEEP(r_call_n(syms_stop_matches_nothing, syms, args)); + Rf_eval(ffi_call, vctrs_ns_env); never_reached("stop_matches_nothing"); } @@ -2387,41 +2443,48 @@ void stop_matches_nothing(r_ssize i, static inline void stop_matches_remaining(r_ssize i, struct vctrs_arg* needles_arg, - struct vctrs_arg* haystack_arg) { - r_obj* syms[4] = { + struct vctrs_arg* haystack_arg, + struct r_lazy call) { + r_obj* syms[5] = { syms_i, syms_needles_arg, syms_haystack_arg, + syms_call, NULL }; - r_obj* args[4] = { + r_obj* args[5] = { KEEP(r_int((int)i + 1)), KEEP(vctrs_arg(needles_arg)), KEEP(vctrs_arg(haystack_arg)), + KEEP(r_lazy_eval_protect(call)), NULL }; - r_obj* call = KEEP(r_call_n(syms_stop_matches_remaining, syms, args)); - Rf_eval(call, vctrs_ns_env); + r_obj* ffi_call = KEEP(r_call_n(syms_stop_matches_remaining, syms, args)); + Rf_eval(ffi_call, vctrs_ns_env); never_reached("stop_matches_remaining"); } static inline -void stop_matches_incomplete(r_ssize i, struct vctrs_arg* needles_arg) { - r_obj* syms[3] = { +void stop_matches_incomplete(r_ssize i, + struct vctrs_arg* needles_arg, + struct r_lazy call) { + r_obj* syms[4] = { syms_i, syms_needles_arg, + syms_call, NULL }; - r_obj* args[3] = { + r_obj* args[4] = { KEEP(r_int((int)i + 1)), KEEP(vctrs_arg(needles_arg)), + KEEP(r_lazy_eval_protect(call)), NULL }; - r_obj* call = KEEP(r_call_n(syms_stop_matches_incomplete, syms, args)); - Rf_eval(call, vctrs_ns_env); + r_obj* ffi_call = KEEP(r_call_n(syms_stop_matches_incomplete, syms, args)); + Rf_eval(ffi_call, vctrs_ns_env); never_reached("stop_matches_incomplete"); } @@ -2429,22 +2492,25 @@ void stop_matches_incomplete(r_ssize i, struct vctrs_arg* needles_arg) { static inline void stop_matches_multiple(r_ssize i, struct vctrs_arg* needles_arg, - struct vctrs_arg* haystack_arg) { - r_obj* syms[4] = { + struct vctrs_arg* haystack_arg, + struct r_lazy call) { + r_obj* syms[5] = { syms_i, syms_needles_arg, syms_haystack_arg, + syms_call, NULL }; - r_obj* args[4] = { + r_obj* args[5] = { KEEP(r_int((int)i + 1)), KEEP(vctrs_arg(needles_arg)), KEEP(vctrs_arg(haystack_arg)), + KEEP(r_lazy_eval_protect(call)), NULL }; - r_obj* call = KEEP(r_call_n(syms_stop_matches_multiple, syms, args)); - Rf_eval(call, vctrs_ns_env); + r_obj* ffi_call = KEEP(r_call_n(syms_stop_matches_multiple, syms, args)); + Rf_eval(ffi_call, vctrs_ns_env); never_reached("stop_matches_multiple"); } @@ -2452,23 +2518,26 @@ void stop_matches_multiple(r_ssize i, static inline void warn_matches_multiple(r_ssize i, struct vctrs_arg* needles_arg, - struct vctrs_arg* haystack_arg) { - r_obj* syms[4] = { + struct vctrs_arg* haystack_arg, + struct r_lazy call) { + r_obj* syms[5] = { syms_i, syms_needles_arg, syms_haystack_arg, + syms_call, NULL }; - r_obj* args[4] = { + r_obj* args[5] = { KEEP(r_int((int)i + 1)), KEEP(vctrs_arg(needles_arg)), KEEP(vctrs_arg(haystack_arg)), + KEEP(r_lazy_eval_protect(call)), NULL }; - r_obj* call = KEEP(r_call_n(syms_warn_matches_multiple, syms, args)); - Rf_eval(call, vctrs_ns_env); - FREE(4); + r_obj* ffi_call = KEEP(r_call_n(syms_warn_matches_multiple, syms, args)); + Rf_eval(ffi_call, vctrs_ns_env); + FREE(5); } // ----------------------------------------------------------------------------- diff --git a/src/ptype2.h b/src/ptype2.h index 6b2c9fe48..9125793f4 100644 --- a/src/ptype2.h +++ b/src/ptype2.h @@ -45,6 +45,7 @@ r_obj* vec_ptype2_params(r_obj* x, r_obj* y, struct vctrs_arg* p_x_arg, struct vctrs_arg* p_y_arg, + struct r_lazy call, enum df_fallback df_fallback, int* left) { const struct ptype2_opts opts = { @@ -52,6 +53,7 @@ r_obj* vec_ptype2_params(r_obj* x, .y = y, .p_x_arg = p_x_arg, .p_y_arg = p_y_arg, + .call = call, .fallback = { .df = df_fallback } diff --git a/src/vctrs.h b/src/vctrs.h index e311c0740..d0f45a51c 100644 --- a/src/vctrs.h +++ b/src/vctrs.h @@ -320,12 +320,16 @@ SEXP vec_names(SEXP x); SEXP vec_proxy_names(SEXP x); SEXP vec_group_loc(SEXP x); SEXP vec_identify_runs(SEXP x); -SEXP vec_match_params(SEXP needles, SEXP haystack, bool na_equal, - struct vctrs_arg* needles_arg, struct vctrs_arg* haystack_arg); +SEXP vec_match_params(SEXP needles, + SEXP haystack, + bool na_equal, + struct vctrs_arg* needles_arg, + struct vctrs_arg* haystack_arg, + struct r_lazy call); static inline SEXP vec_match(SEXP needles, SEXP haystack) { - return vec_match_params(needles, haystack, true, NULL, NULL); + return vec_match_params(needles, haystack, true, NULL, NULL, r_lazy_null); } diff --git a/tests/testthat/_snaps/dictionary.md b/tests/testthat/_snaps/dictionary.md index 309e6541b..e647b02a6 100644 --- a/tests/testthat/_snaps/dictionary.md +++ b/tests/testthat/_snaps/dictionary.md @@ -6,26 +6,26 @@ (expect_error(vec_match(df1, df2), class = "vctrs_error_incompatible_type")) Output - Error: + Error in `vec_match()`: ! Can't combine `x$foo` and `x$foo` . Code (expect_error(vec_match(df1, df2, needles_arg = "n", haystack_arg = "h"), class = "vctrs_error_incompatible_type")) Output - Error: + Error in `vec_match()`: ! Can't combine `n$x$foo` and `h$x$foo` . Code (expect_error(vec_in(df1, df2), class = "vctrs_error_incompatible_type")) Output - Error: + Error in `vec_in()`: ! Can't combine `x$foo` and `x$foo` . Code (expect_error(vec_in(df1, df2, needles_arg = "n", haystack_arg = "h"), class = "vctrs_error_incompatible_type") ) Output - Error: + Error in `vec_in()`: ! Can't combine `n$x$foo` and `h$x$foo` . diff --git a/tests/testthat/_snaps/match.md b/tests/testthat/_snaps/match.md index addaf3b78..6f02c044f 100644 --- a/tests/testthat/_snaps/match.md +++ b/tests/testthat/_snaps/match.md @@ -1,10 +1,42 @@ +# must have at least 1 column to match + + Code + vec_locate_matches(data_frame(), data_frame()) + Condition + Error in `vec_locate_matches()`: + ! Must have at least 1 column to match on. + +--- + + Code + vec_locate_matches(data_frame(), data_frame(), call = call("foo")) + Condition + Error in `foo()`: + ! Must have at least 1 column to match on. + +# common type of `needles` and `haystack` is taken + + Code + vec_locate_matches(x, y) + Condition + Error in `vec_locate_matches()`: + ! Can't combine and . + +--- + + Code + vec_locate_matches(x, y, needles_arg = "x", call = call("foo")) + Condition + Error in `foo()`: + ! Can't combine `x` and . + # `incomplete` can error informatively Code (expect_error(vec_locate_matches(NA, 1, incomplete = "error"))) Output - Error in `stop_matches()`: + Error in `vec_locate_matches()`: ! No element can contain missing values. x The element at location 1 contains missing values. Code @@ -12,7 +44,15 @@ ) Output - Error in `stop_matches()`: + Error in `vec_locate_matches()`: + ! No element of `foo` can contain missing values. + x The element at location 1 contains missing values. + Code + (expect_error(vec_locate_matches(NA, 1, incomplete = "error", needles_arg = "foo", + call = call("fn")))) + Output + + Error in `fn()`: ! No element of `foo` can contain missing values. x The element at location 1 contains missing values. @@ -22,7 +62,7 @@ (expect_error(vec_locate_matches(1, 2, incomplete = 1.5))) Output - Error: + Error in `vec_locate_matches()`: ! Can't convert from `incomplete` to due to loss of precision. * Locations: 1 Code @@ -37,6 +77,12 @@ Error in `vec_locate_matches()`: ! `incomplete` must be one of: "compare", "match", "drop", or "error". + Code + (expect_error(vec_locate_matches(1, 2, incomplete = "x", call = call("fn")))) + Output + + Error in `vec_locate_matches()`: + ! `incomplete` must be one of: "compare", "match", "drop", or "error". # `multiple` can error informatively @@ -44,7 +90,7 @@ (expect_error(vec_locate_matches(1L, c(1L, 1L), multiple = "error"))) Output - Error in `stop_matches()`: + Error in `vec_locate_matches()`: ! Each element can match at most 1 observation. x The element at location 1 has multiple matches. Code @@ -52,7 +98,15 @@ needles_arg = "foo"))) Output - Error in `stop_matches()`: + Error in `vec_locate_matches()`: + ! Each element of `foo` can match at most 1 observation. + x The element at location 1 has multiple matches. + Code + (expect_error(vec_locate_matches(1L, c(1L, 1L), multiple = "error", + needles_arg = "foo", call = call("fn")))) + Output + + Error in `fn()`: ! Each element of `foo` can match at most 1 observation. x The element at location 1 has multiple matches. Code @@ -60,7 +114,7 @@ needles_arg = "foo", haystack_arg = "bar"))) Output - Error in `stop_matches()`: + Error in `vec_locate_matches()`: ! Each element of `foo` can match at most 1 observation from `bar`. x The element at location 1 has multiple matches. @@ -70,7 +124,7 @@ (expect_warning(vec_locate_matches(1L, c(1L, 1L), multiple = "warning"))) Output - Warning in `warn_matches()`: + Warning in `vec_locate_matches()`: Each element can match at most 1 observation. x The element at location 1 has multiple matches. Code @@ -78,7 +132,15 @@ needles_arg = "foo"))) Output - Warning in `warn_matches()`: + Warning in `vec_locate_matches()`: + Each element of `foo` can match at most 1 observation. + x The element at location 1 has multiple matches. + Code + (expect_warning(vec_locate_matches(1L, c(1L, 1L), multiple = "warning", + needles_arg = "foo", call = call("fn")))) + Output + + Warning in `fn()`: Each element of `foo` can match at most 1 observation. x The element at location 1 has multiple matches. Code @@ -86,17 +148,44 @@ needles_arg = "foo", haystack_arg = "bar"))) Output - Warning in `warn_matches()`: + Warning in `vec_locate_matches()`: Each element of `foo` can match at most 1 observation from `bar`. x The element at location 1 has multiple matches. +# `multiple` is validated + + Code + (expect_error(vec_locate_matches(1, 2, multiple = 1.5))) + Output + + Error in `vec_locate_matches()`: + ! `multiple` must be a string. + Code + (expect_error(vec_locate_matches(1, 2, multiple = c("first", "last")))) + Output + + Error in `vec_locate_matches()`: + ! `multiple` must be a string. + Code + (expect_error(vec_locate_matches(1, 2, multiple = "x"))) + Output + + Error in `vec_locate_matches()`: + ! `multiple` must be one of "all", "any", "first", "last", "warning", or "error". + Code + (expect_error(vec_locate_matches(1, 2, multiple = "x", call = call("fn")))) + Output + + Error in `vec_locate_matches()`: + ! `multiple` must be one of "all", "any", "first", "last", "warning", or "error". + # `no_match` can error informatively Code (expect_error(vec_locate_matches(1, 2, no_match = "error"))) Output - Error in `stop_matches()`: + Error in `vec_locate_matches()`: ! Each element must have a match. x The element at location 1 does not have a match. Code @@ -104,7 +193,15 @@ ) Output - Error in `stop_matches()`: + Error in `vec_locate_matches()`: + ! Each element of `foo` must have a match. + x The element at location 1 does not have a match. + Code + (expect_error(vec_locate_matches(1, 2, no_match = "error", needles_arg = "foo", + call = call("fn")))) + Output + + Error in `fn()`: ! Each element of `foo` must have a match. x The element at location 1 does not have a match. Code @@ -112,7 +209,7 @@ haystack_arg = "bar"))) Output - Error in `stop_matches()`: + Error in `vec_locate_matches()`: ! Each element of `foo` must have a match in `bar`. x The element at location 1 does not have a match. @@ -123,7 +220,7 @@ ) Output - Error in `stop_matches()`: + Error in `vec_locate_matches()`: ! Each element must have a match. x The element at location 2 does not have a match. @@ -133,7 +230,7 @@ (expect_error(vec_locate_matches(1, 2, no_match = 1.5))) Output - Error: + Error in `vec_locate_matches()`: ! Can't convert from `no_match` to due to loss of precision. * Locations: 1 Code @@ -148,6 +245,12 @@ Error in `vec_locate_matches()`: ! `no_match` must be either "drop" or "error". + Code + (expect_error(vec_locate_matches(1, 2, no_match = "x", call = call("fn")))) + Output + + Error in `vec_locate_matches()`: + ! `no_match` must be either "drop" or "error". # `remaining` can error informatively @@ -155,7 +258,7 @@ (expect_error(vec_locate_matches(1, 2, remaining = "error"))) Output - Error in `stop_matches()`: + Error in `vec_locate_matches()`: ! Each haystack value must be matched. x The value at location 1 was not matched. Code @@ -163,7 +266,15 @@ ) Output - Error in `stop_matches()`: + Error in `vec_locate_matches()`: + ! Each haystack value must be matched by `foo`. + x The value at location 1 was not matched. + Code + (expect_error(vec_locate_matches(1, 2, remaining = "error", needles_arg = "foo", + call = call("fn")))) + Output + + Error in `fn()`: ! Each haystack value must be matched by `foo`. x The value at location 1 was not matched. Code @@ -171,7 +282,7 @@ haystack_arg = "bar"))) Output - Error in `stop_matches()`: + Error in `vec_locate_matches()`: ! Each haystack value of `bar` must be matched by `foo`. x The value at location 1 was not matched. @@ -181,7 +292,7 @@ (expect_error(vec_locate_matches(1, 2, remaining = 1.5))) Output - Error: + Error in `vec_locate_matches()`: ! Can't convert from `remaining` to due to loss of precision. * Locations: 1 Code @@ -196,6 +307,12 @@ Error in `vec_locate_matches()`: ! `remaining` must be either "drop" or "error". + Code + (expect_error(vec_locate_matches(1, 2, remaining = "x", call = call("fn")))) + Output + + Error in `vec_locate_matches()`: + ! `remaining` must be either "drop" or "error". # potential overflow on large output size is caught informatively @@ -204,5 +321,7 @@ Output Error in `vec_locate_matches()`: - ! Match procedure results in an allocation larger than 2^31-1 elements. Attempted allocation size was 50000005000000. Please report this to the vctrs maintainers at . + ! Match procedure results in an allocation larger than 2^31-1 elements. Attempted allocation size was 50000005000000. + i In file 'match.c' at line . + i This is an internal error in the vctrs package, please report it to the package authors. diff --git a/tests/testthat/helper-expectations.R b/tests/testthat/helper-expectations.R index bfdd9c28f..7eea2948c 100644 --- a/tests/testthat/helper-expectations.R +++ b/tests/testthat/helper-expectations.R @@ -101,3 +101,8 @@ expect_df_fallback_warning_maybe <- function(expr) { expr } } + +scrub_internal_error_line_number <- function(x) { + # Because it varies by OS + sub(pattern = "at line [[:digit:]]+", replacement = "at line ", x = x) +} diff --git a/tests/testthat/test-match.R b/tests/testthat/test-match.R index d2a05530b..0b7cb984e 100644 --- a/tests/testthat/test-match.R +++ b/tests/testthat/test-match.R @@ -390,6 +390,15 @@ test_that("df-cols aren't flattened, so `condition` is applied jointly on the df expect_identical(res$haystack, 1L) }) +test_that("must have at least 1 column to match", { + expect_snapshot(error = TRUE, { + vec_locate_matches(data_frame(), data_frame()) + }) + expect_snapshot(error = TRUE, { + vec_locate_matches(data_frame(), data_frame(), call = call("foo")) + }) +}) + # ------------------------------------------------------------------------------ # vec_locate_matches() - rcrd @@ -524,6 +533,21 @@ test_that("AsIs types are combined before order proxies are taken (#1557)", { expect_identical(res$haystack, c(2L, 3L, NA)) }) +# ------------------------------------------------------------------------------ +# vec_locate_matches() - ptype2 / casting + +test_that("common type of `needles` and `haystack` is taken", { + x <- 1 + y <- "a" + + expect_snapshot(error = TRUE, { + vec_locate_matches(x, y) + }) + expect_snapshot(error = TRUE, { + vec_locate_matches(x, y, needles_arg = "x", call = call("foo")) + }) +}) + # ------------------------------------------------------------------------------ # vec_locate_matches() - missing values @@ -793,6 +817,7 @@ test_that("`incomplete` can error informatively", { expect_snapshot({ (expect_error(vec_locate_matches(NA, 1, incomplete = "error"))) (expect_error(vec_locate_matches(NA, 1, incomplete = "error", needles_arg = "foo"))) + (expect_error(vec_locate_matches(NA, 1, incomplete = "error", needles_arg = "foo", call = call("fn")))) }) }) @@ -805,6 +830,8 @@ test_that("`incomplete` is validated", { (expect_error(vec_locate_matches(1, 2, incomplete = 1.5))) (expect_error(vec_locate_matches(1, 2, incomplete = c("match", "drop")))) (expect_error(vec_locate_matches(1, 2, incomplete = "x"))) + # Uses internal call + (expect_error(vec_locate_matches(1, 2, incomplete = "x", call = call("fn")))) }) }) @@ -882,6 +909,7 @@ test_that("`multiple` can error informatively", { expect_snapshot({ (expect_error(vec_locate_matches(1L, c(1L, 1L), multiple = "error"))) (expect_error(vec_locate_matches(1L, c(1L, 1L), multiple = "error", needles_arg = "foo"))) + (expect_error(vec_locate_matches(1L, c(1L, 1L), multiple = "error", needles_arg = "foo", call = call("fn")))) (expect_error(vec_locate_matches(1L, c(1L, 1L), multiple = "error", needles_arg = "foo", haystack_arg = "bar"))) }) }) @@ -890,6 +918,7 @@ test_that("`multiple` can warn informatively", { expect_snapshot({ (expect_warning(vec_locate_matches(1L, c(1L, 1L), multiple = "warning"))) (expect_warning(vec_locate_matches(1L, c(1L, 1L), multiple = "warning", needles_arg = "foo"))) + (expect_warning(vec_locate_matches(1L, c(1L, 1L), multiple = "warning", needles_arg = "foo", call = call("fn")))) (expect_warning(vec_locate_matches(1L, c(1L, 1L), multiple = "warning", needles_arg = "foo", haystack_arg = "bar"))) }) }) @@ -1000,9 +1029,13 @@ test_that("`multiple = 'error'` doesn't error errneously on the last observation }) test_that("`multiple` is validated", { - expect_error(vec_locate_matches(1, 2, multiple = 1.5), "`multiple` must be a string") - expect_error(vec_locate_matches(1, 2, multiple = c("first", "last")), "`multiple` must be a string") - expect_error(vec_locate_matches(1, 2, multiple = "x"), '`multiple` must be one of "all", "any", "first", "last", "warning", or "error"') + expect_snapshot({ + (expect_error(vec_locate_matches(1, 2, multiple = 1.5))) + (expect_error(vec_locate_matches(1, 2, multiple = c("first", "last")))) + (expect_error(vec_locate_matches(1, 2, multiple = "x"))) + # Uses internal error + (expect_error(vec_locate_matches(1, 2, multiple = "x", call = call("fn")))) + }) }) # ------------------------------------------------------------------------------ @@ -1047,6 +1080,7 @@ test_that("`no_match` can error informatively", { expect_snapshot({ (expect_error(vec_locate_matches(1, 2, no_match = "error"))) (expect_error(vec_locate_matches(1, 2, no_match = "error", needles_arg = "foo"))) + (expect_error(vec_locate_matches(1, 2, no_match = "error", needles_arg = "foo", call = call("fn")))) (expect_error(vec_locate_matches(1, 2, no_match = "error", needles_arg = "foo", haystack_arg = "bar"))) }) }) @@ -1080,6 +1114,8 @@ test_that("`no_match` is validated", { (expect_error(vec_locate_matches(1, 2, no_match = 1.5))) (expect_error(vec_locate_matches(1, 2, no_match = c(1L, 2L)))) (expect_error(vec_locate_matches(1, 2, no_match = "x"))) + # Uses internal call + (expect_error(vec_locate_matches(1, 2, no_match = "x", call = call("fn")))) }) }) @@ -1168,6 +1204,7 @@ test_that("`remaining` can error informatively", { expect_snapshot({ (expect_error(vec_locate_matches(1, 2, remaining = "error"))) (expect_error(vec_locate_matches(1, 2, remaining = "error", needles_arg = "foo"))) + (expect_error(vec_locate_matches(1, 2, remaining = "error", needles_arg = "foo", call = call("fn")))) (expect_error(vec_locate_matches(1, 2, remaining = "error", needles_arg = "foo", haystack_arg = "bar"))) }) }) @@ -1177,6 +1214,8 @@ test_that("`remaining` is validated", { (expect_error(vec_locate_matches(1, 2, remaining = 1.5))) (expect_error(vec_locate_matches(1, 2, remaining = c(1L, 2L)))) (expect_error(vec_locate_matches(1, 2, remaining = "x"))) + # Uses internal call + (expect_error(vec_locate_matches(1, 2, remaining = "x", call = call("fn")))) }) }) @@ -1398,7 +1437,7 @@ test_that("potential overflow on large output size is caught informatively", { # intermediate `r_ssize` will be too large skip_if(.Machine$sizeof.pointer < 8L, message = "No long vector support") - expect_snapshot({ + expect_snapshot(transform = scrub_internal_error_line_number, { (expect_error(vec_locate_matches(1:1e7, 1:1e7, condition = ">="))) }) }) From 78a97da7ddbda6543e1066a322da6b4093c98526 Mon Sep 17 00:00:00 2001 From: Davis Vaughan Date: Mon, 29 Aug 2022 10:26:02 -0400 Subject: [PATCH 002/312] Pass `.call` through `data_frame()` and `df_list()` (#1625) * Pass `.call` through `data_frame()` and `df_list()` Using the following signatures based on how we feel they are used in practice: - `data_frame(.call = current_env())` - `df_list(.call = caller_env())` * NEWS bullet * Use `current_env()` in `df_list()` --- NEWS.md | 2 ++ R/type-data-frame.R | 10 ++++++-- man/data_frame.Rd | 8 ++++++- man/df_list.Rd | 8 ++++++- src/type-data-frame.c | 4 ++-- tests/testthat/_snaps/type-data-frame.md | 30 ++++++++++++++++++++++++ tests/testthat/test-type-data-frame.R | 4 ++++ 7 files changed, 60 insertions(+), 6 deletions(-) diff --git a/NEWS.md b/NEWS.md index cc5d7de75..242090fd7 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,5 +1,7 @@ # vctrs (development version) +* `data_frame()` and `df_list()` have gained `.call` arguments (#1610). + * `vec_locate_matches()` has gained a `call` argument (#1611). * `"select"` and `"relocate"` have been added as valid subscript actions to diff --git a/R/type-data-frame.R b/R/type-data-frame.R index 815e46e0a..2883201c0 100644 --- a/R/type-data-frame.R +++ b/R/type-data-frame.R @@ -59,6 +59,8 @@ new_data_frame <- fn_inline_formals(new_data_frame, "x") #' [new_data_frame()] for constructing data frame subclasses from a validated #' input. [data_frame()] for a fast data frame creation helper. #' +#' @inheritParams rlang::args_error_context +#' #' @param ... Vectors of equal-length. When inputs are named, those names #' are used for names of the resulting list. #' @param .size The common size of vectors supplied in `...`. If `NULL`, this @@ -87,7 +89,8 @@ new_data_frame <- fn_inline_formals(new_data_frame, "x") df_list <- function(..., .size = NULL, .unpack = TRUE, - .name_repair = c("check_unique", "unique", "universal", "minimal")) { + .name_repair = c("check_unique", "unique", "universal", "minimal"), + .call = current_env()) { .Call(ffi_df_list, list2(...), .size, .unpack, .name_repair, environment()) } df_list <- fn_inline_formals(df_list, ".name_repair") @@ -116,6 +119,8 @@ df_list <- fn_inline_formals(df_list, ".name_repair") #' for developers when creating new data frame subclasses supporting #' standard evaluation. #' +#' @inheritParams rlang::args_error_context +#' #' @param ... Vectors to become columns in the data frame. When inputs are #' named, those names are used for column names. #' @param .size The number of rows in the data frame. If `NULL`, this will @@ -158,7 +163,8 @@ df_list <- fn_inline_formals(df_list, ".name_repair") #' data_frame(x = 1, data_frame(y = 1:2, z = "a")) data_frame <- function(..., .size = NULL, - .name_repair = c("check_unique", "unique", "universal", "minimal")) { + .name_repair = c("check_unique", "unique", "universal", "minimal"), + .call = current_env()) { .Call(ffi_data_frame, list2(...), .size, .name_repair, environment()) } data_frame <- fn_inline_formals(data_frame, ".name_repair") diff --git a/man/data_frame.Rd b/man/data_frame.Rd index 37921c466..605224883 100644 --- a/man/data_frame.Rd +++ b/man/data_frame.Rd @@ -7,7 +7,8 @@ data_frame( ..., .size = NULL, - .name_repair = c("check_unique", "unique", "universal", "minimal") + .name_repair = c("check_unique", "unique", "universal", "minimal"), + .call = current_env() ) } \arguments{ @@ -19,6 +20,11 @@ be computed as the common size of the inputs.} \item{.name_repair}{One of \code{"check_unique"}, \code{"unique"}, \code{"universal"} or \code{"minimal"}. See \code{\link[=vec_as_names]{vec_as_names()}} for the meaning of these options.} + +\item{.call}{The execution environment of a currently +running function, e.g. \code{caller_env()}. The function will be +mentioned in error messages as the source of the error. See the +\code{call} argument of \code{\link[rlang:abort]{abort()}} for more information.} } \description{ \code{data_frame()} constructs a data frame. It is similar to diff --git a/man/df_list.Rd b/man/df_list.Rd index e0739786a..2fa85388f 100644 --- a/man/df_list.Rd +++ b/man/df_list.Rd @@ -8,7 +8,8 @@ df_list( ..., .size = NULL, .unpack = TRUE, - .name_repair = c("check_unique", "unique", "universal", "minimal") + .name_repair = c("check_unique", "unique", "universal", "minimal"), + .call = current_env() ) } \arguments{ @@ -23,6 +24,11 @@ will be computed as the common size of the inputs.} \item{.name_repair}{One of \code{"check_unique"}, \code{"unique"}, \code{"universal"} or \code{"minimal"}. See \code{\link[=vec_as_names]{vec_as_names()}} for the meaning of these options.} + +\item{.call}{The execution environment of a currently +running function, e.g. \code{caller_env()}. The function will be +mentioned in error messages as the source of the error. See the +\code{call} argument of \code{\link[rlang:abort]{abort()}} for more information.} } \description{ \code{df_list()} constructs the data structure underlying a data diff --git a/src/type-data-frame.c b/src/type-data-frame.c index b1fd81807..c189427c4 100644 --- a/src/type-data-frame.c +++ b/src/type-data-frame.c @@ -175,7 +175,7 @@ r_obj* ffi_data_frame(r_obj* x, r_obj* size, r_obj* name_repair, r_obj* frame) { - struct r_lazy call = { .x = frame, .env = r_null }; + struct r_lazy call = { .x = syms_dot_call, .env = frame }; struct name_repair_opts name_repair_opts = new_name_repair_opts(name_repair, vec_args.dot_name_repair, @@ -215,7 +215,7 @@ r_obj* ffi_df_list(r_obj* x, r_obj* unpack, r_obj* name_repair, r_obj* frame) { - struct r_lazy call = { .x = frame, .env = r_null }; + struct r_lazy call = { .x = syms_dot_call, .env = frame }; struct name_repair_opts name_repair_opts = new_name_repair_opts(name_repair, vec_args.dot_name_repair, diff --git a/tests/testthat/_snaps/type-data-frame.md b/tests/testthat/_snaps/type-data-frame.md index de0b04866..c92043676 100644 --- a/tests/testthat/_snaps/type-data-frame.md +++ b/tests/testthat/_snaps/type-data-frame.md @@ -163,12 +163,27 @@ x These names are duplicated: * "a" at locations 1 and 2. i Use argument `.name_repair` to specify repair strategy. + Code + (expect_error(data_frame(a = 1, a = 1, .call = call("foo")))) + Output + + Error in `foo()`: + ! Names must be unique. + x These names are duplicated: + * "a" at locations 1 and 2. + i Use argument `.name_repair` to specify repair strategy. Code (expect_error(data_frame(a = 1:2, b = int()))) Output Error in `data_frame()`: ! Can't recycle `a` (size 2) to match `b` (size 0). + Code + (expect_error(data_frame(a = 1:2, b = int(), .call = call("foo")))) + Output + + Error in `foo()`: + ! Can't recycle `a` (size 2) to match `b` (size 0). Code (expect_error(df_list(a = 1, a = 1))) Output @@ -178,12 +193,27 @@ x These names are duplicated: * "a" at locations 1 and 2. i Use argument `.name_repair` to specify repair strategy. + Code + (expect_error(df_list(a = 1, a = 1, .call = call("foo")))) + Output + + Error in `foo()`: + ! Names must be unique. + x These names are duplicated: + * "a" at locations 1 and 2. + i Use argument `.name_repair` to specify repair strategy. Code (expect_error(df_list(a = 1:2, b = int()))) Output Error in `df_list()`: ! Can't recycle `a` (size 2) to match `b` (size 0). + Code + (expect_error(df_list(a = 1:2, b = int(), .call = call("foo")))) + Output + + Error in `foo()`: + ! Can't recycle `a` (size 2) to match `b` (size 0). # input is tidy recycled diff --git a/tests/testthat/test-type-data-frame.R b/tests/testthat/test-type-data-frame.R index ae5f1eb53..ce64d5ff9 100644 --- a/tests/testthat/test-type-data-frame.R +++ b/tests/testthat/test-type-data-frame.R @@ -448,10 +448,14 @@ test_that("new_data_frame() zaps existing attributes", { test_that("data_frame() and df_list() report error context", { expect_snapshot({ (expect_error(data_frame(a = 1, a = 1))) + (expect_error(data_frame(a = 1, a = 1, .call = call("foo")))) (expect_error(data_frame(a = 1:2, b = int()))) + (expect_error(data_frame(a = 1:2, b = int(), .call = call("foo")))) (expect_error(df_list(a = 1, a = 1))) + (expect_error(df_list(a = 1, a = 1, .call = call("foo")))) (expect_error(df_list(a = 1:2, b = int()))) + (expect_error(df_list(a = 1:2, b = int(), .call = call("foo")))) }) }) From 3efc2cfa733853c9904d50fc6e6840418c4baf50 Mon Sep 17 00:00:00 2001 From: Davis Vaughan Date: Tue, 30 Aug 2022 09:30:13 -0400 Subject: [PATCH 003/312] Ensure `zero = "error"` errors when inverting negatives (#1628) * Ensure `zero = "error"` errors when inverting negatives * NEWS bullet --- NEWS.md | 3 +++ src/subscript-loc.c | 6 +++++- tests/testthat/_snaps/subscript-loc.md | 20 ++++++++++++++++++++ tests/testthat/test-subscript-loc.R | 25 +++++++++++++++++++++++++ 4 files changed, 53 insertions(+), 1 deletion(-) diff --git a/NEWS.md b/NEWS.md index 242090fd7..6c972cc8b 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,5 +1,8 @@ # vctrs (development version) +* `num_as_location()` now works correctly when a combination of `zero = "error"` + and `negative = "invert"` are used (#1612). + * `data_frame()` and `df_list()` have gained `.call` arguments (#1610). * `vec_locate_matches()` has gained a `call` argument (#1611). diff --git a/src/subscript-loc.c b/src/subscript-loc.c index 43a7f6abf..20db69170 100644 --- a/src/subscript-loc.c +++ b/src/subscript-loc.c @@ -216,7 +216,11 @@ r_obj* int_invert_location(r_obj* subscript, } if (j >= 0) { if (j == 0) { - continue; + switch (opts->loc_zero) { + case LOC_ZERO_REMOVE: continue; + case LOC_ZERO_IGNORE: continue; + case LOC_ZERO_ERROR: stop_location_zero(subscript, opts); + } } else { stop_location_negative_positive(subscript, opts); } diff --git a/tests/testthat/_snaps/subscript-loc.md b/tests/testthat/_snaps/subscript-loc.md index d94da357f..7205483c4 100644 --- a/tests/testthat/_snaps/subscript-loc.md +++ b/tests/testthat/_snaps/subscript-loc.md @@ -531,6 +531,26 @@ i Location 4 doesn't exist. i There are only 3 elements. +# num_as_location() errors on disallowed zeros when inverting negatives (#1612) + + Code + num_as_location(c(0, -1), n = 2L, negative = "invert", zero = "error") + Condition + Error: + ! Must subset elements with a valid subscript vector. + x Subscript `c(0, -1)` can't contain `0` values. + i It has a `0` value at location 1. + +--- + + Code + num_as_location(c(-1, 0), n = 2L, negative = "invert", zero = "error") + Condition + Error: + ! Must subset elements with a valid subscript vector. + x Subscript `c(-1, 0)` can't contain `0` values. + i It has a `0` value at location 2. + # missing values are supported in error formatters Code diff --git a/tests/testthat/test-subscript-loc.R b/tests/testthat/test-subscript-loc.R index 7b8b4b532..1999a252a 100644 --- a/tests/testthat/test-subscript-loc.R +++ b/tests/testthat/test-subscript-loc.R @@ -298,6 +298,31 @@ test_that("num_as_location() errors when inverting oob negatives unless `oob = ' expect_identical(num_as_location(c(-4, -2), 3, oob = "remove", negative = "invert"), c(1L, 3L)) }) +test_that("num_as_location() generally drops zeros when inverting negatives (#1612)", { + expect_identical( + num_as_location(c(-3, 0, -1), n = 5L, negative = "invert", zero = "remove"), + c(2L, 4L, 5L) + ) + + # Trying to "ignore" and retain the zeroes in the output doesn't make sense, + # where would they be placed? Instead, think of the ignored zeros as being + # inverted as well, they just don't correspond to any location after the + # inversion so they aren't in the output. + expect_identical( + num_as_location(c(-3, 0, -1, 0), n = 5L, negative = "invert", zero = "ignore"), + c(2L, 4L, 5L) + ) +}) + +test_that("num_as_location() errors on disallowed zeros when inverting negatives (#1612)", { + expect_snapshot(error = TRUE, { + num_as_location(c(0, -1), n = 2L, negative = "invert", zero = "error") + }) + expect_snapshot(error = TRUE, { + num_as_location(c(-1, 0), n = 2L, negative = "invert", zero = "error") + }) +}) + test_that("num_as_location() with `oob = 'remove'` doesn't remove missings if they are being propagated", { expect_identical(num_as_location(NA_integer_, 1, oob = "remove"), NA_integer_) }) From c70a7b457214715f18c0cd1c841490a77f28b8cb Mon Sep 17 00:00:00 2001 From: Davis Vaughan Date: Tue, 30 Aug 2022 09:39:14 -0400 Subject: [PATCH 004/312] Correctly error on `"ignore"`d oob negative values (#1631) * Correctly error on `"ignore"`d oob negative values * NEWS bullet --- NEWS.md | 4 ++ R/subscript-loc.R | 11 ++++-- src/decl/subscript-loc-decl.h | 4 ++ src/subscript-loc.c | 55 +++++++++++++++----------- tests/testthat/_snaps/subscript-loc.md | 44 ++++++++++++++++++++- tests/testthat/test-subscript-loc.R | 27 ++++++++++++- 6 files changed, 116 insertions(+), 29 deletions(-) diff --git a/NEWS.md b/NEWS.md index 6c972cc8b..06ee25597 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,5 +1,9 @@ # vctrs (development version) +* `num_as_location()` now throws the right error when there are out-of-bounds + negative values and `oob = "extend"` and `negative = "ignore"` are set + (#1614, #1630). + * `num_as_location()` now works correctly when a combination of `zero = "error"` and `negative = "invert"` are used (#1612). diff --git a/R/subscript-loc.R b/R/subscript-loc.R index 46037121e..d34e8161e 100644 --- a/R/subscript-loc.R +++ b/R/subscript-loc.R @@ -481,12 +481,17 @@ cnd_body.vctrs_error_subscript_oob <- function(cnd, ...) { cnd_body_vctrs_error_subscript_oob_location <- function(cnd, ...) { i <- cnd$i - # In case of negative indexing - i <- abs(i) - # In case of missing locations i <- i[!is.na(i)] + if (cnd_subscript_action(cnd) == "negate") { + # Only report negative indices + i <- i[i < 0L] + } + + # In case of negative indexing + i <- abs(i) + oob <- i[i > cnd$size] oob_enum <- vctrs_cli_vec(oob) diff --git a/src/decl/subscript-loc-decl.h b/src/decl/subscript-loc-decl.h index 463bb8c69..6e4276f20 100644 --- a/src/decl/subscript-loc-decl.h +++ b/src/decl/subscript-loc-decl.h @@ -43,6 +43,10 @@ void stop_subscript_oob_location(r_obj* i, r_ssize size, const struct location_opts* opts); static +void stop_subscript_negative_oob_location(r_obj* i, + r_ssize size, + const struct location_opts* opts); +static void stop_subscript_oob_name(r_obj* i, r_obj* names, const struct location_opts* opts); diff --git a/src/subscript-loc.c b/src/subscript-loc.c index 20db69170..b945dabb5 100644 --- a/src/subscript-loc.c +++ b/src/subscript-loc.c @@ -142,27 +142,32 @@ r_obj* int_as_location(r_obj* subscript, if (opts->missing == SUBSCRIPT_MISSING_ERROR) { stop_subscript_missing(subscript, opts); } - } else { - if (elt < 0) { - switch (opts->loc_negative) { - case LOC_NEGATIVE_INVERT: return int_invert_location(subscript, n, opts); - case LOC_NEGATIVE_ERROR: stop_location_negative(subscript, opts); - case LOC_NEGATIVE_IGNORE: break; - } + } else if (elt == 0) { + switch (opts->loc_zero) { + case LOC_ZERO_REMOVE: ++n_zero; break; + case LOC_ZERO_ERROR: stop_location_zero(subscript, opts); + case LOC_ZERO_IGNORE: break; } - - if (elt == 0) { - switch (opts->loc_zero) { - case LOC_ZERO_REMOVE: ++n_zero; break; - case LOC_ZERO_ERROR: stop_location_zero(subscript, opts); - case LOC_ZERO_IGNORE: break; - } - } else if (abs(elt) > n) { - switch (opts->loc_oob) { - case LOC_OOB_ERROR: stop_subscript_oob_location(subscript, n, opts); - case LOC_OOB_EXTEND: - case LOC_OOB_REMOVE: ++n_oob; break; + } else if (elt < 0) { + switch (opts->loc_negative) { + case LOC_NEGATIVE_INVERT: return int_invert_location(subscript, n, opts); + case LOC_NEGATIVE_ERROR: stop_location_negative(subscript, opts); + case LOC_NEGATIVE_IGNORE: { + if (abs(elt) > n) { + switch (opts->loc_oob) { + case LOC_OOB_ERROR: stop_subscript_oob_location(subscript, n, opts); + case LOC_OOB_EXTEND: stop_subscript_negative_oob_location(subscript, n, opts); + case LOC_OOB_REMOVE: ++n_oob; break; + } } + break; + } + } + } else if (elt > n) { + switch (opts->loc_oob) { + case LOC_OOB_ERROR: stop_subscript_oob_location(subscript, n, opts); + case LOC_OOB_EXTEND: ++n_oob; break; + case LOC_OOB_REMOVE: ++n_oob; break; } } } @@ -236,9 +241,7 @@ r_obj* int_invert_location(r_obj* subscript, case LOC_OOB_ERROR: { // Setting `oob` to `"error"` and `"extend"` result in errors here, // because extending with a negative subscript is nonsensical - struct location_opts updated_opts = *opts; - updated_opts.subscript_opts.action = SUBSCRIPT_ACTION_NEGATE; - stop_subscript_oob_location(subscript, n, &updated_opts); + stop_subscript_negative_oob_location(subscript, n, opts); } } } @@ -593,6 +596,14 @@ void stop_subscript_oob_location(r_obj* i, r_stop_unreachable(); } static +void stop_subscript_negative_oob_location(r_obj* i, + r_ssize size, + const struct location_opts* opts) { + struct location_opts error_opts = *opts; + error_opts.subscript_opts.action = SUBSCRIPT_ACTION_NEGATE; + stop_subscript_oob_location(i, size, &error_opts); +} +static void stop_subscript_oob_name(r_obj* i, r_obj* names, const struct location_opts* opts) { diff --git a/tests/testthat/_snaps/subscript-loc.md b/tests/testthat/_snaps/subscript-loc.md index 7205483c4..a749ef8c9 100644 --- a/tests/testthat/_snaps/subscript-loc.md +++ b/tests/testthat/_snaps/subscript-loc.md @@ -511,7 +511,7 @@ i Input has size 3. x Subscript `c(1:5, 7, 1, 10)` contains non-consecutive locations 4, 7, and 10. -# num_as_location() errors when inverting oob negatives unless `oob = 'remove'` +# num_as_location() errors when inverting oob negatives unless `oob = 'remove'` (#1630) Code num_as_location(-4, 3, oob = "error", negative = "invert") @@ -524,7 +524,7 @@ --- Code - num_as_location(-4, 3, oob = "extend", negative = "invert") + num_as_location(c(-4, 4, 5), 3, oob = "extend", negative = "invert") Condition Error: ! Can't negate elements past the end. @@ -551,6 +551,46 @@ x Subscript `c(-1, 0)` can't contain `0` values. i It has a `0` value at location 2. +# num_as_location() with `oob = 'extend'` doesn't allow ignored oob negative values (#1614) + + Code + num_as_location(-6L, 5L, oob = "extend", negative = "ignore") + Condition + Error: + ! Can't negate elements past the end. + i Location 6 doesn't exist. + i There are only 5 elements. + +--- + + Code + num_as_location(c(-7L, 6L), 5L, oob = "extend", negative = "ignore") + Condition + Error: + ! Can't negate elements past the end. + i Location 7 doesn't exist. + i There are only 5 elements. + +--- + + Code + num_as_location(c(-7L, NA), 5L, oob = "extend", negative = "ignore") + Condition + Error: + ! Can't negate elements past the end. + i Location 7 doesn't exist. + i There are only 5 elements. + +# num_as_location() with `oob = 'error'` reports negative and positive oob values + + Code + num_as_location(c(-6L, 7L), n = 5L, oob = "error", negative = "ignore") + Condition + Error: + ! Can't subset elements past the end. + i Locations 6 and 7 don't exist. + i There are only 5 elements. + # missing values are supported in error formatters Code diff --git a/tests/testthat/test-subscript-loc.R b/tests/testthat/test-subscript-loc.R index 1999a252a..3a7f9516a 100644 --- a/tests/testthat/test-subscript-loc.R +++ b/tests/testthat/test-subscript-loc.R @@ -287,12 +287,12 @@ test_that("num_as_location() can optionally remove oob values (#1595)", { expect_identical(num_as_location(c(-4, 5, 2, -1), 3, oob = "remove", negative = "ignore"), c(2L, -1L)) }) -test_that("num_as_location() errors when inverting oob negatives unless `oob = 'remove'`", { +test_that("num_as_location() errors when inverting oob negatives unless `oob = 'remove'` (#1630)", { expect_snapshot(error = TRUE, { num_as_location(-4, 3, oob = "error", negative = "invert") }) expect_snapshot(error = TRUE, { - num_as_location(-4, 3, oob = "extend", negative = "invert") + num_as_location(c(-4, 4, 5), 3, oob = "extend", negative = "invert") }) expect_identical(num_as_location(-4, 3, oob = "remove", negative = "invert"), c(1L, 2L, 3L)) expect_identical(num_as_location(c(-4, -2), 3, oob = "remove", negative = "invert"), c(1L, 3L)) @@ -332,6 +332,29 @@ test_that("num_as_location() with `oob = 'remove'` doesn't remove zeros if they expect_identical(num_as_location(0, 0, oob = "remove", zero = "ignore"), 0L) }) +test_that("num_as_location() with `oob = 'extend'` doesn't allow ignored oob negative values (#1614)", { + # This is fine (ignored negative that is in bounds) + expect_identical(num_as_location(c(-5L, 6L), 5L, oob = "extend", negative = "ignore"), c(-5L, 6L)) + + expect_snapshot(error = TRUE, { + # Ignored negatives aren't allowed to extend the vector + num_as_location(-6L, 5L, oob = "extend", negative = "ignore") + }) + expect_snapshot(error = TRUE, { + # Ensure error only reports negative indices + num_as_location(c(-7L, 6L), 5L, oob = "extend", negative = "ignore") + }) + expect_snapshot(error = TRUE, { + num_as_location(c(-7L, NA), 5L, oob = "extend", negative = "ignore") + }) +}) + +test_that("num_as_location() with `oob = 'error'` reports negative and positive oob values", { + expect_snapshot(error = TRUE, { + num_as_location(c(-6L, 7L), n = 5L, oob = "error", negative = "ignore") + }) +}) + test_that("missing values are supported in error formatters", { expect_snapshot({ (expect_error( From a34f4ef10498d54b818727c7294c3e05c54764c3 Mon Sep 17 00:00:00 2001 From: Davis Vaughan Date: Tue, 30 Aug 2022 15:55:07 -0400 Subject: [PATCH 005/312] Redocument (#1634) --- man/faq-compatibility-types.Rd | 10 +++++----- man/howto-faq-coercion-data-frame.Rd | 10 +++++----- man/reference-faq-compatibility.Rd | 17 ++++++++--------- man/theory-faq-coercion.Rd | 22 +++++++++++----------- 4 files changed, 29 insertions(+), 30 deletions(-) diff --git a/man/faq-compatibility-types.Rd b/man/faq-compatibility-types.Rd index 63f6e2c17..5b632a491 100644 --- a/man/faq-compatibility-types.Rd +++ b/man/faq-compatibility-types.Rd @@ -17,8 +17,8 @@ other hand, integer and character vectors are not compatible. There are two possible outcomes when multiple vectors of different types are combined into a larger vector: \itemize{ -\item An incompatible type error is thrown because some of the types are -not compatible: +\item An incompatible type error is thrown because some of the types are not +compatible: \if{html}{\out{
}}\preformatted{df1 <- data.frame(x = 1:3) df2 <- data.frame(x = "foo") @@ -26,9 +26,9 @@ dplyr::bind_rows(df1, df2) #> Error in `dplyr::bind_rows()`: #> ! Can't combine `..1$x` and `..2$x` . }\if{html}{\out{
}} -\item The vectors are combined into a vector that has the common type of -all inputs. In this example, the common type of integer and logical -is integer: +\item The vectors are combined into a vector that has the common type of all +inputs. In this example, the common type of integer and logical is +integer: \if{html}{\out{
}}\preformatted{df1 <- data.frame(x = 1:3) df2 <- data.frame(x = FALSE) diff --git a/man/howto-faq-coercion-data-frame.Rd b/man/howto-faq-coercion-data-frame.Rd index 07660f93b..9e94c7d33 100644 --- a/man/howto-faq-coercion-data-frame.Rd +++ b/man/howto-faq-coercion-data-frame.Rd @@ -244,12 +244,12 @@ constant group. The coercion methods for data frames operate in two steps: \itemize{ -\item They check for compatible subclass attributes. In our case the -tibble colour has to be the same, or be undefined. +\item They check for compatible subclass attributes. In our case the tibble +colour has to be the same, or be undefined. \item They call their parent methods, in this case -\code{\link[=tib_ptype2]{tib_ptype2()}} and \code{\link[=tib_cast]{tib_cast()}} -because we have a subclass of tibble. This eventually calls the data -frame methods \code{\link[=df_ptype2]{df_ptype2()}} and +\code{\link[=tib_ptype2]{tib_ptype2()}} and \code{\link[=tib_cast]{tib_cast()}} because +we have a subclass of tibble. This eventually calls the data frame +methods \code{\link[=df_ptype2]{df_ptype2()}} and \code{\link[=tib_ptype2]{tib_ptype2()}} which match the columns and their types. } diff --git a/man/reference-faq-compatibility.Rd b/man/reference-faq-compatibility.Rd index fe19bdc2e..4ee6bd2de 100644 --- a/man/reference-faq-compatibility.Rd +++ b/man/reference-faq-compatibility.Rd @@ -21,15 +21,14 @@ the next section. However there are many higher level operations. The most important ones implement fallbacks to base generics for maximum compatibility with existing classes. \itemize{ -\item \code{\link[=vec_slice]{vec_slice()}} falls back to the base \code{[} generic if -no \code{\link[=vec_proxy]{vec_proxy()}} method is implemented. This way -foreign classes that do not implement -\code{\link[=vec_restore]{vec_restore()}} can restore attributes based on the -new subsetted contents. -\item \code{\link[=vec_c]{vec_c()}} and \code{\link[=vec_rbind]{vec_rbind()}} now fall back -to \code{\link[base:c]{base::c()}} if the inputs have a common parent class -with a \code{c()} method (only if they have no self-to-self -\code{vec_ptype2()} method). +\item \code{\link[=vec_slice]{vec_slice()}} falls back to the base \code{[} generic if no +\code{\link[=vec_proxy]{vec_proxy()}} method is implemented. This way foreign +classes that do not implement \code{\link[=vec_restore]{vec_restore()}} can +restore attributes based on the new subsetted contents. +\item \code{\link[=vec_c]{vec_c()}} and \code{\link[=vec_rbind]{vec_rbind()}} now fall back to +\code{\link[base:c]{base::c()}} if the inputs have a common parent class with +a \code{c()} method (only if they have no self-to-self \code{vec_ptype2()} +method). vctrs works hard to make your \code{c()} method success in various situations (with \code{NULL} and \code{NA} inputs, even as first input which diff --git a/man/theory-faq-coercion.Rd b/man/theory-faq-coercion.Rd index 2463b8660..66974df70 100644 --- a/man/theory-faq-coercion.Rd +++ b/man/theory-faq-coercion.Rd @@ -74,9 +74,9 @@ steps, which require \code{vec_ptype2()} and \code{vec_cast()} implementations. Methods for \code{vec_ptype2()} are passed two \emph{prototypes}, i.e. two inputs emptied of their elements. They implement two behaviours: \itemize{ -\item If the types of their inputs are compatible, indicate which of them -is the richer type by returning it. If the types are of equal -resolution, return any of the two. +\item If the types of their inputs are compatible, indicate which of them is +the richer type by returning it. If the types are of equal resolution, +return any of the two. \item Throw an error with \code{stop_incompatible_type()} when it can be determined from the attributes that the types of the inputs are not compatible. @@ -193,14 +193,14 @@ in more cases. \code{vec_cast()} has three possible behaviours: This must be decided in exactly the same way as for \code{vec_ptype2()}. Call \code{stop_incompatible_cast()} if you can determine from the attributes that the types are not compatible. -\item Detect incompatible values. Usually this is because the target type -is too restricted for the values supported by the input type. For +\item Detect incompatible values. Usually this is because the target type is +too restricted for the values supported by the input type. For example, a fractional number can’t be converted to an integer. The method should throw an error in that case. -\item Return the input vector converted to the target type if all values -are compatible. Whereas \code{vec_ptype2()} must return the same type -when the inputs are permuted, \code{vec_cast()} is \emph{directional}. It -always returns the type of the right-hand side, or dies trying. +\item Return the input vector converted to the target type if all values are +compatible. Whereas \code{vec_ptype2()} must return the same type when the +inputs are permuted, \code{vec_cast()} is \emph{directional}. It always returns +the type of the right-hand side, or dies trying. } } @@ -214,8 +214,8 @@ differences: \item There is no inheritance of ptype2 and cast methods. This is because the S3 class hierarchy is not necessarily the same as the coercion hierarchy. -\item \code{NextMethod()} does not work. Parent methods must be called -explicitly if necessary. +\item \code{NextMethod()} does not work. Parent methods must be called explicitly +if necessary. \item The default method is hard-coded. } } From c2a7710fe55e3a2249c4fdfe75bbccbafcf38804 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Wed, 31 Aug 2022 17:44:05 +0200 Subject: [PATCH 006/312] Export `vec_rank()` (#1621) * Export vec_rank() * Show in pkgdown * Use original NEWS bullet Co-authored-by: DavisVaughan --- NAMESPACE | 1 + NEWS.md | 2 + R/rank.R | 7 +-- _pkgdown.yml | 1 + man/vec_rank.Rd | 146 ++++++++++++++++++++++++++++++++++++++++++++++++ 5 files changed, 151 insertions(+), 6 deletions(-) create mode 100644 man/vec_rank.Rd diff --git a/NAMESPACE b/NAMESPACE index 659063f4f..26a82a31d 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -601,6 +601,7 @@ export(vec_ptype_common) export(vec_ptype_finalise) export(vec_ptype_full) export(vec_ptype_show) +export(vec_rank) export(vec_rbind) export(vec_recycle) export(vec_recycle_common) diff --git a/NEWS.md b/NEWS.md index 06ee25597..38a7f52cf 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,5 +1,7 @@ # vctrs (development version) +* New `vec_rank()` to compute various types of sample ranks (#1600). + * `num_as_location()` now throws the right error when there are out-of-bounds negative values and `oob = "extend"` and `negative = "ignore"` are set (#1614, #1630). diff --git a/R/rank.R b/R/rank.R index 81ddef264..8d17189b0 100644 --- a/R/rank.R +++ b/R/rank.R @@ -1,8 +1,3 @@ -# TODO: Use this NEWS bullet when we export `vec_rank()` -# -# * New `vec_rank()` to compute various types of sample ranks. - - #' Compute ranks #' #' `vec_rank()` computes the sample ranks of a vector. For data frames, ranks @@ -53,7 +48,7 @@ #' - [vec_order_radix()] #' - [vec_slice()] #' -#' @noRd +#' @export #' @examples #' x <- c(5L, 6L, 3L, 3L, 5L, 3L) #' diff --git a/_pkgdown.yml b/_pkgdown.yml index c8fdcf081..dd25a5813 100644 --- a/_pkgdown.yml +++ b/_pkgdown.yml @@ -75,6 +75,7 @@ reference: contents: - vec_sort - vec_order + - vec_rank - title: Matching and splitting contents: diff --git a/man/vec_rank.Rd b/man/vec_rank.Rd new file mode 100644 index 000000000..7a347c578 --- /dev/null +++ b/man/vec_rank.Rd @@ -0,0 +1,146 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/rank.R +\name{vec_rank} +\alias{vec_rank} +\title{Compute ranks} +\usage{ +vec_rank( + x, + ..., + ties = c("min", "max", "sequential", "dense"), + incomplete = c("rank", "na"), + direction = "asc", + na_value = "largest", + nan_distinct = FALSE, + chr_proxy_collate = NULL +) +} +\arguments{ +\item{x}{A vector} + +\item{...}{These dots are for future extensions and must be empty.} + +\item{ties}{Ranking of duplicate values. +\itemize{ +\item \code{"min"}: Use the current rank for all duplicates. The next non-duplicate +value will have a rank incremented by the number of duplicates present. +\item \code{"max"}: Use the current rank \code{+ n_duplicates - 1} for all duplicates. +The next non-duplicate value will have a rank incremented by the number of +duplicates present. +\item \code{"sequential"}: Use an increasing sequence of ranks starting at the +current rank, applied to duplicates in order of appearance. +\item \code{"dense"}: Use the current rank for all duplicates. The next +non-duplicate value will have a rank incremented by \code{1}, effectively +removing any gaps in the ranking. +}} + +\item{incomplete}{Ranking of missing and \link[=vec_detect_complete]{incomplete} +observations. +\itemize{ +\item \code{"rank"}: Rank incomplete observations normally. Missing values within +incomplete observations will be affected by \code{na_value} and \code{nan_distinct}. +\item \code{"na"}: Don't rank incomplete observations at all. Instead, they are +given a rank of \code{NA}. In this case, \code{na_value} and \code{nan_distinct} have +no effect. +}} + +\item{direction}{Direction to sort in. +\itemize{ +\item A single \code{"asc"} or \code{"desc"} for ascending or descending order +respectively. +\item For data frames, a length \code{1} or \code{ncol(x)} character vector containing +only \code{"asc"} or \code{"desc"}, specifying the direction for each column. +}} + +\item{na_value}{Ordering of missing values. +\itemize{ +\item A single \code{"largest"} or \code{"smallest"} for ordering missing values as the +largest or smallest values respectively. +\item For data frames, a length \code{1} or \code{ncol(x)} character vector containing +only \code{"largest"} or \code{"smallest"}, specifying how missing values should +be ordered within each column. +}} + +\item{nan_distinct}{A single logical specifying whether or not \code{NaN} should +be considered distinct from \code{NA} for double and complex vectors. If \code{TRUE}, +\code{NaN} will always be ordered between \code{NA} and non-missing numbers.} + +\item{chr_proxy_collate}{A function generating an alternate representation +of character vectors to use for collation, often used for locale-aware +ordering. +\itemize{ +\item If \code{NULL}, no transformation is done. +\item Otherwise, this must be a function of one argument. If the input contains +a character vector, it will be passed to this function after it has been +translated to UTF-8. This function should return a character vector with +the same length as the input. The result should sort as expected in the +C-locale, regardless of encoding. +} + +For data frames, \code{chr_proxy_collate} will be applied to all character +columns. + +Common transformation functions include: \code{tolower()} for case-insensitive +ordering and \code{stringi::stri_sort_key()} for locale-aware ordering.} +} +\description{ +\code{vec_rank()} computes the sample ranks of a vector. For data frames, ranks +are computed along the rows, using all columns after the first to break +ties. +} +\details{ +Unlike \code{\link[base:rank]{base::rank()}}, when \code{incomplete = "rank"} all missing values are +given the same rank, rather than an increasing sequence of ranks. When +\code{nan_distinct = FALSE}, \code{NaN} values are given the same rank as \code{NA}, +otherwise they are given a rank that differentiates them from \code{NA}. + +Like \code{\link[=vec_order_radix]{vec_order_radix()}}, ordering is done in the C-locale. This can affect +the ranks of character vectors, especially regarding how uppercase and +lowercase letters are ranked. See the documentation of \code{\link[=vec_order_radix]{vec_order_radix()}} +for more information. +} +\section{Dependencies}{ + +\itemize{ +\item \code{\link[=vec_order_radix]{vec_order_radix()}} +\item \code{\link[=vec_slice]{vec_slice()}} +} +} + +\examples{ +x <- c(5L, 6L, 3L, 3L, 5L, 3L) + +vec_rank(x, ties = "min") +vec_rank(x, ties = "max") + +# Sequential ranks use an increasing sequence for duplicates +vec_rank(x, ties = "sequential") + +# Dense ranks remove gaps between distinct values, +# even if there are duplicates +vec_rank(x, ties = "dense") + +y <- c(NA, x, NA, NaN) + +# Incomplete values match other incomplete values by default, and their +# overall position can be adjusted with `na_value` +vec_rank(y, na_value = "largest") +vec_rank(y, na_value = "smallest") + +# NaN can be ranked separately from NA if required +vec_rank(y, nan_distinct = TRUE) + +# Rank in descending order. Since missing values are the largest value, +# they are given a rank of `1` when ranking in descending order. +vec_rank(y, direction = "desc", na_value = "largest") + +# Give incomplete values a rank of `NA` by setting `incomplete = "na"` +vec_rank(y, incomplete = "na") + +# Can also rank data frames, using columns after the first to break ties +z <- c(2L, 3L, 4L, 4L, 5L, 2L) +df <- data_frame(x = x, z = z) +df + +vec_rank(df) +} From 01668d5b427b35f19b932c574e49917581bddb86 Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Fri, 2 Sep 2022 12:45:18 +0200 Subject: [PATCH 007/312] Comment on `loc` updating --- src/bind.c | 1 + 1 file changed, 1 insertion(+) diff --git a/src/bind.c b/src/bind.c index 6cc8a028c..db0fb696a 100644 --- a/src/bind.c +++ b/src/bind.c @@ -203,6 +203,7 @@ r_obj* vec_rbind(r_obj* xs, } r_obj* x = r_list_get(xs, i); + // Update `loc` to assign within `out[counter:counter + size, ]` init_compact_seq(p_loc, counter, size, true); // Total ownership of `out` because it was freshly created with `vec_init()` From 9a45fad850423c5e1dcc641e23f36f7b80247fee Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Fri, 2 Sep 2022 13:15:41 +0200 Subject: [PATCH 008/312] Update style in `proxy.c` --- R/proxy.R | 2 +- R/type-data-frame.R | 2 +- src/decl/proxy.h | 29 ++++++++ src/init.c | 8 +-- src/proxy.c | 161 ++++++++++++++++++++------------------------ src/proxy.h | 15 +++++ src/vctrs.h | 1 + 7 files changed, 123 insertions(+), 95 deletions(-) create mode 100644 src/decl/proxy.h create mode 100644 src/proxy.h diff --git a/R/proxy.R b/R/proxy.R index 72ccc34fa..be61c6210 100644 --- a/R/proxy.R +++ b/R/proxy.R @@ -217,5 +217,5 @@ vec_data <- function(x) { unset_s4(x) } unset_s4 <- function(x) { - .Call(vctrs_unset_s4, x) + .Call(ffi_unset_s4, x) } diff --git a/R/type-data-frame.R b/R/type-data-frame.R index 2883201c0..9e00c994b 100644 --- a/R/type-data-frame.R +++ b/R/type-data-frame.R @@ -196,7 +196,7 @@ VCTRS_PROXY_KIND_compare <- 2L VCTRS_PROXY_KIND_order <- 3L df_proxy <- function(x, kind) { - .Call(vctrs_df_proxy, x, kind) + .Call(ffi_df_proxy, x, kind) } df_is_coercible <- function(x, y, opts) { diff --git a/src/decl/proxy.h b/src/decl/proxy.h new file mode 100644 index 000000000..046c5d40b --- /dev/null +++ b/src/decl/proxy.h @@ -0,0 +1,29 @@ +r_obj* syms_vec_proxy; +r_obj* syms_vec_proxy_equal; +r_obj* syms_vec_proxy_equal_array; +r_obj* syms_vec_proxy_compare; +r_obj* syms_vec_proxy_compare_array; +r_obj* syms_vec_proxy_order; +r_obj* syms_vec_proxy_order_array; + +r_obj* fns_vec_proxy_equal_array; +r_obj* fns_vec_proxy_compare_array; +r_obj* fns_vec_proxy_order_array; + +static inline +r_obj* vec_proxy_equal_method(r_obj* x); + +static inline +r_obj* vec_proxy_equal_invoke(r_obj* x, r_obj* method); + +static inline +r_obj* vec_proxy_compare_method(r_obj* x); + +static inline +r_obj* vec_proxy_compare_invoke(r_obj* x, r_obj* method); + +static inline +r_obj* vec_proxy_order_method(r_obj* x); + +static inline +r_obj* vec_proxy_order_invoke(r_obj* x, r_obj* method); diff --git a/src/init.c b/src/init.c index 6ddfca53d..408184cf6 100644 --- a/src/init.c +++ b/src/init.c @@ -59,7 +59,7 @@ extern SEXP vec_proxy(SEXP); extern SEXP vec_proxy_equal(SEXP); extern SEXP vec_proxy_compare(SEXP); extern SEXP vec_proxy_order(SEXP); -extern SEXP vctrs_df_proxy(SEXP, SEXP); +extern r_obj* ffi_df_proxy(r_obj*, r_obj*); extern SEXP vctrs_unspecified(SEXP); extern r_obj* ffi_ptype(r_obj*, r_obj*, r_obj*); extern SEXP vec_ptype_finalise(SEXP); @@ -85,7 +85,7 @@ extern SEXP vctrs_outer_names(SEXP, SEXP, SEXP); extern SEXP vctrs_df_size(SEXP); extern r_obj* ffi_as_df_col(r_obj*, r_obj*, r_obj*); extern SEXP vctrs_apply_name_spec(SEXP, SEXP, SEXP, SEXP); -extern SEXP vctrs_unset_s4(SEXP); +extern r_obj* ffi_unset_s4(r_obj*); extern SEXP vctrs_validate_name_repair_arg(SEXP); extern SEXP vctrs_validate_minimal_names(SEXP, SEXP); extern r_obj* ffi_as_names(r_obj*, r_obj*, r_obj*, r_obj*); @@ -227,7 +227,7 @@ static const R_CallMethodDef CallEntries[] = { {"vctrs_proxy_equal", (DL_FUNC) &vec_proxy_equal, 1}, {"vctrs_proxy_compare", (DL_FUNC) &vec_proxy_compare, 1}, {"vctrs_proxy_order", (DL_FUNC) &vec_proxy_order, 1}, - {"vctrs_df_proxy", (DL_FUNC) &vctrs_df_proxy, 2}, + {"ffi_df_proxy", (DL_FUNC) &ffi_df_proxy, 2}, {"vctrs_unspecified", (DL_FUNC) &vctrs_unspecified, 1}, {"ffi_ptype", (DL_FUNC) &ffi_ptype, 3}, {"vctrs_ptype_finalise", (DL_FUNC) &vec_ptype_finalise, 1}, @@ -253,7 +253,7 @@ static const R_CallMethodDef CallEntries[] = { {"vctrs_df_size", (DL_FUNC) &vctrs_df_size, 1}, {"ffi_as_df_col", (DL_FUNC) &ffi_as_df_col, 3}, {"vctrs_apply_name_spec", (DL_FUNC) &vctrs_apply_name_spec, 4}, - {"vctrs_unset_s4", (DL_FUNC) &vctrs_unset_s4, 1}, + {"ffi_unset_s4", (DL_FUNC) &ffi_unset_s4, 1}, {"vctrs_altrep_rle_Make", (DL_FUNC) &altrep_rle_Make, 1}, {"vctrs_altrep_rle_is_materialized", (DL_FUNC) &altrep_rle_is_materialized, 1}, {"vctrs_validate_name_repair_arg", (DL_FUNC) &vctrs_validate_name_repair_arg, 1}, diff --git a/src/proxy.c b/src/proxy.c index 4684716ee..873d1a4f5 100644 --- a/src/proxy.c +++ b/src/proxy.c @@ -1,23 +1,8 @@ #include "vctrs.h" #include "type-data-frame.h" +#include "decl/proxy.h" -// Initialised at load time -SEXP syms_vec_proxy = NULL; -SEXP syms_vec_proxy_equal = NULL; -SEXP syms_vec_proxy_equal_array = NULL; -SEXP syms_vec_proxy_compare = NULL; -SEXP syms_vec_proxy_compare_array = NULL; -SEXP syms_vec_proxy_order = NULL; -SEXP syms_vec_proxy_order_array = NULL; - -SEXP fns_vec_proxy_equal_array = NULL; -SEXP fns_vec_proxy_compare_array = NULL; -SEXP fns_vec_proxy_order_array = NULL; - -SEXP vec_proxy_method(SEXP x); -SEXP vec_proxy_invoke(SEXP x, SEXP method); - -// [[ register(); include("vctrs.h") ]] +// [[ register() ]] r_obj* vec_proxy(r_obj* x) { struct vctrs_type_info info = vec_type_info(x); KEEP(info.shelter); @@ -33,48 +18,39 @@ r_obj* vec_proxy(r_obj* x) { return out; } -static inline SEXP vec_proxy_equal_method(SEXP x); -static inline SEXP vec_proxy_equal_invoke(SEXP x, SEXP method); - -// [[ register(); include("vctrs.h") ]] -SEXP vec_proxy_equal(SEXP x) { - SEXP method = PROTECT(vec_proxy_equal_method(x)); - SEXP out = vec_proxy_equal_invoke(x, method); - UNPROTECT(1); +// [[ register() ]] +r_obj* vec_proxy_equal(r_obj* x) { + r_obj* method = KEEP(vec_proxy_equal_method(x)); + r_obj* out = vec_proxy_equal_invoke(x, method); + FREE(1); return out; } -static inline SEXP vec_proxy_compare_method(SEXP x); -static inline SEXP vec_proxy_compare_invoke(SEXP x, SEXP method); - -// [[ register(); include("vctrs.h") ]] -SEXP vec_proxy_compare(SEXP x) { - SEXP method = PROTECT(vec_proxy_compare_method(x)); - SEXP out = vec_proxy_compare_invoke(x, method); - UNPROTECT(1); +// [[ register() ]] +r_obj* vec_proxy_compare(r_obj* x) { + r_obj* method = KEEP(vec_proxy_compare_method(x)); + r_obj* out = vec_proxy_compare_invoke(x, method); + FREE(1); return out; } -static inline SEXP vec_proxy_order_method(SEXP x); -static inline SEXP vec_proxy_order_invoke(SEXP x, SEXP method); - -// [[ register(); include("vctrs.h") ]] -SEXP vec_proxy_order(SEXP x) { - SEXP method = PROTECT(vec_proxy_order_method(x)); - SEXP out = vec_proxy_order_invoke(x, method); - UNPROTECT(1); +// [[ register() ]] +r_obj* vec_proxy_order(r_obj* x) { + r_obj* method = KEEP(vec_proxy_order_method(x)); + r_obj* out = vec_proxy_order_invoke(x, method); + FREE(1); return out; } -SEXP vec_proxy_method(SEXP x) { +r_obj* vec_proxy_method(r_obj* x) { return s3_find_method("vec_proxy", x, vctrs_method_table); } // This should be faster than normal dispatch but also means that // proxy methods can't call `NextMethod()`. This could be changed if // it turns out a problem. -SEXP vec_proxy_invoke(SEXP x, SEXP method) { - if (method == R_NilValue) { +r_obj* vec_proxy_invoke(r_obj* x, r_obj* method) { + if (method == r_null) { return x; } else { return vctrs_dispatch1(syms_vec_proxy, method, syms_x, x); @@ -82,45 +58,45 @@ SEXP vec_proxy_invoke(SEXP x, SEXP method) { } static inline -SEXP vec_proxy_method_impl(SEXP x, const char* generic, SEXP fn_proxy_array) { - SEXP cls = PROTECT(s3_get_class(x)); - SEXP method = s3_class_find_method(generic, cls, vctrs_method_table); +r_obj* vec_proxy_method_impl(r_obj* x, const char* generic, r_obj* fn_proxy_array) { + r_obj* cls = KEEP(s3_get_class(x)); + r_obj* method = s3_class_find_method(generic, cls, vctrs_method_table); - if (method != R_NilValue) { - UNPROTECT(1); + if (method != r_null) { + FREE(1); return method; } /* FIXME: Stopgap check for bare arrays */ /* which equality functions don't handle well */ if (vec_dim_n(x) > 1) { - UNPROTECT(1); + FREE(1); return fn_proxy_array; } - UNPROTECT(1); - return R_NilValue; + FREE(1); + return r_null; } static inline -SEXP vec_proxy_equal_method(SEXP x) { +r_obj* vec_proxy_equal_method(r_obj* x) { return vec_proxy_method_impl(x, "vec_proxy_equal", fns_vec_proxy_equal_array); } static inline -SEXP vec_proxy_compare_method(SEXP x) { +r_obj* vec_proxy_compare_method(r_obj* x) { return vec_proxy_method_impl(x, "vec_proxy_compare", fns_vec_proxy_compare_array); } static inline -SEXP vec_proxy_order_method(SEXP x) { +r_obj* vec_proxy_order_method(r_obj* x) { return vec_proxy_method_impl(x, "vec_proxy_order", fns_vec_proxy_order_array); } static inline -SEXP vec_proxy_invoke_impl(SEXP x, - SEXP method, - SEXP vec_proxy_sym, - SEXP (*vec_proxy_fn)(SEXP)) { - if (method != R_NilValue) { +r_obj* vec_proxy_invoke_impl(r_obj* x, + r_obj* method, + r_obj* vec_proxy_sym, + r_obj* (*vec_proxy_fn)(r_obj*)) { + if (method != r_null) { return vctrs_dispatch1(vec_proxy_sym, method, syms_x, x); } @@ -133,31 +109,31 @@ SEXP vec_proxy_invoke_impl(SEXP x, } static inline -SEXP vec_proxy_equal_invoke(SEXP x, SEXP method) { +r_obj* vec_proxy_equal_invoke(r_obj* x, r_obj* method) { return vec_proxy_invoke_impl(x, method, syms_vec_proxy_equal, vec_proxy); } static inline -SEXP vec_proxy_compare_invoke(SEXP x, SEXP method) { +r_obj* vec_proxy_compare_invoke(r_obj* x, r_obj* method) { return vec_proxy_invoke_impl(x, method, syms_vec_proxy_compare, &vec_proxy_equal); } static inline -SEXP vec_proxy_order_invoke(SEXP x, SEXP method) { +r_obj* vec_proxy_order_invoke(r_obj* x, r_obj* method) { return vec_proxy_invoke_impl(x, method, syms_vec_proxy_order, &vec_proxy_compare); } #define DF_PROXY(PROXY) do { \ - R_len_t n_cols = Rf_length(x); \ + r_ssize n_cols = r_length(x); \ \ - for (R_len_t i = 0; i < n_cols; ++i) { \ - SEXP col = VECTOR_ELT(x, i); \ - SET_VECTOR_ELT(x, i, PROXY(col)); \ + for (r_ssize i = 0; i < n_cols; ++i) { \ + r_obj* col = r_list_get(x, i); \ + r_list_poke(x, i, PROXY(col)); \ } \ } while (0) static -SEXP df_proxy(SEXP x, enum vctrs_proxy_kind kind) { - x = PROTECT(r_clone_referenced(x)); +r_obj* df_proxy(r_obj* x, enum vctrs_proxy_kind kind) { + x = KEEP(r_clone_referenced(x)); switch (kind) { case VCTRS_PROXY_KIND_default: DF_PROXY(vec_proxy); break; @@ -166,17 +142,14 @@ SEXP df_proxy(SEXP x, enum vctrs_proxy_kind kind) { case VCTRS_PROXY_KIND_order: DF_PROXY(vec_proxy_order); break; } - x = PROTECT(df_flatten(x)); + x = KEEP(df_flatten(x)); x = vec_proxy_unwrap(x); - UNPROTECT(2); + FREE(2); return x; } -#undef DF_PROXY - -// [[ register() ]] -SEXP vctrs_df_proxy(SEXP x, SEXP kind) { +r_obj* ffi_df_proxy(r_obj* x, r_obj* kind) { if (!r_is_number(kind)) { r_stop_internal("`kind` must be a single integer."); } @@ -186,36 +159,46 @@ SEXP vctrs_df_proxy(SEXP x, SEXP kind) { return df_proxy(x, c_kind); } -// [[ include("vctrs.h") ]] -SEXP vec_proxy_unwrap(SEXP x) { - if (TYPEOF(x) == VECSXP && XLENGTH(x) == 1 && is_data_frame(x)) { - x = vec_proxy_unwrap(VECTOR_ELT(x, 0)); +r_obj* vec_proxy_unwrap(r_obj* x) { + if (r_typeof(x) == R_TYPE_list && r_length(x) == 1 && is_data_frame(x)) { + x = vec_proxy_unwrap(r_list_get(x, 0)); } return x; } -// [[ register() ]] -SEXP vctrs_unset_s4(SEXP x) { +r_obj* ffi_unset_s4(r_obj* x) { x = r_clone_referenced(x); r_unmark_s4(x); return x; } -void vctrs_init_data(SEXP ns) { - syms_vec_proxy = Rf_install("vec_proxy"); +void vctrs_init_data(r_obj* ns) { + syms_vec_proxy = r_sym("vec_proxy"); - syms_vec_proxy_equal = Rf_install("vec_proxy_equal"); - syms_vec_proxy_equal_array = Rf_install("vec_proxy_equal.array"); + syms_vec_proxy_equal = r_sym("vec_proxy_equal"); + syms_vec_proxy_equal_array = r_sym("vec_proxy_equal.array"); - syms_vec_proxy_compare = Rf_install("vec_proxy_compare"); - syms_vec_proxy_compare_array = Rf_install("vec_proxy_compare.array"); + syms_vec_proxy_compare = r_sym("vec_proxy_compare"); + syms_vec_proxy_compare_array = r_sym("vec_proxy_compare.array"); - syms_vec_proxy_order = Rf_install("vec_proxy_order"); - syms_vec_proxy_order_array = Rf_install("vec_proxy_order.array"); + syms_vec_proxy_order = r_sym("vec_proxy_order"); + syms_vec_proxy_order_array = r_sym("vec_proxy_order.array"); fns_vec_proxy_equal_array = r_env_get(ns, syms_vec_proxy_equal_array); fns_vec_proxy_compare_array = r_env_get(ns, syms_vec_proxy_compare_array); fns_vec_proxy_order_array = r_env_get(ns, syms_vec_proxy_order_array); } + +r_obj* syms_vec_proxy = NULL; +r_obj* syms_vec_proxy_equal = NULL; +r_obj* syms_vec_proxy_equal_array = NULL; +r_obj* syms_vec_proxy_compare = NULL; +r_obj* syms_vec_proxy_compare_array = NULL; +r_obj* syms_vec_proxy_order = NULL; +r_obj* syms_vec_proxy_order_array = NULL; + +r_obj* fns_vec_proxy_equal_array = NULL; +r_obj* fns_vec_proxy_compare_array = NULL; +r_obj* fns_vec_proxy_order_array = NULL; diff --git a/src/proxy.h b/src/proxy.h new file mode 100644 index 000000000..dedbc48db --- /dev/null +++ b/src/proxy.h @@ -0,0 +1,15 @@ +#ifndef VCTRS_PROXY_H +#define VCTRS_PROXY_H + +#include "vctrs-core.h" + +r_obj* vec_proxy(r_obj* x); +r_obj* vec_proxy_equal(r_obj* x); +r_obj* vec_proxy_compare(r_obj* x); +r_obj* vec_proxy_order(r_obj* x); + +r_obj* vec_proxy_method(r_obj* x); +r_obj* vec_proxy_invoke(r_obj* x, r_obj* method); +r_obj* vec_proxy_unwrap(r_obj* x); + +#endif diff --git a/src/vctrs.h b/src/vctrs.h index d0f45a51c..264120a4d 100644 --- a/src/vctrs.h +++ b/src/vctrs.h @@ -277,6 +277,7 @@ bool vec_is_unspecified(SEXP x); #include "order.h" #include "owned.h" #include "poly-op.h" +#include "proxy.h" #include "ptype-common.h" #include "ptype.h" #include "ptype2-dispatch.h" From 4d02e7a6196ad3bb764b2e85953ec6b16a13ef50 Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Fri, 2 Sep 2022 14:18:32 +0200 Subject: [PATCH 009/312] Rename `proxy.h` to `proxy-decl.h` --- src/decl/{proxy.h => proxy-decl.h} | 0 src/proxy.c | 2 +- 2 files changed, 1 insertion(+), 1 deletion(-) rename src/decl/{proxy.h => proxy-decl.h} (100%) diff --git a/src/decl/proxy.h b/src/decl/proxy-decl.h similarity index 100% rename from src/decl/proxy.h rename to src/decl/proxy-decl.h diff --git a/src/proxy.c b/src/proxy.c index 873d1a4f5..983579cfe 100644 --- a/src/proxy.c +++ b/src/proxy.c @@ -1,6 +1,6 @@ #include "vctrs.h" #include "type-data-frame.h" -#include "decl/proxy.h" +#include "decl/proxy-decl.h" // [[ register() ]] r_obj* vec_proxy(r_obj* x) { From afeeaacfd98b9e33eb0e061bd7b8250c9abbfe5a Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Fri, 2 Sep 2022 13:34:01 +0200 Subject: [PATCH 010/312] Update style in `names.c` --- R/names.R | 8 +- R/utils.R | 2 +- src/decl/names-decl.h | 47 +++ src/init.c | 24 +- src/names.c | 582 ++++++++++++++++------------------ src/names.h | 26 +- src/utils.h | 6 - tests/testthat/_snaps/bind.md | 6 +- tests/testthat/test-names.R | 4 +- 9 files changed, 361 insertions(+), 344 deletions(-) diff --git a/R/names.R b/R/names.R index 5d10b6283..0bb885511 100644 --- a/R/names.R +++ b/R/names.R @@ -290,10 +290,10 @@ vec_repair_names <- function(x, } minimal_names <- function(x) { - .Call(vctrs_minimal_names, x) + .Call(ffi_minimal_names, x) } unique_names <- function(x, quiet = FALSE) { - .Call(vctrs_unique_names, x, quiet) + .Call(ffi_unique_names, x, quiet) } #' @rdname vec_names @@ -303,7 +303,7 @@ vec_names <- function(x) { } as_minimal_names <- function(names) { - .Call(vctrs_as_minimal_names, names) + .Call(ffi_as_minimal_names, names) } as_unique_names <- function(names, quiet = FALSE) { .Call(vctrs_as_unique_names, names, quiet) @@ -576,7 +576,7 @@ vec_as_names_legacy <- function(names, prefix = "V", sep = "") { NULL apply_name_spec <- function(name_spec, outer, inner, n = length(inner)) { - .Call(vctrs_apply_name_spec, name_spec, outer, inner, n) + .Call(ffi_apply_name_spec, name_spec, outer, inner, n) } glue_as_name_spec <- function(`_spec`) { diff --git a/R/utils.R b/R/utils.R index e0bf7cdb0..0e31b5709 100644 --- a/R/utils.R +++ b/R/utils.R @@ -21,7 +21,7 @@ vec_coerce_bare <- function(x, type) { # Matches the semantics of c() - based on experimenting with the output # of c(), not reading the source code. outer_names <- function(names, outer, n) { - .Call(vctrs_outer_names, names, outer, vec_cast(n, int())) + .Call(ffi_outer_names, names, outer, vec_cast(n, int())) } has_inner_names <- function(x) { diff --git a/src/decl/names-decl.h b/src/decl/names-decl.h index 2f2f42bac..433749f32 100644 --- a/src/decl/names-decl.h +++ b/src/decl/names-decl.h @@ -1,3 +1,50 @@ +static r_obj* syms_as_universal_names; +static r_obj* syms_check_unique_names; +static r_obj* fns_as_universal_names; +static r_obj* fns_check_unique_names; +static r_obj* syms_glue_as_name_spec; +static r_obj* fns_glue_as_name_spec; +static r_obj* syms_internal_spec; +static r_obj* syms_set_rownames_dispatch; +static r_obj* fns_set_rownames_dispatch; +static r_obj* syms_set_names_dispatch; +static r_obj* fns_set_names_dispatch; + +static +void describe_repair(r_obj* old_names, r_obj* new_names); + static r_obj* check_unique_names(r_obj* names, const struct name_repair_opts* opts); + +static +void vec_validate_minimal_names(r_obj* names, r_ssize n); + +r_obj* ffi_as_minimal_names(r_obj* names); + +static +bool any_has_suffix(r_obj* names); + +static +r_obj* as_unique_names_impl(r_obj* names, bool quiet); + +static +void stop_large_name(); + +static +bool is_dotdotint(const char* name); + +static +ptrdiff_t suffix_pos(const char* name); + +static +bool needs_suffix(r_obj* str); + +static +r_obj* names_iota(r_ssize n); + +static +r_obj* vec_unique_names_impl(r_obj* names, r_ssize n, bool quiet); + +static +r_obj* glue_as_name_spec(r_obj* spec); diff --git a/src/init.c b/src/init.c index 408184cf6..f24166c68 100644 --- a/src/init.c +++ b/src/init.c @@ -63,9 +63,9 @@ extern r_obj* ffi_df_proxy(r_obj*, r_obj*); extern SEXP vctrs_unspecified(SEXP); extern r_obj* ffi_ptype(r_obj*, r_obj*, r_obj*); extern SEXP vec_ptype_finalise(SEXP); -extern SEXP vctrs_minimal_names(SEXP); -extern SEXP vctrs_unique_names(SEXP, SEXP); -extern SEXP vctrs_as_minimal_names(SEXP); +extern r_obj* ffi_minimal_names(r_obj*); +extern r_obj* ffi_unique_names(r_obj*, r_obj*); +extern SEXP ffi_as_minimal_names(SEXP); extern SEXP vec_names(SEXP); extern SEXP vctrs_is_unique_names(SEXP); extern SEXP vctrs_as_unique_names(SEXP, SEXP); @@ -81,10 +81,10 @@ extern r_obj* ffi_assign(r_obj*, r_obj*, r_obj*, r_obj*); extern r_obj* ffi_assign_seq(r_obj*, r_obj*, r_obj*, r_obj*, r_obj*); extern SEXP vctrs_set_attributes(SEXP, SEXP); extern r_obj* ffi_as_df_row(r_obj*, r_obj*, r_obj*); -extern SEXP vctrs_outer_names(SEXP, SEXP, SEXP); +extern r_obj* ffi_outer_names(r_obj*, r_obj*, r_obj*); extern SEXP vctrs_df_size(SEXP); extern r_obj* ffi_as_df_col(r_obj*, r_obj*, r_obj*); -extern SEXP vctrs_apply_name_spec(SEXP, SEXP, SEXP, SEXP); +extern r_obj* ffi_apply_name_spec(r_obj*, r_obj*, r_obj*, r_obj*); extern r_obj* ffi_unset_s4(r_obj*); extern SEXP vctrs_validate_name_repair_arg(SEXP); extern SEXP vctrs_validate_minimal_names(SEXP, SEXP); @@ -132,7 +132,7 @@ extern SEXP vctrs_locate_sorted_groups(SEXP, SEXP, SEXP, SEXP, SEXP); extern SEXP vctrs_order_info(SEXP, SEXP, SEXP, SEXP, SEXP, SEXP); extern SEXP vctrs_unrep(SEXP); extern SEXP vctrs_fill_missing(SEXP, SEXP, SEXP); -extern SEXP vctrs_chr_paste_prefix(SEXP, SEXP, SEXP); +extern r_obj* ffi_chr_paste_prefix(r_obj*, r_obj*, r_obj*); extern r_obj* vctrs_rank(r_obj*, r_obj*, r_obj*, r_obj*, r_obj*, r_obj*, r_obj*); extern r_obj* vctrs_integer64_proxy(r_obj*); extern r_obj* vctrs_integer64_restore(r_obj*); @@ -231,9 +231,9 @@ static const R_CallMethodDef CallEntries[] = { {"vctrs_unspecified", (DL_FUNC) &vctrs_unspecified, 1}, {"ffi_ptype", (DL_FUNC) &ffi_ptype, 3}, {"vctrs_ptype_finalise", (DL_FUNC) &vec_ptype_finalise, 1}, - {"vctrs_minimal_names", (DL_FUNC) &vctrs_minimal_names, 1}, - {"vctrs_unique_names", (DL_FUNC) &vctrs_unique_names, 2}, - {"vctrs_as_minimal_names", (DL_FUNC) &vctrs_as_minimal_names, 1}, + {"ffi_minimal_names", (DL_FUNC) &ffi_minimal_names, 1}, + {"ffi_unique_names", (DL_FUNC) &ffi_unique_names, 2}, + {"ffi_as_minimal_names", (DL_FUNC) &ffi_as_minimal_names, 1}, {"vctrs_names", (DL_FUNC) &vec_names, 1}, {"vctrs_is_unique_names", (DL_FUNC) &vctrs_is_unique_names, 1}, {"vctrs_as_unique_names", (DL_FUNC) &vctrs_as_unique_names, 2}, @@ -249,10 +249,10 @@ static const R_CallMethodDef CallEntries[] = { {"ffi_assign_seq", (DL_FUNC) &ffi_assign_seq, 5}, {"vctrs_set_attributes", (DL_FUNC) &vctrs_set_attributes, 2}, {"ffi_as_df_row", (DL_FUNC) &ffi_as_df_row, 3}, - {"vctrs_outer_names", (DL_FUNC) &vctrs_outer_names, 3}, + {"ffi_outer_names", (DL_FUNC) &ffi_outer_names, 3}, {"vctrs_df_size", (DL_FUNC) &vctrs_df_size, 1}, {"ffi_as_df_col", (DL_FUNC) &ffi_as_df_col, 3}, - {"vctrs_apply_name_spec", (DL_FUNC) &vctrs_apply_name_spec, 4}, + {"ffi_apply_name_spec", (DL_FUNC) &ffi_apply_name_spec, 4}, {"ffi_unset_s4", (DL_FUNC) &ffi_unset_s4, 1}, {"vctrs_altrep_rle_Make", (DL_FUNC) &altrep_rle_Make, 1}, {"vctrs_altrep_rle_is_materialized", (DL_FUNC) &altrep_rle_is_materialized, 1}, @@ -302,7 +302,7 @@ static const R_CallMethodDef CallEntries[] = { {"vctrs_order_info", (DL_FUNC) &vctrs_order_info, 6}, {"vctrs_unrep", (DL_FUNC) &vctrs_unrep, 1}, {"vctrs_fill_missing", (DL_FUNC) &vctrs_fill_missing, 3}, - {"vctrs_chr_paste_prefix", (DL_FUNC) &vctrs_chr_paste_prefix, 3}, + {"ffi_chr_paste_prefix", (DL_FUNC) &ffi_chr_paste_prefix, 3}, {"vctrs_rank", (DL_FUNC) &vctrs_rank, 7}, {"vctrs_integer64_proxy", (DL_FUNC) &vctrs_integer64_proxy, 1}, {"vctrs_integer64_restore", (DL_FUNC) &vctrs_integer64_restore, 1}, diff --git a/src/names.c b/src/names.c index 00dac4eb6..967934908 100644 --- a/src/names.c +++ b/src/names.c @@ -1,34 +1,19 @@ +#include #include "vctrs.h" #include "type-data-frame.h" -#include #include "decl/names-decl.h" -static void describe_repair(SEXP old_names, SEXP new_names); - // 3 leading '.' + 1 trailing '\0' + 24 characters #define MAX_IOTA_SIZE 28 -// Initialised at load time -SEXP syms_as_universal_names = NULL; -SEXP syms_check_unique_names = NULL; -SEXP fns_as_universal_names = NULL; -SEXP fns_check_unique_names = NULL; - -// Defined below -SEXP vctrs_as_minimal_names(SEXP names); -SEXP vec_as_universal_names(SEXP names, bool quiet); -SEXP vec_as_custom_names(SEXP names, const struct name_repair_opts* opts); -static void vec_validate_minimal_names(SEXP names, R_len_t n); - -// [[ include("names.h") ]] -SEXP vec_as_names(SEXP names, const struct name_repair_opts* opts) { +r_obj* vec_as_names(r_obj* names, const struct name_repair_opts* opts) { if (!opts) { return names; } switch (opts->type) { case name_repair_none: return names; - case name_repair_minimal: return vctrs_as_minimal_names(names); + case name_repair_minimal: return ffi_as_minimal_names(names); case name_repair_unique: return vec_as_unique_names(names, opts->quiet); case name_repair_universal: return vec_as_universal_names(names, opts->quiet); case name_repair_check_unique: return check_unique_names(names, opts); @@ -37,7 +22,6 @@ SEXP vec_as_names(SEXP names, const struct name_repair_opts* opts) { never_reached("vec_as_names"); } -// [[ register() ]] r_obj* ffi_as_names(r_obj* names, r_obj* repair, r_obj* ffi_quiet, @@ -64,12 +48,12 @@ r_obj* ffi_as_names(r_obj* names, return out; } -SEXP vec_as_universal_names(SEXP names, bool quiet) { - SEXP quiet_obj = PROTECT(r_lgl(quiet)); - SEXP out = vctrs_dispatch2(syms_as_universal_names, fns_as_universal_names, - syms_names, names, - syms_quiet, quiet_obj); - UNPROTECT(1); +r_obj* vec_as_universal_names(r_obj* names, bool quiet) { + r_obj* quiet_obj = KEEP(r_lgl(quiet)); + r_obj* out = vctrs_dispatch2(syms_as_universal_names, fns_as_universal_names, + syms_names, names, + syms_quiet, quiet_obj); + FREE(1); return out; } @@ -91,38 +75,38 @@ r_obj* check_unique_names(r_obj* names, return out; } -SEXP vec_as_custom_names(SEXP names, const struct name_repair_opts* opts) { - names = PROTECT(vctrs_as_minimal_names(names)); +r_obj* vec_as_custom_names(r_obj* names, const struct name_repair_opts* opts) { + names = KEEP(ffi_as_minimal_names(names)); // Don't use vctrs dispatch utils because we match argument positionally - SEXP call = PROTECT(Rf_lang2(syms_repair, syms_names)); - SEXP mask = PROTECT(r_new_environment(R_GlobalEnv)); - Rf_defineVar(syms_repair, opts->fn, mask); - Rf_defineVar(syms_names, names, mask); - SEXP out = PROTECT(Rf_eval(call, mask)); + r_obj* call = KEEP(r_call2(syms_repair, syms_names)); + r_obj* mask = KEEP(r_new_environment(R_GlobalEnv)); + r_env_poke(mask, syms_repair, opts->fn); + r_env_poke(mask, syms_names, names); + r_obj* out = KEEP(r_eval(call, mask)); - vec_validate_minimal_names(out, Rf_length(names)); + vec_validate_minimal_names(out, r_length(names)); - UNPROTECT(4); + FREE(4); return out; } static -SEXP vec_names_impl(SEXP x, bool proxy) { - bool has_class = OBJECT(x); +r_obj* vec_names_impl(r_obj* x, bool proxy) { + bool has_class = r_is_object(x); - if (has_class && Rf_inherits(x, "data.frame")) { + if (has_class && r_inherits(x, "data.frame")) { // Only return row names if they are character. Data frames with // automatic row names are treated as unnamed. - SEXP rn = df_rownames(x); + r_obj* rn = df_rownames(x); if (rownames_type(rn) == ROWNAMES_IDENTIFIERS) { return rn; } else { - return R_NilValue; + return r_null; } } - if (vec_bare_dim(x) == R_NilValue) { + if (vec_bare_dim(x) == r_null) { if (!proxy && has_class) { return vctrs_dispatch1(syms_names, fns_names, syms_x, x); } else { @@ -130,23 +114,22 @@ SEXP vec_names_impl(SEXP x, bool proxy) { } } - SEXP dimnames = PROTECT(r_attrib_get(x, R_DimNamesSymbol)); - if (dimnames == R_NilValue || Rf_length(dimnames) < 1) { - UNPROTECT(1); - return R_NilValue; + r_obj* dimnames = KEEP(r_attrib_get(x, r_syms.dim_names)); + if (dimnames == r_null || r_length(dimnames) < 1) { + FREE(1); + return r_null; } - SEXP out = VECTOR_ELT(dimnames, 0); - UNPROTECT(1); + r_obj* out = r_list_get(dimnames, 0); + FREE(1); return out; } -// [[ register(); include("vctrs.h") ]] -SEXP vec_names(SEXP x) { +// [[ register() ]] +r_obj* vec_names(r_obj* x) { return vec_names_impl(x, false); } -// [[ include("vctrs.h") ]] -SEXP vec_proxy_names(SEXP x) { +r_obj* vec_proxy_names(r_obj* x) { return vec_names_impl(x, true); } @@ -159,19 +142,17 @@ r_obj* vec_names2(r_obj* x) { } } -// [[ register() ]] -SEXP vctrs_as_minimal_names(SEXP names) { - if (TYPEOF(names) != STRSXP) { - Rf_errorcall(R_NilValue, "`names` must be a character vector"); +r_obj* ffi_as_minimal_names(r_obj* names) { + if (r_typeof(names) != R_TYPE_character) { + r_abort_call(r_null, "`names` must be a character vector"); } - R_len_t i = 0; - R_len_t n = Rf_length(names); - const SEXP* ptr = STRING_PTR_RO(names); + r_ssize i = 0; + r_ssize n = r_length(names); + r_obj* const * v_names = r_chr_cbegin(names); - for (; i < n; ++i, ++ptr) { - SEXP elt = *ptr; - if (elt == NA_STRING) { + for (; i < n; ++i) { + if (v_names[i] == r_globals.na_str) { break; } } @@ -179,46 +160,37 @@ SEXP vctrs_as_minimal_names(SEXP names) { return names; } - names = PROTECT(Rf_shallow_duplicate(names)); + names = KEEP(r_clone(names)); - for (; i < n; ++i, ++ptr) { - SEXP elt = *ptr; - if (elt == NA_STRING) { - SET_STRING_ELT(names, i, strings_empty); + for (; i < n; ++i) { + if (v_names[i] == r_globals.na_str) { + r_chr_poke(names, i, strings_empty); } } - UNPROTECT(1); + FREE(1); return names; } -// [[ register() ]] -SEXP vctrs_minimal_names(SEXP x) { - SEXP names = PROTECT(vec_names(x)); +r_obj* ffi_minimal_names(r_obj* x) { + r_obj* names = KEEP(vec_names(x)); - if (names == R_NilValue) { - names = Rf_allocVector(STRSXP, vec_size(x)); + if (names == r_null) { + names = r_alloc_character(vec_size(x)); } else { - names = vctrs_as_minimal_names(names); + names = ffi_as_minimal_names(names); } - UNPROTECT(1); + FREE(1); return names; } // From dictionary.c -SEXP vctrs_duplicated(SEXP x); - -static bool any_has_suffix(SEXP names); -static SEXP as_unique_names_impl(SEXP names, bool quiet); -static void stop_large_name(); -static bool is_dotdotint(const char* name); -static ptrdiff_t suffix_pos(const char* name); -static bool needs_suffix(SEXP str); +r_obj* vctrs_duplicated(r_obj* x); // [[ include("vctrs.h") ]] -SEXP vec_as_unique_names(SEXP names, bool quiet) { +r_obj* vec_as_unique_names(r_obj* names, bool quiet) { if (is_unique_names(names) && !any_has_suffix(names)) { return names; } else { @@ -227,22 +199,20 @@ SEXP vec_as_unique_names(SEXP names, bool quiet) { } // [[ include("vctrs.h") ]] -bool is_unique_names(SEXP names) { - if (TYPEOF(names) != STRSXP) { - Rf_errorcall(R_NilValue, "`names` must be a character vector"); +bool is_unique_names(r_obj* names) { + if (r_typeof(names) != R_TYPE_character) { + r_abort_call(r_null, "`names` must be a character vector"); } - R_len_t n = Rf_length(names); - const SEXP* names_ptr = STRING_PTR_RO(names); + r_ssize n = r_length(names); + r_obj* const * v_names = r_chr_cbegin(names); if (duplicated_any(names)) { return false; } - for (R_len_t i = 0; i < n; ++i) { - SEXP elt = names_ptr[i]; - - if (needs_suffix(elt)) { + for (r_ssize i = 0; i < n; ++i) { + if (needs_suffix(v_names[i])) { return false; } } @@ -250,14 +220,12 @@ bool is_unique_names(SEXP names) { return true; } -bool any_has_suffix(SEXP names) { - R_len_t n = Rf_length(names); - const SEXP* names_ptr = STRING_PTR_RO(names); +bool any_has_suffix(r_obj* names) { + r_ssize n = r_length(names); + r_obj* const * v_names = r_chr_cbegin(names); - for (R_len_t i = 0; i < n; ++i) { - SEXP elt = names_ptr[i]; - - if (suffix_pos(CHAR(elt)) >= 0) { + for (r_ssize i = 0; i < n; ++i) { + if (suffix_pos(r_str_c_string(v_names[i])) >= 0) { return true; } } @@ -265,46 +233,46 @@ bool any_has_suffix(SEXP names) { return false; } -SEXP as_unique_names_impl(SEXP names, bool quiet) { - R_len_t n = Rf_length(names); +r_obj* as_unique_names_impl(r_obj* names, bool quiet) { + r_ssize n = r_length(names); - SEXP new_names = PROTECT(Rf_shallow_duplicate(names)); - const SEXP* new_names_ptr = STRING_PTR_RO(new_names); + r_obj* new_names = KEEP(r_clone(names)); + r_obj* const * v_new_names = r_chr_cbegin(new_names); - for (R_len_t i = 0; i < n; ++i) { - SEXP elt = new_names_ptr[i]; + for (r_ssize i = 0; i < n; ++i) { + r_obj* elt = v_new_names[i]; // Set `NA` and dots values to "" so they get replaced by `...n` // later on if (needs_suffix(elt)) { elt = strings_empty; - SET_STRING_ELT(new_names, i, elt); + r_chr_poke(new_names, i, elt); continue; } // Strip `...n` suffixes - const char* nm = CHAR(elt); + const char* nm = r_str_c_string(elt); int pos = suffix_pos(nm); if (pos >= 0) { elt = Rf_mkCharLenCE(nm, pos, Rf_getCharCE(elt)); - SET_STRING_ELT(new_names, i, elt); + r_chr_poke(new_names, i, elt); continue; } } // Append all duplicates with a suffix - SEXP dups = PROTECT(vctrs_duplicated(new_names)); - const int* dups_ptr = LOGICAL_RO(dups); + r_obj* dups = KEEP(vctrs_duplicated(new_names)); + const int* dups_ptr = r_lgl_cbegin(dups); - for (R_len_t i = 0; i < n; ++i) { - SEXP elt = new_names_ptr[i]; + for (r_ssize i = 0; i < n; ++i) { + r_obj* elt = v_new_names[i]; if (elt != strings_empty && !dups_ptr[i]) { continue; } - const char* name = CHAR(elt); + const char* name = r_str_c_string(elt); int size = strlen(name); int buf_size = size + MAX_IOTA_SIZE; @@ -316,34 +284,35 @@ SEXP as_unique_names_impl(SEXP names, bool quiet) { memcpy(buf, name, size); int remaining = buf_size - size; - int needed = snprintf(buf + size, remaining, "...%d", i + 1); + int needed = snprintf(buf + size, remaining, "...%d", (int) i + 1); if (needed >= remaining) { stop_large_name(); } - SET_STRING_ELT(new_names, i, Rf_mkCharLenCE(buf, size + needed, Rf_getCharCE(elt))); + r_chr_poke(new_names, i, Rf_mkCharLenCE(buf, size + needed, Rf_getCharCE(elt))); } if (!quiet) { describe_repair(names, new_names); } - UNPROTECT(2); + FREE(2); return new_names; } -SEXP vctrs_as_unique_names(SEXP names, SEXP quiet) { - SEXP out = PROTECT(vec_as_unique_names(names, LOGICAL(quiet)[0])); - UNPROTECT(1); +r_obj* vctrs_as_unique_names(r_obj* names, r_obj* quiet) { + r_obj* out = KEEP(vec_as_unique_names(names, r_lgl_get(quiet, 0))); + FREE(1); return out; } -SEXP vctrs_is_unique_names(SEXP names) { +r_obj* vctrs_is_unique_names(r_obj* names) { bool out = is_unique_names(names); - return Rf_ScalarLogical(out); + return r_lgl(out); } -static bool is_dotdotint(const char* name) { +static +bool is_dotdotint(const char* name) { int n = strlen(name); if (n < 3) { @@ -362,7 +331,8 @@ static bool is_dotdotint(const char* name) { return (bool) strtol(name, NULL, 10); } -static ptrdiff_t suffix_pos(const char* name) { +static +ptrdiff_t suffix_pos(const char* name) { int n = strlen(name); const char* suffix_end = NULL; @@ -422,62 +392,57 @@ static ptrdiff_t suffix_pos(const char* name) { } static void stop_large_name() { - Rf_errorcall(R_NilValue, "Can't tidy up name because it is too large"); + r_abort_call(r_null, "Can't tidy up name because it is too large"); } -static bool needs_suffix(SEXP str) { +static bool needs_suffix(r_obj* str) { return - str == NA_STRING || + str == r_globals.na_str || str == strings_dots || str == strings_empty || - is_dotdotint(CHAR(str)); + is_dotdotint(r_str_c_string(str)); } - -static SEXP names_iota(R_len_t n); -static SEXP vec_unique_names_impl(SEXP names, R_len_t n, bool quiet); - -// [[ register() ]] -SEXP vctrs_unique_names(SEXP x, SEXP quiet) { +r_obj* ffi_unique_names(r_obj* x, r_obj* quiet) { return vec_unique_names(x, LOGICAL(quiet)[0]); } -// [[ include("utils.h") ]] -SEXP vec_unique_names(SEXP x, bool quiet) { - SEXP names = PROTECT(vec_names(x)); - SEXP out = vec_unique_names_impl(names, vec_size(x), quiet); - UNPROTECT(1); +r_obj* vec_unique_names(r_obj* x, bool quiet) { + r_obj* names = KEEP(vec_names(x)); + r_obj* out = vec_unique_names_impl(names, vec_size(x), quiet); + FREE(1); return out; } -// [[ include("utils.h") ]] -SEXP vec_unique_colnames(SEXP x, bool quiet) { - SEXP names = PROTECT(colnames(x)); - SEXP out = vec_unique_names_impl(names, Rf_ncols(x), quiet); - UNPROTECT(1); +r_obj* vec_unique_colnames(r_obj* x, bool quiet) { + r_obj* names = KEEP(colnames(x)); + r_obj* out = vec_unique_names_impl(names, Rf_ncols(x), quiet); + FREE(1); return out; } -static SEXP vec_unique_names_impl(SEXP names, R_len_t n, bool quiet) { - SEXP out; - if (names == R_NilValue) { - out = PROTECT(names_iota(n)); +static +r_obj* vec_unique_names_impl(r_obj* names, r_ssize n, bool quiet) { + r_obj* out; + if (names == r_null) { + out = KEEP(names_iota(n)); if (!quiet) { describe_repair(names, out); } } else { - out = PROTECT(vec_as_unique_names(names, quiet)); + out = KEEP(vec_as_unique_names(names, quiet)); } - UNPROTECT(1); + FREE(1); return(out); } -static SEXP names_iota(R_len_t n) { +static +r_obj* names_iota(r_ssize n) { char buf[MAX_IOTA_SIZE]; - SEXP nms = r_chr_iota(n, buf, MAX_IOTA_SIZE, "..."); + r_obj* nms = r_chr_iota(n, buf, MAX_IOTA_SIZE, "..."); - if (nms == R_NilValue) { - Rf_errorcall(R_NilValue, "Too many names to repair."); + if (nms == r_null) { + r_abort_call(r_null, "Too many names to repair."); } return nms; @@ -485,44 +450,44 @@ static SEXP names_iota(R_len_t n) { -static void describe_repair(SEXP old_names, SEXP new_names) { - SEXP call = PROTECT(Rf_lang3(Rf_install("describe_repair"), - old_names, new_names)); - Rf_eval(call, vctrs_ns_env); +static +void describe_repair(r_obj* old_names, r_obj* new_names) { + r_obj* call = KEEP(r_call3(r_sym("describe_repair"), + old_names, + new_names)); + r_eval(call, vctrs_ns_env); // To reset visibility when called from a `.External2()` - Rf_eval(R_NilValue, R_EmptyEnv); + r_eval(r_null, r_envs.empty); - UNPROTECT(1); + FREE(1); } -// [[ register() ]] -SEXP vctrs_outer_names(SEXP names, SEXP outer, SEXP n) { - if (names != R_NilValue && TYPEOF(names) != STRSXP) { +r_obj* ffi_outer_names(r_obj* names, r_obj* outer, r_obj* n) { + if (names != r_null && r_typeof(names) != R_TYPE_character) { r_stop_internal("`names` must be `NULL` or a string."); } if (!r_is_number(n)) { r_stop_internal("`n` must be a single integer."); } - if (outer != R_NilValue) { + if (outer != r_null) { outer = r_chr_get(outer, 0); } return outer_names(names, outer, r_int_get(n, 0)); } -// [[ include("utils.h") ]] -SEXP outer_names(SEXP names, SEXP outer, R_len_t n) { - if (outer == R_NilValue) { +r_obj* outer_names(r_obj* names, r_obj* outer, r_ssize n) { + if (outer == r_null) { return names; } - if (TYPEOF(outer) != CHARSXP) { + if (r_typeof(outer) != R_TYPE_string) { r_stop_internal("`outer` must be a scalar string."); } - if (outer == strings_empty || outer == NA_STRING) { + if (outer == strings_empty || outer == r_globals.na_str) { return names; } @@ -530,35 +495,31 @@ SEXP outer_names(SEXP names, SEXP outer, R_len_t n) { if (n == 1) { return r_str_as_character(outer); } else { - return r_seq_chr(CHAR(outer), n); + return r_seq_chr(r_str_c_string(outer), n); } } else { - return r_chr_paste_prefix(names, CHAR(outer), ".."); + return r_chr_paste_prefix(names, r_str_c_string(outer), ".."); } } -// [[ register() ]] -SEXP vctrs_apply_name_spec(SEXP name_spec, SEXP outer, SEXP inner, SEXP n) { +r_obj* ffi_apply_name_spec(r_obj* name_spec, r_obj* outer, r_obj* inner, r_obj* n) { return apply_name_spec(name_spec, r_chr_get(outer, 0), inner, r_int_get(n, 0)); } -static SEXP glue_as_name_spec(SEXP spec); - -// [[ include("utils.h") ]] -SEXP apply_name_spec(SEXP name_spec, SEXP outer, SEXP inner, R_len_t n) { - if (Rf_inherits(name_spec, "rlang_zap")) { - return R_NilValue; +r_obj* apply_name_spec(r_obj* name_spec, r_obj* outer, r_obj* inner, r_ssize n) { + if (r_inherits(name_spec, "rlang_zap")) { + return r_null; } - if (outer == R_NilValue) { + if (outer == r_null) { return inner; } - if (TYPEOF(outer) != CHARSXP) { + if (r_typeof(outer) != R_TYPE_string) { r_stop_internal("`outer` must be a scalar string."); } - if (outer == strings_empty || outer == NA_STRING) { - if (inner == R_NilValue) { + if (outer == strings_empty || outer == r_globals.na_str) { + if (inner == r_null) { return chrs_empty; } else { return inner; @@ -572,56 +533,53 @@ SEXP apply_name_spec(SEXP name_spec, SEXP outer, SEXP inner, R_len_t n) { if (n == 1) { return r_str_as_character(outer); } - inner = PROTECT(r_seq(1, n + 1)); + inner = KEEP(r_seq(1, n + 1)); } else { - inner = PROTECT(inner); + inner = KEEP(inner); } - switch (TYPEOF(name_spec)) { - case CLOSXP: + switch (r_typeof(name_spec)) { + case R_TYPE_closure: break; - case STRSXP: + case R_TYPE_character: name_spec = glue_as_name_spec(name_spec); break; default: name_spec = r_as_function(name_spec, ".name_spec"); break; - case NILSXP: - Rf_errorcall(R_NilValue, + case R_TYPE_null: + r_abort_call(r_null, "Can't merge the outer name `%s` with a vector of length > 1.\n" "Please supply a `.name_spec` specification.", - CHAR(outer)); + r_str_c_string(outer)); } - PROTECT(name_spec); + KEEP(name_spec); - SEXP outer_chr = PROTECT(r_str_as_character(outer)); + r_obj* outer_chr = KEEP(r_str_as_character(outer)); - SEXP out = PROTECT(vctrs_dispatch2(syms_dot_name_spec, name_spec, - syms_outer, outer_chr, - syms_inner, inner)); + r_obj* out = KEEP(vctrs_dispatch2(syms_dot_name_spec, name_spec, + syms_outer, outer_chr, + syms_inner, inner)); out = vec_recycle(out, n); - if (out != R_NilValue) { - if (TYPEOF(out) != STRSXP) { - Rf_errorcall(R_NilValue, "`.name_spec` must return a character vector."); + if (out != r_null) { + if (r_typeof(out) != R_TYPE_character) { + r_abort_call(r_null, "`.name_spec` must return a character vector."); } - if (Rf_length(out) != n) { - Rf_errorcall(R_NilValue, "`.name_spec` must return a character vector as long as `inner`."); + if (r_length(out) != n) { + r_abort_call(r_null, "`.name_spec` must return a character vector as long as `inner`."); } } - UNPROTECT(4); + FREE(4); return out; } -static SEXP syms_glue_as_name_spec = NULL; -static SEXP fns_glue_as_name_spec = NULL; -static SEXP syms_internal_spec = NULL; - -static SEXP glue_as_name_spec(SEXP spec) { +static +r_obj* glue_as_name_spec(r_obj* spec) { if (!r_is_string(spec)) { - Rf_errorcall(R_NilValue, "Glue specification in `.name_spec` must be a single string."); + r_abort_call(r_null, "Glue specification in `.name_spec` must be a single string."); } return vctrs_dispatch1(syms_glue_as_name_spec, fns_glue_as_name_spec, syms_internal_spec, spec); @@ -630,12 +588,11 @@ static SEXP glue_as_name_spec(SEXP spec) { #define VCTRS_PASTE_BUFFER_MAX_SIZE 4096 char vctrs_paste_buffer[VCTRS_PASTE_BUFFER_MAX_SIZE]; -// [[ include("names.h") ]] -SEXP r_chr_paste_prefix(SEXP names, const char* prefix, const char* sep) { - int n_protect = 0; +r_obj* r_chr_paste_prefix(r_obj* names, const char* prefix, const char* sep) { + int n_prot = 0; - names = PROTECT_N(Rf_shallow_duplicate(names), &n_protect); - R_len_t n = Rf_length(names); + names = KEEP_N(r_clone(names), &n_prot); + r_ssize n = r_length(names); int outer_len = strlen(prefix); int names_len = r_chr_max_len(names); @@ -645,9 +602,9 @@ SEXP r_chr_paste_prefix(SEXP names, const char* prefix, const char* sep) { char* buf = vctrs_paste_buffer; if (total_len > VCTRS_PASTE_BUFFER_MAX_SIZE) { - SEXP buf_box = PROTECT_N( - Rf_allocVector(RAWSXP, total_len * sizeof(char)), - &n_protect + r_obj* buf_box = KEEP_N( + r_alloc_raw(total_len * sizeof(char)), + &n_prot ); buf = (char*) RAW(buf_box); } @@ -661,31 +618,29 @@ SEXP r_chr_paste_prefix(SEXP names, const char* prefix, const char* sep) { *bufp++ = sep[i]; } - SEXP const* p_names = STRING_PTR_RO(names); + r_obj* const* p_names = r_chr_cbegin(names); - for (R_len_t i = 0; i < n; ++i) { - const char* inner = CHAR(p_names[i]); + for (r_ssize i = 0; i < n; ++i) { + const char* inner = r_str_c_string(p_names[i]); int inner_n = strlen(inner); memcpy(bufp, inner, inner_n); bufp[inner_n] = '\0'; - SET_STRING_ELT(names, i, r_str(buf)); + r_chr_poke(names, i, r_str(buf)); } - UNPROTECT(n_protect); + FREE(n_prot); return names; } -// [[ register() ]] -SEXP vctrs_chr_paste_prefix(SEXP names, SEXP prefix, SEXP sep) { +r_obj* ffi_chr_paste_prefix(r_obj* names, r_obj* prefix, r_obj* sep) { return r_chr_paste_prefix(names, r_chr_get_c_string(prefix, 0), r_chr_get_c_string(sep, 0)); } -// [[ include("names.h") ]] -SEXP r_seq_chr(const char* prefix, R_len_t n) { +r_obj* r_seq_chr(const char* prefix, r_ssize n) { int total_len = 24 + strlen(prefix) + 1; R_CheckStack2(total_len); @@ -695,45 +650,40 @@ SEXP r_seq_chr(const char* prefix, R_len_t n) { } -// Initialised at load time -SEXP syms_set_rownames_dispatch = NULL; -SEXP fns_set_rownames_dispatch = NULL; - -static SEXP set_rownames_dispatch(SEXP x, SEXP names) { +static +r_obj* set_rownames_dispatch(r_obj* x, r_obj* names) { return vctrs_dispatch2(syms_set_rownames_dispatch, fns_set_rownames_dispatch, syms_x, x, syms_names, names); } -// Initialised at load time -SEXP syms_set_names_dispatch = NULL; -SEXP fns_set_names_dispatch = NULL; - -static SEXP set_names_dispatch(SEXP x, SEXP names) { +static +r_obj* set_names_dispatch(r_obj* x, r_obj* names) { return vctrs_dispatch2(syms_set_names_dispatch, fns_set_names_dispatch, syms_x, x, syms_names, names); } -static void check_names(SEXP x, SEXP names) { - if (names == R_NilValue) { +static +void check_names(r_obj* x, r_obj* names) { + if (names == r_null) { return; } - if (TYPEOF(names) != STRSXP) { - Rf_errorcall( - R_NilValue, + if (r_typeof(names) != R_TYPE_character) { + r_abort_call( + r_null, "`names` must be a character vector, not a %s.", - Rf_type2char(TYPEOF(names)) + r_type_as_c_string(r_typeof(names)) ); } - R_len_t x_size = vec_size(x); - R_len_t names_size = vec_size(names); + r_ssize x_size = vec_size(x); + r_ssize names_size = vec_size(names); if (x_size != names_size) { - Rf_errorcall( - R_NilValue, + r_abort_call( + r_null, "The size of `names`, %i, must be the same as the size of `x`, %i.", names_size, x_size @@ -741,49 +691,49 @@ static void check_names(SEXP x, SEXP names) { } } -SEXP vec_set_rownames(SEXP x, SEXP names, bool proxy, const enum vctrs_owned owned) { - if (!proxy && OBJECT(x)) { +r_obj* vec_set_rownames(r_obj* x, r_obj* names, bool proxy, const enum vctrs_owned owned) { + if (!proxy && r_is_object(x)) { return set_rownames_dispatch(x, names); } int nprot = 0; - SEXP dim_names = Rf_getAttrib(x, R_DimNamesSymbol); + r_obj* dim_names = r_attrib_get(x, r_syms.dim_names); // Early exit when no new row names and no existing row names - if (names == R_NilValue) { - if (dim_names == R_NilValue || VECTOR_ELT(dim_names, 0) == R_NilValue) { + if (names == r_null) { + if (dim_names == r_null || r_list_get(dim_names, 0) == r_null) { return x; } } - x = PROTECT_N(vec_clone_referenced(x, owned), &nprot); + x = KEEP_N(vec_clone_referenced(x, owned), &nprot); - if (dim_names == R_NilValue) { - dim_names = PROTECT_N(Rf_allocVector(VECSXP, vec_dim_n(x)), &nprot); + if (dim_names == r_null) { + dim_names = KEEP_N(r_alloc_list(vec_dim_n(x)), &nprot); } else { // Also clone attribute - dim_names = PROTECT_N(Rf_shallow_duplicate(dim_names), &nprot); + dim_names = KEEP_N(r_clone(dim_names), &nprot); } - SET_VECTOR_ELT(dim_names, 0, names); + r_list_poke(dim_names, 0, names); - Rf_setAttrib(x, R_DimNamesSymbol, dim_names); + r_attrib_poke(x, r_syms.dim_names, dim_names); - UNPROTECT(nprot); + FREE(nprot); return x; } -SEXP vec_set_df_rownames(SEXP x, SEXP names, bool proxy, const enum vctrs_owned owned) { - if (names == R_NilValue) { +r_obj* vec_set_df_rownames(r_obj* x, r_obj* names, bool proxy, const enum vctrs_owned owned) { + if (names == r_null) { if (rownames_type(df_rownames(x)) != ROWNAMES_IDENTIFIERS) { return(x); } - x = PROTECT(vec_clone_referenced(x, owned)); + x = KEEP(vec_clone_referenced(x, owned)); init_compact_rownames(x, vec_size(x)); - UNPROTECT(1); + FREE(1); return x; } @@ -791,18 +741,18 @@ SEXP vec_set_df_rownames(SEXP x, SEXP names, bool proxy, const enum vctrs_owned if (!proxy) { names = vec_as_names(names, p_unique_repair_silent_opts); } - PROTECT(names); + KEEP(names); - x = PROTECT(vec_clone_referenced(x, owned)); - Rf_setAttrib(x, R_RowNamesSymbol, names); + x = KEEP(vec_clone_referenced(x, owned)); + r_attrib_poke(x, r_syms.row_names, names); - UNPROTECT(2); + FREE(2); return x; } // FIXME: Do we need to get the vec_proxy() and only fall back if it doesn't // exist? See #526 and #531 for discussion and the related issue. -SEXP vec_set_names_impl(SEXP x, SEXP names, bool proxy, const enum vctrs_owned owned) { +r_obj* vec_set_names_impl(r_obj* x, r_obj* names, bool proxy, const enum vctrs_owned owned) { check_names(x, names); if (is_data_frame(x)) { @@ -813,46 +763,45 @@ SEXP vec_set_names_impl(SEXP x, SEXP names, bool proxy, const enum vctrs_owned o return vec_set_rownames(x, names, proxy, owned); } - if (!proxy && OBJECT(x)) { + if (!proxy && r_is_object(x)) { return set_names_dispatch(x, names); } // Early exit if no new names and no existing names - if (names == R_NilValue && Rf_getAttrib(x, R_NamesSymbol) == R_NilValue) { + if (names == r_null && r_attrib_get(x, r_syms.names) == r_null) { return x; } if (owned) { // Possibly skip the cloning altogether - x = PROTECT(vec_clone_referenced(x, owned)); - Rf_setAttrib(x, R_NamesSymbol, names); + x = KEEP(vec_clone_referenced(x, owned)); + r_attrib_poke(x, r_syms.names, names); } else { // We need to clone, but to do this we will use `names<-` // which can perform a cheaper ALTREP shallow duplication - x = PROTECT(set_names_dispatch(x, names)); + x = KEEP(set_names_dispatch(x, names)); } - UNPROTECT(1); + FREE(1); return x; } -// [[ include("utils.h"); register() ]] -SEXP vec_set_names(SEXP x, SEXP names) { +// [[ register() ]] +r_obj* vec_set_names(r_obj* x, r_obj* names) { return vec_set_names_impl(x, names, false, VCTRS_OWNED_false); } -// [[ include("utils.h") ]] -SEXP vec_proxy_set_names(SEXP x, SEXP names, const enum vctrs_owned owned) { +r_obj* vec_proxy_set_names(r_obj* x, r_obj* names, const enum vctrs_owned owned) { return vec_set_names_impl(x, names, true, owned); } -SEXP vctrs_validate_name_repair_arg(SEXP arg) { +r_obj* vctrs_validate_name_repair_arg(r_obj* arg) { struct name_repair_opts opts = new_name_repair_opts(arg, vec_args.empty, true, r_lazy_null); if (opts.type == name_repair_custom) { return opts.fn; - } else if (Rf_length(arg) != 1) { + } else if (r_length(arg) != 1) { return r_str_as_character(r_str(name_repair_arg_as_c_string(opts.type))); } else { return arg; @@ -860,7 +809,7 @@ SEXP vctrs_validate_name_repair_arg(SEXP arg) { } void stop_name_repair() { - Rf_errorcall(R_NilValue, "`.name_repair` must be a string or a function. See `?vctrs::vec_as_names`."); + r_abort_call(r_null, "`.name_repair` must be a string or a function. See `?vctrs::vec_as_names`."); } struct name_repair_opts new_name_repair_opts(r_obj* name_repair, @@ -876,13 +825,13 @@ struct name_repair_opts new_name_repair_opts(r_obj* name_repair, .call = call }; - switch (TYPEOF(name_repair)) { - case STRSXP: { - if (!Rf_length(name_repair)) { + switch (r_typeof(name_repair)) { + case R_TYPE_character: { + if (!r_length(name_repair)) { stop_name_repair(); } - SEXP c = r_chr_get(name_repair, 0); + r_obj* c = r_chr_get(name_repair, 0); if (c == strings_none) { opts.type = name_repair_none; @@ -895,19 +844,19 @@ struct name_repair_opts new_name_repair_opts(r_obj* name_repair, } else if (c == strings_check_unique) { opts.type = name_repair_check_unique; } else { - Rf_errorcall(R_NilValue, "`.name_repair` can't be \"%s\". See `?vctrs::vec_as_names`.", CHAR(c)); + r_abort_call(r_null, "`.name_repair` can't be \"%s\". See `?vctrs::vec_as_names`.", r_str_c_string(c)); } return opts; } - case LANGSXP: + case R_TYPE_call: opts.fn = r_as_function(name_repair, ".name_repair"); opts.shelter = opts.fn; opts.type = name_repair_custom; return opts; - case CLOSXP: + case R_TYPE_closure: opts.fn = name_repair; opts.type = name_repair_custom; return opts; @@ -919,7 +868,6 @@ struct name_repair_opts new_name_repair_opts(r_obj* name_repair, never_reached("new_name_repair_opts"); } -// [[ include("vctrs.h") ]] const char* name_repair_arg_as_c_string(enum name_repair_type type) { switch (type) { case name_repair_none: return "none"; @@ -932,34 +880,35 @@ const char* name_repair_arg_as_c_string(enum name_repair_type type) { never_reached("name_repair_arg_as_c_string"); } -static void vec_validate_minimal_names(SEXP names, R_len_t n) { - if (names == R_NilValue) { - Rf_errorcall(R_NilValue, "Names repair functions can't return `NULL`."); +static +void vec_validate_minimal_names(r_obj* names, r_ssize n) { + if (names == r_null) { + r_abort_call(r_null, "Names repair functions can't return `NULL`."); } - if (TYPEOF(names) != STRSXP) { - Rf_errorcall(R_NilValue, "Names repair functions must return a character vector."); + if (r_typeof(names) != R_TYPE_character) { + r_abort_call(r_null, "Names repair functions must return a character vector."); } - if (n >= 0 && Rf_length(names) != n) { - Rf_errorcall(R_NilValue, + if (n >= 0 && r_length(names) != n) { + r_abort_call(r_null, "Repaired names have length %d instead of length %d.", - Rf_length(names), + r_length(names), n); } - if (r_chr_has_string(names, NA_STRING)) { - Rf_errorcall(R_NilValue, "Names repair functions can't return `NA` values."); + if (r_chr_has_string(names, r_globals.na_str)) { + r_abort_call(r_null, "Names repair functions can't return `NA` values."); } } -SEXP vctrs_validate_minimal_names(SEXP names, SEXP n_) { - R_len_t n = -1; +r_obj* vctrs_validate_minimal_names(r_obj* names, r_obj* n_) { + r_ssize n = -1; - if (TYPEOF(n_) == INTSXP) { - if (Rf_length(n_) != 1) { + if (r_typeof(n_) == R_TYPE_integer) { + if (r_length(n_) != 1) { r_stop_internal("`n` must be a single number."); } - n = INTEGER(n_)[0]; + n = r_int_get(n_, 0); } vec_validate_minimal_names(names, n); @@ -971,30 +920,43 @@ struct name_repair_opts unique_repair_default_opts; struct name_repair_opts unique_repair_silent_opts; struct name_repair_opts no_repair_opts; -void vctrs_init_names(SEXP ns) { - syms_set_rownames_dispatch = Rf_install("set_rownames_dispatch"); - syms_set_names_dispatch = Rf_install("set_names_dispatch"); - syms_as_universal_names = Rf_install("as_universal_names"); - syms_check_unique_names = Rf_install("validate_unique"); +void vctrs_init_names(r_obj* ns) { + syms_set_rownames_dispatch = r_sym("set_rownames_dispatch"); + syms_set_names_dispatch = r_sym("set_names_dispatch"); + syms_as_universal_names = r_sym("as_universal_names"); + syms_check_unique_names = r_sym("validate_unique"); fns_set_rownames_dispatch = r_env_get(ns, syms_set_rownames_dispatch); fns_set_names_dispatch = r_env_get(ns, syms_set_names_dispatch); fns_as_universal_names = r_env_get(ns, syms_as_universal_names); fns_check_unique_names = r_env_get(ns, syms_check_unique_names); - syms_glue_as_name_spec = Rf_install("glue_as_name_spec"); + syms_glue_as_name_spec = r_sym("glue_as_name_spec"); fns_glue_as_name_spec = r_env_get(ns, syms_glue_as_name_spec); - syms_internal_spec = Rf_install("_spec"); + syms_internal_spec = r_sym("_spec"); unique_repair_default_opts.type = name_repair_unique; - unique_repair_default_opts.fn = R_NilValue; + unique_repair_default_opts.fn = r_null; unique_repair_default_opts.quiet = false; unique_repair_silent_opts.type = name_repair_unique; - unique_repair_silent_opts.fn = R_NilValue; + unique_repair_silent_opts.fn = r_null; unique_repair_silent_opts.quiet = true; no_repair_opts.type = name_repair_none; - no_repair_opts.fn = R_NilValue; + no_repair_opts.fn = r_null; no_repair_opts.quiet = true; } + +static r_obj* syms_as_universal_names = NULL; +static r_obj* syms_check_unique_names = NULL; +static r_obj* syms_glue_as_name_spec = NULL; +static r_obj* syms_internal_spec = NULL; +static r_obj* syms_set_rownames_dispatch = NULL; +static r_obj* syms_set_names_dispatch = NULL; + +static r_obj* fns_as_universal_names = NULL; +static r_obj* fns_check_unique_names = NULL; +static r_obj* fns_glue_as_name_spec = NULL; +static r_obj* fns_set_rownames_dispatch = NULL; +static r_obj* fns_set_names_dispatch = NULL; diff --git a/src/names.h b/src/names.h index 9d1e70a60..d81063218 100644 --- a/src/names.h +++ b/src/names.h @@ -2,9 +2,18 @@ #define VCTRS_NAMES_H #include "vctrs-core.h" +#include "owned.h" #include "utils.h" +r_obj* vec_names(r_obj* x); r_obj* vec_names2(r_obj* x); +r_obj* vec_proxy_names(r_obj* x); + +r_obj* vec_unique_names(r_obj* x, bool quiet); +r_obj* vec_unique_colnames(r_obj* x, bool quiet); + +r_obj* outer_names(r_obj* names, r_obj* outer, r_ssize n); +r_obj* apply_name_spec(r_obj* name_spec, r_obj* outer, r_obj* inner, r_ssize n); enum name_repair_type { name_repair_none = 0, @@ -24,6 +33,9 @@ struct name_repair_opts { struct r_lazy call; }; +r_obj* vec_as_universal_names(r_obj* names, bool quiet); +r_obj* vec_as_custom_names(r_obj* names, const struct name_repair_opts* opts); + extern struct name_repair_opts unique_repair_default_opts; extern struct name_repair_opts unique_repair_silent_opts; extern struct name_repair_opts no_repair_opts; @@ -32,20 +44,20 @@ static struct name_repair_opts const * const p_unique_repair_default_opts = &uni static struct name_repair_opts const * const p_unique_repair_silent_opts = &unique_repair_silent_opts; static struct name_repair_opts const * const p_no_repair_opts = &no_repair_opts; -SEXP vec_as_names(SEXP names, const struct name_repair_opts* opts); +r_obj* vec_as_names(r_obj* names, const struct name_repair_opts* opts); struct name_repair_opts new_name_repair_opts(r_obj* name_repair, struct vctrs_arg* name_repair_arg, bool quiet, struct r_lazy call); const char* name_repair_arg_as_c_string(enum name_repair_type type); -bool is_unique_names(SEXP names); -SEXP vec_as_unique_names(SEXP names, bool quiet); +bool is_unique_names(r_obj* names); +r_obj* vec_as_unique_names(r_obj* names, bool quiet); -SEXP r_seq_chr(const char* prefix, R_len_t n); -SEXP r_chr_paste_prefix(SEXP names, const char* prefix, const char* sep); +r_obj* r_seq_chr(const char* prefix, r_ssize n); +r_obj* r_chr_paste_prefix(r_obj* names, const char* prefix, const char* sep); -#include "owned.h" -SEXP vec_proxy_set_names(SEXP x, SEXP names, const enum vctrs_owned owned); +r_obj* vec_set_names(r_obj* x, r_obj* names); +r_obj* vec_proxy_set_names(r_obj* x, r_obj* names, const enum vctrs_owned owned); #endif diff --git a/src/utils.h b/src/utils.h index 924e63687..82f73b293 100644 --- a/src/utils.h +++ b/src/utils.h @@ -132,9 +132,6 @@ SEXP int_resize(SEXP x, r_ssize x_size, r_ssize size); SEXP raw_resize(SEXP x, r_ssize x_size, r_ssize size); SEXP chr_resize(SEXP x, r_ssize x_size, r_ssize size); -SEXP vec_unique_names(SEXP x, bool quiet); -SEXP vec_unique_colnames(SEXP x, bool quiet); - // Returns S3 / S4 method for `generic` suitable for the class of `x`. The // inheritance hierarchy is explored except for the default method. SEXP s3_get_method(const char* generic, const char* cls, SEXP table); @@ -198,9 +195,6 @@ bool is_integer64(SEXP x); bool lgl_any_na(SEXP x); -SEXP apply_name_spec(SEXP name_spec, SEXP outer, SEXP inner, R_len_t n); -SEXP outer_names(SEXP names, SEXP outer, R_len_t n); -SEXP vec_set_names(SEXP x, SEXP names); SEXP colnames(SEXP x); r_obj* colnames2(r_obj* x); diff --git a/tests/testthat/_snaps/bind.md b/tests/testthat/_snaps/bind.md index 388177054..a479474f8 100644 --- a/tests/testthat/_snaps/bind.md +++ b/tests/testthat/_snaps/bind.md @@ -75,8 +75,10 @@ Code (expect_error(vec_rbind(foo = df1, df2, .names_to = NULL), "specification")) Output - 1. - Please supply a `.name_spec` specification.> + + Error: + ! Can't merge the outer name `foo` with a vector of length > 1. + Please supply a `.name_spec` specification. # vec_cbind() reports error context diff --git a/tests/testthat/test-names.R b/tests/testthat/test-names.R index 6e72b7a7f..e1018db7e 100644 --- a/tests/testthat/test-names.R +++ b/tests/testthat/test-names.R @@ -840,7 +840,7 @@ test_that("r_chr_paste_prefix() works", { nms <- c("foo", "bar") expect_equal( - .Call(vctrs_chr_paste_prefix, nms, "baz", "."), + .Call(ffi_chr_paste_prefix, nms, "baz", "."), c("baz.foo", "baz.bar") ) @@ -848,7 +848,7 @@ test_that("r_chr_paste_prefix() works", { long_prefix <- strrep("a", 5000) expect_equal( - .Call(vctrs_chr_paste_prefix, nms, long_prefix, "."), + .Call(ffi_chr_paste_prefix, nms, long_prefix, "."), paste0(long_prefix, ".", nms) ) }) From 404e56ab1e13b75e37d4092d0b3d80312077ee3a Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Fri, 2 Sep 2022 15:37:37 +0200 Subject: [PATCH 011/312] Update style of `enum name_repair_opts` --- src/bind.c | 12 ++++++------ src/c-unchop.c | 2 +- src/interval.c | 2 +- src/names.c | 46 +++++++++++++++++++++++----------------------- src/names.h | 12 ++++++------ src/type-factor.c | 2 +- 6 files changed, 38 insertions(+), 38 deletions(-) diff --git a/src/bind.c b/src/bind.c index db0fb696a..4e8ddb018 100644 --- a/src/bind.c +++ b/src/bind.c @@ -330,7 +330,7 @@ r_obj* as_df_row_impl(r_obj* x, // [[ register() ]] r_obj* ffi_as_df_row(r_obj* x, r_obj* quiet, r_obj* frame) { struct name_repair_opts name_repair_opts = { - .type = name_repair_unique, + .type = NAME_REPAIR_unique, .fn = r_null, .quiet = r_lgl_get(quiet, 0) }; @@ -624,12 +624,12 @@ struct name_repair_opts validate_bind_name_repair(r_obj* name_repair, bool allow r_lazy_null); switch (opts.type) { - case name_repair_custom: - case name_repair_unique: - case name_repair_universal: - case name_repair_check_unique: + case NAME_REPAIR_custom: + case NAME_REPAIR_unique: + case NAME_REPAIR_universal: + case NAME_REPAIR_check_unique: break; - case name_repair_minimal: + case NAME_REPAIR_minimal: if (allow_minimal) break; // else fallthrough default: if (allow_minimal) { diff --git a/src/c-unchop.c b/src/c-unchop.c index ffd1957ba..66c477b94 100644 --- a/src/c-unchop.c +++ b/src/c-unchop.c @@ -213,7 +213,7 @@ static SEXP vec_unchop_fallback(SEXP ptype, } const struct name_repair_opts name_repair_opts = { - .type = name_repair_none, + .type = NAME_REPAIR_none, .fn = R_NilValue }; diff --git a/src/interval.c b/src/interval.c index e9895f601..975194ef4 100644 --- a/src/interval.c +++ b/src/interval.c @@ -667,7 +667,7 @@ r_obj* vec_interval_complement(r_obj* start, r_obj* args = KEEP_N(r_new_list(2), &n_prot); const struct name_repair_opts name_repair_opts = { - .type = name_repair_none, + .type = NAME_REPAIR_none, .fn = R_NilValue }; diff --git a/src/names.c b/src/names.c index 967934908..402eede55 100644 --- a/src/names.c +++ b/src/names.c @@ -12,12 +12,12 @@ r_obj* vec_as_names(r_obj* names, const struct name_repair_opts* opts) { return names; } switch (opts->type) { - case name_repair_none: return names; - case name_repair_minimal: return ffi_as_minimal_names(names); - case name_repair_unique: return vec_as_unique_names(names, opts->quiet); - case name_repair_universal: return vec_as_universal_names(names, opts->quiet); - case name_repair_check_unique: return check_unique_names(names, opts); - case name_repair_custom: return vec_as_custom_names(names, opts); + case NAME_REPAIR_none: return names; + case NAME_REPAIR_minimal: return ffi_as_minimal_names(names); + case NAME_REPAIR_unique: return vec_as_unique_names(names, opts->quiet); + case NAME_REPAIR_universal: return vec_as_universal_names(names, opts->quiet); + case NAME_REPAIR_check_unique: return check_unique_names(names, opts); + case NAME_REPAIR_custom: return vec_as_custom_names(names, opts); } never_reached("vec_as_names"); } @@ -799,7 +799,7 @@ r_obj* vctrs_validate_name_repair_arg(r_obj* arg) { vec_args.empty, true, r_lazy_null); - if (opts.type == name_repair_custom) { + if (opts.type == NAME_REPAIR_custom) { return opts.fn; } else if (r_length(arg) != 1) { return r_str_as_character(r_str(name_repair_arg_as_c_string(opts.type))); @@ -834,15 +834,15 @@ struct name_repair_opts new_name_repair_opts(r_obj* name_repair, r_obj* c = r_chr_get(name_repair, 0); if (c == strings_none) { - opts.type = name_repair_none; + opts.type = NAME_REPAIR_none; } else if (c == strings_minimal) { - opts.type = name_repair_minimal; + opts.type = NAME_REPAIR_minimal; } else if (c == strings_unique) { - opts.type = name_repair_unique; + opts.type = NAME_REPAIR_unique; } else if (c == strings_universal) { - opts.type = name_repair_universal; + opts.type = NAME_REPAIR_universal; } else if (c == strings_check_unique) { - opts.type = name_repair_check_unique; + opts.type = NAME_REPAIR_check_unique; } else { r_abort_call(r_null, "`.name_repair` can't be \"%s\". See `?vctrs::vec_as_names`.", r_str_c_string(c)); } @@ -853,12 +853,12 @@ struct name_repair_opts new_name_repair_opts(r_obj* name_repair, case R_TYPE_call: opts.fn = r_as_function(name_repair, ".name_repair"); opts.shelter = opts.fn; - opts.type = name_repair_custom; + opts.type = NAME_REPAIR_custom; return opts; case R_TYPE_closure: opts.fn = name_repair; - opts.type = name_repair_custom; + opts.type = NAME_REPAIR_custom; return opts; default: @@ -870,12 +870,12 @@ struct name_repair_opts new_name_repair_opts(r_obj* name_repair, const char* name_repair_arg_as_c_string(enum name_repair_type type) { switch (type) { - case name_repair_none: return "none"; - case name_repair_minimal: return "minimal"; - case name_repair_unique: return "unique"; - case name_repair_universal: return "universal"; - case name_repair_check_unique: return "check_unique"; - case name_repair_custom: return "custom"; + case NAME_REPAIR_none: return "none"; + case NAME_REPAIR_minimal: return "minimal"; + case NAME_REPAIR_unique: return "unique"; + case NAME_REPAIR_universal: return "universal"; + case NAME_REPAIR_check_unique: return "check_unique"; + case NAME_REPAIR_custom: return "custom"; } never_reached("name_repair_arg_as_c_string"); } @@ -935,15 +935,15 @@ void vctrs_init_names(r_obj* ns) { fns_glue_as_name_spec = r_env_get(ns, syms_glue_as_name_spec); syms_internal_spec = r_sym("_spec"); - unique_repair_default_opts.type = name_repair_unique; + unique_repair_default_opts.type = NAME_REPAIR_unique; unique_repair_default_opts.fn = r_null; unique_repair_default_opts.quiet = false; - unique_repair_silent_opts.type = name_repair_unique; + unique_repair_silent_opts.type = NAME_REPAIR_unique; unique_repair_silent_opts.fn = r_null; unique_repair_silent_opts.quiet = true; - no_repair_opts.type = name_repair_none; + no_repair_opts.type = NAME_REPAIR_none; no_repair_opts.fn = r_null; no_repair_opts.quiet = true; } diff --git a/src/names.h b/src/names.h index d81063218..35ca59855 100644 --- a/src/names.h +++ b/src/names.h @@ -16,12 +16,12 @@ r_obj* outer_names(r_obj* names, r_obj* outer, r_ssize n); r_obj* apply_name_spec(r_obj* name_spec, r_obj* outer, r_obj* inner, r_ssize n); enum name_repair_type { - name_repair_none = 0, - name_repair_minimal, - name_repair_unique, - name_repair_universal, - name_repair_check_unique, - name_repair_custom = 99 + NAME_REPAIR_none = 0, + NAME_REPAIR_minimal, + NAME_REPAIR_unique, + NAME_REPAIR_universal, + NAME_REPAIR_check_unique, + NAME_REPAIR_custom = 99 }; struct name_repair_opts { diff --git a/src/type-factor.c b/src/type-factor.c index 6443fef9b..3c2bc45eb 100644 --- a/src/type-factor.c +++ b/src/type-factor.c @@ -67,7 +67,7 @@ static SEXP levels_union(SEXP x, SEXP y) { SET_VECTOR_ELT(args, 1, y); const struct name_repair_opts name_repair_opts = { - .type = name_repair_none, + .type = NAME_REPAIR_none, .fn = R_NilValue }; From b0da1aa343fd455d78f9ae8b1ced56d8c7a65a62 Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Fri, 2 Sep 2022 14:24:18 +0200 Subject: [PATCH 012/312] Fix indentation --- src/proxy.c | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/src/proxy.c b/src/proxy.c index 983579cfe..bbc6dc0bc 100644 --- a/src/proxy.c +++ b/src/proxy.c @@ -93,9 +93,9 @@ r_obj* vec_proxy_order_method(r_obj* x) { static inline r_obj* vec_proxy_invoke_impl(r_obj* x, - r_obj* method, - r_obj* vec_proxy_sym, - r_obj* (*vec_proxy_fn)(r_obj*)) { + r_obj* method, + r_obj* vec_proxy_sym, + r_obj* (*vec_proxy_fn)(r_obj*)) { if (method != r_null) { return vctrs_dispatch1(vec_proxy_sym, method, syms_x, x); } From d518f759c1d64c64a5b7c50d41d44f7daf190f4b Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Mon, 5 Sep 2022 15:10:03 +0200 Subject: [PATCH 013/312] Update `enum vctrs_dbl` style --- src/compare.h | 28 ++++++++++++++-------------- src/equal.h | 6 +++--- src/hash.c | 6 +++--- src/match-compare.h | 28 ++++++++++++++-------------- src/order-sortedness.c | 38 +++++++++++++++++++------------------- src/order.c | 8 ++++---- src/type-complex.h | 28 ++++++++++++++-------------- src/vctrs-core.c | 8 ++++---- src/vctrs-core.h | 10 +++++----- 9 files changed, 80 insertions(+), 80 deletions(-) diff --git a/src/compare.h b/src/compare.h index 6ab5e091f..d18ea088c 100644 --- a/src/compare.h +++ b/src/compare.h @@ -51,29 +51,29 @@ int int_compare_na_equal(int x, int y) { } static inline int dbl_compare_na_equal(double x, double y) { - enum vctrs_dbl_class x_class = dbl_classify(x); - enum vctrs_dbl_class y_class = dbl_classify(y); + enum vctrs_dbl x_class = dbl_classify(x); + enum vctrs_dbl y_class = dbl_classify(y); switch (x_class) { - case vctrs_dbl_number: { + case VCTRS_DBL_number: { switch (y_class) { - case vctrs_dbl_number: return dbl_compare_scalar(x, y); - case vctrs_dbl_missing: return 1; - case vctrs_dbl_nan: return 1; + case VCTRS_DBL_number: return dbl_compare_scalar(x, y); + case VCTRS_DBL_missing: return 1; + case VCTRS_DBL_nan: return 1; } } - case vctrs_dbl_missing: { + case VCTRS_DBL_missing: { switch (y_class) { - case vctrs_dbl_number: return -1; - case vctrs_dbl_missing: return 0; - case vctrs_dbl_nan: return 1; + case VCTRS_DBL_number: return -1; + case VCTRS_DBL_missing: return 0; + case VCTRS_DBL_nan: return 1; } } - case vctrs_dbl_nan: { + case VCTRS_DBL_nan: { switch (y_class) { - case vctrs_dbl_number: return -1; - case vctrs_dbl_missing: return -1; - case vctrs_dbl_nan: return 0; + case VCTRS_DBL_number: return -1; + case VCTRS_DBL_missing: return -1; + case VCTRS_DBL_nan: return 0; } } } diff --git a/src/equal.h b/src/equal.h index f45616771..55e482ab5 100644 --- a/src/equal.h +++ b/src/equal.h @@ -21,9 +21,9 @@ static inline int int_equal_na_equal(int x, int y) { } static inline int dbl_equal_na_equal(double x, double y) { switch (dbl_classify(x)) { - case vctrs_dbl_number: break; - case vctrs_dbl_missing: return dbl_classify(y) == vctrs_dbl_missing; - case vctrs_dbl_nan: return dbl_classify(y) == vctrs_dbl_nan; + case VCTRS_DBL_number: break; + case VCTRS_DBL_missing: return dbl_classify(y) == VCTRS_DBL_missing; + case VCTRS_DBL_nan: return dbl_classify(y) == VCTRS_DBL_nan; } return isnan(y) ? false : x == y; diff --git a/src/hash.c b/src/hash.c index 454b511fb..ac809722d 100644 --- a/src/hash.c +++ b/src/hash.c @@ -70,9 +70,9 @@ static inline uint32_t dbl_hash_scalar(const double* x) { // Hash all NAs and NaNs to same value (i.e. ignoring significand) switch (dbl_classify(val)) { - case vctrs_dbl_number: break; - case vctrs_dbl_missing: val = NA_REAL; break; - case vctrs_dbl_nan: val = R_NaN; break; + case VCTRS_DBL_number: break; + case VCTRS_DBL_missing: val = NA_REAL; break; + case VCTRS_DBL_nan: val = R_NaN; break; } return hash_double(val); diff --git a/src/match-compare.h b/src/match-compare.h index fd331dfb7..2db75c4f6 100644 --- a/src/match-compare.h +++ b/src/match-compare.h @@ -31,29 +31,29 @@ int int_order_compare_na_equal(int x, int y, bool nan_distinct) { } static inline int dbl_order_compare_na_equal(double x, double y, bool nan_distinct) { - enum vctrs_dbl_class x_class = dbl_classify(x); - enum vctrs_dbl_class y_class = dbl_classify(y); + enum vctrs_dbl x_class = dbl_classify(x); + enum vctrs_dbl y_class = dbl_classify(y); switch (x_class) { - case vctrs_dbl_number: { + case VCTRS_DBL_number: { switch (y_class) { - case vctrs_dbl_number: return dbl_compare_scalar(x, y); - case vctrs_dbl_missing: return 1; - case vctrs_dbl_nan: return 1; + case VCTRS_DBL_number: return dbl_compare_scalar(x, y); + case VCTRS_DBL_missing: return 1; + case VCTRS_DBL_nan: return 1; } } - case vctrs_dbl_missing: { + case VCTRS_DBL_missing: { switch (y_class) { - case vctrs_dbl_number: return -1; - case vctrs_dbl_missing: return 0; - case vctrs_dbl_nan: return nan_distinct ? -1 : 0; + case VCTRS_DBL_number: return -1; + case VCTRS_DBL_missing: return 0; + case VCTRS_DBL_nan: return nan_distinct ? -1 : 0; } } - case vctrs_dbl_nan: { + case VCTRS_DBL_nan: { switch (y_class) { - case vctrs_dbl_number: return -1; - case vctrs_dbl_missing: return nan_distinct ? 1 : 0; - case vctrs_dbl_nan: return 0; + case VCTRS_DBL_number: return -1; + case VCTRS_DBL_missing: return nan_distinct ? 1 : 0; + case VCTRS_DBL_nan: return 0; } } } diff --git a/src/order-sortedness.c b/src/order-sortedness.c index 8e9ccf778..e01dd426c 100644 --- a/src/order-sortedness.c +++ b/src/order-sortedness.c @@ -16,8 +16,8 @@ static inline int dbl_cmp(double x, double y, - enum vctrs_dbl_class x_type, - enum vctrs_dbl_class y_type, + enum vctrs_dbl x_type, + enum vctrs_dbl y_type, int direction, int na_order, int na_nan_order); @@ -53,7 +53,7 @@ enum vctrs_sortedness dbl_sortedness(const double* p_x, const int na_nan_order = nan_distinct ? na_order : 0; double previous = p_x[0]; - enum vctrs_dbl_class previous_type = dbl_classify(previous); + enum vctrs_dbl previous_type = dbl_classify(previous); r_ssize count = 0; @@ -61,7 +61,7 @@ enum vctrs_sortedness dbl_sortedness(const double* p_x, // (ties are not allowed so we can reverse the vector stably) for (r_ssize i = 1; i < size; ++i, ++count) { double current = p_x[i]; - enum vctrs_dbl_class current_type = dbl_classify(current); + enum vctrs_dbl current_type = dbl_classify(current); int cmp = dbl_cmp( current, @@ -107,7 +107,7 @@ enum vctrs_sortedness dbl_sortedness(const double* p_x, // reverse the ordering. for (r_ssize i = 1; i < size; ++i) { double current = p_x[i]; - enum vctrs_dbl_class current_type = dbl_classify(current); + enum vctrs_dbl current_type = dbl_classify(current); int cmp = dbl_cmp( current, @@ -154,29 +154,29 @@ static inline int dbl_cmp_numbers(double x, double y, int direction); static inline int dbl_cmp(double x, double y, - enum vctrs_dbl_class x_type, - enum vctrs_dbl_class y_type, + enum vctrs_dbl x_type, + enum vctrs_dbl y_type, int direction, int na_order, int na_nan_order) { switch (x_type) { - case vctrs_dbl_number: + case VCTRS_DBL_number: switch (y_type) { - case vctrs_dbl_number: return dbl_cmp_numbers(x, y, direction); - case vctrs_dbl_missing: return -na_order; - case vctrs_dbl_nan: return -na_order; + case VCTRS_DBL_number: return dbl_cmp_numbers(x, y, direction); + case VCTRS_DBL_missing: return -na_order; + case VCTRS_DBL_nan: return -na_order; } - case vctrs_dbl_missing: + case VCTRS_DBL_missing: switch (y_type) { - case vctrs_dbl_number: return na_order; - case vctrs_dbl_missing: return 0; - case vctrs_dbl_nan: return na_nan_order; + case VCTRS_DBL_number: return na_order; + case VCTRS_DBL_missing: return 0; + case VCTRS_DBL_nan: return na_nan_order; } - case vctrs_dbl_nan: + case VCTRS_DBL_nan: switch (y_type) { - case vctrs_dbl_number: return na_order; - case vctrs_dbl_missing: return -na_nan_order; - case vctrs_dbl_nan: return 0; + case VCTRS_DBL_number: return na_order; + case VCTRS_DBL_missing: return -na_nan_order; + case VCTRS_DBL_nan: return 0; } } never_reached("dbl_cmp"); diff --git a/src/order.c b/src/order.c index adae7a788..b6eba7448 100644 --- a/src/order.c +++ b/src/order.c @@ -2188,19 +2188,19 @@ void dbl_adjust_nan_distinct(const bool decreasing, for (r_ssize i = 0; i < size; ++i) { double elt = p_x_dbl[i]; - const enum vctrs_dbl_class type = dbl_classify(elt); + const enum vctrs_dbl type = dbl_classify(elt); switch (type) { - case vctrs_dbl_number: { + case VCTRS_DBL_number: { elt = elt * direction; p_x_u64[i] = dbl_map_to_uint64(elt); break; } - case vctrs_dbl_missing: { + case VCTRS_DBL_missing: { p_x_u64[i] = na_u64; break; } - case vctrs_dbl_nan: { + case VCTRS_DBL_nan: { p_x_u64[i] = nan_u64; break; } diff --git a/src/type-complex.h b/src/type-complex.h index 1054229f3..94fb919a6 100644 --- a/src/type-complex.h +++ b/src/type-complex.h @@ -17,27 +17,27 @@ r_complex cpl_normalise_missing(r_complex x) { const double na = r_globals.na_dbl; const double nan = R_NaN; - const enum vctrs_dbl_class r_type = dbl_classify(x.r); - const enum vctrs_dbl_class i_type = dbl_classify(x.i); + const enum vctrs_dbl r_type = dbl_classify(x.r); + const enum vctrs_dbl i_type = dbl_classify(x.i); switch (r_type) { - case vctrs_dbl_number: + case VCTRS_DBL_number: switch (i_type) { - case vctrs_dbl_number: return x; - case vctrs_dbl_missing: return (r_complex) {na, na}; - case vctrs_dbl_nan: return (r_complex) {nan, nan}; + case VCTRS_DBL_number: return x; + case VCTRS_DBL_missing: return (r_complex) {na, na}; + case VCTRS_DBL_nan: return (r_complex) {nan, nan}; } - case vctrs_dbl_missing: + case VCTRS_DBL_missing: switch (i_type) { - case vctrs_dbl_number: return (r_complex) {na, na}; - case vctrs_dbl_missing: return x; - case vctrs_dbl_nan: return x; + case VCTRS_DBL_number: return (r_complex) {na, na}; + case VCTRS_DBL_missing: return x; + case VCTRS_DBL_nan: return x; } - case vctrs_dbl_nan: + case VCTRS_DBL_nan: switch (i_type) { - case vctrs_dbl_number: return (r_complex) {nan, nan}; - case vctrs_dbl_missing: return x; - case vctrs_dbl_nan: return x; + case VCTRS_DBL_number: return (r_complex) {nan, nan}; + case VCTRS_DBL_missing: return x; + case VCTRS_DBL_nan: return x; } } diff --git a/src/vctrs-core.c b/src/vctrs-core.c index da6d9c896..22e73e398 100644 --- a/src/vctrs-core.c +++ b/src/vctrs-core.c @@ -1,16 +1,16 @@ #include "vctrs.h" -enum vctrs_dbl_class dbl_classify(double x) { +enum vctrs_dbl dbl_classify(double x) { if (!isnan(x)) { - return vctrs_dbl_number; + return VCTRS_DBL_number; } union vctrs_dbl_indicator indicator; indicator.value = x; if (indicator.key[vctrs_indicator_pos] == 1954) { - return vctrs_dbl_missing; + return VCTRS_DBL_missing; } else { - return vctrs_dbl_nan; + return VCTRS_DBL_nan; } } diff --git a/src/vctrs-core.h b/src/vctrs-core.h index 7182049b0..adcf8f4d6 100644 --- a/src/vctrs-core.h +++ b/src/vctrs-core.h @@ -73,13 +73,13 @@ union vctrs_dbl_indicator { unsigned int key[2]; // 4 * 2 bytes }; -enum vctrs_dbl_class { - vctrs_dbl_number, - vctrs_dbl_missing, - vctrs_dbl_nan +enum vctrs_dbl { + VCTRS_DBL_number, + VCTRS_DBL_missing, + VCTRS_DBL_nan }; -enum vctrs_dbl_class dbl_classify(double x); +enum vctrs_dbl dbl_classify(double x); // Compatibility ------------------------------------------------ From 253326b76d2a3da3c0f4d96456fa28f17e4c0ab3 Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Mon, 5 Sep 2022 15:17:57 +0200 Subject: [PATCH 014/312] Update `enum vctrs_type2` and `enum vctrs_type2_s3` style --- src/cast-dispatch.c | 24 +- src/cast.c | 22 +- src/ptype2-dispatch.c | 24 +- src/ptype2.c | 28 +- src/typeof2-s3.c | 616 ++++++++++++++++++------------------ src/typeof2.c | 444 +++++++++++++------------- src/vctrs.h | 422 ++++++++++++------------ tests/testthat/test-type2.R | 8 +- 8 files changed, 794 insertions(+), 794 deletions(-) diff --git a/src/cast-dispatch.c b/src/cast-dispatch.c index 13729bb10..6e8f0969f 100644 --- a/src/cast-dispatch.c +++ b/src/cast-dispatch.c @@ -17,64 +17,64 @@ r_obj* vec_cast_dispatch_native(const struct cast_opts* opts, switch (type2_s3) { - case vctrs_type2_s3_character_bare_factor: + case VCTRS_TYPE2_S3_character_bare_factor: if (dir == 0) { return chr_as_factor(x, to, lossy, to_arg); } else { return fct_as_character(x, x_arg); } - case vctrs_type2_s3_character_bare_ordered: + case VCTRS_TYPE2_S3_character_bare_ordered: if (dir == 0) { return chr_as_ordered(x, to, lossy, to_arg); } else { return ord_as_character(x, x_arg); } - case vctrs_type2_s3_bare_factor_bare_factor: + case VCTRS_TYPE2_S3_bare_factor_bare_factor: return fct_as_factor(x, to, lossy, x_arg, to_arg); - case vctrs_type2_s3_bare_ordered_bare_ordered: + case VCTRS_TYPE2_S3_bare_ordered_bare_ordered: return ord_as_ordered(opts); - case vctrs_type2_s3_bare_date_bare_posixct: + case VCTRS_TYPE2_S3_bare_date_bare_posixct: if (dir == 0) { return date_as_posixct(x, to); } else { return posixct_as_date(x, lossy); } - case vctrs_type2_s3_bare_date_bare_posixlt: + case VCTRS_TYPE2_S3_bare_date_bare_posixlt: if (dir == 0) { return date_as_posixlt(x, to); } else { return posixlt_as_date(x, lossy); } - case vctrs_type2_s3_bare_posixct_bare_posixlt: + case VCTRS_TYPE2_S3_bare_posixct_bare_posixlt: if (dir == 0) { return posixct_as_posixlt(x, to); } else { return posixlt_as_posixct(x, to); } - case vctrs_type2_s3_bare_date_bare_date: + case VCTRS_TYPE2_S3_bare_date_bare_date: return date_as_date(x); - case vctrs_type2_s3_bare_posixct_bare_posixct: + case VCTRS_TYPE2_S3_bare_posixct_bare_posixct: return posixct_as_posixct(x, to); - case vctrs_type2_s3_bare_posixlt_bare_posixlt: + case VCTRS_TYPE2_S3_bare_posixlt_bare_posixlt: return posixlt_as_posixlt(x, to); - case vctrs_type2_s3_dataframe_bare_tibble: + case VCTRS_TYPE2_S3_dataframe_bare_tibble: if (dir == 0) { return tib_cast(opts); } else { return df_cast_opts(opts); } - case vctrs_type2_s3_bare_tibble_bare_tibble: + case VCTRS_TYPE2_S3_bare_tibble_bare_tibble: return tib_cast(opts); default: diff --git a/src/cast.c b/src/cast.c index 47871650d..e6535121d 100644 --- a/src/cast.c +++ b/src/cast.c @@ -82,37 +82,37 @@ r_obj* vec_cast_switch_native(const struct cast_opts* opts, switch (type2) { - case vctrs_type2_logical_logical: - case vctrs_type2_integer_integer: - case vctrs_type2_double_double: - case vctrs_type2_complex_complex: - case vctrs_type2_raw_raw: - case vctrs_type2_character_character: - case vctrs_type2_list_list: + case VCTRS_TYPE2_logical_logical: + case VCTRS_TYPE2_integer_integer: + case VCTRS_TYPE2_double_double: + case VCTRS_TYPE2_complex_complex: + case VCTRS_TYPE2_raw_raw: + case VCTRS_TYPE2_character_character: + case VCTRS_TYPE2_list_list: return x; - case vctrs_type2_logical_integer: + case VCTRS_TYPE2_logical_integer: if (dir == 0) { return lgl_as_integer(x, lossy); } else { return int_as_logical(x, lossy); } - case vctrs_type2_logical_double: + case VCTRS_TYPE2_logical_double: if (dir == 0) { return lgl_as_double(x, lossy); } else { return dbl_as_logical(x, lossy); } - case vctrs_type2_integer_double: + case VCTRS_TYPE2_integer_double: if (dir == 0) { return int_as_double(x, lossy); } else { return dbl_as_integer(x, lossy); } - case vctrs_type2_dataframe_dataframe: + case VCTRS_TYPE2_dataframe_dataframe: return df_cast_opts(opts); default: diff --git a/src/ptype2-dispatch.c b/src/ptype2-dispatch.c index a096efe4e..81a2d5c8e 100644 --- a/src/ptype2-dispatch.c +++ b/src/ptype2-dispatch.c @@ -13,30 +13,30 @@ r_obj* vec_ptype2_dispatch_native(const struct ptype2_opts* opts, enum vctrs_type2_s3 type2_s3 = vec_typeof2_s3_impl(x, y, x_type, y_type, left); switch (type2_s3) { - case vctrs_type2_s3_character_bare_factor: - case vctrs_type2_s3_character_bare_ordered: + case VCTRS_TYPE2_S3_character_bare_factor: + case VCTRS_TYPE2_S3_character_bare_ordered: return vctrs_shared_empty_chr; - case vctrs_type2_s3_bare_factor_bare_factor: + case VCTRS_TYPE2_S3_bare_factor_bare_factor: return fct_ptype2(opts); - case vctrs_type2_s3_bare_ordered_bare_ordered: + case VCTRS_TYPE2_S3_bare_ordered_bare_ordered: return ord_ptype2(opts); - case vctrs_type2_s3_bare_date_bare_date: + case VCTRS_TYPE2_S3_bare_date_bare_date: return vctrs_shared_empty_date; - case vctrs_type2_s3_bare_date_bare_posixct: - case vctrs_type2_s3_bare_date_bare_posixlt: + case VCTRS_TYPE2_S3_bare_date_bare_posixct: + case VCTRS_TYPE2_S3_bare_date_bare_posixlt: return date_datetime_ptype2(x, y); - case vctrs_type2_s3_bare_posixct_bare_posixct: - case vctrs_type2_s3_bare_posixct_bare_posixlt: - case vctrs_type2_s3_bare_posixlt_bare_posixlt: + case VCTRS_TYPE2_S3_bare_posixct_bare_posixct: + case VCTRS_TYPE2_S3_bare_posixct_bare_posixlt: + case VCTRS_TYPE2_S3_bare_posixlt_bare_posixlt: return datetime_datetime_ptype2(x, y); - case vctrs_type2_s3_dataframe_bare_tibble: - case vctrs_type2_s3_bare_tibble_bare_tibble: + case VCTRS_TYPE2_S3_dataframe_bare_tibble: + case VCTRS_TYPE2_S3_bare_tibble_bare_tibble: return tib_ptype2(opts); default: diff --git a/src/ptype2.c b/src/ptype2.c index 7c8fd8b38..dde28bcc9 100644 --- a/src/ptype2.c +++ b/src/ptype2.c @@ -105,36 +105,36 @@ r_obj* vec_ptype2_switch_native(const struct ptype2_opts* opts, enum vctrs_type2 type2 = vec_typeof2_impl(x_type, y_type, left); switch (type2) { - case vctrs_type2_null_null: + case VCTRS_TYPE2_null_null: return r_null; - case vctrs_type2_logical_logical: + case VCTRS_TYPE2_logical_logical: return vec_shaped_ptype(vctrs_shared_empty_lgl, x, y, x_arg, y_arg); - case vctrs_type2_logical_integer: - case vctrs_type2_integer_integer: + case VCTRS_TYPE2_logical_integer: + case VCTRS_TYPE2_integer_integer: return vec_shaped_ptype(vctrs_shared_empty_int, x, y, x_arg, y_arg); - case vctrs_type2_logical_double: - case vctrs_type2_integer_double: - case vctrs_type2_double_double: + case VCTRS_TYPE2_logical_double: + case VCTRS_TYPE2_integer_double: + case VCTRS_TYPE2_double_double: return vec_shaped_ptype(vctrs_shared_empty_dbl, x, y, x_arg, y_arg); - case vctrs_type2_integer_complex: - case vctrs_type2_double_complex: - case vctrs_type2_complex_complex: + case VCTRS_TYPE2_integer_complex: + case VCTRS_TYPE2_double_complex: + case VCTRS_TYPE2_complex_complex: return vec_shaped_ptype(vctrs_shared_empty_cpl, x, y, x_arg, y_arg); - case vctrs_type2_character_character: + case VCTRS_TYPE2_character_character: return vec_shaped_ptype(vctrs_shared_empty_chr, x, y, x_arg, y_arg); - case vctrs_type2_raw_raw: + case VCTRS_TYPE2_raw_raw: return vec_shaped_ptype(vctrs_shared_empty_raw, x, y, x_arg, y_arg); - case vctrs_type2_list_list: + case VCTRS_TYPE2_list_list: return vec_shaped_ptype(vctrs_shared_empty_list, x, y, x_arg, y_arg); - case vctrs_type2_dataframe_dataframe: + case VCTRS_TYPE2_dataframe_dataframe: return df_ptype2(opts); default: diff --git a/src/typeof2-s3.c b/src/typeof2-s3.c index d3c8969cc..4ca1b6ade 100644 --- a/src/typeof2-s3.c +++ b/src/typeof2-s3.c @@ -14,123 +14,123 @@ enum vctrs_type2_s3 vec_typeof2_s3_impl(SEXP x, switch (type_x) { case vctrs_type_null: { switch (class_type(y)) { - case VCTRS_CLASS_bare_factor: *left = 0; return vctrs_type2_s3_null_bare_factor; - case VCTRS_CLASS_bare_ordered: *left = 0; return vctrs_type2_s3_null_bare_ordered; - case VCTRS_CLASS_bare_date: *left = 0; return vctrs_type2_s3_null_bare_date; - case VCTRS_CLASS_bare_posixct: *left = 0; return vctrs_type2_s3_null_bare_posixct; - case VCTRS_CLASS_bare_posixlt: *left = 0; return vctrs_type2_s3_null_bare_posixlt; - case VCTRS_CLASS_bare_tibble: *left = 0; return vctrs_type2_s3_null_bare_tibble; - default: *left = 0; return vctrs_type2_s3_null_unknown; + case VCTRS_CLASS_bare_factor: *left = 0; return VCTRS_TYPE2_S3_null_bare_factor; + case VCTRS_CLASS_bare_ordered: *left = 0; return VCTRS_TYPE2_S3_null_bare_ordered; + case VCTRS_CLASS_bare_date: *left = 0; return VCTRS_TYPE2_S3_null_bare_date; + case VCTRS_CLASS_bare_posixct: *left = 0; return VCTRS_TYPE2_S3_null_bare_posixct; + case VCTRS_CLASS_bare_posixlt: *left = 0; return VCTRS_TYPE2_S3_null_bare_posixlt; + case VCTRS_CLASS_bare_tibble: *left = 0; return VCTRS_TYPE2_S3_null_bare_tibble; + default: *left = 0; return VCTRS_TYPE2_S3_null_unknown; } } case vctrs_type_unspecified: { switch (class_type(y)) { - case VCTRS_CLASS_bare_factor: *left = 0; return vctrs_type2_s3_unspecified_bare_factor; - case VCTRS_CLASS_bare_ordered: *left = 0; return vctrs_type2_s3_unspecified_bare_ordered; - case VCTRS_CLASS_bare_date: *left = 0; return vctrs_type2_s3_unspecified_bare_date; - case VCTRS_CLASS_bare_posixct: *left = 0; return vctrs_type2_s3_unspecified_bare_posixct; - case VCTRS_CLASS_bare_posixlt: *left = 0; return vctrs_type2_s3_unspecified_bare_posixlt; - case VCTRS_CLASS_bare_tibble: *left = 0; return vctrs_type2_s3_unspecified_bare_tibble; - default: *left = 0; return vctrs_type2_s3_unspecified_unknown; + case VCTRS_CLASS_bare_factor: *left = 0; return VCTRS_TYPE2_S3_unspecified_bare_factor; + case VCTRS_CLASS_bare_ordered: *left = 0; return VCTRS_TYPE2_S3_unspecified_bare_ordered; + case VCTRS_CLASS_bare_date: *left = 0; return VCTRS_TYPE2_S3_unspecified_bare_date; + case VCTRS_CLASS_bare_posixct: *left = 0; return VCTRS_TYPE2_S3_unspecified_bare_posixct; + case VCTRS_CLASS_bare_posixlt: *left = 0; return VCTRS_TYPE2_S3_unspecified_bare_posixlt; + case VCTRS_CLASS_bare_tibble: *left = 0; return VCTRS_TYPE2_S3_unspecified_bare_tibble; + default: *left = 0; return VCTRS_TYPE2_S3_unspecified_unknown; } } case vctrs_type_logical: { switch (class_type(y)) { - case VCTRS_CLASS_bare_factor: *left = 0; return vctrs_type2_s3_logical_bare_factor; - case VCTRS_CLASS_bare_ordered: *left = 0; return vctrs_type2_s3_logical_bare_ordered; - case VCTRS_CLASS_bare_date: *left = 0; return vctrs_type2_s3_logical_bare_date; - case VCTRS_CLASS_bare_posixct: *left = 0; return vctrs_type2_s3_logical_bare_posixct; - case VCTRS_CLASS_bare_posixlt: *left = 0; return vctrs_type2_s3_logical_bare_posixlt; - case VCTRS_CLASS_bare_tibble: *left = 0; return vctrs_type2_s3_logical_bare_tibble; - default: *left = 0; return vctrs_type2_s3_logical_unknown; + case VCTRS_CLASS_bare_factor: *left = 0; return VCTRS_TYPE2_S3_logical_bare_factor; + case VCTRS_CLASS_bare_ordered: *left = 0; return VCTRS_TYPE2_S3_logical_bare_ordered; + case VCTRS_CLASS_bare_date: *left = 0; return VCTRS_TYPE2_S3_logical_bare_date; + case VCTRS_CLASS_bare_posixct: *left = 0; return VCTRS_TYPE2_S3_logical_bare_posixct; + case VCTRS_CLASS_bare_posixlt: *left = 0; return VCTRS_TYPE2_S3_logical_bare_posixlt; + case VCTRS_CLASS_bare_tibble: *left = 0; return VCTRS_TYPE2_S3_logical_bare_tibble; + default: *left = 0; return VCTRS_TYPE2_S3_logical_unknown; } } case vctrs_type_integer: { switch (class_type(y)) { - case VCTRS_CLASS_bare_factor: *left = 0; return vctrs_type2_s3_integer_bare_factor; - case VCTRS_CLASS_bare_ordered: *left = 0; return vctrs_type2_s3_integer_bare_ordered; - case VCTRS_CLASS_bare_date: *left = 0; return vctrs_type2_s3_integer_bare_date; - case VCTRS_CLASS_bare_posixct: *left = 0; return vctrs_type2_s3_integer_bare_posixct; - case VCTRS_CLASS_bare_posixlt: *left = 0; return vctrs_type2_s3_integer_bare_posixlt; - case VCTRS_CLASS_bare_tibble: *left = 0; return vctrs_type2_s3_integer_bare_tibble; - default: *left = 0; return vctrs_type2_s3_integer_unknown; + case VCTRS_CLASS_bare_factor: *left = 0; return VCTRS_TYPE2_S3_integer_bare_factor; + case VCTRS_CLASS_bare_ordered: *left = 0; return VCTRS_TYPE2_S3_integer_bare_ordered; + case VCTRS_CLASS_bare_date: *left = 0; return VCTRS_TYPE2_S3_integer_bare_date; + case VCTRS_CLASS_bare_posixct: *left = 0; return VCTRS_TYPE2_S3_integer_bare_posixct; + case VCTRS_CLASS_bare_posixlt: *left = 0; return VCTRS_TYPE2_S3_integer_bare_posixlt; + case VCTRS_CLASS_bare_tibble: *left = 0; return VCTRS_TYPE2_S3_integer_bare_tibble; + default: *left = 0; return VCTRS_TYPE2_S3_integer_unknown; } } case vctrs_type_double: { switch (class_type(y)) { - case VCTRS_CLASS_bare_factor: *left = 0; return vctrs_type2_s3_double_bare_factor; - case VCTRS_CLASS_bare_ordered: *left = 0; return vctrs_type2_s3_double_bare_ordered; - case VCTRS_CLASS_bare_date: *left = 0; return vctrs_type2_s3_double_bare_date; - case VCTRS_CLASS_bare_posixct: *left = 0; return vctrs_type2_s3_double_bare_posixct; - case VCTRS_CLASS_bare_posixlt: *left = 0; return vctrs_type2_s3_double_bare_posixlt; - case VCTRS_CLASS_bare_tibble: *left = 0; return vctrs_type2_s3_double_bare_tibble; - default: *left = 0; return vctrs_type2_s3_double_unknown; + case VCTRS_CLASS_bare_factor: *left = 0; return VCTRS_TYPE2_S3_double_bare_factor; + case VCTRS_CLASS_bare_ordered: *left = 0; return VCTRS_TYPE2_S3_double_bare_ordered; + case VCTRS_CLASS_bare_date: *left = 0; return VCTRS_TYPE2_S3_double_bare_date; + case VCTRS_CLASS_bare_posixct: *left = 0; return VCTRS_TYPE2_S3_double_bare_posixct; + case VCTRS_CLASS_bare_posixlt: *left = 0; return VCTRS_TYPE2_S3_double_bare_posixlt; + case VCTRS_CLASS_bare_tibble: *left = 0; return VCTRS_TYPE2_S3_double_bare_tibble; + default: *left = 0; return VCTRS_TYPE2_S3_double_unknown; } } case vctrs_type_complex: { switch (class_type(y)) { - case VCTRS_CLASS_bare_factor: *left = 0; return vctrs_type2_s3_complex_bare_factor; - case VCTRS_CLASS_bare_ordered: *left = 0; return vctrs_type2_s3_complex_bare_ordered; - case VCTRS_CLASS_bare_date: *left = 0; return vctrs_type2_s3_complex_bare_date; - case VCTRS_CLASS_bare_posixct: *left = 0; return vctrs_type2_s3_complex_bare_posixct; - case VCTRS_CLASS_bare_posixlt: *left = 0; return vctrs_type2_s3_complex_bare_posixlt; - case VCTRS_CLASS_bare_tibble: *left = 0; return vctrs_type2_s3_complex_bare_tibble; - default: *left = 0; return vctrs_type2_s3_complex_unknown; + case VCTRS_CLASS_bare_factor: *left = 0; return VCTRS_TYPE2_S3_complex_bare_factor; + case VCTRS_CLASS_bare_ordered: *left = 0; return VCTRS_TYPE2_S3_complex_bare_ordered; + case VCTRS_CLASS_bare_date: *left = 0; return VCTRS_TYPE2_S3_complex_bare_date; + case VCTRS_CLASS_bare_posixct: *left = 0; return VCTRS_TYPE2_S3_complex_bare_posixct; + case VCTRS_CLASS_bare_posixlt: *left = 0; return VCTRS_TYPE2_S3_complex_bare_posixlt; + case VCTRS_CLASS_bare_tibble: *left = 0; return VCTRS_TYPE2_S3_complex_bare_tibble; + default: *left = 0; return VCTRS_TYPE2_S3_complex_unknown; } } case vctrs_type_character: { switch (class_type(y)) { - case VCTRS_CLASS_bare_factor: *left = 0; return vctrs_type2_s3_character_bare_factor; - case VCTRS_CLASS_bare_ordered: *left = 0; return vctrs_type2_s3_character_bare_ordered; - case VCTRS_CLASS_bare_date: *left = 0; return vctrs_type2_s3_character_bare_date; - case VCTRS_CLASS_bare_posixct: *left = 0; return vctrs_type2_s3_character_bare_posixct; - case VCTRS_CLASS_bare_posixlt: *left = 0; return vctrs_type2_s3_character_bare_posixlt; - case VCTRS_CLASS_bare_tibble: *left = 0; return vctrs_type2_s3_character_bare_tibble; - default: *left = 0; return vctrs_type2_s3_character_unknown; + case VCTRS_CLASS_bare_factor: *left = 0; return VCTRS_TYPE2_S3_character_bare_factor; + case VCTRS_CLASS_bare_ordered: *left = 0; return VCTRS_TYPE2_S3_character_bare_ordered; + case VCTRS_CLASS_bare_date: *left = 0; return VCTRS_TYPE2_S3_character_bare_date; + case VCTRS_CLASS_bare_posixct: *left = 0; return VCTRS_TYPE2_S3_character_bare_posixct; + case VCTRS_CLASS_bare_posixlt: *left = 0; return VCTRS_TYPE2_S3_character_bare_posixlt; + case VCTRS_CLASS_bare_tibble: *left = 0; return VCTRS_TYPE2_S3_character_bare_tibble; + default: *left = 0; return VCTRS_TYPE2_S3_character_unknown; } } case vctrs_type_raw: { switch (class_type(y)) { - case VCTRS_CLASS_bare_factor: *left = 0; return vctrs_type2_s3_raw_bare_factor; - case VCTRS_CLASS_bare_ordered: *left = 0; return vctrs_type2_s3_raw_bare_ordered; - case VCTRS_CLASS_bare_date: *left = 0; return vctrs_type2_s3_raw_bare_date; - case VCTRS_CLASS_bare_posixct: *left = 0; return vctrs_type2_s3_raw_bare_posixct; - case VCTRS_CLASS_bare_posixlt: *left = 0; return vctrs_type2_s3_raw_bare_posixlt; - case VCTRS_CLASS_bare_tibble: *left = 0; return vctrs_type2_s3_raw_bare_tibble; - default: *left = 0; return vctrs_type2_s3_raw_unknown; + case VCTRS_CLASS_bare_factor: *left = 0; return VCTRS_TYPE2_S3_raw_bare_factor; + case VCTRS_CLASS_bare_ordered: *left = 0; return VCTRS_TYPE2_S3_raw_bare_ordered; + case VCTRS_CLASS_bare_date: *left = 0; return VCTRS_TYPE2_S3_raw_bare_date; + case VCTRS_CLASS_bare_posixct: *left = 0; return VCTRS_TYPE2_S3_raw_bare_posixct; + case VCTRS_CLASS_bare_posixlt: *left = 0; return VCTRS_TYPE2_S3_raw_bare_posixlt; + case VCTRS_CLASS_bare_tibble: *left = 0; return VCTRS_TYPE2_S3_raw_bare_tibble; + default: *left = 0; return VCTRS_TYPE2_S3_raw_unknown; } } case vctrs_type_list: { switch (class_type(y)) { - case VCTRS_CLASS_bare_factor: *left = 0; return vctrs_type2_s3_list_bare_factor; - case VCTRS_CLASS_bare_ordered: *left = 0; return vctrs_type2_s3_list_bare_ordered; - case VCTRS_CLASS_bare_date: *left = 0; return vctrs_type2_s3_list_bare_date; - case VCTRS_CLASS_bare_posixct: *left = 0; return vctrs_type2_s3_list_bare_posixct; - case VCTRS_CLASS_bare_posixlt: *left = 0; return vctrs_type2_s3_list_bare_posixlt; - case VCTRS_CLASS_bare_tibble: *left = 0; return vctrs_type2_s3_list_bare_tibble; - default: *left = 0; return vctrs_type2_s3_list_unknown; + case VCTRS_CLASS_bare_factor: *left = 0; return VCTRS_TYPE2_S3_list_bare_factor; + case VCTRS_CLASS_bare_ordered: *left = 0; return VCTRS_TYPE2_S3_list_bare_ordered; + case VCTRS_CLASS_bare_date: *left = 0; return VCTRS_TYPE2_S3_list_bare_date; + case VCTRS_CLASS_bare_posixct: *left = 0; return VCTRS_TYPE2_S3_list_bare_posixct; + case VCTRS_CLASS_bare_posixlt: *left = 0; return VCTRS_TYPE2_S3_list_bare_posixlt; + case VCTRS_CLASS_bare_tibble: *left = 0; return VCTRS_TYPE2_S3_list_bare_tibble; + default: *left = 0; return VCTRS_TYPE2_S3_list_unknown; } } case vctrs_type_dataframe: { switch (class_type(y)) { - case VCTRS_CLASS_bare_factor: *left = 0; return vctrs_type2_s3_dataframe_bare_factor; - case VCTRS_CLASS_bare_ordered: *left = 0; return vctrs_type2_s3_dataframe_bare_ordered; - case VCTRS_CLASS_bare_date: *left = 0; return vctrs_type2_s3_dataframe_bare_date; - case VCTRS_CLASS_bare_posixct: *left = 0; return vctrs_type2_s3_dataframe_bare_posixct; - case VCTRS_CLASS_bare_posixlt: *left = 0; return vctrs_type2_s3_dataframe_bare_posixlt; - case VCTRS_CLASS_bare_tibble: *left = 0; return vctrs_type2_s3_dataframe_bare_tibble; - default: *left = 0; return vctrs_type2_s3_dataframe_unknown; + case VCTRS_CLASS_bare_factor: *left = 0; return VCTRS_TYPE2_S3_dataframe_bare_factor; + case VCTRS_CLASS_bare_ordered: *left = 0; return VCTRS_TYPE2_S3_dataframe_bare_ordered; + case VCTRS_CLASS_bare_date: *left = 0; return VCTRS_TYPE2_S3_dataframe_bare_date; + case VCTRS_CLASS_bare_posixct: *left = 0; return VCTRS_TYPE2_S3_dataframe_bare_posixct; + case VCTRS_CLASS_bare_posixlt: *left = 0; return VCTRS_TYPE2_S3_dataframe_bare_posixlt; + case VCTRS_CLASS_bare_tibble: *left = 0; return VCTRS_TYPE2_S3_dataframe_bare_tibble; + default: *left = 0; return VCTRS_TYPE2_S3_dataframe_unknown; } } case vctrs_type_scalar: { switch (class_type(y)) { - case VCTRS_CLASS_bare_factor: *left = 0; return vctrs_type2_s3_scalar_bare_factor; - case VCTRS_CLASS_bare_ordered: *left = 0; return vctrs_type2_s3_scalar_bare_ordered; - case VCTRS_CLASS_bare_date: *left = 0; return vctrs_type2_s3_scalar_bare_date; - case VCTRS_CLASS_bare_posixct: *left = 0; return vctrs_type2_s3_scalar_bare_posixct; - case VCTRS_CLASS_bare_posixlt: *left = 0; return vctrs_type2_s3_scalar_bare_posixlt; - case VCTRS_CLASS_bare_tibble: *left = 0; return vctrs_type2_s3_scalar_bare_tibble; - default: *left = 0; return vctrs_type2_s3_scalar_unknown; + case VCTRS_CLASS_bare_factor: *left = 0; return VCTRS_TYPE2_S3_scalar_bare_factor; + case VCTRS_CLASS_bare_ordered: *left = 0; return VCTRS_TYPE2_S3_scalar_bare_ordered; + case VCTRS_CLASS_bare_date: *left = 0; return VCTRS_TYPE2_S3_scalar_bare_date; + case VCTRS_CLASS_bare_posixct: *left = 0; return VCTRS_TYPE2_S3_scalar_bare_posixct; + case VCTRS_CLASS_bare_posixlt: *left = 0; return VCTRS_TYPE2_S3_scalar_bare_posixlt; + case VCTRS_CLASS_bare_tibble: *left = 0; return VCTRS_TYPE2_S3_scalar_bare_tibble; + default: *left = 0; return VCTRS_TYPE2_S3_scalar_unknown; } } case vctrs_type_s3: { @@ -148,176 +148,176 @@ static enum vctrs_type2_s3 vec_typeof2_s3_impl2(SEXP x, switch (class_type(x)) { case VCTRS_CLASS_bare_factor: { switch (type_y) { - case vctrs_type_null: *left = 1; return vctrs_type2_s3_null_bare_factor; - case vctrs_type_unspecified: *left = 1; return vctrs_type2_s3_unspecified_bare_factor; - case vctrs_type_logical: *left = 1; return vctrs_type2_s3_logical_bare_factor; - case vctrs_type_integer: *left = 1; return vctrs_type2_s3_integer_bare_factor; - case vctrs_type_double: *left = 1; return vctrs_type2_s3_double_bare_factor; - case vctrs_type_complex: *left = 1; return vctrs_type2_s3_complex_bare_factor; - case vctrs_type_character: *left = 1; return vctrs_type2_s3_character_bare_factor; - case vctrs_type_raw: *left = 1; return vctrs_type2_s3_raw_bare_factor; - case vctrs_type_list: *left = 1; return vctrs_type2_s3_list_bare_factor; - case vctrs_type_dataframe: *left = 1; return vctrs_type2_s3_dataframe_bare_factor; - case vctrs_type_scalar: *left = 1; return vctrs_type2_s3_scalar_bare_factor; + case vctrs_type_null: *left = 1; return VCTRS_TYPE2_S3_null_bare_factor; + case vctrs_type_unspecified: *left = 1; return VCTRS_TYPE2_S3_unspecified_bare_factor; + case vctrs_type_logical: *left = 1; return VCTRS_TYPE2_S3_logical_bare_factor; + case vctrs_type_integer: *left = 1; return VCTRS_TYPE2_S3_integer_bare_factor; + case vctrs_type_double: *left = 1; return VCTRS_TYPE2_S3_double_bare_factor; + case vctrs_type_complex: *left = 1; return VCTRS_TYPE2_S3_complex_bare_factor; + case vctrs_type_character: *left = 1; return VCTRS_TYPE2_S3_character_bare_factor; + case vctrs_type_raw: *left = 1; return VCTRS_TYPE2_S3_raw_bare_factor; + case vctrs_type_list: *left = 1; return VCTRS_TYPE2_S3_list_bare_factor; + case vctrs_type_dataframe: *left = 1; return VCTRS_TYPE2_S3_dataframe_bare_factor; + case vctrs_type_scalar: *left = 1; return VCTRS_TYPE2_S3_scalar_bare_factor; case vctrs_type_s3: { switch (class_type(y)) { - case VCTRS_CLASS_bare_factor: *left = -1; return vctrs_type2_s3_bare_factor_bare_factor; - case VCTRS_CLASS_bare_ordered: *left = 0; return vctrs_type2_s3_bare_factor_bare_ordered; - case VCTRS_CLASS_bare_date: *left = 0; return vctrs_type2_s3_bare_factor_bare_date; - case VCTRS_CLASS_bare_posixct: *left = 0; return vctrs_type2_s3_bare_factor_bare_posixct; - case VCTRS_CLASS_bare_posixlt: *left = 0; return vctrs_type2_s3_bare_factor_bare_posixlt; - case VCTRS_CLASS_bare_tibble: *left = 0; return vctrs_type2_s3_bare_factor_bare_tibble; - default: *left = 0; return vctrs_type2_s3_bare_factor_unknown; + case VCTRS_CLASS_bare_factor: *left = -1; return VCTRS_TYPE2_S3_bare_factor_bare_factor; + case VCTRS_CLASS_bare_ordered: *left = 0; return VCTRS_TYPE2_S3_bare_factor_bare_ordered; + case VCTRS_CLASS_bare_date: *left = 0; return VCTRS_TYPE2_S3_bare_factor_bare_date; + case VCTRS_CLASS_bare_posixct: *left = 0; return VCTRS_TYPE2_S3_bare_factor_bare_posixct; + case VCTRS_CLASS_bare_posixlt: *left = 0; return VCTRS_TYPE2_S3_bare_factor_bare_posixlt; + case VCTRS_CLASS_bare_tibble: *left = 0; return VCTRS_TYPE2_S3_bare_factor_bare_tibble; + default: *left = 0; return VCTRS_TYPE2_S3_bare_factor_unknown; } }} } case VCTRS_CLASS_bare_ordered: { switch (type_y) { - case vctrs_type_null: *left = 1; return vctrs_type2_s3_null_bare_ordered; - case vctrs_type_unspecified: *left = 1; return vctrs_type2_s3_unspecified_bare_ordered; - case vctrs_type_logical: *left = 1; return vctrs_type2_s3_logical_bare_ordered; - case vctrs_type_integer: *left = 1; return vctrs_type2_s3_integer_bare_ordered; - case vctrs_type_double: *left = 1; return vctrs_type2_s3_double_bare_ordered; - case vctrs_type_complex: *left = 1; return vctrs_type2_s3_complex_bare_ordered; - case vctrs_type_character: *left = 1; return vctrs_type2_s3_character_bare_ordered; - case vctrs_type_raw: *left = 1; return vctrs_type2_s3_raw_bare_ordered; - case vctrs_type_list: *left = 1; return vctrs_type2_s3_list_bare_ordered; - case vctrs_type_dataframe: *left = 1; return vctrs_type2_s3_dataframe_bare_ordered; - case vctrs_type_scalar: *left = 1; return vctrs_type2_s3_scalar_bare_ordered; + case vctrs_type_null: *left = 1; return VCTRS_TYPE2_S3_null_bare_ordered; + case vctrs_type_unspecified: *left = 1; return VCTRS_TYPE2_S3_unspecified_bare_ordered; + case vctrs_type_logical: *left = 1; return VCTRS_TYPE2_S3_logical_bare_ordered; + case vctrs_type_integer: *left = 1; return VCTRS_TYPE2_S3_integer_bare_ordered; + case vctrs_type_double: *left = 1; return VCTRS_TYPE2_S3_double_bare_ordered; + case vctrs_type_complex: *left = 1; return VCTRS_TYPE2_S3_complex_bare_ordered; + case vctrs_type_character: *left = 1; return VCTRS_TYPE2_S3_character_bare_ordered; + case vctrs_type_raw: *left = 1; return VCTRS_TYPE2_S3_raw_bare_ordered; + case vctrs_type_list: *left = 1; return VCTRS_TYPE2_S3_list_bare_ordered; + case vctrs_type_dataframe: *left = 1; return VCTRS_TYPE2_S3_dataframe_bare_ordered; + case vctrs_type_scalar: *left = 1; return VCTRS_TYPE2_S3_scalar_bare_ordered; case vctrs_type_s3: { switch (class_type(y)) { - case VCTRS_CLASS_bare_factor: *left = 1; return vctrs_type2_s3_bare_factor_bare_ordered; - case VCTRS_CLASS_bare_ordered: *left = -1; return vctrs_type2_s3_bare_ordered_bare_ordered; - case VCTRS_CLASS_bare_date: *left = 0; return vctrs_type2_s3_bare_ordered_bare_date; - case VCTRS_CLASS_bare_posixct: *left = 0; return vctrs_type2_s3_bare_ordered_bare_posixct; - case VCTRS_CLASS_bare_posixlt: *left = 0; return vctrs_type2_s3_bare_ordered_bare_posixlt; - case VCTRS_CLASS_bare_tibble: *left = 0; return vctrs_type2_s3_bare_ordered_bare_tibble; - default: *left = 0; return vctrs_type2_s3_bare_ordered_unknown; + case VCTRS_CLASS_bare_factor: *left = 1; return VCTRS_TYPE2_S3_bare_factor_bare_ordered; + case VCTRS_CLASS_bare_ordered: *left = -1; return VCTRS_TYPE2_S3_bare_ordered_bare_ordered; + case VCTRS_CLASS_bare_date: *left = 0; return VCTRS_TYPE2_S3_bare_ordered_bare_date; + case VCTRS_CLASS_bare_posixct: *left = 0; return VCTRS_TYPE2_S3_bare_ordered_bare_posixct; + case VCTRS_CLASS_bare_posixlt: *left = 0; return VCTRS_TYPE2_S3_bare_ordered_bare_posixlt; + case VCTRS_CLASS_bare_tibble: *left = 0; return VCTRS_TYPE2_S3_bare_ordered_bare_tibble; + default: *left = 0; return VCTRS_TYPE2_S3_bare_ordered_unknown; } }} } case VCTRS_CLASS_bare_date: { switch (type_y) { - case vctrs_type_null: *left = 1; return vctrs_type2_s3_null_bare_date; - case vctrs_type_unspecified: *left = 1; return vctrs_type2_s3_unspecified_bare_date; - case vctrs_type_logical: *left = 1; return vctrs_type2_s3_logical_bare_date; - case vctrs_type_integer: *left = 1; return vctrs_type2_s3_integer_bare_date; - case vctrs_type_double: *left = 1; return vctrs_type2_s3_double_bare_date; - case vctrs_type_complex: *left = 1; return vctrs_type2_s3_complex_bare_date; - case vctrs_type_character: *left = 1; return vctrs_type2_s3_character_bare_date; - case vctrs_type_raw: *left = 1; return vctrs_type2_s3_raw_bare_date; - case vctrs_type_list: *left = 1; return vctrs_type2_s3_list_bare_date; - case vctrs_type_dataframe: *left = 1; return vctrs_type2_s3_dataframe_bare_date; - case vctrs_type_scalar: *left = 1; return vctrs_type2_s3_scalar_bare_date; + case vctrs_type_null: *left = 1; return VCTRS_TYPE2_S3_null_bare_date; + case vctrs_type_unspecified: *left = 1; return VCTRS_TYPE2_S3_unspecified_bare_date; + case vctrs_type_logical: *left = 1; return VCTRS_TYPE2_S3_logical_bare_date; + case vctrs_type_integer: *left = 1; return VCTRS_TYPE2_S3_integer_bare_date; + case vctrs_type_double: *left = 1; return VCTRS_TYPE2_S3_double_bare_date; + case vctrs_type_complex: *left = 1; return VCTRS_TYPE2_S3_complex_bare_date; + case vctrs_type_character: *left = 1; return VCTRS_TYPE2_S3_character_bare_date; + case vctrs_type_raw: *left = 1; return VCTRS_TYPE2_S3_raw_bare_date; + case vctrs_type_list: *left = 1; return VCTRS_TYPE2_S3_list_bare_date; + case vctrs_type_dataframe: *left = 1; return VCTRS_TYPE2_S3_dataframe_bare_date; + case vctrs_type_scalar: *left = 1; return VCTRS_TYPE2_S3_scalar_bare_date; case vctrs_type_s3: { switch (class_type(y)) { - case VCTRS_CLASS_bare_factor: *left = 1; return vctrs_type2_s3_bare_factor_bare_date; - case VCTRS_CLASS_bare_ordered: *left = 1; return vctrs_type2_s3_bare_ordered_bare_date; - case VCTRS_CLASS_bare_date: *left = -1; return vctrs_type2_s3_bare_date_bare_date; - case VCTRS_CLASS_bare_posixct: *left = 0; return vctrs_type2_s3_bare_date_bare_posixct; - case VCTRS_CLASS_bare_posixlt: *left = 0; return vctrs_type2_s3_bare_date_bare_posixlt; - case VCTRS_CLASS_bare_tibble: *left = 0; return vctrs_type2_s3_bare_date_bare_tibble; - default: *left = 0; return vctrs_type2_s3_bare_date_unknown; + case VCTRS_CLASS_bare_factor: *left = 1; return VCTRS_TYPE2_S3_bare_factor_bare_date; + case VCTRS_CLASS_bare_ordered: *left = 1; return VCTRS_TYPE2_S3_bare_ordered_bare_date; + case VCTRS_CLASS_bare_date: *left = -1; return VCTRS_TYPE2_S3_bare_date_bare_date; + case VCTRS_CLASS_bare_posixct: *left = 0; return VCTRS_TYPE2_S3_bare_date_bare_posixct; + case VCTRS_CLASS_bare_posixlt: *left = 0; return VCTRS_TYPE2_S3_bare_date_bare_posixlt; + case VCTRS_CLASS_bare_tibble: *left = 0; return VCTRS_TYPE2_S3_bare_date_bare_tibble; + default: *left = 0; return VCTRS_TYPE2_S3_bare_date_unknown; } }} } case VCTRS_CLASS_bare_posixct: { switch (type_y) { - case vctrs_type_null: *left = 1; return vctrs_type2_s3_null_bare_posixct; - case vctrs_type_unspecified: *left = 1; return vctrs_type2_s3_unspecified_bare_posixct; - case vctrs_type_logical: *left = 1; return vctrs_type2_s3_logical_bare_posixct; - case vctrs_type_integer: *left = 1; return vctrs_type2_s3_integer_bare_posixct; - case vctrs_type_double: *left = 1; return vctrs_type2_s3_double_bare_posixct; - case vctrs_type_complex: *left = 1; return vctrs_type2_s3_complex_bare_posixct; - case vctrs_type_character: *left = 1; return vctrs_type2_s3_character_bare_posixct; - case vctrs_type_raw: *left = 1; return vctrs_type2_s3_raw_bare_posixct; - case vctrs_type_list: *left = 1; return vctrs_type2_s3_list_bare_posixct; - case vctrs_type_dataframe: *left = 1; return vctrs_type2_s3_dataframe_bare_posixct; - case vctrs_type_scalar: *left = 1; return vctrs_type2_s3_scalar_bare_posixct; + case vctrs_type_null: *left = 1; return VCTRS_TYPE2_S3_null_bare_posixct; + case vctrs_type_unspecified: *left = 1; return VCTRS_TYPE2_S3_unspecified_bare_posixct; + case vctrs_type_logical: *left = 1; return VCTRS_TYPE2_S3_logical_bare_posixct; + case vctrs_type_integer: *left = 1; return VCTRS_TYPE2_S3_integer_bare_posixct; + case vctrs_type_double: *left = 1; return VCTRS_TYPE2_S3_double_bare_posixct; + case vctrs_type_complex: *left = 1; return VCTRS_TYPE2_S3_complex_bare_posixct; + case vctrs_type_character: *left = 1; return VCTRS_TYPE2_S3_character_bare_posixct; + case vctrs_type_raw: *left = 1; return VCTRS_TYPE2_S3_raw_bare_posixct; + case vctrs_type_list: *left = 1; return VCTRS_TYPE2_S3_list_bare_posixct; + case vctrs_type_dataframe: *left = 1; return VCTRS_TYPE2_S3_dataframe_bare_posixct; + case vctrs_type_scalar: *left = 1; return VCTRS_TYPE2_S3_scalar_bare_posixct; case vctrs_type_s3: { switch (class_type(y)) { - case VCTRS_CLASS_bare_factor: *left = 1; return vctrs_type2_s3_bare_factor_bare_posixct; - case VCTRS_CLASS_bare_ordered: *left = 1; return vctrs_type2_s3_bare_ordered_bare_posixct; - case VCTRS_CLASS_bare_date: *left = 1; return vctrs_type2_s3_bare_date_bare_posixct; - case VCTRS_CLASS_bare_posixct: *left = -1; return vctrs_type2_s3_bare_posixct_bare_posixct; - case VCTRS_CLASS_bare_posixlt: *left = 0; return vctrs_type2_s3_bare_posixct_bare_posixlt; - case VCTRS_CLASS_bare_tibble: *left = 0; return vctrs_type2_s3_bare_posixct_bare_tibble; - default: *left = 0; return vctrs_type2_s3_bare_posixct_unknown; + case VCTRS_CLASS_bare_factor: *left = 1; return VCTRS_TYPE2_S3_bare_factor_bare_posixct; + case VCTRS_CLASS_bare_ordered: *left = 1; return VCTRS_TYPE2_S3_bare_ordered_bare_posixct; + case VCTRS_CLASS_bare_date: *left = 1; return VCTRS_TYPE2_S3_bare_date_bare_posixct; + case VCTRS_CLASS_bare_posixct: *left = -1; return VCTRS_TYPE2_S3_bare_posixct_bare_posixct; + case VCTRS_CLASS_bare_posixlt: *left = 0; return VCTRS_TYPE2_S3_bare_posixct_bare_posixlt; + case VCTRS_CLASS_bare_tibble: *left = 0; return VCTRS_TYPE2_S3_bare_posixct_bare_tibble; + default: *left = 0; return VCTRS_TYPE2_S3_bare_posixct_unknown; } }} } case VCTRS_CLASS_bare_posixlt: { switch (type_y) { - case vctrs_type_null: *left = 1; return vctrs_type2_s3_null_bare_posixlt; - case vctrs_type_unspecified: *left = 1; return vctrs_type2_s3_unspecified_bare_posixlt; - case vctrs_type_logical: *left = 1; return vctrs_type2_s3_logical_bare_posixlt; - case vctrs_type_integer: *left = 1; return vctrs_type2_s3_integer_bare_posixlt; - case vctrs_type_double: *left = 1; return vctrs_type2_s3_double_bare_posixlt; - case vctrs_type_complex: *left = 1; return vctrs_type2_s3_complex_bare_posixlt; - case vctrs_type_character: *left = 1; return vctrs_type2_s3_character_bare_posixlt; - case vctrs_type_raw: *left = 1; return vctrs_type2_s3_raw_bare_posixlt; - case vctrs_type_list: *left = 1; return vctrs_type2_s3_list_bare_posixlt; - case vctrs_type_dataframe: *left = 1; return vctrs_type2_s3_dataframe_bare_posixlt; - case vctrs_type_scalar: *left = 1; return vctrs_type2_s3_scalar_bare_posixlt; + case vctrs_type_null: *left = 1; return VCTRS_TYPE2_S3_null_bare_posixlt; + case vctrs_type_unspecified: *left = 1; return VCTRS_TYPE2_S3_unspecified_bare_posixlt; + case vctrs_type_logical: *left = 1; return VCTRS_TYPE2_S3_logical_bare_posixlt; + case vctrs_type_integer: *left = 1; return VCTRS_TYPE2_S3_integer_bare_posixlt; + case vctrs_type_double: *left = 1; return VCTRS_TYPE2_S3_double_bare_posixlt; + case vctrs_type_complex: *left = 1; return VCTRS_TYPE2_S3_complex_bare_posixlt; + case vctrs_type_character: *left = 1; return VCTRS_TYPE2_S3_character_bare_posixlt; + case vctrs_type_raw: *left = 1; return VCTRS_TYPE2_S3_raw_bare_posixlt; + case vctrs_type_list: *left = 1; return VCTRS_TYPE2_S3_list_bare_posixlt; + case vctrs_type_dataframe: *left = 1; return VCTRS_TYPE2_S3_dataframe_bare_posixlt; + case vctrs_type_scalar: *left = 1; return VCTRS_TYPE2_S3_scalar_bare_posixlt; case vctrs_type_s3: { switch (class_type(y)) { - case VCTRS_CLASS_bare_factor: *left = 1; return vctrs_type2_s3_bare_factor_bare_posixlt; - case VCTRS_CLASS_bare_ordered: *left = 1; return vctrs_type2_s3_bare_ordered_bare_posixlt; - case VCTRS_CLASS_bare_date: *left = 1; return vctrs_type2_s3_bare_date_bare_posixlt; - case VCTRS_CLASS_bare_posixct: *left = 1; return vctrs_type2_s3_bare_posixct_bare_posixlt; - case VCTRS_CLASS_bare_posixlt: *left = -1; return vctrs_type2_s3_bare_posixlt_bare_posixlt; - case VCTRS_CLASS_bare_tibble: *left = 0; return vctrs_type2_s3_bare_posixlt_bare_tibble; - default: *left = 0; return vctrs_type2_s3_bare_posixlt_unknown; + case VCTRS_CLASS_bare_factor: *left = 1; return VCTRS_TYPE2_S3_bare_factor_bare_posixlt; + case VCTRS_CLASS_bare_ordered: *left = 1; return VCTRS_TYPE2_S3_bare_ordered_bare_posixlt; + case VCTRS_CLASS_bare_date: *left = 1; return VCTRS_TYPE2_S3_bare_date_bare_posixlt; + case VCTRS_CLASS_bare_posixct: *left = 1; return VCTRS_TYPE2_S3_bare_posixct_bare_posixlt; + case VCTRS_CLASS_bare_posixlt: *left = -1; return VCTRS_TYPE2_S3_bare_posixlt_bare_posixlt; + case VCTRS_CLASS_bare_tibble: *left = 0; return VCTRS_TYPE2_S3_bare_posixlt_bare_tibble; + default: *left = 0; return VCTRS_TYPE2_S3_bare_posixlt_unknown; } }} } case VCTRS_CLASS_bare_tibble: { switch (type_y) { - case vctrs_type_null: *left = 1; return vctrs_type2_s3_null_bare_tibble; - case vctrs_type_unspecified: *left = 1; return vctrs_type2_s3_unspecified_bare_tibble; - case vctrs_type_logical: *left = 1; return vctrs_type2_s3_logical_bare_tibble; - case vctrs_type_integer: *left = 1; return vctrs_type2_s3_integer_bare_tibble; - case vctrs_type_double: *left = 1; return vctrs_type2_s3_double_bare_tibble; - case vctrs_type_complex: *left = 1; return vctrs_type2_s3_complex_bare_tibble; - case vctrs_type_character: *left = 1; return vctrs_type2_s3_character_bare_tibble; - case vctrs_type_raw: *left = 1; return vctrs_type2_s3_raw_bare_tibble; - case vctrs_type_list: *left = 1; return vctrs_type2_s3_list_bare_tibble; - case vctrs_type_dataframe: *left = 1; return vctrs_type2_s3_dataframe_bare_tibble; - case vctrs_type_scalar: *left = 1; return vctrs_type2_s3_scalar_bare_tibble; + case vctrs_type_null: *left = 1; return VCTRS_TYPE2_S3_null_bare_tibble; + case vctrs_type_unspecified: *left = 1; return VCTRS_TYPE2_S3_unspecified_bare_tibble; + case vctrs_type_logical: *left = 1; return VCTRS_TYPE2_S3_logical_bare_tibble; + case vctrs_type_integer: *left = 1; return VCTRS_TYPE2_S3_integer_bare_tibble; + case vctrs_type_double: *left = 1; return VCTRS_TYPE2_S3_double_bare_tibble; + case vctrs_type_complex: *left = 1; return VCTRS_TYPE2_S3_complex_bare_tibble; + case vctrs_type_character: *left = 1; return VCTRS_TYPE2_S3_character_bare_tibble; + case vctrs_type_raw: *left = 1; return VCTRS_TYPE2_S3_raw_bare_tibble; + case vctrs_type_list: *left = 1; return VCTRS_TYPE2_S3_list_bare_tibble; + case vctrs_type_dataframe: *left = 1; return VCTRS_TYPE2_S3_dataframe_bare_tibble; + case vctrs_type_scalar: *left = 1; return VCTRS_TYPE2_S3_scalar_bare_tibble; case vctrs_type_s3: { switch (class_type(y)) { - case VCTRS_CLASS_bare_factor: *left = 1; return vctrs_type2_s3_bare_factor_bare_tibble; - case VCTRS_CLASS_bare_ordered: *left = 1; return vctrs_type2_s3_bare_ordered_bare_tibble; - case VCTRS_CLASS_bare_date: *left = 1; return vctrs_type2_s3_bare_date_bare_tibble; - case VCTRS_CLASS_bare_posixct: *left = 1; return vctrs_type2_s3_bare_posixct_bare_tibble; - case VCTRS_CLASS_bare_posixlt: *left = 1; return vctrs_type2_s3_bare_posixlt_bare_tibble; - case VCTRS_CLASS_bare_tibble: *left = -1; return vctrs_type2_s3_bare_tibble_bare_tibble; - default: *left = 0; return vctrs_type2_s3_bare_tibble_unknown; + case VCTRS_CLASS_bare_factor: *left = 1; return VCTRS_TYPE2_S3_bare_factor_bare_tibble; + case VCTRS_CLASS_bare_ordered: *left = 1; return VCTRS_TYPE2_S3_bare_ordered_bare_tibble; + case VCTRS_CLASS_bare_date: *left = 1; return VCTRS_TYPE2_S3_bare_date_bare_tibble; + case VCTRS_CLASS_bare_posixct: *left = 1; return VCTRS_TYPE2_S3_bare_posixct_bare_tibble; + case VCTRS_CLASS_bare_posixlt: *left = 1; return VCTRS_TYPE2_S3_bare_posixlt_bare_tibble; + case VCTRS_CLASS_bare_tibble: *left = -1; return VCTRS_TYPE2_S3_bare_tibble_bare_tibble; + default: *left = 0; return VCTRS_TYPE2_S3_bare_tibble_unknown; } }} } default: { switch (type_y) { - case vctrs_type_null: *left = 1; return vctrs_type2_s3_null_unknown; - case vctrs_type_unspecified: *left = 1; return vctrs_type2_s3_unspecified_unknown; - case vctrs_type_logical: *left = 1; return vctrs_type2_s3_logical_unknown; - case vctrs_type_integer: *left = 1; return vctrs_type2_s3_integer_unknown; - case vctrs_type_double: *left = 1; return vctrs_type2_s3_double_unknown; - case vctrs_type_complex: *left = 1; return vctrs_type2_s3_complex_unknown; - case vctrs_type_character: *left = 1; return vctrs_type2_s3_character_unknown; - case vctrs_type_raw: *left = 1; return vctrs_type2_s3_raw_unknown; - case vctrs_type_list: *left = 1; return vctrs_type2_s3_list_unknown; - case vctrs_type_dataframe: *left = 1; return vctrs_type2_s3_dataframe_unknown; - case vctrs_type_scalar: *left = 1; return vctrs_type2_s3_scalar_unknown; + case vctrs_type_null: *left = 1; return VCTRS_TYPE2_S3_null_unknown; + case vctrs_type_unspecified: *left = 1; return VCTRS_TYPE2_S3_unspecified_unknown; + case vctrs_type_logical: *left = 1; return VCTRS_TYPE2_S3_logical_unknown; + case vctrs_type_integer: *left = 1; return VCTRS_TYPE2_S3_integer_unknown; + case vctrs_type_double: *left = 1; return VCTRS_TYPE2_S3_double_unknown; + case vctrs_type_complex: *left = 1; return VCTRS_TYPE2_S3_complex_unknown; + case vctrs_type_character: *left = 1; return VCTRS_TYPE2_S3_character_unknown; + case vctrs_type_raw: *left = 1; return VCTRS_TYPE2_S3_raw_unknown; + case vctrs_type_list: *left = 1; return VCTRS_TYPE2_S3_list_unknown; + case vctrs_type_dataframe: *left = 1; return VCTRS_TYPE2_S3_dataframe_unknown; + case vctrs_type_scalar: *left = 1; return VCTRS_TYPE2_S3_scalar_unknown; case vctrs_type_s3: { switch (class_type(y)) { - case VCTRS_CLASS_bare_factor: *left = 1; return vctrs_type2_s3_bare_factor_unknown; - case VCTRS_CLASS_bare_ordered: *left = 1; return vctrs_type2_s3_bare_ordered_unknown; - case VCTRS_CLASS_bare_date: *left = 1; return vctrs_type2_s3_bare_date_unknown; - case VCTRS_CLASS_bare_posixct: *left = 1; return vctrs_type2_s3_bare_posixct_unknown; - case VCTRS_CLASS_bare_posixlt: *left = 1; return vctrs_type2_s3_bare_posixlt_unknown; - case VCTRS_CLASS_bare_tibble: *left = 1; return vctrs_type2_s3_bare_tibble_unknown; - default: *left = -1; return vctrs_type2_s3_unknown_unknown; + case VCTRS_CLASS_bare_factor: *left = 1; return VCTRS_TYPE2_S3_bare_factor_unknown; + case VCTRS_CLASS_bare_ordered: *left = 1; return VCTRS_TYPE2_S3_bare_ordered_unknown; + case VCTRS_CLASS_bare_date: *left = 1; return VCTRS_TYPE2_S3_bare_date_unknown; + case VCTRS_CLASS_bare_posixct: *left = 1; return VCTRS_TYPE2_S3_bare_posixct_unknown; + case VCTRS_CLASS_bare_posixlt: *left = 1; return VCTRS_TYPE2_S3_bare_posixlt_unknown; + case VCTRS_CLASS_bare_tibble: *left = 1; return VCTRS_TYPE2_S3_bare_tibble_unknown; + default: *left = -1; return VCTRS_TYPE2_S3_unknown_unknown; } }} }} @@ -332,128 +332,128 @@ enum vctrs_type2_s3 vec_typeof2_s3(SEXP x, SEXP y) { const char* vctrs_type2_s3_as_str(enum vctrs_type2_s3 type) { switch (type) { - case vctrs_type2_s3_null_bare_factor: return "vctrs_type2_s3_null_bare_factor"; - case vctrs_type2_s3_null_bare_ordered: return "vctrs_type2_s3_null_bare_ordered"; - case vctrs_type2_s3_null_bare_date: return "vctrs_type2_s3_null_bare_date"; - case vctrs_type2_s3_null_bare_posixct: return "vctrs_type2_s3_null_bare_posixct"; - case vctrs_type2_s3_null_bare_posixlt: return "vctrs_type2_s3_null_bare_posixlt"; - case vctrs_type2_s3_null_bare_tibble: return "vctrs_type2_s3_null_bare_tibble"; - case vctrs_type2_s3_null_unknown: return "vctrs_type2_s3_null_unknown"; + case VCTRS_TYPE2_S3_null_bare_factor: return "VCTRS_TYPE2_S3_null_bare_factor"; + case VCTRS_TYPE2_S3_null_bare_ordered: return "VCTRS_TYPE2_S3_null_bare_ordered"; + case VCTRS_TYPE2_S3_null_bare_date: return "VCTRS_TYPE2_S3_null_bare_date"; + case VCTRS_TYPE2_S3_null_bare_posixct: return "VCTRS_TYPE2_S3_null_bare_posixct"; + case VCTRS_TYPE2_S3_null_bare_posixlt: return "VCTRS_TYPE2_S3_null_bare_posixlt"; + case VCTRS_TYPE2_S3_null_bare_tibble: return "VCTRS_TYPE2_S3_null_bare_tibble"; + case VCTRS_TYPE2_S3_null_unknown: return "VCTRS_TYPE2_S3_null_unknown"; - case vctrs_type2_s3_unspecified_bare_factor: return "vctrs_type2_s3_unspecified_bare_factor"; - case vctrs_type2_s3_unspecified_bare_ordered: return "vctrs_type2_s3_unspecified_bare_ordered"; - case vctrs_type2_s3_unspecified_bare_date: return "vctrs_type2_s3_unspecified_bare_date"; - case vctrs_type2_s3_unspecified_bare_posixct: return "vctrs_type2_s3_unspecified_bare_posixct"; - case vctrs_type2_s3_unspecified_bare_posixlt: return "vctrs_type2_s3_unspecified_bare_posixlt"; - case vctrs_type2_s3_unspecified_bare_tibble: return "vctrs_type2_s3_unspecified_bare_tibble"; - case vctrs_type2_s3_unspecified_unknown: return "vctrs_type2_s3_unspecified_unknown"; + case VCTRS_TYPE2_S3_unspecified_bare_factor: return "VCTRS_TYPE2_S3_unspecified_bare_factor"; + case VCTRS_TYPE2_S3_unspecified_bare_ordered: return "VCTRS_TYPE2_S3_unspecified_bare_ordered"; + case VCTRS_TYPE2_S3_unspecified_bare_date: return "VCTRS_TYPE2_S3_unspecified_bare_date"; + case VCTRS_TYPE2_S3_unspecified_bare_posixct: return "VCTRS_TYPE2_S3_unspecified_bare_posixct"; + case VCTRS_TYPE2_S3_unspecified_bare_posixlt: return "VCTRS_TYPE2_S3_unspecified_bare_posixlt"; + case VCTRS_TYPE2_S3_unspecified_bare_tibble: return "VCTRS_TYPE2_S3_unspecified_bare_tibble"; + case VCTRS_TYPE2_S3_unspecified_unknown: return "VCTRS_TYPE2_S3_unspecified_unknown"; - case vctrs_type2_s3_logical_bare_factor: return "vctrs_type2_s3_logical_bare_factor"; - case vctrs_type2_s3_logical_bare_ordered: return "vctrs_type2_s3_logical_bare_ordered"; - case vctrs_type2_s3_logical_bare_date: return "vctrs_type2_s3_logical_bare_date"; - case vctrs_type2_s3_logical_bare_posixct: return "vctrs_type2_s3_logical_bare_posixct"; - case vctrs_type2_s3_logical_bare_posixlt: return "vctrs_type2_s3_logical_bare_posixlt"; - case vctrs_type2_s3_logical_bare_tibble: return "vctrs_type2_s3_logical_bare_tibble"; - case vctrs_type2_s3_logical_unknown: return "vctrs_type2_s3_logical_unknown"; + case VCTRS_TYPE2_S3_logical_bare_factor: return "VCTRS_TYPE2_S3_logical_bare_factor"; + case VCTRS_TYPE2_S3_logical_bare_ordered: return "VCTRS_TYPE2_S3_logical_bare_ordered"; + case VCTRS_TYPE2_S3_logical_bare_date: return "VCTRS_TYPE2_S3_logical_bare_date"; + case VCTRS_TYPE2_S3_logical_bare_posixct: return "VCTRS_TYPE2_S3_logical_bare_posixct"; + case VCTRS_TYPE2_S3_logical_bare_posixlt: return "VCTRS_TYPE2_S3_logical_bare_posixlt"; + case VCTRS_TYPE2_S3_logical_bare_tibble: return "VCTRS_TYPE2_S3_logical_bare_tibble"; + case VCTRS_TYPE2_S3_logical_unknown: return "VCTRS_TYPE2_S3_logical_unknown"; - case vctrs_type2_s3_integer_bare_factor: return "vctrs_type2_s3_integer_bare_factor"; - case vctrs_type2_s3_integer_bare_ordered: return "vctrs_type2_s3_integer_bare_ordered"; - case vctrs_type2_s3_integer_bare_date: return "vctrs_type2_s3_integer_bare_date"; - case vctrs_type2_s3_integer_bare_posixct: return "vctrs_type2_s3_integer_bare_posixct"; - case vctrs_type2_s3_integer_bare_posixlt: return "vctrs_type2_s3_integer_bare_posixlt"; - case vctrs_type2_s3_integer_bare_tibble: return "vctrs_type2_s3_integer_bare_tibble"; - case vctrs_type2_s3_integer_unknown: return "vctrs_type2_s3_integer_unknown"; + case VCTRS_TYPE2_S3_integer_bare_factor: return "VCTRS_TYPE2_S3_integer_bare_factor"; + case VCTRS_TYPE2_S3_integer_bare_ordered: return "VCTRS_TYPE2_S3_integer_bare_ordered"; + case VCTRS_TYPE2_S3_integer_bare_date: return "VCTRS_TYPE2_S3_integer_bare_date"; + case VCTRS_TYPE2_S3_integer_bare_posixct: return "VCTRS_TYPE2_S3_integer_bare_posixct"; + case VCTRS_TYPE2_S3_integer_bare_posixlt: return "VCTRS_TYPE2_S3_integer_bare_posixlt"; + case VCTRS_TYPE2_S3_integer_bare_tibble: return "VCTRS_TYPE2_S3_integer_bare_tibble"; + case VCTRS_TYPE2_S3_integer_unknown: return "VCTRS_TYPE2_S3_integer_unknown"; - case vctrs_type2_s3_double_bare_factor: return "vctrs_type2_s3_double_bare_factor"; - case vctrs_type2_s3_double_bare_ordered: return "vctrs_type2_s3_double_bare_ordered"; - case vctrs_type2_s3_double_bare_date: return "vctrs_type2_s3_double_bare_date"; - case vctrs_type2_s3_double_bare_posixct: return "vctrs_type2_s3_double_bare_posixct"; - case vctrs_type2_s3_double_bare_posixlt: return "vctrs_type2_s3_double_bare_posixlt"; - case vctrs_type2_s3_double_bare_tibble: return "vctrs_type2_s3_double_bare_tibble"; - case vctrs_type2_s3_double_unknown: return "vctrs_type2_s3_double_unknown"; + case VCTRS_TYPE2_S3_double_bare_factor: return "VCTRS_TYPE2_S3_double_bare_factor"; + case VCTRS_TYPE2_S3_double_bare_ordered: return "VCTRS_TYPE2_S3_double_bare_ordered"; + case VCTRS_TYPE2_S3_double_bare_date: return "VCTRS_TYPE2_S3_double_bare_date"; + case VCTRS_TYPE2_S3_double_bare_posixct: return "VCTRS_TYPE2_S3_double_bare_posixct"; + case VCTRS_TYPE2_S3_double_bare_posixlt: return "VCTRS_TYPE2_S3_double_bare_posixlt"; + case VCTRS_TYPE2_S3_double_bare_tibble: return "VCTRS_TYPE2_S3_double_bare_tibble"; + case VCTRS_TYPE2_S3_double_unknown: return "VCTRS_TYPE2_S3_double_unknown"; - case vctrs_type2_s3_complex_bare_factor: return "vctrs_type2_s3_complex_bare_factor"; - case vctrs_type2_s3_complex_bare_ordered: return "vctrs_type2_s3_complex_bare_ordered"; - case vctrs_type2_s3_complex_bare_date: return "vctrs_type2_s3_complex_bare_date"; - case vctrs_type2_s3_complex_bare_posixct: return "vctrs_type2_s3_complex_bare_posixct"; - case vctrs_type2_s3_complex_bare_posixlt: return "vctrs_type2_s3_complex_bare_posixlt"; - case vctrs_type2_s3_complex_bare_tibble: return "vctrs_type2_s3_complex_bare_tibble"; - case vctrs_type2_s3_complex_unknown: return "vctrs_type2_s3_complex_unknown"; + case VCTRS_TYPE2_S3_complex_bare_factor: return "VCTRS_TYPE2_S3_complex_bare_factor"; + case VCTRS_TYPE2_S3_complex_bare_ordered: return "VCTRS_TYPE2_S3_complex_bare_ordered"; + case VCTRS_TYPE2_S3_complex_bare_date: return "VCTRS_TYPE2_S3_complex_bare_date"; + case VCTRS_TYPE2_S3_complex_bare_posixct: return "VCTRS_TYPE2_S3_complex_bare_posixct"; + case VCTRS_TYPE2_S3_complex_bare_posixlt: return "VCTRS_TYPE2_S3_complex_bare_posixlt"; + case VCTRS_TYPE2_S3_complex_bare_tibble: return "VCTRS_TYPE2_S3_complex_bare_tibble"; + case VCTRS_TYPE2_S3_complex_unknown: return "VCTRS_TYPE2_S3_complex_unknown"; - case vctrs_type2_s3_character_bare_factor: return "vctrs_type2_s3_character_bare_factor"; - case vctrs_type2_s3_character_bare_ordered: return "vctrs_type2_s3_character_bare_ordered"; - case vctrs_type2_s3_character_bare_date: return "vctrs_type2_s3_character_bare_date"; - case vctrs_type2_s3_character_bare_posixct: return "vctrs_type2_s3_character_bare_posixct"; - case vctrs_type2_s3_character_bare_posixlt: return "vctrs_type2_s3_character_bare_posixlt"; - case vctrs_type2_s3_character_bare_tibble: return "vctrs_type2_s3_character_bare_tibble"; - case vctrs_type2_s3_character_unknown: return "vctrs_type2_s3_character_unknown"; + case VCTRS_TYPE2_S3_character_bare_factor: return "VCTRS_TYPE2_S3_character_bare_factor"; + case VCTRS_TYPE2_S3_character_bare_ordered: return "VCTRS_TYPE2_S3_character_bare_ordered"; + case VCTRS_TYPE2_S3_character_bare_date: return "VCTRS_TYPE2_S3_character_bare_date"; + case VCTRS_TYPE2_S3_character_bare_posixct: return "VCTRS_TYPE2_S3_character_bare_posixct"; + case VCTRS_TYPE2_S3_character_bare_posixlt: return "VCTRS_TYPE2_S3_character_bare_posixlt"; + case VCTRS_TYPE2_S3_character_bare_tibble: return "VCTRS_TYPE2_S3_character_bare_tibble"; + case VCTRS_TYPE2_S3_character_unknown: return "VCTRS_TYPE2_S3_character_unknown"; - case vctrs_type2_s3_raw_bare_factor: return "vctrs_type2_s3_raw_bare_factor"; - case vctrs_type2_s3_raw_bare_ordered: return "vctrs_type2_s3_raw_bare_ordered"; - case vctrs_type2_s3_raw_bare_date: return "vctrs_type2_s3_raw_bare_date"; - case vctrs_type2_s3_raw_bare_posixct: return "vctrs_type2_s3_raw_bare_posixct"; - case vctrs_type2_s3_raw_bare_posixlt: return "vctrs_type2_s3_raw_bare_posixlt"; - case vctrs_type2_s3_raw_bare_tibble: return "vctrs_type2_s3_raw_bare_tibble"; - case vctrs_type2_s3_raw_unknown: return "vctrs_type2_s3_raw_unknown"; + case VCTRS_TYPE2_S3_raw_bare_factor: return "VCTRS_TYPE2_S3_raw_bare_factor"; + case VCTRS_TYPE2_S3_raw_bare_ordered: return "VCTRS_TYPE2_S3_raw_bare_ordered"; + case VCTRS_TYPE2_S3_raw_bare_date: return "VCTRS_TYPE2_S3_raw_bare_date"; + case VCTRS_TYPE2_S3_raw_bare_posixct: return "VCTRS_TYPE2_S3_raw_bare_posixct"; + case VCTRS_TYPE2_S3_raw_bare_posixlt: return "VCTRS_TYPE2_S3_raw_bare_posixlt"; + case VCTRS_TYPE2_S3_raw_bare_tibble: return "VCTRS_TYPE2_S3_raw_bare_tibble"; + case VCTRS_TYPE2_S3_raw_unknown: return "VCTRS_TYPE2_S3_raw_unknown"; - case vctrs_type2_s3_list_bare_factor: return "vctrs_type2_s3_list_bare_factor"; - case vctrs_type2_s3_list_bare_ordered: return "vctrs_type2_s3_list_bare_ordered"; - case vctrs_type2_s3_list_bare_date: return "vctrs_type2_s3_list_bare_date"; - case vctrs_type2_s3_list_bare_posixct: return "vctrs_type2_s3_list_bare_posixct"; - case vctrs_type2_s3_list_bare_posixlt: return "vctrs_type2_s3_list_bare_posixlt"; - case vctrs_type2_s3_list_bare_tibble: return "vctrs_type2_s3_list_bare_tibble"; - case vctrs_type2_s3_list_unknown: return "vctrs_type2_s3_list_unknown"; + case VCTRS_TYPE2_S3_list_bare_factor: return "VCTRS_TYPE2_S3_list_bare_factor"; + case VCTRS_TYPE2_S3_list_bare_ordered: return "VCTRS_TYPE2_S3_list_bare_ordered"; + case VCTRS_TYPE2_S3_list_bare_date: return "VCTRS_TYPE2_S3_list_bare_date"; + case VCTRS_TYPE2_S3_list_bare_posixct: return "VCTRS_TYPE2_S3_list_bare_posixct"; + case VCTRS_TYPE2_S3_list_bare_posixlt: return "VCTRS_TYPE2_S3_list_bare_posixlt"; + case VCTRS_TYPE2_S3_list_bare_tibble: return "VCTRS_TYPE2_S3_list_bare_tibble"; + case VCTRS_TYPE2_S3_list_unknown: return "VCTRS_TYPE2_S3_list_unknown"; - case vctrs_type2_s3_dataframe_bare_factor: return "vctrs_type2_s3_dataframe_bare_factor"; - case vctrs_type2_s3_dataframe_bare_ordered: return "vctrs_type2_s3_dataframe_bare_ordered"; - case vctrs_type2_s3_dataframe_bare_date: return "vctrs_type2_s3_dataframe_bare_date"; - case vctrs_type2_s3_dataframe_bare_posixct: return "vctrs_type2_s3_dataframe_bare_posixct"; - case vctrs_type2_s3_dataframe_bare_posixlt: return "vctrs_type2_s3_dataframe_bare_posixlt"; - case vctrs_type2_s3_dataframe_bare_tibble: return "vctrs_type2_s3_dataframe_bare_tibble"; - case vctrs_type2_s3_dataframe_unknown: return "vctrs_type2_s3_dataframe_unknown"; + case VCTRS_TYPE2_S3_dataframe_bare_factor: return "VCTRS_TYPE2_S3_dataframe_bare_factor"; + case VCTRS_TYPE2_S3_dataframe_bare_ordered: return "VCTRS_TYPE2_S3_dataframe_bare_ordered"; + case VCTRS_TYPE2_S3_dataframe_bare_date: return "VCTRS_TYPE2_S3_dataframe_bare_date"; + case VCTRS_TYPE2_S3_dataframe_bare_posixct: return "VCTRS_TYPE2_S3_dataframe_bare_posixct"; + case VCTRS_TYPE2_S3_dataframe_bare_posixlt: return "VCTRS_TYPE2_S3_dataframe_bare_posixlt"; + case VCTRS_TYPE2_S3_dataframe_bare_tibble: return "VCTRS_TYPE2_S3_dataframe_bare_tibble"; + case VCTRS_TYPE2_S3_dataframe_unknown: return "VCTRS_TYPE2_S3_dataframe_unknown"; - case vctrs_type2_s3_scalar_bare_factor: return "vctrs_type2_s3_scalar_bare_factor"; - case vctrs_type2_s3_scalar_bare_ordered: return "vctrs_type2_s3_scalar_bare_ordered"; - case vctrs_type2_s3_scalar_bare_date: return "vctrs_type2_s3_scalar_bare_date"; - case vctrs_type2_s3_scalar_bare_posixct: return "vctrs_type2_s3_scalar_bare_posixct"; - case vctrs_type2_s3_scalar_bare_posixlt: return "vctrs_type2_s3_scalar_bare_posixlt"; - case vctrs_type2_s3_scalar_bare_tibble: return "vctrs_type2_s3_scalar_bare_tibble"; - case vctrs_type2_s3_scalar_unknown: return "vctrs_type2_s3_scalar_unknown"; + case VCTRS_TYPE2_S3_scalar_bare_factor: return "VCTRS_TYPE2_S3_scalar_bare_factor"; + case VCTRS_TYPE2_S3_scalar_bare_ordered: return "VCTRS_TYPE2_S3_scalar_bare_ordered"; + case VCTRS_TYPE2_S3_scalar_bare_date: return "VCTRS_TYPE2_S3_scalar_bare_date"; + case VCTRS_TYPE2_S3_scalar_bare_posixct: return "VCTRS_TYPE2_S3_scalar_bare_posixct"; + case VCTRS_TYPE2_S3_scalar_bare_posixlt: return "VCTRS_TYPE2_S3_scalar_bare_posixlt"; + case VCTRS_TYPE2_S3_scalar_bare_tibble: return "VCTRS_TYPE2_S3_scalar_bare_tibble"; + case VCTRS_TYPE2_S3_scalar_unknown: return "VCTRS_TYPE2_S3_scalar_unknown"; - case vctrs_type2_s3_bare_factor_bare_factor: return "vctrs_type2_s3_bare_factor_bare_factor"; - case vctrs_type2_s3_bare_factor_bare_ordered: return "vctrs_type2_s3_bare_factor_bare_ordered"; - case vctrs_type2_s3_bare_factor_bare_date: return "vctrs_type2_s3_bare_factor_bare_date"; - case vctrs_type2_s3_bare_factor_bare_posixct: return "vctrs_type2_s3_bare_factor_bare_posixct"; - case vctrs_type2_s3_bare_factor_bare_posixlt: return "vctrs_type2_s3_bare_factor_bare_posixlt"; - case vctrs_type2_s3_bare_factor_bare_tibble: return "vctrs_type2_s3_bare_factor_bare_tibble"; - case vctrs_type2_s3_bare_factor_unknown: return "vctrs_type2_s3_bare_factor_unknown"; + case VCTRS_TYPE2_S3_bare_factor_bare_factor: return "VCTRS_TYPE2_S3_bare_factor_bare_factor"; + case VCTRS_TYPE2_S3_bare_factor_bare_ordered: return "VCTRS_TYPE2_S3_bare_factor_bare_ordered"; + case VCTRS_TYPE2_S3_bare_factor_bare_date: return "VCTRS_TYPE2_S3_bare_factor_bare_date"; + case VCTRS_TYPE2_S3_bare_factor_bare_posixct: return "VCTRS_TYPE2_S3_bare_factor_bare_posixct"; + case VCTRS_TYPE2_S3_bare_factor_bare_posixlt: return "VCTRS_TYPE2_S3_bare_factor_bare_posixlt"; + case VCTRS_TYPE2_S3_bare_factor_bare_tibble: return "VCTRS_TYPE2_S3_bare_factor_bare_tibble"; + case VCTRS_TYPE2_S3_bare_factor_unknown: return "VCTRS_TYPE2_S3_bare_factor_unknown"; - case vctrs_type2_s3_bare_ordered_bare_ordered: return "vctrs_type2_s3_bare_ordered_bare_ordered"; - case vctrs_type2_s3_bare_ordered_bare_date: return "vctrs_type2_s3_bare_ordered_bare_date"; - case vctrs_type2_s3_bare_ordered_bare_posixct: return "vctrs_type2_s3_bare_ordered_bare_posixct"; - case vctrs_type2_s3_bare_ordered_bare_posixlt: return "vctrs_type2_s3_bare_ordered_bare_posixlt"; - case vctrs_type2_s3_bare_ordered_bare_tibble: return "vctrs_type2_s3_bare_ordered_bare_tibble"; - case vctrs_type2_s3_bare_ordered_unknown: return "vctrs_type2_s3_bare_ordered_unknown"; + case VCTRS_TYPE2_S3_bare_ordered_bare_ordered: return "VCTRS_TYPE2_S3_bare_ordered_bare_ordered"; + case VCTRS_TYPE2_S3_bare_ordered_bare_date: return "VCTRS_TYPE2_S3_bare_ordered_bare_date"; + case VCTRS_TYPE2_S3_bare_ordered_bare_posixct: return "VCTRS_TYPE2_S3_bare_ordered_bare_posixct"; + case VCTRS_TYPE2_S3_bare_ordered_bare_posixlt: return "VCTRS_TYPE2_S3_bare_ordered_bare_posixlt"; + case VCTRS_TYPE2_S3_bare_ordered_bare_tibble: return "VCTRS_TYPE2_S3_bare_ordered_bare_tibble"; + case VCTRS_TYPE2_S3_bare_ordered_unknown: return "VCTRS_TYPE2_S3_bare_ordered_unknown"; - case vctrs_type2_s3_bare_date_bare_date: return "vctrs_type2_s3_bare_date_bare_date"; - case vctrs_type2_s3_bare_date_bare_posixct: return "vctrs_type2_s3_bare_date_bare_posixct"; - case vctrs_type2_s3_bare_date_bare_posixlt: return "vctrs_type2_s3_bare_date_bare_posixlt"; - case vctrs_type2_s3_bare_date_bare_tibble: return "vctrs_type2_s3_bare_date_bare_tibble"; - case vctrs_type2_s3_bare_date_unknown: return "vctrs_type2_s3_bare_date_unknown"; + case VCTRS_TYPE2_S3_bare_date_bare_date: return "VCTRS_TYPE2_S3_bare_date_bare_date"; + case VCTRS_TYPE2_S3_bare_date_bare_posixct: return "VCTRS_TYPE2_S3_bare_date_bare_posixct"; + case VCTRS_TYPE2_S3_bare_date_bare_posixlt: return "VCTRS_TYPE2_S3_bare_date_bare_posixlt"; + case VCTRS_TYPE2_S3_bare_date_bare_tibble: return "VCTRS_TYPE2_S3_bare_date_bare_tibble"; + case VCTRS_TYPE2_S3_bare_date_unknown: return "VCTRS_TYPE2_S3_bare_date_unknown"; - case vctrs_type2_s3_bare_posixct_bare_posixct: return "vctrs_type2_s3_bare_posixct_bare_posixct"; - case vctrs_type2_s3_bare_posixct_bare_posixlt: return "vctrs_type2_s3_bare_posixct_bare_posixlt"; - case vctrs_type2_s3_bare_posixct_bare_tibble: return "vctrs_type2_s3_bare_posixct_bare_tibble"; - case vctrs_type2_s3_bare_posixct_unknown: return "vctrs_type2_s3_bare_posixct_unknown"; + case VCTRS_TYPE2_S3_bare_posixct_bare_posixct: return "VCTRS_TYPE2_S3_bare_posixct_bare_posixct"; + case VCTRS_TYPE2_S3_bare_posixct_bare_posixlt: return "VCTRS_TYPE2_S3_bare_posixct_bare_posixlt"; + case VCTRS_TYPE2_S3_bare_posixct_bare_tibble: return "VCTRS_TYPE2_S3_bare_posixct_bare_tibble"; + case VCTRS_TYPE2_S3_bare_posixct_unknown: return "VCTRS_TYPE2_S3_bare_posixct_unknown"; - case vctrs_type2_s3_bare_posixlt_bare_posixlt: return "vctrs_type2_s3_bare_posixlt_bare_posixlt"; - case vctrs_type2_s3_bare_posixlt_bare_tibble: return "vctrs_type2_s3_bare_posixlt_bare_tibble"; - case vctrs_type2_s3_bare_posixlt_unknown: return "vctrs_type2_s3_bare_posixlt_unknown"; + case VCTRS_TYPE2_S3_bare_posixlt_bare_posixlt: return "VCTRS_TYPE2_S3_bare_posixlt_bare_posixlt"; + case VCTRS_TYPE2_S3_bare_posixlt_bare_tibble: return "VCTRS_TYPE2_S3_bare_posixlt_bare_tibble"; + case VCTRS_TYPE2_S3_bare_posixlt_unknown: return "VCTRS_TYPE2_S3_bare_posixlt_unknown"; - case vctrs_type2_s3_bare_tibble_bare_tibble: return "vctrs_type2_s3_bare_tibble_bare_tibble"; - case vctrs_type2_s3_bare_tibble_unknown: return "vctrs_type2_s3_bare_tibble_unknown"; + case VCTRS_TYPE2_S3_bare_tibble_bare_tibble: return "VCTRS_TYPE2_S3_bare_tibble_bare_tibble"; + case VCTRS_TYPE2_S3_bare_tibble_unknown: return "VCTRS_TYPE2_S3_bare_tibble_unknown"; - case vctrs_type2_s3_unknown_unknown: return "vctrs_type2_s3_unknown_unknown"; + case VCTRS_TYPE2_S3_unknown_unknown: return "VCTRS_TYPE2_S3_unknown_unknown"; } never_reached("vctrs_type2_s3_as_str"); diff --git a/src/typeof2.c b/src/typeof2.c index 78819b4d7..805050d60 100644 --- a/src/typeof2.c +++ b/src/typeof2.c @@ -24,194 +24,194 @@ enum vctrs_type2 vec_typeof2_impl(enum vctrs_type type_x, switch (type_x) { case vctrs_type_null: { switch (type_y) { - case vctrs_type_null: *left = -1; return vctrs_type2_null_null; - case vctrs_type_unspecified: *left = 0; return vctrs_type2_null_unspecified; - case vctrs_type_logical: *left = 0; return vctrs_type2_null_logical; - case vctrs_type_integer: *left = 0; return vctrs_type2_null_integer; - case vctrs_type_double: *left = 0; return vctrs_type2_null_double; - case vctrs_type_complex: *left = 0; return vctrs_type2_null_complex; - case vctrs_type_character: *left = 0; return vctrs_type2_null_character; - case vctrs_type_raw: *left = 0; return vctrs_type2_null_raw; - case vctrs_type_list: *left = 0; return vctrs_type2_null_list; - case vctrs_type_dataframe: *left = 0; return vctrs_type2_null_dataframe; - case vctrs_type_s3: *left = 0; return vctrs_type2_null_s3; - case vctrs_type_scalar: *left = 0; return vctrs_type2_null_scalar; + case vctrs_type_null: *left = -1; return VCTRS_TYPE2_null_null; + case vctrs_type_unspecified: *left = 0; return VCTRS_TYPE2_null_unspecified; + case vctrs_type_logical: *left = 0; return VCTRS_TYPE2_null_logical; + case vctrs_type_integer: *left = 0; return VCTRS_TYPE2_null_integer; + case vctrs_type_double: *left = 0; return VCTRS_TYPE2_null_double; + case vctrs_type_complex: *left = 0; return VCTRS_TYPE2_null_complex; + case vctrs_type_character: *left = 0; return VCTRS_TYPE2_null_character; + case vctrs_type_raw: *left = 0; return VCTRS_TYPE2_null_raw; + case vctrs_type_list: *left = 0; return VCTRS_TYPE2_null_list; + case vctrs_type_dataframe: *left = 0; return VCTRS_TYPE2_null_dataframe; + case vctrs_type_s3: *left = 0; return VCTRS_TYPE2_null_s3; + case vctrs_type_scalar: *left = 0; return VCTRS_TYPE2_null_scalar; } } case vctrs_type_unspecified: { switch (type_y) { - case vctrs_type_null: *left = 1; return vctrs_type2_null_unspecified; - case vctrs_type_unspecified: *left = -1; return vctrs_type2_unspecified_unspecified; - case vctrs_type_logical: *left = 0; return vctrs_type2_unspecified_logical; - case vctrs_type_integer: *left = 0; return vctrs_type2_unspecified_integer; - case vctrs_type_double: *left = 0; return vctrs_type2_unspecified_double; - case vctrs_type_complex: *left = 0; return vctrs_type2_unspecified_complex; - case vctrs_type_character: *left = 0; return vctrs_type2_unspecified_character; - case vctrs_type_raw: *left = 0; return vctrs_type2_unspecified_raw; - case vctrs_type_list: *left = 0; return vctrs_type2_unspecified_list; - case vctrs_type_dataframe: *left = 0; return vctrs_type2_unspecified_dataframe; - case vctrs_type_s3: *left = 0; return vctrs_type2_unspecified_s3; - case vctrs_type_scalar: *left = 0; return vctrs_type2_unspecified_scalar; + case vctrs_type_null: *left = 1; return VCTRS_TYPE2_null_unspecified; + case vctrs_type_unspecified: *left = -1; return VCTRS_TYPE2_unspecified_unspecified; + case vctrs_type_logical: *left = 0; return VCTRS_TYPE2_unspecified_logical; + case vctrs_type_integer: *left = 0; return VCTRS_TYPE2_unspecified_integer; + case vctrs_type_double: *left = 0; return VCTRS_TYPE2_unspecified_double; + case vctrs_type_complex: *left = 0; return VCTRS_TYPE2_unspecified_complex; + case vctrs_type_character: *left = 0; return VCTRS_TYPE2_unspecified_character; + case vctrs_type_raw: *left = 0; return VCTRS_TYPE2_unspecified_raw; + case vctrs_type_list: *left = 0; return VCTRS_TYPE2_unspecified_list; + case vctrs_type_dataframe: *left = 0; return VCTRS_TYPE2_unspecified_dataframe; + case vctrs_type_s3: *left = 0; return VCTRS_TYPE2_unspecified_s3; + case vctrs_type_scalar: *left = 0; return VCTRS_TYPE2_unspecified_scalar; } } case vctrs_type_logical: { switch (type_y) { - case vctrs_type_null: *left = 1; return vctrs_type2_null_logical; - case vctrs_type_unspecified: *left = 1; return vctrs_type2_unspecified_logical; - case vctrs_type_logical: *left = -1; return vctrs_type2_logical_logical; - case vctrs_type_integer: *left = 0; return vctrs_type2_logical_integer; - case vctrs_type_double: *left = 0; return vctrs_type2_logical_double; - case vctrs_type_complex: *left = 0; return vctrs_type2_logical_complex; - case vctrs_type_character: *left = 0; return vctrs_type2_logical_character; - case vctrs_type_raw: *left = 0; return vctrs_type2_logical_raw; - case vctrs_type_list: *left = 0; return vctrs_type2_logical_list; - case vctrs_type_dataframe: *left = 0; return vctrs_type2_logical_dataframe; - case vctrs_type_s3: *left = 0; return vctrs_type2_logical_s3; - case vctrs_type_scalar: *left = 0; return vctrs_type2_logical_scalar; + case vctrs_type_null: *left = 1; return VCTRS_TYPE2_null_logical; + case vctrs_type_unspecified: *left = 1; return VCTRS_TYPE2_unspecified_logical; + case vctrs_type_logical: *left = -1; return VCTRS_TYPE2_logical_logical; + case vctrs_type_integer: *left = 0; return VCTRS_TYPE2_logical_integer; + case vctrs_type_double: *left = 0; return VCTRS_TYPE2_logical_double; + case vctrs_type_complex: *left = 0; return VCTRS_TYPE2_logical_complex; + case vctrs_type_character: *left = 0; return VCTRS_TYPE2_logical_character; + case vctrs_type_raw: *left = 0; return VCTRS_TYPE2_logical_raw; + case vctrs_type_list: *left = 0; return VCTRS_TYPE2_logical_list; + case vctrs_type_dataframe: *left = 0; return VCTRS_TYPE2_logical_dataframe; + case vctrs_type_s3: *left = 0; return VCTRS_TYPE2_logical_s3; + case vctrs_type_scalar: *left = 0; return VCTRS_TYPE2_logical_scalar; } } case vctrs_type_integer: { switch (type_y) { - case vctrs_type_null: *left = 1; return vctrs_type2_null_integer; - case vctrs_type_unspecified: *left = 1; return vctrs_type2_unspecified_integer; - case vctrs_type_logical: *left = 1; return vctrs_type2_logical_integer; - case vctrs_type_integer: *left = -1; return vctrs_type2_integer_integer; - case vctrs_type_double: *left = 0; return vctrs_type2_integer_double; - case vctrs_type_complex: *left = 0; return vctrs_type2_integer_complex; - case vctrs_type_character: *left = 0; return vctrs_type2_integer_character; - case vctrs_type_raw: *left = 0; return vctrs_type2_integer_raw; - case vctrs_type_list: *left = 0; return vctrs_type2_integer_list; - case vctrs_type_dataframe: *left = 0; return vctrs_type2_integer_dataframe; - case vctrs_type_s3: *left = 0; return vctrs_type2_integer_s3; - case vctrs_type_scalar: *left = 0; return vctrs_type2_integer_scalar; + case vctrs_type_null: *left = 1; return VCTRS_TYPE2_null_integer; + case vctrs_type_unspecified: *left = 1; return VCTRS_TYPE2_unspecified_integer; + case vctrs_type_logical: *left = 1; return VCTRS_TYPE2_logical_integer; + case vctrs_type_integer: *left = -1; return VCTRS_TYPE2_integer_integer; + case vctrs_type_double: *left = 0; return VCTRS_TYPE2_integer_double; + case vctrs_type_complex: *left = 0; return VCTRS_TYPE2_integer_complex; + case vctrs_type_character: *left = 0; return VCTRS_TYPE2_integer_character; + case vctrs_type_raw: *left = 0; return VCTRS_TYPE2_integer_raw; + case vctrs_type_list: *left = 0; return VCTRS_TYPE2_integer_list; + case vctrs_type_dataframe: *left = 0; return VCTRS_TYPE2_integer_dataframe; + case vctrs_type_s3: *left = 0; return VCTRS_TYPE2_integer_s3; + case vctrs_type_scalar: *left = 0; return VCTRS_TYPE2_integer_scalar; } } case vctrs_type_double: { switch (type_y) { - case vctrs_type_null: *left = 1; return vctrs_type2_null_double; - case vctrs_type_unspecified: *left = 1; return vctrs_type2_unspecified_double; - case vctrs_type_logical: *left = 1; return vctrs_type2_logical_double; - case vctrs_type_integer: *left = 1; return vctrs_type2_integer_double; - case vctrs_type_double: *left = -1; return vctrs_type2_double_double; - case vctrs_type_complex: *left = 0; return vctrs_type2_double_complex; - case vctrs_type_character: *left = 0; return vctrs_type2_double_character; - case vctrs_type_raw: *left = 0; return vctrs_type2_double_raw; - case vctrs_type_list: *left = 0; return vctrs_type2_double_list; - case vctrs_type_dataframe: *left = 0; return vctrs_type2_double_dataframe; - case vctrs_type_s3: *left = 0; return vctrs_type2_double_s3; - case vctrs_type_scalar: *left = 0; return vctrs_type2_double_scalar; + case vctrs_type_null: *left = 1; return VCTRS_TYPE2_null_double; + case vctrs_type_unspecified: *left = 1; return VCTRS_TYPE2_unspecified_double; + case vctrs_type_logical: *left = 1; return VCTRS_TYPE2_logical_double; + case vctrs_type_integer: *left = 1; return VCTRS_TYPE2_integer_double; + case vctrs_type_double: *left = -1; return VCTRS_TYPE2_double_double; + case vctrs_type_complex: *left = 0; return VCTRS_TYPE2_double_complex; + case vctrs_type_character: *left = 0; return VCTRS_TYPE2_double_character; + case vctrs_type_raw: *left = 0; return VCTRS_TYPE2_double_raw; + case vctrs_type_list: *left = 0; return VCTRS_TYPE2_double_list; + case vctrs_type_dataframe: *left = 0; return VCTRS_TYPE2_double_dataframe; + case vctrs_type_s3: *left = 0; return VCTRS_TYPE2_double_s3; + case vctrs_type_scalar: *left = 0; return VCTRS_TYPE2_double_scalar; } } case vctrs_type_complex: { switch (type_y) { - case vctrs_type_null: *left = 1; return vctrs_type2_null_complex; - case vctrs_type_unspecified: *left = 1; return vctrs_type2_unspecified_complex; - case vctrs_type_logical: *left = 1; return vctrs_type2_logical_complex; - case vctrs_type_integer: *left = 1; return vctrs_type2_integer_complex; - case vctrs_type_double: *left = 1; return vctrs_type2_double_complex; - case vctrs_type_complex: *left = -1; return vctrs_type2_complex_complex; - case vctrs_type_character: *left = 0; return vctrs_type2_complex_character; - case vctrs_type_raw: *left = 0; return vctrs_type2_complex_raw; - case vctrs_type_list: *left = 0; return vctrs_type2_complex_list; - case vctrs_type_dataframe: *left = 0; return vctrs_type2_complex_dataframe; - case vctrs_type_s3: *left = 0; return vctrs_type2_complex_s3; - case vctrs_type_scalar: *left = 0; return vctrs_type2_complex_scalar; + case vctrs_type_null: *left = 1; return VCTRS_TYPE2_null_complex; + case vctrs_type_unspecified: *left = 1; return VCTRS_TYPE2_unspecified_complex; + case vctrs_type_logical: *left = 1; return VCTRS_TYPE2_logical_complex; + case vctrs_type_integer: *left = 1; return VCTRS_TYPE2_integer_complex; + case vctrs_type_double: *left = 1; return VCTRS_TYPE2_double_complex; + case vctrs_type_complex: *left = -1; return VCTRS_TYPE2_complex_complex; + case vctrs_type_character: *left = 0; return VCTRS_TYPE2_complex_character; + case vctrs_type_raw: *left = 0; return VCTRS_TYPE2_complex_raw; + case vctrs_type_list: *left = 0; return VCTRS_TYPE2_complex_list; + case vctrs_type_dataframe: *left = 0; return VCTRS_TYPE2_complex_dataframe; + case vctrs_type_s3: *left = 0; return VCTRS_TYPE2_complex_s3; + case vctrs_type_scalar: *left = 0; return VCTRS_TYPE2_complex_scalar; } } case vctrs_type_character: { switch (type_y) { - case vctrs_type_null: *left = 1; return vctrs_type2_null_character; - case vctrs_type_unspecified: *left = 1; return vctrs_type2_unspecified_character; - case vctrs_type_logical: *left = 1; return vctrs_type2_logical_character; - case vctrs_type_integer: *left = 1; return vctrs_type2_integer_character; - case vctrs_type_double: *left = 1; return vctrs_type2_double_character; - case vctrs_type_complex: *left = 1; return vctrs_type2_complex_character; - case vctrs_type_character: *left = -1; return vctrs_type2_character_character; - case vctrs_type_raw: *left = 0; return vctrs_type2_character_raw; - case vctrs_type_list: *left = 0; return vctrs_type2_character_list; - case vctrs_type_dataframe: *left = 0; return vctrs_type2_character_dataframe; - case vctrs_type_s3: *left = 0; return vctrs_type2_character_s3; - case vctrs_type_scalar: *left = 0; return vctrs_type2_character_scalar; + case vctrs_type_null: *left = 1; return VCTRS_TYPE2_null_character; + case vctrs_type_unspecified: *left = 1; return VCTRS_TYPE2_unspecified_character; + case vctrs_type_logical: *left = 1; return VCTRS_TYPE2_logical_character; + case vctrs_type_integer: *left = 1; return VCTRS_TYPE2_integer_character; + case vctrs_type_double: *left = 1; return VCTRS_TYPE2_double_character; + case vctrs_type_complex: *left = 1; return VCTRS_TYPE2_complex_character; + case vctrs_type_character: *left = -1; return VCTRS_TYPE2_character_character; + case vctrs_type_raw: *left = 0; return VCTRS_TYPE2_character_raw; + case vctrs_type_list: *left = 0; return VCTRS_TYPE2_character_list; + case vctrs_type_dataframe: *left = 0; return VCTRS_TYPE2_character_dataframe; + case vctrs_type_s3: *left = 0; return VCTRS_TYPE2_character_s3; + case vctrs_type_scalar: *left = 0; return VCTRS_TYPE2_character_scalar; } } case vctrs_type_raw: { switch (type_y) { - case vctrs_type_null: *left = 1; return vctrs_type2_null_raw; - case vctrs_type_unspecified: *left = 1; return vctrs_type2_unspecified_raw; - case vctrs_type_logical: *left = 1; return vctrs_type2_logical_raw; - case vctrs_type_integer: *left = 1; return vctrs_type2_integer_raw; - case vctrs_type_double: *left = 1; return vctrs_type2_double_raw; - case vctrs_type_complex: *left = 1; return vctrs_type2_complex_raw; - case vctrs_type_character: *left = 1; return vctrs_type2_character_raw; - case vctrs_type_raw: *left = -1; return vctrs_type2_raw_raw; - case vctrs_type_list: *left = 0; return vctrs_type2_raw_list; - case vctrs_type_dataframe: *left = 0; return vctrs_type2_raw_dataframe; - case vctrs_type_s3: *left = 0; return vctrs_type2_raw_s3; - case vctrs_type_scalar: *left = 0; return vctrs_type2_raw_scalar; + case vctrs_type_null: *left = 1; return VCTRS_TYPE2_null_raw; + case vctrs_type_unspecified: *left = 1; return VCTRS_TYPE2_unspecified_raw; + case vctrs_type_logical: *left = 1; return VCTRS_TYPE2_logical_raw; + case vctrs_type_integer: *left = 1; return VCTRS_TYPE2_integer_raw; + case vctrs_type_double: *left = 1; return VCTRS_TYPE2_double_raw; + case vctrs_type_complex: *left = 1; return VCTRS_TYPE2_complex_raw; + case vctrs_type_character: *left = 1; return VCTRS_TYPE2_character_raw; + case vctrs_type_raw: *left = -1; return VCTRS_TYPE2_raw_raw; + case vctrs_type_list: *left = 0; return VCTRS_TYPE2_raw_list; + case vctrs_type_dataframe: *left = 0; return VCTRS_TYPE2_raw_dataframe; + case vctrs_type_s3: *left = 0; return VCTRS_TYPE2_raw_s3; + case vctrs_type_scalar: *left = 0; return VCTRS_TYPE2_raw_scalar; } } case vctrs_type_list: { switch (type_y) { - case vctrs_type_null: *left = 1; return vctrs_type2_null_list; - case vctrs_type_unspecified: *left = 1; return vctrs_type2_unspecified_list; - case vctrs_type_logical: *left = 1; return vctrs_type2_logical_list; - case vctrs_type_integer: *left = 1; return vctrs_type2_integer_list; - case vctrs_type_double: *left = 1; return vctrs_type2_double_list; - case vctrs_type_complex: *left = 1; return vctrs_type2_complex_list; - case vctrs_type_character: *left = 1; return vctrs_type2_character_list; - case vctrs_type_raw: *left = 1; return vctrs_type2_raw_list; - case vctrs_type_list: *left = -1; return vctrs_type2_list_list; - case vctrs_type_dataframe: *left = 0; return vctrs_type2_list_dataframe; - case vctrs_type_s3: *left = 0; return vctrs_type2_list_s3; - case vctrs_type_scalar: *left = 0; return vctrs_type2_list_scalar; + case vctrs_type_null: *left = 1; return VCTRS_TYPE2_null_list; + case vctrs_type_unspecified: *left = 1; return VCTRS_TYPE2_unspecified_list; + case vctrs_type_logical: *left = 1; return VCTRS_TYPE2_logical_list; + case vctrs_type_integer: *left = 1; return VCTRS_TYPE2_integer_list; + case vctrs_type_double: *left = 1; return VCTRS_TYPE2_double_list; + case vctrs_type_complex: *left = 1; return VCTRS_TYPE2_complex_list; + case vctrs_type_character: *left = 1; return VCTRS_TYPE2_character_list; + case vctrs_type_raw: *left = 1; return VCTRS_TYPE2_raw_list; + case vctrs_type_list: *left = -1; return VCTRS_TYPE2_list_list; + case vctrs_type_dataframe: *left = 0; return VCTRS_TYPE2_list_dataframe; + case vctrs_type_s3: *left = 0; return VCTRS_TYPE2_list_s3; + case vctrs_type_scalar: *left = 0; return VCTRS_TYPE2_list_scalar; } } case vctrs_type_dataframe: { switch (type_y) { - case vctrs_type_null: *left = 1; return vctrs_type2_null_dataframe; - case vctrs_type_unspecified: *left = 1; return vctrs_type2_unspecified_dataframe; - case vctrs_type_logical: *left = 1; return vctrs_type2_logical_dataframe; - case vctrs_type_integer: *left = 1; return vctrs_type2_integer_dataframe; - case vctrs_type_double: *left = 1; return vctrs_type2_double_dataframe; - case vctrs_type_complex: *left = 1; return vctrs_type2_complex_dataframe; - case vctrs_type_character: *left = 1; return vctrs_type2_character_dataframe; - case vctrs_type_raw: *left = 1; return vctrs_type2_raw_dataframe; - case vctrs_type_list: *left = 1; return vctrs_type2_list_dataframe; - case vctrs_type_dataframe: *left = -1; return vctrs_type2_dataframe_dataframe; - case vctrs_type_s3: *left = 0; return vctrs_type2_dataframe_s3; - case vctrs_type_scalar: *left = 0; return vctrs_type2_dataframe_scalar; + case vctrs_type_null: *left = 1; return VCTRS_TYPE2_null_dataframe; + case vctrs_type_unspecified: *left = 1; return VCTRS_TYPE2_unspecified_dataframe; + case vctrs_type_logical: *left = 1; return VCTRS_TYPE2_logical_dataframe; + case vctrs_type_integer: *left = 1; return VCTRS_TYPE2_integer_dataframe; + case vctrs_type_double: *left = 1; return VCTRS_TYPE2_double_dataframe; + case vctrs_type_complex: *left = 1; return VCTRS_TYPE2_complex_dataframe; + case vctrs_type_character: *left = 1; return VCTRS_TYPE2_character_dataframe; + case vctrs_type_raw: *left = 1; return VCTRS_TYPE2_raw_dataframe; + case vctrs_type_list: *left = 1; return VCTRS_TYPE2_list_dataframe; + case vctrs_type_dataframe: *left = -1; return VCTRS_TYPE2_dataframe_dataframe; + case vctrs_type_s3: *left = 0; return VCTRS_TYPE2_dataframe_s3; + case vctrs_type_scalar: *left = 0; return VCTRS_TYPE2_dataframe_scalar; } } case vctrs_type_s3: { switch (type_y) { - case vctrs_type_null: *left = 1; return vctrs_type2_null_s3; - case vctrs_type_unspecified: *left = 1; return vctrs_type2_unspecified_s3; - case vctrs_type_logical: *left = 1; return vctrs_type2_logical_s3; - case vctrs_type_integer: *left = 1; return vctrs_type2_integer_s3; - case vctrs_type_double: *left = 1; return vctrs_type2_double_s3; - case vctrs_type_complex: *left = 1; return vctrs_type2_complex_s3; - case vctrs_type_character: *left = 1; return vctrs_type2_character_s3; - case vctrs_type_raw: *left = 1; return vctrs_type2_raw_s3; - case vctrs_type_list: *left = 1; return vctrs_type2_list_s3; - case vctrs_type_dataframe: *left = 1; return vctrs_type2_dataframe_s3; - case vctrs_type_s3: *left = -1; return vctrs_type2_s3_s3; - case vctrs_type_scalar: *left = 0; return vctrs_type2_s3_scalar; + case vctrs_type_null: *left = 1; return VCTRS_TYPE2_null_s3; + case vctrs_type_unspecified: *left = 1; return VCTRS_TYPE2_unspecified_s3; + case vctrs_type_logical: *left = 1; return VCTRS_TYPE2_logical_s3; + case vctrs_type_integer: *left = 1; return VCTRS_TYPE2_integer_s3; + case vctrs_type_double: *left = 1; return VCTRS_TYPE2_double_s3; + case vctrs_type_complex: *left = 1; return VCTRS_TYPE2_complex_s3; + case vctrs_type_character: *left = 1; return VCTRS_TYPE2_character_s3; + case vctrs_type_raw: *left = 1; return VCTRS_TYPE2_raw_s3; + case vctrs_type_list: *left = 1; return VCTRS_TYPE2_list_s3; + case vctrs_type_dataframe: *left = 1; return VCTRS_TYPE2_dataframe_s3; + case vctrs_type_s3: *left = -1; return VCTRS_TYPE2_S3_s3; + case vctrs_type_scalar: *left = 0; return VCTRS_TYPE2_S3_scalar; } } case vctrs_type_scalar: { switch (type_y) { - case vctrs_type_null: *left = 1; return vctrs_type2_null_scalar; - case vctrs_type_unspecified: *left = 1; return vctrs_type2_unspecified_scalar; - case vctrs_type_logical: *left = 1; return vctrs_type2_logical_scalar; - case vctrs_type_integer: *left = 1; return vctrs_type2_integer_scalar; - case vctrs_type_double: *left = 1; return vctrs_type2_double_scalar; - case vctrs_type_complex: *left = 1; return vctrs_type2_complex_scalar; - case vctrs_type_character: *left = 1; return vctrs_type2_character_scalar; - case vctrs_type_raw: *left = 1; return vctrs_type2_raw_scalar; - case vctrs_type_list: *left = 1; return vctrs_type2_list_scalar; - case vctrs_type_dataframe: *left = 1; return vctrs_type2_dataframe_scalar; - case vctrs_type_s3: *left = 1; return vctrs_type2_s3_scalar; - case vctrs_type_scalar: *left = -1; return vctrs_type2_scalar_scalar; + case vctrs_type_null: *left = 1; return VCTRS_TYPE2_null_scalar; + case vctrs_type_unspecified: *left = 1; return VCTRS_TYPE2_unspecified_scalar; + case vctrs_type_logical: *left = 1; return VCTRS_TYPE2_logical_scalar; + case vctrs_type_integer: *left = 1; return VCTRS_TYPE2_integer_scalar; + case vctrs_type_double: *left = 1; return VCTRS_TYPE2_double_scalar; + case vctrs_type_complex: *left = 1; return VCTRS_TYPE2_complex_scalar; + case vctrs_type_character: *left = 1; return VCTRS_TYPE2_character_scalar; + case vctrs_type_raw: *left = 1; return VCTRS_TYPE2_raw_scalar; + case vctrs_type_list: *left = 1; return VCTRS_TYPE2_list_scalar; + case vctrs_type_dataframe: *left = 1; return VCTRS_TYPE2_dataframe_scalar; + case vctrs_type_s3: *left = 1; return VCTRS_TYPE2_S3_scalar; + case vctrs_type_scalar: *left = -1; return VCTRS_TYPE2_scalar_scalar; } }} @@ -226,95 +226,95 @@ enum vctrs_type2 vec_typeof2(SEXP x, SEXP y) { const char* vctrs_type2_as_str(enum vctrs_type2 type) { switch (type) { - case vctrs_type2_null_null: return "vctrs_type2_null_null"; - case vctrs_type2_null_logical: return "vctrs_type2_null_logical"; - case vctrs_type2_null_integer: return "vctrs_type2_null_integer"; - case vctrs_type2_null_double: return "vctrs_type2_null_double"; - case vctrs_type2_null_complex: return "vctrs_type2_null_complex"; - case vctrs_type2_null_character: return "vctrs_type2_null_character"; - case vctrs_type2_null_raw: return "vctrs_type2_null_raw"; - case vctrs_type2_null_list: return "vctrs_type2_null_list"; - case vctrs_type2_null_dataframe: return "vctrs_type2_null_dataframe"; - case vctrs_type2_null_s3: return "vctrs_type2_null_s3"; - case vctrs_type2_null_unspecified: return "vctrs_type2_null_unspecified"; - case vctrs_type2_null_scalar: return "vctrs_type2_null_scalar"; + case VCTRS_TYPE2_null_null: return "VCTRS_TYPE2_null_null"; + case VCTRS_TYPE2_null_logical: return "VCTRS_TYPE2_null_logical"; + case VCTRS_TYPE2_null_integer: return "VCTRS_TYPE2_null_integer"; + case VCTRS_TYPE2_null_double: return "VCTRS_TYPE2_null_double"; + case VCTRS_TYPE2_null_complex: return "VCTRS_TYPE2_null_complex"; + case VCTRS_TYPE2_null_character: return "VCTRS_TYPE2_null_character"; + case VCTRS_TYPE2_null_raw: return "VCTRS_TYPE2_null_raw"; + case VCTRS_TYPE2_null_list: return "VCTRS_TYPE2_null_list"; + case VCTRS_TYPE2_null_dataframe: return "VCTRS_TYPE2_null_dataframe"; + case VCTRS_TYPE2_null_s3: return "VCTRS_TYPE2_null_s3"; + case VCTRS_TYPE2_null_unspecified: return "VCTRS_TYPE2_null_unspecified"; + case VCTRS_TYPE2_null_scalar: return "VCTRS_TYPE2_null_scalar"; - case vctrs_type2_unspecified_logical: return "vctrs_type2_unspecified_logical"; - case vctrs_type2_unspecified_integer: return "vctrs_type2_unspecified_integer"; - case vctrs_type2_unspecified_double: return "vctrs_type2_unspecified_double"; - case vctrs_type2_unspecified_complex: return "vctrs_type2_unspecified_complex"; - case vctrs_type2_unspecified_character: return "vctrs_type2_unspecified_character"; - case vctrs_type2_unspecified_raw: return "vctrs_type2_unspecified_raw"; - case vctrs_type2_unspecified_list: return "vctrs_type2_unspecified_list"; - case vctrs_type2_unspecified_dataframe: return "vctrs_type2_unspecified_dataframe"; - case vctrs_type2_unspecified_s3: return "vctrs_type2_unspecified_s3"; - case vctrs_type2_unspecified_unspecified: return "vctrs_type2_unspecified_unspecified"; - case vctrs_type2_unspecified_scalar: return "vctrs_type2_unspecified_scalar"; + case VCTRS_TYPE2_unspecified_logical: return "VCTRS_TYPE2_unspecified_logical"; + case VCTRS_TYPE2_unspecified_integer: return "VCTRS_TYPE2_unspecified_integer"; + case VCTRS_TYPE2_unspecified_double: return "VCTRS_TYPE2_unspecified_double"; + case VCTRS_TYPE2_unspecified_complex: return "VCTRS_TYPE2_unspecified_complex"; + case VCTRS_TYPE2_unspecified_character: return "VCTRS_TYPE2_unspecified_character"; + case VCTRS_TYPE2_unspecified_raw: return "VCTRS_TYPE2_unspecified_raw"; + case VCTRS_TYPE2_unspecified_list: return "VCTRS_TYPE2_unspecified_list"; + case VCTRS_TYPE2_unspecified_dataframe: return "VCTRS_TYPE2_unspecified_dataframe"; + case VCTRS_TYPE2_unspecified_s3: return "VCTRS_TYPE2_unspecified_s3"; + case VCTRS_TYPE2_unspecified_unspecified: return "VCTRS_TYPE2_unspecified_unspecified"; + case VCTRS_TYPE2_unspecified_scalar: return "VCTRS_TYPE2_unspecified_scalar"; - case vctrs_type2_logical_logical: return "vctrs_type2_logical_logical"; - case vctrs_type2_logical_integer: return "vctrs_type2_logical_integer"; - case vctrs_type2_logical_double: return "vctrs_type2_logical_double"; - case vctrs_type2_logical_complex: return "vctrs_type2_logical_complex"; - case vctrs_type2_logical_character: return "vctrs_type2_logical_character"; - case vctrs_type2_logical_raw: return "vctrs_type2_logical_raw"; - case vctrs_type2_logical_list: return "vctrs_type2_logical_list"; - case vctrs_type2_logical_dataframe: return "vctrs_type2_logical_dataframe"; - case vctrs_type2_logical_s3: return "vctrs_type2_logical_s3"; - case vctrs_type2_logical_scalar: return "vctrs_type2_logical_scalar"; + case VCTRS_TYPE2_logical_logical: return "VCTRS_TYPE2_logical_logical"; + case VCTRS_TYPE2_logical_integer: return "VCTRS_TYPE2_logical_integer"; + case VCTRS_TYPE2_logical_double: return "VCTRS_TYPE2_logical_double"; + case VCTRS_TYPE2_logical_complex: return "VCTRS_TYPE2_logical_complex"; + case VCTRS_TYPE2_logical_character: return "VCTRS_TYPE2_logical_character"; + case VCTRS_TYPE2_logical_raw: return "VCTRS_TYPE2_logical_raw"; + case VCTRS_TYPE2_logical_list: return "VCTRS_TYPE2_logical_list"; + case VCTRS_TYPE2_logical_dataframe: return "VCTRS_TYPE2_logical_dataframe"; + case VCTRS_TYPE2_logical_s3: return "VCTRS_TYPE2_logical_s3"; + case VCTRS_TYPE2_logical_scalar: return "VCTRS_TYPE2_logical_scalar"; - case vctrs_type2_integer_integer: return "vctrs_type2_integer_integer"; - case vctrs_type2_integer_double: return "vctrs_type2_integer_double"; - case vctrs_type2_integer_complex: return "vctrs_type2_integer_complex"; - case vctrs_type2_integer_character: return "vctrs_type2_integer_character"; - case vctrs_type2_integer_raw: return "vctrs_type2_integer_raw"; - case vctrs_type2_integer_list: return "vctrs_type2_integer_list"; - case vctrs_type2_integer_dataframe: return "vctrs_type2_integer_dataframe"; - case vctrs_type2_integer_s3: return "vctrs_type2_integer_s3"; - case vctrs_type2_integer_scalar: return "vctrs_type2_integer_scalar"; + case VCTRS_TYPE2_integer_integer: return "VCTRS_TYPE2_integer_integer"; + case VCTRS_TYPE2_integer_double: return "VCTRS_TYPE2_integer_double"; + case VCTRS_TYPE2_integer_complex: return "VCTRS_TYPE2_integer_complex"; + case VCTRS_TYPE2_integer_character: return "VCTRS_TYPE2_integer_character"; + case VCTRS_TYPE2_integer_raw: return "VCTRS_TYPE2_integer_raw"; + case VCTRS_TYPE2_integer_list: return "VCTRS_TYPE2_integer_list"; + case VCTRS_TYPE2_integer_dataframe: return "VCTRS_TYPE2_integer_dataframe"; + case VCTRS_TYPE2_integer_s3: return "VCTRS_TYPE2_integer_s3"; + case VCTRS_TYPE2_integer_scalar: return "VCTRS_TYPE2_integer_scalar"; - case vctrs_type2_double_double: return "vctrs_type2_double_double"; - case vctrs_type2_double_complex: return "vctrs_type2_double_complex"; - case vctrs_type2_double_character: return "vctrs_type2_double_character"; - case vctrs_type2_double_raw: return "vctrs_type2_double_raw"; - case vctrs_type2_double_list: return "vctrs_type2_double_list"; - case vctrs_type2_double_dataframe: return "vctrs_type2_double_dataframe"; - case vctrs_type2_double_s3: return "vctrs_type2_double_s3"; - case vctrs_type2_double_scalar: return "vctrs_type2_double_scalar"; + case VCTRS_TYPE2_double_double: return "VCTRS_TYPE2_double_double"; + case VCTRS_TYPE2_double_complex: return "VCTRS_TYPE2_double_complex"; + case VCTRS_TYPE2_double_character: return "VCTRS_TYPE2_double_character"; + case VCTRS_TYPE2_double_raw: return "VCTRS_TYPE2_double_raw"; + case VCTRS_TYPE2_double_list: return "VCTRS_TYPE2_double_list"; + case VCTRS_TYPE2_double_dataframe: return "VCTRS_TYPE2_double_dataframe"; + case VCTRS_TYPE2_double_s3: return "VCTRS_TYPE2_double_s3"; + case VCTRS_TYPE2_double_scalar: return "VCTRS_TYPE2_double_scalar"; - case vctrs_type2_complex_complex: return "vctrs_type2_complex_complex"; - case vctrs_type2_complex_character: return "vctrs_type2_complex_character"; - case vctrs_type2_complex_raw: return "vctrs_type2_complex_raw"; - case vctrs_type2_complex_list: return "vctrs_type2_complex_list"; - case vctrs_type2_complex_dataframe: return "vctrs_type2_complex_dataframe"; - case vctrs_type2_complex_s3: return "vctrs_type2_complex_s3"; - case vctrs_type2_complex_scalar: return "vctrs_type2_complex_scalar"; + case VCTRS_TYPE2_complex_complex: return "VCTRS_TYPE2_complex_complex"; + case VCTRS_TYPE2_complex_character: return "VCTRS_TYPE2_complex_character"; + case VCTRS_TYPE2_complex_raw: return "VCTRS_TYPE2_complex_raw"; + case VCTRS_TYPE2_complex_list: return "VCTRS_TYPE2_complex_list"; + case VCTRS_TYPE2_complex_dataframe: return "VCTRS_TYPE2_complex_dataframe"; + case VCTRS_TYPE2_complex_s3: return "VCTRS_TYPE2_complex_s3"; + case VCTRS_TYPE2_complex_scalar: return "VCTRS_TYPE2_complex_scalar"; - case vctrs_type2_character_character: return "vctrs_type2_character_character"; - case vctrs_type2_character_raw: return "vctrs_type2_character_raw"; - case vctrs_type2_character_list: return "vctrs_type2_character_list"; - case vctrs_type2_character_dataframe: return "vctrs_type2_character_dataframe"; - case vctrs_type2_character_s3: return "vctrs_type2_character_s3"; - case vctrs_type2_character_scalar: return "vctrs_type2_character_scalar"; + case VCTRS_TYPE2_character_character: return "VCTRS_TYPE2_character_character"; + case VCTRS_TYPE2_character_raw: return "VCTRS_TYPE2_character_raw"; + case VCTRS_TYPE2_character_list: return "VCTRS_TYPE2_character_list"; + case VCTRS_TYPE2_character_dataframe: return "VCTRS_TYPE2_character_dataframe"; + case VCTRS_TYPE2_character_s3: return "VCTRS_TYPE2_character_s3"; + case VCTRS_TYPE2_character_scalar: return "VCTRS_TYPE2_character_scalar"; - case vctrs_type2_raw_raw: return "vctrs_type2_raw_raw"; - case vctrs_type2_raw_list: return "vctrs_type2_raw_list"; - case vctrs_type2_raw_dataframe: return "vctrs_type2_raw_dataframe"; - case vctrs_type2_raw_s3: return "vctrs_type2_raw_s3"; - case vctrs_type2_raw_scalar: return "vctrs_type2_raw_scalar"; + case VCTRS_TYPE2_raw_raw: return "VCTRS_TYPE2_raw_raw"; + case VCTRS_TYPE2_raw_list: return "VCTRS_TYPE2_raw_list"; + case VCTRS_TYPE2_raw_dataframe: return "VCTRS_TYPE2_raw_dataframe"; + case VCTRS_TYPE2_raw_s3: return "VCTRS_TYPE2_raw_s3"; + case VCTRS_TYPE2_raw_scalar: return "VCTRS_TYPE2_raw_scalar"; - case vctrs_type2_list_list: return "vctrs_type2_list_list"; - case vctrs_type2_list_dataframe: return "vctrs_type2_list_dataframe"; - case vctrs_type2_list_s3: return "vctrs_type2_list_s3"; - case vctrs_type2_list_scalar: return "vctrs_type2_list_scalar"; + case VCTRS_TYPE2_list_list: return "VCTRS_TYPE2_list_list"; + case VCTRS_TYPE2_list_dataframe: return "VCTRS_TYPE2_list_dataframe"; + case VCTRS_TYPE2_list_s3: return "VCTRS_TYPE2_list_s3"; + case VCTRS_TYPE2_list_scalar: return "VCTRS_TYPE2_list_scalar"; - case vctrs_type2_dataframe_dataframe: return "vctrs_type2_dataframe_dataframe"; - case vctrs_type2_dataframe_s3: return "vctrs_type2_dataframe_s3"; - case vctrs_type2_dataframe_scalar: return "vctrs_type2_dataframe_scalar"; + case VCTRS_TYPE2_dataframe_dataframe: return "VCTRS_TYPE2_dataframe_dataframe"; + case VCTRS_TYPE2_dataframe_s3: return "VCTRS_TYPE2_dataframe_s3"; + case VCTRS_TYPE2_dataframe_scalar: return "VCTRS_TYPE2_dataframe_scalar"; - case vctrs_type2_s3_s3: return "vctrs_type2_s3_s3"; - case vctrs_type2_s3_scalar: return "vctrs_type2_s3_scalar"; + case VCTRS_TYPE2_S3_s3: return "VCTRS_TYPE2_S3_s3"; + case VCTRS_TYPE2_S3_scalar: return "VCTRS_TYPE2_S3_scalar"; - case vctrs_type2_scalar_scalar: return "vctrs_type2_scalar_scalar"; + case VCTRS_TYPE2_scalar_scalar: return "VCTRS_TYPE2_scalar_scalar"; } never_reached("vctrs_type2_as_str"); diff --git a/src/vctrs.h b/src/vctrs.h index 264120a4d..8fd7c12b8 100644 --- a/src/vctrs.h +++ b/src/vctrs.h @@ -9,220 +9,220 @@ // After adding a new `vctrs_dispatch` type, add the missing entries // in `vec_typeof2()` enum vctrs_type2 { - vctrs_type2_null_null, - vctrs_type2_null_unspecified, - vctrs_type2_null_logical, - vctrs_type2_null_integer, - vctrs_type2_null_double, - vctrs_type2_null_complex, - vctrs_type2_null_character, - vctrs_type2_null_raw, - vctrs_type2_null_list, - vctrs_type2_null_dataframe, - vctrs_type2_null_s3, - vctrs_type2_null_scalar, - - vctrs_type2_unspecified_unspecified, - vctrs_type2_unspecified_logical, - vctrs_type2_unspecified_integer, - vctrs_type2_unspecified_double, - vctrs_type2_unspecified_complex, - vctrs_type2_unspecified_character, - vctrs_type2_unspecified_raw, - vctrs_type2_unspecified_list, - vctrs_type2_unspecified_dataframe, - vctrs_type2_unspecified_s3, - vctrs_type2_unspecified_scalar, - - vctrs_type2_logical_logical, - vctrs_type2_logical_integer, - vctrs_type2_logical_double, - vctrs_type2_logical_complex, - vctrs_type2_logical_character, - vctrs_type2_logical_raw, - vctrs_type2_logical_list, - vctrs_type2_logical_dataframe, - vctrs_type2_logical_s3, - vctrs_type2_logical_scalar, - - vctrs_type2_integer_integer, - vctrs_type2_integer_double, - vctrs_type2_integer_complex, - vctrs_type2_integer_character, - vctrs_type2_integer_raw, - vctrs_type2_integer_list, - vctrs_type2_integer_dataframe, - vctrs_type2_integer_s3, - vctrs_type2_integer_scalar, - - vctrs_type2_double_double, - vctrs_type2_double_complex, - vctrs_type2_double_character, - vctrs_type2_double_raw, - vctrs_type2_double_list, - vctrs_type2_double_dataframe, - vctrs_type2_double_s3, - vctrs_type2_double_scalar, - - vctrs_type2_complex_complex, - vctrs_type2_complex_character, - vctrs_type2_complex_raw, - vctrs_type2_complex_list, - vctrs_type2_complex_dataframe, - vctrs_type2_complex_s3, - vctrs_type2_complex_scalar, - - vctrs_type2_character_character, - vctrs_type2_character_raw, - vctrs_type2_character_list, - vctrs_type2_character_dataframe, - vctrs_type2_character_s3, - vctrs_type2_character_scalar, - - vctrs_type2_raw_raw, - vctrs_type2_raw_list, - vctrs_type2_raw_dataframe, - vctrs_type2_raw_s3, - vctrs_type2_raw_scalar, - - vctrs_type2_list_list, - vctrs_type2_list_dataframe, - vctrs_type2_list_s3, - vctrs_type2_list_scalar, - - vctrs_type2_dataframe_dataframe, - vctrs_type2_dataframe_s3, - vctrs_type2_dataframe_scalar, - - vctrs_type2_s3_s3, - vctrs_type2_s3_scalar, - - vctrs_type2_scalar_scalar + VCTRS_TYPE2_null_null, + VCTRS_TYPE2_null_unspecified, + VCTRS_TYPE2_null_logical, + VCTRS_TYPE2_null_integer, + VCTRS_TYPE2_null_double, + VCTRS_TYPE2_null_complex, + VCTRS_TYPE2_null_character, + VCTRS_TYPE2_null_raw, + VCTRS_TYPE2_null_list, + VCTRS_TYPE2_null_dataframe, + VCTRS_TYPE2_null_s3, + VCTRS_TYPE2_null_scalar, + + VCTRS_TYPE2_unspecified_unspecified, + VCTRS_TYPE2_unspecified_logical, + VCTRS_TYPE2_unspecified_integer, + VCTRS_TYPE2_unspecified_double, + VCTRS_TYPE2_unspecified_complex, + VCTRS_TYPE2_unspecified_character, + VCTRS_TYPE2_unspecified_raw, + VCTRS_TYPE2_unspecified_list, + VCTRS_TYPE2_unspecified_dataframe, + VCTRS_TYPE2_unspecified_s3, + VCTRS_TYPE2_unspecified_scalar, + + VCTRS_TYPE2_logical_logical, + VCTRS_TYPE2_logical_integer, + VCTRS_TYPE2_logical_double, + VCTRS_TYPE2_logical_complex, + VCTRS_TYPE2_logical_character, + VCTRS_TYPE2_logical_raw, + VCTRS_TYPE2_logical_list, + VCTRS_TYPE2_logical_dataframe, + VCTRS_TYPE2_logical_s3, + VCTRS_TYPE2_logical_scalar, + + VCTRS_TYPE2_integer_integer, + VCTRS_TYPE2_integer_double, + VCTRS_TYPE2_integer_complex, + VCTRS_TYPE2_integer_character, + VCTRS_TYPE2_integer_raw, + VCTRS_TYPE2_integer_list, + VCTRS_TYPE2_integer_dataframe, + VCTRS_TYPE2_integer_s3, + VCTRS_TYPE2_integer_scalar, + + VCTRS_TYPE2_double_double, + VCTRS_TYPE2_double_complex, + VCTRS_TYPE2_double_character, + VCTRS_TYPE2_double_raw, + VCTRS_TYPE2_double_list, + VCTRS_TYPE2_double_dataframe, + VCTRS_TYPE2_double_s3, + VCTRS_TYPE2_double_scalar, + + VCTRS_TYPE2_complex_complex, + VCTRS_TYPE2_complex_character, + VCTRS_TYPE2_complex_raw, + VCTRS_TYPE2_complex_list, + VCTRS_TYPE2_complex_dataframe, + VCTRS_TYPE2_complex_s3, + VCTRS_TYPE2_complex_scalar, + + VCTRS_TYPE2_character_character, + VCTRS_TYPE2_character_raw, + VCTRS_TYPE2_character_list, + VCTRS_TYPE2_character_dataframe, + VCTRS_TYPE2_character_s3, + VCTRS_TYPE2_character_scalar, + + VCTRS_TYPE2_raw_raw, + VCTRS_TYPE2_raw_list, + VCTRS_TYPE2_raw_dataframe, + VCTRS_TYPE2_raw_s3, + VCTRS_TYPE2_raw_scalar, + + VCTRS_TYPE2_list_list, + VCTRS_TYPE2_list_dataframe, + VCTRS_TYPE2_list_s3, + VCTRS_TYPE2_list_scalar, + + VCTRS_TYPE2_dataframe_dataframe, + VCTRS_TYPE2_dataframe_s3, + VCTRS_TYPE2_dataframe_scalar, + + VCTRS_TYPE2_S3_s3, + VCTRS_TYPE2_S3_scalar, + + VCTRS_TYPE2_scalar_scalar }; enum vctrs_type2_s3 { - vctrs_type2_s3_null_bare_factor, - vctrs_type2_s3_null_bare_ordered, - vctrs_type2_s3_null_bare_date, - vctrs_type2_s3_null_bare_posixct, - vctrs_type2_s3_null_bare_posixlt, - vctrs_type2_s3_null_bare_tibble, - vctrs_type2_s3_null_unknown, - - vctrs_type2_s3_unspecified_bare_factor, - vctrs_type2_s3_unspecified_bare_ordered, - vctrs_type2_s3_unspecified_bare_date, - vctrs_type2_s3_unspecified_bare_posixct, - vctrs_type2_s3_unspecified_bare_posixlt, - vctrs_type2_s3_unspecified_bare_tibble, - vctrs_type2_s3_unspecified_unknown, - - vctrs_type2_s3_logical_bare_factor, - vctrs_type2_s3_logical_bare_ordered, - vctrs_type2_s3_logical_bare_date, - vctrs_type2_s3_logical_bare_posixct, - vctrs_type2_s3_logical_bare_posixlt, - vctrs_type2_s3_logical_bare_tibble, - vctrs_type2_s3_logical_unknown, - - vctrs_type2_s3_integer_bare_factor, - vctrs_type2_s3_integer_bare_ordered, - vctrs_type2_s3_integer_bare_date, - vctrs_type2_s3_integer_bare_posixct, - vctrs_type2_s3_integer_bare_posixlt, - vctrs_type2_s3_integer_bare_tibble, - vctrs_type2_s3_integer_unknown, - - vctrs_type2_s3_double_bare_factor, - vctrs_type2_s3_double_bare_ordered, - vctrs_type2_s3_double_bare_date, - vctrs_type2_s3_double_bare_posixct, - vctrs_type2_s3_double_bare_posixlt, - vctrs_type2_s3_double_bare_tibble, - vctrs_type2_s3_double_unknown, - - vctrs_type2_s3_complex_bare_factor, - vctrs_type2_s3_complex_bare_ordered, - vctrs_type2_s3_complex_bare_date, - vctrs_type2_s3_complex_bare_posixct, - vctrs_type2_s3_complex_bare_posixlt, - vctrs_type2_s3_complex_bare_tibble, - vctrs_type2_s3_complex_unknown, - - vctrs_type2_s3_character_bare_factor, - vctrs_type2_s3_character_bare_ordered, - vctrs_type2_s3_character_bare_date, - vctrs_type2_s3_character_bare_posixct, - vctrs_type2_s3_character_bare_posixlt, - vctrs_type2_s3_character_bare_tibble, - vctrs_type2_s3_character_unknown, - - vctrs_type2_s3_raw_bare_factor, - vctrs_type2_s3_raw_bare_ordered, - vctrs_type2_s3_raw_bare_date, - vctrs_type2_s3_raw_bare_posixct, - vctrs_type2_s3_raw_bare_posixlt, - vctrs_type2_s3_raw_bare_tibble, - vctrs_type2_s3_raw_unknown, - - vctrs_type2_s3_list_bare_factor, - vctrs_type2_s3_list_bare_ordered, - vctrs_type2_s3_list_bare_date, - vctrs_type2_s3_list_bare_posixct, - vctrs_type2_s3_list_bare_posixlt, - vctrs_type2_s3_list_bare_tibble, - vctrs_type2_s3_list_unknown, - - vctrs_type2_s3_dataframe_bare_factor, - vctrs_type2_s3_dataframe_bare_ordered, - vctrs_type2_s3_dataframe_bare_date, - vctrs_type2_s3_dataframe_bare_posixct, - vctrs_type2_s3_dataframe_bare_posixlt, - vctrs_type2_s3_dataframe_bare_tibble, - vctrs_type2_s3_dataframe_unknown, - - vctrs_type2_s3_scalar_bare_factor, - vctrs_type2_s3_scalar_bare_ordered, - vctrs_type2_s3_scalar_bare_date, - vctrs_type2_s3_scalar_bare_posixct, - vctrs_type2_s3_scalar_bare_posixlt, - vctrs_type2_s3_scalar_bare_tibble, - vctrs_type2_s3_scalar_unknown, - - vctrs_type2_s3_bare_factor_bare_factor, - vctrs_type2_s3_bare_factor_bare_ordered, - vctrs_type2_s3_bare_factor_bare_date, - vctrs_type2_s3_bare_factor_bare_posixct, - vctrs_type2_s3_bare_factor_bare_posixlt, - vctrs_type2_s3_bare_factor_bare_tibble, - vctrs_type2_s3_bare_factor_unknown, - - vctrs_type2_s3_bare_ordered_bare_ordered, - vctrs_type2_s3_bare_ordered_bare_date, - vctrs_type2_s3_bare_ordered_bare_posixct, - vctrs_type2_s3_bare_ordered_bare_posixlt, - vctrs_type2_s3_bare_ordered_bare_tibble, - vctrs_type2_s3_bare_ordered_unknown, - - vctrs_type2_s3_bare_date_bare_date, - vctrs_type2_s3_bare_date_bare_posixct, - vctrs_type2_s3_bare_date_bare_posixlt, - vctrs_type2_s3_bare_date_bare_tibble, - vctrs_type2_s3_bare_date_unknown, - - vctrs_type2_s3_bare_posixct_bare_posixct, - vctrs_type2_s3_bare_posixct_bare_posixlt, - vctrs_type2_s3_bare_posixct_bare_tibble, - vctrs_type2_s3_bare_posixct_unknown, - - vctrs_type2_s3_bare_posixlt_bare_posixlt, - vctrs_type2_s3_bare_posixlt_bare_tibble, - vctrs_type2_s3_bare_posixlt_unknown, - - vctrs_type2_s3_bare_tibble_bare_tibble, - vctrs_type2_s3_bare_tibble_unknown, - - vctrs_type2_s3_unknown_unknown + VCTRS_TYPE2_S3_null_bare_factor, + VCTRS_TYPE2_S3_null_bare_ordered, + VCTRS_TYPE2_S3_null_bare_date, + VCTRS_TYPE2_S3_null_bare_posixct, + VCTRS_TYPE2_S3_null_bare_posixlt, + VCTRS_TYPE2_S3_null_bare_tibble, + VCTRS_TYPE2_S3_null_unknown, + + VCTRS_TYPE2_S3_unspecified_bare_factor, + VCTRS_TYPE2_S3_unspecified_bare_ordered, + VCTRS_TYPE2_S3_unspecified_bare_date, + VCTRS_TYPE2_S3_unspecified_bare_posixct, + VCTRS_TYPE2_S3_unspecified_bare_posixlt, + VCTRS_TYPE2_S3_unspecified_bare_tibble, + VCTRS_TYPE2_S3_unspecified_unknown, + + VCTRS_TYPE2_S3_logical_bare_factor, + VCTRS_TYPE2_S3_logical_bare_ordered, + VCTRS_TYPE2_S3_logical_bare_date, + VCTRS_TYPE2_S3_logical_bare_posixct, + VCTRS_TYPE2_S3_logical_bare_posixlt, + VCTRS_TYPE2_S3_logical_bare_tibble, + VCTRS_TYPE2_S3_logical_unknown, + + VCTRS_TYPE2_S3_integer_bare_factor, + VCTRS_TYPE2_S3_integer_bare_ordered, + VCTRS_TYPE2_S3_integer_bare_date, + VCTRS_TYPE2_S3_integer_bare_posixct, + VCTRS_TYPE2_S3_integer_bare_posixlt, + VCTRS_TYPE2_S3_integer_bare_tibble, + VCTRS_TYPE2_S3_integer_unknown, + + VCTRS_TYPE2_S3_double_bare_factor, + VCTRS_TYPE2_S3_double_bare_ordered, + VCTRS_TYPE2_S3_double_bare_date, + VCTRS_TYPE2_S3_double_bare_posixct, + VCTRS_TYPE2_S3_double_bare_posixlt, + VCTRS_TYPE2_S3_double_bare_tibble, + VCTRS_TYPE2_S3_double_unknown, + + VCTRS_TYPE2_S3_complex_bare_factor, + VCTRS_TYPE2_S3_complex_bare_ordered, + VCTRS_TYPE2_S3_complex_bare_date, + VCTRS_TYPE2_S3_complex_bare_posixct, + VCTRS_TYPE2_S3_complex_bare_posixlt, + VCTRS_TYPE2_S3_complex_bare_tibble, + VCTRS_TYPE2_S3_complex_unknown, + + VCTRS_TYPE2_S3_character_bare_factor, + VCTRS_TYPE2_S3_character_bare_ordered, + VCTRS_TYPE2_S3_character_bare_date, + VCTRS_TYPE2_S3_character_bare_posixct, + VCTRS_TYPE2_S3_character_bare_posixlt, + VCTRS_TYPE2_S3_character_bare_tibble, + VCTRS_TYPE2_S3_character_unknown, + + VCTRS_TYPE2_S3_raw_bare_factor, + VCTRS_TYPE2_S3_raw_bare_ordered, + VCTRS_TYPE2_S3_raw_bare_date, + VCTRS_TYPE2_S3_raw_bare_posixct, + VCTRS_TYPE2_S3_raw_bare_posixlt, + VCTRS_TYPE2_S3_raw_bare_tibble, + VCTRS_TYPE2_S3_raw_unknown, + + VCTRS_TYPE2_S3_list_bare_factor, + VCTRS_TYPE2_S3_list_bare_ordered, + VCTRS_TYPE2_S3_list_bare_date, + VCTRS_TYPE2_S3_list_bare_posixct, + VCTRS_TYPE2_S3_list_bare_posixlt, + VCTRS_TYPE2_S3_list_bare_tibble, + VCTRS_TYPE2_S3_list_unknown, + + VCTRS_TYPE2_S3_dataframe_bare_factor, + VCTRS_TYPE2_S3_dataframe_bare_ordered, + VCTRS_TYPE2_S3_dataframe_bare_date, + VCTRS_TYPE2_S3_dataframe_bare_posixct, + VCTRS_TYPE2_S3_dataframe_bare_posixlt, + VCTRS_TYPE2_S3_dataframe_bare_tibble, + VCTRS_TYPE2_S3_dataframe_unknown, + + VCTRS_TYPE2_S3_scalar_bare_factor, + VCTRS_TYPE2_S3_scalar_bare_ordered, + VCTRS_TYPE2_S3_scalar_bare_date, + VCTRS_TYPE2_S3_scalar_bare_posixct, + VCTRS_TYPE2_S3_scalar_bare_posixlt, + VCTRS_TYPE2_S3_scalar_bare_tibble, + VCTRS_TYPE2_S3_scalar_unknown, + + VCTRS_TYPE2_S3_bare_factor_bare_factor, + VCTRS_TYPE2_S3_bare_factor_bare_ordered, + VCTRS_TYPE2_S3_bare_factor_bare_date, + VCTRS_TYPE2_S3_bare_factor_bare_posixct, + VCTRS_TYPE2_S3_bare_factor_bare_posixlt, + VCTRS_TYPE2_S3_bare_factor_bare_tibble, + VCTRS_TYPE2_S3_bare_factor_unknown, + + VCTRS_TYPE2_S3_bare_ordered_bare_ordered, + VCTRS_TYPE2_S3_bare_ordered_bare_date, + VCTRS_TYPE2_S3_bare_ordered_bare_posixct, + VCTRS_TYPE2_S3_bare_ordered_bare_posixlt, + VCTRS_TYPE2_S3_bare_ordered_bare_tibble, + VCTRS_TYPE2_S3_bare_ordered_unknown, + + VCTRS_TYPE2_S3_bare_date_bare_date, + VCTRS_TYPE2_S3_bare_date_bare_posixct, + VCTRS_TYPE2_S3_bare_date_bare_posixlt, + VCTRS_TYPE2_S3_bare_date_bare_tibble, + VCTRS_TYPE2_S3_bare_date_unknown, + + VCTRS_TYPE2_S3_bare_posixct_bare_posixct, + VCTRS_TYPE2_S3_bare_posixct_bare_posixlt, + VCTRS_TYPE2_S3_bare_posixct_bare_tibble, + VCTRS_TYPE2_S3_bare_posixct_unknown, + + VCTRS_TYPE2_S3_bare_posixlt_bare_posixlt, + VCTRS_TYPE2_S3_bare_posixlt_bare_tibble, + VCTRS_TYPE2_S3_bare_posixlt_unknown, + + VCTRS_TYPE2_S3_bare_tibble_bare_tibble, + VCTRS_TYPE2_S3_bare_tibble_unknown, + + VCTRS_TYPE2_S3_unknown_unknown }; enum vctrs_type2 vec_typeof2(SEXP x, SEXP y); diff --git a/tests/testthat/test-type2.R b/tests/testthat/test-type2.R index 517fbf3d4..68f2a285c 100644 --- a/tests/testthat/test-type2.R +++ b/tests/testthat/test-type2.R @@ -30,9 +30,9 @@ test_that("vec_typeof2() returns common type", { that <- nms[[j]] if (i <= j) { - exp <- paste0("vctrs_type2_", this, "_", that) + exp <- paste0("VCTRS_TYPE2_", this, "_", that) } else { - exp <- paste0("vctrs_type2_", that, "_", this) + exp <- paste0("VCTRS_TYPE2_", that, "_", this) } out <- vec_typeof2(base_empty_types[[this]], base_empty_types[[that]]) @@ -59,9 +59,9 @@ test_that("vec_typeof2_s3() returns common type", { } if (i <= j) { - exp <- paste0("vctrs_type2_s3_", this, "_", that) + exp <- paste0("VCTRS_TYPE2_S3_", this, "_", that) } else { - exp <- paste0("vctrs_type2_s3_", that, "_", this) + exp <- paste0("VCTRS_TYPE2_S3_", that, "_", this) } out <- vec_typeof2_s3(all_base_empty_types[[this]], all_base_empty_types[[that]]) From a875c809ad6ae6fccd66130727dc03e74dedf8e0 Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Mon, 5 Sep 2022 15:28:29 +0200 Subject: [PATCH 015/312] Update `enum vctrs_type` style --- src/cast.c | 8 +- src/compare.c | 52 +++---- src/compare.h | 32 ++-- src/complete.c | 18 +-- src/equal.c | 54 +++---- src/equal.h | 28 ++-- src/hash.c | 32 ++-- src/match-compare.h | 10 +- src/match-joint.c | 36 ++--- src/match.c | 10 +- src/missing.c | 64 ++++---- src/missing.h | 14 +- src/order-collate.c | 10 +- src/order.c | 66 ++++----- src/poly-op.c | 90 +++++------ src/proxy.c | 4 +- src/ptype.c | 24 +-- src/ptype2.c | 18 +-- src/runs.c | 34 ++--- src/size.c | 18 +-- src/slice-array.c | 14 +- src/slice-assign-array.c | 14 +- src/slice-assign.c | 18 +-- src/slice-chop.c | 18 +-- src/slice.c | 36 ++--- src/type-info.c | 58 ++++---- src/type-info.h | 24 +-- src/typeof2-s3.c | 192 ++++++++++++------------ src/typeof2.c | 312 +++++++++++++++++++-------------------- src/utils.c | 4 +- src/utils.h | 12 +- 31 files changed, 662 insertions(+), 662 deletions(-) diff --git a/src/cast.c b/src/cast.c index e6535121d..1a38fea79 100644 --- a/src/cast.c +++ b/src/cast.c @@ -39,14 +39,14 @@ r_obj* vec_cast_opts(const struct cast_opts* opts) { enum vctrs_type x_type = vec_typeof(x); enum vctrs_type to_type = vec_typeof(to); - if (x_type == vctrs_type_unspecified) { + if (x_type == VCTRS_TYPE_unspecified) { return vec_init(to, vec_size(x)); } - if (x_type == vctrs_type_scalar) { + if (x_type == VCTRS_TYPE_scalar) { stop_scalar_type(x, x_arg, opts->call); } - if (to_type == vctrs_type_scalar) { + if (to_type == VCTRS_TYPE_scalar) { stop_scalar_type(to, to_arg, opts->call); } @@ -57,7 +57,7 @@ r_obj* vec_cast_opts(const struct cast_opts* opts) { r_obj* out = r_null; bool lossy = false; - if (to_type == vctrs_type_s3 || x_type == vctrs_type_s3) { + if (to_type == VCTRS_TYPE_s3 || x_type == VCTRS_TYPE_s3) { out = vec_cast_dispatch_native(opts, x_type, to_type, &lossy); } else { out = vec_cast_switch_native(opts, x_type, to_type, &lossy); diff --git a/src/compare.c b/src/compare.c index 3eae80f17..53401d89c 100644 --- a/src/compare.c +++ b/src/compare.c @@ -38,7 +38,7 @@ SEXP vec_compare(SEXP x, SEXP y, bool na_equal) { x = PROTECT(vec_normalize_encoding(x)); y = PROTECT(vec_normalize_encoding(y)); - if (type == vctrs_type_dataframe) { + if (type == VCTRS_TYPE_dataframe) { SEXP out = df_compare(x, y, na_equal, size); UNPROTECT(2); return out; @@ -46,22 +46,22 @@ SEXP vec_compare(SEXP x, SEXP y, bool na_equal) { if (na_equal) { switch (type) { - case vctrs_type_logical: COMPARE(int, LOGICAL_RO, lgl_compare_na_equal); - case vctrs_type_integer: COMPARE(int, INTEGER_RO, int_compare_na_equal); - case vctrs_type_double: COMPARE(double, REAL_RO, dbl_compare_na_equal); - case vctrs_type_character: COMPARE(SEXP, STRING_PTR_RO, chr_compare_na_equal); - case vctrs_type_scalar: r_abort("Can't compare scalars with `vec_compare()`"); - case vctrs_type_list: r_abort("Can't compare lists with `vec_compare()`"); + case VCTRS_TYPE_logical: COMPARE(int, LOGICAL_RO, lgl_compare_na_equal); + case VCTRS_TYPE_integer: COMPARE(int, INTEGER_RO, int_compare_na_equal); + case VCTRS_TYPE_double: COMPARE(double, REAL_RO, dbl_compare_na_equal); + case VCTRS_TYPE_character: COMPARE(SEXP, STRING_PTR_RO, chr_compare_na_equal); + case VCTRS_TYPE_scalar: r_abort("Can't compare scalars with `vec_compare()`"); + case VCTRS_TYPE_list: r_abort("Can't compare lists with `vec_compare()`"); default: stop_unimplemented_vctrs_type("vec_compare", type); } } else { switch (type) { - case vctrs_type_logical: COMPARE(int, LOGICAL_RO, lgl_compare_na_propagate); - case vctrs_type_integer: COMPARE(int, INTEGER_RO, int_compare_na_propagate); - case vctrs_type_double: COMPARE(double, REAL_RO, dbl_compare_na_propagate); - case vctrs_type_character: COMPARE(SEXP, STRING_PTR_RO, chr_compare_na_propagate); - case vctrs_type_scalar: r_abort("Can't compare scalars with `vec_compare()`"); - case vctrs_type_list: r_abort("Can't compare lists with `vec_compare()`"); + case VCTRS_TYPE_logical: COMPARE(int, LOGICAL_RO, lgl_compare_na_propagate); + case VCTRS_TYPE_integer: COMPARE(int, INTEGER_RO, int_compare_na_propagate); + case VCTRS_TYPE_double: COMPARE(double, REAL_RO, dbl_compare_na_propagate); + case VCTRS_TYPE_character: COMPARE(SEXP, STRING_PTR_RO, chr_compare_na_propagate); + case VCTRS_TYPE_scalar: r_abort("Can't compare scalars with `vec_compare()`"); + case VCTRS_TYPE_list: r_abort("Can't compare lists with `vec_compare()`"); default: stop_unimplemented_vctrs_type("vec_compare", type); } } @@ -167,29 +167,29 @@ static void vec_compare_col(int* p_out, bool na_equal) { enum vctrs_type type = vec_proxy_typeof(x); - if (type == vctrs_type_dataframe) { + if (type == VCTRS_TYPE_dataframe) { df_compare_impl(p_out, p_info, x, y, na_equal); return; } if (na_equal) { switch (type) { - case vctrs_type_logical: COMPARE_COL(int, LOGICAL_RO, lgl_compare_na_equal); break; - case vctrs_type_integer: COMPARE_COL(int, INTEGER_RO, int_compare_na_equal); break; - case vctrs_type_double: COMPARE_COL(double, REAL_RO, dbl_compare_na_equal); break; - case vctrs_type_character: COMPARE_COL(SEXP, STRING_PTR_RO, chr_compare_na_equal); break; - case vctrs_type_scalar: r_abort("Can't compare scalars with `vctrs_compare()`"); - case vctrs_type_list: r_abort("Can't compare lists with `vctrs_compare()`"); + case VCTRS_TYPE_logical: COMPARE_COL(int, LOGICAL_RO, lgl_compare_na_equal); break; + case VCTRS_TYPE_integer: COMPARE_COL(int, INTEGER_RO, int_compare_na_equal); break; + case VCTRS_TYPE_double: COMPARE_COL(double, REAL_RO, dbl_compare_na_equal); break; + case VCTRS_TYPE_character: COMPARE_COL(SEXP, STRING_PTR_RO, chr_compare_na_equal); break; + case VCTRS_TYPE_scalar: r_abort("Can't compare scalars with `vctrs_compare()`"); + case VCTRS_TYPE_list: r_abort("Can't compare lists with `vctrs_compare()`"); default: stop_unimplemented_vctrs_type("vec_compare_col", type); } } else { switch (type) { - case vctrs_type_logical: COMPARE_COL(int, LOGICAL_RO, lgl_compare_na_propagate); break; - case vctrs_type_integer: COMPARE_COL(int, INTEGER_RO, int_compare_na_propagate); break; - case vctrs_type_double: COMPARE_COL(double, REAL_RO, dbl_compare_na_propagate); break; - case vctrs_type_character: COMPARE_COL(SEXP, STRING_PTR_RO, chr_compare_na_propagate); break; - case vctrs_type_scalar: r_abort("Can't compare scalars with `vctrs_compare()`"); - case vctrs_type_list: r_abort("Can't compare lists with `vctrs_compare()`"); + case VCTRS_TYPE_logical: COMPARE_COL(int, LOGICAL_RO, lgl_compare_na_propagate); break; + case VCTRS_TYPE_integer: COMPARE_COL(int, INTEGER_RO, int_compare_na_propagate); break; + case VCTRS_TYPE_double: COMPARE_COL(double, REAL_RO, dbl_compare_na_propagate); break; + case VCTRS_TYPE_character: COMPARE_COL(SEXP, STRING_PTR_RO, chr_compare_na_propagate); break; + case VCTRS_TYPE_scalar: r_abort("Can't compare scalars with `vctrs_compare()`"); + case VCTRS_TYPE_list: r_abort("Can't compare lists with `vctrs_compare()`"); default: stop_unimplemented_vctrs_type("vec_compare_col", type); } } diff --git a/src/compare.h b/src/compare.h index d18ea088c..162d095c9 100644 --- a/src/compare.h +++ b/src/compare.h @@ -153,14 +153,14 @@ int p_compare_na_equal(const void* p_x, r_ssize j, const enum vctrs_type type) { switch (type) { - case vctrs_type_null: return p_nil_compare_na_equal(p_x, i, p_y, j); - case vctrs_type_logical: return p_lgl_compare_na_equal(p_x, i, p_y, j); - case vctrs_type_integer: return p_int_compare_na_equal(p_x, i, p_y, j); - case vctrs_type_double: return p_dbl_compare_na_equal(p_x, i, p_y, j); - case vctrs_type_complex: return p_cpl_compare_na_equal(p_x, i, p_y, j); - case vctrs_type_character: return p_chr_compare_na_equal(p_x, i, p_y, j); - case vctrs_type_raw: return p_raw_compare_na_equal(p_x, i, p_y, j); - case vctrs_type_list: return p_list_compare_na_equal(p_x, i, p_y, j); + case VCTRS_TYPE_null: return p_nil_compare_na_equal(p_x, i, p_y, j); + case VCTRS_TYPE_logical: return p_lgl_compare_na_equal(p_x, i, p_y, j); + case VCTRS_TYPE_integer: return p_int_compare_na_equal(p_x, i, p_y, j); + case VCTRS_TYPE_double: return p_dbl_compare_na_equal(p_x, i, p_y, j); + case VCTRS_TYPE_complex: return p_cpl_compare_na_equal(p_x, i, p_y, j); + case VCTRS_TYPE_character: return p_chr_compare_na_equal(p_x, i, p_y, j); + case VCTRS_TYPE_raw: return p_raw_compare_na_equal(p_x, i, p_y, j); + case VCTRS_TYPE_list: return p_list_compare_na_equal(p_x, i, p_y, j); default: stop_unimplemented_vctrs_type("p_compare_na_equal", type); } } @@ -266,14 +266,14 @@ int p_compare_na_propagate(const void* p_x, r_ssize j, const enum vctrs_type type) { switch (type) { - case vctrs_type_null: return p_nil_compare_na_propagate(p_x, i, p_y, j); - case vctrs_type_logical: return p_lgl_compare_na_propagate(p_x, i, p_y, j); - case vctrs_type_integer: return p_int_compare_na_propagate(p_x, i, p_y, j); - case vctrs_type_double: return p_dbl_compare_na_propagate(p_x, i, p_y, j); - case vctrs_type_complex: return p_cpl_compare_na_propagate(p_x, i, p_y, j); - case vctrs_type_character: return p_chr_compare_na_propagate(p_x, i, p_y, j); - case vctrs_type_raw: return p_raw_compare_na_propagate(p_x, i, p_y, j); - case vctrs_type_list: return p_list_compare_na_propagate(p_x, i, p_y, j); + case VCTRS_TYPE_null: return p_nil_compare_na_propagate(p_x, i, p_y, j); + case VCTRS_TYPE_logical: return p_lgl_compare_na_propagate(p_x, i, p_y, j); + case VCTRS_TYPE_integer: return p_int_compare_na_propagate(p_x, i, p_y, j); + case VCTRS_TYPE_double: return p_dbl_compare_na_propagate(p_x, i, p_y, j); + case VCTRS_TYPE_complex: return p_cpl_compare_na_propagate(p_x, i, p_y, j); + case VCTRS_TYPE_character: return p_chr_compare_na_propagate(p_x, i, p_y, j); + case VCTRS_TYPE_raw: return p_raw_compare_na_propagate(p_x, i, p_y, j); + case VCTRS_TYPE_list: return p_list_compare_na_propagate(p_x, i, p_y, j); default: stop_unimplemented_vctrs_type("p_compare_na_propagate", type); } } diff --git a/src/complete.c b/src/complete.c index a01b25549..1723f0c21 100644 --- a/src/complete.c +++ b/src/complete.c @@ -81,15 +81,15 @@ static inline void df_detect_complete(SEXP x, R_len_t size, int* p_out); static inline void vec_detect_complete_switch(SEXP x, R_len_t size, int* p_out) { switch (vec_proxy_typeof(x)) { - case vctrs_type_logical: lgl_detect_complete(x, size, p_out); break; - case vctrs_type_integer: int_detect_complete(x, size, p_out); break; - case vctrs_type_double: dbl_detect_complete(x, size, p_out); break; - case vctrs_type_complex: cpl_detect_complete(x, size, p_out); break; - case vctrs_type_character: chr_detect_complete(x, size, p_out); break; - case vctrs_type_raw: raw_detect_complete(x, size, p_out); break; - case vctrs_type_list: list_detect_complete(x, size, p_out); break; - case vctrs_type_dataframe: df_detect_complete(x, size, p_out); break; - case vctrs_type_scalar: r_stop_internal("Can't detect missing values in scalars."); + case VCTRS_TYPE_logical: lgl_detect_complete(x, size, p_out); break; + case VCTRS_TYPE_integer: int_detect_complete(x, size, p_out); break; + case VCTRS_TYPE_double: dbl_detect_complete(x, size, p_out); break; + case VCTRS_TYPE_complex: cpl_detect_complete(x, size, p_out); break; + case VCTRS_TYPE_character: chr_detect_complete(x, size, p_out); break; + case VCTRS_TYPE_raw: raw_detect_complete(x, size, p_out); break; + case VCTRS_TYPE_list: list_detect_complete(x, size, p_out); break; + case VCTRS_TYPE_dataframe: df_detect_complete(x, size, p_out); break; + case VCTRS_TYPE_scalar: r_stop_internal("Can't detect missing values in scalars."); default: stop_unimplemented_vctrs_type("vec_detect_complete", vec_proxy_typeof(x)); } } diff --git a/src/equal.c b/src/equal.c index 66e6175b6..0ddd0de6e 100644 --- a/src/equal.c +++ b/src/equal.c @@ -41,15 +41,15 @@ SEXP vec_equal(SEXP x, SEXP y, bool na_equal) { SEXP out; switch (type) { - case vctrs_type_logical: out = lgl_equal(x_proxy, y_proxy, size, na_equal); break; - case vctrs_type_integer: out = int_equal(x_proxy, y_proxy, size, na_equal); break; - case vctrs_type_double: out = dbl_equal(x_proxy, y_proxy, size, na_equal); break; - case vctrs_type_complex: out = cpl_equal(x_proxy, y_proxy, size, na_equal); break; - case vctrs_type_character: out = chr_equal(x_proxy, y_proxy, size, na_equal); break; - case vctrs_type_raw: out = raw_equal(x_proxy, y_proxy, size, na_equal); break; - case vctrs_type_list: out = list_equal(x_proxy, y_proxy, size, na_equal); break; - case vctrs_type_dataframe: out = df_equal(x_proxy, y_proxy, size, na_equal); break; - case vctrs_type_scalar: Rf_errorcall(R_NilValue, "Can't compare scalars with `vec_equal()`."); + case VCTRS_TYPE_logical: out = lgl_equal(x_proxy, y_proxy, size, na_equal); break; + case VCTRS_TYPE_integer: out = int_equal(x_proxy, y_proxy, size, na_equal); break; + case VCTRS_TYPE_double: out = dbl_equal(x_proxy, y_proxy, size, na_equal); break; + case VCTRS_TYPE_complex: out = cpl_equal(x_proxy, y_proxy, size, na_equal); break; + case VCTRS_TYPE_character: out = chr_equal(x_proxy, y_proxy, size, na_equal); break; + case VCTRS_TYPE_raw: out = raw_equal(x_proxy, y_proxy, size, na_equal); break; + case VCTRS_TYPE_list: out = list_equal(x_proxy, y_proxy, size, na_equal); break; + case VCTRS_TYPE_dataframe: out = df_equal(x_proxy, y_proxy, size, na_equal); break; + case VCTRS_TYPE_scalar: Rf_errorcall(R_NilValue, "Can't compare scalars with `vec_equal()`."); default: stop_unimplemented_vctrs_type("vec_equal", type); } @@ -200,15 +200,15 @@ void vec_equal_col_na_equal(SEXP x, int* p_out, struct df_short_circuit_info* p_info) { switch (vec_proxy_typeof(x)) { - case vctrs_type_logical: EQUAL_COL(int, LOGICAL_RO, lgl_equal_na_equal); break; - case vctrs_type_integer: EQUAL_COL(int, INTEGER_RO, int_equal_na_equal); break; - case vctrs_type_double: EQUAL_COL(double, REAL_RO, dbl_equal_na_equal); break; - case vctrs_type_complex: EQUAL_COL(Rcomplex, COMPLEX_RO, cpl_equal_na_equal); break; - case vctrs_type_character: EQUAL_COL(SEXP, STRING_PTR_RO, chr_equal_na_equal); break; - case vctrs_type_raw: EQUAL_COL(Rbyte, RAW_RO, raw_equal_na_equal); break; - case vctrs_type_list: EQUAL_COL(SEXP, VECTOR_PTR_RO, list_equal_na_equal); break; - case vctrs_type_dataframe: r_stop_internal("Data frame columns should be flattened already."); - case vctrs_type_scalar: Rf_errorcall(R_NilValue, "Can't compare scalars with `vec_equal()`."); + case VCTRS_TYPE_logical: EQUAL_COL(int, LOGICAL_RO, lgl_equal_na_equal); break; + case VCTRS_TYPE_integer: EQUAL_COL(int, INTEGER_RO, int_equal_na_equal); break; + case VCTRS_TYPE_double: EQUAL_COL(double, REAL_RO, dbl_equal_na_equal); break; + case VCTRS_TYPE_complex: EQUAL_COL(Rcomplex, COMPLEX_RO, cpl_equal_na_equal); break; + case VCTRS_TYPE_character: EQUAL_COL(SEXP, STRING_PTR_RO, chr_equal_na_equal); break; + case VCTRS_TYPE_raw: EQUAL_COL(Rbyte, RAW_RO, raw_equal_na_equal); break; + case VCTRS_TYPE_list: EQUAL_COL(SEXP, VECTOR_PTR_RO, list_equal_na_equal); break; + case VCTRS_TYPE_dataframe: r_stop_internal("Data frame columns should be flattened already."); + case VCTRS_TYPE_scalar: Rf_errorcall(R_NilValue, "Can't compare scalars with `vec_equal()`."); default: stop_unimplemented_vctrs_type("vec_equal", vec_proxy_typeof(x)); } } @@ -219,15 +219,15 @@ void vec_equal_col_na_propagate(SEXP x, int* p_out, struct df_short_circuit_info* p_info) { switch (vec_proxy_typeof(x)) { - case vctrs_type_logical: EQUAL_COL(int, LOGICAL_RO, lgl_equal_na_propagate); break; - case vctrs_type_integer: EQUAL_COL(int, INTEGER_RO, int_equal_na_propagate); break; - case vctrs_type_double: EQUAL_COL(double, REAL_RO, dbl_equal_na_propagate); break; - case vctrs_type_complex: EQUAL_COL(Rcomplex, COMPLEX_RO, cpl_equal_na_propagate); break; - case vctrs_type_character: EQUAL_COL(SEXP, STRING_PTR_RO, chr_equal_na_propagate); break; - case vctrs_type_raw: EQUAL_COL(Rbyte, RAW_RO, raw_equal_na_propagate); break; - case vctrs_type_list: EQUAL_COL(SEXP, VECTOR_PTR_RO, list_equal_na_propagate); break; - case vctrs_type_dataframe: r_stop_internal("Data frame columns should be flattened already."); - case vctrs_type_scalar: Rf_errorcall(R_NilValue, "Can't compare scalars with `vec_equal()`."); + case VCTRS_TYPE_logical: EQUAL_COL(int, LOGICAL_RO, lgl_equal_na_propagate); break; + case VCTRS_TYPE_integer: EQUAL_COL(int, INTEGER_RO, int_equal_na_propagate); break; + case VCTRS_TYPE_double: EQUAL_COL(double, REAL_RO, dbl_equal_na_propagate); break; + case VCTRS_TYPE_complex: EQUAL_COL(Rcomplex, COMPLEX_RO, cpl_equal_na_propagate); break; + case VCTRS_TYPE_character: EQUAL_COL(SEXP, STRING_PTR_RO, chr_equal_na_propagate); break; + case VCTRS_TYPE_raw: EQUAL_COL(Rbyte, RAW_RO, raw_equal_na_propagate); break; + case VCTRS_TYPE_list: EQUAL_COL(SEXP, VECTOR_PTR_RO, list_equal_na_propagate); break; + case VCTRS_TYPE_dataframe: r_stop_internal("Data frame columns should be flattened already."); + case VCTRS_TYPE_scalar: Rf_errorcall(R_NilValue, "Can't compare scalars with `vec_equal()`."); default: stop_unimplemented_vctrs_type("vec_equal", vec_proxy_typeof(x)); } } diff --git a/src/equal.h b/src/equal.h index 55e482ab5..38ac82f2e 100644 --- a/src/equal.h +++ b/src/equal.h @@ -81,13 +81,13 @@ static inline bool p_equal_na_equal(const void* p_x, r_ssize j, const enum vctrs_type type) { switch (type) { - case vctrs_type_logical: return p_lgl_equal_na_equal(p_x, i, p_y, j); - case vctrs_type_integer: return p_int_equal_na_equal(p_x, i, p_y, j); - case vctrs_type_double: return p_dbl_equal_na_equal(p_x, i, p_y, j); - case vctrs_type_complex: return p_cpl_equal_na_equal(p_x, i, p_y, j); - case vctrs_type_character: return p_chr_equal_na_equal(p_x, i, p_y, j); - case vctrs_type_raw: return p_raw_equal_na_equal(p_x, i, p_y, j); - case vctrs_type_list: return p_list_equal_na_equal(p_x, i, p_y, j); + case VCTRS_TYPE_logical: return p_lgl_equal_na_equal(p_x, i, p_y, j); + case VCTRS_TYPE_integer: return p_int_equal_na_equal(p_x, i, p_y, j); + case VCTRS_TYPE_double: return p_dbl_equal_na_equal(p_x, i, p_y, j); + case VCTRS_TYPE_complex: return p_cpl_equal_na_equal(p_x, i, p_y, j); + case VCTRS_TYPE_character: return p_chr_equal_na_equal(p_x, i, p_y, j); + case VCTRS_TYPE_raw: return p_raw_equal_na_equal(p_x, i, p_y, j); + case VCTRS_TYPE_list: return p_list_equal_na_equal(p_x, i, p_y, j); default: stop_unimplemented_vctrs_type("p_equal_na_equal", type); } } @@ -185,13 +185,13 @@ static inline bool p_equal_na_propagate(const void* p_x, r_ssize j, const enum vctrs_type type) { switch (type) { - case vctrs_type_logical: return p_lgl_equal_na_propagate(p_x, i, p_y, j); - case vctrs_type_integer: return p_int_equal_na_propagate(p_x, i, p_y, j); - case vctrs_type_double: return p_dbl_equal_na_propagate(p_x, i, p_y, j); - case vctrs_type_complex: return p_cpl_equal_na_propagate(p_x, i, p_y, j); - case vctrs_type_character: return p_chr_equal_na_propagate(p_x, i, p_y, j); - case vctrs_type_raw: return p_raw_equal_na_propagate(p_x, i, p_y, j); - case vctrs_type_list: return p_list_equal_na_propagate(p_x, i, p_y, j); + case VCTRS_TYPE_logical: return p_lgl_equal_na_propagate(p_x, i, p_y, j); + case VCTRS_TYPE_integer: return p_int_equal_na_propagate(p_x, i, p_y, j); + case VCTRS_TYPE_double: return p_dbl_equal_na_propagate(p_x, i, p_y, j); + case VCTRS_TYPE_complex: return p_cpl_equal_na_propagate(p_x, i, p_y, j); + case VCTRS_TYPE_character: return p_chr_equal_na_propagate(p_x, i, p_y, j); + case VCTRS_TYPE_raw: return p_raw_equal_na_propagate(p_x, i, p_y, j); + case VCTRS_TYPE_list: return p_list_equal_na_propagate(p_x, i, p_y, j); default: stop_unimplemented_vctrs_type("p_equal_na_propagate", type); } } diff --git a/src/hash.c b/src/hash.c index ac809722d..f57de1b5c 100644 --- a/src/hash.c +++ b/src/hash.c @@ -252,26 +252,26 @@ void hash_fill(uint32_t* p, R_len_t size, SEXP x, bool na_equal) { if (na_equal) { switch (vec_proxy_typeof(x)) { - case vctrs_type_logical: lgl_hash_fill_na_equal(p, size, x); return; - case vctrs_type_integer: int_hash_fill_na_equal(p, size, x); return; - case vctrs_type_double: dbl_hash_fill_na_equal(p, size, x); return; - case vctrs_type_complex: cpl_hash_fill_na_equal(p, size, x); return; - case vctrs_type_character: chr_hash_fill_na_equal(p, size, x); return; - case vctrs_type_raw: raw_hash_fill_na_equal(p, size, x); return; - case vctrs_type_list: list_hash_fill_na_equal(p, size, x); return; - case vctrs_type_dataframe: df_hash_fill(p, size, x, true); return; + case VCTRS_TYPE_logical: lgl_hash_fill_na_equal(p, size, x); return; + case VCTRS_TYPE_integer: int_hash_fill_na_equal(p, size, x); return; + case VCTRS_TYPE_double: dbl_hash_fill_na_equal(p, size, x); return; + case VCTRS_TYPE_complex: cpl_hash_fill_na_equal(p, size, x); return; + case VCTRS_TYPE_character: chr_hash_fill_na_equal(p, size, x); return; + case VCTRS_TYPE_raw: raw_hash_fill_na_equal(p, size, x); return; + case VCTRS_TYPE_list: list_hash_fill_na_equal(p, size, x); return; + case VCTRS_TYPE_dataframe: df_hash_fill(p, size, x, true); return; default: break; } } else { switch (vec_proxy_typeof(x)) { - case vctrs_type_logical: lgl_hash_fill_na_propagate(p, size, x); return; - case vctrs_type_integer: int_hash_fill_na_propagate(p, size, x); return; - case vctrs_type_double: dbl_hash_fill_na_propagate(p, size, x); return; - case vctrs_type_complex: cpl_hash_fill_na_propagate(p, size, x); return; - case vctrs_type_character: chr_hash_fill_na_propagate(p, size, x); return; - case vctrs_type_raw: raw_hash_fill_na_propagate(p, size, x); return; - case vctrs_type_list: list_hash_fill_na_propagate(p, size, x); return; - case vctrs_type_dataframe: df_hash_fill(p, size, x, false); return; + case VCTRS_TYPE_logical: lgl_hash_fill_na_propagate(p, size, x); return; + case VCTRS_TYPE_integer: int_hash_fill_na_propagate(p, size, x); return; + case VCTRS_TYPE_double: dbl_hash_fill_na_propagate(p, size, x); return; + case VCTRS_TYPE_complex: cpl_hash_fill_na_propagate(p, size, x); return; + case VCTRS_TYPE_character: chr_hash_fill_na_propagate(p, size, x); return; + case VCTRS_TYPE_raw: raw_hash_fill_na_propagate(p, size, x); return; + case VCTRS_TYPE_list: list_hash_fill_na_propagate(p, size, x); return; + case VCTRS_TYPE_dataframe: df_hash_fill(p, size, x, false); return; default: break; } } diff --git a/src/match-compare.h b/src/match-compare.h index 2db75c4f6..bedb1869f 100644 --- a/src/match-compare.h +++ b/src/match-compare.h @@ -118,11 +118,11 @@ int p_order_compare_na_equal(const void* p_x, bool nan_distinct, const enum vctrs_type type) { switch (type) { - case vctrs_type_logical: return p_lgl_order_compare_na_equal(p_x, i, p_y, j, nan_distinct); - case vctrs_type_integer: return p_int_order_compare_na_equal(p_x, i, p_y, j, nan_distinct); - case vctrs_type_double: return p_dbl_order_compare_na_equal(p_x, i, p_y, j, nan_distinct); - case vctrs_type_complex: return p_cpl_order_compare_na_equal(p_x, i, p_y, j, nan_distinct); - case vctrs_type_character: return p_chr_order_compare_na_equal(p_x, i, p_y, j, nan_distinct); + case VCTRS_TYPE_logical: return p_lgl_order_compare_na_equal(p_x, i, p_y, j, nan_distinct); + case VCTRS_TYPE_integer: return p_int_order_compare_na_equal(p_x, i, p_y, j, nan_distinct); + case VCTRS_TYPE_double: return p_dbl_order_compare_na_equal(p_x, i, p_y, j, nan_distinct); + case VCTRS_TYPE_complex: return p_cpl_order_compare_na_equal(p_x, i, p_y, j, nan_distinct); + case VCTRS_TYPE_character: return p_chr_order_compare_na_equal(p_x, i, p_y, j, nan_distinct); default: stop_unimplemented_vctrs_type("p_order_compare_na_equal", type); } } diff --git a/src/match-joint.c b/src/match-joint.c index bfee5cb79..d0c007bc8 100644 --- a/src/match-joint.c +++ b/src/match-joint.c @@ -157,12 +157,12 @@ r_obj* vec_joint_xtfrm(r_obj* x, // Now that we have the ordering of both vectors, // it is just a matter of merging two sorted arrays switch (type) { - case vctrs_type_logical: VEC_JOINT_XTFRM_LOOP(p_lgl_order_compare_na_equal); break; - case vctrs_type_integer: VEC_JOINT_XTFRM_LOOP(p_int_order_compare_na_equal); break; - case vctrs_type_double: VEC_JOINT_XTFRM_LOOP(p_dbl_order_compare_na_equal); break; - case vctrs_type_complex: VEC_JOINT_XTFRM_LOOP(p_cpl_order_compare_na_equal); break; - case vctrs_type_character: VEC_JOINT_XTFRM_LOOP(p_chr_order_compare_na_equal); break; - case vctrs_type_dataframe: VEC_JOINT_XTFRM_LOOP(p_df_order_compare_na_equal); break; + case VCTRS_TYPE_logical: VEC_JOINT_XTFRM_LOOP(p_lgl_order_compare_na_equal); break; + case VCTRS_TYPE_integer: VEC_JOINT_XTFRM_LOOP(p_int_order_compare_na_equal); break; + case VCTRS_TYPE_double: VEC_JOINT_XTFRM_LOOP(p_dbl_order_compare_na_equal); break; + case VCTRS_TYPE_complex: VEC_JOINT_XTFRM_LOOP(p_cpl_order_compare_na_equal); break; + case VCTRS_TYPE_character: VEC_JOINT_XTFRM_LOOP(p_chr_order_compare_na_equal); break; + case VCTRS_TYPE_dataframe: VEC_JOINT_XTFRM_LOOP(p_df_order_compare_na_equal); break; default: stop_unimplemented_vctrs_type("vec_joint_xtfrm", type); } @@ -240,26 +240,26 @@ r_obj* vec_joint_proxy_order(r_obj* x, r_obj* y) { } switch (vec_typeof(x)) { - case vctrs_type_unspecified: - case vctrs_type_logical: - case vctrs_type_integer: - case vctrs_type_double: - case vctrs_type_complex: - case vctrs_type_character: - case vctrs_type_raw: { + case VCTRS_TYPE_unspecified: + case VCTRS_TYPE_logical: + case VCTRS_TYPE_integer: + case VCTRS_TYPE_double: + case VCTRS_TYPE_complex: + case VCTRS_TYPE_character: + case VCTRS_TYPE_raw: { return vec_joint_proxy_order_independent(x, y); } - case vctrs_type_list: { + case VCTRS_TYPE_list: { return vec_joint_proxy_order_dependent(x, y); } - case vctrs_type_dataframe: { + case VCTRS_TYPE_dataframe: { return df_joint_proxy_order(x, y); } - case vctrs_type_s3: { + case VCTRS_TYPE_s3: { return vec_joint_proxy_order_s3(x, y); } - case vctrs_type_null: - case vctrs_type_scalar: { + case VCTRS_TYPE_null: + case VCTRS_TYPE_scalar: { stop_unimplemented_vctrs_type("vec_joint_proxy_order", vec_typeof(x)); } } diff --git a/src/match.c b/src/match.c index a346a9e22..9696109e3 100644 --- a/src/match.c +++ b/src/match.c @@ -362,19 +362,19 @@ r_obj* df_locate_matches(r_obj* needles, v_loc_filter_match_o_haystack = r_int_begin(loc_filter_match_o_haystack); } - struct poly_vec* p_poly_needles = new_poly_vec(needles, vctrs_type_dataframe); + struct poly_vec* p_poly_needles = new_poly_vec(needles, VCTRS_TYPE_dataframe); PROTECT_POLY_VEC(p_poly_needles, &n_prot); const struct poly_df_data* p_needles = (const struct poly_df_data*) p_poly_needles->p_vec; - struct poly_vec* p_poly_haystack = new_poly_vec(haystack, vctrs_type_dataframe); + struct poly_vec* p_poly_haystack = new_poly_vec(haystack, VCTRS_TYPE_dataframe); PROTECT_POLY_VEC(p_poly_haystack, &n_prot); const struct poly_df_data* p_haystack = (const struct poly_df_data*) p_poly_haystack->p_vec; - const struct poly_vec* p_poly_needles_complete = new_poly_vec(needles_complete, vctrs_type_dataframe); + const struct poly_vec* p_poly_needles_complete = new_poly_vec(needles_complete, VCTRS_TYPE_dataframe); PROTECT_POLY_VEC(p_poly_needles_complete, &n_prot); const struct poly_df_data* p_needles_complete = (const struct poly_df_data*) p_poly_needles_complete->p_vec; - struct poly_vec* p_poly_haystack_complete = new_poly_vec(haystack_complete, vctrs_type_dataframe); + struct poly_vec* p_poly_haystack_complete = new_poly_vec(haystack_complete, VCTRS_TYPE_dataframe); PROTECT_POLY_VEC(p_poly_haystack_complete, &n_prot); const struct poly_df_data* p_haystack_complete = (const struct poly_df_data*) p_poly_haystack_complete->p_vec; @@ -2218,7 +2218,7 @@ r_obj* compute_nesting_container_ids(r_obj* x, struct r_dyn_array* p_prev_rows = r_new_dyn_vector(R_TYPE_integer, 10000); KEEP_N(p_prev_rows->shelter, &n_prot); - struct poly_vec* p_poly_x = new_poly_vec(x, vctrs_type_dataframe); + struct poly_vec* p_poly_x = new_poly_vec(x, VCTRS_TYPE_dataframe); PROTECT_POLY_VEC(p_poly_x, &n_prot); const void* v_x = p_poly_x->p_vec; diff --git a/src/missing.c b/src/missing.c index 9d87a0244..a97edd041 100644 --- a/src/missing.c +++ b/src/missing.c @@ -20,16 +20,16 @@ r_obj* proxy_equal_na(r_obj* proxy) { const enum vctrs_type type = vec_proxy_typeof(proxy); switch (type) { - case vctrs_type_logical: return lgl_equal_na(proxy); - case vctrs_type_integer: return int_equal_na(proxy); - case vctrs_type_double: return dbl_equal_na(proxy); - case vctrs_type_complex: return cpl_equal_na(proxy); - case vctrs_type_raw: return raw_equal_na(proxy); - case vctrs_type_character: return chr_equal_na(proxy); - case vctrs_type_list: return list_equal_na(proxy); - case vctrs_type_dataframe: return df_equal_na(proxy); - case vctrs_type_null: return vctrs_shared_empty_lgl; - case vctrs_type_scalar: stop_scalar_type(proxy, vec_args.empty, r_lazy_null); + case VCTRS_TYPE_logical: return lgl_equal_na(proxy); + case VCTRS_TYPE_integer: return int_equal_na(proxy); + case VCTRS_TYPE_double: return dbl_equal_na(proxy); + case VCTRS_TYPE_complex: return cpl_equal_na(proxy); + case VCTRS_TYPE_raw: return raw_equal_na(proxy); + case VCTRS_TYPE_character: return chr_equal_na(proxy); + case VCTRS_TYPE_list: return list_equal_na(proxy); + case VCTRS_TYPE_dataframe: return df_equal_na(proxy); + case VCTRS_TYPE_null: return vctrs_shared_empty_lgl; + case VCTRS_TYPE_scalar: stop_scalar_type(proxy, vec_args.empty, r_lazy_null); default: stop_unimplemented_vctrs_type("vec_equal_na", type); } @@ -139,16 +139,16 @@ r_ssize col_equal_na(r_obj* x, const enum vctrs_type type = vec_proxy_typeof(x); switch (type) { - case vctrs_type_logical: return lgl_col_equal_na(x, v_loc, loc_size); - case vctrs_type_integer: return int_col_equal_na(x, v_loc, loc_size); - case vctrs_type_double: return dbl_col_equal_na(x, v_loc, loc_size); - case vctrs_type_complex: return cpl_col_equal_na(x, v_loc, loc_size); - case vctrs_type_raw: return raw_col_equal_na(x, v_loc, loc_size); - case vctrs_type_character: return chr_col_equal_na(x, v_loc, loc_size); - case vctrs_type_list: return list_col_equal_na(x, v_loc, loc_size); - case vctrs_type_dataframe: r_stop_internal("Data frame columns should have been flattened by now."); - case vctrs_type_null: r_abort("Unexpected `NULL` column found in a data frame."); - case vctrs_type_scalar: stop_scalar_type(x, vec_args.empty, r_lazy_null); + case VCTRS_TYPE_logical: return lgl_col_equal_na(x, v_loc, loc_size); + case VCTRS_TYPE_integer: return int_col_equal_na(x, v_loc, loc_size); + case VCTRS_TYPE_double: return dbl_col_equal_na(x, v_loc, loc_size); + case VCTRS_TYPE_complex: return cpl_col_equal_na(x, v_loc, loc_size); + case VCTRS_TYPE_raw: return raw_col_equal_na(x, v_loc, loc_size); + case VCTRS_TYPE_character: return chr_col_equal_na(x, v_loc, loc_size); + case VCTRS_TYPE_list: return list_col_equal_na(x, v_loc, loc_size); + case VCTRS_TYPE_dataframe: r_stop_internal("Data frame columns should have been flattened by now."); + case VCTRS_TYPE_null: r_abort("Unexpected `NULL` column found in a data frame."); + case VCTRS_TYPE_scalar: stop_scalar_type(x, vec_args.empty, r_lazy_null); default: stop_unimplemented_vctrs_type("vec_equal_na", type); } } @@ -280,16 +280,16 @@ r_ssize proxy_first_missing(r_obj* proxy) { const enum vctrs_type type = vec_proxy_typeof(proxy); switch (type) { - case vctrs_type_logical: return lgl_first_missing(proxy); - case vctrs_type_integer: return int_first_missing(proxy); - case vctrs_type_double: return dbl_first_missing(proxy); - case vctrs_type_complex: return cpl_first_missing(proxy); - case vctrs_type_raw: return raw_first_missing(proxy); - case vctrs_type_character: return chr_first_missing(proxy); - case vctrs_type_list: return list_first_missing(proxy); - case vctrs_type_dataframe: return df_first_missing(proxy); - case vctrs_type_null: return 0; - case vctrs_type_scalar: stop_scalar_type(proxy, vec_args.empty, r_lazy_null); + case VCTRS_TYPE_logical: return lgl_first_missing(proxy); + case VCTRS_TYPE_integer: return int_first_missing(proxy); + case VCTRS_TYPE_double: return dbl_first_missing(proxy); + case VCTRS_TYPE_complex: return cpl_first_missing(proxy); + case VCTRS_TYPE_raw: return raw_first_missing(proxy); + case VCTRS_TYPE_character: return chr_first_missing(proxy); + case VCTRS_TYPE_list: return list_first_missing(proxy); + case VCTRS_TYPE_dataframe: return df_first_missing(proxy); + case VCTRS_TYPE_null: return 0; + case VCTRS_TYPE_scalar: stop_scalar_type(proxy, vec_args.empty, r_lazy_null); default: stop_unimplemented_vctrs_type("vec_first_missing", type); } @@ -368,9 +368,9 @@ r_ssize df_first_missing(r_obj* x) { int n_prot = 0; - const poly_unary_bool_fn_ptr fn_is_missing = new_poly_p_is_missing(vctrs_type_dataframe); + const poly_unary_bool_fn_ptr fn_is_missing = new_poly_p_is_missing(VCTRS_TYPE_dataframe); - struct poly_vec* p_poly_x = new_poly_vec(x, vctrs_type_dataframe); + struct poly_vec* p_poly_x = new_poly_vec(x, VCTRS_TYPE_dataframe); PROTECT_POLY_VEC(p_poly_x, &n_prot); const void* v_x = p_poly_x->p_vec; diff --git a/src/missing.h b/src/missing.h index 865449995..11c7164f0 100644 --- a/src/missing.h +++ b/src/missing.h @@ -87,13 +87,13 @@ bool p_is_missing(const void* p_x, r_ssize i, const enum vctrs_type type) { switch (type) { - case vctrs_type_logical: return p_lgl_is_missing(p_x, i); - case vctrs_type_integer: return p_int_is_missing(p_x, i); - case vctrs_type_double: return p_dbl_is_missing(p_x, i); - case vctrs_type_complex: return p_cpl_is_missing(p_x, i); - case vctrs_type_character: return p_chr_is_missing(p_x, i); - case vctrs_type_raw: return p_raw_is_missing(p_x, i); - case vctrs_type_list: return p_list_is_missing(p_x, i); + case VCTRS_TYPE_logical: return p_lgl_is_missing(p_x, i); + case VCTRS_TYPE_integer: return p_int_is_missing(p_x, i); + case VCTRS_TYPE_double: return p_dbl_is_missing(p_x, i); + case VCTRS_TYPE_complex: return p_cpl_is_missing(p_x, i); + case VCTRS_TYPE_character: return p_chr_is_missing(p_x, i); + case VCTRS_TYPE_raw: return p_raw_is_missing(p_x, i); + case VCTRS_TYPE_list: return p_list_is_missing(p_x, i); default: stop_unimplemented_vctrs_type("p_is_missing", type); } } diff --git a/src/order-collate.c b/src/order-collate.c index 1884cf603..8ae333a9f 100644 --- a/src/order-collate.c +++ b/src/order-collate.c @@ -28,8 +28,8 @@ SEXP proxy_apply_chr_proxy_collate(SEXP proxy, SEXP chr_proxy_collate) { SEXP out; switch (vec_proxy_typeof(proxy)) { - case vctrs_type_character: out = chr_apply(proxy, chr_proxy_collate); break; - case vctrs_type_dataframe: out = df_apply(proxy, chr_proxy_collate); break; + case VCTRS_TYPE_character: out = chr_apply(proxy, chr_proxy_collate); break; + case VCTRS_TYPE_dataframe: out = df_apply(proxy, chr_proxy_collate); break; default: out = proxy; } @@ -50,7 +50,7 @@ SEXP chr_apply(SEXP x, SEXP chr_proxy_collate) { SEXP out = PROTECT(Rf_eval(call, mask)); - if (vec_typeof(out) != vctrs_type_character) { + if (vec_typeof(out) != VCTRS_TYPE_character) { Rf_errorcall( R_NilValue, "`chr_proxy_collate` must return a character vector." @@ -84,7 +84,7 @@ SEXP df_apply(SEXP x, SEXP chr_proxy_collate) { for (; i < n_cols; ++i) { SEXP col = v_x[i]; - if (vec_proxy_typeof(col) == vctrs_type_character) { + if (vec_proxy_typeof(col) == VCTRS_TYPE_character) { break; } } @@ -99,7 +99,7 @@ SEXP df_apply(SEXP x, SEXP chr_proxy_collate) { for (; i < n_cols; ++i) { SEXP col = v_x[i]; - if (vec_proxy_typeof(col) != vctrs_type_character) { + if (vec_proxy_typeof(col) != VCTRS_TYPE_character) { continue; } diff --git a/src/order.c b/src/order.c index b6eba7448..c87599fd6 100644 --- a/src/order.c +++ b/src/order.c @@ -532,7 +532,7 @@ void vec_order_switch(SEXP x, struct lazy_raw* p_lazy_counts, struct group_infos* p_group_infos, struct truelength_info* p_truelength_info) { - if (type == vctrs_type_dataframe) { + if (type == VCTRS_TYPE_dataframe) { df_order( x, decreasing, @@ -687,7 +687,7 @@ void vec_order_base_switch(SEXP x, struct group_infos* p_group_infos, struct truelength_info* p_truelength_info) { switch (type) { - case vctrs_type_integer: { + case VCTRS_TYPE_integer: { int_order( x, decreasing, @@ -704,7 +704,7 @@ void vec_order_base_switch(SEXP x, break; } - case vctrs_type_logical: { + case VCTRS_TYPE_logical: { lgl_order( x, decreasing, @@ -721,7 +721,7 @@ void vec_order_base_switch(SEXP x, break; } - case vctrs_type_double: { + case VCTRS_TYPE_double: { dbl_order( x, decreasing, @@ -739,7 +739,7 @@ void vec_order_base_switch(SEXP x, break; } - case vctrs_type_complex: { + case VCTRS_TYPE_complex: { cpl_order( x, decreasing, @@ -757,7 +757,7 @@ void vec_order_base_switch(SEXP x, break; } - case vctrs_type_character: { + case VCTRS_TYPE_character: { if (chr_ordered) { chr_order( x, @@ -792,7 +792,7 @@ void vec_order_base_switch(SEXP x, break; } - case vctrs_type_dataframe: { + case VCTRS_TYPE_dataframe: { Rf_errorcall(R_NilValue, "Internal error: Data frames should have been handled by now"); } default: { @@ -4033,13 +4033,13 @@ void df_order_internal(SEXP x, // If we are on the rerun pass, flip this back off so the // imaginary part is extracted below. - if (type == vctrs_type_complex) { + if (type == VCTRS_TYPE_complex) { rerun_complex = rerun_complex ? false : true; } // Pre-sort unique characters once for the whole column. // Don't sort uniques if computing appearance ordering. - if (chr_ordered && type == vctrs_type_character) { + if (chr_ordered && type == VCTRS_TYPE_character) { const SEXP* p_col = STRING_PTR_RO(col); chr_mark_sorted_uniques( @@ -4078,11 +4078,11 @@ void df_order_internal(SEXP x, // Extract current chunk and place into `x_chunk` in sequential order switch (type) { - case vctrs_type_integer: DF_ORDER_EXTRACT_CHUNK(INTEGER_RO, int); break; - case vctrs_type_logical: DF_ORDER_EXTRACT_CHUNK(LOGICAL_RO, int); break; - case vctrs_type_double: DF_ORDER_EXTRACT_CHUNK(REAL_RO, double); break; - case vctrs_type_character: DF_ORDER_EXTRACT_CHUNK(STRING_PTR_RO, SEXP); break; - case vctrs_type_complex: DF_ORDER_EXTRACT_CHUNK_CPL(); break; + case VCTRS_TYPE_integer: DF_ORDER_EXTRACT_CHUNK(INTEGER_RO, int); break; + case VCTRS_TYPE_logical: DF_ORDER_EXTRACT_CHUNK(LOGICAL_RO, int); break; + case VCTRS_TYPE_double: DF_ORDER_EXTRACT_CHUNK(REAL_RO, double); break; + case VCTRS_TYPE_character: DF_ORDER_EXTRACT_CHUNK(STRING_PTR_RO, SEXP); break; + case VCTRS_TYPE_complex: DF_ORDER_EXTRACT_CHUNK_CPL(); break; default: Rf_errorcall(R_NilValue, "Unknown data frame column type in `vec_order()`."); } @@ -4109,7 +4109,7 @@ void df_order_internal(SEXP x, // Reset TRUELENGTHs between columns if ordering character vectors. // When ordering by appearance, `chr_appearance_counting()` resets the // TRUELENGTHs between chunks. - if (chr_ordered && type == vctrs_type_character) { + if (chr_ordered && type == VCTRS_TYPE_character) { truelength_reset(p_truelength_info); } } @@ -4140,7 +4140,7 @@ void vec_order_chunk_switch(bool decreasing, struct group_infos* p_group_infos, struct truelength_info* p_truelength_info) { switch (type) { - case vctrs_type_integer: { + case VCTRS_TYPE_integer: { int_order_chunk( decreasing, na_last, @@ -4156,7 +4156,7 @@ void vec_order_chunk_switch(bool decreasing, break; } - case vctrs_type_logical: { + case VCTRS_TYPE_logical: { lgl_order_chunk( decreasing, na_last, @@ -4172,7 +4172,7 @@ void vec_order_chunk_switch(bool decreasing, break; } - case vctrs_type_double: { + case VCTRS_TYPE_double: { dbl_order_chunk( decreasing, na_last, @@ -4189,7 +4189,7 @@ void vec_order_chunk_switch(bool decreasing, break; } - case vctrs_type_complex: { + case VCTRS_TYPE_complex: { // Complex types are run in two passes, once over real then over imaginary dbl_order_chunk( decreasing, @@ -4207,7 +4207,7 @@ void vec_order_chunk_switch(bool decreasing, break; } - case vctrs_type_character: { + case VCTRS_TYPE_character: { if (chr_ordered) { chr_order_chunk( decreasing, @@ -4239,7 +4239,7 @@ void vec_order_chunk_switch(bool decreasing, break; } - case vctrs_type_dataframe: { + case VCTRS_TYPE_dataframe: { Rf_errorcall(R_NilValue, "Internal error: df-cols should have already been flattened."); break; } @@ -4263,18 +4263,18 @@ static inline size_t df_compute_n_bytes_lazy_raw(SEXP x); static inline size_t vec_compute_n_bytes_lazy_raw(SEXP x, const enum vctrs_type type) { switch (type) { - case vctrs_type_integer: - case vctrs_type_logical: + case VCTRS_TYPE_integer: + case VCTRS_TYPE_logical: return sizeof(int); - case vctrs_type_double: + case VCTRS_TYPE_double: return sizeof(double); - case vctrs_type_complex: + case VCTRS_TYPE_complex: // Complex types will be split into two double vectors return sizeof(double); - case vctrs_type_character: + case VCTRS_TYPE_character: // Auxiliary data will store SEXP and ints, so return the larger return sizeof(SEXP) > sizeof(int) ? sizeof(SEXP) : sizeof(int); - case vctrs_type_dataframe: + case VCTRS_TYPE_dataframe: return df_compute_n_bytes_lazy_raw(x); default: Rf_errorcall(R_NilValue, "This type is not supported by `vec_order()`."); @@ -4318,14 +4318,14 @@ static size_t df_compute_n_bytes_lazy_counts(SEXP x); static inline size_t vec_compute_n_bytes_lazy_counts(SEXP x, const enum vctrs_type type) { switch (type) { - case vctrs_type_integer: - case vctrs_type_logical: - case vctrs_type_character: + case VCTRS_TYPE_integer: + case VCTRS_TYPE_logical: + case VCTRS_TYPE_character: return INT_MAX_RADIX_PASS; - case vctrs_type_double: - case vctrs_type_complex: + case VCTRS_TYPE_double: + case VCTRS_TYPE_complex: return DBL_MAX_RADIX_PASS; - case vctrs_type_dataframe: + case VCTRS_TYPE_dataframe: return df_compute_n_bytes_lazy_counts(x); default: Rf_errorcall(R_NilValue, "This type is not supported by `vec_order()`."); diff --git a/src/poly-op.c b/src/poly-op.c index 88b7ab14e..264dc4952 100644 --- a/src/poly-op.c +++ b/src/poly-op.c @@ -7,15 +7,15 @@ static int p_df_equal_na_equal(const void* x, r_ssize i, const void* y, r_ssize // [[ include("poly-op.h") ]] poly_binary_int_fn_ptr new_poly_p_equal_na_equal(enum vctrs_type type) { switch (type) { - case vctrs_type_null: return p_nil_equal_na_equal; - case vctrs_type_logical: return p_lgl_equal_na_equal; - case vctrs_type_integer: return p_int_equal_na_equal; - case vctrs_type_double: return p_dbl_equal_na_equal; - case vctrs_type_complex: return p_cpl_equal_na_equal; - case vctrs_type_character: return p_chr_equal_na_equal; - case vctrs_type_raw: return p_raw_equal_na_equal; - case vctrs_type_list: return p_list_equal_na_equal; - case vctrs_type_dataframe: return p_df_equal_na_equal; + case VCTRS_TYPE_null: return p_nil_equal_na_equal; + case VCTRS_TYPE_logical: return p_lgl_equal_na_equal; + case VCTRS_TYPE_integer: return p_int_equal_na_equal; + case VCTRS_TYPE_double: return p_dbl_equal_na_equal; + case VCTRS_TYPE_complex: return p_cpl_equal_na_equal; + case VCTRS_TYPE_character: return p_chr_equal_na_equal; + case VCTRS_TYPE_raw: return p_raw_equal_na_equal; + case VCTRS_TYPE_list: return p_list_equal_na_equal; + case VCTRS_TYPE_dataframe: return p_df_equal_na_equal; default: stop_unimplemented_vctrs_type("new_poly_p_equal_na_equal", type); } } @@ -51,15 +51,15 @@ static int p_df_compare_na_equal(const void* x, r_ssize i, const void* y, r_ssiz // [[ include("poly-op.h") ]] poly_binary_int_fn_ptr new_poly_p_compare_na_equal(enum vctrs_type type) { switch (type) { - case vctrs_type_null: return p_nil_compare_na_equal; - case vctrs_type_logical: return p_lgl_compare_na_equal; - case vctrs_type_integer: return p_int_compare_na_equal; - case vctrs_type_double: return p_dbl_compare_na_equal; - case vctrs_type_complex: return p_cpl_compare_na_equal; - case vctrs_type_character: return p_chr_compare_na_equal; - case vctrs_type_raw: return p_raw_compare_na_equal; - case vctrs_type_list: return p_list_compare_na_equal; - case vctrs_type_dataframe: return p_df_compare_na_equal; + case VCTRS_TYPE_null: return p_nil_compare_na_equal; + case VCTRS_TYPE_logical: return p_lgl_compare_na_equal; + case VCTRS_TYPE_integer: return p_int_compare_na_equal; + case VCTRS_TYPE_double: return p_dbl_compare_na_equal; + case VCTRS_TYPE_complex: return p_cpl_compare_na_equal; + case VCTRS_TYPE_character: return p_chr_compare_na_equal; + case VCTRS_TYPE_raw: return p_raw_compare_na_equal; + case VCTRS_TYPE_list: return p_list_compare_na_equal; + case VCTRS_TYPE_dataframe: return p_df_compare_na_equal; default: stop_unimplemented_vctrs_type("new_poly_p_compare_na_equal", type); } } @@ -101,15 +101,15 @@ static bool p_df_is_missing(const void* x, r_ssize i); // [[ include("poly-op.h") ]] poly_unary_bool_fn_ptr new_poly_p_is_missing(enum vctrs_type type) { switch (type) { - case vctrs_type_null: return p_nil_is_missing; - case vctrs_type_logical: return p_lgl_is_missing; - case vctrs_type_integer: return p_int_is_missing; - case vctrs_type_double: return p_dbl_is_missing; - case vctrs_type_complex: return p_cpl_is_missing; - case vctrs_type_character: return p_chr_is_missing; - case vctrs_type_raw: return p_raw_is_missing; - case vctrs_type_list: return p_list_is_missing; - case vctrs_type_dataframe: return p_df_is_missing; + case VCTRS_TYPE_null: return p_nil_is_missing; + case VCTRS_TYPE_logical: return p_lgl_is_missing; + case VCTRS_TYPE_integer: return p_int_is_missing; + case VCTRS_TYPE_double: return p_dbl_is_missing; + case VCTRS_TYPE_complex: return p_cpl_is_missing; + case VCTRS_TYPE_character: return p_chr_is_missing; + case VCTRS_TYPE_raw: return p_raw_is_missing; + case VCTRS_TYPE_list: return p_list_is_missing; + case VCTRS_TYPE_dataframe: return p_df_is_missing; default: stop_unimplemented_vctrs_type("new_poly_p_is_missing", type); } } @@ -139,15 +139,15 @@ static bool p_df_is_incomplete(const void* x, r_ssize i); // [[ include("poly-op.h") ]] poly_unary_bool_fn_ptr new_poly_p_is_incomplete(enum vctrs_type type) { switch (type) { - case vctrs_type_null: return p_nil_is_missing; - case vctrs_type_logical: return p_lgl_is_missing; - case vctrs_type_integer: return p_int_is_missing; - case vctrs_type_double: return p_dbl_is_missing; - case vctrs_type_complex: return p_cpl_is_missing; - case vctrs_type_character: return p_chr_is_missing; - case vctrs_type_raw: return p_raw_is_missing; - case vctrs_type_list: return p_list_is_missing; - case vctrs_type_dataframe: return p_df_is_incomplete; + case VCTRS_TYPE_null: return p_nil_is_missing; + case VCTRS_TYPE_logical: return p_lgl_is_missing; + case VCTRS_TYPE_integer: return p_int_is_missing; + case VCTRS_TYPE_double: return p_dbl_is_missing; + case VCTRS_TYPE_complex: return p_cpl_is_missing; + case VCTRS_TYPE_character: return p_chr_is_missing; + case VCTRS_TYPE_raw: return p_raw_is_missing; + case VCTRS_TYPE_list: return p_list_is_missing; + case VCTRS_TYPE_dataframe: return p_df_is_incomplete; default: stop_unimplemented_vctrs_type("new_poly_p_is_incomplete", type); } } @@ -192,15 +192,15 @@ struct poly_vec* new_poly_vec(SEXP proxy, enum vctrs_type type) { p_poly_vec->vec = proxy; switch (type) { - case vctrs_type_null: init_nil_poly_vec(p_poly_vec); break; - case vctrs_type_logical: init_lgl_poly_vec(p_poly_vec); break; - case vctrs_type_integer: init_int_poly_vec(p_poly_vec); break; - case vctrs_type_double: init_dbl_poly_vec(p_poly_vec); break; - case vctrs_type_complex: init_cpl_poly_vec(p_poly_vec); break; - case vctrs_type_character: init_chr_poly_vec(p_poly_vec); break; - case vctrs_type_raw: init_raw_poly_vec(p_poly_vec); break; - case vctrs_type_list: init_list_poly_vec(p_poly_vec); break; - case vctrs_type_dataframe: init_df_poly_vec(p_poly_vec); break; + case VCTRS_TYPE_null: init_nil_poly_vec(p_poly_vec); break; + case VCTRS_TYPE_logical: init_lgl_poly_vec(p_poly_vec); break; + case VCTRS_TYPE_integer: init_int_poly_vec(p_poly_vec); break; + case VCTRS_TYPE_double: init_dbl_poly_vec(p_poly_vec); break; + case VCTRS_TYPE_complex: init_cpl_poly_vec(p_poly_vec); break; + case VCTRS_TYPE_character: init_chr_poly_vec(p_poly_vec); break; + case VCTRS_TYPE_raw: init_raw_poly_vec(p_poly_vec); break; + case VCTRS_TYPE_list: init_list_poly_vec(p_poly_vec); break; + case VCTRS_TYPE_dataframe: init_df_poly_vec(p_poly_vec); break; default: stop_unimplemented_vctrs_type("new_poly_vec", type); } diff --git a/src/proxy.c b/src/proxy.c index bbc6dc0bc..140bfb856 100644 --- a/src/proxy.c +++ b/src/proxy.c @@ -8,7 +8,7 @@ r_obj* vec_proxy(r_obj* x) { KEEP(info.shelter); r_obj* out; - if (info.type == vctrs_type_s3) { + if (info.type == VCTRS_TYPE_s3) { out = vec_proxy_invoke(x, info.proxy_method); } else { out = x; @@ -101,7 +101,7 @@ r_obj* vec_proxy_invoke_impl(r_obj* x, } /* Fallback on S3 objects with no proxy */ - if (vec_typeof(x) == vctrs_type_s3) { + if (vec_typeof(x) == VCTRS_TYPE_s3) { return vec_proxy_fn(x); } else { return x; diff --git a/src/ptype.c b/src/ptype.c index 0917980a5..8dc1895aa 100644 --- a/src/ptype.c +++ b/src/ptype.c @@ -12,18 +12,18 @@ r_obj* ffi_ptype(r_obj* x, r_obj* x_arg_ffi, r_obj* frame) { r_obj* vec_ptype(r_obj* x, struct vctrs_arg* x_arg, struct r_lazy call) { switch (vec_typeof(x)) { - case vctrs_type_null: return r_null; - case vctrs_type_unspecified: return vctrs_shared_empty_uns; - case vctrs_type_logical: return vec_ptype_slice(x, vctrs_shared_empty_lgl); - case vctrs_type_integer: return vec_ptype_slice(x, vctrs_shared_empty_int); - case vctrs_type_double: return vec_ptype_slice(x, vctrs_shared_empty_dbl); - case vctrs_type_complex: return vec_ptype_slice(x, vctrs_shared_empty_cpl); - case vctrs_type_character: return vec_ptype_slice(x, vctrs_shared_empty_chr); - case vctrs_type_raw: return vec_ptype_slice(x, vctrs_shared_empty_raw); - case vctrs_type_list: return vec_ptype_slice(x, vctrs_shared_empty_list); - case vctrs_type_dataframe: return df_ptype(x, true); - case vctrs_type_s3: return s3_ptype(x, x_arg, call); - case vctrs_type_scalar: stop_scalar_type(x, x_arg, call); + case VCTRS_TYPE_null: return r_null; + case VCTRS_TYPE_unspecified: return vctrs_shared_empty_uns; + case VCTRS_TYPE_logical: return vec_ptype_slice(x, vctrs_shared_empty_lgl); + case VCTRS_TYPE_integer: return vec_ptype_slice(x, vctrs_shared_empty_int); + case VCTRS_TYPE_double: return vec_ptype_slice(x, vctrs_shared_empty_dbl); + case VCTRS_TYPE_complex: return vec_ptype_slice(x, vctrs_shared_empty_cpl); + case VCTRS_TYPE_character: return vec_ptype_slice(x, vctrs_shared_empty_chr); + case VCTRS_TYPE_raw: return vec_ptype_slice(x, vctrs_shared_empty_raw); + case VCTRS_TYPE_list: return vec_ptype_slice(x, vctrs_shared_empty_list); + case VCTRS_TYPE_dataframe: return df_ptype(x, true); + case VCTRS_TYPE_s3: return s3_ptype(x, x_arg, call); + case VCTRS_TYPE_scalar: stop_scalar_type(x, x_arg, call); } r_stop_unreachable(); } diff --git a/src/ptype2.c b/src/ptype2.c index dde28bcc9..9a7919d22 100644 --- a/src/ptype2.c +++ b/src/ptype2.c @@ -37,34 +37,34 @@ r_obj* vec_ptype2_opts_impl(const struct ptype2_opts* opts, enum vctrs_type x_type = vec_typeof(x); enum vctrs_type y_type = vec_typeof(y); - if (x_type == vctrs_type_null) { + if (x_type == VCTRS_TYPE_null) { *left = y == r_null; return vec_ptype2_from_unspecified(opts, x_type, y, y_arg); } - if (y_type == vctrs_type_null) { + if (y_type == VCTRS_TYPE_null) { *left = x == r_null; return vec_ptype2_from_unspecified(opts, x_type, x, x_arg); } - if (x_type == vctrs_type_unspecified) { + if (x_type == VCTRS_TYPE_unspecified) { return vec_ptype2_from_unspecified(opts, y_type, y, y_arg); } - if (y_type == vctrs_type_unspecified) { + if (y_type == VCTRS_TYPE_unspecified) { return vec_ptype2_from_unspecified(opts, x_type, x, x_arg); } - if (x_type == vctrs_type_scalar) { + if (x_type == VCTRS_TYPE_scalar) { stop_scalar_type(x, x_arg, opts->call); } - if (y_type == vctrs_type_scalar) { + if (y_type == VCTRS_TYPE_scalar) { stop_scalar_type(y, y_arg, opts->call); } - if (x_type != vctrs_type_s3 && y_type != vctrs_type_s3) { + if (x_type != VCTRS_TYPE_s3 && y_type != VCTRS_TYPE_s3) { return vec_ptype2_switch_native(opts, x_type, y_type, left); } - if (x_type == vctrs_type_s3 || y_type == vctrs_type_s3) { + if (x_type == VCTRS_TYPE_s3 || y_type == VCTRS_TYPE_s3) { r_obj* out = vec_ptype2_dispatch_native(opts, x_type, y_type, left); if (out != r_null) { return out; @@ -154,7 +154,7 @@ r_obj* vec_ptype2_from_unspecified(const struct ptype2_opts* opts, enum vctrs_type other_type, r_obj* other, struct vctrs_arg* other_arg) { - if (other_type == vctrs_type_unspecified || other_type == vctrs_type_null) { + if (other_type == VCTRS_TYPE_unspecified || other_type == VCTRS_TYPE_null) { return vec_ptype(other, other_arg, opts->call); } diff --git a/src/runs.c b/src/runs.c index 22ac2d569..4b94ccb0d 100644 --- a/src/runs.c +++ b/src/runs.c @@ -199,14 +199,14 @@ SEXP vec_identify_runs(SEXP x) { int n; switch (type) { - case vctrs_type_logical: n = lgl_identify_runs(proxy, size, p_out); break; - case vctrs_type_integer: n = int_identify_runs(proxy, size, p_out); break; - case vctrs_type_double: n = dbl_identify_runs(proxy, size, p_out); break; - case vctrs_type_complex: n = cpl_identify_runs(proxy, size, p_out); break; - case vctrs_type_character: n = chr_identify_runs(proxy, size, p_out); break; - case vctrs_type_raw: n = raw_identify_runs(proxy, size, p_out); break; - case vctrs_type_list: n = list_identify_runs(proxy, size, p_out); break; - case vctrs_type_dataframe: n = df_identify_runs(proxy, size, p_out); break; + case VCTRS_TYPE_logical: n = lgl_identify_runs(proxy, size, p_out); break; + case VCTRS_TYPE_integer: n = int_identify_runs(proxy, size, p_out); break; + case VCTRS_TYPE_double: n = dbl_identify_runs(proxy, size, p_out); break; + case VCTRS_TYPE_complex: n = cpl_identify_runs(proxy, size, p_out); break; + case VCTRS_TYPE_character: n = chr_identify_runs(proxy, size, p_out); break; + case VCTRS_TYPE_raw: n = raw_identify_runs(proxy, size, p_out); break; + case VCTRS_TYPE_list: n = list_identify_runs(proxy, size, p_out); break; + case VCTRS_TYPE_dataframe: n = df_identify_runs(proxy, size, p_out); break; default: stop_unimplemented_vctrs_type("vec_identify_runs", type); } @@ -371,15 +371,15 @@ int vec_identify_runs_col(SEXP x, struct df_short_circuit_info* p_info, int* p_out) { switch (vec_proxy_typeof(x)) { - case vctrs_type_logical: return lgl_identify_runs_col(x, id, p_info, p_out); - case vctrs_type_integer: return int_identify_runs_col(x, id, p_info, p_out); - case vctrs_type_double: return dbl_identify_runs_col(x, id, p_info, p_out); - case vctrs_type_complex: return cpl_identify_runs_col(x, id, p_info, p_out); - case vctrs_type_character: return chr_identify_runs_col(x, id, p_info, p_out); - case vctrs_type_raw: return raw_identify_runs_col(x, id, p_info, p_out); - case vctrs_type_list: return list_identify_runs_col(x, id, p_info, p_out); - case vctrs_type_dataframe: r_stop_internal("Data frame columns should be flattened."); - case vctrs_type_scalar: Rf_errorcall(R_NilValue, "Can't compare scalars with `vec_identify_runs()`"); + case VCTRS_TYPE_logical: return lgl_identify_runs_col(x, id, p_info, p_out); + case VCTRS_TYPE_integer: return int_identify_runs_col(x, id, p_info, p_out); + case VCTRS_TYPE_double: return dbl_identify_runs_col(x, id, p_info, p_out); + case VCTRS_TYPE_complex: return cpl_identify_runs_col(x, id, p_info, p_out); + case VCTRS_TYPE_character: return chr_identify_runs_col(x, id, p_info, p_out); + case VCTRS_TYPE_raw: return raw_identify_runs_col(x, id, p_info, p_out); + case VCTRS_TYPE_list: return list_identify_runs_col(x, id, p_info, p_out); + case VCTRS_TYPE_dataframe: r_stop_internal("Data frame columns should be flattened."); + case VCTRS_TYPE_scalar: Rf_errorcall(R_NilValue, "Can't compare scalars with `vec_identify_runs()`"); default: Rf_error("Unimplemented type in `vec_identify_runs()`"); } } diff --git a/src/size.c b/src/size.c index 612cba91d..2a78be4ce 100644 --- a/src/size.c +++ b/src/size.c @@ -28,20 +28,20 @@ r_ssize vec_size_opts(r_obj* x, const struct vec_error_opts* opts) { r_ssize size; switch (info.type) { - case vctrs_type_null: + case VCTRS_TYPE_null: size = 0; break; - case vctrs_type_logical: - case vctrs_type_integer: - case vctrs_type_double: - case vctrs_type_complex: - case vctrs_type_character: - case vctrs_type_raw: - case vctrs_type_list: + case VCTRS_TYPE_logical: + case VCTRS_TYPE_integer: + case VCTRS_TYPE_double: + case VCTRS_TYPE_complex: + case VCTRS_TYPE_character: + case VCTRS_TYPE_raw: + case VCTRS_TYPE_list: size = vec_raw_size(data); break; - case vctrs_type_dataframe: + case VCTRS_TYPE_dataframe: size = df_size(data); break; diff --git a/src/slice-array.c b/src/slice-array.c index 3e0e8e2dc..b4da7ca66 100644 --- a/src/slice-array.c +++ b/src/slice-array.c @@ -276,13 +276,13 @@ SEXP vec_slice_shaped_base(enum vctrs_type type, SEXP index, struct strides_info* p_info) { switch (type) { - case vctrs_type_logical: return lgl_slice_shaped(x, index, p_info); - case vctrs_type_integer: return int_slice_shaped(x, index, p_info); - case vctrs_type_double: return dbl_slice_shaped(x, index, p_info); - case vctrs_type_complex: return cpl_slice_shaped(x, index, p_info); - case vctrs_type_character: return chr_slice_shaped(x, index, p_info); - case vctrs_type_raw: return raw_slice_shaped(x, index, p_info); - case vctrs_type_list: return list_slice_shaped(x, index, p_info); + case VCTRS_TYPE_logical: return lgl_slice_shaped(x, index, p_info); + case VCTRS_TYPE_integer: return int_slice_shaped(x, index, p_info); + case VCTRS_TYPE_double: return dbl_slice_shaped(x, index, p_info); + case VCTRS_TYPE_complex: return cpl_slice_shaped(x, index, p_info); + case VCTRS_TYPE_character: return chr_slice_shaped(x, index, p_info); + case VCTRS_TYPE_raw: return raw_slice_shaped(x, index, p_info); + case VCTRS_TYPE_list: return list_slice_shaped(x, index, p_info); default: stop_unimplemented_vctrs_type("vec_slice_shaped_base", type); } } diff --git a/src/slice-assign-array.c b/src/slice-assign-array.c index 151e7353c..68ca41161 100644 --- a/src/slice-assign-array.c +++ b/src/slice-assign-array.c @@ -195,13 +195,13 @@ static inline SEXP vec_assign_shaped_switch(SEXP proxy, const enum vctrs_owned owned, struct strides_info* p_info) { switch (vec_proxy_typeof(proxy)) { - case vctrs_type_logical: return lgl_assign_shaped(proxy, index, value, owned, p_info); - case vctrs_type_integer: return int_assign_shaped(proxy, index, value, owned, p_info); - case vctrs_type_double: return dbl_assign_shaped(proxy, index, value, owned, p_info); - case vctrs_type_complex: return cpl_assign_shaped(proxy, index, value, owned, p_info); - case vctrs_type_character: return chr_assign_shaped(proxy, index, value, owned, p_info); - case vctrs_type_raw: return raw_assign_shaped(proxy, index, value, owned, p_info); - case vctrs_type_list: return list_assign_shaped(proxy, index, value, owned, p_info); + case VCTRS_TYPE_logical: return lgl_assign_shaped(proxy, index, value, owned, p_info); + case VCTRS_TYPE_integer: return int_assign_shaped(proxy, index, value, owned, p_info); + case VCTRS_TYPE_double: return dbl_assign_shaped(proxy, index, value, owned, p_info); + case VCTRS_TYPE_complex: return cpl_assign_shaped(proxy, index, value, owned, p_info); + case VCTRS_TYPE_character: return chr_assign_shaped(proxy, index, value, owned, p_info); + case VCTRS_TYPE_raw: return raw_assign_shaped(proxy, index, value, owned, p_info); + case VCTRS_TYPE_list: return list_assign_shaped(proxy, index, value, owned, p_info); default: stop_unimplemented_vctrs_type("vec_assign_shaped_switch", vec_proxy_typeof(proxy)); } diff --git a/src/slice-assign.c b/src/slice-assign.c index 6c3da1e68..9f4818a09 100644 --- a/src/slice-assign.c +++ b/src/slice-assign.c @@ -80,15 +80,15 @@ r_obj* vec_assign_switch(r_obj* proxy, const enum vctrs_owned owned, const struct vec_assign_opts* opts) { switch (vec_proxy_typeof(proxy)) { - case vctrs_type_logical: return lgl_assign(proxy, index, value, owned); - case vctrs_type_integer: return int_assign(proxy, index, value, owned); - case vctrs_type_double: return dbl_assign(proxy, index, value, owned); - case vctrs_type_complex: return cpl_assign(proxy, index, value, owned); - case vctrs_type_character: return chr_assign(proxy, index, value, owned); - case vctrs_type_raw: return raw_assign(proxy, index, value, owned); - case vctrs_type_list: return list_assign(proxy, index, value, owned); - case vctrs_type_dataframe: return df_assign(proxy, index, value, owned, opts); - case vctrs_type_scalar: stop_scalar_type(proxy, vec_args.empty, r_lazy_null); + case VCTRS_TYPE_logical: return lgl_assign(proxy, index, value, owned); + case VCTRS_TYPE_integer: return int_assign(proxy, index, value, owned); + case VCTRS_TYPE_double: return dbl_assign(proxy, index, value, owned); + case VCTRS_TYPE_complex: return cpl_assign(proxy, index, value, owned); + case VCTRS_TYPE_character: return chr_assign(proxy, index, value, owned); + case VCTRS_TYPE_raw: return raw_assign(proxy, index, value, owned); + case VCTRS_TYPE_list: return list_assign(proxy, index, value, owned); + case VCTRS_TYPE_dataframe: return df_assign(proxy, index, value, owned, opts); + case VCTRS_TYPE_scalar: stop_scalar_type(proxy, vec_args.empty, r_lazy_null); default: stop_unimplemented_vctrs_type("vec_assign_switch", vec_typeof(proxy)); } r_stop_unreachable(); diff --git a/src/slice-chop.c b/src/slice-chop.c index 3b6b740bd..1627aae76 100644 --- a/src/slice-chop.c +++ b/src/slice-chop.c @@ -127,7 +127,7 @@ static SEXP vec_chop_base(SEXP x, SEXP indices, struct vctrs_chop_info info) { // Fallback to `[` if the class doesn't implement a proxy. This is // to be maximally compatible with existing classes. if (vec_requires_fallback(x, proxy_info)) { - if (proxy_info.type == vctrs_type_scalar) { + if (proxy_info.type == VCTRS_TYPE_scalar) { Rf_errorcall(R_NilValue, "Can't slice a scalar"); } @@ -149,20 +149,20 @@ static SEXP vec_chop_base(SEXP x, SEXP indices, struct vctrs_chop_info info) { } switch (proxy_info.type) { - case vctrs_type_logical: - case vctrs_type_integer: - case vctrs_type_double: - case vctrs_type_complex: - case vctrs_type_character: - case vctrs_type_raw: - case vctrs_type_list: { + case VCTRS_TYPE_logical: + case VCTRS_TYPE_integer: + case VCTRS_TYPE_double: + case VCTRS_TYPE_complex: + case VCTRS_TYPE_character: + case VCTRS_TYPE_raw: + case VCTRS_TYPE_list: { if (has_dim(x)) { return chop_shaped(x, indices, info); } return chop(x, indices, info); } - case vctrs_type_dataframe: { + case VCTRS_TYPE_dataframe: { return chop_df(x, indices, info); } default: diff --git a/src/slice.c b/src/slice.c index 6fcb17790..07c2eb57c 100644 --- a/src/slice.c +++ b/src/slice.c @@ -238,7 +238,7 @@ r_obj* vec_slice_dispatch(r_obj* x, r_obj* subscript) { bool vec_requires_fallback(r_obj* x, struct vctrs_proxy_info info) { return r_is_object(x) && info.proxy_method == r_null && - info.type != vctrs_type_dataframe; + info.type != VCTRS_TYPE_dataframe; } r_obj* vec_slice_base(enum vctrs_type type, @@ -246,13 +246,13 @@ r_obj* vec_slice_base(enum vctrs_type type, r_obj* subscript, enum vctrs_materialize materialize) { switch (type) { - case vctrs_type_logical: return lgl_slice(x, subscript, materialize); - case vctrs_type_integer: return int_slice(x, subscript, materialize); - case vctrs_type_double: return dbl_slice(x, subscript, materialize); - case vctrs_type_complex: return cpl_slice(x, subscript, materialize); - case vctrs_type_character: return chr_slice(x, subscript, materialize); - case vctrs_type_raw: return raw_slice(x, subscript, materialize); - case vctrs_type_list: return list_slice(x, subscript); + case VCTRS_TYPE_logical: return lgl_slice(x, subscript, materialize); + case VCTRS_TYPE_integer: return int_slice(x, subscript, materialize); + case VCTRS_TYPE_double: return dbl_slice(x, subscript, materialize); + case VCTRS_TYPE_complex: return cpl_slice(x, subscript, materialize); + case VCTRS_TYPE_character: return chr_slice(x, subscript, materialize); + case VCTRS_TYPE_raw: return raw_slice(x, subscript, materialize); + case VCTRS_TYPE_list: return list_slice(x, subscript); default: stop_unimplemented_vctrs_type("vec_slice_base", type); } } @@ -292,7 +292,7 @@ r_obj* vec_slice_unsafe(r_obj* x, r_obj* subscript) { // Fallback to `[` if the class doesn't implement a proxy. This is // to be maximally compatible with existing classes. if (vec_requires_fallback(x, info)) { - if (info.type == vctrs_type_scalar) { + if (info.type == VCTRS_TYPE_scalar) { vec_check_vector(x, NULL, r_lazy_null); } @@ -318,16 +318,16 @@ r_obj* vec_slice_unsafe(r_obj* x, r_obj* subscript) { } switch (info.type) { - case vctrs_type_null: + case VCTRS_TYPE_null: r_stop_internal("Unexpected `NULL`."); - case vctrs_type_logical: - case vctrs_type_integer: - case vctrs_type_double: - case vctrs_type_complex: - case vctrs_type_character: - case vctrs_type_raw: - case vctrs_type_list: { + case VCTRS_TYPE_logical: + case VCTRS_TYPE_integer: + case VCTRS_TYPE_double: + case VCTRS_TYPE_complex: + case VCTRS_TYPE_character: + case VCTRS_TYPE_raw: + case VCTRS_TYPE_list: { r_obj* out; if (has_dim(x)) { @@ -355,7 +355,7 @@ r_obj* vec_slice_unsafe(r_obj* x, r_obj* subscript) { return out; } - case vctrs_type_dataframe: { + case VCTRS_TYPE_dataframe: { r_obj* out = KEEP_N(df_slice(data, subscript), &nprot); out = vec_restore(out, x, restore_size, vec_owned(out)); FREE(nprot); diff --git a/src/type-info.c b/src/type-info.c index 2527a6709..3950b193c 100644 --- a/src/type-info.c +++ b/src/type-info.c @@ -8,7 +8,7 @@ struct vctrs_type_info vec_type_info(r_obj* x) { }; switch (info.type) { - case vctrs_type_s3: info.proxy_method = vec_proxy_method(x); break; + case VCTRS_TYPE_s3: info.proxy_method = vec_proxy_method(x); break; default: info.proxy_method = r_null; } info.shelter = info.proxy_method; @@ -66,21 +66,21 @@ static enum vctrs_type vec_base_typeof(r_obj* x, bool proxied) { switch (r_typeof(x)) { // Atomic types are always vectors - case R_TYPE_null: return vctrs_type_null; - case R_TYPE_logical: return vctrs_type_logical; - case R_TYPE_integer: return vctrs_type_integer; - case R_TYPE_double: return vctrs_type_double; - case R_TYPE_complex: return vctrs_type_complex; - case R_TYPE_character: return vctrs_type_character; - case R_TYPE_raw: return vctrs_type_raw; + case R_TYPE_null: return VCTRS_TYPE_null; + case R_TYPE_logical: return VCTRS_TYPE_logical; + case R_TYPE_integer: return VCTRS_TYPE_integer; + case R_TYPE_double: return VCTRS_TYPE_double; + case R_TYPE_complex: return VCTRS_TYPE_complex; + case R_TYPE_character: return VCTRS_TYPE_character; + case R_TYPE_raw: return VCTRS_TYPE_raw; case R_TYPE_list: // Bare lists and data frames are vectors - if (!r_is_object(x)) return vctrs_type_list; - if (is_data_frame(x)) return vctrs_type_dataframe; + if (!r_is_object(x)) return VCTRS_TYPE_list; + if (is_data_frame(x)) return VCTRS_TYPE_dataframe; // S3 lists are only vectors if they are proxied - if (proxied || r_inherits(x, "list")) return vctrs_type_list; + if (proxied || r_inherits(x, "list")) return VCTRS_TYPE_list; // fallthrough - default: return vctrs_type_scalar; + default: return VCTRS_TYPE_scalar; } } @@ -123,7 +123,7 @@ bool vec_is_vector(r_obj* x) { } struct vctrs_proxy_info info = vec_proxy_info(x); - return info.type != vctrs_type_scalar; + return info.type != VCTRS_TYPE_scalar; } // [[ register() ]] @@ -153,9 +153,9 @@ r_obj* vctrs_typeof(r_obj* x, r_obj* dispatch) { enum vctrs_type vec_typeof(r_obj* x) { // Check for unspecified vectors before `vec_base_typeof()` which - // allows vectors of `NA` to pass through as `vctrs_type_logical` + // allows vectors of `NA` to pass through as `VCTRS_TYPE_logical` if (vec_is_unspecified(x)) { - return vctrs_type_unspecified; + return VCTRS_TYPE_unspecified; } if (!r_is_object(x) || r_class(x) == r_null) { @@ -166,10 +166,10 @@ enum vctrs_type vec_typeof(r_obj* x) { // data frames are treated as S3 to give them a chance to be proxied // or implement their own methods for cast, type2, etc. if (is_bare_data_frame(x)) { - return vctrs_type_dataframe; + return VCTRS_TYPE_dataframe; } - return vctrs_type_s3; + return VCTRS_TYPE_s3; } r_no_return @@ -179,18 +179,18 @@ void stop_unimplemented_vctrs_type(const char* fn, enum vctrs_type type) { const char* vec_type_as_str(enum vctrs_type type) { switch (type) { - case vctrs_type_null: return "null"; - case vctrs_type_unspecified: return "unspecified"; - case vctrs_type_logical: return "logical"; - case vctrs_type_integer: return "integer"; - case vctrs_type_double: return "double"; - case vctrs_type_complex: return "complex"; - case vctrs_type_character: return "character"; - case vctrs_type_raw: return "raw"; - case vctrs_type_list: return "list"; - case vctrs_type_dataframe: return "dataframe"; - case vctrs_type_s3: return "s3"; - case vctrs_type_scalar: return "scalar"; + case VCTRS_TYPE_null: return "null"; + case VCTRS_TYPE_unspecified: return "unspecified"; + case VCTRS_TYPE_logical: return "logical"; + case VCTRS_TYPE_integer: return "integer"; + case VCTRS_TYPE_double: return "double"; + case VCTRS_TYPE_complex: return "complex"; + case VCTRS_TYPE_character: return "character"; + case VCTRS_TYPE_raw: return "raw"; + case VCTRS_TYPE_list: return "list"; + case VCTRS_TYPE_dataframe: return "dataframe"; + case VCTRS_TYPE_s3: return "s3"; + case VCTRS_TYPE_scalar: return "scalar"; } never_reached("vec_type_as_str"); } diff --git a/src/type-info.h b/src/type-info.h index 125b32a5a..4af36a69b 100644 --- a/src/type-info.h +++ b/src/type-info.h @@ -4,18 +4,18 @@ #include enum vctrs_type { - vctrs_type_null = 0, - vctrs_type_unspecified, - vctrs_type_logical, - vctrs_type_integer, - vctrs_type_double, - vctrs_type_complex, - vctrs_type_character, - vctrs_type_raw, - vctrs_type_list, - vctrs_type_dataframe, - vctrs_type_scalar, - vctrs_type_s3 = 255 + VCTRS_TYPE_null = 0, + VCTRS_TYPE_unspecified, + VCTRS_TYPE_logical, + VCTRS_TYPE_integer, + VCTRS_TYPE_double, + VCTRS_TYPE_complex, + VCTRS_TYPE_character, + VCTRS_TYPE_raw, + VCTRS_TYPE_list, + VCTRS_TYPE_dataframe, + VCTRS_TYPE_scalar, + VCTRS_TYPE_s3 = 255 }; /** diff --git a/src/typeof2-s3.c b/src/typeof2-s3.c index 4ca1b6ade..907b4cea9 100644 --- a/src/typeof2-s3.c +++ b/src/typeof2-s3.c @@ -12,7 +12,7 @@ enum vctrs_type2_s3 vec_typeof2_s3_impl(SEXP x, enum vctrs_type type_y, int* left) { switch (type_x) { - case vctrs_type_null: { + case VCTRS_TYPE_null: { switch (class_type(y)) { case VCTRS_CLASS_bare_factor: *left = 0; return VCTRS_TYPE2_S3_null_bare_factor; case VCTRS_CLASS_bare_ordered: *left = 0; return VCTRS_TYPE2_S3_null_bare_ordered; @@ -23,7 +23,7 @@ enum vctrs_type2_s3 vec_typeof2_s3_impl(SEXP x, default: *left = 0; return VCTRS_TYPE2_S3_null_unknown; } } - case vctrs_type_unspecified: { + case VCTRS_TYPE_unspecified: { switch (class_type(y)) { case VCTRS_CLASS_bare_factor: *left = 0; return VCTRS_TYPE2_S3_unspecified_bare_factor; case VCTRS_CLASS_bare_ordered: *left = 0; return VCTRS_TYPE2_S3_unspecified_bare_ordered; @@ -34,7 +34,7 @@ enum vctrs_type2_s3 vec_typeof2_s3_impl(SEXP x, default: *left = 0; return VCTRS_TYPE2_S3_unspecified_unknown; } } - case vctrs_type_logical: { + case VCTRS_TYPE_logical: { switch (class_type(y)) { case VCTRS_CLASS_bare_factor: *left = 0; return VCTRS_TYPE2_S3_logical_bare_factor; case VCTRS_CLASS_bare_ordered: *left = 0; return VCTRS_TYPE2_S3_logical_bare_ordered; @@ -45,7 +45,7 @@ enum vctrs_type2_s3 vec_typeof2_s3_impl(SEXP x, default: *left = 0; return VCTRS_TYPE2_S3_logical_unknown; } } - case vctrs_type_integer: { + case VCTRS_TYPE_integer: { switch (class_type(y)) { case VCTRS_CLASS_bare_factor: *left = 0; return VCTRS_TYPE2_S3_integer_bare_factor; case VCTRS_CLASS_bare_ordered: *left = 0; return VCTRS_TYPE2_S3_integer_bare_ordered; @@ -56,7 +56,7 @@ enum vctrs_type2_s3 vec_typeof2_s3_impl(SEXP x, default: *left = 0; return VCTRS_TYPE2_S3_integer_unknown; } } - case vctrs_type_double: { + case VCTRS_TYPE_double: { switch (class_type(y)) { case VCTRS_CLASS_bare_factor: *left = 0; return VCTRS_TYPE2_S3_double_bare_factor; case VCTRS_CLASS_bare_ordered: *left = 0; return VCTRS_TYPE2_S3_double_bare_ordered; @@ -67,7 +67,7 @@ enum vctrs_type2_s3 vec_typeof2_s3_impl(SEXP x, default: *left = 0; return VCTRS_TYPE2_S3_double_unknown; } } - case vctrs_type_complex: { + case VCTRS_TYPE_complex: { switch (class_type(y)) { case VCTRS_CLASS_bare_factor: *left = 0; return VCTRS_TYPE2_S3_complex_bare_factor; case VCTRS_CLASS_bare_ordered: *left = 0; return VCTRS_TYPE2_S3_complex_bare_ordered; @@ -78,7 +78,7 @@ enum vctrs_type2_s3 vec_typeof2_s3_impl(SEXP x, default: *left = 0; return VCTRS_TYPE2_S3_complex_unknown; } } - case vctrs_type_character: { + case VCTRS_TYPE_character: { switch (class_type(y)) { case VCTRS_CLASS_bare_factor: *left = 0; return VCTRS_TYPE2_S3_character_bare_factor; case VCTRS_CLASS_bare_ordered: *left = 0; return VCTRS_TYPE2_S3_character_bare_ordered; @@ -89,7 +89,7 @@ enum vctrs_type2_s3 vec_typeof2_s3_impl(SEXP x, default: *left = 0; return VCTRS_TYPE2_S3_character_unknown; } } - case vctrs_type_raw: { + case VCTRS_TYPE_raw: { switch (class_type(y)) { case VCTRS_CLASS_bare_factor: *left = 0; return VCTRS_TYPE2_S3_raw_bare_factor; case VCTRS_CLASS_bare_ordered: *left = 0; return VCTRS_TYPE2_S3_raw_bare_ordered; @@ -100,7 +100,7 @@ enum vctrs_type2_s3 vec_typeof2_s3_impl(SEXP x, default: *left = 0; return VCTRS_TYPE2_S3_raw_unknown; } } - case vctrs_type_list: { + case VCTRS_TYPE_list: { switch (class_type(y)) { case VCTRS_CLASS_bare_factor: *left = 0; return VCTRS_TYPE2_S3_list_bare_factor; case VCTRS_CLASS_bare_ordered: *left = 0; return VCTRS_TYPE2_S3_list_bare_ordered; @@ -111,7 +111,7 @@ enum vctrs_type2_s3 vec_typeof2_s3_impl(SEXP x, default: *left = 0; return VCTRS_TYPE2_S3_list_unknown; } } - case vctrs_type_dataframe: { + case VCTRS_TYPE_dataframe: { switch (class_type(y)) { case VCTRS_CLASS_bare_factor: *left = 0; return VCTRS_TYPE2_S3_dataframe_bare_factor; case VCTRS_CLASS_bare_ordered: *left = 0; return VCTRS_TYPE2_S3_dataframe_bare_ordered; @@ -122,7 +122,7 @@ enum vctrs_type2_s3 vec_typeof2_s3_impl(SEXP x, default: *left = 0; return VCTRS_TYPE2_S3_dataframe_unknown; } } - case vctrs_type_scalar: { + case VCTRS_TYPE_scalar: { switch (class_type(y)) { case VCTRS_CLASS_bare_factor: *left = 0; return VCTRS_TYPE2_S3_scalar_bare_factor; case VCTRS_CLASS_bare_ordered: *left = 0; return VCTRS_TYPE2_S3_scalar_bare_ordered; @@ -133,7 +133,7 @@ enum vctrs_type2_s3 vec_typeof2_s3_impl(SEXP x, default: *left = 0; return VCTRS_TYPE2_S3_scalar_unknown; } } - case vctrs_type_s3: { + case VCTRS_TYPE_s3: { return vec_typeof2_s3_impl2(x, y, type_y, left); }} @@ -148,18 +148,18 @@ static enum vctrs_type2_s3 vec_typeof2_s3_impl2(SEXP x, switch (class_type(x)) { case VCTRS_CLASS_bare_factor: { switch (type_y) { - case vctrs_type_null: *left = 1; return VCTRS_TYPE2_S3_null_bare_factor; - case vctrs_type_unspecified: *left = 1; return VCTRS_TYPE2_S3_unspecified_bare_factor; - case vctrs_type_logical: *left = 1; return VCTRS_TYPE2_S3_logical_bare_factor; - case vctrs_type_integer: *left = 1; return VCTRS_TYPE2_S3_integer_bare_factor; - case vctrs_type_double: *left = 1; return VCTRS_TYPE2_S3_double_bare_factor; - case vctrs_type_complex: *left = 1; return VCTRS_TYPE2_S3_complex_bare_factor; - case vctrs_type_character: *left = 1; return VCTRS_TYPE2_S3_character_bare_factor; - case vctrs_type_raw: *left = 1; return VCTRS_TYPE2_S3_raw_bare_factor; - case vctrs_type_list: *left = 1; return VCTRS_TYPE2_S3_list_bare_factor; - case vctrs_type_dataframe: *left = 1; return VCTRS_TYPE2_S3_dataframe_bare_factor; - case vctrs_type_scalar: *left = 1; return VCTRS_TYPE2_S3_scalar_bare_factor; - case vctrs_type_s3: { + case VCTRS_TYPE_null: *left = 1; return VCTRS_TYPE2_S3_null_bare_factor; + case VCTRS_TYPE_unspecified: *left = 1; return VCTRS_TYPE2_S3_unspecified_bare_factor; + case VCTRS_TYPE_logical: *left = 1; return VCTRS_TYPE2_S3_logical_bare_factor; + case VCTRS_TYPE_integer: *left = 1; return VCTRS_TYPE2_S3_integer_bare_factor; + case VCTRS_TYPE_double: *left = 1; return VCTRS_TYPE2_S3_double_bare_factor; + case VCTRS_TYPE_complex: *left = 1; return VCTRS_TYPE2_S3_complex_bare_factor; + case VCTRS_TYPE_character: *left = 1; return VCTRS_TYPE2_S3_character_bare_factor; + case VCTRS_TYPE_raw: *left = 1; return VCTRS_TYPE2_S3_raw_bare_factor; + case VCTRS_TYPE_list: *left = 1; return VCTRS_TYPE2_S3_list_bare_factor; + case VCTRS_TYPE_dataframe: *left = 1; return VCTRS_TYPE2_S3_dataframe_bare_factor; + case VCTRS_TYPE_scalar: *left = 1; return VCTRS_TYPE2_S3_scalar_bare_factor; + case VCTRS_TYPE_s3: { switch (class_type(y)) { case VCTRS_CLASS_bare_factor: *left = -1; return VCTRS_TYPE2_S3_bare_factor_bare_factor; case VCTRS_CLASS_bare_ordered: *left = 0; return VCTRS_TYPE2_S3_bare_factor_bare_ordered; @@ -173,18 +173,18 @@ static enum vctrs_type2_s3 vec_typeof2_s3_impl2(SEXP x, } case VCTRS_CLASS_bare_ordered: { switch (type_y) { - case vctrs_type_null: *left = 1; return VCTRS_TYPE2_S3_null_bare_ordered; - case vctrs_type_unspecified: *left = 1; return VCTRS_TYPE2_S3_unspecified_bare_ordered; - case vctrs_type_logical: *left = 1; return VCTRS_TYPE2_S3_logical_bare_ordered; - case vctrs_type_integer: *left = 1; return VCTRS_TYPE2_S3_integer_bare_ordered; - case vctrs_type_double: *left = 1; return VCTRS_TYPE2_S3_double_bare_ordered; - case vctrs_type_complex: *left = 1; return VCTRS_TYPE2_S3_complex_bare_ordered; - case vctrs_type_character: *left = 1; return VCTRS_TYPE2_S3_character_bare_ordered; - case vctrs_type_raw: *left = 1; return VCTRS_TYPE2_S3_raw_bare_ordered; - case vctrs_type_list: *left = 1; return VCTRS_TYPE2_S3_list_bare_ordered; - case vctrs_type_dataframe: *left = 1; return VCTRS_TYPE2_S3_dataframe_bare_ordered; - case vctrs_type_scalar: *left = 1; return VCTRS_TYPE2_S3_scalar_bare_ordered; - case vctrs_type_s3: { + case VCTRS_TYPE_null: *left = 1; return VCTRS_TYPE2_S3_null_bare_ordered; + case VCTRS_TYPE_unspecified: *left = 1; return VCTRS_TYPE2_S3_unspecified_bare_ordered; + case VCTRS_TYPE_logical: *left = 1; return VCTRS_TYPE2_S3_logical_bare_ordered; + case VCTRS_TYPE_integer: *left = 1; return VCTRS_TYPE2_S3_integer_bare_ordered; + case VCTRS_TYPE_double: *left = 1; return VCTRS_TYPE2_S3_double_bare_ordered; + case VCTRS_TYPE_complex: *left = 1; return VCTRS_TYPE2_S3_complex_bare_ordered; + case VCTRS_TYPE_character: *left = 1; return VCTRS_TYPE2_S3_character_bare_ordered; + case VCTRS_TYPE_raw: *left = 1; return VCTRS_TYPE2_S3_raw_bare_ordered; + case VCTRS_TYPE_list: *left = 1; return VCTRS_TYPE2_S3_list_bare_ordered; + case VCTRS_TYPE_dataframe: *left = 1; return VCTRS_TYPE2_S3_dataframe_bare_ordered; + case VCTRS_TYPE_scalar: *left = 1; return VCTRS_TYPE2_S3_scalar_bare_ordered; + case VCTRS_TYPE_s3: { switch (class_type(y)) { case VCTRS_CLASS_bare_factor: *left = 1; return VCTRS_TYPE2_S3_bare_factor_bare_ordered; case VCTRS_CLASS_bare_ordered: *left = -1; return VCTRS_TYPE2_S3_bare_ordered_bare_ordered; @@ -198,18 +198,18 @@ static enum vctrs_type2_s3 vec_typeof2_s3_impl2(SEXP x, } case VCTRS_CLASS_bare_date: { switch (type_y) { - case vctrs_type_null: *left = 1; return VCTRS_TYPE2_S3_null_bare_date; - case vctrs_type_unspecified: *left = 1; return VCTRS_TYPE2_S3_unspecified_bare_date; - case vctrs_type_logical: *left = 1; return VCTRS_TYPE2_S3_logical_bare_date; - case vctrs_type_integer: *left = 1; return VCTRS_TYPE2_S3_integer_bare_date; - case vctrs_type_double: *left = 1; return VCTRS_TYPE2_S3_double_bare_date; - case vctrs_type_complex: *left = 1; return VCTRS_TYPE2_S3_complex_bare_date; - case vctrs_type_character: *left = 1; return VCTRS_TYPE2_S3_character_bare_date; - case vctrs_type_raw: *left = 1; return VCTRS_TYPE2_S3_raw_bare_date; - case vctrs_type_list: *left = 1; return VCTRS_TYPE2_S3_list_bare_date; - case vctrs_type_dataframe: *left = 1; return VCTRS_TYPE2_S3_dataframe_bare_date; - case vctrs_type_scalar: *left = 1; return VCTRS_TYPE2_S3_scalar_bare_date; - case vctrs_type_s3: { + case VCTRS_TYPE_null: *left = 1; return VCTRS_TYPE2_S3_null_bare_date; + case VCTRS_TYPE_unspecified: *left = 1; return VCTRS_TYPE2_S3_unspecified_bare_date; + case VCTRS_TYPE_logical: *left = 1; return VCTRS_TYPE2_S3_logical_bare_date; + case VCTRS_TYPE_integer: *left = 1; return VCTRS_TYPE2_S3_integer_bare_date; + case VCTRS_TYPE_double: *left = 1; return VCTRS_TYPE2_S3_double_bare_date; + case VCTRS_TYPE_complex: *left = 1; return VCTRS_TYPE2_S3_complex_bare_date; + case VCTRS_TYPE_character: *left = 1; return VCTRS_TYPE2_S3_character_bare_date; + case VCTRS_TYPE_raw: *left = 1; return VCTRS_TYPE2_S3_raw_bare_date; + case VCTRS_TYPE_list: *left = 1; return VCTRS_TYPE2_S3_list_bare_date; + case VCTRS_TYPE_dataframe: *left = 1; return VCTRS_TYPE2_S3_dataframe_bare_date; + case VCTRS_TYPE_scalar: *left = 1; return VCTRS_TYPE2_S3_scalar_bare_date; + case VCTRS_TYPE_s3: { switch (class_type(y)) { case VCTRS_CLASS_bare_factor: *left = 1; return VCTRS_TYPE2_S3_bare_factor_bare_date; case VCTRS_CLASS_bare_ordered: *left = 1; return VCTRS_TYPE2_S3_bare_ordered_bare_date; @@ -223,18 +223,18 @@ static enum vctrs_type2_s3 vec_typeof2_s3_impl2(SEXP x, } case VCTRS_CLASS_bare_posixct: { switch (type_y) { - case vctrs_type_null: *left = 1; return VCTRS_TYPE2_S3_null_bare_posixct; - case vctrs_type_unspecified: *left = 1; return VCTRS_TYPE2_S3_unspecified_bare_posixct; - case vctrs_type_logical: *left = 1; return VCTRS_TYPE2_S3_logical_bare_posixct; - case vctrs_type_integer: *left = 1; return VCTRS_TYPE2_S3_integer_bare_posixct; - case vctrs_type_double: *left = 1; return VCTRS_TYPE2_S3_double_bare_posixct; - case vctrs_type_complex: *left = 1; return VCTRS_TYPE2_S3_complex_bare_posixct; - case vctrs_type_character: *left = 1; return VCTRS_TYPE2_S3_character_bare_posixct; - case vctrs_type_raw: *left = 1; return VCTRS_TYPE2_S3_raw_bare_posixct; - case vctrs_type_list: *left = 1; return VCTRS_TYPE2_S3_list_bare_posixct; - case vctrs_type_dataframe: *left = 1; return VCTRS_TYPE2_S3_dataframe_bare_posixct; - case vctrs_type_scalar: *left = 1; return VCTRS_TYPE2_S3_scalar_bare_posixct; - case vctrs_type_s3: { + case VCTRS_TYPE_null: *left = 1; return VCTRS_TYPE2_S3_null_bare_posixct; + case VCTRS_TYPE_unspecified: *left = 1; return VCTRS_TYPE2_S3_unspecified_bare_posixct; + case VCTRS_TYPE_logical: *left = 1; return VCTRS_TYPE2_S3_logical_bare_posixct; + case VCTRS_TYPE_integer: *left = 1; return VCTRS_TYPE2_S3_integer_bare_posixct; + case VCTRS_TYPE_double: *left = 1; return VCTRS_TYPE2_S3_double_bare_posixct; + case VCTRS_TYPE_complex: *left = 1; return VCTRS_TYPE2_S3_complex_bare_posixct; + case VCTRS_TYPE_character: *left = 1; return VCTRS_TYPE2_S3_character_bare_posixct; + case VCTRS_TYPE_raw: *left = 1; return VCTRS_TYPE2_S3_raw_bare_posixct; + case VCTRS_TYPE_list: *left = 1; return VCTRS_TYPE2_S3_list_bare_posixct; + case VCTRS_TYPE_dataframe: *left = 1; return VCTRS_TYPE2_S3_dataframe_bare_posixct; + case VCTRS_TYPE_scalar: *left = 1; return VCTRS_TYPE2_S3_scalar_bare_posixct; + case VCTRS_TYPE_s3: { switch (class_type(y)) { case VCTRS_CLASS_bare_factor: *left = 1; return VCTRS_TYPE2_S3_bare_factor_bare_posixct; case VCTRS_CLASS_bare_ordered: *left = 1; return VCTRS_TYPE2_S3_bare_ordered_bare_posixct; @@ -248,18 +248,18 @@ static enum vctrs_type2_s3 vec_typeof2_s3_impl2(SEXP x, } case VCTRS_CLASS_bare_posixlt: { switch (type_y) { - case vctrs_type_null: *left = 1; return VCTRS_TYPE2_S3_null_bare_posixlt; - case vctrs_type_unspecified: *left = 1; return VCTRS_TYPE2_S3_unspecified_bare_posixlt; - case vctrs_type_logical: *left = 1; return VCTRS_TYPE2_S3_logical_bare_posixlt; - case vctrs_type_integer: *left = 1; return VCTRS_TYPE2_S3_integer_bare_posixlt; - case vctrs_type_double: *left = 1; return VCTRS_TYPE2_S3_double_bare_posixlt; - case vctrs_type_complex: *left = 1; return VCTRS_TYPE2_S3_complex_bare_posixlt; - case vctrs_type_character: *left = 1; return VCTRS_TYPE2_S3_character_bare_posixlt; - case vctrs_type_raw: *left = 1; return VCTRS_TYPE2_S3_raw_bare_posixlt; - case vctrs_type_list: *left = 1; return VCTRS_TYPE2_S3_list_bare_posixlt; - case vctrs_type_dataframe: *left = 1; return VCTRS_TYPE2_S3_dataframe_bare_posixlt; - case vctrs_type_scalar: *left = 1; return VCTRS_TYPE2_S3_scalar_bare_posixlt; - case vctrs_type_s3: { + case VCTRS_TYPE_null: *left = 1; return VCTRS_TYPE2_S3_null_bare_posixlt; + case VCTRS_TYPE_unspecified: *left = 1; return VCTRS_TYPE2_S3_unspecified_bare_posixlt; + case VCTRS_TYPE_logical: *left = 1; return VCTRS_TYPE2_S3_logical_bare_posixlt; + case VCTRS_TYPE_integer: *left = 1; return VCTRS_TYPE2_S3_integer_bare_posixlt; + case VCTRS_TYPE_double: *left = 1; return VCTRS_TYPE2_S3_double_bare_posixlt; + case VCTRS_TYPE_complex: *left = 1; return VCTRS_TYPE2_S3_complex_bare_posixlt; + case VCTRS_TYPE_character: *left = 1; return VCTRS_TYPE2_S3_character_bare_posixlt; + case VCTRS_TYPE_raw: *left = 1; return VCTRS_TYPE2_S3_raw_bare_posixlt; + case VCTRS_TYPE_list: *left = 1; return VCTRS_TYPE2_S3_list_bare_posixlt; + case VCTRS_TYPE_dataframe: *left = 1; return VCTRS_TYPE2_S3_dataframe_bare_posixlt; + case VCTRS_TYPE_scalar: *left = 1; return VCTRS_TYPE2_S3_scalar_bare_posixlt; + case VCTRS_TYPE_s3: { switch (class_type(y)) { case VCTRS_CLASS_bare_factor: *left = 1; return VCTRS_TYPE2_S3_bare_factor_bare_posixlt; case VCTRS_CLASS_bare_ordered: *left = 1; return VCTRS_TYPE2_S3_bare_ordered_bare_posixlt; @@ -273,18 +273,18 @@ static enum vctrs_type2_s3 vec_typeof2_s3_impl2(SEXP x, } case VCTRS_CLASS_bare_tibble: { switch (type_y) { - case vctrs_type_null: *left = 1; return VCTRS_TYPE2_S3_null_bare_tibble; - case vctrs_type_unspecified: *left = 1; return VCTRS_TYPE2_S3_unspecified_bare_tibble; - case vctrs_type_logical: *left = 1; return VCTRS_TYPE2_S3_logical_bare_tibble; - case vctrs_type_integer: *left = 1; return VCTRS_TYPE2_S3_integer_bare_tibble; - case vctrs_type_double: *left = 1; return VCTRS_TYPE2_S3_double_bare_tibble; - case vctrs_type_complex: *left = 1; return VCTRS_TYPE2_S3_complex_bare_tibble; - case vctrs_type_character: *left = 1; return VCTRS_TYPE2_S3_character_bare_tibble; - case vctrs_type_raw: *left = 1; return VCTRS_TYPE2_S3_raw_bare_tibble; - case vctrs_type_list: *left = 1; return VCTRS_TYPE2_S3_list_bare_tibble; - case vctrs_type_dataframe: *left = 1; return VCTRS_TYPE2_S3_dataframe_bare_tibble; - case vctrs_type_scalar: *left = 1; return VCTRS_TYPE2_S3_scalar_bare_tibble; - case vctrs_type_s3: { + case VCTRS_TYPE_null: *left = 1; return VCTRS_TYPE2_S3_null_bare_tibble; + case VCTRS_TYPE_unspecified: *left = 1; return VCTRS_TYPE2_S3_unspecified_bare_tibble; + case VCTRS_TYPE_logical: *left = 1; return VCTRS_TYPE2_S3_logical_bare_tibble; + case VCTRS_TYPE_integer: *left = 1; return VCTRS_TYPE2_S3_integer_bare_tibble; + case VCTRS_TYPE_double: *left = 1; return VCTRS_TYPE2_S3_double_bare_tibble; + case VCTRS_TYPE_complex: *left = 1; return VCTRS_TYPE2_S3_complex_bare_tibble; + case VCTRS_TYPE_character: *left = 1; return VCTRS_TYPE2_S3_character_bare_tibble; + case VCTRS_TYPE_raw: *left = 1; return VCTRS_TYPE2_S3_raw_bare_tibble; + case VCTRS_TYPE_list: *left = 1; return VCTRS_TYPE2_S3_list_bare_tibble; + case VCTRS_TYPE_dataframe: *left = 1; return VCTRS_TYPE2_S3_dataframe_bare_tibble; + case VCTRS_TYPE_scalar: *left = 1; return VCTRS_TYPE2_S3_scalar_bare_tibble; + case VCTRS_TYPE_s3: { switch (class_type(y)) { case VCTRS_CLASS_bare_factor: *left = 1; return VCTRS_TYPE2_S3_bare_factor_bare_tibble; case VCTRS_CLASS_bare_ordered: *left = 1; return VCTRS_TYPE2_S3_bare_ordered_bare_tibble; @@ -298,18 +298,18 @@ static enum vctrs_type2_s3 vec_typeof2_s3_impl2(SEXP x, } default: { switch (type_y) { - case vctrs_type_null: *left = 1; return VCTRS_TYPE2_S3_null_unknown; - case vctrs_type_unspecified: *left = 1; return VCTRS_TYPE2_S3_unspecified_unknown; - case vctrs_type_logical: *left = 1; return VCTRS_TYPE2_S3_logical_unknown; - case vctrs_type_integer: *left = 1; return VCTRS_TYPE2_S3_integer_unknown; - case vctrs_type_double: *left = 1; return VCTRS_TYPE2_S3_double_unknown; - case vctrs_type_complex: *left = 1; return VCTRS_TYPE2_S3_complex_unknown; - case vctrs_type_character: *left = 1; return VCTRS_TYPE2_S3_character_unknown; - case vctrs_type_raw: *left = 1; return VCTRS_TYPE2_S3_raw_unknown; - case vctrs_type_list: *left = 1; return VCTRS_TYPE2_S3_list_unknown; - case vctrs_type_dataframe: *left = 1; return VCTRS_TYPE2_S3_dataframe_unknown; - case vctrs_type_scalar: *left = 1; return VCTRS_TYPE2_S3_scalar_unknown; - case vctrs_type_s3: { + case VCTRS_TYPE_null: *left = 1; return VCTRS_TYPE2_S3_null_unknown; + case VCTRS_TYPE_unspecified: *left = 1; return VCTRS_TYPE2_S3_unspecified_unknown; + case VCTRS_TYPE_logical: *left = 1; return VCTRS_TYPE2_S3_logical_unknown; + case VCTRS_TYPE_integer: *left = 1; return VCTRS_TYPE2_S3_integer_unknown; + case VCTRS_TYPE_double: *left = 1; return VCTRS_TYPE2_S3_double_unknown; + case VCTRS_TYPE_complex: *left = 1; return VCTRS_TYPE2_S3_complex_unknown; + case VCTRS_TYPE_character: *left = 1; return VCTRS_TYPE2_S3_character_unknown; + case VCTRS_TYPE_raw: *left = 1; return VCTRS_TYPE2_S3_raw_unknown; + case VCTRS_TYPE_list: *left = 1; return VCTRS_TYPE2_S3_list_unknown; + case VCTRS_TYPE_dataframe: *left = 1; return VCTRS_TYPE2_S3_dataframe_unknown; + case VCTRS_TYPE_scalar: *left = 1; return VCTRS_TYPE2_S3_scalar_unknown; + case VCTRS_TYPE_s3: { switch (class_type(y)) { case VCTRS_CLASS_bare_factor: *left = 1; return VCTRS_TYPE2_S3_bare_factor_unknown; case VCTRS_CLASS_bare_ordered: *left = 1; return VCTRS_TYPE2_S3_bare_ordered_unknown; diff --git a/src/typeof2.c b/src/typeof2.c index 805050d60..c0fee4251 100644 --- a/src/typeof2.c +++ b/src/typeof2.c @@ -22,196 +22,196 @@ enum vctrs_type2 vec_typeof2_impl(enum vctrs_type type_x, enum vctrs_type type_y, int* left) { switch (type_x) { - case vctrs_type_null: { + case VCTRS_TYPE_null: { switch (type_y) { - case vctrs_type_null: *left = -1; return VCTRS_TYPE2_null_null; - case vctrs_type_unspecified: *left = 0; return VCTRS_TYPE2_null_unspecified; - case vctrs_type_logical: *left = 0; return VCTRS_TYPE2_null_logical; - case vctrs_type_integer: *left = 0; return VCTRS_TYPE2_null_integer; - case vctrs_type_double: *left = 0; return VCTRS_TYPE2_null_double; - case vctrs_type_complex: *left = 0; return VCTRS_TYPE2_null_complex; - case vctrs_type_character: *left = 0; return VCTRS_TYPE2_null_character; - case vctrs_type_raw: *left = 0; return VCTRS_TYPE2_null_raw; - case vctrs_type_list: *left = 0; return VCTRS_TYPE2_null_list; - case vctrs_type_dataframe: *left = 0; return VCTRS_TYPE2_null_dataframe; - case vctrs_type_s3: *left = 0; return VCTRS_TYPE2_null_s3; - case vctrs_type_scalar: *left = 0; return VCTRS_TYPE2_null_scalar; + case VCTRS_TYPE_null: *left = -1; return VCTRS_TYPE2_null_null; + case VCTRS_TYPE_unspecified: *left = 0; return VCTRS_TYPE2_null_unspecified; + case VCTRS_TYPE_logical: *left = 0; return VCTRS_TYPE2_null_logical; + case VCTRS_TYPE_integer: *left = 0; return VCTRS_TYPE2_null_integer; + case VCTRS_TYPE_double: *left = 0; return VCTRS_TYPE2_null_double; + case VCTRS_TYPE_complex: *left = 0; return VCTRS_TYPE2_null_complex; + case VCTRS_TYPE_character: *left = 0; return VCTRS_TYPE2_null_character; + case VCTRS_TYPE_raw: *left = 0; return VCTRS_TYPE2_null_raw; + case VCTRS_TYPE_list: *left = 0; return VCTRS_TYPE2_null_list; + case VCTRS_TYPE_dataframe: *left = 0; return VCTRS_TYPE2_null_dataframe; + case VCTRS_TYPE_s3: *left = 0; return VCTRS_TYPE2_null_s3; + case VCTRS_TYPE_scalar: *left = 0; return VCTRS_TYPE2_null_scalar; } } - case vctrs_type_unspecified: { + case VCTRS_TYPE_unspecified: { switch (type_y) { - case vctrs_type_null: *left = 1; return VCTRS_TYPE2_null_unspecified; - case vctrs_type_unspecified: *left = -1; return VCTRS_TYPE2_unspecified_unspecified; - case vctrs_type_logical: *left = 0; return VCTRS_TYPE2_unspecified_logical; - case vctrs_type_integer: *left = 0; return VCTRS_TYPE2_unspecified_integer; - case vctrs_type_double: *left = 0; return VCTRS_TYPE2_unspecified_double; - case vctrs_type_complex: *left = 0; return VCTRS_TYPE2_unspecified_complex; - case vctrs_type_character: *left = 0; return VCTRS_TYPE2_unspecified_character; - case vctrs_type_raw: *left = 0; return VCTRS_TYPE2_unspecified_raw; - case vctrs_type_list: *left = 0; return VCTRS_TYPE2_unspecified_list; - case vctrs_type_dataframe: *left = 0; return VCTRS_TYPE2_unspecified_dataframe; - case vctrs_type_s3: *left = 0; return VCTRS_TYPE2_unspecified_s3; - case vctrs_type_scalar: *left = 0; return VCTRS_TYPE2_unspecified_scalar; + case VCTRS_TYPE_null: *left = 1; return VCTRS_TYPE2_null_unspecified; + case VCTRS_TYPE_unspecified: *left = -1; return VCTRS_TYPE2_unspecified_unspecified; + case VCTRS_TYPE_logical: *left = 0; return VCTRS_TYPE2_unspecified_logical; + case VCTRS_TYPE_integer: *left = 0; return VCTRS_TYPE2_unspecified_integer; + case VCTRS_TYPE_double: *left = 0; return VCTRS_TYPE2_unspecified_double; + case VCTRS_TYPE_complex: *left = 0; return VCTRS_TYPE2_unspecified_complex; + case VCTRS_TYPE_character: *left = 0; return VCTRS_TYPE2_unspecified_character; + case VCTRS_TYPE_raw: *left = 0; return VCTRS_TYPE2_unspecified_raw; + case VCTRS_TYPE_list: *left = 0; return VCTRS_TYPE2_unspecified_list; + case VCTRS_TYPE_dataframe: *left = 0; return VCTRS_TYPE2_unspecified_dataframe; + case VCTRS_TYPE_s3: *left = 0; return VCTRS_TYPE2_unspecified_s3; + case VCTRS_TYPE_scalar: *left = 0; return VCTRS_TYPE2_unspecified_scalar; } } - case vctrs_type_logical: { + case VCTRS_TYPE_logical: { switch (type_y) { - case vctrs_type_null: *left = 1; return VCTRS_TYPE2_null_logical; - case vctrs_type_unspecified: *left = 1; return VCTRS_TYPE2_unspecified_logical; - case vctrs_type_logical: *left = -1; return VCTRS_TYPE2_logical_logical; - case vctrs_type_integer: *left = 0; return VCTRS_TYPE2_logical_integer; - case vctrs_type_double: *left = 0; return VCTRS_TYPE2_logical_double; - case vctrs_type_complex: *left = 0; return VCTRS_TYPE2_logical_complex; - case vctrs_type_character: *left = 0; return VCTRS_TYPE2_logical_character; - case vctrs_type_raw: *left = 0; return VCTRS_TYPE2_logical_raw; - case vctrs_type_list: *left = 0; return VCTRS_TYPE2_logical_list; - case vctrs_type_dataframe: *left = 0; return VCTRS_TYPE2_logical_dataframe; - case vctrs_type_s3: *left = 0; return VCTRS_TYPE2_logical_s3; - case vctrs_type_scalar: *left = 0; return VCTRS_TYPE2_logical_scalar; + case VCTRS_TYPE_null: *left = 1; return VCTRS_TYPE2_null_logical; + case VCTRS_TYPE_unspecified: *left = 1; return VCTRS_TYPE2_unspecified_logical; + case VCTRS_TYPE_logical: *left = -1; return VCTRS_TYPE2_logical_logical; + case VCTRS_TYPE_integer: *left = 0; return VCTRS_TYPE2_logical_integer; + case VCTRS_TYPE_double: *left = 0; return VCTRS_TYPE2_logical_double; + case VCTRS_TYPE_complex: *left = 0; return VCTRS_TYPE2_logical_complex; + case VCTRS_TYPE_character: *left = 0; return VCTRS_TYPE2_logical_character; + case VCTRS_TYPE_raw: *left = 0; return VCTRS_TYPE2_logical_raw; + case VCTRS_TYPE_list: *left = 0; return VCTRS_TYPE2_logical_list; + case VCTRS_TYPE_dataframe: *left = 0; return VCTRS_TYPE2_logical_dataframe; + case VCTRS_TYPE_s3: *left = 0; return VCTRS_TYPE2_logical_s3; + case VCTRS_TYPE_scalar: *left = 0; return VCTRS_TYPE2_logical_scalar; } } - case vctrs_type_integer: { + case VCTRS_TYPE_integer: { switch (type_y) { - case vctrs_type_null: *left = 1; return VCTRS_TYPE2_null_integer; - case vctrs_type_unspecified: *left = 1; return VCTRS_TYPE2_unspecified_integer; - case vctrs_type_logical: *left = 1; return VCTRS_TYPE2_logical_integer; - case vctrs_type_integer: *left = -1; return VCTRS_TYPE2_integer_integer; - case vctrs_type_double: *left = 0; return VCTRS_TYPE2_integer_double; - case vctrs_type_complex: *left = 0; return VCTRS_TYPE2_integer_complex; - case vctrs_type_character: *left = 0; return VCTRS_TYPE2_integer_character; - case vctrs_type_raw: *left = 0; return VCTRS_TYPE2_integer_raw; - case vctrs_type_list: *left = 0; return VCTRS_TYPE2_integer_list; - case vctrs_type_dataframe: *left = 0; return VCTRS_TYPE2_integer_dataframe; - case vctrs_type_s3: *left = 0; return VCTRS_TYPE2_integer_s3; - case vctrs_type_scalar: *left = 0; return VCTRS_TYPE2_integer_scalar; + case VCTRS_TYPE_null: *left = 1; return VCTRS_TYPE2_null_integer; + case VCTRS_TYPE_unspecified: *left = 1; return VCTRS_TYPE2_unspecified_integer; + case VCTRS_TYPE_logical: *left = 1; return VCTRS_TYPE2_logical_integer; + case VCTRS_TYPE_integer: *left = -1; return VCTRS_TYPE2_integer_integer; + case VCTRS_TYPE_double: *left = 0; return VCTRS_TYPE2_integer_double; + case VCTRS_TYPE_complex: *left = 0; return VCTRS_TYPE2_integer_complex; + case VCTRS_TYPE_character: *left = 0; return VCTRS_TYPE2_integer_character; + case VCTRS_TYPE_raw: *left = 0; return VCTRS_TYPE2_integer_raw; + case VCTRS_TYPE_list: *left = 0; return VCTRS_TYPE2_integer_list; + case VCTRS_TYPE_dataframe: *left = 0; return VCTRS_TYPE2_integer_dataframe; + case VCTRS_TYPE_s3: *left = 0; return VCTRS_TYPE2_integer_s3; + case VCTRS_TYPE_scalar: *left = 0; return VCTRS_TYPE2_integer_scalar; } } - case vctrs_type_double: { + case VCTRS_TYPE_double: { switch (type_y) { - case vctrs_type_null: *left = 1; return VCTRS_TYPE2_null_double; - case vctrs_type_unspecified: *left = 1; return VCTRS_TYPE2_unspecified_double; - case vctrs_type_logical: *left = 1; return VCTRS_TYPE2_logical_double; - case vctrs_type_integer: *left = 1; return VCTRS_TYPE2_integer_double; - case vctrs_type_double: *left = -1; return VCTRS_TYPE2_double_double; - case vctrs_type_complex: *left = 0; return VCTRS_TYPE2_double_complex; - case vctrs_type_character: *left = 0; return VCTRS_TYPE2_double_character; - case vctrs_type_raw: *left = 0; return VCTRS_TYPE2_double_raw; - case vctrs_type_list: *left = 0; return VCTRS_TYPE2_double_list; - case vctrs_type_dataframe: *left = 0; return VCTRS_TYPE2_double_dataframe; - case vctrs_type_s3: *left = 0; return VCTRS_TYPE2_double_s3; - case vctrs_type_scalar: *left = 0; return VCTRS_TYPE2_double_scalar; + case VCTRS_TYPE_null: *left = 1; return VCTRS_TYPE2_null_double; + case VCTRS_TYPE_unspecified: *left = 1; return VCTRS_TYPE2_unspecified_double; + case VCTRS_TYPE_logical: *left = 1; return VCTRS_TYPE2_logical_double; + case VCTRS_TYPE_integer: *left = 1; return VCTRS_TYPE2_integer_double; + case VCTRS_TYPE_double: *left = -1; return VCTRS_TYPE2_double_double; + case VCTRS_TYPE_complex: *left = 0; return VCTRS_TYPE2_double_complex; + case VCTRS_TYPE_character: *left = 0; return VCTRS_TYPE2_double_character; + case VCTRS_TYPE_raw: *left = 0; return VCTRS_TYPE2_double_raw; + case VCTRS_TYPE_list: *left = 0; return VCTRS_TYPE2_double_list; + case VCTRS_TYPE_dataframe: *left = 0; return VCTRS_TYPE2_double_dataframe; + case VCTRS_TYPE_s3: *left = 0; return VCTRS_TYPE2_double_s3; + case VCTRS_TYPE_scalar: *left = 0; return VCTRS_TYPE2_double_scalar; } } - case vctrs_type_complex: { + case VCTRS_TYPE_complex: { switch (type_y) { - case vctrs_type_null: *left = 1; return VCTRS_TYPE2_null_complex; - case vctrs_type_unspecified: *left = 1; return VCTRS_TYPE2_unspecified_complex; - case vctrs_type_logical: *left = 1; return VCTRS_TYPE2_logical_complex; - case vctrs_type_integer: *left = 1; return VCTRS_TYPE2_integer_complex; - case vctrs_type_double: *left = 1; return VCTRS_TYPE2_double_complex; - case vctrs_type_complex: *left = -1; return VCTRS_TYPE2_complex_complex; - case vctrs_type_character: *left = 0; return VCTRS_TYPE2_complex_character; - case vctrs_type_raw: *left = 0; return VCTRS_TYPE2_complex_raw; - case vctrs_type_list: *left = 0; return VCTRS_TYPE2_complex_list; - case vctrs_type_dataframe: *left = 0; return VCTRS_TYPE2_complex_dataframe; - case vctrs_type_s3: *left = 0; return VCTRS_TYPE2_complex_s3; - case vctrs_type_scalar: *left = 0; return VCTRS_TYPE2_complex_scalar; + case VCTRS_TYPE_null: *left = 1; return VCTRS_TYPE2_null_complex; + case VCTRS_TYPE_unspecified: *left = 1; return VCTRS_TYPE2_unspecified_complex; + case VCTRS_TYPE_logical: *left = 1; return VCTRS_TYPE2_logical_complex; + case VCTRS_TYPE_integer: *left = 1; return VCTRS_TYPE2_integer_complex; + case VCTRS_TYPE_double: *left = 1; return VCTRS_TYPE2_double_complex; + case VCTRS_TYPE_complex: *left = -1; return VCTRS_TYPE2_complex_complex; + case VCTRS_TYPE_character: *left = 0; return VCTRS_TYPE2_complex_character; + case VCTRS_TYPE_raw: *left = 0; return VCTRS_TYPE2_complex_raw; + case VCTRS_TYPE_list: *left = 0; return VCTRS_TYPE2_complex_list; + case VCTRS_TYPE_dataframe: *left = 0; return VCTRS_TYPE2_complex_dataframe; + case VCTRS_TYPE_s3: *left = 0; return VCTRS_TYPE2_complex_s3; + case VCTRS_TYPE_scalar: *left = 0; return VCTRS_TYPE2_complex_scalar; } } - case vctrs_type_character: { + case VCTRS_TYPE_character: { switch (type_y) { - case vctrs_type_null: *left = 1; return VCTRS_TYPE2_null_character; - case vctrs_type_unspecified: *left = 1; return VCTRS_TYPE2_unspecified_character; - case vctrs_type_logical: *left = 1; return VCTRS_TYPE2_logical_character; - case vctrs_type_integer: *left = 1; return VCTRS_TYPE2_integer_character; - case vctrs_type_double: *left = 1; return VCTRS_TYPE2_double_character; - case vctrs_type_complex: *left = 1; return VCTRS_TYPE2_complex_character; - case vctrs_type_character: *left = -1; return VCTRS_TYPE2_character_character; - case vctrs_type_raw: *left = 0; return VCTRS_TYPE2_character_raw; - case vctrs_type_list: *left = 0; return VCTRS_TYPE2_character_list; - case vctrs_type_dataframe: *left = 0; return VCTRS_TYPE2_character_dataframe; - case vctrs_type_s3: *left = 0; return VCTRS_TYPE2_character_s3; - case vctrs_type_scalar: *left = 0; return VCTRS_TYPE2_character_scalar; + case VCTRS_TYPE_null: *left = 1; return VCTRS_TYPE2_null_character; + case VCTRS_TYPE_unspecified: *left = 1; return VCTRS_TYPE2_unspecified_character; + case VCTRS_TYPE_logical: *left = 1; return VCTRS_TYPE2_logical_character; + case VCTRS_TYPE_integer: *left = 1; return VCTRS_TYPE2_integer_character; + case VCTRS_TYPE_double: *left = 1; return VCTRS_TYPE2_double_character; + case VCTRS_TYPE_complex: *left = 1; return VCTRS_TYPE2_complex_character; + case VCTRS_TYPE_character: *left = -1; return VCTRS_TYPE2_character_character; + case VCTRS_TYPE_raw: *left = 0; return VCTRS_TYPE2_character_raw; + case VCTRS_TYPE_list: *left = 0; return VCTRS_TYPE2_character_list; + case VCTRS_TYPE_dataframe: *left = 0; return VCTRS_TYPE2_character_dataframe; + case VCTRS_TYPE_s3: *left = 0; return VCTRS_TYPE2_character_s3; + case VCTRS_TYPE_scalar: *left = 0; return VCTRS_TYPE2_character_scalar; } } - case vctrs_type_raw: { + case VCTRS_TYPE_raw: { switch (type_y) { - case vctrs_type_null: *left = 1; return VCTRS_TYPE2_null_raw; - case vctrs_type_unspecified: *left = 1; return VCTRS_TYPE2_unspecified_raw; - case vctrs_type_logical: *left = 1; return VCTRS_TYPE2_logical_raw; - case vctrs_type_integer: *left = 1; return VCTRS_TYPE2_integer_raw; - case vctrs_type_double: *left = 1; return VCTRS_TYPE2_double_raw; - case vctrs_type_complex: *left = 1; return VCTRS_TYPE2_complex_raw; - case vctrs_type_character: *left = 1; return VCTRS_TYPE2_character_raw; - case vctrs_type_raw: *left = -1; return VCTRS_TYPE2_raw_raw; - case vctrs_type_list: *left = 0; return VCTRS_TYPE2_raw_list; - case vctrs_type_dataframe: *left = 0; return VCTRS_TYPE2_raw_dataframe; - case vctrs_type_s3: *left = 0; return VCTRS_TYPE2_raw_s3; - case vctrs_type_scalar: *left = 0; return VCTRS_TYPE2_raw_scalar; + case VCTRS_TYPE_null: *left = 1; return VCTRS_TYPE2_null_raw; + case VCTRS_TYPE_unspecified: *left = 1; return VCTRS_TYPE2_unspecified_raw; + case VCTRS_TYPE_logical: *left = 1; return VCTRS_TYPE2_logical_raw; + case VCTRS_TYPE_integer: *left = 1; return VCTRS_TYPE2_integer_raw; + case VCTRS_TYPE_double: *left = 1; return VCTRS_TYPE2_double_raw; + case VCTRS_TYPE_complex: *left = 1; return VCTRS_TYPE2_complex_raw; + case VCTRS_TYPE_character: *left = 1; return VCTRS_TYPE2_character_raw; + case VCTRS_TYPE_raw: *left = -1; return VCTRS_TYPE2_raw_raw; + case VCTRS_TYPE_list: *left = 0; return VCTRS_TYPE2_raw_list; + case VCTRS_TYPE_dataframe: *left = 0; return VCTRS_TYPE2_raw_dataframe; + case VCTRS_TYPE_s3: *left = 0; return VCTRS_TYPE2_raw_s3; + case VCTRS_TYPE_scalar: *left = 0; return VCTRS_TYPE2_raw_scalar; } } - case vctrs_type_list: { + case VCTRS_TYPE_list: { switch (type_y) { - case vctrs_type_null: *left = 1; return VCTRS_TYPE2_null_list; - case vctrs_type_unspecified: *left = 1; return VCTRS_TYPE2_unspecified_list; - case vctrs_type_logical: *left = 1; return VCTRS_TYPE2_logical_list; - case vctrs_type_integer: *left = 1; return VCTRS_TYPE2_integer_list; - case vctrs_type_double: *left = 1; return VCTRS_TYPE2_double_list; - case vctrs_type_complex: *left = 1; return VCTRS_TYPE2_complex_list; - case vctrs_type_character: *left = 1; return VCTRS_TYPE2_character_list; - case vctrs_type_raw: *left = 1; return VCTRS_TYPE2_raw_list; - case vctrs_type_list: *left = -1; return VCTRS_TYPE2_list_list; - case vctrs_type_dataframe: *left = 0; return VCTRS_TYPE2_list_dataframe; - case vctrs_type_s3: *left = 0; return VCTRS_TYPE2_list_s3; - case vctrs_type_scalar: *left = 0; return VCTRS_TYPE2_list_scalar; + case VCTRS_TYPE_null: *left = 1; return VCTRS_TYPE2_null_list; + case VCTRS_TYPE_unspecified: *left = 1; return VCTRS_TYPE2_unspecified_list; + case VCTRS_TYPE_logical: *left = 1; return VCTRS_TYPE2_logical_list; + case VCTRS_TYPE_integer: *left = 1; return VCTRS_TYPE2_integer_list; + case VCTRS_TYPE_double: *left = 1; return VCTRS_TYPE2_double_list; + case VCTRS_TYPE_complex: *left = 1; return VCTRS_TYPE2_complex_list; + case VCTRS_TYPE_character: *left = 1; return VCTRS_TYPE2_character_list; + case VCTRS_TYPE_raw: *left = 1; return VCTRS_TYPE2_raw_list; + case VCTRS_TYPE_list: *left = -1; return VCTRS_TYPE2_list_list; + case VCTRS_TYPE_dataframe: *left = 0; return VCTRS_TYPE2_list_dataframe; + case VCTRS_TYPE_s3: *left = 0; return VCTRS_TYPE2_list_s3; + case VCTRS_TYPE_scalar: *left = 0; return VCTRS_TYPE2_list_scalar; } } - case vctrs_type_dataframe: { + case VCTRS_TYPE_dataframe: { switch (type_y) { - case vctrs_type_null: *left = 1; return VCTRS_TYPE2_null_dataframe; - case vctrs_type_unspecified: *left = 1; return VCTRS_TYPE2_unspecified_dataframe; - case vctrs_type_logical: *left = 1; return VCTRS_TYPE2_logical_dataframe; - case vctrs_type_integer: *left = 1; return VCTRS_TYPE2_integer_dataframe; - case vctrs_type_double: *left = 1; return VCTRS_TYPE2_double_dataframe; - case vctrs_type_complex: *left = 1; return VCTRS_TYPE2_complex_dataframe; - case vctrs_type_character: *left = 1; return VCTRS_TYPE2_character_dataframe; - case vctrs_type_raw: *left = 1; return VCTRS_TYPE2_raw_dataframe; - case vctrs_type_list: *left = 1; return VCTRS_TYPE2_list_dataframe; - case vctrs_type_dataframe: *left = -1; return VCTRS_TYPE2_dataframe_dataframe; - case vctrs_type_s3: *left = 0; return VCTRS_TYPE2_dataframe_s3; - case vctrs_type_scalar: *left = 0; return VCTRS_TYPE2_dataframe_scalar; + case VCTRS_TYPE_null: *left = 1; return VCTRS_TYPE2_null_dataframe; + case VCTRS_TYPE_unspecified: *left = 1; return VCTRS_TYPE2_unspecified_dataframe; + case VCTRS_TYPE_logical: *left = 1; return VCTRS_TYPE2_logical_dataframe; + case VCTRS_TYPE_integer: *left = 1; return VCTRS_TYPE2_integer_dataframe; + case VCTRS_TYPE_double: *left = 1; return VCTRS_TYPE2_double_dataframe; + case VCTRS_TYPE_complex: *left = 1; return VCTRS_TYPE2_complex_dataframe; + case VCTRS_TYPE_character: *left = 1; return VCTRS_TYPE2_character_dataframe; + case VCTRS_TYPE_raw: *left = 1; return VCTRS_TYPE2_raw_dataframe; + case VCTRS_TYPE_list: *left = 1; return VCTRS_TYPE2_list_dataframe; + case VCTRS_TYPE_dataframe: *left = -1; return VCTRS_TYPE2_dataframe_dataframe; + case VCTRS_TYPE_s3: *left = 0; return VCTRS_TYPE2_dataframe_s3; + case VCTRS_TYPE_scalar: *left = 0; return VCTRS_TYPE2_dataframe_scalar; } } - case vctrs_type_s3: { + case VCTRS_TYPE_s3: { switch (type_y) { - case vctrs_type_null: *left = 1; return VCTRS_TYPE2_null_s3; - case vctrs_type_unspecified: *left = 1; return VCTRS_TYPE2_unspecified_s3; - case vctrs_type_logical: *left = 1; return VCTRS_TYPE2_logical_s3; - case vctrs_type_integer: *left = 1; return VCTRS_TYPE2_integer_s3; - case vctrs_type_double: *left = 1; return VCTRS_TYPE2_double_s3; - case vctrs_type_complex: *left = 1; return VCTRS_TYPE2_complex_s3; - case vctrs_type_character: *left = 1; return VCTRS_TYPE2_character_s3; - case vctrs_type_raw: *left = 1; return VCTRS_TYPE2_raw_s3; - case vctrs_type_list: *left = 1; return VCTRS_TYPE2_list_s3; - case vctrs_type_dataframe: *left = 1; return VCTRS_TYPE2_dataframe_s3; - case vctrs_type_s3: *left = -1; return VCTRS_TYPE2_S3_s3; - case vctrs_type_scalar: *left = 0; return VCTRS_TYPE2_S3_scalar; + case VCTRS_TYPE_null: *left = 1; return VCTRS_TYPE2_null_s3; + case VCTRS_TYPE_unspecified: *left = 1; return VCTRS_TYPE2_unspecified_s3; + case VCTRS_TYPE_logical: *left = 1; return VCTRS_TYPE2_logical_s3; + case VCTRS_TYPE_integer: *left = 1; return VCTRS_TYPE2_integer_s3; + case VCTRS_TYPE_double: *left = 1; return VCTRS_TYPE2_double_s3; + case VCTRS_TYPE_complex: *left = 1; return VCTRS_TYPE2_complex_s3; + case VCTRS_TYPE_character: *left = 1; return VCTRS_TYPE2_character_s3; + case VCTRS_TYPE_raw: *left = 1; return VCTRS_TYPE2_raw_s3; + case VCTRS_TYPE_list: *left = 1; return VCTRS_TYPE2_list_s3; + case VCTRS_TYPE_dataframe: *left = 1; return VCTRS_TYPE2_dataframe_s3; + case VCTRS_TYPE_s3: *left = -1; return VCTRS_TYPE2_S3_s3; + case VCTRS_TYPE_scalar: *left = 0; return VCTRS_TYPE2_S3_scalar; } } - case vctrs_type_scalar: { + case VCTRS_TYPE_scalar: { switch (type_y) { - case vctrs_type_null: *left = 1; return VCTRS_TYPE2_null_scalar; - case vctrs_type_unspecified: *left = 1; return VCTRS_TYPE2_unspecified_scalar; - case vctrs_type_logical: *left = 1; return VCTRS_TYPE2_logical_scalar; - case vctrs_type_integer: *left = 1; return VCTRS_TYPE2_integer_scalar; - case vctrs_type_double: *left = 1; return VCTRS_TYPE2_double_scalar; - case vctrs_type_complex: *left = 1; return VCTRS_TYPE2_complex_scalar; - case vctrs_type_character: *left = 1; return VCTRS_TYPE2_character_scalar; - case vctrs_type_raw: *left = 1; return VCTRS_TYPE2_raw_scalar; - case vctrs_type_list: *left = 1; return VCTRS_TYPE2_list_scalar; - case vctrs_type_dataframe: *left = 1; return VCTRS_TYPE2_dataframe_scalar; - case vctrs_type_s3: *left = 1; return VCTRS_TYPE2_S3_scalar; - case vctrs_type_scalar: *left = -1; return VCTRS_TYPE2_scalar_scalar; + case VCTRS_TYPE_null: *left = 1; return VCTRS_TYPE2_null_scalar; + case VCTRS_TYPE_unspecified: *left = 1; return VCTRS_TYPE2_unspecified_scalar; + case VCTRS_TYPE_logical: *left = 1; return VCTRS_TYPE2_logical_scalar; + case VCTRS_TYPE_integer: *left = 1; return VCTRS_TYPE2_integer_scalar; + case VCTRS_TYPE_double: *left = 1; return VCTRS_TYPE2_double_scalar; + case VCTRS_TYPE_complex: *left = 1; return VCTRS_TYPE2_complex_scalar; + case VCTRS_TYPE_character: *left = 1; return VCTRS_TYPE2_character_scalar; + case VCTRS_TYPE_raw: *left = 1; return VCTRS_TYPE2_raw_scalar; + case VCTRS_TYPE_list: *left = 1; return VCTRS_TYPE2_list_scalar; + case VCTRS_TYPE_dataframe: *left = 1; return VCTRS_TYPE2_dataframe_scalar; + case VCTRS_TYPE_s3: *left = 1; return VCTRS_TYPE2_S3_scalar; + case VCTRS_TYPE_scalar: *left = -1; return VCTRS_TYPE2_scalar_scalar; } }} diff --git a/src/utils.c b/src/utils.c index 861fb3ed2..9f8564da3 100644 --- a/src/utils.c +++ b/src/utils.c @@ -663,9 +663,9 @@ SEXP s4_class_find_method(SEXP class, SEXP table) { // [[ include("utils.h") ]] bool vec_implements_ptype2(SEXP x) { switch (vec_typeof(x)) { - case vctrs_type_scalar: + case VCTRS_TYPE_scalar: return false; - case vctrs_type_s3: { + case VCTRS_TYPE_s3: { SEXP method_sym = R_NilValue; SEXP method = s3_find_method_xy("vec_ptype2", x, x, vctrs_method_table, &method_sym); diff --git a/src/utils.h b/src/utils.h index 82f73b293..039ad4e24 100644 --- a/src/utils.h +++ b/src/utils.h @@ -366,12 +366,12 @@ static inline SEXP expr_protect(SEXP x) { static inline const void* vec_type_missing_value(enum vctrs_type type) { switch (type) { - case vctrs_type_logical: return &NA_LOGICAL; - case vctrs_type_integer: return &NA_INTEGER; - case vctrs_type_double: return &NA_REAL; - case vctrs_type_complex: return &vctrs_shared_na_cpl; - case vctrs_type_character: return &NA_STRING; - case vctrs_type_list: return &R_NilValue; + case VCTRS_TYPE_logical: return &NA_LOGICAL; + case VCTRS_TYPE_integer: return &NA_INTEGER; + case VCTRS_TYPE_double: return &NA_REAL; + case VCTRS_TYPE_complex: return &vctrs_shared_na_cpl; + case VCTRS_TYPE_character: return &NA_STRING; + case VCTRS_TYPE_list: return &R_NilValue; default: stop_unimplemented_vctrs_type("vec_type_missing_value", type); } } From 8a3b9a72ea41bf6575b9002063d5577d29a36b81 Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Mon, 5 Sep 2022 15:36:16 +0200 Subject: [PATCH 016/312] Update style of `typeof2.c` --- R/type2.R | 2 +- src/init.c | 4 ++-- src/typeof2.c | 11 +++++------ src/typeof2.h | 17 +++++++++++++++++ src/utils.h | 3 --- src/vctrs.h | 4 +--- 6 files changed, 26 insertions(+), 15 deletions(-) create mode 100644 src/typeof2.h diff --git a/R/type2.R b/R/type2.R index 6ca4a85ed..4953fdabc 100644 --- a/R/type2.R +++ b/R/type2.R @@ -370,7 +370,7 @@ with_fallback_quiet <- function(expr) { } vec_typeof2 <- function(x, y) { - .Call(vctrs_typeof2, x, y) + .Call(ffi_typeof2, x, y) } vec_typeof2_s3 <- function(x, y) { diff --git a/src/init.c b/src/init.c index f24166c68..62b8fe783 100644 --- a/src/init.c +++ b/src/init.c @@ -42,7 +42,7 @@ extern SEXP vctrs_is_unspecified(SEXP); extern SEXP vctrs_typeof(SEXP, SEXP); extern SEXP vctrs_is_vector(SEXP); extern r_obj* ffi_ptype2(r_obj*, r_obj*, r_obj*); -extern SEXP vctrs_typeof2(SEXP, SEXP); +extern r_obj* ffi_typeof2(r_obj*, r_obj*); extern SEXP vctrs_typeof2_s3(SEXP, SEXP); extern r_obj* ffi_cast(r_obj*, r_obj*, r_obj*); extern r_obj* ffi_as_location(r_obj*, r_obj*, r_obj*, r_obj*, r_obj*, r_obj*, r_obj*, r_obj*); @@ -210,7 +210,7 @@ static const R_CallMethodDef CallEntries[] = { {"vctrs_init_library", (DL_FUNC) &vctrs_init_library, 1}, {"vctrs_is_vector", (DL_FUNC) &vctrs_is_vector, 1}, {"ffi_ptype2", (DL_FUNC) &ffi_ptype2, 3}, - {"vctrs_typeof2", (DL_FUNC) &vctrs_typeof2, 2}, + {"ffi_typeof2", (DL_FUNC) &ffi_typeof2, 2}, {"vctrs_typeof2_s3", (DL_FUNC) &vctrs_typeof2_s3, 2}, {"ffi_cast", (DL_FUNC) &ffi_cast, 3}, {"ffi_as_location", (DL_FUNC) &ffi_as_location, 8}, diff --git a/src/typeof2.c b/src/typeof2.c index c0fee4251..aa1428496 100644 --- a/src/typeof2.c +++ b/src/typeof2.c @@ -215,11 +215,10 @@ enum vctrs_type2 vec_typeof2_impl(enum vctrs_type type_x, } }} - never_reached("vec_typeof2_impl()"); + r_stop_unreachable(); } -// [[ include("vctrs.h") ]] -enum vctrs_type2 vec_typeof2(SEXP x, SEXP y) { +enum vctrs_type2 vec_typeof2(r_obj* x, r_obj* y) { int _; return vec_typeof2_impl(vec_typeof(x), vec_typeof(y), &_); } @@ -317,10 +316,10 @@ const char* vctrs_type2_as_str(enum vctrs_type2 type) { case VCTRS_TYPE2_scalar_scalar: return "VCTRS_TYPE2_scalar_scalar"; } - never_reached("vctrs_type2_as_str"); + r_stop_unreachable(); } -SEXP vctrs_typeof2(SEXP x, SEXP y) { +r_obj* ffi_typeof2(r_obj* x, r_obj* y) { enum vctrs_type2 type = vec_typeof2(x, y); - return Rf_mkString(vctrs_type2_as_str(type)); + return r_chr(vctrs_type2_as_str(type)); } diff --git a/src/typeof2.h b/src/typeof2.h new file mode 100644 index 000000000..0a815fe83 --- /dev/null +++ b/src/typeof2.h @@ -0,0 +1,17 @@ +#ifndef VCTRS_TYPEOF2_H +#define VCTRS_TYPEOF2_H + +#include "vctrs-core.h" + + +enum vctrs_type2 vec_typeof2_impl(enum vctrs_type type_x, + enum vctrs_type type_y, + int* left); + +enum vctrs_type2_s3 vec_typeof2_s3_impl(r_obj* x, r_obj* y, enum vctrs_type type_x, enum vctrs_type type_y, int* left); + +enum vctrs_type2 vec_typeof2(r_obj* x, r_obj* y); +const char* vctrs_type2_as_str(enum vctrs_type2 type); + + +#endif diff --git a/src/utils.h b/src/utils.h index 039ad4e24..a918941a3 100644 --- a/src/utils.h +++ b/src/utils.h @@ -170,9 +170,6 @@ SEXP node_compact_d(SEXP xs); void never_reached(const char* fn) __attribute__((noreturn)); -enum vctrs_type2 vec_typeof2_impl(enum vctrs_type type_x, enum vctrs_type type_y, int* left); -enum vctrs_type2_s3 vec_typeof2_s3_impl(SEXP x, SEXP y, enum vctrs_type type_x, enum vctrs_type type_y, int* left); - SEXP new_empty_factor(SEXP levels); SEXP new_empty_ordered(SEXP levels); diff --git a/src/vctrs.h b/src/vctrs.h index 8fd7c12b8..f01e3fee6 100644 --- a/src/vctrs.h +++ b/src/vctrs.h @@ -225,9 +225,6 @@ enum vctrs_type2_s3 { VCTRS_TYPE2_S3_unknown_unknown }; -enum vctrs_type2 vec_typeof2(SEXP x, SEXP y); -const char* vctrs_type2_as_str(enum vctrs_type2 type); - extern SEXP vctrs_shared_empty_lgl; extern SEXP vctrs_shared_empty_int; extern SEXP vctrs_shared_empty_dbl; @@ -291,6 +288,7 @@ bool vec_is_unspecified(SEXP x); #include "subscript-loc.h" #include "subscript.h" #include "translate.h" +#include "typeof2.h" #include "utils-dispatch.h" #include "utils.h" From b7b5765e1869809509f3b16f5f94ee6de7c8be79 Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Mon, 5 Sep 2022 15:46:14 +0200 Subject: [PATCH 017/312] Update style of `typeof2-s3.c` --- R/type2.R | 2 +- src/decl/typeof2-s3-decl.h | 5 +++++ src/init.c | 4 ++-- src/typeof2-s3.c | 35 ++++++++++++++++------------------- src/typeof2-s3.h | 14 ++++++++++++++ src/typeof2.h | 2 -- src/vctrs.h | 1 + 7 files changed, 39 insertions(+), 24 deletions(-) create mode 100644 src/decl/typeof2-s3-decl.h create mode 100644 src/typeof2-s3.h diff --git a/R/type2.R b/R/type2.R index 4953fdabc..28e9c5d74 100644 --- a/R/type2.R +++ b/R/type2.R @@ -374,7 +374,7 @@ vec_typeof2 <- function(x, y) { } vec_typeof2_s3 <- function(x, y) { - .Call(vctrs_typeof2_s3, x, y) + .Call(ffi_typeof2_s3, x, y) } # https://github.com/r-lib/vctrs/issues/571 diff --git a/src/decl/typeof2-s3-decl.h b/src/decl/typeof2-s3-decl.h new file mode 100644 index 000000000..6f81b1c75 --- /dev/null +++ b/src/decl/typeof2-s3-decl.h @@ -0,0 +1,5 @@ +static +enum vctrs_type2_s3 vec_typeof2_s3_impl2(SEXP x, + SEXP y, + enum vctrs_type type_y, + int* left); diff --git a/src/init.c b/src/init.c index 62b8fe783..33fb3b734 100644 --- a/src/init.c +++ b/src/init.c @@ -43,7 +43,7 @@ extern SEXP vctrs_typeof(SEXP, SEXP); extern SEXP vctrs_is_vector(SEXP); extern r_obj* ffi_ptype2(r_obj*, r_obj*, r_obj*); extern r_obj* ffi_typeof2(r_obj*, r_obj*); -extern SEXP vctrs_typeof2_s3(SEXP, SEXP); +extern r_obj* ffi_typeof2_s3(r_obj*, r_obj*); extern r_obj* ffi_cast(r_obj*, r_obj*, r_obj*); extern r_obj* ffi_as_location(r_obj*, r_obj*, r_obj*, r_obj*, r_obj*, r_obj*, r_obj*, r_obj*); extern r_obj* ffi_slice(r_obj*, r_obj*, r_obj*); @@ -211,7 +211,7 @@ static const R_CallMethodDef CallEntries[] = { {"vctrs_is_vector", (DL_FUNC) &vctrs_is_vector, 1}, {"ffi_ptype2", (DL_FUNC) &ffi_ptype2, 3}, {"ffi_typeof2", (DL_FUNC) &ffi_typeof2, 2}, - {"vctrs_typeof2_s3", (DL_FUNC) &vctrs_typeof2_s3, 2}, + {"ffi_typeof2_s3", (DL_FUNC) &ffi_typeof2_s3, 2}, {"ffi_cast", (DL_FUNC) &ffi_cast, 3}, {"ffi_as_location", (DL_FUNC) &ffi_as_location, 8}, {"ffi_slice", (DL_FUNC) &ffi_slice, 3}, diff --git a/src/typeof2-s3.c b/src/typeof2-s3.c index 907b4cea9..fa67518bd 100644 --- a/src/typeof2-s3.c +++ b/src/typeof2-s3.c @@ -1,13 +1,8 @@ #include "vctrs.h" +#include "decl/typeof2-s3-decl.h" -static enum vctrs_type2_s3 vec_typeof2_s3_impl2(SEXP x, - SEXP y, - enum vctrs_type type_y, - int* left); - -// [[ include("ptype2.h") ]] -enum vctrs_type2_s3 vec_typeof2_s3_impl(SEXP x, - SEXP y, +enum vctrs_type2_s3 vec_typeof2_s3_impl(r_obj* x, + r_obj* y, enum vctrs_type type_x, enum vctrs_type type_y, int* left) { @@ -137,14 +132,15 @@ enum vctrs_type2_s3 vec_typeof2_s3_impl(SEXP x, return vec_typeof2_s3_impl2(x, y, type_y, left); }} - never_reached("vec_typeof2_s3_impl()"); + r_stop_unreachable(); } -static enum vctrs_type2_s3 vec_typeof2_s3_impl2(SEXP x, - SEXP y, - enum vctrs_type type_y, - int* left) { +static +enum vctrs_type2_s3 vec_typeof2_s3_impl2(r_obj* x, + r_obj* y, + enum vctrs_type type_y, + int* left) { switch (class_type(x)) { case VCTRS_CLASS_bare_factor: { switch (type_y) { @@ -322,14 +318,16 @@ static enum vctrs_type2_s3 vec_typeof2_s3_impl2(SEXP x, }} }} - never_reached("vec_typeof2_s3_impl2()"); + r_stop_unreachable(); } -enum vctrs_type2_s3 vec_typeof2_s3(SEXP x, SEXP y) { +static +enum vctrs_type2_s3 vec_typeof2_s3(r_obj* x, r_obj* y) { int _; return vec_typeof2_s3_impl(x, y, vec_typeof(x), vec_typeof(y), &_); } +static const char* vctrs_type2_s3_as_str(enum vctrs_type2_s3 type) { switch (type) { case VCTRS_TYPE2_S3_null_bare_factor: return "VCTRS_TYPE2_S3_null_bare_factor"; @@ -456,11 +454,10 @@ const char* vctrs_type2_s3_as_str(enum vctrs_type2_s3 type) { case VCTRS_TYPE2_S3_unknown_unknown: return "VCTRS_TYPE2_S3_unknown_unknown"; } - never_reached("vctrs_type2_s3_as_str"); + r_stop_unreachable(); } -// [[ register() ]] -SEXP vctrs_typeof2_s3(SEXP x, SEXP y) { +r_obj* ffi_typeof2_s3(r_obj* x, r_obj* y) { enum vctrs_type2_s3 type = vec_typeof2_s3(x, y); - return Rf_mkString(vctrs_type2_s3_as_str(type)); + return r_chr(vctrs_type2_s3_as_str(type)); } diff --git a/src/typeof2-s3.h b/src/typeof2-s3.h new file mode 100644 index 000000000..79f00fa0a --- /dev/null +++ b/src/typeof2-s3.h @@ -0,0 +1,14 @@ +#ifndef VCTRS_TYPEOF2_S3_H +#define VCTRS_TYPEOF2_S3_H + +#include "vctrs-core.h" + + +enum vctrs_type2_s3 vec_typeof2_s3_impl(r_obj* x, + r_obj* y, + enum vctrs_type type_x, + enum vctrs_type type_y, + int* left); + + +#endif diff --git a/src/typeof2.h b/src/typeof2.h index 0a815fe83..df312f455 100644 --- a/src/typeof2.h +++ b/src/typeof2.h @@ -8,8 +8,6 @@ enum vctrs_type2 vec_typeof2_impl(enum vctrs_type type_x, enum vctrs_type type_y, int* left); -enum vctrs_type2_s3 vec_typeof2_s3_impl(r_obj* x, r_obj* y, enum vctrs_type type_x, enum vctrs_type type_y, int* left); - enum vctrs_type2 vec_typeof2(r_obj* x, r_obj* y); const char* vctrs_type2_as_str(enum vctrs_type2 type); diff --git a/src/vctrs.h b/src/vctrs.h index f01e3fee6..33edb0a72 100644 --- a/src/vctrs.h +++ b/src/vctrs.h @@ -289,6 +289,7 @@ bool vec_is_unspecified(SEXP x); #include "subscript.h" #include "translate.h" #include "typeof2.h" +#include "typeof2-s3.h" #include "utils-dispatch.h" #include "utils.h" From 7bab381f295a294a411de86480051ea6dcef17bd Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Mon, 5 Sep 2022 15:50:22 +0200 Subject: [PATCH 018/312] Move `enum vctrs_type2` and friend to own header files --- src/typeof2-s3.h | 126 +++++++++++++++++++++++++++ src/typeof2.h | 93 ++++++++++++++++++++ src/vctrs.h | 219 ----------------------------------------------- 3 files changed, 219 insertions(+), 219 deletions(-) diff --git a/src/typeof2-s3.h b/src/typeof2-s3.h index 79f00fa0a..0fc41bea4 100644 --- a/src/typeof2-s3.h +++ b/src/typeof2-s3.h @@ -4,6 +4,132 @@ #include "vctrs-core.h" +enum vctrs_type2_s3 { + VCTRS_TYPE2_S3_null_bare_factor, + VCTRS_TYPE2_S3_null_bare_ordered, + VCTRS_TYPE2_S3_null_bare_date, + VCTRS_TYPE2_S3_null_bare_posixct, + VCTRS_TYPE2_S3_null_bare_posixlt, + VCTRS_TYPE2_S3_null_bare_tibble, + VCTRS_TYPE2_S3_null_unknown, + + VCTRS_TYPE2_S3_unspecified_bare_factor, + VCTRS_TYPE2_S3_unspecified_bare_ordered, + VCTRS_TYPE2_S3_unspecified_bare_date, + VCTRS_TYPE2_S3_unspecified_bare_posixct, + VCTRS_TYPE2_S3_unspecified_bare_posixlt, + VCTRS_TYPE2_S3_unspecified_bare_tibble, + VCTRS_TYPE2_S3_unspecified_unknown, + + VCTRS_TYPE2_S3_logical_bare_factor, + VCTRS_TYPE2_S3_logical_bare_ordered, + VCTRS_TYPE2_S3_logical_bare_date, + VCTRS_TYPE2_S3_logical_bare_posixct, + VCTRS_TYPE2_S3_logical_bare_posixlt, + VCTRS_TYPE2_S3_logical_bare_tibble, + VCTRS_TYPE2_S3_logical_unknown, + + VCTRS_TYPE2_S3_integer_bare_factor, + VCTRS_TYPE2_S3_integer_bare_ordered, + VCTRS_TYPE2_S3_integer_bare_date, + VCTRS_TYPE2_S3_integer_bare_posixct, + VCTRS_TYPE2_S3_integer_bare_posixlt, + VCTRS_TYPE2_S3_integer_bare_tibble, + VCTRS_TYPE2_S3_integer_unknown, + + VCTRS_TYPE2_S3_double_bare_factor, + VCTRS_TYPE2_S3_double_bare_ordered, + VCTRS_TYPE2_S3_double_bare_date, + VCTRS_TYPE2_S3_double_bare_posixct, + VCTRS_TYPE2_S3_double_bare_posixlt, + VCTRS_TYPE2_S3_double_bare_tibble, + VCTRS_TYPE2_S3_double_unknown, + + VCTRS_TYPE2_S3_complex_bare_factor, + VCTRS_TYPE2_S3_complex_bare_ordered, + VCTRS_TYPE2_S3_complex_bare_date, + VCTRS_TYPE2_S3_complex_bare_posixct, + VCTRS_TYPE2_S3_complex_bare_posixlt, + VCTRS_TYPE2_S3_complex_bare_tibble, + VCTRS_TYPE2_S3_complex_unknown, + + VCTRS_TYPE2_S3_character_bare_factor, + VCTRS_TYPE2_S3_character_bare_ordered, + VCTRS_TYPE2_S3_character_bare_date, + VCTRS_TYPE2_S3_character_bare_posixct, + VCTRS_TYPE2_S3_character_bare_posixlt, + VCTRS_TYPE2_S3_character_bare_tibble, + VCTRS_TYPE2_S3_character_unknown, + + VCTRS_TYPE2_S3_raw_bare_factor, + VCTRS_TYPE2_S3_raw_bare_ordered, + VCTRS_TYPE2_S3_raw_bare_date, + VCTRS_TYPE2_S3_raw_bare_posixct, + VCTRS_TYPE2_S3_raw_bare_posixlt, + VCTRS_TYPE2_S3_raw_bare_tibble, + VCTRS_TYPE2_S3_raw_unknown, + + VCTRS_TYPE2_S3_list_bare_factor, + VCTRS_TYPE2_S3_list_bare_ordered, + VCTRS_TYPE2_S3_list_bare_date, + VCTRS_TYPE2_S3_list_bare_posixct, + VCTRS_TYPE2_S3_list_bare_posixlt, + VCTRS_TYPE2_S3_list_bare_tibble, + VCTRS_TYPE2_S3_list_unknown, + + VCTRS_TYPE2_S3_dataframe_bare_factor, + VCTRS_TYPE2_S3_dataframe_bare_ordered, + VCTRS_TYPE2_S3_dataframe_bare_date, + VCTRS_TYPE2_S3_dataframe_bare_posixct, + VCTRS_TYPE2_S3_dataframe_bare_posixlt, + VCTRS_TYPE2_S3_dataframe_bare_tibble, + VCTRS_TYPE2_S3_dataframe_unknown, + + VCTRS_TYPE2_S3_scalar_bare_factor, + VCTRS_TYPE2_S3_scalar_bare_ordered, + VCTRS_TYPE2_S3_scalar_bare_date, + VCTRS_TYPE2_S3_scalar_bare_posixct, + VCTRS_TYPE2_S3_scalar_bare_posixlt, + VCTRS_TYPE2_S3_scalar_bare_tibble, + VCTRS_TYPE2_S3_scalar_unknown, + + VCTRS_TYPE2_S3_bare_factor_bare_factor, + VCTRS_TYPE2_S3_bare_factor_bare_ordered, + VCTRS_TYPE2_S3_bare_factor_bare_date, + VCTRS_TYPE2_S3_bare_factor_bare_posixct, + VCTRS_TYPE2_S3_bare_factor_bare_posixlt, + VCTRS_TYPE2_S3_bare_factor_bare_tibble, + VCTRS_TYPE2_S3_bare_factor_unknown, + + VCTRS_TYPE2_S3_bare_ordered_bare_ordered, + VCTRS_TYPE2_S3_bare_ordered_bare_date, + VCTRS_TYPE2_S3_bare_ordered_bare_posixct, + VCTRS_TYPE2_S3_bare_ordered_bare_posixlt, + VCTRS_TYPE2_S3_bare_ordered_bare_tibble, + VCTRS_TYPE2_S3_bare_ordered_unknown, + + VCTRS_TYPE2_S3_bare_date_bare_date, + VCTRS_TYPE2_S3_bare_date_bare_posixct, + VCTRS_TYPE2_S3_bare_date_bare_posixlt, + VCTRS_TYPE2_S3_bare_date_bare_tibble, + VCTRS_TYPE2_S3_bare_date_unknown, + + VCTRS_TYPE2_S3_bare_posixct_bare_posixct, + VCTRS_TYPE2_S3_bare_posixct_bare_posixlt, + VCTRS_TYPE2_S3_bare_posixct_bare_tibble, + VCTRS_TYPE2_S3_bare_posixct_unknown, + + VCTRS_TYPE2_S3_bare_posixlt_bare_posixlt, + VCTRS_TYPE2_S3_bare_posixlt_bare_tibble, + VCTRS_TYPE2_S3_bare_posixlt_unknown, + + VCTRS_TYPE2_S3_bare_tibble_bare_tibble, + VCTRS_TYPE2_S3_bare_tibble_unknown, + + VCTRS_TYPE2_S3_unknown_unknown +}; + + enum vctrs_type2_s3 vec_typeof2_s3_impl(r_obj* x, r_obj* y, enum vctrs_type type_x, diff --git a/src/typeof2.h b/src/typeof2.h index df312f455..de339177b 100644 --- a/src/typeof2.h +++ b/src/typeof2.h @@ -4,6 +4,99 @@ #include "vctrs-core.h" +enum vctrs_type2 { + VCTRS_TYPE2_null_null, + VCTRS_TYPE2_null_unspecified, + VCTRS_TYPE2_null_logical, + VCTRS_TYPE2_null_integer, + VCTRS_TYPE2_null_double, + VCTRS_TYPE2_null_complex, + VCTRS_TYPE2_null_character, + VCTRS_TYPE2_null_raw, + VCTRS_TYPE2_null_list, + VCTRS_TYPE2_null_dataframe, + VCTRS_TYPE2_null_s3, + VCTRS_TYPE2_null_scalar, + + VCTRS_TYPE2_unspecified_unspecified, + VCTRS_TYPE2_unspecified_logical, + VCTRS_TYPE2_unspecified_integer, + VCTRS_TYPE2_unspecified_double, + VCTRS_TYPE2_unspecified_complex, + VCTRS_TYPE2_unspecified_character, + VCTRS_TYPE2_unspecified_raw, + VCTRS_TYPE2_unspecified_list, + VCTRS_TYPE2_unspecified_dataframe, + VCTRS_TYPE2_unspecified_s3, + VCTRS_TYPE2_unspecified_scalar, + + VCTRS_TYPE2_logical_logical, + VCTRS_TYPE2_logical_integer, + VCTRS_TYPE2_logical_double, + VCTRS_TYPE2_logical_complex, + VCTRS_TYPE2_logical_character, + VCTRS_TYPE2_logical_raw, + VCTRS_TYPE2_logical_list, + VCTRS_TYPE2_logical_dataframe, + VCTRS_TYPE2_logical_s3, + VCTRS_TYPE2_logical_scalar, + + VCTRS_TYPE2_integer_integer, + VCTRS_TYPE2_integer_double, + VCTRS_TYPE2_integer_complex, + VCTRS_TYPE2_integer_character, + VCTRS_TYPE2_integer_raw, + VCTRS_TYPE2_integer_list, + VCTRS_TYPE2_integer_dataframe, + VCTRS_TYPE2_integer_s3, + VCTRS_TYPE2_integer_scalar, + + VCTRS_TYPE2_double_double, + VCTRS_TYPE2_double_complex, + VCTRS_TYPE2_double_character, + VCTRS_TYPE2_double_raw, + VCTRS_TYPE2_double_list, + VCTRS_TYPE2_double_dataframe, + VCTRS_TYPE2_double_s3, + VCTRS_TYPE2_double_scalar, + + VCTRS_TYPE2_complex_complex, + VCTRS_TYPE2_complex_character, + VCTRS_TYPE2_complex_raw, + VCTRS_TYPE2_complex_list, + VCTRS_TYPE2_complex_dataframe, + VCTRS_TYPE2_complex_s3, + VCTRS_TYPE2_complex_scalar, + + VCTRS_TYPE2_character_character, + VCTRS_TYPE2_character_raw, + VCTRS_TYPE2_character_list, + VCTRS_TYPE2_character_dataframe, + VCTRS_TYPE2_character_s3, + VCTRS_TYPE2_character_scalar, + + VCTRS_TYPE2_raw_raw, + VCTRS_TYPE2_raw_list, + VCTRS_TYPE2_raw_dataframe, + VCTRS_TYPE2_raw_s3, + VCTRS_TYPE2_raw_scalar, + + VCTRS_TYPE2_list_list, + VCTRS_TYPE2_list_dataframe, + VCTRS_TYPE2_list_s3, + VCTRS_TYPE2_list_scalar, + + VCTRS_TYPE2_dataframe_dataframe, + VCTRS_TYPE2_dataframe_s3, + VCTRS_TYPE2_dataframe_scalar, + + VCTRS_TYPE2_S3_s3, + VCTRS_TYPE2_S3_scalar, + + VCTRS_TYPE2_scalar_scalar +}; + + enum vctrs_type2 vec_typeof2_impl(enum vctrs_type type_x, enum vctrs_type type_y, int* left); diff --git a/src/vctrs.h b/src/vctrs.h index 33edb0a72..cccfa86a8 100644 --- a/src/vctrs.h +++ b/src/vctrs.h @@ -6,225 +6,6 @@ // Vector types ------------------------------------------------- -// After adding a new `vctrs_dispatch` type, add the missing entries -// in `vec_typeof2()` -enum vctrs_type2 { - VCTRS_TYPE2_null_null, - VCTRS_TYPE2_null_unspecified, - VCTRS_TYPE2_null_logical, - VCTRS_TYPE2_null_integer, - VCTRS_TYPE2_null_double, - VCTRS_TYPE2_null_complex, - VCTRS_TYPE2_null_character, - VCTRS_TYPE2_null_raw, - VCTRS_TYPE2_null_list, - VCTRS_TYPE2_null_dataframe, - VCTRS_TYPE2_null_s3, - VCTRS_TYPE2_null_scalar, - - VCTRS_TYPE2_unspecified_unspecified, - VCTRS_TYPE2_unspecified_logical, - VCTRS_TYPE2_unspecified_integer, - VCTRS_TYPE2_unspecified_double, - VCTRS_TYPE2_unspecified_complex, - VCTRS_TYPE2_unspecified_character, - VCTRS_TYPE2_unspecified_raw, - VCTRS_TYPE2_unspecified_list, - VCTRS_TYPE2_unspecified_dataframe, - VCTRS_TYPE2_unspecified_s3, - VCTRS_TYPE2_unspecified_scalar, - - VCTRS_TYPE2_logical_logical, - VCTRS_TYPE2_logical_integer, - VCTRS_TYPE2_logical_double, - VCTRS_TYPE2_logical_complex, - VCTRS_TYPE2_logical_character, - VCTRS_TYPE2_logical_raw, - VCTRS_TYPE2_logical_list, - VCTRS_TYPE2_logical_dataframe, - VCTRS_TYPE2_logical_s3, - VCTRS_TYPE2_logical_scalar, - - VCTRS_TYPE2_integer_integer, - VCTRS_TYPE2_integer_double, - VCTRS_TYPE2_integer_complex, - VCTRS_TYPE2_integer_character, - VCTRS_TYPE2_integer_raw, - VCTRS_TYPE2_integer_list, - VCTRS_TYPE2_integer_dataframe, - VCTRS_TYPE2_integer_s3, - VCTRS_TYPE2_integer_scalar, - - VCTRS_TYPE2_double_double, - VCTRS_TYPE2_double_complex, - VCTRS_TYPE2_double_character, - VCTRS_TYPE2_double_raw, - VCTRS_TYPE2_double_list, - VCTRS_TYPE2_double_dataframe, - VCTRS_TYPE2_double_s3, - VCTRS_TYPE2_double_scalar, - - VCTRS_TYPE2_complex_complex, - VCTRS_TYPE2_complex_character, - VCTRS_TYPE2_complex_raw, - VCTRS_TYPE2_complex_list, - VCTRS_TYPE2_complex_dataframe, - VCTRS_TYPE2_complex_s3, - VCTRS_TYPE2_complex_scalar, - - VCTRS_TYPE2_character_character, - VCTRS_TYPE2_character_raw, - VCTRS_TYPE2_character_list, - VCTRS_TYPE2_character_dataframe, - VCTRS_TYPE2_character_s3, - VCTRS_TYPE2_character_scalar, - - VCTRS_TYPE2_raw_raw, - VCTRS_TYPE2_raw_list, - VCTRS_TYPE2_raw_dataframe, - VCTRS_TYPE2_raw_s3, - VCTRS_TYPE2_raw_scalar, - - VCTRS_TYPE2_list_list, - VCTRS_TYPE2_list_dataframe, - VCTRS_TYPE2_list_s3, - VCTRS_TYPE2_list_scalar, - - VCTRS_TYPE2_dataframe_dataframe, - VCTRS_TYPE2_dataframe_s3, - VCTRS_TYPE2_dataframe_scalar, - - VCTRS_TYPE2_S3_s3, - VCTRS_TYPE2_S3_scalar, - - VCTRS_TYPE2_scalar_scalar -}; - -enum vctrs_type2_s3 { - VCTRS_TYPE2_S3_null_bare_factor, - VCTRS_TYPE2_S3_null_bare_ordered, - VCTRS_TYPE2_S3_null_bare_date, - VCTRS_TYPE2_S3_null_bare_posixct, - VCTRS_TYPE2_S3_null_bare_posixlt, - VCTRS_TYPE2_S3_null_bare_tibble, - VCTRS_TYPE2_S3_null_unknown, - - VCTRS_TYPE2_S3_unspecified_bare_factor, - VCTRS_TYPE2_S3_unspecified_bare_ordered, - VCTRS_TYPE2_S3_unspecified_bare_date, - VCTRS_TYPE2_S3_unspecified_bare_posixct, - VCTRS_TYPE2_S3_unspecified_bare_posixlt, - VCTRS_TYPE2_S3_unspecified_bare_tibble, - VCTRS_TYPE2_S3_unspecified_unknown, - - VCTRS_TYPE2_S3_logical_bare_factor, - VCTRS_TYPE2_S3_logical_bare_ordered, - VCTRS_TYPE2_S3_logical_bare_date, - VCTRS_TYPE2_S3_logical_bare_posixct, - VCTRS_TYPE2_S3_logical_bare_posixlt, - VCTRS_TYPE2_S3_logical_bare_tibble, - VCTRS_TYPE2_S3_logical_unknown, - - VCTRS_TYPE2_S3_integer_bare_factor, - VCTRS_TYPE2_S3_integer_bare_ordered, - VCTRS_TYPE2_S3_integer_bare_date, - VCTRS_TYPE2_S3_integer_bare_posixct, - VCTRS_TYPE2_S3_integer_bare_posixlt, - VCTRS_TYPE2_S3_integer_bare_tibble, - VCTRS_TYPE2_S3_integer_unknown, - - VCTRS_TYPE2_S3_double_bare_factor, - VCTRS_TYPE2_S3_double_bare_ordered, - VCTRS_TYPE2_S3_double_bare_date, - VCTRS_TYPE2_S3_double_bare_posixct, - VCTRS_TYPE2_S3_double_bare_posixlt, - VCTRS_TYPE2_S3_double_bare_tibble, - VCTRS_TYPE2_S3_double_unknown, - - VCTRS_TYPE2_S3_complex_bare_factor, - VCTRS_TYPE2_S3_complex_bare_ordered, - VCTRS_TYPE2_S3_complex_bare_date, - VCTRS_TYPE2_S3_complex_bare_posixct, - VCTRS_TYPE2_S3_complex_bare_posixlt, - VCTRS_TYPE2_S3_complex_bare_tibble, - VCTRS_TYPE2_S3_complex_unknown, - - VCTRS_TYPE2_S3_character_bare_factor, - VCTRS_TYPE2_S3_character_bare_ordered, - VCTRS_TYPE2_S3_character_bare_date, - VCTRS_TYPE2_S3_character_bare_posixct, - VCTRS_TYPE2_S3_character_bare_posixlt, - VCTRS_TYPE2_S3_character_bare_tibble, - VCTRS_TYPE2_S3_character_unknown, - - VCTRS_TYPE2_S3_raw_bare_factor, - VCTRS_TYPE2_S3_raw_bare_ordered, - VCTRS_TYPE2_S3_raw_bare_date, - VCTRS_TYPE2_S3_raw_bare_posixct, - VCTRS_TYPE2_S3_raw_bare_posixlt, - VCTRS_TYPE2_S3_raw_bare_tibble, - VCTRS_TYPE2_S3_raw_unknown, - - VCTRS_TYPE2_S3_list_bare_factor, - VCTRS_TYPE2_S3_list_bare_ordered, - VCTRS_TYPE2_S3_list_bare_date, - VCTRS_TYPE2_S3_list_bare_posixct, - VCTRS_TYPE2_S3_list_bare_posixlt, - VCTRS_TYPE2_S3_list_bare_tibble, - VCTRS_TYPE2_S3_list_unknown, - - VCTRS_TYPE2_S3_dataframe_bare_factor, - VCTRS_TYPE2_S3_dataframe_bare_ordered, - VCTRS_TYPE2_S3_dataframe_bare_date, - VCTRS_TYPE2_S3_dataframe_bare_posixct, - VCTRS_TYPE2_S3_dataframe_bare_posixlt, - VCTRS_TYPE2_S3_dataframe_bare_tibble, - VCTRS_TYPE2_S3_dataframe_unknown, - - VCTRS_TYPE2_S3_scalar_bare_factor, - VCTRS_TYPE2_S3_scalar_bare_ordered, - VCTRS_TYPE2_S3_scalar_bare_date, - VCTRS_TYPE2_S3_scalar_bare_posixct, - VCTRS_TYPE2_S3_scalar_bare_posixlt, - VCTRS_TYPE2_S3_scalar_bare_tibble, - VCTRS_TYPE2_S3_scalar_unknown, - - VCTRS_TYPE2_S3_bare_factor_bare_factor, - VCTRS_TYPE2_S3_bare_factor_bare_ordered, - VCTRS_TYPE2_S3_bare_factor_bare_date, - VCTRS_TYPE2_S3_bare_factor_bare_posixct, - VCTRS_TYPE2_S3_bare_factor_bare_posixlt, - VCTRS_TYPE2_S3_bare_factor_bare_tibble, - VCTRS_TYPE2_S3_bare_factor_unknown, - - VCTRS_TYPE2_S3_bare_ordered_bare_ordered, - VCTRS_TYPE2_S3_bare_ordered_bare_date, - VCTRS_TYPE2_S3_bare_ordered_bare_posixct, - VCTRS_TYPE2_S3_bare_ordered_bare_posixlt, - VCTRS_TYPE2_S3_bare_ordered_bare_tibble, - VCTRS_TYPE2_S3_bare_ordered_unknown, - - VCTRS_TYPE2_S3_bare_date_bare_date, - VCTRS_TYPE2_S3_bare_date_bare_posixct, - VCTRS_TYPE2_S3_bare_date_bare_posixlt, - VCTRS_TYPE2_S3_bare_date_bare_tibble, - VCTRS_TYPE2_S3_bare_date_unknown, - - VCTRS_TYPE2_S3_bare_posixct_bare_posixct, - VCTRS_TYPE2_S3_bare_posixct_bare_posixlt, - VCTRS_TYPE2_S3_bare_posixct_bare_tibble, - VCTRS_TYPE2_S3_bare_posixct_unknown, - - VCTRS_TYPE2_S3_bare_posixlt_bare_posixlt, - VCTRS_TYPE2_S3_bare_posixlt_bare_tibble, - VCTRS_TYPE2_S3_bare_posixlt_unknown, - - VCTRS_TYPE2_S3_bare_tibble_bare_tibble, - VCTRS_TYPE2_S3_bare_tibble_unknown, - - VCTRS_TYPE2_S3_unknown_unknown -}; - extern SEXP vctrs_shared_empty_lgl; extern SEXP vctrs_shared_empty_int; extern SEXP vctrs_shared_empty_dbl; From 52dbb00f33597b78fc40de84094f0bca0542f508 Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Mon, 5 Sep 2022 15:53:13 +0200 Subject: [PATCH 019/312] Use rlang globals --- src/bind.c | 6 +++--- src/c-unchop.c | 2 +- src/cast.c | 2 +- src/fill.c | 2 +- src/globals.h | 10 ++++++++++ src/interval.c | 4 ++-- src/match.c | 10 +++++----- src/missing.c | 2 +- src/names.c | 2 +- src/order-groups.c | 2 +- src/order-truelength.c | 10 +++++----- src/ptype.c | 18 +++++++++--------- src/ptype2-dispatch.c | 4 ++-- src/ptype2.c | 14 +++++++------- src/rep.c | 6 +++--- src/size.c | 2 +- src/strides.h | 2 +- src/subscript-loc.c | 8 ++++---- src/subscript.c | 14 +++++++------- src/type-data-frame.c | 8 ++++---- src/type-date-time.c | 2 +- src/type-factor.c | 2 +- src/unspecified.c | 2 +- src/utils.c | 22 ---------------------- src/vctrs.h | 17 ----------------- 25 files changed, 72 insertions(+), 101 deletions(-) diff --git a/src/bind.c b/src/bind.c index 4e8ddb018..a55be0860 100644 --- a/src/bind.c +++ b/src/bind.c @@ -77,7 +77,7 @@ r_obj* vec_rbind(r_obj* xs, if (ptype == r_null) { FREE(n_prot); - return new_data_frame(vctrs_shared_empty_list, 0); + return new_data_frame(r_globals.empty_list, 0); } if (r_typeof(ptype) == R_TYPE_logical && !n_cols) { ptype = as_df_row_impl(vctrs_shared_na_lgl, @@ -343,7 +343,7 @@ r_obj* cbind_names_to(bool has_names, r_obj* names_to, r_obj* ptype, struct r_lazy call) { - r_obj* index_ptype = has_names ? vctrs_shared_empty_chr : vctrs_shared_empty_int; + r_obj* index_ptype = has_names ? r_globals.empty_chr : r_globals.empty_int; r_obj* tmp = KEEP(r_alloc_list(2)); r_list_poke(tmp, 0, index_ptype); @@ -406,7 +406,7 @@ r_obj* vec_cbind(r_obj* xs, p_arg, call)); if (type == r_null) { - type = new_data_frame(vctrs_shared_empty_list, 0); + type = new_data_frame(r_globals.empty_list, 0); } else if (!is_data_frame(type)) { type = r_as_data_frame(type); } diff --git a/src/c-unchop.c b/src/c-unchop.c index 66c477b94..351bc9211 100644 --- a/src/c-unchop.c +++ b/src/c-unchop.c @@ -219,7 +219,7 @@ static SEXP vec_unchop_fallback(SEXP ptype, indices = PROTECT(vec_c( indices, - vctrs_shared_empty_int, + r_globals.empty_int, R_NilValue, &name_repair_opts )); diff --git a/src/cast.c b/src/cast.c index 1a38fea79..5c3c29ef4 100644 --- a/src/cast.c +++ b/src/cast.c @@ -138,7 +138,7 @@ r_obj* vec_cast_default(r_obj* x, syms_x_arg, p_x_arg, syms_to_arg, p_to_arg, syms_call, ffi_call, - syms_from_dispatch, vctrs_shared_true, + syms_from_dispatch, r_true, syms_df_fallback, df_fallback, syms_s3_fallback, s3_fallback); FREE(3); diff --git a/src/fill.c b/src/fill.c index 6764a1974..6c01f10dd 100644 --- a/src/fill.c +++ b/src/fill.c @@ -249,7 +249,7 @@ int parse_max_fill(r_obj* x) { } x = KEEP(vec_cast(x, - vctrs_shared_empty_int, + r_globals.empty_int, vec_args.max_fill, vec_args.empty, r_lazy_null)); diff --git a/src/globals.h b/src/globals.h index b955de079..d0673f823 100644 --- a/src/globals.h +++ b/src/globals.h @@ -2,6 +2,7 @@ #define VCTRS_GLOBALS_H #include +#include "globals.h" #include "rlang-dev.h" struct syms { @@ -61,4 +62,13 @@ extern struct fns fns; extern struct vec_args vec_args; extern struct lazy_calls lazy_calls; + +extern r_obj* vctrs_shared_empty_date; +extern r_obj* vctrs_shared_empty_uns; + +extern Rcomplex vctrs_shared_na_cpl; +extern r_obj* vctrs_shared_na_lgl; +extern r_obj* vctrs_shared_na_list; + + #endif diff --git a/src/interval.c b/src/interval.c index 975194ef4..6aff5ba65 100644 --- a/src/interval.c +++ b/src/interval.c @@ -439,8 +439,8 @@ r_obj* vec_interval_complement(r_obj* start, // - `lower > upper` is an invalid interval. // - `lower = upper` will always result in an empty complement. r_obj* out = KEEP_N(r_new_list(2), &n_prot); - r_list_poke(out, 0, vec_slice_unsafe(start, vctrs_shared_empty_int)); - r_list_poke(out, 1, vec_slice_unsafe(end, vctrs_shared_empty_int)); + r_list_poke(out, 0, vec_slice_unsafe(start, r_globals.empty_int)); + r_list_poke(out, 1, vec_slice_unsafe(end, r_globals.empty_int)); r_obj* out_names = r_new_character(2); r_attrib_poke_names(out, out_names); diff --git a/src/match.c b/src/match.c index 9696109e3..5b5afd8d0 100644 --- a/src/match.c +++ b/src/match.c @@ -1341,7 +1341,7 @@ struct vctrs_incomplete parse_incomplete(r_obj* incomplete, incomplete = vec_cast( incomplete, - vctrs_shared_empty_int, + r_globals.empty_int, args_incomplete, vec_args.empty, call @@ -1461,7 +1461,7 @@ struct vctrs_no_match parse_no_match(r_obj* no_match, no_match = vec_cast( no_match, - vctrs_shared_empty_int, + r_globals.empty_int, args_no_match, vec_args.empty, call @@ -1512,7 +1512,7 @@ struct vctrs_remaining parse_remaining(r_obj* remaining, remaining = vec_cast( remaining, - vctrs_shared_empty_int, + r_globals.empty_int, args_remaining, vec_args.empty, call @@ -2002,7 +2002,7 @@ r_obj* compute_nesting_container_info(r_obj* haystack, if (!any_non_equi) { // Container info isn't required for only `==` r_list_poke(out, 0, vec_order(haystack, chrs_asc, chrs_smallest, true, r_null)); - r_list_poke(out, 1, vctrs_shared_empty_int); + r_list_poke(out, 1, r_globals.empty_int); r_list_poke(out, 2, r_int(1)); r_list_poke(out, 3, r_lgl(any_non_equi)); FREE(n_prot); @@ -2107,7 +2107,7 @@ r_obj* compute_nesting_container_info(r_obj* haystack, // that is already in nested containment order. In that case, original // haystack ordering is sufficient and we don't need the ids. r_list_poke(out, 0, o_haystack); - r_list_poke(out, 1, vctrs_shared_empty_int); + r_list_poke(out, 1, r_globals.empty_int); r_list_poke(out, 2, r_int(1)); r_list_poke(out, 3, r_lgl(any_non_equi)); FREE(n_prot); diff --git a/src/missing.c b/src/missing.c index a97edd041..84333c90f 100644 --- a/src/missing.c +++ b/src/missing.c @@ -28,7 +28,7 @@ r_obj* proxy_equal_na(r_obj* proxy) { case VCTRS_TYPE_character: return chr_equal_na(proxy); case VCTRS_TYPE_list: return list_equal_na(proxy); case VCTRS_TYPE_dataframe: return df_equal_na(proxy); - case VCTRS_TYPE_null: return vctrs_shared_empty_lgl; + case VCTRS_TYPE_null: return r_globals.empty_lgl; case VCTRS_TYPE_scalar: stop_scalar_type(proxy, vec_args.empty, r_lazy_null); default: stop_unimplemented_vctrs_type("vec_equal_na", type); } diff --git a/src/names.c b/src/names.c index 402eede55..e86d01569 100644 --- a/src/names.c +++ b/src/names.c @@ -528,7 +528,7 @@ r_obj* apply_name_spec(r_obj* name_spec, r_obj* outer, r_obj* inner, r_ssize n) if (r_is_empty_names(inner)) { if (n == 0) { - return vctrs_shared_empty_chr; + return r_globals.empty_chr; } if (n == 1) { return r_str_as_character(outer); diff --git a/src/order-groups.c b/src/order-groups.c index 8507edfb9..2bd270c6f 100644 --- a/src/order-groups.c +++ b/src/order-groups.c @@ -21,7 +21,7 @@ struct group_info* new_group_info() { p_group_info->self = self; p_group_info->data_size = 0; - p_group_info->data = vctrs_shared_empty_int; + p_group_info->data = r_globals.empty_int; p_group_info->n_groups = 0; p_group_info->max_group_size = 0; diff --git a/src/order-truelength.c b/src/order-truelength.c index a9cbe2d7b..6208a9712 100644 --- a/src/order-truelength.c +++ b/src/order-truelength.c @@ -33,17 +33,17 @@ struct truelength_info* new_truelength_info(r_ssize n_max) { p_truelength_info->self = self; - p_truelength_info->strings = vctrs_shared_empty_chr; - p_truelength_info->truelengths = vctrs_shared_empty_raw; + p_truelength_info->strings = r_globals.empty_chr; + p_truelength_info->truelengths = r_globals.empty_raw; p_truelength_info->n_strings_alloc = 0; p_truelength_info->n_strings_used = 0; - p_truelength_info->uniques = vctrs_shared_empty_chr; + p_truelength_info->uniques = r_globals.empty_chr; p_truelength_info->n_uniques_alloc = 0; p_truelength_info->n_uniques_used = 0; - p_truelength_info->sizes = vctrs_shared_empty_int; - p_truelength_info->sizes_aux = vctrs_shared_empty_int; + p_truelength_info->sizes = r_globals.empty_int; + p_truelength_info->sizes_aux = r_globals.empty_int; p_truelength_info->n_sizes_alloc = 0; p_truelength_info->n_sizes_used = 0; p_truelength_info->max_string_size = 0; diff --git a/src/ptype.c b/src/ptype.c index 8dc1895aa..38e82f4f5 100644 --- a/src/ptype.c +++ b/src/ptype.c @@ -14,13 +14,13 @@ r_obj* vec_ptype(r_obj* x, struct vctrs_arg* x_arg, struct r_lazy call) { switch (vec_typeof(x)) { case VCTRS_TYPE_null: return r_null; case VCTRS_TYPE_unspecified: return vctrs_shared_empty_uns; - case VCTRS_TYPE_logical: return vec_ptype_slice(x, vctrs_shared_empty_lgl); - case VCTRS_TYPE_integer: return vec_ptype_slice(x, vctrs_shared_empty_int); - case VCTRS_TYPE_double: return vec_ptype_slice(x, vctrs_shared_empty_dbl); - case VCTRS_TYPE_complex: return vec_ptype_slice(x, vctrs_shared_empty_cpl); - case VCTRS_TYPE_character: return vec_ptype_slice(x, vctrs_shared_empty_chr); - case VCTRS_TYPE_raw: return vec_ptype_slice(x, vctrs_shared_empty_raw); - case VCTRS_TYPE_list: return vec_ptype_slice(x, vctrs_shared_empty_list); + case VCTRS_TYPE_logical: return vec_ptype_slice(x, r_globals.empty_lgl); + case VCTRS_TYPE_integer: return vec_ptype_slice(x, r_globals.empty_int); + case VCTRS_TYPE_double: return vec_ptype_slice(x, r_globals.empty_dbl); + case VCTRS_TYPE_complex: return vec_ptype_slice(x, r_globals.empty_cpl); + case VCTRS_TYPE_character: return vec_ptype_slice(x, r_globals.empty_chr); + case VCTRS_TYPE_raw: return vec_ptype_slice(x, r_globals.empty_raw); + case VCTRS_TYPE_list: return vec_ptype_slice(x, r_globals.empty_list); case VCTRS_TYPE_dataframe: return df_ptype(x, true); case VCTRS_TYPE_s3: return s3_ptype(x, x_arg, call); case VCTRS_TYPE_scalar: stop_scalar_type(x, x_arg, call); @@ -107,7 +107,7 @@ r_obj* df_ptype(r_obj* x, bool bare) { } if (r_typeof(row_nms) == R_TYPE_character) { - r_attrib_poke(ptype, r_syms.row_names, vctrs_shared_empty_chr); + r_attrib_poke(ptype, r_syms.row_names, r_globals.empty_chr); } FREE(2); @@ -177,7 +177,7 @@ r_obj* vec_ptype_finalise_unspecified(r_obj* x) { r_ssize size = r_length(x); if (size == 0) { - return vctrs_shared_empty_lgl; + return r_globals.empty_lgl; } r_obj* out = KEEP(r_alloc_logical(size)); diff --git a/src/ptype2-dispatch.c b/src/ptype2-dispatch.c index 81a2d5c8e..e6a709ae4 100644 --- a/src/ptype2-dispatch.c +++ b/src/ptype2-dispatch.c @@ -15,7 +15,7 @@ r_obj* vec_ptype2_dispatch_native(const struct ptype2_opts* opts, switch (type2_s3) { case VCTRS_TYPE2_S3_character_bare_factor: case VCTRS_TYPE2_S3_character_bare_ordered: - return vctrs_shared_empty_chr; + return r_globals.empty_chr; case VCTRS_TYPE2_S3_bare_factor_bare_factor: return fct_ptype2(opts); @@ -63,7 +63,7 @@ r_obj* vec_ptype2_default(r_obj* x, syms_x_arg, ffi_x_arg, syms_y_arg, ffi_y_arg, syms_call, ffi_call, - syms_from_dispatch, vctrs_shared_true, + syms_from_dispatch, r_true, syms_df_fallback, df_fallback_obj, syms_s3_fallback, s3_fallback_obj); diff --git a/src/ptype2.c b/src/ptype2.c index 9a7919d22..e3cd974d3 100644 --- a/src/ptype2.c +++ b/src/ptype2.c @@ -109,30 +109,30 @@ r_obj* vec_ptype2_switch_native(const struct ptype2_opts* opts, return r_null; case VCTRS_TYPE2_logical_logical: - return vec_shaped_ptype(vctrs_shared_empty_lgl, x, y, x_arg, y_arg); + return vec_shaped_ptype(r_globals.empty_lgl, x, y, x_arg, y_arg); case VCTRS_TYPE2_logical_integer: case VCTRS_TYPE2_integer_integer: - return vec_shaped_ptype(vctrs_shared_empty_int, x, y, x_arg, y_arg); + return vec_shaped_ptype(r_globals.empty_int, x, y, x_arg, y_arg); case VCTRS_TYPE2_logical_double: case VCTRS_TYPE2_integer_double: case VCTRS_TYPE2_double_double: - return vec_shaped_ptype(vctrs_shared_empty_dbl, x, y, x_arg, y_arg); + return vec_shaped_ptype(r_globals.empty_dbl, x, y, x_arg, y_arg); case VCTRS_TYPE2_integer_complex: case VCTRS_TYPE2_double_complex: case VCTRS_TYPE2_complex_complex: - return vec_shaped_ptype(vctrs_shared_empty_cpl, x, y, x_arg, y_arg); + return vec_shaped_ptype(r_globals.empty_cpl, x, y, x_arg, y_arg); case VCTRS_TYPE2_character_character: - return vec_shaped_ptype(vctrs_shared_empty_chr, x, y, x_arg, y_arg); + return vec_shaped_ptype(r_globals.empty_chr, x, y, x_arg, y_arg); case VCTRS_TYPE2_raw_raw: - return vec_shaped_ptype(vctrs_shared_empty_raw, x, y, x_arg, y_arg); + return vec_shaped_ptype(r_globals.empty_raw, x, y, x_arg, y_arg); case VCTRS_TYPE2_list_list: - return vec_shaped_ptype(vctrs_shared_empty_list, x, y, x_arg, y_arg); + return vec_shaped_ptype(r_globals.empty_list, x, y, x_arg, y_arg); case VCTRS_TYPE2_dataframe_dataframe: return df_ptype2(opts); diff --git a/src/rep.c b/src/rep.c index 2b49d456a..12da92671 100644 --- a/src/rep.c +++ b/src/rep.c @@ -23,7 +23,7 @@ SEXP vctrs_rep(SEXP x, SEXP times) { struct r_lazy call = r_lazy_null; times = PROTECT(vec_cast(times, - vctrs_shared_empty_int, + r_globals.empty_int, args_times, vec_args.empty, call)); @@ -91,7 +91,7 @@ static SEXP vec_rep_each_impl(SEXP x, SEXP times, const R_len_t times_size); static SEXP vec_rep_each(SEXP x, SEXP times) { times = PROTECT(vec_cast(times, - vctrs_shared_empty_int, + r_globals.empty_int, args_times, vec_args.empty, r_lazy_null)); @@ -321,7 +321,7 @@ SEXP vec_unrep(SEXP x) { r_ssize x_size = r_length(id); if (x_size == 0) { - SEXP out = new_unrep_data_frame(x, vctrs_shared_empty_int, 0); + SEXP out = new_unrep_data_frame(x, r_globals.empty_int, 0); UNPROTECT(1); return out; } diff --git a/src/size.c b/src/size.c index 2a78be4ce..30eabb0a3 100644 --- a/src/size.c +++ b/src/size.c @@ -194,7 +194,7 @@ r_obj* ffi_recycle(r_obj* x, struct r_lazy recycle_call = { .x = frame, .env = r_null }; size_obj = KEEP(vec_cast(size_obj, - vctrs_shared_empty_int, + r_globals.empty_int, vec_args.empty, vec_args.empty, recycle_call)); diff --git a/src/strides.h b/src/strides.h index 6b4224d45..399a92b7f 100644 --- a/src/strides.h +++ b/src/strides.h @@ -165,7 +165,7 @@ static inline struct strides_info new_strides_info(SEXP x, SEXP index) { // need to put something in the struct SEXP steps; if (is_compact(index)) { - steps = vctrs_shared_empty_int; + steps = r_globals.empty_int; } else { steps = vec_steps(p_index, index_n); } diff --git a/src/subscript-loc.c b/src/subscript-loc.c index b945dabb5..5c6b95e95 100644 --- a/src/subscript-loc.c +++ b/src/subscript-loc.c @@ -43,7 +43,7 @@ r_obj* vec_as_location_opts(r_obj* subscript, r_obj* out = r_null; switch (r_typeof(subscript)) { - case R_TYPE_null: out = vctrs_shared_empty_int; break; + case R_TYPE_null: out = r_globals.empty_int; break; case R_TYPE_logical: out = lgl_as_location(subscript, n, opts); break; case R_TYPE_integer: out = int_as_location(subscript, n, opts); break; case R_TYPE_double: out = dbl_as_location(subscript, n, opts); break; @@ -100,7 +100,7 @@ r_obj* lgl_as_location(r_obj* subscript, out = KEEP(r_alloc_integer(n)); r_int_fill_seq(out, 1, n); } else { - return vctrs_shared_empty_int; + return r_globals.empty_int; } r_obj* nms = KEEP(r_names(subscript)); @@ -364,7 +364,7 @@ r_obj* dbl_as_location(r_obj* subscript, r_ssize n, const struct location_opts* opts) { subscript = KEEP(vec_cast(subscript, - vctrs_shared_empty_int, + r_globals.empty_int, vec_args.empty, vec_args.empty, r_lazy_null)); @@ -429,7 +429,7 @@ r_obj* ffi_as_location(r_obj* subscript, } else { if (r_is_object(ffi_n) || r_typeof(ffi_n) != R_TYPE_integer) { ffi_n = vec_cast(ffi_n, - vctrs_shared_empty_int, + r_globals.empty_int, vec_args.n, vec_args.empty, (struct r_lazy) { .x = frame, .env = r_null }); diff --git a/src/subscript.c b/src/subscript.c index 2ea0ea829..99c99e77b 100644 --- a/src/subscript.c +++ b/src/subscript.c @@ -18,7 +18,7 @@ r_obj* vec_as_subscript_opts(r_obj* subscript, switch (r_typeof(subscript)) { case R_TYPE_null: if (opts->numeric == SUBSCRIPT_TYPE_ACTION_CAST) { - subscript = vctrs_shared_empty_int; + subscript = r_globals.empty_int; } break; case R_TYPE_symbol: @@ -55,13 +55,13 @@ r_obj* vec_as_subscript_opts(r_obj* subscript, struct vctrs_arg* arg = opts->subscript_arg; if (opts->numeric == SUBSCRIPT_TYPE_ACTION_CAST) { subscript = vec_cast(subscript, - vctrs_shared_empty_int, + r_globals.empty_int, arg, NULL, r_lazy_null); } else { subscript = vec_cast(subscript, - vctrs_shared_empty_chr, + r_globals.empty_chr, arg, NULL, r_lazy_null); @@ -111,17 +111,17 @@ r_obj* obj_cast_subscript(r_obj* subscript, .p_x_arg = opts->subscript_arg }; - ptype2_opts.y = cast_opts.to = vctrs_shared_empty_lgl; + ptype2_opts.y = cast_opts.to = r_globals.empty_lgl; if (vec_is_coercible(&ptype2_opts, &dir)) { return vec_cast_opts(&cast_opts); } - ptype2_opts.y = cast_opts.to = vctrs_shared_empty_int; + ptype2_opts.y = cast_opts.to = r_globals.empty_int; if (vec_is_coercible(&ptype2_opts, &dir)) { return vec_cast_opts(&cast_opts); } - ptype2_opts.y = cast_opts.to = vctrs_shared_empty_chr; + ptype2_opts.y = cast_opts.to = r_globals.empty_chr; if (vec_is_coercible(&ptype2_opts, &dir)) { return vec_cast_opts(&cast_opts); } @@ -178,7 +178,7 @@ r_obj* dbl_cast_subscript_fallback(r_obj* subscript, ERR* err) { struct cast_opts cast_opts = { .x = subscript, - .to = vctrs_shared_empty_int, + .to = r_globals.empty_int, opts->subscript_arg }; r_obj* out = KEEP(vec_cast_e(&cast_opts, err)); diff --git a/src/type-data-frame.c b/src/type-data-frame.c index c189427c4..8bb263ec5 100644 --- a/src/type-data-frame.c +++ b/src/type-data-frame.c @@ -85,7 +85,7 @@ r_obj* ffi_new_data_frame(r_obj* args) { // Take names from `x` if `attrib` doesn't have any if (!has_names) { - r_obj* nms = vctrs_shared_empty_chr; + r_obj* nms = r_globals.empty_chr; if (r_length(out)) { nms = r_names(out); } @@ -457,7 +457,7 @@ void init_tibble(r_obj* x, r_ssize n) { static void init_bare_data_frame(r_obj* x, r_ssize n) { if (r_length(x) == 0) { - r_attrib_poke(x, r_syms.names, vctrs_shared_empty_chr); + r_attrib_poke(x, r_syms.names, r_globals.empty_chr); } init_compact_rownames(x, n); @@ -473,7 +473,7 @@ void init_compact_rownames(r_obj* x, r_ssize n) { static r_obj* new_compact_rownames(r_ssize n) { if (n <= 0) { - return vctrs_shared_empty_int; + return r_globals.empty_int; } r_obj* out = r_alloc_integer(2); @@ -744,7 +744,7 @@ r_obj* df_cast_match(const struct cast_opts* opts, // `base_c_invoke()`. if (opts->fallback.s3 && vec_is_common_class_fallback(to_col)) { KEEP(col); - r_attrib_poke(col, r_sym("vctrs:::unspecified"), vctrs_shared_true); + r_attrib_poke(col, r_sym("vctrs:::unspecified"), r_true); FREE(1); } } else { diff --git a/src/type-date-time.c b/src/type-date-time.c index 0885c8c62..d419586c5 100644 --- a/src/type-date-time.c +++ b/src/type-date-time.c @@ -322,7 +322,7 @@ static SEXP new_datetime(SEXP x, SEXP tzone) { static SEXP new_empty_datetime(SEXP tzone) { - return new_datetime(vctrs_shared_empty_dbl, tzone); + return new_datetime(r_globals.empty_dbl, tzone); } // ----------------------------------------------------------------------------- diff --git a/src/type-factor.c b/src/type-factor.c index 3c2bc45eb..3606e113a 100644 --- a/src/type-factor.c +++ b/src/type-factor.c @@ -75,7 +75,7 @@ static SEXP levels_union(SEXP x, SEXP y) { // No name repair because this is just combining factor levels SEXP xy = PROTECT(vec_c( args, - vctrs_shared_empty_chr, + r_globals.empty_chr, R_NilValue, &name_repair_opts )); diff --git a/src/unspecified.c b/src/unspecified.c index 10ed334df..c49b468e0 100644 --- a/src/unspecified.c +++ b/src/unspecified.c @@ -24,7 +24,7 @@ SEXP vctrs_unspecified(SEXP n) { } if (TYPEOF(n) != INTSXP) { n = vec_cast(n, - vctrs_shared_empty_int, + r_globals.empty_int, vec_args.empty, vec_args.empty, r_lazy_null); diff --git a/src/utils.c b/src/utils.c index 9f8564da3..caed38ba4 100644 --- a/src/utils.c +++ b/src/utils.c @@ -1490,16 +1490,7 @@ bool vctrs_debug_verbose = false; SEXP vctrs_ns_env = NULL; SEXP vctrs_shared_empty_str = NULL; -SEXP vctrs_shared_empty_lgl = NULL; -SEXP vctrs_shared_empty_int = NULL; -SEXP vctrs_shared_empty_dbl = NULL; -SEXP vctrs_shared_empty_cpl = NULL; -SEXP vctrs_shared_empty_chr = NULL; -SEXP vctrs_shared_empty_raw = NULL; -SEXP vctrs_shared_empty_list = NULL; SEXP vctrs_shared_empty_date = NULL; -SEXP vctrs_shared_true = NULL; -SEXP vctrs_shared_false = NULL; Rcomplex vctrs_shared_na_cpl; SEXP vctrs_shared_na_lgl = NULL; @@ -1807,22 +1798,9 @@ void vctrs_init_utils(SEXP ns) { SET_STRING_ELT(classes_vctrs_group_rle, 2, Rf_mkChar("vctrs_vctr")); - vctrs_shared_empty_lgl = r_new_shared_vector(LGLSXP, 0); - vctrs_shared_empty_int = r_new_shared_vector(INTSXP, 0); - vctrs_shared_empty_dbl = r_new_shared_vector(REALSXP, 0); - vctrs_shared_empty_cpl = r_new_shared_vector(CPLXSXP, 0); - vctrs_shared_empty_chr = r_new_shared_vector(STRSXP, 0); - vctrs_shared_empty_raw = r_new_shared_vector(RAWSXP, 0); - vctrs_shared_empty_list = r_new_shared_vector(VECSXP, 0); vctrs_shared_empty_date = r_new_shared_vector(REALSXP, 0); Rf_setAttrib(vctrs_shared_empty_date, R_ClassSymbol, classes_date); - vctrs_shared_true = r_new_shared_vector(LGLSXP, 1); - LOGICAL(vctrs_shared_true)[0] = 1; - - vctrs_shared_false = r_new_shared_vector(LGLSXP, 1); - LOGICAL(vctrs_shared_false)[0] = 0; - vctrs_shared_na_cpl.i = NA_REAL; vctrs_shared_na_cpl.r = NA_REAL; diff --git a/src/vctrs.h b/src/vctrs.h index cccfa86a8..5d0a1d8e4 100644 --- a/src/vctrs.h +++ b/src/vctrs.h @@ -6,23 +6,6 @@ // Vector types ------------------------------------------------- -extern SEXP vctrs_shared_empty_lgl; -extern SEXP vctrs_shared_empty_int; -extern SEXP vctrs_shared_empty_dbl; -extern SEXP vctrs_shared_empty_cpl; -extern SEXP vctrs_shared_empty_chr; -extern SEXP vctrs_shared_empty_raw; -extern SEXP vctrs_shared_empty_list; -extern SEXP vctrs_shared_empty_date; -extern SEXP vctrs_shared_empty_uns; - -extern SEXP vctrs_shared_true; -extern SEXP vctrs_shared_false; - -extern Rcomplex vctrs_shared_na_cpl; -extern SEXP vctrs_shared_na_lgl; -extern SEXP vctrs_shared_na_list; - SEXP vec_unspecified(R_len_t n); bool vec_is_unspecified(SEXP x); From adbbfd10a36b82ae969e1eaa2e940e21d6ae33f3 Mon Sep 17 00:00:00 2001 From: Davis Vaughan Date: Tue, 6 Sep 2022 15:52:49 -0400 Subject: [PATCH 020/312] Implement internal `vec_interval_locate_containers()` for ivs (#1644) --- R/interval.R | 77 ++++++++++-- src/decl/interval-decl.h | 9 +- src/init.c | 2 + src/interval.c | 187 ++++++++++++++++++++++++++++-- tests/testthat/_snaps/interval.md | 9 ++ tests/testthat/test-interval.R | 113 ++++++++++++++++++ 6 files changed, 376 insertions(+), 21 deletions(-) diff --git a/R/interval.R b/R/interval.R index 740936105..3a35661d2 100644 --- a/R/interval.R +++ b/R/interval.R @@ -34,10 +34,10 @@ #' If any of these assumptions are invalid, then the result is undefined. #' #' Developer note: These assumptions stem from the idea that if these functions -#' were in iv itself, then we could safely make these assumptions in the C code, -#' because the `iv()` helper would assert them for us ahead of time. Trying to -#' re-assert these checks in the C code here is wasteful and makes the code -#' more complex. +#' were in ivs itself, then we could safely make these assumptions in the C +#' code, because the `iv()` helper would assert them for us ahead of time. +#' Trying to re-assert these checks in the C code here is wasteful and makes the +#' code more complex. #' #' @inheritParams rlang::args_dots_empty #' @@ -176,16 +176,70 @@ vec_interval_complement <- function(start, # ------------------------------------------------------------------------------ -# Experimental shims of interval functions used by other packages (mainly, iv). +#' Interval containers +#' +#' @description +#' `vec_interval_locate_containers()` locates interval _containers_. Containers +#' are defined as the widest intervals that aren't contained by any other +#' interval. The returned locations will arrange the containers in ascending +#' order. +#' +#' For example, with the following vector of intervals: `[1, 5), [2, 6), [3, 4), +#' [5, 9), [5, 8)`, the containers are: `[1, 5), [2, 6), [5, 9)`. The intervals +#' `[3, 4)` and `[5, 8)` aren't containers because they are completely contained +#' within at least one other interval. Note that containers can partially +#' overlap, i.e. `[1, 5)` and `[2, 6)`, and multiple containers can contain the +#' same intervals, i.e. both `[1, 5)` and `[2, 6)` contain `[3, 4)`. +#' +#' Missing intervals are placed into their own container at the end, separate +#' from all other intervals. +#' +#' These functions require that `start < end`. Additionally, intervals are +#' treated as if they are right-open, i.e. `[start, end)`. +#' +#' @inheritSection interval-groups Assumptions +#' +#' @param start,end +#' A pair of vectors representing the starts and ends of the intervals. +#' +#' It is required that `start < end`. +#' +#' `start` and `end` will be cast to their common type, and must have the same +#' size. +#' +#' @return +#' An integer vector that represents the locations of the containers in `start` +#' and `end`. +#' +#' @examples +#' x <- data_frame( +#' start = c(10, 0, NA, 3, 2, 2, NA, 11), +#' end = c(12, 5, NA, 5, 6, 6, NA, 12) +#' ) +#' x +#' +#' loc <- vec_interval_locate_containers(x$start, x$end) +#' loc +#' +#' vec_slice(x, loc) +#' +#' @noRd +vec_interval_locate_containers <- function(start, end) { + .Call(ffi_interval_locate_containers, start, end) +} + +# ------------------------------------------------------------------------------ + +# Experimental shims of interval functions used by other packages (mainly, ivs). # # This gives us the freedom to experiment with the signature of these functions -# while being backwards compatible with iv in the meantime. +# while being backwards compatible with ivs in the meantime. # # We can remove these after: # - The interval functions are exported -# - iv updates to use them directly +# - ivs updates to use them directly # - A short deprecation period goes by that allows users time to update their -# version of iv +# version of ivs exp_vec_interval_groups <- function(start, end, @@ -228,3 +282,10 @@ exp_vec_interval_complement <- function(start, upper = upper ) } + +exp_vec_interval_locate_containers <- function(start, end) { + vec_interval_locate_containers( + start = start, + end = end + ) +} diff --git a/src/decl/interval-decl.h b/src/decl/interval-decl.h index ad122f01c..8739073c3 100644 --- a/src/decl/interval-decl.h +++ b/src/decl/interval-decl.h @@ -23,8 +23,15 @@ r_obj* vec_interval_complement(r_obj* start, r_obj* lower, r_obj* upper); +static +r_obj* vec_interval_locate_containers(r_obj* start, r_obj* end); + static inline -r_obj* interval_order(r_obj* start, r_obj* end, r_ssize size); +r_obj* interval_order(r_obj* start, + r_obj* end, + r_obj* direction, + r_obj* na_value, + r_ssize size); static inline enum vctrs_interval_missing parse_missing(r_obj* missing); diff --git a/src/init.c b/src/init.c index 33fb3b734..ec8b45b2b 100644 --- a/src/init.c +++ b/src/init.c @@ -144,6 +144,7 @@ extern r_obj* ffi_locate_matches(r_obj*, r_obj*, r_obj*, r_obj*, r_obj*, r_obj*, extern r_obj* ffi_interval_groups(r_obj*, r_obj*, r_obj*, r_obj*); extern r_obj* ffi_interval_locate_groups(r_obj*, r_obj*, r_obj*, r_obj*); extern r_obj* ffi_interval_complement(r_obj*, r_obj*, r_obj*, r_obj*); +extern r_obj* ffi_interval_locate_containers(r_obj*, r_obj*); extern r_obj* ffi_check_list(r_obj*, r_obj*); extern r_obj* ffi_list_all_vectors(r_obj*, r_obj*); extern r_obj* ffi_list_check_all_vectors(r_obj*, r_obj*); @@ -314,6 +315,7 @@ static const R_CallMethodDef CallEntries[] = { {"ffi_interval_groups", (DL_FUNC) &ffi_interval_groups, 4}, {"ffi_interval_locate_groups", (DL_FUNC) &ffi_interval_locate_groups, 4}, {"ffi_interval_complement", (DL_FUNC) &ffi_interval_complement, 4}, + {"ffi_interval_locate_containers", (DL_FUNC) &ffi_interval_locate_containers, 2}, {"ffi_check_list", (DL_FUNC) &ffi_check_list, 2}, {"ffi_list_all_vectors", (DL_FUNC) &ffi_list_all_vectors, 2}, {"ffi_list_check_all_vectors", (DL_FUNC) &ffi_list_check_all_vectors, 2}, diff --git a/src/interval.c b/src/interval.c index 6aff5ba65..8824f4804 100644 --- a/src/interval.c +++ b/src/interval.c @@ -9,7 +9,6 @@ enum vctrs_interval_missing { // ----------------------------------------------------------------------------- -// [[ register() ]] r_obj* ffi_interval_groups(r_obj* start, r_obj* end, r_obj* ffi_abutting, @@ -30,7 +29,6 @@ r_obj* ffi_interval_groups(r_obj* start, return out; } -// [[ register() ]] r_obj* ffi_interval_locate_groups(r_obj* start, r_obj* end, r_obj* ffi_abutting, @@ -136,7 +134,14 @@ r_obj* vec_interval_group_info(r_obj* start, // Order is computed as ascending order, placing missing intervals up front // as the "smallest" values. We document that we assume that if `start` is // missing, then `end` is missing too. - r_obj* order = KEEP_N(interval_order(start_proxy, end_proxy, size), &n_prot); + r_obj* order = interval_order( + start_proxy, + end_proxy, + chrs_asc, + chrs_smallest, + size + ); + KEEP_N(order, &n_prot); const int* v_order = r_int_cbegin(order); // Assume the intervals can be merged into half their original size. @@ -298,7 +303,6 @@ r_obj* vec_interval_group_info(r_obj* start, // ----------------------------------------------------------------------------- -// [[ register() ]] r_obj* ffi_interval_complement(r_obj* start, r_obj* end, r_obj* lower, @@ -715,16 +719,175 @@ r_obj* vec_interval_complement(r_obj* start, // ----------------------------------------------------------------------------- +r_obj* ffi_interval_locate_containers(r_obj* start, r_obj* end) { + return vec_interval_locate_containers(start, end); +} + +static +r_obj* vec_interval_locate_containers(r_obj* start, r_obj* end) { + int n_prot = 0; + + int _; + r_obj* ptype = vec_ptype2_params( + start, + end, + args_start, + args_end, + r_lazy_null, + DF_FALLBACK_quiet, + &_ + ); + KEEP_N(ptype, &n_prot); + + start = vec_cast_params( + start, + ptype, + args_start, + vec_args.empty, + r_lazy_null, + DF_FALLBACK_quiet, + S3_FALLBACK_false + ); + KEEP_N(start, &n_prot); + + end = vec_cast_params( + end, + ptype, + args_end, + vec_args.empty, + r_lazy_null, + DF_FALLBACK_quiet, + S3_FALLBACK_false + ); + KEEP_N(end, &n_prot); + + r_obj* start_proxy = KEEP_N(vec_proxy_compare(start), &n_prot); + start_proxy = KEEP_N(vec_normalize_encoding(start_proxy), &n_prot); + + r_obj* end_proxy = KEEP_N(vec_proxy_compare(end), &n_prot); + end_proxy = KEEP_N(vec_normalize_encoding(end_proxy), &n_prot); + + const enum vctrs_type type_proxy = vec_proxy_typeof(start_proxy); + + struct poly_vec* p_poly_start = new_poly_vec(start_proxy, type_proxy); + PROTECT_POLY_VEC(p_poly_start, &n_prot); + const void* p_start = p_poly_start->p_vec; + + struct poly_vec* p_poly_end = new_poly_vec(end_proxy, type_proxy); + PROTECT_POLY_VEC(p_poly_end, &n_prot); + const void* p_end = p_poly_end->p_vec; + + const poly_binary_int_fn_ptr fn_compare = new_poly_p_compare_na_equal(type_proxy); + const poly_unary_bool_fn_ptr fn_is_missing = new_poly_p_is_missing(type_proxy); + + const r_ssize size = vec_size(start_proxy); + + if (size != vec_size(end_proxy)) { + r_abort("`start` and `end` must have the same size."); + } + + // Order is computed with the first column in ascending order, and the + // second column in descending order. This makes it easy to find the + // containers, as any time we detect something that isn't contained in the + // current container, it must be a new container. Missing intervals are up + // front for easy detection. We document that we assume that if `start` is + // missing, then `end` is missing too. + r_obj* direction = KEEP_N(r_new_character(2), &n_prot); + r_chr_poke(direction, 0, r_str("asc")); + r_chr_poke(direction, 1, r_str("desc")); + + r_obj* na_value = KEEP_N(r_new_character(2), &n_prot); + r_chr_poke(na_value, 0, r_str("smallest")); + r_chr_poke(na_value, 1, r_str("largest")); + + r_obj* order = interval_order( + start_proxy, + end_proxy, + direction, + na_value, + size + ); + KEEP_N(order, &n_prot); + const int* v_order = r_int_cbegin(order); + + // Assume that half the intervals are containers. + // This is probably a little high. + // Apply a minimum size to avoid a size of zero. + const r_ssize initial_size = r_ssize_max(size / 2, 1); + + struct r_dyn_array* p_loc = r_new_dyn_vector(R_TYPE_integer, initial_size); + KEEP_N(p_loc->shelter, &n_prot); + + r_ssize i = 0; + bool any_missing = false; + + // Move `i` past any missing intervals (they are at the front), + // recording if there are any missing intervals for later. Only need to check + // missingness of `start`, because we document that we assume that `end` + // is missing if `start` is missing. + for (; i < size; ++i) { + const r_ssize loc = v_order[i] - 1; + + if (!fn_is_missing(p_start, loc)) { + break; + } + + any_missing = true; + } + + r_ssize loc_container = -1; + + if (i < size) { + // Set information about first usable container + const r_ssize loc = v_order[i] - 1; + loc_container = loc; + r_dyn_int_push_back(p_loc, loc_container + 1); + ++i; + } + + for (; i < size; ++i) { + const r_ssize loc = v_order[i] - 1; + + if ((fn_compare(p_start, loc_container, p_start, loc) != 1) && + (fn_compare(p_end, loc_container, p_end, loc) != -1)) { + // Still in current container + continue; + } + + // New container + loc_container = loc; + r_dyn_int_push_back(p_loc, loc_container + 1); + } + + if (any_missing) { + // Push missing container as the last container. + // We know missings are at the front, so just use the first order value + // as the location. This matches ascending ordering with missing values + // at the end, and breaking ties with the first missing location we saw. + r_dyn_int_push_back(p_loc, v_order[0]); + } + + r_obj* out = r_dyn_unwrap(p_loc); + + FREE(n_prot); + return out; +} + +// ----------------------------------------------------------------------------- + /* * `interval_order()` orders the `start` and `end` values of a vector of - * intervals in ascending order. It places missing intervals at the front. - * We document that we make the assumption that if `start` is missing, then - * `end` is also missing. We also document the assumption that partially missing - * (i.e. incomplete but not missing) observations are not allowed in either - * bound. + * intervals. We document that we make the assumption that if `start` is + * missing, then `end` is also missing. We also document the assumption that + * partially missing (i.e. incomplete but not missing) observations are not + * allowed in either bound. */ static inline -r_obj* interval_order(r_obj* start, r_obj* end, r_ssize size) { +r_obj* interval_order(r_obj* start, + r_obj* end, + r_obj* direction, + r_obj* na_value, + r_ssize size) { // Put them in a data frame to compute joint ordering r_obj* df = KEEP(r_new_list(2)); r_list_poke(df, 0, start); @@ -742,8 +905,8 @@ r_obj* interval_order(r_obj* start, r_obj* end, r_ssize size) { r_obj* out = vec_order( df, - chrs_asc, - chrs_smallest, + direction, + na_value, nan_distinct, chr_proxy_collate ); diff --git a/tests/testthat/_snaps/interval.md b/tests/testthat/_snaps/interval.md index 433b872d9..e1531c989 100644 --- a/tests/testthat/_snaps/interval.md +++ b/tests/testthat/_snaps/interval.md @@ -25,6 +25,15 @@ Error: ! Can't combine `start` and `end` . +--- + + Code + (expect_error(vec_interval_locate_containers(1, "x"))) + Output + + Error: + ! Can't combine `start` and `end` . + # `lower` and `upper` can't contain missing values Code diff --git a/tests/testthat/test-interval.R b/tests/testthat/test-interval.R index 20d181508..239950f31 100644 --- a/tests/testthat/test-interval.R +++ b/tests/testthat/test-interval.R @@ -554,3 +554,116 @@ test_that("`lower` and `upper` can't contain missing values", { (expect_error(vec_interval_complement(start, end, upper = data_frame(x = 1, y = NA)))) }) }) + +# ------------------------------------------------------------------------------ +# vec_interval_locate_containers() + +test_that("can locate containers", { + x <- data_frame( + start = c(1L, 9L, 2L, 2L, 10L), + end = c(5L, 12L, 6L, 8L, 12L) + ) + + expect_identical( + vec_interval_locate_containers(x$start, x$end), + c(1L, 4L, 2L) + ) +}) + +test_that("can locate containers with size one input", { + x <- data_frame(start = 1L, end = 2L) + + expect_identical( + vec_interval_locate_containers(x$start, x$end), + 1L + ) +}) + +test_that("can locate containers with size zero input", { + x <- data_frame(start = integer(), end = integer()) + + expect_identical( + vec_interval_locate_containers(x$start, x$end), + integer() + ) +}) + +test_that("missing intervals are retained", { + x <- data_frame(start = NA, end = NA) + + expect_identical( + vec_interval_locate_containers(x$start, x$end), + 1L + ) + + x <- data_frame(start = c(NA, NA), end = c(NA, NA)) + + # Ties use first missing value seen + expect_identical( + vec_interval_locate_containers(x$start, x$end), + 1L + ) + + x <- data_frame(start = c(3, NA, 2, NA), end = c(5, NA, 5, NA)) + + # Missing intervals at the end + expect_identical( + vec_interval_locate_containers(x$start, x$end), + c(3L, 2L) + ) +}) + +test_that("locations order the intervals", { + x <- data_frame(start = c(4L, 4L, 1L, NA, 4L), end = c(5L, 6L, 2L, NA, 6L)) + + out <- vec_interval_locate_containers(x$start, x$end) + + expect_identical( + out, + c(3L, 2L, 4L) + ) + + # This orders `x` + expect_identical( + vec_slice(x, out), + vec_sort(vec_slice(x, out)) + ) +}) + +test_that("treats NA and NaN as equivalent with doubles", { + x <- data_frame(start = c(NA, NaN, NA, NaN), end = c(NA, NA, NaN, NaN)) + + expect_identical(vec_interval_locate_containers(x$start, x$end), 1L) +}) + +test_that("recognizes missing rows in data frames", { + start <- data_frame(year = c(2019, NA, NA, 2019, 2019), month = c(12, NA, NA, 12, 12)) + end <- data_frame(year = c(2020, NA, NA, 2020, 2020), month = c(2, NA, NA, 11, 12)) + x <- data_frame(start = start, end = end) + + expect_identical( + vec_interval_locate_containers(x$start, x$end), + c(5L, 2L) + ) +}) + +test_that("duplicate containers return the first", { + x <- data_frame(start = c(1, 1, 2, 1, 2), end = c(2, 2, 3, 2, 3)) + expect_identical(vec_interval_locate_containers(x$start, x$end), c(1L, 3L)) +}) + +test_that("works on various types", { + x <- data_frame(start = c(1.5, 3, NA, 1.6, NA), end = c(1.7, 3.1, NA, 3.2, NA)) + + out <- vec_interval_locate_containers(x$start, x$end) + expect_identical(out, c(1L, 4L, 3L)) + + x <- data_frame(start = c("a", "a", NA, "f", NA), end = c("b", "g", NA, "h", NA)) + + out <- vec_interval_locate_containers(x$start, x$end) + expect_identical(out, c(2L, 4L, 3L)) +}) + +test_that("common type is taken", { + expect_snapshot((expect_error(vec_interval_locate_containers(1, "x")))) +}) From 88ceda2cadfdd05bc636ecb213454dce2d6b9e68 Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Wed, 7 Sep 2022 10:08:38 +0200 Subject: [PATCH 021/312] Update style in `proxy-restore.c` --- R/proxy.R | 6 +- R/type-data-frame.R | 2 +- src/bind.c | 2 +- src/decl/proxy-restore-decl.h | 5 + src/init.c | 12 +- src/names.c | 4 +- src/proxy-restore.c | 238 +++++++++++++++++----------------- src/proxy-restore.h | 12 ++ src/type-data-frame.c | 12 +- src/type-data-frame.h | 6 +- src/vctrs.h | 6 +- 11 files changed, 156 insertions(+), 149 deletions(-) create mode 100644 src/decl/proxy-restore-decl.h create mode 100644 src/proxy-restore.h diff --git a/R/proxy.R b/R/proxy.R index be61c6210..742b97b43 100644 --- a/R/proxy.R +++ b/R/proxy.R @@ -156,7 +156,7 @@ vec_proxy.default <- function(x, ...) { #' @export vec_restore <- function(x, to, ..., n = NULL) { check_dots_empty0(...) - return(.Call(vctrs_restore, x, to, n)) + return(.Call(ffi_restore, x, to, n)) UseMethod("vec_restore", to) } vec_restore_dispatch <- function(x, to, ..., n = NULL) { @@ -164,10 +164,10 @@ vec_restore_dispatch <- function(x, to, ..., n = NULL) { } #' @export vec_restore.default <- function(x, to, ..., n = NULL) { - .Call(vctrs_restore_default, x, to) + .Call(ffi_restore_default, x, to) } vec_restore_default <- function(x, to, ...) { - .Call(vctrs_restore_default, x, to) + .Call(ffi_restore_default, x, to) } #' Extract underlying data diff --git a/R/type-data-frame.R b/R/type-data-frame.R index 9e00c994b..7bd6c7ca0 100644 --- a/R/type-data-frame.R +++ b/R/type-data-frame.R @@ -485,7 +485,7 @@ vec_cast.data.frame.data.frame <- function(x, to, ..., x_arg = "", to_arg = "") #' @export vec_restore.data.frame <- function(x, to, ..., n = NULL) { - .Call(vctrs_bare_df_restore, x, to, n) + .Call(ffi_bare_df_restore, x, to, n) } # Helpers ----------------------------------------------------------------- diff --git a/src/bind.c b/src/bind.c index a55be0860..6d4edde3d 100644 --- a/src/bind.c +++ b/src/bind.c @@ -533,7 +533,7 @@ r_obj* cbind_container_type(r_obj* x, void* data) { if (is_data_frame(x)) { r_obj* rn = df_rownames(x); - if (rownames_type(rn) == ROWNAMES_IDENTIFIERS) { + if (rownames_type(rn) == ROWNAMES_TYPE_identifiers) { r_obj** learned_rn_p = (r_obj**) data; r_obj* learned_rn = *learned_rn_p; diff --git a/src/decl/proxy-restore-decl.h b/src/decl/proxy-restore-decl.h new file mode 100644 index 000000000..2c80d31c6 --- /dev/null +++ b/src/decl/proxy-restore-decl.h @@ -0,0 +1,5 @@ +static r_obj* syms_vec_restore_dispatch; +static r_obj* fns_vec_restore_dispatch; + +static +r_obj* vec_restore_dispatch(r_obj* x, r_obj* to, r_obj* n); diff --git a/src/init.c b/src/init.c index ec8b45b2b..89b971d3f 100644 --- a/src/init.c +++ b/src/init.c @@ -53,8 +53,8 @@ extern SEXP vctrs_unchop(SEXP, SEXP, SEXP, SEXP, SEXP); extern SEXP vctrs_chop_seq(SEXP, SEXP, SEXP, SEXP); extern r_obj* ffi_slice_seq(r_obj*, r_obj*, r_obj*, r_obj*); extern r_obj* ffi_slice_rep(r_obj*, r_obj*, r_obj*); -extern SEXP vctrs_restore(SEXP, SEXP, SEXP); -extern SEXP vctrs_restore_default(SEXP, SEXP); +extern r_obj* ffi_restore(r_obj*, r_obj*, r_obj*); +extern r_obj* ffi_restore_default(r_obj*, r_obj*); extern SEXP vec_proxy(SEXP); extern SEXP vec_proxy_equal(SEXP); extern SEXP vec_proxy_compare(SEXP); @@ -75,7 +75,7 @@ extern r_obj* ffi_df_ptype2_opts(r_obj*, r_obj*, r_obj*, r_obj*); extern r_obj* ffi_type_info(r_obj*); extern SEXP ffi_proxy_info(SEXP); extern r_obj* ffi_class_type(r_obj*); -extern SEXP vctrs_bare_df_restore(SEXP, SEXP, SEXP); +extern r_obj* ffi_bare_df_restore(r_obj*, r_obj*, r_obj*); extern r_obj* ffi_recycle(r_obj*, r_obj*, r_obj*); extern r_obj* ffi_assign(r_obj*, r_obj*, r_obj*, r_obj*); extern r_obj* ffi_assign_seq(r_obj*, r_obj*, r_obj*, r_obj*, r_obj*); @@ -222,8 +222,8 @@ static const R_CallMethodDef CallEntries[] = { {"vctrs_chop_seq", (DL_FUNC) &vctrs_chop_seq, 4}, {"ffi_slice_seq", (DL_FUNC) &ffi_slice_seq, 4}, {"ffi_slice_rep", (DL_FUNC) &ffi_slice_rep, 3}, - {"vctrs_restore", (DL_FUNC) &vctrs_restore, 3}, - {"vctrs_restore_default", (DL_FUNC) &vctrs_restore_default, 2}, + {"ffi_restore", (DL_FUNC) &ffi_restore, 3}, + {"ffi_restore_default", (DL_FUNC) &ffi_restore_default, 2}, {"vctrs_proxy", (DL_FUNC) &vec_proxy, 1}, {"vctrs_proxy_equal", (DL_FUNC) &vec_proxy_equal, 1}, {"vctrs_proxy_compare", (DL_FUNC) &vec_proxy_compare, 1}, @@ -244,7 +244,7 @@ static const R_CallMethodDef CallEntries[] = { {"ffi_type_info", (DL_FUNC) &ffi_type_info, 1}, {"ffi_proxy_info", (DL_FUNC) &ffi_proxy_info, 1}, {"ffi_class_type", (DL_FUNC) &ffi_class_type, 1}, - {"vctrs_bare_df_restore", (DL_FUNC) &vctrs_bare_df_restore, 3}, + {"ffi_bare_df_restore", (DL_FUNC) &ffi_bare_df_restore, 3}, {"ffi_recycle", (DL_FUNC) &ffi_recycle, 3}, {"ffi_assign", (DL_FUNC) &ffi_assign, 4}, {"ffi_assign_seq", (DL_FUNC) &ffi_assign_seq, 5}, diff --git a/src/names.c b/src/names.c index e86d01569..f9c7873fb 100644 --- a/src/names.c +++ b/src/names.c @@ -99,7 +99,7 @@ r_obj* vec_names_impl(r_obj* x, bool proxy) { // Only return row names if they are character. Data frames with // automatic row names are treated as unnamed. r_obj* rn = df_rownames(x); - if (rownames_type(rn) == ROWNAMES_IDENTIFIERS) { + if (rownames_type(rn) == ROWNAMES_TYPE_identifiers) { return rn; } else { return r_null; @@ -726,7 +726,7 @@ r_obj* vec_set_rownames(r_obj* x, r_obj* names, bool proxy, const enum vctrs_own r_obj* vec_set_df_rownames(r_obj* x, r_obj* names, bool proxy, const enum vctrs_owned owned) { if (names == r_null) { - if (rownames_type(df_rownames(x)) != ROWNAMES_IDENTIFIERS) { + if (rownames_type(df_rownames(x)) != ROWNAMES_TYPE_identifiers) { return(x); } diff --git a/src/proxy-restore.c b/src/proxy-restore.c index 3242916e3..1f9cdbf1e 100644 --- a/src/proxy-restore.c +++ b/src/proxy-restore.c @@ -1,201 +1,195 @@ #include "vctrs.h" #include "type-data-frame.h" +#include "decl/proxy-restore-decl.h" -// Initialised at load time -static SEXP syms_vec_restore_dispatch = NULL; -static SEXP fns_vec_restore_dispatch = NULL; -// [[ register() ]] -SEXP vctrs_restore_default(SEXP x, SEXP to) { - return vec_restore_default(x, to, vec_owned(x)); +// FIXME: Having `owned` as an argument to `vec_restore()` may be +// unnecessary once we have recursive proxy / restore mechanisms. +// It currently helps resolve performance issues in `vec_rbind()`'s usage of +// `df_assign()`, which repeatedly proxies and restores each column, +// causing duplication to occur. Passing `owned` through here allows us to +// call `vec_clone_referenced()`, which won't attempt to clone if we know we +// own the object. See #1151. +r_obj* vec_restore(r_obj* x, r_obj* to, r_obj* n, const enum vctrs_owned owned) { + switch (class_type(to)) { + case VCTRS_CLASS_bare_factor: + case VCTRS_CLASS_bare_ordered: + case VCTRS_CLASS_none: return vec_restore_default(x, to, owned); + case VCTRS_CLASS_bare_date: return vec_date_restore(x, to, owned); + case VCTRS_CLASS_bare_posixct: return vec_posixct_restore(x, to, owned); + case VCTRS_CLASS_bare_posixlt: return vec_posixlt_restore(x, to, owned); + case VCTRS_CLASS_bare_data_frame: + case VCTRS_CLASS_bare_tibble: return vec_bare_df_restore(x, to, n, owned); + case VCTRS_CLASS_data_frame: return vec_df_restore(x, to, n, owned); + default: return vec_restore_dispatch(x, to, n); + } +} + +r_obj* ffi_restore(r_obj* x, r_obj* to, r_obj* n) { + return vec_restore(x, to, n, vec_owned(x)); } + +static +r_obj* vec_restore_dispatch(r_obj* x, r_obj* to, r_obj* n) { + return vctrs_dispatch3(syms_vec_restore_dispatch, fns_vec_restore_dispatch, + syms_x, x, + syms_to, to, + syms_n, n); +} + + // Copy attributes except names and dim. This duplicates `x` if needed. -// [[ include("vctrs.h") ]] -SEXP vec_restore_default(SEXP x, SEXP to, const enum vctrs_owned owned) { - SEXP attrib = ATTRIB(to); +r_obj* vec_restore_default(r_obj* x, r_obj* to, const enum vctrs_owned owned) { + r_obj* attrib = r_attrib(to); const bool is_s4 = IS_S4_OBJECT(to); - if (attrib == R_NilValue && !is_s4) { + if (attrib == r_null && !is_s4) { return x; } - int n_protect = 0; + int n_prot = 0; - attrib = PROTECT(Rf_shallow_duplicate(attrib)); - ++n_protect; + attrib = KEEP(r_clone(attrib)); + ++n_prot; - x = PROTECT(vec_clone_referenced(x, owned)); - ++n_protect; + x = KEEP(vec_clone_referenced(x, owned)); + ++n_prot; // Remove vectorised attributes which might be incongruent after reshaping. // Shouldn't matter for GNU R but other R implementations might have checks. - // Also record class to set it later with `Rf_setAttrib()`. This restores + // Also record class to set it later with `r_attrib_poke()`. This restores // the OBJECT bit and is likely more compatible with other implementations. - SEXP class = R_NilValue; + r_obj* class = r_null; { - SEXP node = attrib; - SEXP prev = R_NilValue; + r_obj* node = attrib; + r_obj* prev = r_null; - while (node != R_NilValue) { - SEXP tag = TAG(node); + while (node != r_null) { + r_obj* tag = r_node_tag(node); // Skip special attributes - if (tag == R_NamesSymbol || tag == R_DimSymbol || - tag == R_DimNamesSymbol || tag == R_ClassSymbol || - tag == R_RowNamesSymbol) { - if (tag == R_ClassSymbol) { - class = CAR(node); + if (tag == r_syms.names || tag == r_syms.dim || + tag == r_syms.dim_names || tag == r_syms.class_ || + tag == r_syms.row_names) { + if (tag == r_syms.class_) { + class = r_node_car(node); } - if (prev == R_NilValue) { - attrib = CDR(attrib); + if (prev == r_null) { + attrib = r_node_cdr(attrib); } else { - SETCDR(prev, CDR(node)); + r_node_poke_cdr(prev, r_node_cdr(node)); } - node = CDR(node); + node = r_node_cdr(node); continue; } prev = node; - node = CDR(node); + node = r_node_cdr(node); } } // Copy attributes but keep names and dims. Don't restore names for // shaped objects since those are generated from dimnames. - SEXP dim = PROTECT(Rf_getAttrib(x, R_DimSymbol)); - ++n_protect; + r_obj* dim = KEEP(r_attrib_get(x, r_syms.dim)); + ++n_prot; - if (dim == R_NilValue) { - SEXP nms = PROTECT(Rf_getAttrib(x, R_NamesSymbol)); + if (dim == r_null) { + r_obj* nms = KEEP(r_attrib_get(x, r_syms.names)); // Check if `to` is a data frame early. If `x` and `to` point - // to the same reference, then `SET_ATTRIB()` would alter `to`. - SEXP rownms = PROTECT(df_rownames(x)); - const bool restore_rownms = rownms != R_NilValue && is_data_frame(to); + // to the same reference, then `r_poke_attrib()` would alter `to`. + r_obj* rownms = KEEP(df_rownames(x)); + const bool restore_rownms = rownms != r_null && is_data_frame(to); - SET_ATTRIB(x, attrib); + r_poke_attrib(x, attrib); - Rf_setAttrib(x, R_NamesSymbol, nms); + r_attrib_poke(x, r_syms.names, nms); // Don't restore row names if `to` isn't a data frame if (restore_rownms) { - Rf_setAttrib(x, R_RowNamesSymbol, rownms); + r_attrib_poke(x, r_syms.row_names, rownms); } - UNPROTECT(2); + FREE(2); } else { - SEXP dimnames = PROTECT(Rf_getAttrib(x, R_DimNamesSymbol)); + r_obj* dimnames = KEEP(r_attrib_get(x, r_syms.dim_names)); - SET_ATTRIB(x, attrib); + r_poke_attrib(x, attrib); - Rf_setAttrib(x, R_DimSymbol, dim); - Rf_setAttrib(x, R_DimNamesSymbol, dimnames); - UNPROTECT(1); + r_attrib_poke(x, r_syms.dim, dim); + r_attrib_poke(x, r_syms.dim_names, dimnames); + FREE(1); } - if (class != R_NilValue) { - Rf_setAttrib(x, R_ClassSymbol, class); + if (class != r_null) { + r_attrib_poke(x, r_syms.class_, class); } if (is_s4) { r_mark_s4(x); } - UNPROTECT(n_protect); + FREE(n_prot); return x; } -static SEXP vec_restore_dispatch(SEXP x, SEXP to, SEXP n) { - return vctrs_dispatch3(syms_vec_restore_dispatch, fns_vec_restore_dispatch, - syms_x, x, - syms_to, to, - syms_n, n); +r_obj* ffi_restore_default(r_obj* x, r_obj* to) { + return vec_restore_default(x, to, vec_owned(x)); } -static SEXP vec_bare_df_restore_impl(SEXP x, SEXP to, R_len_t size, - const enum vctrs_owned owned) { - x = PROTECT(vec_restore_default(x, to, owned)); - if (Rf_getAttrib(x, R_NamesSymbol) == R_NilValue) { - SEXP names = PROTECT(Rf_allocVector(STRSXP, Rf_length(x))); - Rf_setAttrib(x, R_NamesSymbol, names); - UNPROTECT(1); +// Restore methods are passed the original atomic type back, so we +// first restore data frames as such before calling the restore +// method, if any +r_obj* vec_df_restore(r_obj* x, r_obj* to, r_obj* n, const enum vctrs_owned owned) { + r_obj* out = KEEP(vec_bare_df_restore(x, to, n, owned)); + out = vec_restore_dispatch(out, to, n); + FREE(1); + return out; +} + +r_obj* vec_bare_df_restore(r_obj* x, r_obj* to, r_obj* n, const enum vctrs_owned owned) { + if (r_typeof(x) != R_TYPE_list) { + r_stop_internal("Attempt to restore data frame from a %s.", + r_type_as_c_string(r_typeof(x))); + } + + x = KEEP(vec_restore_default(x, to, owned)); + + if (r_attrib_get(x, r_syms.names) == r_null) { + r_obj* names = KEEP(r_alloc_character(r_length(x))); + r_attrib_poke(x, r_syms.names, names); + FREE(1); } - SEXP rownames = PROTECT(df_rownames(x)); - if (rownames == R_NilValue) { + r_obj* rownames = KEEP(df_rownames(x)); + r_ssize size = (n == r_null) ? df_raw_size(x) : r_int_get(n, 0); + + if (rownames == r_null) { init_compact_rownames(x, size); - } else if (rownames_type(rownames) == ROWNAMES_IDENTIFIERS) { - rownames = PROTECT(vec_as_names(rownames, p_unique_repair_silent_opts)); + } else if (rownames_type(rownames) == ROWNAMES_TYPE_identifiers) { + rownames = KEEP(vec_as_names(rownames, p_unique_repair_silent_opts)); x = vec_proxy_set_names(x, rownames, owned); - UNPROTECT(1); + FREE(1); } - UNPROTECT(2); + FREE(2); return x; } -// [[ register() ]] -SEXP vctrs_bare_df_restore(SEXP x, SEXP to, SEXP n) { +r_obj* ffi_bare_df_restore(r_obj* x, r_obj* to, r_obj* n) { return vec_bare_df_restore(x, to, n, vec_owned(x)); } -// [[ include("vctrs.h") ]] -SEXP vec_bare_df_restore(SEXP x, SEXP to, SEXP n, const enum vctrs_owned owned) { - if (TYPEOF(x) != VECSXP) { - r_stop_internal("Attempt to restore data frame from a %s.", - Rf_type2char(TYPEOF(x))); - } - R_len_t size = (n == R_NilValue) ? df_raw_size(x) : r_int_get(n, 0); - return vec_bare_df_restore_impl(x, to, size, owned); +void vctrs_init_proxy_restore(r_obj* ns) { + syms_vec_restore_dispatch = r_sym("vec_restore_dispatch"); + fns_vec_restore_dispatch = r_eval(syms_vec_restore_dispatch, ns); } -// Restore methods are passed the original atomic type back, so we -// first restore data frames as such before calling the restore -// method, if any -// [[ include("vctrs.h") ]] -SEXP vec_df_restore(SEXP x, SEXP to, SEXP n, const enum vctrs_owned owned) { - SEXP out = PROTECT(vec_bare_df_restore(x, to, n, owned)); - out = vec_restore_dispatch(out, to, n); - UNPROTECT(1); - return out; -} - -// [[ register() ]] -SEXP vctrs_restore(SEXP x, SEXP to, SEXP n) { - return vec_restore(x, to, n, vec_owned(x)); -} - -// FIXME: Having `owned` as an argument to `vec_restore()` may be -// unnecessary once we have recursive proxy / restore mechanisms. -// It currently helps resolve performance issues in `vec_rbind()`'s usage of -// `df_assign()`, which repeatedly proxies and restores each column, -// causing duplication to occur. Passing `owned` through here allows us to -// call `vec_clone_referenced()`, which won't attempt to clone if we know we -// own the object. See #1151. -// [[ include("vctrs.h") ]] -SEXP vec_restore(SEXP x, SEXP to, SEXP n, const enum vctrs_owned owned) { - switch (class_type(to)) { - default: return vec_restore_dispatch(x, to, n); - case VCTRS_CLASS_bare_factor: - case VCTRS_CLASS_bare_ordered: - case VCTRS_CLASS_none: return vec_restore_default(x, to, owned); - case VCTRS_CLASS_bare_date: return vec_date_restore(x, to, owned); - case VCTRS_CLASS_bare_posixct: return vec_posixct_restore(x, to, owned); - case VCTRS_CLASS_bare_posixlt: return vec_posixlt_restore(x, to, owned); - case VCTRS_CLASS_bare_data_frame: - case VCTRS_CLASS_bare_tibble: return vec_bare_df_restore(x, to, n, owned); - case VCTRS_CLASS_data_frame: return vec_df_restore(x, to, n, owned); - } -} - - -void vctrs_init_proxy_restore(SEXP ns) { - syms_vec_restore_dispatch = Rf_install("vec_restore_dispatch"); - fns_vec_restore_dispatch = Rf_findVar(syms_vec_restore_dispatch, ns); -} +static r_obj* syms_vec_restore_dispatch = NULL; +static r_obj* fns_vec_restore_dispatch = NULL; diff --git a/src/proxy-restore.h b/src/proxy-restore.h new file mode 100644 index 000000000..14520c3a8 --- /dev/null +++ b/src/proxy-restore.h @@ -0,0 +1,12 @@ +#ifndef VCTRS_PROXY_RESTORE_H +#define VCTRS_PROXY_RESTORE_H + + +r_obj* vec_restore(r_obj* x, r_obj* to, r_obj* n, const enum vctrs_owned owned); +r_obj* vec_restore_default(r_obj* x, r_obj* to, const enum vctrs_owned owned); + +r_obj* vec_bare_df_restore(r_obj* x, r_obj* to, r_obj* n, const enum vctrs_owned owned); +r_obj* vec_df_restore(r_obj* x, r_obj* to, r_obj* n, const enum vctrs_owned owned); + + +#endif diff --git a/src/type-data-frame.c b/src/type-data-frame.c index 8bb263ec5..f2e716d35 100644 --- a/src/type-data-frame.c +++ b/src/type-data-frame.c @@ -413,12 +413,12 @@ r_obj* df_list_unpack(r_obj* x) { enum rownames_type rownames_type(r_obj* x) { switch (r_typeof(x)) { case R_TYPE_character: - return ROWNAMES_IDENTIFIERS; + return ROWNAMES_TYPE_identifiers; case R_TYPE_integer: if (r_length(x) == 2 && r_int_begin(x)[0] == r_globals.na_int) { - return ROWNAMES_AUTOMATIC_COMPACT; + return ROWNAMES_TYPE_automatic_compact; } else { - return ROWNAMES_AUTOMATIC; + return ROWNAMES_TYPE_automatic; } default: r_stop_internal("Unexpected type `%s`.", Rf_type2char(r_typeof(x))); @@ -433,10 +433,10 @@ r_ssize compact_rownames_length(r_obj* x) { // [[ include("type-data-frame.h") ]] r_ssize rownames_size(r_obj* rn) { switch (rownames_type(rn)) { - case ROWNAMES_IDENTIFIERS: - case ROWNAMES_AUTOMATIC: + case ROWNAMES_TYPE_identifiers: + case ROWNAMES_TYPE_automatic: return r_length(rn); - case ROWNAMES_AUTOMATIC_COMPACT: + case ROWNAMES_TYPE_automatic_compact: return compact_rownames_length(rn); } diff --git a/src/type-data-frame.h b/src/type-data-frame.h index 0887cef11..02d505899 100644 --- a/src/type-data-frame.h +++ b/src/type-data-frame.h @@ -41,9 +41,9 @@ r_obj* df_cast(r_obj* x, } enum rownames_type { - ROWNAMES_AUTOMATIC, - ROWNAMES_AUTOMATIC_COMPACT, - ROWNAMES_IDENTIFIERS + ROWNAMES_TYPE_automatic, + ROWNAMES_TYPE_automatic_compact, + ROWNAMES_TYPE_identifiers }; enum rownames_type rownames_type(r_obj* rn); r_ssize rownames_size(r_obj* rn); diff --git a/src/vctrs.h b/src/vctrs.h index 5d0a1d8e4..e08792f39 100644 --- a/src/vctrs.h +++ b/src/vctrs.h @@ -39,6 +39,7 @@ bool vec_is_unspecified(SEXP x); #include "owned.h" #include "poly-op.h" #include "proxy.h" +#include "proxy-restore.h" #include "ptype-common.h" #include "ptype.h" #include "ptype2-dispatch.h" @@ -72,8 +73,6 @@ SEXP vec_proxy_equal(SEXP x); SEXP vec_proxy_compare(SEXP x); SEXP vec_proxy_order(SEXP x); SEXP vec_proxy_unwrap(SEXP x); -SEXP vec_restore(SEXP x, SEXP to, SEXP n, const enum vctrs_owned owned); -SEXP vec_restore_default(SEXP x, SEXP to, const enum vctrs_owned owned); SEXP vec_chop(SEXP x, SEXP indices); SEXP vec_slice_shaped(enum vctrs_type type, SEXP x, SEXP index); bool vec_requires_fallback(SEXP x, struct vctrs_proxy_info info); @@ -104,9 +103,6 @@ SEXP vec_c(SEXP xs, bool is_data_frame(SEXP x); -SEXP vec_bare_df_restore(SEXP x, SEXP to, SEXP n, const enum vctrs_owned owned); -SEXP vec_df_restore(SEXP x, SEXP to, SEXP n, const enum vctrs_owned owned); - uint32_t hash_object(SEXP x); void hash_fill(uint32_t* p, R_len_t n, SEXP x, bool na_equal); From e9b71b133e859992d4b3d30ddadef5ae537ead16 Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Wed, 7 Sep 2022 12:50:27 +0200 Subject: [PATCH 022/312] Fix scoping of `enum vctrs_owned` --- src/owned.h | 7 ------- src/proxy-restore.h | 2 ++ src/vctrs-core.h | 7 +++++++ 3 files changed, 9 insertions(+), 7 deletions(-) diff --git a/src/owned.h b/src/owned.h index 2b8055608..419b73fc6 100644 --- a/src/owned.h +++ b/src/owned.h @@ -6,13 +6,6 @@ #include "utils.h" -// Ownership is recursive -enum vctrs_owned { - VCTRS_OWNED_false = 0, - VCTRS_OWNED_true -}; - - static inline enum vctrs_owned vec_owned(SEXP x) { return NO_REFERENCES(x) ? VCTRS_OWNED_true : VCTRS_OWNED_false; } diff --git a/src/proxy-restore.h b/src/proxy-restore.h index 14520c3a8..263e1624c 100644 --- a/src/proxy-restore.h +++ b/src/proxy-restore.h @@ -1,6 +1,8 @@ #ifndef VCTRS_PROXY_RESTORE_H #define VCTRS_PROXY_RESTORE_H +#include "vctrs-core.h" + r_obj* vec_restore(r_obj* x, r_obj* to, r_obj* n, const enum vctrs_owned owned); r_obj* vec_restore_default(r_obj* x, r_obj* to, const enum vctrs_owned owned); diff --git a/src/vctrs-core.h b/src/vctrs-core.h index adcf8f4d6..65164adeb 100644 --- a/src/vctrs-core.h +++ b/src/vctrs-core.h @@ -21,6 +21,13 @@ extern bool vctrs_debug_verbose; #define ERR SEXP +// Ownership is recursive +enum vctrs_owned { + VCTRS_OWNED_false = 0, + VCTRS_OWNED_true +}; + + /** * Structure for argument tags * From c8e1e2593d8767d65d4bf233a79885801c07da62 Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Thu, 1 Sep 2022 15:13:29 +0200 Subject: [PATCH 023/312] Remove `logical` argument of `vec_as_subscript2()` Closes #1608 --- DESCRIPTION | 1 + NEWS.md | 2 ++ R/subscript-loc.R | 2 -- R/subscript.R | 23 +++++++++++++---------- man/vec_as_subscript.Rd | 1 - tests/testthat/_snaps/subscript.md | 30 ++++++++++++++++++++++++------ tests/testthat/test-subscript.R | 21 +++++++++++++++++---- 7 files changed, 57 insertions(+), 23 deletions(-) diff --git a/DESCRIPTION b/DESCRIPTION index 0299aaa31..a5e690bc8 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -30,6 +30,7 @@ Depends: R (>= 3.3) Imports: cli (>= 3.2.0), + lifecycle (>= 1.0.1), glue, rlang (>= 1.0.4) Suggests: diff --git a/NEWS.md b/NEWS.md index 38a7f52cf..e159ced33 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,5 +1,7 @@ # vctrs (development version) +* Fixed confusing error message with logical `[[` subscripts (#1608). + * New `vec_rank()` to compute various types of sample ranks (#1600). * `num_as_location()` now throws the right error when there are out-of-bounds diff --git a/R/subscript-loc.R b/R/subscript-loc.R index d34e8161e..c47e36cf0 100644 --- a/R/subscript-loc.R +++ b/R/subscript-loc.R @@ -174,7 +174,6 @@ vec_as_location2_result <- function(i, result <- vec_as_subscript2_result( i = i, arg = arg, - logical = "error", call = call ) @@ -324,7 +323,6 @@ new_error_location2_type <- function(i, new_error_subscript2_type( class = class, i = i, - logical = "error", numeric = "cast", character = "cast", ... diff --git a/R/subscript.R b/R/subscript.R index 47039325d..fd5a439ef 100644 --- a/R/subscript.R +++ b/R/subscript.R @@ -64,17 +64,25 @@ vec_as_subscript_result <- function(i, #' @export vec_as_subscript2 <- function(i, ..., - logical = c("cast", "error"), numeric = c("cast", "error"), character = c("cast", "error"), arg = NULL, call = caller_env()) { - check_dots_empty0(...) + check_dots <- function(..., logical = "error") { + if (!is_string(logical, "error")) { + lifecycle::deprecate_stop( + "0.4.1.9000", + "vctrs::vec_as_subscript2(logical = 'no longer supports \"cast\"')" + ) + } + check_dots_empty0(...) + } + check_dots(...) + result_get(vec_as_subscript2_result( i, arg, call, - logical = logical, numeric = numeric, character = character )) @@ -82,10 +90,8 @@ vec_as_subscript2 <- function(i, vec_as_subscript2_result <- function(i, arg, call, - logical = "cast", numeric = "cast", character = "cast") { - logical <- arg_match0(logical, c("cast", "error")) numeric <- arg_match0(numeric, c("cast", "error")) character <- arg_match0(character, c("cast", "error")) @@ -93,7 +99,7 @@ vec_as_subscript2_result <- function(i, i, arg = arg, call = call, - logical = logical, + logical = "error", numeric = numeric, character = character ) @@ -110,7 +116,6 @@ vec_as_subscript2_result <- function(i, result$err <- new_error_subscript2_type( i = result$err$i, - logical = logical, numeric = numeric, character = character, subscript_arg = arg, @@ -126,7 +131,6 @@ vec_as_subscript2_result <- function(i, if (typeof(i) == "logical") { return(result(err = new_error_subscript2_type( i = i, - logical = logical, numeric = numeric, character = character, subscript_arg = arg, @@ -254,13 +258,12 @@ cnd_header.vctrs_error_subscript_size <- function(cnd, ...) { } new_error_subscript2_type <- function(i, - logical, numeric, character, ...) { new_error_subscript_type( i = i, - logical = logical, + logical = "error", numeric = numeric, character = character, subscript_scalar = TRUE, diff --git a/man/vec_as_subscript.Rd b/man/vec_as_subscript.Rd index 017d5c438..6dff091a4 100644 --- a/man/vec_as_subscript.Rd +++ b/man/vec_as_subscript.Rd @@ -18,7 +18,6 @@ vec_as_subscript( vec_as_subscript2( i, ..., - logical = c("cast", "error"), numeric = c("cast", "error"), character = c("cast", "error"), arg = NULL, diff --git a/tests/testthat/_snaps/subscript.md b/tests/testthat/_snaps/subscript.md index 0e5dec35e..c119446e1 100644 --- a/tests/testthat/_snaps/subscript.md +++ b/tests/testthat/_snaps/subscript.md @@ -112,7 +112,7 @@ # vec_as_subscript2() forbids subscript types Code - vec_as_subscript2(1L, numeric = "error", logical = "error") + vec_as_subscript2(1L, numeric = "error") Condition Error: ! Must extract element with a single valid subscript. @@ -122,7 +122,7 @@ --- Code - vec_as_subscript2("foo", character = "error", logical = "error") + vec_as_subscript2("foo", character = "error") Condition Error: ! Must extract element with a single valid subscript. @@ -132,7 +132,7 @@ --- Code - vec_as_subscript2(TRUE, logical = "error") + vec_as_subscript2(TRUE) Condition Error: ! Must extract element with a single valid subscript. @@ -147,7 +147,7 @@ Error in `foo()`: ! Must extract element with a single valid subscript. x Subscript has the wrong type `integer`. - i It must be logical or character. + i It must be character. --- @@ -157,7 +157,7 @@ Error in `foo()`: ! Must extract element with a single valid subscript. x Subscript has the wrong type `double`. - i It must be logical, numeric, or character. + i It must be numeric or character. # vec_as_subscript2() retains the call when erroring on logical input (#1605) @@ -167,5 +167,23 @@ Error in `foo()`: ! Must extract element with a single valid subscript. x Subscript has the wrong type `logical`. - i It must be logical, numeric, or character. + i It must be numeric or character. + +# `logical = 'cast'` is deprecated + + Code + vec_as_subscript2(TRUE, logical = "cast") + Condition + Error: + ! The `logical` argument of `vec_as_subscript2()` no longer supports "cast" as of vctrs 0.4.1.9000. + +--- + + Code + vec_as_subscript2(TRUE, logical = "error") + Condition + Error: + ! Must extract element with a single valid subscript. + x Subscript has the wrong type `logical`. + i It must be numeric or character. diff --git a/tests/testthat/test-subscript.R b/tests/testthat/test-subscript.R index cf30ea174..a78e704a9 100644 --- a/tests/testthat/test-subscript.R +++ b/tests/testthat/test-subscript.R @@ -81,9 +81,9 @@ test_that("vec_as_subscript() forbids subscript types", { }) test_that("vec_as_subscript2() forbids subscript types", { - expect_snapshot(error = TRUE, vec_as_subscript2(1L, numeric = "error", logical = "error")) - expect_snapshot(error = TRUE, vec_as_subscript2("foo", character = "error", logical = "error")) - expect_snapshot(error = TRUE, vec_as_subscript2(TRUE, logical = "error")) + expect_snapshot(error = TRUE, vec_as_subscript2(1L, numeric = "error")) + expect_snapshot(error = TRUE, vec_as_subscript2("foo", character = "error")) + expect_snapshot(error = TRUE, vec_as_subscript2(TRUE)) }) test_that("vec_as_subscript2() retains the call when throwing vec_as_subscript() errors (#1605)", { @@ -102,5 +102,18 @@ test_that("vec_as_subscript() evaluates arg lazily", { test_that("vec_as_subscript2() evaluates arg lazily", { expect_silent(vec_as_subscript2(1L, arg = print("oof"))) - expect_silent(vec_as_subscript2_result(1L, arg = print("oof"), NULL, logical = "error", numeric = "cast", character = "error")) + expect_silent(vec_as_subscript2_result(1L, arg = print("oof"), NULL, numeric = "cast", character = "error")) +}) + +test_that("`logical = 'cast'` is deprecated", { + expect_snapshot( + error = TRUE, + vec_as_subscript2(TRUE, logical = "cast") + ) + + # `logical = "error"` still works + expect_snapshot( + error = TRUE, + vec_as_subscript2(TRUE, logical = "error") + ) }) From 56d539a95a176aa2794447cdf048c88eac6ae094 Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Thu, 1 Sep 2022 15:38:45 +0200 Subject: [PATCH 024/312] Don't bring in lifecycle for a defunct argument --- DESCRIPTION | 1 - R/subscript.R | 6 +++--- tests/testthat/_snaps/subscript.md | 4 ++-- 3 files changed, 5 insertions(+), 6 deletions(-) diff --git a/DESCRIPTION b/DESCRIPTION index a5e690bc8..0299aaa31 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -30,7 +30,6 @@ Depends: R (>= 3.3) Imports: cli (>= 3.2.0), - lifecycle (>= 1.0.1), glue, rlang (>= 1.0.4) Suggests: diff --git a/R/subscript.R b/R/subscript.R index fd5a439ef..ae29fd5c1 100644 --- a/R/subscript.R +++ b/R/subscript.R @@ -70,9 +70,9 @@ vec_as_subscript2 <- function(i, call = caller_env()) { check_dots <- function(..., logical = "error") { if (!is_string(logical, "error")) { - lifecycle::deprecate_stop( - "0.4.1.9000", - "vctrs::vec_as_subscript2(logical = 'no longer supports \"cast\"')" + abort( + "`vctrs::vec_as_subscript2(logical = 'cast')` is deprecated.", + call = caller_env() ) } check_dots_empty0(...) diff --git a/tests/testthat/_snaps/subscript.md b/tests/testthat/_snaps/subscript.md index c119446e1..0bb01d70f 100644 --- a/tests/testthat/_snaps/subscript.md +++ b/tests/testthat/_snaps/subscript.md @@ -174,8 +174,8 @@ Code vec_as_subscript2(TRUE, logical = "cast") Condition - Error: - ! The `logical` argument of `vec_as_subscript2()` no longer supports "cast" as of vctrs 0.4.1.9000. + Error in `vec_as_subscript2()`: + ! `vctrs::vec_as_subscript2(logical = 'cast')` is deprecated. --- From 7062241dc64fe7a298d899d8be9681121fc44f8f Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Thu, 8 Sep 2022 08:47:44 +0200 Subject: [PATCH 025/312] Pass correct env to `check_dots_empty0()` --- R/subscript.R | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/R/subscript.R b/R/subscript.R index ae29fd5c1..eaf8258ee 100644 --- a/R/subscript.R +++ b/R/subscript.R @@ -68,14 +68,14 @@ vec_as_subscript2 <- function(i, character = c("cast", "error"), arg = NULL, call = caller_env()) { - check_dots <- function(..., logical = "error") { + check_dots <- function(..., logical = "error", call = caller_env()) { if (!is_string(logical, "error")) { abort( "`vctrs::vec_as_subscript2(logical = 'cast')` is deprecated.", call = caller_env() ) } - check_dots_empty0(...) + check_dots_empty0(..., call = call) } check_dots(...) From 05873665a25983ace4854c508f588e857c02923f Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Thu, 8 Sep 2022 08:50:10 +0200 Subject: [PATCH 026/312] Simplify error handling in `vec_as_subscript2()` --- R/subscript.R | 26 +------------------------- 1 file changed, 1 insertion(+), 25 deletions(-) diff --git a/R/subscript.R b/R/subscript.R index eaf8258ee..f1e901661 100644 --- a/R/subscript.R +++ b/R/subscript.R @@ -104,39 +104,15 @@ vec_as_subscript2_result <- function(i, character = character ) - # Return a child of subscript error. The child error messages refer - # to single subscripts instead of subscript vectors. + # Transform `[` errors into `[[` errors if (!is_null(result$err)) { - parent <- result$err$parent - if (inherits(parent, "vctrs_error_cast_lossy")) { - bullets <- new_cnd_bullets_subscript_lossy_cast(parent) - } else { - bullets <- cnd_body.vctrs_error_subscript_type - } - result$err <- new_error_subscript2_type( i = result$err$i, numeric = numeric, character = character, subscript_arg = arg, - body = bullets, call = call ) - - return(result) - } - - i <- result$ok - - if (typeof(i) == "logical") { - return(result(err = new_error_subscript2_type( - i = i, - numeric = numeric, - character = character, - subscript_arg = arg, - body = cnd_body.vctrs_error_subscript_type, - call = call - ))) } result From 9d6bc369262628965ba6517d095f9146174cd8d7 Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Thu, 1 Sep 2022 16:28:22 +0200 Subject: [PATCH 027/312] Simplify and fix scalar subscript errors Fixes #1606 --- NEWS.md | 3 +++ R/subscript.R | 11 +++-------- tests/testthat/_snaps/subscript-loc.md | 12 ++++-------- tests/testthat/_snaps/subscript.md | 12 ++++++++++-- tests/testthat/test-subscript.R | 7 +++++++ 5 files changed, 27 insertions(+), 18 deletions(-) diff --git a/NEWS.md b/NEWS.md index e159ced33..d9dcc7b0c 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,5 +1,8 @@ # vctrs (development version) +* Lossy cast errors during scalar subscript validation now have the + correct message (#1606). + * Fixed confusing error message with logical `[[` subscripts (#1608). * New `vec_rank()` to compute various types of sample ranks (#1600). diff --git a/R/subscript.R b/R/subscript.R index f1e901661..be9df5b36 100644 --- a/R/subscript.R +++ b/R/subscript.R @@ -104,15 +104,10 @@ vec_as_subscript2_result <- function(i, character = character ) - # Transform `[` errors into `[[` errors + # This should normally be a `vctrs_error_subscript`. Indicate to + # message methods that this error refers to a `[[` subscript. if (!is_null(result$err)) { - result$err <- new_error_subscript2_type( - i = result$err$i, - numeric = numeric, - character = character, - subscript_arg = arg, - call = call - ) + result$err$subscript_scalar <- TRUE } result diff --git a/tests/testthat/_snaps/subscript-loc.md b/tests/testthat/_snaps/subscript-loc.md index a749ef8c9..c55acaa09 100644 --- a/tests/testthat/_snaps/subscript-loc.md +++ b/tests/testthat/_snaps/subscript-loc.md @@ -54,16 +54,14 @@ Error: ! Must extract element with a single valid subscript. - x Subscript `2.5` has the wrong type `double`. - i It must be numeric or character. + x Can't convert from `2.5` to due to loss of precision. Code (expect_error(vec_as_location2(Inf, 10L), class = "vctrs_error_subscript_type")) Output Error: ! Must extract element with a single valid subscript. - x Subscript `Inf` has the wrong type `double`. - i It must be numeric or character. + x Can't convert from `Inf` to due to loss of precision. Code (expect_error(vec_as_location2(-Inf, 10L), class = "vctrs_error_subscript_type") ) @@ -71,8 +69,7 @@ Error: ! Must extract element with a single valid subscript. - x Subscript `-Inf` has the wrong type `double`. - i It must be numeric or character. + x Can't convert from `-Inf` to due to loss of precision. Code # Idem with custom `arg` (expect_error(vec_as_location2(foobar(), 10L, arg = "foo", call = call( @@ -90,8 +87,7 @@ Error in `my_function()`: ! Must extract element with a single valid subscript. - x Subscript `foo` has the wrong type `double`. - i It must be numeric or character. + x Can't convert from `foo` to due to loss of precision. Code (expect_error(with_tibble_rows(vec_as_location2(TRUE)), class = "vctrs_error_subscript_type") ) diff --git a/tests/testthat/_snaps/subscript.md b/tests/testthat/_snaps/subscript.md index 0bb01d70f..f48dd13cb 100644 --- a/tests/testthat/_snaps/subscript.md +++ b/tests/testthat/_snaps/subscript.md @@ -156,8 +156,7 @@ Condition Error in `foo()`: ! Must extract element with a single valid subscript. - x Subscript has the wrong type `double`. - i It must be numeric or character. + x Can't convert from to due to loss of precision. # vec_as_subscript2() retains the call when erroring on logical input (#1605) @@ -187,3 +186,12 @@ x Subscript has the wrong type `logical`. i It must be numeric or character. +# lossy cast errors for scalar subscripts work (#1606) + + Code + vec_as_subscript2(1.5) + Condition + Error: + ! Must extract element with a single valid subscript. + x Can't convert from to due to loss of precision. + diff --git a/tests/testthat/test-subscript.R b/tests/testthat/test-subscript.R index a78e704a9..12925df01 100644 --- a/tests/testthat/test-subscript.R +++ b/tests/testthat/test-subscript.R @@ -117,3 +117,10 @@ test_that("`logical = 'cast'` is deprecated", { vec_as_subscript2(TRUE, logical = "error") ) }) + +test_that("lossy cast errors for scalar subscripts work (#1606)", { + expect_snapshot( + error = TRUE, + vec_as_subscript2(1.5) + ) +}) From 5191dfc9a0a2550e5ab94a992ccbeb30446e52e5 Mon Sep 17 00:00:00 2001 From: Davis Vaughan Date: Thu, 8 Sep 2022 09:29:52 -0400 Subject: [PATCH 028/312] Update rlang C library (#1645) * Update rlang C library * Trim back `rlang-dev.c/h` files Now that this has made it into rlang directly * Use new `r_syms.arg` * Update snapshot tests * Require rlang >=1.0.5 to ensure `r_obj_type_friendly()` is available --- DESCRIPTION | 2 +- src/conditions.c | 2 +- src/decl/rlang-dev-decl.h | 3 - src/names.c | 2 +- src/rlang-dev.c | 25 +---- src/rlang-dev.h | 43 +------- src/rlang/arg.c | 8 +- src/rlang/arg.h | 5 +- src/rlang/c-utils.h | 2 + src/rlang/cnd.c | 19 ++-- src/rlang/cnd.h | 14 ++- src/rlang/decl/env-decl.h | 33 +++++- src/rlang/env-binding.c | 10 +- src/rlang/env.c | 129 ++++++++++++++--------- src/rlang/env.h | 2 + src/rlang/eval.c | 8 ++ src/rlang/eval.h | 33 ++++++ src/rlang/globals.c | 3 + src/rlang/globals.h | 3 + src/rlang/obj.c | 27 +++++ src/rlang/obj.h | 4 + src/rlang/rlang-types.h | 5 + src/rlang/rlang.c | 1 + src/rlang/rlang.h | 4 + src/rlang/session.c | 43 ++++++++ src/rlang/session.h | 1 + src/rlang/vec-lgl.c | 69 ++++++++---- src/rlang/vec.h | 10 +- src/size.c | 4 +- src/utils.c | 6 -- src/utils.h | 1 - tests/testthat/_snaps/type-data-frame.md | 4 +- 32 files changed, 352 insertions(+), 173 deletions(-) diff --git a/DESCRIPTION b/DESCRIPTION index 0299aaa31..6c99a7f15 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -31,7 +31,7 @@ Depends: Imports: cli (>= 3.2.0), glue, - rlang (>= 1.0.4) + rlang (>= 1.0.5) Suggests: bit64, covr, diff --git a/src/conditions.c b/src/conditions.c index 3283b6b5b..921687336 100644 --- a/src/conditions.c +++ b/src/conditions.c @@ -23,7 +23,7 @@ void stop_assert_size(r_ssize actual, r_obj* syms[4] = { syms_actual, syms_required, - syms_arg, + r_syms.arg, NULL }; r_obj* args[4] = { diff --git a/src/decl/rlang-dev-decl.h b/src/decl/rlang-dev-decl.h index 7a4307afa..e69de29bb 100644 --- a/src/decl/rlang-dev-decl.h +++ b/src/decl/rlang-dev-decl.h @@ -1,3 +0,0 @@ -const char* r_friendly_type_of_opts(r_obj* x, - bool value, - bool length); diff --git a/src/names.c b/src/names.c index f9c7873fb..21724801f 100644 --- a/src/names.c +++ b/src/names.c @@ -65,7 +65,7 @@ r_obj* check_unique_names(r_obj* names, r_obj* out = KEEP(vctrs_dispatch3(syms_check_unique_names, fns_check_unique_names, syms_names, names, - syms_arg, ffi_arg, + r_syms.arg, ffi_arg, syms_call, ffi_call)); // Restore visibility diff --git a/src/rlang-dev.c b/src/rlang-dev.c index 653c255f3..30fecaa58 100644 --- a/src/rlang-dev.c +++ b/src/rlang-dev.c @@ -1,27 +1,6 @@ #include "vctrs.h" #include "decl/rlang-dev-decl.h" -const char* r_friendly_type_of(r_obj* x) { - return r_friendly_type_of_opts(x, true, false); -} - -const char* r_friendly_type_of_length(r_obj* x) { - return r_friendly_type_of_opts(x, true, true); -} - -const char* r_friendly_type_of_opts(r_obj* x, - bool value, - bool length) { - r_obj* call = KEEP(r_parse("friendly_type_of(x, value = y, length = z)")); - r_obj* ffi_out = KEEP(r_eval_with_xyz(call, x, r_lgl(value), r_lgl(length), vctrs_ns_env)); - - const char* out_str = r_chr_get_c_string(ffi_out, 0); - int n = strlen(out_str) + 1; - - // Uses the vmax protection stack. - char* out = R_alloc(n, sizeof(char)); - memcpy(out, out_str, n); - - FREE(2); - return out; +const char* r_obj_type_friendly_length(r_obj* x) { + return r_obj_type_friendly_full(x, true, true); } diff --git a/src/rlang-dev.h b/src/rlang-dev.h index b9922ce36..5f2993b23 100644 --- a/src/rlang-dev.h +++ b/src/rlang-dev.h @@ -3,46 +3,6 @@ #include -struct r_lazy { - r_obj* x; - r_obj* env; -}; - -static inline -r_obj* r_lazy_eval(struct r_lazy lazy) { - if (!lazy.env) { - // Unitialised lazy variable - return r_null; - } else if (lazy.env == r_null) { - // Forced lazy variable - return lazy.x; - } else { - return r_eval(lazy.x, lazy.env); - } -} - -extern -struct r_lazy r_lazy_null; - -static inline -r_obj* r_lazy_eval_protect(struct r_lazy lazy) { - r_obj* out = KEEP(r_lazy_eval(lazy)); - out = r_expr_protect(out); - - FREE(1); - return out; -} - -static inline -bool r_lazy_is_null(struct r_lazy call) { - return !call.x && !call.env; -} - - -#define r_abort_lazy_call(LAZY, ...) \ - r_abort_call(KEEP(r_lazy_eval(LAZY)), __VA_ARGS__) - - static inline const char* r_c_str_format_error_arg(const char* x) { r_obj* ffi_x = KEEP(r_chr(x)); @@ -52,8 +12,7 @@ const char* r_c_str_format_error_arg(const char* x) { } // vmax-protected result -const char* r_friendly_type_of(r_obj* x); -const char* r_friendly_type_of_length(r_obj* x); +const char* r_obj_type_friendly_length(r_obj* x); #endif diff --git a/src/rlang/arg.c b/src/rlang/arg.c index d9d948352..0bc74bb10 100644 --- a/src/rlang/arg.c +++ b/src/rlang/arg.c @@ -1,7 +1,11 @@ #include "rlang.h" -int (*r_arg_match)(r_obj* arg, r_obj* values, r_obj* error_arg, r_obj* error_call); +int (*r_arg_match)(r_obj* arg, + r_obj* values, + struct r_lazy error_arg, + struct r_lazy error_call); void r_init_library_arg() { - r_arg_match = (int (*)(r_obj*, r_obj*, r_obj*, r_obj*)) r_peek_c_callable("rlang", "rlang_arg_match"); + r_arg_match = (int (*)(r_obj*, r_obj*, struct r_lazy, struct r_lazy)) + r_peek_c_callable("rlang", "rlang_arg_match_2"); } diff --git a/src/rlang/arg.h b/src/rlang/arg.h index f66bee74e..b49ccc136 100644 --- a/src/rlang/arg.h +++ b/src/rlang/arg.h @@ -2,7 +2,10 @@ #define RLANG_ARG_H -extern int (*r_arg_match)(r_obj* arg, r_obj* values, r_obj* error_arg, r_obj* error_call); +extern int (*r_arg_match)(r_obj* arg, + r_obj* values, + struct r_lazy error_arg, + struct r_lazy error_call); #endif diff --git a/src/rlang/c-utils.h b/src/rlang/c-utils.h index 9aa028aaa..fbb5b7ff6 100644 --- a/src/rlang/c-utils.h +++ b/src/rlang/c-utils.h @@ -6,6 +6,8 @@ #include "cnd.h" #define R_ARR_SIZEOF(X) sizeof(X) / sizeof(X[0]) +#define R_MIN(a, b) ((a) < (b) ? (a) : (b)) +#define R_MAX(a, b) ((a) > (b) ? (a) : (b)) // Like `memset()` with support for multi-byte types #define R_MEM_SET(TYPE, PTR, VALUE, N) do { \ diff --git a/src/rlang/cnd.c b/src/rlang/cnd.c index 71ad36167..2a738dcd2 100644 --- a/src/rlang/cnd.c +++ b/src/rlang/cnd.c @@ -54,16 +54,6 @@ void r_abort(const char* fmt, ...) { while (1); // No return } -r_no_return -void (r_stop_c_internal)(const char* file, - int line, - const char* fn, - const char* fmt, ...) { - char buf[BUFSIZE]; - INTERP(buf, fmt, ...); - r_abort("TODO"); -} - r_no_return void r_abort_n(const struct r_pair* args, int n) { r_exec_mask_n(r_null, r_syms.abort, args, n, r_peek_frame()); @@ -169,6 +159,7 @@ void r_init_library_cnd() { r_stop_internal = (r_stop_internal_t) R_GetCCallable("rlang", "rlang_stop_internal2"); r_format_error_arg = (const char* (*)(r_obj*)) r_peek_c_callable("rlang", "rlang_format_error_arg"); + r_obj_type_friendly_full = (const char* (*)(r_obj*, bool, bool)) r_peek_c_callable("rlang", "rlang_obj_type_friendly_full"); } r_no_return @@ -182,3 +173,11 @@ static r_obj* cnd_signal_call = NULL; const char* (*r_format_error_arg)(r_obj* arg) = NULL; +const char* (*r_obj_type_friendly_full)(r_obj* x, bool value, bool length) = NULL; + +const char* r_format_lazy_error_arg(struct r_lazy arg) { + r_obj* ffi_arg = KEEP(r_lazy_eval(arg)); + const char* out = r_format_error_arg(ffi_arg); + FREE(1); + return out; +} diff --git a/src/rlang/cnd.h b/src/rlang/cnd.h index 694a6db03..d42362158 100644 --- a/src/rlang/cnd.h +++ b/src/rlang/cnd.h @@ -13,7 +13,19 @@ void r_no_return r_abort_call(r_obj* call, const char* fmt, ...); // Formats input as an argument, using cli if available. Returns a // vmax-protected string. -extern const char* (*r_format_error_arg)(r_obj* arg); +extern +const char* (*r_format_error_arg)(r_obj* arg); + +const char* r_format_lazy_error_arg(struct r_lazy arg); + +// Return vmax-protected strings +extern +const char* (*r_obj_type_friendly_full)(r_obj* x, bool value, bool length); + +static inline +const char* r_obj_type_friendly(r_obj* x) { + return r_obj_type_friendly_full(x, true, false); +} extern diff --git a/src/rlang/decl/env-decl.h b/src/rlang/decl/env-decl.h index afa683c23..839300196 100644 --- a/src/rlang/decl/env-decl.h +++ b/src/rlang/decl/env-decl.h @@ -1,8 +1,39 @@ +r_obj* eval_with_x(r_obj* call, r_obj* x); +r_obj* eval_with_xy(r_obj* call, r_obj* x, r_obj* y); +r_obj* eval_with_xyz(r_obj* call, r_obj* x, r_obj* y, r_obj* z); + +static +r_obj* new_env_call; + +static +r_obj* new_env__parent_node; + static -r_obj* env_clone_roundtrip(r_obj* env, r_obj* parent); +r_obj* new_env__size_node; static r_obj* exists_call; static r_obj* remove_call; + +static +r_obj* poke_lazy_call; + +static +r_obj* poke_lazy_value_node; + + +static +r_obj* env2list_call; + +static +r_obj* list2env_call; + +#if R_VERSION < R_Version(4, 0, 0) +static +r_obj* env_as_list_compat(r_obj* env, r_obj* out); +#endif + +static +void env_coalesce_plain(r_obj* env, r_obj* from, r_obj* nms); diff --git a/src/rlang/env-binding.c b/src/rlang/env-binding.c index 7ea3db09f..8e38c675c 100644 --- a/src/rlang/env-binding.c +++ b/src/rlang/env-binding.c @@ -20,14 +20,16 @@ static r_obj* new_binding_types(r_ssize n) { } static enum r_env_binding_type which_env_binding(r_obj* env, r_obj* sym) { - if (r_env_binding_is_promise(env, sym)) { - return R_ENV_BINDING_TYPE_promise; - } - if (r_env_binding_is_active(env, sym)) { + // Check for active bindings first, since promise detection triggers + // active bindings through `r_env_find()` (#1376) return R_ENV_BINDING_TYPE_active; } + if (r_env_binding_is_promise(env, sym)) { + return R_ENV_BINDING_TYPE_promise; + } + return R_ENV_BINDING_TYPE_value; } diff --git a/src/rlang/env.c b/src/rlang/env.c index a323c2201..9dab9c492 100644 --- a/src/rlang/env.c +++ b/src/rlang/env.c @@ -1,10 +1,8 @@ #include "rlang.h" - #include "decl/env-decl.h" -r_obj* eval_with_x(r_obj* call, r_obj* x); -r_obj* eval_with_xy(r_obj* call, r_obj* x, r_obj* y); -r_obj* eval_with_xyz(r_obj* call, r_obj* x, r_obj* y, r_obj* z); + +r_obj* rlang_ns_env; r_obj* r_ns_env(const char* pkg) { @@ -20,7 +18,7 @@ r_obj* ns_env_get(r_obj* env, const char* name) { r_obj* obj = KEEP(r_env_find(env, r_sym(name))); // Can be a promise to a lazyLoadDBfetch() call - if (r_typeof(obj) == PROMSXP) { + if (r_typeof(obj) == R_TYPE_promise) { obj = r_eval(obj, r_envs.empty); } if (obj != r_syms.unbound) { @@ -37,17 +35,11 @@ r_obj* r_base_ns_get(const char* name) { } -r_obj* rlang_ns_env = NULL; - r_obj* rlang_ns_get(const char* name) { return ns_env_get(rlang_ns_env, name); } -static r_obj* new_env_call = NULL; -static r_obj* new_env__parent_node = NULL; -static r_obj* new_env__size_node = NULL; - r_obj* r_alloc_environment(r_ssize size, r_obj* parent) { parent = parent ? parent : r_envs.empty; r_node_poke_car(new_env__parent_node, parent); @@ -64,16 +56,11 @@ r_obj* r_alloc_environment(r_ssize size, r_obj* parent) { } -static r_obj* env2list_call = NULL; -static r_obj* list2env_call = NULL; - -r_obj* r_env_as_list_compat(r_obj* env, r_obj* out); - r_obj* r_env_as_list(r_obj* env) { r_obj* out = KEEP(eval_with_x(env2list_call, env)); #if R_VERSION < R_Version(4, 0, 0) - out = r_env_as_list_compat(env, out); + out = env_as_list_compat(env, out); #endif FREE(1); @@ -83,11 +70,12 @@ r_obj* r_env_as_list(r_obj* env) { // On R < 4.0, the active binding function is returned instead of // its value. We invoke the active bindings here to get consistent // behaviour in all supported R versions. -r_obj* r_env_as_list_compat(r_obj* env, r_obj* out) { +#if R_VERSION < R_Version(4, 0, 0) +r_obj* env_as_list_compat(r_obj* env, r_obj* out) { r_obj* nms = KEEP(r_env_names(env)); r_obj* types = KEEP(r_env_binding_types(env, nms)); - if (types == R_NilValue) { + if (types == r_null) { FREE(2); return out; } @@ -114,71 +102,96 @@ r_obj* r_env_as_list_compat(r_obj* env, r_obj* out) { FREE(2); return out; } +#endif r_obj* r_env_clone(r_obj* env, r_obj* parent) { if (parent == NULL) { parent = r_env_parent(env); } - r_obj* nms = KEEP(r_env_names(env)); - r_obj* types = KEEP(r_env_binding_types(env, nms)); + // This better reproduces the behaviour of `list2env()` which in + // turn affects how bindings are stored in the hash table and the + // default sort of the character vector generated by `names()`. + size_t size = R_MAX(r_length(env), 29); + + r_obj* out = KEEP(r_alloc_environment(size, parent)); + r_env_coalesce(out, env); + + FREE(1); + return out; +} + +void r_env_coalesce(r_obj* env, r_obj* from) { + r_obj* nms = KEEP(r_env_names(from)); + r_obj* types = KEEP(r_env_binding_types(from, nms)); if (types == r_null) { + env_coalesce_plain(env, from, nms); FREE(2); - return env_clone_roundtrip(env, parent); + return; } - r_ssize n = r_length(nms); - -#if R_VERSION < R_Version(4, 0, 0) // In older R versions there is no way of accessing the function of // an active binding except through env2list. This makes it // impossible to preserve active bindings without forcing promises. - - r_obj* env_list = KEEP(eval_with_x(env2list_call, env)); - r_obj* out = KEEP(r_list_as_environment(env_list, parent)); +#if R_VERSION < R_Version(4, 0, 0) + r_obj* from_list = KEEP(eval_with_x(env2list_call, from)); #else - r_obj* out = KEEP(r_alloc_environment(n, parent)); KEEP(r_null); #endif + r_ssize n = r_length(nms); r_obj* const * v_nms = r_chr_cbegin(nms); enum r_env_binding_type* v_types = (enum r_env_binding_type*) r_int_begin(types); - for (r_ssize i = 0; i < n; ++i, ++v_nms, ++v_types) { - r_obj* sym = r_str_as_symbol(*v_nms); + for (r_ssize i = 0; i < n; ++i) { + r_obj* sym = r_str_as_symbol(v_nms[i]); - switch (*v_types) { + if (r_env_has(env, sym)) { + continue; + } + + switch (v_types[i]) { case R_ENV_BINDING_TYPE_value: case R_ENV_BINDING_TYPE_promise: - r_env_poke(out, sym, r_env_find(env, sym)); + r_env_poke(env, sym, r_env_find(from, sym)); break; case R_ENV_BINDING_TYPE_active: { #if R_VERSION < R_Version(4, 0, 0) r_ssize fn_idx = r_chr_detect_index(nms, r_sym_c_string(sym)); if (fn_idx < 0) { - r_abort("Internal error: Can't find active binding in temporary list"); + r_stop_internal("Can't find active binding in temporary list."); } - r_obj* fn = r_list_get(env_list, fn_idx); + r_obj* fn = r_list_get(from_list, fn_idx); #else - r_obj* fn = R_ActiveBindingFunction(sym, env); + r_obj* fn = R_ActiveBindingFunction(sym, from); #endif - r_env_poke_active(out, sym, fn); + r_env_poke_active(env, sym, fn); break; }} } - FREE(4); - return out; + FREE(3); + return; } static -r_obj* env_clone_roundtrip(r_obj* env, r_obj* parent) { - r_obj* out_list = KEEP(r_env_as_list(env)); - r_obj* out = r_list_as_environment(out_list, parent); - FREE(1); - return(out); +void env_coalesce_plain(r_obj* env, r_obj* from, r_obj* nms) { + r_ssize n = r_length(nms); + r_obj* const * v_nms = r_chr_cbegin(nms); + + for (r_ssize i = 0; i < n; ++i) { + r_obj* sym = r_str_as_symbol(v_nms[i]); + + if (r_env_has(env, sym)) { + continue; + } + + r_env_poke(env, sym, r_env_find(from, sym)); + } + + return; } r_obj* r_list_as_environment(r_obj* x, r_obj* parent) { @@ -186,9 +199,6 @@ r_obj* r_list_as_environment(r_obj* x, r_obj* parent) { return eval_with_xy(list2env_call, x, parent); } -static r_obj* poke_lazy_call = NULL; -static r_obj* poke_lazy_value_node = NULL; - void r_env_poke_lazy(r_obj* env, r_obj* sym, r_obj* expr, r_obj* eval_env) { KEEP(expr); r_obj* name = KEEP(r_sym_as_utf8_character(sym)); @@ -276,8 +286,6 @@ void r_init_rlang_ns_env() { rlang_ns_env = r_ns_env("rlang"); } -r_obj* r_methods_ns_env = NULL; - void r_init_library_env() { new_env_call = r_parse_eval("as.call(list(new.env, TRUE, NULL, NULL))", r_envs.base); r_preserve(new_env_call); @@ -305,9 +313,32 @@ void r_init_library_env() { r_methods_ns_env = r_parse_eval("asNamespace('methods')", r_envs.base); } +r_obj* rlang_ns_env = NULL; +r_obj* r_methods_ns_env = NULL; + +static +r_obj* new_env_call = NULL; + +static +r_obj* new_env__parent_node = NULL; + +static +r_obj* new_env__size_node = NULL; static r_obj* exists_call = NULL; static r_obj* remove_call = NULL; + +static +r_obj* poke_lazy_call = NULL; + +static +r_obj* poke_lazy_value_node = NULL; + +static +r_obj* env2list_call = NULL; + +static +r_obj* list2env_call = NULL; diff --git a/src/rlang/env.h b/src/rlang/env.h index b2552b524..a2758d3cc 100644 --- a/src/rlang/env.h +++ b/src/rlang/env.h @@ -85,6 +85,8 @@ r_obj* r_env_as_list(r_obj* x); r_obj* r_list_as_environment(r_obj* x, r_obj* parent); r_obj* r_env_clone(r_obj* env, r_obj* parent); +void r_env_coalesce(r_obj* env, r_obj* from); + // Silently ignores bindings that are not defined in `env`. static inline diff --git a/src/rlang/eval.c b/src/rlang/eval.c index 087db18b5..ce581c5d8 100644 --- a/src/rlang/eval.c +++ b/src/rlang/eval.c @@ -166,3 +166,11 @@ r_obj* r_exec_mask_n_call_poke(r_obj* fn_sym, FREE(1); return call; } + + +void r_init_library_eval() { + r_lazy_missing_arg = (struct r_lazy) { .x = r_missing_arg, .env = r_null }; +} + +struct r_lazy r_lazy_null = { 0 }; +struct r_lazy r_lazy_missing_arg = { 0 }; diff --git a/src/rlang/eval.h b/src/rlang/eval.h index 3e8d72574..128f77194 100644 --- a/src/rlang/eval.h +++ b/src/rlang/eval.h @@ -143,4 +143,37 @@ r_obj* r_exec_mask7(r_obj* fn_sym, r_obj* fn, } +static inline +r_obj* r_lazy_eval(struct r_lazy lazy) { + if (!lazy.env) { + // Unitialised lazy variable + return r_null; + } else if (lazy.env == r_null) { + // Forced lazy variable + return lazy.x; + } else { + return r_eval(lazy.x, lazy.env); + } +} + +extern +struct r_lazy r_lazy_null; + +extern +struct r_lazy r_lazy_missing_arg; + +static inline +r_obj* r_lazy_eval_protect(struct r_lazy lazy) { + r_obj* out = KEEP(r_lazy_eval(lazy)); + out = r_expr_protect(out); + + FREE(1); + return out; +} + +static inline +bool r_lazy_is_null(struct r_lazy call) { + return !call.x && !call.env; +} + #endif diff --git a/src/rlang/globals.c b/src/rlang/globals.c index b588af2a1..c42e47c72 100644 --- a/src/rlang/globals.c +++ b/src/rlang/globals.c @@ -57,6 +57,7 @@ void r_init_library_globals(r_obj* ns) { void r_init_library_globals_syms() { r_syms.abort = r_sym("abort"); + r_syms.arg = r_sym("arg"); r_syms.brackets = R_BracketSymbol; r_syms.brackets2 = R_Bracket2Symbol; r_syms.call = r_sym("call"); @@ -66,6 +67,8 @@ void r_init_library_globals_syms() { r_syms.condition = r_sym("condition"); r_syms.dots = R_DotsSymbol; r_syms.error = r_sym("error"); + r_syms.error_arg = r_sym("error_arg"); + r_syms.error_call = r_sym("error_call"); r_syms.error_call_flag = r_sym(".__error_call__."); r_syms.expr = r_sym("expr"); r_syms.interrupt = r_sym("interrupt"); diff --git a/src/rlang/globals.h b/src/rlang/globals.h index 27c27a50d..89faf36dc 100644 --- a/src/rlang/globals.h +++ b/src/rlang/globals.h @@ -41,6 +41,7 @@ struct r_globals_strs { struct r_globals_syms { r_obj* abort; + r_obj* arg; r_obj* brackets; r_obj* brackets2; r_obj* call; @@ -54,6 +55,8 @@ struct r_globals_syms { r_obj* dot_x; r_obj* dot_y; r_obj* error; + r_obj* error_arg; + r_obj* error_call; r_obj* error_call_flag; r_obj* expr; r_obj* function; diff --git a/src/rlang/obj.c b/src/rlang/obj.c index 5a4567e71..9f1762a24 100644 --- a/src/rlang/obj.c +++ b/src/rlang/obj.c @@ -7,6 +7,33 @@ struct r_dict* p_precious_dict = NULL; #include "decl/obj-decl.h" + +r_obj* r_vec_clone(r_obj* x) { + r_obj* out = KEEP(r_clone(x)); + + r_obj* names = r_names(x); + if (names != r_null) { + r_attrib_poke_names(out, r_clone(names)); + } + + FREE(1); + return out; +} + +r_obj* r_vec_clone_shared(r_obj* x) { + if (r_is_shared(x)) { + return r_vec_clone(x); + } + + r_obj* names = r_names(x); + if (names != r_null && r_is_shared(names)) { + r_attrib_poke_names(x, r_clone(names)); + return x; + } + + return x; +} + void (_r_preserve)(r_obj* x) { if (!_r_use_local_precious_list) { return; diff --git a/src/rlang/obj.h b/src/rlang/obj.h index ffdd2a41c..e836d3a89 100644 --- a/src/rlang/obj.h +++ b/src/rlang/obj.h @@ -81,6 +81,10 @@ r_obj* r_clone_shared(r_obj* x) { return r_is_shared(x) ? r_clone(x) : x; } +// These also clone names +r_obj* r_vec_clone(r_obj* x); +r_obj* r_vec_clone_shared(r_obj* x); + static inline r_obj* r_poke_type(r_obj* x, enum r_type type) { SET_TYPEOF(x, type); diff --git a/src/rlang/rlang-types.h b/src/rlang/rlang-types.h index bd37e7c11..0dd2e82ff 100644 --- a/src/rlang/rlang-types.h +++ b/src/rlang/rlang-types.h @@ -89,6 +89,11 @@ struct r_pair_callback { void* data; }; +struct r_lazy { + r_obj* x; + r_obj* env; +}; + #define KEEP PROTECT #define FREE UNPROTECT diff --git a/src/rlang/rlang.c b/src/rlang/rlang.c index 54fb9b105..9fcc9db62 100644 --- a/src/rlang/rlang.c +++ b/src/rlang/rlang.c @@ -94,6 +94,7 @@ r_obj* r_init_library(r_obj* ns) { r_init_library_cnd(); r_init_library_dyn_array(); r_init_library_env(); + r_init_library_eval(); r_init_library_fn(); r_init_library_quo(); r_init_library_session(); diff --git a/src/rlang/rlang.h b/src/rlang/rlang.h index 60d6408dc..7e71e4b07 100644 --- a/src/rlang/rlang.h +++ b/src/rlang/rlang.h @@ -75,4 +75,8 @@ bool _r_use_local_precious_list; #include "walk.h" +#define r_abort_lazy_call(LAZY, ...) \ + r_abort_call(KEEP(r_lazy_eval(LAZY)), __VA_ARGS__) + + #endif diff --git a/src/rlang/session.c b/src/rlang/session.c index fece96b7c..ccd50a309 100644 --- a/src/rlang/session.c +++ b/src/rlang/session.c @@ -32,3 +32,46 @@ void r_init_library_session() { has_colour_call = r_parse("crayon::has_color()"); r_preserve(has_colour_call); } + + +#ifdef _WIN32 + +# include +# include + +r_obj* r_getppid() { + DWORD pid = GetCurrentProcessId(); + HANDLE handle = NULL; + PROCESSENTRY32W pe = { 0 }; + + pe.dwSize = sizeof(PROCESSENTRY32W); + handle = CreateToolhelp32Snapshot(TH32CS_SNAPPROCESS, 0); + if (handle == INVALID_HANDLE_VALUE) { + r_abort("Can't query parent pid."); + } + + if (Process32FirstW(handle, &pe)) { + do { + if (pe.th32ProcessID == pid) { + DWORD ppid = pe.th32ParentProcessID; + CloseHandle(handle); + return r_int(ppid); + } + } while (Process32NextW(handle, &pe)); + } + + /* Should not get here */ + CloseHandle(handle); + r_stop_internal("Can't find my own process."); + return r_null; +} + +#else + +# include + +r_obj* r_getppid() { + return r_int(getppid()); +} + +#endif diff --git a/src/rlang/session.h b/src/rlang/session.h index e36eeba72..cf4ba4454 100644 --- a/src/rlang/session.h +++ b/src/rlang/session.h @@ -4,6 +4,7 @@ bool r_is_installed(const char* pkg); bool r_has_colour(); +r_obj* r_getppid(); #endif diff --git a/src/rlang/vec-lgl.c b/src/rlang/vec-lgl.c index 4e43b5eb9..2adb34816 100644 --- a/src/rlang/vec-lgl.c +++ b/src/rlang/vec-lgl.c @@ -26,32 +26,65 @@ r_ssize r_lgl_sum(r_obj* x, bool na_true) { } r_obj* r_lgl_which(r_obj* x, bool na_propagate) { - if (r_typeof(x) != R_TYPE_logical) { - r_abort("Internal error: Expected logical vector in `r_lgl_which()`"); + const enum r_type type = r_typeof(x); + + if (type != R_TYPE_logical) { + r_stop_unexpected_type(type); } - r_ssize n = r_length(x); - const int* p_x = r_lgl_cbegin(x); + const r_ssize n = r_length(x); + const int* v_x = r_lgl_cbegin(x); - r_ssize which_n = r_lgl_sum(x, na_propagate); + r_obj* names = r_names(x); + const bool has_names = names != r_null; + r_obj* const* v_names = NULL; + if (has_names) { + v_names = r_chr_cbegin(names); + } + + const r_ssize which_n = r_lgl_sum(x, na_propagate); if (which_n > INT_MAX) { - r_abort("Internal error: Can't fit result of `r_lgl_which()` in an integer vector"); + r_stop_internal("Can't fit result in an integer vector."); } r_obj* which = KEEP(r_alloc_integer(which_n)); - int* p_which = r_int_begin(which); - - for (int i = 0; i < n; ++i) { - int elt = p_x[i]; - - if (elt) { - if (na_propagate && elt == r_globals.na_lgl) { - *p_which = r_globals.na_int; - ++p_which; - } else if (elt != r_globals.na_lgl) { - *p_which = i + 1; - ++p_which; + int* v_which = r_int_begin(which); + + r_obj* which_names = r_null; + if (has_names) { + which_names = r_alloc_character(which_n); + r_attrib_poke_names(which, which_names); + } + + r_ssize j = 0; + + if (na_propagate) { + for (r_ssize i = 0; i < n; ++i) { + const int elt = v_x[i]; + + if (elt != 0) { + v_which[j] = (elt == r_globals.na_lgl) ? r_globals.na_int : i + 1; + + if (has_names) { + r_chr_poke(which_names, j, v_names[i]); + } + + ++j; + } + } + } else { + for (r_ssize i = 0; i < n; ++i) { + const int elt = v_x[i]; + + if (elt == 1) { + v_which[j] = i + 1; + + if (has_names) { + r_chr_poke(which_names, j, v_names[i]); + } + + ++j; } } } diff --git a/src/rlang/vec.h b/src/rlang/vec.h index c1b745ba4..33392dff9 100644 --- a/src/rlang/vec.h +++ b/src/rlang/vec.h @@ -339,7 +339,7 @@ bool r_is_string(r_obj* x) { static inline bool r_arg_as_bool(r_obj* x, const char* arg) { if (!r_is_bool(x)) { - r_abort("`%s` must be a logical value.", arg); + r_abort("`%s` must be `TRUE` or `FALSE`.", arg); } return r_lgl_get(x, 0); } @@ -351,7 +351,7 @@ bool r_as_bool(r_obj* x) { static inline int r_arg_as_int(r_obj* x, const char* arg) { if (!r_is_int(x)) { - r_abort("`%s` must be an integer value.", arg); + r_abort("`%s` must be a single integer value.", arg); } return r_int_get(x, 0); } @@ -364,7 +364,7 @@ static inline double r_arg_as_double(r_obj* x, const char* arg) { // TODO: Coercion of int and lgl values if (!_r_is_double(x, 1, 1)) { - r_abort("`%s` must be a double value.", arg); + r_abort("`%s` must be a single double value.", arg); } return r_dbl_get(x, 0); } @@ -376,7 +376,7 @@ double r_as_double(r_obj* x) { static inline r_complex r_arg_as_complex(r_obj* x, const char* arg) { if (!_r_is_complex(x, 1, 1)) { - r_abort("`%s` must be a complex value.", arg); + r_abort("`%s` must be a single complex value.", arg); } return r_cpl_get(x, 0); } @@ -388,7 +388,7 @@ r_complex r_as_complex(r_obj* x) { static inline char r_arg_as_char(r_obj* x, const char* arg) { if (r_typeof(x) != R_TYPE_raw && r_length(x) != 1) { - r_abort("`%s` must be a raw value.", arg); + r_abort("`%s` must be a single raw value.", arg); } return r_raw_get(x, 0); } diff --git a/src/size.c b/src/size.c index 30eabb0a3..4048e04e0 100644 --- a/src/size.c +++ b/src/size.c @@ -83,7 +83,7 @@ r_obj* list_sizes(r_obj* x, const struct vec_error_opts* opts) { r_abort_lazy_call(opts->call, "%s must be a list, not %s.", r_c_str_format_error_arg("x"), - r_friendly_type_of(x)); + r_obj_type_friendly(x)); } r_ssize size = vec_size(x); @@ -331,6 +331,6 @@ r_ssize vec_as_ssize(r_obj* n, r_abort_lazy_call(call, "%s must be a single number, not %s.", vec_arg_format(p_arg), - r_friendly_type_of_length(n)); + r_obj_type_friendly_length(n)); } } diff --git a/src/utils.c b/src/utils.c index caed38ba4..81bf6b84a 100644 --- a/src/utils.c +++ b/src/utils.c @@ -1552,7 +1552,6 @@ SEXP syms_y_size = NULL; SEXP syms_to = NULL; SEXP syms_dots = NULL; SEXP syms_bracket = NULL; -SEXP syms_arg = NULL; SEXP syms_x_arg = NULL; SEXP syms_y_arg = NULL; SEXP syms_to_arg = NULL; @@ -1646,8 +1645,6 @@ void c_print_backtrace() { } -struct r_lazy r_lazy_null; - void vctrs_init_utils(SEXP ns) { vctrs_ns_env = ns; @@ -1822,7 +1819,6 @@ void vctrs_init_utils(SEXP ns) { syms_to = Rf_install("to"); syms_dots = Rf_install("..."); syms_bracket = Rf_install("["); - syms_arg = Rf_install("arg"); syms_x_arg = Rf_install("x_arg"); syms_y_arg = Rf_install("y_arg"); syms_to_arg = Rf_install("to_arg"); @@ -1928,8 +1924,6 @@ void vctrs_init_utils(SEXP ns) { UNPROTECT(4); } - r_lazy_null = (struct r_lazy) { 0 }; - // We assume the following in `union vctrs_dbl_indicator` VCTRS_ASSERT(sizeof(double) == sizeof(int64_t)); VCTRS_ASSERT(sizeof(double) == 2 * sizeof(int)); diff --git a/src/utils.h b/src/utils.h index a918941a3..8734e3cc2 100644 --- a/src/utils.h +++ b/src/utils.h @@ -453,7 +453,6 @@ extern SEXP syms_y_size; extern SEXP syms_to; extern SEXP syms_dots; extern SEXP syms_bracket; -extern SEXP syms_arg; extern SEXP syms_x_arg; extern SEXP syms_y_arg; extern SEXP syms_to_arg; diff --git a/tests/testthat/_snaps/type-data-frame.md b/tests/testthat/_snaps/type-data-frame.md index c92043676..9d1bcf387 100644 --- a/tests/testthat/_snaps/type-data-frame.md +++ b/tests/testthat/_snaps/type-data-frame.md @@ -226,7 +226,7 @@ df_list(.unpack = 1) Condition Error in `df_list()`: - ! `.unpack` must be a logical value. + ! `.unpack` must be `TRUE` or `FALSE`. --- @@ -234,7 +234,7 @@ df_list(.unpack = c(TRUE, FALSE)) Condition Error in `df_list()`: - ! `.unpack` must be a logical value. + ! `.unpack` must be `TRUE` or `FALSE`. # data frame fallback handles column types (#999) From ca5f3ed1edffca60f56bf8357012db8fda5d1173 Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Fri, 9 Sep 2022 08:59:19 +0200 Subject: [PATCH 029/312] Export `vec_as_indices()` from header --- src/c-unchop.c | 4 ---- src/slice-chop.c | 10 ++++------ src/slice-chop.h | 10 ++++++++++ src/vctrs.h | 1 + 4 files changed, 15 insertions(+), 10 deletions(-) create mode 100644 src/slice-chop.h diff --git a/src/c-unchop.c b/src/c-unchop.c index 351bc9211..e2a127478 100644 --- a/src/c-unchop.c +++ b/src/c-unchop.c @@ -1,9 +1,5 @@ #include "vctrs.h" -// Defined in slice-chop.c -SEXP vec_as_indices(SEXP indices, R_len_t n, SEXP names); - - static SEXP vec_unchop(SEXP x, SEXP indices, SEXP ptype, diff --git a/src/slice-chop.c b/src/slice-chop.c index 1627aae76..1c4c97ae8 100644 --- a/src/slice-chop.c +++ b/src/slice-chop.c @@ -72,8 +72,6 @@ static SEXP chop_fallback_shaped(SEXP x, SEXP indices, struct vctrs_chop_info in static SEXP vec_chop_base(SEXP x, SEXP indices, struct vctrs_chop_info info); -SEXP vec_as_indices(SEXP indices, R_len_t n, SEXP names); - // [[ register() ]] SEXP vctrs_chop_seq(SEXP x, SEXP starts, SEXP sizes, SEXP increasings) { int* p_starts = INTEGER(starts); @@ -359,7 +357,7 @@ static SEXP chop_fallback(SEXP x, SEXP indices, struct vctrs_chop_info info) { return info.out; } -static SEXP chop_fallback_shaped(SEXP x, SEXP indices, struct vctrs_chop_info info) { +static r_obj* chop_fallback_shaped(r_obj* x, r_obj* indices, struct vctrs_chop_info info) { for (R_len_t i = 0; i < info.out_size; ++i) { if (info.has_indices) { info.index = VECTOR_ELT(indices, i); @@ -368,7 +366,7 @@ static SEXP chop_fallback_shaped(SEXP x, SEXP indices, struct vctrs_chop_info in } // `vec_slice_fallback()` will also `vec_restore()` for us - SEXP elt = PROTECT(vec_slice_fallback(x, info.index)); + r_obj* elt = PROTECT(vec_slice_fallback(x, info.index)); SET_VECTOR_ELT(info.out, i, elt); UNPROTECT(1); @@ -379,7 +377,7 @@ static SEXP chop_fallback_shaped(SEXP x, SEXP indices, struct vctrs_chop_info in // ----------------------------------------------------------------------------- -SEXP vec_as_indices(SEXP indices, R_len_t n, SEXP names) { +SEXP vec_as_indices(SEXP indices, r_ssize n, SEXP names) { if (indices == R_NilValue) { return indices; } @@ -390,7 +388,7 @@ SEXP vec_as_indices(SEXP indices, R_len_t n, SEXP names) { indices = PROTECT(r_clone_referenced(indices)); - R_len_t size = vec_size(indices); + r_ssize size = vec_size(indices); // Restrict index values to positive integer locations const struct location_opts opts = { diff --git a/src/slice-chop.h b/src/slice-chop.h new file mode 100644 index 000000000..1ee008450 --- /dev/null +++ b/src/slice-chop.h @@ -0,0 +1,10 @@ +#ifndef VCTRS_SLICE_CHOP_H +#define VCTRS_SLICE_CHOP_H + +#include "vctrs-core.h" + + +r_obj* vec_as_indices(r_obj* indices, r_ssize n, r_obj* names); + + +#endif diff --git a/src/vctrs.h b/src/vctrs.h index e08792f39..33a2d641e 100644 --- a/src/vctrs.h +++ b/src/vctrs.h @@ -49,6 +49,7 @@ bool vec_is_unspecified(SEXP x); #include "size.h" #include "slice-assign.h" #include "slice.h" +#include "slice-chop.h" #include "strides.h" #include "subscript-loc.h" #include "subscript.h" From 222d76f6f4f0b994f7940143c916f45ef8c558da Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Fri, 9 Sep 2022 09:05:23 +0200 Subject: [PATCH 030/312] Update style in `c-unchop.c` --- R/slice-chop.R | 2 +- src/c-unchop.c | 236 +++++++++++++++++++-------------------- src/c-unchop.h | 9 ++ src/decl/c-unchop-decl.h | 14 +++ src/init.c | 4 +- 5 files changed, 144 insertions(+), 121 deletions(-) create mode 100644 src/c-unchop.h create mode 100644 src/decl/c-unchop-decl.h diff --git a/R/slice-chop.R b/R/slice-chop.R index 5cef57052..4cdbcfdd7 100644 --- a/R/slice-chop.R +++ b/R/slice-chop.R @@ -97,7 +97,7 @@ vec_unchop <- function(x, ptype = NULL, name_spec = NULL, name_repair = c("minimal", "unique", "check_unique", "universal")) { - .Call(vctrs_unchop, x, indices, ptype, name_spec, name_repair) + .Call(ffi_vec_unchop, x, indices, ptype, name_spec, name_repair) } # Exposed for testing (`starts` is 0-based) diff --git a/src/c-unchop.c b/src/c-unchop.c index e2a127478..5f3206d13 100644 --- a/src/c-unchop.c +++ b/src/c-unchop.c @@ -1,247 +1,247 @@ +#include "rlang-types.h" #include "vctrs.h" -static SEXP vec_unchop(SEXP x, - SEXP indices, - SEXP ptype, - SEXP name_spec, - const struct name_repair_opts* name_repair); - -// [[ register() ]] -SEXP vctrs_unchop(SEXP x, SEXP indices, SEXP ptype, SEXP name_spec, SEXP name_repair) { - struct name_repair_opts name_repair_opts = new_name_repair_opts(name_repair, - vec_args.empty, - false, - r_lazy_null); - KEEP(name_repair_opts.shelter); - - SEXP out = vec_unchop(x, indices, ptype, name_spec, &name_repair_opts); - - FREE(1); - return out; -} - enum fallback_homogeneous { FALLBACK_HOMOGENEOUS_false = 0, FALLBACK_HOMOGENEOUS_true }; -static SEXP vec_unchop_fallback(SEXP ptype, - SEXP x, - SEXP indices, - SEXP name_spec, - const struct name_repair_opts* name_repair, - enum fallback_homogeneous homogenous); - -static SEXP vec_unchop(SEXP xs, - SEXP indices, - SEXP ptype, - SEXP name_spec, - const struct name_repair_opts* name_repair) { + +#include "decl/c-unchop-decl.h" + + +static +r_obj* vec_unchop(r_obj* xs, + r_obj* indices, + r_obj* ptype, + r_obj* name_spec, + const struct name_repair_opts* name_repair) { if (!vec_is_list(xs)) { - Rf_errorcall(R_NilValue, "`x` must be a list"); + r_abort("`x` must be a list."); } - if (indices == R_NilValue) { + if (indices == r_null) { return vec_c(xs, ptype, name_spec, name_repair); } - R_len_t xs_size = vec_size(xs); + r_ssize xs_size = vec_size(xs); // Apply size/type checking to `indices` before possibly exiting early from // having a `NULL` common type if (xs_size != vec_size(indices)) { - Rf_errorcall(R_NilValue, "`x` and `indices` must be lists of the same size"); + r_abort("`x` and `indices` must be lists of the same size."); } if (!vec_is_list(indices)) { - Rf_errorcall(R_NilValue, "`indices` must be a list of integers, or `NULL`"); + r_abort("`indices` must be a list of integers, or `NULL`."); } - ptype = PROTECT(vec_ptype_common_params(xs, - ptype, - DF_FALLBACK_DEFAULT, - S3_FALLBACK_true, - vec_args.empty, - r_lazy_null)); + ptype = KEEP(vec_ptype_common_params(xs, + ptype, + DF_FALLBACK_DEFAULT, + S3_FALLBACK_true, + vec_args.empty, + r_lazy_null)); if (needs_vec_c_fallback(ptype)) { - SEXP out = vec_unchop_fallback(ptype, xs, indices, name_spec, name_repair, FALLBACK_HOMOGENEOUS_false); - UNPROTECT(1); + r_obj* out = vec_unchop_fallback(ptype, xs, indices, name_spec, name_repair, FALLBACK_HOMOGENEOUS_false); + FREE(1); return out; } + // FIXME: Needed for dplyr::summarise() which passes a non-fallback ptype if (needs_vec_c_homogeneous_fallback(xs, ptype)) { - SEXP out = vec_unchop_fallback(ptype, xs, indices, name_spec, name_repair, FALLBACK_HOMOGENEOUS_true); - UNPROTECT(1); + r_obj* out = vec_unchop_fallback(ptype, xs, indices, name_spec, name_repair, FALLBACK_HOMOGENEOUS_true); + FREE(1); return out; } - if (ptype == R_NilValue) { - UNPROTECT(1); - return R_NilValue; + if (ptype == r_null) { + FREE(1); + return r_null; } - xs = PROTECT(vec_cast_common(xs, ptype, vec_args.empty, r_lazy_null)); + xs = KEEP(vec_cast_common(xs, ptype, vec_args.empty, r_lazy_null)); - bool assign_names = !Rf_inherits(name_spec, "rlang_zap"); - SEXP xs_names = PROTECT(r_names(xs)); - bool xs_is_named = xs_names != R_NilValue && !is_data_frame(ptype); + bool assign_names = !r_inherits(name_spec, "rlang_zap"); + r_obj* xs_names = KEEP(r_names(xs)); + bool xs_is_named = xs_names != r_null && !is_data_frame(ptype); - R_len_t out_size = 0; + r_ssize out_size = 0; // `out_size` is computed from `indices` - for (R_len_t i = 0; i < xs_size; ++i) { - SEXP x = VECTOR_ELT(xs, i); + for (r_ssize i = 0; i < xs_size; ++i) { + r_obj* x = r_list_get(xs, i); - if (x == R_NilValue) { + if (x == r_null) { continue; } - R_len_t index_size = Rf_length(VECTOR_ELT(indices, i)); + r_ssize index_size = r_length(r_list_get(indices, i)); out_size += index_size; // Each element of `xs` is recycled to its corresponding index's size x = vec_check_recycle(x, index_size, vec_args.empty, r_lazy_null); - SET_VECTOR_ELT(xs, i, x); + r_list_poke(xs, i, x); } - SEXP locs = PROTECT(vec_as_indices(indices, out_size, R_NilValue)); + r_obj* locs = KEEP(vec_as_indices(indices, out_size, r_null)); - SEXP proxy = vec_proxy(ptype); - PROTECT_INDEX proxy_pi; - PROTECT_WITH_INDEX(proxy, &proxy_pi); + r_obj* proxy = vec_proxy(ptype); + r_keep_loc proxy_pi; + KEEP_HERE(proxy, &proxy_pi); proxy = vec_init(proxy, out_size); - REPROTECT(proxy, proxy_pi); + KEEP_AT(proxy, proxy_pi); - SEXP out_names = R_NilValue; - PROTECT_INDEX out_names_pi; - PROTECT_WITH_INDEX(out_names, &out_names_pi); + r_obj* out_names = r_null; + r_keep_loc out_names_pi; + KEEP_HERE(out_names, &out_names_pi); const struct vec_assign_opts unchop_assign_opts = { .assign_names = assign_names, .ignore_outer_names = true }; - for (R_len_t i = 0; i < xs_size; ++i) { - SEXP x = VECTOR_ELT(xs, i); + for (r_ssize i = 0; i < xs_size; ++i) { + r_obj* x = r_list_get(xs, i); - if (x == R_NilValue) { + if (x == r_null) { continue; } - SEXP loc = VECTOR_ELT(locs, i); + r_obj* loc = r_list_get(locs, i); if (assign_names) { - R_len_t size = Rf_length(loc); - SEXP outer = xs_is_named ? STRING_ELT(xs_names, i) : R_NilValue; - SEXP inner = PROTECT(vec_names(x)); - SEXP x_nms = PROTECT(apply_name_spec(name_spec, outer, inner, size)); + r_ssize size = r_length(loc); + r_obj* outer = xs_is_named ? r_chr_get(xs_names, i) : r_null; + r_obj* inner = KEEP(vec_names(x)); + r_obj* x_nms = KEEP(apply_name_spec(name_spec, outer, inner, size)); - if (x_nms != R_NilValue) { - R_LAZY_ALLOC(out_names, out_names_pi, STRSXP, out_size); + if (x_nms != r_null) { + R_LAZY_ALLOC(out_names, out_names_pi, R_TYPE_character, out_size); // If there is no name to assign, skip the assignment since // `out_names` already contains empty strings if (x_nms != chrs_empty) { out_names = chr_assign(out_names, loc, x_nms, VCTRS_OWNED_true); - REPROTECT(out_names, out_names_pi); + KEEP_AT(out_names, out_names_pi); } } - UNPROTECT(2); + FREE(2); } // Total ownership of `proxy` because it was freshly created with `vec_init()` proxy = vec_proxy_assign_opts(proxy, loc, x, VCTRS_OWNED_true, &unchop_assign_opts); - REPROTECT(proxy, proxy_pi); + KEEP_AT(proxy, proxy_pi); } - SEXP out_size_sexp = PROTECT(r_int(out_size)); + r_obj* out_size_sexp = KEEP(r_int(out_size)); - SEXP out = PROTECT(vec_restore(proxy, ptype, out_size_sexp, VCTRS_OWNED_true)); + r_obj* out = KEEP(vec_restore(proxy, ptype, out_size_sexp, VCTRS_OWNED_true)); - if (out_names != R_NilValue) { - out_names = PROTECT(vec_as_names(out_names, name_repair)); + if (out_names != r_null) { + out_names = KEEP(vec_as_names(out_names, name_repair)); out = vec_set_names(out, out_names); - UNPROTECT(1); + FREE(1); } else if (!assign_names) { // FIXME: `vec_ptype2()` doesn't consistently zaps names, so `out` // might have been initialised with names. This branch can be // removed once #1020 is resolved. - out = vec_set_names(out, R_NilValue); + out = vec_set_names(out, r_null); } - UNPROTECT(8); + FREE(8); + return out; +} + +r_obj* ffi_vec_unchop(r_obj* x, + r_obj* indices, + r_obj* ptype, + r_obj* name_spec, + r_obj* name_repair) { + struct name_repair_opts name_repair_opts = + new_name_repair_opts(name_repair, + vec_args.empty, + false, + r_lazy_null); + KEEP(name_repair_opts.shelter); + + r_obj* out = vec_unchop(x, indices, ptype, name_spec, &name_repair_opts); + + FREE(1); return out; } + // This is essentially: // vec_slice_fallback(vec_c_fallback_invoke(!!!x), order(vec_c(!!!indices))) // with recycling of each element of `x` to the corresponding index size -static SEXP vec_unchop_fallback(SEXP ptype, - SEXP x, - SEXP indices, - SEXP name_spec, - const struct name_repair_opts* name_repair, - enum fallback_homogeneous homogeneous) { - R_len_t x_size = vec_size(x); - x = PROTECT(r_clone_referenced(x)); - - R_len_t out_size = 0; +static +r_obj* vec_unchop_fallback(r_obj* ptype, + r_obj* x, + r_obj* indices, + r_obj* name_spec, + const struct name_repair_opts* name_repair, + enum fallback_homogeneous homogeneous) { + r_ssize x_size = vec_size(x); + x = KEEP(r_clone_referenced(x)); + + r_ssize out_size = 0; // Recycle `x` elements to the size of their corresponding index - for (R_len_t i = 0; i < x_size; ++i) { - SEXP elt = VECTOR_ELT(x, i); + for (r_ssize i = 0; i < x_size; ++i) { + r_obj* elt = r_list_get(x, i); - R_len_t index_size = vec_size(VECTOR_ELT(indices, i)); + r_ssize index_size = vec_size(r_list_get(indices, i)); out_size += index_size; - SET_VECTOR_ELT(x, i, vec_recycle_fallback(elt, index_size, vec_args.empty)); + r_list_poke(x, i, vec_recycle_fallback(elt, index_size, vec_args.empty)); } - indices = PROTECT(vec_as_indices(indices, out_size, R_NilValue)); + indices = KEEP(vec_as_indices(indices, out_size, r_null)); - SEXP out = R_NilValue; + r_obj* out = r_null; if (homogeneous) { - out = PROTECT(vec_c_fallback_invoke(x, name_spec)); + out = KEEP(vec_c_fallback_invoke(x, name_spec)); } else { - out = PROTECT(vec_c_fallback(ptype, x, name_spec, name_repair)); + out = KEEP(vec_c_fallback(ptype, x, name_spec, name_repair)); } const struct name_repair_opts name_repair_opts = { .type = NAME_REPAIR_none, - .fn = R_NilValue + .fn = r_null }; - indices = PROTECT(vec_c( + indices = KEEP(vec_c( indices, r_globals.empty_int, - R_NilValue, + r_null, &name_repair_opts )); - const int* p_indices = INTEGER(indices); + const int* p_indices = r_int_cbegin(indices); - SEXP locations = PROTECT(Rf_allocVector(INTSXP, out_size)); - int* p_locations = INTEGER(locations); + r_obj* locations = KEEP(r_alloc_integer(out_size)); + int* p_locations = r_int_begin(locations); // Initialize with missing to handle locations that are never selected - for (R_len_t i = 0; i < out_size; ++i) { - p_locations[i] = NA_INTEGER; + for (r_ssize i = 0; i < out_size; ++i) { + p_locations[i] = r_globals.na_int; } - for (R_len_t i = 0; i < out_size; ++i) { + for (r_ssize i = 0; i < out_size; ++i) { const int index = p_indices[i]; - if (index == NA_INTEGER) { + if (index == r_globals.na_int) { continue; } p_locations[index - 1] = i + 1; } - out = PROTECT(vec_slice_fallback(out, locations)); + out = KEEP(vec_slice_fallback(out, locations)); - UNPROTECT(6); + FREE(6); return out; } diff --git a/src/c-unchop.h b/src/c-unchop.h new file mode 100644 index 000000000..d860298ad --- /dev/null +++ b/src/c-unchop.h @@ -0,0 +1,9 @@ +#ifndef VCTRS_C_UNCHOP_H +#define VCTRS_C_UNCHOP_H + +#include "vctrs-core.h" + + + + +#endif diff --git a/src/decl/c-unchop-decl.h b/src/decl/c-unchop-decl.h new file mode 100644 index 000000000..6f2ca4bdd --- /dev/null +++ b/src/decl/c-unchop-decl.h @@ -0,0 +1,14 @@ +static +r_obj* vec_unchop(r_obj* x, + r_obj* indices, + r_obj* ptype, + r_obj* name_spec, + const struct name_repair_opts* name_repair); + +static +r_obj* vec_unchop_fallback(r_obj* ptype, + r_obj* x, + r_obj* indices, + r_obj* name_spec, + const struct name_repair_opts* name_repair, + enum fallback_homogeneous homogenous); diff --git a/src/init.c b/src/init.c index 89b971d3f..df1faff20 100644 --- a/src/init.c +++ b/src/init.c @@ -49,7 +49,7 @@ extern r_obj* ffi_as_location(r_obj*, r_obj*, r_obj*, r_obj*, r_obj*, r_obj*, r_ extern r_obj* ffi_slice(r_obj*, r_obj*, r_obj*); extern r_obj* ffi_init(r_obj*, r_obj*, r_obj*); extern SEXP vctrs_chop(SEXP, SEXP); -extern SEXP vctrs_unchop(SEXP, SEXP, SEXP, SEXP, SEXP); +extern r_obj* ffi_vec_unchop(r_obj*, r_obj*, r_obj*, r_obj*, r_obj*); extern SEXP vctrs_chop_seq(SEXP, SEXP, SEXP, SEXP); extern r_obj* ffi_slice_seq(r_obj*, r_obj*, r_obj*, r_obj*); extern r_obj* ffi_slice_rep(r_obj*, r_obj*, r_obj*); @@ -218,7 +218,7 @@ static const R_CallMethodDef CallEntries[] = { {"ffi_slice", (DL_FUNC) &ffi_slice, 3}, {"ffi_init", (DL_FUNC) &ffi_init, 3}, {"vctrs_chop", (DL_FUNC) &vctrs_chop, 2}, - {"vctrs_unchop", (DL_FUNC) &vctrs_unchop, 5}, + {"ffi_vec_unchop", (DL_FUNC) &ffi_vec_unchop, 5}, {"vctrs_chop_seq", (DL_FUNC) &vctrs_chop_seq, 4}, {"ffi_slice_seq", (DL_FUNC) &ffi_slice_seq, 4}, {"ffi_slice_rep", (DL_FUNC) &ffi_slice_rep, 3}, From 7c9d973b3c432da00329ae9a1873236cabd07abb Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Fri, 9 Sep 2022 09:56:02 +0200 Subject: [PATCH 031/312] Update style in `c.c` --- R/c.R | 2 +- src/c.c | 269 +++++++++++++--------------- src/c.h | 33 ++-- src/decl/c-decl.h | 8 + src/init.c | 4 +- src/vctrs.h | 5 - tests/testthat/_snaps/c.md | 6 +- tests/testthat/_snaps/slice-chop.md | 6 +- 8 files changed, 163 insertions(+), 170 deletions(-) create mode 100644 src/decl/c-decl.h diff --git a/R/c.R b/R/c.R index be263bd89..28a4d36ab 100644 --- a/R/c.R +++ b/R/c.R @@ -66,7 +66,7 @@ vec_c <- function(..., .ptype = NULL, .name_spec = NULL, .name_repair = c("minimal", "unique", "check_unique", "universal")) { - .External2(vctrs_c, .ptype, .name_spec, .name_repair) + .External2(ffi_vec_c, .ptype, .name_spec, .name_repair) } vec_c <- fn_inline_formals(vec_c, ".name_repair") diff --git a/src/c.c b/src/c.c index a1b821cbd..4ec6ee49c 100644 --- a/src/c.c +++ b/src/c.c @@ -1,38 +1,10 @@ #include "vctrs.h" -#include "c.h" -#include "ptype-common.h" -#include "slice-assign.h" -#include "owned.h" -#include "utils.h" - - -// [[ register(external = TRUE) ]] -SEXP vctrs_c(SEXP call, SEXP op, SEXP args, SEXP env) { - args = CDR(args); - - SEXP xs = PROTECT(rlang_env_dots_list(env)); - SEXP ptype = PROTECT(Rf_eval(CAR(args), env)); args = CDR(args); - SEXP name_spec = PROTECT(Rf_eval(CAR(args), env)); args = CDR(args); - SEXP name_repair = PROTECT(Rf_eval(CAR(args), env)); - - struct name_repair_opts name_repair_opts = new_name_repair_opts(name_repair, - vec_args.empty, - false, - r_lazy_null); - KEEP(name_repair_opts.shelter); - - SEXP out = vec_c(xs, ptype, name_spec, &name_repair_opts); - - UNPROTECT(5); - return out; -} +#include "decl/c-decl.h" - -// [[ include("vctrs.h") ]] -SEXP vec_c(SEXP xs, - SEXP ptype, - SEXP name_spec, - const struct name_repair_opts* name_repair) { +r_obj* vec_c(r_obj* xs, + r_obj* ptype, + r_obj* name_spec, + const struct name_repair_opts* name_repair) { struct fallback_opts opts = { .df = DF_FALLBACK_DEFAULT, .s3 = S3_FALLBACK_true @@ -40,32 +12,32 @@ SEXP vec_c(SEXP xs, return vec_c_opts(xs, ptype, name_spec, name_repair, &opts); } -SEXP vec_c_opts(SEXP xs, - SEXP ptype, - SEXP name_spec, - const struct name_repair_opts* name_repair, - const struct fallback_opts* fallback_opts) { +r_obj* vec_c_opts(r_obj* xs, + r_obj* ptype, + r_obj* name_spec, + const struct name_repair_opts* name_repair, + const struct fallback_opts* fallback_opts) { struct ptype_common_opts ptype_opts = { .fallback = *fallback_opts }; - SEXP orig_ptype = ptype; - ptype = PROTECT(vec_ptype_common_opts(xs, orig_ptype, &ptype_opts)); + r_obj* orig_ptype = ptype; + ptype = KEEP(vec_ptype_common_opts(xs, orig_ptype, &ptype_opts)); - if (ptype == R_NilValue) { - UNPROTECT(1); - return R_NilValue; + if (ptype == r_null) { + FREE(1); + return r_null; } if (needs_vec_c_fallback(ptype)) { - SEXP out = vec_c_fallback(ptype, xs, name_spec, name_repair); - UNPROTECT(1); + r_obj* out = vec_c_fallback(ptype, xs, name_spec, name_repair); + FREE(1); return out; } // FIXME: Needed for dplyr::summarise() which passes a non-fallback ptype if (needs_vec_c_homogeneous_fallback(xs, ptype)) { - SEXP out = vec_c_fallback_invoke(xs, name_spec); - UNPROTECT(1); + r_obj* out = vec_c_fallback_invoke(xs, name_spec); + FREE(1); return out; } @@ -81,75 +53,75 @@ SEXP vec_c_opts(SEXP xs, if ((is_data_frame(ptype) && fallback_opts->s3 == S3_FALLBACK_true) || vec_is_common_class_fallback(ptype)) { ptype_opts.fallback.s3 = S3_FALLBACK_false; - ptype = PROTECT(vec_ptype_common_opts(xs, orig_ptype, &ptype_opts)); + ptype = KEEP(vec_ptype_common_opts(xs, orig_ptype, &ptype_opts)); } else { - ptype = PROTECT(vec_ptype_common_opts(xs, ptype, &ptype_opts)); + ptype = KEEP(vec_ptype_common_opts(xs, ptype, &ptype_opts)); } // Find individual input sizes and total size of output - R_len_t n = Rf_length(xs); - R_len_t out_size = 0; + r_ssize n = r_length(xs); + r_ssize out_size = 0; // Caching the sizes causes an extra allocation but it improves performance - SEXP sizes = PROTECT(Rf_allocVector(INTSXP, n)); - int* p_sizes = INTEGER(sizes); + r_obj* sizes = KEEP(r_alloc_integer(n)); + int* p_sizes = r_int_begin(sizes); - for (R_len_t i = 0; i < n; ++i) { - SEXP x = VECTOR_ELT(xs, i); - R_len_t size = (x == R_NilValue) ? 0 : vec_size(x); + for (r_ssize i = 0; i < n; ++i) { + r_obj* x = r_list_get(xs, i); + r_ssize size = (x == r_null) ? 0 : vec_size(x); out_size += size; p_sizes[i] = size; } - SEXP out = vec_init(ptype, out_size); - PROTECT_INDEX out_pi; - PROTECT_WITH_INDEX(out, &out_pi); + r_obj* out = vec_init(ptype, out_size); + r_keep_loc out_pi; + KEEP_HERE(out, &out_pi); out = vec_proxy(out); - REPROTECT(out, out_pi); + KEEP_AT(out, out_pi); - SEXP loc = PROTECT(compact_seq(0, 0, true)); - int* p_loc = INTEGER(loc); + r_obj* loc = KEEP(compact_seq(0, 0, true)); + int* p_loc = r_int_begin(loc); - bool assign_names = !Rf_inherits(name_spec, "rlang_zap"); - SEXP xs_names = PROTECT(r_names(xs)); - bool xs_is_named = xs_names != R_NilValue && !is_data_frame(ptype); + bool assign_names = !r_inherits(name_spec, "rlang_zap"); + r_obj* xs_names = KEEP(r_names(xs)); + bool xs_is_named = xs_names != r_null && !is_data_frame(ptype); - SEXP out_names = R_NilValue; - PROTECT_INDEX out_names_pi; - PROTECT_WITH_INDEX(R_NilValue, &out_names_pi); + r_obj* out_names = r_null; + r_keep_loc out_names_pi; + KEEP_HERE(r_null, &out_names_pi); // Compact sequences use 0-based counters - R_len_t counter = 0; + r_ssize counter = 0; const struct vec_assign_opts c_assign_opts = { .assign_names = assign_names, .ignore_outer_names = true }; - for (R_len_t i = 0; i < n; ++i) { - SEXP x = VECTOR_ELT(xs, i); - R_len_t size = p_sizes[i]; + for (r_ssize i = 0; i < n; ++i) { + r_obj* x = r_list_get(xs, i); + r_ssize size = p_sizes[i]; init_compact_seq(p_loc, counter, size, true); if (assign_names) { - SEXP outer = xs_is_named ? STRING_ELT(xs_names, i) : R_NilValue; - SEXP inner = PROTECT(vec_names(x)); - SEXP x_nms = PROTECT(apply_name_spec(name_spec, outer, inner, size)); + r_obj* outer = xs_is_named ? r_chr_get(xs_names, i) : r_null; + r_obj* inner = KEEP(vec_names(x)); + r_obj* x_nms = KEEP(apply_name_spec(name_spec, outer, inner, size)); - if (x_nms != R_NilValue) { - R_LAZY_ALLOC(out_names, out_names_pi, STRSXP, out_size); + if (x_nms != r_null) { + R_LAZY_ALLOC(out_names, out_names_pi, R_TYPE_character, out_size); // If there is no name to assign, skip the assignment since // `out_names` already contains empty strings if (x_nms != chrs_empty) { out_names = chr_assign(out_names, loc, x_nms, VCTRS_OWNED_true); - REPROTECT(out_names, out_names_pi); + KEEP_AT(out_names, out_names_pi); } } - UNPROTECT(2); + FREE(2); } if (!size) { @@ -161,76 +133,88 @@ SEXP vec_c_opts(SEXP xs, .to = ptype, .fallback = *fallback_opts }; - x = PROTECT(vec_cast_opts(&opts)); + x = KEEP(vec_cast_opts(&opts)); // Total ownership of `out` because it was freshly created with `vec_init()` out = vec_proxy_assign_opts(out, loc, x, VCTRS_OWNED_true, &c_assign_opts); - REPROTECT(out, out_pi); + KEEP_AT(out, out_pi); counter += size; - UNPROTECT(1); + FREE(1); } - out = PROTECT(vec_restore(out, ptype, R_NilValue, VCTRS_OWNED_true)); + out = KEEP(vec_restore(out, ptype, r_null, VCTRS_OWNED_true)); - if (out_names != R_NilValue) { - out_names = PROTECT(vec_as_names(out_names, name_repair)); + if (out_names != r_null) { + out_names = KEEP(vec_as_names(out_names, name_repair)); out = vec_set_names(out, out_names); - UNPROTECT(1); + FREE(1); } else if (!assign_names) { // FIXME: `vec_ptype2()` doesn't consistently zaps names, so `out` // might have been initialised with names. This branch can be // removed once #1020 is resolved. - out = vec_set_names(out, R_NilValue); + out = vec_set_names(out, r_null); } - UNPROTECT(8); + FREE(8); + return out; +} + +r_obj* ffi_vec_c(r_obj* call, r_obj* op, r_obj* args, r_obj* env) { + args = r_node_cdr(args); + + r_obj* xs = KEEP(rlang_env_dots_list(env)); + r_obj* ptype = KEEP(r_eval(r_node_car(args), env)); args = r_node_cdr(args); + r_obj* name_spec = KEEP(r_eval(r_node_car(args), env)); args = r_node_cdr(args); + r_obj* name_repair = KEEP(r_eval(r_node_car(args), env)); + + struct name_repair_opts name_repair_opts = + new_name_repair_opts(name_repair, + vec_args.empty, + false, + r_lazy_null); + KEEP(name_repair_opts.shelter); + + r_obj* out = vec_c(xs, ptype, name_spec, &name_repair_opts); + + FREE(5); return out; } -static inline bool vec_implements_base_c(SEXP x); -// [[ include("c.h") ]] -bool needs_vec_c_fallback(SEXP ptype) { +bool needs_vec_c_fallback(r_obj* ptype) { if (!vec_is_common_class_fallback(ptype)) { return false; } // Suboptimal: Prevent infinite recursion through `vctrs_vctr` method - SEXP class = PROTECT(Rf_getAttrib(ptype, syms_fallback_class)); + r_obj* class = r_attrib_get(ptype, syms_fallback_class); class = r_chr_get(class, r_length(class) - 1); - if (class == strings_vctrs_vctr) { - UNPROTECT(1); - return false; - } - - UNPROTECT(1); - return true; + return class != strings_vctrs_vctr; } -// [[ include("c.h") ]] -bool needs_vec_c_homogeneous_fallback(SEXP xs, SEXP ptype) { - if (!Rf_length(xs)) { +bool needs_vec_c_homogeneous_fallback(r_obj* xs, r_obj* ptype) { + if (!r_length(xs)) { return false; } - SEXP x = list_first_non_null(xs, NULL); + r_obj* x = list_first_non_null(xs, NULL); if (!vec_is_vector(x)) { return false; } // Never fall back for `vctrs_vctr` classes to avoid infinite // recursion through `c.vctrs_vctr()` - if (Rf_inherits(x, "vctrs_vctr")) { + if (r_inherits(x, "vctrs_vctr")) { return false; } - if (ptype != R_NilValue) { - SEXP x_class = PROTECT(r_class(x)); - SEXP ptype_class = PROTECT(r_class(ptype)); + if (ptype != r_null) { + r_obj* x_class = KEEP(r_class(x)); + r_obj* ptype_class = KEEP(r_class(ptype)); bool equal = equal_object(x_class, ptype_class); - UNPROTECT(2); + FREE(2); if (!equal) { return false; @@ -244,39 +228,37 @@ bool needs_vec_c_homogeneous_fallback(SEXP xs, SEXP ptype) { } static inline -bool vec_implements_base_c(SEXP x) { - if (!OBJECT(x)) { +bool vec_implements_base_c(r_obj* x) { + if (!r_is_object(x)) { return false; } if (IS_S4_OBJECT(x)) { - return s4_find_method(x, s4_c_method_table) != R_NilValue; + return s4_find_method(x, s4_c_method_table) != r_null; } else { - return s3_find_method("c", x, base_method_table) != R_NilValue; + return s3_find_method("c", x, base_method_table) != r_null; } } + static inline -bool class_implements_base_c(SEXP cls) { - if (s3_class_find_method("c", cls, base_method_table) != R_NilValue) { +bool class_implements_base_c(r_obj* cls) { + if (s3_class_find_method("c", cls, base_method_table) != r_null) { return true; } - if (s4_class_find_method(cls, s4_c_method_table) != R_NilValue) { + if (s4_class_find_method(cls, s4_c_method_table) != r_null) { return true; } return false; } -static inline int vec_c_fallback_validate_args(SEXP x, SEXP name_spec); -static inline void stop_vec_c_fallback(SEXP xs, int err_type); -// [[ include("c.h") ]] -SEXP vec_c_fallback(SEXP ptype, - SEXP xs, - SEXP name_spec, - const struct name_repair_opts* name_repair) { - SEXP class = PROTECT(Rf_getAttrib(ptype, syms_fallback_class)); +r_obj* vec_c_fallback(r_obj* ptype, + r_obj* xs, + r_obj* name_spec, + const struct name_repair_opts* name_repair) { + r_obj* class = KEEP(r_attrib_get(ptype, syms_fallback_class)); bool implements_c = class_implements_base_c(class); - UNPROTECT(1); + FREE(1); if (implements_c) { return vec_c_fallback_invoke(xs, name_spec); @@ -291,21 +273,20 @@ SEXP vec_c_fallback(SEXP ptype, // Should cause a common type error, unless another fallback // kicks in (for instance, homogeneous class with homogeneous // attributes) - vec_ptype_common_opts(xs, R_NilValue, &ptype_opts); + vec_ptype_common_opts(xs, r_null, &ptype_opts); // Suboptimal: Call `vec_c()` again to combine vector with // homogeneous class fallback - return vec_c_opts(xs, R_NilValue, name_spec, name_repair, &ptype_opts.fallback); + return vec_c_opts(xs, r_null, name_spec, name_repair, &ptype_opts.fallback); } } -// [[ include("c.h") ]] -SEXP vec_c_fallback_invoke(SEXP xs, SEXP name_spec) { - SEXP x = list_first_non_null(xs, NULL); +r_obj* vec_c_fallback_invoke(r_obj* xs, r_obj* name_spec) { + r_obj* x = list_first_non_null(xs, NULL); if (vctrs_debug_verbose) { - Rprintf("Falling back to `base::c()` for class `%s`.\n", - r_chr_get_c_string(r_class(x), 0)); + r_printf("Falling back to `base::c()` for class `%s`.\n", + r_chr_get_c_string(r_class(x), 0)); } int err_type = vec_c_fallback_validate_args(x, name_spec); @@ -313,23 +294,24 @@ SEXP vec_c_fallback_invoke(SEXP xs, SEXP name_spec) { stop_vec_c_fallback(xs, err_type); } - SEXP call = PROTECT(Rf_lang2(Rf_install("base_c_invoke"), xs)); - SEXP out = Rf_eval(call, vctrs_ns_env); + r_obj* call = KEEP(r_call2(r_sym("base_c_invoke"), xs)); + r_obj* out = r_eval(call, vctrs_ns_env); - UNPROTECT(1); + FREE(1); return out; } static inline -int vec_c_fallback_validate_args(SEXP x, SEXP name_spec) { - if (name_spec != R_NilValue) { +int vec_c_fallback_validate_args(r_obj* x, r_obj* name_spec) { + if (name_spec != r_null) { return 2; } return 0; } -static void stop_vec_c_fallback(SEXP xs, int err_type) { - SEXP common_class = PROTECT(r_class(list_first_non_null(xs, NULL))); +static +void stop_vec_c_fallback(r_obj* xs, int err_type) { + r_obj* common_class = KEEP(r_class(list_first_non_null(xs, NULL))); const char* class_str = r_chr_get_c_string(common_class, 0); const char* msg = NULL; @@ -339,10 +321,9 @@ static void stop_vec_c_fallback(SEXP xs, int err_type) { default: msg = "Internal error: Unexpected error type."; break; } - Rf_errorcall(R_NilValue, - "%s\n" - "vctrs methods must be implemented for class `%s`.\n" - "See .", - msg, - class_str); + r_abort("%s\n" + "vctrs methods must be implemented for class `%s`.\n" + "See .", + msg, + class_str); } diff --git a/src/c.h b/src/c.h index 38463e9f1..dda87f710 100644 --- a/src/c.h +++ b/src/c.h @@ -6,20 +6,25 @@ #include "ptype2.h" -SEXP vec_c_opts(SEXP xs, - SEXP ptype, - SEXP name_spec, - const struct name_repair_opts* name_repair, - const struct fallback_opts* fallback_opts); - -SEXP vec_c_fallback_invoke(SEXP xs, SEXP name_spec); -SEXP vec_c_fallback(SEXP ptype, - SEXP xs, - SEXP name_spec, - const struct name_repair_opts* name_repair); - -bool needs_vec_c_fallback(SEXP ptype); -bool needs_vec_c_homogeneous_fallback(SEXP xs, SEXP ptype); +r_obj* vec_c(r_obj* xs, + r_obj* ptype, + r_obj* name_spec, + const struct name_repair_opts* name_repair); + +r_obj* vec_c_opts(r_obj* xs, + r_obj* ptype, + r_obj* name_spec, + const struct name_repair_opts* name_repair, + const struct fallback_opts* fallback_opts); + +r_obj* vec_c_fallback_invoke(r_obj* xs, r_obj* name_spec); +r_obj* vec_c_fallback(r_obj* ptype, + r_obj* xs, + r_obj* name_spec, + const struct name_repair_opts* name_repair); + +bool needs_vec_c_fallback(r_obj* ptype); +bool needs_vec_c_homogeneous_fallback(r_obj* xs, r_obj* ptype); #endif diff --git a/src/decl/c-decl.h b/src/decl/c-decl.h new file mode 100644 index 000000000..51e9bba42 --- /dev/null +++ b/src/decl/c-decl.h @@ -0,0 +1,8 @@ +static inline +bool vec_implements_base_c(r_obj* x); + +static inline +int vec_c_fallback_validate_args(r_obj* x, r_obj* name_spec); + +static +void stop_vec_c_fallback(r_obj* xs, int err_type); diff --git a/src/init.c b/src/init.c index df1faff20..dba022d15 100644 --- a/src/init.c +++ b/src/init.c @@ -332,7 +332,7 @@ extern r_obj* ffi_cast_common(r_obj*, r_obj*, r_obj*, r_obj*); extern r_obj* ffi_cast_common_opts(r_obj*, r_obj*, r_obj*, r_obj*); extern r_obj* ffi_rbind(r_obj*, r_obj*, r_obj*, r_obj*); extern r_obj* ffi_cbind(r_obj*, r_obj*, r_obj*, r_obj*); -extern SEXP vctrs_c(SEXP, SEXP, SEXP, SEXP); +extern r_obj* ffi_vec_c(r_obj*, r_obj*, r_obj*, r_obj*); extern r_obj* ffi_new_data_frame(r_obj*); static @@ -345,7 +345,7 @@ const R_ExternalMethodDef ExtEntries[] = { {"ffi_cast_common_opts", (DL_FUNC) &ffi_cast_common_opts, 2}, {"ffi_rbind", (DL_FUNC) &ffi_rbind, 4}, {"ffi_cbind", (DL_FUNC) &ffi_cbind, 3}, - {"vctrs_c", (DL_FUNC) &vctrs_c, 3}, + {"ffi_vec_c", (DL_FUNC) &ffi_vec_c, 3}, {"ffi_new_data_frame", (DL_FUNC) &ffi_new_data_frame, -1}, {NULL, NULL, 0} }; diff --git a/src/vctrs.h b/src/vctrs.h index 33a2d641e..aaecfa9d5 100644 --- a/src/vctrs.h +++ b/src/vctrs.h @@ -97,11 +97,6 @@ SEXP vec_match(SEXP needles, SEXP haystack) { } -SEXP vec_c(SEXP xs, - SEXP ptype, - SEXP name_spec, - const struct name_repair_opts* name_repair); - bool is_data_frame(SEXP x); uint32_t hash_object(SEXP x); diff --git a/tests/testthat/_snaps/c.md b/tests/testthat/_snaps/c.md index f3530c76d..d0aef9005 100644 --- a/tests/testthat/_snaps/c.md +++ b/tests/testthat/_snaps/c.md @@ -56,9 +56,11 @@ (expect_error(with_c_foobar(vec_c(foobar(1), foobar(2), .name_spec = "{outer}_{inner}")), "name specification")) Output - + Error in `vec_c()`: + ! Can't use a name specification with non-vctrs types. vctrs methods must be implemented for class `vctrs_foobar`. - See .> + See . Code (expect_error(with_c_foobar(vec_c(foobar(1), foobar(2), .ptype = "")), class = "vctrs_error_incompatible_type") ) diff --git a/tests/testthat/_snaps/slice-chop.md b/tests/testthat/_snaps/slice-chop.md index bce63cda1..e65daf469 100644 --- a/tests/testthat/_snaps/slice-chop.md +++ b/tests/testthat/_snaps/slice-chop.md @@ -65,9 +65,11 @@ (expect_error(with_c_foobar(vec_unchop(list(foo, bar), name_spec = "{outer}_{inner}")), "name specification")) Output - + Error in `vec_unchop()`: + ! Can't use a name specification with non-vctrs types. vctrs methods must be implemented for class `vctrs_foobar`. - See .> + See . Code (expect_error(with_c_foobar(vec_unchop(list(foobar(1)), ptype = "")), class = "vctrs_error_incompatible_type") ) From aea8877f6a2d3a814a34b95fa7545397c72b4ebd Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Mon, 12 Sep 2022 13:24:02 +0200 Subject: [PATCH 032/312] Update snapshots to latest cli --- DESCRIPTION | 2 +- tests/testthat/_snaps/slice.md | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/DESCRIPTION b/DESCRIPTION index 6c99a7f15..895bb8643 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -29,7 +29,7 @@ BugReports: https://github.com/r-lib/vctrs/issues Depends: R (>= 3.3) Imports: - cli (>= 3.2.0), + cli (>= 3.4.0), glue, rlang (>= 1.0.5) Suggests: diff --git a/tests/testthat/_snaps/slice.md b/tests/testthat/_snaps/slice.md index c6311c9db..e57ea165d 100644 --- a/tests/testthat/_snaps/slice.md +++ b/tests/testthat/_snaps/slice.md @@ -100,7 +100,7 @@ Condition Error in `vec_slice()`: ! Can't subset elements past the end. - i Locations 100, 101, 102, 103, 104, ... don't exist. + i Locations 100, 101, 102, ..., 109, and 110 don't exist. i There are only 26 elements. --- From b33f4cb6f00eaf77f6730484f0a74cd26de9b4bd Mon Sep 17 00:00:00 2001 From: Davis Vaughan Date: Mon, 12 Sep 2022 09:43:57 -0400 Subject: [PATCH 033/312] Rename `vec_unchop()` to `list_unchop()` (#1637) * Rename `vec_unchop()` to `list_unchop()`. Soft-deprecate `vec_unchop()`. * Test that `vec_unchop()` still works and is deprecated * NEWS bullet * Use lifecycle tooling in `vec_unchop()` --- DESCRIPTION | 1 + NAMESPACE | 1 + NEWS.md | 4 + R/slice-chop.R | 39 ++-- R/slice-interleave.R | 4 +- R/vctrs-deprecated.R | 29 +++ man/vec_chop.Rd | 31 +-- man/vec_interleave.Rd | 2 +- man/vec_unchop.Rd | 68 ++++++ src/c-unchop.c | 38 +-- src/decl/c-unchop-decl.h | 22 +- src/init.c | 4 +- tests/testthat/_snaps/c.md | 24 +- tests/testthat/_snaps/lifecycle-deprecated.md | 11 + tests/testthat/_snaps/slice-chop.md | 38 +-- tests/testthat/test-c.R | 38 +-- tests/testthat/test-lifecycle-deprecated.R | 13 ++ tests/testthat/test-slice-chop.R | 220 +++++++++--------- tests/testthat/test-type-table.R | 6 +- 19 files changed, 361 insertions(+), 232 deletions(-) create mode 100644 man/vec_unchop.Rd create mode 100644 tests/testthat/_snaps/lifecycle-deprecated.md diff --git a/DESCRIPTION b/DESCRIPTION index 895bb8643..62047f927 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -31,6 +31,7 @@ Depends: Imports: cli (>= 3.4.0), glue, + lifecycle (>= 1.0.2), rlang (>= 1.0.5) Suggests: bit64, diff --git a/NAMESPACE b/NAMESPACE index 26a82a31d..189ec626d 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -467,6 +467,7 @@ export(list_check_all_vectors) export(list_drop_empty) export(list_of) export(list_sizes) +export(list_unchop) export(maybe_lossy_cast) export(n_fields) export(new_data_frame) diff --git a/NEWS.md b/NEWS.md index d9dcc7b0c..4920c81d5 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,5 +1,9 @@ # vctrs (development version) +* `vec_unchop()` has been renamed to `list_unchop()` to better indicate that it + requires list input. `vec_unchop()` will stick around for a few minor + versions, but has been formally soft-deprecated (#1209). + * Lossy cast errors during scalar subscript validation now have the correct message (#1606). diff --git a/R/slice-chop.R b/R/slice-chop.R index 4cdbcfdd7..f47b2fc49 100644 --- a/R/slice-chop.R +++ b/R/slice-chop.R @@ -5,17 +5,18 @@ #' captures the pattern of `map(indices, vec_slice, x = x)`. When no indices #' are supplied, it is generally equivalent to [as.list()]. #' -#' - `vec_unchop()` combines a list of vectors into a single vector, placing +#' - `list_unchop()` combines a list of vectors into a single vector, placing #' elements in the output according to the locations specified by `indices`. #' It is similar to [vec_c()], but gives greater control over how the elements -#' are combined. When no indices are supplied, it is identical to `vec_c()`. +#' are combined. When no indices are supplied, it is identical to `vec_c()`, +#' but typically a little faster. #' #' If `indices` selects every value in `x` exactly once, in any order, then -#' `vec_unchop()` is the inverse of `vec_chop()` and the following invariant +#' `list_unchop()` is the inverse of `vec_chop()` and the following invariant #' holds: #' #' ``` -#' vec_unchop(vec_chop(x, indices), indices) == x +#' list_unchop(vec_chop(x, indices), indices) == x #' ``` #' #' @inheritParams vec_c @@ -24,7 +25,7 @@ #' slice `x` with, or `NULL`. If `NULL`, `x` is split into its individual #' elements, equivalent to using an `indices` of `as.list(vec_seq_along(x))`. #' -#' For `vec_unchop()`, a list of positive integer vectors specifying the +#' For `list_unchop()`, a list of positive integer vectors specifying the #' locations to place elements of `x` in. Each element of `x` is recycled to #' the size of the corresponding index vector. The size of `indices` must #' match the size of `x`. If `NULL`, `x` is combined in the order it is @@ -36,14 +37,14 @@ #' - `vec_chop()`: A list of size `vec_size(indices)` or, if `indices == NULL`, #' `vec_size(x)`. #' -#' - `vec_unchop()`: A vector of type `vec_ptype_common(!!!x)`, or `ptype`, if +#' - `list_unchop()`: A vector of type `vec_ptype_common(!!!x)`, or `ptype`, if #' specified. The size is computed as `vec_size_common(!!!indices)` unless #' the indices are `NULL`, in which case the size is `vec_size_common(!!!x)`. #' #' @section Dependencies of `vec_chop()`: #' - [vec_slice()] #' -#' @section Dependencies of `vec_unchop()`: +#' @section Dependencies of `list_unchop()`: #' - [vec_c()] #' #' @export @@ -53,28 +54,28 @@ #' vec_chop(mtcars, list(1:3, 4:6)) #' #' # If `indices` selects every value in `x` exactly once, -#' # in any order, then `vec_unchop()` inverts `vec_chop()` +#' # in any order, then `list_unchop()` inverts `vec_chop()` #' x <- c("a", "b", "c", "d") #' indices <- list(2, c(3, 1), 4) #' vec_chop(x, indices) -#' vec_unchop(vec_chop(x, indices), indices) +#' list_unchop(vec_chop(x, indices), indices) #' #' # When unchopping, size 1 elements of `x` are recycled #' # to the size of the corresponding index -#' vec_unchop(list(1, 2:3), list(c(1, 3, 5), c(2, 4))) +#' list_unchop(list(1, 2:3), list(c(1, 3, 5), c(2, 4))) #' #' # Names are retained, and outer names can be combined with inner #' # names through the use of a `name_spec` #' lst <- list(x = c(a = 1, b = 2), y = 1) -#' vec_unchop(lst, list(c(3, 2), c(1, 4)), name_spec = "{outer}_{inner}") +#' list_unchop(lst, list(c(3, 2), c(1, 4)), name_spec = "{outer}_{inner}") #' #' # An alternative implementation of `ave()` can be constructed using -#' # `vec_chop()` and `vec_unchop()` in combination with `vec_group_loc()` +#' # `vec_chop()` and `list_unchop()` in combination with `vec_group_loc()` #' ave2 <- function(.x, .by, .f, ...) { #' indices <- vec_group_loc(.by)$loc #' chopped <- vec_chop(.x, indices) #' out <- lapply(chopped, .f, ...) -#' vec_unchop(out, indices) +#' list_unchop(out, indices) #' } #' #' breaks <- warpbreaks$breaks @@ -92,12 +93,12 @@ vec_chop <- function(x, indices = NULL) { #' @rdname vec_chop #' @export -vec_unchop <- function(x, - indices = NULL, - ptype = NULL, - name_spec = NULL, - name_repair = c("minimal", "unique", "check_unique", "universal")) { - .Call(ffi_vec_unchop, x, indices, ptype, name_spec, name_repair) +list_unchop <- function(x, + indices = NULL, + ptype = NULL, + name_spec = NULL, + name_repair = c("minimal", "unique", "check_unique", "universal")) { + .Call(ffi_list_unchop, x, indices, ptype, name_spec, name_repair) } # Exposed for testing (`starts` is 0-based) diff --git a/R/slice-interleave.R b/R/slice-interleave.R index 4c9c2f456..5224b1e6c 100644 --- a/R/slice-interleave.R +++ b/R/slice-interleave.R @@ -15,7 +15,7 @@ #' #' ## vctrs dependencies #' -#' - [vec_unchop()] +#' - [list_unchop()] #' #' @inheritParams vec_c #' @@ -53,7 +53,7 @@ vec_interleave <- function(..., indices <- vec_interleave_indices(n, size) - vec_unchop( + list_unchop( x = args, indices = indices, ptype = .ptype, diff --git a/R/vctrs-deprecated.R b/R/vctrs-deprecated.R index 7287fe18c..20575d4e0 100644 --- a/R/vctrs-deprecated.R +++ b/R/vctrs-deprecated.R @@ -114,3 +114,32 @@ vec_repeat <- function(x, each = 1L, times = 1L) { idx <- rep(vec_seq_along(x), times = times, each = each) vec_slice(x, idx) } + +#' Chopping +#' +#' @description +#' `r lifecycle::badge("deprecated")` +#' +#' `vec_unchop()` has been renamed to [list_unchop()] and is deprecated as of +#' vctrs 0.5.0. +#' +#' @inheritParams list_unchop +#' @inherit list_unchop return +#' +#' @keywords internal +#' @export +vec_unchop <- function(x, + indices = NULL, + ptype = NULL, + name_spec = NULL, + name_repair = c("minimal", "unique", "check_unique", "universal")) { + lifecycle::deprecate_soft("0.5.0", "vec_unchop()", "list_unchop()") + + list_unchop( + x = x, + indices = indices, + ptype = ptype, + name_spec = name_spec, + name_repair = name_repair + ) +} diff --git a/man/vec_chop.Rd b/man/vec_chop.Rd index 18e54ffa4..95e53357d 100644 --- a/man/vec_chop.Rd +++ b/man/vec_chop.Rd @@ -2,12 +2,12 @@ % Please edit documentation in R/slice-chop.R \name{vec_chop} \alias{vec_chop} -\alias{vec_unchop} +\alias{list_unchop} \title{Chopping} \usage{ vec_chop(x, indices = NULL) -vec_unchop( +list_unchop( x, indices = NULL, ptype = NULL, @@ -22,7 +22,7 @@ vec_unchop( slice \code{x} with, or \code{NULL}. If \code{NULL}, \code{x} is split into its individual elements, equivalent to using an \code{indices} of \code{as.list(vec_seq_along(x))}. -For \code{vec_unchop()}, a list of positive integer vectors specifying the +For \code{list_unchop()}, a list of positive integer vectors specifying the locations to place elements of \code{x} in. Each element of \code{x} is recycled to the size of the corresponding index vector. The size of \code{indices} must match the size of \code{x}. If \code{NULL}, \code{x} is combined in the order it is @@ -57,7 +57,7 @@ See the \link[=name_spec]{name specification topic}.} \itemize{ \item \code{vec_chop()}: A list of size \code{vec_size(indices)} or, if \code{indices == NULL}, \code{vec_size(x)}. -\item \code{vec_unchop()}: A vector of type \code{vec_ptype_common(!!!x)}, or \code{ptype}, if +\item \code{list_unchop()}: A vector of type \code{vec_ptype_common(!!!x)}, or \code{ptype}, if specified. The size is computed as \code{vec_size_common(!!!indices)} unless the indices are \code{NULL}, in which case the size is \code{vec_size_common(!!!x)}. } @@ -67,17 +67,18 @@ the indices are \code{NULL}, in which case the size is \code{vec_size_common(!!! \item \code{vec_chop()} provides an efficient method to repeatedly slice a vector. It captures the pattern of \code{map(indices, vec_slice, x = x)}. When no indices are supplied, it is generally equivalent to \code{\link[=as.list]{as.list()}}. -\item \code{vec_unchop()} combines a list of vectors into a single vector, placing +\item \code{list_unchop()} combines a list of vectors into a single vector, placing elements in the output according to the locations specified by \code{indices}. It is similar to \code{\link[=vec_c]{vec_c()}}, but gives greater control over how the elements -are combined. When no indices are supplied, it is identical to \code{vec_c()}. +are combined. When no indices are supplied, it is identical to \code{vec_c()}, +but typically a little faster. } If \code{indices} selects every value in \code{x} exactly once, in any order, then -\code{vec_unchop()} is the inverse of \code{vec_chop()} and the following invariant +\code{list_unchop()} is the inverse of \code{vec_chop()} and the following invariant holds: -\if{html}{\out{
}}\preformatted{vec_unchop(vec_chop(x, indices), indices) == x +\if{html}{\out{
}}\preformatted{list_unchop(vec_chop(x, indices), indices) == x }\if{html}{\out{
}} } \section{Dependencies of \code{vec_chop()}}{ @@ -87,7 +88,7 @@ holds: } } -\section{Dependencies of \code{vec_unchop()}}{ +\section{Dependencies of \code{list_unchop()}}{ \itemize{ \item \code{\link[=vec_c]{vec_c()}} @@ -100,28 +101,28 @@ vec_chop(1:5, list(1, 1:2)) vec_chop(mtcars, list(1:3, 4:6)) # If `indices` selects every value in `x` exactly once, -# in any order, then `vec_unchop()` inverts `vec_chop()` +# in any order, then `list_unchop()` inverts `vec_chop()` x <- c("a", "b", "c", "d") indices <- list(2, c(3, 1), 4) vec_chop(x, indices) -vec_unchop(vec_chop(x, indices), indices) +list_unchop(vec_chop(x, indices), indices) # When unchopping, size 1 elements of `x` are recycled # to the size of the corresponding index -vec_unchop(list(1, 2:3), list(c(1, 3, 5), c(2, 4))) +list_unchop(list(1, 2:3), list(c(1, 3, 5), c(2, 4))) # Names are retained, and outer names can be combined with inner # names through the use of a `name_spec` lst <- list(x = c(a = 1, b = 2), y = 1) -vec_unchop(lst, list(c(3, 2), c(1, 4)), name_spec = "{outer}_{inner}") +list_unchop(lst, list(c(3, 2), c(1, 4)), name_spec = "{outer}_{inner}") # An alternative implementation of `ave()` can be constructed using -# `vec_chop()` and `vec_unchop()` in combination with `vec_group_loc()` +# `vec_chop()` and `list_unchop()` in combination with `vec_group_loc()` ave2 <- function(.x, .by, .f, ...) { indices <- vec_group_loc(.by)$loc chopped <- vec_chop(.x, indices) out <- lapply(chopped, .f, ...) - vec_unchop(out, indices) + list_unchop(out, indices) } breaks <- warpbreaks$breaks diff --git a/man/vec_interleave.Rd b/man/vec_interleave.Rd index 69e017239..1b352c63a 100644 --- a/man/vec_interleave.Rd +++ b/man/vec_interleave.Rd @@ -57,7 +57,7 @@ It is a more efficient equivalent to the following usage of \code{vec_c()}: \subsection{vctrs dependencies}{ \itemize{ -\item \code{\link[=vec_unchop]{vec_unchop()}} +\item \code{\link[=list_unchop]{list_unchop()}} } } } diff --git a/man/vec_unchop.Rd b/man/vec_unchop.Rd new file mode 100644 index 000000000..f132cef83 --- /dev/null +++ b/man/vec_unchop.Rd @@ -0,0 +1,68 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/vctrs-deprecated.R +\name{vec_unchop} +\alias{vec_unchop} +\title{Chopping} +\usage{ +vec_unchop( + x, + indices = NULL, + ptype = NULL, + name_spec = NULL, + name_repair = c("minimal", "unique", "check_unique", "universal") +) +} +\arguments{ +\item{x}{A vector} + +\item{indices}{For \code{vec_chop()}, a list of positive integer vectors to +slice \code{x} with, or \code{NULL}. If \code{NULL}, \code{x} is split into its individual +elements, equivalent to using an \code{indices} of \code{as.list(vec_seq_along(x))}. + +For \code{list_unchop()}, a list of positive integer vectors specifying the +locations to place elements of \code{x} in. Each element of \code{x} is recycled to +the size of the corresponding index vector. The size of \code{indices} must +match the size of \code{x}. If \code{NULL}, \code{x} is combined in the order it is +provided in, which is equivalent to using \code{\link[=vec_c]{vec_c()}}.} + +\item{ptype}{If \code{NULL}, the default, the output type is determined by +computing the common type across all elements of \code{x}. Alternatively, you +can supply \code{ptype} to give the output a known type.} + +\item{name_spec}{A name specification for combining +inner and outer names. This is relevant for inputs passed with a +name, when these inputs are themselves named, like \code{outer = c(inner = 1)}, or when they have length greater than 1: \code{outer = 1:2}. By default, these cases trigger an error. You can resolve +the error by providing a specification that describes how to +combine the names or the indices of the inner vector with the +name of the input. This specification can be: +\itemize{ +\item A function of two arguments. The outer name is passed as a +string to the first argument, and the inner names or positions +are passed as second argument. +\item An anonymous function as a purrr-style formula. +\item A glue specification of the form \code{"{outer}_{inner}"}. +\item An \code{\link[rlang:zap]{rlang::zap()}} object, in which case both outer and inner +names are ignored and the result is unnamed. +} + +See the \link[=name_spec]{name specification topic}.} + +\item{name_repair}{How to repair names, see \code{repair} options in +\code{\link[=vec_as_names]{vec_as_names()}}.} +} +\value{ +\itemize{ +\item \code{vec_chop()}: A list of size \code{vec_size(indices)} or, if \code{indices == NULL}, +\code{vec_size(x)}. +\item \code{list_unchop()}: A vector of type \code{vec_ptype_common(!!!x)}, or \code{ptype}, if +specified. The size is computed as \code{vec_size_common(!!!indices)} unless +the indices are \code{NULL}, in which case the size is \code{vec_size_common(!!!x)}. +} +} +\description{ +\ifelse{html}{\href{https://lifecycle.r-lib.org/articles/stages.html#deprecated}{\figure{lifecycle-deprecated.svg}{options: alt='[Deprecated]'}}}{\strong{[Deprecated]}} + +\code{vec_unchop()} has been renamed to \code{\link[=list_unchop]{list_unchop()}} and is deprecated as of +vctrs 0.5.0. +} +\keyword{internal} diff --git a/src/c-unchop.c b/src/c-unchop.c index 5f3206d13..49a8de381 100644 --- a/src/c-unchop.c +++ b/src/c-unchop.c @@ -10,11 +10,11 @@ enum fallback_homogeneous { static -r_obj* vec_unchop(r_obj* xs, - r_obj* indices, - r_obj* ptype, - r_obj* name_spec, - const struct name_repair_opts* name_repair) { +r_obj* list_unchop(r_obj* xs, + r_obj* indices, + r_obj* ptype, + r_obj* name_spec, + const struct name_repair_opts* name_repair) { if (!vec_is_list(xs)) { r_abort("`x` must be a list."); } @@ -43,14 +43,14 @@ r_obj* vec_unchop(r_obj* xs, r_lazy_null)); if (needs_vec_c_fallback(ptype)) { - r_obj* out = vec_unchop_fallback(ptype, xs, indices, name_spec, name_repair, FALLBACK_HOMOGENEOUS_false); + r_obj* out = list_unchop_fallback(ptype, xs, indices, name_spec, name_repair, FALLBACK_HOMOGENEOUS_false); FREE(1); return out; } // FIXME: Needed for dplyr::summarise() which passes a non-fallback ptype if (needs_vec_c_homogeneous_fallback(xs, ptype)) { - r_obj* out = vec_unchop_fallback(ptype, xs, indices, name_spec, name_repair, FALLBACK_HOMOGENEOUS_true); + r_obj* out = list_unchop_fallback(ptype, xs, indices, name_spec, name_repair, FALLBACK_HOMOGENEOUS_true); FREE(1); return out; } @@ -155,11 +155,11 @@ r_obj* vec_unchop(r_obj* xs, return out; } -r_obj* ffi_vec_unchop(r_obj* x, - r_obj* indices, - r_obj* ptype, - r_obj* name_spec, - r_obj* name_repair) { +r_obj* ffi_list_unchop(r_obj* x, + r_obj* indices, + r_obj* ptype, + r_obj* name_spec, + r_obj* name_repair) { struct name_repair_opts name_repair_opts = new_name_repair_opts(name_repair, vec_args.empty, @@ -167,7 +167,7 @@ r_obj* ffi_vec_unchop(r_obj* x, r_lazy_null); KEEP(name_repair_opts.shelter); - r_obj* out = vec_unchop(x, indices, ptype, name_spec, &name_repair_opts); + r_obj* out = list_unchop(x, indices, ptype, name_spec, &name_repair_opts); FREE(1); return out; @@ -178,12 +178,12 @@ r_obj* ffi_vec_unchop(r_obj* x, // vec_slice_fallback(vec_c_fallback_invoke(!!!x), order(vec_c(!!!indices))) // with recycling of each element of `x` to the corresponding index size static -r_obj* vec_unchop_fallback(r_obj* ptype, - r_obj* x, - r_obj* indices, - r_obj* name_spec, - const struct name_repair_opts* name_repair, - enum fallback_homogeneous homogeneous) { +r_obj* list_unchop_fallback(r_obj* ptype, + r_obj* x, + r_obj* indices, + r_obj* name_spec, + const struct name_repair_opts* name_repair, + enum fallback_homogeneous homogeneous) { r_ssize x_size = vec_size(x); x = KEEP(r_clone_referenced(x)); diff --git a/src/decl/c-unchop-decl.h b/src/decl/c-unchop-decl.h index 6f2ca4bdd..6c9419ff8 100644 --- a/src/decl/c-unchop-decl.h +++ b/src/decl/c-unchop-decl.h @@ -1,14 +1,14 @@ static -r_obj* vec_unchop(r_obj* x, - r_obj* indices, - r_obj* ptype, - r_obj* name_spec, - const struct name_repair_opts* name_repair); +r_obj* list_unchop(r_obj* x, + r_obj* indices, + r_obj* ptype, + r_obj* name_spec, + const struct name_repair_opts* name_repair); static -r_obj* vec_unchop_fallback(r_obj* ptype, - r_obj* x, - r_obj* indices, - r_obj* name_spec, - const struct name_repair_opts* name_repair, - enum fallback_homogeneous homogenous); +r_obj* list_unchop_fallback(r_obj* ptype, + r_obj* x, + r_obj* indices, + r_obj* name_spec, + const struct name_repair_opts* name_repair, + enum fallback_homogeneous homogenous); diff --git a/src/init.c b/src/init.c index dba022d15..d144e6b56 100644 --- a/src/init.c +++ b/src/init.c @@ -49,7 +49,7 @@ extern r_obj* ffi_as_location(r_obj*, r_obj*, r_obj*, r_obj*, r_obj*, r_obj*, r_ extern r_obj* ffi_slice(r_obj*, r_obj*, r_obj*); extern r_obj* ffi_init(r_obj*, r_obj*, r_obj*); extern SEXP vctrs_chop(SEXP, SEXP); -extern r_obj* ffi_vec_unchop(r_obj*, r_obj*, r_obj*, r_obj*, r_obj*); +extern r_obj* ffi_list_unchop(r_obj*, r_obj*, r_obj*, r_obj*, r_obj*); extern SEXP vctrs_chop_seq(SEXP, SEXP, SEXP, SEXP); extern r_obj* ffi_slice_seq(r_obj*, r_obj*, r_obj*, r_obj*); extern r_obj* ffi_slice_rep(r_obj*, r_obj*, r_obj*); @@ -218,7 +218,7 @@ static const R_CallMethodDef CallEntries[] = { {"ffi_slice", (DL_FUNC) &ffi_slice, 3}, {"ffi_init", (DL_FUNC) &ffi_init, 3}, {"vctrs_chop", (DL_FUNC) &vctrs_chop, 2}, - {"ffi_vec_unchop", (DL_FUNC) &ffi_vec_unchop, 5}, + {"ffi_list_unchop", (DL_FUNC) &ffi_list_unchop, 5}, {"vctrs_chop_seq", (DL_FUNC) &vctrs_chop_seq, 4}, {"ffi_slice_seq", (DL_FUNC) &ffi_slice_seq, 4}, {"ffi_slice_rep", (DL_FUNC) &ffi_slice_rep, 3}, diff --git a/tests/testthat/_snaps/c.md b/tests/testthat/_snaps/c.md index d0aef9005..315c0fb34 100644 --- a/tests/testthat/_snaps/c.md +++ b/tests/testthat/_snaps/c.md @@ -105,38 +105,38 @@ Output [1] 1.7KB Code - # # `vec_unchop()` + # # `list_unchop()` # Integers - with_memory_prof(vec_unchop(ints)) + with_memory_prof(list_unchop(ints)) Output [1] 1.13KB Code # Doubles - with_memory_prof(vec_unchop(dbls)) + with_memory_prof(list_unchop(dbls)) Output [1] 1.52KB Code # Integers to integer - with_memory_prof(vec_unchop(ints, ptype = int())) + with_memory_prof(list_unchop(ints, ptype = int())) Output [1] 896B Code # Doubles to integer - with_memory_prof(vec_unchop(dbls, ptype = int())) + with_memory_prof(list_unchop(dbls, ptype = int())) Output [1] 896B Code # # Concatenation with names # Named integers ints <- rep(list(set_names(1:3, letters[1:3])), 100) - with_memory_prof(vec_unchop(ints)) + with_memory_prof(list_unchop(ints)) Output [1] 4.3KB Code # Named matrices mat <- matrix(1:4, 2, dimnames = list(c("foo", "bar"))) mats <- rep(list(mat), 100) - with_memory_prof(vec_unchop(mats)) + with_memory_prof(list_unchop(mats)) Output [1] 5.52KB Code @@ -144,7 +144,7 @@ df <- data_frame(x = set_names(as.list(1:2), c("a", "b")), y = set_names(1:2, c( "A", "B")), z = data_frame(Z = set_names(1:2, c("Za", "Zb")))) dfs <- rep(list(df), 100) - with_memory_prof(vec_unchop(dfs)) + with_memory_prof(list_unchop(dfs)) Output [1] 9.05KB Code @@ -152,13 +152,13 @@ df <- data_frame(x = 1:2) dfs <- rep(list(df), 100) dfs <- map2(dfs, seq_along(dfs), set_rownames_recursively) - with_memory_prof(vec_unchop(dfs)) + with_memory_prof(list_unchop(dfs)) Output [1] 6.28KB Code # Data frame with rownames (repaired, non-recursive case) dfs <- map(dfs, set_rownames_recursively) - with_memory_prof(vec_unchop(dfs)) + with_memory_prof(list_unchop(dfs)) Output [1] 12.4KB Code @@ -166,13 +166,13 @@ df <- data_frame(x = 1:2, y = data_frame(x = 1:2)) dfs <- rep(list(df), 100) dfs <- map2(dfs, seq_along(dfs), set_rownames_recursively) - with_memory_prof(vec_unchop(dfs)) + with_memory_prof(list_unchop(dfs)) Output [1] 908KB Code # FIXME (#1217): Data frame with rownames (repaired, recursive case) dfs <- map(dfs, set_rownames_recursively) - with_memory_prof(vec_unchop(dfs)) + with_memory_prof(list_unchop(dfs)) Output [1] 920KB diff --git a/tests/testthat/_snaps/lifecycle-deprecated.md b/tests/testthat/_snaps/lifecycle-deprecated.md new file mode 100644 index 000000000..8f8decc9e --- /dev/null +++ b/tests/testthat/_snaps/lifecycle-deprecated.md @@ -0,0 +1,11 @@ +# vec_unchop() is soft-deprecated + + Code + vec_unchop(list(1), indices = list(1)) + Condition + Warning: + `vec_unchop()` was deprecated in vctrs 0.5.0. + Please use `list_unchop()` instead. + Output + [1] 1 + diff --git a/tests/testthat/_snaps/slice-chop.md b/tests/testthat/_snaps/slice-chop.md index e65daf469..20a6847e6 100644 --- a/tests/testthat/_snaps/slice-chop.md +++ b/tests/testthat/_snaps/slice-chop.md @@ -1,7 +1,7 @@ -# vec_unchop() errors on unsupported location values +# list_unchop() errors on unsupported location values Code - (expect_error(vec_unchop(list(1, 2), list(c(1, 2), 0)), class = "vctrs_error_subscript_type") + (expect_error(list_unchop(list(1, 2), list(c(1, 2), 0)), class = "vctrs_error_subscript_type") ) Output @@ -10,7 +10,7 @@ x Subscript can't contain `0` values. i It has a `0` value at location 1. Code - (expect_error(vec_unchop(list(1), list(-1)), class = "vctrs_error_subscript_type") + (expect_error(list_unchop(list(1), list(-1)), class = "vctrs_error_subscript_type") ) Output @@ -18,12 +18,12 @@ ! Must subset elements with a valid subscript vector. x Subscript can't contain negative locations. -# vec_unchop() fails with complex foreign S3 classes +# list_unchop() fails with complex foreign S3 classes Code x <- structure(foobar(1), attr_foo = "foo") y <- structure(foobar(2), attr_bar = "bar") - (expect_error(vec_unchop(list(x, y)), class = "vctrs_error_incompatible_type")) + (expect_error(list_unchop(list(x, y)), class = "vctrs_error_incompatible_type")) Output Error: @@ -32,12 +32,12 @@ i The author of the class should implement vctrs methods. i See . -# vec_unchop() fails with complex foreign S4 classes +# list_unchop() fails with complex foreign S4 classes Code joe <- .Counts(c(1L, 2L), name = "Joe") jane <- .Counts(3L, name = "Jane") - (expect_error(vec_unchop(list(joe, jane)), class = "vctrs_error_incompatible_type") + (expect_error(list_unchop(list(joe, jane)), class = "vctrs_error_incompatible_type") ) Output @@ -47,41 +47,41 @@ i The author of the class should implement vctrs methods. i See . -# vec_unchop() falls back for S4 classes with a registered c() method +# list_unchop() falls back for S4 classes with a registered c() method Code - (expect_error(vec_unchop(list(joe, 1, jane), list(c(1, 2), 3, 4)), class = "vctrs_error_incompatible_type") + (expect_error(list_unchop(list(joe, 1, jane), list(c(1, 2), 3, 4)), class = "vctrs_error_incompatible_type") ) Output Error: ! Can't combine `..1` and `..2` . -# vec_unchop() fallback doesn't support `name_spec` or `ptype` +# list_unchop() fallback doesn't support `name_spec` or `ptype` Code foo <- structure(foobar(1), foo = "foo") bar <- structure(foobar(2), bar = "bar") - (expect_error(with_c_foobar(vec_unchop(list(foo, bar), name_spec = "{outer}_{inner}")), + (expect_error(with_c_foobar(list_unchop(list(foo, bar), name_spec = "{outer}_{inner}")), "name specification")) Output - Error in `vec_unchop()`: + Error in `list_unchop()`: ! Can't use a name specification with non-vctrs types. vctrs methods must be implemented for class `vctrs_foobar`. See . Code - (expect_error(with_c_foobar(vec_unchop(list(foobar(1)), ptype = "")), class = "vctrs_error_incompatible_type") + (expect_error(with_c_foobar(list_unchop(list(foobar(1)), ptype = "")), class = "vctrs_error_incompatible_type") ) Output Error: ! Can't convert to . -# vec_unchop() does not support non-numeric S3 indices +# list_unchop() does not support non-numeric S3 indices Code - (expect_error(vec_unchop(list(1), list(factor("x"))), class = "vctrs_error_subscript_type") + (expect_error(list_unchop(list(1), list(factor("x"))), class = "vctrs_error_subscript_type") ) Output @@ -90,7 +90,7 @@ x Subscript has the wrong type `character`. i It must be numeric. Code - (expect_error(vec_unchop(list(1), list(foobar(1L))), class = "vctrs_error_subscript_type") + (expect_error(list_unchop(list(1), list(foobar(1L))), class = "vctrs_error_subscript_type") ) Output @@ -99,17 +99,17 @@ x Subscript has the wrong type `vctrs_foobar`. i It must be numeric. -# can ignore names in `vec_unchop()` by providing a `zap()` name-spec (#232) +# can ignore names in `list_unchop()` by providing a `zap()` name-spec (#232) Code - (expect_error(vec_unchop(list(a = c(b = letters), b = 3L), name_spec = zap()), + (expect_error(list_unchop(list(a = c(b = letters), b = 3L), name_spec = zap()), class = "vctrs_error_incompatible_type")) Output Error: ! Can't combine `a` and `b` . Code - (expect_error(vec_unchop(list(a = c(foo = 1:2), b = c(bar = "")), indices = list( + (expect_error(list_unchop(list(a = c(foo = 1:2), b = c(bar = "")), indices = list( 2:1, 3), name_spec = zap()), class = "vctrs_error_incompatible_type")) Output diff --git a/tests/testthat/test-c.R b/tests/testthat/test-c.R index 9713aae42..51899ec3a 100644 --- a/tests/testthat/test-c.R +++ b/tests/testthat/test-c.R @@ -399,10 +399,10 @@ test_that("can zap outer names from a name-spec (#1215)", { ) expect_null( - names(vec_unchop(list(a = 1:2), indices = list(1:2), name_spec = zap_outer_spec)) + names(list_unchop(list(a = 1:2), indices = list(1:2), name_spec = zap_outer_spec)) ) expect_identical( - names(vec_unchop(list(a = 1:2, c(foo = 3L)), indices = list(1:2, 3), name_spec = zap_outer_spec)), + names(list_unchop(list(a = 1:2, c(foo = 3L)), indices = list(1:2, 3), name_spec = zap_outer_spec)), c("", "", "foo") ) }) @@ -415,14 +415,14 @@ test_that("named empty vectors force named output (#1263)", { expect_named(vec_c(x, 1L), "") expect_named(vec_c(x, 1), "") - expect_named(vec_unchop(list(x), list(int())), chr()) - expect_named(vec_unchop(list(x, x), list(int(), int())), chr()) - expect_named(vec_unchop(list(x, 1L), list(int(), 1)), "") + expect_named(list_unchop(list(x), list(int())), chr()) + expect_named(list_unchop(list(x, x), list(int(), int())), chr()) + expect_named(list_unchop(list(x, 1L), list(int(), 1)), "") # FIXME: `vec_cast_common()` dropped names # https://github.com/r-lib/vctrs/issues/623 expect_failure( - expect_named(vec_unchop(list(x, 1), list(int(), 1)), "") + expect_named(list_unchop(list(x, 1), list(int(), 1)), "") ) }) @@ -452,30 +452,30 @@ test_that("concatenation performs expected allocations", { with_memory_prof(vec_c_list(dbls, ptype = int())) - "# `vec_unchop()` " + "# `list_unchop()` " "Integers" - with_memory_prof(vec_unchop(ints)) + with_memory_prof(list_unchop(ints)) "Doubles" - with_memory_prof(vec_unchop(dbls)) + with_memory_prof(list_unchop(dbls)) "Integers to integer" - with_memory_prof(vec_unchop(ints, ptype = int())) + with_memory_prof(list_unchop(ints, ptype = int())) "Doubles to integer" - with_memory_prof(vec_unchop(dbls, ptype = int())) + with_memory_prof(list_unchop(dbls, ptype = int())) "# Concatenation with names" "Named integers" ints <- rep(list(set_names(1:3, letters[1:3])), 1e2) - with_memory_prof(vec_unchop(ints)) + with_memory_prof(list_unchop(ints)) "Named matrices" mat <- matrix(1:4, 2, dimnames = list(c("foo", "bar"))) mats <- rep(list(mat), 1e2) - with_memory_prof(vec_unchop(mats)) + with_memory_prof(list_unchop(mats)) "Data frame with named columns" df <- data_frame( @@ -484,17 +484,17 @@ test_that("concatenation performs expected allocations", { z = data_frame(Z = set_names(1:2, c("Za", "Zb"))) ) dfs <- rep(list(df), 1e2) - with_memory_prof(vec_unchop(dfs)) + with_memory_prof(list_unchop(dfs)) "Data frame with rownames (non-repaired, non-recursive case)" df <- data_frame(x = 1:2) dfs <- rep(list(df), 1e2) dfs <- map2(dfs, seq_along(dfs), set_rownames_recursively) - with_memory_prof(vec_unchop(dfs)) + with_memory_prof(list_unchop(dfs)) "Data frame with rownames (repaired, non-recursive case)" dfs <- map(dfs, set_rownames_recursively) - with_memory_prof(vec_unchop(dfs)) + with_memory_prof(list_unchop(dfs)) # FIXME: The following recursive cases duplicate rownames # excessively because df-cols are restored at each chunk @@ -506,11 +506,11 @@ test_that("concatenation performs expected allocations", { ) dfs <- rep(list(df), 1e2) dfs <- map2(dfs, seq_along(dfs), set_rownames_recursively) - with_memory_prof(vec_unchop(dfs)) + with_memory_prof(list_unchop(dfs)) "FIXME (#1217): Data frame with rownames (repaired, recursive case)" dfs <- map(dfs, set_rownames_recursively) - with_memory_prof(vec_unchop(dfs)) + with_memory_prof(list_unchop(dfs)) }) }) @@ -522,7 +522,7 @@ test_that("can dispatch many times", { class = c("vctrs_foobar", "tbl_df", "tbl", "data.frame") ) x <- lapply(1:200, function(...) foo) - expect_error(NA, object = vctrs::vec_unchop(x)) + expect_error(NA, object = vctrs::list_unchop(x)) }) test_that("dots splicing clones as appropriate", { diff --git a/tests/testthat/test-lifecycle-deprecated.R b/tests/testthat/test-lifecycle-deprecated.R index 5587f589c..1c5fb6197 100644 --- a/tests/testthat/test-lifecycle-deprecated.R +++ b/tests/testthat/test-lifecycle-deprecated.R @@ -13,3 +13,16 @@ test_that("vec_repeat() still works", { expect_identical(vec_repeat(1:2, times = 2), vec_rep(1:2, 2)) expect_identical(vec_repeat(1:2, each = 2), vec_rep_each(1:2, 2)) }) + +test_that("vec_unchop() is soft-deprecated", { + local_options(lifecycle_verbosity = "warning") + expect_snapshot(vec_unchop(list(1), indices = list(1))) +}) + +test_that("vec_unchop() still works", { + local_options(lifecycle_verbosity = "quiet") + expect_identical( + vec_unchop(list(1L, 2:3), indices = list(2, c(3, 1))), + c(3L, 1L, 2L) + ) +}) diff --git a/tests/testthat/test-slice-chop.R b/tests/testthat/test-slice-chop.R index e22ffecb1..e9b8365a0 100644 --- a/tests/testthat/test-slice-chop.R +++ b/tests/testthat/test-slice-chop.R @@ -249,60 +249,60 @@ test_that("can chop S3 objects using the fallback method with compact seqs", { expect_equal(vec_chop_seq(x, 2L, 2L), list(vec_slice(x, 3:4))) }) -# vec_unchop -------------------------------------------------------------- +# list_unchop -------------------------------------------------------------- test_that("`x` must be a list", { - expect_error(vec_unchop(1, list(1)), "`x` must be a list") - expect_error(vec_unchop(data.frame(x=1), list(1)), "`x` must be a list") + expect_error(list_unchop(1, list(1)), "`x` must be a list") + expect_error(list_unchop(data.frame(x=1), list(1)), "`x` must be a list") }) test_that("`indices` must be a list", { - expect_error(vec_unchop(list(1), 1), "`indices` must be a list of integers, or `NULL`") - expect_error(vec_unchop(list(1), data.frame(x=1)), "`indices` must be a list of integers, or `NULL`") + expect_error(list_unchop(list(1), 1), "`indices` must be a list of integers, or `NULL`") + expect_error(list_unchop(list(1), data.frame(x=1)), "`indices` must be a list of integers, or `NULL`") }) test_that("`indices` must be a list of integers", { - expect_error(vec_unchop(list(1), list("x")), class = "vctrs_error_subscript_type") - expect_error(vec_unchop(list(1), list(TRUE)), class = "vctrs_error_subscript_type") - expect_error(vec_unchop(list(1), list(quote(name))), class = "vctrs_error_subscript_type") + expect_error(list_unchop(list(1), list("x")), class = "vctrs_error_subscript_type") + expect_error(list_unchop(list(1), list(TRUE)), class = "vctrs_error_subscript_type") + expect_error(list_unchop(list(1), list(quote(name))), class = "vctrs_error_subscript_type") }) test_that("`x` and `indices` must be lists of the same size", { - expect_error(vec_unchop(list(1, 2), list(1)), "`x` and `indices` must be lists of the same size") + expect_error(list_unchop(list(1, 2), list(1)), "`x` and `indices` must be lists of the same size") }) test_that("can unchop with an AsIs list (#1463)", { x <- I(list(1, 2)) - expect_identical(vec_unchop(x), c(1, 2)) + expect_identical(list_unchop(x), c(1, 2)) }) test_that("can unchop empty vectors", { - expect_null(vec_unchop(list())) - expect_null(vec_unchop(list(), list())) - expect_identical(vec_unchop(list(), list(), ptype = numeric()), numeric()) + expect_null(list_unchop(list())) + expect_null(list_unchop(list(), list())) + expect_identical(list_unchop(list(), list(), ptype = numeric()), numeric()) }) test_that("can unchop a list of NULL", { - expect_null(vec_unchop(list(NULL), list(integer()))) - expect_identical(vec_unchop(list(NULL), list(integer()), ptype = numeric()), numeric()) - expect_identical(vec_unchop(list(NULL, NULL), list(integer(), integer()), ptype = numeric()), numeric()) + expect_null(list_unchop(list(NULL), list(integer()))) + expect_identical(list_unchop(list(NULL), list(integer()), ptype = numeric()), numeric()) + expect_identical(list_unchop(list(NULL, NULL), list(integer(), integer()), ptype = numeric()), numeric()) }) test_that("NULLs are ignored when unchopped with other vectors", { - expect_identical(vec_unchop(list("a", NULL, "b")), c("a", "b")) - expect_identical(vec_unchop(list("a", NULL, "b"), list(2, integer(), 1)), c("b", "a")) + expect_identical(list_unchop(list("a", NULL, "b")), c("a", "b")) + expect_identical(list_unchop(list("a", NULL, "b"), list(2, integer(), 1)), c("b", "a")) }) test_that("can unchop atomic vectors", { - expect_identical(vec_unchop(list(1, 2), list(2, 1)), c(2, 1)) - expect_identical(vec_unchop(list("a", "b"), list(2, 1)), c("b", "a")) + expect_identical(list_unchop(list(1, 2), list(2, 1)), c(2, 1)) + expect_identical(list_unchop(list("a", "b"), list(2, 1)), c("b", "a")) }) test_that("can unchop lists", { x <- list(list("a", "b"), list("c")) indices <- list(c(2, 3), 1) - expect_identical(vec_unchop(x, indices), list("c", "a", "b")) + expect_identical(list_unchop(x, indices), list("c", "a", "b")) }) test_that("can unchop data frames", { @@ -314,7 +314,7 @@ test_that("can unchop data frames", { expect <- vec_slice(vec_c(df1, df2), vec_order(vec_c(!!! indices))) - expect_identical(vec_unchop(x, indices), expect) + expect_identical(list_unchop(x, indices), expect) }) test_that("can unchop factors", { @@ -327,7 +327,7 @@ test_that("can unchop factors", { # levels are in the order they are seen! expect <- factor(c("y", "z", "x"), levels = c("z", "x", "y")) - expect_identical(vec_unchop(x, indices), expect) + expect_identical(list_unchop(x, indices), expect) }) test_that("can fallback when unchopping matrices", { @@ -339,8 +339,8 @@ test_that("can fallback when unchopping matrices", { expect <- vec_slice(vec_c(mat1, mat2), vec_order(vec_c(!!! indices))) - expect_identical(vec_unchop(x, indices), expect) - expect_identical(vec_unchop(x), vec_c(mat1, mat2)) + expect_identical(list_unchop(x, indices), expect) + expect_identical(list_unchop(x), vec_c(mat1, mat2)) }) test_that("can fallback when unchopping arrays of >2D", { @@ -352,92 +352,92 @@ test_that("can fallback when unchopping arrays of >2D", { expect <- vec_slice(vec_c(arr1, arr2), vec_order(vec_c(!!! indices))) - expect_identical(vec_unchop(x, indices), expect) - expect_identical(vec_unchop(x), vec_c(arr1, arr2)) + expect_identical(list_unchop(x, indices), expect) + expect_identical(list_unchop(x), vec_c(arr1, arr2)) }) test_that("can unchop with all size 0 elements and get the right ptype", { x <- list(integer(), integer()) indices <- list(integer(), integer()) - expect_identical(vec_unchop(x, indices), integer()) + expect_identical(list_unchop(x, indices), integer()) }) test_that("can unchop with some size 0 elements", { x <- list(integer(), 1:2, integer()) indices <- list(integer(), 2:1, integer()) - expect_identical(vec_unchop(x, indices), 2:1) + expect_identical(list_unchop(x, indices), 2:1) }) test_that("NULL is a valid index", { - expect_equal(vec_unchop(list(1, 2), list(NULL, 1)), 2) - expect_error(vec_unchop(list(1, 2), list(NULL, 2)), class = "vctrs_error_subscript_oob") + expect_equal(list_unchop(list(1, 2), list(NULL, 1)), 2) + expect_error(list_unchop(list(1, 2), list(NULL, 2)), class = "vctrs_error_subscript_oob") }) test_that("unchopping recycles elements of x to the size of the index", { x <- list(1, 2) indices <- list(c(3, 4, 5), c(2, 1)) - expect_identical(vec_unchop(x, indices), c(2, 2, 1, 1, 1)) + expect_identical(list_unchop(x, indices), c(2, 2, 1, 1, 1)) }) test_that("unchopping takes the common type", { x <- list(1, "a") indices <- list(1, 2) - expect_error(vec_unchop(x, indices), class = "vctrs_error_incompatible_type") + expect_error(list_unchop(x, indices), class = "vctrs_error_incompatible_type") x <- list(1, 2L) - expect_type(vec_unchop(x, indices), "double") + expect_type(list_unchop(x, indices), "double") }) test_that("can specify a ptype to override common type", { x <- list(1, 2L) indices <- list(1, 2) - expect_identical(vec_unchop(x, indices, ptype = integer()), c(1L, 2L)) + expect_identical(list_unchop(x, indices, ptype = integer()), c(1L, 2L)) }) test_that("leaving `indices = NULL` unchops sequentially", { x <- list(1:2, 3:5, 6L) - expect_identical(vec_unchop(x), 1:6) + expect_identical(list_unchop(x), 1:6) }) test_that("outer names are kept", { x <- list(x = 1, y = 2) - expect_named(vec_unchop(x), c("x", "y")) - expect_named(vec_unchop(x, list(2, 1)), c("y", "x")) + expect_named(list_unchop(x), c("x", "y")) + expect_named(list_unchop(x, list(2, 1)), c("y", "x")) }) test_that("outer names are recycled in the right order", { x <- list(x = 1, y = 2) - expect_error(vec_unchop(x, list(c(1, 2), 3)), "Can't merge") - expect_named(vec_unchop(x, list(c(1, 3), 2), name_spec = "{outer}_{inner}"), c("x_1", "y", "x_2")) - expect_named(vec_unchop(x, list(c(3, 1), 2), name_spec = "{outer}_{inner}"), c("x_2", "y", "x_1")) + expect_error(list_unchop(x, list(c(1, 2), 3)), "Can't merge") + expect_named(list_unchop(x, list(c(1, 3), 2), name_spec = "{outer}_{inner}"), c("x_1", "y", "x_2")) + expect_named(list_unchop(x, list(c(3, 1), 2), name_spec = "{outer}_{inner}"), c("x_2", "y", "x_1")) }) test_that("outer names can be merged with inner names", { x <- list(x = c(a = 1), y = c(b = 2)) - expect_error(vec_unchop(x), "Can't merge") - expect_named(vec_unchop(x, name_spec = "{outer}_{inner}"), c("x_a", "y_b")) - expect_named(vec_unchop(x, list(2, 1), name_spec = "{outer}_{inner}"), c("y_b", "x_a")) + expect_error(list_unchop(x), "Can't merge") + expect_named(list_unchop(x, name_spec = "{outer}_{inner}"), c("x_a", "y_b")) + expect_named(list_unchop(x, list(2, 1), name_spec = "{outer}_{inner}"), c("y_b", "x_a")) }) test_that("not all inputs have to be named", { x <- list(c(a = 1), 2, c(c = 3)) indices <- list(2, 1, 3) - expect_named(vec_unchop(x, indices), c("", "a", "c")) + expect_named(list_unchop(x, indices), c("", "a", "c")) }) -test_that("vec_unchop() keeps data frame row names", { +test_that("list_unchop() keeps data frame row names", { df1 <- data.frame(x = 1:2, row.names = c("r1", "r2")) df2 <- data.frame(x = 3:4, row.names = c("r3", "r4")) x <- list(df1, df2) indices <- list(c(3, 1), c(2, 4)) - result <- vec_unchop(x, indices) + result <- list_unchop(x, indices) expect <- c("r2", "r3", "r1", "r4") expect_identical(vec_names(result), expect) @@ -450,12 +450,12 @@ test_that("individual data frame columns retain vector names", { x <- list(df1, df2) indices <- list(c(1, 2), 3) - result <- vec_unchop(x, indices = indices) + result <- list_unchop(x, indices = indices) expect_named(result$x, c("a", "b", "c")) # Names should be identical to equivalent `vec_c()` call - expect_identical(vec_unchop(x, indices = indices), vec_c(!!!x)) + expect_identical(list_unchop(x, indices = indices), vec_c(!!!x)) }) test_that("df-col row names are repaired silently", { @@ -466,7 +466,7 @@ test_that("df-col row names are repaired silently", { indices <- list(1, 2) expect_silent({ - result <- vec_unchop(x, indices = indices) + result <- list_unchop(x, indices = indices) }) expect_identical(vec_names(result$x), c("inner...1", "inner...2")) @@ -476,7 +476,7 @@ test_that("monitoring - can technically assign to the same location twice", { x <- list(1:2, 3L) indices <- list(1:2, 1L) - expect_identical(vec_unchop(x, indices), c(3L, 2L, NA)) + expect_identical(list_unchop(x, indices), c(3L, 2L, NA)) }) test_that("index values are validated", { @@ -485,10 +485,10 @@ test_that("index values are validated", { indices2 <- list(c(1, 4), 2) indices3 <- list(c(1, 3, 4), 2) - expect_error(vec_unchop(x, indices1), class = "vctrs_error_subscript_oob") - expect_error(vec_unchop(x, indices2), class = "vctrs_error_subscript_oob") + expect_error(list_unchop(x, indices1), class = "vctrs_error_subscript_oob") + expect_error(list_unchop(x, indices2), class = "vctrs_error_subscript_oob") - expect_identical(vec_unchop(x, indices3), c(1, 2, 1, 1)) + expect_identical(list_unchop(x, indices3), c(1, 2, 1, 1)) }) test_that("name repair is respected and happens after ordering according to `indices`", { @@ -497,18 +497,18 @@ test_that("name repair is respected and happens after ordering according to `ind x <- list(c(a = 1), c(a = 2)) indices <- list(2, 1) - expect_named(vec_unchop(x, indices), c("a", "a")) - expect_named(vec_unchop(x, indices, name_repair = "unique"), c("a...1", "a...2")) + expect_named(list_unchop(x, indices), c("a", "a")) + expect_named(list_unchop(x, indices, name_repair = "unique"), c("a...1", "a...2")) }) -test_that("vec_unchop() errors on unsupported location values", { +test_that("list_unchop() errors on unsupported location values", { expect_snapshot({ (expect_error( - vec_unchop(list(1, 2), list(c(1, 2), 0)), + list_unchop(list(1, 2), list(c(1, 2), 0)), class = "vctrs_error_subscript_type" )) (expect_error( - vec_unchop(list(1), list(-1)), + list_unchop(list(1), list(-1)), class = "vctrs_error_subscript_type" )) }) @@ -516,35 +516,35 @@ test_that("vec_unchop() errors on unsupported location values", { test_that("missing values propagate", { expect_identical( - vec_unchop(list(1, 2), list(c(NA_integer_, NA_integer_), c(NA_integer_, 3))), + list_unchop(list(1, 2), list(c(NA_integer_, NA_integer_), c(NA_integer_, 3))), c(NA, NA, 2, NA) ) }) -test_that("vec_unchop() works with simple homogeneous foreign S3 classes", { - expect_identical(vec_unchop(list(foobar(1), foobar(2))), vec_c(foobar(c(1, 2)))) +test_that("list_unchop() works with simple homogeneous foreign S3 classes", { + expect_identical(list_unchop(list(foobar(1), foobar(2))), vec_c(foobar(c(1, 2)))) }) -test_that("vec_unchop() fails with complex foreign S3 classes", { +test_that("list_unchop() fails with complex foreign S3 classes", { expect_snapshot({ x <- structure(foobar(1), attr_foo = "foo") y <- structure(foobar(2), attr_bar = "bar") - (expect_error(vec_unchop(list(x, y)), class = "vctrs_error_incompatible_type")) + (expect_error(list_unchop(list(x, y)), class = "vctrs_error_incompatible_type")) }) }) -test_that("vec_unchop() fails with complex foreign S4 classes", { +test_that("list_unchop() fails with complex foreign S4 classes", { expect_snapshot({ joe <- .Counts(c(1L, 2L), name = "Joe") jane <- .Counts(3L, name = "Jane") - (expect_error(vec_unchop(list(joe, jane)), class = "vctrs_error_incompatible_type")) + (expect_error(list_unchop(list(joe, jane)), class = "vctrs_error_incompatible_type")) }) }) -test_that("vec_unchop() falls back to c() if S3 method is available", { +test_that("list_unchop() falls back to c() if S3 method is available", { # Check off-by-one error expect_error( - vec_unchop(list(foobar(1), "", foobar(2)), list(1, 2, 3)), + list_unchop(list(foobar(1), "", foobar(2)), list(1, 2, 3)), class = "vctrs_error_incompatible_type" ) @@ -560,56 +560,56 @@ test_that("vec_unchop() falls back to c() if S3 method is available", { c.vctrs_foobar = method_foobar ) expect_identical( - vec_unchop(list(foobar(1), foobar(2))), + list_unchop(list(foobar(1), foobar(2))), foobar(c(1, 2)) ) expect_identical( - vec_unchop(list(foobar(1), foobar(2)), list(1, 2)), + list_unchop(list(foobar(1), foobar(2)), list(1, 2)), foobar(c(1, 2)) ) expect_identical( - vec_unchop(list(foobar(1), foobar(2)), list(2, 1)), + list_unchop(list(foobar(1), foobar(2)), list(2, 1)), foobar(c(2, 1)) ) expect_identical( - vec_unchop(list(NULL, foobar(1), NULL, foobar(2))), + list_unchop(list(NULL, foobar(1), NULL, foobar(2))), foobar(c(1, 2)) ) # OOB error is respected expect_error( - vec_unchop(list(foobar(1), foobar(2)), list(1, 3)), + list_unchop(list(foobar(1), foobar(2)), list(1, 3)), class = "vctrs_error_subscript_oob" ) # Unassigned locations results in missing values. # Repeated assignment uses the last assigned value. expect_identical( - vec_unchop(list(foobar(c(1, 2)), foobar(3)), list(c(1, 3), 1)), + list_unchop(list(foobar(c(1, 2)), foobar(3)), list(c(1, 3), 1)), foobar(c(3, NA, 2)) ) expect_identical( - vec_unchop(list(foobar(c(1, 2)), foobar(3)), list(c(2, NA), NA)), + list_unchop(list(foobar(c(1, 2)), foobar(3)), list(c(2, NA), NA)), foobar(c(NA, 1, NA)) ) # Names are kept expect_identical( - vec_unchop(list(foobar(c(x = 1, y = 2)), foobar(c(x = 1))), list(c(2, 1), 3)), + list_unchop(list(foobar(c(x = 1, y = 2)), foobar(c(x = 1))), list(c(2, 1), 3)), foobar(c(y = 2, x = 1, x = 1)) ) # Recycles to the size of index expect_identical( - vec_unchop(list(foobar(1), foobar(2)), list(c(1, 3), 2)), + list_unchop(list(foobar(1), foobar(2)), list(c(1, 3), 2)), foobar(c(1, 2, 1)) ) expect_identical( - vec_unchop(list(foobar(1), foobar(2)), list(c(1, 2), integer())), + list_unchop(list(foobar(1), foobar(2)), list(c(1, 2), integer())), foobar(c(1, 1)) ) expect_error( - vec_unchop(list(foobar(1), foobar(2)), list(c(1, 3), integer())), + list_unchop(list(foobar(1), foobar(2)), list(c(1, 3), integer())), class = "vctrs_error_subscript_oob" ) @@ -623,7 +623,7 @@ test_that("vec_unchop() falls back to c() if S3 method is available", { # Registered fallback s3_register("base::c", "vctrs_c_fallback", method_vctrs_c_fallback) expect_identical( - vec_unchop( + list_unchop( list( structure(1, class = "vctrs_c_fallback"), structure(2, class = "vctrs_c_fallback") @@ -635,18 +635,18 @@ test_that("vec_unchop() falls back to c() if S3 method is available", { # Don't fallback for S3 lists which are treated as scalars by default expect_error( - vec_unchop(list(foobar(list(1)), foobar(list(2)))), + list_unchop(list(foobar(list(1)), foobar(list(2)))), class = "vctrs_error_scalar_type" ) }) -test_that("vec_unchop() falls back for S4 classes with a registered c() method", { +test_that("list_unchop() falls back for S4 classes with a registered c() method", { joe <- .Counts(c(1L, 2L), name = "Joe") jane <- .Counts(3L, name = "Jane") expect_snapshot({ (expect_error( - vec_unchop(list(joe, 1, jane), list(c(1, 2), 3, 4)), + list_unchop(list(joe, 1, jane), list(c(1, 2), 3, 4)), class = "vctrs_error_incompatible_type" )) }) @@ -654,74 +654,74 @@ test_that("vec_unchop() falls back for S4 classes with a registered c() method", local_c_counts() expect_identical( - vec_unchop(list(joe, jane), list(c(1, 3), 2)), + list_unchop(list(joe, jane), list(c(1, 3), 2)), .Counts(c(1L, 3L, 2L), name = "Dispatched") ) expect_identical( - vec_unchop(list(NULL, joe, jane), list(integer(), c(1, 3), 2)), + list_unchop(list(NULL, joe, jane), list(integer(), c(1, 3), 2)), .Counts(c(1L, 3L, 2L), name = "Dispatched") ) # Unassigned locations results in missing values. # Repeated assignment uses the last assigned value. expect_identical( - vec_unchop(list(joe, jane), list(c(1, 3), 1)), + list_unchop(list(joe, jane), list(c(1, 3), 1)), .Counts(c(3L, NA, 2L), name = "Dispatched") ) expect_identical( - vec_unchop(list(joe, jane), list(c(2, NA), NA)), + list_unchop(list(joe, jane), list(c(2, NA), NA)), .Counts(c(NA, 1L, NA), name = "Dispatched") ) }) -test_that("vec_unchop() fallback doesn't support `name_spec` or `ptype`", { +test_that("list_unchop() fallback doesn't support `name_spec` or `ptype`", { expect_snapshot({ foo <- structure(foobar(1), foo = "foo") bar <- structure(foobar(2), bar = "bar") (expect_error( - with_c_foobar(vec_unchop(list(foo, bar), name_spec = "{outer}_{inner}")), + with_c_foobar(list_unchop(list(foo, bar), name_spec = "{outer}_{inner}")), "name specification" )) # Used to be an error about `ptype` (expect_error( - with_c_foobar(vec_unchop(list(foobar(1)), ptype = "")), + with_c_foobar(list_unchop(list(foobar(1)), ptype = "")), class = "vctrs_error_incompatible_type" )) }) }) -test_that("vec_unchop() supports numeric S3 indices", { +test_that("list_unchop() supports numeric S3 indices", { local_methods( vec_ptype2.vctrs_foobar = function(x, y, ...) UseMethod("vec_ptype2.vctrs_foobar"), vec_ptype2.vctrs_foobar.integer = function(x, y, ...) foobar(integer()), vec_cast.integer.vctrs_foobar = function(x, to, ...) vec_data(x) ) - expect_identical(vec_unchop(list(1), list(foobar(1L))), 1) + expect_identical(list_unchop(list(1), list(foobar(1L))), 1) }) -test_that("vec_unchop() does not support non-numeric S3 indices", { +test_that("list_unchop() does not support non-numeric S3 indices", { expect_snapshot({ (expect_error( - vec_unchop(list(1), list(factor("x"))), + list_unchop(list(1), list(factor("x"))), class = "vctrs_error_subscript_type" )) (expect_error( - vec_unchop(list(1), list(foobar(1L))), + list_unchop(list(1), list(foobar(1L))), class = "vctrs_error_subscript_type" )) }) }) -test_that("can ignore names in `vec_unchop()` by providing a `zap()` name-spec (#232)", { - expect_error(vec_unchop(list(a = c(b = 1:2)))) +test_that("can ignore names in `list_unchop()` by providing a `zap()` name-spec (#232)", { + expect_error(list_unchop(list(a = c(b = 1:2)))) expect_identical( - vec_unchop(list(a = c(b = 1:2), b = 3L), name_spec = zap()), + list_unchop(list(a = c(b = 1:2), b = 3L), name_spec = zap()), 1:3 ) expect_identical( - vec_unchop( + list_unchop( list(a = c(foo = 1:2), b = c(bar = 3L)), indices = list(2:1, 3), name_spec = zap() @@ -731,11 +731,11 @@ test_that("can ignore names in `vec_unchop()` by providing a `zap()` name-spec ( expect_snapshot({ (expect_error( - vec_unchop(list(a = c(b = letters), b = 3L), name_spec = zap()), + list_unchop(list(a = c(b = letters), b = 3L), name_spec = zap()), class = "vctrs_error_incompatible_type" )) (expect_error( - vec_unchop( + list_unchop( list(a = c(foo = 1:2), b = c(bar = "")), indices = list(2:1, 3), name_spec = zap() @@ -745,9 +745,9 @@ test_that("can ignore names in `vec_unchop()` by providing a `zap()` name-spec ( }) }) -test_that("vec_unchop() falls back to c() methods (#1120)", { +test_that("list_unchop() falls back to c() methods (#1120)", { expect_error( - vec_unchop(list(foobar(1), foobar(2, class = "foo"))), + list_unchop(list(foobar(1), foobar(2, class = "foo"))), class = "vctrs_error_incompatible_type" ) @@ -762,11 +762,11 @@ test_that("vec_unchop() falls back to c() methods (#1120)", { xs <- list(foobar(1), foobar(2, class = "foo")) expect_identical( - vec_unchop(xs), + list_unchop(xs), c("dispatched1", "dispatched2") ) expect_identical( - vec_unchop(xs, indices = list(2, 1)), + list_unchop(xs, indices = list(2, 1)), c("dispatched2", "dispatched1") ) @@ -777,26 +777,26 @@ test_that("vec_unchop() falls back to c() methods (#1120)", { ) expect_identical( - vec_unchop(xs), + list_unchop(xs), c("dispatched1", "dispatched2", "dispatched3") ) expect_identical( - vec_unchop(xs, list(c(2, 1), 3)), + list_unchop(xs, list(c(2, 1), 3)), c("dispatched2", "dispatched1", "dispatched3") ) }) -test_that("vec_unchop() fails if foreign classes are not homogeneous and there is no c() method", { +test_that("list_unchop() fails if foreign classes are not homogeneous and there is no c() method", { xs <- list( foobar(c(x = 1, y = 2), class = "foo"), foobar(c(x = 1), foo = 1) ) expect_error( - vec_unchop(xs), + list_unchop(xs), class = "vctrs_error_incompatible_type" ) expect_error( - vec_unchop(xs, list(c(2, 1), 3)), + list_unchop(xs, list(c(2, 1), 3)), class = "vctrs_error_incompatible_type" ) }) diff --git a/tests/testthat/test-type-table.R b/tests/testthat/test-type-table.R index a9562ab96..d9a127cda 100644 --- a/tests/testthat/test-type-table.R +++ b/tests/testthat/test-type-table.R @@ -198,11 +198,11 @@ test_that("names of the first dimension are kept in `vec_c()`", { expect_identical(dimnames(xx), list(c("r1", "r2", "r1", "r2"), NULL)) }) -test_that("can use a table in `vec_unchop()`", { +test_that("can use a table in `list_unchop()`", { x <- new_table(1:4, dim = c(2L, 2L)) - expect_identical(vec_unchop(list(x)), x) - expect_identical(vec_unchop(list(x, x), list(1:2, 4:3)), vec_slice(x, c(1:2, 2:1))) + expect_identical(list_unchop(list(x)), x) + expect_identical(list_unchop(list(x, x), list(1:2, 4:3)), vec_slice(x, c(1:2, 2:1))) }) test_that("can concatenate tables", { From 1062d7ff817095de8d40ea090a508b02ebc75e44 Mon Sep 17 00:00:00 2001 From: Davis Vaughan Date: Mon, 12 Sep 2022 10:59:18 -0400 Subject: [PATCH 034/312] Implement `missing = "remove"` (#1633) * Document our beliefs about missing values with negative indices * R side of `missing = "remove"` * Add logical support * Add integer support * Mention `"remove"` in error * Add character support * NEWS bullets * Initialize `na_propagate` to avoid potential compiler complaints * Don't modify the shared `integer()` * Add comment about `missing = "propagate", negative = "invert"` behavior * Propagate names when removing missing, zero, and oob values * Prepare for the merge of https://github.com/r-lib/rlang/pull/1471 * Remove skips and regenerate snapshots --- NEWS.md | 6 + R/subscript-loc.R | 34 +++- man/vec_as_location.Rd | 11 +- src/decl/subscript-loc-decl.h | 5 + src/subscript-loc.c | 209 +++++++++++++++++++------ src/subscript-loc.h | 1 + tests/testthat/_snaps/error-call.md | 2 +- tests/testthat/_snaps/subscript-loc.md | 84 +++++++++- tests/testthat/test-subscript-loc.R | 140 +++++++++++++++++ 9 files changed, 430 insertions(+), 62 deletions(-) diff --git a/NEWS.md b/NEWS.md index 4920c81d5..a70b8330e 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,5 +1,11 @@ # vctrs (development version) +* `vec_as_location()` and `num_as_location()` have gained a `missing = "remove"` + option (#1595). + +* `vec_as_location()` no longer matches `NA_character_` and `""` indices if + those invalid names appear in `names` (#1489). + * `vec_unchop()` has been renamed to `list_unchop()` to better indicate that it requires list input. `vec_unchop()` will stick around for a few minor versions, but has been formally soft-deprecated (#1209). diff --git a/R/subscript-loc.R b/R/subscript-loc.R index c47e36cf0..ad3f61359 100644 --- a/R/subscript-loc.R +++ b/R/subscript-loc.R @@ -25,9 +25,10 @@ #' vector that `i` will be matched against to construct the index. Otherwise, #' not used. The default value of `NULL` will result in an error #' if `i` is a character vector. -#' @param missing Whether to throw an `"error"` when `i` is a missing -#' value, or `"propagate"` it (return it as is). By default, vector +#' @param missing Whether to throw an `"error"` when `i` is a missing value, +#' `"propagate"` it (return it as is), or `"remove"` it. By default, vector #' subscripts can contain missing values and scalar subscripts can't. +#' Propagated missing values can't be combined with negative indices. #' @param arg The argument name to be displayed in error messages when #' `vec_as_location()` and `vec_as_location2()` are used to check the #' type of a function input. @@ -59,7 +60,7 @@ vec_as_location <- function(i, n, names = NULL, ..., - missing = c("propagate", "error"), + missing = c("propagate", "remove", "error"), arg = caller_arg(i), call = caller_env()) { check_dots_empty0(...) @@ -90,7 +91,7 @@ vec_as_location <- function(i, num_as_location <- function(i, n, ..., - missing = c("propagate", "error"), + missing = c("propagate", "remove", "error"), negative = c("invert", "error", "ignore"), oob = c("error", "remove", "extend"), zero = c("remove", "error", "ignore"), @@ -414,6 +415,31 @@ cnd_bullets_subscript_missing <- function(cnd, ...) { )) } +stop_subscript_empty <- function(i, ..., call = caller_env()) { + cnd_signal(new_error_subscript_type( + i = i, + body = cnd_bullets_subscript_empty, + ..., + call = call + )) +} +cnd_bullets_subscript_empty <- function(cnd, ...) { + cnd$subscript_arg <- append_arg("Subscript", cnd$subscript_arg) + + loc <- which(cnd$i == "") + if (length(loc) == 1) { + line <- glue::glue("It has an empty string at location {loc}.") + } else { + enum <- ensure_full_stop(enumerate(loc)) + line <- glue::glue("It has an empty string at locations {enum}") + } + + format_error_bullets(c( + x = glue::glue_data(cnd, "{subscript_arg} can't contain the empty string."), + x = line + )) +} + stop_indicator_size <- function(i, n, ..., call = caller_env()) { cnd_signal(new_error_subscript_size( i, diff --git a/man/vec_as_location.Rd b/man/vec_as_location.Rd index 1fd4f87ea..c371a2135 100644 --- a/man/vec_as_location.Rd +++ b/man/vec_as_location.Rd @@ -12,7 +12,7 @@ vec_as_location( n, names = NULL, ..., - missing = c("propagate", "error"), + missing = c("propagate", "remove", "error"), arg = caller_arg(i), call = caller_env() ) @@ -21,7 +21,7 @@ num_as_location( i, n, ..., - missing = c("propagate", "error"), + missing = c("propagate", "remove", "error"), negative = c("invert", "error", "ignore"), oob = c("error", "remove", "extend"), zero = c("remove", "error", "ignore"), @@ -65,9 +65,10 @@ if \code{i} is a character vector.} \item{...}{These dots are for future extensions and must be empty.} -\item{missing}{Whether to throw an \code{"error"} when \code{i} is a missing -value, or \code{"propagate"} it (return it as is). By default, vector -subscripts can contain missing values and scalar subscripts can't.} +\item{missing}{Whether to throw an \code{"error"} when \code{i} is a missing value, +\code{"propagate"} it (return it as is), or \code{"remove"} it. By default, vector +subscripts can contain missing values and scalar subscripts can't. +Propagated missing values can't be combined with negative indices.} \item{arg}{The argument name to be displayed in error messages when \code{vec_as_location()} and \code{vec_as_location2()} are used to check the diff --git a/src/decl/subscript-loc-decl.h b/src/decl/subscript-loc-decl.h index 6e4276f20..4ce4416a9 100644 --- a/src/decl/subscript-loc-decl.h +++ b/src/decl/subscript-loc-decl.h @@ -14,6 +14,8 @@ r_obj* int_invert_location(r_obj* subscript, const struct location_opts* opts); static r_obj* int_filter_zero(r_obj* subscript, r_ssize n_zero); +static +r_obj* int_filter_missing(r_obj* subscript, r_ssize n_missing); static r_obj* int_filter_oob(r_obj* subscript, r_ssize n, r_ssize n_oob); @@ -37,6 +39,9 @@ r_obj* chr_as_location(r_obj* subscript, static void stop_subscript_missing(r_obj* i, const struct location_opts* opts); +static +void stop_subscript_empty(r_obj* i, + const struct location_opts* opts); static void stop_subscript_oob_location(r_obj* i, diff --git a/src/subscript-loc.c b/src/subscript-loc.c index 5c6b95e95..b6d7536e7 100644 --- a/src/subscript-loc.c +++ b/src/subscript-loc.c @@ -62,22 +62,21 @@ r_obj* lgl_as_location(r_obj* subscript, const struct location_opts* opts) { r_ssize subscript_n = r_length(subscript); - if (opts->missing == SUBSCRIPT_MISSING_ERROR && lgl_any_na(subscript)) { - stop_subscript_missing(subscript, opts); - } - if (subscript_n == n) { - r_obj* out = KEEP(r_lgl_which(subscript, true)); + bool na_propagate = false; - r_obj* nms = KEEP(r_names(subscript)); - if (nms != R_NilValue) { - nms = KEEP(vec_slice(nms, out)); - r_attrib_poke_names(out, nms); - FREE(1); + switch (opts->missing) { + case SUBSCRIPT_MISSING_PROPAGATE: na_propagate = true; break; + case SUBSCRIPT_MISSING_REMOVE: break; + case SUBSCRIPT_MISSING_ERROR: { + if (lgl_any_na(subscript)) { + stop_subscript_missing(subscript, opts); + } + break; + } } - FREE(2); - return out; + return r_lgl_which(subscript, na_propagate); } /* A single `TRUE` or `FALSE` index is recycled to the full vector @@ -92,23 +91,45 @@ r_obj* lgl_as_location(r_obj* subscript, if (subscript_n == 1) { int elt = r_lgl_get(subscript, 0); - r_obj* out; + r_ssize recycle_size = n; + + r_obj* out = r_null; + r_keep_loc out_shelter; + KEEP_HERE(out, &out_shelter); + if (elt == r_globals.na_lgl) { - out = KEEP(r_alloc_integer(n)); - r_int_fill(out, r_globals.na_int, n); + switch (opts->missing) { + case SUBSCRIPT_MISSING_PROPAGATE: { + out = r_alloc_integer(n); + KEEP_AT(out, out_shelter); + r_int_fill(out, r_globals.na_int, n); + break; + } + case SUBSCRIPT_MISSING_REMOVE: { + out = r_copy(r_globals.empty_int); + KEEP_AT(out, out_shelter); + recycle_size = 0; + break; + } + case SUBSCRIPT_MISSING_ERROR: { + stop_subscript_missing(subscript, opts); + } + } } else if (elt) { - out = KEEP(r_alloc_integer(n)); + out = r_alloc_integer(n); + KEEP_AT(out, out_shelter); r_int_fill_seq(out, 1, n); } else { - return r_globals.empty_int; + out = r_copy(r_globals.empty_int); + KEEP_AT(out, out_shelter); + recycle_size = 0; } r_obj* nms = KEEP(r_names(subscript)); if (nms != R_NilValue) { - r_obj* recycled_nms = KEEP(r_alloc_character(n)); - r_chr_fill(recycled_nms, r_chr_get(nms, 0), n); + r_obj* recycled_nms = r_alloc_character(recycle_size); r_attrib_poke_names(out, recycled_nms); - FREE(1); + r_chr_fill(recycled_nms, r_chr_get(nms, 0), recycle_size); } FREE(2); @@ -134,13 +155,16 @@ r_obj* int_as_location(r_obj* subscript, r_ssize n_zero = 0; r_ssize n_oob = 0; + r_ssize n_missing = 0; for (r_ssize i = 0; i < loc_n; ++i, ++data) { int elt = *data; if (elt == r_globals.na_int) { - if (opts->missing == SUBSCRIPT_MISSING_ERROR) { - stop_subscript_missing(subscript, opts); + switch (opts->missing) { + case SUBSCRIPT_MISSING_PROPAGATE: break; + case SUBSCRIPT_MISSING_REMOVE: ++n_missing; break; + case SUBSCRIPT_MISSING_ERROR: stop_subscript_missing(subscript, opts); } } else if (elt == 0) { switch (opts->loc_zero) { @@ -175,7 +199,12 @@ r_obj* int_as_location(r_obj* subscript, r_keep_loc subscript_shelter; KEEP_HERE(subscript, &subscript_shelter); - if (n_zero) { + if (n_missing > 0) { + subscript = int_filter_missing(subscript, n_missing); + KEEP_AT(subscript, subscript_shelter); + } + + if (n_zero > 0) { subscript = int_filter_zero(subscript, n_zero); KEEP_AT(subscript, subscript_shelter); } @@ -217,8 +246,15 @@ r_obj* int_invert_location(r_obj* subscript, int j = *data; if (j == r_globals.na_int) { - stop_location_negative_missing(subscript, opts); + // Following base R by erroring on `missing = "propagate"`, e.g. `1[c(NA, -1)]`. + // Doesn't make sense to invert an `NA`, so we can't meaningfully propagate. + switch (opts->missing) { + case SUBSCRIPT_MISSING_PROPAGATE: stop_location_negative_missing(subscript, opts); + case SUBSCRIPT_MISSING_REMOVE: continue; + case SUBSCRIPT_MISSING_ERROR: stop_location_negative_missing(subscript, opts); + } } + if (j >= 0) { if (j == 0) { switch (opts->loc_zero) { @@ -256,43 +292,84 @@ r_obj* int_invert_location(r_obj* subscript, } static -r_obj* int_filter_zero(r_obj* subscript, - r_ssize n_zero) { - r_ssize loc_n = vec_size(subscript); - const int* data = r_int_cbegin(subscript); +r_obj* int_filter(r_obj* subscript, r_ssize n_filter, int value) { + const r_ssize size = r_length(subscript); + const int* v_subscript = r_int_cbegin(subscript); - r_obj* out = KEEP(r_alloc_integer(loc_n - n_zero)); - int* out_data = r_int_begin(out); + r_obj* out = KEEP(r_alloc_integer(size - n_filter)); + int* v_out = r_int_begin(out); - for (r_ssize i = 0; i < loc_n; ++i, ++data) { - int elt = *data; - if (elt != 0) { - *out_data = elt; - ++out_data; + r_obj* names = r_names(subscript); + const bool has_names = names != r_null; + r_obj* const* v_names = NULL; + r_obj* out_names = r_null; + if (has_names) { + v_names = r_chr_cbegin(names); + out_names = r_alloc_character(size - n_filter); + r_attrib_poke_names(out, out_names); + } + + r_ssize j = 0; + + for (r_ssize i = 0; i < size; ++i) { + const int elt = v_subscript[i]; + + if (elt != value) { + v_out[j] = elt; + + if (has_names) { + r_chr_poke(out_names, j, v_names[i]); + } + + ++j; } } FREE(1); return out; } +static +r_obj* int_filter_zero(r_obj* subscript, r_ssize n_zero) { + return int_filter(subscript, n_zero, 0); +} +static +r_obj* int_filter_missing(r_obj* subscript, r_ssize n_missing) { + return int_filter(subscript, n_missing, r_globals.na_int); +} static r_obj* int_filter_oob(r_obj* subscript, r_ssize n, r_ssize n_oob) { const r_ssize n_subscript = r_length(subscript); const r_ssize n_out = n_subscript - n_oob; + const int* v_subscript = r_int_cbegin(subscript); + r_obj* out = KEEP(r_alloc_integer(n_out)); int* v_out = r_int_begin(out); - r_ssize i_out = 0; - const int* v_subscript = r_int_cbegin(subscript); + r_obj* names = r_names(subscript); + const bool has_names = names != r_null; + r_obj* const* v_names = NULL; + r_obj* out_names = r_null; + if (has_names) { + v_names = r_chr_cbegin(names); + out_names = r_alloc_character(n_out); + r_attrib_poke_names(out, out_names); + } + + r_ssize j = 0; for (r_ssize i = 0; i < n_subscript; ++i) { const int elt = v_subscript[i]; if (abs(elt) <= n || elt == r_globals.na_int) { - v_out[i_out] = elt; - ++i_out; + v_out[j] = elt; + + if (has_names) { + r_chr_poke(out_names, j, v_names[i]); + } + + ++j; } } @@ -385,31 +462,52 @@ r_obj* chr_as_location(r_obj* subscript, r_abort("`names` must be a character vector."); } + bool remove_missing = false; + r_obj* matched = KEEP(Rf_match(names, subscript, r_globals.na_int)); + r_attrib_poke_names(matched, r_names(subscript)); r_ssize n = r_length(matched); - const int* p = r_int_cbegin(matched); + int* p = r_int_begin(matched); r_obj* const * ip = r_chr_cbegin(subscript); for (r_ssize k = 0; k < n; ++k) { - if (p[k] != r_globals.na_int) { - continue; + const r_obj* elt = ip[k]; + + if (elt == r_strs.empty) { + // `""` never matches, even if `names` contains a `""` name + stop_subscript_empty(subscript, opts); } - if (ip[k] != r_globals.na_str) { + if (elt == r_globals.na_str) { + // `NA_character_` never matches, even if `names` contains a missing name + p[k] = r_globals.na_int; + + switch (opts->missing) { + case SUBSCRIPT_MISSING_PROPAGATE: continue; + case SUBSCRIPT_MISSING_REMOVE: remove_missing = true; continue; + case SUBSCRIPT_MISSING_ERROR: stop_subscript_missing(subscript, opts); + } + } + + if (p[k] == r_globals.na_int) { stop_subscript_oob_name(subscript, names, opts); } + } - if (opts->missing != SUBSCRIPT_MISSING_ERROR) { - continue; + if (remove_missing) { + if (opts->missing != SUBSCRIPT_MISSING_REMOVE) { + r_stop_internal("`missing = 'remove'` must be set if `n_missing > 0`."); } - stop_subscript_missing(subscript, opts); - } + r_obj* not_missing = KEEP(vec_detect_complete(matched)); + matched = KEEP(vec_slice(matched, not_missing)); - r_attrib_poke_names(matched, KEEP(r_names(subscript))); FREE(1); + FREE(2); + } + KEEP(matched); - FREE(1); + FREE(2); return matched; } @@ -473,6 +571,7 @@ enum subscript_missing parse_subscript_arg_missing(r_obj* x, const char* str = r_chr_get_c_string(x, 0); if (!strcmp(str, "propagate")) return SUBSCRIPT_MISSING_PROPAGATE; + if (!strcmp(str, "remove")) return SUBSCRIPT_MISSING_REMOVE; if (!strcmp(str, "error")) return SUBSCRIPT_MISSING_ERROR; stop_subscript_arg_missing(call); @@ -529,7 +628,7 @@ enum num_loc_zero parse_loc_zero(r_obj* x, static void stop_subscript_arg_missing(struct r_lazy call) { - r_abort_call(call.env, "`missing` must be one of \"propagate\" or \"error\"."); + r_abort_call(call.env, "`missing` must be one of \"propagate\", \"remove\", or \"error\"."); } static void stop_bad_negative(struct r_lazy call) { @@ -554,6 +653,16 @@ void stop_subscript_missing(r_obj* i, r_stop_unreachable(); } +static +void stop_subscript_empty(r_obj* i, + const struct location_opts* opts) { + r_obj* call = KEEP(r_lazy_eval(opts->subscript_opts.call)); + vctrs_eval_mask2(r_sym("stop_subscript_empty"), + syms_i, i, + syms_call, call); + r_stop_unreachable(); +} + static void stop_location_negative_missing(r_obj* i, const struct location_opts* opts) { diff --git a/src/subscript-loc.h b/src/subscript-loc.h index 8783ae55f..6cf59c61c 100644 --- a/src/subscript-loc.h +++ b/src/subscript-loc.h @@ -8,6 +8,7 @@ enum subscript_missing { SUBSCRIPT_MISSING_PROPAGATE = 0, + SUBSCRIPT_MISSING_REMOVE, SUBSCRIPT_MISSING_ERROR }; enum num_loc_negative { diff --git a/tests/testthat/_snaps/error-call.md b/tests/testthat/_snaps/error-call.md index a6e082a78..1650117fd 100644 --- a/tests/testthat/_snaps/error-call.md +++ b/tests/testthat/_snaps/error-call.md @@ -198,7 +198,7 @@ Output Error in `vctrs::num_as_location()`: - ! `missing` must be one of "propagate" or "error". + ! `missing` must be one of "propagate", "remove", or "error". --- diff --git a/tests/testthat/_snaps/subscript-loc.md b/tests/testthat/_snaps/subscript-loc.md index c55acaa09..2b2b2887b 100644 --- a/tests/testthat/_snaps/subscript-loc.md +++ b/tests/testthat/_snaps/subscript-loc.md @@ -674,6 +674,86 @@ x Subscript `foo(bar)` can't contain missing values. x It has a missing value at location 1. +# can alter logical missing value handling (#1595) + + Code + vec_as_location(x, n = 4L, missing = "error") + Condition + Error: + ! Must subset elements with a valid subscript vector. + x Subscript can't contain missing values. + x It has missing values at locations 2 and 4. + +--- + + Code + vec_as_location(x, n = 2L, missing = "error") + Condition + Error: + ! Must subset elements with a valid subscript vector. + x Subscript can't contain missing values. + x It has a missing value at location 1. + +# can alter character missing value handling (#1595) + + Code + vec_as_location(x, n = 2L, names = names, missing = "error") + Condition + Error: + ! Must subset elements with a valid subscript vector. + x Subscript can't contain missing values. + x It has missing values at locations 1 and 3. + +# can alter integer missing value handling (#1595) + + Code + vec_as_location(x, n = 4L, missing = "error") + Condition + Error: + ! Must subset elements with a valid subscript vector. + x Subscript can't contain missing values. + x It has missing values at locations 1 and 3. + +# can alter negative integer missing value handling (#1595) + + Code + num_as_location(x, n = 4L, missing = "propagate", negative = "invert") + Condition + Error: + ! Must subset elements with a valid subscript vector. + x Negative locations can't have missing values. + i Subscript `x` has 2 missing values at locations 2 and 3. + +--- + + Code + num_as_location(x, n = 4L, missing = "error", negative = "invert") + Condition + Error: + ! Must subset elements with a valid subscript vector. + x Negative locations can't have missing values. + i Subscript `x` has 2 missing values at locations 2 and 3. + +# empty string character indices never match empty string names (#1489) + + Code + vec_as_location("", n = 2L, names = names) + Condition + Error: + ! Must subset elements with a valid subscript vector. + x Subscript can't contain the empty string. + x It has an empty string at location 1. + +--- + + Code + vec_as_location(c("", "y", ""), n = 2L, names = names) + Condition + Error: + ! Must subset elements with a valid subscript vector. + x Subscript can't contain the empty string. + x It has an empty string at locations 1 and 3. + # can customise subscript type errors Code @@ -1019,7 +1099,7 @@ vec_as_location(1, 1L, missing = "bogus") Condition Error in `vec_as_location()`: - ! `missing` must be one of "propagate" or "error". + ! `missing` must be one of "propagate", "remove", or "error". # num_as_location() UI @@ -1027,7 +1107,7 @@ num_as_location(1, 1L, missing = "bogus") Condition Error in `num_as_location()`: - ! `missing` must be one of "propagate" or "error". + ! `missing` must be one of "propagate", "remove", or "error". --- diff --git a/tests/testthat/test-subscript-loc.R b/tests/testthat/test-subscript-loc.R index 3a7f9516a..9c71840d6 100644 --- a/tests/testthat/test-subscript-loc.R +++ b/tests/testthat/test-subscript-loc.R @@ -355,6 +355,27 @@ test_that("num_as_location() with `oob = 'error'` reports negative and positive }) }) +test_that("num_as_location() with `missing = 'remove'` retains names (#1633)", { + x <- c(a = 1, b = NA, c = 2, d = NA) + expect_named(num_as_location(x, n = 2, missing = "remove"), c("a", "c")) +}) + +test_that("num_as_location() with `zero = 'remove'` retains names (#1633)", { + x <- c(a = 1, b = 0, c = 2, d = 0) + expect_named(num_as_location(x, n = 2, zero = "remove"), c("a", "c")) +}) + +test_that("num_as_location() with `oob = 'remove'` retains names (#1633)", { + x <- c(a = 1, b = 3, c = 2, d = 4) + expect_named(num_as_location(x, n = 2, oob = "remove"), c("a", "c")) +}) + +test_that("num_as_location() with `negative = 'invert'` drops names (#1633)", { + # The inputs don't map 1:1 to outputs + x <- c(a = -1, b = -3) + expect_named(num_as_location(x, n = 5), NULL) +}) + test_that("missing values are supported in error formatters", { expect_snapshot({ (expect_error( @@ -401,6 +422,125 @@ test_that("can disallow missing values", { }) }) +test_that("can alter logical missing value handling (#1595)", { + x <- c(a = TRUE, b = NA, c = FALSE, d = NA) + + expect_identical( + vec_as_location(x, n = 4L, missing = "propagate"), + c(a = 1L, b = NA, d = NA) + ) + expect_identical( + vec_as_location(x, n = 4L, missing = "remove"), + c(a = 1L) + ) + expect_snapshot(error = TRUE, { + vec_as_location(x, n = 4L, missing = "error") + }) + + # Specifically test size 1 case, which has its own special path + x <- c(a = NA) + + expect_identical( + vec_as_location(x, n = 2L, missing = "propagate"), + c(a = NA_integer_, a = NA_integer_) + ) + expect_identical( + vec_as_location(x, n = 2L, missing = "remove"), + named(integer()) + ) + expect_snapshot(error = TRUE, { + vec_as_location(x, n = 2L, missing = "error") + }) +}) + +test_that("can alter character missing value handling (#1595)", { + x <- c(NA, "z", NA) + names(x) <- c("a", "b", "c") + names <- c("x", "z") + + expect_identical( + vec_as_location(x, n = 2L, names = names, missing = "propagate"), + set_names(c(NA, 2L, NA), names(x)) + ) + expect_identical( + vec_as_location(x, n = 2L, names = names, missing = "remove"), + set_names(2L, "b") + ) + expect_snapshot(error = TRUE, { + vec_as_location(x, n = 2L, names = names, missing = "error") + }) +}) + +test_that("can alter integer missing value handling (#1595)", { + x <- c(NA, 1L, NA, 3L) + names(x) <- c("a", "b", "c", "d") + + expect_identical( + vec_as_location(x, n = 4L, missing = "propagate"), + x + ) + expect_identical( + vec_as_location(x, n = 4L, missing = "remove"), + c(b = 1L, d = 3L) + ) + expect_snapshot(error = TRUE, { + vec_as_location(x, n = 4L, missing = "error") + }) +}) + +test_that("can alter negative integer missing value handling (#1595)", { + x <- c(-1L, NA, NA, -3L) + + expect_snapshot(error = TRUE, { + num_as_location(x, n = 4L, missing = "propagate", negative = "invert") + }) + expect_identical( + num_as_location(x, n = 4L, missing = "remove", negative = "invert"), + c(2L, 4L) + ) + expect_snapshot(error = TRUE, { + num_as_location(x, n = 4L, missing = "error", negative = "invert") + }) +}) + +test_that("missing value character indices never match missing value names (#1489)", { + x <- NA_character_ + names <- NA_character_ + + expect_identical(vec_as_location(x, n = 1L, names = names, missing = "propagate"), NA_integer_) + expect_identical(vec_as_location(x, n = 1L, names = names, missing = "remove"), integer()) +}) + +test_that("empty string character indices never match empty string names (#1489)", { + names <- c("", "y") + + expect_snapshot(error = TRUE, { + vec_as_location("", n = 2L, names = names) + }) + expect_snapshot(error = TRUE, { + vec_as_location(c("", "y", ""), n = 2L, names = names) + }) +}) + +test_that("scalar logical `FALSE` and `NA` cases don't modify a shared object (#1633)", { + x <- vec_as_location(FALSE, n = 2) + expect_identical(x, integer()) + + y <- vec_as_location(c(a = FALSE), n = 2) + expect_identical(y, named(integer())) + # Still unnamed + expect_identical(x, integer()) + + + x <- vec_as_location(NA, n = 2, missing = "remove") + expect_identical(x, integer()) + + y <- vec_as_location(c(a = FALSE), n = 2, missing = "remove") + expect_identical(y, named(integer())) + # Still unnamed + expect_identical(x, integer()) +}) + test_that("can customise subscript type errors", { expect_snapshot({ "With custom `arg`" From 8ced26d20c09c52ee841264f1d430af91fee08fc Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Mon, 12 Sep 2022 20:04:23 +0200 Subject: [PATCH 035/312] Mark equality methods as inline Closes #620 --- src/equal.c | 30 +++++++++++++++--------------- 1 file changed, 15 insertions(+), 15 deletions(-) diff --git a/src/equal.c b/src/equal.c index 0ddd0de6e..359bbb4af 100644 --- a/src/equal.c +++ b/src/equal.c @@ -11,14 +11,14 @@ SEXP vctrs_equal(SEXP x, SEXP y, SEXP na_equal) { return vec_equal(x, y, c_na_equal); } -static SEXP lgl_equal(SEXP x, SEXP y, R_len_t size, bool na_equal); -static SEXP int_equal(SEXP x, SEXP y, R_len_t size, bool na_equal); -static SEXP dbl_equal(SEXP x, SEXP y, R_len_t size, bool na_equal); -static SEXP cpl_equal(SEXP x, SEXP y, R_len_t size, bool na_equal); -static SEXP chr_equal(SEXP x, SEXP y, R_len_t size, bool na_equal); -static SEXP raw_equal(SEXP x, SEXP y, R_len_t size, bool na_equal); -static SEXP list_equal(SEXP x, SEXP y, R_len_t size, bool na_equal); -static SEXP df_equal(SEXP x, SEXP y, R_len_t size, bool na_equal); +static inline SEXP lgl_equal(SEXP x, SEXP y, R_len_t size, bool na_equal); +static inline SEXP int_equal(SEXP x, SEXP y, R_len_t size, bool na_equal); +static inline SEXP dbl_equal(SEXP x, SEXP y, R_len_t size, bool na_equal); +static inline SEXP cpl_equal(SEXP x, SEXP y, R_len_t size, bool na_equal); +static inline SEXP chr_equal(SEXP x, SEXP y, R_len_t size, bool na_equal); +static inline SEXP raw_equal(SEXP x, SEXP y, R_len_t size, bool na_equal); +static inline SEXP list_equal(SEXP x, SEXP y, R_len_t size, bool na_equal); +static inline SEXP df_equal(SEXP x, SEXP y, R_len_t size, bool na_equal); /* * Recycling and casting is done at the R level @@ -80,31 +80,31 @@ SEXP vec_equal(SEXP x, SEXP y, bool na_equal) { return out; -static +static inline SEXP lgl_equal(SEXP x, SEXP y, R_len_t size, bool na_equal) { EQUAL(int, LOGICAL_RO, lgl_equal_na_equal, lgl_equal_na_propagate); } -static +static inline SEXP int_equal(SEXP x, SEXP y, R_len_t size, bool na_equal) { EQUAL(int, INTEGER_RO, int_equal_na_equal, int_equal_na_propagate); } -static +static inline SEXP dbl_equal(SEXP x, SEXP y, R_len_t size, bool na_equal) { EQUAL(double, REAL_RO, dbl_equal_na_equal, dbl_equal_na_propagate); } -static +static inline SEXP cpl_equal(SEXP x, SEXP y, R_len_t size, bool na_equal) { EQUAL(Rcomplex, COMPLEX_RO, cpl_equal_na_equal, cpl_equal_na_propagate); } -static +static inline SEXP chr_equal(SEXP x, SEXP y, R_len_t size, bool na_equal) { EQUAL(SEXP, STRING_PTR_RO, chr_equal_na_equal, chr_equal_na_propagate); } -static +static inline SEXP raw_equal(SEXP x, SEXP y, R_len_t size, bool na_equal) { EQUAL(Rbyte, RAW_RO, raw_equal_na_equal, raw_equal_na_propagate); } -static +static inline SEXP list_equal(SEXP x, SEXP y, R_len_t size, bool na_equal) { EQUAL(SEXP, VECTOR_PTR_RO, list_equal_na_equal, list_equal_na_propagate); } From 14679e81993792163cc0ddc26f63f019182f86b2 Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Tue, 13 Sep 2022 10:30:01 +0200 Subject: [PATCH 036/312] Test that `names<-` is not called with partial data Closes #1108 --- tests/testthat/test-proxy-restore.R | 17 +++++++++++++++++ 1 file changed, 17 insertions(+) diff --git a/tests/testthat/test-proxy-restore.R b/tests/testthat/test-proxy-restore.R index 506dfc7e1..e8f6adb26 100644 --- a/tests/testthat/test-proxy-restore.R +++ b/tests/testthat/test-proxy-restore.R @@ -120,3 +120,20 @@ test_that("attributes are properly restored when they contain special attributes out <- vec_restore_default(list(), x) expect_identical(attributes(out), exp) }) + +test_that("names<- is not called with partial data (#1108)", { + x <- set_names(foobar(1:2), c("a", "b")) + + values <- list() + local_methods( + `names<-.vctrs_foobar` = function(x, value) { + if (!is_null(value)) { + values <<- c(values, list(value)) + } + NextMethod() + } + ) + + vec_c(x, x) + expect_equal(values, list(c("a", "b", "a", "b"))) +}) From 04889daaf8507a0f3c883642c468cd54723ccf09 Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Tue, 13 Sep 2022 15:14:06 +0200 Subject: [PATCH 037/312] Discuss difference between coercion and structural hierarchies (#1650) Closes #980 --- man/faq/developer/theory-coercion.Rmd | 7 ++++- man/theory-faq-coercion.Rd | 41 +++++++++++++++++---------- 2 files changed, 32 insertions(+), 16 deletions(-) diff --git a/man/faq/developer/theory-coercion.Rmd b/man/faq/developer/theory-coercion.Rmd index a8cc373e0..315eb4f66 100644 --- a/man/faq/developer/theory-coercion.Rmd +++ b/man/faq/developer/theory-coercion.Rmd @@ -101,10 +101,15 @@ In any case, permuting the input should not return a fundamentally different typ ### Coercion hierarchy -Coercible classes form a coercion (or subtyping) hierarchy. Here is a simplified diagram of the hierarchy for base types. In this diagram the directions of the arrows express which type is richer. They flow from the bottom (more constrained types) to the top (richer types). +The classes that you can coerce together form a coercion (or subtyping) hierarchy. Below is a schema of the hierarchy for the base types like integer and factor. In this diagram the directions of the arrows express which type is richer. They flow from the bottom (more constrained types) to the top (richer types). \\figure{coerce.png} +A coercion hierarchy is distinct from the structural hierarchy implied by memory types and classes. For instance, in a structural hierarchy, factors are built on top of integers. But in the coercion hierarchy they are more related to character vectors. Similarly, subclasses are not necessarily coercible with their superclasses because the coercion and structural hierarchies are separate. + + +### Implementing a coercion hierarchy + As a class implementor, you have two options. The simplest is to create an entirely separate hierarchy. The date and date-time classes are an example of an S3-based hierarchy that is completely separate. Alternatively, you can integrate your class in an existing hierarchy, typically by adding parent nodes on top of the hierarchy (your class is richer), by adding children node at the root of the hierarchy (your class is more constrained), or by inserting a node in the tree. These coercion hierarchies are _implicit_, in the sense that they are implied by the `vec_ptype2()` implementations. There is no structured way to create or modify a hierarchy, instead you need to implement the appropriate coercion methods for all the types in your hierarchy, and diligently return the richer type in each case. The `vec_ptype2()` implementations are not transitive nor inherited, so all pairwise methods between classes lying on a given path must be implemented manually. This is something we might make easier in the future. diff --git a/man/theory-faq-coercion.Rd b/man/theory-faq-coercion.Rd index 66974df70..20c1d35ad 100644 --- a/man/theory-faq-coercion.Rd +++ b/man/theory-faq-coercion.Rd @@ -74,9 +74,9 @@ steps, which require \code{vec_ptype2()} and \code{vec_cast()} implementations. Methods for \code{vec_ptype2()} are passed two \emph{prototypes}, i.e. two inputs emptied of their elements. They implement two behaviours: \itemize{ -\item If the types of their inputs are compatible, indicate which of them is -the richer type by returning it. If the types are of equal resolution, -return any of the two. +\item If the types of their inputs are compatible, indicate which of them +is the richer type by returning it. If the types are of equal +resolution, return any of the two. \item Throw an error with \code{stop_incompatible_type()} when it can be determined from the attributes that the types of the inputs are not compatible. @@ -155,13 +155,24 @@ different type or introduce an incompatible type error. \subsection{Coercion hierarchy}{ -Coercible classes form a coercion (or subtyping) hierarchy. Here is a -simplified diagram of the hierarchy for base types. In this diagram the -directions of the arrows express which type is richer. They flow from -the bottom (more constrained types) to the top (richer types). +The classes that you can coerce together form a coercion (or subtyping) +hierarchy. Below is a schema of the hierarchy for the base types like +integer and factor. In this diagram the directions of the arrows express +which type is richer. They flow from the bottom (more constrained types) +to the top (richer types). \figure{coerce.png} +A coercion hierarchy is distinct from the structural hierarchy implied +by memory types and classes. For instance, in a structural hierarchy, +factors are built on top of integers. But in the coercion hierarchy they +are more related to character vectors. Similarly, subclasses are not +necessarily coercible with their superclasses because the coercion and +structural hierarchies are separate. +} + +\subsection{Implementing a coercion hierarchy}{ + As a class implementor, you have two options. The simplest is to create an entirely separate hierarchy. The date and date-time classes are an example of an S3-based hierarchy that is completely separate. @@ -193,14 +204,14 @@ in more cases. \code{vec_cast()} has three possible behaviours: This must be decided in exactly the same way as for \code{vec_ptype2()}. Call \code{stop_incompatible_cast()} if you can determine from the attributes that the types are not compatible. -\item Detect incompatible values. Usually this is because the target type is -too restricted for the values supported by the input type. For +\item Detect incompatible values. Usually this is because the target type +is too restricted for the values supported by the input type. For example, a fractional number can’t be converted to an integer. The method should throw an error in that case. -\item Return the input vector converted to the target type if all values are -compatible. Whereas \code{vec_ptype2()} must return the same type when the -inputs are permuted, \code{vec_cast()} is \emph{directional}. It always returns -the type of the right-hand side, or dies trying. +\item Return the input vector converted to the target type if all values +are compatible. Whereas \code{vec_ptype2()} must return the same type +when the inputs are permuted, \code{vec_cast()} is \emph{directional}. It +always returns the type of the right-hand side, or dies trying. } } @@ -214,8 +225,8 @@ differences: \item There is no inheritance of ptype2 and cast methods. This is because the S3 class hierarchy is not necessarily the same as the coercion hierarchy. -\item \code{NextMethod()} does not work. Parent methods must be called explicitly -if necessary. +\item \code{NextMethod()} does not work. Parent methods must be called +explicitly if necessary. \item The default method is hard-coded. } } From 725948e0138d856e4483348aa23889c8ab50dfba Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Tue, 13 Sep 2022 15:38:59 +0200 Subject: [PATCH 038/312] Support `anyNA(recursive = TRUE)` for `vctrs_vctr` (#1653) Closes #1278 --- NEWS.md | 3 +++ R/type-vctr.R | 10 ++++------ tests/testthat/test-type-vctr.R | 10 ++++++++++ 3 files changed, 17 insertions(+), 6 deletions(-) diff --git a/NEWS.md b/NEWS.md index a70b8330e..8c2ccc420 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,5 +1,8 @@ # vctrs (development version) +* The `anyNA()` method for `vctrs_vctr` (and thus `vctrs_list_of`) now + supports the `recursive` argument (#1278). + * `vec_as_location()` and `num_as_location()` have gained a `missing = "remove"` option (#1595). diff --git a/R/type-vctr.R b/R/type-vctr.R index 7875153f1..3c6cd8803 100644 --- a/R/type-vctr.R +++ b/R/type-vctr.R @@ -460,12 +460,10 @@ na_remove <- function(x, type) { } #' @export -anyNA.vctrs_vctr <- if (getRversion() >= "3.2") { - function(x, recursive = FALSE) { - any(is.na(x)) - } -} else { - function(x) { +anyNA.vctrs_vctr <- function(x, recursive = FALSE) { + if (recursive && vec_is_list(x)) { + any(map_lgl(x, anyNA, recursive = recursive)) + } else { any(is.na(x)) } } diff --git a/tests/testthat/test-type-vctr.R b/tests/testthat/test-type-vctr.R index 56a7e05da..f47a8aa9e 100644 --- a/tests/testthat/test-type-vctr.R +++ b/tests/testthat/test-type-vctr.R @@ -711,3 +711,13 @@ test_that("Summary generics behave as expected for empty vctrs (#1357)", { expect_identical(max(new_vctr(logical()), na.rm = TRUE), new_vctr(NA)) expect_identical(range(new_vctr(logical()), na.rm = TRUE), new_vctr(c(NA, NA))) }) + +test_that("anyNA(recursive = TRUE) works with lists (#1278)", { + x <- list_of(1:4, c(2, NA, 5)) + expect_false(anyNA(x)) + expect_true(anyNA(x, recursive = TRUE)) + + x <- new_vctr(list(1:4, list(c(2, NA, 5)))) + expect_false(anyNA(x)) + expect_true(anyNA(x, recursive = TRUE)) +}) From 3d1f2255081ac4108d2f2d224843b743024a5c4e Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Tue, 13 Sep 2022 09:09:23 +0200 Subject: [PATCH 039/312] Don't pass restore size to non-dfs --- src/slice.c | 7 +++---- tests/testthat/test-proxy-restore.R | 8 -------- 2 files changed, 3 insertions(+), 12 deletions(-) diff --git a/src/slice.c b/src/slice.c index 07c2eb57c..997984b3b 100644 --- a/src/slice.c +++ b/src/slice.c @@ -282,8 +282,6 @@ r_obj* slice_rownames(r_obj* names, r_obj* subscript) { r_obj* vec_slice_unsafe(r_obj* x, r_obj* subscript) { int nprot = 0; - r_obj* restore_size = KEEP_N(r_int(vec_subscript_size(subscript)), &nprot); - struct vctrs_proxy_info info = vec_proxy_info(x); KEEP_N(info.shelter, &nprot); @@ -310,7 +308,7 @@ r_obj* vec_slice_unsafe(r_obj* x, r_obj* subscript) { // Take over attribute restoration only if there is no `[` method if (!vec_is_restored(out, x)) { - out = vec_restore(out, x, restore_size, vec_owned(out)); + out = vec_restore(out, x, r_null, vec_owned(out)); } FREE(nprot); @@ -349,7 +347,7 @@ r_obj* vec_slice_unsafe(r_obj* x, r_obj* subscript) { r_attrib_poke_names(out, names); } - out = vec_restore(out, x, restore_size, vec_owned(out)); + out = vec_restore(out, x, r_null, vec_owned(out)); FREE(nprot); return out; @@ -357,6 +355,7 @@ r_obj* vec_slice_unsafe(r_obj* x, r_obj* subscript) { case VCTRS_TYPE_dataframe: { r_obj* out = KEEP_N(df_slice(data, subscript), &nprot); + r_obj* restore_size = KEEP_N(r_int(vec_subscript_size(subscript)), &nprot); out = vec_restore(out, x, restore_size, vec_owned(out)); FREE(nprot); return out; diff --git a/tests/testthat/test-proxy-restore.R b/tests/testthat/test-proxy-restore.R index e8f6adb26..bf3c1c76b 100644 --- a/tests/testthat/test-proxy-restore.R +++ b/tests/testthat/test-proxy-restore.R @@ -44,14 +44,6 @@ test_that("can use vctrs primitives from vec_restore() without inflooping", { expect_identical(vec_slice(foobar, 2), "woot") }) -test_that("vec_restore() passes `n` argument to methods", { - local_methods( - vec_proxy.vctrs_foobar = identity, - vec_restore.vctrs_foobar = function(x, to, ..., n) n - ) - expect_identical(vec_slice(foobar(1:3), 2), 1L) -}) - test_that("dimensions are preserved by default restore method", { x <- foobar(1:4) dim(x) <- c(2, 2) From 318889486d6bb63e7cc93c2788e36184af2d1d21 Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Tue, 13 Sep 2022 09:12:57 +0200 Subject: [PATCH 040/312] Initialise sliced data frames before restoration To avoid having to pass a restoration size --- src/slice.c | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/src/slice.c b/src/slice.c index 997984b3b..bb34e204a 100644 --- a/src/slice.c +++ b/src/slice.c @@ -195,6 +195,8 @@ r_obj* df_slice(r_obj* x, r_obj* subscript) { r_list_poke(out, i, sliced); } + init_data_frame(out, vec_subscript_size(subscript)); + r_obj* row_nms = KEEP(df_rownames(x)); if (r_typeof(row_nms) == R_TYPE_character) { row_nms = slice_rownames(row_nms, subscript); @@ -355,8 +357,7 @@ r_obj* vec_slice_unsafe(r_obj* x, r_obj* subscript) { case VCTRS_TYPE_dataframe: { r_obj* out = KEEP_N(df_slice(data, subscript), &nprot); - r_obj* restore_size = KEEP_N(r_int(vec_subscript_size(subscript)), &nprot); - out = vec_restore(out, x, restore_size, vec_owned(out)); + out = vec_restore(out, x, r_null, vec_owned(out)); FREE(nprot); return out; } From 5ba7c24b2809307bf8b154547a0f754a9ed8b567 Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Tue, 13 Sep 2022 09:26:09 +0200 Subject: [PATCH 041/312] Remove `n` argument of `vec_restore()` Closes #650 --- NEWS.md | 7 ++++++ R/proxy.R | 19 +++++----------- R/type-data-frame.R | 4 ++-- man/vec_proxy.Rd | 10 +-------- src/bind.c | 5 ++--- src/c-unchop.c | 6 ++--- src/c.c | 2 +- src/decl/proxy-restore-decl.h | 2 +- src/init.c | 12 +++++----- src/proxy-restore.c | 35 ++++++++++++++--------------- src/proxy-restore.h | 6 ++--- src/slice-assign.c | 6 ++--- src/slice-chop.c | 28 +++++------------------ src/slice.c | 6 ++--- src/utils.c | 4 ++-- tests/testthat/test-proxy-restore.R | 4 ++-- 16 files changed, 64 insertions(+), 92 deletions(-) diff --git a/NEWS.md b/NEWS.md index 8c2ccc420..1d3dec2e5 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,5 +1,12 @@ # vctrs (development version) +* The experimental `n` argument of `vec_restore()` has been + removed. It was only used to inform on the size of data frames in + case a bare list is restored. It is now expected that bare lists be + initialised to data frame so that the size is carried through row + attributes. This makes the generic simpler and fixes some + performance issues (#650). + * The `anyNA()` method for `vctrs_vctr` (and thus `vctrs_list_of`) now supports the `recursive` argument (#1278). diff --git a/R/proxy.R b/R/proxy.R index 742b97b43..bc58c6492 100644 --- a/R/proxy.R +++ b/R/proxy.R @@ -146,28 +146,21 @@ vec_proxy.default <- function(x, ...) { #' @rdname vec_proxy #' @param to The original vector to restore to. -#' @param n `r lifecycle::badge("experimental")` -#' The total size to restore to. This is currently passed by -#' `vec_slice()` to solve edge cases arising in data frame -#' restoration. In most cases you don't need this information and -#' can safely ignore that argument. This parameter should be -#' considered internal and experimental, it might change in the -#' future. #' @export -vec_restore <- function(x, to, ..., n = NULL) { +vec_restore <- function(x, to, ...) { check_dots_empty0(...) - return(.Call(ffi_restore, x, to, n)) + return(.Call(ffi_vec_restore, x, to)) UseMethod("vec_restore", to) } -vec_restore_dispatch <- function(x, to, ..., n = NULL) { +vec_restore_dispatch <- function(x, to, ...) { UseMethod("vec_restore", to) } #' @export -vec_restore.default <- function(x, to, ..., n = NULL) { - .Call(ffi_restore_default, x, to) +vec_restore.default <- function(x, to, ...) { + .Call(ffi_vec_restore_default, x, to) } vec_restore_default <- function(x, to, ...) { - .Call(ffi_restore_default, x, to) + .Call(ffi_vec_restore_default, x, to) } #' Extract underlying data diff --git a/R/type-data-frame.R b/R/type-data-frame.R index 7bd6c7ca0..8a99de1ed 100644 --- a/R/type-data-frame.R +++ b/R/type-data-frame.R @@ -484,8 +484,8 @@ vec_cast.data.frame.data.frame <- function(x, to, ..., x_arg = "", to_arg = "") } #' @export -vec_restore.data.frame <- function(x, to, ..., n = NULL) { - .Call(ffi_bare_df_restore, x, to, n) +vec_restore.data.frame <- function(x, to, ...) { + .Call(ffi_vec_bare_df_restore, x, to) } # Helpers ----------------------------------------------------------------- diff --git a/man/vec_proxy.Rd b/man/vec_proxy.Rd index d0da8043c..15fb85c04 100644 --- a/man/vec_proxy.Rd +++ b/man/vec_proxy.Rd @@ -7,7 +7,7 @@ \usage{ vec_proxy(x, ...) -vec_restore(x, to, ..., n = NULL) +vec_restore(x, to, ...) } \arguments{ \item{x}{A vector.} @@ -15,14 +15,6 @@ vec_restore(x, to, ..., n = NULL) \item{...}{These dots are for future extensions and must be empty.} \item{to}{The original vector to restore to.} - -\item{n}{\ifelse{html}{\href{https://lifecycle.r-lib.org/articles/stages.html#experimental}{\figure{lifecycle-experimental.svg}{options: alt='[Experimental]'}}}{\strong{[Experimental]}} -The total size to restore to. This is currently passed by -\code{vec_slice()} to solve edge cases arising in data frame -restoration. In most cases you don't need this information and -can safely ignore that argument. This parameter should be -considered internal and experimental, it might change in the -future.} } \description{ \ifelse{html}{\href{https://lifecycle.r-lib.org/articles/stages.html#experimental}{\figure{lifecycle-experimental.svg}{options: alt='[Experimental]'}}}{\strong{[Experimental]}} diff --git a/src/bind.c b/src/bind.c index 6d4edde3d..2cff4ecf7 100644 --- a/src/bind.c +++ b/src/bind.c @@ -261,8 +261,7 @@ r_obj* vec_rbind(r_obj* xs, } } - r_obj* r_n_rows = KEEP_N(r_int(n_rows), &n_prot); - out = vec_restore(out, ptype, r_n_rows, VCTRS_OWNED_true); + out = vec_restore(out, ptype, VCTRS_OWNED_true); FREE(n_prot); return out; @@ -515,7 +514,7 @@ r_obj* vec_cbind(r_obj* xs, r_attrib_poke(out, r_syms.row_names, rownames); } - out = vec_restore(out, type, r_null, VCTRS_OWNED_true); + out = vec_restore(out, type, VCTRS_OWNED_true); FREE(9); return out; diff --git a/src/c-unchop.c b/src/c-unchop.c index 49a8de381..0f2da4e53 100644 --- a/src/c-unchop.c +++ b/src/c-unchop.c @@ -136,9 +136,7 @@ r_obj* list_unchop(r_obj* xs, KEEP_AT(proxy, proxy_pi); } - r_obj* out_size_sexp = KEEP(r_int(out_size)); - - r_obj* out = KEEP(vec_restore(proxy, ptype, out_size_sexp, VCTRS_OWNED_true)); + r_obj* out = KEEP(vec_restore(proxy, ptype, VCTRS_OWNED_true)); if (out_names != r_null) { out_names = KEEP(vec_as_names(out_names, name_repair)); @@ -151,7 +149,7 @@ r_obj* list_unchop(r_obj* xs, out = vec_set_names(out, r_null); } - FREE(8); + FREE(7); return out; } diff --git a/src/c.c b/src/c.c index 4ec6ee49c..9647db8e1 100644 --- a/src/c.c +++ b/src/c.c @@ -143,7 +143,7 @@ r_obj* vec_c_opts(r_obj* xs, FREE(1); } - out = KEEP(vec_restore(out, ptype, r_null, VCTRS_OWNED_true)); + out = KEEP(vec_restore(out, ptype, VCTRS_OWNED_true)); if (out_names != r_null) { out_names = KEEP(vec_as_names(out_names, name_repair)); diff --git a/src/decl/proxy-restore-decl.h b/src/decl/proxy-restore-decl.h index 2c80d31c6..577ba0d95 100644 --- a/src/decl/proxy-restore-decl.h +++ b/src/decl/proxy-restore-decl.h @@ -2,4 +2,4 @@ static r_obj* syms_vec_restore_dispatch; static r_obj* fns_vec_restore_dispatch; static -r_obj* vec_restore_dispatch(r_obj* x, r_obj* to, r_obj* n); +r_obj* vec_restore_dispatch(r_obj* x, r_obj* to); diff --git a/src/init.c b/src/init.c index d144e6b56..c71a383e5 100644 --- a/src/init.c +++ b/src/init.c @@ -53,8 +53,8 @@ extern r_obj* ffi_list_unchop(r_obj*, r_obj*, r_obj*, r_obj*, r_obj*); extern SEXP vctrs_chop_seq(SEXP, SEXP, SEXP, SEXP); extern r_obj* ffi_slice_seq(r_obj*, r_obj*, r_obj*, r_obj*); extern r_obj* ffi_slice_rep(r_obj*, r_obj*, r_obj*); -extern r_obj* ffi_restore(r_obj*, r_obj*, r_obj*); -extern r_obj* ffi_restore_default(r_obj*, r_obj*); +extern r_obj* ffi_vec_restore(r_obj*, r_obj*); +extern r_obj* ffi_vec_restore_default(r_obj*, r_obj*); extern SEXP vec_proxy(SEXP); extern SEXP vec_proxy_equal(SEXP); extern SEXP vec_proxy_compare(SEXP); @@ -75,7 +75,7 @@ extern r_obj* ffi_df_ptype2_opts(r_obj*, r_obj*, r_obj*, r_obj*); extern r_obj* ffi_type_info(r_obj*); extern SEXP ffi_proxy_info(SEXP); extern r_obj* ffi_class_type(r_obj*); -extern r_obj* ffi_bare_df_restore(r_obj*, r_obj*, r_obj*); +extern r_obj* ffi_vec_bare_df_restore(r_obj*, r_obj*); extern r_obj* ffi_recycle(r_obj*, r_obj*, r_obj*); extern r_obj* ffi_assign(r_obj*, r_obj*, r_obj*, r_obj*); extern r_obj* ffi_assign_seq(r_obj*, r_obj*, r_obj*, r_obj*, r_obj*); @@ -222,8 +222,8 @@ static const R_CallMethodDef CallEntries[] = { {"vctrs_chop_seq", (DL_FUNC) &vctrs_chop_seq, 4}, {"ffi_slice_seq", (DL_FUNC) &ffi_slice_seq, 4}, {"ffi_slice_rep", (DL_FUNC) &ffi_slice_rep, 3}, - {"ffi_restore", (DL_FUNC) &ffi_restore, 3}, - {"ffi_restore_default", (DL_FUNC) &ffi_restore_default, 2}, + {"ffi_vec_restore", (DL_FUNC) &ffi_vec_restore, 2}, + {"ffi_vec_restore_default", (DL_FUNC) &ffi_vec_restore_default, 2}, {"vctrs_proxy", (DL_FUNC) &vec_proxy, 1}, {"vctrs_proxy_equal", (DL_FUNC) &vec_proxy_equal, 1}, {"vctrs_proxy_compare", (DL_FUNC) &vec_proxy_compare, 1}, @@ -244,7 +244,7 @@ static const R_CallMethodDef CallEntries[] = { {"ffi_type_info", (DL_FUNC) &ffi_type_info, 1}, {"ffi_proxy_info", (DL_FUNC) &ffi_proxy_info, 1}, {"ffi_class_type", (DL_FUNC) &ffi_class_type, 1}, - {"ffi_bare_df_restore", (DL_FUNC) &ffi_bare_df_restore, 3}, + {"ffi_vec_bare_df_restore", (DL_FUNC) &ffi_vec_bare_df_restore, 2}, {"ffi_recycle", (DL_FUNC) &ffi_recycle, 3}, {"ffi_assign", (DL_FUNC) &ffi_assign, 4}, {"ffi_assign_seq", (DL_FUNC) &ffi_assign_seq, 5}, diff --git a/src/proxy-restore.c b/src/proxy-restore.c index 1f9cdbf1e..2f19717bd 100644 --- a/src/proxy-restore.c +++ b/src/proxy-restore.c @@ -10,7 +10,7 @@ // causing duplication to occur. Passing `owned` through here allows us to // call `vec_clone_referenced()`, which won't attempt to clone if we know we // own the object. See #1151. -r_obj* vec_restore(r_obj* x, r_obj* to, r_obj* n, const enum vctrs_owned owned) { +r_obj* vec_restore(r_obj* x, r_obj* to, const enum vctrs_owned owned) { switch (class_type(to)) { case VCTRS_CLASS_bare_factor: case VCTRS_CLASS_bare_ordered: @@ -19,23 +19,22 @@ r_obj* vec_restore(r_obj* x, r_obj* to, r_obj* n, const enum vctrs_owned owned) case VCTRS_CLASS_bare_posixct: return vec_posixct_restore(x, to, owned); case VCTRS_CLASS_bare_posixlt: return vec_posixlt_restore(x, to, owned); case VCTRS_CLASS_bare_data_frame: - case VCTRS_CLASS_bare_tibble: return vec_bare_df_restore(x, to, n, owned); - case VCTRS_CLASS_data_frame: return vec_df_restore(x, to, n, owned); - default: return vec_restore_dispatch(x, to, n); + case VCTRS_CLASS_bare_tibble: return vec_bare_df_restore(x, to, owned); + case VCTRS_CLASS_data_frame: return vec_df_restore(x, to, owned); + default: return vec_restore_dispatch(x, to); } } -r_obj* ffi_restore(r_obj* x, r_obj* to, r_obj* n) { - return vec_restore(x, to, n, vec_owned(x)); +r_obj* ffi_vec_restore(r_obj* x, r_obj* to) { + return vec_restore(x, to, vec_owned(x)); } static -r_obj* vec_restore_dispatch(r_obj* x, r_obj* to, r_obj* n) { - return vctrs_dispatch3(syms_vec_restore_dispatch, fns_vec_restore_dispatch, +r_obj* vec_restore_dispatch(r_obj* x, r_obj* to) { + return vctrs_dispatch2(syms_vec_restore_dispatch, fns_vec_restore_dispatch, syms_x, x, - syms_to, to, - syms_n, n); + syms_to, to); } @@ -137,7 +136,7 @@ r_obj* vec_restore_default(r_obj* x, r_obj* to, const enum vctrs_owned owned) { return x; } -r_obj* ffi_restore_default(r_obj* x, r_obj* to) { +r_obj* ffi_vec_restore_default(r_obj* x, r_obj* to) { return vec_restore_default(x, to, vec_owned(x)); } @@ -145,14 +144,14 @@ r_obj* ffi_restore_default(r_obj* x, r_obj* to) { // Restore methods are passed the original atomic type back, so we // first restore data frames as such before calling the restore // method, if any -r_obj* vec_df_restore(r_obj* x, r_obj* to, r_obj* n, const enum vctrs_owned owned) { - r_obj* out = KEEP(vec_bare_df_restore(x, to, n, owned)); - out = vec_restore_dispatch(out, to, n); +r_obj* vec_df_restore(r_obj* x, r_obj* to, const enum vctrs_owned owned) { + r_obj* out = KEEP(vec_bare_df_restore(x, to, owned)); + out = vec_restore_dispatch(out, to); FREE(1); return out; } -r_obj* vec_bare_df_restore(r_obj* x, r_obj* to, r_obj* n, const enum vctrs_owned owned) { +r_obj* vec_bare_df_restore(r_obj* x, r_obj* to, const enum vctrs_owned owned) { if (r_typeof(x) != R_TYPE_list) { r_stop_internal("Attempt to restore data frame from a %s.", r_type_as_c_string(r_typeof(x))); @@ -167,7 +166,7 @@ r_obj* vec_bare_df_restore(r_obj* x, r_obj* to, r_obj* n, const enum vctrs_owned } r_obj* rownames = KEEP(df_rownames(x)); - r_ssize size = (n == r_null) ? df_raw_size(x) : r_int_get(n, 0); + r_ssize size = df_raw_size(x); if (rownames == r_null) { init_compact_rownames(x, size); @@ -181,8 +180,8 @@ r_obj* vec_bare_df_restore(r_obj* x, r_obj* to, r_obj* n, const enum vctrs_owned return x; } -r_obj* ffi_bare_df_restore(r_obj* x, r_obj* to, r_obj* n) { - return vec_bare_df_restore(x, to, n, vec_owned(x)); +r_obj* ffi_vec_bare_df_restore(r_obj* x, r_obj* to) { + return vec_bare_df_restore(x, to, vec_owned(x)); } diff --git a/src/proxy-restore.h b/src/proxy-restore.h index 263e1624c..e67ab4fc4 100644 --- a/src/proxy-restore.h +++ b/src/proxy-restore.h @@ -4,11 +4,11 @@ #include "vctrs-core.h" -r_obj* vec_restore(r_obj* x, r_obj* to, r_obj* n, const enum vctrs_owned owned); +r_obj* vec_restore(r_obj* x, r_obj* to, const enum vctrs_owned owned); r_obj* vec_restore_default(r_obj* x, r_obj* to, const enum vctrs_owned owned); -r_obj* vec_bare_df_restore(r_obj* x, r_obj* to, r_obj* n, const enum vctrs_owned owned); -r_obj* vec_df_restore(r_obj* x, r_obj* to, r_obj* n, const enum vctrs_owned owned); +r_obj* vec_bare_df_restore(r_obj* x, r_obj* to, const enum vctrs_owned owned); +r_obj* vec_df_restore(r_obj* x, r_obj* to, const enum vctrs_owned owned); #endif diff --git a/src/slice-assign.c b/src/slice-assign.c index 9f4818a09..a0e9019f2 100644 --- a/src/slice-assign.c +++ b/src/slice-assign.c @@ -35,7 +35,7 @@ r_obj* vec_assign_opts(r_obj* x, const enum vctrs_owned owned = vec_owned(proxy); proxy = KEEP(vec_proxy_assign_opts(proxy, index, value, owned, &opts)); - r_obj* out = vec_restore(proxy, x, r_null, owned); + r_obj* out = vec_restore(proxy, x, owned); FREE(6); return out; @@ -352,7 +352,7 @@ r_obj* df_assign(r_obj* x, r_obj* proxy_elt = KEEP(vec_proxy(out_elt)); r_obj* assigned = KEEP(vec_proxy_assign_opts(proxy_elt, index, value_elt, owned, opts)); - assigned = vec_restore(assigned, out_elt, r_null, owned); + assigned = vec_restore(assigned, out_elt, owned); r_list_poke(out, i, assigned); FREE(2); @@ -421,7 +421,7 @@ r_obj* ffi_assign_seq(r_obj* x, const enum vctrs_owned owned = vec_owned(proxy); proxy = KEEP(vec_proxy_check_assign(proxy, index, value, vec_args.x, vec_args.value, call)); - r_obj* out = vec_restore(proxy, x, r_null, owned); + r_obj* out = vec_restore(proxy, x, owned); FREE(5); return out; diff --git a/src/slice-chop.c b/src/slice-chop.c index 1c4c97ae8..19fe51414 100644 --- a/src/slice-chop.c +++ b/src/slice-chop.c @@ -3,9 +3,6 @@ /* * @member proxy_info The result of `vec_proxy_info(x)`. - * @member restore_size The restore size used in each call to `vec_restore()`. - * Will always be 1 for `indices = NULL`. - * @member p_restore_size A pointer to update the restore size. * @member index The current index value. If `indices` are provided, this is * the i-th element of indices. For the default of `indices = NULL`, this * starts at 0 and is incremented by 1 repeatedly through `p_index`. @@ -18,8 +15,6 @@ */ struct vctrs_chop_info { struct vctrs_proxy_info proxy_info; - SEXP restore_size; - int* p_restore_size; SEXP index; int* p_index; bool has_indices; @@ -29,10 +24,9 @@ struct vctrs_chop_info { #define PROTECT_CHOP_INFO(info, n) do { \ KEEP((info)->proxy_info.shelter); \ - KEEP((info)->restore_size); \ KEEP((info)->index); \ KEEP((info)->out); \ - *n += 4; \ + *n += 3; \ } while (0) \ static @@ -42,9 +36,6 @@ struct vctrs_chop_info init_chop_info(r_obj* x, r_obj* indices) { info.proxy_info = vec_proxy_info(x); KEEP(info.proxy_info.shelter); - info.restore_size = KEEP(r_int(1)); - info.p_restore_size = INTEGER(info.restore_size); - info.index = KEEP(r_int(0)); info.p_index = r_int_begin(info.index); @@ -58,7 +49,7 @@ struct vctrs_chop_info init_chop_info(r_obj* x, r_obj* indices) { info.out = r_alloc_list(info.out_size); - FREE(3); + FREE(2); return info; } @@ -176,7 +167,6 @@ static SEXP chop(SEXP x, SEXP indices, struct vctrs_chop_info info) { for (R_len_t i = 0; i < info.out_size; ++i) { if (info.has_indices) { info.index = VECTOR_ELT(indices, i); - *info.p_restore_size = vec_subscript_size(info.index); } else { ++(*info.p_index); } @@ -199,7 +189,7 @@ static SEXP chop(SEXP x, SEXP indices, struct vctrs_chop_info info) { UNPROTECT(1); } - elt = vec_restore(elt, x, info.restore_size, vec_owned(elt)); + elt = vec_restore(elt, x, vec_owned(elt)); SET_VECTOR_ELT(info.out, i, elt); UNPROTECT(1); @@ -255,12 +245,8 @@ static SEXP chop_df(SEXP x, SEXP indices, struct vctrs_chop_info info) { // Restore each data frame for (int i = 0; i < info.out_size; ++i) { - if (info.has_indices) { - *info.p_restore_size = vec_subscript_size(VECTOR_ELT(indices, i)); - } - SEXP elt = VECTOR_ELT(info.out, i); - elt = vec_restore(elt, x, info.restore_size, vec_owned(elt)); + elt = vec_restore(elt, x, vec_owned(elt)); SET_VECTOR_ELT(info.out, i, elt); } @@ -280,7 +266,6 @@ static SEXP chop_shaped(SEXP x, SEXP indices, struct vctrs_chop_info info) { for (R_len_t i = 0; i < info.out_size; ++i) { if (info.has_indices) { info.index = VECTOR_ELT(indices, i); - *info.p_restore_size = vec_subscript_size(info.index); } else { ++(*info.p_index); } @@ -300,7 +285,7 @@ static SEXP chop_shaped(SEXP x, SEXP indices, struct vctrs_chop_info info) { } } - elt = vec_restore(elt, x, info.restore_size, vec_owned(elt)); + elt = vec_restore(elt, x, vec_owned(elt)); SET_VECTOR_ELT(info.out, i, elt); UNPROTECT(1); @@ -335,7 +320,6 @@ static SEXP chop_fallback(SEXP x, SEXP indices, struct vctrs_chop_info info) { for (R_len_t i = 0; i < info.out_size; ++i) { if (info.has_indices) { info.index = VECTOR_ELT(indices, i); - *info.p_restore_size = vec_size(info.index); // Update `i` binding with the new index value Rf_defineVar(syms_i, info.index, env); @@ -346,7 +330,7 @@ static SEXP chop_fallback(SEXP x, SEXP indices, struct vctrs_chop_info info) { SEXP elt = PROTECT(Rf_eval(call, env)); if (!vec_is_restored(elt, x)) { - elt = vec_restore(elt, x, info.restore_size, vec_owned(elt)); + elt = vec_restore(elt, x, vec_owned(elt)); } SET_VECTOR_ELT(info.out, i, elt); diff --git a/src/slice.c b/src/slice.c index bb34e204a..26a67d838 100644 --- a/src/slice.c +++ b/src/slice.c @@ -310,7 +310,7 @@ r_obj* vec_slice_unsafe(r_obj* x, r_obj* subscript) { // Take over attribute restoration only if there is no `[` method if (!vec_is_restored(out, x)) { - out = vec_restore(out, x, r_null, vec_owned(out)); + out = vec_restore(out, x, vec_owned(out)); } FREE(nprot); @@ -349,7 +349,7 @@ r_obj* vec_slice_unsafe(r_obj* x, r_obj* subscript) { r_attrib_poke_names(out, names); } - out = vec_restore(out, x, r_null, vec_owned(out)); + out = vec_restore(out, x, vec_owned(out)); FREE(nprot); return out; @@ -357,7 +357,7 @@ r_obj* vec_slice_unsafe(r_obj* x, r_obj* subscript) { case VCTRS_TYPE_dataframe: { r_obj* out = KEEP_N(df_slice(data, subscript), &nprot); - out = vec_restore(out, x, r_null, vec_owned(out)); + out = vec_restore(out, x, vec_owned(out)); FREE(nprot); return out; } diff --git a/src/utils.c b/src/utils.c index 81bf6b84a..98c25554b 100644 --- a/src/utils.c +++ b/src/utils.c @@ -357,7 +357,7 @@ SEXP bare_df_map(SEXP df, SEXP (*fn)(SEXP)) { SEXP out = PROTECT(map(df, fn)); // Total ownership because `map()` generates a fresh list - out = vec_bare_df_restore(out, df, vctrs_shared_zero_int, VCTRS_OWNED_true); + out = vec_bare_df_restore(out, df, VCTRS_OWNED_true); UNPROTECT(1); return out; @@ -368,7 +368,7 @@ SEXP df_map(SEXP df, SEXP (*fn)(SEXP)) { SEXP out = PROTECT(map(df, fn)); // Total ownership because `map()` generates a fresh list - out = vec_df_restore(out, df, vctrs_shared_zero_int, VCTRS_OWNED_true); + out = vec_df_restore(out, df, VCTRS_OWNED_true); UNPROTECT(1); return out; diff --git a/tests/testthat/test-proxy-restore.R b/tests/testthat/test-proxy-restore.R index bf3c1c76b..aa71054f1 100644 --- a/tests/testthat/test-proxy-restore.R +++ b/tests/testthat/test-proxy-restore.R @@ -71,11 +71,11 @@ test_that("names attribute isn't set when restoring 1D arrays using 2D+ objects" test_that("arguments are not inlined in the dispatch call (#300)", { local_methods( - vec_restore.vctrs_foobar = function(x, to, ..., n) sys.call(), + vec_restore.vctrs_foobar = function(x, to, ...) sys.call(), vec_proxy.vctrs_foobar = unclass ) call <- vec_restore(foobar(list(1)), foobar(list(1))) - expect_equal(call, quote(vec_restore.vctrs_foobar(x = x, to = to, n = n))) + expect_equal(call, quote(vec_restore.vctrs_foobar(x = x, to = to))) }) test_that("restoring to non-bare data frames calls `vec_bare_df_restore()` before dispatching", { From eb19e94730541ae6472f711c5b7ff25331e84d33 Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Tue, 13 Sep 2022 13:33:50 +0200 Subject: [PATCH 042/312] Clean up style in polynomial methods --- vignettes/s3-vector.Rmd | 11 +++++++---- 1 file changed, 7 insertions(+), 4 deletions(-) diff --git a/vignettes/s3-vector.Rmd b/vignettes/s3-vector.Rmd index 5513dee59..5113b067c 100644 --- a/vignettes/s3-vector.Rmd +++ b/vignettes/s3-vector.Rmd @@ -717,7 +717,9 @@ format.vctrs_poly <- function(x, ...) { format_one <- function(x) { if (length(x) == 0) { return("") - } else if (length(x) == 1) { + } + + if (length(x) == 1) { format(x) } else { suffix <- c(paste0("\u22C5x^", seq(length(x) - 1, 1)), "") @@ -726,13 +728,14 @@ format.vctrs_poly <- function(x, ...) { paste0(out, collapse = " + ") } } + vapply(x, format_one, character(1)) } obj_print_data.vctrs_poly <- function(x, ...) { - if (length(x) == 0) - return() - print(format(x), quote = FALSE) + if (length(x) != 0) { + print(format(x), quote = FALSE) + } } p <- poly(1, c(1, 0, 0, 0, 2), c(1, 0, 1)) From 3c8a6e2d18cee92ec67c526349c70e6d8248e4fc Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Tue, 13 Sep 2022 13:36:11 +0200 Subject: [PATCH 043/312] Rename `vctrs_poly` to `vctrs_poly_list` --- vignettes/s3-vector.Rmd | 14 +++++++------- 1 file changed, 7 insertions(+), 7 deletions(-) diff --git a/vignettes/s3-vector.Rmd b/vignettes/s3-vector.Rmd index 5113b067c..f5f90cd48 100644 --- a/vignettes/s3-vector.Rmd +++ b/vignettes/s3-vector.Rmd @@ -701,7 +701,7 @@ A related problem occurs if we build our vector on top of a list. The following ```{r} new_poly <- function(x) { - new_list_of(x, ptype = integer(), class = "vctrs_poly") + new_list_of(x, ptype = integer(), class = "vctrs_poly_list") } poly <- function(...) { @@ -710,10 +710,10 @@ poly <- function(...) { new_poly(x) } -vec_ptype_full.vctrs_poly <- function(x, ...) "polynomial" -vec_ptype_abbr.vctrs_poly <- function(x, ...) "poly" +vec_ptype_full.vctrs_poly_list <- function(x, ...) "polynomial" +vec_ptype_abbr.vctrs_poly_list <- function(x, ...) "poly" -format.vctrs_poly <- function(x, ...) { +format.vctrs_poly_list <- function(x, ...) { format_one <- function(x) { if (length(x) == 0) { return("") @@ -732,7 +732,7 @@ format.vctrs_poly <- function(x, ...) { vapply(x, format_one, character(1)) } -obj_print_data.vctrs_poly <- function(x, ...) { +obj_print_data.vctrs_poly_list <- function(x, ...) { if (length(x) != 0) { print(format(x), quote = FALSE) } @@ -765,7 +765,7 @@ p < p[2] To enable comparison, we implement a `vec_proxy_compare()` method: ```{r} -vec_proxy_compare.vctrs_poly <- function(x, ...) { +vec_proxy_compare.vctrs_poly_list <- function(x, ...) { x_raw <- vec_data(x) # First figure out the maximum length n <- max(vapply(x_raw, length, integer(1))) @@ -790,7 +790,7 @@ sort(p[c(1:3, 1:2)]) To ensure consistency between ordering and comparison, we forward `vec_proxy_order()` to `vec_proxy_compare()`: ```{r} -vec_proxy_order.vctrs_poly <- function(x, ...) { +vec_proxy_order.vctrs_poly_list <- function(x, ...) { vec_proxy_compare(x, ...) } From 9e848296777c37a31d2f3c4df8630b4d42b6db9d Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Tue, 13 Sep 2022 13:43:27 +0200 Subject: [PATCH 044/312] Simplify `poly()` constructor --- vignettes/s3-vector.Rmd | 10 ++++------ 1 file changed, 4 insertions(+), 6 deletions(-) diff --git a/vignettes/s3-vector.Rmd b/vignettes/s3-vector.Rmd index f5f90cd48..3208a1dc1 100644 --- a/vignettes/s3-vector.Rmd +++ b/vignettes/s3-vector.Rmd @@ -700,15 +700,13 @@ sort(x) A related problem occurs if we build our vector on top of a list. The following code defines a polynomial class that represents polynomials (like `1 + 3x - 2x^2`) using a list of integer vectors (like `c(1, 3, -2)`). Note the use of `new_list_of()` in the constructor. ```{r} -new_poly <- function(x) { - new_list_of(x, ptype = integer(), class = "vctrs_poly_list") -} - poly <- function(...) { - x <- list(...) - x <- lapply(x, vec_cast, integer()) + x <- vec_cast_common(..., .to = integer()) new_poly(x) } +new_poly <- function(x) { + new_list_of(x, ptype = integer(), class = "vctrs_poly_list") +} vec_ptype_full.vctrs_poly_list <- function(x, ...) "polynomial" vec_ptype_abbr.vctrs_poly_list <- function(x, ...) "poly" From 29a6e0e0b38d6d36822875a1c9b26a8c3ab79cee Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Tue, 13 Sep 2022 13:48:48 +0200 Subject: [PATCH 045/312] Show how to make `poly()` return an atomic vector Closes #1030 --- NEWS.md | 3 +++ vignettes/s3-vector.Rmd | 56 ++++++++++++++++++++++++++++++++++++++--- 2 files changed, 55 insertions(+), 4 deletions(-) diff --git a/NEWS.md b/NEWS.md index 1d3dec2e5..4046b2e2d 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,5 +1,8 @@ # vctrs (development version) +* S3 vignette was extended to show how to make the polynomial class + atomic instead of a list (#1030). + * The experimental `n` argument of `vec_restore()` has been removed. It was only used to inform on the size of data frames in case a bare list is restored. It is now expected that bare lists be diff --git a/vignettes/s3-vector.Rmd b/vignettes/s3-vector.Rmd index 3208a1dc1..ac6ee78f7 100644 --- a/vignettes/s3-vector.Rmd +++ b/vignettes/s3-vector.Rmd @@ -748,13 +748,59 @@ p[2] p[[2]] ``` +The class implements the list interface: + +```{r} +vec_is_list(p) +``` + +This is fine for the internal implementation of this class but it would be more appropriate if it behaved like an atomic vector rather than a list. + + +#### Make an atomic polynomial vector + +To make it an atomic vector, we'll wrap the internal `list_of()` class within a record vector. + +```{r} +poly <- function(...) { + x <- vec_cast_common(..., .to = integer()) + x <- new_poly(x) + new_rcrd(list(data = x), class = "vctrs_poly") +} +format.vctrs_poly <- function(x, ...) { + format(field(x, "data")) +} +``` + +The new `format()` method delegates to the one we wrote for the internal list. The vector looks just like before: + +```{r} +p <- poly(1, c(1, 0, 0, 0, 2), c(1, 0, 1)) +p +``` + +Making the class atomic means that `vec_is_list()` now returns `FALSE`. This prevents recursive algorithms that traverse lists from reaching too far inside the polynomial internals. + +```{r} +vec_is_list(p) +``` + +Most importantly, it prevents users from reaching into the internals with `[[`: + +```{r} +p[[2]] +``` + + +#### Implementing equality and comparison + Equality works out of the box because we can tell if two integer vectors are equal: ```{r} p == poly(c(1, 0, 1)) ``` -We can't compare individual elements, because by default lists are not comparable: +We can't compare individual elements, because the data is stored in a list and by default lists are not comparable: ```{r, error = TRUE} p < p[2] @@ -763,8 +809,10 @@ p < p[2] To enable comparison, we implement a `vec_proxy_compare()` method: ```{r} -vec_proxy_compare.vctrs_poly_list <- function(x, ...) { - x_raw <- vec_data(x) +vec_proxy_compare.vctrs_poly <- function(x, ...) { + # Get the list inside the record vector + x_raw <- vec_data(field(x, "data")) + # First figure out the maximum length n <- max(vapply(x_raw, length, integer(1))) @@ -788,7 +836,7 @@ sort(p[c(1:3, 1:2)]) To ensure consistency between ordering and comparison, we forward `vec_proxy_order()` to `vec_proxy_compare()`: ```{r} -vec_proxy_order.vctrs_poly_list <- function(x, ...) { +vec_proxy_order.vctrs_poly <- function(x, ...) { vec_proxy_compare(x, ...) } From 5f63bed51f89d3bc3eae71bf7ccc40a3fa24bd6e Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Tue, 13 Sep 2022 14:58:23 +0200 Subject: [PATCH 046/312] Briefly describe atomicity --- vignettes/s3-vector.Rmd | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/vignettes/s3-vector.Rmd b/vignettes/s3-vector.Rmd index ac6ee78f7..beadae189 100644 --- a/vignettes/s3-vector.Rmd +++ b/vignettes/s3-vector.Rmd @@ -759,7 +759,9 @@ This is fine for the internal implementation of this class but it would be more #### Make an atomic polynomial vector -To make it an atomic vector, we'll wrap the internal `list_of()` class within a record vector. +An atomic vector is a vector like integer or character for which `[[` returns the same type. Unlike lists, you can't reach inside an atomic vector. + +To make the polynomial class an atomic vector, we'll wrap the internal `list_of()` class within a record vector. Usually records are used because they can store several fields of data for each observation. Here we have only one, but we use the class anyway to inherit its atomicity. ```{r} poly <- function(...) { From 12e549d6bc707cb69f826952a4558f3de183502e Mon Sep 17 00:00:00 2001 From: DavisVaughan Date: Tue, 13 Sep 2022 11:48:33 -0400 Subject: [PATCH 047/312] Update `oob` error message --- src/subscript-loc.c | 2 +- tests/testthat/_snaps/subscript-loc.md | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/src/subscript-loc.c b/src/subscript-loc.c index b6d7536e7..eb76a65fc 100644 --- a/src/subscript-loc.c +++ b/src/subscript-loc.c @@ -636,7 +636,7 @@ void stop_bad_negative(struct r_lazy call) { } static void stop_bad_oob(struct r_lazy call) { - r_abort_call(call.env, "`oob` must be one of \"error\" or \"extend\"."); + r_abort_call(call.env, "`oob` must be one of \"error\", \"remove\", or \"extend\"."); } static void stop_bad_zero(struct r_lazy call) { diff --git a/tests/testthat/_snaps/subscript-loc.md b/tests/testthat/_snaps/subscript-loc.md index 2b2b2887b..89badc74f 100644 --- a/tests/testthat/_snaps/subscript-loc.md +++ b/tests/testthat/_snaps/subscript-loc.md @@ -1123,7 +1123,7 @@ num_as_location(1, 1L, oob = "bogus") Condition Error in `num_as_location()`: - ! `oob` must be one of "error" or "extend". + ! `oob` must be one of "error", "remove", or "extend". --- From 11639bd1cd56afeb9eae94571a180ccb03277bb2 Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Tue, 13 Sep 2022 22:50:14 +0200 Subject: [PATCH 048/312] Update style in `poly-op.c` --- src/decl/poly-op-decl.h | 21 ++++++ src/dictionary.c | 6 +- src/dictionary.h | 10 +-- src/interval.c | 26 +++---- src/match-joint.c | 4 +- src/match.c | 10 +-- src/missing.c | 4 +- src/poly-op.c | 159 +++++++++++++++++----------------------- src/poly-op.h | 32 ++++---- 9 files changed, 133 insertions(+), 139 deletions(-) create mode 100644 src/decl/poly-op-decl.h diff --git a/src/decl/poly-op-decl.h b/src/decl/poly-op-decl.h new file mode 100644 index 000000000..03e4a6424 --- /dev/null +++ b/src/decl/poly-op-decl.h @@ -0,0 +1,21 @@ +static +int p_df_equal_na_equal(const void* x, r_ssize i, const void* y, r_ssize j); + +static +int p_df_compare_na_equal(const void* x, r_ssize i, const void* y, r_ssize j); + +static +bool p_df_is_missing(const void* x, r_ssize i); + +static +bool p_df_is_incomplete(const void* x, r_ssize i); + +static void init_nil_poly_vec(struct poly_vec* p_poly_vec); +static void init_lgl_poly_vec(struct poly_vec* p_poly_vec); +static void init_int_poly_vec(struct poly_vec* p_poly_vec); +static void init_dbl_poly_vec(struct poly_vec* p_poly_vec); +static void init_cpl_poly_vec(struct poly_vec* p_poly_vec); +static void init_chr_poly_vec(struct poly_vec* p_poly_vec); +static void init_raw_poly_vec(struct poly_vec* p_poly_vec); +static void init_list_poly_vec(struct poly_vec* p_poly_vec); +static void init_df_poly_vec(struct poly_vec* p_poly_vec); diff --git a/src/dictionary.c b/src/dictionary.c index ea5aae24e..dd02b23c0 100644 --- a/src/dictionary.c +++ b/src/dictionary.c @@ -70,11 +70,11 @@ static struct dictionary* new_dictionary_opts(SEXP x, struct dictionary_opts* op enum vctrs_type type = vec_proxy_typeof(x); struct poly_vec* p_poly_vec = new_poly_vec(x, type); - PROTECT_POLY_VEC(p_poly_vec, &nprot); + KEEP_N(p_poly_vec->shelter, &nprot); d->p_poly_vec = p_poly_vec; - d->p_equal_na_equal = new_poly_p_equal_na_equal(type); - d->p_is_incomplete = new_poly_p_is_incomplete(type); + d->p_equal_na_equal = poly_p_equal_na_equal(type); + d->p_is_incomplete = poly_p_is_incomplete(type); d->used = 0; diff --git a/src/dictionary.h b/src/dictionary.h index 4854abef1..b1f47ae5b 100644 --- a/src/dictionary.h +++ b/src/dictionary.h @@ -15,8 +15,8 @@ struct dictionary { SEXP protect; - poly_binary_int_fn_ptr p_equal_na_equal; - poly_unary_bool_fn_ptr p_is_incomplete; + poly_binary_int_fn* p_equal_na_equal; + poly_unary_bool_fn* p_is_incomplete; struct poly_vec* p_poly_vec; uint32_t* hash; @@ -47,9 +47,9 @@ struct dictionary* new_dictionary_partial(SEXP x); #define PROTECT_DICT(d, n) do { \ struct dictionary* d_ = (d); \ - PROTECT_POLY_VEC(d_->p_poly_vec, n); \ - PROTECT(d_->protect); \ - *(n) += 1; \ + KEEP(d_->p_poly_vec->shelter); \ + KEEP(d_->protect); \ + *(n) += 2; \ } while(0) /** diff --git a/src/interval.c b/src/interval.c index 8824f4804..258dee502 100644 --- a/src/interval.c +++ b/src/interval.c @@ -115,15 +115,15 @@ r_obj* vec_interval_group_info(r_obj* start, const enum vctrs_type type_proxy = vec_proxy_typeof(start_proxy); struct poly_vec* p_poly_start = new_poly_vec(start_proxy, type_proxy); - PROTECT_POLY_VEC(p_poly_start, &n_prot); + KEEP_N(p_poly_start->shelter, &n_prot); const void* p_start = p_poly_start->p_vec; struct poly_vec* p_poly_end = new_poly_vec(end_proxy, type_proxy); - PROTECT_POLY_VEC(p_poly_end, &n_prot); + KEEP_N(p_poly_end->shelter, &n_prot); const void* p_end = p_poly_end->p_vec; - const poly_binary_int_fn_ptr fn_compare = new_poly_p_compare_na_equal(type_proxy); - const poly_unary_bool_fn_ptr fn_is_missing = new_poly_p_is_missing(type_proxy); + poly_binary_int_fn* const fn_compare = poly_p_compare_na_equal(type_proxy); + poly_unary_bool_fn* const fn_is_missing = poly_p_is_missing(type_proxy); const r_ssize size = vec_size(start_proxy); @@ -360,14 +360,14 @@ r_obj* vec_interval_complement(r_obj* start, const enum vctrs_type type_proxy = vec_proxy_typeof(start_proxy); struct poly_vec* p_poly_start = new_poly_vec(start_proxy, type_proxy); - PROTECT_POLY_VEC(p_poly_start, &n_prot); + KEEP_N(p_poly_start->shelter, &n_prot); const void* p_start = p_poly_start->p_vec; struct poly_vec* p_poly_end = new_poly_vec(end_proxy, type_proxy); - PROTECT_POLY_VEC(p_poly_end, &n_prot); + KEEP_N(p_poly_end->shelter, &n_prot); const void* p_end = p_poly_end->p_vec; - const poly_binary_int_fn_ptr fn_compare = new_poly_p_compare_na_equal(type_proxy); + poly_binary_int_fn* const fn_compare = poly_p_compare_na_equal(type_proxy); bool use_lower = (lower != r_null); bool use_upper = (upper != r_null); @@ -401,7 +401,7 @@ r_obj* vec_interval_complement(r_obj* start, } struct poly_vec* p_poly_lower = new_poly_vec(lower_proxy, type_proxy); - PROTECT_POLY_VEC(p_poly_lower, &n_prot); + KEEP_N(p_poly_lower->shelter, &n_prot); p_lower = p_poly_lower->p_vec; } @@ -431,7 +431,7 @@ r_obj* vec_interval_complement(r_obj* start, } struct poly_vec* p_poly_upper = new_poly_vec(upper_proxy, type_proxy); - PROTECT_POLY_VEC(p_poly_upper, &n_prot); + KEEP_N(p_poly_upper->shelter, &n_prot); p_upper = p_poly_upper->p_vec; } @@ -770,15 +770,15 @@ r_obj* vec_interval_locate_containers(r_obj* start, r_obj* end) { const enum vctrs_type type_proxy = vec_proxy_typeof(start_proxy); struct poly_vec* p_poly_start = new_poly_vec(start_proxy, type_proxy); - PROTECT_POLY_VEC(p_poly_start, &n_prot); + KEEP_N(p_poly_start->shelter, &n_prot); const void* p_start = p_poly_start->p_vec; struct poly_vec* p_poly_end = new_poly_vec(end_proxy, type_proxy); - PROTECT_POLY_VEC(p_poly_end, &n_prot); + KEEP_N(p_poly_end->shelter, &n_prot); const void* p_end = p_poly_end->p_vec; - const poly_binary_int_fn_ptr fn_compare = new_poly_p_compare_na_equal(type_proxy); - const poly_unary_bool_fn_ptr fn_is_missing = new_poly_p_is_missing(type_proxy); + poly_binary_int_fn* const fn_compare = poly_p_compare_na_equal(type_proxy); + poly_unary_bool_fn* const fn_is_missing = poly_p_is_missing(type_proxy); const r_ssize size = vec_size(start_proxy); diff --git a/src/match-joint.c b/src/match-joint.c index d0c007bc8..aa568d2d5 100644 --- a/src/match-joint.c +++ b/src/match-joint.c @@ -138,11 +138,11 @@ r_obj* vec_joint_xtfrm(r_obj* x, const enum vctrs_type type = vec_proxy_typeof(x_proxy); const struct poly_vec* p_x_poly = new_poly_vec(x_proxy, type); - PROTECT_POLY_VEC(p_x_poly, &n_prot); + KEEP_N(p_x_poly->shelter, &n_prot); const void* p_x_vec = p_x_poly->p_vec; const struct poly_vec* p_y_poly = new_poly_vec(y_proxy, type); - PROTECT_POLY_VEC(p_x_poly, &n_prot); + KEEP_N(p_y_poly->shelter, &n_prot); const void* p_y_vec = p_y_poly->p_vec; r_ssize i = 0; diff --git a/src/match.c b/src/match.c index 5b5afd8d0..6980dd695 100644 --- a/src/match.c +++ b/src/match.c @@ -363,19 +363,19 @@ r_obj* df_locate_matches(r_obj* needles, } struct poly_vec* p_poly_needles = new_poly_vec(needles, VCTRS_TYPE_dataframe); - PROTECT_POLY_VEC(p_poly_needles, &n_prot); + KEEP_N(p_poly_needles->shelter, &n_prot); const struct poly_df_data* p_needles = (const struct poly_df_data*) p_poly_needles->p_vec; struct poly_vec* p_poly_haystack = new_poly_vec(haystack, VCTRS_TYPE_dataframe); - PROTECT_POLY_VEC(p_poly_haystack, &n_prot); + KEEP_N(p_poly_haystack->shelter, &n_prot); const struct poly_df_data* p_haystack = (const struct poly_df_data*) p_poly_haystack->p_vec; const struct poly_vec* p_poly_needles_complete = new_poly_vec(needles_complete, VCTRS_TYPE_dataframe); - PROTECT_POLY_VEC(p_poly_needles_complete, &n_prot); + KEEP_N(p_poly_needles_complete->shelter, &n_prot); const struct poly_df_data* p_needles_complete = (const struct poly_df_data*) p_poly_needles_complete->p_vec; struct poly_vec* p_poly_haystack_complete = new_poly_vec(haystack_complete, VCTRS_TYPE_dataframe); - PROTECT_POLY_VEC(p_poly_haystack_complete, &n_prot); + KEEP_N(p_poly_haystack_complete->shelter, &n_prot); const struct poly_df_data* p_haystack_complete = (const struct poly_df_data*) p_poly_haystack_complete->p_vec; if (size_needles > 0) { @@ -2219,7 +2219,7 @@ r_obj* compute_nesting_container_ids(r_obj* x, KEEP_N(p_prev_rows->shelter, &n_prot); struct poly_vec* p_poly_x = new_poly_vec(x, VCTRS_TYPE_dataframe); - PROTECT_POLY_VEC(p_poly_x, &n_prot); + KEEP_N(p_poly_x->shelter, &n_prot); const void* v_x = p_poly_x->p_vec; // Will be used if `has_outer_group_sizes` is `true` diff --git a/src/missing.c b/src/missing.c index 84333c90f..632aa7643 100644 --- a/src/missing.c +++ b/src/missing.c @@ -368,10 +368,10 @@ r_ssize df_first_missing(r_obj* x) { int n_prot = 0; - const poly_unary_bool_fn_ptr fn_is_missing = new_poly_p_is_missing(VCTRS_TYPE_dataframe); + poly_unary_bool_fn* const fn_is_missing = poly_p_is_missing(VCTRS_TYPE_dataframe); struct poly_vec* p_poly_x = new_poly_vec(x, VCTRS_TYPE_dataframe); - PROTECT_POLY_VEC(p_poly_x, &n_prot); + KEEP_N(p_poly_x->shelter, &n_prot); const void* v_x = p_poly_x->p_vec; r_ssize out = size; diff --git a/src/poly-op.c b/src/poly-op.c index 264dc4952..3ff98f8c8 100644 --- a/src/poly-op.c +++ b/src/poly-op.c @@ -1,11 +1,8 @@ #include "vctrs.h" +#include "decl/poly-op-decl.h" -// ----------------------------------------------------------------------------- -static int p_df_equal_na_equal(const void* x, r_ssize i, const void* y, r_ssize j); - -// [[ include("poly-op.h") ]] -poly_binary_int_fn_ptr new_poly_p_equal_na_equal(enum vctrs_type type) { +poly_binary_int_fn* poly_p_equal_na_equal(enum vctrs_type type) { switch (type) { case VCTRS_TYPE_null: return p_nil_equal_na_equal; case VCTRS_TYPE_logical: return p_lgl_equal_na_equal; @@ -16,23 +13,23 @@ poly_binary_int_fn_ptr new_poly_p_equal_na_equal(enum vctrs_type type) { case VCTRS_TYPE_raw: return p_raw_equal_na_equal; case VCTRS_TYPE_list: return p_list_equal_na_equal; case VCTRS_TYPE_dataframe: return p_df_equal_na_equal; - default: stop_unimplemented_vctrs_type("new_poly_p_equal_na_equal", type); + default: stop_unimplemented_vctrs_type("poly_p_equal_na_equal", type); } } static -int p_df_equal_na_equal(const void* x, r_ssize i, const void* y, r_ssize j) { - struct poly_df_data* x_data = (struct poly_df_data*) x; - struct poly_df_data* y_data = (struct poly_df_data*) y; +int p_df_equal_na_equal(const void* p_x, r_ssize i, const void* p_y, r_ssize j) { + struct poly_df_data* p_x_data = (struct poly_df_data*) p_x; + struct poly_df_data* p_y_data = (struct poly_df_data*) p_y; - r_ssize n_col = x_data->n_col; - if (n_col != y_data->n_col) { + r_ssize n_col = p_x_data->n_col; + if (n_col != p_y_data->n_col) { r_stop_internal("`x` and `y` must have the same number of columns."); } - enum vctrs_type* v_col_type = x_data->v_col_type; - const void** v_x_col_ptr = x_data->v_col_ptr; - const void** v_y_col_ptr = y_data->v_col_ptr; + enum vctrs_type* v_col_type = p_x_data->v_col_type; + const void** v_x_col_ptr = p_x_data->v_col_ptr; + const void** v_y_col_ptr = p_y_data->v_col_ptr; // df-cols should already be flattened for (r_ssize col = 0; col < n_col; ++col) { @@ -44,12 +41,8 @@ int p_df_equal_na_equal(const void* x, r_ssize i, const void* y, r_ssize j) { return true; } -// ----------------------------------------------------------------------------- - -static int p_df_compare_na_equal(const void* x, r_ssize i, const void* y, r_ssize j); -// [[ include("poly-op.h") ]] -poly_binary_int_fn_ptr new_poly_p_compare_na_equal(enum vctrs_type type) { +poly_binary_int_fn* poly_p_compare_na_equal(enum vctrs_type type) { switch (type) { case VCTRS_TYPE_null: return p_nil_compare_na_equal; case VCTRS_TYPE_logical: return p_lgl_compare_na_equal; @@ -60,23 +53,23 @@ poly_binary_int_fn_ptr new_poly_p_compare_na_equal(enum vctrs_type type) { case VCTRS_TYPE_raw: return p_raw_compare_na_equal; case VCTRS_TYPE_list: return p_list_compare_na_equal; case VCTRS_TYPE_dataframe: return p_df_compare_na_equal; - default: stop_unimplemented_vctrs_type("new_poly_p_compare_na_equal", type); + default: stop_unimplemented_vctrs_type("poly_p_compare_na_equal", type); } } static -int p_df_compare_na_equal(const void* x, r_ssize i, const void* y, r_ssize j) { - struct poly_df_data* x_data = (struct poly_df_data*) x; - struct poly_df_data* y_data = (struct poly_df_data*) y; +int p_df_compare_na_equal(const void* p_x, r_ssize i, const void* p_y, r_ssize j) { + struct poly_df_data* p_x_data = (struct poly_df_data*) p_x; + struct poly_df_data* p_y_data = (struct poly_df_data*) p_y; - r_ssize n_col = x_data->n_col; - if (n_col != y_data->n_col) { + r_ssize n_col = p_x_data->n_col; + if (n_col != p_y_data->n_col) { r_stop_internal("`x` and `y` must have the same number of columns."); } - enum vctrs_type* v_col_type = x_data->v_col_type; - const void** v_x_col_ptr = x_data->v_col_ptr; - const void** v_y_col_ptr = y_data->v_col_ptr; + enum vctrs_type* v_col_type = p_x_data->v_col_type; + const void** v_x_col_ptr = p_x_data->v_col_ptr; + const void** v_y_col_ptr = p_y_data->v_col_ptr; // df-cols should already be flattened for (r_ssize col = 0; col < n_col; ++col) { @@ -94,12 +87,8 @@ int p_df_compare_na_equal(const void* x, r_ssize i, const void* y, r_ssize j) { return 0; } -// ----------------------------------------------------------------------------- - -static bool p_df_is_missing(const void* x, r_ssize i); -// [[ include("poly-op.h") ]] -poly_unary_bool_fn_ptr new_poly_p_is_missing(enum vctrs_type type) { +poly_unary_bool_fn* poly_p_is_missing(enum vctrs_type type) { switch (type) { case VCTRS_TYPE_null: return p_nil_is_missing; case VCTRS_TYPE_logical: return p_lgl_is_missing; @@ -110,17 +99,17 @@ poly_unary_bool_fn_ptr new_poly_p_is_missing(enum vctrs_type type) { case VCTRS_TYPE_raw: return p_raw_is_missing; case VCTRS_TYPE_list: return p_list_is_missing; case VCTRS_TYPE_dataframe: return p_df_is_missing; - default: stop_unimplemented_vctrs_type("new_poly_p_is_missing", type); + default: stop_unimplemented_vctrs_type("poly_p_is_missing", type); } } static -bool p_df_is_missing(const void* x, r_ssize i) { - struct poly_df_data* x_data = (struct poly_df_data*) x; +bool p_df_is_missing(const void* p_x, r_ssize i) { + struct poly_df_data* p_x_data = (struct poly_df_data*) p_x; - enum vctrs_type* v_col_type = x_data->v_col_type; - const void** v_col_ptr = x_data->v_col_ptr; - r_ssize n_col = x_data->n_col; + enum vctrs_type* v_col_type = p_x_data->v_col_type; + const void** v_col_ptr = p_x_data->v_col_ptr; + r_ssize n_col = p_x_data->n_col; // df-cols should already be flattened for (r_ssize col = 0; col < n_col; ++col) { @@ -132,12 +121,8 @@ bool p_df_is_missing(const void* x, r_ssize i) { return true; } -// ----------------------------------------------------------------------------- -static bool p_df_is_incomplete(const void* x, r_ssize i); - -// [[ include("poly-op.h") ]] -poly_unary_bool_fn_ptr new_poly_p_is_incomplete(enum vctrs_type type) { +poly_unary_bool_fn* poly_p_is_incomplete(enum vctrs_type type) { switch (type) { case VCTRS_TYPE_null: return p_nil_is_missing; case VCTRS_TYPE_logical: return p_lgl_is_missing; @@ -148,17 +133,17 @@ poly_unary_bool_fn_ptr new_poly_p_is_incomplete(enum vctrs_type type) { case VCTRS_TYPE_raw: return p_raw_is_missing; case VCTRS_TYPE_list: return p_list_is_missing; case VCTRS_TYPE_dataframe: return p_df_is_incomplete; - default: stop_unimplemented_vctrs_type("new_poly_p_is_incomplete", type); + default: stop_unimplemented_vctrs_type("poly_p_is_incomplete", type); } } static -bool p_df_is_incomplete(const void* x, r_ssize i) { - struct poly_df_data* x_data = (struct poly_df_data*) x; +bool p_df_is_incomplete(const void* p_x, r_ssize i) { + struct poly_df_data* p_x_data = (struct poly_df_data*) p_x; - enum vctrs_type* v_col_type = x_data->v_col_type; - const void** v_col_ptr = x_data->v_col_ptr; - r_ssize n_col = x_data->n_col; + enum vctrs_type* v_col_type = p_x_data->v_col_type; + const void** v_col_ptr = p_x_data->v_col_ptr; + r_ssize n_col = p_x_data->n_col; // df-cols should already be flattened, // so we only need missingness of each column, not completeness @@ -171,24 +156,17 @@ bool p_df_is_incomplete(const void* x, r_ssize i) { return false; } -// ----------------------------------------------------------------------------- -static void init_nil_poly_vec(struct poly_vec* p_poly_vec); -static void init_lgl_poly_vec(struct poly_vec* p_poly_vec); -static void init_int_poly_vec(struct poly_vec* p_poly_vec); -static void init_dbl_poly_vec(struct poly_vec* p_poly_vec); -static void init_cpl_poly_vec(struct poly_vec* p_poly_vec); -static void init_chr_poly_vec(struct poly_vec* p_poly_vec); -static void init_raw_poly_vec(struct poly_vec* p_poly_vec); -static void init_list_poly_vec(struct poly_vec* p_poly_vec); -static void init_df_poly_vec(struct poly_vec* p_poly_vec); +struct poly_vec* new_poly_vec(r_obj* proxy, enum vctrs_type type) { + r_obj* shelter = KEEP(r_alloc_list(2)); + + r_obj* self = r_alloc_raw(sizeof(struct poly_vec)); + r_list_poke(shelter, 0, self); + r_list_poke(shelter, 1, proxy); -// [[ include("poly-op.h") ]] -struct poly_vec* new_poly_vec(SEXP proxy, enum vctrs_type type) { - SEXP self = PROTECT(Rf_allocVector(RAWSXP, sizeof(struct poly_vec))); - struct poly_vec* p_poly_vec = (struct poly_vec*) RAW(self); + struct poly_vec* p_poly_vec = r_raw_begin(self); - p_poly_vec->self = self; + p_poly_vec->shelter = shelter; p_poly_vec->vec = proxy; switch (type) { @@ -204,10 +182,7 @@ struct poly_vec* new_poly_vec(SEXP proxy, enum vctrs_type type) { default: stop_unimplemented_vctrs_type("new_poly_vec", type); } - // `init_*_poly_vec()` functions may allocate - PROTECT(p_poly_vec->self); - - UNPROTECT(2); + FREE(1); return p_poly_vec; } @@ -217,56 +192,56 @@ void init_nil_poly_vec(struct poly_vec* p_poly_vec) { } static void init_lgl_poly_vec(struct poly_vec* p_poly_vec) { - p_poly_vec->p_vec = (const void*) LOGICAL_RO(p_poly_vec->vec); + p_poly_vec->p_vec = (const void*) r_lgl_cbegin(p_poly_vec->vec); } static void init_int_poly_vec(struct poly_vec* p_poly_vec) { - p_poly_vec->p_vec = (const void*) INTEGER_RO(p_poly_vec->vec); + p_poly_vec->p_vec = (const void*) r_int_cbegin(p_poly_vec->vec); } static void init_dbl_poly_vec(struct poly_vec* p_poly_vec) { - p_poly_vec->p_vec = (const void*) REAL_RO(p_poly_vec->vec); + p_poly_vec->p_vec = (const void*) r_dbl_cbegin(p_poly_vec->vec); } static void init_cpl_poly_vec(struct poly_vec* p_poly_vec) { - p_poly_vec->p_vec = (const void*) COMPLEX_RO(p_poly_vec->vec); + p_poly_vec->p_vec = (const void*) r_cpl_cbegin(p_poly_vec->vec); } static void init_chr_poly_vec(struct poly_vec* p_poly_vec) { - p_poly_vec->p_vec = (const void*) STRING_PTR_RO(p_poly_vec->vec); + p_poly_vec->p_vec = (const void*) r_chr_cbegin(p_poly_vec->vec); } static void init_raw_poly_vec(struct poly_vec* p_poly_vec) { - p_poly_vec->p_vec = (const void*) RAW_RO(p_poly_vec->vec); + p_poly_vec->p_vec = (const void*) r_raw_cbegin(p_poly_vec->vec); } static void init_list_poly_vec(struct poly_vec* p_poly_vec) { - p_poly_vec->p_vec = (const void*) VECTOR_PTR_RO(p_poly_vec->vec); + p_poly_vec->p_vec = (const void*) r_list_cbegin(p_poly_vec->vec); } static void init_df_poly_vec(struct poly_vec* p_poly_vec) { - SEXP df = p_poly_vec->vec; - r_ssize n_col = Rf_xlength(df); + r_obj* df = p_poly_vec->vec; + r_ssize n_col = r_length(df); - SEXP self = PROTECT(Rf_allocVector(VECSXP, 4)); + r_obj* shelter = KEEP(r_alloc_list(4)); - SET_VECTOR_ELT(self, 0, p_poly_vec->self); - p_poly_vec->self = self; + r_list_poke(shelter, 0, p_poly_vec->shelter); + p_poly_vec->shelter = shelter; - SEXP data_handle = PROTECT(Rf_allocVector(RAWSXP, sizeof(struct poly_df_data))); - struct poly_df_data* data = (struct poly_df_data*) RAW(data_handle); - SET_VECTOR_ELT(self, 1, data_handle); + r_obj* data_handle = KEEP(r_alloc_raw(sizeof(struct poly_df_data))); + struct poly_df_data* data = (struct poly_df_data*) r_raw_begin(data_handle); + r_list_poke(shelter, 1, data_handle); - SEXP col_type_handle = PROTECT(Rf_allocVector(RAWSXP, n_col * sizeof(enum vctrs_type))); - enum vctrs_type* v_col_type = (enum vctrs_type*) RAW(col_type_handle); - SET_VECTOR_ELT(self, 2, col_type_handle); + r_obj* col_type_handle = KEEP(r_alloc_raw(n_col * sizeof(enum vctrs_type))); + enum vctrs_type* v_col_type = (enum vctrs_type*) r_raw_begin(col_type_handle); + r_list_poke(shelter, 2, col_type_handle); - SEXP col_ptr_handle = PROTECT(Rf_allocVector(RAWSXP, n_col * sizeof(void*))); - const void** v_col_ptr = (const void**) RAW(col_ptr_handle); - SET_VECTOR_ELT(self, 3, col_ptr_handle); + r_obj* col_ptr_handle = KEEP(r_alloc_raw(n_col * sizeof(void*))); + const void** v_col_ptr = (const void**) r_raw_begin(col_ptr_handle); + r_list_poke(shelter, 3, col_ptr_handle); for (r_ssize i = 0; i < n_col; ++i) { - SEXP col = VECTOR_ELT(df, i); + r_obj* col = r_list_get(df, i); v_col_type[i] = vec_proxy_typeof(col); v_col_ptr[i] = r_vec_cbegin(col); } @@ -277,5 +252,5 @@ void init_df_poly_vec(struct poly_vec* p_poly_vec) { p_poly_vec->p_vec = (void*) data; - UNPROTECT(4); + FREE(4); } diff --git a/src/poly-op.h b/src/poly-op.h index 3db5fa510..e5edb18fa 100644 --- a/src/poly-op.h +++ b/src/poly-op.h @@ -3,13 +3,15 @@ #include "vctrs-core.h" -typedef int (*poly_binary_int_fn_ptr)(const void* x, r_ssize i, const void* y, r_ssize j); -poly_binary_int_fn_ptr new_poly_p_equal_na_equal(enum vctrs_type type); -poly_binary_int_fn_ptr new_poly_p_compare_na_equal(enum vctrs_type type); -typedef bool (*poly_unary_bool_fn_ptr)(const void* x, r_ssize i); -poly_unary_bool_fn_ptr new_poly_p_is_missing(enum vctrs_type type); -poly_unary_bool_fn_ptr new_poly_p_is_incomplete(enum vctrs_type type); +struct poly_vec { + r_obj* shelter; + r_obj* vec; + const void* p_vec; +}; + +struct poly_vec* new_poly_vec(r_obj* proxy, enum vctrs_type type); + struct poly_df_data { enum vctrs_type* v_col_type; @@ -17,18 +19,14 @@ struct poly_df_data { r_ssize n_col; }; -struct poly_vec { - SEXP vec; - const void* p_vec; - SEXP self; -}; -struct poly_vec* new_poly_vec(SEXP proxy, enum vctrs_type type); +typedef int (poly_binary_int_fn)(const void* x, r_ssize i, const void* y, r_ssize j); +poly_binary_int_fn* poly_p_equal_na_equal(enum vctrs_type type); +poly_binary_int_fn* poly_p_compare_na_equal(enum vctrs_type type); + +typedef bool (poly_unary_bool_fn)(const void* x, r_ssize i); +poly_unary_bool_fn* poly_p_is_missing(enum vctrs_type type); +poly_unary_bool_fn* poly_p_is_incomplete(enum vctrs_type type); -#define PROTECT_POLY_VEC(p_poly_vec, p_n) do { \ - PROTECT((p_poly_vec)->vec); \ - PROTECT((p_poly_vec)->self); \ - *(p_n) += 2; \ -} while(0) #endif From 8e6f1f224ffbe3510f535d1fa8dc2e5689ac0c9a Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Wed, 14 Sep 2022 14:00:45 +0200 Subject: [PATCH 049/312] Make `stop_native_implementation()` an internal error --- R/conditions.R | 12 +++++++----- 1 file changed, 7 insertions(+), 5 deletions(-) diff --git a/R/conditions.R b/R/conditions.R index 92614a16f..107fcacae 100644 --- a/R/conditions.R +++ b/R/conditions.R @@ -814,12 +814,14 @@ ensure_full_stop <- function(x) { } -# TODO! cli + .internal stop_native_implementation <- function(fn) { - abort(paste_line( - glue::glue("`{fn}()` is implemented at C level."), - "This R function is purely indicative and should never be called." - )) + cli::cli_abort( + c( + "{.fn {fn}} is implemented at C level.", + " " = "This R function is purely indicative and should never be called." + ), + .internal = TRUE + ) } From 98f1a1585f3056ede396c4f4557c75182227647b Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Wed, 14 Sep 2022 16:40:33 +0200 Subject: [PATCH 050/312] Update style in `rep.c` --- R/rep.R | 6 +- src/decl/rep-decl.h | 50 ++++++ src/init.c | 12 +- src/rep.c | 312 +++++++++++++++++------------------ tests/testthat/_snaps/rep.md | 14 +- 5 files changed, 216 insertions(+), 178 deletions(-) create mode 100644 src/decl/rep-decl.h diff --git a/R/rep.R b/R/rep.R index 86a372706..8ade0bb19 100644 --- a/R/rep.R +++ b/R/rep.R @@ -84,17 +84,17 @@ NULL #' @rdname vec-rep #' @export vec_rep <- function(x, times) { - .Call(vctrs_rep, x, times) + .Call(ffi_vec_rep, x, times) } #' @rdname vec-rep #' @export vec_rep_each <- function(x, times) { - .Call(vctrs_rep_each, x, times) + .Call(ffi_vec_rep_each, x, times) } #' @rdname vec-rep #' @export vec_unrep <- function(x) { - .Call(vctrs_unrep, x) + .Call(ffi_vec_unrep, x) } diff --git a/src/decl/rep-decl.h b/src/decl/rep-decl.h new file mode 100644 index 000000000..f6cfe08f3 --- /dev/null +++ b/src/decl/rep-decl.h @@ -0,0 +1,50 @@ +static struct vctrs_arg args_times_; +static struct vctrs_arg* const p_args_times; + +static inline +void stop_rep_times_size(); + +static inline +void check_rep_times(int times); + +static inline +void check_rep_each_times(int times, r_ssize i); + +static inline +bool multiply_would_overflow(r_ssize x, r_ssize y); + +static inline +bool plus_would_overflow(r_ssize x, r_ssize y); + +static inline +void stop_rep_size_oob(); + +static +r_obj* vec_rep_each_uniform(r_obj* x, int times); + +static +r_obj* vec_rep_each_impl(r_obj* x, r_obj* times, const r_ssize times_size); + +static inline +void stop_rep_times_negative(); + +static inline +void stop_rep_times_missing(); + +static inline +void stop_rep_times_oob(int times); + +static inline +void stop_rep_each_times_negative(r_ssize i); + +static inline +void stop_rep_each_times_missing(r_ssize i); + +static inline +void stop_rep_each_times_oob(int times, r_ssize i); + +static +r_obj* vec_unrep(r_obj* x); + +static +r_obj* new_unrep_data_frame(r_obj* key, r_obj* times, r_ssize size); diff --git a/src/init.c b/src/init.c index c71a383e5..235b18c2b 100644 --- a/src/init.c +++ b/src/init.c @@ -102,8 +102,8 @@ extern r_obj* ffi_tib_ptype2(r_obj*, r_obj*, r_obj*, r_obj*, r_obj*); extern r_obj* ffi_tib_cast(r_obj*, r_obj*, r_obj*, r_obj*, r_obj*); extern r_obj* ffi_assign_params(r_obj*, r_obj*, r_obj*, r_obj*); extern SEXP vctrs_has_dim(SEXP); -extern SEXP vctrs_rep(SEXP, SEXP); -extern SEXP vctrs_rep_each(SEXP, SEXP); +extern r_obj* ffi_vec_rep(r_obj*, r_obj*); +extern SEXP ffi_vec_rep_each(SEXP, SEXP); extern SEXP vctrs_maybe_shared_col(SEXP, SEXP); extern SEXP vctrs_new_df_unshared_col(); extern SEXP vctrs_shaped_ptype(SEXP, SEXP, SEXP, SEXP); @@ -130,7 +130,7 @@ extern SEXP vctrs_normalize_encoding(SEXP); extern SEXP vctrs_order(SEXP, SEXP, SEXP, SEXP, SEXP); extern SEXP vctrs_locate_sorted_groups(SEXP, SEXP, SEXP, SEXP, SEXP); extern SEXP vctrs_order_info(SEXP, SEXP, SEXP, SEXP, SEXP, SEXP); -extern SEXP vctrs_unrep(SEXP); +extern r_obj* ffi_vec_unrep(r_obj*); extern SEXP vctrs_fill_missing(SEXP, SEXP, SEXP); extern r_obj* ffi_chr_paste_prefix(r_obj*, r_obj*, r_obj*); extern r_obj* vctrs_rank(r_obj*, r_obj*, r_obj*, r_obj*, r_obj*, r_obj*, r_obj*); @@ -273,8 +273,8 @@ static const R_CallMethodDef CallEntries[] = { {"ffi_tib_cast", (DL_FUNC) &ffi_tib_cast, 5}, {"ffi_assign_params", (DL_FUNC) &ffi_assign_params, 4}, {"vctrs_has_dim", (DL_FUNC) &vctrs_has_dim, 1}, - {"vctrs_rep", (DL_FUNC) &vctrs_rep, 2}, - {"vctrs_rep_each", (DL_FUNC) &vctrs_rep_each, 2}, + {"ffi_vec_rep", (DL_FUNC) &ffi_vec_rep, 2}, + {"ffi_vec_rep_each", (DL_FUNC) &ffi_vec_rep_each, 2}, {"vctrs_maybe_shared_col", (DL_FUNC) &vctrs_maybe_shared_col, 2}, {"vctrs_new_df_unshared_col", (DL_FUNC) &vctrs_new_df_unshared_col, 0}, {"vctrs_shaped_ptype", (DL_FUNC) &vctrs_shaped_ptype, 4}, @@ -301,7 +301,7 @@ static const R_CallMethodDef CallEntries[] = { {"vctrs_order", (DL_FUNC) &vctrs_order, 5}, {"vctrs_locate_sorted_groups", (DL_FUNC) &vctrs_locate_sorted_groups, 5}, {"vctrs_order_info", (DL_FUNC) &vctrs_order_info, 6}, - {"vctrs_unrep", (DL_FUNC) &vctrs_unrep, 1}, + {"ffi_vec_unrep", (DL_FUNC) &ffi_vec_unrep, 1}, {"vctrs_fill_missing", (DL_FUNC) &vctrs_fill_missing, 3}, {"ffi_chr_paste_prefix", (DL_FUNC) &ffi_chr_paste_prefix, 3}, {"vctrs_rank", (DL_FUNC) &vctrs_rank, 7}, diff --git a/src/rep.c b/src/rep.c index 12da92671..681b34ead 100644 --- a/src/rep.c +++ b/src/rep.c @@ -1,104 +1,80 @@ #include "vctrs.h" #include "type-data-frame.h" +#include "decl/rep-decl.h" -// Initialised at load time -static struct vctrs_arg args_times_; -static struct vctrs_arg* const args_times = &args_times_; -static inline void stop_rep_times_size(); - -static inline void check_rep_times(int times); -static inline void check_rep_each_times(int times, R_len_t i); - -static inline bool multiply_would_overflow(R_len_t x, R_len_t y); -static inline bool plus_would_overflow(R_len_t x, R_len_t y); -static inline void stop_rep_size_oob(); - -// ----------------------------------------------------------------------------- - -static SEXP vec_rep(SEXP x, int times); - -// [[ register() ]] -SEXP vctrs_rep(SEXP x, SEXP times) { - struct r_lazy call = r_lazy_null; - - times = PROTECT(vec_cast(times, - r_globals.empty_int, - args_times, - vec_args.empty, - call)); - - if (vec_size(times) != 1) { - stop_rep_times_size(); - } - - const int times_ = r_int_get(times, 0); - - SEXP out = vec_rep(x, times_); - - UNPROTECT(1); - return out; -} - -static SEXP vec_rep(SEXP x, int times) { +static +r_obj* vec_rep(r_obj* x, int times) { check_rep_times(times); if (times == 1) { return x; } - const R_len_t times_ = (R_len_t) times; - const R_len_t x_size = vec_size(x); + const r_ssize times_ = (r_ssize) times; + const r_ssize x_size = vec_size(x); if (x_size == 1) { - return vec_check_recycle(x, times_, args_times, r_lazy_null); + return vec_check_recycle(x, times_, p_args_times, r_lazy_null); } if (multiply_would_overflow(x_size, times_)) { stop_rep_size_oob(); }; - const R_len_t size = x_size * times_; + const r_ssize size = x_size * times_; - SEXP subscript = PROTECT(Rf_allocVector(INTSXP, size)); - int* p_subscript = INTEGER(subscript); + r_obj* subscript = KEEP(r_alloc_integer(size)); + int* v_subscript = r_int_begin(subscript); - R_len_t k = 0; + r_ssize k = 0; - for (R_len_t i = 0; i < times_; ++i) { - for (R_len_t j = 1; j <= x_size; ++j, ++k) { - p_subscript[k] = j; + for (r_ssize i = 0; i < times_; ++i) { + for (r_ssize j = 1; j <= x_size; ++j, ++k) { + v_subscript[k] = j; } } - SEXP out = vec_slice_unsafe(x, subscript); + r_obj* out = vec_slice_unsafe(x, subscript); - UNPROTECT(1); + FREE(1); return out; } -// ----------------------------------------------------------------------------- +r_obj* ffi_vec_rep(r_obj* x, r_obj* ffi_times) { + struct r_lazy call = r_lazy_null; -static SEXP vec_rep_each(SEXP x, SEXP times); + ffi_times = KEEP(vec_cast(ffi_times, + r_globals.empty_int, + p_args_times, + vec_args.empty, + call)); -// [[ register() ]] -SEXP vctrs_rep_each(SEXP x, SEXP times) { - return vec_rep_each(x, times); + if (vec_size(ffi_times) != 1) { + stop_rep_times_size(); + } + + const int times = r_int_get(ffi_times, 0); + r_obj* out = vec_rep(x, times); + + FREE(1); + return out; } -static SEXP vec_rep_each_uniform(SEXP x, int times); -static SEXP vec_rep_each_impl(SEXP x, SEXP times, const R_len_t times_size); -static SEXP vec_rep_each(SEXP x, SEXP times) { - times = PROTECT(vec_cast(times, - r_globals.empty_int, - args_times, - vec_args.empty, - r_lazy_null)); +// ----------------------------------------------------------------------------- + +static +r_obj* vec_rep_each(r_obj* x, r_obj* times) { + times = KEEP(vec_cast(times, + r_globals.empty_int, + p_args_times, + vec_args.empty, + r_lazy_null)); - const R_len_t times_size = vec_size(times); + const r_ssize times_size = vec_size(times); - SEXP out; + r_obj* out; if (times_size == 1) { const int times_ = r_int_get(times, 0); @@ -114,58 +90,66 @@ static SEXP vec_rep_each(SEXP x, SEXP times) { out = vec_rep_each_impl(x, times, times_size); } - UNPROTECT(1); + FREE(1); return out; } -static SEXP vec_rep_each_uniform(SEXP x, int times) { +r_obj* ffi_vec_rep_each(r_obj* x, r_obj* times) { + return vec_rep_each(x, times); +} + + +// ----------------------------------------------------------------------------- + +static +r_obj* vec_rep_each_uniform(r_obj* x, int times) { check_rep_each_times(times, 1); - const R_len_t times_ = (R_len_t) times; - const R_len_t x_size = vec_size(x); + const r_ssize times_ = (r_ssize) times; + const r_ssize x_size = vec_size(x); if (multiply_would_overflow(x_size, times_)) { stop_rep_size_oob(); }; - const R_len_t size = x_size * times_; + const r_ssize size = x_size * times_; - SEXP subscript = PROTECT(Rf_allocVector(INTSXP, size)); - int* p_subscript = INTEGER(subscript); + r_obj* subscript = KEEP(r_alloc_integer(size)); + int* v_subscript = r_int_begin(subscript); - R_len_t k = 0; + r_ssize k = 0; - for (R_len_t i = 1; i <= x_size; ++i) { - for (R_len_t j = 0; j < times_; ++j, ++k) { - p_subscript[k] = i; + for (r_ssize i = 1; i <= x_size; ++i) { + for (r_ssize j = 0; j < times_; ++j, ++k) { + v_subscript[k] = i; } } - SEXP out = vec_slice_unsafe(x, subscript); + r_obj* out = vec_slice_unsafe(x, subscript); - UNPROTECT(1); + FREE(1); return out; } -static SEXP vec_rep_each_impl(SEXP x, SEXP times, const R_len_t times_size) { - const R_len_t x_size = vec_size(x); +static r_obj* vec_rep_each_impl(r_obj* x, r_obj* times, const r_ssize times_size) { + const r_ssize x_size = vec_size(x); if (x_size != times_size) { stop_recycle_incompatible_size(times_size, x_size, - args_times, + p_args_times, r_lazy_null); } - const int* p_times = INTEGER_RO(times); + const int* v_times = r_int_cbegin(times); - R_len_t size = 0; - for (R_len_t i = 0; i < times_size; ++i) { - const int elt_times = p_times[i]; + r_ssize size = 0; + for (r_ssize i = 0; i < times_size; ++i) { + const int elt_times = v_times[i]; check_rep_each_times(elt_times, i + 1); - const R_len_t elt_times_ = (R_len_t) elt_times; + const r_ssize elt_times_ = (r_ssize) elt_times; if (plus_would_overflow(size, elt_times_)) { stop_rep_size_oob(); @@ -174,52 +158,54 @@ static SEXP vec_rep_each_impl(SEXP x, SEXP times, const R_len_t times_size) { size += elt_times_; } - SEXP subscript = PROTECT(Rf_allocVector(INTSXP, size)); - int* p_subscript = INTEGER(subscript); + r_obj* subscript = KEEP(r_alloc_integer(size)); + int* v_subscript = r_int_begin(subscript); - R_len_t k = 0; + r_ssize k = 0; - for (R_len_t i = 1; i <= x_size; ++i) { - const R_len_t elt_times = (R_len_t) p_times[i - 1]; + for (r_ssize i = 1; i <= x_size; ++i) { + const r_ssize elt_times = (r_ssize) v_times[i - 1]; - for (R_len_t j = 0; j < elt_times; ++j, ++k) { - p_subscript[k] = i; + for (r_ssize j = 0; j < elt_times; ++j, ++k) { + v_subscript[k] = i; } } - SEXP out = vec_slice_unsafe(x, subscript); + r_obj* out = vec_slice_unsafe(x, subscript); - UNPROTECT(1); + FREE(1); return out; } + // ----------------------------------------------------------------------------- // TODO: Modify for long vectors with `R_XLEN_T_MAX` and `R_xlen_t`. -static inline bool times_is_oob(int times) { +static inline +bool times_is_oob(int times) { return times > R_LEN_T_MAX; } // Only useful for positive or zero inputs -static inline bool multiply_would_overflow(R_len_t x, R_len_t y) { +static inline +bool multiply_would_overflow(r_ssize x, r_ssize y) { return (double) x * y > R_LEN_T_MAX; } // Only useful for positive or zero inputs -static inline bool plus_would_overflow(R_len_t x, R_len_t y) { +static inline +bool plus_would_overflow(r_ssize x, r_ssize y) { return x > R_LEN_T_MAX - y; } -// ----------------------------------------------------------------------------- -static inline void stop_rep_times_negative(); -static inline void stop_rep_times_missing(); -static inline void stop_rep_times_oob(int times); +// ----------------------------------------------------------------------------- -static inline void check_rep_times(int times) { +static inline +void check_rep_times(int times) { if (times < 0) { - if (times == NA_INTEGER) { + if (times == r_globals.na_int) { stop_rep_times_missing(); } else { stop_rep_times_negative(); @@ -229,34 +215,34 @@ static inline void check_rep_times(int times) { } } -static inline void stop_rep_times_negative() { - Rf_errorcall(R_NilValue, "`times` must be a positive number."); +static inline +void stop_rep_times_negative() { + r_abort("`times` must be a positive number."); } -static inline void stop_rep_times_missing() { - Rf_errorcall(R_NilValue, "`times` can't be missing."); +static inline +void stop_rep_times_missing() { + r_abort("`times` can't be missing."); } -// Not currently thrown since `R_len_t == int`, but might be once +// Not currently thrown since `r_ssize == int`, but might be once // long vectors are supported -static inline void stop_rep_times_oob(int times) { - Rf_errorcall( - R_NilValue, +static inline +void stop_rep_times_oob(int times) { + r_abort( "`times` must be less than %i, not %i.", R_LEN_T_MAX, times ); } -// ----------------------------------------------------------------------------- -static inline void stop_rep_each_times_negative(R_len_t i); -static inline void stop_rep_each_times_missing(R_len_t i); -static inline void stop_rep_each_times_oob(int times, R_len_t i); +// ----------------------------------------------------------------------------- -static inline void check_rep_each_times(int times, R_len_t i) { +static inline +void check_rep_each_times(int times, r_ssize i) { if (times < 0) { - if (times == NA_INTEGER) { + if (times == r_globals.na_int) { stop_rep_each_times_missing(i); } else { stop_rep_each_times_negative(i); @@ -266,19 +252,21 @@ static inline void check_rep_each_times(int times, R_len_t i) { } } -static inline void stop_rep_each_times_negative(R_len_t i) { - Rf_errorcall(R_NilValue, "`times` must be a vector of positive numbers. Location %i is negative.", i); +static inline +void stop_rep_each_times_negative(r_ssize i) { + r_abort("`times` must be a vector of positive numbers. Location %i is negative.", i); } -static inline void stop_rep_each_times_missing(R_len_t i) { - Rf_errorcall(R_NilValue, "`times` can't be missing. Location %i is missing.", i); +static inline +void stop_rep_each_times_missing(r_ssize i) { + r_abort("`times` can't be missing. Location %i is missing.", i); } -// Not currently thrown since `R_len_t == int`, but might be once +// Not currently thrown since `r_ssize == int`, but might be once // long vectors are supported -static inline void stop_rep_each_times_oob(int times, R_len_t i) { - Rf_errorcall( - R_NilValue, +static inline +void stop_rep_each_times_oob(int times, r_ssize i) { + r_abort( "`times` must be less than %i, not %i. ", "Location %i is too large.", R_LEN_T_MAX, @@ -287,54 +275,45 @@ static inline void stop_rep_each_times_oob(int times, R_len_t i) { ); } -// ----------------------------------------------------------------------------- - -static inline void stop_rep_size_oob() { - Rf_errorcall( - R_NilValue, +static inline +void stop_rep_size_oob() { + r_abort( "Long vectors are not yet supported. " "Requested output size must be less than %i.", R_LEN_T_MAX ); } -static inline void stop_rep_times_size() { - Rf_errorcall(R_NilValue, "`times` must be a single number."); +static inline +void stop_rep_times_size() { + r_abort("`times` must be a single number."); } -// ----------------------------------------------------------------------------- - -static SEXP vec_unrep(SEXP x); -// [[register()]] -SEXP vctrs_unrep(SEXP x) { - return vec_unrep(x); -} - -static SEXP new_unrep_data_frame(SEXP key, SEXP times, r_ssize size); +// ----------------------------------------------------------------------------- static -SEXP vec_unrep(SEXP x) { - SEXP id = PROTECT(vec_identify_runs(x)); - const int* p_id = INTEGER_RO(id); +r_obj* vec_unrep(r_obj* x) { + r_obj* id = KEEP(vec_identify_runs(x)); + const int* p_id = r_int_cbegin(id); r_ssize x_size = r_length(id); if (x_size == 0) { - SEXP out = new_unrep_data_frame(x, r_globals.empty_int, 0); - UNPROTECT(1); + r_obj* out = new_unrep_data_frame(x, r_globals.empty_int, 0); + FREE(1); return out; } r_ssize out_size = (r_ssize) r_int_get(r_attrib_get(id, syms_n), 0); // Size of each run - SEXP times = PROTECT(r_new_integer(out_size)); - int* p_times = INTEGER(times); + r_obj* times = KEEP(r_new_integer(out_size)); + int* v_times = r_int_begin(times); // Location of the start of each run. For slicing `x`. - SEXP loc = PROTECT(r_new_integer(out_size)); - int* p_loc = INTEGER(loc); + r_obj* loc = KEEP(r_new_integer(out_size)); + int* p_loc = r_int_begin(loc); r_ssize idx = 0; r_ssize previous = 0; @@ -355,7 +334,7 @@ SEXP vec_unrep(SEXP x) { reference = elt; // Size of current run - p_times[idx - 1] = i - previous; + v_times[idx - 1] = i - previous; previous = i; // 1-based location of the start of the new run @@ -364,23 +343,28 @@ SEXP vec_unrep(SEXP x) { } // Handle last case - p_times[idx - 1] = x_size - previous; + v_times[idx - 1] = x_size - previous; - SEXP key = PROTECT(vec_slice(x, loc)); - SEXP out = new_unrep_data_frame(key, times, out_size); + r_obj* key = KEEP(vec_slice(x, loc)); + r_obj* out = new_unrep_data_frame(key, times, out_size); - UNPROTECT(4); + FREE(4); return out; } +r_obj* ffi_vec_unrep(r_obj* x) { + return vec_unrep(x); +} + + static -SEXP new_unrep_data_frame(SEXP key, SEXP times, r_ssize size) { - SEXP out = PROTECT(r_new_list(2)); +r_obj* new_unrep_data_frame(r_obj* key, r_obj* times, r_ssize size) { + r_obj* out = KEEP(r_new_list(2)); r_list_poke(out, 0, key); r_list_poke(out, 1, times); - SEXP names = PROTECT(r_new_character(2)); + r_obj* names = KEEP(r_new_character(2)); r_attrib_poke_names(out, names); r_chr_poke(names, 0, strings_key); @@ -388,12 +372,16 @@ SEXP new_unrep_data_frame(SEXP key, SEXP times, r_ssize size) { init_data_frame(out, size); - UNPROTECT(2); + FREE(2); return out; } + // ----------------------------------------------------------------------------- -void vctrs_init_rep(SEXP ns) { +void vctrs_init_rep(r_obj* ns) { args_times_ = new_wrapper_arg(NULL, "times"); } + +static +struct vctrs_arg* const p_args_times = &args_times_; diff --git a/tests/testthat/_snaps/rep.md b/tests/testthat/_snaps/rep.md index 627b2b4f0..41e41f588 100644 --- a/tests/testthat/_snaps/rep.md +++ b/tests/testthat/_snaps/rep.md @@ -11,7 +11,7 @@ Code vec_rep(1, c(1, 2)) Condition - Error: + Error in `vec_rep()`: ! `times` must be a single number. --- @@ -19,7 +19,7 @@ Code vec_rep(1, -1) Condition - Error: + Error in `vec_rep()`: ! `times` must be a positive number. --- @@ -27,7 +27,7 @@ Code vec_rep(1, NA_integer_) Condition - Error: + Error in `vec_rep()`: ! `times` can't be missing. # `vec_rep_each()` validates `times` @@ -43,7 +43,7 @@ Code vec_rep_each(1, -1) Condition - Error: + Error in `vec_rep_each()`: ! `times` must be a vector of positive numbers. Location 1 is negative. --- @@ -51,7 +51,7 @@ Code vec_rep_each(c(1, 2), c(1, -1)) Condition - Error: + Error in `vec_rep_each()`: ! `times` must be a vector of positive numbers. Location 2 is negative. --- @@ -59,7 +59,7 @@ Code vec_rep_each(1, NA_integer_) Condition - Error: + Error in `vec_rep_each()`: ! `times` can't be missing. Location 1 is missing. --- @@ -67,7 +67,7 @@ Code vec_rep_each(c(1, 2), c(1, NA_integer_)) Condition - Error: + Error in `vec_rep_each()`: ! `times` can't be missing. Location 2 is missing. # `vec_rep_each()` uses recyclying errors From 1436c5177f9a1376633333c5fadb5304fbc1e4b9 Mon Sep 17 00:00:00 2001 From: Davis Vaughan Date: Wed, 14 Sep 2022 11:41:57 -0400 Subject: [PATCH 051/312] Add empty `...` to `vec_order()` and `vec_sort()` (#1654) * Add empty `...` to `vec_order()` and `vec_sort()` * NEWS bullet --- NEWS.md | 3 +++ R/order.R | 12 ++++++++++-- man/vec_order.Rd | 20 ++++++++++++++++---- tests/testthat/_snaps/order.md | 22 ++++++++++++++++++++++ tests/testthat/test-order.R | 17 +++++++++++++---- 5 files changed, 64 insertions(+), 10 deletions(-) create mode 100644 tests/testthat/_snaps/order.md diff --git a/NEWS.md b/NEWS.md index 4046b2e2d..c0e3df78f 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,5 +1,8 @@ # vctrs (development version) +* `vec_order()` and `vec_sort()` now have `...` between the required and + optional arguments to make them easier to extend (#1647). + * S3 vignette was extended to show how to make the polynomial class atomic instead of a list (#1030). diff --git a/R/order.R b/R/order.R index 829873c07..bc573bcca 100644 --- a/R/order.R +++ b/R/order.R @@ -306,6 +306,8 @@ vec_order_base <- function(x, #' Order and sort vectors #' +#' @inheritParams rlang::args_dots_empty +#' #' @param x A vector #' @param direction Direction to sort in. Defaults to `asc`ending. #' @param na_value Should `NA`s be treated as the largest or smallest values? @@ -333,21 +335,24 @@ vec_order_base <- function(x, #' x <- round(c(runif(9), NA), 3) #' vec_order(x) #' vec_sort(x) -#' vec_sort(x, "desc") +#' vec_sort(x, direction = "desc") #' #' # Can also handle data frames #' df <- data.frame(g = sample(2, 10, replace = TRUE), x = x) #' vec_order(df) #' vec_sort(df) -#' vec_sort(df, "desc") +#' vec_sort(df, direction = "desc") #' #' # Missing values interpreted as largest values are last when #' # in increasing order: #' vec_order(c(1, NA), na_value = "largest", direction = "asc") #' vec_order(c(1, NA), na_value = "largest", direction = "desc") vec_order <- function(x, + ..., direction = c("asc", "desc"), na_value = c("largest", "smallest")) { + check_dots_empty0(...) + direction <- arg_match0(direction, c("asc", "desc")) na_value <- arg_match0(na_value, c("largest", "smallest")) @@ -384,8 +389,11 @@ vec_order <- function(x, #' @export #' @rdname vec_order vec_sort <- function(x, + ..., direction = c("asc", "desc"), na_value = c("largest", "smallest")) { + check_dots_empty0(...) + direction <- arg_match0(direction, c("asc", "desc")) na_value <- arg_match0(na_value, c("largest", "smallest")) diff --git a/man/vec_order.Rd b/man/vec_order.Rd index a673b0ad0..14bab6714 100644 --- a/man/vec_order.Rd +++ b/man/vec_order.Rd @@ -5,13 +5,25 @@ \alias{vec_sort} \title{Order and sort vectors} \usage{ -vec_order(x, direction = c("asc", "desc"), na_value = c("largest", "smallest")) +vec_order( + x, + ..., + direction = c("asc", "desc"), + na_value = c("largest", "smallest") +) -vec_sort(x, direction = c("asc", "desc"), na_value = c("largest", "smallest")) +vec_sort( + x, + ..., + direction = c("asc", "desc"), + na_value = c("largest", "smallest") +) } \arguments{ \item{x}{A vector} +\item{...}{These dots are for future extensions and must be empty.} + \item{direction}{Direction to sort in. Defaults to \code{asc}ending.} \item{na_value}{Should \code{NA}s be treated as the largest or smallest values?} @@ -55,13 +67,13 @@ order. x <- round(c(runif(9), NA), 3) vec_order(x) vec_sort(x) -vec_sort(x, "desc") +vec_sort(x, direction = "desc") # Can also handle data frames df <- data.frame(g = sample(2, 10, replace = TRUE), x = x) vec_order(df) vec_sort(df) -vec_sort(df, "desc") +vec_sort(df, direction = "desc") # Missing values interpreted as largest values are last when # in increasing order: diff --git a/tests/testthat/_snaps/order.md b/tests/testthat/_snaps/order.md new file mode 100644 index 000000000..068598e9f --- /dev/null +++ b/tests/testthat/_snaps/order.md @@ -0,0 +1,22 @@ +# dots must be empty (#1647) + + Code + vec_order(1, 2) + Condition + Error in `vec_order()`: + ! `...` must be empty. + x Problematic argument: + * ..1 = 2 + i Did you forget to name an argument? + +--- + + Code + vec_sort(1, 2) + Condition + Error in `vec_sort()`: + ! `...` must be empty. + x Problematic argument: + * ..1 = 2 + i Did you forget to name an argument? + diff --git a/tests/testthat/test-order.R b/tests/testthat/test-order.R index 0d54e8176..13014fb0d 100644 --- a/tests/testthat/test-order.R +++ b/tests/testthat/test-order.R @@ -1246,11 +1246,11 @@ test_that("can sort empty data frames (#356)", { # vec_order test_that("can request NAs sorted first", { - expect_equal(vec_order(c(1, NA), "asc", "largest"), 1:2) - expect_equal(vec_order(c(1, NA), "desc", "largest"), 2:1) + expect_equal(vec_order(c(1, NA), direction = "asc", na_value = "largest"), 1:2) + expect_equal(vec_order(c(1, NA), direction = "desc", na_value = "largest"), 2:1) - expect_equal(vec_order(c(1, NA), "asc", "smallest"), 2:1) - expect_equal(vec_order(c(1, NA), "desc", "smallest"), 1:2) + expect_equal(vec_order(c(1, NA), direction = "asc", na_value = "smallest"), 2:1) + expect_equal(vec_order(c(1, NA), direction = "desc", na_value = "smallest"), 1:2) }) test_that("can order complex vectors", { @@ -1343,3 +1343,12 @@ test_that("missing values in lists are respected (#1401)", { expect_identical(vec_order(x, na_value = "largest"), c(1L, 3L, 2L, 4L)) expect_identical(vec_order(x, na_value = "smallest"), c(2L, 4L, 1L, 3L)) }) + +test_that("dots must be empty (#1647)", { + expect_snapshot(error = TRUE, { + vec_order(1, 2) + }) + expect_snapshot(error = TRUE, { + vec_sort(1, 2) + }) +}) From 28c8724f1fe68cc4c6fe6cf5e2f775a46363eec9 Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Wed, 14 Sep 2022 18:39:25 +0200 Subject: [PATCH 052/312] Disallow indexing record vectors on multiple dimensions (#1656) Closes #1295 --- NEWS.md | 3 +++ R/type-rcrd.R | 5 ++++- tests/testthat/_snaps/type-rcrd.md | 8 ++++++++ tests/testthat/test-type-rcrd.R | 5 +++-- 4 files changed, 18 insertions(+), 3 deletions(-) diff --git a/NEWS.md b/NEWS.md index c0e3df78f..406e987ec 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,5 +1,8 @@ # vctrs (development version) +* Record vectors now fail as expected when indexed along dimensions + greater than 1 (#1295). + * `vec_order()` and `vec_sort()` now have `...` between the required and optional arguments to make them easier to extend (#1647). diff --git a/R/type-rcrd.R b/R/type-rcrd.R index 075733fe2..6a1dbe227 100644 --- a/R/type-rcrd.R +++ b/R/type-rcrd.R @@ -95,7 +95,10 @@ vec_cast.vctrs_rcrd.vctrs_rcrd <- function(x, to, ...) { #' @export `[.vctrs_rcrd` <- function(x, i, ...) { - vec_index(x, i, ...) + if (!missing(...)) { + abort("Can't index record vectors on dimensions greater than 1.") + } + vec_slice(x, maybe_missing(i)) } #' @export diff --git a/tests/testthat/_snaps/type-rcrd.md b/tests/testthat/_snaps/type-rcrd.md index 70b901dcd..2001b639e 100644 --- a/tests/testthat/_snaps/type-rcrd.md +++ b/tests/testthat/_snaps/type-rcrd.md @@ -43,3 +43,11 @@ .. ..$ : vctrs_tp [1:100] (1,1), (1,2), (1,3), (1,4), (1,5), (1,6), (1,7)... .. ..$ : int [1:100] 1 2 3 4 5 6 7 8 9 10 ... +# dots are an error (#1295) + + Code + foo[1, 2] + Condition + Error in `foo[1, 2]`: + ! Can't index record vectors on dimensions greater than 1. + diff --git a/tests/testthat/test-type-rcrd.R b/tests/testthat/test-type-rcrd.R index 0cdeacf78..94d13e099 100644 --- a/tests/testthat/test-type-rcrd.R +++ b/tests/testthat/test-type-rcrd.R @@ -279,8 +279,9 @@ test_that("dangerous methods marked as unimplemented", { # slicing ----------------------------------------------------------------- -test_that("dots are forwarded", { - expect_error(new_rcrd(list(foo = "foo"))[1, 2], "undefined columns selected") +test_that("dots are an error (#1295)", { + foo <- new_rcrd(list(foo = "foo")) + expect_snapshot(error = TRUE, foo[1, 2]) }) test_that("records are restored after slicing the proxy", { From 374e171709bb9e9b04f11bd96ec224a2f2133b1c Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Wed, 14 Sep 2022 17:05:46 +0200 Subject: [PATCH 053/312] Add `call` arguments to `vec_rep()` and friends Part of #1303 --- R/rep.R | 9 ++-- man/vec-rep.Rd | 11 +++-- src/decl/rep-decl.h | 24 ++++----- src/init.c | 8 +-- src/rep.c | 96 +++++++++++++++++++----------------- tests/testthat/_snaps/rep.md | 6 +-- 6 files changed, 84 insertions(+), 70 deletions(-) diff --git a/R/rep.R b/R/rep.R index 8ade0bb19..ca0962bad 100644 --- a/R/rep.R +++ b/R/rep.R @@ -36,6 +36,7 @@ #' For `vec_rep_each()`, an integer vector of the number of times to repeat #' each element of `x`. `times` will be [recycled][vector_recycling_rules] to #' the size of `x`. +#' @inheritParams rlang::args_error_context #' #' @return #' For `vec_rep()`, a vector the same type as `x` with size @@ -83,14 +84,14 @@ NULL #' @rdname vec-rep #' @export -vec_rep <- function(x, times) { - .Call(ffi_vec_rep, x, times) +vec_rep <- function(x, times, call = current_env()) { + .Call(ffi_vec_rep, x, times, environment()) } #' @rdname vec-rep #' @export -vec_rep_each <- function(x, times) { - .Call(ffi_vec_rep_each, x, times) +vec_rep_each <- function(x, times, call = current_env()) { + .Call(ffi_vec_rep_each, x, times, environment()) } #' @rdname vec-rep diff --git a/man/vec-rep.Rd b/man/vec-rep.Rd index 243371c48..4180042ce 100644 --- a/man/vec-rep.Rd +++ b/man/vec-rep.Rd @@ -7,11 +7,11 @@ \alias{vec_unrep} \title{Repeat a vector} \usage{ -vec_rep(x, times) +vec_rep(x, times, call = current_env()) -vec_rep_each(x, times) +vec_rep_each(x, times, call = current_env()) -vec_unrep(x) +vec_unrep(x, call = current_env()) } \arguments{ \item{x}{A vector.} @@ -22,6 +22,11 @@ the entire vector. For \code{vec_rep_each()}, an integer vector of the number of times to repeat each element of \code{x}. \code{times} will be \link[=vector_recycling_rules]{recycled} to the size of \code{x}.} + +\item{call}{The execution environment of a currently +running function, e.g. \code{caller_env()}. The function will be +mentioned in error messages as the source of the error. See the +\code{call} argument of \code{\link[rlang:abort]{abort()}} for more information.} } \value{ For \code{vec_rep()}, a vector the same type as \code{x} with size diff --git a/src/decl/rep-decl.h b/src/decl/rep-decl.h index f6cfe08f3..2fa7354df 100644 --- a/src/decl/rep-decl.h +++ b/src/decl/rep-decl.h @@ -2,13 +2,13 @@ static struct vctrs_arg args_times_; static struct vctrs_arg* const p_args_times; static inline -void stop_rep_times_size(); +void stop_rep_times_size(struct r_lazy call); static inline -void check_rep_times(int times); +void check_rep_times(int times, struct r_lazy call); static inline -void check_rep_each_times(int times, r_ssize i); +void check_rep_each_times(int times, r_ssize i, struct r_lazy call); static inline bool multiply_would_overflow(r_ssize x, r_ssize y); @@ -17,31 +17,31 @@ static inline bool plus_would_overflow(r_ssize x, r_ssize y); static inline -void stop_rep_size_oob(); +void stop_rep_size_oob(struct r_lazy call); static -r_obj* vec_rep_each_uniform(r_obj* x, int times); +r_obj* vec_rep_each_uniform(r_obj* x, int times, struct r_lazy call); static -r_obj* vec_rep_each_impl(r_obj* x, r_obj* times, const r_ssize times_size); +r_obj* vec_rep_each_impl(r_obj* x, r_obj* times, const r_ssize times_size, struct r_lazy call); static inline -void stop_rep_times_negative(); +void stop_rep_times_negative(struct r_lazy call); static inline -void stop_rep_times_missing(); +void stop_rep_times_missing(struct r_lazy call); static inline -void stop_rep_times_oob(int times); +void stop_rep_times_oob(int times, struct r_lazy call); static inline -void stop_rep_each_times_negative(r_ssize i); +void stop_rep_each_times_negative(r_ssize i, struct r_lazy call); static inline -void stop_rep_each_times_missing(r_ssize i); +void stop_rep_each_times_missing(r_ssize i, struct r_lazy call); static inline -void stop_rep_each_times_oob(int times, r_ssize i); +void stop_rep_each_times_oob(int times, r_ssize i, struct r_lazy call); static r_obj* vec_unrep(r_obj* x); diff --git a/src/init.c b/src/init.c index 235b18c2b..035742f4a 100644 --- a/src/init.c +++ b/src/init.c @@ -102,8 +102,8 @@ extern r_obj* ffi_tib_ptype2(r_obj*, r_obj*, r_obj*, r_obj*, r_obj*); extern r_obj* ffi_tib_cast(r_obj*, r_obj*, r_obj*, r_obj*, r_obj*); extern r_obj* ffi_assign_params(r_obj*, r_obj*, r_obj*, r_obj*); extern SEXP vctrs_has_dim(SEXP); -extern r_obj* ffi_vec_rep(r_obj*, r_obj*); -extern SEXP ffi_vec_rep_each(SEXP, SEXP); +extern r_obj* ffi_vec_rep(r_obj*, r_obj*, r_obj*); +extern r_obj* ffi_vec_rep_each(r_obj*, r_obj*, r_obj*); extern SEXP vctrs_maybe_shared_col(SEXP, SEXP); extern SEXP vctrs_new_df_unshared_col(); extern SEXP vctrs_shaped_ptype(SEXP, SEXP, SEXP, SEXP); @@ -273,8 +273,8 @@ static const R_CallMethodDef CallEntries[] = { {"ffi_tib_cast", (DL_FUNC) &ffi_tib_cast, 5}, {"ffi_assign_params", (DL_FUNC) &ffi_assign_params, 4}, {"vctrs_has_dim", (DL_FUNC) &vctrs_has_dim, 1}, - {"ffi_vec_rep", (DL_FUNC) &ffi_vec_rep, 2}, - {"ffi_vec_rep_each", (DL_FUNC) &ffi_vec_rep_each, 2}, + {"ffi_vec_rep", (DL_FUNC) &ffi_vec_rep, 3}, + {"ffi_vec_rep_each", (DL_FUNC) &ffi_vec_rep_each, 3}, {"vctrs_maybe_shared_col", (DL_FUNC) &vctrs_maybe_shared_col, 2}, {"vctrs_new_df_unshared_col", (DL_FUNC) &vctrs_new_df_unshared_col, 0}, {"vctrs_shaped_ptype", (DL_FUNC) &vctrs_shaped_ptype, 4}, diff --git a/src/rep.c b/src/rep.c index 681b34ead..788ab8a7e 100644 --- a/src/rep.c +++ b/src/rep.c @@ -1,11 +1,12 @@ +#include "rlang.h" #include "vctrs.h" #include "type-data-frame.h" #include "decl/rep-decl.h" static -r_obj* vec_rep(r_obj* x, int times) { - check_rep_times(times); +r_obj* vec_rep(r_obj* x, int times, struct r_lazy call) { + check_rep_times(times, call); if (times == 1) { return x; @@ -19,7 +20,7 @@ r_obj* vec_rep(r_obj* x, int times) { } if (multiply_would_overflow(x_size, times_)) { - stop_rep_size_oob(); + stop_rep_size_oob(call); }; const r_ssize size = x_size * times_; @@ -41,8 +42,8 @@ r_obj* vec_rep(r_obj* x, int times) { return out; } -r_obj* ffi_vec_rep(r_obj* x, r_obj* ffi_times) { - struct r_lazy call = r_lazy_null; +r_obj* ffi_vec_rep(r_obj* x, r_obj* ffi_times, r_obj* frame) { + struct r_lazy call = { .x = r_syms.call, .env = frame }; ffi_times = KEEP(vec_cast(ffi_times, r_globals.empty_int, @@ -51,11 +52,11 @@ r_obj* ffi_vec_rep(r_obj* x, r_obj* ffi_times) { call)); if (vec_size(ffi_times) != 1) { - stop_rep_times_size(); + stop_rep_times_size(call); } const int times = r_int_get(ffi_times, 0); - r_obj* out = vec_rep(x, times); + r_obj* out = vec_rep(x, times, call); FREE(1); return out; @@ -65,12 +66,12 @@ r_obj* ffi_vec_rep(r_obj* x, r_obj* ffi_times) { // ----------------------------------------------------------------------------- static -r_obj* vec_rep_each(r_obj* x, r_obj* times) { +r_obj* vec_rep_each(r_obj* x, r_obj* times, struct r_lazy call) { times = KEEP(vec_cast(times, r_globals.empty_int, p_args_times, vec_args.empty, - r_lazy_null)); + call)); const r_ssize times_size = vec_size(times); @@ -84,32 +85,33 @@ r_obj* vec_rep_each(r_obj* x, r_obj* times) { } else if (times_ == 0) { out = vec_ptype(x, vec_args.empty, r_lazy_null); } else { - out = vec_rep_each_uniform(x, times_); + out = vec_rep_each_uniform(x, times_, call); } } else { - out = vec_rep_each_impl(x, times, times_size); + out = vec_rep_each_impl(x, times, times_size, call); } FREE(1); return out; } -r_obj* ffi_vec_rep_each(r_obj* x, r_obj* times) { - return vec_rep_each(x, times); +r_obj* ffi_vec_rep_each(r_obj* x, r_obj* times, r_obj* frame) { + struct r_lazy call = { .x = r_syms.call, .env = frame }; + return vec_rep_each(x, times, call); } // ----------------------------------------------------------------------------- static -r_obj* vec_rep_each_uniform(r_obj* x, int times) { - check_rep_each_times(times, 1); +r_obj* vec_rep_each_uniform(r_obj* x, int times, struct r_lazy call) { + check_rep_each_times(times, 1, call); const r_ssize times_ = (r_ssize) times; const r_ssize x_size = vec_size(x); if (multiply_would_overflow(x_size, times_)) { - stop_rep_size_oob(); + stop_rep_size_oob(call); }; const r_ssize size = x_size * times_; @@ -131,14 +133,17 @@ r_obj* vec_rep_each_uniform(r_obj* x, int times) { return out; } -static r_obj* vec_rep_each_impl(r_obj* x, r_obj* times, const r_ssize times_size) { +static r_obj* vec_rep_each_impl(r_obj* x, + r_obj* times, + const r_ssize times_size, + struct r_lazy call) { const r_ssize x_size = vec_size(x); if (x_size != times_size) { stop_recycle_incompatible_size(times_size, x_size, p_args_times, - r_lazy_null); + call); } const int* v_times = r_int_cbegin(times); @@ -147,12 +152,12 @@ static r_obj* vec_rep_each_impl(r_obj* x, r_obj* times, const r_ssize times_size for (r_ssize i = 0; i < times_size; ++i) { const int elt_times = v_times[i]; - check_rep_each_times(elt_times, i + 1); + check_rep_each_times(elt_times, i + 1, call); const r_ssize elt_times_ = (r_ssize) elt_times; if (plus_would_overflow(size, elt_times_)) { - stop_rep_size_oob(); + stop_rep_size_oob(call); } size += elt_times_; @@ -203,33 +208,34 @@ bool plus_would_overflow(r_ssize x, r_ssize y) { // ----------------------------------------------------------------------------- static inline -void check_rep_times(int times) { +void check_rep_times(int times, struct r_lazy call) { if (times < 0) { if (times == r_globals.na_int) { - stop_rep_times_missing(); + stop_rep_times_missing(call); } else { - stop_rep_times_negative(); + stop_rep_times_negative(call); } } else if (times_is_oob(times)) { - stop_rep_times_oob(times); + stop_rep_times_oob(times, call); } } static inline -void stop_rep_times_negative() { - r_abort("`times` must be a positive number."); +void stop_rep_times_negative(struct r_lazy call) { + r_abort_lazy_call(call, "`times` must be a positive number."); } static inline -void stop_rep_times_missing() { - r_abort("`times` can't be missing."); +void stop_rep_times_missing(struct r_lazy call) { + r_abort_lazy_call(call, "`times` can't be missing."); } // Not currently thrown since `r_ssize == int`, but might be once // long vectors are supported static inline -void stop_rep_times_oob(int times) { - r_abort( +void stop_rep_times_oob(int times, struct r_lazy call) { + r_abort_lazy_call( + call, "`times` must be less than %i, not %i.", R_LEN_T_MAX, times @@ -240,33 +246,34 @@ void stop_rep_times_oob(int times) { // ----------------------------------------------------------------------------- static inline -void check_rep_each_times(int times, r_ssize i) { +void check_rep_each_times(int times, r_ssize i, struct r_lazy call) { if (times < 0) { if (times == r_globals.na_int) { - stop_rep_each_times_missing(i); + stop_rep_each_times_missing(i, call); } else { - stop_rep_each_times_negative(i); + stop_rep_each_times_negative(i, call); } } else if (times_is_oob(times)) { - stop_rep_each_times_oob(times, i); + stop_rep_each_times_oob(times, i, call); } } static inline -void stop_rep_each_times_negative(r_ssize i) { - r_abort("`times` must be a vector of positive numbers. Location %i is negative.", i); +void stop_rep_each_times_negative(r_ssize i, struct r_lazy call) { + r_abort_lazy_call(call, "`times` must be a vector of positive numbers. Location %i is negative.", i); } static inline -void stop_rep_each_times_missing(r_ssize i) { - r_abort("`times` can't be missing. Location %i is missing.", i); +void stop_rep_each_times_missing(r_ssize i, struct r_lazy call) { + r_abort_lazy_call(call, "`times` can't be missing. Location %i is missing.", i); } // Not currently thrown since `r_ssize == int`, but might be once // long vectors are supported static inline -void stop_rep_each_times_oob(int times, r_ssize i) { - r_abort( +void stop_rep_each_times_oob(int times, r_ssize i, struct r_lazy call) { + r_abort_lazy_call( + call, "`times` must be less than %i, not %i. ", "Location %i is too large.", R_LEN_T_MAX, @@ -276,8 +283,9 @@ void stop_rep_each_times_oob(int times, r_ssize i) { } static inline -void stop_rep_size_oob() { - r_abort( +void stop_rep_size_oob(struct r_lazy call) { + r_abort_lazy_call( + call, "Long vectors are not yet supported. " "Requested output size must be less than %i.", R_LEN_T_MAX @@ -285,8 +293,8 @@ void stop_rep_size_oob() { } static inline -void stop_rep_times_size() { - r_abort("`times` must be a single number."); +void stop_rep_times_size(struct r_lazy call) { + r_abort_lazy_call(call, "`times` must be a single number."); } diff --git a/tests/testthat/_snaps/rep.md b/tests/testthat/_snaps/rep.md index 41e41f588..0ae49d620 100644 --- a/tests/testthat/_snaps/rep.md +++ b/tests/testthat/_snaps/rep.md @@ -3,7 +3,7 @@ Code vec_rep(1, "x") Condition - Error: + Error in `vec_rep()`: ! Can't convert `times` to . --- @@ -35,7 +35,7 @@ Code vec_rep_each(1, "x") Condition - Error: + Error in `vec_rep_each()`: ! Can't convert `times` to . --- @@ -75,6 +75,6 @@ Code vec_rep_each(1:2, 1:3) Condition - Error: + Error in `vec_rep_each()`: ! Can't recycle `times` (size 3) to size 2. From 45eded6862c9e6d13c3a98eeb81ca9b1890513b8 Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Wed, 14 Sep 2022 17:27:41 +0200 Subject: [PATCH 054/312] Add `x_arg` and `times_arg` arguments to `vec_rep()` and friends Closes #1303 --- NEWS.md | 3 + R/rep.R | 13 ++- man/vec-rep.Rd | 8 +- src/decl/rep-decl.h | 38 +++++--- src/globals.c | 1 + src/globals.h | 2 +- src/rep.c | 138 +++++++++++++++++++---------- tests/testthat/_snaps/rep.md | 130 ++++++++++++++++++++------- tests/testthat/helper-conditions.R | 20 +++++ tests/testthat/test-rep.R | 46 +++++----- 10 files changed, 284 insertions(+), 115 deletions(-) diff --git a/NEWS.md b/NEWS.md index 406e987ec..0e1ca6d35 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,5 +1,8 @@ # vctrs (development version) +* `vec_rep()` and friends gain `call`, `x_arg`, and `times_arg` + arguments so they can be embedded in frontends (#1303). + * Record vectors now fail as expected when indexed along dimensions greater than 1 (#1295). diff --git a/R/rep.R b/R/rep.R index ca0962bad..b6f3b6d61 100644 --- a/R/rep.R +++ b/R/rep.R @@ -37,6 +37,7 @@ #' each element of `x`. `times` will be [recycled][vector_recycling_rules] to #' the size of `x`. #' @inheritParams rlang::args_error_context +#' @param x_arg,times_arg Argument names for errors. #' #' @return #' For `vec_rep()`, a vector the same type as `x` with size @@ -84,13 +85,21 @@ NULL #' @rdname vec-rep #' @export -vec_rep <- function(x, times, call = current_env()) { +vec_rep <- function(x, + times, + call = current_env(), + x_arg = "x", + times_arg = "times") { .Call(ffi_vec_rep, x, times, environment()) } #' @rdname vec-rep #' @export -vec_rep_each <- function(x, times, call = current_env()) { +vec_rep_each <- function(x, + times, + call = current_env(), + x_arg = "x", + times_arg = "times") { .Call(ffi_vec_rep_each, x, times, environment()) } diff --git a/man/vec-rep.Rd b/man/vec-rep.Rd index 4180042ce..c5b6ef413 100644 --- a/man/vec-rep.Rd +++ b/man/vec-rep.Rd @@ -7,11 +7,11 @@ \alias{vec_unrep} \title{Repeat a vector} \usage{ -vec_rep(x, times, call = current_env()) +vec_rep(x, times, call = current_env(), x_arg = "x", times_arg = "times") -vec_rep_each(x, times, call = current_env()) +vec_rep_each(x, times, call = current_env(), x_arg = "x", times_arg = "times") -vec_unrep(x, call = current_env()) +vec_unrep(x) } \arguments{ \item{x}{A vector.} @@ -27,6 +27,8 @@ the size of \code{x}.} running function, e.g. \code{caller_env()}. The function will be mentioned in error messages as the source of the error. See the \code{call} argument of \code{\link[rlang:abort]{abort()}} for more information.} + +\item{x_arg, times_arg}{Argument names for errors.} } \value{ For \code{vec_rep()}, a vector the same type as \code{x} with size diff --git a/src/decl/rep-decl.h b/src/decl/rep-decl.h index 2fa7354df..efb368789 100644 --- a/src/decl/rep-decl.h +++ b/src/decl/rep-decl.h @@ -1,14 +1,17 @@ -static struct vctrs_arg args_times_; -static struct vctrs_arg* const p_args_times; - static inline -void stop_rep_times_size(struct r_lazy call); +void stop_rep_times_size(struct r_lazy call, + struct vctrs_arg* p_times_arg); static inline -void check_rep_times(int times, struct r_lazy call); +void check_rep_times(int times, + struct r_lazy call, + struct vctrs_arg* p_times_arg); static inline -void check_rep_each_times(int times, r_ssize i, struct r_lazy call); +void check_rep_each_times(int times, + r_ssize i, + struct r_lazy call, + struct vctrs_arg* p_times_arg); static inline bool multiply_would_overflow(r_ssize x, r_ssize y); @@ -20,28 +23,35 @@ static inline void stop_rep_size_oob(struct r_lazy call); static -r_obj* vec_rep_each_uniform(r_obj* x, int times, struct r_lazy call); +r_obj* vec_rep_each_uniform(r_obj* x, + int times, + struct r_lazy call, + struct vctrs_arg* p_times_arg); static -r_obj* vec_rep_each_impl(r_obj* x, r_obj* times, const r_ssize times_size, struct r_lazy call); +r_obj* vec_rep_each_impl(r_obj* x, + r_obj* times, + const r_ssize times_size, + struct r_lazy call, + struct vctrs_arg* p_times_arg); static inline -void stop_rep_times_negative(struct r_lazy call); +void stop_rep_times_negative(struct r_lazy call, struct vctrs_arg* p_times_arg); static inline -void stop_rep_times_missing(struct r_lazy call); +void stop_rep_times_missing(struct r_lazy call, struct vctrs_arg* p_times_arg); static inline -void stop_rep_times_oob(int times, struct r_lazy call); +void stop_rep_times_oob(int times, struct r_lazy call, struct vctrs_arg* p_times_arg); static inline -void stop_rep_each_times_negative(r_ssize i, struct r_lazy call); +void stop_rep_each_times_negative(r_ssize i, struct r_lazy call, struct vctrs_arg* p_times_arg); static inline -void stop_rep_each_times_missing(r_ssize i, struct r_lazy call); +void stop_rep_each_times_missing(r_ssize i, struct r_lazy call, struct vctrs_arg* p_times_arg); static inline -void stop_rep_each_times_oob(int times, r_ssize i, struct r_lazy call); +void stop_rep_each_times_oob(int times, r_ssize i, struct r_lazy call, struct vctrs_arg* p_times_arg); static r_obj* vec_unrep(r_obj* x); diff --git a/src/globals.c b/src/globals.c index 845be29d4..dc17c3804 100644 --- a/src/globals.c +++ b/src/globals.c @@ -41,6 +41,7 @@ void vctrs_init_globals(r_obj* ns) { syms.haystack_arg = r_sym("haystack_arg"); syms.needles_arg = r_sym("needles_arg"); syms.repair_arg = r_sym("repair_arg"); + syms.times_arg = r_sym("times_arg"); syms.to_arg = r_sym("to_arg"); syms.value_arg = r_sym("value_arg"); syms.x_arg = r_sym("x_arg"); diff --git a/src/globals.h b/src/globals.h index d0673f823..80eb5661c 100644 --- a/src/globals.h +++ b/src/globals.h @@ -2,7 +2,6 @@ #define VCTRS_GLOBALS_H #include -#include "globals.h" #include "rlang-dev.h" struct syms { @@ -12,6 +11,7 @@ struct syms { r_obj* haystack_arg; r_obj* needles_arg; r_obj* repair_arg; + r_obj* times_arg; r_obj* to_arg; r_obj* value_arg; r_obj* vec_default_cast; diff --git a/src/rep.c b/src/rep.c index 788ab8a7e..90a366f4d 100644 --- a/src/rep.c +++ b/src/rep.c @@ -2,11 +2,16 @@ #include "vctrs.h" #include "type-data-frame.h" #include "decl/rep-decl.h" +#include "vec.h" static -r_obj* vec_rep(r_obj* x, int times, struct r_lazy call) { - check_rep_times(times, call); +r_obj* vec_rep(r_obj* x, + int times, + struct r_lazy call, + struct vctrs_arg* p_x_arg, + struct vctrs_arg* p_times_arg) { + check_rep_times(times, call, p_times_arg); if (times == 1) { return x; @@ -16,7 +21,7 @@ r_obj* vec_rep(r_obj* x, int times, struct r_lazy call) { const r_ssize x_size = vec_size(x); if (x_size == 1) { - return vec_check_recycle(x, times_, p_args_times, r_lazy_null); + return vec_check_recycle(x, times_, p_x_arg, call); } if (multiply_would_overflow(x_size, times_)) { @@ -45,18 +50,24 @@ r_obj* vec_rep(r_obj* x, int times, struct r_lazy call) { r_obj* ffi_vec_rep(r_obj* x, r_obj* ffi_times, r_obj* frame) { struct r_lazy call = { .x = r_syms.call, .env = frame }; + struct r_lazy x_arg_lazy = { .x = syms.x_arg, .env = frame }; + struct vctrs_arg x_arg = new_lazy_arg(&x_arg_lazy); + + struct r_lazy times_arg_lazy = { .x = syms.times_arg, .env = frame }; + struct vctrs_arg times_arg = new_lazy_arg(×_arg_lazy); + ffi_times = KEEP(vec_cast(ffi_times, r_globals.empty_int, - p_args_times, + ×_arg, vec_args.empty, call)); if (vec_size(ffi_times) != 1) { - stop_rep_times_size(call); + stop_rep_times_size(call, ×_arg); } const int times = r_int_get(ffi_times, 0); - r_obj* out = vec_rep(x, times, call); + r_obj* out = vec_rep(x, times, call, &x_arg, ×_arg); FREE(1); return out; @@ -66,10 +77,14 @@ r_obj* ffi_vec_rep(r_obj* x, r_obj* ffi_times, r_obj* frame) { // ----------------------------------------------------------------------------- static -r_obj* vec_rep_each(r_obj* x, r_obj* times, struct r_lazy call) { +r_obj* vec_rep_each(r_obj* x, + r_obj* times, + struct r_lazy call, + struct vctrs_arg* p_x_arg, + struct vctrs_arg* p_times_arg) { times = KEEP(vec_cast(times, r_globals.empty_int, - p_args_times, + p_times_arg, vec_args.empty, call)); @@ -83,12 +98,12 @@ r_obj* vec_rep_each(r_obj* x, r_obj* times, struct r_lazy call) { if (times_ == 1) { out = x; } else if (times_ == 0) { - out = vec_ptype(x, vec_args.empty, r_lazy_null); + out = vec_ptype(x, p_x_arg, call); } else { - out = vec_rep_each_uniform(x, times_, call); + out = vec_rep_each_uniform(x, times_, call, p_times_arg); } } else { - out = vec_rep_each_impl(x, times, times_size, call); + out = vec_rep_each_impl(x, times, times_size, call, p_times_arg); } FREE(1); @@ -97,15 +112,25 @@ r_obj* vec_rep_each(r_obj* x, r_obj* times, struct r_lazy call) { r_obj* ffi_vec_rep_each(r_obj* x, r_obj* times, r_obj* frame) { struct r_lazy call = { .x = r_syms.call, .env = frame }; - return vec_rep_each(x, times, call); + + struct r_lazy x_arg_lazy = { .x = syms.times_arg, .env = frame }; + struct vctrs_arg x_arg = new_lazy_arg(&x_arg_lazy); + + struct r_lazy times_arg_lazy = { .x = syms.times_arg, .env = frame }; + struct vctrs_arg times_arg = new_lazy_arg(×_arg_lazy); + + return vec_rep_each(x, times, call, &x_arg, ×_arg); } // ----------------------------------------------------------------------------- static -r_obj* vec_rep_each_uniform(r_obj* x, int times, struct r_lazy call) { - check_rep_each_times(times, 1, call); +r_obj* vec_rep_each_uniform(r_obj* x, + int times, + struct r_lazy call, + struct vctrs_arg* p_times_arg) { + check_rep_each_times(times, 1, call, p_times_arg); const r_ssize times_ = (r_ssize) times; const r_ssize x_size = vec_size(x); @@ -136,13 +161,14 @@ r_obj* vec_rep_each_uniform(r_obj* x, int times, struct r_lazy call) { static r_obj* vec_rep_each_impl(r_obj* x, r_obj* times, const r_ssize times_size, - struct r_lazy call) { + struct r_lazy call, + struct vctrs_arg* p_times_arg) { const r_ssize x_size = vec_size(x); if (x_size != times_size) { stop_recycle_incompatible_size(times_size, x_size, - p_args_times, + p_times_arg, call); } @@ -152,7 +178,7 @@ static r_obj* vec_rep_each_impl(r_obj* x, for (r_ssize i = 0; i < times_size; ++i) { const int elt_times = v_times[i]; - check_rep_each_times(elt_times, i + 1, call); + check_rep_each_times(elt_times, i + 1, call, p_times_arg); const r_ssize elt_times_ = (r_ssize) elt_times; @@ -208,35 +234,45 @@ bool plus_would_overflow(r_ssize x, r_ssize y) { // ----------------------------------------------------------------------------- static inline -void check_rep_times(int times, struct r_lazy call) { +void check_rep_times(int times, + struct r_lazy call, + struct vctrs_arg* p_times_arg) { if (times < 0) { if (times == r_globals.na_int) { - stop_rep_times_missing(call); + stop_rep_times_missing(call, p_times_arg); } else { - stop_rep_times_negative(call); + stop_rep_times_negative(call, p_times_arg); } } else if (times_is_oob(times)) { - stop_rep_times_oob(times, call); + stop_rep_times_oob(times, call, p_times_arg); } } static inline -void stop_rep_times_negative(struct r_lazy call) { - r_abort_lazy_call(call, "`times` must be a positive number."); +void stop_rep_times_negative(struct r_lazy call, struct vctrs_arg* p_times_arg) { + r_obj* times_arg = KEEP(vctrs_arg(p_times_arg)); + r_abort_lazy_call(call, + "`%s` must be a positive number.", + r_chr_get_c_string(times_arg, 0)); } static inline -void stop_rep_times_missing(struct r_lazy call) { - r_abort_lazy_call(call, "`times` can't be missing."); +void stop_rep_times_missing(struct r_lazy call, struct vctrs_arg* p_times_arg) { + r_obj* times_arg = KEEP(vctrs_arg(p_times_arg)); + r_abort_lazy_call(call, + "`%s` can't be missing.", + r_chr_get_c_string(times_arg, 0)); } // Not currently thrown since `r_ssize == int`, but might be once // long vectors are supported static inline -void stop_rep_times_oob(int times, struct r_lazy call) { +void stop_rep_times_oob(int times, struct r_lazy call, struct vctrs_arg* p_times_arg) { + r_obj* times_arg = KEEP(vctrs_arg(p_times_arg)); r_abort_lazy_call( call, - "`times` must be less than %i, not %i.", + "`%s` must be less than %i, not %i.", + r_chr_get_c_string(times_arg, 0), R_LEN_T_MAX, times ); @@ -246,36 +282,49 @@ void stop_rep_times_oob(int times, struct r_lazy call) { // ----------------------------------------------------------------------------- static inline -void check_rep_each_times(int times, r_ssize i, struct r_lazy call) { +void check_rep_each_times(int times, + r_ssize i, + struct r_lazy call, + struct vctrs_arg* p_times_arg) { if (times < 0) { if (times == r_globals.na_int) { - stop_rep_each_times_missing(i, call); + stop_rep_each_times_missing(i, call, p_times_arg); } else { - stop_rep_each_times_negative(i, call); + stop_rep_each_times_negative(i, call, p_times_arg); } } else if (times_is_oob(times)) { - stop_rep_each_times_oob(times, i, call); + stop_rep_each_times_oob(times, i, call, p_times_arg); } } static inline -void stop_rep_each_times_negative(r_ssize i, struct r_lazy call) { - r_abort_lazy_call(call, "`times` must be a vector of positive numbers. Location %i is negative.", i); +void stop_rep_each_times_negative(r_ssize i, struct r_lazy call, struct vctrs_arg* p_times_arg) { + r_obj* times_arg = KEEP(vctrs_arg(p_times_arg)); + r_abort_lazy_call(call, + "`%s` must be a vector of positive numbers. Location %i is negative.", + r_chr_get_c_string(times_arg, 0), + i); } static inline -void stop_rep_each_times_missing(r_ssize i, struct r_lazy call) { - r_abort_lazy_call(call, "`times` can't be missing. Location %i is missing.", i); +void stop_rep_each_times_missing(r_ssize i, struct r_lazy call, struct vctrs_arg* p_times_arg) { + r_obj* times_arg = KEEP(vctrs_arg(p_times_arg)); + r_abort_lazy_call(call, + "`%s` can't be missing. Location %i is missing.", + r_chr_get_c_string(times_arg, 0), + i); } // Not currently thrown since `r_ssize == int`, but might be once // long vectors are supported static inline -void stop_rep_each_times_oob(int times, r_ssize i, struct r_lazy call) { +void stop_rep_each_times_oob(int times, r_ssize i, struct r_lazy call, struct vctrs_arg* p_times_arg) { + r_obj* times_arg = KEEP(vctrs_arg(p_times_arg)); r_abort_lazy_call( call, - "`times` must be less than %i, not %i. ", + "`%s` must be less than %i, not %i. ", "Location %i is too large.", + r_chr_get_c_string(times_arg, 0), R_LEN_T_MAX, times, i @@ -293,8 +342,12 @@ void stop_rep_size_oob(struct r_lazy call) { } static inline -void stop_rep_times_size(struct r_lazy call) { - r_abort_lazy_call(call, "`times` must be a single number."); +void stop_rep_times_size(struct r_lazy call, + struct vctrs_arg* p_times_arg) { + r_obj* times_arg = KEEP(vctrs_arg(p_times_arg)); + r_abort_lazy_call(call, + "`%s` must be a single number.", + r_chr_get_c_string(times_arg, 0)); } @@ -387,9 +440,4 @@ r_obj* new_unrep_data_frame(r_obj* key, r_obj* times, r_ssize size) { // ----------------------------------------------------------------------------- -void vctrs_init_rep(r_obj* ns) { - args_times_ = new_wrapper_arg(NULL, "times"); -} - -static -struct vctrs_arg* const p_args_times = &args_times_; +void vctrs_init_rep(r_obj* ns) { } diff --git a/tests/testthat/_snaps/rep.md b/tests/testthat/_snaps/rep.md index 0ae49d620..26ff74c4d 100644 --- a/tests/testthat/_snaps/rep.md +++ b/tests/testthat/_snaps/rep.md @@ -1,80 +1,150 @@ # `vec_rep()` validates `times` Code - vec_rep(1, "x") + (expect_error(my_vec_rep(1, "x"), class = "vctrs_error_incompatible_type")) + Output + + Error in `my_vec_rep()`: + ! Can't convert `my_times` to . + Code + (expect_error(my_vec_rep(1, c(1, 2)))) + Output + + Error in `my_vec_rep()`: + ! `my_times` must be a single number. + Code + (expect_error(my_vec_rep(1, -1))) + Output + + Error in `my_vec_rep()`: + ! `my_times` must be a positive number. + Code + (expect_error(my_vec_rep(1, NA_integer_))) + Output + + Error in `my_vec_rep()`: + ! `my_times` can't be missing. + +--- + + Code + my_vec_rep(1, "x") Condition - Error in `vec_rep()`: - ! Can't convert `times` to . + Error in `my_vec_rep()`: + ! Can't convert `my_times` to . --- Code - vec_rep(1, c(1, 2)) + my_vec_rep(1, c(1, 2)) Condition - Error in `vec_rep()`: - ! `times` must be a single number. + Error in `my_vec_rep()`: + ! `my_times` must be a single number. --- Code - vec_rep(1, -1) + my_vec_rep(1, -1) Condition - Error in `vec_rep()`: - ! `times` must be a positive number. + Error in `my_vec_rep()`: + ! `my_times` must be a positive number. --- Code - vec_rep(1, NA_integer_) + my_vec_rep(1, NA_integer_) Condition - Error in `vec_rep()`: - ! `times` can't be missing. + Error in `my_vec_rep()`: + ! `my_times` can't be missing. # `vec_rep_each()` validates `times` Code - vec_rep_each(1, "x") + (expect_error(my_vec_rep_each(1, "x"), class = "vctrs_error_incompatible_type")) + Output + + Error in `my_vec_rep_each()`: + ! Can't convert `my_times` to . + Code + (expect_error(my_vec_rep_each(1, -1))) + Output + + Error in `my_vec_rep_each()`: + ! `my_times` must be a vector of positive numbers. Location 1 is negative. + Code + (expect_error(my_vec_rep_each(c(1, 2), c(1, -1)))) + Output + + Error in `my_vec_rep_each()`: + ! `my_times` must be a vector of positive numbers. Location 2 is negative. + Code + (expect_error(my_vec_rep_each(1, NA_integer_))) + Output + + Error in `my_vec_rep_each()`: + ! `my_times` can't be missing. Location 1 is missing. + Code + (expect_error(my_vec_rep_each(c(1, 2), c(1, NA_integer_)))) + Output + + Error in `my_vec_rep_each()`: + ! `my_times` can't be missing. Location 2 is missing. + +--- + + Code + my_vec_rep_each(1, "x") Condition - Error in `vec_rep_each()`: - ! Can't convert `times` to . + Error in `my_vec_rep_each()`: + ! Can't convert `my_times` to . --- Code - vec_rep_each(1, -1) + my_vec_rep_each(1, -1) Condition - Error in `vec_rep_each()`: - ! `times` must be a vector of positive numbers. Location 1 is negative. + Error in `my_vec_rep_each()`: + ! `my_times` must be a vector of positive numbers. Location 1 is negative. --- Code - vec_rep_each(c(1, 2), c(1, -1)) + my_vec_rep_each(c(1, 2), c(1, -1)) Condition - Error in `vec_rep_each()`: - ! `times` must be a vector of positive numbers. Location 2 is negative. + Error in `my_vec_rep_each()`: + ! `my_times` must be a vector of positive numbers. Location 2 is negative. --- Code - vec_rep_each(1, NA_integer_) + my_vec_rep_each(1, NA_integer_) Condition - Error in `vec_rep_each()`: - ! `times` can't be missing. Location 1 is missing. + Error in `my_vec_rep_each()`: + ! `my_times` can't be missing. Location 1 is missing. --- Code - vec_rep_each(c(1, 2), c(1, NA_integer_)) + my_vec_rep_each(c(1, 2), c(1, NA_integer_)) Condition - Error in `vec_rep_each()`: - ! `times` can't be missing. Location 2 is missing. + Error in `my_vec_rep_each()`: + ! `my_times` can't be missing. Location 2 is missing. # `vec_rep_each()` uses recyclying errors Code - vec_rep_each(1:2, 1:3) + (expect_error(my_vec_rep_each(1:2, 1:3), class = "vctrs_error_recycle_incompatible_size") + ) + Output + + Error in `my_vec_rep_each()`: + ! Can't recycle `my_times` (size 3) to size 2. + +--- + + Code + my_vec_rep_each(1:2, 1:3) Condition - Error in `vec_rep_each()`: - ! Can't recycle `times` (size 3) to size 2. + Error in `my_vec_rep_each()`: + ! Can't recycle `my_times` (size 3) to size 2. diff --git a/tests/testthat/helper-conditions.R b/tests/testthat/helper-conditions.R index 2290ad4c3..fc47029b6 100644 --- a/tests/testthat/helper-conditions.R +++ b/tests/testthat/helper-conditions.R @@ -55,3 +55,23 @@ with_tidyselect_relocate <- function(expr) { subscript_action = "relocate" ) } + +my_vec_rep <- function(my_x, my_times) { + vec_rep( + my_x, + my_times, + call = current_env(), + x_arg = "my_x", + times_arg = "my_times" + ) +} + +my_vec_rep_each <- function(my_x, my_times) { + vec_rep_each( + my_x, + my_times, + call = current_env(), + x_arg = "my_x", + times_arg = "my_times" + ) +} diff --git a/tests/testthat/test-rep.R b/tests/testthat/test-rep.R index 89b71d4bb..ea6daaa0c 100644 --- a/tests/testthat/test-rep.R +++ b/tests/testthat/test-rep.R @@ -29,10 +29,12 @@ test_that("`vec_rep()` errors on long vector output", { }) test_that("`vec_rep()` validates `times`", { - expect_error(vec_rep(1, "x"), class = "vctrs_error_incompatible_type") - expect_error(vec_rep(1, c(1, 2))) - expect_error(vec_rep(1, -1)) - expect_error(vec_rep(1, NA_integer_)) + expect_snapshot({ + (expect_error(my_vec_rep(1, "x"), class = "vctrs_error_incompatible_type")) + (expect_error(my_vec_rep(1, c(1, 2)))) + (expect_error(my_vec_rep(1, -1))) + (expect_error(my_vec_rep(1, NA_integer_))) + }) }) # ------------------------------------------------------------------------------ @@ -66,36 +68,40 @@ test_that("`vec_rep_each()` errors on long vector output", { }) test_that("`vec_rep_each()` validates `times`", { - expect_error(vec_rep_each(1, "x"), class = "vctrs_error_incompatible_type") - expect_error(vec_rep_each(1, -1)) - expect_error(vec_rep_each(c(1, 2), c(1, -1))) - expect_error(vec_rep_each(1, NA_integer_)) - expect_error(vec_rep_each(c(1, 2), c(1, NA_integer_))) + expect_snapshot({ + (expect_error(my_vec_rep_each(1, "x"), class = "vctrs_error_incompatible_type")) + (expect_error(my_vec_rep_each(1, -1))) + (expect_error(my_vec_rep_each(c(1, 2), c(1, -1)))) + (expect_error(my_vec_rep_each(1, NA_integer_))) + (expect_error(my_vec_rep_each(c(1, 2), c(1, NA_integer_)))) + }) }) test_that("`vec_rep_each()` uses recyclying errors", { - expect_error(vec_rep_each(1:2, 1:3), class = "vctrs_error_recycle_incompatible_size") + expect_snapshot({ + (expect_error(my_vec_rep_each(1:2, 1:3), class = "vctrs_error_recycle_incompatible_size")) + }) }) # ------------------------------------------------------------------------------ test_that("`vec_rep()` validates `times`", { - expect_snapshot(error = TRUE, vec_rep(1, "x")) - expect_snapshot(error = TRUE, vec_rep(1, c(1, 2))) - expect_snapshot(error = TRUE, vec_rep(1, -1)) - expect_snapshot(error = TRUE, vec_rep(1, NA_integer_)) + expect_snapshot(error = TRUE, my_vec_rep(1, "x")) + expect_snapshot(error = TRUE, my_vec_rep(1, c(1, 2))) + expect_snapshot(error = TRUE, my_vec_rep(1, -1)) + expect_snapshot(error = TRUE, my_vec_rep(1, NA_integer_)) }) test_that("`vec_rep_each()` validates `times`", { - expect_snapshot(error = TRUE, vec_rep_each(1, "x")) - expect_snapshot(error = TRUE, vec_rep_each(1, -1)) - expect_snapshot(error = TRUE, vec_rep_each(c(1, 2), c(1, -1))) - expect_snapshot(error = TRUE, vec_rep_each(1, NA_integer_)) - expect_snapshot(error = TRUE, vec_rep_each(c(1, 2), c(1, NA_integer_))) + expect_snapshot(error = TRUE, my_vec_rep_each(1, "x")) + expect_snapshot(error = TRUE, my_vec_rep_each(1, -1)) + expect_snapshot(error = TRUE, my_vec_rep_each(c(1, 2), c(1, -1))) + expect_snapshot(error = TRUE, my_vec_rep_each(1, NA_integer_)) + expect_snapshot(error = TRUE, my_vec_rep_each(c(1, 2), c(1, NA_integer_))) }) test_that("`vec_rep_each()` uses recyclying errors", { - expect_snapshot(error = TRUE, vec_rep_each(1:2, 1:3)) + expect_snapshot(error = TRUE, my_vec_rep_each(1:2, 1:3)) }) # vec_unrep -------------------------------------------------------------------- From 9180faea1989fb4612c23d094c7bc2e018bcc77d Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Wed, 14 Sep 2022 18:42:10 +0200 Subject: [PATCH 055/312] Take empty dots in `vec_rep()` and `vec_rep_each()` --- R/rep.R | 7 ++++++- man/vec-rep.Rd | 13 +++++++++++-- 2 files changed, 17 insertions(+), 3 deletions(-) diff --git a/R/rep.R b/R/rep.R index b6f3b6d61..c86ac6a53 100644 --- a/R/rep.R +++ b/R/rep.R @@ -28,6 +28,8 @@ #' length. This means that `vec_unrep()` works on data frames by compressing #' repeated rows. #' +#' @inheritParams rlang::args_error_context +#' @inheritParams rlang::args_dots_empty #' @param x A vector. #' @param times #' For `vec_rep()`, a single integer for the number of times to repeat @@ -36,7 +38,6 @@ #' For `vec_rep_each()`, an integer vector of the number of times to repeat #' each element of `x`. `times` will be [recycled][vector_recycling_rules] to #' the size of `x`. -#' @inheritParams rlang::args_error_context #' @param x_arg,times_arg Argument names for errors. #' #' @return @@ -87,9 +88,11 @@ NULL #' @export vec_rep <- function(x, times, + ..., call = current_env(), x_arg = "x", times_arg = "times") { + check_dots_empty0(...) .Call(ffi_vec_rep, x, times, environment()) } @@ -97,9 +100,11 @@ vec_rep <- function(x, #' @export vec_rep_each <- function(x, times, + ..., call = current_env(), x_arg = "x", times_arg = "times") { + check_dots_empty0(...) .Call(ffi_vec_rep_each, x, times, environment()) } diff --git a/man/vec-rep.Rd b/man/vec-rep.Rd index c5b6ef413..f28e3aa5d 100644 --- a/man/vec-rep.Rd +++ b/man/vec-rep.Rd @@ -7,9 +7,16 @@ \alias{vec_unrep} \title{Repeat a vector} \usage{ -vec_rep(x, times, call = current_env(), x_arg = "x", times_arg = "times") +vec_rep(x, times, ..., call = current_env(), x_arg = "x", times_arg = "times") -vec_rep_each(x, times, call = current_env(), x_arg = "x", times_arg = "times") +vec_rep_each( + x, + times, + ..., + call = current_env(), + x_arg = "x", + times_arg = "times" +) vec_unrep(x) } @@ -23,6 +30,8 @@ For \code{vec_rep_each()}, an integer vector of the number of times to repeat each element of \code{x}. \code{times} will be \link[=vector_recycling_rules]{recycled} to the size of \code{x}.} +\item{...}{These dots are for future extensions and must be empty.} + \item{call}{The execution environment of a currently running function, e.g. \code{caller_env()}. The function will be mentioned in error messages as the source of the error. See the From 53542f9d35011f7e6975d96f92948d83398a93ed Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Wed, 14 Sep 2022 18:42:54 +0200 Subject: [PATCH 056/312] Remove redundant headers --- src/rep.c | 2 -- 1 file changed, 2 deletions(-) diff --git a/src/rep.c b/src/rep.c index 90a366f4d..6fc28621b 100644 --- a/src/rep.c +++ b/src/rep.c @@ -1,8 +1,6 @@ -#include "rlang.h" #include "vctrs.h" #include "type-data-frame.h" #include "decl/rep-decl.h" -#include "vec.h" static From facb752cd3da921a0d4c2a0d139df4a036d1c13e Mon Sep 17 00:00:00 2001 From: Davis Vaughan Date: Wed, 14 Sep 2022 13:14:38 -0400 Subject: [PATCH 057/312] Update style in `compare.c` (#1658) --- R/compare.R | 2 +- src/compare.c | 156 ++++++++++++++++------------------ src/compare.h | 2 +- src/decl/compare-decl.h | 16 ++++ src/init.c | 4 +- tests/testthat/test-compare.R | 12 +-- 6 files changed, 99 insertions(+), 93 deletions(-) create mode 100644 src/decl/compare-decl.h diff --git a/R/compare.R b/R/compare.R index 785e27d90..0ff533c57 100644 --- a/R/compare.R +++ b/R/compare.R @@ -131,7 +131,7 @@ vec_compare <- function(x, y, na_equal = FALSE, .ptype = NULL) { .df_fallback = DF_FALLBACK_quiet ) - .Call(vctrs_compare, vec_proxy_compare(args[[1]]), vec_proxy_compare(args[[2]]), na_equal) + .Call(ffi_vec_compare, vec_proxy_compare(args[[1]]), vec_proxy_compare(args[[2]]), na_equal) } diff --git a/src/compare.c b/src/compare.c index 53401d89c..4a76ad030 100644 --- a/src/compare.c +++ b/src/compare.c @@ -1,65 +1,65 @@ #include "vctrs.h" #include -static void stop_not_comparable(SEXP x, SEXP y, const char* message) { +#include "decl/compare-decl.h" + +static +void stop_not_comparable(r_obj* x, r_obj* y, const char* message) { r_abort("`x` and `y` are not comparable: %s", message); } // ----------------------------------------------------------------------------- -static SEXP df_compare(SEXP x, SEXP y, bool na_equal, R_len_t size); - -#define COMPARE(CTYPE, CONST_DEREF, SCALAR_COMPARE) \ +#define COMPARE(CTYPE, CBEGIN, SCALAR_COMPARE) \ do { \ - SEXP out = PROTECT(Rf_allocVector(INTSXP, size)); \ - int* p_out = INTEGER(out); \ + r_obj* out = KEEP(r_alloc_integer(size)); \ + int* v_out = r_int_begin(out); \ \ - const CTYPE* p_x = CONST_DEREF(x); \ - const CTYPE* p_y = CONST_DEREF(y); \ + CTYPE const* v_x = CBEGIN(x); \ + CTYPE const* v_y = CBEGIN(y); \ \ - for (R_len_t i = 0; i < size; ++i) { \ - p_out[i] = SCALAR_COMPARE(p_x[i], p_y[i]); \ + for (r_ssize i = 0; i < size; ++i) { \ + v_out[i] = SCALAR_COMPARE(v_x[i], v_y[i]); \ } \ \ - UNPROTECT(3); \ + FREE(3); \ return out; \ } \ while (0) -// [[ include("compare.h") ]] -SEXP vec_compare(SEXP x, SEXP y, bool na_equal) { - R_len_t size = vec_size(x); +r_obj* vec_compare(r_obj* x, r_obj* y, bool na_equal) { + r_ssize size = vec_size(x); enum vctrs_type type = vec_proxy_typeof(x); if (type != vec_proxy_typeof(y) || size != vec_size(y)) { stop_not_comparable(x, y, "must have the same types and lengths"); } - x = PROTECT(vec_normalize_encoding(x)); - y = PROTECT(vec_normalize_encoding(y)); + x = KEEP(vec_normalize_encoding(x)); + y = KEEP(vec_normalize_encoding(y)); if (type == VCTRS_TYPE_dataframe) { - SEXP out = df_compare(x, y, na_equal, size); - UNPROTECT(2); + r_obj* out = df_compare(x, y, na_equal, size); + FREE(2); return out; } if (na_equal) { switch (type) { - case VCTRS_TYPE_logical: COMPARE(int, LOGICAL_RO, lgl_compare_na_equal); - case VCTRS_TYPE_integer: COMPARE(int, INTEGER_RO, int_compare_na_equal); - case VCTRS_TYPE_double: COMPARE(double, REAL_RO, dbl_compare_na_equal); - case VCTRS_TYPE_character: COMPARE(SEXP, STRING_PTR_RO, chr_compare_na_equal); + case VCTRS_TYPE_logical: COMPARE(int, r_lgl_cbegin, lgl_compare_na_equal); + case VCTRS_TYPE_integer: COMPARE(int, r_int_cbegin, int_compare_na_equal); + case VCTRS_TYPE_double: COMPARE(double, r_dbl_cbegin, dbl_compare_na_equal); + case VCTRS_TYPE_character: COMPARE(r_obj*, r_chr_cbegin, chr_compare_na_equal); case VCTRS_TYPE_scalar: r_abort("Can't compare scalars with `vec_compare()`"); case VCTRS_TYPE_list: r_abort("Can't compare lists with `vec_compare()`"); default: stop_unimplemented_vctrs_type("vec_compare", type); } } else { switch (type) { - case VCTRS_TYPE_logical: COMPARE(int, LOGICAL_RO, lgl_compare_na_propagate); - case VCTRS_TYPE_integer: COMPARE(int, INTEGER_RO, int_compare_na_propagate); - case VCTRS_TYPE_double: COMPARE(double, REAL_RO, dbl_compare_na_propagate); - case VCTRS_TYPE_character: COMPARE(SEXP, STRING_PTR_RO, chr_compare_na_propagate); + case VCTRS_TYPE_logical: COMPARE(int, r_lgl_cbegin, lgl_compare_na_propagate); + case VCTRS_TYPE_integer: COMPARE(int, r_int_cbegin, int_compare_na_propagate); + case VCTRS_TYPE_double: COMPARE(double, r_dbl_cbegin, dbl_compare_na_propagate); + case VCTRS_TYPE_character: COMPARE(r_obj*, r_chr_cbegin, chr_compare_na_propagate); case VCTRS_TYPE_scalar: r_abort("Can't compare scalars with `vec_compare()`"); case VCTRS_TYPE_list: r_abort("Can't compare lists with `vec_compare()`"); default: stop_unimplemented_vctrs_type("vec_compare", type); @@ -69,62 +69,51 @@ SEXP vec_compare(SEXP x, SEXP y, bool na_equal) { #undef COMPARE -// [[ register() ]] -SEXP vctrs_compare(SEXP x, SEXP y, SEXP na_equal) { - const bool c_na_equal = r_bool_as_int(na_equal); - return vec_compare(x, y, c_na_equal); +r_obj* ffi_vec_compare(r_obj* x, r_obj* y, r_obj* ffi_na_equal) { + const bool na_equal = r_bool_as_int(ffi_na_equal); + return vec_compare(x, y, na_equal); } // ----------------------------------------------------------------------------- -static void vec_compare_col(int* p_out, - struct df_short_circuit_info* p_info, - SEXP x, - SEXP y, - bool na_equal); - -static void df_compare_impl(int* p_out, - struct df_short_circuit_info* p_info, - SEXP x, - SEXP y, - bool na_equal); - -static SEXP df_compare(SEXP x, SEXP y, bool na_equal, R_len_t size) { +static +r_obj* df_compare(r_obj* x, r_obj* y, bool na_equal, r_ssize size) { int nprot = 0; - SEXP out = PROTECT_N(Rf_allocVector(INTSXP, size), &nprot); - int* p_out = INTEGER(out); + r_obj* out = KEEP_N(r_alloc_integer(size), &nprot); + int* v_out = r_int_begin(out); // Initialize to "equality" value and only change if we learn that it differs. // This also determines the zero column result. - memset(p_out, 0, size * sizeof(int)); + memset(v_out, 0, size * sizeof(int)); struct df_short_circuit_info info = new_df_short_circuit_info(size, false); struct df_short_circuit_info* p_info = &info; PROTECT_DF_SHORT_CIRCUIT_INFO(p_info, &nprot); - df_compare_impl(p_out, p_info, x, y, na_equal); + df_compare_impl(v_out, p_info, x, y, na_equal); - UNPROTECT(nprot); + FREE(nprot); return out; } -static void df_compare_impl(int* p_out, - struct df_short_circuit_info* p_info, - SEXP x, - SEXP y, - bool na_equal) { - int n_col = Rf_length(x); +static +void df_compare_impl(int* v_out, + struct df_short_circuit_info* p_info, + r_obj* x, + r_obj* y, + bool na_equal) { + r_ssize n_col = r_length(x); - if (n_col != Rf_length(y)) { + if (n_col != r_length(y)) { stop_not_comparable(x, y, "must have the same number of columns"); } - for (R_len_t i = 0; i < n_col; ++i) { - SEXP x_col = VECTOR_ELT(x, i); - SEXP y_col = VECTOR_ELT(y, i); + for (r_ssize i = 0; i < n_col; ++i) { + r_obj* x_col = r_list_get(x, i); + r_obj* y_col = r_list_get(y, i); - vec_compare_col(p_out, p_info, x_col, y_col, na_equal); + vec_compare_col(v_out, p_info, x_col, y_col, na_equal); // If we know all comparison values, break if (p_info->remaining == 0) { @@ -135,20 +124,20 @@ static void df_compare_impl(int* p_out, // ----------------------------------------------------------------------------- -#define COMPARE_COL(CTYPE, CONST_DEREF, SCALAR_COMPARE) \ +#define COMPARE_COL(CTYPE, CBEGIN, SCALAR_COMPARE) \ do { \ - const CTYPE* p_x = CONST_DEREF(x); \ - const CTYPE* p_y = CONST_DEREF(y); \ + CTYPE const* v_x = CBEGIN(x); \ + CTYPE const* v_y = CBEGIN(y); \ \ - for (R_len_t i = 0; i < p_info->size; ++i) { \ + for (r_ssize i = 0; i < p_info->size; ++i) { \ if (p_info->p_row_known[i]) { \ continue; \ } \ \ - int cmp = SCALAR_COMPARE(p_x[i], p_y[i]); \ + int cmp = SCALAR_COMPARE(v_x[i], v_y[i]); \ \ if (cmp != 0) { \ - p_out[i] = cmp; \ + v_out[i] = cmp; \ p_info->p_row_known[i] = true; \ --p_info->remaining; \ \ @@ -160,36 +149,37 @@ do { \ } \ while (0) -static void vec_compare_col(int* p_out, - struct df_short_circuit_info* p_info, - SEXP x, - SEXP y, - bool na_equal) { +static +void vec_compare_col(int* v_out, + struct df_short_circuit_info* p_info, + r_obj* x, + r_obj* y, + bool na_equal) { enum vctrs_type type = vec_proxy_typeof(x); if (type == VCTRS_TYPE_dataframe) { - df_compare_impl(p_out, p_info, x, y, na_equal); + df_compare_impl(v_out, p_info, x, y, na_equal); return; } if (na_equal) { switch (type) { - case VCTRS_TYPE_logical: COMPARE_COL(int, LOGICAL_RO, lgl_compare_na_equal); break; - case VCTRS_TYPE_integer: COMPARE_COL(int, INTEGER_RO, int_compare_na_equal); break; - case VCTRS_TYPE_double: COMPARE_COL(double, REAL_RO, dbl_compare_na_equal); break; - case VCTRS_TYPE_character: COMPARE_COL(SEXP, STRING_PTR_RO, chr_compare_na_equal); break; - case VCTRS_TYPE_scalar: r_abort("Can't compare scalars with `vctrs_compare()`"); - case VCTRS_TYPE_list: r_abort("Can't compare lists with `vctrs_compare()`"); + case VCTRS_TYPE_logical: COMPARE_COL(int, r_lgl_cbegin, lgl_compare_na_equal); break; + case VCTRS_TYPE_integer: COMPARE_COL(int, r_int_cbegin, int_compare_na_equal); break; + case VCTRS_TYPE_double: COMPARE_COL(double, r_dbl_cbegin, dbl_compare_na_equal); break; + case VCTRS_TYPE_character: COMPARE_COL(r_obj*, r_chr_cbegin, chr_compare_na_equal); break; + case VCTRS_TYPE_scalar: r_abort("Can't compare scalars with `vec_compare()`"); + case VCTRS_TYPE_list: r_abort("Can't compare lists with `vec_compare()`"); default: stop_unimplemented_vctrs_type("vec_compare_col", type); } } else { switch (type) { - case VCTRS_TYPE_logical: COMPARE_COL(int, LOGICAL_RO, lgl_compare_na_propagate); break; - case VCTRS_TYPE_integer: COMPARE_COL(int, INTEGER_RO, int_compare_na_propagate); break; - case VCTRS_TYPE_double: COMPARE_COL(double, REAL_RO, dbl_compare_na_propagate); break; - case VCTRS_TYPE_character: COMPARE_COL(SEXP, STRING_PTR_RO, chr_compare_na_propagate); break; - case VCTRS_TYPE_scalar: r_abort("Can't compare scalars with `vctrs_compare()`"); - case VCTRS_TYPE_list: r_abort("Can't compare lists with `vctrs_compare()`"); + case VCTRS_TYPE_logical: COMPARE_COL(int, r_lgl_cbegin, lgl_compare_na_propagate); break; + case VCTRS_TYPE_integer: COMPARE_COL(int, r_int_cbegin, int_compare_na_propagate); break; + case VCTRS_TYPE_double: COMPARE_COL(double, r_dbl_cbegin, dbl_compare_na_propagate); break; + case VCTRS_TYPE_character: COMPARE_COL(r_obj*, r_chr_cbegin, chr_compare_na_propagate); break; + case VCTRS_TYPE_scalar: r_abort("Can't compare scalars with `vec_compare()`"); + case VCTRS_TYPE_list: r_abort("Can't compare lists with `vec_compare()`"); default: stop_unimplemented_vctrs_type("vec_compare_col", type); } } diff --git a/src/compare.h b/src/compare.h index 162d095c9..02d02f6cf 100644 --- a/src/compare.h +++ b/src/compare.h @@ -8,7 +8,7 @@ // ----------------------------------------------------------------------------- -SEXP vec_compare(SEXP x, SEXP y, bool na_equal); +r_obj* vec_compare(r_obj* x, r_obj* y, bool na_equal); // ----------------------------------------------------------------------------- diff --git a/src/decl/compare-decl.h b/src/decl/compare-decl.h new file mode 100644 index 000000000..b43384d27 --- /dev/null +++ b/src/decl/compare-decl.h @@ -0,0 +1,16 @@ +static +r_obj* df_compare(r_obj* x, r_obj* y, bool na_equal, r_ssize size); + +static +void df_compare_impl(int* v_out, + struct df_short_circuit_info* p_info, + r_obj* x, + r_obj* y, + bool na_equal); + +static +void vec_compare_col(int* v_out, + struct df_short_circuit_info* p_info, + r_obj* x, + r_obj* y, + bool na_equal); diff --git a/src/init.c b/src/init.c index 035742f4a..2ef2377b9 100644 --- a/src/init.c +++ b/src/init.c @@ -30,7 +30,7 @@ extern SEXP vec_group_loc(SEXP); extern SEXP vctrs_equal(SEXP, SEXP, SEXP); extern r_obj* ffi_vec_equal_na(r_obj*); extern r_obj* ffi_vec_any_missing(r_obj* x); -extern SEXP vctrs_compare(SEXP, SEXP, SEXP); +extern r_obj* ffi_vec_compare(r_obj*, r_obj*, r_obj*); extern SEXP vctrs_match(SEXP, SEXP, SEXP, SEXP); extern r_obj* vctrs_in(r_obj*, r_obj*, r_obj*, r_obj*); extern SEXP vctrs_duplicated_any(SEXP); @@ -204,7 +204,7 @@ static const R_CallMethodDef CallEntries[] = { {"vctrs_equal", (DL_FUNC) &vctrs_equal, 3}, {"ffi_vec_equal_na", (DL_FUNC) &ffi_vec_equal_na, 1}, {"ffi_vec_any_missing", (DL_FUNC) &ffi_vec_any_missing, 1}, - {"vctrs_compare", (DL_FUNC) &vctrs_compare, 3}, + {"ffi_vec_compare", (DL_FUNC) &ffi_vec_compare, 3}, {"vctrs_match", (DL_FUNC) &vctrs_match, 4}, {"vctrs_in", (DL_FUNC) &vctrs_in, 4}, {"vctrs_typeof", (DL_FUNC) &vctrs_typeof, 2}, diff --git a/tests/testthat/test-compare.R b/tests/testthat/test-compare.R index 5b05e10ea..7a4207fff 100644 --- a/tests/testthat/test-compare.R +++ b/tests/testthat/test-compare.R @@ -89,16 +89,16 @@ test_that("can compare data frames with 0 columns", { test_that("C code doesn't crash with bad inputs", { df <- data.frame(x = c(1, 1, 1), y = c(-1, 0, 1)) - expect_error(.Call(vctrs_compare, df, df[1], TRUE), "not comparable") + expect_error(.Call(ffi_vec_compare, df, df[1], TRUE), "not comparable") # Names are not checked, as `vec_cast_common()` should take care of the type. # So if `vec_cast_common()` is not called, or is improperly specified, then # this could result in false equality. - expect_equal(.Call(vctrs_compare, df, setNames(df, c("x", "z")), TRUE), c(0, 0, 0)) + expect_equal(.Call(ffi_vec_compare, df, setNames(df, c("x", "z")), TRUE), c(0, 0, 0)) df1 <- new_data_frame(list(x = 1:3, y = c(1, 1, 1))) df2 <- new_data_frame(list(y = 1:2, x = 1:2)) - expect_error(.Call(vctrs_compare, df1, df2, TRUE), "must have the same types and lengths") + expect_error(.Call(ffi_vec_compare, df1, df2, TRUE), "must have the same types and lengths") }) test_that("xtfrm.vctrs_vctr works for variety of base classes", { @@ -202,19 +202,19 @@ test_that("vec_proxy_order() works on deeply nested lists", { test_that("error is thrown when comparing lists", { expect_error(vec_compare(list(), list()), class = "vctrs_error_unsupported") - expect_error(.Call(vctrs_compare, list(), list(), FALSE), "Can't compare lists") + expect_error(.Call(ffi_vec_compare, list(), list(), FALSE), "Can't compare lists") }) test_that("error is thrown when comparing data frames with list columns", { df <- data_frame(x = list()) expect_error(vec_compare(df, df), class = "vctrs_error_unsupported") - expect_error(.Call(vctrs_compare, df, df, FALSE), "Can't compare lists") + expect_error(.Call(ffi_vec_compare, df, df, FALSE), "Can't compare lists") }) test_that("error is thrown when comparing scalars", { x <- new_sclr(x = 1) expect_error(vec_compare(x, x), class = "vctrs_error_scalar_type") - expect_error(.Call(vctrs_compare, x, x, FALSE), class = "vctrs_error_scalar_type") + expect_error(.Call(ffi_vec_compare, x, x, FALSE), class = "vctrs_error_scalar_type") }) test_that("`na_equal` is validated", { From 958c507a652022b1b725ccc0dc5b556555e4be4b Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Thu, 15 Sep 2022 09:45:55 +0200 Subject: [PATCH 058/312] Use `vec_arg_format()` in `rep.c` --- src/rep.c | 35 ++++++++++++++--------------------- 1 file changed, 14 insertions(+), 21 deletions(-) diff --git a/src/rep.c b/src/rep.c index 6fc28621b..aa7c97b15 100644 --- a/src/rep.c +++ b/src/rep.c @@ -248,29 +248,26 @@ void check_rep_times(int times, static inline void stop_rep_times_negative(struct r_lazy call, struct vctrs_arg* p_times_arg) { - r_obj* times_arg = KEEP(vctrs_arg(p_times_arg)); r_abort_lazy_call(call, - "`%s` must be a positive number.", - r_chr_get_c_string(times_arg, 0)); + "%s must be a positive number.", + vec_arg_format(p_times_arg)); } static inline void stop_rep_times_missing(struct r_lazy call, struct vctrs_arg* p_times_arg) { - r_obj* times_arg = KEEP(vctrs_arg(p_times_arg)); r_abort_lazy_call(call, - "`%s` can't be missing.", - r_chr_get_c_string(times_arg, 0)); + "%s can't be missing.", + vec_arg_format(p_times_arg)); } // Not currently thrown since `r_ssize == int`, but might be once // long vectors are supported static inline void stop_rep_times_oob(int times, struct r_lazy call, struct vctrs_arg* p_times_arg) { - r_obj* times_arg = KEEP(vctrs_arg(p_times_arg)); r_abort_lazy_call( call, - "`%s` must be less than %i, not %i.", - r_chr_get_c_string(times_arg, 0), + "%s must be less than %i, not %i.", + vec_arg_format(p_times_arg), R_LEN_T_MAX, times ); @@ -297,19 +294,17 @@ void check_rep_each_times(int times, static inline void stop_rep_each_times_negative(r_ssize i, struct r_lazy call, struct vctrs_arg* p_times_arg) { - r_obj* times_arg = KEEP(vctrs_arg(p_times_arg)); r_abort_lazy_call(call, - "`%s` must be a vector of positive numbers. Location %i is negative.", - r_chr_get_c_string(times_arg, 0), + "%s must be a vector of positive numbers. Location %i is negative.", + vec_arg_format(p_times_arg), i); } static inline void stop_rep_each_times_missing(r_ssize i, struct r_lazy call, struct vctrs_arg* p_times_arg) { - r_obj* times_arg = KEEP(vctrs_arg(p_times_arg)); r_abort_lazy_call(call, - "`%s` can't be missing. Location %i is missing.", - r_chr_get_c_string(times_arg, 0), + "%s can't be missing. Location %i is missing.", + vec_arg_format(p_times_arg), i); } @@ -317,12 +312,11 @@ void stop_rep_each_times_missing(r_ssize i, struct r_lazy call, struct vctrs_arg // long vectors are supported static inline void stop_rep_each_times_oob(int times, r_ssize i, struct r_lazy call, struct vctrs_arg* p_times_arg) { - r_obj* times_arg = KEEP(vctrs_arg(p_times_arg)); r_abort_lazy_call( call, - "`%s` must be less than %i, not %i. ", + "%s must be less than %i, not %i. ", "Location %i is too large.", - r_chr_get_c_string(times_arg, 0), + vec_arg_format(p_times_arg), R_LEN_T_MAX, times, i @@ -342,10 +336,9 @@ void stop_rep_size_oob(struct r_lazy call) { static inline void stop_rep_times_size(struct r_lazy call, struct vctrs_arg* p_times_arg) { - r_obj* times_arg = KEEP(vctrs_arg(p_times_arg)); r_abort_lazy_call(call, - "`%s` must be a single number.", - r_chr_get_c_string(times_arg, 0)); + "%s must be a single number.", + vec_arg_format(p_times_arg)); } From 0af1953ec59fb5565de979047964012f5dc9c295 Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Thu, 15 Sep 2022 10:04:30 +0200 Subject: [PATCH 059/312] Use simpler `struct r_lazy` for arguments in `names.c` --- src/bind.c | 2 +- src/c-unchop.c | 2 +- src/c.c | 2 +- src/globals.c | 12 ++++++++++++ src/globals.h | 5 +++++ src/names.c | 12 +++++------- src/names.h | 4 ++-- src/type-data-frame.c | 4 ++-- 8 files changed, 29 insertions(+), 14 deletions(-) diff --git a/src/bind.c b/src/bind.c index 2cff4ecf7..007b84d81 100644 --- a/src/bind.c +++ b/src/bind.c @@ -618,7 +618,7 @@ r_obj* vec_as_df_col(r_obj* x, r_obj* outer) { static struct name_repair_opts validate_bind_name_repair(r_obj* name_repair, bool allow_minimal) { struct name_repair_opts opts = new_name_repair_opts(name_repair, - vec_args.empty, + r_lazy_null, false, r_lazy_null); diff --git a/src/c-unchop.c b/src/c-unchop.c index 0f2da4e53..0dad0025c 100644 --- a/src/c-unchop.c +++ b/src/c-unchop.c @@ -160,7 +160,7 @@ r_obj* ffi_list_unchop(r_obj* x, r_obj* name_repair) { struct name_repair_opts name_repair_opts = new_name_repair_opts(name_repair, - vec_args.empty, + r_lazy_null, false, r_lazy_null); KEEP(name_repair_opts.shelter); diff --git a/src/c.c b/src/c.c index 9647db8e1..76e827914 100644 --- a/src/c.c +++ b/src/c.c @@ -170,7 +170,7 @@ r_obj* ffi_vec_c(r_obj* call, r_obj* op, r_obj* args, r_obj* env) { struct name_repair_opts name_repair_opts = new_name_repair_opts(name_repair, - vec_args.empty, + r_lazy_null, false, r_lazy_null); KEEP(name_repair_opts.shelter); diff --git a/src/globals.c b/src/globals.c index dc17c3804..7aee6d2ad 100644 --- a/src/globals.c +++ b/src/globals.c @@ -4,6 +4,7 @@ struct syms syms; struct strings strings; struct fns fns; struct vec_args vec_args; +struct lazy_args lazy_args; struct lazy_calls lazy_calls; struct r_dyn_array* globals_shelter = NULL; @@ -21,6 +22,14 @@ struct r_dyn_array* globals_shelter = NULL; strings.ARG = r_str(#ARG); \ r_dyn_list_push_back(globals_shelter, strings.ARG); +#define INIT_LAZY_ARG(ARG) \ + lazy_args.ARG = (struct r_lazy) { .x = r_chr(#ARG), .env = r_null }; \ + r_dyn_list_push_back(globals_shelter, lazy_calls.ARG.x) + +#define INIT_LAZY_ARG_2(ARG, STR) \ + lazy_args.ARG = (struct r_lazy) { .x = r_chr(STR), .env = r_null }; \ + r_dyn_list_push_back(globals_shelter, lazy_args.ARG.x) + #define INIT_CALL(ARG) \ lazy_calls.ARG = (struct r_lazy) { .x = r_parse(#ARG "()"), .env = r_null }; \ r_dyn_list_push_back(globals_shelter, lazy_calls.ARG.x) @@ -61,6 +70,9 @@ void vctrs_init_globals(r_obj* ns) { INIT_ARG(value); INIT_ARG(x); + // Lazy args --------------------------------------------------------- + INIT_LAZY_ARG_2(dot_name_repair, ".name_repair"); + // Calls ------------------------------------------------------------- INIT_CALL(vec_assign); INIT_CALL(vec_assign_params); diff --git a/src/globals.h b/src/globals.h index 80eb5661c..3f61f3704 100644 --- a/src/globals.h +++ b/src/globals.h @@ -44,6 +44,10 @@ struct vec_args { struct vctrs_arg* x; }; +struct lazy_args { + struct r_lazy dot_name_repair; +}; + struct lazy_calls { struct r_lazy vec_assign; struct r_lazy vec_assign_params; @@ -60,6 +64,7 @@ extern struct syms syms; extern struct strings strings; extern struct fns fns; extern struct vec_args vec_args; +extern struct lazy_args lazy_args; extern struct lazy_calls lazy_calls; diff --git a/src/names.c b/src/names.c index 21724801f..4ee900bff 100644 --- a/src/names.c +++ b/src/names.c @@ -32,12 +32,10 @@ r_obj* ffi_as_names(r_obj* names, bool quiet = r_lgl_get(ffi_quiet, 0); struct r_lazy call = (struct r_lazy) { .x = syms_call, .env = frame }; - - struct r_lazy repair_arg_ = { .x = syms.repair_arg, .env = frame }; - struct vctrs_arg repair_arg = new_lazy_arg(&repair_arg_); + struct r_lazy repair_arg = { .x = syms.repair_arg, .env = frame }; struct name_repair_opts repair_opts = new_name_repair_opts(repair, - &repair_arg, + repair_arg, quiet, call); KEEP(repair_opts.shelter); @@ -60,7 +58,7 @@ r_obj* vec_as_universal_names(r_obj* names, bool quiet) { static r_obj* check_unique_names(r_obj* names, const struct name_repair_opts* opts) { - r_obj* ffi_arg = KEEP(vctrs_arg(opts->name_repair_arg)); + r_obj* ffi_arg = KEEP(r_lazy_eval(opts->name_repair_arg)); r_obj* ffi_call = KEEP(r_lazy_eval(opts->call)); r_obj* out = KEEP(vctrs_dispatch3(syms_check_unique_names, fns_check_unique_names, @@ -796,7 +794,7 @@ r_obj* vec_proxy_set_names(r_obj* x, r_obj* names, const enum vctrs_owned owned) r_obj* vctrs_validate_name_repair_arg(r_obj* arg) { struct name_repair_opts opts = new_name_repair_opts(arg, - vec_args.empty, + r_lazy_null, true, r_lazy_null); if (opts.type == NAME_REPAIR_custom) { @@ -813,7 +811,7 @@ void stop_name_repair() { } struct name_repair_opts new_name_repair_opts(r_obj* name_repair, - struct vctrs_arg* name_repair_arg, + struct r_lazy name_repair_arg, bool quiet, struct r_lazy call) { struct name_repair_opts opts = { diff --git a/src/names.h b/src/names.h index 35ca59855..ffe7f0c1f 100644 --- a/src/names.h +++ b/src/names.h @@ -27,7 +27,7 @@ enum name_repair_type { struct name_repair_opts { r_obj* shelter; enum name_repair_type type; - struct vctrs_arg* name_repair_arg; + struct r_lazy name_repair_arg; r_obj* fn; bool quiet; struct r_lazy call; @@ -46,7 +46,7 @@ static struct name_repair_opts const * const p_no_repair_opts = &no_repair_opts; r_obj* vec_as_names(r_obj* names, const struct name_repair_opts* opts); struct name_repair_opts new_name_repair_opts(r_obj* name_repair, - struct vctrs_arg* name_repair_arg, + struct r_lazy name_repair_arg, bool quiet, struct r_lazy call); const char* name_repair_arg_as_c_string(enum name_repair_type type); diff --git a/src/type-data-frame.c b/src/type-data-frame.c index f2e716d35..93a8b363b 100644 --- a/src/type-data-frame.c +++ b/src/type-data-frame.c @@ -178,7 +178,7 @@ r_obj* ffi_data_frame(r_obj* x, struct r_lazy call = { .x = syms_dot_call, .env = frame }; struct name_repair_opts name_repair_opts = new_name_repair_opts(name_repair, - vec_args.dot_name_repair, + lazy_args.dot_name_repair, false, call); KEEP(name_repair_opts.shelter); @@ -218,7 +218,7 @@ r_obj* ffi_df_list(r_obj* x, struct r_lazy call = { .x = syms_dot_call, .env = frame }; struct name_repair_opts name_repair_opts = new_name_repair_opts(name_repair, - vec_args.dot_name_repair, + lazy_args.dot_name_repair, false, call); KEEP(name_repair_opts.shelter); From 7d67a39e738b4916a55d9c116184ad190267bfe8 Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Thu, 15 Sep 2022 10:06:26 +0200 Subject: [PATCH 060/312] Update arg and call in `names.c` --- R/names.R | 2 +- man/vec_as_names.Rd | 2 +- src/decl/names-decl.h | 2 +- src/names.c | 69 ++++++------ tests/testthat/_snaps/bind.md | 2 +- tests/testthat/_snaps/conditions.md | 2 + tests/testthat/_snaps/names.md | 161 ++++++++++++++++++++++++++++ tests/testthat/test-names.R | 54 ++++++---- 8 files changed, 236 insertions(+), 58 deletions(-) diff --git a/R/names.R b/R/names.R index 0bb885511..0083c37ca 100644 --- a/R/names.R +++ b/R/names.R @@ -158,7 +158,7 @@ vec_as_names <- function(names, ..., repair = c("minimal", "unique", "universal", "check_unique"), - repair_arg = "", + repair_arg = caller_arg(repair), quiet = FALSE, call = caller_env()) { check_dots_empty0(...) diff --git a/man/vec_as_names.Rd b/man/vec_as_names.Rd index 86c5064bc..ada69129d 100644 --- a/man/vec_as_names.Rd +++ b/man/vec_as_names.Rd @@ -8,7 +8,7 @@ vec_as_names( names, ..., repair = c("minimal", "unique", "universal", "check_unique"), - repair_arg = "", + repair_arg = caller_arg(repair), quiet = FALSE, call = caller_env() ) diff --git a/src/decl/names-decl.h b/src/decl/names-decl.h index 433749f32..c35b46ddc 100644 --- a/src/decl/names-decl.h +++ b/src/decl/names-decl.h @@ -18,7 +18,7 @@ r_obj* check_unique_names(r_obj* names, const struct name_repair_opts* opts); static -void vec_validate_minimal_names(r_obj* names, r_ssize n); +void vec_validate_minimal_names(r_obj* names, r_ssize n, struct r_lazy call); r_obj* ffi_as_minimal_names(r_obj* names); diff --git a/src/names.c b/src/names.c index 4ee900bff..c6a84d403 100644 --- a/src/names.c +++ b/src/names.c @@ -19,7 +19,7 @@ r_obj* vec_as_names(r_obj* names, const struct name_repair_opts* opts) { case NAME_REPAIR_check_unique: return check_unique_names(names, opts); case NAME_REPAIR_custom: return vec_as_custom_names(names, opts); } - never_reached("vec_as_names"); + r_stop_unreachable(); } r_obj* ffi_as_names(r_obj* names, @@ -83,7 +83,7 @@ r_obj* vec_as_custom_names(r_obj* names, const struct name_repair_opts* opts) { r_env_poke(mask, syms_names, names); r_obj* out = KEEP(r_eval(call, mask)); - vec_validate_minimal_names(out, r_length(names)); + vec_validate_minimal_names(out, r_length(names), opts->call); FREE(4); return out; @@ -142,7 +142,7 @@ r_obj* vec_names2(r_obj* x) { r_obj* ffi_as_minimal_names(r_obj* names) { if (r_typeof(names) != R_TYPE_character) { - r_abort_call(r_null, "`names` must be a character vector"); + r_abort("`names` must be a character vector"); } r_ssize i = 0; @@ -199,7 +199,7 @@ r_obj* vec_as_unique_names(r_obj* names, bool quiet) { // [[ include("vctrs.h") ]] bool is_unique_names(r_obj* names) { if (r_typeof(names) != R_TYPE_character) { - r_abort_call(r_null, "`names` must be a character vector"); + r_abort("`names` must be a character vector"); } r_ssize n = r_length(names); @@ -390,7 +390,7 @@ ptrdiff_t suffix_pos(const char* name) { } static void stop_large_name() { - r_abort_call(r_null, "Can't tidy up name because it is too large"); + r_abort("Can't tidy up name because it is too large."); } static bool needs_suffix(r_obj* str) { @@ -440,7 +440,7 @@ r_obj* names_iota(r_ssize n) { r_obj* nms = r_chr_iota(n, buf, MAX_IOTA_SIZE, "..."); if (nms == r_null) { - r_abort_call(r_null, "Too many names to repair."); + r_abort("Too many names to repair."); } return nms; @@ -546,10 +546,9 @@ r_obj* apply_name_spec(r_obj* name_spec, r_obj* outer, r_obj* inner, r_ssize n) name_spec = r_as_function(name_spec, ".name_spec"); break; case R_TYPE_null: - r_abort_call(r_null, - "Can't merge the outer name `%s` with a vector of length > 1.\n" - "Please supply a `.name_spec` specification.", - r_str_c_string(outer)); + r_abort("Can't merge the outer name `%s` with a vector of length > 1.\n" + "Please supply a `.name_spec` specification.", + r_str_c_string(outer)); } KEEP(name_spec); @@ -562,10 +561,10 @@ r_obj* apply_name_spec(r_obj* name_spec, r_obj* outer, r_obj* inner, r_ssize n) if (out != r_null) { if (r_typeof(out) != R_TYPE_character) { - r_abort_call(r_null, "`.name_spec` must return a character vector."); + r_abort("`.name_spec` must return a character vector."); } if (r_length(out) != n) { - r_abort_call(r_null, "`.name_spec` must return a character vector as long as `inner`."); + r_abort("`.name_spec` must return a character vector as long as `inner`."); } } @@ -577,7 +576,7 @@ r_obj* apply_name_spec(r_obj* name_spec, r_obj* outer, r_obj* inner, r_ssize n) static r_obj* glue_as_name_spec(r_obj* spec) { if (!r_is_string(spec)) { - r_abort_call(r_null, "Glue specification in `.name_spec` must be a single string."); + r_abort("Glue specification in `.name_spec` must be a single string."); } return vctrs_dispatch1(syms_glue_as_name_spec, fns_glue_as_name_spec, syms_internal_spec, spec); @@ -669,8 +668,7 @@ void check_names(r_obj* x, r_obj* names) { } if (r_typeof(names) != R_TYPE_character) { - r_abort_call( - r_null, + r_abort( "`names` must be a character vector, not a %s.", r_type_as_c_string(r_typeof(names)) ); @@ -680,8 +678,7 @@ void check_names(r_obj* x, r_obj* names) { r_ssize names_size = vec_size(names); if (x_size != names_size) { - r_abort_call( - r_null, + r_abort( "The size of `names`, %i, must be the same as the size of `x`, %i.", names_size, x_size @@ -806,8 +803,11 @@ r_obj* vctrs_validate_name_repair_arg(r_obj* arg) { } } -void stop_name_repair() { - r_abort_call(r_null, "`.name_repair` must be a string or a function. See `?vctrs::vec_as_names`."); +void stop_name_repair(struct r_lazy call, + struct r_lazy name_repair_arg) { + r_abort_lazy_call(call, + "%s must be a string or a function. See `?vctrs::vec_as_names`.", + r_format_lazy_error_arg(name_repair_arg)); } struct name_repair_opts new_name_repair_opts(r_obj* name_repair, @@ -826,7 +826,7 @@ struct name_repair_opts new_name_repair_opts(r_obj* name_repair, switch (r_typeof(name_repair)) { case R_TYPE_character: { if (!r_length(name_repair)) { - stop_name_repair(); + stop_name_repair(call, name_repair_arg); } r_obj* c = r_chr_get(name_repair, 0); @@ -842,7 +842,10 @@ struct name_repair_opts new_name_repair_opts(r_obj* name_repair, } else if (c == strings_check_unique) { opts.type = NAME_REPAIR_check_unique; } else { - r_abort_call(r_null, "`.name_repair` can't be \"%s\". See `?vctrs::vec_as_names`.", r_str_c_string(c)); + r_abort_lazy_call(call, + "%s can't be \"%s\". See `?vctrs::vec_as_names`.", + r_format_lazy_error_arg(name_repair_arg), + r_str_c_string(c)); } return opts; @@ -860,10 +863,10 @@ struct name_repair_opts new_name_repair_opts(r_obj* name_repair, return opts; default: - stop_name_repair(); + stop_name_repair(call, name_repair_arg); } - never_reached("new_name_repair_opts"); + r_stop_unreachable(); } const char* name_repair_arg_as_c_string(enum name_repair_type type) { @@ -875,28 +878,28 @@ const char* name_repair_arg_as_c_string(enum name_repair_type type) { case NAME_REPAIR_check_unique: return "check_unique"; case NAME_REPAIR_custom: return "custom"; } - never_reached("name_repair_arg_as_c_string"); + r_stop_unreachable(); } static -void vec_validate_minimal_names(r_obj* names, r_ssize n) { +void vec_validate_minimal_names(r_obj* names, r_ssize n, struct r_lazy call) { if (names == r_null) { - r_abort_call(r_null, "Names repair functions can't return `NULL`."); + r_abort_lazy_call(call, "Names repair functions can't return `NULL`."); } if (r_typeof(names) != R_TYPE_character) { - r_abort_call(r_null, "Names repair functions must return a character vector."); + r_abort_lazy_call(call, "Names repair functions must return a character vector."); } if (n >= 0 && r_length(names) != n) { - r_abort_call(r_null, - "Repaired names have length %d instead of length %d.", - r_length(names), - n); + r_abort_lazy_call(call, + "Repaired names have length %d instead of length %d.", + r_length(names), + n); } if (r_chr_has_string(names, r_globals.na_str)) { - r_abort_call(r_null, "Names repair functions can't return `NA` values."); + r_abort_lazy_call(call, "Names repair functions can't return `NA` values."); } } r_obj* vctrs_validate_minimal_names(r_obj* names, r_obj* n_) { @@ -909,7 +912,7 @@ r_obj* vctrs_validate_minimal_names(r_obj* names, r_obj* n_) { n = r_int_get(n_, 0); } - vec_validate_minimal_names(names, n); + vec_validate_minimal_names(names, n, r_lazy_null); return names; } diff --git a/tests/testthat/_snaps/bind.md b/tests/testthat/_snaps/bind.md index a479474f8..fe9ab0ef1 100644 --- a/tests/testthat/_snaps/bind.md +++ b/tests/testthat/_snaps/bind.md @@ -76,7 +76,7 @@ (expect_error(vec_rbind(foo = df1, df2, .names_to = NULL), "specification")) Output - Error: + Error in `vec_rbind()`: ! Can't merge the outer name `foo` with a vector of length > 1. Please supply a `.name_spec` specification. diff --git a/tests/testthat/_snaps/conditions.md b/tests/testthat/_snaps/conditions.md index 3a6e2b713..73666a6a1 100644 --- a/tests/testthat/_snaps/conditions.md +++ b/tests/testthat/_snaps/conditions.md @@ -124,6 +124,7 @@ x These names are duplicated: * "x" at locations 1, 2, and 3. * "y" at locations 4 and 5. + i Use argument `"check_unique"` to specify repair strategy. Code (expect_error(vec_as_names(c(rep("x", 20), rep(c("a", "b", "c", "d", "e"), 2)), repair = "check_unique"), class = "vctrs_error_names_must_be_unique")) @@ -138,6 +139,7 @@ * "c" at locations 23 and 28. * "d" at locations 24 and 29. * ... + i Use argument `"check_unique"` to specify repair strategy. # lossy cast from character to factor mentions loss of generality diff --git a/tests/testthat/_snaps/names.md b/tests/testthat/_snaps/names.md index 39c07cf92..6505ee609 100644 --- a/tests/testthat/_snaps/names.md +++ b/tests/testthat/_snaps/names.md @@ -1,3 +1,67 @@ +# vec_as_names() validates `repair` + + Code + (expect_error(vec_as_names("x", repair = "foo"), "can't be \"foo\"")) + Output + + Error: + ! `"foo"` can't be "foo". See `?vctrs::vec_as_names`. + Code + (expect_error(vec_as_names(1, repair = 1), "string or a function")) + Output + + Error: + ! `1` must be a string or a function. See `?vctrs::vec_as_names`. + +# vec_as_names() checks unique names + + Code + (expect_error(vec_as_names(chr(NA), repair = "check_unique"))) + Output + + Error: + ! Names repair functions can't return `NA` values. + Code + (expect_error(vec_as_names(chr(""), repair = "check_unique"))) + Output + + Error: + ! Names can't be empty. + x Empty name found at location 1. + Code + (expect_error(vec_as_names(chr("a", "a"), repair = "check_unique"))) + Output + + Error: + ! Names must be unique. + x These names are duplicated: + * "a" at locations 1 and 2. + i Use argument `"check_unique"` to specify repair strategy. + Code + (expect_error(vec_as_names(chr("..1"), repair = "check_unique"))) + Output + + Error: + ! Names can't be of the form `...` or `..j`. + x These names are invalid: + * "..1" at location 1. + Code + (expect_error(vec_as_names(chr("..."), repair = "check_unique"))) + Output + + Error: + ! Names can't be of the form `...` or `..j`. + x These names are invalid: + * "..." at location 1. + +# vec_as_names() accepts and checks repair function + + Code + vec_as_names(c("", ""), repair = function(nms) "foo") + Condition + Error: + ! Repaired names have length 1 instead of length 2. + # vec_as_names() is noisy by default Code @@ -23,6 +87,86 @@ * "x" at locations 1 and 2. i Use argument `repair` to specify repair strategy. +# validate_minimal_names() checks names + + Code + (expect_error(validate_minimal_names(1), "must return a character vector")) + Output + + Error: + ! Names repair functions must return a character vector. + Code + (expect_error(validate_minimal_names(NULL), "can't return `NULL`")) + Output + + Error: + ! Names repair functions can't return `NULL`. + Code + (expect_error(validate_minimal_names(chr(NA)), "can't return `NA` values")) + Output + + Error: + ! Names repair functions can't return `NA` values. + +# validate_unique() checks unique names + + Code + (expect_error(validate_unique(chr(NA)), "`NA`")) + Output + + Error: + ! Names repair functions can't return `NA` values. + Code + (expect_error(validate_unique(chr("")), class = "vctrs_error_names_cannot_be_empty") + ) + Output + + Error: + ! Names can't be empty. + x Empty name found at location 1. + Code + (expect_error(validate_unique(chr("a", "a")), class = "vctrs_error_names_must_be_unique") + ) + Output + + Error: + ! Names must be unique. + x These names are duplicated: + * "a" at locations 1 and 2. + Code + (expect_error(validate_unique(chr("..1")), class = "vctrs_error_names_cannot_be_dot_dot") + ) + Output + + Error: + ! Names can't be of the form `...` or `..j`. + x These names are invalid: + * "..1" at location 1. + Code + (expect_error(validate_unique(chr("...")), class = "vctrs_error_names_cannot_be_dot_dot") + ) + Output + + Error: + ! Names can't be of the form `...` or `..j`. + x These names are invalid: + * "..." at location 1. + +# vec_set_names() errors with bad `names` + + Code + (expect_error(vec_set_names(1, 1), "character vector, not a double")) + Output + + Error in `vec_set_names()`: + ! `names` must be a character vector, not a double. + Code + (expect_error(vec_set_names(1, c("x", "y")), "The size of `names`, 2")) + Output + + Error in `vec_set_names()`: + ! The size of `names`, 2, must be the same as the size of `x`, 1. + # unique_names() and as_unique_names() are verbose or silent Code @@ -78,3 +222,20 @@ a.b 1 +# NULL name specs works with scalars + + Code + (expect_error(vec_c(foo = c(a = 1, b = 2)), "vector of length > 1")) + Output + + Error in `vec_c()`: + ! Can't merge the outer name `foo` with a vector of length > 1. + Please supply a `.name_spec` specification. + Code + (expect_error(vec_c(foo = 1:2), "vector of length > 1")) + Output + + Error in `vec_c()`: + ! Can't merge the outer name `foo` with a vector of length > 1. + Please supply a `.name_spec` specification. + diff --git a/tests/testthat/test-names.R b/tests/testthat/test-names.R index e1018db7e..b3ddd4356 100644 --- a/tests/testthat/test-names.R +++ b/tests/testthat/test-names.R @@ -59,8 +59,10 @@ test_that("vec_as_names() requires character vector", { }) test_that("vec_as_names() validates `repair`", { - expect_error(vec_as_names("x", repair = "foo"), "can't be \"foo\"") - expect_error(vec_as_names(1, repair = 1), "string or a function") + expect_snapshot({ + (expect_error(vec_as_names("x", repair = "foo"), "can't be \"foo\"")) + (expect_error(vec_as_names(1, repair = 1), "string or a function")) + }) }) test_that("vec_as_names() repairs names", { @@ -71,11 +73,13 @@ test_that("vec_as_names() repairs names", { }) test_that("vec_as_names() checks unique names", { - expect_error(vec_as_names(chr(NA), repair = "check_unique")) - expect_error(vec_as_names(chr(""), repair = "check_unique")) - expect_error(vec_as_names(chr("a", "a"), repair = "check_unique")) - expect_error(vec_as_names(chr("..1"), repair = "check_unique")) - expect_error(vec_as_names(chr("..."), repair = "check_unique")) + expect_snapshot({ + (expect_error(vec_as_names(chr(NA), repair = "check_unique"))) + (expect_error(vec_as_names(chr(""), repair = "check_unique"))) + (expect_error(vec_as_names(chr("a", "a"), repair = "check_unique"))) + (expect_error(vec_as_names(chr("..1"), repair = "check_unique"))) + (expect_error(vec_as_names(chr("..."), repair = "check_unique"))) + }) }) test_that("vec_as_names() keeps the names of a named vector", { @@ -103,7 +107,7 @@ test_that("vec_as_names() accepts and checks repair function", { ~ rep_along(.x, local_obj) }) expect_identical(vec_as_names(c("", ""), repair = f), c("foo", "foo")) - expect_error(vec_as_names(c("", ""), repair = function(nms) "foo"), "length 1 instead of length 2") + expect_snapshot(error = TRUE, vec_as_names(c("", ""), repair = function(nms) "foo")) }) test_that("vec_as_names() repairs names before invoking repair function", { @@ -128,17 +132,21 @@ test_that("vec_as_names() is noisy by default", { }) test_that("validate_minimal_names() checks names", { - expect_error(validate_minimal_names(1), "must return a character vector") - expect_error(validate_minimal_names(NULL), "can't return `NULL`") - expect_error(validate_minimal_names(chr(NA)), "can't return `NA` values") + expect_snapshot({ + (expect_error(validate_minimal_names(1), "must return a character vector")) + (expect_error(validate_minimal_names(NULL), "can't return `NULL`")) + (expect_error(validate_minimal_names(chr(NA)), "can't return `NA` values")) + }) }) test_that("validate_unique() checks unique names", { - expect_error(validate_unique(chr(NA)), "`NA`") - expect_error(validate_unique(chr("")), class = "vctrs_error_names_cannot_be_empty") - expect_error(validate_unique(chr("a", "a")), class = "vctrs_error_names_must_be_unique") - expect_error(validate_unique(chr("..1")), class = "vctrs_error_names_cannot_be_dot_dot") - expect_error(validate_unique(chr("...")), class = "vctrs_error_names_cannot_be_dot_dot") + expect_snapshot({ + (expect_error(validate_unique(chr(NA)), "`NA`")) + (expect_error(validate_unique(chr("")), class = "vctrs_error_names_cannot_be_empty")) + (expect_error(validate_unique(chr("a", "a")), class = "vctrs_error_names_must_be_unique")) + (expect_error(validate_unique(chr("..1")), class = "vctrs_error_names_cannot_be_dot_dot")) + (expect_error(validate_unique(chr("...")), class = "vctrs_error_names_cannot_be_dot_dot")) + }) }) test_that("vec_as_names_validate() validates repair arguments", { @@ -278,8 +286,10 @@ test_that("vec_set_names() can set NULL names", { }) test_that("vec_set_names() errors with bad `names`", { - expect_error(vec_set_names(1, 1), "character vector, not a double") - expect_error(vec_set_names(1, c("x", "y")), "The size of `names`, 2") + expect_snapshot({ + (expect_error(vec_set_names(1, 1), "character vector, not a double")) + (expect_error(vec_set_names(1, c("x", "y")), "The size of `names`, 2")) + }) }) test_that("vec_names() and vec_set_names() work with 1-dimensional arrays", { @@ -783,10 +793,12 @@ test_that("NULL name specs works with scalars", { expect_named(vec_c(foo = set_names(dbl()), bar = set_names(dbl())), chr()) expect_error(apply_name_spec(NULL, "foo", c("a", "b")), "vector of length > 1") - expect_error(vec_c(foo = c(a = 1, b = 2)), "vector of length > 1") - expect_error(apply_name_spec(NULL, "foo", NULL, 2L), "vector of length > 1") - expect_error(vec_c(foo = 1:2), "vector of length > 1") + + expect_snapshot({ + (expect_error(vec_c(foo = c(a = 1, b = 2)), "vector of length > 1")) + (expect_error(vec_c(foo = 1:2), "vector of length > 1")) + }) }) test_that("function name spec is applied", { From 65f5e87b8d55ad6d2606e1e5ee89ae33bb162bc9 Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Thu, 15 Sep 2022 10:44:40 +0200 Subject: [PATCH 061/312] Use `vec_as_names()` wrapper in snapshot tests --- tests/testthat/_snaps/names.md | 43 +++++++++++++++--------------- tests/testthat/helper-conditions.R | 7 +++++ tests/testthat/test-names.R | 18 ++++++------- 3 files changed, 37 insertions(+), 31 deletions(-) diff --git a/tests/testthat/_snaps/names.md b/tests/testthat/_snaps/names.md index 6505ee609..0c1678c5e 100644 --- a/tests/testthat/_snaps/names.md +++ b/tests/testthat/_snaps/names.md @@ -1,55 +1,55 @@ # vec_as_names() validates `repair` Code - (expect_error(vec_as_names("x", repair = "foo"), "can't be \"foo\"")) + (expect_error(my_vec_as_names("x", my_repair = "foo"), "can't be \"foo\"")) Output - Error: - ! `"foo"` can't be "foo". See `?vctrs::vec_as_names`. + Error in `my_vec_as_names()`: + ! `my_repair` can't be "foo". See `?vctrs::vec_as_names`. Code - (expect_error(vec_as_names(1, repair = 1), "string or a function")) + (expect_error(my_vec_as_names(1, my_repair = 1), "string or a function")) Output - Error: - ! `1` must be a string or a function. See `?vctrs::vec_as_names`. + Error in `my_vec_as_names()`: + ! `my_repair` must be a string or a function. See `?vctrs::vec_as_names`. # vec_as_names() checks unique names Code - (expect_error(vec_as_names(chr(NA), repair = "check_unique"))) + (expect_error(my_vec_as_names(chr(NA), my_repair = "check_unique"))) Output Error: ! Names repair functions can't return `NA` values. Code - (expect_error(vec_as_names(chr(""), repair = "check_unique"))) + (expect_error(my_vec_as_names(chr(""), my_repair = "check_unique"))) Output - Error: + Error in `my_vec_as_names()`: ! Names can't be empty. x Empty name found at location 1. Code - (expect_error(vec_as_names(chr("a", "a"), repair = "check_unique"))) + (expect_error(my_vec_as_names(chr("a", "a"), my_repair = "check_unique"))) Output - Error: + Error in `my_vec_as_names()`: ! Names must be unique. x These names are duplicated: * "a" at locations 1 and 2. - i Use argument `"check_unique"` to specify repair strategy. + i Use argument `my_repair` to specify repair strategy. Code - (expect_error(vec_as_names(chr("..1"), repair = "check_unique"))) + (expect_error(my_vec_as_names(chr("..1"), my_repair = "check_unique"))) Output - Error: + Error in `my_vec_as_names()`: ! Names can't be of the form `...` or `..j`. x These names are invalid: * "..1" at location 1. Code - (expect_error(vec_as_names(chr("..."), repair = "check_unique"))) + (expect_error(my_vec_as_names(chr("..."), my_repair = "check_unique"))) Output - Error: + Error in `my_vec_as_names()`: ! Names can't be of the form `...` or `..j`. x These names are invalid: * "..." at location 1. @@ -57,9 +57,9 @@ # vec_as_names() accepts and checks repair function Code - vec_as_names(c("", ""), repair = function(nms) "foo") + my_vec_as_names(c("", ""), my_repair = function(nms) "foo") Condition - Error: + Error in `my_vec_as_names()`: ! Repaired names have length 1 instead of length 2. # vec_as_names() is noisy by default @@ -77,15 +77,14 @@ Output [1] "x...1" "x...2" Code - (expect_error(vec_as_names(c("x", "x"), repair = "check_unique", repair_arg = "repair")) - ) + (expect_error(my_vec_as_names(c("x", "x"), my_repair = "check_unique"))) Output - Error: + Error in `my_vec_as_names()`: ! Names must be unique. x These names are duplicated: * "x" at locations 1 and 2. - i Use argument `repair` to specify repair strategy. + i Use argument `my_repair` to specify repair strategy. # validate_minimal_names() checks names diff --git a/tests/testthat/helper-conditions.R b/tests/testthat/helper-conditions.R index fc47029b6..356adb72c 100644 --- a/tests/testthat/helper-conditions.R +++ b/tests/testthat/helper-conditions.R @@ -75,3 +75,10 @@ my_vec_rep_each <- function(my_x, my_times) { times_arg = "my_times" ) } + +my_vec_as_names <- function(my_names, + ..., + my_repair = "minimal", + my_quiet = FALSE) { + vec_as_names(my_names, repair = my_repair, quiet = my_quiet) +} diff --git a/tests/testthat/test-names.R b/tests/testthat/test-names.R index b3ddd4356..9f370709e 100644 --- a/tests/testthat/test-names.R +++ b/tests/testthat/test-names.R @@ -60,8 +60,8 @@ test_that("vec_as_names() requires character vector", { test_that("vec_as_names() validates `repair`", { expect_snapshot({ - (expect_error(vec_as_names("x", repair = "foo"), "can't be \"foo\"")) - (expect_error(vec_as_names(1, repair = 1), "string or a function")) + (expect_error(my_vec_as_names("x", my_repair = "foo"), "can't be \"foo\"")) + (expect_error(my_vec_as_names(1, my_repair = 1), "string or a function")) }) }) @@ -74,11 +74,11 @@ test_that("vec_as_names() repairs names", { test_that("vec_as_names() checks unique names", { expect_snapshot({ - (expect_error(vec_as_names(chr(NA), repair = "check_unique"))) - (expect_error(vec_as_names(chr(""), repair = "check_unique"))) - (expect_error(vec_as_names(chr("a", "a"), repair = "check_unique"))) - (expect_error(vec_as_names(chr("..1"), repair = "check_unique"))) - (expect_error(vec_as_names(chr("..."), repair = "check_unique"))) + (expect_error(my_vec_as_names(chr(NA), my_repair = "check_unique"))) + (expect_error(my_vec_as_names(chr(""), my_repair = "check_unique"))) + (expect_error(my_vec_as_names(chr("a", "a"), my_repair = "check_unique"))) + (expect_error(my_vec_as_names(chr("..1"), my_repair = "check_unique"))) + (expect_error(my_vec_as_names(chr("..."), my_repair = "check_unique"))) }) }) @@ -107,7 +107,7 @@ test_that("vec_as_names() accepts and checks repair function", { ~ rep_along(.x, local_obj) }) expect_identical(vec_as_names(c("", ""), repair = f), c("foo", "foo")) - expect_snapshot(error = TRUE, vec_as_names(c("", ""), repair = function(nms) "foo")) + expect_snapshot(error = TRUE, my_vec_as_names(c("", ""), my_repair = function(nms) "foo")) }) test_that("vec_as_names() repairs names before invoking repair function", { @@ -126,7 +126,7 @@ test_that("vec_as_names() is noisy by default", { # Hint at repair argument, if known (expect_error( - vec_as_names(c("x", "x"), repair = "check_unique", repair_arg = "repair") + my_vec_as_names(c("x", "x"), my_repair = "check_unique") )) }) }) From aa41a008645b0b6b760647e37cd2f5eb262b6bd7 Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Thu, 15 Sep 2022 10:51:17 +0200 Subject: [PATCH 062/312] Update style in `shape.c` --- R/shape.R | 4 +- src/decl/shape-decl.h | 19 ++++++ src/init.c | 8 +-- src/shape.c | 139 +++++++++++++++++++++--------------------- 4 files changed, 96 insertions(+), 74 deletions(-) create mode 100644 src/decl/shape-decl.h diff --git a/R/shape.R b/R/shape.R index 110b53c88..2503856ad 100644 --- a/R/shape.R +++ b/R/shape.R @@ -9,12 +9,12 @@ new_shape <- function(type, shape = integer()) { vec_shaped_ptype <- function(ptype, x, y, ..., x_arg = "", y_arg = "") { check_dots_empty0(...) - .Call(vctrs_shaped_ptype, ptype, x, y, environment()) + .Call(ffi_vec_shaped_ptype, ptype, x, y, environment()) } vec_shape2 <- function(x, y, ..., x_arg = "", y_arg = "") { check_dots_empty0(...) - .Call(vctrs_shape2, x, y, environment()) + .Call(ffi_vec_shape2, x, y, environment()) } # Should take same signature as `vec_cast()` diff --git a/src/decl/shape-decl.h b/src/decl/shape-decl.h new file mode 100644 index 000000000..64f64736e --- /dev/null +++ b/src/decl/shape-decl.h @@ -0,0 +1,19 @@ +static +r_obj* vec_shape2(r_obj* x, r_obj* y, struct vctrs_arg* p_x_arg, struct vctrs_arg* p_y_arg); + +static +r_obj* vec_shape2_impl(r_obj* x_dimensions, + r_obj* y_dimensions, + r_obj* x, + r_obj* y, + struct vctrs_arg* p_x_arg, + struct vctrs_arg* p_y_arg); + +static +r_obj* vec_shape(r_obj* dimensions); + +static inline +int vec_dimension2(int x_dimension, int y_dimension, + int axis, + r_obj* x, r_obj* y, + struct vctrs_arg* p_x_arg, struct vctrs_arg* p_y_arg); diff --git a/src/init.c b/src/init.c index 2ef2377b9..c20fe0272 100644 --- a/src/init.c +++ b/src/init.c @@ -106,8 +106,8 @@ extern r_obj* ffi_vec_rep(r_obj*, r_obj*, r_obj*); extern r_obj* ffi_vec_rep_each(r_obj*, r_obj*, r_obj*); extern SEXP vctrs_maybe_shared_col(SEXP, SEXP); extern SEXP vctrs_new_df_unshared_col(); -extern SEXP vctrs_shaped_ptype(SEXP, SEXP, SEXP, SEXP); -extern SEXP vctrs_shape2(SEXP, SEXP, SEXP); +extern r_obj* ffi_vec_shaped_ptype(r_obj*, r_obj*, r_obj*, r_obj*); +extern r_obj* ffi_vec_shape2(r_obj*, r_obj*, r_obj*); extern SEXP vctrs_new_date(SEXP); extern SEXP vctrs_date_validate(SEXP); extern SEXP vctrs_new_datetime(SEXP, SEXP); @@ -277,8 +277,8 @@ static const R_CallMethodDef CallEntries[] = { {"ffi_vec_rep_each", (DL_FUNC) &ffi_vec_rep_each, 3}, {"vctrs_maybe_shared_col", (DL_FUNC) &vctrs_maybe_shared_col, 2}, {"vctrs_new_df_unshared_col", (DL_FUNC) &vctrs_new_df_unshared_col, 0}, - {"vctrs_shaped_ptype", (DL_FUNC) &vctrs_shaped_ptype, 4}, - {"vctrs_shape2", (DL_FUNC) &vctrs_shape2, 3}, + {"ffi_vec_shaped_ptype", (DL_FUNC) &ffi_vec_shaped_ptype, 4}, + {"ffi_vec_shape2", (DL_FUNC) &ffi_vec_shape2, 3}, {"vctrs_new_date", (DL_FUNC) &vctrs_new_date, 1}, {"vctrs_date_validate", (DL_FUNC) &vctrs_date_validate, 1}, {"vctrs_new_datetime", (DL_FUNC) &vctrs_new_datetime, 2}, diff --git a/src/shape.c b/src/shape.c index 08c79df07..5a6646bea 100644 --- a/src/shape.c +++ b/src/shape.c @@ -1,94 +1,91 @@ #include "vctrs.h" +#include "decl/shape-decl.h" -// [[ register() ]] -SEXP vctrs_shaped_ptype(SEXP ptype, SEXP x, SEXP y, SEXP frame) { - struct r_lazy x_arg_ = { .x = syms.x_arg, .env = frame }; - struct vctrs_arg x_arg = new_lazy_arg(&x_arg_); - - struct r_lazy y_arg_ = { .x = syms.y_arg, .env = frame }; - struct vctrs_arg y_arg = new_lazy_arg(&y_arg_); - - return vec_shaped_ptype(ptype, x, y, &x_arg, &y_arg); -} - -static SEXP vec_shape2(SEXP x, SEXP y, struct vctrs_arg* p_x_arg, struct vctrs_arg* p_y_arg); // Computes the common shape of `x` and `y` and attaches it as the // dimensions of `ptype`. If `x` and `y` are both atomic with `NULL` dimensions, // then no dimensions are attached and `ptype` is returned unmodified. // [[ include("shape.h") ]] -SEXP vec_shaped_ptype(SEXP ptype, - SEXP x, SEXP y, - struct vctrs_arg* p_x_arg, struct vctrs_arg* p_y_arg) { - SEXP ptype_dimensions = PROTECT(vec_shape2(x, y, p_x_arg, p_y_arg)); +r_obj* vec_shaped_ptype(r_obj* ptype, + r_obj* x, r_obj* y, + struct vctrs_arg* p_x_arg, struct vctrs_arg* p_y_arg) { + r_obj* ptype_dimensions = KEEP(vec_shape2(x, y, p_x_arg, p_y_arg)); - if (ptype_dimensions == R_NilValue) { - UNPROTECT(1); + if (ptype_dimensions == r_null) { + FREE(1); return ptype; } - ptype = PROTECT(r_clone_referenced(ptype)); - + ptype = KEEP(r_clone_referenced(ptype)); r_attrib_poke_dim(ptype, ptype_dimensions); - UNPROTECT(2); + FREE(2); return ptype; } -// ----------------------------------------------------------------------------- - -// [[ register() ]] -SEXP vctrs_shape2(SEXP x, SEXP y, SEXP frame) { +r_obj* ffi_vec_shaped_ptype(r_obj* ptype, r_obj* x, r_obj* y, r_obj* frame) { struct r_lazy x_arg_ = { .x = syms.x_arg, .env = frame }; struct vctrs_arg x_arg = new_lazy_arg(&x_arg_); struct r_lazy y_arg_ = { .x = syms.y_arg, .env = frame }; struct vctrs_arg y_arg = new_lazy_arg(&y_arg_); - return vec_shape2(x, y, &x_arg, &y_arg); + return vec_shaped_ptype(ptype, x, y, &x_arg, &y_arg); } -static SEXP vec_shape2_impl(SEXP x_dimensions, SEXP y_dimensions, - SEXP x, SEXP y, - struct vctrs_arg* p_x_arg, struct vctrs_arg* p_y_arg); -static SEXP vec_shape2(SEXP x, SEXP y, struct vctrs_arg* p_x_arg, struct vctrs_arg* p_y_arg) { - SEXP x_dimensions = PROTECT(r_dim(x)); - SEXP y_dimensions = PROTECT(r_dim(y)); +// ----------------------------------------------------------------------------- + +static +r_obj* vec_shape2(r_obj* x, + r_obj* y, + struct vctrs_arg* p_x_arg, + struct vctrs_arg* p_y_arg) { + r_obj* x_dimensions = KEEP(r_dim(x)); + r_obj* y_dimensions = KEEP(r_dim(y)); - SEXP out = vec_shape2_impl(x_dimensions, y_dimensions, x, y, p_x_arg, p_y_arg); + r_obj* out = vec_shape2_impl(x_dimensions, y_dimensions, x, y, p_x_arg, p_y_arg); - UNPROTECT(2); + FREE(2); return out; } -static SEXP vec_shape(SEXP dimensions); -static inline int vec_dimension2(int x_dimension, int y_dimension, - int axis, - SEXP x, SEXP y, - struct vctrs_arg* p_x_arg, struct vctrs_arg* p_y_arg); +r_obj* ffi_vec_shape2(r_obj* x, r_obj* y, r_obj* frame) { + struct r_lazy x_arg_ = { .x = syms.x_arg, .env = frame }; + struct vctrs_arg x_arg = new_lazy_arg(&x_arg_); + + struct r_lazy y_arg_ = { .x = syms.y_arg, .env = frame }; + struct vctrs_arg y_arg = new_lazy_arg(&y_arg_); + + return vec_shape2(x, y, &x_arg, &y_arg); +} + /* * Returns `NULL` if `x` and `y` are atomic. * Otherwise returns a dimensions vector where the first dimension length * is forcibly set to 0, and the rest are the common shape of `x` and `y`. */ -static SEXP vec_shape2_impl(SEXP x_dimensions, SEXP y_dimensions, - SEXP x, SEXP y, - struct vctrs_arg* p_x_arg, struct vctrs_arg* p_y_arg) { - if (x_dimensions == R_NilValue) { +static +r_obj* vec_shape2_impl(r_obj* x_dimensions, + r_obj* y_dimensions, + r_obj* x, + r_obj* y, + struct vctrs_arg* p_x_arg, + struct vctrs_arg* p_y_arg) { + if (x_dimensions == r_null) { return vec_shape(y_dimensions); } - if (y_dimensions == R_NilValue) { + if (y_dimensions == r_null) { return vec_shape(x_dimensions); } - R_len_t x_dimensionality = Rf_length(x_dimensions); - R_len_t y_dimensionality = Rf_length(y_dimensions); + r_ssize x_dimensionality = r_length(x_dimensions); + r_ssize y_dimensionality = r_length(y_dimensions); - SEXP max_dimensions; - R_len_t max_dimensionality; - R_len_t min_dimensionality; + r_obj* max_dimensions; + r_ssize max_dimensionality; + r_ssize min_dimensionality; if (x_dimensionality >= y_dimensionality) { max_dimensions = x_dimensions; @@ -105,18 +102,18 @@ static SEXP vec_shape2_impl(SEXP x_dimensions, SEXP y_dimensions, r_stop_internal("`max_dimensionality` must have length."); } - const int* p_x_dimensions = INTEGER_RO(x_dimensions); - const int* p_y_dimensions = INTEGER_RO(y_dimensions); - const int* p_max_dimensions = INTEGER_RO(max_dimensions); + const int* p_x_dimensions = r_int_cbegin(x_dimensions); + const int* p_y_dimensions = r_int_cbegin(y_dimensions); + const int* p_max_dimensions = r_int_cbegin(max_dimensions); - SEXP out = PROTECT(Rf_allocVector(INTSXP, max_dimensionality)); - int* p_out = INTEGER(out); + r_obj* out = KEEP(r_alloc_integer(max_dimensionality)); + int* p_out = r_int_begin(out); // Set the first axis to zero p_out[0] = 0; // Start loop at the second axis - R_len_t i = 1; + r_ssize i = 1; for (; i < min_dimensionality; ++i) { const int axis = i + 1; @@ -130,38 +127,44 @@ static SEXP vec_shape2_impl(SEXP x_dimensions, SEXP y_dimensions, p_out[i] = p_max_dimensions[i]; } - UNPROTECT(1); + FREE(1); return out; } + // ----------------------------------------------------------------------------- // Sets the first axis to zero -static SEXP vec_shape(SEXP dimensions) { - if (dimensions == R_NilValue) { - return R_NilValue; +static +r_obj* vec_shape(r_obj* dimensions) { + if (dimensions == r_null) { + return r_null; } - dimensions = PROTECT(r_clone_referenced(dimensions)); + dimensions = KEEP(r_clone_referenced(dimensions)); - if (Rf_length(dimensions) == 0) { + if (r_length(dimensions) == 0) { r_stop_internal("`dimensions` must have length."); } - if (TYPEOF(dimensions) != INTSXP) { + if (r_typeof(dimensions) != R_TYPE_integer) { r_stop_internal("`dimensions` must be an integer vector."); } - INTEGER(dimensions)[0] = 0; + r_int_begin(dimensions)[0] = 0; - UNPROTECT(1); + FREE(1); return dimensions; } -static inline int vec_dimension2(int x_dimension, int y_dimension, - int axis, - SEXP x, SEXP y, - struct vctrs_arg* p_x_arg, struct vctrs_arg* p_y_arg) { +static inline +int vec_dimension2(int x_dimension, + int y_dimension, + int axis, + r_obj* x, + r_obj* y, + struct vctrs_arg* p_x_arg, + struct vctrs_arg* p_y_arg) { if (x_dimension == y_dimension) { return x_dimension; } else if (x_dimension == 1) { From 96ce2d077e318113919979a31dc17d43c0498fa0 Mon Sep 17 00:00:00 2001 From: Davis Vaughan Date: Thu, 15 Sep 2022 10:57:21 -0400 Subject: [PATCH 063/312] Call out complex as an incomparable type (#1659) * Call out complex as an incomparable type * NEWS bullet * Don't mention function name in error message Since the call will do this for us --- NEWS.md | 3 +++ src/compare.c | 20 ++++++++++++-------- tests/testthat/_snaps/compare.md | 9 +++++++++ tests/testthat/test-compare.R | 6 ++++++ 4 files changed, 30 insertions(+), 8 deletions(-) create mode 100644 tests/testthat/_snaps/compare.md diff --git a/NEWS.md b/NEWS.md index 0e1ca6d35..85d09cbcb 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,5 +1,8 @@ # vctrs (development version) +* `vec_compare()` now throws a more informative error when attempting to compare + complex vectors (#1655). + * `vec_rep()` and friends gain `call`, `x_arg`, and `times_arg` arguments so they can be embedded in frontends (#1303). diff --git a/src/compare.c b/src/compare.c index 4a76ad030..dbfeb662c 100644 --- a/src/compare.c +++ b/src/compare.c @@ -50,8 +50,9 @@ r_obj* vec_compare(r_obj* x, r_obj* y, bool na_equal) { case VCTRS_TYPE_integer: COMPARE(int, r_int_cbegin, int_compare_na_equal); case VCTRS_TYPE_double: COMPARE(double, r_dbl_cbegin, dbl_compare_na_equal); case VCTRS_TYPE_character: COMPARE(r_obj*, r_chr_cbegin, chr_compare_na_equal); - case VCTRS_TYPE_scalar: r_abort("Can't compare scalars with `vec_compare()`"); - case VCTRS_TYPE_list: r_abort("Can't compare lists with `vec_compare()`"); + case VCTRS_TYPE_complex: r_abort("Can't compare complexes."); + case VCTRS_TYPE_scalar: r_abort("Can't compare scalars."); + case VCTRS_TYPE_list: r_abort("Can't compare lists."); default: stop_unimplemented_vctrs_type("vec_compare", type); } } else { @@ -60,8 +61,9 @@ r_obj* vec_compare(r_obj* x, r_obj* y, bool na_equal) { case VCTRS_TYPE_integer: COMPARE(int, r_int_cbegin, int_compare_na_propagate); case VCTRS_TYPE_double: COMPARE(double, r_dbl_cbegin, dbl_compare_na_propagate); case VCTRS_TYPE_character: COMPARE(r_obj*, r_chr_cbegin, chr_compare_na_propagate); - case VCTRS_TYPE_scalar: r_abort("Can't compare scalars with `vec_compare()`"); - case VCTRS_TYPE_list: r_abort("Can't compare lists with `vec_compare()`"); + case VCTRS_TYPE_complex: r_abort("Can't compare complexes."); + case VCTRS_TYPE_scalar: r_abort("Can't compare scalars."); + case VCTRS_TYPE_list: r_abort("Can't compare lists."); default: stop_unimplemented_vctrs_type("vec_compare", type); } } @@ -168,8 +170,9 @@ void vec_compare_col(int* v_out, case VCTRS_TYPE_integer: COMPARE_COL(int, r_int_cbegin, int_compare_na_equal); break; case VCTRS_TYPE_double: COMPARE_COL(double, r_dbl_cbegin, dbl_compare_na_equal); break; case VCTRS_TYPE_character: COMPARE_COL(r_obj*, r_chr_cbegin, chr_compare_na_equal); break; - case VCTRS_TYPE_scalar: r_abort("Can't compare scalars with `vec_compare()`"); - case VCTRS_TYPE_list: r_abort("Can't compare lists with `vec_compare()`"); + case VCTRS_TYPE_complex: r_abort("Can't compare complexes."); + case VCTRS_TYPE_scalar: r_abort("Can't compare scalars."); + case VCTRS_TYPE_list: r_abort("Can't compare lists."); default: stop_unimplemented_vctrs_type("vec_compare_col", type); } } else { @@ -178,8 +181,9 @@ void vec_compare_col(int* v_out, case VCTRS_TYPE_integer: COMPARE_COL(int, r_int_cbegin, int_compare_na_propagate); break; case VCTRS_TYPE_double: COMPARE_COL(double, r_dbl_cbegin, dbl_compare_na_propagate); break; case VCTRS_TYPE_character: COMPARE_COL(r_obj*, r_chr_cbegin, chr_compare_na_propagate); break; - case VCTRS_TYPE_scalar: r_abort("Can't compare scalars with `vec_compare()`"); - case VCTRS_TYPE_list: r_abort("Can't compare lists with `vec_compare()`"); + case VCTRS_TYPE_complex: r_abort("Can't compare complexes."); + case VCTRS_TYPE_scalar: r_abort("Can't compare scalars."); + case VCTRS_TYPE_list: r_abort("Can't compare lists."); default: stop_unimplemented_vctrs_type("vec_compare_col", type); } } diff --git a/tests/testthat/_snaps/compare.md b/tests/testthat/_snaps/compare.md new file mode 100644 index 000000000..16cc0a3eb --- /dev/null +++ b/tests/testthat/_snaps/compare.md @@ -0,0 +1,9 @@ +# error is thrown when comparing complexes (#1655) + + Code + (expect_error(vec_compare(complex(), complex()))) + Output + + Error in `vec_compare()`: + ! Can't compare complexes. + diff --git a/tests/testthat/test-compare.R b/tests/testthat/test-compare.R index 7a4207fff..b4926db0e 100644 --- a/tests/testthat/test-compare.R +++ b/tests/testthat/test-compare.R @@ -200,6 +200,12 @@ test_that("vec_proxy_order() works on deeply nested lists", { expect_identical(vec_proxy_order(df2), data_frame(x = c(1L, 2L, 1L), y = 1:3)) }) +test_that("error is thrown when comparing complexes (#1655)", { + expect_snapshot({ + (expect_error(vec_compare(complex(), complex()))) + }) +}) + test_that("error is thrown when comparing lists", { expect_error(vec_compare(list(), list()), class = "vctrs_error_unsupported") expect_error(.Call(ffi_vec_compare, list(), list(), FALSE), "Can't compare lists") From 833902b741a3883412062c08b30feadf1cc41ead Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Wed, 14 Sep 2022 14:48:43 +0200 Subject: [PATCH 064/312] Preserve shape in native dispatch Closes #1290 Closes #1329 --- NEWS.md | 2 ++ src/cast.c | 19 +++++++++++-------- src/ptype2.c | 2 +- src/shape.c | 23 +++++++++++++++++++++++ src/shape.h | 5 +++++ tests/testthat/_snaps/shape.md | 9 +++++++++ tests/testthat/test-shape.R | 20 ++++++++++++++++++++ 7 files changed, 71 insertions(+), 9 deletions(-) diff --git a/NEWS.md b/NEWS.md index 85d09cbcb..844d210df 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,5 +1,7 @@ # vctrs (development version) +* Native classes like dates and datetimes now accept dimensions (#1290, #1329). + * `vec_compare()` now throws a more informative error when attempting to compare complex vectors (#1655). diff --git a/src/cast.c b/src/cast.c index 5c3c29ef4..6591b9986 100644 --- a/src/cast.c +++ b/src/cast.c @@ -50,24 +50,27 @@ r_obj* vec_cast_opts(const struct cast_opts* opts) { stop_scalar_type(to, to_arg, opts->call); } - if (has_dim(x) || has_dim(to)) { - return vec_cast_dispatch_s3(opts); - } - r_obj* out = r_null; bool lossy = false; if (to_type == VCTRS_TYPE_s3 || x_type == VCTRS_TYPE_s3) { - out = vec_cast_dispatch_native(opts, x_type, to_type, &lossy); + out = KEEP(vec_cast_dispatch_native(opts, x_type, to_type, &lossy)); } else { - out = vec_cast_switch_native(opts, x_type, to_type, &lossy); + out = KEEP(vec_cast_switch_native(opts, x_type, to_type, &lossy)); } if (lossy || out == r_null) { + // This broadcasts dimensions too + FREE(1); return vec_cast_dispatch_s3(opts); - } else { - return out; } + + if (has_dim(x) || has_dim(to)) { + out = vec_shape_broadcast(out, opts); + } + + FREE(1); + return out; } static diff --git a/src/ptype2.c b/src/ptype2.c index e3cd974d3..e6e091bc2 100644 --- a/src/ptype2.c +++ b/src/ptype2.c @@ -67,7 +67,7 @@ r_obj* vec_ptype2_opts_impl(const struct ptype2_opts* opts, if (x_type == VCTRS_TYPE_s3 || y_type == VCTRS_TYPE_s3) { r_obj* out = vec_ptype2_dispatch_native(opts, x_type, y_type, left); if (out != r_null) { - return out; + return vec_shaped_ptype(out, x, y, x_arg, y_arg); } } diff --git a/src/shape.c b/src/shape.c index 5a6646bea..5ce2adbd1 100644 --- a/src/shape.c +++ b/src/shape.c @@ -175,3 +175,26 @@ int vec_dimension2(int x_dimension, stop_incompatible_shape(x, y, x_dimension, y_dimension, axis, p_x_arg, p_y_arg); } } + + +// ----------------------------------------------------------------------------- + +r_obj* vec_shape_broadcast(r_obj* out, const struct cast_opts* p_opts) { + r_obj* r_x_arg = KEEP(vctrs_arg(p_opts->p_x_arg)); + r_obj* r_to_arg = KEEP(vctrs_arg(p_opts->p_to_arg)); + r_obj* call = KEEP(r_lazy_eval(p_opts->call)); + + out = KEEP(r_clone_referenced(out)); + + r_attrib_poke_dim(out, r_dim(p_opts->x)); + r_attrib_poke_dim_names(out, r_dim_names(p_opts->x)); + + out = vctrs_eval_mask5(r_sym("shape_broadcast"), + r_syms.x, out, + r_sym("to"), p_opts->to, + syms.x_arg, r_x_arg, + syms.to_arg, r_to_arg, + r_syms.call, call); + FREE(4); + return out; +} diff --git a/src/shape.h b/src/shape.h index 408060816..17cf2d987 100644 --- a/src/shape.h +++ b/src/shape.h @@ -2,9 +2,14 @@ #define VCTRS_SHAPE_H #include "vctrs-core.h" +#include "cast.h" + SEXP vec_shaped_ptype(SEXP ptype, SEXP x, SEXP y, struct vctrs_arg* p_x_arg, struct vctrs_arg* p_y_arg); +r_obj* vec_shape_broadcast(r_obj* out, const struct cast_opts* p_opts); + + #endif diff --git a/tests/testthat/_snaps/shape.md b/tests/testthat/_snaps/shape.md index 8ef1a4381..07650884f 100644 --- a/tests/testthat/_snaps/shape.md +++ b/tests/testthat/_snaps/shape.md @@ -28,3 +28,12 @@ ! Can't combine `foo` and `bar` . x Incompatible sizes 0 and 5 along axis 2. +# can combine shaped native classes (#1290, #1329) + + Code + vec_c(x, y) + Condition + Error: + ! Can't combine `..1` > and `..2` >. + x Incompatible sizes 2 and 3 along axis 2. + diff --git a/tests/testthat/test-shape.R b/tests/testthat/test-shape.R index 3542d439c..da250d95f 100644 --- a/tests/testthat/test-shape.R +++ b/tests/testthat/test-shape.R @@ -83,3 +83,23 @@ test_that("shape_broadcast_() applies recycling rules", { class = "vctrs_error_incompatible_type" ) }) + +test_that("can combine shaped native classes (#1290, #1329)", { + x <- Sys.time() + c(1, 1e6) + dim(x) <- c(1, 2) + out <- vec_c(x, x) + + expect_s3_class(out, c("POSIXct", "POSIXt")) + expect_dim(out, c(2, 2)) + + y <- Sys.time() + 1:3 + dim(y) <- c(1, 3) + + expect_snapshot(error = TRUE, vec_c(x, y)) + + d <- structure(Sys.Date(), dim = 1) + expect_equal( + vec_rbind(data.frame(d), data.frame(d)), + data.frame(d = structure(rep(Sys.Date(), 2), dim = 2)) + ) +}) From 41bc8e37fa5ff9adb57adceb79fae4fc91000b55 Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Thu, 15 Sep 2022 10:59:59 +0200 Subject: [PATCH 065/312] Protect result before calling `vec_shaped_ptype()` --- src/ptype2.c | 9 +++++++-- 1 file changed, 7 insertions(+), 2 deletions(-) diff --git a/src/ptype2.c b/src/ptype2.c index e6e091bc2..ee361de8c 100644 --- a/src/ptype2.c +++ b/src/ptype2.c @@ -65,10 +65,15 @@ r_obj* vec_ptype2_opts_impl(const struct ptype2_opts* opts, } if (x_type == VCTRS_TYPE_s3 || y_type == VCTRS_TYPE_s3) { - r_obj* out = vec_ptype2_dispatch_native(opts, x_type, y_type, left); + r_obj* out = KEEP(vec_ptype2_dispatch_native(opts, x_type, y_type, left)); + if (out != r_null) { - return vec_shaped_ptype(out, x, y, x_arg, y_arg); + out = vec_shaped_ptype(out, x, y, x_arg, y_arg); + FREE(1); + return out; } + + FREE(1); } // Try native dispatch again with prototypes, in case the prototype From f1a7423f395ce3099476432bcfa7bdc86d80e6e0 Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Fri, 16 Sep 2022 16:17:37 +0200 Subject: [PATCH 066/312] Tweak tests --- tests/testthat/test-shape.R | 22 ++++++++++++++++++++-- 1 file changed, 20 insertions(+), 2 deletions(-) diff --git a/tests/testthat/test-shape.R b/tests/testthat/test-shape.R index da250d95f..06b79cf1c 100644 --- a/tests/testthat/test-shape.R +++ b/tests/testthat/test-shape.R @@ -85,14 +85,14 @@ test_that("shape_broadcast_() applies recycling rules", { }) test_that("can combine shaped native classes (#1290, #1329)", { - x <- Sys.time() + c(1, 1e6) + x <- new_datetime(c(1, 1e6)) dim(x) <- c(1, 2) out <- vec_c(x, x) expect_s3_class(out, c("POSIXct", "POSIXt")) expect_dim(out, c(2, 2)) - y <- Sys.time() + 1:3 + y <- new_datetime(1:3 + 0.0) dim(y) <- c(1, 3) expect_snapshot(error = TRUE, vec_c(x, y)) @@ -103,3 +103,21 @@ test_that("can combine shaped native classes (#1290, #1329)", { data.frame(d = structure(rep(Sys.Date(), 2), dim = 2)) ) }) + +test_that("factor casts support shape", { + x <- factor(c("x", "y", "z")) + dim(x) <- c(3, 1) + dimnames(x) <- list(c("r1", "r2", "r3"), "c1") + + y <- factor(c("w", "x", "y", "z")) + dim(y) <- c(2, 2) + + exp <- factor( + c("x", "y", "z", "x", "y", "z"), + levels = c("w", "x", "y", "z") + ) + dim(exp) <- c(3, 2) + dimnames(exp) <- list(c("r1", "r2", "r3"), c("c1", "c1")) + + expect_equal(vec_cast(x, y), exp) +}) From b724bbfe7be661e854d07f14c860f8752646da8a Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Fri, 16 Sep 2022 16:20:50 +0200 Subject: [PATCH 067/312] Give more details about dimension decrease --- R/shape.R | 7 ++++++- tests/testthat/_snaps/error-call.md | 2 +- tests/testthat/_snaps/shape.md | 9 +++++++++ tests/testthat/test-shape.R | 5 +++++ 4 files changed, 21 insertions(+), 2 deletions(-) diff --git a/R/shape.R b/R/shape.R index 2503856ad..a0f03e03a 100644 --- a/R/shape.R +++ b/R/shape.R @@ -37,10 +37,15 @@ shape_broadcast <- function(x, } if (length(dim_x) > length(dim_to)) { + details <- sprintf( + "Can't decrease dimensions from %s to %s.", + length(dim_x), + length(dim_to) + ) stop_incompatible_cast( x, to, - details = "Cannot decrease dimensions.", + details = details, x_arg = x_arg, to_arg = to_arg, call = call diff --git a/tests/testthat/_snaps/error-call.md b/tests/testthat/_snaps/error-call.md index 1650117fd..d311ae02b 100644 --- a/tests/testthat/_snaps/error-call.md +++ b/tests/testthat/_snaps/error-call.md @@ -146,7 +146,7 @@ Error in `my_function()`: ! Can't convert `matrix(TRUE)` to . - Cannot decrease dimensions. + Can't decrease dimensions from 2 to 1. # base S3 casts report correct error call diff --git a/tests/testthat/_snaps/shape.md b/tests/testthat/_snaps/shape.md index 07650884f..7f5aff14c 100644 --- a/tests/testthat/_snaps/shape.md +++ b/tests/testthat/_snaps/shape.md @@ -37,3 +37,12 @@ ! Can't combine `..1` > and `..2` >. x Incompatible sizes 2 and 3 along axis 2. +# factor casts support shape + + Code + vec_cast(x, y) + Condition + Error: + ! Can't convert `x` > to >. + Can't decrease dimensions from 2 to 1. + diff --git a/tests/testthat/test-shape.R b/tests/testthat/test-shape.R index 06b79cf1c..b82430699 100644 --- a/tests/testthat/test-shape.R +++ b/tests/testthat/test-shape.R @@ -120,4 +120,9 @@ test_that("factor casts support shape", { dimnames(exp) <- list(c("r1", "r2", "r3"), c("c1", "c1")) expect_equal(vec_cast(x, y), exp) + + x <- factor(c("x", "y", "z")) + dim(x) <- c(3, 1) + y <- factor(c("x", "y", "z")) + expect_snapshot(error = TRUE, vec_cast(x, y)) }) From 77cb8123c95f40bb783bb9952ce7f6af23db5546 Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Fri, 16 Sep 2022 16:23:44 +0200 Subject: [PATCH 068/312] Mention shape in ptype-full factor method --- R/type-factor.R | 4 ++-- tests/testthat/_snaps/shape.md | 2 +- 2 files changed, 3 insertions(+), 3 deletions(-) diff --git a/R/type-factor.R b/R/type-factor.R index d502d7f5c..16ca045be 100644 --- a/R/type-factor.R +++ b/R/type-factor.R @@ -58,7 +58,7 @@ vec_restore.ordered <- function(x, to, ...) { #' @export vec_ptype_full.factor <- function(x, ...) { - paste0("factor<", hash_label(levels(x)), ">") + paste0("factor<", hash_label(levels(x)), ">", vec_ptype_shape(x)) } #' @export @@ -68,7 +68,7 @@ vec_ptype_abbr.factor <- function(x, ...) { #' @export vec_ptype_full.ordered <- function(x, ...) { - paste0("ordered<", hash_label(levels(x)), ">") + paste0("ordered<", hash_label(levels(x)), ">", vec_ptype_shape(x)) } #' @export diff --git a/tests/testthat/_snaps/shape.md b/tests/testthat/_snaps/shape.md index 7f5aff14c..5a1832535 100644 --- a/tests/testthat/_snaps/shape.md +++ b/tests/testthat/_snaps/shape.md @@ -43,6 +43,6 @@ vec_cast(x, y) Condition Error: - ! Can't convert `x` > to >. + ! Can't convert `x` [,1]> to >. Can't decrease dimensions from 2 to 1. From b3cfb6bb8e4e5500190dd51d5b30c9407ea93f40 Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Fri, 16 Sep 2022 16:37:45 +0200 Subject: [PATCH 069/312] Use "dimensionality" term --- R/shape.R | 2 +- tests/testthat/_snaps/error-call.md | 2 +- tests/testthat/_snaps/shape.md | 2 +- 3 files changed, 3 insertions(+), 3 deletions(-) diff --git a/R/shape.R b/R/shape.R index a0f03e03a..3d2ac18f9 100644 --- a/R/shape.R +++ b/R/shape.R @@ -38,7 +38,7 @@ shape_broadcast <- function(x, if (length(dim_x) > length(dim_to)) { details <- sprintf( - "Can't decrease dimensions from %s to %s.", + "Can't decrease dimensionality from %s to %s.", length(dim_x), length(dim_to) ) diff --git a/tests/testthat/_snaps/error-call.md b/tests/testthat/_snaps/error-call.md index d311ae02b..efa833e17 100644 --- a/tests/testthat/_snaps/error-call.md +++ b/tests/testthat/_snaps/error-call.md @@ -146,7 +146,7 @@ Error in `my_function()`: ! Can't convert `matrix(TRUE)` to . - Can't decrease dimensions from 2 to 1. + Can't decrease dimensionality from 2 to 1. # base S3 casts report correct error call diff --git a/tests/testthat/_snaps/shape.md b/tests/testthat/_snaps/shape.md index 5a1832535..2eb381093 100644 --- a/tests/testthat/_snaps/shape.md +++ b/tests/testthat/_snaps/shape.md @@ -44,5 +44,5 @@ Condition Error: ! Can't convert `x` [,1]> to >. - Can't decrease dimensions from 2 to 1. + Can't decrease dimensionality from 2 to 1. From 005788ded7d7dc88e1cf767b0597c4f72674b5f4 Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Fri, 16 Sep 2022 16:58:16 +0200 Subject: [PATCH 070/312] Update snapshot test for table dimensionality error --- tests/testthat/_snaps/type-table.md | 10 ++++++++++ tests/testthat/test-type-table.R | 4 +++- 2 files changed, 13 insertions(+), 1 deletion(-) create mode 100644 tests/testthat/_snaps/type-table.md diff --git a/tests/testthat/_snaps/type-table.md b/tests/testthat/_snaps/type-table.md new file mode 100644 index 000000000..80272e206 --- /dev/null +++ b/tests/testthat/_snaps/type-table.md @@ -0,0 +1,10 @@ +# cannot decrease dimensionality + + Code + (expect_error(vec_cast(x, y), class = "vctrs_error_incompatible_type")) + Output + + Error: + ! Can't convert `x` to . + Can't decrease dimensionality from 3 to 2. + diff --git a/tests/testthat/test-type-table.R b/tests/testthat/test-type-table.R index d9a127cda..9d33a8a24 100644 --- a/tests/testthat/test-type-table.R +++ b/tests/testthat/test-type-table.R @@ -126,7 +126,9 @@ test_that("cannot decrease dimensionality", { x <- new_table(dim = c(0L, 1L, 1L)) y <- new_table(dim = c(0L, 1L)) - expect_error(vec_cast(x, y), "decrease dimensions", class = "vctrs_error_incompatible_type") + expect_snapshot({ + (expect_error(vec_cast(x, y), class = "vctrs_error_incompatible_type")) + }) }) test_that("vec_cast() errors on non-tables", { From f3c5c51c1ba9049fea62a661a9bfeaf9bf92d557 Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Fri, 16 Sep 2022 17:23:48 +0200 Subject: [PATCH 071/312] Remove `vec_list_cast()` Closes #1382 --- NAMESPACE | 1 - NEWS.md | 3 +++ R/cast-list.R | 47 --------------------------------- man/vec_list_cast.Rd | 26 ------------------ tests/testthat/test-cast-list.R | 18 ------------- 5 files changed, 3 insertions(+), 92 deletions(-) delete mode 100644 R/cast-list.R delete mode 100644 man/vec_list_cast.Rd delete mode 100644 tests/testthat/test-cast-list.R diff --git a/NAMESPACE b/NAMESPACE index 189ec626d..e4c2e8bef 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -565,7 +565,6 @@ export(vec_interleave) export(vec_is) export(vec_is_empty) export(vec_is_list) -export(vec_list_cast) export(vec_locate_matches) export(vec_locate_sorted_groups) export(vec_match) diff --git a/NEWS.md b/NEWS.md index 844d210df..8bf11e9c1 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,5 +1,8 @@ # vctrs (development version) +* The experimental function `vec_list_cast()` has been removed from + the package (#1382). + * Native classes like dates and datetimes now accept dimensions (#1290, #1329). * `vec_compare()` now throws a more informative error when attempting to compare diff --git a/R/cast-list.R b/R/cast-list.R deleted file mode 100644 index f78e37358..000000000 --- a/R/cast-list.R +++ /dev/null @@ -1,47 +0,0 @@ -#' Cast a list to vector of specific type -#' -#' This is a function for developers to use when extending vctrs. It casts -#' a list to a more specific vectoring type, keeping the length constant. -#' It does this by discarding (with a warning), any elements after the 1. -#' It is called from `vec_cast.XYZ.list()` methods to preserve symmetry with -#' `vec_cast.list.XYZ()`. -#' -#' See `vignette("s3-vector")` for details. -#' -#' @param x A list -#' @param to Type to coerce to -#' @inheritParams rlang::args_dots_empty -#' -#' @export -#' @keywords internal -vec_list_cast <- function(x, to, ..., x_arg = "", to_arg = "") { - check_dots_empty0(...) - - ns <- map_int(x, vec_size) - - n <- vec_size(x) - out <- vec_init(to, n) - - for (i in seq_len(n)) { - val <- x[[i]] - if (vec_size(val) == 0) { - next - } - - val <- vec_slice(val, 1L) - vec_slice(out, i) <- vec_cast(val, to, x_arg = x_arg, to_arg = to_arg) - } - - if (!is.object(to)) { - out <- shape_broadcast(out, to, x_arg = x_arg, to_arg = to_arg) - } - - maybe_lossy_cast( - out, - x, - to, - lossy = !ns %in% c(0L, 1L), - x_arg = x_arg, - to_arg = to_arg - ) -} diff --git a/man/vec_list_cast.Rd b/man/vec_list_cast.Rd deleted file mode 100644 index 788682b69..000000000 --- a/man/vec_list_cast.Rd +++ /dev/null @@ -1,26 +0,0 @@ -% Generated by roxygen2: do not edit by hand -% Please edit documentation in R/cast-list.R -\name{vec_list_cast} -\alias{vec_list_cast} -\title{Cast a list to vector of specific type} -\usage{ -vec_list_cast(x, to, ..., x_arg = "", to_arg = "") -} -\arguments{ -\item{x}{A list} - -\item{to}{Type to coerce to} - -\item{...}{These dots are for future extensions and must be empty.} -} -\description{ -This is a function for developers to use when extending vctrs. It casts -a list to a more specific vectoring type, keeping the length constant. -It does this by discarding (with a warning), any elements after the 1. -It is called from \code{vec_cast.XYZ.list()} methods to preserve symmetry with -\code{vec_cast.list.XYZ()}. -} -\details{ -See \code{vignette("s3-vector")} for details. -} -\keyword{internal} diff --git a/tests/testthat/test-cast-list.R b/tests/testthat/test-cast-list.R deleted file mode 100644 index 46d623f4e..000000000 --- a/tests/testthat/test-cast-list.R +++ /dev/null @@ -1,18 +0,0 @@ - -test_that("silently extracts elements of length 1", { - expect_equal(vec_list_cast(list(1, 2), double()), c(1, 2)) -}) - -test_that("elements of length 0 become NA without error", { - x <- list(1, double()) - out <- vec_list_cast(x, double()) - expect_equal(out, c(1, NA)) -}) - -test_that("elements of length >1 are truncated with error", { - x <- list(1, c(2, 1), c(3, 2, 1)) - expect_lossy(vec_list_cast(x, dbl()), dbl(1, 2, 3), x = list(), to = dbl()) - - x <- list(c(2, 1), c(3, 2, 1)) - expect_lossy(vec_list_cast(x, dbl()), dbl(2, 3), x = list(), to = dbl()) -}) From 04d12a7facf50b10abf3a3721d791468752c5cf0 Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Fri, 16 Sep 2022 17:35:05 +0200 Subject: [PATCH 072/312] Remove `vec_list_cast()` from pkgdown index --- _pkgdown.yml | 1 - 1 file changed, 1 deletion(-) diff --git a/_pkgdown.yml b/_pkgdown.yml index dd25a5813..ce18047fd 100644 --- a/_pkgdown.yml +++ b/_pkgdown.yml @@ -114,7 +114,6 @@ reference: - title: Developer tools contents: - vctr - - vec_list_cast - vec_ptype_full - vec_ptype_finalise - "vctrs-conditions" From d7cebc9ebcd02fd28aad055413f6ed826beade37 Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Fri, 16 Sep 2022 14:30:08 +0200 Subject: [PATCH 073/312] Cache `repair` string and add a character cache --- src/globals.c | 9 +++++++-- src/globals.h | 7 +++++++ 2 files changed, 14 insertions(+), 2 deletions(-) diff --git a/src/globals.c b/src/globals.c index 7aee6d2ad..cd193a12c 100644 --- a/src/globals.c +++ b/src/globals.c @@ -2,6 +2,7 @@ struct syms syms; struct strings strings; +struct chrs chrs; struct fns fns; struct vec_args vec_args; struct lazy_args lazy_args; @@ -18,9 +19,12 @@ struct r_dyn_array* globals_shelter = NULL; static struct vctrs_arg ARG; ARG = new_wrapper_arg(NULL, STR); \ vec_args.ARG = &ARG +// Defines both a string and a length 1 character vector #define INIT_STRING(ARG) \ strings.ARG = r_str(#ARG); \ - r_dyn_list_push_back(globals_shelter, strings.ARG); + r_dyn_list_push_back(globals_shelter, strings.ARG); \ + chrs.ARG = r_chr(#ARG); \ + r_dyn_list_push_back(globals_shelter, chrs.ARG); #define INIT_LAZY_ARG(ARG) \ lazy_args.ARG = (struct r_lazy) { .x = r_chr(#ARG), .env = r_null }; \ @@ -56,8 +60,9 @@ void vctrs_init_globals(r_obj* ns) { syms.x_arg = r_sym("x_arg"); syms.y_arg = r_sym("y_arg"); - // Strings ----------------------------------------------------------- + // Strings and characters -------------------------------------------- INIT_STRING(AsIs); + INIT_STRING(repair); // Args -------------------------------------------------------------- INIT_ARG2(dot_name_repair, ".name_repair"); diff --git a/src/globals.h b/src/globals.h index 3f61f3704..e76884ebe 100644 --- a/src/globals.h +++ b/src/globals.h @@ -22,8 +22,15 @@ struct syms { r_obj* y_arg; }; +// These structs must be in sync as their elements are defined +// together by the `INIT_STRING()` macro struct strings { r_obj* AsIs; + r_obj* repair; +}; +struct chrs { + r_obj* AsIs; + r_obj* repair; }; struct fns { From 2214b144a027d2db29399a5f580ca6ff99cf555f Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Fri, 16 Sep 2022 14:36:26 +0200 Subject: [PATCH 074/312] Distinguish between internal and user `repair_arg` errors --- R/names.R | 4 +- man/vec_as_names.Rd | 2 +- src/init.c | 4 +- src/names.c | 82 +++++++++++++++++++++++------ src/names.h | 10 ++-- tests/testthat/_snaps/conditions.md | 2 - tests/testthat/helper-conditions.R | 7 ++- 7 files changed, 82 insertions(+), 29 deletions(-) diff --git a/R/names.R b/R/names.R index 0083c37ca..364e00e7b 100644 --- a/R/names.R +++ b/R/names.R @@ -158,12 +158,12 @@ vec_as_names <- function(names, ..., repair = c("minimal", "unique", "universal", "check_unique"), - repair_arg = caller_arg(repair), + repair_arg = NULL, quiet = FALSE, call = caller_env()) { check_dots_empty0(...) .Call( - ffi_as_names, + ffi_vec_as_names, names, repair, quiet, diff --git a/man/vec_as_names.Rd b/man/vec_as_names.Rd index ada69129d..64c5df84c 100644 --- a/man/vec_as_names.Rd +++ b/man/vec_as_names.Rd @@ -8,7 +8,7 @@ vec_as_names( names, ..., repair = c("minimal", "unique", "universal", "check_unique"), - repair_arg = caller_arg(repair), + repair_arg = NULL, quiet = FALSE, call = caller_env() ) diff --git a/src/init.c b/src/init.c index c20fe0272..b1f338d48 100644 --- a/src/init.c +++ b/src/init.c @@ -88,7 +88,7 @@ extern r_obj* ffi_apply_name_spec(r_obj*, r_obj*, r_obj*, r_obj*); extern r_obj* ffi_unset_s4(r_obj*); extern SEXP vctrs_validate_name_repair_arg(SEXP); extern SEXP vctrs_validate_minimal_names(SEXP, SEXP); -extern r_obj* ffi_as_names(r_obj*, r_obj*, r_obj*, r_obj*); +extern r_obj* ffi_vec_as_names(r_obj*, r_obj*, r_obj*, r_obj*); extern r_obj* ffi_is_partial(r_obj*); extern SEXP vctrs_is_list(SEXP); extern SEXP vctrs_try_catch_callback(SEXP, SEXP); @@ -259,7 +259,7 @@ static const R_CallMethodDef CallEntries[] = { {"vctrs_altrep_rle_is_materialized", (DL_FUNC) &altrep_rle_is_materialized, 1}, {"vctrs_validate_name_repair_arg", (DL_FUNC) &vctrs_validate_name_repair_arg, 1}, {"vctrs_validate_minimal_names", (DL_FUNC) &vctrs_validate_minimal_names, 2}, - {"ffi_as_names", (DL_FUNC) &ffi_as_names, 4}, + {"ffi_vec_as_names", (DL_FUNC) &ffi_vec_as_names, 4}, {"ffi_is_partial", (DL_FUNC) &ffi_is_partial, 1}, {"vctrs_is_list", (DL_FUNC) &vctrs_is_list, 1}, {"vctrs_try_catch_callback", (DL_FUNC) &vctrs_try_catch_callback, 2}, diff --git a/src/names.c b/src/names.c index c6a84d403..4a22e9c88 100644 --- a/src/names.c +++ b/src/names.c @@ -22,16 +22,16 @@ r_obj* vec_as_names(r_obj* names, const struct name_repair_opts* opts) { r_stop_unreachable(); } -r_obj* ffi_as_names(r_obj* names, - r_obj* repair, - r_obj* ffi_quiet, - r_obj* frame) { +r_obj* ffi_vec_as_names(r_obj* names, + r_obj* repair, + r_obj* ffi_quiet, + r_obj* frame) { if (!r_is_bool(ffi_quiet)) { r_abort("`quiet` must a boolean value."); } bool quiet = r_lgl_get(ffi_quiet, 0); - struct r_lazy call = (struct r_lazy) { .x = syms_call, .env = frame }; + struct r_lazy call = (struct r_lazy) { .x = r_syms.call, .env = frame }; struct r_lazy repair_arg = { .x = syms.repair_arg, .env = frame }; struct name_repair_opts repair_opts = new_name_repair_opts(repair, @@ -46,6 +46,50 @@ r_obj* ffi_as_names(r_obj* names, return out; } + +struct repair_error_info { + r_obj* shelter; + r_obj* repair_arg; + r_obj* call; + r_obj* input_error_repair_arg; + r_obj* input_error_call; +}; + +struct repair_error_info new_repair_error_info(struct name_repair_opts* p_opts) { + struct r_lazy input_error_call = p_opts->call; + struct r_lazy input_error_repair_arg = p_opts->name_repair_arg; + + // If this is NULL, the `repair` value has been hard-coded by the + // frontend. Input errors are internal, and we provide no + // recommendation to fix user errors by providing a different value + // for `repair`. + if (p_opts->name_repair_arg.x == r_null) { + input_error_repair_arg = (struct r_lazy) { .x = strings.repair, .env = r_null }; + input_error_call = (struct r_lazy) { .x = p_opts->frame, .env = r_null }; + } + + struct repair_error_info out; + + out.shelter = r_new_list(4); + KEEP(out.shelter); + + out.repair_arg = r_lazy_eval(p_opts->name_repair_arg); + r_list_poke(out.shelter, 0, out.repair_arg); + + out.call = r_lazy_eval(p_opts->call); + r_list_poke(out.shelter, 1, out.call); + + out.input_error_repair_arg = r_lazy_eval(input_error_repair_arg); + r_list_poke(out.shelter, 2, out.input_error_repair_arg); + + out.input_error_call = r_lazy_eval(input_error_call); + r_list_poke(out.shelter, 3, out.input_error_call); + + FREE(1); + return out; +} + + r_obj* vec_as_universal_names(r_obj* names, bool quiet) { r_obj* quiet_obj = KEEP(r_lgl(quiet)); r_obj* out = vctrs_dispatch2(syms_as_universal_names, fns_as_universal_names, @@ -803,11 +847,13 @@ r_obj* vctrs_validate_name_repair_arg(r_obj* arg) { } } -void stop_name_repair(struct r_lazy call, - struct r_lazy name_repair_arg) { - r_abort_lazy_call(call, - "%s must be a string or a function. See `?vctrs::vec_as_names`.", - r_format_lazy_error_arg(name_repair_arg)); +void stop_name_repair(struct name_repair_opts* p_opts) { + struct repair_error_info info = new_repair_error_info(p_opts); + KEEP(info.shelter); + + r_abort_call(info.input_error_call, + "%s must be a string or a function. See `?vctrs::vec_as_names`.", + r_format_error_arg(info.input_error_repair_arg)); } struct name_repair_opts new_name_repair_opts(r_obj* name_repair, @@ -820,13 +866,13 @@ struct name_repair_opts new_name_repair_opts(r_obj* name_repair, .fn = r_null, .name_repair_arg = name_repair_arg, .quiet = quiet, - .call = call + .call = call, }; switch (r_typeof(name_repair)) { case R_TYPE_character: { if (!r_length(name_repair)) { - stop_name_repair(call, name_repair_arg); + stop_name_repair(&opts); } r_obj* c = r_chr_get(name_repair, 0); @@ -842,10 +888,12 @@ struct name_repair_opts new_name_repair_opts(r_obj* name_repair, } else if (c == strings_check_unique) { opts.type = NAME_REPAIR_check_unique; } else { - r_abort_lazy_call(call, - "%s can't be \"%s\". See `?vctrs::vec_as_names`.", - r_format_lazy_error_arg(name_repair_arg), - r_str_c_string(c)); + struct repair_error_info info = new_repair_error_info(&opts); + KEEP(info.shelter); + r_abort_call(info.input_error_call, + "%s can't be \"%s\". See `?vctrs::vec_as_names`.", + r_format_error_arg(info.input_error_repair_arg), + r_str_c_string(c)); } return opts; @@ -863,7 +911,7 @@ struct name_repair_opts new_name_repair_opts(r_obj* name_repair, return opts; default: - stop_name_repair(call, name_repair_arg); + stop_name_repair(&opts); } r_stop_unreachable(); diff --git a/src/names.h b/src/names.h index ffe7f0c1f..012e893db 100644 --- a/src/names.h +++ b/src/names.h @@ -31,8 +31,14 @@ struct name_repair_opts { r_obj* fn; bool quiet; struct r_lazy call; + r_obj* frame; }; +struct name_repair_opts new_name_repair_opts(r_obj* name_repair, + struct r_lazy name_repair_arg, + bool quiet, + struct r_lazy call); + r_obj* vec_as_universal_names(r_obj* names, bool quiet); r_obj* vec_as_custom_names(r_obj* names, const struct name_repair_opts* opts); @@ -45,10 +51,6 @@ static struct name_repair_opts const * const p_unique_repair_silent_opts = &uniq static struct name_repair_opts const * const p_no_repair_opts = &no_repair_opts; r_obj* vec_as_names(r_obj* names, const struct name_repair_opts* opts); -struct name_repair_opts new_name_repair_opts(r_obj* name_repair, - struct r_lazy name_repair_arg, - bool quiet, - struct r_lazy call); const char* name_repair_arg_as_c_string(enum name_repair_type type); bool is_unique_names(r_obj* names); r_obj* vec_as_unique_names(r_obj* names, bool quiet); diff --git a/tests/testthat/_snaps/conditions.md b/tests/testthat/_snaps/conditions.md index 73666a6a1..3a6e2b713 100644 --- a/tests/testthat/_snaps/conditions.md +++ b/tests/testthat/_snaps/conditions.md @@ -124,7 +124,6 @@ x These names are duplicated: * "x" at locations 1, 2, and 3. * "y" at locations 4 and 5. - i Use argument `"check_unique"` to specify repair strategy. Code (expect_error(vec_as_names(c(rep("x", 20), rep(c("a", "b", "c", "d", "e"), 2)), repair = "check_unique"), class = "vctrs_error_names_must_be_unique")) @@ -139,7 +138,6 @@ * "c" at locations 23 and 28. * "d" at locations 24 and 29. * ... - i Use argument `"check_unique"` to specify repair strategy. # lossy cast from character to factor mentions loss of generality diff --git a/tests/testthat/helper-conditions.R b/tests/testthat/helper-conditions.R index 356adb72c..dd0378eb2 100644 --- a/tests/testthat/helper-conditions.R +++ b/tests/testthat/helper-conditions.R @@ -80,5 +80,10 @@ my_vec_as_names <- function(my_names, ..., my_repair = "minimal", my_quiet = FALSE) { - vec_as_names(my_names, repair = my_repair, quiet = my_quiet) + vec_as_names( + my_names, + repair = my_repair, + repair_arg = "my_repair", + quiet = my_quiet + ) } From c1c8c2af782a5a9e02b4618bd281c6678bb81195 Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Fri, 16 Sep 2022 17:13:57 +0200 Subject: [PATCH 075/312] Actually use frame for internal calls --- src/globals.h | 1 + src/names.c | 41 ++++++++++++++++++++-------------- tests/testthat/_snaps/names.md | 15 +++++++++++++ tests/testthat/test-names.R | 7 ++++++ 4 files changed, 47 insertions(+), 17 deletions(-) diff --git a/src/globals.h b/src/globals.h index e76884ebe..0c5162a54 100644 --- a/src/globals.h +++ b/src/globals.h @@ -69,6 +69,7 @@ struct lazy_calls { extern struct syms syms; extern struct strings strings; +extern struct chrs chrs; extern struct fns fns; extern struct vec_args vec_args; extern struct lazy_args lazy_args; diff --git a/src/names.c b/src/names.c index 4a22e9c88..5cc7f5f11 100644 --- a/src/names.c +++ b/src/names.c @@ -39,6 +39,7 @@ r_obj* ffi_vec_as_names(r_obj* names, quiet, call); KEEP(repair_opts.shelter); + repair_opts.frame = frame; r_obj* out = vec_as_names(names, &repair_opts); @@ -56,18 +57,6 @@ struct repair_error_info { }; struct repair_error_info new_repair_error_info(struct name_repair_opts* p_opts) { - struct r_lazy input_error_call = p_opts->call; - struct r_lazy input_error_repair_arg = p_opts->name_repair_arg; - - // If this is NULL, the `repair` value has been hard-coded by the - // frontend. Input errors are internal, and we provide no - // recommendation to fix user errors by providing a different value - // for `repair`. - if (p_opts->name_repair_arg.x == r_null) { - input_error_repair_arg = (struct r_lazy) { .x = strings.repair, .env = r_null }; - input_error_call = (struct r_lazy) { .x = p_opts->frame, .env = r_null }; - } - struct repair_error_info out; out.shelter = r_new_list(4); @@ -79,11 +68,29 @@ struct repair_error_info new_repair_error_info(struct name_repair_opts* p_opts) out.call = r_lazy_eval(p_opts->call); r_list_poke(out.shelter, 1, out.call); - out.input_error_repair_arg = r_lazy_eval(input_error_repair_arg); - r_list_poke(out.shelter, 2, out.input_error_repair_arg); + // If this is NULL, the `repair` value has been hard-coded by the + // frontend. Input errors are internal, and we provide no + // recommendation to fix user errors by providing a different value + // for `repair`. + if (out.repair_arg == r_null) { + out.input_error_repair_arg = chrs.repair; + r_list_poke(out.shelter, 2, out.input_error_repair_arg); + + if (p_opts->frame) { + // This is only set when `vec_as_names()` is called from R + out.input_error_call = p_opts->frame; + } else { + // Create fake `vec_as_names()` call for the C case + out.input_error_call = r_call(r_sym("vec_as_names")); + } + r_list_poke(out.shelter, 3, out.input_error_call); + } else { + out.input_error_repair_arg = r_lazy_eval(p_opts->name_repair_arg); + r_list_poke(out.shelter, 2, out.input_error_repair_arg); - out.input_error_call = r_lazy_eval(input_error_call); - r_list_poke(out.shelter, 3, out.input_error_call); + out.input_error_call = r_lazy_eval(p_opts->call); + r_list_poke(out.shelter, 3, out.input_error_call); + } FREE(1); return out; @@ -866,7 +873,7 @@ struct name_repair_opts new_name_repair_opts(r_obj* name_repair, .fn = r_null, .name_repair_arg = name_repair_arg, .quiet = quiet, - .call = call, + .call = call }; switch (r_typeof(name_repair)) { diff --git a/tests/testthat/_snaps/names.md b/tests/testthat/_snaps/names.md index 0c1678c5e..6a64cc4aa 100644 --- a/tests/testthat/_snaps/names.md +++ b/tests/testthat/_snaps/names.md @@ -238,3 +238,18 @@ ! Can't merge the outer name `foo` with a vector of length > 1. Please supply a `.name_spec` specification. +# vec_as_names() uses internal error if `repair_arg` is not supplied + + Code + (expect_error(vec_as_names("", repair = "foobar", call = quote(tilt())))) + Output + + Error in `vec_as_names()`: + ! `repair` can't be "foobar". See `?vctrs::vec_as_names`. + Code + (expect_error(vec_as_names("", repair = env(), call = quote(tilt())))) + Output + + Error in `vec_as_names()`: + ! `repair` must be a string or a function. See `?vctrs::vec_as_names`. + diff --git a/tests/testthat/test-names.R b/tests/testthat/test-names.R index 9f370709e..63d2d9505 100644 --- a/tests/testthat/test-names.R +++ b/tests/testthat/test-names.R @@ -864,3 +864,10 @@ test_that("r_chr_paste_prefix() works", { paste0(long_prefix, ".", nms) ) }) + +test_that("vec_as_names() uses internal error if `repair_arg` is not supplied", { + expect_snapshot({ + (expect_error(vec_as_names("", repair = "foobar", call = quote(tilt())))) + (expect_error(vec_as_names("", repair = env(), call = quote(tilt())))) + }) +}) From b1517415360ab20d18b19edc942e3b430e8d04f0 Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Fri, 16 Sep 2022 17:34:06 +0200 Subject: [PATCH 076/312] Don't use `frame` and always create an internal call instead --- src/names.c | 9 +-------- src/names.h | 1 - 2 files changed, 1 insertion(+), 9 deletions(-) diff --git a/src/names.c b/src/names.c index 5cc7f5f11..0d1ee17db 100644 --- a/src/names.c +++ b/src/names.c @@ -39,7 +39,6 @@ r_obj* ffi_vec_as_names(r_obj* names, quiet, call); KEEP(repair_opts.shelter); - repair_opts.frame = frame; r_obj* out = vec_as_names(names, &repair_opts); @@ -76,13 +75,7 @@ struct repair_error_info new_repair_error_info(struct name_repair_opts* p_opts) out.input_error_repair_arg = chrs.repair; r_list_poke(out.shelter, 2, out.input_error_repair_arg); - if (p_opts->frame) { - // This is only set when `vec_as_names()` is called from R - out.input_error_call = p_opts->frame; - } else { - // Create fake `vec_as_names()` call for the C case - out.input_error_call = r_call(r_sym("vec_as_names")); - } + out.input_error_call = r_call(r_sym("vec_as_names")); r_list_poke(out.shelter, 3, out.input_error_call); } else { out.input_error_repair_arg = r_lazy_eval(p_opts->name_repair_arg); diff --git a/src/names.h b/src/names.h index 012e893db..7cb75ab13 100644 --- a/src/names.h +++ b/src/names.h @@ -31,7 +31,6 @@ struct name_repair_opts { r_obj* fn; bool quiet; struct r_lazy call; - r_obj* frame; }; struct name_repair_opts new_name_repair_opts(r_obj* name_repair, From 192f8c4186916bb8a96485c812cfad99369854d8 Mon Sep 17 00:00:00 2001 From: DavisVaughan Date: Fri, 16 Sep 2022 15:18:01 -0400 Subject: [PATCH 077/312] Remove `vec_order_base()` No longer needed by dplyr, so no need to keep it around --- R/order.R | 52 ---------------------------------------------------- 1 file changed, 52 deletions(-) diff --git a/R/order.R b/R/order.R index bc573bcca..47c7f167a 100644 --- a/R/order.R +++ b/R/order.R @@ -252,58 +252,6 @@ vec_order_info <- function(x, # ------------------------------------------------------------------------------ -#' Order vectors with base compatibility -#' -#' @description -#' `vec_order_base()` orders vectors using [base::order()], but can handle -#' more complex types, like data frames and [`vctrs_vctr`][vctr] objects, using -#' vctrs principles. -#' -#' `vec_order_base()` is mainly provided for backwards compatibility with vctrs -#' <= 0.3.7. New code should instead use [vec_order_radix()], which has more -#' capabilities. The main difference between the two is that `vec_order_radix()` -#' orders character vectors in the C locale (which is highly performant), while -#' `vec_order_base()` respects the system locale. -#' -#' @param x A vector -#' @param direction Direction to sort in. Defaults to `asc`ending. -#' @param na_value Should `NA`s be treated as the largest or smallest values? -#' @return An integer vector the same size as `x`. -#' -#' @section Differences with `order()`: -#' Unlike the `na.last` argument of `order()` which decides the positions of -#' missing values irrespective of the `decreasing` argument, the `na_value` -#' argument of `vec_order_base()` interacts with `direction`. If missing values -#' are considered the largest value, they will appear last in ascending order, -#' and first in descending order. -#' -#' @section Dependencies of `vec_order_base()`: -#' * [vec_proxy_order()] -#' -#' @noRd -#' @keywords internal -#' @examples -#' x <- round(c(runif(9), NA), 3) -#' vec_order_base(x) -#' vec_order_base(x, "desc") -#' -#' # Can also handle data frames -#' df <- data.frame(g = sample(2, 10, replace = TRUE), x = x) -#' vec_order_base(df) -#' vec_order_base(df, "desc") -#' -#' # Missing values interpreted as largest values are last when -#' # in increasing order: -#' vec_order_base(c(1, NA), na_value = "largest", direction = "asc") -#' vec_order_base(c(1, NA), na_value = "largest", direction = "desc") -vec_order_base <- function(x, - direction = c("asc", "desc"), - na_value = c("largest", "smallest")) { - vec_order(x = x, direction = direction, na_value = na_value) -} - -# ------------------------------------------------------------------------------ - #' Order and sort vectors #' #' @inheritParams rlang::args_dots_empty From 18331e287e8beb8b80d2e2f66cbf95e4ce851e7a Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Mon, 19 Sep 2022 15:41:45 +0200 Subject: [PATCH 078/312] Evaluate in the vctrs namespace rather than the caller environment Closes #1666 --- src/init.c | 1 + src/utils.c | 6 +----- tests/testthat/test-cast.R | 10 ++++++++++ tests/testthat/test-conditions.R | 13 ------------- 4 files changed, 12 insertions(+), 18 deletions(-) diff --git a/src/init.c b/src/init.c index b1f338d48..3ce079ec0 100644 --- a/src/init.c +++ b/src/init.c @@ -321,6 +321,7 @@ static const R_CallMethodDef CallEntries[] = { {"ffi_list_check_all_vectors", (DL_FUNC) &ffi_list_check_all_vectors, 2}, {"ffi_as_short_length", (DL_FUNC) &ffi_as_short_length, 2}, {"ffi_s3_get_method", (DL_FUNC) &ffi_s3_get_method, 3}, + {"ffi_exp_vec_cast", (DL_FUNC) &exp_vec_cast, 2}, {NULL, NULL, 0} }; diff --git a/src/utils.c b/src/utils.c index 98c25554b..1f35671f2 100644 --- a/src/utils.c +++ b/src/utils.c @@ -62,11 +62,7 @@ static SEXP vctrs_eval_mask_n_impl(SEXP fn_sym, SEXP fn, SEXP* syms, SEXP* args, * @param env The environment in which to evaluate. */ SEXP vctrs_eval_mask_n(SEXP fn, SEXP* syms, SEXP* args) { - SEXP mask = PROTECT(r_peek_frame()); - SEXP out = vctrs_eval_mask_n_impl(R_NilValue, fn, syms, args, mask); - - UNPROTECT(1); - return out; + return vctrs_eval_mask_n_impl(R_NilValue, fn, syms, args, vctrs_ns_env); } SEXP vctrs_eval_mask1(SEXP fn, SEXP x_sym, SEXP x) { diff --git a/tests/testthat/test-cast.R b/tests/testthat/test-cast.R index a6926ef21..752c1be62 100644 --- a/tests/testthat/test-cast.R +++ b/tests/testthat/test-cast.R @@ -256,3 +256,13 @@ test_that("vec_cast_common_fallback() works with tibbles", { expect_identical(vec_cast_common_fallback(tib, df), exp) expect_identical(vec_cast_common_fallback(df, tib), exp) }) + +test_that("can call `vec_cast()` from C (#1666)", { + fn <- inject(function(x, i) .Call(!!ffi_exp_vec_cast, x, i)) + environment(fn) <- ns_env("utils") + + x <- array(1, dim = c(1, 1)) + y <- array(2, dim = c(2, 2)) + + expect_equal(fn(x, y), vec_cast(x, y)) +}) diff --git a/tests/testthat/test-conditions.R b/tests/testthat/test-conditions.R index a4e020f70..acd72d22b 100644 --- a/tests/testthat/test-conditions.R +++ b/tests/testthat/test-conditions.R @@ -171,16 +171,3 @@ test_that("incompatible size errors", { (expect_error(stop_incompatible_size(1:2, 3:5, 2L, 3L, x_arg = quote(foo), y_arg = quote(bar)))) }) }) - -test_that("simplified backtraces include whole vctrs context", { - skip_on_cran() - - top <- current_env() - trace <- NULL - expect_error(withCallingHandlers(vec_slice(1, 2), error = function(...) { - trace <<- trace_back(top, sys.frame(-1L)) - })) - - trace_lines <- format(trace, simplify = "branch") - expect_true(any(grepl("vec_slice", trace_lines))) -}) From 413460f9bf3fa3f74d162e4d9b9605c5f9fa658a Mon Sep 17 00:00:00 2001 From: Davis Vaughan Date: Mon, 19 Sep 2022 10:00:07 -0400 Subject: [PATCH 079/312] Always apply specialized proxy methods recursively over data frames (#1664) * Add recursive `vec_proxy_compare()` and `vec_proxy_order()` rcrd methods * Add a proxy-order method for the rational class Required because now there is a `vec_proxy_order.vctrs_rcrd()` method that would otherwise sit in front of the `vec_proxy_compare.vctrs_rational()` method * Link test to PR * NEWS bullet * Remove unused default proxy-kind * Always recursively proxy data frame proxies This allows us to remove the data frame and record methods: - Data frames return themselves as the proxy by default, which is then automatically recursively proxied - Records fall through to `vec_proxy.vctrs_rcrd()`, which returns a data frame that is then proxied recursively * Revert changes to rational class and vignette * NEWS bullet updates * Add vignette spacing back in --- NAMESPACE | 4 -- NEWS.md | 11 +++++ R/compare.R | 2 + R/equal.R | 8 +++- R/type-data-frame.R | 24 ++-------- R/type-rcrd.R | 6 --- man/vec_proxy_compare.Rd | 9 ++++ man/vec_proxy_equal.Rd | 10 +++- src/decl/proxy-decl.h | 10 ++++ src/proxy.c | 73 +++++++++++++++++++++++------ src/vctrs.h | 3 +- tests/testthat/test-proxy.R | 32 +++++++++++++ tests/testthat/test-type-rational.R | 2 +- tests/testthat/test-type-rcrd.R | 35 ++++++++++---- 14 files changed, 170 insertions(+), 59 deletions(-) diff --git a/NAMESPACE b/NAMESPACE index e4c2e8bef..df6778dd2 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -299,20 +299,16 @@ S3method(vec_proxy,vctrs_vctr) S3method(vec_proxy_compare,AsIs) S3method(vec_proxy_compare,POSIXlt) S3method(vec_proxy_compare,array) -S3method(vec_proxy_compare,data.frame) S3method(vec_proxy_compare,default) S3method(vec_proxy_compare,list) S3method(vec_proxy_compare,raw) S3method(vec_proxy_equal,AsIs) S3method(vec_proxy_equal,POSIXlt) S3method(vec_proxy_equal,array) -S3method(vec_proxy_equal,data.frame) S3method(vec_proxy_equal,default) S3method(vec_proxy_equal,integer64) -S3method(vec_proxy_equal,vctrs_rcrd) S3method(vec_proxy_order,AsIs) S3method(vec_proxy_order,array) -S3method(vec_proxy_order,data.frame) S3method(vec_proxy_order,default) S3method(vec_proxy_order,list) S3method(vec_proxy_order,raw) diff --git a/NEWS.md b/NEWS.md index 8bf11e9c1..90d7a20b5 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,5 +1,16 @@ # vctrs (development version) +* If a data frame is returned as the proxy from `vec_proxy_equal()`, + `vec_proxy_compare()`, or `vec_proxy_order()`, then the corresponding proxy + function is now automatically applied recursively along all of the columns. + Additionally, packed data frame columns will be unpacked, and 1 column data + frames will be unwrapped. This ensures that the simplest possible types are + provided to the native C algorithms, improving both correctness and + performance (#1664). + +* When used with record vectors, `vec_proxy_compare()` and `vec_proxy_order()` + now call the correct proxy function while recursing over the fields (#1664). + * The experimental function `vec_list_cast()` has been removed from the package (#1382). diff --git a/R/compare.R b/R/compare.R index 0ff533c57..3c545004b 100644 --- a/R/compare.R +++ b/R/compare.R @@ -36,6 +36,8 @@ #' classes (with identical implementations) to avoid mismatches between #' comparison and sorting. #' +#' @inheritSection vec_proxy_equal Data frames +#' #' @param x A vector x. #' @inheritParams rlang::args_dots_empty #' @return A 1d atomic vector or a data frame. diff --git a/R/equal.R b/R/equal.R index 8ec317c55..80198524f 100644 --- a/R/equal.R +++ b/R/equal.R @@ -11,8 +11,12 @@ #' not equal-able, provide a `vec_proxy_equal()` method that throws an #' error. #' -#' If the proxy for `x` is a data frame, `vec_proxy_equal()` is -#' recursively applied on all columns as well. +#' @section Data frames: +#' If the proxy for `x` is a data frame, the proxy function is automatically +#' recursively applied on all columns as well. After applying the proxy +#' recursively, if there are any data frame columns present in the proxy, then +#' they are unpacked. Finally, if the resulting data frame only has a single +#' column, then it is unwrapped and a vector is returned as the proxy. #' #' @param x A vector x. #' @inheritParams rlang::args_dots_empty diff --git a/R/type-data-frame.R b/R/type-data-frame.R index 8a99de1ed..6e72e766e 100644 --- a/R/type-data-frame.R +++ b/R/type-data-frame.R @@ -174,30 +174,14 @@ vec_ptype_abbr.data.frame <- function(x, ...) { "df" } -#' @export -vec_proxy_equal.data.frame <- function(x, ...) { - df_proxy(x, VCTRS_PROXY_KIND_equal) -} - -#' @export -vec_proxy_compare.data.frame <- function(x, ...) { - df_proxy(x, VCTRS_PROXY_KIND_compare) -} - -#' @export -vec_proxy_order.data.frame <- function(x, ...) { - df_proxy(x, VCTRS_PROXY_KIND_order) -} - +# For testing # Keep in sync with `enum vctrs_proxy_kind` in `vctrs.h` -VCTRS_PROXY_KIND_default <- 0L -VCTRS_PROXY_KIND_equal <- 1L -VCTRS_PROXY_KIND_compare <- 2L -VCTRS_PROXY_KIND_order <- 3L - df_proxy <- function(x, kind) { .Call(ffi_df_proxy, x, kind) } +VCTRS_PROXY_KIND_equal <- 0L +VCTRS_PROXY_KIND_compare <- 1L +VCTRS_PROXY_KIND_order <- 2L df_is_coercible <- function(x, y, opts) { vec_is_coercible( diff --git a/R/type-rcrd.R b/R/type-rcrd.R index 6a1dbe227..6f8b9d531 100644 --- a/R/type-rcrd.R +++ b/R/type-rcrd.R @@ -40,12 +40,6 @@ vec_restore.vctrs_rcrd <- function(x, to, ...) { x } -#' @export -vec_proxy_equal.vctrs_rcrd <- function(x, ...) { - # Recursively proxy using a data frame - vec_proxy_equal(new_data_frame(x)) -} - #' @export length.vctrs_rcrd <- function(x) { vec_size(x) diff --git a/man/vec_proxy_compare.Rd b/man/vec_proxy_compare.Rd index e58143d6e..ff8f1ffc5 100644 --- a/man/vec_proxy_compare.Rd +++ b/man/vec_proxy_compare.Rd @@ -59,6 +59,15 @@ comparison and sorting. } } +\section{Data frames}{ + +If the proxy for \code{x} is a data frame, the proxy function is automatically +recursively applied on all columns as well. After applying the proxy +recursively, if there are any data frame columns present in the proxy, then +they are unpacked. Finally, if the resulting data frame only has a single +column, then it is unwrapped and a vector is returned as the proxy. +} + \examples{ # Lists are not comparable x <- list(1:2, 1, 1:2, 3) diff --git a/man/vec_proxy_equal.Rd b/man/vec_proxy_equal.Rd index 5fc119703..932cfb025 100644 --- a/man/vec_proxy_equal.Rd +++ b/man/vec_proxy_equal.Rd @@ -26,10 +26,16 @@ The default method calls \code{\link[=vec_proxy]{vec_proxy()}}, as the default u vector data should be equal-able in most cases. If your class is not equal-able, provide a \code{vec_proxy_equal()} method that throws an error. +} +\section{Data frames}{ -If the proxy for \code{x} is a data frame, \code{vec_proxy_equal()} is -recursively applied on all columns as well. +If the proxy for \code{x} is a data frame, the proxy function is automatically +recursively applied on all columns as well. After applying the proxy +recursively, if there are any data frame columns present in the proxy, then +they are unpacked. Finally, if the resulting data frame only has a single +column, then it is unwrapped and a vector is returned as the proxy. } + \section{Dependencies}{ \itemize{ diff --git a/src/decl/proxy-decl.h b/src/decl/proxy-decl.h index 046c5d40b..9ea60944a 100644 --- a/src/decl/proxy-decl.h +++ b/src/decl/proxy-decl.h @@ -10,6 +10,13 @@ r_obj* fns_vec_proxy_equal_array; r_obj* fns_vec_proxy_compare_array; r_obj* fns_vec_proxy_order_array; +static inline +r_obj* vec_proxy_equal_impl(r_obj* x); +static inline +r_obj* vec_proxy_compare_impl(r_obj* x); +static inline +r_obj* vec_proxy_order_impl(r_obj* x); + static inline r_obj* vec_proxy_equal_method(r_obj* x); @@ -27,3 +34,6 @@ r_obj* vec_proxy_order_method(r_obj* x); static inline r_obj* vec_proxy_order_invoke(r_obj* x, r_obj* method); + +static inline +r_obj* df_proxy(r_obj* x, enum vctrs_proxy_kind kind); diff --git a/src/proxy.c b/src/proxy.c index 140bfb856..b3616d374 100644 --- a/src/proxy.c +++ b/src/proxy.c @@ -20,28 +20,73 @@ r_obj* vec_proxy(r_obj* x) { // [[ register() ]] r_obj* vec_proxy_equal(r_obj* x) { - r_obj* method = KEEP(vec_proxy_equal_method(x)); - r_obj* out = vec_proxy_equal_invoke(x, method); + r_obj* out = KEEP(vec_proxy_equal_impl(x)); + + if (is_data_frame(out)) { + // Automatically proxy df-proxies recursively. + // Also flattens and unwraps them (#1537, #1664). + out = df_proxy(out, VCTRS_PROXY_KIND_equal); + } + FREE(1); return out; } // [[ register() ]] r_obj* vec_proxy_compare(r_obj* x) { - r_obj* method = KEEP(vec_proxy_compare_method(x)); - r_obj* out = vec_proxy_compare_invoke(x, method); + r_obj* out = KEEP(vec_proxy_compare_impl(x)); + + if (is_data_frame(out)) { + // Automatically proxy df-proxies recursively. + // Also flattens and unwraps them (#1537, #1664). + out = df_proxy(out, VCTRS_PROXY_KIND_compare); + } + FREE(1); return out; } // [[ register() ]] r_obj* vec_proxy_order(r_obj* x) { - r_obj* method = KEEP(vec_proxy_order_method(x)); - r_obj* out = vec_proxy_order_invoke(x, method); + r_obj* out = KEEP(vec_proxy_order_impl(x)); + + if (is_data_frame(out)) { + // Automatically proxy df-proxies recursively. + // Also flattens and unwraps them (#1537, #1664). + out = df_proxy(out, VCTRS_PROXY_KIND_order); + } + FREE(1); return out; } + +// Non-recursive variants called by the fallback path to ensure we only +// fallback on the container itself (like a df or rcrd) and not its elements +// (like columns or fields) +#define VEC_PROXY_KIND_IMPL(METHOD, INVOKE) do { \ + r_obj* method = KEEP(METHOD(x)); \ + r_obj* out = INVOKE(x, method); \ + FREE(1); \ + return out; \ +} while (0) \ + +static inline +r_obj* vec_proxy_equal_impl(r_obj* x) { + VEC_PROXY_KIND_IMPL(vec_proxy_equal_method, vec_proxy_equal_invoke); +} +static inline +r_obj* vec_proxy_compare_impl(r_obj* x) { + VEC_PROXY_KIND_IMPL(vec_proxy_compare_method, vec_proxy_compare_invoke); +} +static inline +r_obj* vec_proxy_order_impl(r_obj* x) { + VEC_PROXY_KIND_IMPL(vec_proxy_order_method, vec_proxy_order_invoke); +} + +#undef VEC_PROXY_KIND_IMPL + + r_obj* vec_proxy_method(r_obj* x) { return s3_find_method("vec_proxy", x, vctrs_method_table); } @@ -95,14 +140,14 @@ static inline r_obj* vec_proxy_invoke_impl(r_obj* x, r_obj* method, r_obj* vec_proxy_sym, - r_obj* (*vec_proxy_fn)(r_obj*)) { + r_obj* (*vec_proxy_impl_fn)(r_obj*)) { if (method != r_null) { return vctrs_dispatch1(vec_proxy_sym, method, syms_x, x); } /* Fallback on S3 objects with no proxy */ if (vec_typeof(x) == VCTRS_TYPE_s3) { - return vec_proxy_fn(x); + return vec_proxy_impl_fn(x); } else { return x; } @@ -114,29 +159,29 @@ r_obj* vec_proxy_equal_invoke(r_obj* x, r_obj* method) { } static inline r_obj* vec_proxy_compare_invoke(r_obj* x, r_obj* method) { - return vec_proxy_invoke_impl(x, method, syms_vec_proxy_compare, &vec_proxy_equal); + return vec_proxy_invoke_impl(x, method, syms_vec_proxy_compare, &vec_proxy_equal_impl); } static inline r_obj* vec_proxy_order_invoke(r_obj* x, r_obj* method) { - return vec_proxy_invoke_impl(x, method, syms_vec_proxy_order, &vec_proxy_compare); + return vec_proxy_invoke_impl(x, method, syms_vec_proxy_order, &vec_proxy_compare_impl); } #define DF_PROXY(PROXY) do { \ - r_ssize n_cols = r_length(x); \ + const r_ssize n_cols = r_length(x); \ + r_obj* const* v_x = r_list_cbegin(x); \ \ for (r_ssize i = 0; i < n_cols; ++i) { \ - r_obj* col = r_list_get(x, i); \ + r_obj* col = v_x[i]; \ r_list_poke(x, i, PROXY(col)); \ } \ } while (0) -static +static inline r_obj* df_proxy(r_obj* x, enum vctrs_proxy_kind kind) { x = KEEP(r_clone_referenced(x)); switch (kind) { - case VCTRS_PROXY_KIND_default: DF_PROXY(vec_proxy); break; case VCTRS_PROXY_KIND_equal: DF_PROXY(vec_proxy_equal); break; case VCTRS_PROXY_KIND_compare: DF_PROXY(vec_proxy_compare); break; case VCTRS_PROXY_KIND_order: DF_PROXY(vec_proxy_order); break; diff --git a/src/vctrs.h b/src/vctrs.h index aaecfa9d5..8324458dc 100644 --- a/src/vctrs.h +++ b/src/vctrs.h @@ -63,8 +63,7 @@ bool vec_is_unspecified(SEXP x); // Vector methods ------------------------------------------------ enum vctrs_proxy_kind { - VCTRS_PROXY_KIND_default, - VCTRS_PROXY_KIND_equal, + VCTRS_PROXY_KIND_equal = 0, VCTRS_PROXY_KIND_compare, VCTRS_PROXY_KIND_order }; diff --git a/tests/testthat/test-proxy.R b/tests/testthat/test-proxy.R index 78d7062f4..208129e93 100644 --- a/tests/testthat/test-proxy.R +++ b/tests/testthat/test-proxy.R @@ -111,6 +111,38 @@ test_that("vec_proxy_equal() defaults to vec_proxy() and vec_proxy_compare() def expect_identical(vec_proxy_compare(x), data_frame(x = letters[3:1], y = 1:3)) }) +test_that("equal/compare/order proxy methods that return data frames are automatically flattened", { + x <- new_vctr(1:2, class = "custom") + + equal <- data_frame(a = 1:2, b = 3:4) + order <- data_frame(a = 3:4, b = 4:5) + + local_methods( + vec_proxy_equal.custom = function(x, ...) data_frame(col = equal), + vec_proxy_order.custom = function(x, ...) data_frame(col = order) + ) + + expect_identical(vec_proxy_equal(x), equal) + expect_identical(vec_proxy_compare(x), equal) + expect_identical(vec_proxy_order(x), order) +}) + +test_that("equal/compare/order proxy methods that return 1 column data frames are automatically unwrapped", { + x <- new_vctr(1:2, class = "custom") + + equal <- 1:2 + order <- 3:4 + + local_methods( + vec_proxy_equal.custom = function(x, ...) data_frame(a = equal), + vec_proxy_order.custom = function(x, ...) data_frame(col = data_frame(a = order)) + ) + + expect_identical(vec_proxy_equal(x), equal) + expect_identical(vec_proxy_compare(x), equal) + expect_identical(vec_proxy_order(x), order) +}) + test_that("vec_data() preserves data frames", { expect_identical( vec_data(tibble(x = 1)), diff --git a/tests/testthat/test-type-rational.R b/tests/testthat/test-type-rational.R index b1b18569e..6a78ee8d4 100644 --- a/tests/testthat/test-type-rational.R +++ b/tests/testthat/test-type-rational.R @@ -10,7 +10,7 @@ test_that("equality proxy is taken (#375)", { expect_identical(unique(x), rational(c(1, 2, 1, 6), c(1, 1, 2, 2))) }) -test_that("compare proxy is taken", { +test_that("order proxy is taken", { local_rational_class() x <- rational(c(1, 2, 1, 2, 6), c(1, 1, 2, 2, 2)) expect_identical(sort(x), rational(c(1, 1, 2, 2, 6), c(2, 1, 2, 1, 2))) diff --git a/tests/testthat/test-type-rcrd.R b/tests/testthat/test-type-rcrd.R index 94d13e099..ceb525bd1 100644 --- a/tests/testthat/test-type-rcrd.R +++ b/tests/testthat/test-type-rcrd.R @@ -26,22 +26,41 @@ test_that("vec_proxy() transforms records to data frames", { ) }) -test_that("equality, comparison, and order proxies are recursive (#1503)", { - base <- new_rcrd(list(a = 1)) +test_that("equality, comparison, and order proxies are recursive and fall through (#1503, #1664)", { + base <- new_rcrd(list(a = 1), class = "custom") x <- new_rcrd(list(x = base)) expect_identical(vec_proxy_equal(x), 1) expect_identical(vec_proxy_compare(x), 1) expect_identical(vec_proxy_order(x), 1) - base <- new_rcrd(list(a = 1, b = 2)) - x <- new_rcrd(list(x = base, y = base)) + local_methods(vec_proxy_equal.custom = function(x, ...) rep("equal", length(x))) - expect <- data_frame(a = 1, b = 2, a = 1, b = 2, .name_repair = "minimal") + expect_identical(vec_proxy_equal(x), "equal") + expect_identical(vec_proxy_compare(x), "equal") + expect_identical(vec_proxy_order(x), "equal") - expect_identical(vec_proxy_equal(x), expect) - expect_identical(vec_proxy_compare(x), expect) - expect_identical(vec_proxy_order(x), expect) + local_methods(vec_proxy_compare.custom = function(x, ...) rep("compare", length(x))) + + expect_identical(vec_proxy_equal(x), "equal") + expect_identical(vec_proxy_compare(x), "compare") + expect_identical(vec_proxy_order(x), "compare") + + local_methods(vec_proxy_order.custom = function(x, ...) rep("order", length(x))) + + expect_identical(vec_proxy_equal(x), "equal") + expect_identical(vec_proxy_compare(x), "compare") + expect_identical(vec_proxy_order(x), "order") + + y <- new_rcrd(list(a = 1), class = "custom2") + local_methods(vec_proxy_compare.custom2 = function(x, ...) rep("compare2", length(x))) + + z <- data_frame(x = x, y = y) + + # Each column falls back independently + expect_identical(vec_proxy_equal(z), data_frame(x = "equal", y = 1)) + expect_identical(vec_proxy_compare(z), data_frame(x = "compare", y = "compare2")) + expect_identical(vec_proxy_order(z), data_frame(x = "order", y = "compare2")) }) # base methods ------------------------------------------------------------ From 01a80ec50069b7c56d9c042f5b88f85fb633e320 Mon Sep 17 00:00:00 2001 From: Davis Vaughan Date: Mon, 19 Sep 2022 10:11:00 -0400 Subject: [PATCH 080/312] Provide advice about implementing `vec_arith()` methods (#1667) --- vignettes/s3-vector.Rmd | 40 ++++++++++++++++++++++++++++++++++++++++ 1 file changed, 40 insertions(+) diff --git a/vignettes/s3-vector.Rmd b/vignettes/s3-vector.Rmd index beadae189..8894a95f5 100644 --- a/vignettes/s3-vector.Rmd +++ b/vignettes/s3-vector.Rmd @@ -867,6 +867,7 @@ vec_arith.MYCLASS.default <- function(op, x, y, ...) { } ``` +Correctly exporting `vec_arith()` methods from a package is currently a little awkward. See the instructions in the Arithmetic section of the "Implementing a vctrs S3 class in a package" section below. ### Cached sum class @@ -1147,6 +1148,45 @@ vec_cast.pizza_percent.double <- function(x, to, ...) percent(x) vec_cast.double.pizza_percent <- function(x, to, ...) vec_data(x) ``` +### Arithmetic + +Writing double dispatch methods for `vec_arith()` is currently more awkward than writing them for `vec_ptype2()` or `vec_cast()`. We plan to improve this in the future. For now, you can use the following instructions. + +If you define a new type and want to write `vec_arith()` methods for it, you'll need to provide a new single dispatch S3 generic for it of the following form: + +```{r, eval=FALSE} +#' @export +#' @method vec_arith my_type +vec_arith.my_type <- function(op, x, y, ...) { + UseMethod("vec_arith.my_type", y) +} +``` + +Note that this actually functions as both an S3 method for `vec_arith()` and an S3 generic called `vec_arith.my_type()` that dispatches off `y`. roxygen2 only recognizes it as an S3 generic, so you have to register the S3 method part of this with an explicit `@method` call. + +After that, you can define double dispatch methods, but you still need an explicit `@method` tag to ensure it is registered with the correct generic: + +```{r, eval=FALSE} +#' @export +#' @method vec_arith.my_type my_type +vec_arith.my_type.my_type <- function(op, x, y, ...) { + # implementation here +} + +#' @export +#' @method vec_arith.my_type integer +vec_arith.my_type.integer <- function(op, x, y, ...) { + # implementation here +} + +#' @export +#' @method vec_arith.integer my_type +vec_arith.integer.my_type <- function(op, x, y, ...) { + # implementation here +} +``` + +vctrs provides the hybrid S3 generics/methods for most of the base R types, like `vec_arith.integer()`. If you don't fully import vctrs with `@import vctrs`, then you will need to explicitly import the generic you are registering double dispatch methods for with `@importFrom vctrs vec_arith.integer`. ### Testing From fb97be9ac67f4a599b88e99ca158a90cd612a17c Mon Sep 17 00:00:00 2001 From: Davis Vaughan Date: Mon, 19 Sep 2022 11:06:14 -0400 Subject: [PATCH 081/312] Clean up location documentation (#1668) --- R/subscript-loc.R | 66 ++++++++++++++++++++++++++-------------- man/vec_as_location.Rd | 67 +++++++++++++++++++++++++++-------------- man/vec_as_subscript.Rd | 4 +-- 3 files changed, 90 insertions(+), 47 deletions(-) diff --git a/R/subscript-loc.R b/R/subscript-loc.R index ad3f61359..711cb9556 100644 --- a/R/subscript-loc.R +++ b/R/subscript-loc.R @@ -16,27 +16,39 @@ #' a single location as a integer vector of size 1. This is suitable #' for extracting with `[[`. #' +#' * `num_as_location()` and `num_as_location2()` are specialized variants +#' that have extra options for numeric indices. +#' #' @inheritParams vec_slice #' @inheritParams rlang::args_error_context #' #' @param n A single integer representing the total size of the #' object that `i` is meant to index into. +#' #' @param names If `i` is a character vector, `names` should be a character #' vector that `i` will be matched against to construct the index. Otherwise, #' not used. The default value of `NULL` will result in an error #' if `i` is a character vector. -#' @param missing Whether to throw an `"error"` when `i` is a missing value, -#' `"propagate"` it (return it as is), or `"remove"` it. By default, vector -#' subscripts can contain missing values and scalar subscripts can't. -#' Propagated missing values can't be combined with negative indices. -#' @param arg The argument name to be displayed in error messages when -#' `vec_as_location()` and `vec_as_location2()` are used to check the -#' type of a function input. #' -#' @return `vec_as_location()` returns an integer vector that can be used -#' as an index in a subsetting operation. `vec_as_location2()` -#' returns an integer of size 1 that can be used a scalar index for -#' extracting an element. +#' @param missing How should missing `i` values be handled? +#' - `"error"` throws an error. +#' - `"propagate"` returns them as is. +#' - `"remove"` removes them. +#' +#' By default, vector subscripts propagate missing values but scalar +#' subscripts error on them. +#' +#' Propagated missing values can't be combined with negative indices when +#' `negative = "invert"`, because they can't be meaningfully inverted. +#' +#' @param arg The argument name to be displayed in error messages. +#' +#' @return +#' - `vec_as_location()` and `num_as_location()` return an integer vector that +#' can be used as an index in a subsetting operation. +#' +#' - `vec_as_location2()` and `num_as_location2()` return an integer of size 1 +#' that can be used a scalar index for extracting an element. #' #' @examples #' x <- array(1:6, c(2, 3)) @@ -77,16 +89,28 @@ vec_as_location <- function(i, frame = environment() ) } + #' @rdname vec_as_location -#' @param negative Whether to `"invert"` negative values to positive -#' locations, throw an informative `"error"`, or `"ignore"` them. -#' @param oob If `"error"`, throws an informative `"error"` if some elements are -#' out-of-bounds. If `"remove"`, removes both positive and negative -#' out-of-bounds locations. If `"extend"`, out-of-bounds locations are allowed -#' if they are consecutive after the end. This can be used to implement -#' extendable vectors like `letters[1:30]`. -#' @param zero Whether to `"remove"` zero values, throw an informative -#' `"error"`, or `"ignore"` them. +#' +#' @param negative How should negative `i` values be handled? +#' - `"error"` throws an error. +#' - `"ignore"` returns them as is. +#' - `"invert"` returns the positive location generated by inverting the +#' negative location. When inverting, positive and negative locations +#' can't be mixed. This option is only applicable for `num_as_location()`. +#' +#' @param oob How should out-of-bounds `i` values be handled? +#' - `"error"` throws an error. +#' - `"remove"` removes both positive and negative out-of-bounds locations. +#' - `"extend"` allows positive out-of-bounds locations if they directly +#' follow the end of a vector. This can be used to implement extendable +#' vectors, like `letters[1:30]`. +#' +#' @param zero How should zero `i` values be handled? +#' - `"error"` throws an error. +#' - `"remove"` removes them. +#' - `"ignore"` returns them as is. +#' #' @export num_as_location <- function(i, n, @@ -136,8 +160,6 @@ vec_as_location2 <- function(i, )) } #' @rdname vec_as_location -#' @param negative Whether to throw an `"error"` when `i` is a -#' negative location value, or `"ignore"` it. #' @export num_as_location2 <- function(i, n, diff --git a/man/vec_as_location.Rd b/man/vec_as_location.Rd index c371a2135..99a4f508f 100644 --- a/man/vec_as_location.Rd +++ b/man/vec_as_location.Rd @@ -65,37 +65,58 @@ if \code{i} is a character vector.} \item{...}{These dots are for future extensions and must be empty.} -\item{missing}{Whether to throw an \code{"error"} when \code{i} is a missing value, -\code{"propagate"} it (return it as is), or \code{"remove"} it. By default, vector -subscripts can contain missing values and scalar subscripts can't. -Propagated missing values can't be combined with negative indices.} +\item{missing}{How should missing \code{i} values be handled? +\itemize{ +\item \code{"error"} throws an error. +\item \code{"propagate"} returns them as is. +\item \code{"remove"} removes them. +} + +By default, vector subscripts propagate missing values but scalar +subscripts error on them. -\item{arg}{The argument name to be displayed in error messages when -\code{vec_as_location()} and \code{vec_as_location2()} are used to check the -type of a function input.} +Propagated missing values can't be combined with negative indices when +\code{negative = "invert"}, because they can't be meaningfully inverted.} + +\item{arg}{The argument name to be displayed in error messages.} \item{call}{The execution environment of a currently running function, e.g. \code{caller_env()}. The function will be mentioned in error messages as the source of the error. See the \code{call} argument of \code{\link[rlang:abort]{abort()}} for more information.} -\item{negative}{Whether to throw an \code{"error"} when \code{i} is a -negative location value, or \code{"ignore"} it.} - -\item{oob}{If \code{"error"}, throws an informative \code{"error"} if some elements are -out-of-bounds. If \code{"remove"}, removes both positive and negative -out-of-bounds locations. If \code{"extend"}, out-of-bounds locations are allowed -if they are consecutive after the end. This can be used to implement -extendable vectors like \code{letters[1:30]}.} - -\item{zero}{Whether to \code{"remove"} zero values, throw an informative -\code{"error"}, or \code{"ignore"} them.} +\item{negative}{How should negative \code{i} values be handled? +\itemize{ +\item \code{"error"} throws an error. +\item \code{"ignore"} returns them as is. +\item \code{"invert"} returns the positive location generated by inverting the +negative location. When inverting, positive and negative locations +can't be mixed. This option is only applicable for \code{num_as_location()}. +}} + +\item{oob}{How should out-of-bounds \code{i} values be handled? +\itemize{ +\item \code{"error"} throws an error. +\item \code{"remove"} removes both positive and negative out-of-bounds locations. +\item \code{"extend"} allows positive out-of-bounds locations if they directly +follow the end of a vector. This can be used to implement extendable +vectors, like \code{letters[1:30]}. +}} + +\item{zero}{How should zero \code{i} values be handled? +\itemize{ +\item \code{"error"} throws an error. +\item \code{"remove"} removes them. +\item \code{"ignore"} returns them as is. +}} } \value{ -\code{vec_as_location()} returns an integer vector that can be used -as an index in a subsetting operation. \code{vec_as_location2()} -returns an integer of size 1 that can be used a scalar index for -extracting an element. +\itemize{ +\item \code{vec_as_location()} and \code{num_as_location()} return an integer vector that +can be used as an index in a subsetting operation. +\item \code{vec_as_location2()} and \code{num_as_location2()} return an integer of size 1 +that can be used a scalar index for extracting an element. +} } \description{ These helpers provide a means of standardizing common indexing @@ -110,6 +131,8 @@ to a vector of indices for the \code{TRUE} locations. \item \code{vec_as_location2()} accepts a single number or string. It returns a single location as a integer vector of size 1. This is suitable for extracting with \code{[[}. +\item \code{num_as_location()} and \code{num_as_location2()} are specialized variants +that have extra options for numeric indices. } } \examples{ diff --git a/man/vec_as_subscript.Rd b/man/vec_as_subscript.Rd index 6dff091a4..d427b0175 100644 --- a/man/vec_as_subscript.Rd +++ b/man/vec_as_subscript.Rd @@ -46,9 +46,7 @@ coercible depending on the setting of \code{character}. If \code{"error"}, the subscript type is disallowed and triggers an informative error.} -\item{arg}{The argument name to be displayed in error messages when -\code{vec_as_location()} and \code{vec_as_location2()} are used to check the -type of a function input.} +\item{arg}{The argument name to be displayed in error messages.} \item{call}{The execution environment of a currently running function, e.g. \code{caller_env()}. The function will be From 16ba9db2d5647adc5d454cf1a923bcdbef77464b Mon Sep 17 00:00:00 2001 From: DavisVaughan Date: Mon, 19 Sep 2022 11:38:33 -0400 Subject: [PATCH 082/312] Use my `width` settings to generate documentation for now --- man/theory-faq-coercion.Rd | 22 +++++++++++----------- 1 file changed, 11 insertions(+), 11 deletions(-) diff --git a/man/theory-faq-coercion.Rd b/man/theory-faq-coercion.Rd index 20c1d35ad..5904b06f5 100644 --- a/man/theory-faq-coercion.Rd +++ b/man/theory-faq-coercion.Rd @@ -74,9 +74,9 @@ steps, which require \code{vec_ptype2()} and \code{vec_cast()} implementations. Methods for \code{vec_ptype2()} are passed two \emph{prototypes}, i.e. two inputs emptied of their elements. They implement two behaviours: \itemize{ -\item If the types of their inputs are compatible, indicate which of them -is the richer type by returning it. If the types are of equal -resolution, return any of the two. +\item If the types of their inputs are compatible, indicate which of them is +the richer type by returning it. If the types are of equal resolution, +return any of the two. \item Throw an error with \code{stop_incompatible_type()} when it can be determined from the attributes that the types of the inputs are not compatible. @@ -204,14 +204,14 @@ in more cases. \code{vec_cast()} has three possible behaviours: This must be decided in exactly the same way as for \code{vec_ptype2()}. Call \code{stop_incompatible_cast()} if you can determine from the attributes that the types are not compatible. -\item Detect incompatible values. Usually this is because the target type -is too restricted for the values supported by the input type. For +\item Detect incompatible values. Usually this is because the target type is +too restricted for the values supported by the input type. For example, a fractional number can’t be converted to an integer. The method should throw an error in that case. -\item Return the input vector converted to the target type if all values -are compatible. Whereas \code{vec_ptype2()} must return the same type -when the inputs are permuted, \code{vec_cast()} is \emph{directional}. It -always returns the type of the right-hand side, or dies trying. +\item Return the input vector converted to the target type if all values are +compatible. Whereas \code{vec_ptype2()} must return the same type when the +inputs are permuted, \code{vec_cast()} is \emph{directional}. It always returns +the type of the right-hand side, or dies trying. } } @@ -225,8 +225,8 @@ differences: \item There is no inheritance of ptype2 and cast methods. This is because the S3 class hierarchy is not necessarily the same as the coercion hierarchy. -\item \code{NextMethod()} does not work. Parent methods must be called -explicitly if necessary. +\item \code{NextMethod()} does not work. Parent methods must be called explicitly +if necessary. \item The default method is hard-coded. } } From 0a219ba242ee368df63bc3876f06f9a6220e85c0 Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Mon, 19 Sep 2022 18:13:02 +0200 Subject: [PATCH 083/312] Fix error message when combining outer name with single inner name (#1670) Closes #522 --- NEWS.md | 2 ++ src/names.c | 15 +++++++++++---- tests/testthat/_snaps/names.md | 7 +++++++ tests/testthat/test-names.R | 2 ++ 4 files changed, 22 insertions(+), 4 deletions(-) diff --git a/NEWS.md b/NEWS.md index 90d7a20b5..aa83bc011 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,5 +1,7 @@ # vctrs (development version) +* `vec_c(outer = c(inner = 1))` now produces correct error messages (#522). + * If a data frame is returned as the proxy from `vec_proxy_equal()`, `vec_proxy_compare()`, or `vec_proxy_order()`, then the corresponding proxy function is now automatically applied recursively along all of the columns. diff --git a/src/names.c b/src/names.c index 0d1ee17db..5e2967d07 100644 --- a/src/names.c +++ b/src/names.c @@ -589,11 +589,18 @@ r_obj* apply_name_spec(r_obj* name_spec, r_obj* outer, r_obj* inner, r_ssize n) default: name_spec = r_as_function(name_spec, ".name_spec"); break; - case R_TYPE_null: - r_abort("Can't merge the outer name `%s` with a vector of length > 1.\n" + case R_TYPE_null: { + const char* reason; + if (n > 1) { + reason = "a vector of length > 1"; + } else { + reason = "a named vector"; + } + r_abort("Can't merge the outer name `%s` with %s.\n" "Please supply a `.name_spec` specification.", - r_str_c_string(outer)); - } + r_str_c_string(outer), + reason); + }} KEEP(name_spec); r_obj* outer_chr = KEEP(r_str_as_character(outer)); diff --git a/tests/testthat/_snaps/names.md b/tests/testthat/_snaps/names.md index 6a64cc4aa..b33d7e5d6 100644 --- a/tests/testthat/_snaps/names.md +++ b/tests/testthat/_snaps/names.md @@ -237,6 +237,13 @@ Error in `vec_c()`: ! Can't merge the outer name `foo` with a vector of length > 1. Please supply a `.name_spec` specification. + Code + (expect_error(vec_c(x = c(xx = 1)), "named vector")) + Output + + Error in `vec_c()`: + ! Can't merge the outer name `x` with a named vector. + Please supply a `.name_spec` specification. # vec_as_names() uses internal error if `repair_arg` is not supplied diff --git a/tests/testthat/test-names.R b/tests/testthat/test-names.R index 63d2d9505..5156ae69b 100644 --- a/tests/testthat/test-names.R +++ b/tests/testthat/test-names.R @@ -789,6 +789,7 @@ test_that("NULL name specs works with scalars", { expect_named(vec_c(foo = 1), "foo") expect_identical(apply_name_spec(NULL, "foo", chr(), 0L), chr()) + expect_equal(vec_c(foo = dbl()), set_names(dbl(), "")) expect_named(vec_c(foo = set_names(dbl())), chr()) expect_named(vec_c(foo = set_names(dbl()), bar = set_names(dbl())), chr()) @@ -798,6 +799,7 @@ test_that("NULL name specs works with scalars", { expect_snapshot({ (expect_error(vec_c(foo = c(a = 1, b = 2)), "vector of length > 1")) (expect_error(vec_c(foo = 1:2), "vector of length > 1")) + (expect_error(vec_c(x = c(xx = 1)), "named vector")) }) }) From 75447055f2fc035afab1a58dc774cde7c043c1b6 Mon Sep 17 00:00:00 2001 From: Davis Vaughan Date: Mon, 26 Sep 2022 10:43:42 -0400 Subject: [PATCH 084/312] Soft-deprecate `vec_equal_na()` in favor of `vec_detect_missing()` (#1672) * Internally switch to `vec_detect_missing()` * Deprecate `vec_equal_na()` in favor of `vec_detect_missing()` Also: - Exports `vec_any_missing()` - Writes a full help page for missing values - Cleans up equality help page * NEWS bullets --- NAMESPACE | 2 + NEWS.md | 7 + R/complete.R | 15 +- R/equal.R | 21 +- R/interval.R | 2 +- R/missing.R | 58 +++++- R/slice-interleave.R | 2 +- R/type-bare.R | 2 +- R/type-vctr.R | 8 +- R/vctrs-deprecated.R | 20 ++ _pkgdown.yml | 1 + man/missing.Rd | 66 ++++++ man/vec_detect_complete.Rd | 15 +- man/vec_equal.Rd | 27 +-- man/vec_equal_na.Rd | 21 ++ man/vec_proxy_equal.Rd | 2 +- src/decl/missing-decl.h | 66 +++--- src/fill.c | 2 +- src/init.c | 4 +- src/missing.c | 196 +++++++++--------- src/missing.h | 2 +- tests/testthat/_snaps/lifecycle-deprecated.md | 11 + tests/testthat/test-lifecycle-deprecated.R | 13 ++ tests/testthat/test-missing.R | 58 +++--- tests/testthat/test-type-integer64.R | 4 +- 25 files changed, 403 insertions(+), 222 deletions(-) create mode 100644 man/missing.Rd create mode 100644 man/vec_equal_na.Rd diff --git a/NAMESPACE b/NAMESPACE index df6778dd2..4ffec0c04 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -497,6 +497,7 @@ export(tib_cast) export(tib_ptype2) export(unspecified) export(validate_list_of) +export(vec_any_missing) export(vec_arith) export(vec_arith.Date) export(vec_arith.POSIXct) @@ -543,6 +544,7 @@ export(vec_data) export(vec_default_cast) export(vec_default_ptype2) export(vec_detect_complete) +export(vec_detect_missing) export(vec_duplicate_any) export(vec_duplicate_detect) export(vec_duplicate_id) diff --git a/NEWS.md b/NEWS.md index aa83bc011..a27cc49de 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,5 +1,12 @@ # vctrs (development version) +* New `vec_any_missing()` for quickly determining if a vector has any missing + values (#1672). + +* `vec_equal_na()` has been renamed to `vec_detect_missing()` to align better + with vctrs naming conventions. `vec_equal_na()` will stick around for a few + minor versions, but has been formally soft-deprecated (#1672). + * `vec_c(outer = c(inner = 1))` now produces correct error messages (#522). * If a data frame is returned as the proxy from `vec_proxy_equal()`, diff --git a/R/complete.R b/R/complete.R index 5061b76e4..bcc471246 100644 --- a/R/complete.R +++ b/R/complete.R @@ -3,11 +3,12 @@ #' @description #' `vec_detect_complete()` detects "complete" observations. An observation is #' considered complete if it is non-missing. For most vectors, this implies that -#' `vec_detect_complete(x) == !vec_equal_na(x)`. +#' `vec_detect_complete(x) == !vec_detect_missing(x)`. #' #' For data frames and matrices, a row is only considered complete if all -#' elements of that row are non-missing. To compare, `!vec_equal_na(x)` detects -#' rows that are partially complete (they have at least one non-missing value). +#' elements of that row are non-missing. To compare, `!vec_detect_missing(x)` +#' detects rows that are partially complete (they have at least one non-missing +#' value). #' #' @details #' A [record][new_rcrd] type vector is similar to a data frame, and is only @@ -23,9 +24,9 @@ #' @examples #' x <- c(1, 2, NA, 4, NA) #' -#' # For most vectors, this is identical to `!vec_equal_na(x)` +#' # For most vectors, this is identical to `!vec_detect_missing(x)` #' vec_detect_complete(x) -#' !vec_equal_na(x) +#' !vec_detect_missing(x) #' #' df <- data_frame( #' x = x, @@ -33,11 +34,11 @@ #' ) #' #' # This returns `TRUE` where all elements of the row are non-missing. -#' # Compare that with `!vec_equal_na()`, which detects rows that have at +#' # Compare that with `!vec_detect_missing()`, which detects rows that have at #' # least one non-missing value. #' df2 <- df #' df2$all_non_missing <- vec_detect_complete(df) -#' df2$any_non_missing <- !vec_equal_na(df) +#' df2$any_non_missing <- !vec_detect_missing(df) #' df2 vec_detect_complete <- function(x) { .Call(vctrs_detect_complete, x) diff --git a/R/equal.R b/R/equal.R index 80198524f..75e16c027 100644 --- a/R/equal.R +++ b/R/equal.R @@ -4,7 +4,7 @@ #' vectors). For [vctr]s, this determines the behaviour of `==` and #' `!=` (via [vec_equal()]); [unique()], [duplicated()] (via #' [vec_unique()] and [vec_duplicate_detect()]); [is.na()] and [anyNA()] -#' (via [vec_equal_na()]). +#' (via [vec_detect_missing()]). #' #' The default method calls [vec_proxy()], as the default underlying #' vector data should be equal-able in most cases. If your class is @@ -38,36 +38,31 @@ vec_proxy_equal.default <- function(x, ...) { stop_native_implementation("vec_proxy_equal.default") } -#' Test if two vectors are equal +#' Equality #' -#' `vec_equal_na()` tests a special case: equality with `NA`. It is similar to -#' [is.na] but: -#' * Considers the missing element of a list to be `NULL`. -#' * Considered data frames and records to be missing if every component -#' is missing. -#' This preserves the invariant that `vec_equal_na(x)` is equal to -#' `vec_equal(x, vec_init(x), na_equal = TRUE)`. +#' `vec_equal()` tests if two vectors are equal. #' #' @inheritParams vec_compare -#' @return A logical vector the same size as. Will only contain `NA`s if `na_equal` is `FALSE`. +#' @return A logical vector the same size as the common size of `x` and `y`. +#' Will only contain `NA`s if `na_equal` is `FALSE`. #' #' @section Dependencies: #' - [vec_cast_common()] with fallback #' - [vec_recycle_common()] #' - [vec_proxy_equal()] #' +#' @seealso [vec_detect_missing()] +#' #' @export #' @examples #' vec_equal(c(TRUE, FALSE, NA), FALSE) #' vec_equal(c(TRUE, FALSE, NA), FALSE, na_equal = TRUE) -#' vec_equal_na(c(TRUE, FALSE, NA)) #' #' vec_equal(5, 1:10) #' vec_equal("d", letters[1:10]) #' -#' df <- data.frame(x = c(1, 1, 2, 1, NA), y = c(1, 2, 1, NA, NA)) +#' df <- data.frame(x = c(1, 1, 2, 1), y = c(1, 2, 1, NA)) #' vec_equal(df, data.frame(x = 1, y = 2)) -#' vec_equal_na(df) vec_equal <- function(x, y, na_equal = FALSE, .ptype = NULL) { vec_assert(na_equal, ptype = logical(), size = 1L) args <- vec_recycle_common(x, y) diff --git a/R/interval.R b/R/interval.R index 3a35661d2..c27f2af49 100644 --- a/R/interval.R +++ b/R/interval.R @@ -28,7 +28,7 @@ #' of `end` must also be missing. #' #' - Each observation of `start` and `end` must be either -#' [complete][vec_detect_complete] or [missing][vec_equal_na]. Partially +#' [complete][vec_detect_complete] or [missing][vec_detect_missing]. Partially #' complete values such as `start = data_frame(x = 1, y = NA)` are not allowed. #' #' If any of these assumptions are invalid, then the result is undefined. diff --git a/R/missing.R b/R/missing.R index aff916949..afda18d2c 100644 --- a/R/missing.R +++ b/R/missing.R @@ -1,9 +1,61 @@ +#' Missing values +#' +#' @description +#' - `vec_detect_missing()` returns a logical vector the same size as `x`. For +#' each element of `x`, it returns `TRUE` if the element is missing, and `FALSE` +#' otherwise. +#' +#' - `vec_any_missing()` returns a single `TRUE` or `FALSE` depending on whether +#' or not `x` has _any_ missing values. +#' +#' ## Differences with [is.na()] +#' +#' Data frame rows are only considered missing if every element in the row is +#' missing. Similarly, [record vector][new_rcrd()] elements are only considered +#' missing if every field in the record is missing. Put another way, rows with +#' _any_ missing values are considered [incomplete][vec_detect_complete()], but +#' only rows with _all_ missing values are considered missing. +#' +#' List elements are only considered missing if they are `NULL`. +#' +#' @param x A vector +#' +#' @return +#' - `vec_detect_missing()` returns a logical vector the same size as `x`. +#' +#' - `vec_any_missing()` returns a single `TRUE` or `FALSE`. +#' +#' @section Dependencies: +#' - [vec_proxy_equal()] +#' +#' @name missing +#' @seealso [vec_detect_complete()] +#' +#' @examples +#' x <- c(1, 2, NA, 4, NA) +#' +#' vec_detect_missing(x) +#' vec_any_missing(x) +#' +#' # Data frames are iterated over rowwise, and only report a row as missing +#' # if every element of that row is missing. If a row is only partially +#' # missing, it is said to be incomplete, but not missing. +#' y <- c("a", "b", NA, "d", "e") +#' df <- data_frame(x = x, y = y) +#' +#' df$missing <- vec_detect_missing(df) +#' df$incomplete <- !vec_detect_complete(df) +#' df +NULL + +#' @rdname missing #' @export -#' @rdname vec_equal -vec_equal_na <- function(x) { - .Call(ffi_vec_equal_na, x) +vec_detect_missing <- function(x) { + .Call(ffi_vec_detect_missing, x) } +#' @rdname missing +#' @export vec_any_missing <- function(x) { .Call(ffi_vec_any_missing, x) } diff --git a/R/slice-interleave.R b/R/slice-interleave.R index 5224b1e6c..2226a7a74 100644 --- a/R/slice-interleave.R +++ b/R/slice-interleave.R @@ -43,7 +43,7 @@ vec_interleave <- function(..., # TODO: Use `vec_drop_missing()` # `NULL`s must be dropped up front to generate appropriate indices - missing <- vec_equal_na(args) + missing <- vec_detect_missing(args) if (any(missing)) { args <- vec_slice(args, !missing) } diff --git a/R/type-bare.R b/R/type-bare.R index ae5eb0a6f..fa178f96a 100644 --- a/R/type-bare.R +++ b/R/type-bare.R @@ -414,7 +414,7 @@ vec_proxy_order.list <- function(x, ...) { # This allows list elements to be grouped in `vec_order()`. # Have to separately ensure missing values are propagated. out <- vec_duplicate_id(x) - na <- vec_equal_na(x) + na <- vec_detect_missing(x) out <- vec_assign(out, na, NA_integer_) out } diff --git a/R/type-vctr.R b/R/type-vctr.R index 3c6cd8803..a069c9d2a 100644 --- a/R/type-vctr.R +++ b/R/type-vctr.R @@ -103,7 +103,7 @@ names_repair_missing <- function(x) { return(x) } - missing <- vec_equal_na(x) + missing <- vec_detect_missing(x) if (any(missing)) { # We never want to allow `NA_character_` names to slip through, but @@ -404,13 +404,13 @@ as.difftime.vctrs_vctr <- function(x, units = "secs", ...) { #' @export is.na.vctrs_vctr <- function(x) { - vec_equal_na(x) + vec_detect_missing(x) } #' @importFrom stats na.fail #' @export na.fail.vctrs_vctr <- function(object, ...) { - missing <- vec_equal_na(object) + missing <- vec_detect_missing(object) if (any(missing)) { # Return the same error as `na.fail.default()` @@ -436,7 +436,7 @@ na_remove <- function(x, type) { # The only difference between `na.omit()` and `na.exclude()` is the class # of the `na.action` attribute - missing <- vec_equal_na(x) + missing <- vec_detect_missing(x) if (!any(missing)) { return(x) diff --git a/R/vctrs-deprecated.R b/R/vctrs-deprecated.R index 20575d4e0..f2f6c1dce 100644 --- a/R/vctrs-deprecated.R +++ b/R/vctrs-deprecated.R @@ -143,3 +143,23 @@ vec_unchop <- function(x, name_repair = name_repair ) } + +#' Missing values +#' +#' @description +#' `r lifecycle::badge("deprecated")` +#' +#' `vec_equal_na()` has been renamed to [vec_detect_missing()] and is deprecated +#' as of vctrs 0.5.0. +#' +#' @inheritParams vec_detect_missing +#' +#' @return +#' A logical vector the same size as `x`. +#' +#' @keywords internal +#' @export +vec_equal_na <- function(x) { + lifecycle::deprecate_soft("0.5.0", "vec_equal_na()", "vec_detect_missing()") + vec_detect_missing(x) +} diff --git a/_pkgdown.yml b/_pkgdown.yml index ce18047fd..1efe6962c 100644 --- a/_pkgdown.yml +++ b/_pkgdown.yml @@ -69,6 +69,7 @@ reference: contents: - vec_equal - vec_detect_complete + - vec_detect_missing - vec_compare - title: Sorting diff --git a/man/missing.Rd b/man/missing.Rd new file mode 100644 index 000000000..1510b1c3f --- /dev/null +++ b/man/missing.Rd @@ -0,0 +1,66 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/missing.R +\name{missing} +\alias{missing} +\alias{vec_detect_missing} +\alias{vec_any_missing} +\title{Missing values} +\usage{ +vec_detect_missing(x) + +vec_any_missing(x) +} +\arguments{ +\item{x}{A vector} +} +\value{ +\itemize{ +\item \code{vec_detect_missing()} returns a logical vector the same size as \code{x}. +\item \code{vec_any_missing()} returns a single \code{TRUE} or \code{FALSE}. +} +} +\description{ +\itemize{ +\item \code{vec_detect_missing()} returns a logical vector the same size as \code{x}. For +each element of \code{x}, it returns \code{TRUE} if the element is missing, and \code{FALSE} +otherwise. +\item \code{vec_any_missing()} returns a single \code{TRUE} or \code{FALSE} depending on whether +or not \code{x} has \emph{any} missing values. +} +\subsection{Differences with \code{\link[=is.na]{is.na()}}}{ + +Data frame rows are only considered missing if every element in the row is +missing. Similarly, \link[=new_rcrd]{record vector} elements are only considered +missing if every field in the record is missing. Put another way, rows with +\emph{any} missing values are considered \link[=vec_detect_complete]{incomplete}, but +only rows with \emph{all} missing values are considered missing. + +List elements are only considered missing if they are \code{NULL}. +} +} +\section{Dependencies}{ + +\itemize{ +\item \code{\link[=vec_proxy_equal]{vec_proxy_equal()}} +} +} + +\examples{ +x <- c(1, 2, NA, 4, NA) + +vec_detect_missing(x) +vec_any_missing(x) + +# Data frames are iterated over rowwise, and only report a row as missing +# if every element of that row is missing. If a row is only partially +# missing, it is said to be incomplete, but not missing. +y <- c("a", "b", NA, "d", "e") +df <- data_frame(x = x, y = y) + +df$missing <- vec_detect_missing(df) +df$incomplete <- !vec_detect_complete(df) +df +} +\seealso{ +\code{\link[=vec_detect_complete]{vec_detect_complete()}} +} diff --git a/man/vec_detect_complete.Rd b/man/vec_detect_complete.Rd index b608d4955..80c114316 100644 --- a/man/vec_detect_complete.Rd +++ b/man/vec_detect_complete.Rd @@ -15,11 +15,12 @@ A logical vector with the same size as \code{x}. \description{ \code{vec_detect_complete()} detects "complete" observations. An observation is considered complete if it is non-missing. For most vectors, this implies that -\code{vec_detect_complete(x) == !vec_equal_na(x)}. +\code{vec_detect_complete(x) == !vec_detect_missing(x)}. For data frames and matrices, a row is only considered complete if all -elements of that row are non-missing. To compare, \code{!vec_equal_na(x)} detects -rows that are partially complete (they have at least one non-missing value). +elements of that row are non-missing. To compare, \code{!vec_detect_missing(x)} +detects rows that are partially complete (they have at least one non-missing +value). } \details{ A \link[=new_rcrd]{record} type vector is similar to a data frame, and is only @@ -28,9 +29,9 @@ considered complete if all fields are non-missing. \examples{ x <- c(1, 2, NA, 4, NA) -# For most vectors, this is identical to `!vec_equal_na(x)` +# For most vectors, this is identical to `!vec_detect_missing(x)` vec_detect_complete(x) -!vec_equal_na(x) +!vec_detect_missing(x) df <- data_frame( x = x, @@ -38,11 +39,11 @@ df <- data_frame( ) # This returns `TRUE` where all elements of the row are non-missing. -# Compare that with `!vec_equal_na()`, which detects rows that have at +# Compare that with `!vec_detect_missing()`, which detects rows that have at # least one non-missing value. df2 <- df df2$all_non_missing <- vec_detect_complete(df) -df2$any_non_missing <- !vec_equal_na(df) +df2$any_non_missing <- !vec_detect_missing(df) df2 } \seealso{ diff --git a/man/vec_equal.Rd b/man/vec_equal.Rd index 14bff3b30..55275e082 100644 --- a/man/vec_equal.Rd +++ b/man/vec_equal.Rd @@ -1,13 +1,10 @@ % Generated by roxygen2: do not edit by hand -% Please edit documentation in R/equal.R, R/missing.R +% Please edit documentation in R/equal.R \name{vec_equal} \alias{vec_equal} -\alias{vec_equal_na} -\title{Test if two vectors are equal} +\title{Equality} \usage{ vec_equal(x, y, na_equal = FALSE, .ptype = NULL) - -vec_equal_na(x) } \arguments{ \item{x, y}{Vectors with compatible types and lengths.} @@ -17,18 +14,11 @@ vec_equal_na(x) \item{.ptype}{Override to optionally specify common type} } \value{ -A logical vector the same size as. Will only contain \code{NA}s if \code{na_equal} is \code{FALSE}. +A logical vector the same size as the common size of \code{x} and \code{y}. +Will only contain \code{NA}s if \code{na_equal} is \code{FALSE}. } \description{ -\code{vec_equal_na()} tests a special case: equality with \code{NA}. It is similar to -\link{is.na} but: -\itemize{ -\item Considers the missing element of a list to be \code{NULL}. -\item Considered data frames and records to be missing if every component -is missing. -This preserves the invariant that \code{vec_equal_na(x)} is equal to -\code{vec_equal(x, vec_init(x), na_equal = TRUE)}. -} +\code{vec_equal()} tests if two vectors are equal. } \section{Dependencies}{ @@ -42,12 +32,13 @@ This preserves the invariant that \code{vec_equal_na(x)} is equal to \examples{ vec_equal(c(TRUE, FALSE, NA), FALSE) vec_equal(c(TRUE, FALSE, NA), FALSE, na_equal = TRUE) -vec_equal_na(c(TRUE, FALSE, NA)) vec_equal(5, 1:10) vec_equal("d", letters[1:10]) -df <- data.frame(x = c(1, 1, 2, 1, NA), y = c(1, 2, 1, NA, NA)) +df <- data.frame(x = c(1, 1, 2, 1), y = c(1, 2, 1, NA)) vec_equal(df, data.frame(x = 1, y = 2)) -vec_equal_na(df) +} +\seealso{ +\code{\link[=vec_detect_missing]{vec_detect_missing()}} } diff --git a/man/vec_equal_na.Rd b/man/vec_equal_na.Rd new file mode 100644 index 000000000..736df2d7f --- /dev/null +++ b/man/vec_equal_na.Rd @@ -0,0 +1,21 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/vctrs-deprecated.R +\name{vec_equal_na} +\alias{vec_equal_na} +\title{Missing values} +\usage{ +vec_equal_na(x) +} +\arguments{ +\item{x}{A vector} +} +\value{ +A logical vector the same size as \code{x}. +} +\description{ +\ifelse{html}{\href{https://lifecycle.r-lib.org/articles/stages.html#deprecated}{\figure{lifecycle-deprecated.svg}{options: alt='[Deprecated]'}}}{\strong{[Deprecated]}} + +\code{vec_equal_na()} has been renamed to \code{\link[=vec_detect_missing]{vec_detect_missing()}} and is deprecated +as of vctrs 0.5.0. +} +\keyword{internal} diff --git a/man/vec_proxy_equal.Rd b/man/vec_proxy_equal.Rd index 932cfb025..e8aea2473 100644 --- a/man/vec_proxy_equal.Rd +++ b/man/vec_proxy_equal.Rd @@ -19,7 +19,7 @@ Returns a proxy object (i.e. an atomic vector or data frame of atomic vectors). For \link{vctr}s, this determines the behaviour of \code{==} and \code{!=} (via \code{\link[=vec_equal]{vec_equal()}}); \code{\link[=unique]{unique()}}, \code{\link[=duplicated]{duplicated()}} (via \code{\link[=vec_unique]{vec_unique()}} and \code{\link[=vec_duplicate_detect]{vec_duplicate_detect()}}); \code{\link[=is.na]{is.na()}} and \code{\link[=anyNA]{anyNA()}} -(via \code{\link[=vec_equal_na]{vec_equal_na()}}). +(via \code{\link[=vec_detect_missing]{vec_detect_missing()}}). } \details{ The default method calls \code{\link[=vec_proxy]{vec_proxy()}}, as the default underlying diff --git a/src/decl/missing-decl.h b/src/decl/missing-decl.h index 8ae53566f..3882fe7c6 100644 --- a/src/decl/missing-decl.h +++ b/src/decl/missing-decl.h @@ -1,57 +1,57 @@ static inline -r_obj* proxy_equal_na(r_obj* proxy); +r_obj* proxy_detect_missing(r_obj* proxy); static inline -r_obj* lgl_equal_na(r_obj* x); +r_obj* lgl_detect_missing(r_obj* x); static inline -r_obj* int_equal_na(r_obj* x); +r_obj* int_detect_missing(r_obj* x); static inline -r_obj* dbl_equal_na(r_obj* x); +r_obj* dbl_detect_missing(r_obj* x); static inline -r_obj* cpl_equal_na(r_obj* x); +r_obj* cpl_detect_missing(r_obj* x); static inline -r_obj* raw_equal_na(r_obj* x); +r_obj* raw_detect_missing(r_obj* x); static inline -r_obj* chr_equal_na(r_obj* x); +r_obj* chr_detect_missing(r_obj* x); static inline -r_obj* list_equal_na(r_obj* x); +r_obj* list_detect_missing(r_obj* x); static inline -r_obj* df_equal_na(r_obj* x); +r_obj* df_detect_missing(r_obj* x); static inline -r_ssize col_equal_na(r_obj* x, - r_ssize* v_loc, - r_ssize loc_size); +r_ssize col_detect_missing(r_obj* x, + r_ssize* v_loc, + r_ssize loc_size); static inline -r_ssize lgl_col_equal_na(r_obj* x, - r_ssize* v_loc, - r_ssize loc_size); +r_ssize lgl_col_detect_missing(r_obj* x, + r_ssize* v_loc, + r_ssize loc_size); static inline -r_ssize int_col_equal_na(r_obj* x, - r_ssize* v_loc, - r_ssize loc_size); +r_ssize int_col_detect_missing(r_obj* x, + r_ssize* v_loc, + r_ssize loc_size); static inline -r_ssize dbl_col_equal_na(r_obj* x, - r_ssize* v_loc, - r_ssize loc_size); +r_ssize dbl_col_detect_missing(r_obj* x, + r_ssize* v_loc, + r_ssize loc_size); static inline -r_ssize cpl_col_equal_na(r_obj* x, - r_ssize* v_loc, - r_ssize loc_size); +r_ssize cpl_col_detect_missing(r_obj* x, + r_ssize* v_loc, + r_ssize loc_size); static inline -r_ssize raw_col_equal_na(r_obj* x, - r_ssize* v_loc, - r_ssize loc_size); +r_ssize raw_col_detect_missing(r_obj* x, + r_ssize* v_loc, + r_ssize loc_size); static inline -r_ssize chr_col_equal_na(r_obj* x, - r_ssize* v_loc, - r_ssize loc_size); +r_ssize chr_col_detect_missing(r_obj* x, + r_ssize* v_loc, + r_ssize loc_size); static inline -r_ssize list_col_equal_na(r_obj* x, - r_ssize* v_loc, - r_ssize loc_size); +r_ssize list_col_detect_missing(r_obj* x, + r_ssize* v_loc, + r_ssize loc_size); static inline r_ssize proxy_first_missing(r_obj* proxy); diff --git a/src/fill.c b/src/fill.c index 6c01f10dd..404a20c04 100644 --- a/src/fill.c +++ b/src/fill.c @@ -26,7 +26,7 @@ static SEXP vec_fill_missing(SEXP x, bool down, bool leading, int max_fill) { r_ssize size = vec_size(x); - SEXP na = PROTECT(vec_equal_na(x)); + SEXP na = PROTECT(vec_detect_missing(x)); const int* p_na = LOGICAL_RO(na); SEXP loc = PROTECT(r_new_integer(size)); diff --git a/src/init.c b/src/init.c index 3ce079ec0..befe5ec7f 100644 --- a/src/init.c +++ b/src/init.c @@ -28,7 +28,7 @@ extern SEXP vctrs_group_id(SEXP); extern SEXP vctrs_group_rle(SEXP); extern SEXP vec_group_loc(SEXP); extern SEXP vctrs_equal(SEXP, SEXP, SEXP); -extern r_obj* ffi_vec_equal_na(r_obj*); +extern r_obj* ffi_vec_detect_missing(r_obj*); extern r_obj* ffi_vec_any_missing(r_obj* x); extern r_obj* ffi_vec_compare(r_obj*, r_obj*, r_obj*); extern SEXP vctrs_match(SEXP, SEXP, SEXP, SEXP); @@ -202,7 +202,7 @@ static const R_CallMethodDef CallEntries[] = { {"vctrs_dim_n", (DL_FUNC) &vctrs_dim_n, 1}, {"vctrs_is_unspecified", (DL_FUNC) &vctrs_is_unspecified, 1}, {"vctrs_equal", (DL_FUNC) &vctrs_equal, 3}, - {"ffi_vec_equal_na", (DL_FUNC) &ffi_vec_equal_na, 1}, + {"ffi_vec_detect_missing", (DL_FUNC) &ffi_vec_detect_missing, 1}, {"ffi_vec_any_missing", (DL_FUNC) &ffi_vec_any_missing, 1}, {"ffi_vec_compare", (DL_FUNC) &ffi_vec_compare, 3}, {"vctrs_match", (DL_FUNC) &vctrs_match, 4}, diff --git a/src/missing.c b/src/missing.c index 632aa7643..d4058f170 100644 --- a/src/missing.c +++ b/src/missing.c @@ -3,34 +3,34 @@ #include "decl/missing-decl.h" // [[ register() ]] -r_obj* ffi_vec_equal_na(r_obj* x) { - return vec_equal_na(x); +r_obj* ffi_vec_detect_missing(r_obj* x) { + return vec_detect_missing(x); } // [[ include("missing.h") ]] -r_obj* vec_equal_na(r_obj* x) { +r_obj* vec_detect_missing(r_obj* x) { r_obj* proxy = KEEP(vec_proxy_equal(x)); - r_obj* out = proxy_equal_na(proxy); + r_obj* out = proxy_detect_missing(proxy); FREE(1); return out; } static inline -r_obj* proxy_equal_na(r_obj* proxy) { +r_obj* proxy_detect_missing(r_obj* proxy) { const enum vctrs_type type = vec_proxy_typeof(proxy); switch (type) { - case VCTRS_TYPE_logical: return lgl_equal_na(proxy); - case VCTRS_TYPE_integer: return int_equal_na(proxy); - case VCTRS_TYPE_double: return dbl_equal_na(proxy); - case VCTRS_TYPE_complex: return cpl_equal_na(proxy); - case VCTRS_TYPE_raw: return raw_equal_na(proxy); - case VCTRS_TYPE_character: return chr_equal_na(proxy); - case VCTRS_TYPE_list: return list_equal_na(proxy); - case VCTRS_TYPE_dataframe: return df_equal_na(proxy); + case VCTRS_TYPE_logical: return lgl_detect_missing(proxy); + case VCTRS_TYPE_integer: return int_detect_missing(proxy); + case VCTRS_TYPE_double: return dbl_detect_missing(proxy); + case VCTRS_TYPE_complex: return cpl_detect_missing(proxy); + case VCTRS_TYPE_raw: return raw_detect_missing(proxy); + case VCTRS_TYPE_character: return chr_detect_missing(proxy); + case VCTRS_TYPE_list: return list_detect_missing(proxy); + case VCTRS_TYPE_dataframe: return df_detect_missing(proxy); case VCTRS_TYPE_null: return r_globals.empty_lgl; case VCTRS_TYPE_scalar: stop_scalar_type(proxy, vec_args.empty, r_lazy_null); - default: stop_unimplemented_vctrs_type("vec_equal_na", type); + default: stop_unimplemented_vctrs_type("vec_detect_missing", type); } r_stop_unreachable(); @@ -38,57 +38,57 @@ r_obj* proxy_equal_na(r_obj* proxy) { // ----------------------------------------------------------------------------- -#define EQUAL_NA(CTYPE, CBEGIN, IS_MISSING) do { \ - const r_ssize size = vec_size(x); \ - \ - r_obj* out = KEEP(r_new_logical(size)); \ - int* v_out = r_lgl_begin(out); \ - \ - CTYPE const* v_x = CBEGIN(x); \ - \ - for (r_ssize i = 0; i < size; ++i) { \ - v_out[i] = IS_MISSING(v_x[i]); \ - } \ - \ - FREE(1); \ - return out; \ +#define DETECT_MISSING(CTYPE, CBEGIN, IS_MISSING) do { \ + const r_ssize size = vec_size(x); \ + \ + r_obj* out = KEEP(r_new_logical(size)); \ + int* v_out = r_lgl_begin(out); \ + \ + CTYPE const* v_x = CBEGIN(x); \ + \ + for (r_ssize i = 0; i < size; ++i) { \ + v_out[i] = IS_MISSING(v_x[i]); \ + } \ + \ + FREE(1); \ + return out; \ } while (0) static inline -r_obj* lgl_equal_na(r_obj* x) { - EQUAL_NA(int, r_lgl_cbegin, lgl_is_missing); +r_obj* lgl_detect_missing(r_obj* x) { + DETECT_MISSING(int, r_lgl_cbegin, lgl_is_missing); } static inline -r_obj* int_equal_na(r_obj* x) { - EQUAL_NA(int, r_int_cbegin, int_is_missing); +r_obj* int_detect_missing(r_obj* x) { + DETECT_MISSING(int, r_int_cbegin, int_is_missing); } static inline -r_obj* dbl_equal_na(r_obj* x) { - EQUAL_NA(double, r_dbl_cbegin, dbl_is_missing); +r_obj* dbl_detect_missing(r_obj* x) { + DETECT_MISSING(double, r_dbl_cbegin, dbl_is_missing); } static inline -r_obj* cpl_equal_na(r_obj* x) { - EQUAL_NA(r_complex, r_cpl_cbegin, cpl_is_missing); +r_obj* cpl_detect_missing(r_obj* x) { + DETECT_MISSING(r_complex, r_cpl_cbegin, cpl_is_missing); } static inline -r_obj* raw_equal_na(r_obj* x) { - EQUAL_NA(unsigned char, r_uchar_cbegin, raw_is_missing); +r_obj* raw_detect_missing(r_obj* x) { + DETECT_MISSING(unsigned char, r_uchar_cbegin, raw_is_missing); } static inline -r_obj* chr_equal_na(r_obj* x) { - EQUAL_NA(r_obj*, r_chr_cbegin, chr_is_missing); +r_obj* chr_detect_missing(r_obj* x) { + DETECT_MISSING(r_obj*, r_chr_cbegin, chr_is_missing); } static inline -r_obj* list_equal_na(r_obj* x) { - EQUAL_NA(r_obj*, r_list_cbegin, list_is_missing); +r_obj* list_detect_missing(r_obj* x) { + DETECT_MISSING(r_obj*, r_list_cbegin, list_is_missing); } -#undef EQUAL_NA +#undef DETECT_MISSING // ----------------------------------------------------------------------------- static inline -r_obj* df_equal_na(r_obj* x) { +r_obj* df_detect_missing(r_obj* x) { int n_prot = 0; const r_ssize n_col = r_length(x); @@ -109,7 +109,7 @@ r_obj* df_equal_na(r_obj* x) { for (r_ssize i = 0; i < n_col; ++i) { r_obj* col = v_x[i]; - loc_size = col_equal_na(col, v_loc, loc_size); + loc_size = col_detect_missing(col, v_loc, loc_size); // If all rows have at least one non-missing value, break if (loc_size == 0) { @@ -133,31 +133,31 @@ r_obj* df_equal_na(r_obj* x) { // ----------------------------------------------------------------------------- static inline -r_ssize col_equal_na(r_obj* x, - r_ssize* v_loc, - r_ssize loc_size) { +r_ssize col_detect_missing(r_obj* x, + r_ssize* v_loc, + r_ssize loc_size) { const enum vctrs_type type = vec_proxy_typeof(x); switch (type) { - case VCTRS_TYPE_logical: return lgl_col_equal_na(x, v_loc, loc_size); - case VCTRS_TYPE_integer: return int_col_equal_na(x, v_loc, loc_size); - case VCTRS_TYPE_double: return dbl_col_equal_na(x, v_loc, loc_size); - case VCTRS_TYPE_complex: return cpl_col_equal_na(x, v_loc, loc_size); - case VCTRS_TYPE_raw: return raw_col_equal_na(x, v_loc, loc_size); - case VCTRS_TYPE_character: return chr_col_equal_na(x, v_loc, loc_size); - case VCTRS_TYPE_list: return list_col_equal_na(x, v_loc, loc_size); + case VCTRS_TYPE_logical: return lgl_col_detect_missing(x, v_loc, loc_size); + case VCTRS_TYPE_integer: return int_col_detect_missing(x, v_loc, loc_size); + case VCTRS_TYPE_double: return dbl_col_detect_missing(x, v_loc, loc_size); + case VCTRS_TYPE_complex: return cpl_col_detect_missing(x, v_loc, loc_size); + case VCTRS_TYPE_raw: return raw_col_detect_missing(x, v_loc, loc_size); + case VCTRS_TYPE_character: return chr_col_detect_missing(x, v_loc, loc_size); + case VCTRS_TYPE_list: return list_col_detect_missing(x, v_loc, loc_size); case VCTRS_TYPE_dataframe: r_stop_internal("Data frame columns should have been flattened by now."); case VCTRS_TYPE_null: r_abort("Unexpected `NULL` column found in a data frame."); case VCTRS_TYPE_scalar: stop_scalar_type(x, vec_args.empty, r_lazy_null); - default: stop_unimplemented_vctrs_type("vec_equal_na", type); + default: stop_unimplemented_vctrs_type("vec_detect_missing", type); } } // ----------------------------------------------------------------------------- /* - * The data frame algorithm for `vec_equal_na()` is fast because this inner - * for loop doesn't have any `if` branches in it. We utilize the fact that + * The data frame algorithm for `vec_detect_missing()` is fast because this + * inner for loop doesn't have any `if` branches in it. We utilize the fact that * this is a no-op when the element isn't missing: * `new_loc_size += IS_MISSING(v_x[loc])` * This is faster than doing `if (IS_MISSING())` at each iteration, especially @@ -200,63 +200,63 @@ r_ssize col_equal_na(r_obj* x, * * For more details, see: https://github.com/r-lib/vctrs/pull/1584 */ -#define COL_EQUAL_NA(CTYPE, CBEGIN, IS_MISSING) do { \ - CTYPE const* v_x = CBEGIN(x); \ - r_ssize new_loc_size = 0; \ - \ - for (r_ssize i = 0; i < loc_size; ++i) { \ - const r_ssize loc = v_loc[i]; \ - v_loc[new_loc_size] = loc; \ - new_loc_size += IS_MISSING(v_x[loc]); \ - } \ - \ - return new_loc_size; \ +#define COL_DETECT_MISSING(CTYPE, CBEGIN, IS_MISSING) do { \ + CTYPE const* v_x = CBEGIN(x); \ + r_ssize new_loc_size = 0; \ + \ + for (r_ssize i = 0; i < loc_size; ++i) { \ + const r_ssize loc = v_loc[i]; \ + v_loc[new_loc_size] = loc; \ + new_loc_size += IS_MISSING(v_x[loc]); \ + } \ + \ + return new_loc_size; \ } while (0) static inline -r_ssize lgl_col_equal_na(r_obj* x, - r_ssize* v_loc, - r_ssize loc_size) { - COL_EQUAL_NA(int, r_lgl_cbegin, lgl_is_missing); +r_ssize lgl_col_detect_missing(r_obj* x, + r_ssize* v_loc, + r_ssize loc_size) { + COL_DETECT_MISSING(int, r_lgl_cbegin, lgl_is_missing); } static inline -r_ssize int_col_equal_na(r_obj* x, - r_ssize* v_loc, - r_ssize loc_size) { - COL_EQUAL_NA(int, r_int_cbegin, int_is_missing); +r_ssize int_col_detect_missing(r_obj* x, + r_ssize* v_loc, + r_ssize loc_size) { + COL_DETECT_MISSING(int, r_int_cbegin, int_is_missing); } static inline -r_ssize dbl_col_equal_na(r_obj* x, - r_ssize* v_loc, - r_ssize loc_size) { - COL_EQUAL_NA(double, r_dbl_cbegin, dbl_is_missing); +r_ssize dbl_col_detect_missing(r_obj* x, + r_ssize* v_loc, + r_ssize loc_size) { + COL_DETECT_MISSING(double, r_dbl_cbegin, dbl_is_missing); } static inline -r_ssize cpl_col_equal_na(r_obj* x, - r_ssize* v_loc, - r_ssize loc_size) { - COL_EQUAL_NA(r_complex, r_cpl_cbegin, cpl_is_missing); +r_ssize cpl_col_detect_missing(r_obj* x, + r_ssize* v_loc, + r_ssize loc_size) { + COL_DETECT_MISSING(r_complex, r_cpl_cbegin, cpl_is_missing); } static inline -r_ssize raw_col_equal_na(r_obj* x, - r_ssize* v_loc, - r_ssize loc_size) { - COL_EQUAL_NA(unsigned char, r_uchar_cbegin, raw_is_missing); +r_ssize raw_col_detect_missing(r_obj* x, + r_ssize* v_loc, + r_ssize loc_size) { + COL_DETECT_MISSING(unsigned char, r_uchar_cbegin, raw_is_missing); } static inline -r_ssize chr_col_equal_na(r_obj* x, - r_ssize* v_loc, - r_ssize loc_size) { - COL_EQUAL_NA(r_obj*, r_chr_cbegin, chr_is_missing); +r_ssize chr_col_detect_missing(r_obj* x, + r_ssize* v_loc, + r_ssize loc_size) { + COL_DETECT_MISSING(r_obj*, r_chr_cbegin, chr_is_missing); } static inline -r_ssize list_col_equal_na(r_obj* x, - r_ssize* v_loc, - r_ssize loc_size) { - COL_EQUAL_NA(r_obj*, r_list_cbegin, list_is_missing); +r_ssize list_col_detect_missing(r_obj* x, + r_ssize* v_loc, + r_ssize loc_size) { + COL_DETECT_MISSING(r_obj*, r_list_cbegin, list_is_missing); } -#undef COL_EQUAL_NA +#undef COL_DETECT_MISSING // ----------------------------------------------------------------------------- diff --git a/src/missing.h b/src/missing.h index 11c7164f0..8b42be999 100644 --- a/src/missing.h +++ b/src/missing.h @@ -6,7 +6,7 @@ // ----------------------------------------------------------------------------- -r_obj* vec_equal_na(r_obj* x); +r_obj* vec_detect_missing(r_obj* x); bool vec_any_missing(r_obj* x); r_ssize vec_first_missing(r_obj* x); diff --git a/tests/testthat/_snaps/lifecycle-deprecated.md b/tests/testthat/_snaps/lifecycle-deprecated.md index 8f8decc9e..65039d900 100644 --- a/tests/testthat/_snaps/lifecycle-deprecated.md +++ b/tests/testthat/_snaps/lifecycle-deprecated.md @@ -9,3 +9,14 @@ Output [1] 1 +# vec_equal_na() is soft-deprecated + + Code + vec_equal_na(c(1, NA)) + Condition + Warning: + `vec_equal_na()` was deprecated in vctrs 0.5.0. + Please use `vec_detect_missing()` instead. + Output + [1] FALSE TRUE + diff --git a/tests/testthat/test-lifecycle-deprecated.R b/tests/testthat/test-lifecycle-deprecated.R index 1c5fb6197..d80cea837 100644 --- a/tests/testthat/test-lifecycle-deprecated.R +++ b/tests/testthat/test-lifecycle-deprecated.R @@ -26,3 +26,16 @@ test_that("vec_unchop() still works", { c(3L, 1L, 2L) ) }) + +test_that("vec_equal_na() is soft-deprecated", { + local_options(lifecycle_verbosity = "warning") + expect_snapshot(vec_equal_na(c(1, NA))) +}) + +test_that("vec_equal_na() still works", { + local_options(lifecycle_verbosity = "quiet") + expect_identical( + vec_equal_na(c(1, NA, 2, NA)), + c(FALSE, TRUE, FALSE, TRUE) + ) +}) diff --git a/tests/testthat/test-missing.R b/tests/testthat/test-missing.R index 59f15bff2..4d3456bc8 100644 --- a/tests/testthat/test-missing.R +++ b/tests/testthat/test-missing.R @@ -1,61 +1,61 @@ # ------------------------------------------------------------------------------ -# vec_equal_na() +# vec_detect_missing() test_that("can detect different types of NA", { - expect_true(vec_equal_na(NA)) - expect_true(vec_equal_na(NA_integer_)) - expect_true(vec_equal_na(NA_real_)) - expect_true(vec_equal_na(NA_complex_)) - expect_true(vec_equal_na(complex(real = NA, imaginary = 1))) - expect_true(vec_equal_na(NaN)) - expect_true(vec_equal_na(NA_character_)) - expect_true(vec_equal_na(list(NULL))) + expect_true(vec_detect_missing(NA)) + expect_true(vec_detect_missing(NA_integer_)) + expect_true(vec_detect_missing(NA_real_)) + expect_true(vec_detect_missing(NA_complex_)) + expect_true(vec_detect_missing(complex(real = NA, imaginary = 1))) + expect_true(vec_detect_missing(NaN)) + expect_true(vec_detect_missing(NA_character_)) + expect_true(vec_detect_missing(list(NULL))) }) test_that("can detect different types of NA in data frames", { # using multiple columns to prevent proxy unwrapping - expect_true(vec_equal_na(data.frame(x = NA, y = NA))) - expect_true(vec_equal_na(data.frame(x = NA_integer_, y = NA_integer_))) - expect_true(vec_equal_na(data.frame(x = NA_real_, y = NaN))) - expect_true(vec_equal_na(data.frame(x = NA_complex_, y = NA_complex_))) - expect_true(vec_equal_na(data.frame(x = complex(real = NA, imaginary = 1), y = complex(real = 1, imaginary = NA)))) - expect_true(vec_equal_na(data.frame(x = NA_character_, y = NA_character_))) - expect_true(vec_equal_na(new_data_frame(list(x = list(NULL), y = list(NULL))))) + expect_true(vec_detect_missing(data.frame(x = NA, y = NA))) + expect_true(vec_detect_missing(data.frame(x = NA_integer_, y = NA_integer_))) + expect_true(vec_detect_missing(data.frame(x = NA_real_, y = NaN))) + expect_true(vec_detect_missing(data.frame(x = NA_complex_, y = NA_complex_))) + expect_true(vec_detect_missing(data.frame(x = complex(real = NA, imaginary = 1), y = complex(real = 1, imaginary = NA)))) + expect_true(vec_detect_missing(data.frame(x = NA_character_, y = NA_character_))) + expect_true(vec_detect_missing(new_data_frame(list(x = list(NULL), y = list(NULL))))) }) test_that("raw vectors can never be NA", { - expect_false(vec_equal_na(raw(1))) - expect_false(vec_equal_na(data.frame(x = raw(1), y = raw(1)))) + expect_false(vec_detect_missing(raw(1))) + expect_false(vec_detect_missing(data.frame(x = raw(1), y = raw(1)))) }) test_that("vectorised over rows of a data frame", { df <- data.frame(x = c(1, 1, NA, NA), y = c(1, NA, 1, NA)) - expect_equal(vec_equal_na(df), c(FALSE, FALSE, FALSE, TRUE)) + expect_equal(vec_detect_missing(df), c(FALSE, FALSE, FALSE, TRUE)) }) test_that("works recursively with data frame columns", { df <- data.frame(x = c(1, 1, NA, NA)) df$df <- data.frame(y = c(NA, 1, 1, NA), z = c(1, NA, 1, NA)) - expect_equal(vec_equal_na(df), c(FALSE, FALSE, FALSE, TRUE)) + expect_equal(vec_detect_missing(df), c(FALSE, FALSE, FALSE, TRUE)) }) test_that("0 row, N col data frame always returns `logical()` (#1585)", { - expect_identical(vec_equal_na(data_frame()), logical()) - expect_identical(vec_equal_na(data_frame(x = integer(), y = double())), logical()) + expect_identical(vec_detect_missing(data_frame()), logical()) + expect_identical(vec_detect_missing(data_frame(x = integer(), y = double())), logical()) }) test_that(">0 row, 0 col data frame always returns `TRUE` for each row (#1585)", { - # `vec_equal_na()` returns `TRUE` for each row because it (in theory) does + # `vec_detect_missing()` returns `TRUE` for each row because it (in theory) does # `all()` on each row, and since there are 0 columns we get # `all(logical()) == TRUE` for each row. expect_identical( - vec_equal_na(data_frame(.size = 2L)), + vec_detect_missing(data_frame(.size = 2L)), c(TRUE, TRUE) ) }) test_that("works with `NULL` input (#1494)", { - expect_identical(vec_equal_na(NULL), logical()) + expect_identical(vec_detect_missing(NULL), logical()) }) # ------------------------------------------------------------------------------ @@ -121,11 +121,11 @@ test_that("0 row, N col data frame always returns `FALSE` (#1585)", { expect_false(vec_any_missing(df)) expect_false(vec_any_missing(data_frame(x = integer(), y = double()))) - # This is consistent with `vec_equal_na()` returning `logical()` for 0 row + # This is consistent with `vec_detect_missing()` returning `logical()` for 0 row # data frames. Then `any(logical()) == FALSE` to get `vec_any_missing()`. expect_identical( vec_any_missing(df), - any(vec_equal_na(df)) + any(vec_detect_missing(df)) ) }) @@ -134,12 +134,12 @@ test_that(">0 row, 0 col data frame always returns `TRUE` (#1585)", { expect_true(vec_any_missing(df)) - # This is consistent with `vec_equal_na()` returning `TRUE` for each row + # This is consistent with `vec_detect_missing()` returning `TRUE` for each row # because it (in theory) does `all()` on each row, and since there are 0 # columns we get `all(logical()) == TRUE` for each row. # Then `any(c(TRUE, TRUE)) == TRUE` to get `vec_any_missing()`. expect_identical( vec_any_missing(df), - any(vec_equal_na(df)) + any(vec_detect_missing(df)) ) }) diff --git a/tests/testthat/test-type-integer64.R b/tests/testthat/test-type-integer64.R index 7c7b9376b..82a36a151 100644 --- a/tests/testthat/test-type-integer64.R +++ b/tests/testthat/test-type-integer64.R @@ -176,10 +176,10 @@ test_that("equality proxy on >=2-D input converts to data frame and proxies each test_that("can detect missing values with integer64 (#1304)", { x <- bit64::as.integer64(c(NA, NA, 2, NA, 2, 2)) - expect_identical(vec_equal_na(x), c(TRUE, TRUE, FALSE, TRUE, FALSE, FALSE)) + expect_identical(vec_detect_missing(x), c(TRUE, TRUE, FALSE, TRUE, FALSE, FALSE)) dim(x) <- c(3, 2) - expect_identical(vec_equal_na(x), c(TRUE, FALSE, FALSE)) + expect_identical(vec_detect_missing(x), c(TRUE, FALSE, FALSE)) }) test_that("can fill missing values with integer64", { From 5e8f7b5788ff60ceb109047552901e1f1975fcff Mon Sep 17 00:00:00 2001 From: Davis Vaughan Date: Mon, 26 Sep 2022 10:49:58 -0400 Subject: [PATCH 085/312] Transition from `call` to `error_call` (#1674) * Add `syms.dot_error_call` * Update `data_frame()` * Update `df_list()` * Update `vec_rep()` and `vec_rep_each()` * Update `vec_locate_matches()` * Update `vec_rbind()` * Update `vec_cbind()` --- NEWS.md | 8 +-- R/bind.R | 4 +- R/match.R | 2 +- R/rep.R | 4 +- R/type-data-frame.R | 4 +- man/data_frame.Rd | 4 +- man/df_list.Rd | 4 +- man/vec-rep.Rd | 13 +++-- man/vec_bind.Rd | 6 +-- man/vec_locate_matches.Rd | 4 +- src/bind.c | 68 ++++++++++++------------ src/decl/bind-decl.h | 12 ++--- src/decl/match-decl.h | 6 +-- src/decl/rep-decl.h | 4 +- src/decl/type-data-frame-decl.h | 4 +- src/globals.c | 1 + src/globals.h | 1 + src/match.c | 32 +++++------ src/rep.c | 44 +++++++-------- src/type-data-frame.c | 28 +++++----- tests/testthat/_snaps/bind.md | 18 +++---- tests/testthat/_snaps/match.md | 26 +++++---- tests/testthat/_snaps/type-data-frame.md | 8 +-- tests/testthat/helper-conditions.R | 4 +- tests/testthat/test-bind.R | 18 +++---- tests/testthat/test-match.R | 22 ++++---- tests/testthat/test-type-data-frame.R | 8 +-- 27 files changed, 185 insertions(+), 172 deletions(-) diff --git a/NEWS.md b/NEWS.md index a27cc49de..01774f490 100644 --- a/NEWS.md +++ b/NEWS.md @@ -28,7 +28,7 @@ * `vec_compare()` now throws a more informative error when attempting to compare complex vectors (#1655). -* `vec_rep()` and friends gain `call`, `x_arg`, and `times_arg` +* `vec_rep()` and friends gain `error_call`, `x_arg`, and `times_arg` arguments so they can be embedded in frontends (#1303). * Record vectors now fail as expected when indexed along dimensions @@ -74,9 +74,9 @@ * `num_as_location()` now works correctly when a combination of `zero = "error"` and `negative = "invert"` are used (#1612). -* `data_frame()` and `df_list()` have gained `.call` arguments (#1610). +* `data_frame()` and `df_list()` have gained `.error_call` arguments (#1610). -* `vec_locate_matches()` has gained a `call` argument (#1611). +* `vec_locate_matches()` has gained an `error_call` argument (#1611). * `"select"` and `"relocate"` have been added as valid subscript actions to support tidyselect and dplyr (#1596). @@ -84,7 +84,7 @@ * `num_as_location()` has a new `oob = "remove"` argument to remove out-of-bounds locations (#1595). -* `vec_rbind()` and `vec_cbind()` now have `.call` arguments (#1597). +* `vec_rbind()` and `vec_cbind()` now have `.error_call` arguments (#1597). * `df_list()` has gained a new `.unpack` argument to optionally disable data frame unpacking (#1616). diff --git a/R/bind.R b/R/bind.R index daad2d403..efa4e103d 100644 --- a/R/bind.R +++ b/R/bind.R @@ -178,7 +178,7 @@ vec_rbind <- function(..., .names_to = rlang::zap(), .name_repair = c("unique", "universal", "check_unique"), .name_spec = NULL, - .call = current_env()) { + .error_call = current_env()) { .External2(ffi_rbind, .ptype, .names_to, .name_repair, .name_spec) } vec_rbind <- fn_inline_formals(vec_rbind, ".name_repair") @@ -195,7 +195,7 @@ vec_cbind <- function(..., .ptype = NULL, .size = NULL, .name_repair = c("unique", "universal", "check_unique", "minimal"), - .call = current_env()) { + .error_call = current_env()) { .External2(ffi_cbind, .ptype, .size, .name_repair) } vec_cbind <- fn_inline_formals(vec_cbind, ".name_repair") diff --git a/R/match.R b/R/match.R index 537ebd92b..19142bd42 100644 --- a/R/match.R +++ b/R/match.R @@ -243,7 +243,7 @@ vec_locate_matches <- function(needles, chr_proxy_collate = NULL, needles_arg = "", haystack_arg = "", - call = current_env()) { + error_call = current_env()) { check_dots_empty0(...) frame <- environment() diff --git a/R/rep.R b/R/rep.R index c86ac6a53..1caacfe34 100644 --- a/R/rep.R +++ b/R/rep.R @@ -89,7 +89,7 @@ NULL vec_rep <- function(x, times, ..., - call = current_env(), + error_call = current_env(), x_arg = "x", times_arg = "times") { check_dots_empty0(...) @@ -101,7 +101,7 @@ vec_rep <- function(x, vec_rep_each <- function(x, times, ..., - call = current_env(), + error_call = current_env(), x_arg = "x", times_arg = "times") { check_dots_empty0(...) diff --git a/R/type-data-frame.R b/R/type-data-frame.R index 6e72e766e..93cf7dce2 100644 --- a/R/type-data-frame.R +++ b/R/type-data-frame.R @@ -90,7 +90,7 @@ df_list <- function(..., .size = NULL, .unpack = TRUE, .name_repair = c("check_unique", "unique", "universal", "minimal"), - .call = current_env()) { + .error_call = current_env()) { .Call(ffi_df_list, list2(...), .size, .unpack, .name_repair, environment()) } df_list <- fn_inline_formals(df_list, ".name_repair") @@ -164,7 +164,7 @@ df_list <- fn_inline_formals(df_list, ".name_repair") data_frame <- function(..., .size = NULL, .name_repair = c("check_unique", "unique", "universal", "minimal"), - .call = current_env()) { + .error_call = current_env()) { .Call(ffi_data_frame, list2(...), .size, .name_repair, environment()) } data_frame <- fn_inline_formals(data_frame, ".name_repair") diff --git a/man/data_frame.Rd b/man/data_frame.Rd index 605224883..df1c93982 100644 --- a/man/data_frame.Rd +++ b/man/data_frame.Rd @@ -8,7 +8,7 @@ data_frame( ..., .size = NULL, .name_repair = c("check_unique", "unique", "universal", "minimal"), - .call = current_env() + .error_call = current_env() ) } \arguments{ @@ -21,7 +21,7 @@ be computed as the common size of the inputs.} \item{.name_repair}{One of \code{"check_unique"}, \code{"unique"}, \code{"universal"} or \code{"minimal"}. See \code{\link[=vec_as_names]{vec_as_names()}} for the meaning of these options.} -\item{.call}{The execution environment of a currently +\item{.error_call}{The execution environment of a currently running function, e.g. \code{caller_env()}. The function will be mentioned in error messages as the source of the error. See the \code{call} argument of \code{\link[rlang:abort]{abort()}} for more information.} diff --git a/man/df_list.Rd b/man/df_list.Rd index 2fa85388f..fafee6637 100644 --- a/man/df_list.Rd +++ b/man/df_list.Rd @@ -9,7 +9,7 @@ df_list( .size = NULL, .unpack = TRUE, .name_repair = c("check_unique", "unique", "universal", "minimal"), - .call = current_env() + .error_call = current_env() ) } \arguments{ @@ -25,7 +25,7 @@ will be computed as the common size of the inputs.} \item{.name_repair}{One of \code{"check_unique"}, \code{"unique"}, \code{"universal"} or \code{"minimal"}. See \code{\link[=vec_as_names]{vec_as_names()}} for the meaning of these options.} -\item{.call}{The execution environment of a currently +\item{.error_call}{The execution environment of a currently running function, e.g. \code{caller_env()}. The function will be mentioned in error messages as the source of the error. See the \code{call} argument of \code{\link[rlang:abort]{abort()}} for more information.} diff --git a/man/vec-rep.Rd b/man/vec-rep.Rd index f28e3aa5d..2f19c0507 100644 --- a/man/vec-rep.Rd +++ b/man/vec-rep.Rd @@ -7,13 +7,20 @@ \alias{vec_unrep} \title{Repeat a vector} \usage{ -vec_rep(x, times, ..., call = current_env(), x_arg = "x", times_arg = "times") +vec_rep( + x, + times, + ..., + error_call = current_env(), + x_arg = "x", + times_arg = "times" +) vec_rep_each( x, times, ..., - call = current_env(), + error_call = current_env(), x_arg = "x", times_arg = "times" ) @@ -32,7 +39,7 @@ the size of \code{x}.} \item{...}{These dots are for future extensions and must be empty.} -\item{call}{The execution environment of a currently +\item{error_call}{The execution environment of a currently running function, e.g. \code{caller_env()}. The function will be mentioned in error messages as the source of the error. See the \code{call} argument of \code{\link[rlang:abort]{abort()}} for more information.} diff --git a/man/vec_bind.Rd b/man/vec_bind.Rd index 429a38954..7acc9a8b2 100644 --- a/man/vec_bind.Rd +++ b/man/vec_bind.Rd @@ -12,7 +12,7 @@ vec_rbind( .names_to = rlang::zap(), .name_repair = c("unique", "universal", "check_unique"), .name_spec = NULL, - .call = current_env() + .error_call = current_env() ) vec_cbind( @@ -20,7 +20,7 @@ vec_cbind( .ptype = NULL, .size = NULL, .name_repair = c("unique", "universal", "check_unique", "minimal"), - .call = current_env() + .error_call = current_env() ) } \arguments{ @@ -73,7 +73,7 @@ names of the inputs. This only has an effect when \code{.names_to} is set to \code{NULL}, which causes the input names to be assigned as row names.} -\item{.call}{The execution environment of a currently +\item{.error_call}{The execution environment of a currently running function, e.g. \code{caller_env()}. The function will be mentioned in error messages as the source of the error. See the \code{call} argument of \code{\link[rlang:abort]{abort()}} for more information.} diff --git a/man/vec_locate_matches.Rd b/man/vec_locate_matches.Rd index 05dbe929e..95108cf00 100644 --- a/man/vec_locate_matches.Rd +++ b/man/vec_locate_matches.Rd @@ -18,7 +18,7 @@ vec_locate_matches( chr_proxy_collate = NULL, needles_arg = "", haystack_arg = "", - call = current_env() + error_call = current_env() ) } \arguments{ @@ -138,7 +138,7 @@ ordering and \code{stringi::stri_sort_key()} for locale-aware ordering.} \item{needles_arg, haystack_arg}{Argument tags for \code{needles} and \code{haystack} used in error messages.} -\item{call}{The execution environment of a currently +\item{error_call}{The execution environment of a currently running function, e.g. \code{caller_env()}. The function will be mentioned in error messages as the source of the error. See the \code{call} argument of \code{\link[rlang:abort]{abort()}} for more information.} diff --git a/src/bind.c b/src/bind.c index 007b84d81..1446ce9da 100644 --- a/src/bind.c +++ b/src/bind.c @@ -6,7 +6,7 @@ r_obj* ffi_rbind(r_obj* ffi_call, r_obj* op, r_obj* args, r_obj* frame) { args = r_node_cdr(args); - struct r_lazy call = { .x = syms_dot_call, .env = frame }; + struct r_lazy error_call = { .x = syms.dot_error_call, .env = frame }; r_obj* xs = KEEP(rlang_env_dots_list(frame)); r_obj* ptype = r_node_car(args); args = r_node_cdr(args); @@ -21,7 +21,7 @@ r_obj* ffi_rbind(r_obj* ffi_call, r_obj* op, r_obj* args, r_obj* frame) { } else if (r_is_string(names_to)) { names_to = r_chr_get(names_to, 0); } else { - r_abort_lazy_call(call, + r_abort_lazy_call(error_call, "%s must be `NULL`, a string, or an `rlang::zap()` object.", r_c_str_format_error_arg(".names_to")); } @@ -30,14 +30,14 @@ r_obj* ffi_rbind(r_obj* ffi_call, r_obj* op, r_obj* args, r_obj* frame) { struct name_repair_opts name_repair_opts = validate_bind_name_repair(name_repair, false); KEEP(name_repair_opts.shelter); - name_repair_opts.call = call; + name_repair_opts.call = error_call; r_obj* out = vec_rbind(xs, ptype, names_to, &name_repair_opts, name_spec, - call); + error_call); FREE(2); return out; @@ -49,7 +49,7 @@ r_obj* vec_rbind(r_obj* xs, r_obj* names_to, struct name_repair_opts* name_repair, r_obj* name_spec, - struct r_lazy call) { + struct r_lazy error_call) { // In case `.arg` is added later on struct vctrs_arg* p_arg = vec_args.empty; @@ -59,7 +59,7 @@ r_obj* vec_rbind(r_obj* xs, for (r_ssize i = 0; i < n_inputs; ++i) { r_list_poke(xs, i, as_df_row(r_list_get(xs, i), name_repair, - call)); + error_call)); } // The common type holds information about common column names, @@ -70,7 +70,7 @@ r_obj* vec_rbind(r_obj* xs, DF_FALLBACK_DEFAULT, S3_FALLBACK_true, p_arg, - call); + error_call); KEEP_N(ptype, &n_prot); r_ssize n_cols = r_length(ptype); @@ -82,11 +82,11 @@ r_obj* vec_rbind(r_obj* xs, if (r_typeof(ptype) == R_TYPE_logical && !n_cols) { ptype = as_df_row_impl(vctrs_shared_na_lgl, name_repair, - call); + error_call); KEEP_N(ptype, &n_prot); } if (!is_data_frame(ptype)) { - r_abort_lazy_call(call, "Can't bind objects that are not coercible to a data frame."); + r_abort_lazy_call(error_call, "Can't bind objects that are not coercible to a data frame."); } bool assign_names = !r_inherits(name_spec, "rlang_zap"); @@ -96,7 +96,7 @@ r_obj* vec_rbind(r_obj* xs, if (has_names_to) { if (!assign_names) { - r_abort_lazy_call(call, + r_abort_lazy_call(error_call, "Can't zap outer names when %s is supplied.", r_c_str_format_error_arg(".names_to")); } @@ -109,7 +109,7 @@ r_obj* vec_rbind(r_obj* xs, ptype = cbind_names_to(r_names(xs) != r_null, names_to, ptype, - call); + error_call); KEEP_N(ptype, &n_prot); names_to_loc = 0; } @@ -121,7 +121,7 @@ r_obj* vec_rbind(r_obj* xs, DF_FALLBACK_DEFAULT, S3_FALLBACK_true, vec_args.empty, - call); + error_call); KEEP_N(xs, &n_prot); // Find individual input sizes and total size of output @@ -139,7 +139,7 @@ r_obj* vec_rbind(r_obj* xs, r_obj* proxy = KEEP_N(vec_proxy(ptype), &n_prot); if (!is_data_frame(proxy)) { - r_abort_lazy_call(call, "Can't fill a data frame that doesn't have a data frame proxy."); + r_abort_lazy_call(error_call, "Can't fill a data frame that doesn't have a data frame proxy."); } r_keep_loc out_pi; @@ -270,18 +270,18 @@ r_obj* vec_rbind(r_obj* xs, static r_obj* as_df_row(r_obj* x, struct name_repair_opts* name_repair, - struct r_lazy call) { + struct r_lazy error_call) { if (vec_is_unspecified(x) && r_names(x) == r_null) { return x; } else { - return as_df_row_impl(x, name_repair, call); + return as_df_row_impl(x, name_repair, error_call); } } static r_obj* as_df_row_impl(r_obj* x, struct name_repair_opts* name_repair, - struct r_lazy call) { + struct r_lazy error_call) { if (x == r_null) { return x; } @@ -295,7 +295,7 @@ r_obj* as_df_row_impl(r_obj* x, r_ssize ndim = (dim == r_null) ? 1 : r_length(dim); if (ndim > 2) { - r_abort_lazy_call(call, "Can't bind arrays."); + r_abort_lazy_call(error_call, "Can't bind arrays."); } if (ndim == 2) { r_obj* out = KEEP(r_as_data_frame(x)); @@ -333,15 +333,15 @@ r_obj* ffi_as_df_row(r_obj* x, r_obj* quiet, r_obj* frame) { .fn = r_null, .quiet = r_lgl_get(quiet, 0) }; - struct r_lazy call = { .x = frame, .env = r_null }; - return as_df_row(x, &name_repair_opts, call); + struct r_lazy error_call = { .x = frame, .env = r_null }; + return as_df_row(x, &name_repair_opts, error_call); } static r_obj* cbind_names_to(bool has_names, r_obj* names_to, r_obj* ptype, - struct r_lazy call) { + struct r_lazy error_call) { r_obj* index_ptype = has_names ? r_globals.empty_chr : r_globals.empty_int; r_obj* tmp = KEEP(r_alloc_list(2)); @@ -354,7 +354,7 @@ r_obj* cbind_names_to(bool has_names, r_attrib_poke_names(tmp, tmp_nms); - r_obj* out = vec_cbind(tmp, r_null, r_null, NULL, call); + r_obj* out = vec_cbind(tmp, r_null, r_null, NULL, error_call); FREE(2); return out; @@ -365,7 +365,7 @@ r_obj* cbind_names_to(bool has_names, r_obj* ffi_cbind(r_obj* ffi_call, r_obj* op, r_obj* args, r_obj* frame) { args = r_node_cdr(args); - struct r_lazy call = { .x = syms_dot_call, .env = frame }; + struct r_lazy error_call = { .x = syms.dot_error_call, .env = frame }; r_obj* xs = KEEP(rlang_env_dots_list(frame)); r_obj* ptype = r_node_car(args); args = r_node_cdr(args); @@ -374,9 +374,9 @@ r_obj* ffi_cbind(r_obj* ffi_call, r_obj* op, r_obj* args, r_obj* frame) { struct name_repair_opts name_repair_opts = validate_bind_name_repair(name_repair, true); KEEP(name_repair_opts.shelter); - name_repair_opts.call = call; + name_repair_opts.call = error_call; - r_obj* out = vec_cbind(xs, ptype, size, &name_repair_opts, call); + r_obj* out = vec_cbind(xs, ptype, size, &name_repair_opts, error_call); FREE(2); return out; @@ -387,7 +387,7 @@ r_obj* vec_cbind(r_obj* xs, r_obj* ptype, r_obj* size, struct name_repair_opts* name_repair, - struct r_lazy call) { + struct r_lazy error_call) { // In case `.arg` is added later on struct vctrs_arg* p_arg = vec_args.empty; @@ -403,7 +403,7 @@ r_obj* vec_cbind(r_obj* xs, DF_FALLBACK_DEFAULT, S3_FALLBACK_false, p_arg, - call)); + error_call)); if (type == r_null) { type = new_data_frame(r_globals.empty_list, 0); } else if (!is_data_frame(type)) { @@ -415,13 +415,13 @@ r_obj* vec_cbind(r_obj* xs, r_ssize nrow; if (size == r_null) { - nrow = vec_check_size_common(xs, 0, p_arg, call); + nrow = vec_check_size_common(xs, 0, p_arg, error_call); } else { - nrow = vec_as_short_length(size, vec_args.dot_size, call); + nrow = vec_as_short_length(size, vec_args.dot_size, error_call); } if (rownames != r_null && r_length(rownames) != nrow) { - rownames = KEEP(vec_check_recycle(rownames, nrow, vec_args.empty, call)); + rownames = KEEP(vec_check_recycle(rownames, nrow, vec_args.empty, error_call)); rownames = vec_as_unique_names(rownames, false); FREE(1); } @@ -444,7 +444,7 @@ r_obj* vec_cbind(r_obj* xs, r_obj* outer_name = has_names ? xs_names_p[i] : strings_empty; bool allow_packing; - x = KEEP(as_df_col(x, outer_name, &allow_packing, call)); + x = KEEP(as_df_col(x, outer_name, &allow_packing, error_call)); // Remove outer name of column vectors because they shouldn't be repacked if (has_names && !allow_packing) { @@ -550,16 +550,16 @@ r_obj* cbind_container_type(r_obj* x, void* data) { // [[ register() ]] r_obj* ffi_as_df_col(r_obj* x, r_obj* outer, r_obj* frame) { - struct r_lazy call = { .x = frame, .env = r_null }; + struct r_lazy error_call = { .x = frame, .env = r_null }; bool allow_pack; - return as_df_col(x, r_chr_get(outer, 0), &allow_pack, call); + return as_df_col(x, r_chr_get(outer, 0), &allow_pack, error_call); } static r_obj* as_df_col(r_obj* x, r_obj* outer, bool* allow_pack, - struct r_lazy call) { + struct r_lazy error_call) { if (is_data_frame(x)) { *allow_pack = true; return r_clone(x); @@ -567,7 +567,7 @@ r_obj* as_df_col(r_obj* x, r_ssize ndim = vec_bare_dim_n(x); if (ndim > 2) { - r_abort_lazy_call(call, "Can't bind arrays."); + r_abort_lazy_call(error_call, "Can't bind arrays."); } if (ndim > 0) { *allow_pack = true; diff --git a/src/decl/bind-decl.h b/src/decl/bind-decl.h index 4dfe56456..30a36b678 100644 --- a/src/decl/bind-decl.h +++ b/src/decl/bind-decl.h @@ -4,17 +4,17 @@ r_obj* vec_rbind(r_obj* xs, r_obj* id, struct name_repair_opts* name_repair, r_obj* name_spec, - struct r_lazy call); + struct r_lazy error_call); static r_obj* as_df_row(r_obj* x, struct name_repair_opts* name_repair, - struct r_lazy call); + struct r_lazy error_call); static r_obj* as_df_row_impl(r_obj* x, struct name_repair_opts* name_repair, - struct r_lazy call); + struct r_lazy error_call); static struct name_repair_opts validate_bind_name_repair(r_obj* name_repair, bool allow_minimal); @@ -24,19 +24,19 @@ r_obj* vec_cbind(r_obj* xs, r_obj* ptype, r_obj* size, struct name_repair_opts* name_repair, - struct r_lazy call); + struct r_lazy error_call); static r_obj* cbind_names_to(bool has_names, r_obj* names_to, r_obj* ptype, - struct r_lazy call); + struct r_lazy error_call); static r_obj* as_df_col(r_obj* x, r_obj* outer, bool* allow_pack, - struct r_lazy call); + struct r_lazy error_call); static r_obj* cbind_container_type(r_obj* x, void* data); diff --git a/src/decl/match-decl.h b/src/decl/match-decl.h index ab2580d78..d7b4b03e3 100644 --- a/src/decl/match-decl.h +++ b/src/decl/match-decl.h @@ -22,7 +22,7 @@ r_obj* vec_locate_matches(r_obj* needles, r_obj* chr_proxy_collate, struct vctrs_arg* needles_arg, struct vctrs_arg* haystack_arg, - struct r_lazy call); + struct r_lazy error_call); static r_obj* df_locate_matches(r_obj* needles, @@ -40,7 +40,7 @@ r_obj* df_locate_matches(r_obj* needles, const enum vctrs_ops* v_ops, struct vctrs_arg* needles_arg, struct vctrs_arg* haystack_arg, - struct r_lazy call); + struct r_lazy error_call); static void df_locate_matches_recurse(r_ssize col, @@ -167,7 +167,7 @@ r_obj* expand_compact_indices(const int* v_o_haystack, const struct poly_df_data* p_haystack, struct vctrs_arg* needles_arg, struct vctrs_arg* haystack_arg, - struct r_lazy call); + struct r_lazy error_call); static r_obj* compute_nesting_container_info(r_obj* haystack, diff --git a/src/decl/rep-decl.h b/src/decl/rep-decl.h index efb368789..ada05d49d 100644 --- a/src/decl/rep-decl.h +++ b/src/decl/rep-decl.h @@ -25,14 +25,14 @@ void stop_rep_size_oob(struct r_lazy call); static r_obj* vec_rep_each_uniform(r_obj* x, int times, - struct r_lazy call, + struct r_lazy error_call, struct vctrs_arg* p_times_arg); static r_obj* vec_rep_each_impl(r_obj* x, r_obj* times, const r_ssize times_size, - struct r_lazy call, + struct r_lazy error_call, struct vctrs_arg* p_times_arg); static inline diff --git a/src/decl/type-data-frame-decl.h b/src/decl/type-data-frame-decl.h index d80c6208a..e9677c2db 100644 --- a/src/decl/type-data-frame-decl.h +++ b/src/decl/type-data-frame-decl.h @@ -17,14 +17,14 @@ static r_obj* data_frame(r_obj* x, r_ssize size, const struct name_repair_opts* p_name_repair_opts, - struct r_lazy call); + struct r_lazy error_call); static r_obj* df_list(r_obj* x, r_ssize size, bool unpack, const struct name_repair_opts* p_name_repair_opts, - struct r_lazy call); + struct r_lazy error_call); static r_obj* df_list_drop_null(r_obj* x); diff --git a/src/globals.c b/src/globals.c index cd193a12c..16426fefa 100644 --- a/src/globals.c +++ b/src/globals.c @@ -51,6 +51,7 @@ void vctrs_init_globals(r_obj* ns) { syms.arg = r_sym("arg"); syms.dot_arg = r_sym(".arg"); syms.dot_call = r_sym(".call"); + syms.dot_error_call = r_sym(".error_call"); syms.haystack_arg = r_sym("haystack_arg"); syms.needles_arg = r_sym("needles_arg"); syms.repair_arg = r_sym("repair_arg"); diff --git a/src/globals.h b/src/globals.h index 0c5162a54..f32d01cf8 100644 --- a/src/globals.h +++ b/src/globals.h @@ -8,6 +8,7 @@ struct syms { r_obj* arg; r_obj* dot_arg; r_obj* dot_call; + r_obj* dot_error_call; r_obj* haystack_arg; r_obj* needles_arg; r_obj* repair_arg; diff --git a/src/match.c b/src/match.c index 6980dd695..17e369128 100644 --- a/src/match.c +++ b/src/match.c @@ -85,7 +85,7 @@ r_obj* ffi_locate_matches(r_obj* needles, r_obj* needles_arg, r_obj* haystack_arg, r_obj* frame) { - struct r_lazy call = { .x = syms_call, .env = frame }; + struct r_lazy error_call = { .x = r_syms.error_call, .env = frame }; struct r_lazy internal_call = { .x = frame, .env = r_null }; const struct vctrs_incomplete c_incomplete = parse_incomplete(incomplete, internal_call); @@ -110,7 +110,7 @@ r_obj* ffi_locate_matches(r_obj* needles, chr_proxy_collate, &c_needles_arg, &c_haystack_arg, - call + error_call ); } @@ -127,7 +127,7 @@ r_obj* vec_locate_matches(r_obj* needles, r_obj* chr_proxy_collate, struct vctrs_arg* needles_arg, struct vctrs_arg* haystack_arg, - struct r_lazy call) { + struct r_lazy error_call) { int n_prot = 0; int _; @@ -136,7 +136,7 @@ r_obj* vec_locate_matches(r_obj* needles, haystack, needles_arg, haystack_arg, - call, + error_call, DF_FALLBACK_quiet, &_ ), &n_prot); @@ -146,7 +146,7 @@ r_obj* vec_locate_matches(r_obj* needles, ptype, needles_arg, vec_args.empty, - call, + error_call, DF_FALLBACK_quiet, S3_FALLBACK_false ), &n_prot); @@ -156,7 +156,7 @@ r_obj* vec_locate_matches(r_obj* needles, ptype, haystack_arg, vec_args.empty, - call, + error_call, DF_FALLBACK_quiet, S3_FALLBACK_false ), &n_prot); @@ -195,7 +195,7 @@ r_obj* vec_locate_matches(r_obj* needles, if (n_cols == 0) { // If there are no columns, this operation isn't well defined. - r_abort_lazy_call(call, "Must have at least 1 column to match on."); + r_abort_lazy_call(error_call, "Must have at least 1 column to match on."); } // Compute the locations of incomplete values per column since computing @@ -236,7 +236,7 @@ r_obj* vec_locate_matches(r_obj* needles, v_ops, needles_arg, haystack_arg, - call + error_call ); FREE(n_prot); @@ -261,7 +261,7 @@ r_obj* df_locate_matches(r_obj* needles, const enum vctrs_ops* v_ops, struct vctrs_arg* needles_arg, struct vctrs_arg* haystack_arg, - struct r_lazy call) { + struct r_lazy error_call) { int n_prot = 0; r_obj* o_needles = KEEP_N(vec_order( @@ -460,7 +460,7 @@ r_obj* df_locate_matches(r_obj* needles, p_haystack, needles_arg, haystack_arg, - call + error_call ), &n_prot); FREE(n_prot); @@ -1568,7 +1568,7 @@ r_obj* expand_compact_indices(const int* v_o_haystack, const struct poly_df_data* p_haystack, struct vctrs_arg* needles_arg, struct vctrs_arg* haystack_arg, - struct r_lazy call) { + struct r_lazy error_call) { int n_prot = 0; const r_ssize n_used = p_loc_first_match_o_haystack->count; @@ -1678,7 +1678,7 @@ r_obj* expand_compact_indices(const int* v_o_haystack, continue; } case VCTRS_INCOMPLETE_ACTION_error: { - stop_matches_incomplete(loc_needles, needles_arg, call); + stop_matches_incomplete(loc_needles, needles_arg, error_call); } case VCTRS_INCOMPLETE_ACTION_compare: case VCTRS_INCOMPLETE_ACTION_match: { @@ -1711,7 +1711,7 @@ r_obj* expand_compact_indices(const int* v_o_haystack, continue; } case VCTRS_NO_MATCH_ACTION_error: { - stop_matches_nothing(loc_needles, needles_arg, haystack_arg, call); + stop_matches_nothing(loc_needles, needles_arg, haystack_arg, error_call); } default: { r_stop_internal("Unknown `no_match->action`."); @@ -1760,9 +1760,9 @@ r_obj* expand_compact_indices(const int* v_o_haystack, if (any_multiple) { if (multiple == VCTRS_MULTIPLE_error) { - stop_matches_multiple(loc_needles, needles_arg, haystack_arg, call); + stop_matches_multiple(loc_needles, needles_arg, haystack_arg, error_call); } else if (multiple == VCTRS_MULTIPLE_warning) { - warn_matches_multiple(loc_needles, needles_arg, haystack_arg, call); + warn_matches_multiple(loc_needles, needles_arg, haystack_arg, error_call); } // We know there are multiple and don't need to continue checking @@ -1923,7 +1923,7 @@ r_obj* expand_compact_indices(const int* v_o_haystack, } if (remaining->action == VCTRS_REMAINING_ACTION_error) { - stop_matches_remaining(i, needles_arg, haystack_arg, call); + stop_matches_remaining(i, needles_arg, haystack_arg, error_call); } // Overwrite with location, this moves all "remaining" locations to the diff --git a/src/rep.c b/src/rep.c index aa7c97b15..cd6490863 100644 --- a/src/rep.c +++ b/src/rep.c @@ -6,10 +6,10 @@ static r_obj* vec_rep(r_obj* x, int times, - struct r_lazy call, + struct r_lazy error_call, struct vctrs_arg* p_x_arg, struct vctrs_arg* p_times_arg) { - check_rep_times(times, call, p_times_arg); + check_rep_times(times, error_call, p_times_arg); if (times == 1) { return x; @@ -19,11 +19,11 @@ r_obj* vec_rep(r_obj* x, const r_ssize x_size = vec_size(x); if (x_size == 1) { - return vec_check_recycle(x, times_, p_x_arg, call); + return vec_check_recycle(x, times_, p_x_arg, error_call); } if (multiply_would_overflow(x_size, times_)) { - stop_rep_size_oob(call); + stop_rep_size_oob(error_call); }; const r_ssize size = x_size * times_; @@ -46,7 +46,7 @@ r_obj* vec_rep(r_obj* x, } r_obj* ffi_vec_rep(r_obj* x, r_obj* ffi_times, r_obj* frame) { - struct r_lazy call = { .x = r_syms.call, .env = frame }; + struct r_lazy error_call = { .x = r_syms.error_call, .env = frame }; struct r_lazy x_arg_lazy = { .x = syms.x_arg, .env = frame }; struct vctrs_arg x_arg = new_lazy_arg(&x_arg_lazy); @@ -58,14 +58,14 @@ r_obj* ffi_vec_rep(r_obj* x, r_obj* ffi_times, r_obj* frame) { r_globals.empty_int, ×_arg, vec_args.empty, - call)); + error_call)); if (vec_size(ffi_times) != 1) { - stop_rep_times_size(call, ×_arg); + stop_rep_times_size(error_call, ×_arg); } const int times = r_int_get(ffi_times, 0); - r_obj* out = vec_rep(x, times, call, &x_arg, ×_arg); + r_obj* out = vec_rep(x, times, error_call, &x_arg, ×_arg); FREE(1); return out; @@ -77,14 +77,14 @@ r_obj* ffi_vec_rep(r_obj* x, r_obj* ffi_times, r_obj* frame) { static r_obj* vec_rep_each(r_obj* x, r_obj* times, - struct r_lazy call, + struct r_lazy error_call, struct vctrs_arg* p_x_arg, struct vctrs_arg* p_times_arg) { times = KEEP(vec_cast(times, r_globals.empty_int, p_times_arg, vec_args.empty, - call)); + error_call)); const r_ssize times_size = vec_size(times); @@ -96,12 +96,12 @@ r_obj* vec_rep_each(r_obj* x, if (times_ == 1) { out = x; } else if (times_ == 0) { - out = vec_ptype(x, p_x_arg, call); + out = vec_ptype(x, p_x_arg, error_call); } else { - out = vec_rep_each_uniform(x, times_, call, p_times_arg); + out = vec_rep_each_uniform(x, times_, error_call, p_times_arg); } } else { - out = vec_rep_each_impl(x, times, times_size, call, p_times_arg); + out = vec_rep_each_impl(x, times, times_size, error_call, p_times_arg); } FREE(1); @@ -109,7 +109,7 @@ r_obj* vec_rep_each(r_obj* x, } r_obj* ffi_vec_rep_each(r_obj* x, r_obj* times, r_obj* frame) { - struct r_lazy call = { .x = r_syms.call, .env = frame }; + struct r_lazy error_call = { .x = r_syms.error_call, .env = frame }; struct r_lazy x_arg_lazy = { .x = syms.times_arg, .env = frame }; struct vctrs_arg x_arg = new_lazy_arg(&x_arg_lazy); @@ -117,7 +117,7 @@ r_obj* ffi_vec_rep_each(r_obj* x, r_obj* times, r_obj* frame) { struct r_lazy times_arg_lazy = { .x = syms.times_arg, .env = frame }; struct vctrs_arg times_arg = new_lazy_arg(×_arg_lazy); - return vec_rep_each(x, times, call, &x_arg, ×_arg); + return vec_rep_each(x, times, error_call, &x_arg, ×_arg); } @@ -126,15 +126,15 @@ r_obj* ffi_vec_rep_each(r_obj* x, r_obj* times, r_obj* frame) { static r_obj* vec_rep_each_uniform(r_obj* x, int times, - struct r_lazy call, + struct r_lazy error_call, struct vctrs_arg* p_times_arg) { - check_rep_each_times(times, 1, call, p_times_arg); + check_rep_each_times(times, 1, error_call, p_times_arg); const r_ssize times_ = (r_ssize) times; const r_ssize x_size = vec_size(x); if (multiply_would_overflow(x_size, times_)) { - stop_rep_size_oob(call); + stop_rep_size_oob(error_call); }; const r_ssize size = x_size * times_; @@ -159,7 +159,7 @@ r_obj* vec_rep_each_uniform(r_obj* x, static r_obj* vec_rep_each_impl(r_obj* x, r_obj* times, const r_ssize times_size, - struct r_lazy call, + struct r_lazy error_call, struct vctrs_arg* p_times_arg) { const r_ssize x_size = vec_size(x); @@ -167,7 +167,7 @@ static r_obj* vec_rep_each_impl(r_obj* x, stop_recycle_incompatible_size(times_size, x_size, p_times_arg, - call); + error_call); } const int* v_times = r_int_cbegin(times); @@ -176,12 +176,12 @@ static r_obj* vec_rep_each_impl(r_obj* x, for (r_ssize i = 0; i < times_size; ++i) { const int elt_times = v_times[i]; - check_rep_each_times(elt_times, i + 1, call, p_times_arg); + check_rep_each_times(elt_times, i + 1, error_call, p_times_arg); const r_ssize elt_times_ = (r_ssize) elt_times; if (plus_would_overflow(size, elt_times_)) { - stop_rep_size_oob(call); + stop_rep_size_oob(error_call); } size += elt_times_; diff --git a/src/type-data-frame.c b/src/type-data-frame.c index 93a8b363b..b7cb054f7 100644 --- a/src/type-data-frame.c +++ b/src/type-data-frame.c @@ -175,22 +175,22 @@ r_obj* ffi_data_frame(r_obj* x, r_obj* size, r_obj* name_repair, r_obj* frame) { - struct r_lazy call = { .x = syms_dot_call, .env = frame }; + struct r_lazy error_call = { .x = syms.dot_error_call, .env = frame }; struct name_repair_opts name_repair_opts = new_name_repair_opts(name_repair, lazy_args.dot_name_repair, false, - call); + error_call); KEEP(name_repair_opts.shelter); r_ssize c_size = 0; if (size == r_null) { - c_size = vec_check_size_common(x, 0, vec_args.empty, call); + c_size = vec_check_size_common(x, 0, vec_args.empty, error_call); } else { - c_size = vec_as_short_length(size, vec_args.dot_size, call); + c_size = vec_as_short_length(size, vec_args.dot_size, error_call); } - r_obj* out = data_frame(x, c_size, &name_repair_opts, call); + r_obj* out = data_frame(x, c_size, &name_repair_opts, error_call); FREE(1); return out; @@ -200,9 +200,9 @@ static r_obj* data_frame(r_obj* x, r_ssize size, const struct name_repair_opts* p_name_repair_opts, - struct r_lazy call) { + struct r_lazy error_call) { const bool unpack = true; - r_obj* out = KEEP(df_list(x, size, unpack, p_name_repair_opts, call)); + r_obj* out = KEEP(df_list(x, size, unpack, p_name_repair_opts, error_call)); out = new_data_frame(out, size); FREE(1); return out; @@ -215,24 +215,24 @@ r_obj* ffi_df_list(r_obj* x, r_obj* unpack, r_obj* name_repair, r_obj* frame) { - struct r_lazy call = { .x = syms_dot_call, .env = frame }; + struct r_lazy error_call = { .x = syms.dot_error_call, .env = frame }; struct name_repair_opts name_repair_opts = new_name_repair_opts(name_repair, lazy_args.dot_name_repair, false, - call); + error_call); KEEP(name_repair_opts.shelter); r_ssize c_size = 0; if (size == r_null) { - c_size = vec_check_size_common(x, 0, vec_args.empty, call); + c_size = vec_check_size_common(x, 0, vec_args.empty, error_call); } else { - c_size = vec_as_short_length(size, vec_args.dot_size, call); + c_size = vec_as_short_length(size, vec_args.dot_size, error_call); } const bool c_unpack = r_arg_as_bool(unpack, ".unpack"); - r_obj* out = df_list(x, c_size, c_unpack, &name_repair_opts, call); + r_obj* out = df_list(x, c_size, c_unpack, &name_repair_opts, error_call); FREE(1); return out; @@ -243,12 +243,12 @@ r_obj* df_list(r_obj* x, r_ssize size, bool unpack, const struct name_repair_opts* p_name_repair_opts, - struct r_lazy call) { + struct r_lazy error_call) { if (r_typeof(x) != R_TYPE_list) { r_stop_internal("`x` must be a list."); } - x = KEEP(vec_check_recycle_common(x, size, vec_args.empty, call)); + x = KEEP(vec_check_recycle_common(x, size, vec_args.empty, error_call)); r_ssize n_cols = r_length(x); diff --git a/tests/testthat/_snaps/bind.md b/tests/testthat/_snaps/bind.md index fe9ab0ef1..9c9a10ff5 100644 --- a/tests/testthat/_snaps/bind.md +++ b/tests/testthat/_snaps/bind.md @@ -7,14 +7,14 @@ Error in `vec_rbind()`: ! Can't combine `..1$x` and `..2$x` . Code - (expect_error(vec_rbind(x_int, x_chr, .call = call("foo")), class = "vctrs_error_incompatible_type") + (expect_error(vec_rbind(x_int, x_chr, .error_call = call("foo")), class = "vctrs_error_incompatible_type") ) Output Error in `foo()`: ! Can't combine `..1$x` and `..2$x` . Code - (expect_error(vec_rbind(x_int, x_chr, .ptype = x_chr, .call = call("foo")), + (expect_error(vec_rbind(x_int, x_chr, .ptype = x_chr, .error_call = call("foo")), class = "vctrs_error_incompatible_type")) Output @@ -64,7 +64,7 @@ Error in `vec_rbind()`: ! Can't bind arrays. Code - (expect_error(vec_rbind(array(NA, c(1, 1, 1)), .call = call("foo")))) + (expect_error(vec_rbind(array(NA, c(1, 1, 1)), .error_call = call("foo")))) Output Error in `foo()`: @@ -89,7 +89,7 @@ Error in `vec_cbind()`: ! `..1` must be a vector, not a object. Code - (expect_error(vec_cbind(foobar(list()), .call = call("foo")))) + (expect_error(vec_cbind(foobar(list()), .error_call = call("foo")))) Output Error in `foo()`: @@ -101,7 +101,7 @@ Error in `vec_cbind()`: ! Can't recycle `a` (size 2) to match `b` (size 0). Code - (expect_error(vec_cbind(a = 1:2, b = int(), .call = call("foo")))) + (expect_error(vec_cbind(a = 1:2, b = int(), .error_call = call("foo")))) Output Error in `foo()`: @@ -164,7 +164,7 @@ Error in `vec_rbind()`: ! `.names_to` must be `NULL`, a string, or an `rlang::zap()` object. Code - (expect_error(vec_rbind(.names_to = letters, .call = call("foo")))) + (expect_error(vec_rbind(.names_to = letters, .error_call = call("foo")))) Output Error in `foo()`: @@ -179,7 +179,7 @@ Error in `vec_cbind()`: ! Can't bind arrays. Code - (expect_error(vec_cbind(a, .call = call("foo")))) + (expect_error(vec_cbind(a, .error_call = call("foo")))) Output Error in `foo()`: @@ -353,7 +353,7 @@ x These names are duplicated: * "x" at locations 1 and 2. Code - (expect_error(vec_rbind(df, df, .name_repair = "check_unique", .call = call( + (expect_error(vec_rbind(df, df, .name_repair = "check_unique", .error_call = call( "foo")), class = "vctrs_error_names_must_be_unique")) Output @@ -399,7 +399,7 @@ ! Can't zap outer names when `.names_to` is supplied. Code (expect_error(vec_rbind(foo = c(x = 1), .names_to = "id", .name_spec = zap(), - .call = call("foo")))) + .error_call = call("foo")))) Output Error in `foo()`: diff --git a/tests/testthat/_snaps/match.md b/tests/testthat/_snaps/match.md index 6f02c044f..0d2afc637 100644 --- a/tests/testthat/_snaps/match.md +++ b/tests/testthat/_snaps/match.md @@ -9,7 +9,7 @@ --- Code - vec_locate_matches(data_frame(), data_frame(), call = call("foo")) + vec_locate_matches(data_frame(), data_frame(), error_call = call("foo")) Condition Error in `foo()`: ! Must have at least 1 column to match on. @@ -25,7 +25,7 @@ --- Code - vec_locate_matches(x, y, needles_arg = "x", call = call("foo")) + vec_locate_matches(x, y, needles_arg = "x", error_call = call("foo")) Condition Error in `foo()`: ! Can't combine `x` and . @@ -49,7 +49,7 @@ x The element at location 1 contains missing values. Code (expect_error(vec_locate_matches(NA, 1, incomplete = "error", needles_arg = "foo", - call = call("fn")))) + error_call = call("fn")))) Output Error in `fn()`: @@ -78,7 +78,8 @@ Error in `vec_locate_matches()`: ! `incomplete` must be one of: "compare", "match", "drop", or "error". Code - (expect_error(vec_locate_matches(1, 2, incomplete = "x", call = call("fn")))) + (expect_error(vec_locate_matches(1, 2, incomplete = "x", error_call = call("fn"))) + ) Output Error in `vec_locate_matches()`: @@ -103,7 +104,7 @@ x The element at location 1 has multiple matches. Code (expect_error(vec_locate_matches(1L, c(1L, 1L), multiple = "error", - needles_arg = "foo", call = call("fn")))) + needles_arg = "foo", error_call = call("fn")))) Output Error in `fn()`: @@ -137,7 +138,7 @@ x The element at location 1 has multiple matches. Code (expect_warning(vec_locate_matches(1L, c(1L, 1L), multiple = "warning", - needles_arg = "foo", call = call("fn")))) + needles_arg = "foo", error_call = call("fn")))) Output Warning in `fn()`: @@ -173,7 +174,8 @@ Error in `vec_locate_matches()`: ! `multiple` must be one of "all", "any", "first", "last", "warning", or "error". Code - (expect_error(vec_locate_matches(1, 2, multiple = "x", call = call("fn")))) + (expect_error(vec_locate_matches(1, 2, multiple = "x", error_call = call("fn"))) + ) Output Error in `vec_locate_matches()`: @@ -198,7 +200,7 @@ x The element at location 1 does not have a match. Code (expect_error(vec_locate_matches(1, 2, no_match = "error", needles_arg = "foo", - call = call("fn")))) + error_call = call("fn")))) Output Error in `fn()`: @@ -246,7 +248,8 @@ Error in `vec_locate_matches()`: ! `no_match` must be either "drop" or "error". Code - (expect_error(vec_locate_matches(1, 2, no_match = "x", call = call("fn")))) + (expect_error(vec_locate_matches(1, 2, no_match = "x", error_call = call("fn"))) + ) Output Error in `vec_locate_matches()`: @@ -271,7 +274,7 @@ x The value at location 1 was not matched. Code (expect_error(vec_locate_matches(1, 2, remaining = "error", needles_arg = "foo", - call = call("fn")))) + error_call = call("fn")))) Output Error in `fn()`: @@ -308,7 +311,8 @@ Error in `vec_locate_matches()`: ! `remaining` must be either "drop" or "error". Code - (expect_error(vec_locate_matches(1, 2, remaining = "x", call = call("fn")))) + (expect_error(vec_locate_matches(1, 2, remaining = "x", error_call = call("fn"))) + ) Output Error in `vec_locate_matches()`: diff --git a/tests/testthat/_snaps/type-data-frame.md b/tests/testthat/_snaps/type-data-frame.md index 9d1bcf387..b558b7406 100644 --- a/tests/testthat/_snaps/type-data-frame.md +++ b/tests/testthat/_snaps/type-data-frame.md @@ -164,7 +164,7 @@ * "a" at locations 1 and 2. i Use argument `.name_repair` to specify repair strategy. Code - (expect_error(data_frame(a = 1, a = 1, .call = call("foo")))) + (expect_error(data_frame(a = 1, a = 1, .error_call = call("foo")))) Output Error in `foo()`: @@ -179,7 +179,7 @@ Error in `data_frame()`: ! Can't recycle `a` (size 2) to match `b` (size 0). Code - (expect_error(data_frame(a = 1:2, b = int(), .call = call("foo")))) + (expect_error(data_frame(a = 1:2, b = int(), .error_call = call("foo")))) Output Error in `foo()`: @@ -194,7 +194,7 @@ * "a" at locations 1 and 2. i Use argument `.name_repair` to specify repair strategy. Code - (expect_error(df_list(a = 1, a = 1, .call = call("foo")))) + (expect_error(df_list(a = 1, a = 1, .error_call = call("foo")))) Output Error in `foo()`: @@ -209,7 +209,7 @@ Error in `df_list()`: ! Can't recycle `a` (size 2) to match `b` (size 0). Code - (expect_error(df_list(a = 1:2, b = int(), .call = call("foo")))) + (expect_error(df_list(a = 1:2, b = int(), .error_call = call("foo")))) Output Error in `foo()`: diff --git a/tests/testthat/helper-conditions.R b/tests/testthat/helper-conditions.R index dd0378eb2..8d62668b2 100644 --- a/tests/testthat/helper-conditions.R +++ b/tests/testthat/helper-conditions.R @@ -60,7 +60,7 @@ my_vec_rep <- function(my_x, my_times) { vec_rep( my_x, my_times, - call = current_env(), + error_call = current_env(), x_arg = "my_x", times_arg = "my_times" ) @@ -70,7 +70,7 @@ my_vec_rep_each <- function(my_x, my_times) { vec_rep_each( my_x, my_times, - call = current_env(), + error_call = current_env(), x_arg = "my_x", times_arg = "my_times" ) diff --git a/tests/testthat/test-bind.R b/tests/testthat/test-bind.R index 06004cdb1..507027f54 100644 --- a/tests/testthat/test-bind.R +++ b/tests/testthat/test-bind.R @@ -39,11 +39,11 @@ test_that("incompatible columns throws common type error", { class = "vctrs_error_incompatible_type" )) (expect_error( - vec_rbind(x_int, x_chr, .call = call("foo")), + vec_rbind(x_int, x_chr, .error_call = call("foo")), class = "vctrs_error_incompatible_type" )) (expect_error( - vec_rbind(x_int, x_chr, .ptype = x_chr, .call = call("foo")), + vec_rbind(x_int, x_chr, .ptype = x_chr, .error_call = call("foo")), class = "vctrs_error_incompatible_type" )) }) @@ -221,7 +221,7 @@ test_that("can construct an id column", { test_that("vec_rbind() fails with arrays of dimensionality > 3", { expect_snapshot({ (expect_error(vec_rbind(array(NA, c(1, 1, 1))))) - (expect_error(vec_rbind(array(NA, c(1, 1, 1)), .call = call("foo")))) + (expect_error(vec_rbind(array(NA, c(1, 1, 1)), .error_call = call("foo")))) }) }) @@ -396,10 +396,10 @@ test_that("performance: Row binding with df-cols doesn't duplicate on every assi test_that("vec_cbind() reports error context", { expect_snapshot({ (expect_error(vec_cbind(foobar(list())))) - (expect_error(vec_cbind(foobar(list()), .call = call("foo")))) + (expect_error(vec_cbind(foobar(list()), .error_call = call("foo")))) (expect_error(vec_cbind(a = 1:2, b = int()))) - (expect_error(vec_cbind(a = 1:2, b = int(), .call = call("foo")))) + (expect_error(vec_cbind(a = 1:2, b = int(), .error_call = call("foo")))) }) }) @@ -497,7 +497,7 @@ test_that("can supply `.names_to` to `vec_rbind()` (#229)", { expect_snapshot({ (expect_error(vec_rbind(.names_to = letters))) (expect_error(vec_rbind(.names_to = 10))) - (expect_error(vec_rbind(.names_to = letters, .call = call("foo")))) + (expect_error(vec_rbind(.names_to = letters, .error_call = call("foo")))) }) x <- data_frame(foo = 1:2, bar = 3:4) @@ -597,7 +597,7 @@ test_that("vec_cbind() fails with arrays of dimensionality > 3", { expect_snapshot({ (expect_error(vec_cbind(a))) - (expect_error(vec_cbind(a, .call = call("foo")))) + (expect_error(vec_cbind(a, .error_call = call("foo")))) (expect_error(vec_cbind(x = a))) }) }) @@ -752,7 +752,7 @@ test_that("rbind repairs names of data frames (#704)", { class = "vctrs_error_names_must_be_unique" )) (expect_error( - vec_rbind(df, df, .name_repair = "check_unique", .call = call("foo")), + vec_rbind(df, df, .name_repair = "check_unique", .error_call = call("foo")), class = "vctrs_error_names_must_be_unique" )) }) @@ -995,7 +995,7 @@ test_that("can't zap names when `.names_to` is supplied", { vec_rbind(foo = c(x = 1), .names_to = "id", .name_spec = zap()) )) (expect_error( - vec_rbind(foo = c(x = 1), .names_to = "id", .name_spec = zap(), .call = call("foo")) + vec_rbind(foo = c(x = 1), .names_to = "id", .name_spec = zap(), .error_call = call("foo")) )) }) }) diff --git a/tests/testthat/test-match.R b/tests/testthat/test-match.R index 0b7cb984e..98fb9a1a3 100644 --- a/tests/testthat/test-match.R +++ b/tests/testthat/test-match.R @@ -395,7 +395,7 @@ test_that("must have at least 1 column to match", { vec_locate_matches(data_frame(), data_frame()) }) expect_snapshot(error = TRUE, { - vec_locate_matches(data_frame(), data_frame(), call = call("foo")) + vec_locate_matches(data_frame(), data_frame(), error_call = call("foo")) }) }) @@ -544,7 +544,7 @@ test_that("common type of `needles` and `haystack` is taken", { vec_locate_matches(x, y) }) expect_snapshot(error = TRUE, { - vec_locate_matches(x, y, needles_arg = "x", call = call("foo")) + vec_locate_matches(x, y, needles_arg = "x", error_call = call("foo")) }) }) @@ -817,7 +817,7 @@ test_that("`incomplete` can error informatively", { expect_snapshot({ (expect_error(vec_locate_matches(NA, 1, incomplete = "error"))) (expect_error(vec_locate_matches(NA, 1, incomplete = "error", needles_arg = "foo"))) - (expect_error(vec_locate_matches(NA, 1, incomplete = "error", needles_arg = "foo", call = call("fn")))) + (expect_error(vec_locate_matches(NA, 1, incomplete = "error", needles_arg = "foo", error_call = call("fn")))) }) }) @@ -831,7 +831,7 @@ test_that("`incomplete` is validated", { (expect_error(vec_locate_matches(1, 2, incomplete = c("match", "drop")))) (expect_error(vec_locate_matches(1, 2, incomplete = "x"))) # Uses internal call - (expect_error(vec_locate_matches(1, 2, incomplete = "x", call = call("fn")))) + (expect_error(vec_locate_matches(1, 2, incomplete = "x", error_call = call("fn")))) }) }) @@ -909,7 +909,7 @@ test_that("`multiple` can error informatively", { expect_snapshot({ (expect_error(vec_locate_matches(1L, c(1L, 1L), multiple = "error"))) (expect_error(vec_locate_matches(1L, c(1L, 1L), multiple = "error", needles_arg = "foo"))) - (expect_error(vec_locate_matches(1L, c(1L, 1L), multiple = "error", needles_arg = "foo", call = call("fn")))) + (expect_error(vec_locate_matches(1L, c(1L, 1L), multiple = "error", needles_arg = "foo", error_call = call("fn")))) (expect_error(vec_locate_matches(1L, c(1L, 1L), multiple = "error", needles_arg = "foo", haystack_arg = "bar"))) }) }) @@ -918,7 +918,7 @@ test_that("`multiple` can warn informatively", { expect_snapshot({ (expect_warning(vec_locate_matches(1L, c(1L, 1L), multiple = "warning"))) (expect_warning(vec_locate_matches(1L, c(1L, 1L), multiple = "warning", needles_arg = "foo"))) - (expect_warning(vec_locate_matches(1L, c(1L, 1L), multiple = "warning", needles_arg = "foo", call = call("fn")))) + (expect_warning(vec_locate_matches(1L, c(1L, 1L), multiple = "warning", needles_arg = "foo", error_call = call("fn")))) (expect_warning(vec_locate_matches(1L, c(1L, 1L), multiple = "warning", needles_arg = "foo", haystack_arg = "bar"))) }) }) @@ -1034,7 +1034,7 @@ test_that("`multiple` is validated", { (expect_error(vec_locate_matches(1, 2, multiple = c("first", "last")))) (expect_error(vec_locate_matches(1, 2, multiple = "x"))) # Uses internal error - (expect_error(vec_locate_matches(1, 2, multiple = "x", call = call("fn")))) + (expect_error(vec_locate_matches(1, 2, multiple = "x", error_call = call("fn")))) }) }) @@ -1080,7 +1080,7 @@ test_that("`no_match` can error informatively", { expect_snapshot({ (expect_error(vec_locate_matches(1, 2, no_match = "error"))) (expect_error(vec_locate_matches(1, 2, no_match = "error", needles_arg = "foo"))) - (expect_error(vec_locate_matches(1, 2, no_match = "error", needles_arg = "foo", call = call("fn")))) + (expect_error(vec_locate_matches(1, 2, no_match = "error", needles_arg = "foo", error_call = call("fn")))) (expect_error(vec_locate_matches(1, 2, no_match = "error", needles_arg = "foo", haystack_arg = "bar"))) }) }) @@ -1115,7 +1115,7 @@ test_that("`no_match` is validated", { (expect_error(vec_locate_matches(1, 2, no_match = c(1L, 2L)))) (expect_error(vec_locate_matches(1, 2, no_match = "x"))) # Uses internal call - (expect_error(vec_locate_matches(1, 2, no_match = "x", call = call("fn")))) + (expect_error(vec_locate_matches(1, 2, no_match = "x", error_call = call("fn")))) }) }) @@ -1204,7 +1204,7 @@ test_that("`remaining` can error informatively", { expect_snapshot({ (expect_error(vec_locate_matches(1, 2, remaining = "error"))) (expect_error(vec_locate_matches(1, 2, remaining = "error", needles_arg = "foo"))) - (expect_error(vec_locate_matches(1, 2, remaining = "error", needles_arg = "foo", call = call("fn")))) + (expect_error(vec_locate_matches(1, 2, remaining = "error", needles_arg = "foo", error_call = call("fn")))) (expect_error(vec_locate_matches(1, 2, remaining = "error", needles_arg = "foo", haystack_arg = "bar"))) }) }) @@ -1215,7 +1215,7 @@ test_that("`remaining` is validated", { (expect_error(vec_locate_matches(1, 2, remaining = c(1L, 2L)))) (expect_error(vec_locate_matches(1, 2, remaining = "x"))) # Uses internal call - (expect_error(vec_locate_matches(1, 2, remaining = "x", call = call("fn")))) + (expect_error(vec_locate_matches(1, 2, remaining = "x", error_call = call("fn")))) }) }) diff --git a/tests/testthat/test-type-data-frame.R b/tests/testthat/test-type-data-frame.R index ce64d5ff9..566e79641 100644 --- a/tests/testthat/test-type-data-frame.R +++ b/tests/testthat/test-type-data-frame.R @@ -448,14 +448,14 @@ test_that("new_data_frame() zaps existing attributes", { test_that("data_frame() and df_list() report error context", { expect_snapshot({ (expect_error(data_frame(a = 1, a = 1))) - (expect_error(data_frame(a = 1, a = 1, .call = call("foo")))) + (expect_error(data_frame(a = 1, a = 1, .error_call = call("foo")))) (expect_error(data_frame(a = 1:2, b = int()))) - (expect_error(data_frame(a = 1:2, b = int(), .call = call("foo")))) + (expect_error(data_frame(a = 1:2, b = int(), .error_call = call("foo")))) (expect_error(df_list(a = 1, a = 1))) - (expect_error(df_list(a = 1, a = 1, .call = call("foo")))) + (expect_error(df_list(a = 1, a = 1, .error_call = call("foo")))) (expect_error(df_list(a = 1:2, b = int()))) - (expect_error(df_list(a = 1:2, b = int(), .call = call("foo")))) + (expect_error(df_list(a = 1:2, b = int(), .error_call = call("foo")))) }) }) From 27c334e53d31cd512e39d2f1c6092b0a171df9f4 Mon Sep 17 00:00:00 2001 From: DavisVaughan Date: Mon, 26 Sep 2022 10:55:55 -0400 Subject: [PATCH 086/312] Bump the dev version To allow us to force this dev version in dplyr --- DESCRIPTION | 2 +- src/version.c | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/DESCRIPTION b/DESCRIPTION index 62047f927..a7762afbb 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -1,6 +1,6 @@ Package: vctrs Title: Vector Helpers -Version: 0.4.1.9000 +Version: 0.4.1.9001 Authors@R: c(person(given = "Hadley", family = "Wickham", diff --git a/src/version.c b/src/version.c index 5d66a50c1..6419bc496 100644 --- a/src/version.c +++ b/src/version.c @@ -1,7 +1,7 @@ #define R_NO_REMAP #include -const char* vctrs_version = "0.4.1.9000"; +const char* vctrs_version = "0.4.1.9001"; /** * This file records the expected package version in the shared From a0ee85860d94459bf83194e036138f3160329cdc Mon Sep 17 00:00:00 2001 From: DavisVaughan Date: Mon, 26 Sep 2022 15:08:27 -0400 Subject: [PATCH 087/312] Require rlang 1.0.6 and update snapshots --- DESCRIPTION | 2 +- tests/testthat/_snaps/match.md | 3 ++- 2 files changed, 3 insertions(+), 2 deletions(-) diff --git a/DESCRIPTION b/DESCRIPTION index a7762afbb..bbb3f1d8a 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -32,7 +32,7 @@ Imports: cli (>= 3.4.0), glue, lifecycle (>= 1.0.2), - rlang (>= 1.0.5) + rlang (>= 1.0.6) Suggests: bit64, covr, diff --git a/tests/testthat/_snaps/match.md b/tests/testthat/_snaps/match.md index 0d2afc637..f9c3d18f7 100644 --- a/tests/testthat/_snaps/match.md +++ b/tests/testthat/_snaps/match.md @@ -327,5 +327,6 @@ Error in `vec_locate_matches()`: ! Match procedure results in an allocation larger than 2^31-1 elements. Attempted allocation size was 50000005000000. i In file 'match.c' at line . - i This is an internal error in the vctrs package, please report it to the package authors. + i This is an internal error that was detected in the vctrs package. + Please report it at with a reprex () and the full backtrace. From d191324f3df4971eb91694c608d094935f5056b2 Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Wed, 7 Sep 2022 11:26:30 +0200 Subject: [PATCH 088/312] Add `vec_proxy_recurse()` --- R/proxy.R | 7 +++++- src/decl/proxy-decl.h | 6 ++++++ src/init.c | 6 ++++-- src/proxy.c | 50 ++++++++++++++++++++++++++++++++++++++----- src/proxy.h | 1 + 5 files changed, 62 insertions(+), 8 deletions(-) diff --git a/R/proxy.R b/R/proxy.R index bc58c6492..93a48a5e2 100644 --- a/R/proxy.R +++ b/R/proxy.R @@ -136,7 +136,7 @@ #' @export vec_proxy <- function(x, ...) { check_dots_empty0(...) - return(.Call(vctrs_proxy, x)) + return(.Call(ffi_vec_proxy, x)) UseMethod("vec_proxy") } #' @export @@ -144,6 +144,11 @@ vec_proxy.default <- function(x, ...) { x } +vec_proxy_recurse <- function(x, ...) { + check_dots_empty0(...) + .Call(ffi_vec_proxy_recurse, x) +} + #' @rdname vec_proxy #' @param to The original vector to restore to. #' @export diff --git a/src/decl/proxy-decl.h b/src/decl/proxy-decl.h index 9ea60944a..d2a78abda 100644 --- a/src/decl/proxy-decl.h +++ b/src/decl/proxy-decl.h @@ -10,6 +10,9 @@ r_obj* fns_vec_proxy_equal_array; r_obj* fns_vec_proxy_compare_array; r_obj* fns_vec_proxy_order_array; +static +r_obj* vec_proxy_2(r_obj* x, bool recurse); + static inline r_obj* vec_proxy_equal_impl(r_obj* x); static inline @@ -37,3 +40,6 @@ r_obj* vec_proxy_order_invoke(r_obj* x, r_obj* method); static inline r_obj* df_proxy(r_obj* x, enum vctrs_proxy_kind kind); + +static inline +r_obj* df_proxy_recurse(r_obj* x); diff --git a/src/init.c b/src/init.c index befe5ec7f..5f2ede27a 100644 --- a/src/init.c +++ b/src/init.c @@ -55,7 +55,8 @@ extern r_obj* ffi_slice_seq(r_obj*, r_obj*, r_obj*, r_obj*); extern r_obj* ffi_slice_rep(r_obj*, r_obj*, r_obj*); extern r_obj* ffi_vec_restore(r_obj*, r_obj*); extern r_obj* ffi_vec_restore_default(r_obj*, r_obj*); -extern SEXP vec_proxy(SEXP); +extern r_obj* vec_proxy(r_obj*); +extern r_obj* vec_proxy_recurse(r_obj*); extern SEXP vec_proxy_equal(SEXP); extern SEXP vec_proxy_compare(SEXP); extern SEXP vec_proxy_order(SEXP); @@ -224,7 +225,8 @@ static const R_CallMethodDef CallEntries[] = { {"ffi_slice_rep", (DL_FUNC) &ffi_slice_rep, 3}, {"ffi_vec_restore", (DL_FUNC) &ffi_vec_restore, 2}, {"ffi_vec_restore_default", (DL_FUNC) &ffi_vec_restore_default, 2}, - {"vctrs_proxy", (DL_FUNC) &vec_proxy, 1}, + {"ffi_vec_proxy", (DL_FUNC) &vec_proxy, 1}, + {"ffi_vec_proxy_recurse", (DL_FUNC) &vec_proxy_recurse, 1}, {"vctrs_proxy_equal", (DL_FUNC) &vec_proxy_equal, 1}, {"vctrs_proxy_compare", (DL_FUNC) &vec_proxy_compare, 1}, {"vctrs_proxy_order", (DL_FUNC) &vec_proxy_order, 1}, diff --git a/src/proxy.c b/src/proxy.c index b3616d374..153976f3e 100644 --- a/src/proxy.c +++ b/src/proxy.c @@ -2,16 +2,56 @@ #include "type-data-frame.h" #include "decl/proxy-decl.h" + // [[ register() ]] r_obj* vec_proxy(r_obj* x) { + return vec_proxy_2(x, false); +} + +// [[ register() ]] +r_obj* vec_proxy_recurse(r_obj* x) { + return vec_proxy_2(x, true); +} + +static +r_obj* vec_proxy_2(r_obj* x, bool recurse) { struct vctrs_type_info info = vec_type_info(x); KEEP(info.shelter); - r_obj* out; - if (info.type == VCTRS_TYPE_s3) { - out = vec_proxy_invoke(x, info.proxy_method); - } else { - out = x; + switch (info.type) { + case VCTRS_TYPE_dataframe: { + r_obj* out = recurse ? df_proxy_recurse(x) : x; + FREE(1); + return out; + } + + case VCTRS_TYPE_s3: { + r_obj* out = KEEP(vec_proxy_invoke(x, info.proxy_method)); + if (!is_data_frame(out)) { + FREE(2); + return out; + } + + out = KEEP(recurse ? df_proxy_recurse(out) : out); + + FREE(3); + return out; + } + + default: + FREE(1); + return x; + } +} + +// Recurse into data frames +static +r_obj* df_proxy_recurse(r_obj* x) { + r_obj* out = KEEP(vec_clone_referenced(x, VCTRS_OWNED_false)); + + for (r_ssize i = 0, n = r_length(out); i < n; ++i) { + r_obj* col = r_list_get(out, i); + r_list_poke(out, i, vec_proxy_recurse(col)); } FREE(1); diff --git a/src/proxy.h b/src/proxy.h index dedbc48db..c33bafd9a 100644 --- a/src/proxy.h +++ b/src/proxy.h @@ -7,6 +7,7 @@ r_obj* vec_proxy(r_obj* x); r_obj* vec_proxy_equal(r_obj* x); r_obj* vec_proxy_compare(r_obj* x); r_obj* vec_proxy_order(r_obj* x); +r_obj* vec_proxy_recurse(r_obj* x); r_obj* vec_proxy_method(r_obj* x); r_obj* vec_proxy_invoke(r_obj* x, r_obj* method); From d9d065331332fb6d4ce8d2add4a6cd09e39b0b7c Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Wed, 7 Sep 2022 11:48:22 +0200 Subject: [PATCH 089/312] Add `vec_restore_recurse()` --- R/proxy.R | 14 ++++++---- src/decl/proxy-restore-decl.h | 6 +++++ src/init.c | 2 ++ src/proxy-restore.c | 50 ++++++++++++++++++++++++++++++----- src/proxy-restore.h | 13 +++++++-- src/proxy.c | 2 +- src/utils.c | 4 +-- 7 files changed, 74 insertions(+), 17 deletions(-) diff --git a/R/proxy.R b/R/proxy.R index 93a48a5e2..317f74a8d 100644 --- a/R/proxy.R +++ b/R/proxy.R @@ -144,11 +144,6 @@ vec_proxy.default <- function(x, ...) { x } -vec_proxy_recurse <- function(x, ...) { - check_dots_empty0(...) - .Call(ffi_vec_proxy_recurse, x) -} - #' @rdname vec_proxy #' @param to The original vector to restore to. #' @export @@ -168,6 +163,15 @@ vec_restore_default <- function(x, to, ...) { .Call(ffi_vec_restore_default, x, to) } +vec_proxy_recurse <- function(x, ...) { + check_dots_empty0(...) + .Call(ffi_vec_proxy_recurse, x) +} +vec_restore_recurse <- function(x, to, ...) { + check_dots_empty0(...) + .Call(ffi_vec_restore_recurse, x, to) +} + #' Extract underlying data #' #' @description diff --git a/src/decl/proxy-restore-decl.h b/src/decl/proxy-restore-decl.h index 577ba0d95..81ea3638f 100644 --- a/src/decl/proxy-restore-decl.h +++ b/src/decl/proxy-restore-decl.h @@ -1,5 +1,11 @@ static r_obj* syms_vec_restore_dispatch; static r_obj* fns_vec_restore_dispatch; +static +r_obj* vec_restore_4(r_obj* x, + r_obj* to, + const enum vctrs_owned owned, + bool recurse); + static r_obj* vec_restore_dispatch(r_obj* x, r_obj* to); diff --git a/src/init.c b/src/init.c index 5f2ede27a..046fb4310 100644 --- a/src/init.c +++ b/src/init.c @@ -55,6 +55,7 @@ extern r_obj* ffi_slice_seq(r_obj*, r_obj*, r_obj*, r_obj*); extern r_obj* ffi_slice_rep(r_obj*, r_obj*, r_obj*); extern r_obj* ffi_vec_restore(r_obj*, r_obj*); extern r_obj* ffi_vec_restore_default(r_obj*, r_obj*); +extern r_obj* ffi_vec_restore_recurse(r_obj*, r_obj*); extern r_obj* vec_proxy(r_obj*); extern r_obj* vec_proxy_recurse(r_obj*); extern SEXP vec_proxy_equal(SEXP); @@ -225,6 +226,7 @@ static const R_CallMethodDef CallEntries[] = { {"ffi_slice_rep", (DL_FUNC) &ffi_slice_rep, 3}, {"ffi_vec_restore", (DL_FUNC) &ffi_vec_restore, 2}, {"ffi_vec_restore_default", (DL_FUNC) &ffi_vec_restore_default, 2}, + {"ffi_vec_restore_recurse", (DL_FUNC) &ffi_vec_restore_recurse, 2}, {"ffi_vec_proxy", (DL_FUNC) &vec_proxy, 1}, {"ffi_vec_proxy_recurse", (DL_FUNC) &vec_proxy_recurse, 1}, {"vctrs_proxy_equal", (DL_FUNC) &vec_proxy_equal, 1}, diff --git a/src/proxy-restore.c b/src/proxy-restore.c index 2f19717bd..eae34e9bf 100644 --- a/src/proxy-restore.c +++ b/src/proxy-restore.c @@ -2,7 +2,6 @@ #include "type-data-frame.h" #include "decl/proxy-restore-decl.h" - // FIXME: Having `owned` as an argument to `vec_restore()` may be // unnecessary once we have recursive proxy / restore mechanisms. // It currently helps resolve performance issues in `vec_rbind()`'s usage of @@ -11,6 +10,18 @@ // call `vec_clone_referenced()`, which won't attempt to clone if we know we // own the object. See #1151. r_obj* vec_restore(r_obj* x, r_obj* to, const enum vctrs_owned owned) { + return vec_restore_4(x, to, owned, false); +} + +r_obj* vec_restore_recurse(r_obj* x, r_obj* to, const enum vctrs_owned owned) { + return vec_restore_4(x, to, owned, true); +} + +static +r_obj* vec_restore_4(r_obj* x, + r_obj* to, + const enum vctrs_owned owned, + bool recurse) { switch (class_type(to)) { case VCTRS_CLASS_bare_factor: case VCTRS_CLASS_bare_ordered: @@ -19,8 +30,8 @@ r_obj* vec_restore(r_obj* x, r_obj* to, const enum vctrs_owned owned) { case VCTRS_CLASS_bare_posixct: return vec_posixct_restore(x, to, owned); case VCTRS_CLASS_bare_posixlt: return vec_posixlt_restore(x, to, owned); case VCTRS_CLASS_bare_data_frame: - case VCTRS_CLASS_bare_tibble: return vec_bare_df_restore(x, to, owned); - case VCTRS_CLASS_data_frame: return vec_df_restore(x, to, owned); + case VCTRS_CLASS_bare_tibble: return vec_bare_df_restore(x, to, owned, recurse); + case VCTRS_CLASS_data_frame: return vec_df_restore(x, to, owned, recurse); default: return vec_restore_dispatch(x, to); } } @@ -28,6 +39,9 @@ r_obj* vec_restore(r_obj* x, r_obj* to, const enum vctrs_owned owned) { r_obj* ffi_vec_restore(r_obj* x, r_obj* to) { return vec_restore(x, to, vec_owned(x)); } +r_obj* ffi_vec_restore_recurse(r_obj* x, r_obj* to) { + return vec_restore_recurse(x, to, vec_owned(x)); +} static @@ -141,22 +155,44 @@ r_obj* ffi_vec_restore_default(r_obj* x, r_obj* to) { } +// TODO: be recursive from the inside out. + // Restore methods are passed the original atomic type back, so we // first restore data frames as such before calling the restore // method, if any -r_obj* vec_df_restore(r_obj* x, r_obj* to, const enum vctrs_owned owned) { - r_obj* out = KEEP(vec_bare_df_restore(x, to, owned)); +r_obj* vec_df_restore(r_obj* x, + r_obj* to, + const enum vctrs_owned owned, + bool recurse) { + r_obj* out = KEEP(vec_bare_df_restore(x, to, owned, recurse)); out = vec_restore_dispatch(out, to); FREE(1); return out; } -r_obj* vec_bare_df_restore(r_obj* x, r_obj* to, const enum vctrs_owned owned) { +r_obj* vec_bare_df_restore(r_obj* x, + r_obj* to, + const enum vctrs_owned owned, + bool recurse) { if (r_typeof(x) != R_TYPE_list) { r_stop_internal("Attempt to restore data frame from a %s.", r_type_as_c_string(r_typeof(x))); } + if (recurse) { + r_ssize n_cols = r_length(x); + if (n_cols != r_length(to)) { + r_stop_internal("Shape of `x` doesn't match `to` in recursive df restoration."); + }; + + for (r_ssize i = 0; i < n_cols; ++i) { + r_obj* x_col = r_list_get(x, i); + r_obj* to_col = r_list_get(to, i); + r_obj* x_restored = vec_restore_recurse(x_col, to_col, owned); + r_list_poke(x, i, x_restored); + } + } + x = KEEP(vec_restore_default(x, to, owned)); if (r_attrib_get(x, r_syms.names) == r_null) { @@ -181,7 +217,7 @@ r_obj* vec_bare_df_restore(r_obj* x, r_obj* to, const enum vctrs_owned owned) { } r_obj* ffi_vec_bare_df_restore(r_obj* x, r_obj* to) { - return vec_bare_df_restore(x, to, vec_owned(x)); + return vec_bare_df_restore(x, to, vec_owned(x), false); } diff --git a/src/proxy-restore.h b/src/proxy-restore.h index e67ab4fc4..7364e5d82 100644 --- a/src/proxy-restore.h +++ b/src/proxy-restore.h @@ -7,8 +7,17 @@ r_obj* vec_restore(r_obj* x, r_obj* to, const enum vctrs_owned owned); r_obj* vec_restore_default(r_obj* x, r_obj* to, const enum vctrs_owned owned); -r_obj* vec_bare_df_restore(r_obj* x, r_obj* to, const enum vctrs_owned owned); -r_obj* vec_df_restore(r_obj* x, r_obj* to, const enum vctrs_owned owned); +r_obj* vec_restore_recurse(r_obj* x, r_obj* to, const enum vctrs_owned owned); + +r_obj* vec_df_restore(r_obj* x, + r_obj* to, + const enum vctrs_owned owned, + bool recurse); + +r_obj* vec_bare_df_restore(r_obj* x, + r_obj* to, + const enum vctrs_owned owned, + bool recurse); #endif diff --git a/src/proxy.c b/src/proxy.c index 153976f3e..0aba9aac4 100644 --- a/src/proxy.c +++ b/src/proxy.c @@ -47,7 +47,7 @@ r_obj* vec_proxy_2(r_obj* x, bool recurse) { // Recurse into data frames static r_obj* df_proxy_recurse(r_obj* x) { - r_obj* out = KEEP(vec_clone_referenced(x, VCTRS_OWNED_false)); + r_obj* out = KEEP(r_clone(x)); for (r_ssize i = 0, n = r_length(out); i < n; ++i) { r_obj* col = r_list_get(out, i); diff --git a/src/utils.c b/src/utils.c index 1f35671f2..f09a7fb3b 100644 --- a/src/utils.c +++ b/src/utils.c @@ -353,7 +353,7 @@ SEXP bare_df_map(SEXP df, SEXP (*fn)(SEXP)) { SEXP out = PROTECT(map(df, fn)); // Total ownership because `map()` generates a fresh list - out = vec_bare_df_restore(out, df, VCTRS_OWNED_true); + out = vec_bare_df_restore(out, df, VCTRS_OWNED_true, false); UNPROTECT(1); return out; @@ -364,7 +364,7 @@ SEXP df_map(SEXP df, SEXP (*fn)(SEXP)) { SEXP out = PROTECT(map(df, fn)); // Total ownership because `map()` generates a fresh list - out = vec_df_restore(out, df, VCTRS_OWNED_true); + out = vec_df_restore(out, df, VCTRS_OWNED_true, false); UNPROTECT(1); return out; From 8530c06524396e9a34c836da8e6d45088ce10f82 Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Wed, 7 Sep 2022 15:46:47 +0200 Subject: [PATCH 090/312] Proxy recursively in `vec_rbind()` Closes #1217 --- src/bind.c | 5 +++-- src/slice-assign.c | 18 ++++++++++++++---- src/slice-assign.h | 1 + tests/testthat/_snaps/bind.md | 8 ++++---- tests/testthat/_snaps/c.md | 4 ++-- tests/testthat/test-bind.R | 36 +++++++++++++++++++++++++++-------- 6 files changed, 52 insertions(+), 20 deletions(-) diff --git a/src/bind.c b/src/bind.c index 1446ce9da..14deeed1e 100644 --- a/src/bind.c +++ b/src/bind.c @@ -137,7 +137,7 @@ r_obj* vec_rbind(r_obj* xs, ns[i] = size; } - r_obj* proxy = KEEP_N(vec_proxy(ptype), &n_prot); + r_obj* proxy = KEEP_N(vec_proxy_recurse(ptype), &n_prot); if (!is_data_frame(proxy)) { r_abort_lazy_call(error_call, "Can't fill a data frame that doesn't have a data frame proxy."); } @@ -190,6 +190,7 @@ r_obj* vec_rbind(r_obj* xs, r_ssize counter = 0; const struct vec_assign_opts bind_assign_opts = { + .recursive = true, .assign_names = assign_names, // Unlike in `vec_c()` we don't need to ignore outer names because // `df_assign()` doesn't deal with those @@ -261,7 +262,7 @@ r_obj* vec_rbind(r_obj* xs, } } - out = vec_restore(out, ptype, VCTRS_OWNED_true); + out = vec_restore_recurse(out, ptype, VCTRS_OWNED_true); FREE(n_prot); return out; diff --git a/src/slice-assign.c b/src/slice-assign.c index a0e9019f2..f51c225c1 100644 --- a/src/slice-assign.c +++ b/src/slice-assign.c @@ -347,12 +347,22 @@ r_obj* df_assign(r_obj* x, // No need to cast or recycle because those operations are // recursive and have already been performed. However, proxy and - // restore are not recursive so need to be done for each element - // we recurse into. `vec_proxy_assign()` will proxy the `value_elt`. - r_obj* proxy_elt = KEEP(vec_proxy(out_elt)); + // restore are not necessarily recursive and we wight need to + // proxy each element we recurse into. + // + // NOTE: `vec_proxy_assign()` proxies `value_elt`. + r_obj* proxy_elt = r_null; + if (opts->recursive) { + proxy_elt = KEEP(out_elt); + } else { + proxy_elt = KEEP(vec_proxy(out_elt)); + } r_obj* assigned = KEEP(vec_proxy_assign_opts(proxy_elt, index, value_elt, owned, opts)); - assigned = vec_restore(assigned, out_elt, owned); + + if (!opts->recursive) { + assigned = vec_restore(assigned, out_elt, owned); + } r_list_poke(out, i, assigned); FREE(2); diff --git a/src/slice-assign.h b/src/slice-assign.h index 6511fbd15..ccadf7376 100644 --- a/src/slice-assign.h +++ b/src/slice-assign.h @@ -7,6 +7,7 @@ struct vec_assign_opts { bool assign_names; bool ignore_outer_names; + bool recursive; struct vctrs_arg* x_arg; struct vctrs_arg* value_arg; struct r_lazy call; diff --git a/tests/testthat/_snaps/bind.md b/tests/testthat/_snaps/bind.md index 9c9a10ff5..1c0d42f2c 100644 --- a/tests/testthat/_snaps/bind.md +++ b/tests/testthat/_snaps/bind.md @@ -441,17 +441,17 @@ Output [1] 13.8KB Code - # FIXME (#1217): Data frame with rownames (non-repaired, recursive case) + # Data frame with rownames (non-repaired, recursive case) (#1217) df <- data_frame(x = 1:2, y = data_frame(x = 1:2)) dfs <- rep(list(df), 100) dfs <- map2(dfs, seq_along(dfs), set_rownames_recursively) with_memory_prof(vec_rbind_list(dfs)) Output - [1] 909KB + [1] 13KB Code - # FIXME (#1217): Data frame with rownames (repaired, recursive case) + # Data frame with rownames (repaired, recursive case) (#1217) dfs <- map(dfs, set_rownames_recursively) with_memory_prof(vec_rbind_list(dfs)) Output - [1] 922KB + [1] 25.3KB diff --git a/tests/testthat/_snaps/c.md b/tests/testthat/_snaps/c.md index 315c0fb34..99642150f 100644 --- a/tests/testthat/_snaps/c.md +++ b/tests/testthat/_snaps/c.md @@ -168,11 +168,11 @@ dfs <- map2(dfs, seq_along(dfs), set_rownames_recursively) with_memory_prof(list_unchop(dfs)) Output - [1] 908KB + [1] 11.6KB Code # FIXME (#1217): Data frame with rownames (repaired, recursive case) dfs <- map(dfs, set_rownames_recursively) with_memory_prof(list_unchop(dfs)) Output - [1] 920KB + [1] 23.9KB diff --git a/tests/testthat/test-bind.R b/tests/testthat/test-bind.R index 507027f54..615ab4443 100644 --- a/tests/testthat/test-bind.R +++ b/tests/testthat/test-bind.R @@ -832,8 +832,6 @@ test_that("vec_rbind() falls back to c() if S3 method is available", { ) expect_identical(out, foobaz(data_frame(x = quux(c(1, 2))))) - skip("FIXME: c() fallback with recursion through df-col") - wrapper_x_df <- data_frame(x = x_df) wrapper_y_df <- data_frame(x = y_df) @@ -841,7 +839,7 @@ test_that("vec_rbind() falls back to c() if S3 method is available", { c.vctrs_foobar = function(...) quux(NextMethod()), vec_rbind(wrapper_x_df, wrapper_y_df) ) - expect_identical(out, data_frame(data_frame(x = quux(c(1, 2))))) + expect_identical(out, data_frame(x = data_frame(x = quux(c(1, 2))))) }) test_that("c() fallback works with unspecified columns", { @@ -1068,6 +1066,31 @@ test_that("can repair names of row-binded matrices", { }) }) +test_that("vec_rbind() only restores one time", { + restored <- list() + + local_methods( + vec_ptype2.vctrs_foobar.vctrs_foobar = function(x, y, ...) x, + vec_cast.vctrs_foobar.vctrs_foobar = function(x, to, ...) x, + vec_proxy.vctrs_foobar = function(x, ...) x, + vec_restore.vctrs_foobar = function(x, to, ...) { + # Ignore proxying and restoration of ptypes + if (length(x)) { + restored <<- c(restored, list(x)) + } + foobar(x) + } + ) + + df <- data_frame(x = foobar(1:3)) + vec_rbind(df, df) + + expect_equal(restored, list( + rep(na_int, 6), # From `vec_init()` + foobar(c(1:3, 1:3)) # Final restoration + )) +}) + # Golden tests ------------------------------------------------------- @@ -1103,10 +1126,7 @@ test_that("row-binding performs expected allocations", { dfs <- map(dfs, set_rownames_recursively) with_memory_prof(vec_rbind_list(dfs)) - # FIXME: The following recursive cases duplicate rownames - # excessively because df-cols are restored at each chunk - # assignment, causing a premature name-repair - "FIXME (#1217): Data frame with rownames (non-repaired, recursive case)" + "Data frame with rownames (non-repaired, recursive case) (#1217)" df <- data_frame( x = 1:2, y = data_frame(x = 1:2) @@ -1115,7 +1135,7 @@ test_that("row-binding performs expected allocations", { dfs <- map2(dfs, seq_along(dfs), set_rownames_recursively) with_memory_prof(vec_rbind_list(dfs)) - "FIXME (#1217): Data frame with rownames (repaired, recursive case)" + "Data frame with rownames (repaired, recursive case) (#1217)" dfs <- map(dfs, set_rownames_recursively) with_memory_prof(vec_rbind_list(dfs)) }) From 27cf699b34f82fe11540772fe752db28c8b0ffe9 Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Fri, 9 Sep 2022 09:28:03 +0200 Subject: [PATCH 091/312] Proxy recursively in `vec_c()` and `vec_unchop()` Closes #1107 Closes #1496 Progress towards #1098 --- NEWS.md | 5 +++++ src/c-unchop.c | 5 +++-- src/c.c | 5 +++-- tests/testthat/_snaps/c.md | 4 ++-- tests/testthat/test-c.R | 7 ++----- 5 files changed, 15 insertions(+), 11 deletions(-) diff --git a/NEWS.md b/NEWS.md index 01774f490..efd7c386e 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,5 +1,10 @@ # vctrs (development version) +* `vec_c()`, `vec_unchop()`, and `vec_rbind()` now proxy and restore + recursively (#1107). This prevents `vec_restore()` from being called + with partially filled vectors and improves performance (#1217, + #1496). + * New `vec_any_missing()` for quickly determining if a vector has any missing values (#1672). diff --git a/src/c-unchop.c b/src/c-unchop.c index 0dad0025c..a586a9d71 100644 --- a/src/c-unchop.c +++ b/src/c-unchop.c @@ -86,7 +86,7 @@ r_obj* list_unchop(r_obj* xs, r_obj* locs = KEEP(vec_as_indices(indices, out_size, r_null)); - r_obj* proxy = vec_proxy(ptype); + r_obj* proxy = vec_proxy_recurse(ptype); r_keep_loc proxy_pi; KEEP_HERE(proxy, &proxy_pi); @@ -98,6 +98,7 @@ r_obj* list_unchop(r_obj* xs, KEEP_HERE(out_names, &out_names_pi); const struct vec_assign_opts unchop_assign_opts = { + .recursive = true, .assign_names = assign_names, .ignore_outer_names = true }; @@ -136,7 +137,7 @@ r_obj* list_unchop(r_obj* xs, KEEP_AT(proxy, proxy_pi); } - r_obj* out = KEEP(vec_restore(proxy, ptype, VCTRS_OWNED_true)); + r_obj* out = KEEP(vec_restore_recurse(proxy, ptype, VCTRS_OWNED_true)); if (out_names != r_null) { out_names = KEEP(vec_as_names(out_names, name_repair)); diff --git a/src/c.c b/src/c.c index 76e827914..84aa79893 100644 --- a/src/c.c +++ b/src/c.c @@ -77,7 +77,7 @@ r_obj* vec_c_opts(r_obj* xs, r_keep_loc out_pi; KEEP_HERE(out, &out_pi); - out = vec_proxy(out); + out = vec_proxy_recurse(out); KEEP_AT(out, out_pi); r_obj* loc = KEEP(compact_seq(0, 0, true)); @@ -95,6 +95,7 @@ r_obj* vec_c_opts(r_obj* xs, r_ssize counter = 0; const struct vec_assign_opts c_assign_opts = { + .recursive = true, .assign_names = assign_names, .ignore_outer_names = true }; @@ -143,7 +144,7 @@ r_obj* vec_c_opts(r_obj* xs, FREE(1); } - out = KEEP(vec_restore(out, ptype, VCTRS_OWNED_true)); + out = KEEP(vec_restore_recurse(out, ptype, VCTRS_OWNED_true)); if (out_names != r_null) { out_names = KEEP(vec_as_names(out_names, name_repair)); diff --git a/tests/testthat/_snaps/c.md b/tests/testthat/_snaps/c.md index 99642150f..194896e14 100644 --- a/tests/testthat/_snaps/c.md +++ b/tests/testthat/_snaps/c.md @@ -162,7 +162,7 @@ Output [1] 12.4KB Code - # FIXME (#1217): Data frame with rownames (non-repaired, recursive case) + # Data frame with rownames (non-repaired, recursive case) (#1217) df <- data_frame(x = 1:2, y = data_frame(x = 1:2)) dfs <- rep(list(df), 100) dfs <- map2(dfs, seq_along(dfs), set_rownames_recursively) @@ -170,7 +170,7 @@ Output [1] 11.6KB Code - # FIXME (#1217): Data frame with rownames (repaired, recursive case) + # Data frame with rownames (repaired, recursive case) (#1217) dfs <- map(dfs, set_rownames_recursively) with_memory_prof(list_unchop(dfs)) Output diff --git a/tests/testthat/test-c.R b/tests/testthat/test-c.R index 51899ec3a..a076b6c7f 100644 --- a/tests/testthat/test-c.R +++ b/tests/testthat/test-c.R @@ -496,10 +496,7 @@ test_that("concatenation performs expected allocations", { dfs <- map(dfs, set_rownames_recursively) with_memory_prof(list_unchop(dfs)) - # FIXME: The following recursive cases duplicate rownames - # excessively because df-cols are restored at each chunk - # assignment, causing a premature name-repair - "FIXME (#1217): Data frame with rownames (non-repaired, recursive case)" + "Data frame with rownames (non-repaired, recursive case) (#1217)" df <- data_frame( x = 1:2, y = data_frame(x = 1:2) @@ -508,7 +505,7 @@ test_that("concatenation performs expected allocations", { dfs <- map2(dfs, seq_along(dfs), set_rownames_recursively) with_memory_prof(list_unchop(dfs)) - "FIXME (#1217): Data frame with rownames (repaired, recursive case)" + "Data frame with rownames (repaired, recursive case) (#1217)" dfs <- map(dfs, set_rownames_recursively) with_memory_prof(list_unchop(dfs)) }) From f90b3cee4200a7bf616317da2e45a16079daa1dc Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Thu, 8 Sep 2022 14:49:36 +0200 Subject: [PATCH 092/312] Apply `base::c()` fallback recursively Closes #1331 Closes #1462 Closes #1640 --- NEWS.md | 3 ++ R/utils.R | 5 +++ src/bind.c | 57 +++++++++++++++++++++++++++++------ src/decl/bind-decl.h | 8 +++++ src/slice-assign.c | 6 ++++ src/utils.c | 18 ++++++----- src/utils.h | 2 +- tests/testthat/_snaps/bind.md | 14 ++++----- tests/testthat/test-bind.R | 20 ++++++++---- tests/testthat/test-type-sf.R | 15 +++++++++ 10 files changed, 116 insertions(+), 32 deletions(-) diff --git a/NEWS.md b/NEWS.md index efd7c386e..f65628aab 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,5 +1,8 @@ # vctrs (development version) +* `vec_rbind()` now applies `base::c()` fallback recursively within + packed df-cols (#1331, #1462, #1640). + * `vec_c()`, `vec_unchop()`, and `vec_rbind()` now proxy and restore recursively (#1107). This prevents `vec_restore()` from being called with partially filled vectors and improves performance (#1217, diff --git a/R/utils.R b/R/utils.R index 0e31b5709..42d21939d 100644 --- a/R/utils.R +++ b/R/utils.R @@ -328,3 +328,8 @@ browser <- function(..., # contexts. on.exit(base::browser(..., skipCalls = skipCalls + 1)) } + +vec_paste0 <- function(...) { + args <- vec_recycle_common(...) + exec(paste0, !!!args) +} diff --git a/src/bind.c b/src/bind.c index 14deeed1e..c83d20b63 100644 --- a/src/bind.c +++ b/src/bind.c @@ -251,16 +251,7 @@ r_obj* vec_rbind(r_obj* xs, // assigned already, ideally they should be ignored. Also this is // currently not recursive. Should we deal with this during // restoration? - for (r_ssize i = 0; i < n_cols; ++i) { - r_obj* col = r_list_get(ptype, i); - - if (vec_is_common_class_fallback(col)) { - r_obj* col_xs = KEEP(list_pluck(xs, i)); - r_obj* col_out = vec_c_fallback(col, col_xs, name_spec, name_repair); - r_list_poke(out, i, col_out); - FREE(1); - } - } + df_c_fallback(out, ptype, xs, n_rows, name_spec, name_repair); out = vec_restore_recurse(out, ptype, VCTRS_OWNED_true); @@ -268,6 +259,52 @@ r_obj* vec_rbind(r_obj* xs, return out; } +// `ptype` contains fallback information +static +void df_c_fallback(r_obj* out, + r_obj* ptype, + r_obj* xs, + r_ssize n_rows, + r_obj* name_spec, + struct name_repair_opts* name_repair) { + r_ssize n_cols = r_length(out); + + if (r_length(ptype) != n_cols || + r_typeof(out) != R_TYPE_list || + r_typeof(ptype) != R_TYPE_list) { + r_stop_internal("`ptype` and `out` must be lists of the same length."); + } + + for (r_ssize i = 0; i < n_cols; ++i) { + r_obj* ptype_col = r_list_get(ptype, i); + r_obj* xs_col = KEEP(list_pluck(xs, i)); + + // Recurse into df-cols + if (is_data_frame(ptype_col)) { + r_obj* out_col = r_list_get(out, i); + df_c_fallback(out_col, ptype_col, xs_col, n_rows, name_spec, name_repair); + } + + if (vec_is_common_class_fallback(ptype_col)) { + r_obj* out_col = vec_c_fallback(ptype_col, xs_col, name_spec, name_repair); + r_list_poke(out, i, out_col); + + if (vec_size(out_col) != n_rows) { + r_stop_internal("`c()` method returned a vector of unexpected size %d instead of %d.", + vec_size(out_col), + n_rows); + } + + // Remove fallback vector from the ptype so it doesn't get in + // the way of restoration later on + r_list_poke(ptype, i, vec_slice(out_col, r_null)); + } + + FREE(1); + } +} + + static r_obj* as_df_row(r_obj* x, struct name_repair_opts* name_repair, diff --git a/src/decl/bind-decl.h b/src/decl/bind-decl.h index 30a36b678..6024136c0 100644 --- a/src/decl/bind-decl.h +++ b/src/decl/bind-decl.h @@ -49,3 +49,11 @@ r_obj* shaped_as_df_col(r_obj* x, r_obj* outer); static r_obj* vec_as_df_col(r_obj* x, r_obj* outer); + +static +void df_c_fallback(r_obj* out, + r_obj* ptype, + r_obj* xs, + r_ssize n_rows, + r_obj* name_spec, + struct name_repair_opts* name_repair); diff --git a/src/slice-assign.c b/src/slice-assign.c index f51c225c1..7ca34be21 100644 --- a/src/slice-assign.c +++ b/src/slice-assign.c @@ -143,6 +143,12 @@ r_obj* vec_proxy_assign_opts(r_obj* proxy, const struct vec_assign_opts* opts) { int n_protect = 0; + // Ignore vectors marked as fallback because the caller will apply + // a fallback method instead + if (vec_is_common_class_fallback(proxy)) { + return proxy; + } + struct vec_assign_opts mut_opts = *opts; bool ignore_outer_names = mut_opts.ignore_outer_names; mut_opts.ignore_outer_names = false; diff --git a/src/utils.c b/src/utils.c index f09a7fb3b..ac8207801 100644 --- a/src/utils.c +++ b/src/utils.c @@ -793,16 +793,18 @@ bool list_has_inner_vec_names(SEXP x, R_len_t size) { * @return A list of the same length as `xs`. */ // [[ include("utils.h") ]] -SEXP list_pluck(SEXP xs, R_len_t i) { - R_len_t n = Rf_length(xs); - SEXP out = PROTECT(r_new_list(n)); - - for (R_len_t j = 0; j < n; ++j) { - SEXP x = r_list_get(xs, j); - r_list_poke(out, j, r_list_get(x, i)); +r_obj* list_pluck(r_obj* xs, r_ssize i) { + r_ssize n = r_length(xs); + r_obj* out = KEEP(r_new_list(n)); + + for (r_ssize j = 0; j < n; ++j) { + r_obj* x = r_list_get(xs, j); + if (x != r_null) { + r_list_poke(out, j, r_list_get(x, i)); + } } - UNPROTECT(1); + FREE(1); return out; } diff --git a/src/utils.h b/src/utils.h index 8734e3cc2..46363d49e 100644 --- a/src/utils.h +++ b/src/utils.h @@ -174,7 +174,7 @@ SEXP new_empty_factor(SEXP levels); SEXP new_empty_ordered(SEXP levels); bool list_has_inner_vec_names(SEXP x, R_len_t size); -SEXP list_pluck(SEXP xs, R_len_t i); +r_obj* list_pluck(r_obj* xs, r_ssize i); void init_compact_seq(int* p, R_len_t start, R_len_t size, bool increasing); SEXP compact_seq(R_len_t start, R_len_t size, bool increasing); diff --git a/tests/testthat/_snaps/bind.md b/tests/testthat/_snaps/bind.md index 1c0d42f2c..d8f3fc732 100644 --- a/tests/testthat/_snaps/bind.md +++ b/tests/testthat/_snaps/bind.md @@ -413,11 +413,11 @@ # Integers as rows suppressMessages(with_memory_prof(vec_rbind_list(ints))) Output - [1] 2.79KB + [1] 3.62KB Code suppressMessages(with_memory_prof(vec_rbind_list(named_ints))) Output - [1] 3.66KB + [1] 6.15KB Code # Data frame with named columns df <- data_frame(x = set_names(as.list(1:2), c("a", "b")), y = set_names(1:2, c( @@ -425,7 +425,7 @@ dfs <- rep(list(df), 100) with_memory_prof(vec_rbind_list(dfs)) Output - [1] 10.4KB + [1] 13.8KB Code # Data frame with rownames (non-repaired, non-recursive case) df <- data_frame(x = 1:2) @@ -433,13 +433,13 @@ dfs <- map2(dfs, seq_along(dfs), set_rownames_recursively) with_memory_prof(vec_rbind_list(dfs)) Output - [1] 7.68KB + [1] 8.51KB Code # Data frame with rownames (repaired, non-recursive case) dfs <- map(dfs, set_rownames_recursively) with_memory_prof(vec_rbind_list(dfs)) Output - [1] 13.8KB + [1] 14.7KB Code # Data frame with rownames (non-repaired, recursive case) (#1217) df <- data_frame(x = 1:2, y = data_frame(x = 1:2)) @@ -447,11 +447,11 @@ dfs <- map2(dfs, seq_along(dfs), set_rownames_recursively) with_memory_prof(vec_rbind_list(dfs)) Output - [1] 13KB + [1] 15.5KB Code # Data frame with rownames (repaired, recursive case) (#1217) dfs <- map(dfs, set_rownames_recursively) with_memory_prof(vec_rbind_list(dfs)) Output - [1] 25.3KB + [1] 27.8KB diff --git a/tests/testthat/test-bind.R b/tests/testthat/test-bind.R index 615ab4443..53c0f002e 100644 --- a/tests/testthat/test-bind.R +++ b/tests/testthat/test-bind.R @@ -860,8 +860,8 @@ test_that("c() fallback works with unspecified columns", { test_that("c() fallback works with vctrs-powered data frame subclass", { local_methods( - c.vctrs_quux = function(...) quux(NextMethod(), c_dispatched = TRUE), - `[.vctrs_quux` = function(x, i, ...) quux(NextMethod(), bracket_dispatched = TRUE) + c.vctrs_quux = function(...) quux(vec_paste0(NextMethod(), "-c")), + `[.vctrs_quux` = function(x, i, ...) quux(vec_paste0(NextMethod(), "-[")) ) local_foobar_df_methods() @@ -870,11 +870,11 @@ test_that("c() fallback works with vctrs-powered data frame subclass", { df2 <- data_frame(x = quux(4:5)) out <- vctrs::vec_rbind(df1, df2) - exp <- foobar(data_frame(x = quux(1:5, c_dispatched = TRUE))) + exp <- foobar(data_frame(x = quux(paste0(1:5, "-c")))) expect_identical(out, exp) out <- vctrs::vec_rbind(df2, df1) - exp <- foobar(data_frame(x = quux(c(4:5, 1:3), c_dispatched = TRUE))) + exp <- foobar(data_frame(x = quux(paste0(c(4:5, 1:3), "-c")))) expect_identical(out, exp) ### Disjoint case @@ -883,7 +883,7 @@ test_that("c() fallback works with vctrs-powered data frame subclass", { out <- vctrs::vec_rbind(df1, df2) exp <- foobar(data_frame( - x = quux(c(1:3, NA, NA), bracket_dispatched = TRUE), + x = quux(c(paste0(1:3, "-c-["), paste0(c(NA, NA), "-["))), y = c(rep(NA, 3), 4:5) )) expect_identical(out, exp) @@ -891,7 +891,7 @@ test_that("c() fallback works with vctrs-powered data frame subclass", { out <- vctrs::vec_rbind(df2, df1) exp <- foobar(data_frame( y = c(4:5, rep(NA, 3)), - x = quux(c(NA, NA, 1:3), bracket_dispatched = TRUE) + x = quux(c(paste0(c(NA, NA), "-["), paste0(1:3, "-c-["))) )) expect_identical(out, exp) }) @@ -1091,6 +1091,14 @@ test_that("vec_rbind() only restores one time", { )) }) +test_that("vec_rbind() applies `base::c()` fallback to df-cols (#1462, #1640)", { + x <- structure(1, class = "myclass") + df <- tibble(a = tibble(x = x)) + df <- vec_rbind(df, df) + + expect_equal(df$a$x, structure(c(1, 1), class = "myclass")) +}) + # Golden tests ------------------------------------------------------- diff --git a/tests/testthat/test-type-sf.R b/tests/testthat/test-type-sf.R index 0e2286605..a558fe1e7 100644 --- a/tests/testthat/test-type-sf.R +++ b/tests/testthat/test-type-sf.R @@ -256,6 +256,21 @@ test_that("`vec_locate_matches()` works with `sfc` vectors", { expect_identical(out$haystack, c(2L, 4L, 5L, NA, 1L)) }) +test_that("`vec_rbind()` doesn't leak common type fallbacks (#1331)", { + sf = st_sf(id = 1:2, geo = st_sfc(st_point(c(1, 1)), st_point(c(2, 2)))) + + expect_equal( + vec_rbind(sf, sf), + data_frame(id = rep(1:2, 2), geo = rep(sf$geo, 2)) + ) + + expect_equal( + vec_rbind(sf, sf, .names_to = "id"), + data_frame(id = rep(1:2, each = 2), geo = rep(sf$geo, 2)) + ) +}) + + # Local Variables: # indent-tabs-mode: t # ess-indent-offset: 4 From fe4bfa72543fb3709a5c2e1e786dddeec8f3c931 Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Fri, 9 Sep 2022 12:37:08 +0200 Subject: [PATCH 093/312] Add memory snapshot tests for #1496 --- tests/testthat/_snaps/c.md | 17 +++++++++++++++++ tests/testthat/test-c.R | 11 +++++++++++ 2 files changed, 28 insertions(+) diff --git a/tests/testthat/_snaps/c.md b/tests/testthat/_snaps/c.md index 194896e14..90d0691bd 100644 --- a/tests/testthat/_snaps/c.md +++ b/tests/testthat/_snaps/c.md @@ -175,4 +175,21 @@ with_memory_prof(list_unchop(dfs)) Output [1] 23.9KB + Code + # list-ofs (#1496) + make_list_of <- (function(n) { + df <- tibble::tibble(x = new_list_of(vec_chop(1:n), ptype = integer())) + vec_chop(df) + }) + with_memory_prof(list_unchop(make_list_of(1000))) + Output + [1] 112KB + Code + with_memory_prof(list_unchop(make_list_of(2000))) + Output + [1] 222KB + Code + with_memory_prof(list_unchop(make_list_of(4000))) + Output + [1] 440KB diff --git a/tests/testthat/test-c.R b/tests/testthat/test-c.R index a076b6c7f..7c55a8741 100644 --- a/tests/testthat/test-c.R +++ b/tests/testthat/test-c.R @@ -508,6 +508,17 @@ test_that("concatenation performs expected allocations", { "Data frame with rownames (repaired, recursive case) (#1217)" dfs <- map(dfs, set_rownames_recursively) with_memory_prof(list_unchop(dfs)) + + "list-ofs (#1496)" + make_list_of <- function(n) { + df <- tibble::tibble( + x = new_list_of(vec_chop(1:n), ptype = integer()) + ) + vec_chop(df) + } + with_memory_prof(list_unchop(make_list_of(1e3))) + with_memory_prof(list_unchop(make_list_of(2e3))) + with_memory_prof(list_unchop(make_list_of(4e3))) }) }) From c2e9e56ce2b68f7b73b381bd62c116597b4cf64f Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Fri, 9 Sep 2022 15:38:18 +0200 Subject: [PATCH 094/312] Don't recurse into record vectors automatically --- src/proxy.c | 11 ++--------- tests/testthat/_snaps/c.md | 6 +++--- 2 files changed, 5 insertions(+), 12 deletions(-) diff --git a/src/proxy.c b/src/proxy.c index 0aba9aac4..e31c93be3 100644 --- a/src/proxy.c +++ b/src/proxy.c @@ -26,15 +26,8 @@ r_obj* vec_proxy_2(r_obj* x, bool recurse) { } case VCTRS_TYPE_s3: { - r_obj* out = KEEP(vec_proxy_invoke(x, info.proxy_method)); - if (!is_data_frame(out)) { - FREE(2); - return out; - } - - out = KEEP(recurse ? df_proxy_recurse(out) : out); - - FREE(3); + r_obj* out = vec_proxy_invoke(x, info.proxy_method); + FREE(1); return out; } diff --git a/tests/testthat/_snaps/c.md b/tests/testthat/_snaps/c.md index 90d0691bd..103a6da8e 100644 --- a/tests/testthat/_snaps/c.md +++ b/tests/testthat/_snaps/c.md @@ -183,13 +183,13 @@ }) with_memory_prof(list_unchop(make_list_of(1000))) Output - [1] 112KB + [1] 104KB Code with_memory_prof(list_unchop(make_list_of(2000))) Output - [1] 222KB + [1] 206KB Code with_memory_prof(list_unchop(make_list_of(4000))) Output - [1] 440KB + [1] 409KB From bdf6e737375c4cbeca5084edcfb407bd0c85faa0 Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Fri, 9 Sep 2022 15:58:21 +0200 Subject: [PATCH 095/312] Mention sizes in internal errors --- src/slice-assign.c | 8 ++++++-- 1 file changed, 6 insertions(+), 2 deletions(-) diff --git a/src/slice-assign.c b/src/slice-assign.c index 7ca34be21..e69175237 100644 --- a/src/slice-assign.c +++ b/src/slice-assign.c @@ -262,7 +262,9 @@ r_obj* raw_assign(r_obj* x, r_obj* index, r_obj* value, const enum vctrs_owned o int* index_data = r_int_begin(index); \ \ if (n != r_length(value)) { \ - r_stop_internal("`value` should have been recycled to fit `x`."); \ + r_stop_internal("`value` (size %d) doesn't match `x` (size %d).", \ + r_length(value), \ + n); \ } \ \ r_obj* out = KEEP(vec_clone_referenced(x, owned)); \ @@ -284,7 +286,9 @@ r_obj* raw_assign(r_obj* x, r_obj* index, r_obj* value, const enum vctrs_owned o r_ssize step = index_data[2]; \ \ if (n != r_length(value)) { \ - r_stop_internal("`value` should have been recycled to fit `x`."); \ + r_stop_internal("`value` (size %d) doesn't match `x` (size %d).", \ + r_length(value), \ + n); \ } \ \ r_obj* out = KEEP(vec_clone_referenced(x, owned)); \ From 258a2f142efa75832dab5565a00cf6926ec790a8 Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Tue, 13 Sep 2022 17:19:14 +0200 Subject: [PATCH 096/312] Pass `recurse = ` through dots of `vec_proxy()` and `vec_restore()` --- R/proxy.R | 19 +++++++------ src/decl/proxy-restore-decl.h | 2 +- src/decl/type-info-decl.h | 4 --- src/globals.c | 1 + src/globals.h | 1 + src/init.c | 12 +++------ src/proxy-restore.c | 19 ++++++++----- src/proxy.c | 19 ++++++++----- src/proxy.h | 2 +- src/type-info.c | 2 +- tests/testthat/helper-s3.R | 4 +-- tests/testthat/test-assert.R | 2 +- tests/testthat/test-proxy-restore.R | 42 ++++++++++++++++++++++++++++- tests/testthat/test-slice-chop.R | 2 +- tests/testthat/test-slice.R | 8 +++--- 15 files changed, 94 insertions(+), 45 deletions(-) diff --git a/R/proxy.R b/R/proxy.R index 317f74a8d..521248856 100644 --- a/R/proxy.R +++ b/R/proxy.R @@ -135,8 +135,8 @@ #' @keywords internal #' @export vec_proxy <- function(x, ...) { - check_dots_empty0(...) - return(.Call(ffi_vec_proxy, x)) + recurse <- match_recurse(...) + return(.Call(ffi_vec_proxy, x, recurse)) UseMethod("vec_proxy") } #' @export @@ -148,8 +148,8 @@ vec_proxy.default <- function(x, ...) { #' @param to The original vector to restore to. #' @export vec_restore <- function(x, to, ...) { - check_dots_empty0(...) - return(.Call(ffi_vec_restore, x, to)) + recurse <- match_recurse(...) + return(.Call(ffi_vec_restore, x, to, recurse)) UseMethod("vec_restore", to) } vec_restore_dispatch <- function(x, to, ...) { @@ -163,13 +163,16 @@ vec_restore_default <- function(x, to, ...) { .Call(ffi_vec_restore_default, x, to) } +match_recurse <- function(..., recurse = FALSE) { + check_dots_empty0(..., call = caller_env()) + recurse +} + vec_proxy_recurse <- function(x, ...) { - check_dots_empty0(...) - .Call(ffi_vec_proxy_recurse, x) + vec_proxy(x, ..., recurse = TRUE) } vec_restore_recurse <- function(x, to, ...) { - check_dots_empty0(...) - .Call(ffi_vec_restore_recurse, x, to) + vec_restore(x, to, ..., recurse = TRUE) } #' Extract underlying data diff --git a/src/decl/proxy-restore-decl.h b/src/decl/proxy-restore-decl.h index 81ea3638f..48352fd71 100644 --- a/src/decl/proxy-restore-decl.h +++ b/src/decl/proxy-restore-decl.h @@ -8,4 +8,4 @@ r_obj* vec_restore_4(r_obj* x, bool recurse); static -r_obj* vec_restore_dispatch(r_obj* x, r_obj* to); +r_obj* vec_restore_dispatch(r_obj* x, r_obj* to, bool recurse); diff --git a/src/decl/type-info-decl.h b/src/decl/type-info-decl.h index d910464fc..d0cc118b9 100644 --- a/src/decl/type-info-decl.h +++ b/src/decl/type-info-decl.h @@ -6,7 +6,3 @@ r_obj* fns_vec_is_vector_dispatch; static enum vctrs_type vec_base_typeof(r_obj* x, bool proxied); - -// From proxy.c -r_obj* vec_proxy_method(r_obj* x); -r_obj* vec_proxy_invoke(r_obj* x, r_obj* method); diff --git a/src/globals.c b/src/globals.c index 16426fefa..f84b35ea3 100644 --- a/src/globals.c +++ b/src/globals.c @@ -54,6 +54,7 @@ void vctrs_init_globals(r_obj* ns) { syms.dot_error_call = r_sym(".error_call"); syms.haystack_arg = r_sym("haystack_arg"); syms.needles_arg = r_sym("needles_arg"); + syms.recurse = r_sym("recurse"); syms.repair_arg = r_sym("repair_arg"); syms.times_arg = r_sym("times_arg"); syms.to_arg = r_sym("to_arg"); diff --git a/src/globals.h b/src/globals.h index f32d01cf8..22f93f020 100644 --- a/src/globals.h +++ b/src/globals.h @@ -11,6 +11,7 @@ struct syms { r_obj* dot_error_call; r_obj* haystack_arg; r_obj* needles_arg; + r_obj* recurse; r_obj* repair_arg; r_obj* times_arg; r_obj* to_arg; diff --git a/src/init.c b/src/init.c index 046fb4310..b0e68ee1a 100644 --- a/src/init.c +++ b/src/init.c @@ -53,11 +53,9 @@ extern r_obj* ffi_list_unchop(r_obj*, r_obj*, r_obj*, r_obj*, r_obj*); extern SEXP vctrs_chop_seq(SEXP, SEXP, SEXP, SEXP); extern r_obj* ffi_slice_seq(r_obj*, r_obj*, r_obj*, r_obj*); extern r_obj* ffi_slice_rep(r_obj*, r_obj*, r_obj*); -extern r_obj* ffi_vec_restore(r_obj*, r_obj*); +extern r_obj* ffi_vec_restore(r_obj*, r_obj*, r_obj*); extern r_obj* ffi_vec_restore_default(r_obj*, r_obj*); -extern r_obj* ffi_vec_restore_recurse(r_obj*, r_obj*); -extern r_obj* vec_proxy(r_obj*); -extern r_obj* vec_proxy_recurse(r_obj*); +extern r_obj* ffi_vec_proxy(r_obj*, r_obj*); extern SEXP vec_proxy_equal(SEXP); extern SEXP vec_proxy_compare(SEXP); extern SEXP vec_proxy_order(SEXP); @@ -224,11 +222,9 @@ static const R_CallMethodDef CallEntries[] = { {"vctrs_chop_seq", (DL_FUNC) &vctrs_chop_seq, 4}, {"ffi_slice_seq", (DL_FUNC) &ffi_slice_seq, 4}, {"ffi_slice_rep", (DL_FUNC) &ffi_slice_rep, 3}, - {"ffi_vec_restore", (DL_FUNC) &ffi_vec_restore, 2}, + {"ffi_vec_restore", (DL_FUNC) &ffi_vec_restore, 3}, {"ffi_vec_restore_default", (DL_FUNC) &ffi_vec_restore_default, 2}, - {"ffi_vec_restore_recurse", (DL_FUNC) &ffi_vec_restore_recurse, 2}, - {"ffi_vec_proxy", (DL_FUNC) &vec_proxy, 1}, - {"ffi_vec_proxy_recurse", (DL_FUNC) &vec_proxy_recurse, 1}, + {"ffi_vec_proxy", (DL_FUNC) &ffi_vec_proxy, 2}, {"vctrs_proxy_equal", (DL_FUNC) &vec_proxy_equal, 1}, {"vctrs_proxy_compare", (DL_FUNC) &vec_proxy_compare, 1}, {"vctrs_proxy_order", (DL_FUNC) &vec_proxy_order, 1}, diff --git a/src/proxy-restore.c b/src/proxy-restore.c index eae34e9bf..1c59ccd4b 100644 --- a/src/proxy-restore.c +++ b/src/proxy-restore.c @@ -32,12 +32,16 @@ r_obj* vec_restore_4(r_obj* x, case VCTRS_CLASS_bare_data_frame: case VCTRS_CLASS_bare_tibble: return vec_bare_df_restore(x, to, owned, recurse); case VCTRS_CLASS_data_frame: return vec_df_restore(x, to, owned, recurse); - default: return vec_restore_dispatch(x, to); + default: return vec_restore_dispatch(x, to, recurse); } } -r_obj* ffi_vec_restore(r_obj* x, r_obj* to) { - return vec_restore(x, to, vec_owned(x)); +r_obj* ffi_vec_restore(r_obj* x, r_obj* to, r_obj* recurse) { + if (r_lgl_get(recurse, 0)) { + return vec_restore_recurse(x, to, vec_owned(x)); + } else { + return vec_restore(x, to, vec_owned(x)); + } } r_obj* ffi_vec_restore_recurse(r_obj* x, r_obj* to) { return vec_restore_recurse(x, to, vec_owned(x)); @@ -45,10 +49,11 @@ r_obj* ffi_vec_restore_recurse(r_obj* x, r_obj* to) { static -r_obj* vec_restore_dispatch(r_obj* x, r_obj* to) { - return vctrs_dispatch2(syms_vec_restore_dispatch, fns_vec_restore_dispatch, +r_obj* vec_restore_dispatch(r_obj* x, r_obj* to, bool recurse) { + return vctrs_dispatch3(syms_vec_restore_dispatch, fns_vec_restore_dispatch, syms_x, x, - syms_to, to); + syms_to, to, + syms.recurse, r_lgl(recurse)); } @@ -165,7 +170,7 @@ r_obj* vec_df_restore(r_obj* x, const enum vctrs_owned owned, bool recurse) { r_obj* out = KEEP(vec_bare_df_restore(x, to, owned, recurse)); - out = vec_restore_dispatch(out, to); + out = vec_restore_dispatch(out, to, recurse); FREE(1); return out; } diff --git a/src/proxy.c b/src/proxy.c index e31c93be3..7089f1c49 100644 --- a/src/proxy.c +++ b/src/proxy.c @@ -3,16 +3,21 @@ #include "decl/proxy-decl.h" -// [[ register() ]] r_obj* vec_proxy(r_obj* x) { return vec_proxy_2(x, false); } - -// [[ register() ]] r_obj* vec_proxy_recurse(r_obj* x) { return vec_proxy_2(x, true); } +r_obj* ffi_vec_proxy(r_obj* x, r_obj* recurse) { + if (r_as_bool(recurse)) { + return vec_proxy_2(x, true); + } else { + return vec_proxy_2(x, false); + } +} + static r_obj* vec_proxy_2(r_obj* x, bool recurse) { struct vctrs_type_info info = vec_type_info(x); @@ -26,7 +31,7 @@ r_obj* vec_proxy_2(r_obj* x, bool recurse) { } case VCTRS_TYPE_s3: { - r_obj* out = vec_proxy_invoke(x, info.proxy_method); + r_obj* out = vec_proxy_invoke(x, info.proxy_method, recurse); FREE(1); return out; } @@ -127,11 +132,13 @@ r_obj* vec_proxy_method(r_obj* x) { // This should be faster than normal dispatch but also means that // proxy methods can't call `NextMethod()`. This could be changed if // it turns out a problem. -r_obj* vec_proxy_invoke(r_obj* x, r_obj* method) { +r_obj* vec_proxy_invoke(r_obj* x, r_obj* method, bool recurse) { if (method == r_null) { return x; } else { - return vctrs_dispatch1(syms_vec_proxy, method, syms_x, x); + return vctrs_dispatch2(syms_vec_proxy, method, + syms_x, x, + syms.recurse, r_lgl(recurse)); } } diff --git a/src/proxy.h b/src/proxy.h index c33bafd9a..1ee6b8968 100644 --- a/src/proxy.h +++ b/src/proxy.h @@ -10,7 +10,7 @@ r_obj* vec_proxy_order(r_obj* x); r_obj* vec_proxy_recurse(r_obj* x); r_obj* vec_proxy_method(r_obj* x); -r_obj* vec_proxy_invoke(r_obj* x, r_obj* method); +r_obj* vec_proxy_invoke(r_obj* x, r_obj* method, bool recurse); r_obj* vec_proxy_unwrap(r_obj* x); #endif diff --git a/src/type-info.c b/src/type-info.c index 3950b193c..b8edf830a 100644 --- a/src/type-info.c +++ b/src/type-info.c @@ -27,7 +27,7 @@ struct vctrs_proxy_info vec_proxy_info(r_obj* x) { info.type = vec_base_typeof(x, false); info.proxy = x; } else { - r_obj* proxy = KEEP(vec_proxy_invoke(x, info.proxy_method)); + r_obj* proxy = KEEP(vec_proxy_invoke(x, info.proxy_method, false)); info.type = vec_base_typeof(proxy, true); info.proxy = proxy; FREE(1); diff --git a/tests/testthat/helper-s3.R b/tests/testthat/helper-s3.R index 558350ca4..ed23f4c61 100644 --- a/tests/testthat/helper-s3.R +++ b/tests/testthat/helper-s3.R @@ -55,7 +55,7 @@ local_proxy <- function(frame = caller_env()) { new_proxy <- function(x) { structure(list(env(x = x)), class = "vctrs_proxy") } -proxy_deref <- function(x) { +proxy_deref <- function(x, ...) { x[[1]]$x } local_env_proxy <- function(frame = caller_env()) { @@ -78,7 +78,7 @@ tibble <- function(...) { } local_foobar_proxy <- function(frame = caller_env()) { - local_methods(.frame = frame, vec_proxy.vctrs_foobar = identity) + local_methods(.frame = frame, vec_proxy.vctrs_foobar = function(x, ...) x) } subclass <- function(x) { diff --git a/tests/testthat/test-assert.R b/tests/testthat/test-assert.R index cd978c500..6118f9070 100644 --- a/tests/testthat/test-assert.R +++ b/tests/testthat/test-assert.R @@ -160,7 +160,7 @@ test_that("data frames are always classified as such even when dispatch is off", test_that("assertion is not applied on proxy", { local_methods( - vec_proxy.vctrs_foobar = unclass, + vec_proxy.vctrs_foobar = function(x, ...) unclass(x), vec_restore.vctrs_foobar = function(x, ...) foobar(x), `[.vctrs_foobar` = function(x, i) vec_slice(x, i) ) diff --git a/tests/testthat/test-proxy-restore.R b/tests/testthat/test-proxy-restore.R index aa71054f1..c99f3561b 100644 --- a/tests/testthat/test-proxy-restore.R +++ b/tests/testthat/test-proxy-restore.R @@ -75,7 +75,7 @@ test_that("arguments are not inlined in the dispatch call (#300)", { vec_proxy.vctrs_foobar = unclass ) call <- vec_restore(foobar(list(1)), foobar(list(1))) - expect_equal(call, quote(vec_restore.vctrs_foobar(x = x, to = to))) + expect_equal(call, quote(vec_restore.vctrs_foobar(x = x, to = to, recurse = recurse))) }) test_that("restoring to non-bare data frames calls `vec_bare_df_restore()` before dispatching", { @@ -129,3 +129,43 @@ test_that("names<- is not called with partial data (#1108)", { vec_c(x, x) expect_equal(values, list(c("a", "b", "a", "b"))) }) + +test_that("proxy and restore pass `recurse` through `...`", { + new_recursive_rcrd <- function(x) { + new_rcrd( + list(field = x), + class = "my_recursive_rcrd" + ) + } + + internal <- new_rcrd(list(internal_field = 1:2)) + x <- new_recursive_rcrd(data_frame(col = internal)) + + local_methods( + vec_proxy.my_recursive_rcrd = function(x, ...) { + vec_proxy(field(x, "field"), ...) + }, + vec_restore.my_recursive_rcrd = function(x, to, ...) { + out <- vec_restore(x, field(to, "field"), ...) + new_recursive_rcrd(out) + } + ) + + proxy <- vec_proxy(x, recurse = TRUE) + exp <- data_frame(col = data_frame(internal_field = 1:2)) + expect_equal(proxy, exp) + + out <- vec_restore(proxy, x, recurse = TRUE) + expect_equal(out, x) + + x_exp <- new_recursive_rcrd(data_frame(col = vec_rep(internal, 2))) + expect_equal( + list_unchop(list(x, x)), + x_exp + ) + + df <- data_frame(x = x) + df_exp <- data_frame(x = x_exp) + expect_equal(vec_rbind(df, df), df_exp) + expect_equal(vec_c(df, df), df_exp) +}) diff --git a/tests/testthat/test-slice-chop.R b/tests/testthat/test-slice-chop.R index e9b8365a0..a690f64ba 100644 --- a/tests/testthat/test-slice-chop.R +++ b/tests/testthat/test-slice-chop.R @@ -170,7 +170,7 @@ test_that("vec_chop() falls back to `[` for shaped objects with no proxy when in test_that("vec_chop() with data frame proxies always uses the proxy's length info", { local_methods( - vec_proxy.vctrs_proxy = function(x) { + vec_proxy.vctrs_proxy = function(x, ...) { x <- proxy_deref(x) new_data_frame(list(x = x$x, y = x$y)) }, diff --git a/tests/testthat/test-slice.R b/tests/testthat/test-slice.R index 3bbeaeec7..02939d748 100644 --- a/tests/testthat/test-slice.R +++ b/tests/testthat/test-slice.R @@ -205,7 +205,7 @@ test_that("can `vec_slice()` records", { test_that("vec_restore() is called after proxied slicing", { local_methods( - vec_proxy.vctrs_foobar = identity, + vec_proxy.vctrs_foobar = function(x, ...) x, vec_restore.vctrs_foobar = function(x, to, ...) "dispatch" ) expect_identical(vec_slice(foobar(1:3), 2), "dispatch") @@ -236,7 +236,7 @@ test_that("dimensions are preserved by vec_slice()", { attrib <- NULL local_methods( - vec_proxy.vctrs_foobar = identity, + vec_proxy.vctrs_foobar = function(x, ...) x, vec_restore.vctrs_foobar = function(x, to, ...) attrib <<- attributes(x) ) @@ -260,7 +260,7 @@ test_that("can slice shaped objects by name", { test_that("vec_slice() unclasses input before calling `vec_restore()`", { oo <- NULL local_methods( - vec_proxy.vctrs_foobar = identity, + vec_proxy.vctrs_foobar = function(x, ...) x, vec_restore.vctrs_foobar = function(x, ...) oo <<- is.object(x) ) @@ -302,7 +302,7 @@ test_that("vec_slice() falls back to `[` with S3 objects", { expect_error(vec_slice(foobar(list(NA)), 1), class = "vctrs_error_scalar_type") local_methods( - vec_proxy.vctrs_foobar = identity + vec_proxy.vctrs_foobar = function(x, ...) x ) expect_identical(vec_slice(foobar(list(NA)), 1), foobar(list(NA))) }) From 669d1b4e0749b368800d7b7e376fabea124d42e3 Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Tue, 20 Sep 2022 10:45:26 +0200 Subject: [PATCH 097/312] Update comment about recursive restoration --- src/bind.c | 4 +--- 1 file changed, 1 insertion(+), 3 deletions(-) diff --git a/src/bind.c b/src/bind.c index c83d20b63..b520e86fd 100644 --- a/src/bind.c +++ b/src/bind.c @@ -248,9 +248,7 @@ r_obj* vec_rbind(r_obj* xs, } // Not optimal. Happens after the fallback columns have been - // assigned already, ideally they should be ignored. Also this is - // currently not recursive. Should we deal with this during - // restoration? + // assigned already, ideally they should be ignored. df_c_fallback(out, ptype, xs, n_rows, name_spec, name_repair); out = vec_restore_recurse(out, ptype, VCTRS_OWNED_true); From 005577c60f31dd0fe3dbb9a6c58839528956bc55 Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Tue, 20 Sep 2022 10:50:31 +0200 Subject: [PATCH 098/312] Simplify `ffi_vec_restore()` --- src/proxy-restore.c | 6 +----- 1 file changed, 1 insertion(+), 5 deletions(-) diff --git a/src/proxy-restore.c b/src/proxy-restore.c index 1c59ccd4b..5455b7a14 100644 --- a/src/proxy-restore.c +++ b/src/proxy-restore.c @@ -37,11 +37,7 @@ r_obj* vec_restore_4(r_obj* x, } r_obj* ffi_vec_restore(r_obj* x, r_obj* to, r_obj* recurse) { - if (r_lgl_get(recurse, 0)) { - return vec_restore_recurse(x, to, vec_owned(x)); - } else { - return vec_restore(x, to, vec_owned(x)); - } + return vec_restore_4(x, to, vec_owned(x), r_as_bool(recurse)); } r_obj* ffi_vec_restore_recurse(r_obj* x, r_obj* to) { return vec_restore_recurse(x, to, vec_owned(x)); From 889bf27a4f1ae88c62abb40e538abbd2144b3068 Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Tue, 20 Sep 2022 10:52:14 +0200 Subject: [PATCH 099/312] Iterate over list arrays --- src/proxy-restore.c | 7 ++++--- src/proxy.c | 8 +++++--- src/utils.c | 4 +++- 3 files changed, 12 insertions(+), 7 deletions(-) diff --git a/src/proxy-restore.c b/src/proxy-restore.c index 5455b7a14..88b1000e6 100644 --- a/src/proxy-restore.c +++ b/src/proxy-restore.c @@ -186,10 +186,11 @@ r_obj* vec_bare_df_restore(r_obj* x, r_stop_internal("Shape of `x` doesn't match `to` in recursive df restoration."); }; + r_obj* const * v_x = r_list_cbegin(x); + r_obj* const * v_to = r_list_cbegin(to); + for (r_ssize i = 0; i < n_cols; ++i) { - r_obj* x_col = r_list_get(x, i); - r_obj* to_col = r_list_get(to, i); - r_obj* x_restored = vec_restore_recurse(x_col, to_col, owned); + r_obj* x_restored = vec_restore_recurse(v_x[i], v_to[i], owned); r_list_poke(x, i, x_restored); } } diff --git a/src/proxy.c b/src/proxy.c index 7089f1c49..ae34c6c24 100644 --- a/src/proxy.c +++ b/src/proxy.c @@ -47,9 +47,11 @@ static r_obj* df_proxy_recurse(r_obj* x) { r_obj* out = KEEP(r_clone(x)); - for (r_ssize i = 0, n = r_length(out); i < n; ++i) { - r_obj* col = r_list_get(out, i); - r_list_poke(out, i, vec_proxy_recurse(col)); + r_ssize n = r_length(out); + r_obj* const * v_out = r_list_cbegin(out); + + for (r_ssize i = 0; i < n; ++i) { + r_list_poke(out, i, vec_proxy_recurse(v_out[i])); } FREE(1); diff --git a/src/utils.c b/src/utils.c index ac8207801..66f329ff2 100644 --- a/src/utils.c +++ b/src/utils.c @@ -795,10 +795,12 @@ bool list_has_inner_vec_names(SEXP x, R_len_t size) { // [[ include("utils.h") ]] r_obj* list_pluck(r_obj* xs, r_ssize i) { r_ssize n = r_length(xs); + r_obj* const * v_xs = r_list_cbegin(xs); + r_obj* out = KEEP(r_new_list(n)); for (r_ssize j = 0; j < n; ++j) { - r_obj* x = r_list_get(xs, j); + r_obj* x = v_xs[j]; if (x != r_null) { r_list_poke(out, j, r_list_get(x, i)); } From 2de73934d598974e4bd993d4858f29c27f6d4ac7 Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Tue, 20 Sep 2022 10:57:26 +0200 Subject: [PATCH 100/312] Apply suggestions from code review Co-authored-by: Davis Vaughan --- src/proxy.c | 6 +----- src/slice-assign.c | 9 ++------- 2 files changed, 3 insertions(+), 12 deletions(-) diff --git a/src/proxy.c b/src/proxy.c index ae34c6c24..55ba7f98e 100644 --- a/src/proxy.c +++ b/src/proxy.c @@ -11,11 +11,7 @@ r_obj* vec_proxy_recurse(r_obj* x) { } r_obj* ffi_vec_proxy(r_obj* x, r_obj* recurse) { - if (r_as_bool(recurse)) { - return vec_proxy_2(x, true); - } else { - return vec_proxy_2(x, false); - } + return vec_proxy_2(x, r_as_bool(recurse)); } static diff --git a/src/slice-assign.c b/src/slice-assign.c index e69175237..e79bd88c2 100644 --- a/src/slice-assign.c +++ b/src/slice-assign.c @@ -357,16 +357,11 @@ r_obj* df_assign(r_obj* x, // No need to cast or recycle because those operations are // recursive and have already been performed. However, proxy and - // restore are not necessarily recursive and we wight need to + // restore are not necessarily recursive and we might need to // proxy each element we recurse into. // // NOTE: `vec_proxy_assign()` proxies `value_elt`. - r_obj* proxy_elt = r_null; - if (opts->recursive) { - proxy_elt = KEEP(out_elt); - } else { - proxy_elt = KEEP(vec_proxy(out_elt)); - } + r_obj* proxy_elt = KEEP(opts->recursive ? out_elt : vec_proxy(out_elt)); r_obj* assigned = KEEP(vec_proxy_assign_opts(proxy_elt, index, value_elt, owned, opts)); From 2ee2d43bcad8a05c863f5cf35bfdaa25f9544b15 Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Tue, 20 Sep 2022 11:12:16 +0200 Subject: [PATCH 101/312] Recurse automatically in proxy and restore --- R/proxy.R | 17 ++++------ src/decl/proxy-restore-decl.h | 2 +- src/init.c | 10 +++--- src/proxy-restore.c | 49 +++++++++++++++++------------ src/proxy.c | 18 +++++------ src/proxy.h | 2 +- src/type-info.c | 2 +- src/utils-dispatch.c | 11 +++++++ src/utils-dispatch.h | 2 ++ tests/testthat/_snaps/c.md | 6 ++-- tests/testthat/test-proxy-restore.R | 22 +++---------- 11 files changed, 73 insertions(+), 68 deletions(-) diff --git a/R/proxy.R b/R/proxy.R index 521248856..d572cf79d 100644 --- a/R/proxy.R +++ b/R/proxy.R @@ -135,8 +135,8 @@ #' @keywords internal #' @export vec_proxy <- function(x, ...) { - recurse <- match_recurse(...) - return(.Call(ffi_vec_proxy, x, recurse)) + check_dots_empty0(...) + return(.Call(ffi_vec_proxy, x)) UseMethod("vec_proxy") } #' @export @@ -148,8 +148,8 @@ vec_proxy.default <- function(x, ...) { #' @param to The original vector to restore to. #' @export vec_restore <- function(x, to, ...) { - recurse <- match_recurse(...) - return(.Call(ffi_vec_restore, x, to, recurse)) + check_dots_empty0(...) + return(.Call(ffi_vec_restore, x, to)) UseMethod("vec_restore", to) } vec_restore_dispatch <- function(x, to, ...) { @@ -163,16 +163,11 @@ vec_restore_default <- function(x, to, ...) { .Call(ffi_vec_restore_default, x, to) } -match_recurse <- function(..., recurse = FALSE) { - check_dots_empty0(..., call = caller_env()) - recurse -} - vec_proxy_recurse <- function(x, ...) { - vec_proxy(x, ..., recurse = TRUE) + .Call(ffi_vec_proxy_recurse, x) } vec_restore_recurse <- function(x, to, ...) { - vec_restore(x, to, ..., recurse = TRUE) + .Call(ffi_vec_restore_recurse, x, to) } #' Extract underlying data diff --git a/src/decl/proxy-restore-decl.h b/src/decl/proxy-restore-decl.h index 48352fd71..81ea3638f 100644 --- a/src/decl/proxy-restore-decl.h +++ b/src/decl/proxy-restore-decl.h @@ -8,4 +8,4 @@ r_obj* vec_restore_4(r_obj* x, bool recurse); static -r_obj* vec_restore_dispatch(r_obj* x, r_obj* to, bool recurse); +r_obj* vec_restore_dispatch(r_obj* x, r_obj* to); diff --git a/src/init.c b/src/init.c index b0e68ee1a..f68e671e5 100644 --- a/src/init.c +++ b/src/init.c @@ -53,9 +53,9 @@ extern r_obj* ffi_list_unchop(r_obj*, r_obj*, r_obj*, r_obj*, r_obj*); extern SEXP vctrs_chop_seq(SEXP, SEXP, SEXP, SEXP); extern r_obj* ffi_slice_seq(r_obj*, r_obj*, r_obj*, r_obj*); extern r_obj* ffi_slice_rep(r_obj*, r_obj*, r_obj*); -extern r_obj* ffi_vec_restore(r_obj*, r_obj*, r_obj*); +extern r_obj* ffi_vec_restore(r_obj*, r_obj*); +extern r_obj* ffi_vec_restore_recurse(r_obj*, r_obj*); extern r_obj* ffi_vec_restore_default(r_obj*, r_obj*); -extern r_obj* ffi_vec_proxy(r_obj*, r_obj*); extern SEXP vec_proxy_equal(SEXP); extern SEXP vec_proxy_compare(SEXP); extern SEXP vec_proxy_order(SEXP); @@ -222,9 +222,11 @@ static const R_CallMethodDef CallEntries[] = { {"vctrs_chop_seq", (DL_FUNC) &vctrs_chop_seq, 4}, {"ffi_slice_seq", (DL_FUNC) &ffi_slice_seq, 4}, {"ffi_slice_rep", (DL_FUNC) &ffi_slice_rep, 3}, - {"ffi_vec_restore", (DL_FUNC) &ffi_vec_restore, 3}, + {"ffi_vec_restore", (DL_FUNC) &ffi_vec_restore, 2}, + {"ffi_vec_restore_recurse", (DL_FUNC) &ffi_vec_restore_recurse, 2}, {"ffi_vec_restore_default", (DL_FUNC) &ffi_vec_restore_default, 2}, - {"ffi_vec_proxy", (DL_FUNC) &ffi_vec_proxy, 2}, + {"ffi_vec_proxy", (DL_FUNC) &vec_proxy, 1}, + {"ffi_vec_proxy_recurse", (DL_FUNC) &vec_proxy_recurse, 1}, {"vctrs_proxy_equal", (DL_FUNC) &vec_proxy_equal, 1}, {"vctrs_proxy_compare", (DL_FUNC) &vec_proxy_compare, 1}, {"vctrs_proxy_order", (DL_FUNC) &vec_proxy_order, 1}, diff --git a/src/proxy-restore.c b/src/proxy-restore.c index 88b1000e6..446a5bb85 100644 --- a/src/proxy-restore.c +++ b/src/proxy-restore.c @@ -12,17 +12,29 @@ r_obj* vec_restore(r_obj* x, r_obj* to, const enum vctrs_owned owned) { return vec_restore_4(x, to, owned, false); } - r_obj* vec_restore_recurse(r_obj* x, r_obj* to, const enum vctrs_owned owned) { return vec_restore_4(x, to, owned, true); } +r_obj* ffi_vec_restore(r_obj* x, r_obj* to) { + return vec_restore_4(x, to, vec_owned(x), false); +} +r_obj* ffi_vec_restore_recurse(r_obj* x, r_obj* to) { + return vec_restore_4(x, to, vec_owned(x), true); +} + static r_obj* vec_restore_4(r_obj* x, r_obj* to, const enum vctrs_owned owned, bool recurse) { - switch (class_type(to)) { + enum vctrs_class_type to_type = class_type(to); + + if (recurse && !class_type_is_data_frame(to_type) && is_data_frame(x)) { + return vec_df_restore(x, to, owned, recurse); + } + + switch (to_type) { case VCTRS_CLASS_bare_factor: case VCTRS_CLASS_bare_ordered: case VCTRS_CLASS_none: return vec_restore_default(x, to, owned); @@ -32,24 +44,16 @@ r_obj* vec_restore_4(r_obj* x, case VCTRS_CLASS_bare_data_frame: case VCTRS_CLASS_bare_tibble: return vec_bare_df_restore(x, to, owned, recurse); case VCTRS_CLASS_data_frame: return vec_df_restore(x, to, owned, recurse); - default: return vec_restore_dispatch(x, to, recurse); + default: return vec_restore_dispatch(x, to); } } -r_obj* ffi_vec_restore(r_obj* x, r_obj* to, r_obj* recurse) { - return vec_restore_4(x, to, vec_owned(x), r_as_bool(recurse)); -} -r_obj* ffi_vec_restore_recurse(r_obj* x, r_obj* to) { - return vec_restore_recurse(x, to, vec_owned(x)); -} - static -r_obj* vec_restore_dispatch(r_obj* x, r_obj* to, bool recurse) { - return vctrs_dispatch3(syms_vec_restore_dispatch, fns_vec_restore_dispatch, +r_obj* vec_restore_dispatch(r_obj* x, r_obj* to) { + return vctrs_dispatch2(syms_vec_restore_dispatch, fns_vec_restore_dispatch, syms_x, x, - syms_to, to, - syms.recurse, r_lgl(recurse)); + syms_to, to); } @@ -156,17 +160,12 @@ r_obj* ffi_vec_restore_default(r_obj* x, r_obj* to) { } -// TODO: be recursive from the inside out. - -// Restore methods are passed the original atomic type back, so we -// first restore data frames as such before calling the restore -// method, if any r_obj* vec_df_restore(r_obj* x, r_obj* to, const enum vctrs_owned owned, bool recurse) { r_obj* out = KEEP(vec_bare_df_restore(x, to, owned, recurse)); - out = vec_restore_dispatch(out, to, recurse); + out = vec_restore_dispatch(out, to); FREE(1); return out; } @@ -180,6 +179,15 @@ r_obj* vec_bare_df_restore(r_obj* x, r_type_as_c_string(r_typeof(x))); } + int n_prot = 0; + + if (!is_data_frame(to)) { + to = KEEP_N(vec_proxy(to), &n_prot); + if (!is_data_frame(to)) { + r_stop_internal("Expected restoration target to have a df proxy."); + } + } + if (recurse) { r_ssize n_cols = r_length(x); if (n_cols != r_length(to)) { @@ -215,6 +223,7 @@ r_obj* vec_bare_df_restore(r_obj* x, } FREE(2); + FREE(n_prot); return x; } diff --git a/src/proxy.c b/src/proxy.c index 55ba7f98e..29eeee0d1 100644 --- a/src/proxy.c +++ b/src/proxy.c @@ -10,10 +10,6 @@ r_obj* vec_proxy_recurse(r_obj* x) { return vec_proxy_2(x, true); } -r_obj* ffi_vec_proxy(r_obj* x, r_obj* recurse) { - return vec_proxy_2(x, r_as_bool(recurse)); -} - static r_obj* vec_proxy_2(r_obj* x, bool recurse) { struct vctrs_type_info info = vec_type_info(x); @@ -27,8 +23,11 @@ r_obj* vec_proxy_2(r_obj* x, bool recurse) { } case VCTRS_TYPE_s3: { - r_obj* out = vec_proxy_invoke(x, info.proxy_method, recurse); - FREE(1); + r_obj* out = KEEP(vec_proxy_invoke(x, info.proxy_method)); + if (recurse && is_data_frame(out)) { + out = df_proxy_recurse(out); + } + FREE(2); return out; } @@ -130,13 +129,12 @@ r_obj* vec_proxy_method(r_obj* x) { // This should be faster than normal dispatch but also means that // proxy methods can't call `NextMethod()`. This could be changed if // it turns out a problem. -r_obj* vec_proxy_invoke(r_obj* x, r_obj* method, bool recurse) { +r_obj* vec_proxy_invoke(r_obj* x, r_obj* method) { if (method == r_null) { return x; } else { - return vctrs_dispatch2(syms_vec_proxy, method, - syms_x, x, - syms.recurse, r_lgl(recurse)); + return vctrs_dispatch1(syms_vec_proxy, method, + syms_x, x); } } diff --git a/src/proxy.h b/src/proxy.h index 1ee6b8968..c33bafd9a 100644 --- a/src/proxy.h +++ b/src/proxy.h @@ -10,7 +10,7 @@ r_obj* vec_proxy_order(r_obj* x); r_obj* vec_proxy_recurse(r_obj* x); r_obj* vec_proxy_method(r_obj* x); -r_obj* vec_proxy_invoke(r_obj* x, r_obj* method, bool recurse); +r_obj* vec_proxy_invoke(r_obj* x, r_obj* method); r_obj* vec_proxy_unwrap(r_obj* x); #endif diff --git a/src/type-info.c b/src/type-info.c index b8edf830a..3950b193c 100644 --- a/src/type-info.c +++ b/src/type-info.c @@ -27,7 +27,7 @@ struct vctrs_proxy_info vec_proxy_info(r_obj* x) { info.type = vec_base_typeof(x, false); info.proxy = x; } else { - r_obj* proxy = KEEP(vec_proxy_invoke(x, info.proxy_method, false)); + r_obj* proxy = KEEP(vec_proxy_invoke(x, info.proxy_method)); info.type = vec_base_typeof(proxy, true); info.proxy = proxy; FREE(1); diff --git a/src/utils-dispatch.c b/src/utils-dispatch.c index cb5d03217..0838096fa 100644 --- a/src/utils-dispatch.c +++ b/src/utils-dispatch.c @@ -91,6 +91,17 @@ enum vctrs_class_type class_type_impl(r_obj* class) { return VCTRS_CLASS_unknown; } +bool class_type_is_data_frame(enum vctrs_class_type type) { + switch (type) { + case VCTRS_CLASS_data_frame: + case VCTRS_CLASS_bare_data_frame: + case VCTRS_CLASS_bare_tibble: + return true; + default: + return false; + } +} + static const char* class_type_as_str(enum vctrs_class_type type) { switch (type) { diff --git a/src/utils-dispatch.h b/src/utils-dispatch.h index a5047f498..37a369665 100644 --- a/src/utils-dispatch.h +++ b/src/utils-dispatch.h @@ -20,6 +20,8 @@ enum vctrs_class_type { enum vctrs_class_type class_type(r_obj* x); +bool class_type_is_data_frame(enum vctrs_class_type type); + bool vec_is_partial(r_obj* x); diff --git a/tests/testthat/_snaps/c.md b/tests/testthat/_snaps/c.md index 103a6da8e..90d0691bd 100644 --- a/tests/testthat/_snaps/c.md +++ b/tests/testthat/_snaps/c.md @@ -183,13 +183,13 @@ }) with_memory_prof(list_unchop(make_list_of(1000))) Output - [1] 104KB + [1] 112KB Code with_memory_prof(list_unchop(make_list_of(2000))) Output - [1] 206KB + [1] 222KB Code with_memory_prof(list_unchop(make_list_of(4000))) Output - [1] 409KB + [1] 440KB diff --git a/tests/testthat/test-proxy-restore.R b/tests/testthat/test-proxy-restore.R index c99f3561b..2406e4ee4 100644 --- a/tests/testthat/test-proxy-restore.R +++ b/tests/testthat/test-proxy-restore.R @@ -75,7 +75,7 @@ test_that("arguments are not inlined in the dispatch call (#300)", { vec_proxy.vctrs_foobar = unclass ) call <- vec_restore(foobar(list(1)), foobar(list(1))) - expect_equal(call, quote(vec_restore.vctrs_foobar(x = x, to = to, recurse = recurse))) + expect_equal(call, quote(vec_restore.vctrs_foobar(x = x, to = to))) }) test_that("restoring to non-bare data frames calls `vec_bare_df_restore()` before dispatching", { @@ -130,7 +130,7 @@ test_that("names<- is not called with partial data (#1108)", { expect_equal(values, list(c("a", "b", "a", "b"))) }) -test_that("proxy and restore pass `recurse` through `...`", { +test_that("recursive proxy and restore work with recursive records", { new_recursive_rcrd <- function(x) { new_rcrd( list(field = x), @@ -141,22 +141,10 @@ test_that("proxy and restore pass `recurse` through `...`", { internal <- new_rcrd(list(internal_field = 1:2)) x <- new_recursive_rcrd(data_frame(col = internal)) - local_methods( - vec_proxy.my_recursive_rcrd = function(x, ...) { - vec_proxy(field(x, "field"), ...) - }, - vec_restore.my_recursive_rcrd = function(x, to, ...) { - out <- vec_restore(x, field(to, "field"), ...) - new_recursive_rcrd(out) - } - ) - - proxy <- vec_proxy(x, recurse = TRUE) - exp <- data_frame(col = data_frame(internal_field = 1:2)) + proxy <- vec_proxy_recurse(x) + exp <- data_frame(field = data_frame(col = data_frame(internal_field = 1:2))) expect_equal(proxy, exp) - - out <- vec_restore(proxy, x, recurse = TRUE) - expect_equal(out, x) + expect_equal(vec_restore_recurse(proxy, x), x) x_exp <- new_recursive_rcrd(data_frame(col = vec_rep(internal, 2))) expect_equal( From 580ab42465e71424e3d12923a23d7ac394d35895 Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Tue, 20 Sep 2022 13:23:59 +0200 Subject: [PATCH 102/312] Use named enum for bool `recurse` --- src/proxy-restore.c | 14 +++++++------- src/proxy-restore.h | 14 +++++++------- src/proxy.c | 4 ++-- src/vctrs-core.h | 5 +++++ 4 files changed, 21 insertions(+), 16 deletions(-) diff --git a/src/proxy-restore.c b/src/proxy-restore.c index 446a5bb85..7d59095aa 100644 --- a/src/proxy-restore.c +++ b/src/proxy-restore.c @@ -10,17 +10,17 @@ // call `vec_clone_referenced()`, which won't attempt to clone if we know we // own the object. See #1151. r_obj* vec_restore(r_obj* x, r_obj* to, const enum vctrs_owned owned) { - return vec_restore_4(x, to, owned, false); + return vec_restore_4(x, to, owned, VCTRS_RECURSE_false); } r_obj* vec_restore_recurse(r_obj* x, r_obj* to, const enum vctrs_owned owned) { - return vec_restore_4(x, to, owned, true); + return vec_restore_4(x, to, owned, VCTRS_RECURSE_true); } r_obj* ffi_vec_restore(r_obj* x, r_obj* to) { - return vec_restore_4(x, to, vec_owned(x), false); + return vec_restore_4(x, to, vec_owned(x), VCTRS_RECURSE_false); } r_obj* ffi_vec_restore_recurse(r_obj* x, r_obj* to) { - return vec_restore_4(x, to, vec_owned(x), true); + return vec_restore_4(x, to, vec_owned(x), VCTRS_RECURSE_true); } static @@ -162,8 +162,8 @@ r_obj* ffi_vec_restore_default(r_obj* x, r_obj* to) { r_obj* vec_df_restore(r_obj* x, r_obj* to, - const enum vctrs_owned owned, - bool recurse) { + enum vctrs_owned owned, + enum vctrs_recurse recurse) { r_obj* out = KEEP(vec_bare_df_restore(x, to, owned, recurse)); out = vec_restore_dispatch(out, to); FREE(1); @@ -173,7 +173,7 @@ r_obj* vec_df_restore(r_obj* x, r_obj* vec_bare_df_restore(r_obj* x, r_obj* to, const enum vctrs_owned owned, - bool recurse) { + enum vctrs_recurse recurse) { if (r_typeof(x) != R_TYPE_list) { r_stop_internal("Attempt to restore data frame from a %s.", r_type_as_c_string(r_typeof(x))); diff --git a/src/proxy-restore.h b/src/proxy-restore.h index 7364e5d82..7b4bc2cdb 100644 --- a/src/proxy-restore.h +++ b/src/proxy-restore.h @@ -4,20 +4,20 @@ #include "vctrs-core.h" -r_obj* vec_restore(r_obj* x, r_obj* to, const enum vctrs_owned owned); -r_obj* vec_restore_default(r_obj* x, r_obj* to, const enum vctrs_owned owned); +r_obj* vec_restore(r_obj* x, r_obj* to, enum vctrs_owned owned); +r_obj* vec_restore_default(r_obj* x, r_obj* to, enum vctrs_owned owned); -r_obj* vec_restore_recurse(r_obj* x, r_obj* to, const enum vctrs_owned owned); +r_obj* vec_restore_recurse(r_obj* x, r_obj* to, enum vctrs_owned owned); r_obj* vec_df_restore(r_obj* x, r_obj* to, - const enum vctrs_owned owned, - bool recurse); + enum vctrs_owned owned, + enum vctrs_recurse recurse); r_obj* vec_bare_df_restore(r_obj* x, r_obj* to, - const enum vctrs_owned owned, - bool recurse); + enum vctrs_owned owned, + enum vctrs_recurse recurse); #endif diff --git a/src/proxy.c b/src/proxy.c index 29eeee0d1..23a174ebd 100644 --- a/src/proxy.c +++ b/src/proxy.c @@ -4,10 +4,10 @@ r_obj* vec_proxy(r_obj* x) { - return vec_proxy_2(x, false); + return vec_proxy_2(x, VCTRS_RECURSE_false); } r_obj* vec_proxy_recurse(r_obj* x) { - return vec_proxy_2(x, true); + return vec_proxy_2(x, VCTRS_RECURSE_true); } static diff --git a/src/vctrs-core.h b/src/vctrs-core.h index 65164adeb..6ce64dd9a 100644 --- a/src/vctrs-core.h +++ b/src/vctrs-core.h @@ -27,6 +27,11 @@ enum vctrs_owned { VCTRS_OWNED_true }; +enum vctrs_recurse { + VCTRS_RECURSE_false = 0, + VCTRS_RECURSE_true +}; + /** * Structure for argument tags From 92a50d33331792e1d86601ee0983633412e437bd Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Tue, 20 Sep 2022 13:50:07 +0200 Subject: [PATCH 103/312] Avoid calling `list_pluck()` in the non-df non-fallback case --- src/bind.c | 12 ++++++------ tests/testthat/_snaps/bind.md | 14 +++++++------- 2 files changed, 13 insertions(+), 13 deletions(-) diff --git a/src/bind.c b/src/bind.c index b520e86fd..7bf1285e2 100644 --- a/src/bind.c +++ b/src/bind.c @@ -275,15 +275,15 @@ void df_c_fallback(r_obj* out, for (r_ssize i = 0; i < n_cols; ++i) { r_obj* ptype_col = r_list_get(ptype, i); - r_obj* xs_col = KEEP(list_pluck(xs, i)); // Recurse into df-cols if (is_data_frame(ptype_col)) { + r_obj* xs_col = KEEP(list_pluck(xs, i)); r_obj* out_col = r_list_get(out, i); df_c_fallback(out_col, ptype_col, xs_col, n_rows, name_spec, name_repair); - } - - if (vec_is_common_class_fallback(ptype_col)) { + FREE(1); + } else if (vec_is_common_class_fallback(ptype_col)) { + r_obj* xs_col = KEEP(list_pluck(xs, i)); r_obj* out_col = vec_c_fallback(ptype_col, xs_col, name_spec, name_repair); r_list_poke(out, i, out_col); @@ -296,9 +296,9 @@ void df_c_fallback(r_obj* out, // Remove fallback vector from the ptype so it doesn't get in // the way of restoration later on r_list_poke(ptype, i, vec_slice(out_col, r_null)); - } - FREE(1); + FREE(1); + } } } diff --git a/tests/testthat/_snaps/bind.md b/tests/testthat/_snaps/bind.md index d8f3fc732..ecf31abce 100644 --- a/tests/testthat/_snaps/bind.md +++ b/tests/testthat/_snaps/bind.md @@ -413,11 +413,11 @@ # Integers as rows suppressMessages(with_memory_prof(vec_rbind_list(ints))) Output - [1] 3.62KB + [1] 2.79KB Code suppressMessages(with_memory_prof(vec_rbind_list(named_ints))) Output - [1] 6.15KB + [1] 3.66KB Code # Data frame with named columns df <- data_frame(x = set_names(as.list(1:2), c("a", "b")), y = set_names(1:2, c( @@ -425,7 +425,7 @@ dfs <- rep(list(df), 100) with_memory_prof(vec_rbind_list(dfs)) Output - [1] 13.8KB + [1] 11.3KB Code # Data frame with rownames (non-repaired, non-recursive case) df <- data_frame(x = 1:2) @@ -433,13 +433,13 @@ dfs <- map2(dfs, seq_along(dfs), set_rownames_recursively) with_memory_prof(vec_rbind_list(dfs)) Output - [1] 8.51KB + [1] 7.68KB Code # Data frame with rownames (repaired, non-recursive case) dfs <- map(dfs, set_rownames_recursively) with_memory_prof(vec_rbind_list(dfs)) Output - [1] 14.7KB + [1] 13.8KB Code # Data frame with rownames (non-repaired, recursive case) (#1217) df <- data_frame(x = 1:2, y = data_frame(x = 1:2)) @@ -447,11 +447,11 @@ dfs <- map2(dfs, seq_along(dfs), set_rownames_recursively) with_memory_prof(vec_rbind_list(dfs)) Output - [1] 15.5KB + [1] 13.8KB Code # Data frame with rownames (repaired, recursive case) (#1217) dfs <- map(dfs, set_rownames_recursively) with_memory_prof(vec_rbind_list(dfs)) Output - [1] 27.8KB + [1] 26.2KB From 15d6b1868b30e6ef21146e246ac3fcafab5871c8 Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Tue, 20 Sep 2022 13:57:48 +0200 Subject: [PATCH 104/312] Avoid calling `list_pluck()` in the df non-fallback case --- src/bind.c | 21 ++++++++++++++++++++- src/decl/bind-decl.h | 3 +++ tests/testthat/_snaps/bind.md | 6 +++--- 3 files changed, 26 insertions(+), 4 deletions(-) diff --git a/src/bind.c b/src/bind.c index 7bf1285e2..379614658 100644 --- a/src/bind.c +++ b/src/bind.c @@ -277,7 +277,7 @@ void df_c_fallback(r_obj* out, r_obj* ptype_col = r_list_get(ptype, i); // Recurse into df-cols - if (is_data_frame(ptype_col)) { + if (is_data_frame(ptype_col) && df_needs_fallback(ptype_col)) { r_obj* xs_col = KEEP(list_pluck(xs, i)); r_obj* out_col = r_list_get(out, i); df_c_fallback(out_col, ptype_col, xs_col, n_rows, name_spec, name_repair); @@ -302,6 +302,25 @@ void df_c_fallback(r_obj* out, } } +static +bool df_needs_fallback(r_obj* x) { + r_ssize n_cols = r_length(x); + r_obj* const * v_x = r_list_cbegin(x); + + for (r_ssize i = 0; i < n_cols; ++i) { + r_obj* col = v_x[i]; + + if (vec_is_common_class_fallback(col)) { + return true; + } + if (is_data_frame(col) && df_needs_fallback(col)) { + return true; + } + } + + return false; +} + static r_obj* as_df_row(r_obj* x, diff --git a/src/decl/bind-decl.h b/src/decl/bind-decl.h index 6024136c0..d4a8c7cdd 100644 --- a/src/decl/bind-decl.h +++ b/src/decl/bind-decl.h @@ -57,3 +57,6 @@ void df_c_fallback(r_obj* out, r_ssize n_rows, r_obj* name_spec, struct name_repair_opts* name_repair); + +static +bool df_needs_fallback(r_obj* x); diff --git a/tests/testthat/_snaps/bind.md b/tests/testthat/_snaps/bind.md index ecf31abce..1c0d42f2c 100644 --- a/tests/testthat/_snaps/bind.md +++ b/tests/testthat/_snaps/bind.md @@ -425,7 +425,7 @@ dfs <- rep(list(df), 100) with_memory_prof(vec_rbind_list(dfs)) Output - [1] 11.3KB + [1] 10.4KB Code # Data frame with rownames (non-repaired, non-recursive case) df <- data_frame(x = 1:2) @@ -447,11 +447,11 @@ dfs <- map2(dfs, seq_along(dfs), set_rownames_recursively) with_memory_prof(vec_rbind_list(dfs)) Output - [1] 13.8KB + [1] 13KB Code # Data frame with rownames (repaired, recursive case) (#1217) dfs <- map(dfs, set_rownames_recursively) with_memory_prof(vec_rbind_list(dfs)) Output - [1] 26.2KB + [1] 25.3KB From 56089dd5642ca60cb6f1bb52cf76311e32fa4353 Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Tue, 27 Sep 2022 11:39:44 +0200 Subject: [PATCH 105/312] Finish switching to recurse enum --- src/decl/proxy-decl.h | 2 +- src/decl/proxy-restore-decl.h | 4 ++-- src/proxy-restore.c | 21 ++++++++++++--------- src/proxy.c | 2 +- src/utils.c | 11 +++++++++-- 5 files changed, 25 insertions(+), 15 deletions(-) diff --git a/src/decl/proxy-decl.h b/src/decl/proxy-decl.h index d2a78abda..39623c500 100644 --- a/src/decl/proxy-decl.h +++ b/src/decl/proxy-decl.h @@ -11,7 +11,7 @@ r_obj* fns_vec_proxy_compare_array; r_obj* fns_vec_proxy_order_array; static -r_obj* vec_proxy_2(r_obj* x, bool recurse); +r_obj* vec_proxy_2(r_obj* x, enum vctrs_recurse recurse); static inline r_obj* vec_proxy_equal_impl(r_obj* x); diff --git a/src/decl/proxy-restore-decl.h b/src/decl/proxy-restore-decl.h index 81ea3638f..93cbe8a5c 100644 --- a/src/decl/proxy-restore-decl.h +++ b/src/decl/proxy-restore-decl.h @@ -4,8 +4,8 @@ static r_obj* fns_vec_restore_dispatch; static r_obj* vec_restore_4(r_obj* x, r_obj* to, - const enum vctrs_owned owned, - bool recurse); + enum vctrs_owned owned, + enum vctrs_recurse recurse); static r_obj* vec_restore_dispatch(r_obj* x, r_obj* to); diff --git a/src/proxy-restore.c b/src/proxy-restore.c index 7d59095aa..534cbb500 100644 --- a/src/proxy-restore.c +++ b/src/proxy-restore.c @@ -9,25 +9,25 @@ // causing duplication to occur. Passing `owned` through here allows us to // call `vec_clone_referenced()`, which won't attempt to clone if we know we // own the object. See #1151. -r_obj* vec_restore(r_obj* x, r_obj* to, const enum vctrs_owned owned) { +r_obj* vec_restore(r_obj* x, r_obj* to, enum vctrs_owned owned) { return vec_restore_4(x, to, owned, VCTRS_RECURSE_false); } -r_obj* vec_restore_recurse(r_obj* x, r_obj* to, const enum vctrs_owned owned) { +r_obj* vec_restore_recurse(r_obj* x, r_obj* to, enum vctrs_owned owned) { return vec_restore_4(x, to, owned, VCTRS_RECURSE_true); } r_obj* ffi_vec_restore(r_obj* x, r_obj* to) { - return vec_restore_4(x, to, vec_owned(x), VCTRS_RECURSE_false); + return vec_restore(x, to, vec_owned(x)); } r_obj* ffi_vec_restore_recurse(r_obj* x, r_obj* to) { - return vec_restore_4(x, to, vec_owned(x), VCTRS_RECURSE_true); + return vec_restore_recurse(x, to, vec_owned(x)); } static r_obj* vec_restore_4(r_obj* x, r_obj* to, - const enum vctrs_owned owned, - bool recurse) { + enum vctrs_owned owned, + enum vctrs_recurse recurse) { enum vctrs_class_type to_type = class_type(to); if (recurse && !class_type_is_data_frame(to_type) && is_data_frame(x)) { @@ -58,7 +58,7 @@ r_obj* vec_restore_dispatch(r_obj* x, r_obj* to) { // Copy attributes except names and dim. This duplicates `x` if needed. -r_obj* vec_restore_default(r_obj* x, r_obj* to, const enum vctrs_owned owned) { +r_obj* vec_restore_default(r_obj* x, r_obj* to, enum vctrs_owned owned) { r_obj* attrib = r_attrib(to); const bool is_s4 = IS_S4_OBJECT(to); @@ -172,7 +172,7 @@ r_obj* vec_df_restore(r_obj* x, r_obj* vec_bare_df_restore(r_obj* x, r_obj* to, - const enum vctrs_owned owned, + enum vctrs_owned owned, enum vctrs_recurse recurse) { if (r_typeof(x) != R_TYPE_list) { r_stop_internal("Attempt to restore data frame from a %s.", @@ -228,7 +228,10 @@ r_obj* vec_bare_df_restore(r_obj* x, } r_obj* ffi_vec_bare_df_restore(r_obj* x, r_obj* to) { - return vec_bare_df_restore(x, to, vec_owned(x), false); + return vec_bare_df_restore(x, + to, + vec_owned(x), + VCTRS_RECURSE_false); } diff --git a/src/proxy.c b/src/proxy.c index 23a174ebd..d7bd89865 100644 --- a/src/proxy.c +++ b/src/proxy.c @@ -11,7 +11,7 @@ r_obj* vec_proxy_recurse(r_obj* x) { } static -r_obj* vec_proxy_2(r_obj* x, bool recurse) { +r_obj* vec_proxy_2(r_obj* x, enum vctrs_recurse recurse) { struct vctrs_type_info info = vec_type_info(x); KEEP(info.shelter); diff --git a/src/utils.c b/src/utils.c index 66f329ff2..b4f6cad8f 100644 --- a/src/utils.c +++ b/src/utils.c @@ -1,3 +1,4 @@ +#include "vctrs-core.h" #include "vctrs.h" #include "type-data-frame.h" #include @@ -353,7 +354,10 @@ SEXP bare_df_map(SEXP df, SEXP (*fn)(SEXP)) { SEXP out = PROTECT(map(df, fn)); // Total ownership because `map()` generates a fresh list - out = vec_bare_df_restore(out, df, VCTRS_OWNED_true, false); + out = vec_bare_df_restore(out, + df, + VCTRS_OWNED_true, + VCTRS_RECURSE_false); UNPROTECT(1); return out; @@ -364,7 +368,10 @@ SEXP df_map(SEXP df, SEXP (*fn)(SEXP)) { SEXP out = PROTECT(map(df, fn)); // Total ownership because `map()` generates a fresh list - out = vec_df_restore(out, df, VCTRS_OWNED_true, false); + out = vec_df_restore(out, + df, + VCTRS_OWNED_true, + VCTRS_RECURSE_false); UNPROTECT(1); return out; From 4da4c3a017d619f60e398239996664aa1147591d Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Tue, 27 Sep 2022 11:51:05 +0200 Subject: [PATCH 106/312] Add `vec_ptype_final()` and use it in `vec_rbind()` --- src/bind.c | 2 +- src/decl/ptype-decl.h | 6 ++++++ src/ptype.c | 25 ++++++++++++++++++------- src/ptype.h | 1 + 4 files changed, 26 insertions(+), 8 deletions(-) diff --git a/src/bind.c b/src/bind.c index 379614658..55488f42d 100644 --- a/src/bind.c +++ b/src/bind.c @@ -295,7 +295,7 @@ void df_c_fallback(r_obj* out, // Remove fallback vector from the ptype so it doesn't get in // the way of restoration later on - r_list_poke(ptype, i, vec_slice(out_col, r_null)); + r_list_poke(ptype, i, vec_ptype_final(out_col)); FREE(1); } diff --git a/src/decl/ptype-decl.h b/src/decl/ptype-decl.h index bea467496..e3eeb770a 100644 --- a/src/decl/ptype-decl.h +++ b/src/decl/ptype-decl.h @@ -32,3 +32,9 @@ r_obj* vec_ptype_finalise_unspecified(r_obj* x); static r_obj* vec_ptype_finalise_dispatch(r_obj* x); + +static +r_obj* vec_ptype_final_call; + +static +struct r_lazy vec_ptype_final_lazy_call; diff --git a/src/ptype.c b/src/ptype.c index 38e82f4f5..132cde7e0 100644 --- a/src/ptype.c +++ b/src/ptype.c @@ -195,18 +195,29 @@ r_obj* vec_ptype_finalise_dispatch(r_obj* x) { ); } +r_obj* vec_ptype_final(r_obj* x) { + r_obj* out = KEEP(vec_ptype(x, vec_args.x, vec_ptype_final_lazy_call)); + out = vec_ptype_finalise(out); + + FREE(1); + return out; +} + + void vctrs_init_ptype(r_obj* ns) { syms_vec_ptype = r_sym("vec_ptype"); syms_vec_ptype_finalise_dispatch = r_sym("vec_ptype_finalise_dispatch"); fns_vec_ptype_finalise_dispatch = r_eval(syms_vec_ptype_finalise_dispatch, ns); -} -static -r_obj* syms_vec_ptype = NULL; + vec_ptype_final_call = r_parse("vec_ptype_final()"); + r_preserve_global(vec_ptype_final_call); -static -r_obj* syms_vec_ptype_finalise_dispatch = NULL; + vec_ptype_final_lazy_call = (struct r_lazy) { .x = vec_ptype_final_call, .env = r_null }; +} -static -r_obj* fns_vec_ptype_finalise_dispatch = NULL; +static r_obj* syms_vec_ptype = NULL; +static r_obj* syms_vec_ptype_finalise_dispatch = NULL; +static r_obj* fns_vec_ptype_finalise_dispatch = NULL; +static r_obj* vec_ptype_final_call = NULL; +static struct r_lazy vec_ptype_final_lazy_call = { 0 }; diff --git a/src/ptype.h b/src/ptype.h index 29ec40103..7c38d84f7 100644 --- a/src/ptype.h +++ b/src/ptype.h @@ -4,5 +4,6 @@ #include "vctrs-core.h" r_obj* vec_ptype(r_obj* x, struct vctrs_arg* x_arg, struct r_lazy call); +r_obj* vec_ptype_final(r_obj* x); #endif From 9eee3ed57ee13c9f6e78d860f0e8755d6957849c Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Tue, 27 Sep 2022 12:00:22 +0200 Subject: [PATCH 107/312] Use `class_type_is_data_frame()` in `is_data_frame()` --- src/type-data-frame.c | 11 +++-------- src/utils-dispatch.c | 11 ----------- src/utils-dispatch.h | 12 +++++++++++- 3 files changed, 14 insertions(+), 20 deletions(-) diff --git a/src/type-data-frame.c b/src/type-data-frame.c index b7cb054f7..d8d099db0 100644 --- a/src/type-data-frame.c +++ b/src/type-data-frame.c @@ -1,17 +1,12 @@ +#include "utils-dispatch.h" #include "vctrs.h" #include "type-data-frame.h" #include "decl/type-data-frame-decl.h" bool is_data_frame(r_obj* x) { - if (r_typeof(x) != R_TYPE_list) { - return false; - } - - enum vctrs_class_type type = class_type(x); return - type == VCTRS_CLASS_bare_data_frame || - type == VCTRS_CLASS_bare_tibble || - type == VCTRS_CLASS_data_frame; + r_typeof(x) == R_TYPE_list && + class_type_is_data_frame(class_type(x)); } bool is_native_df(r_obj* x) { diff --git a/src/utils-dispatch.c b/src/utils-dispatch.c index 0838096fa..cb5d03217 100644 --- a/src/utils-dispatch.c +++ b/src/utils-dispatch.c @@ -91,17 +91,6 @@ enum vctrs_class_type class_type_impl(r_obj* class) { return VCTRS_CLASS_unknown; } -bool class_type_is_data_frame(enum vctrs_class_type type) { - switch (type) { - case VCTRS_CLASS_data_frame: - case VCTRS_CLASS_bare_data_frame: - case VCTRS_CLASS_bare_tibble: - return true; - default: - return false; - } -} - static const char* class_type_as_str(enum vctrs_class_type type) { switch (type) { diff --git a/src/utils-dispatch.h b/src/utils-dispatch.h index 37a369665..aea76b25f 100644 --- a/src/utils-dispatch.h +++ b/src/utils-dispatch.h @@ -20,7 +20,17 @@ enum vctrs_class_type { enum vctrs_class_type class_type(r_obj* x); -bool class_type_is_data_frame(enum vctrs_class_type type); +static inline +bool class_type_is_data_frame(enum vctrs_class_type type) { + switch (type) { + case VCTRS_CLASS_data_frame: + case VCTRS_CLASS_bare_data_frame: + case VCTRS_CLASS_bare_tibble: + return true; + default: + return false; + } +} bool vec_is_partial(r_obj* x); From 4425ed0ce4230760dc2744dd23847dcbc2d3f902 Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Tue, 27 Sep 2022 12:02:49 +0200 Subject: [PATCH 108/312] Move data frame check to default case --- src/proxy-restore.c | 11 ++++++----- 1 file changed, 6 insertions(+), 5 deletions(-) diff --git a/src/proxy-restore.c b/src/proxy-restore.c index 534cbb500..eecc7c3e6 100644 --- a/src/proxy-restore.c +++ b/src/proxy-restore.c @@ -30,10 +30,6 @@ r_obj* vec_restore_4(r_obj* x, enum vctrs_recurse recurse) { enum vctrs_class_type to_type = class_type(to); - if (recurse && !class_type_is_data_frame(to_type) && is_data_frame(x)) { - return vec_df_restore(x, to, owned, recurse); - } - switch (to_type) { case VCTRS_CLASS_bare_factor: case VCTRS_CLASS_bare_ordered: @@ -44,7 +40,12 @@ r_obj* vec_restore_4(r_obj* x, case VCTRS_CLASS_bare_data_frame: case VCTRS_CLASS_bare_tibble: return vec_bare_df_restore(x, to, owned, recurse); case VCTRS_CLASS_data_frame: return vec_df_restore(x, to, owned, recurse); - default: return vec_restore_dispatch(x, to); + default: + if (recurse && is_data_frame(x)) { + return vec_df_restore(x, to, owned, recurse); + } else { + return vec_restore_dispatch(x, to); + } } } From ac0e516d9a27a40ff983aa781b0002f283986d24 Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Tue, 27 Sep 2022 12:05:28 +0200 Subject: [PATCH 109/312] Test non-recursive proxies are not recursive --- tests/testthat/test-proxy-restore.R | 6 ++++++ 1 file changed, 6 insertions(+) diff --git a/tests/testthat/test-proxy-restore.R b/tests/testthat/test-proxy-restore.R index 2406e4ee4..a39da2a5c 100644 --- a/tests/testthat/test-proxy-restore.R +++ b/tests/testthat/test-proxy-restore.R @@ -146,6 +146,12 @@ test_that("recursive proxy and restore work with recursive records", { expect_equal(proxy, exp) expect_equal(vec_restore_recurse(proxy, x), x) + # Non-recursive case doesn't proxy `internal` + proxy <- vec_proxy(x) + exp <- data_frame(field = data_frame(col = internal)) + expect_equal(proxy, exp) + expect_equal(vec_restore(proxy, x), x) + x_exp <- new_recursive_rcrd(data_frame(col = vec_rep(internal, 2))) expect_equal( list_unchop(list(x, x)), From 217d02fe893571ef52e302a8c2a69ea945537b23 Mon Sep 17 00:00:00 2001 From: Davis Vaughan Date: Tue, 27 Sep 2022 09:17:15 -0400 Subject: [PATCH 110/312] Use `vec_any_missing()` internally (#1681) * Use `vec_any_missing()` in `vec_interleave()` * Use `vec_any_missing()` in `vec_proxy_order.list()` * Use `vec_any_missing()` in `` tooling --- R/slice-interleave.R | 5 ++--- R/type-bare.R | 8 ++++++-- R/type-vctr.R | 14 +++++--------- 3 files changed, 13 insertions(+), 14 deletions(-) diff --git a/R/slice-interleave.R b/R/slice-interleave.R index 2226a7a74..6679faefe 100644 --- a/R/slice-interleave.R +++ b/R/slice-interleave.R @@ -41,10 +41,9 @@ vec_interleave <- function(..., .name_repair = c("minimal", "unique", "check_unique", "universal")) { args <- list2(...) - # TODO: Use `vec_drop_missing()` # `NULL`s must be dropped up front to generate appropriate indices - missing <- vec_detect_missing(args) - if (any(missing)) { + if (vec_any_missing(args)) { + missing <- vec_detect_missing(args) args <- vec_slice(args, !missing) } diff --git a/R/type-bare.R b/R/type-bare.R index fa178f96a..84cf6e470 100644 --- a/R/type-bare.R +++ b/R/type-bare.R @@ -414,8 +414,12 @@ vec_proxy_order.list <- function(x, ...) { # This allows list elements to be grouped in `vec_order()`. # Have to separately ensure missing values are propagated. out <- vec_duplicate_id(x) - na <- vec_detect_missing(x) - out <- vec_assign(out, na, NA_integer_) + + if (vec_any_missing(x)) { + missing <- vec_detect_missing(x) + out <- vec_assign(out, missing, NA_integer_) + } + out } diff --git a/R/type-vctr.R b/R/type-vctr.R index a069c9d2a..1f5fcc8cd 100644 --- a/R/type-vctr.R +++ b/R/type-vctr.R @@ -103,12 +103,11 @@ names_repair_missing <- function(x) { return(x) } - missing <- vec_detect_missing(x) - - if (any(missing)) { + if (vec_any_missing(x)) { # We never want to allow `NA_character_` names to slip through, but # erroring on them has caused issues. Instead, we repair them to the # empty string (#784). + missing <- vec_detect_missing(x) x <- vec_assign(x, missing, "") } @@ -410,9 +409,7 @@ is.na.vctrs_vctr <- function(x) { #' @importFrom stats na.fail #' @export na.fail.vctrs_vctr <- function(object, ...) { - missing <- vec_detect_missing(object) - - if (any(missing)) { + if (vec_any_missing(object)) { # Return the same error as `na.fail.default()` abort("missing values in object") } @@ -436,13 +433,12 @@ na_remove <- function(x, type) { # The only difference between `na.omit()` and `na.exclude()` is the class # of the `na.action` attribute - missing <- vec_detect_missing(x) - - if (!any(missing)) { + if (!vec_any_missing(x)) { return(x) } # `na.omit/exclude()` attach the locations of the omitted values to the result + missing <- vec_detect_missing(x) loc <- which(missing) names <- vec_names(x) From 2c7f127016f99102eba0ee1c4420486796af1ba7 Mon Sep 17 00:00:00 2001 From: Davis Vaughan Date: Tue, 27 Sep 2022 09:21:32 -0400 Subject: [PATCH 111/312] Update `runs.c` style (#1682) --- src/decl/runs-decl.h | 77 +++++++ src/runs.c | 380 +++++++++++++++------------------- src/runs.h | 8 + src/vctrs.h | 2 +- tests/testthat/_snaps/runs.md | 48 +++++ tests/testthat/test-runs.R | 24 ++- 6 files changed, 314 insertions(+), 225 deletions(-) create mode 100644 src/decl/runs-decl.h create mode 100644 src/runs.h create mode 100644 tests/testthat/_snaps/runs.md diff --git a/src/decl/runs-decl.h b/src/decl/runs-decl.h new file mode 100644 index 000000000..69d910d03 --- /dev/null +++ b/src/decl/runs-decl.h @@ -0,0 +1,77 @@ +static +r_obj* vec_locate_runs(r_obj* x, bool start); + +static inline +void vec_locate_run_starts(const int* v_id, r_ssize size, int* v_out); +static inline +void vec_locate_run_ends(const int* v_id, r_ssize size, int* v_out); + + +static +r_obj* vec_detect_runs(r_obj* x, bool start); + +static inline +void vec_detect_run_starts(const int* v_id, r_ssize size, int* v_out); +static inline +void vec_detect_run_ends(const int* v_id, r_ssize size, int* v_out); + + +static inline +int lgl_identify_runs(r_obj* x, r_ssize size, int* v_out); +static inline +int int_identify_runs(r_obj* x, r_ssize size, int* v_out); +static inline +int dbl_identify_runs(r_obj* x, r_ssize size, int* v_out); +static inline +int cpl_identify_runs(r_obj* x, r_ssize size, int* v_out); +static inline +int chr_identify_runs(r_obj* x, r_ssize size, int* v_out); +static inline +int raw_identify_runs(r_obj* x, r_ssize size, int* v_out); +static inline +int list_identify_runs(r_obj* x, r_ssize size, int* v_out); +static inline +int df_identify_runs(r_obj* x, r_ssize size, int* v_out); + + +static inline +int vec_identify_runs_col(r_obj* x, + int id, + struct df_short_circuit_info* p_info, + int* v_out); + +static inline +int lgl_identify_runs_col(r_obj* x, + int id, + struct df_short_circuit_info* p_info, + int* v_out); +static inline +int int_identify_runs_col(r_obj* x, + int id, + struct df_short_circuit_info* p_info, + int* v_out); +static inline +int dbl_identify_runs_col(r_obj* x, + int id, + struct df_short_circuit_info* p_info, + int* v_out); +static inline +int cpl_identify_runs_col(r_obj* x, + int id, + struct df_short_circuit_info* p_info, + int* v_out); +static inline +int chr_identify_runs_col(r_obj* x, + int id, + struct df_short_circuit_info* p_info, + int* v_out); +static inline +int raw_identify_runs_col(r_obj* x, + int id, + struct df_short_circuit_info* p_info, + int* v_out); +static inline +int list_identify_runs_col(r_obj* x, + int id, + struct df_short_circuit_info* p_info, + int* v_out); diff --git a/src/runs.c b/src/runs.c index 4b94ccb0d..d16390b03 100644 --- a/src/runs.c +++ b/src/runs.c @@ -1,313 +1,286 @@ #include "vctrs.h" -// ----------------------------------------------------------------------------- +#include "decl/runs-decl.h" -static SEXP vec_locate_runs(SEXP x, bool start); +// ----------------------------------------------------------------------------- -// [[register()]] -SEXP vctrs_locate_runs(SEXP x, SEXP start) { - bool c_start = (bool) r_bool_as_int(start); - return vec_locate_runs(x, c_start); +r_obj* vctrs_locate_runs(r_obj* x, r_obj* ffi_start) { + const bool start = r_arg_as_bool(ffi_start, "start"); + return vec_locate_runs(x, start); } -static void vec_locate_run_starts(const int* p_id, r_ssize size, int* p_out); -static void vec_locate_run_ends(const int* p_id, r_ssize size, int* p_out); - static -SEXP vec_locate_runs(SEXP x, bool start) { - SEXP id = PROTECT(vec_identify_runs(x)); - const int* p_id = INTEGER(id); - - r_ssize size = r_length(id); +r_obj* vec_locate_runs(r_obj* x, bool start) { + r_obj* id = KEEP(vec_identify_runs(x)); + const int* v_id = r_int_cbegin(id); - int n = r_int_get(r_attrib_get(id, syms_n), 0); + const r_ssize size = r_length(id); + const int n = r_int_get(r_attrib_get(id, syms_n), 0); - SEXP out = PROTECT(r_new_integer(n)); - int* p_out = INTEGER(out); + r_obj* out = KEEP(r_new_integer(n)); + int* v_out = r_int_begin(out); if (n == 0) { - UNPROTECT(2); + FREE(2); return out; } if (start) { - vec_locate_run_starts(p_id, size, p_out); + vec_locate_run_starts(v_id, size, v_out); } else { - vec_locate_run_ends(p_id, size, p_out); + vec_locate_run_ends(v_id, size, v_out); } - UNPROTECT(2); + FREE(2); return out; } -static -void vec_locate_run_starts(const int* p_id, r_ssize size, int* p_out) { +static inline +void vec_locate_run_starts(const int* v_id, r_ssize size, int* v_out) { r_ssize loc = 0; // Handle first case - int ref = p_id[0]; - p_out[loc] = 1; + int ref = v_id[0]; + v_out[loc] = 1; ++loc; for (r_ssize i = 1; i < size; ++i) { - const int elt = p_id[i]; + const int elt = v_id[i]; if (elt == ref) { continue; } ref = elt; - p_out[loc] = i + 1; + v_out[loc] = i + 1; ++loc; } } -static -void vec_locate_run_ends(const int* p_id, r_ssize size, int* p_out) { +static inline +void vec_locate_run_ends(const int* v_id, r_ssize size, int* v_out) { r_ssize loc = 0; - int ref = p_id[0]; + int ref = v_id[0]; for (r_ssize i = 1; i < size; ++i) { - const int elt = p_id[i]; + const int elt = v_id[i]; if (elt == ref) { continue; } ref = elt; - p_out[loc] = i; + v_out[loc] = i; ++loc; } // Handle last case - p_out[loc] = size; + v_out[loc] = size; } // ----------------------------------------------------------------------------- -static SEXP vec_detect_runs(SEXP x, bool start); - -// [[register()]] -SEXP vctrs_detect_runs(SEXP x, SEXP start) { - bool c_start = (bool) r_bool_as_int(start); - return vec_detect_runs(x, c_start); +r_obj* vctrs_detect_runs(r_obj* x, r_obj* ffi_start) { + bool start = r_arg_as_bool(ffi_start, "start"); + return vec_detect_runs(x, start); } -static void vec_detect_run_starts(const int* p_id, r_ssize size, int* p_out); -static void vec_detect_run_ends(const int* p_id, r_ssize size, int* p_out); - static -SEXP vec_detect_runs(SEXP x, bool start) { - SEXP id = PROTECT(vec_identify_runs(x)); - const int* p_id = INTEGER(id); +r_obj* vec_detect_runs(r_obj* x, bool start) { + r_obj* id = KEEP(vec_identify_runs(x)); + const int* v_id = r_int_cbegin(id); r_ssize size = r_length(id); - SEXP out = PROTECT(r_new_logical(size)); - int* p_out = LOGICAL(out); - memset(p_out, 0, size * sizeof(int)); + r_obj* out = KEEP(r_new_logical(size)); + int* v_out = r_lgl_begin(out); + memset(v_out, 0, size * sizeof(int)); if (size == 0) { - UNPROTECT(2); + FREE(2); return out; } if (start) { - vec_detect_run_starts(p_id, size, p_out); + vec_detect_run_starts(v_id, size, v_out); } else { - vec_detect_run_ends(p_id, size, p_out); + vec_detect_run_ends(v_id, size, v_out); } - UNPROTECT(2); + FREE(2); return out; } -static -void vec_detect_run_starts(const int* p_id, r_ssize size, int* p_out) { +static inline +void vec_detect_run_starts(const int* v_id, r_ssize size, int* v_out) { // Handle first case - int ref = p_id[0]; - p_out[0] = 1; + int ref = v_id[0]; + v_out[0] = 1; for (r_ssize i = 1; i < size; ++i) { - const int elt = p_id[i]; + const int elt = v_id[i]; if (elt == ref) { continue; } ref = elt; - p_out[i] = 1; + v_out[i] = 1; } } -static -void vec_detect_run_ends(const int* p_id, r_ssize size, int* p_out) { - int ref = p_id[0]; +static inline +void vec_detect_run_ends(const int* v_id, r_ssize size, int* v_out) { + int ref = v_id[0]; for (r_ssize i = 1; i < size; ++i) { - const int elt = p_id[i]; + const int elt = v_id[i]; if (elt == ref) { continue; } ref = elt; - p_out[i - 1] = 1; + v_out[i - 1] = 1; } // Handle last case - p_out[size - 1] = 1; + v_out[size - 1] = 1; } // ----------------------------------------------------------------------------- -// [[register()]] -SEXP vctrs_identify_runs(SEXP x) { +r_obj* vctrs_identify_runs(r_obj* x) { return vec_identify_runs(x); } -static int lgl_identify_runs(SEXP x, R_len_t size, int* p_out); -static int int_identify_runs(SEXP x, R_len_t size, int* p_out); -static int dbl_identify_runs(SEXP x, R_len_t size, int* p_out); -static int cpl_identify_runs(SEXP x, R_len_t size, int* p_out); -static int chr_identify_runs(SEXP x, R_len_t size, int* p_out); -static int raw_identify_runs(SEXP x, R_len_t size, int* p_out); -static int list_identify_runs(SEXP x, R_len_t size, int* p_out); -static int df_identify_runs(SEXP x, R_len_t size, int* p_out); - -// [[ include("vctrs.h") ]] -SEXP vec_identify_runs(SEXP x) { - SEXP proxy = PROTECT(vec_proxy_equal(x)); - R_len_t size = vec_size(proxy); - proxy = PROTECT(vec_normalize_encoding(proxy)); +r_obj* vec_identify_runs(r_obj* x) { + r_obj* proxy = KEEP(vec_proxy_equal(x)); + r_ssize size = vec_size(proxy); + proxy = KEEP(vec_normalize_encoding(proxy)); - SEXP out = PROTECT(Rf_allocVector(INTSXP, size)); - int* p_out = INTEGER(out); + r_obj* out = KEEP(r_alloc_integer(size)); + int* v_out = r_int_begin(out); // Handle size 0 up front. // All implementations assume at least 1 element. if (size == 0) { - SEXP n = PROTECT(r_int(0)); - r_attrib_poke(out, syms_n, n); - UNPROTECT(4); + r_obj* ffi_n = r_int(0); + r_attrib_poke(out, syms_n, ffi_n); + FREE(3); return out; } - enum vctrs_type type = vec_proxy_typeof(proxy); + const enum vctrs_type type = vec_proxy_typeof(proxy); int n; switch (type) { - case VCTRS_TYPE_logical: n = lgl_identify_runs(proxy, size, p_out); break; - case VCTRS_TYPE_integer: n = int_identify_runs(proxy, size, p_out); break; - case VCTRS_TYPE_double: n = dbl_identify_runs(proxy, size, p_out); break; - case VCTRS_TYPE_complex: n = cpl_identify_runs(proxy, size, p_out); break; - case VCTRS_TYPE_character: n = chr_identify_runs(proxy, size, p_out); break; - case VCTRS_TYPE_raw: n = raw_identify_runs(proxy, size, p_out); break; - case VCTRS_TYPE_list: n = list_identify_runs(proxy, size, p_out); break; - case VCTRS_TYPE_dataframe: n = df_identify_runs(proxy, size, p_out); break; + case VCTRS_TYPE_logical: n = lgl_identify_runs(proxy, size, v_out); break; + case VCTRS_TYPE_integer: n = int_identify_runs(proxy, size, v_out); break; + case VCTRS_TYPE_double: n = dbl_identify_runs(proxy, size, v_out); break; + case VCTRS_TYPE_complex: n = cpl_identify_runs(proxy, size, v_out); break; + case VCTRS_TYPE_character: n = chr_identify_runs(proxy, size, v_out); break; + case VCTRS_TYPE_raw: n = raw_identify_runs(proxy, size, v_out); break; + case VCTRS_TYPE_list: n = list_identify_runs(proxy, size, v_out); break; + case VCTRS_TYPE_dataframe: n = df_identify_runs(proxy, size, v_out); break; default: stop_unimplemented_vctrs_type("vec_identify_runs", type); } - SEXP r_n = PROTECT(r_int(n)); - r_attrib_poke(out, syms_n, r_n); + r_obj* ffi_n = r_int(n); + r_attrib_poke(out, syms_n, ffi_n); - UNPROTECT(4); + FREE(3); return out; } // ----------------------------------------------------------------------------- -#define VEC_IDENTIFY_RUNS(CTYPE, CONST_DEREF, EQUAL_NA_EQUAL) { \ +#define VEC_IDENTIFY_RUNS(CTYPE, CBEGIN, EQUAL_NA_EQUAL) { \ int id = 1; \ - const CTYPE* p_x = CONST_DEREF(x); \ + CTYPE const* v_x = CBEGIN(x); \ \ /* Handle first case */ \ - CTYPE ref = p_x[0]; \ - p_out[0] = id; \ + CTYPE ref = v_x[0]; \ + v_out[0] = id; \ \ - for (R_len_t i = 1; i < size; ++i) { \ - const CTYPE elt = p_x[i]; \ + for (r_ssize i = 1; i < size; ++i) { \ + CTYPE const elt = v_x[i]; \ \ if (EQUAL_NA_EQUAL(elt, ref) == 0) { \ ++id; \ ref = elt; \ } \ \ - p_out[i] = id; \ + v_out[i] = id; \ } \ \ return id; \ } static -int lgl_identify_runs(SEXP x, R_len_t size, int* p_out) { - VEC_IDENTIFY_RUNS(int, LOGICAL_RO, lgl_equal_na_equal); +int lgl_identify_runs(r_obj* x, r_ssize size, int* v_out) { + VEC_IDENTIFY_RUNS(int, r_lgl_cbegin, lgl_equal_na_equal); } static -int int_identify_runs(SEXP x, R_len_t size, int* p_out) { - VEC_IDENTIFY_RUNS(int, INTEGER_RO, int_equal_na_equal); +int int_identify_runs(r_obj* x, r_ssize size, int* v_out) { + VEC_IDENTIFY_RUNS(int, r_int_cbegin, int_equal_na_equal); } static -int dbl_identify_runs(SEXP x, R_len_t size, int* p_out) { - VEC_IDENTIFY_RUNS(double, REAL_RO, dbl_equal_na_equal); +int dbl_identify_runs(r_obj* x, r_ssize size, int* v_out) { + VEC_IDENTIFY_RUNS(double, r_dbl_cbegin, dbl_equal_na_equal); } static -int cpl_identify_runs(SEXP x, R_len_t size, int* p_out) { - VEC_IDENTIFY_RUNS(Rcomplex, COMPLEX_RO, cpl_equal_na_equal); +int cpl_identify_runs(r_obj* x, r_ssize size, int* v_out) { + VEC_IDENTIFY_RUNS(Rcomplex, r_cpl_cbegin, cpl_equal_na_equal); } static -int chr_identify_runs(SEXP x, R_len_t size, int* p_out) { - VEC_IDENTIFY_RUNS(SEXP, STRING_PTR_RO, chr_equal_na_equal); +int chr_identify_runs(r_obj* x, r_ssize size, int* v_out) { + VEC_IDENTIFY_RUNS(r_obj*, r_chr_cbegin, chr_equal_na_equal); } static -int raw_identify_runs(SEXP x, R_len_t size, int* p_out) { - VEC_IDENTIFY_RUNS(Rbyte, RAW_RO, raw_equal_na_equal); +int raw_identify_runs(r_obj* x, r_ssize size, int* v_out) { + VEC_IDENTIFY_RUNS(Rbyte, r_raw_cbegin, raw_equal_na_equal); } static -int list_identify_runs(SEXP x, R_len_t size, int* p_out) { - VEC_IDENTIFY_RUNS(SEXP, VECTOR_PTR_RO, list_equal_na_equal); +int list_identify_runs(r_obj* x, r_ssize size, int* v_out) { + VEC_IDENTIFY_RUNS(r_obj*, r_list_cbegin, list_equal_na_equal); } #undef VEC_IDENTIFY_RUNS // ----------------------------------------------------------------------------- -static inline int vec_identify_runs_col(SEXP x, - int id, - struct df_short_circuit_info* p_info, - int* p_out); - -static -int df_identify_runs(SEXP x, R_len_t size, int* p_out) { - int nprot = 0; +static inline +int df_identify_runs(r_obj* x, r_ssize size, int* v_out) { + int n_prot = 0; - const SEXP* p_x = VECTOR_PTR_RO(x); + r_obj* const* v_x = r_list_cbegin(x); struct df_short_circuit_info info = new_df_short_circuit_info(size, false); - PROTECT_DF_SHORT_CIRCUIT_INFO(&info, &nprot); + PROTECT_DF_SHORT_CIRCUIT_INFO(&info, &n_prot); int id = 1; - R_len_t n_col = Rf_length(x); + r_ssize n_col = r_length(x); // Define 0 column case to be a single run if (n_col == 0) { - r_p_int_fill(p_out, id, size); - UNPROTECT(nprot); + r_p_int_fill(v_out, id, size); + FREE(n_prot); return id; } // Handle first case - p_out[0] = id; + v_out[0] = id; info.p_row_known[0] = true; --info.remaining; // Compute non-sequential run IDs - for (R_len_t i = 0; i < n_col; ++i) { - SEXP col = p_x[i]; + for (r_ssize i = 0; i < n_col; ++i) { + r_obj* col = v_x[i]; - id = vec_identify_runs_col(col, id, &info, p_out); + id = vec_identify_runs_col(col, id, &info, v_out); // All values are unique if (info.remaining == 0) { @@ -316,106 +289,77 @@ int df_identify_runs(SEXP x, R_len_t size, int* p_out) { } id = 1; - int previous = p_out[0]; + int previous = v_out[0]; // Overwrite with sequential IDs - for (R_len_t i = 1; i < size; ++i) { - const int current = p_out[i]; + for (r_ssize i = 1; i < size; ++i) { + const int current = v_out[i]; if (current != previous) { ++id; previous = current; } - p_out[i] = id; + v_out[i] = id; } - UNPROTECT(nprot); + FREE(n_prot); return id; } // ----------------------------------------------------------------------------- -static int lgl_identify_runs_col(SEXP x, - int id, - struct df_short_circuit_info* p_info, - int* p_out); -static int int_identify_runs_col(SEXP x, - int id, - struct df_short_circuit_info* p_info, - int* p_out); -static int dbl_identify_runs_col(SEXP x, - int id, - struct df_short_circuit_info* p_info, - int* p_out); -static int cpl_identify_runs_col(SEXP x, - int id, - struct df_short_circuit_info* p_info, - int* p_out); -static int chr_identify_runs_col(SEXP x, - int id, - struct df_short_circuit_info* p_info, - int* p_out); -static int raw_identify_runs_col(SEXP x, - int id, - struct df_short_circuit_info* p_info, - int* p_out); -static int list_identify_runs_col(SEXP x, - int id, - struct df_short_circuit_info* p_info, - int* p_out); - static inline -int vec_identify_runs_col(SEXP x, +int vec_identify_runs_col(r_obj* x, int id, struct df_short_circuit_info* p_info, - int* p_out) { + int* v_out) { switch (vec_proxy_typeof(x)) { - case VCTRS_TYPE_logical: return lgl_identify_runs_col(x, id, p_info, p_out); - case VCTRS_TYPE_integer: return int_identify_runs_col(x, id, p_info, p_out); - case VCTRS_TYPE_double: return dbl_identify_runs_col(x, id, p_info, p_out); - case VCTRS_TYPE_complex: return cpl_identify_runs_col(x, id, p_info, p_out); - case VCTRS_TYPE_character: return chr_identify_runs_col(x, id, p_info, p_out); - case VCTRS_TYPE_raw: return raw_identify_runs_col(x, id, p_info, p_out); - case VCTRS_TYPE_list: return list_identify_runs_col(x, id, p_info, p_out); + case VCTRS_TYPE_logical: return lgl_identify_runs_col(x, id, p_info, v_out); + case VCTRS_TYPE_integer: return int_identify_runs_col(x, id, p_info, v_out); + case VCTRS_TYPE_double: return dbl_identify_runs_col(x, id, p_info, v_out); + case VCTRS_TYPE_complex: return cpl_identify_runs_col(x, id, p_info, v_out); + case VCTRS_TYPE_character: return chr_identify_runs_col(x, id, p_info, v_out); + case VCTRS_TYPE_raw: return raw_identify_runs_col(x, id, p_info, v_out); + case VCTRS_TYPE_list: return list_identify_runs_col(x, id, p_info, v_out); case VCTRS_TYPE_dataframe: r_stop_internal("Data frame columns should be flattened."); - case VCTRS_TYPE_scalar: Rf_errorcall(R_NilValue, "Can't compare scalars with `vec_identify_runs()`"); - default: Rf_error("Unimplemented type in `vec_identify_runs()`"); + case VCTRS_TYPE_scalar: r_abort("Can't compare scalars."); + default: r_abort("Unimplemented type."); } } // ----------------------------------------------------------------------------- -#define VEC_IDENTIFY_RUNS_COL(CTYPE, CONST_DEREF, EQUAL_NA_EQUAL) { \ - const CTYPE* p_x = CONST_DEREF(x); \ +#define VEC_IDENTIFY_RUNS_COL(CTYPE, CBEGIN, EQUAL_NA_EQUAL) { \ + CTYPE const* v_x = CBEGIN(x); \ \ /* First row is always known, so `run_val` and `run_id` */ \ /* will always be overwritten immediately below. */ \ /* But for gcc11 we have to initialize these variables. */ \ - CTYPE run_val = p_x[0]; \ + CTYPE run_val = v_x[0]; \ int run_id = 0; \ \ - for (R_len_t i = 0; i < p_info->size; ++i) { \ + for (r_ssize i = 0; i < p_info->size; ++i) { \ /* Start of new run */ \ if (p_info->p_row_known[i]) { \ - run_val = p_x[i]; \ - run_id = p_out[i]; \ + run_val = v_x[i]; \ + run_id = v_out[i]; \ continue; \ } \ \ - const CTYPE elt = p_x[i]; \ + CTYPE const elt = v_x[i]; \ const int eq = EQUAL_NA_EQUAL(elt, run_val); \ \ /* Update ID of identical values */ \ if (eq != 0) { \ - p_out[i] = run_id; \ + v_out[i] = run_id; \ continue; \ } \ \ ++id; \ run_val = elt; \ run_id = id; \ - p_out[i] = id; \ + v_out[i] = id; \ \ /* This is a run change, so don't check this row again */ \ p_info->p_row_known[i] = true; \ @@ -429,54 +373,54 @@ int vec_identify_runs_col(SEXP x, return id; \ } -static -int lgl_identify_runs_col(SEXP x, +static inline +int lgl_identify_runs_col(r_obj* x, int id, struct df_short_circuit_info* p_info, - int* p_out) { - VEC_IDENTIFY_RUNS_COL(int, LOGICAL_RO, lgl_equal_na_equal); + int* v_out) { + VEC_IDENTIFY_RUNS_COL(int, r_lgl_cbegin, lgl_equal_na_equal); } -static -int int_identify_runs_col(SEXP x, +static inline +int int_identify_runs_col(r_obj* x, int id, struct df_short_circuit_info* p_info, - int* p_out) { - VEC_IDENTIFY_RUNS_COL(int, INTEGER_RO, int_equal_na_equal); + int* v_out) { + VEC_IDENTIFY_RUNS_COL(int, r_int_cbegin, int_equal_na_equal); } -static -int dbl_identify_runs_col(SEXP x, +static inline +int dbl_identify_runs_col(r_obj* x, int id, struct df_short_circuit_info* p_info, - int* p_out) { - VEC_IDENTIFY_RUNS_COL(double, REAL_RO, dbl_equal_na_equal); + int* v_out) { + VEC_IDENTIFY_RUNS_COL(double, r_dbl_cbegin, dbl_equal_na_equal); } -static -int cpl_identify_runs_col(SEXP x, +static inline +int cpl_identify_runs_col(r_obj* x, int id, struct df_short_circuit_info* p_info, - int* p_out) { - VEC_IDENTIFY_RUNS_COL(Rcomplex, COMPLEX_RO, cpl_equal_na_equal); + int* v_out) { + VEC_IDENTIFY_RUNS_COL(Rcomplex, r_cpl_cbegin, cpl_equal_na_equal); } -static -int chr_identify_runs_col(SEXP x, +static inline +int chr_identify_runs_col(r_obj* x, int id, struct df_short_circuit_info* p_info, - int* p_out) { - VEC_IDENTIFY_RUNS_COL(SEXP, STRING_PTR_RO, chr_equal_na_equal); + int* v_out) { + VEC_IDENTIFY_RUNS_COL(r_obj*, r_chr_cbegin, chr_equal_na_equal); } -static -int raw_identify_runs_col(SEXP x, - R_len_t id, +static inline +int raw_identify_runs_col(r_obj* x, + int id, struct df_short_circuit_info* p_info, - int* p_out) { - VEC_IDENTIFY_RUNS_COL(Rbyte, RAW_RO, raw_equal_na_equal); + int* v_out) { + VEC_IDENTIFY_RUNS_COL(Rbyte, r_raw_cbegin, raw_equal_na_equal); } -static -int list_identify_runs_col(SEXP x, +static inline +int list_identify_runs_col(r_obj* x, int id, struct df_short_circuit_info* p_info, - int* p_out) { - VEC_IDENTIFY_RUNS_COL(SEXP, VECTOR_PTR_RO, list_equal_na_equal); + int* v_out) { + VEC_IDENTIFY_RUNS_COL(r_obj*, r_list_cbegin, list_equal_na_equal); } #undef VEC_IDENTIFY_RUNS_COL diff --git a/src/runs.h b/src/runs.h new file mode 100644 index 000000000..da1ce3921 --- /dev/null +++ b/src/runs.h @@ -0,0 +1,8 @@ +#ifndef VCTRS_RUNS_H +#define VCTRS_RUNS_H + +#include "vctrs-core.h" + +r_obj* vec_identify_runs(r_obj* x); + +#endif diff --git a/src/vctrs.h b/src/vctrs.h index 8324458dc..6abe7faae 100644 --- a/src/vctrs.h +++ b/src/vctrs.h @@ -44,6 +44,7 @@ bool vec_is_unspecified(SEXP x); #include "ptype.h" #include "ptype2-dispatch.h" #include "ptype2.h" +#include "runs.h" #include "shape.h" #include "size-common.h" #include "size.h" @@ -82,7 +83,6 @@ bool vec_is_unspecified(SEXP x); SEXP vec_names(SEXP x); SEXP vec_proxy_names(SEXP x); SEXP vec_group_loc(SEXP x); -SEXP vec_identify_runs(SEXP x); SEXP vec_match_params(SEXP needles, SEXP haystack, bool na_equal, diff --git a/tests/testthat/_snaps/runs.md b/tests/testthat/_snaps/runs.md new file mode 100644 index 000000000..064a46ff8 --- /dev/null +++ b/tests/testthat/_snaps/runs.md @@ -0,0 +1,48 @@ +# vec_locate_runs() validates `start` + + Code + vec_locate_runs(1, start = "x") + Condition + Error in `vec_locate_runs()`: + ! `start` must be `TRUE` or `FALSE`. + +--- + + Code + vec_locate_runs(1, start = NA) + Condition + Error in `vec_locate_runs()`: + ! `start` must be `TRUE` or `FALSE`. + +--- + + Code + vec_locate_runs(1, start = c(TRUE, TRUE)) + Condition + Error in `vec_locate_runs()`: + ! `start` must be `TRUE` or `FALSE`. + +# vec_detect_runs() validates `start` + + Code + vec_detect_runs(1, start = "x") + Condition + Error in `vec_detect_runs()`: + ! `start` must be `TRUE` or `FALSE`. + +--- + + Code + vec_detect_runs(1, start = NA) + Condition + Error in `vec_detect_runs()`: + ! `start` must be `TRUE` or `FALSE`. + +--- + + Code + vec_detect_runs(1, start = c(TRUE, TRUE)) + Condition + Error in `vec_detect_runs()`: + ! `start` must be `TRUE` or `FALSE`. + diff --git a/tests/testthat/test-runs.R b/tests/testthat/test-runs.R index ef3830981..9badc0f2d 100644 --- a/tests/testthat/test-runs.R +++ b/tests/testthat/test-runs.R @@ -108,9 +108,15 @@ test_that("vec_locate_runs() works with size zero input", { }) test_that("vec_locate_runs() validates `start`", { - expect_error(vec_locate_runs(1, start = "x"), "single `TRUE` or `FALSE`") - expect_error(vec_locate_runs(1, start = NA), "single `TRUE` or `FALSE`") - expect_error(vec_locate_runs(1, start = c(TRUE, TRUE)), "single `TRUE` or `FALSE`") + expect_snapshot(error = TRUE, { + vec_locate_runs(1, start = "x") + }) + expect_snapshot(error = TRUE, { + vec_locate_runs(1, start = NA) + }) + expect_snapshot(error = TRUE, { + vec_locate_runs(1, start = c(TRUE, TRUE)) + }) }) # vec_detect_runs -------------------------------------------------------------- @@ -135,7 +141,13 @@ test_that("vec_detect_runs() works with size zero input", { }) test_that("vec_detect_runs() validates `start`", { - expect_error(vec_detect_runs(1, start = "x"), "single `TRUE` or `FALSE`") - expect_error(vec_detect_runs(1, start = NA), "single `TRUE` or `FALSE`") - expect_error(vec_detect_runs(1, start = c(TRUE, TRUE)), "single `TRUE` or `FALSE`") + expect_snapshot(error = TRUE, { + vec_detect_runs(1, start = "x") + }) + expect_snapshot(error = TRUE, { + vec_detect_runs(1, start = NA) + }) + expect_snapshot(error = TRUE, { + vec_detect_runs(1, start = c(TRUE, TRUE)) + }) }) From 2d9410ee175bb7370de4969e3221686029ce988b Mon Sep 17 00:00:00 2001 From: Davis Vaughan Date: Tue, 27 Sep 2022 11:02:20 -0400 Subject: [PATCH 112/312] Performance updates to runs helpers (#1683) * Use branchless code in atomic paths of runs functions * Share memory in `vec_locate_runs()` --- src/runs.c | 82 +++++++++++++++++++++++------------------------------- 1 file changed, 35 insertions(+), 47 deletions(-) diff --git a/src/runs.c b/src/runs.c index d16390b03..4bcadb981 100644 --- a/src/runs.c +++ b/src/runs.c @@ -17,62 +17,61 @@ r_obj* vec_locate_runs(r_obj* x, bool start) { const r_ssize size = r_length(id); const int n = r_int_get(r_attrib_get(id, syms_n), 0); - r_obj* out = KEEP(r_new_integer(n)); + // Share memory with `id`. + // `vec_locate_run_starts/ends()` are carefully written to avoid + // overwrite issues. + r_obj* out = id; int* v_out = r_int_begin(out); - if (n == 0) { - FREE(2); - return out; - } - if (start) { vec_locate_run_starts(v_id, size, v_out); } else { vec_locate_run_ends(v_id, size, v_out); } + // Resize shared memory to output size and clear attribute + out = KEEP(r_int_resize(out, n)); + r_attrib_poke(out, syms_n, r_null); + FREE(2); return out; } static inline void vec_locate_run_starts(const int* v_id, r_ssize size, int* v_out) { + if (size == 0) { + return; + } + r_ssize loc = 0; + int ref = v_id[0]; // Handle first case - int ref = v_id[0]; v_out[loc] = 1; ++loc; for (r_ssize i = 1; i < size; ++i) { const int elt = v_id[i]; - - if (elt == ref) { - continue; - } - - ref = elt; v_out[loc] = i + 1; - ++loc; + loc += elt != ref; + ref = elt; } } static inline void vec_locate_run_ends(const int* v_id, r_ssize size, int* v_out) { - r_ssize loc = 0; + if (size == 0) { + return; + } + r_ssize loc = 0; int ref = v_id[0]; for (r_ssize i = 1; i < size; ++i) { const int elt = v_id[i]; - - if (elt == ref) { - continue; - } - - ref = elt; v_out[loc] = i; - ++loc; + loc += elt != ref; + ref = elt; } // Handle last case @@ -95,12 +94,6 @@ r_obj* vec_detect_runs(r_obj* x, bool start) { r_obj* out = KEEP(r_new_logical(size)); int* v_out = r_lgl_begin(out); - memset(v_out, 0, size * sizeof(int)); - - if (size == 0) { - FREE(2); - return out; - } if (start) { vec_detect_run_starts(v_id, size, v_out); @@ -114,35 +107,34 @@ r_obj* vec_detect_runs(r_obj* x, bool start) { static inline void vec_detect_run_starts(const int* v_id, r_ssize size, int* v_out) { - // Handle first case + if (size == 0) { + return; + } + int ref = v_id[0]; + + // Handle first case v_out[0] = 1; for (r_ssize i = 1; i < size; ++i) { const int elt = v_id[i]; - - if (elt == ref) { - continue; - } - + v_out[i] = elt != ref; ref = elt; - v_out[i] = 1; } } static inline void vec_detect_run_ends(const int* v_id, r_ssize size, int* v_out) { + if (size == 0) { + return; + } + int ref = v_id[0]; for (r_ssize i = 1; i < size; ++i) { const int elt = v_id[i]; - - if (elt == ref) { - continue; - } - + v_out[i - 1] = elt != ref; ref = elt; - v_out[i - 1] = 1; } // Handle last case @@ -207,13 +199,9 @@ r_obj* vec_identify_runs(r_obj* x) { \ for (r_ssize i = 1; i < size; ++i) { \ CTYPE const elt = v_x[i]; \ - \ - if (EQUAL_NA_EQUAL(elt, ref) == 0) { \ - ++id; \ - ref = elt; \ - } \ - \ + id += !EQUAL_NA_EQUAL(elt, ref); \ v_out[i] = id; \ + ref = elt; \ } \ \ return id; \ From 022f6595af3d9757dad1be0e7e9c8bc14dd5910f Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Wed, 28 Sep 2022 14:26:49 +0200 Subject: [PATCH 113/312] Remove broken link --- R/names.R | 4 ---- man/vec_as_names.Rd | 3 --- 2 files changed, 7 deletions(-) diff --git a/R/names.R b/R/names.R index 364e00e7b..a5bf49b06 100644 --- a/R/names.R +++ b/R/names.R @@ -141,10 +141,6 @@ #' #' @seealso [rlang::names2()] returns the names of an object, after #' making them `minimal`. -#' -#' The [Names attribute](https://principles.tidyverse.org/names-attribute.html) -#' section in the "tidyverse package development principles". -#' #' @examples #' # By default, `vec_as_names()` returns minimal names: #' vec_as_names(c(NA, NA, "foo")) diff --git a/man/vec_as_names.Rd b/man/vec_as_names.Rd index 64c5df84c..b590fe2f7 100644 --- a/man/vec_as_names.Rd +++ b/man/vec_as_names.Rd @@ -171,7 +171,4 @@ vec_as_names(c("_foo", "+"), repair = "universal") \seealso{ \code{\link[rlang:names2]{rlang::names2()}} returns the names of an object, after making them \code{minimal}. - -The \href{https://principles.tidyverse.org/names-attribute.html}{Names attribute} -section in the "tidyverse package development principles". } From d4d4398145ae361f75eb0c073ba3c3c47053a92d Mon Sep 17 00:00:00 2001 From: Davis Vaughan Date: Wed, 28 Sep 2022 10:18:08 -0400 Subject: [PATCH 114/312] Improve performance of list-of implementation (#1686) * Improve performance of list-of implementation * NEWS bullet * NEWS bullet * Remove micro optimization --- NEWS.md | 5 +++++ R/type-list-of.R | 47 ++++++++++++++++++++++++++++++----------------- 2 files changed, 35 insertions(+), 17 deletions(-) diff --git a/NEWS.md b/NEWS.md index f65628aab..dae319df2 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,5 +1,10 @@ # vctrs (development version) +* Improved the performance of list-of common type methods (#1686). + +* The list-of method for `as_list_of()` now places the optional `.ptype` + argument after the `...` (#1686). + * `vec_rbind()` now applies `base::c()` fallback recursively within packed df-cols (#1331, #1462, #1640). diff --git a/R/type-list-of.R b/R/type-list-of.R index fb6960e7b..6ee82b2ca 100644 --- a/R/type-list-of.R +++ b/R/type-list-of.R @@ -20,15 +20,7 @@ #' vec_c(list_of(1, 2), list_of(FALSE, TRUE)) list_of <- function(..., .ptype = NULL) { args <- list2(...) - - ptype <- vec_ptype_common(!!!args, .ptype = .ptype) - if (is.null(ptype)) { - abort("Could not find common type for elements of `x`.") - } - - args <- vec_cast_common(!!!args, .to = ptype) - - new_list_of(args, ptype) + list_as_list_of(args, ptype = .ptype) } #' @export @@ -38,9 +30,10 @@ as_list_of <- function(x, ...) { } #' @export -as_list_of.vctrs_list_of <- function(x, .ptype = NULL, ...) { +as_list_of.vctrs_list_of <- function(x, ..., .ptype = NULL) { if (!is.null(.ptype)) { - list_of(!!!x, .ptype = .ptype) + x <- unclass(x) + list_as_list_of(x, ptype = .ptype) } else { x } @@ -48,7 +41,7 @@ as_list_of.vctrs_list_of <- function(x, .ptype = NULL, ...) { #' @export as_list_of.list <- function(x, ..., .ptype = NULL) { - list_of(!!!x, .ptype = .ptype) + list_as_list_of(x, ptype = .ptype) } #' Create list_of subclass @@ -68,6 +61,10 @@ new_list_of <- function(x = list(), ptype = logical(), ..., class = character()) abort("`ptype` must have size 0.") } + new_list_of0(x = x, ptype = ptype, ..., class = class) +} + +new_list_of0 <- function(x, ptype, ..., class = character()) { new_vctr(x, ..., ptype = ptype, class = c(class, "vctrs_list_of")) } @@ -157,7 +154,7 @@ as.character.vctrs_list_of <- function(x, ...) { `[<-.vctrs_list_of` <- function(x, i, value) { wrapped_type <- attr(x, "ptype") value <- map(value, vec_cast, to = wrapped_type) - value <- new_list_of(value, ptype = attr(x, "ptype")) + value <- new_list_of0(value, ptype = wrapped_type) NextMethod() } #' @export @@ -192,8 +189,8 @@ vec_ptype2.vctrs_list_of <- function(x, y, ..., x_arg = "", y_arg = "") { #' @method vec_ptype2.vctrs_list_of vctrs_list_of #' @export vec_ptype2.vctrs_list_of.vctrs_list_of <- function(x, y, ...) { - type <- vec_ptype2(attr(x, "ptype"), attr(y, "ptype")) - new_list_of(list(), type) + ptype <- vec_ptype2(attr(x, "ptype"), attr(y, "ptype")) + new_list_of0(x = list(), ptype = ptype) } #' @rdname list_of @@ -206,9 +203,25 @@ vec_cast.vctrs_list_of <- function(x, to, ...) { #' @export #' @method vec_cast.vctrs_list_of vctrs_list_of -vec_cast.vctrs_list_of.vctrs_list_of <-function(x, to, ...) { +vec_cast.vctrs_list_of.vctrs_list_of <- function(x, to, ...) { # Casting list to list_of will warn/err if the cast is lossy, # but the locations refer to the inner vectors, # and the cast fails if all (vector) elements in a single (list) element - as_list_of(x, .ptype = attr(to, "ptype")) + x <- unclass(x) + ptype <- attr(to, "ptype") + list_as_list_of(x, ptype = ptype) +} + +# Helpers ----------------------------------------------------------------- + +list_as_list_of <- function(x, ptype = NULL, error_call = caller_env()) { + ptype <- vec_ptype_common(!!!x, .ptype = ptype, .call = error_call) + + if (is.null(ptype)) { + abort("Can't find common type for elements of `x`.", call = error_call) + } + + x <- vec_cast_common(!!!x, .to = ptype, .call = error_call) + + new_list_of0(x = x, ptype = ptype) } From cdeaccbd7dd1d16f36158c9003cd13700eb69dd5 Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Wed, 28 Sep 2022 16:30:55 +0200 Subject: [PATCH 115/312] Update `s3_register()` from the rlang compat Closes #1418 --- R/register-s3.R | 30 +++++++++++++++++++++--------- 1 file changed, 21 insertions(+), 9 deletions(-) diff --git a/R/register-s3.R b/R/register-s3.R index 9eae7c1be..4407613dd 100644 --- a/R/register-s3.R +++ b/R/register-s3.R @@ -74,7 +74,7 @@ s3_register <- function(generic, class, method = NULL) { caller } } - get_method <- function(method, env) { + get_method <- function(method) { if (is.null(method)) { get(paste0(generic, ".", class), envir = get_method_env()) } else { @@ -95,19 +95,31 @@ s3_register <- function(generic, class, method = NULL) { if (exists(generic, envir)) { registerS3method(generic, class, method_fn, envir = envir) } else if (identical(Sys.getenv("NOT_CRAN"), "true")) { - warning(sprintf( - "Can't find generic `%s` in package %s to register S3 method.", - generic, - package + warn <- .rlang_s3_register_compat("warn") + + warn(c( + sprintf( + "Can't find generic `%s` in package %s to register S3 method.", + generic, + package + ), + "i" = "This message is only shown to developers using devtools.", + "i" = sprintf("Do you need to update %s to the latest version?", package) )) } } # Always register hook in case package is later unloaded & reloaded - setHook(packageEvent(package, "onLoad"), register) - - # Avoid registration failures during loading (pkgload or regular) - if (isNamespaceLoaded(package)) { + setHook(packageEvent(package, "onLoad"), function(...) { + register() + }) + + # Avoid registration failures during loading (pkgload or regular). + # Check that environment is locked because the registering package + # might be a dependency of the package that exports the generic. In + # that case, the exports (and the generic) might not be populated + # yet (#1225). + if (isNamespaceLoaded(package) && environmentIsLocked(asNamespace(package))) { register() } From af4652b3851f93790500972e474c5413dc4ee0e4 Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Wed, 28 Sep 2022 17:12:15 +0200 Subject: [PATCH 116/312] Add missing `s3_register()` helper --- R/register-s3.R | 51 +++++++++++++++++++++++++++++++++++++++++++++++++ 1 file changed, 51 insertions(+) diff --git a/R/register-s3.R b/R/register-s3.R index 4407613dd..15d28a908 100644 --- a/R/register-s3.R +++ b/R/register-s3.R @@ -125,6 +125,57 @@ s3_register <- function(generic, class, method = NULL) { invisible() } + +.rlang_s3_register_compat <- function(fn, try_rlang = TRUE) { + # Compats that behave the same independently of rlang's presence + out <- switch( + fn, + is_installed = return(function(pkg) requireNamespace(pkg, quietly = TRUE)) + ) + + # Only use rlang if it is fully loaded (#1482) + if (try_rlang && + requireNamespace("rlang", quietly = TRUE) && + environmentIsLocked(asNamespace("rlang"))) { + switch( + fn, + is_interactive = return(rlang::is_interactive) + ) + + # Make sure rlang knows about "x" and "i" bullets + if (utils::packageVersion("rlang") >= "0.4.2") { + switch( + fn, + abort = return(rlang::abort), + warn = return((rlang::warn)), + inform = return(rlang::inform) + ) + } + } + + # Fall back to base compats + + is_interactive_compat <- function() { + opt <- getOption("rlang_interactive") + if (!is.null(opt)) { + opt + } else { + interactive() + } + } + + format_msg <- function(x) paste(x, collapse = "\n") + switch( + fn, + is_interactive = return(is_interactive_compat), + abort = return(function(msg) stop(format_msg(msg), call. = FALSE)), + warn = return(function(msg) warning(format_msg(msg), call. = FALSE)), + inform = return(function(msg) message(format_msg(msg))) + ) + + stop(sprintf("Internal error in rlang shims: Unknown function `%s()`.", fn)) +} + on_load({ s3_register <- replace_from("s3_register", "rlang") }) From 3b271604e6330853f73ebc91529da177a22cbaaa Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Wed, 28 Sep 2022 17:25:24 +0200 Subject: [PATCH 117/312] Update `s3_register()` --- R/register-s3.R | 7 ++++++- 1 file changed, 6 insertions(+), 1 deletion(-) diff --git a/R/register-s3.R b/R/register-s3.R index 15d28a908..4fa0762f0 100644 --- a/R/register-s3.R +++ b/R/register-s3.R @@ -114,12 +114,17 @@ s3_register <- function(generic, class, method = NULL) { register() }) + # For compatibility with R < 4.0 where base isn't locked + is_sealed <- function(pkg) { + identical(pkg, "base") || environmentIsLocked(asNamespace(pkg)) + } + # Avoid registration failures during loading (pkgload or regular). # Check that environment is locked because the registering package # might be a dependency of the package that exports the generic. In # that case, the exports (and the generic) might not be populated # yet (#1225). - if (isNamespaceLoaded(package) && environmentIsLocked(asNamespace(package))) { + if (isNamespaceLoaded(package) && is_sealed(package)) { register() } From c0bf5ab90f5a5ca45d73ca1a9727e9b4d0b25768 Mon Sep 17 00:00:00 2001 From: Davis Vaughan Date: Wed, 28 Sep 2022 11:35:12 -0400 Subject: [PATCH 118/312] Add `.call` to `vec_c()` (#1660) * Pass error call through `vec_c()` internals * Pass error call through usage of c fallback in `vec_rbind()` * Pass null error call through `list_unchop()` This will be improved in a follow up PR * Pass null error call through additional C level usage of `vec_c()` * NEWS bullet * Move from `.call` to `.error_call` --- NEWS.md | 2 + R/c.R | 12 +++-- man/howto-faq-coercion.Rd | 4 +- man/theory-faq-coercion.Rd | 2 +- man/vec_c.Rd | 8 +++- src/bind.c | 9 ++-- src/c-unchop.c | 9 ++-- src/c.c | 71 ++++++++++++++++++----------- src/c.h | 11 +++-- src/decl/bind-decl.h | 3 +- src/decl/c-decl.h | 2 +- src/interval.c | 6 ++- src/match-joint.c | 2 +- src/rlang/globals.c | 1 + src/rlang/globals.h | 1 + src/type-factor.c | 3 +- tests/testthat/_snaps/bind.md | 4 +- tests/testthat/_snaps/c.md | 59 +++++++++++++++++++++--- tests/testthat/_snaps/slice-chop.md | 2 +- tests/testthat/test-c.R | 20 ++++++++ 20 files changed, 169 insertions(+), 62 deletions(-) diff --git a/NEWS.md b/NEWS.md index dae319df2..e79f8b8d6 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,5 +1,7 @@ # vctrs (development version) +* `vec_c()` has gained an `.error_call` argument (#1641). + * Improved the performance of list-of common type methods (#1686). * The list-of method for `as_list_of()` now places the optional `.ptype` diff --git a/R/c.R b/R/c.R index 28a4d36ab..9afda2559 100644 --- a/R/c.R +++ b/R/c.R @@ -23,6 +23,11 @@ #' back to `base::c()` if there exists a `c()` method implemented for #' this class hierarchy. #' +#' @inheritParams rlang::args_error_context +#' @inheritParams vec_ptype_show +#' @inheritParams name_spec +#' @inheritParams vec_as_names +#' #' @param ... Vectors to coerce. #' @param .name_repair How to repair names, see `repair` options in #' [vec_as_names()]. @@ -33,9 +38,7 @@ #' (inner names) or if the arguments are named (outer names). If both #' inner and outer names are present, an error is thrown unless a #' `.name_spec` is provided. -#' @inheritParams vec_ptype_show -#' @inheritParams name_spec -#' @inheritParams vec_as_names +#' #' @seealso [vec_cbind()]/[vec_rbind()] for combining data frames by rows #' or columns. #' @export @@ -65,7 +68,8 @@ vec_c <- function(..., .ptype = NULL, .name_spec = NULL, - .name_repair = c("minimal", "unique", "check_unique", "universal")) { + .name_repair = c("minimal", "unique", "check_unique", "universal"), + .error_call = current_env()) { .External2(ffi_vec_c, .ptype, .name_spec, .name_repair) } vec_c <- fn_inline_formals(vec_c, ".name_repair") diff --git a/man/howto-faq-coercion.Rd b/man/howto-faq-coercion.Rd index a03d53d08..7ca8cdecc 100644 --- a/man/howto-faq-coercion.Rd +++ b/man/howto-faq-coercion.Rd @@ -256,10 +256,10 @@ doesn’t know how to combine natural with the richer integer and double types: \if{html}{\out{
}}\preformatted{vec_c(new_natural(1), 10L) -#> Error: +#> Error in `vec_c()`: #> ! Can't convert to . vec_c(1.5, new_natural(1)) -#> Error: +#> Error in `vec_c()`: #> ! Can't convert to . }\if{html}{\out{
}} diff --git a/man/theory-faq-coercion.Rd b/man/theory-faq-coercion.Rd index 5904b06f5..62273f4a9 100644 --- a/man/theory-faq-coercion.Rd +++ b/man/theory-faq-coercion.Rd @@ -26,7 +26,7 @@ functions that use the split-apply-combine strategy. For example: #> [1] 1 1 vec_c("a", 1) -#> Error: +#> Error in `vec_c()`: #> ! Can't combine `..1` and `..2` . vec_rbind( diff --git a/man/vec_c.Rd b/man/vec_c.Rd index b455eec38..5ac0e77a6 100644 --- a/man/vec_c.Rd +++ b/man/vec_c.Rd @@ -8,7 +8,8 @@ vec_c( ..., .ptype = NULL, .name_spec = NULL, - .name_repair = c("minimal", "unique", "check_unique", "universal") + .name_repair = c("minimal", "unique", "check_unique", "universal"), + .error_call = current_env() ) } \arguments{ @@ -41,6 +42,11 @@ See the \link[=name_spec]{name specification topic}.} \item{.name_repair}{How to repair names, see \code{repair} options in \code{\link[=vec_as_names]{vec_as_names()}}.} + +\item{.error_call}{The execution environment of a currently +running function, e.g. \code{caller_env()}. The function will be +mentioned in error messages as the source of the error. See the +\code{call} argument of \code{\link[rlang:abort]{abort()}} for more information.} } \value{ A vector with class given by \code{.ptype}, and length equal to the diff --git a/src/bind.c b/src/bind.c index 55488f42d..017a64be9 100644 --- a/src/bind.c +++ b/src/bind.c @@ -249,7 +249,7 @@ r_obj* vec_rbind(r_obj* xs, // Not optimal. Happens after the fallback columns have been // assigned already, ideally they should be ignored. - df_c_fallback(out, ptype, xs, n_rows, name_spec, name_repair); + df_c_fallback(out, ptype, xs, n_rows, name_spec, name_repair, error_call); out = vec_restore_recurse(out, ptype, VCTRS_OWNED_true); @@ -264,7 +264,8 @@ void df_c_fallback(r_obj* out, r_obj* xs, r_ssize n_rows, r_obj* name_spec, - struct name_repair_opts* name_repair) { + struct name_repair_opts* name_repair, + struct r_lazy error_call) { r_ssize n_cols = r_length(out); if (r_length(ptype) != n_cols || @@ -280,11 +281,11 @@ void df_c_fallback(r_obj* out, if (is_data_frame(ptype_col) && df_needs_fallback(ptype_col)) { r_obj* xs_col = KEEP(list_pluck(xs, i)); r_obj* out_col = r_list_get(out, i); - df_c_fallback(out_col, ptype_col, xs_col, n_rows, name_spec, name_repair); + df_c_fallback(out_col, ptype_col, xs_col, n_rows, name_spec, name_repair, error_call); FREE(1); } else if (vec_is_common_class_fallback(ptype_col)) { r_obj* xs_col = KEEP(list_pluck(xs, i)); - r_obj* out_col = vec_c_fallback(ptype_col, xs_col, name_spec, name_repair); + r_obj* out_col = vec_c_fallback(ptype_col, xs_col, name_spec, name_repair, error_call); r_list_poke(out, i, out_col); if (vec_size(out_col) != n_rows) { diff --git a/src/c-unchop.c b/src/c-unchop.c index a586a9d71..a51b54aec 100644 --- a/src/c-unchop.c +++ b/src/c-unchop.c @@ -20,7 +20,7 @@ r_obj* list_unchop(r_obj* xs, } if (indices == r_null) { - return vec_c(xs, ptype, name_spec, name_repair); + return vec_c(xs, ptype, name_spec, name_repair, r_lazy_null); } r_ssize xs_size = vec_size(xs); @@ -202,9 +202,9 @@ r_obj* list_unchop_fallback(r_obj* ptype, r_obj* out = r_null; if (homogeneous) { - out = KEEP(vec_c_fallback_invoke(x, name_spec)); + out = KEEP(vec_c_fallback_invoke(x, name_spec, r_lazy_null)); } else { - out = KEEP(vec_c_fallback(ptype, x, name_spec, name_repair)); + out = KEEP(vec_c_fallback(ptype, x, name_spec, name_repair, r_lazy_null)); } const struct name_repair_opts name_repair_opts = { @@ -216,7 +216,8 @@ r_obj* list_unchop_fallback(r_obj* ptype, indices, r_globals.empty_int, r_null, - &name_repair_opts + &name_repair_opts, + r_lazy_null )); const int* p_indices = r_int_cbegin(indices); diff --git a/src/c.c b/src/c.c index 84aa79893..b175e10c2 100644 --- a/src/c.c +++ b/src/c.c @@ -4,20 +4,23 @@ r_obj* vec_c(r_obj* xs, r_obj* ptype, r_obj* name_spec, - const struct name_repair_opts* name_repair) { + const struct name_repair_opts* name_repair, + struct r_lazy error_call) { struct fallback_opts opts = { .df = DF_FALLBACK_DEFAULT, .s3 = S3_FALLBACK_true }; - return vec_c_opts(xs, ptype, name_spec, name_repair, &opts); + return vec_c_opts(xs, ptype, name_spec, name_repair, &opts, error_call); } r_obj* vec_c_opts(r_obj* xs, r_obj* ptype, r_obj* name_spec, const struct name_repair_opts* name_repair, - const struct fallback_opts* fallback_opts) { + const struct fallback_opts* fallback_opts, + struct r_lazy error_call) { struct ptype_common_opts ptype_opts = { + .call = error_call, .fallback = *fallback_opts }; @@ -30,13 +33,13 @@ r_obj* vec_c_opts(r_obj* xs, } if (needs_vec_c_fallback(ptype)) { - r_obj* out = vec_c_fallback(ptype, xs, name_spec, name_repair); + r_obj* out = vec_c_fallback(ptype, xs, name_spec, name_repair, error_call); FREE(1); return out; } // FIXME: Needed for dplyr::summarise() which passes a non-fallback ptype if (needs_vec_c_homogeneous_fallback(xs, ptype)) { - r_obj* out = vec_c_fallback_invoke(xs, name_spec); + r_obj* out = vec_c_fallback_invoke(xs, name_spec, error_call); FREE(1); return out; } @@ -97,7 +100,8 @@ r_obj* vec_c_opts(r_obj* xs, const struct vec_assign_opts c_assign_opts = { .recursive = true, .assign_names = assign_names, - .ignore_outer_names = true + .ignore_outer_names = true, + .call = error_call }; for (r_ssize i = 0; i < n; ++i) { @@ -132,6 +136,7 @@ r_obj* vec_c_opts(r_obj* xs, struct cast_opts opts = (struct cast_opts) { .x = x, .to = ptype, + .call = error_call, .fallback = *fallback_opts }; x = KEEP(vec_cast_opts(&opts)); @@ -161,22 +166,24 @@ r_obj* vec_c_opts(r_obj* xs, return out; } -r_obj* ffi_vec_c(r_obj* call, r_obj* op, r_obj* args, r_obj* env) { +r_obj* ffi_vec_c(r_obj* ffi_call, r_obj* op, r_obj* args, r_obj* frame) { args = r_node_cdr(args); - r_obj* xs = KEEP(rlang_env_dots_list(env)); - r_obj* ptype = KEEP(r_eval(r_node_car(args), env)); args = r_node_cdr(args); - r_obj* name_spec = KEEP(r_eval(r_node_car(args), env)); args = r_node_cdr(args); - r_obj* name_repair = KEEP(r_eval(r_node_car(args), env)); + r_obj* xs = KEEP(rlang_env_dots_list(frame)); + r_obj* ptype = KEEP(r_eval(r_node_car(args), frame)); args = r_node_cdr(args); + r_obj* name_spec = KEEP(r_eval(r_node_car(args), frame)); args = r_node_cdr(args); + r_obj* name_repair = KEEP(r_eval(r_node_car(args), frame)); + + struct r_lazy error_call = { .x = syms.dot_error_call, .env = frame }; struct name_repair_opts name_repair_opts = new_name_repair_opts(name_repair, r_lazy_null, false, - r_lazy_null); + error_call); KEEP(name_repair_opts.shelter); - r_obj* out = vec_c(xs, ptype, name_spec, &name_repair_opts); + r_obj* out = vec_c(xs, ptype, name_spec, &name_repair_opts, error_call); FREE(5); return out; @@ -256,15 +263,17 @@ bool class_implements_base_c(r_obj* cls) { r_obj* vec_c_fallback(r_obj* ptype, r_obj* xs, r_obj* name_spec, - const struct name_repair_opts* name_repair) { + const struct name_repair_opts* name_repair, + struct r_lazy error_call) { r_obj* class = KEEP(r_attrib_get(ptype, syms_fallback_class)); bool implements_c = class_implements_base_c(class); FREE(1); if (implements_c) { - return vec_c_fallback_invoke(xs, name_spec); + return vec_c_fallback_invoke(xs, name_spec, error_call); } else { struct ptype_common_opts ptype_opts = { + .call = error_call, .fallback = { .df = DF_FALLBACK_none, .s3 = S3_FALLBACK_false @@ -278,11 +287,18 @@ r_obj* vec_c_fallback(r_obj* ptype, // Suboptimal: Call `vec_c()` again to combine vector with // homogeneous class fallback - return vec_c_opts(xs, r_null, name_spec, name_repair, &ptype_opts.fallback); + return vec_c_opts( + xs, + r_null, + name_spec, + name_repair, + &ptype_opts.fallback, + error_call + ); } } -r_obj* vec_c_fallback_invoke(r_obj* xs, r_obj* name_spec) { +r_obj* vec_c_fallback_invoke(r_obj* xs, r_obj* name_spec, struct r_lazy error_call) { r_obj* x = list_first_non_null(xs, NULL); if (vctrs_debug_verbose) { @@ -292,11 +308,11 @@ r_obj* vec_c_fallback_invoke(r_obj* xs, r_obj* name_spec) { int err_type = vec_c_fallback_validate_args(x, name_spec); if (err_type) { - stop_vec_c_fallback(xs, err_type); + stop_vec_c_fallback(xs, err_type, error_call); } - r_obj* call = KEEP(r_call2(r_sym("base_c_invoke"), xs)); - r_obj* out = r_eval(call, vctrs_ns_env); + r_obj* ffi_call = KEEP(r_call2(r_sym("base_c_invoke"), xs)); + r_obj* out = r_eval(ffi_call, vctrs_ns_env); FREE(1); return out; @@ -311,7 +327,7 @@ int vec_c_fallback_validate_args(r_obj* x, r_obj* name_spec) { } static -void stop_vec_c_fallback(r_obj* xs, int err_type) { +void stop_vec_c_fallback(r_obj* xs, int err_type, struct r_lazy call) { r_obj* common_class = KEEP(r_class(list_first_non_null(xs, NULL))); const char* class_str = r_chr_get_c_string(common_class, 0); @@ -322,9 +338,12 @@ void stop_vec_c_fallback(r_obj* xs, int err_type) { default: msg = "Internal error: Unexpected error type."; break; } - r_abort("%s\n" - "vctrs methods must be implemented for class `%s`.\n" - "See .", - msg, - class_str); + r_abort_lazy_call( + call, + "%s\n" + "vctrs methods must be implemented for class `%s`.\n" + "See .", + msg, + class_str + ); } diff --git a/src/c.h b/src/c.h index dda87f710..f7d7bb749 100644 --- a/src/c.h +++ b/src/c.h @@ -9,19 +9,22 @@ r_obj* vec_c(r_obj* xs, r_obj* ptype, r_obj* name_spec, - const struct name_repair_opts* name_repair); + const struct name_repair_opts* name_repair, + struct r_lazy error_call); r_obj* vec_c_opts(r_obj* xs, r_obj* ptype, r_obj* name_spec, const struct name_repair_opts* name_repair, - const struct fallback_opts* fallback_opts); + const struct fallback_opts* fallback_opts, + struct r_lazy error_call); -r_obj* vec_c_fallback_invoke(r_obj* xs, r_obj* name_spec); +r_obj* vec_c_fallback_invoke(r_obj* xs, r_obj* name_spec, struct r_lazy error_call); r_obj* vec_c_fallback(r_obj* ptype, r_obj* xs, r_obj* name_spec, - const struct name_repair_opts* name_repair); + const struct name_repair_opts* name_repair, + struct r_lazy error_call); bool needs_vec_c_fallback(r_obj* ptype); bool needs_vec_c_homogeneous_fallback(r_obj* xs, r_obj* ptype); diff --git a/src/decl/bind-decl.h b/src/decl/bind-decl.h index d4a8c7cdd..da20ad949 100644 --- a/src/decl/bind-decl.h +++ b/src/decl/bind-decl.h @@ -56,7 +56,8 @@ void df_c_fallback(r_obj* out, r_obj* xs, r_ssize n_rows, r_obj* name_spec, - struct name_repair_opts* name_repair); + struct name_repair_opts* name_repair, + struct r_lazy error_call); static bool df_needs_fallback(r_obj* x); diff --git a/src/decl/c-decl.h b/src/decl/c-decl.h index 51e9bba42..659e7013f 100644 --- a/src/decl/c-decl.h +++ b/src/decl/c-decl.h @@ -5,4 +5,4 @@ static inline int vec_c_fallback_validate_args(r_obj* x, r_obj* name_spec); static -void stop_vec_c_fallback(r_obj* xs, int err_type); +void stop_vec_c_fallback(r_obj* xs, int err_type, struct r_lazy call); diff --git a/src/interval.c b/src/interval.c index 258dee502..9120c7897 100644 --- a/src/interval.c +++ b/src/interval.c @@ -684,7 +684,8 @@ r_obj* vec_interval_complement(r_obj* start, args, ptype, R_NilValue, - &name_repair_opts + &name_repair_opts, + r_lazy_null ), &n_prot); } @@ -697,7 +698,8 @@ r_obj* vec_interval_complement(r_obj* start, args, ptype, R_NilValue, - &name_repair_opts + &name_repair_opts, + r_lazy_null ), &n_prot); } } diff --git a/src/match-joint.c b/src/match-joint.c index aa568d2d5..c4f808092 100644 --- a/src/match-joint.c +++ b/src/match-joint.c @@ -297,7 +297,7 @@ r_obj* vec_joint_proxy_order_dependent(r_obj* x, r_obj* y) { // size of `vec_locate_matches()` input to // `vec_size(x) + vec_size(y) <= INT_MAX` // when foreign columns are used. - r_obj* combined = KEEP(vec_c(out, ptype, r_null, p_no_repair_opts)); + r_obj* combined = KEEP(vec_c(out, ptype, r_null, p_no_repair_opts, r_lazy_null)); // Compute joint order-proxy r_obj* proxy = KEEP(vec_proxy_order(combined)); diff --git a/src/rlang/globals.c b/src/rlang/globals.c index c42e47c72..c18917a9f 100644 --- a/src/rlang/globals.c +++ b/src/rlang/globals.c @@ -83,6 +83,7 @@ void r_init_library_globals_syms() { r_syms.unbound = R_UnboundValue; r_syms.warning = r_sym("warning"); + r_syms.dot_call = r_sym(".call"); r_syms.dot_environment = r_sym(".Environment"); r_syms.dot_fn = r_sym(".fn"); r_syms.dot_x = r_sym(".x"); diff --git a/src/rlang/globals.h b/src/rlang/globals.h index 89faf36dc..c9a0df7bd 100644 --- a/src/rlang/globals.h +++ b/src/rlang/globals.h @@ -50,6 +50,7 @@ struct r_globals_syms { r_obj* class_; r_obj* condition; r_obj* dots; + r_obj* dot_call; r_obj* dot_environment; r_obj* dot_fn; r_obj* dot_x; diff --git a/src/type-factor.c b/src/type-factor.c index 3606e113a..5a380b257 100644 --- a/src/type-factor.c +++ b/src/type-factor.c @@ -77,7 +77,8 @@ static SEXP levels_union(SEXP x, SEXP y) { args, r_globals.empty_chr, R_NilValue, - &name_repair_opts + &name_repair_opts, + r_lazy_null )); SEXP out = vec_unique(xy); diff --git a/tests/testthat/_snaps/bind.md b/tests/testthat/_snaps/bind.md index 1c0d42f2c..433ceaf74 100644 --- a/tests/testthat/_snaps/bind.md +++ b/tests/testthat/_snaps/bind.md @@ -371,7 +371,7 @@ ) Output - Error: + Error in `vec_rbind()`: ! Can't combine `..1` and `..2` . x Some attributes are incompatible. i The author of the class should implement vctrs methods. @@ -386,7 +386,7 @@ ) Output - Error: + Error in `vec_rbind()`: ! Can't combine `..1` and `..2` . # can't zap names when `.names_to` is supplied diff --git a/tests/testthat/_snaps/c.md b/tests/testthat/_snaps/c.md index 90d0691bd..a0e111ad4 100644 --- a/tests/testthat/_snaps/c.md +++ b/tests/testthat/_snaps/c.md @@ -1,9 +1,25 @@ +# common type failure uses error call (#1641) + + Code + vec_c("x", 1, .error_call = call("foo")) + Condition + Error in `foo()`: + ! Can't combine `..1` and `..2` . + +--- + + Code + vec_c("x", .ptype = integer(), .error_call = call("foo")) + Condition + Error in `foo()`: + ! Can't convert to . + # vec_c() includes index in argument tag Code vec_c(df1, df2) Condition - Error: + Error in `vec_c()`: ! Can't combine `..1$x$y$z` and `..2$x$y$z` . --- @@ -11,7 +27,7 @@ Code vec_c(df1, df1, df2) Condition - Error: + Error in `vec_c()`: ! Can't combine `..1$x$y$z` and `..3$x$y$z` . --- @@ -19,7 +35,7 @@ Code vec_c(foo = df1, bar = df2) Condition - Error: + Error in `vec_c()`: ! Can't combine `foo$x$y$z` and `bar$x$y$z` . # vec_c() fails with complex foreign S3 classes @@ -30,7 +46,17 @@ (expect_error(vec_c(x, y), class = "vctrs_error_incompatible_type")) Output - Error: + Error in `vec_c()`: + ! Can't combine `..1` and `..2` . + x Some attributes are incompatible. + i The author of the class should implement vctrs methods. + i See . + Code + (expect_error(vec_c(x, y, .error_call = call("foo")), class = "vctrs_error_incompatible_type") + ) + Output + + Error in `foo()`: ! Can't combine `..1` and `..2` . x Some attributes are incompatible. i The author of the class should implement vctrs methods. @@ -44,7 +70,17 @@ (expect_error(vec_c(joe, jane), class = "vctrs_error_incompatible_type")) Output - Error: + Error in `vec_c()`: + ! Can't combine `..1` and `..2` . + x Some attributes are incompatible. + i The author of the class should implement vctrs methods. + i See . + Code + (expect_error(vec_c(joe, jane, .error_call = call("foo")), class = "vctrs_error_incompatible_type") + ) + Output + + Error in `foo()`: ! Can't combine `..1` and `..2` . x Some attributes are incompatible. i The author of the class should implement vctrs methods. @@ -66,8 +102,17 @@ ) Output - Error: + Error in `vec_c()`: ! Can't convert to . + Code + (expect_error(with_c_foobar(vec_c(foobar(1), foobar(2), .error_call = call( + "foo"), .name_spec = "{outer}_{inner}")))) + Output + + Error in `foo()`: + ! Can't use a name specification with non-vctrs types. + vctrs methods must be implemented for class `vctrs_foobar`. + See . # can ignore names in `vec_c()` by providing a `zap()` name-spec (#232) @@ -76,7 +121,7 @@ ) Output - Error: + Error in `vec_c()`: ! Can't combine `a` and `b` . # concatenation performs expected allocations diff --git a/tests/testthat/_snaps/slice-chop.md b/tests/testthat/_snaps/slice-chop.md index 20a6847e6..bb8775bd9 100644 --- a/tests/testthat/_snaps/slice-chop.md +++ b/tests/testthat/_snaps/slice-chop.md @@ -66,7 +66,7 @@ "name specification")) Output - Error in `list_unchop()`: + Error: ! Can't use a name specification with non-vctrs types. vctrs methods must be implemented for class `vctrs_foobar`. See . diff --git a/tests/testthat/test-c.R b/tests/testthat/test-c.R index 7c55a8741..7a31a250c 100644 --- a/tests/testthat/test-c.R +++ b/tests/testthat/test-c.R @@ -40,6 +40,15 @@ test_that("specified .ptypes do not allow more casts", { ) }) +test_that("common type failure uses error call (#1641)", { + expect_snapshot(error = TRUE, { + vec_c("x", 1, .error_call = call("foo")) + }) + expect_snapshot(error = TRUE, { + vec_c("x", .ptype = integer(), .error_call = call("foo")) + }) +}) + test_that("combines outer an inner names", { expect_equal(vec_c(x = 1), c(x = 1)) expect_equal(vec_c(c(x = 1)), c(x = 1)) @@ -183,6 +192,7 @@ test_that("vec_c() fails with complex foreign S3 classes", { x <- structure(foobar(1), attr_foo = "foo") y <- structure(foobar(2), attr_bar = "bar") (expect_error(vec_c(x, y), class = "vctrs_error_incompatible_type")) + (expect_error(vec_c(x, y, .error_call = call("foo")), class = "vctrs_error_incompatible_type")) }) }) @@ -191,6 +201,7 @@ test_that("vec_c() fails with complex foreign S4 classes", { joe <- .Counts(c(1L, 2L), name = "Joe") jane <- .Counts(3L, name = "Jane") (expect_error(vec_c(joe, jane), class = "vctrs_error_incompatible_type")) + (expect_error(vec_c(joe, jane, .error_call = call("foo")), class = "vctrs_error_incompatible_type")) }) }) @@ -290,6 +301,15 @@ test_that("vec_c() fallback doesn't support `name_spec` or `ptype`", { with_c_foobar(vec_c(foobar(1), foobar(2), .ptype = "")), class = "vctrs_error_incompatible_type" )) + + # Uses error call (#1641) + (expect_error( + with_c_foobar(vec_c( + foobar(1), foobar(2), + .error_call = call("foo"), + .name_spec = "{outer}_{inner}" + )) + )) }) }) From 38d2d4c4c73ad4162489e52fc347a8c397d4fdc7 Mon Sep 17 00:00:00 2001 From: Davis Vaughan Date: Thu, 29 Sep 2022 10:14:27 -0400 Subject: [PATCH 119/312] Don't compute the common ptype twice (#1693) --- src/c.c | 5 ++--- 1 file changed, 2 insertions(+), 3 deletions(-) diff --git a/src/c.c b/src/c.c index b175e10c2..d66a58f45 100644 --- a/src/c.c +++ b/src/c.c @@ -56,10 +56,9 @@ r_obj* vec_c_opts(r_obj* xs, if ((is_data_frame(ptype) && fallback_opts->s3 == S3_FALLBACK_true) || vec_is_common_class_fallback(ptype)) { ptype_opts.fallback.s3 = S3_FALLBACK_false; - ptype = KEEP(vec_ptype_common_opts(xs, orig_ptype, &ptype_opts)); - } else { - ptype = KEEP(vec_ptype_common_opts(xs, ptype, &ptype_opts)); + ptype = vec_ptype_common_opts(xs, orig_ptype, &ptype_opts); } + KEEP(ptype); // Find individual input sizes and total size of output r_ssize n = r_length(xs); From 7acf2e5a827417a5ffefb72936d3abb245d3ba54 Mon Sep 17 00:00:00 2001 From: Davis Vaughan Date: Thu, 29 Sep 2022 10:17:36 -0400 Subject: [PATCH 120/312] Add `error_call` to `list_unchop()` (#1691) * Add `error_call` to `list_unchop()` * NEWS bullet --- NEWS.md | 2 + R/slice-chop.R | 5 +- man/vec_chop.Rd | 8 +- src/c-unchop.c | 60 ++++++----- src/decl/c-unchop-decl.h | 6 +- src/globals.c | 1 + src/globals.h | 1 + src/init.c | 4 +- tests/testthat/_snaps/slice-chop.md | 157 ++++++++++++++++++++++++++-- tests/testthat/test-slice-chop.R | 56 ++++++++-- 10 files changed, 253 insertions(+), 47 deletions(-) diff --git a/NEWS.md b/NEWS.md index e79f8b8d6..846868f40 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,5 +1,7 @@ # vctrs (development version) +* `list_unchop()` has gained an `error_call` argument (#1641). + * `vec_c()` has gained an `.error_call` argument (#1641). * Improved the performance of list-of common type methods (#1686). diff --git a/R/slice-chop.R b/R/slice-chop.R index f47b2fc49..2606e03f1 100644 --- a/R/slice-chop.R +++ b/R/slice-chop.R @@ -97,8 +97,9 @@ list_unchop <- function(x, indices = NULL, ptype = NULL, name_spec = NULL, - name_repair = c("minimal", "unique", "check_unique", "universal")) { - .Call(ffi_list_unchop, x, indices, ptype, name_spec, name_repair) + name_repair = c("minimal", "unique", "check_unique", "universal"), + error_call = current_env()) { + .Call(ffi_list_unchop, x, indices, ptype, name_spec, name_repair, environment()) } # Exposed for testing (`starts` is 0-based) diff --git a/man/vec_chop.Rd b/man/vec_chop.Rd index 95e53357d..dddb7657d 100644 --- a/man/vec_chop.Rd +++ b/man/vec_chop.Rd @@ -12,7 +12,8 @@ list_unchop( indices = NULL, ptype = NULL, name_spec = NULL, - name_repair = c("minimal", "unique", "check_unique", "universal") + name_repair = c("minimal", "unique", "check_unique", "universal"), + error_call = current_env() ) } \arguments{ @@ -52,6 +53,11 @@ See the \link[=name_spec]{name specification topic}.} \item{name_repair}{How to repair names, see \code{repair} options in \code{\link[=vec_as_names]{vec_as_names()}}.} + +\item{error_call}{The execution environment of a currently +running function, e.g. \code{caller_env()}. The function will be +mentioned in error messages as the source of the error. See the +\code{call} argument of \code{\link[rlang:abort]{abort()}} for more information.} } \value{ \itemize{ diff --git a/src/c-unchop.c b/src/c-unchop.c index a51b54aec..914e6a5b5 100644 --- a/src/c-unchop.c +++ b/src/c-unchop.c @@ -14,43 +14,40 @@ r_obj* list_unchop(r_obj* xs, r_obj* indices, r_obj* ptype, r_obj* name_spec, - const struct name_repair_opts* name_repair) { - if (!vec_is_list(xs)) { - r_abort("`x` must be a list."); - } + const struct name_repair_opts* name_repair, + struct r_lazy error_call) { + vec_check_list(xs, vec_args.x, error_call); if (indices == r_null) { - return vec_c(xs, ptype, name_spec, name_repair, r_lazy_null); + return vec_c(xs, ptype, name_spec, name_repair, error_call); } + // Apply size/type checking to `indices` before possibly early exiting from + // having a `NULL` common type or needing to apply a fallback + vec_check_list(indices, vec_args.indices, error_call); + r_ssize xs_size = vec_size(xs); - // Apply size/type checking to `indices` before possibly exiting early from - // having a `NULL` common type if (xs_size != vec_size(indices)) { r_abort("`x` and `indices` must be lists of the same size."); } - if (!vec_is_list(indices)) { - r_abort("`indices` must be a list of integers, or `NULL`."); - } - ptype = KEEP(vec_ptype_common_params(xs, ptype, DF_FALLBACK_DEFAULT, S3_FALLBACK_true, vec_args.empty, - r_lazy_null)); + error_call)); if (needs_vec_c_fallback(ptype)) { - r_obj* out = list_unchop_fallback(ptype, xs, indices, name_spec, name_repair, FALLBACK_HOMOGENEOUS_false); + r_obj* out = list_unchop_fallback(ptype, xs, indices, name_spec, name_repair, FALLBACK_HOMOGENEOUS_false, error_call); FREE(1); return out; } // FIXME: Needed for dplyr::summarise() which passes a non-fallback ptype if (needs_vec_c_homogeneous_fallback(xs, ptype)) { - r_obj* out = list_unchop_fallback(ptype, xs, indices, name_spec, name_repair, FALLBACK_HOMOGENEOUS_true); + r_obj* out = list_unchop_fallback(ptype, xs, indices, name_spec, name_repair, FALLBACK_HOMOGENEOUS_true, error_call); FREE(1); return out; } @@ -60,7 +57,7 @@ r_obj* list_unchop(r_obj* xs, return r_null; } - xs = KEEP(vec_cast_common(xs, ptype, vec_args.empty, r_lazy_null)); + xs = KEEP(vec_cast_common(xs, ptype, vec_args.empty, error_call)); bool assign_names = !r_inherits(name_spec, "rlang_zap"); r_obj* xs_names = KEEP(r_names(xs)); @@ -80,7 +77,7 @@ r_obj* list_unchop(r_obj* xs, out_size += index_size; // Each element of `xs` is recycled to its corresponding index's size - x = vec_check_recycle(x, index_size, vec_args.empty, r_lazy_null); + x = vec_check_recycle(x, index_size, vec_args.empty, error_call); r_list_poke(xs, i, x); } @@ -100,7 +97,8 @@ r_obj* list_unchop(r_obj* xs, const struct vec_assign_opts unchop_assign_opts = { .recursive = true, .assign_names = assign_names, - .ignore_outer_names = true + .ignore_outer_names = true, + .call = error_call }; for (r_ssize i = 0; i < xs_size; ++i) { @@ -158,15 +156,25 @@ r_obj* ffi_list_unchop(r_obj* x, r_obj* indices, r_obj* ptype, r_obj* name_spec, - r_obj* name_repair) { + r_obj* name_repair, + r_obj* frame) { + struct r_lazy error_call = { .x = r_syms.error_call, .env = frame }; + struct name_repair_opts name_repair_opts = new_name_repair_opts(name_repair, r_lazy_null, false, - r_lazy_null); + error_call); KEEP(name_repair_opts.shelter); - r_obj* out = list_unchop(x, indices, ptype, name_spec, &name_repair_opts); + r_obj* out = list_unchop( + x, + indices, + ptype, + name_spec, + &name_repair_opts, + error_call + ); FREE(1); return out; @@ -182,7 +190,8 @@ r_obj* list_unchop_fallback(r_obj* ptype, r_obj* indices, r_obj* name_spec, const struct name_repair_opts* name_repair, - enum fallback_homogeneous homogeneous) { + enum fallback_homogeneous homogeneous, + struct r_lazy error_call) { r_ssize x_size = vec_size(x); x = KEEP(r_clone_referenced(x)); @@ -202,14 +211,15 @@ r_obj* list_unchop_fallback(r_obj* ptype, r_obj* out = r_null; if (homogeneous) { - out = KEEP(vec_c_fallback_invoke(x, name_spec, r_lazy_null)); + out = KEEP(vec_c_fallback_invoke(x, name_spec, error_call)); } else { - out = KEEP(vec_c_fallback(ptype, x, name_spec, name_repair, r_lazy_null)); + out = KEEP(vec_c_fallback(ptype, x, name_spec, name_repair, error_call)); } const struct name_repair_opts name_repair_opts = { .type = NAME_REPAIR_none, - .fn = r_null + .fn = r_null, + .call = error_call }; indices = KEEP(vec_c( @@ -217,7 +227,7 @@ r_obj* list_unchop_fallback(r_obj* ptype, r_globals.empty_int, r_null, &name_repair_opts, - r_lazy_null + error_call )); const int* p_indices = r_int_cbegin(indices); diff --git a/src/decl/c-unchop-decl.h b/src/decl/c-unchop-decl.h index 6c9419ff8..f09d9fcf2 100644 --- a/src/decl/c-unchop-decl.h +++ b/src/decl/c-unchop-decl.h @@ -3,7 +3,8 @@ r_obj* list_unchop(r_obj* x, r_obj* indices, r_obj* ptype, r_obj* name_spec, - const struct name_repair_opts* name_repair); + const struct name_repair_opts* name_repair, + struct r_lazy error_call); static r_obj* list_unchop_fallback(r_obj* ptype, @@ -11,4 +12,5 @@ r_obj* list_unchop_fallback(r_obj* ptype, r_obj* indices, r_obj* name_spec, const struct name_repair_opts* name_repair, - enum fallback_homogeneous homogenous); + enum fallback_homogeneous homogenous, + struct r_lazy error_call); diff --git a/src/globals.c b/src/globals.c index f84b35ea3..f406fc333 100644 --- a/src/globals.c +++ b/src/globals.c @@ -76,6 +76,7 @@ void vctrs_init_globals(r_obj* ns) { INIT_ARG(n); INIT_ARG(value); INIT_ARG(x); + INIT_ARG(indices); // Lazy args --------------------------------------------------------- INIT_LAZY_ARG_2(dot_name_repair, ".name_repair"); diff --git a/src/globals.h b/src/globals.h index 22f93f020..0e879fa7a 100644 --- a/src/globals.h +++ b/src/globals.h @@ -51,6 +51,7 @@ struct vec_args { struct vctrs_arg* n; struct vctrs_arg* value; struct vctrs_arg* x; + struct vctrs_arg* indices; }; struct lazy_args { diff --git a/src/init.c b/src/init.c index f68e671e5..3cf9f76fc 100644 --- a/src/init.c +++ b/src/init.c @@ -49,7 +49,7 @@ extern r_obj* ffi_as_location(r_obj*, r_obj*, r_obj*, r_obj*, r_obj*, r_obj*, r_ extern r_obj* ffi_slice(r_obj*, r_obj*, r_obj*); extern r_obj* ffi_init(r_obj*, r_obj*, r_obj*); extern SEXP vctrs_chop(SEXP, SEXP); -extern r_obj* ffi_list_unchop(r_obj*, r_obj*, r_obj*, r_obj*, r_obj*); +extern r_obj* ffi_list_unchop(r_obj*, r_obj*, r_obj*, r_obj*, r_obj*, r_obj*); extern SEXP vctrs_chop_seq(SEXP, SEXP, SEXP, SEXP); extern r_obj* ffi_slice_seq(r_obj*, r_obj*, r_obj*, r_obj*); extern r_obj* ffi_slice_rep(r_obj*, r_obj*, r_obj*); @@ -218,7 +218,7 @@ static const R_CallMethodDef CallEntries[] = { {"ffi_slice", (DL_FUNC) &ffi_slice, 3}, {"ffi_init", (DL_FUNC) &ffi_init, 3}, {"vctrs_chop", (DL_FUNC) &vctrs_chop, 2}, - {"ffi_list_unchop", (DL_FUNC) &ffi_list_unchop, 5}, + {"ffi_list_unchop", (DL_FUNC) &ffi_list_unchop, 6}, {"vctrs_chop_seq", (DL_FUNC) &vctrs_chop_seq, 4}, {"ffi_slice_seq", (DL_FUNC) &ffi_slice_seq, 4}, {"ffi_slice_rep", (DL_FUNC) &ffi_slice_rep, 3}, diff --git a/tests/testthat/_snaps/slice-chop.md b/tests/testthat/_snaps/slice-chop.md index bb8775bd9..677b7a583 100644 --- a/tests/testthat/_snaps/slice-chop.md +++ b/tests/testthat/_snaps/slice-chop.md @@ -1,3 +1,100 @@ +# `x` must be a list + + Code + list_unchop(1, list(1)) + Condition + Error in `list_unchop()`: + ! `x` must be a list, not a number. + +--- + + Code + list_unchop(1, list(1), error_call = call("foo")) + Condition + Error in `foo()`: + ! `x` must be a list, not a number. + +--- + + Code + list_unchop(data.frame(x = 1), list(1)) + Condition + Error in `list_unchop()`: + ! `x` must be a list, not a object. + +# `indices` must be a list + + Code + list_unchop(list(1), 1) + Condition + Error in `list_unchop()`: + ! `indices` must be a list, not a number. + +--- + + Code + list_unchop(list(1), 1, error_call = call("foo")) + Condition + Error in `foo()`: + ! `indices` must be a list, not a number. + +--- + + Code + list_unchop(list(1), data.frame(x = 1)) + Condition + Error in `list_unchop()`: + ! `indices` must be a list, not a object. + +# unchopping recycles elements of x to the size of the index + + Code + (expect_error(list_unchop(x, indices = indices))) + Output + + Error in `list_unchop()`: + ! Can't recycle input of size 2 to size 3. + Code + (expect_error(list_unchop(x, indices = indices, error_call = call("foo")))) + Output + + Error in `foo()`: + ! Can't recycle input of size 2 to size 3. + +# unchopping takes the common type + + Code + (expect_error(list_unchop(x, indices), class = "vctrs_error_incompatible_type")) + Output + + Error in `list_unchop()`: + ! Can't combine `..1` and `..2` . + Code + (expect_error(list_unchop(x, indices, error_call = call("foo")), class = "vctrs_error_incompatible_type") + ) + Output + + Error in `foo()`: + ! Can't combine `..1` and `..2` . + +# can specify a ptype to override common type + + Code + (expect_error(list_unchop(x, indices = indices, ptype = integer()))) + Output + + Error in `list_unchop()`: + ! Can't convert from `..1` to due to loss of precision. + * Locations: 1 + Code + (expect_error(list_unchop(x, indices = indices, ptype = integer(), error_call = call( + "foo")))) + Output + + Error in `foo()`: + ! Can't convert from `..1` to due to loss of precision. + * Locations: 1 + # list_unchop() errors on unsupported location values Code @@ -26,7 +123,17 @@ (expect_error(list_unchop(list(x, y)), class = "vctrs_error_incompatible_type")) Output - Error: + Error in `list_unchop()`: + ! Can't combine `..1` and `..2` . + x Some attributes are incompatible. + i The author of the class should implement vctrs methods. + i See . + Code + (expect_error(list_unchop(list(x, y), error_call = call("foo")), class = "vctrs_error_incompatible_type") + ) + Output + + Error in `foo()`: ! Can't combine `..1` and `..2` . x Some attributes are incompatible. i The author of the class should implement vctrs methods. @@ -41,7 +148,17 @@ ) Output - Error: + Error in `list_unchop()`: + ! Can't combine `..1` and `..2` . + x Some attributes are incompatible. + i The author of the class should implement vctrs methods. + i See . + Code + (expect_error(list_unchop(list(joe, jane), error_call = call("foo")), class = "vctrs_error_incompatible_type") + ) + Output + + Error in `foo()`: ! Can't combine `..1` and `..2` . x Some attributes are incompatible. i The author of the class should implement vctrs methods. @@ -54,7 +171,7 @@ ) Output - Error: + Error in `list_unchop()`: ! Can't combine `..1` and `..2` . # list_unchop() fallback doesn't support `name_spec` or `ptype` @@ -66,7 +183,16 @@ "name specification")) Output - Error: + Error in `list_unchop()`: + ! Can't use a name specification with non-vctrs types. + vctrs methods must be implemented for class `vctrs_foobar`. + See . + Code + (expect_error(with_c_foobar(list_unchop(list(foo, bar), name_spec = "{outer}_{inner}", + error_call = call("foo"))), "name specification")) + Output + + Error in `foo()`: ! Can't use a name specification with non-vctrs types. vctrs methods must be implemented for class `vctrs_foobar`. See . @@ -75,7 +201,7 @@ ) Output - Error: + Error in `list_unchop()`: ! Can't convert to . # list_unchop() does not support non-numeric S3 indices @@ -101,18 +227,35 @@ # can ignore names in `list_unchop()` by providing a `zap()` name-spec (#232) + Code + (expect_error(list_unchop(list(a = c(b = 1:2))))) + Output + + Error in `list_unchop()`: + ! Can't merge the outer name `a` with a vector of length > 1. + Please supply a `.name_spec` specification. + Code + (expect_error(list_unchop(list(a = c(b = 1:2)), error_call = call("foo")))) + Output + + Error in `list_unchop()`: + ! Can't merge the outer name `a` with a vector of length > 1. + Please supply a `.name_spec` specification. + +--- + Code (expect_error(list_unchop(list(a = c(b = letters), b = 3L), name_spec = zap()), class = "vctrs_error_incompatible_type")) Output - Error: + Error in `list_unchop()`: ! Can't combine `a` and `b` . Code (expect_error(list_unchop(list(a = c(foo = 1:2), b = c(bar = "")), indices = list( 2:1, 3), name_spec = zap()), class = "vctrs_error_incompatible_type")) Output - Error: + Error in `list_unchop()`: ! Can't combine `a` and `b` . diff --git a/tests/testthat/test-slice-chop.R b/tests/testthat/test-slice-chop.R index a690f64ba..e0385b61d 100644 --- a/tests/testthat/test-slice-chop.R +++ b/tests/testthat/test-slice-chop.R @@ -252,13 +252,27 @@ test_that("can chop S3 objects using the fallback method with compact seqs", { # list_unchop -------------------------------------------------------------- test_that("`x` must be a list", { - expect_error(list_unchop(1, list(1)), "`x` must be a list") - expect_error(list_unchop(data.frame(x=1), list(1)), "`x` must be a list") + expect_snapshot(error = TRUE, { + list_unchop(1, list(1)) + }) + expect_snapshot(error = TRUE, { + list_unchop(1, list(1), error_call = call("foo")) + }) + expect_snapshot(error = TRUE, { + list_unchop(data.frame(x=1), list(1)) + }) }) test_that("`indices` must be a list", { - expect_error(list_unchop(list(1), 1), "`indices` must be a list of integers, or `NULL`") - expect_error(list_unchop(list(1), data.frame(x=1)), "`indices` must be a list of integers, or `NULL`") + expect_snapshot(error = TRUE, { + list_unchop(list(1), 1) + }) + expect_snapshot(error = TRUE, { + list_unchop(list(1), 1, error_call = call("foo")) + }) + expect_snapshot(error = TRUE, { + list_unchop(list(1), data.frame(x=1)) + }) }) test_that("`indices` must be a list of integers", { @@ -376,15 +390,24 @@ test_that("NULL is a valid index", { test_that("unchopping recycles elements of x to the size of the index", { x <- list(1, 2) indices <- list(c(3, 4, 5), c(2, 1)) - expect_identical(list_unchop(x, indices), c(2, 2, 1, 1, 1)) + + x <- list(1:2) + indices <- list(1:3) + expect_snapshot({ + (expect_error(list_unchop(x, indices = indices))) + (expect_error(list_unchop(x, indices = indices, error_call = call("foo")))) + }) }) test_that("unchopping takes the common type", { x <- list(1, "a") indices <- list(1, 2) - expect_error(list_unchop(x, indices), class = "vctrs_error_incompatible_type") + expect_snapshot({ + (expect_error(list_unchop(x, indices), class = "vctrs_error_incompatible_type")) + (expect_error(list_unchop(x, indices, error_call = call("foo")), class = "vctrs_error_incompatible_type")) + }) x <- list(1, 2L) @@ -392,10 +415,16 @@ test_that("unchopping takes the common type", { }) test_that("can specify a ptype to override common type", { - x <- list(1, 2L) indices <- list(1, 2) + x <- list(1, 2L) expect_identical(list_unchop(x, indices, ptype = integer()), c(1L, 2L)) + + x <- list(1.5, 2) + expect_snapshot({ + (expect_error(list_unchop(x, indices = indices, ptype = integer()))) + (expect_error(list_unchop(x, indices = indices, ptype = integer(), error_call = call("foo")))) + }) }) test_that("leaving `indices = NULL` unchops sequentially", { @@ -530,6 +559,7 @@ test_that("list_unchop() fails with complex foreign S3 classes", { x <- structure(foobar(1), attr_foo = "foo") y <- structure(foobar(2), attr_bar = "bar") (expect_error(list_unchop(list(x, y)), class = "vctrs_error_incompatible_type")) + (expect_error(list_unchop(list(x, y), error_call = call("foo")), class = "vctrs_error_incompatible_type")) }) }) @@ -538,6 +568,7 @@ test_that("list_unchop() fails with complex foreign S4 classes", { joe <- .Counts(c(1L, 2L), name = "Joe") jane <- .Counts(3L, name = "Jane") (expect_error(list_unchop(list(joe, jane)), class = "vctrs_error_incompatible_type")) + (expect_error(list_unchop(list(joe, jane), error_call = call("foo")), class = "vctrs_error_incompatible_type")) }) }) @@ -683,6 +714,11 @@ test_that("list_unchop() fallback doesn't support `name_spec` or `ptype`", { with_c_foobar(list_unchop(list(foo, bar), name_spec = "{outer}_{inner}")), "name specification" )) + # With error call + (expect_error( + with_c_foobar(list_unchop(list(foo, bar), name_spec = "{outer}_{inner}", error_call = call("foo"))), + "name specification" + )) # Used to be an error about `ptype` (expect_error( with_c_foobar(list_unchop(list(foobar(1)), ptype = "")), @@ -715,7 +751,11 @@ test_that("list_unchop() does not support non-numeric S3 indices", { }) test_that("can ignore names in `list_unchop()` by providing a `zap()` name-spec (#232)", { - expect_error(list_unchop(list(a = c(b = 1:2)))) + expect_snapshot({ + (expect_error(list_unchop(list(a = c(b = 1:2))))) + (expect_error(list_unchop(list(a = c(b = 1:2)), error_call = call("foo")))) + }) + expect_identical( list_unchop(list(a = c(b = 1:2), b = 3L), name_spec = zap()), 1:3 From 765fbf2b8d1f018c134c6cc337f48f27f43c34fb Mon Sep 17 00:00:00 2001 From: "Jennifer (Jenny) Bryan" Date: Fri, 30 Sep 2022 03:09:23 -0700 Subject: [PATCH 121/312] Add "quiet" variants of name-repair options (#1677) Closes #1629 --- NEWS.md | 8 ++++++++ R/names.R | 25 +++++++++++++++++-------- man/vec_as_names.Rd | 19 +++++++++++++------ man/vec_names.Rd | 19 +++++++++++++------ src/names.c | 14 ++++++++++++++ src/names.h | 2 ++ src/utils.c | 10 +++++++++- src/utils.h | 2 ++ tests/testthat/_snaps/names.md | 24 ++++++++++++++++++++++++ tests/testthat/test-names.R | 27 +++++++++++++++++++++++++++ 10 files changed, 129 insertions(+), 21 deletions(-) diff --git a/NEWS.md b/NEWS.md index 846868f40..a5701d3b9 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,5 +1,13 @@ # vctrs (development version) +* `"unique_quiet"` and `"universal_quiet"` are newly accepted by + `vec_as_names(repair =)` and `vec_names2(repair =)`. These options exist to + help users who call these functions indirectly, via another function which + only exposes `repair` but not `quiet`. Specifying `repair = "unique_quiet"` is + like specifying `repair = "unique", quiet = TRUE`. When the `"*_quiet"` + options are used, any setting of `quiet` is silently overridden (@jennybc, + #1629). + * `list_unchop()` has gained an `error_call` argument (#1641). * `vec_c()` has gained an `.error_call` argument (#1641). diff --git a/R/names.R b/R/names.R index a5bf49b06..a7cdf6e23 100644 --- a/R/names.R +++ b/R/names.R @@ -36,10 +36,11 @@ #' @inheritParams rlang::args_dots_empty #' #' @param names A character vector. -#' @param repair Either a string or a function. If a string, it must -#' be one of `"check_unique"`, `"minimal"`, `"unique"`, or `"universal"`. -#' If a function, it is invoked with a vector of minimal names and must -#' return minimal names, otherwise an error is thrown. + +#' @param repair Either a string or a function. If a string, it must be one of +#' `"check_unique"`, `"minimal"`, `"unique"`, `"universal"`, `"unique_quiet"`, +#' or `"universal_quiet"` If a function, it is invoked with a vector of +#' minimal names and must return minimal names, otherwise an error is thrown. #' #' * Minimal names are never `NULL` or `NA`. When an element doesn't #' have a name, its minimal name is an empty string. @@ -54,6 +55,12 @@ #' The `"check_unique"` option doesn't perform any name repair. #' Instead, an error is raised if the names don't suit the #' `"unique"` criteria. +#' +#' The options `"unique_quiet"` and `"universal_quiet"` are here to help the +#' user who calls this function indirectly, via another function which exposes +#' `repair` but not `quiet`. Specifying `repair = "unique_quiet"` is like +#' specifying `repair = "unique", quiet = TRUE`. When the `"*_quiet"` options +#' are used, any setting of `quiet` is silently overridden. #' @param repair_arg If specified and `repair = "check_unique"`, any errors #' will include a hint to set the `repair_arg`. #' @param quiet By default, the user is informed of any renaming @@ -153,7 +160,7 @@ #' @export vec_as_names <- function(names, ..., - repair = c("minimal", "unique", "universal", "check_unique"), + repair = c("minimal", "unique", "universal", "check_unique", "unique_quiet", "universal_quiet"), repair_arg = NULL, quiet = FALSE, call = caller_env()) { @@ -250,7 +257,7 @@ detect_dot_dot <- function(names) { #' vec_set_names(data.frame(a = 1:3), letters[1:3]) vec_names2 <- function(x, ..., - repair = c("minimal", "unique", "universal", "check_unique"), + repair = c("minimal", "unique", "universal", "check_unique", "unique_quiet", "universal_quiet"), quiet = FALSE) { check_dots_empty0(...) repair <- validate_name_repair_arg(repair) @@ -271,11 +278,13 @@ vec_names2 <- function(x, minimal = minimal_names(x), unique = unique_names(x, quiet = quiet), universal = as_universal_names(minimal_names(x), quiet = quiet), - check_unique = validate_unique(minimal_names(x)) + check_unique = validate_unique(minimal_names(x)), + unique_quiet = unique_names(x, quiet = TRUE), + universal_quiet = as_universal_names(minimal_names(x), quiet = TRUE) ) } vec_repair_names <- function(x, - repair = c("minimal", "unique", "universal", "check_unique"), + repair = c("minimal", "unique", "universal", "check_unique", "unique_quiet", "universal_quiet"), ..., quiet = FALSE) { if (is.data.frame(x)) { diff --git a/man/vec_as_names.Rd b/man/vec_as_names.Rd index b590fe2f7..d4a68159f 100644 --- a/man/vec_as_names.Rd +++ b/man/vec_as_names.Rd @@ -7,7 +7,8 @@ vec_as_names( names, ..., - repair = c("minimal", "unique", "universal", "check_unique"), + repair = c("minimal", "unique", "universal", "check_unique", "unique_quiet", + "universal_quiet"), repair_arg = NULL, quiet = FALSE, call = caller_env() @@ -18,10 +19,10 @@ vec_as_names( \item{...}{These dots are for future extensions and must be empty.} -\item{repair}{Either a string or a function. If a string, it must -be one of \code{"check_unique"}, \code{"minimal"}, \code{"unique"}, or \code{"universal"}. -If a function, it is invoked with a vector of minimal names and must -return minimal names, otherwise an error is thrown. +\item{repair}{Either a string or a function. If a string, it must be one of +\code{"check_unique"}, \code{"minimal"}, \code{"unique"}, \code{"universal"}, \code{"unique_quiet"}, +or \code{"universal_quiet"} If a function, it is invoked with a vector of +minimal names and must return minimal names, otherwise an error is thrown. \itemize{ \item Minimal names are never \code{NULL} or \code{NA}. When an element doesn't have a name, its minimal name is an empty string. @@ -34,7 +35,13 @@ error. The \code{"check_unique"} option doesn't perform any name repair. Instead, an error is raised if the names don't suit the -\code{"unique"} criteria.} +\code{"unique"} criteria. + +The options \code{"unique_quiet"} and \code{"universal_quiet"} are here to help the +user who calls this function indirectly, via another function which exposes +\code{repair} but not \code{quiet}. Specifying \code{repair = "unique_quiet"} is like +specifying \verb{repair = "unique", quiet = TRUE}. When the \code{"*_quiet"} options +are used, any setting of \code{quiet} is silently overridden.} \item{repair_arg}{If specified and \code{repair = "check_unique"}, any errors will include a hint to set the \code{repair_arg}.} diff --git a/man/vec_names.Rd b/man/vec_names.Rd index 75a6a5587..70c9df7c4 100644 --- a/man/vec_names.Rd +++ b/man/vec_names.Rd @@ -9,7 +9,8 @@ vec_names2( x, ..., - repair = c("minimal", "unique", "universal", "check_unique"), + repair = c("minimal", "unique", "universal", "check_unique", "unique_quiet", + "universal_quiet"), quiet = FALSE ) @@ -22,10 +23,10 @@ vec_set_names(x, names) \item{...}{These dots are for future extensions and must be empty.} -\item{repair}{Either a string or a function. If a string, it must -be one of \code{"check_unique"}, \code{"minimal"}, \code{"unique"}, or \code{"universal"}. -If a function, it is invoked with a vector of minimal names and must -return minimal names, otherwise an error is thrown. +\item{repair}{Either a string or a function. If a string, it must be one of +\code{"check_unique"}, \code{"minimal"}, \code{"unique"}, \code{"universal"}, \code{"unique_quiet"}, +or \code{"universal_quiet"} If a function, it is invoked with a vector of +minimal names and must return minimal names, otherwise an error is thrown. \itemize{ \item Minimal names are never \code{NULL} or \code{NA}. When an element doesn't have a name, its minimal name is an empty string. @@ -38,7 +39,13 @@ error. The \code{"check_unique"} option doesn't perform any name repair. Instead, an error is raised if the names don't suit the -\code{"unique"} criteria.} +\code{"unique"} criteria. + +The options \code{"unique_quiet"} and \code{"universal_quiet"} are here to help the +user who calls this function indirectly, via another function which exposes +\code{repair} but not \code{quiet}. Specifying \code{repair = "unique_quiet"} is like +specifying \verb{repair = "unique", quiet = TRUE}. When the \code{"*_quiet"} options +are used, any setting of \code{quiet} is silently overridden.} \item{quiet}{By default, the user is informed of any renaming caused by repairing the names. This only concerns unique and diff --git a/src/names.c b/src/names.c index 5e2967d07..58956936d 100644 --- a/src/names.c +++ b/src/names.c @@ -17,6 +17,12 @@ r_obj* vec_as_names(r_obj* names, const struct name_repair_opts* opts) { case NAME_REPAIR_unique: return vec_as_unique_names(names, opts->quiet); case NAME_REPAIR_universal: return vec_as_universal_names(names, opts->quiet); case NAME_REPAIR_check_unique: return check_unique_names(names, opts); + // At the time when unique_quiet and universal_quiet were added, no function + // that calls the C function vec_as_names() actually accepts these strings at + // the R level, because these functions enforce `quiet = false`. + // But we still have to handle every case for the enum. + case NAME_REPAIR_unique_quiet: return vec_as_unique_names(names, true); + case NAME_REPAIR_universal_quiet: return vec_as_universal_names(names, true); case NAME_REPAIR_custom: return vec_as_custom_names(names, opts); } r_stop_unreachable(); @@ -894,6 +900,12 @@ struct name_repair_opts new_name_repair_opts(r_obj* name_repair, opts.type = NAME_REPAIR_universal; } else if (c == strings_check_unique) { opts.type = NAME_REPAIR_check_unique; + } else if (c == strings_unique_quiet) { + opts.type = NAME_REPAIR_unique; + opts.quiet = true; + } else if (c == strings_universal_quiet) { + opts.type = NAME_REPAIR_universal; + opts.quiet = true; } else { struct repair_error_info info = new_repair_error_info(&opts); KEEP(info.shelter); @@ -931,6 +943,8 @@ const char* name_repair_arg_as_c_string(enum name_repair_type type) { case NAME_REPAIR_unique: return "unique"; case NAME_REPAIR_universal: return "universal"; case NAME_REPAIR_check_unique: return "check_unique"; + case NAME_REPAIR_unique_quiet: return "unique_quiet"; + case NAME_REPAIR_universal_quiet: return "universal_quiet"; case NAME_REPAIR_custom: return "custom"; } r_stop_unreachable(); diff --git a/src/names.h b/src/names.h index 7cb75ab13..7025cf27d 100644 --- a/src/names.h +++ b/src/names.h @@ -21,6 +21,8 @@ enum name_repair_type { NAME_REPAIR_unique, NAME_REPAIR_universal, NAME_REPAIR_check_unique, + NAME_REPAIR_unique_quiet, + NAME_REPAIR_universal_quiet, NAME_REPAIR_custom = 99 }; diff --git a/src/utils.c b/src/utils.c index b4f6cad8f..687c43c4a 100644 --- a/src/utils.c +++ b/src/utils.c @@ -1513,6 +1513,8 @@ SEXP strings_minimal = NULL; SEXP strings_unique = NULL; SEXP strings_universal = NULL; SEXP strings_check_unique = NULL; +SEXP strings_unique_quiet = NULL; +SEXP strings_universal_quiet = NULL; SEXP strings_key = NULL; SEXP strings_loc = NULL; SEXP strings_val = NULL; @@ -1669,7 +1671,7 @@ void vctrs_init_utils(SEXP ns) { // Holds the CHARSXP objects because unlike symbols they can be // garbage collected - strings2 = r_new_shared_vector(STRSXP, 23); + strings2 = r_new_shared_vector(STRSXP, 25); strings_dots = Rf_mkChar("..."); SET_STRING_ELT(strings2, 0, strings_dots); @@ -1704,6 +1706,12 @@ void vctrs_init_utils(SEXP ns) { strings_check_unique = Rf_mkChar("check_unique"); SET_STRING_ELT(strings2, 10, strings_check_unique); + strings_unique_quiet = Rf_mkChar("unique_quiet"); + SET_STRING_ELT(strings2, 23, strings_unique_quiet); + + strings_universal_quiet = Rf_mkChar("universal_quiet"); + SET_STRING_ELT(strings2, 24, strings_universal_quiet); + strings_key = Rf_mkChar("key"); SET_STRING_ELT(strings2, 11, strings_key); diff --git a/src/utils.h b/src/utils.h index 46363d49e..fafc6b40c 100644 --- a/src/utils.h +++ b/src/utils.h @@ -407,6 +407,8 @@ extern SEXP strings_minimal; extern SEXP strings_unique; extern SEXP strings_universal; extern SEXP strings_check_unique; +extern SEXP strings_unique_quiet; +extern SEXP strings_universal_quiet; extern SEXP strings_key; extern SEXP strings_loc; extern SEXP strings_val; diff --git a/tests/testthat/_snaps/names.md b/tests/testthat/_snaps/names.md index b33d7e5d6..637c70f18 100644 --- a/tests/testthat/_snaps/names.md +++ b/tests/testthat/_snaps/names.md @@ -85,6 +85,30 @@ x These names are duplicated: * "x" at locations 1 and 2. i Use argument `my_repair` to specify repair strategy. + Code + vec_as_names(c("1", "1"), repair = "unique_quiet") + Output + [1] "1...1" "1...2" + Code + vec_as_names(c("1", "1"), repair = "universal_quiet") + Output + [1] "...1...1" "...1...2" + Code + vec_as_names(c("1", "1"), repair = "unique_quiet", quiet = TRUE) + Output + [1] "1...1" "1...2" + Code + vec_as_names(c("1", "1"), repair = "universal_quiet", quiet = TRUE) + Output + [1] "...1...1" "...1...2" + Code + vec_as_names(c("1", "1"), repair = "unique_quiet", quiet = FALSE) + Output + [1] "1...1" "1...2" + Code + vec_as_names(c("1", "1"), repair = "universal_quiet", quiet = FALSE) + Output + [1] "...1...1" "...1...2" # validate_minimal_names() checks names diff --git a/tests/testthat/test-names.R b/tests/testthat/test-names.R index 5156ae69b..908a1dda1 100644 --- a/tests/testthat/test-names.R +++ b/tests/testthat/test-names.R @@ -51,6 +51,10 @@ test_that("vec_names2() repairs names before invoking repair function", { expect_identical(vec_names2(x, repair = identity), c("", "")) }) +test_that("vec_names2() result is correct for *_quiet repair", { + expect_identical(vec_names2(1:2, repair = "unique"), vec_names2(1:2, repair = "unique_quiet")) + expect_identical(vec_names2(1:2, repair = "universal"), vec_names2(1:2, repair = "universal_quiet")) +}) # vec_as_names() ----------------------------------------------------------- @@ -82,6 +86,17 @@ test_that("vec_as_names() checks unique names", { }) }) +test_that("vec_as_names() result is correct for *_quiet repair", { + expect_identical( + vec_as_names(chr("_foo", "_bar"), repair = "unique"), + vec_as_names(chr("_foo", "_bar"), repair = "unique_quiet") + ) + expect_identical( + vec_as_names(chr("_foo", "_bar"), repair = "universal"), + vec_as_names(chr("_foo", "_bar"), repair = "universal_quiet") + ) +}) + test_that("vec_as_names() keeps the names of a named vector", { x_unnamed <- c(NA, "", "..1", "...2") x_names <- letters[1:4] @@ -128,6 +143,18 @@ test_that("vec_as_names() is noisy by default", { (expect_error( my_vec_as_names(c("x", "x"), my_repair = "check_unique") )) + + # request quiet via name repair string, don't specify `quiet` + vec_as_names(c("1", "1"), repair = "unique_quiet") + vec_as_names(c("1", "1"), repair = "universal_quiet") + + # request quiet via name repair string, specify `quiet` = TRUE + vec_as_names(c("1", "1"), repair = "unique_quiet", quiet = TRUE) + vec_as_names(c("1", "1"), repair = "universal_quiet", quiet = TRUE) + + # request quiet via name repair string, specify `quiet` = FALSE + vec_as_names(c("1", "1"), repair = "unique_quiet", quiet = FALSE) + vec_as_names(c("1", "1"), repair = "universal_quiet", quiet = FALSE) }) }) From 1d85e4c24b6eda3c04866102282ac2225912b2b6 Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Fri, 30 Sep 2022 15:05:28 +0200 Subject: [PATCH 122/312] Add 0.4.2 NEWS bullet --- NEWS.md | 8 +++++++- 1 file changed, 7 insertions(+), 1 deletion(-) diff --git a/NEWS.md b/NEWS.md index a5701d3b9..628ba9024 100644 --- a/NEWS.md +++ b/NEWS.md @@ -145,7 +145,7 @@ * `vec_locate_matches()` now uses a more conservative heuristic when taking the joint ordering proxy. This allows it to work correctly with sf's sfc vectors and the classes from the bignum package (#1558). - + * An sfc method for `vec_proxy_order()` was added to better support the sf package. These vectors are generally treated like list-columns even though they don't explicitly have a `"list"` class, and the `vec_proxy_order()` @@ -155,6 +155,12 @@ `vec_proxy_order()` now works correctly for raw and list vectors wrapped in `I()` (#1557). + +# vctrs 0.4.2 + +* HTML documentation fixes for CRAN checks. + + # vctrs 0.4.1 * OOB errors with `character()` indexes use "that don't exist" instead From 3f27175a1df64cf3eb28171cb5d66d8a85ae55d1 Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Fri, 30 Sep 2022 15:06:47 +0200 Subject: [PATCH 123/312] Increment version number to 0.4.2.9000 --- DESCRIPTION | 2 +- src/version.c | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/DESCRIPTION b/DESCRIPTION index bbb3f1d8a..b38880889 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -1,6 +1,6 @@ Package: vctrs Title: Vector Helpers -Version: 0.4.1.9001 +Version: 0.4.2.9000 Authors@R: c(person(given = "Hadley", family = "Wickham", diff --git a/src/version.c b/src/version.c index 6419bc496..01e6c7d13 100644 --- a/src/version.c +++ b/src/version.c @@ -1,7 +1,7 @@ #define R_NO_REMAP #include -const char* vctrs_version = "0.4.1.9001"; +const char* vctrs_version = "0.4.2.9000"; /** * This file records the expected package version in the shared From 35d9a7c8a95aa46c040da7dfacd2f8b6e8055029 Mon Sep 17 00:00:00 2001 From: Davis Vaughan Date: Fri, 30 Sep 2022 10:39:09 -0400 Subject: [PATCH 124/312] Add `` self-self cast optimization (#1695) * Add `` self-self cast optimization * Tweak NEWS bullet --- NEWS.md | 2 +- R/type-list-of.R | 18 ++++++++++++------ tests/testthat/test-type-list-of.R | 17 +++++++++++++++++ 3 files changed, 30 insertions(+), 7 deletions(-) diff --git a/NEWS.md b/NEWS.md index 628ba9024..5dd1ab037 100644 --- a/NEWS.md +++ b/NEWS.md @@ -12,7 +12,7 @@ * `vec_c()` has gained an `.error_call` argument (#1641). -* Improved the performance of list-of common type methods (#1686). +* Improved the performance of list-of common type methods (#1686, #875). * The list-of method for `as_list_of()` now places the optional `.ptype` argument after the `...` (#1686). diff --git a/R/type-list-of.R b/R/type-list-of.R index 6ee82b2ca..3b2b93da5 100644 --- a/R/type-list-of.R +++ b/R/type-list-of.R @@ -204,12 +204,18 @@ vec_cast.vctrs_list_of <- function(x, to, ...) { #' @export #' @method vec_cast.vctrs_list_of vctrs_list_of vec_cast.vctrs_list_of.vctrs_list_of <- function(x, to, ...) { - # Casting list to list_of will warn/err if the cast is lossy, - # but the locations refer to the inner vectors, - # and the cast fails if all (vector) elements in a single (list) element - x <- unclass(x) - ptype <- attr(to, "ptype") - list_as_list_of(x, ptype = ptype) + x_ptype <- attr(x, "ptype", exact = TRUE) + to_ptype <- attr(to, "ptype", exact = TRUE) + + if (identical(x_ptype, to_ptype)) { + # FIXME: Suboptimal check for "same type", but should be good enough for the + # common case of unchopping a list of identically generated list-ofs (#875). + # Would be fixed by https://github.com/r-lib/vctrs/issues/1688. + x + } else { + x <- unclass(x) + list_as_list_of(x, ptype = to_ptype) + } } # Helpers ----------------------------------------------------------------- diff --git a/tests/testthat/test-type-list-of.R b/tests/testthat/test-type-list-of.R index f678d5c13..12045f5fc 100644 --- a/tests/testthat/test-type-list-of.R +++ b/tests/testthat/test-type-list-of.R @@ -146,6 +146,23 @@ test_that("max, list_of> is list_of>", { expect_equal(vec_ptype_common(r_int, r_dbl), r_int) }) +test_that("can cast to self type", { + x <- list_of(1) + expect_identical(vec_cast(x, x), x) +}) + +test_that("can cast between different list_of types", { + x <- list_of(1, 2) + to <- list_of(.ptype = integer()) + expect_identical(vec_cast(x, to), list_of(1L, 2L)) +}) + +test_that("list_of casting retains outer names", { + x <- list_of(x = 1, 2, z = 3) + to <- list_of(.ptype = integer()) + expect_named(vec_cast(x, to), c("x", "", "z")) +}) + test_that("safe casts work as expected", { x <- list_of(1) expect_equal(vec_cast(NULL, x), NULL) From 572d7afdf21b8161adbe81c74653dd8789e31719 Mon Sep 17 00:00:00 2001 From: Davis Vaughan Date: Fri, 30 Sep 2022 10:49:37 -0400 Subject: [PATCH 125/312] Retain names in `list_unchop()` (#1699) * Cast and recycle inside the assign loop - More similar to `vec_c()` - Doesn't require duplicating `xs` anymore - Still allows for nice positional errors with `new_subscript_arg()` * Remove FIXME for now fixed test * NEWS bullet --- NEWS.md | 3 ++ src/c-unchop.c | 48 +++++++++++++++++------------ tests/testthat/_snaps/slice-chop.md | 4 +-- tests/testthat/test-c.R | 6 +--- tests/testthat/test-slice-chop.R | 31 +++++++++++++++++++ 5 files changed, 66 insertions(+), 26 deletions(-) diff --git a/NEWS.md b/NEWS.md index 5dd1ab037..08d0ef039 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,5 +1,8 @@ # vctrs (development version) +* `list_unchop()` no longer drops names in some cases when `indices` were + supplied (#1689). + * `"unique_quiet"` and `"universal_quiet"` are newly accepted by `vec_as_names(repair =)` and `vec_names2(repair =)`. These options exist to help users who call these functions indirectly, via another function which diff --git a/src/c-unchop.c b/src/c-unchop.c index 914e6a5b5..2d0d888d5 100644 --- a/src/c-unchop.c +++ b/src/c-unchop.c @@ -57,28 +57,14 @@ r_obj* list_unchop(r_obj* xs, return r_null; } - xs = KEEP(vec_cast_common(xs, ptype, vec_args.empty, error_call)); - bool assign_names = !r_inherits(name_spec, "rlang_zap"); r_obj* xs_names = KEEP(r_names(xs)); bool xs_is_named = xs_names != r_null && !is_data_frame(ptype); - r_ssize out_size = 0; - // `out_size` is computed from `indices` + r_ssize out_size = 0; for (r_ssize i = 0; i < xs_size; ++i) { - r_obj* x = r_list_get(xs, i); - - if (x == r_null) { - continue; - } - - r_ssize index_size = r_length(r_list_get(indices, i)); - out_size += index_size; - - // Each element of `xs` is recycled to its corresponding index's size - x = vec_check_recycle(x, index_size, vec_args.empty, error_call); - r_list_poke(xs, i, x); + out_size += r_length(r_list_get(indices, i)); } r_obj* locs = KEEP(vec_as_indices(indices, out_size, r_null)); @@ -94,6 +80,22 @@ r_obj* list_unchop(r_obj* xs, r_keep_loc out_names_pi; KEEP_HERE(out_names, &out_names_pi); + r_ssize i = 0; + + struct vctrs_arg* p_x_arg = new_subscript_arg( + vec_args.empty, + xs_names, + xs_size, + &i + ); + KEEP(p_x_arg->shelter); + + struct cast_opts unchop_cast_opts = { + .to = ptype, + .p_x_arg = p_x_arg, + .call = error_call + }; + const struct vec_assign_opts unchop_assign_opts = { .recursive = true, .assign_names = assign_names, @@ -101,7 +103,7 @@ r_obj* list_unchop(r_obj* xs, .call = error_call }; - for (r_ssize i = 0; i < xs_size; ++i) { + for (; i < xs_size; ++i) { r_obj* x = r_list_get(xs, i); if (x == r_null) { @@ -109,12 +111,15 @@ r_obj* list_unchop(r_obj* xs, } r_obj* loc = r_list_get(locs, i); + const r_ssize loc_size = r_length(loc); + + // Each element of `xs` is recycled to its corresponding index's size + x = KEEP(vec_check_recycle(x, loc_size, p_x_arg, error_call)); if (assign_names) { - r_ssize size = r_length(loc); r_obj* outer = xs_is_named ? r_chr_get(xs_names, i) : r_null; r_obj* inner = KEEP(vec_names(x)); - r_obj* x_nms = KEEP(apply_name_spec(name_spec, outer, inner, size)); + r_obj* x_nms = KEEP(apply_name_spec(name_spec, outer, inner, loc_size)); if (x_nms != r_null) { R_LAZY_ALLOC(out_names, out_names_pi, R_TYPE_character, out_size); @@ -130,9 +135,14 @@ r_obj* list_unchop(r_obj* xs, FREE(2); } + unchop_cast_opts.x = x; + x = KEEP(vec_cast_opts(&unchop_cast_opts)); + // Total ownership of `proxy` because it was freshly created with `vec_init()` proxy = vec_proxy_assign_opts(proxy, loc, x, VCTRS_OWNED_true, &unchop_assign_opts); KEEP_AT(proxy, proxy_pi); + + FREE(2); } r_obj* out = KEEP(vec_restore_recurse(proxy, ptype, VCTRS_OWNED_true)); diff --git a/tests/testthat/_snaps/slice-chop.md b/tests/testthat/_snaps/slice-chop.md index 677b7a583..b6a4fb58c 100644 --- a/tests/testthat/_snaps/slice-chop.md +++ b/tests/testthat/_snaps/slice-chop.md @@ -53,13 +53,13 @@ Output Error in `list_unchop()`: - ! Can't recycle input of size 2 to size 3. + ! Can't recycle `..1` (size 2) to size 3. Code (expect_error(list_unchop(x, indices = indices, error_call = call("foo")))) Output Error in `foo()`: - ! Can't recycle input of size 2 to size 3. + ! Can't recycle `..1` (size 2) to size 3. # unchopping takes the common type diff --git a/tests/testthat/test-c.R b/tests/testthat/test-c.R index 7a31a250c..24794621c 100644 --- a/tests/testthat/test-c.R +++ b/tests/testthat/test-c.R @@ -439,11 +439,7 @@ test_that("named empty vectors force named output (#1263)", { expect_named(list_unchop(list(x, x), list(int(), int())), chr()) expect_named(list_unchop(list(x, 1L), list(int(), 1)), "") - # FIXME: `vec_cast_common()` dropped names - # https://github.com/r-lib/vctrs/issues/623 - expect_failure( - expect_named(list_unchop(list(x, 1), list(int(), 1)), "") - ) + expect_named(list_unchop(list(x, 1), list(int(), 1)), "") }) # Golden tests ------------------------------------------------------- diff --git a/tests/testthat/test-slice-chop.R b/tests/testthat/test-slice-chop.R index e0385b61d..0292be0db 100644 --- a/tests/testthat/test-slice-chop.R +++ b/tests/testthat/test-slice-chop.R @@ -307,6 +307,22 @@ test_that("NULLs are ignored when unchopped with other vectors", { expect_identical(list_unchop(list("a", NULL, "b"), list(2, integer(), 1)), c("b", "a")) }) +test_that("can use a `NULL` element with a corresponding index", { + # FIXME: Probably not quite right, but not entirely clear what it should be: + # - Maybe `unspecified(2)`? + # - Or should `NULL`s even be allowed in `list_unchop()`? + expect_null(list_unchop(list(NULL), indices = list(1:2))) + + expect_identical( + list_unchop(list(NULL), indices = list(1:2), ptype = integer()), + c(NA_integer_, NA_integer_) + ) + + x <- list("a", NULL, c("b", "c")) + indices <- list(3L, c(1L, 4L), c(2L, 5L)) + expect_identical(list_unchop(x, indices = indices), c(NA, "b", "a", NA, "c")) +}) + test_that("can unchop atomic vectors", { expect_identical(list_unchop(list(1, 2), list(2, 1)), c(2, 1)) expect_identical(list_unchop(list("a", "b"), list(2, 1)), c("b", "a")) @@ -452,6 +468,21 @@ test_that("outer names can be merged with inner names", { expect_named(list_unchop(x, list(2, 1), name_spec = "{outer}_{inner}"), c("y_b", "x_a")) }) +test_that("preserves names when inputs are cast to a common type (#1689)", { + expect_named(list_unchop(list(c(a = 1)), ptype = integer()), "a") + expect_named(list_unchop(list(c(a = 1)), ptype = integer(), indices = list(1)), "a") + + # With name spec + name_spec <- "{outer}_{inner}" + expect_named(list_unchop(list(foo = c(a = 1)), ptype = integer(), name_spec = name_spec), "foo_a") + expect_named(list_unchop(list(foo = c(a = 1)), ptype = integer(), name_spec = name_spec, indices = list(1)), "foo_a") + + # When `x` elements are recycled, names are also recycled + x <- list(c(a = 1), c(b = 2)) + indices <- list(1:2, 3:4) + expect_named(list_unchop(x, indices = indices, ptype = integer()), c("a", "a", "b", "b")) +}) + test_that("not all inputs have to be named", { x <- list(c(a = 1), 2, c(c = 3)) indices <- list(2, 1, 3) From 8cc709d15f82e87b4ebdae069fa051027213961a Mon Sep 17 00:00:00 2001 From: Davis Vaughan Date: Fri, 30 Sep 2022 10:52:36 -0400 Subject: [PATCH 126/312] Use positional errors in `vec_c()` (#1700) * Use positional errors in `vec_c()` * NEWS bullet --- NEWS.md | 3 ++ src/c.c | 35 ++++++++++++++-------- tests/testthat/_snaps/c.md | 26 +++++++++++++++-- tests/testthat/_snaps/slice-chop.md | 45 ++++++++++++++++++++++++++++- tests/testthat/test-c.R | 18 ++++++++++++ tests/testthat/test-slice-chop.R | 16 ++++++++++ 6 files changed, 128 insertions(+), 15 deletions(-) diff --git a/NEWS.md b/NEWS.md index 08d0ef039..9bb933fe0 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,5 +1,8 @@ # vctrs (development version) +* Directed calls to `vec_c()`, like `vec_c(.ptype = )`, now mention the + position of the problematic argument when there are cast errors (#1690). + * `list_unchop()` no longer drops names in some cases when `indices` were supplied (#1689). diff --git a/src/c.c b/src/c.c index d66a58f45..67424fa79 100644 --- a/src/c.c +++ b/src/c.c @@ -61,14 +61,14 @@ r_obj* vec_c_opts(r_obj* xs, KEEP(ptype); // Find individual input sizes and total size of output - r_ssize n = r_length(xs); + r_ssize xs_size = r_length(xs); r_ssize out_size = 0; // Caching the sizes causes an extra allocation but it improves performance - r_obj* sizes = KEEP(r_alloc_integer(n)); + r_obj* sizes = KEEP(r_alloc_integer(xs_size)); int* p_sizes = r_int_begin(sizes); - for (r_ssize i = 0; i < n; ++i) { + for (r_ssize i = 0; i < xs_size; ++i) { r_obj* x = r_list_get(xs, i); r_ssize size = (x == r_null) ? 0 : vec_size(x); out_size += size; @@ -96,6 +96,22 @@ r_obj* vec_c_opts(r_obj* xs, // Compact sequences use 0-based counters r_ssize counter = 0; + r_ssize i = 0; + + struct vctrs_arg* p_x_arg = new_subscript_arg( + vec_args.empty, + xs_names, + xs_size, + &i + ); + KEEP(p_x_arg->shelter); + + struct cast_opts c_cast_opts = { + .to = ptype, + .p_x_arg = p_x_arg, + .call = error_call + }; + const struct vec_assign_opts c_assign_opts = { .recursive = true, .assign_names = assign_names, @@ -103,7 +119,7 @@ r_obj* vec_c_opts(r_obj* xs, .call = error_call }; - for (r_ssize i = 0; i < n; ++i) { + for (; i < xs_size; ++i) { r_obj* x = r_list_get(xs, i); r_ssize size = p_sizes[i]; @@ -132,13 +148,8 @@ r_obj* vec_c_opts(r_obj* xs, continue; } - struct cast_opts opts = (struct cast_opts) { - .x = x, - .to = ptype, - .call = error_call, - .fallback = *fallback_opts - }; - x = KEEP(vec_cast_opts(&opts)); + c_cast_opts.x = x; + x = KEEP(vec_cast_opts(&c_cast_opts)); // Total ownership of `out` because it was freshly created with `vec_init()` out = vec_proxy_assign_opts(out, loc, x, VCTRS_OWNED_true, &c_assign_opts); @@ -161,7 +172,7 @@ r_obj* vec_c_opts(r_obj* xs, out = vec_set_names(out, r_null); } - FREE(8); + FREE(9); return out; } diff --git a/tests/testthat/_snaps/c.md b/tests/testthat/_snaps/c.md index a0e111ad4..fa0f801e1 100644 --- a/tests/testthat/_snaps/c.md +++ b/tests/testthat/_snaps/c.md @@ -12,7 +12,29 @@ vec_c("x", .ptype = integer(), .error_call = call("foo")) Condition Error in `foo()`: - ! Can't convert to . + ! Can't convert `..1` to . + +# common type failure uses positional errors + + Code + (expect_error(vec_c(1, a = "x", 2))) + Output + + Error in `vec_c()`: + ! Can't combine `..1` and `a` . + Code + (expect_error(vec_c(1, a = "x", 2, .ptype = double()))) + Output + + Error in `vec_c()`: + ! Can't convert `a` to . + Code + (expect_error(vec_c(1, a = 2.5, .ptype = integer()))) + Output + + Error in `vec_c()`: + ! Can't convert from `a` to due to loss of precision. + * Locations: 1 # vec_c() includes index in argument tag @@ -103,7 +125,7 @@ Output Error in `vec_c()`: - ! Can't convert to . + ! Can't convert `..1` to . Code (expect_error(with_c_foobar(vec_c(foobar(1), foobar(2), .error_call = call( "foo"), .name_spec = "{outer}_{inner}")))) diff --git a/tests/testthat/_snaps/slice-chop.md b/tests/testthat/_snaps/slice-chop.md index b6a4fb58c..4b61e4dd8 100644 --- a/tests/testthat/_snaps/slice-chop.md +++ b/tests/testthat/_snaps/slice-chop.md @@ -77,6 +77,49 @@ Error in `foo()`: ! Can't combine `..1` and `..2` . +# common type failure uses positional errors + + Code + (expect_error(list_unchop(list(1, a = "x", 2)))) + Output + + Error in `list_unchop()`: + ! Can't combine `..1` and `a` . + Code + (expect_error(list_unchop(list(1, a = "x", 2), indices = list(2, 1, 3)))) + Output + + Error in `list_unchop()`: + ! Can't combine `..1` and `a` . + Code + (expect_error(list_unchop(list(1, a = "x", 2), ptype = double()))) + Output + + Error in `list_unchop()`: + ! Can't convert `a` to . + Code + (expect_error(list_unchop(list(1, a = "x", 2), indices = list(2, 1, 3), ptype = double())) + ) + Output + + Error in `list_unchop()`: + ! Can't convert `a` to . + Code + (expect_error(list_unchop(list(1, a = 2.5), ptype = integer()))) + Output + + Error in `list_unchop()`: + ! Can't convert from `a` to due to loss of precision. + * Locations: 1 + Code + (expect_error(list_unchop(list(1, a = 2.5), indices = list(2, 1), ptype = integer())) + ) + Output + + Error in `list_unchop()`: + ! Can't convert from `a` to due to loss of precision. + * Locations: 1 + # can specify a ptype to override common type Code @@ -202,7 +245,7 @@ Output Error in `list_unchop()`: - ! Can't convert to . + ! Can't convert `..1` to . # list_unchop() does not support non-numeric S3 indices diff --git a/tests/testthat/test-c.R b/tests/testthat/test-c.R index 24794621c..dd272783b 100644 --- a/tests/testthat/test-c.R +++ b/tests/testthat/test-c.R @@ -49,6 +49,19 @@ test_that("common type failure uses error call (#1641)", { }) }) +test_that("common type failure uses positional errors", { + expect_snapshot({ + # Looking for `..1` and `a` + (expect_error(vec_c(1, a = "x", 2))) + + # Directed cast should also produce directional errors (#1690) + (expect_error(vec_c(1, a = "x", 2, .ptype = double()))) + + # Lossy cast + (expect_error(vec_c(1, a = 2.5, .ptype = integer()))) + }) +}) + test_that("combines outer an inner names", { expect_equal(vec_c(x = 1), c(x = 1)) expect_equal(vec_c(c(x = 1)), c(x = 1)) @@ -104,6 +117,11 @@ test_that("can mix named and unnamed vectors (#271)", { expect_identical(vec_c(0, c(a = 1), 2, b = 3), c(0, a = 1, 2, b =3)) }) +test_that("preserves names when inputs are cast to a common type (#1690)", { + expect_named(vec_c(c(a = 1), .ptype = integer()), "a") + expect_named(vec_c(foo = c(a = 1), .ptype = integer(), .name_spec = "{outer}_{inner}"), "foo_a", ) +}) + test_that("vec_c() repairs names", { local_name_repair_quiet() diff --git a/tests/testthat/test-slice-chop.R b/tests/testthat/test-slice-chop.R index 0292be0db..3ee823971 100644 --- a/tests/testthat/test-slice-chop.R +++ b/tests/testthat/test-slice-chop.R @@ -430,6 +430,22 @@ test_that("unchopping takes the common type", { expect_type(list_unchop(x, indices), "double") }) +test_that("common type failure uses positional errors", { + expect_snapshot({ + # Looking for `..1` and `a` + (expect_error(list_unchop(list(1, a = "x", 2)))) + (expect_error(list_unchop(list(1, a = "x", 2), indices = list(2, 1, 3)))) + + # Directed cast should also produce directional errors (#1690) + (expect_error(list_unchop(list(1, a = "x", 2), ptype = double()))) + (expect_error(list_unchop(list(1, a = "x", 2), indices = list(2, 1, 3), ptype = double()))) + + # Lossy cast + (expect_error(list_unchop(list(1, a = 2.5), ptype = integer()))) + (expect_error(list_unchop(list(1, a = 2.5), indices = list(2, 1), ptype = integer()))) + }) +}) + test_that("can specify a ptype to override common type", { indices <- list(1, 2) From e3fff439eea4f6643a5bc4e145bbca3ce5946553 Mon Sep 17 00:00:00 2001 From: DavisVaughan Date: Fri, 30 Sep 2022 11:00:06 -0400 Subject: [PATCH 127/312] Redocument to show positional errors in help docs Follow up to #1700 --- man/howto-faq-coercion.Rd | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/man/howto-faq-coercion.Rd b/man/howto-faq-coercion.Rd index 7ca8cdecc..a5fffa849 100644 --- a/man/howto-faq-coercion.Rd +++ b/man/howto-faq-coercion.Rd @@ -257,10 +257,10 @@ types: \if{html}{\out{
}}\preformatted{vec_c(new_natural(1), 10L) #> Error in `vec_c()`: -#> ! Can't convert to . +#> ! Can't convert `..1` to . vec_c(1.5, new_natural(1)) #> Error in `vec_c()`: -#> ! Can't convert to . +#> ! Can't convert `..2` to . }\if{html}{\out{
}} This is quick work which completes the implementation of coercion From 3660f941b389e8e3bccb5d861329d2a7fa98571e Mon Sep 17 00:00:00 2001 From: DavisVaughan Date: Fri, 30 Sep 2022 11:08:12 -0400 Subject: [PATCH 128/312] Fix small typo in `repair` docs --- R/names.R | 2 +- man/vec_as_names.Rd | 2 +- man/vec_names.Rd | 2 +- 3 files changed, 3 insertions(+), 3 deletions(-) diff --git a/R/names.R b/R/names.R index a7cdf6e23..6a5755f15 100644 --- a/R/names.R +++ b/R/names.R @@ -39,7 +39,7 @@ #' @param repair Either a string or a function. If a string, it must be one of #' `"check_unique"`, `"minimal"`, `"unique"`, `"universal"`, `"unique_quiet"`, -#' or `"universal_quiet"` If a function, it is invoked with a vector of +#' or `"universal_quiet"`. If a function, it is invoked with a vector of #' minimal names and must return minimal names, otherwise an error is thrown. #' #' * Minimal names are never `NULL` or `NA`. When an element doesn't diff --git a/man/vec_as_names.Rd b/man/vec_as_names.Rd index d4a68159f..3c6effa31 100644 --- a/man/vec_as_names.Rd +++ b/man/vec_as_names.Rd @@ -21,7 +21,7 @@ vec_as_names( \item{repair}{Either a string or a function. If a string, it must be one of \code{"check_unique"}, \code{"minimal"}, \code{"unique"}, \code{"universal"}, \code{"unique_quiet"}, -or \code{"universal_quiet"} If a function, it is invoked with a vector of +or \code{"universal_quiet"}. If a function, it is invoked with a vector of minimal names and must return minimal names, otherwise an error is thrown. \itemize{ \item Minimal names are never \code{NULL} or \code{NA}. When an element doesn't diff --git a/man/vec_names.Rd b/man/vec_names.Rd index 70c9df7c4..293f13ef1 100644 --- a/man/vec_names.Rd +++ b/man/vec_names.Rd @@ -25,7 +25,7 @@ vec_set_names(x, names) \item{repair}{Either a string or a function. If a string, it must be one of \code{"check_unique"}, \code{"minimal"}, \code{"unique"}, \code{"universal"}, \code{"unique_quiet"}, -or \code{"universal_quiet"} If a function, it is invoked with a vector of +or \code{"universal_quiet"}. If a function, it is invoked with a vector of minimal names and must return minimal names, otherwise an error is thrown. \itemize{ \item Minimal names are never \code{NULL} or \code{NA}. When an element doesn't From 28b110f40eda8df778cfcc46ce0fea211ca830a1 Mon Sep 17 00:00:00 2001 From: Davis Vaughan Date: Fri, 30 Sep 2022 12:44:05 -0400 Subject: [PATCH 129/312] Remove `validate_list_of()` (#1697) * Remove `validate_list_of()` * NEWS bullet --- NAMESPACE | 1 - NEWS.md | 3 +++ R/type-list-of.R | 17 ----------------- man/list_of.Rd | 3 --- tests/testthat/test-type-list-of.R | 8 -------- 5 files changed, 3 insertions(+), 29 deletions(-) diff --git a/NAMESPACE b/NAMESPACE index 4ffec0c04..ce3d2d3cf 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -496,7 +496,6 @@ export(stop_incompatible_type) export(tib_cast) export(tib_ptype2) export(unspecified) -export(validate_list_of) export(vec_any_missing) export(vec_arith) export(vec_arith.Date) diff --git a/NEWS.md b/NEWS.md index 9bb933fe0..0f789df29 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,5 +1,8 @@ # vctrs (development version) +* `validate_list_of()` has been removed. It hasn't proven to be practically + useful, and isn't used by any packages on CRAN (#1697). + * Directed calls to `vec_c()`, like `vec_c(.ptype = )`, now mention the position of the problematic argument when there are cast errors (#1690). diff --git a/R/type-list-of.R b/R/type-list-of.R index 3b2b93da5..4210fa267 100644 --- a/R/type-list-of.R +++ b/R/type-list-of.R @@ -68,23 +68,6 @@ new_list_of0 <- function(x, ptype, ..., class = character()) { new_vctr(x, ..., ptype = ptype, class = c(class, "vctrs_list_of")) } -#' @export -#' @rdname list_of -validate_list_of <- function(x) { - if (!vec_is_list(x)) { - abort("`x` must be a list.") - } - - ptype <- attr(x, "ptype") - if (vec_size(ptype) != 0L) { - abort("`ptype` must have size 0.") - } - - walk(x, vec_cast, to = ptype) - - invisible(x) -} - #' @export #' @rdname list_of is_list_of <- function(x) { diff --git a/man/list_of.Rd b/man/list_of.Rd index 31e796a89..55e4bf7a4 100644 --- a/man/list_of.Rd +++ b/man/list_of.Rd @@ -3,7 +3,6 @@ \name{list_of} \alias{list_of} \alias{as_list_of} -\alias{validate_list_of} \alias{is_list_of} \alias{vec_ptype2.vctrs_list_of} \alias{vec_cast.vctrs_list_of} @@ -13,8 +12,6 @@ list_of(..., .ptype = NULL) as_list_of(x, ...) -validate_list_of(x) - is_list_of(x) \method{vec_ptype2}{vctrs_list_of}(x, y, ..., x_arg = "", y_arg = "") diff --git a/tests/testthat/test-type-list-of.R b/tests/testthat/test-type-list-of.R index 12045f5fc..eec79659b 100644 --- a/tests/testthat/test-type-list-of.R +++ b/tests/testthat/test-type-list-of.R @@ -188,14 +188,6 @@ test_that("invalid casts generate error", { expect_error(vec_cast(factor("a"), list_of(1)), class = "vctrs_error_incompatible_type") }) -test_that("validation", { - expect_error(validate_list_of(list_of(1, 2, 3)), NA) - expect_error( - validate_list_of(new_list_of(list(factor("foo")), vec_ptype(factor("bar")))), - class = "vctrs_error_cast_lossy" - ) -}) - test_that("list_of() has as.character() method (tidyverse/tidyr#654)", { exp <- rep(paste0("<", vec_ptype_abbr(mtcars), ">"), 2) expect_identical(as.character(list_of(mtcars, mtcars)), exp) From 6fbb3151086fc417288758d1d4475fd134589b5d Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Fri, 30 Sep 2022 13:12:11 +0200 Subject: [PATCH 130/312] Allow coercions between list and list-of Closes #1161 Closes #1231 --- NAMESPACE | 4 +++ NEWS.md | 2 ++ R/type-list-of.R | 22 ++++++++++++++++ tests/testthat/_snaps/type-list-of.md | 8 +++--- tests/testthat/test-type-list-of.R | 37 ++++++++++++++++++++++++--- 5 files changed, 66 insertions(+), 7 deletions(-) diff --git a/NAMESPACE b/NAMESPACE index ce3d2d3cf..88d84c5d5 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -226,6 +226,7 @@ S3method(vec_cast,integer.exclude) S3method(vec_cast,integer.omit) S3method(vec_cast,integer64) S3method(vec_cast,list) +S3method(vec_cast,list.vctrs_list_of) S3method(vec_cast,logical) S3method(vec_cast,omit.double) S3method(vec_cast,omit.integer) @@ -236,6 +237,7 @@ S3method(vec_cast,ordered.ordered) S3method(vec_cast,raw) S3method(vec_cast,table.table) S3method(vec_cast,vctrs_list_of) +S3method(vec_cast,vctrs_list_of.list) S3method(vec_cast,vctrs_rcrd) S3method(vec_cast,vctrs_rcrd.vctrs_rcrd) S3method(vec_cast,vctrs_vctr) @@ -340,6 +342,7 @@ S3method(vec_ptype2,integer.exclude) S3method(vec_ptype2,integer.omit) S3method(vec_ptype2,integer64) S3method(vec_ptype2,list) +S3method(vec_ptype2,list.vctrs_list_of) S3method(vec_ptype2,logical) S3method(vec_ptype2,omit.double) S3method(vec_ptype2,omit.integer) @@ -351,6 +354,7 @@ S3method(vec_ptype2,ordered.ordered) S3method(vec_ptype2,raw) S3method(vec_ptype2,table.table) S3method(vec_ptype2,vctrs_list_of) +S3method(vec_ptype2,vctrs_list_of.list) S3method(vec_ptype2,vctrs_partial_factor) S3method(vec_ptype2,vctrs_partial_frame) S3method(vec_ptype2.AsIs,AsIs) diff --git a/NEWS.md b/NEWS.md index 0f789df29..844577b23 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,5 +1,7 @@ # vctrs (development version) +* `list_of()` is now coercible with `list()` (#1161). + * `validate_list_of()` has been removed. It hasn't proven to be practically useful, and isn't used by any packages on CRAN (#1697). diff --git a/R/type-list-of.R b/R/type-list-of.R index 4210fa267..db2103f0d 100644 --- a/R/type-list-of.R +++ b/R/type-list-of.R @@ -176,6 +176,15 @@ vec_ptype2.vctrs_list_of.vctrs_list_of <- function(x, y, ...) { new_list_of0(x = list(), ptype = ptype) } +#' @export +vec_ptype2.list.vctrs_list_of <- function(x, y, ...) { + list() +} +#' @export +vec_ptype2.vctrs_list_of.list <- function(x, y, ...) { + list() +} + #' @rdname list_of #' @export vec_cast.vctrs_list_of #' @method vec_cast vctrs_list_of @@ -201,6 +210,19 @@ vec_cast.vctrs_list_of.vctrs_list_of <- function(x, to, ...) { } } +#' @export +vec_cast.list.vctrs_list_of <-function(x, to, ...) { + vec_data(x) +} +#' @export +vec_cast.vctrs_list_of.list <-function(x, to, ...) { + list_as_list_of( + x, + attr(to, "ptype"), + error_call = caller_env() + ) +} + # Helpers ----------------------------------------------------------------- list_as_list_of <- function(x, ptype = NULL, error_call = caller_env()) { diff --git a/tests/testthat/_snaps/type-list-of.md b/tests/testthat/_snaps/type-list-of.md index 5c46e692c..f48412b55 100644 --- a/tests/testthat/_snaps/type-list-of.md +++ b/tests/testthat/_snaps/type-list-of.md @@ -72,8 +72,8 @@ print(mat) Output list list_of list_of list_of - list "list" NA NA NA - list_of NA "list_of" "list_of" NA - list_of NA "list_of" "list_of" NA - list_of NA NA NA "list_of" + list "list" "list" "list" "list" + list_of "list" "list_of" "list_of" NA + list_of "list" "list_of" "list_of" NA + list_of "list" NA NA "list_of" diff --git a/tests/testthat/test-type-list-of.R b/tests/testthat/test-type-list-of.R index eec79659b..808a16cf5 100644 --- a/tests/testthat/test-type-list-of.R +++ b/tests/testthat/test-type-list-of.R @@ -168,12 +168,14 @@ test_that("safe casts work as expected", { expect_equal(vec_cast(NULL, x), NULL) expect_equal(vec_cast(NA, x), list_of(NULL, .ptype = double())) + expect_identical(vec_cast(list(1), x), list_of(1)) + expect_identical(vec_cast(list(TRUE), x), list_of(1)) + expect_identical(vec_cast(x, list()), list(1)) + expect_identical(vec_cast(x, list()), list(1)) + # These used to be allowed expect_error(vec_cast(1L, x), class = "vctrs_error_incompatible_type") expect_error(vec_cast(1, x), class = "vctrs_error_incompatible_type") - expect_error(vec_cast(list(1), x), class = "vctrs_error_incompatible_type") - expect_error(vec_cast(list(TRUE), x), class = "vctrs_error_incompatible_type") - expect_error(vec_cast(x, list()), class = "vctrs_error_incompatible_type") }) test_that("lossy casts generate warning (no longer the case)", { @@ -198,3 +200,32 @@ test_that("vec_ptype2(>, NA) is symmetric (#687)", { expect_identical(vec_ptype2(lof, NA), vec_ptype(lof)) expect_identical(vec_ptype2(NA, lof), vec_ptype(lof)) }) + +test_that("list_of() coerces to list() and list_of()", { + expect_equal(vec_ptype_common(list_of(1), list()), list()) + expect_equal(vec_cast_common(list_of(1), list()), list(list(1), list())) + + expect_equal(vec_ptype_common(list_of(1), list("")), list()) + expect_equal(vec_cast_common(list_of(1), list("")), list(list(1), list(""))) + + # FIXME + expect_error( + vec_ptype_common(list_of(1), list_of("")), + class = "vctrs_error_incompatible_type" + ) + expect_equal( + vec_ptype_common(list_of(1), list(), list_of("")), + list() + ) +}) + +test_that("can concatenate list and list-of (#1161)", { + expect_equal( + vec_c(list(1), list_of(2)), + list(1, 2) + ) + expect_equal( + vec_c(list(""), list_of(2)), + list("", 2) + ) +}) From f6c7f4c3a35eb061817594b7eda516a12e96809c Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Fri, 30 Sep 2022 13:34:57 +0200 Subject: [PATCH 131/312] Make `list_of` lax in case of incompatible inner type --- NEWS.md | 8 +++++++- R/type-list-of.R | 10 ++++++++-- tests/testthat/_snaps/type-list-of.md | 6 +++--- tests/testthat/test-type-list-of.R | 10 +++++++--- 4 files changed, 25 insertions(+), 9 deletions(-) diff --git a/NEWS.md b/NEWS.md index 844577b23..10e11c1e9 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,6 +1,12 @@ # vctrs (development version) -* `list_of()` is now coercible with `list()` (#1161). +* `list_of()` was relaxed to make it easier to combine. It is now + coercible with `list()` (#1161). When incompatible `list_of()` types + are combined, the result is now a bare `list()`. + + Following this change, the role of `list_of()` is mainly to carry + type information for potential optimisations, rather than to + guarantee a certain type throughout an analysis. * `validate_list_of()` has been removed. It hasn't proven to be practically useful, and isn't used by any packages on CRAN (#1697). diff --git a/R/type-list-of.R b/R/type-list-of.R index db2103f0d..7618b970b 100644 --- a/R/type-list-of.R +++ b/R/type-list-of.R @@ -171,8 +171,14 @@ vec_ptype2.vctrs_list_of <- function(x, y, ..., x_arg = "", y_arg = "") { } #' @method vec_ptype2.vctrs_list_of vctrs_list_of #' @export -vec_ptype2.vctrs_list_of.vctrs_list_of <- function(x, y, ...) { - ptype <- vec_ptype2(attr(x, "ptype"), attr(y, "ptype")) +vec_ptype2.vctrs_list_of.vctrs_list_of <- function(x, y, ..., x_arg = "", y_arg = "") { + frame <- current_env() + ptype <- tryCatch( + vec_ptype2(attr(x, "ptype"), attr(y, "ptype"), x_arg = x_arg, y_arg = y_arg), + vctrs_error_incompatible_type = function(cnd) { + return_from(frame, list()) + } + ) new_list_of0(x = list(), ptype = ptype) } diff --git a/tests/testthat/_snaps/type-list-of.md b/tests/testthat/_snaps/type-list-of.md index f48412b55..f2d2929a4 100644 --- a/tests/testthat/_snaps/type-list-of.md +++ b/tests/testthat/_snaps/type-list-of.md @@ -73,7 +73,7 @@ Output list list_of list_of list_of list "list" "list" "list" "list" - list_of "list" "list_of" "list_of" NA - list_of "list" "list_of" "list_of" NA - list_of "list" NA NA "list_of" + list_of "list" "list_of" "list_of" "list" + list_of "list" "list_of" "list_of" "list" + list_of "list" "list" "list" "list_of" diff --git a/tests/testthat/test-type-list-of.R b/tests/testthat/test-type-list-of.R index 808a16cf5..35976d429 100644 --- a/tests/testthat/test-type-list-of.R +++ b/tests/testthat/test-type-list-of.R @@ -173,6 +173,11 @@ test_that("safe casts work as expected", { expect_identical(vec_cast(x, list()), list(1)) expect_identical(vec_cast(x, list()), list(1)) + expect_error( + vec_cast(list_of(1), list_of("")), + class = "vctrs_error_incompatible_type" + ) + # These used to be allowed expect_error(vec_cast(1L, x), class = "vctrs_error_incompatible_type") expect_error(vec_cast(1, x), class = "vctrs_error_incompatible_type") @@ -208,10 +213,9 @@ test_that("list_of() coerces to list() and list_of()", { expect_equal(vec_ptype_common(list_of(1), list("")), list()) expect_equal(vec_cast_common(list_of(1), list("")), list(list(1), list(""))) - # FIXME - expect_error( + expect_equal( vec_ptype_common(list_of(1), list_of("")), - class = "vctrs_error_incompatible_type" + list() ) expect_equal( vec_ptype_common(list_of(1), list(), list_of("")), From 95cf269e8076d7bf423d93a59142e67654576b65 Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Sat, 1 Oct 2022 09:00:26 +0200 Subject: [PATCH 132/312] Extract `list_of_unstructure()` --- R/type-list-of.R | 12 ++++++++---- 1 file changed, 8 insertions(+), 4 deletions(-) diff --git a/R/type-list-of.R b/R/type-list-of.R index 7618b970b..3e384dfa7 100644 --- a/R/type-list-of.R +++ b/R/type-list-of.R @@ -68,6 +68,12 @@ new_list_of0 <- function(x, ptype, ..., class = character()) { new_vctr(x, ..., ptype = ptype, class = c(class, "vctrs_list_of")) } +list_of_unstructure <- function(x) { + attr(x, "ptype") <- NULL + attr(x, "class") <- NULL + x +} + #' @export #' @rdname list_of is_list_of <- function(x) { @@ -113,9 +119,7 @@ vec_ptype_abbr.vctrs_list_of <- function(x, ...) { #' @export as.list.vctrs_list_of <- function(x, ...) { - attr(x, "ptype") <- NULL - attr(x, "class") <- NULL - x + list_of_unstructure(x) } #' @export as.character.vctrs_list_of <- function(x, ...) { @@ -218,7 +222,7 @@ vec_cast.vctrs_list_of.vctrs_list_of <- function(x, to, ...) { #' @export vec_cast.list.vctrs_list_of <-function(x, to, ...) { - vec_data(x) + list_of_unstructure(x) } #' @export vec_cast.vctrs_list_of.list <-function(x, to, ...) { From 2481e4ef4f27e9c9739623cda918fbbd83c5844c Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Sat, 1 Oct 2022 09:05:35 +0200 Subject: [PATCH 133/312] Pass error call to cast methods --- R/type-list-of.R | 8 ++++---- tests/testthat/_snaps/type-list-of.md | 15 +++++++++++++++ tests/testthat/test-type-list-of.R | 9 +++++++++ 3 files changed, 28 insertions(+), 4 deletions(-) diff --git a/R/type-list-of.R b/R/type-list-of.R index 3e384dfa7..556f65a62 100644 --- a/R/type-list-of.R +++ b/R/type-list-of.R @@ -205,7 +205,7 @@ vec_cast.vctrs_list_of <- function(x, to, ...) { #' @export #' @method vec_cast.vctrs_list_of vctrs_list_of -vec_cast.vctrs_list_of.vctrs_list_of <- function(x, to, ...) { +vec_cast.vctrs_list_of.vctrs_list_of <- function(x, to, ..., call = caller_env()) { x_ptype <- attr(x, "ptype", exact = TRUE) to_ptype <- attr(to, "ptype", exact = TRUE) @@ -216,7 +216,7 @@ vec_cast.vctrs_list_of.vctrs_list_of <- function(x, to, ...) { x } else { x <- unclass(x) - list_as_list_of(x, ptype = to_ptype) + list_as_list_of(x, ptype = to_ptype, error_call = call) } } @@ -225,11 +225,11 @@ vec_cast.list.vctrs_list_of <-function(x, to, ...) { list_of_unstructure(x) } #' @export -vec_cast.vctrs_list_of.list <-function(x, to, ...) { +vec_cast.vctrs_list_of.list <-function(x, to, ..., call = caller_env()) { list_as_list_of( x, attr(to, "ptype"), - error_call = caller_env() + error_call = call ) } diff --git a/tests/testthat/_snaps/type-list-of.md b/tests/testthat/_snaps/type-list-of.md index f2d2929a4..f7c9b4003 100644 --- a/tests/testthat/_snaps/type-list-of.md +++ b/tests/testthat/_snaps/type-list-of.md @@ -77,3 +77,18 @@ list_of "list" "list_of" "list_of" "list" list_of "list" "list" "list" "list_of" +# error call is passed to inner cast methods + + Code + (expect_error(fn1())) + Output + + Error in `fn1()`: + ! Can't convert `..1` to . + Code + (expect_error(fn2())) + Output + + Error in `fn2()`: + ! Can't convert `..1` to . + diff --git a/tests/testthat/test-type-list-of.R b/tests/testthat/test-type-list-of.R index 35976d429..7229ef9c9 100644 --- a/tests/testthat/test-type-list-of.R +++ b/tests/testthat/test-type-list-of.R @@ -183,6 +183,15 @@ test_that("safe casts work as expected", { expect_error(vec_cast(1, x), class = "vctrs_error_incompatible_type") }) +test_that("error call is passed to inner cast methods", { + fn1 <- function() vec_cast(list_of(1), list_of("")) + fn2 <- function() vec_cast(list(1), list_of("")) + expect_snapshot({ + (expect_error(fn1())) + (expect_error(fn2())) + }) +}) + test_that("lossy casts generate warning (no longer the case)", { # This used to be a lossy cast warning expect_error( From 09b3fd0505bb3448c74fef4a3dc99ffd300dd2ef Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Sat, 1 Oct 2022 09:06:18 +0200 Subject: [PATCH 134/312] Apply suggestions from code review Co-authored-by: Davis Vaughan --- R/type-list-of.R | 17 ++++++++++++----- tests/testthat/test-type-list-of.R | 2 +- 2 files changed, 13 insertions(+), 6 deletions(-) diff --git a/R/type-list-of.R b/R/type-list-of.R index 556f65a62..84714b89b 100644 --- a/R/type-list-of.R +++ b/R/type-list-of.R @@ -176,14 +176,21 @@ vec_ptype2.vctrs_list_of <- function(x, y, ..., x_arg = "", y_arg = "") { #' @method vec_ptype2.vctrs_list_of vctrs_list_of #' @export vec_ptype2.vctrs_list_of.vctrs_list_of <- function(x, y, ..., x_arg = "", y_arg = "") { - frame <- current_env() - ptype <- tryCatch( - vec_ptype2(attr(x, "ptype"), attr(y, "ptype"), x_arg = x_arg, y_arg = y_arg), + x_ptype <- attr(x, "ptype", exact = TRUE) + y_ptype <- attr(y, "ptype", exact = TRUE) + if (identical(x_ptype, y_ptype)) { + return(x) + } + + tryCatch( + expr = { + ptype <- vec_ptype2(x_ptype, y_ptype, x_arg = x_arg, y_arg = y_arg) + new_list_of0(x = list(), ptype = ptype) + }, vctrs_error_incompatible_type = function(cnd) { - return_from(frame, list()) + list() } ) - new_list_of0(x = list(), ptype = ptype) } #' @export diff --git a/tests/testthat/test-type-list-of.R b/tests/testthat/test-type-list-of.R index 7229ef9c9..641254c83 100644 --- a/tests/testthat/test-type-list-of.R +++ b/tests/testthat/test-type-list-of.R @@ -215,7 +215,7 @@ test_that("vec_ptype2(>, NA) is symmetric (#687)", { expect_identical(vec_ptype2(NA, lof), vec_ptype(lof)) }) -test_that("list_of() coerces to list() and list_of()", { +test_that("list_of() coerces to list() and list_of() (#1701)", { expect_equal(vec_ptype_common(list_of(1), list()), list()) expect_equal(vec_cast_common(list_of(1), list()), list(list(1), list())) From 5745004e4b554697f246538cfa792b06855eeb3a Mon Sep 17 00:00:00 2001 From: Davis Vaughan Date: Mon, 3 Oct 2022 13:52:01 -0400 Subject: [PATCH 135/312] No need for `_quiet` enum options (#1703) At the C level, we create the `name_repair_opts` struct through either: - `new_name_repair_opts()`, which handles translating the `"unique_quiet"` and `"universal_quiet"` strings into existing enum options - Manual creation of the struct, with a hardcoded enum value and control of `quiet` This means the enum options themselves don't need to know about `_quiet` --- src/names.c | 8 -------- src/names.h | 2 -- 2 files changed, 10 deletions(-) diff --git a/src/names.c b/src/names.c index 58956936d..d0d7f257b 100644 --- a/src/names.c +++ b/src/names.c @@ -17,12 +17,6 @@ r_obj* vec_as_names(r_obj* names, const struct name_repair_opts* opts) { case NAME_REPAIR_unique: return vec_as_unique_names(names, opts->quiet); case NAME_REPAIR_universal: return vec_as_universal_names(names, opts->quiet); case NAME_REPAIR_check_unique: return check_unique_names(names, opts); - // At the time when unique_quiet and universal_quiet were added, no function - // that calls the C function vec_as_names() actually accepts these strings at - // the R level, because these functions enforce `quiet = false`. - // But we still have to handle every case for the enum. - case NAME_REPAIR_unique_quiet: return vec_as_unique_names(names, true); - case NAME_REPAIR_universal_quiet: return vec_as_universal_names(names, true); case NAME_REPAIR_custom: return vec_as_custom_names(names, opts); } r_stop_unreachable(); @@ -943,8 +937,6 @@ const char* name_repair_arg_as_c_string(enum name_repair_type type) { case NAME_REPAIR_unique: return "unique"; case NAME_REPAIR_universal: return "universal"; case NAME_REPAIR_check_unique: return "check_unique"; - case NAME_REPAIR_unique_quiet: return "unique_quiet"; - case NAME_REPAIR_universal_quiet: return "universal_quiet"; case NAME_REPAIR_custom: return "custom"; } r_stop_unreachable(); diff --git a/src/names.h b/src/names.h index 7025cf27d..7cb75ab13 100644 --- a/src/names.h +++ b/src/names.h @@ -21,8 +21,6 @@ enum name_repair_type { NAME_REPAIR_unique, NAME_REPAIR_universal, NAME_REPAIR_check_unique, - NAME_REPAIR_unique_quiet, - NAME_REPAIR_universal_quiet, NAME_REPAIR_custom = 99 }; From 39e1adcbd721f36c45b4f35361520e8ecf01eb18 Mon Sep 17 00:00:00 2001 From: Davis Vaughan Date: Mon, 3 Oct 2022 14:09:03 -0400 Subject: [PATCH 136/312] Ensure `vec_rep_each(times = 0)` early exit works properly (#1708) * Use `vec_slice()` rather than `vec_ptype()` * NEWS bullet --- NEWS.md | 3 +++ src/rep.c | 2 +- tests/testthat/test-rep.R | 9 +++++++++ 3 files changed, 13 insertions(+), 1 deletion(-) diff --git a/NEWS.md b/NEWS.md index 10e11c1e9..f51b2551d 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,5 +1,8 @@ # vctrs (development version) +* `vec_rep_each(times = 0)` now works correctly with logical vectors that are + considered unspecified and with named vectors (#1673). + * `list_of()` was relaxed to make it easier to combine. It is now coercible with `list()` (#1161). When incompatible `list_of()` types are combined, the result is now a bare `list()`. diff --git a/src/rep.c b/src/rep.c index cd6490863..7b1e57deb 100644 --- a/src/rep.c +++ b/src/rep.c @@ -96,7 +96,7 @@ r_obj* vec_rep_each(r_obj* x, if (times_ == 1) { out = x; } else if (times_ == 0) { - out = vec_ptype(x, p_x_arg, error_call); + out = vec_slice_unsafe(x, r_globals.empty_int); } else { out = vec_rep_each_uniform(x, times_, error_call, p_times_arg); } diff --git a/tests/testthat/test-rep.R b/tests/testthat/test-rep.R index ea6daaa0c..e3346707a 100644 --- a/tests/testthat/test-rep.R +++ b/tests/testthat/test-rep.R @@ -58,6 +58,15 @@ test_that("`vec_rep_each()` can repeat 0 `times`", { expect_identical(vec_rep_each(1:2, 0), integer()) }) +test_that("`vec_rep_each()` finalizes type when repeating 0 times (#1673)", { + expect_identical(vec_rep_each(NA, 0), logical()) +}) + +test_that("`vec_rep_each()` retains names when repeating 0 times (#1673)", { + x <- c(a = 1, b = 2) + expect_identical(vec_rep_each(x, 0), named(numeric())) +}) + test_that("`vec_rep_each()` can repeat 1 `time`", { expect_identical(vec_rep_each(1:2, 1), 1:2) }) From bce4cd0c76bab8a9b31679496874c736cbea6549 Mon Sep 17 00:00:00 2001 From: Davis Vaughan Date: Mon, 3 Oct 2022 14:19:19 -0400 Subject: [PATCH 137/312] Add `.error_arg` to `vec_c()` (#1709) * Add `.error_arg` to `vec_c()` * NEWS bullet --- NEWS.md | 2 +- R/c.R | 1 + man/vec_c.Rd | 5 +++++ src/bind.c | 10 +++++++++- src/c-unchop.c | 5 +++-- src/c.c | 21 ++++++++++++++++----- src/c.h | 7 ++++++- src/globals.c | 1 + src/globals.h | 1 + src/interval.c | 2 ++ src/match-joint.c | 9 ++++++++- src/type-factor.c | 1 + tests/testthat/_snaps/c.md | 26 +++++++++++++------------- tests/testthat/test-c.R | 16 ++++++++-------- 14 files changed, 75 insertions(+), 32 deletions(-) diff --git a/NEWS.md b/NEWS.md index f51b2551d..a7a7836b2 100644 --- a/NEWS.md +++ b/NEWS.md @@ -30,7 +30,7 @@ * `list_unchop()` has gained an `error_call` argument (#1641). -* `vec_c()` has gained an `.error_call` argument (#1641). +* `vec_c()` has gained `.error_call` and `.error_arg` arguments (#1641, #1692). * Improved the performance of list-of common type methods (#1686, #875). diff --git a/R/c.R b/R/c.R index 9afda2559..89b058e3a 100644 --- a/R/c.R +++ b/R/c.R @@ -69,6 +69,7 @@ vec_c <- function(..., .ptype = NULL, .name_spec = NULL, .name_repair = c("minimal", "unique", "check_unique", "universal"), + .error_arg = "", .error_call = current_env()) { .External2(ffi_vec_c, .ptype, .name_spec, .name_repair) } diff --git a/man/vec_c.Rd b/man/vec_c.Rd index 5ac0e77a6..130d17c17 100644 --- a/man/vec_c.Rd +++ b/man/vec_c.Rd @@ -9,6 +9,7 @@ vec_c( .ptype = NULL, .name_spec = NULL, .name_repair = c("minimal", "unique", "check_unique", "universal"), + .error_arg = "", .error_call = current_env() ) } @@ -43,6 +44,10 @@ See the \link[=name_spec]{name specification topic}.} \item{.name_repair}{How to repair names, see \code{repair} options in \code{\link[=vec_as_names]{vec_as_names()}}.} +\item{.error_arg}{An argument name as a string. This argument +will be mentioned in error messages as the input that is at the +origin of a problem.} + \item{.error_call}{The execution environment of a currently running function, e.g. \code{caller_env()}. The function will be mentioned in error messages as the source of the error. See the diff --git a/src/bind.c b/src/bind.c index 017a64be9..d2358e9bc 100644 --- a/src/bind.c +++ b/src/bind.c @@ -285,7 +285,15 @@ void df_c_fallback(r_obj* out, FREE(1); } else if (vec_is_common_class_fallback(ptype_col)) { r_obj* xs_col = KEEP(list_pluck(xs, i)); - r_obj* out_col = vec_c_fallback(ptype_col, xs_col, name_spec, name_repair, error_call); + + r_obj* out_col = vec_c_fallback( + ptype_col, + xs_col, + name_spec, + name_repair, + vec_args.empty, + error_call + ); r_list_poke(out, i, out_col); if (vec_size(out_col) != n_rows) { diff --git a/src/c-unchop.c b/src/c-unchop.c index 2d0d888d5..920ee7c62 100644 --- a/src/c-unchop.c +++ b/src/c-unchop.c @@ -19,7 +19,7 @@ r_obj* list_unchop(r_obj* xs, vec_check_list(xs, vec_args.x, error_call); if (indices == r_null) { - return vec_c(xs, ptype, name_spec, name_repair, error_call); + return vec_c(xs, ptype, name_spec, name_repair, vec_args.empty, error_call); } // Apply size/type checking to `indices` before possibly early exiting from @@ -223,7 +223,7 @@ r_obj* list_unchop_fallback(r_obj* ptype, if (homogeneous) { out = KEEP(vec_c_fallback_invoke(x, name_spec, error_call)); } else { - out = KEEP(vec_c_fallback(ptype, x, name_spec, name_repair, error_call)); + out = KEEP(vec_c_fallback(ptype, x, name_spec, name_repair, vec_args.empty, error_call)); } const struct name_repair_opts name_repair_opts = { @@ -237,6 +237,7 @@ r_obj* list_unchop_fallback(r_obj* ptype, r_globals.empty_int, r_null, &name_repair_opts, + vec_args.empty, error_call )); diff --git a/src/c.c b/src/c.c index 67424fa79..8a2225935 100644 --- a/src/c.c +++ b/src/c.c @@ -5,12 +5,13 @@ r_obj* vec_c(r_obj* xs, r_obj* ptype, r_obj* name_spec, const struct name_repair_opts* name_repair, + struct vctrs_arg* p_error_arg, struct r_lazy error_call) { struct fallback_opts opts = { .df = DF_FALLBACK_DEFAULT, .s3 = S3_FALLBACK_true }; - return vec_c_opts(xs, ptype, name_spec, name_repair, &opts, error_call); + return vec_c_opts(xs, ptype, name_spec, name_repair, &opts, p_error_arg, error_call); } r_obj* vec_c_opts(r_obj* xs, @@ -18,8 +19,10 @@ r_obj* vec_c_opts(r_obj* xs, r_obj* name_spec, const struct name_repair_opts* name_repair, const struct fallback_opts* fallback_opts, + struct vctrs_arg* p_error_arg, struct r_lazy error_call) { struct ptype_common_opts ptype_opts = { + .p_arg = p_error_arg, .call = error_call, .fallback = *fallback_opts }; @@ -33,7 +36,7 @@ r_obj* vec_c_opts(r_obj* xs, } if (needs_vec_c_fallback(ptype)) { - r_obj* out = vec_c_fallback(ptype, xs, name_spec, name_repair, error_call); + r_obj* out = vec_c_fallback(ptype, xs, name_spec, name_repair, p_error_arg, error_call); FREE(1); return out; } @@ -99,7 +102,7 @@ r_obj* vec_c_opts(r_obj* xs, r_ssize i = 0; struct vctrs_arg* p_x_arg = new_subscript_arg( - vec_args.empty, + p_error_arg, xs_names, xs_size, &i @@ -184,6 +187,9 @@ r_obj* ffi_vec_c(r_obj* ffi_call, r_obj* op, r_obj* args, r_obj* frame) { r_obj* name_spec = KEEP(r_eval(r_node_car(args), frame)); args = r_node_cdr(args); r_obj* name_repair = KEEP(r_eval(r_node_car(args), frame)); + struct r_lazy error_arg_lazy = { .x = syms.dot_error_arg, .env = frame }; + struct vctrs_arg error_arg = new_lazy_arg(&error_arg_lazy); + struct r_lazy error_call = { .x = syms.dot_error_call, .env = frame }; struct name_repair_opts name_repair_opts = @@ -193,7 +199,7 @@ r_obj* ffi_vec_c(r_obj* ffi_call, r_obj* op, r_obj* args, r_obj* frame) { error_call); KEEP(name_repair_opts.shelter); - r_obj* out = vec_c(xs, ptype, name_spec, &name_repair_opts, error_call); + r_obj* out = vec_c(xs, ptype, name_spec, &name_repair_opts, &error_arg, error_call); FREE(5); return out; @@ -274,6 +280,7 @@ r_obj* vec_c_fallback(r_obj* ptype, r_obj* xs, r_obj* name_spec, const struct name_repair_opts* name_repair, + struct vctrs_arg* p_error_arg, struct r_lazy error_call) { r_obj* class = KEEP(r_attrib_get(ptype, syms_fallback_class)); bool implements_c = class_implements_base_c(class); @@ -283,6 +290,7 @@ r_obj* vec_c_fallback(r_obj* ptype, return vec_c_fallback_invoke(xs, name_spec, error_call); } else { struct ptype_common_opts ptype_opts = { + .p_arg = p_error_arg, .call = error_call, .fallback = { .df = DF_FALLBACK_none, @@ -303,12 +311,15 @@ r_obj* vec_c_fallback(r_obj* ptype, name_spec, name_repair, &ptype_opts.fallback, + p_error_arg, error_call ); } } -r_obj* vec_c_fallback_invoke(r_obj* xs, r_obj* name_spec, struct r_lazy error_call) { +r_obj* vec_c_fallback_invoke(r_obj* xs, + r_obj* name_spec, + struct r_lazy error_call) { r_obj* x = list_first_non_null(xs, NULL); if (vctrs_debug_verbose) { diff --git a/src/c.h b/src/c.h index f7d7bb749..5f48335c1 100644 --- a/src/c.h +++ b/src/c.h @@ -10,6 +10,7 @@ r_obj* vec_c(r_obj* xs, r_obj* ptype, r_obj* name_spec, const struct name_repair_opts* name_repair, + struct vctrs_arg* p_error_arg, struct r_lazy error_call); r_obj* vec_c_opts(r_obj* xs, @@ -17,13 +18,17 @@ r_obj* vec_c_opts(r_obj* xs, r_obj* name_spec, const struct name_repair_opts* name_repair, const struct fallback_opts* fallback_opts, + struct vctrs_arg* p_error_arg, struct r_lazy error_call); -r_obj* vec_c_fallback_invoke(r_obj* xs, r_obj* name_spec, struct r_lazy error_call); +r_obj* vec_c_fallback_invoke(r_obj* xs, + r_obj* name_spec, + struct r_lazy error_call); r_obj* vec_c_fallback(r_obj* ptype, r_obj* xs, r_obj* name_spec, const struct name_repair_opts* name_repair, + struct vctrs_arg* p_error_arg, struct r_lazy error_call); bool needs_vec_c_fallback(r_obj* ptype); diff --git a/src/globals.c b/src/globals.c index f406fc333..3ee74a9fa 100644 --- a/src/globals.c +++ b/src/globals.c @@ -51,6 +51,7 @@ void vctrs_init_globals(r_obj* ns) { syms.arg = r_sym("arg"); syms.dot_arg = r_sym(".arg"); syms.dot_call = r_sym(".call"); + syms.dot_error_arg = r_sym(".error_arg"); syms.dot_error_call = r_sym(".error_call"); syms.haystack_arg = r_sym("haystack_arg"); syms.needles_arg = r_sym("needles_arg"); diff --git a/src/globals.h b/src/globals.h index 0e879fa7a..8286087fe 100644 --- a/src/globals.h +++ b/src/globals.h @@ -8,6 +8,7 @@ struct syms { r_obj* arg; r_obj* dot_arg; r_obj* dot_call; + r_obj* dot_error_arg; r_obj* dot_error_call; r_obj* haystack_arg; r_obj* needles_arg; diff --git a/src/interval.c b/src/interval.c index 9120c7897..2769ac79e 100644 --- a/src/interval.c +++ b/src/interval.c @@ -685,6 +685,7 @@ r_obj* vec_interval_complement(r_obj* start, ptype, R_NilValue, &name_repair_opts, + vec_args.empty, r_lazy_null ), &n_prot); } @@ -699,6 +700,7 @@ r_obj* vec_interval_complement(r_obj* start, ptype, R_NilValue, &name_repair_opts, + vec_args.empty, r_lazy_null ), &n_prot); } diff --git a/src/match-joint.c b/src/match-joint.c index c4f808092..6b8e7fa1c 100644 --- a/src/match-joint.c +++ b/src/match-joint.c @@ -297,7 +297,14 @@ r_obj* vec_joint_proxy_order_dependent(r_obj* x, r_obj* y) { // size of `vec_locate_matches()` input to // `vec_size(x) + vec_size(y) <= INT_MAX` // when foreign columns are used. - r_obj* combined = KEEP(vec_c(out, ptype, r_null, p_no_repair_opts, r_lazy_null)); + r_obj* combined = KEEP(vec_c( + out, + ptype, + r_null, + p_no_repair_opts, + vec_args.empty, + r_lazy_null + )); // Compute joint order-proxy r_obj* proxy = KEEP(vec_proxy_order(combined)); diff --git a/src/type-factor.c b/src/type-factor.c index 5a380b257..6ff18978e 100644 --- a/src/type-factor.c +++ b/src/type-factor.c @@ -78,6 +78,7 @@ static SEXP levels_union(SEXP x, SEXP y) { r_globals.empty_chr, R_NilValue, &name_repair_opts, + vec_args.empty, r_lazy_null )); diff --git a/tests/testthat/_snaps/c.md b/tests/testthat/_snaps/c.md index fa0f801e1..dedd3edd2 100644 --- a/tests/testthat/_snaps/c.md +++ b/tests/testthat/_snaps/c.md @@ -1,18 +1,18 @@ -# common type failure uses error call (#1641) +# common type failure uses error call and error arg (#1641, #1692) Code - vec_c("x", 1, .error_call = call("foo")) + vec_c("x", 1, .error_call = call("foo"), .error_arg = "arg") Condition Error in `foo()`: - ! Can't combine `..1` and `..2` . + ! Can't combine `arg[[1]]` and `arg[[2]]` . --- Code - vec_c("x", .ptype = integer(), .error_call = call("foo")) + vec_c("x", .ptype = integer(), .error_call = call("foo"), .error_arg = "arg") Condition Error in `foo()`: - ! Can't convert `..1` to . + ! Can't convert `arg[[1]]` to . # common type failure uses positional errors @@ -23,11 +23,11 @@ Error in `vec_c()`: ! Can't combine `..1` and `a` . Code - (expect_error(vec_c(1, a = "x", 2, .ptype = double()))) + (expect_error(vec_c(1, a = "x", 2, .ptype = double(), .error_arg = "arg"))) Output Error in `vec_c()`: - ! Can't convert `a` to . + ! Can't convert `arg$a` to . Code (expect_error(vec_c(1, a = 2.5, .ptype = integer()))) Output @@ -74,12 +74,12 @@ i The author of the class should implement vctrs methods. i See . Code - (expect_error(vec_c(x, y, .error_call = call("foo")), class = "vctrs_error_incompatible_type") - ) + (expect_error(vec_c(x, y, .error_call = call("foo"), .error_arg = "arg"), + class = "vctrs_error_incompatible_type")) Output Error in `foo()`: - ! Can't combine `..1` and `..2` . + ! Can't combine `arg[[1]]` and `arg[[2]]` . x Some attributes are incompatible. i The author of the class should implement vctrs methods. i See . @@ -98,12 +98,12 @@ i The author of the class should implement vctrs methods. i See . Code - (expect_error(vec_c(joe, jane, .error_call = call("foo")), class = "vctrs_error_incompatible_type") - ) + (expect_error(vec_c(joe, jane, .error_call = call("foo"), .error_arg = "arg"), + class = "vctrs_error_incompatible_type")) Output Error in `foo()`: - ! Can't combine `..1` and `..2` . + ! Can't combine `arg[[1]]` and `arg[[2]]` . x Some attributes are incompatible. i The author of the class should implement vctrs methods. i See . diff --git a/tests/testthat/test-c.R b/tests/testthat/test-c.R index dd272783b..cf34d4a3e 100644 --- a/tests/testthat/test-c.R +++ b/tests/testthat/test-c.R @@ -40,12 +40,12 @@ test_that("specified .ptypes do not allow more casts", { ) }) -test_that("common type failure uses error call (#1641)", { +test_that("common type failure uses error call and error arg (#1641, #1692)", { expect_snapshot(error = TRUE, { - vec_c("x", 1, .error_call = call("foo")) + vec_c("x", 1, .error_call = call("foo"), .error_arg = "arg") }) expect_snapshot(error = TRUE, { - vec_c("x", .ptype = integer(), .error_call = call("foo")) + vec_c("x", .ptype = integer(), .error_call = call("foo"), .error_arg = "arg") }) }) @@ -54,8 +54,8 @@ test_that("common type failure uses positional errors", { # Looking for `..1` and `a` (expect_error(vec_c(1, a = "x", 2))) - # Directed cast should also produce directional errors (#1690) - (expect_error(vec_c(1, a = "x", 2, .ptype = double()))) + # Directed cast should also produce positional errors (#1690) + (expect_error(vec_c(1, a = "x", 2, .ptype = double(), .error_arg = "arg"))) # Lossy cast (expect_error(vec_c(1, a = 2.5, .ptype = integer()))) @@ -119,7 +119,7 @@ test_that("can mix named and unnamed vectors (#271)", { test_that("preserves names when inputs are cast to a common type (#1690)", { expect_named(vec_c(c(a = 1), .ptype = integer()), "a") - expect_named(vec_c(foo = c(a = 1), .ptype = integer(), .name_spec = "{outer}_{inner}"), "foo_a", ) + expect_named(vec_c(foo = c(a = 1), .ptype = integer(), .name_spec = "{outer}_{inner}"), "foo_a") }) test_that("vec_c() repairs names", { @@ -210,7 +210,7 @@ test_that("vec_c() fails with complex foreign S3 classes", { x <- structure(foobar(1), attr_foo = "foo") y <- structure(foobar(2), attr_bar = "bar") (expect_error(vec_c(x, y), class = "vctrs_error_incompatible_type")) - (expect_error(vec_c(x, y, .error_call = call("foo")), class = "vctrs_error_incompatible_type")) + (expect_error(vec_c(x, y, .error_call = call("foo"), .error_arg = "arg"), class = "vctrs_error_incompatible_type")) }) }) @@ -219,7 +219,7 @@ test_that("vec_c() fails with complex foreign S4 classes", { joe <- .Counts(c(1L, 2L), name = "Joe") jane <- .Counts(3L, name = "Jane") (expect_error(vec_c(joe, jane), class = "vctrs_error_incompatible_type")) - (expect_error(vec_c(joe, jane, .error_call = call("foo")), class = "vctrs_error_incompatible_type")) + (expect_error(vec_c(joe, jane, .error_call = call("foo"), .error_arg = "arg"), class = "vctrs_error_incompatible_type")) }) }) From 2d33d97272aff90a84b8043c4d2262276d8e186c Mon Sep 17 00:00:00 2001 From: Davis Vaughan Date: Tue, 4 Oct 2022 11:25:04 -0400 Subject: [PATCH 138/312] Add `error_arg` to `list_unchop()` (#1712) * Add `error_arg` to `list_unchop()` * Pass the call through `vec_recycle_fallback()` * NEWS bullet * Use `"x"` as the `error_arg` default since we use `current_env()` i.e. `list_unchop()` has completely ownership over the default errors --- NEWS.md | 3 +- R/slice-chop.R | 1 + man/vec_chop.Rd | 5 ++ src/c-unchop.c | 71 +++++++++++----- src/decl/c-unchop-decl.h | 6 +- src/size.c | 5 +- src/size.h | 3 +- tests/testthat/_snaps/slice-chop.md | 120 ++++++++++++++++++---------- tests/testthat/test-slice-chop.R | 55 ++++++++----- 9 files changed, 182 insertions(+), 87 deletions(-) diff --git a/NEWS.md b/NEWS.md index a7a7836b2..21f398729 100644 --- a/NEWS.md +++ b/NEWS.md @@ -28,7 +28,8 @@ options are used, any setting of `quiet` is silently overridden (@jennybc, #1629). -* `list_unchop()` has gained an `error_call` argument (#1641). +* `list_unchop()` has gained `error_call` and `error_arg` arguments (#1641, + #1692). * `vec_c()` has gained `.error_call` and `.error_arg` arguments (#1641, #1692). diff --git a/R/slice-chop.R b/R/slice-chop.R index 2606e03f1..ab1b8717d 100644 --- a/R/slice-chop.R +++ b/R/slice-chop.R @@ -98,6 +98,7 @@ list_unchop <- function(x, ptype = NULL, name_spec = NULL, name_repair = c("minimal", "unique", "check_unique", "universal"), + error_arg = "x", error_call = current_env()) { .Call(ffi_list_unchop, x, indices, ptype, name_spec, name_repair, environment()) } diff --git a/man/vec_chop.Rd b/man/vec_chop.Rd index dddb7657d..5a1e02780 100644 --- a/man/vec_chop.Rd +++ b/man/vec_chop.Rd @@ -13,6 +13,7 @@ list_unchop( ptype = NULL, name_spec = NULL, name_repair = c("minimal", "unique", "check_unique", "universal"), + error_arg = "x", error_call = current_env() ) } @@ -54,6 +55,10 @@ See the \link[=name_spec]{name specification topic}.} \item{name_repair}{How to repair names, see \code{repair} options in \code{\link[=vec_as_names]{vec_as_names()}}.} +\item{error_arg}{An argument name as a string. This argument +will be mentioned in error messages as the input that is at the +origin of a problem.} + \item{error_call}{The execution environment of a currently running function, e.g. \code{caller_env()}. The function will be mentioned in error messages as the source of the error. See the diff --git a/src/c-unchop.c b/src/c-unchop.c index 920ee7c62..c465bd23c 100644 --- a/src/c-unchop.c +++ b/src/c-unchop.c @@ -15,11 +15,12 @@ r_obj* list_unchop(r_obj* xs, r_obj* ptype, r_obj* name_spec, const struct name_repair_opts* name_repair, + struct vctrs_arg* p_error_arg, struct r_lazy error_call) { - vec_check_list(xs, vec_args.x, error_call); + vec_check_list(xs, p_error_arg, error_call); if (indices == r_null) { - return vec_c(xs, ptype, name_spec, name_repair, vec_args.empty, error_call); + return vec_c(xs, ptype, name_spec, name_repair, p_error_arg, error_call); } // Apply size/type checking to `indices` before possibly early exiting from @@ -36,18 +37,36 @@ r_obj* list_unchop(r_obj* xs, ptype, DF_FALLBACK_DEFAULT, S3_FALLBACK_true, - vec_args.empty, + p_error_arg, error_call)); if (needs_vec_c_fallback(ptype)) { - r_obj* out = list_unchop_fallback(ptype, xs, indices, name_spec, name_repair, FALLBACK_HOMOGENEOUS_false, error_call); + r_obj* out = list_unchop_fallback( + ptype, + xs, + indices, + name_spec, + name_repair, + FALLBACK_HOMOGENEOUS_false, + p_error_arg, + error_call + ); FREE(1); return out; } // FIXME: Needed for dplyr::summarise() which passes a non-fallback ptype if (needs_vec_c_homogeneous_fallback(xs, ptype)) { - r_obj* out = list_unchop_fallback(ptype, xs, indices, name_spec, name_repair, FALLBACK_HOMOGENEOUS_true, error_call); + r_obj* out = list_unchop_fallback( + ptype, + xs, + indices, + name_spec, + name_repair, + FALLBACK_HOMOGENEOUS_true, + p_error_arg, + error_call + ); FREE(1); return out; } @@ -83,7 +102,7 @@ r_obj* list_unchop(r_obj* xs, r_ssize i = 0; struct vctrs_arg* p_x_arg = new_subscript_arg( - vec_args.empty, + p_error_arg, xs_names, xs_size, &i @@ -168,6 +187,9 @@ r_obj* ffi_list_unchop(r_obj* x, r_obj* name_spec, r_obj* name_repair, r_obj* frame) { + struct r_lazy error_arg_lazy = { .x = r_syms.error_arg, .env = frame }; + struct vctrs_arg error_arg = new_lazy_arg(&error_arg_lazy); + struct r_lazy error_call = { .x = r_syms.error_call, .env = frame }; struct name_repair_opts name_repair_opts = @@ -183,6 +205,7 @@ r_obj* ffi_list_unchop(r_obj* x, ptype, name_spec, &name_repair_opts, + &error_arg, error_call ); @@ -196,34 +219,46 @@ r_obj* ffi_list_unchop(r_obj* x, // with recycling of each element of `x` to the corresponding index size static r_obj* list_unchop_fallback(r_obj* ptype, - r_obj* x, + r_obj* xs, r_obj* indices, r_obj* name_spec, const struct name_repair_opts* name_repair, enum fallback_homogeneous homogeneous, + struct vctrs_arg* p_error_arg, struct r_lazy error_call) { - r_ssize x_size = vec_size(x); - x = KEEP(r_clone_referenced(x)); + r_ssize xs_size = vec_size(xs); + r_obj* xs_names = r_names(xs); + xs = KEEP(r_clone_referenced(xs)); r_ssize out_size = 0; - // Recycle `x` elements to the size of their corresponding index - for (r_ssize i = 0; i < x_size; ++i) { - r_obj* elt = r_list_get(x, i); + r_ssize i = 0; + + struct vctrs_arg* p_x_arg = new_subscript_arg( + p_error_arg, + xs_names, + xs_size, + &i + ); + KEEP(p_x_arg->shelter); + + // Recycle `xs` elements to the size of their corresponding index + for (; i < xs_size; ++i) { + r_obj* x = r_list_get(xs, i); - r_ssize index_size = vec_size(r_list_get(indices, i)); + r_ssize index_size = r_length(r_list_get(indices, i)); out_size += index_size; - r_list_poke(x, i, vec_recycle_fallback(elt, index_size, vec_args.empty)); + r_list_poke(xs, i, vec_recycle_fallback(x, index_size, p_x_arg, error_call)); } indices = KEEP(vec_as_indices(indices, out_size, r_null)); r_obj* out = r_null; if (homogeneous) { - out = KEEP(vec_c_fallback_invoke(x, name_spec, error_call)); + out = KEEP(vec_c_fallback_invoke(xs, name_spec, error_call)); } else { - out = KEEP(vec_c_fallback(ptype, x, name_spec, name_repair, vec_args.empty, error_call)); + out = KEEP(vec_c_fallback(ptype, xs, name_spec, name_repair, p_error_arg, error_call)); } const struct name_repair_opts name_repair_opts = { @@ -237,7 +272,7 @@ r_obj* list_unchop_fallback(r_obj* ptype, r_globals.empty_int, r_null, &name_repair_opts, - vec_args.empty, + vec_args.indices, error_call )); @@ -263,6 +298,6 @@ r_obj* list_unchop_fallback(r_obj* ptype, out = KEEP(vec_slice_fallback(out, locations)); - FREE(6); + FREE(7); return out; } diff --git a/src/decl/c-unchop-decl.h b/src/decl/c-unchop-decl.h index f09d9fcf2..04ed32721 100644 --- a/src/decl/c-unchop-decl.h +++ b/src/decl/c-unchop-decl.h @@ -1,16 +1,18 @@ static -r_obj* list_unchop(r_obj* x, +r_obj* list_unchop(r_obj* xs, r_obj* indices, r_obj* ptype, r_obj* name_spec, const struct name_repair_opts* name_repair, + struct vctrs_arg* p_error_arg, struct r_lazy error_call); static r_obj* list_unchop_fallback(r_obj* ptype, - r_obj* x, + r_obj* xs, r_obj* indices, r_obj* name_spec, const struct name_repair_opts* name_repair, enum fallback_homogeneous homogenous, + struct vctrs_arg* p_error_arg, struct r_lazy error_call); diff --git a/src/size.c b/src/size.c index 4048e04e0..306e57168 100644 --- a/src/size.c +++ b/src/size.c @@ -211,7 +211,8 @@ r_obj* ffi_recycle(r_obj* x, r_obj* vec_recycle_fallback(r_obj* x, r_ssize size, - struct vctrs_arg* x_arg) { + struct vctrs_arg* x_arg, + struct r_lazy call) { if (x == r_null) { return r_null; } @@ -232,7 +233,7 @@ r_obj* vec_recycle_fallback(r_obj* x, return out; } - stop_recycle_incompatible_size(x_size, size, x_arg, r_lazy_null); + stop_recycle_incompatible_size(x_size, size, x_arg, call); } r_obj* ffi_as_short_length(r_obj* n, r_obj* frame) { diff --git a/src/size.h b/src/size.h index e15309f5c..d41c94655 100644 --- a/src/size.h +++ b/src/size.h @@ -19,7 +19,8 @@ r_obj* vec_recycle(r_obj* x, r_obj* vec_recycle_fallback(r_obj* x, r_ssize size, - struct vctrs_arg* x_arg); + struct vctrs_arg* x_arg, + struct r_lazy call); r_ssize df_size(r_obj* x); r_ssize df_raw_size(r_obj* x); diff --git a/tests/testthat/_snaps/slice-chop.md b/tests/testthat/_snaps/slice-chop.md index 4b61e4dd8..06b47c8ff 100644 --- a/tests/testthat/_snaps/slice-chop.md +++ b/tests/testthat/_snaps/slice-chop.md @@ -9,10 +9,10 @@ --- Code - list_unchop(1, list(1), error_call = call("foo")) + list_unchop(1, list(1), error_call = call("foo"), error_arg = "arg") Condition Error in `foo()`: - ! `x` must be a list, not a number. + ! `arg` must be a list, not a number. --- @@ -53,13 +53,14 @@ Output Error in `list_unchop()`: - ! Can't recycle `..1` (size 2) to size 3. + ! Can't recycle `x[[1]]` (size 2) to size 3. Code - (expect_error(list_unchop(x, indices = indices, error_call = call("foo")))) + (expect_error(list_unchop(x, indices = indices, error_call = call("foo"), + error_arg = "arg"))) Output Error in `foo()`: - ! Can't recycle `..1` (size 2) to size 3. + ! Can't recycle `arg[[1]]` (size 2) to size 3. # unchopping takes the common type @@ -68,56 +69,56 @@ Output Error in `list_unchop()`: - ! Can't combine `..1` and `..2` . + ! Can't combine `x[[1]]` and `x[[2]]` . Code - (expect_error(list_unchop(x, indices, error_call = call("foo")), class = "vctrs_error_incompatible_type") - ) + (expect_error(list_unchop(x, indices, error_call = call("foo"), error_arg = "arg"), + class = "vctrs_error_incompatible_type")) Output Error in `foo()`: - ! Can't combine `..1` and `..2` . + ! Can't combine `arg[[1]]` and `arg[[2]]` . # common type failure uses positional errors Code - (expect_error(list_unchop(list(1, a = "x", 2)))) + x <- list(1, a = "x", 2) + (expect_error(list_unchop(x))) Output Error in `list_unchop()`: - ! Can't combine `..1` and `a` . + ! Can't combine `x[[1]]` and `x$a` . Code - (expect_error(list_unchop(list(1, a = "x", 2), indices = list(2, 1, 3)))) + (expect_error(list_unchop(x, indices = list(2, 1, 3)))) Output Error in `list_unchop()`: - ! Can't combine `..1` and `a` . + ! Can't combine `x[[1]]` and `x$a` . Code - (expect_error(list_unchop(list(1, a = "x", 2), ptype = double()))) + (expect_error(list_unchop(x, ptype = double()))) Output Error in `list_unchop()`: - ! Can't convert `a` to . + ! Can't convert `x$a` to . Code - (expect_error(list_unchop(list(1, a = "x", 2), indices = list(2, 1, 3), ptype = double())) - ) + (expect_error(list_unchop(x, indices = list(2, 1, 3), ptype = double()))) Output Error in `list_unchop()`: - ! Can't convert `a` to . + ! Can't convert `x$a` to . Code - (expect_error(list_unchop(list(1, a = 2.5), ptype = integer()))) + y <- list(1, a = 2.5) + (expect_error(list_unchop(y, ptype = integer()))) Output Error in `list_unchop()`: - ! Can't convert from `a` to due to loss of precision. + ! Can't convert from `x$a` to due to loss of precision. * Locations: 1 Code - (expect_error(list_unchop(list(1, a = 2.5), indices = list(2, 1), ptype = integer())) - ) + (expect_error(list_unchop(y, indices = list(2, 1), ptype = integer()))) Output Error in `list_unchop()`: - ! Can't convert from `a` to due to loss of precision. + ! Can't convert from `x$a` to due to loss of precision. * Locations: 1 # can specify a ptype to override common type @@ -127,15 +128,15 @@ Output Error in `list_unchop()`: - ! Can't convert from `..1` to due to loss of precision. + ! Can't convert from `x[[1]]` to due to loss of precision. * Locations: 1 Code (expect_error(list_unchop(x, indices = indices, ptype = integer(), error_call = call( - "foo")))) + "foo"), error_arg = "arg"))) Output Error in `foo()`: - ! Can't convert from `..1` to due to loss of precision. + ! Can't convert from `arg[[1]]` to due to loss of precision. * Locations: 1 # list_unchop() errors on unsupported location values @@ -167,17 +168,17 @@ Output Error in `list_unchop()`: - ! Can't combine `..1` and `..2` . + ! Can't combine `x[[1]]` and `x[[2]]` . x Some attributes are incompatible. i The author of the class should implement vctrs methods. i See . Code - (expect_error(list_unchop(list(x, y), error_call = call("foo")), class = "vctrs_error_incompatible_type") - ) + (expect_error(list_unchop(list(x, y), error_call = call("foo"), error_arg = "arg"), + class = "vctrs_error_incompatible_type")) Output Error in `foo()`: - ! Can't combine `..1` and `..2` . + ! Can't combine `arg[[1]]` and `arg[[2]]` . x Some attributes are incompatible. i The author of the class should implement vctrs methods. i See . @@ -192,21 +193,51 @@ Output Error in `list_unchop()`: - ! Can't combine `..1` and `..2` . + ! Can't combine `x[[1]]` and `x[[2]]` . x Some attributes are incompatible. i The author of the class should implement vctrs methods. i See . Code - (expect_error(list_unchop(list(joe, jane), error_call = call("foo")), class = "vctrs_error_incompatible_type") - ) + (expect_error(list_unchop(list(joe, jane), error_call = call("foo"), error_arg = "arg"), + class = "vctrs_error_incompatible_type")) Output Error in `foo()`: - ! Can't combine `..1` and `..2` . + ! Can't combine `arg[[1]]` and `arg[[2]]` . x Some attributes are incompatible. i The author of the class should implement vctrs methods. i See . +# list_unchop() falls back to c() if S3 method is available + + Code + (expect_error(list_unchop(list(foobar(1), foobar(2)), list(c(1, 3), integer())), + class = "vctrs_error_subscript_oob")) + Output + + Error: + ! Can't subset elements past the end. + i Location 3 doesn't exist. + i There are only 2 elements. + +--- + + Code + x <- list(foobar(1:2)) + indices <- list(1:3) + (expect_error(list_unchop(x, indices))) + Output + + Error in `list_unchop()`: + ! Can't recycle `x[[1]]` (size 2) to size 3. + Code + (expect_error(list_unchop(x, indices, error_arg = "arg", error_call = call( + "foo")))) + Output + + Error in `foo()`: + ! Can't recycle `arg[[1]]` (size 2) to size 3. + # list_unchop() falls back for S4 classes with a registered c() method Code @@ -215,7 +246,7 @@ Output Error in `list_unchop()`: - ! Can't combine `..1` and `..2` . + ! Can't combine `x[[1]]` and `x[[2]]` . # list_unchop() fallback doesn't support `name_spec` or `ptype` @@ -240,12 +271,13 @@ vctrs methods must be implemented for class `vctrs_foobar`. See . Code - (expect_error(with_c_foobar(list_unchop(list(foobar(1)), ptype = "")), class = "vctrs_error_incompatible_type") + x <- list(foobar(1)) + (expect_error(with_c_foobar(list_unchop(x, ptype = "")), class = "vctrs_error_incompatible_type") ) Output Error in `list_unchop()`: - ! Can't convert `..1` to . + ! Can't convert `x[[1]]` to . # list_unchop() does not support non-numeric S3 indices @@ -288,17 +320,19 @@ --- Code - (expect_error(list_unchop(list(a = c(b = letters), b = 3L), name_spec = zap()), - class = "vctrs_error_incompatible_type")) + x <- list(a = c(b = letters), b = 3L) + (expect_error(list_unchop(x, name_spec = zap()), class = "vctrs_error_incompatible_type") + ) Output Error in `list_unchop()`: - ! Can't combine `a` and `b` . + ! Can't combine `x$a` and `x$b` . Code - (expect_error(list_unchop(list(a = c(foo = 1:2), b = c(bar = "")), indices = list( - 2:1, 3), name_spec = zap()), class = "vctrs_error_incompatible_type")) + x <- list(a = c(foo = 1:2), b = c(bar = "")) + (expect_error(list_unchop(x, indices = list(2:1, 3), name_spec = zap()), class = "vctrs_error_incompatible_type") + ) Output Error in `list_unchop()`: - ! Can't combine `a` and `b` . + ! Can't combine `x$a` and `x$b` . diff --git a/tests/testthat/test-slice-chop.R b/tests/testthat/test-slice-chop.R index 3ee823971..c86be65d1 100644 --- a/tests/testthat/test-slice-chop.R +++ b/tests/testthat/test-slice-chop.R @@ -256,7 +256,7 @@ test_that("`x` must be a list", { list_unchop(1, list(1)) }) expect_snapshot(error = TRUE, { - list_unchop(1, list(1), error_call = call("foo")) + list_unchop(1, list(1), error_call = call("foo"), error_arg = "arg") }) expect_snapshot(error = TRUE, { list_unchop(data.frame(x=1), list(1)) @@ -412,7 +412,7 @@ test_that("unchopping recycles elements of x to the size of the index", { indices <- list(1:3) expect_snapshot({ (expect_error(list_unchop(x, indices = indices))) - (expect_error(list_unchop(x, indices = indices, error_call = call("foo")))) + (expect_error(list_unchop(x, indices = indices, error_call = call("foo"), error_arg = "arg"))) }) }) @@ -422,7 +422,7 @@ test_that("unchopping takes the common type", { expect_snapshot({ (expect_error(list_unchop(x, indices), class = "vctrs_error_incompatible_type")) - (expect_error(list_unchop(x, indices, error_call = call("foo")), class = "vctrs_error_incompatible_type")) + (expect_error(list_unchop(x, indices, error_call = call("foo"), error_arg = "arg"), class = "vctrs_error_incompatible_type")) }) x <- list(1, 2L) @@ -432,17 +432,20 @@ test_that("unchopping takes the common type", { test_that("common type failure uses positional errors", { expect_snapshot({ - # Looking for `..1` and `a` - (expect_error(list_unchop(list(1, a = "x", 2)))) - (expect_error(list_unchop(list(1, a = "x", 2), indices = list(2, 1, 3)))) + x <- list(1, a = "x", 2) + + # Looking for `x[[1]]` and `x$a` + (expect_error(list_unchop(x))) + (expect_error(list_unchop(x, indices = list(2, 1, 3)))) # Directed cast should also produce directional errors (#1690) - (expect_error(list_unchop(list(1, a = "x", 2), ptype = double()))) - (expect_error(list_unchop(list(1, a = "x", 2), indices = list(2, 1, 3), ptype = double()))) + (expect_error(list_unchop(x, ptype = double()))) + (expect_error(list_unchop(x, indices = list(2, 1, 3), ptype = double()))) # Lossy cast - (expect_error(list_unchop(list(1, a = 2.5), ptype = integer()))) - (expect_error(list_unchop(list(1, a = 2.5), indices = list(2, 1), ptype = integer()))) + y <- list(1, a = 2.5) + (expect_error(list_unchop(y, ptype = integer()))) + (expect_error(list_unchop(y, indices = list(2, 1), ptype = integer()))) }) }) @@ -455,7 +458,7 @@ test_that("can specify a ptype to override common type", { x <- list(1.5, 2) expect_snapshot({ (expect_error(list_unchop(x, indices = indices, ptype = integer()))) - (expect_error(list_unchop(x, indices = indices, ptype = integer(), error_call = call("foo")))) + (expect_error(list_unchop(x, indices = indices, ptype = integer(), error_call = call("foo"), error_arg = "arg"))) }) }) @@ -606,7 +609,7 @@ test_that("list_unchop() fails with complex foreign S3 classes", { x <- structure(foobar(1), attr_foo = "foo") y <- structure(foobar(2), attr_bar = "bar") (expect_error(list_unchop(list(x, y)), class = "vctrs_error_incompatible_type")) - (expect_error(list_unchop(list(x, y), error_call = call("foo")), class = "vctrs_error_incompatible_type")) + (expect_error(list_unchop(list(x, y), error_call = call("foo"), error_arg = "arg"), class = "vctrs_error_incompatible_type")) }) }) @@ -615,7 +618,7 @@ test_that("list_unchop() fails with complex foreign S4 classes", { joe <- .Counts(c(1L, 2L), name = "Joe") jane <- .Counts(3L, name = "Jane") (expect_error(list_unchop(list(joe, jane)), class = "vctrs_error_incompatible_type")) - (expect_error(list_unchop(list(joe, jane), error_call = call("foo")), class = "vctrs_error_incompatible_type")) + (expect_error(list_unchop(list(joe, jane), error_call = call("foo"), error_arg = "arg"), class = "vctrs_error_incompatible_type")) }) }) @@ -686,10 +689,18 @@ test_that("list_unchop() falls back to c() if S3 method is available", { list_unchop(list(foobar(1), foobar(2)), list(c(1, 2), integer())), foobar(c(1, 1)) ) - expect_error( - list_unchop(list(foobar(1), foobar(2)), list(c(1, 3), integer())), - class = "vctrs_error_subscript_oob" - ) + expect_snapshot({ + (expect_error( + list_unchop(list(foobar(1), foobar(2)), list(c(1, 3), integer())), + class = "vctrs_error_subscript_oob" + )) + }) + expect_snapshot({ + x <- list(foobar(1:2)) + indices <- list(1:3) + (expect_error(list_unchop(x, indices))) + (expect_error(list_unchop(x, indices, error_arg = "arg", error_call = call("foo")))) + }) method_vctrs_c_fallback <- function(...) { xs <- list(...) @@ -767,8 +778,9 @@ test_that("list_unchop() fallback doesn't support `name_spec` or `ptype`", { "name specification" )) # Used to be an error about `ptype` + x <- list(foobar(1)) (expect_error( - with_c_foobar(list_unchop(list(foobar(1)), ptype = "")), + with_c_foobar(list_unchop(x, ptype = "")), class = "vctrs_error_incompatible_type" )) }) @@ -817,13 +829,16 @@ test_that("can ignore names in `list_unchop()` by providing a `zap()` name-spec ) expect_snapshot({ + x <- list(a = c(b = letters), b = 3L) (expect_error( - list_unchop(list(a = c(b = letters), b = 3L), name_spec = zap()), + list_unchop(x, name_spec = zap()), class = "vctrs_error_incompatible_type" )) + + x <- list(a = c(foo = 1:2), b = c(bar = "")) (expect_error( list_unchop( - list(a = c(foo = 1:2), b = c(bar = "")), + x, indices = list(2:1, 3), name_spec = zap() ), From 64fb9afad9d0b1f5459ab98f7483773e10b8e060 Mon Sep 17 00:00:00 2001 From: Davis Vaughan Date: Tue, 4 Oct 2022 11:26:57 -0400 Subject: [PATCH 139/312] Remove old dplyr backwards compatibility patch (#1706) --- R/compare.R | 12 +----------- 1 file changed, 1 insertion(+), 11 deletions(-) diff --git a/R/compare.R b/R/compare.R index 3c545004b..5ece20a15 100644 --- a/R/compare.R +++ b/R/compare.R @@ -58,13 +58,7 @@ #' df <- new_data_frame(list(x = x)) #' vec_sort(df) vec_proxy_compare <- function(x, ...) { - if (!missing(...)) { - # For backward compatibility with older dplyr versions - if (match_relax(...)) { - return(vec_proxy_order(x)) - } - check_dots_empty0(...) - } + check_dots_empty0(...) return(.Call(vctrs_proxy_compare, x)) UseMethod("vec_proxy_compare") } @@ -73,10 +67,6 @@ vec_proxy_compare.default <- function(x, ...) { stop_native_implementation("vec_proxy_compare.default") } -match_relax <- function(..., relax = FALSE) { - relax -} - #' @rdname vec_proxy_compare #' @export vec_proxy_order <- function(x, ...) { From a19cb38e13aa9e14e10213857c07c837fedf3cc5 Mon Sep 17 00:00:00 2001 From: Davis Vaughan Date: Wed, 5 Oct 2022 09:52:20 -0400 Subject: [PATCH 140/312] Add `...` to `list_unchop()` (#1715) * Add `...` to `list_unchop()` * NEWS bullet --- NEWS.md | 3 + R/slice-chop.R | 12 ++- man/vec_chop.Rd | 11 ++- tests/testthat/_snaps/slice-chop.md | 39 ++++---- tests/testthat/test-c.R | 8 +- tests/testthat/test-slice-chop.R | 142 ++++++++++++++-------------- tests/testthat/test-type-table.R | 2 +- 7 files changed, 114 insertions(+), 103 deletions(-) diff --git a/NEWS.md b/NEWS.md index 21f398729..a366770f9 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,5 +1,8 @@ # vctrs (development version) +* `list_unchop()` has gained empty `...` to force optional arguments to be + named (#1715). + * `vec_rep_each(times = 0)` now works correctly with logical vectors that are considered unspecified and with named vectors (#1673). diff --git a/R/slice-chop.R b/R/slice-chop.R index ab1b8717d..e7b416d42 100644 --- a/R/slice-chop.R +++ b/R/slice-chop.R @@ -19,7 +19,9 @@ #' list_unchop(vec_chop(x, indices), indices) == x #' ``` #' +#' @inheritParams rlang::args_dots_empty #' @inheritParams vec_c +#' #' @param x A vector #' @param indices For `vec_chop()`, a list of positive integer vectors to #' slice `x` with, or `NULL`. If `NULL`, `x` is split into its individual @@ -58,16 +60,16 @@ #' x <- c("a", "b", "c", "d") #' indices <- list(2, c(3, 1), 4) #' vec_chop(x, indices) -#' list_unchop(vec_chop(x, indices), indices) +#' list_unchop(vec_chop(x, indices), indices = indices) #' #' # When unchopping, size 1 elements of `x` are recycled #' # to the size of the corresponding index -#' list_unchop(list(1, 2:3), list(c(1, 3, 5), c(2, 4))) +#' list_unchop(list(1, 2:3), indices = list(c(1, 3, 5), c(2, 4))) #' #' # Names are retained, and outer names can be combined with inner #' # names through the use of a `name_spec` #' lst <- list(x = c(a = 1, b = 2), y = 1) -#' list_unchop(lst, list(c(3, 2), c(1, 4)), name_spec = "{outer}_{inner}") +#' list_unchop(lst, indices = list(c(3, 2), c(1, 4)), name_spec = "{outer}_{inner}") #' #' # An alternative implementation of `ave()` can be constructed using #' # `vec_chop()` and `list_unchop()` in combination with `vec_group_loc()` @@ -75,7 +77,7 @@ #' indices <- vec_group_loc(.by)$loc #' chopped <- vec_chop(.x, indices) #' out <- lapply(chopped, .f, ...) -#' list_unchop(out, indices) +#' list_unchop(out, indices = indices) #' } #' #' breaks <- warpbreaks$breaks @@ -94,12 +96,14 @@ vec_chop <- function(x, indices = NULL) { #' @rdname vec_chop #' @export list_unchop <- function(x, + ..., indices = NULL, ptype = NULL, name_spec = NULL, name_repair = c("minimal", "unique", "check_unique", "universal"), error_arg = "x", error_call = current_env()) { + check_dots_empty0(...) .Call(ffi_list_unchop, x, indices, ptype, name_spec, name_repair, environment()) } diff --git a/man/vec_chop.Rd b/man/vec_chop.Rd index 5a1e02780..3bb6e5c3e 100644 --- a/man/vec_chop.Rd +++ b/man/vec_chop.Rd @@ -9,6 +9,7 @@ vec_chop(x, indices = NULL) list_unchop( x, + ..., indices = NULL, ptype = NULL, name_spec = NULL, @@ -30,6 +31,8 @@ the size of the corresponding index vector. The size of \code{indices} must match the size of \code{x}. If \code{NULL}, \code{x} is combined in the order it is provided in, which is equivalent to using \code{\link[=vec_c]{vec_c()}}.} +\item{...}{These dots are for future extensions and must be empty.} + \item{ptype}{If \code{NULL}, the default, the output type is determined by computing the common type across all elements of \code{x}. Alternatively, you can supply \code{ptype} to give the output a known type.} @@ -116,16 +119,16 @@ vec_chop(mtcars, list(1:3, 4:6)) x <- c("a", "b", "c", "d") indices <- list(2, c(3, 1), 4) vec_chop(x, indices) -list_unchop(vec_chop(x, indices), indices) +list_unchop(vec_chop(x, indices), indices = indices) # When unchopping, size 1 elements of `x` are recycled # to the size of the corresponding index -list_unchop(list(1, 2:3), list(c(1, 3, 5), c(2, 4))) +list_unchop(list(1, 2:3), indices = list(c(1, 3, 5), c(2, 4))) # Names are retained, and outer names can be combined with inner # names through the use of a `name_spec` lst <- list(x = c(a = 1, b = 2), y = 1) -list_unchop(lst, list(c(3, 2), c(1, 4)), name_spec = "{outer}_{inner}") +list_unchop(lst, indices = list(c(3, 2), c(1, 4)), name_spec = "{outer}_{inner}") # An alternative implementation of `ave()` can be constructed using # `vec_chop()` and `list_unchop()` in combination with `vec_group_loc()` @@ -133,7 +136,7 @@ ave2 <- function(.x, .by, .f, ...) { indices <- vec_group_loc(.by)$loc chopped <- vec_chop(.x, indices) out <- lapply(chopped, .f, ...) - list_unchop(out, indices) + list_unchop(out, indices = indices) } breaks <- warpbreaks$breaks diff --git a/tests/testthat/_snaps/slice-chop.md b/tests/testthat/_snaps/slice-chop.md index 06b47c8ff..e511b8faf 100644 --- a/tests/testthat/_snaps/slice-chop.md +++ b/tests/testthat/_snaps/slice-chop.md @@ -1,7 +1,7 @@ # `x` must be a list Code - list_unchop(1, list(1)) + list_unchop(1, indices = list(1)) Condition Error in `list_unchop()`: ! `x` must be a list, not a number. @@ -9,7 +9,7 @@ --- Code - list_unchop(1, list(1), error_call = call("foo"), error_arg = "arg") + list_unchop(1, indices = list(1), error_call = call("foo"), error_arg = "arg") Condition Error in `foo()`: ! `arg` must be a list, not a number. @@ -17,7 +17,7 @@ --- Code - list_unchop(data.frame(x = 1), list(1)) + list_unchop(data.frame(x = 1), indices = list(1)) Condition Error in `list_unchop()`: ! `x` must be a list, not a object. @@ -25,7 +25,7 @@ # `indices` must be a list Code - list_unchop(list(1), 1) + list_unchop(list(1), indices = 1) Condition Error in `list_unchop()`: ! `indices` must be a list, not a number. @@ -33,7 +33,7 @@ --- Code - list_unchop(list(1), 1, error_call = call("foo")) + list_unchop(list(1), indices = 1, error_call = call("foo")) Condition Error in `foo()`: ! `indices` must be a list, not a number. @@ -41,7 +41,7 @@ --- Code - list_unchop(list(1), data.frame(x = 1)) + list_unchop(list(1), indices = data.frame(x = 1)) Condition Error in `list_unchop()`: ! `indices` must be a list, not a object. @@ -65,14 +65,15 @@ # unchopping takes the common type Code - (expect_error(list_unchop(x, indices), class = "vctrs_error_incompatible_type")) + (expect_error(list_unchop(x, indices = indices), class = "vctrs_error_incompatible_type") + ) Output Error in `list_unchop()`: ! Can't combine `x[[1]]` and `x[[2]]` . Code - (expect_error(list_unchop(x, indices, error_call = call("foo"), error_arg = "arg"), - class = "vctrs_error_incompatible_type")) + (expect_error(list_unchop(x, indices = indices, error_call = call("foo"), + error_arg = "arg"), class = "vctrs_error_incompatible_type")) Output Error in `foo()`: @@ -142,7 +143,7 @@ # list_unchop() errors on unsupported location values Code - (expect_error(list_unchop(list(1, 2), list(c(1, 2), 0)), class = "vctrs_error_subscript_type") + (expect_error(list_unchop(list(1, 2), indices = list(c(1, 2), 0)), class = "vctrs_error_subscript_type") ) Output @@ -151,7 +152,7 @@ x Subscript can't contain `0` values. i It has a `0` value at location 1. Code - (expect_error(list_unchop(list(1), list(-1)), class = "vctrs_error_subscript_type") + (expect_error(list_unchop(list(1), indices = list(-1)), class = "vctrs_error_subscript_type") ) Output @@ -211,8 +212,8 @@ # list_unchop() falls back to c() if S3 method is available Code - (expect_error(list_unchop(list(foobar(1), foobar(2)), list(c(1, 3), integer())), - class = "vctrs_error_subscript_oob")) + (expect_error(list_unchop(list(foobar(1), foobar(2)), indices = list(c(1, 3), + integer())), class = "vctrs_error_subscript_oob")) Output Error: @@ -225,13 +226,13 @@ Code x <- list(foobar(1:2)) indices <- list(1:3) - (expect_error(list_unchop(x, indices))) + (expect_error(list_unchop(x, indices = indices))) Output Error in `list_unchop()`: ! Can't recycle `x[[1]]` (size 2) to size 3. Code - (expect_error(list_unchop(x, indices, error_arg = "arg", error_call = call( + (expect_error(list_unchop(x, indices = indices, error_arg = "arg", error_call = call( "foo")))) Output @@ -241,8 +242,8 @@ # list_unchop() falls back for S4 classes with a registered c() method Code - (expect_error(list_unchop(list(joe, 1, jane), list(c(1, 2), 3, 4)), class = "vctrs_error_incompatible_type") - ) + (expect_error(list_unchop(list(joe, 1, jane), indices = list(c(1, 2), 3, 4)), + class = "vctrs_error_incompatible_type")) Output Error in `list_unchop()`: @@ -282,7 +283,7 @@ # list_unchop() does not support non-numeric S3 indices Code - (expect_error(list_unchop(list(1), list(factor("x"))), class = "vctrs_error_subscript_type") + (expect_error(list_unchop(list(1), indices = list(factor("x"))), class = "vctrs_error_subscript_type") ) Output @@ -291,7 +292,7 @@ x Subscript has the wrong type `character`. i It must be numeric. Code - (expect_error(list_unchop(list(1), list(foobar(1L))), class = "vctrs_error_subscript_type") + (expect_error(list_unchop(list(1), indices = list(foobar(1L))), class = "vctrs_error_subscript_type") ) Output diff --git a/tests/testthat/test-c.R b/tests/testthat/test-c.R index cf34d4a3e..3e85f3367 100644 --- a/tests/testthat/test-c.R +++ b/tests/testthat/test-c.R @@ -453,11 +453,11 @@ test_that("named empty vectors force named output (#1263)", { expect_named(vec_c(x, 1L), "") expect_named(vec_c(x, 1), "") - expect_named(list_unchop(list(x), list(int())), chr()) - expect_named(list_unchop(list(x, x), list(int(), int())), chr()) - expect_named(list_unchop(list(x, 1L), list(int(), 1)), "") + expect_named(list_unchop(list(x), indices = list(int())), chr()) + expect_named(list_unchop(list(x, x), indices = list(int(), int())), chr()) + expect_named(list_unchop(list(x, 1L), indices = list(int(), 1)), "") - expect_named(list_unchop(list(x, 1), list(int(), 1)), "") + expect_named(list_unchop(list(x, 1), indices = list(int(), 1)), "") }) # Golden tests ------------------------------------------------------- diff --git a/tests/testthat/test-slice-chop.R b/tests/testthat/test-slice-chop.R index c86be65d1..a0ef6de2d 100644 --- a/tests/testthat/test-slice-chop.R +++ b/tests/testthat/test-slice-chop.R @@ -253,36 +253,36 @@ test_that("can chop S3 objects using the fallback method with compact seqs", { test_that("`x` must be a list", { expect_snapshot(error = TRUE, { - list_unchop(1, list(1)) + list_unchop(1, indices = list(1)) }) expect_snapshot(error = TRUE, { - list_unchop(1, list(1), error_call = call("foo"), error_arg = "arg") + list_unchop(1, indices = list(1), error_call = call("foo"), error_arg = "arg") }) expect_snapshot(error = TRUE, { - list_unchop(data.frame(x=1), list(1)) + list_unchop(data.frame(x=1), indices = list(1)) }) }) test_that("`indices` must be a list", { expect_snapshot(error = TRUE, { - list_unchop(list(1), 1) + list_unchop(list(1), indices = 1) }) expect_snapshot(error = TRUE, { - list_unchop(list(1), 1, error_call = call("foo")) + list_unchop(list(1), indices = 1, error_call = call("foo")) }) expect_snapshot(error = TRUE, { - list_unchop(list(1), data.frame(x=1)) + list_unchop(list(1), indices = data.frame(x=1)) }) }) test_that("`indices` must be a list of integers", { - expect_error(list_unchop(list(1), list("x")), class = "vctrs_error_subscript_type") - expect_error(list_unchop(list(1), list(TRUE)), class = "vctrs_error_subscript_type") - expect_error(list_unchop(list(1), list(quote(name))), class = "vctrs_error_subscript_type") + expect_error(list_unchop(list(1), indices = list("x")), class = "vctrs_error_subscript_type") + expect_error(list_unchop(list(1), indices = list(TRUE)), class = "vctrs_error_subscript_type") + expect_error(list_unchop(list(1), indices = list(quote(name))), class = "vctrs_error_subscript_type") }) test_that("`x` and `indices` must be lists of the same size", { - expect_error(list_unchop(list(1, 2), list(1)), "`x` and `indices` must be lists of the same size") + expect_error(list_unchop(list(1, 2), indices = list(1)), "`x` and `indices` must be lists of the same size") }) test_that("can unchop with an AsIs list (#1463)", { @@ -292,19 +292,19 @@ test_that("can unchop with an AsIs list (#1463)", { test_that("can unchop empty vectors", { expect_null(list_unchop(list())) - expect_null(list_unchop(list(), list())) - expect_identical(list_unchop(list(), list(), ptype = numeric()), numeric()) + expect_null(list_unchop(list(), indices = list())) + expect_identical(list_unchop(list(), indices = list(), ptype = numeric()), numeric()) }) test_that("can unchop a list of NULL", { - expect_null(list_unchop(list(NULL), list(integer()))) - expect_identical(list_unchop(list(NULL), list(integer()), ptype = numeric()), numeric()) - expect_identical(list_unchop(list(NULL, NULL), list(integer(), integer()), ptype = numeric()), numeric()) + expect_null(list_unchop(list(NULL), indices = list(integer()))) + expect_identical(list_unchop(list(NULL), indices = list(integer()), ptype = numeric()), numeric()) + expect_identical(list_unchop(list(NULL, NULL), indices = list(integer(), integer()), ptype = numeric()), numeric()) }) test_that("NULLs are ignored when unchopped with other vectors", { expect_identical(list_unchop(list("a", NULL, "b")), c("a", "b")) - expect_identical(list_unchop(list("a", NULL, "b"), list(2, integer(), 1)), c("b", "a")) + expect_identical(list_unchop(list("a", NULL, "b"), indices = list(2, integer(), 1)), c("b", "a")) }) test_that("can use a `NULL` element with a corresponding index", { @@ -324,15 +324,15 @@ test_that("can use a `NULL` element with a corresponding index", { }) test_that("can unchop atomic vectors", { - expect_identical(list_unchop(list(1, 2), list(2, 1)), c(2, 1)) - expect_identical(list_unchop(list("a", "b"), list(2, 1)), c("b", "a")) + expect_identical(list_unchop(list(1, 2), indices = list(2, 1)), c(2, 1)) + expect_identical(list_unchop(list("a", "b"), indices = list(2, 1)), c("b", "a")) }) test_that("can unchop lists", { x <- list(list("a", "b"), list("c")) indices <- list(c(2, 3), 1) - expect_identical(list_unchop(x, indices), list("c", "a", "b")) + expect_identical(list_unchop(x, indices = indices), list("c", "a", "b")) }) test_that("can unchop data frames", { @@ -344,7 +344,7 @@ test_that("can unchop data frames", { expect <- vec_slice(vec_c(df1, df2), vec_order(vec_c(!!! indices))) - expect_identical(list_unchop(x, indices), expect) + expect_identical(list_unchop(x, indices = indices), expect) }) test_that("can unchop factors", { @@ -357,7 +357,7 @@ test_that("can unchop factors", { # levels are in the order they are seen! expect <- factor(c("y", "z", "x"), levels = c("z", "x", "y")) - expect_identical(list_unchop(x, indices), expect) + expect_identical(list_unchop(x, indices = indices), expect) }) test_that("can fallback when unchopping matrices", { @@ -369,7 +369,7 @@ test_that("can fallback when unchopping matrices", { expect <- vec_slice(vec_c(mat1, mat2), vec_order(vec_c(!!! indices))) - expect_identical(list_unchop(x, indices), expect) + expect_identical(list_unchop(x, indices = indices), expect) expect_identical(list_unchop(x), vec_c(mat1, mat2)) }) @@ -382,31 +382,31 @@ test_that("can fallback when unchopping arrays of >2D", { expect <- vec_slice(vec_c(arr1, arr2), vec_order(vec_c(!!! indices))) - expect_identical(list_unchop(x, indices), expect) + expect_identical(list_unchop(x, indices = indices), expect) expect_identical(list_unchop(x), vec_c(arr1, arr2)) }) test_that("can unchop with all size 0 elements and get the right ptype", { x <- list(integer(), integer()) indices <- list(integer(), integer()) - expect_identical(list_unchop(x, indices), integer()) + expect_identical(list_unchop(x, indices = indices), integer()) }) test_that("can unchop with some size 0 elements", { x <- list(integer(), 1:2, integer()) indices <- list(integer(), 2:1, integer()) - expect_identical(list_unchop(x, indices), 2:1) + expect_identical(list_unchop(x, indices = indices), 2:1) }) test_that("NULL is a valid index", { - expect_equal(list_unchop(list(1, 2), list(NULL, 1)), 2) - expect_error(list_unchop(list(1, 2), list(NULL, 2)), class = "vctrs_error_subscript_oob") + expect_equal(list_unchop(list(1, 2), indices = list(NULL, 1)), 2) + expect_error(list_unchop(list(1, 2), indices = list(NULL, 2)), class = "vctrs_error_subscript_oob") }) test_that("unchopping recycles elements of x to the size of the index", { x <- list(1, 2) indices <- list(c(3, 4, 5), c(2, 1)) - expect_identical(list_unchop(x, indices), c(2, 2, 1, 1, 1)) + expect_identical(list_unchop(x, indices = indices), c(2, 2, 1, 1, 1)) x <- list(1:2) indices <- list(1:3) @@ -421,13 +421,13 @@ test_that("unchopping takes the common type", { indices <- list(1, 2) expect_snapshot({ - (expect_error(list_unchop(x, indices), class = "vctrs_error_incompatible_type")) - (expect_error(list_unchop(x, indices, error_call = call("foo"), error_arg = "arg"), class = "vctrs_error_incompatible_type")) + (expect_error(list_unchop(x, indices = indices), class = "vctrs_error_incompatible_type")) + (expect_error(list_unchop(x, indices = indices, error_call = call("foo"), error_arg = "arg"), class = "vctrs_error_incompatible_type")) }) x <- list(1, 2L) - expect_type(list_unchop(x, indices), "double") + expect_type(list_unchop(x, indices = indices), "double") }) test_that("common type failure uses positional errors", { @@ -453,7 +453,7 @@ test_that("can specify a ptype to override common type", { indices <- list(1, 2) x <- list(1, 2L) - expect_identical(list_unchop(x, indices, ptype = integer()), c(1L, 2L)) + expect_identical(list_unchop(x, indices = indices, ptype = integer()), c(1L, 2L)) x <- list(1.5, 2) expect_snapshot({ @@ -470,21 +470,21 @@ test_that("leaving `indices = NULL` unchops sequentially", { test_that("outer names are kept", { x <- list(x = 1, y = 2) expect_named(list_unchop(x), c("x", "y")) - expect_named(list_unchop(x, list(2, 1)), c("y", "x")) + expect_named(list_unchop(x, indices = list(2, 1)), c("y", "x")) }) test_that("outer names are recycled in the right order", { x <- list(x = 1, y = 2) - expect_error(list_unchop(x, list(c(1, 2), 3)), "Can't merge") - expect_named(list_unchop(x, list(c(1, 3), 2), name_spec = "{outer}_{inner}"), c("x_1", "y", "x_2")) - expect_named(list_unchop(x, list(c(3, 1), 2), name_spec = "{outer}_{inner}"), c("x_2", "y", "x_1")) + expect_error(list_unchop(x, indices = list(c(1, 2), 3)), "Can't merge") + expect_named(list_unchop(x, indices = list(c(1, 3), 2), name_spec = "{outer}_{inner}"), c("x_1", "y", "x_2")) + expect_named(list_unchop(x, indices = list(c(3, 1), 2), name_spec = "{outer}_{inner}"), c("x_2", "y", "x_1")) }) test_that("outer names can be merged with inner names", { x <- list(x = c(a = 1), y = c(b = 2)) expect_error(list_unchop(x), "Can't merge") expect_named(list_unchop(x, name_spec = "{outer}_{inner}"), c("x_a", "y_b")) - expect_named(list_unchop(x, list(2, 1), name_spec = "{outer}_{inner}"), c("y_b", "x_a")) + expect_named(list_unchop(x, indices = list(2, 1), name_spec = "{outer}_{inner}"), c("y_b", "x_a")) }) test_that("preserves names when inputs are cast to a common type (#1689)", { @@ -506,7 +506,7 @@ test_that("not all inputs have to be named", { x <- list(c(a = 1), 2, c(c = 3)) indices <- list(2, 1, 3) - expect_named(list_unchop(x, indices), c("", "a", "c")) + expect_named(list_unchop(x, indices = indices), c("", "a", "c")) }) test_that("list_unchop() keeps data frame row names", { @@ -516,7 +516,7 @@ test_that("list_unchop() keeps data frame row names", { x <- list(df1, df2) indices <- list(c(3, 1), c(2, 4)) - result <- list_unchop(x, indices) + result <- list_unchop(x, indices = indices) expect <- c("r2", "r3", "r1", "r4") expect_identical(vec_names(result), expect) @@ -555,7 +555,7 @@ test_that("monitoring - can technically assign to the same location twice", { x <- list(1:2, 3L) indices <- list(1:2, 1L) - expect_identical(list_unchop(x, indices), c(3L, 2L, NA)) + expect_identical(list_unchop(x, indices = indices), c(3L, 2L, NA)) }) test_that("index values are validated", { @@ -564,10 +564,10 @@ test_that("index values are validated", { indices2 <- list(c(1, 4), 2) indices3 <- list(c(1, 3, 4), 2) - expect_error(list_unchop(x, indices1), class = "vctrs_error_subscript_oob") - expect_error(list_unchop(x, indices2), class = "vctrs_error_subscript_oob") + expect_error(list_unchop(x, indices = indices1), class = "vctrs_error_subscript_oob") + expect_error(list_unchop(x, indices = indices2), class = "vctrs_error_subscript_oob") - expect_identical(list_unchop(x, indices3), c(1, 2, 1, 1)) + expect_identical(list_unchop(x, indices = indices3), c(1, 2, 1, 1)) }) test_that("name repair is respected and happens after ordering according to `indices`", { @@ -576,18 +576,18 @@ test_that("name repair is respected and happens after ordering according to `ind x <- list(c(a = 1), c(a = 2)) indices <- list(2, 1) - expect_named(list_unchop(x, indices), c("a", "a")) - expect_named(list_unchop(x, indices, name_repair = "unique"), c("a...1", "a...2")) + expect_named(list_unchop(x, indices = indices), c("a", "a")) + expect_named(list_unchop(x, indices = indices, name_repair = "unique"), c("a...1", "a...2")) }) test_that("list_unchop() errors on unsupported location values", { expect_snapshot({ (expect_error( - list_unchop(list(1, 2), list(c(1, 2), 0)), + list_unchop(list(1, 2), indices = list(c(1, 2), 0)), class = "vctrs_error_subscript_type" )) (expect_error( - list_unchop(list(1), list(-1)), + list_unchop(list(1), indices = list(-1)), class = "vctrs_error_subscript_type" )) }) @@ -595,7 +595,7 @@ test_that("list_unchop() errors on unsupported location values", { test_that("missing values propagate", { expect_identical( - list_unchop(list(1, 2), list(c(NA_integer_, NA_integer_), c(NA_integer_, 3))), + list_unchop(list(1, 2), indices = list(c(NA_integer_, NA_integer_), c(NA_integer_, 3))), c(NA, NA, 2, NA) ) }) @@ -625,7 +625,7 @@ test_that("list_unchop() fails with complex foreign S4 classes", { test_that("list_unchop() falls back to c() if S3 method is available", { # Check off-by-one error expect_error( - list_unchop(list(foobar(1), "", foobar(2)), list(1, 2, 3)), + list_unchop(list(foobar(1), "", foobar(2)), indices = list(1, 2, 3)), class = "vctrs_error_incompatible_type" ) @@ -645,11 +645,11 @@ test_that("list_unchop() falls back to c() if S3 method is available", { foobar(c(1, 2)) ) expect_identical( - list_unchop(list(foobar(1), foobar(2)), list(1, 2)), + list_unchop(list(foobar(1), foobar(2)), indices = list(1, 2)), foobar(c(1, 2)) ) expect_identical( - list_unchop(list(foobar(1), foobar(2)), list(2, 1)), + list_unchop(list(foobar(1), foobar(2)), indices = list(2, 1)), foobar(c(2, 1)) ) expect_identical( @@ -659,47 +659,47 @@ test_that("list_unchop() falls back to c() if S3 method is available", { # OOB error is respected expect_error( - list_unchop(list(foobar(1), foobar(2)), list(1, 3)), + list_unchop(list(foobar(1), foobar(2)), indices = list(1, 3)), class = "vctrs_error_subscript_oob" ) # Unassigned locations results in missing values. # Repeated assignment uses the last assigned value. expect_identical( - list_unchop(list(foobar(c(1, 2)), foobar(3)), list(c(1, 3), 1)), + list_unchop(list(foobar(c(1, 2)), foobar(3)), indices = list(c(1, 3), 1)), foobar(c(3, NA, 2)) ) expect_identical( - list_unchop(list(foobar(c(1, 2)), foobar(3)), list(c(2, NA), NA)), + list_unchop(list(foobar(c(1, 2)), foobar(3)), indices = list(c(2, NA), NA)), foobar(c(NA, 1, NA)) ) # Names are kept expect_identical( - list_unchop(list(foobar(c(x = 1, y = 2)), foobar(c(x = 1))), list(c(2, 1), 3)), + list_unchop(list(foobar(c(x = 1, y = 2)), foobar(c(x = 1))), indices = list(c(2, 1), 3)), foobar(c(y = 2, x = 1, x = 1)) ) # Recycles to the size of index expect_identical( - list_unchop(list(foobar(1), foobar(2)), list(c(1, 3), 2)), + list_unchop(list(foobar(1), foobar(2)), indices = list(c(1, 3), 2)), foobar(c(1, 2, 1)) ) expect_identical( - list_unchop(list(foobar(1), foobar(2)), list(c(1, 2), integer())), + list_unchop(list(foobar(1), foobar(2)), indices = list(c(1, 2), integer())), foobar(c(1, 1)) ) expect_snapshot({ (expect_error( - list_unchop(list(foobar(1), foobar(2)), list(c(1, 3), integer())), + list_unchop(list(foobar(1), foobar(2)), indices = list(c(1, 3), integer())), class = "vctrs_error_subscript_oob" )) }) expect_snapshot({ x <- list(foobar(1:2)) indices <- list(1:3) - (expect_error(list_unchop(x, indices))) - (expect_error(list_unchop(x, indices, error_arg = "arg", error_call = call("foo")))) + (expect_error(list_unchop(x, indices = indices))) + (expect_error(list_unchop(x, indices = indices, error_arg = "arg", error_call = call("foo")))) }) method_vctrs_c_fallback <- function(...) { @@ -717,7 +717,7 @@ test_that("list_unchop() falls back to c() if S3 method is available", { structure(1, class = "vctrs_c_fallback"), structure(2, class = "vctrs_c_fallback") ), - list(2, 1) + indices = list(2, 1) ), structure(c(2, 1), class = "vctrs_c_fallback") ) @@ -735,7 +735,7 @@ test_that("list_unchop() falls back for S4 classes with a registered c() method" expect_snapshot({ (expect_error( - list_unchop(list(joe, 1, jane), list(c(1, 2), 3, 4)), + list_unchop(list(joe, 1, jane), indices = list(c(1, 2), 3, 4)), class = "vctrs_error_incompatible_type" )) }) @@ -743,23 +743,23 @@ test_that("list_unchop() falls back for S4 classes with a registered c() method" local_c_counts() expect_identical( - list_unchop(list(joe, jane), list(c(1, 3), 2)), + list_unchop(list(joe, jane), indices = list(c(1, 3), 2)), .Counts(c(1L, 3L, 2L), name = "Dispatched") ) expect_identical( - list_unchop(list(NULL, joe, jane), list(integer(), c(1, 3), 2)), + list_unchop(list(NULL, joe, jane), indices = list(integer(), c(1, 3), 2)), .Counts(c(1L, 3L, 2L), name = "Dispatched") ) # Unassigned locations results in missing values. # Repeated assignment uses the last assigned value. expect_identical( - list_unchop(list(joe, jane), list(c(1, 3), 1)), + list_unchop(list(joe, jane), indices = list(c(1, 3), 1)), .Counts(c(3L, NA, 2L), name = "Dispatched") ) expect_identical( - list_unchop(list(joe, jane), list(c(2, NA), NA)), + list_unchop(list(joe, jane), indices = list(c(2, NA), NA)), .Counts(c(NA, 1L, NA), name = "Dispatched") ) }) @@ -793,17 +793,17 @@ test_that("list_unchop() supports numeric S3 indices", { vec_cast.integer.vctrs_foobar = function(x, to, ...) vec_data(x) ) - expect_identical(list_unchop(list(1), list(foobar(1L))), 1) + expect_identical(list_unchop(list(1), indices = list(foobar(1L))), 1) }) test_that("list_unchop() does not support non-numeric S3 indices", { expect_snapshot({ (expect_error( - list_unchop(list(1), list(factor("x"))), + list_unchop(list(1), indices = list(factor("x"))), class = "vctrs_error_subscript_type" )) (expect_error( - list_unchop(list(1), list(foobar(1L))), + list_unchop(list(1), indices = list(foobar(1L))), class = "vctrs_error_subscript_type" )) }) @@ -883,7 +883,7 @@ test_that("list_unchop() falls back to c() methods (#1120)", { c("dispatched1", "dispatched2", "dispatched3") ) expect_identical( - list_unchop(xs, list(c(2, 1), 3)), + list_unchop(xs, indices = list(c(2, 1), 3)), c("dispatched2", "dispatched1", "dispatched3") ) }) @@ -898,7 +898,7 @@ test_that("list_unchop() fails if foreign classes are not homogeneous and there class = "vctrs_error_incompatible_type" ) expect_error( - list_unchop(xs, list(c(2, 1), 3)), + list_unchop(xs, indices = list(c(2, 1), 3)), class = "vctrs_error_incompatible_type" ) }) diff --git a/tests/testthat/test-type-table.R b/tests/testthat/test-type-table.R index 9d33a8a24..0e29b23a3 100644 --- a/tests/testthat/test-type-table.R +++ b/tests/testthat/test-type-table.R @@ -204,7 +204,7 @@ test_that("can use a table in `list_unchop()`", { x <- new_table(1:4, dim = c(2L, 2L)) expect_identical(list_unchop(list(x)), x) - expect_identical(list_unchop(list(x, x), list(1:2, 4:3)), vec_slice(x, c(1:2, 2:1))) + expect_identical(list_unchop(list(x, x), indices = list(1:2, 4:3)), vec_slice(x, c(1:2, 2:1))) }) test_that("can concatenate tables", { From a2dcac5ccd169730f95b586693df3a113b168dc8 Mon Sep 17 00:00:00 2001 From: Davis Vaughan Date: Wed, 5 Oct 2022 10:43:25 -0400 Subject: [PATCH 141/312] Implement `list_all_size()` and `list_check_all_size()` (#1714) * Pass the call through `stop_assert_size()` * Introduce `vec_size_params()` * Implement `list_all_size()` and `list_check_all_size()` * NEWS bullet * Document `size` * Rename to `vec_size_3()` * Use wrappers to better mimic real life usage --- NAMESPACE | 2 + NEWS.md | 3 ++ R/assert.R | 49 ++++++++++++++++++------ man/vec_is_list.Rd | 37 +++++++++++++----- src/assert.c | 45 +++++++++++++++++++++- src/conditions.c | 16 +++++--- src/decl/assert-decl.h | 6 +++ src/decl/size-decl.h | 3 ++ src/globals.c | 1 + src/globals.h | 1 + src/init.c | 4 ++ src/size.c | 59 ++++++++++++++++++++++++---- src/size.h | 1 + src/vctrs.h | 3 +- tests/testthat/_snaps/assert.md | 68 +++++++++++++++++++++++++++++++++ tests/testthat/test-assert.R | 59 ++++++++++++++++++++++++++++ 16 files changed, 321 insertions(+), 36 deletions(-) diff --git a/NAMESPACE b/NAMESPACE index 88d84c5d5..2e5a286bc 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -462,7 +462,9 @@ export(field) export(fields) export(is_list_of) export(is_partial) +export(list_all_size) export(list_all_vectors) +export(list_check_all_size) export(list_check_all_vectors) export(list_drop_empty) export(list_of) diff --git a/NEWS.md b/NEWS.md index a366770f9..cd9d2317f 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,5 +1,8 @@ # vctrs (development version) +* New `list_all_size()` and `list_check_all_size()` to quickly determine if a + list contains elements of a particular `size` (#1582). + * `list_unchop()` has gained empty `...` to force optional arguments to be named (#1715). diff --git a/R/assert.R b/R/assert.R index 1b3ef81b0..ba7af57c6 100644 --- a/R/assert.R +++ b/R/assert.R @@ -194,30 +194,37 @@ vec_is_vector <- function(x) { .Call(vctrs_is_vector, x) } -#' Is the object a list? +#' List checks #' #' @description -#' `vec_is_list()` tests if `x` is considered a list in the vctrs sense. It -#' returns `TRUE` if: +#' - `vec_is_list()` tests if `x` is considered a list in the vctrs sense. It +#' returns `TRUE` if: +#' - `x` is a bare list with no class. +#' - `x` is a list explicitly inheriting from `"list"`. #' -#' * `x` is a bare list with no class. -#' * `x` is a list explicitly inheriting from `"list"`. +#' - `list_all_vectors()` takes a list and returns `TRUE` if all elements of +#' that list are vectors. #' -#' `list_all_vectors()` takes a list and checks that all elements of -#' `x` are vectors. +#' - `list_all_size()` takes a list and returns `TRUE` if all elements of that +#' list have the same `size`. #' -#' `vec_check_list()` and `list_check_all_vectors()` throw a type -#' error if the input is not a list as defined by `vec_is_list()` and -#' `list_all_vectors()` respectively. +#' - `vec_check_list()`, `list_check_all_vectors()`, and `list_check_all_size()` +#' use the above functions, but throw a standardized and informative error if +#' they return `FALSE`. #' #' @inheritParams rlang::args_error_context #' @inheritParams rlang::args_dots_empty -#' @param x An object. +#' +#' @param x For `vec_*()` functions, an object. For `list_*()` functions, a +#' list. +#' +#' @param size The size to check each element for. #' #' @details #' Notably, data frames and S3 record style classes like POSIXlt are not #' considered lists. #' +#' @seealso [list_sizes()] #' @export #' @examples #' vec_is_list(list()) @@ -227,6 +234,9 @@ vec_is_vector <- function(x) { #' list_all_vectors(list(1, mtcars)) #' list_all_vectors(list(1, environment())) #' +#' list_all_size(list(1:2, 2:3), 2) +#' list_all_size(list(1:2, 2:4), 2) +#' #' # `list_`-prefixed functions assume a list: #' try(list_all_vectors(environment())) vec_is_list <- function(x) { @@ -258,6 +268,23 @@ list_check_all_vectors <- function(x, invisible(.Call(ffi_list_check_all_vectors, x, environment())) } +#' @rdname vec_is_list +#' @export +list_all_size <- function(x, size) { + .Call(ffi_list_all_size, x, size, environment()) +} + +#' @rdname vec_is_list +#' @export +list_check_all_size <- function(x, + size, + ..., + arg = caller_arg(x), + call = caller_env()) { + check_dots_empty0(...) + invisible(.Call(ffi_list_check_all_size, x, size, environment())) +} + # Called from C stop_non_list_type <- function(x, arg, call) { if (nzchar(arg)) { diff --git a/man/vec_is_list.Rd b/man/vec_is_list.Rd index 71deb0694..c565f76ab 100644 --- a/man/vec_is_list.Rd +++ b/man/vec_is_list.Rd @@ -5,7 +5,9 @@ \alias{vec_check_list} \alias{list_all_vectors} \alias{list_check_all_vectors} -\title{Is the object a list?} +\alias{list_all_size} +\alias{list_check_all_size} +\title{List checks} \usage{ vec_is_list(x) @@ -14,9 +16,14 @@ vec_check_list(x, ..., arg = caller_arg(x), call = caller_env()) list_all_vectors(x) list_check_all_vectors(x, ..., arg = caller_arg(x), call = caller_env()) + +list_all_size(x, size) + +list_check_all_size(x, size, ..., arg = caller_arg(x), call = caller_env()) } \arguments{ -\item{x}{An object.} +\item{x}{For \verb{vec_*()} functions, an object. For \verb{list_*()} functions, a +list.} \item{...}{These dots are for future extensions and must be empty.} @@ -28,21 +35,25 @@ origin of a problem.} running function, e.g. \code{caller_env()}. The function will be mentioned in error messages as the source of the error. See the \code{call} argument of \code{\link[rlang:abort]{abort()}} for more information.} + +\item{size}{The size to check each element for.} } \description{ -\code{vec_is_list()} tests if \code{x} is considered a list in the vctrs sense. It +\itemize{ +\item \code{vec_is_list()} tests if \code{x} is considered a list in the vctrs sense. It returns \code{TRUE} if: \itemize{ \item \code{x} is a bare list with no class. \item \code{x} is a list explicitly inheriting from \code{"list"}. } - -\code{list_all_vectors()} takes a list and checks that all elements of -\code{x} are vectors. - -\code{vec_check_list()} and \code{list_check_all_vectors()} throw a type -error if the input is not a list as defined by \code{vec_is_list()} and -\code{list_all_vectors()} respectively. +\item \code{list_all_vectors()} takes a list and returns \code{TRUE} if all elements of +that list are vectors. +\item \code{list_all_size()} takes a list and returns \code{TRUE} if all elements of that +list have the same \code{size}. +\item \code{vec_check_list()}, \code{list_check_all_vectors()}, and \code{list_check_all_size()} +use the above functions, but throw a standardized and informative error if +they return \code{FALSE}. +} } \details{ Notably, data frames and S3 record style classes like POSIXlt are not @@ -56,6 +67,12 @@ vec_is_list(data.frame()) list_all_vectors(list(1, mtcars)) list_all_vectors(list(1, environment())) +list_all_size(list(1:2, 2:3), 2) +list_all_size(list(1:2, 2:4), 2) + # `list_`-prefixed functions assume a list: try(list_all_vectors(environment())) } +\seealso{ +\code{\link[=list_sizes]{list_sizes()}} +} diff --git a/src/assert.c b/src/assert.c index 8cc9a33e3..1aa8217f8 100644 --- a/src/assert.c +++ b/src/assert.c @@ -25,10 +25,10 @@ void vec_check_size(r_obj* x, r_ssize size, struct vctrs_arg* arg, struct r_lazy call) { - r_ssize x_size = vec_size(x); + r_ssize x_size = vec_size_3(x, arg, call); if (x_size != size) { - stop_assert_size(x_size, size, arg); + stop_assert_size(x_size, size, arg, call); } } @@ -85,3 +85,44 @@ r_obj* ffi_list_check_all_vectors(r_obj* x, r_obj* frame) { FREE(1); return r_null; } + +r_obj* ffi_list_check_all_size(r_obj* xs, r_obj* ffi_size, r_obj* frame) { + // This is an internal error + vec_check_list(xs, vec_args.x, (struct r_lazy) {.x = frame, .env = r_null }); + + struct r_lazy arg_lazy = { .x = syms.arg, .env = frame }; + struct vctrs_arg arg = new_lazy_arg(&arg_lazy); + + struct r_lazy call = { .x = r_syms.call, .env = frame }; + + r_ssize size = r_arg_as_ssize(ffi_size, "size"); + + list_check_all_size(xs, size, &arg, call); + + return r_null; +} + +static +void list_check_all_size(r_obj* xs, + r_ssize size, + struct vctrs_arg* p_arg, + struct r_lazy call) { + if (r_typeof(xs) != R_TYPE_list) { + r_stop_unexpected_type(r_typeof(xs)); + } + + r_ssize i = 0; + + r_ssize xs_size = r_length(xs); + r_obj* xs_names = r_names(xs); + r_obj* const* v_xs = r_list_cbegin(xs); + + struct vctrs_arg* p_x_arg = new_subscript_arg(p_arg, xs_names, xs_size, &i); + KEEP(p_x_arg->shelter); + + for (; i < xs_size; ++i) { + vec_check_size(v_xs[i], size, p_x_arg, call); + } + + FREE(1); +} diff --git a/src/conditions.c b/src/conditions.c index 921687336..1472d4e52 100644 --- a/src/conditions.c +++ b/src/conditions.c @@ -19,22 +19,28 @@ void stop_scalar_type(r_obj* x, // [[ include("vctrs.h") ]] void stop_assert_size(r_ssize actual, r_ssize required, - struct vctrs_arg* arg) { - r_obj* syms[4] = { + struct vctrs_arg* arg, + struct r_lazy call) { + r_obj* ffi_call = KEEP(r_lazy_eval(call)); + ffi_call = KEEP(r_expr_protect(ffi_call)); + + r_obj* syms[5] = { syms_actual, syms_required, r_syms.arg, + r_syms.call, NULL }; - r_obj* args[4] = { + r_obj* args[5] = { KEEP(r_int(actual)), KEEP(r_int(required)), KEEP(vctrs_arg(arg)), + ffi_call, NULL }; - r_obj* call = KEEP(r_call_n(syms_stop_assert_size, syms, args)); - r_eval(call, vctrs_ns_env); + r_obj* stop_call = KEEP(r_call_n(syms_stop_assert_size, syms, args)); + r_eval(stop_call, vctrs_ns_env); never_reached("stop_assert_size"); } diff --git a/src/decl/assert-decl.h b/src/decl/assert-decl.h index 893bf016d..43b007d58 100644 --- a/src/decl/assert-decl.h +++ b/src/decl/assert-decl.h @@ -2,3 +2,9 @@ static r_no_return void stop_non_list_type(r_obj* x, struct vctrs_arg* arg, struct r_lazy call); + +static +void list_check_all_size(r_obj* xs, + r_ssize size, + struct vctrs_arg* p_arg, + struct r_lazy call); diff --git a/src/decl/size-decl.h b/src/decl/size-decl.h index acdeb46af..556a95e93 100644 --- a/src/decl/size-decl.h +++ b/src/decl/size-decl.h @@ -6,3 +6,6 @@ r_ssize vec_raw_size(r_obj* x); static r_obj* list_sizes(r_obj* x, const struct vec_error_opts* err); + +static +bool list_all_size(r_obj* xs, r_ssize size); diff --git a/src/globals.c b/src/globals.c index 3ee74a9fa..772e4998a 100644 --- a/src/globals.c +++ b/src/globals.c @@ -92,4 +92,5 @@ void vctrs_init_globals(r_obj* ns) { INIT_CALL(vec_recycle_common); INIT_CALL(vec_size); INIT_CALL(vec_size_common); + INIT_CALL(list_all_size); } diff --git a/src/globals.h b/src/globals.h index 8286087fe..b2a6e501d 100644 --- a/src/globals.h +++ b/src/globals.h @@ -69,6 +69,7 @@ struct lazy_calls { struct r_lazy vec_recycle_common; struct r_lazy vec_size; struct r_lazy vec_size_common; + struct r_lazy list_all_size; }; extern struct syms syms; diff --git a/src/init.c b/src/init.c index 3cf9f76fc..e8b6de15a 100644 --- a/src/init.c +++ b/src/init.c @@ -150,6 +150,8 @@ extern r_obj* ffi_list_all_vectors(r_obj*, r_obj*); extern r_obj* ffi_list_check_all_vectors(r_obj*, r_obj*); extern r_obj* ffi_as_short_length(r_obj*, r_obj*); extern r_obj* ffi_s3_get_method(r_obj*, r_obj*, r_obj*); +extern r_obj* ffi_list_all_size(r_obj*, r_obj*, r_obj*); +extern r_obj* ffi_list_check_all_size(r_obj*, r_obj*, r_obj*); // Maturing @@ -323,6 +325,8 @@ static const R_CallMethodDef CallEntries[] = { {"ffi_list_check_all_vectors", (DL_FUNC) &ffi_list_check_all_vectors, 2}, {"ffi_as_short_length", (DL_FUNC) &ffi_as_short_length, 2}, {"ffi_s3_get_method", (DL_FUNC) &ffi_s3_get_method, 3}, + {"ffi_list_all_size", (DL_FUNC) &ffi_list_all_size, 3}, + {"ffi_list_check_all_size", (DL_FUNC) &ffi_list_check_all_size, 3}, {"ffi_exp_vec_cast", (DL_FUNC) &exp_vec_cast, 2}, {NULL, NULL, 0} }; diff --git a/src/size.c b/src/size.c index 306e57168..9b448d25e 100644 --- a/src/size.c +++ b/src/size.c @@ -4,17 +4,20 @@ // [[ register() ]] r_obj* ffi_size(r_obj* x, r_obj* frame) { - struct vec_error_opts err = { - .p_arg = vec_args.x, - .call = { .x = frame, .env = r_null } - }; - return r_len(vec_size_opts(x, &err)); + struct r_lazy call = { .x = frame, .env = r_null }; + return r_len(vec_size_3(x, vec_args.x, call)); } r_ssize vec_size(r_obj* x) { + return vec_size_3(x, vec_args.x, lazy_calls.vec_size); +} + +r_ssize vec_size_3(r_obj* x, + struct vctrs_arg* p_arg, + struct r_lazy call) { struct vec_error_opts err = { - .p_arg = vec_args.x, - .call = lazy_calls.vec_size + .p_arg = p_arg, + .call = call }; return vec_size_opts(x, &err); } @@ -110,6 +113,48 @@ r_obj* list_sizes(r_obj* x, const struct vec_error_opts* opts) { return out; } +r_obj* ffi_list_all_size(r_obj* xs, r_obj* ffi_size, r_obj* frame) { + // This is an internal error + vec_check_list(xs, vec_args.x, (struct r_lazy) {.x = frame, .env = r_null }); + + r_ssize size = r_arg_as_ssize(ffi_size, "size"); + + return r_lgl(list_all_size(xs, size)); +} + +static +bool list_all_size(r_obj* xs, r_ssize size) { + if (r_typeof(xs) != R_TYPE_list) { + r_stop_unexpected_type(r_typeof(xs)); + } + + r_ssize i = 0; + + r_ssize xs_size = r_length(xs); + r_obj* xs_names = r_names(xs); + r_obj* const* v_xs = r_list_cbegin(xs); + + struct vctrs_arg* p_x_arg = new_subscript_arg(vec_args.x, xs_names, xs_size, &i); + KEEP(p_x_arg->shelter); + + bool out = true; + + for (; i < xs_size; ++i) { + r_obj* x = v_xs[i]; + + // Scalar list elements throw an error internal to `list_all_size()` + r_ssize x_size = vec_size_3(x, p_x_arg, lazy_calls.list_all_size); + + if (x_size != size) { + out = false; + break; + } + } + + FREE(1); + return out; +} + r_ssize df_rownames_size(r_obj* x) { for (r_obj* attr = r_attrib(x); attr != r_null; diff --git a/src/size.h b/src/size.h index d41c94655..ad1e7692e 100644 --- a/src/size.h +++ b/src/size.h @@ -5,6 +5,7 @@ #include "globals.h" r_ssize vec_size(r_obj* x); +r_ssize vec_size_3(r_obj* x, struct vctrs_arg* p_arg, struct r_lazy call); r_obj* vec_check_recycle(r_obj* x, r_ssize size, diff --git a/src/vctrs.h b/src/vctrs.h index 6abe7faae..3da88ee7b 100644 --- a/src/vctrs.h +++ b/src/vctrs.h @@ -247,7 +247,8 @@ void stop_scalar_type(SEXP x, __attribute__((noreturn)) void stop_assert_size(r_ssize actual, r_ssize required, - struct vctrs_arg* arg); + struct vctrs_arg* arg, + struct r_lazy call); __attribute__((noreturn)) void stop_incompatible_type(SEXP x, SEXP y, diff --git a/tests/testthat/_snaps/assert.md b/tests/testthat/_snaps/assert.md index f6f9c9191..185ed5156 100644 --- a/tests/testthat/_snaps/assert.md +++ b/tests/testthat/_snaps/assert.md @@ -243,6 +243,74 @@ Error in `my_function()`: ! `my_arg$foo` must be a vector, not an environment. +# list_check_all_size() works + + Code + my_function <- (function(my_arg, size) list_check_all_size(my_arg, size)) + (expect_error(list_check_all_size(list(1:2, 1:3), 2))) + Output + + Error: + ! `list(1:2, 1:3)[[2]]` must have size 2, not size 3. + Code + (expect_error(my_function(list(1:2, 1:3), 2))) + Output + + Error in `my_function()`: + ! `my_arg[[2]]` must have size 2, not size 3. + Code + (expect_error(my_function(list(NULL, 1:2), 2))) + Output + + Error in `my_function()`: + ! `my_arg[[1]]` must have size 2, not size 0. + +# list_all_size() and list_check_all_size() error on scalars + + Code + (expect_error(list_all_size(x, 2))) + Output + + Error in `list_all_size()`: + ! `x[[1]]` must be a vector, not an environment. + Code + my_function <- (function(my_arg, size) list_check_all_size(my_arg, size)) + (expect_error(my_function(x, 2))) + Output + + Error in `my_function()`: + ! `my_arg[[1]]` must be a vector, not an environment. + +# list_all_size() and list_check_all_size() throw error using internal call on non-list input + + Code + (expect_error(list_all_size(1, 2))) + Output + + Error in `list_all_size()`: + ! `x` must be a list, not a number. + Code + (expect_error(list_check_all_size(1, 2, arg = "arg", call = call("foo")))) + Output + + Error in `list_check_all_size()`: + ! `x` must be a list, not a number. + +# list_all_size() and list_check_all_size() validate `size` + + Code + (expect_error(list_all_size(list(), size = "x"))) + Output + + Error in `list_all_size()`: + ! `size` must be a scalar integer or double. + Code + (expect_error(list_check_all_size(list(), size = "x"))) + Output + + Error in `list_check_all_size()`: + ! `size` must be a scalar integer or double. + # informative messages when 1d array doesn't match vector Code diff --git a/tests/testthat/test-assert.R b/tests/testthat/test-assert.R index 6118f9070..fde573716 100644 --- a/tests/testthat/test-assert.R +++ b/tests/testthat/test-assert.R @@ -355,6 +355,65 @@ test_that("vec_check_list() and list_check_all_vectors() work", { }) }) +test_that("list_all_size() works", { + expect_true(list_all_size(list(), 2)) + expect_true(list_all_size(list(integer()), 0)) + expect_true(list_all_size(list(NULL), 0)) + expect_true(list_all_size(list(1:2, 2:3), 2)) + + expect_false(list_all_size(list(1:2, 1:3), 2)) + expect_false(list_all_size(list(NULL, 1:2), 2)) + + expect_true(list_all_size(list_of(1:3, 2:4), 3)) + expect_false(list_all_size(list_of(1:3, 2:4), 4)) +}) + +test_that("list_check_all_size() works", { + expect_null(list_check_all_size(list(), 2)) + expect_null(list_check_all_size(list(integer()), 0)) + expect_null(list_check_all_size(list(NULL), 0)) + expect_null(list_check_all_size(list(1:2, 2:3), 2)) + + expect_snapshot({ + my_function <- function(my_arg, size) list_check_all_size(my_arg, size) + + # Validates sizes + (expect_error(list_check_all_size(list(1:2, 1:3), 2))) + (expect_error(my_function(list(1:2, 1:3), 2))) + + # `NULL` is not ignored + (expect_error(my_function(list(NULL, 1:2), 2))) + }) +}) + +test_that("list_all_size() and list_check_all_size() error on scalars", { + x <- list(env()) + + expect_snapshot({ + # Error considered internal to `list_all_size()` + (expect_error(list_all_size(x, 2))) + + my_function <- function(my_arg, size) list_check_all_size(my_arg, size) + (expect_error(my_function(x, 2))) + }) +}) + +test_that("list_all_size() and list_check_all_size() throw error using internal call on non-list input", { + expect_snapshot({ + (expect_error(list_all_size(1, 2))) + + # `arg` and `call` are ignored + (expect_error(list_check_all_size(1, 2, arg = "arg", call = call("foo")))) + }) +}) + +test_that("list_all_size() and list_check_all_size() validate `size`", { + expect_snapshot({ + (expect_error(list_all_size(list(), size = "x"))) + (expect_error(list_check_all_size(list(), size = "x"))) + }) +}) + test_that("informative messages when 1d array doesn't match vector", { x <- array(1:3) expect_snapshot((expect_error(vec_assert(x, int())))) From 1ab17d562183dd78b9f941644f35735d5c810a80 Mon Sep 17 00:00:00 2001 From: "Jennifer (Jenny) Bryan" Date: Wed, 5 Oct 2022 08:11:23 -0700 Subject: [PATCH 142/312] More work re `"*_quiet"` name repair strings (#1716) * Handle data_frame() and df_list() * vec_c(): change signature and add a test * list_unchop(): Change signature, add test * vec_interleave(): change signature, add test * vec_rbind(), vec_cbind(): change signatures, add tests * Add to the existing NEWS bullet * Apply suggestions from code review Co-authored-by: Davis Vaughan Co-authored-by: Davis Vaughan --- NEWS.md | 5 +++++ R/bind.R | 10 +++++----- R/c.R | 2 +- R/slice-chop.R | 2 +- R/slice-interleave.R | 2 +- R/type-data-frame.R | 22 ++++++++++++---------- man/data_frame.Rd | 16 +++++++++------- man/df_list.Rd | 8 +++++--- man/vec_bind.Rd | 12 +++++++----- man/vec_c.Rd | 3 ++- man/vec_chop.Rd | 3 ++- man/vec_interleave.Rd | 3 ++- tests/testthat/_snaps/bind.md | 13 +++++++++++++ tests/testthat/_snaps/c.md | 6 ++++++ tests/testthat/_snaps/slice-chop.md | 10 ++++++++++ tests/testthat/_snaps/slice-interleave.md | 6 ++++++ tests/testthat/_snaps/type-data-frame.md | 8 ++++++++ tests/testthat/test-bind.R | 22 ++++++++++++++++++++++ tests/testthat/test-c.R | 11 +++++++++++ tests/testthat/test-slice-chop.R | 18 ++++++++++++++++++ tests/testthat/test-slice-interleave.R | 11 +++++++++++ tests/testthat/test-type-data-frame.R | 16 ++++++++++++++++ 22 files changed, 173 insertions(+), 36 deletions(-) diff --git a/NEWS.md b/NEWS.md index cd9d2317f..14f390672 100644 --- a/NEWS.md +++ b/NEWS.md @@ -33,6 +33,11 @@ like specifying `repair = "unique", quiet = TRUE`. When the `"*_quiet"` options are used, any setting of `quiet` is silently overridden (@jennybc, #1629). + + `"unique_quiet"` and `"universal_quiet"` are also newly accepted for the name + repair argument of several other functions that do not expose a `quiet` + argument: `data_frame()`, `df_list()`, `vec_c()`, `list_unchop()`, + `vec_interleave()`, `vec_rbind()`, and `vec_cbind()` (@jennybc, #1716). * `list_unchop()` has gained `error_call` and `error_arg` arguments (#1641, #1692). diff --git a/R/bind.R b/R/bind.R index efa4e103d..45a1b295b 100644 --- a/R/bind.R +++ b/R/bind.R @@ -54,9 +54,9 @@ #' not named, an integer column is used instead. #' #' * If `NULL`, the input names are used as row names. -#' @param .name_repair One of `"unique"`, `"universal"`, or -#' `"check_unique"`. See [vec_as_names()] for the meaning of these -#' options. +#' @param .name_repair One of `"unique"`, `"universal"`, `"check_unique"`, +#' `"unique_quiet"`, or `"universal_quiet"`. See [vec_as_names()] for the +#' meaning of these options. #' #' With `vec_rbind()`, the repair function is applied to all inputs #' separately. This is because `vec_rbind()` needs to align their @@ -176,7 +176,7 @@ NULL vec_rbind <- function(..., .ptype = NULL, .names_to = rlang::zap(), - .name_repair = c("unique", "universal", "check_unique"), + .name_repair = c("unique", "universal", "check_unique", "unique_quiet", "universal_quiet"), .name_spec = NULL, .error_call = current_env()) { .External2(ffi_rbind, .ptype, .names_to, .name_repair, .name_spec) @@ -194,7 +194,7 @@ vec_rbind <- fn_inline_formals(vec_rbind, ".name_repair") vec_cbind <- function(..., .ptype = NULL, .size = NULL, - .name_repair = c("unique", "universal", "check_unique", "minimal"), + .name_repair = c("unique", "universal", "check_unique", "minimal", "unique_quiet", "universal_quiet"), .error_call = current_env()) { .External2(ffi_cbind, .ptype, .size, .name_repair) } diff --git a/R/c.R b/R/c.R index 89b058e3a..4ab207cfa 100644 --- a/R/c.R +++ b/R/c.R @@ -68,7 +68,7 @@ vec_c <- function(..., .ptype = NULL, .name_spec = NULL, - .name_repair = c("minimal", "unique", "check_unique", "universal"), + .name_repair = c("minimal", "unique", "check_unique", "universal", "unique_quiet", "universal_quiet"), .error_arg = "", .error_call = current_env()) { .External2(ffi_vec_c, .ptype, .name_spec, .name_repair) diff --git a/R/slice-chop.R b/R/slice-chop.R index e7b416d42..d9be9b2e3 100644 --- a/R/slice-chop.R +++ b/R/slice-chop.R @@ -100,7 +100,7 @@ list_unchop <- function(x, indices = NULL, ptype = NULL, name_spec = NULL, - name_repair = c("minimal", "unique", "check_unique", "universal"), + name_repair = c("minimal", "unique", "check_unique", "universal", "unique_quiet", "universal_quiet"), error_arg = "x", error_call = current_env()) { check_dots_empty0(...) diff --git a/R/slice-interleave.R b/R/slice-interleave.R index 6679faefe..dd26557ac 100644 --- a/R/slice-interleave.R +++ b/R/slice-interleave.R @@ -38,7 +38,7 @@ vec_interleave <- function(..., .ptype = NULL, .name_spec = NULL, - .name_repair = c("minimal", "unique", "check_unique", "universal")) { + .name_repair = c("minimal", "unique", "check_unique", "universal", "unique_quiet", "universal_quiet")) { args <- list2(...) # `NULL`s must be dropped up front to generate appropriate indices diff --git a/R/type-data-frame.R b/R/type-data-frame.R index 93cf7dce2..18f824dc3 100644 --- a/R/type-data-frame.R +++ b/R/type-data-frame.R @@ -67,8 +67,9 @@ new_data_frame <- fn_inline_formals(new_data_frame, "x") #' will be computed as the common size of the inputs. #' @param .unpack Should unnamed data frame inputs be unpacked? Defaults to #' `TRUE`. -#' @param .name_repair One of `"check_unique"`, `"unique"`, `"universal"` or -#' `"minimal"`. See [vec_as_names()] for the meaning of these options. +#' @param .name_repair One of `"check_unique"`, `"unique"`, `"universal"`, +#' `"minimal"`, `"unique_quiet"`, or `"universal_quiet"`. See [vec_as_names()] +#' for the meaning of these options. #' #' @export #' @examples @@ -89,7 +90,7 @@ new_data_frame <- fn_inline_formals(new_data_frame, "x") df_list <- function(..., .size = NULL, .unpack = TRUE, - .name_repair = c("check_unique", "unique", "universal", "minimal"), + .name_repair = c("check_unique", "unique", "universal", "minimal", "unique_quiet", "universal_quiet"), .error_call = current_env()) { .Call(ffi_df_list, list2(...), .size, .unpack, .name_repair, environment()) } @@ -103,10 +104,10 @@ df_list <- fn_inline_formals(df_list, ".name_repair") #' more in line with vctrs principles. The Properties section outlines these. #' #' @details -#' If no column names are supplied, `""` will be used as a default for all -#' columns. This is applied before name repair occurs, so the default -#' name repair of `"check_unique"` will error if any unnamed inputs -#' are supplied and `"unique"` will repair the empty string column names +#' If no column names are supplied, `""` will be used as a default name for all +#' columns. This is applied before name repair occurs, so the default name +#' repair of `"check_unique"` will error if any unnamed inputs are supplied and +#' `"unique"` (or `"unique_quiet"`) will repair the empty string column names #' appropriately. If the column names don't matter, use a `"minimal"` name #' repair for convenience and performance. #' @@ -125,8 +126,9 @@ df_list <- fn_inline_formals(df_list, ".name_repair") #' named, those names are used for column names. #' @param .size The number of rows in the data frame. If `NULL`, this will #' be computed as the common size of the inputs. -#' @param .name_repair One of `"check_unique"`, `"unique"`, `"universal"` or -#' `"minimal"`. See [vec_as_names()] for the meaning of these options. +#' @param .name_repair One of `"check_unique"`, `"unique"`, `"universal"`, +#' `"minimal"`, `"unique_quiet"`, or `"universal_quiet"`. See [vec_as_names()] +#' for the meaning of these options. #' #' @export #' @examples @@ -163,7 +165,7 @@ df_list <- fn_inline_formals(df_list, ".name_repair") #' data_frame(x = 1, data_frame(y = 1:2, z = "a")) data_frame <- function(..., .size = NULL, - .name_repair = c("check_unique", "unique", "universal", "minimal"), + .name_repair = c("check_unique", "unique", "universal", "minimal", "unique_quiet", "universal_quiet"), .error_call = current_env()) { .Call(ffi_data_frame, list2(...), .size, .name_repair, environment()) } diff --git a/man/data_frame.Rd b/man/data_frame.Rd index df1c93982..36fae58e7 100644 --- a/man/data_frame.Rd +++ b/man/data_frame.Rd @@ -7,7 +7,8 @@ data_frame( ..., .size = NULL, - .name_repair = c("check_unique", "unique", "universal", "minimal"), + .name_repair = c("check_unique", "unique", "universal", "minimal", "unique_quiet", + "universal_quiet"), .error_call = current_env() ) } @@ -18,8 +19,9 @@ named, those names are used for column names.} \item{.size}{The number of rows in the data frame. If \code{NULL}, this will be computed as the common size of the inputs.} -\item{.name_repair}{One of \code{"check_unique"}, \code{"unique"}, \code{"universal"} or -\code{"minimal"}. See \code{\link[=vec_as_names]{vec_as_names()}} for the meaning of these options.} +\item{.name_repair}{One of \code{"check_unique"}, \code{"unique"}, \code{"universal"}, +\code{"minimal"}, \code{"unique_quiet"}, or \code{"universal_quiet"}. See \code{\link[=vec_as_names]{vec_as_names()}} +for the meaning of these options.} \item{.error_call}{The execution environment of a currently running function, e.g. \code{caller_env()}. The function will be @@ -32,10 +34,10 @@ mentioned in error messages as the source of the error. See the more in line with vctrs principles. The Properties section outlines these. } \details{ -If no column names are supplied, \code{""} will be used as a default for all -columns. This is applied before name repair occurs, so the default -name repair of \code{"check_unique"} will error if any unnamed inputs -are supplied and \code{"unique"} will repair the empty string column names +If no column names are supplied, \code{""} will be used as a default name for all +columns. This is applied before name repair occurs, so the default name +repair of \code{"check_unique"} will error if any unnamed inputs are supplied and +\code{"unique"} (or \code{"unique_quiet"}) will repair the empty string column names appropriately. If the column names don't matter, use a \code{"minimal"} name repair for convenience and performance. } diff --git a/man/df_list.Rd b/man/df_list.Rd index fafee6637..91f6f2ae3 100644 --- a/man/df_list.Rd +++ b/man/df_list.Rd @@ -8,7 +8,8 @@ df_list( ..., .size = NULL, .unpack = TRUE, - .name_repair = c("check_unique", "unique", "universal", "minimal"), + .name_repair = c("check_unique", "unique", "universal", "minimal", "unique_quiet", + "universal_quiet"), .error_call = current_env() ) } @@ -22,8 +23,9 @@ will be computed as the common size of the inputs.} \item{.unpack}{Should unnamed data frame inputs be unpacked? Defaults to \code{TRUE}.} -\item{.name_repair}{One of \code{"check_unique"}, \code{"unique"}, \code{"universal"} or -\code{"minimal"}. See \code{\link[=vec_as_names]{vec_as_names()}} for the meaning of these options.} +\item{.name_repair}{One of \code{"check_unique"}, \code{"unique"}, \code{"universal"}, +\code{"minimal"}, \code{"unique_quiet"}, or \code{"universal_quiet"}. See \code{\link[=vec_as_names]{vec_as_names()}} +for the meaning of these options.} \item{.error_call}{The execution environment of a currently running function, e.g. \code{caller_env()}. The function will be diff --git a/man/vec_bind.Rd b/man/vec_bind.Rd index 7acc9a8b2..e20f6a628 100644 --- a/man/vec_bind.Rd +++ b/man/vec_bind.Rd @@ -10,7 +10,8 @@ vec_rbind( ..., .ptype = NULL, .names_to = rlang::zap(), - .name_repair = c("unique", "universal", "check_unique"), + .name_repair = c("unique", "universal", "check_unique", "unique_quiet", + "universal_quiet"), .name_spec = NULL, .error_call = current_env() ) @@ -19,7 +20,8 @@ vec_cbind( ..., .ptype = NULL, .size = NULL, - .name_repair = c("unique", "universal", "check_unique", "minimal"), + .name_repair = c("unique", "universal", "check_unique", "minimal", "unique_quiet", + "universal_quiet"), .error_call = current_env() ) } @@ -55,9 +57,9 @@ not named, an integer column is used instead. \item If \code{NULL}, the input names are used as row names. }} -\item{.name_repair}{One of \code{"unique"}, \code{"universal"}, or -\code{"check_unique"}. See \code{\link[=vec_as_names]{vec_as_names()}} for the meaning of these -options. +\item{.name_repair}{One of \code{"unique"}, \code{"universal"}, \code{"check_unique"}, +\code{"unique_quiet"}, or \code{"universal_quiet"}. See \code{\link[=vec_as_names]{vec_as_names()}} for the +meaning of these options. With \code{vec_rbind()}, the repair function is applied to all inputs separately. This is because \code{vec_rbind()} needs to align their diff --git a/man/vec_c.Rd b/man/vec_c.Rd index 130d17c17..4f5d2df5f 100644 --- a/man/vec_c.Rd +++ b/man/vec_c.Rd @@ -8,7 +8,8 @@ vec_c( ..., .ptype = NULL, .name_spec = NULL, - .name_repair = c("minimal", "unique", "check_unique", "universal"), + .name_repair = c("minimal", "unique", "check_unique", "universal", "unique_quiet", + "universal_quiet"), .error_arg = "", .error_call = current_env() ) diff --git a/man/vec_chop.Rd b/man/vec_chop.Rd index 3bb6e5c3e..6422e2233 100644 --- a/man/vec_chop.Rd +++ b/man/vec_chop.Rd @@ -13,7 +13,8 @@ list_unchop( indices = NULL, ptype = NULL, name_spec = NULL, - name_repair = c("minimal", "unique", "check_unique", "universal"), + name_repair = c("minimal", "unique", "check_unique", "universal", "unique_quiet", + "universal_quiet"), error_arg = "x", error_call = current_env() ) diff --git a/man/vec_interleave.Rd b/man/vec_interleave.Rd index 1b352c63a..5cc415027 100644 --- a/man/vec_interleave.Rd +++ b/man/vec_interleave.Rd @@ -8,7 +8,8 @@ vec_interleave( ..., .ptype = NULL, .name_spec = NULL, - .name_repair = c("minimal", "unique", "check_unique", "universal") + .name_repair = c("minimal", "unique", "check_unique", "universal", "unique_quiet", + "universal_quiet") ) } \arguments{ diff --git a/tests/testthat/_snaps/bind.md b/tests/testthat/_snaps/bind.md index 433ceaf74..c0bce8b5d 100644 --- a/tests/testthat/_snaps/bind.md +++ b/tests/testthat/_snaps/bind.md @@ -55,6 +55,19 @@ x These names are duplicated: * "a" at locations 1 and 2. +# can repair names quietly + + Code + res_unique <- vec_rbind(c(x = 1, x = 2), c(x = 3, x = 4), .name_repair = "unique_quiet") + res_universal <- vec_rbind(c(`if` = 1, `in` = 2), c(`if` = 3, `for` = 4), + .name_repair = "universal_quiet") + +--- + + Code + res_unique <- vec_cbind(x = 1, x = 2, .name_repair = "unique_quiet") + res_universal <- vec_cbind(`if` = 1, `in` = 2, .name_repair = "universal_quiet") + # vec_rbind() fails with arrays of dimensionality > 3 Code diff --git a/tests/testthat/_snaps/c.md b/tests/testthat/_snaps/c.md index dedd3edd2..e40632580 100644 --- a/tests/testthat/_snaps/c.md +++ b/tests/testthat/_snaps/c.md @@ -60,6 +60,12 @@ Error in `vec_c()`: ! Can't combine `foo$x$y$z` and `bar$x$y$z` . +# vec_c() can repair names quietly + + Code + res_unique <- vec_c(x = TRUE, x = 0, .name_repair = "unique_quiet") + res_universal <- vec_c(`if` = TRUE, `in` = 0, .name_repair = "universal_quiet") + # vec_c() fails with complex foreign S3 classes Code diff --git a/tests/testthat/_snaps/slice-chop.md b/tests/testthat/_snaps/slice-chop.md index e511b8faf..66313e5f4 100644 --- a/tests/testthat/_snaps/slice-chop.md +++ b/tests/testthat/_snaps/slice-chop.md @@ -140,6 +140,16 @@ ! Can't convert from `arg[[1]]` to due to loss of precision. * Locations: 1 +# list_unchop() can repair names quietly + + Code + res <- list_unchop(vec_chop(x, indices), indices, name_repair = "unique_quiet") + +--- + + Code + res <- list_unchop(vec_chop(x, indices), indices, name_repair = "universal_quiet") + # list_unchop() errors on unsupported location values Code diff --git a/tests/testthat/_snaps/slice-interleave.md b/tests/testthat/_snaps/slice-interleave.md index 99898ada2..fae12eaee 100644 --- a/tests/testthat/_snaps/slice-interleave.md +++ b/tests/testthat/_snaps/slice-interleave.md @@ -10,6 +10,12 @@ x...1 x...2 1 1 +# can repair names quietly + + Code + res_unique <- vec_interleave(c(x = 1), c(x = 2), .name_repair = "unique_quiet") + res_universal <- vec_interleave(c(`if` = 1), c(`in` = 2), .name_repair = "universal_quiet") + # uses recycling errors Code diff --git a/tests/testthat/_snaps/type-data-frame.md b/tests/testthat/_snaps/type-data-frame.md index b558b7406..4452a6421 100644 --- a/tests/testthat/_snaps/type-data-frame.md +++ b/tests/testthat/_snaps/type-data-frame.md @@ -236,6 +236,14 @@ Error in `df_list()`: ! `.unpack` must be `TRUE` or `FALSE`. +# `.name_repair` can be quiet + + Code + dfl_unique <- df_list(1, 2, .name_repair = "unique_quiet") + dfl_universal <- df_list(`if` = 1, `in` = 2, .name_repair = "universal_quiet") + df_unique <- data_frame(1, 2, .name_repair = "unique_quiet") + df_universal <- data_frame(`if` = 1, `in` = 2, .name_repair = "universal_quiet") + # data frame fallback handles column types (#999) Code diff --git a/tests/testthat/test-bind.R b/tests/testthat/test-bind.R index 53c0f002e..2c2f52494 100644 --- a/tests/testthat/test-bind.R +++ b/tests/testthat/test-bind.R @@ -207,6 +207,17 @@ test_that("can repair names in `vec_rbind()` (#229)", { expect_named(vec_rbind(list(a = 1, a = 2), .name_repair = ~ toupper(.)), c("A", "A")) }) +test_that("can repair names quietly", { + local_name_repair_verbose() + + expect_snapshot({ + res_unique <- vec_rbind(c(x = 1, x = 2), c(x = 3, x = 4), .name_repair = "unique_quiet") + res_universal <- vec_rbind(c("if" = 1, "in" = 2), c("if" = 3, "for" = 4), .name_repair = "universal_quiet") + }) + expect_named(res_unique, c("x...1", "x...2")) + expect_named(res_universal, c(".if", ".in", ".for")) +}) + test_that("can construct an id column", { df <- data.frame(x = 1) @@ -493,6 +504,17 @@ test_that("can repair names in `vec_cbind()` (#227)", { expect_named(vec_cbind(a = 1, a = 2, .name_repair = toupper), c("A", "A")) }) +test_that("can repair names quietly", { + local_name_repair_verbose() + + expect_snapshot({ + res_unique <- vec_cbind(x = 1, x = 2, .name_repair = "unique_quiet") + res_universal <- vec_cbind("if" = 1, "in" = 2, .name_repair = "universal_quiet") + }) + expect_named(res_unique, c("x...1", "x...2")) + expect_named(res_universal, c(".if", ".in")) +}) + test_that("can supply `.names_to` to `vec_rbind()` (#229)", { expect_snapshot({ (expect_error(vec_rbind(.names_to = letters))) diff --git a/tests/testthat/test-c.R b/tests/testthat/test-c.R index 3e85f3367..8233246ed 100644 --- a/tests/testthat/test-c.R +++ b/tests/testthat/test-c.R @@ -138,6 +138,17 @@ test_that("vec_c() repairs names", { expect_named(vec_c(a = 1, a = 2, .name_repair = ~ toupper(.)), c("A", "A")) }) +test_that("vec_c() can repair names quietly", { + local_name_repair_verbose() + + expect_snapshot({ + res_unique <- vec_c(x = TRUE, x = 0, .name_repair = "unique_quiet") + res_universal <- vec_c("if" = TRUE, "in" = 0, .name_repair = "universal_quiet") + }) + expect_named(res_unique, c("x...1", "x...2")) + expect_named(res_universal, c(".if", ".in")) +}) + test_that("vec_c() doesn't use outer names for data frames (#524)", { x <- data.frame(inner = 1) expect_equal(vec_c(outer = x), x) diff --git a/tests/testthat/test-slice-chop.R b/tests/testthat/test-slice-chop.R index a0ef6de2d..80b2f0b15 100644 --- a/tests/testthat/test-slice-chop.R +++ b/tests/testthat/test-slice-chop.R @@ -580,6 +580,24 @@ test_that("name repair is respected and happens after ordering according to `ind expect_named(list_unchop(x, indices = indices, name_repair = "unique"), c("a...1", "a...2")) }) +test_that("list_unchop() can repair names quietly", { + local_name_repair_verbose() + + x <- c(x = "a", x = "b", x = "c") + indices <- list(2, c(3, 1)) + expect_snapshot({ + res <- list_unchop(vec_chop(x, indices), indices = indices, name_repair = "unique_quiet") + }) + expect_named(res, c("x...1", "x...2", "x...3")) + + x <- c("if" = "a", "in" = "b", "for" = "c") + indices <- list(2, c(3, 1)) + expect_snapshot({ + res <- list_unchop(vec_chop(x, indices), indices = indices, name_repair = "universal_quiet") + }) + expect_named(res, c(".if", ".in", ".for")) +}) + test_that("list_unchop() errors on unsupported location values", { expect_snapshot({ (expect_error( diff --git a/tests/testthat/test-slice-interleave.R b/tests/testthat/test-slice-interleave.R index 0c3b0601f..d4ae49be5 100644 --- a/tests/testthat/test-slice-interleave.R +++ b/tests/testthat/test-slice-interleave.R @@ -37,6 +37,17 @@ test_that("allows for name repair", { expect_snapshot(vec_interleave(x, x, .name_repair = "unique")) }) +test_that("can repair names quietly", { + local_name_repair_verbose() + + expect_snapshot({ + res_unique <- vec_interleave(c(x = 1), c(x = 2), .name_repair = "unique_quiet") + res_universal <- vec_interleave(c("if" = 1), c("in" = 2), .name_repair = "universal_quiet") + }) + expect_named(res_unique, c("x...1", "x...2")) + expect_named(res_universal, c(".if", ".in")) +}) + test_that("works with name specs", { x <- c(x = 1) y <- 1 diff --git a/tests/testthat/test-type-data-frame.R b/tests/testthat/test-type-data-frame.R index 566e79641..de7c960d8 100644 --- a/tests/testthat/test-type-data-frame.R +++ b/tests/testthat/test-type-data-frame.R @@ -572,6 +572,22 @@ test_that("`.name_repair` happens after splicing", { expect_named(res, c("x...1", "x...2")) }) +test_that("`.name_repair` can be quiet", { + local_name_repair_verbose() + + expect_snapshot({ + dfl_unique <- df_list(1, 2, .name_repair = "unique_quiet") + dfl_universal <- df_list("if" = 1, "in" = 2, .name_repair = "universal_quiet") + df_unique <- data_frame(1, 2, .name_repair = "unique_quiet") + df_universal <- data_frame("if" = 1, "in" = 2, .name_repair = "universal_quiet") + }) + + expect_named(dfl_unique, c("...1", "...2")) + expect_named(dfl_universal, c(".if", ".in")) + expect_named(df_unique, c("...1", "...2")) + expect_named(df_universal, c(".if", ".in")) +}) + # fallback ---------------------------------------------------------------- test_that("data frame fallback handles column types (#999)", { From 453892788ccde5d09735cbd6d146d934433f5188 Mon Sep 17 00:00:00 2001 From: Jenny Bryan Date: Wed, 5 Oct 2022 08:47:03 -0700 Subject: [PATCH 143/312] Update snapshots Should have been part of #1716, oops --- tests/testthat/_snaps/slice-chop.md | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/tests/testthat/_snaps/slice-chop.md b/tests/testthat/_snaps/slice-chop.md index 66313e5f4..2aa84837c 100644 --- a/tests/testthat/_snaps/slice-chop.md +++ b/tests/testthat/_snaps/slice-chop.md @@ -143,12 +143,12 @@ # list_unchop() can repair names quietly Code - res <- list_unchop(vec_chop(x, indices), indices, name_repair = "unique_quiet") + res <- list_unchop(vec_chop(x, indices), indices = indices, name_repair = "unique_quiet") --- Code - res <- list_unchop(vec_chop(x, indices), indices, name_repair = "universal_quiet") + res <- list_unchop(vec_chop(x, indices), indices = indices, name_repair = "universal_quiet") # list_unchop() errors on unsupported location values From 9854c08bd25629fbca0d6130baa0b076ea1d75ae Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Wed, 5 Oct 2022 14:31:14 +0200 Subject: [PATCH 144/312] Call `vec_default_ptype2()` from `ordered` method --- src/cast.h | 13 ++++++++++ src/ptype2-dispatch.c | 54 ++++++++++++++++++++++++++-------------- src/ptype2-dispatch.h | 8 ++++++ src/type-factor.c | 58 +++++++++++++++++++++++++++---------------- 4 files changed, 92 insertions(+), 41 deletions(-) diff --git a/src/cast.h b/src/cast.h index 440e832df..7a1f350cf 100644 --- a/src/cast.h +++ b/src/cast.h @@ -13,6 +13,19 @@ struct cast_opts { struct fallback_opts fallback; }; +// FIXME: Should we merge these two structs? +static inline +struct ptype2_opts cast_opts_as_ptype2_opts(const struct cast_opts* p_opts) { + return (struct ptype2_opts) { + .x = p_opts->x, + .y = p_opts->to, + .p_x_arg = p_opts->p_x_arg, + .p_y_arg = p_opts->p_to_arg, + .call = p_opts->call, + .fallback = p_opts->fallback, + }; +} + struct cast_common_opts { struct vctrs_arg* p_arg; struct r_lazy call; diff --git a/src/ptype2-dispatch.c b/src/ptype2-dispatch.c index e6a709ae4..feb07dd5a 100644 --- a/src/ptype2-dispatch.c +++ b/src/ptype2-dispatch.c @@ -44,13 +44,18 @@ r_obj* vec_ptype2_dispatch_native(const struct ptype2_opts* opts, } } +// @param from_dispatch Used to implement special behaviour when +// `vec_default_ptype2()` is invoked directly from the dispatch +// mechanism as opposed from a method. + static inline -r_obj* vec_ptype2_default(r_obj* x, - r_obj* y, - struct vctrs_arg* x_arg, - struct vctrs_arg* y_arg, - struct r_lazy call, - const struct fallback_opts* opts) { +r_obj* vec_ptype2_default_full(r_obj* x, + r_obj* y, + struct vctrs_arg* x_arg, + struct vctrs_arg* y_arg, + struct r_lazy call, + const struct fallback_opts* opts, + bool from_dispatch) { r_obj* df_fallback_obj = KEEP(r_int(opts->df)); r_obj* s3_fallback_obj = KEEP(r_int(opts->s3)); r_obj* ffi_x_arg = KEEP(vctrs_arg(x_arg)); @@ -63,7 +68,7 @@ r_obj* vec_ptype2_default(r_obj* x, syms_x_arg, ffi_x_arg, syms_y_arg, ffi_y_arg, syms_call, ffi_call, - syms_from_dispatch, r_true, + syms_from_dispatch, r_lgl(from_dispatch), syms_df_fallback, df_fallback_obj, syms_s3_fallback, s3_fallback_obj); @@ -71,6 +76,15 @@ r_obj* vec_ptype2_default(r_obj* x, return out; } +r_obj* vec_ptype2_default(r_obj* x, + r_obj* y, + struct vctrs_arg* x_arg, + struct vctrs_arg* y_arg, + struct r_lazy call, + const struct fallback_opts* p_opts) { + return vec_ptype2_default_full(x, y, x_arg, y_arg, call, p_opts, false); +} + r_obj* vec_ptype2_dispatch_s3(const struct ptype2_opts* opts) { r_obj* x = KEEP(vec_ptype(opts->x, opts->p_x_arg, opts->call)); r_obj* y = KEEP(vec_ptype(opts->y, opts->p_y_arg, opts->call)); @@ -102,12 +116,13 @@ r_obj* vec_ptype2_dispatch_s3(const struct ptype2_opts* opts) { KEEP(method); if (method == r_null) { - r_obj* out = vec_ptype2_default(x, - y, - opts->p_x_arg, - opts->p_y_arg, - opts->call, - &(opts->fallback)); + r_obj* out = vec_ptype2_default_full(x, + y, + opts->p_x_arg, + opts->p_y_arg, + opts->call, + &(opts->fallback), + true); FREE(3); return out; } @@ -188,12 +203,13 @@ r_obj* ffi_ptype2_dispatch_native(r_obj* x, r_obj* out = vec_ptype2_dispatch_native(&opts, vec_typeof(x), vec_typeof(y), &_left); if (out == r_null) { - out = vec_ptype2_default(x, - y, - &x_arg, - &y_arg, - opts.call, - &opts.fallback); + out = vec_ptype2_default_full(x, + y, + &x_arg, + &y_arg, + opts.call, + &opts.fallback, + true); return out; } else { return out; diff --git a/src/ptype2-dispatch.h b/src/ptype2-dispatch.h index 6cda1503d..a0b1d6d86 100644 --- a/src/ptype2-dispatch.h +++ b/src/ptype2-dispatch.h @@ -2,6 +2,7 @@ #define VCTRS_PTYPE2_DISPATCH_H #include "vctrs-core.h" +#include "ptype2.h" r_obj* vec_ptype2_dispatch_native(const struct ptype2_opts* opts, enum vctrs_type x_type, @@ -18,5 +19,12 @@ r_obj* vec_invoke_coerce_method(r_obj* method_sym, r_obj* method, struct r_lazy call, const struct fallback_opts* opts); +r_obj* vec_ptype2_default(r_obj* x, + r_obj* y, + struct vctrs_arg* x_arg, + struct vctrs_arg* y_arg, + struct r_lazy call, + const struct fallback_opts* p_opts); + #endif diff --git a/src/type-factor.c b/src/type-factor.c index 6ff18978e..a843d96f1 100644 --- a/src/type-factor.c +++ b/src/type-factor.c @@ -32,33 +32,34 @@ SEXP fct_ptype2(const struct ptype2_opts* opts) { } static -SEXP ord_ptype2_validate(SEXP x, - SEXP y, - struct vctrs_arg* x_arg, - struct vctrs_arg* y_arg, - bool cast) { - SEXP x_levels = Rf_getAttrib(x, R_LevelsSymbol); - SEXP y_levels = Rf_getAttrib(y, R_LevelsSymbol); - +bool ord_ptype2_validate(r_obj* x_levels, + r_obj* y_levels, + const struct ptype2_opts* p_opts) { if (TYPEOF(x_levels) != STRSXP) { - stop_corrupt_ordered_levels(x, x_arg); + stop_corrupt_ordered_levels(p_opts->x, p_opts->p_x_arg); } if (TYPEOF(y_levels) != STRSXP) { - stop_corrupt_ordered_levels(y, y_arg); + stop_corrupt_ordered_levels(p_opts->y, p_opts->p_y_arg); } - if (!equal_object(x_levels, y_levels)) { - stop_incompatible_type(x, y, x_arg, y_arg, cast); - } - - return x_levels; + return equal_object(x_levels, y_levels); } // [[ include("type-factor.h") ]] -SEXP ord_ptype2(const struct ptype2_opts* opts) { - SEXP levels = PROTECT(ord_ptype2_validate(opts->x, opts->y, opts->p_x_arg, opts->p_y_arg, false)); - SEXP out = new_empty_ordered(levels); - return UNPROTECT(1), out; +r_obj* ord_ptype2(const struct ptype2_opts* p_opts) { + r_obj* x_levels = r_attrib_get(p_opts->x, R_LevelsSymbol); + r_obj* y_levels = r_attrib_get(p_opts->y, R_LevelsSymbol); + + if (ord_ptype2_validate(x_levels, y_levels, p_opts)) { + return new_empty_ordered(x_levels); + } else { + return vec_ptype2_default(p_opts->x, + p_opts->y, + p_opts->p_x_arg, + p_opts->p_y_arg, + r_lazy_null, + &p_opts->fallback); + } } static SEXP levels_union(SEXP x, SEXP y) { @@ -255,9 +256,22 @@ SEXP fct_as_factor(SEXP x, } // [[ include("factor.h") ]] -SEXP ord_as_ordered(const struct cast_opts* opts) { - ord_ptype2_validate(opts->x, opts->to, opts->p_x_arg, opts->p_to_arg, true); - return opts->x; +SEXP ord_as_ordered(const struct cast_opts* p_opts) { + r_obj* x_levels = r_attrib_get(p_opts->x, R_LevelsSymbol); + r_obj* y_levels = r_attrib_get(p_opts->to, R_LevelsSymbol); + + struct ptype2_opts ptype2_opts = cast_opts_as_ptype2_opts(p_opts); + + if (ord_ptype2_validate(x_levels, y_levels, &ptype2_opts)) { + return p_opts->x; + } else { + // FIXME: Call default cast method + stop_incompatible_type(p_opts->x, + p_opts->to, + p_opts->p_x_arg, + p_opts->p_to_arg, + true); + } } static SEXP fct_as_factor_impl(SEXP x, SEXP x_levels, SEXP to_levels, bool* lossy, bool ordered) { From 1bcdfd72a84c93faff34ad1d7da4e146023e18d7 Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Wed, 5 Oct 2022 14:48:37 +0200 Subject: [PATCH 145/312] Call `vec_default_cast()` from `ordered` method --- src/cast-dispatch.c | 4 ++-- src/cast.c | 56 +++++++++++++++++++++++++++++---------------- src/cast.h | 8 +++---- src/type-factor.c | 12 +++++----- 4 files changed, 48 insertions(+), 32 deletions(-) diff --git a/src/cast-dispatch.c b/src/cast-dispatch.c index 6e8f0969f..740d06442 100644 --- a/src/cast-dispatch.c +++ b/src/cast-dispatch.c @@ -106,8 +106,8 @@ r_obj* ffi_cast_dispatch_native(r_obj* x, if (lossy || out == r_null) { return vec_cast_default(x, to, - x_arg, - to_arg, + &c_x_arg, + &c_to_arg, c_opts.call, &c_opts.fallback); } else { diff --git a/src/cast.c b/src/cast.c index 6591b9986..e12630799 100644 --- a/src/cast.c +++ b/src/cast.c @@ -126,35 +126,47 @@ r_obj* vec_cast_switch_native(const struct cast_opts* opts, } -r_obj* vec_cast_default(r_obj* x, - r_obj* to, - r_obj* p_x_arg, - r_obj* p_to_arg, - struct r_lazy call, - const struct fallback_opts* opts) { +static inline +r_obj* vec_cast_default_full(r_obj* x, + r_obj* to, + struct vctrs_arg* p_x_arg, + struct vctrs_arg* p_to_arg, + struct r_lazy call, + const struct fallback_opts* opts, + bool from_dispatch) { r_obj* df_fallback = KEEP(r_int(opts->df)); r_obj* s3_fallback = KEEP(r_int(opts->s3)); + + r_obj* ffi_x_arg = KEEP(vctrs_arg(p_x_arg)); + r_obj* ffi_to_arg = KEEP(vctrs_arg(p_to_arg)); + r_obj* ffi_call = KEEP(r_lazy_eval(call)); r_obj* out = vctrs_eval_mask8(syms.vec_default_cast, syms_x, x, syms_to, to, - syms_x_arg, p_x_arg, - syms_to_arg, p_to_arg, + syms_x_arg, ffi_x_arg, + syms_to_arg, ffi_to_arg, syms_call, ffi_call, - syms_from_dispatch, r_true, + syms_from_dispatch, r_lgl(from_dispatch), syms_df_fallback, df_fallback, syms_s3_fallback, s3_fallback); - FREE(3); + FREE(5); return out; } +r_obj* vec_cast_default(r_obj* x, + r_obj* to, + struct vctrs_arg* p_x_arg, + struct vctrs_arg* p_to_arg, + struct r_lazy call, + const struct fallback_opts* p_opts) { + return vec_cast_default_full(x, to, p_x_arg, p_to_arg, call, p_opts, false); +} + static r_obj* vec_cast_dispatch_s3(const struct cast_opts* opts) { r_obj* x = opts->x; r_obj* to = opts->to; - r_obj* r_x_arg = KEEP(vctrs_arg(opts->p_x_arg)); - r_obj* r_to_arg = KEEP(vctrs_arg(opts->p_to_arg)); - r_obj* method_sym = r_null; r_obj* method = s3_find_method_xy("vec_cast", to, x, vctrs_method_table, &method_sym); @@ -182,16 +194,20 @@ r_obj* vec_cast_dispatch_s3(const struct cast_opts* opts) { KEEP(method); if (method == r_null) { - r_obj* out = vec_cast_default(x, - to, - r_x_arg, - r_to_arg, - opts->call, - &(opts->fallback)); - FREE(3); + r_obj* out = vec_cast_default_full(x, + to, + opts->p_x_arg, + opts->p_to_arg, + opts->call, + &(opts->fallback), + true); + FREE(1); return out; } + r_obj* r_x_arg = KEEP(vctrs_arg(opts->p_x_arg)); + r_obj* r_to_arg = KEEP(vctrs_arg(opts->p_to_arg)); + r_obj* out = vec_invoke_coerce_method(method_sym, method, syms_x, x, syms_to, to, diff --git a/src/cast.h b/src/cast.h index 7a1f350cf..861aa159b 100644 --- a/src/cast.h +++ b/src/cast.h @@ -99,11 +99,11 @@ r_obj* vec_cast_e(const struct cast_opts* opts, ERR* err); r_obj* vec_cast_default(r_obj* x, - r_obj* y, - r_obj* p_x_arg, - r_obj* p_to_arg, + r_obj* to, + struct vctrs_arg* p_x_arg, + struct vctrs_arg* p_to_arg, struct r_lazy call, - const struct fallback_opts* opts); + const struct fallback_opts* p_opts); #endif diff --git a/src/type-factor.c b/src/type-factor.c index a843d96f1..18a23ba09 100644 --- a/src/type-factor.c +++ b/src/type-factor.c @@ -265,12 +265,12 @@ SEXP ord_as_ordered(const struct cast_opts* p_opts) { if (ord_ptype2_validate(x_levels, y_levels, &ptype2_opts)) { return p_opts->x; } else { - // FIXME: Call default cast method - stop_incompatible_type(p_opts->x, - p_opts->to, - p_opts->p_x_arg, - p_opts->p_to_arg, - true); + return vec_cast_default(p_opts->x, + p_opts->to, + p_opts->p_x_arg, + p_opts->p_to_arg, + p_opts->call, + &p_opts->fallback); } } From 2ae89b86589b2aea9723fe8574173ec1acd910a0 Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Wed, 5 Oct 2022 11:52:25 +0200 Subject: [PATCH 146/312] Add restart for ptype2 errors --- NEWS.md | 4 +++ R/conditions.R | 1 + R/type2.R | 70 +++++++++++++++++++++++++++++++++---- tests/testthat/test-type2.R | 23 ++++++++++++ 4 files changed, 91 insertions(+), 7 deletions(-) diff --git a/NEWS.md b/NEWS.md index 14f390672..e76d6b8bf 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,5 +1,9 @@ # vctrs (development version) +* `vec_ptype2()` errors can now be restarted via + `"vctrs_restart_incompatible_type"`. The restart resumes execution + from `vec_default_ptype2()`. + * New `list_all_size()` and `list_check_all_size()` to quickly determine if a list contains elements of a particular `size` (#1582). diff --git a/R/conditions.R b/R/conditions.R index 107fcacae..1c8067c42 100644 --- a/R/conditions.R +++ b/R/conditions.R @@ -135,6 +135,7 @@ stop_incompatible_type <- function(x, x_arg = x_arg, y_arg = y_arg, details = details, + action = action, ..., message = message, class = c(class, "vctrs_error_incompatible_type"), diff --git a/R/type2.R b/R/type2.R index 28e9c5d74..43d724aa2 100644 --- a/R/type2.R +++ b/R/type2.R @@ -170,13 +170,18 @@ vec_default_ptype2 <- function(x, # dispatch mechanism, when no method is found to dispatch to. It # indicates whether the error message should provide advice about # diverging attributes. - stop_incompatible_type( - x, - y, - x_arg = x_arg, - y_arg = y_arg, - `vctrs:::from_dispatch` = match_from_dispatch(...), - call = call + withRestarts( + stop_incompatible_type( + x, + y, + x_arg = x_arg, + y_arg = y_arg, + `vctrs:::from_dispatch` = match_from_dispatch(...), + call = call + ), + vctrs_restart_incompatible_type = function(ptype) { + ptype + } ) } @@ -219,6 +224,14 @@ can_fall_back <- function(x, y) { has_no_proxy(x) && has_no_proxy(y) } has_no_proxy <- function(x) { + if (inherits(x, "vctrs:::common_class_fallback")) { + return(TRUE) + } + + if (!is_null(s3_get_method(class(x)[[1]], "vec_proxy", ns = "vctrs"))) { + return(FALSE) + } + proxy <- vec_proxy(x) # Don't compare data for performance @@ -409,3 +422,46 @@ vec_is_subtype <- function(x, super, ..., x_arg = "", super_arg = "") { vec_implements_ptype2 <- function(x) { .Call(vctrs_implements_ptype2, x) } + +# Example usage of ptype2 restart. As there is no cast restart (yet), +# it requires `x` and `y` to be convertible to the restarted ptype. +with_ordered_restart <- function(expr) { + withCallingHandlers( + expr, + vctrs_error_incompatible_type = function(cnd) { + # Don't handle cast errors + if (is_string(cnd[["action"]], "convert")) { + return(zap()) + } + + x <- cnd[["x"]] + y <- cnd[["y"]] + + restart <- FALSE + + if (is.ordered(x)) { + restart <- TRUE + x <- as.character(x) + } + if (is.ordered(y)) { + restart <- TRUE + y <- as.character(y) + } + + # Don't recurse and let ptype2 error keep its course + if (!restart) { + return(zap()) + } + + # Recurse with character methods and restart with the result + ptype <- vec_ptype2(x, y) + maybe_restart("vctrs_restart_incompatible_type", ptype) + } + ) +} + +maybe_restart <- function(restart, ...) { + if (!is_null(findRestart(restart))) { + invokeRestart(restart, ...) + } +} diff --git a/tests/testthat/test-type2.R b/tests/testthat/test-type2.R index 68f2a285c..56e737413 100644 --- a/tests/testthat/test-type2.R +++ b/tests/testthat/test-type2.R @@ -344,3 +344,26 @@ test_that("vec_ptype2() evaluates x_arg and y_arg lazily", { expect_silent(vec_ptype2(1L, 1L, x_arg = print("oof"))) expect_silent(vec_ptype2(1L, 1L, y_arg = print("oof"))) }) + +test_that("can restart ptype2 errors", { + x <- data_frame(x = ordered(c("a", "b", "c"))) + y <- data_frame(x = ordered(c("A", "B", "C"))) + + expect_equal( + with_ordered_restart(vec_rbind(x, y)), + data_frame(x = c("a", "b", "c", "A", "B", "C")) + ) + + expect_equal( + with_ordered_restart(vec_ptype_common(x, y)), + data_frame(x = chr()) + ) + + expect_equal( + with_ordered_restart(vec_cast_common(x, y)), + list( + data_frame(x = c("a", "b", "c")), + data_frame(x = c("A", "B", "C")) + ) + ) +}) From 5c6ad40016b67f0d02c76fcbbad6fa9b8508bfba Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Wed, 5 Oct 2022 13:34:31 +0200 Subject: [PATCH 147/312] Add specific classes for ptype2 and cast errors --- NEWS.md | 7 +++++- R/conditions.R | 9 ++++++-- R/type2.R | 11 +++------- tests/testthat/_snaps/assert.md | 2 +- tests/testthat/_snaps/bind.md | 10 ++++----- tests/testthat/_snaps/c.md | 16 +++++++------- tests/testthat/_snaps/cast.md | 2 +- tests/testthat/_snaps/conditions.md | 2 +- tests/testthat/_snaps/dictionary.md | 8 +++---- tests/testthat/_snaps/error-call.md | 24 ++++++++++---------- tests/testthat/_snaps/interval.md | 4 ++-- tests/testthat/_snaps/rep.md | 4 ++-- tests/testthat/_snaps/shape.md | 6 ++--- tests/testthat/_snaps/slice-assign.md | 2 +- tests/testthat/_snaps/slice-chop.md | 28 ++++++++++++------------ tests/testthat/_snaps/type-asis.md | 4 ++-- tests/testthat/_snaps/type-data-frame.md | 4 ++-- tests/testthat/_snaps/type-list-of.md | 4 ++-- tests/testthat/_snaps/type-table.md | 2 +- tests/testthat/_snaps/type-tibble.md | 6 ++--- tests/testthat/_snaps/type2.md | 14 ++++++------ 21 files changed, 87 insertions(+), 82 deletions(-) diff --git a/NEWS.md b/NEWS.md index e76d6b8bf..5b747a862 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,7 +1,12 @@ # vctrs (development version) +* Common type and cast errors now inherit from `"vctrs_error_ptype2"` + and `"vctrs_error_cast"` respectively. They are still both + subclasses from `"vctrs_error_incompatible_type"` (which used to be + their most specific class and is now a parent class). + * `vec_ptype2()` errors can now be restarted via - `"vctrs_restart_incompatible_type"`. The restart resumes execution + `"vctrs_restart_ptype2"`. The restart resumes execution from `vec_default_ptype2()`. * New `list_all_size()` and `list_check_all_size()` to quickly determine if a diff --git a/R/conditions.R b/R/conditions.R index 1c8067c42..848016e11 100644 --- a/R/conditions.R +++ b/R/conditions.R @@ -130,15 +130,20 @@ stop_incompatible_type <- function(x, from_dispatch = match_from_dispatch(...) ) + subclass <- switch( + action, + combine = "vctrs_error_ptype2", + convert = "vctrs_error_cast" + ) + stop_incompatible( x, y, x_arg = x_arg, y_arg = y_arg, details = details, - action = action, ..., message = message, - class = c(class, "vctrs_error_incompatible_type"), + class = c(class, subclass, "vctrs_error_incompatible_type"), call = call ) } diff --git a/R/type2.R b/R/type2.R index 43d724aa2..b0914907c 100644 --- a/R/type2.R +++ b/R/type2.R @@ -179,7 +179,7 @@ vec_default_ptype2 <- function(x, `vctrs:::from_dispatch` = match_from_dispatch(...), call = call ), - vctrs_restart_incompatible_type = function(ptype) { + vctrs_restart_ptype2 = function(ptype) { ptype } ) @@ -428,12 +428,7 @@ vec_implements_ptype2 <- function(x) { with_ordered_restart <- function(expr) { withCallingHandlers( expr, - vctrs_error_incompatible_type = function(cnd) { - # Don't handle cast errors - if (is_string(cnd[["action"]], "convert")) { - return(zap()) - } - + vctrs_error_ptype2 = function(cnd) { x <- cnd[["x"]] y <- cnd[["y"]] @@ -455,7 +450,7 @@ with_ordered_restart <- function(expr) { # Recurse with character methods and restart with the result ptype <- vec_ptype2(x, y) - maybe_restart("vctrs_restart_incompatible_type", ptype) + maybe_restart("vctrs_restart_ptype2", ptype) } ) } diff --git a/tests/testthat/_snaps/assert.md b/tests/testthat/_snaps/assert.md index 185ed5156..8f4542bcb 100644 --- a/tests/testthat/_snaps/assert.md +++ b/tests/testthat/_snaps/assert.md @@ -184,7 +184,7 @@ Code (expect_error(vec_assert(1, size = "x"))) Output - + Error in `vec_assert()`: ! Can't convert `size` to . diff --git a/tests/testthat/_snaps/bind.md b/tests/testthat/_snaps/bind.md index c0bce8b5d..5ed40ae23 100644 --- a/tests/testthat/_snaps/bind.md +++ b/tests/testthat/_snaps/bind.md @@ -3,21 +3,21 @@ Code (expect_error(vec_rbind(x_int, x_chr), class = "vctrs_error_incompatible_type")) Output - + Error in `vec_rbind()`: ! Can't combine `..1$x` and `..2$x` . Code (expect_error(vec_rbind(x_int, x_chr, .error_call = call("foo")), class = "vctrs_error_incompatible_type") ) Output - + Error in `foo()`: ! Can't combine `..1$x` and `..2$x` . Code (expect_error(vec_rbind(x_int, x_chr, .ptype = x_chr, .error_call = call("foo")), class = "vctrs_error_incompatible_type")) Output - + Error in `foo()`: ! Can't convert `..1$x` to match type of `x` . @@ -383,7 +383,7 @@ (expect_error(vec_rbind(set_names(x, "x"), set_names(y, "x")), class = "vctrs_error_incompatible_type") ) Output - + Error in `vec_rbind()`: ! Can't combine `..1` and `..2` . x Some attributes are incompatible. @@ -398,7 +398,7 @@ (expect_error(vec_rbind(set_names(joe, "x"), set_names(jane, "y")), class = "vctrs_error_incompatible_type") ) Output - + Error in `vec_rbind()`: ! Can't combine `..1` and `..2` . diff --git a/tests/testthat/_snaps/c.md b/tests/testthat/_snaps/c.md index e40632580..4139d8424 100644 --- a/tests/testthat/_snaps/c.md +++ b/tests/testthat/_snaps/c.md @@ -19,13 +19,13 @@ Code (expect_error(vec_c(1, a = "x", 2))) Output - + Error in `vec_c()`: ! Can't combine `..1` and `a` . Code (expect_error(vec_c(1, a = "x", 2, .ptype = double(), .error_arg = "arg"))) Output - + Error in `vec_c()`: ! Can't convert `arg$a` to . Code @@ -73,7 +73,7 @@ y <- structure(foobar(2), attr_bar = "bar") (expect_error(vec_c(x, y), class = "vctrs_error_incompatible_type")) Output - + Error in `vec_c()`: ! Can't combine `..1` and `..2` . x Some attributes are incompatible. @@ -83,7 +83,7 @@ (expect_error(vec_c(x, y, .error_call = call("foo"), .error_arg = "arg"), class = "vctrs_error_incompatible_type")) Output - + Error in `foo()`: ! Can't combine `arg[[1]]` and `arg[[2]]` . x Some attributes are incompatible. @@ -97,7 +97,7 @@ jane <- .Counts(3L, name = "Jane") (expect_error(vec_c(joe, jane), class = "vctrs_error_incompatible_type")) Output - + Error in `vec_c()`: ! Can't combine `..1` and `..2` . x Some attributes are incompatible. @@ -107,7 +107,7 @@ (expect_error(vec_c(joe, jane, .error_call = call("foo"), .error_arg = "arg"), class = "vctrs_error_incompatible_type")) Output - + Error in `foo()`: ! Can't combine `arg[[1]]` and `arg[[2]]` . x Some attributes are incompatible. @@ -129,7 +129,7 @@ (expect_error(with_c_foobar(vec_c(foobar(1), foobar(2), .ptype = "")), class = "vctrs_error_incompatible_type") ) Output - + Error in `vec_c()`: ! Can't convert `..1` to . Code @@ -148,7 +148,7 @@ (expect_error(vec_c(a = c(b = letters), b = 1, .name_spec = zap()), class = "vctrs_error_incompatible_type") ) Output - + Error in `vec_c()`: ! Can't combine `a` and `b` . diff --git a/tests/testthat/_snaps/cast.md b/tests/testthat/_snaps/cast.md index 6844182b4..d77ca4507 100644 --- a/tests/testthat/_snaps/cast.md +++ b/tests/testthat/_snaps/cast.md @@ -68,7 +68,7 @@ (expect_error(vec_cast(foobar(mtcars), 1), class = "vctrs_error_incompatible_type") ) Output - + Error: ! Can't convert `foobar(mtcars)` to . diff --git a/tests/testthat/_snaps/conditions.md b/tests/testthat/_snaps/conditions.md index 3a6e2b713..921b36990 100644 --- a/tests/testthat/_snaps/conditions.md +++ b/tests/testthat/_snaps/conditions.md @@ -163,7 +163,7 @@ (expect_error(vec_cast(ordered("x"), ordered("y")), class = "vctrs_error_incompatible_type") ) Output - + Error: ! Can't convert `ordered("x")` > to >. diff --git a/tests/testthat/_snaps/dictionary.md b/tests/testthat/_snaps/dictionary.md index e647b02a6..34682f121 100644 --- a/tests/testthat/_snaps/dictionary.md +++ b/tests/testthat/_snaps/dictionary.md @@ -5,27 +5,27 @@ df2 <- data_frame(x = data_frame(foo = "")) (expect_error(vec_match(df1, df2), class = "vctrs_error_incompatible_type")) Output - + Error in `vec_match()`: ! Can't combine `x$foo` and `x$foo` . Code (expect_error(vec_match(df1, df2, needles_arg = "n", haystack_arg = "h"), class = "vctrs_error_incompatible_type")) Output - + Error in `vec_match()`: ! Can't combine `n$x$foo` and `h$x$foo` . Code (expect_error(vec_in(df1, df2), class = "vctrs_error_incompatible_type")) Output - + Error in `vec_in()`: ! Can't combine `x$foo` and `x$foo` . Code (expect_error(vec_in(df1, df2, needles_arg = "n", haystack_arg = "h"), class = "vctrs_error_incompatible_type") ) Output - + Error in `vec_in()`: ! Can't combine `n$x$foo` and `h$x$foo` . diff --git a/tests/testthat/_snaps/error-call.md b/tests/testthat/_snaps/error-call.md index efa833e17..52b1f1a8a 100644 --- a/tests/testthat/_snaps/error-call.md +++ b/tests/testthat/_snaps/error-call.md @@ -3,7 +3,7 @@ Code (expect_error(my_function())) Output - + Error in `my_function()`: ! Can't combine `2` and `chr()` . @@ -12,7 +12,7 @@ Code (expect_error(my_function())) Output - + Error in `my_function()`: ! Can't convert `2` to . @@ -21,7 +21,7 @@ Code (expect_error(my_function(df1, df2))) Output - + Error in `my_function()`: ! Can't convert `lhs$y` to match type of `y` . @@ -30,7 +30,7 @@ Code (expect_error(my_function(df1, df2))) Output - + Error in `my_function()`: ! Can't convert `lhs$y` to match type of `y` . @@ -143,7 +143,7 @@ Code (expect_error(my_function())) Output - + Error in `my_function()`: ! Can't convert `matrix(TRUE)` to . Can't decrease dimensionality from 2 to 1. @@ -295,7 +295,7 @@ Code (expect_error(vec_cast(1, list()))) Output - + Error in `foo()`: ! Can't convert `1` to . Code @@ -392,7 +392,7 @@ Code (expect_error(my_function(this_arg = 1, that_arg = "foo", .arg = "my_arg"))) Output - + Error in `my_function()`: ! Can't combine `my_arg$this_arg` and `my_arg$that_arg` . @@ -401,7 +401,7 @@ Code (expect_error(my_function(1, "foo", .arg = "my_arg"))) Output - + Error in `my_function()`: ! Can't combine `my_arg[[1]]` and `my_arg[[2]]` . @@ -410,7 +410,7 @@ Code (expect_error(my_function(this_arg = x, that_arg = y))) Output - + Error in `my_function()`: ! Can't combine `this_arg$x` and `that_arg$x` . @@ -419,7 +419,7 @@ Code (expect_error(my_function(this_arg = 1, that_arg = "foo"))) Output - + Error in `my_function()`: ! Can't combine `this_arg` and `that_arg` . @@ -428,7 +428,7 @@ Code (expect_error(my_function(this_arg = 1, that_arg = "foo", .arg = "my_arg"))) Output - + Error in `my_function()`: ! Can't combine `my_arg$this_arg` and `my_arg$that_arg` . @@ -437,7 +437,7 @@ Code (expect_error(my_function(1, "foo", .arg = "my_arg"))) Output - + Error in `my_function()`: ! Can't combine `my_arg[[1]]` and `my_arg[[2]]` . diff --git a/tests/testthat/_snaps/interval.md b/tests/testthat/_snaps/interval.md index e1531c989..ee1460cc7 100644 --- a/tests/testthat/_snaps/interval.md +++ b/tests/testthat/_snaps/interval.md @@ -21,7 +21,7 @@ Code (expect_error(vec_interval_locate_groups(1, "x"))) Output - + Error: ! Can't combine `start` and `end` . @@ -30,7 +30,7 @@ Code (expect_error(vec_interval_locate_containers(1, "x"))) Output - + Error: ! Can't combine `start` and `end` . diff --git a/tests/testthat/_snaps/rep.md b/tests/testthat/_snaps/rep.md index 26ff74c4d..2996685c2 100644 --- a/tests/testthat/_snaps/rep.md +++ b/tests/testthat/_snaps/rep.md @@ -3,7 +3,7 @@ Code (expect_error(my_vec_rep(1, "x"), class = "vctrs_error_incompatible_type")) Output - + Error in `my_vec_rep()`: ! Can't convert `my_times` to . Code @@ -62,7 +62,7 @@ Code (expect_error(my_vec_rep_each(1, "x"), class = "vctrs_error_incompatible_type")) Output - + Error in `my_vec_rep_each()`: ! Can't convert `my_times` to . Code diff --git a/tests/testthat/_snaps/shape.md b/tests/testthat/_snaps/shape.md index 2eb381093..69ecfcdca 100644 --- a/tests/testthat/_snaps/shape.md +++ b/tests/testthat/_snaps/shape.md @@ -4,7 +4,7 @@ (expect_error(vec_shape2(shaped_int(1, 0, 5), shaped_int(1, 5, 1)), class = "vctrs_error_incompatible_type") ) Output - + Error: ! Can't combine and . x Incompatible sizes 0 and 5 along axis 2. @@ -12,7 +12,7 @@ (expect_error(vec_shape2(shaped_int(1, 5, 0), shaped_int(1, 1, 5)), class = "vctrs_error_incompatible_type") ) Output - + Error: ! Can't combine and . x Incompatible sizes 0 and 5 along axis 3. @@ -23,7 +23,7 @@ (expect_error(vec_shape2(shaped_int(1, 0, 5), shaped_int(1, 5, 1), x_arg = "foo", y_arg = "bar"), class = "vctrs_error_incompatible_type")) Output - + Error: ! Can't combine `foo` and `bar` . x Incompatible sizes 0 and 5 along axis 2. diff --git a/tests/testthat/_snaps/slice-assign.md b/tests/testthat/_snaps/slice-assign.md index 462d1730c..5c9997a6d 100644 --- a/tests/testthat/_snaps/slice-assign.md +++ b/tests/testthat/_snaps/slice-assign.md @@ -93,7 +93,7 @@ (expect_error(vec_assign(1:2, 1L, "x", x_arg = "foo", value_arg = "bar"), class = "vctrs_error_incompatible_type")) Output - + Error in `vec_assign()`: ! Can't convert `bar` to match type of `foo` . Code diff --git a/tests/testthat/_snaps/slice-chop.md b/tests/testthat/_snaps/slice-chop.md index 2aa84837c..5d929a14f 100644 --- a/tests/testthat/_snaps/slice-chop.md +++ b/tests/testthat/_snaps/slice-chop.md @@ -68,14 +68,14 @@ (expect_error(list_unchop(x, indices = indices), class = "vctrs_error_incompatible_type") ) Output - + Error in `list_unchop()`: ! Can't combine `x[[1]]` and `x[[2]]` . Code (expect_error(list_unchop(x, indices = indices, error_call = call("foo"), error_arg = "arg"), class = "vctrs_error_incompatible_type")) Output - + Error in `foo()`: ! Can't combine `arg[[1]]` and `arg[[2]]` . @@ -85,25 +85,25 @@ x <- list(1, a = "x", 2) (expect_error(list_unchop(x))) Output - + Error in `list_unchop()`: ! Can't combine `x[[1]]` and `x$a` . Code (expect_error(list_unchop(x, indices = list(2, 1, 3)))) Output - + Error in `list_unchop()`: ! Can't combine `x[[1]]` and `x$a` . Code (expect_error(list_unchop(x, ptype = double()))) Output - + Error in `list_unchop()`: ! Can't convert `x$a` to . Code (expect_error(list_unchop(x, indices = list(2, 1, 3), ptype = double()))) Output - + Error in `list_unchop()`: ! Can't convert `x$a` to . Code @@ -177,7 +177,7 @@ y <- structure(foobar(2), attr_bar = "bar") (expect_error(list_unchop(list(x, y)), class = "vctrs_error_incompatible_type")) Output - + Error in `list_unchop()`: ! Can't combine `x[[1]]` and `x[[2]]` . x Some attributes are incompatible. @@ -187,7 +187,7 @@ (expect_error(list_unchop(list(x, y), error_call = call("foo"), error_arg = "arg"), class = "vctrs_error_incompatible_type")) Output - + Error in `foo()`: ! Can't combine `arg[[1]]` and `arg[[2]]` . x Some attributes are incompatible. @@ -202,7 +202,7 @@ (expect_error(list_unchop(list(joe, jane)), class = "vctrs_error_incompatible_type") ) Output - + Error in `list_unchop()`: ! Can't combine `x[[1]]` and `x[[2]]` . x Some attributes are incompatible. @@ -212,7 +212,7 @@ (expect_error(list_unchop(list(joe, jane), error_call = call("foo"), error_arg = "arg"), class = "vctrs_error_incompatible_type")) Output - + Error in `foo()`: ! Can't combine `arg[[1]]` and `arg[[2]]` . x Some attributes are incompatible. @@ -255,7 +255,7 @@ (expect_error(list_unchop(list(joe, 1, jane), indices = list(c(1, 2), 3, 4)), class = "vctrs_error_incompatible_type")) Output - + Error in `list_unchop()`: ! Can't combine `x[[1]]` and `x[[2]]` . @@ -286,7 +286,7 @@ (expect_error(with_c_foobar(list_unchop(x, ptype = "")), class = "vctrs_error_incompatible_type") ) Output - + Error in `list_unchop()`: ! Can't convert `x[[1]]` to . @@ -335,7 +335,7 @@ (expect_error(list_unchop(x, name_spec = zap()), class = "vctrs_error_incompatible_type") ) Output - + Error in `list_unchop()`: ! Can't combine `x$a` and `x$b` . Code @@ -343,7 +343,7 @@ (expect_error(list_unchop(x, indices = list(2:1, 3), name_spec = zap()), class = "vctrs_error_incompatible_type") ) Output - + Error in `list_unchop()`: ! Can't combine `x$a` and `x$b` . diff --git a/tests/testthat/_snaps/type-asis.md b/tests/testthat/_snaps/type-asis.md index 792ece922..f19c2990c 100644 --- a/tests/testthat/_snaps/type-asis.md +++ b/tests/testthat/_snaps/type-asis.md @@ -4,7 +4,7 @@ (expect_error(vec_ptype2(I(1), I("x")), class = "vctrs_error_incompatible_type") ) Output - + Error: ! Can't combine `I(1)` and `I("x")` . @@ -14,7 +14,7 @@ (expect_error(vec_cast(I(1), I(factor("x"))), class = "vctrs_error_incompatible_type") ) Output - + Error: ! Can't convert `I(1)` to >. diff --git a/tests/testthat/_snaps/type-data-frame.md b/tests/testthat/_snaps/type-data-frame.md index 4452a6421..a11a312f5 100644 --- a/tests/testthat/_snaps/type-data-frame.md +++ b/tests/testthat/_snaps/type-data-frame.md @@ -250,13 +250,13 @@ local_error_call(call("my_function")) (expect_error(vec_ptype2(df1, df3), class = "vctrs_error_incompatible_type")) Output - + Error in `my_function()`: ! Can't combine `x` and `x` . Code (expect_error(vec_ptype2(df3, df1), class = "vctrs_error_incompatible_type")) Output - + Error in `my_function()`: ! Can't combine `x` and `x` . diff --git a/tests/testthat/_snaps/type-list-of.md b/tests/testthat/_snaps/type-list-of.md index f7c9b4003..3076afd05 100644 --- a/tests/testthat/_snaps/type-list-of.md +++ b/tests/testthat/_snaps/type-list-of.md @@ -82,13 +82,13 @@ Code (expect_error(fn1())) Output - + Error in `fn1()`: ! Can't convert `..1` to . Code (expect_error(fn2())) Output - + Error in `fn2()`: ! Can't convert `..1` to . diff --git a/tests/testthat/_snaps/type-table.md b/tests/testthat/_snaps/type-table.md index 80272e206..b3c553709 100644 --- a/tests/testthat/_snaps/type-table.md +++ b/tests/testthat/_snaps/type-table.md @@ -3,7 +3,7 @@ Code (expect_error(vec_cast(x, y), class = "vctrs_error_incompatible_type")) Output - + Error: ! Can't convert `x` to . Can't decrease dimensionality from 3 to 2. diff --git a/tests/testthat/_snaps/type-tibble.md b/tests/testthat/_snaps/type-tibble.md index 49b8607b7..1b3786edb 100644 --- a/tests/testthat/_snaps/type-tibble.md +++ b/tests/testthat/_snaps/type-tibble.md @@ -4,19 +4,19 @@ local_error_call(call("my_function")) (expect_error(vec_ptype2(v, dt), class = "vctrs_error_incompatible_type")) Output - + Error in `my_function()`: ! Can't combine `v` and `dt` . Code (expect_error(vec_ptype2(dt, v), class = "vctrs_error_incompatible_type")) Output - + Error in `my_function()`: ! Can't combine `dt` and `v` . Code (expect_error(vec_cast(v, dt), class = "vctrs_error_incompatible_type")) Output - + Error in `my_function()`: ! Can't convert `v` to . diff --git a/tests/testthat/_snaps/type2.md b/tests/testthat/_snaps/type2.md index 055fbb5ae..8c748d9a9 100644 --- a/tests/testthat/_snaps/type2.md +++ b/tests/testthat/_snaps/type2.md @@ -69,7 +69,7 @@ (expect_error(vec_cast(foobar(1, bar = TRUE), foobar(2, baz = TRUE)), class = "vctrs_error_incompatible_type") ) Output - + Error: ! Can't convert `foobar(1, bar = TRUE)` to . x Some attributes are incompatible. @@ -79,7 +79,7 @@ (expect_error(vec_ptype2(foobar(1, bar = TRUE), foobar(2, baz = TRUE)), class = "vctrs_error_incompatible_type") ) Output - + Error: ! Can't combine `foobar(1, bar = TRUE)` and `foobar(2, baz = TRUE)` . x Some attributes are incompatible. @@ -102,14 +102,14 @@ (expect_error(with_foobar_cast(vec_cast(foobar(1, bar = TRUE), foobar(2, baz = TRUE))), class = "vctrs_error_incompatible_type")) Output - + Error: ! Can't convert `foobar(1, bar = TRUE)` to . Code (expect_error(with_foobar_ptype2(vec_ptype2(foobar(1, bar = TRUE), foobar(2, baz = TRUE))), class = "vctrs_error_incompatible_type")) Output - + Error: ! Can't combine `foobar(1, bar = TRUE)` and `foobar(2, baz = TRUE)` . @@ -122,7 +122,7 @@ (expect_error(vec_cast_no_fallback(foo, bar), class = "vctrs_error_incompatible_type") ) Output - + Error in `vec_cast_no_fallback()`: ! Can't convert `x` to . @@ -153,7 +153,7 @@ (expect_error(vec_ptype2_no_fallback(foobar(mtcars), foobaz(mtcars)), class = "vctrs_error_incompatible_type") ) Output - + Error: ! Can't combine and . @@ -173,7 +173,7 @@ Code (expect_error(vec_ptype2_no_fallback(foobar(mtcars), foobaz(mtcars)))) Output - + Error: ! Can't combine and . From 10a8659a32353c43e4cbc0ee648dfb6156388bae Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Fri, 7 Oct 2022 09:27:19 +0200 Subject: [PATCH 148/312] Don't mention restart in NEWS --- NEWS.md | 4 ---- 1 file changed, 4 deletions(-) diff --git a/NEWS.md b/NEWS.md index 5b747a862..7445d909f 100644 --- a/NEWS.md +++ b/NEWS.md @@ -5,10 +5,6 @@ subclasses from `"vctrs_error_incompatible_type"` (which used to be their most specific class and is now a parent class). -* `vec_ptype2()` errors can now be restarted via - `"vctrs_restart_ptype2"`. The restart resumes execution - from `vec_default_ptype2()`. - * New `list_all_size()` and `list_check_all_size()` to quickly determine if a list contains elements of a particular `size` (#1582). From 4c3381a05c40bc0b0cfc6bf46a93efb817f0d390 Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Fri, 7 Oct 2022 09:31:02 +0200 Subject: [PATCH 149/312] Inline `try_restart()` --- R/type2.R | 15 ++++++++------- 1 file changed, 8 insertions(+), 7 deletions(-) diff --git a/R/type2.R b/R/type2.R index b0914907c..c58af9eb5 100644 --- a/R/type2.R +++ b/R/type2.R @@ -450,13 +450,14 @@ with_ordered_restart <- function(expr) { # Recurse with character methods and restart with the result ptype <- vec_ptype2(x, y) - maybe_restart("vctrs_restart_ptype2", ptype) + + # Old-R compat for `tryInvokeRestart()` + try_restart <- function(restart, ...) { + if (!is_null(findRestart(restart))) { + invokeRestart(restart, ...) + } + } + try_restart("vctrs_restart_ptype2", ptype) } ) } - -maybe_restart <- function(restart, ...) { - if (!is_null(findRestart(restart))) { - invokeRestart(restart, ...) - } -} From 014fcce6e854f038bdadb837fb6c79a5cc3a388b Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Fri, 7 Oct 2022 09:54:02 +0200 Subject: [PATCH 150/312] Add cast restart And use it to return factors from ordered retry handler --- R/cast.R | 19 ++++++++++++------- R/conditions.R | 13 ++++++++++--- R/type2.R | 25 ++++++++++++++++++++----- tests/testthat/test-type2.R | 23 +++++++++++++++++++++-- 4 files changed, 63 insertions(+), 17 deletions(-) diff --git a/R/cast.R b/R/cast.R index 0d38460e0..34d11d90a 100644 --- a/R/cast.R +++ b/R/cast.R @@ -227,13 +227,18 @@ vec_default_cast <- function(x, return(out) } - stop_incompatible_cast( - x, - to, - x_arg = x_arg, - to_arg = to_arg, - `vctrs:::from_dispatch` = match_from_dispatch(...), - call = call + withRestarts( + stop_incompatible_cast( + x, + to, + x_arg = x_arg, + to_arg = to_arg, + `vctrs:::from_dispatch` = match_from_dispatch(...), + call = call + ), + vctrs_restart_cast = function(out) { + out + } ) } diff --git a/R/conditions.R b/R/conditions.R index 848016e11..ce830c87b 100644 --- a/R/conditions.R +++ b/R/conditions.R @@ -130,10 +130,16 @@ stop_incompatible_type <- function(x, from_dispatch = match_from_dispatch(...) ) - subclass <- switch( + switch( action, - combine = "vctrs_error_ptype2", - convert = "vctrs_error_cast" + combine = { + type <- "ptype2" + subclass <- "vctrs_error_ptype2" + }, + convert = { + type <- "cast" + subclass <- "vctrs_error_cast" + } ) stop_incompatible( @@ -141,6 +147,7 @@ stop_incompatible_type <- function(x, x_arg = x_arg, y_arg = y_arg, details = details, + type = type, ..., message = message, class = c(class, subclass, "vctrs_error_incompatible_type"), diff --git a/R/type2.R b/R/type2.R index c58af9eb5..c556e5ffd 100644 --- a/R/type2.R +++ b/R/type2.R @@ -428,7 +428,7 @@ vec_implements_ptype2 <- function(x) { with_ordered_restart <- function(expr) { withCallingHandlers( expr, - vctrs_error_ptype2 = function(cnd) { + vctrs_error_incompatible_type = function(cnd) { x <- cnd[["x"]] y <- cnd[["y"]] @@ -436,11 +436,11 @@ with_ordered_restart <- function(expr) { if (is.ordered(x)) { restart <- TRUE - x <- as.character(x) + x <- factor(as.character(x), levels = levels(x)) } if (is.ordered(y)) { restart <- TRUE - y <- as.character(y) + y <- factor(as.character(y), levels = levels(y)) } # Don't recurse and let ptype2 error keep its course @@ -448,8 +448,23 @@ with_ordered_restart <- function(expr) { return(zap()) } + x_arg <- cnd[["x_arg"]] + y_arg <- cnd[["y_arg"]] + call <- cnd[["call"]] + # Recurse with character methods and restart with the result - ptype <- vec_ptype2(x, y) + switch( + cnd[["type"]], + ptype2 = { + out <- vec_ptype2(x, y, x_arg = x_arg, y_arg = y_arg, call = call) + restart <- "vctrs_restart_ptype2" + }, + cast = { + out <- vec_cast(x, y, x_arg = x_arg, to_arg = y_arg, call = call) + restart <- "vctrs_restart_cast" + }, + abort("Unexpected incompatible-type field.", .internal = TRUE) + ) # Old-R compat for `tryInvokeRestart()` try_restart <- function(restart, ...) { @@ -457,7 +472,7 @@ with_ordered_restart <- function(expr) { invokeRestart(restart, ...) } } - try_restart("vctrs_restart_ptype2", ptype) + try_restart(restart, out) } ) } diff --git a/tests/testthat/test-type2.R b/tests/testthat/test-type2.R index 56e737413..2e1779a08 100644 --- a/tests/testthat/test-type2.R +++ b/tests/testthat/test-type2.R @@ -349,21 +349,40 @@ test_that("can restart ptype2 errors", { x <- data_frame(x = ordered(c("a", "b", "c"))) y <- data_frame(x = ordered(c("A", "B", "C"))) + exp <- c("a", "b", "c", "A", "B", "C") + exp <- factor(exp, exp) + + expect_error(vec_rbind(x, y), class = "vctrs_error_incompatible_type") + expect_equal( with_ordered_restart(vec_rbind(x, y)), - data_frame(x = c("a", "b", "c", "A", "B", "C")) + data_frame(x = exp) ) + z <- data_frame(x = chr()) + expect_equal( with_ordered_restart(vec_ptype_common(x, y)), + data_frame(x = exp[0]) + ) + expect_equal( + with_ordered_restart(vec_ptype_common(x, y, z)), data_frame(x = chr()) ) expect_equal( with_ordered_restart(vec_cast_common(x, y)), + list( + data_frame(x = factor(c("a", "b", "c"), levels(exp))), + data_frame(x = factor(c("A", "B", "C"), levels(exp))) + ) + ) + expect_equal( + with_ordered_restart(vec_cast_common(x, y, z)), list( data_frame(x = c("a", "b", "c")), - data_frame(x = c("A", "B", "C")) + data_frame(x = c("A", "B", "C")), + data_frame(x = chr()) ) ) }) From df11b0a5e629f2f7bb09fda8e6efa9d39f5303a3 Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Fri, 7 Oct 2022 09:55:46 +0200 Subject: [PATCH 151/312] Move `with_ordered_restart()` to helper file --- R/type2.R | 54 -------------------------------- tests/testthat/helper-restart.R | 55 +++++++++++++++++++++++++++++++++ 2 files changed, 55 insertions(+), 54 deletions(-) create mode 100644 tests/testthat/helper-restart.R diff --git a/R/type2.R b/R/type2.R index c556e5ffd..69a01d307 100644 --- a/R/type2.R +++ b/R/type2.R @@ -422,57 +422,3 @@ vec_is_subtype <- function(x, super, ..., x_arg = "", super_arg = "") { vec_implements_ptype2 <- function(x) { .Call(vctrs_implements_ptype2, x) } - -# Example usage of ptype2 restart. As there is no cast restart (yet), -# it requires `x` and `y` to be convertible to the restarted ptype. -with_ordered_restart <- function(expr) { - withCallingHandlers( - expr, - vctrs_error_incompatible_type = function(cnd) { - x <- cnd[["x"]] - y <- cnd[["y"]] - - restart <- FALSE - - if (is.ordered(x)) { - restart <- TRUE - x <- factor(as.character(x), levels = levels(x)) - } - if (is.ordered(y)) { - restart <- TRUE - y <- factor(as.character(y), levels = levels(y)) - } - - # Don't recurse and let ptype2 error keep its course - if (!restart) { - return(zap()) - } - - x_arg <- cnd[["x_arg"]] - y_arg <- cnd[["y_arg"]] - call <- cnd[["call"]] - - # Recurse with character methods and restart with the result - switch( - cnd[["type"]], - ptype2 = { - out <- vec_ptype2(x, y, x_arg = x_arg, y_arg = y_arg, call = call) - restart <- "vctrs_restart_ptype2" - }, - cast = { - out <- vec_cast(x, y, x_arg = x_arg, to_arg = y_arg, call = call) - restart <- "vctrs_restart_cast" - }, - abort("Unexpected incompatible-type field.", .internal = TRUE) - ) - - # Old-R compat for `tryInvokeRestart()` - try_restart <- function(restart, ...) { - if (!is_null(findRestart(restart))) { - invokeRestart(restart, ...) - } - } - try_restart(restart, out) - } - ) -} diff --git a/tests/testthat/helper-restart.R b/tests/testthat/helper-restart.R new file mode 100644 index 000000000..7eae97464 --- /dev/null +++ b/tests/testthat/helper-restart.R @@ -0,0 +1,55 @@ +# Example usage of ptype2 and cast restart. This handler treats any +# input that inherits from as a . In other words, it +# allows incompatible inputs to benefit from all +# coercion methods. +with_ordered_restart <- function(expr) { + withCallingHandlers( + expr, + vctrs_error_incompatible_type = function(cnd) { + x <- cnd[["x"]] + y <- cnd[["y"]] + + restart <- FALSE + + if (is.ordered(x)) { + restart <- TRUE + x <- factor(as.character(x), levels = levels(x)) + } + if (is.ordered(y)) { + restart <- TRUE + y <- factor(as.character(y), levels = levels(y)) + } + + # Don't recurse and let ptype2 error keep its course + if (!restart) { + return(zap()) + } + + x_arg <- cnd[["x_arg"]] + y_arg <- cnd[["y_arg"]] + call <- cnd[["call"]] + + # Recurse with character methods and restart with the result + switch( + cnd[["type"]], + ptype2 = { + out <- vec_ptype2(x, y, x_arg = x_arg, y_arg = y_arg, call = call) + restart <- "vctrs_restart_ptype2" + }, + cast = { + out <- vec_cast(x, y, x_arg = x_arg, to_arg = y_arg, call = call) + restart <- "vctrs_restart_cast" + }, + abort("Unexpected incompatible-type field.", .internal = TRUE) + ) + + # Old-R compat for `tryInvokeRestart()` + try_restart <- function(restart, ...) { + if (!is_null(findRestart(restart))) { + invokeRestart(restart, ...) + } + } + try_restart(restart, out) + } + ) +} From 1c1f6a79e990895047c0779b5a30e3118e1929f6 Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Fri, 7 Oct 2022 10:10:00 +0200 Subject: [PATCH 152/312] Simplify `has_no_proxy()` --- R/type2.R | 10 +--------- 1 file changed, 1 insertion(+), 9 deletions(-) diff --git a/R/type2.R b/R/type2.R index 69a01d307..59a81eedb 100644 --- a/R/type2.R +++ b/R/type2.R @@ -228,15 +228,7 @@ has_no_proxy <- function(x) { return(TRUE) } - if (!is_null(s3_get_method(class(x)[[1]], "vec_proxy", ns = "vctrs"))) { - return(FALSE) - } - - proxy <- vec_proxy(x) - - # Don't compare data for performance - identical(typeof(x), typeof(proxy)) && - identical(attributes(x), attributes(proxy)) + is_null(s3_get_method(class(x)[[1]], "vec_proxy", ns = "vctrs")) } new_common_class_fallback <- function(x, fallback_class) { From 7e784189554c900f5707180f50d41b2baedec655 Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Fri, 7 Oct 2022 10:14:02 +0200 Subject: [PATCH 153/312] Don't add `type` field and check class inheritance instead --- R/conditions.R | 13 +++---------- tests/testthat/helper-restart.R | 23 ++++++++++------------- 2 files changed, 13 insertions(+), 23 deletions(-) diff --git a/R/conditions.R b/R/conditions.R index ce830c87b..848016e11 100644 --- a/R/conditions.R +++ b/R/conditions.R @@ -130,16 +130,10 @@ stop_incompatible_type <- function(x, from_dispatch = match_from_dispatch(...) ) - switch( + subclass <- switch( action, - combine = { - type <- "ptype2" - subclass <- "vctrs_error_ptype2" - }, - convert = { - type <- "cast" - subclass <- "vctrs_error_cast" - } + combine = "vctrs_error_ptype2", + convert = "vctrs_error_cast" ) stop_incompatible( @@ -147,7 +141,6 @@ stop_incompatible_type <- function(x, x_arg = x_arg, y_arg = y_arg, details = details, - type = type, ..., message = message, class = c(class, subclass, "vctrs_error_incompatible_type"), diff --git a/tests/testthat/helper-restart.R b/tests/testthat/helper-restart.R index 7eae97464..3bdbe945d 100644 --- a/tests/testthat/helper-restart.R +++ b/tests/testthat/helper-restart.R @@ -29,19 +29,16 @@ with_ordered_restart <- function(expr) { y_arg <- cnd[["y_arg"]] call <- cnd[["call"]] - # Recurse with character methods and restart with the result - switch( - cnd[["type"]], - ptype2 = { - out <- vec_ptype2(x, y, x_arg = x_arg, y_arg = y_arg, call = call) - restart <- "vctrs_restart_ptype2" - }, - cast = { - out <- vec_cast(x, y, x_arg = x_arg, to_arg = y_arg, call = call) - restart <- "vctrs_restart_cast" - }, - abort("Unexpected incompatible-type field.", .internal = TRUE) - ) + # Recurse with factor methods and restart with the result + if (inherits(cnd, "vctrs_error_ptype2")) { + out <- vec_ptype2(x, y, x_arg = x_arg, y_arg = y_arg, call = call) + restart <- "vctrs_restart_ptype2" + } else if (inherits(cnd, "vctrs_error_cast")) { + out <- vec_cast(x, y, x_arg = x_arg, to_arg = y_arg, call = call) + restart <- "vctrs_restart_cast" + } else { + return(zap()) + } # Old-R compat for `tryInvokeRestart()` try_restart <- function(restart, ...) { From d0718443c3c1e9e46b235bbc66454ecae961e43b Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Fri, 7 Oct 2022 13:29:43 +0200 Subject: [PATCH 154/312] Update revdeps --- revdep/README.md | 18 +- revdep/cran.md | 43 +++- revdep/failures.md | 35 ++++ revdep/problems.md | 498 ++++++++++++++++++++++++++++++++++++++++++++- 4 files changed, 590 insertions(+), 4 deletions(-) diff --git a/revdep/README.md b/revdep/README.md index f6bcd0cb1..6d6fc0fdf 100644 --- a/revdep/README.md +++ b/revdep/README.md @@ -1,6 +1,6 @@ # Revdeps -## Failed to check (4) +## Failed to check (5) |package |version |error |warning |note | |:-------|:-------|:-----|:-------|:----| @@ -8,4 +8,20 @@ |NA |? | | | | |NA |? | | | | |NA |? | | | | +|NA |? | | | | + +## New problems (10) + +|package |version |error |warning |note | +|:------------|:-------|:--------|:-------|:----| +|[dm](problems.md#dm)|1.0.2 |1 __+1__ | | | +|[ggh4x](problems.md#ggh4x)|0.2.2 |__+1__ | | | +|[ggip](problems.md#ggip)|0.2.2 |__+1__ | | | +|[gratia](problems.md#gratia)|0.7.3 |__+1__ | | | +|[groupr](problems.md#groupr)|0.1.0 |__+1__ |__+1__ |1 | +|[recipes](problems.md#recipes)|1.0.1 |__+1__ | |1 | +|[ricu](problems.md#ricu)|0.5.3 |__+2__ |__+1__ | | +|[RSDA](problems.md#rsda)|3.0.13 |__+1__ |__+1__ | | +|[tidyr](problems.md#tidyr)|1.2.1 |__+1__ | |1 | +|[workflowsets](problems.md#workflowsets)|1.0.0 |__+1__ | | | diff --git a/revdep/cran.md b/revdep/cran.md index bbf58f109..c7e2509ec 100644 --- a/revdep/cran.md +++ b/revdep/cran.md @@ -1,7 +1,46 @@ ## revdepcheck results -We checked 175 reverse dependencies (171 from CRAN + 4 from Bioconductor), comparing R CMD check results across CRAN and dev versions of this package. +We checked 196 reverse dependencies (191 from CRAN + 5 from Bioconductor), comparing R CMD check results across CRAN and dev versions of this package. - * We saw 0 new problems + * We saw 10 new problems * We failed to check 0 packages +Issues with CRAN packages are summarised below. + +### New problems +(This reports the first line of each new failure) + +* dm + checking tests ... ERROR + +* ggh4x + checking tests ... ERROR + +* ggip + checking tests ... ERROR + +* gratia + checking tests ... ERROR + +* groupr + checking tests ... ERROR + checking re-building of vignette outputs ... WARNING + +* recipes + checking tests ... ERROR + +* ricu + checking examples ... ERROR + checking tests ... ERROR + checking re-building of vignette outputs ... WARNING + +* RSDA + checking tests ... ERROR + checking re-building of vignette outputs ... WARNING + +* tidyr + checking tests ... ERROR + +* workflowsets + checking tests ... ERROR + diff --git a/revdep/failures.md b/revdep/failures.md index 22c284730..fd10f3c24 100644 --- a/revdep/failures.md +++ b/revdep/failures.md @@ -137,4 +137,39 @@ Run `cloud_details(, "NA")` for more info +``` +# NA + +
+ +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/NA +* Number of recursive dependencies: 0 + +Run `cloud_details(, "NA")` for more info + +
+ +## Error before installation + +### Devel + +``` + + + + + + +``` +### CRAN + +``` + + + + + + ``` diff --git a/revdep/problems.md b/revdep/problems.md index 9a2073633..24dd72b1a 100644 --- a/revdep/problems.md +++ b/revdep/problems.md @@ -1 +1,497 @@ -*Wow, no problems at all. :)* \ No newline at end of file +# dm + +
+ +* Version: 1.0.2 +* GitHub: https://github.com/cynkra/dm +* Source code: https://github.com/cran/dm +* Date/Publication: 2022-09-20 07:46:26 UTC +* Number of recursive dependencies: 152 + +Run `cloud_details(, "dm")` for more info + +
+ +## Newly broken + +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Last 13 lines of output: + • only works on `sqlite` (1) + + ══ Failed tests ════════════════════════════════════════════════════════════════ + ── Failure (test-dplyr.R:210:3): basic test: 'slice()'-methods work ──────────── + `expect_equivalent_tbl(...)` produced warnings. + ── Failure (test-filter-dm.R:200:3): dm_filter() works without primary keys ──── + ``%>%`(...)` produced warnings. + ── Failure (test-dm.R:49:3): dm() works for adding tables ────────────────────── + `expect_equivalent_tbl(...)` produced warnings. + ── Failure (test-validate.R:13:3): validator is silent ───────────────────────── + `dm(a = tibble(x = 1)) %>% dm_add_pk(a, x) %>% dm_validate()` produced warnings. + + [ FAIL 4 | WARN 639 | SKIP 191 | PASS 1333 ] + Error: Test failures + Execution halted + ``` + +## In both + +* checking examples ... ERROR + ``` + Running examples in ‘dm-Ex.R’ failed + The error most likely occurred in: + + > ### Name: dm_flatten_to_tbl + > ### Title: Flatten a part of a 'dm' into a wide table + > ### Aliases: dm_flatten_to_tbl + > + > ### ** Examples + > + > + ... + 8. │ └─dm:::check_dm(dm) + 9. │ └─dm::is_dm(dm) + 10. ├─dm::dm_financial() + 11. │ ├─base::withVisible(eval(mc, parent.frame())) + 12. │ └─base::eval(mc, parent.frame()) + 13. │ └─base::eval(mc, parent.frame()) + 14. └─dm (local) ``() + 15. └─dm:::financial_db_con() + 16. └─rlang::abort(...) + Execution halted + ``` + +# ggh4x + +
+ +* Version: 0.2.2 +* GitHub: https://github.com/teunbrand/ggh4x +* Source code: https://github.com/cran/ggh4x +* Date/Publication: 2022-08-14 16:50:13 UTC +* Number of recursive dependencies: 78 + +Run `cloud_details(, "ggh4x")` for more info + +
+ +## Newly broken + +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Last 13 lines of output: + + ══ Skipped tests ═══════════════════════════════════════════════════════════════ + • On CRAN (6) + + ══ Failed tests ════════════════════════════════════════════════════════════════ + ── Failure (test-facetted_pos_scales.R:313:3): facetted_pos_scales can handle empty panels ── + `ggplotGrob(g)` produced warnings. + ── Failure (test-facetted_pos_scales.R:326:3): facetted_pos_scales can handle discrete scales ── + `ggplotGrob(g)` produced warnings. + ── Failure (test-facetted_pos_scales.R:341:3): facetted_pos_scales can handle date scales ── + `ggplotGrob(g)` produced warnings. + + [ FAIL 3 | WARN 24 | SKIP 6 | PASS 769 ] + Error: Test failures + Execution halted + ``` + +# ggip + +
+ +* Version: 0.2.2 +* GitHub: https://github.com/davidchall/ggip +* Source code: https://github.com/cran/ggip +* Date/Publication: 2022-09-29 06:00:02 UTC +* Number of recursive dependencies: 72 + +Run `cloud_details(, "ggip")` for more info + +
+ +## Newly broken + +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Last 13 lines of output: + Loading required package: ipaddress + > + > test_check("ggip") + [ FAIL 1 | WARN 47 | SKIP 5 | PASS 93 ] + + ══ Skipped tests ═══════════════════════════════════════════════════════════════ + • On CRAN (5) + + ══ Failed tests ════════════════════════════════════════════════════════════════ + ── Failure (test-stat-summary-address.R:97:3): addresses outside 2D grid raise warning ── + `layer_data(p + stat_summary_address(na.rm = TRUE))` produced warnings. + + [ FAIL 1 | WARN 47 | SKIP 5 | PASS 93 ] + Error: Test failures + Execution halted + ``` + +# gratia + +
+ +* Version: 0.7.3 +* GitHub: https://github.com/gavinsimpson/gratia +* Source code: https://github.com/cran/gratia +* Date/Publication: 2022-05-09 11:20:03 UTC +* Number of recursive dependencies: 83 + +Run `cloud_details(, "gratia")` for more info + +
+ +## Newly broken + +* checking tests ... ERROR + ``` + Running ‘test-all.R’ + Running the tests in ‘tests/test-all.R’ failed. + Last 13 lines of output: + • hgam-paper/hgam-paper-bird-move-model-1.svg + • hgam-paper/hgam-paper-bird-move-model-2.svg + • hgam-paper/hgam-paper-bird-move-model-3.svg + • hgam-paper/hgam-paper-bird-move-model-5.svg + • hgam-paper/hgam-paper-co2-model-1.svg + • hgam-paper/hgam-paper-co2-model-2.svg + • hgam-paper/hgam-paper-co2-model-3.svg + • hgam-paper/hgam-paper-co2-model-4.svg + • hgam-paper/hgam-paper-co2-model-5.svg + • hgam-paper/hgam-paper-zoop-model-4.svg + • hgam-paper/hgam-paper-zoop-model-5.svg + • rootograms/draw-gaussian-rootogram.svg + • rootograms/draw-neg-bin-rootogram.svg + Error: Test failures + Execution halted + ``` + +# groupr + +
+ +* Version: 0.1.0 +* GitHub: https://github.com/ngriffiths21/groupr +* Source code: https://github.com/cran/groupr +* Date/Publication: 2020-10-14 12:30:06 UTC +* Number of recursive dependencies: 63 + +Run `cloud_details(, "groupr")` for more info + +
+ +## Newly broken + +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Last 13 lines of output: + Please report it at with a reprex () and the full backtrace. + Backtrace: + ▆ + 1. ├─... %>% group_by2(is_ok, grp) at test_pivots.R:3:0 + 2. ├─groupr::group_by2(., is_ok, grp) + 3. ├─groupr:::group_by2.data.frame(., is_ok, grp) + 4. │ └─groupr:::group_by2_ok(data, dots) + 5. │ └─groupr:::igrouped_df(grouped, groups_out) + 6. │ └─vctrs::vec_rbind(groups, data.frame()) + 7. └─rlang:::stop_internal_c_lib(...) + 8. └─rlang::abort(message, call = call, .internal = TRUE, .frame = frame) + + [ FAIL 3 | WARN 0 | SKIP 0 | PASS 0 ] + Error: Test failures + Execution halted + ``` + +* checking re-building of vignette outputs ... WARNING + ``` + Error(s) in re-building vignettes: + ... + --- re-building ‘introduction.Rmd’ using rmarkdown + Quitting from lines 33-35 (introduction.Rmd) + Error: processing vignette 'introduction.Rmd' failed with diagnostics: + Column `.rows` (size 0) must match the data frame (size 2). + ℹ In file 'slice.c' at line 188. + ℹ This is an internal error that was detected in the vctrs package. + Please report it at with a reprex () and the full backtrace. + --- failed re-building ‘introduction.Rmd’ + + SUMMARY: processing the following file failed: + ‘introduction.Rmd’ + + Error: Vignette re-building failed. + Execution halted + ``` + +## In both + +* checking LazyData ... NOTE + ``` + 'LazyData' is specified without a 'data' directory + ``` + +# recipes + +
+ +* Version: 1.0.1 +* GitHub: https://github.com/tidymodels/recipes +* Source code: https://github.com/cran/recipes +* Date/Publication: 2022-07-07 22:30:06 UTC +* Number of recursive dependencies: 128 + +Run `cloud_details(, "recipes")` for more info + +
+ +## Newly broken + +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Last 13 lines of output: + + ══ Skipped tests ═══════════════════════════════════════════════════════════════ + • On CRAN (343) + • dimRed cannot be loaded (10) + • mixOmics cannot be loaded (14) + • redundant with check_new_data checks (1) + • tune_check() is TRUE (6) + + ══ Failed tests ════════════════════════════════════════════════════════════════ + ── Failure (test_relu.R:63:3): works with all_predictors() selector ──────────── + `prepped_rec <- prep(rec, iris)` produced warnings. + + [ FAIL 1 | WARN 255 | SKIP 374 | PASS 1753 ] + Error: Test failures + Execution halted + ``` + +## In both + +* checking Rd cross-references ... NOTE + ``` + Packages unavailable to check Rd xrefs: ‘fastICA’, ‘dimRed’ + ``` + +# ricu + +
+ +* Version: 0.5.3 +* GitHub: https://github.com/eth-mds/ricu +* Source code: https://github.com/cran/ricu +* Date/Publication: 2022-07-12 10:50:14 UTC +* Number of recursive dependencies: 114 + +Run `cloud_details(, "ricu")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘ricu-Ex.R’ failed + The error most likely occurred in: + + > ### Name: load_dictionary + > ### Title: Load concept dictionaries + > ### Aliases: load_dictionary concept_availability explain_dictionary + > + > ### ** Examples + > + > if (require(mimic.demo)) { + + head(load_dictionary("mimic_demo")) + + load_dictionary("mimic_demo", c("glu", "lact")) + + } + Loading required package: mimic.demo + Error: C stack usage 9967268 is too close to the limit + Execution halted + ``` + +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Last 13 lines of output: + ──────────────────────────────────────────────────────────────────────────────── + + + Attaching package: 'ricu' + + The following objects are masked from 'package:testthat': + + is_false, is_true + + > + > # for running interactively, do Sys.setenv(TESTTHAT_PKG = "ricu") + > + > test_check("ricu") + Error: C stack usage 9968580 is too close to the limit + Execution halted + ``` + +* checking re-building of vignette outputs ... WARNING + ``` + Error(s) in re-building vignettes: + ... + --- re-building ‘jss.Rmd’ using rmarkdown + Error: C stack usage 9966020 is too close to the limit + Execution halted + --- re-building ‘ricu.Rmd’ using rmarkdown + Error: C stack usage 9968660 is too close to the limit + Execution halted + --- re-building ‘uom.Rmd’ using rmarkdown + Error: C stack usage 9961828 is too close to the limit + Execution halted + SUMMARY: processing the following files failed: + ‘jss.Rmd’ ‘ricu.Rmd’ ‘uom.Rmd’ + + Error: Vignette re-building failed. + Execution halted + ``` + +# RSDA + +
+ +* Version: 3.0.13 +* GitHub: NA +* Source code: https://github.com/cran/RSDA +* Date/Publication: 2022-07-16 07:30:37 UTC +* Number of recursive dependencies: 154 + +Run `cloud_details(, "RSDA")` for more info + +
+ +## Newly broken + +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Last 13 lines of output: + > library(testthat) + > library(RSDA) + + + Attaching package: 'RSDA' + + The following objects are masked from 'package:stats': + + cor, sd, var + + > + > test_check("RSDA") + Error: C stack usage 9969876 is too close to the limit + Execution halted + ``` + +* checking re-building of vignette outputs ... WARNING + ``` + Error(s) in re-building vignettes: + ... + --- re-building ‘introduction.Rmd’ using rmarkdown + Error: C stack usage 9969444 is too close to the limit + Execution halted + ``` + +# tidyr + +
+ +* Version: 1.2.1 +* GitHub: https://github.com/tidyverse/tidyr +* Source code: https://github.com/cran/tidyr +* Date/Publication: 2022-09-08 07:30:02 UTC +* Number of recursive dependencies: 73 + +Run `cloud_details(, "tidyr")` for more info + +
+ +## Newly broken + +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Last 13 lines of output: + 1. ├─testthat::expect_warning(...) at test-rectangle.R:349:2 + 2. │ └─testthat:::expect_condition_matching(...) + 3. │ └─testthat:::quasi_capture(...) + 4. │ ├─testthat (local) .capture(...) + 5. │ │ └─base::withCallingHandlers(...) + 6. │ └─rlang::eval_bare(quo_get_expr(.quo), quo_get_env(.quo)) + 7. └─tidyr::unnest_wider(df, y, names_sep = "_") + 8. └─tidyr::unchop(data, all_of(cols)) + 9. └─tidyr:::df_unchop(cols, ptype = ptype, keep_empty = keep_empty) + 10. └─tidyr:::list_init_empty(x = col, null = TRUE, typed = keep_empty) + 11. └─vctrs::vec_equal_na(x) + + [ FAIL 3 | WARN 596 | SKIP 95 | PASS 962 ] + Error: Test failures + Execution halted + ``` + +## In both + +* checking data for non-ASCII characters ... NOTE + ``` + Note: found 24 marked UTF-8 strings + ``` + +# workflowsets + +
+ +* Version: 1.0.0 +* GitHub: https://github.com/tidymodels/workflowsets +* Source code: https://github.com/cran/workflowsets +* Date/Publication: 2022-07-12 23:20:01 UTC +* Number of recursive dependencies: 123 + +Run `cloud_details(, "workflowsets")` for more info + +
+ +## Newly broken + +* checking tests ... ERROR + ``` + Running ‘spelling.R’ + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Last 13 lines of output: + `vec_equal_na()` was deprecated in vctrs 0.5.0. + Please use `vec_detect_missing()` instead. + [ FAIL 1 | WARN 523 | SKIP 10 | PASS 376 ] + + ══ Skipped tests ═══════════════════════════════════════════════════════════════ + • On CRAN (9) + • rlang::is_installed("rlang") is TRUE (1) + + ══ Failed tests ════════════════════════════════════════════════════════════════ + ── Failure (test-workflow_set.R:142:4): workflow_set can handle correctly passed case weights ── + `{ ... }` produced messages. + + [ FAIL 1 | WARN 523 | SKIP 10 | PASS 376 ] + Error: Test failures + Execution halted + ``` + From 963b2141a93fb372bc808953affa0bb6f8ccc5ef Mon Sep 17 00:00:00 2001 From: Davis Vaughan Date: Fri, 7 Oct 2022 12:20:35 -0400 Subject: [PATCH 155/312] Teach `vec_chop()` to initialize data frames outside of `vec_restore()` (#1723) * Only compute raw size when needed * Teach `vec_chop()` to initialize data frames outside of `vec_restore()` --- src/proxy-restore.c | 2 +- src/slice-chop.c | 27 ++++++++++++++---------- tests/testthat/test-slice-chop.R | 36 ++++++++++++++++++++++++++++++++ 3 files changed, 53 insertions(+), 12 deletions(-) diff --git a/src/proxy-restore.c b/src/proxy-restore.c index eecc7c3e6..7e1ec67f3 100644 --- a/src/proxy-restore.c +++ b/src/proxy-restore.c @@ -213,9 +213,9 @@ r_obj* vec_bare_df_restore(r_obj* x, } r_obj* rownames = KEEP(df_rownames(x)); - r_ssize size = df_raw_size(x); if (rownames == r_null) { + r_ssize size = df_raw_size(x); init_compact_rownames(x, size); } else if (rownames_type(rownames) == ROWNAMES_TYPE_identifiers) { rownames = KEEP(vec_as_names(rownames, p_unique_repair_silent_opts)); diff --git a/src/slice-chop.c b/src/slice-chop.c index 19fe51414..b60f5dcf9 100644 --- a/src/slice-chop.c +++ b/src/slice-chop.c @@ -209,24 +209,29 @@ static SEXP chop_df(SEXP x, SEXP indices, struct vctrs_chop_info info) { bool has_row_names = TYPEOF(row_names) == STRSXP; - // Pre-load the `out` container with lists that will become data frames + // Pre-load the `out` container with empty bare data frames for (R_len_t i = 0; i < info.out_size; ++i) { - SEXP elt = PROTECT(Rf_allocVector(VECSXP, n_cols)); + SEXP elt = Rf_allocVector(VECSXP, n_cols); + SET_VECTOR_ELT(info.out, i, elt); Rf_setAttrib(elt, R_NamesSymbol, col_names); - if (has_row_names) { - if (info.has_indices) { - info.index = VECTOR_ELT(indices, i); - } else { - ++(*info.p_index); - } + r_ssize size = -1; - Rf_setAttrib(elt, R_RowNamesSymbol, slice_rownames(row_names, info.index)); + if (info.has_indices) { + info.index = VECTOR_ELT(indices, i); + size = vec_subscript_size(info.index); + } else { + ++(*info.p_index); + size = 1; } - SET_VECTOR_ELT(info.out, i, elt); - UNPROTECT(1); + init_data_frame(elt, size); + + if (has_row_names) { + SEXP elt_row_names = slice_rownames(row_names, info.index); + Rf_setAttrib(elt, R_RowNamesSymbol, elt_row_names); + } } // Split each column according to the indices, and then assign the results diff --git a/tests/testthat/test-slice-chop.R b/tests/testthat/test-slice-chop.R index 80b2f0b15..63ada09cf 100644 --- a/tests/testthat/test-slice-chop.R +++ b/tests/testthat/test-slice-chop.R @@ -53,6 +53,33 @@ test_that("vec_chop() keeps data frame row names", { expect_equal(result, list("r1", "r2")) }) +test_that("vec_chop() keeps data frame row names for data frames with 0 columns (#1722)", { + x <- data_frame(.size = 3) + rownames(x) <- c("r1", "r2", "r3") + + out <- lapply(vec_chop(x), rownames) + expect_identical(out, list("r1", "r2", "r3")) + + out <- vec_chop(x, indices = list(c(2, NA), 3)) + out <- lapply(out, rownames) + expect_identical(out, list(c("r2", "...2"), "r3")) +}) + +test_that("data frames with 0 columns retain the right number of rows (#1722)", { + x <- data_frame(.size = 4) + + one <- data_frame(.size = 1L) + expect_identical( + vec_chop(x), + list(one, one, one, one) + ) + + expect_identical( + vec_chop(x, indices = list(c(1, 3, 2), c(3, NA))), + list(data_frame(.size = 3), data_frame(.size = 2)) + ) +}) + test_that("matrices / arrays are split rowwise", { x <- array(1:12, c(2, 2, 2)) result <- list(vec_slice(x, 1), vec_slice(x, 2)) @@ -249,6 +276,15 @@ test_that("can chop S3 objects using the fallback method with compact seqs", { expect_equal(vec_chop_seq(x, 2L, 2L), list(vec_slice(x, 3:4))) }) +test_that("data frames with 0 columns retain the right number of rows with compact seqs (#1722)", { + x <- data_frame(.size = 4) + + out <- vec_chop_seq(x, starts = c(0L, 0L, 2L), sizes = c(0L, 2L, 1L)) + out <- map_int(out, vec_size) + + expect_identical(out, c(0L, 2L, 1L)) +}) + # list_unchop -------------------------------------------------------------- test_that("`x` must be a list", { From 74785261ccf290e4db30261b37bbe665cd046ec8 Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Mon, 10 Oct 2022 10:25:44 +0200 Subject: [PATCH 156/312] Update lifecycle snapshots --- DESCRIPTION | 2 +- tests/testthat/_snaps/lifecycle-deprecated.md | 4 ++-- 2 files changed, 3 insertions(+), 3 deletions(-) diff --git a/DESCRIPTION b/DESCRIPTION index b38880889..c438d3b43 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -31,7 +31,7 @@ Depends: Imports: cli (>= 3.4.0), glue, - lifecycle (>= 1.0.2), + lifecycle (>= 1.0.3), rlang (>= 1.0.6) Suggests: bit64, diff --git a/tests/testthat/_snaps/lifecycle-deprecated.md b/tests/testthat/_snaps/lifecycle-deprecated.md index 65039d900..055e8949f 100644 --- a/tests/testthat/_snaps/lifecycle-deprecated.md +++ b/tests/testthat/_snaps/lifecycle-deprecated.md @@ -5,7 +5,7 @@ Condition Warning: `vec_unchop()` was deprecated in vctrs 0.5.0. - Please use `list_unchop()` instead. + i Please use `list_unchop()` instead. Output [1] 1 @@ -16,7 +16,7 @@ Condition Warning: `vec_equal_na()` was deprecated in vctrs 0.5.0. - Please use `vec_detect_missing()` instead. + i Please use `vec_detect_missing()` instead. Output [1] FALSE TRUE From 6cf9bc5bc5ba9d6f528218b8991386e021ae3491 Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Mon, 10 Oct 2022 13:42:53 +0200 Subject: [PATCH 157/312] Call default method on incompatible factor + ordered --- R/type-factor.R | 5 +++-- tests/testthat/test-type2.R | 7 +++++++ 2 files changed, 10 insertions(+), 2 deletions(-) diff --git a/R/type-factor.R b/R/type-factor.R index 16ca045be..9d260ae86 100644 --- a/R/type-factor.R +++ b/R/type-factor.R @@ -117,13 +117,14 @@ vec_ptype2.ordered.character <- function(x, y, ...) { vec_ptype2.character.ordered <- function(x, y, ...) { stop_native_implementation("vec_ptype2.character.ordered") } + #' @export vec_ptype2.ordered.factor <- function(x, y, ...) { - vec_incompatible_ptype2(x, y, ...) + vec_default_ptype2(x, y, ...) } #' @export vec_ptype2.factor.ordered <- function(x, y, ...) { - vec_incompatible_ptype2(x, y, ...) + vec_default_ptype2(x, y, ...) } diff --git a/tests/testthat/test-type2.R b/tests/testthat/test-type2.R index 2e1779a08..b9649bc6b 100644 --- a/tests/testthat/test-type2.R +++ b/tests/testthat/test-type2.R @@ -385,4 +385,11 @@ test_that("can restart ptype2 errors", { data_frame(x = chr()) ) ) + + # Factor case + y <- data_frame(x = factor(c("A", "B", "C"))) + expect_equal( + with_ordered_restart(vec_rbind(x, y)), + data_frame(x = exp) + ) }) From 3a65c057196584105d6db34a363754f87f37ca6f Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Mon, 10 Oct 2022 16:33:36 +0200 Subject: [PATCH 158/312] Fix `base::c()` fallback in data frames within `list_unchop()` (#1725) Closes #1724 --- revdep/README.md | 20 +-- revdep/cran.md | 24 +-- revdep/problems.md | 318 +++---------------------------------- src/bind.c | 74 --------- src/c-unchop.c | 4 + src/c.c | 73 +++++++++ src/c.h | 9 ++ src/decl/bind-decl.h | 12 -- src/decl/c-decl.h | 3 + tests/testthat/test-bind.R | 70 ++++++-- 10 files changed, 176 insertions(+), 431 deletions(-) diff --git a/revdep/README.md b/revdep/README.md index 6d6fc0fdf..caa7582a2 100644 --- a/revdep/README.md +++ b/revdep/README.md @@ -10,18 +10,12 @@ |NA |? | | | | |NA |? | | | | -## New problems (10) +## New problems (4) -|package |version |error |warning |note | -|:------------|:-------|:--------|:-------|:----| -|[dm](problems.md#dm)|1.0.2 |1 __+1__ | | | -|[ggh4x](problems.md#ggh4x)|0.2.2 |__+1__ | | | -|[ggip](problems.md#ggip)|0.2.2 |__+1__ | | | -|[gratia](problems.md#gratia)|0.7.3 |__+1__ | | | -|[groupr](problems.md#groupr)|0.1.0 |__+1__ |__+1__ |1 | -|[recipes](problems.md#recipes)|1.0.1 |__+1__ | |1 | -|[ricu](problems.md#ricu)|0.5.3 |__+2__ |__+1__ | | -|[RSDA](problems.md#rsda)|3.0.13 |__+1__ |__+1__ | | -|[tidyr](problems.md#tidyr)|1.2.1 |__+1__ | |1 | -|[workflowsets](problems.md#workflowsets)|1.0.0 |__+1__ | | | +|package |version |error |warning |note | +|:-------|:-------|:------|:-------|:----| +|[errors](problems.md#errors)|0.3.6 |__+1__ | | | +|[groupr](problems.md#groupr)|0.1.0 |__+1__ |__+1__ |1 | +|[ricu](problems.md#ricu)|0.5.3 |__+2__ |__+1__ | | +|[RSDA](problems.md#rsda)|3.0.13 |__+1__ |__+1__ | | diff --git a/revdep/cran.md b/revdep/cran.md index c7e2509ec..e47490508 100644 --- a/revdep/cran.md +++ b/revdep/cran.md @@ -1,8 +1,8 @@ ## revdepcheck results -We checked 196 reverse dependencies (191 from CRAN + 5 from Bioconductor), comparing R CMD check results across CRAN and dev versions of this package. +We checked 198 reverse dependencies (193 from CRAN + 5 from Bioconductor), comparing R CMD check results across CRAN and dev versions of this package. - * We saw 10 new problems + * We saw 4 new problems * We failed to check 0 packages Issues with CRAN packages are summarised below. @@ -10,25 +10,13 @@ Issues with CRAN packages are summarised below. ### New problems (This reports the first line of each new failure) -* dm - checking tests ... ERROR - -* ggh4x - checking tests ... ERROR - -* ggip - checking tests ... ERROR - -* gratia +* errors checking tests ... ERROR * groupr checking tests ... ERROR checking re-building of vignette outputs ... WARNING -* recipes - checking tests ... ERROR - * ricu checking examples ... ERROR checking tests ... ERROR @@ -38,9 +26,3 @@ Issues with CRAN packages are summarised below. checking tests ... ERROR checking re-building of vignette outputs ... WARNING -* tidyr - checking tests ... ERROR - -* workflowsets - checking tests ... ERROR - diff --git a/revdep/problems.md b/revdep/problems.md index 24dd72b1a..88156cca5 100644 --- a/revdep/problems.md +++ b/revdep/problems.md @@ -1,14 +1,14 @@ -# dm +# errors
-* Version: 1.0.2 -* GitHub: https://github.com/cynkra/dm -* Source code: https://github.com/cran/dm -* Date/Publication: 2022-09-20 07:46:26 UTC -* Number of recursive dependencies: 152 +* Version: 0.3.6 +* GitHub: https://github.com/r-quantities/errors +* Source code: https://github.com/cran/errors +* Date/Publication: 2020-11-10 16:50:02 UTC +* Number of recursive dependencies: 52 -Run `cloud_details(, "dm")` for more info +Run `cloud_details(, "errors")` for more info
@@ -19,160 +19,19 @@ Run `cloud_details(, "dm")` for more info Running ‘testthat.R’ Running the tests in ‘tests/testthat.R’ failed. Last 13 lines of output: - • only works on `sqlite` (1) ══ Failed tests ════════════════════════════════════════════════════════════════ - ── Failure (test-dplyr.R:210:3): basic test: 'slice()'-methods work ──────────── - `expect_equivalent_tbl(...)` produced warnings. - ── Failure (test-filter-dm.R:200:3): dm_filter() works without primary keys ──── - ``%>%`(...)` produced warnings. - ── Failure (test-dm.R:49:3): dm() works for adding tables ────────────────────── - `expect_equivalent_tbl(...)` produced warnings. - ── Failure (test-validate.R:13:3): validator is silent ───────────────────────── - `dm(a = tibble(x = 1)) %>% dm_add_pk(a, x) %>% dm_validate()` produced warnings. - - [ FAIL 4 | WARN 639 | SKIP 191 | PASS 1333 ] - Error: Test failures - Execution halted - ``` - -## In both - -* checking examples ... ERROR - ``` - Running examples in ‘dm-Ex.R’ failed - The error most likely occurred in: - - > ### Name: dm_flatten_to_tbl - > ### Title: Flatten a part of a 'dm' into a wide table - > ### Aliases: dm_flatten_to_tbl - > - > ### ** Examples - > - > - ... - 8. │ └─dm:::check_dm(dm) - 9. │ └─dm::is_dm(dm) - 10. ├─dm::dm_financial() - 11. │ ├─base::withVisible(eval(mc, parent.frame())) - 12. │ └─base::eval(mc, parent.frame()) - 13. │ └─base::eval(mc, parent.frame()) - 14. └─dm (local) ``() - 15. └─dm:::financial_db_con() - 16. └─rlang::abort(...) - Execution halted - ``` - -# ggh4x - -
- -* Version: 0.2.2 -* GitHub: https://github.com/teunbrand/ggh4x -* Source code: https://github.com/cran/ggh4x -* Date/Publication: 2022-08-14 16:50:13 UTC -* Number of recursive dependencies: 78 - -Run `cloud_details(, "ggh4x")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Last 13 lines of output: - - ══ Skipped tests ═══════════════════════════════════════════════════════════════ - • On CRAN (6) - - ══ Failed tests ════════════════════════════════════════════════════════════════ - ── Failure (test-facetted_pos_scales.R:313:3): facetted_pos_scales can handle empty panels ── - `ggplotGrob(g)` produced warnings. - ── Failure (test-facetted_pos_scales.R:326:3): facetted_pos_scales can handle discrete scales ── - `ggplotGrob(g)` produced warnings. - ── Failure (test-facetted_pos_scales.R:341:3): facetted_pos_scales can handle date scales ── - `ggplotGrob(g)` produced warnings. - - [ FAIL 3 | WARN 24 | SKIP 6 | PASS 769 ] - Error: Test failures - Execution halted - ``` - -# ggip - -
- -* Version: 0.2.2 -* GitHub: https://github.com/davidchall/ggip -* Source code: https://github.com/cran/ggip -* Date/Publication: 2022-09-29 06:00:02 UTC -* Number of recursive dependencies: 72 - -Run `cloud_details(, "ggip")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Last 13 lines of output: - Loading required package: ipaddress - > - > test_check("ggip") - [ FAIL 1 | WARN 47 | SKIP 5 | PASS 93 ] - - ══ Skipped tests ═══════════════════════════════════════════════════════════════ - • On CRAN (5) - - ══ Failed tests ════════════════════════════════════════════════════════════════ - ── Failure (test-stat-summary-address.R:97:3): addresses outside 2D grid raise warning ── - `layer_data(p + stat_summary_address(na.rm = TRUE))` produced warnings. + ── Error ('test-tidyverse.R:123'): split-apply-combine with dplyr can combine integers and errors ── + + Error in `dplyr::mutate(., out = if (x) 0L else y)`: Problem while computing `out = if (x) 0L else y`. + ℹ The error occurred in group 3: g = 3. + Caused by error in `list_unchop()`: + ! `ptype` and `out` must be lists of the same length. + ℹ In file 'c.c' at line 386. + ℹ This is an internal error that was detected in the vctrs package. + Please report it at with a reprex () and the full backtrace. - [ FAIL 1 | WARN 47 | SKIP 5 | PASS 93 ] - Error: Test failures - Execution halted - ``` - -# gratia - -
- -* Version: 0.7.3 -* GitHub: https://github.com/gavinsimpson/gratia -* Source code: https://github.com/cran/gratia -* Date/Publication: 2022-05-09 11:20:03 UTC -* Number of recursive dependencies: 83 - -Run `cloud_details(, "gratia")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘test-all.R’ - Running the tests in ‘tests/test-all.R’ failed. - Last 13 lines of output: - • hgam-paper/hgam-paper-bird-move-model-1.svg - • hgam-paper/hgam-paper-bird-move-model-2.svg - • hgam-paper/hgam-paper-bird-move-model-3.svg - • hgam-paper/hgam-paper-bird-move-model-5.svg - • hgam-paper/hgam-paper-co2-model-1.svg - • hgam-paper/hgam-paper-co2-model-2.svg - • hgam-paper/hgam-paper-co2-model-3.svg - • hgam-paper/hgam-paper-co2-model-4.svg - • hgam-paper/hgam-paper-co2-model-5.svg - • hgam-paper/hgam-paper-zoop-model-4.svg - • hgam-paper/hgam-paper-zoop-model-5.svg - • rootograms/draw-gaussian-rootogram.svg - • rootograms/draw-neg-bin-rootogram.svg + [ FAIL 1 | WARN 2 | SKIP 0 | PASS 322 ] Error: Test failures Execution halted ``` @@ -242,51 +101,6 @@ Run `cloud_details(, "groupr")` for more info 'LazyData' is specified without a 'data' directory ``` -# recipes - -
- -* Version: 1.0.1 -* GitHub: https://github.com/tidymodels/recipes -* Source code: https://github.com/cran/recipes -* Date/Publication: 2022-07-07 22:30:06 UTC -* Number of recursive dependencies: 128 - -Run `cloud_details(, "recipes")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Last 13 lines of output: - - ══ Skipped tests ═══════════════════════════════════════════════════════════════ - • On CRAN (343) - • dimRed cannot be loaded (10) - • mixOmics cannot be loaded (14) - • redundant with check_new_data checks (1) - • tune_check() is TRUE (6) - - ══ Failed tests ════════════════════════════════════════════════════════════════ - ── Failure (test_relu.R:63:3): works with all_predictors() selector ──────────── - `prepped_rec <- prep(rec, iris)` produced warnings. - - [ FAIL 1 | WARN 255 | SKIP 374 | PASS 1753 ] - Error: Test failures - Execution halted - ``` - -## In both - -* checking Rd cross-references ... NOTE - ``` - Packages unavailable to check Rd xrefs: ‘fastICA’, ‘dimRed’ - ``` - # ricu
@@ -319,7 +133,7 @@ Run `cloud_details(, "ricu")` for more info + load_dictionary("mimic_demo", c("glu", "lact")) + } Loading required package: mimic.demo - Error: C stack usage 9967268 is too close to the limit + Error: C stack usage 9966868 is too close to the limit Execution halted ``` @@ -341,7 +155,7 @@ Run `cloud_details(, "ricu")` for more info > # for running interactively, do Sys.setenv(TESTTHAT_PKG = "ricu") > > test_check("ricu") - Error: C stack usage 9968580 is too close to the limit + Error: C stack usage 9961876 is too close to the limit Execution halted ``` @@ -350,13 +164,13 @@ Run `cloud_details(, "ricu")` for more info Error(s) in re-building vignettes: ... --- re-building ‘jss.Rmd’ using rmarkdown - Error: C stack usage 9966020 is too close to the limit + Error: C stack usage 9963460 is too close to the limit Execution halted --- re-building ‘ricu.Rmd’ using rmarkdown - Error: C stack usage 9968660 is too close to the limit + Error: C stack usage 9967556 is too close to the limit Execution halted --- re-building ‘uom.Rmd’ using rmarkdown - Error: C stack usage 9961828 is too close to the limit + Error: C stack usage 9967956 is too close to the limit Execution halted SUMMARY: processing the following files failed: ‘jss.Rmd’ ‘ricu.Rmd’ ‘uom.Rmd’ @@ -398,7 +212,7 @@ Run `cloud_details(, "RSDA")` for more info > > test_check("RSDA") - Error: C stack usage 9969876 is too close to the limit + Error: C stack usage 9961492 is too close to the limit Execution halted ``` @@ -407,91 +221,7 @@ Run `cloud_details(, "RSDA")` for more info Error(s) in re-building vignettes: ... --- re-building ‘introduction.Rmd’ using rmarkdown - Error: C stack usage 9969444 is too close to the limit + Error: C stack usage 9961956 is too close to the limit Execution halted ``` -# tidyr - -
- -* Version: 1.2.1 -* GitHub: https://github.com/tidyverse/tidyr -* Source code: https://github.com/cran/tidyr -* Date/Publication: 2022-09-08 07:30:02 UTC -* Number of recursive dependencies: 73 - -Run `cloud_details(, "tidyr")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Last 13 lines of output: - 1. ├─testthat::expect_warning(...) at test-rectangle.R:349:2 - 2. │ └─testthat:::expect_condition_matching(...) - 3. │ └─testthat:::quasi_capture(...) - 4. │ ├─testthat (local) .capture(...) - 5. │ │ └─base::withCallingHandlers(...) - 6. │ └─rlang::eval_bare(quo_get_expr(.quo), quo_get_env(.quo)) - 7. └─tidyr::unnest_wider(df, y, names_sep = "_") - 8. └─tidyr::unchop(data, all_of(cols)) - 9. └─tidyr:::df_unchop(cols, ptype = ptype, keep_empty = keep_empty) - 10. └─tidyr:::list_init_empty(x = col, null = TRUE, typed = keep_empty) - 11. └─vctrs::vec_equal_na(x) - - [ FAIL 3 | WARN 596 | SKIP 95 | PASS 962 ] - Error: Test failures - Execution halted - ``` - -## In both - -* checking data for non-ASCII characters ... NOTE - ``` - Note: found 24 marked UTF-8 strings - ``` - -# workflowsets - -
- -* Version: 1.0.0 -* GitHub: https://github.com/tidymodels/workflowsets -* Source code: https://github.com/cran/workflowsets -* Date/Publication: 2022-07-12 23:20:01 UTC -* Number of recursive dependencies: 123 - -Run `cloud_details(, "workflowsets")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘spelling.R’ - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Last 13 lines of output: - `vec_equal_na()` was deprecated in vctrs 0.5.0. - Please use `vec_detect_missing()` instead. - [ FAIL 1 | WARN 523 | SKIP 10 | PASS 376 ] - - ══ Skipped tests ═══════════════════════════════════════════════════════════════ - • On CRAN (9) - • rlang::is_installed("rlang") is TRUE (1) - - ══ Failed tests ════════════════════════════════════════════════════════════════ - ── Failure (test-workflow_set.R:142:4): workflow_set can handle correctly passed case weights ── - `{ ... }` produced messages. - - [ FAIL 1 | WARN 523 | SKIP 10 | PASS 376 ] - Error: Test failures - Execution halted - ``` - diff --git a/src/bind.c b/src/bind.c index d2358e9bc..3bb857735 100644 --- a/src/bind.c +++ b/src/bind.c @@ -257,80 +257,6 @@ r_obj* vec_rbind(r_obj* xs, return out; } -// `ptype` contains fallback information -static -void df_c_fallback(r_obj* out, - r_obj* ptype, - r_obj* xs, - r_ssize n_rows, - r_obj* name_spec, - struct name_repair_opts* name_repair, - struct r_lazy error_call) { - r_ssize n_cols = r_length(out); - - if (r_length(ptype) != n_cols || - r_typeof(out) != R_TYPE_list || - r_typeof(ptype) != R_TYPE_list) { - r_stop_internal("`ptype` and `out` must be lists of the same length."); - } - - for (r_ssize i = 0; i < n_cols; ++i) { - r_obj* ptype_col = r_list_get(ptype, i); - - // Recurse into df-cols - if (is_data_frame(ptype_col) && df_needs_fallback(ptype_col)) { - r_obj* xs_col = KEEP(list_pluck(xs, i)); - r_obj* out_col = r_list_get(out, i); - df_c_fallback(out_col, ptype_col, xs_col, n_rows, name_spec, name_repair, error_call); - FREE(1); - } else if (vec_is_common_class_fallback(ptype_col)) { - r_obj* xs_col = KEEP(list_pluck(xs, i)); - - r_obj* out_col = vec_c_fallback( - ptype_col, - xs_col, - name_spec, - name_repair, - vec_args.empty, - error_call - ); - r_list_poke(out, i, out_col); - - if (vec_size(out_col) != n_rows) { - r_stop_internal("`c()` method returned a vector of unexpected size %d instead of %d.", - vec_size(out_col), - n_rows); - } - - // Remove fallback vector from the ptype so it doesn't get in - // the way of restoration later on - r_list_poke(ptype, i, vec_ptype_final(out_col)); - - FREE(1); - } - } -} - -static -bool df_needs_fallback(r_obj* x) { - r_ssize n_cols = r_length(x); - r_obj* const * v_x = r_list_cbegin(x); - - for (r_ssize i = 0; i < n_cols; ++i) { - r_obj* col = v_x[i]; - - if (vec_is_common_class_fallback(col)) { - return true; - } - if (is_data_frame(col) && df_needs_fallback(col)) { - return true; - } - } - - return false; -} - - static r_obj* as_df_row(r_obj* x, struct name_repair_opts* name_repair, diff --git a/src/c-unchop.c b/src/c-unchop.c index c465bd23c..359ca764b 100644 --- a/src/c-unchop.c +++ b/src/c-unchop.c @@ -164,6 +164,10 @@ r_obj* list_unchop(r_obj* xs, FREE(2); } + if (is_data_frame(proxy)) { + df_c_fallback(proxy, ptype, xs, out_size, name_spec, name_repair, error_call); + } + r_obj* out = KEEP(vec_restore_recurse(proxy, ptype, VCTRS_OWNED_true)); if (out_names != r_null) { diff --git a/src/c.c b/src/c.c index 8a2225935..30bf22ad5 100644 --- a/src/c.c +++ b/src/c.c @@ -368,3 +368,76 @@ void stop_vec_c_fallback(r_obj* xs, int err_type, struct r_lazy call) { class_str ); } + + +// `ptype` contains fallback information +void df_c_fallback(r_obj* out, + r_obj* ptype, + r_obj* xs, + r_ssize n_rows, + r_obj* name_spec, + const struct name_repair_opts* name_repair, + struct r_lazy error_call) { + r_ssize n_cols = r_length(out); + + if (r_length(ptype) != n_cols || + r_typeof(out) != R_TYPE_list || + r_typeof(ptype) != R_TYPE_list) { + r_stop_internal("`ptype` and `out` must be lists of the same length."); + } + + for (r_ssize i = 0; i < n_cols; ++i) { + r_obj* ptype_col = r_list_get(ptype, i); + + // Recurse into df-cols + if (is_data_frame(ptype_col) && df_needs_fallback(ptype_col)) { + r_obj* xs_col = KEEP(list_pluck(xs, i)); + r_obj* out_col = r_list_get(out, i); + df_c_fallback(out_col, ptype_col, xs_col, n_rows, name_spec, name_repair, error_call); + FREE(1); + } else if (vec_is_common_class_fallback(ptype_col)) { + r_obj* xs_col = KEEP(list_pluck(xs, i)); + + r_obj* out_col = vec_c_fallback( + ptype_col, + xs_col, + name_spec, + name_repair, + vec_args.empty, + error_call + ); + r_list_poke(out, i, out_col); + + if (vec_size(out_col) != n_rows) { + r_stop_internal("`c()` method returned a vector of unexpected size %d instead of %d.", + vec_size(out_col), + n_rows); + } + + // Remove fallback vector from the ptype so it doesn't get in + // the way of restoration later on + r_list_poke(ptype, i, vec_ptype_final(out_col)); + + FREE(1); + } + } +} + +static +bool df_needs_fallback(r_obj* x) { + r_ssize n_cols = r_length(x); + r_obj* const * v_x = r_list_cbegin(x); + + for (r_ssize i = 0; i < n_cols; ++i) { + r_obj* col = v_x[i]; + + if (vec_is_common_class_fallback(col)) { + return true; + } + if (is_data_frame(col) && df_needs_fallback(col)) { + return true; + } + } + + return false; +} diff --git a/src/c.h b/src/c.h index 5f48335c1..efdd08d33 100644 --- a/src/c.h +++ b/src/c.h @@ -34,5 +34,14 @@ r_obj* vec_c_fallback(r_obj* ptype, bool needs_vec_c_fallback(r_obj* ptype); bool needs_vec_c_homogeneous_fallback(r_obj* xs, r_obj* ptype); +// Defined in bind.c +void df_c_fallback(r_obj* out, + r_obj* ptype, + r_obj* xs, + r_ssize n_rows, + r_obj* name_spec, + const struct name_repair_opts* name_repair, + struct r_lazy error_call); + #endif diff --git a/src/decl/bind-decl.h b/src/decl/bind-decl.h index da20ad949..30a36b678 100644 --- a/src/decl/bind-decl.h +++ b/src/decl/bind-decl.h @@ -49,15 +49,3 @@ r_obj* shaped_as_df_col(r_obj* x, r_obj* outer); static r_obj* vec_as_df_col(r_obj* x, r_obj* outer); - -static -void df_c_fallback(r_obj* out, - r_obj* ptype, - r_obj* xs, - r_ssize n_rows, - r_obj* name_spec, - struct name_repair_opts* name_repair, - struct r_lazy error_call); - -static -bool df_needs_fallback(r_obj* x); diff --git a/src/decl/c-decl.h b/src/decl/c-decl.h index 659e7013f..0cde5aa9c 100644 --- a/src/decl/c-decl.h +++ b/src/decl/c-decl.h @@ -6,3 +6,6 @@ int vec_c_fallback_validate_args(r_obj* x, r_obj* name_spec); static void stop_vec_c_fallback(r_obj* xs, int err_type, struct r_lazy call); + +static +bool df_needs_fallback(r_obj* x); diff --git a/tests/testthat/test-bind.R b/tests/testthat/test-bind.R index 2c2f52494..d5b03f596 100644 --- a/tests/testthat/test-bind.R +++ b/tests/testthat/test-bind.R @@ -829,39 +829,75 @@ test_that("vec_rbind() falls back to c() if S3 method is available", { y_df <- data_frame(x = y) expect_error(vec_rbind(x_df, y_df), class = "vctrs_error_incompatible_type") + expect_error(vec_c(x_df, y_df), class = "vctrs_error_incompatible_type") + expect_error(list_unchop(list(x_df, y_df), indices = list(1, 2)), class = "vctrs_error_incompatible_type") - out <- with_methods( - c.vctrs_foobar = function(...) quux(NextMethod()), - vec_rbind(x_df, y_df) + with_c_method <- function(expr) { + with_methods( + c.vctrs_foobar = function(...) quux(NextMethod()), + expr + ) + } + + out <- with_c_method(vec_rbind(x_df, y_df)) + exp <- data_frame(x = quux(c(1, 2))) + expect_identical(out, exp) + + # FIXME: This currently fails + # expect_identical(with_c_method(vec_c(x_df, y_df)), exp) + expect_identical( + with_c_method(list_unchop(list(x_df, y_df), indices = list(1, 2))), + exp ) - expect_identical(out, data_frame(x = quux(c(1, 2)))) # Fallback is used with data frame subclasses, with or without # ptype2 method foo_df <- foobaz(x_df) bar_df <- foobaz(y_df) - out <- with_methods( - c.vctrs_foobar = function(...) quux(NextMethod()), - vec_rbind(foo_df, bar_df) + out <- with_c_method(vec_rbind(foo_df, bar_df)) + exp <- foobaz(data_frame(x = quux(c(1, 2)))) + expect_identical(out, exp) + + # FIXME: This currently fails + # expect_identical(with_c_method(vec_c(foo_df, bar_df)), exp) + expect_identical( + with_c_method(list_unchop(list(foo_df, bar_df), indices = list(1, 2))), + exp ) - expect_identical(out, foobaz(data_frame(x = quux(c(1, 2))))) - out <- with_methods( - c.vctrs_foobar = function(...) quux(NextMethod()), - vec_ptype2.vctrs_foobaz.vctrs_foobaz = function(...) foobaz(df_ptype2(...)), - vec_rbind(foo_df, bar_df) + with_hybrid_methods <- function(expr) { + with_methods( + c.vctrs_foobar = function(...) quux(NextMethod()), + vec_ptype2.vctrs_foobaz.vctrs_foobaz = function(...) foobaz(df_ptype2(...)), + expr + ) + } + + out <- with_hybrid_methods(vec_rbind(foo_df, bar_df)) + exp <- foobaz(data_frame(x = quux(c(1, 2)))) + expect_identical(out, exp) + + # FIXME: This currently fails + # expect_identical(with_hybrid_methods(vec_c(foo_df, bar_df)), exp) + expect_identical( + with_hybrid_methods(list_unchop(list(foo_df, bar_df), indices = list(1, 2))), + exp ) - expect_identical(out, foobaz(data_frame(x = quux(c(1, 2))))) wrapper_x_df <- data_frame(x = x_df) wrapper_y_df <- data_frame(x = y_df) - out <- with_methods( - c.vctrs_foobar = function(...) quux(NextMethod()), - vec_rbind(wrapper_x_df, wrapper_y_df) + out <- with_c_method(vec_rbind(wrapper_x_df, wrapper_y_df)) + exp <- data_frame(x = data_frame(x = quux(c(1, 2)))) + expect_identical(out, exp) + + # FIXME: This currently fails + # expect_identical(with_c_method(vec_c(wrapper_x_df, wrapper_y_df)), exp) + expect_identical( + with_c_method(list_unchop(list(wrapper_x_df, wrapper_y_df), indices = list(1, 2))), + exp ) - expect_identical(out, data_frame(x = data_frame(x = quux(c(1, 2))))) }) test_that("c() fallback works with unspecified columns", { From e04fef0f68e25eb4c653750a0e778d954624c83b Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Tue, 11 Oct 2022 08:06:56 +0200 Subject: [PATCH 159/312] Remove outdated comment --- src/c.h | 1 - 1 file changed, 1 deletion(-) diff --git a/src/c.h b/src/c.h index efdd08d33..91aecdb75 100644 --- a/src/c.h +++ b/src/c.h @@ -34,7 +34,6 @@ r_obj* vec_c_fallback(r_obj* ptype, bool needs_vec_c_fallback(r_obj* ptype); bool needs_vec_c_homogeneous_fallback(r_obj* xs, r_obj* ptype); -// Defined in bind.c void df_c_fallback(r_obj* out, r_obj* ptype, r_obj* xs, From 25a1e586206d4821a4bebba01d21102b9a9598fc Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Mon, 10 Oct 2022 10:51:51 +0200 Subject: [PATCH 160/312] Fix `base::c()` fallback in `vec_c()` Update revdeps --- R/c.R | 2 + revdep/README.md | 12 +- revdep/cran.md | 16 ++- revdep/problems.md | 217 ++++++++++++++++++++++++------------- src/c.c | 27 ++--- tests/testthat/_snaps/c.md | 12 +- tests/testthat/test-bind.R | 12 +- tests/testthat/test-c.R | 13 +-- 8 files changed, 182 insertions(+), 129 deletions(-) diff --git a/R/c.R b/R/c.R index 4ab207cfa..083880968 100644 --- a/R/c.R +++ b/R/c.R @@ -81,6 +81,8 @@ base_c <- function(xs) { } base_c_invoke <- function(xs) { + local_options("vctrs:::base_c_in_progress" = TRUE) + # Remove all `NULL` arguments which prevent dispatch if in first # position and might not be handled correctly by methods xs <- compact(xs) diff --git a/revdep/README.md b/revdep/README.md index caa7582a2..81369297a 100644 --- a/revdep/README.md +++ b/revdep/README.md @@ -10,12 +10,14 @@ |NA |? | | | | |NA |? | | | | -## New problems (4) +## New problems (6) -|package |version |error |warning |note | -|:-------|:-------|:------|:-------|:----| +|package |version |error |warning |note | +|:----------|:-------|:------|:-------|:----| |[errors](problems.md#errors)|0.3.6 |__+1__ | | | |[groupr](problems.md#groupr)|0.1.0 |__+1__ |__+1__ |1 | -|[ricu](problems.md#ricu)|0.5.3 |__+2__ |__+1__ | | -|[RSDA](problems.md#rsda)|3.0.13 |__+1__ |__+1__ | | +|[lubridate](problems.md#lubridate)|1.8.0 |__+1__ | |1 | +|[quantities](problems.md#quantities)|0.1.6 |__+1__ |__+1__ | | +|[ricu](problems.md#ricu)|0.5.3 |__+1__ | | | +|[tibble](problems.md#tibble)|3.1.8 |__+1__ | | | diff --git a/revdep/cran.md b/revdep/cran.md index e47490508..be714177d 100644 --- a/revdep/cran.md +++ b/revdep/cran.md @@ -1,8 +1,8 @@ ## revdepcheck results -We checked 198 reverse dependencies (193 from CRAN + 5 from Bioconductor), comparing R CMD check results across CRAN and dev versions of this package. +We checked 199 reverse dependencies (194 from CRAN + 5 from Bioconductor), comparing R CMD check results across CRAN and dev versions of this package. - * We saw 4 new problems + * We saw 6 new problems * We failed to check 0 packages Issues with CRAN packages are summarised below. @@ -17,12 +17,16 @@ Issues with CRAN packages are summarised below. checking tests ... ERROR checking re-building of vignette outputs ... WARNING -* ricu - checking examples ... ERROR +* lubridate checking tests ... ERROR - checking re-building of vignette outputs ... WARNING -* RSDA +* quantities checking tests ... ERROR checking re-building of vignette outputs ... WARNING +* ricu + checking tests ... ERROR + +* tibble + checking tests ... ERROR + diff --git a/revdep/problems.md b/revdep/problems.md index 88156cca5..ffeca9669 100644 --- a/revdep/problems.md +++ b/revdep/problems.md @@ -19,19 +19,19 @@ Run `cloud_details(, "errors")` for more info Running ‘testthat.R’ Running the tests in ‘tests/testthat.R’ failed. Last 13 lines of output: - - ══ Failed tests ════════════════════════════════════════════════════════════════ + ℹ This is an internal error that was detected in the vctrs package. + Please report it at with a reprex () and the full backtrace. ── Error ('test-tidyverse.R:123'): split-apply-combine with dplyr can combine integers and errors ── Error in `dplyr::mutate(., out = if (x) 0L else y)`: Problem while computing `out = if (x) 0L else y`. ℹ The error occurred in group 3: g = 3. Caused by error in `list_unchop()`: ! `ptype` and `out` must be lists of the same length. - ℹ In file 'c.c' at line 386. + ℹ In file 'c.c' at line 375. ℹ This is an internal error that was detected in the vctrs package. Please report it at with a reprex () and the full backtrace. - [ FAIL 1 | WARN 2 | SKIP 0 | PASS 322 ] + [ FAIL 4 | WARN 2 | SKIP 0 | PASS 317 ] Error: Test failures Execution halted ``` @@ -101,95 +101,126 @@ Run `cloud_details(, "groupr")` for more info 'LazyData' is specified without a 'data' directory ``` -# ricu +# lubridate
-* Version: 0.5.3 -* GitHub: https://github.com/eth-mds/ricu -* Source code: https://github.com/cran/ricu -* Date/Publication: 2022-07-12 10:50:14 UTC -* Number of recursive dependencies: 114 +* Version: 1.8.0 +* GitHub: https://github.com/tidyverse/lubridate +* Source code: https://github.com/cran/lubridate +* Date/Publication: 2021-10-07 15:20:02 UTC +* Number of recursive dependencies: 59 -Run `cloud_details(, "ricu")` for more info +Run `cloud_details(, "lubridate")` for more info
## Newly broken -* checking examples ... ERROR +* checking tests ... ERROR ``` - Running examples in ‘ricu-Ex.R’ failed - The error most likely occurred in: - - > ### Name: load_dictionary - > ### Title: Load concept dictionaries - > ### Aliases: load_dictionary concept_availability explain_dictionary - > - > ### ** Examples - > - > if (require(mimic.demo)) { - + head(load_dictionary("mimic_demo")) - + load_dictionary("mimic_demo", c("glu", "lact")) - + } - Loading required package: mimic.demo - Error: C stack usage 9966868 is too close to the limit - Execution halted + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Last 13 lines of output: + Please report it at with a reprex () and the full backtrace. + Backtrace: + ▆ + 1. ├─testthat::expect_identical(vec_order(vec_c(y, x)), c(2L, 1L)) at test-vctrs.R:520:2 + 2. │ └─testthat::quasi_label(enquo(object), label, arg = "object") + 3. │ └─rlang::eval_bare(expr, quo_get_env(quo)) + 4. ├─vctrs::vec_order(vec_c(y, x)) + 5. │ └─vctrs::vec_proxy_order(x) + 6. ├─vctrs::vec_c(y, x) + 7. └─rlang:::stop_internal_c_lib(...) + 8. └─rlang::abort(message, call = call, .internal = TRUE, .frame = frame) + + [ FAIL 7 | WARN 0 | SKIP 8 | PASS 2737 ] + Error: Test failures + Execution halted ``` +## In both + +* checking package dependencies ... NOTE + ``` + Packages which this enhances but not available for checking: + 'chron', 'timeDate', 'tis', 'zoo' + ``` + +# quantities + +
+ +* Version: 0.1.6 +* GitHub: https://github.com/r-quantities/quantities +* Source code: https://github.com/cran/quantities +* Date/Publication: 2021-02-21 15:50:02 UTC +* Number of recursive dependencies: 57 + +Run `cloud_details(, "quantities")` for more info + +
+ +## Newly broken + * checking tests ... ERROR ``` Running ‘testthat.R’ Running the tests in ‘tests/testthat.R’ failed. Last 13 lines of output: - ──────────────────────────────────────────────────────────────────────────────── - - - Attaching package: 'ricu' - - The following objects are masked from 'package:testthat': - - is_false, is_true + 2. │ └─vctrs::list_unchop(...) + 3. └─rlang:::stop_internal_c_lib(...) + 4. └─rlang::abort(message, call = call, .internal = TRUE, .frame = frame) + ── Error ('test-tidyverse.R:98'): split-apply-combine with dplyr and base agree ── + Error in `dplyr::summarise(., dplyr::across(where(is.numeric), mean))`: Problem while computing `..1 = dplyr::across(where(is.numeric), mean)`. + ℹ The error occurred in group 3: Species = virginica. + Caused by error in `vec_c()`: + ! `ptype` and `out` must be lists of the same length. + ℹ In file 'c.c' at line 375. + ℹ This is an internal error that was detected in the vctrs package. + Please report it at with a reprex () and the full backtrace. - > - > # for running interactively, do Sys.setenv(TESTTHAT_PKG = "ricu") - > - > test_check("ricu") - Error: C stack usage 9961876 is too close to the limit + [ FAIL 2 | WARN 12 | SKIP 0 | PASS 634 ] + Error: Test failures Execution halted ``` * checking re-building of vignette outputs ... WARNING ``` Error(s) in re-building vignettes: - ... - --- re-building ‘jss.Rmd’ using rmarkdown - Error: C stack usage 9963460 is too close to the limit - Execution halted - --- re-building ‘ricu.Rmd’ using rmarkdown - Error: C stack usage 9967556 is too close to the limit - Execution halted - --- re-building ‘uom.Rmd’ using rmarkdown - Error: C stack usage 9967956 is too close to the limit - Execution halted - SUMMARY: processing the following files failed: - ‘jss.Rmd’ ‘ricu.Rmd’ ‘uom.Rmd’ + --- re-building ‘introduction.Rmd’ using rmarkdown + + Attaching package: 'dplyr' + + The following objects are masked from 'package:stats': + + filter, lag + + The following objects are masked from 'package:base': + ... + --- failed re-building ‘introduction.Rmd’ + + --- re-building ‘parsing.Rmd’ using rmarkdown + --- finished re-building ‘parsing.Rmd’ + + SUMMARY: processing the following file failed: + ‘introduction.Rmd’ Error: Vignette re-building failed. Execution halted ``` -# RSDA +# ricu
-* Version: 3.0.13 -* GitHub: NA -* Source code: https://github.com/cran/RSDA -* Date/Publication: 2022-07-16 07:30:37 UTC -* Number of recursive dependencies: 154 +* Version: 0.5.3 +* GitHub: https://github.com/eth-mds/ricu +* Source code: https://github.com/cran/ricu +* Date/Publication: 2022-07-12 10:50:14 UTC +* Number of recursive dependencies: 114 -Run `cloud_details(, "RSDA")` for more info +Run `cloud_details(, "ricu")` for more info
@@ -200,28 +231,58 @@ Run `cloud_details(, "RSDA")` for more info Running ‘testthat.R’ Running the tests in ‘tests/testthat.R’ failed. Last 13 lines of output: - > library(testthat) - > library(RSDA) - - - Attaching package: 'RSDA' - - The following objects are masked from 'package:stats': - - cor, sd, var + See . + Backtrace: + ▆ + 1. ├─testthat::expect_identical(as_src_cfg(mimic_demo), mi) at test-config.R:19:2 + 2. │ └─testthat::quasi_label(enquo(object), label, arg = "object") + 3. │ └─rlang::eval_bare(expr, quo_get_env(quo)) + 4. ├─ricu::as_src_cfg(mimic_demo) + 5. ├─ricu:::as_src_cfg.src_env(mimic_demo) + 6. │ └─vctrs::vec_unchop(lapply(x, as_col_cfg), name_spec = "{inner}") + 7. │ └─vctrs::list_unchop(...) + 8. └─rlang::abort(message = message, call = call) - > - > test_check("RSDA") - Error: C stack usage 9961492 is too close to the limit + [ FAIL 1 | WARN 1 | SKIP 7 | PASS 592 ] + Error: Test failures Execution halted ``` -* checking re-building of vignette outputs ... WARNING +# tibble + +
+ +* Version: 3.1.8 +* GitHub: https://github.com/tidyverse/tibble +* Source code: https://github.com/cran/tibble +* Date/Publication: 2022-07-22 06:10:02 UTC +* Number of recursive dependencies: 103 + +Run `cloud_details(, "tibble")` for more info + +
+ +## Newly broken + +* checking tests ... ERROR ``` - Error(s) in re-building vignettes: - ... - --- re-building ‘introduction.Rmd’ using rmarkdown - Error: C stack usage 9961956 is too close to the limit - Execution halted + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Last 13 lines of output: + 1. ├─testthat::expect_equal(...) at test-tribble.R:170:2 + 2. │ └─testthat::quasi_label(enquo(object), label, arg = "object") + 3. │ └─rlang::eval_bare(expr, quo_get_env(quo)) + 4. ├─tibble::tribble(~x, lubridate::days(1), lubridate::days(2)) + 5. │ └─tibble:::turn_frame_data_into_tibble(data$frame_names, data$frame_rest) + 6. │ └─tibble:::turn_matrix_into_column_list(frame_mat) + 7. │ ├─tibble:::subclass_tribble_c_errors(names(frame_col)[[i]], col <- vec_c(!!!unname(col))) + 8. │ │ └─base::withCallingHandlers(...) + 9. │ └─vctrs::vec_c(!!!unname(col)) + 10. └─rlang:::stop_internal_c_lib(...) + 11. └─rlang::abort(message, call = call, .internal = TRUE, .frame = frame) + + [ FAIL 1 | WARN 1 | SKIP 144 | PASS 1335 ] + Error: Test failures + Execution halted ``` diff --git a/src/c.c b/src/c.c index 30bf22ad5..5ca82ce51 100644 --- a/src/c.c +++ b/src/c.c @@ -35,11 +35,12 @@ r_obj* vec_c_opts(r_obj* xs, return r_null; } - if (needs_vec_c_fallback(ptype)) { + if (vec_is_common_class_fallback(ptype)) { r_obj* out = vec_c_fallback(ptype, xs, name_spec, name_repair, p_error_arg, error_call); FREE(1); return out; } + // FIXME: Needed for dplyr::summarise() which passes a non-fallback ptype if (needs_vec_c_homogeneous_fallback(xs, ptype)) { r_obj* out = vec_c_fallback_invoke(xs, name_spec, error_call); @@ -47,22 +48,6 @@ r_obj* vec_c_opts(r_obj* xs, return out; } - // FIXME: If data frame, recompute ptype without common class - // fallback. Should refactor this to allow common class fallback - // with data frame columns. - // - // FIXME: If `ptype` is a `vctrs_vctr` class without a - // `vec_ptype2()` method, the common type is a common class - // fallback. To avoid infinit recursion through `c.vctrs_vctr()`, we - // bail out from `needs_vec_c_fallback()`. In this case recurse with - // fallback disabled as well. - if ((is_data_frame(ptype) && fallback_opts->s3 == S3_FALLBACK_true) || - vec_is_common_class_fallback(ptype)) { - ptype_opts.fallback.s3 = S3_FALLBACK_false; - ptype = vec_ptype_common_opts(xs, orig_ptype, &ptype_opts); - } - KEEP(ptype); - // Find individual input sizes and total size of output r_ssize xs_size = r_length(xs); r_ssize out_size = 0; @@ -162,6 +147,10 @@ r_obj* vec_c_opts(r_obj* xs, FREE(1); } + if (is_data_frame(out)) { + df_c_fallback(out, ptype, xs, out_size, name_spec, name_repair, error_call); + } + out = KEEP(vec_restore_recurse(out, ptype, VCTRS_OWNED_true)); if (out_names != r_null) { @@ -175,7 +164,7 @@ r_obj* vec_c_opts(r_obj* xs, out = vec_set_names(out, r_null); } - FREE(9); + FREE(8); return out; } @@ -286,7 +275,7 @@ r_obj* vec_c_fallback(r_obj* ptype, bool implements_c = class_implements_base_c(class); FREE(1); - if (implements_c) { + if (implements_c && !r_is_true(r_peek_option("vctrs:::base_c_in_progress"))) { return vec_c_fallback_invoke(xs, name_spec, error_call); } else { struct ptype_common_opts ptype_opts = { diff --git a/tests/testthat/_snaps/c.md b/tests/testthat/_snaps/c.md index 4139d8424..c4c851c0a 100644 --- a/tests/testthat/_snaps/c.md +++ b/tests/testthat/_snaps/c.md @@ -219,7 +219,7 @@ dfs <- rep(list(df), 100) with_memory_prof(list_unchop(dfs)) Output - [1] 9.05KB + [1] 8.79KB Code # Data frame with rownames (non-repaired, non-recursive case) df <- data_frame(x = 1:2) @@ -227,13 +227,13 @@ dfs <- map2(dfs, seq_along(dfs), set_rownames_recursively) with_memory_prof(list_unchop(dfs)) Output - [1] 6.28KB + [1] 6.02KB Code # Data frame with rownames (repaired, non-recursive case) dfs <- map(dfs, set_rownames_recursively) with_memory_prof(list_unchop(dfs)) Output - [1] 12.4KB + [1] 12.2KB Code # Data frame with rownames (non-repaired, recursive case) (#1217) df <- data_frame(x = 1:2, y = data_frame(x = 1:2)) @@ -241,13 +241,13 @@ dfs <- map2(dfs, seq_along(dfs), set_rownames_recursively) with_memory_prof(list_unchop(dfs)) Output - [1] 11.6KB + [1] 11.4KB Code # Data frame with rownames (repaired, recursive case) (#1217) dfs <- map(dfs, set_rownames_recursively) with_memory_prof(list_unchop(dfs)) Output - [1] 23.9KB + [1] 23.7KB Code # list-ofs (#1496) make_list_of <- (function(n) { @@ -260,7 +260,7 @@ Code with_memory_prof(list_unchop(make_list_of(2000))) Output - [1] 222KB + [1] 221KB Code with_memory_prof(list_unchop(make_list_of(4000))) Output diff --git a/tests/testthat/test-bind.R b/tests/testthat/test-bind.R index d5b03f596..b067bcb5c 100644 --- a/tests/testthat/test-bind.R +++ b/tests/testthat/test-bind.R @@ -843,8 +843,7 @@ test_that("vec_rbind() falls back to c() if S3 method is available", { exp <- data_frame(x = quux(c(1, 2))) expect_identical(out, exp) - # FIXME: This currently fails - # expect_identical(with_c_method(vec_c(x_df, y_df)), exp) + expect_identical(with_c_method(vec_c(x_df, y_df)), exp) expect_identical( with_c_method(list_unchop(list(x_df, y_df), indices = list(1, 2))), exp @@ -859,8 +858,7 @@ test_that("vec_rbind() falls back to c() if S3 method is available", { exp <- foobaz(data_frame(x = quux(c(1, 2)))) expect_identical(out, exp) - # FIXME: This currently fails - # expect_identical(with_c_method(vec_c(foo_df, bar_df)), exp) + expect_identical(with_c_method(vec_c(foo_df, bar_df)), exp) expect_identical( with_c_method(list_unchop(list(foo_df, bar_df), indices = list(1, 2))), exp @@ -878,8 +876,7 @@ test_that("vec_rbind() falls back to c() if S3 method is available", { exp <- foobaz(data_frame(x = quux(c(1, 2)))) expect_identical(out, exp) - # FIXME: This currently fails - # expect_identical(with_hybrid_methods(vec_c(foo_df, bar_df)), exp) + expect_identical(with_hybrid_methods(vec_c(foo_df, bar_df)), exp) expect_identical( with_hybrid_methods(list_unchop(list(foo_df, bar_df), indices = list(1, 2))), exp @@ -892,8 +889,7 @@ test_that("vec_rbind() falls back to c() if S3 method is available", { exp <- data_frame(x = data_frame(x = quux(c(1, 2)))) expect_identical(out, exp) - # FIXME: This currently fails - # expect_identical(with_c_method(vec_c(wrapper_x_df, wrapper_y_df)), exp) + expect_identical(with_c_method(vec_c(wrapper_x_df, wrapper_y_df)), exp) expect_identical( with_c_method(list_unchop(list(wrapper_x_df, wrapper_y_df), indices = list(1, 2))), exp diff --git a/tests/testthat/test-c.R b/tests/testthat/test-c.R index 8233246ed..210126174 100644 --- a/tests/testthat/test-c.R +++ b/tests/testthat/test-c.R @@ -272,7 +272,7 @@ test_that("vec_c() falls back to c() if S3 method is available", { ) }) -test_that("c() fallback is consistent (FIXME)", { +test_that("c() fallback is consistent", { out <- with_methods( c.vctrs_foobar = function(...) structure(NextMethod(), class = "dispatched"), list( @@ -283,13 +283,12 @@ test_that("c() fallback is consistent (FIXME)", { ) ) - # Proper `c()` dispatch: - expect_identical(out$direct, structure(1:2, class = "dispatched")) + dispatched <- function(x) structure(x, class = "dispatched") - # Inconsistent: - expect_identical(out$df$x, foobar(1:2)) - expect_identical(out$tib$x, foobar(1:2)) - expect_identical(out$foreign_df$x, foobar(1:2)) + expect_identical(out$direct, dispatched(1:2)) + expect_identical(out$df$x, dispatched(1:2)) + expect_identical(out$tib$x, dispatched(1:2)) + expect_identical(out$foreign_df$x, dispatched(1:2)) }) test_that("vec_c() falls back to c() if S4 method is available", { From 7895bd56f0f10cbfe6152ce7d0c107e0bd027a72 Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Mon, 10 Oct 2022 14:25:22 +0200 Subject: [PATCH 161/312] Apply `c()` fallback after restoration Update revdeps --- revdep/README.md | 10 +-- revdep/cran.md | 15 +--- revdep/problems.md | 185 ---------------------------------------- src/bind.c | 3 - src/c-unchop.c | 1 - src/c.c | 4 +- tests/testthat/test-c.R | 29 +++++++ 7 files changed, 35 insertions(+), 212 deletions(-) diff --git a/revdep/README.md b/revdep/README.md index 81369297a..023a28d1c 100644 --- a/revdep/README.md +++ b/revdep/README.md @@ -10,14 +10,10 @@ |NA |? | | | | |NA |? | | | | -## New problems (6) +## New problems (2) -|package |version |error |warning |note | -|:----------|:-------|:------|:-------|:----| -|[errors](problems.md#errors)|0.3.6 |__+1__ | | | +|package |version |error |warning |note | +|:-------|:-------|:------|:-------|:----| |[groupr](problems.md#groupr)|0.1.0 |__+1__ |__+1__ |1 | -|[lubridate](problems.md#lubridate)|1.8.0 |__+1__ | |1 | -|[quantities](problems.md#quantities)|0.1.6 |__+1__ |__+1__ | | |[ricu](problems.md#ricu)|0.5.3 |__+1__ | | | -|[tibble](problems.md#tibble)|3.1.8 |__+1__ | | | diff --git a/revdep/cran.md b/revdep/cran.md index be714177d..020ea8d0c 100644 --- a/revdep/cran.md +++ b/revdep/cran.md @@ -2,7 +2,7 @@ We checked 199 reverse dependencies (194 from CRAN + 5 from Bioconductor), comparing R CMD check results across CRAN and dev versions of this package. - * We saw 6 new problems + * We saw 2 new problems * We failed to check 0 packages Issues with CRAN packages are summarised below. @@ -10,23 +10,10 @@ Issues with CRAN packages are summarised below. ### New problems (This reports the first line of each new failure) -* errors - checking tests ... ERROR - * groupr checking tests ... ERROR checking re-building of vignette outputs ... WARNING -* lubridate - checking tests ... ERROR - -* quantities - checking tests ... ERROR - checking re-building of vignette outputs ... WARNING - * ricu checking tests ... ERROR -* tibble - checking tests ... ERROR - diff --git a/revdep/problems.md b/revdep/problems.md index ffeca9669..96d31e955 100644 --- a/revdep/problems.md +++ b/revdep/problems.md @@ -1,41 +1,3 @@ -# errors - -
- -* Version: 0.3.6 -* GitHub: https://github.com/r-quantities/errors -* Source code: https://github.com/cran/errors -* Date/Publication: 2020-11-10 16:50:02 UTC -* Number of recursive dependencies: 52 - -Run `cloud_details(, "errors")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Last 13 lines of output: - ℹ This is an internal error that was detected in the vctrs package. - Please report it at with a reprex () and the full backtrace. - ── Error ('test-tidyverse.R:123'): split-apply-combine with dplyr can combine integers and errors ── - - Error in `dplyr::mutate(., out = if (x) 0L else y)`: Problem while computing `out = if (x) 0L else y`. - ℹ The error occurred in group 3: g = 3. - Caused by error in `list_unchop()`: - ! `ptype` and `out` must be lists of the same length. - ℹ In file 'c.c' at line 375. - ℹ This is an internal error that was detected in the vctrs package. - Please report it at with a reprex () and the full backtrace. - - [ FAIL 4 | WARN 2 | SKIP 0 | PASS 317 ] - Error: Test failures - Execution halted - ``` - # groupr
@@ -101,115 +63,6 @@ Run `cloud_details(, "groupr")` for more info 'LazyData' is specified without a 'data' directory ``` -# lubridate - -
- -* Version: 1.8.0 -* GitHub: https://github.com/tidyverse/lubridate -* Source code: https://github.com/cran/lubridate -* Date/Publication: 2021-10-07 15:20:02 UTC -* Number of recursive dependencies: 59 - -Run `cloud_details(, "lubridate")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Last 13 lines of output: - Please report it at with a reprex () and the full backtrace. - Backtrace: - ▆ - 1. ├─testthat::expect_identical(vec_order(vec_c(y, x)), c(2L, 1L)) at test-vctrs.R:520:2 - 2. │ └─testthat::quasi_label(enquo(object), label, arg = "object") - 3. │ └─rlang::eval_bare(expr, quo_get_env(quo)) - 4. ├─vctrs::vec_order(vec_c(y, x)) - 5. │ └─vctrs::vec_proxy_order(x) - 6. ├─vctrs::vec_c(y, x) - 7. └─rlang:::stop_internal_c_lib(...) - 8. └─rlang::abort(message, call = call, .internal = TRUE, .frame = frame) - - [ FAIL 7 | WARN 0 | SKIP 8 | PASS 2737 ] - Error: Test failures - Execution halted - ``` - -## In both - -* checking package dependencies ... NOTE - ``` - Packages which this enhances but not available for checking: - 'chron', 'timeDate', 'tis', 'zoo' - ``` - -# quantities - -
- -* Version: 0.1.6 -* GitHub: https://github.com/r-quantities/quantities -* Source code: https://github.com/cran/quantities -* Date/Publication: 2021-02-21 15:50:02 UTC -* Number of recursive dependencies: 57 - -Run `cloud_details(, "quantities")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Last 13 lines of output: - 2. │ └─vctrs::list_unchop(...) - 3. └─rlang:::stop_internal_c_lib(...) - 4. └─rlang::abort(message, call = call, .internal = TRUE, .frame = frame) - ── Error ('test-tidyverse.R:98'): split-apply-combine with dplyr and base agree ── - Error in `dplyr::summarise(., dplyr::across(where(is.numeric), mean))`: Problem while computing `..1 = dplyr::across(where(is.numeric), mean)`. - ℹ The error occurred in group 3: Species = virginica. - Caused by error in `vec_c()`: - ! `ptype` and `out` must be lists of the same length. - ℹ In file 'c.c' at line 375. - ℹ This is an internal error that was detected in the vctrs package. - Please report it at with a reprex () and the full backtrace. - - [ FAIL 2 | WARN 12 | SKIP 0 | PASS 634 ] - Error: Test failures - Execution halted - ``` - -* checking re-building of vignette outputs ... WARNING - ``` - Error(s) in re-building vignettes: - --- re-building ‘introduction.Rmd’ using rmarkdown - - Attaching package: 'dplyr' - - The following objects are masked from 'package:stats': - - filter, lag - - The following objects are masked from 'package:base': - ... - --- failed re-building ‘introduction.Rmd’ - - --- re-building ‘parsing.Rmd’ using rmarkdown - --- finished re-building ‘parsing.Rmd’ - - SUMMARY: processing the following file failed: - ‘introduction.Rmd’ - - Error: Vignette re-building failed. - Execution halted - ``` - # ricu
@@ -248,41 +101,3 @@ Run `cloud_details(, "ricu")` for more info Execution halted ``` -# tibble - -
- -* Version: 3.1.8 -* GitHub: https://github.com/tidyverse/tibble -* Source code: https://github.com/cran/tibble -* Date/Publication: 2022-07-22 06:10:02 UTC -* Number of recursive dependencies: 103 - -Run `cloud_details(, "tibble")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Last 13 lines of output: - 1. ├─testthat::expect_equal(...) at test-tribble.R:170:2 - 2. │ └─testthat::quasi_label(enquo(object), label, arg = "object") - 3. │ └─rlang::eval_bare(expr, quo_get_env(quo)) - 4. ├─tibble::tribble(~x, lubridate::days(1), lubridate::days(2)) - 5. │ └─tibble:::turn_frame_data_into_tibble(data$frame_names, data$frame_rest) - 6. │ └─tibble:::turn_matrix_into_column_list(frame_mat) - 7. │ ├─tibble:::subclass_tribble_c_errors(names(frame_col)[[i]], col <- vec_c(!!!unname(col))) - 8. │ │ └─base::withCallingHandlers(...) - 9. │ └─vctrs::vec_c(!!!unname(col)) - 10. └─rlang:::stop_internal_c_lib(...) - 11. └─rlang::abort(message, call = call, .internal = TRUE, .frame = frame) - - [ FAIL 1 | WARN 1 | SKIP 144 | PASS 1335 ] - Error: Test failures - Execution halted - ``` - diff --git a/src/bind.c b/src/bind.c index 3bb857735..cdd8bb65f 100644 --- a/src/bind.c +++ b/src/bind.c @@ -247,10 +247,7 @@ r_obj* vec_rbind(r_obj* xs, KEEP_AT(out, out_pi); } - // Not optimal. Happens after the fallback columns have been - // assigned already, ideally they should be ignored. df_c_fallback(out, ptype, xs, n_rows, name_spec, name_repair, error_call); - out = vec_restore_recurse(out, ptype, VCTRS_OWNED_true); FREE(n_prot); diff --git a/src/c-unchop.c b/src/c-unchop.c index 359ca764b..84c0d5a31 100644 --- a/src/c-unchop.c +++ b/src/c-unchop.c @@ -167,7 +167,6 @@ r_obj* list_unchop(r_obj* xs, if (is_data_frame(proxy)) { df_c_fallback(proxy, ptype, xs, out_size, name_spec, name_repair, error_call); } - r_obj* out = KEEP(vec_restore_recurse(proxy, ptype, VCTRS_OWNED_true)); if (out_names != r_null) { diff --git a/src/c.c b/src/c.c index 5ca82ce51..9a8479545 100644 --- a/src/c.c +++ b/src/c.c @@ -147,12 +147,12 @@ r_obj* vec_c_opts(r_obj* xs, FREE(1); } + out = KEEP(vec_restore_recurse(out, ptype, VCTRS_OWNED_true)); + if (is_data_frame(out)) { df_c_fallback(out, ptype, xs, out_size, name_spec, name_repair, error_call); } - out = KEEP(vec_restore_recurse(out, ptype, VCTRS_OWNED_true)); - if (out_names != r_null) { out_names = KEEP(vec_as_names(out_names, name_repair)); out = vec_set_names(out, out_names); diff --git a/tests/testthat/test-c.R b/tests/testthat/test-c.R index 210126174..6ad4969e3 100644 --- a/tests/testthat/test-c.R +++ b/tests/testthat/test-c.R @@ -603,3 +603,32 @@ test_that("dots splicing clones as appropriate", { vctrs::vec_c(!!!x, 2) expect_equal(x, list(a = 1)) }) + +test_that("can combine records wrapped in data frames", { + local_methods( + vec_proxy.vctrs_foobar = function(x, ...) { + data_frame(x = unclass(x), y = seq_along(x)) + }, + vec_restore.vctrs_foobar = function(x, to, ...) { + foobar(x$x) + } + ) + + x <- foobar(1:2) + y <- foobar(3:4) + + expect_equal( + vec_c(x, y), + foobar(1:4) + ) + + expect_equal( + list_unchop(list(x, y), indices = list(1:2, 3:4)), + foobar(1:4) + ) + + expect_equal( + vec_rbind(data_frame(x = x), data_frame(x = y)), + data_frame(x = foobar(1:4)) + ) +}) From 047542c7f83af0ba27c96aac526f635bf35ae37b Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Tue, 11 Oct 2022 11:40:12 +0200 Subject: [PATCH 162/312] Fix recursive case of `base::c()` fallback Use same approach as in recursive restoration to support record vectors that contain fields for which we fall back to `c()` --- R/type2.R | 8 ++++++++ src/c.c | 25 ++++++++++++++++++++----- tests/testthat/test-c.R | 34 +++++++++++++++++++++++++++------- 3 files changed, 55 insertions(+), 12 deletions(-) diff --git a/R/type2.R b/R/type2.R index 59a81eedb..8f45d89cf 100644 --- a/R/type2.R +++ b/R/type2.R @@ -36,6 +36,14 @@ vec_ptype2 <- function(x, call = caller_env()) { if (!missing(...)) { check_ptype2_dots_empty(...) + return(vec_ptype2_opts( + x, + y, + opts = match_fallback_opts(...), + x_arg = x_arg, + y_arg = y_arg, + call = call + )) } return(.Call(ffi_ptype2, x, y, environment())) UseMethod("vec_ptype2") diff --git a/src/c.c b/src/c.c index 9a8479545..22b369b20 100644 --- a/src/c.c +++ b/src/c.c @@ -97,7 +97,10 @@ r_obj* vec_c_opts(r_obj* xs, struct cast_opts c_cast_opts = { .to = ptype, .p_x_arg = p_x_arg, - .call = error_call + .call = error_call, + .fallback = { + .s3 = S3_FALLBACK_true + } }; const struct vec_assign_opts c_assign_opts = { @@ -147,11 +150,10 @@ r_obj* vec_c_opts(r_obj* xs, FREE(1); } - out = KEEP(vec_restore_recurse(out, ptype, VCTRS_OWNED_true)); - if (is_data_frame(out)) { df_c_fallback(out, ptype, xs, out_size, name_spec, name_repair, error_call); } + out = KEEP(vec_restore_recurse(out, ptype, VCTRS_OWNED_true)); if (out_names != r_null) { out_names = KEEP(vec_as_names(out_names, name_repair)); @@ -367,8 +369,18 @@ void df_c_fallback(r_obj* out, r_obj* name_spec, const struct name_repair_opts* name_repair, struct r_lazy error_call) { + int n_prot = 0; r_ssize n_cols = r_length(out); + r_obj* ptype_orig = ptype; + + if (!is_data_frame(ptype)) { + ptype = KEEP_N(vec_proxy(ptype), &n_prot); + if (!is_data_frame(ptype)) { + r_stop_internal("Expected c fallback target to have a df proxy."); + } + } + if (r_length(ptype) != n_cols || r_typeof(out) != R_TYPE_list || r_typeof(ptype) != R_TYPE_list) { @@ -376,10 +388,11 @@ void df_c_fallback(r_obj* out, } for (r_ssize i = 0; i < n_cols; ++i) { + r_obj* col = r_list_get(out, i); r_obj* ptype_col = r_list_get(ptype, i); // Recurse into df-cols - if (is_data_frame(ptype_col) && df_needs_fallback(ptype_col)) { + if (is_data_frame(col) && df_needs_fallback(ptype_col)) { r_obj* xs_col = KEEP(list_pluck(xs, i)); r_obj* out_col = r_list_get(out, i); df_c_fallback(out_col, ptype_col, xs_col, n_rows, name_spec, name_repair, error_call); @@ -405,11 +418,13 @@ void df_c_fallback(r_obj* out, // Remove fallback vector from the ptype so it doesn't get in // the way of restoration later on - r_list_poke(ptype, i, vec_ptype_final(out_col)); + r_list_poke(ptype_orig, i, vec_ptype_final(out_col)); FREE(1); } } + + FREE(n_prot); } static diff --git a/tests/testthat/test-c.R b/tests/testthat/test-c.R index 6ad4969e3..7081db3a2 100644 --- a/tests/testthat/test-c.R +++ b/tests/testthat/test-c.R @@ -273,8 +273,11 @@ test_that("vec_c() falls back to c() if S3 method is available", { }) test_that("c() fallback is consistent", { + dispatched <- function(x) structure(x, class = "dispatched") + c_method <- function(...) dispatched(NextMethod()) + out <- with_methods( - c.vctrs_foobar = function(...) structure(NextMethod(), class = "dispatched"), + c.vctrs_foobar = c_method, list( direct = vec_c(foobar(1L), foobar(2L)), df = vec_c(data_frame(x = foobar(1L)), data_frame(x = foobar(2L))), @@ -282,13 +285,30 @@ test_that("c() fallback is consistent", { foreign_df = vec_c(foobaz(data_frame(x = foobar(1L))), foobaz(data_frame(x = foobar(2L)))) ) ) + expect_equal(out$direct, dispatched(1:2)) + expect_equal(out$df$x, dispatched(1:2)) + expect_equal(out$tib$x, dispatched(1:2)) + expect_equal(out$foreign_df$x, dispatched(1:2)) + + # Hard case: generic record vectors + my_rec_record <- function(x) { + new_rcrd(list(x = x), class = "my_rec_record") + } - dispatched <- function(x) structure(x, class = "dispatched") - - expect_identical(out$direct, dispatched(1:2)) - expect_identical(out$df$x, dispatched(1:2)) - expect_identical(out$tib$x, dispatched(1:2)) - expect_identical(out$foreign_df$x, dispatched(1:2)) + out <- with_methods( + c.vctrs_foobar = c_method, + vec_ptype2.my_rec_record.my_rec_record = function(x, y, ...) { + my_rec_record(vec_ptype2(field(x, "x"), field(y, "x"), ...)) + }, + vec_cast.my_rec_record.my_rec_record = function(x, to, ...) { + x + }, + vec_c( + data_frame(x = my_rec_record(foobar(1L))), + data_frame(x = my_rec_record(foobar(2L))) + ) + ) + expect_equal(field(out$x, "x"), dispatched(1:2)) }) test_that("vec_c() falls back to c() if S4 method is available", { From b21219cb6d973ff7bee30478598b1e6bea396a82 Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Tue, 11 Oct 2022 13:37:31 +0200 Subject: [PATCH 163/312] Fix base case of fallback recursion E.g. when a `c()` method like `c.vctrs_vctr()` calls back `vec_c()` --- src/c.c | 12 ++++++------ 1 file changed, 6 insertions(+), 6 deletions(-) diff --git a/src/c.c b/src/c.c index 22b369b20..3ae38b237 100644 --- a/src/c.c +++ b/src/c.c @@ -9,7 +9,9 @@ r_obj* vec_c(r_obj* xs, struct r_lazy error_call) { struct fallback_opts opts = { .df = DF_FALLBACK_DEFAULT, - .s3 = S3_FALLBACK_true + .s3 = r_is_true(r_peek_option("vctrs:::base_c_in_progress")) ? + S3_FALLBACK_false : + S3_FALLBACK_true }; return vec_c_opts(xs, ptype, name_spec, name_repair, &opts, p_error_arg, error_call); } @@ -98,9 +100,7 @@ r_obj* vec_c_opts(r_obj* xs, .to = ptype, .p_x_arg = p_x_arg, .call = error_call, - .fallback = { - .s3 = S3_FALLBACK_true - } + .fallback = *fallback_opts }; const struct vec_assign_opts c_assign_opts = { @@ -150,7 +150,7 @@ r_obj* vec_c_opts(r_obj* xs, FREE(1); } - if (is_data_frame(out)) { + if (is_data_frame(out) && fallback_opts->s3) { df_c_fallback(out, ptype, xs, out_size, name_spec, name_repair, error_call); } out = KEEP(vec_restore_recurse(out, ptype, VCTRS_OWNED_true)); @@ -277,7 +277,7 @@ r_obj* vec_c_fallback(r_obj* ptype, bool implements_c = class_implements_base_c(class); FREE(1); - if (implements_c && !r_is_true(r_peek_option("vctrs:::base_c_in_progress"))) { + if (implements_c) { return vec_c_fallback_invoke(xs, name_spec, error_call); } else { struct ptype_common_opts ptype_opts = { From 8c470366bbccfa6333487392b6d777d7d748b569 Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Wed, 19 Oct 2022 09:15:20 +0200 Subject: [PATCH 164/312] Don't fall back to `c()` for subclasses of `vctrs_vctr` --- R/type2.R | 4 ++++ tests/testthat/test-c.R | 25 +++++++++++++++++++++++++ 2 files changed, 29 insertions(+) diff --git a/R/type2.R b/R/type2.R index 8f45d89cf..0d92e1183 100644 --- a/R/type2.R +++ b/R/type2.R @@ -215,6 +215,10 @@ vec_incompatible_ptype2 <- function(x, # class is foreign, because we implement these generics for many base # classes and we still need to allow base fallbacks with subclasses. can_fall_back <- function(x, y) { + if (inherits(x, "vctrs_vctr") || inherits(y, "vctrs_vctr")) { + return(FALSE) + } + # Work around bug with hard-coded `tsp` attribute in Rf_setAttrib() if (inherits(x, "ts") || inherits(y, "ts")) { return(FALSE) diff --git a/tests/testthat/test-c.R b/tests/testthat/test-c.R index 7081db3a2..b190a7be9 100644 --- a/tests/testthat/test-c.R +++ b/tests/testthat/test-c.R @@ -652,3 +652,28 @@ test_that("can combine records wrapped in data frames", { data_frame(x = foobar(1:4)) ) }) + +test_that("fallback works with subclasses of `vctrs_vctr`", { + # Used to fail because of interaction between common class fallback + # for `base::c()` and the `c()` method for `vctrs_vctr` that called + # back into `vec_c()`. + + # Reprex for failure in the ricu package + x <- new_rcrd(list(a = 1), class = "vctrs_foobar") + expect_equal( + vec_c(x, x, .name_spec = "{inner}"), + new_rcrd(list(a = c(1, 1)), class = "vctrs_foobar") + ) + + # Reprex for failure in the groupr package + x <- new_rcrd(list(a = 1), class = "vctrs_foobar") + df <- data_frame(x = x) + expect_equal( + vec_rbind(df, data.frame()), + df + ) + expect_equal( + vec_cast_common(df, data.frame()), + list(df, data_frame(x = x[0])) + ) +}) From f3d9f2c1b313da1d576c62b860b809cf9c70a791 Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Wed, 19 Oct 2022 09:27:16 +0200 Subject: [PATCH 165/312] Refactor `can_fall_back()` into a generic --- NAMESPACE | 5 +++++ R/type2.R | 54 +++++++++++++++++++++++++++++++++++++----------------- 2 files changed, 42 insertions(+), 17 deletions(-) diff --git a/NAMESPACE b/NAMESPACE index 2e5a286bc..e752736e0 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -85,6 +85,11 @@ S3method(as_list_of,list) S3method(as_list_of,vctrs_list_of) S3method(c,vctrs_sclr) S3method(c,vctrs_vctr) +S3method(can_fall_back,"vctrs:::common_class_fallback") +S3method(can_fall_back,data.frame) +S3method(can_fall_back,default) +S3method(can_fall_back,ts) +S3method(can_fall_back,vctrs_vctr) S3method(cnd_body,vctrs_error_cast_lossy) S3method(cnd_body,vctrs_error_incompatible_size) S3method(cnd_body,vctrs_error_matches_incomplete) diff --git a/R/type2.R b/R/type2.R index 0d92e1183..bcb853da1 100644 --- a/R/type2.R +++ b/R/type2.R @@ -140,7 +140,7 @@ vec_default_ptype2 <- function(x, y <- out$y } - if (opts$s3_fallback && can_fall_back(x, y)) { + if (opts$s3_fallback && can_fall_back_2(x, y)) { common <- common_class_suffix(x, y) if (length(common)) { return(new_common_class_fallback(x, common)) @@ -214,32 +214,52 @@ vec_incompatible_ptype2 <- function(x, # We can't check for a proxy or ptype2 method to determine whether a # class is foreign, because we implement these generics for many base # classes and we still need to allow base fallbacks with subclasses. -can_fall_back <- function(x, y) { - if (inherits(x, "vctrs_vctr") || inherits(y, "vctrs_vctr")) { +can_fall_back_2 <- function(x, y) { + if (!identical(typeof(x), typeof(y))) { return(FALSE) } - # Work around bug with hard-coded `tsp` attribute in Rf_setAttrib() - if (inherits(x, "ts") || inherits(y, "ts")) { + if (!can_fall_back(x) || !can_fall_back(y)) { return(FALSE) } - if (is.data.frame(x) || is.data.frame(y)) { - return(FALSE) - } + TRUE +} - if (!identical(typeof(x), typeof(y))) { - return(FALSE) - } +can_fall_back <- function(x) { + UseMethod("can_fall_back") +} + +#' @export +can_fall_back.vctrs_vctr <- function(x) { + # Work aronud bad interaction when `c()` method calls back into `vec_c()` + FALSE +} +#' @export +can_fall_back.ts <- function(x) { + # Work around bug with hard-coded `tsp` attribute in Rf_setAttrib() + FALSE +} +#' @export +can_fall_back.data.frame <- function(x) { + # The `c()` fallback is only for 1D vectors + FALSE +} - # Suboptimal: Prevent bad interaction with proxy-assign - has_no_proxy(x) && has_no_proxy(y) +#' @export +`can_fall_back.vctrs:::common_class_fallback` <- function(x) { + TRUE } -has_no_proxy <- function(x) { - if (inherits(x, "vctrs:::common_class_fallback")) { - return(TRUE) - } +#' @export +can_fall_back.default <- function(x) { + # Don't all back for classes that directly implement a proxy. + # + # NOTE: That's suboptimal. For instance this forces us to override + # `can_fall_back()` for `vctrs_vctr` to avoid recursing into + # `vec_c()` through `c()`. Maybe we want to avoid falling back for + # any vector that inherits a `vec_proxy()` method implemented + # _outside_ of vctrs, i.e. not for a base class? is_null(s3_get_method(class(x)[[1]], "vec_proxy", ns = "vctrs")) } From d3af1e0cd36d52904da556a09b54a8d4b5b310a9 Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Wed, 19 Oct 2022 11:06:42 +0200 Subject: [PATCH 166/312] Update revdeps --- revdep/README.md | 7 --- revdep/cran.md | 16 +------ revdep/problems.md | 104 +-------------------------------------------- 3 files changed, 3 insertions(+), 124 deletions(-) diff --git a/revdep/README.md b/revdep/README.md index 023a28d1c..bf98e2d58 100644 --- a/revdep/README.md +++ b/revdep/README.md @@ -10,10 +10,3 @@ |NA |? | | | | |NA |? | | | | -## New problems (2) - -|package |version |error |warning |note | -|:-------|:-------|:------|:-------|:----| -|[groupr](problems.md#groupr)|0.1.0 |__+1__ |__+1__ |1 | -|[ricu](problems.md#ricu)|0.5.3 |__+1__ | | | - diff --git a/revdep/cran.md b/revdep/cran.md index 020ea8d0c..59788e97a 100644 --- a/revdep/cran.md +++ b/revdep/cran.md @@ -1,19 +1,7 @@ ## revdepcheck results -We checked 199 reverse dependencies (194 from CRAN + 5 from Bioconductor), comparing R CMD check results across CRAN and dev versions of this package. +We checked 202 reverse dependencies (197 from CRAN + 5 from Bioconductor), comparing R CMD check results across CRAN and dev versions of this package. - * We saw 2 new problems + * We saw 0 new problems * We failed to check 0 packages -Issues with CRAN packages are summarised below. - -### New problems -(This reports the first line of each new failure) - -* groupr - checking tests ... ERROR - checking re-building of vignette outputs ... WARNING - -* ricu - checking tests ... ERROR - diff --git a/revdep/problems.md b/revdep/problems.md index 96d31e955..9a2073633 100644 --- a/revdep/problems.md +++ b/revdep/problems.md @@ -1,103 +1 @@ -# groupr - -
- -* Version: 0.1.0 -* GitHub: https://github.com/ngriffiths21/groupr -* Source code: https://github.com/cran/groupr -* Date/Publication: 2020-10-14 12:30:06 UTC -* Number of recursive dependencies: 63 - -Run `cloud_details(, "groupr")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Last 13 lines of output: - Please report it at with a reprex () and the full backtrace. - Backtrace: - ▆ - 1. ├─... %>% group_by2(is_ok, grp) at test_pivots.R:3:0 - 2. ├─groupr::group_by2(., is_ok, grp) - 3. ├─groupr:::group_by2.data.frame(., is_ok, grp) - 4. │ └─groupr:::group_by2_ok(data, dots) - 5. │ └─groupr:::igrouped_df(grouped, groups_out) - 6. │ └─vctrs::vec_rbind(groups, data.frame()) - 7. └─rlang:::stop_internal_c_lib(...) - 8. └─rlang::abort(message, call = call, .internal = TRUE, .frame = frame) - - [ FAIL 3 | WARN 0 | SKIP 0 | PASS 0 ] - Error: Test failures - Execution halted - ``` - -* checking re-building of vignette outputs ... WARNING - ``` - Error(s) in re-building vignettes: - ... - --- re-building ‘introduction.Rmd’ using rmarkdown - Quitting from lines 33-35 (introduction.Rmd) - Error: processing vignette 'introduction.Rmd' failed with diagnostics: - Column `.rows` (size 0) must match the data frame (size 2). - ℹ In file 'slice.c' at line 188. - ℹ This is an internal error that was detected in the vctrs package. - Please report it at with a reprex () and the full backtrace. - --- failed re-building ‘introduction.Rmd’ - - SUMMARY: processing the following file failed: - ‘introduction.Rmd’ - - Error: Vignette re-building failed. - Execution halted - ``` - -## In both - -* checking LazyData ... NOTE - ``` - 'LazyData' is specified without a 'data' directory - ``` - -# ricu - -
- -* Version: 0.5.3 -* GitHub: https://github.com/eth-mds/ricu -* Source code: https://github.com/cran/ricu -* Date/Publication: 2022-07-12 10:50:14 UTC -* Number of recursive dependencies: 114 - -Run `cloud_details(, "ricu")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Last 13 lines of output: - See . - Backtrace: - ▆ - 1. ├─testthat::expect_identical(as_src_cfg(mimic_demo), mi) at test-config.R:19:2 - 2. │ └─testthat::quasi_label(enquo(object), label, arg = "object") - 3. │ └─rlang::eval_bare(expr, quo_get_env(quo)) - 4. ├─ricu::as_src_cfg(mimic_demo) - 5. ├─ricu:::as_src_cfg.src_env(mimic_demo) - 6. │ └─vctrs::vec_unchop(lapply(x, as_col_cfg), name_spec = "{inner}") - 7. │ └─vctrs::list_unchop(...) - 8. └─rlang::abort(message = message, call = call) - - [ FAIL 1 | WARN 1 | SKIP 7 | PASS 592 ] - Error: Test failures - Execution halted - ``` - +*Wow, no problems at all. :)* \ No newline at end of file From 4e5b48d9c5fc2f4acc0cc58f8140fcc1609367d1 Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Wed, 19 Oct 2022 13:37:02 +0200 Subject: [PATCH 167/312] Update revdeps for vctrs + dplyr + tidyr --- revdep/README.md | 41 ++- revdep/cran.md | 29 +- revdep/failures.md | 889 +++++++++++++++++++++++++++++++++++++++++++++ revdep/problems.md | 116 +++++- 4 files changed, 1062 insertions(+), 13 deletions(-) diff --git a/revdep/README.md b/revdep/README.md index bf98e2d58..a8f69affa 100644 --- a/revdep/README.md +++ b/revdep/README.md @@ -1,12 +1,35 @@ # Revdeps -## Failed to check (5) - -|package |version |error |warning |note | -|:-------|:-------|:-----|:-------|:----| -|NA |? | | | | -|NA |? | | | | -|NA |? | | | | -|NA |? | | | | -|NA |? | | | | +## Failed to check (21) + +|package |version |error |warning |note | +|:-------------|:-------|:-----|:-------|:----| +|NA |? | | | | +|elbird |0.2.5 |1 | | | +|ggPMX |? | | | | +|NA |? | | | | +|loon.ggplot |? | | | | +|loon.shiny |? | | | | +|NA |? | | | | +|NA |? | | | | +|NA |? | | | | +|nlmixr2plot |? | | | | +|NA |? | | | | +|NA |? | | | | +|Platypus |? | | | | +|NA |? | | | | +|NA |? | | | | +|NA |? | | | | +|NA |? | | | | +|tidySEM |? | | | | +|NA |? | | | | +|vivid |? | | | | +|xpose.nlmixr2 |? | | | | + +## New problems (2) + +|package |version |error |warning |note | +|:-----------|:-------|:------|:-------|:----| +|[brokenstick](problems.md#brokenstick)|2.3.0 | |__+1__ | | +|[psfmi](problems.md#psfmi)|1.0.0 |__+1__ |__+1__ |1 | diff --git a/revdep/cran.md b/revdep/cran.md index 59788e97a..9b6513d08 100644 --- a/revdep/cran.md +++ b/revdep/cran.md @@ -1,7 +1,30 @@ ## revdepcheck results -We checked 202 reverse dependencies (197 from CRAN + 5 from Bioconductor), comparing R CMD check results across CRAN and dev versions of this package. +We checked 3546 reverse dependencies (3534 from CRAN + 12 from Bioconductor), comparing R CMD check results across CRAN and dev versions of this package. - * We saw 0 new problems - * We failed to check 0 packages + * We saw 2 new problems + * We failed to check 9 packages +Issues with CRAN packages are summarised below. + +### New problems +(This reports the first line of each new failure) + +* brokenstick + checking re-building of vignette outputs ... WARNING + +* psfmi + checking examples ... ERROR + checking re-building of vignette outputs ... WARNING + +### Failed to check + +* elbird (NA) +* ggPMX (NA) +* loon.ggplot (NA) +* loon.shiny (NA) +* nlmixr2plot (NA) +* Platypus (NA) +* tidySEM (NA) +* vivid (NA) +* xpose.nlmixr2 (NA) diff --git a/revdep/failures.md b/revdep/failures.md index fd10f3c24..72ebd3a9b 100644 --- a/revdep/failures.md +++ b/revdep/failures.md @@ -32,6 +32,144 @@ Run `cloud_details(, "NA")` for more info +``` +# elbird + +
+ +* Version: 0.2.5 +* GitHub: https://github.com/mrchypark/elbird +* Source code: https://github.com/cran/elbird +* Date/Publication: 2022-08-12 15:50:02 UTC +* Number of recursive dependencies: 54 + +Run `cloud_details(, "elbird")` for more info + +
+ +## In both + +* checking whether package ‘elbird’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/elbird/new/elbird.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘elbird’ ... +** package ‘elbird’ successfully unpacked and MD5 sums checked +** using staged installation +/usr/bin/uname +Prior system libkiwi installation not found +Preparing to download and build library from source... +------------------------------[ ELBIRD ]------------------------------ +Configuration failed because 'git' was not found. +If you want to kiwi build from source in package installation prosess, +make sure git and cmake work in system. +------------------------------------------------------------------------- +ERROR: configuration failed for package ‘elbird’ +* removing ‘/tmp/workdir/elbird/new/elbird.Rcheck/elbird’ + + +``` +### CRAN + +``` +* installing *source* package ‘elbird’ ... +** package ‘elbird’ successfully unpacked and MD5 sums checked +** using staged installation +/usr/bin/uname +Prior system libkiwi installation not found +Preparing to download and build library from source... +------------------------------[ ELBIRD ]------------------------------ +Configuration failed because 'git' was not found. +If you want to kiwi build from source in package installation prosess, +make sure git and cmake work in system. +------------------------------------------------------------------------- +ERROR: configuration failed for package ‘elbird’ +* removing ‘/tmp/workdir/elbird/old/elbird.Rcheck/elbird’ + + +``` +# ggPMX + +
+ +* Version: 1.2.8 +* GitHub: https://github.com/ggPMXdevelopment/ggPMX +* Source code: https://github.com/cran/ggPMX +* Date/Publication: 2022-06-17 23:10:02 UTC +* Number of recursive dependencies: 172 + +Run `cloud_details(, "ggPMX")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/ggPMX/new/ggPMX.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘ggPMX/DESCRIPTION’ ... OK +* this is package ‘ggPMX’ version ‘1.2.8’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... NOTE +... + [ FAIL 1 | WARN 11 | SKIP 8 | PASS 327 ] + 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 ... NONE + ‘ggPMX-guide.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 1 ERROR, 2 NOTEs + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/ggPMX/old/ggPMX.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘ggPMX/DESCRIPTION’ ... OK +* this is package ‘ggPMX’ version ‘1.2.8’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... NOTE +... + [ FAIL 1 | WARN 11 | SKIP 8 | PASS 327 ] + 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 ... NONE + ‘ggPMX-guide.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 1 ERROR, 2 NOTEs + + + + + ``` # NA @@ -67,6 +205,146 @@ Run `cloud_details(, "NA")` for more info +``` +# loon.ggplot + +
+ +* Version: 1.3.2 +* GitHub: https://github.com/great-northern-diver/loon.ggplot +* Source code: https://github.com/cran/loon.ggplot +* Date/Publication: 2022-10-03 14:50:02 UTC +* Number of recursive dependencies: 104 + +Run `cloud_details(, "loon.ggplot")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/loon.ggplot/new/loon.ggplot.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘loon.ggplot/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘loon.ggplot’ version ‘1.3.2’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘loon’ + +Package suggested but not available for checking: ‘zenplots’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/loon.ggplot/old/loon.ggplot.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘loon.ggplot/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘loon.ggplot’ version ‘1.3.2’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘loon’ + +Package suggested but not available for checking: ‘zenplots’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# loon.shiny + +
+ +* Version: 1.0.3 +* GitHub: NA +* Source code: https://github.com/cran/loon.shiny +* Date/Publication: 2022-10-08 15:30:02 UTC +* Number of recursive dependencies: 132 + +Run `cloud_details(, "loon.shiny")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/loon.shiny/new/loon.shiny.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘loon.shiny/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘loon.shiny’ version ‘1.0.3’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Packages required but not available: 'loon', 'loon.ggplot' + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/loon.shiny/old/loon.shiny.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘loon.shiny/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘loon.shiny’ version ‘1.0.3’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Packages required but not available: 'loon', 'loon.ggplot' + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + ``` # NA @@ -172,4 +450,615 @@ Run `cloud_details(, "NA")` for more info +``` +# nlmixr2plot + +
+ +* Version: 2.0.6 +* GitHub: https://github.com/nlmixr2/nlmixr2plot +* Source code: https://github.com/cran/nlmixr2plot +* Date/Publication: 2022-05-23 07:50:02 UTC +* Number of recursive dependencies: 155 + +Run `cloud_details(, "nlmixr2plot")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/nlmixr2plot/new/nlmixr2plot.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘nlmixr2plot/DESCRIPTION’ ... OK +* this is package ‘nlmixr2plot’ version ‘2.0.6’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Packages required but not available: 'nlmixr2est', 'nlmixr2extra' + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/nlmixr2plot/old/nlmixr2plot.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘nlmixr2plot/DESCRIPTION’ ... OK +* this is package ‘nlmixr2plot’ version ‘2.0.6’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Packages required but not available: 'nlmixr2est', 'nlmixr2extra' + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# NA + +
+ +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/NA +* Number of recursive dependencies: 0 + +Run `cloud_details(, "NA")` for more info + +
+ +## Error before installation + +### Devel + +``` + + + + + + +``` +### CRAN + +``` + + + + + + +``` +# NA + +
+ +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/NA +* Number of recursive dependencies: 0 + +Run `cloud_details(, "NA")` for more info + +
+ +## Error before installation + +### Devel + +``` + + + + + + +``` +### CRAN + +``` + + + + + + +``` +# Platypus + +
+ +* Version: 3.4.1 +* GitHub: NA +* Source code: https://github.com/cran/Platypus +* Date/Publication: 2022-08-15 07:20:20 UTC +* Number of recursive dependencies: 355 + +Run `cloud_details(, "Platypus")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/Platypus/new/Platypus.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘Platypus/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘Platypus’ version ‘3.4.1’ +* package encoding: UTF-8 +* checking package namespace information ... 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 + ‘PlatypusV3_agedCNS.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 1 NOTE + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/Platypus/old/Platypus.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘Platypus/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘Platypus’ version ‘3.4.1’ +* package encoding: UTF-8 +* checking package namespace information ... 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 + ‘PlatypusV3_agedCNS.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 1 NOTE + + + + + +``` +# NA + +
+ +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/NA +* Number of recursive dependencies: 0 + +Run `cloud_details(, "NA")` for more info + +
+ +## Error before installation + +### Devel + +``` + + + + + + +``` +### CRAN + +``` + + + + + + +``` +# NA + +
+ +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/NA +* Number of recursive dependencies: 0 + +Run `cloud_details(, "NA")` for more info + +
+ +## Error before installation + +### Devel + +``` + + + + + + +``` +### CRAN + +``` + + + + + + +``` +# NA + +
+ +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/NA +* Number of recursive dependencies: 0 + +Run `cloud_details(, "NA")` for more info + +
+ +## Error before installation + +### Devel + +``` + + + + + + +``` +### CRAN + +``` + + + + + + +``` +# NA + +
+ +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/NA +* Number of recursive dependencies: 0 + +Run `cloud_details(, "NA")` for more info + +
+ +## Error before installation + +### Devel + +``` + + + + + + +``` +### CRAN + +``` + + + + + + +``` +# tidySEM + +
+ +* Version: 0.2.3 +* GitHub: https://github.com/cjvanlissa/tidySEM +* Source code: https://github.com/cran/tidySEM +* Date/Publication: 2022-04-14 17:50:02 UTC +* Number of recursive dependencies: 170 + +Run `cloud_details(, "tidySEM")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/tidySEM/new/tidySEM.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘tidySEM/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘tidySEM’ version ‘0.2.3’ +* package encoding: UTF-8 +* checking package namespace information ... OK +... +* checking for unstated dependencies in vignettes ... OK +* checking package vignettes in ‘inst/doc’ ... OK +* checking running R code from vignettes ... NONE + ‘Generating_syntax.Rmd’ using ‘UTF-8’... OK + ‘Plotting_graphs.Rmd’ using ‘UTF-8’... OK + ‘Tabulating_results.Rmd’ using ‘UTF-8’... OK + ‘sem_graph.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 1 NOTE + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/tidySEM/old/tidySEM.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘tidySEM/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘tidySEM’ version ‘0.2.3’ +* package encoding: UTF-8 +* checking package namespace information ... OK +... +* checking for unstated dependencies in vignettes ... OK +* checking package vignettes in ‘inst/doc’ ... OK +* checking running R code from vignettes ... NONE + ‘Generating_syntax.Rmd’ using ‘UTF-8’... OK + ‘Plotting_graphs.Rmd’ using ‘UTF-8’... OK + ‘Tabulating_results.Rmd’ using ‘UTF-8’... OK + ‘sem_graph.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 1 NOTE + + + + + +``` +# NA + +
+ +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/NA +* Number of recursive dependencies: 0 + +Run `cloud_details(, "NA")` for more info + +
+ +## Error before installation + +### Devel + +``` + + + + + + +``` +### CRAN + +``` + + + + + + +``` +# vivid + +
+ +* Version: 0.2.3 +* GitHub: NA +* Source code: https://github.com/cran/vivid +* Date/Publication: 2021-11-20 01:30:02 UTC +* Number of recursive dependencies: 201 + +Run `cloud_details(, "vivid")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/vivid/new/vivid.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘vivid/DESCRIPTION’ ... OK +* this is package ‘vivid’ version ‘0.2.3’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... NOTE +... +* 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 + ‘vivid.Rmd’ using ‘UTF-8’... OK + ‘vividQStart.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 2 NOTEs + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/vivid/old/vivid.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘vivid/DESCRIPTION’ ... OK +* this is package ‘vivid’ version ‘0.2.3’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... NOTE +... +* 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 + ‘vivid.Rmd’ using ‘UTF-8’... OK + ‘vividQStart.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 2 NOTEs + + + + + +``` +# xpose.nlmixr2 + +
+ +* Version: 0.4.0 +* GitHub: NA +* Source code: https://github.com/cran/xpose.nlmixr2 +* Date/Publication: 2022-06-08 09:10:02 UTC +* Number of recursive dependencies: 149 + +Run `cloud_details(, "xpose.nlmixr2")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/xpose.nlmixr2/new/xpose.nlmixr2.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘xpose.nlmixr2/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘xpose.nlmixr2’ version ‘0.4.0’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘nlmixr2est’ + +Package suggested but not available for checking: ‘nlmixr2’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/xpose.nlmixr2/old/xpose.nlmixr2.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘xpose.nlmixr2/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘xpose.nlmixr2’ version ‘0.4.0’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘nlmixr2est’ + +Package suggested but not available for checking: ‘nlmixr2’ + +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 9a2073633..0735483f1 100644 --- a/revdep/problems.md +++ b/revdep/problems.md @@ -1 +1,115 @@ -*Wow, no problems at all. :)* \ No newline at end of file +# brokenstick + +
+ +* Version: 2.3.0 +* GitHub: https://github.com/growthcharts/brokenstick +* Source code: https://github.com/cran/brokenstick +* Date/Publication: 2022-09-07 22:23:04 UTC +* Number of recursive dependencies: 92 + +Run `cloud_details(, "brokenstick")` for more info + +
+ +## Newly broken + +* checking re-building of vignette outputs ... WARNING + ``` + Error(s) in re-building vignettes: + --- re-building ‘brokenstick.Rmd’ using rmarkdown + --- finished re-building ‘brokenstick.Rmd’ + + --- re-building ‘mainfunctions.Rmd’ using rmarkdown + Loading required package: brokenstick + Loading required package: dplyr + + Attaching package: 'dplyr' + + ... + --- failed re-building ‘oldfriends.Rmd’ + + --- re-building ‘perfectmodel.Rmd’ using rmarkdown + --- finished re-building ‘perfectmodel.Rmd’ + + SUMMARY: processing the following files failed: + ‘mainfunctions.Rmd’ ‘oldfriends.Rmd’ + + Error: Vignette re-building failed. + Execution halted + ``` + +# psfmi + +
+ +* Version: 1.0.0 +* GitHub: https://github.com/mwheymans/psfmi +* Source code: https://github.com/cran/psfmi +* Date/Publication: 2021-09-23 10:10:05 UTC +* Number of recursive dependencies: 156 + +Run `cloud_details(, "psfmi")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘psfmi-Ex.R’ failed + The error most likely occurred in: + + > ### Name: psfmi_validate + > ### Title: Internal validation and performance of logistic prediction + > ### models across Multiply Imputed datasets + > ### Aliases: psfmi_validate + > + > ### ** Examples + > + ... + ! `strata` should be a single name or character value. + Backtrace: + ▆ + 1. └─psfmi::psfmi_validate(...) + 2. └─psfmi::cv_MI(...) + 3. ├─purrr::map(...) + 4. └─rsample::vfold_cv(data_orig, v = folds, strata = unlist(data_orig[pobj$Outcome])) + 5. └─rsample:::strata_check(strata, data) + 6. └─rlang::abort("`strata` should be a single name or character value.") + Execution halted + ``` + +* checking re-building of vignette outputs ... WARNING + ``` + Error(s) in re-building vignettes: + --- re-building ‘MI_boot.Rmd’ using rmarkdown + --- finished re-building ‘MI_boot.Rmd’ + + --- re-building ‘MI_cv_naive.Rmd’ using rmarkdown + --- finished re-building ‘MI_cv_naive.Rmd’ + + --- re-building ‘Pool_Model_Performance.Rmd’ using rmarkdown + --- finished re-building ‘Pool_Model_Performance.Rmd’ + + ... + --- finished re-building ‘psfmi_StabilityAnalysis.Rmd’ + + --- re-building ‘psfmi_mice.Rmd’ using rmarkdown + --- finished re-building ‘psfmi_mice.Rmd’ + + SUMMARY: processing the following files failed: + ‘cv_MI.Rmd’ ‘cv_MI_RR.Rmd’ ‘development_workflow.Rmd’ + + Error: Vignette re-building failed. + Execution halted + ``` + +## In both + +* checking dependencies in R code ... NOTE + ``` + Namespace in Imports field not imported from: ‘miceadds’ + All declared Imports should be used. + ``` + From 0c537e278d8d2a4ed6643bd6fc562f89ba647f3a Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Wed, 19 Oct 2022 16:25:50 +0200 Subject: [PATCH 168/312] Assign `.names_to` after restoration Part of #1732 --- src/bind.c | 6 +++--- tests/testthat/test-bind.R | 12 ++++++++++++ 2 files changed, 15 insertions(+), 3 deletions(-) diff --git a/src/bind.c b/src/bind.c index cdd8bb65f..fee0144f6 100644 --- a/src/bind.c +++ b/src/bind.c @@ -242,14 +242,14 @@ r_obj* vec_rbind(r_obj* xs, r_attrib_poke(out, r_syms.row_names, row_names); } + df_c_fallback(out, ptype, xs, n_rows, name_spec, name_repair, error_call); + out = vec_restore_recurse(out, ptype, VCTRS_OWNED_true); + if (has_names_to) { out = df_poke(out, names_to_loc, names_to_col); KEEP_AT(out, out_pi); } - df_c_fallback(out, ptype, xs, n_rows, name_spec, name_repair, error_call); - out = vec_restore_recurse(out, ptype, VCTRS_OWNED_true); - FREE(n_prot); return out; } diff --git a/tests/testthat/test-bind.R b/tests/testthat/test-bind.R index b067bcb5c..84e7d7c39 100644 --- a/tests/testthat/test-bind.R +++ b/tests/testthat/test-bind.R @@ -1202,3 +1202,15 @@ test_that("row-binding performs expected allocations", { with_memory_prof(vec_rbind_list(dfs)) }) }) + +test_that("`.names_to` is assigned after restoration (#1648)", { + df <- data_frame(x = factor("foo")) + expect_equal( + vec_rbind(name = df, .names_to = "x"), + data_frame(x = "name") + ) + + # This used to fail with: + #> Error in `vctrs::vec_rbind()`: + #> ! adding class "factor" to an invalid object +}) From a45eebd21a78ed0f907d126b842762cc8d433ce8 Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Fri, 14 Oct 2022 14:06:22 +0200 Subject: [PATCH 169/312] Simplify data frame fallback --- R/cast.R | 16 ++----------- R/type-data-frame.R | 48 -------------------------------------- R/type2.R | 46 ++++++++---------------------------- tests/testthat/test-bind.R | 2 +- 4 files changed, 13 insertions(+), 99 deletions(-) diff --git a/R/cast.R b/R/cast.R index 34d11d90a..0bfffdcd1 100644 --- a/R/cast.R +++ b/R/cast.R @@ -192,24 +192,12 @@ vec_default_cast <- function(x, return(x) } - # If both data frames, first find the `to` type of columns before - # the same-type fallback - if (df_needs_normalisation(x, to, opts)) { - x <- vec_cast_df_fallback_normalise( - x, - to, - opts, - x_arg = x_arg, - to_arg = to_arg, - call = call - ) - } - if (is_same_type(x, to)) { return(x) } - if (has_df_fallback(opts$df_fallback) && is_df_subclass(x) && is.data.frame(to)) { + # If both data frames, fall back to base data frame + if (is.data.frame(x) && is.data.frame(to)) { out <- df_cast_opts( x, to, diff --git a/R/type-data-frame.R b/R/type-data-frame.R index 18f824dc3..c3071c46d 100644 --- a/R/type-data-frame.R +++ b/R/type-data-frame.R @@ -312,54 +312,6 @@ vec_ptype2.data.frame.data.frame <- function(x, y, ...) { df_ptype2(x, y, ...) } -vec_ptype2_df_fallback_normalise <- function(x, y, opts, ...) { - x_orig <- x - y_orig <- y - - ptype <- df_ptype2_opts(x, y, opts = opts, ...) - - x <- x[0, , drop = FALSE] - y <- y[0, , drop = FALSE] - - x[seq_along(ptype)] <- ptype - y[seq_along(ptype)] <- ptype - - # Names might have been repaired by `[<-` - names(x) <- names(ptype) - names(y) <- names(ptype) - - # Restore attributes if no `[` method is implemented - if (df_has_base_subset(x)) { - x <- vec_restore(x, x_orig) - } - if (df_has_base_subset(y)) { - y <- vec_restore(y, y_orig) - } - - list(x = x, y = y) -} -vec_cast_df_fallback_normalise <- function(x, to, opts, ...) { - orig <- x - cast <- df_cast_opts(x, to, opts = opts, ...) - - # Seq-assign should be more widely implemented than empty-assign? - x[seq_along(to)] <- cast - - # Names might have been repaired by `[<-` - names(x) <- names(cast) - - # Restore attributes if no `[` method is implemented - if (df_has_base_subset(x)) { - x <- vec_restore(x, orig) - } - - x -} - -df_needs_normalisation <- function(x, y, opts) { - is.data.frame(x) && is.data.frame(y) && df_is_coercible(x, y, opts) -} - # Fallback for data frame subclasses (#981) vec_ptype2_df_fallback <- function(x, y, diff --git a/R/type2.R b/R/type2.R index bcb853da1..ac3406d2d 100644 --- a/R/type2.R +++ b/R/type2.R @@ -125,21 +125,6 @@ vec_default_ptype2 <- function(x, opts <- match_fallback_opts(...) - # If both data frames, first find common type of columns before the - # same-type fallback - if (df_needs_normalisation(x, y, opts)) { - out <- vec_ptype2_df_fallback_normalise( - x, - y, - opts, - x_arg = x_arg, - y_arg = y_arg, - call = call - ) - x <- out$x - y <- out$y - } - if (opts$s3_fallback && can_fall_back_2(x, y)) { common <- common_class_suffix(x, y) if (length(common)) { @@ -151,27 +136,15 @@ vec_default_ptype2 <- function(x, return(vec_ptype(x, x_arg = x_arg)) } - if (has_df_fallback(opts$df_fallback)) { - if (is_df_subclass(x) && is.data.frame(y)) { - return(vec_ptype2_df_fallback( - x, - y, - opts, - x_arg = x_arg, - y_arg = y_arg, - call = call - )) - } - if (is_df_subclass(y) && is.data.frame(x)) { - return(vec_ptype2_df_fallback( - x, - y, - opts, - x_arg = x_arg, - y_arg = y_arg, - call = call - )) - } + if (is.data.frame(x) && is.data.frame(y)) { + return(vec_ptype2_df_fallback( + x, + y, + opts, + x_arg = x_arg, + y_arg = y_arg, + call = call + )) } # The from-dispatch parameter is set only when called from our S3 @@ -392,6 +365,7 @@ S3_FALLBACK_true <- 1L has_df_fallback <- function(df_fallback) { df_fallback != DF_FALLBACK_none } +# TODO: Remove? needs_fallback_warning <- function(df_fallback) { if (df_fallback == DF_FALLBACK_warn_maybe) { is_true(peek_option("vctrs:::warn_on_fallback")) diff --git a/tests/testthat/test-bind.R b/tests/testthat/test-bind.R index 84e7d7c39..0cb49d06e 100644 --- a/tests/testthat/test-bind.R +++ b/tests/testthat/test-bind.R @@ -855,7 +855,7 @@ test_that("vec_rbind() falls back to c() if S3 method is available", { bar_df <- foobaz(y_df) out <- with_c_method(vec_rbind(foo_df, bar_df)) - exp <- foobaz(data_frame(x = quux(c(1, 2)))) + exp <- data_frame(x = quux(c(1, 2))) expect_identical(out, exp) expect_identical(with_c_method(vec_c(foo_df, bar_df)), exp) From 8af4dd34579d100b4b93c40f503d72bfdba2b9c8 Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Fri, 14 Oct 2022 14:24:11 +0200 Subject: [PATCH 170/312] Remove df-fallback infrastructure --- R/cast.R | 11 ++- R/compare.R | 6 +- R/equal.R | 6 +- R/type-data-frame.R | 89 +++--------------------- R/type.R | 2 - R/type2.R | 40 +---------- src/bind.c | 3 - src/c-unchop.c | 1 - src/c.c | 2 - src/cast.c | 12 +--- src/cast.h | 3 - src/dictionary.c | 6 -- src/interval.c | 11 --- src/match.c | 3 - src/ptype-common.c | 3 - src/ptype-common.h | 1 - src/ptype.c | 20 +----- src/ptype2-dispatch.c | 23 +++--- src/ptype2.c | 3 +- src/ptype2.h | 17 +---- src/type-data-frame.h | 8 +-- src/utils.c | 1 - src/utils.h | 1 - tests/testthat/_snaps/type-data-frame.md | 86 +---------------------- tests/testthat/_snaps/type2.md | 56 +-------------- tests/testthat/helper-expectations.R | 22 ------ tests/testthat/helper-vctrs.R | 11 --- tests/testthat/test-cast.R | 2 +- tests/testthat/test-type-data-frame.R | 12 ++-- tests/testthat/test-type-misc.R | 8 +-- tests/testthat/test-type2.R | 59 ++++------------ 31 files changed, 63 insertions(+), 465 deletions(-) diff --git a/R/cast.R b/R/cast.R index 0bfffdcd1..cc1eb65d9 100644 --- a/R/cast.R +++ b/R/cast.R @@ -82,9 +82,6 @@ vec_cast_dispatch <- function(x, to, ..., x_arg = "", to_arg = "") { UseMethod("vec_cast", to) } -vec_cast_no_fallback <- function(x, to) { - vec_cast_common_params(x = x, .to = to, .df_fallback = DF_FALLBACK_none)$x -} vec_cast_dispatch_native <- function(x, to, ..., @@ -119,12 +116,10 @@ vec_cast_common_opts <- function(..., } vec_cast_common_params <- function(..., .to = NULL, - .df_fallback = NULL, .s3_fallback = NULL, .arg = "", .call = caller_env()) { opts <- fallback_opts( - df_fallback = .df_fallback, s3_fallback = .s3_fallback ) vec_cast_common_opts( @@ -197,7 +192,7 @@ vec_default_cast <- function(x, } # If both data frames, fall back to base data frame - if (is.data.frame(x) && is.data.frame(to)) { + if (is.data.frame(x) && is_bare_df(to)) { out <- df_cast_opts( x, to, @@ -230,6 +225,10 @@ vec_default_cast <- function(x, ) } +is_bare_df <- function(x) { + inherits_only(x, "data.frame") || inherits_only(x, c("tbl_df", "tbl", "data.frame")) +} + is_informative_error.vctrs_error_cast_lossy <- function(x, ...) { FALSE } diff --git a/R/compare.R b/R/compare.R index 5ece20a15..56e790f19 100644 --- a/R/compare.R +++ b/R/compare.R @@ -117,11 +117,7 @@ vec_compare <- function(x, y, na_equal = FALSE, .ptype = NULL) { vec_assert(na_equal, ptype = logical(), size = 1L) args <- vec_recycle_common(x, y) - args <- vec_cast_common_params( - !!!args, - .to = .ptype, - .df_fallback = DF_FALLBACK_quiet - ) + args <- vec_cast_common_params(!!!args, .to = .ptype) .Call(ffi_vec_compare, vec_proxy_compare(args[[1]]), vec_proxy_compare(args[[2]]), na_equal) } diff --git a/R/equal.R b/R/equal.R index 75e16c027..0f5dbff34 100644 --- a/R/equal.R +++ b/R/equal.R @@ -66,11 +66,7 @@ vec_proxy_equal.default <- function(x, ...) { vec_equal <- function(x, y, na_equal = FALSE, .ptype = NULL) { vec_assert(na_equal, ptype = logical(), size = 1L) args <- vec_recycle_common(x, y) - args <- vec_cast_common_params( - !!!args, - .to = .ptype, - .df_fallback = DF_FALLBACK_quiet - ) + args <- vec_cast_common_params(!!!args, .to = .ptype) .Call(vctrs_equal, args[[1]], args[[2]], na_equal) } diff --git a/R/type-data-frame.R b/R/type-data-frame.R index c3071c46d..77e04f65b 100644 --- a/R/type-data-frame.R +++ b/R/type-data-frame.R @@ -281,12 +281,8 @@ df_cast_params <- function(x, ..., x_arg = "", to_arg = "", - df_fallback = NULL, s3_fallback = NULL) { - opts <- fallback_opts( - df_fallback = df_fallback, - s3_fallback = s3_fallback - ) + opts <- fallback_opts(s3_fallback = s3_fallback) df_cast_opts(x, to, opts = opts, x_arg = x_arg, to_arg = to_arg) } @@ -319,91 +315,22 @@ vec_ptype2_df_fallback <- function(x, x_arg = "", y_arg = "", call = caller_env()) { - seen_tibble <- inherits(x, "tbl_df") || inherits(y, "tbl_df") - - ptype <- vec_ptype2_params( - new_data_frame(x), - new_data_frame(y), - df_fallback = opts$df_fallback, + vec_ptype2_params( + as_base_df(x), + as_base_df(y), s3_fallback = opts$s3_fallback, + x_arg = x_arg, + y_arg = y_arg, call = call ) - - classes <- NULL - if (is_df_fallback(x)) { - classes <- c(classes, known_classes(x)) - x <- df_fallback_as_df(x) - } - if (is_df_fallback(y)) { - classes <- c(classes, known_classes(y)) - y <- df_fallback_as_df(y) - } - x_class <- class(x)[[1]] - y_class <- class(y)[[1]] - - if (needs_fallback_warning(opts$df_fallback) && - !all(c(x_class, y_class) %in% c(classes, "tbl_df"))) { - fallback_class <- if (seen_tibble) "" else "" - msg <- cnd_type_message( - x, y, - x_arg, y_arg, - NULL, - "combine", - NULL, - fallback = fallback_class - ) - - if (identical(x_class, y_class)) { - msg <- c( - msg, - incompatible_attrib_bullets() - ) - } - - warn(msg) - } - - # Return a fallback class so we don't warn multiple times. This - # fallback class is stripped in `vec_ptype_finalise()`. - new_fallback_df( - ptype, - known_classes = unique(c(classes, x_class, y_class)), - seen_tibble = seen_tibble - ) -} - -is_df_subclass <- function(x) { - inherits(x, "data.frame") && !identical(class(x), "data.frame") -} -is_df_fallback <- function(x) { - inherits(x, "vctrs:::df_fallback") -} -new_fallback_df <- function(x, known_classes, seen_tibble = FALSE, n = nrow(x)) { - class <- "vctrs:::df_fallback" - if (seen_tibble) { - class <- c(class, "tbl_df", "tbl") - } - - new_data_frame( - x, - n = n, - known_classes = known_classes, - seen_tibble = seen_tibble, - class = class - ) } -df_fallback_as_df <- function(x) { +as_base_df <- function(x) { if (inherits(x, "tbl_df")) { - new_data_frame(x, class = c("tbl_df", "tbl", "data.frame")) + new_data_frame(x, class = c("tbl_df", "tbl")) } else { new_data_frame(x) } } -known_classes <- function(x) { - if (is_df_fallback(x)) { - attr(x, "known_classes") - } -} # Cast -------------------------------------------------------------------- diff --git a/R/type.R b/R/type.R index f985d4395..4f3058ee1 100644 --- a/R/type.R +++ b/R/type.R @@ -122,11 +122,9 @@ vec_ptype_common_opts <- function(..., } vec_ptype_common_params <- function(..., .ptype = NULL, - .df_fallback = NULL, .s3_fallback = NULL, .call = caller_env()) { opts <- fallback_opts( - df_fallback = .df_fallback, s3_fallback = .s3_fallback ) vec_ptype_common_opts( diff --git a/R/type2.R b/R/type2.R index ac3406d2d..c06b33f25 100644 --- a/R/type2.R +++ b/R/type2.R @@ -264,15 +264,11 @@ fallback_class <- function(x) { check_ptype2_dots_empty <- function(..., `vctrs:::from_dispatch`, - `vctrs:::df_fallback`, `vctrs:::s3_fallback`) { check_dots_empty0(...) } -match_fallback_opts <- function(..., - `vctrs:::df_fallback` = NULL, - `vctrs:::s3_fallback` = NULL) { +match_fallback_opts <- function(..., `vctrs:::s3_fallback` = NULL) { fallback_opts( - df_fallback = `vctrs:::df_fallback`, s3_fallback = `vctrs:::s3_fallback` ) } @@ -280,18 +276,15 @@ match_from_dispatch <- function(..., `vctrs:::from_dispatch` = FALSE) { `vctrs:::from_dispatch` } -fallback_opts <- function(df_fallback = NULL, - s3_fallback = NULL) { +fallback_opts <- function(s3_fallback = NULL) { # Order is important for the C side list( - df_fallback = df_fallback %||% df_fallback_default(), s3_fallback = s3_fallback %||% s3_fallback_default() ) } full_fallback_opts <- function() { fallback_opts( - df_fallback = DF_FALLBACK_quiet, s3_fallback = S3_FALLBACK_true ) } @@ -308,13 +301,11 @@ vec_ptype2_opts <- function(x, vec_ptype2_params <- function(x, y, ..., - df_fallback = NULL, s3_fallback = NULL, x_arg = "", y_arg = "", call = caller_env()) { opts <- fallback_opts( - df_fallback = df_fallback, s3_fallback = s3_fallback ) vec_ptype2_opts( @@ -334,7 +325,6 @@ vec_ptype2_no_fallback <- function(x, y_arg = "", call = caller_env()) { opts <- fallback_opts( - df_fallback = DF_FALLBACK_none, s3_fallback = S3_FALLBACK_false ) vec_ptype2_opts( @@ -349,37 +339,11 @@ vec_ptype2_no_fallback <- function(x, ) } - -# Kept in sync with ptype2.h -df_fallback_default <- function() 0L -DF_FALLBACK_warn_maybe <- 0L -DF_FALLBACK_warn <- 1L -DF_FALLBACK_none <- 2L -DF_FALLBACK_quiet <- 3L - s3_fallback_default <- function() 0L S3_FALLBACK_false <- 0L S3_FALLBACK_true <- 1L -has_df_fallback <- function(df_fallback) { - df_fallback != DF_FALLBACK_none -} -# TODO: Remove? -needs_fallback_warning <- function(df_fallback) { - if (df_fallback == DF_FALLBACK_warn_maybe) { - is_true(peek_option("vctrs:::warn_on_fallback")) - } else { - df_fallback == DF_FALLBACK_warn - } -} -with_fallback_warning <- function(expr) { - with_options(expr, `vctrs:::warn_on_fallback` = TRUE) -} -with_fallback_quiet <- function(expr) { - with_options(expr, `vctrs:::warn_on_fallback` = FALSE) -} - vec_typeof2 <- function(x, y) { .Call(ffi_typeof2, x, y) } diff --git a/src/bind.c b/src/bind.c index fee0144f6..506024be6 100644 --- a/src/bind.c +++ b/src/bind.c @@ -67,7 +67,6 @@ r_obj* vec_rbind(r_obj* xs, // before assignment. ptype = vec_ptype_common_params(xs, ptype, - DF_FALLBACK_DEFAULT, S3_FALLBACK_true, p_arg, error_call); @@ -118,7 +117,6 @@ r_obj* vec_rbind(r_obj* xs, // Must happen after the `names_to` column has been added to `ptype` xs = vec_cast_common_params(xs, ptype, - DF_FALLBACK_DEFAULT, S3_FALLBACK_true, vec_args.empty, error_call); @@ -387,7 +385,6 @@ r_obj* vec_cbind(r_obj* xs, r_obj* type = KEEP(vec_ptype_common_params(containers, ptype, - DF_FALLBACK_DEFAULT, S3_FALLBACK_false, p_arg, error_call)); diff --git a/src/c-unchop.c b/src/c-unchop.c index 84c0d5a31..4d1da6cf5 100644 --- a/src/c-unchop.c +++ b/src/c-unchop.c @@ -35,7 +35,6 @@ r_obj* list_unchop(r_obj* xs, ptype = KEEP(vec_ptype_common_params(xs, ptype, - DF_FALLBACK_DEFAULT, S3_FALLBACK_true, p_error_arg, error_call)); diff --git a/src/c.c b/src/c.c index 3ae38b237..e090b445b 100644 --- a/src/c.c +++ b/src/c.c @@ -8,7 +8,6 @@ r_obj* vec_c(r_obj* xs, struct vctrs_arg* p_error_arg, struct r_lazy error_call) { struct fallback_opts opts = { - .df = DF_FALLBACK_DEFAULT, .s3 = r_is_true(r_peek_option("vctrs:::base_c_in_progress")) ? S3_FALLBACK_false : S3_FALLBACK_true @@ -284,7 +283,6 @@ r_obj* vec_c_fallback(r_obj* ptype, .p_arg = p_error_arg, .call = error_call, .fallback = { - .df = DF_FALLBACK_none, .s3 = S3_FALLBACK_false } }; diff --git a/src/cast.c b/src/cast.c index e12630799..eef768bfa 100644 --- a/src/cast.c +++ b/src/cast.c @@ -134,23 +134,21 @@ r_obj* vec_cast_default_full(r_obj* x, struct r_lazy call, const struct fallback_opts* opts, bool from_dispatch) { - r_obj* df_fallback = KEEP(r_int(opts->df)); r_obj* s3_fallback = KEEP(r_int(opts->s3)); r_obj* ffi_x_arg = KEEP(vctrs_arg(p_x_arg)); r_obj* ffi_to_arg = KEEP(vctrs_arg(p_to_arg)); r_obj* ffi_call = KEEP(r_lazy_eval(call)); - r_obj* out = vctrs_eval_mask8(syms.vec_default_cast, + r_obj* out = vctrs_eval_mask7(syms.vec_default_cast, syms_x, x, syms_to, to, syms_x_arg, ffi_x_arg, syms_to_arg, ffi_to_arg, syms_call, ffi_call, syms_from_dispatch, r_lgl(from_dispatch), - syms_df_fallback, df_fallback, syms_s3_fallback, s3_fallback); - FREE(5); + FREE(4); return out; } @@ -285,7 +283,6 @@ r_obj* vec_cast_common_opts(r_obj* xs, } r_obj* vec_cast_common_params(r_obj* xs, r_obj* to, - enum df_fallback df_fallback, enum s3_fallback s3_fallback, struct vctrs_arg* p_arg, struct r_lazy call) { @@ -293,7 +290,6 @@ r_obj* vec_cast_common_params(r_obj* xs, .p_arg = p_arg, .call = call, .fallback = { - .df = df_fallback, .s3 = s3_fallback } }; @@ -306,7 +302,6 @@ r_obj* vec_cast_common(r_obj* xs, struct r_lazy call) { return vec_cast_common_params(xs, to, - DF_FALLBACK_DEFAULT, S3_FALLBACK_DEFAULT, p_arg, call); @@ -365,8 +360,7 @@ struct cast_opts new_cast_opts(r_obj* x, .p_to_arg = p_to_arg, .call = call, .fallback = { - .df = r_int_get(r_list_get(opts, 0), 0), - .s3 = r_int_get(r_list_get(opts, 1), 0) + .s3 = r_int_get(r_list_get(opts, 0), 0) } }; } diff --git a/src/cast.h b/src/cast.h index 861aa159b..1b93627bc 100644 --- a/src/cast.h +++ b/src/cast.h @@ -56,7 +56,6 @@ r_obj* vec_cast_params(r_obj* x, struct vctrs_arg* p_x_arg, struct vctrs_arg* p_to_arg, struct r_lazy call, - enum df_fallback df_fallback, enum s3_fallback s3_fallback) { const struct cast_opts opts = { .x = x, @@ -65,7 +64,6 @@ r_obj* vec_cast_params(r_obj* x, .p_to_arg = p_to_arg, .call = call, .fallback = { - .df = df_fallback, .s3 = s3_fallback } }; @@ -83,7 +81,6 @@ r_obj* vec_cast_common_opts(r_obj* xs, r_obj* vec_cast_common_params(r_obj* xs, r_obj* to, - enum df_fallback df_fallback, enum s3_fallback s3_fallback, struct vctrs_arg* p_arg, struct r_lazy call); diff --git a/src/dictionary.c b/src/dictionary.c index dd02b23c0..0fa7b3fa2 100644 --- a/src/dictionary.c +++ b/src/dictionary.c @@ -366,21 +366,18 @@ SEXP vec_match_params(SEXP needles, SEXP type = vec_ptype2_params(needles, haystack, needles_arg, haystack_arg, call, - DF_FALLBACK_quiet, &_); PROTECT_N(type, &nprot); needles = vec_cast_params(needles, type, needles_arg, vec_args.empty, call, - DF_FALLBACK_quiet, S3_FALLBACK_false); PROTECT_N(needles, &nprot); haystack = vec_cast_params(haystack, type, haystack_arg, vec_args.empty, call, - DF_FALLBACK_quiet, S3_FALLBACK_false); PROTECT_N(haystack, &nprot); @@ -476,21 +473,18 @@ SEXP vctrs_in(SEXP needles, SEXP haystack, SEXP na_equal_, SEXP frame) { SEXP type = vec_ptype2_params(needles, haystack, &needles_arg, &haystack_arg, call, - DF_FALLBACK_quiet, &_); PROTECT_N(type, &nprot); needles = vec_cast_params(needles, type, &needles_arg, vec_args.empty, call, - DF_FALLBACK_quiet, S3_FALLBACK_false); PROTECT_N(needles, &nprot); haystack = vec_cast_params(haystack, type, &haystack_arg, vec_args.empty, call, - DF_FALLBACK_quiet, S3_FALLBACK_false); PROTECT_N(haystack, &nprot); diff --git a/src/interval.c b/src/interval.c index 2769ac79e..ec12044f2 100644 --- a/src/interval.c +++ b/src/interval.c @@ -79,7 +79,6 @@ r_obj* vec_interval_group_info(r_obj* start, args_start, args_end, r_lazy_null, - DF_FALLBACK_quiet, &_ ); KEEP_N(ptype, &n_prot); @@ -90,7 +89,6 @@ r_obj* vec_interval_group_info(r_obj* start, args_start, vec_args.empty, r_lazy_null, - DF_FALLBACK_quiet, S3_FALLBACK_false ); KEEP_N(start, &n_prot); @@ -101,7 +99,6 @@ r_obj* vec_interval_group_info(r_obj* start, args_end, vec_args.empty, r_lazy_null, - DF_FALLBACK_quiet, S3_FALLBACK_false ); KEEP_N(end, &n_prot); @@ -324,7 +321,6 @@ r_obj* vec_interval_complement(r_obj* start, args_start, args_end, r_lazy_null, - DF_FALLBACK_quiet, &_ ); KEEP_N(ptype, &n_prot); @@ -335,7 +331,6 @@ r_obj* vec_interval_complement(r_obj* start, args_start, vec_args.empty, r_lazy_null, - DF_FALLBACK_quiet, S3_FALLBACK_false ); KEEP_N(start, &n_prot); @@ -346,7 +341,6 @@ r_obj* vec_interval_complement(r_obj* start, args_end, vec_args.empty, r_lazy_null, - DF_FALLBACK_quiet, S3_FALLBACK_false ); KEEP_N(end, &n_prot); @@ -387,7 +381,6 @@ r_obj* vec_interval_complement(r_obj* start, args_lower, vec_args.empty, r_lazy_null, - DF_FALLBACK_quiet, S3_FALLBACK_false ); KEEP_N(lower, &n_prot); @@ -417,7 +410,6 @@ r_obj* vec_interval_complement(r_obj* start, args_upper, vec_args.empty, r_lazy_null, - DF_FALLBACK_quiet, S3_FALLBACK_false ); KEEP_N(upper, &n_prot); @@ -738,7 +730,6 @@ r_obj* vec_interval_locate_containers(r_obj* start, r_obj* end) { args_start, args_end, r_lazy_null, - DF_FALLBACK_quiet, &_ ); KEEP_N(ptype, &n_prot); @@ -749,7 +740,6 @@ r_obj* vec_interval_locate_containers(r_obj* start, r_obj* end) { args_start, vec_args.empty, r_lazy_null, - DF_FALLBACK_quiet, S3_FALLBACK_false ); KEEP_N(start, &n_prot); @@ -760,7 +750,6 @@ r_obj* vec_interval_locate_containers(r_obj* start, r_obj* end) { args_end, vec_args.empty, r_lazy_null, - DF_FALLBACK_quiet, S3_FALLBACK_false ); KEEP_N(end, &n_prot); diff --git a/src/match.c b/src/match.c index 17e369128..dabea1b62 100644 --- a/src/match.c +++ b/src/match.c @@ -137,7 +137,6 @@ r_obj* vec_locate_matches(r_obj* needles, needles_arg, haystack_arg, error_call, - DF_FALLBACK_quiet, &_ ), &n_prot); @@ -147,7 +146,6 @@ r_obj* vec_locate_matches(r_obj* needles, needles_arg, vec_args.empty, error_call, - DF_FALLBACK_quiet, S3_FALLBACK_false ), &n_prot); @@ -157,7 +155,6 @@ r_obj* vec_locate_matches(r_obj* needles, haystack_arg, vec_args.empty, error_call, - DF_FALLBACK_quiet, S3_FALLBACK_false ), &n_prot); diff --git a/src/ptype-common.c b/src/ptype-common.c index 3ba20cc96..24ac0abc9 100644 --- a/src/ptype-common.c +++ b/src/ptype-common.c @@ -14,7 +14,6 @@ r_obj* ffi_ptype_common(r_obj* ffi_call, r_obj* op, r_obj* args, r_obj* env) { r_obj* out = vec_ptype_common_params(types, ptype, - DF_FALLBACK_DEFAULT, S3_FALLBACK_false, &arg, call); @@ -70,7 +69,6 @@ r_obj* vec_ptype_common_opts(r_obj* dots, r_obj* vec_ptype_common_params(r_obj* dots, r_obj* ptype, - enum df_fallback df_fallback, enum s3_fallback s3_fallback, struct vctrs_arg* p_arg, struct r_lazy call) { @@ -78,7 +76,6 @@ r_obj* vec_ptype_common_params(r_obj* dots, .call = call, .p_arg = p_arg, .fallback = { - .df = df_fallback, .s3 = s3_fallback } }; diff --git a/src/ptype-common.h b/src/ptype-common.h index 388d16a6b..e768b3361 100644 --- a/src/ptype-common.h +++ b/src/ptype-common.h @@ -18,7 +18,6 @@ bool vec_is_common_class_fallback(r_obj* ptype) { r_obj* vec_ptype_common_params(r_obj* dots, r_obj* ptype, - enum df_fallback df_fallback, enum s3_fallback s3_fallback, struct vctrs_arg* p_arg, struct r_lazy call); diff --git a/src/ptype.c b/src/ptype.c index 132cde7e0..d74ff6fc1 100644 --- a/src/ptype.c +++ b/src/ptype.c @@ -144,25 +144,7 @@ r_obj* vec_ptype_finalise(r_obj* x) { return bare_df_map(x, &vec_ptype_finalise); case VCTRS_CLASS_data_frame: - x = KEEP(df_map(x, &vec_ptype_finalise)); - - if (r_inherits(x, "vctrs:::df_fallback")) { - r_obj* seen_tibble_attr = KEEP(r_attrib_get(x, r_sym("seen_tibble"))); - bool seen_tibble = r_is_true(seen_tibble_attr); - FREE(1); - - if (seen_tibble) { - r_attrib_poke_class(x, classes_tibble); - } else { - r_attrib_poke_class(x, classes_data_frame); - } - - r_attrib_poke(x, r_sym("known_classes"), r_null); - r_attrib_poke(x, r_sym("seen_tibble"), r_null); - } - - FREE(1); - return x; + return df_map(x, &vec_ptype_finalise); case VCTRS_CLASS_none: r_stop_internal("Non-S3 classes should have returned by now."); diff --git a/src/ptype2-dispatch.c b/src/ptype2-dispatch.c index feb07dd5a..6aa69d689 100644 --- a/src/ptype2-dispatch.c +++ b/src/ptype2-dispatch.c @@ -56,23 +56,21 @@ r_obj* vec_ptype2_default_full(r_obj* x, struct r_lazy call, const struct fallback_opts* opts, bool from_dispatch) { - r_obj* df_fallback_obj = KEEP(r_int(opts->df)); - r_obj* s3_fallback_obj = KEEP(r_int(opts->s3)); + r_obj* ffi_s3_fallback = KEEP(r_int(opts->s3)); r_obj* ffi_x_arg = KEEP(vctrs_arg(x_arg)); r_obj* ffi_y_arg = KEEP(vctrs_arg(y_arg)); r_obj* ffi_call = KEEP(r_lazy_eval(call)); - r_obj* out = vctrs_eval_mask8(syms_vec_ptype2_default, + r_obj* out = vctrs_eval_mask7(syms_vec_ptype2_default, syms_x, x, syms_y, y, syms_x_arg, ffi_x_arg, syms_y_arg, ffi_y_arg, syms_call, ffi_call, syms_from_dispatch, r_lgl(from_dispatch), - syms_df_fallback, df_fallback_obj, - syms_s3_fallback, s3_fallback_obj); + syms_s3_fallback, ffi_s3_fallback); - FREE(5); + FREE(4); return out; } @@ -151,20 +149,17 @@ r_obj* vec_invoke_coerce_method(r_obj* method_sym, r_obj* method, const struct fallback_opts* opts) { r_obj* call = KEEP(r_lazy_eval(lazy_call)); - if (opts->df != DF_FALLBACK_DEFAULT || - opts->s3 != S3_FALLBACK_DEFAULT) { - r_obj* df_fallback_obj = KEEP(r_int(opts->df)); - r_obj* s3_fallback_obj = KEEP(r_int(opts->s3)); + if (opts->s3 != S3_FALLBACK_DEFAULT) { + r_obj* ffi_s3_fallback = KEEP(r_int(opts->s3)); - r_obj* out = vctrs_dispatch7(method_sym, method, + r_obj* out = vctrs_dispatch6(method_sym, method, x_sym, x, y_sym, y, x_arg_sym, x_arg, y_arg_sym, y_arg, syms_call, call, - syms_df_fallback, df_fallback_obj, - syms_s3_fallback, s3_fallback_obj); - FREE(3); + syms_s3_fallback, ffi_s3_fallback); + FREE(2); return out; } else { r_obj* out = vctrs_dispatch5(method_sym, method, diff --git a/src/ptype2.c b/src/ptype2.c index ee361de8c..406d417dd 100644 --- a/src/ptype2.c +++ b/src/ptype2.c @@ -292,8 +292,7 @@ struct ptype2_opts new_ptype2_opts(r_obj* x, struct fallback_opts new_fallback_opts(r_obj* opts) { return (struct fallback_opts) { - .df = r_int_get(r_list_get(opts, 0), 0), - .s3 = r_int_get(r_list_get(opts, 1), 0) + .s3 = r_int_get(r_list_get(opts, 0), 0) }; } diff --git a/src/ptype2.h b/src/ptype2.h index 9125793f4..37bcaccbc 100644 --- a/src/ptype2.h +++ b/src/ptype2.h @@ -6,16 +6,6 @@ // Sync with R constants in ptype2.R -#define DF_FALLBACK_DEFAULT 0 - -enum df_fallback { - DF_FALLBACK_warn_maybe = 0, - DF_FALLBACK_warn, - DF_FALLBACK_none, - DF_FALLBACK_quiet -}; - - #define S3_FALLBACK_DEFAULT 0 enum s3_fallback { @@ -24,7 +14,6 @@ enum s3_fallback { }; struct fallback_opts { - enum df_fallback df; enum s3_fallback s3; }; @@ -46,17 +35,13 @@ r_obj* vec_ptype2_params(r_obj* x, struct vctrs_arg* p_x_arg, struct vctrs_arg* p_y_arg, struct r_lazy call, - enum df_fallback df_fallback, int* left) { const struct ptype2_opts opts = { .x = x, .y = y, .p_x_arg = p_x_arg, .p_y_arg = p_y_arg, - .call = call, - .fallback = { - .df = df_fallback - } + .call = call }; return vec_ptype2_opts(&opts, left); } diff --git a/src/type-data-frame.h b/src/type-data-frame.h index 02d505899..d124b7109 100644 --- a/src/type-data-frame.h +++ b/src/type-data-frame.h @@ -55,16 +55,12 @@ static inline r_obj* df_ptype2_params(r_obj* x, r_obj* y, struct vctrs_arg* p_x_arg, - struct vctrs_arg* p_y_arg, - enum df_fallback df_fallback) { + struct vctrs_arg* p_y_arg) { const struct ptype2_opts opts = { .x = x, .y = y, .p_x_arg = p_x_arg, - .p_y_arg = p_y_arg, - .fallback = { - .df = df_fallback - } + .p_y_arg = p_y_arg }; return df_ptype2(&opts); } diff --git a/src/utils.c b/src/utils.c index 687c43c4a..091082021 100644 --- a/src/utils.c +++ b/src/utils.c @@ -1869,7 +1869,6 @@ void vctrs_init_utils(SEXP ns) { syms_parent = Rf_install("parent"); syms_s3_methods_table = Rf_install(".__S3MethodsTable__."); syms_from_dispatch = Rf_install("vctrs:::from_dispatch"); - syms_df_fallback = Rf_install("vctrs:::df_fallback"); syms_s3_fallback = Rf_install("vctrs:::s3_fallback"); syms_stop_incompatible_type = Rf_install("stop_incompatible_type"); syms_stop_incompatible_size = Rf_install("stop_incompatible_size"); diff --git a/src/utils.h b/src/utils.h index fafc6b40c..b4b6a0243 100644 --- a/src/utils.h +++ b/src/utils.h @@ -487,7 +487,6 @@ extern SEXP syms_character; extern SEXP syms_body; extern SEXP syms_parent; extern SEXP syms_from_dispatch; -extern SEXP syms_df_fallback; extern SEXP syms_s3_fallback; extern SEXP syms_stop_incompatible_type; extern SEXP syms_stop_incompatible_size; diff --git a/tests/testthat/_snaps/type-data-frame.md b/tests/testthat/_snaps/type-data-frame.md index a11a312f5..83eff7e29 100644 --- a/tests/testthat/_snaps/type-data-frame.md +++ b/tests/testthat/_snaps/type-data-frame.md @@ -52,58 +52,6 @@ > > -# combining data frames with foreign classes uses fallback - - Code - vec_ptype_common_df_fallback(foo, bar, baz) - Condition - Warning: - Can't combine `..1` and `..2` ; falling back to . - Warning: - Can't combine `..1` and `..3` ; falling back to . - Output - [1] mpg cyl disp hp drat wt qsec vs am - <0 rows> (or 0-length row.names) - Code - vec_ptype_common_df_fallback(foo, baz, bar, baz, foo, bar) - Condition - Warning: - Can't combine `..1` and `..2` ; falling back to . - Warning: - Can't combine `..1` and `..3` ; falling back to . - Output - [1] mpg cyl disp qsec vs am hp drat wt - <0 rows> (or 0-length row.names) - Code - with_fallback_warning(invisible(vec_rbind(foo, data.frame(), foo))) - Condition - Warning: - Can't combine `..1` and `..2` ; falling back to . - Code - with_fallback_warning(invisible(vec_cbind(foo, data.frame(x = 1)))) - Condition - Warning: - Can't combine `..1` and `..2` ; falling back to . - Code - with_fallback_warning(invisible(vec_cbind(foo, data.frame(x = 1), bar))) - Condition - Warning: - Can't combine `..1` and `..2` ; falling back to . - Warning: - Can't combine `..1` and `..3` ; falling back to . - Code - with_fallback_warning(invisible(vec_rbind(foo, baz, bar, baz, foo, bar))) - Condition - Warning: - Can't combine `..1` and `..2` ; falling back to . - Warning: - Can't combine `..1` and `..3` ; falling back to . - Code - with_fallback_quiet(invisible(vec_rbind(foo, data.frame(), foo))) - with_fallback_quiet(invisible(vec_cbind(foo, data.frame(x = 1)))) - with_fallback_quiet(invisible(vec_cbind(foo, data.frame(x = 1), bar))) - with_fallback_quiet(invisible(vec_rbind(foo, baz, bar, baz, foo, bar))) - # `x` must be a list Code @@ -252,41 +200,11 @@ Output Error in `my_function()`: - ! Can't combine `x` and `x` . + ! Can't combine `df1$x` and `df3$x` . Code (expect_error(vec_ptype2(df3, df1), class = "vctrs_error_incompatible_type")) Output Error in `my_function()`: - ! Can't combine `x` and `x` . - -# falls back to tibble for tibble subclasses (#1025) - - Code - with_fallback_warning(invisible(vec_rbind(foobar(tibble::as_tibble(mtcars)), - mtcars, foobaz(mtcars)))) - Condition - Warning: - Can't combine `..1` and `..2` ; falling back to . - Warning: - Can't combine `..1` and `..3` ; falling back to . - Code - with_fallback_warning(invisible(vec_rbind(tibble::as_tibble(mtcars), foobar( - tibble::as_tibble(mtcars))))) - Condition - Warning: - Can't combine `..1` and `..2` ; falling back to . - Code - with_fallback_warning(invisible(vec_rbind(foobar(tibble::as_tibble(mtcars)), - mtcars, foobar(tibble::as_tibble(mtcars))))) - Condition - Warning: - Can't combine `..1` and `..2` ; falling back to . - Code - with_fallback_quiet(invisible(vec_rbind(foobar(tibble::as_tibble(mtcars)), - mtcars, foobaz(mtcars)))) - with_fallback_quiet(invisible(vec_rbind(tibble::as_tibble(mtcars), foobar( - tibble::as_tibble(mtcars))))) - with_fallback_quiet(invisible(vec_rbind(foobar(tibble::as_tibble(mtcars)), - mtcars, foobar(tibble::as_tibble(mtcars))))) + ! Can't combine `df3$x` and `df1$x` . diff --git a/tests/testthat/_snaps/type2.md b/tests/testthat/_snaps/type2.md index 8c748d9a9..c1e32cad2 100644 --- a/tests/testthat/_snaps/type2.md +++ b/tests/testthat/_snaps/type2.md @@ -119,61 +119,9 @@ df <- data.frame(x = 1, y = "") foo <- structure(df, class = c("vctrs_foo", "data.frame")) bar <- structure(df, class = c("vctrs_bar", "data.frame")) - (expect_error(vec_cast_no_fallback(foo, bar), class = "vctrs_error_incompatible_type") - ) + (expect_error(vec_cast(foo, bar), class = "vctrs_error_incompatible_type")) Output - Error in `vec_cast_no_fallback()`: - ! Can't convert `x` to . - -# common type warnings for data frames take attributes into account - - Code - vec_ptype2_fallback(foobar_bud, foobar_boo) - Condition - Warning: - Can't combine and ; falling back to . - x Some attributes are incompatible. - i The author of the class should implement vctrs methods. - i See . - Output - [1] mpg cyl disp hp drat wt qsec vs am gear carb - <0 rows> (or 0-length row.names) - Code - # For reference, warning for incompatible classes - vec_ptype2_fallback(foobar(mtcars), foobaz(mtcars)) - Condition - Warning: - Can't combine and ; falling back to . - Output - [1] mpg cyl disp hp drat wt qsec vs am gear carb - <0 rows> (or 0-length row.names) - Code - # For reference, error when fallback is disabled - (expect_error(vec_ptype2_no_fallback(foobar(mtcars), foobaz(mtcars)), class = "vctrs_error_incompatible_type") - ) - Output - - Error: - ! Can't combine and . - -# For reference, warning for incompatible classes - - Code - vec_ptype2_fallback(foobar(mtcars), foobaz(mtcars)) - Condition - Warning: - Can't combine and ; falling back to . - Output - [1] mpg cyl disp hp drat wt qsec vs am gear carb - <0 rows> (or 0-length row.names) - -# For reference, error when fallback is disabled - - Code - (expect_error(vec_ptype2_no_fallback(foobar(mtcars), foobaz(mtcars)))) - Output - Error: - ! Can't combine and . + ! Can't convert `foo` to . diff --git a/tests/testthat/helper-expectations.R b/tests/testthat/helper-expectations.R index 7eea2948c..91e91c2b9 100644 --- a/tests/testthat/helper-expectations.R +++ b/tests/testthat/helper-expectations.R @@ -80,28 +80,6 @@ expect_error_cnd <- function(object, class, message = NULL, ..., .fixed = TRUE) expect_equal(cnd[names(exp_fields)], exp_fields) } -expect_incompatible_df <- function(x, fallback) { - if (is_true(peek_option("vctrs:::warn_on_fallback"))) { - x <- expect_df_fallback_warning(x) - } - expect_identical(x, fallback) -} -# Never warns so we don't get repeat warnings -expect_incompatible_df_cast <- function(x, fallback) { - expect_identical(x, fallback) -} - -expect_df_fallback_warning <- function(expr) { - suppressWarnings(expect_warning({{ expr }}, "falling back to (|)")) -} -expect_df_fallback_warning_maybe <- function(expr) { - if (is_true(peek_option("vctrs:::warn_on_fallback"))) { - expect_warning({{ expr }}, "falling back to (|)") - } else { - expr - } -} - scrub_internal_error_line_number <- function(x) { # Because it varies by OS sub(pattern = "at line [[:digit:]]+", replacement = "at line ", x = x) diff --git a/tests/testthat/helper-vctrs.R b/tests/testthat/helper-vctrs.R index 42d6b9a33..95bd60a70 100644 --- a/tests/testthat/helper-vctrs.R +++ b/tests/testthat/helper-vctrs.R @@ -3,17 +3,6 @@ testthat_import_from <- function(ns, names, env = caller_env()) { import_from(ns, names, env = env) } -vec_ptype2_fallback <- function(x, y, ...) { - vec_ptype2_params(x, y, ..., df_fallback = DF_FALLBACK_warn) -} -vec_ptype_common_df_fallback <- function(..., .ptype = NULL) { - vec_ptype_common_params( - ..., - .ptype = .ptype, - .df_fallback = DF_FALLBACK_warn - ) -} - shaped_int <- function(...) { array(NA_integer_, c(...)) } diff --git a/tests/testthat/test-cast.R b/tests/testthat/test-cast.R index 752c1be62..c2f974fef 100644 --- a/tests/testthat/test-cast.R +++ b/tests/testthat/test-cast.R @@ -93,7 +93,7 @@ test_that("unspecified can be cast to shaped vectors", { }) test_that("vec_cast() only falls back when casting to base type", { - expect_incompatible_df_cast(vec_cast(foobar(mtcars), mtcars), mtcars) + expect_equal(vec_cast(foobar(mtcars), mtcars), mtcars) expect_error( vec_cast(mtcars, foobar(mtcars)), class = "vctrs_error_incompatible_type" diff --git a/tests/testthat/test-type-data-frame.R b/tests/testthat/test-type-data-frame.R index de7c960d8..8619d07df 100644 --- a/tests/testthat/test-type-data-frame.R +++ b/tests/testthat/test-type-data-frame.R @@ -55,7 +55,7 @@ test_that("combining data frames with foreign classes uses fallback", { # Same type fallback expect_identical(vec_ptype_common(foo, foo, foo), foo) - expect_incompatible_df(vec_ptype_common(foo, foo, df, foo), df) + expect_equal(vec_ptype_common(foo, foo, df, foo), df) expect_df_fallback_warning(res <- vec_ptype2_fallback(foo, df)) expect_identical(res, new_fallback_df(df, c("vctrs_foobar", "data.frame"))) @@ -86,11 +86,11 @@ test_that("combining data frames with foreign classes uses fallback", { expect_s3_class(cnds[[1]], "warning") expect_match(cnds[[1]]$message, "falling back to ") - expect_incompatible_df( + expect_equal( vec_cbind(foobar(data.frame(x = 1)), data.frame(y = 2)), data.frame(x = 1, y = 2) ) - expect_incompatible_df( + expect_equal( vec_rbind(foo, data.frame(), foo), df ) @@ -629,7 +629,7 @@ test_that("data frame fallback handles column types (#999)", { df1_attrib <- foobar(df1, foo = "foo") df2_attrib <- foobar(df2, bar = "bar") exp <- data.frame(x = c(1, 1), y = c(NA, 2)) - expect_incompatible_df( + expect_equal( vec_rbind(df1_attrib, df2_attrib), exp ) @@ -728,8 +728,8 @@ test_that("fallback is recursive", { baz <- new_data_frame(list(y = 1:3, x = foobar(df, bar = TRUE))) exp <- new_data_frame(list(x = vec_rbind(df, df))) - expect_incompatible_df(vec_rbind(foo, bar), exp) + expect_equal(vec_rbind(foo, bar), exp) exp <- new_data_frame(list(x = vec_rbind(df, df), y = c(NA, NA, NA, 1:3))) - expect_incompatible_df(vec_rbind(foo, baz), exp) + expect_equal(vec_rbind(foo, baz), exp) }) diff --git a/tests/testthat/test-type-misc.R b/tests/testthat/test-type-misc.R index 7946b6af6..e38fa9302 100644 --- a/tests/testthat/test-type-misc.R +++ b/tests/testthat/test-type-misc.R @@ -64,20 +64,20 @@ test_that("common type of data.table and data.frame is data.table", { test_that("data.table and tibble do not have a common type", { testthat_import_from("data.table", "data.table") - expect_incompatible_df( + expect_equal( vec_ptype_common(data.table(x = TRUE), tibble(y = 2)), tibble(x = lgl(), y = dbl()) ) - expect_incompatible_df( + expect_equal( vec_ptype_common(tibble(y = 2), data.table(x = TRUE)), tibble(y = dbl(), x = lgl()) ) - expect_incompatible_df_cast( + expect_equal( vec_cast(tibble(y = 2), data.table(x = TRUE, y = 1L)), data.frame(x = NA, y = 2L) ) - expect_incompatible_df_cast( + expect_equal( vec_cast(data.table(y = 2), tibble(x = TRUE, y = 1L)), tibble(x = NA, y = 2L) ) diff --git a/tests/testthat/test-type2.R b/tests/testthat/test-type2.R index b9649bc6b..99518ac48 100644 --- a/tests/testthat/test-type2.R +++ b/tests/testthat/test-type2.R @@ -159,31 +159,17 @@ test_that("Subclasses of data.frame dispatch to `vec_ptype2()` methods", { expect_identical(vec_ptype2(mtcars, quux), "dispatched!") }) -test_that("Subclasses of `tbl_df` do not have `tbl_df` common type (#481)", { - quux <- tibble() - quux <- foobar(quux) +test_that("Subclasses of `tbl_df` have `tbl_df` common type (#481)", { + quux <- foobar(tibble()) - expect_incompatible_df( + expect_identical( vec_ptype_common(quux, tibble()), tibble() ) - expect_incompatible_df( + expect_identical( vec_ptype_common(tibble(), quux), tibble() ) - - expect_df_fallback_warning( - expect_identical( - vec_ptype_common_df_fallback(quux, tibble()), - tibble() - ) - ) - expect_df_fallback_warning( - expect_identical( - vec_ptype_common_df_fallback(tibble(), quux), - tibble() - ) - ) }) test_that("Column name encodings are handled correctly in the common type (#553)", { @@ -276,31 +262,24 @@ test_that("common type errors don't mention columns if they are compatible", { bar <- structure(df, class = c("vctrs_bar", "data.frame")) (expect_error( - vec_cast_no_fallback(foo, bar), + vec_cast(foo, bar), class = "vctrs_error_incompatible_type" )) }) }) -test_that("common type warnings for data frames take attributes into account", { +test_that("attributes no longer play a role in bare data frame fallback", { foobar_bud <- foobar(mtcars, bud = TRUE) foobar_boo <- foobar(mtcars, boo = TRUE) - expect_df_fallback_warning(vec_ptype2_fallback(foobar_bud, foobar_boo)) - expect_df_fallback_warning(vec_ptype2_fallback(foobar(mtcars), foobaz(mtcars))) - - expect_snapshot({ - vec_ptype2_fallback(foobar_bud, foobar_boo) - - "For reference, warning for incompatible classes" - vec_ptype2_fallback(foobar(mtcars), foobaz(mtcars)) - - "For reference, error when fallback is disabled" - (expect_error( - vec_ptype2_no_fallback(foobar(mtcars), foobaz(mtcars)), - class = "vctrs_error_incompatible_type" - )) - }) + expect_equal( + vec_ptype2(foobar_bud, foobar_boo), + vec_slice(unrownames(mtcars), 0) + ) + expect_equal( + vec_ptype2(foobar(mtcars), foobaz(mtcars)), + vec_slice(unrownames(mtcars), 0) + ) }) test_that("vec_ptype2() methods get prototypes", { @@ -330,16 +309,6 @@ test_that("vec_ptype2() allows vec_ptype() to return another type", { expect_identical(out, dbl()) }) -test_that("For reference, warning for incompatible classes", { - expect_snapshot(vec_ptype2_fallback(foobar(mtcars), foobaz(mtcars))) -}) - -test_that("For reference, error when fallback is disabled", { - expect_snapshot( - (expect_error(vec_ptype2_no_fallback(foobar(mtcars), foobaz(mtcars)))) - ) -}) - test_that("vec_ptype2() evaluates x_arg and y_arg lazily", { expect_silent(vec_ptype2(1L, 1L, x_arg = print("oof"))) expect_silent(vec_ptype2(1L, 1L, y_arg = print("oof"))) From 588168271d7f7fd75756d4e829be47c71b1b6855 Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Mon, 17 Oct 2022 13:11:17 +0200 Subject: [PATCH 171/312] Remove same-type fallback for data frames --- R/cast.R | 10 +- R/conditions.R | 6 +- R/type2.R | 8 +- tests/testthat/_snaps/bind.md | 8 ++ tests/testthat/_snaps/type-data-frame.md | 12 ++ tests/testthat/_snaps/type-misc.md | 9 ++ tests/testthat/_snaps/type-tibble.md | 22 ++-- tests/testthat/_snaps/type2.md | 3 - tests/testthat/test-bind.R | 29 ++++- tests/testthat/test-c.R | 2 + tests/testthat/test-type-data-frame.R | 147 ++++------------------- tests/testthat/test-type-dplyr.R | 4 +- tests/testthat/test-type-misc.R | 14 ++- tests/testthat/test-type-sf.R | 4 - tests/testthat/test-type-tibble.R | 17 ++- 15 files changed, 123 insertions(+), 172 deletions(-) diff --git a/R/cast.R b/R/cast.R index cc1eb65d9..5e9abb2dd 100644 --- a/R/cast.R +++ b/R/cast.R @@ -187,10 +187,6 @@ vec_default_cast <- function(x, return(x) } - if (is_same_type(x, to)) { - return(x) - } - # If both data frames, fall back to base data frame if (is.data.frame(x) && is_bare_df(to)) { out <- df_cast_opts( @@ -210,6 +206,12 @@ vec_default_cast <- function(x, return(out) } + # Data frames no longer have an is-same-type fallback because their + # common types now fall back to bare data frames + if (!is.data.frame(x) && is_same_type(x, to)) { + return(x) + } + withRestarts( stop_incompatible_cast( x, diff --git a/R/conditions.R b/R/conditions.R index 848016e11..c52242e1b 100644 --- a/R/conditions.R +++ b/R/conditions.R @@ -256,12 +256,14 @@ cnd_type_message <- function(x, y_type <- cnd_type_message_type_label(y) } + converting <- action == "convert" + # If we are here directly from dispatch, this means there is no # ptype2 method implemented and the is-same-class fallback has # failed because of diverging attributes. The author of the class # should implement a ptype2 method as documented in the FAQ # indicated below. - if (from_dispatch && identical(class(x)[[1]], class(y)[[1]])) { + if (from_dispatch && !converting && identical(class(x)[[1]], class(y)[[1]])) { details <- c(incompatible_attrib_bullets(), details) details <- format_error_bullets(details) } @@ -272,7 +274,7 @@ cnd_type_message <- function(x, end <- glue::glue("; falling back to {fallback}.") } - if (action == "convert" && nzchar(y_arg)) { + if (converting && nzchar(y_arg)) { header <- glue::glue("Can't convert{x_name}<{x_type}> to match type of{y_name}<{y_type}>{end}") } else { header <- glue::glue("Can't {action}{x_name}<{x_type}> {separator}{y_name}<{y_type}>{end}") diff --git a/R/type2.R b/R/type2.R index c06b33f25..9ab713b45 100644 --- a/R/type2.R +++ b/R/type2.R @@ -132,10 +132,6 @@ vec_default_ptype2 <- function(x, } } - if (is_same_type(x, y)) { - return(vec_ptype(x, x_arg = x_arg)) - } - if (is.data.frame(x) && is.data.frame(y)) { return(vec_ptype2_df_fallback( x, @@ -147,6 +143,10 @@ vec_default_ptype2 <- function(x, )) } + if (is_same_type(x, y)) { + return(vec_ptype(x, x_arg = x_arg)) + } + # The from-dispatch parameter is set only when called from our S3 # dispatch mechanism, when no method is found to dispatch to. It # indicates whether the error message should provide advice about diff --git a/tests/testthat/_snaps/bind.md b/tests/testthat/_snaps/bind.md index 5ed40ae23..6983aefb9 100644 --- a/tests/testthat/_snaps/bind.md +++ b/tests/testthat/_snaps/bind.md @@ -402,6 +402,14 @@ Error in `vec_rbind()`: ! Can't combine `..1` and `..2` . +# vec_rbind() falls back to c() if S3 method is available + + Code + with_hybrid_methods(cast = FALSE, vec_rbind(foo_df, bar_df)) + Condition + Error in `vec_rbind()`: + ! Can't convert `..1` > to >. + # can't zap names when `.names_to` is supplied Code diff --git a/tests/testthat/_snaps/type-data-frame.md b/tests/testthat/_snaps/type-data-frame.md index 83eff7e29..56e816551 100644 --- a/tests/testthat/_snaps/type-data-frame.md +++ b/tests/testthat/_snaps/type-data-frame.md @@ -207,4 +207,16 @@ Error in `my_function()`: ! Can't combine `df3$x` and `df1$x` . + Code + (expect_error(vec_cast(df1, df2), class = "vctrs_error_incompatible_type")) + Output + + Error in `my_function()`: + ! Can't convert `df1` to . + Code + (expect_error(vec_cast(df2, df1), class = "vctrs_error_incompatible_type")) + Output + + Error in `my_function()`: + ! Can't convert `df2` to . diff --git a/tests/testthat/_snaps/type-misc.md b/tests/testthat/_snaps/type-misc.md index ba0833783..dc44c3fa8 100644 --- a/tests/testthat/_snaps/type-misc.md +++ b/tests/testthat/_snaps/type-misc.md @@ -1,3 +1,12 @@ +# data.table and tibble do not have a common type + + Code + (expect_error(vec_cast(tibble(y = 2), data.table(x = TRUE, y = 1L)))) + Output + + Error: + ! Can't convert `tibble(y = 2)` to . + # data table has formatting methods Code diff --git a/tests/testthat/_snaps/type-tibble.md b/tests/testthat/_snaps/type-tibble.md index 1b3786edb..fe26c142b 100644 --- a/tests/testthat/_snaps/type-tibble.md +++ b/tests/testthat/_snaps/type-tibble.md @@ -24,23 +24,27 @@ Code local_error_call(call("my_function")) - (expect_error(vec_cast(tib1, tib2), class = "vctrs_error_cast_lossy_dropped")) + (expect_error(vec_cast(tib1, tib1), class = "vctrs_error_cast")) Output - + + Error in `my_function()`: + ! Can't convert `tib1` to . + Code + (expect_error(vec_cast(tib1, tib2), class = "vctrs_error_cast")) + Output + Error in `my_function()`: - ! Can't convert from `tib1` > to > due to loss of precision. + ! Can't convert `tib1` to . Code - (expect_error(vec_cast(tib1, data.frame(y = 2)), class = "vctrs_error_cast_lossy_dropped") - ) + (expect_error(vec_cast(tib1, data.frame(y = 2)), class = "vctrs_error_cast")) Output Error in `my_function()`: ! Can't convert from `tib1` > to > due to loss of precision. Code - (expect_error(vec_cast(data.frame(x = 1), tib2), class = "vctrs_error_cast_lossy_dropped") - ) + (expect_error(vec_cast(data.frame(x = 1), tib2), class = "vctrs_error_cast")) Output - + Error in `my_function()`: - ! Can't convert from `data.frame(x = 1)` > to > due to loss of precision. + ! Can't convert `data.frame(x = 1)` to . diff --git a/tests/testthat/_snaps/type2.md b/tests/testthat/_snaps/type2.md index c1e32cad2..8df5b9f75 100644 --- a/tests/testthat/_snaps/type2.md +++ b/tests/testthat/_snaps/type2.md @@ -72,9 +72,6 @@ Error: ! Can't convert `foobar(1, bar = TRUE)` to . - x Some attributes are incompatible. - i The author of the class should implement vctrs methods. - i See . Code (expect_error(vec_ptype2(foobar(1, bar = TRUE), foobar(2, baz = TRUE)), class = "vctrs_error_incompatible_type") ) diff --git a/tests/testthat/test-bind.R b/tests/testthat/test-bind.R index 0cb49d06e..43596dc68 100644 --- a/tests/testthat/test-bind.R +++ b/tests/testthat/test-bind.R @@ -313,6 +313,9 @@ test_that("vec_rbind() takes the proxy and restores", { vec_ptype2.vctrs_foobar.vctrs_foobar = function(x, y, ...) { x }, + vec_cast.vctrs_foobar.vctrs_foobar = function(x, to, ...) { + x + }, vec_proxy.vctrs_foobar = function(x, ...) { x }, @@ -341,6 +344,9 @@ test_that("vec_rbind() proxies before initializing", { vec_ptype2.vctrs_foobar.vctrs_foobar = function(x, y, ...) { x }, + vec_cast.vctrs_foobar.vctrs_foobar = function(x, to, ...) { + x + }, vec_proxy.vctrs_foobar = function(x, ...) { new_data_frame(x) }, @@ -363,10 +369,14 @@ test_that("vec_rbind() requires a data frame proxy for data frame ptypes", { local_methods( vec_ptype2.vctrs_foobar.vctrs_foobar = function(x, y, ...) x, + vec_cast.vctrs_foobar.vctrs_foobar = function(x, to, ...) x, vec_proxy.vctrs_foobar = function(x, ...) 1 ) - expect_error(vec_rbind(df, df), "Attempt to restore data frame from a double") + expect_error( + vec_rbind(df, df), + "Can't fill a data frame that doesn't have a data frame proxy" + ) }) test_that("monitoring: name repair while rbinding doesn't modify in place", { @@ -864,14 +874,25 @@ test_that("vec_rbind() falls back to c() if S3 method is available", { exp ) - with_hybrid_methods <- function(expr) { - with_methods( + with_hybrid_methods <- function(expr, cast = TRUE) { + methods <- list( c.vctrs_foobar = function(...) quux(NextMethod()), vec_ptype2.vctrs_foobaz.vctrs_foobaz = function(...) foobaz(df_ptype2(...)), - expr + vec_cast.vctrs_foobaz.vctrs_foobaz = if (cast) function(...) foobaz(df_cast(...)) ) + with_methods(expr, !!!compact(methods)) } + # FIXME!: test without cast method: should not montion common type + # fallback in error message + expect_snapshot(error = TRUE, + with_hybrid_methods( + cast = FALSE, + vec_rbind(foo_df, bar_df) + ) + ) + + # Falls back to data frame because there is no ptype2/cast methods out <- with_hybrid_methods(vec_rbind(foo_df, bar_df)) exp <- foobaz(data_frame(x = quux(c(1, 2)))) expect_identical(out, exp) diff --git a/tests/testthat/test-c.R b/tests/testthat/test-c.R index b190a7be9..dc1e69ea2 100644 --- a/tests/testthat/test-c.R +++ b/tests/testthat/test-c.R @@ -277,6 +277,8 @@ test_that("c() fallback is consistent", { c_method <- function(...) dispatched(NextMethod()) out <- with_methods( + vec_ptype2.vctrs_foobaz.vctrs_foobaz = function(...) foobaz(df_ptype2(...)), + vec_cast.vctrs_foobaz.vctrs_foobaz = function(...) foobaz(df_cast(...)), c.vctrs_foobar = c_method, list( direct = vec_c(foobar(1L), foobar(2L)), diff --git a/tests/testthat/test-type-data-frame.R b/tests/testthat/test-type-data-frame.R index 8619d07df..169605f8a 100644 --- a/tests/testthat/test-type-data-frame.R +++ b/tests/testthat/test-type-data-frame.R @@ -53,21 +53,13 @@ test_that("combining data frames with foreign classes uses fallback", { foo <- foobar(data.frame()) df <- data.frame() - # Same type fallback - expect_identical(vec_ptype_common(foo, foo, foo), foo) - expect_equal(vec_ptype_common(foo, foo, df, foo), df) + expect_identical(vec_ptype_common(foo, foo, foo), df) + expect_identical(vec_ptype_common(foo, foo, df, foo), df) - expect_df_fallback_warning(res <- vec_ptype2_fallback(foo, df)) - expect_identical(res, new_fallback_df(df, c("vctrs_foobar", "data.frame"))) - - expect_df_fallback_warning(res <- vec_ptype2_fallback(df, foo)) - expect_identical(res, new_fallback_df(df, c("data.frame", "vctrs_foobar"))) - - expect_df_fallback_warning(res <- vec_ptype_common_df_fallback(foo, df)) - expect_identical(res, df) - - expect_df_fallback_warning(res <- vec_ptype_common_df_fallback(df, foo)) - expect_identical(res, df) + expect_identical(vec_ptype2(foo, df), data.frame()) + expect_identical(vec_ptype2(df, foo), data.frame()) + expect_identical(vec_ptype_common(foo, df), df) + expect_identical(vec_ptype_common(df, foo), df) cnds <- list() withCallingHandlers( @@ -76,15 +68,13 @@ test_that("combining data frames with foreign classes uses fallback", { invokeRestart("muffleWarning") }, expect_identical( - vec_ptype_common_df_fallback(foo, df, foo, foo), + vec_ptype_common(foo, df, foo, foo), df ) ) - # There should be only one warning even if many fallbacks - expect_length(cnds, 1) - expect_s3_class(cnds[[1]], "warning") - expect_match(cnds[[1]]$message, "falling back to ") + # There are no longer any warnings + expect_length(cnds, 0) expect_equal( vec_cbind(foobar(data.frame(x = 1)), data.frame(y = 2)), @@ -94,30 +84,6 @@ test_that("combining data frames with foreign classes uses fallback", { vec_rbind(foo, data.frame(), foo), df ) - - foo <- structure(mtcars[1:3], class = c("foo", "data.frame")) - bar <- structure(mtcars[4:6], class = c("bar", "data.frame")) - baz <- structure(mtcars[7:9], class = c("baz", "data.frame")) - - with_fallback_warning(expect_df_fallback_warning(invisible(vec_rbind(foo, data.frame(), foo)))) - with_fallback_warning(expect_df_fallback_warning(invisible(vec_cbind(foo, data.frame(x = 1))))) - with_fallback_warning(expect_df_fallback_warning(invisible(vec_cbind(foo, data.frame(x = 1), bar)))) - with_fallback_warning(expect_df_fallback_warning(invisible(vec_rbind(foo, baz, bar, baz, foo, bar)))) - - expect_snapshot({ - vec_ptype_common_df_fallback(foo, bar, baz) - vec_ptype_common_df_fallback(foo, baz, bar, baz, foo, bar) - - with_fallback_warning(invisible(vec_rbind(foo, data.frame(), foo))) - with_fallback_warning(invisible(vec_cbind(foo, data.frame(x = 1)))) - with_fallback_warning(invisible(vec_cbind(foo, data.frame(x = 1), bar))) - with_fallback_warning(invisible(vec_rbind(foo, baz, bar, baz, foo, bar))) - - with_fallback_quiet(invisible(vec_rbind(foo, data.frame(), foo))) - with_fallback_quiet(invisible(vec_cbind(foo, data.frame(x = 1)))) - with_fallback_quiet(invisible(vec_cbind(foo, data.frame(x = 1), bar))) - with_fallback_quiet(invisible(vec_rbind(foo, baz, bar, baz, foo, bar))) - }) }) @@ -595,7 +561,7 @@ test_that("data frame fallback handles column types (#999)", { df2 <- foobar(data.frame(x = 1, y = 2)) df3 <- foobar(data.frame(x = "", y = 2)) - common <- foobar(data.frame(x = dbl(), y = dbl())) + common <- data.frame(x = dbl(), y = dbl()) expect_identical(vec_ptype2(df1, df2), common) expect_identical(vec_ptype2(df2, df1), common) @@ -609,20 +575,19 @@ test_that("data frame fallback handles column types (#999)", { vec_ptype2(df3, df1), class = "vctrs_error_incompatible_type" )) + (expect_error( + vec_cast(df1, df2), + class = "vctrs_error_incompatible_type" + )) + (expect_error( + vec_cast(df2, df1), + class = "vctrs_error_incompatible_type" + )) }) - expect_identical( - vec_cast(df1, df2), - foobar(data.frame(x = 1, y = na_dbl)) - ) - expect_error( - vec_cast(df2, df1), - class = "vctrs_error_cast_lossy" - ) - expect_identical( vec_rbind(df1, df2), - foobar(data.frame(x = c(1, 1), y = c(NA, 2))) + data.frame(x = c(1, 1), y = c(NA, 2)) ) # Attributes are not restored @@ -644,80 +609,14 @@ test_that("data frame fallback handles column types (#999)", { }, vec_rbind(df1_attrib, df2_attrib) ) - - expect_identical(out, foobar(exp, dispatched = TRUE)) + expect_identical(out, exp) }) test_that("falls back to tibble for tibble subclasses (#1025)", { foo <- foobar(tibble::as_tibble(mtcars)) - expect_s3_class(expect_df_fallback_warning_maybe(vec_rbind(foo, mtcars)), "tbl_df") - expect_s3_class(expect_df_fallback_warning_maybe(vec_rbind(foo, mtcars, mtcars)), "tbl_df") - expect_s3_class(expect_df_fallback_warning_maybe(vec_rbind(foo, mtcars, foobar(mtcars))), "tbl_df") - - with_fallback_warning(expect_df_fallback_warning( - vec_rbind( - foobar(tibble::as_tibble(mtcars)), - mtcars, - foobaz(mtcars) - ) - )) - with_fallback_warning(expect_df_fallback_warning( - vec_rbind( - tibble::as_tibble(mtcars), - foobar(tibble::as_tibble(mtcars)) - ) - )) - with_fallback_warning(expect_df_fallback_warning( - vec_rbind( - foobar(tibble::as_tibble(mtcars)), - mtcars, - foobar(tibble::as_tibble(mtcars)) - ) - )) - - expect_snapshot({ - with_fallback_warning( - invisible(vec_rbind( - foobar(tibble::as_tibble(mtcars)), - mtcars, - foobaz(mtcars) - )) - ) - with_fallback_warning( - invisible(vec_rbind( - tibble::as_tibble(mtcars), - foobar(tibble::as_tibble(mtcars)) - )) - ) - with_fallback_warning( - invisible(vec_rbind( - foobar(tibble::as_tibble(mtcars)), - mtcars, - foobar(tibble::as_tibble(mtcars)) - )) - ) - - with_fallback_quiet( - invisible(vec_rbind( - foobar(tibble::as_tibble(mtcars)), - mtcars, - foobaz(mtcars) - )) - ) - with_fallback_quiet( - invisible(vec_rbind( - tibble::as_tibble(mtcars), - foobar(tibble::as_tibble(mtcars)) - )) - ) - with_fallback_quiet( - invisible(vec_rbind( - foobar(tibble::as_tibble(mtcars)), - mtcars, - foobar(tibble::as_tibble(mtcars)) - )) - ) - }) + expect_s3_class(vec_rbind(foo, mtcars), "tbl_df") + expect_s3_class(vec_rbind(foo, mtcars, mtcars), "tbl_df") + expect_s3_class(vec_rbind(foo, mtcars, foobar(mtcars)), "tbl_df") }) test_that("fallback is recursive", { diff --git a/tests/testthat/test-type-dplyr.R b/tests/testthat/test-type-dplyr.R index b4b6b354a..c1795cf4e 100644 --- a/tests/testthat/test-type-dplyr.R +++ b/tests/testthat/test-type-dplyr.R @@ -163,8 +163,6 @@ test_that("can cbind rowwise data frames", { }) test_that("no common type between rowwise and grouped data frames", { - expect_df_fallback_warning( - out <- vec_ptype_common_df_fallback(dplyr::rowwise(bare_mtcars), dplyr::group_by(bare_mtcars, cyl)) - ) + out <- vec_ptype_common(dplyr::rowwise(bare_mtcars), dplyr::group_by(bare_mtcars, cyl)) expect_identical(out, tibble::as_tibble(bare_mtcars[0, ])) }) diff --git a/tests/testthat/test-type-misc.R b/tests/testthat/test-type-misc.R index e38fa9302..6dff982ef 100644 --- a/tests/testthat/test-type-misc.R +++ b/tests/testthat/test-type-misc.R @@ -73,14 +73,16 @@ test_that("data.table and tibble do not have a common type", { tibble(y = dbl(), x = lgl()) ) - expect_equal( - vec_cast(tibble(y = 2), data.table(x = TRUE, y = 1L)), - data.frame(x = NA, y = 2L) - ) - expect_equal( + # Works because tibble is a bare df type + expect_identical( vec_cast(data.table(y = 2), tibble(x = TRUE, y = 1L)), - tibble(x = NA, y = 2L) + tibble(x = lgl(NA), y = 2L) ) + + # Fails because dt isn't + expect_snapshot({ + (expect_error(vec_cast(tibble(y = 2), data.table(x = TRUE, y = 1L)))) + }) }) test_that("data table has formatting methods", { diff --git a/tests/testthat/test-type-sf.R b/tests/testthat/test-type-sf.R index a558fe1e7..59740e20d 100644 --- a/tests/testthat/test-type-sf.R +++ b/tests/testthat/test-type-sf.R @@ -102,10 +102,6 @@ test_that("can combine sf data frames", { sf1 = st_sf(x = c(TRUE, FALSE), geo1 = sfc1) sf2 = st_sf(y = "", geo2 = sfc2, x = 0, stringsAsFactors = FALSE) - # FIXME: Currently `vec_rbind()` returns a data frame because we - # are temporarily working around bugs due to bad interaction of - # different fallbacks. `bind_rows()` returns an `sf` data frame as - # expected because of `dplyr_reconstruct()`. exp = data_frame( x = c(1, 0, 0), geo1 = sfc1[c(1:2, NA)], diff --git a/tests/testthat/test-type-tibble.R b/tests/testthat/test-type-tibble.R index 2ccf12dd4..bf47441fe 100644 --- a/tests/testthat/test-type-tibble.R +++ b/tests/testthat/test-type-tibble.R @@ -76,7 +76,7 @@ test_that("vec_ptype_finalise() can handle tibble df columns", { test_that("can use ptype2 and cast with tibble that has incorrect class vector", { tib1 <- structure(data.frame(x = 1), class = c("tbl_df", "data.frame")) tib2 <- structure(data.frame(y = 2), class = c("tbl_df", "data.frame")) - exp <- structure(data.frame(x = dbl(), y = dbl()), class = c("tbl_df", "data.frame")) + exp <- structure(data.frame(x = dbl(), y = dbl()), class = c("tbl_df", "tbl", "data.frame")) requireNamespace("tibble") @@ -93,24 +93,23 @@ test_that("can use ptype2 and cast with tibble that has incorrect class vector", tibble::new_tibble(exp, nrow = nrow(exp)) ) - expect_identical( - vec_cast(tib1, tib1), - tib1 - ) - expect_snapshot({ local_error_call(call("my_function")) + (expect_error( + vec_cast(tib1, tib1), + class = "vctrs_error_cast" + )) (expect_error( vec_cast(tib1, tib2), - class = "vctrs_error_cast_lossy_dropped" + class = "vctrs_error_cast" )) (expect_error( vec_cast(tib1, data.frame(y = 2)), - class = "vctrs_error_cast_lossy_dropped" + class = "vctrs_error_cast" )) (expect_error( vec_cast(data.frame(x = 1), tib2), - class = "vctrs_error_cast_lossy_dropped" + class = "vctrs_error_cast" )) }) }) From b4885305f61e0087c7a9a228effe198173f3a9c6 Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Mon, 17 Oct 2022 18:53:58 +0200 Subject: [PATCH 172/312] Update revdeps --- revdep/README.md | 18 ++ revdep/cran.md | 60 +++- revdep/problems.md | 768 ++++++++++++++++++++++++++++++++++++++++++--- 3 files changed, 779 insertions(+), 67 deletions(-) diff --git a/revdep/README.md b/revdep/README.md index a8f69affa..274eeb1c9 100644 --- a/revdep/README.md +++ b/revdep/README.md @@ -33,3 +33,21 @@ |[brokenstick](problems.md#brokenstick)|2.3.0 | |__+1__ | | |[psfmi](problems.md#psfmi)|1.0.0 |__+1__ |__+1__ |1 | +## New problems (13) + +|package |version |error |warning |note | +|:----------|:-------|:------|:-------|:----| +|[codebook](problems.md#codebook)|0.9.2 | |__+1__ |3 | +|[cubble](problems.md#cubble)|0.1.1 |__+1__ |1 | | +|[cutpointr](problems.md#cutpointr)|1.1.2 |__+2__ |__+1__ | | +|[dm](problems.md#dm)|1.0.3 |__+1__ | | | +|[dplyr](problems.md#dplyr)|1.0.10 |__+1__ | |1 | +|[gratia](problems.md#gratia)|0.7.3 |__+2__ | | | +|[groupr](problems.md#groupr)|0.1.0 |__+1__ |__+1__ |1 | +|[multidplyr](problems.md#multidplyr)|0.1.2 | |__+1__ | | +|[ricu](problems.md#ricu)|0.5.3 |__+1__ | | | +|[srvyr](problems.md#srvyr)|1.1.2 |__+2__ |__+1__ |1 | +|[tibbletime](problems.md#tibbletime)|0.1.6 |__+2__ | | | +|[tidyjson](problems.md#tidyjson)|0.3.1 |__+2__ |__+1__ | | +|[yamlet](problems.md#yamlet)|0.9.6 |__+1__ | | | + diff --git a/revdep/cran.md b/revdep/cran.md index 9b6513d08..3f119cb66 100644 --- a/revdep/cran.md +++ b/revdep/cran.md @@ -2,29 +2,59 @@ We checked 3546 reverse dependencies (3534 from CRAN + 12 from Bioconductor), comparing R CMD check results across CRAN and dev versions of this package. - * We saw 2 new problems - * We failed to check 9 packages + * We saw 13 new problems + * We failed to check 0 packages Issues with CRAN packages are summarised below. ### New problems (This reports the first line of each new failure) -* brokenstick +* codebook checking re-building of vignette outputs ... WARNING -* psfmi +* cubble + checking tests ... ERROR + +* cutpointr + checking examples ... ERROR + checking tests ... ERROR + checking re-building of vignette outputs ... WARNING + +* dm + checking tests ... ERROR + +* dplyr + checking tests ... ERROR + +* gratia checking examples ... ERROR + checking tests ... ERROR + +* groupr + checking tests ... ERROR checking re-building of vignette outputs ... WARNING -### Failed to check - -* elbird (NA) -* ggPMX (NA) -* loon.ggplot (NA) -* loon.shiny (NA) -* nlmixr2plot (NA) -* Platypus (NA) -* tidySEM (NA) -* vivid (NA) -* xpose.nlmixr2 (NA) +* multidplyr + checking re-building of vignette outputs ... WARNING + +* ricu + checking tests ... ERROR + +* srvyr + checking examples ... ERROR + checking tests ... ERROR + checking re-building of vignette outputs ... WARNING + +* tibbletime + checking examples ... ERROR + checking tests ... ERROR + +* tidyjson + checking examples ... ERROR + checking tests ... ERROR + checking re-building of vignette outputs ... WARNING + +* yamlet + checking tests ... ERROR + diff --git a/revdep/problems.md b/revdep/problems.md index 0735483f1..0359d3e31 100644 --- a/revdep/problems.md +++ b/revdep/problems.md @@ -1,14 +1,14 @@ -# brokenstick +# codebook
-* Version: 2.3.0 -* GitHub: https://github.com/growthcharts/brokenstick -* Source code: https://github.com/cran/brokenstick -* Date/Publication: 2022-09-07 22:23:04 UTC -* Number of recursive dependencies: 92 +* Version: 0.9.2 +* GitHub: https://github.com/rubenarslan/codebook +* Source code: https://github.com/cran/codebook +* Date/Publication: 2020-06-06 23:40:03 UTC +* Number of recursive dependencies: 154 -Run `cloud_details(, "brokenstick")` for more info +Run `cloud_details(, "codebook")` for more info
@@ -17,39 +17,123 @@ Run `cloud_details(, "brokenstick")` for more info * checking re-building of vignette outputs ... WARNING ``` Error(s) in re-building vignettes: - --- re-building ‘brokenstick.Rmd’ using rmarkdown - --- finished re-building ‘brokenstick.Rmd’ - - --- re-building ‘mainfunctions.Rmd’ using rmarkdown - Loading required package: brokenstick - Loading required package: dplyr + --- re-building ‘codebook.Rmd’ using rmarkdown Attaching package: 'dplyr' + The following objects are masked from 'package:stats': + + filter, lag + + The following objects are masked from 'package:base': ... - --- failed re-building ‘oldfriends.Rmd’ + ! Can't convert `haven_labelled` to . - --- re-building ‘perfectmodel.Rmd’ using rmarkdown - --- finished re-building ‘perfectmodel.Rmd’ + --- failed re-building ‘codebook_tutorial.Rmd’ + + SUMMARY: processing the following files failed: + ‘codebook.Rmd’ ‘codebook_qualtrics.Rmd’ ‘codebook_sav.Rmd’ + ‘codebook_tutorial.Rmd’ + + Error: Vignette re-building failed. + Execution halted + ``` + +## In both + +* checking package dependencies ... NOTE + ``` + Package suggested but not available for checking: ‘userfriendlyscience’ + ``` + +* checking dependencies in R code ... NOTE + ``` + Namespaces in Imports field not imported from: + ‘graphics’ ‘jsonlite’ ‘rlang’ ‘tidyselect’ ‘vctrs’ + All declared Imports should be used. + ``` + +* checking data for non-ASCII characters ... NOTE + ``` + Note: found 65 marked UTF-8 strings + ``` + +# cubble + +
+ +* Version: 0.1.1 +* GitHub: https://github.com/huizezhang-sherry/cubble +* Source code: https://github.com/cran/cubble +* Date/Publication: 2022-06-02 12:30:06 UTC +* Number of recursive dependencies: 137 + +Run `cloud_details(, "cubble")` for more info + +
+ +## Newly broken + +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Last 13 lines of output: + 4. │ └─vctrs::vec_rbind(!!!dots, .names_to = .id) + 5. └─vctrs (local) ``() + 6. └─vctrs::vec_default_cast(...) + 7. ├─base::withRestarts(...) + 8. │ └─base (local) withOneRestart(expr, restarts[[1L]]) + 9. │ └─base (local) doWithOneRestart(return(expr), restart) + 10. └─vctrs::stop_incompatible_cast(...) + 11. └─vctrs::stop_incompatible_type(...) + 12. └─vctrs:::stop_incompatible(...) + 13. └─vctrs:::stop_vctrs(...) + 14. └─rlang::abort(message, class = c(class, "vctrs_error"), ..., call = vctrs_error_call(call)) + + [ FAIL 2 | WARN 0 | SKIP 6 | PASS 31 ] + Error: Test failures + Execution halted + ``` + +## In both + +* checking re-building of vignette outputs ... WARNING + ``` + Error(s) in re-building vignettes: + --- re-building ‘aggregation.Rmd’ using rmarkdown + `summarise()` has grouped output by 'id'. You can override using the `.groups` + argument. + `summarise()` has grouped output by 'cluster', 'id'. You can override using the + `.groups` argument. + `geom_smooth()` using method = 'gam' and formula 'y ~ s(x, bs = "cs")' + Adding missing grouping variables: `id` + Quitting from lines 123-131 (aggregation.Rmd) + Error: processing vignette 'aggregation.Rmd' failed with diagnostics: + ... + Quitting from lines 75-79 (matching.Rmd) + Error: processing vignette 'matching.Rmd' failed with diagnostics: + Can't convert `..1` to . + --- failed re-building ‘matching.Rmd’ SUMMARY: processing the following files failed: - ‘mainfunctions.Rmd’ ‘oldfriends.Rmd’ + ‘aggregation.Rmd’ ‘matching.Rmd’ Error: Vignette re-building failed. Execution halted ``` -# psfmi +# cutpointr
-* Version: 1.0.0 -* GitHub: https://github.com/mwheymans/psfmi -* Source code: https://github.com/cran/psfmi -* Date/Publication: 2021-09-23 10:10:05 UTC -* Number of recursive dependencies: 156 +* Version: 1.1.2 +* GitHub: https://github.com/thie1e/cutpointr +* Source code: https://github.com/cran/cutpointr +* Date/Publication: 2022-04-13 18:12:29 UTC +* Number of recursive dependencies: 83 -Run `cloud_details(, "psfmi")` for more info +Run `cloud_details(, "cutpointr")` for more info
@@ -57,49 +141,275 @@ Run `cloud_details(, "psfmi")` for more info * checking examples ... ERROR ``` - Running examples in ‘psfmi-Ex.R’ failed + Running examples in ‘cutpointr-Ex.R’ failed The error most likely occurred in: - > ### Name: psfmi_validate - > ### Title: Internal validation and performance of logistic prediction - > ### models across Multiply Imputed datasets - > ### Aliases: psfmi_validate + > ### Name: cutpointr + > ### Title: Determine and evaluate optimal cutpoints + > ### Aliases: cutpointr cutpointr.default cutpointr.numeric > > ### ** Examples > + > library(cutpointr) ... - ! `strata` should be a single name or character value. - Backtrace: - ▆ - 1. └─psfmi::psfmi_validate(...) - 2. └─psfmi::cv_MI(...) - 3. ├─purrr::map(...) - 4. └─rsample::vfold_cv(data_orig, v = folds, strata = unlist(data_orig[pobj$Outcome])) - 5. └─rsample:::strata_check(strata, data) - 6. └─rlang::abort("`strata` should be a single name or character value.") + 13. └─vctrs::vec_default_cast(...) + 14. ├─base::withRestarts(...) + 15. │ └─base (local) withOneRestart(expr, restarts[[1L]]) + 16. │ └─base (local) doWithOneRestart(return(expr), restart) + 17. └─vctrs::stop_incompatible_cast(...) + 18. └─vctrs::stop_incompatible_type(...) + 19. └─vctrs:::stop_incompatible(...) + 20. └─vctrs:::stop_vctrs(...) + 21. └─rlang::abort(message, class = c(class, "vctrs_error"), ..., call = vctrs_error_call(call)) Execution halted ``` +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Last 13 lines of output: + 12. │ └─vctrs::list_unchop(...) + 13. └─vctrs (local) ``() + 14. └─vctrs::vec_default_cast(...) + 15. ├─base::withRestarts(...) + 16. │ └─base (local) withOneRestart(expr, restarts[[1L]]) + 17. │ └─base (local) doWithOneRestart(return(expr), restart) + 18. └─vctrs::stop_incompatible_cast(...) + 19. └─vctrs::stop_incompatible_type(...) + 20. └─vctrs:::stop_incompatible(...) + 21. └─vctrs:::stop_vctrs(...) + 22. └─rlang::abort(message, class = c(class, "vctrs_error"), ..., call = vctrs_error_call(call)) + + [ FAIL 10 | WARN 8 | SKIP 0 | PASS 273 ] + Error: Test failures + Execution halted + ``` + * checking re-building of vignette outputs ... WARNING ``` Error(s) in re-building vignettes: - --- re-building ‘MI_boot.Rmd’ using rmarkdown - --- finished re-building ‘MI_boot.Rmd’ + --- re-building ‘cutpointr.Rmd’ using rmarkdown + Quitting from lines 51-52 (cutpointr.Rmd) + Error: processing vignette 'cutpointr.Rmd' failed with diagnostics: + Can't convert `x[[1]]` to . + --- failed re-building ‘cutpointr.Rmd’ - --- re-building ‘MI_cv_naive.Rmd’ using rmarkdown - --- finished re-building ‘MI_cv_naive.Rmd’ - - --- re-building ‘Pool_Model_Performance.Rmd’ using rmarkdown - --- finished re-building ‘Pool_Model_Performance.Rmd’ + --- re-building ‘cutpointr_benchmarks.Rmd’ using rmarkdown + --- finished re-building ‘cutpointr_benchmarks.Rmd’ ... - --- finished re-building ‘psfmi_StabilityAnalysis.Rmd’ - --- re-building ‘psfmi_mice.Rmd’ using rmarkdown - --- finished re-building ‘psfmi_mice.Rmd’ + --- re-building ‘cutpointr_user_functions.Rmd’ using rmarkdown + --- finished re-building ‘cutpointr_user_functions.Rmd’ SUMMARY: processing the following files failed: - ‘cv_MI.Rmd’ ‘cv_MI_RR.Rmd’ ‘development_workflow.Rmd’ + ‘cutpointr.Rmd’ ‘cutpointr_bootstrapping.Rmd’ + ‘cutpointr_estimation.Rmd’ + + Error: Vignette re-building failed. + Execution halted + ``` + +# dm + +
+ +* Version: 1.0.3 +* GitHub: https://github.com/cynkra/dm +* Source code: https://github.com/cran/dm +* Date/Publication: 2022-10-12 15:42:33 UTC +* Number of recursive dependencies: 152 + +Run `cloud_details(, "dm")` for more info + +
+ +## Newly broken + +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Last 13 lines of output: + + `actual$parent_key_cols[[4]]` is absent + `expected$parent_key_cols[[4]]` is a character vector ('h') + + `actual$parent_key_cols[[5]]` is absent + `expected$parent_key_cols[[5]]` is a character vector ('n') + Backtrace: + ▆ + 1. └─dm:::expect_equivalent_dm(...) at test-dm_wrap.R:73:2 + 2. └─dm:::expect_equivalent_tbl(...) at tests/testthat/helper-expectations.R:13:4 + 3. └─testthat::expect_identical(...) at tests/testthat/helper-expectations.R:76:2 + + [ FAIL 18 | WARN 0 | SKIP 191 | PASS 1275 ] + Error: Test failures + Execution halted + ``` + +# dplyr + +
+ +* Version: 1.0.10 +* GitHub: https://github.com/tidyverse/dplyr +* Source code: https://github.com/cran/dplyr +* Date/Publication: 2022-09-01 09:20:06 UTC +* Number of recursive dependencies: 97 + +Run `cloud_details(, "dplyr")` for more info + +
+ +## Newly broken + +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Last 13 lines of output: + ── Failure ('test-group_split.R:115'): group_split() works with subclasses implementing group_by() / ungroup() ── + group_split(df, x) (`actual`) not identical to `expect` (`expected`). + + `class(attr(actual, 'ptype'))`: "foo_df" "tbl_df" "tbl" "data.frame" + `class(attr(expected, 'ptype'))`: "tbl_df" "tbl" "data.frame" + + `class(actual[[1]])`: "foo_df" "tbl_df" "tbl" "data.frame" + `class(expected[[1]])`: "tbl_df" "tbl" "data.frame" + + `class(actual[[2]])`: "foo_df" "tbl_df" "tbl" "data.frame" + `class(expected[[2]])`: "tbl_df" "tbl" "data.frame" + + [ FAIL 1 | WARN 109 | SKIP 107 | PASS 2364 ] + Error: Test failures + Execution halted + ``` + +## In both + +* checking data for non-ASCII characters ... NOTE + ``` + Note: found 4 marked UTF-8 strings + ``` + +# gratia + +
+ +* Version: 0.7.3 +* GitHub: https://github.com/gavinsimpson/gratia +* Source code: https://github.com/cran/gratia +* Date/Publication: 2022-05-09 11:20:03 UTC +* Number of recursive dependencies: 83 + +Run `cloud_details(, "gratia")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘gratia-Ex.R’ failed + The error most likely occurred in: + + > ### Name: basis + > ### Title: Basis expansions for smooths + > ### Aliases: basis + > + > ### ** Examples + > + > load_mgcv() + ... + 7. \-vctrs::vec_default_cast(...) + 8. +-base::withRestarts(...) + 9. | \-base (local) withOneRestart(expr, restarts[[1L]]) + 10. | \-base (local) doWithOneRestart(return(expr), restart) + 11. \-vctrs::stop_incompatible_cast(...) + 12. \-vctrs::stop_incompatible_type(...) + 13. \-vctrs:::stop_incompatible(...) + 14. \-vctrs:::stop_vctrs(...) + 15. \-rlang::abort(message, class = c(class, "vctrs_error"), ..., call = vctrs_error_call(call)) + Execution halted + ``` + +* checking tests ... ERROR + ``` + Running ‘test-all.R’ + Running the tests in ‘tests/test-all.R’ failed. + Last 13 lines of output: + • hgam-paper/hgam-paper-bird-move-model-1.svg + • hgam-paper/hgam-paper-bird-move-model-2.svg + • hgam-paper/hgam-paper-bird-move-model-3.svg + • hgam-paper/hgam-paper-bird-move-model-5.svg + • hgam-paper/hgam-paper-co2-model-1.svg + • hgam-paper/hgam-paper-co2-model-2.svg + • hgam-paper/hgam-paper-co2-model-3.svg + • hgam-paper/hgam-paper-co2-model-4.svg + • hgam-paper/hgam-paper-co2-model-5.svg + • hgam-paper/hgam-paper-zoop-model-4.svg + • hgam-paper/hgam-paper-zoop-model-5.svg + • rootograms/draw-gaussian-rootogram.svg + • rootograms/draw-neg-bin-rootogram.svg + Error: Test failures + Execution halted + ``` + +# groupr + +
+ +* Version: 0.1.0 +* GitHub: https://github.com/ngriffiths21/groupr +* Source code: https://github.com/cran/groupr +* Date/Publication: 2020-10-14 12:30:06 UTC +* Number of recursive dependencies: 63 + +Run `cloud_details(, "groupr")` for more info + +
+ +## Newly broken + +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Last 13 lines of output: + Please report it at with a reprex () and the full backtrace. + Backtrace: + ▆ + 1. ├─... %>% group_by2(is_ok, grp) at test_pivots.R:3:0 + 2. ├─groupr::group_by2(., is_ok, grp) + 3. ├─groupr:::group_by2.data.frame(., is_ok, grp) + 4. │ └─groupr:::group_by2_ok(data, dots) + 5. │ └─groupr:::igrouped_df(grouped, groups_out) + 6. │ └─vctrs::vec_rbind(groups, data.frame()) + 7. └─rlang:::stop_internal_c_lib(...) + 8. └─rlang::abort(message, call = call, .internal = TRUE, .frame = frame) + + [ FAIL 3 | WARN 0 | SKIP 0 | PASS 0 ] + Error: Test failures + Execution halted + ``` + +* checking re-building of vignette outputs ... WARNING + ``` + Error(s) in re-building vignettes: + ... + --- re-building ‘introduction.Rmd’ using rmarkdown + Quitting from lines 33-35 (introduction.Rmd) + Error: processing vignette 'introduction.Rmd' failed with diagnostics: + Column `.rows` (size 0) must match the data frame (size 2). + ℹ In file 'slice.c' at line 188. + ℹ This is an internal error that was detected in the vctrs package. + Please report it at with a reprex () and the full backtrace. + --- failed re-building ‘introduction.Rmd’ + + SUMMARY: processing the following file failed: + ‘introduction.Rmd’ Error: Vignette re-building failed. Execution halted @@ -107,9 +417,363 @@ Run `cloud_details(, "psfmi")` for more info ## In both -* checking dependencies in R code ... NOTE +* checking LazyData ... NOTE ``` - Namespace in Imports field not imported from: ‘miceadds’ - All declared Imports should be used. + 'LazyData' is specified without a 'data' directory + ``` + +# multidplyr + +
+ +* Version: 0.1.2 +* GitHub: https://github.com/tidyverse/multidplyr +* Source code: https://github.com/cran/multidplyr +* Date/Publication: 2022-09-26 19:40:02 UTC +* Number of recursive dependencies: 79 + +Run `cloud_details(, "multidplyr")` for more info + +
+ +## Newly broken + +* checking re-building of vignette outputs ... WARNING + ``` + Error(s) in re-building vignettes: + ... + --- re-building ‘multidplyr.Rmd’ using rmarkdown + Quitting from lines 81-85 (multidplyr.Rmd) + Error: processing vignette 'multidplyr.Rmd' failed with diagnostics: + Can't convert `..1` to . + --- failed re-building ‘multidplyr.Rmd’ + + SUMMARY: processing the following file failed: + ‘multidplyr.Rmd’ + + Error: Vignette re-building failed. + Execution halted + ``` + +# ricu + +
+ +* Version: 0.5.3 +* GitHub: https://github.com/eth-mds/ricu +* Source code: https://github.com/cran/ricu +* Date/Publication: 2022-07-12 10:50:14 UTC +* Number of recursive dependencies: 114 + +Run `cloud_details(, "ricu")` for more info + +
+ +## Newly broken + +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Last 13 lines of output: + See . + Backtrace: + ▆ + 1. ├─testthat::expect_identical(as_src_cfg(mimic_demo), mi) at test-config.R:19:2 + 2. │ └─testthat::quasi_label(enquo(object), label, arg = "object") + 3. │ └─rlang::eval_bare(expr, quo_get_env(quo)) + 4. ├─ricu::as_src_cfg(mimic_demo) + 5. ├─ricu:::as_src_cfg.src_env(mimic_demo) + 6. │ └─vctrs::vec_unchop(lapply(x, as_col_cfg), name_spec = "{inner}") + 7. │ └─vctrs::list_unchop(...) + 8. └─rlang::abort(message = message, call = call) + + [ FAIL 1 | WARN 1 | SKIP 7 | PASS 592 ] + Error: Test failures + Execution halted + ``` + +# srvyr + +
+ +* Version: 1.1.2 +* GitHub: https://github.com/gergness/srvyr +* Source code: https://github.com/cran/srvyr +* Date/Publication: 2022-10-05 23:00:06 UTC +* Number of recursive dependencies: 87 + +Run `cloud_details(, "srvyr")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘srvyr-Ex.R’ failed + The error most likely occurred in: + + > ### Name: as_survey_twophase + > ### Title: Create a tbl_svy survey object using two phase design + > ### Aliases: as_survey_twophase as_survey_twophase.data.frame + > ### as_survey_twophase.twophase2 + > + > ### ** Examples + > + ... + 13. └─vctrs::vec_default_cast(...) + 14. ├─base::withRestarts(...) + 15. │ └─base (local) withOneRestart(expr, restarts[[1L]]) + 16. │ └─base (local) doWithOneRestart(return(expr), restart) + 17. └─vctrs::stop_incompatible_cast(...) + 18. └─vctrs::stop_incompatible_type(...) + 19. └─vctrs:::stop_incompatible(...) + 20. └─vctrs:::stop_vctrs(...) + 21. └─rlang::abort(message, class = c(class, "vctrs_error"), ..., call = vctrs_error_call(call)) + Execution halted + ``` + +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Last 13 lines of output: + ! Can't convert `..1` to . + ── Error ('test_survey_statistics.r:17'): (code run outside of `test_that()`) ── + Error in `dplyr::summarise(.data$variables, ..., .groups = .groups)`: Problem while computing `api_ratio = survey_ratio(api00, api99)`. + Caused by error in `FUN()`: + ! Can't convert `..1` to . + ── Error ('test_survey_statistics_basic.r:17'): (code run outside of `test_that()`) ── + Error in `dplyr::summarise(.data$variables, ..., .groups = .groups)`: Problem while computing `survey_mean = survey_mean(api99)`. + Caused by error in `FUN()`: + ! Can't convert `..1` to . + + [ FAIL 49 | WARN 6 | SKIP 0 | PASS 127 ] + Error: Test failures + In addition: Warning message: + call dbDisconnect() when finished working with a connection + Execution halted + ``` + +* checking re-building of vignette outputs ... WARNING + ``` + Error(s) in re-building vignettes: + --- re-building ‘extending-srvyr.Rmd’ using rmarkdown + --- finished re-building ‘extending-srvyr.Rmd’ + + --- re-building ‘srvyr-database.Rmd’ using rmarkdown + --- finished re-building ‘srvyr-database.Rmd’ + + --- re-building ‘srvyr-vs-survey.Rmd’ using rmarkdown + Loading required package: grid + Loading required package: Matrix + ... + "ci")`. + Caused by error in `FUN()`: + ! Can't convert `..1` to . + --- failed re-building ‘srvyr-vs-survey.Rmd’ + + SUMMARY: processing the following file failed: + ‘srvyr-vs-survey.Rmd’ + + Error: Vignette re-building failed. + Execution halted + ``` + +## In both + +* checking package dependencies ... NOTE + ``` + Package suggested but not available for checking: ‘convey’ + ``` + +# tibbletime + +
+ +* Version: 0.1.6 +* GitHub: https://github.com/business-science/tibbletime +* Source code: https://github.com/cran/tibbletime +* Date/Publication: 2020-07-21 13:50:02 UTC +* Number of recursive dependencies: 86 + +Run `cloud_details(, "tibbletime")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘tibbletime-Ex.R’ failed + The error most likely occurred in: + + > ### Name: collapse_index + > ### Title: Collapse an index vector so that all observations in an interval + > ### share the same date + > ### Aliases: collapse_index + > + > ### ** Examples + > + ... + 14. └─vctrs::vec_default_cast(...) + 15. ├─base::withRestarts(...) + 16. │ └─base (local) withOneRestart(expr, restarts[[1L]]) + 17. │ └─base (local) doWithOneRestart(return(expr), restart) + 18. └─vctrs::stop_incompatible_cast(...) + 19. └─vctrs::stop_incompatible_type(...) + 20. └─vctrs:::stop_incompatible(...) + 21. └─vctrs:::stop_vctrs(...) + 22. └─rlang::abort(message, class = c(class, "vctrs_error"), ..., call = vctrs_error_call(call)) + Execution halted + ``` + +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Last 13 lines of output: + data[[1]])`. + Caused by error in `vctrs::as_list_of()`: + ! Can't convert `..1` to . + ── Error ('test_compat-tidyr.R:47'): unnest() with index goes back to tbl_time ── + + Error in `dplyr::mutate(.data_nested, `:=`(!!nested_column_sym, purrr::map(!!nested_column_sym, + ~reconstruct(.x, ..original_data))), `:=`(!!nested_column_sym, + vctrs::as_list_of(!!nested_column_sym, .ptype = (!!nested_column_sym)[[1]])))`: Problem while computing `data = vctrs::as_list_of(data, .ptype = + data[[1]])`. + Caused by error in `vctrs::as_list_of()`: + ! Can't convert `..1` to . + + [ FAIL 2 | WARN 2 | SKIP 0 | PASS 141 ] + Error: Test failures + Execution halted + ``` + +# tidyjson + +
+ +* Version: 0.3.1 +* GitHub: https://github.com/colearendt/tidyjson +* Source code: https://github.com/cran/tidyjson +* Date/Publication: 2020-05-31 21:30:03 UTC +* Number of recursive dependencies: 96 + +Run `cloud_details(, "tidyjson")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘tidyjson-Ex.R’ failed + The error most likely occurred in: + + > ### Name: json_schema + > ### Title: Create a schema for a JSON document or collection + > ### Aliases: json_schema + > + > ### ** Examples + > + > + ... + 12. └─vctrs::vec_default_cast(...) + 13. ├─base::withRestarts(...) + 14. │ └─base (local) withOneRestart(expr, restarts[[1L]]) + 15. │ └─base (local) doWithOneRestart(return(expr), restart) + 16. └─vctrs::stop_incompatible_cast(...) + 17. └─vctrs::stop_incompatible_type(...) + 18. └─vctrs:::stop_incompatible(...) + 19. └─vctrs:::stop_vctrs(...) + 20. └─rlang::abort(message, class = c(class, "vctrs_error"), ..., call = vctrs_error_call(call)) + Execution halted + ``` + +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Last 13 lines of output: + 12. │ └─vctrs::vec_rbind(!!!dots, .names_to = .id) + 13. └─vctrs (local) ``() + 14. └─vctrs::vec_default_cast(...) + 15. ├─base::withRestarts(...) + 16. │ └─base (local) withOneRestart(expr, restarts[[1L]]) + 17. │ └─base (local) doWithOneRestart(return(expr), restart) + 18. └─vctrs::stop_incompatible_cast(...) + 19. └─vctrs::stop_incompatible_type(...) + 20. └─vctrs:::stop_incompatible(...) + 21. └─vctrs:::stop_vctrs(...) + 22. └─rlang::abort(message, class = c(class, "vctrs_error"), ..., call = vctrs_error_call(call)) + + [ FAIL 8 | WARN 0 | SKIP 10 | PASS 347 ] + Error: Test failures + Execution halted + ``` + +* checking re-building of vignette outputs ... WARNING + ``` + Error(s) in re-building vignettes: + --- re-building ‘introduction-to-tidyjson.Rmd’ using rmarkdown + + Attaching package: 'tidyjson' + + The following object is masked from 'package:stats': + + filter + + + ... + Quitting from lines 327-328 (visualizing-json.Rmd) + Error: processing vignette 'visualizing-json.Rmd' failed with diagnostics: + Can't convert `..1` to . + --- failed re-building ‘visualizing-json.Rmd’ + + SUMMARY: processing the following file failed: + ‘visualizing-json.Rmd’ + + Error: Vignette re-building failed. + Execution halted + ``` + +# yamlet + +
+ +* Version: 0.9.6 +* GitHub: https://github.com/bergsmat/yamlet +* Source code: https://github.com/cran/yamlet +* Date/Publication: 2022-09-20 20:10:01 UTC +* Number of recursive dependencies: 81 + +Run `cloud_details(, "yamlet")` for more info + +
+ +## Newly broken + +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Last 13 lines of output: + 12. │ └─vctrs::vec_rbind(!!!dots, .names_to = .id) + 13. └─vctrs (local) ``() + 14. └─vctrs::vec_default_cast(...) + 15. ├─base::withRestarts(...) + 16. │ └─base (local) withOneRestart(expr, restarts[[1L]]) + 17. │ └─base (local) doWithOneRestart(return(expr), restart) + 18. └─vctrs::stop_incompatible_cast(...) + 19. └─vctrs::stop_incompatible_type(...) + 20. └─vctrs:::stop_incompatible(...) + 21. └─vctrs:::stop_vctrs(...) + 22. └─rlang::abort(message, class = c(class, "vctrs_error"), ..., call = vctrs_error_call(call)) + + [ FAIL 1 | WARN 0 | SKIP 2 | PASS 402 ] + Error: Test failures + Execution halted ``` From 1a5f476392346a9b00b090b3a8bdc72d94abd841 Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Tue, 18 Oct 2022 11:10:30 +0200 Subject: [PATCH 173/312] Restore same-type fallback for data frame cast --- R/cast.R | 28 +- R/type-data-frame.R | 8 + revdep/README.md | 12 +- revdep/cran.md | 26 +- revdep/problems.md | 451 ++--------------------- tests/testthat/_snaps/bind.md | 8 - tests/testthat/_snaps/type-data-frame.md | 13 +- tests/testthat/_snaps/type-tibble.md | 14 +- tests/testthat/helper-s3.R | 6 + tests/testthat/test-bind.R | 7 +- tests/testthat/test-type-data-frame.R | 8 +- tests/testthat/test-type-tibble.R | 8 +- 12 files changed, 86 insertions(+), 503 deletions(-) diff --git a/R/cast.R b/R/cast.R index 5e9abb2dd..00b001425 100644 --- a/R/cast.R +++ b/R/cast.R @@ -187,8 +187,8 @@ vec_default_cast <- function(x, return(x) } - # If both data frames, fall back to base data frame - if (is.data.frame(x) && is_bare_df(to)) { + # Data frames have special bare class and same type fallbacks + if (is.data.frame(x) && is.data.frame(to)) { out <- df_cast_opts( x, to, @@ -199,16 +199,28 @@ vec_default_cast <- function(x, call = call ) - if (inherits(to, "tbl_df")) { - out <- df_as_tibble(out) + # Bare-class fallback for data frames + if (is_bare_df(to)) { + if (inherits(to, "tbl_df")) { + out <- df_as_tibble(out) + } + return(out) } - return(out) + # Same-type fallback for data frames. If attributes of the empty + # data frames are congruent, just reproduce these attributes. This + # eschews any constraints on rows and cols that `[` and `[<-` + # methods might have. If that is a problem, the class needs to + # implement vctrs methods. + if (is_same_type(x[0, 0], to[0, 0])) { + attributes(out) <- c(df_attrib(out), non_df_attrib(to)) + return(out) + } + + # else fallthrough } - # Data frames no longer have an is-same-type fallback because their - # common types now fall back to bare data frames - if (!is.data.frame(x) && is_same_type(x, to)) { + if (is_same_type(x, to)) { return(x) } diff --git a/R/type-data-frame.R b/R/type-data-frame.R index 77e04f65b..5b7d148cc 100644 --- a/R/type-data-frame.R +++ b/R/type-data-frame.R @@ -385,3 +385,11 @@ df_lossy_cast <- function(out, is_informative_error.vctrs_error_cast_lossy_dropped <- function(x, ...) { FALSE } + +df_attrib <- function(x) { + attributes(x)[c("row.names", "names")] +} +non_df_attrib <- function(x) { + attrib <- attributes(x) + attrib[!names(attrib) %in% c("row.names", "names")] +} diff --git a/revdep/README.md b/revdep/README.md index 274eeb1c9..bfb79d77c 100644 --- a/revdep/README.md +++ b/revdep/README.md @@ -33,21 +33,15 @@ |[brokenstick](problems.md#brokenstick)|2.3.0 | |__+1__ | | |[psfmi](problems.md#psfmi)|1.0.0 |__+1__ |__+1__ |1 | -## New problems (13) +## New problems (7) -|package |version |error |warning |note | -|:----------|:-------|:------|:-------|:----| -|[codebook](problems.md#codebook)|0.9.2 | |__+1__ |3 | +|package |version |error |warning |note | +|:-------|:-------|:------|:-------|:----| |[cubble](problems.md#cubble)|0.1.1 |__+1__ |1 | | -|[cutpointr](problems.md#cutpointr)|1.1.2 |__+2__ |__+1__ | | |[dm](problems.md#dm)|1.0.3 |__+1__ | | | |[dplyr](problems.md#dplyr)|1.0.10 |__+1__ | |1 | -|[gratia](problems.md#gratia)|0.7.3 |__+2__ | | | |[groupr](problems.md#groupr)|0.1.0 |__+1__ |__+1__ |1 | -|[multidplyr](problems.md#multidplyr)|0.1.2 | |__+1__ | | |[ricu](problems.md#ricu)|0.5.3 |__+1__ | | | |[srvyr](problems.md#srvyr)|1.1.2 |__+2__ |__+1__ |1 | -|[tibbletime](problems.md#tibbletime)|0.1.6 |__+2__ | | | -|[tidyjson](problems.md#tidyjson)|0.3.1 |__+2__ |__+1__ | | |[yamlet](problems.md#yamlet)|0.9.6 |__+1__ | | | diff --git a/revdep/cran.md b/revdep/cran.md index 3f119cb66..6b69da963 100644 --- a/revdep/cran.md +++ b/revdep/cran.md @@ -2,7 +2,7 @@ We checked 3546 reverse dependencies (3534 from CRAN + 12 from Bioconductor), comparing R CMD check results across CRAN and dev versions of this package. - * We saw 13 new problems + * We saw 7 new problems * We failed to check 0 packages Issues with CRAN packages are summarised below. @@ -10,34 +10,19 @@ Issues with CRAN packages are summarised below. ### New problems (This reports the first line of each new failure) -* codebook - checking re-building of vignette outputs ... WARNING - * cubble checking tests ... ERROR -* cutpointr - checking examples ... ERROR - checking tests ... ERROR - checking re-building of vignette outputs ... WARNING - * dm checking tests ... ERROR * dplyr checking tests ... ERROR -* gratia - checking examples ... ERROR - checking tests ... ERROR - * groupr checking tests ... ERROR checking re-building of vignette outputs ... WARNING -* multidplyr - checking re-building of vignette outputs ... WARNING - * ricu checking tests ... ERROR @@ -46,15 +31,6 @@ Issues with CRAN packages are summarised below. checking tests ... ERROR checking re-building of vignette outputs ... WARNING -* tibbletime - checking examples ... ERROR - checking tests ... ERROR - -* tidyjson - checking examples ... ERROR - checking tests ... ERROR - checking re-building of vignette outputs ... WARNING - * yamlet checking tests ... ERROR diff --git a/revdep/problems.md b/revdep/problems.md index 0359d3e31..487d05010 100644 --- a/revdep/problems.md +++ b/revdep/problems.md @@ -1,63 +1,3 @@ -# codebook - -
- -* Version: 0.9.2 -* GitHub: https://github.com/rubenarslan/codebook -* Source code: https://github.com/cran/codebook -* Date/Publication: 2020-06-06 23:40:03 UTC -* Number of recursive dependencies: 154 - -Run `cloud_details(, "codebook")` for more info - -
- -## Newly broken - -* checking re-building of vignette outputs ... WARNING - ``` - Error(s) in re-building vignettes: - --- re-building ‘codebook.Rmd’ using rmarkdown - - Attaching package: 'dplyr' - - The following objects are masked from 'package:stats': - - filter, lag - - The following objects are masked from 'package:base': - ... - ! Can't convert `haven_labelled` to . - - --- failed re-building ‘codebook_tutorial.Rmd’ - - SUMMARY: processing the following files failed: - ‘codebook.Rmd’ ‘codebook_qualtrics.Rmd’ ‘codebook_sav.Rmd’ - ‘codebook_tutorial.Rmd’ - - Error: Vignette re-building failed. - Execution halted - ``` - -## In both - -* checking package dependencies ... NOTE - ``` - Package suggested but not available for checking: ‘userfriendlyscience’ - ``` - -* checking dependencies in R code ... NOTE - ``` - Namespaces in Imports field not imported from: - ‘graphics’ ‘jsonlite’ ‘rlang’ ‘tidyselect’ ‘vctrs’ - All declared Imports should be used. - ``` - -* checking data for non-ASCII characters ... NOTE - ``` - Note: found 65 marked UTF-8 strings - ``` - # cubble
@@ -123,94 +63,6 @@ Run `cloud_details(, "cubble")` for more info Execution halted ``` -# cutpointr - -
- -* Version: 1.1.2 -* GitHub: https://github.com/thie1e/cutpointr -* Source code: https://github.com/cran/cutpointr -* Date/Publication: 2022-04-13 18:12:29 UTC -* Number of recursive dependencies: 83 - -Run `cloud_details(, "cutpointr")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘cutpointr-Ex.R’ failed - The error most likely occurred in: - - > ### Name: cutpointr - > ### Title: Determine and evaluate optimal cutpoints - > ### Aliases: cutpointr cutpointr.default cutpointr.numeric - > - > ### ** Examples - > - > library(cutpointr) - ... - 13. └─vctrs::vec_default_cast(...) - 14. ├─base::withRestarts(...) - 15. │ └─base (local) withOneRestart(expr, restarts[[1L]]) - 16. │ └─base (local) doWithOneRestart(return(expr), restart) - 17. └─vctrs::stop_incompatible_cast(...) - 18. └─vctrs::stop_incompatible_type(...) - 19. └─vctrs:::stop_incompatible(...) - 20. └─vctrs:::stop_vctrs(...) - 21. └─rlang::abort(message, class = c(class, "vctrs_error"), ..., call = vctrs_error_call(call)) - Execution halted - ``` - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Last 13 lines of output: - 12. │ └─vctrs::list_unchop(...) - 13. └─vctrs (local) ``() - 14. └─vctrs::vec_default_cast(...) - 15. ├─base::withRestarts(...) - 16. │ └─base (local) withOneRestart(expr, restarts[[1L]]) - 17. │ └─base (local) doWithOneRestart(return(expr), restart) - 18. └─vctrs::stop_incompatible_cast(...) - 19. └─vctrs::stop_incompatible_type(...) - 20. └─vctrs:::stop_incompatible(...) - 21. └─vctrs:::stop_vctrs(...) - 22. └─rlang::abort(message, class = c(class, "vctrs_error"), ..., call = vctrs_error_call(call)) - - [ FAIL 10 | WARN 8 | SKIP 0 | PASS 273 ] - Error: Test failures - Execution halted - ``` - -* checking re-building of vignette outputs ... WARNING - ``` - Error(s) in re-building vignettes: - --- re-building ‘cutpointr.Rmd’ using rmarkdown - Quitting from lines 51-52 (cutpointr.Rmd) - Error: processing vignette 'cutpointr.Rmd' failed with diagnostics: - Can't convert `x[[1]]` to . - --- failed re-building ‘cutpointr.Rmd’ - - --- re-building ‘cutpointr_benchmarks.Rmd’ using rmarkdown - --- finished re-building ‘cutpointr_benchmarks.Rmd’ - - ... - - --- re-building ‘cutpointr_user_functions.Rmd’ using rmarkdown - --- finished re-building ‘cutpointr_user_functions.Rmd’ - - SUMMARY: processing the following files failed: - ‘cutpointr.Rmd’ ‘cutpointr_bootstrapping.Rmd’ - ‘cutpointr_estimation.Rmd’ - - Error: Vignette re-building failed. - Execution halted - ``` - # dm
@@ -294,69 +146,6 @@ Run `cloud_details(, "dplyr")` for more info Note: found 4 marked UTF-8 strings ``` -# gratia - -
- -* Version: 0.7.3 -* GitHub: https://github.com/gavinsimpson/gratia -* Source code: https://github.com/cran/gratia -* Date/Publication: 2022-05-09 11:20:03 UTC -* Number of recursive dependencies: 83 - -Run `cloud_details(, "gratia")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘gratia-Ex.R’ failed - The error most likely occurred in: - - > ### Name: basis - > ### Title: Basis expansions for smooths - > ### Aliases: basis - > - > ### ** Examples - > - > load_mgcv() - ... - 7. \-vctrs::vec_default_cast(...) - 8. +-base::withRestarts(...) - 9. | \-base (local) withOneRestart(expr, restarts[[1L]]) - 10. | \-base (local) doWithOneRestart(return(expr), restart) - 11. \-vctrs::stop_incompatible_cast(...) - 12. \-vctrs::stop_incompatible_type(...) - 13. \-vctrs:::stop_incompatible(...) - 14. \-vctrs:::stop_vctrs(...) - 15. \-rlang::abort(message, class = c(class, "vctrs_error"), ..., call = vctrs_error_call(call)) - Execution halted - ``` - -* checking tests ... ERROR - ``` - Running ‘test-all.R’ - Running the tests in ‘tests/test-all.R’ failed. - Last 13 lines of output: - • hgam-paper/hgam-paper-bird-move-model-1.svg - • hgam-paper/hgam-paper-bird-move-model-2.svg - • hgam-paper/hgam-paper-bird-move-model-3.svg - • hgam-paper/hgam-paper-bird-move-model-5.svg - • hgam-paper/hgam-paper-co2-model-1.svg - • hgam-paper/hgam-paper-co2-model-2.svg - • hgam-paper/hgam-paper-co2-model-3.svg - • hgam-paper/hgam-paper-co2-model-4.svg - • hgam-paper/hgam-paper-co2-model-5.svg - • hgam-paper/hgam-paper-zoop-model-4.svg - • hgam-paper/hgam-paper-zoop-model-5.svg - • rootograms/draw-gaussian-rootogram.svg - • rootograms/draw-neg-bin-rootogram.svg - Error: Test failures - Execution halted - ``` - # groupr
@@ -422,39 +211,6 @@ Run `cloud_details(, "groupr")` for more info 'LazyData' is specified without a 'data' directory ``` -# multidplyr - -
- -* Version: 0.1.2 -* GitHub: https://github.com/tidyverse/multidplyr -* Source code: https://github.com/cran/multidplyr -* Date/Publication: 2022-09-26 19:40:02 UTC -* Number of recursive dependencies: 79 - -Run `cloud_details(, "multidplyr")` for more info - -
- -## Newly broken - -* checking re-building of vignette outputs ... WARNING - ``` - Error(s) in re-building vignettes: - ... - --- re-building ‘multidplyr.Rmd’ using rmarkdown - Quitting from lines 81-85 (multidplyr.Rmd) - Error: processing vignette 'multidplyr.Rmd' failed with diagnostics: - Can't convert `..1` to . - --- failed re-building ‘multidplyr.Rmd’ - - SUMMARY: processing the following file failed: - ‘multidplyr.Rmd’ - - Error: Vignette re-building failed. - Execution halted - ``` - # ricu
@@ -514,23 +270,23 @@ Run `cloud_details(, "srvyr")` for more info Running examples in ‘srvyr-Ex.R’ failed The error most likely occurred in: - > ### Name: as_survey_twophase - > ### Title: Create a tbl_svy survey object using two phase design - > ### Aliases: as_survey_twophase as_survey_twophase.data.frame - > ### as_survey_twophase.twophase2 + > ### Name: cascade + > ### Title: Summarise multiple values into cascading groups + > ### Aliases: cascade > > ### ** Examples > + > library(survey) ... - 13. └─vctrs::vec_default_cast(...) - 14. ├─base::withRestarts(...) - 15. │ └─base (local) withOneRestart(expr, restarts[[1L]]) - 16. │ └─base (local) doWithOneRestart(return(expr), restart) - 17. └─vctrs::stop_incompatible_cast(...) - 18. └─vctrs::stop_incompatible_type(...) - 19. └─vctrs:::stop_incompatible(...) - 20. └─vctrs:::stop_vctrs(...) - 21. └─rlang::abort(message, class = c(class, "vctrs_error"), ..., call = vctrs_error_call(call)) + 8. └─vctrs (local) ``() + 9. └─vctrs::vec_default_ptype2(...) + 10. ├─base::withRestarts(...) + 11. │ └─base (local) withOneRestart(expr, restarts[[1L]]) + 12. │ └─base (local) doWithOneRestart(return(expr), restart) + 13. └─vctrs::stop_incompatible_type(...) + 14. └─vctrs:::stop_incompatible(...) + 15. └─vctrs:::stop_vctrs(...) + 16. └─rlang::abort(message, class = c(class, "vctrs_error"), ..., call = vctrs_error_call(call)) Execution halted ``` @@ -539,20 +295,20 @@ Run `cloud_details(, "srvyr")` for more info Running ‘testthat.R’ Running the tests in ‘tests/testthat.R’ failed. Last 13 lines of output: - ! Can't convert `..1` to . - ── Error ('test_survey_statistics.r:17'): (code run outside of `test_that()`) ── - Error in `dplyr::summarise(.data$variables, ..., .groups = .groups)`: Problem while computing `api_ratio = survey_ratio(api00, api99)`. - Caused by error in `FUN()`: - ! Can't convert `..1` to . - ── Error ('test_survey_statistics_basic.r:17'): (code run outside of `test_that()`) ── - Error in `dplyr::summarise(.data$variables, ..., .groups = .groups)`: Problem while computing `survey_mean = survey_mean(api99)`. - Caused by error in `FUN()`: - ! Can't convert `..1` to . + ── Failure (???): deff and df work for grouped survey total ──────────────────── + `x` not equivalent to `y`. + Length mismatch: comparison on first 2 components + Component "survey_total": Length mismatch: comparison on first 3 components + Component "survey_total": Component 1: Numeric: lengths (3, 1) differ + Component "survey_total": Component 2: Numeric: lengths (3, 1) differ + Component "survey_total": Component 3: Numeric: lengths (3, 1) differ + Backtrace: + ▆ + 1. └─global expect_df_equal(out_srvyr, select(out_survey, -survey_total_se)) + 2. └─testthat::expect_equivalent(x, y) - [ FAIL 49 | WARN 6 | SKIP 0 | PASS 127 ] + [ FAIL 47 | WARN 12 | SKIP 0 | PASS 216 ] Error: Test failures - In addition: Warning message: - call dbDisconnect() when finished working with a connection Execution halted ``` @@ -569,9 +325,9 @@ Run `cloud_details(, "srvyr")` for more info Loading required package: grid Loading required package: Matrix ... - "ci")`. - Caused by error in `FUN()`: - ! Can't convert `..1` to . + ! Problem while computing column `n`. + Caused by error in `initialize()`: + ! attempt to use zero-length variable name --- failed re-building ‘srvyr-vs-survey.Rmd’ SUMMARY: processing the following file failed: @@ -588,157 +344,6 @@ Run `cloud_details(, "srvyr")` for more info Package suggested but not available for checking: ‘convey’ ``` -# tibbletime - -
- -* Version: 0.1.6 -* GitHub: https://github.com/business-science/tibbletime -* Source code: https://github.com/cran/tibbletime -* Date/Publication: 2020-07-21 13:50:02 UTC -* Number of recursive dependencies: 86 - -Run `cloud_details(, "tibbletime")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘tibbletime-Ex.R’ failed - The error most likely occurred in: - - > ### Name: collapse_index - > ### Title: Collapse an index vector so that all observations in an interval - > ### share the same date - > ### Aliases: collapse_index - > - > ### ** Examples - > - ... - 14. └─vctrs::vec_default_cast(...) - 15. ├─base::withRestarts(...) - 16. │ └─base (local) withOneRestart(expr, restarts[[1L]]) - 17. │ └─base (local) doWithOneRestart(return(expr), restart) - 18. └─vctrs::stop_incompatible_cast(...) - 19. └─vctrs::stop_incompatible_type(...) - 20. └─vctrs:::stop_incompatible(...) - 21. └─vctrs:::stop_vctrs(...) - 22. └─rlang::abort(message, class = c(class, "vctrs_error"), ..., call = vctrs_error_call(call)) - Execution halted - ``` - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Last 13 lines of output: - data[[1]])`. - Caused by error in `vctrs::as_list_of()`: - ! Can't convert `..1` to . - ── Error ('test_compat-tidyr.R:47'): unnest() with index goes back to tbl_time ── - - Error in `dplyr::mutate(.data_nested, `:=`(!!nested_column_sym, purrr::map(!!nested_column_sym, - ~reconstruct(.x, ..original_data))), `:=`(!!nested_column_sym, - vctrs::as_list_of(!!nested_column_sym, .ptype = (!!nested_column_sym)[[1]])))`: Problem while computing `data = vctrs::as_list_of(data, .ptype = - data[[1]])`. - Caused by error in `vctrs::as_list_of()`: - ! Can't convert `..1` to . - - [ FAIL 2 | WARN 2 | SKIP 0 | PASS 141 ] - Error: Test failures - Execution halted - ``` - -# tidyjson - -
- -* Version: 0.3.1 -* GitHub: https://github.com/colearendt/tidyjson -* Source code: https://github.com/cran/tidyjson -* Date/Publication: 2020-05-31 21:30:03 UTC -* Number of recursive dependencies: 96 - -Run `cloud_details(, "tidyjson")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘tidyjson-Ex.R’ failed - The error most likely occurred in: - - > ### Name: json_schema - > ### Title: Create a schema for a JSON document or collection - > ### Aliases: json_schema - > - > ### ** Examples - > - > - ... - 12. └─vctrs::vec_default_cast(...) - 13. ├─base::withRestarts(...) - 14. │ └─base (local) withOneRestart(expr, restarts[[1L]]) - 15. │ └─base (local) doWithOneRestart(return(expr), restart) - 16. └─vctrs::stop_incompatible_cast(...) - 17. └─vctrs::stop_incompatible_type(...) - 18. └─vctrs:::stop_incompatible(...) - 19. └─vctrs:::stop_vctrs(...) - 20. └─rlang::abort(message, class = c(class, "vctrs_error"), ..., call = vctrs_error_call(call)) - Execution halted - ``` - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Last 13 lines of output: - 12. │ └─vctrs::vec_rbind(!!!dots, .names_to = .id) - 13. └─vctrs (local) ``() - 14. └─vctrs::vec_default_cast(...) - 15. ├─base::withRestarts(...) - 16. │ └─base (local) withOneRestart(expr, restarts[[1L]]) - 17. │ └─base (local) doWithOneRestart(return(expr), restart) - 18. └─vctrs::stop_incompatible_cast(...) - 19. └─vctrs::stop_incompatible_type(...) - 20. └─vctrs:::stop_incompatible(...) - 21. └─vctrs:::stop_vctrs(...) - 22. └─rlang::abort(message, class = c(class, "vctrs_error"), ..., call = vctrs_error_call(call)) - - [ FAIL 8 | WARN 0 | SKIP 10 | PASS 347 ] - Error: Test failures - Execution halted - ``` - -* checking re-building of vignette outputs ... WARNING - ``` - Error(s) in re-building vignettes: - --- re-building ‘introduction-to-tidyjson.Rmd’ using rmarkdown - - Attaching package: 'tidyjson' - - The following object is masked from 'package:stats': - - filter - - - ... - Quitting from lines 327-328 (visualizing-json.Rmd) - Error: processing vignette 'visualizing-json.Rmd' failed with diagnostics: - Can't convert `..1` to . - --- failed re-building ‘visualizing-json.Rmd’ - - SUMMARY: processing the following file failed: - ‘visualizing-json.Rmd’ - - Error: Vignette re-building failed. - Execution halted - ``` - # yamlet
diff --git a/tests/testthat/_snaps/bind.md b/tests/testthat/_snaps/bind.md index 6983aefb9..5ed40ae23 100644 --- a/tests/testthat/_snaps/bind.md +++ b/tests/testthat/_snaps/bind.md @@ -402,14 +402,6 @@ Error in `vec_rbind()`: ! Can't combine `..1` and `..2` . -# vec_rbind() falls back to c() if S3 method is available - - Code - with_hybrid_methods(cast = FALSE, vec_rbind(foo_df, bar_df)) - Condition - Error in `vec_rbind()`: - ! Can't convert `..1` > to >. - # can't zap names when `.names_to` is supplied Code diff --git a/tests/testthat/_snaps/type-data-frame.md b/tests/testthat/_snaps/type-data-frame.md index 56e816551..e989402e8 100644 --- a/tests/testthat/_snaps/type-data-frame.md +++ b/tests/testthat/_snaps/type-data-frame.md @@ -207,16 +207,13 @@ Error in `my_function()`: ! Can't combine `df3$x` and `df1$x` . - Code - (expect_error(vec_cast(df1, df2), class = "vctrs_error_incompatible_type")) - Output - - Error in `my_function()`: - ! Can't convert `df1` to . Code (expect_error(vec_cast(df2, df1), class = "vctrs_error_incompatible_type")) Output - + Error in `my_function()`: - ! Can't convert `df2` to . + ! Can't convert from `df2` > to > due to loss of precision. diff --git a/tests/testthat/_snaps/type-tibble.md b/tests/testthat/_snaps/type-tibble.md index fe26c142b..8b92b41bc 100644 --- a/tests/testthat/_snaps/type-tibble.md +++ b/tests/testthat/_snaps/type-tibble.md @@ -24,17 +24,11 @@ Code local_error_call(call("my_function")) - (expect_error(vec_cast(tib1, tib1), class = "vctrs_error_cast")) - Output - - Error in `my_function()`: - ! Can't convert `tib1` to . - Code (expect_error(vec_cast(tib1, tib2), class = "vctrs_error_cast")) Output - + Error in `my_function()`: - ! Can't convert `tib1` to . + ! Can't convert from `tib1` > to > due to loss of precision. Code (expect_error(vec_cast(tib1, data.frame(y = 2)), class = "vctrs_error_cast")) Output @@ -44,7 +38,7 @@ Code (expect_error(vec_cast(data.frame(x = 1), tib2), class = "vctrs_error_cast")) Output - + Error in `my_function()`: - ! Can't convert `data.frame(x = 1)` to . + ! Can't convert from `data.frame(x = 1)` > to > due to loss of precision. diff --git a/tests/testthat/helper-s3.R b/tests/testthat/helper-s3.R index ed23f4c61..fd64c2fbd 100644 --- a/tests/testthat/helper-s3.R +++ b/tests/testthat/helper-s3.R @@ -154,3 +154,9 @@ with_foobar_df_methods <- function(expr) { local_foobar_df_methods() expr } + +set_tibble <- function(x) { + base <- class(x)[-length(class(x))] + class(x) <- c(base, "tbl_df", "tbl", "data.frame") + x +} diff --git a/tests/testthat/test-bind.R b/tests/testthat/test-bind.R index 43596dc68..efa74ac4e 100644 --- a/tests/testthat/test-bind.R +++ b/tests/testthat/test-bind.R @@ -883,13 +883,12 @@ test_that("vec_rbind() falls back to c() if S3 method is available", { with_methods(expr, !!!compact(methods)) } - # FIXME!: test without cast method: should not montion common type - # fallback in error message - expect_snapshot(error = TRUE, + expect_equal( with_hybrid_methods( cast = FALSE, vec_rbind(foo_df, bar_df) - ) + ), + foobaz(data_frame(x = quux(c(1, 2)))) ) # Falls back to data frame because there is no ptype2/cast methods diff --git a/tests/testthat/test-type-data-frame.R b/tests/testthat/test-type-data-frame.R index 169605f8a..c2bafaf80 100644 --- a/tests/testthat/test-type-data-frame.R +++ b/tests/testthat/test-type-data-frame.R @@ -565,6 +565,10 @@ test_that("data frame fallback handles column types (#999)", { expect_identical(vec_ptype2(df1, df2), common) expect_identical(vec_ptype2(df2, df1), common) + exp <- foobar(data_frame(x = 1, y = na_dbl)) + expect_identical(vec_cast(df1, df2), exp) + expect_identical(vec_cast(set_tibble(df1), set_tibble(df2)), set_tibble(exp)) + expect_snapshot({ local_error_call(call("my_function")) (expect_error( @@ -575,10 +579,6 @@ test_that("data frame fallback handles column types (#999)", { vec_ptype2(df3, df1), class = "vctrs_error_incompatible_type" )) - (expect_error( - vec_cast(df1, df2), - class = "vctrs_error_incompatible_type" - )) (expect_error( vec_cast(df2, df1), class = "vctrs_error_incompatible_type" diff --git a/tests/testthat/test-type-tibble.R b/tests/testthat/test-type-tibble.R index bf47441fe..9b26058fa 100644 --- a/tests/testthat/test-type-tibble.R +++ b/tests/testthat/test-type-tibble.R @@ -92,13 +92,13 @@ test_that("can use ptype2 and cast with tibble that has incorrect class vector", vec_ptype_common(data.frame(x = 1), tib2), tibble::new_tibble(exp, nrow = nrow(exp)) ) + expect_identical( + vec_cast(tib1, tib1), + tib1 + ) expect_snapshot({ local_error_call(call("my_function")) - (expect_error( - vec_cast(tib1, tib1), - class = "vctrs_error_cast" - )) (expect_error( vec_cast(tib1, tib2), class = "vctrs_error_cast" From 18d5d0ef18670adc260eff0c759fd3f934907893 Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Tue, 18 Oct 2022 14:51:52 +0200 Subject: [PATCH 174/312] Restore same-type fallback for data frame ptype2 --- R/cast.R | 2 +- R/type2.R | 10 ++++++++-- tests/testthat/test-bind.R | 2 +- tests/testthat/test-type-data-frame.R | 6 +++--- tests/testthat/test-type-tibble.R | 2 +- tests/testthat/test-type2.R | 8 ++++++++ 6 files changed, 22 insertions(+), 8 deletions(-) diff --git a/R/cast.R b/R/cast.R index 00b001425..0515976b8 100644 --- a/R/cast.R +++ b/R/cast.R @@ -212,7 +212,7 @@ vec_default_cast <- function(x, # eschews any constraints on rows and cols that `[` and `[<-` # methods might have. If that is a problem, the class needs to # implement vctrs methods. - if (is_same_type(x[0, 0], to[0, 0])) { + if (identical(non_df_attrib(x), non_df_attrib(to))) { attributes(out) <- c(df_attrib(out), non_df_attrib(to)) return(out) } diff --git a/R/type2.R b/R/type2.R index 9ab713b45..74d9fe575 100644 --- a/R/type2.R +++ b/R/type2.R @@ -133,14 +133,20 @@ vec_default_ptype2 <- function(x, } if (is.data.frame(x) && is.data.frame(y)) { - return(vec_ptype2_df_fallback( + out <- vec_ptype2_df_fallback( x, y, opts, x_arg = x_arg, y_arg = y_arg, call = call - )) + ) + + if (identical(non_df_attrib(x), non_df_attrib(y))) { + attributes(out) <- c(df_attrib(out), non_df_attrib(x)) + } + + return(out) } if (is_same_type(x, y)) { diff --git a/tests/testthat/test-bind.R b/tests/testthat/test-bind.R index efa74ac4e..3a08f956f 100644 --- a/tests/testthat/test-bind.R +++ b/tests/testthat/test-bind.R @@ -865,7 +865,7 @@ test_that("vec_rbind() falls back to c() if S3 method is available", { bar_df <- foobaz(y_df) out <- with_c_method(vec_rbind(foo_df, bar_df)) - exp <- data_frame(x = quux(c(1, 2))) + exp <- foobaz(data_frame(x = quux(c(1, 2)))) expect_identical(out, exp) expect_identical(with_c_method(vec_c(foo_df, bar_df)), exp) diff --git a/tests/testthat/test-type-data-frame.R b/tests/testthat/test-type-data-frame.R index c2bafaf80..df4de80e9 100644 --- a/tests/testthat/test-type-data-frame.R +++ b/tests/testthat/test-type-data-frame.R @@ -53,7 +53,7 @@ test_that("combining data frames with foreign classes uses fallback", { foo <- foobar(data.frame()) df <- data.frame() - expect_identical(vec_ptype_common(foo, foo, foo), df) + expect_identical(vec_ptype_common(foo, foo, foo), foo) expect_identical(vec_ptype_common(foo, foo, df, foo), df) expect_identical(vec_ptype2(foo, df), data.frame()) @@ -561,7 +561,7 @@ test_that("data frame fallback handles column types (#999)", { df2 <- foobar(data.frame(x = 1, y = 2)) df3 <- foobar(data.frame(x = "", y = 2)) - common <- data.frame(x = dbl(), y = dbl()) + common <- foobar(data.frame(x = dbl(), y = dbl())) expect_identical(vec_ptype2(df1, df2), common) expect_identical(vec_ptype2(df2, df1), common) @@ -587,7 +587,7 @@ test_that("data frame fallback handles column types (#999)", { expect_identical( vec_rbind(df1, df2), - data.frame(x = c(1, 1), y = c(NA, 2)) + foobar(data.frame(x = c(1, 1), y = c(NA, 2))) ) # Attributes are not restored diff --git a/tests/testthat/test-type-tibble.R b/tests/testthat/test-type-tibble.R index 9b26058fa..0ea9b7c29 100644 --- a/tests/testthat/test-type-tibble.R +++ b/tests/testthat/test-type-tibble.R @@ -76,7 +76,7 @@ test_that("vec_ptype_finalise() can handle tibble df columns", { test_that("can use ptype2 and cast with tibble that has incorrect class vector", { tib1 <- structure(data.frame(x = 1), class = c("tbl_df", "data.frame")) tib2 <- structure(data.frame(y = 2), class = c("tbl_df", "data.frame")) - exp <- structure(data.frame(x = dbl(), y = dbl()), class = c("tbl_df", "tbl", "data.frame")) + exp <- structure(data.frame(x = dbl(), y = dbl()), class = c("tbl_df", "data.frame")) requireNamespace("tibble") diff --git a/tests/testthat/test-type2.R b/tests/testthat/test-type2.R index 99518ac48..ee786d5a0 100644 --- a/tests/testthat/test-type2.R +++ b/tests/testthat/test-type2.R @@ -362,3 +362,11 @@ test_that("can restart ptype2 errors", { data_frame(x = exp) ) }) + +test_that("subclasses of tibble are compatible", { + tib <- foobar(tibble(x = 1)) + ptype <- foobar(tibble(x = dbl())) + + expect_equal(vec_ptype_common(tib), ptype) + expect_equal(vec_ptype_common(tib, tib), ptype) +}) From e72dbec1d9eb9efd3bc873f5d18e546c4a174ca6 Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Tue, 18 Oct 2022 16:16:40 +0200 Subject: [PATCH 175/312] Restore bare-type fallback for df-cast for target too --- R/cast.R | 14 +- revdep/README.md | 38 - revdep/cran.md | 19 +- revdep/failures.md | 1065 +--------------------------- revdep/problems.md | 281 -------- tests/testthat/_snaps/type-misc.md | 9 - tests/testthat/_snaps/type2.md | 12 - tests/testthat/test-cast.R | 7 +- tests/testthat/test-type-misc.R | 10 +- tests/testthat/test-type2.R | 14 - 10 files changed, 13 insertions(+), 1456 deletions(-) diff --git a/R/cast.R b/R/cast.R index 0515976b8..54a9d71e1 100644 --- a/R/cast.R +++ b/R/cast.R @@ -199,14 +199,6 @@ vec_default_cast <- function(x, call = call ) - # Bare-class fallback for data frames - if (is_bare_df(to)) { - if (inherits(to, "tbl_df")) { - out <- df_as_tibble(out) - } - return(out) - } - # Same-type fallback for data frames. If attributes of the empty # data frames are congruent, just reproduce these attributes. This # eschews any constraints on rows and cols that `[` and `[<-` @@ -217,7 +209,11 @@ vec_default_cast <- function(x, return(out) } - # else fallthrough + # Bare-class fallback for data frames + if (inherits(to, "tbl_df")) { + out <- df_as_tibble(out) + } + return(out) } if (is_same_type(x, to)) { diff --git a/revdep/README.md b/revdep/README.md index bfb79d77c..930ad8497 100644 --- a/revdep/README.md +++ b/revdep/README.md @@ -1,47 +1,9 @@ # Revdeps -## Failed to check (21) - -|package |version |error |warning |note | -|:-------------|:-------|:-----|:-------|:----| -|NA |? | | | | -|elbird |0.2.5 |1 | | | -|ggPMX |? | | | | -|NA |? | | | | -|loon.ggplot |? | | | | -|loon.shiny |? | | | | -|NA |? | | | | -|NA |? | | | | -|NA |? | | | | -|nlmixr2plot |? | | | | -|NA |? | | | | -|NA |? | | | | -|Platypus |? | | | | -|NA |? | | | | -|NA |? | | | | -|NA |? | | | | -|NA |? | | | | -|tidySEM |? | | | | -|NA |? | | | | -|vivid |? | | | | -|xpose.nlmixr2 |? | | | | - ## New problems (2) -|package |version |error |warning |note | -|:-----------|:-------|:------|:-------|:----| -|[brokenstick](problems.md#brokenstick)|2.3.0 | |__+1__ | | -|[psfmi](problems.md#psfmi)|1.0.0 |__+1__ |__+1__ |1 | - -## New problems (7) - |package |version |error |warning |note | |:-------|:-------|:------|:-------|:----| -|[cubble](problems.md#cubble)|0.1.1 |__+1__ |1 | | -|[dm](problems.md#dm)|1.0.3 |__+1__ | | | -|[dplyr](problems.md#dplyr)|1.0.10 |__+1__ | |1 | |[groupr](problems.md#groupr)|0.1.0 |__+1__ |__+1__ |1 | |[ricu](problems.md#ricu)|0.5.3 |__+1__ | | | -|[srvyr](problems.md#srvyr)|1.1.2 |__+2__ |__+1__ |1 | -|[yamlet](problems.md#yamlet)|0.9.6 |__+1__ | | | diff --git a/revdep/cran.md b/revdep/cran.md index 6b69da963..cce066553 100644 --- a/revdep/cran.md +++ b/revdep/cran.md @@ -2,7 +2,7 @@ We checked 3546 reverse dependencies (3534 from CRAN + 12 from Bioconductor), comparing R CMD check results across CRAN and dev versions of this package. - * We saw 7 new problems + * We saw 2 new problems * We failed to check 0 packages Issues with CRAN packages are summarised below. @@ -10,15 +10,6 @@ Issues with CRAN packages are summarised below. ### New problems (This reports the first line of each new failure) -* cubble - checking tests ... ERROR - -* dm - checking tests ... ERROR - -* dplyr - checking tests ... ERROR - * groupr checking tests ... ERROR checking re-building of vignette outputs ... WARNING @@ -26,11 +17,3 @@ Issues with CRAN packages are summarised below. * ricu checking tests ... ERROR -* srvyr - checking examples ... ERROR - checking tests ... ERROR - checking re-building of vignette outputs ... WARNING - -* yamlet - checking tests ... ERROR - diff --git a/revdep/failures.md b/revdep/failures.md index 72ebd3a9b..5bb8c014a 100644 --- a/revdep/failures.md +++ b/revdep/failures.md @@ -1,1064 +1 @@ -# NA - -
- -* Version: NA -* GitHub: NA -* Source code: https://github.com/cran/NA -* Number of recursive dependencies: 0 - -Run `cloud_details(, "NA")` for more info - -
- -## Error before installation - -### Devel - -``` - - - - - - -``` -### CRAN - -``` - - - - - - -``` -# elbird - -
- -* Version: 0.2.5 -* GitHub: https://github.com/mrchypark/elbird -* Source code: https://github.com/cran/elbird -* Date/Publication: 2022-08-12 15:50:02 UTC -* Number of recursive dependencies: 54 - -Run `cloud_details(, "elbird")` for more info - -
- -## In both - -* checking whether package ‘elbird’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/elbird/new/elbird.Rcheck/00install.out’ for details. - ``` - -## Installation - -### Devel - -``` -* installing *source* package ‘elbird’ ... -** package ‘elbird’ successfully unpacked and MD5 sums checked -** using staged installation -/usr/bin/uname -Prior system libkiwi installation not found -Preparing to download and build library from source... -------------------------------[ ELBIRD ]------------------------------ -Configuration failed because 'git' was not found. -If you want to kiwi build from source in package installation prosess, -make sure git and cmake work in system. -------------------------------------------------------------------------- -ERROR: configuration failed for package ‘elbird’ -* removing ‘/tmp/workdir/elbird/new/elbird.Rcheck/elbird’ - - -``` -### CRAN - -``` -* installing *source* package ‘elbird’ ... -** package ‘elbird’ successfully unpacked and MD5 sums checked -** using staged installation -/usr/bin/uname -Prior system libkiwi installation not found -Preparing to download and build library from source... -------------------------------[ ELBIRD ]------------------------------ -Configuration failed because 'git' was not found. -If you want to kiwi build from source in package installation prosess, -make sure git and cmake work in system. -------------------------------------------------------------------------- -ERROR: configuration failed for package ‘elbird’ -* removing ‘/tmp/workdir/elbird/old/elbird.Rcheck/elbird’ - - -``` -# ggPMX - -
- -* Version: 1.2.8 -* GitHub: https://github.com/ggPMXdevelopment/ggPMX -* Source code: https://github.com/cran/ggPMX -* Date/Publication: 2022-06-17 23:10:02 UTC -* Number of recursive dependencies: 172 - -Run `cloud_details(, "ggPMX")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/ggPMX/new/ggPMX.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘ggPMX/DESCRIPTION’ ... OK -* this is package ‘ggPMX’ version ‘1.2.8’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... NOTE -... - [ FAIL 1 | WARN 11 | SKIP 8 | PASS 327 ] - 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 ... NONE - ‘ggPMX-guide.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: 1 ERROR, 2 NOTEs - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/ggPMX/old/ggPMX.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘ggPMX/DESCRIPTION’ ... OK -* this is package ‘ggPMX’ version ‘1.2.8’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... NOTE -... - [ FAIL 1 | WARN 11 | SKIP 8 | PASS 327 ] - 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 ... NONE - ‘ggPMX-guide.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: 1 ERROR, 2 NOTEs - - - - - -``` -# NA - -
- -* Version: NA -* GitHub: NA -* Source code: https://github.com/cran/NA -* Number of recursive dependencies: 0 - -Run `cloud_details(, "NA")` for more info - -
- -## Error before installation - -### Devel - -``` - - - - - - -``` -### CRAN - -``` - - - - - - -``` -# loon.ggplot - -
- -* Version: 1.3.2 -* GitHub: https://github.com/great-northern-diver/loon.ggplot -* Source code: https://github.com/cran/loon.ggplot -* Date/Publication: 2022-10-03 14:50:02 UTC -* Number of recursive dependencies: 104 - -Run `cloud_details(, "loon.ggplot")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/loon.ggplot/new/loon.ggplot.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘loon.ggplot/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘loon.ggplot’ version ‘1.3.2’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘loon’ - -Package suggested but not available for checking: ‘zenplots’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/loon.ggplot/old/loon.ggplot.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘loon.ggplot/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘loon.ggplot’ version ‘1.3.2’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘loon’ - -Package suggested but not available for checking: ‘zenplots’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# loon.shiny - -
- -* Version: 1.0.3 -* GitHub: NA -* Source code: https://github.com/cran/loon.shiny -* Date/Publication: 2022-10-08 15:30:02 UTC -* Number of recursive dependencies: 132 - -Run `cloud_details(, "loon.shiny")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/loon.shiny/new/loon.shiny.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘loon.shiny/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘loon.shiny’ version ‘1.0.3’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Packages required but not available: 'loon', 'loon.ggplot' - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/loon.shiny/old/loon.shiny.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘loon.shiny/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘loon.shiny’ version ‘1.0.3’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Packages required but not available: 'loon', 'loon.ggplot' - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# NA - -
- -* Version: NA -* GitHub: NA -* Source code: https://github.com/cran/NA -* Number of recursive dependencies: 0 - -Run `cloud_details(, "NA")` for more info - -
- -## Error before installation - -### Devel - -``` - - - - - - -``` -### CRAN - -``` - - - - - - -``` -# NA - -
- -* Version: NA -* GitHub: NA -* Source code: https://github.com/cran/NA -* Number of recursive dependencies: 0 - -Run `cloud_details(, "NA")` for more info - -
- -## Error before installation - -### Devel - -``` - - - - - - -``` -### CRAN - -``` - - - - - - -``` -# NA - -
- -* Version: NA -* GitHub: NA -* Source code: https://github.com/cran/NA -* Number of recursive dependencies: 0 - -Run `cloud_details(, "NA")` for more info - -
- -## Error before installation - -### Devel - -``` - - - - - - -``` -### CRAN - -``` - - - - - - -``` -# nlmixr2plot - -
- -* Version: 2.0.6 -* GitHub: https://github.com/nlmixr2/nlmixr2plot -* Source code: https://github.com/cran/nlmixr2plot -* Date/Publication: 2022-05-23 07:50:02 UTC -* Number of recursive dependencies: 155 - -Run `cloud_details(, "nlmixr2plot")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/nlmixr2plot/new/nlmixr2plot.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘nlmixr2plot/DESCRIPTION’ ... OK -* this is package ‘nlmixr2plot’ version ‘2.0.6’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Packages required but not available: 'nlmixr2est', 'nlmixr2extra' - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/nlmixr2plot/old/nlmixr2plot.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘nlmixr2plot/DESCRIPTION’ ... OK -* this is package ‘nlmixr2plot’ version ‘2.0.6’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Packages required but not available: 'nlmixr2est', 'nlmixr2extra' - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# NA - -
- -* Version: NA -* GitHub: NA -* Source code: https://github.com/cran/NA -* Number of recursive dependencies: 0 - -Run `cloud_details(, "NA")` for more info - -
- -## Error before installation - -### Devel - -``` - - - - - - -``` -### CRAN - -``` - - - - - - -``` -# NA - -
- -* Version: NA -* GitHub: NA -* Source code: https://github.com/cran/NA -* Number of recursive dependencies: 0 - -Run `cloud_details(, "NA")` for more info - -
- -## Error before installation - -### Devel - -``` - - - - - - -``` -### CRAN - -``` - - - - - - -``` -# Platypus - -
- -* Version: 3.4.1 -* GitHub: NA -* Source code: https://github.com/cran/Platypus -* Date/Publication: 2022-08-15 07:20:20 UTC -* Number of recursive dependencies: 355 - -Run `cloud_details(, "Platypus")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/Platypus/new/Platypus.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘Platypus/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘Platypus’ version ‘3.4.1’ -* package encoding: UTF-8 -* checking package namespace information ... 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 - ‘PlatypusV3_agedCNS.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: 1 NOTE - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/Platypus/old/Platypus.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘Platypus/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘Platypus’ version ‘3.4.1’ -* package encoding: UTF-8 -* checking package namespace information ... 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 - ‘PlatypusV3_agedCNS.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: 1 NOTE - - - - - -``` -# NA - -
- -* Version: NA -* GitHub: NA -* Source code: https://github.com/cran/NA -* Number of recursive dependencies: 0 - -Run `cloud_details(, "NA")` for more info - -
- -## Error before installation - -### Devel - -``` - - - - - - -``` -### CRAN - -``` - - - - - - -``` -# NA - -
- -* Version: NA -* GitHub: NA -* Source code: https://github.com/cran/NA -* Number of recursive dependencies: 0 - -Run `cloud_details(, "NA")` for more info - -
- -## Error before installation - -### Devel - -``` - - - - - - -``` -### CRAN - -``` - - - - - - -``` -# NA - -
- -* Version: NA -* GitHub: NA -* Source code: https://github.com/cran/NA -* Number of recursive dependencies: 0 - -Run `cloud_details(, "NA")` for more info - -
- -## Error before installation - -### Devel - -``` - - - - - - -``` -### CRAN - -``` - - - - - - -``` -# NA - -
- -* Version: NA -* GitHub: NA -* Source code: https://github.com/cran/NA -* Number of recursive dependencies: 0 - -Run `cloud_details(, "NA")` for more info - -
- -## Error before installation - -### Devel - -``` - - - - - - -``` -### CRAN - -``` - - - - - - -``` -# tidySEM - -
- -* Version: 0.2.3 -* GitHub: https://github.com/cjvanlissa/tidySEM -* Source code: https://github.com/cran/tidySEM -* Date/Publication: 2022-04-14 17:50:02 UTC -* Number of recursive dependencies: 170 - -Run `cloud_details(, "tidySEM")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/tidySEM/new/tidySEM.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘tidySEM/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘tidySEM’ version ‘0.2.3’ -* package encoding: UTF-8 -* checking package namespace information ... OK -... -* checking for unstated dependencies in vignettes ... OK -* checking package vignettes in ‘inst/doc’ ... OK -* checking running R code from vignettes ... NONE - ‘Generating_syntax.Rmd’ using ‘UTF-8’... OK - ‘Plotting_graphs.Rmd’ using ‘UTF-8’... OK - ‘Tabulating_results.Rmd’ using ‘UTF-8’... OK - ‘sem_graph.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: 1 NOTE - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/tidySEM/old/tidySEM.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘tidySEM/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘tidySEM’ version ‘0.2.3’ -* package encoding: UTF-8 -* checking package namespace information ... OK -... -* checking for unstated dependencies in vignettes ... OK -* checking package vignettes in ‘inst/doc’ ... OK -* checking running R code from vignettes ... NONE - ‘Generating_syntax.Rmd’ using ‘UTF-8’... OK - ‘Plotting_graphs.Rmd’ using ‘UTF-8’... OK - ‘Tabulating_results.Rmd’ using ‘UTF-8’... OK - ‘sem_graph.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: 1 NOTE - - - - - -``` -# NA - -
- -* Version: NA -* GitHub: NA -* Source code: https://github.com/cran/NA -* Number of recursive dependencies: 0 - -Run `cloud_details(, "NA")` for more info - -
- -## Error before installation - -### Devel - -``` - - - - - - -``` -### CRAN - -``` - - - - - - -``` -# vivid - -
- -* Version: 0.2.3 -* GitHub: NA -* Source code: https://github.com/cran/vivid -* Date/Publication: 2021-11-20 01:30:02 UTC -* Number of recursive dependencies: 201 - -Run `cloud_details(, "vivid")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/vivid/new/vivid.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘vivid/DESCRIPTION’ ... OK -* this is package ‘vivid’ version ‘0.2.3’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... NOTE -... -* 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 - ‘vivid.Rmd’ using ‘UTF-8’... OK - ‘vividQStart.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: 2 NOTEs - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/vivid/old/vivid.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘vivid/DESCRIPTION’ ... OK -* this is package ‘vivid’ version ‘0.2.3’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... NOTE -... -* 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 - ‘vivid.Rmd’ using ‘UTF-8’... OK - ‘vividQStart.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: 2 NOTEs - - - - - -``` -# xpose.nlmixr2 - -
- -* Version: 0.4.0 -* GitHub: NA -* Source code: https://github.com/cran/xpose.nlmixr2 -* Date/Publication: 2022-06-08 09:10:02 UTC -* Number of recursive dependencies: 149 - -Run `cloud_details(, "xpose.nlmixr2")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/xpose.nlmixr2/new/xpose.nlmixr2.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘xpose.nlmixr2/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘xpose.nlmixr2’ version ‘0.4.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘nlmixr2est’ - -Package suggested but not available for checking: ‘nlmixr2’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/xpose.nlmixr2/old/xpose.nlmixr2.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘xpose.nlmixr2/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘xpose.nlmixr2’ version ‘0.4.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘nlmixr2est’ - -Package suggested but not available for checking: ‘nlmixr2’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` +*Wow, no problems at all. :)* diff --git a/revdep/problems.md b/revdep/problems.md index 487d05010..96d31e955 100644 --- a/revdep/problems.md +++ b/revdep/problems.md @@ -1,151 +1,3 @@ -# cubble - -
- -* Version: 0.1.1 -* GitHub: https://github.com/huizezhang-sherry/cubble -* Source code: https://github.com/cran/cubble -* Date/Publication: 2022-06-02 12:30:06 UTC -* Number of recursive dependencies: 137 - -Run `cloud_details(, "cubble")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Last 13 lines of output: - 4. │ └─vctrs::vec_rbind(!!!dots, .names_to = .id) - 5. └─vctrs (local) ``() - 6. └─vctrs::vec_default_cast(...) - 7. ├─base::withRestarts(...) - 8. │ └─base (local) withOneRestart(expr, restarts[[1L]]) - 9. │ └─base (local) doWithOneRestart(return(expr), restart) - 10. └─vctrs::stop_incompatible_cast(...) - 11. └─vctrs::stop_incompatible_type(...) - 12. └─vctrs:::stop_incompatible(...) - 13. └─vctrs:::stop_vctrs(...) - 14. └─rlang::abort(message, class = c(class, "vctrs_error"), ..., call = vctrs_error_call(call)) - - [ FAIL 2 | WARN 0 | SKIP 6 | PASS 31 ] - Error: Test failures - Execution halted - ``` - -## In both - -* checking re-building of vignette outputs ... WARNING - ``` - Error(s) in re-building vignettes: - --- re-building ‘aggregation.Rmd’ using rmarkdown - `summarise()` has grouped output by 'id'. You can override using the `.groups` - argument. - `summarise()` has grouped output by 'cluster', 'id'. You can override using the - `.groups` argument. - `geom_smooth()` using method = 'gam' and formula 'y ~ s(x, bs = "cs")' - Adding missing grouping variables: `id` - Quitting from lines 123-131 (aggregation.Rmd) - Error: processing vignette 'aggregation.Rmd' failed with diagnostics: - ... - Quitting from lines 75-79 (matching.Rmd) - Error: processing vignette 'matching.Rmd' failed with diagnostics: - Can't convert `..1` to . - --- failed re-building ‘matching.Rmd’ - - SUMMARY: processing the following files failed: - ‘aggregation.Rmd’ ‘matching.Rmd’ - - Error: Vignette re-building failed. - Execution halted - ``` - -# dm - -
- -* Version: 1.0.3 -* GitHub: https://github.com/cynkra/dm -* Source code: https://github.com/cran/dm -* Date/Publication: 2022-10-12 15:42:33 UTC -* Number of recursive dependencies: 152 - -Run `cloud_details(, "dm")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Last 13 lines of output: - - `actual$parent_key_cols[[4]]` is absent - `expected$parent_key_cols[[4]]` is a character vector ('h') - - `actual$parent_key_cols[[5]]` is absent - `expected$parent_key_cols[[5]]` is a character vector ('n') - Backtrace: - ▆ - 1. └─dm:::expect_equivalent_dm(...) at test-dm_wrap.R:73:2 - 2. └─dm:::expect_equivalent_tbl(...) at tests/testthat/helper-expectations.R:13:4 - 3. └─testthat::expect_identical(...) at tests/testthat/helper-expectations.R:76:2 - - [ FAIL 18 | WARN 0 | SKIP 191 | PASS 1275 ] - Error: Test failures - Execution halted - ``` - -# dplyr - -
- -* Version: 1.0.10 -* GitHub: https://github.com/tidyverse/dplyr -* Source code: https://github.com/cran/dplyr -* Date/Publication: 2022-09-01 09:20:06 UTC -* Number of recursive dependencies: 97 - -Run `cloud_details(, "dplyr")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Last 13 lines of output: - ── Failure ('test-group_split.R:115'): group_split() works with subclasses implementing group_by() / ungroup() ── - group_split(df, x) (`actual`) not identical to `expect` (`expected`). - - `class(attr(actual, 'ptype'))`: "foo_df" "tbl_df" "tbl" "data.frame" - `class(attr(expected, 'ptype'))`: "tbl_df" "tbl" "data.frame" - - `class(actual[[1]])`: "foo_df" "tbl_df" "tbl" "data.frame" - `class(expected[[1]])`: "tbl_df" "tbl" "data.frame" - - `class(actual[[2]])`: "foo_df" "tbl_df" "tbl" "data.frame" - `class(expected[[2]])`: "tbl_df" "tbl" "data.frame" - - [ FAIL 1 | WARN 109 | SKIP 107 | PASS 2364 ] - Error: Test failures - Execution halted - ``` - -## In both - -* checking data for non-ASCII characters ... NOTE - ``` - Note: found 4 marked UTF-8 strings - ``` - # groupr
@@ -249,136 +101,3 @@ Run `cloud_details(, "ricu")` for more info Execution halted ``` -# srvyr - -
- -* Version: 1.1.2 -* GitHub: https://github.com/gergness/srvyr -* Source code: https://github.com/cran/srvyr -* Date/Publication: 2022-10-05 23:00:06 UTC -* Number of recursive dependencies: 87 - -Run `cloud_details(, "srvyr")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘srvyr-Ex.R’ failed - The error most likely occurred in: - - > ### Name: cascade - > ### Title: Summarise multiple values into cascading groups - > ### Aliases: cascade - > - > ### ** Examples - > - > library(survey) - ... - 8. └─vctrs (local) ``() - 9. └─vctrs::vec_default_ptype2(...) - 10. ├─base::withRestarts(...) - 11. │ └─base (local) withOneRestart(expr, restarts[[1L]]) - 12. │ └─base (local) doWithOneRestart(return(expr), restart) - 13. └─vctrs::stop_incompatible_type(...) - 14. └─vctrs:::stop_incompatible(...) - 15. └─vctrs:::stop_vctrs(...) - 16. └─rlang::abort(message, class = c(class, "vctrs_error"), ..., call = vctrs_error_call(call)) - Execution halted - ``` - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Last 13 lines of output: - ── Failure (???): deff and df work for grouped survey total ──────────────────── - `x` not equivalent to `y`. - Length mismatch: comparison on first 2 components - Component "survey_total": Length mismatch: comparison on first 3 components - Component "survey_total": Component 1: Numeric: lengths (3, 1) differ - Component "survey_total": Component 2: Numeric: lengths (3, 1) differ - Component "survey_total": Component 3: Numeric: lengths (3, 1) differ - Backtrace: - ▆ - 1. └─global expect_df_equal(out_srvyr, select(out_survey, -survey_total_se)) - 2. └─testthat::expect_equivalent(x, y) - - [ FAIL 47 | WARN 12 | SKIP 0 | PASS 216 ] - Error: Test failures - Execution halted - ``` - -* checking re-building of vignette outputs ... WARNING - ``` - Error(s) in re-building vignettes: - --- re-building ‘extending-srvyr.Rmd’ using rmarkdown - --- finished re-building ‘extending-srvyr.Rmd’ - - --- re-building ‘srvyr-database.Rmd’ using rmarkdown - --- finished re-building ‘srvyr-database.Rmd’ - - --- re-building ‘srvyr-vs-survey.Rmd’ using rmarkdown - Loading required package: grid - Loading required package: Matrix - ... - ! Problem while computing column `n`. - Caused by error in `initialize()`: - ! attempt to use zero-length variable name - --- failed re-building ‘srvyr-vs-survey.Rmd’ - - SUMMARY: processing the following file failed: - ‘srvyr-vs-survey.Rmd’ - - Error: Vignette re-building failed. - Execution halted - ``` - -## In both - -* checking package dependencies ... NOTE - ``` - Package suggested but not available for checking: ‘convey’ - ``` - -# yamlet - -
- -* Version: 0.9.6 -* GitHub: https://github.com/bergsmat/yamlet -* Source code: https://github.com/cran/yamlet -* Date/Publication: 2022-09-20 20:10:01 UTC -* Number of recursive dependencies: 81 - -Run `cloud_details(, "yamlet")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Last 13 lines of output: - 12. │ └─vctrs::vec_rbind(!!!dots, .names_to = .id) - 13. └─vctrs (local) ``() - 14. └─vctrs::vec_default_cast(...) - 15. ├─base::withRestarts(...) - 16. │ └─base (local) withOneRestart(expr, restarts[[1L]]) - 17. │ └─base (local) doWithOneRestart(return(expr), restart) - 18. └─vctrs::stop_incompatible_cast(...) - 19. └─vctrs::stop_incompatible_type(...) - 20. └─vctrs:::stop_incompatible(...) - 21. └─vctrs:::stop_vctrs(...) - 22. └─rlang::abort(message, class = c(class, "vctrs_error"), ..., call = vctrs_error_call(call)) - - [ FAIL 1 | WARN 0 | SKIP 2 | PASS 402 ] - Error: Test failures - Execution halted - ``` - diff --git a/tests/testthat/_snaps/type-misc.md b/tests/testthat/_snaps/type-misc.md index dc44c3fa8..ba0833783 100644 --- a/tests/testthat/_snaps/type-misc.md +++ b/tests/testthat/_snaps/type-misc.md @@ -1,12 +1,3 @@ -# data.table and tibble do not have a common type - - Code - (expect_error(vec_cast(tibble(y = 2), data.table(x = TRUE, y = 1L)))) - Output - - Error: - ! Can't convert `tibble(y = 2)` to . - # data table has formatting methods Code diff --git a/tests/testthat/_snaps/type2.md b/tests/testthat/_snaps/type2.md index 8df5b9f75..e6bca62db 100644 --- a/tests/testthat/_snaps/type2.md +++ b/tests/testthat/_snaps/type2.md @@ -110,15 +110,3 @@ Error: ! Can't combine `foobar(1, bar = TRUE)` and `foobar(2, baz = TRUE)` . -# common type errors don't mention columns if they are compatible - - Code - df <- data.frame(x = 1, y = "") - foo <- structure(df, class = c("vctrs_foo", "data.frame")) - bar <- structure(df, class = c("vctrs_bar", "data.frame")) - (expect_error(vec_cast(foo, bar), class = "vctrs_error_incompatible_type")) - Output - - Error: - ! Can't convert `foo` to . - diff --git a/tests/testthat/test-cast.R b/tests/testthat/test-cast.R index c2f974fef..c3b6b8202 100644 --- a/tests/testthat/test-cast.R +++ b/tests/testthat/test-cast.R @@ -92,12 +92,9 @@ test_that("unspecified can be cast to shaped vectors", { expect_identical(out, exp) }) -test_that("vec_cast() only falls back when casting to base type", { +test_that("vec_cast() falls back to base class even when casting to non-base type", { expect_equal(vec_cast(foobar(mtcars), mtcars), mtcars) - expect_error( - vec_cast(mtcars, foobar(mtcars)), - class = "vctrs_error_incompatible_type" - ) + expect_equal(vec_cast(mtcars, foobar(mtcars)), mtcars) }) test_that("vec_cast() only attempts to fall back if `to` is a data frame (#1568)", { diff --git a/tests/testthat/test-type-misc.R b/tests/testthat/test-type-misc.R index 6dff982ef..e1c61c7d4 100644 --- a/tests/testthat/test-type-misc.R +++ b/tests/testthat/test-type-misc.R @@ -73,16 +73,14 @@ test_that("data.table and tibble do not have a common type", { tibble(y = dbl(), x = lgl()) ) - # Works because tibble is a bare df type expect_identical( vec_cast(data.table(y = 2), tibble(x = TRUE, y = 1L)), tibble(x = lgl(NA), y = 2L) ) - - # Fails because dt isn't - expect_snapshot({ - (expect_error(vec_cast(tibble(y = 2), data.table(x = TRUE, y = 1L)))) - }) + expect_identical( + vec_cast(tibble(y = 2), data.table(x = TRUE, y = 1L)), + data_frame(x = lgl(NA), y = 2L) + ) }) test_that("data table has formatting methods", { diff --git a/tests/testthat/test-type2.R b/tests/testthat/test-type2.R index ee786d5a0..f4b53f02f 100644 --- a/tests/testthat/test-type2.R +++ b/tests/testthat/test-type2.R @@ -254,20 +254,6 @@ test_that("Incompatible attributes bullets are not show when methods are impleme }) }) -test_that("common type errors don't mention columns if they are compatible", { - expect_snapshot({ - df <- data.frame(x = 1, y = "") - - foo <- structure(df, class = c("vctrs_foo", "data.frame")) - bar <- structure(df, class = c("vctrs_bar", "data.frame")) - - (expect_error( - vec_cast(foo, bar), - class = "vctrs_error_incompatible_type" - )) - }) -}) - test_that("attributes no longer play a role in bare data frame fallback", { foobar_bud <- foobar(mtcars, bud = TRUE) foobar_boo <- foobar(mtcars, boo = TRUE) From 689561a02d3e18d05fb807986a148aef3725b0e9 Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Wed, 19 Oct 2022 11:09:45 +0200 Subject: [PATCH 176/312] Update revdeps --- revdep/README.md | 19 +++-- revdep/cran.md | 8 +-- revdep/failures.md | 176 ++++++++++++++++++++++++++++++++++++++++++++- revdep/problems.md | 103 +++++--------------------- 4 files changed, 210 insertions(+), 96 deletions(-) diff --git a/revdep/README.md b/revdep/README.md index 930ad8497..b9299e6d0 100644 --- a/revdep/README.md +++ b/revdep/README.md @@ -1,9 +1,18 @@ # Revdeps -## New problems (2) +## Failed to check (5) -|package |version |error |warning |note | -|:-------|:-------|:------|:-------|:----| -|[groupr](problems.md#groupr)|0.1.0 |__+1__ |__+1__ |1 | -|[ricu](problems.md#ricu)|0.5.3 |__+1__ | | | +|package |version |error |warning |note | +|:-------|:-------|:-----|:-------|:----| +|NA |? | | | | +|NA |? | | | | +|NA |? | | | | +|NA |? | | | | +|NA |? | | | | + +## New problems (1) + +|package |version |error |warning |note | +|:----------|:-------|:------|:-------|:----| +|[tibbletime](problems.md#tibbletime)|0.1.6 |__+1__ | | | diff --git a/revdep/cran.md b/revdep/cran.md index cce066553..6e65e9e14 100644 --- a/revdep/cran.md +++ b/revdep/cran.md @@ -2,7 +2,7 @@ We checked 3546 reverse dependencies (3534 from CRAN + 12 from Bioconductor), comparing R CMD check results across CRAN and dev versions of this package. - * We saw 2 new problems + * We saw 1 new problems * We failed to check 0 packages Issues with CRAN packages are summarised below. @@ -10,10 +10,6 @@ Issues with CRAN packages are summarised below. ### New problems (This reports the first line of each new failure) -* groupr - checking tests ... ERROR - checking re-building of vignette outputs ... WARNING - -* ricu +* tibbletime checking tests ... ERROR diff --git a/revdep/failures.md b/revdep/failures.md index 5bb8c014a..fd10f3c24 100644 --- a/revdep/failures.md +++ b/revdep/failures.md @@ -1 +1,175 @@ -*Wow, no problems at all. :)* +# NA + +
+ +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/NA +* Number of recursive dependencies: 0 + +Run `cloud_details(, "NA")` for more info + +
+ +## Error before installation + +### Devel + +``` + + + + + + +``` +### CRAN + +``` + + + + + + +``` +# NA + +
+ +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/NA +* Number of recursive dependencies: 0 + +Run `cloud_details(, "NA")` for more info + +
+ +## Error before installation + +### Devel + +``` + + + + + + +``` +### CRAN + +``` + + + + + + +``` +# NA + +
+ +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/NA +* Number of recursive dependencies: 0 + +Run `cloud_details(, "NA")` for more info + +
+ +## Error before installation + +### Devel + +``` + + + + + + +``` +### CRAN + +``` + + + + + + +``` +# NA + +
+ +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/NA +* Number of recursive dependencies: 0 + +Run `cloud_details(, "NA")` for more info + +
+ +## Error before installation + +### Devel + +``` + + + + + + +``` +### CRAN + +``` + + + + + + +``` +# NA + +
+ +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/NA +* Number of recursive dependencies: 0 + +Run `cloud_details(, "NA")` for more info + +
+ +## Error before installation + +### Devel + +``` + + + + + + +``` +### CRAN + +``` + + + + + + +``` diff --git a/revdep/problems.md b/revdep/problems.md index 96d31e955..9d12db4cd 100644 --- a/revdep/problems.md +++ b/revdep/problems.md @@ -1,14 +1,14 @@ -# groupr +# tibbletime
-* Version: 0.1.0 -* GitHub: https://github.com/ngriffiths21/groupr -* Source code: https://github.com/cran/groupr -* Date/Publication: 2020-10-14 12:30:06 UTC -* Number of recursive dependencies: 63 +* Version: 0.1.6 +* GitHub: https://github.com/business-science/tibbletime +* Source code: https://github.com/cran/tibbletime +* Date/Publication: 2020-07-21 13:50:02 UTC +* Number of recursive dependencies: 86 -Run `cloud_details(, "groupr")` for more info +Run `cloud_details(, "tibbletime")` for more info
@@ -19,84 +19,19 @@ Run `cloud_details(, "groupr")` for more info Running ‘testthat.R’ Running the tests in ‘tests/testthat.R’ failed. Last 13 lines of output: - Please report it at with a reprex () and the full backtrace. - Backtrace: - ▆ - 1. ├─... %>% group_by2(is_ok, grp) at test_pivots.R:3:0 - 2. ├─groupr::group_by2(., is_ok, grp) - 3. ├─groupr:::group_by2.data.frame(., is_ok, grp) - 4. │ └─groupr:::group_by2_ok(data, dots) - 5. │ └─groupr:::igrouped_df(grouped, groups_out) - 6. │ └─vctrs::vec_rbind(groups, data.frame()) - 7. └─rlang:::stop_internal_c_lib(...) - 8. └─rlang::abort(message, call = call, .internal = TRUE, .frame = frame) + 4. └─tibbletime::get_index_col(FANG_unnested) + 5. ├─.tbl_time[[get_index_char(.tbl_time)]] + 6. ├─tibble:::`[[.tbl_df`(.tbl_time, get_index_char(.tbl_time)) + 7. │ └─tibble:::tbl_subset2(x, j = i, j_arg = substitute(i)) + 8. └─tibbletime::get_index_char(.tbl_time) + 9. ├─rlang::quo_name(get_index_quo(.tbl_time)) + 10. │ ├─rlang::expr_name(quo_squash(quo)) + 11. │ └─rlang::quo_squash(quo) + 12. │ └─rlang::is_quosure(quo) + 13. └─tibbletime::get_index_quo(.tbl_time) + 14. └─tibbletime:::glue_stop("Object is not of class `tbl_time`.") - [ FAIL 3 | WARN 0 | SKIP 0 | PASS 0 ] - Error: Test failures - Execution halted - ``` - -* checking re-building of vignette outputs ... WARNING - ``` - Error(s) in re-building vignettes: - ... - --- re-building ‘introduction.Rmd’ using rmarkdown - Quitting from lines 33-35 (introduction.Rmd) - Error: processing vignette 'introduction.Rmd' failed with diagnostics: - Column `.rows` (size 0) must match the data frame (size 2). - ℹ In file 'slice.c' at line 188. - ℹ This is an internal error that was detected in the vctrs package. - Please report it at with a reprex () and the full backtrace. - --- failed re-building ‘introduction.Rmd’ - - SUMMARY: processing the following file failed: - ‘introduction.Rmd’ - - Error: Vignette re-building failed. - Execution halted - ``` - -## In both - -* checking LazyData ... NOTE - ``` - 'LazyData' is specified without a 'data' directory - ``` - -# ricu - -
- -* Version: 0.5.3 -* GitHub: https://github.com/eth-mds/ricu -* Source code: https://github.com/cran/ricu -* Date/Publication: 2022-07-12 10:50:14 UTC -* Number of recursive dependencies: 114 - -Run `cloud_details(, "ricu")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Last 13 lines of output: - See . - Backtrace: - ▆ - 1. ├─testthat::expect_identical(as_src_cfg(mimic_demo), mi) at test-config.R:19:2 - 2. │ └─testthat::quasi_label(enquo(object), label, arg = "object") - 3. │ └─rlang::eval_bare(expr, quo_get_env(quo)) - 4. ├─ricu::as_src_cfg(mimic_demo) - 5. ├─ricu:::as_src_cfg.src_env(mimic_demo) - 6. │ └─vctrs::vec_unchop(lapply(x, as_col_cfg), name_spec = "{inner}") - 7. │ └─vctrs::list_unchop(...) - 8. └─rlang::abort(message = message, call = call) - - [ FAIL 1 | WARN 1 | SKIP 7 | PASS 592 ] + [ FAIL 3 | WARN 2 | SKIP 0 | PASS 142 ] Error: Test failures Execution halted ``` From b7df05a1b2ad3db556628e97e8af4bb9bc08317b Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Wed, 19 Oct 2022 12:45:07 +0200 Subject: [PATCH 177/312] Fix same-type fallback for df-cast with unordered attributes --- R/type-data-frame.R | 5 ++++- tests/testthat/test-cast.R | 19 +++++++++++++++++++ 2 files changed, 23 insertions(+), 1 deletion(-) diff --git a/R/type-data-frame.R b/R/type-data-frame.R index 5b7d148cc..2a57a4324 100644 --- a/R/type-data-frame.R +++ b/R/type-data-frame.R @@ -391,5 +391,8 @@ df_attrib <- function(x) { } non_df_attrib <- function(x) { attrib <- attributes(x) - attrib[!names(attrib) %in% c("row.names", "names")] + attrib <- attrib[!names(attrib) %in% c("row.names", "names")] + + # Sort to allow comparison + attrib[order(names(attrib))] } diff --git a/tests/testthat/test-cast.R b/tests/testthat/test-cast.R index c3b6b8202..e6105bbdb 100644 --- a/tests/testthat/test-cast.R +++ b/tests/testthat/test-cast.R @@ -263,3 +263,22 @@ test_that("can call `vec_cast()` from C (#1666)", { expect_equal(fn(x, y), vec_cast(x, y)) }) + +test_that("df-fallback for cast is not sensitive to attributes order", { + x <- structure( + list(col = ""), + class = c("vctrs_foobar", "tbl_df", "tbl", "data.frame"), + row.names = c(NA, -1L), + foo = "foo", + bar = "bar" + ) + ptype <- structure( + list(col = character(0)), + foo = "foo", + bar = "bar", + row.names = integer(0), + class = c("vctrs_foobar", "tbl_df", "tbl", "data.frame") + ) + + expect_identical(vec_cast(x, ptype), x) +}) From 6bf78843e2fa39f6a6726ca70739a28865e58674 Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Wed, 19 Oct 2022 18:08:10 +0200 Subject: [PATCH 178/312] Update revdeps for vctrs + tidyr + dplyr --- revdep/README.md | 43 ++- revdep/cran.md | 26 +- revdep/failures.md | 924 +++++++++++++++++++++++++++++++++++++++++++++ revdep/problems.md | 151 +++++++- 4 files changed, 1109 insertions(+), 35 deletions(-) diff --git a/revdep/README.md b/revdep/README.md index b9299e6d0..9bf0437fd 100644 --- a/revdep/README.md +++ b/revdep/README.md @@ -1,18 +1,37 @@ # Revdeps -## Failed to check (5) +## Failed to check (22) -|package |version |error |warning |note | -|:-------|:-------|:-----|:-------|:----| -|NA |? | | | | -|NA |? | | | | -|NA |? | | | | -|NA |? | | | | -|NA |? | | | | +|package |version |error |warning |note | +|:-------------|:-------|:-----|:-------|:----| +|NA |? | | | | +|NA |? | | | | +|elbird |0.2.5 |1 | | | +|ggPMX |? | | | | +|NA |? | | | | +|loon.ggplot |? | | | | +|loon.shiny |? | | | | +|NA |? | | | | +|NA |? | | | | +|NA |? | | | | +|nlmixr2plot |? | | | | +|NA |? | | | | +|NA |? | | | | +|Platypus |? | | | | +|NA |? | | | | +|NA |? | | | | +|NA |? | | | | +|NA |? | | | | +|tidySEM |? | | | | +|NA |? | | | | +|vivid |? | | | | +|xpose.nlmixr2 |? | | | | -## New problems (1) +## New problems (3) -|package |version |error |warning |note | -|:----------|:-------|:------|:-------|:----| -|[tibbletime](problems.md#tibbletime)|0.1.6 |__+1__ | | | +|package |version |error |warning |note | +|:------------|:-------|:------|:-------|:----| +|[globaltrends](problems.md#globaltrends)|0.0.12 |__+1__ | | | +|[goldilocks](problems.md#goldilocks)|0.3.0 |__+1__ | | | +|[psfmi](problems.md#psfmi)|1.0.0 |__+1__ |__+1__ |1 | diff --git a/revdep/cran.md b/revdep/cran.md index 6e65e9e14..3de654e88 100644 --- a/revdep/cran.md +++ b/revdep/cran.md @@ -1,15 +1,33 @@ ## revdepcheck results -We checked 3546 reverse dependencies (3534 from CRAN + 12 from Bioconductor), comparing R CMD check results across CRAN and dev versions of this package. +We checked 3743 reverse dependencies (3730 from CRAN + 13 from Bioconductor), comparing R CMD check results across CRAN and dev versions of this package. - * We saw 1 new problems - * We failed to check 0 packages + * We saw 3 new problems + * We failed to check 9 packages Issues with CRAN packages are summarised below. ### New problems (This reports the first line of each new failure) -* tibbletime +* globaltrends checking tests ... ERROR +* goldilocks + checking tests ... ERROR + +* psfmi + checking examples ... ERROR + checking re-building of vignette outputs ... WARNING + +### Failed to check + +* elbird (NA) +* ggPMX (NA) +* loon.ggplot (NA) +* loon.shiny (NA) +* nlmixr2plot (NA) +* Platypus (NA) +* tidySEM (NA) +* vivid (NA) +* xpose.nlmixr2 (NA) diff --git a/revdep/failures.md b/revdep/failures.md index fd10f3c24..0af7bf749 100644 --- a/revdep/failures.md +++ b/revdep/failures.md @@ -67,6 +67,706 @@ Run `cloud_details(, "NA")` for more info +``` +# elbird + +
+ +* Version: 0.2.5 +* GitHub: https://github.com/mrchypark/elbird +* Source code: https://github.com/cran/elbird +* Date/Publication: 2022-08-12 15:50:02 UTC +* Number of recursive dependencies: 54 + +Run `cloud_details(, "elbird")` for more info + +
+ +## In both + +* checking whether package ‘elbird’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/elbird/new/elbird.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘elbird’ ... +** package ‘elbird’ successfully unpacked and MD5 sums checked +** using staged installation +/usr/bin/uname +Prior system libkiwi installation not found +Preparing to download and build library from source... +------------------------------[ ELBIRD ]------------------------------ +Configuration failed because 'git' was not found. +If you want to kiwi build from source in package installation prosess, +make sure git and cmake work in system. +------------------------------------------------------------------------- +ERROR: configuration failed for package ‘elbird’ +* removing ‘/tmp/workdir/elbird/new/elbird.Rcheck/elbird’ + + +``` +### CRAN + +``` +* installing *source* package ‘elbird’ ... +** package ‘elbird’ successfully unpacked and MD5 sums checked +** using staged installation +/usr/bin/uname +Prior system libkiwi installation not found +Preparing to download and build library from source... +------------------------------[ ELBIRD ]------------------------------ +Configuration failed because 'git' was not found. +If you want to kiwi build from source in package installation prosess, +make sure git and cmake work in system. +------------------------------------------------------------------------- +ERROR: configuration failed for package ‘elbird’ +* removing ‘/tmp/workdir/elbird/old/elbird.Rcheck/elbird’ + + +``` +# ggPMX + +
+ +* Version: 1.2.8 +* GitHub: https://github.com/ggPMXdevelopment/ggPMX +* Source code: https://github.com/cran/ggPMX +* Date/Publication: 2022-06-17 23:10:02 UTC +* Number of recursive dependencies: 208 + +Run `cloud_details(, "ggPMX")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/ggPMX/new/ggPMX.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘ggPMX/DESCRIPTION’ ... OK +* this is package ‘ggPMX’ version ‘1.2.8’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... NOTE +... + [ FAIL 1 | WARN 11 | SKIP 8 | PASS 327 ] + 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 ... NONE + ‘ggPMX-guide.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 1 ERROR, 2 NOTEs + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/ggPMX/old/ggPMX.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘ggPMX/DESCRIPTION’ ... OK +* this is package ‘ggPMX’ version ‘1.2.8’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... NOTE +... + [ FAIL 1 | WARN 11 | SKIP 8 | PASS 327 ] + 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 ... NONE + ‘ggPMX-guide.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 1 ERROR, 2 NOTEs + + + + + +``` +# NA + +
+ +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/NA +* Number of recursive dependencies: 0 + +Run `cloud_details(, "NA")` for more info + +
+ +## Error before installation + +### Devel + +``` + + + + + + +``` +### CRAN + +``` + + + + + + +``` +# loon.ggplot + +
+ +* Version: 1.3.2 +* GitHub: https://github.com/great-northern-diver/loon.ggplot +* Source code: https://github.com/cran/loon.ggplot +* Date/Publication: 2022-10-03 14:50:02 UTC +* Number of recursive dependencies: 104 + +Run `cloud_details(, "loon.ggplot")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/loon.ggplot/new/loon.ggplot.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘loon.ggplot/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘loon.ggplot’ version ‘1.3.2’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘loon’ + +Package suggested but not available for checking: ‘zenplots’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/loon.ggplot/old/loon.ggplot.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘loon.ggplot/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘loon.ggplot’ version ‘1.3.2’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘loon’ + +Package suggested but not available for checking: ‘zenplots’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# loon.shiny + +
+ +* Version: 1.0.3 +* GitHub: NA +* Source code: https://github.com/cran/loon.shiny +* Date/Publication: 2022-10-08 15:30:02 UTC +* Number of recursive dependencies: 132 + +Run `cloud_details(, "loon.shiny")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/loon.shiny/new/loon.shiny.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘loon.shiny/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘loon.shiny’ version ‘1.0.3’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Packages required but not available: 'loon', 'loon.ggplot' + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/loon.shiny/old/loon.shiny.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘loon.shiny/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘loon.shiny’ version ‘1.0.3’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Packages required but not available: 'loon', 'loon.ggplot' + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# NA + +
+ +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/NA +* Number of recursive dependencies: 0 + +Run `cloud_details(, "NA")` for more info + +
+ +## Error before installation + +### Devel + +``` + + + + + + +``` +### CRAN + +``` + + + + + + +``` +# NA + +
+ +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/NA +* Number of recursive dependencies: 0 + +Run `cloud_details(, "NA")` for more info + +
+ +## Error before installation + +### Devel + +``` + + + + + + +``` +### CRAN + +``` + + + + + + +``` +# NA + +
+ +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/NA +* Number of recursive dependencies: 0 + +Run `cloud_details(, "NA")` for more info + +
+ +## Error before installation + +### Devel + +``` + + + + + + +``` +### CRAN + +``` + + + + + + +``` +# nlmixr2plot + +
+ +* Version: 2.0.6 +* GitHub: https://github.com/nlmixr2/nlmixr2plot +* Source code: https://github.com/cran/nlmixr2plot +* Date/Publication: 2022-05-23 07:50:02 UTC +* Number of recursive dependencies: 198 + +Run `cloud_details(, "nlmixr2plot")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/nlmixr2plot/new/nlmixr2plot.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘nlmixr2plot/DESCRIPTION’ ... OK +* this is package ‘nlmixr2plot’ version ‘2.0.6’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Packages required but not available: 'nlmixr2est', 'nlmixr2extra' + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/nlmixr2plot/old/nlmixr2plot.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘nlmixr2plot/DESCRIPTION’ ... OK +* this is package ‘nlmixr2plot’ version ‘2.0.6’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Packages required but not available: 'nlmixr2est', 'nlmixr2extra' + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# NA + +
+ +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/NA +* Number of recursive dependencies: 0 + +Run `cloud_details(, "NA")` for more info + +
+ +## Error before installation + +### Devel + +``` + + + + + + +``` +### CRAN + +``` + + + + + + +``` +# NA + +
+ +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/NA +* Number of recursive dependencies: 0 + +Run `cloud_details(, "NA")` for more info + +
+ +## Error before installation + +### Devel + +``` + + + + + + +``` +### CRAN + +``` + + + + + + +``` +# Platypus + +
+ +* Version: 3.4.1 +* GitHub: NA +* Source code: https://github.com/cran/Platypus +* Date/Publication: 2022-08-15 07:20:20 UTC +* Number of recursive dependencies: 355 + +Run `cloud_details(, "Platypus")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/Platypus/new/Platypus.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘Platypus/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘Platypus’ version ‘3.4.1’ +* package encoding: UTF-8 +* checking package namespace information ... 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 + ‘PlatypusV3_agedCNS.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 1 NOTE + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/Platypus/old/Platypus.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘Platypus/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘Platypus’ version ‘3.4.1’ +* package encoding: UTF-8 +* checking package namespace information ... 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 + ‘PlatypusV3_agedCNS.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 1 NOTE + + + + + +``` +# NA + +
+ +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/NA +* Number of recursive dependencies: 0 + +Run `cloud_details(, "NA")` for more info + +
+ +## Error before installation + +### Devel + +``` + + + + + + +``` +### CRAN + +``` + + + + + + +``` +# NA + +
+ +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/NA +* Number of recursive dependencies: 0 + +Run `cloud_details(, "NA")` for more info + +
+ +## Error before installation + +### Devel + +``` + + + + + + +``` +### CRAN + +``` + + + + + + ``` # NA @@ -137,6 +837,82 @@ Run `cloud_details(, "NA")` for more info +``` +# tidySEM + +
+ +* Version: 0.2.3 +* GitHub: https://github.com/cjvanlissa/tidySEM +* Source code: https://github.com/cran/tidySEM +* Date/Publication: 2022-04-14 17:50:02 UTC +* Number of recursive dependencies: 170 + +Run `cloud_details(, "tidySEM")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/tidySEM/new/tidySEM.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘tidySEM/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘tidySEM’ version ‘0.2.3’ +* package encoding: UTF-8 +* checking package namespace information ... OK +... +* checking for unstated dependencies in vignettes ... OK +* checking package vignettes in ‘inst/doc’ ... OK +* checking running R code from vignettes ... NONE + ‘Generating_syntax.Rmd’ using ‘UTF-8’... OK + ‘Plotting_graphs.Rmd’ using ‘UTF-8’... OK + ‘Tabulating_results.Rmd’ using ‘UTF-8’... OK + ‘sem_graph.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 1 NOTE + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/tidySEM/old/tidySEM.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘tidySEM/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘tidySEM’ version ‘0.2.3’ +* package encoding: UTF-8 +* checking package namespace information ... OK +... +* checking for unstated dependencies in vignettes ... OK +* checking package vignettes in ‘inst/doc’ ... OK +* checking running R code from vignettes ... NONE + ‘Generating_syntax.Rmd’ using ‘UTF-8’... OK + ‘Plotting_graphs.Rmd’ using ‘UTF-8’... OK + ‘Tabulating_results.Rmd’ using ‘UTF-8’... OK + ‘sem_graph.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 1 NOTE + + + + + ``` # NA @@ -172,4 +948,152 @@ Run `cloud_details(, "NA")` for more info +``` +# vivid + +
+ +* Version: 0.2.3 +* GitHub: NA +* Source code: https://github.com/cran/vivid +* Date/Publication: 2021-11-20 01:30:02 UTC +* Number of recursive dependencies: 201 + +Run `cloud_details(, "vivid")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/vivid/new/vivid.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘vivid/DESCRIPTION’ ... OK +* this is package ‘vivid’ version ‘0.2.3’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... NOTE +... +* 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 + ‘vivid.Rmd’ using ‘UTF-8’... OK + ‘vividQStart.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 2 NOTEs + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/vivid/old/vivid.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘vivid/DESCRIPTION’ ... OK +* this is package ‘vivid’ version ‘0.2.3’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... NOTE +... +* 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 + ‘vivid.Rmd’ using ‘UTF-8’... OK + ‘vividQStart.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 2 NOTEs + + + + + +``` +# xpose.nlmixr2 + +
+ +* Version: 0.4.0 +* GitHub: NA +* Source code: https://github.com/cran/xpose.nlmixr2 +* Date/Publication: 2022-06-08 09:10:02 UTC +* Number of recursive dependencies: 204 + +Run `cloud_details(, "xpose.nlmixr2")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/xpose.nlmixr2/new/xpose.nlmixr2.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘xpose.nlmixr2/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘xpose.nlmixr2’ version ‘0.4.0’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘nlmixr2est’ + +Package suggested but not available for checking: ‘nlmixr2’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/xpose.nlmixr2/old/xpose.nlmixr2.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘xpose.nlmixr2/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘xpose.nlmixr2’ version ‘0.4.0’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘nlmixr2est’ + +Package suggested but not available for checking: ‘nlmixr2’ + +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 9d12db4cd..af1985c00 100644 --- a/revdep/problems.md +++ b/revdep/problems.md @@ -1,14 +1,53 @@ -# tibbletime +# globaltrends
-* Version: 0.1.6 -* GitHub: https://github.com/business-science/tibbletime -* Source code: https://github.com/cran/tibbletime -* Date/Publication: 2020-07-21 13:50:02 UTC -* Number of recursive dependencies: 86 +* Version: 0.0.12 +* GitHub: https://github.com/ha-pu/globaltrends +* Source code: https://github.com/cran/globaltrends +* Date/Publication: 2022-06-23 07:10:11 UTC +* Number of recursive dependencies: 108 -Run `cloud_details(, "tibbletime")` for more info +Run `cloud_details(, "globaltrends")` for more info + +
+ +## Newly broken + +* checking tests ... ERROR + ``` + Running ‘test_functions.r’ + Running ‘testthat.r’ + Running the tests in ‘tests/testthat.r’ failed. + Last 13 lines of output: + Error in `initialize_db()`: Error: File 'db/globaltrends_db.sqlite' already exists. + Backtrace: + ▆ + 1. └─globaltrends::initialize_db() at test-plot_voi_doi.R:8:0 + ── Error ('test-synonyms.R:8'): (code run outside of `test_that()`) ──────────── + Error in `initialize_db()`: Error: File 'db/globaltrends_db.sqlite' already exists. + Backtrace: + ▆ + 1. └─globaltrends::initialize_db() at test-synonyms.R:8:0 + + [ FAIL 15 | WARN 22 | SKIP 0 | PASS 33 ] + Error: Test failures + In addition: Warning message: + call dbDisconnect() when finished working with a connection + Execution halted + ``` + +# goldilocks + +
+ +* Version: 0.3.0 +* GitHub: NA +* Source code: https://github.com/cran/goldilocks +* Date/Publication: 2021-05-10 08:20:11 UTC +* Number of recursive dependencies: 68 + +Run `cloud_details(, "goldilocks")` for more info
@@ -19,20 +58,94 @@ Run `cloud_details(, "tibbletime")` for more info Running ‘testthat.R’ Running the tests in ‘tests/testthat.R’ failed. Last 13 lines of output: - 4. └─tibbletime::get_index_col(FANG_unnested) - 5. ├─.tbl_time[[get_index_char(.tbl_time)]] - 6. ├─tibble:::`[[.tbl_df`(.tbl_time, get_index_char(.tbl_time)) - 7. │ └─tibble:::tbl_subset2(x, j = i, j_arg = substitute(i)) - 8. └─tibbletime::get_index_char(.tbl_time) - 9. ├─rlang::quo_name(get_index_quo(.tbl_time)) - 10. │ ├─rlang::expr_name(quo_squash(quo)) - 11. │ └─rlang::quo_squash(quo) - 12. │ └─rlang::is_quosure(quo) - 13. └─tibbletime::get_index_quo(.tbl_time) - 14. └─tibbletime:::glue_stop("Object is not of class `tbl_time`.") + ══ Skipped tests ═══════════════════════════════════════════════════════════════ + • On CRAN (1) - [ FAIL 3 | WARN 2 | SKIP 0 | PASS 142 ] + ══ Failed tests ════════════════════════════════════════════════════════════════ + ── Error ('test-survival_adapt.R:54'): survival_adapt-cox ────────────────────── + Error in `if (success > prob_ha) { + expected_success_test <- expected_success_test + 1 + }`: missing value where TRUE/FALSE needed + Backtrace: + ▆ + 1. └─goldilocks::survival_adapt(...) at test-survival_adapt.R:54:2 + + [ FAIL 1 | WARN 2 | SKIP 1 | PASS 17 ] Error: Test failures Execution halted ``` +# psfmi + +
+ +* Version: 1.0.0 +* GitHub: https://github.com/mwheymans/psfmi +* Source code: https://github.com/cran/psfmi +* Date/Publication: 2021-09-23 10:10:05 UTC +* Number of recursive dependencies: 156 + +Run `cloud_details(, "psfmi")` for more info + +
+ +## Newly broken + +* checking examples ... ERROR + ``` + Running examples in ‘psfmi-Ex.R’ failed + The error most likely occurred in: + + > ### Name: psfmi_validate + > ### Title: Internal validation and performance of logistic prediction + > ### models across Multiply Imputed datasets + > ### Aliases: psfmi_validate + > + > ### ** Examples + > + ... + ! `strata` should be a single name or character value. + Backtrace: + ▆ + 1. └─psfmi::psfmi_validate(...) + 2. └─psfmi::cv_MI(...) + 3. ├─purrr::map(...) + 4. └─rsample::vfold_cv(data_orig, v = folds, strata = unlist(data_orig[pobj$Outcome])) + 5. └─rsample:::strata_check(strata, data) + 6. └─rlang::abort("`strata` should be a single name or character value.") + Execution halted + ``` + +* checking re-building of vignette outputs ... WARNING + ``` + Error(s) in re-building vignettes: + --- re-building ‘MI_boot.Rmd’ using rmarkdown + --- finished re-building ‘MI_boot.Rmd’ + + --- re-building ‘MI_cv_naive.Rmd’ using rmarkdown + --- finished re-building ‘MI_cv_naive.Rmd’ + + --- re-building ‘Pool_Model_Performance.Rmd’ using rmarkdown + --- finished re-building ‘Pool_Model_Performance.Rmd’ + + ... + --- finished re-building ‘psfmi_StabilityAnalysis.Rmd’ + + --- re-building ‘psfmi_mice.Rmd’ using rmarkdown + --- finished re-building ‘psfmi_mice.Rmd’ + + SUMMARY: processing the following files failed: + ‘cv_MI.Rmd’ ‘cv_MI_RR.Rmd’ ‘development_workflow.Rmd’ + + Error: Vignette re-building failed. + Execution halted + ``` + +## In both + +* checking dependencies in R code ... NOTE + ``` + Namespace in Imports field not imported from: ‘miceadds’ + All declared Imports should be used. + ``` + From b4f1c4098a3f432e1569a90475d45f5c22555be2 Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Wed, 19 Oct 2022 19:36:46 +0200 Subject: [PATCH 179/312] Don't allow casting to non-bare data frames --- R/cast.R | 10 ++++++---- tests/testthat/_snaps/cast.md | 9 +++++++++ tests/testthat/_snaps/type-misc.md | 9 +++++++++ tests/testthat/test-cast.R | 6 ++++-- tests/testthat/test-type-misc.R | 8 ++++---- 5 files changed, 32 insertions(+), 10 deletions(-) diff --git a/R/cast.R b/R/cast.R index 54a9d71e1..3eab09067 100644 --- a/R/cast.R +++ b/R/cast.R @@ -209,11 +209,13 @@ vec_default_cast <- function(x, return(out) } - # Bare-class fallback for data frames - if (inherits(to, "tbl_df")) { - out <- df_as_tibble(out) + if (is_bare_df(to)) { + # Bare-class fallback for data frames + if (inherits(to, "tbl_df")) { + out <- df_as_tibble(out) + } + return(out) } - return(out) } if (is_same_type(x, to)) { diff --git a/tests/testthat/_snaps/cast.md b/tests/testthat/_snaps/cast.md index d77ca4507..170a26aba 100644 --- a/tests/testthat/_snaps/cast.md +++ b/tests/testthat/_snaps/cast.md @@ -62,6 +62,15 @@ Error: ! Can't combine `..1$a$b` > and `..2$a$b` . +# vec_cast() only falls back when casting to base type + + Code + (expect_error(vec_cast(mtcars, foobar(mtcars)))) + Output + + Error: + ! Can't convert `mtcars` to . + # vec_cast() only attempts to fall back if `to` is a data frame (#1568) Code diff --git a/tests/testthat/_snaps/type-misc.md b/tests/testthat/_snaps/type-misc.md index ba0833783..dc44c3fa8 100644 --- a/tests/testthat/_snaps/type-misc.md +++ b/tests/testthat/_snaps/type-misc.md @@ -1,3 +1,12 @@ +# data.table and tibble do not have a common type + + Code + (expect_error(vec_cast(tibble(y = 2), data.table(x = TRUE, y = 1L)))) + Output + + Error: + ! Can't convert `tibble(y = 2)` to . + # data table has formatting methods Code diff --git a/tests/testthat/test-cast.R b/tests/testthat/test-cast.R index e6105bbdb..163e9ca68 100644 --- a/tests/testthat/test-cast.R +++ b/tests/testthat/test-cast.R @@ -92,9 +92,11 @@ test_that("unspecified can be cast to shaped vectors", { expect_identical(out, exp) }) -test_that("vec_cast() falls back to base class even when casting to non-base type", { +test_that("vec_cast() only falls back when casting to base type", { expect_equal(vec_cast(foobar(mtcars), mtcars), mtcars) - expect_equal(vec_cast(mtcars, foobar(mtcars)), mtcars) + expect_snapshot({ + (expect_error(vec_cast(mtcars, foobar(mtcars)))) + }) }) test_that("vec_cast() only attempts to fall back if `to` is a data frame (#1568)", { diff --git a/tests/testthat/test-type-misc.R b/tests/testthat/test-type-misc.R index e1c61c7d4..8b4905467 100644 --- a/tests/testthat/test-type-misc.R +++ b/tests/testthat/test-type-misc.R @@ -77,10 +77,10 @@ test_that("data.table and tibble do not have a common type", { vec_cast(data.table(y = 2), tibble(x = TRUE, y = 1L)), tibble(x = lgl(NA), y = 2L) ) - expect_identical( - vec_cast(tibble(y = 2), data.table(x = TRUE, y = 1L)), - data_frame(x = lgl(NA), y = 2L) - ) + + expect_snapshot({ + (expect_error(vec_cast(tibble(y = 2), data.table(x = TRUE, y = 1L)))) + }) }) test_that("data table has formatting methods", { From 440e314b82baeee9c2d579ff92457c23590d2685 Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Wed, 19 Oct 2022 19:47:58 +0200 Subject: [PATCH 180/312] Mention relaxed behaviour in NEWS --- NEWS.md | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/NEWS.md b/NEWS.md index 7445d909f..e9e487900 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,5 +1,9 @@ # vctrs (development version) +* `vec_ptype2()` now consistently falls back to bare data frame in + case of incompatible data frame subclasses. This is part of a + general move towards relaxed coercion rules. + * Common type and cast errors now inherit from `"vctrs_error_ptype2"` and `"vctrs_error_cast"` respectively. They are still both subclasses from `"vctrs_error_incompatible_type"` (which used to be From ac2f0a1c41a6a5c8c788eef68aef25cfe0bc6980 Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Thu, 6 Oct 2022 15:31:17 +0200 Subject: [PATCH 181/312] Import type checking compats --- R/compat-obj-type.R | 339 ++++++++++++++++++++++++++++++ R/compat-types.check.R | 463 +++++++++++++++++++++++++++++++++++++++++ 2 files changed, 802 insertions(+) create mode 100644 R/compat-obj-type.R create mode 100644 R/compat-types.check.R diff --git a/R/compat-obj-type.R b/R/compat-obj-type.R new file mode 100644 index 000000000..d86dca51b --- /dev/null +++ b/R/compat-obj-type.R @@ -0,0 +1,339 @@ +# nocov start --- r-lib/rlang compat-obj-type +# +# Changelog +# ========= +# +# 2022-10-04: +# - `obj_type_friendly(value = TRUE)` now shows numeric scalars +# literally. +# - `stop_friendly_type()` now takes `show_value`, passed to +# `obj_type_friendly()` as the `value` argument. +# +# 2022-10-03: +# - Added `allow_na` and `allow_null` arguments. +# - `NULL` is now backticked. +# - Better friendly type for infinities and `NaN`. +# +# 2022-09-16: +# - Unprefixed usage of rlang functions with `rlang::` to +# avoid onLoad issues when called from rlang (#1482). +# +# 2022-08-11: +# - Prefixed usage of rlang functions with `rlang::`. +# +# 2022-06-22: +# - `friendly_type_of()` is now `obj_type_friendly()`. +# - Added `obj_type_oo()`. +# +# 2021-12-20: +# - Added support for scalar values and empty vectors. +# - Added `stop_input_type()` +# +# 2021-06-30: +# - Added support for missing arguments. +# +# 2021-04-19: +# - Added support for matrices and arrays (#141). +# - Added documentation. +# - Added changelog. + + +#' Return English-friendly type +#' @param x Any R object. +#' @param value Whether to describe the value of `x`. Special values +#' like `NA` or `""` are always described. +#' @param length Whether to mention the length of vectors and lists. +#' @return A string describing the type. Starts with an indefinite +#' article, e.g. "an integer vector". +#' @noRd +obj_type_friendly <- function(x, value = TRUE) { + if (is_missing(x)) { + return("absent") + } + + if (is.object(x)) { + if (inherits(x, "quosure")) { + type <- "quosure" + } else { + type <- paste(class(x), collapse = "/") + } + return(sprintf("a <%s> object", type)) + } + + if (!is_vector(x)) { + return(.rlang_as_friendly_type(typeof(x))) + } + + n_dim <- length(dim(x)) + + if (!n_dim) { + if (!is_list(x) && length(x) == 1) { + if (is_na(x)) { + return(switch( + typeof(x), + logical = "`NA`", + integer = "an integer `NA`", + double = + if (is.nan(x)) { + "`NaN`" + } else { + "a numeric `NA`" + }, + complex = "a complex `NA`", + character = "a character `NA`", + .rlang_stop_unexpected_typeof(x) + )) + } + + show_infinites <- function(x) { + if (x > 0) { + "`Inf`" + } else { + "`-Inf`" + } + } + str_encode <- function(x, width = 30, ...) { + if (nchar(x) > width) { + x <- substr(x, 1, width - 3) + x <- paste0(x, "...") + } + encodeString(x, ...) + } + + if (value) { + if (is.numeric(x) && is.infinite(x)) { + return(show_infinites(x)) + } + + if (is.numeric(x) || is.complex(x)) { + number <- as.character(round(x, 2)) + what <- if (is.complex(x)) "the complex number" else "the number" + return(paste(what, number)) + } + + return(switch( + typeof(x), + logical = if (x) "`TRUE`" else "`FALSE`", + character = { + what <- if (nzchar(x)) "the string" else "the empty string" + paste(what, str_encode(x, quote = "\"")) + }, + raw = paste("the raw value", as.character(x)), + .rlang_stop_unexpected_typeof(x) + )) + } + + return(switch( + typeof(x), + logical = "a logical value", + integer = "an integer", + double = if (is.infinite(x)) show_infinites(x) else "a number", + complex = "a complex number", + character = if (nzchar(x)) "a string" else "\"\"", + raw = "a raw value", + .rlang_stop_unexpected_typeof(x) + )) + } + + if (length(x) == 0) { + return(switch( + typeof(x), + logical = "an empty logical vector", + integer = "an empty integer vector", + double = "an empty numeric vector", + complex = "an empty complex vector", + character = "an empty character vector", + raw = "an empty raw vector", + list = "an empty list", + .rlang_stop_unexpected_typeof(x) + )) + } + } + + vec_type_friendly(x) +} + +vec_type_friendly <- function(x, length = FALSE) { + if (!is_vector(x)) { + abort("`x` must be a vector.") + } + type <- typeof(x) + n_dim <- length(dim(x)) + + add_length <- function(type) { + if (length && !n_dim) { + paste0(type, sprintf(" of length %s", length(x))) + } else { + type + } + } + + if (type == "list") { + if (n_dim < 2) { + return(add_length("a list")) + } else if (is.data.frame(x)) { + return("a data frame") + } else if (n_dim == 2) { + return("a list matrix") + } else { + return("a list array") + } + } + + type <- switch( + type, + logical = "a logical %s", + integer = "an integer %s", + numeric = , + double = "a double %s", + complex = "a complex %s", + character = "a character %s", + raw = "a raw %s", + type = paste0("a ", type, " %s") + ) + + if (n_dim < 2) { + kind <- "vector" + } else if (n_dim == 2) { + kind <- "matrix" + } else { + kind <- "array" + } + out <- sprintf(type, kind) + + if (n_dim >= 2) { + out + } else { + add_length(out) + } +} + +.rlang_as_friendly_type <- function(type) { + switch( + type, + + list = "a list", + + NULL = "`NULL`", + environment = "an environment", + externalptr = "a pointer", + weakref = "a weak reference", + S4 = "an S4 object", + + name = , + symbol = "a symbol", + language = "a call", + pairlist = "a pairlist node", + expression = "an expression vector", + + char = "an internal string", + promise = "an internal promise", + ... = "an internal dots object", + any = "an internal `any` object", + bytecode = "an internal bytecode object", + + primitive = , + builtin = , + special = "a primitive function", + closure = "a function", + + type + ) +} + +.rlang_stop_unexpected_typeof <- function(x, call = caller_env()) { + abort( + sprintf("Unexpected type <%s>.", typeof(x)), + call = call + ) +} + +#' Return OO type +#' @param x Any R object. +#' @return One of `"bare"` (for non-OO objects), `"S3"`, `"S4"`, +#' `"R6"`, or `"R7"`. +#' @noRd +obj_type_oo <- function(x) { + if (!is.object(x)) { + return("bare") + } + + class <- inherits(x, c("R6", "R7_object"), which = TRUE) + + if (class[[1]]) { + "R6" + } else if (class[[2]]) { + "R7" + } else if (isS4(x)) { + "S4" + } else { + "S3" + } +} + +#' @param x The object type which does not conform to `what`. Its +#' `obj_type_friendly()` is taken and mentioned in the error message. +#' @param what The friendly expected type as a string. Can be a +#' character vector of expected types, in which case the error +#' message mentions all of them in an "or" enumeration. +#' @param show_value Passed to `value` argument of `obj_type_friendly()`. +#' @param ... Arguments passed to [abort()]. +#' @inheritParams args_error_context +#' @noRd +stop_input_type <- function(x, + what, + ..., + allow_na = FALSE, + allow_null = FALSE, + show_value = TRUE, + arg = caller_arg(x), + call = caller_env()) { + # From compat-cli.R + cli <- env_get_list( + nms = c("format_arg", "format_code"), + last = topenv(), + default = function(x) sprintf("`%s`", x), + inherit = TRUE + ) + + if (allow_na) { + what <- c(what, cli$format_code("NA")) + } + if (allow_null) { + what <- c(what, cli$format_code("NULL")) + } + if (length(what)) { + what <- oxford_comma(what) + } + + message <- sprintf( + "%s must be %s, not %s.", + cli$format_arg(arg), + what, + obj_type_friendly(x, value = show_value) + ) + + abort(message, ..., call = call, arg = arg) +} + +oxford_comma <- function(chr, sep = ", ", final = "or") { + n <- length(chr) + + if (n < 2) { + return(chr) + } + + head <- chr[seq_len(n - 1)] + last <- chr[n] + + head <- paste(head, collapse = sep) + + # Write a or b. But a, b, or c. + if (n > 2) { + paste0(head, sep, final, " ", last) + } else { + paste0(head, " ", final, " ", last) + } +} + +# nocov end diff --git a/R/compat-types.check.R b/R/compat-types.check.R new file mode 100644 index 000000000..3e46ca431 --- /dev/null +++ b/R/compat-types.check.R @@ -0,0 +1,463 @@ +# nocov start --- r-lib/rlang compat-types-check +# +# Dependencies +# ============ +# +# - compat-obj-type.R +# +# Changelog +# ========= +# +# 2022-10-04: +# - Added `check_name()` that forbids the empty string. +# `check_string()` allows the empty string by default. +# +# 2022-09-28: +# - Removed `what` arguments. +# - Added `allow_na` and `allow_null` arguments. +# - Added `allow_decimal` and `allow_infinite` arguments. +# - Improved errors with absent arguments. +# +# +# 2022-09-16: +# - Unprefixed usage of rlang functions with `rlang::` to +# avoid onLoad issues when called from rlang (#1482). +# +# 2022-08-11: +# - Added changelog. + +# Scalars ----------------------------------------------------------------- + +check_bool <- function(x, + ..., + allow_na = FALSE, + allow_null = FALSE, + arg = caller_arg(x), + call = caller_env()) { + if (!missing(x)) { + if (is_bool(x)) { + return(invisible(NULL)) + } + if (allow_null && is_null(x)) { + return(invisible(NULL)) + } + if (allow_na && identical(x, NA)) { + return(invisible(NULL)) + } + } + + stop_input_type( + x, + c("`TRUE`", "`FALSE`"), + ..., + allow_na = allow_na, + allow_null = allow_null, + arg = arg, + call = call + ) +} + +check_string <- function(x, + ..., + allow_empty = TRUE, + allow_na = FALSE, + allow_null = FALSE, + arg = caller_arg(x), + call = caller_env()) { + if (!missing(x)) { + is_string <- .rlang_check_is_string( + x, + allow_empty = allow_empty, + allow_na = allow_na, + allow_null = allow_null + ) + if (is_string) { + return(invisible(NULL)) + } + } + + stop_input_type( + x, + "a single string", + ..., + allow_na = allow_na, + allow_null = allow_null, + arg = arg, + call = call + ) +} + +.rlang_check_is_string <- function(x, + allow_empty, + allow_na, + allow_null) { + if (is_string(x)) { + if (allow_empty || !is_string(x, "")) { + return(TRUE) + } + } + + if (allow_null && is_null(x)) { + return(TRUE) + } + + if (allow_na && (identical(x, NA) || identical(x, na_chr))) { + return(TRUE) + } + + FALSE +} + +check_name <- function(x, + ..., + allow_null = FALSE, + arg = caller_arg(x), + call = caller_env()) { + if (!missing(x)) { + is_string <- .rlang_check_is_string( + x, + allow_empty = FALSE, + allow_na = FALSE, + allow_null = allow_null + ) + if (is_string) { + return(invisible(NULL)) + } + } + + stop_input_type( + x, + "a valid name", + ..., + allow_na = FALSE, + allow_null = allow_null, + arg = arg, + call = call + ) +} + +check_number_decimal <- function(x, + ..., + min = -Inf, + max = Inf, + allow_infinite = TRUE, + allow_na = FALSE, + allow_null = FALSE, + arg = caller_arg(x), + call = caller_env()) { + .rlang_types_check_number( + x, + ..., + min = min, + max = max, + allow_decimal = TRUE, + allow_infinite = allow_infinite, + allow_na = allow_na, + allow_null = allow_null, + arg = arg, + call = call + ) +} + +check_number_whole <- function(x, + ..., + min = -Inf, + max = Inf, + allow_na = FALSE, + allow_null = FALSE, + arg = caller_arg(x), + call = caller_env()) { + .rlang_types_check_number( + x, + ..., + min = min, + max = max, + allow_decimal = FALSE, + allow_infinite = FALSE, + allow_na = allow_na, + allow_null = allow_null, + arg = arg, + call = call + ) +} + +.rlang_types_check_number <- function(x, + ..., + min = -Inf, + max = Inf, + allow_decimal = FALSE, + allow_infinite = FALSE, + allow_na = FALSE, + allow_null = FALSE, + arg = caller_arg(x), + call = caller_env()) { + if (allow_decimal) { + what <- "a number" + } else { + what <- "a whole number" + } + + .stop <- function(x, what, ...) stop_input_type( + x, + what, + ..., + allow_na = allow_na, + allow_null = allow_null, + arg = arg, + call = call + ) + + if (!missing(x)) { + is_number <- is_number( + x, + allow_decimal = allow_decimal, + allow_infinite = allow_infinite + ) + + if (is_number) { + if (min > -Inf && max < Inf) { + what <- sprintf("a number between %s and %s", min, max) + } else { + what <- NULL + } + if (x < min) { + what <- what %||% sprintf("a number larger than %s", min) + .stop(x, what, ...) + } + if (x > max) { + what <- what %||% sprintf("a number smaller than %s", max) + .stop(x, what, ...) + } + return(invisible(NULL)) + } + + if (allow_null && is_null(x)) { + return(invisible(NULL)) + } + if (allow_na && (identical(x, NA) || + identical(x, na_dbl) || + identical(x, na_int))) { + return(invisible(NULL)) + } + } + + .stop(x, what, ...) +} + +is_number <- function(x, + allow_decimal = FALSE, + allow_infinite = FALSE) { + if (!typeof(x) %in% c("integer", "double")) { + return(FALSE) + } + if (length(x) != 1) { + return(FALSE) + } + if (is.na(x)) { + return(FALSE) + } + if (!allow_decimal && !is_integerish(x)) { + return(FALSE) + } + if (!allow_infinite && is.infinite(x)) { + return(FALSE) + } + TRUE +} + +check_symbol <- function(x, + ..., + allow_null = FALSE, + arg = caller_arg(x), + call = caller_env()) { + if (!missing(x)) { + if (is_symbol(x)) { + return(invisible(NULL)) + } + if (allow_null && is_null(x)) { + return(invisible(NULL)) + } + } + + stop_input_type( + x, + "a symbol", + ..., + allow_null = allow_null, + arg = arg, + call = call + ) +} + +check_arg <- function(x, + ..., + allow_null = FALSE, + arg = caller_arg(x), + call = caller_env()) { + if (!missing(x)) { + if (is_symbol(x)) { + return(invisible(NULL)) + } + if (allow_null && is_null(x)) { + return(invisible(NULL)) + } + } + + stop_input_type( + x, + "an argument name", + ..., + allow_null = allow_null, + arg = arg, + call = call + ) +} + +check_call <- function(x, + ..., + allow_null = FALSE, + arg = caller_arg(x), + call = caller_env()) { + if (!missing(x)) { + if (is_call(x)) { + return(invisible(NULL)) + } + if (allow_null && is_null(x)) { + return(invisible(NULL)) + } + } + + stop_input_type( + x, + "a defused call", + ..., + allow_null = allow_null, + arg = arg, + call = call + ) +} + +check_environment <- function(x, + ..., + allow_null = FALSE, + arg = caller_arg(x), + call = caller_env()) { + if (!missing(x)) { + if (is_environment(x)) { + return(invisible(NULL)) + } + if (allow_null && is_null(x)) { + return(invisible(NULL)) + } + } + + stop_input_type( + x, + "an environment", + ..., + allow_null = allow_null, + arg = arg, + call = call + ) +} + +check_function <- function(x, + ..., + allow_null = FALSE, + arg = caller_arg(x), + call = caller_env()) { + if (!missing(x)) { + if (is_function(x)) { + return(invisible(NULL)) + } + if (allow_null && is_null(x)) { + return(invisible(NULL)) + } + } + + stop_input_type( + x, + "a function", + ..., + allow_null = allow_null, + arg = arg, + call = call + ) +} + +check_closure <- function(x, + ..., + allow_null = FALSE, + arg = caller_arg(x), + call = caller_env()) { + if (!missing(x)) { + if (is_closure(x)) { + return(invisible(NULL)) + } + if (allow_null && is_null(x)) { + return(invisible(NULL)) + } + } + + stop_input_type( + x, + "an R function", + ..., + allow_null = allow_null, + arg = arg, + call = call + ) +} + +check_formula <- function(x, + ..., + allow_null = FALSE, + arg = caller_arg(x), + call = caller_env()) { + if (!missing(x)) { + if (is_formula(x)) { + return(invisible(NULL)) + } + if (allow_null && is_null(x)) { + return(invisible(NULL)) + } + } + + stop_input_type( + x, + "a formula", + ..., + allow_null = allow_null, + arg = arg, + call = call + ) +} + + +# Vectors ----------------------------------------------------------------- + +check_character <- function(x, + ..., + allow_null = FALSE, + arg = caller_arg(x), + call = caller_env()) { + if (!missing(x)) { + if (is_character(x)) { + return(invisible(NULL)) + } + if (allow_null && is_null(x)) { + return(invisible(NULL)) + } + } + + stop_input_type( + x, + "a character vector", + ..., + allow_null = allow_null, + arg = arg, + call = call + ) +} + +# nocov end From 11b3a9d2a8afe5d5cbd5aa64a3391b699b71ad10 Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Thu, 6 Oct 2022 15:34:48 +0200 Subject: [PATCH 182/312] State expected value first --- R/subscript-loc.R | 2 +- tests/testthat/_snaps/conditions.md | 2 +- tests/testthat/_snaps/size.md | 10 +++++----- tests/testthat/_snaps/slice.md | 2 +- tests/testthat/_snaps/subscript-loc.md | 14 +++++++------- 5 files changed, 15 insertions(+), 15 deletions(-) diff --git a/R/subscript-loc.R b/R/subscript-loc.R index 711cb9556..292f00982 100644 --- a/R/subscript-loc.R +++ b/R/subscript-loc.R @@ -366,7 +366,7 @@ cnd_bullets_location2_need_present <- function(cnd, ...) { cnd_bullets_location2_need_positive <- function(cnd, ...) { cnd$subscript_arg <- append_arg("Subscript", cnd$subscript_arg) format_error_bullets(c( - x = glue::glue_data(cnd, "{subscript_arg} has value {i} but must be a positive location.") + x = glue::glue_data(cnd, "{subscript_arg} must be a positive location, not {i}.") )) } diff --git a/tests/testthat/_snaps/conditions.md b/tests/testthat/_snaps/conditions.md index 921b36990..e2b642403 100644 --- a/tests/testthat/_snaps/conditions.md +++ b/tests/testthat/_snaps/conditions.md @@ -12,7 +12,7 @@ Output Error in `stop_incompatible_type()`: - ! `action` must be a character vector, not a number. + ! `action` must be a character vector, not the number 1. # can override arg in OOB conditions diff --git a/tests/testthat/_snaps/size.md b/tests/testthat/_snaps/size.md index 38d9665e3..4040948ce 100644 --- a/tests/testthat/_snaps/size.md +++ b/tests/testthat/_snaps/size.md @@ -11,7 +11,7 @@ Output Error in `vec_as_short_length()`: - ! `my_arg` must be a single number, not an integer vector of length 2. + ! `my_arg` must be a single number, not an integer vector. Code (expect_error(my_function(1.5))) Output @@ -35,13 +35,13 @@ Output Error in `vec_as_short_length()`: - ! `my_arg` must be a single number, not a string. + ! `my_arg` must be a single number, not the string "foo". Code (expect_error(my_function(foobar(1:2)))) Output Error in `vec_as_short_length()`: - ! `my_arg` must be a single number, not NULL. + ! `my_arg` must be a single number, not `NULL`. Code (expect_error(my_function(.Machine$double.xmax))) Output @@ -65,13 +65,13 @@ Output Error in `vec_size_common()`: - ! `.size` must be a single number, not a string. + ! `.size` must be a single number, not the string "foo". Code (expect_error(vec_size_common(.size = 1:2))) Output Error in `vec_size_common()`: - ! `.size` must be a single number, not an integer vector of length 2. + ! `.size` must be a single number, not an integer vector. # vec_size_common() mentions `arg` in errors diff --git a/tests/testthat/_snaps/slice.md b/tests/testthat/_snaps/slice.md index e57ea165d..94420902c 100644 --- a/tests/testthat/_snaps/slice.md +++ b/tests/testthat/_snaps/slice.md @@ -134,7 +134,7 @@ Output Error in `vec_init()`: - ! `n` must be a single number, not a double vector of length 2. + ! `n` must be a single number, not a double vector. Code (expect_error(vec_init(1L, -1L))) Output diff --git a/tests/testthat/_snaps/subscript-loc.md b/tests/testthat/_snaps/subscript-loc.md index 89badc74f..22b009961 100644 --- a/tests/testthat/_snaps/subscript-loc.md +++ b/tests/testthat/_snaps/subscript-loc.md @@ -318,14 +318,14 @@ Error: ! Must extract element with a single valid subscript. - x Subscript `0` has value 0 but must be a positive location. + x Subscript `0` must be a positive location, not 0. Code (expect_error(vec_as_location2(-1, 2L), class = "vctrs_error_subscript_type")) Output Error: ! Must extract element with a single valid subscript. - x Subscript `-1` has value -1 but must be a positive location. + x Subscript `-1` must be a positive location, not -1. Code # Idem with custom `arg` (expect_error(vec_as_location2(0, 2L, arg = "foo", call = call("my_function")), @@ -334,7 +334,7 @@ Error in `my_function()`: ! Must extract element with a single valid subscript. - x Subscript `foo` has value 0 but must be a positive location. + x Subscript `foo` must be a positive location, not 0. # vec_as_location2() fails with NA @@ -772,7 +772,7 @@ Error in `my_function()`: ! Must extract element with a single valid subscript. - x Subscript `foo` has value -1 but must be a positive location. + x Subscript `foo` must be a positive location, not -1. Code (expect_error(vec_as_location2(0, 2, arg = "foo", call = call("my_function")), class = "vctrs_error_subscript_type")) @@ -780,7 +780,7 @@ Error in `my_function()`: ! Must extract element with a single valid subscript. - x Subscript `foo` has value 0 but must be a positive location. + x Subscript `foo` must be a positive location, not 0. Code (expect_error(vec_as_location2(na_dbl, 2, arg = "foo", call = call( "my_function")), class = "vctrs_error_subscript_type")) @@ -858,7 +858,7 @@ Error: ! Must rename column with a single valid subscript. - x Subscript `foo(bar)` has value -1 but must be a positive location. + x Subscript `foo(bar)` must be a positive location, not -1. Code (expect_error(with_tibble_cols(vec_as_location2(0, 2)), class = "vctrs_error_subscript_type") ) @@ -866,7 +866,7 @@ Error: ! Must rename column with a single valid subscript. - x Subscript `foo(bar)` has value 0 but must be a positive location. + x Subscript `foo(bar)` must be a positive location, not 0. Code (expect_error(with_tibble_cols(vec_as_location2(na_dbl, 2)), class = "vctrs_error_subscript_type") ) From c77d0ea731a2c97217501c4d87d56fab11092195 Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Thu, 6 Oct 2022 15:37:37 +0200 Subject: [PATCH 183/312] State expected type in `NA` location errors --- R/subscript-loc.R | 2 +- tests/testthat/_snaps/subscript-loc.md | 10 +++++----- 2 files changed, 6 insertions(+), 6 deletions(-) diff --git a/R/subscript-loc.R b/R/subscript-loc.R index 292f00982..1dd658dc9 100644 --- a/R/subscript-loc.R +++ b/R/subscript-loc.R @@ -360,7 +360,7 @@ cnd_bullets_location2_need_scalar <- function(cnd, ...) { cnd_bullets_location2_need_present <- function(cnd, ...) { cnd$subscript_arg <- append_arg("Subscript", cnd$subscript_arg) format_error_bullets(c( - x = glue::glue_data(cnd, "{subscript_arg} can't be `NA`.") + x = glue::glue_data(cnd, "{subscript_arg} must be an actual location, not {obj_type_friendly(i)}.") )) } cnd_bullets_location2_need_positive <- function(cnd, ...) { diff --git a/tests/testthat/_snaps/subscript-loc.md b/tests/testthat/_snaps/subscript-loc.md index 22b009961..ce68f10ff 100644 --- a/tests/testthat/_snaps/subscript-loc.md +++ b/tests/testthat/_snaps/subscript-loc.md @@ -345,7 +345,7 @@ Error: ! Must extract element with a single valid subscript. - x Subscript `na_int` can't be `NA`. + x Subscript `na_int` must be an actual location, not an integer `NA`. Code (expect_error(vec_as_location2(na_chr, 1L, names = "foo"), class = "vctrs_error_subscript_type") ) @@ -353,7 +353,7 @@ Error: ! Must extract element with a single valid subscript. - x Subscript `na_chr` can't be `NA`. + x Subscript `na_chr` must be an actual location, not a character `NA`. Code # Idem with custom `arg` (expect_error(vec_as_location2(na_int, 2L, arg = "foo", call = call( @@ -362,7 +362,7 @@ Error in `my_function()`: ! Must extract element with a single valid subscript. - x Subscript `foo` can't be `NA`. + x Subscript `foo` must be an actual location, not an integer `NA`. # num_as_location() optionally forbids negative indices @@ -788,7 +788,7 @@ Error in `my_function()`: ! Must extract element with a single valid subscript. - x Subscript `foo` can't be `NA`. + x Subscript `foo` must be an actual location, not an integer `NA`. Code (expect_error(vec_as_location2(c(1, 2), 2, arg = "foo", call = call( "my_function")), class = "vctrs_error_subscript_type")) @@ -874,7 +874,7 @@ Error: ! Must rename column with a single valid subscript. - x Subscript `foo(bar)` can't be `NA`. + x Subscript `foo(bar)` must be an actual location, not an integer `NA`. Code (expect_error(with_tibble_cols(vec_as_location2(c(1, 2), 2)), class = "vctrs_error_subscript_type") ) From 5166c653ce3ff276bfb7403d7c05d09a5aeea346 Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Thu, 6 Oct 2022 15:38:36 +0200 Subject: [PATCH 184/312] State expected size first --- R/subscript-loc.R | 2 +- tests/testthat/_snaps/subscript-loc.md | 12 ++++++------ 2 files changed, 7 insertions(+), 7 deletions(-) diff --git a/R/subscript-loc.R b/R/subscript-loc.R index 1dd658dc9..3e732bc67 100644 --- a/R/subscript-loc.R +++ b/R/subscript-loc.R @@ -354,7 +354,7 @@ new_error_location2_type <- function(i, cnd_bullets_location2_need_scalar <- function(cnd, ...) { cnd$subscript_arg <- append_arg("Subscript", cnd$subscript_arg) format_error_bullets(c( - x = glue::glue_data(cnd, "{subscript_arg} has size {length(i)} but must be size 1.") + x = glue::glue_data(cnd, "{subscript_arg} must be size 1, not {length(i)}.") )) } cnd_bullets_location2_need_present <- function(cnd, ...) { diff --git a/tests/testthat/_snaps/subscript-loc.md b/tests/testthat/_snaps/subscript-loc.md index ce68f10ff..cfc4620ae 100644 --- a/tests/testthat/_snaps/subscript-loc.md +++ b/tests/testthat/_snaps/subscript-loc.md @@ -262,7 +262,7 @@ Error: ! Must extract element with a single valid subscript. - x Subscript `1:2` has size 2 but must be size 1. + x Subscript `1:2` must be size 1, not 2. Code (expect_error(vec_as_location2(c("foo", "bar"), 2L, c("foo", "bar")), class = "vctrs_error_subscript_type") ) @@ -270,7 +270,7 @@ Error: ! Must extract element with a single valid subscript. - x Subscript `c("foo", "bar")` has size 2 but must be size 1. + x Subscript `c("foo", "bar")` must be size 1, not 2. Code # Idem with custom `arg` (expect_error(vec_as_location2(1:2, 2L, arg = "foo", call = call("my_function")), @@ -279,7 +279,7 @@ Error in `my_function()`: ! Must extract element with a single valid subscript. - x Subscript `foo` has size 2 but must be size 1. + x Subscript `foo` must be size 1, not 2. Code (expect_error(vec_as_location2(mtcars, 10L, arg = "foo", call = call( "my_function")), class = "vctrs_error_subscript_type")) @@ -308,7 +308,7 @@ Error in `my_function()`: ! Must extract element with a single valid subscript. - x Subscript `foo` has size 2 but must be size 1. + x Subscript `foo` must be size 1, not 2. # vec_as_location2() requires positive integers @@ -796,7 +796,7 @@ Error in `my_function()`: ! Must extract element with a single valid subscript. - x Subscript `foo` has size 2 but must be size 1. + x Subscript `foo` must be size 1, not 2. Code (expect_error(vec_as_location(c(TRUE, FALSE), 3, arg = "foo", call = call( "my_function")), class = "vctrs_error_subscript_size")) @@ -882,7 +882,7 @@ Error: ! Must rename column with a single valid subscript. - x Subscript `foo(bar)` has size 2 but must be size 1. + x Subscript `foo(bar)` must be size 1, not 2. Code (expect_error(with_tibble_cols(vec_as_location(c(TRUE, FALSE), 3)), class = "vctrs_error_subscript_size") ) From 51cac7b600f4eff0e72b735e81f7448ec9e5fc80 Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Thu, 20 Oct 2022 13:42:13 +0200 Subject: [PATCH 185/312] State expected type first in subscript type errors --- R/subscript.R | 39 ++++++++++--- tests/testthat/_snaps/error-call.md | 6 +- tests/testthat/_snaps/slice-chop.md | 6 +- tests/testthat/_snaps/slice.md | 3 +- tests/testthat/_snaps/subscript-loc.md | 81 +++++--------------------- tests/testthat/_snaps/subscript.md | 42 +++++-------- 6 files changed, 65 insertions(+), 112 deletions(-) diff --git a/R/subscript.R b/R/subscript.R index be9df5b36..7b87c0ba0 100644 --- a/R/subscript.R +++ b/R/subscript.R @@ -185,13 +185,12 @@ cnd_header.vctrs_error_subscript_type <- function(cnd) { } #' @export cnd_body.vctrs_error_subscript_type <- function(cnd) { - arg <- append_arg("Subscript", cnd$subscript_arg) - type <- obj_type(cnd$i) - expected_types <- collapse_subscript_type(cnd) + arg <- cnd_subscript_arg(cnd) + type <- obj_type_friendly(cnd$i) + expected_types <- cnd_subscript_expected_types(cnd) format_error_bullets(c( - x = glue::glue("{arg} has the wrong type `{type}`."), - i = glue::glue("It must be {expected_types}.") + x = cli::format_inline("{arg} must be {.or {expected_types}}, not {type}.") )) } new_cnd_bullets_subscript_lossy_cast <- function(lossy_err) { @@ -201,9 +200,7 @@ new_cnd_bullets_subscript_lossy_cast <- function(lossy_err) { } collapse_subscript_type <- function(cnd) { - types <- c("logical", "numeric", "character") - allowed <- cnd[types] != "error" - types <- types[allowed] + types <- cnd_subscript_expected_types(cnd) if (length(types) == 2) { last <- " or " @@ -213,6 +210,11 @@ collapse_subscript_type <- function(cnd) { glue::glue_collapse(types, sep = ", ", last = last) } +cnd_subscript_expected_types <- function(cnd) { + types <- c("logical", "numeric", "character") + allowed <- cnd[types] != "error" + types[allowed] +} new_error_subscript_size <- function(i, ..., @@ -349,6 +351,27 @@ cnd_subscript_action <- function(cnd, assign_to = TRUE) { } } +cnd_subscript_arg <- function(cnd, ...) { + format_subscript_arg(cnd[["subscript_arg"]], ...) +} +format_subscript_arg <- function(arg, capitalise = TRUE) { + if (is_subscript_arg(arg)) { + if (!is_string(arg)) { + arg <- as_label(arg) + } + cli::format_inline("{.arg {arg}}") + } else { + if (capitalise) { + "Subscript" + } else { + "subscript" + } + } +} +is_subscript_arg <- function(x) { + !is_null(x) && !is_string(x, "") +} + cnd_subscript_type <- function(cnd) { type <- cnd$subscript_type diff --git a/tests/testthat/_snaps/error-call.md b/tests/testthat/_snaps/error-call.md index 52b1f1a8a..eb9c1af3b 100644 --- a/tests/testthat/_snaps/error-call.md +++ b/tests/testthat/_snaps/error-call.md @@ -239,8 +239,7 @@ Error in `my_function()`: ! Must subset elements with a valid subscript vector. - x Subscript `my_arg` has the wrong type `list`. - i It must be logical, numeric, or character. + x `my_arg` must be logical, numeric, or character, not an empty list. --- @@ -328,8 +327,7 @@ Error in `vec_slice()`: ! Must subset elements with a valid subscript vector. - x Subscript `i` has the wrong type `environment`. - i It must be logical, numeric, or character. + x `i` must be logical, numeric, or character, not an environment. # list_sizes() reports error context diff --git a/tests/testthat/_snaps/slice-chop.md b/tests/testthat/_snaps/slice-chop.md index 5d929a14f..97d2cd8d1 100644 --- a/tests/testthat/_snaps/slice-chop.md +++ b/tests/testthat/_snaps/slice-chop.md @@ -299,8 +299,7 @@ Error: ! Must subset elements with a valid subscript vector. - x Subscript has the wrong type `character`. - i It must be numeric. + x Subscript must be numeric, not the string "x". Code (expect_error(list_unchop(list(1), indices = list(foobar(1L))), class = "vctrs_error_subscript_type") ) @@ -308,8 +307,7 @@ Error: ! Must subset elements with a valid subscript vector. - x Subscript has the wrong type `vctrs_foobar`. - i It must be numeric. + x Subscript must be numeric, not a object. # can ignore names in `list_unchop()` by providing a `zap()` name-spec (#232) diff --git a/tests/testthat/_snaps/slice.md b/tests/testthat/_snaps/slice.md index 94420902c..c22c927b3 100644 --- a/tests/testthat/_snaps/slice.md +++ b/tests/testthat/_snaps/slice.md @@ -6,8 +6,7 @@ Error in `vec_slice()`: ! Must subset elements with a valid subscript vector. - x Subscript `i` has the wrong type `date`. - i It must be logical, numeric, or character. + x `i` must be logical, numeric, or character, not a object. Code (expect_error(vec_slice(1:3, matrix(TRUE, nrow = 1)), class = "vctrs_error_subscript_type") ) diff --git a/tests/testthat/_snaps/subscript-loc.md b/tests/testthat/_snaps/subscript-loc.md index cfc4620ae..c4966db07 100644 --- a/tests/testthat/_snaps/subscript-loc.md +++ b/tests/testthat/_snaps/subscript-loc.md @@ -7,8 +7,7 @@ Error: ! Must extract element with a single valid subscript. - x Subscript `TRUE` has the wrong type `logical`. - i It must be numeric or character. + x `TRUE` must be numeric or character, not `TRUE`. Code (expect_error(vec_as_location2(mtcars, 10L), class = "vctrs_error_subscript_type") ) @@ -16,20 +15,7 @@ Error: ! Must extract element with a single valid subscript. - x Subscript `mtcars` has the wrong type `data.frame< - mpg : double - cyl : double - disp: double - hp : double - drat: double - wt : double - qsec: double - vs : double - am : double - gear: double - carb: double - >`. - i It must be numeric or character. + x `mtcars` must be numeric or character, not a object. Code (expect_error(vec_as_location2(env(), 10L), class = "vctrs_error_subscript_type") ) @@ -37,8 +23,7 @@ Error: ! Must extract element with a single valid subscript. - x Subscript `env()` has the wrong type `environment`. - i It must be numeric or character. + x `env()` must be numeric or character, not an environment. Code (expect_error(vec_as_location2(foobar(), 10L), class = "vctrs_error_subscript_type") ) @@ -46,8 +31,7 @@ Error: ! Must extract element with a single valid subscript. - x Subscript `foobar()` has the wrong type `vctrs_foobar`. - i It must be numeric or character. + x `foobar()` must be numeric or character, not a object. Code (expect_error(vec_as_location2(2.5, 10L), class = "vctrs_error_subscript_type")) Output @@ -78,8 +62,7 @@ Error in `my_function()`: ! Must extract element with a single valid subscript. - x Subscript `foo` has the wrong type `vctrs_foobar`. - i It must be numeric or character. + x `foo` must be numeric or character, not a object. Code (expect_error(vec_as_location2(2.5, 3L, arg = "foo", call = call("my_function")), class = "vctrs_error_subscript_type")) @@ -95,8 +78,7 @@ Error: ! Must remove row with a single valid subscript. - x Subscript `foo(bar)` has the wrong type `logical`. - i It must be numeric or character. + x `foo(bar)` must be numeric or character, not `TRUE`. # vec_as_location() requires integer, character, or logical inputs @@ -107,20 +89,7 @@ Error: ! Must subset elements with a valid subscript vector. - x Subscript `mtcars` has the wrong type `data.frame< - mpg : double - cyl : double - disp: double - hp : double - drat: double - wt : double - qsec: double - vs : double - am : double - gear: double - carb: double - >`. - i It must be logical, numeric, or character. + x `mtcars` must be logical, numeric, or character, not a object. Code (expect_error(vec_as_location(env(), 10L), class = "vctrs_error_subscript_type") ) @@ -128,8 +97,7 @@ Error: ! Must subset elements with a valid subscript vector. - x Subscript `env()` has the wrong type `environment`. - i It must be logical, numeric, or character. + x `env()` must be logical, numeric, or character, not an environment. Code (expect_error(vec_as_location(foobar(), 10L), class = "vctrs_error_subscript_type") ) @@ -137,8 +105,7 @@ Error: ! Must subset elements with a valid subscript vector. - x Subscript `foobar()` has the wrong type `vctrs_foobar`. - i It must be logical, numeric, or character. + x `foobar()` must be logical, numeric, or character, not a object. Code (expect_error(vec_as_location(2.5, 10L), class = "vctrs_error_subscript_type")) Output @@ -153,8 +120,7 @@ Error: ! Must subset elements with a valid subscript vector. - x Subscript `list()` has the wrong type `list`. - i It must be logical, numeric, or character. + x `list()` must be logical, numeric, or character, not an empty list. Code (expect_error(vec_as_location(function() NULL, 10L), class = "vctrs_error_subscript_type") ) @@ -162,8 +128,7 @@ Error: ! Must subset elements with a valid subscript vector. - x Subscript `function() NULL` has the wrong type `function`. - i It must be logical, numeric, or character. + x `function() NULL` must be logical, numeric, or character, not a function. Code (expect_error(vec_as_location(Sys.Date(), 3L), class = "vctrs_error_subscript_type") ) @@ -171,8 +136,7 @@ Error: ! Must subset elements with a valid subscript vector. - x Subscript `Sys.Date()` has the wrong type `date`. - i It must be logical, numeric, or character. + x `Sys.Date()` must be logical, numeric, or character, not a object. Code # Idem with custom `arg` (expect_error(vec_as_location(env(), 10L, arg = "foo", call = call( @@ -181,8 +145,7 @@ Error in `my_function()`: ! Must subset elements with a valid subscript vector. - x Subscript `foo` has the wrong type `environment`. - i It must be logical, numeric, or character. + x `foo` must be logical, numeric, or character, not an environment. Code (expect_error(vec_as_location(foobar(), 10L, arg = "foo", call = call( "my_function")), class = "vctrs_error_subscript_type")) @@ -190,8 +153,7 @@ Error in `my_function()`: ! Must subset elements with a valid subscript vector. - x Subscript `foo` has the wrong type `vctrs_foobar`. - i It must be logical, numeric, or character. + x `foo` must be logical, numeric, or character, not a object. Code (expect_error(vec_as_location(2.5, 3L, arg = "foo", call = call("my_function")), class = "vctrs_error_subscript_type")) @@ -287,20 +249,7 @@ Error in `my_function()`: ! Must extract element with a single valid subscript. - x Subscript `foo` has the wrong type `data.frame< - mpg : double - cyl : double - disp: double - hp : double - drat: double - wt : double - qsec: double - vs : double - am : double - gear: double - carb: double - >`. - i It must be numeric or character. + x `foo` must be numeric or character, not a object. Code (expect_error(vec_as_location2(1:2, 2L, arg = "foo", call = call("my_function")), class = "vctrs_error_subscript_type")) diff --git a/tests/testthat/_snaps/subscript.md b/tests/testthat/_snaps/subscript.md index f48dd13cb..1e0a13fa4 100644 --- a/tests/testthat/_snaps/subscript.md +++ b/tests/testthat/_snaps/subscript.md @@ -7,8 +7,7 @@ Error: ! Must rename columns with a valid subscript vector. - x Subscript `foo(bar)` has the wrong type `environment`. - i It must be logical, numeric, or character. + x `foo(bar)` must be logical, numeric, or character, not an environment. --- @@ -19,8 +18,7 @@ Error: ! Must extract tables with a valid subscript vector. - x Subscript `foo(bar)` has the wrong type `environment`. - i It must be logical, numeric, or character. + x `foo(bar)` must be logical, numeric, or character, not an environment. # vec_as_subscript() checks dimensionality @@ -56,8 +54,7 @@ Condition Error: ! Must subset elements with a valid subscript vector. - x Subscript has the wrong type `integer`. - i It must be character. + x Subscript must be character, not the number 1. --- @@ -66,8 +63,7 @@ Condition Error: ! Must subset elements with a valid subscript vector. - x Subscript has the wrong type `character`. - i It must be numeric. + x Subscript must be numeric, not the string "foo". --- @@ -76,8 +72,7 @@ Condition Error: ! Must subset elements with a valid subscript vector. - x Subscript has the wrong type `logical`. - i It must be numeric or character. + x Subscript must be numeric or character, not `TRUE`. --- @@ -86,8 +81,7 @@ Condition Error: ! Must subset elements with a valid subscript vector. - x Subscript has the wrong type `character`. - i It must be logical or numeric. + x Subscript must be logical or numeric, not the string "foo". --- @@ -96,8 +90,7 @@ Condition Error: ! Must subset elements with a valid subscript vector. - x Subscript has the wrong type `NULL`. - i It must be logical or character. + x Subscript must be logical or character, not `NULL`. --- @@ -106,8 +99,7 @@ Condition Error: ! Must subset elements with a valid subscript vector. - x Subscript has the wrong type `symbol`. - i It must be logical or numeric. + x Subscript must be logical or numeric, not a symbol. # vec_as_subscript2() forbids subscript types @@ -116,8 +108,7 @@ Condition Error: ! Must extract element with a single valid subscript. - x Subscript has the wrong type `integer`. - i It must be character. + x Subscript must be character, not the number 1. --- @@ -126,8 +117,7 @@ Condition Error: ! Must extract element with a single valid subscript. - x Subscript has the wrong type `character`. - i It must be numeric. + x Subscript must be numeric, not the string "foo". --- @@ -136,8 +126,7 @@ Condition Error: ! Must extract element with a single valid subscript. - x Subscript has the wrong type `logical`. - i It must be numeric or character. + x Subscript must be numeric or character, not `TRUE`. # vec_as_subscript2() retains the call when throwing vec_as_subscript() errors (#1605) @@ -146,8 +135,7 @@ Condition Error in `foo()`: ! Must extract element with a single valid subscript. - x Subscript has the wrong type `integer`. - i It must be character. + x Subscript must be character, not the number 1. --- @@ -165,8 +153,7 @@ Condition Error in `foo()`: ! Must extract element with a single valid subscript. - x Subscript has the wrong type `logical`. - i It must be numeric or character. + x Subscript must be numeric or character, not `TRUE`. # `logical = 'cast'` is deprecated @@ -183,8 +170,7 @@ Condition Error: ! Must extract element with a single valid subscript. - x Subscript has the wrong type `logical`. - i It must be numeric or character. + x Subscript must be numeric or character, not `TRUE`. # lossy cast errors for scalar subscripts work (#1606) From 28a925206187d0bbebd1b0aaad20106120913b96 Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Thu, 20 Oct 2022 15:32:21 +0200 Subject: [PATCH 186/312] State expected and actual sizes in logical subscript errors --- R/subscript-loc.R | 5 ++--- tests/testthat/_snaps/slice-assign.md | 6 ++---- tests/testthat/_snaps/subscript-loc.md | 9 +++------ 3 files changed, 7 insertions(+), 13 deletions(-) diff --git a/R/subscript-loc.R b/R/subscript-loc.R index 3e732bc67..0da72587a 100644 --- a/R/subscript-loc.R +++ b/R/subscript-loc.R @@ -472,11 +472,10 @@ stop_indicator_size <- function(i, n, ..., call = caller_env()) { )) } cnd_body_vctrs_error_indicator_size <- function(cnd, ...) { - cnd$subscript_arg <- append_arg("subscript", cnd$subscript_arg) + cnd$subscript_arg <- append_arg("Logical subscript", cnd$subscript_arg) glue_data_bullets( cnd, - i = "Logical subscripts must match the size of the indexed input.", - x = "Input has size {n} but {subscript_arg} has size {vec_size(i)}." + x = "{subscript_arg} must be size 1 or {n}, not {vec_size(i)}." ) } diff --git a/tests/testthat/_snaps/slice-assign.md b/tests/testthat/_snaps/slice-assign.md index 5c9997a6d..5d1d2b540 100644 --- a/tests/testthat/_snaps/slice-assign.md +++ b/tests/testthat/_snaps/slice-assign.md @@ -17,8 +17,7 @@ Error: ! Must assign to elements with a valid subscript vector. - i Logical subscripts must match the size of the indexed input. - x Input has size 2 but subscript has size 3. + x Logical subscript must be size 1 or 2, not 3. --- @@ -29,8 +28,7 @@ Error: ! Must assign to elements with a valid subscript vector. - i Logical subscripts must match the size of the indexed input. - x Input has size 32 but subscript has size 2. + x Logical subscript must be size 1 or 32, not 2. # must assign existing elements diff --git a/tests/testthat/_snaps/subscript-loc.md b/tests/testthat/_snaps/subscript-loc.md index c4966db07..9ab8b1aed 100644 --- a/tests/testthat/_snaps/subscript-loc.md +++ b/tests/testthat/_snaps/subscript-loc.md @@ -396,8 +396,7 @@ Error: ! Must subset elements with a valid subscript vector. - i Logical subscripts must match the size of the indexed input. - x Input has size 3 but subscript `c(TRUE, FALSE)` has size 2. + x Logical subscript `c(TRUE, FALSE)` must be size 1 or 3, not 2. # character subscripts require named vectors @@ -753,8 +752,7 @@ Error in `my_function()`: ! Must subset elements with a valid subscript vector. - i Logical subscripts must match the size of the indexed input. - x Input has size 3 but subscript `foo` has size 2. + x Logical subscript `foo` must be size 1 or 3, not 2. Code (expect_error(vec_as_location(c(-1, NA), 3, arg = "foo", call = call( "my_function")), class = "vctrs_error_subscript_type")) @@ -839,8 +837,7 @@ Error: ! Must rename columns with a valid subscript vector. - i Logical subscripts must match the size of the indexed input. - x Input has size 3 but subscript `foo(bar)` has size 2. + x Logical subscript `foo(bar)` must be size 1 or 3, not 2. Code (expect_error(with_tibble_cols(vec_as_location(c(-1, NA), 3)), class = "vctrs_error_subscript_type") ) From 5eb18ec9dea05f3fbdbdb9f651780720540e5526 Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Thu, 20 Oct 2022 16:29:08 +0200 Subject: [PATCH 187/312] Refer to "location" instead of "actual location" --- R/subscript-loc.R | 2 +- tests/testthat/_snaps/subscript-loc.md | 10 +++++----- 2 files changed, 6 insertions(+), 6 deletions(-) diff --git a/R/subscript-loc.R b/R/subscript-loc.R index 0da72587a..3fabb24b3 100644 --- a/R/subscript-loc.R +++ b/R/subscript-loc.R @@ -360,7 +360,7 @@ cnd_bullets_location2_need_scalar <- function(cnd, ...) { cnd_bullets_location2_need_present <- function(cnd, ...) { cnd$subscript_arg <- append_arg("Subscript", cnd$subscript_arg) format_error_bullets(c( - x = glue::glue_data(cnd, "{subscript_arg} must be an actual location, not {obj_type_friendly(i)}.") + x = glue::glue_data(cnd, "{subscript_arg} must be a location, not {obj_type_friendly(i)}.") )) } cnd_bullets_location2_need_positive <- function(cnd, ...) { diff --git a/tests/testthat/_snaps/subscript-loc.md b/tests/testthat/_snaps/subscript-loc.md index 9ab8b1aed..641f0af34 100644 --- a/tests/testthat/_snaps/subscript-loc.md +++ b/tests/testthat/_snaps/subscript-loc.md @@ -294,7 +294,7 @@ Error: ! Must extract element with a single valid subscript. - x Subscript `na_int` must be an actual location, not an integer `NA`. + x Subscript `na_int` must be a location, not an integer `NA`. Code (expect_error(vec_as_location2(na_chr, 1L, names = "foo"), class = "vctrs_error_subscript_type") ) @@ -302,7 +302,7 @@ Error: ! Must extract element with a single valid subscript. - x Subscript `na_chr` must be an actual location, not a character `NA`. + x Subscript `na_chr` must be a location, not a character `NA`. Code # Idem with custom `arg` (expect_error(vec_as_location2(na_int, 2L, arg = "foo", call = call( @@ -311,7 +311,7 @@ Error in `my_function()`: ! Must extract element with a single valid subscript. - x Subscript `foo` must be an actual location, not an integer `NA`. + x Subscript `foo` must be a location, not an integer `NA`. # num_as_location() optionally forbids negative indices @@ -736,7 +736,7 @@ Error in `my_function()`: ! Must extract element with a single valid subscript. - x Subscript `foo` must be an actual location, not an integer `NA`. + x Subscript `foo` must be a location, not an integer `NA`. Code (expect_error(vec_as_location2(c(1, 2), 2, arg = "foo", call = call( "my_function")), class = "vctrs_error_subscript_type")) @@ -821,7 +821,7 @@ Error: ! Must rename column with a single valid subscript. - x Subscript `foo(bar)` must be an actual location, not an integer `NA`. + x Subscript `foo(bar)` must be a location, not an integer `NA`. Code (expect_error(with_tibble_cols(vec_as_location2(c(1, 2), 2)), class = "vctrs_error_subscript_type") ) From 48c418ea31293c208ee2aebf11818c7a1edffd6f Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Thu, 20 Oct 2022 16:58:14 +0200 Subject: [PATCH 188/312] Use CRAN rlang in snapshots --- tests/testthat/_snaps/conditions.md | 2 +- tests/testthat/_snaps/size.md | 10 +++++----- tests/testthat/_snaps/slice.md | 2 +- 3 files changed, 7 insertions(+), 7 deletions(-) diff --git a/tests/testthat/_snaps/conditions.md b/tests/testthat/_snaps/conditions.md index e2b642403..921b36990 100644 --- a/tests/testthat/_snaps/conditions.md +++ b/tests/testthat/_snaps/conditions.md @@ -12,7 +12,7 @@ Output Error in `stop_incompatible_type()`: - ! `action` must be a character vector, not the number 1. + ! `action` must be a character vector, not a number. # can override arg in OOB conditions diff --git a/tests/testthat/_snaps/size.md b/tests/testthat/_snaps/size.md index 4040948ce..38d9665e3 100644 --- a/tests/testthat/_snaps/size.md +++ b/tests/testthat/_snaps/size.md @@ -11,7 +11,7 @@ Output Error in `vec_as_short_length()`: - ! `my_arg` must be a single number, not an integer vector. + ! `my_arg` must be a single number, not an integer vector of length 2. Code (expect_error(my_function(1.5))) Output @@ -35,13 +35,13 @@ Output Error in `vec_as_short_length()`: - ! `my_arg` must be a single number, not the string "foo". + ! `my_arg` must be a single number, not a string. Code (expect_error(my_function(foobar(1:2)))) Output Error in `vec_as_short_length()`: - ! `my_arg` must be a single number, not `NULL`. + ! `my_arg` must be a single number, not NULL. Code (expect_error(my_function(.Machine$double.xmax))) Output @@ -65,13 +65,13 @@ Output Error in `vec_size_common()`: - ! `.size` must be a single number, not the string "foo". + ! `.size` must be a single number, not a string. Code (expect_error(vec_size_common(.size = 1:2))) Output Error in `vec_size_common()`: - ! `.size` must be a single number, not an integer vector. + ! `.size` must be a single number, not an integer vector of length 2. # vec_size_common() mentions `arg` in errors diff --git a/tests/testthat/_snaps/slice.md b/tests/testthat/_snaps/slice.md index c22c927b3..62fed97f0 100644 --- a/tests/testthat/_snaps/slice.md +++ b/tests/testthat/_snaps/slice.md @@ -133,7 +133,7 @@ Output Error in `vec_init()`: - ! `n` must be a single number, not a double vector. + ! `n` must be a single number, not a double vector of length 2. Code (expect_error(vec_init(1L, -1L))) Output From d1afb473840c9c3b2a6ae88577ae2fdea0e6f73d Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Fri, 21 Oct 2022 18:04:13 +0200 Subject: [PATCH 189/312] Use "can't" phrasing in headers of subscript errors (#1736) --- R/subscript.R | 14 ++- tests/testthat/_snaps/error-call.md | 10 +- tests/testthat/_snaps/slice-assign.md | 8 +- tests/testthat/_snaps/slice-chop.md | 8 +- tests/testthat/_snaps/slice.md | 10 +- tests/testthat/_snaps/subscript-loc.md | 154 ++++++++++++------------- tests/testthat/_snaps/subscript.md | 38 +++--- 7 files changed, 125 insertions(+), 117 deletions(-) diff --git a/R/subscript.R b/R/subscript.R index 7b87c0ba0..e524a2f58 100644 --- a/R/subscript.R +++ b/R/subscript.R @@ -175,12 +175,20 @@ new_error_subscript_type <- function(i, #' @export cnd_header.vctrs_error_subscript_type <- function(cnd) { - action <- cnd_subscript_action(cnd) + arg <- cnd[["subscript_arg"]] + if (is_subscript_arg(arg)) { + with <- glue::glue(" with {format_subscript_arg(arg)}") + } else { + with <- "" + } + + action <- cnd_subscript_action(cnd, assign_to = FALSE) elt <- cnd_subscript_element(cnd) + if (cnd_subscript_scalar(cnd)) { - glue::glue("Must {action} {elt[[1]]} with a single valid subscript.") + glue::glue("Can't {action} {elt[[1]]}{with}.") } else { - glue::glue("Must {action} {elt[[2]]} with a valid subscript vector.") + glue::glue("Can't {action} {elt[[2]]}{with}.") } } #' @export diff --git a/tests/testthat/_snaps/error-call.md b/tests/testthat/_snaps/error-call.md index eb9c1af3b..9fa9ddc08 100644 --- a/tests/testthat/_snaps/error-call.md +++ b/tests/testthat/_snaps/error-call.md @@ -218,7 +218,7 @@ Output Error in `my_function()`: - ! Must subset elements with a valid subscript vector. + ! Can't subset elements with `my_arg`. x Can't convert from `my_arg` to due to loss of precision. --- @@ -228,7 +228,7 @@ Output Error in `my_function()`: - ! Must subset elements with a valid subscript vector. + ! Can't subset elements. x Can't convert from to due to loss of precision. --- @@ -238,7 +238,7 @@ Output Error in `my_function()`: - ! Must subset elements with a valid subscript vector. + ! Can't subset elements with `my_arg`. x `my_arg` must be logical, numeric, or character, not an empty list. --- @@ -258,7 +258,7 @@ Output Error in `my_function()`: - ! Must subset elements with a valid subscript vector. + ! Can't subset elements. x Subscript can't contain missing values. x It has a missing value at location 1. @@ -326,7 +326,7 @@ Output Error in `vec_slice()`: - ! Must subset elements with a valid subscript vector. + ! Can't subset elements with `i`. x `i` must be logical, numeric, or character, not an environment. # list_sizes() reports error context diff --git a/tests/testthat/_snaps/slice-assign.md b/tests/testthat/_snaps/slice-assign.md index 5d1d2b540..93eebb30e 100644 --- a/tests/testthat/_snaps/slice-assign.md +++ b/tests/testthat/_snaps/slice-assign.md @@ -16,7 +16,7 @@ Output Error: - ! Must assign to elements with a valid subscript vector. + ! Can't assign elements. x Logical subscript must be size 1 or 2, not 3. --- @@ -27,7 +27,7 @@ Output Error: - ! Must assign to elements with a valid subscript vector. + ! Can't assign elements. x Logical subscript must be size 1 or 32, not 2. # must assign existing elements @@ -72,7 +72,7 @@ Output Error: - ! Must assign to elements with a valid subscript vector. + ! Can't assign elements. x Negative and positive locations can't be mixed. i Subscript has a positive value at location 2. Code @@ -81,7 +81,7 @@ Output Error: - ! Must assign to elements with a valid subscript vector. + ! Can't assign elements. x Negative locations can't have missing values. i Subscript has a missing value at location 2. diff --git a/tests/testthat/_snaps/slice-chop.md b/tests/testthat/_snaps/slice-chop.md index 97d2cd8d1..f79e057c2 100644 --- a/tests/testthat/_snaps/slice-chop.md +++ b/tests/testthat/_snaps/slice-chop.md @@ -158,7 +158,7 @@ Output Error: - ! Must subset elements with a valid subscript vector. + ! Can't subset elements. x Subscript can't contain `0` values. i It has a `0` value at location 1. Code @@ -167,7 +167,7 @@ Output Error: - ! Must subset elements with a valid subscript vector. + ! Can't subset elements. x Subscript can't contain negative locations. # list_unchop() fails with complex foreign S3 classes @@ -298,7 +298,7 @@ Output Error: - ! Must subset elements with a valid subscript vector. + ! Can't subset elements. x Subscript must be numeric, not the string "x". Code (expect_error(list_unchop(list(1), indices = list(foobar(1L))), class = "vctrs_error_subscript_type") @@ -306,7 +306,7 @@ Output Error: - ! Must subset elements with a valid subscript vector. + ! Can't subset elements. x Subscript must be numeric, not a object. # can ignore names in `list_unchop()` by providing a `zap()` name-spec (#232) diff --git a/tests/testthat/_snaps/slice.md b/tests/testthat/_snaps/slice.md index 62fed97f0..ef493a9a2 100644 --- a/tests/testthat/_snaps/slice.md +++ b/tests/testthat/_snaps/slice.md @@ -5,7 +5,7 @@ Output Error in `vec_slice()`: - ! Must subset elements with a valid subscript vector. + ! Can't subset elements with `i`. x `i` must be logical, numeric, or character, not a object. Code (expect_error(vec_slice(1:3, matrix(TRUE, nrow = 1)), class = "vctrs_error_subscript_type") @@ -13,7 +13,7 @@ Output Error in `vec_slice()`: - ! Must subset elements with a valid subscript vector. + ! Can't subset elements with `i`. x Subscript `i` must be a simple vector, not a matrix. # can't index beyond the end of a vector @@ -42,7 +42,7 @@ Output Error: - ! Must subset elements with a valid subscript vector. + ! Can't subset elements with `2^31`. x Can't convert from `2^31` to due to loss of precision. # Unnamed vector with character subscript is caught @@ -59,7 +59,7 @@ vec_slice(1:3, -c(1L, NA)) Condition Error in `vec_slice()`: - ! Must subset elements with a valid subscript vector. + ! Can't subset elements with `i`. x Negative locations can't have missing values. i Subscript `i` has a missing value at location 2. @@ -69,7 +69,7 @@ vec_slice(1:3, c(-1L, 1L)) Condition Error in `vec_slice()`: - ! Must subset elements with a valid subscript vector. + ! Can't subset elements with `i`. x Negative and positive locations can't be mixed. i Subscript `i` has a positive value at location 2. diff --git a/tests/testthat/_snaps/subscript-loc.md b/tests/testthat/_snaps/subscript-loc.md index 641f0af34..b60ade633 100644 --- a/tests/testthat/_snaps/subscript-loc.md +++ b/tests/testthat/_snaps/subscript-loc.md @@ -6,7 +6,7 @@ Output Error: - ! Must extract element with a single valid subscript. + ! Can't extract element with `TRUE`. x `TRUE` must be numeric or character, not `TRUE`. Code (expect_error(vec_as_location2(mtcars, 10L), class = "vctrs_error_subscript_type") @@ -14,7 +14,7 @@ Output Error: - ! Must extract element with a single valid subscript. + ! Can't extract element with `mtcars`. x `mtcars` must be numeric or character, not a object. Code (expect_error(vec_as_location2(env(), 10L), class = "vctrs_error_subscript_type") @@ -22,7 +22,7 @@ Output Error: - ! Must extract element with a single valid subscript. + ! Can't extract element with `env()`. x `env()` must be numeric or character, not an environment. Code (expect_error(vec_as_location2(foobar(), 10L), class = "vctrs_error_subscript_type") @@ -30,21 +30,21 @@ Output Error: - ! Must extract element with a single valid subscript. + ! Can't extract element with `foobar()`. x `foobar()` must be numeric or character, not a object. Code (expect_error(vec_as_location2(2.5, 10L), class = "vctrs_error_subscript_type")) Output Error: - ! Must extract element with a single valid subscript. + ! Can't extract element with `2.5`. x Can't convert from `2.5` to due to loss of precision. Code (expect_error(vec_as_location2(Inf, 10L), class = "vctrs_error_subscript_type")) Output Error: - ! Must extract element with a single valid subscript. + ! Can't extract element with `Inf`. x Can't convert from `Inf` to due to loss of precision. Code (expect_error(vec_as_location2(-Inf, 10L), class = "vctrs_error_subscript_type") @@ -52,7 +52,7 @@ Output Error: - ! Must extract element with a single valid subscript. + ! Can't extract element with `-Inf`. x Can't convert from `-Inf` to due to loss of precision. Code # Idem with custom `arg` @@ -61,7 +61,7 @@ Output Error in `my_function()`: - ! Must extract element with a single valid subscript. + ! Can't extract element with `foo`. x `foo` must be numeric or character, not a object. Code (expect_error(vec_as_location2(2.5, 3L, arg = "foo", call = call("my_function")), @@ -69,7 +69,7 @@ Output Error in `my_function()`: - ! Must extract element with a single valid subscript. + ! Can't extract element with `foo`. x Can't convert from `foo` to due to loss of precision. Code (expect_error(with_tibble_rows(vec_as_location2(TRUE)), class = "vctrs_error_subscript_type") @@ -77,7 +77,7 @@ Output Error: - ! Must remove row with a single valid subscript. + ! Can't remove row with `foo(bar)`. x `foo(bar)` must be numeric or character, not `TRUE`. # vec_as_location() requires integer, character, or logical inputs @@ -88,7 +88,7 @@ Output Error: - ! Must subset elements with a valid subscript vector. + ! Can't subset elements with `mtcars`. x `mtcars` must be logical, numeric, or character, not a object. Code (expect_error(vec_as_location(env(), 10L), class = "vctrs_error_subscript_type") @@ -96,7 +96,7 @@ Output Error: - ! Must subset elements with a valid subscript vector. + ! Can't subset elements with `env()`. x `env()` must be logical, numeric, or character, not an environment. Code (expect_error(vec_as_location(foobar(), 10L), class = "vctrs_error_subscript_type") @@ -104,14 +104,14 @@ Output Error: - ! Must subset elements with a valid subscript vector. + ! Can't subset elements with `foobar()`. x `foobar()` must be logical, numeric, or character, not a object. Code (expect_error(vec_as_location(2.5, 10L), class = "vctrs_error_subscript_type")) Output Error: - ! Must subset elements with a valid subscript vector. + ! Can't subset elements with `2.5`. x Can't convert from `2.5` to due to loss of precision. Code (expect_error(vec_as_location(list(), 10L), class = "vctrs_error_subscript_type") @@ -119,7 +119,7 @@ Output Error: - ! Must subset elements with a valid subscript vector. + ! Can't subset elements with `list()`. x `list()` must be logical, numeric, or character, not an empty list. Code (expect_error(vec_as_location(function() NULL, 10L), class = "vctrs_error_subscript_type") @@ -127,7 +127,7 @@ Output Error: - ! Must subset elements with a valid subscript vector. + ! Can't subset elements with `function() NULL`. x `function() NULL` must be logical, numeric, or character, not a function. Code (expect_error(vec_as_location(Sys.Date(), 3L), class = "vctrs_error_subscript_type") @@ -135,7 +135,7 @@ Output Error: - ! Must subset elements with a valid subscript vector. + ! Can't subset elements with `Sys.Date()`. x `Sys.Date()` must be logical, numeric, or character, not a object. Code # Idem with custom `arg` @@ -144,7 +144,7 @@ Output Error in `my_function()`: - ! Must subset elements with a valid subscript vector. + ! Can't subset elements with `foo`. x `foo` must be logical, numeric, or character, not an environment. Code (expect_error(vec_as_location(foobar(), 10L, arg = "foo", call = call( @@ -152,7 +152,7 @@ Output Error in `my_function()`: - ! Must subset elements with a valid subscript vector. + ! Can't subset elements with `foo`. x `foo` must be logical, numeric, or character, not a object. Code (expect_error(vec_as_location(2.5, 3L, arg = "foo", call = call("my_function")), @@ -160,7 +160,7 @@ Output Error in `my_function()`: - ! Must subset elements with a valid subscript vector. + ! Can't subset elements with `foo`. x Can't convert from `foo` to due to loss of precision. # vec_as_location() and variants check for OOB elements (#1605) @@ -223,7 +223,7 @@ Output Error: - ! Must extract element with a single valid subscript. + ! Can't extract element with `1:2`. x Subscript `1:2` must be size 1, not 2. Code (expect_error(vec_as_location2(c("foo", "bar"), 2L, c("foo", "bar")), class = "vctrs_error_subscript_type") @@ -231,7 +231,7 @@ Output Error: - ! Must extract element with a single valid subscript. + ! Can't extract element with `c("foo", "bar")`. x Subscript `c("foo", "bar")` must be size 1, not 2. Code # Idem with custom `arg` @@ -240,7 +240,7 @@ Output Error in `my_function()`: - ! Must extract element with a single valid subscript. + ! Can't extract element with `foo`. x Subscript `foo` must be size 1, not 2. Code (expect_error(vec_as_location2(mtcars, 10L, arg = "foo", call = call( @@ -248,7 +248,7 @@ Output Error in `my_function()`: - ! Must extract element with a single valid subscript. + ! Can't extract element with `foo`. x `foo` must be numeric or character, not a object. Code (expect_error(vec_as_location2(1:2, 2L, arg = "foo", call = call("my_function")), @@ -256,7 +256,7 @@ Output Error in `my_function()`: - ! Must extract element with a single valid subscript. + ! Can't extract element with `foo`. x Subscript `foo` must be size 1, not 2. # vec_as_location2() requires positive integers @@ -266,14 +266,14 @@ Output Error: - ! Must extract element with a single valid subscript. + ! Can't extract element with `0`. x Subscript `0` must be a positive location, not 0. Code (expect_error(vec_as_location2(-1, 2L), class = "vctrs_error_subscript_type")) Output Error: - ! Must extract element with a single valid subscript. + ! Can't extract element with `-1`. x Subscript `-1` must be a positive location, not -1. Code # Idem with custom `arg` @@ -282,7 +282,7 @@ Output Error in `my_function()`: - ! Must extract element with a single valid subscript. + ! Can't extract element with `foo`. x Subscript `foo` must be a positive location, not 0. # vec_as_location2() fails with NA @@ -293,7 +293,7 @@ Output Error: - ! Must extract element with a single valid subscript. + ! Can't extract element with `na_int`. x Subscript `na_int` must be a location, not an integer `NA`. Code (expect_error(vec_as_location2(na_chr, 1L, names = "foo"), class = "vctrs_error_subscript_type") @@ -301,7 +301,7 @@ Output Error: - ! Must extract element with a single valid subscript. + ! Can't extract element with `na_chr`. x Subscript `na_chr` must be a location, not a character `NA`. Code # Idem with custom `arg` @@ -310,7 +310,7 @@ Output Error in `my_function()`: - ! Must extract element with a single valid subscript. + ! Can't extract element with `foo`. x Subscript `foo` must be a location, not an integer `NA`. # num_as_location() optionally forbids negative indices @@ -321,7 +321,7 @@ Output Error: - ! Must subset elements with a valid subscript vector. + ! Can't subset elements with `dbl(1, -1)`. x Subscript `dbl(1, -1)` can't contain negative locations. # num_as_location() optionally forbids zero indices @@ -332,7 +332,7 @@ Output Error: - ! Must subset elements with a valid subscript vector. + ! Can't subset elements with `0L`. x Subscript `0L` can't contain `0` values. i It has a `0` value at location 1. Code @@ -341,7 +341,7 @@ Output Error: - ! Must subset elements with a valid subscript vector. + ! Can't subset elements with `c(0, 0, 0, 0, 0, 0)`. x Subscript `c(0, 0, 0, 0, 0, 0)` can't contain `0` values. i It has 6 `0` values at locations 1, 2, 3, 4, 5, etc. @@ -353,7 +353,7 @@ Output Error: - ! Must subset elements with a valid subscript vector. + ! Can't subset elements with `-c(1L, NA)`. x Negative locations can't have missing values. i Subscript `-c(1L, NA)` has a missing value at location 2. Code @@ -362,7 +362,7 @@ Output Error: - ! Must subset elements with a valid subscript vector. + ! Can't subset elements with `-c(1L, rep(NA, 10))`. x Negative locations can't have missing values. i Subscript `-c(1L, rep(NA, 10))` has 10 missing values at locations 2, 3, 4, 5, 6, etc. @@ -374,7 +374,7 @@ Output Error: - ! Must subset elements with a valid subscript vector. + ! Can't subset elements with `c(-1L, 1L)`. x Negative and positive locations can't be mixed. i Subscript `c(-1L, 1L)` has a positive value at location 2. Code @@ -383,7 +383,7 @@ Output Error: - ! Must subset elements with a valid subscript vector. + ! Can't subset elements with `c(-1L, rep(1L, 10))`. x Negative and positive locations can't be mixed. i Subscript `c(-1L, rep(1L, 10))` has 10 positive values at locations 2, 3, 4, 5, 6, etc. @@ -395,7 +395,7 @@ Output Error: - ! Must subset elements with a valid subscript vector. + ! Can't subset elements with `c(TRUE, FALSE)`. x Logical subscript `c(TRUE, FALSE)` must be size 1 or 3, not 2. # character subscripts require named vectors @@ -481,7 +481,7 @@ num_as_location(c(0, -1), n = 2L, negative = "invert", zero = "error") Condition Error: - ! Must subset elements with a valid subscript vector. + ! Can't subset elements with `c(0, -1)`. x Subscript `c(0, -1)` can't contain `0` values. i It has a `0` value at location 1. @@ -491,7 +491,7 @@ num_as_location(c(-1, 0), n = 2L, negative = "invert", zero = "error") Condition Error: - ! Must subset elements with a valid subscript vector. + ! Can't subset elements with `c(-1, 0)`. x Subscript `c(-1, 0)` can't contain `0` values. i It has a `0` value at location 2. @@ -564,7 +564,7 @@ Output Error: - ! Must subset elements with a valid subscript vector. + ! Can't subset elements. x Subscript can't contain missing values. x It has a missing value at location 2. Code @@ -573,7 +573,7 @@ Output Error in `my_function()`: - ! Must subset elements with a valid subscript vector. + ! Can't subset elements. x Subscript can't contain missing values. x It has missing values at locations 2 and 4. Code @@ -582,7 +582,7 @@ Output Error: - ! Must rename columns with a valid subscript vector. + ! Can't rename columns with `foo(bar)`. x Subscript `foo(bar)` can't contain missing values. x It has missing values at locations 2 and 4. Code @@ -591,7 +591,7 @@ Output Error: - ! Must rename columns with a valid subscript vector. + ! Can't rename columns with `foo(bar)`. x Subscript `foo(bar)` can't contain missing values. x It has a missing value at location 1. Code @@ -600,7 +600,7 @@ Output Error: - ! Must rename columns with a valid subscript vector. + ! Can't rename columns with `foo(bar)`. x Subscript `foo(bar)` can't contain missing values. x It has a missing value at location 1. Code @@ -609,7 +609,7 @@ Output Error: - ! Must rename columns with a valid subscript vector. + ! Can't rename columns with `foo(bar)`. x Subscript `foo(bar)` can't contain missing values. x It has a missing value at location 2. Code @@ -618,7 +618,7 @@ Output Error: - ! Must rename columns with a valid subscript vector. + ! Can't rename columns with `foo(bar)`. x Subscript `foo(bar)` can't contain missing values. x It has a missing value at location 1. @@ -628,7 +628,7 @@ vec_as_location(x, n = 4L, missing = "error") Condition Error: - ! Must subset elements with a valid subscript vector. + ! Can't subset elements. x Subscript can't contain missing values. x It has missing values at locations 2 and 4. @@ -638,7 +638,7 @@ vec_as_location(x, n = 2L, missing = "error") Condition Error: - ! Must subset elements with a valid subscript vector. + ! Can't subset elements. x Subscript can't contain missing values. x It has a missing value at location 1. @@ -648,7 +648,7 @@ vec_as_location(x, n = 2L, names = names, missing = "error") Condition Error: - ! Must subset elements with a valid subscript vector. + ! Can't subset elements. x Subscript can't contain missing values. x It has missing values at locations 1 and 3. @@ -658,7 +658,7 @@ vec_as_location(x, n = 4L, missing = "error") Condition Error: - ! Must subset elements with a valid subscript vector. + ! Can't subset elements. x Subscript can't contain missing values. x It has missing values at locations 1 and 3. @@ -668,7 +668,7 @@ num_as_location(x, n = 4L, missing = "propagate", negative = "invert") Condition Error: - ! Must subset elements with a valid subscript vector. + ! Can't subset elements with `x`. x Negative locations can't have missing values. i Subscript `x` has 2 missing values at locations 2 and 3. @@ -678,7 +678,7 @@ num_as_location(x, n = 4L, missing = "error", negative = "invert") Condition Error: - ! Must subset elements with a valid subscript vector. + ! Can't subset elements with `x`. x Negative locations can't have missing values. i Subscript `x` has 2 missing values at locations 2 and 3. @@ -688,7 +688,7 @@ vec_as_location("", n = 2L, names = names) Condition Error: - ! Must subset elements with a valid subscript vector. + ! Can't subset elements. x Subscript can't contain the empty string. x It has an empty string at location 1. @@ -698,7 +698,7 @@ vec_as_location(c("", "y", ""), n = 2L, names = names) Condition Error: - ! Must subset elements with a valid subscript vector. + ! Can't subset elements. x Subscript can't contain the empty string. x It has an empty string at locations 1 and 3. @@ -711,7 +711,7 @@ Output Error in `my_function()`: - ! Must subset elements with a valid subscript vector. + ! Can't subset elements with `foo`. x Subscript `foo` can't contain negative locations. Code (expect_error(num_as_location2(-1, 2, negative = "error", arg = "foo", call = call( @@ -719,7 +719,7 @@ Output Error in `my_function()`: - ! Must extract element with a single valid subscript. + ! Can't extract element with `foo`. x Subscript `foo` must be a positive location, not -1. Code (expect_error(vec_as_location2(0, 2, arg = "foo", call = call("my_function")), @@ -727,7 +727,7 @@ Output Error in `my_function()`: - ! Must extract element with a single valid subscript. + ! Can't extract element with `foo`. x Subscript `foo` must be a positive location, not 0. Code (expect_error(vec_as_location2(na_dbl, 2, arg = "foo", call = call( @@ -735,7 +735,7 @@ Output Error in `my_function()`: - ! Must extract element with a single valid subscript. + ! Can't extract element with `foo`. x Subscript `foo` must be a location, not an integer `NA`. Code (expect_error(vec_as_location2(c(1, 2), 2, arg = "foo", call = call( @@ -743,7 +743,7 @@ Output Error in `my_function()`: - ! Must extract element with a single valid subscript. + ! Can't extract element with `foo`. x Subscript `foo` must be size 1, not 2. Code (expect_error(vec_as_location(c(TRUE, FALSE), 3, arg = "foo", call = call( @@ -751,7 +751,7 @@ Output Error in `my_function()`: - ! Must subset elements with a valid subscript vector. + ! Can't subset elements with `foo`. x Logical subscript `foo` must be size 1 or 3, not 2. Code (expect_error(vec_as_location(c(-1, NA), 3, arg = "foo", call = call( @@ -759,7 +759,7 @@ Output Error in `my_function()`: - ! Must subset elements with a valid subscript vector. + ! Can't subset elements with `foo`. x Negative locations can't have missing values. i Subscript `foo` has a missing value at location 2. Code @@ -768,7 +768,7 @@ Output Error in `my_function()`: - ! Must subset elements with a valid subscript vector. + ! Can't subset elements with `foo`. x Negative and positive locations can't be mixed. i Subscript `foo` has a positive value at location 2. Code @@ -786,7 +786,7 @@ Output Error in `my_function()`: - ! Must subset elements with a valid subscript vector. + ! Can't subset elements with `foo`. x Subscript `foo` can't contain `0` values. i It has a `0` value at location 1. Code @@ -796,7 +796,7 @@ Output Error: - ! Must rename columns with a valid subscript vector. + ! Can't rename columns with `foo(bar)`. x Subscript `foo(bar)` can't contain negative locations. Code (expect_error(with_tibble_cols(num_as_location2(-1, 2, negative = "error")), @@ -804,7 +804,7 @@ Output Error: - ! Must rename column with a single valid subscript. + ! Can't rename column with `foo(bar)`. x Subscript `foo(bar)` must be a positive location, not -1. Code (expect_error(with_tibble_cols(vec_as_location2(0, 2)), class = "vctrs_error_subscript_type") @@ -812,7 +812,7 @@ Output Error: - ! Must rename column with a single valid subscript. + ! Can't rename column with `foo(bar)`. x Subscript `foo(bar)` must be a positive location, not 0. Code (expect_error(with_tibble_cols(vec_as_location2(na_dbl, 2)), class = "vctrs_error_subscript_type") @@ -820,7 +820,7 @@ Output Error: - ! Must rename column with a single valid subscript. + ! Can't rename column with `foo(bar)`. x Subscript `foo(bar)` must be a location, not an integer `NA`. Code (expect_error(with_tibble_cols(vec_as_location2(c(1, 2), 2)), class = "vctrs_error_subscript_type") @@ -828,7 +828,7 @@ Output Error: - ! Must rename column with a single valid subscript. + ! Can't rename column with `foo(bar)`. x Subscript `foo(bar)` must be size 1, not 2. Code (expect_error(with_tibble_cols(vec_as_location(c(TRUE, FALSE), 3)), class = "vctrs_error_subscript_size") @@ -836,7 +836,7 @@ Output Error: - ! Must rename columns with a valid subscript vector. + ! Can't rename columns with `foo(bar)`. x Logical subscript `foo(bar)` must be size 1 or 3, not 2. Code (expect_error(with_tibble_cols(vec_as_location(c(-1, NA), 3)), class = "vctrs_error_subscript_type") @@ -844,7 +844,7 @@ Output Error: - ! Must rename columns with a valid subscript vector. + ! Can't rename columns with `foo(bar)`. x Negative locations can't have missing values. i Subscript `foo(bar)` has a missing value at location 2. Code @@ -853,7 +853,7 @@ Output Error: - ! Must rename columns with a valid subscript vector. + ! Can't rename columns with `foo(bar)`. x Negative and positive locations can't be mixed. i Subscript `foo(bar)` has a positive value at location 2. Code @@ -871,7 +871,7 @@ Output Error: - ! Must rename columns with a valid subscript vector. + ! Can't rename columns with `foo(bar)`. x Subscript `foo(bar)` can't contain `0` values. i It has a `0` value at location 1. @@ -1020,7 +1020,7 @@ Output Error: - ! Must subset elements with a valid subscript vector. + ! Can't subset elements with `matrix(TRUE, nrow = 1)`. x Subscript `matrix(TRUE, nrow = 1)` must be a simple vector, not a matrix. Code (expect_error(vec_as_location(array(TRUE, dim = c(1, 1, 1)), 3L), class = "vctrs_error_subscript_type") @@ -1028,7 +1028,7 @@ Output Error: - ! Must subset elements with a valid subscript vector. + ! Can't subset elements with `array(TRUE, dim = c(1, 1, 1))`. x Subscript `array(TRUE, dim = c(1, 1, 1))` must be a simple vector, not an array. Code (expect_error(with_tibble_rows(vec_as_location(matrix(TRUE, nrow = 1), 3L)), @@ -1036,7 +1036,7 @@ Output Error: - ! Must remove rows with a valid subscript vector. + ! Can't remove rows with `foo(bar)`. x Subscript `foo(bar)` must be a simple vector, not a matrix. # vec_as_location() UI diff --git a/tests/testthat/_snaps/subscript.md b/tests/testthat/_snaps/subscript.md index 1e0a13fa4..43aa2ff5c 100644 --- a/tests/testthat/_snaps/subscript.md +++ b/tests/testthat/_snaps/subscript.md @@ -6,7 +6,7 @@ Output Error: - ! Must rename columns with a valid subscript vector. + ! Can't rename columns with `foo(bar)`. x `foo(bar)` must be logical, numeric, or character, not an environment. --- @@ -17,7 +17,7 @@ Output Error: - ! Must extract tables with a valid subscript vector. + ! Can't extract tables with `foo(bar)`. x `foo(bar)` must be logical, numeric, or character, not an environment. # vec_as_subscript() checks dimensionality @@ -28,7 +28,7 @@ Output Error: - ! Must subset elements with a valid subscript vector. + ! Can't subset elements. x Subscript must be a simple vector, not a matrix. Code (expect_error(vec_as_subscript(array(TRUE, dim = c(1, 1, 1))), class = "vctrs_error_subscript_type") @@ -36,7 +36,7 @@ Output Error: - ! Must subset elements with a valid subscript vector. + ! Can't subset elements. x Subscript must be a simple vector, not an array. Code (expect_error(with_tibble_rows(vec_as_subscript(matrix(TRUE, nrow = 1))), @@ -44,7 +44,7 @@ Output Error: - ! Must remove rows with a valid subscript vector. + ! Can't remove rows with `foo(bar)`. x Subscript `foo(bar)` must be a simple vector, not a matrix. # vec_as_subscript() forbids subscript types @@ -53,7 +53,7 @@ vec_as_subscript(1L, logical = "error", numeric = "error") Condition Error: - ! Must subset elements with a valid subscript vector. + ! Can't subset elements. x Subscript must be character, not the number 1. --- @@ -62,7 +62,7 @@ vec_as_subscript("foo", logical = "error", character = "error") Condition Error: - ! Must subset elements with a valid subscript vector. + ! Can't subset elements. x Subscript must be numeric, not the string "foo". --- @@ -71,7 +71,7 @@ vec_as_subscript(TRUE, logical = "error") Condition Error: - ! Must subset elements with a valid subscript vector. + ! Can't subset elements. x Subscript must be numeric or character, not `TRUE`. --- @@ -80,7 +80,7 @@ vec_as_subscript("foo", character = "error") Condition Error: - ! Must subset elements with a valid subscript vector. + ! Can't subset elements. x Subscript must be logical or numeric, not the string "foo". --- @@ -89,7 +89,7 @@ vec_as_subscript(NULL, numeric = "error") Condition Error: - ! Must subset elements with a valid subscript vector. + ! Can't subset elements. x Subscript must be logical or character, not `NULL`. --- @@ -98,7 +98,7 @@ vec_as_subscript(quote(foo), character = "error") Condition Error: - ! Must subset elements with a valid subscript vector. + ! Can't subset elements. x Subscript must be logical or numeric, not a symbol. # vec_as_subscript2() forbids subscript types @@ -107,7 +107,7 @@ vec_as_subscript2(1L, numeric = "error") Condition Error: - ! Must extract element with a single valid subscript. + ! Can't extract element. x Subscript must be character, not the number 1. --- @@ -116,7 +116,7 @@ vec_as_subscript2("foo", character = "error") Condition Error: - ! Must extract element with a single valid subscript. + ! Can't extract element. x Subscript must be numeric, not the string "foo". --- @@ -125,7 +125,7 @@ vec_as_subscript2(TRUE) Condition Error: - ! Must extract element with a single valid subscript. + ! Can't extract element. x Subscript must be numeric or character, not `TRUE`. # vec_as_subscript2() retains the call when throwing vec_as_subscript() errors (#1605) @@ -134,7 +134,7 @@ vec_as_subscript2(1L, numeric = "error", call = call("foo")) Condition Error in `foo()`: - ! Must extract element with a single valid subscript. + ! Can't extract element. x Subscript must be character, not the number 1. --- @@ -143,7 +143,7 @@ vec_as_subscript2(1.5, call = call("foo")) Condition Error in `foo()`: - ! Must extract element with a single valid subscript. + ! Can't extract element. x Can't convert from to due to loss of precision. # vec_as_subscript2() retains the call when erroring on logical input (#1605) @@ -152,7 +152,7 @@ vec_as_subscript2(TRUE, call = call("foo")) Condition Error in `foo()`: - ! Must extract element with a single valid subscript. + ! Can't extract element. x Subscript must be numeric or character, not `TRUE`. # `logical = 'cast'` is deprecated @@ -169,7 +169,7 @@ vec_as_subscript2(TRUE, logical = "error") Condition Error: - ! Must extract element with a single valid subscript. + ! Can't extract element. x Subscript must be numeric or character, not `TRUE`. # lossy cast errors for scalar subscripts work (#1606) @@ -178,6 +178,6 @@ vec_as_subscript2(1.5) Condition Error: - ! Must extract element with a single valid subscript. + ! Can't extract element. x Can't convert from to due to loss of precision. From 252428c227634dd161bf1b2641e19a3cd55cfa98 Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Fri, 21 Oct 2022 09:46:12 +0200 Subject: [PATCH 190/312] Throw scalar location errors more consistently --- R/subscript-loc.R | 19 +++++++------------ tests/testthat/_snaps/subscript-loc.md | 6 +++--- 2 files changed, 10 insertions(+), 15 deletions(-) diff --git a/R/subscript-loc.R b/R/subscript-loc.R index 3fabb24b3..53d7989c3 100644 --- a/R/subscript-loc.R +++ b/R/subscript-loc.R @@ -259,29 +259,24 @@ vec_as_location2_result <- function(i, ))) } - # FIXME: Use result approach in internal implementation? err <- NULL i <- tryCatch( vec_as_location(i, n, names = names, arg = arg, call = call), - vctrs_error_subscript_type = function(err) { + vctrs_error_subscript = function(err) { + err[["subscript_scalar"]] <- TRUE err <<- err i } ) + if (!is_null(err)) { + return(result(err = err)) + } if (neg) { i <- -i } - if (is_null(err)) { - result(i) - } else { - result(err = new_error_location2_type( - i = i, - subscript_arg = arg, - call = call - )) - } + result(i) } @@ -610,6 +605,6 @@ cnd_body_vctrs_error_subscript_oob_non_consecutive <- function(cnd, ...) { cnd_subscript_oob_non_consecutive <- function(cnd) { out <- cnd$subscript_oob_non_consecutive %||% FALSE - stopifnot(is_bool(out)) + check_bool(out) out } diff --git a/tests/testthat/_snaps/subscript-loc.md b/tests/testthat/_snaps/subscript-loc.md index b60ade633..e1f40b9f0 100644 --- a/tests/testthat/_snaps/subscript-loc.md +++ b/tests/testthat/_snaps/subscript-loc.md @@ -187,7 +187,7 @@ Output Error: - ! Can't subset elements past the end. + ! Can't extract elements past the end. i Location 10 doesn't exist. i There are only 2 elements. Code @@ -205,7 +205,7 @@ Output Error: - ! Can't subset elements that don't exist. + ! Can't extract elements that don't exist. x Element `foo` doesn't exist. Code (expect_error(vec_as_location2("foo", 1L, names = "bar", call = call("baz")), @@ -213,7 +213,7 @@ Output Error in `baz()`: - ! Can't subset elements that don't exist. + ! Can't extract elements that don't exist. x Element `foo` doesn't exist. # vec_as_location2() requires length 1 inputs From 7e0150fe26eab70231a77666ce004d3511edf743 Mon Sep 17 00:00:00 2001 From: Davis Vaughan Date: Fri, 21 Oct 2022 13:10:23 -0400 Subject: [PATCH 191/312] Updates for `-Wstrict-prototypes` (#1729) --- NEWS.md | 3 +++ inst/include/vctrs.c | 2 +- inst/include/vctrs.h | 2 +- src/decl/names-decl.h | 2 +- src/fill.c | 4 ++-- src/init.c | 4 ++-- src/names.c | 2 +- src/order-groups.c | 2 +- src/order-groups.h | 2 +- src/utils.c | 4 ++-- src/utils.h | 2 +- src/version.c | 2 +- 12 files changed, 17 insertions(+), 14 deletions(-) diff --git a/NEWS.md b/NEWS.md index e9e487900..6ece9d138 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,5 +1,8 @@ # vctrs (development version) +* vctrs is now compliant with `-Wstrict-prototypes` as requested by CRAN + (#1729). + * `vec_ptype2()` now consistently falls back to bare data frame in case of incompatible data frame subclasses. This is part of a general move towards relaxed coercion rules. diff --git a/inst/include/vctrs.c b/inst/include/vctrs.c index 5f9fe8689..af4819e72 100644 --- a/inst/include/vctrs.c +++ b/inst/include/vctrs.c @@ -4,7 +4,7 @@ bool (*vec_is_vector)(SEXP) = NULL; R_len_t (*short_vec_size)(SEXP) = NULL; SEXP (*short_vec_recycle)(SEXP, R_len_t) = NULL; -void vctrs_init_api() { +void vctrs_init_api(void) { vec_is_vector = (bool (*)(SEXP)) R_GetCCallable("vctrs", "vec_is_vector"); short_vec_size = (R_len_t (*)(SEXP)) R_GetCCallable("vctrs", "short_vec_size"); short_vec_recycle = (SEXP (*)(SEXP, R_len_t)) R_GetCCallable("vctrs", "short_vec_recycle"); diff --git a/inst/include/vctrs.h b/inst/include/vctrs.h index 23d70f6f7..6c8205aba 100644 --- a/inst/include/vctrs.h +++ b/inst/include/vctrs.h @@ -9,6 +9,6 @@ extern bool (*vec_is_vector)(SEXP); extern R_len_t (*short_vec_size)(SEXP); extern SEXP (*short_vec_recycle)(SEXP, R_len_t); -void vctrs_init_api(); +void vctrs_init_api(void); #endif diff --git a/src/decl/names-decl.h b/src/decl/names-decl.h index c35b46ddc..75c5c92ae 100644 --- a/src/decl/names-decl.h +++ b/src/decl/names-decl.h @@ -29,7 +29,7 @@ static r_obj* as_unique_names_impl(r_obj* names, bool quiet); static -void stop_large_name(); +void stop_large_name(void); static bool is_dotdotint(const char* name); diff --git a/src/fill.c b/src/fill.c index 404a20c04..7bc37ca8a 100644 --- a/src/fill.c +++ b/src/fill.c @@ -202,7 +202,7 @@ void vec_fill_missing_up_with_max_fill(const int* p_na, r_ssize size, bool leadi // ----------------------------------------------------------------------------- -static void stop_bad_direction(); +static void stop_bad_direction(void); static void parse_direction(SEXP x, bool* p_down, bool* p_leading) { @@ -238,7 +238,7 @@ void parse_direction(SEXP x, bool* p_down, bool* p_leading) { } static -void stop_bad_direction() { +void stop_bad_direction(void) { r_abort("`direction` must be one of \"down\", \"up\", \"downup\", or \"updown\"."); } diff --git a/src/init.c b/src/init.c index e8b6de15a..cbff4f412 100644 --- a/src/init.c +++ b/src/init.c @@ -97,7 +97,7 @@ extern r_obj* ffi_as_subscript(r_obj*, r_obj*, r_obj*, r_obj*, r_obj*); extern r_obj* ffi_as_subscript_result(r_obj*, r_obj*, r_obj*, r_obj*, r_obj*); extern r_obj* ffi_df_flatten_info(r_obj*); extern r_obj* df_flatten(r_obj*); -extern SEXP vctrs_linked_version(); +extern SEXP vctrs_linked_version(void); extern r_obj* ffi_tib_ptype2(r_obj*, r_obj*, r_obj*, r_obj*, r_obj*); extern r_obj* ffi_tib_cast(r_obj*, r_obj*, r_obj*, r_obj*, r_obj*); extern r_obj* ffi_assign_params(r_obj*, r_obj*, r_obj*, r_obj*); @@ -105,7 +105,7 @@ extern SEXP vctrs_has_dim(SEXP); extern r_obj* ffi_vec_rep(r_obj*, r_obj*, r_obj*); extern r_obj* ffi_vec_rep_each(r_obj*, r_obj*, r_obj*); extern SEXP vctrs_maybe_shared_col(SEXP, SEXP); -extern SEXP vctrs_new_df_unshared_col(); +extern SEXP vctrs_new_df_unshared_col(void); extern r_obj* ffi_vec_shaped_ptype(r_obj*, r_obj*, r_obj*, r_obj*); extern r_obj* ffi_vec_shape2(r_obj*, r_obj*, r_obj*); extern SEXP vctrs_new_date(SEXP); diff --git a/src/names.c b/src/names.c index d0d7f257b..5373e01c7 100644 --- a/src/names.c +++ b/src/names.c @@ -433,7 +433,7 @@ ptrdiff_t suffix_pos(const char* name) { } } -static void stop_large_name() { +static void stop_large_name(void) { r_abort("Can't tidy up name because it is too large."); } diff --git a/src/order-groups.c b/src/order-groups.c index 2bd270c6f..065d002b4 100644 --- a/src/order-groups.c +++ b/src/order-groups.c @@ -15,7 +15,7 @@ // ----------------------------------------------------------------------------- // Pair with `PROTECT_GROUP_INFO()` in the caller -struct group_info* new_group_info() { +struct group_info* new_group_info(void) { SEXP self = PROTECT(r_new_raw(sizeof(struct group_info))); struct group_info* p_group_info = (struct group_info*) RAW(self); diff --git a/src/order-groups.h b/src/order-groups.h index f64ff1f23..c35a6f937 100644 --- a/src/order-groups.h +++ b/src/order-groups.h @@ -105,7 +105,7 @@ struct group_infos { // ----------------------------------------------------------------------------- -struct group_info* new_group_info(); +struct group_info* new_group_info(void); struct group_infos* new_group_infos(struct group_info* p_group_info0, struct group_info* p_group_info1, diff --git a/src/utils.c b/src/utils.c index 091082021..74e98beff 100644 --- a/src/utils.c +++ b/src/utils.c @@ -236,7 +236,7 @@ SEXP vctrs_maybe_shared_col(SEXP x, SEXP i) { } // [[ register() ]] -SEXP vctrs_new_df_unshared_col() { +SEXP vctrs_new_df_unshared_col(void) { SEXP col = PROTECT(Rf_allocVector(INTSXP, 1)); INTEGER(col)[0] = 1; @@ -1635,7 +1635,7 @@ SEXP r_new_shared_character(const char* name) { return out; } -void c_print_backtrace() { +void c_print_backtrace(void) { #if defined(RLIB_DEBUG) #include #include diff --git a/src/utils.h b/src/utils.h index b4b6a0243..e1943fc51 100644 --- a/src/utils.h +++ b/src/utils.h @@ -373,7 +373,7 @@ static inline const void* vec_type_missing_value(enum vctrs_type type) { } } -void c_print_backtrace(); +void c_print_backtrace(void); SEXP chr_c(SEXP x, SEXP y); diff --git a/src/version.c b/src/version.c index 01e6c7d13..ec627bdac 100644 --- a/src/version.c +++ b/src/version.c @@ -22,6 +22,6 @@ const char* vctrs_version = "0.4.2.9000"; */ // [[ register() ]] -SEXP vctrs_linked_version() { +SEXP vctrs_linked_version(void) { return Rf_mkString(vctrs_version); } From f17a4fcbbf120ef238a261476a6398b2b350082c Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Fri, 21 Oct 2022 19:14:44 +0200 Subject: [PATCH 192/312] Update rlang C library --- src/rlang/arg.c | 2 +- src/rlang/call.c | 2 +- src/rlang/cnd.c | 6 +++--- src/rlang/cnd.h | 4 ++-- src/rlang/dyn-array.c | 2 +- src/rlang/env.c | 4 ++-- src/rlang/eval.c | 2 +- src/rlang/fn.c | 2 +- src/rlang/globals.c | 3 +-- src/rlang/globals.h | 1 - src/rlang/obj.c | 2 +- src/rlang/quo.c | 2 +- src/rlang/session.c | 8 ++++---- src/rlang/session.h | 4 ++-- src/rlang/stack.c | 4 ++-- src/rlang/stack.h | 2 +- src/rlang/sym.c | 2 +- src/rlang/vendor.c | 2 +- 18 files changed, 26 insertions(+), 28 deletions(-) diff --git a/src/rlang/arg.c b/src/rlang/arg.c index 0bc74bb10..5b80f9bfc 100644 --- a/src/rlang/arg.c +++ b/src/rlang/arg.c @@ -5,7 +5,7 @@ int (*r_arg_match)(r_obj* arg, struct r_lazy error_arg, struct r_lazy error_call); -void r_init_library_arg() { +void r_init_library_arg(void) { r_arg_match = (int (*)(r_obj*, r_obj*, struct r_lazy, struct r_lazy)) r_peek_c_callable("rlang", "rlang_arg_match_2"); } diff --git a/src/rlang/call.c b/src/rlang/call.c index 0b0b48a0b..1ff89cf71 100644 --- a/src/rlang/call.c +++ b/src/rlang/call.c @@ -62,6 +62,6 @@ r_obj* r_call_clone(r_obj* x) { } -void r_init_library_call() { +void r_init_library_call(void) { quote_prim = r_base_ns_get("quote"); } diff --git a/src/rlang/cnd.c b/src/rlang/cnd.c index 2a738dcd2..a5fd5d17c 100644 --- a/src/rlang/cnd.c +++ b/src/rlang/cnd.c @@ -87,13 +87,13 @@ void r_cnd_signal(r_obj* cnd) { #ifdef _WIN32 #include -void r_interrupt() { +void r_interrupt(void) { UserBreak = 1; R_CheckUserInterrupt(); } #else #include -void r_interrupt() { +void r_interrupt(void) { Rf_onintr(); } #endif @@ -134,7 +134,7 @@ enum r_cnd_type r_cnd_type(r_obj* cnd) { } -void r_init_library_cnd() { +void r_init_library_cnd(void) { msg_call = r_parse("message(x)"); r_preserve(msg_call); diff --git a/src/rlang/cnd.h b/src/rlang/cnd.h index d42362158..8a1b71e13 100644 --- a/src/rlang/cnd.h +++ b/src/rlang/cnd.h @@ -6,7 +6,7 @@ void r_inform(const char* fmt, ...); void r_warn(const char* fmt, ...); -void r_interrupt(); +void r_interrupt(void); void r_no_return r_abort(const char* fmt, ...); void r_no_return r_abort_n(const struct r_pair* args, int n); void r_no_return r_abort_call(r_obj* call, const char* fmt, ...); @@ -36,7 +36,7 @@ void (*r_stop_internal)(const char* file, const char* fmt, ...); -r_obj* r_peek_frame(); +r_obj* r_peek_frame(void); #define r_stop_internal(...) \ (r_stop_internal)(__FILE__, __LINE__, r_peek_frame(), \ diff --git a/src/rlang/dyn-array.c b/src/rlang/dyn-array.c index 28b024bef..07ad57ca4 100644 --- a/src/rlang/dyn-array.c +++ b/src/rlang/dyn-array.c @@ -119,7 +119,7 @@ void r_dyn_resize(struct r_dyn_array* p_arr, } -void r_init_library_dyn_array() { +void r_init_library_dyn_array(void) { r_preserve_global(attribs_dyn_array = r_pairlist(r_chr("rlang_dyn_array"))); r_node_poke_tag(attribs_dyn_array, r_syms.class_); } diff --git a/src/rlang/env.c b/src/rlang/env.c index 9dab9c492..00d5f7208 100644 --- a/src/rlang/env.c +++ b/src/rlang/env.c @@ -282,11 +282,11 @@ r_obj* r_env_find_until(r_obj* env, r_obj* sym, r_obj* last) { } -void r_init_rlang_ns_env() { +void r_init_rlang_ns_env(void) { rlang_ns_env = r_ns_env("rlang"); } -void r_init_library_env() { +void r_init_library_env(void) { new_env_call = r_parse_eval("as.call(list(new.env, TRUE, NULL, NULL))", r_envs.base); r_preserve(new_env_call); diff --git a/src/rlang/eval.c b/src/rlang/eval.c index ce581c5d8..ba069ddde 100644 --- a/src/rlang/eval.c +++ b/src/rlang/eval.c @@ -168,7 +168,7 @@ r_obj* r_exec_mask_n_call_poke(r_obj* fn_sym, } -void r_init_library_eval() { +void r_init_library_eval(void) { r_lazy_missing_arg = (struct r_lazy) { .x = r_missing_arg, .env = r_null }; } diff --git a/src/rlang/fn.c b/src/rlang/fn.c index 60ed6a940..67a330a36 100644 --- a/src/rlang/fn.c +++ b/src/rlang/fn.c @@ -25,7 +25,7 @@ r_obj* r_as_function(r_obj* x, const char* arg) { } } -void r_init_library_fn() { +void r_init_library_fn(void) { const char* formals_code = "formals(function(..., .x = ..1, .y = ..2, . = ..1) NULL)"; rlang_formula_formals = r_parse_eval(formals_code, r_envs.base); r_preserve_global(rlang_formula_formals); diff --git a/src/rlang/globals.c b/src/rlang/globals.c index c18917a9f..123ed720a 100644 --- a/src/rlang/globals.c +++ b/src/rlang/globals.c @@ -55,7 +55,7 @@ void r_init_library_globals(r_obj* ns) { r_envs.ns = ns; } -void r_init_library_globals_syms() { +void r_init_library_globals_syms(void) { r_syms.abort = r_sym("abort"); r_syms.arg = r_sym("arg"); r_syms.brackets = R_BracketSymbol; @@ -83,7 +83,6 @@ void r_init_library_globals_syms() { r_syms.unbound = R_UnboundValue; r_syms.warning = r_sym("warning"); - r_syms.dot_call = r_sym(".call"); r_syms.dot_environment = r_sym(".Environment"); r_syms.dot_fn = r_sym(".fn"); r_syms.dot_x = r_sym(".x"); diff --git a/src/rlang/globals.h b/src/rlang/globals.h index c9a0df7bd..89faf36dc 100644 --- a/src/rlang/globals.h +++ b/src/rlang/globals.h @@ -50,7 +50,6 @@ struct r_globals_syms { r_obj* class_; r_obj* condition; r_obj* dots; - r_obj* dot_call; r_obj* dot_environment; r_obj* dot_fn; r_obj* dot_x; diff --git a/src/rlang/obj.c b/src/rlang/obj.c index 9f1762a24..1883ba292 100644 --- a/src/rlang/obj.c +++ b/src/rlang/obj.c @@ -96,7 +96,7 @@ int pop_precious(r_obj* stack) { } // For unit tests -struct r_dict* rlang__precious_dict() { +struct r_dict* rlang__precious_dict(void) { return p_precious_dict; } diff --git a/src/rlang/quo.c b/src/rlang/quo.c index 8e782a9ca..6d07ceee3 100644 --- a/src/rlang/quo.c +++ b/src/rlang/quo.c @@ -5,7 +5,7 @@ r_obj* (*r_quo_set_expr)(r_obj* quo, r_obj* expr); r_obj* (*r_quo_get_env)(r_obj* quo); r_obj* (*r_quo_set_env)(r_obj* quo, r_obj* env); -void r_init_library_quo() { +void r_init_library_quo(void) { r_quo_get_expr = (r_obj* (*)(r_obj*)) r_peek_c_callable("rlang", "rlang_quo_get_expr"); r_quo_set_expr = (r_obj* (*)(r_obj*, r_obj*)) r_peek_c_callable("rlang", "rlang_quo_set_expr"); r_quo_get_env = (r_obj* (*)(r_obj*)) r_peek_c_callable("rlang", "rlang_quo_get_env"); diff --git a/src/rlang/session.c b/src/rlang/session.c index ccd50a309..12c7dcbc2 100644 --- a/src/rlang/session.c +++ b/src/rlang/session.c @@ -16,7 +16,7 @@ bool r_is_installed(const char* pkg) { static r_obj* has_colour_call = NULL; -bool r_has_colour() { +bool r_has_colour(void) { if (!r_is_installed("crayon")) { return false; } @@ -25,7 +25,7 @@ bool r_has_colour() { } -void r_init_library_session() { +void r_init_library_session(void) { is_installed_call = r_parse("requireNamespace(x, quietly = TRUE)"); r_preserve(is_installed_call); @@ -39,7 +39,7 @@ void r_init_library_session() { # include # include -r_obj* r_getppid() { +r_obj* r_getppid(void) { DWORD pid = GetCurrentProcessId(); HANDLE handle = NULL; PROCESSENTRY32W pe = { 0 }; @@ -70,7 +70,7 @@ r_obj* r_getppid() { # include -r_obj* r_getppid() { +r_obj* r_getppid(void) { return r_int(getppid()); } diff --git a/src/rlang/session.h b/src/rlang/session.h index cf4ba4454..4ad6ed130 100644 --- a/src/rlang/session.h +++ b/src/rlang/session.h @@ -3,8 +3,8 @@ bool r_is_installed(const char* pkg); -bool r_has_colour(); -r_obj* r_getppid(); +bool r_has_colour(void); +r_obj* r_getppid(void); #endif diff --git a/src/rlang/stack.c b/src/rlang/stack.c index 7de0efc3f..e51e9a6c0 100644 --- a/src/rlang/stack.c +++ b/src/rlang/stack.c @@ -16,7 +16,7 @@ void r_on_exit(r_obj* expr, r_obj* frame) { } -r_obj* r_peek_frame() { +r_obj* r_peek_frame(void) { return r_eval(peek_frame_call, r_envs.empty); } @@ -74,7 +74,7 @@ static r_obj* generate_sys_call(const char* name, int** n_addr) { return sys_call; } -void r_init_library_stack() { +void r_init_library_stack(void) { r_obj* current_frame_body = KEEP(r_parse_eval("as.call(list(sys.frame, -1))", r_envs.base)); r_obj* current_frame_fn = KEEP(r_new_function(r_null, current_frame_body, r_envs.empty)); peek_frame_call = r_new_call(current_frame_fn, r_null); diff --git a/src/rlang/stack.h b/src/rlang/stack.h index 8c90078e5..4453d113c 100644 --- a/src/rlang/stack.h +++ b/src/rlang/stack.h @@ -4,7 +4,7 @@ void r_on_exit(r_obj* expr, r_obj* frame); -r_obj* r_peek_frame(); +r_obj* r_peek_frame(void); r_obj* r_caller_env(r_obj* n); r_obj* r_sys_frame(int n, r_obj* frame); r_obj* r_sys_call(int n, r_obj* frame); diff --git a/src/rlang/sym.c b/src/rlang/sym.c index 0bd2f8402..88607654c 100644 --- a/src/rlang/sym.c +++ b/src/rlang/sym.c @@ -53,7 +53,7 @@ bool r_is_symbol_any(r_obj* x, const char** strings, int n) { r_obj* (*r_sym_as_utf8_character)(r_obj* x) = NULL; r_obj* (*r_sym_as_utf8_string)(r_obj* x) = NULL; -void r_init_library_sym() { +void r_init_library_sym(void) { r_sym_as_utf8_character = (r_obj* (*)(r_obj*)) r_peek_c_callable("rlang", "rlang_sym_as_character"); r_sym_as_utf8_string = (r_obj* (*)(r_obj*)) r_peek_c_callable("rlang", "rlang_sym_as_string"); } diff --git a/src/rlang/vendor.c b/src/rlang/vendor.c index 894eef695..631c3f4e6 100644 --- a/src/rlang/vendor.c +++ b/src/rlang/vendor.c @@ -2,6 +2,6 @@ uint64_t (*r_xxh3_64bits)(const void*, size_t); -void r_init_library_vendor() { +void r_init_library_vendor(void) { r_xxh3_64bits = (uint64_t (*)(const void*, size_t)) r_peek_c_callable("rlang", "rlang_xxh3_64bits"); } From 3509722b2e5f08ac8a0ff23385c53e70f0d5d850 Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Fri, 21 Oct 2022 19:19:48 +0200 Subject: [PATCH 193/312] Silence remaining warnings --- src/rlang/stack.h | 2 +- src/subscript-loc.h | 2 +- src/subscript.h | 2 +- 3 files changed, 3 insertions(+), 3 deletions(-) diff --git a/src/rlang/stack.h b/src/rlang/stack.h index 4453d113c..bf1424ffc 100644 --- a/src/rlang/stack.h +++ b/src/rlang/stack.h @@ -10,7 +10,7 @@ r_obj* r_sys_frame(int n, r_obj* frame); r_obj* r_sys_call(int n, r_obj* frame); static inline -void r_yield_interrupt() { +void r_yield_interrupt(void) { R_CheckUserInterrupt(); } diff --git a/src/subscript-loc.h b/src/subscript-loc.h index 6cf59c61c..55d974ec9 100644 --- a/src/subscript-loc.h +++ b/src/subscript-loc.h @@ -36,7 +36,7 @@ struct location_opts { }; static inline -struct location_opts new_location_opts_assign() { +struct location_opts new_location_opts_assign(void) { return (struct location_opts) { .subscript_opts = new_subscript_opts_assign() }; diff --git a/src/subscript.h b/src/subscript.h index 550720f63..21cbb95f9 100644 --- a/src/subscript.h +++ b/src/subscript.h @@ -29,7 +29,7 @@ struct subscript_opts { }; static inline -struct subscript_opts new_subscript_opts_assign() { +struct subscript_opts new_subscript_opts_assign(void) { return (struct subscript_opts) { .action = SUBSCRIPT_ACTION_ASSIGN }; From 6a7fccda174bb8ddbfc1efa8e770f1453e516ddd Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Fri, 21 Oct 2022 20:48:56 +0200 Subject: [PATCH 194/312] Revert "Don't allow casting to non-bare data frames" This reverts commit b4f1c4098a3f432e1569a90475d45f5c22555be2. --- R/cast.R | 11 +++++------ tests/testthat/_snaps/cast.md | 9 --------- tests/testthat/_snaps/type-misc.md | 9 --------- tests/testthat/test-cast.R | 23 +++++++++++++++++++---- tests/testthat/test-type-misc.R | 8 ++++---- 5 files changed, 28 insertions(+), 32 deletions(-) diff --git a/R/cast.R b/R/cast.R index 3eab09067..d32e4fb17 100644 --- a/R/cast.R +++ b/R/cast.R @@ -209,13 +209,12 @@ vec_default_cast <- function(x, return(out) } - if (is_bare_df(to)) { - # Bare-class fallback for data frames - if (inherits(to, "tbl_df")) { - out <- df_as_tibble(out) - } - return(out) + # Bare-class fallback for data frames. + # FIXME: Should we only allow it when target is a bare df? + if (inherits(to, "tbl_df")) { + out <- df_as_tibble(out) } + return(out) } if (is_same_type(x, to)) { diff --git a/tests/testthat/_snaps/cast.md b/tests/testthat/_snaps/cast.md index 170a26aba..d77ca4507 100644 --- a/tests/testthat/_snaps/cast.md +++ b/tests/testthat/_snaps/cast.md @@ -62,15 +62,6 @@ Error: ! Can't combine `..1$a$b` > and `..2$a$b` . -# vec_cast() only falls back when casting to base type - - Code - (expect_error(vec_cast(mtcars, foobar(mtcars)))) - Output - - Error: - ! Can't convert `mtcars` to . - # vec_cast() only attempts to fall back if `to` is a data frame (#1568) Code diff --git a/tests/testthat/_snaps/type-misc.md b/tests/testthat/_snaps/type-misc.md index dc44c3fa8..ba0833783 100644 --- a/tests/testthat/_snaps/type-misc.md +++ b/tests/testthat/_snaps/type-misc.md @@ -1,12 +1,3 @@ -# data.table and tibble do not have a common type - - Code - (expect_error(vec_cast(tibble(y = 2), data.table(x = TRUE, y = 1L)))) - Output - - Error: - ! Can't convert `tibble(y = 2)` to . - # data table has formatting methods Code diff --git a/tests/testthat/test-cast.R b/tests/testthat/test-cast.R index 163e9ca68..d9000a99d 100644 --- a/tests/testthat/test-cast.R +++ b/tests/testthat/test-cast.R @@ -92,11 +92,9 @@ test_that("unspecified can be cast to shaped vectors", { expect_identical(out, exp) }) -test_that("vec_cast() only falls back when casting to base type", { +test_that("vec_cast() falls back to base class even when casting to non-base type", { expect_equal(vec_cast(foobar(mtcars), mtcars), mtcars) - expect_snapshot({ - (expect_error(vec_cast(mtcars, foobar(mtcars)))) - }) + expect_equal(vec_cast(mtcars, foobar(mtcars)), mtcars) }) test_that("vec_cast() only attempts to fall back if `to` is a data frame (#1568)", { @@ -284,3 +282,20 @@ test_that("df-fallback for cast is not sensitive to attributes order", { expect_identical(vec_cast(x, ptype), x) }) + +test_that("bare-type fallback for df-cast works", { + # NOTE: Not sure why this was necessary. The cubble and yamlet + # packages fail without this. + local_methods( + c.vctrs_foobaz = function(...) quux(NextMethod()) + ) + + df <- data_frame(x = 1, y = foobaz("foo")) + gdf <- dplyr::new_grouped_df( + df, + data_frame(x = 1, .rows = list(1L)), + class = "vctrs_foobar" + ) + + expect_error(vec_rbind(gdf, gdf), NA) +}) diff --git a/tests/testthat/test-type-misc.R b/tests/testthat/test-type-misc.R index 8b4905467..e1c61c7d4 100644 --- a/tests/testthat/test-type-misc.R +++ b/tests/testthat/test-type-misc.R @@ -77,10 +77,10 @@ test_that("data.table and tibble do not have a common type", { vec_cast(data.table(y = 2), tibble(x = TRUE, y = 1L)), tibble(x = lgl(NA), y = 2L) ) - - expect_snapshot({ - (expect_error(vec_cast(tibble(y = 2), data.table(x = TRUE, y = 1L)))) - }) + expect_identical( + vec_cast(tibble(y = 2), data.table(x = TRUE, y = 1L)), + data_frame(x = lgl(NA), y = 2L) + ) }) test_that("data table has formatting methods", { From 652f0c5b1091e78a4eaf8a60c7db35d070411808 Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Fri, 21 Oct 2022 19:20:33 +0200 Subject: [PATCH 195/312] Increment version number to 0.5.0 --- DESCRIPTION | 2 +- NEWS.md | 2 +- src/version.c | 2 +- 3 files changed, 3 insertions(+), 3 deletions(-) diff --git a/DESCRIPTION b/DESCRIPTION index c438d3b43..3e272a210 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -1,6 +1,6 @@ Package: vctrs Title: Vector Helpers -Version: 0.4.2.9000 +Version: 0.5.0 Authors@R: c(person(given = "Hadley", family = "Wickham", diff --git a/NEWS.md b/NEWS.md index 6ece9d138..7df5da704 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,4 +1,4 @@ -# vctrs (development version) +# vctrs 0.5.0 * vctrs is now compliant with `-Wstrict-prototypes` as requested by CRAN (#1729). diff --git a/src/version.c b/src/version.c index ec627bdac..3927266bc 100644 --- a/src/version.c +++ b/src/version.c @@ -1,7 +1,7 @@ #define R_NO_REMAP #include -const char* vctrs_version = "0.4.2.9000"; +const char* vctrs_version = "0.5.0"; /** * This file records the expected package version in the shared From fb238a14a7c7e602fc81365ea29b459f128b17c1 Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Mon, 24 Oct 2022 13:24:56 +0200 Subject: [PATCH 196/312] Increment version number to 0.5.0.9000 --- DESCRIPTION | 2 +- NEWS.md | 2 ++ src/version.c | 2 +- 3 files changed, 4 insertions(+), 2 deletions(-) diff --git a/DESCRIPTION b/DESCRIPTION index 3e272a210..c5787ceae 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -1,6 +1,6 @@ Package: vctrs Title: Vector Helpers -Version: 0.5.0 +Version: 0.5.0.9000 Authors@R: c(person(given = "Hadley", family = "Wickham", diff --git a/NEWS.md b/NEWS.md index 7df5da704..d384f15cc 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,3 +1,5 @@ +# vctrs (development version) + # vctrs 0.5.0 * vctrs is now compliant with `-Wstrict-prototypes` as requested by CRAN diff --git a/src/version.c b/src/version.c index 3927266bc..41ae1263f 100644 --- a/src/version.c +++ b/src/version.c @@ -1,7 +1,7 @@ #define R_NO_REMAP #include -const char* vctrs_version = "0.5.0"; +const char* vctrs_version = "0.5.0.9000"; /** * This file records the expected package version in the shared From 57c99a93935735191d63a3ec2dcf5da35b85d7b8 Mon Sep 17 00:00:00 2001 From: DavisVaughan Date: Mon, 31 Oct 2022 11:00:30 -0400 Subject: [PATCH 197/312] Fix two typos --- R/type2.R | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/R/type2.R b/R/type2.R index 74d9fe575..b694364ba 100644 --- a/R/type2.R +++ b/R/type2.R @@ -211,7 +211,7 @@ can_fall_back <- function(x) { #' @export can_fall_back.vctrs_vctr <- function(x) { - # Work aronud bad interaction when `c()` method calls back into `vec_c()` + # Work around bad interaction when `c()` method calls back into `vec_c()` FALSE } #' @export @@ -232,7 +232,7 @@ can_fall_back.data.frame <- function(x) { #' @export can_fall_back.default <- function(x) { - # Don't all back for classes that directly implement a proxy. + # Don't fall back for classes that directly implement a proxy. # # NOTE: That's suboptimal. For instance this forces us to override # `can_fall_back()` for `vctrs_vctr` to avoid recursing into From ece04d3b8d7d6974c8e0b15ab540969a741ce201 Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Wed, 2 Nov 2022 11:35:47 +0100 Subject: [PATCH 198/312] Update test description --- tests/testthat/test-type-dplyr.R | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/tests/testthat/test-type-dplyr.R b/tests/testthat/test-type-dplyr.R index c1795cf4e..5e31a5461 100644 --- a/tests/testthat/test-type-dplyr.R +++ b/tests/testthat/test-type-dplyr.R @@ -162,7 +162,7 @@ test_that("can cbind rowwise data frames", { expect_identical(vec_cbind(rww, gdf), exp) }) -test_that("no common type between rowwise and grouped data frames", { +test_that("common type between rowwise and grouped data frames is a bare df", { out <- vec_ptype_common(dplyr::rowwise(bare_mtcars), dplyr::group_by(bare_mtcars, cyl)) expect_identical(out, tibble::as_tibble(bare_mtcars[0, ])) }) From 9a8ae85a2a93da3a57ff2b8a4f6c522a37d9059c Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Mon, 14 Nov 2022 13:25:22 +0100 Subject: [PATCH 199/312] Fix slice-assign test for names with POSIXlt (#1744) --- NEWS.md | 3 +++ tests/testthat/test-slice-assign.R | 38 +++++++++++++++++++++--------- 2 files changed, 30 insertions(+), 11 deletions(-) diff --git a/NEWS.md b/NEWS.md index d384f15cc..85335a20e 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,5 +1,8 @@ # vctrs (development version) +* Fix for CRAN checks. + + # vctrs 0.5.0 * vctrs is now compliant with `-Wstrict-prototypes` as requested by CRAN diff --git a/tests/testthat/test-slice-assign.R b/tests/testthat/test-slice-assign.R index eb7963eb4..d2c56ecfd 100644 --- a/tests/testthat/test-slice-assign.R +++ b/tests/testthat/test-slice-assign.R @@ -530,14 +530,6 @@ test_that("can optionally assign names", { vec_out ) - oo_x <- set_names(as_posixlt(c("2020-01-01", "2020-01-02", "2020-01-03")), letters[1:3]) - oo_y <- as_posixlt(c(FOO = "2020-01-04")) - oo_out <- as_posixlt(c(a = "2020-01-01", FOO = "2020-01-04", c = "2020-01-03")) - expect_identical( - vec_assign_params(oo_x, 2, oo_y, assign_names = TRUE), - oo_out - ) - df_x <- new_data_frame(list(x = 1:3), row.names = letters[1:3]) df_y <- new_data_frame(list(x = 4L), row.names = "FOO") df_out <- new_data_frame(list(x = c(1L, 4L, 3L)), row.names = c("a", "FOO", "c")) @@ -554,9 +546,33 @@ test_that("can optionally assign names", { mat_out ) - nested_x <- new_data_frame(list(df = df_x, mat = mat_x, vec = vec_x, oo = oo_x), row.names = c("foo", "bar", "baz")) - nested_y <- new_data_frame(list(df = df_y, mat = mat_y, vec = vec_y, oo = oo_y), row.names = c("quux")) - nested_out <- new_data_frame(list(df = df_out, mat = mat_out, vec = vec_out, oo = oo_out), row.names = c("foo", "quux", "baz")) + nested_x <- new_data_frame(list(df = df_x, mat = mat_x, vec = vec_x), row.names = c("foo", "bar", "baz")) + nested_y <- new_data_frame(list(df = df_y, mat = mat_y, vec = vec_y), row.names = c("quux")) + nested_out <- new_data_frame(list(df = df_out, mat = mat_out, vec = vec_out), row.names = c("foo", "quux", "baz")) + + expect_identical( + vec_assign_params(nested_x, 2, nested_y, assign_names = TRUE), + nested_out + ) +}) + +test_that("can optionally assign names (OO case)", { + # In case upstream attributes handling changes + skip_on_cran() + + # `set_names()` must be on the inside, otherwise the POSIXlt object + # gets a `balanced` attribute of `NA` + oo_x <- as_posixlt(set_names(c("2020-01-01", "2020-01-02", "2020-01-03"), letters[1:3])) + oo_y <- as_posixlt(c(FOO = "2020-01-04")) + oo_out <- as_posixlt(c(a = "2020-01-01", FOO = "2020-01-04", c = "2020-01-03")) + expect_identical( + vec_assign_params(oo_x, 2, oo_y, assign_names = TRUE), + oo_out + ) + + nested_x <- new_data_frame(list(oo = oo_x), row.names = c("foo", "bar", "baz")) + nested_y <- new_data_frame(list(oo = oo_y), row.names = c("quux")) + nested_out <- new_data_frame(list(oo = oo_out), row.names = c("foo", "quux", "baz")) expect_identical( vec_assign_params(nested_x, 2, nested_y, assign_names = TRUE), From c35a9163833ec12a74022b1b66c3fbc523c51a71 Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Mon, 14 Nov 2022 13:26:53 +0100 Subject: [PATCH 200/312] Increment version number to 0.5.1 --- DESCRIPTION | 2 +- NEWS.md | 2 +- cran-comments.md | 12 +----------- src/version.c | 2 +- 4 files changed, 4 insertions(+), 14 deletions(-) diff --git a/DESCRIPTION b/DESCRIPTION index c5787ceae..2a12c7a4c 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -1,6 +1,6 @@ Package: vctrs Title: Vector Helpers -Version: 0.5.0.9000 +Version: 0.5.1 Authors@R: c(person(given = "Hadley", family = "Wickham", diff --git a/NEWS.md b/NEWS.md index 85335a20e..2a43c5335 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,4 +1,4 @@ -# vctrs (development version) +# vctrs 0.5.1 * Fix for CRAN checks. diff --git a/cran-comments.md b/cran-comments.md index 56688d3a0..3585fd769 100644 --- a/cran-comments.md +++ b/cran-comments.md @@ -1,11 +1 @@ -## R CMD check results - -0 errors | 0 warnings | 0 notes - - -## revdepcheck results - -We checked 175 reverse dependencies (171 from CRAN + 4 from Bioconductor), comparing R CMD check results across CRAN and dev versions of this package. - - * We saw 0 new problems - * We failed to check 0 packages +Fixes the failure with R-devel. diff --git a/src/version.c b/src/version.c index 41ae1263f..a8da097ff 100644 --- a/src/version.c +++ b/src/version.c @@ -1,7 +1,7 @@ #define R_NO_REMAP #include -const char* vctrs_version = "0.5.0.9000"; +const char* vctrs_version = "0.5.1"; /** * This file records the expected package version in the shared From 48794fd3e486ed3bca7fc3842f625d01eb02ed6b Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Wed, 16 Nov 2022 16:46:09 +0100 Subject: [PATCH 201/312] Increment version number to 0.5.1.9000 --- DESCRIPTION | 2 +- NEWS.md | 2 ++ src/version.c | 2 +- 3 files changed, 4 insertions(+), 2 deletions(-) diff --git a/DESCRIPTION b/DESCRIPTION index 2a12c7a4c..d33cb2623 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -1,6 +1,6 @@ Package: vctrs Title: Vector Helpers -Version: 0.5.1 +Version: 0.5.1.9000 Authors@R: c(person(given = "Hadley", family = "Wickham", diff --git a/NEWS.md b/NEWS.md index 2a43c5335..266c9a46f 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,3 +1,5 @@ +# vctrs (development version) + # vctrs 0.5.1 * Fix for CRAN checks. diff --git a/src/version.c b/src/version.c index a8da097ff..573a574a3 100644 --- a/src/version.c +++ b/src/version.c @@ -1,7 +1,7 @@ #define R_NO_REMAP #include -const char* vctrs_version = "0.5.1"; +const char* vctrs_version = "0.5.1.9000"; /** * This file records the expected package version in the shared From 0f8212c5ba1505f60f423c18bb31b91d478796b1 Mon Sep 17 00:00:00 2001 From: DavisVaughan Date: Thu, 15 Dec 2022 16:59:46 -0500 Subject: [PATCH 202/312] Update GitHub Actions workflows --- .github/workflows/R-CMD-check.yaml | 19 ++++++++++--------- .github/workflows/pkgdown.yaml | 4 ++-- .github/workflows/pr-commands.yaml | 4 ++-- .github/workflows/test-coverage.yaml | 23 +++++++++++++++++++++-- 4 files changed, 35 insertions(+), 15 deletions(-) diff --git a/.github/workflows/R-CMD-check.yaml b/.github/workflows/R-CMD-check.yaml index 4efedd965..ee65ccb57 100644 --- a/.github/workflows/R-CMD-check.yaml +++ b/.github/workflows/R-CMD-check.yaml @@ -22,26 +22,27 @@ jobs: fail-fast: false matrix: config: - - {os: macOS-latest, r: 'release'} + - {os: macos-latest, r: 'release'} - {os: windows-latest, r: 'release'} # Use 3.6 to trigger usage of RTools35 - {os: windows-latest, r: '3.6'} + # use 4.1 to check with rtools40's older compiler + - {os: windows-latest, r: '4.1'} - # Use older ubuntu to maximise backward compatibility - - {os: ubuntu-18.04, r: 'devel', http-user-agent: 'release'} - - {os: ubuntu-18.04, r: 'release'} - - {os: ubuntu-18.04, r: 'oldrel-1'} - - {os: ubuntu-18.04, r: 'oldrel-2'} - - {os: ubuntu-18.04, r: 'oldrel-3'} - - {os: ubuntu-18.04, r: 'oldrel-4'} + - {os: ubuntu-latest, r: 'devel', http-user-agent: 'release'} + - {os: ubuntu-latest, r: 'release'} + - {os: ubuntu-latest, r: 'oldrel-1'} + - {os: ubuntu-latest, r: 'oldrel-2'} + - {os: ubuntu-latest, r: 'oldrel-3'} + - {os: ubuntu-latest, r: 'oldrel-4'} env: GITHUB_PAT: ${{ secrets.GITHUB_TOKEN }} R_KEEP_PKG_SOURCE: yes steps: - - uses: actions/checkout@v2 + - uses: actions/checkout@v3 - uses: r-lib/actions/setup-pandoc@v2 diff --git a/.github/workflows/pkgdown.yaml b/.github/workflows/pkgdown.yaml index 0b2602168..087f0b05f 100644 --- a/.github/workflows/pkgdown.yaml +++ b/.github/workflows/pkgdown.yaml @@ -20,7 +20,7 @@ jobs: env: GITHUB_PAT: ${{ secrets.GITHUB_TOKEN }} steps: - - uses: actions/checkout@v2 + - uses: actions/checkout@v3 - uses: r-lib/actions/setup-pandoc@v2 @@ -39,7 +39,7 @@ jobs: - name: Deploy to GitHub pages 🚀 if: github.event_name != 'pull_request' - uses: JamesIves/github-pages-deploy-action@4.1.4 + uses: JamesIves/github-pages-deploy-action@v4.4.1 with: clean: false branch: gh-pages diff --git a/.github/workflows/pr-commands.yaml b/.github/workflows/pr-commands.yaml index 97271eb29..71f335b3e 100644 --- a/.github/workflows/pr-commands.yaml +++ b/.github/workflows/pr-commands.yaml @@ -14,7 +14,7 @@ jobs: env: GITHUB_PAT: ${{ secrets.GITHUB_TOKEN }} steps: - - uses: actions/checkout@v2 + - uses: actions/checkout@v3 - uses: r-lib/actions/pr-fetch@v2 with: @@ -51,7 +51,7 @@ jobs: env: GITHUB_PAT: ${{ secrets.GITHUB_TOKEN }} steps: - - uses: actions/checkout@v2 + - uses: actions/checkout@v3 - uses: r-lib/actions/pr-fetch@v2 with: diff --git a/.github/workflows/test-coverage.yaml b/.github/workflows/test-coverage.yaml index 4b6541829..2c5bb5029 100644 --- a/.github/workflows/test-coverage.yaml +++ b/.github/workflows/test-coverage.yaml @@ -15,7 +15,7 @@ jobs: GITHUB_PAT: ${{ secrets.GITHUB_TOKEN }} steps: - - uses: actions/checkout@v2 + - uses: actions/checkout@v3 - uses: r-lib/actions/setup-r@v2 with: @@ -27,5 +27,24 @@ jobs: needs: coverage - name: Test coverage - run: covr::codecov(quiet = FALSE) + run: | + covr::codecov( + quiet = FALSE, + clean = FALSE, + install_path = file.path(Sys.getenv("RUNNER_TEMP"), "package") + ) shell: Rscript {0} + + - name: Show testthat output + if: always() + run: | + ## -------------------------------------------------------------------- + find ${{ runner.temp }}/package -name 'testthat.Rout*' -exec cat '{}' \; || true + shell: bash + + - name: Upload test results + if: failure() + uses: actions/upload-artifact@v3 + with: + name: coverage-test-failures + path: ${{ runner.temp }}/package From 2d7de765c93cd91ac2fe1a8c820aa0ddf40643d2 Mon Sep 17 00:00:00 2001 From: Davis Vaughan Date: Thu, 15 Dec 2022 18:26:44 -0400 Subject: [PATCH 203/312] Call `vec_proxy_order()` with arrays, which aren't objects (#1754) * Call `vec_proxy_order()` with arrays, which aren't objects * NEWS bullet --- NEWS.md | 3 ++ src/order.c | 4 +-- tests/testthat/_snaps/order.md | 16 ++++++++++ tests/testthat/test-order.R | 54 ++++++++++++++++++++++++++++++++++ 4 files changed, 75 insertions(+), 2 deletions(-) diff --git a/NEWS.md b/NEWS.md index 266c9a46f..39ef17148 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,5 +1,8 @@ # vctrs (development version) +* Fixed a bug with the internal `vec_order_radix()` function related to matrix + columns (#1753). + # vctrs 0.5.1 * Fix for CRAN checks. diff --git a/src/order.c b/src/order.c index c87599fd6..cb7e48783 100644 --- a/src/order.c +++ b/src/order.c @@ -4519,8 +4519,8 @@ static int df_decreasing_expansion(SEXP x); static int vec_decreasing_expansion(SEXP x) { - // Bare columns - if (!OBJECT(x)) { + // Bare vectors + if (!OBJECT(x) && !has_dim(x)) { return 1; } diff --git a/tests/testthat/_snaps/order.md b/tests/testthat/_snaps/order.md index 068598e9f..cfbe1959c 100644 --- a/tests/testthat/_snaps/order.md +++ b/tests/testthat/_snaps/order.md @@ -1,3 +1,19 @@ +# `direction` is recycled right with array columns (#1753) + + Code + vec_order_radix(df, direction = c("asc", "desc", "desc")) + Condition + Error: + ! `direction` should have length 1 or length equal to the number of columns of `x` when `x` is a data frame. + +# `na_value` is recycled right with array columns (#1753) + + Code + vec_order_radix(df, direction = c("smallest", "largest", "largest")) + Condition + Error: + ! `direction` must contain only "asc" or "desc". + # dots must be empty (#1647) Code diff --git a/tests/testthat/test-order.R b/tests/testthat/test-order.R index 13014fb0d..d64cd5ebb 100644 --- a/tests/testthat/test-order.R +++ b/tests/testthat/test-order.R @@ -885,6 +885,60 @@ test_that("`na_value` and `direction` can both be vectors", { ) }) +test_that("`direction` is recycled right with array columns (#1753)", { + df <- data_frame( + x = matrix(c(1, 1, 1, 3, 2, 2), ncol = 2), + y = 3:1 + ) + expect_identical( + vec_order_radix(df, direction = c("asc", "desc")), + c(2L, 3L, 1L) + ) + expect_snapshot(error = TRUE, { + vec_order_radix(df, direction = c("asc", "desc", "desc")) + }) + + df <- data_frame( + x = array(c(1, 1, 1, 2, 2, 2, 3, 3, 3, 4, 3, 3), dim = c(3, 2, 2)), + y = 3:1 + ) + expect_identical( + vec_order_radix(df, direction = c("asc", "desc")), + c(2L, 3L, 1L) + ) +}) + +test_that("`na_value` is recycled right with array columns (#1753)", { + df <- data_frame( + x = matrix(c(1, 1, 1, 3, NA, 2), ncol = 2), + y = 3:1 + ) + expect_identical( + vec_order_radix(df, na_value = c("largest", "smallest")), + c(3L, 1L, 2L) + ) + expect_identical( + vec_order_radix(df, na_value = c("smallest", "largest")), + c(2L, 3L, 1L) + ) + expect_snapshot(error = TRUE, { + vec_order_radix(df, direction = c("smallest", "largest", "largest")) + }) + + df <- data_frame( + x = array(c(1, 1, 1, 2, 2, 2, 3, 3, 3, 4, NA, 3), dim = c(3, 2, 2)), + y = 3:1 + ) + expect_identical( + vec_order_radix(df, na_value = c("largest", "smallest")), + c(3L, 1L, 2L) + ) + expect_identical( + vec_order_radix(df, na_value = c("smallest", "largest")), + c(2L, 3L, 1L) + ) +}) + # ------------------------------------------------------------------------------ # vec_order_radix() - counting From cc78d5c1d63257f442d65f4b45985606bb060b13 Mon Sep 17 00:00:00 2001 From: Davis Vaughan Date: Wed, 21 Dec 2022 12:17:27 -0400 Subject: [PATCH 204/312] Fix incorrect `sizeof()` type (#1756) --- src/dictionary.c | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/dictionary.c b/src/dictionary.c index 0fa7b3fa2..17f2ac8c7 100644 --- a/src/dictionary.c +++ b/src/dictionary.c @@ -98,7 +98,7 @@ static struct dictionary* new_dictionary_opts(SEXP x, struct dictionary_opts* op Rf_errorcall(R_NilValue, "Can't allocate hash lookup table. Please free memory."); } - memset(d->hash, 0, n * sizeof(R_len_t)); + memset(d->hash, 0, n * sizeof(uint32_t)); hash_fill(d->hash, n, x, opts->na_equal); } else { d->hash = NULL; From b077069af51030df1b1cdd859e6c8bb90e80e1e6 Mon Sep 17 00:00:00 2001 From: Davis Vaughan Date: Wed, 21 Dec 2022 12:18:35 -0400 Subject: [PATCH 205/312] Don't `memset()` with `DICT_EMPTY` (#1757) --- src/dictionary.c | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/src/dictionary.c b/src/dictionary.c index 17f2ac8c7..8c83c34be 100644 --- a/src/dictionary.c +++ b/src/dictionary.c @@ -85,7 +85,10 @@ static struct dictionary* new_dictionary_opts(SEXP x, struct dictionary_opts* op uint32_t size = dict_key_size(x); d->key = (R_len_t*) R_alloc(size, sizeof(R_len_t)); - memset(d->key, DICT_EMPTY, size * sizeof(R_len_t)); + + for (uint32_t i = 0; i < size; ++i) { + d->key[i] = DICT_EMPTY; + } d->size = size; } From 65df197a928edeac5cbb568376b1e0bdd42d13cf Mon Sep 17 00:00:00 2001 From: Davis Vaughan Date: Wed, 21 Dec 2022 13:23:18 -0400 Subject: [PATCH 206/312] Implement `vec_set_*()` family (#1755) * Implement hash based `vec_set_intersect()` * Implement sort based `vec_set_intersect()` * Revert "Implement sort based `vec_set_intersect()`" This reverts commit bc1c382d01173a8800ede2cf59c0fe06f8c770d2. * Don't accidentally write outside `v_loc` * Implement `vec_set_difference()` and `vec_set_union()` And document, export, and further test all of them * NEWS bullet * Full pass through the set docs based on code review feedback --- NAMESPACE | 3 + NEWS.md | 4 + R/set.R | 139 ++++++++++++ _pkgdown.yml | 3 +- man/vec-set.Rd | 151 +++++++++++++ src/decl/set-decl.h | 0 src/init.c | 6 + src/set.c | 426 +++++++++++++++++++++++++++++++++++ src/set.h | 27 +++ src/vctrs.h | 1 + tests/testthat/_snaps/set.md | 140 ++++++++++++ tests/testthat/test-set.R | 325 ++++++++++++++++++++++++++ 12 files changed, 1224 insertions(+), 1 deletion(-) create mode 100644 R/set.R create mode 100644 man/vec-set.Rd create mode 100644 src/decl/set-decl.h create mode 100644 src/set.c create mode 100644 src/set.h create mode 100644 tests/testthat/_snaps/set.md create mode 100644 tests/testthat/test-set.R diff --git a/NAMESPACE b/NAMESPACE index e752736e0..f592e9fae 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -618,7 +618,10 @@ export(vec_rep_each) export(vec_repeat) export(vec_restore) export(vec_seq_along) +export(vec_set_difference) +export(vec_set_intersect) export(vec_set_names) +export(vec_set_union) export(vec_size) export(vec_size_common) export(vec_slice) diff --git a/NEWS.md b/NEWS.md index 39ef17148..36515ed45 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,5 +1,9 @@ # vctrs (development version) +* New `vec_set_intersect()`, `vec_set_difference()`, and `vec_set_union()` which + compute set operations like `intersect()`, `setdiff()`, and `union()`, but + the vctrs variants don't strip attributes and work with data frames (#1755). + * Fixed a bug with the internal `vec_order_radix()` function related to matrix columns (#1753). diff --git a/R/set.R b/R/set.R new file mode 100644 index 000000000..fd9073572 --- /dev/null +++ b/R/set.R @@ -0,0 +1,139 @@ +#' Set operations +#' +#' @description +#' - `vec_set_intersect()` returns all values in both `x` and `y`. +#' +#' - `vec_set_difference()` returns all values in `x` but not `y`. Note +#' that this is an asymmetric set difference, meaning it is not commutative. +#' +#' - `vec_set_union()` returns all values in either `x` or `y`. +#' +#' Because these are _set_ operations, these functions only return unique values +#' from `x` and `y`, returned in the order they first appeared in the original +#' input. Names of `x` and `y` are retained on the result, but names are always +#' taken from `x` if the value appears in both inputs. +#' +#' These functions work similarly to [intersect()], [setdiff()], and [union()], +#' but don't strip attributes and can be used with data frames. +#' +#' @inheritParams rlang::args_dots_empty +#' @inheritParams rlang::args_error_context +#' +#' @param x,y A pair of vectors. +#' +#' @param ptype If `NULL`, the default, the output type is determined by +#' computing the common type between `x` and `y`. If supplied, both `x` and +#' `y` will be cast to this type. +#' +#' @param x_arg,y_arg Argument names for `x` and `y`. These are used in error +#' messages. +#' +#' @returns +#' A vector of the common type of `x` and `y` (or `ptype`, if supplied) +#' containing the result of the corresponding set function. +#' +#' @details +#' Missing values are treated as equal to other missing values. For doubles and +#' complexes, `NaN` are equal to other `NaN`, but not to `NA`. +#' +#' @section Dependencies: +#' +#' ## `vec_set_intersect()` +#' - [vec_proxy_equal()] +#' - [vec_slice()] +#' - [vec_ptype2()] +#' - [vec_cast()] +#' +#' ## `vec_set_difference()` +#' - [vec_proxy_equal()] +#' - [vec_slice()] +#' - [vec_ptype2()] +#' - [vec_cast()] +#' +#' ## `vec_set_union()` +#' - [vec_proxy_equal()] +#' - [vec_slice()] +#' - [vec_ptype2()] +#' - [vec_cast()] +#' - [vec_c()] +#' +#' @name vec-set +#' @examples +#' x <- c(1, 2, 1, 4, 3) +#' y <- c(2, 5, 5, 1) +#' +#' # All unique values in both `x` and `y`. +#' # Duplicates in `x` and `y` are always removed. +#' vec_set_intersect(x, y) +#' +#' # All unique values in `x` but not `y` +#' vec_set_difference(x, y) +#' +#' # All unique values in either `x` or `y` +#' vec_set_union(x, y) +#' +#' # These functions can also be used with data frames +#' x <- data_frame( +#' a = c(2, 3, 2, 2), +#' b = c("j", "k", "j", "l") +#' ) +#' y <- data_frame( +#' a = c(1, 2, 2, 2, 3), +#' b = c("j", "l", "j", "l", "j") +#' ) +#' +#' vec_set_intersect(x, y) +#' vec_set_difference(x, y) +#' vec_set_union(x, y) +#' +#' # Vector names don't affect set membership, but if you'd like to force +#' # them to, you can transform the vector into a two column data frame +#' x <- c(a = 1, b = 2, c = 2, d = 3) +#' y <- c(c = 2, b = 1, a = 3, d = 3) +#' +#' vec_set_intersect(x, y) +#' +#' x <- data_frame(name = names(x), value = unname(x)) +#' y <- data_frame(name = names(y), value = unname(y)) +#' +#' vec_set_intersect(x, y) +NULL + +#' @rdname vec-set +#' @export +vec_set_intersect <- function(x, + y, + ..., + ptype = NULL, + x_arg = "x", + y_arg = "y", + error_call = current_env()) { + check_dots_empty0(...) + .Call(ffi_vec_set_intersect, x, y, ptype, environment()) +} + +#' @rdname vec-set +#' @export +vec_set_difference <- function(x, + y, + ..., + ptype = NULL, + x_arg = "x", + y_arg = "y", + error_call = current_env()) { + check_dots_empty0(...) + .Call(ffi_vec_set_difference, x, y, ptype, environment()) +} + +#' @rdname vec-set +#' @export +vec_set_union <- function(x, + y, + ..., + ptype = NULL, + x_arg = "x", + y_arg = "y", + error_call = current_env()) { + check_dots_empty0(...) + .Call(ffi_vec_set_union, x, y, ptype, environment()) +} diff --git a/_pkgdown.yml b/_pkgdown.yml index 1efe6962c..51a999d44 100644 --- a/_pkgdown.yml +++ b/_pkgdown.yml @@ -9,7 +9,7 @@ template: includes: in_header: | - + reference: - title: User FAQ @@ -85,6 +85,7 @@ reference: - vec_unique - vec_in - vec_locate_matches + - vec_set_intersect - vec_split - title: Sequences and repetitions diff --git a/man/vec-set.Rd b/man/vec-set.Rd new file mode 100644 index 000000000..daf77002a --- /dev/null +++ b/man/vec-set.Rd @@ -0,0 +1,151 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/set.R +\name{vec-set} +\alias{vec-set} +\alias{vec_set_intersect} +\alias{vec_set_difference} +\alias{vec_set_union} +\title{Set operations} +\usage{ +vec_set_intersect( + x, + y, + ..., + ptype = NULL, + x_arg = "x", + y_arg = "y", + error_call = current_env() +) + +vec_set_difference( + x, + y, + ..., + ptype = NULL, + x_arg = "x", + y_arg = "y", + error_call = current_env() +) + +vec_set_union( + x, + y, + ..., + ptype = NULL, + x_arg = "x", + y_arg = "y", + error_call = current_env() +) +} +\arguments{ +\item{x, y}{A pair of vectors.} + +\item{...}{These dots are for future extensions and must be empty.} + +\item{ptype}{If \code{NULL}, the default, the output type is determined by +computing the common type between \code{x} and \code{y}. If supplied, both \code{x} and +\code{y} will be cast to this type.} + +\item{x_arg, y_arg}{Argument names for \code{x} and \code{y}. These are used in error +messages.} + +\item{error_call}{The execution environment of a currently +running function, e.g. \code{caller_env()}. The function will be +mentioned in error messages as the source of the error. See the +\code{call} argument of \code{\link[rlang:abort]{abort()}} for more information.} +} +\value{ +A vector of the common type of \code{x} and \code{y} (or \code{ptype}, if supplied) +containing the result of the corresponding set function. +} +\description{ +\itemize{ +\item \code{vec_set_intersect()} returns all values in both \code{x} and \code{y}. +\item \code{vec_set_difference()} returns all values in \code{x} but not \code{y}. Note +that this is an asymmetric set difference, meaning it is not commutative. +\item \code{vec_set_union()} returns all values in either \code{x} or \code{y}. +} + +Because these are \emph{set} operations, these functions only return unique values +from \code{x} and \code{y}, returned in the order they first appeared in the original +input. Names of \code{x} and \code{y} are retained on the result, but names are always +taken from \code{x} if the value appears in both inputs. + +These functions work similarly to \code{\link[=intersect]{intersect()}}, \code{\link[=setdiff]{setdiff()}}, and \code{\link[=union]{union()}}, +but don't strip attributes and can be used with data frames. +} +\details{ +Missing values are treated as equal to other missing values. For doubles and +complexes, \code{NaN} are equal to other \code{NaN}, but not to \code{NA}. +} +\section{Dependencies}{ + +\subsection{\code{vec_set_intersect()}}{ +\itemize{ +\item \code{\link[=vec_proxy_equal]{vec_proxy_equal()}} +\item \code{\link[=vec_slice]{vec_slice()}} +\item \code{\link[=vec_ptype2]{vec_ptype2()}} +\item \code{\link[=vec_cast]{vec_cast()}} +} +} + +\subsection{\code{vec_set_difference()}}{ +\itemize{ +\item \code{\link[=vec_proxy_equal]{vec_proxy_equal()}} +\item \code{\link[=vec_slice]{vec_slice()}} +\item \code{\link[=vec_ptype2]{vec_ptype2()}} +\item \code{\link[=vec_cast]{vec_cast()}} +} +} + +\subsection{\code{vec_set_union()}}{ +\itemize{ +\item \code{\link[=vec_proxy_equal]{vec_proxy_equal()}} +\item \code{\link[=vec_slice]{vec_slice()}} +\item \code{\link[=vec_ptype2]{vec_ptype2()}} +\item \code{\link[=vec_cast]{vec_cast()}} +\item \code{\link[=vec_c]{vec_c()}} +} +} +} + +\examples{ +x <- c(1, 2, 1, 4, 3) +y <- c(2, 5, 5, 1) + +# All unique values in both `x` and `y`. +# Duplicates in `x` and `y` are always removed. +vec_set_intersect(x, y) + +# All unique values in `x` but not `y` +vec_set_difference(x, y) + +# All unique values in either `x` or `y` +vec_set_union(x, y) + +# These functions can also be used with data frames +x <- data_frame( + a = c(2, 3, 2, 2), + b = c("j", "k", "j", "l") +) +y <- data_frame( + a = c(1, 2, 2, 2, 3), + b = c("j", "l", "j", "l", "j") +) + +vec_set_intersect(x, y) +vec_set_difference(x, y) +vec_set_union(x, y) + +# Vector names don't affect set membership, but if you'd like to force +# them to, you can transform the vector into a two column data frame +x <- c(a = 1, b = 2, c = 2, d = 3) +y <- c(c = 2, b = 1, a = 3, d = 3) + +vec_set_intersect(x, y) + +x <- data_frame(name = names(x), value = unname(x)) +y <- data_frame(name = names(y), value = unname(y)) + +vec_set_intersect(x, y) +} diff --git a/src/decl/set-decl.h b/src/decl/set-decl.h new file mode 100644 index 000000000..e69de29bb diff --git a/src/init.c b/src/init.c index cbff4f412..8a504cc1b 100644 --- a/src/init.c +++ b/src/init.c @@ -152,6 +152,9 @@ extern r_obj* ffi_as_short_length(r_obj*, r_obj*); extern r_obj* ffi_s3_get_method(r_obj*, r_obj*, r_obj*); extern r_obj* ffi_list_all_size(r_obj*, r_obj*, r_obj*); extern r_obj* ffi_list_check_all_size(r_obj*, r_obj*, r_obj*); +extern r_obj* ffi_vec_set_intersect(r_obj*, r_obj*, r_obj*, r_obj*); +extern r_obj* ffi_vec_set_difference(r_obj*, r_obj*, r_obj*, r_obj*); +extern r_obj* ffi_vec_set_union(r_obj*, r_obj*, r_obj*, r_obj*); // Maturing @@ -327,6 +330,9 @@ static const R_CallMethodDef CallEntries[] = { {"ffi_s3_get_method", (DL_FUNC) &ffi_s3_get_method, 3}, {"ffi_list_all_size", (DL_FUNC) &ffi_list_all_size, 3}, {"ffi_list_check_all_size", (DL_FUNC) &ffi_list_check_all_size, 3}, + {"ffi_vec_set_intersect", (DL_FUNC) &ffi_vec_set_intersect, 4}, + {"ffi_vec_set_difference", (DL_FUNC) &ffi_vec_set_difference, 4}, + {"ffi_vec_set_union", (DL_FUNC) &ffi_vec_set_union, 4}, {"ffi_exp_vec_cast", (DL_FUNC) &exp_vec_cast, 2}, {NULL, NULL, 0} }; diff --git a/src/set.c b/src/set.c new file mode 100644 index 000000000..6b72d5782 --- /dev/null +++ b/src/set.c @@ -0,0 +1,426 @@ +#include "vctrs.h" + +#include "decl/set-decl.h" + +r_obj* ffi_vec_set_intersect(r_obj* x, + r_obj* y, + r_obj* ptype, + r_obj* frame) { + struct r_lazy call = { .x = r_syms.error_call, .env = frame }; + + struct r_lazy x_arg_lazy = { .x = syms.x_arg, .env = frame }; + struct vctrs_arg x_arg = new_lazy_arg(&x_arg_lazy); + + struct r_lazy y_arg_lazy = { .x = syms.y_arg, .env = frame }; + struct vctrs_arg y_arg = new_lazy_arg(&y_arg_lazy); + + return vec_set_intersect(x, y, ptype, &x_arg, &y_arg, call); +} + +r_obj* vec_set_intersect(r_obj* x, + r_obj* y, + r_obj* ptype, + struct vctrs_arg* x_arg, + struct vctrs_arg* y_arg, + struct r_lazy call) { + int n_prot = 0; + + if (ptype == r_null) { + int _; + + ptype = vec_ptype2_params( + x, + y, + x_arg, + y_arg, + call, + &_ + ); + KEEP_N(ptype, &n_prot); + + ptype = vec_ptype_finalise(ptype); + KEEP_N(ptype, &n_prot); + } + + x = vec_cast_params( + x, + ptype, + x_arg, + vec_args.empty, + call, + S3_FALLBACK_false + ); + KEEP_N(x, &n_prot); + + y = vec_cast_params( + y, + ptype, + y_arg, + vec_args.empty, + call, + S3_FALLBACK_false + ); + KEEP_N(y, &n_prot); + + r_obj* x_proxy = KEEP_N(vec_proxy_equal(x), &n_prot); + x_proxy = KEEP_N(vec_normalize_encoding(x_proxy), &n_prot); + + r_obj* y_proxy = KEEP_N(vec_proxy_equal(y), &n_prot); + y_proxy = KEEP_N(vec_normalize_encoding(y_proxy), &n_prot); + + const r_ssize x_size = vec_size(x_proxy); + const r_ssize y_size = vec_size(y_proxy); + + struct dictionary* x_dict = new_dictionary(x_proxy); + PROTECT_DICT(x_dict, &n_prot); + + // Load dictionary with `x`. + // Key values point to first time we saw that `x` value. + for (r_ssize i = 0; i < x_size; ++i) { + const uint32_t hash = dict_hash_scalar(x_dict, i); + + if (x_dict->key[hash] == DICT_EMPTY) { + dict_put(x_dict, hash, i); + } + } + + struct dictionary* y_dict = new_dictionary_partial(y_proxy); + PROTECT_DICT(y_dict, &n_prot); + + r_obj* marked_shelter = KEEP_N(r_alloc_raw(x_size * sizeof(bool)), &n_prot); + bool* v_marked = (bool*) r_raw_begin(marked_shelter); + memset(v_marked, 0, x_size * sizeof(bool)); + + // Mark unique elements of `x` that are also in `y` + for (r_ssize i = 0; i < y_size; ++i) { + const uint32_t hash = dict_hash_with(x_dict, y_dict, i); + const r_ssize loc = x_dict->key[hash]; + + if (loc != DICT_EMPTY) { + v_marked[loc] = true; + } + } + + r_ssize n_marked = 0; + for (r_ssize i = 0; i < x_size; ++i) { + n_marked += v_marked[i]; + } + + r_obj* loc = KEEP_N(r_alloc_integer(n_marked), &n_prot); + int* v_loc = r_int_begin(loc); + r_ssize j = 0; + + for (r_ssize i = 0; i < x_size; ++i) { + if (v_marked[i]) { + v_loc[j] = i + 1; + ++j; + } + } + + r_obj* out = vec_slice_unsafe(x, loc); + + FREE(n_prot); + return out; +} + +// ----------------------------------------------------------------------------- + +r_obj* ffi_vec_set_difference(r_obj* x, + r_obj* y, + r_obj* ptype, + r_obj* frame) { + struct r_lazy call = { .x = r_syms.error_call, .env = frame }; + + struct r_lazy x_arg_lazy = { .x = syms.x_arg, .env = frame }; + struct vctrs_arg x_arg = new_lazy_arg(&x_arg_lazy); + + struct r_lazy y_arg_lazy = { .x = syms.y_arg, .env = frame }; + struct vctrs_arg y_arg = new_lazy_arg(&y_arg_lazy); + + return vec_set_difference(x, y, ptype, &x_arg, &y_arg, call); +} + +r_obj* vec_set_difference(r_obj* x, + r_obj* y, + r_obj* ptype, + struct vctrs_arg* x_arg, + struct vctrs_arg* y_arg, + struct r_lazy call) { + int n_prot = 0; + + if (ptype == r_null) { + int _; + + ptype = vec_ptype2_params( + x, + y, + x_arg, + y_arg, + call, + &_ + ); + KEEP_N(ptype, &n_prot); + + ptype = vec_ptype_finalise(ptype); + KEEP_N(ptype, &n_prot); + } + + x = vec_cast_params( + x, + ptype, + x_arg, + vec_args.empty, + call, + S3_FALLBACK_false + ); + KEEP_N(x, &n_prot); + + y = vec_cast_params( + y, + ptype, + y_arg, + vec_args.empty, + call, + S3_FALLBACK_false + ); + KEEP_N(y, &n_prot); + + r_obj* x_proxy = KEEP_N(vec_proxy_equal(x), &n_prot); + x_proxy = KEEP_N(vec_normalize_encoding(x_proxy), &n_prot); + + r_obj* y_proxy = KEEP_N(vec_proxy_equal(y), &n_prot); + y_proxy = KEEP_N(vec_normalize_encoding(y_proxy), &n_prot); + + const r_ssize x_size = vec_size(x_proxy); + const r_ssize y_size = vec_size(y_proxy); + + struct dictionary* x_dict = new_dictionary(x_proxy); + PROTECT_DICT(x_dict, &n_prot); + + r_obj* marked_shelter = KEEP_N(r_alloc_raw(x_size * sizeof(bool)), &n_prot); + bool* v_marked = (bool*) r_raw_begin(marked_shelter); + + // Load dictionary with `x`. + // Key values point to first time we saw that `x` value. + // Mark those first seen locations as potential results. + for (r_ssize i = 0; i < x_size; ++i) { + const uint32_t hash = dict_hash_scalar(x_dict, i); + const bool first_time = x_dict->key[hash] == DICT_EMPTY; + + if (first_time) { + dict_put(x_dict, hash, i); + } + + v_marked[i] = first_time; + } + + struct dictionary* y_dict = new_dictionary_partial(y_proxy); + PROTECT_DICT(y_dict, &n_prot); + + // If we've seen the `y` element in `x`, unmark it + for (r_ssize i = 0; i < y_size; ++i) { + const uint32_t hash = dict_hash_with(x_dict, y_dict, i); + const r_ssize loc = x_dict->key[hash]; + + if (loc != DICT_EMPTY) { + v_marked[loc] = false; + } + } + + r_ssize n_marked = 0; + for (r_ssize i = 0; i < x_size; ++i) { + n_marked += v_marked[i]; + } + + r_obj* loc = KEEP_N(r_alloc_integer(n_marked), &n_prot); + int* v_loc = r_int_begin(loc); + r_ssize j = 0; + + for (r_ssize i = 0; i < x_size; ++i) { + if (v_marked[i]) { + v_loc[j] = i + 1; + ++j; + } + } + + r_obj* out = vec_slice_unsafe(x, loc); + + FREE(n_prot); + return out; +} + +// ----------------------------------------------------------------------------- + +r_obj* ffi_vec_set_union(r_obj* x, + r_obj* y, + r_obj* ptype, + r_obj* frame) { + struct r_lazy call = { .x = r_syms.error_call, .env = frame }; + + struct r_lazy x_arg_lazy = { .x = syms.x_arg, .env = frame }; + struct vctrs_arg x_arg = new_lazy_arg(&x_arg_lazy); + + struct r_lazy y_arg_lazy = { .x = syms.y_arg, .env = frame }; + struct vctrs_arg y_arg = new_lazy_arg(&y_arg_lazy); + + return vec_set_union(x, y, ptype, &x_arg, &y_arg, call); +} + +r_obj* vec_set_union(r_obj* x, + r_obj* y, + r_obj* ptype, + struct vctrs_arg* x_arg, + struct vctrs_arg* y_arg, + struct r_lazy call) { + int n_prot = 0; + + if (ptype == r_null) { + int _; + + ptype = vec_ptype2_params( + x, + y, + x_arg, + y_arg, + call, + &_ + ); + KEEP_N(ptype, &n_prot); + + ptype = vec_ptype_finalise(ptype); + KEEP_N(ptype, &n_prot); + } + + x = vec_cast_params( + x, + ptype, + x_arg, + vec_args.empty, + call, + S3_FALLBACK_false + ); + KEEP_N(x, &n_prot); + + y = vec_cast_params( + y, + ptype, + y_arg, + vec_args.empty, + call, + S3_FALLBACK_false + ); + KEEP_N(y, &n_prot); + + r_obj* x_proxy = KEEP_N(vec_proxy_equal(x), &n_prot); + x_proxy = KEEP_N(vec_normalize_encoding(x_proxy), &n_prot); + + r_obj* y_proxy = KEEP_N(vec_proxy_equal(y), &n_prot); + y_proxy = KEEP_N(vec_normalize_encoding(y_proxy), &n_prot); + + const r_ssize x_size = vec_size(x_proxy); + const r_ssize y_size = vec_size(y_proxy); + + struct dictionary* x_dict = new_dictionary(x_proxy); + PROTECT_DICT(x_dict, &n_prot); + + r_obj* marked_shelter = KEEP_N(r_alloc_raw(x_size * sizeof(bool)), &n_prot); + bool* v_marked = (bool*) r_raw_begin(marked_shelter); + + // Load dictionary with `x`. + // Key values point to first time we saw that `x` value. + // Mark those first seen locations as definite results. + for (r_ssize i = 0; i < x_size; ++i) { + const uint32_t hash = dict_hash_scalar(x_dict, i); + const bool first_time = x_dict->key[hash] == DICT_EMPTY; + + if (first_time) { + dict_put(x_dict, hash, i); + } + + v_marked[i] = first_time; + } + + r_obj* loc = KEEP_N(r_alloc_integer(x_dict->used), &n_prot); + int* v_loc = r_int_begin(loc); + r_ssize j = 0; + + for (r_ssize i = 0; i < x_size; ++i) { + if (v_marked[i]) { + v_loc[j] = i + 1; + ++j; + } + } + + // Go ahead and slice out `x` + x = KEEP_N(vec_slice_unsafe(x, loc), &n_prot); + + // Resize `v_marked` for use with `y` + marked_shelter = KEEP_N(r_raw_resize(marked_shelter, y_size * sizeof(bool)), &n_prot); + v_marked = (bool*) r_raw_begin(marked_shelter); + + struct dictionary* y_dict = new_dictionary(y_proxy); + PROTECT_DICT(y_dict, &n_prot); + + // Load dictionary with `y`. + // Key values point to first time we saw that `y` value. + // Mark those first seen locations as possible results. + for (r_ssize i = 0; i < y_size; ++i) { + const uint32_t hash = dict_hash_scalar(y_dict, i); + const bool first_time = y_dict->key[hash] == DICT_EMPTY; + + if (first_time) { + dict_put(y_dict, hash, i); + } + + v_marked[i] = first_time; + } + + r_ssize n_marked = y_dict->used; + + // Check if unique elements of `y` are in `x`. If they are, unmark them. + for (r_ssize i = 0; i < y_size; ++i) { + if (!v_marked[i]) { + continue; + } + + const uint32_t hash = dict_hash_with(x_dict, y_dict, i); + const bool in_x = x_dict->key[hash] != DICT_EMPTY; + + v_marked[i] = !in_x; + n_marked -= in_x; + } + + loc = KEEP_N(r_int_resize(loc, n_marked), &n_prot); + v_loc = r_int_begin(loc); + j = 0; + + for (r_ssize i = 0; i < y_size; ++i) { + if (v_marked[i]) { + v_loc[j] = i + 1; + ++j; + } + } + + y = KEEP_N(vec_slice_unsafe(y, loc), &n_prot); + + const struct name_repair_opts name_repair_opts = { + .type = NAME_REPAIR_none, + .fn = r_null + }; + + r_obj* args = KEEP_N(r_alloc_list(2), &n_prot); + r_list_poke(args, 0, x); + r_list_poke(args, 1, y); + + r_obj* out = vec_c( + args, + ptype, + r_null, + &name_repair_opts, + vec_args.empty, + r_lazy_null + ); + + FREE(n_prot); + return out; +} diff --git a/src/set.h b/src/set.h new file mode 100644 index 000000000..ac2de4b86 --- /dev/null +++ b/src/set.h @@ -0,0 +1,27 @@ +#ifndef VCTRS_SET_H +#define VCTRS_SET_H + +#include "vctrs-core.h" + +r_obj* vec_set_intersect(r_obj* x, + r_obj* y, + r_obj* ptype, + struct vctrs_arg* x_arg, + struct vctrs_arg* y_arg, + struct r_lazy call); + +r_obj* vec_set_difference(r_obj* x, + r_obj* y, + r_obj* ptype, + struct vctrs_arg* x_arg, + struct vctrs_arg* y_arg, + struct r_lazy call); + +r_obj* vec_set_union(r_obj* x, + r_obj* y, + r_obj* ptype, + struct vctrs_arg* x_arg, + struct vctrs_arg* y_arg, + struct r_lazy call); + +#endif diff --git a/src/vctrs.h b/src/vctrs.h index 3da88ee7b..9a1fa8c86 100644 --- a/src/vctrs.h +++ b/src/vctrs.h @@ -45,6 +45,7 @@ bool vec_is_unspecified(SEXP x); #include "ptype2-dispatch.h" #include "ptype2.h" #include "runs.h" +#include "set.h" #include "shape.h" #include "size-common.h" #include "size.h" diff --git a/tests/testthat/_snaps/set.md b/tests/testthat/_snaps/set.md new file mode 100644 index 000000000..dbded808d --- /dev/null +++ b/tests/testthat/_snaps/set.md @@ -0,0 +1,140 @@ +# errors nicely if common type can't be taken + + Code + vec_set_intersect(1, "x") + Condition + Error in `vec_set_intersect()`: + ! Can't combine `x` and `y` . + +--- + + Code + vec_set_difference(1, "x") + Condition + Error in `vec_set_difference()`: + ! Can't combine `x` and `y` . + +--- + + Code + vec_set_union(1, "x") + Condition + Error in `vec_set_union()`: + ! Can't combine `x` and `y` . + +# dots must be empty + + Code + vec_set_intersect(1, 2, 3) + Condition + Error in `vec_set_intersect()`: + ! `...` must be empty. + x Problematic argument: + * ..1 = 3 + i Did you forget to name an argument? + +--- + + Code + vec_set_difference(1, 2, 3) + Condition + Error in `vec_set_difference()`: + ! `...` must be empty. + x Problematic argument: + * ..1 = 3 + i Did you forget to name an argument? + +--- + + Code + vec_set_union(1, 2, 3) + Condition + Error in `vec_set_union()`: + ! `...` must be empty. + x Problematic argument: + * ..1 = 3 + i Did you forget to name an argument? + +# `ptype` is respected + + Code + vec_set_intersect(1, 1.5, ptype = integer()) + Condition + Error in `vec_set_intersect()`: + ! Can't convert from `y` to due to loss of precision. + * Locations: 1 + +--- + + Code + vec_set_difference(1, 1.5, ptype = integer()) + Condition + Error in `vec_set_difference()`: + ! Can't convert from `y` to due to loss of precision. + * Locations: 1 + +--- + + Code + vec_set_union(1, 1.5, ptype = integer()) + Condition + Error in `vec_set_union()`: + ! Can't convert from `y` to due to loss of precision. + * Locations: 1 + +# `x_arg` and `y_arg` can be adjusted + + Code + vec_set_intersect(1, "2", x_arg = "foo", y_arg = "bar") + Condition + Error in `vec_set_intersect()`: + ! Can't combine `foo` and `bar` . + +--- + + Code + vec_set_difference(1, "2", x_arg = "foo", y_arg = "bar") + Condition + Error in `vec_set_difference()`: + ! Can't combine `foo` and `bar` . + +--- + + Code + vec_set_union(1, "2", x_arg = "foo", y_arg = "bar") + Condition + Error in `vec_set_union()`: + ! Can't combine `foo` and `bar` . + +--- + + Code + vec_set_intersect(1, "2", x_arg = "", y_arg = "") + Condition + Error in `vec_set_intersect()`: + ! Can't combine and . + +# `error_call` can be adjusted + + Code + my_set_intersect() + Condition + Error in `my_set_intersect()`: + ! Can't combine `x` and `y` . + +--- + + Code + my_set_difference() + Condition + Error in `my_set_difference()`: + ! Can't combine `x` and `y` . + +--- + + Code + my_set_union() + Condition + Error in `my_set_union()`: + ! Can't combine `x` and `y` . + diff --git a/tests/testthat/test-set.R b/tests/testthat/test-set.R new file mode 100644 index 000000000..7c177d89c --- /dev/null +++ b/tests/testthat/test-set.R @@ -0,0 +1,325 @@ +# vec_set_intersect ------------------------------------------------------- + +test_that("retains names of `x` elements", { + x <- c(a = 1, b = 4, c = 1, d = 4, e = 2) + y <- c(w = 3, x = 2, y = 1, z = 2) + + expect_identical( + vec_set_intersect(x, y), + c(a = 1, e = 2) + ) +}) + +test_that("returns elements in order they first appear in `x`", { + expect_identical(vec_set_intersect(c(3, 1, 2, 3), c(2, 3)), c(3, 2)) +}) + +test_that("returns unique elements", { + expect_identical(vec_set_intersect(c(1, 2, 1), c(2, 2, 1)), c(1, 2)) +}) + +test_that("works with character vectors of different encodings", { + encs <- encodings() + # Always returns UTF-8 + expect_identical(vec_set_intersect(encs$utf8, encs$latin1), encs$utf8) + expect_identical(vec_set_intersect(encs$latin1, encs$utf8), encs$utf8) +}) + +test_that("has consistency with `NA` values", { + expect_identical(vec_set_intersect(c(NA_real_, 1), NA_real_), NA_real_) + expect_identical(vec_set_intersect(c(1, NA_real_), NA_real_), NA_real_) + + expect_identical(vec_set_intersect(c(NA_real_, NaN), NaN), NaN) + expect_identical(vec_set_intersect(c(NaN, NA_real_), NaN), NaN) +}) + +test_that("works with complex missing values", { + na <- complex( + real = c(NA_real_, NA_real_, NaN, NaN), + imaginary = c(NA_real_, NaN, NA_real_, NaN) + ) + expect_identical(vec_set_intersect(na, na), na) + expect_identical(vec_set_intersect(na, na[2]), na[2]) +}) + +test_that("works correctly with unspecified logical vectors", { + expect_identical(vec_set_intersect(NA, NA), NA) +}) + +test_that("returns a vector of the common type", { + expect_identical(vec_set_intersect(1L, c(2, 1)), 1) +}) + +test_that("works with data frames", { + x <- data_frame( + a = c(1, 2, 1, 1), + b = c("a", "b", "a", "d") + ) + y <- data_frame( + a = c(2, 3, 1, 2), + b = c("b", "b", "d", "d") + ) + + expect_identical(vec_set_intersect(x, y), vec_slice(x, c(2, 4))) + expect_identical(vec_set_intersect(y, x), vec_slice(y, c(1, 3))) +}) + +test_that("works with rcrds", { + x <- new_rcrd(list( + a = c(1, 2, 1, 1), + b = c("a", "b", "a", "d") + )) + y <- new_rcrd(list( + a = c(2, 3, 1, 2), + b = c("b", "b", "d", "d") + )) + + expect_identical(vec_set_intersect(x, y), vec_slice(x, c(2, 4))) + expect_identical(vec_set_intersect(y, x), vec_slice(y, c(1, 3))) +}) + +# vec_set_difference ------------------------------------------------------ + +test_that("retains names of `x` elements", { + x <- c(a = 1, b = 4, c = 1, d = 4, e = 5) + y <- c(w = 3, x = 2, y = 1, z = 2) + + expect_identical( + vec_set_difference(x, y), + c(b = 4, e = 5) + ) +}) + +test_that("returns elements in order they first appear in `x`", { + expect_identical(vec_set_difference(c(3, 1, 2, 3), 1), c(3, 2)) +}) + +test_that("returns unique elements", { + expect_identical(vec_set_difference(c(1, 2, 1, 4), c(4, 5)), c(1, 2)) +}) + +test_that("works with character vectors of different encodings", { + encs <- encodings() + expect_identical(vec_set_difference(encs$utf8, encs$latin1), character()) + expect_identical(vec_set_difference(encs$latin1, encs$utf8), character()) +}) + +test_that("has consistency with `NA` values", { + expect_identical(vec_set_difference(c(NA_real_, 1), NA_real_), 1) + expect_identical(vec_set_difference(c(1, NA_real_), NA_real_), 1) + + expect_identical(vec_set_difference(c(NA_real_, NaN), NaN), NA_real_) + expect_identical(vec_set_difference(c(NaN, NA_real_), NaN), NA_real_) +}) + +test_that("works with complex missing values", { + na <- complex( + real = c(NA_real_, NA_real_, NaN, NaN), + imaginary = c(NA_real_, NaN, NA_real_, NaN) + ) + expect_identical(vec_set_difference(na, na), complex()) + expect_identical(vec_set_difference(na, na[2]), na[c(1, 3, 4)]) +}) + +test_that("works correctly with unspecified logical vectors", { + expect_identical(vec_set_difference(NA, NA), logical()) +}) + +test_that("returns a vector of the common type", { + expect_identical(vec_set_difference(c(3L, 1L), c(2, 1)), 3) +}) + +test_that("works with data frames", { + x <- data_frame( + a = c(1, 2, 1, 1), + b = c("a", "b", "a", "d") + ) + y <- data_frame( + a = c(2, 3, 1, 2), + b = c("b", "b", "d", "d") + ) + + expect_identical(vec_set_difference(x, y), vec_slice(x, 1)) + expect_identical(vec_set_difference(y, x), vec_slice(y, c(2, 4))) +}) + +test_that("works with rcrds", { + x <- new_rcrd(list( + a = c(1, 2, 1, 1), + b = c("a", "b", "a", "d") + )) + y <- new_rcrd(list( + a = c(2, 3, 1, 2), + b = c("b", "b", "d", "d") + )) + + expect_identical(vec_set_difference(x, y), vec_slice(x, 1)) + expect_identical(vec_set_difference(y, x), vec_slice(y, c(2, 4))) +}) + +# vec_set_union ----------------------------------------------------------- + +test_that("retains names of `x` and `y` elements", { + x <- c(a = 1, b = 4, c = 1, d = 4, e = 5) + y <- c(w = 3, x = 2, y = 1, z = 2) + + expect_identical( + vec_set_union(x, y), + c(a = 1, b = 4, e = 5, w = 3, x = 2) + ) +}) + +test_that("does minimal name repair on duplicate names", { + x <- c(a = 1) + y <- c(a = 2) + + expect_named(vec_set_union(x, y), c("a", "a")) +}) + +test_that("returns elements in order they first appear in `x` and `y`", { + expect_identical(vec_set_union(c(3, 1, 2, 3), c(4, 2, 5, 4)), c(3, 1, 2, 4, 5)) +}) + +test_that("returns unique elements", { + expect_identical(vec_set_union(c(1, 2, 1, 4), c(4, 5, 5)), c(1, 2, 4, 5)) +}) + +test_that("works with character vectors of different encodings", { + encs <- encodings() + # Always returns UTF-8 + expect_identical(vec_set_union(encs$utf8, encs$latin1), encs$utf8) + expect_identical(vec_set_union(encs$latin1, encs$utf8), encs$utf8) +}) + +test_that("has consistency with `NA` values", { + expect_identical(vec_set_union(c(NA_real_, 1), NA_real_), c(NA_real_, 1)) + expect_identical(vec_set_union(c(1, NA_real_), NA_real_), c(1, NA_real_)) + + expect_identical(vec_set_union(NA_real_, NaN), c(NA_real_, NaN)) + expect_identical(vec_set_union(NaN, NA_real_), c(NaN, NA_real_)) +}) + +test_that("works with complex missing values", { + na <- complex( + real = c(NA_real_, NA_real_, NaN, NaN), + imaginary = c(NA_real_, NaN, NA_real_, NaN) + ) + expect_identical(vec_set_union(na, na), na) + expect_identical(vec_set_union(na[-2], na), na[c(1, 3, 4, 2)]) +}) + +test_that("works correctly with unspecified logical vectors", { + expect_identical(vec_set_union(NA, NA), NA) +}) + +test_that("returns a vector of the common type", { + expect_identical(vec_set_union(c(3L, 1L), c(2, 1)), c(3, 1, 2)) +}) + +test_that("works with data frames", { + x <- data_frame( + a = c(1, 2, 1, 1), + b = c("a", "b", "a", "d") + ) + y <- data_frame( + a = c(2, 3, 1, 2), + b = c("b", "b", "d", "d") + ) + + expect_identical(vec_set_union(x, y), vec_c(vec_slice(x, c(1, 2, 4)), vec_slice(y, c(2, 4)))) + expect_identical(vec_set_union(y, x), vec_c(vec_slice(y, c(1, 2, 3, 4)), vec_slice(x, 1))) +}) + +test_that("works with rcrds", { + x <- new_rcrd(list( + a = c(1, 2, 1, 1), + b = c("a", "b", "a", "d") + )) + y <- new_rcrd(list( + a = c(2, 3, 1, 2), + b = c("b", "b", "d", "d") + )) + + expect_identical(vec_set_union(x, y), vec_c(vec_slice(x, c(1, 2, 4)), vec_slice(y, c(2, 4)))) + expect_identical(vec_set_union(y, x), vec_c(vec_slice(y, c(1, 2, 3, 4)), vec_slice(x, 1))) +}) + +# common ------------------------------------------------------------------ + +test_that("errors nicely if common type can't be taken", { + expect_snapshot(error = TRUE, { + vec_set_intersect(1, "x") + }) + expect_snapshot(error = TRUE, { + vec_set_difference(1, "x") + }) + expect_snapshot(error = TRUE, { + vec_set_union(1, "x") + }) +}) + +test_that("dots must be empty", { + expect_snapshot(error = TRUE, { + vec_set_intersect(1, 2, 3) + }) + expect_snapshot(error = TRUE, { + vec_set_difference(1, 2, 3) + }) + expect_snapshot(error = TRUE, { + vec_set_union(1, 2, 3) + }) +}) + +test_that("`ptype` is respected", { + expect_identical(vec_set_intersect(1, 1, ptype = integer()), 1L) + expect_identical(vec_set_difference(1, 1, ptype = integer()), integer()) + expect_identical(vec_set_union(1, 2, ptype = integer()), c(1L, 2L)) + + expect_snapshot(error = TRUE, { + vec_set_intersect(1, 1.5, ptype = integer()) + }) + expect_snapshot(error = TRUE, { + vec_set_difference(1, 1.5, ptype = integer()) + }) + expect_snapshot(error = TRUE, { + vec_set_union(1, 1.5, ptype = integer()) + }) +}) + +test_that("`x_arg` and `y_arg` can be adjusted", { + expect_snapshot(error = TRUE, { + vec_set_intersect(1, "2", x_arg = "foo", y_arg = "bar") + }) + expect_snapshot(error = TRUE, { + vec_set_difference(1, "2", x_arg = "foo", y_arg = "bar") + }) + expect_snapshot(error = TRUE, { + vec_set_union(1, "2", x_arg = "foo", y_arg = "bar") + }) + + expect_snapshot(error = TRUE, { + vec_set_intersect(1, "2", x_arg = "", y_arg = "") + }) +}) + +test_that("`error_call` can be adjusted", { + my_set_intersect <- function() { + vec_set_intersect(1, "x", error_call = current_env()) + } + my_set_difference <- function() { + vec_set_difference(1, "x", error_call = current_env()) + } + my_set_union <- function() { + vec_set_union(1, "x", error_call = current_env()) + } + + expect_snapshot(error = TRUE, { + my_set_intersect() + }) + expect_snapshot(error = TRUE, { + my_set_difference() + }) + expect_snapshot(error = TRUE, { + my_set_union() + }) +}) From 7f1edf071021e6f344bbee3c463b588c6310622f Mon Sep 17 00:00:00 2001 From: Davis Vaughan Date: Thu, 22 Dec 2022 13:17:46 -0400 Subject: [PATCH 207/312] Use correct `uint64_t` to right shift with (#1759) * Use correct `uint64_t` to right shift with * Update snapshot test * Fix naming of unsigned int hashers --- src/hash.c | 16 ++++----- tests/testthat/_snaps/hash.md | 64 +++++++++++++++++------------------ 2 files changed, 40 insertions(+), 40 deletions(-) diff --git a/src/hash.c b/src/hash.c index f57de1b5c..154c9fb37 100644 --- a/src/hash.c +++ b/src/hash.c @@ -7,7 +7,7 @@ static inline uint32_t hash_combine(uint32_t x, uint32_t y) { // 32-bit mixer from murmurhash // https://github.com/aappleby/smhasher/blob/master/src/MurmurHash3.cpp#L68 -static inline uint32_t hash_int32(uint32_t x) { +static inline uint32_t hash_uint32(uint32_t x) { x ^= x >> 16; x *= 0x85ebca6b; x ^= x >> 13; @@ -19,7 +19,7 @@ static inline uint32_t hash_int32(uint32_t x) { // 64-bit mixer from murmurhash // https://github.com/aappleby/smhasher/blob/master/src/MurmurHash3.cpp#L81 -static inline uint32_t hash_int64(int64_t x) { +static inline uint32_t hash_uint64(uint64_t x) { x ^= x >> 33; x *= UINT64_C(0xff51afd7ed558ccd); x ^= x >> 33; @@ -42,11 +42,11 @@ static inline uint32_t hash_double(double x) { } value; value.d = x; - return hash_int64(value.i); + return hash_uint64(value.i); } static inline uint32_t hash_char(SEXP x) { - return hash_int64((uintptr_t) x); + return hash_uint64((uintptr_t) x); } // Hashing scalars ----------------------------------------------------- @@ -60,10 +60,10 @@ static inline uint32_t raw_hash_scalar(const Rbyte* x); static inline uint32_t lgl_hash_scalar(const int* x) { - return hash_int32(*x); + return hash_uint32(*x); } static inline uint32_t int_hash_scalar(const int* x) { - return hash_int32(*x); + return hash_uint32(*x); } static inline uint32_t dbl_hash_scalar(const double* x) { double val = *x; @@ -87,7 +87,7 @@ static inline uint32_t chr_hash_scalar(const SEXP* x) { return hash_char(*x); } static inline uint32_t raw_hash_scalar(const Rbyte* x) { - return hash_int32(*x); + return hash_uint32(*x); } static inline uint32_t list_hash_scalar_na_equal(SEXP x, R_len_t i) { @@ -153,7 +153,7 @@ static uint32_t sexp_hash(SEXP x) { case SPECIALSXP: case BUILTINSXP: case ENVSXP: - case EXTPTRSXP: return hash_int64((uintptr_t) x); + case EXTPTRSXP: return hash_uint64((uintptr_t) x); default: Rf_errorcall(R_NilValue, "Unsupported type %s", Rf_type2char(TYPEOF(x))); } } diff --git a/tests/testthat/_snaps/hash.md b/tests/testthat/_snaps/hash.md index 9c7ab7413..9d6fc935e 100644 --- a/tests/testthat/_snaps/hash.md +++ b/tests/testthat/_snaps/hash.md @@ -25,39 +25,39 @@ [376] f4 1a a5 4f 41 4b 7a 10 f2 d2 98 6e 7e 7f 11 0f c9 93 eb 84 3a a3 d6 05 9c $dbl1 - [1] 00 c1 04 29 59 03 e1 f3 6a 26 91 1e a7 0a 94 81 d0 c2 58 ef 6a b0 2f 59 c2 - [26] f7 fe 63 c3 ce 8a 90 1d 1d ce 14 05 c8 d4 e8 2f cf 98 46 e2 99 af e3 b9 cf - [51] 1b 4b 39 8b 47 f3 e3 49 63 d1 0a af 42 9d 48 fe c7 7b ab b4 ab 5b a8 d7 94 - [76] 6e 0c 82 24 08 fc 20 d8 cb 7a bb c7 ba 9e 3b 0d d5 d6 8c 9e 2b 48 97 9e c8 - [101] f0 c9 4b ad da 6b 9e 41 8b 82 e8 82 ba 6a f2 99 a1 81 82 d5 c0 ca 3d fb ce - [126] 54 60 0e 7d 93 bd 32 8e 02 d8 db e0 cb f9 e7 f5 ae e1 b9 73 17 5d ed ff a7 - [151] 43 68 23 ee 2d 63 73 d9 a0 43 f6 72 2d 68 19 ff fc 46 0b 49 69 3e 1f bc 03 - [176] 1d 1a ab de c9 b0 4a ed 85 af 2f e3 fc 80 99 b7 c4 7f 65 ac c1 96 17 5b 86 - [201] 78 2e c8 67 65 45 5d 95 77 3d 3a 9b d8 c7 01 fd e7 1d 5b 2d f6 19 7b 18 20 - [226] 67 7c af 43 01 54 b6 2c 99 10 85 28 c4 68 e1 99 67 d9 ae f4 5a e2 04 87 14 - [251] 63 8a 89 96 5e f6 fc 9c a3 6a f1 23 29 09 82 c9 2a cc 51 b7 8f 27 53 47 a0 - [276] a6 fa 73 2d 07 86 f5 cc 07 98 1a f2 6c d4 e0 f2 43 31 90 98 2c 94 28 25 40 - [301] 23 1f 2f 2f 41 50 c3 d2 65 6f 01 32 a1 7f 7a 40 a8 5c 11 db 88 7d 7e a4 1d - [326] 7d 43 c3 17 cd 2e ca dc 56 aa c3 74 8d 37 1a 16 07 d4 c5 0a f9 03 8f a7 6d - [351] 23 c5 b8 05 ad 7c e1 33 d1 0e 0e 8c 19 72 0d 80 3e c7 80 5c 77 58 b1 ef 89 - [376] 39 a5 a2 72 0a c4 c4 c5 16 47 90 da 47 49 a1 b1 81 70 ce cf cf b3 5c ca 3a + [1] 6b 2c 06 3b 59 03 e1 f3 6a 26 91 9e dd 27 af 6c d0 c2 58 6f a7 71 b0 a8 c2 + [26] f7 fe 63 40 5a f1 9d 92 c5 0e c6 05 c8 d4 68 2f cf 98 c6 69 41 ad 1d 2a 6f + [51] bb a3 b1 f9 09 f0 e3 49 63 d1 0a af 42 9d 59 31 8b 1e db 3f f1 61 a8 d7 94 + [76] 6e fd ec bf 5c fc 20 d8 cb 7a bb c7 ba 8b 60 53 00 d6 8c 9e 2b fc 76 73 e7 + [101] f0 c9 4b ad da 6b 9e 41 9f 88 3f 20 ba 6a f2 99 56 48 e0 57 c0 ca 3d 7b ce + [126] 54 60 0e 5b ad 1b 94 a3 cb 2f c3 e0 cb f9 67 f5 ae e1 39 73 17 5d 6d 70 0a + [151] a5 bc 01 08 f3 9d 8c de 10 d3 f6 72 2d e8 19 ff fc c6 24 4e 95 b4 90 5e 7b + [176] da e2 12 4e f4 b0 4a ed 85 af 2f e3 fc 48 33 5d aa 7f 78 05 2f d3 d2 44 c4 + [201] 78 2e c8 e7 65 45 5d 15 af 8b 5e 5c 49 48 fb 55 d1 4e 09 d0 f6 19 7b 98 20 + [226] 67 7c 2f 2e ba 70 2a 0a ad c8 48 3d 69 7b c5 99 67 d9 2e f4 5a e2 84 24 9c + [251] 00 22 1d 75 e7 c6 fc 9c a3 6a dd 1d 96 b0 53 67 35 59 51 b7 8f a7 3f 78 39 + [276] ed fa 73 2d 07 24 3b 9e 97 83 06 0d 2a d4 e0 f2 43 75 c3 6f 09 94 28 25 40 + [301] f8 c1 9e 13 41 50 c3 d2 65 6f 01 b2 26 fb 1f d2 a8 5c 11 db b4 e6 4d e1 1d + [326] 7d 43 c3 17 cd 2e ca ad 05 b4 bd 74 8d 37 9a 5a 1e 85 d4 0a f9 03 8f a7 6d + [351] 23 c5 7b e7 54 ee e1 33 d1 8e a3 5d a4 cb 0d 80 3e c7 80 5c 77 d8 36 fb 94 + [376] a5 a5 a2 72 8a 95 ab f3 da 47 90 da c7 49 a1 b1 81 01 19 29 96 b3 5c ca ba $dbl2 - [1] b9 79 37 9e 87 e6 d0 04 ff 57 34 47 e9 da db 08 35 18 46 24 36 7b 48 f3 75 - [26] 78 db 2d 6c 77 76 c5 67 0a 4b b9 64 57 19 b8 f4 69 d5 5d c2 04 8f 91 55 6a - [51] d5 2f 33 2d 76 e9 9d f6 f8 5e cf c6 06 5d 6a 73 96 c6 21 e5 ca ad 3f d6 4c - [76] 1d 3c 72 9b b3 3a 66 7a e4 91 0d 96 82 63 22 50 12 56 6b 1a 7f 0f 3e 5b e8 - [101] bc 28 55 9c 90 22 9c f7 9a f9 60 5f 64 8c d0 c8 c4 cd fa 2d 20 1a db 65 c0 - [126] 7e 70 5f 2d 59 57 6f cc 52 4f 75 87 f9 6a 7a e8 1e 2c 5c e7 1b 72 ea 69 8a - [151] 6b fb a5 7d 41 05 1a e3 ed e6 ea 50 2b 06 3f 39 e8 a1 e0 69 29 56 5e 0e 72 - [176] 29 b2 4c 65 ae 76 d2 cd 18 6c 74 3d f4 62 1f 67 51 37 e4 1f eb 54 0f 00 71 - [201] 5b da 32 37 d5 fc 9d f3 c3 0e a6 81 09 19 25 1e 06 61 2f 2c 62 7a 33 fc 41 - [226] 13 fc f9 44 55 57 9d d6 4b a7 ba 87 fe 1e 00 d7 1c 0c 34 ba 25 ce 21 7f 97 - [251] d5 11 f5 cf 2f a4 34 2f 60 a7 b2 a5 2c 8f 90 29 c5 55 06 c6 6a 19 e4 bc 46 - [276] 24 c0 43 8c bf ac d9 db 43 ea 2f 29 da 48 64 fa 51 55 85 81 40 cd ac bc 6e - [301] 9b d2 07 e2 94 df 2a 7d c2 bd 63 87 5e 5e 47 8d 2d 21 ac 92 0a b8 52 e4 e5 - [326] fb ec d6 5b 17 34 01 02 21 78 b2 83 28 f9 f0 f5 ae 90 27 30 aa 4b 5c 6a d2 - [351] da 71 2e 3c c6 68 a7 9f a9 36 16 81 cb cb d8 6d 07 96 6e f4 f9 29 8d 61 f7 - [376] 86 51 af f2 7e cc 3d 4f 24 8e e0 9f 70 be b1 af c9 73 f2 4b c9 00 c1 04 29 + [1] b9 79 37 9e ea 40 52 d2 fa 14 1e 2f c1 55 60 05 35 18 46 24 ba 76 ed 56 75 + [26] 78 db ad 6c 77 76 c5 67 0a 4b b9 d2 19 61 03 f4 69 d5 5d db d2 f9 7d 55 6a + [51] d5 af 33 2d 76 69 9d f6 f8 de 6f d3 54 05 97 a0 7f 08 f0 19 33 e0 e4 4a 20 + [76] 61 67 40 d0 00 b5 ad 11 fb 94 d6 28 78 ef 95 69 a6 e5 9f ed cf 10 69 4f 59 + [101] bc 28 55 9c e7 bd ea 9d c2 cb 77 e7 9d 22 f6 ee ad 0c 46 0d 6d 15 f2 26 c0 + [126] 7e 70 df 9c 1b ce cc cc 52 4f 75 87 f9 6a fa 5f b8 4d 42 e7 1b 72 ea 69 8a + [151] 6b 7b ab 97 7b 86 e6 9a 7c 62 ac eb 08 df 3f 39 e8 a1 ec ce 45 f9 26 c5 27 + [176] 47 b2 4c 65 ae 11 07 52 d4 6c 74 3d f4 62 1f 67 51 37 e4 1f eb b7 3e 51 26 + [201] 5b da 32 b7 d5 fc 9d 73 8d 98 42 fa 90 23 50 bf 06 61 2f ac 54 8c 87 0e 53 + [226] 3d 98 5f 44 55 57 9d 69 b7 59 9f 87 fe 1e 00 d7 1c 0c 34 ba 25 ce a1 77 68 + [251] cc 7a f5 cf 2f a4 34 2f 60 a7 a0 c7 e9 cd 90 29 c5 55 06 c6 6a 99 e4 bc 46 + [276] a4 c0 43 8c 3f f8 8c ee 17 d7 9f 8d 03 48 64 fa d1 55 85 81 c0 cd ac bc 6e + [301] d5 59 0a 28 94 df 2a 7d ea ca 7f 09 5e 5e 47 0d 02 ad 8c 67 0a b8 52 e4 17 + [326] 3a 25 5d 5b 17 34 01 09 18 7e ca 83 28 f9 f0 c1 b0 10 bc 30 aa 4b 5c 85 68 + [351] 75 71 2e 3c c6 e8 a7 9f a9 36 16 81 cb 4b d7 94 88 15 6e f4 f9 a9 03 ac 21 + [376] 65 43 cb 1a ca cd 69 96 b6 8e e0 9f 70 be b1 af c9 73 f2 4b c9 6b 2c 06 3b From 4c574184f75597fabcd60b194ee05becec649094 Mon Sep 17 00:00:00 2001 From: Davis Vaughan Date: Tue, 3 Jan 2023 09:24:49 -0500 Subject: [PATCH 208/312] Adjust the max load factor of the dictionary to 50% (#1760) * Temporarily expose a way to dynamically set the load factor * Revert "Temporarily expose a way to dynamically set the load factor" This reverts commit f5135cb9260c7b0d434c1a1daeb7b645d2047816. * Use a 50% max load factor in the dictionary * Add link to discussion and update values in comment * NEWS bullet (for internal referencing) --- NEWS.md | 4 ++++ src/dictionary.c | 11 ++++++----- 2 files changed, 10 insertions(+), 5 deletions(-) diff --git a/NEWS.md b/NEWS.md index 36515ed45..94dc5db30 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,5 +1,9 @@ # vctrs (development version) +* The maximum load factor of the internal dictionary was reduced from 77% to + 50%, which improves performance of functions like `vec_match()`, + `vec_set_intersect()`, and `vec_unique()` in some cases (#1760). + * New `vec_set_intersect()`, `vec_set_difference()`, and `vec_set_union()` which compute set operations like `intersect()`, `setdiff()`, and `union()`, but the vctrs variants don't strip attributes and work with data frames (#1755). diff --git a/src/dictionary.c b/src/dictionary.c index 8c83c34be..74ab6fa77 100644 --- a/src/dictionary.c +++ b/src/dictionary.c @@ -166,13 +166,14 @@ void dict_put(struct dictionary* d, uint32_t hash, R_len_t i) { } // Assume worst case, that every value is distinct, aiming for a load factor -// of at most 77%. We round up to power of 2 to ensure quadratic probing +// of at most 50%. We round up to power of 2 to ensure quadratic probing // strategy works. Maximum power of 2 we can store in a uint32_t is 2^31, // as 2^32 is 1 greater than the max uint32_t value, so we clamp sizes that // would result in 2^32 to INT32_MAX to ensure that our maximum ceiling value -// is only 2^31. This will increase the load factor above 77% for `x` with -// length greater than 1653562409 (2147483648 * .77), but it ensures that -// it can run. +// is only 2^31. This will increase the max load factor above 50% for `x` with +// length greater than 1073741824 (2147483648 * .50), but it ensures that +// it can run. See https://github.com/r-lib/vctrs/pull/1760 for further +// discussion of why 50% was chosen. static inline uint32_t dict_key_size(SEXP x) { const R_len_t x_size = vec_size(x); @@ -182,7 +183,7 @@ uint32_t dict_key_size(SEXP x) { r_stop_internal("Dictionary functions do not support long vectors."); } - const double load_adjusted_size = x_size / 0.77; + const double load_adjusted_size = x_size / 0.50; if (load_adjusted_size > UINT32_MAX) { r_stop_internal("Can't safely cast load adjusted size to a `uint32_t`."); From b5352f7d090c038ef27ee9ed603c4b5a37d61721 Mon Sep 17 00:00:00 2001 From: Davis Vaughan Date: Thu, 19 Jan 2023 09:36:56 -0500 Subject: [PATCH 209/312] Implement `vec_set_symmetric_difference()` (#1765) * Implement `vec_set_symmetric_difference()` * NEWS bullet --- NAMESPACE | 1 + NEWS.md | 7 +- R/set.R | 28 ++++++ man/vec-set.Rd | 27 ++++++ src/init.c | 2 + src/set.c | 182 +++++++++++++++++++++++++++++++++++ src/set.h | 7 ++ tests/testthat/_snaps/set.md | 44 +++++++++ tests/testthat/test-set.R | 114 ++++++++++++++++++++++ 9 files changed, 409 insertions(+), 3 deletions(-) diff --git a/NAMESPACE b/NAMESPACE index f592e9fae..ec52c3f71 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -621,6 +621,7 @@ export(vec_seq_along) export(vec_set_difference) export(vec_set_intersect) export(vec_set_names) +export(vec_set_symmetric_difference) export(vec_set_union) export(vec_size) export(vec_size_common) diff --git a/NEWS.md b/NEWS.md index 94dc5db30..b87d4b588 100644 --- a/NEWS.md +++ b/NEWS.md @@ -4,9 +4,10 @@ 50%, which improves performance of functions like `vec_match()`, `vec_set_intersect()`, and `vec_unique()` in some cases (#1760). -* New `vec_set_intersect()`, `vec_set_difference()`, and `vec_set_union()` which - compute set operations like `intersect()`, `setdiff()`, and `union()`, but - the vctrs variants don't strip attributes and work with data frames (#1755). +* New `vec_set_intersect()`, `vec_set_difference()`, `vec_set_union()`, and + `vec_set_symmetric_difference()` which compute set operations like + `intersect()`, `setdiff()`, and `union()`, but the vctrs variants don't strip + attributes and work with data frames (#1755, #1765). * Fixed a bug with the internal `vec_order_radix()` function related to matrix columns (#1753). diff --git a/R/set.R b/R/set.R index fd9073572..9a2c1edb3 100644 --- a/R/set.R +++ b/R/set.R @@ -8,6 +8,9 @@ #' #' - `vec_set_union()` returns all values in either `x` or `y`. #' +#' - `vec_set_symmetric_difference()` returns all values in either `x` or `y` +#' but not both. This is a commutative difference. +#' #' Because these are _set_ operations, these functions only return unique values #' from `x` and `y`, returned in the order they first appeared in the original #' input. Names of `x` and `y` are retained on the result, but names are always @@ -57,6 +60,13 @@ #' - [vec_cast()] #' - [vec_c()] #' +#' ## `vec_set_symmetric_difference()` +#' - [vec_proxy_equal()] +#' - [vec_slice()] +#' - [vec_ptype2()] +#' - [vec_cast()] +#' - [vec_c()] +#' #' @name vec-set #' @examples #' x <- c(1, 2, 1, 4, 3) @@ -72,6 +82,9 @@ #' # All unique values in either `x` or `y` #' vec_set_union(x, y) #' +#' # All unique values in either `x` or `y` but not both +#' vec_set_symmetric_difference(x, y) +#' #' # These functions can also be used with data frames #' x <- data_frame( #' a = c(2, 3, 2, 2), @@ -85,6 +98,7 @@ #' vec_set_intersect(x, y) #' vec_set_difference(x, y) #' vec_set_union(x, y) +#' vec_set_symmetric_difference(x, y) #' #' # Vector names don't affect set membership, but if you'd like to force #' # them to, you can transform the vector into a two column data frame @@ -137,3 +151,17 @@ vec_set_union <- function(x, check_dots_empty0(...) .Call(ffi_vec_set_union, x, y, ptype, environment()) } + +#' @rdname vec-set +#' @export +vec_set_symmetric_difference <- function(x, + y, + ..., + ptype = NULL, + x_arg = "x", + y_arg = "y", + error_call = current_env()) { + check_dots_empty0(...) + .Call(ffi_vec_set_symmetric_difference, x, y, ptype, environment()) +} + diff --git a/man/vec-set.Rd b/man/vec-set.Rd index daf77002a..02bbe4579 100644 --- a/man/vec-set.Rd +++ b/man/vec-set.Rd @@ -5,6 +5,7 @@ \alias{vec_set_intersect} \alias{vec_set_difference} \alias{vec_set_union} +\alias{vec_set_symmetric_difference} \title{Set operations} \usage{ vec_set_intersect( @@ -36,6 +37,16 @@ vec_set_union( y_arg = "y", error_call = current_env() ) + +vec_set_symmetric_difference( + x, + y, + ..., + ptype = NULL, + x_arg = "x", + y_arg = "y", + error_call = current_env() +) } \arguments{ \item{x, y}{A pair of vectors.} @@ -64,6 +75,8 @@ containing the result of the corresponding set function. \item \code{vec_set_difference()} returns all values in \code{x} but not \code{y}. Note that this is an asymmetric set difference, meaning it is not commutative. \item \code{vec_set_union()} returns all values in either \code{x} or \code{y}. +\item \code{vec_set_symmetric_difference()} returns all values in either \code{x} or \code{y} +but not both. This is a commutative difference. } Because these are \emph{set} operations, these functions only return unique values @@ -107,6 +120,16 @@ complexes, \code{NaN} are equal to other \code{NaN}, but not to \code{NA}. \item \code{\link[=vec_c]{vec_c()}} } } + +\subsection{\code{vec_set_symmetric_difference()}}{ +\itemize{ +\item \code{\link[=vec_proxy_equal]{vec_proxy_equal()}} +\item \code{\link[=vec_slice]{vec_slice()}} +\item \code{\link[=vec_ptype2]{vec_ptype2()}} +\item \code{\link[=vec_cast]{vec_cast()}} +\item \code{\link[=vec_c]{vec_c()}} +} +} } \examples{ @@ -123,6 +146,9 @@ vec_set_difference(x, y) # All unique values in either `x` or `y` vec_set_union(x, y) +# All unique values in either `x` or `y` but not both +vec_set_symmetric_difference(x, y) + # These functions can also be used with data frames x <- data_frame( a = c(2, 3, 2, 2), @@ -136,6 +162,7 @@ y <- data_frame( vec_set_intersect(x, y) vec_set_difference(x, y) vec_set_union(x, y) +vec_set_symmetric_difference(x, y) # Vector names don't affect set membership, but if you'd like to force # them to, you can transform the vector into a two column data frame diff --git a/src/init.c b/src/init.c index 8a504cc1b..65c40873c 100644 --- a/src/init.c +++ b/src/init.c @@ -155,6 +155,7 @@ extern r_obj* ffi_list_check_all_size(r_obj*, r_obj*, r_obj*); extern r_obj* ffi_vec_set_intersect(r_obj*, r_obj*, r_obj*, r_obj*); extern r_obj* ffi_vec_set_difference(r_obj*, r_obj*, r_obj*, r_obj*); extern r_obj* ffi_vec_set_union(r_obj*, r_obj*, r_obj*, r_obj*); +extern r_obj* ffi_vec_set_symmetric_difference(r_obj*, r_obj*, r_obj*, r_obj*); // Maturing @@ -333,6 +334,7 @@ static const R_CallMethodDef CallEntries[] = { {"ffi_vec_set_intersect", (DL_FUNC) &ffi_vec_set_intersect, 4}, {"ffi_vec_set_difference", (DL_FUNC) &ffi_vec_set_difference, 4}, {"ffi_vec_set_union", (DL_FUNC) &ffi_vec_set_union, 4}, + {"ffi_vec_set_symmetric_difference", (DL_FUNC) &ffi_vec_set_symmetric_difference, 4}, {"ffi_exp_vec_cast", (DL_FUNC) &exp_vec_cast, 2}, {NULL, NULL, 0} }; diff --git a/src/set.c b/src/set.c index 6b72d5782..5281b319d 100644 --- a/src/set.c +++ b/src/set.c @@ -424,3 +424,185 @@ r_obj* vec_set_union(r_obj* x, FREE(n_prot); return out; } + +// ----------------------------------------------------------------------------- + +r_obj* ffi_vec_set_symmetric_difference(r_obj* x, + r_obj* y, + r_obj* ptype, + r_obj* frame) { + struct r_lazy call = { .x = r_syms.error_call, .env = frame }; + + struct r_lazy x_arg_lazy = { .x = syms.x_arg, .env = frame }; + struct vctrs_arg x_arg = new_lazy_arg(&x_arg_lazy); + + struct r_lazy y_arg_lazy = { .x = syms.y_arg, .env = frame }; + struct vctrs_arg y_arg = new_lazy_arg(&y_arg_lazy); + + return vec_set_symmetric_difference(x, y, ptype, &x_arg, &y_arg, call); +} + +r_obj* vec_set_symmetric_difference(r_obj* x, + r_obj* y, + r_obj* ptype, + struct vctrs_arg* x_arg, + struct vctrs_arg* y_arg, + struct r_lazy call) { + int n_prot = 0; + + if (ptype == r_null) { + int _; + + ptype = vec_ptype2_params( + x, + y, + x_arg, + y_arg, + call, + &_ + ); + KEEP_N(ptype, &n_prot); + + ptype = vec_ptype_finalise(ptype); + KEEP_N(ptype, &n_prot); + } + + x = vec_cast_params( + x, + ptype, + x_arg, + vec_args.empty, + call, + S3_FALLBACK_false + ); + KEEP_N(x, &n_prot); + + y = vec_cast_params( + y, + ptype, + y_arg, + vec_args.empty, + call, + S3_FALLBACK_false + ); + KEEP_N(y, &n_prot); + + r_obj* x_proxy = KEEP_N(vec_proxy_equal(x), &n_prot); + x_proxy = KEEP_N(vec_normalize_encoding(x_proxy), &n_prot); + + r_obj* y_proxy = KEEP_N(vec_proxy_equal(y), &n_prot); + y_proxy = KEEP_N(vec_normalize_encoding(y_proxy), &n_prot); + + const r_ssize x_size = vec_size(x_proxy); + const r_ssize y_size = vec_size(y_proxy); + + struct dictionary* x_dict = new_dictionary(x_proxy); + PROTECT_DICT(x_dict, &n_prot); + + struct dictionary* y_dict = new_dictionary(y_proxy); + PROTECT_DICT(y_dict, &n_prot); + + r_obj* x_marked_shelter = KEEP_N(r_alloc_raw(x_size * sizeof(bool)), &n_prot); + bool* v_x_marked = (bool*) r_raw_begin(x_marked_shelter); + + r_obj* y_marked_shelter = KEEP_N(r_alloc_raw(y_size * sizeof(bool)), &n_prot); + bool* v_y_marked = (bool*) r_raw_begin(y_marked_shelter); + + // Load dictionary with `x`. + // Key values point to first time we saw that `x` value. + // Mark those first seen locations as possible results. + for (r_ssize i = 0; i < x_size; ++i) { + const uint32_t hash = dict_hash_scalar(x_dict, i); + const bool first_time = x_dict->key[hash] == DICT_EMPTY; + + if (first_time) { + dict_put(x_dict, hash, i); + } + + v_x_marked[i] = first_time; + } + + // Load dictionary with `y`. + // Key values point to first time we saw that `y` value. + // Mark those first seen locations as possible results. + for (r_ssize i = 0; i < y_size; ++i) { + const uint32_t hash = dict_hash_scalar(y_dict, i); + const bool first_time = y_dict->key[hash] == DICT_EMPTY; + + if (first_time) { + dict_put(y_dict, hash, i); + } + + v_y_marked[i] = first_time; + } + + r_ssize n_x_marked = x_dict->used; + r_ssize n_y_marked = y_dict->used; + + // Check if unique elements of `y` are in `x`. + // If they are, unmark them from both `x` and `y`. + for (r_ssize i = 0; i < y_size; ++i) { + if (!v_y_marked[i]) { + continue; + } + + const uint32_t hash = dict_hash_with(x_dict, y_dict, i); + const r_ssize loc = x_dict->key[hash]; + const bool in_x = loc != DICT_EMPTY; + + if (in_x) { + v_x_marked[loc] = false; + v_y_marked[i] = false; + --n_x_marked; + --n_y_marked; + } + } + + r_obj* loc = KEEP_N(r_alloc_integer(n_x_marked), &n_prot); + int* v_loc = r_int_begin(loc); + r_ssize j = 0; + + for (r_ssize i = 0; i < x_size; ++i) { + if (v_x_marked[i]) { + v_loc[j] = i + 1; + ++j; + } + } + + // Slice out `x`, then reuse `loc` for slicing `y` + x = KEEP_N(vec_slice_unsafe(x, loc), &n_prot); + + loc = KEEP_N(r_int_resize(loc, n_y_marked), &n_prot); + v_loc = r_int_begin(loc); + j = 0; + + for (r_ssize i = 0; i < y_size; ++i) { + if (v_y_marked[i]) { + v_loc[j] = i + 1; + ++j; + } + } + + y = KEEP_N(vec_slice_unsafe(y, loc), &n_prot); + + const struct name_repair_opts name_repair_opts = { + .type = NAME_REPAIR_none, + .fn = r_null + }; + + r_obj* args = KEEP_N(r_alloc_list(2), &n_prot); + r_list_poke(args, 0, x); + r_list_poke(args, 1, y); + + r_obj* out = vec_c( + args, + ptype, + r_null, + &name_repair_opts, + vec_args.empty, + r_lazy_null + ); + + FREE(n_prot); + return out; +} diff --git a/src/set.h b/src/set.h index ac2de4b86..b04444885 100644 --- a/src/set.h +++ b/src/set.h @@ -24,4 +24,11 @@ r_obj* vec_set_union(r_obj* x, struct vctrs_arg* y_arg, struct r_lazy call); +r_obj* vec_set_symmetric_difference(r_obj* x, + r_obj* y, + r_obj* ptype, + struct vctrs_arg* x_arg, + struct vctrs_arg* y_arg, + struct r_lazy call); + #endif diff --git a/tests/testthat/_snaps/set.md b/tests/testthat/_snaps/set.md index dbded808d..bfcd3e069 100644 --- a/tests/testthat/_snaps/set.md +++ b/tests/testthat/_snaps/set.md @@ -22,6 +22,14 @@ Error in `vec_set_union()`: ! Can't combine `x` and `y` . +--- + + Code + vec_set_symmetric_difference(1, "x") + Condition + Error in `vec_set_symmetric_difference()`: + ! Can't combine `x` and `y` . + # dots must be empty Code @@ -55,6 +63,17 @@ * ..1 = 3 i Did you forget to name an argument? +--- + + Code + vec_set_symmetric_difference(1, 2, 3) + Condition + Error in `vec_set_symmetric_difference()`: + ! `...` must be empty. + x Problematic argument: + * ..1 = 3 + i Did you forget to name an argument? + # `ptype` is respected Code @@ -82,6 +101,15 @@ ! Can't convert from `y` to due to loss of precision. * Locations: 1 +--- + + Code + vec_set_symmetric_difference(1, 1.5, ptype = integer()) + Condition + Error in `vec_set_symmetric_difference()`: + ! Can't convert from `y` to due to loss of precision. + * Locations: 1 + # `x_arg` and `y_arg` can be adjusted Code @@ -106,6 +134,14 @@ Error in `vec_set_union()`: ! Can't combine `foo` and `bar` . +--- + + Code + vec_set_symmetric_difference(1, "2", x_arg = "foo", y_arg = "bar") + Condition + Error in `vec_set_symmetric_difference()`: + ! Can't combine `foo` and `bar` . + --- Code @@ -138,3 +174,11 @@ Error in `my_set_union()`: ! Can't combine `x` and `y` . +--- + + Code + my_set_symmetric_difference() + Condition + Error in `my_set_symmetric_difference()`: + ! Can't combine `x` and `y` . + diff --git a/tests/testthat/test-set.R b/tests/testthat/test-set.R index 7c177d89c..737ea2657 100644 --- a/tests/testthat/test-set.R +++ b/tests/testthat/test-set.R @@ -244,6 +244,101 @@ test_that("works with rcrds", { expect_identical(vec_set_union(y, x), vec_c(vec_slice(y, c(1, 2, 3, 4)), vec_slice(x, 1))) }) +# vec_set_symmetric_difference -------------------------------------------- + +test_that("retains names of `x` and `y` elements", { + x <- c(a = 1, b = 4, c = 1, d = 4, e = 5) + y <- c(w = 3, x = 2, y = 1, z = 2) + + expect_identical( + vec_set_symmetric_difference(x, y), + c(b = 4, e = 5, w = 3, x = 2) + ) +}) + +test_that("returns elements in order they first appear in `x` and `y`", { + expect_identical(vec_set_symmetric_difference(c(3, 1, 2, 3), c(4, 2, 5, 4)), c(3, 1, 4, 5)) +}) + +test_that("returns unique elements", { + expect_identical(vec_set_symmetric_difference(c(1, 2, 1, 4), c(4, 5, 5)), c(1, 2, 5)) +}) + +test_that("works with character vectors of different encodings", { + encs <- encodings() + # Always returns UTF-8 + expect_identical(vec_set_symmetric_difference(encs$utf8, encs$latin1), character()) + expect_identical(vec_set_symmetric_difference(encs$latin1, encs$utf8), character()) +}) + +test_that("has consistency with `NA` values", { + expect_identical(vec_set_symmetric_difference(c(NA_real_, 1), NA_real_), 1) + expect_identical(vec_set_symmetric_difference(c(1, NA_real_), NA_real_), 1) + + expect_identical(vec_set_symmetric_difference(c(NaN, 1), NaN), 1) + expect_identical(vec_set_symmetric_difference(c(1, NaN), NaN), 1) + + expect_identical(vec_set_symmetric_difference(NA_real_, NaN), c(NA_real_, NaN)) + expect_identical(vec_set_symmetric_difference(NaN, NA_real_), c(NaN, NA_real_)) +}) + +test_that("works with complex missing values", { + na <- complex( + real = c(NA_real_, NA_real_, NaN, NaN), + imaginary = c(NA_real_, NaN, NA_real_, NaN) + ) + expect_identical(vec_set_symmetric_difference(na, na), complex()) + expect_identical(vec_set_symmetric_difference(na[-2], na[-4]), na[c(2, 4)]) +}) + +test_that("works correctly with unspecified logical vectors", { + expect_identical(vec_set_symmetric_difference(NA, NA), logical()) +}) + +test_that("returns a vector of the common type", { + expect_identical(vec_set_symmetric_difference(c(3L, 1L), c(2, 1)), c(3, 2)) +}) + +test_that("works with data frames", { + x <- data_frame( + a = c(1, 2, 1, 1), + b = c("a", "b", "a", "d") + ) + y <- data_frame( + a = c(2, 3, 1, 2), + b = c("b", "b", "d", "d") + ) + + expect_identical( + vec_set_symmetric_difference(x, y), + vec_c(vec_slice(x, 1), vec_slice(y, c(2, 4))) + ) + expect_identical( + vec_set_symmetric_difference(y, x), + vec_c(vec_slice(y, c(2, 4)), vec_slice(x, 1)) + ) +}) + +test_that("works with rcrds", { + x <- new_rcrd(list( + a = c(1, 2, 1, 1), + b = c("a", "b", "a", "d") + )) + y <- new_rcrd(list( + a = c(2, 3, 1, 2), + b = c("b", "b", "d", "d") + )) + + expect_identical( + vec_set_symmetric_difference(x, y), + vec_c(vec_slice(x, 1), vec_slice(y, c(2, 4))) + ) + expect_identical( + vec_set_symmetric_difference(y, x), + vec_c(vec_slice(y, c(2, 4)), vec_slice(x, 1)) + ) +}) + # common ------------------------------------------------------------------ test_that("errors nicely if common type can't be taken", { @@ -256,6 +351,9 @@ test_that("errors nicely if common type can't be taken", { expect_snapshot(error = TRUE, { vec_set_union(1, "x") }) + expect_snapshot(error = TRUE, { + vec_set_symmetric_difference(1, "x") + }) }) test_that("dots must be empty", { @@ -268,12 +366,16 @@ test_that("dots must be empty", { expect_snapshot(error = TRUE, { vec_set_union(1, 2, 3) }) + expect_snapshot(error = TRUE, { + vec_set_symmetric_difference(1, 2, 3) + }) }) test_that("`ptype` is respected", { expect_identical(vec_set_intersect(1, 1, ptype = integer()), 1L) expect_identical(vec_set_difference(1, 1, ptype = integer()), integer()) expect_identical(vec_set_union(1, 2, ptype = integer()), c(1L, 2L)) + expect_identical(vec_set_symmetric_difference(1, 2, ptype = integer()), c(1L, 2L)) expect_snapshot(error = TRUE, { vec_set_intersect(1, 1.5, ptype = integer()) @@ -284,6 +386,9 @@ test_that("`ptype` is respected", { expect_snapshot(error = TRUE, { vec_set_union(1, 1.5, ptype = integer()) }) + expect_snapshot(error = TRUE, { + vec_set_symmetric_difference(1, 1.5, ptype = integer()) + }) }) test_that("`x_arg` and `y_arg` can be adjusted", { @@ -296,6 +401,9 @@ test_that("`x_arg` and `y_arg` can be adjusted", { expect_snapshot(error = TRUE, { vec_set_union(1, "2", x_arg = "foo", y_arg = "bar") }) + expect_snapshot(error = TRUE, { + vec_set_symmetric_difference(1, "2", x_arg = "foo", y_arg = "bar") + }) expect_snapshot(error = TRUE, { vec_set_intersect(1, "2", x_arg = "", y_arg = "") @@ -312,6 +420,9 @@ test_that("`error_call` can be adjusted", { my_set_union <- function() { vec_set_union(1, "x", error_call = current_env()) } + my_set_symmetric_difference <- function() { + vec_set_symmetric_difference(1, "x", error_call = current_env()) + } expect_snapshot(error = TRUE, { my_set_intersect() @@ -322,4 +433,7 @@ test_that("`error_call` can be adjusted", { expect_snapshot(error = TRUE, { my_set_union() }) + expect_snapshot(error = TRUE, { + my_set_symmetric_difference() + }) }) From 06dc9b93ad8f1b02b1b7d78399843d62c8f46154 Mon Sep 17 00:00:00 2001 From: Davis Vaughan Date: Thu, 19 Jan 2023 10:13:12 -0500 Subject: [PATCH 210/312] Implement `vec_expand_grid()` (#1766) * Expose `list_sizes()` for C level usage * Expose `vec_rep()` and `vec_rep_each()` for C level usage * Implement `vec_expand_grid()` * Add to `_pkgdown.yml` * NEWS bullet * Update src/expand.c Co-authored-by: Lionel Henry * Tweak message based on code review * Add a sentence about the general functionality * Use the correct max value for `R_len_t` Co-authored-by: Lionel Henry --- NAMESPACE | 1 + NEWS.md | 3 + R/expand.R | 66 ++++++++++++++ _pkgdown.yml | 1 + man/vec_expand_grid.Rd | 69 ++++++++++++++ src/decl/expand-decl.h | 2 + src/decl/size-decl.h | 3 - src/expand.c | 138 ++++++++++++++++++++++++++++ src/expand.h | 17 ++++ src/init.c | 2 + src/rep.c | 2 - src/rep.h | 16 ++++ src/size.c | 1 - src/size.h | 2 + src/vctrs.h | 2 + tests/testthat/_snaps/expand.md | 78 ++++++++++++++++ tests/testthat/test-expand.R | 157 ++++++++++++++++++++++++++++++++ 17 files changed, 554 insertions(+), 6 deletions(-) create mode 100644 R/expand.R create mode 100644 man/vec_expand_grid.Rd create mode 100644 src/decl/expand-decl.h create mode 100644 src/expand.c create mode 100644 src/expand.h create mode 100644 src/rep.h create mode 100644 tests/testthat/_snaps/expand.md create mode 100644 tests/testthat/test-expand.R diff --git a/NAMESPACE b/NAMESPACE index ec52c3f71..e0958f5c3 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -561,6 +561,7 @@ export(vec_duplicate_id) export(vec_empty) export(vec_equal) export(vec_equal_na) +export(vec_expand_grid) export(vec_fill_missing) export(vec_group_id) export(vec_group_loc) diff --git a/NEWS.md b/NEWS.md index b87d4b588..2c99bbc42 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,5 +1,8 @@ # vctrs (development version) +* New `vec_expand_grid()`, which is a lower level helper that is similar to + `tidyr::expand_grid()` (#1325). + * The maximum load factor of the internal dictionary was reduced from 77% to 50%, which improves performance of functions like `vec_match()`, `vec_set_intersect()`, and `vec_unique()` in some cases (#1760). diff --git a/R/expand.R b/R/expand.R new file mode 100644 index 000000000..1c3bcda26 --- /dev/null +++ b/R/expand.R @@ -0,0 +1,66 @@ +#' Create a data frame from all combinations of the inputs +#' +#' @description +#' `vec_expand_grid()` creates a new data frame by creating a grid of all +#' possible combinations of the input vectors. It is inspired by +#' [expand.grid()]. Compared with `expand.grid()`, it: +#' +#' - Produces sorted output by default by varying the first column the slowest, +#' rather than the fastest. Control this with `.vary`. +#' +#' - Never converts strings to factors. +#' +#' - Does not add additional attributes. +#' +#' - Drops `NULL` inputs. +#' +#' - Can expand any vector type, including data frames and [records][new_rcrd]. +#' +#' @details +#' If any input is empty (i.e. size 0), then the result will have 0 rows. +#' +#' If no inputs are provided, the result is a 1 row data frame with 0 columns. +#' This is consistent with the fact that `prod()` with no inputs returns `1`. +#' +#' @inheritParams rlang::args_error_context +#' @inheritParams df_list +#' +#' @param ... Name-value pairs. The name will become the column name in the +#' resulting data frame. +#' +#' @param .vary One of: +#' +#' - `"slowest"` to vary the first column slowest. This produces sorted +#' output and is generally the most useful. +#' +#' - `"fastest"` to vary the first column fastest. This matches the behavior +#' of [expand.grid()]. +#' +#' @returns +#' A data frame with as many columns as there are inputs in `...` and as many +#' rows as the [prod()] of the sizes of the inputs. +#' +#' @export +#' @examples +#' vec_expand_grid(x = 1:2, y = 1:3) +#' +#' # Use `.vary` to match `expand.grid()`: +#' vec_expand_grid(x = 1:2, y = 1:3, .vary = "fastest") +#' +#' # Can also expand data frames +#' vec_expand_grid( +#' x = data_frame(a = 1:2, b = 3:4), +#' y = 1:4 +#' ) +vec_expand_grid <- function(..., + .vary = "slowest", + .name_repair = "check_unique", + .error_call = current_env()) { + .vary <- arg_match0( + arg = .vary, + values = c("slowest", "fastest"), + error_call = .error_call + ) + + .Call(ffi_vec_expand_grid, list2(...), .vary, .name_repair, environment()) +} diff --git a/_pkgdown.yml b/_pkgdown.yml index 51a999d44..bb5286ba0 100644 --- a/_pkgdown.yml +++ b/_pkgdown.yml @@ -94,6 +94,7 @@ reference: - vec_rep_each - vec_seq_along - vec_identify_runs + - vec_expand_grid - title: New classes contents: diff --git a/man/vec_expand_grid.Rd b/man/vec_expand_grid.Rd new file mode 100644 index 000000000..e0525adc8 --- /dev/null +++ b/man/vec_expand_grid.Rd @@ -0,0 +1,69 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/expand.R +\name{vec_expand_grid} +\alias{vec_expand_grid} +\title{Create a data frame from all combinations of the inputs} +\usage{ +vec_expand_grid( + ..., + .vary = "slowest", + .name_repair = "check_unique", + .error_call = current_env() +) +} +\arguments{ +\item{...}{Name-value pairs. The name will become the column name in the +resulting data frame.} + +\item{.vary}{One of: +\itemize{ +\item \code{"slowest"} to vary the first column slowest. This produces sorted +output and is generally the most useful. +\item \code{"fastest"} to vary the first column fastest. This matches the behavior +of \code{\link[=expand.grid]{expand.grid()}}. +}} + +\item{.name_repair}{One of \code{"check_unique"}, \code{"unique"}, \code{"universal"}, +\code{"minimal"}, \code{"unique_quiet"}, or \code{"universal_quiet"}. See \code{\link[=vec_as_names]{vec_as_names()}} +for the meaning of these options.} + +\item{.error_call}{The execution environment of a currently +running function, e.g. \code{caller_env()}. The function will be +mentioned in error messages as the source of the error. See the +\code{call} argument of \code{\link[rlang:abort]{abort()}} for more information.} +} +\value{ +A data frame with as many columns as there are inputs in \code{...} and as many +rows as the \code{\link[=prod]{prod()}} of the sizes of the inputs. +} +\description{ +\code{vec_expand_grid()} creates a new data frame by creating a grid of all +possible combinations of the input vectors. It is inspired by +\code{\link[=expand.grid]{expand.grid()}}. Compared with \code{expand.grid()}, it: +\itemize{ +\item Produces sorted output by default by varying the first column the slowest, +rather than the fastest. Control this with \code{.vary}. +\item Never converts strings to factors. +\item Does not add additional attributes. +\item Drops \code{NULL} inputs. +\item Can expand any vector type, including data frames and \link[=new_rcrd]{records}. +} +} +\details{ +If any input is empty (i.e. size 0), then the result will have 0 rows. + +If no inputs are provided, the result is a 1 row data frame with 0 columns. +This is consistent with the fact that \code{prod()} with no inputs returns \code{1}. +} +\examples{ +vec_expand_grid(x = 1:2, y = 1:3) + +# Use `.vary` to match `expand.grid()`: +vec_expand_grid(x = 1:2, y = 1:3, .vary = "fastest") + +# Can also expand data frames +vec_expand_grid( + x = data_frame(a = 1:2, b = 3:4), + y = 1:4 +) +} diff --git a/src/decl/expand-decl.h b/src/decl/expand-decl.h new file mode 100644 index 000000000..05f6c98e1 --- /dev/null +++ b/src/decl/expand-decl.h @@ -0,0 +1,2 @@ +static inline +enum vctrs_expand_vary parse_vary(r_obj* vary); diff --git a/src/decl/size-decl.h b/src/decl/size-decl.h index 556a95e93..739e85411 100644 --- a/src/decl/size-decl.h +++ b/src/decl/size-decl.h @@ -4,8 +4,5 @@ r_ssize vec_size_opts(r_obj* x, const struct vec_error_opts* opts); static r_ssize vec_raw_size(r_obj* x); -static -r_obj* list_sizes(r_obj* x, const struct vec_error_opts* err); - static bool list_all_size(r_obj* xs, r_ssize size); diff --git a/src/expand.c b/src/expand.c new file mode 100644 index 000000000..a2914e978 --- /dev/null +++ b/src/expand.c @@ -0,0 +1,138 @@ +#include "vctrs.h" +#include "type-data-frame.h" + +#include "decl/expand-decl.h" + +r_obj* ffi_vec_expand_grid(r_obj* xs, + r_obj* ffi_vary, + r_obj* ffi_name_repair, + r_obj* frame) { + struct r_lazy error_call = { .x = syms.dot_error_call, .env = frame }; + + enum vctrs_expand_vary vary = parse_vary(ffi_vary); + + struct name_repair_opts name_repair_opts = new_name_repair_opts( + ffi_name_repair, + lazy_args.dot_name_repair, + false, + error_call + ); + KEEP(name_repair_opts.shelter); + + r_obj* out = vec_expand_grid(xs, vary, &name_repair_opts, error_call); + + FREE(1); + return out; +} + +r_obj* vec_expand_grid(r_obj* xs, + enum vctrs_expand_vary vary, + const struct name_repair_opts* p_name_repair_opts, + struct r_lazy error_call) { + vec_check_list(xs, vec_args.empty, error_call); + + if (vec_any_missing(xs)) { + // Drop `NULL`s before any other checks + r_obj* complete = KEEP(vec_detect_complete(xs)); + xs = vec_slice(xs, complete); + FREE(1); + } + KEEP(xs); + + const r_ssize n = r_length(xs); + + r_obj* out = KEEP(r_alloc_list(n)); + + r_obj* names = KEEP(vec_names2(xs)); + if (!r_is_minimal_names(names)) { + r_abort_lazy_call(error_call, "All inputs must be named."); + } + names = vec_as_names(names, p_name_repair_opts); + r_attrib_poke_names(out, names); + + const struct vec_error_opts error_opts = { + .p_arg = vec_args.empty, + .call = error_call + }; + + r_obj* sizes = KEEP(list_sizes(xs, &error_opts)); + const int* v_sizes = r_int_cbegin(sizes); + + r_obj* cumulative = KEEP(r_alloc_raw(n * sizeof(r_ssize))); + r_ssize* v_cumulative = r_raw_begin(cumulative); + + r_ssize size = 1; + + for (r_ssize i = 0; i < n; ++i) { + size = r_ssize_mult(size, v_sizes[i]); + v_cumulative[i] = size; + } + + // TODO: Support long vectors here + if (size > R_LEN_T_MAX) { + r_abort_lazy_call( + error_call, + "Long vectors are not yet supported. " + "Expansion results in an allocation larger than 2^31-1 elements. " + "Attempted allocation size was %.0lf.", + (double) size + ); + } + + r_obj* const* v_xs = r_list_cbegin(xs); + + r_obj* ffi_times_each = KEEP(r_alloc_integer(1)); + int* p_ffi_times_each = r_int_begin(ffi_times_each); + + for (r_ssize i = 0; i < n; ++i) { + r_obj* x = v_xs[i]; + + r_ssize times_each = 0; + r_ssize times = 0; + + if (size != 0) { + switch (vary) { + case VCTRS_EXPAND_VARY_slowest: { + times_each = size / v_cumulative[i]; + times = v_cumulative[i] / v_sizes[i]; + break; + }; + case VCTRS_EXPAND_VARY_fastest: { + times_each = v_cumulative[i] / v_sizes[i]; + times = size / v_cumulative[i]; + break; + } + } + } + + *p_ffi_times_each = r_ssize_as_integer(times_each); + + x = KEEP(vec_rep_each(x, ffi_times_each, error_call, vec_args.x, vec_args.empty)); + x = vec_rep(x, r_ssize_as_integer(times), error_call, vec_args.x, vec_args.empty); + + r_list_poke(out, i, x); + + FREE(1); + } + + init_data_frame(out, size); + + FREE(6); + return out; +} + +static inline +enum vctrs_expand_vary parse_vary(r_obj* vary) { + if (!r_is_string(vary)) { + r_stop_internal("`vary` must be a string."); + } + + const char* c_vary = r_chr_get_c_string(vary, 0); + + if (!strcmp(c_vary, "slowest")) return VCTRS_EXPAND_VARY_slowest; + if (!strcmp(c_vary, "fastest")) return VCTRS_EXPAND_VARY_fastest; + + r_stop_internal( + "`vary` must be either \"slowest\" or \"fastest\"." + ); +} diff --git a/src/expand.h b/src/expand.h new file mode 100644 index 000000000..ffedbe566 --- /dev/null +++ b/src/expand.h @@ -0,0 +1,17 @@ +#ifndef VCTRS_EXPAND_H +#define VCTRS_EXPAND_H + +#include "vctrs-core.h" +#include "names.h" + +enum vctrs_expand_vary { + VCTRS_EXPAND_VARY_slowest = 0, + VCTRS_EXPAND_VARY_fastest = 1 +}; + +r_obj* vec_expand_grid(r_obj* xs, + enum vctrs_expand_vary vary, + const struct name_repair_opts* p_name_repair_opts, + struct r_lazy error_call); + +#endif diff --git a/src/init.c b/src/init.c index 65c40873c..ce5de0ad7 100644 --- a/src/init.c +++ b/src/init.c @@ -156,6 +156,7 @@ extern r_obj* ffi_vec_set_intersect(r_obj*, r_obj*, r_obj*, r_obj*); extern r_obj* ffi_vec_set_difference(r_obj*, r_obj*, r_obj*, r_obj*); extern r_obj* ffi_vec_set_union(r_obj*, r_obj*, r_obj*, r_obj*); extern r_obj* ffi_vec_set_symmetric_difference(r_obj*, r_obj*, r_obj*, r_obj*); +extern r_obj* ffi_vec_expand_grid(r_obj*, r_obj*, r_obj*, r_obj*); // Maturing @@ -335,6 +336,7 @@ static const R_CallMethodDef CallEntries[] = { {"ffi_vec_set_difference", (DL_FUNC) &ffi_vec_set_difference, 4}, {"ffi_vec_set_union", (DL_FUNC) &ffi_vec_set_union, 4}, {"ffi_vec_set_symmetric_difference", (DL_FUNC) &ffi_vec_set_symmetric_difference, 4}, + {"ffi_vec_expand_grid", (DL_FUNC) &ffi_vec_expand_grid, 4}, {"ffi_exp_vec_cast", (DL_FUNC) &exp_vec_cast, 2}, {NULL, NULL, 0} }; diff --git a/src/rep.c b/src/rep.c index 7b1e57deb..37dd184cf 100644 --- a/src/rep.c +++ b/src/rep.c @@ -3,7 +3,6 @@ #include "decl/rep-decl.h" -static r_obj* vec_rep(r_obj* x, int times, struct r_lazy error_call, @@ -74,7 +73,6 @@ r_obj* ffi_vec_rep(r_obj* x, r_obj* ffi_times, r_obj* frame) { // ----------------------------------------------------------------------------- -static r_obj* vec_rep_each(r_obj* x, r_obj* times, struct r_lazy error_call, diff --git a/src/rep.h b/src/rep.h new file mode 100644 index 000000000..64bba414a --- /dev/null +++ b/src/rep.h @@ -0,0 +1,16 @@ +#ifndef VCTRS_REP_H +#define VCTRS_REP_H + +r_obj* vec_rep(r_obj* x, + int times, + struct r_lazy error_call, + struct vctrs_arg* p_x_arg, + struct vctrs_arg* p_times_arg); + +r_obj* vec_rep_each(r_obj* x, + r_obj* times, + struct r_lazy error_call, + struct vctrs_arg* p_x_arg, + struct vctrs_arg* p_times_arg); + +#endif diff --git a/src/size.c b/src/size.c index 9b448d25e..61712c421 100644 --- a/src/size.c +++ b/src/size.c @@ -80,7 +80,6 @@ r_obj* ffi_list_sizes(r_obj* x, r_obj* frame) { return list_sizes(x, &err); } -static r_obj* list_sizes(r_obj* x, const struct vec_error_opts* opts) { if (!vec_is_list(x)) { r_abort_lazy_call(opts->call, diff --git a/src/size.h b/src/size.h index ad1e7692e..3dcaec09a 100644 --- a/src/size.h +++ b/src/size.h @@ -23,6 +23,8 @@ r_obj* vec_recycle_fallback(r_obj* x, struct vctrs_arg* x_arg, struct r_lazy call); +r_obj* list_sizes(r_obj* x, const struct vec_error_opts* opts); + r_ssize df_size(r_obj* x); r_ssize df_raw_size(r_obj* x); r_ssize df_rownames_size(r_obj* x); diff --git a/src/vctrs.h b/src/vctrs.h index 9a1fa8c86..0de83938c 100644 --- a/src/vctrs.h +++ b/src/vctrs.h @@ -25,6 +25,7 @@ bool vec_is_unspecified(SEXP x); #include "dictionary.h" #include "dim.h" #include "equal.h" +#include "expand.h" #include "hash.h" #include "lazy.h" #include "match-compare.h" @@ -44,6 +45,7 @@ bool vec_is_unspecified(SEXP x); #include "ptype.h" #include "ptype2-dispatch.h" #include "ptype2.h" +#include "rep.h" #include "runs.h" #include "set.h" #include "shape.h" diff --git a/tests/testthat/_snaps/expand.md b/tests/testthat/_snaps/expand.md new file mode 100644 index 000000000..0c39110fd --- /dev/null +++ b/tests/testthat/_snaps/expand.md @@ -0,0 +1,78 @@ +# inputs must be named + + Code + vec_expand_grid(1) + Condition + Error in `vec_expand_grid()`: + ! All inputs must be named. + +--- + + Code + vec_expand_grid(x = 1, 2, y = 3) + Condition + Error in `vec_expand_grid()`: + ! All inputs must be named. + +# catches duplicate names by default + + Code + vec_expand_grid(a = 1, a = 2) + Condition + Error in `vec_expand_grid()`: + ! Names must be unique. + x These names are duplicated: + * "a" at locations 1 and 2. + i Use argument `.name_repair` to specify repair strategy. + +# errors on non vectors and mentions the element name + + Code + vec_expand_grid(y = environment()) + Condition + Error in `vec_expand_grid()`: + ! `y` must be a vector, not an environment. + +# can adjust the `.error_call` + + Code + my_expand_grid() + Condition + Error in `my_expand_grid()`: + ! `x` must be a vector, not an environment. + +# errors nicely when expansion results in a size larger than `R_len_t` + + Code + vec_expand_grid(x = x, y = y) + Condition + Error in `vec_expand_grid()`: + ! Long vectors are not yet supported. Expansion results in an allocation larger than 2^31-1 elements. Attempted allocation size was 3221225469. + +# errors nicely when expansion results in a size larger than `R_xlen_t` + + Code + vec_expand_grid(x = x, y = x) + Condition + Error in `vec_expand_grid()`: + ! Result too large for an `r_ssize`. + i In file './rlang/c-utils.h' at line . + i This is an internal error that was detected in the vctrs package. + Please report it at with a reprex () and the full backtrace. + +# validates `.vary` + + Code + vec_expand_grid(.vary = 1) + Condition + Error in `vec_expand_grid()`: + ! `.vary` must be a string or character vector. + +--- + + Code + vec_expand_grid(.vary = "x") + Condition + Error in `vec_expand_grid()`: + ! `.vary` must be one of "slowest" or "fastest", not "x". + diff --git a/tests/testthat/test-expand.R b/tests/testthat/test-expand.R new file mode 100644 index 000000000..25186aa80 --- /dev/null +++ b/tests/testthat/test-expand.R @@ -0,0 +1,157 @@ +test_that("expands the first column slowest by default", { + x <- 1:4 + y <- 1:3 + z <- 1:2 + + expect_identical( + vec_expand_grid(x = x, y = y, z = z), + data_frame( + x = vec_rep(vec_rep_each(x, times = 6), times = 1), + y = vec_rep(vec_rep_each(y, times = 2), times = 4), + z = vec_rep(vec_rep_each(z, times = 1), times = 12) + ) + ) +}) + +test_that("can expand the first column fastest with `.vary`", { + x <- 1:4 + y <- 1:3 + z <- 1:2 + + expect_identical( + vec_expand_grid(x = x, y = y, z = z, .vary = "fastest"), + data_frame( + x = vec_rep(vec_rep_each(x, times = 1), times = 6), + y = vec_rep(vec_rep_each(y, times = 4), times = 2), + z = vec_rep(vec_rep_each(z, times = 12), times = 1) + ) + ) +}) + +test_that("size 0 elements force a size 0 result", { + expect_identical( + vec_expand_grid(x = 1:3, y = integer(), z = 1:2), + data_frame(x = integer(), y = integer(), z = integer()) + ) + + expect_identical( + vec_expand_grid(x = integer()), + data_frame(x = integer()) + ) +}) + +test_that("returns 1 row and 0 cols with no input", { + # Because `prod(integer()) == 1L` + expect_identical(vec_expand_grid(), data_frame(.size = 1L)) +}) + +test_that("drops `NULL` values", { + expect_identical( + vec_expand_grid(NULL, NULL), + vec_expand_grid() + ) + + # And that happens before all names checks + expect_identical( + vec_expand_grid(x = 1:2, x = NULL, y = 1:3, NULL), + vec_expand_grid(x = 1:2, y = 1:3) + ) +}) + +test_that("works with data frame inputs", { + x <- data_frame(a = 1:2, b = 2:3) + y <- 1:3 + + expect_identical( + vec_expand_grid(x = x, y = y), + data_frame( + x = vec_rep(vec_rep_each(x, times = 3), times = 1), + y = vec_rep(vec_rep_each(y, times = 1), times = 2), + ) + ) +}) + +test_that("`.name_repair` isn't affected by `.vary`", { + expect <- vec_as_names(c("a", "b", "a", "z"), repair = "unique_quiet") + + expect_named( + vec_expand_grid(a = 1, b = 2, a = 3, z = 4, .vary = "slowest", .name_repair = "unique_quiet"), + expect + ) + expect_named( + vec_expand_grid(a = 1, b = 2, a = 3, z = 4, .vary = "fastest", .name_repair = "unique_quiet"), + expect + ) +}) + +test_that("can use `.name_repair`", { + expect_identical( + vec_expand_grid(a = 1:2, a = 2:3, .name_repair = "minimal"), + data_frame(a = c(1L, 1L, 2L, 2L), a = c(2L, 3L, 2L, 3L), .name_repair = "minimal") + ) +}) + +test_that("inputs must be named", { + expect_snapshot(error = TRUE, { + vec_expand_grid(1) + }) + expect_snapshot(error = TRUE, { + vec_expand_grid(x = 1, 2, y = 3) + }) +}) + +test_that("catches duplicate names by default", { + expect_snapshot(error = TRUE, { + vec_expand_grid(a = 1, a = 2) + }) +}) + +test_that("errors on non vectors and mentions the element name", { + expect_snapshot(error = TRUE, { + vec_expand_grid(y = environment()) + }) +}) + +test_that("can adjust the `.error_call`", { + my_expand_grid <- function() { + vec_expand_grid(x = environment(), .error_call = current_env()) + } + + expect_snapshot(error = TRUE, { + my_expand_grid() + }) +}) + +test_that("errors nicely when expansion results in a size larger than `R_len_t`", { + # Windows 32-bit doesn't support long vectors of this size, and the + # intermediate `r_ssize` will be too large + skip_if(.Machine$sizeof.pointer < 8L, message = "No long vector support") + + x <- seq_len((2^31 - 1) / 2) + y <- 1:3 + + expect_snapshot(error = TRUE, { + vec_expand_grid(x = x, y = y) + }) +}) + +test_that("errors nicely when expansion results in a size larger than `R_xlen_t`", { + # Windows 32-bit doesn't support long vectors of this size, and the + # intermediate `r_ssize` will be too large + skip_if(.Machine$sizeof.pointer < 8L, message = "No long vector support") + + x <- seq_len(2^31 - 1) + + expect_snapshot(error = TRUE, transform = scrub_internal_error_line_number, { + vec_expand_grid(x = x, y = x) + }) +}) + +test_that("validates `.vary`", { + expect_snapshot(error = TRUE, { + vec_expand_grid(.vary = 1) + }) + expect_snapshot(error = TRUE, { + vec_expand_grid(.vary = "x") + }) +}) From 4a3a2f5f19998b1060eeee76cb120ba3a173d98a Mon Sep 17 00:00:00 2001 From: Davis Vaughan Date: Thu, 19 Jan 2023 12:05:38 -0500 Subject: [PATCH 211/312] Branchless `df_identify_runs()` approach (#1684) * Branchless `df_identify_runs()` approach * No longer need 0-column special case * NEWS bullet --- NEWS.md | 2 + src/decl/runs-decl.h | 52 ++++--------- src/runs.c | 174 +++++++++++-------------------------------- 3 files changed, 61 insertions(+), 167 deletions(-) diff --git a/NEWS.md b/NEWS.md index 2c99bbc42..edc951620 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,5 +1,7 @@ # vctrs (development version) +* `vec_identify_runs()` is now faster when used with data frames (#1684). + * New `vec_expand_grid()`, which is a lower level helper that is similar to `tidyr::expand_grid()` (#1325). diff --git a/src/decl/runs-decl.h b/src/decl/runs-decl.h index 69d910d03..e84f80ce7 100644 --- a/src/decl/runs-decl.h +++ b/src/decl/runs-decl.h @@ -35,43 +35,19 @@ int df_identify_runs(r_obj* x, r_ssize size, int* v_out); static inline -int vec_identify_runs_col(r_obj* x, - int id, - struct df_short_circuit_info* p_info, - int* v_out); +void col_identify_runs(r_obj* x, r_ssize size, bool* v_where); static inline -int lgl_identify_runs_col(r_obj* x, - int id, - struct df_short_circuit_info* p_info, - int* v_out); -static inline -int int_identify_runs_col(r_obj* x, - int id, - struct df_short_circuit_info* p_info, - int* v_out); -static inline -int dbl_identify_runs_col(r_obj* x, - int id, - struct df_short_circuit_info* p_info, - int* v_out); -static inline -int cpl_identify_runs_col(r_obj* x, - int id, - struct df_short_circuit_info* p_info, - int* v_out); -static inline -int chr_identify_runs_col(r_obj* x, - int id, - struct df_short_circuit_info* p_info, - int* v_out); -static inline -int raw_identify_runs_col(r_obj* x, - int id, - struct df_short_circuit_info* p_info, - int* v_out); -static inline -int list_identify_runs_col(r_obj* x, - int id, - struct df_short_circuit_info* p_info, - int* v_out); +void lgl_col_identify_runs(r_obj* x, r_ssize size, bool* v_where); +static inline +void int_col_identify_runs(r_obj* x, r_ssize size, bool* v_where); +static inline +void dbl_col_identify_runs(r_obj* x, r_ssize size, bool* v_where); +static inline +void cpl_col_identify_runs(r_obj* x, r_ssize size, bool* v_where); +static inline +void chr_col_identify_runs(r_obj* x, r_ssize size, bool* v_where); +static inline +void raw_col_identify_runs(r_obj* x, r_ssize size, bool* v_where); +static inline +void list_col_identify_runs(r_obj* x, r_ssize size, bool* v_where); diff --git a/src/runs.c b/src/runs.c index 4bcadb981..c5d97e3fe 100644 --- a/src/runs.c +++ b/src/runs.c @@ -242,173 +242,89 @@ int list_identify_runs(r_obj* x, r_ssize size, int* v_out) { static inline int df_identify_runs(r_obj* x, r_ssize size, int* v_out) { - int n_prot = 0; - + const r_ssize n_col = r_length(x); r_obj* const* v_x = r_list_cbegin(x); - struct df_short_circuit_info info = new_df_short_circuit_info(size, false); - PROTECT_DF_SHORT_CIRCUIT_INFO(&info, &n_prot); - - int id = 1; - r_ssize n_col = r_length(x); + // Boolean vector that will eventually be `true` if we are in a run + // continuation, and `false` if we are starting a new run. + r_obj* where_shelter = KEEP(r_alloc_raw(size * sizeof(bool))); + bool* v_where = (bool*) r_raw_begin(where_shelter); - // Define 0 column case to be a single run - if (n_col == 0) { - r_p_int_fill(v_out, id, size); - FREE(n_prot); - return id; + v_where[0] = false; + for (r_ssize i = 1; i < size; ++i) { + v_where[i] = true; } - // Handle first case - v_out[0] = id; - info.p_row_known[0] = true; - --info.remaining; - - // Compute non-sequential run IDs for (r_ssize i = 0; i < n_col; ++i) { - r_obj* col = v_x[i]; - - id = vec_identify_runs_col(col, id, &info, v_out); - - // All values are unique - if (info.remaining == 0) { - break; - } + col_identify_runs(v_x[i], size, v_where); } - id = 1; - int previous = v_out[0]; + int id = 1; - // Overwrite with sequential IDs + v_out[0] = id; for (r_ssize i = 1; i < size; ++i) { - const int current = v_out[i]; - - if (current != previous) { - ++id; - previous = current; - } - + id += !v_where[i]; v_out[i] = id; } - FREE(n_prot); + FREE(1); return id; } -// ----------------------------------------------------------------------------- - static inline -int vec_identify_runs_col(r_obj* x, - int id, - struct df_short_circuit_info* p_info, - int* v_out) { +void col_identify_runs(r_obj* x, r_ssize size, bool* v_where) { switch (vec_proxy_typeof(x)) { - case VCTRS_TYPE_logical: return lgl_identify_runs_col(x, id, p_info, v_out); - case VCTRS_TYPE_integer: return int_identify_runs_col(x, id, p_info, v_out); - case VCTRS_TYPE_double: return dbl_identify_runs_col(x, id, p_info, v_out); - case VCTRS_TYPE_complex: return cpl_identify_runs_col(x, id, p_info, v_out); - case VCTRS_TYPE_character: return chr_identify_runs_col(x, id, p_info, v_out); - case VCTRS_TYPE_raw: return raw_identify_runs_col(x, id, p_info, v_out); - case VCTRS_TYPE_list: return list_identify_runs_col(x, id, p_info, v_out); + case VCTRS_TYPE_logical: lgl_col_identify_runs(x, size, v_where); break; + case VCTRS_TYPE_integer: int_col_identify_runs(x, size, v_where); break; + case VCTRS_TYPE_double: dbl_col_identify_runs(x, size, v_where); break; + case VCTRS_TYPE_complex: cpl_col_identify_runs(x, size, v_where); break; + case VCTRS_TYPE_character: chr_col_identify_runs(x, size, v_where); break; + case VCTRS_TYPE_raw: raw_col_identify_runs(x, size, v_where); break; + case VCTRS_TYPE_list: list_col_identify_runs(x, size, v_where); break; case VCTRS_TYPE_dataframe: r_stop_internal("Data frame columns should be flattened."); case VCTRS_TYPE_scalar: r_abort("Can't compare scalars."); default: r_abort("Unimplemented type."); } } -// ----------------------------------------------------------------------------- - -#define VEC_IDENTIFY_RUNS_COL(CTYPE, CBEGIN, EQUAL_NA_EQUAL) { \ - CTYPE const* v_x = CBEGIN(x); \ - \ - /* First row is always known, so `run_val` and `run_id` */ \ - /* will always be overwritten immediately below. */ \ - /* But for gcc11 we have to initialize these variables. */ \ - CTYPE run_val = v_x[0]; \ - int run_id = 0; \ - \ - for (r_ssize i = 0; i < p_info->size; ++i) { \ - /* Start of new run */ \ - if (p_info->p_row_known[i]) { \ - run_val = v_x[i]; \ - run_id = v_out[i]; \ - continue; \ - } \ - \ - CTYPE const elt = v_x[i]; \ - const int eq = EQUAL_NA_EQUAL(elt, run_val); \ - \ - /* Update ID of identical values */ \ - if (eq != 0) { \ - v_out[i] = run_id; \ - continue; \ - } \ - \ - ++id; \ - run_val = elt; \ - run_id = id; \ - v_out[i] = id; \ - \ - /* This is a run change, so don't check this row again */ \ - p_info->p_row_known[i] = true; \ - --p_info->remaining; \ - \ - if (p_info->remaining == 0) { \ - break; \ - } \ - } \ - \ - return id; \ +#define VEC_COL_IDENTIFY_RUNS(CTYPE, CBEGIN, EQUAL_NA_EQUAL) { \ + CTYPE const* v_x = CBEGIN(x); \ + CTYPE ref = v_x[0]; \ + \ + for (r_ssize i = 1; i < size; ++i) { \ + CTYPE const elt = v_x[i]; \ + v_where[i] = v_where[i] && EQUAL_NA_EQUAL(ref, elt); \ + ref = elt; \ + } \ } static inline -int lgl_identify_runs_col(r_obj* x, - int id, - struct df_short_circuit_info* p_info, - int* v_out) { - VEC_IDENTIFY_RUNS_COL(int, r_lgl_cbegin, lgl_equal_na_equal); +void lgl_col_identify_runs(r_obj* x, r_ssize size, bool* v_where) { + VEC_COL_IDENTIFY_RUNS(int, r_lgl_cbegin, lgl_equal_na_equal); } static inline -int int_identify_runs_col(r_obj* x, - int id, - struct df_short_circuit_info* p_info, - int* v_out) { - VEC_IDENTIFY_RUNS_COL(int, r_int_cbegin, int_equal_na_equal); +void int_col_identify_runs(r_obj* x, r_ssize size, bool* v_where) { + VEC_COL_IDENTIFY_RUNS(int, r_int_cbegin, int_equal_na_equal); } static inline -int dbl_identify_runs_col(r_obj* x, - int id, - struct df_short_circuit_info* p_info, - int* v_out) { - VEC_IDENTIFY_RUNS_COL(double, r_dbl_cbegin, dbl_equal_na_equal); +void dbl_col_identify_runs(r_obj* x, r_ssize size, bool* v_where) { + VEC_COL_IDENTIFY_RUNS(double, r_dbl_cbegin, dbl_equal_na_equal); } static inline -int cpl_identify_runs_col(r_obj* x, - int id, - struct df_short_circuit_info* p_info, - int* v_out) { - VEC_IDENTIFY_RUNS_COL(Rcomplex, r_cpl_cbegin, cpl_equal_na_equal); +void cpl_col_identify_runs(r_obj* x, r_ssize size, bool* v_where) { + VEC_COL_IDENTIFY_RUNS(Rcomplex, r_cpl_cbegin, cpl_equal_na_equal); } static inline -int chr_identify_runs_col(r_obj* x, - int id, - struct df_short_circuit_info* p_info, - int* v_out) { - VEC_IDENTIFY_RUNS_COL(r_obj*, r_chr_cbegin, chr_equal_na_equal); +void chr_col_identify_runs(r_obj* x, r_ssize size, bool* v_where) { + VEC_COL_IDENTIFY_RUNS(r_obj*, r_chr_cbegin, chr_equal_na_equal); } static inline -int raw_identify_runs_col(r_obj* x, - int id, - struct df_short_circuit_info* p_info, - int* v_out) { - VEC_IDENTIFY_RUNS_COL(Rbyte, r_raw_cbegin, raw_equal_na_equal); +void raw_col_identify_runs(r_obj* x, r_ssize size, bool* v_where) { + VEC_COL_IDENTIFY_RUNS(Rbyte, r_raw_cbegin, raw_equal_na_equal); } static inline -int list_identify_runs_col(r_obj* x, - int id, - struct df_short_circuit_info* p_info, - int* v_out) { - VEC_IDENTIFY_RUNS_COL(r_obj*, r_list_cbegin, list_equal_na_equal); +void list_col_identify_runs(r_obj* x, r_ssize size, bool* v_where) { + VEC_COL_IDENTIFY_RUNS(r_obj*, r_list_cbegin, list_equal_na_equal); } -#undef VEC_IDENTIFY_RUNS_COL +#undef VEC_COL_IDENTIFY_RUNS From 13b645bc5cc7322718c5e7497aad7cade2a346c4 Mon Sep 17 00:00:00 2001 From: DavisVaughan Date: Thu, 19 Jan 2023 15:12:38 -0500 Subject: [PATCH 212/312] Bump roxygen2 version --- DESCRIPTION | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/DESCRIPTION b/DESCRIPTION index d33cb2623..1695964bc 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -56,6 +56,6 @@ SystemRequirements: Encoding: UTF-8 Language: en-GB Roxygen: list(markdown = TRUE) -RoxygenNote: 7.2.1 +RoxygenNote: 7.2.3 Config/testthat/edition: 3 Config/Needs/website: tidyverse/tidytemplate From d18c323b784e6c7b653886124782826c5d1caf92 Mon Sep 17 00:00:00 2001 From: Davis Vaughan Date: Thu, 19 Jan 2023 16:42:46 -0500 Subject: [PATCH 213/312] Update the rlang C library (#1768) --- src/rlang/dyn-array.c | 14 ++------ src/rlang/dyn-array.h | 77 ++++++++++++++++++++++++++----------------- src/rlang/stack.c | 13 ++++++-- 3 files changed, 60 insertions(+), 44 deletions(-) diff --git a/src/rlang/dyn-array.c b/src/rlang/dyn-array.c index 07ad57ca4..0a986aa1b 100644 --- a/src/rlang/dyn-array.c +++ b/src/rlang/dyn-array.c @@ -70,20 +70,12 @@ struct r_dyn_array* r_new_dyn_array(r_ssize elt_byte_size, void r_dyn_push_back(struct r_dyn_array* p_arr, const void* p_elt) { - r_ssize count = ++p_arr->count; - if (count > p_arr->capacity) { - r_ssize new_capacity = r_ssize_mult(p_arr->capacity, - p_arr->growth_factor); - r_dyn_resize(p_arr, new_capacity); - } + r_ssize loc = r__dyn_increment(p_arr); if (p_arr->barrier_set) { r_obj* value = *((r_obj* const *) p_elt); - p_arr->barrier_set(p_arr->data, count - 1, value); - return; - } - - if (p_elt) { + p_arr->barrier_set(p_arr->data, loc, value); + } else if (p_elt) { memcpy(r_dyn_last(p_arr), p_elt, p_arr->elt_byte_size); } else { memset(r_dyn_last(p_arr), 0, p_arr->elt_byte_size); diff --git a/src/rlang/dyn-array.h b/src/rlang/dyn-array.h index 3e0363faf..daba3a4e2 100644 --- a/src/rlang/dyn-array.h +++ b/src/rlang/dyn-array.h @@ -73,36 +73,6 @@ const void* r_dyn_cend(struct r_dyn_array* p_arr) { return r_dyn_cpointer(p_arr, p_arr->count); } -static inline -void* const * r_dyn_pop_back(struct r_dyn_array* p_arr) { - void* const * out = (void* const *) r_dyn_clast(p_arr); - --p_arr->count; - return out; -} - -static inline -void r_dyn_lgl_push_back(struct r_dyn_array* p_vec, int elt) { - r_dyn_push_back(p_vec, &elt); -} -static inline -void r_dyn_int_push_back(struct r_dyn_array* p_vec, int elt) { - r_dyn_push_back(p_vec, &elt); -} -static inline -void r_dyn_dbl_push_back(struct r_dyn_array* p_vec, double elt) { - r_dyn_push_back(p_vec, &elt); -} -static inline -void r_dyn_cpl_push_back(struct r_dyn_array* p_vec, r_complex elt) { - r_dyn_push_back(p_vec, &elt); -} -static inline -void r_dyn_list_push_back(struct r_dyn_array* p_vec, r_obj* elt) { - KEEP(elt); - r_dyn_push_back(p_vec, &elt); - FREE(1); -} - #define R_DYN_GET(TYPE, X, I) (*((TYPE*) r_dyn_pointer((X), (I)))) #define R_DYN_POKE(TYPE, X, I, VAL) (*((TYPE*) r_dyn_pointer((X), (I))) = (VAL)) @@ -164,4 +134,51 @@ void r_dyn_list_poke(struct r_dyn_array* p_vec, r_ssize i, r_obj* value) { r_list_poke(p_vec->data, i, value); } +static inline +void* const * r_dyn_pop_back(struct r_dyn_array* p_arr) { + void* const * out = (void* const *) r_dyn_clast(p_arr); + --p_arr->count; + return out; +} + +static inline +r_ssize r__dyn_increment(struct r_dyn_array* p_arr) { + r_ssize loc = p_arr->count++; + + if (p_arr->count > p_arr->capacity) { + r_ssize new_capacity = r_ssize_mult(p_arr->capacity, p_arr->growth_factor); + r_dyn_resize(p_arr, new_capacity); + } + + return loc; +} + +static inline +void r_dyn_lgl_push_back(struct r_dyn_array* p_vec, int elt) { + r_ssize loc = r__dyn_increment(p_vec); + r_dyn_lgl_poke(p_vec, loc, elt); +} +static inline +void r_dyn_int_push_back(struct r_dyn_array* p_vec, int elt) { + r_ssize loc = r__dyn_increment(p_vec); + r_dyn_int_poke(p_vec, loc, elt); +} +static inline +void r_dyn_dbl_push_back(struct r_dyn_array* p_vec, double elt) { + r_ssize loc = r__dyn_increment(p_vec); + r_dyn_dbl_poke(p_vec, loc, elt); +} +static inline +void r_dyn_cpl_push_back(struct r_dyn_array* p_vec, r_complex elt) { + r_ssize loc = r__dyn_increment(p_vec); + r_dyn_cpl_poke(p_vec, loc, elt); +} +static inline +void r_dyn_list_push_back(struct r_dyn_array* p_vec, r_obj* elt) { + KEEP(elt); + r_ssize loc = r__dyn_increment(p_vec); + r_dyn_list_poke(p_vec, loc, elt); + FREE(1); +} + #endif diff --git a/src/rlang/stack.c b/src/rlang/stack.c index e51e9a6c0..78017ed2a 100644 --- a/src/rlang/stack.c +++ b/src/rlang/stack.c @@ -17,7 +17,7 @@ void r_on_exit(r_obj* expr, r_obj* frame) { r_obj* r_peek_frame(void) { - return r_eval(peek_frame_call, r_envs.empty); + return r_eval(peek_frame_call, r_envs.base); } r_obj* r_caller_env(r_obj* n) { @@ -75,8 +75,15 @@ static r_obj* generate_sys_call(const char* name, int** n_addr) { } void r_init_library_stack(void) { - r_obj* current_frame_body = KEEP(r_parse_eval("as.call(list(sys.frame, -1))", r_envs.base)); - r_obj* current_frame_fn = KEEP(r_new_function(r_null, current_frame_body, r_envs.empty)); + // `sys.frame(sys.nframe())` doesn't work because `sys.nframe()` + // returns the number of the frame in which evaluation occurs. It + // doesn't return the number of frames on the stack. So we'd need + // to evaluate it in the last frame on the stack which is what we + // are looking for to begin with. We use instead this workaround: + // Call `sys.frame()` from a closure to push a new frame on the + // stack, and use negative indexing to get the previous frame. + r_obj* current_frame_body = KEEP(r_parse("sys.frame(-1)")); + r_obj* current_frame_fn = KEEP(r_new_function(r_null, current_frame_body, r_envs.base)); peek_frame_call = r_new_call(current_frame_fn, r_null); r_preserve(peek_frame_call); FREE(2); From 1fc5f49285f62992cc0bffca3153e4e50f1d2a34 Mon Sep 17 00:00:00 2001 From: Davis Vaughan Date: Fri, 20 Jan 2023 12:34:39 -0500 Subject: [PATCH 214/312] Rewrite run functions on top of "detect" implementation (#1770) We were already doing this for `df_identify_runs()`, and this way we optimize `vec_locate_run_bounds()` and `vec_detect_run_bounds()`. Plus it makes all of the implementations much simpler, since everything can easily be derived from the logical vector. --- R/runs.R | 10 +- src/decl/runs-decl.h | 54 ++--- src/init.c | 12 +- src/runs.c | 399 +++++++++++++++------------------- tests/testthat/_snaps/runs.md | 28 +-- tests/testthat/test-runs.R | 40 ++-- 6 files changed, 247 insertions(+), 296 deletions(-) diff --git a/R/runs.R b/R/runs.R index 5167c5660..4184a25fb 100644 --- a/R/runs.R +++ b/R/runs.R @@ -32,13 +32,13 @@ #' #' vec_identify_runs(df) vec_identify_runs <- function(x) { - .Call(vctrs_identify_runs, x) + .Call(ffi_vec_identify_runs, x) } -vec_locate_runs <- function(x, start = TRUE) { - .Call(vctrs_locate_runs, x, start) +vec_locate_run_bounds <- function(x, start = TRUE) { + .Call(ffi_vec_locate_run_bounds, x, start) } -vec_detect_runs <- function(x, start = TRUE) { - .Call(vctrs_detect_runs, x, start) +vec_detect_run_bounds <- function(x, start = TRUE) { + .Call(ffi_vec_detect_run_bounds, x, start) } diff --git a/src/decl/runs-decl.h b/src/decl/runs-decl.h index e84f80ce7..f9d243c54 100644 --- a/src/decl/runs-decl.h +++ b/src/decl/runs-decl.h @@ -1,53 +1,41 @@ static -r_obj* vec_locate_runs(r_obj* x, bool start); - -static inline -void vec_locate_run_starts(const int* v_id, r_ssize size, int* v_out); -static inline -void vec_locate_run_ends(const int* v_id, r_ssize size, int* v_out); - - +r_obj* vec_detect_run_bounds(r_obj* x, bool start); static -r_obj* vec_detect_runs(r_obj* x, bool start); - -static inline -void vec_detect_run_starts(const int* v_id, r_ssize size, int* v_out); -static inline -void vec_detect_run_ends(const int* v_id, r_ssize size, int* v_out); +r_obj* vec_locate_run_bounds(r_obj* x, bool start); +static +r_obj* vec_detect_run_bounds0(r_obj* x, bool start); static inline -int lgl_identify_runs(r_obj* x, r_ssize size, int* v_out); -static inline -int int_identify_runs(r_obj* x, r_ssize size, int* v_out); +void lgl_detect_run_bounds0(r_obj* x, r_ssize size, bool start, bool* v_out); static inline -int dbl_identify_runs(r_obj* x, r_ssize size, int* v_out); +void int_detect_run_bounds0(r_obj* x, r_ssize size, bool start, bool* v_out); static inline -int cpl_identify_runs(r_obj* x, r_ssize size, int* v_out); +void dbl_detect_run_bounds0(r_obj* x, r_ssize size, bool start, bool* v_out); static inline -int chr_identify_runs(r_obj* x, r_ssize size, int* v_out); +void cpl_detect_run_bounds0(r_obj* x, r_ssize size, bool start, bool* v_out); static inline -int raw_identify_runs(r_obj* x, r_ssize size, int* v_out); +void chr_detect_run_bounds0(r_obj* x, r_ssize size, bool start, bool* v_out); static inline -int list_identify_runs(r_obj* x, r_ssize size, int* v_out); +void raw_detect_run_bounds0(r_obj* x, r_ssize size, bool start, bool* v_out); static inline -int df_identify_runs(r_obj* x, r_ssize size, int* v_out); - +void list_detect_run_bounds0(r_obj* x, r_ssize size, bool start, bool* v_out); static inline -void col_identify_runs(r_obj* x, r_ssize size, bool* v_where); - +void df_detect_run_bounds0(r_obj* x, r_ssize size, bool start, bool* v_out); +static inline +void col_detect_run_bounds0(r_obj* x, r_ssize size, bool start, bool* v_out); static inline -void lgl_col_identify_runs(r_obj* x, r_ssize size, bool* v_where); +void lgl_col_detect_run_bounds0(r_obj* x, r_ssize size, bool start, bool* v_out); static inline -void int_col_identify_runs(r_obj* x, r_ssize size, bool* v_where); +void int_col_detect_run_bounds0(r_obj* x, r_ssize size, bool start, bool* v_out); static inline -void dbl_col_identify_runs(r_obj* x, r_ssize size, bool* v_where); +void dbl_col_detect_run_bounds0(r_obj* x, r_ssize size, bool start, bool* v_out); static inline -void cpl_col_identify_runs(r_obj* x, r_ssize size, bool* v_where); +void cpl_col_detect_run_bounds0(r_obj* x, r_ssize size, bool start, bool* v_out); static inline -void chr_col_identify_runs(r_obj* x, r_ssize size, bool* v_where); +void chr_col_detect_run_bounds0(r_obj* x, r_ssize size, bool start, bool* v_out); static inline -void raw_col_identify_runs(r_obj* x, r_ssize size, bool* v_where); +void raw_col_detect_run_bounds0(r_obj* x, r_ssize size, bool start, bool* v_out); static inline -void list_col_identify_runs(r_obj* x, r_ssize size, bool* v_where); +void list_col_detect_run_bounds0(r_obj* x, r_ssize size, bool start, bool* v_out); diff --git a/src/init.c b/src/init.c index ce5de0ad7..3d5320fee 100644 --- a/src/init.c +++ b/src/init.c @@ -120,9 +120,9 @@ extern r_obj* ffi_cast_dispatch_native(r_obj*, r_obj*, r_obj*, r_obj*, r_obj*, r extern SEXP vctrs_fast_c(SEXP, SEXP); extern r_obj* ffi_data_frame(r_obj*, r_obj*, r_obj*, r_obj*); extern r_obj* ffi_df_list(r_obj*, r_obj*, r_obj*, r_obj*, r_obj*); -extern SEXP vctrs_identify_runs(SEXP); -extern SEXP vctrs_locate_runs(SEXP, SEXP); -extern SEXP vctrs_detect_runs(SEXP, SEXP); +extern SEXP ffi_vec_detect_run_bounds(r_obj*, r_obj*); +extern SEXP ffi_vec_locate_run_bounds(r_obj*, r_obj*); +extern SEXP ffi_vec_identify_runs(r_obj*); extern SEXP vctrs_slice_complete(SEXP); extern SEXP vctrs_locate_complete(SEXP); extern SEXP vctrs_detect_complete(SEXP); @@ -300,9 +300,9 @@ static const R_CallMethodDef CallEntries[] = { {"vctrs_fast_c", (DL_FUNC) &vctrs_fast_c, 2}, {"ffi_data_frame", (DL_FUNC) &ffi_data_frame, 4}, {"ffi_df_list", (DL_FUNC) &ffi_df_list, 5}, - {"vctrs_identify_runs", (DL_FUNC) &vctrs_identify_runs, 1}, - {"vctrs_locate_runs", (DL_FUNC) &vctrs_locate_runs, 2}, - {"vctrs_detect_runs", (DL_FUNC) &vctrs_detect_runs, 2}, + {"ffi_vec_detect_run_bounds", (DL_FUNC) &ffi_vec_detect_run_bounds, 2}, + {"ffi_vec_locate_run_bounds", (DL_FUNC) &ffi_vec_locate_run_bounds, 2}, + {"ffi_vec_identify_runs", (DL_FUNC) &ffi_vec_identify_runs, 1}, {"vctrs_slice_complete", (DL_FUNC) &vctrs_slice_complete, 1}, {"vctrs_locate_complete", (DL_FUNC) &vctrs_locate_complete, 1}, {"vctrs_detect_complete", (DL_FUNC) &vctrs_detect_complete, 1}, diff --git a/src/runs.c b/src/runs.c index c5d97e3fe..e07876d94 100644 --- a/src/runs.c +++ b/src/runs.c @@ -4,327 +4,290 @@ // ----------------------------------------------------------------------------- -r_obj* vctrs_locate_runs(r_obj* x, r_obj* ffi_start) { +r_obj* ffi_vec_detect_run_bounds(r_obj* x, r_obj* ffi_start) { const bool start = r_arg_as_bool(ffi_start, "start"); - return vec_locate_runs(x, start); + return vec_detect_run_bounds(x, start); } static -r_obj* vec_locate_runs(r_obj* x, bool start) { - r_obj* id = KEEP(vec_identify_runs(x)); - const int* v_id = r_int_cbegin(id); +r_obj* vec_detect_run_bounds(r_obj* x, bool start) { + r_obj* where = KEEP(vec_detect_run_bounds0(x, start)); + const bool* v_where = r_raw_cbegin(where); - const r_ssize size = r_length(id); - const int n = r_int_get(r_attrib_get(id, syms_n), 0); + const r_ssize size = r_length(where) / sizeof(bool); - // Share memory with `id`. - // `vec_locate_run_starts/ends()` are carefully written to avoid - // overwrite issues. - r_obj* out = id; - int* v_out = r_int_begin(out); + r_obj* out = KEEP(r_alloc_logical(size)); + int* v_out = r_lgl_begin(out); - if (start) { - vec_locate_run_starts(v_id, size, v_out); - } else { - vec_locate_run_ends(v_id, size, v_out); + for (r_ssize i = 0; i < size; ++i) { + v_out[i] = v_where[i]; } - // Resize shared memory to output size and clear attribute - out = KEEP(r_int_resize(out, n)); - r_attrib_poke(out, syms_n, r_null); - FREE(2); return out; } -static inline -void vec_locate_run_starts(const int* v_id, r_ssize size, int* v_out) { - if (size == 0) { - return; - } - - r_ssize loc = 0; - int ref = v_id[0]; - - // Handle first case - v_out[loc] = 1; - ++loc; - - for (r_ssize i = 1; i < size; ++i) { - const int elt = v_id[i]; - v_out[loc] = i + 1; - loc += elt != ref; - ref = elt; - } -} - -static inline -void vec_locate_run_ends(const int* v_id, r_ssize size, int* v_out) { - if (size == 0) { - return; - } - - r_ssize loc = 0; - int ref = v_id[0]; - - for (r_ssize i = 1; i < size; ++i) { - const int elt = v_id[i]; - v_out[loc] = i; - loc += elt != ref; - ref = elt; - } - - // Handle last case - v_out[loc] = size; -} - // ----------------------------------------------------------------------------- -r_obj* vctrs_detect_runs(r_obj* x, r_obj* ffi_start) { - bool start = r_arg_as_bool(ffi_start, "start"); - return vec_detect_runs(x, start); +r_obj* ffi_vec_locate_run_bounds(r_obj* x, r_obj* ffi_start) { + const bool start = r_arg_as_bool(ffi_start, "start"); + return vec_locate_run_bounds(x, start); } static -r_obj* vec_detect_runs(r_obj* x, bool start) { - r_obj* id = KEEP(vec_identify_runs(x)); - const int* v_id = r_int_cbegin(id); +r_obj* vec_locate_run_bounds(r_obj* x, bool start) { + r_obj* where = KEEP(vec_detect_run_bounds0(x, start)); + const bool* v_where = r_raw_cbegin(where); - r_ssize size = r_length(id); + const r_ssize size = r_length(where) / sizeof(bool); - r_obj* out = KEEP(r_new_logical(size)); - int* v_out = r_lgl_begin(out); + r_ssize n = 0; + for (r_ssize i = 0; i < size; ++i) { + n += v_where[i]; + } - if (start) { - vec_detect_run_starts(v_id, size, v_out); - } else { - vec_detect_run_ends(v_id, size, v_out); + r_obj* out = KEEP(r_alloc_integer(n)); + int* v_out = r_int_begin(out); + + for (r_ssize i = 0, j = 0; i < size && j < n; ++i) { + v_out[j] = i + 1; + j += v_where[i]; } FREE(2); return out; } -static inline -void vec_detect_run_starts(const int* v_id, r_ssize size, int* v_out) { - if (size == 0) { - return; - } +// ----------------------------------------------------------------------------- - int ref = v_id[0]; +r_obj* ffi_vec_identify_runs(r_obj* x) { + return vec_identify_runs(x); +} - // Handle first case - v_out[0] = 1; +r_obj* vec_identify_runs(r_obj* x) { + const bool start = true; + r_obj* where = KEEP(vec_detect_run_bounds0(x, start)); + const bool* v_where = r_raw_cbegin(where); - for (r_ssize i = 1; i < size; ++i) { - const int elt = v_id[i]; - v_out[i] = elt != ref; - ref = elt; - } -} + const r_ssize size = r_length(where) / sizeof(bool); -static inline -void vec_detect_run_ends(const int* v_id, r_ssize size, int* v_out) { - if (size == 0) { - return; - } + r_obj* out = KEEP(r_alloc_integer(size)); + int* v_out = r_int_begin(out); - int ref = v_id[0]; + int n = 0; - for (r_ssize i = 1; i < size; ++i) { - const int elt = v_id[i]; - v_out[i - 1] = elt != ref; - ref = elt; + for (r_ssize i = 0; i < size; ++i) { + n += v_where[i]; + v_out[i] = n; } - // Handle last case - v_out[size - 1] = 1; + r_obj* ffi_n = r_int(n); + r_attrib_poke(out, syms_n, ffi_n); + + FREE(2); + return out; } // ----------------------------------------------------------------------------- -r_obj* vctrs_identify_runs(r_obj* x) { - return vec_identify_runs(x); -} - -r_obj* vec_identify_runs(r_obj* x) { +/* + * Like `vec_detect_run_bounds()`, but returns a less memory intensive + * boolean array as a raw vector. + */ +static +r_obj* vec_detect_run_bounds0(r_obj* x, bool start) { r_obj* proxy = KEEP(vec_proxy_equal(x)); - r_ssize size = vec_size(proxy); proxy = KEEP(vec_normalize_encoding(proxy)); - r_obj* out = KEEP(r_alloc_integer(size)); - int* v_out = r_int_begin(out); + const r_ssize size = vec_size(proxy); - // Handle size 0 up front. - // All implementations assume at least 1 element. - if (size == 0) { - r_obj* ffi_n = r_int(0); - r_attrib_poke(out, syms_n, ffi_n); - FREE(3); - return out; - } + r_obj* out = KEEP(r_alloc_raw(size * sizeof(bool))); + bool* v_out = r_raw_begin(out); const enum vctrs_type type = vec_proxy_typeof(proxy); - int n; - switch (type) { - case VCTRS_TYPE_logical: n = lgl_identify_runs(proxy, size, v_out); break; - case VCTRS_TYPE_integer: n = int_identify_runs(proxy, size, v_out); break; - case VCTRS_TYPE_double: n = dbl_identify_runs(proxy, size, v_out); break; - case VCTRS_TYPE_complex: n = cpl_identify_runs(proxy, size, v_out); break; - case VCTRS_TYPE_character: n = chr_identify_runs(proxy, size, v_out); break; - case VCTRS_TYPE_raw: n = raw_identify_runs(proxy, size, v_out); break; - case VCTRS_TYPE_list: n = list_identify_runs(proxy, size, v_out); break; - case VCTRS_TYPE_dataframe: n = df_identify_runs(proxy, size, v_out); break; - default: stop_unimplemented_vctrs_type("vec_identify_runs", type); + case VCTRS_TYPE_logical: lgl_detect_run_bounds0(proxy, size, start, v_out); break; + case VCTRS_TYPE_integer: int_detect_run_bounds0(proxy, size, start, v_out); break; + case VCTRS_TYPE_double: dbl_detect_run_bounds0(proxy, size, start, v_out); break; + case VCTRS_TYPE_complex: cpl_detect_run_bounds0(proxy, size, start, v_out); break; + case VCTRS_TYPE_character: chr_detect_run_bounds0(proxy, size, start, v_out); break; + case VCTRS_TYPE_raw: raw_detect_run_bounds0(proxy, size, start, v_out); break; + case VCTRS_TYPE_list: list_detect_run_bounds0(proxy, size, start, v_out); break; + case VCTRS_TYPE_dataframe: df_detect_run_bounds0(proxy, size, start, v_out); break; + default: stop_unimplemented_vctrs_type("vec_detect_run_bounds0", type); } - r_obj* ffi_n = r_int(n); - r_attrib_poke(out, syms_n, ffi_n); - FREE(3); return out; } // ----------------------------------------------------------------------------- -#define VEC_IDENTIFY_RUNS(CTYPE, CBEGIN, EQUAL_NA_EQUAL) { \ - int id = 1; \ - CTYPE const* v_x = CBEGIN(x); \ - \ - /* Handle first case */ \ - CTYPE ref = v_x[0]; \ - v_out[0] = id; \ - \ - for (r_ssize i = 1; i < size; ++i) { \ - CTYPE const elt = v_x[i]; \ - id += !EQUAL_NA_EQUAL(elt, ref); \ - v_out[i] = id; \ - ref = elt; \ - } \ - \ - return id; \ +// Algorithm for "ends" is same as "starts", we just iterate in reverse +#define VEC_DETECT_RUN_BOUNDS0(CTYPE, CBEGIN, EQUAL_NA_EQUAL) { \ + if (size == 0) { \ + /* Algorithm requires at least 1 value */ \ + return; \ + } \ + \ + CTYPE const* v_x = CBEGIN(x); \ + \ + if (start) { \ + /* Handle first case */ \ + CTYPE ref = v_x[0]; \ + v_out[0] = true; \ + \ + for (r_ssize i = 1; i < size; ++i) { \ + CTYPE const elt = v_x[i]; \ + v_out[i] = !EQUAL_NA_EQUAL(elt, ref); \ + ref = elt; \ + } \ + } else { \ + /* Handle last case */ \ + CTYPE ref = v_x[size - 1]; \ + v_out[size - 1] = true; \ + \ + for (r_ssize i = size - 2; i >= 0; --i) { \ + CTYPE const elt = v_x[i]; \ + v_out[i] = !EQUAL_NA_EQUAL(elt, ref); \ + ref = elt; \ + } \ + } \ } -static -int lgl_identify_runs(r_obj* x, r_ssize size, int* v_out) { - VEC_IDENTIFY_RUNS(int, r_lgl_cbegin, lgl_equal_na_equal); +static inline +void lgl_detect_run_bounds0(r_obj* x, r_ssize size, bool start, bool* v_out) { + VEC_DETECT_RUN_BOUNDS0(int, r_lgl_cbegin, lgl_equal_na_equal); } -static -int int_identify_runs(r_obj* x, r_ssize size, int* v_out) { - VEC_IDENTIFY_RUNS(int, r_int_cbegin, int_equal_na_equal); +static inline +void int_detect_run_bounds0(r_obj* x, r_ssize size, bool start, bool* v_out) { + VEC_DETECT_RUN_BOUNDS0(int, r_int_cbegin, int_equal_na_equal); } -static -int dbl_identify_runs(r_obj* x, r_ssize size, int* v_out) { - VEC_IDENTIFY_RUNS(double, r_dbl_cbegin, dbl_equal_na_equal); +static inline +void dbl_detect_run_bounds0(r_obj* x, r_ssize size, bool start, bool* v_out) { + VEC_DETECT_RUN_BOUNDS0(double, r_dbl_cbegin, dbl_equal_na_equal); } -static -int cpl_identify_runs(r_obj* x, r_ssize size, int* v_out) { - VEC_IDENTIFY_RUNS(Rcomplex, r_cpl_cbegin, cpl_equal_na_equal); +static inline +void cpl_detect_run_bounds0(r_obj* x, r_ssize size, bool start, bool* v_out) { + VEC_DETECT_RUN_BOUNDS0(Rcomplex, r_cpl_cbegin, cpl_equal_na_equal); } -static -int chr_identify_runs(r_obj* x, r_ssize size, int* v_out) { - VEC_IDENTIFY_RUNS(r_obj*, r_chr_cbegin, chr_equal_na_equal); +static inline +void chr_detect_run_bounds0(r_obj* x, r_ssize size, bool start, bool* v_out) { + VEC_DETECT_RUN_BOUNDS0(r_obj*, r_chr_cbegin, chr_equal_na_equal); } -static -int raw_identify_runs(r_obj* x, r_ssize size, int* v_out) { - VEC_IDENTIFY_RUNS(Rbyte, r_raw_cbegin, raw_equal_na_equal); +static inline +void raw_detect_run_bounds0(r_obj* x, r_ssize size, bool start, bool* v_out) { + VEC_DETECT_RUN_BOUNDS0(Rbyte, r_raw_cbegin, raw_equal_na_equal); } -static -int list_identify_runs(r_obj* x, r_ssize size, int* v_out) { - VEC_IDENTIFY_RUNS(r_obj*, r_list_cbegin, list_equal_na_equal); +static inline +void list_detect_run_bounds0(r_obj* x, r_ssize size, bool start, bool* v_out) { + VEC_DETECT_RUN_BOUNDS0(r_obj*, r_list_cbegin, list_equal_na_equal); } -#undef VEC_IDENTIFY_RUNS +#undef VEC_DETECT_RUN_BOUNDS0 // ----------------------------------------------------------------------------- static inline -int df_identify_runs(r_obj* x, r_ssize size, int* v_out) { +void df_detect_run_bounds0(r_obj* x, r_ssize size, bool start, bool* v_out) { + if (size == 0) { + // Algorithm requires at least 1 value + return; + } + const r_ssize n_col = r_length(x); r_obj* const* v_x = r_list_cbegin(x); - // Boolean vector that will eventually be `true` if we are in a run + // `v_out` will eventually be `true` if we are in a run // continuation, and `false` if we are starting a new run. - r_obj* where_shelter = KEEP(r_alloc_raw(size * sizeof(bool))); - bool* v_where = (bool*) r_raw_begin(where_shelter); - - v_where[0] = false; - for (r_ssize i = 1; i < size; ++i) { - v_where[i] = true; + if (start) { + v_out[0] = false; + for (r_ssize i = 1; i < size; ++i) { + v_out[i] = true; + } + } else { + v_out[size - 1] = false; + for (r_ssize i = size - 2; i >= 0; --i) { + v_out[i] = true; + } } for (r_ssize i = 0; i < n_col; ++i) { - col_identify_runs(v_x[i], size, v_where); + col_detect_run_bounds0(v_x[i], size, start, v_out); } - int id = 1; - - v_out[0] = id; - for (r_ssize i = 1; i < size; ++i) { - id += !v_where[i]; - v_out[i] = id; + // Now invert to detect the bounds + for (r_ssize i = 0; i < size; ++i) { + v_out[i] = !v_out[i]; } - - FREE(1); - return id; } static inline -void col_identify_runs(r_obj* x, r_ssize size, bool* v_where) { +void col_detect_run_bounds0(r_obj* x, r_ssize size, bool start, bool* v_out) { switch (vec_proxy_typeof(x)) { - case VCTRS_TYPE_logical: lgl_col_identify_runs(x, size, v_where); break; - case VCTRS_TYPE_integer: int_col_identify_runs(x, size, v_where); break; - case VCTRS_TYPE_double: dbl_col_identify_runs(x, size, v_where); break; - case VCTRS_TYPE_complex: cpl_col_identify_runs(x, size, v_where); break; - case VCTRS_TYPE_character: chr_col_identify_runs(x, size, v_where); break; - case VCTRS_TYPE_raw: raw_col_identify_runs(x, size, v_where); break; - case VCTRS_TYPE_list: list_col_identify_runs(x, size, v_where); break; + case VCTRS_TYPE_logical: lgl_col_detect_run_bounds0(x, size, start, v_out); break; + case VCTRS_TYPE_integer: int_col_detect_run_bounds0(x, size, start, v_out); break; + case VCTRS_TYPE_double: dbl_col_detect_run_bounds0(x, size, start, v_out); break; + case VCTRS_TYPE_complex: cpl_col_detect_run_bounds0(x, size, start, v_out); break; + case VCTRS_TYPE_character: chr_col_detect_run_bounds0(x, size, start, v_out); break; + case VCTRS_TYPE_raw: raw_col_detect_run_bounds0(x, size, start, v_out); break; + case VCTRS_TYPE_list: list_col_detect_run_bounds0(x, size, start, v_out); break; case VCTRS_TYPE_dataframe: r_stop_internal("Data frame columns should be flattened."); case VCTRS_TYPE_scalar: r_abort("Can't compare scalars."); default: r_abort("Unimplemented type."); } } -#define VEC_COL_IDENTIFY_RUNS(CTYPE, CBEGIN, EQUAL_NA_EQUAL) { \ - CTYPE const* v_x = CBEGIN(x); \ - CTYPE ref = v_x[0]; \ - \ - for (r_ssize i = 1; i < size; ++i) { \ - CTYPE const elt = v_x[i]; \ - v_where[i] = v_where[i] && EQUAL_NA_EQUAL(ref, elt); \ - ref = elt; \ - } \ +#define VEC_COL_DETECT_RUN_BOUNDS0(CTYPE, CBEGIN, EQUAL_NA_EQUAL) { \ + CTYPE const* v_x = CBEGIN(x); \ + \ + if (start) { \ + CTYPE ref = v_x[0]; \ + \ + for (r_ssize i = 1; i < size; ++i) { \ + CTYPE const elt = v_x[i]; \ + v_out[i] = v_out[i] && EQUAL_NA_EQUAL(ref, elt); \ + ref = elt; \ + } \ + } else { \ + CTYPE ref = v_x[size - 1]; \ + \ + for (r_ssize i = size - 2; i >= 0; --i) { \ + CTYPE const elt = v_x[i]; \ + v_out[i] = v_out[i] && EQUAL_NA_EQUAL(ref, elt); \ + ref = elt; \ + } \ + } \ } static inline -void lgl_col_identify_runs(r_obj* x, r_ssize size, bool* v_where) { - VEC_COL_IDENTIFY_RUNS(int, r_lgl_cbegin, lgl_equal_na_equal); +void lgl_col_detect_run_bounds0(r_obj* x, r_ssize size, bool start, bool* v_out) { + VEC_COL_DETECT_RUN_BOUNDS0(int, r_lgl_cbegin, lgl_equal_na_equal); } static inline -void int_col_identify_runs(r_obj* x, r_ssize size, bool* v_where) { - VEC_COL_IDENTIFY_RUNS(int, r_int_cbegin, int_equal_na_equal); +void int_col_detect_run_bounds0(r_obj* x, r_ssize size, bool start, bool* v_out) { + VEC_COL_DETECT_RUN_BOUNDS0(int, r_int_cbegin, int_equal_na_equal); } static inline -void dbl_col_identify_runs(r_obj* x, r_ssize size, bool* v_where) { - VEC_COL_IDENTIFY_RUNS(double, r_dbl_cbegin, dbl_equal_na_equal); +void dbl_col_detect_run_bounds0(r_obj* x, r_ssize size, bool start, bool* v_out) { + VEC_COL_DETECT_RUN_BOUNDS0(double, r_dbl_cbegin, dbl_equal_na_equal); } static inline -void cpl_col_identify_runs(r_obj* x, r_ssize size, bool* v_where) { - VEC_COL_IDENTIFY_RUNS(Rcomplex, r_cpl_cbegin, cpl_equal_na_equal); +void cpl_col_detect_run_bounds0(r_obj* x, r_ssize size, bool start, bool* v_out) { + VEC_COL_DETECT_RUN_BOUNDS0(Rcomplex, r_cpl_cbegin, cpl_equal_na_equal); } static inline -void chr_col_identify_runs(r_obj* x, r_ssize size, bool* v_where) { - VEC_COL_IDENTIFY_RUNS(r_obj*, r_chr_cbegin, chr_equal_na_equal); +void chr_col_detect_run_bounds0(r_obj* x, r_ssize size, bool start, bool* v_out) { + VEC_COL_DETECT_RUN_BOUNDS0(r_obj*, r_chr_cbegin, chr_equal_na_equal); } static inline -void raw_col_identify_runs(r_obj* x, r_ssize size, bool* v_where) { - VEC_COL_IDENTIFY_RUNS(Rbyte, r_raw_cbegin, raw_equal_na_equal); +void raw_col_detect_run_bounds0(r_obj* x, r_ssize size, bool start, bool* v_out) { + VEC_COL_DETECT_RUN_BOUNDS0(Rbyte, r_raw_cbegin, raw_equal_na_equal); } static inline -void list_col_identify_runs(r_obj* x, r_ssize size, bool* v_where) { - VEC_COL_IDENTIFY_RUNS(r_obj*, r_list_cbegin, list_equal_na_equal); +void list_col_detect_run_bounds0(r_obj* x, r_ssize size, bool start, bool* v_out) { + VEC_COL_DETECT_RUN_BOUNDS0(r_obj*, r_list_cbegin, list_equal_na_equal); } -#undef VEC_COL_IDENTIFY_RUNS +#undef VEC_COL_DETECT_RUN_BOUNDS0 diff --git a/tests/testthat/_snaps/runs.md b/tests/testthat/_snaps/runs.md index 064a46ff8..b53d1b1f0 100644 --- a/tests/testthat/_snaps/runs.md +++ b/tests/testthat/_snaps/runs.md @@ -1,48 +1,48 @@ -# vec_locate_runs() validates `start` +# vec_locate_run_bounds() validates `start` Code - vec_locate_runs(1, start = "x") + vec_locate_run_bounds(1, start = "x") Condition - Error in `vec_locate_runs()`: + Error in `vec_locate_run_bounds()`: ! `start` must be `TRUE` or `FALSE`. --- Code - vec_locate_runs(1, start = NA) + vec_locate_run_bounds(1, start = NA) Condition - Error in `vec_locate_runs()`: + Error in `vec_locate_run_bounds()`: ! `start` must be `TRUE` or `FALSE`. --- Code - vec_locate_runs(1, start = c(TRUE, TRUE)) + vec_locate_run_bounds(1, start = c(TRUE, TRUE)) Condition - Error in `vec_locate_runs()`: + Error in `vec_locate_run_bounds()`: ! `start` must be `TRUE` or `FALSE`. -# vec_detect_runs() validates `start` +# vec_detect_run_bounds() validates `start` Code - vec_detect_runs(1, start = "x") + vec_detect_run_bounds(1, start = "x") Condition - Error in `vec_detect_runs()`: + Error in `vec_detect_run_bounds()`: ! `start` must be `TRUE` or `FALSE`. --- Code - vec_detect_runs(1, start = NA) + vec_detect_run_bounds(1, start = NA) Condition - Error in `vec_detect_runs()`: + Error in `vec_detect_run_bounds()`: ! `start` must be `TRUE` or `FALSE`. --- Code - vec_detect_runs(1, start = c(TRUE, TRUE)) + vec_detect_run_bounds(1, start = c(TRUE, TRUE)) Condition - Error in `vec_detect_runs()`: + Error in `vec_detect_run_bounds()`: ! `start` must be `TRUE` or `FALSE`. diff --git a/tests/testthat/test-runs.R b/tests/testthat/test-runs.R index 9badc0f2d..2556ca26b 100644 --- a/tests/testthat/test-runs.R +++ b/tests/testthat/test-runs.R @@ -86,68 +86,68 @@ test_that("works with columns of various types", { expect_identical(vec_identify_runs(add_col(list(1, 1, 2, 2, 3))), expect) }) -# vec_locate_runs -------------------------------------------------------------- +# vec_locate_run_bounds -------------------------------------------------------- test_that("can locate run starts", { expect_identical( - vec_locate_runs(c(1, 3, 3, 1, 5, 5, 6)), + vec_locate_run_bounds(c(1, 3, 3, 1, 5, 5, 6)), c(1L, 2L, 4L, 5L, 7L) ) }) test_that("can locate run ends", { expect_identical( - vec_locate_runs(c(1, 3, 3, 1, 5, 5, 6), start = FALSE), + vec_locate_run_bounds(c(1, 3, 3, 1, 5, 5, 6), start = FALSE), c(1L, 3L, 4L, 6L, 7L) ) }) -test_that("vec_locate_runs() works with size zero input", { - expect_identical(vec_locate_runs(integer(), start = TRUE), integer()) - expect_identical(vec_locate_runs(integer(), start = FALSE), integer()) +test_that("vec_locate_run_bounds() works with size zero input", { + expect_identical(vec_locate_run_bounds(integer(), start = TRUE), integer()) + expect_identical(vec_locate_run_bounds(integer(), start = FALSE), integer()) }) -test_that("vec_locate_runs() validates `start`", { +test_that("vec_locate_run_bounds() validates `start`", { expect_snapshot(error = TRUE, { - vec_locate_runs(1, start = "x") + vec_locate_run_bounds(1, start = "x") }) expect_snapshot(error = TRUE, { - vec_locate_runs(1, start = NA) + vec_locate_run_bounds(1, start = NA) }) expect_snapshot(error = TRUE, { - vec_locate_runs(1, start = c(TRUE, TRUE)) + vec_locate_run_bounds(1, start = c(TRUE, TRUE)) }) }) -# vec_detect_runs -------------------------------------------------------------- +# vec_detect_run_bounds -------------------------------------------------------- test_that("can detect run starts", { expect_identical( - vec_detect_runs(c(1, 3, 3, 1, 5, 5, 6)), + vec_detect_run_bounds(c(1, 3, 3, 1, 5, 5, 6)), c(TRUE, TRUE, FALSE, TRUE, TRUE, FALSE, TRUE) ) }) test_that("can detect run ends", { expect_identical( - vec_detect_runs(c(1, 3, 3, 1, 5, 5, 6), start = FALSE), + vec_detect_run_bounds(c(1, 3, 3, 1, 5, 5, 6), start = FALSE), c(TRUE, FALSE, TRUE, TRUE, FALSE, TRUE, TRUE) ) }) -test_that("vec_detect_runs() works with size zero input", { - expect_identical(vec_detect_runs(integer(), start = TRUE), logical()) - expect_identical(vec_detect_runs(integer(), start = FALSE), logical()) +test_that("vec_detect_run_bounds() works with size zero input", { + expect_identical(vec_detect_run_bounds(integer(), start = TRUE), logical()) + expect_identical(vec_detect_run_bounds(integer(), start = FALSE), logical()) }) -test_that("vec_detect_runs() validates `start`", { +test_that("vec_detect_run_bounds() validates `start`", { expect_snapshot(error = TRUE, { - vec_detect_runs(1, start = "x") + vec_detect_run_bounds(1, start = "x") }) expect_snapshot(error = TRUE, { - vec_detect_runs(1, start = NA) + vec_detect_run_bounds(1, start = NA) }) expect_snapshot(error = TRUE, { - vec_detect_runs(1, start = c(TRUE, TRUE)) + vec_detect_run_bounds(1, start = c(TRUE, TRUE)) }) }) From b1ad86719e77b5d03e73028151a81a0dd3421c1f Mon Sep 17 00:00:00 2001 From: DavisVaughan Date: Fri, 20 Jan 2023 15:52:53 -0500 Subject: [PATCH 215/312] Polish NEWS --- NEWS.md | 14 +++++++------- 1 file changed, 7 insertions(+), 7 deletions(-) diff --git a/NEWS.md b/NEWS.md index edc951620..60dddec7a 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,19 +1,19 @@ # vctrs (development version) -* `vec_identify_runs()` is now faster when used with data frames (#1684). - * New `vec_expand_grid()`, which is a lower level helper that is similar to `tidyr::expand_grid()` (#1325). - -* The maximum load factor of the internal dictionary was reduced from 77% to - 50%, which improves performance of functions like `vec_match()`, - `vec_set_intersect()`, and `vec_unique()` in some cases (#1760). - + * New `vec_set_intersect()`, `vec_set_difference()`, `vec_set_union()`, and `vec_set_symmetric_difference()` which compute set operations like `intersect()`, `setdiff()`, and `union()`, but the vctrs variants don't strip attributes and work with data frames (#1755, #1765). +* `vec_identify_runs()` is now faster when used with data frames (#1684). + +* The maximum load factor of the internal dictionary was reduced from 77% to + 50%, which improves performance of functions like `vec_match()`, + `vec_set_intersect()`, and `vec_unique()` in some cases (#1760). + * Fixed a bug with the internal `vec_order_radix()` function related to matrix columns (#1753). From db967f24a80e86a346eb0c35d642bc2c9fa96f73 Mon Sep 17 00:00:00 2001 From: DavisVaughan Date: Fri, 20 Jan 2023 16:00:46 -0500 Subject: [PATCH 216/312] Update revdep checks --- revdep/README.md | 33 +- revdep/cran.md | 30 +- revdep/failures.md | 998 ++------------------------------------------- revdep/problems.md | 152 +------ 4 files changed, 47 insertions(+), 1166 deletions(-) diff --git a/revdep/README.md b/revdep/README.md index 9bf0437fd..77762c863 100644 --- a/revdep/README.md +++ b/revdep/README.md @@ -1,37 +1,10 @@ # Revdeps -## Failed to check (22) +## Failed to check (3) |package |version |error |warning |note | |:-------------|:-------|:-----|:-------|:----| |NA |? | | | | -|NA |? | | | | -|elbird |0.2.5 |1 | | | -|ggPMX |? | | | | -|NA |? | | | | -|loon.ggplot |? | | | | -|loon.shiny |? | | | | -|NA |? | | | | -|NA |? | | | | -|NA |? | | | | -|nlmixr2plot |? | | | | -|NA |? | | | | -|NA |? | | | | -|Platypus |? | | | | -|NA |? | | | | -|NA |? | | | | -|NA |? | | | | -|NA |? | | | | -|tidySEM |? | | | | -|NA |? | | | | -|vivid |? | | | | -|xpose.nlmixr2 |? | | | | - -## New problems (3) - -|package |version |error |warning |note | -|:------------|:-------|:------|:-------|:----| -|[globaltrends](problems.md#globaltrends)|0.0.12 |__+1__ | | | -|[goldilocks](problems.md#goldilocks)|0.3.0 |__+1__ | | | -|[psfmi](problems.md#psfmi)|1.0.0 |__+1__ |__+1__ |1 | +|tidybayes |? | | | | +|tidyposterior |? | | | | diff --git a/revdep/cran.md b/revdep/cran.md index 3de654e88..597743524 100644 --- a/revdep/cran.md +++ b/revdep/cran.md @@ -1,33 +1,13 @@ ## revdepcheck results -We checked 3743 reverse dependencies (3730 from CRAN + 13 from Bioconductor), comparing R CMD check results across CRAN and dev versions of this package. +We checked 217 reverse dependencies (216 from CRAN + 1 from Bioconductor), comparing R CMD check results across CRAN and dev versions of this package. - * We saw 3 new problems - * We failed to check 9 packages + * We saw 0 new problems + * We failed to check 2 packages Issues with CRAN packages are summarised below. -### New problems -(This reports the first line of each new failure) - -* globaltrends - checking tests ... ERROR - -* goldilocks - checking tests ... ERROR - -* psfmi - checking examples ... ERROR - checking re-building of vignette outputs ... WARNING - ### Failed to check -* elbird (NA) -* ggPMX (NA) -* loon.ggplot (NA) -* loon.shiny (NA) -* nlmixr2plot (NA) -* Platypus (NA) -* tidySEM (NA) -* vivid (NA) -* xpose.nlmixr2 (NA) +* tidybayes (NA) +* tidyposterior (NA) diff --git a/revdep/failures.md b/revdep/failures.md index 0af7bf749..0e4698947 100644 --- a/revdep/failures.md +++ b/revdep/failures.md @@ -33,933 +33,17 @@ Run `cloud_details(, "NA")` for more info ``` -# NA - -
- -* Version: NA -* GitHub: NA -* Source code: https://github.com/cran/NA -* Number of recursive dependencies: 0 - -Run `cloud_details(, "NA")` for more info - -
- -## Error before installation - -### Devel - -``` - - - - - - -``` -### CRAN - -``` - - - - - - -``` -# elbird - -
- -* Version: 0.2.5 -* GitHub: https://github.com/mrchypark/elbird -* Source code: https://github.com/cran/elbird -* Date/Publication: 2022-08-12 15:50:02 UTC -* Number of recursive dependencies: 54 - -Run `cloud_details(, "elbird")` for more info - -
- -## In both - -* checking whether package ‘elbird’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/elbird/new/elbird.Rcheck/00install.out’ for details. - ``` - -## Installation - -### Devel - -``` -* installing *source* package ‘elbird’ ... -** package ‘elbird’ successfully unpacked and MD5 sums checked -** using staged installation -/usr/bin/uname -Prior system libkiwi installation not found -Preparing to download and build library from source... -------------------------------[ ELBIRD ]------------------------------ -Configuration failed because 'git' was not found. -If you want to kiwi build from source in package installation prosess, -make sure git and cmake work in system. -------------------------------------------------------------------------- -ERROR: configuration failed for package ‘elbird’ -* removing ‘/tmp/workdir/elbird/new/elbird.Rcheck/elbird’ - - -``` -### CRAN - -``` -* installing *source* package ‘elbird’ ... -** package ‘elbird’ successfully unpacked and MD5 sums checked -** using staged installation -/usr/bin/uname -Prior system libkiwi installation not found -Preparing to download and build library from source... -------------------------------[ ELBIRD ]------------------------------ -Configuration failed because 'git' was not found. -If you want to kiwi build from source in package installation prosess, -make sure git and cmake work in system. -------------------------------------------------------------------------- -ERROR: configuration failed for package ‘elbird’ -* removing ‘/tmp/workdir/elbird/old/elbird.Rcheck/elbird’ - - -``` -# ggPMX - -
- -* Version: 1.2.8 -* GitHub: https://github.com/ggPMXdevelopment/ggPMX -* Source code: https://github.com/cran/ggPMX -* Date/Publication: 2022-06-17 23:10:02 UTC -* Number of recursive dependencies: 208 - -Run `cloud_details(, "ggPMX")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/ggPMX/new/ggPMX.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘ggPMX/DESCRIPTION’ ... OK -* this is package ‘ggPMX’ version ‘1.2.8’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... NOTE -... - [ FAIL 1 | WARN 11 | SKIP 8 | PASS 327 ] - 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 ... NONE - ‘ggPMX-guide.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: 1 ERROR, 2 NOTEs - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/ggPMX/old/ggPMX.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘ggPMX/DESCRIPTION’ ... OK -* this is package ‘ggPMX’ version ‘1.2.8’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... NOTE -... - [ FAIL 1 | WARN 11 | SKIP 8 | PASS 327 ] - 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 ... NONE - ‘ggPMX-guide.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: 1 ERROR, 2 NOTEs - - - - - -``` -# NA - -
- -* Version: NA -* GitHub: NA -* Source code: https://github.com/cran/NA -* Number of recursive dependencies: 0 - -Run `cloud_details(, "NA")` for more info - -
- -## Error before installation - -### Devel - -``` - - - - - - -``` -### CRAN - -``` - - - - - - -``` -# loon.ggplot - -
- -* Version: 1.3.2 -* GitHub: https://github.com/great-northern-diver/loon.ggplot -* Source code: https://github.com/cran/loon.ggplot -* Date/Publication: 2022-10-03 14:50:02 UTC -* Number of recursive dependencies: 104 - -Run `cloud_details(, "loon.ggplot")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/loon.ggplot/new/loon.ggplot.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘loon.ggplot/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘loon.ggplot’ version ‘1.3.2’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘loon’ - -Package suggested but not available for checking: ‘zenplots’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/loon.ggplot/old/loon.ggplot.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘loon.ggplot/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘loon.ggplot’ version ‘1.3.2’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘loon’ - -Package suggested but not available for checking: ‘zenplots’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# loon.shiny - -
- -* Version: 1.0.3 -* GitHub: NA -* Source code: https://github.com/cran/loon.shiny -* Date/Publication: 2022-10-08 15:30:02 UTC -* Number of recursive dependencies: 132 - -Run `cloud_details(, "loon.shiny")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/loon.shiny/new/loon.shiny.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘loon.shiny/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘loon.shiny’ version ‘1.0.3’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Packages required but not available: 'loon', 'loon.ggplot' - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/loon.shiny/old/loon.shiny.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘loon.shiny/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘loon.shiny’ version ‘1.0.3’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Packages required but not available: 'loon', 'loon.ggplot' - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# NA - -
- -* Version: NA -* GitHub: NA -* Source code: https://github.com/cran/NA -* Number of recursive dependencies: 0 - -Run `cloud_details(, "NA")` for more info - -
- -## Error before installation - -### Devel - -``` - - - - - - -``` -### CRAN - -``` - - - - - - -``` -# NA - -
- -* Version: NA -* GitHub: NA -* Source code: https://github.com/cran/NA -* Number of recursive dependencies: 0 - -Run `cloud_details(, "NA")` for more info - -
- -## Error before installation - -### Devel - -``` - - - - - - -``` -### CRAN - -``` - - - - - - -``` -# NA - -
- -* Version: NA -* GitHub: NA -* Source code: https://github.com/cran/NA -* Number of recursive dependencies: 0 - -Run `cloud_details(, "NA")` for more info - -
- -## Error before installation - -### Devel - -``` - - - - - - -``` -### CRAN - -``` - - - - - - -``` -# nlmixr2plot - -
- -* Version: 2.0.6 -* GitHub: https://github.com/nlmixr2/nlmixr2plot -* Source code: https://github.com/cran/nlmixr2plot -* Date/Publication: 2022-05-23 07:50:02 UTC -* Number of recursive dependencies: 198 - -Run `cloud_details(, "nlmixr2plot")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/nlmixr2plot/new/nlmixr2plot.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘nlmixr2plot/DESCRIPTION’ ... OK -* this is package ‘nlmixr2plot’ version ‘2.0.6’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Packages required but not available: 'nlmixr2est', 'nlmixr2extra' - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/nlmixr2plot/old/nlmixr2plot.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘nlmixr2plot/DESCRIPTION’ ... OK -* this is package ‘nlmixr2plot’ version ‘2.0.6’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Packages required but not available: 'nlmixr2est', 'nlmixr2extra' - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# NA - -
- -* Version: NA -* GitHub: NA -* Source code: https://github.com/cran/NA -* Number of recursive dependencies: 0 - -Run `cloud_details(, "NA")` for more info - -
- -## Error before installation - -### Devel - -``` - - - - - - -``` -### CRAN - -``` - - - - - - -``` -# NA - -
- -* Version: NA -* GitHub: NA -* Source code: https://github.com/cran/NA -* Number of recursive dependencies: 0 - -Run `cloud_details(, "NA")` for more info - -
- -## Error before installation - -### Devel - -``` - - - - - - -``` -### CRAN - -``` - - - - - - -``` -# Platypus - -
- -* Version: 3.4.1 -* GitHub: NA -* Source code: https://github.com/cran/Platypus -* Date/Publication: 2022-08-15 07:20:20 UTC -* Number of recursive dependencies: 355 - -Run `cloud_details(, "Platypus")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/Platypus/new/Platypus.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘Platypus/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘Platypus’ version ‘3.4.1’ -* package encoding: UTF-8 -* checking package namespace information ... 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 - ‘PlatypusV3_agedCNS.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: 1 NOTE - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/Platypus/old/Platypus.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘Platypus/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘Platypus’ version ‘3.4.1’ -* package encoding: UTF-8 -* checking package namespace information ... 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 - ‘PlatypusV3_agedCNS.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: 1 NOTE - - - - - -``` -# NA - -
- -* Version: NA -* GitHub: NA -* Source code: https://github.com/cran/NA -* Number of recursive dependencies: 0 - -Run `cloud_details(, "NA")` for more info - -
- -## Error before installation - -### Devel - -``` - - - - - - -``` -### CRAN - -``` - - - - - - -``` -# NA - -
- -* Version: NA -* GitHub: NA -* Source code: https://github.com/cran/NA -* Number of recursive dependencies: 0 - -Run `cloud_details(, "NA")` for more info - -
- -## Error before installation - -### Devel - -``` - - - - - - -``` -### CRAN - -``` - - - - - - -``` -# NA - -
- -* Version: NA -* GitHub: NA -* Source code: https://github.com/cran/NA -* Number of recursive dependencies: 0 - -Run `cloud_details(, "NA")` for more info - -
- -## Error before installation - -### Devel - -``` - - - - - - -``` -### CRAN - -``` - - - - - - -``` -# NA - -
- -* Version: NA -* GitHub: NA -* Source code: https://github.com/cran/NA -* Number of recursive dependencies: 0 - -Run `cloud_details(, "NA")` for more info - -
- -## Error before installation - -### Devel - -``` - - - - - - -``` -### CRAN - -``` - - - - - - -``` -# tidySEM - -
- -* Version: 0.2.3 -* GitHub: https://github.com/cjvanlissa/tidySEM -* Source code: https://github.com/cran/tidySEM -* Date/Publication: 2022-04-14 17:50:02 UTC -* Number of recursive dependencies: 170 - -Run `cloud_details(, "tidySEM")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/tidySEM/new/tidySEM.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘tidySEM/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘tidySEM’ version ‘0.2.3’ -* package encoding: UTF-8 -* checking package namespace information ... OK -... -* checking for unstated dependencies in vignettes ... OK -* checking package vignettes in ‘inst/doc’ ... OK -* checking running R code from vignettes ... NONE - ‘Generating_syntax.Rmd’ using ‘UTF-8’... OK - ‘Plotting_graphs.Rmd’ using ‘UTF-8’... OK - ‘Tabulating_results.Rmd’ using ‘UTF-8’... OK - ‘sem_graph.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: 1 NOTE - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/tidySEM/old/tidySEM.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘tidySEM/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘tidySEM’ version ‘0.2.3’ -* package encoding: UTF-8 -* checking package namespace information ... OK -... -* checking for unstated dependencies in vignettes ... OK -* checking package vignettes in ‘inst/doc’ ... OK -* checking running R code from vignettes ... NONE - ‘Generating_syntax.Rmd’ using ‘UTF-8’... OK - ‘Plotting_graphs.Rmd’ using ‘UTF-8’... OK - ‘Tabulating_results.Rmd’ using ‘UTF-8’... OK - ‘sem_graph.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: 1 NOTE - - - - - -``` -# NA - -
- -* Version: NA -* GitHub: NA -* Source code: https://github.com/cran/NA -* Number of recursive dependencies: 0 - -Run `cloud_details(, "NA")` for more info - -
- -## Error before installation - -### Devel - -``` - - - - - - -``` -### CRAN - -``` - - - - - - -``` -# vivid +# tidybayes
-* Version: 0.2.3 -* GitHub: NA -* Source code: https://github.com/cran/vivid -* Date/Publication: 2021-11-20 01:30:02 UTC -* Number of recursive dependencies: 201 +* Version: 3.0.2 +* GitHub: https://github.com/mjskay/tidybayes +* Source code: https://github.com/cran/tidybayes +* Date/Publication: 2022-01-05 06:10:02 UTC +* Number of recursive dependencies: 206 -Run `cloud_details(, "vivid")` for more info +Run `cloud_details(, "tidybayes")` for more info
@@ -968,24 +52,24 @@ Run `cloud_details(, "vivid")` for more info ### Devel ``` -* using log directory ‘/tmp/workdir/vivid/new/vivid.Rcheck’ +* using log directory ‘/tmp/workdir/tidybayes/new/tidybayes.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘vivid/DESCRIPTION’ ... OK -* this is package ‘vivid’ version ‘0.2.3’ +* checking for file ‘tidybayes/DESCRIPTION’ ... OK +* this is package ‘tidybayes’ version ‘3.0.2’ * package encoding: UTF-8 * checking package namespace information ... OK * checking package dependencies ... NOTE ... -* 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 - ‘vivid.Rmd’ using ‘UTF-8’... OK - ‘vividQStart.Rmd’ using ‘UTF-8’... OK + ‘tidy-brms.Rmd’ using ‘UTF-8’... OK + ‘tidy-posterior.Rmd’ using ‘UTF-8’... OK + ‘tidy-rstanarm.Rmd’ using ‘UTF-8’... OK + ‘tidybayes-residuals.Rmd’ using ‘UTF-8’... OK + ‘tidybayes.Rmd’ using ‘UTF-8’... OK * checking re-building of vignette outputs ... OK * DONE Status: 2 NOTEs @@ -998,24 +82,24 @@ Status: 2 NOTEs ### CRAN ``` -* using log directory ‘/tmp/workdir/vivid/old/vivid.Rcheck’ +* using log directory ‘/tmp/workdir/tidybayes/old/tidybayes.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘vivid/DESCRIPTION’ ... OK -* this is package ‘vivid’ version ‘0.2.3’ +* checking for file ‘tidybayes/DESCRIPTION’ ... OK +* this is package ‘tidybayes’ version ‘3.0.2’ * package encoding: UTF-8 * checking package namespace information ... OK * checking package dependencies ... NOTE ... -* 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 - ‘vivid.Rmd’ using ‘UTF-8’... OK - ‘vividQStart.Rmd’ using ‘UTF-8’... OK + ‘tidy-brms.Rmd’ using ‘UTF-8’... OK + ‘tidy-posterior.Rmd’ using ‘UTF-8’... OK + ‘tidy-rstanarm.Rmd’ using ‘UTF-8’... OK + ‘tidybayes-residuals.Rmd’ using ‘UTF-8’... OK + ‘tidybayes.Rmd’ using ‘UTF-8’... OK * checking re-building of vignette outputs ... OK * DONE Status: 2 NOTEs @@ -1025,17 +109,17 @@ Status: 2 NOTEs ``` -# xpose.nlmixr2 +# tidyposterior
-* Version: 0.4.0 -* GitHub: NA -* Source code: https://github.com/cran/xpose.nlmixr2 -* Date/Publication: 2022-06-08 09:10:02 UTC -* Number of recursive dependencies: 204 +* Version: 1.0.0 +* GitHub: https://github.com/tidymodels/tidyposterior +* Source code: https://github.com/cran/tidyposterior +* Date/Publication: 2022-06-23 20:20:02 UTC +* Number of recursive dependencies: 170 -Run `cloud_details(, "xpose.nlmixr2")` for more info +Run `cloud_details(, "tidyposterior")` for more info
@@ -1044,20 +128,17 @@ Run `cloud_details(, "xpose.nlmixr2")` for more info ### Devel ``` -* using log directory ‘/tmp/workdir/xpose.nlmixr2/new/xpose.nlmixr2.Rcheck’ +* using log directory ‘/tmp/workdir/tidyposterior/new/tidyposterior.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘xpose.nlmixr2/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘xpose.nlmixr2’ version ‘0.4.0’ +* checking for file ‘tidyposterior/DESCRIPTION’ ... OK +* this is package ‘tidyposterior’ version ‘1.0.0’ * package encoding: UTF-8 * checking package namespace information ... OK * checking package dependencies ... ERROR -Package required but not available: ‘nlmixr2est’ - -Package suggested but not available for checking: ‘nlmixr2’ +Package required but not available: ‘rstanarm’ See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ manual. @@ -1072,20 +153,17 @@ Status: 1 ERROR ### CRAN ``` -* using log directory ‘/tmp/workdir/xpose.nlmixr2/old/xpose.nlmixr2.Rcheck’ +* using log directory ‘/tmp/workdir/tidyposterior/old/tidyposterior.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘xpose.nlmixr2/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘xpose.nlmixr2’ version ‘0.4.0’ +* checking for file ‘tidyposterior/DESCRIPTION’ ... OK +* this is package ‘tidyposterior’ version ‘1.0.0’ * package encoding: UTF-8 * checking package namespace information ... OK * checking package dependencies ... ERROR -Package required but not available: ‘nlmixr2est’ - -Package suggested but not available for checking: ‘nlmixr2’ +Package required but not available: ‘rstanarm’ See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ manual. diff --git a/revdep/problems.md b/revdep/problems.md index af1985c00..9a2073633 100644 --- a/revdep/problems.md +++ b/revdep/problems.md @@ -1,151 +1 @@ -# globaltrends - -
- -* Version: 0.0.12 -* GitHub: https://github.com/ha-pu/globaltrends -* Source code: https://github.com/cran/globaltrends -* Date/Publication: 2022-06-23 07:10:11 UTC -* Number of recursive dependencies: 108 - -Run `cloud_details(, "globaltrends")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘test_functions.r’ - Running ‘testthat.r’ - Running the tests in ‘tests/testthat.r’ failed. - Last 13 lines of output: - Error in `initialize_db()`: Error: File 'db/globaltrends_db.sqlite' already exists. - Backtrace: - ▆ - 1. └─globaltrends::initialize_db() at test-plot_voi_doi.R:8:0 - ── Error ('test-synonyms.R:8'): (code run outside of `test_that()`) ──────────── - Error in `initialize_db()`: Error: File 'db/globaltrends_db.sqlite' already exists. - Backtrace: - ▆ - 1. └─globaltrends::initialize_db() at test-synonyms.R:8:0 - - [ FAIL 15 | WARN 22 | SKIP 0 | PASS 33 ] - Error: Test failures - In addition: Warning message: - call dbDisconnect() when finished working with a connection - Execution halted - ``` - -# goldilocks - -
- -* Version: 0.3.0 -* GitHub: NA -* Source code: https://github.com/cran/goldilocks -* Date/Publication: 2021-05-10 08:20:11 UTC -* Number of recursive dependencies: 68 - -Run `cloud_details(, "goldilocks")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Last 13 lines of output: - ══ Skipped tests ═══════════════════════════════════════════════════════════════ - • On CRAN (1) - - ══ Failed tests ════════════════════════════════════════════════════════════════ - ── Error ('test-survival_adapt.R:54'): survival_adapt-cox ────────────────────── - Error in `if (success > prob_ha) { - expected_success_test <- expected_success_test + 1 - }`: missing value where TRUE/FALSE needed - Backtrace: - ▆ - 1. └─goldilocks::survival_adapt(...) at test-survival_adapt.R:54:2 - - [ FAIL 1 | WARN 2 | SKIP 1 | PASS 17 ] - Error: Test failures - Execution halted - ``` - -# psfmi - -
- -* Version: 1.0.0 -* GitHub: https://github.com/mwheymans/psfmi -* Source code: https://github.com/cran/psfmi -* Date/Publication: 2021-09-23 10:10:05 UTC -* Number of recursive dependencies: 156 - -Run `cloud_details(, "psfmi")` for more info - -
- -## Newly broken - -* checking examples ... ERROR - ``` - Running examples in ‘psfmi-Ex.R’ failed - The error most likely occurred in: - - > ### Name: psfmi_validate - > ### Title: Internal validation and performance of logistic prediction - > ### models across Multiply Imputed datasets - > ### Aliases: psfmi_validate - > - > ### ** Examples - > - ... - ! `strata` should be a single name or character value. - Backtrace: - ▆ - 1. └─psfmi::psfmi_validate(...) - 2. └─psfmi::cv_MI(...) - 3. ├─purrr::map(...) - 4. └─rsample::vfold_cv(data_orig, v = folds, strata = unlist(data_orig[pobj$Outcome])) - 5. └─rsample:::strata_check(strata, data) - 6. └─rlang::abort("`strata` should be a single name or character value.") - Execution halted - ``` - -* checking re-building of vignette outputs ... WARNING - ``` - Error(s) in re-building vignettes: - --- re-building ‘MI_boot.Rmd’ using rmarkdown - --- finished re-building ‘MI_boot.Rmd’ - - --- re-building ‘MI_cv_naive.Rmd’ using rmarkdown - --- finished re-building ‘MI_cv_naive.Rmd’ - - --- re-building ‘Pool_Model_Performance.Rmd’ using rmarkdown - --- finished re-building ‘Pool_Model_Performance.Rmd’ - - ... - --- finished re-building ‘psfmi_StabilityAnalysis.Rmd’ - - --- re-building ‘psfmi_mice.Rmd’ using rmarkdown - --- finished re-building ‘psfmi_mice.Rmd’ - - SUMMARY: processing the following files failed: - ‘cv_MI.Rmd’ ‘cv_MI_RR.Rmd’ ‘development_workflow.Rmd’ - - Error: Vignette re-building failed. - Execution halted - ``` - -## In both - -* checking dependencies in R code ... NOTE - ``` - Namespace in Imports field not imported from: ‘miceadds’ - All declared Imports should be used. - ``` - +*Wow, no problems at all. :)* \ No newline at end of file From 765a600621ff1faba0317f831b49e856645f512e Mon Sep 17 00:00:00 2001 From: DavisVaughan Date: Fri, 20 Jan 2023 16:02:55 -0500 Subject: [PATCH 217/312] Increment version number to 0.5.2 --- DESCRIPTION | 2 +- NEWS.md | 2 +- src/version.c | 2 +- 3 files changed, 3 insertions(+), 3 deletions(-) diff --git a/DESCRIPTION b/DESCRIPTION index 1695964bc..61e2434ca 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -1,6 +1,6 @@ Package: vctrs Title: Vector Helpers -Version: 0.5.1.9000 +Version: 0.5.2 Authors@R: c(person(given = "Hadley", family = "Wickham", diff --git a/NEWS.md b/NEWS.md index 60dddec7a..e96b4f23f 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,4 +1,4 @@ -# vctrs (development version) +# vctrs 0.5.2 * New `vec_expand_grid()`, which is a lower level helper that is similar to `tidyr::expand_grid()` (#1325). diff --git a/src/version.c b/src/version.c index 573a574a3..35c6ced1a 100644 --- a/src/version.c +++ b/src/version.c @@ -1,7 +1,7 @@ #define R_NO_REMAP #include -const char* vctrs_version = "0.5.1.9000"; +const char* vctrs_version = "0.5.2"; /** * This file records the expected package version in the shared From c47b2f03ab4d1a2573eba6e88a4c253d405a5e8e Mon Sep 17 00:00:00 2001 From: DavisVaughan Date: Fri, 20 Jan 2023 16:04:28 -0500 Subject: [PATCH 218/312] Update `cran-comments.md` --- cran-comments.md | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/cran-comments.md b/cran-comments.md index 3585fd769..1ea825650 100644 --- a/cran-comments.md +++ b/cran-comments.md @@ -1 +1 @@ -Fixes the failure with R-devel. +This is a patch release with no expected breakage of any reverse dependencies. From 9f5f4e12db8740e0cae3c0fa0ace31e81a4f38ba Mon Sep 17 00:00:00 2001 From: DavisVaughan Date: Sat, 21 Jan 2023 09:23:44 -0500 Subject: [PATCH 219/312] Fix protection issue detected by rchk ``` #> [UP] calling allocating function df_poke with a fresh pointer (out ) /home/docker/R-svn/packages/build/MBHF3DPc/vctrs/src/bind.c:247 ``` --- src/bind.c | 1 + 1 file changed, 1 insertion(+) diff --git a/src/bind.c b/src/bind.c index 506024be6..335574c24 100644 --- a/src/bind.c +++ b/src/bind.c @@ -242,6 +242,7 @@ r_obj* vec_rbind(r_obj* xs, df_c_fallback(out, ptype, xs, n_rows, name_spec, name_repair, error_call); out = vec_restore_recurse(out, ptype, VCTRS_OWNED_true); + KEEP_AT(out, out_pi); if (has_names_to) { out = df_poke(out, names_to_loc, names_to_col); From 639419b128141ec50ec83c0158659d3ff946a944 Mon Sep 17 00:00:00 2001 From: DavisVaughan Date: Sat, 21 Jan 2023 15:11:46 -0500 Subject: [PATCH 220/312] CRAN-SUBMISSION --- CRAN-SUBMISSION | 3 +++ 1 file changed, 3 insertions(+) create mode 100644 CRAN-SUBMISSION diff --git a/CRAN-SUBMISSION b/CRAN-SUBMISSION new file mode 100644 index 000000000..599b1a7f5 --- /dev/null +++ b/CRAN-SUBMISSION @@ -0,0 +1,3 @@ +Version: 0.5.2 +Date: 2023-01-21 20:11:35 UTC +SHA: 9f5f4e12db8740e0cae3c0fa0ace31e81a4f38ba From 0aac1b35bf24365ef35e694ad0e73f7b49573e7b Mon Sep 17 00:00:00 2001 From: DavisVaughan Date: Mon, 23 Jan 2023 08:49:43 -0500 Subject: [PATCH 221/312] Delete CRAN-SUBMISSION --- CRAN-SUBMISSION | 3 --- 1 file changed, 3 deletions(-) delete mode 100644 CRAN-SUBMISSION diff --git a/CRAN-SUBMISSION b/CRAN-SUBMISSION deleted file mode 100644 index 599b1a7f5..000000000 --- a/CRAN-SUBMISSION +++ /dev/null @@ -1,3 +0,0 @@ -Version: 0.5.2 -Date: 2023-01-21 20:11:35 UTC -SHA: 9f5f4e12db8740e0cae3c0fa0ace31e81a4f38ba From f6a79e70a8c2123fc37a18daacd920a2903771d4 Mon Sep 17 00:00:00 2001 From: DavisVaughan Date: Mon, 23 Jan 2023 08:51:15 -0500 Subject: [PATCH 222/312] Increment version number to 0.5.2.9000 --- DESCRIPTION | 2 +- NEWS.md | 2 ++ src/version.c | 2 +- 3 files changed, 4 insertions(+), 2 deletions(-) diff --git a/DESCRIPTION b/DESCRIPTION index 61e2434ca..6d7698124 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -1,6 +1,6 @@ Package: vctrs Title: Vector Helpers -Version: 0.5.2 +Version: 0.5.2.9000 Authors@R: c(person(given = "Hadley", family = "Wickham", diff --git a/NEWS.md b/NEWS.md index e96b4f23f..dc298a512 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,3 +1,5 @@ +# vctrs (development version) + # vctrs 0.5.2 * New `vec_expand_grid()`, which is a lower level helper that is similar to diff --git a/src/version.c b/src/version.c index 35c6ced1a..6146e60c2 100644 --- a/src/version.c +++ b/src/version.c @@ -1,7 +1,7 @@ #define R_NO_REMAP #include -const char* vctrs_version = "0.5.2"; +const char* vctrs_version = "0.5.2.9000"; /** * This file records the expected package version in the shared From 6dffe526500d332fa12b897a3b3917e588a34999 Mon Sep 17 00:00:00 2001 From: Davis Vaughan Date: Mon, 23 Jan 2023 14:17:01 -0500 Subject: [PATCH 223/312] Implement `vec_run_sizes()` (#1771) * Implement `vec_run_sizes()` * NEWS bullet * Rewrite `vec_unrep()` with faster `vec_run_sizes()` And connect it to `vec_run_sizes()` in the runs docs * Add `struct r_lazy error_call` arguments to the runs functions - And use `vec_check_vector()` in `vec_detect_run_bounds0()` - Together this generates much better error messages in this family on functions on non-vector types * Swap `where` for `ends` in `vec_run_sizes()` --- NAMESPACE | 1 + NEWS.md | 4 ++ R/rep.R | 2 +- R/runs.R | 46 ++++++++++++++---- man/runs.Rd | 63 +++++++++++++++++++++++++ man/vec_identify_runs.Rd | 40 ---------------- src/decl/rep-decl.h | 5 +- src/decl/runs-decl.h | 6 +-- src/init.c | 18 ++++---- src/rep.c | 81 +++++++------------------------- src/runs.c | 67 +++++++++++++++++++++------ src/runs.h | 3 +- tests/testthat/_snaps/rep.md | 8 ++++ tests/testthat/_snaps/runs.md | 16 +++++++ tests/testthat/test-rep.R | 6 +++ tests/testthat/test-runs.R | 87 ++++++++++++++++++++++++++++++++++- 16 files changed, 309 insertions(+), 144 deletions(-) create mode 100644 man/runs.Rd delete mode 100644 man/vec_identify_runs.Rd diff --git a/NAMESPACE b/NAMESPACE index e0958f5c3..9c27255af 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -618,6 +618,7 @@ export(vec_rep) export(vec_rep_each) export(vec_repeat) export(vec_restore) +export(vec_run_sizes) export(vec_seq_along) export(vec_set_difference) export(vec_set_intersect) diff --git a/NEWS.md b/NEWS.md index dc298a512..152f35dd7 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,5 +1,9 @@ # vctrs (development version) +* New `vec_run_sizes()` for computing the size of each run within a vector. It + is identical to the `times` column from `vec_unrep()`, but is faster if you + don't need the run key (#1210). + # vctrs 0.5.2 * New `vec_expand_grid()`, which is a lower level helper that is similar to diff --git a/R/rep.R b/R/rep.R index 1caacfe34..ac08a1719 100644 --- a/R/rep.R +++ b/R/rep.R @@ -111,5 +111,5 @@ vec_rep_each <- function(x, #' @rdname vec-rep #' @export vec_unrep <- function(x) { - .Call(ffi_vec_unrep, x) + .Call(ffi_vec_unrep, x, environment()) } diff --git a/R/runs.R b/R/runs.R index 4184a25fb..069d74c0f 100644 --- a/R/runs.R +++ b/R/runs.R @@ -1,9 +1,17 @@ #' Runs #' #' @description -#' `vec_identify_runs()` returns a vector of identifiers for the elements of -#' `x` that indicate which run of repeated values they fall in. The number of -#' runs is also returned as an attribute, `n`. +#' - `vec_identify_runs()` returns a vector of identifiers for the elements of +#' `x` that indicate which run of repeated values they fall in. The number of +#' runs is also returned as an attribute, `n`. +#' +#' - `vec_run_sizes()` returns an integer vector corresponding to the size of +#' each run. This is identical to the `times` column from `vec_unrep()`, but +#' is faster if you don't need the run keys. +#' +#' - [vec_unrep()] is a generalized [base::rle()]. It is documented alongside +#' the "repeat" functions of [vec_rep()] and [vec_rep_each()]; look there for +#' more information. #' #' @details #' Unlike [base::rle()], adjacent missing values are considered identical when @@ -13,14 +21,22 @@ #' @param x A vector. #' #' @return -#' An integer vector with the same size as `x`. A scalar integer attribute, -#' `n`, is attached. +#' - For `vec_identify_runs()`, an integer vector with the same size as `x`. A +#' scalar integer attribute, `n`, is attached. #' -#' @export +#' - For `vec_run_sizes()`, an integer vector with size equal to the number of +#' runs in `x`. +#' +#' @seealso +#' [vec_unrep()] for a generalized [base::rle()]. +#' +#' @name runs #' @examples #' x <- c("a", "z", "z", "c", "a", "a") #' #' vec_identify_runs(x) +#' vec_run_sizes(x) +#' vec_unrep(x) #' #' y <- c(1, 1, 1, 2, 2, 3) #' @@ -31,14 +47,26 @@ #' ) #' #' vec_identify_runs(df) +#' vec_run_sizes(df) +#' vec_unrep(df) +NULL + +#' @rdname runs +#' @export vec_identify_runs <- function(x) { - .Call(ffi_vec_identify_runs, x) + .Call(ffi_vec_identify_runs, x, environment()) +} + +#' @rdname runs +#' @export +vec_run_sizes <- function(x) { + .Call(ffi_vec_run_sizes, x, environment()) } vec_locate_run_bounds <- function(x, start = TRUE) { - .Call(ffi_vec_locate_run_bounds, x, start) + .Call(ffi_vec_locate_run_bounds, x, start, environment()) } vec_detect_run_bounds <- function(x, start = TRUE) { - .Call(ffi_vec_detect_run_bounds, x, start) + .Call(ffi_vec_detect_run_bounds, x, start, environment()) } diff --git a/man/runs.Rd b/man/runs.Rd new file mode 100644 index 000000000..21cc87903 --- /dev/null +++ b/man/runs.Rd @@ -0,0 +1,63 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/runs.R +\name{runs} +\alias{runs} +\alias{vec_identify_runs} +\alias{vec_run_sizes} +\title{Runs} +\usage{ +vec_identify_runs(x) + +vec_run_sizes(x) +} +\arguments{ +\item{x}{A vector.} +} +\value{ +\itemize{ +\item For \code{vec_identify_runs()}, an integer vector with the same size as \code{x}. A +scalar integer attribute, \code{n}, is attached. +\item For \code{vec_run_sizes()}, an integer vector with size equal to the number of +runs in \code{x}. +} +} +\description{ +\itemize{ +\item \code{vec_identify_runs()} returns a vector of identifiers for the elements of +\code{x} that indicate which run of repeated values they fall in. The number of +runs is also returned as an attribute, \code{n}. +\item \code{vec_run_sizes()} returns an integer vector corresponding to the size of +each run. This is identical to the \code{times} column from \code{vec_unrep()}, but +is faster if you don't need the run keys. +\item \code{\link[=vec_unrep]{vec_unrep()}} is a generalized \code{\link[base:rle]{base::rle()}}. It is documented alongside +the "repeat" functions of \code{\link[=vec_rep]{vec_rep()}} and \code{\link[=vec_rep_each]{vec_rep_each()}}; look there for +more information. +} +} +\details{ +Unlike \code{\link[base:rle]{base::rle()}}, adjacent missing values are considered identical when +constructing runs. For example, \code{vec_identify_runs(c(NA, NA))} will return +\code{c(1, 1)}, not \code{c(1, 2)}. +} +\examples{ +x <- c("a", "z", "z", "c", "a", "a") + +vec_identify_runs(x) +vec_run_sizes(x) +vec_unrep(x) + +y <- c(1, 1, 1, 2, 2, 3) + +# With multiple columns, the runs are constructed rowwise +df <- data_frame( + x = x, + y = y +) + +vec_identify_runs(df) +vec_run_sizes(df) +vec_unrep(df) +} +\seealso{ +\code{\link[=vec_unrep]{vec_unrep()}} for a generalized \code{\link[base:rle]{base::rle()}}. +} diff --git a/man/vec_identify_runs.Rd b/man/vec_identify_runs.Rd deleted file mode 100644 index c7e69fb3d..000000000 --- a/man/vec_identify_runs.Rd +++ /dev/null @@ -1,40 +0,0 @@ -% Generated by roxygen2: do not edit by hand -% Please edit documentation in R/runs.R -\name{vec_identify_runs} -\alias{vec_identify_runs} -\title{Runs} -\usage{ -vec_identify_runs(x) -} -\arguments{ -\item{x}{A vector.} -} -\value{ -An integer vector with the same size as \code{x}. A scalar integer attribute, -\code{n}, is attached. -} -\description{ -\code{vec_identify_runs()} returns a vector of identifiers for the elements of -\code{x} that indicate which run of repeated values they fall in. The number of -runs is also returned as an attribute, \code{n}. -} -\details{ -Unlike \code{\link[base:rle]{base::rle()}}, adjacent missing values are considered identical when -constructing runs. For example, \code{vec_identify_runs(c(NA, NA))} will return -\code{c(1, 1)}, not \code{c(1, 2)}. -} -\examples{ -x <- c("a", "z", "z", "c", "a", "a") - -vec_identify_runs(x) - -y <- c(1, 1, 1, 2, 2, 3) - -# With multiple columns, the runs are constructed rowwise -df <- data_frame( - x = x, - y = y -) - -vec_identify_runs(df) -} diff --git a/src/decl/rep-decl.h b/src/decl/rep-decl.h index ada05d49d..fe2b1de84 100644 --- a/src/decl/rep-decl.h +++ b/src/decl/rep-decl.h @@ -54,7 +54,4 @@ static inline void stop_rep_each_times_oob(int times, r_ssize i, struct r_lazy call, struct vctrs_arg* p_times_arg); static -r_obj* vec_unrep(r_obj* x); - -static -r_obj* new_unrep_data_frame(r_obj* key, r_obj* times, r_ssize size); +r_obj* vec_unrep(r_obj* x, struct r_lazy error_call); diff --git a/src/decl/runs-decl.h b/src/decl/runs-decl.h index f9d243c54..134d38d2d 100644 --- a/src/decl/runs-decl.h +++ b/src/decl/runs-decl.h @@ -1,10 +1,10 @@ static -r_obj* vec_detect_run_bounds(r_obj* x, bool start); +r_obj* vec_detect_run_bounds(r_obj* x, bool start, struct r_lazy error_call); static -r_obj* vec_locate_run_bounds(r_obj* x, bool start); +r_obj* vec_locate_run_bounds(r_obj* x, bool start, struct r_lazy error_call); static -r_obj* vec_detect_run_bounds0(r_obj* x, bool start); +r_obj* vec_detect_run_bounds0(r_obj* x, bool start, struct r_lazy error_call); static inline void lgl_detect_run_bounds0(r_obj* x, r_ssize size, bool start, bool* v_out); diff --git a/src/init.c b/src/init.c index 3d5320fee..673fba741 100644 --- a/src/init.c +++ b/src/init.c @@ -120,9 +120,10 @@ extern r_obj* ffi_cast_dispatch_native(r_obj*, r_obj*, r_obj*, r_obj*, r_obj*, r extern SEXP vctrs_fast_c(SEXP, SEXP); extern r_obj* ffi_data_frame(r_obj*, r_obj*, r_obj*, r_obj*); extern r_obj* ffi_df_list(r_obj*, r_obj*, r_obj*, r_obj*, r_obj*); -extern SEXP ffi_vec_detect_run_bounds(r_obj*, r_obj*); -extern SEXP ffi_vec_locate_run_bounds(r_obj*, r_obj*); -extern SEXP ffi_vec_identify_runs(r_obj*); +extern r_obj* ffi_vec_detect_run_bounds(r_obj*, r_obj*, r_obj*); +extern r_obj* ffi_vec_locate_run_bounds(r_obj*, r_obj*, r_obj*); +extern r_obj* ffi_vec_identify_runs(r_obj*, r_obj*); +extern r_obj* ffi_vec_run_sizes(r_obj*, r_obj*); extern SEXP vctrs_slice_complete(SEXP); extern SEXP vctrs_locate_complete(SEXP); extern SEXP vctrs_detect_complete(SEXP); @@ -130,7 +131,7 @@ extern SEXP vctrs_normalize_encoding(SEXP); extern SEXP vctrs_order(SEXP, SEXP, SEXP, SEXP, SEXP); extern SEXP vctrs_locate_sorted_groups(SEXP, SEXP, SEXP, SEXP, SEXP); extern SEXP vctrs_order_info(SEXP, SEXP, SEXP, SEXP, SEXP, SEXP); -extern r_obj* ffi_vec_unrep(r_obj*); +extern r_obj* ffi_vec_unrep(r_obj*, r_obj*); extern SEXP vctrs_fill_missing(SEXP, SEXP, SEXP); extern r_obj* ffi_chr_paste_prefix(r_obj*, r_obj*, r_obj*); extern r_obj* vctrs_rank(r_obj*, r_obj*, r_obj*, r_obj*, r_obj*, r_obj*, r_obj*); @@ -300,9 +301,10 @@ static const R_CallMethodDef CallEntries[] = { {"vctrs_fast_c", (DL_FUNC) &vctrs_fast_c, 2}, {"ffi_data_frame", (DL_FUNC) &ffi_data_frame, 4}, {"ffi_df_list", (DL_FUNC) &ffi_df_list, 5}, - {"ffi_vec_detect_run_bounds", (DL_FUNC) &ffi_vec_detect_run_bounds, 2}, - {"ffi_vec_locate_run_bounds", (DL_FUNC) &ffi_vec_locate_run_bounds, 2}, - {"ffi_vec_identify_runs", (DL_FUNC) &ffi_vec_identify_runs, 1}, + {"ffi_vec_detect_run_bounds", (DL_FUNC) &ffi_vec_detect_run_bounds, 3}, + {"ffi_vec_locate_run_bounds", (DL_FUNC) &ffi_vec_locate_run_bounds, 3}, + {"ffi_vec_identify_runs", (DL_FUNC) &ffi_vec_identify_runs, 2}, + {"ffi_vec_run_sizes", (DL_FUNC) &ffi_vec_run_sizes, 2}, {"vctrs_slice_complete", (DL_FUNC) &vctrs_slice_complete, 1}, {"vctrs_locate_complete", (DL_FUNC) &vctrs_locate_complete, 1}, {"vctrs_detect_complete", (DL_FUNC) &vctrs_detect_complete, 1}, @@ -310,7 +312,7 @@ static const R_CallMethodDef CallEntries[] = { {"vctrs_order", (DL_FUNC) &vctrs_order, 5}, {"vctrs_locate_sorted_groups", (DL_FUNC) &vctrs_locate_sorted_groups, 5}, {"vctrs_order_info", (DL_FUNC) &vctrs_order_info, 6}, - {"ffi_vec_unrep", (DL_FUNC) &ffi_vec_unrep, 1}, + {"ffi_vec_unrep", (DL_FUNC) &ffi_vec_unrep, 2}, {"vctrs_fill_missing", (DL_FUNC) &vctrs_fill_missing, 3}, {"ffi_chr_paste_prefix", (DL_FUNC) &ffi_chr_paste_prefix, 3}, {"vctrs_rank", (DL_FUNC) &vctrs_rank, 7}, diff --git a/src/rep.c b/src/rep.c index 37dd184cf..268511b22 100644 --- a/src/rep.c +++ b/src/rep.c @@ -343,89 +343,42 @@ void stop_rep_times_size(struct r_lazy call, // ----------------------------------------------------------------------------- static -r_obj* vec_unrep(r_obj* x) { - r_obj* id = KEEP(vec_identify_runs(x)); - const int* p_id = r_int_cbegin(id); - - r_ssize x_size = r_length(id); - - if (x_size == 0) { - r_obj* out = new_unrep_data_frame(x, r_globals.empty_int, 0); - FREE(1); - return out; - } - - r_ssize out_size = (r_ssize) r_int_get(r_attrib_get(id, syms_n), 0); - - // Size of each run - r_obj* times = KEEP(r_new_integer(out_size)); - int* v_times = r_int_begin(times); - - // Location of the start of each run. For slicing `x`. - r_obj* loc = KEEP(r_new_integer(out_size)); - int* p_loc = r_int_begin(loc); - - r_ssize idx = 0; - r_ssize previous = 0; - - int reference = p_id[0]; - - // Handle first case - p_loc[idx] = 1; - ++idx; - - for (r_ssize i = 1; i < x_size; ++i) { - const int elt = p_id[i]; +r_obj* vec_unrep(r_obj* x, struct r_lazy error_call) { + r_obj* times = KEEP(vec_run_sizes(x, error_call)); + const int* v_times = r_int_cbegin(times); - if (elt == reference) { - continue; - } + const r_ssize size = r_length(times); - reference = elt; + r_obj* loc = KEEP(r_alloc_integer(size)); + int* v_loc = r_int_begin(loc); - // Size of current run - v_times[idx - 1] = i - previous; - previous = i; + r_ssize current = 1; - // 1-based location of the start of the new run - p_loc[idx] = i + 1; - ++idx; + for (r_ssize i = 0; i < size; ++i) { + v_loc[i] = current; + current += v_times[i]; } - // Handle last case - v_times[idx - 1] = x_size - previous; - - r_obj* key = KEEP(vec_slice(x, loc)); - r_obj* out = new_unrep_data_frame(key, times, out_size); - - FREE(4); - return out; -} - -r_obj* ffi_vec_unrep(r_obj* x) { - return vec_unrep(x); -} - - -static -r_obj* new_unrep_data_frame(r_obj* key, r_obj* times, r_ssize size) { r_obj* out = KEEP(r_new_list(2)); - r_list_poke(out, 0, key); + r_list_poke(out, 0, vec_slice_unsafe(x, loc)); r_list_poke(out, 1, times); - r_obj* names = KEEP(r_new_character(2)); + r_obj* names = r_new_character(2); r_attrib_poke_names(out, names); - r_chr_poke(names, 0, strings_key); r_chr_poke(names, 1, strings_times); init_data_frame(out, size); - FREE(2); + FREE(3); return out; } +r_obj* ffi_vec_unrep(r_obj* x, r_obj* frame) { + struct r_lazy error_call = { .x = frame, .env = r_null }; + return vec_unrep(x, error_call); +} // ----------------------------------------------------------------------------- diff --git a/src/runs.c b/src/runs.c index e07876d94..16c00958b 100644 --- a/src/runs.c +++ b/src/runs.c @@ -4,14 +4,15 @@ // ----------------------------------------------------------------------------- -r_obj* ffi_vec_detect_run_bounds(r_obj* x, r_obj* ffi_start) { +r_obj* ffi_vec_detect_run_bounds(r_obj* x, r_obj* ffi_start, r_obj* frame) { + struct r_lazy error_call = { .x = frame, .env = r_null }; const bool start = r_arg_as_bool(ffi_start, "start"); - return vec_detect_run_bounds(x, start); + return vec_detect_run_bounds(x, start, error_call); } static -r_obj* vec_detect_run_bounds(r_obj* x, bool start) { - r_obj* where = KEEP(vec_detect_run_bounds0(x, start)); +r_obj* vec_detect_run_bounds(r_obj* x, bool start, struct r_lazy error_call) { + r_obj* where = KEEP(vec_detect_run_bounds0(x, start, error_call)); const bool* v_where = r_raw_cbegin(where); const r_ssize size = r_length(where) / sizeof(bool); @@ -29,14 +30,15 @@ r_obj* vec_detect_run_bounds(r_obj* x, bool start) { // ----------------------------------------------------------------------------- -r_obj* ffi_vec_locate_run_bounds(r_obj* x, r_obj* ffi_start) { +r_obj* ffi_vec_locate_run_bounds(r_obj* x, r_obj* ffi_start, r_obj* frame) { + struct r_lazy error_call = { .x = frame, .env = r_null }; const bool start = r_arg_as_bool(ffi_start, "start"); - return vec_locate_run_bounds(x, start); + return vec_locate_run_bounds(x, start, error_call); } static -r_obj* vec_locate_run_bounds(r_obj* x, bool start) { - r_obj* where = KEEP(vec_detect_run_bounds0(x, start)); +r_obj* vec_locate_run_bounds(r_obj* x, bool start, struct r_lazy error_call) { + r_obj* where = KEEP(vec_detect_run_bounds0(x, start, error_call)); const bool* v_where = r_raw_cbegin(where); const r_ssize size = r_length(where) / sizeof(bool); @@ -60,13 +62,14 @@ r_obj* vec_locate_run_bounds(r_obj* x, bool start) { // ----------------------------------------------------------------------------- -r_obj* ffi_vec_identify_runs(r_obj* x) { - return vec_identify_runs(x); +r_obj* ffi_vec_identify_runs(r_obj* x, r_obj* frame) { + struct r_lazy error_call = { .x = frame, .env = r_null }; + return vec_identify_runs(x, error_call); } -r_obj* vec_identify_runs(r_obj* x) { +r_obj* vec_identify_runs(r_obj* x, struct r_lazy error_call) { const bool start = true; - r_obj* where = KEEP(vec_detect_run_bounds0(x, start)); + r_obj* where = KEEP(vec_detect_run_bounds0(x, start, error_call)); const bool* v_where = r_raw_cbegin(where); const r_ssize size = r_length(where) / sizeof(bool); @@ -90,12 +93,50 @@ r_obj* vec_identify_runs(r_obj* x) { // ----------------------------------------------------------------------------- +r_obj* ffi_vec_run_sizes(r_obj* x, r_obj* frame) { + struct r_lazy error_call = { .x = frame, .env = r_null }; + return vec_run_sizes(x, error_call); +} + +r_obj* vec_run_sizes(r_obj* x, struct r_lazy error_call) { + const bool start = false; + r_obj* ends = KEEP(vec_detect_run_bounds0(x, start, error_call)); + const bool* v_ends = r_raw_cbegin(ends); + + const r_ssize size = r_length(ends) / sizeof(bool); + + r_ssize n = 0; + for (r_ssize i = 0; i < size; ++i) { + n += v_ends[i]; + } + + r_obj* out = KEEP(r_alloc_integer(n)); + int* v_out = r_int_begin(out); + r_ssize j = 0; + + int count = 1; + + for (r_ssize i = 0; i < size; ++i) { + const bool end = v_ends[i]; + v_out[j] = count; + j += end; + count = !end * count + 1; + } + + FREE(2); + return out; +} + +// ----------------------------------------------------------------------------- + /* * Like `vec_detect_run_bounds()`, but returns a less memory intensive * boolean array as a raw vector. */ static -r_obj* vec_detect_run_bounds0(r_obj* x, bool start) { +r_obj* vec_detect_run_bounds0(r_obj* x, bool start, struct r_lazy error_call) { + vec_check_vector(x, vec_args.x, error_call); + r_obj* proxy = KEEP(vec_proxy_equal(x)); proxy = KEEP(vec_normalize_encoding(proxy)); diff --git a/src/runs.h b/src/runs.h index da1ce3921..458b01b10 100644 --- a/src/runs.h +++ b/src/runs.h @@ -3,6 +3,7 @@ #include "vctrs-core.h" -r_obj* vec_identify_runs(r_obj* x); +r_obj* vec_identify_runs(r_obj* x, struct r_lazy error_call); +r_obj* vec_run_sizes(r_obj* x, struct r_lazy error_call); #endif diff --git a/tests/testthat/_snaps/rep.md b/tests/testthat/_snaps/rep.md index 2996685c2..33478f600 100644 --- a/tests/testthat/_snaps/rep.md +++ b/tests/testthat/_snaps/rep.md @@ -148,3 +148,11 @@ Error in `my_vec_rep_each()`: ! Can't recycle `my_times` (size 3) to size 2. +# errors on scalars + + Code + vec_unrep(environment()) + Condition + Error in `vec_unrep()`: + ! `x` must be a vector, not an environment. + diff --git a/tests/testthat/_snaps/runs.md b/tests/testthat/_snaps/runs.md index b53d1b1f0..b7d3d6c75 100644 --- a/tests/testthat/_snaps/runs.md +++ b/tests/testthat/_snaps/runs.md @@ -1,3 +1,19 @@ +# errors on scalars + + Code + vec_identify_runs(foobar()) + Condition + Error in `vec_identify_runs()`: + ! `x` must be a vector, not a object. + +--- + + Code + vec_run_sizes(foobar()) + Condition + Error in `vec_run_sizes()`: + ! `x` must be a vector, not a object. + # vec_locate_run_bounds() validates `start` Code diff --git a/tests/testthat/test-rep.R b/tests/testthat/test-rep.R index e3346707a..0a3be03fc 100644 --- a/tests/testthat/test-rep.R +++ b/tests/testthat/test-rep.R @@ -159,3 +159,9 @@ test_that("works with data frames with rows but no columns", { expect <- data_frame(key = data_frame(.size = 1L), times = 5L) expect_identical(vec_unrep(x), expect) }) + +test_that("errors on scalars", { + expect_snapshot(error = TRUE, { + vec_unrep(environment()) + }) +}) diff --git a/tests/testthat/test-runs.R b/tests/testthat/test-runs.R index 2556ca26b..8aa9d3b54 100644 --- a/tests/testthat/test-runs.R +++ b/tests/testthat/test-runs.R @@ -43,7 +43,9 @@ test_that("normalizes character encodings", { }) test_that("errors on scalars", { - expect_error(vec_identify_runs(foobar()), class = "vctrs_error_scalar_type") + expect_snapshot(error = TRUE, { + vec_identify_runs(foobar()) + }) }) test_that("works with data frames rowwise", { @@ -86,6 +88,89 @@ test_that("works with columns of various types", { expect_identical(vec_identify_runs(add_col(list(1, 1, 2, 2, 3))), expect) }) +# vec_run_sizes ---------------------------------------------------------------- + +test_that("vec_run_sizes() works with size zero input", { + expect_identical(vec_run_sizes(integer()), integer()) + expect_identical(vec_run_sizes(data.frame()), integer()) +}) + +test_that("works with atomic input of various types", { + expect <- c(2L, 2L, 1L) + + expect_identical(vec_run_sizes(c(TRUE, TRUE, FALSE, FALSE, TRUE)), expect) + expect_identical(vec_run_sizes(c(1L, 1L, 2L, 2L, 3L)), expect) + expect_identical(vec_run_sizes(c(1, 1, 2, 2, 3)), expect) + expect_identical(vec_run_sizes(complex(real = c(1, 1, 2, 2, 2), imaginary = c(1, 1, 2, 2, 3))), expect) + expect_identical(vec_run_sizes(c("a", "a", "b", "b", "c")), expect) + expect_identical(vec_run_sizes(as.raw(c(1, 1, 2, 2, 3))), expect) + expect_identical(vec_run_sizes(list(1, 1, 2, 2, 3)), expect) +}) + +test_that("NA values are identical", { + expect <- 2L + + expect_identical(vec_run_sizes(c(NA, NA)), expect) + expect_identical(vec_run_sizes(c(NA_integer_, NA_integer_)), expect) + expect_identical(vec_run_sizes(c(NA_real_, NA_real_)), expect) + expect_identical(vec_run_sizes(c(NA_complex_, NA_complex_)), expect) + expect_identical(vec_run_sizes(c(NA_character_, NA_character_)), expect) + # No NA type for raw + expect_identical(vec_run_sizes(list(NULL, NULL)), expect) +}) + +test_that("NA and NaN are different", { + expect_identical(vec_run_sizes(c(NA_real_, NaN)), c(1L, 1L)) +}) + +test_that("normalizes character encodings", { + encs <- encodings() + x <- c(encs$utf8, encs$unknown, encs$latin1) + expect_identical(vec_run_sizes(x), 3L) +}) + +test_that("errors on scalars", { + expect_snapshot(error = TRUE, { + vec_run_sizes(foobar()) + }) +}) + +test_that("works with data frames rowwise", { + df <- data_frame(x = c(1, 1, 1, 2), y = c(1, 1, 2, 3)) + expect_identical(vec_run_sizes(df), c(2L, 1L, 1L)) + + df <- data_frame(x = c(1, 1, 1), y = c(2, 2, 2), z = c("b", "a", "a")) + expect_identical(vec_run_sizes(df), c(1L, 2L)) +}) + +test_that("works with data frames with rows but no columns", { + expect_identical(vec_run_sizes(new_data_frame(n = 5L)), 5L) +}) + +test_that("works with data frame columns", { + col <- data_frame(a = c(1, 1, 2, 2), b = c(1, 2, 3, 3)) + df <- data_frame(x = rep(1, 4), y = col) + expect_identical(vec_run_sizes(df), c(1L, 1L, 2L)) +}) + +test_that("works with columns of various types", { + # Use two columns to keep the data frame from being squashed to a vector + add_col <- function(col) { + x <- rep(1L, 5) + data_frame(x = x, y = col) + } + + expect <- c(2L, 2L, 1L) + + expect_identical(vec_run_sizes(add_col(c(TRUE, TRUE, FALSE, FALSE, TRUE))), expect) + expect_identical(vec_run_sizes(add_col(c(1L, 1L, 2L, 2L, 3L))), expect) + expect_identical(vec_run_sizes(add_col(c(1, 1, 2, 2, 3))), expect) + expect_identical(vec_run_sizes(add_col(complex(real = c(1, 1, 2, 2, 2), imaginary = c(1, 1, 2, 2, 3)))), expect) + expect_identical(vec_run_sizes(add_col(c("a", "a", "b", "b", "c"))), expect) + expect_identical(vec_run_sizes(add_col(as.raw(c(1, 1, 2, 2, 3)))), expect) + expect_identical(vec_run_sizes(add_col(list(1, 1, 2, 2, 3))), expect) +}) + # vec_locate_run_bounds -------------------------------------------------------- test_that("can locate run starts", { From 864e92ec9a11863cdedde96385e1795759fe111b Mon Sep 17 00:00:00 2001 From: DavisVaughan Date: Mon, 23 Jan 2023 16:05:21 -0500 Subject: [PATCH 224/312] Switch from `bounds0` to `bounds_bool` --- src/decl/runs-decl.h | 34 +++---- src/runs.c | 206 +++++++++++++++++++++---------------------- 2 files changed, 120 insertions(+), 120 deletions(-) diff --git a/src/decl/runs-decl.h b/src/decl/runs-decl.h index 134d38d2d..8abfbfb26 100644 --- a/src/decl/runs-decl.h +++ b/src/decl/runs-decl.h @@ -4,38 +4,38 @@ static r_obj* vec_locate_run_bounds(r_obj* x, bool start, struct r_lazy error_call); static -r_obj* vec_detect_run_bounds0(r_obj* x, bool start, struct r_lazy error_call); +r_obj* vec_detect_run_bounds_bool(r_obj* x, bool start, struct r_lazy error_call); static inline -void lgl_detect_run_bounds0(r_obj* x, r_ssize size, bool start, bool* v_out); +void lgl_detect_run_bounds_bool(r_obj* x, r_ssize size, bool start, bool* v_out); static inline -void int_detect_run_bounds0(r_obj* x, r_ssize size, bool start, bool* v_out); +void int_detect_run_bounds_bool(r_obj* x, r_ssize size, bool start, bool* v_out); static inline -void dbl_detect_run_bounds0(r_obj* x, r_ssize size, bool start, bool* v_out); +void dbl_detect_run_bounds_bool(r_obj* x, r_ssize size, bool start, bool* v_out); static inline -void cpl_detect_run_bounds0(r_obj* x, r_ssize size, bool start, bool* v_out); +void cpl_detect_run_bounds_bool(r_obj* x, r_ssize size, bool start, bool* v_out); static inline -void chr_detect_run_bounds0(r_obj* x, r_ssize size, bool start, bool* v_out); +void chr_detect_run_bounds_bool(r_obj* x, r_ssize size, bool start, bool* v_out); static inline -void raw_detect_run_bounds0(r_obj* x, r_ssize size, bool start, bool* v_out); +void raw_detect_run_bounds_bool(r_obj* x, r_ssize size, bool start, bool* v_out); static inline -void list_detect_run_bounds0(r_obj* x, r_ssize size, bool start, bool* v_out); +void list_detect_run_bounds_bool(r_obj* x, r_ssize size, bool start, bool* v_out); static inline -void df_detect_run_bounds0(r_obj* x, r_ssize size, bool start, bool* v_out); +void df_detect_run_bounds_bool(r_obj* x, r_ssize size, bool start, bool* v_out); static inline -void col_detect_run_bounds0(r_obj* x, r_ssize size, bool start, bool* v_out); +void col_detect_run_bounds_bool(r_obj* x, r_ssize size, bool start, bool* v_out); static inline -void lgl_col_detect_run_bounds0(r_obj* x, r_ssize size, bool start, bool* v_out); +void lgl_col_detect_run_bounds_bool(r_obj* x, r_ssize size, bool start, bool* v_out); static inline -void int_col_detect_run_bounds0(r_obj* x, r_ssize size, bool start, bool* v_out); +void int_col_detect_run_bounds_bool(r_obj* x, r_ssize size, bool start, bool* v_out); static inline -void dbl_col_detect_run_bounds0(r_obj* x, r_ssize size, bool start, bool* v_out); +void dbl_col_detect_run_bounds_bool(r_obj* x, r_ssize size, bool start, bool* v_out); static inline -void cpl_col_detect_run_bounds0(r_obj* x, r_ssize size, bool start, bool* v_out); +void cpl_col_detect_run_bounds_bool(r_obj* x, r_ssize size, bool start, bool* v_out); static inline -void chr_col_detect_run_bounds0(r_obj* x, r_ssize size, bool start, bool* v_out); +void chr_col_detect_run_bounds_bool(r_obj* x, r_ssize size, bool start, bool* v_out); static inline -void raw_col_detect_run_bounds0(r_obj* x, r_ssize size, bool start, bool* v_out); +void raw_col_detect_run_bounds_bool(r_obj* x, r_ssize size, bool start, bool* v_out); static inline -void list_col_detect_run_bounds0(r_obj* x, r_ssize size, bool start, bool* v_out); +void list_col_detect_run_bounds_bool(r_obj* x, r_ssize size, bool start, bool* v_out); diff --git a/src/runs.c b/src/runs.c index 16c00958b..01e5599d3 100644 --- a/src/runs.c +++ b/src/runs.c @@ -12,7 +12,7 @@ r_obj* ffi_vec_detect_run_bounds(r_obj* x, r_obj* ffi_start, r_obj* frame) { static r_obj* vec_detect_run_bounds(r_obj* x, bool start, struct r_lazy error_call) { - r_obj* where = KEEP(vec_detect_run_bounds0(x, start, error_call)); + r_obj* where = KEEP(vec_detect_run_bounds_bool(x, start, error_call)); const bool* v_where = r_raw_cbegin(where); const r_ssize size = r_length(where) / sizeof(bool); @@ -38,7 +38,7 @@ r_obj* ffi_vec_locate_run_bounds(r_obj* x, r_obj* ffi_start, r_obj* frame) { static r_obj* vec_locate_run_bounds(r_obj* x, bool start, struct r_lazy error_call) { - r_obj* where = KEEP(vec_detect_run_bounds0(x, start, error_call)); + r_obj* where = KEEP(vec_detect_run_bounds_bool(x, start, error_call)); const bool* v_where = r_raw_cbegin(where); const r_ssize size = r_length(where) / sizeof(bool); @@ -69,7 +69,7 @@ r_obj* ffi_vec_identify_runs(r_obj* x, r_obj* frame) { r_obj* vec_identify_runs(r_obj* x, struct r_lazy error_call) { const bool start = true; - r_obj* where = KEEP(vec_detect_run_bounds0(x, start, error_call)); + r_obj* where = KEEP(vec_detect_run_bounds_bool(x, start, error_call)); const bool* v_where = r_raw_cbegin(where); const r_ssize size = r_length(where) / sizeof(bool); @@ -100,7 +100,7 @@ r_obj* ffi_vec_run_sizes(r_obj* x, r_obj* frame) { r_obj* vec_run_sizes(r_obj* x, struct r_lazy error_call) { const bool start = false; - r_obj* ends = KEEP(vec_detect_run_bounds0(x, start, error_call)); + r_obj* ends = KEEP(vec_detect_run_bounds_bool(x, start, error_call)); const bool* v_ends = r_raw_cbegin(ends); const r_ssize size = r_length(ends) / sizeof(bool); @@ -134,7 +134,7 @@ r_obj* vec_run_sizes(r_obj* x, struct r_lazy error_call) { * boolean array as a raw vector. */ static -r_obj* vec_detect_run_bounds0(r_obj* x, bool start, struct r_lazy error_call) { +r_obj* vec_detect_run_bounds_bool(r_obj* x, bool start, struct r_lazy error_call) { vec_check_vector(x, vec_args.x, error_call); r_obj* proxy = KEEP(vec_proxy_equal(x)); @@ -148,15 +148,15 @@ r_obj* vec_detect_run_bounds0(r_obj* x, bool start, struct r_lazy error_call) { const enum vctrs_type type = vec_proxy_typeof(proxy); switch (type) { - case VCTRS_TYPE_logical: lgl_detect_run_bounds0(proxy, size, start, v_out); break; - case VCTRS_TYPE_integer: int_detect_run_bounds0(proxy, size, start, v_out); break; - case VCTRS_TYPE_double: dbl_detect_run_bounds0(proxy, size, start, v_out); break; - case VCTRS_TYPE_complex: cpl_detect_run_bounds0(proxy, size, start, v_out); break; - case VCTRS_TYPE_character: chr_detect_run_bounds0(proxy, size, start, v_out); break; - case VCTRS_TYPE_raw: raw_detect_run_bounds0(proxy, size, start, v_out); break; - case VCTRS_TYPE_list: list_detect_run_bounds0(proxy, size, start, v_out); break; - case VCTRS_TYPE_dataframe: df_detect_run_bounds0(proxy, size, start, v_out); break; - default: stop_unimplemented_vctrs_type("vec_detect_run_bounds0", type); + case VCTRS_TYPE_logical: lgl_detect_run_bounds_bool(proxy, size, start, v_out); break; + case VCTRS_TYPE_integer: int_detect_run_bounds_bool(proxy, size, start, v_out); break; + case VCTRS_TYPE_double: dbl_detect_run_bounds_bool(proxy, size, start, v_out); break; + case VCTRS_TYPE_complex: cpl_detect_run_bounds_bool(proxy, size, start, v_out); break; + case VCTRS_TYPE_character: chr_detect_run_bounds_bool(proxy, size, start, v_out); break; + case VCTRS_TYPE_raw: raw_detect_run_bounds_bool(proxy, size, start, v_out); break; + case VCTRS_TYPE_list: list_detect_run_bounds_bool(proxy, size, start, v_out); break; + case VCTRS_TYPE_dataframe: df_detect_run_bounds_bool(proxy, size, start, v_out); break; + default: stop_unimplemented_vctrs_type("vec_detect_run_bounds_bool", type); } FREE(3); @@ -166,72 +166,72 @@ r_obj* vec_detect_run_bounds0(r_obj* x, bool start, struct r_lazy error_call) { // ----------------------------------------------------------------------------- // Algorithm for "ends" is same as "starts", we just iterate in reverse -#define VEC_DETECT_RUN_BOUNDS0(CTYPE, CBEGIN, EQUAL_NA_EQUAL) { \ - if (size == 0) { \ - /* Algorithm requires at least 1 value */ \ - return; \ - } \ - \ - CTYPE const* v_x = CBEGIN(x); \ - \ - if (start) { \ - /* Handle first case */ \ - CTYPE ref = v_x[0]; \ - v_out[0] = true; \ - \ - for (r_ssize i = 1; i < size; ++i) { \ - CTYPE const elt = v_x[i]; \ - v_out[i] = !EQUAL_NA_EQUAL(elt, ref); \ - ref = elt; \ - } \ - } else { \ - /* Handle last case */ \ - CTYPE ref = v_x[size - 1]; \ - v_out[size - 1] = true; \ - \ - for (r_ssize i = size - 2; i >= 0; --i) { \ - CTYPE const elt = v_x[i]; \ - v_out[i] = !EQUAL_NA_EQUAL(elt, ref); \ - ref = elt; \ - } \ - } \ +#define VEC_DETECT_RUN_BOUNDS_BOOL(CTYPE, CBEGIN, EQUAL_NA_EQUAL) { \ + if (size == 0) { \ + /* Algorithm requires at least 1 value */ \ + return; \ + } \ + \ + CTYPE const* v_x = CBEGIN(x); \ + \ + if (start) { \ + /* Handle first case */ \ + CTYPE ref = v_x[0]; \ + v_out[0] = true; \ + \ + for (r_ssize i = 1; i < size; ++i) { \ + CTYPE const elt = v_x[i]; \ + v_out[i] = !EQUAL_NA_EQUAL(elt, ref); \ + ref = elt; \ + } \ + } else { \ + /* Handle last case */ \ + CTYPE ref = v_x[size - 1]; \ + v_out[size - 1] = true; \ + \ + for (r_ssize i = size - 2; i >= 0; --i) { \ + CTYPE const elt = v_x[i]; \ + v_out[i] = !EQUAL_NA_EQUAL(elt, ref); \ + ref = elt; \ + } \ + } \ } static inline -void lgl_detect_run_bounds0(r_obj* x, r_ssize size, bool start, bool* v_out) { - VEC_DETECT_RUN_BOUNDS0(int, r_lgl_cbegin, lgl_equal_na_equal); +void lgl_detect_run_bounds_bool(r_obj* x, r_ssize size, bool start, bool* v_out) { + VEC_DETECT_RUN_BOUNDS_BOOL(int, r_lgl_cbegin, lgl_equal_na_equal); } static inline -void int_detect_run_bounds0(r_obj* x, r_ssize size, bool start, bool* v_out) { - VEC_DETECT_RUN_BOUNDS0(int, r_int_cbegin, int_equal_na_equal); +void int_detect_run_bounds_bool(r_obj* x, r_ssize size, bool start, bool* v_out) { + VEC_DETECT_RUN_BOUNDS_BOOL(int, r_int_cbegin, int_equal_na_equal); } static inline -void dbl_detect_run_bounds0(r_obj* x, r_ssize size, bool start, bool* v_out) { - VEC_DETECT_RUN_BOUNDS0(double, r_dbl_cbegin, dbl_equal_na_equal); +void dbl_detect_run_bounds_bool(r_obj* x, r_ssize size, bool start, bool* v_out) { + VEC_DETECT_RUN_BOUNDS_BOOL(double, r_dbl_cbegin, dbl_equal_na_equal); } static inline -void cpl_detect_run_bounds0(r_obj* x, r_ssize size, bool start, bool* v_out) { - VEC_DETECT_RUN_BOUNDS0(Rcomplex, r_cpl_cbegin, cpl_equal_na_equal); +void cpl_detect_run_bounds_bool(r_obj* x, r_ssize size, bool start, bool* v_out) { + VEC_DETECT_RUN_BOUNDS_BOOL(Rcomplex, r_cpl_cbegin, cpl_equal_na_equal); } static inline -void chr_detect_run_bounds0(r_obj* x, r_ssize size, bool start, bool* v_out) { - VEC_DETECT_RUN_BOUNDS0(r_obj*, r_chr_cbegin, chr_equal_na_equal); +void chr_detect_run_bounds_bool(r_obj* x, r_ssize size, bool start, bool* v_out) { + VEC_DETECT_RUN_BOUNDS_BOOL(r_obj*, r_chr_cbegin, chr_equal_na_equal); } static inline -void raw_detect_run_bounds0(r_obj* x, r_ssize size, bool start, bool* v_out) { - VEC_DETECT_RUN_BOUNDS0(Rbyte, r_raw_cbegin, raw_equal_na_equal); +void raw_detect_run_bounds_bool(r_obj* x, r_ssize size, bool start, bool* v_out) { + VEC_DETECT_RUN_BOUNDS_BOOL(Rbyte, r_raw_cbegin, raw_equal_na_equal); } static inline -void list_detect_run_bounds0(r_obj* x, r_ssize size, bool start, bool* v_out) { - VEC_DETECT_RUN_BOUNDS0(r_obj*, r_list_cbegin, list_equal_na_equal); +void list_detect_run_bounds_bool(r_obj* x, r_ssize size, bool start, bool* v_out) { + VEC_DETECT_RUN_BOUNDS_BOOL(r_obj*, r_list_cbegin, list_equal_na_equal); } -#undef VEC_DETECT_RUN_BOUNDS0 +#undef VEC_DETECT_RUN_BOUNDS_BOOL // ----------------------------------------------------------------------------- static inline -void df_detect_run_bounds0(r_obj* x, r_ssize size, bool start, bool* v_out) { +void df_detect_run_bounds_bool(r_obj* x, r_ssize size, bool start, bool* v_out) { if (size == 0) { // Algorithm requires at least 1 value return; @@ -255,7 +255,7 @@ void df_detect_run_bounds0(r_obj* x, r_ssize size, bool start, bool* v_out) { } for (r_ssize i = 0; i < n_col; ++i) { - col_detect_run_bounds0(v_x[i], size, start, v_out); + col_detect_run_bounds_bool(v_x[i], size, start, v_out); } // Now invert to detect the bounds @@ -265,70 +265,70 @@ void df_detect_run_bounds0(r_obj* x, r_ssize size, bool start, bool* v_out) { } static inline -void col_detect_run_bounds0(r_obj* x, r_ssize size, bool start, bool* v_out) { +void col_detect_run_bounds_bool(r_obj* x, r_ssize size, bool start, bool* v_out) { switch (vec_proxy_typeof(x)) { - case VCTRS_TYPE_logical: lgl_col_detect_run_bounds0(x, size, start, v_out); break; - case VCTRS_TYPE_integer: int_col_detect_run_bounds0(x, size, start, v_out); break; - case VCTRS_TYPE_double: dbl_col_detect_run_bounds0(x, size, start, v_out); break; - case VCTRS_TYPE_complex: cpl_col_detect_run_bounds0(x, size, start, v_out); break; - case VCTRS_TYPE_character: chr_col_detect_run_bounds0(x, size, start, v_out); break; - case VCTRS_TYPE_raw: raw_col_detect_run_bounds0(x, size, start, v_out); break; - case VCTRS_TYPE_list: list_col_detect_run_bounds0(x, size, start, v_out); break; + case VCTRS_TYPE_logical: lgl_col_detect_run_bounds_bool(x, size, start, v_out); break; + case VCTRS_TYPE_integer: int_col_detect_run_bounds_bool(x, size, start, v_out); break; + case VCTRS_TYPE_double: dbl_col_detect_run_bounds_bool(x, size, start, v_out); break; + case VCTRS_TYPE_complex: cpl_col_detect_run_bounds_bool(x, size, start, v_out); break; + case VCTRS_TYPE_character: chr_col_detect_run_bounds_bool(x, size, start, v_out); break; + case VCTRS_TYPE_raw: raw_col_detect_run_bounds_bool(x, size, start, v_out); break; + case VCTRS_TYPE_list: list_col_detect_run_bounds_bool(x, size, start, v_out); break; case VCTRS_TYPE_dataframe: r_stop_internal("Data frame columns should be flattened."); case VCTRS_TYPE_scalar: r_abort("Can't compare scalars."); default: r_abort("Unimplemented type."); } } -#define VEC_COL_DETECT_RUN_BOUNDS0(CTYPE, CBEGIN, EQUAL_NA_EQUAL) { \ - CTYPE const* v_x = CBEGIN(x); \ - \ - if (start) { \ - CTYPE ref = v_x[0]; \ - \ - for (r_ssize i = 1; i < size; ++i) { \ - CTYPE const elt = v_x[i]; \ - v_out[i] = v_out[i] && EQUAL_NA_EQUAL(ref, elt); \ - ref = elt; \ - } \ - } else { \ - CTYPE ref = v_x[size - 1]; \ - \ - for (r_ssize i = size - 2; i >= 0; --i) { \ - CTYPE const elt = v_x[i]; \ - v_out[i] = v_out[i] && EQUAL_NA_EQUAL(ref, elt); \ - ref = elt; \ - } \ - } \ +#define VEC_COL_DETECT_RUN_BOUNDS_BOOL(CTYPE, CBEGIN, EQUAL_NA_EQUAL) { \ + CTYPE const* v_x = CBEGIN(x); \ + \ + if (start) { \ + CTYPE ref = v_x[0]; \ + \ + for (r_ssize i = 1; i < size; ++i) { \ + CTYPE const elt = v_x[i]; \ + v_out[i] = v_out[i] && EQUAL_NA_EQUAL(ref, elt); \ + ref = elt; \ + } \ + } else { \ + CTYPE ref = v_x[size - 1]; \ + \ + for (r_ssize i = size - 2; i >= 0; --i) { \ + CTYPE const elt = v_x[i]; \ + v_out[i] = v_out[i] && EQUAL_NA_EQUAL(ref, elt); \ + ref = elt; \ + } \ + } \ } static inline -void lgl_col_detect_run_bounds0(r_obj* x, r_ssize size, bool start, bool* v_out) { - VEC_COL_DETECT_RUN_BOUNDS0(int, r_lgl_cbegin, lgl_equal_na_equal); +void lgl_col_detect_run_bounds_bool(r_obj* x, r_ssize size, bool start, bool* v_out) { + VEC_COL_DETECT_RUN_BOUNDS_BOOL(int, r_lgl_cbegin, lgl_equal_na_equal); } static inline -void int_col_detect_run_bounds0(r_obj* x, r_ssize size, bool start, bool* v_out) { - VEC_COL_DETECT_RUN_BOUNDS0(int, r_int_cbegin, int_equal_na_equal); +void int_col_detect_run_bounds_bool(r_obj* x, r_ssize size, bool start, bool* v_out) { + VEC_COL_DETECT_RUN_BOUNDS_BOOL(int, r_int_cbegin, int_equal_na_equal); } static inline -void dbl_col_detect_run_bounds0(r_obj* x, r_ssize size, bool start, bool* v_out) { - VEC_COL_DETECT_RUN_BOUNDS0(double, r_dbl_cbegin, dbl_equal_na_equal); +void dbl_col_detect_run_bounds_bool(r_obj* x, r_ssize size, bool start, bool* v_out) { + VEC_COL_DETECT_RUN_BOUNDS_BOOL(double, r_dbl_cbegin, dbl_equal_na_equal); } static inline -void cpl_col_detect_run_bounds0(r_obj* x, r_ssize size, bool start, bool* v_out) { - VEC_COL_DETECT_RUN_BOUNDS0(Rcomplex, r_cpl_cbegin, cpl_equal_na_equal); +void cpl_col_detect_run_bounds_bool(r_obj* x, r_ssize size, bool start, bool* v_out) { + VEC_COL_DETECT_RUN_BOUNDS_BOOL(Rcomplex, r_cpl_cbegin, cpl_equal_na_equal); } static inline -void chr_col_detect_run_bounds0(r_obj* x, r_ssize size, bool start, bool* v_out) { - VEC_COL_DETECT_RUN_BOUNDS0(r_obj*, r_chr_cbegin, chr_equal_na_equal); +void chr_col_detect_run_bounds_bool(r_obj* x, r_ssize size, bool start, bool* v_out) { + VEC_COL_DETECT_RUN_BOUNDS_BOOL(r_obj*, r_chr_cbegin, chr_equal_na_equal); } static inline -void raw_col_detect_run_bounds0(r_obj* x, r_ssize size, bool start, bool* v_out) { - VEC_COL_DETECT_RUN_BOUNDS0(Rbyte, r_raw_cbegin, raw_equal_na_equal); +void raw_col_detect_run_bounds_bool(r_obj* x, r_ssize size, bool start, bool* v_out) { + VEC_COL_DETECT_RUN_BOUNDS_BOOL(Rbyte, r_raw_cbegin, raw_equal_na_equal); } static inline -void list_col_detect_run_bounds0(r_obj* x, r_ssize size, bool start, bool* v_out) { - VEC_COL_DETECT_RUN_BOUNDS0(r_obj*, r_list_cbegin, list_equal_na_equal); +void list_col_detect_run_bounds_bool(r_obj* x, r_ssize size, bool start, bool* v_out) { + VEC_COL_DETECT_RUN_BOUNDS_BOOL(r_obj*, r_list_cbegin, list_equal_na_equal); } -#undef VEC_COL_DETECT_RUN_BOUNDS0 +#undef VEC_COL_DETECT_RUN_BOUNDS_BOOL From 3db1bc7f8c61d86dd1d0719f09aa2ce4523417c5 Mon Sep 17 00:00:00 2001 From: Davis Vaughan Date: Tue, 24 Jan 2023 09:44:44 -0500 Subject: [PATCH 225/312] Use `enum vctrs_run_bound` to clarify code (#1774) --- R/runs.R | 8 +-- src/decl/runs-decl.h | 41 ++++++----- src/runs.c | 129 ++++++++++++++++++++-------------- src/utils.c | 2 + src/utils.h | 1 + tests/testthat/_snaps/runs.md | 32 ++++----- tests/testthat/test-runs.R | 28 ++++---- 7 files changed, 137 insertions(+), 104 deletions(-) diff --git a/R/runs.R b/R/runs.R index 069d74c0f..0b59665a4 100644 --- a/R/runs.R +++ b/R/runs.R @@ -63,10 +63,10 @@ vec_run_sizes <- function(x) { .Call(ffi_vec_run_sizes, x, environment()) } -vec_locate_run_bounds <- function(x, start = TRUE) { - .Call(ffi_vec_locate_run_bounds, x, start, environment()) +vec_locate_run_bounds <- function(x, which = c("start", "end")) { + .Call(ffi_vec_locate_run_bounds, x, which, environment()) } -vec_detect_run_bounds <- function(x, start = TRUE) { - .Call(ffi_vec_detect_run_bounds, x, start, environment()) +vec_detect_run_bounds <- function(x, which = c("start", "end")) { + .Call(ffi_vec_detect_run_bounds, x, which, environment()) } diff --git a/src/decl/runs-decl.h b/src/decl/runs-decl.h index 8abfbfb26..83da0e8d9 100644 --- a/src/decl/runs-decl.h +++ b/src/decl/runs-decl.h @@ -1,41 +1,44 @@ static -r_obj* vec_detect_run_bounds(r_obj* x, bool start, struct r_lazy error_call); +r_obj* vec_detect_run_bounds(r_obj* x, enum vctrs_run_bound which, struct r_lazy error_call); static -r_obj* vec_locate_run_bounds(r_obj* x, bool start, struct r_lazy error_call); +r_obj* vec_locate_run_bounds(r_obj* x, enum vctrs_run_bound which, struct r_lazy error_call); static -r_obj* vec_detect_run_bounds_bool(r_obj* x, bool start, struct r_lazy error_call); +r_obj* vec_detect_run_bounds_bool(r_obj* x, enum vctrs_run_bound which, struct r_lazy error_call); static inline -void lgl_detect_run_bounds_bool(r_obj* x, r_ssize size, bool start, bool* v_out); +void lgl_detect_run_bounds_bool(r_obj* x, r_ssize size, enum vctrs_run_bound which, bool* v_out); static inline -void int_detect_run_bounds_bool(r_obj* x, r_ssize size, bool start, bool* v_out); +void int_detect_run_bounds_bool(r_obj* x, r_ssize size, enum vctrs_run_bound which, bool* v_out); static inline -void dbl_detect_run_bounds_bool(r_obj* x, r_ssize size, bool start, bool* v_out); +void dbl_detect_run_bounds_bool(r_obj* x, r_ssize size, enum vctrs_run_bound which, bool* v_out); static inline -void cpl_detect_run_bounds_bool(r_obj* x, r_ssize size, bool start, bool* v_out); +void cpl_detect_run_bounds_bool(r_obj* x, r_ssize size, enum vctrs_run_bound which, bool* v_out); static inline -void chr_detect_run_bounds_bool(r_obj* x, r_ssize size, bool start, bool* v_out); +void chr_detect_run_bounds_bool(r_obj* x, r_ssize size, enum vctrs_run_bound which, bool* v_out); static inline -void raw_detect_run_bounds_bool(r_obj* x, r_ssize size, bool start, bool* v_out); +void raw_detect_run_bounds_bool(r_obj* x, r_ssize size, enum vctrs_run_bound which, bool* v_out); static inline -void list_detect_run_bounds_bool(r_obj* x, r_ssize size, bool start, bool* v_out); +void list_detect_run_bounds_bool(r_obj* x, r_ssize size, enum vctrs_run_bound which, bool* v_out); static inline -void df_detect_run_bounds_bool(r_obj* x, r_ssize size, bool start, bool* v_out); +void df_detect_run_bounds_bool(r_obj* x, r_ssize size, enum vctrs_run_bound which, bool* v_out); static inline -void col_detect_run_bounds_bool(r_obj* x, r_ssize size, bool start, bool* v_out); +void col_detect_run_bounds_bool(r_obj* x, r_ssize size, enum vctrs_run_bound which, bool* v_out); static inline -void lgl_col_detect_run_bounds_bool(r_obj* x, r_ssize size, bool start, bool* v_out); +void lgl_col_detect_run_bounds_bool(r_obj* x, r_ssize size, enum vctrs_run_bound which, bool* v_out); static inline -void int_col_detect_run_bounds_bool(r_obj* x, r_ssize size, bool start, bool* v_out); +void int_col_detect_run_bounds_bool(r_obj* x, r_ssize size, enum vctrs_run_bound which, bool* v_out); static inline -void dbl_col_detect_run_bounds_bool(r_obj* x, r_ssize size, bool start, bool* v_out); +void dbl_col_detect_run_bounds_bool(r_obj* x, r_ssize size, enum vctrs_run_bound which, bool* v_out); static inline -void cpl_col_detect_run_bounds_bool(r_obj* x, r_ssize size, bool start, bool* v_out); +void cpl_col_detect_run_bounds_bool(r_obj* x, r_ssize size, enum vctrs_run_bound which, bool* v_out); static inline -void chr_col_detect_run_bounds_bool(r_obj* x, r_ssize size, bool start, bool* v_out); +void chr_col_detect_run_bounds_bool(r_obj* x, r_ssize size, enum vctrs_run_bound which, bool* v_out); static inline -void raw_col_detect_run_bounds_bool(r_obj* x, r_ssize size, bool start, bool* v_out); +void raw_col_detect_run_bounds_bool(r_obj* x, r_ssize size, enum vctrs_run_bound which, bool* v_out); static inline -void list_col_detect_run_bounds_bool(r_obj* x, r_ssize size, bool start, bool* v_out); +void list_col_detect_run_bounds_bool(r_obj* x, r_ssize size, enum vctrs_run_bound which, bool* v_out); + +static inline +enum vctrs_run_bound as_run_bound(r_obj* which, struct r_lazy error_call); diff --git a/src/runs.c b/src/runs.c index 01e5599d3..d68fede50 100644 --- a/src/runs.c +++ b/src/runs.c @@ -1,18 +1,23 @@ #include "vctrs.h" +enum vctrs_run_bound { + VCTRS_RUN_BOUND_start = 0, + VCTRS_RUN_BOUND_end = 1 +}; + #include "decl/runs-decl.h" // ----------------------------------------------------------------------------- r_obj* ffi_vec_detect_run_bounds(r_obj* x, r_obj* ffi_start, r_obj* frame) { struct r_lazy error_call = { .x = frame, .env = r_null }; - const bool start = r_arg_as_bool(ffi_start, "start"); - return vec_detect_run_bounds(x, start, error_call); + const enum vctrs_run_bound which = as_run_bound(ffi_start, error_call); + return vec_detect_run_bounds(x, which, error_call); } static -r_obj* vec_detect_run_bounds(r_obj* x, bool start, struct r_lazy error_call) { - r_obj* where = KEEP(vec_detect_run_bounds_bool(x, start, error_call)); +r_obj* vec_detect_run_bounds(r_obj* x, enum vctrs_run_bound which, struct r_lazy error_call) { + r_obj* where = KEEP(vec_detect_run_bounds_bool(x, which, error_call)); const bool* v_where = r_raw_cbegin(where); const r_ssize size = r_length(where) / sizeof(bool); @@ -32,13 +37,13 @@ r_obj* vec_detect_run_bounds(r_obj* x, bool start, struct r_lazy error_call) { r_obj* ffi_vec_locate_run_bounds(r_obj* x, r_obj* ffi_start, r_obj* frame) { struct r_lazy error_call = { .x = frame, .env = r_null }; - const bool start = r_arg_as_bool(ffi_start, "start"); - return vec_locate_run_bounds(x, start, error_call); + const enum vctrs_run_bound which = as_run_bound(ffi_start, error_call); + return vec_locate_run_bounds(x, which, error_call); } static -r_obj* vec_locate_run_bounds(r_obj* x, bool start, struct r_lazy error_call) { - r_obj* where = KEEP(vec_detect_run_bounds_bool(x, start, error_call)); +r_obj* vec_locate_run_bounds(r_obj* x, enum vctrs_run_bound which, struct r_lazy error_call) { + r_obj* where = KEEP(vec_detect_run_bounds_bool(x, which, error_call)); const bool* v_where = r_raw_cbegin(where); const r_ssize size = r_length(where) / sizeof(bool); @@ -68,11 +73,10 @@ r_obj* ffi_vec_identify_runs(r_obj* x, r_obj* frame) { } r_obj* vec_identify_runs(r_obj* x, struct r_lazy error_call) { - const bool start = true; - r_obj* where = KEEP(vec_detect_run_bounds_bool(x, start, error_call)); - const bool* v_where = r_raw_cbegin(where); + r_obj* starts = KEEP(vec_detect_run_bounds_bool(x, VCTRS_RUN_BOUND_start, error_call)); + const bool* v_starts = r_raw_cbegin(starts); - const r_ssize size = r_length(where) / sizeof(bool); + const r_ssize size = r_length(starts) / sizeof(bool); r_obj* out = KEEP(r_alloc_integer(size)); int* v_out = r_int_begin(out); @@ -80,7 +84,7 @@ r_obj* vec_identify_runs(r_obj* x, struct r_lazy error_call) { int n = 0; for (r_ssize i = 0; i < size; ++i) { - n += v_where[i]; + n += v_starts[i]; v_out[i] = n; } @@ -99,8 +103,7 @@ r_obj* ffi_vec_run_sizes(r_obj* x, r_obj* frame) { } r_obj* vec_run_sizes(r_obj* x, struct r_lazy error_call) { - const bool start = false; - r_obj* ends = KEEP(vec_detect_run_bounds_bool(x, start, error_call)); + r_obj* ends = KEEP(vec_detect_run_bounds_bool(x, VCTRS_RUN_BOUND_end, error_call)); const bool* v_ends = r_raw_cbegin(ends); const r_ssize size = r_length(ends) / sizeof(bool); @@ -134,7 +137,7 @@ r_obj* vec_run_sizes(r_obj* x, struct r_lazy error_call) { * boolean array as a raw vector. */ static -r_obj* vec_detect_run_bounds_bool(r_obj* x, bool start, struct r_lazy error_call) { +r_obj* vec_detect_run_bounds_bool(r_obj* x, enum vctrs_run_bound which, struct r_lazy error_call) { vec_check_vector(x, vec_args.x, error_call); r_obj* proxy = KEEP(vec_proxy_equal(x)); @@ -148,14 +151,14 @@ r_obj* vec_detect_run_bounds_bool(r_obj* x, bool start, struct r_lazy error_call const enum vctrs_type type = vec_proxy_typeof(proxy); switch (type) { - case VCTRS_TYPE_logical: lgl_detect_run_bounds_bool(proxy, size, start, v_out); break; - case VCTRS_TYPE_integer: int_detect_run_bounds_bool(proxy, size, start, v_out); break; - case VCTRS_TYPE_double: dbl_detect_run_bounds_bool(proxy, size, start, v_out); break; - case VCTRS_TYPE_complex: cpl_detect_run_bounds_bool(proxy, size, start, v_out); break; - case VCTRS_TYPE_character: chr_detect_run_bounds_bool(proxy, size, start, v_out); break; - case VCTRS_TYPE_raw: raw_detect_run_bounds_bool(proxy, size, start, v_out); break; - case VCTRS_TYPE_list: list_detect_run_bounds_bool(proxy, size, start, v_out); break; - case VCTRS_TYPE_dataframe: df_detect_run_bounds_bool(proxy, size, start, v_out); break; + case VCTRS_TYPE_logical: lgl_detect_run_bounds_bool(proxy, size, which, v_out); break; + case VCTRS_TYPE_integer: int_detect_run_bounds_bool(proxy, size, which, v_out); break; + case VCTRS_TYPE_double: dbl_detect_run_bounds_bool(proxy, size, which, v_out); break; + case VCTRS_TYPE_complex: cpl_detect_run_bounds_bool(proxy, size, which, v_out); break; + case VCTRS_TYPE_character: chr_detect_run_bounds_bool(proxy, size, which, v_out); break; + case VCTRS_TYPE_raw: raw_detect_run_bounds_bool(proxy, size, which, v_out); break; + case VCTRS_TYPE_list: list_detect_run_bounds_bool(proxy, size, which, v_out); break; + case VCTRS_TYPE_dataframe: df_detect_run_bounds_bool(proxy, size, which, v_out); break; default: stop_unimplemented_vctrs_type("vec_detect_run_bounds_bool", type); } @@ -174,7 +177,7 @@ r_obj* vec_detect_run_bounds_bool(r_obj* x, bool start, struct r_lazy error_call \ CTYPE const* v_x = CBEGIN(x); \ \ - if (start) { \ + if (which == VCTRS_RUN_BOUND_start) { \ /* Handle first case */ \ CTYPE ref = v_x[0]; \ v_out[0] = true; \ @@ -198,31 +201,31 @@ r_obj* vec_detect_run_bounds_bool(r_obj* x, bool start, struct r_lazy error_call } static inline -void lgl_detect_run_bounds_bool(r_obj* x, r_ssize size, bool start, bool* v_out) { +void lgl_detect_run_bounds_bool(r_obj* x, r_ssize size, enum vctrs_run_bound which, bool* v_out) { VEC_DETECT_RUN_BOUNDS_BOOL(int, r_lgl_cbegin, lgl_equal_na_equal); } static inline -void int_detect_run_bounds_bool(r_obj* x, r_ssize size, bool start, bool* v_out) { +void int_detect_run_bounds_bool(r_obj* x, r_ssize size, enum vctrs_run_bound which, bool* v_out) { VEC_DETECT_RUN_BOUNDS_BOOL(int, r_int_cbegin, int_equal_na_equal); } static inline -void dbl_detect_run_bounds_bool(r_obj* x, r_ssize size, bool start, bool* v_out) { +void dbl_detect_run_bounds_bool(r_obj* x, r_ssize size, enum vctrs_run_bound which, bool* v_out) { VEC_DETECT_RUN_BOUNDS_BOOL(double, r_dbl_cbegin, dbl_equal_na_equal); } static inline -void cpl_detect_run_bounds_bool(r_obj* x, r_ssize size, bool start, bool* v_out) { +void cpl_detect_run_bounds_bool(r_obj* x, r_ssize size, enum vctrs_run_bound which, bool* v_out) { VEC_DETECT_RUN_BOUNDS_BOOL(Rcomplex, r_cpl_cbegin, cpl_equal_na_equal); } static inline -void chr_detect_run_bounds_bool(r_obj* x, r_ssize size, bool start, bool* v_out) { +void chr_detect_run_bounds_bool(r_obj* x, r_ssize size, enum vctrs_run_bound which, bool* v_out) { VEC_DETECT_RUN_BOUNDS_BOOL(r_obj*, r_chr_cbegin, chr_equal_na_equal); } static inline -void raw_detect_run_bounds_bool(r_obj* x, r_ssize size, bool start, bool* v_out) { +void raw_detect_run_bounds_bool(r_obj* x, r_ssize size, enum vctrs_run_bound which, bool* v_out) { VEC_DETECT_RUN_BOUNDS_BOOL(Rbyte, r_raw_cbegin, raw_equal_na_equal); } static inline -void list_detect_run_bounds_bool(r_obj* x, r_ssize size, bool start, bool* v_out) { +void list_detect_run_bounds_bool(r_obj* x, r_ssize size, enum vctrs_run_bound which, bool* v_out) { VEC_DETECT_RUN_BOUNDS_BOOL(r_obj*, r_list_cbegin, list_equal_na_equal); } @@ -231,7 +234,7 @@ void list_detect_run_bounds_bool(r_obj* x, r_ssize size, bool start, bool* v_out // ----------------------------------------------------------------------------- static inline -void df_detect_run_bounds_bool(r_obj* x, r_ssize size, bool start, bool* v_out) { +void df_detect_run_bounds_bool(r_obj* x, r_ssize size, enum vctrs_run_bound which, bool* v_out) { if (size == 0) { // Algorithm requires at least 1 value return; @@ -242,7 +245,7 @@ void df_detect_run_bounds_bool(r_obj* x, r_ssize size, bool start, bool* v_out) // `v_out` will eventually be `true` if we are in a run // continuation, and `false` if we are starting a new run. - if (start) { + if (which == VCTRS_RUN_BOUND_start) { v_out[0] = false; for (r_ssize i = 1; i < size; ++i) { v_out[i] = true; @@ -255,7 +258,7 @@ void df_detect_run_bounds_bool(r_obj* x, r_ssize size, bool start, bool* v_out) } for (r_ssize i = 0; i < n_col; ++i) { - col_detect_run_bounds_bool(v_x[i], size, start, v_out); + col_detect_run_bounds_bool(v_x[i], size, which, v_out); } // Now invert to detect the bounds @@ -265,15 +268,15 @@ void df_detect_run_bounds_bool(r_obj* x, r_ssize size, bool start, bool* v_out) } static inline -void col_detect_run_bounds_bool(r_obj* x, r_ssize size, bool start, bool* v_out) { +void col_detect_run_bounds_bool(r_obj* x, r_ssize size, enum vctrs_run_bound which, bool* v_out) { switch (vec_proxy_typeof(x)) { - case VCTRS_TYPE_logical: lgl_col_detect_run_bounds_bool(x, size, start, v_out); break; - case VCTRS_TYPE_integer: int_col_detect_run_bounds_bool(x, size, start, v_out); break; - case VCTRS_TYPE_double: dbl_col_detect_run_bounds_bool(x, size, start, v_out); break; - case VCTRS_TYPE_complex: cpl_col_detect_run_bounds_bool(x, size, start, v_out); break; - case VCTRS_TYPE_character: chr_col_detect_run_bounds_bool(x, size, start, v_out); break; - case VCTRS_TYPE_raw: raw_col_detect_run_bounds_bool(x, size, start, v_out); break; - case VCTRS_TYPE_list: list_col_detect_run_bounds_bool(x, size, start, v_out); break; + case VCTRS_TYPE_logical: lgl_col_detect_run_bounds_bool(x, size, which, v_out); break; + case VCTRS_TYPE_integer: int_col_detect_run_bounds_bool(x, size, which, v_out); break; + case VCTRS_TYPE_double: dbl_col_detect_run_bounds_bool(x, size, which, v_out); break; + case VCTRS_TYPE_complex: cpl_col_detect_run_bounds_bool(x, size, which, v_out); break; + case VCTRS_TYPE_character: chr_col_detect_run_bounds_bool(x, size, which, v_out); break; + case VCTRS_TYPE_raw: raw_col_detect_run_bounds_bool(x, size, which, v_out); break; + case VCTRS_TYPE_list: list_col_detect_run_bounds_bool(x, size, which, v_out); break; case VCTRS_TYPE_dataframe: r_stop_internal("Data frame columns should be flattened."); case VCTRS_TYPE_scalar: r_abort("Can't compare scalars."); default: r_abort("Unimplemented type."); @@ -283,7 +286,7 @@ void col_detect_run_bounds_bool(r_obj* x, r_ssize size, bool start, bool* v_out) #define VEC_COL_DETECT_RUN_BOUNDS_BOOL(CTYPE, CBEGIN, EQUAL_NA_EQUAL) { \ CTYPE const* v_x = CBEGIN(x); \ \ - if (start) { \ + if (which == VCTRS_RUN_BOUND_start) { \ CTYPE ref = v_x[0]; \ \ for (r_ssize i = 1; i < size; ++i) { \ @@ -303,32 +306,56 @@ void col_detect_run_bounds_bool(r_obj* x, r_ssize size, bool start, bool* v_out) } static inline -void lgl_col_detect_run_bounds_bool(r_obj* x, r_ssize size, bool start, bool* v_out) { +void lgl_col_detect_run_bounds_bool(r_obj* x, r_ssize size, enum vctrs_run_bound which, bool* v_out) { VEC_COL_DETECT_RUN_BOUNDS_BOOL(int, r_lgl_cbegin, lgl_equal_na_equal); } static inline -void int_col_detect_run_bounds_bool(r_obj* x, r_ssize size, bool start, bool* v_out) { +void int_col_detect_run_bounds_bool(r_obj* x, r_ssize size, enum vctrs_run_bound which, bool* v_out) { VEC_COL_DETECT_RUN_BOUNDS_BOOL(int, r_int_cbegin, int_equal_na_equal); } static inline -void dbl_col_detect_run_bounds_bool(r_obj* x, r_ssize size, bool start, bool* v_out) { +void dbl_col_detect_run_bounds_bool(r_obj* x, r_ssize size, enum vctrs_run_bound which, bool* v_out) { VEC_COL_DETECT_RUN_BOUNDS_BOOL(double, r_dbl_cbegin, dbl_equal_na_equal); } static inline -void cpl_col_detect_run_bounds_bool(r_obj* x, r_ssize size, bool start, bool* v_out) { +void cpl_col_detect_run_bounds_bool(r_obj* x, r_ssize size, enum vctrs_run_bound which, bool* v_out) { VEC_COL_DETECT_RUN_BOUNDS_BOOL(Rcomplex, r_cpl_cbegin, cpl_equal_na_equal); } static inline -void chr_col_detect_run_bounds_bool(r_obj* x, r_ssize size, bool start, bool* v_out) { +void chr_col_detect_run_bounds_bool(r_obj* x, r_ssize size, enum vctrs_run_bound which, bool* v_out) { VEC_COL_DETECT_RUN_BOUNDS_BOOL(r_obj*, r_chr_cbegin, chr_equal_na_equal); } static inline -void raw_col_detect_run_bounds_bool(r_obj* x, r_ssize size, bool start, bool* v_out) { +void raw_col_detect_run_bounds_bool(r_obj* x, r_ssize size, enum vctrs_run_bound which, bool* v_out) { VEC_COL_DETECT_RUN_BOUNDS_BOOL(Rbyte, r_raw_cbegin, raw_equal_na_equal); } static inline -void list_col_detect_run_bounds_bool(r_obj* x, r_ssize size, bool start, bool* v_out) { +void list_col_detect_run_bounds_bool(r_obj* x, r_ssize size, enum vctrs_run_bound which, bool* v_out) { VEC_COL_DETECT_RUN_BOUNDS_BOOL(r_obj*, r_list_cbegin, list_equal_na_equal); } #undef VEC_COL_DETECT_RUN_BOUNDS_BOOL + +// ----------------------------------------------------------------------------- + +static inline +enum vctrs_run_bound as_run_bound(r_obj* which, struct r_lazy error_call) { + struct r_lazy error_arg = { .x = chrs_which, .env = r_null }; + + r_obj* values = KEEP(r_alloc_character(2)); + r_chr_poke(values, 0, r_str("start")); + r_chr_poke(values, 1, r_str("end")); + + const int match = r_arg_match(which, values, error_arg, error_call); + + enum vctrs_run_bound out; + + switch (match) { + case 0: out = VCTRS_RUN_BOUND_start; break; + case 1: out = VCTRS_RUN_BOUND_end; break; + default: r_stop_internal("Unknown `which` value."); + } + + FREE(1); + return out; +} diff --git a/src/utils.c b/src/utils.c index 74e98beff..97ec8dcb1 100644 --- a/src/utils.c +++ b/src/utils.c @@ -1551,6 +1551,7 @@ SEXP chrs_asc = NULL; SEXP chrs_desc = NULL; SEXP chrs_largest = NULL; SEXP chrs_smallest = NULL; +SEXP chrs_which = NULL; SEXP syms_i = NULL; SEXP syms_n = NULL; @@ -1793,6 +1794,7 @@ void vctrs_init_utils(SEXP ns) { chrs_desc = r_new_shared_character("desc"); chrs_largest = r_new_shared_character("largest"); chrs_smallest = r_new_shared_character("smallest"); + chrs_which = r_new_shared_character("which"); classes_tibble = r_new_shared_vector(STRSXP, 3); diff --git a/src/utils.h b/src/utils.h index e1943fc51..f195d328a 100644 --- a/src/utils.h +++ b/src/utils.h @@ -445,6 +445,7 @@ extern SEXP chrs_asc; extern SEXP chrs_desc; extern SEXP chrs_largest; extern SEXP chrs_smallest; +extern SEXP chrs_which; extern SEXP syms_i; extern SEXP syms_n; diff --git a/tests/testthat/_snaps/runs.md b/tests/testthat/_snaps/runs.md index b7d3d6c75..fe5f3a976 100644 --- a/tests/testthat/_snaps/runs.md +++ b/tests/testthat/_snaps/runs.md @@ -14,51 +14,51 @@ Error in `vec_run_sizes()`: ! `x` must be a vector, not a object. -# vec_locate_run_bounds() validates `start` +# vec_locate_run_bounds() validates `which` Code - vec_locate_run_bounds(1, start = "x") + vec_locate_run_bounds(1, which = "x") Condition Error in `vec_locate_run_bounds()`: - ! `start` must be `TRUE` or `FALSE`. + ! `which` must be one of "start" or "end", not "x". --- Code - vec_locate_run_bounds(1, start = NA) + vec_locate_run_bounds(1, which = 1) Condition Error in `vec_locate_run_bounds()`: - ! `start` must be `TRUE` or `FALSE`. + ! `which` must be a string or character vector. --- Code - vec_locate_run_bounds(1, start = c(TRUE, TRUE)) + vec_locate_run_bounds(1, which = c("foo", "bar")) Condition - Error in `vec_locate_run_bounds()`: - ! `start` must be `TRUE` or `FALSE`. + Error in `arg_match()`: + ! `arg` must be length 1 or a permutation of `values`. -# vec_detect_run_bounds() validates `start` +# vec_detect_run_bounds() validates `which` Code - vec_detect_run_bounds(1, start = "x") + vec_detect_run_bounds(1, which = "x") Condition Error in `vec_detect_run_bounds()`: - ! `start` must be `TRUE` or `FALSE`. + ! `which` must be one of "start" or "end", not "x". --- Code - vec_detect_run_bounds(1, start = NA) + vec_detect_run_bounds(1, which = 1) Condition Error in `vec_detect_run_bounds()`: - ! `start` must be `TRUE` or `FALSE`. + ! `which` must be a string or character vector. --- Code - vec_detect_run_bounds(1, start = c(TRUE, TRUE)) + vec_detect_run_bounds(1, which = c("foo", "bar")) Condition - Error in `vec_detect_run_bounds()`: - ! `start` must be `TRUE` or `FALSE`. + Error in `arg_match()`: + ! `arg` must be length 1 or a permutation of `values`. diff --git a/tests/testthat/test-runs.R b/tests/testthat/test-runs.R index 8aa9d3b54..a917da57d 100644 --- a/tests/testthat/test-runs.R +++ b/tests/testthat/test-runs.R @@ -182,25 +182,25 @@ test_that("can locate run starts", { test_that("can locate run ends", { expect_identical( - vec_locate_run_bounds(c(1, 3, 3, 1, 5, 5, 6), start = FALSE), + vec_locate_run_bounds(c(1, 3, 3, 1, 5, 5, 6), which = "end"), c(1L, 3L, 4L, 6L, 7L) ) }) test_that("vec_locate_run_bounds() works with size zero input", { - expect_identical(vec_locate_run_bounds(integer(), start = TRUE), integer()) - expect_identical(vec_locate_run_bounds(integer(), start = FALSE), integer()) + expect_identical(vec_locate_run_bounds(integer(), which = "start"), integer()) + expect_identical(vec_locate_run_bounds(integer(), which = "end"), integer()) }) -test_that("vec_locate_run_bounds() validates `start`", { +test_that("vec_locate_run_bounds() validates `which`", { expect_snapshot(error = TRUE, { - vec_locate_run_bounds(1, start = "x") + vec_locate_run_bounds(1, which = "x") }) expect_snapshot(error = TRUE, { - vec_locate_run_bounds(1, start = NA) + vec_locate_run_bounds(1, which = 1) }) expect_snapshot(error = TRUE, { - vec_locate_run_bounds(1, start = c(TRUE, TRUE)) + vec_locate_run_bounds(1, which = c("foo", "bar")) }) }) @@ -215,24 +215,24 @@ test_that("can detect run starts", { test_that("can detect run ends", { expect_identical( - vec_detect_run_bounds(c(1, 3, 3, 1, 5, 5, 6), start = FALSE), + vec_detect_run_bounds(c(1, 3, 3, 1, 5, 5, 6), which = "end"), c(TRUE, FALSE, TRUE, TRUE, FALSE, TRUE, TRUE) ) }) test_that("vec_detect_run_bounds() works with size zero input", { - expect_identical(vec_detect_run_bounds(integer(), start = TRUE), logical()) - expect_identical(vec_detect_run_bounds(integer(), start = FALSE), logical()) + expect_identical(vec_detect_run_bounds(integer(), which = "start"), logical()) + expect_identical(vec_detect_run_bounds(integer(), which = "end"), logical()) }) -test_that("vec_detect_run_bounds() validates `start`", { +test_that("vec_detect_run_bounds() validates `which`", { expect_snapshot(error = TRUE, { - vec_detect_run_bounds(1, start = "x") + vec_detect_run_bounds(1, which = "x") }) expect_snapshot(error = TRUE, { - vec_detect_run_bounds(1, start = NA) + vec_detect_run_bounds(1, which = 1) }) expect_snapshot(error = TRUE, { - vec_detect_run_bounds(1, start = c(TRUE, TRUE)) + vec_detect_run_bounds(1, which = c("foo", "bar")) }) }) From 630873de4b6f4d5b4b872dbf427d2cdc565c7950 Mon Sep 17 00:00:00 2001 From: Davis Vaughan Date: Tue, 24 Jan 2023 11:15:45 -0500 Subject: [PATCH 226/312] Collapse start/end loops into a single loop (#1775) --- src/decl/runs-decl.h | 5 +++ src/runs.c | 102 ++++++++++++++++++++++++------------------- 2 files changed, 62 insertions(+), 45 deletions(-) diff --git a/src/decl/runs-decl.h b/src/decl/runs-decl.h index 83da0e8d9..d3f2eb675 100644 --- a/src/decl/runs-decl.h +++ b/src/decl/runs-decl.h @@ -40,5 +40,10 @@ void raw_col_detect_run_bounds_bool(r_obj* x, r_ssize size, enum vctrs_run_bound static inline void list_col_detect_run_bounds_bool(r_obj* x, r_ssize size, enum vctrs_run_bound which, bool* v_out); +static inline +r_ssize compute_iter_loc(r_ssize size, enum vctrs_run_bound which); +static inline +r_ssize compute_iter_step(enum vctrs_run_bound which); + static inline enum vctrs_run_bound as_run_bound(r_obj* which, struct r_lazy error_call); diff --git a/src/runs.c b/src/runs.c index d68fede50..758083d42 100644 --- a/src/runs.c +++ b/src/runs.c @@ -55,10 +55,17 @@ r_obj* vec_locate_run_bounds(r_obj* x, enum vctrs_run_bound which, struct r_lazy r_obj* out = KEEP(r_alloc_integer(n)); int* v_out = r_int_begin(out); + r_ssize j = compute_iter_loc(n, which); - for (r_ssize i = 0, j = 0; i < size && j < n; ++i) { - v_out[j] = i + 1; - j += v_where[i]; + r_ssize loc = compute_iter_loc(size, which); + const r_ssize step = compute_iter_step(which); + + // First/last value are always the final bound locations + // (depending on `which`), so `j` won't ever write to OOB locations + for (r_ssize i = 0; i < size; ++i) { + v_out[j] = loc + 1; + j += step * v_where[loc]; + loc += step; } FREE(2); @@ -177,26 +184,19 @@ r_obj* vec_detect_run_bounds_bool(r_obj* x, enum vctrs_run_bound which, struct r \ CTYPE const* v_x = CBEGIN(x); \ \ - if (which == VCTRS_RUN_BOUND_start) { \ - /* Handle first case */ \ - CTYPE ref = v_x[0]; \ - v_out[0] = true; \ + r_ssize loc = compute_iter_loc(size, which); \ + const r_ssize step = compute_iter_step(which); \ \ - for (r_ssize i = 1; i < size; ++i) { \ - CTYPE const elt = v_x[i]; \ - v_out[i] = !EQUAL_NA_EQUAL(elt, ref); \ - ref = elt; \ - } \ - } else { \ - /* Handle last case */ \ - CTYPE ref = v_x[size - 1]; \ - v_out[size - 1] = true; \ + /* Handle first/last value */ \ + CTYPE ref = v_x[loc]; \ + v_out[loc] = true; \ + loc += step; \ \ - for (r_ssize i = size - 2; i >= 0; --i) { \ - CTYPE const elt = v_x[i]; \ - v_out[i] = !EQUAL_NA_EQUAL(elt, ref); \ - ref = elt; \ - } \ + for (r_ssize i = 1; i < size; ++i) { \ + CTYPE const elt = v_x[loc]; \ + v_out[loc] = !EQUAL_NA_EQUAL(elt, ref); \ + ref = elt; \ + loc += step; \ } \ } @@ -243,18 +243,17 @@ void df_detect_run_bounds_bool(r_obj* x, r_ssize size, enum vctrs_run_bound whic const r_ssize n_col = r_length(x); r_obj* const* v_x = r_list_cbegin(x); + r_ssize loc = compute_iter_loc(size, which); + const r_ssize step = compute_iter_step(which); + // `v_out` will eventually be `true` if we are in a run // continuation, and `false` if we are starting a new run. - if (which == VCTRS_RUN_BOUND_start) { - v_out[0] = false; - for (r_ssize i = 1; i < size; ++i) { - v_out[i] = true; - } - } else { - v_out[size - 1] = false; - for (r_ssize i = size - 2; i >= 0; --i) { - v_out[i] = true; - } + v_out[loc] = false; + loc += step; + + for (r_ssize i = 1; i < size; ++i) { + v_out[loc] = true; + loc += step; } for (r_ssize i = 0; i < n_col; ++i) { @@ -286,22 +285,17 @@ void col_detect_run_bounds_bool(r_obj* x, r_ssize size, enum vctrs_run_bound whi #define VEC_COL_DETECT_RUN_BOUNDS_BOOL(CTYPE, CBEGIN, EQUAL_NA_EQUAL) { \ CTYPE const* v_x = CBEGIN(x); \ \ - if (which == VCTRS_RUN_BOUND_start) { \ - CTYPE ref = v_x[0]; \ + r_ssize loc = compute_iter_loc(size, which); \ + const r_ssize step = compute_iter_step(which); \ \ - for (r_ssize i = 1; i < size; ++i) { \ - CTYPE const elt = v_x[i]; \ - v_out[i] = v_out[i] && EQUAL_NA_EQUAL(ref, elt); \ - ref = elt; \ - } \ - } else { \ - CTYPE ref = v_x[size - 1]; \ + CTYPE ref = v_x[loc]; \ + loc += step; \ \ - for (r_ssize i = size - 2; i >= 0; --i) { \ - CTYPE const elt = v_x[i]; \ - v_out[i] = v_out[i] && EQUAL_NA_EQUAL(ref, elt); \ - ref = elt; \ - } \ + for (r_ssize i = 1; i < size; ++i) { \ + CTYPE const elt = v_x[loc]; \ + v_out[loc] = v_out[loc] && EQUAL_NA_EQUAL(ref, elt); \ + ref = elt; \ + loc += step; \ } \ } @@ -338,6 +332,24 @@ void list_col_detect_run_bounds_bool(r_obj* x, r_ssize size, enum vctrs_run_boun // ----------------------------------------------------------------------------- +static inline +r_ssize compute_iter_loc(r_ssize size, enum vctrs_run_bound which) { + switch (which) { + case VCTRS_RUN_BOUND_start: return 0; + case VCTRS_RUN_BOUND_end: return size - 1; + default: r_stop_internal("Unknown `which` value."); + } +} + +static inline +r_ssize compute_iter_step(enum vctrs_run_bound which) { + switch (which) { + case VCTRS_RUN_BOUND_start: return 1; + case VCTRS_RUN_BOUND_end: return -1; + default: r_stop_internal("Unknown `which` value."); + } +} + static inline enum vctrs_run_bound as_run_bound(r_obj* which, struct r_lazy error_call) { struct r_lazy error_arg = { .x = chrs_which, .env = r_null }; From af3fcc486664e30b588df1296a212e583ef00d18 Mon Sep 17 00:00:00 2001 From: Davis Vaughan Date: Wed, 25 Jan 2023 10:53:50 -0500 Subject: [PATCH 227/312] Introduce `struct r_bool_vector` and use in runs helpers (#1776) * Introduce `struct r_bool_vector` and use in runs helpers * `r_bool_vector` -> `r_vector_bool` --- src/decl/runs-decl.h | 4 +++- src/runs.c | 42 ++++++++++++++++++++++--------------- src/vec-bool.h | 49 ++++++++++++++++++++++++++++++++++++++++++++ 3 files changed, 77 insertions(+), 18 deletions(-) create mode 100644 src/vec-bool.h diff --git a/src/decl/runs-decl.h b/src/decl/runs-decl.h index d3f2eb675..42d20fe08 100644 --- a/src/decl/runs-decl.h +++ b/src/decl/runs-decl.h @@ -4,7 +4,9 @@ static r_obj* vec_locate_run_bounds(r_obj* x, enum vctrs_run_bound which, struct r_lazy error_call); static -r_obj* vec_detect_run_bounds_bool(r_obj* x, enum vctrs_run_bound which, struct r_lazy error_call); +struct r_vector_bool* vec_detect_run_bounds_bool(r_obj* x, + enum vctrs_run_bound which, + struct r_lazy error_call); static inline void lgl_detect_run_bounds_bool(r_obj* x, r_ssize size, enum vctrs_run_bound which, bool* v_out); diff --git a/src/runs.c b/src/runs.c index 758083d42..7f4326d39 100644 --- a/src/runs.c +++ b/src/runs.c @@ -1,4 +1,5 @@ #include "vctrs.h" +#include "vec-bool.h" enum vctrs_run_bound { VCTRS_RUN_BOUND_start = 0, @@ -17,10 +18,11 @@ r_obj* ffi_vec_detect_run_bounds(r_obj* x, r_obj* ffi_start, r_obj* frame) { static r_obj* vec_detect_run_bounds(r_obj* x, enum vctrs_run_bound which, struct r_lazy error_call) { - r_obj* where = KEEP(vec_detect_run_bounds_bool(x, which, error_call)); - const bool* v_where = r_raw_cbegin(where); + struct r_vector_bool* p_where = vec_detect_run_bounds_bool(x, which, error_call); + KEEP(p_where->shelter); + const bool* v_where = r_vector_bool_cbegin(p_where); - const r_ssize size = r_length(where) / sizeof(bool); + const r_ssize size = r_vector_bool_length(p_where); r_obj* out = KEEP(r_alloc_logical(size)); int* v_out = r_lgl_begin(out); @@ -43,10 +45,11 @@ r_obj* ffi_vec_locate_run_bounds(r_obj* x, r_obj* ffi_start, r_obj* frame) { static r_obj* vec_locate_run_bounds(r_obj* x, enum vctrs_run_bound which, struct r_lazy error_call) { - r_obj* where = KEEP(vec_detect_run_bounds_bool(x, which, error_call)); - const bool* v_where = r_raw_cbegin(where); + struct r_vector_bool* p_where = vec_detect_run_bounds_bool(x, which, error_call); + KEEP(p_where->shelter); + const bool* v_where = r_vector_bool_cbegin(p_where); - const r_ssize size = r_length(where) / sizeof(bool); + const r_ssize size = r_vector_bool_length(p_where); r_ssize n = 0; for (r_ssize i = 0; i < size; ++i) { @@ -80,10 +83,11 @@ r_obj* ffi_vec_identify_runs(r_obj* x, r_obj* frame) { } r_obj* vec_identify_runs(r_obj* x, struct r_lazy error_call) { - r_obj* starts = KEEP(vec_detect_run_bounds_bool(x, VCTRS_RUN_BOUND_start, error_call)); - const bool* v_starts = r_raw_cbegin(starts); + struct r_vector_bool* p_starts = vec_detect_run_bounds_bool(x, VCTRS_RUN_BOUND_start, error_call); + KEEP(p_starts->shelter); + const bool* v_starts = r_vector_bool_cbegin(p_starts); - const r_ssize size = r_length(starts) / sizeof(bool); + const r_ssize size = r_vector_bool_length(p_starts); r_obj* out = KEEP(r_alloc_integer(size)); int* v_out = r_int_begin(out); @@ -110,10 +114,11 @@ r_obj* ffi_vec_run_sizes(r_obj* x, r_obj* frame) { } r_obj* vec_run_sizes(r_obj* x, struct r_lazy error_call) { - r_obj* ends = KEEP(vec_detect_run_bounds_bool(x, VCTRS_RUN_BOUND_end, error_call)); - const bool* v_ends = r_raw_cbegin(ends); + struct r_vector_bool* p_ends = vec_detect_run_bounds_bool(x, VCTRS_RUN_BOUND_end, error_call); + KEEP(p_ends->shelter); + const bool* v_ends = r_vector_bool_cbegin(p_ends); - const r_ssize size = r_length(ends) / sizeof(bool); + const r_ssize size = r_vector_bool_length(p_ends); r_ssize n = 0; for (r_ssize i = 0; i < size; ++i) { @@ -141,10 +146,12 @@ r_obj* vec_run_sizes(r_obj* x, struct r_lazy error_call) { /* * Like `vec_detect_run_bounds()`, but returns a less memory intensive - * boolean array as a raw vector. + * boolean array as an `r_vector_bool`. */ static -r_obj* vec_detect_run_bounds_bool(r_obj* x, enum vctrs_run_bound which, struct r_lazy error_call) { +struct r_vector_bool* vec_detect_run_bounds_bool(r_obj* x, + enum vctrs_run_bound which, + struct r_lazy error_call) { vec_check_vector(x, vec_args.x, error_call); r_obj* proxy = KEEP(vec_proxy_equal(x)); @@ -152,8 +159,9 @@ r_obj* vec_detect_run_bounds_bool(r_obj* x, enum vctrs_run_bound which, struct r const r_ssize size = vec_size(proxy); - r_obj* out = KEEP(r_alloc_raw(size * sizeof(bool))); - bool* v_out = r_raw_begin(out); + struct r_vector_bool* p_out = r_new_vector_bool(size); + KEEP(p_out->shelter); + bool* v_out = r_vector_bool_begin(p_out); const enum vctrs_type type = vec_proxy_typeof(proxy); @@ -170,7 +178,7 @@ r_obj* vec_detect_run_bounds_bool(r_obj* x, enum vctrs_run_bound which, struct r } FREE(3); - return out; + return p_out; } // ----------------------------------------------------------------------------- diff --git a/src/vec-bool.h b/src/vec-bool.h new file mode 100644 index 000000000..19a2a4c34 --- /dev/null +++ b/src/vec-bool.h @@ -0,0 +1,49 @@ +#ifndef VCTRS_VEC_BOOL_H +#define VCTRS_VEC_BOOL_H + +#include + +struct r_vector_bool { + r_obj* shelter; + + r_obj* data; + bool* v_data; + + r_ssize n; +}; + +static inline +struct r_vector_bool* r_new_vector_bool(r_ssize n) { + r_obj* shelter = KEEP(r_alloc_list(2)); + + r_obj* vec = r_alloc_raw(sizeof(struct r_vector_bool)); + r_list_poke(shelter, 0, vec); + + r_obj* data = r_alloc_raw(n * sizeof(bool)); + r_list_poke(shelter, 1, data); + + struct r_vector_bool* p_vec = r_raw_begin(vec); + p_vec->shelter = shelter; + p_vec->data = data; + p_vec->v_data = r_raw_begin(data); + p_vec->n = n; + + FREE(1); + return p_vec; +} + +static inline +bool* r_vector_bool_begin(struct r_vector_bool* p_vec) { + return p_vec->v_data; +} +static inline +const bool* r_vector_bool_cbegin(struct r_vector_bool* p_vec) { + return (const bool*) p_vec->v_data; +} + +static inline +r_ssize r_vector_bool_length(struct r_vector_bool* p_vec) { + return p_vec->n; +} + +#endif From 793d028250824ce907970135105c461c66b7dd25 Mon Sep 17 00:00:00 2001 From: Davis Vaughan Date: Wed, 8 Feb 2023 11:36:08 -0500 Subject: [PATCH 228/312] Implement a `numeric_version` equality proxy (#1782) * Implement a `numeric_version` equality proxy * NEWS bullet * Add a comparison test with max components --- NAMESPACE | 1 + NEWS.md | 3 + R/type-misc.R | 87 ++++++++++++++++++- tests/testthat/_snaps/type-misc.md | 8 ++ tests/testthat/test-type-misc.R | 134 +++++++++++++++++++++++++++++ 5 files changed, 232 insertions(+), 1 deletion(-) diff --git a/NAMESPACE b/NAMESPACE index 9c27255af..8c5daf81f 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -314,6 +314,7 @@ S3method(vec_proxy_equal,POSIXlt) S3method(vec_proxy_equal,array) S3method(vec_proxy_equal,default) S3method(vec_proxy_equal,integer64) +S3method(vec_proxy_equal,numeric_version) S3method(vec_proxy_order,AsIs) S3method(vec_proxy_order,array) S3method(vec_proxy_order,default) diff --git a/NEWS.md b/NEWS.md index 152f35dd7..177f451f8 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,5 +1,8 @@ # vctrs (development version) +* The `numeric_version` type from base R is now better supported in equality, + comparison, and order based operations (tidyverse/dplyr#6680). + * New `vec_run_sizes()` for computing the size of each run within a vector. It is identical to the `times` column from `vec_unrep()`, but is faster if you don't need the run key (#1210). diff --git a/R/type-misc.R b/R/type-misc.R index 506e6e303..56399d690 100644 --- a/R/type-misc.R +++ b/R/type-misc.R @@ -2,8 +2,93 @@ # `numeric_version` from base ---------------------------------------- #' @export -vec_proxy.numeric_version <- function(x, ...) x +vec_proxy.numeric_version <- function(x, ...) { + x +} + +#' @export +vec_proxy_equal.numeric_version <- function(x, ...) { + proxy_equal_numeric_version(x) +} + +# To generate data agnostic proxies of ``, we enforce a +# restriction that each version can have at most 8 components. This allows us +# to `vec_compare()` them without needing a "joint" comparison proxy, unlike +# what `.encode_numeric_version()` returns. +proxy_equal_numeric_version <- function(x, error_call = caller_env()) { + N_COMPONENTS <- 8L + + x <- unclass(x) + + size <- length(x) + sizes <- lengths(x) + + if (length(sizes) != 0L) { + max <- max(sizes) + } else { + max <- N_COMPONENTS + } + + if (max > N_COMPONENTS) { + cli::cli_abort( + "`x` can't contain more than {N_COMPONENTS} version components.", + call = error_call + ) + } + + if (any(sizes != max)) { + # Pad with zeros where needed to be able to transpose. + # This is somewhat slow if required. + pad_sizes <- max - sizes + pad_needed <- which(pad_sizes != 0L) + + x[pad_needed] <- map2( + x[pad_needed], + pad_sizes[pad_needed], + function(elt, pad_size) { + c(elt, vec_rep(0L, times = pad_size)) + } + ) + } + + # Transpose with combination of `vec_interleave()` and `vec_chop()` + x <- vec_interleave(!!!x, .ptype = integer()) + + # TODO: `vec_chop(sizes = vec_rep(size, times = max))` + index <- seq_len(size) + indices <- vector("list", length = max) + + for (i in seq_len(max)) { + indices[[i]] <- index + index <- index + size + } + + out <- vec_chop(x, indices) + + n_zeros <- N_COMPONENTS - max + if (n_zeros != 0L) { + # Pad columns of zeros out to `N_COMPONENTS` columns + zero <- list(vec_rep(0L, times = size)) + out <- c(out, vec_rep(zero, times = n_zeros)) + } + + # Use a data frame as the proxy + names(out) <- paste0("...", seq_len(N_COMPONENTS)) + out <- new_data_frame(out, n = size) + + # A `` internally stored as `integer()` is considered the + # `NA` value. We patch that in at the very end if needed. It is hard to create + # so should be very uncommon. + missing <- sizes == 0L + + if (any(missing)) { + na <- vec_init(out) + out <- vec_assign(out, missing, na) + } + + out +} # `omit` from base --------------------------------------------------- diff --git a/tests/testthat/_snaps/type-misc.md b/tests/testthat/_snaps/type-misc.md index ba0833783..185491613 100644 --- a/tests/testthat/_snaps/type-misc.md +++ b/tests/testthat/_snaps/type-misc.md @@ -1,3 +1,11 @@ +# `numeric_version` proxy can handle at most 8 components + + Code + vec_proxy_equal(x) + Condition + Error in `vec_proxy_equal()`: + ! `x` can't contain more than 8 version components. + # data table has formatting methods Code diff --git a/tests/testthat/test-type-misc.R b/tests/testthat/test-type-misc.R index e1c61c7d4..bc407c42c 100644 --- a/tests/testthat/test-type-misc.R +++ b/tests/testthat/test-type-misc.R @@ -29,6 +29,140 @@ test_that("`numeric_version` falls back to base methods", { expect_identical(vec_c(x, y), z) }) +test_that("`numeric_version` has an equality, comparison, and order proxy", { + numeric_row <- function(...) { + out <- list2(...) + out <- map(out, as.integer) + names(out) <- paste0("...", seq_len(8L)) + new_data_frame(out, n = 1L) + } + + x <- numeric_version(c("1.2-3", "1.21.1", "3", "2.21.0.9000", "0.5.01")) + + expect <- vec_rbind( + numeric_row(1, 2, 3, 0, 0, 0, 0, 0), + numeric_row(1, 21, 1, 0, 0, 0, 0, 0), + numeric_row(3, 0, 0, 0, 0, 0, 0, 0), + numeric_row(2, 21, 0, 9000, 0, 0, 0, 0), + numeric_row(0, 5, 1, 0, 0, 0, 0, 0) + ) + + expect_identical(vec_proxy_equal(x), expect) + expect_identical(vec_proxy_compare(x), expect) + expect_identical(vec_proxy_order(x), expect) +}) + +test_that("`numeric_version` proxy works with empty vectors", { + x <- numeric_version(character()) + + expect <- vec_rep(list(integer()), times = 8L) + names(expect) <- paste0("...", seq_len(8L)) + expect <- new_data_frame(expect, n = 0L) + + expect_identical(vec_proxy_equal(x), expect) +}) + +test_that("`numeric_version` proxy handles pseudo-`NA`", { + numeric_row <- function(...) { + out <- list2(...) + out <- map(out, as.integer) + names(out) <- paste0("...", seq_len(8L)) + new_data_frame(out, n = 1L) + } + + x <- numeric_version(c("1_1", "1.2", NA), strict = FALSE) + + expect <- vec_rbind( + numeric_row(NA, NA, NA, NA, NA, NA, NA, NA), + numeric_row(1, 2, 0, 0, 0, 0, 0, 0), + numeric_row(NA, NA, NA, NA, NA, NA, NA, NA) + ) + + expect_identical(vec_proxy_equal(x), expect) + expect_identical(vec_proxy_compare(x), expect) + expect_identical(vec_proxy_order(x), expect) +}) + +test_that("`numeric_version` works with functions using the equality proxy", { + x <- numeric_version(c("1.2-3", "1.21.1", "1_1", "0.5", "1.3"), strict = FALSE) + y <- numeric_version(c("1.21.1", "1.21.1", "1_2", "0.05", "1_3"), strict = FALSE) + + expect_identical(vec_unique(x), x) + expect_identical(vec_unique(y), y[c(1, 3, 4)]) + + expect_identical(vec_detect_missing(y), c(FALSE, FALSE, TRUE, FALSE, TRUE)) + + expect_identical(vec_equal(x, y), c(FALSE, TRUE, NA, TRUE, NA)) + expect_identical(vec_equal(x, y, na_equal = TRUE), c(FALSE, TRUE, TRUE, TRUE, FALSE)) +}) + +test_that("`numeric_version` works with functions using the comparison proxy", { + x <- numeric_version(c("1.2-3", "1.21.1", "1_1", "0.5", "1.3"), strict = FALSE) + y <- numeric_version(c("1.21.1", "1.21.1", "1_2", "0.05", "1_3"), strict = FALSE) + + expect_identical(vec_compare(x, y), c(-1L, 0L, NA, 0L, NA)) + expect_identical(vec_compare(x, y, na_equal = TRUE), c(-1L, 0L, 0L, 0L, 1L)) + + # Specifically related to base R taking a joint proxy in `Ops.numeric_version` + x <- numeric_version("3.3") + y <- numeric_version("3.21") + # `.encode_numeric_version(x) < .encode_numeric_version(y)` == FALSE + # `x < y` == TRUE + expect_identical(vec_compare(x, y), -1L) +}) + +test_that("`numeric_version` works with functions using the order proxy (tidyverse/dplyr#6680)", { + x <- numeric_version(c("1.2-3", "1.21.1", "1_1", "0.5", "1.30"), strict = FALSE) + y <- numeric_version(c("1.21.1", "1.21.1", "1_2", "0.05", "1_3"), strict = FALSE) + + expect_identical(vec_order(y), c(4L, 1L, 2L, 3L, 5L)) + expect_identical(vec_order_radix(y), c(4L, 1L, 2L, 3L, 5L)) + + expect_identical(vec_order(y, na_value = "smallest"), c(3L, 5L, 4L, 1L, 2L)) + expect_identical(vec_order_radix(y, na_value = "smallest"), c(3L, 5L, 4L, 1L, 2L)) + + expect_identical( + vec_locate_matches(x, y), + data_frame( + needles = c(1L, 2L, 2L, 3L, 3L, 4L, 5L), + haystack = c(NA, 1L, 2L, 3L, 5L, 4L, NA) + ) + ) + expect_identical( + vec_locate_matches(x, y, condition = "<"), + data_frame( + needles = c(1L, 1L, 2L, 3L, 4L, 4L, 5L), + haystack = c(1L, 2L, NA, NA, 1L, 2L, NA) + ) + ) +}) + +test_that("`numeric_version` proxy can handle at most 8 components", { + x <- numeric_version("1.2.3.4.5.6.7.8") + expect_silent(vec_proxy_equal(x)) + + x <- numeric_version("1.2.3.4.5.6.7.8.9") + expect_snapshot(error = TRUE, { + vec_proxy_equal(x) + }) +}) + +test_that("`numeric_version` can compare against components with 8 components", { + x <- numeric_version("2.3.4.5.6.7.8.9") + y <- c(x, numeric_version(c("1.1", "11.2", "2.1"))) + + expect_identical(vec_compare(x, y), c(0L, 1L, -1L, 1L)) +}) + +test_that("`package_version` and `R_system_version` use the `numeric_version` proxy", { + x <- numeric_version("1.5.6") + y <- package_version("1.5.6") + z <- R_system_version("1.5.6") + + expect_identical(vec_proxy_equal(y), vec_proxy_equal(x)) + expect_identical(vec_proxy_equal(z), vec_proxy_equal(x)) +}) + test_that("common type of data.table and data.frame is data.table", { # As data.table is not in Suggests, these checks are only run on the # devs' machines From 6837eb4c86234438df1d9cf01ec0cf8b96f41b4b Mon Sep 17 00:00:00 2001 From: Davis Vaughan Date: Wed, 15 Feb 2023 11:16:55 -0500 Subject: [PATCH 229/312] Implement vector assertion helpers (#1786) * `vctrs_is_vector` -> `ffi_vec_is_vector` * Implement `vec_is_vector()` / `vec_check_vector()` / `vec_check_size()` Mark `vec_is()` and `vec_assert()` as questioning and internal * NEWS bullet * Rename `vec_is_vector()` to `obj_is_vector()` * Rename `vec_check_vector()` to `obj_check_vector()` * Tweak argument description * Preemptively error in `vec_check_size()` test * Tweak `vec_check_size()` description * Add technical limitations section * Provide C callable for `obj_is_vector()` - For use in dplyr - Soft-soft-deprecate `vec_is_vector()` - We can't remove the C callable for `"vec_is_vector"`. It you have new vctrs, but old dplyr, then initialization of the vctrs public API on the dplyr side won't be able to find the C callable if we removed it. --- NAMESPACE | 3 + NEWS.md | 7 ++ R/assert.R | 182 ++++++++++++++++++++++------- _pkgdown.yml | 3 +- inst/include/vctrs.c | 10 +- inst/include/vctrs.h | 8 +- man/vec_assert.Rd | 81 +++++++------ man/vector-checks.Rd | 123 +++++++++++++++++++ src/assert.c | 32 ++++- src/assert.h | 2 +- src/c.c | 2 +- src/cast.c | 4 +- src/decl/type-info-decl.h | 6 - src/fields.c | 2 +- src/init.c | 17 ++- src/ptype.c | 6 +- src/runs.c | 2 +- src/size-common.c | 4 +- src/slice-assign.c | 4 +- src/slice-chop.c | 2 +- src/slice.c | 6 +- src/subscript.c | 2 +- src/type-info.c | 18 +-- src/type-info.h | 2 +- tests/testthat/_snaps/assert.md | 97 +++++++++++++++ tests/testthat/test-assert.R | 141 +++++++++++++++++----- tests/testthat/test-type-list-of.R | 2 +- 27 files changed, 611 insertions(+), 157 deletions(-) create mode 100644 man/vector-checks.Rd diff --git a/NAMESPACE b/NAMESPACE index 8c5daf81f..4d020d8de 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -490,6 +490,8 @@ export(new_rcrd) export(new_vctr) export(num_as_location) export(num_as_location2) +export(obj_check_vector) +export(obj_is_vector) export(obj_print) export(obj_print_data) export(obj_print_footer) @@ -548,6 +550,7 @@ export(vec_cast_common) export(vec_cbind) export(vec_cbind_frame_ptype) export(vec_check_list) +export(vec_check_size) export(vec_chop) export(vec_compare) export(vec_count) diff --git a/NEWS.md b/NEWS.md index 177f451f8..bed8662b2 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,5 +1,12 @@ # vctrs (development version) +* New `obj_is_vector()`, `obj_check_vector()`, and `vec_check_size()` validation + helpers. We believe these are a better approach to vector validation than + `vec_assert()` and `vec_is()`, which have been marked as questioning because + the semantics of their `ptype` arguments are hard to define and can often be + replaced by `vec_cast()` or a type predicate function like + `rlang::is_logical()` (#1784). + * The `numeric_version` type from base R is now better supported in equality, comparison, and order based operations (tidyverse/dplyr#6680). diff --git a/R/assert.R b/R/assert.R index ba7af57c6..21fb42d62 100644 --- a/R/assert.R +++ b/R/assert.R @@ -1,6 +1,7 @@ #' Assert an argument has known prototype and/or size #' #' @description +#' `r lifecycle::badge("questioning")` #' #' * `vec_is()` is a predicate that checks if its input is a vector that #' conforms to a prototype and/or a size. @@ -8,37 +9,7 @@ #' * `vec_assert()` throws an error when the input is not a vector or #' doesn't conform. #' -#' @section Scalars and vectors: -#' -#' Informally, a vector is a collection that makes sense to use as -#' column in a data frame. An object is a vector if one of the -#' following conditions hold: -#' -#' - A [vec_proxy()] method is implemented for the class of the -#' object. -#' -#' - The [base type][typeof] of the object is atomic: `"logical"`, -#' `"integer"`, `"double"`, `"complex"`, `"character"`, `"raw"` -#' -#' - The object is a [data.frame]. -#' -#' - The base type is `"list"`, and one of: -#' - The object is a bare `"list"` without a `"class"` attribute. -#' - The object explicitly inherits from `"list"`. That is, the -#' `"class"` attribute contains `"list"` and `inherits(x, -#' "list")` is `TRUE`. -#' -#' Otherwise an object is treated as scalar and cannot be used as a -#' vector. In particular: -#' -#' - `NULL` is not a vector. -#' - S3 lists like `lm` objects are treated as scalars by default. -#' - Objects of type [expression] are not treated as vectors. -#' - Support for S4 vectors is currently limited to objects that -#' inherit from an atomic type. -#' - Subclasses of [data.frame] that *append* their class to the `"class"` -#' attribute are not treated as vectors. If you inherit from an S3 class, -#' always prepend your class to the `"class"` attribute for correct dispatch. +#' @inheritSection vector-checks Vectors and scalars #' #' @section Error types: #' @@ -56,6 +27,19 @@ #' #' Both errors inherit from `"vctrs_error_assert"`. #' +#' @section Lifecycle: +#' +#' Both `vec_is()` and `vec_assert()` are questioning because their `ptype` +#' arguments have semantics that are challenging to define clearly and are +#' rarely useful. +#' +#' - Use [obj_is_vector()] or [obj_check_vector()] for vector checks +#' +#' - Use [vec_check_size()] for size checks +#' +#' - Use [vec_cast()], [inherits()], or simple type predicates like +#' [rlang::is_logical()] for specific type checks +#' #' @inheritParams rlang::args_error_context #' #' @param x A vector argument to check. @@ -71,13 +55,14 @@ #' @return `vec_is()` returns `TRUE` or `FALSE`. `vec_assert()` either #' throws a typed error (see section on error types) or returns `x`, #' invisibly. +#' @keywords internal #' @export vec_assert <- function(x, ptype = NULL, size = NULL, arg = caller_arg(x), call = caller_env()) { - if (!vec_is_vector(x)) { + if (!obj_is_vector(x)) { stop_scalar_type(x, arg, call = call) } @@ -155,7 +140,7 @@ stop_assert <- function(message = NULL, #' @rdname vec_assert #' @export vec_is <- function(x, ptype = NULL, size = NULL) { - if (!vec_is_vector(x)) { + if (!obj_is_vector(x)) { return(FALSE) } @@ -178,20 +163,133 @@ vec_is <- function(x, ptype = NULL, size = NULL) { TRUE } -#' Is object a vector? -#' @noRd +#' Vector checks #' #' @description #' -#' Returns `TRUE` if: +#' - `obj_is_vector()` tests if `x` is considered a vector in the vctrs sense. +#' See _Vectors and scalars_ below for the exact details. +#' +#' - `obj_check_vector()` uses `obj_is_vector()` and throws a standardized and +#' informative error if it returns `FALSE`. +#' +#' - `vec_check_size()` tests if `x` has size `size`, and throws an informative +#' error if it doesn't. +#' +#' @inheritParams rlang::args_dots_empty +#' @inheritParams rlang::args_error_context +#' +#' @param x For `obj_*()` functions, an object. For `vec_*()` functions, a +#' vector. +#' +#' @param size The size to check for. +#' +#' @returns +#' - `obj_is_vector()` returns a single `TRUE` or `FALSE`. +#' +#' - `obj_check_vector()` returns `NULL` invisibly, or errors. +#' +#' - `vec_check_size()` returns `NULL` invisibly, or errors. +#' +#' @section Vectors and scalars: +#' +#' Informally, a vector is a collection that makes sense to use as column in a +#' data frame. The following rules define whether or not `x` is considered a +#' vector. +#' +#' If no [vec_proxy()] method has been registered, `x` is a vector if: +#' +#' - The [base type][typeof] of the object is atomic: `"logical"`, `"integer"`, +#' `"double"`, `"complex"`, `"character"`, or `"raw"`. #' -#' * `x` is an atomic, whether it has a class or not. -#' * `x` is a bare list without class. -#' * `x` implements [vec_proxy()]. +#' - `x` is a list, as defined by [vec_is_list()]. #' -#' S3 lists are thus treated as scalars unless they implement a proxy. -vec_is_vector <- function(x) { - .Call(vctrs_is_vector, x) +#' - `x` is a [data.frame]. +#' +#' If a `vec_proxy()` method has been registered, `x` is a vector if: +#' +#' - The proxy satisfies one of the above conditions. +#' +#' - The base type of the proxy is `"list"`, regardless of its class. S3 lists +#' are thus treated as scalars unless they implement a `vec_proxy()` method. +#' +#' Otherwise an object is treated as scalar and cannot be used as a vector. +#' In particular: +#' +#' - `NULL` is not a vector. +#' +#' - S3 lists like `lm` objects are treated as scalars by default. +#' +#' - Objects of type [expression] are not treated as vectors. +#' +#' @section Technical limitations: +#' +#' - Support for S4 vectors is currently limited to objects that inherit from an +#' atomic type. +#' +#' - Subclasses of [data.frame] that *append* their class to the back of the +#' `"class"` attribute are not treated as vectors. If you inherit from an S3 +#' class, always prepend your class to the front of the `"class"` attribute +#' for correct dispatch. This matches our general principle of allowing +#' subclasses but not mixins. +#' +#' @name vector-checks +#' @examples +#' obj_is_vector(1) +#' +#' # Data frames are vectors +#' obj_is_vector(data_frame()) +#' +#' # Bare lists are vectors +#' obj_is_vector(list()) +#' +#' # S3 lists are vectors if they explicitly inherit from `"list"` +#' x <- structure(list(), class = c("my_list", "list")) +#' vec_is_list(x) +#' obj_is_vector(x) +#' +#' # But if they don't explicitly inherit from `"list"`, they aren't +#' # automatically considered to be vectors. Instead, vctrs considers this +#' # to be a scalar object, like a linear model returned from `lm()`. +#' y <- structure(list(), class = "my_list") +#' vec_is_list(y) +#' obj_is_vector(y) +#' +#' # `obj_check_vector()` throws an informative error if the input +#' # isn't a vector +#' try(obj_check_vector(y)) +#' +#' # `vec_check_size()` throws an informative error if the size of the +#' # input doesn't match `size` +#' vec_check_size(1:5, size = 5) +#' try(vec_check_size(1:5, size = 4)) +NULL + +#' @export +#' @rdname vector-checks +obj_is_vector <- function(x) { + .Call(ffi_obj_is_vector, x) +} + +#' @export +#' @rdname vector-checks +obj_check_vector <- function(x, + ..., + arg = caller_arg(x), + call = caller_env()) { + check_dots_empty0(...) + invisible(.Call(ffi_obj_check_vector, x, environment())) +} + +#' @export +#' @rdname vector-checks +vec_check_size <- function(x, + size, + ..., + arg = caller_arg(x), + call = caller_env()) { + check_dots_empty0(...) + invisible(.Call(ffi_vec_check_size, x, size, environment())) } #' List checks diff --git a/_pkgdown.yml b/_pkgdown.yml index bb5286ba0..f7c8e4924 100644 --- a/_pkgdown.yml +++ b/_pkgdown.yml @@ -40,9 +40,8 @@ reference: - vec_data - vec_ptype - vec_size - - vec_is + - obj_is_vector - vec_is_list - - vec_assert - title: Combining contents: diff --git a/inst/include/vctrs.c b/inst/include/vctrs.c index af4819e72..ce849c4aa 100644 --- a/inst/include/vctrs.c +++ b/inst/include/vctrs.c @@ -1,11 +1,17 @@ #include "vctrs.h" -bool (*vec_is_vector)(SEXP) = NULL; +// Maturing +bool (*obj_is_vector)(SEXP) = NULL; R_len_t (*short_vec_size)(SEXP) = NULL; SEXP (*short_vec_recycle)(SEXP, R_len_t) = NULL; +// Deprecated +bool (*vec_is_vector)(SEXP) = NULL; + void vctrs_init_api(void) { - vec_is_vector = (bool (*)(SEXP)) R_GetCCallable("vctrs", "vec_is_vector"); + obj_is_vector = (bool (*)(SEXP)) R_GetCCallable("vctrs", "obj_is_vector"); short_vec_size = (R_len_t (*)(SEXP)) R_GetCCallable("vctrs", "short_vec_size"); short_vec_recycle = (SEXP (*)(SEXP, R_len_t)) R_GetCCallable("vctrs", "short_vec_recycle"); + + vec_is_vector = (bool (*)(SEXP)) R_GetCCallable("vctrs", "vec_is_vector"); } diff --git a/inst/include/vctrs.h b/inst/include/vctrs.h index 6c8205aba..2b379b683 100644 --- a/inst/include/vctrs.h +++ b/inst/include/vctrs.h @@ -5,10 +5,16 @@ #include #include -extern bool (*vec_is_vector)(SEXP); +// Maturing +extern bool (*obj_is_vector)(SEXP); extern R_len_t (*short_vec_size)(SEXP); extern SEXP (*short_vec_recycle)(SEXP, R_len_t); +// Deprecated in favor of `obj_is_vector()` +// version: 0.5.3 +// date: 2023-02-15 +extern bool (*vec_is_vector)(SEXP); + void vctrs_init_api(void); #endif diff --git a/man/vec_assert.Rd b/man/vec_assert.Rd index 54adc3f5d..aaee687eb 100644 --- a/man/vec_assert.Rd +++ b/man/vec_assert.Rd @@ -40,6 +40,7 @@ throws a typed error (see section on error types) or returns \code{x}, invisibly. } \description{ +\ifelse{html}{\href{https://lifecycle.r-lib.org/articles/stages.html#questioning}{\figure{lifecycle-questioning.svg}{options: alt='[Questioning]'}}}{\strong{[Questioning]}} \itemize{ \item \code{vec_is()} is a predicate that checks if its input is a vector that conforms to a prototype and/or a size. @@ -47,40 +48,6 @@ conforms to a prototype and/or a size. doesn't conform. } } -\section{Scalars and vectors}{ - - -Informally, a vector is a collection that makes sense to use as -column in a data frame. An object is a vector if one of the -following conditions hold: -\itemize{ -\item A \code{\link[=vec_proxy]{vec_proxy()}} method is implemented for the class of the -object. -\item The \link[=typeof]{base type} of the object is atomic: \code{"logical"}, -\code{"integer"}, \code{"double"}, \code{"complex"}, \code{"character"}, \code{"raw"} -\item The object is a \link{data.frame}. -\item The base type is \code{"list"}, and one of: -\itemize{ -\item The object is a bare \code{"list"} without a \code{"class"} attribute. -\item The object explicitly inherits from \code{"list"}. That is, the -\code{"class"} attribute contains \code{"list"} and \code{inherits(x, "list")} is \code{TRUE}. -} -} - -Otherwise an object is treated as scalar and cannot be used as a -vector. In particular: -\itemize{ -\item \code{NULL} is not a vector. -\item S3 lists like \code{lm} objects are treated as scalars by default. -\item Objects of type \link{expression} are not treated as vectors. -\item Support for S4 vectors is currently limited to objects that -inherit from an atomic type. -\item Subclasses of \link{data.frame} that \emph{append} their class to the \code{"class"} -attribute are not treated as vectors. If you inherit from an S3 class, -always prepend your class to the \code{"class"} attribute for correct dispatch. -} -} - \section{Error types}{ @@ -98,3 +65,49 @@ always prepend your class to the \code{"class"} attribute for correct dispatch. Both errors inherit from \code{"vctrs_error_assert"}. } +\section{Lifecycle}{ + + +Both \code{vec_is()} and \code{vec_assert()} are questioning because their \code{ptype} +arguments have semantics that are challenging to define clearly and are +rarely useful. +\itemize{ +\item Use \code{\link[=obj_is_vector]{obj_is_vector()}} or \code{\link[=obj_check_vector]{obj_check_vector()}} for vector checks +\item Use \code{\link[=vec_check_size]{vec_check_size()}} for size checks +\item Use \code{\link[=vec_cast]{vec_cast()}}, \code{\link[=inherits]{inherits()}}, or simple type predicates like +\code{\link[rlang:type-predicates]{rlang::is_logical()}} for specific type checks +} +} + +\section{Vectors and scalars}{ + + +Informally, a vector is a collection that makes sense to use as column in a +data frame. The following rules define whether or not \code{x} is considered a +vector. + +If no \code{\link[=vec_proxy]{vec_proxy()}} method has been registered, \code{x} is a vector if: +\itemize{ +\item The \link[=typeof]{base type} of the object is atomic: \code{"logical"}, \code{"integer"}, +\code{"double"}, \code{"complex"}, \code{"character"}, or \code{"raw"}. +\item \code{x} is a list, as defined by \code{\link[=vec_is_list]{vec_is_list()}}. +\item \code{x} is a \link{data.frame}. +} + +If a \code{vec_proxy()} method has been registered, \code{x} is a vector if: +\itemize{ +\item The proxy satisfies one of the above conditions. +\item The base type of the proxy is \code{"list"}, regardless of its class. S3 lists +are thus treated as scalars unless they implement a \code{vec_proxy()} method. +} + +Otherwise an object is treated as scalar and cannot be used as a vector. +In particular: +\itemize{ +\item \code{NULL} is not a vector. +\item S3 lists like \code{lm} objects are treated as scalars by default. +\item Objects of type \link{expression} are not treated as vectors. +} +} + +\keyword{internal} diff --git a/man/vector-checks.Rd b/man/vector-checks.Rd new file mode 100644 index 000000000..f88cf00ee --- /dev/null +++ b/man/vector-checks.Rd @@ -0,0 +1,123 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/assert.R +\name{vector-checks} +\alias{vector-checks} +\alias{obj_is_vector} +\alias{obj_check_vector} +\alias{vec_check_size} +\title{Vector checks} +\usage{ +obj_is_vector(x) + +obj_check_vector(x, ..., arg = caller_arg(x), call = caller_env()) + +vec_check_size(x, size, ..., arg = caller_arg(x), call = caller_env()) +} +\arguments{ +\item{x}{For \verb{obj_*()} functions, an object. For \verb{vec_*()} functions, a +vector.} + +\item{...}{These dots are for future extensions and must be empty.} + +\item{arg}{An argument name as a string. This argument +will be mentioned in error messages as the input that is at the +origin of a problem.} + +\item{call}{The execution environment of a currently +running function, e.g. \code{caller_env()}. The function will be +mentioned in error messages as the source of the error. See the +\code{call} argument of \code{\link[rlang:abort]{abort()}} for more information.} + +\item{size}{The size to check for.} +} +\value{ +\itemize{ +\item \code{obj_is_vector()} returns a single \code{TRUE} or \code{FALSE}. +\item \code{obj_check_vector()} returns \code{NULL} invisibly, or errors. +\item \code{vec_check_size()} returns \code{NULL} invisibly, or errors. +} +} +\description{ +\itemize{ +\item \code{obj_is_vector()} tests if \code{x} is considered a vector in the vctrs sense. +See \emph{Vectors and scalars} below for the exact details. +\item \code{obj_check_vector()} uses \code{obj_is_vector()} and throws a standardized and +informative error if it returns \code{FALSE}. +\item \code{vec_check_size()} tests if \code{x} has size \code{size}, and throws an informative +error if it doesn't. +} +} +\section{Vectors and scalars}{ + + +Informally, a vector is a collection that makes sense to use as column in a +data frame. The following rules define whether or not \code{x} is considered a +vector. + +If no \code{\link[=vec_proxy]{vec_proxy()}} method has been registered, \code{x} is a vector if: +\itemize{ +\item The \link[=typeof]{base type} of the object is atomic: \code{"logical"}, \code{"integer"}, +\code{"double"}, \code{"complex"}, \code{"character"}, or \code{"raw"}. +\item \code{x} is a list, as defined by \code{\link[=vec_is_list]{vec_is_list()}}. +\item \code{x} is a \link{data.frame}. +} + +If a \code{vec_proxy()} method has been registered, \code{x} is a vector if: +\itemize{ +\item The proxy satisfies one of the above conditions. +\item The base type of the proxy is \code{"list"}, regardless of its class. S3 lists +are thus treated as scalars unless they implement a \code{vec_proxy()} method. +} + +Otherwise an object is treated as scalar and cannot be used as a vector. +In particular: +\itemize{ +\item \code{NULL} is not a vector. +\item S3 lists like \code{lm} objects are treated as scalars by default. +\item Objects of type \link{expression} are not treated as vectors. +} +} + +\section{Technical limitations}{ + +\itemize{ +\item Support for S4 vectors is currently limited to objects that inherit from an +atomic type. +\item Subclasses of \link{data.frame} that \emph{append} their class to the back of the +\code{"class"} attribute are not treated as vectors. If you inherit from an S3 +class, always prepend your class to the front of the \code{"class"} attribute +for correct dispatch. This matches our general principle of allowing +subclasses but not mixins. +} +} + +\examples{ +obj_is_vector(1) + +# Data frames are vectors +obj_is_vector(data_frame()) + +# Bare lists are vectors +obj_is_vector(list()) + +# S3 lists are vectors if they explicitly inherit from `"list"` +x <- structure(list(), class = c("my_list", "list")) +vec_is_list(x) +obj_is_vector(x) + +# But if they don't explicitly inherit from `"list"`, they aren't +# automatically considered to be vectors. Instead, vctrs considers this +# to be a scalar object, like a linear model returned from `lm()`. +y <- structure(list(), class = "my_list") +vec_is_list(y) +obj_is_vector(y) + +# `obj_check_vector()` throws an informative error if the input +# isn't a vector +try(obj_check_vector(y)) + +# `vec_check_size()` throws an informative error if the size of the +# input doesn't match `size` +vec_check_size(1:5, size = 5) +try(vec_check_size(1:5, size = 4)) +} diff --git a/src/assert.c b/src/assert.c index 1aa8217f8..7c004967e 100644 --- a/src/assert.c +++ b/src/assert.c @@ -5,7 +5,7 @@ void vec_assert(r_obj* x, r_ssize size, struct vctrs_arg* arg, struct r_lazy call) { - vec_check_vector(x, arg, call); + obj_check_vector(x, arg, call); if (size != -1) { // `size == -1` makes no assertion about size @@ -13,19 +13,41 @@ void vec_assert(r_obj* x, } } -void vec_check_vector(r_obj* x, +r_obj* ffi_obj_check_vector(r_obj* x, r_obj* frame) { + struct r_lazy call = { .x = r_syms.call, .env = frame }; + struct r_lazy arg_lazy = { .x = r_syms.arg, .env = frame }; + struct vctrs_arg arg = new_lazy_arg(&arg_lazy); + + obj_check_vector(x, &arg, call); + + return r_null; +} + +void obj_check_vector(r_obj* x, struct vctrs_arg* arg, struct r_lazy call) { - if (!vec_is_vector(x)) { + if (!obj_is_vector(x)) { stop_scalar_type(x, arg, call); } } +r_obj* ffi_vec_check_size(r_obj* x, r_obj* ffi_size, r_obj* frame) { + struct r_lazy call = { .x = r_syms.call, .env = frame }; + struct r_lazy arg_lazy = { .x = r_syms.arg, .env = frame }; + struct vctrs_arg arg = new_lazy_arg(&arg_lazy); + + const r_ssize size = r_arg_as_ssize(ffi_size, "size"); + + vec_check_size(x, size, &arg, call); + + return r_null; +} + void vec_check_size(r_obj* x, r_ssize size, struct vctrs_arg* arg, struct r_lazy call) { - r_ssize x_size = vec_size_3(x, arg, call); + const r_ssize x_size = vec_size_3(x, arg, call); if (x_size != size) { stop_assert_size(x_size, size, arg, call); @@ -79,7 +101,7 @@ r_obj* ffi_list_check_all_vectors(r_obj* x, r_obj* frame) { r_obj* const * v_x = r_list_cbegin(x); for (; i < n; ++i) { - vec_check_vector(v_x[i], arg, call); + obj_check_vector(v_x[i], arg, call); } FREE(1); diff --git a/src/assert.h b/src/assert.h index 4decae4e1..9798ad8e5 100644 --- a/src/assert.h +++ b/src/assert.h @@ -8,7 +8,7 @@ void vec_assert(r_obj* x, struct vctrs_arg* arg, struct r_lazy call); -void vec_check_vector(r_obj* x, +void obj_check_vector(r_obj* x, struct vctrs_arg* arg, struct r_lazy call); diff --git a/src/c.c b/src/c.c index e090b445b..4265bb000 100644 --- a/src/c.c +++ b/src/c.c @@ -214,7 +214,7 @@ bool needs_vec_c_homogeneous_fallback(r_obj* xs, r_obj* ptype) { } r_obj* x = list_first_non_null(xs, NULL); - if (!vec_is_vector(x)) { + if (!obj_is_vector(x)) { return false; } diff --git a/src/cast.c b/src/cast.c index eef768bfa..395cec34b 100644 --- a/src/cast.c +++ b/src/cast.c @@ -25,13 +25,13 @@ r_obj* vec_cast_opts(const struct cast_opts* opts) { if (x == r_null) { if (!vec_is_partial(to)) { - vec_check_vector(to, to_arg, opts->call); + obj_check_vector(to, to_arg, opts->call); } return x; } if (to == r_null) { if (!vec_is_partial(x)) { - vec_check_vector(x, x_arg, opts->call); + obj_check_vector(x, x_arg, opts->call); } return x; } diff --git a/src/decl/type-info-decl.h b/src/decl/type-info-decl.h index d0cc118b9..2370dc3bd 100644 --- a/src/decl/type-info-decl.h +++ b/src/decl/type-info-decl.h @@ -1,8 +1,2 @@ -static -r_obj* syms_vec_is_vector_dispatch; - -static -r_obj* fns_vec_is_vector_dispatch; - static enum vctrs_type vec_base_typeof(r_obj* x, bool proxied); diff --git a/src/fields.c b/src/fields.c index 9265d3ed9..5ab254713 100644 --- a/src/fields.c +++ b/src/fields.c @@ -126,7 +126,7 @@ SEXP vctrs_field_get(SEXP x, SEXP index) { SEXP vctrs_field_set(SEXP x, SEXP index, SEXP value) { check_rcrd(x); - if (!vec_is_vector(value)) { + if (!obj_is_vector(value)) { Rf_errorcall(R_NilValue, "Invalid value: not a vector."); } diff --git a/src/init.c b/src/init.c index 673fba741..6923f608e 100644 --- a/src/init.c +++ b/src/init.c @@ -40,7 +40,9 @@ extern SEXP vctrs_dim(SEXP); extern SEXP vctrs_dim_n(SEXP); extern SEXP vctrs_is_unspecified(SEXP); extern SEXP vctrs_typeof(SEXP, SEXP); -extern SEXP vctrs_is_vector(SEXP); +extern r_obj* ffi_obj_is_vector(r_obj*); +extern r_obj* ffi_obj_check_vector(r_obj*, r_obj*); +extern r_obj* ffi_vec_check_size(r_obj*, r_obj*, r_obj*); extern r_obj* ffi_ptype2(r_obj*, r_obj*, r_obj*); extern r_obj* ffi_typeof2(r_obj*, r_obj*); extern r_obj* ffi_typeof2_s3(r_obj*, r_obj*); @@ -162,7 +164,7 @@ extern r_obj* ffi_vec_expand_grid(r_obj*, r_obj*, r_obj*, r_obj*); // Maturing // In the public header -extern bool vec_is_vector(SEXP); +extern bool obj_is_vector(SEXP); extern R_len_t short_vec_size(SEXP); extern SEXP short_vec_recycle(SEXP, R_len_t); @@ -217,7 +219,9 @@ static const R_CallMethodDef CallEntries[] = { {"vctrs_in", (DL_FUNC) &vctrs_in, 4}, {"vctrs_typeof", (DL_FUNC) &vctrs_typeof, 2}, {"vctrs_init_library", (DL_FUNC) &vctrs_init_library, 1}, - {"vctrs_is_vector", (DL_FUNC) &vctrs_is_vector, 1}, + {"ffi_obj_is_vector", (DL_FUNC) &ffi_obj_is_vector, 1}, + {"ffi_obj_check_vector", (DL_FUNC) &ffi_obj_check_vector, 2}, + {"ffi_vec_check_size", (DL_FUNC) &ffi_vec_check_size, 3}, {"ffi_ptype2", (DL_FUNC) &ffi_ptype2, 3}, {"ffi_typeof2", (DL_FUNC) &ffi_typeof2, 2}, {"ffi_typeof2_s3", (DL_FUNC) &ffi_typeof2_s3, 2}, @@ -376,10 +380,15 @@ export void R_init_vctrs(DllInfo *dll) // Maturing // In the public header - R_RegisterCCallable("vctrs", "vec_is_vector", (DL_FUNC) &vec_is_vector); + R_RegisterCCallable("vctrs", "obj_is_vector", (DL_FUNC) &obj_is_vector); R_RegisterCCallable("vctrs", "short_vec_size", (DL_FUNC) &short_vec_size); R_RegisterCCallable("vctrs", "short_vec_recycle", (DL_FUNC) &short_vec_recycle); + // Deprecated + // In the public header + // See `inst/include/vctrs.h` for details + R_RegisterCCallable("vctrs", "vec_is_vector", (DL_FUNC) &obj_is_vector); + // Experimental // Exported but not available in the public header R_RegisterCCallable("vctrs", "exp_vec_cast", (DL_FUNC) &exp_vec_cast); diff --git a/src/ptype.c b/src/ptype.c index d74ff6fc1..6ea50fb50 100644 --- a/src/ptype.c +++ b/src/ptype.c @@ -73,7 +73,7 @@ r_obj* s3_ptype(r_obj* x, r_obj* out; if (method == r_null) { - vec_check_vector(x, x_arg, call); + obj_check_vector(x, x_arg, call); out = vec_slice(x, r_null); } else { out = vec_ptype_invoke(x, method); @@ -124,7 +124,7 @@ r_obj* vec_ptype_finalise(r_obj* x) { struct r_lazy call = lazy_calls.vec_ptype_finalise; if (!r_is_object(x)) { - vec_check_vector(x, vec_args.x, call); + obj_check_vector(x, vec_args.x, call); return x; } @@ -136,7 +136,7 @@ r_obj* vec_ptype_finalise(r_obj* x) { return vec_ptype_finalise_dispatch(x); } - vec_check_vector(x, vec_args.x, call); + obj_check_vector(x, vec_args.x, call); switch (class_type(x)) { case VCTRS_CLASS_bare_tibble: diff --git a/src/runs.c b/src/runs.c index 7f4326d39..53284062c 100644 --- a/src/runs.c +++ b/src/runs.c @@ -152,7 +152,7 @@ static struct r_vector_bool* vec_detect_run_bounds_bool(r_obj* x, enum vctrs_run_bound which, struct r_lazy error_call) { - vec_check_vector(x, vec_args.x, error_call); + obj_check_vector(x, vec_args.x, error_call); r_obj* proxy = KEEP(vec_proxy_equal(x)); proxy = KEEP(vec_normalize_encoding(proxy)); diff --git a/src/size-common.c b/src/size-common.c index 0c11bb624..d74ad325a 100644 --- a/src/size-common.c +++ b/src/size-common.c @@ -84,10 +84,10 @@ r_obj* vctrs_size2_common(r_obj* x, struct size_common_opts* opts = data; if (x != r_null) { - vec_check_vector(x, counters->curr_arg, opts->call); + obj_check_vector(x, counters->curr_arg, opts->call); } if (y != r_null) { - vec_check_vector(y, counters->next_arg, opts->call); + obj_check_vector(y, counters->next_arg, opts->call); } if (x == r_null) { diff --git a/src/slice-assign.c b/src/slice-assign.c index e79bd88c2..ab340c9cd 100644 --- a/src/slice-assign.c +++ b/src/slice-assign.c @@ -18,8 +18,8 @@ r_obj* vec_assign_opts(r_obj* x, opts.value_arg = vec_args.value; } - vec_check_vector(x, opts.x_arg, opts.call); - vec_check_vector(value, opts.value_arg, opts.call); + obj_check_vector(x, opts.x_arg, opts.call); + obj_check_vector(value, opts.value_arg, opts.call); const struct location_opts location_opts = new_location_opts_assign(); index = KEEP(vec_as_location_opts(index, diff --git a/src/slice-chop.c b/src/slice-chop.c index b60f5dcf9..d924b3925 100644 --- a/src/slice-chop.c +++ b/src/slice-chop.c @@ -155,7 +155,7 @@ static SEXP vec_chop_base(SEXP x, SEXP indices, struct vctrs_chop_info info) { return chop_df(x, indices, info); } default: - vec_check_vector(x, vec_args.empty, r_lazy_null); + obj_check_vector(x, vec_args.empty, r_lazy_null); stop_unimplemented_vctrs_type("vec_chop_base", proxy_info.type); } } diff --git a/src/slice.c b/src/slice.c index 26a67d838..2da78a3ea 100644 --- a/src/slice.c +++ b/src/slice.c @@ -293,7 +293,7 @@ r_obj* vec_slice_unsafe(r_obj* x, r_obj* subscript) { // to be maximally compatible with existing classes. if (vec_requires_fallback(x, info)) { if (info.type == VCTRS_TYPE_scalar) { - vec_check_vector(x, NULL, r_lazy_null); + obj_check_vector(x, NULL, r_lazy_null); } if (is_compact(subscript)) { @@ -409,7 +409,7 @@ r_obj* ffi_slice(r_obj* x, r_obj* vec_slice_opts(r_obj* x, r_obj* i, const struct vec_slice_opts* opts) { - vec_check_vector(x, opts->x_arg, opts->call); + obj_check_vector(x, opts->x_arg, opts->call); r_obj* names = KEEP(vec_names(x)); i = KEEP(vec_as_location_ctxt(i, @@ -425,7 +425,7 @@ r_obj* vec_slice_opts(r_obj* x, } r_obj* vec_init(r_obj* x, r_ssize n) { - vec_check_vector(x, vec_args.x, lazy_calls.vec_init); + obj_check_vector(x, vec_args.x, lazy_calls.vec_init); if (n < 0) { r_abort_lazy_call(lazy_calls.vec_init, diff --git a/src/subscript.c b/src/subscript.c index 99c99e77b..ceb66c771 100644 --- a/src/subscript.c +++ b/src/subscript.c @@ -31,7 +31,7 @@ r_obj* vec_as_subscript_opts(r_obj* subscript, } KEEP_AT(subscript, subscript_pi); - if (!vec_is_vector(subscript)) { + if (!obj_is_vector(subscript)) { *err = new_error_subscript_type(subscript, opts, r_null); FREE(2); return r_null; diff --git a/src/type-info.c b/src/type-info.c index 3950b193c..a9323f99e 100644 --- a/src/type-info.c +++ b/src/type-info.c @@ -112,12 +112,11 @@ bool vec_is_list(r_obj* x) { return (type == VCTRS_CLASS_list) || (type == VCTRS_CLASS_bare_asis); } -// [[ register() ]] -r_obj* vctrs_is_vector(r_obj* x) { - return r_lgl(vec_is_vector(x)); +r_obj* ffi_obj_is_vector(r_obj* x) { + return r_lgl(obj_is_vector(x)); } -bool vec_is_vector(r_obj* x) { +bool obj_is_vector(r_obj* x) { if (x == r_null) { return false; } @@ -136,7 +135,7 @@ bool list_all_vectors(r_obj* x) { if (r_typeof(x) != R_TYPE_list) { r_stop_unexpected_type(r_typeof(x)); } - return r_list_all_of(x, &vec_is_vector); + return r_list_all_of(x, &obj_is_vector); } @@ -197,12 +196,5 @@ const char* vec_type_as_str(enum vctrs_type type) { void vctrs_init_type_info(r_obj* ns) { - syms_vec_is_vector_dispatch = r_sym("vec_is_vector"); - fns_vec_is_vector_dispatch = r_eval(syms_vec_is_vector_dispatch, ns); -} - -static -r_obj* syms_vec_is_vector_dispatch = NULL; -static -r_obj* fns_vec_is_vector_dispatch = NULL; +} diff --git a/src/type-info.h b/src/type-info.h index 4af36a69b..867699a68 100644 --- a/src/type-info.h +++ b/src/type-info.h @@ -66,7 +66,7 @@ enum vctrs_type vec_proxy_typeof(r_obj* x); const char* vec_type_as_str(enum vctrs_type type); bool vec_is_list(r_obj* x); -bool vec_is_vector(r_obj* x); +bool obj_is_vector(r_obj* x); bool list_all_vectors(r_obj* x); r_no_return diff --git a/tests/testthat/_snaps/assert.md b/tests/testthat/_snaps/assert.md index 8f4542bcb..56b313bf5 100644 --- a/tests/testthat/_snaps/assert.md +++ b/tests/testthat/_snaps/assert.md @@ -1,3 +1,27 @@ +# obj_check_vector() errors on scalars + + Code + obj_check_vector(quote(foo)) + Condition + Error: + ! `quote(foo)` must be a vector, not a symbol. + +--- + + Code + obj_check_vector(foobar()) + Condition + Error: + ! `foobar()` must be a vector, not a object. + +# obj_check_vector() error respects `arg` and `call` + + Code + my_check_vector(foobar()) + Condition + Error in `my_check_vector()`: + ! `foo` must be a vector, not a object. + # assertion failures are explained Code @@ -188,6 +212,79 @@ Error in `vec_assert()`: ! Can't convert `size` to . +# vec_check_size() errors on the wrong size + + Code + vec_check_size(1:5, size = 1L) + Condition + Error: + ! `1:5` must have size 1, not size 5. + +--- + + Code + vec_check_size(1:5, size = 10L) + Condition + Error: + ! `1:5` must have size 10, not size 5. + +# vec_check_size() errors on scalars + + Code + vec_check_size(quote(foo), size = 1L) + Condition + Error: + ! `quote(foo)` must be a vector, not a symbol. + +--- + + Code + vec_check_size(foobar(), size = 1L) + Condition + Error: + ! `foobar()` must be a vector, not a object. + +# vec_check_size() error respects `arg` and `call` + + Code + my_check_size(1L, size = 5L) + Condition + Error in `my_check_size()`: + ! `foo` must have size 5, not size 1. + +--- + + Code + my_check_size(foobar(), size = 5L) + Condition + Error in `my_check_size()`: + ! `foo` must be a vector, not a object. + +# vec_check_size() validates `size` + + Code + vec_check_size(1, size = "x") + Condition + Error in `vec_check_size()`: + ! `size` must be a scalar integer or double. + +--- + + Code + vec_check_size(1, size = c(1L, 2L)) + Condition + Error in `vec_check_size()`: + ! `size` must be a scalar integer or double. + +--- + + Code + vec_check_size(1, size = 1.5) + abort("`vec_check_size()` should error for us") + Condition + Error: + ! `vec_check_size()` should error for us + # list_all_vectors() works Code diff --git a/tests/testthat/test-assert.R b/tests/testthat/test-assert.R index fde573716..445eebd88 100644 --- a/tests/testthat/test-assert.R +++ b/tests/testthat/test-assert.R @@ -49,36 +49,43 @@ test_that("vec_assert() labels input", { }) test_that("bare atomic vectors are vectors but not recursive", { - expect_true(vec_is_vector(TRUE)) - expect_true(vec_is_vector(1L)) - expect_true(vec_is_vector(1)) - expect_true(vec_is_vector(1i)) - expect_true(vec_is_vector("foo")) - expect_true(vec_is_vector(as.raw(1))) + expect_true(obj_is_vector(TRUE)) + expect_true(obj_is_vector(1L)) + expect_true(obj_is_vector(1)) + expect_true(obj_is_vector(1i)) + expect_true(obj_is_vector("foo")) + expect_true(obj_is_vector(as.raw(1))) }) test_that("S3 atomic vectors are vectors", { - expect_true(vec_is_vector(foobar(TRUE))) - expect_true(vec_is_vector(foobar(1L))) - expect_true(vec_is_vector(foobar(1))) - expect_true(vec_is_vector(foobar(1i))) - expect_true(vec_is_vector(foobar("foo"))) - expect_true(vec_is_vector(foobar(as.raw(1)))) + expect_true(obj_is_vector(foobar(TRUE))) + expect_true(obj_is_vector(foobar(1L))) + expect_true(obj_is_vector(foobar(1))) + expect_true(obj_is_vector(foobar(1i))) + expect_true(obj_is_vector(foobar("foo"))) + expect_true(obj_is_vector(foobar(as.raw(1)))) }) test_that("bare lists are vectors", { - expect_true(vec_is_vector(list())) + expect_true(obj_is_vector(list())) }) test_that("S3 lists are not vectors by default", { - expect_false(vec_is_vector(foobar())) + expect_false(obj_is_vector(foobar())) + expect_false(vec_is_list(foobar())) + local_foobar_proxy() - expect_true(vec_is_vector(foobar())) + + # TODO: These seem inconsistent. + # Should we require that S3 list proxies satisfy `vec_is_list()`? + # (i.e. unclass themselves or explicitly inherit from `"list"`?) + expect_true(obj_is_vector(foobar())) + expect_false(vec_is_list(foobar())) }) test_that("data frames and records are vectors", { - expect_true(vec_is_vector(mtcars)) - expect_true(vec_is_vector(new_rcrd(list(x = 1, y = 2)))) + expect_true(obj_is_vector(mtcars)) + expect_true(obj_is_vector(new_rcrd(list(x = 1, y = 2)))) }) test_that("non-vector base types are scalars", { @@ -92,14 +99,14 @@ test_that("non-vector base types are scalars", { expect_identical(vec_typeof(base::c), "scalar") expect_identical(vec_typeof(expression()), "scalar") - expect_false(vec_is_vector(quote(foo))) - expect_false(vec_is_vector(pairlist(""))) - expect_false(vec_is_vector(function() NULL)) - expect_false(vec_is_vector(env())) - expect_false(vec_is_vector(~foo)) - expect_false(vec_is_vector(base::`{`)) - expect_false(vec_is_vector(base::c)) - expect_false(vec_is_vector(expression())) + expect_false(obj_is_vector(quote(foo))) + expect_false(obj_is_vector(pairlist(""))) + expect_false(obj_is_vector(function() NULL)) + expect_false(obj_is_vector(env())) + expect_false(obj_is_vector(~foo)) + expect_false(obj_is_vector(base::`{`)) + expect_false(obj_is_vector(base::c)) + expect_false(obj_is_vector(expression())) expect_false(vec_is(quote(foo))) expect_false(vec_is(pairlist(""))) @@ -124,18 +131,42 @@ test_that("non-vector types can be proxied", { x <- new_proxy(1:3) expect_identical(vec_typeof(x), "scalar") - expect_false(vec_is_vector(x)) + expect_false(obj_is_vector(x)) expect_false(vec_is(x)) expect_error(vec_assert(x), class = "vctrs_error_scalar_type") local_env_proxy() expect_identical(vec_typeof(x), "integer") - expect_true(vec_is_vector(x)) + expect_true(obj_is_vector(x)) expect_true(vec_is(x)) expect_error(regexp = NA, vec_assert(x)) }) +test_that("obj_check_vector() is silent on vectors", { + expect_null(obj_check_vector(1)) + expect_null(obj_check_vector(data_frame())) +}) + +test_that("obj_check_vector() errors on scalars", { + expect_snapshot(error = TRUE, { + obj_check_vector(quote(foo)) + }) + expect_snapshot(error = TRUE, { + obj_check_vector(foobar()) + }) +}) + +test_that("obj_check_vector() error respects `arg` and `call`", { + my_check_vector <- function(foo) { + obj_check_vector(foo) + } + + expect_snapshot(error = TRUE, { + my_check_vector(foobar()) + }) +}) + test_that("vec_assert() uses friendly type in error messages", { # Friendly type will be generated in rlang in the future. Upstream # changes should not cause CRAN failures. @@ -227,7 +258,7 @@ test_that("vec_assert() validates `size` (#1470)", { }) test_that("NULL is not a vector", { - expect_false(vec_is_vector(NULL)) + expect_false(obj_is_vector(NULL)) expect_false(vec_is(NULL)) }) @@ -238,6 +269,60 @@ test_that("names and row names do not influence type identity (#707)", { expect_true(vec_is(mtcars, structure(mtcars, row.names = 1:32))) }) +# vec_check_size -------------------------------------------------------- + +test_that("vec_check_size() is silent if the size is right", { + expect_null(vec_check_size(1:5, size = 5L)) + expect_null(vec_check_size(data_frame(.size = 10L), size = 10L)) +}) + +test_that("vec_check_size() errors on the wrong size", { + expect_snapshot(error = TRUE, { + vec_check_size(1:5, size = 1L) + }) + expect_snapshot(error = TRUE, { + vec_check_size(1:5, size = 10L) + }) +}) + +test_that("vec_check_size() errors on scalars", { + expect_snapshot(error = TRUE, { + vec_check_size(quote(foo), size = 1L) + }) + expect_snapshot(error = TRUE, { + vec_check_size(foobar(), size = 1L) + }) +}) + +test_that("vec_check_size() error respects `arg` and `call`", { + my_check_size <- function(foo, size) { + vec_check_size(foo, size) + } + + expect_snapshot(error = TRUE, { + my_check_size(1L, size = 5L) + }) + expect_snapshot(error = TRUE, { + my_check_size(foobar(), size = 5L) + }) +}) + +test_that("vec_check_size() validates `size`", { + expect_snapshot(error = TRUE, { + vec_check_size(1, size = "x") + }) + expect_snapshot(error = TRUE, { + vec_check_size(1, size = c(1L, 2L)) + }) + + # TODO: This should be an error, and we want to know when it changes + # https://github.com/r-lib/rlang/issues/1562 + expect_snapshot(error = TRUE, { + vec_check_size(1, size = 1.5) + abort("`vec_check_size()` should error for us") + }) +}) + # vec_is_list ----------------------------------------------------------- test_that("bare lists are lists", { diff --git a/tests/testthat/test-type-list-of.R b/tests/testthat/test-type-list-of.R index 641254c83..6c2de2ac4 100644 --- a/tests/testthat/test-type-list-of.R +++ b/tests/testthat/test-type-list-of.R @@ -119,7 +119,7 @@ test_that("assingment can increase size of vector", { # Type system ------------------------------------------------------------- test_that("list_of() are vectors", { - expect_true(vec_is_vector(list_of(1))) + expect_true(obj_is_vector(list_of(1))) expect_true(vec_is(list_of(1))) }) From 303b5dd0c5fb5fd811386e1397a6f2b1160485ee Mon Sep 17 00:00:00 2001 From: Davis Vaughan Date: Wed, 15 Feb 2023 11:39:38 -0500 Subject: [PATCH 230/312] Add `error_call` to `vec_slice()` (#1788) * Add `error_call` argument to `vec_slice()` And remove the local-vctrs-error-call infrastructure * NEWS bullet --- NEWS.md | 2 ++ R/conditions.R | 45 +---------------------------- R/slice.R | 9 ++++-- R/subscript-loc.R | 2 +- R/subscript.R | 4 +-- man/vec_slice.Rd | 11 +++++-- src/slice.c | 2 +- tests/testthat/_snaps/error-call.md | 39 +++++++------------------ tests/testthat/test-error-call.R | 24 ++++----------- 9 files changed, 36 insertions(+), 102 deletions(-) diff --git a/NEWS.md b/NEWS.md index bed8662b2..55addec33 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,5 +1,7 @@ # vctrs (development version) +* `vec_slice()` has gained an `error_call` argument (#1785). + * New `obj_is_vector()`, `obj_check_vector()`, and `vec_check_size()` validation helpers. We believe these are a better approach to vector validation than `vec_assert()` and `vec_is()`, which have been marked as questioning because diff --git a/R/conditions.R b/R/conditions.R index c52242e1b..072217cad 100644 --- a/R/conditions.R +++ b/R/conditions.R @@ -65,7 +65,7 @@ stop_vctrs <- function(message = NULL, message, class = c(class, "vctrs_error"), ..., - call = vctrs_error_call(call) + call = call ) } warn_vctrs <- function(message = NULL, @@ -870,46 +870,3 @@ append_arg <- function(x, arg) { x } } - -vctrs_local_error_call <- function(call = frame, frame = caller_env()) { - # This doesn't implement the semantics of a `local_` function - # perfectly in order to be as fast as possible - frame$.__vctrs_error_call__. <- call - invisible(NULL) -} - -vctrs_error_call <- function(call) { - if (is_function(call)) { - call <- call() - } - - if (is_environment(call)) { - caller_call <- get_vctrs_error_call(call) - if (!is_null(caller_call)) { - return(caller_call) - } - } - - call -} - -vctrs_error_borrowed_call <- function(call = caller_env(), - borrower = caller_env(2)) { - borrower_call <- get_vctrs_error_call(borrower) - - if (is_null(borrower_call)) { - call - } else { - borrower_call - } -} - -get_vctrs_error_call <- function(call) { - env_get( - call, - ".__vctrs_error_call__.", - inherit = TRUE, - last = topenv(call), - default = NULL - ) -} diff --git a/R/slice.R b/R/slice.R index e5ceb33bc..c06c9175a 100644 --- a/R/slice.R +++ b/R/slice.R @@ -4,6 +4,9 @@ #' for all vector types, regardless of dimensionality. It is an analog to `[` #' that matches [vec_size()] instead of `length()`. #' +#' @inheritParams rlang::args_dots_empty +#' @inheritParams rlang::args_error_context +#' #' @param x A vector #' @param i An integer, character or logical vector specifying the #' locations or names of the observations to get/set. Specify @@ -16,7 +19,7 @@ #' in error messages to inform the user about the locations of #' incompatible types and sizes (see [stop_incompatible_type()] and #' [stop_incompatible_size()]). -#' @param ... These dots are for future extensions and must be empty. +#' #' @return A vector of the same type as `x`. #' #' @section Genericity: @@ -104,8 +107,8 @@ #' # vector: #' x <- 1:3 #' try(vec_slice(x, 2) <- 1.5) -vec_slice <- function(x, i) { - delayedAssign("call", vctrs_error_borrowed_call()) +vec_slice <- function(x, i, ..., error_call = current_env()) { + check_dots_empty0(...) .Call(ffi_slice, x, i, environment()) } diff --git a/R/subscript-loc.R b/R/subscript-loc.R index 53d7989c3..3e529f027 100644 --- a/R/subscript-loc.R +++ b/R/subscript-loc.R @@ -171,7 +171,7 @@ num_as_location2 <- function(i, check_dots_empty0(...) if (!is_integer(i) && !is_double(i)) { - abort("`i` must be a numeric vector.", call = vctrs_error_call(call)) + abort("`i` must be a numeric vector.", call = call) } result_get(vec_as_location2_result( i, diff --git a/R/subscript.R b/R/subscript.R index e524a2f58..5ffcd9993 100644 --- a/R/subscript.R +++ b/R/subscript.R @@ -145,7 +145,7 @@ stop_subscript <- function(i, class = c(class, "vctrs_error_subscript"), i = i, ..., - call = vctrs_error_call(call) + call = call ) } new_error_subscript <- function(class = NULL, i, ...) { @@ -169,7 +169,7 @@ new_error_subscript_type <- function(i, numeric = numeric, character = character, ..., - call = vctrs_error_call(call) + call = call ) } diff --git a/man/vec_slice.Rd b/man/vec_slice.Rd index 5e1b25631..147a63b6a 100644 --- a/man/vec_slice.Rd +++ b/man/vec_slice.Rd @@ -6,7 +6,7 @@ \alias{vec_assign} \title{Get or set observations in a vector} \usage{ -vec_slice(x, i) +vec_slice(x, i, ..., error_call = current_env()) vec_slice(x, i) <- value @@ -20,12 +20,17 @@ locations or names of the observations to get/set. Specify \code{TRUE} to index all elements (as in \code{x[]}), or \code{NULL}, \code{FALSE} or \code{integer()} to index none (as in \code{x[NULL]}).} +\item{...}{These dots are for future extensions and must be empty.} + +\item{error_call}{The execution environment of a currently +running function, e.g. \code{caller_env()}. The function will be +mentioned in error messages as the source of the error. See the +\code{call} argument of \code{\link[rlang:abort]{abort()}} for more information.} + \item{value}{Replacement values. \code{value} is cast to the type of \code{x}, but only if they have a common type. See below for examples of this rule.} -\item{...}{These dots are for future extensions and must be empty.} - \item{x_arg, value_arg}{Argument names for \code{x} and \code{value}. These are used in error messages to inform the user about the locations of incompatible types and sizes (see \code{\link[=stop_incompatible_type]{stop_incompatible_type()}} and diff --git a/src/slice.c b/src/slice.c index 2da78a3ea..acced87b1 100644 --- a/src/slice.c +++ b/src/slice.c @@ -401,7 +401,7 @@ r_obj* ffi_slice(r_obj* x, struct vec_slice_opts opts = { .x_arg = vec_args.x, .i_arg = vec_args.i, - .call = {.x = r_syms.call, .env = frame} + .call = {.x = r_syms.error_call, .env = frame} }; return vec_slice_opts(x, i, &opts); } diff --git a/tests/testthat/_snaps/error-call.md b/tests/testthat/_snaps/error-call.md index 9fa9ddc08..65b9bbf17 100644 --- a/tests/testthat/_snaps/error-call.md +++ b/tests/testthat/_snaps/error-call.md @@ -277,43 +277,24 @@ Error in `my_function()`: ! Input must be a vector, not a object. -# can take ownership of vctrs errors +# `vec_slice()` uses `error_call` Code - (expect_error(vec_assert(foobar(list())))) + (expect_error(my_function(env(), 1))) Output - Error in `foo()`: - ! `foobar(list())` must be a vector, not a object. - Code - (expect_error(local(vec_assert(foobar(list()))))) - Output - - Error in `foo()`: - ! `foobar(list())` must be a vector, not a object. - Code - (expect_error(vec_cast(1, list()))) - Output - - Error in `foo()`: - ! Can't convert `1` to . - Code - (expect_error(vec_slice(env(), list()))) - Output - - Error in `foo()`: + Error in `my_function()`: ! `x` must be a vector, not an environment. Code - local({ - vctrs_local_error_call(NULL) - (expect_error(vec_slice(env(), list()))) - }) + (expect_error(my_function(1, 2))) Output - - Error in `vec_slice()`: - ! `x` must be a vector, not an environment. + + Error in `my_function()`: + ! Can't subset elements past the end. + i Location 2 doesn't exist. + i There is only 1 element. -# vec_slice() reports error context +# vec_slice() reports self in error context Code (expect_error(vec_slice(foobar(list()), 1))) diff --git a/tests/testthat/test-error-call.R b/tests/testthat/test-error-call.R index bc6279b96..6422fe95d 100644 --- a/tests/testthat/test-error-call.R +++ b/tests/testthat/test-error-call.R @@ -114,29 +114,15 @@ test_that("`vec_ptype()` reports correct error call", { }) }) -test_that("can take ownership of vctrs errors", { - vctrs_local_error_call(call("foo")) - +test_that("`vec_slice()` uses `error_call`", { + my_function <- function(x, i) vec_slice(x, i, error_call = current_env()) expect_snapshot({ - (expect_error(vec_assert(foobar(list())))) - (expect_error(local(vec_assert(foobar(list()))))) - - (expect_error(vec_cast(1, list()))) - - # Suboptimal because `foo()` might not have an `x` argument. It - # might be better to comprehensively check inputs with explicit - # error context and treat all other errors as programming errors. - (expect_error(vec_slice(env(), list()))) - - # This should show `vec_slice()` if no local call - local({ - vctrs_local_error_call(NULL) - (expect_error(vec_slice(env(), list()))) - }) + (expect_error(my_function(env(), 1))) + (expect_error(my_function(1, 2))) }) }) -test_that("vec_slice() reports error context", { +test_that("vec_slice() reports self in error context", { expect_snapshot({ (expect_error(vec_slice(foobar(list()), 1))) (expect_error(vec_slice(list(), env()))) From c1b7b9e10600c8f465271288808f8906829ccbe3 Mon Sep 17 00:00:00 2001 From: Davis Vaughan Date: Wed, 22 Feb 2023 10:08:47 -0500 Subject: [PATCH 231/312] Implement `relationship` for `vec_locate_matches()` (#1791) * Implement `relationship` for `vec_locate_matches()` And silently soft-deprecate `multiple = "error"` and `multiple = "warning"` * NEWS bullet * Remove slightly incorrect comment --- NAMESPACE | 6 + NEWS.md | 7 + R/match.R | 214 +++++++++++++++-- man/vec_locate_matches.Rd | 57 ++++- src/decl/match-decl.h | 33 +++ src/init.c | 4 +- src/match.c | 428 +++++++++++++++++++++++++++++---- src/utils.c | 12 + src/utils.h | 6 + tests/testthat/_snaps/match.md | 260 +++++++++++++++++++- tests/testthat/test-match.R | 339 +++++++++++++++++++++++--- 11 files changed, 1246 insertions(+), 120 deletions(-) diff --git a/NAMESPACE b/NAMESPACE index 4d020d8de..f4350d243 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -95,6 +95,9 @@ S3method(cnd_body,vctrs_error_incompatible_size) S3method(cnd_body,vctrs_error_matches_incomplete) S3method(cnd_body,vctrs_error_matches_multiple) S3method(cnd_body,vctrs_error_matches_nothing) +S3method(cnd_body,vctrs_error_matches_relationship_many_to_one) +S3method(cnd_body,vctrs_error_matches_relationship_one_to_many) +S3method(cnd_body,vctrs_error_matches_relationship_one_to_one) S3method(cnd_body,vctrs_error_matches_remaining) S3method(cnd_body,vctrs_error_names_cannot_be_dot_dot) S3method(cnd_body,vctrs_error_names_cannot_be_empty) @@ -106,6 +109,9 @@ S3method(cnd_header,vctrs_error_incompatible_size) S3method(cnd_header,vctrs_error_matches_incomplete) S3method(cnd_header,vctrs_error_matches_multiple) S3method(cnd_header,vctrs_error_matches_nothing) +S3method(cnd_header,vctrs_error_matches_relationship_many_to_one) +S3method(cnd_header,vctrs_error_matches_relationship_one_to_many) +S3method(cnd_header,vctrs_error_matches_relationship_one_to_one) S3method(cnd_header,vctrs_error_matches_remaining) S3method(cnd_header,vctrs_error_names_cannot_be_dot_dot) S3method(cnd_header,vctrs_error_names_cannot_be_empty) diff --git a/NEWS.md b/NEWS.md index 55addec33..a0aefa844 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,5 +1,12 @@ # vctrs (development version) +* `vec_locate_matches()` gains a new `relationship` argument that holistically + handles multiple matches between `needles` and `haystack`. In particular, + `relationship = "many_to_one"` replaces `multiple = "error"` and + `multiple = "warning"`, which have been removed from the documentation and + silently soft-deprecated. Official deprecation for those options will start in + a future release (#1791). + * `vec_slice()` has gained an `error_call` argument (#1785). * New `obj_is_vector()`, `obj_check_vector()`, and `vec_check_size()` validation diff --git a/R/match.R b/R/match.R index 19142bd42..a51a2ad57 100644 --- a/R/match.R +++ b/R/match.R @@ -108,9 +108,43 @@ #' `"last"` if you just need to detect if there is at least one match. #' - `"first"` returns the first match detected in `haystack`. #' - `"last"` returns the last match detected in `haystack`. -#' - `"warning"` throws a warning if multiple matches are detected, but -#' otherwise falls back to `"all"`. -#' - `"error"` throws an error if multiple matches are detected. +#' +#' @param relationship Handling of the expected relationship between +#' `needles` and `haystack`. If the expectations chosen from the list below +#' are invalidated, an error is thrown. +#' +#' - `"none"` doesn't perform any relationship checks. +#' +#' - `"one_to_one"` expects: +#' - Each value in `needles` matches at most 1 value in `haystack`. +#' - Each value in `haystack` matches at most 1 value in `needles`. +#' +#' - `"one_to_many"` expects: +#' - Each value in `needles` matches any number of values in `haystack`. +#' - Each value in `haystack` matches at most 1 value in `needles`. +#' +#' - `"many_to_one"` expects: +#' - Each value in `needles` matches at most 1 value in `haystack`. +#' - Each value in `haystack` matches any number of values in `needles`. +#' +#' - `"many_to_many"` expects: +#' - Each value in `needles` matches any number of values in `haystack`. +#' - Each value in `haystack` matches any number of values in `needles`. +#' +#' This performs no checks, and is identical to `"none"`, but is provided to +#' allow you to be explicit about this relationship if you know it exists. +#' +#' - `"warn_many_to_many"` doesn't assume there is any known relationship, but +#' will warn if `needles` and `haystack` have a many-to-many relationship +#' (which is typically unexpected), encouraging you to either take a closer +#' look at your inputs or make this relationship explicit by specifying +#' `"many_to_many"`. +#' +#' `relationship` is applied after `filter` and `multiple` to allow potential +#' multiple matches to be filtered out first. +#' +#' `relationship` doesn't handle cases where there are zero matches. For that, +#' see `no_match` and `remaining`. #' #' @param needles_arg,haystack_arg Argument tags for `needles` and `haystack` #' used in error messages. @@ -141,7 +175,13 @@ #' vec_locate_matches(x, y, multiple = "first") #' vec_locate_matches(x, y, multiple = "last") #' vec_locate_matches(x, y, multiple = "any") -#' try(vec_locate_matches(x, y, multiple = "error")) +#' +#' # Use `relationship` to add constraints and error on multiple matches if +#' # they aren't expected +#' try(vec_locate_matches(x, y, relationship = "one_to_one")) +#' +#' # In this case, the `NA` in `y` matches two rows in `x` +#' try(vec_locate_matches(x, y, relationship = "one_to_many")) #' #' # By default, NA is treated as being identical to NaN. #' # Using `nan_distinct = TRUE` treats NA and NaN as different values, so NA @@ -153,6 +193,10 @@ #' # in `needles`. #' vec_locate_matches(x, y, incomplete = NA) #' +#' # Using `incomplete = NA` allows us to enforce the one-to-many relationship +#' # that we couldn't before +#' vec_locate_matches(x, y, relationship = "one_to_many", incomplete = NA) +#' #' # `no_match` allows you to specify the returned value for a needle with #' # zero matches. Note that this is different from an incomplete value, #' # so specifying `no_match` allows you to differentiate between incomplete @@ -239,6 +283,7 @@ vec_locate_matches <- function(needles, no_match = NA_integer_, remaining = "drop", multiple = "all", + relationship = "none", nan_distinct = FALSE, chr_proxy_collate = NULL, needles_arg = "", @@ -257,6 +302,7 @@ vec_locate_matches <- function(needles, no_match, remaining, multiple, + relationship, nan_distinct, chr_proxy_collate, needles_arg, @@ -419,47 +465,173 @@ stop_matches_multiple <- function(i, needles_arg, haystack_arg, call) { cnd_header.vctrs_error_matches_multiple <- function(cnd, ...) { cnd_matches_multiple_header(cnd$needles_arg, cnd$haystack_arg) } -cnd_matches_multiple_header <- function(needles_arg, haystack_arg) { - if (nzchar(needles_arg)) { - needles_name <- glue::glue(" of `{needles_arg}` ") + +#' @export +cnd_body.vctrs_error_matches_multiple <- function(cnd, ...) { + cnd_matches_multiple_body(cnd$i) +} + +# ------------------------------------------------------------------------------ + +warn_matches_multiple <- function(i, needles_arg, haystack_arg, call) { + message <- paste( + cnd_matches_multiple_header(needles_arg, haystack_arg), + cnd_matches_multiple_body(i), + sep = "\n" + ) + + warn_matches( + message = message, + class = "vctrs_warning_matches_multiple", + i = i, + needles_arg = needles_arg, + haystack_arg = haystack_arg, + call = call + ) +} + +# ------------------------------------------------------------------------------ + +stop_matches_relationship_one_to_one <- function(i, which, needles_arg, haystack_arg, call) { + stop_matches_relationship( + class = "vctrs_error_matches_relationship_one_to_one", + i = i, + which = which, + needles_arg = needles_arg, + haystack_arg = haystack_arg, + call = call + ) +} + +#' @export +cnd_header.vctrs_error_matches_relationship_one_to_one <- function(cnd, ...) { + if (cnd$which == "needles") { + cnd_matches_multiple_header(cnd$needles_arg, cnd$haystack_arg) } else { - needles_name <- " " + cnd_matches_multiple_header(cnd$haystack_arg, cnd$needles_arg) } +} - if (nzchar(haystack_arg)) { - haystack_name <- glue::glue(" from `{haystack_arg}`") +#' @export +cnd_body.vctrs_error_matches_relationship_one_to_one <- function(cnd, ...) { + if (cnd$which == "needles") { + cnd_matches_multiple_body(cnd$i, cnd$needles_arg) } else { - haystack_name <- "" + cnd_matches_multiple_body(cnd$i, cnd$haystack_arg) } +} + - glue::glue("Each element{needles_name}can match at most 1 observation{haystack_name}.") +stop_matches_relationship_one_to_many <- function(i, needles_arg, haystack_arg, call) { + stop_matches_relationship( + class = "vctrs_error_matches_relationship_one_to_many", + i = i, + needles_arg = needles_arg, + haystack_arg = haystack_arg, + call = call + ) } #' @export -cnd_body.vctrs_error_matches_multiple <- function(cnd, ...) { - cnd_matches_multiple_body(cnd$i) +cnd_header.vctrs_error_matches_relationship_one_to_many <- function(cnd, ...) { + cnd_matches_multiple_header(cnd$haystack_arg, cnd$needles_arg) +} + +#' @export +cnd_body.vctrs_error_matches_relationship_one_to_many <- function(cnd, ...) { + cnd_matches_multiple_body(cnd$i, cnd$haystack_arg) +} + + +stop_matches_relationship_many_to_one <- function(i, needles_arg, haystack_arg, call) { + stop_matches_relationship( + class = "vctrs_error_matches_relationship_many_to_one", + i = i, + needles_arg = needles_arg, + haystack_arg = haystack_arg, + call = call + ) +} + +#' @export +cnd_header.vctrs_error_matches_relationship_many_to_one <- function(cnd, ...) { + cnd_matches_multiple_header(cnd$needles_arg, cnd$haystack_arg) +} + +#' @export +cnd_body.vctrs_error_matches_relationship_many_to_one <- function(cnd, ...) { + cnd_matches_multiple_body(cnd$i, cnd$needles_arg) +} + + +stop_matches_relationship <- function(class = NULL, ..., call = caller_env()) { + stop_matches( + class = c(class, "vctrs_error_matches_relationship"), + ..., + call = call + ) +} + +cnd_matches_multiple_header <- function(x_arg, y_arg) { + if (nzchar(x_arg)) { + x_name <- glue::glue(" of `{x_arg}` ") + } else { + x_name <- " " + } + + if (nzchar(y_arg)) { + y_name <- glue::glue(" from `{y_arg}`") + } else { + y_name <- "" + } + + glue::glue("Each element{x_name}can match at most 1 observation{y_name}.") } -cnd_matches_multiple_body <- function(i) { - bullet <- glue::glue("The element at location {i} has multiple matches.") + +cnd_matches_multiple_body <- function(i, name = "") { + if (nzchar(name)) { + bullet <- glue::glue("The element of `{name}` at location {i} has multiple matches.") + } else { + bullet <- glue::glue("The element at location {i} has multiple matches.") + } bullet <- c(x = bullet) format_error_bullets(bullet) } # ------------------------------------------------------------------------------ -warn_matches_multiple <- function(i, needles_arg, haystack_arg, call) { +warn_matches_relationship_many_to_many <- function(i, j, needles_arg, haystack_arg, call) { + if (nzchar(needles_arg) && nzchar(haystack_arg)) { + name_needles_and_haystack <- glue::glue(" between `{needles_arg}` and `{haystack_arg}`") + } else { + name_needles_and_haystack <- "" + } + + header <- glue::glue("Detected an unexpected many-to-many relationship{name_needles_and_haystack}.") + message <- paste( - cnd_matches_multiple_header(needles_arg, haystack_arg), - cnd_matches_multiple_body(i), + header, + cnd_matches_multiple_body(i, needles_arg), + cnd_matches_multiple_body(j, haystack_arg), sep = "\n" ) - warn_matches( + warn_matches_relationship( message = message, - class = "vctrs_warning_matches_multiple", + class = "vctrs_warning_matches_relationship_many_to_many", i = i, + j = j, needles_arg = needles_arg, haystack_arg = haystack_arg, call = call ) } + +warn_matches_relationship <- function(message, class = NULL, ..., call = caller_env()) { + warn_matches( + message = message, + class = c(class, "vctrs_warning_matches_relationship"), + ..., + call = call + ) +} diff --git a/man/vec_locate_matches.Rd b/man/vec_locate_matches.Rd index 95108cf00..1a0d8d19b 100644 --- a/man/vec_locate_matches.Rd +++ b/man/vec_locate_matches.Rd @@ -14,6 +14,7 @@ vec_locate_matches( no_match = NA_integer_, remaining = "drop", multiple = "all", + relationship = "none", nan_distinct = FALSE, chr_proxy_collate = NULL, needles_arg = "", @@ -108,11 +109,49 @@ which match will be returned. It is often faster than \code{"first"} and \code{"last"} if you just need to detect if there is at least one match. \item \code{"first"} returns the first match detected in \code{haystack}. \item \code{"last"} returns the last match detected in \code{haystack}. -\item \code{"warning"} throws a warning if multiple matches are detected, but -otherwise falls back to \code{"all"}. -\item \code{"error"} throws an error if multiple matches are detected. }} +\item{relationship}{Handling of the expected relationship between +\code{needles} and \code{haystack}. If the expectations chosen from the list below +are invalidated, an error is thrown. +\itemize{ +\item \code{"none"} doesn't perform any relationship checks. +\item \code{"one_to_one"} expects: +\itemize{ +\item Each value in \code{needles} matches at most 1 value in \code{haystack}. +\item Each value in \code{haystack} matches at most 1 value in \code{needles}. +} +\item \code{"one_to_many"} expects: +\itemize{ +\item Each value in \code{needles} matches any number of values in \code{haystack}. +\item Each value in \code{haystack} matches at most 1 value in \code{needles}. +} +\item \code{"many_to_one"} expects: +\itemize{ +\item Each value in \code{needles} matches at most 1 value in \code{haystack}. +\item Each value in \code{haystack} matches any number of values in \code{needles}. +} +\item \code{"many_to_many"} expects: +\itemize{ +\item Each value in \code{needles} matches any number of values in \code{haystack}. +\item Each value in \code{haystack} matches any number of values in \code{needles}. +} + +This performs no checks, and is identical to \code{"none"}, but is provided to +allow you to be explicit about this relationship if you know it exists. +\item \code{"warn_many_to_many"} doesn't assume there is any known relationship, but +will warn if \code{needles} and \code{haystack} have a many-to-many relationship +(which is typically unexpected), encouraging you to either take a closer +look at your inputs or make this relationship explicit by specifying +\code{"many_to_many"}. +} + +\code{relationship} is applied after \code{filter} and \code{multiple} to allow potential +multiple matches to be filtered out first. + +\code{relationship} doesn't handle cases where there are zero matches. For that, +see \code{no_match} and \code{remaining}.} + \item{nan_distinct}{A single logical specifying whether or not \code{NaN} should be considered distinct from \code{NA} for double and complex vectors. If \code{TRUE}, \code{NaN} will always be ordered between \code{NA} and non-missing numbers.} @@ -207,7 +246,13 @@ data_frame( vec_locate_matches(x, y, multiple = "first") vec_locate_matches(x, y, multiple = "last") vec_locate_matches(x, y, multiple = "any") -try(vec_locate_matches(x, y, multiple = "error")) + +# Use `relationship` to add constraints and error on multiple matches if +# they aren't expected +try(vec_locate_matches(x, y, relationship = "one_to_one")) + +# In this case, the `NA` in `y` matches two rows in `x` +try(vec_locate_matches(x, y, relationship = "one_to_many")) # By default, NA is treated as being identical to NaN. # Using `nan_distinct = TRUE` treats NA and NaN as different values, so NA @@ -219,6 +264,10 @@ vec_locate_matches(x, y, nan_distinct = TRUE) # in `needles`. vec_locate_matches(x, y, incomplete = NA) +# Using `incomplete = NA` allows us to enforce the one-to-many relationship +# that we couldn't before +vec_locate_matches(x, y, relationship = "one_to_many", incomplete = NA) + # `no_match` allows you to specify the returned value for a needle with # zero matches. Note that this is different from an incomplete value, # so specifying `no_match` allows you to differentiate between incomplete diff --git a/src/decl/match-decl.h b/src/decl/match-decl.h index d7b4b03e3..e2e12868e 100644 --- a/src/decl/match-decl.h +++ b/src/decl/match-decl.h @@ -18,6 +18,7 @@ r_obj* vec_locate_matches(r_obj* needles, const struct vctrs_no_match* no_match, const struct vctrs_remaining* remaining, enum vctrs_multiple multiple, + enum vctrs_relationship relationship, bool nan_distinct, r_obj* chr_proxy_collate, struct vctrs_arg* needles_arg, @@ -35,6 +36,7 @@ r_obj* df_locate_matches(r_obj* needles, const struct vctrs_no_match* no_match, const struct vctrs_remaining* remaining, enum vctrs_multiple multiple, + enum vctrs_relationship relationship, bool any_filters, const enum vctrs_filter* v_filters, const enum vctrs_ops* v_ops, @@ -144,6 +146,10 @@ static inline enum vctrs_multiple parse_multiple(r_obj* multiple, struct r_lazy call); +static inline +enum vctrs_relationship parse_relationship(r_obj* relationship, + struct r_lazy call); + static inline void parse_filter(r_obj* filter, r_ssize n_cols, enum vctrs_filter* v_filters); @@ -158,6 +164,7 @@ r_obj* expand_compact_indices(const int* v_o_haystack, const struct vctrs_no_match* no_match, const struct vctrs_remaining* remaining, enum vctrs_multiple multiple, + enum vctrs_relationship relationship, r_ssize size_needles, r_ssize size_haystack, bool any_non_equi, @@ -237,3 +244,29 @@ void warn_matches_multiple(r_ssize i, struct vctrs_arg* needles_arg, struct vctrs_arg* haystack_arg, struct r_lazy call); + +static inline +void stop_matches_relationship_one_to_one(r_ssize i, + const char* which, + struct vctrs_arg* needles_arg, + struct vctrs_arg* haystack_arg, + struct r_lazy call); + +static inline +void stop_matches_relationship_one_to_many(r_ssize i, + struct vctrs_arg* needles_arg, + struct vctrs_arg* haystack_arg, + struct r_lazy call); + +static inline +void stop_matches_relationship_many_to_one(r_ssize i, + struct vctrs_arg* needles_arg, + struct vctrs_arg* haystack_arg, + struct r_lazy call); + +static inline +void warn_matches_relationship_many_to_many(r_ssize i, + r_ssize j, + struct vctrs_arg* needles_arg, + struct vctrs_arg* haystack_arg, + struct r_lazy call); diff --git a/src/init.c b/src/init.c index 6923f608e..75cb9505f 100644 --- a/src/init.c +++ b/src/init.c @@ -143,7 +143,7 @@ extern r_obj* vctrs_list_drop_empty(r_obj*); extern r_obj* vctrs_is_altrep(r_obj* x); extern r_obj* ffi_interleave_indices(r_obj*, r_obj*); extern r_obj* ffi_compute_nesting_container_info(r_obj*, r_obj*); -extern r_obj* ffi_locate_matches(r_obj*, r_obj*, r_obj*, r_obj*, r_obj*, r_obj*, r_obj*, r_obj*, r_obj*, r_obj*, r_obj*, r_obj*, r_obj*); +extern r_obj* ffi_locate_matches(r_obj*, r_obj*, r_obj*, r_obj*, r_obj*, r_obj*, r_obj*, r_obj*, r_obj*, r_obj*, r_obj*, r_obj*, r_obj*, r_obj*); extern r_obj* ffi_interval_groups(r_obj*, r_obj*, r_obj*, r_obj*); extern r_obj* ffi_interval_locate_groups(r_obj*, r_obj*, r_obj*, r_obj*); extern r_obj* ffi_interval_complement(r_obj*, r_obj*, r_obj*, r_obj*); @@ -326,7 +326,7 @@ static const R_CallMethodDef CallEntries[] = { {"vctrs_is_altrep", (DL_FUNC) &vctrs_is_altrep, 1}, {"ffi_interleave_indices", (DL_FUNC) &ffi_interleave_indices, 2}, {"ffi_compute_nesting_container_info", (DL_FUNC) &ffi_compute_nesting_container_info, 2}, - {"ffi_locate_matches", (DL_FUNC) &ffi_locate_matches, 13}, + {"ffi_locate_matches", (DL_FUNC) &ffi_locate_matches, 14}, {"ffi_interval_groups", (DL_FUNC) &ffi_interval_groups, 4}, {"ffi_interval_locate_groups", (DL_FUNC) &ffi_interval_locate_groups, 4}, {"ffi_interval_complement", (DL_FUNC) &ffi_interval_complement, 4}, diff --git a/src/match.c b/src/match.c index dabea1b62..793e2ad2e 100644 --- a/src/match.c +++ b/src/match.c @@ -4,11 +4,22 @@ enum vctrs_multiple { VCTRS_MULTIPLE_all = 0, - VCTRS_MULTIPLE_warning = 1, - VCTRS_MULTIPLE_error = 2, - VCTRS_MULTIPLE_first = 3, - VCTRS_MULTIPLE_last = 4, - VCTRS_MULTIPLE_any = 5 + VCTRS_MULTIPLE_any = 1, + VCTRS_MULTIPLE_first = 2, + VCTRS_MULTIPLE_last = 3, + + // Deprecated in favor of `relationship` + VCTRS_MULTIPLE_warning = 4, + VCTRS_MULTIPLE_error = 5 +}; + +enum vctrs_relationship { + VCTRS_RELATIONSHIP_none = 0, + VCTRS_RELATIONSHIP_one_to_one = 1, + VCTRS_RELATIONSHIP_one_to_many = 2, + VCTRS_RELATIONSHIP_many_to_one = 3, + VCTRS_RELATIONSHIP_many_to_many = 4, + VCTRS_RELATIONSHIP_warn_many_to_many = 5 }; enum vctrs_filter { @@ -80,6 +91,7 @@ r_obj* ffi_locate_matches(r_obj* needles, r_obj* no_match, r_obj* remaining, r_obj* multiple, + r_obj* relationship, r_obj* nan_distinct, r_obj* chr_proxy_collate, r_obj* needles_arg, @@ -92,6 +104,7 @@ r_obj* ffi_locate_matches(r_obj* needles, const struct vctrs_no_match c_no_match = parse_no_match(no_match, internal_call); const struct vctrs_remaining c_remaining = parse_remaining(remaining, internal_call); const enum vctrs_multiple c_multiple = parse_multiple(multiple, internal_call); + const enum vctrs_relationship c_relationship = parse_relationship(relationship, internal_call); const bool c_nan_distinct = r_arg_as_bool(nan_distinct, "nan_distinct"); struct vctrs_arg c_needles_arg = vec_as_arg(needles_arg); @@ -106,6 +119,7 @@ r_obj* ffi_locate_matches(r_obj* needles, &c_no_match, &c_remaining, c_multiple, + c_relationship, c_nan_distinct, chr_proxy_collate, &c_needles_arg, @@ -123,6 +137,7 @@ r_obj* vec_locate_matches(r_obj* needles, const struct vctrs_no_match* no_match, const struct vctrs_remaining* remaining, enum vctrs_multiple multiple, + enum vctrs_relationship relationship, bool nan_distinct, r_obj* chr_proxy_collate, struct vctrs_arg* needles_arg, @@ -228,6 +243,7 @@ r_obj* vec_locate_matches(r_obj* needles, no_match, remaining, multiple, + relationship, any_filters, v_filters, v_ops, @@ -253,6 +269,7 @@ r_obj* df_locate_matches(r_obj* needles, const struct vctrs_no_match* no_match, const struct vctrs_remaining* remaining, enum vctrs_multiple multiple, + enum vctrs_relationship relationship, bool any_filters, const enum vctrs_filter* v_filters, const enum vctrs_ops* v_ops, @@ -448,6 +465,7 @@ r_obj* df_locate_matches(r_obj* needles, no_match, remaining, multiple, + relationship, size_needles, size_haystack, any_non_equi, @@ -1365,12 +1383,36 @@ enum vctrs_multiple parse_multiple(r_obj* multiple, struct r_lazy call) { if (!strcmp(c_multiple, "any")) return VCTRS_MULTIPLE_any; if (!strcmp(c_multiple, "first")) return VCTRS_MULTIPLE_first; if (!strcmp(c_multiple, "last")) return VCTRS_MULTIPLE_last; + // TODO: Remove deprecated support for `multiple = "error"/"warning"` if (!strcmp(c_multiple, "warning")) return VCTRS_MULTIPLE_warning; if (!strcmp(c_multiple, "error")) return VCTRS_MULTIPLE_error; r_abort_lazy_call( call, - "`multiple` must be one of \"all\", \"any\", \"first\", \"last\", \"warning\", or \"error\"." + "`multiple` must be one of \"all\", \"any\", \"first\", or \"last\"." + ); +} + +// ----------------------------------------------------------------------------- + +static inline +enum vctrs_relationship parse_relationship(r_obj* relationship, struct r_lazy call) { + if (!r_is_string(relationship)) { + r_abort_lazy_call(call, "`relationship` must be a string."); + } + + const char* c_relationship = r_chr_get_c_string(relationship, 0); + + if (!strcmp(c_relationship, "none")) return VCTRS_RELATIONSHIP_none; + if (!strcmp(c_relationship, "one_to_one")) return VCTRS_RELATIONSHIP_one_to_one; + if (!strcmp(c_relationship, "one_to_many")) return VCTRS_RELATIONSHIP_one_to_many; + if (!strcmp(c_relationship, "many_to_one")) return VCTRS_RELATIONSHIP_many_to_one; + if (!strcmp(c_relationship, "many_to_many")) return VCTRS_RELATIONSHIP_many_to_many; + if (!strcmp(c_relationship, "warn_many_to_many")) return VCTRS_RELATIONSHIP_warn_many_to_many; + + r_abort_lazy_call( + call, + "`relationship` must be one of \"none\", \"one_to_one\", \"one_to_many\", \"many_to_one\", \"many_to_many\", or \"warn_many_to_many\"." ); } @@ -1556,6 +1598,7 @@ r_obj* expand_compact_indices(const int* v_o_haystack, const struct vctrs_no_match* no_match, const struct vctrs_remaining* remaining, enum vctrs_multiple multiple, + enum vctrs_relationship relationship, r_ssize size_needles, r_ssize size_haystack, bool any_non_equi, @@ -1626,25 +1669,58 @@ r_obj* expand_compact_indices(const int* v_o_haystack, v_o_loc_needles = r_int_cbegin(o_loc_needles); } - const bool retain_remaining_haystack = (remaining->action != VCTRS_REMAINING_ACTION_drop); - int* v_detect_remaining_haystack = NULL; - if (retain_remaining_haystack) { - r_obj* detect_remaining_haystack = KEEP_N(r_alloc_integer(size_haystack), &n_prot); - v_detect_remaining_haystack = r_int_begin(detect_remaining_haystack); + bool any_multiple_needles = false; + bool any_multiple_haystack = false; - for (r_ssize i = 0; i < size_haystack; ++i) { - // Initialize to "remaining" (i.e. this haystack value wasn't matched) - v_detect_remaining_haystack[i] = 1; - } - } + r_ssize loc_first_multiple_needles = -1; + r_ssize loc_first_multiple_haystack = -1; - bool any_multiple = false; - bool check_for_multiple = + // Check is always needed for `multiple = "all"`. + // This also handles `relationship` options too, since if `multiple` is + // `"any"`, `"first"`, or `"last"`, we can't invalidate a `relationship`. + bool check_multiple_needles = multiple == VCTRS_MULTIPLE_all || + // TODO: Remove deprecated support for `multiple = "error"/"warning"` multiple == VCTRS_MULTIPLE_error || multiple == VCTRS_MULTIPLE_warning; - // For multiple = "first" / "last" + bool check_multiple_haystack = false; + switch (relationship) { + // Expecting `haystack` can match any number of `needles` + case VCTRS_RELATIONSHIP_none: + case VCTRS_RELATIONSHIP_many_to_one: + case VCTRS_RELATIONSHIP_many_to_many: { + check_multiple_haystack = false; + break; + } + // Expecting `haystack` to match at most 1 `needles` + case VCTRS_RELATIONSHIP_one_to_one: + case VCTRS_RELATIONSHIP_one_to_many: { + check_multiple_haystack = true; + break; + } + // Only check for multiple matches in `haystack` if we are also checking + // for them in `needles`. Otherwise we can't possibly have a many-to-many + // issue so there is no need to check for one. + case VCTRS_RELATIONSHIP_warn_many_to_many: { + check_multiple_haystack = check_multiple_needles; + break; + } + } + + const bool retain_remaining_haystack = + remaining->action == VCTRS_REMAINING_ACTION_value || + remaining->action == VCTRS_REMAINING_ACTION_error; + + bool track_matches_haystack = check_multiple_haystack || retain_remaining_haystack; + bool* v_detect_matches_haystack = NULL; + if (track_matches_haystack) { + r_obj* detect_matches_haystack = KEEP_N(r_alloc_raw(size_haystack * sizeof(bool)), &n_prot); + v_detect_matches_haystack = r_raw_begin(detect_matches_haystack); + memset(v_detect_matches_haystack, 0, size_haystack * sizeof(bool)); + } + + // For `multiple = "first" / "last"` r_ssize loc_haystack_overall = r_globals.na_int; r_ssize loc_out = 0; @@ -1747,23 +1823,74 @@ r_obj* expand_compact_indices(const int* v_o_haystack, } } - if (check_for_multiple) { + if (check_multiple_needles) { if (loc < size_needles) { - any_multiple = size_match > 1; + any_multiple_needles = size_match > 1; } else { // Guaranteed second match if in the "extra" matches section - any_multiple = true; + any_multiple_needles = true; } - if (any_multiple) { - if (multiple == VCTRS_MULTIPLE_error) { - stop_matches_multiple(loc_needles, needles_arg, haystack_arg, error_call); - } else if (multiple == VCTRS_MULTIPLE_warning) { - warn_matches_multiple(loc_needles, needles_arg, haystack_arg, error_call); + if (any_multiple_needles) { + loc_first_multiple_needles = loc_needles; + + switch (relationship) { + case VCTRS_RELATIONSHIP_one_to_one: + stop_matches_relationship_one_to_one( + loc_first_multiple_needles, + "needles", + needles_arg, + haystack_arg, + error_call + ); + case VCTRS_RELATIONSHIP_many_to_one: + stop_matches_relationship_many_to_one( + loc_first_multiple_needles, + needles_arg, + haystack_arg, + error_call + ); + case VCTRS_RELATIONSHIP_warn_many_to_many: { + if (any_multiple_haystack) { + warn_matches_relationship_many_to_many( + loc_first_multiple_needles, + loc_first_multiple_haystack, + needles_arg, + haystack_arg, + error_call + ); + } + break; + } + default: { + switch (multiple) { + case VCTRS_MULTIPLE_all: + break; + // TODO: Remove deprecated support for `multiple = "error"/"warning"` + case VCTRS_MULTIPLE_error: + stop_matches_multiple( + loc_first_multiple_needles, + needles_arg, + haystack_arg, + error_call + ); + case VCTRS_MULTIPLE_warning: { + warn_matches_multiple( + loc_first_multiple_needles, + needles_arg, + haystack_arg, + error_call + ); + break; + } + default: + r_stop_internal("`check_multiple_needles` should have been false."); + } + } } // We know there are multiple and don't need to continue checking - check_for_multiple = false; + check_multiple_needles = false; } } @@ -1829,9 +1956,44 @@ r_obj* expand_compact_indices(const int* v_o_haystack, v_out_needles[loc_out] = loc_needles + 1; v_out_haystack[loc_out] = loc_haystack_overall + 1; - if (retain_remaining_haystack) { - // This haystack value was a match, so it isn't "remaining" - v_detect_remaining_haystack[loc_haystack_overall] = 0; + if (track_matches_haystack) { + if (check_multiple_haystack) { + // `true` if a match already existed + any_multiple_haystack = v_detect_matches_haystack[loc_haystack_overall]; + + if (any_multiple_haystack) { + loc_first_multiple_haystack = loc_haystack_overall; + + switch (relationship) { + case VCTRS_RELATIONSHIP_one_to_one: + stop_matches_relationship_one_to_one( + loc_first_multiple_haystack, + "haystack", + needles_arg, + haystack_arg, + error_call + ); + case VCTRS_RELATIONSHIP_one_to_many: + stop_matches_relationship_one_to_many( + loc_first_multiple_haystack, + needles_arg, + haystack_arg, + error_call + ); + case VCTRS_RELATIONSHIP_warn_many_to_many: + r_stop_internal( + "`relationship = 'warn_many_to_many'` with " + "`multiple = 'first'/'last' should have resulted in " + "`check_multiple_haystack = false`." + ); + default: + r_stop_internal("`check_multiple_haystack` should have been false."); + } + } + } + + // This haystack value was a match, so it isn't "remaining". + v_detect_matches_haystack[loc_haystack_overall] = true; } ++loc_out; @@ -1850,9 +2012,57 @@ r_obj* expand_compact_indices(const int* v_o_haystack, v_out_needles[loc_out] = loc_needles + 1; v_out_haystack[loc_out] = loc_haystack + 1; - if (retain_remaining_haystack) { - // This haystack value was a match, so it isn't "remaining" - v_detect_remaining_haystack[loc_haystack] = 0; + if (track_matches_haystack) { + if (check_multiple_haystack) { + // `true` if a match already existed + any_multiple_haystack = v_detect_matches_haystack[loc_haystack]; + + if (any_multiple_haystack) { + loc_first_multiple_haystack = loc_haystack; + + switch (relationship) { + case VCTRS_RELATIONSHIP_one_to_one: + stop_matches_relationship_one_to_one( + loc_first_multiple_haystack, + "haystack", + needles_arg, + haystack_arg, + error_call + ); + case VCTRS_RELATIONSHIP_one_to_many: + stop_matches_relationship_one_to_many( + loc_first_multiple_haystack, + needles_arg, + haystack_arg, + error_call + ); + case VCTRS_RELATIONSHIP_warn_many_to_many: { + if (any_multiple_needles) { + warn_matches_relationship_many_to_many( + loc_first_multiple_needles, + loc_first_multiple_haystack, + needles_arg, + haystack_arg, + error_call + ); + } + + // We know there are multiple and don't need to continue checking + check_multiple_haystack = false; + + // Only continue tracking if needed for `remaining` + track_matches_haystack = retain_remaining_haystack; + + break; + } + default: + r_stop_internal("`check_multiple_haystack` should have been false."); + } + } + } + + // This haystack value was a match, so it isn't "remaining". + v_detect_matches_haystack[loc_haystack] = true; } ++loc_out; @@ -1881,7 +2091,7 @@ r_obj* expand_compact_indices(const int* v_o_haystack, v_out_haystack = r_int_begin(out_haystack); } - if (any_multiple && any_non_equi) { + if (any_multiple_needles && any_non_equi) { // If we had multiple matches and we were doing a non-equi join, then // the needles column will be correct, but any group of multiple matches in // the haystack column will be ordered incorrectly within the needle group. @@ -1914,19 +2124,24 @@ r_obj* expand_compact_indices(const int* v_o_haystack, if (retain_remaining_haystack) { r_ssize n_remaining_haystack = 0; - for (r_ssize i = 0; i < size_haystack; ++i) { - if (!v_detect_remaining_haystack[i]) { - continue; + switch (remaining->action) { + case VCTRS_REMAINING_ACTION_error: { + for (r_ssize i = 0; i < size_haystack; ++i) { + if (!v_detect_matches_haystack[i]) { + stop_matches_remaining(i, needles_arg, haystack_arg, error_call); + } } - - if (remaining->action == VCTRS_REMAINING_ACTION_error) { - stop_matches_remaining(i, needles_arg, haystack_arg, error_call); + break; + } + case VCTRS_REMAINING_ACTION_value: { + for (r_ssize i = 0; i < size_haystack; ++i) { + n_remaining_haystack += !v_detect_matches_haystack[i]; } - - // Overwrite with location, this moves all "remaining" locations to the - // front so we can loop over them sequentially - v_detect_remaining_haystack[n_remaining_haystack] = i; - ++n_remaining_haystack; + break; + } + case VCTRS_REMAINING_ACTION_drop: { + r_stop_internal("`remaining` should never be 'drop' here."); + } } if (n_remaining_haystack > 0) { @@ -1942,9 +2157,17 @@ r_obj* expand_compact_indices(const int* v_o_haystack, v_out_haystack = r_int_begin(out_haystack); // Add in "remaining" values at the end of the output - for (r_ssize i = size_out, j = 0; i < new_size_out; ++i, ++j) { + for (r_ssize i = size_out; i < new_size_out; ++i) { v_out_needles[i] = remaining->value; - v_out_haystack[i] = v_detect_remaining_haystack[j] + 1; + } + + r_ssize j = size_out; + + for (r_ssize i = 0; i < size_haystack; ++i) { + if (!v_detect_matches_haystack[i]) { + v_out_haystack[j] = i + 1; + ++j; + } } size_out = new_size_out; @@ -2537,6 +2760,115 @@ void warn_matches_multiple(r_ssize i, FREE(5); } +static inline +void stop_matches_relationship_one_to_one(r_ssize i, + const char* which, + struct vctrs_arg* needles_arg, + struct vctrs_arg* haystack_arg, + struct r_lazy call) { + r_obj* syms[6] = { + syms_i, + syms_which, + syms_needles_arg, + syms_haystack_arg, + syms_call, + NULL + }; + r_obj* args[6] = { + KEEP(r_int((int)i + 1)), + KEEP(r_chr(which)), + KEEP(vctrs_arg(needles_arg)), + KEEP(vctrs_arg(haystack_arg)), + KEEP(r_lazy_eval_protect(call)), + NULL + }; + + r_obj* ffi_call = KEEP(r_call_n(syms_stop_matches_relationship_one_to_one, syms, args)); + Rf_eval(ffi_call, vctrs_ns_env); + + never_reached("stop_matches_relationship_one_to_one"); +} + +static inline +void stop_matches_relationship_one_to_many(r_ssize i, + struct vctrs_arg* needles_arg, + struct vctrs_arg* haystack_arg, + struct r_lazy call) { + r_obj* syms[5] = { + syms_i, + syms_needles_arg, + syms_haystack_arg, + syms_call, + NULL + }; + r_obj* args[5] = { + KEEP(r_int((int)i + 1)), + KEEP(vctrs_arg(needles_arg)), + KEEP(vctrs_arg(haystack_arg)), + KEEP(r_lazy_eval_protect(call)), + NULL + }; + + r_obj* ffi_call = KEEP(r_call_n(syms_stop_matches_relationship_one_to_many, syms, args)); + Rf_eval(ffi_call, vctrs_ns_env); + + never_reached("stop_matches_relationship_one_to_many"); +} + +static inline +void stop_matches_relationship_many_to_one(r_ssize i, + struct vctrs_arg* needles_arg, + struct vctrs_arg* haystack_arg, + struct r_lazy call) { + r_obj* syms[5] = { + syms_i, + syms_needles_arg, + syms_haystack_arg, + syms_call, + NULL + }; + r_obj* args[5] = { + KEEP(r_int((int)i + 1)), + KEEP(vctrs_arg(needles_arg)), + KEEP(vctrs_arg(haystack_arg)), + KEEP(r_lazy_eval_protect(call)), + NULL + }; + + r_obj* ffi_call = KEEP(r_call_n(syms_stop_matches_relationship_many_to_one, syms, args)); + Rf_eval(ffi_call, vctrs_ns_env); + + never_reached("stop_matches_relationship_many_to_one"); +} + +static inline +void warn_matches_relationship_many_to_many(r_ssize i, + r_ssize j, + struct vctrs_arg* needles_arg, + struct vctrs_arg* haystack_arg, + struct r_lazy call) { + r_obj* syms[6] = { + syms_i, + syms_j, + syms_needles_arg, + syms_haystack_arg, + syms_call, + NULL + }; + r_obj* args[6] = { + KEEP(r_int((int)i + 1)), + KEEP(r_int((int)j + 1)), + KEEP(vctrs_arg(needles_arg)), + KEEP(vctrs_arg(haystack_arg)), + KEEP(r_lazy_eval_protect(call)), + NULL + }; + + r_obj* ffi_call = KEEP(r_call_n(syms_warn_matches_relationship_many_to_many, syms, args)); + Rf_eval(ffi_call, vctrs_ns_env); + FREE(6); +} + // ----------------------------------------------------------------------------- void vctrs_init_match(r_obj* ns) { diff --git a/src/utils.c b/src/utils.c index 97ec8dcb1..a4cd4033c 100644 --- a/src/utils.c +++ b/src/utils.c @@ -1554,6 +1554,7 @@ SEXP chrs_smallest = NULL; SEXP chrs_which = NULL; SEXP syms_i = NULL; +SEXP syms_j = NULL; SEXP syms_n = NULL; SEXP syms_x = NULL; SEXP syms_y = NULL; @@ -1605,6 +1606,10 @@ SEXP syms_stop_matches_remaining = NULL; SEXP syms_stop_matches_incomplete = NULL; SEXP syms_stop_matches_multiple = NULL; SEXP syms_warn_matches_multiple = NULL; +SEXP syms_stop_matches_relationship_one_to_one = NULL; +SEXP syms_stop_matches_relationship_one_to_many = NULL; +SEXP syms_stop_matches_relationship_many_to_one = NULL; +SEXP syms_warn_matches_relationship_many_to_many = NULL; SEXP syms_action = NULL; SEXP syms_vctrs_common_class_fallback = NULL; SEXP syms_fallback_class = NULL; @@ -1615,6 +1620,7 @@ SEXP syms_actual = NULL; SEXP syms_required = NULL; SEXP syms_call = NULL; SEXP syms_dot_call = NULL; +SEXP syms_which = NULL; SEXP fns_bracket = NULL; SEXP fns_quote = NULL; @@ -1828,6 +1834,7 @@ void vctrs_init_utils(SEXP ns) { INTEGER(vctrs_shared_zero_int)[0] = 0; syms_i = Rf_install("i"); + syms_j = Rf_install("j"); syms_n = Rf_install("n"); syms_x = Rf_install("x"); syms_y = Rf_install("y"); @@ -1880,6 +1887,10 @@ void vctrs_init_utils(SEXP ns) { syms_stop_matches_incomplete = Rf_install("stop_matches_incomplete"); syms_stop_matches_multiple = Rf_install("stop_matches_multiple"); syms_warn_matches_multiple = Rf_install("warn_matches_multiple"); + syms_stop_matches_relationship_one_to_one = Rf_install("stop_matches_relationship_one_to_one"); + syms_stop_matches_relationship_one_to_many = Rf_install("stop_matches_relationship_one_to_many"); + syms_stop_matches_relationship_many_to_one = Rf_install("stop_matches_relationship_many_to_one"); + syms_warn_matches_relationship_many_to_many = Rf_install("warn_matches_relationship_many_to_many"); syms_action = Rf_install("action"); syms_vctrs_common_class_fallback = Rf_install(c_strs_vctrs_common_class_fallback); syms_fallback_class = Rf_install("fallback_class"); @@ -1890,6 +1901,7 @@ void vctrs_init_utils(SEXP ns) { syms_required = Rf_install("required"); syms_call = Rf_install("call"); syms_dot_call = Rf_install(".call"); + syms_which = Rf_install("which"); fns_bracket = Rf_findVar(syms_bracket, R_BaseEnv); fns_quote = Rf_findVar(Rf_install("quote"), R_BaseEnv); diff --git a/src/utils.h b/src/utils.h index f195d328a..3cdb1dc6b 100644 --- a/src/utils.h +++ b/src/utils.h @@ -448,6 +448,7 @@ extern SEXP chrs_smallest; extern SEXP chrs_which; extern SEXP syms_i; +extern SEXP syms_j; extern SEXP syms_n; extern SEXP syms_x; extern SEXP syms_y; @@ -497,6 +498,10 @@ extern SEXP syms_stop_matches_remaining; extern SEXP syms_stop_matches_incomplete; extern SEXP syms_stop_matches_multiple; extern SEXP syms_warn_matches_multiple; +extern SEXP syms_stop_matches_relationship_one_to_one; +extern SEXP syms_stop_matches_relationship_one_to_many; +extern SEXP syms_stop_matches_relationship_many_to_one; +extern SEXP syms_warn_matches_relationship_many_to_many; extern SEXP syms_action; extern SEXP syms_vctrs_common_class_fallback; extern SEXP syms_fallback_class; @@ -507,6 +512,7 @@ extern SEXP syms_actual; extern SEXP syms_required; extern SEXP syms_call; extern SEXP syms_dot_call; +extern SEXP syms_which; static const char * const c_strs_vctrs_common_class_fallback = "vctrs:::common_class_fallback"; diff --git a/tests/testthat/_snaps/match.md b/tests/testthat/_snaps/match.md index f9c3d18f7..fbddbabe6 100644 --- a/tests/testthat/_snaps/match.md +++ b/tests/testthat/_snaps/match.md @@ -85,6 +85,34 @@ Error in `vec_locate_matches()`: ! `incomplete` must be one of: "compare", "match", "drop", or "error". +# `multiple` is validated + + Code + (expect_error(vec_locate_matches(1, 2, multiple = 1.5))) + Output + + Error in `vec_locate_matches()`: + ! `multiple` must be a string. + Code + (expect_error(vec_locate_matches(1, 2, multiple = c("first", "last")))) + Output + + Error in `vec_locate_matches()`: + ! `multiple` must be a string. + Code + (expect_error(vec_locate_matches(1, 2, multiple = "x"))) + Output + + Error in `vec_locate_matches()`: + ! `multiple` must be one of "all", "any", "first", or "last". + Code + (expect_error(vec_locate_matches(1, 2, multiple = "x", error_call = call("fn"))) + ) + Output + + Error in `vec_locate_matches()`: + ! `multiple` must be one of "all", "any", "first", or "last". + # `multiple` can error informatively Code @@ -153,33 +181,245 @@ Each element of `foo` can match at most 1 observation from `bar`. x The element at location 1 has multiple matches. -# `multiple` is validated +# `relationship` handles one-to-one case Code - (expect_error(vec_locate_matches(1, 2, multiple = 1.5))) + (expect_error(vec_locate_matches(c(2, 1), c(1, 1), relationship = "one_to_one")) + ) + Output + + Error in `vec_locate_matches()`: + ! Each element can match at most 1 observation. + x The element at location 2 has multiple matches. + Code + (expect_error(vec_locate_matches(c(1, 1), c(1, 2), relationship = "one_to_one")) + ) + Output + + Error in `vec_locate_matches()`: + ! Each element can match at most 1 observation. + x The element at location 1 has multiple matches. + +# `relationship` handles one-to-many case + + Code + (expect_error(vec_locate_matches(c(1, 2, 2), c(2, 1), relationship = "one_to_many")) + ) + Output + + Error in `vec_locate_matches()`: + ! Each element can match at most 1 observation. + x The element at location 1 has multiple matches. + +# `relationship` handles many-to-one case + + Code + (expect_error(vec_locate_matches(c(1, 2), c(1, 2, 2), relationship = "many_to_one")) + ) + Output + + Error in `vec_locate_matches()`: + ! Each element can match at most 1 observation. + x The element at location 2 has multiple matches. + +# `relationship` handles warn-many-to-many case + + Code + (expect_warning(vec_locate_matches(c(1, 2, 1), c(1, 2, 2), relationship = "warn_many_to_many")) + ) + Output + + Warning in `vec_locate_matches()`: + Detected an unexpected many-to-many relationship. + x The element at location 2 has multiple matches. + x The element at location 1 has multiple matches. + Code + (expect_warning(vec_locate_matches(c(1, 1, 2), c(2, 2, 1), relationship = "warn_many_to_many")) + ) + Output + + Warning in `vec_locate_matches()`: + Detected an unexpected many-to-many relationship. + x The element at location 3 has multiple matches. + x The element at location 3 has multiple matches. + +# `relationship` considers `incomplete` matches as possible multiple matches + + Code + (expect_error(vec_locate_matches(x, y, relationship = "one_to_many"))) + Output + + Error in `vec_locate_matches()`: + ! Each element can match at most 1 observation. + x The element at location 1 has multiple matches. + +# `relationship` errors on multiple matches that come from different nesting containers + + Code + (expect_error(vec_locate_matches(df, df2, condition = c("<=", "<="), + relationship = "many_to_one"))) + Output + + Error in `vec_locate_matches()`: + ! Each element can match at most 1 observation. + x The element at location 1 has multiple matches. + +# `relationship` errors when a match from a different nesting container is processed early on + + Code + (expect_error(vec_locate_matches(needles, haystack, condition = "<", + relationship = "many_to_one"))) + Output + + Error in `vec_locate_matches()`: + ! Each element can match at most 1 observation. + x The element at location 1 has multiple matches. + +# `relationship` can still detect problematic `haystack` relationships when `multiple = first/last` are used + + Code + (expect_error(vec_locate_matches(c(3, 1, 1), c(2, 1, 3, 3), multiple = "first", + relationship = "one_to_one"))) + Output + + Error in `vec_locate_matches()`: + ! Each element can match at most 1 observation. + x The element at location 2 has multiple matches. + Code + (expect_error(vec_locate_matches(c(3, 1, 1), c(2, 1, 3, 3), multiple = "first", + relationship = "one_to_many"))) + Output + + Error in `vec_locate_matches()`: + ! Each element can match at most 1 observation. + x The element at location 2 has multiple matches. + +# `relationship` and `remaining` work properly together + + Code + out <- vec_locate_matches(c(1, 2, 2), c(2, 3, 1, 1, 4), relationship = "warn_many_to_many", + remaining = NA_integer_) + Condition + Warning in `vec_locate_matches()`: + Detected an unexpected many-to-many relationship. + x The element at location 1 has multiple matches. + x The element at location 1 has multiple matches. + +# `relationship` errors if `condition` creates multiple matches + + Code + (expect_error(vec_locate_matches(1, c(1, 2), condition = "<=", relationship = "many_to_one")) + ) + Output + + Error in `vec_locate_matches()`: + ! Each element can match at most 1 observation. + x The element at location 1 has multiple matches. + +# `relationship` still errors if `filter` hasn't removed all multiple matches + + Code + (expect_error(vec_locate_matches(1, c(1, 2, 1), condition = "<=", filter = "min", + relationship = "many_to_one"))) + Output + + Error in `vec_locate_matches()`: + ! Each element can match at most 1 observation. + x The element at location 1 has multiple matches. + +# `relationship` errors respect argument tags and error call + + Code + (expect_error(vec_locate_matches(1L, c(1L, 1L), relationship = "one_to_one", + needles_arg = "foo", haystack_arg = "bar", error_call = call("fn")))) + Output + + Error in `fn()`: + ! Each element of `foo` can match at most 1 observation from `bar`. + x The element of `foo` at location 1 has multiple matches. + Code + (expect_error(vec_locate_matches(c(1L, 1L), 1L, relationship = "one_to_one", + needles_arg = "foo", haystack_arg = "bar", error_call = call("fn")))) + Output + + Error in `fn()`: + ! Each element of `bar` can match at most 1 observation from `foo`. + x The element of `bar` at location 1 has multiple matches. + Code + (expect_error(vec_locate_matches(c(1L, 1L), 1L, relationship = "one_to_many", + needles_arg = "foo", haystack_arg = "bar", error_call = call("fn")))) + Output + + Error in `fn()`: + ! Each element of `bar` can match at most 1 observation from `foo`. + x The element of `bar` at location 1 has multiple matches. + Code + (expect_error(vec_locate_matches(1L, c(1L, 1L), relationship = "many_to_one", + needles_arg = "foo", haystack_arg = "bar", error_call = call("fn")))) + Output + + Error in `fn()`: + ! Each element of `foo` can match at most 1 observation from `bar`. + x The element of `foo` at location 1 has multiple matches. + +# `relationship` warnings respect argument tags and error call + + Code + (expect_warning(vec_locate_matches(c(1L, 1L), c(1L, 1L), relationship = "warn_many_to_many", + needles_arg = "foo", haystack_arg = "bar", error_call = call("fn")))) + Output + + Warning in `fn()`: + Detected an unexpected many-to-many relationship between `foo` and `bar`. + x The element of `foo` at location 1 has multiple matches. + x The element of `bar` at location 1 has multiple matches. + Code + (expect_warning(vec_locate_matches(c(1L, 1L), c(1L, 1L), relationship = "warn_many_to_many", + needles_arg = "foo", error_call = call("fn")))) + Output + + Warning in `fn()`: + Detected an unexpected many-to-many relationship. + x The element of `foo` at location 1 has multiple matches. + x The element at location 1 has multiple matches. + Code + (expect_warning(vec_locate_matches(c(1L, 1L), c(1L, 1L), relationship = "warn_many_to_many", + haystack_arg = "bar", error_call = call("fn")))) + Output + + Warning in `fn()`: + Detected an unexpected many-to-many relationship. + x The element at location 1 has multiple matches. + x The element of `bar` at location 1 has multiple matches. + +# `relationship` is validated + + Code + (expect_error(vec_locate_matches(1, 2, relationship = 1.5))) Output Error in `vec_locate_matches()`: - ! `multiple` must be a string. + ! `relationship` must be a string. Code - (expect_error(vec_locate_matches(1, 2, multiple = c("first", "last")))) + (expect_error(vec_locate_matches(1, 2, relationship = c("one_to_one", + "one_to_many")))) Output Error in `vec_locate_matches()`: - ! `multiple` must be a string. + ! `relationship` must be a string. Code - (expect_error(vec_locate_matches(1, 2, multiple = "x"))) + (expect_error(vec_locate_matches(1, 2, relationship = "x"))) Output Error in `vec_locate_matches()`: - ! `multiple` must be one of "all", "any", "first", "last", "warning", or "error". + ! `relationship` must be one of "none", "one_to_one", "one_to_many", "many_to_one", "many_to_many", or "warn_many_to_many". Code - (expect_error(vec_locate_matches(1, 2, multiple = "x", error_call = call("fn"))) - ) + (expect_error(vec_locate_matches(1, 2, relationship = "x", error_call = call( + "fn")))) Output Error in `vec_locate_matches()`: - ! `multiple` must be one of "all", "any", "first", "last", "warning", or "error". + ! `relationship` must be one of "none", "one_to_one", "one_to_many", "many_to_one", "many_to_many", or "warn_many_to_many". # `no_match` can error informatively diff --git a/tests/testthat/test-match.R b/tests/testthat/test-match.R index 98fb9a1a3..7fe1d67cf 100644 --- a/tests/testthat/test-match.R +++ b/tests/testthat/test-match.R @@ -905,6 +905,71 @@ test_that("duplicate needles match the same haystack locations", { expect_identical(x$haystack, c(1L, 3L, 2L, 1L, 3L, 2L)) }) +test_that("correctly gets all matches when they come from different nesting containers", { + needles <- data_frame( + a = c(1, 8), + b = c(2, 9) + ) + haystack <- data_frame( + a = c(6, 5), + b = c(6, 7) + ) + + expect_identical( + vec_locate_matches(needles, haystack, condition = "<", multiple = "all"), + data_frame(needles = c(1L, 1L, 2L), haystack = c(1L, 2L, NA)) + ) +}) + +test_that("correctly gets first/last/any match when they come from different nesting containers", { + needles <- data_frame( + a = c(1, 8), + b = c(2, 9) + ) + haystack <- data_frame( + a = c(6, 5, 0), + b = c(6, 7, 1) + ) + + expect_identical( + vec_locate_matches(needles, haystack, condition = "<", multiple = "first"), + data_frame(needles = c(1L, 2L), haystack = c(1L, NA)) + ) + expect_identical( + vec_locate_matches(needles, haystack, condition = "<", multiple = "last"), + data_frame(needles = c(1L, 2L), haystack = c(2L, NA)) + ) + expect_identical( + vec_locate_matches(needles, haystack, condition = "<", multiple = "any"), + data_frame(needles = c(1L, 2L), haystack = c(2L, NA)) + ) + expect_identical( + vec_locate_matches(needles, haystack, condition = "<", multiple = "first", remaining = NA_integer_), + data_frame(needles = c(1L, 2L, NA, NA), haystack = c(1L, NA, 2L, 3L)) + ) + expect_identical( + vec_locate_matches(needles, haystack, condition = "<", multiple = "last", remaining = NA_integer_), + data_frame(needles = c(1L, 2L, NA, NA), haystack = c(2L, NA, 1L, 3L)) + ) + expect_identical( + vec_locate_matches(needles, haystack, condition = "<", multiple = "any", remaining = NA_integer_), + data_frame(needles = c(1L, 2L, NA, NA), haystack = c(2L, NA, 1L, 3L)) + ) +}) + +test_that("`multiple` is validated", { + expect_snapshot({ + (expect_error(vec_locate_matches(1, 2, multiple = 1.5))) + (expect_error(vec_locate_matches(1, 2, multiple = c("first", "last")))) + (expect_error(vec_locate_matches(1, 2, multiple = "x"))) + # Uses internal error + (expect_error(vec_locate_matches(1, 2, multiple = "x", error_call = call("fn")))) + }) +}) + +# ------------------------------------------------------------------------------ +# vec_locate_matches() - `multiple` (deprecated) + test_that("`multiple` can error informatively", { expect_snapshot({ (expect_error(vec_locate_matches(1L, c(1L, 1L), multiple = "error"))) @@ -970,71 +1035,275 @@ test_that("errors when a match from a different nesting container is processed e ) }) -test_that("correctly gets all matches when they come from different nesting containers", { - needles <- data_frame( - a = c(1, 8), - b = c(2, 9) +test_that("`multiple = 'error'` doesn't error errneously on the last observation", { + expect_error(res <- vec_locate_matches(1:2, 1:2, multiple = "error"), NA) + expect_identical(res$needles, 1:2) + expect_identical(res$haystack, 1:2) +}) + +# ------------------------------------------------------------------------------ +# vec_locate_matches() - `relationship` + +test_that("`relationship` handles one-to-one case", { + # No error + expect_identical( + vec_locate_matches(1:2, 2:1, relationship = "one_to_one"), + vec_locate_matches(1:2, 2:1) ) - haystack <- data_frame( - a = c(6, 5), - b = c(6, 7) + + # Doesn't care about the zero match case + expect_identical( + vec_locate_matches(1:2, 3:4, relationship = "one_to_one"), + vec_locate_matches(1:2, 3:4) ) + expect_snapshot({ + (expect_error(vec_locate_matches(c(2, 1), c(1, 1), relationship = "one_to_one"))) + (expect_error(vec_locate_matches(c(1, 1), c(1, 2), relationship = "one_to_one"))) + }) +}) + +test_that("`relationship` handles one-to-many case", { + # No error expect_identical( - vec_locate_matches(needles, haystack, condition = "<", multiple = "all"), - data_frame(needles = c(1L, 1L, 2L), haystack = c(1L, 2L, NA)) + vec_locate_matches(c(1, 2), c(1, 2, 2), relationship = "one_to_many"), + vec_locate_matches(c(1, 2), c(1, 2, 2)) + ) + + # Doesn't care about the zero match case + expect_identical( + vec_locate_matches(1:2, 3:4, relationship = "one_to_many"), + vec_locate_matches(1:2, 3:4) ) + + expect_snapshot({ + (expect_error(vec_locate_matches(c(1, 2, 2), c(2, 1), relationship = "one_to_many"))) + }) }) -test_that("correctly gets first/last/any match when they come from different nesting containers", { - needles <- data_frame( - a = c(1, 8), - b = c(2, 9) +test_that("`relationship` handles many-to-one case", { + # No error + expect_identical( + vec_locate_matches(c(1, 2, 2), c(1, 2), relationship = "many_to_one"), + vec_locate_matches(c(1, 2, 2), c(1, 2)) ) - haystack <- data_frame( - a = c(6, 5, 0), - b = c(6, 7, 1) + + # Doesn't care about the zero match case + expect_identical( + vec_locate_matches(1:2, 3:4, relationship = "many_to_one"), + vec_locate_matches(1:2, 3:4) ) + expect_snapshot({ + (expect_error(vec_locate_matches(c(1, 2), c(1, 2, 2), relationship = "many_to_one"))) + }) +}) + +test_that("`relationship` handles many-to-many case", { + # No error expect_identical( - vec_locate_matches(needles, haystack, condition = "<", multiple = "first"), - data_frame(needles = c(1L, 2L), haystack = c(1L, NA)) + vec_locate_matches(c(1, 2, 2), c(1, 2), relationship = "many_to_many"), + vec_locate_matches(c(1, 2, 2), c(1, 2)) ) + + # No error expect_identical( - vec_locate_matches(needles, haystack, condition = "<", multiple = "last"), - data_frame(needles = c(1L, 2L), haystack = c(2L, NA)) + vec_locate_matches(c(1, 2), c(1, 2, 2), relationship = "many_to_many"), + vec_locate_matches(c(1, 2), c(1, 2, 2)) ) + + # No error expect_identical( - vec_locate_matches(needles, haystack, condition = "<", multiple = "any"), - data_frame(needles = c(1L, 2L), haystack = c(2L, NA)) + vec_locate_matches(c(1, 1, 2), c(1, 2, 2), relationship = "many_to_many"), + vec_locate_matches(c(1, 1, 2), c(1, 2, 2)) ) + + # Doesn't care about the zero match case expect_identical( - vec_locate_matches(needles, haystack, condition = "<", multiple = "first", remaining = NA_integer_), - data_frame(needles = c(1L, 2L, NA, NA), haystack = c(1L, NA, 2L, 3L)) + vec_locate_matches(1:2, 3:4, relationship = "many_to_many"), + vec_locate_matches(1:2, 3:4) ) +}) + +test_that("`relationship` handles warn-many-to-many case", { + # No warning expect_identical( - vec_locate_matches(needles, haystack, condition = "<", multiple = "last", remaining = NA_integer_), - data_frame(needles = c(1L, 2L, NA, NA), haystack = c(2L, NA, 1L, 3L)) + expect_silent( + vec_locate_matches(c(1, 2, 2), c(1, 2), relationship = "warn_many_to_many") + ), + vec_locate_matches(c(1, 2, 2), c(1, 2)) ) + + # No warning expect_identical( - vec_locate_matches(needles, haystack, condition = "<", multiple = "any", remaining = NA_integer_), - data_frame(needles = c(1L, 2L, NA, NA), haystack = c(2L, NA, 1L, 3L)) + expect_silent( + vec_locate_matches(c(1, 2), c(1, 2, 2), relationship = "warn_many_to_many") + ), + vec_locate_matches(c(1, 2), c(1, 2, 2)) ) + + # Doesn't care about the zero match case + expect_identical( + expect_silent( + vec_locate_matches(1:2, 3:4, relationship = "warn_many_to_many") + ), + vec_locate_matches(1:2, 3:4) + ) + + # Specifically designed to ensure we test both: + # - Finding multiple `needles` matches before multiple `haystack` matches + # - Finding multiple `haystack` matches before multiple `needles` matches + expect_snapshot({ + (expect_warning(vec_locate_matches(c(1, 2, 1), c(1, 2, 2), relationship = "warn_many_to_many"))) + (expect_warning(vec_locate_matches(c(1, 1, 2), c(2, 2, 1), relationship = "warn_many_to_many"))) + }) }) -test_that("`multiple = 'error'` doesn't error errneously on the last observation", { - expect_error(res <- vec_locate_matches(1:2, 1:2, multiple = "error"), NA) +test_that("`relationship` considers `incomplete` matches as possible multiple matches", { + x <- c(1, NA, NaN) + y <- c(NA, 1) + + expect_snapshot({ + (expect_error(vec_locate_matches(x, y, relationship = "one_to_many"))) + }) + + # No error + expect_identical( + vec_locate_matches(x, y, relationship = "one_to_many", incomplete = NA), + vec_locate_matches(x, y, incomplete = NA) + ) + + # No error + expect_identical( + vec_locate_matches(x, y, relationship = "one_to_many", nan_distinct = TRUE), + vec_locate_matches(x, y, nan_distinct = TRUE) + ) +}) + +test_that("`relationship` errors on multiple matches that come from different nesting containers", { + df <- data_frame(x = 0, y = 0) + df2 <- data_frame(x = 1:2, y = 2:1) + + expect_snapshot({ + (expect_error(vec_locate_matches(df, df2, condition = c("<=", "<="), relationship = "many_to_one"))) + }) +}) + +test_that("`relationship` errors when a match from a different nesting container is processed early on", { + # Row 1 has 2 matches + # Row 2 has 0 matches + needles <- data_frame( + a = c(1, 8), + b = c(2, 9) + ) + + # Rows 1 and 2 end up in different nesting containers + haystack <- data_frame( + a = c(5, 6), + b = c(7, 6) + ) + + # needles[1,] records the haystack[1,] match first, which is in the 1st + # value of `loc_first_match_o_haystack`, then records the haystack[3,] match + # which is in the 3rd value of `loc_first_match_o_haystack` even though it + # is processed 2nd (i.e. we need to use `loc` rather than `i` when detecting + # multiple matches) + expect_snapshot({ + (expect_error(vec_locate_matches(needles, haystack, condition = "<", relationship = "many_to_one"))) + }) +}) + +test_that("`relationship` doesn't error errneously on the last observation", { + expect_error(res <- vec_locate_matches(1:2, 1:2, relationship = "many_to_one"), NA) expect_identical(res$needles, 1:2) expect_identical(res$haystack, 1:2) }) -test_that("`multiple` is validated", { +test_that("`relationship` doesn't error if `multiple` removes multiple matches", { + out <- vec_locate_matches(c(1, 2), c(1, 1), multiple = "any", relationship = "one_to_one") + expect_identical(out$needles, c(1L, 2L)) + expect_identical(out$haystack, c(1L, NA)) + + out <- vec_locate_matches(c(1, 2), c(1, 1), multiple = "first", relationship = "one_to_one") + expect_identical(out$needles, c(1L, 2L)) + expect_identical(out$haystack, c(1L, NA)) + + out <- vec_locate_matches(c(1, 2), c(1, 1), multiple = "last", relationship = "one_to_one") + expect_identical(out$needles, c(1L, 2L)) + expect_identical(out$haystack, c(2L, NA)) +}) + +test_that("`relationship` can still detect problematic `haystack` relationships when `multiple = first/last` are used", { expect_snapshot({ - (expect_error(vec_locate_matches(1, 2, multiple = 1.5))) - (expect_error(vec_locate_matches(1, 2, multiple = c("first", "last")))) - (expect_error(vec_locate_matches(1, 2, multiple = "x"))) + (expect_error(vec_locate_matches(c(3, 1, 1), c(2, 1, 3, 3), multiple = "first", relationship = "one_to_one"))) + (expect_error(vec_locate_matches(c(3, 1, 1), c(2, 1, 3, 3), multiple = "first", relationship = "one_to_many"))) + }) +}) + +test_that("`relationship` and `remaining` work properly together", { + expect_snapshot({ + out <- vec_locate_matches( + c(1, 2, 2), + c(2, 3, 1, 1, 4), + relationship = "warn_many_to_many", + remaining = NA_integer_ + ) + }) + expect_identical(out$needles, c(1L, 1L, 2L, 3L, NA, NA)) + expect_identical(out$haystack, c(3L, 4L, 1L, 1L, 2L, 5L)) +}) + +test_that("`relationship` errors if `condition` creates multiple matches", { + expect_snapshot({ + (expect_error(vec_locate_matches(1, c(1, 2), condition = "<=", relationship = "many_to_one"))) + }) +}) + +test_that("`relationship` doesn't error if `filter` removes multiple matches", { + out <- vec_locate_matches(1, c(1, 2), condition = "<=", filter = "min", relationship = "many_to_one") + expect_identical(out$needles, 1L) + expect_identical(out$haystack, 1L) + + out <- vec_locate_matches(1, c(1, 2), condition = "<=", filter = "max", relationship = "many_to_one") + expect_identical(out$needles, 1L) + expect_identical(out$haystack, 2L) +}) + +test_that("`relationship` still errors if `filter` hasn't removed all multiple matches", { + expect_snapshot({ + (expect_error(vec_locate_matches(1, c(1, 2, 1), condition = "<=", filter = "min", relationship = "many_to_one"))) + }) + + # But not here + out <- vec_locate_matches(c(1, 1), c(1, 2, 1), condition = "<=", filter = "max", relationship = "many_to_one") + expect_identical(out$needles, c(1L, 2L)) + expect_identical(out$haystack, c(2L, 2L)) +}) + +test_that("`relationship` errors respect argument tags and error call", { + expect_snapshot({ + (expect_error(vec_locate_matches(1L, c(1L, 1L), relationship = "one_to_one", needles_arg = "foo", haystack_arg = "bar", error_call = call("fn")))) + (expect_error(vec_locate_matches(c(1L, 1L), 1L, relationship = "one_to_one", needles_arg = "foo", haystack_arg = "bar", error_call = call("fn")))) + (expect_error(vec_locate_matches(c(1L, 1L), 1L, relationship = "one_to_many", needles_arg = "foo", haystack_arg = "bar", error_call = call("fn")))) + (expect_error(vec_locate_matches(1L, c(1L, 1L), relationship = "many_to_one", needles_arg = "foo", haystack_arg = "bar", error_call = call("fn")))) + }) +}) + +test_that("`relationship` warnings respect argument tags and error call", { + expect_snapshot({ + (expect_warning(vec_locate_matches(c(1L, 1L), c(1L, 1L), relationship = "warn_many_to_many", needles_arg = "foo", haystack_arg = "bar", error_call = call("fn")))) + (expect_warning(vec_locate_matches(c(1L, 1L), c(1L, 1L), relationship = "warn_many_to_many", needles_arg = "foo", error_call = call("fn")))) + (expect_warning(vec_locate_matches(c(1L, 1L), c(1L, 1L), relationship = "warn_many_to_many", haystack_arg = "bar", error_call = call("fn")))) + }) +}) + +test_that("`relationship` is validated", { + expect_snapshot({ + (expect_error(vec_locate_matches(1, 2, relationship = 1.5))) + (expect_error(vec_locate_matches(1, 2, relationship = c("one_to_one", "one_to_many")))) + (expect_error(vec_locate_matches(1, 2, relationship = "x"))) # Uses internal error - (expect_error(vec_locate_matches(1, 2, multiple = "x", error_call = call("fn")))) + (expect_error(vec_locate_matches(1, 2, relationship = "x", error_call = call("fn")))) }) }) From 6687d0df84e5a253b657b3f7c74ec0ad8ce6f044 Mon Sep 17 00:00:00 2001 From: Davis Vaughan Date: Wed, 22 Feb 2023 11:14:16 -0500 Subject: [PATCH 232/312] Update `needles_arg` and `haystack_arg` defaults (#1792) * Switch to `"needles"` and `"haystack"` Greatly simplify and improve the error reporting code * Minor documentation improvements * NEWS bullet --- NEWS.md | 4 + R/match.R | 151 ++++++++++--------------- man/vec_locate_matches.Rd | 44 ++++---- tests/testthat/_snaps/match.md | 196 ++++++++++++++++++--------------- tests/testthat/test-match.R | 14 +-- 5 files changed, 200 insertions(+), 209 deletions(-) diff --git a/NEWS.md b/NEWS.md index a0aefa844..ef6e5817c 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,5 +1,9 @@ # vctrs (development version) +* `vec_locate_matches()` has changed its default `needles_arg` and + `haystack_arg` values from `""` to `"needles"` and `"haystack"`, respectively. + This generally generates more informative error messages (#1792). + * `vec_locate_matches()` gains a new `relationship` argument that holistically handles multiple matches between `needles` and `haystack`. In particular, `relationship = "many_to_one"` replaces `multiple = "error"` and diff --git a/R/match.R b/R/match.R index a51a2ad57..f18f4c843 100644 --- a/R/match.R +++ b/R/match.R @@ -4,10 +4,10 @@ #' `r lifecycle::badge("experimental")` #' #' `vec_locate_matches()` is a more flexible version of [vec_match()] used to -#' identify locations where each observation of `needles` matches one or -#' multiple observations in `haystack`. Unlike `vec_match()`, -#' `vec_locate_matches()` returns all matches by default, and can match on -#' binary conditions other than equality, such as `>`, `>=`, `<`, and `<=`. +#' identify locations where each value of `needles` matches one or multiple +#' values in `haystack`. Unlike `vec_match()`, `vec_locate_matches()` returns +#' all matches by default, and can match on binary conditions other than +#' equality, such as `>`, `>=`, `<`, and `<=`. #' #' @details #' [vec_match()] is identical to (but often slightly faster than): @@ -26,36 +26,44 @@ #' and `haystack`, with the default being most similar to a left join. #' #' Be very careful when specifying match `condition`s. If a condition is -#' mis-specified, it is very easy to accidentally generate an exponentially +#' misspecified, it is very easy to accidentally generate an exponentially #' large number of matches. #' #' @section Dependencies of `vec_locate_matches()`: -#' * [vec_order_radix()] -#' * [vec_detect_complete()] +#' - [vec_order_radix()] +#' - [vec_detect_complete()] #' #' @inheritParams rlang::args_dots_empty #' @inheritParams rlang::args_error_context #' @inheritParams order-radix #' #' @param needles,haystack Vectors used for matching. +#' #' - `needles` represents the vector to search for. +#' #' - `haystack` represents the vector to search in. #' #' Prior to comparison, `needles` and `haystack` are coerced to the same type. #' #' @param condition Condition controlling how `needles` should be compared #' against `haystack` to identify a successful match. +#' #' - One of: `"=="`, `">"`, `">="`, `"<"`, or `"<="`. +#' #' - For data frames, a length `1` or `ncol(needles)` character vector #' containing only the above options, specifying how matching is determined #' for each column. #' #' @param filter Filter to be applied to the matched results. +#' #' - `"none"` doesn't apply any filter. +#' #' - `"min"` returns only the minimum haystack value matching the current #' needle. +#' #' - `"max"` returns only the maximum haystack value matching the current #' needle. +#' #' - For data frames, a length `1` or `ncol(needles)` character vector #' containing only the above options, specifying a filter to apply to #' each column. @@ -67,46 +75,61 @@ #' if the maximum or minimum haystack value is duplicated in `haystack`. These #' can be further controlled with `multiple`. #' -#' @param incomplete Handling of missing values and -#' [incomplete][vec_detect_complete] observations in `needles`. +#' @param incomplete Handling of missing and [incomplete][vec_detect_complete] +#' values in `needles`. +#' #' - `"compare"` uses `condition` to determine whether or not a missing value #' in `needles` matches a missing value in `haystack`. If `condition` is #' `==`, `>=`, or `<=`, then missing values will match. +#' #' - `"match"` always allows missing values in `needles` to match missing #' values in `haystack`, regardless of the `condition`. -#' - `"drop"` drops incomplete observations in `needles` from the result. +#' +#' - `"drop"` drops incomplete values in `needles` from the result. +#' #' - `"error"` throws an error if any `needles` are incomplete. +#' #' - If a single integer is provided, this represents the value returned -#' in the `haystack` column for observations of `needles` that are -#' incomplete. If `no_match = NA`, setting `incomplete = NA` forces -#' incomplete observations in `needles` to be treated like unmatched values. +#' in the `haystack` column for values of `needles` that are incomplete. If +#' `no_match = NA`, setting `incomplete = NA` forces incomplete values in +#' `needles` to be treated like unmatched values. #' #' `nan_distinct` determines whether a `NA` is allowed to match a `NaN`. #' #' @param no_match Handling of `needles` without a match. +#' #' - `"drop"` drops `needles` with zero matches from the result. +#' #' - `"error"` throws an error if any `needles` have zero matches. +#' #' - If a single integer is provided, this represents the value returned in -#' the `haystack` column for observations of `needles` that have zero -#' matches. The default represents an unmatched needle with `NA`. +#' the `haystack` column for values of `needles` that have zero matches. The +#' default represents an unmatched needle with `NA`. #' #' @param remaining Handling of `haystack` values that `needles` never matched. +#' #' - `"drop"` drops remaining `haystack` values from the result. #' Typically, this is the desired behavior if you only care when `needles` #' has a match. +#' #' - `"error"` throws an error if there are any remaining `haystack` #' values. +#' #' - If a single integer is provided (often `NA`), this represents the value #' returned in the `needles` column for the remaining `haystack` values #' that `needles` never matched. Remaining `haystack` values are always #' returned at the end of the result. #' #' @param multiple Handling of `needles` with multiple matches. For each needle: +#' #' - `"all"` returns all matches detected in `haystack`. +#' #' - `"any"` returns any match detected in `haystack` with no guarantees on #' which match will be returned. It is often faster than `"first"` and #' `"last"` if you just need to detect if there is at least one match. +#' #' - `"first"` returns the first match detected in `haystack`. +#' #' - `"last"` returns the last match detected in `haystack`. #' #' @param relationship Handling of the expected relationship between @@ -150,8 +173,10 @@ #' used in error messages. #' #' @return A two column data frame containing the locations of the matches. +#' #' - `needles` is an integer vector containing the location of #' the needle currently being matched. +#' #' - `haystack` is an integer vector containing the location of the #' corresponding match in the haystack for the current needle. #' @@ -160,7 +185,7 @@ #' x <- c(1, 2, NA, 3, NaN) #' y <- c(2, 1, 4, NA, 1, 2, NaN) #' -#' # By default, for each element of `x`, all matching locations in `y` are +#' # By default, for each value of `x`, all matching locations in `y` are #' # returned #' matches <- vec_locate_matches(x, y) #' matches @@ -183,13 +208,13 @@ #' # In this case, the `NA` in `y` matches two rows in `x` #' try(vec_locate_matches(x, y, relationship = "one_to_many")) #' -#' # By default, NA is treated as being identical to NaN. -#' # Using `nan_distinct = TRUE` treats NA and NaN as different values, so NA -#' # can only match NA, and NaN can only match NaN. +#' # By default, `NA` is treated as being identical to `NaN`. +#' # Using `nan_distinct = TRUE` treats `NA` and `NaN` as different values, so +#' # `NA` can only match `NA`, and `NaN` can only match `NaN`. #' vec_locate_matches(x, y, nan_distinct = TRUE) #' #' # If you never want missing values to match, set `incomplete = NA` to return -#' # `NA` in the `haystack` column anytime there was an incomplete observation +#' # `NA` in the `haystack` column anytime there was an incomplete value #' # in `needles`. #' vec_locate_matches(x, y, incomplete = NA) #' @@ -231,8 +256,8 @@ #' ) #' #' # In the very rare case that you need to generate locations for a -#' # cross match, where every observation of `x` is forced to match every -#' # observation of `y` regardless of what the actual values are, you can +#' # cross match, where every value of `x` is forced to match every +#' # value of `y` regardless of what the actual values are, you can #' # replace `x` and `y` with integer vectors of the same size that contain #' # a single value and match on those instead. #' x_proxy <- vec_rep(1L, vec_size(x)) @@ -286,8 +311,8 @@ vec_locate_matches <- function(needles, relationship = "none", nan_distinct = FALSE, chr_proxy_collate = NULL, - needles_arg = "", - haystack_arg = "", + needles_arg = "needles", + haystack_arg = "haystack", error_call = current_env()) { check_dots_empty0(...) frame <- environment() @@ -362,24 +387,12 @@ stop_matches_nothing <- function(i, needles_arg, haystack_arg, call) { #' @export cnd_header.vctrs_error_matches_nothing <- function(cnd, ...) { - if (nzchar(cnd$needles_arg)) { - needles_name <- glue::glue(" of `{cnd$needles_arg}` ") - } else { - needles_name <- " " - } - - if (nzchar(cnd$haystack_arg)) { - haystack_name <- glue::glue(" in `{cnd$haystack_arg}`") - } else { - haystack_name <- "" - } - - glue::glue("Each element{needles_name}must have a match{haystack_name}.") + glue::glue("Each value of `{cnd$needles_arg}` must have a match in `{cnd$haystack_arg}`.") } #' @export cnd_body.vctrs_error_matches_nothing <- function(cnd, ...) { - bullet <- glue::glue("The element at location {cnd$i} does not have a match.") + bullet <- glue::glue("Location {cnd$i} of `{cnd$needles_arg}` does not have a match.") bullet <- c(x = bullet) format_error_bullets(bullet) } @@ -398,24 +411,12 @@ stop_matches_remaining <- function(i, needles_arg, haystack_arg, call) { #' @export cnd_header.vctrs_error_matches_remaining <- function(cnd, ...) { - if (nzchar(cnd$haystack_arg)) { - haystack_name <- glue::glue(" of `{cnd$haystack_arg}` ") - } else { - haystack_name <- " " - } - - if (nzchar(cnd$needles_arg)) { - needles_name <- glue::glue(" by `{cnd$needles_arg}`") - } else { - needles_name <- "" - } - - glue::glue("Each haystack value{haystack_name}must be matched{needles_name}.") + glue::glue("Each value of `{cnd$haystack_arg}` must be matched by `{cnd$needles_arg}`.") } #' @export cnd_body.vctrs_error_matches_remaining <- function(cnd, ...) { - bullet <- glue::glue("The value at location {cnd$i} was not matched.") + bullet <- glue::glue("Location {cnd$i} of `{cnd$haystack_arg}` was not matched.") bullet <- c(x = bullet) format_error_bullets(bullet) } @@ -433,18 +434,12 @@ stop_matches_incomplete <- function(i, needles_arg, call) { #' @export cnd_header.vctrs_error_matches_incomplete <- function(cnd, ...) { - if (nzchar(cnd$needles_arg)) { - needles_name <- glue::glue(" of `{cnd$needles_arg}` ") - } else { - needles_name <- " " - } - - glue::glue("No element{needles_name}can contain missing values.") + glue::glue("`{cnd$needles_arg}` can't contain missing values.") } #' @export cnd_body.vctrs_error_matches_incomplete <- function(cnd, ...) { - bullet <- glue::glue("The element at location {cnd$i} contains missing values.") + bullet <- glue::glue("Location {cnd$i} contains missing values.") bullet <- c(x = bullet) format_error_bullets(bullet) } @@ -468,7 +463,7 @@ cnd_header.vctrs_error_matches_multiple <- function(cnd, ...) { #' @export cnd_body.vctrs_error_matches_multiple <- function(cnd, ...) { - cnd_matches_multiple_body(cnd$i) + cnd_matches_multiple_body(cnd$i, cnd$needles_arg) } # ------------------------------------------------------------------------------ @@ -476,7 +471,7 @@ cnd_body.vctrs_error_matches_multiple <- function(cnd, ...) { warn_matches_multiple <- function(i, needles_arg, haystack_arg, call) { message <- paste( cnd_matches_multiple_header(needles_arg, haystack_arg), - cnd_matches_multiple_body(i), + cnd_matches_multiple_body(i, needles_arg), sep = "\n" ) @@ -573,27 +568,11 @@ stop_matches_relationship <- function(class = NULL, ..., call = caller_env()) { } cnd_matches_multiple_header <- function(x_arg, y_arg) { - if (nzchar(x_arg)) { - x_name <- glue::glue(" of `{x_arg}` ") - } else { - x_name <- " " - } - - if (nzchar(y_arg)) { - y_name <- glue::glue(" from `{y_arg}`") - } else { - y_name <- "" - } - - glue::glue("Each element{x_name}can match at most 1 observation{y_name}.") + glue::glue("Each value of `{x_arg}` can match at most 1 value from `{y_arg}`.") } -cnd_matches_multiple_body <- function(i, name = "") { - if (nzchar(name)) { - bullet <- glue::glue("The element of `{name}` at location {i} has multiple matches.") - } else { - bullet <- glue::glue("The element at location {i} has multiple matches.") - } +cnd_matches_multiple_body <- function(i, name) { + bullet <- glue::glue("Location {i} of `{name}` matches multiple values.") bullet <- c(x = bullet) format_error_bullets(bullet) } @@ -601,16 +580,8 @@ cnd_matches_multiple_body <- function(i, name = "") { # ------------------------------------------------------------------------------ warn_matches_relationship_many_to_many <- function(i, j, needles_arg, haystack_arg, call) { - if (nzchar(needles_arg) && nzchar(haystack_arg)) { - name_needles_and_haystack <- glue::glue(" between `{needles_arg}` and `{haystack_arg}`") - } else { - name_needles_and_haystack <- "" - } - - header <- glue::glue("Detected an unexpected many-to-many relationship{name_needles_and_haystack}.") - message <- paste( - header, + glue::glue("Detected an unexpected many-to-many relationship between `{needles_arg}` and `{haystack_arg}`."), cnd_matches_multiple_body(i, needles_arg), cnd_matches_multiple_body(j, haystack_arg), sep = "\n" diff --git a/man/vec_locate_matches.Rd b/man/vec_locate_matches.Rd index 1a0d8d19b..cff0a0a0e 100644 --- a/man/vec_locate_matches.Rd +++ b/man/vec_locate_matches.Rd @@ -17,8 +17,8 @@ vec_locate_matches( relationship = "none", nan_distinct = FALSE, chr_proxy_collate = NULL, - needles_arg = "", - haystack_arg = "", + needles_arg = "needles", + haystack_arg = "haystack", error_call = current_env() ) } @@ -61,20 +61,20 @@ A filter can return multiple haystack matches for a particular needle if the maximum or minimum haystack value is duplicated in \code{haystack}. These can be further controlled with \code{multiple}.} -\item{incomplete}{Handling of missing values and -\link[=vec_detect_complete]{incomplete} observations in \code{needles}. +\item{incomplete}{Handling of missing and \link[=vec_detect_complete]{incomplete} +values in \code{needles}. \itemize{ \item \code{"compare"} uses \code{condition} to determine whether or not a missing value in \code{needles} matches a missing value in \code{haystack}. If \code{condition} is \code{==}, \code{>=}, or \code{<=}, then missing values will match. \item \code{"match"} always allows missing values in \code{needles} to match missing values in \code{haystack}, regardless of the \code{condition}. -\item \code{"drop"} drops incomplete observations in \code{needles} from the result. +\item \code{"drop"} drops incomplete values in \code{needles} from the result. \item \code{"error"} throws an error if any \code{needles} are incomplete. \item If a single integer is provided, this represents the value returned -in the \code{haystack} column for observations of \code{needles} that are -incomplete. If \code{no_match = NA}, setting \code{incomplete = NA} forces -incomplete observations in \code{needles} to be treated like unmatched values. +in the \code{haystack} column for values of \code{needles} that are incomplete. If +\code{no_match = NA}, setting \code{incomplete = NA} forces incomplete values in +\code{needles} to be treated like unmatched values. } \code{nan_distinct} determines whether a \code{NA} is allowed to match a \code{NaN}.} @@ -84,8 +84,8 @@ incomplete observations in \code{needles} to be treated like unmatched values. \item \code{"drop"} drops \code{needles} with zero matches from the result. \item \code{"error"} throws an error if any \code{needles} have zero matches. \item If a single integer is provided, this represents the value returned in -the \code{haystack} column for observations of \code{needles} that have zero -matches. The default represents an unmatched needle with \code{NA}. +the \code{haystack} column for values of \code{needles} that have zero matches. The +default represents an unmatched needle with \code{NA}. }} \item{remaining}{Handling of \code{haystack} values that \code{needles} never matched. @@ -195,10 +195,10 @@ corresponding match in the haystack for the current needle. \ifelse{html}{\href{https://lifecycle.r-lib.org/articles/stages.html#experimental}{\figure{lifecycle-experimental.svg}{options: alt='[Experimental]'}}}{\strong{[Experimental]}} \code{vec_locate_matches()} is a more flexible version of \code{\link[=vec_match]{vec_match()}} used to -identify locations where each observation of \code{needles} matches one or -multiple observations in \code{haystack}. Unlike \code{vec_match()}, -\code{vec_locate_matches()} returns all matches by default, and can match on -binary conditions other than equality, such as \code{>}, \code{>=}, \code{<}, and \code{<=}. +identify locations where each value of \code{needles} matches one or multiple +values in \code{haystack}. Unlike \code{vec_match()}, \code{vec_locate_matches()} returns +all matches by default, and can match on binary conditions other than +equality, such as \code{>}, \code{>=}, \code{<}, and \code{<=}. } \details{ \code{\link[=vec_match]{vec_match()}} is identical to (but often slightly faster than): @@ -216,7 +216,7 @@ binary conditions other than equality, such as \code{>}, \code{>=}, \code{<}, an and \code{haystack}, with the default being most similar to a left join. Be very careful when specifying match \code{condition}s. If a condition is -mis-specified, it is very easy to accidentally generate an exponentially +misspecified, it is very easy to accidentally generate an exponentially large number of matches. } \section{Dependencies of \code{vec_locate_matches()}}{ @@ -231,7 +231,7 @@ large number of matches. x <- c(1, 2, NA, 3, NaN) y <- c(2, 1, 4, NA, 1, 2, NaN) -# By default, for each element of `x`, all matching locations in `y` are +# By default, for each value of `x`, all matching locations in `y` are # returned matches <- vec_locate_matches(x, y) matches @@ -254,13 +254,13 @@ try(vec_locate_matches(x, y, relationship = "one_to_one")) # In this case, the `NA` in `y` matches two rows in `x` try(vec_locate_matches(x, y, relationship = "one_to_many")) -# By default, NA is treated as being identical to NaN. -# Using `nan_distinct = TRUE` treats NA and NaN as different values, so NA -# can only match NA, and NaN can only match NaN. +# By default, `NA` is treated as being identical to `NaN`. +# Using `nan_distinct = TRUE` treats `NA` and `NaN` as different values, so +# `NA` can only match `NA`, and `NaN` can only match `NaN`. vec_locate_matches(x, y, nan_distinct = TRUE) # If you never want missing values to match, set `incomplete = NA` to return -# `NA` in the `haystack` column anytime there was an incomplete observation +# `NA` in the `haystack` column anytime there was an incomplete value # in `needles`. vec_locate_matches(x, y, incomplete = NA) @@ -302,8 +302,8 @@ data_frame( ) # In the very rare case that you need to generate locations for a -# cross match, where every observation of `x` is forced to match every -# observation of `y` regardless of what the actual values are, you can +# cross match, where every value of `x` is forced to match every +# value of `y` regardless of what the actual values are, you can # replace `x` and `y` with integer vectors of the same size that contain # a single value and match on those instead. x_proxy <- vec_rep(1L, vec_size(x)) diff --git a/tests/testthat/_snaps/match.md b/tests/testthat/_snaps/match.md index fbddbabe6..2a30183d6 100644 --- a/tests/testthat/_snaps/match.md +++ b/tests/testthat/_snaps/match.md @@ -20,7 +20,7 @@ vec_locate_matches(x, y) Condition Error in `vec_locate_matches()`: - ! Can't combine and . + ! Can't combine `needles` and `haystack` . --- @@ -28,7 +28,7 @@ vec_locate_matches(x, y, needles_arg = "x", error_call = call("foo")) Condition Error in `foo()`: - ! Can't combine `x` and . + ! Can't combine `x` and `haystack` . # `incomplete` can error informatively @@ -37,24 +37,24 @@ Output Error in `vec_locate_matches()`: - ! No element can contain missing values. - x The element at location 1 contains missing values. + ! `needles` can't contain missing values. + x Location 1 contains missing values. Code (expect_error(vec_locate_matches(NA, 1, incomplete = "error", needles_arg = "foo")) ) Output Error in `vec_locate_matches()`: - ! No element of `foo` can contain missing values. - x The element at location 1 contains missing values. + ! `foo` can't contain missing values. + x Location 1 contains missing values. Code (expect_error(vec_locate_matches(NA, 1, incomplete = "error", needles_arg = "foo", error_call = call("fn")))) Output Error in `fn()`: - ! No element of `foo` can contain missing values. - x The element at location 1 contains missing values. + ! `foo` can't contain missing values. + x Location 1 contains missing values. # `incomplete` is validated @@ -120,32 +120,32 @@ Output Error in `vec_locate_matches()`: - ! Each element can match at most 1 observation. - x The element at location 1 has multiple matches. + ! Each value of `needles` can match at most 1 value from `haystack`. + x Location 1 of `needles` matches multiple values. Code (expect_error(vec_locate_matches(1L, c(1L, 1L), multiple = "error", needles_arg = "foo"))) Output Error in `vec_locate_matches()`: - ! Each element of `foo` can match at most 1 observation. - x The element at location 1 has multiple matches. + ! Each value of `foo` can match at most 1 value from `haystack`. + x Location 1 of `foo` matches multiple values. Code (expect_error(vec_locate_matches(1L, c(1L, 1L), multiple = "error", needles_arg = "foo", error_call = call("fn")))) Output Error in `fn()`: - ! Each element of `foo` can match at most 1 observation. - x The element at location 1 has multiple matches. + ! Each value of `foo` can match at most 1 value from `haystack`. + x Location 1 of `foo` matches multiple values. Code (expect_error(vec_locate_matches(1L, c(1L, 1L), multiple = "error", needles_arg = "foo", haystack_arg = "bar"))) Output Error in `vec_locate_matches()`: - ! Each element of `foo` can match at most 1 observation from `bar`. - x The element at location 1 has multiple matches. + ! Each value of `foo` can match at most 1 value from `bar`. + x Location 1 of `foo` matches multiple values. # `multiple` can warn informatively @@ -154,32 +154,50 @@ Output Warning in `vec_locate_matches()`: - Each element can match at most 1 observation. - x The element at location 1 has multiple matches. + Each value of `needles` can match at most 1 value from `haystack`. + x Location 1 of `needles` matches multiple values. Code (expect_warning(vec_locate_matches(1L, c(1L, 1L), multiple = "warning", needles_arg = "foo"))) Output Warning in `vec_locate_matches()`: - Each element of `foo` can match at most 1 observation. - x The element at location 1 has multiple matches. + Each value of `foo` can match at most 1 value from `haystack`. + x Location 1 of `foo` matches multiple values. Code (expect_warning(vec_locate_matches(1L, c(1L, 1L), multiple = "warning", needles_arg = "foo", error_call = call("fn")))) Output Warning in `fn()`: - Each element of `foo` can match at most 1 observation. - x The element at location 1 has multiple matches. + Each value of `foo` can match at most 1 value from `haystack`. + x Location 1 of `foo` matches multiple values. Code (expect_warning(vec_locate_matches(1L, c(1L, 1L), multiple = "warning", needles_arg = "foo", haystack_arg = "bar"))) Output Warning in `vec_locate_matches()`: - Each element of `foo` can match at most 1 observation from `bar`. - x The element at location 1 has multiple matches. + Each value of `foo` can match at most 1 value from `bar`. + x Location 1 of `foo` matches multiple values. + +# errors on multiple matches that come from different nesting containers + + Code + vec_locate_matches(df, df2, condition = c("<=", "<="), multiple = "error") + Condition + Error in `vec_locate_matches()`: + ! Each value of `needles` can match at most 1 value from `haystack`. + x Location 1 of `needles` matches multiple values. + +# errors when a match from a different nesting container is processed early on + + Code + vec_locate_matches(needles, haystack, condition = "<", multiple = "error") + Condition + Error in `vec_locate_matches()`: + ! Each value of `needles` can match at most 1 value from `haystack`. + x Location 1 of `needles` matches multiple values. # `relationship` handles one-to-one case @@ -189,16 +207,16 @@ Output Error in `vec_locate_matches()`: - ! Each element can match at most 1 observation. - x The element at location 2 has multiple matches. + ! Each value of `needles` can match at most 1 value from `haystack`. + x Location 2 of `needles` matches multiple values. Code (expect_error(vec_locate_matches(c(1, 1), c(1, 2), relationship = "one_to_one")) ) Output Error in `vec_locate_matches()`: - ! Each element can match at most 1 observation. - x The element at location 1 has multiple matches. + ! Each value of `haystack` can match at most 1 value from `needles`. + x Location 1 of `haystack` matches multiple values. # `relationship` handles one-to-many case @@ -208,8 +226,8 @@ Output Error in `vec_locate_matches()`: - ! Each element can match at most 1 observation. - x The element at location 1 has multiple matches. + ! Each value of `haystack` can match at most 1 value from `needles`. + x Location 1 of `haystack` matches multiple values. # `relationship` handles many-to-one case @@ -219,8 +237,8 @@ Output Error in `vec_locate_matches()`: - ! Each element can match at most 1 observation. - x The element at location 2 has multiple matches. + ! Each value of `needles` can match at most 1 value from `haystack`. + x Location 2 of `needles` matches multiple values. # `relationship` handles warn-many-to-many case @@ -230,18 +248,18 @@ Output Warning in `vec_locate_matches()`: - Detected an unexpected many-to-many relationship. - x The element at location 2 has multiple matches. - x The element at location 1 has multiple matches. + Detected an unexpected many-to-many relationship between `needles` and `haystack`. + x Location 2 of `needles` matches multiple values. + x Location 1 of `haystack` matches multiple values. Code (expect_warning(vec_locate_matches(c(1, 1, 2), c(2, 2, 1), relationship = "warn_many_to_many")) ) Output Warning in `vec_locate_matches()`: - Detected an unexpected many-to-many relationship. - x The element at location 3 has multiple matches. - x The element at location 3 has multiple matches. + Detected an unexpected many-to-many relationship between `needles` and `haystack`. + x Location 3 of `needles` matches multiple values. + x Location 3 of `haystack` matches multiple values. # `relationship` considers `incomplete` matches as possible multiple matches @@ -250,8 +268,8 @@ Output Error in `vec_locate_matches()`: - ! Each element can match at most 1 observation. - x The element at location 1 has multiple matches. + ! Each value of `haystack` can match at most 1 value from `needles`. + x Location 1 of `haystack` matches multiple values. # `relationship` errors on multiple matches that come from different nesting containers @@ -261,8 +279,8 @@ Output Error in `vec_locate_matches()`: - ! Each element can match at most 1 observation. - x The element at location 1 has multiple matches. + ! Each value of `needles` can match at most 1 value from `haystack`. + x Location 1 of `needles` matches multiple values. # `relationship` errors when a match from a different nesting container is processed early on @@ -272,8 +290,8 @@ Output Error in `vec_locate_matches()`: - ! Each element can match at most 1 observation. - x The element at location 1 has multiple matches. + ! Each value of `needles` can match at most 1 value from `haystack`. + x Location 1 of `needles` matches multiple values. # `relationship` can still detect problematic `haystack` relationships when `multiple = first/last` are used @@ -283,16 +301,16 @@ Output Error in `vec_locate_matches()`: - ! Each element can match at most 1 observation. - x The element at location 2 has multiple matches. + ! Each value of `haystack` can match at most 1 value from `needles`. + x Location 2 of `haystack` matches multiple values. Code (expect_error(vec_locate_matches(c(3, 1, 1), c(2, 1, 3, 3), multiple = "first", relationship = "one_to_many"))) Output Error in `vec_locate_matches()`: - ! Each element can match at most 1 observation. - x The element at location 2 has multiple matches. + ! Each value of `haystack` can match at most 1 value from `needles`. + x Location 2 of `haystack` matches multiple values. # `relationship` and `remaining` work properly together @@ -301,9 +319,9 @@ remaining = NA_integer_) Condition Warning in `vec_locate_matches()`: - Detected an unexpected many-to-many relationship. - x The element at location 1 has multiple matches. - x The element at location 1 has multiple matches. + Detected an unexpected many-to-many relationship between `needles` and `haystack`. + x Location 1 of `needles` matches multiple values. + x Location 1 of `haystack` matches multiple values. # `relationship` errors if `condition` creates multiple matches @@ -313,8 +331,8 @@ Output Error in `vec_locate_matches()`: - ! Each element can match at most 1 observation. - x The element at location 1 has multiple matches. + ! Each value of `needles` can match at most 1 value from `haystack`. + x Location 1 of `needles` matches multiple values. # `relationship` still errors if `filter` hasn't removed all multiple matches @@ -324,8 +342,8 @@ Output Error in `vec_locate_matches()`: - ! Each element can match at most 1 observation. - x The element at location 1 has multiple matches. + ! Each value of `needles` can match at most 1 value from `haystack`. + x Location 1 of `needles` matches multiple values. # `relationship` errors respect argument tags and error call @@ -335,32 +353,32 @@ Output Error in `fn()`: - ! Each element of `foo` can match at most 1 observation from `bar`. - x The element of `foo` at location 1 has multiple matches. + ! Each value of `foo` can match at most 1 value from `bar`. + x Location 1 of `foo` matches multiple values. Code (expect_error(vec_locate_matches(c(1L, 1L), 1L, relationship = "one_to_one", needles_arg = "foo", haystack_arg = "bar", error_call = call("fn")))) Output Error in `fn()`: - ! Each element of `bar` can match at most 1 observation from `foo`. - x The element of `bar` at location 1 has multiple matches. + ! Each value of `bar` can match at most 1 value from `foo`. + x Location 1 of `bar` matches multiple values. Code (expect_error(vec_locate_matches(c(1L, 1L), 1L, relationship = "one_to_many", needles_arg = "foo", haystack_arg = "bar", error_call = call("fn")))) Output Error in `fn()`: - ! Each element of `bar` can match at most 1 observation from `foo`. - x The element of `bar` at location 1 has multiple matches. + ! Each value of `bar` can match at most 1 value from `foo`. + x Location 1 of `bar` matches multiple values. Code (expect_error(vec_locate_matches(1L, c(1L, 1L), relationship = "many_to_one", needles_arg = "foo", haystack_arg = "bar", error_call = call("fn")))) Output Error in `fn()`: - ! Each element of `foo` can match at most 1 observation from `bar`. - x The element of `foo` at location 1 has multiple matches. + ! Each value of `foo` can match at most 1 value from `bar`. + x Location 1 of `foo` matches multiple values. # `relationship` warnings respect argument tags and error call @@ -371,26 +389,26 @@ Warning in `fn()`: Detected an unexpected many-to-many relationship between `foo` and `bar`. - x The element of `foo` at location 1 has multiple matches. - x The element of `bar` at location 1 has multiple matches. + x Location 1 of `foo` matches multiple values. + x Location 1 of `bar` matches multiple values. Code (expect_warning(vec_locate_matches(c(1L, 1L), c(1L, 1L), relationship = "warn_many_to_many", needles_arg = "foo", error_call = call("fn")))) Output Warning in `fn()`: - Detected an unexpected many-to-many relationship. - x The element of `foo` at location 1 has multiple matches. - x The element at location 1 has multiple matches. + Detected an unexpected many-to-many relationship between `foo` and `haystack`. + x Location 1 of `foo` matches multiple values. + x Location 1 of `haystack` matches multiple values. Code (expect_warning(vec_locate_matches(c(1L, 1L), c(1L, 1L), relationship = "warn_many_to_many", haystack_arg = "bar", error_call = call("fn")))) Output Warning in `fn()`: - Detected an unexpected many-to-many relationship. - x The element at location 1 has multiple matches. - x The element of `bar` at location 1 has multiple matches. + Detected an unexpected many-to-many relationship between `needles` and `bar`. + x Location 1 of `needles` matches multiple values. + x Location 1 of `bar` matches multiple values. # `relationship` is validated @@ -428,32 +446,32 @@ Output Error in `vec_locate_matches()`: - ! Each element must have a match. - x The element at location 1 does not have a match. + ! Each value of `needles` must have a match in `haystack`. + x Location 1 of `needles` does not have a match. Code (expect_error(vec_locate_matches(1, 2, no_match = "error", needles_arg = "foo")) ) Output Error in `vec_locate_matches()`: - ! Each element of `foo` must have a match. - x The element at location 1 does not have a match. + ! Each value of `foo` must have a match in `haystack`. + x Location 1 of `foo` does not have a match. Code (expect_error(vec_locate_matches(1, 2, no_match = "error", needles_arg = "foo", error_call = call("fn")))) Output Error in `fn()`: - ! Each element of `foo` must have a match. - x The element at location 1 does not have a match. + ! Each value of `foo` must have a match in `haystack`. + x Location 1 of `foo` does not have a match. Code (expect_error(vec_locate_matches(1, 2, no_match = "error", needles_arg = "foo", haystack_arg = "bar"))) Output Error in `vec_locate_matches()`: - ! Each element of `foo` must have a match in `bar`. - x The element at location 1 does not have a match. + ! Each value of `foo` must have a match in `bar`. + x Location 1 of `foo` does not have a match. # errors with the right location on unmatched needles when different nesting containers are present @@ -463,8 +481,8 @@ Output Error in `vec_locate_matches()`: - ! Each element must have a match. - x The element at location 2 does not have a match. + ! Each value of `needles` must have a match in `haystack`. + x Location 2 of `needles` does not have a match. # `no_match` is validated @@ -502,32 +520,32 @@ Output Error in `vec_locate_matches()`: - ! Each haystack value must be matched. - x The value at location 1 was not matched. + ! Each value of `haystack` must be matched by `needles`. + x Location 1 of `haystack` was not matched. Code (expect_error(vec_locate_matches(1, 2, remaining = "error", needles_arg = "foo")) ) Output Error in `vec_locate_matches()`: - ! Each haystack value must be matched by `foo`. - x The value at location 1 was not matched. + ! Each value of `haystack` must be matched by `foo`. + x Location 1 of `haystack` was not matched. Code (expect_error(vec_locate_matches(1, 2, remaining = "error", needles_arg = "foo", error_call = call("fn")))) Output Error in `fn()`: - ! Each haystack value must be matched by `foo`. - x The value at location 1 was not matched. + ! Each value of `haystack` must be matched by `foo`. + x Location 1 of `haystack` was not matched. Code (expect_error(vec_locate_matches(1, 2, remaining = "error", needles_arg = "foo", haystack_arg = "bar"))) Output Error in `vec_locate_matches()`: - ! Each haystack value of `bar` must be matched by `foo`. - x The value at location 1 was not matched. + ! Each value of `bar` must be matched by `foo`. + x Location 1 of `bar` was not matched. # `remaining` is validated diff --git a/tests/testthat/test-match.R b/tests/testthat/test-match.R index 7fe1d67cf..aa5b9de09 100644 --- a/tests/testthat/test-match.R +++ b/tests/testthat/test-match.R @@ -1004,10 +1004,9 @@ test_that("errors on multiple matches that come from different nesting container df <- data_frame(x = 0, y = 0) df2 <- data_frame(x = 1:2, y = 2:1) - expect_error( - vec_locate_matches(df, df2, condition = c("<=", "<="), multiple = "error"), - "multiple matches" - ) + expect_snapshot(error = TRUE, { + vec_locate_matches(df, df2, condition = c("<=", "<="), multiple = "error") + }) }) test_that("errors when a match from a different nesting container is processed early on", { @@ -1029,10 +1028,9 @@ test_that("errors when a match from a different nesting container is processed e # which is in the 3rd value of `loc_first_match_o_haystack` even though it # is processed 2nd (i.e. we need to use `loc` rather than `i` when detecting # multiple matches) - expect_error( - vec_locate_matches(needles, haystack, condition = "<", multiple = "error"), - "multiple matches" - ) + expect_snapshot(error = TRUE, { + vec_locate_matches(needles, haystack, condition = "<", multiple = "error") + }) }) test_that("`multiple = 'error'` doesn't error errneously on the last observation", { From e66bcf9bb548df7260161e4a069ee75a69ed6f15 Mon Sep 17 00:00:00 2001 From: Davis Vaughan Date: Wed, 22 Feb 2023 12:54:58 -0500 Subject: [PATCH 233/312] Fix deprecated `multiple` options when combined with `relationship` (#1793) --- src/match.c | 42 ++++++++++++------ tests/testthat/_snaps/match.md | 79 ++++++++++++++++++++++++++++++++++ tests/testthat/test-match.R | 34 +++++++++++++++ 3 files changed, 141 insertions(+), 14 deletions(-) diff --git a/src/match.c b/src/match.c index 793e2ad2e..1a8106324 100644 --- a/src/match.c +++ b/src/match.c @@ -1834,6 +1834,30 @@ r_obj* expand_compact_indices(const int* v_o_haystack, if (any_multiple_needles) { loc_first_multiple_needles = loc_needles; + // TODO: Remove deprecated support for `multiple = "error"/"warning"` + switch (multiple) { + case VCTRS_MULTIPLE_all: + break; + case VCTRS_MULTIPLE_error: + stop_matches_multiple( + loc_first_multiple_needles, + needles_arg, + haystack_arg, + error_call + ); + case VCTRS_MULTIPLE_warning: { + warn_matches_multiple( + loc_first_multiple_needles, + needles_arg, + haystack_arg, + error_call + ); + break; + } + default: + r_stop_internal("`check_multiple_needles` should have been false."); + } + switch (relationship) { case VCTRS_RELATIONSHIP_one_to_one: stop_matches_relationship_one_to_one( @@ -1865,24 +1889,14 @@ r_obj* expand_compact_indices(const int* v_o_haystack, default: { switch (multiple) { case VCTRS_MULTIPLE_all: + // We are tracking if there are multiple matches, but don't throw + // any errors or warnings on them break; // TODO: Remove deprecated support for `multiple = "error"/"warning"` case VCTRS_MULTIPLE_error: - stop_matches_multiple( - loc_first_multiple_needles, - needles_arg, - haystack_arg, - error_call - ); - case VCTRS_MULTIPLE_warning: { - warn_matches_multiple( - loc_first_multiple_needles, - needles_arg, - haystack_arg, - error_call - ); + r_stop_internal("`multiple = 'error'` should have thrown by now."); + case VCTRS_MULTIPLE_warning: break; - } default: r_stop_internal("`check_multiple_needles` should have been false."); } diff --git a/tests/testthat/_snaps/match.md b/tests/testthat/_snaps/match.md index 2a30183d6..23288214d 100644 --- a/tests/testthat/_snaps/match.md +++ b/tests/testthat/_snaps/match.md @@ -199,6 +199,85 @@ ! Each value of `needles` can match at most 1 value from `haystack`. x Location 1 of `needles` matches multiple values. +# `multiple = 'error' / 'warning'` throw correctly when combined with `relationship` + + Code + (expect_error(vec_locate_matches(x, y, relationship = "one_to_one", multiple = "error")) + ) + Output + + Error in `vec_locate_matches()`: + ! Each value of `needles` can match at most 1 value from `haystack`. + x Location 2 of `needles` matches multiple values. + +--- + + Code + (expect_error(vec_locate_matches(x, y, relationship = "warn_many_to_many", + multiple = "error"))) + Output + + Error in `vec_locate_matches()`: + ! Each value of `needles` can match at most 1 value from `haystack`. + x Location 2 of `needles` matches multiple values. + +--- + + Code + vec_locate_matches(x, y, relationship = "warn_many_to_many", multiple = "warning") + Condition + Warning in `vec_locate_matches()`: + Each value of `needles` can match at most 1 value from `haystack`. + x Location 2 of `needles` matches multiple values. + Warning in `vec_locate_matches()`: + Detected an unexpected many-to-many relationship between `needles` and `haystack`. + x Location 2 of `needles` matches multiple values. + x Location 1 of `haystack` matches multiple values. + Output + needles haystack + 1 1 2 + 2 2 1 + 3 2 3 + 4 3 1 + 5 3 3 + +--- + + Code + vec_locate_matches(x, y, relationship = "one_to_one", multiple = "warning") + Condition + Warning in `vec_locate_matches()`: + Each value of `needles` can match at most 1 value from `haystack`. + x Location 2 of `needles` matches multiple values. + Error in `vec_locate_matches()`: + ! Each value of `needles` can match at most 1 value from `haystack`. + x Location 2 of `needles` matches multiple values. + +--- + + Code + (expect_error(vec_locate_matches(x, y, relationship = "warn_many_to_many", + multiple = "error"))) + Output + + Error in `vec_locate_matches()`: + ! Each value of `needles` can match at most 1 value from `haystack`. + x Location 2 of `needles` matches multiple values. + +--- + + Code + vec_locate_matches(x, y, relationship = "warn_many_to_many", multiple = "warning") + Condition + Warning in `vec_locate_matches()`: + Each value of `needles` can match at most 1 value from `haystack`. + x Location 2 of `needles` matches multiple values. + Output + needles haystack + 1 1 2 + 2 2 1 + 3 2 3 + # `relationship` handles one-to-one case Code diff --git a/tests/testthat/test-match.R b/tests/testthat/test-match.R index aa5b9de09..cdccd1c7a 100644 --- a/tests/testthat/test-match.R +++ b/tests/testthat/test-match.R @@ -1039,6 +1039,40 @@ test_that("`multiple = 'error'` doesn't error errneously on the last observation expect_identical(res$haystack, 1:2) }) +test_that("`multiple = 'error' / 'warning'` throw correctly when combined with `relationship`", { + x <- c(1, 2, 2) + y <- c(2, 1, 2) + + # `multiple` error technically fires first + expect_snapshot({ + (expect_error(vec_locate_matches(x, y, relationship = "one_to_one", multiple = "error"))) + }) + + # Works when warning is also requested + expect_snapshot({ + (expect_error(vec_locate_matches(x, y, relationship = "warn_many_to_many", multiple = "error"))) + }) + # Both warnings are thrown if applicable + expect_snapshot({ + vec_locate_matches(x, y, relationship = "warn_many_to_many", multiple = "warning") + }) + # Both warning and error are thrown if applicable + expect_snapshot(error = TRUE, { + vec_locate_matches(x, y, relationship = "one_to_one", multiple = "warning") + }) + + x <- c(1, 2) + y <- c(2, 1, 2) + + expect_snapshot({ + (expect_error(vec_locate_matches(x, y, relationship = "warn_many_to_many", multiple = "error"))) + }) + # Only `multiple` warning is applicable here + expect_snapshot({ + vec_locate_matches(x, y, relationship = "warn_many_to_many", multiple = "warning") + }) +}) + # ------------------------------------------------------------------------------ # vec_locate_matches() - `relationship` From 2fabdc7f6bf83af43afcd5ab79e184a3919ec1fc Mon Sep 17 00:00:00 2001 From: Davis Vaughan Date: Fri, 24 Feb 2023 12:49:57 -0500 Subject: [PATCH 234/312] Use `-` rather than `_` for `relationship` options (#1795) Because: - `one-to-one` is the name of the entire concept, and is how we refer to it in documentation, so it does make sense here to use hyphens even though we often use `_` - It is slightly faster to type - We just accept that we then inherit `warn-many-to-many` because `warn_many-to-many` would be too awkward. This shouldn't matter much because it won't be exposed anywhere else. --- NEWS.md | 2 +- R/match.R | 18 +++--- man/vec_locate_matches.Rd | 18 +++--- src/match.c | 14 ++--- tests/testthat/_snaps/match.md | 62 ++++++++++---------- tests/testthat/test-match.R | 100 ++++++++++++++++----------------- 6 files changed, 107 insertions(+), 107 deletions(-) diff --git a/NEWS.md b/NEWS.md index ef6e5817c..6b630f425 100644 --- a/NEWS.md +++ b/NEWS.md @@ -6,7 +6,7 @@ * `vec_locate_matches()` gains a new `relationship` argument that holistically handles multiple matches between `needles` and `haystack`. In particular, - `relationship = "many_to_one"` replaces `multiple = "error"` and + `relationship = "many-to-one"` replaces `multiple = "error"` and `multiple = "warning"`, which have been removed from the documentation and silently soft-deprecated. Official deprecation for those options will start in a future release (#1791). diff --git a/R/match.R b/R/match.R index f18f4c843..edf7cc1e1 100644 --- a/R/match.R +++ b/R/match.R @@ -138,30 +138,30 @@ #' #' - `"none"` doesn't perform any relationship checks. #' -#' - `"one_to_one"` expects: +#' - `"one-to-one"` expects: #' - Each value in `needles` matches at most 1 value in `haystack`. #' - Each value in `haystack` matches at most 1 value in `needles`. #' -#' - `"one_to_many"` expects: +#' - `"one-to-many"` expects: #' - Each value in `needles` matches any number of values in `haystack`. #' - Each value in `haystack` matches at most 1 value in `needles`. #' -#' - `"many_to_one"` expects: +#' - `"many-to-one"` expects: #' - Each value in `needles` matches at most 1 value in `haystack`. #' - Each value in `haystack` matches any number of values in `needles`. #' -#' - `"many_to_many"` expects: +#' - `"many-to-many"` expects: #' - Each value in `needles` matches any number of values in `haystack`. #' - Each value in `haystack` matches any number of values in `needles`. #' #' This performs no checks, and is identical to `"none"`, but is provided to #' allow you to be explicit about this relationship if you know it exists. #' -#' - `"warn_many_to_many"` doesn't assume there is any known relationship, but +#' - `"warn-many-to-many"` doesn't assume there is any known relationship, but #' will warn if `needles` and `haystack` have a many-to-many relationship #' (which is typically unexpected), encouraging you to either take a closer #' look at your inputs or make this relationship explicit by specifying -#' `"many_to_many"`. +#' `"many-to-many"`. #' #' `relationship` is applied after `filter` and `multiple` to allow potential #' multiple matches to be filtered out first. @@ -203,10 +203,10 @@ #' #' # Use `relationship` to add constraints and error on multiple matches if #' # they aren't expected -#' try(vec_locate_matches(x, y, relationship = "one_to_one")) +#' try(vec_locate_matches(x, y, relationship = "one-to-one")) #' #' # In this case, the `NA` in `y` matches two rows in `x` -#' try(vec_locate_matches(x, y, relationship = "one_to_many")) +#' try(vec_locate_matches(x, y, relationship = "one-to-many")) #' #' # By default, `NA` is treated as being identical to `NaN`. #' # Using `nan_distinct = TRUE` treats `NA` and `NaN` as different values, so @@ -220,7 +220,7 @@ #' #' # Using `incomplete = NA` allows us to enforce the one-to-many relationship #' # that we couldn't before -#' vec_locate_matches(x, y, relationship = "one_to_many", incomplete = NA) +#' vec_locate_matches(x, y, relationship = "one-to-many", incomplete = NA) #' #' # `no_match` allows you to specify the returned value for a needle with #' # zero matches. Note that this is different from an incomplete value, diff --git a/man/vec_locate_matches.Rd b/man/vec_locate_matches.Rd index cff0a0a0e..5bb11e40c 100644 --- a/man/vec_locate_matches.Rd +++ b/man/vec_locate_matches.Rd @@ -116,22 +116,22 @@ which match will be returned. It is often faster than \code{"first"} and are invalidated, an error is thrown. \itemize{ \item \code{"none"} doesn't perform any relationship checks. -\item \code{"one_to_one"} expects: +\item \code{"one-to-one"} expects: \itemize{ \item Each value in \code{needles} matches at most 1 value in \code{haystack}. \item Each value in \code{haystack} matches at most 1 value in \code{needles}. } -\item \code{"one_to_many"} expects: +\item \code{"one-to-many"} expects: \itemize{ \item Each value in \code{needles} matches any number of values in \code{haystack}. \item Each value in \code{haystack} matches at most 1 value in \code{needles}. } -\item \code{"many_to_one"} expects: +\item \code{"many-to-one"} expects: \itemize{ \item Each value in \code{needles} matches at most 1 value in \code{haystack}. \item Each value in \code{haystack} matches any number of values in \code{needles}. } -\item \code{"many_to_many"} expects: +\item \code{"many-to-many"} expects: \itemize{ \item Each value in \code{needles} matches any number of values in \code{haystack}. \item Each value in \code{haystack} matches any number of values in \code{needles}. @@ -139,11 +139,11 @@ are invalidated, an error is thrown. This performs no checks, and is identical to \code{"none"}, but is provided to allow you to be explicit about this relationship if you know it exists. -\item \code{"warn_many_to_many"} doesn't assume there is any known relationship, but +\item \code{"warn-many-to-many"} doesn't assume there is any known relationship, but will warn if \code{needles} and \code{haystack} have a many-to-many relationship (which is typically unexpected), encouraging you to either take a closer look at your inputs or make this relationship explicit by specifying -\code{"many_to_many"}. +\code{"many-to-many"}. } \code{relationship} is applied after \code{filter} and \code{multiple} to allow potential @@ -249,10 +249,10 @@ vec_locate_matches(x, y, multiple = "any") # Use `relationship` to add constraints and error on multiple matches if # they aren't expected -try(vec_locate_matches(x, y, relationship = "one_to_one")) +try(vec_locate_matches(x, y, relationship = "one-to-one")) # In this case, the `NA` in `y` matches two rows in `x` -try(vec_locate_matches(x, y, relationship = "one_to_many")) +try(vec_locate_matches(x, y, relationship = "one-to-many")) # By default, `NA` is treated as being identical to `NaN`. # Using `nan_distinct = TRUE` treats `NA` and `NaN` as different values, so @@ -266,7 +266,7 @@ vec_locate_matches(x, y, incomplete = NA) # Using `incomplete = NA` allows us to enforce the one-to-many relationship # that we couldn't before -vec_locate_matches(x, y, relationship = "one_to_many", incomplete = NA) +vec_locate_matches(x, y, relationship = "one-to-many", incomplete = NA) # `no_match` allows you to specify the returned value for a needle with # zero matches. Note that this is different from an incomplete value, diff --git a/src/match.c b/src/match.c index 1a8106324..548e846df 100644 --- a/src/match.c +++ b/src/match.c @@ -1404,15 +1404,15 @@ enum vctrs_relationship parse_relationship(r_obj* relationship, struct r_lazy ca const char* c_relationship = r_chr_get_c_string(relationship, 0); if (!strcmp(c_relationship, "none")) return VCTRS_RELATIONSHIP_none; - if (!strcmp(c_relationship, "one_to_one")) return VCTRS_RELATIONSHIP_one_to_one; - if (!strcmp(c_relationship, "one_to_many")) return VCTRS_RELATIONSHIP_one_to_many; - if (!strcmp(c_relationship, "many_to_one")) return VCTRS_RELATIONSHIP_many_to_one; - if (!strcmp(c_relationship, "many_to_many")) return VCTRS_RELATIONSHIP_many_to_many; - if (!strcmp(c_relationship, "warn_many_to_many")) return VCTRS_RELATIONSHIP_warn_many_to_many; + if (!strcmp(c_relationship, "one-to-one")) return VCTRS_RELATIONSHIP_one_to_one; + if (!strcmp(c_relationship, "one-to-many")) return VCTRS_RELATIONSHIP_one_to_many; + if (!strcmp(c_relationship, "many-to-one")) return VCTRS_RELATIONSHIP_many_to_one; + if (!strcmp(c_relationship, "many-to-many")) return VCTRS_RELATIONSHIP_many_to_many; + if (!strcmp(c_relationship, "warn-many-to-many")) return VCTRS_RELATIONSHIP_warn_many_to_many; r_abort_lazy_call( call, - "`relationship` must be one of \"none\", \"one_to_one\", \"one_to_many\", \"many_to_one\", \"many_to_many\", or \"warn_many_to_many\"." + "`relationship` must be one of \"none\", \"one-to-one\", \"one-to-many\", \"many-to-one\", \"many-to-many\", or \"warn-many-to-many\"." ); } @@ -1996,7 +1996,7 @@ r_obj* expand_compact_indices(const int* v_o_haystack, ); case VCTRS_RELATIONSHIP_warn_many_to_many: r_stop_internal( - "`relationship = 'warn_many_to_many'` with " + "`relationship = 'warn-many-to-many'` with " "`multiple = 'first'/'last' should have resulted in " "`check_multiple_haystack = false`." ); diff --git a/tests/testthat/_snaps/match.md b/tests/testthat/_snaps/match.md index 23288214d..505f80bab 100644 --- a/tests/testthat/_snaps/match.md +++ b/tests/testthat/_snaps/match.md @@ -202,7 +202,7 @@ # `multiple = 'error' / 'warning'` throw correctly when combined with `relationship` Code - (expect_error(vec_locate_matches(x, y, relationship = "one_to_one", multiple = "error")) + (expect_error(vec_locate_matches(x, y, relationship = "one-to-one", multiple = "error")) ) Output @@ -213,7 +213,7 @@ --- Code - (expect_error(vec_locate_matches(x, y, relationship = "warn_many_to_many", + (expect_error(vec_locate_matches(x, y, relationship = "warn-many-to-many", multiple = "error"))) Output @@ -224,7 +224,7 @@ --- Code - vec_locate_matches(x, y, relationship = "warn_many_to_many", multiple = "warning") + vec_locate_matches(x, y, relationship = "warn-many-to-many", multiple = "warning") Condition Warning in `vec_locate_matches()`: Each value of `needles` can match at most 1 value from `haystack`. @@ -244,7 +244,7 @@ --- Code - vec_locate_matches(x, y, relationship = "one_to_one", multiple = "warning") + vec_locate_matches(x, y, relationship = "one-to-one", multiple = "warning") Condition Warning in `vec_locate_matches()`: Each value of `needles` can match at most 1 value from `haystack`. @@ -256,7 +256,7 @@ --- Code - (expect_error(vec_locate_matches(x, y, relationship = "warn_many_to_many", + (expect_error(vec_locate_matches(x, y, relationship = "warn-many-to-many", multiple = "error"))) Output @@ -267,7 +267,7 @@ --- Code - vec_locate_matches(x, y, relationship = "warn_many_to_many", multiple = "warning") + vec_locate_matches(x, y, relationship = "warn-many-to-many", multiple = "warning") Condition Warning in `vec_locate_matches()`: Each value of `needles` can match at most 1 value from `haystack`. @@ -281,7 +281,7 @@ # `relationship` handles one-to-one case Code - (expect_error(vec_locate_matches(c(2, 1), c(1, 1), relationship = "one_to_one")) + (expect_error(vec_locate_matches(c(2, 1), c(1, 1), relationship = "one-to-one")) ) Output @@ -289,7 +289,7 @@ ! Each value of `needles` can match at most 1 value from `haystack`. x Location 2 of `needles` matches multiple values. Code - (expect_error(vec_locate_matches(c(1, 1), c(1, 2), relationship = "one_to_one")) + (expect_error(vec_locate_matches(c(1, 1), c(1, 2), relationship = "one-to-one")) ) Output @@ -300,7 +300,7 @@ # `relationship` handles one-to-many case Code - (expect_error(vec_locate_matches(c(1, 2, 2), c(2, 1), relationship = "one_to_many")) + (expect_error(vec_locate_matches(c(1, 2, 2), c(2, 1), relationship = "one-to-many")) ) Output @@ -311,7 +311,7 @@ # `relationship` handles many-to-one case Code - (expect_error(vec_locate_matches(c(1, 2), c(1, 2, 2), relationship = "many_to_one")) + (expect_error(vec_locate_matches(c(1, 2), c(1, 2, 2), relationship = "many-to-one")) ) Output @@ -322,7 +322,7 @@ # `relationship` handles warn-many-to-many case Code - (expect_warning(vec_locate_matches(c(1, 2, 1), c(1, 2, 2), relationship = "warn_many_to_many")) + (expect_warning(vec_locate_matches(c(1, 2, 1), c(1, 2, 2), relationship = "warn-many-to-many")) ) Output @@ -331,7 +331,7 @@ x Location 2 of `needles` matches multiple values. x Location 1 of `haystack` matches multiple values. Code - (expect_warning(vec_locate_matches(c(1, 1, 2), c(2, 2, 1), relationship = "warn_many_to_many")) + (expect_warning(vec_locate_matches(c(1, 1, 2), c(2, 2, 1), relationship = "warn-many-to-many")) ) Output @@ -343,7 +343,7 @@ # `relationship` considers `incomplete` matches as possible multiple matches Code - (expect_error(vec_locate_matches(x, y, relationship = "one_to_many"))) + (expect_error(vec_locate_matches(x, y, relationship = "one-to-many"))) Output Error in `vec_locate_matches()`: @@ -354,7 +354,7 @@ Code (expect_error(vec_locate_matches(df, df2, condition = c("<=", "<="), - relationship = "many_to_one"))) + relationship = "many-to-one"))) Output Error in `vec_locate_matches()`: @@ -365,7 +365,7 @@ Code (expect_error(vec_locate_matches(needles, haystack, condition = "<", - relationship = "many_to_one"))) + relationship = "many-to-one"))) Output Error in `vec_locate_matches()`: @@ -376,7 +376,7 @@ Code (expect_error(vec_locate_matches(c(3, 1, 1), c(2, 1, 3, 3), multiple = "first", - relationship = "one_to_one"))) + relationship = "one-to-one"))) Output Error in `vec_locate_matches()`: @@ -384,7 +384,7 @@ x Location 2 of `haystack` matches multiple values. Code (expect_error(vec_locate_matches(c(3, 1, 1), c(2, 1, 3, 3), multiple = "first", - relationship = "one_to_many"))) + relationship = "one-to-many"))) Output Error in `vec_locate_matches()`: @@ -394,7 +394,7 @@ # `relationship` and `remaining` work properly together Code - out <- vec_locate_matches(c(1, 2, 2), c(2, 3, 1, 1, 4), relationship = "warn_many_to_many", + out <- vec_locate_matches(c(1, 2, 2), c(2, 3, 1, 1, 4), relationship = "warn-many-to-many", remaining = NA_integer_) Condition Warning in `vec_locate_matches()`: @@ -405,7 +405,7 @@ # `relationship` errors if `condition` creates multiple matches Code - (expect_error(vec_locate_matches(1, c(1, 2), condition = "<=", relationship = "many_to_one")) + (expect_error(vec_locate_matches(1, c(1, 2), condition = "<=", relationship = "many-to-one")) ) Output @@ -417,7 +417,7 @@ Code (expect_error(vec_locate_matches(1, c(1, 2, 1), condition = "<=", filter = "min", - relationship = "many_to_one"))) + relationship = "many-to-one"))) Output Error in `vec_locate_matches()`: @@ -427,7 +427,7 @@ # `relationship` errors respect argument tags and error call Code - (expect_error(vec_locate_matches(1L, c(1L, 1L), relationship = "one_to_one", + (expect_error(vec_locate_matches(1L, c(1L, 1L), relationship = "one-to-one", needles_arg = "foo", haystack_arg = "bar", error_call = call("fn")))) Output @@ -435,7 +435,7 @@ ! Each value of `foo` can match at most 1 value from `bar`. x Location 1 of `foo` matches multiple values. Code - (expect_error(vec_locate_matches(c(1L, 1L), 1L, relationship = "one_to_one", + (expect_error(vec_locate_matches(c(1L, 1L), 1L, relationship = "one-to-one", needles_arg = "foo", haystack_arg = "bar", error_call = call("fn")))) Output @@ -443,7 +443,7 @@ ! Each value of `bar` can match at most 1 value from `foo`. x Location 1 of `bar` matches multiple values. Code - (expect_error(vec_locate_matches(c(1L, 1L), 1L, relationship = "one_to_many", + (expect_error(vec_locate_matches(c(1L, 1L), 1L, relationship = "one-to-many", needles_arg = "foo", haystack_arg = "bar", error_call = call("fn")))) Output @@ -451,7 +451,7 @@ ! Each value of `bar` can match at most 1 value from `foo`. x Location 1 of `bar` matches multiple values. Code - (expect_error(vec_locate_matches(1L, c(1L, 1L), relationship = "many_to_one", + (expect_error(vec_locate_matches(1L, c(1L, 1L), relationship = "many-to-one", needles_arg = "foo", haystack_arg = "bar", error_call = call("fn")))) Output @@ -462,7 +462,7 @@ # `relationship` warnings respect argument tags and error call Code - (expect_warning(vec_locate_matches(c(1L, 1L), c(1L, 1L), relationship = "warn_many_to_many", + (expect_warning(vec_locate_matches(c(1L, 1L), c(1L, 1L), relationship = "warn-many-to-many", needles_arg = "foo", haystack_arg = "bar", error_call = call("fn")))) Output @@ -471,7 +471,7 @@ x Location 1 of `foo` matches multiple values. x Location 1 of `bar` matches multiple values. Code - (expect_warning(vec_locate_matches(c(1L, 1L), c(1L, 1L), relationship = "warn_many_to_many", + (expect_warning(vec_locate_matches(c(1L, 1L), c(1L, 1L), relationship = "warn-many-to-many", needles_arg = "foo", error_call = call("fn")))) Output @@ -480,7 +480,7 @@ x Location 1 of `foo` matches multiple values. x Location 1 of `haystack` matches multiple values. Code - (expect_warning(vec_locate_matches(c(1L, 1L), c(1L, 1L), relationship = "warn_many_to_many", + (expect_warning(vec_locate_matches(c(1L, 1L), c(1L, 1L), relationship = "warn-many-to-many", haystack_arg = "bar", error_call = call("fn")))) Output @@ -498,8 +498,8 @@ Error in `vec_locate_matches()`: ! `relationship` must be a string. Code - (expect_error(vec_locate_matches(1, 2, relationship = c("one_to_one", - "one_to_many")))) + (expect_error(vec_locate_matches(1, 2, relationship = c("one-to-one", + "one-to-many")))) Output Error in `vec_locate_matches()`: @@ -509,14 +509,14 @@ Output Error in `vec_locate_matches()`: - ! `relationship` must be one of "none", "one_to_one", "one_to_many", "many_to_one", "many_to_many", or "warn_many_to_many". + ! `relationship` must be one of "none", "one-to-one", "one-to-many", "many-to-one", "many-to-many", or "warn-many-to-many". Code (expect_error(vec_locate_matches(1, 2, relationship = "x", error_call = call( "fn")))) Output Error in `vec_locate_matches()`: - ! `relationship` must be one of "none", "one_to_one", "one_to_many", "many_to_one", "many_to_many", or "warn_many_to_many". + ! `relationship` must be one of "none", "one-to-one", "one-to-many", "many-to-one", "many-to-many", or "warn-many-to-many". # `no_match` can error informatively diff --git a/tests/testthat/test-match.R b/tests/testthat/test-match.R index cdccd1c7a..ca8c52ccc 100644 --- a/tests/testthat/test-match.R +++ b/tests/testthat/test-match.R @@ -1045,31 +1045,31 @@ test_that("`multiple = 'error' / 'warning'` throw correctly when combined with ` # `multiple` error technically fires first expect_snapshot({ - (expect_error(vec_locate_matches(x, y, relationship = "one_to_one", multiple = "error"))) + (expect_error(vec_locate_matches(x, y, relationship = "one-to-one", multiple = "error"))) }) # Works when warning is also requested expect_snapshot({ - (expect_error(vec_locate_matches(x, y, relationship = "warn_many_to_many", multiple = "error"))) + (expect_error(vec_locate_matches(x, y, relationship = "warn-many-to-many", multiple = "error"))) }) # Both warnings are thrown if applicable expect_snapshot({ - vec_locate_matches(x, y, relationship = "warn_many_to_many", multiple = "warning") + vec_locate_matches(x, y, relationship = "warn-many-to-many", multiple = "warning") }) # Both warning and error are thrown if applicable expect_snapshot(error = TRUE, { - vec_locate_matches(x, y, relationship = "one_to_one", multiple = "warning") + vec_locate_matches(x, y, relationship = "one-to-one", multiple = "warning") }) x <- c(1, 2) y <- c(2, 1, 2) expect_snapshot({ - (expect_error(vec_locate_matches(x, y, relationship = "warn_many_to_many", multiple = "error"))) + (expect_error(vec_locate_matches(x, y, relationship = "warn-many-to-many", multiple = "error"))) }) # Only `multiple` warning is applicable here expect_snapshot({ - vec_locate_matches(x, y, relationship = "warn_many_to_many", multiple = "warning") + vec_locate_matches(x, y, relationship = "warn-many-to-many", multiple = "warning") }) }) @@ -1079,80 +1079,80 @@ test_that("`multiple = 'error' / 'warning'` throw correctly when combined with ` test_that("`relationship` handles one-to-one case", { # No error expect_identical( - vec_locate_matches(1:2, 2:1, relationship = "one_to_one"), + vec_locate_matches(1:2, 2:1, relationship = "one-to-one"), vec_locate_matches(1:2, 2:1) ) # Doesn't care about the zero match case expect_identical( - vec_locate_matches(1:2, 3:4, relationship = "one_to_one"), + vec_locate_matches(1:2, 3:4, relationship = "one-to-one"), vec_locate_matches(1:2, 3:4) ) expect_snapshot({ - (expect_error(vec_locate_matches(c(2, 1), c(1, 1), relationship = "one_to_one"))) - (expect_error(vec_locate_matches(c(1, 1), c(1, 2), relationship = "one_to_one"))) + (expect_error(vec_locate_matches(c(2, 1), c(1, 1), relationship = "one-to-one"))) + (expect_error(vec_locate_matches(c(1, 1), c(1, 2), relationship = "one-to-one"))) }) }) test_that("`relationship` handles one-to-many case", { # No error expect_identical( - vec_locate_matches(c(1, 2), c(1, 2, 2), relationship = "one_to_many"), + vec_locate_matches(c(1, 2), c(1, 2, 2), relationship = "one-to-many"), vec_locate_matches(c(1, 2), c(1, 2, 2)) ) # Doesn't care about the zero match case expect_identical( - vec_locate_matches(1:2, 3:4, relationship = "one_to_many"), + vec_locate_matches(1:2, 3:4, relationship = "one-to-many"), vec_locate_matches(1:2, 3:4) ) expect_snapshot({ - (expect_error(vec_locate_matches(c(1, 2, 2), c(2, 1), relationship = "one_to_many"))) + (expect_error(vec_locate_matches(c(1, 2, 2), c(2, 1), relationship = "one-to-many"))) }) }) test_that("`relationship` handles many-to-one case", { # No error expect_identical( - vec_locate_matches(c(1, 2, 2), c(1, 2), relationship = "many_to_one"), + vec_locate_matches(c(1, 2, 2), c(1, 2), relationship = "many-to-one"), vec_locate_matches(c(1, 2, 2), c(1, 2)) ) # Doesn't care about the zero match case expect_identical( - vec_locate_matches(1:2, 3:4, relationship = "many_to_one"), + vec_locate_matches(1:2, 3:4, relationship = "many-to-one"), vec_locate_matches(1:2, 3:4) ) expect_snapshot({ - (expect_error(vec_locate_matches(c(1, 2), c(1, 2, 2), relationship = "many_to_one"))) + (expect_error(vec_locate_matches(c(1, 2), c(1, 2, 2), relationship = "many-to-one"))) }) }) test_that("`relationship` handles many-to-many case", { # No error expect_identical( - vec_locate_matches(c(1, 2, 2), c(1, 2), relationship = "many_to_many"), + vec_locate_matches(c(1, 2, 2), c(1, 2), relationship = "many-to-many"), vec_locate_matches(c(1, 2, 2), c(1, 2)) ) # No error expect_identical( - vec_locate_matches(c(1, 2), c(1, 2, 2), relationship = "many_to_many"), + vec_locate_matches(c(1, 2), c(1, 2, 2), relationship = "many-to-many"), vec_locate_matches(c(1, 2), c(1, 2, 2)) ) # No error expect_identical( - vec_locate_matches(c(1, 1, 2), c(1, 2, 2), relationship = "many_to_many"), + vec_locate_matches(c(1, 1, 2), c(1, 2, 2), relationship = "many-to-many"), vec_locate_matches(c(1, 1, 2), c(1, 2, 2)) ) # Doesn't care about the zero match case expect_identical( - vec_locate_matches(1:2, 3:4, relationship = "many_to_many"), + vec_locate_matches(1:2, 3:4, relationship = "many-to-many"), vec_locate_matches(1:2, 3:4) ) }) @@ -1161,7 +1161,7 @@ test_that("`relationship` handles warn-many-to-many case", { # No warning expect_identical( expect_silent( - vec_locate_matches(c(1, 2, 2), c(1, 2), relationship = "warn_many_to_many") + vec_locate_matches(c(1, 2, 2), c(1, 2), relationship = "warn-many-to-many") ), vec_locate_matches(c(1, 2, 2), c(1, 2)) ) @@ -1169,7 +1169,7 @@ test_that("`relationship` handles warn-many-to-many case", { # No warning expect_identical( expect_silent( - vec_locate_matches(c(1, 2), c(1, 2, 2), relationship = "warn_many_to_many") + vec_locate_matches(c(1, 2), c(1, 2, 2), relationship = "warn-many-to-many") ), vec_locate_matches(c(1, 2), c(1, 2, 2)) ) @@ -1177,7 +1177,7 @@ test_that("`relationship` handles warn-many-to-many case", { # Doesn't care about the zero match case expect_identical( expect_silent( - vec_locate_matches(1:2, 3:4, relationship = "warn_many_to_many") + vec_locate_matches(1:2, 3:4, relationship = "warn-many-to-many") ), vec_locate_matches(1:2, 3:4) ) @@ -1186,8 +1186,8 @@ test_that("`relationship` handles warn-many-to-many case", { # - Finding multiple `needles` matches before multiple `haystack` matches # - Finding multiple `haystack` matches before multiple `needles` matches expect_snapshot({ - (expect_warning(vec_locate_matches(c(1, 2, 1), c(1, 2, 2), relationship = "warn_many_to_many"))) - (expect_warning(vec_locate_matches(c(1, 1, 2), c(2, 2, 1), relationship = "warn_many_to_many"))) + (expect_warning(vec_locate_matches(c(1, 2, 1), c(1, 2, 2), relationship = "warn-many-to-many"))) + (expect_warning(vec_locate_matches(c(1, 1, 2), c(2, 2, 1), relationship = "warn-many-to-many"))) }) }) @@ -1196,18 +1196,18 @@ test_that("`relationship` considers `incomplete` matches as possible multiple ma y <- c(NA, 1) expect_snapshot({ - (expect_error(vec_locate_matches(x, y, relationship = "one_to_many"))) + (expect_error(vec_locate_matches(x, y, relationship = "one-to-many"))) }) # No error expect_identical( - vec_locate_matches(x, y, relationship = "one_to_many", incomplete = NA), + vec_locate_matches(x, y, relationship = "one-to-many", incomplete = NA), vec_locate_matches(x, y, incomplete = NA) ) # No error expect_identical( - vec_locate_matches(x, y, relationship = "one_to_many", nan_distinct = TRUE), + vec_locate_matches(x, y, relationship = "one-to-many", nan_distinct = TRUE), vec_locate_matches(x, y, nan_distinct = TRUE) ) }) @@ -1217,7 +1217,7 @@ test_that("`relationship` errors on multiple matches that come from different ne df2 <- data_frame(x = 1:2, y = 2:1) expect_snapshot({ - (expect_error(vec_locate_matches(df, df2, condition = c("<=", "<="), relationship = "many_to_one"))) + (expect_error(vec_locate_matches(df, df2, condition = c("<=", "<="), relationship = "many-to-one"))) }) }) @@ -1241,34 +1241,34 @@ test_that("`relationship` errors when a match from a different nesting container # is processed 2nd (i.e. we need to use `loc` rather than `i` when detecting # multiple matches) expect_snapshot({ - (expect_error(vec_locate_matches(needles, haystack, condition = "<", relationship = "many_to_one"))) + (expect_error(vec_locate_matches(needles, haystack, condition = "<", relationship = "many-to-one"))) }) }) test_that("`relationship` doesn't error errneously on the last observation", { - expect_error(res <- vec_locate_matches(1:2, 1:2, relationship = "many_to_one"), NA) + expect_error(res <- vec_locate_matches(1:2, 1:2, relationship = "many-to-one"), NA) expect_identical(res$needles, 1:2) expect_identical(res$haystack, 1:2) }) test_that("`relationship` doesn't error if `multiple` removes multiple matches", { - out <- vec_locate_matches(c(1, 2), c(1, 1), multiple = "any", relationship = "one_to_one") + out <- vec_locate_matches(c(1, 2), c(1, 1), multiple = "any", relationship = "one-to-one") expect_identical(out$needles, c(1L, 2L)) expect_identical(out$haystack, c(1L, NA)) - out <- vec_locate_matches(c(1, 2), c(1, 1), multiple = "first", relationship = "one_to_one") + out <- vec_locate_matches(c(1, 2), c(1, 1), multiple = "first", relationship = "one-to-one") expect_identical(out$needles, c(1L, 2L)) expect_identical(out$haystack, c(1L, NA)) - out <- vec_locate_matches(c(1, 2), c(1, 1), multiple = "last", relationship = "one_to_one") + out <- vec_locate_matches(c(1, 2), c(1, 1), multiple = "last", relationship = "one-to-one") expect_identical(out$needles, c(1L, 2L)) expect_identical(out$haystack, c(2L, NA)) }) test_that("`relationship` can still detect problematic `haystack` relationships when `multiple = first/last` are used", { expect_snapshot({ - (expect_error(vec_locate_matches(c(3, 1, 1), c(2, 1, 3, 3), multiple = "first", relationship = "one_to_one"))) - (expect_error(vec_locate_matches(c(3, 1, 1), c(2, 1, 3, 3), multiple = "first", relationship = "one_to_many"))) + (expect_error(vec_locate_matches(c(3, 1, 1), c(2, 1, 3, 3), multiple = "first", relationship = "one-to-one"))) + (expect_error(vec_locate_matches(c(3, 1, 1), c(2, 1, 3, 3), multiple = "first", relationship = "one-to-many"))) }) }) @@ -1277,7 +1277,7 @@ test_that("`relationship` and `remaining` work properly together", { out <- vec_locate_matches( c(1, 2, 2), c(2, 3, 1, 1, 4), - relationship = "warn_many_to_many", + relationship = "warn-many-to-many", remaining = NA_integer_ ) }) @@ -1287,52 +1287,52 @@ test_that("`relationship` and `remaining` work properly together", { test_that("`relationship` errors if `condition` creates multiple matches", { expect_snapshot({ - (expect_error(vec_locate_matches(1, c(1, 2), condition = "<=", relationship = "many_to_one"))) + (expect_error(vec_locate_matches(1, c(1, 2), condition = "<=", relationship = "many-to-one"))) }) }) test_that("`relationship` doesn't error if `filter` removes multiple matches", { - out <- vec_locate_matches(1, c(1, 2), condition = "<=", filter = "min", relationship = "many_to_one") + out <- vec_locate_matches(1, c(1, 2), condition = "<=", filter = "min", relationship = "many-to-one") expect_identical(out$needles, 1L) expect_identical(out$haystack, 1L) - out <- vec_locate_matches(1, c(1, 2), condition = "<=", filter = "max", relationship = "many_to_one") + out <- vec_locate_matches(1, c(1, 2), condition = "<=", filter = "max", relationship = "many-to-one") expect_identical(out$needles, 1L) expect_identical(out$haystack, 2L) }) test_that("`relationship` still errors if `filter` hasn't removed all multiple matches", { expect_snapshot({ - (expect_error(vec_locate_matches(1, c(1, 2, 1), condition = "<=", filter = "min", relationship = "many_to_one"))) + (expect_error(vec_locate_matches(1, c(1, 2, 1), condition = "<=", filter = "min", relationship = "many-to-one"))) }) # But not here - out <- vec_locate_matches(c(1, 1), c(1, 2, 1), condition = "<=", filter = "max", relationship = "many_to_one") + out <- vec_locate_matches(c(1, 1), c(1, 2, 1), condition = "<=", filter = "max", relationship = "many-to-one") expect_identical(out$needles, c(1L, 2L)) expect_identical(out$haystack, c(2L, 2L)) }) test_that("`relationship` errors respect argument tags and error call", { expect_snapshot({ - (expect_error(vec_locate_matches(1L, c(1L, 1L), relationship = "one_to_one", needles_arg = "foo", haystack_arg = "bar", error_call = call("fn")))) - (expect_error(vec_locate_matches(c(1L, 1L), 1L, relationship = "one_to_one", needles_arg = "foo", haystack_arg = "bar", error_call = call("fn")))) - (expect_error(vec_locate_matches(c(1L, 1L), 1L, relationship = "one_to_many", needles_arg = "foo", haystack_arg = "bar", error_call = call("fn")))) - (expect_error(vec_locate_matches(1L, c(1L, 1L), relationship = "many_to_one", needles_arg = "foo", haystack_arg = "bar", error_call = call("fn")))) + (expect_error(vec_locate_matches(1L, c(1L, 1L), relationship = "one-to-one", needles_arg = "foo", haystack_arg = "bar", error_call = call("fn")))) + (expect_error(vec_locate_matches(c(1L, 1L), 1L, relationship = "one-to-one", needles_arg = "foo", haystack_arg = "bar", error_call = call("fn")))) + (expect_error(vec_locate_matches(c(1L, 1L), 1L, relationship = "one-to-many", needles_arg = "foo", haystack_arg = "bar", error_call = call("fn")))) + (expect_error(vec_locate_matches(1L, c(1L, 1L), relationship = "many-to-one", needles_arg = "foo", haystack_arg = "bar", error_call = call("fn")))) }) }) test_that("`relationship` warnings respect argument tags and error call", { expect_snapshot({ - (expect_warning(vec_locate_matches(c(1L, 1L), c(1L, 1L), relationship = "warn_many_to_many", needles_arg = "foo", haystack_arg = "bar", error_call = call("fn")))) - (expect_warning(vec_locate_matches(c(1L, 1L), c(1L, 1L), relationship = "warn_many_to_many", needles_arg = "foo", error_call = call("fn")))) - (expect_warning(vec_locate_matches(c(1L, 1L), c(1L, 1L), relationship = "warn_many_to_many", haystack_arg = "bar", error_call = call("fn")))) + (expect_warning(vec_locate_matches(c(1L, 1L), c(1L, 1L), relationship = "warn-many-to-many", needles_arg = "foo", haystack_arg = "bar", error_call = call("fn")))) + (expect_warning(vec_locate_matches(c(1L, 1L), c(1L, 1L), relationship = "warn-many-to-many", needles_arg = "foo", error_call = call("fn")))) + (expect_warning(vec_locate_matches(c(1L, 1L), c(1L, 1L), relationship = "warn-many-to-many", haystack_arg = "bar", error_call = call("fn")))) }) }) test_that("`relationship` is validated", { expect_snapshot({ (expect_error(vec_locate_matches(1, 2, relationship = 1.5))) - (expect_error(vec_locate_matches(1, 2, relationship = c("one_to_one", "one_to_many")))) + (expect_error(vec_locate_matches(1, 2, relationship = c("one-to-one", "one-to-many")))) (expect_error(vec_locate_matches(1, 2, relationship = "x"))) # Uses internal error (expect_error(vec_locate_matches(1, 2, relationship = "x", error_call = call("fn")))) From 1ffa790c09aaa70e71cab81f640fb18eba6025b7 Mon Sep 17 00:00:00 2001 From: Davis Vaughan Date: Fri, 24 Feb 2023 16:06:05 -0500 Subject: [PATCH 235/312] Avoid using `vec_assert()` internally (#1796) * Update `vec_compare()` * Update `stop_incompatible_type()` * Update `vec_equal()` * Update `new_group_rle()` * Update `partial_factor()` docs * Update `vec_data()` * Update `vec_slice_fallback()` * Update deprecated functions * Update scalar type FAQ * Update `new_rational()` * Update error call test * Update proxy/restore test * Remove C level `vec_assert()` * Update vignettes --- R/compare.R | 6 +-- R/conditions.R | 4 +- R/equal.R | 2 +- R/group.R | 7 +-- R/partial-factor.R | 13 ----- R/proxy.R | 2 +- R/slice.R | 2 +- R/vctrs-deprecated.R | 6 +-- .../howto-faq-fix-scalar-type-error.Rmd | 4 +- man/howto-faq-fix-scalar-type-error.Rd | 6 +-- man/partial_factor.Rd | 13 ----- src/assert.c | 12 ----- src/assert.h | 5 -- tests/testthat/_snaps/compare.md | 23 +++++++++ tests/testthat/_snaps/equal.md | 24 +++++++++ tests/testthat/_snaps/error-call.md | 12 +---- tests/testthat/helper-rational.R | 8 ++- tests/testthat/test-compare.R | 10 ++-- tests/testthat/test-equal.R | 12 +++-- tests/testthat/test-error-call.R | 9 ++-- tests/testthat/test-proxy-restore.R | 2 +- vignettes/s3-vector.Rmd | 50 ++++++++++++++----- vignettes/stability.Rmd | 6 ++- 23 files changed, 138 insertions(+), 100 deletions(-) create mode 100644 tests/testthat/_snaps/equal.md diff --git a/R/compare.R b/R/compare.R index 56e790f19..dccc4c31f 100644 --- a/R/compare.R +++ b/R/compare.R @@ -112,9 +112,9 @@ vec_proxy_order.default <- function(x, ...) { #' df <- data.frame(x = c(1, 1, 1, 2), y = c(0, 1, 2, 1)) #' vec_compare(df, data.frame(x = 1, y = 1)) vec_compare <- function(x, y, na_equal = FALSE, .ptype = NULL) { - vec_assert(x) - vec_assert(y) - vec_assert(na_equal, ptype = logical(), size = 1L) + obj_check_vector(x) + obj_check_vector(y) + check_bool(na_equal) args <- vec_recycle_common(x, y) args <- vec_cast_common_params(!!!args, .to = .ptype) diff --git a/R/conditions.R b/R/conditions.R index 072217cad..f05e4abff 100644 --- a/R/conditions.R +++ b/R/conditions.R @@ -114,8 +114,8 @@ stop_incompatible_type <- function(x, message = NULL, class = NULL, call = caller_env()) { - vec_assert(x, arg = x_arg) - vec_assert(y, arg = y_arg) + obj_check_vector(x, arg = x_arg) + obj_check_vector(y, arg = y_arg) action <- arg_match(action) diff --git a/R/equal.R b/R/equal.R index 0f5dbff34..de4bc7d4f 100644 --- a/R/equal.R +++ b/R/equal.R @@ -64,7 +64,7 @@ vec_proxy_equal.default <- function(x, ...) { #' df <- data.frame(x = c(1, 1, 2, 1), y = c(1, 2, 1, NA)) #' vec_equal(df, data.frame(x = 1, y = 2)) vec_equal <- function(x, y, na_equal = FALSE, .ptype = NULL) { - vec_assert(na_equal, ptype = logical(), size = 1L) + check_bool(na_equal) args <- vec_recycle_common(x, y) args <- vec_cast_common_params(!!!args, .to = .ptype) .Call(vctrs_equal, args[[1]], args[[2]], na_equal) diff --git a/R/group.R b/R/group.R index 541c045fe..2c91df28a 100644 --- a/R/group.R +++ b/R/group.R @@ -97,9 +97,10 @@ obj_print_header.vctrs_group_rle <- function(x, ...) { # For testing new_group_rle <- function(group, length, n) { - vec_assert(group, integer()) - vec_assert(length, integer()) - vec_assert(n, integer(), 1L) + stopifnot(is_integer(group)) + stopifnot(is_integer(length)) + stopifnot(is_integer(n)) + vec_check_size(n, size = 1L) if (vec_size(group) != vec_size(length)) { abort("`group` and `length` must have the same size.") diff --git a/R/partial-factor.R b/R/partial-factor.R index bc3156d77..d9cbfeb77 100644 --- a/R/partial-factor.R +++ b/R/partial-factor.R @@ -10,19 +10,6 @@ #' @keywords internal #' @export #' @examples -#' # Assert that `x` is a factor -#' vec_assert(factor("x"), partial_factor()) -#' -#' # Testing with `factor()` is too strict, -#' # because it tries to match the levels exactly -#' # rather than learning them from the data. -#' try(vec_assert(factor("x"), factor())) -#' -#' # You can also enforce a minimum set of levels -#' try(vec_assert(factor("x"), partial_factor("y"))) -#' -#' vec_assert(factor(c("x", "y")), partial_factor("y")) -#' #' pf <- partial_factor(levels = c("x", "y")) #' pf #' diff --git a/R/proxy.R b/R/proxy.R index d572cf79d..44bbbb7ae 100644 --- a/R/proxy.R +++ b/R/proxy.R @@ -200,7 +200,7 @@ vec_restore_recurse <- function(x, to, ...) { #' @keywords internal #' @export vec_data <- function(x) { - vec_assert(x) + obj_check_vector(x) x <- vec_proxy(x) if (is.data.frame(x)) { diff --git a/R/slice.R b/R/slice.R index c06c9175a..0c017d42e 100644 --- a/R/slice.R +++ b/R/slice.R @@ -115,7 +115,7 @@ vec_slice <- function(x, i, ..., error_call = current_env()) { # Called when `x` has dimensions vec_slice_fallback <- function(x, i) { out <- unclass(vec_proxy(x)) - vec_assert(out) + obj_check_vector(out) d <- vec_dim_n(out) if (d == 2) { diff --git a/R/vctrs-deprecated.R b/R/vctrs-deprecated.R index f2f6c1dce..2f233c600 100644 --- a/R/vctrs-deprecated.R +++ b/R/vctrs-deprecated.R @@ -69,7 +69,7 @@ vec_as_index <- function(i, n, names = NULL) { "Please use `vec_as_location() instead.`" )) n <- vec_cast(n, integer()) - vec_assert(n, integer(), 1L) + vec_check_size(n, size = 1L) i <- vec_as_subscript(i) # Picked up from the environment at the C level @@ -108,8 +108,8 @@ vec_repeat <- function(x, each = 1L, times = 1L) { "Please use either `vec_rep()` or `vec_rep_each()` instead." )) - vec_assert(each, size = 1L) - vec_assert(times, size = 1L) + vec_check_size(each, size = 1L) + vec_check_size(times, size = 1L) idx <- rep(vec_seq_along(x), times = times, each = each) vec_slice(x, idx) diff --git a/man/faq/developer/howto-faq-fix-scalar-type-error.Rmd b/man/faq/developer/howto-faq-fix-scalar-type-error.Rmd index 5dd047387..0ebd28edb 100644 --- a/man/faq/developer/howto-faq-fix-scalar-type-error.Rmd +++ b/man/faq/developer/howto-faq-fix-scalar-type-error.Rmd @@ -58,7 +58,7 @@ However, if you get an "Input must be a vector" error with a data frame subclass my_df <- data.frame(x = 1) class(my_df) <- c("data.frame", "my_class") -vctrs::vec_assert(my_df) +vctrs::obj_check_vector(my_df) ``` This is problematic as many tidyverse functions won't work properly: @@ -72,7 +72,7 @@ It is generally not appropriate to declare your class to be a superclass of anot ```{r} class(my_df) <- c("my_class", "data.frame") -vctrs::vec_assert(my_df) +vctrs::obj_check_vector(my_df) dplyr::slice(my_df, 1) ``` diff --git a/man/howto-faq-fix-scalar-type-error.Rd b/man/howto-faq-fix-scalar-type-error.Rd index ff965bd07..eafdfddac 100644 --- a/man/howto-faq-fix-scalar-type-error.Rd +++ b/man/howto-faq-fix-scalar-type-error.Rd @@ -62,7 +62,7 @@ class} is not \code{"data.frame"}: \if{html}{\out{
}}\preformatted{my_df <- data.frame(x = 1) class(my_df) <- c("data.frame", "my_class") -vctrs::vec_assert(my_df) +vctrs::obj_check_vector(my_df) #> Error: #> ! `my_df` must be a vector, not a object. }\if{html}{\out{
}} @@ -70,7 +70,7 @@ vctrs::vec_assert(my_df) This is problematic as many tidyverse functions won’t work properly: \if{html}{\out{
}}\preformatted{dplyr::slice(my_df, 1) -#> Error in `vec_slice()`: +#> Error in `eval_select_impl()`: #> ! `x` must be a vector, not a object. }\if{html}{\out{
}} @@ -82,7 +82,7 @@ last in the class vector: \if{html}{\out{
}}\preformatted{class(my_df) <- c("my_class", "data.frame") -vctrs::vec_assert(my_df) +vctrs::obj_check_vector(my_df) dplyr::slice(my_df, 1) #> x diff --git a/man/partial_factor.Rd b/man/partial_factor.Rd index c1a15b761..ef4cdcd2c 100644 --- a/man/partial_factor.Rd +++ b/man/partial_factor.Rd @@ -16,19 +16,6 @@ This special class can be passed as a \code{ptype} in order to specify that the result should be a factor that contains at least the specified levels. } \examples{ -# Assert that `x` is a factor -vec_assert(factor("x"), partial_factor()) - -# Testing with `factor()` is too strict, -# because it tries to match the levels exactly -# rather than learning them from the data. -try(vec_assert(factor("x"), factor())) - -# You can also enforce a minimum set of levels -try(vec_assert(factor("x"), partial_factor("y"))) - -vec_assert(factor(c("x", "y")), partial_factor("y")) - pf <- partial_factor(levels = c("x", "y")) pf diff --git a/src/assert.c b/src/assert.c index 7c004967e..03d33b190 100644 --- a/src/assert.c +++ b/src/assert.c @@ -1,18 +1,6 @@ #include "vctrs.h" #include "decl/assert-decl.h" -void vec_assert(r_obj* x, - r_ssize size, - struct vctrs_arg* arg, - struct r_lazy call) { - obj_check_vector(x, arg, call); - - if (size != -1) { - // `size == -1` makes no assertion about size - vec_check_size(x, size, arg, call); - } -} - r_obj* ffi_obj_check_vector(r_obj* x, r_obj* frame) { struct r_lazy call = { .x = r_syms.call, .env = frame }; struct r_lazy arg_lazy = { .x = r_syms.arg, .env = frame }; diff --git a/src/assert.h b/src/assert.h index 9798ad8e5..8f6f18249 100644 --- a/src/assert.h +++ b/src/assert.h @@ -3,11 +3,6 @@ #include "vctrs-core.h" -void vec_assert(r_obj* x, - r_ssize size, - struct vctrs_arg* arg, - struct r_lazy call); - void obj_check_vector(r_obj* x, struct vctrs_arg* arg, struct r_lazy call); diff --git a/tests/testthat/_snaps/compare.md b/tests/testthat/_snaps/compare.md index 16cc0a3eb..371f71c57 100644 --- a/tests/testthat/_snaps/compare.md +++ b/tests/testthat/_snaps/compare.md @@ -7,3 +7,26 @@ Error in `vec_compare()`: ! Can't compare complexes. +# `na_equal` is validated + + Code + (expect_error(vec_compare(1, 1, na_equal = 1))) + Output + + Error in `vec_compare()`: + ! `na_equal` must be `TRUE` or `FALSE`, not the number 1. + Code + (expect_error(vec_compare(1, 1, na_equal = c(TRUE, FALSE)))) + Output + + Error in `vec_compare()`: + ! `na_equal` must be `TRUE` or `FALSE`, not a logical vector. + +# can't supply NA as `na_equal` + + Code + vec_compare(NA, NA, na_equal = NA) + Condition + Error in `vec_compare()`: + ! `na_equal` must be `TRUE` or `FALSE`, not `NA`. + diff --git a/tests/testthat/_snaps/equal.md b/tests/testthat/_snaps/equal.md new file mode 100644 index 000000000..a29f5262e --- /dev/null +++ b/tests/testthat/_snaps/equal.md @@ -0,0 +1,24 @@ +# `na_equal` is validated + + Code + vec_equal(1, 1, na_equal = 1) + Condition + Error in `vec_equal()`: + ! `na_equal` must be `TRUE` or `FALSE`, not the number 1. + +--- + + Code + vec_equal(1, 1, na_equal = c(TRUE, FALSE)) + Condition + Error in `vec_equal()`: + ! `na_equal` must be `TRUE` or `FALSE`, not a logical vector. + +# can't supply NA as `na_equal` + + Code + vec_equal(NA, NA, na_equal = NA) + Condition + Error in `vec_equal()`: + ! `na_equal` must be `TRUE` or `FALSE`, not `NA`. + diff --git a/tests/testthat/_snaps/error-call.md b/tests/testthat/_snaps/error-call.md index 65b9bbf17..c3214b0c4 100644 --- a/tests/testthat/_snaps/error-call.md +++ b/tests/testthat/_snaps/error-call.md @@ -89,17 +89,7 @@ Error in `my_function()`: ! `foobar()` must be a vector, not a object. ---- - - Code - (expect_error(my_function())) - Output - - Error in `my_function()`: - ! `1:2` must be a vector with type . - Instead, it has type . - ---- +# size error reports correct error call Code (expect_error(my_function())) diff --git a/tests/testthat/helper-rational.R b/tests/testthat/helper-rational.R index 8957c1eb3..7e5c2aefc 100644 --- a/tests/testthat/helper-rational.R +++ b/tests/testthat/helper-rational.R @@ -2,8 +2,12 @@ # Rational record class from the S3 vector vignette new_rational <- function(n = integer(), d = integer()) { - vec_assert(n, ptype = integer()) - vec_assert(d, ptype = integer()) + if (!is_integer(n)) { + abort("`n` must be an integer.") + } + if (!is_integer(d)) { + abort("`d` must be an integer.") + } new_rcrd(list(n = n, d = d), class = "vctrs_rational") } diff --git a/tests/testthat/test-compare.R b/tests/testthat/test-compare.R index b4926db0e..bb960dcb5 100644 --- a/tests/testthat/test-compare.R +++ b/tests/testthat/test-compare.R @@ -224,8 +224,10 @@ test_that("error is thrown when comparing scalars", { }) test_that("`na_equal` is validated", { - expect_error(vec_compare(1, 1, na_equal = 1), class = "vctrs_error_assert_ptype") - expect_error(vec_compare(1, 1, na_equal = c(TRUE, FALSE)), class = "vctrs_error_assert_size") + expect_snapshot({ + (expect_error(vec_compare(1, 1, na_equal = 1))) + (expect_error(vec_compare(1, 1, na_equal = c(TRUE, FALSE)))) + }) }) test_that("can compare equal strings with different encodings", { @@ -273,7 +275,9 @@ test_that("can compare unspecified", { }) test_that("can't supply NA as `na_equal`", { - expect_error(vec_compare(NA, NA, na_equal = NA), "single `TRUE` or `FALSE`") + expect_snapshot(error = TRUE, { + vec_compare(NA, NA, na_equal = NA) + }) }) test_that("vec_compare() silently falls back to base data frame", { diff --git a/tests/testthat/test-equal.R b/tests/testthat/test-equal.R index f40369174..99cac704b 100644 --- a/tests/testthat/test-equal.R +++ b/tests/testthat/test-equal.R @@ -191,8 +191,12 @@ test_that("equality is known to fail when comparing bytes to other encodings", { }) test_that("`na_equal` is validated", { - expect_error(vec_equal(1, 1, na_equal = 1), class = "vctrs_error_assert_ptype") - expect_error(vec_equal(1, 1, na_equal = c(TRUE, FALSE)), class = "vctrs_error_assert_size") + expect_snapshot(error = TRUE, { + vec_equal(1, 1, na_equal = 1) + }) + expect_snapshot(error = TRUE, { + vec_equal(1, 1, na_equal = c(TRUE, FALSE)) + }) }) test_that("can compare lists of expressions", { @@ -349,7 +353,9 @@ test_that("can check equality of unspecified objects", { }) test_that("can't supply NA as `na_equal`", { - expect_error(vec_equal(NA, NA, na_equal = NA), "single `TRUE` or `FALSE`") + expect_snapshot(error = TRUE, { + vec_equal(NA, NA, na_equal = NA) + }) }) diff --git a/tests/testthat/test-error-call.R b/tests/testthat/test-error-call.R index 6422fe95d..c78eafc3d 100644 --- a/tests/testthat/test-error-call.R +++ b/tests/testthat/test-error-call.R @@ -42,13 +42,12 @@ test_that("unsupported error reports correct error call", { }) test_that("scalar error reports correct error call", { - my_function <- function() vec_assert(foobar()) - expect_snapshot((expect_error(my_function()))) - - my_function <- function() vec_assert(1:2, dbl()) + my_function <- function() obj_check_vector(foobar()) expect_snapshot((expect_error(my_function()))) +}) - my_function <- function() vec_assert(1:2, size = 1) +test_that("size error reports correct error call", { + my_function <- function() vec_check_size(1:2, size = 1) expect_snapshot((expect_error(my_function()))) }) diff --git a/tests/testthat/test-proxy-restore.R b/tests/testthat/test-proxy-restore.R index a39da2a5c..87f4019cf 100644 --- a/tests/testthat/test-proxy-restore.R +++ b/tests/testthat/test-proxy-restore.R @@ -34,7 +34,7 @@ test_that("can use vctrs primitives from vec_restore() without inflooping", { vec_restore.vctrs_foobar = function(x, to, ...) { vec_ptype(x) vec_init(x) - vec_assert(x) + obj_check_vector(x) vec_slice(x, 0) "woot" } diff --git a/vignettes/s3-vector.Rmd b/vignettes/s3-vector.Rmd index 8894a95f5..a444c4688 100644 --- a/vignettes/s3-vector.Rmd +++ b/vignettes/s3-vector.Rmd @@ -23,6 +23,7 @@ This article refers to "vectors of numbers" as *double vectors*. Here, "double" ```{r setup} library(vctrs) +library(rlang) library(zeallot) ``` @@ -66,13 +67,15 @@ In this section you'll learn how to create a new vctrs class by calling `new_vct ### Percent class -In this section, I'll show you how to make a `percent` class, i.e., a double vector that is printed as a percentage. We start by defining a low-level [constructor](https://adv-r.hadley.nz/s3.html#s3-constrcutor) that uses `vec_assert()` to checks types and/or sizes then calls `new_vctr()`. +In this section, I'll show you how to make a `percent` class, i.e., a double vector that is printed as a percentage. We start by defining a low-level [constructor](https://adv-r.hadley.nz/s3.html#s3-constrcutor) to check types and/or sizes and call `new_vctr()`. `percent` is built on a double vector of any length and doesn't have any attributes. ```{r} new_percent <- function(x = double()) { - vec_assert(x, double()) + if (!is_double(x)) { + abort("`x` must be a double vector.") + } new_vctr(x, class = "vctrs_percent") } @@ -306,8 +309,13 @@ We start off as before, defining a low-level constructor, a user-friendly constr ```{r} new_decimal <- function(x = double(), digits = 2L) { - vec_assert(x, ptype = double()) - vec_assert(digits, ptype = integer(), size = 1) + if (!is_double(x)) { + abort("`x` must be a double vector.") + } + if (!is_integer(digits)) { + abort("`digits` must be an integer vector.") + } + vec_check_size(digits, size = 1L) new_vctr(x, digits = digits, class = "vctrs_decimal") } @@ -393,8 +401,13 @@ The next level up in complexity is an object that has data-dependent attributes. ```{r} new_cached_sum <- function(x = double(), sum = 0L) { - vec_assert(x, ptype = double()) - vec_assert(sum, ptype = double(), size = 1L) + if (!is_double(x)) { + abort("`x` must be a double vector.") + } + if (!is_double(sum)) { + abort("`sum` must be a double vector.") + } + vec_check_size(sum, size = 1L) new_vctr(x, sum = sum, class = "vctrs_cached_sum") } @@ -478,8 +491,12 @@ As usual we start with low-level and user-friendly constructors. The low-level c ```{r} new_rational <- function(n = integer(), d = integer()) { - vec_assert(n, ptype = integer()) - vec_assert(d, ptype = integer()) + if (!is_integer(n)) { + abort("`n` must be an integer vector.") + } + if (!is_integer(d)) { + abort("`d` must be an integer vector.") + } new_rcrd(list(n = n, d = d), class = "vctrs_rational") } @@ -576,9 +593,16 @@ A better implementation of a decimal class would be to use pair of integers, one ```{r} new_decimal2 <- function(l, r, scale = 2L) { - vec_assert(l, ptype = integer()) - vec_assert(r, ptype = integer()) - vec_assert(scale, ptype = integer(), size = 1L) + if (!is_integer(l)) { + abort("`l` must be an integer vector.") + } + if (!is_integer(r)) { + abort("`r` must be an integer vector.") + } + if (!is_integer(scale)) { + abort("`scale` must be an integer vector.") + } + vec_check_size(scale, size = 1L) new_rcrd(list(l = l, r = r), scale = scale, class = "vctrs_decimal2") } @@ -1056,7 +1080,9 @@ Next we add our constructor: ```{r} new_percent <- function(x = double()) { - vec_assert(x, double()) + if (!is_double(x)) { + abort("`x` must be a double vector.") + } new_vctr(x, class = "pizza_percent") } ``` diff --git a/vignettes/stability.Rmd b/vignettes/stability.Rmd index bb40648ec..d6cf480bb 100644 --- a/vignettes/stability.Rmd +++ b/vignettes/stability.Rmd @@ -20,6 +20,7 @@ This work is partly motivated by a common pattern that I noticed when reviewing ```{r setup} library(vctrs) +library(rlang) library(zeallot) ``` @@ -370,7 +371,10 @@ This leads to the following implementation: ```{r} if_else <- function(test, yes, no) { - vec_assert(test, logical()) + if (!is_logical(test)) { + abort("`test` must be a logical vector.") + } + c(yes, no) %<-% vec_cast_common(yes, no) c(test, yes, no) %<-% vec_recycle_common(test, yes, no) From 0d759ef8e50a59215b5cf5634a345bbfd47ca19c Mon Sep 17 00:00:00 2001 From: DavisVaughan Date: Mon, 27 Feb 2023 09:43:47 -0500 Subject: [PATCH 236/312] Remove `compat-friendly-type.R` --- R/assert.R | 2 +- R/compat-friendly-type.R | 197 ---------------------------- R/conditions.R | 2 +- tests/testthat/_snaps/assert.md | 6 +- tests/testthat/_snaps/slice-chop.md | 8 +- 5 files changed, 9 insertions(+), 206 deletions(-) delete mode 100644 R/compat-friendly-type.R diff --git a/R/assert.R b/R/assert.R index 21fb42d62..d59832fd1 100644 --- a/R/assert.R +++ b/R/assert.R @@ -392,7 +392,7 @@ stop_non_list_type <- function(x, arg, call) { } cli::cli_abort( - "{arg} must be a list, not {friendly_type_of(x)}.", + "{arg} must be a list, not {obj_type_friendly(x)}.", call = call ) } diff --git a/R/compat-friendly-type.R b/R/compat-friendly-type.R deleted file mode 100644 index 90e55d319..000000000 --- a/R/compat-friendly-type.R +++ /dev/null @@ -1,197 +0,0 @@ -# nocov start --- r-lib/rlang compat-friendly-type -# -# Changelog -# ========= -# -# 2021-12-20: -# - Added support for scalar values and empty vectors. -# - Added `stop_input_type()` -# -# 2021-06-30: -# - Added support for missing arguments. -# -# 2021-04-19: -# - Added support for matrices and arrays (#141). -# - Added documentation. -# - Added changelog. - - -#' Return English-friendly type -#' @param x Any R object. -#' @param value Whether to describe the value of `x`. -#' @param length Whether to mention the length of vectors and lists. -#' @return A string describing the type. Starts with an indefinite -#' article, e.g. "an integer vector". -#' @noRd -friendly_type_of <- function(x, value = TRUE, length = FALSE) { - if (is_missing(x)) { - return("absent") - } - - if (is.object(x)) { - if (inherits(x, "quosure")) { - type <- "quosure" - } else { - type <- paste(class(x), collapse = "/") - } - return(sprintf("a <%s> object", type)) - } - - if (!rlang::is_vector(x)) { - return(.rlang_as_friendly_type(typeof(x))) - } - - n_dim <- length(dim(x)) - - if (value && !n_dim) { - if (is_na(x)) { - return(switch( - typeof(x), - logical = "`NA`", - integer = "an integer `NA`", - double = "a numeric `NA`", - complex = "a complex `NA`", - character = "a character `NA`", - .rlang_stop_unexpected_typeof(x) - )) - } - if (length(x) == 1 && !is_list(x)) { - return(switch( - typeof(x), - logical = if (x) "`TRUE`" else "`FALSE`", - integer = "an integer", - double = "a number", - complex = "a complex number", - character = if (nzchar(x)) "a string" else "`\"\"`", - raw = "a raw value", - .rlang_stop_unexpected_typeof(x) - )) - } - if (length(x) == 0) { - return(switch( - typeof(x), - logical = "an empty logical vector", - integer = "an empty integer vector", - double = "an empty numeric vector", - complex = "an empty complex vector", - character = "an empty character vector", - raw = "an empty raw vector", - list = "an empty list", - .rlang_stop_unexpected_typeof(x) - )) - } - } - - type <- .rlang_as_friendly_vector_type(typeof(x), n_dim) - - if (length && !n_dim) { - type <- paste0(type, sprintf(" of length %s", length(x))) - } - - type -} - -.rlang_as_friendly_vector_type <- function(type, n_dim) { - if (type == "list") { - if (n_dim < 2) { - return("a list") - } else if (n_dim == 2) { - return("a list matrix") - } else { - return("a list array") - } - } - - type <- switch( - type, - logical = "a logical %s", - integer = "an integer %s", - numeric = , - double = "a double %s", - complex = "a complex %s", - character = "a character %s", - raw = "a raw %s", - type = paste0("a ", type, " %s") - ) - - if (n_dim < 2) { - kind <- "vector" - } else if (n_dim == 2) { - kind <- "matrix" - } else { - kind <- "array" - } - sprintf(type, kind) -} - -.rlang_as_friendly_type <- function(type) { - switch( - type, - - list = "a list", - - NULL = "NULL", - environment = "an environment", - externalptr = "a pointer", - weakref = "a weak reference", - S4 = "an S4 object", - - name = , - symbol = "a symbol", - language = "a call", - pairlist = "a pairlist node", - expression = "an expression vector", - - char = "an internal string", - promise = "an internal promise", - ... = "an internal dots object", - any = "an internal `any` object", - bytecode = "an internal bytecode object", - - primitive = , - builtin = , - special = "a primitive function", - closure = "a function", - - type - ) -} - -.rlang_stop_unexpected_typeof <- function(x, call = rlang::caller_env()) { - rlang::abort( - sprintf("Unexpected type <%s>.", typeof(x)), - call = call - ) -} - -#' @param x The object type which does not conform to `what`. Its -#' `friendly_type_of()` is taken and mentioned in the error message. -#' @param what The friendly expected type. -#' @param ... Arguments passed to [abort()]. -#' @inheritParams args_error_context -#' @noRd -stop_input_type <- function(x, - what, - ..., - arg = rlang::caller_arg(x), - call = rlang::caller_env()) { - # From compat-cli.R - format_arg <- rlang::env_get( - nm = "format_arg", - last = topenv(), - default = NULL - ) - if (!is.function(format_arg)) { - format_arg <- function(x) sprintf("`%s`", x) - } - - message <- sprintf( - "%s must be %s, not %s.", - format_arg(arg), - what, - friendly_type_of(x) - ) - rlang::abort(message, ..., call = call) -} - -# nocov end diff --git a/R/conditions.R b/R/conditions.R index f05e4abff..d4dc0a9ed 100644 --- a/R/conditions.R +++ b/R/conditions.R @@ -636,7 +636,7 @@ stop_scalar_type <- function(x, arg = NULL, call = caller_env()) { } else { arg <- glue::backtick(arg) } - msg <- glue::glue("{arg} must be a vector, not {friendly_type_of(x)}.") + msg <- glue::glue("{arg} must be a vector, not {obj_type_friendly(x)}.") stop_vctrs( msg, "vctrs_error_scalar_type", diff --git a/tests/testthat/_snaps/assert.md b/tests/testthat/_snaps/assert.md index 56b313bf5..a691e0f8d 100644 --- a/tests/testthat/_snaps/assert.md +++ b/tests/testthat/_snaps/assert.md @@ -310,7 +310,7 @@ vec_check_list(1, arg = "") Condition Error: - ! Input must be a list, not a number. + ! Input must be a list, not the number 1. # vec_check_list() and list_check_all_vectors() work @@ -385,13 +385,13 @@ Output Error in `list_all_size()`: - ! `x` must be a list, not a number. + ! `x` must be a list, not the number 1. Code (expect_error(list_check_all_size(1, 2, arg = "arg", call = call("foo")))) Output Error in `list_check_all_size()`: - ! `x` must be a list, not a number. + ! `x` must be a list, not the number 1. # list_all_size() and list_check_all_size() validate `size` diff --git a/tests/testthat/_snaps/slice-chop.md b/tests/testthat/_snaps/slice-chop.md index f79e057c2..bcbf31621 100644 --- a/tests/testthat/_snaps/slice-chop.md +++ b/tests/testthat/_snaps/slice-chop.md @@ -4,7 +4,7 @@ list_unchop(1, indices = list(1)) Condition Error in `list_unchop()`: - ! `x` must be a list, not a number. + ! `x` must be a list, not the number 1. --- @@ -12,7 +12,7 @@ list_unchop(1, indices = list(1), error_call = call("foo"), error_arg = "arg") Condition Error in `foo()`: - ! `arg` must be a list, not a number. + ! `arg` must be a list, not the number 1. --- @@ -28,7 +28,7 @@ list_unchop(list(1), indices = 1) Condition Error in `list_unchop()`: - ! `indices` must be a list, not a number. + ! `indices` must be a list, not the number 1. --- @@ -36,7 +36,7 @@ list_unchop(list(1), indices = 1, error_call = call("foo")) Condition Error in `foo()`: - ! `indices` must be a list, not a number. + ! `indices` must be a list, not the number 1. --- From a30909b75c81a973fbb39d1afa1eafd81aaed193 Mon Sep 17 00:00:00 2001 From: DavisVaughan Date: Mon, 27 Feb 2023 09:44:25 -0500 Subject: [PATCH 237/312] Fix incorrectly named file --- R/{compat-types.check.R => compat-types-check.R} | 0 1 file changed, 0 insertions(+), 0 deletions(-) rename R/{compat-types.check.R => compat-types-check.R} (100%) diff --git a/R/compat-types.check.R b/R/compat-types-check.R similarity index 100% rename from R/compat-types.check.R rename to R/compat-types-check.R From bff58c91cbbb10cedf711bd84e8c535b5df28180 Mon Sep 17 00:00:00 2001 From: Davis Vaughan Date: Mon, 27 Feb 2023 10:16:02 -0500 Subject: [PATCH 238/312] Update to dev rlang (#1799) --- DESCRIPTION | 4 +++- tests/testthat/_snaps/c.md | 6 +++--- tests/testthat/_snaps/conditions.md | 2 +- tests/testthat/_snaps/expand.md | 2 +- tests/testthat/_snaps/match.md | 2 +- tests/testthat/_snaps/runs.md | 8 ++++---- tests/testthat/_snaps/size.md | 10 +++++----- tests/testthat/_snaps/slice.md | 2 +- tests/testthat/helper-vctrs.R | 2 +- 9 files changed, 20 insertions(+), 18 deletions(-) diff --git a/DESCRIPTION b/DESCRIPTION index 6d7698124..9cf251bc5 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -32,7 +32,7 @@ Imports: cli (>= 3.4.0), glue, lifecycle (>= 1.0.3), - rlang (>= 1.0.6) + rlang (>= 1.0.6.9000) Suggests: bit64, covr, @@ -59,3 +59,5 @@ Roxygen: list(markdown = TRUE) RoxygenNote: 7.2.3 Config/testthat/edition: 3 Config/Needs/website: tidyverse/tidytemplate +Remotes: + r-lib/rlang diff --git a/tests/testthat/_snaps/c.md b/tests/testthat/_snaps/c.md index c4c851c0a..06e9e6d60 100644 --- a/tests/testthat/_snaps/c.md +++ b/tests/testthat/_snaps/c.md @@ -256,13 +256,13 @@ }) with_memory_prof(list_unchop(make_list_of(1000))) Output - [1] 112KB + [1] 111KB Code with_memory_prof(list_unchop(make_list_of(2000))) Output - [1] 221KB + [1] 220KB Code with_memory_prof(list_unchop(make_list_of(4000))) Output - [1] 440KB + [1] 439KB diff --git a/tests/testthat/_snaps/conditions.md b/tests/testthat/_snaps/conditions.md index 921b36990..e2b642403 100644 --- a/tests/testthat/_snaps/conditions.md +++ b/tests/testthat/_snaps/conditions.md @@ -12,7 +12,7 @@ Output Error in `stop_incompatible_type()`: - ! `action` must be a character vector, not a number. + ! `action` must be a character vector, not the number 1. # can override arg in OOB conditions diff --git a/tests/testthat/_snaps/expand.md b/tests/testthat/_snaps/expand.md index 0c39110fd..8e3c62f5b 100644 --- a/tests/testthat/_snaps/expand.md +++ b/tests/testthat/_snaps/expand.md @@ -58,7 +58,7 @@ ! Result too large for an `r_ssize`. i In file './rlang/c-utils.h' at line . i This is an internal error that was detected in the vctrs package. - Please report it at with a reprex () and the full backtrace. + Please report it at with a reprex () and the full backtrace. # validates `.vary` diff --git a/tests/testthat/_snaps/match.md b/tests/testthat/_snaps/match.md index 505f80bab..37d0077dc 100644 --- a/tests/testthat/_snaps/match.md +++ b/tests/testthat/_snaps/match.md @@ -665,5 +665,5 @@ ! Match procedure results in an allocation larger than 2^31-1 elements. Attempted allocation size was 50000005000000. i In file 'match.c' at line . i This is an internal error that was detected in the vctrs package. - Please report it at with a reprex () and the full backtrace. + Please report it at with a reprex () and the full backtrace. diff --git a/tests/testthat/_snaps/runs.md b/tests/testthat/_snaps/runs.md index fe5f3a976..da34489a3 100644 --- a/tests/testthat/_snaps/runs.md +++ b/tests/testthat/_snaps/runs.md @@ -35,8 +35,8 @@ Code vec_locate_run_bounds(1, which = c("foo", "bar")) Condition - Error in `arg_match()`: - ! `arg` must be length 1 or a permutation of `values`. + Error in `vec_locate_run_bounds()`: + ! `arg` must be length 1 or a permutation of `c("start", "end")`. # vec_detect_run_bounds() validates `which` @@ -59,6 +59,6 @@ Code vec_detect_run_bounds(1, which = c("foo", "bar")) Condition - Error in `arg_match()`: - ! `arg` must be length 1 or a permutation of `values`. + Error in `vec_detect_run_bounds()`: + ! `arg` must be length 1 or a permutation of `c("start", "end")`. diff --git a/tests/testthat/_snaps/size.md b/tests/testthat/_snaps/size.md index 38d9665e3..4040948ce 100644 --- a/tests/testthat/_snaps/size.md +++ b/tests/testthat/_snaps/size.md @@ -11,7 +11,7 @@ Output Error in `vec_as_short_length()`: - ! `my_arg` must be a single number, not an integer vector of length 2. + ! `my_arg` must be a single number, not an integer vector. Code (expect_error(my_function(1.5))) Output @@ -35,13 +35,13 @@ Output Error in `vec_as_short_length()`: - ! `my_arg` must be a single number, not a string. + ! `my_arg` must be a single number, not the string "foo". Code (expect_error(my_function(foobar(1:2)))) Output Error in `vec_as_short_length()`: - ! `my_arg` must be a single number, not NULL. + ! `my_arg` must be a single number, not `NULL`. Code (expect_error(my_function(.Machine$double.xmax))) Output @@ -65,13 +65,13 @@ Output Error in `vec_size_common()`: - ! `.size` must be a single number, not a string. + ! `.size` must be a single number, not the string "foo". Code (expect_error(vec_size_common(.size = 1:2))) Output Error in `vec_size_common()`: - ! `.size` must be a single number, not an integer vector of length 2. + ! `.size` must be a single number, not an integer vector. # vec_size_common() mentions `arg` in errors diff --git a/tests/testthat/_snaps/slice.md b/tests/testthat/_snaps/slice.md index ef493a9a2..4f65a7146 100644 --- a/tests/testthat/_snaps/slice.md +++ b/tests/testthat/_snaps/slice.md @@ -133,7 +133,7 @@ Output Error in `vec_init()`: - ! `n` must be a single number, not a double vector of length 2. + ! `n` must be a single number, not a double vector. Code (expect_error(vec_init(1L, -1L))) Output diff --git a/tests/testthat/helper-vctrs.R b/tests/testthat/helper-vctrs.R index 95bd60a70..98f8fe793 100644 --- a/tests/testthat/helper-vctrs.R +++ b/tests/testthat/helper-vctrs.R @@ -54,5 +54,5 @@ expect_equal <- function(object, expected, ..., } raw2 <- function(...) { - as.raw(flatten_int(list2(...))) + as.raw(list_unchop(list2(...), ptype = integer())) } From 84eb4c6bb3165a5685caecd0271b492e0db65fb1 Mon Sep 17 00:00:00 2001 From: Davis Vaughan Date: Mon, 27 Feb 2023 13:49:24 -0500 Subject: [PATCH 239/312] Remove `compat-lifecycle.R` in favor of official machinery (#1800) --- R/compat-lifecycle.R | 262 --------------------- R/conditions.R | 32 +-- R/vctrs-deprecated.R | 48 ++-- tests/testthat/_snaps/cast.md | 11 + tests/testthat/test-cast.R | 6 +- tests/testthat/test-lifecycle-deprecated.R | 4 +- 6 files changed, 68 insertions(+), 295 deletions(-) delete mode 100644 R/compat-lifecycle.R diff --git a/R/compat-lifecycle.R b/R/compat-lifecycle.R deleted file mode 100644 index bc11f7d61..000000000 --- a/R/compat-lifecycle.R +++ /dev/null @@ -1,262 +0,0 @@ -# nocov start --- compat-lifecycle --- 2019-11-15 Fri 15:55 - -# This file serves as a reference for currently unexported rlang -# lifecycle functions. Please find the most recent version in rlang's -# repository. These functions require rlang in your `Imports` -# DESCRIPTION field but you don't need to import rlang in your -# namespace. - - -#' Signal deprecation -#' -#' @description -#' -#' These functions provide two levels of verbosity for deprecation -#' warnings. -#' -#' * `signal_soft_deprecated()` warns only if called from the global -#' environment (so the user can change their script) or from the -#' package currently being tested (so the package developer can fix -#' the package). -#' -#' * `warn_deprecated()` warns unconditionally. -#' -#' * `stop_defunct()` fails unconditionally. -#' -#' Both functions warn only once per session by default to avoid -#' overwhelming the user with repeated warnings. -#' -#' @param msg The deprecation message. -#' @param id The id of the deprecation. A warning is issued only once -#' for each `id`. Defaults to `msg`, but you should give a unique ID -#' when the message is built programmatically and depends on inputs. -#' @param env The environment in which the soft-deprecated function -#' was called. A warning is issued if called from the global -#' environment. If testthat is running, a warning is also called if -#' the retired function was called from the package being tested. -#' -#' @section Controlling verbosity: -#' -#' The verbosity of retirement warnings can be controlled with global -#' options. You'll generally want to set these options locally with -#' one of these helpers: -#' -#' * `with_lifecycle_silence()` disables all soft-deprecation and -#' deprecation warnings. -#' -#' * `with_lifecycle_warnings()` enforces warnings for both -#' soft-deprecated and deprecated functions. The warnings are -#' repeated rather than signalled once per session. -#' -#' * `with_lifecycle_errors()` enforces errors for both -#' soft-deprecated and deprecated functions. -#' -#' All the `with_` helpers have `scoped_` variants that are -#' particularly useful in testthat blocks. -#' -#' @noRd -#' @seealso [lifecycle()] -NULL - -signal_soft_deprecated <- function(msg, id = msg, env = caller_env(2)) { - msg <- lifecycle_validate_message(msg) - stopifnot( - rlang::is_string(id), - rlang::is_environment(env) - ) - - if (rlang::is_true(rlang::peek_option("lifecycle_disable_warnings"))) { - return(invisible(NULL)) - } - - env_inherits_global <- function(env) { - # `topenv(emptyenv())` returns the global env. Return `FALSE` in - # that case to allow passing the empty env when the - # soft-deprecation should not be promoted to deprecation based on - # the caller environment. - if (rlang::is_reference(env, emptyenv())) { - return(FALSE) - } - - rlang::is_reference(topenv(env), rlang::global_env()) - } - - if (rlang::is_true(rlang::peek_option("lifecycle_verbose_soft_deprecation")) || - env_inherits_global(env)) { - warn_deprecated(msg, id) - return(invisible(NULL)) - } - - # Test for environment names rather than reference/contents because - # testthat clones the namespace - tested_package <- Sys.getenv("TESTTHAT_PKG") - if (nzchar(tested_package) && - identical(Sys.getenv("NOT_CRAN"), "true") && - rlang::env_name(topenv(env)) == rlang::env_name(ns_env(tested_package))) { - warn_deprecated(msg, id) - return(invisible(NULL)) - } - - rlang::signal(msg, "lifecycle_soft_deprecated") -} - -warn_deprecated <- function(msg, id = msg) { - msg <- lifecycle_validate_message(msg) - stopifnot(rlang::is_string(id)) - - if (rlang::is_true(rlang::peek_option("lifecycle_disable_warnings"))) { - return(invisible(NULL)) - } - - if (!rlang::is_true(rlang::peek_option("lifecycle_repeat_warnings")) && - rlang::env_has(deprecation_env, id)) { - return(invisible(NULL)) - } - - rlang::env_poke(deprecation_env, id, TRUE); - - has_colour <- function() rlang::is_installed("crayon") && crayon::has_color() - silver <- function(x) if (has_colour()) crayon::silver(x) else x - - if (rlang::is_true(rlang::peek_option("lifecycle_warnings_as_errors"))) { - .Signal <- stop_defunct - } else { - .Signal <- .Deprecated - } - - if (!rlang::is_true(rlang::peek_option("lifecycle_repeat_warnings"))) { - msg <- paste0(msg, "\n", silver("This warning is displayed once per session.")) - } - - .Signal(msg = msg) -} -deprecation_env <- new.env(parent = emptyenv()) - -stop_defunct <- function(msg) { - msg <- lifecycle_validate_message(msg) - err <- cnd( - c("defunctError", "error", "condition"), - old = NULL, - new = NULL, - package = NULL, - message = msg - ) - stop(err) -} - -local_lifecycle_silence <- function(frame = rlang::caller_env()) { - rlang::local_options(.frame = frame, - lifecycle_disable_warnings = TRUE - ) -} -with_lifecycle_silence <- function(expr) { - local_lifecycle_silence() - expr -} - -local_lifecycle_warnings <- function(frame = rlang::caller_env()) { - rlang::local_options(.frame = frame, - lifecycle_disable_warnings = FALSE, - lifecycle_verbose_soft_deprecation = TRUE, - lifecycle_repeat_warnings = TRUE - ) -} -with_lifecycle_warnings <- function(expr) { - local_lifecycle_warnings() - expr -} - -local_lifecycle_errors <- function(frame = rlang::caller_env()) { - local_lifecycle_warnings(frame = frame) - rlang::local_options(.frame = frame, - lifecycle_warnings_as_errors = TRUE - ) -} -with_lifecycle_errors <- function(expr) { - local_lifecycle_errors() - expr -} - - -#' Embed a lifecycle badge in documentation -#' -#' @description -#' -#' Use `lifecycle()` within a `Sexpr` macro to embed a -#' [lifecycle](https://www.tidyverse.org/lifecycle/) badge in your -#' documentation. The badge should appear first in the description: -#' -#' ``` -#' \Sexpr[results=rd, stage=render]{mypkg:::lifecycle("questioning")} -#' ``` -#' -#' The badge appears as an image in the HTML version of the -#' documentation. To make them available in your package, visit -#' and copy -#' all the files starting with `lifecycle-` in your `man/figures/` -#' folder. -#' -#' @param stage A lifecycle stage as a string, one of: -#' `"experimental"`, `"maturing"`, `"stable"`, `"questioning"`, -#' `"archived"`, `"soft-deprecated"`, `"deprecated"`, `"defunct"`. -#' -#' @keywords internal -#' @noRd -NULL - -lifecycle <- function(stage) { - url <- paste0("https://www.tidyverse.org/lifecycle/#", stage) - img <- lifecycle_img(stage, url) - - sprintf( - "\\ifelse{html}{%s}{\\strong{%s}}", - img, - upcase1(stage) - ) -} - -lifecycle_img <- function(stage, url) { - file <- sprintf("lifecycle-%s.svg", stage) - stage_alt <- upcase1(stage) - - switch(stage, - - experimental = , - maturing = , - stable = , - questioning = , - retired = , - archived = - sprintf( - "\\out{%s lifecycle}", - url, - file.path("figures", file), - stage_alt - ) - , - - `soft-deprecated` = , - deprecated = , - defunct = - sprintf( - "\\figure{%s}{options: alt='%s lifecycle'}", - file, - stage_alt - ), - - rlang::abort(sprintf("Unknown lifecycle stage `%s`", stage)) - - ) -} -upcase1 <- function(x) { - substr(x, 1, 1) <- toupper(substr(x, 1, 1)) - x -} - -lifecycle_validate_message <- function(msg) { - stopifnot(is_character(msg)) - paste0(msg, collapse = "\n") -} - - -# nocov end diff --git a/R/conditions.R b/R/conditions.R index d4dc0a9ed..6b68fbfa0 100644 --- a/R/conditions.R +++ b/R/conditions.R @@ -562,7 +562,12 @@ allow_lossy_cast <- function(expr, x_ptype = NULL, to_ptype = NULL) { ) } -maybe_warn_deprecated_lossy_cast <- function(x, to, loss_type, x_arg, to_arg) { +maybe_warn_deprecated_lossy_cast <- function(x, + to, + loss_type, + x_arg, + to_arg, + user_env = caller_env(2)) { # Returns `TRUE` if `allow_lossy_cast()` is on the stack and accepts # to handle the condition handled <- withRestarts( @@ -591,19 +596,18 @@ maybe_warn_deprecated_lossy_cast <- function(x, to, loss_type, x_arg, to_arg) { from <- format_arg_label(vec_ptype_abbr(x), x_arg) to <- format_arg_label(vec_ptype_abbr(to), to_arg) - warn_deprecated(paste_line( - glue::glue("We detected a lossy transformation from `{ from }` to `{ to }`."), - "The result will contain lower-resolution values or missing values.", - "To suppress this warning, wrap your code with `allow_lossy_cast()`:", - "", - " # Allow all lossy transformations:", - " vctrs::allow_lossy_cast(mycode())", - "", - " # Allow only a specific transformation:", - " vctrs::allow_lossy_cast(mycode(), x_ptype = from, to_ptype = to)", - "", - "Consult `?vctrs::allow_lossy_cast` for more information." - )) + lifecycle::deprecate_warn( + when = "0.2.0", + what = I("Coercion with lossy casts"), + with = "allow_lossy_cast()", + details = paste0( + glue::glue("We detected a lossy transformation from { from } to { to }. "), + "The result will contain lower-resolution values or missing values. ", + "To suppress this warning, wrap your code with `allow_lossy_cast()`." + ), + always = TRUE, + user_env = user_env + ) invisible() } diff --git a/R/vctrs-deprecated.R b/R/vctrs-deprecated.R index 2f233c600..ceed216eb 100644 --- a/R/vctrs-deprecated.R +++ b/R/vctrs-deprecated.R @@ -11,10 +11,11 @@ #' @keywords internal #' @export vec_empty <- function(x) { - stop_defunct(paste_line( - "`vec_empty()` is defunct as of vctrs 0.2.0.", - "Please use `vec_is_empty()` instead." - )) + lifecycle::deprecate_stop( + when = "0.2.0", + what = "vec_empty()", + with = "vec_is_empty()" + ) } #' Deprecated type functions @@ -34,19 +35,34 @@ vec_empty <- function(x) { #' @keywords internal #' @export vec_type <- function(x) { - warn_deprecated(c("`vec_type()` has been renamed to `vec_ptype()`.")) + lifecycle::deprecate_warn( + when = "0.2.0", + what = "vec_type()", + with = "vec_ptype()", + always = TRUE + ) vec_ptype(x) } #' @rdname vec_type #' @export vec_type_common <- function(..., .ptype = NULL) { - warn_deprecated(c("`vec_type_common()` has been renamed to `vec_ptype_common()`.")) + lifecycle::deprecate_warn( + when = "0.2.0", + what = "vec_type_common()", + with = "vec_ptype_common()", + always = TRUE + ) vec_ptype_common(..., .ptype = .ptype) } #' @rdname vec_type #' @export vec_type2 <- function(x, y, ...) { - warn_deprecated(c("`vec_type2()` has been renamed to `vec_ptype2()`.")) + lifecycle::deprecate_warn( + when = "0.2.0", + what = "vec_type2()", + with = "vec_ptype2()", + always = TRUE + ) vec_ptype2(x, y, ...) } @@ -64,10 +80,11 @@ vec_type2 <- function(x, y, ...) { #' @keywords internal #' @export vec_as_index <- function(i, n, names = NULL) { - signal_soft_deprecated(paste_line( - "`vec_as_index()` is deprecated as of vctrs 0.2.2.", - "Please use `vec_as_location() instead.`" - )) + lifecycle::deprecate_soft( + when = "0.2.2", + what = "vec_as_index()", + with = "vec_as_location()" + ) n <- vec_cast(n, integer()) vec_check_size(n, size = 1L) i <- vec_as_subscript(i) @@ -103,10 +120,11 @@ vec_as_index <- function(i, n, names = NULL) { #' @keywords internal #' @export vec_repeat <- function(x, each = 1L, times = 1L) { - signal_soft_deprecated(paste_line( - "`vec_repeat()` is deprecated as of vctrs 0.3.0.", - "Please use either `vec_rep()` or `vec_rep_each()` instead." - )) + lifecycle::deprecate_soft( + when = "0.3.0", + what = "vec_repeat()", + with = I("either `vec_rep()` or `vec_rep_each()`") + ) vec_check_size(each, size = 1L) vec_check_size(times, size = 1L) diff --git a/tests/testthat/_snaps/cast.md b/tests/testthat/_snaps/cast.md index d77ca4507..390d12fee 100644 --- a/tests/testthat/_snaps/cast.md +++ b/tests/testthat/_snaps/cast.md @@ -72,3 +72,14 @@ Error: ! Can't convert `foobar(mtcars)` to . +# can signal deprecation warnings for lossy casts + + Code + (expect_warning(expect_true(lossy_cast()))) + Output + + Warning: + Coercion with lossy casts was deprecated in vctrs 0.2.0. + i Please use `allow_lossy_cast()` instead. + i We detected a lossy transformation from `x` to `to` . The result will contain lower-resolution values or missing values. To suppress this warning, wrap your code with `allow_lossy_cast()`. + diff --git a/tests/testthat/test-cast.R b/tests/testthat/test-cast.R index d9000a99d..2d8632c20 100644 --- a/tests/testthat/test-cast.R +++ b/tests/testthat/test-cast.R @@ -126,7 +126,7 @@ test_that("can suppress cast errors selectively", { }) test_that("can signal deprecation warnings for lossy casts", { - local_lifecycle_warnings() + local_options(lifecycle_verbosity = "warning") lossy_cast <- function() { maybe_lossy_cast( @@ -140,7 +140,9 @@ test_that("can signal deprecation warnings for lossy casts", { ) } - expect_warning(expect_true(lossy_cast()), "detected a lossy transformation") + expect_snapshot({ + (expect_warning(expect_true(lossy_cast()))) + }) expect_warning(regexp = NA, expect_true(allow_lossy_cast(lossy_cast()))) expect_warning(regexp = NA, expect_true(allow_lossy_cast(lossy_cast(), factor("foo"), factor("bar")))) expect_warning(expect_true(allow_lossy_cast(lossy_cast(), factor("bar"), double()))) diff --git a/tests/testthat/test-lifecycle-deprecated.R b/tests/testthat/test-lifecycle-deprecated.R index d80cea837..7d53594a7 100644 --- a/tests/testthat/test-lifecycle-deprecated.R +++ b/tests/testthat/test-lifecycle-deprecated.R @@ -1,6 +1,6 @@ test_that("vec_as_index() still works", { - local_lifecycle_silence() + local_options(lifecycle_verbosity = "quiet") expect_identical(vec_as_index(-2, 10), vec_as_location(-2, 10)) expect_identical( vec_as_index("cyl", length(mtcars), names(mtcars)), @@ -9,7 +9,7 @@ test_that("vec_as_index() still works", { }) test_that("vec_repeat() still works", { - local_lifecycle_silence() + local_options(lifecycle_verbosity = "quiet") expect_identical(vec_repeat(1:2, times = 2), vec_rep(1:2, 2)) expect_identical(vec_repeat(1:2, each = 2), vec_rep_each(1:2, 2)) }) From 19797849a2d6a4f1167286167797e16bee054c18 Mon Sep 17 00:00:00 2001 From: Davis Vaughan Date: Mon, 27 Feb 2023 16:05:49 -0500 Subject: [PATCH 240/312] Update to latest standalone compat files (#1801) --- ...n.R => import-standalone-linked-version.R} | 17 +- ...bj-type.R => import-standalone-obj-type.R} | 19 +- ...mpat-purrr.R => import-standalone-purrr.R} | 187 +++++++++------ ...heck.R => import-standalone-types-check.R} | 220 ++++++++++-------- 4 files changed, 272 insertions(+), 171 deletions(-) rename R/{compat-linked-version.R => import-standalone-linked-version.R} (79%) rename R/{compat-obj-type.R => import-standalone-obj-type.R} (95%) rename R/{compat-purrr.R => import-standalone-purrr.R} (51%) rename R/{compat-types-check.R => import-standalone-types-check.R} (70%) diff --git a/R/compat-linked-version.R b/R/import-standalone-linked-version.R similarity index 79% rename from R/compat-linked-version.R rename to R/import-standalone-linked-version.R index 036161cb5..4f1c458a2 100644 --- a/R/compat-linked-version.R +++ b/R/import-standalone-linked-version.R @@ -1,9 +1,20 @@ -# nocov start --- compat-linked-version --- 2020-02-24 Mon 13:05 CET +# Standalone file: do not edit by hand +# Source: +# ---------------------------------------------------------------------- +# +# --- +# repo: r-lib/rlang +# file: standalone-linked-version.R +# last-updated: 2022-05-26 +# license: https://unlicense.org +# --- +# +# nocov start check_linked_version <- local({ - # Keep in sync with compat-downstream-deps.R + # Keep in sync with standalone-downstream-deps.R howto_reinstall_msg <- function(pkg) { os <- tolower(Sys.info()[["sysname"]]) @@ -20,7 +31,7 @@ check_linked_version <- local({ } } - function(pkg, with_rlang = requireNamespace("rlang")) { + function(pkg, with_rlang = requireNamespace("rlang", quietly = TRUE)) { ver <- utils::packageVersion(pkg) ns <- asNamespace(pkg) diff --git a/R/compat-obj-type.R b/R/import-standalone-obj-type.R similarity index 95% rename from R/compat-obj-type.R rename to R/import-standalone-obj-type.R index d86dca51b..7cd62fc03 100644 --- a/R/compat-obj-type.R +++ b/R/import-standalone-obj-type.R @@ -1,7 +1,15 @@ -# nocov start --- r-lib/rlang compat-obj-type +# Standalone file: do not edit by hand +# Source: +# ---------------------------------------------------------------------- # -# Changelog -# ========= +# --- +# repo: r-lib/rlang +# file: standalone-obj-type.R +# last-updated: 2022-10-04 +# license: https://unlicense.org +# --- +# +# ## Changelog # # 2022-10-04: # - `obj_type_friendly(value = TRUE)` now shows numeric scalars @@ -36,7 +44,8 @@ # - Added support for matrices and arrays (#141). # - Added documentation. # - Added changelog. - +# +# nocov start #' Return English-friendly type #' @param x Any R object. @@ -288,7 +297,7 @@ stop_input_type <- function(x, show_value = TRUE, arg = caller_arg(x), call = caller_env()) { - # From compat-cli.R + # From standalone-cli.R cli <- env_get_list( nms = c("format_arg", "format_code"), last = topenv(), diff --git a/R/compat-purrr.R b/R/import-standalone-purrr.R similarity index 51% rename from R/compat-purrr.R rename to R/import-standalone-purrr.R index f8f362cb8..42e132d7e 100644 --- a/R/compat-purrr.R +++ b/R/import-standalone-purrr.R @@ -1,61 +1,77 @@ -# nocov start - compat-purrr (last updated: rlang 0.2.0) - -# This file serves as a reference for compatibility functions for -# purrr. They are not drop-in replacements but allow a similar style -# of programming. This is useful in cases where purrr is too heavy a -# package to depend on. Please find the most recent version in rlang's -# repository. +# Standalone file: do not edit by hand +# Source: +# ---------------------------------------------------------------------- +# +# --- +# repo: r-lib/rlang +# file: standalone-purrr.R +# last-updated: 2023-02-23 +# license: https://unlicense.org +# --- +# +# This file provides a minimal shim to provide a purrr-like API on top of +# base R functions. They are not drop-in replacements but allow a similar style +# of programming. +# +# ## Changelog +# +# 2023-02-23: +# * Added `list_c()` +# +# 2022-06-07: +# * `transpose()` is now more consistent with purrr when inner names +# are not congruent (#1346). +# +# 2021-12-15: +# * `transpose()` now supports empty lists. +# +# 2021-05-21: +# * Fixed "object `x` not found" error in `imap()` (@mgirlich) +# +# 2020-04-14: +# * Removed `pluck*()` functions +# * Removed `*_cpl()` functions +# * Used `as_function()` to allow use of `~` +# * Used `.` prefix for helpers +# +# nocov start map <- function(.x, .f, ...) { + .f <- as_function(.f, env = global_env()) lapply(.x, .f, ...) } -map_mold <- function(.x, .f, .mold, ...) { - out <- vapply(.x, .f, .mold, ..., USE.NAMES = FALSE) - names(out) <- names(.x) - out -} -map_lgl <- function(.x, .f, ...) { - map_mold(.x, .f, logical(1), ...) -} -map_int <- function(.x, .f, ...) { - map_mold(.x, .f, integer(1), ...) -} -map_dbl <- function(.x, .f, ...) { - map_mold(.x, .f, double(1), ...) -} -map_chr <- function(.x, .f, ...) { - map_mold(.x, .f, character(1), ...) -} -map_cpl <- function(.x, .f, ...) { - map_mold(.x, .f, complex(1), ...) -} - walk <- function(.x, .f, ...) { map(.x, .f, ...) invisible(.x) } -pluck <- function(.x, .f) { - map(.x, `[[`, .f) -} -pluck_lgl <- function(.x, .f) { - map_lgl(.x, `[[`, .f) +map_lgl <- function(.x, .f, ...) { + .rlang_purrr_map_mold(.x, .f, logical(1), ...) } -pluck_int <- function(.x, .f) { - map_int(.x, `[[`, .f) +map_int <- function(.x, .f, ...) { + .rlang_purrr_map_mold(.x, .f, integer(1), ...) } -pluck_dbl <- function(.x, .f) { - map_dbl(.x, `[[`, .f) +map_dbl <- function(.x, .f, ...) { + .rlang_purrr_map_mold(.x, .f, double(1), ...) } -pluck_chr <- function(.x, .f) { - map_chr(.x, `[[`, .f) +map_chr <- function(.x, .f, ...) { + .rlang_purrr_map_mold(.x, .f, character(1), ...) } -pluck_cpl <- function(.x, .f) { - map_cpl(.x, `[[`, .f) +.rlang_purrr_map_mold <- function(.x, .f, .mold, ...) { + .f <- as_function(.f, env = global_env()) + out <- vapply(.x, .f, .mold, ..., USE.NAMES = FALSE) + names(out) <- names(.x) + out } map2 <- function(.x, .y, .f, ...) { - Map(.f, .x, .y, ...) + .f <- as_function(.f, env = global_env()) + out <- mapply(.f, .x, .y, MoreArgs = list(...), SIMPLIFY = FALSE) + if (length(out) == length(.x)) { + set_names(out, names(.x)) + } else { + set_names(out, NULL) + } } map2_lgl <- function(.x, .y, .f, ...) { as.vector(map2(.x, .y, .f, ...), "logical") @@ -69,77 +85,103 @@ map2_dbl <- function(.x, .y, .f, ...) { map2_chr <- function(.x, .y, .f, ...) { as.vector(map2(.x, .y, .f, ...), "character") } -map2_cpl <- function(.x, .y, .f, ...) { - as.vector(map2(.x, .y, .f, ...), "complex") +imap <- function(.x, .f, ...) { + map2(.x, names(.x) %||% seq_along(.x), .f, ...) } -args_recycle <- function(args) { - lengths <- map_int(args, length) - n <- max(lengths) - - stopifnot(all(lengths == 1L | lengths == n)) - to_recycle <- lengths == 1L - args[to_recycle] <- map(args[to_recycle], function(x) rep.int(x, n)) - - args -} pmap <- function(.l, .f, ...) { - args <- args_recycle(.l) + .f <- as.function(.f) + args <- .rlang_purrr_args_recycle(.l) do.call("mapply", c( FUN = list(quote(.f)), args, MoreArgs = quote(list(...)), SIMPLIFY = FALSE, USE.NAMES = FALSE )) } +.rlang_purrr_args_recycle <- function(args) { + lengths <- map_int(args, length) + n <- max(lengths) -probe <- function(.x, .p, ...) { - if (is_logical(.p)) { - stopifnot(length(.p) == length(.x)) - .p - } else { - map_lgl(.x, .p, ...) - } + stopifnot(all(lengths == 1L | lengths == n)) + to_recycle <- lengths == 1L + args[to_recycle] <- map(args[to_recycle], function(x) rep.int(x, n)) + + args } keep <- function(.x, .f, ...) { - .x[probe(.x, .f, ...)] + .x[.rlang_purrr_probe(.x, .f, ...)] } discard <- function(.x, .p, ...) { - sel <- probe(.x, .p, ...) + sel <- .rlang_purrr_probe(.x, .p, ...) .x[is.na(sel) | !sel] } map_if <- function(.x, .p, .f, ...) { - matches <- probe(.x, .p) + matches <- .rlang_purrr_probe(.x, .p) .x[matches] <- map(.x[matches], .f, ...) .x } +.rlang_purrr_probe <- function(.x, .p, ...) { + if (is_logical(.p)) { + stopifnot(length(.p) == length(.x)) + .p + } else { + .p <- as_function(.p, env = global_env()) + map_lgl(.x, .p, ...) + } +} + +compact <- function(.x) { + Filter(length, .x) +} transpose <- function(.l) { + if (!length(.l)) { + return(.l) + } + inner_names <- names(.l[[1]]) + if (is.null(inner_names)) { fields <- seq_along(.l[[1]]) } else { fields <- set_names(inner_names) + .l <- map(.l, function(x) { + if (is.null(names(x))) { + set_names(x, inner_names) + } else { + x + } + }) } + # This way missing fields are subsetted as `NULL` instead of causing + # an error + .l <- map(.l, as.list) + map(fields, function(i) { map(.l, .subset2, i) }) } every <- function(.x, .p, ...) { + .p <- as_function(.p, env = global_env()) + for (i in seq_along(.x)) { if (!rlang::is_true(.p(.x[[i]], ...))) return(FALSE) } TRUE } some <- function(.x, .p, ...) { + .p <- as_function(.p, env = global_env()) + for (i in seq_along(.x)) { if (rlang::is_true(.p(.x[[i]], ...))) return(TRUE) } FALSE } negate <- function(.p) { + .p <- as_function(.p, env = global_env()) function(...) !.p(...) } @@ -161,7 +203,10 @@ accumulate_right <- function(.x, .f, ..., .init) { } detect <- function(.x, .f, ..., .right = FALSE, .p = is_true) { - for (i in index(.x, .right)) { + .p <- as_function(.p, env = global_env()) + .f <- as_function(.f, env = global_env()) + + for (i in .rlang_purrr_index(.x, .right)) { if (.p(.f(.x[[i]], ...))) { return(.x[[i]]) } @@ -169,14 +214,17 @@ detect <- function(.x, .f, ..., .right = FALSE, .p = is_true) { NULL } detect_index <- function(.x, .f, ..., .right = FALSE, .p = is_true) { - for (i in index(.x, .right)) { + .p <- as_function(.p, env = global_env()) + .f <- as_function(.f, env = global_env()) + + for (i in .rlang_purrr_index(.x, .right)) { if (.p(.f(.x[[i]], ...))) { return(i) } } 0L } -index <- function(x, right = FALSE) { +.rlang_purrr_index <- function(x, right = FALSE) { idx <- seq_along(x) if (right) { idx <- rev(idx) @@ -184,5 +232,8 @@ index <- function(x, right = FALSE) { idx } +list_c <- function(x) { + inject(c(!!!x)) +} # nocov end diff --git a/R/compat-types-check.R b/R/import-standalone-types-check.R similarity index 70% rename from R/compat-types-check.R rename to R/import-standalone-types-check.R index 3e46ca431..4c4ca85c9 100644 --- a/R/compat-types-check.R +++ b/R/import-standalone-types-check.R @@ -1,12 +1,32 @@ -# nocov start --- r-lib/rlang compat-types-check +# Standalone file: do not edit by hand +# Source: +# ---------------------------------------------------------------------- # -# Dependencies -# ============ +# --- +# repo: r-lib/rlang +# file: standalone-types-check.R +# last-updated: 2023-02-15 +# license: https://unlicense.org +# dependencies: standalone-obj-type.R +# --- # -# - compat-obj-type.R +# ## Changelog # -# Changelog -# ========= +# 2023-02-15: +# - Added `check_logical()`. +# +# - `check_bool()`, `check_number_whole()`, and +# `check_number_decimal()` are now implemented in C. +# +# - For efficiency, `check_number_whole()` and +# `check_number_decimal()` now take a `NULL` default for `min` and +# `max`. This makes it possible to bypass unnecessary type-checking +# and comparisons in the default case of no bounds checks. +# +# 2022-10-07: +# - `check_number_whole()` and `_decimal()` no longer treat +# non-numeric types such as factors or dates as numbers. Numeric +# types are detected with `is.numeric()`. # # 2022-10-04: # - Added `check_name()` that forbids the empty string. @@ -25,25 +45,21 @@ # # 2022-08-11: # - Added changelog. +# +# nocov start # Scalars ----------------------------------------------------------------- +.standalone_types_check_dot_call <- .Call + check_bool <- function(x, ..., allow_na = FALSE, allow_null = FALSE, arg = caller_arg(x), call = caller_env()) { - if (!missing(x)) { - if (is_bool(x)) { - return(invisible(NULL)) - } - if (allow_null && is_null(x)) { - return(invisible(NULL)) - } - if (allow_na && identical(x, NA)) { - return(invisible(NULL)) - } + if (!missing(x) && .standalone_types_check_dot_call(ffi_standalone_is_bool_1.0.7, x, allow_na, allow_null)) { + return(invisible(NULL)) } stop_input_type( @@ -136,22 +152,41 @@ check_name <- function(x, ) } +IS_NUMBER_true <- 0 +IS_NUMBER_false <- 1 +IS_NUMBER_oob <- 2 + check_number_decimal <- function(x, ..., - min = -Inf, - max = Inf, + min = NULL, + max = NULL, allow_infinite = TRUE, allow_na = FALSE, allow_null = FALSE, arg = caller_arg(x), call = caller_env()) { - .rlang_types_check_number( + if (missing(x)) { + exit_code <- IS_NUMBER_false + } else if (0 == (exit_code <- .standalone_types_check_dot_call( + ffi_standalone_check_number_1.0.7, + x, + allow_decimal = TRUE, + min, + max, + allow_infinite, + allow_na, + allow_null + ))) { + return(invisible(NULL)) + } + + .stop_not_number( x, ..., + exit_code = exit_code, + allow_decimal = TRUE, min = min, max = max, - allow_decimal = TRUE, - allow_infinite = allow_infinite, allow_na = allow_na, allow_null = allow_null, arg = arg, @@ -161,19 +196,34 @@ check_number_decimal <- function(x, check_number_whole <- function(x, ..., - min = -Inf, - max = Inf, + min = NULL, + max = NULL, allow_na = FALSE, allow_null = FALSE, arg = caller_arg(x), call = caller_env()) { - .rlang_types_check_number( + if (missing(x)) { + exit_code <- IS_NUMBER_false + } else if (0 == (exit_code <- .standalone_types_check_dot_call( + ffi_standalone_check_number_1.0.7, + x, + allow_decimal = FALSE, + min, + max, + allow_infinite = FALSE, + allow_na, + allow_null + ))) { + return(invisible(NULL)) + } + + .stop_not_number( x, ..., + exit_code = exit_code, + allow_decimal = FALSE, min = min, max = max, - allow_decimal = FALSE, - allow_infinite = FALSE, allow_na = allow_na, allow_null = allow_null, arg = arg, @@ -181,23 +231,36 @@ check_number_whole <- function(x, ) } -.rlang_types_check_number <- function(x, - ..., - min = -Inf, - max = Inf, - allow_decimal = FALSE, - allow_infinite = FALSE, - allow_na = FALSE, - allow_null = FALSE, - arg = caller_arg(x), - call = caller_env()) { - if (allow_decimal) { +.stop_not_number <- function(x, + ..., + exit_code, + allow_decimal, + min, + max, + allow_na, + allow_null, + arg, + call) { + if (exit_code == IS_NUMBER_oob) { + min <- min %||% -Inf + max <- max %||% Inf + + if (min > -Inf && max < Inf) { + what <- sprintf("a number between %s and %s", min, max) + } else if (x < min) { + what <- sprintf("a number larger than %s", min) + } else if (x > max) { + what <- sprintf("a number smaller than %s", max) + } else { + abort("Unexpected state in OOB check", .internal = TRUE) + } + } else if (allow_decimal) { what <- "a number" } else { what <- "a whole number" } - .stop <- function(x, what, ...) stop_input_type( + stop_input_type( x, what, ..., @@ -206,63 +269,6 @@ check_number_whole <- function(x, arg = arg, call = call ) - - if (!missing(x)) { - is_number <- is_number( - x, - allow_decimal = allow_decimal, - allow_infinite = allow_infinite - ) - - if (is_number) { - if (min > -Inf && max < Inf) { - what <- sprintf("a number between %s and %s", min, max) - } else { - what <- NULL - } - if (x < min) { - what <- what %||% sprintf("a number larger than %s", min) - .stop(x, what, ...) - } - if (x > max) { - what <- what %||% sprintf("a number smaller than %s", max) - .stop(x, what, ...) - } - return(invisible(NULL)) - } - - if (allow_null && is_null(x)) { - return(invisible(NULL)) - } - if (allow_na && (identical(x, NA) || - identical(x, na_dbl) || - identical(x, na_int))) { - return(invisible(NULL)) - } - } - - .stop(x, what, ...) -} - -is_number <- function(x, - allow_decimal = FALSE, - allow_infinite = FALSE) { - if (!typeof(x) %in% c("integer", "double")) { - return(FALSE) - } - if (length(x) != 1) { - return(FALSE) - } - if (is.na(x)) { - return(FALSE) - } - if (!allow_decimal && !is_integerish(x)) { - return(FALSE) - } - if (!allow_infinite && is.infinite(x)) { - return(FALSE) - } - TRUE } check_symbol <- function(x, @@ -460,4 +466,28 @@ check_character <- function(x, ) } +check_logical <- function(x, + ..., + allow_null = FALSE, + arg = caller_arg(x), + call = caller_env()) { + if (!missing(x)) { + if (is_logical(x)) { + return(invisible(NULL)) + } + if (allow_null && is_null(x)) { + return(invisible(NULL)) + } + } + + stop_input_type( + x, + "a logical vector", + ..., + allow_null = allow_null, + arg = arg, + call = call + ) +} + # nocov end From 81a8b48197bdf641e5af33699d8b46bb0a7d23af Mon Sep 17 00:00:00 2001 From: DavisVaughan Date: Thu, 2 Mar 2023 13:07:05 -0500 Subject: [PATCH 241/312] Record deprecation timeline information --- R/vctrs-deprecated.R | 8 ++++++++ 1 file changed, 8 insertions(+) diff --git a/R/vctrs-deprecated.R b/R/vctrs-deprecated.R index ceed216eb..c9441c6c5 100644 --- a/R/vctrs-deprecated.R +++ b/R/vctrs-deprecated.R @@ -11,6 +11,7 @@ #' @keywords internal #' @export vec_empty <- function(x) { + # Defunct: 2019-06 lifecycle::deprecate_stop( when = "0.2.0", what = "vec_empty()", @@ -35,6 +36,7 @@ vec_empty <- function(x) { #' @keywords internal #' @export vec_type <- function(x) { + # Deprecated: 2019-06 lifecycle::deprecate_warn( when = "0.2.0", what = "vec_type()", @@ -46,6 +48,7 @@ vec_type <- function(x) { #' @rdname vec_type #' @export vec_type_common <- function(..., .ptype = NULL) { + # Deprecated: 2019-06 lifecycle::deprecate_warn( when = "0.2.0", what = "vec_type_common()", @@ -57,6 +60,7 @@ vec_type_common <- function(..., .ptype = NULL) { #' @rdname vec_type #' @export vec_type2 <- function(x, y, ...) { + # Deprecated: 2019-06 lifecycle::deprecate_warn( when = "0.2.0", what = "vec_type2()", @@ -80,6 +84,7 @@ vec_type2 <- function(x, y, ...) { #' @keywords internal #' @export vec_as_index <- function(i, n, names = NULL) { + # Soft-deprecated: 2020-01 lifecycle::deprecate_soft( when = "0.2.2", what = "vec_as_index()", @@ -120,6 +125,7 @@ vec_as_index <- function(i, n, names = NULL) { #' @keywords internal #' @export vec_repeat <- function(x, each = 1L, times = 1L) { + # Soft-deprecated: 2020-03 lifecycle::deprecate_soft( when = "0.3.0", what = "vec_repeat()", @@ -151,6 +157,7 @@ vec_unchop <- function(x, ptype = NULL, name_spec = NULL, name_repair = c("minimal", "unique", "check_unique", "universal")) { + # Soft-deprecated: 2022-09 lifecycle::deprecate_soft("0.5.0", "vec_unchop()", "list_unchop()") list_unchop( @@ -178,6 +185,7 @@ vec_unchop <- function(x, #' @keywords internal #' @export vec_equal_na <- function(x) { + # Soft-deprecated: 2022-09 lifecycle::deprecate_soft("0.5.0", "vec_equal_na()", "vec_detect_missing()") vec_detect_missing(x) } From 6b5c51a828ce476bf0b0502f09776f82aac3a72d Mon Sep 17 00:00:00 2001 From: Davis Vaughan Date: Mon, 6 Mar 2023 09:55:26 -0500 Subject: [PATCH 242/312] Rename `vec_is_list()` and `vec_check_list()` (#1803) * Rename `vec_is_list()` to `obj_is_list()` Silently deprecate `vec_is_list()` for now * Rename `vec_check_list()` to `obj_check_list()` Silently deprecate `vec_check_list()` for now * Update pkgdown reference * NEWS bullet --- NAMESPACE | 2 + NEWS.md | 5 + R/assert.R | 32 +- R/size.R | 2 +- R/type-list-of.R | 2 +- R/type-rcrd.R | 2 +- R/type-vctr.R | 6 +- R/vctrs-deprecated.R | 31 ++ _pkgdown.yml | 2 +- man/new_vctr.Rd | 2 +- man/obj_is_list.Rd | 78 ++++ man/vec_assert.Rd | 2 +- man/vec_is_list.Rd | 56 +-- man/vec_size.Rd | 2 +- man/vector-checks.Rd | 6 +- src/assert.c | 10 +- src/assert.h | 2 +- src/c-unchop.c | 4 +- src/empty.c | 2 +- src/expand.c | 2 +- src/init.c | 4 +- src/size.c | 4 +- src/type-info.c | 8 +- src/type-info.h | 2 +- tests/testthat/_snaps/assert.md | 10 +- tests/testthat/_snaps/lifecycle-deprecated.md | 16 + tests/testthat/test-assert.R | 64 +-- tests/testthat/test-lifecycle-deprecated.R | 16 + vignettes/s3-vector.Rmd | 424 +++++++++++------- 29 files changed, 507 insertions(+), 291 deletions(-) create mode 100644 man/obj_is_list.Rd diff --git a/NAMESPACE b/NAMESPACE index f4350d243..85dd9fe84 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -496,7 +496,9 @@ export(new_rcrd) export(new_vctr) export(num_as_location) export(num_as_location2) +export(obj_check_list) export(obj_check_vector) +export(obj_is_list) export(obj_is_vector) export(obj_print) export(obj_print_data) diff --git a/NEWS.md b/NEWS.md index 6b630f425..020f23076 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,5 +1,10 @@ # vctrs (development version) +* `vec_is_list()` and `vec_check_list()` have been renamed to `obj_is_list()` + and `obj_check_list()`, in line with the new `obj_is_vector()` helper. The + old functions have been silently deprecated, but an official deprecation + process will start in the next vctrs release (#1803). + * `vec_locate_matches()` has changed its default `needles_arg` and `haystack_arg` values from `""` to `"needles"` and `"haystack"`, respectively. This generally generates more informative error messages (#1792). diff --git a/R/assert.R b/R/assert.R index d59832fd1..31ffedf1a 100644 --- a/R/assert.R +++ b/R/assert.R @@ -202,7 +202,7 @@ vec_is <- function(x, ptype = NULL, size = NULL) { #' - The [base type][typeof] of the object is atomic: `"logical"`, `"integer"`, #' `"double"`, `"complex"`, `"character"`, or `"raw"`. #' -#' - `x` is a list, as defined by [vec_is_list()]. +#' - `x` is a list, as defined by [obj_is_list()]. #' #' - `x` is a [data.frame]. #' @@ -245,14 +245,14 @@ vec_is <- function(x, ptype = NULL, size = NULL) { #' #' # S3 lists are vectors if they explicitly inherit from `"list"` #' x <- structure(list(), class = c("my_list", "list")) -#' vec_is_list(x) +#' obj_is_list(x) #' obj_is_vector(x) #' #' # But if they don't explicitly inherit from `"list"`, they aren't #' # automatically considered to be vectors. Instead, vctrs considers this #' # to be a scalar object, like a linear model returned from `lm()`. #' y <- structure(list(), class = "my_list") -#' vec_is_list(y) +#' obj_is_list(y) #' obj_is_vector(y) #' #' # `obj_check_vector()` throws an informative error if the input @@ -295,7 +295,7 @@ vec_check_size <- function(x, #' List checks #' #' @description -#' - `vec_is_list()` tests if `x` is considered a list in the vctrs sense. It +#' - `obj_is_list()` tests if `x` is considered a list in the vctrs sense. It #' returns `TRUE` if: #' - `x` is a bare list with no class. #' - `x` is a list explicitly inheriting from `"list"`. @@ -306,7 +306,7 @@ vec_check_size <- function(x, #' - `list_all_size()` takes a list and returns `TRUE` if all elements of that #' list have the same `size`. #' -#' - `vec_check_list()`, `list_check_all_vectors()`, and `list_check_all_size()` +#' - `obj_check_list()`, `list_check_all_vectors()`, and `list_check_all_size()` #' use the above functions, but throw a standardized and informative error if #' they return `FALSE`. #' @@ -325,9 +325,9 @@ vec_check_size <- function(x, #' @seealso [list_sizes()] #' @export #' @examples -#' vec_is_list(list()) -#' vec_is_list(list_of(1)) -#' vec_is_list(data.frame()) +#' obj_is_list(list()) +#' obj_is_list(list_of(1)) +#' obj_is_list(data.frame()) #' #' list_all_vectors(list(1, mtcars)) #' list_all_vectors(list(1, environment())) @@ -337,12 +337,12 @@ vec_check_size <- function(x, #' #' # `list_`-prefixed functions assume a list: #' try(list_all_vectors(environment())) -vec_is_list <- function(x) { - .Call(vctrs_is_list, x) +obj_is_list <- function(x) { + .Call(ffi_obj_is_list, x) } -#' @rdname vec_is_list +#' @rdname obj_is_list #' @export -vec_check_list <- function(x, +obj_check_list <- function(x, ..., arg = caller_arg(x), call = caller_env()) { @@ -350,13 +350,13 @@ vec_check_list <- function(x, invisible(.Call(ffi_check_list, x, environment())) } -#' @rdname vec_is_list +#' @rdname obj_is_list #' @export list_all_vectors <- function(x) { .Call(ffi_list_all_vectors, x, environment()) } -#' @rdname vec_is_list +#' @rdname obj_is_list #' @export list_check_all_vectors <- function(x, ..., @@ -366,13 +366,13 @@ list_check_all_vectors <- function(x, invisible(.Call(ffi_list_check_all_vectors, x, environment())) } -#' @rdname vec_is_list +#' @rdname obj_is_list #' @export list_all_size <- function(x, size) { .Call(ffi_list_all_size, x, size, environment()) } -#' @rdname vec_is_list +#' @rdname obj_is_list #' @export list_check_all_size <- function(x, size, diff --git a/R/size.R b/R/size.R index 43d790c36..1ee03f75e 100644 --- a/R/size.R +++ b/R/size.R @@ -15,7 +15,7 @@ #' `list_sizes()` returns an integer vector containing the size of each element #' of a list. It is nearly equivalent to, but faster than, #' `map_int(x, vec_size)`, with the exception that `list_sizes()` will -#' error on non-list inputs, as defined by [vec_is_list()]. `list_sizes()` is +#' error on non-list inputs, as defined by [obj_is_list()]. `list_sizes()` is #' to `vec_size()` as [lengths()] is to [length()]. #' #' @seealso [vec_slice()] for a variation of `[` compatible with `vec_size()`, diff --git a/R/type-list-of.R b/R/type-list-of.R index 84714b89b..72db01ce1 100644 --- a/R/type-list-of.R +++ b/R/type-list-of.R @@ -53,7 +53,7 @@ as_list_of.list <- function(x, ..., .ptype = NULL) { #' @keywords internal #' @export new_list_of <- function(x = list(), ptype = logical(), ..., class = character()) { - if (!vec_is_list(x)) { + if (!obj_is_list(x)) { abort("`x` must be a list.") } diff --git a/R/type-rcrd.R b/R/type-rcrd.R index 6f8b9d531..faa3a5888 100644 --- a/R/type-rcrd.R +++ b/R/type-rcrd.R @@ -18,7 +18,7 @@ #' @aliases ses rcrd #' @keywords internal new_rcrd <- function(fields, ..., class = character()) { - if (vec_is_list(fields) && length(vec_unique(list_sizes(fields))) > 1L) { + if (obj_is_list(fields) && length(vec_unique(list_sizes(fields))) > 1L) { abort("All fields must be the same size.") } diff --git a/R/type-vctr.R b/R/type-vctr.R index 1f5fcc8cd..9770bb9d4 100644 --- a/R/type-vctr.R +++ b/R/type-vctr.R @@ -9,7 +9,7 @@ #' @details #' List vctrs are special cases. When created through `new_vctr()`, the #' resulting list vctr should always be recognized as a list by -#' `vec_is_list()`. Because of this, if `inherit_base_type` is `FALSE` +#' `obj_is_list()`. Because of this, if `inherit_base_type` is `FALSE` #' an error is thrown. #' #' @section Base methods: @@ -311,7 +311,7 @@ as.character.vctrs_vctr <- function(x, ...) { as.list.vctrs_vctr <- function(x, ...) { out <- vec_chop(x) - if (vec_is_list(x)) { + if (obj_is_list(x)) { out <- lapply(out, `[[`, 1) } @@ -457,7 +457,7 @@ na_remove <- function(x, type) { #' @export anyNA.vctrs_vctr <- function(x, recursive = FALSE) { - if (recursive && vec_is_list(x)) { + if (recursive && obj_is_list(x)) { any(map_lgl(x, anyNA, recursive = recursive)) } else { any(is.na(x)) diff --git a/R/vctrs-deprecated.R b/R/vctrs-deprecated.R index c9441c6c5..d4490a509 100644 --- a/R/vctrs-deprecated.R +++ b/R/vctrs-deprecated.R @@ -189,3 +189,34 @@ vec_equal_na <- function(x) { lifecycle::deprecate_soft("0.5.0", "vec_equal_na()", "vec_detect_missing()") vec_detect_missing(x) } + +#' List checks +#' +#' @description +#' `r lifecycle::badge("deprecated")` +#' +#' These functions have been deprecated as of vctrs 0.6.0. +#' +#' - `vec_is_list()` has been renamed to [obj_is_list()]. +#' - `vec_check_list()` has been renamed to [obj_check_list()]. +#' +#' @inheritParams obj_is_list +#' +#' @keywords internal +#' @export +vec_is_list <- function(x) { + # Silently-deprecated: 2023-03 + # lifecycle::deprecate_soft("0.6.0", "vec_is_list()", "obj_is_list()") + obj_is_list(x) +} + +#' @rdname vec_is_list +#' @export +vec_check_list <- function(x, + ..., + arg = caller_arg(x), + call = caller_env()) { + # Silently-deprecated: 2023-03 + # lifecycle::deprecate_soft("0.6.0", "vec_check_list()", "obj_check_list()") + obj_check_list(x, ..., arg = arg, call = call) +} diff --git a/_pkgdown.yml b/_pkgdown.yml index f7c8e4924..812117b9f 100644 --- a/_pkgdown.yml +++ b/_pkgdown.yml @@ -41,7 +41,7 @@ reference: - vec_ptype - vec_size - obj_is_vector - - vec_is_list + - obj_is_list - title: Combining contents: diff --git a/man/new_vctr.Rd b/man/new_vctr.Rd index d3101a8f6..8b8f75cb3 100644 --- a/man/new_vctr.Rd +++ b/man/new_vctr.Rd @@ -29,7 +29,7 @@ vector classes. \details{ List vctrs are special cases. When created through \code{new_vctr()}, the resulting list vctr should always be recognized as a list by -\code{vec_is_list()}. Because of this, if \code{inherit_base_type} is \code{FALSE} +\code{obj_is_list()}. Because of this, if \code{inherit_base_type} is \code{FALSE} an error is thrown. } \section{Base methods}{ diff --git a/man/obj_is_list.Rd b/man/obj_is_list.Rd new file mode 100644 index 000000000..70e4cf318 --- /dev/null +++ b/man/obj_is_list.Rd @@ -0,0 +1,78 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/assert.R +\name{obj_is_list} +\alias{obj_is_list} +\alias{obj_check_list} +\alias{list_all_vectors} +\alias{list_check_all_vectors} +\alias{list_all_size} +\alias{list_check_all_size} +\title{List checks} +\usage{ +obj_is_list(x) + +obj_check_list(x, ..., arg = caller_arg(x), call = caller_env()) + +list_all_vectors(x) + +list_check_all_vectors(x, ..., arg = caller_arg(x), call = caller_env()) + +list_all_size(x, size) + +list_check_all_size(x, size, ..., arg = caller_arg(x), call = caller_env()) +} +\arguments{ +\item{x}{For \verb{vec_*()} functions, an object. For \verb{list_*()} functions, a +list.} + +\item{...}{These dots are for future extensions and must be empty.} + +\item{arg}{An argument name as a string. This argument +will be mentioned in error messages as the input that is at the +origin of a problem.} + +\item{call}{The execution environment of a currently +running function, e.g. \code{caller_env()}. The function will be +mentioned in error messages as the source of the error. See the +\code{call} argument of \code{\link[rlang:abort]{abort()}} for more information.} + +\item{size}{The size to check each element for.} +} +\description{ +\itemize{ +\item \code{obj_is_list()} tests if \code{x} is considered a list in the vctrs sense. It +returns \code{TRUE} if: +\itemize{ +\item \code{x} is a bare list with no class. +\item \code{x} is a list explicitly inheriting from \code{"list"}. +} +\item \code{list_all_vectors()} takes a list and returns \code{TRUE} if all elements of +that list are vectors. +\item \code{list_all_size()} takes a list and returns \code{TRUE} if all elements of that +list have the same \code{size}. +\item \code{obj_check_list()}, \code{list_check_all_vectors()}, and \code{list_check_all_size()} +use the above functions, but throw a standardized and informative error if +they return \code{FALSE}. +} +} +\details{ +Notably, data frames and S3 record style classes like POSIXlt are not +considered lists. +} +\examples{ +obj_is_list(list()) +obj_is_list(list_of(1)) +obj_is_list(data.frame()) + +list_all_vectors(list(1, mtcars)) +list_all_vectors(list(1, environment())) + +list_all_size(list(1:2, 2:3), 2) +list_all_size(list(1:2, 2:4), 2) + +# `list_`-prefixed functions assume a list: +try(list_all_vectors(environment())) +} +\seealso{ +\code{\link[=list_sizes]{list_sizes()}} +} diff --git a/man/vec_assert.Rd b/man/vec_assert.Rd index aaee687eb..f1c127476 100644 --- a/man/vec_assert.Rd +++ b/man/vec_assert.Rd @@ -90,7 +90,7 @@ If no \code{\link[=vec_proxy]{vec_proxy()}} method has been registered, \code{x} \itemize{ \item The \link[=typeof]{base type} of the object is atomic: \code{"logical"}, \code{"integer"}, \code{"double"}, \code{"complex"}, \code{"character"}, or \code{"raw"}. -\item \code{x} is a list, as defined by \code{\link[=vec_is_list]{vec_is_list()}}. +\item \code{x} is a list, as defined by \code{\link[=obj_is_list]{obj_is_list()}}. \item \code{x} is a \link{data.frame}. } diff --git a/man/vec_is_list.Rd b/man/vec_is_list.Rd index c565f76ab..a566dd8ff 100644 --- a/man/vec_is_list.Rd +++ b/man/vec_is_list.Rd @@ -1,25 +1,13 @@ % Generated by roxygen2: do not edit by hand -% Please edit documentation in R/assert.R +% Please edit documentation in R/vctrs-deprecated.R \name{vec_is_list} \alias{vec_is_list} \alias{vec_check_list} -\alias{list_all_vectors} -\alias{list_check_all_vectors} -\alias{list_all_size} -\alias{list_check_all_size} \title{List checks} \usage{ vec_is_list(x) vec_check_list(x, ..., arg = caller_arg(x), call = caller_env()) - -list_all_vectors(x) - -list_check_all_vectors(x, ..., arg = caller_arg(x), call = caller_env()) - -list_all_size(x, size) - -list_check_all_size(x, size, ..., arg = caller_arg(x), call = caller_env()) } \arguments{ \item{x}{For \verb{vec_*()} functions, an object. For \verb{list_*()} functions, a @@ -35,44 +23,14 @@ origin of a problem.} running function, e.g. \code{caller_env()}. The function will be mentioned in error messages as the source of the error. See the \code{call} argument of \code{\link[rlang:abort]{abort()}} for more information.} - -\item{size}{The size to check each element for.} } \description{ -\itemize{ -\item \code{vec_is_list()} tests if \code{x} is considered a list in the vctrs sense. It -returns \code{TRUE} if: -\itemize{ -\item \code{x} is a bare list with no class. -\item \code{x} is a list explicitly inheriting from \code{"list"}. -} -\item \code{list_all_vectors()} takes a list and returns \code{TRUE} if all elements of -that list are vectors. -\item \code{list_all_size()} takes a list and returns \code{TRUE} if all elements of that -list have the same \code{size}. -\item \code{vec_check_list()}, \code{list_check_all_vectors()}, and \code{list_check_all_size()} -use the above functions, but throw a standardized and informative error if -they return \code{FALSE}. -} -} -\details{ -Notably, data frames and S3 record style classes like POSIXlt are not -considered lists. -} -\examples{ -vec_is_list(list()) -vec_is_list(list_of(1)) -vec_is_list(data.frame()) +\ifelse{html}{\href{https://lifecycle.r-lib.org/articles/stages.html#deprecated}{\figure{lifecycle-deprecated.svg}{options: alt='[Deprecated]'}}}{\strong{[Deprecated]}} -list_all_vectors(list(1, mtcars)) -list_all_vectors(list(1, environment())) - -list_all_size(list(1:2, 2:3), 2) -list_all_size(list(1:2, 2:4), 2) - -# `list_`-prefixed functions assume a list: -try(list_all_vectors(environment())) +These functions have been deprecated as of vctrs 0.6.0. +\itemize{ +\item \code{vec_is_list()} has been renamed to \code{\link[=obj_is_list]{obj_is_list()}}. +\item \code{vec_check_list()} has been renamed to \code{\link[=obj_check_list]{obj_check_list()}}. } -\seealso{ -\code{\link[=list_sizes]{list_sizes()}} } +\keyword{internal} diff --git a/man/vec_size.Rd b/man/vec_size.Rd index 66e980f33..6a257f4c1 100644 --- a/man/vec_size.Rd +++ b/man/vec_size.Rd @@ -61,7 +61,7 @@ frame (even data frame and matrix columns) have the same size. \code{list_sizes()} returns an integer vector containing the size of each element of a list. It is nearly equivalent to, but faster than, \code{map_int(x, vec_size)}, with the exception that \code{list_sizes()} will -error on non-list inputs, as defined by \code{\link[=vec_is_list]{vec_is_list()}}. \code{list_sizes()} is +error on non-list inputs, as defined by \code{\link[=obj_is_list]{obj_is_list()}}. \code{list_sizes()} is to \code{vec_size()} as \code{\link[=lengths]{lengths()}} is to \code{\link[=length]{length()}}. } \details{ diff --git a/man/vector-checks.Rd b/man/vector-checks.Rd index f88cf00ee..9d0bde483 100644 --- a/man/vector-checks.Rd +++ b/man/vector-checks.Rd @@ -58,7 +58,7 @@ If no \code{\link[=vec_proxy]{vec_proxy()}} method has been registered, \code{x} \itemize{ \item The \link[=typeof]{base type} of the object is atomic: \code{"logical"}, \code{"integer"}, \code{"double"}, \code{"complex"}, \code{"character"}, or \code{"raw"}. -\item \code{x} is a list, as defined by \code{\link[=vec_is_list]{vec_is_list()}}. +\item \code{x} is a list, as defined by \code{\link[=obj_is_list]{obj_is_list()}}. \item \code{x} is a \link{data.frame}. } @@ -102,14 +102,14 @@ obj_is_vector(list()) # S3 lists are vectors if they explicitly inherit from `"list"` x <- structure(list(), class = c("my_list", "list")) -vec_is_list(x) +obj_is_list(x) obj_is_vector(x) # But if they don't explicitly inherit from `"list"`, they aren't # automatically considered to be vectors. Instead, vctrs considers this # to be a scalar object, like a linear model returned from `lm()`. y <- structure(list(), class = "my_list") -vec_is_list(y) +obj_is_list(y) obj_is_vector(y) # `obj_check_vector()` throws an informative error if the input diff --git a/src/assert.c b/src/assert.c index 03d33b190..ce4c3321e 100644 --- a/src/assert.c +++ b/src/assert.c @@ -60,14 +60,14 @@ r_obj* ffi_check_list(r_obj* x, r_obj* frame) { struct r_lazy arg_data = { .x = syms.arg, .env = frame }; struct vctrs_arg arg = new_lazy_arg(&arg_data); - vec_check_list(x, &arg, call); + obj_check_list(x, &arg, call); return r_null; } -void vec_check_list(r_obj* x, +void obj_check_list(r_obj* x, struct vctrs_arg* arg, struct r_lazy call) { - if (!vec_is_list(x)) { + if (!obj_is_list(x)) { stop_non_list_type(x, arg, call); } } @@ -75,7 +75,7 @@ void vec_check_list(r_obj* x, r_obj* ffi_list_check_all_vectors(r_obj* x, r_obj* frame) { // This is an internal error - vec_check_list(x, vec_args.x, (struct r_lazy) {.x = frame, .env = r_null }); + obj_check_list(x, vec_args.x, (struct r_lazy) {.x = frame, .env = r_null }); struct r_lazy call = { .x = r_syms.call, .env = frame }; struct r_lazy arg_caller_data = { .x = syms.arg, .env = frame }; @@ -98,7 +98,7 @@ r_obj* ffi_list_check_all_vectors(r_obj* x, r_obj* frame) { r_obj* ffi_list_check_all_size(r_obj* xs, r_obj* ffi_size, r_obj* frame) { // This is an internal error - vec_check_list(xs, vec_args.x, (struct r_lazy) {.x = frame, .env = r_null }); + obj_check_list(xs, vec_args.x, (struct r_lazy) {.x = frame, .env = r_null }); struct r_lazy arg_lazy = { .x = syms.arg, .env = frame }; struct vctrs_arg arg = new_lazy_arg(&arg_lazy); diff --git a/src/assert.h b/src/assert.h index 8f6f18249..b606c669e 100644 --- a/src/assert.h +++ b/src/assert.h @@ -12,7 +12,7 @@ void vec_check_size(r_obj* x, struct vctrs_arg* arg, struct r_lazy call); -void vec_check_list(r_obj* x, +void obj_check_list(r_obj* x, struct vctrs_arg* arg, struct r_lazy call); diff --git a/src/c-unchop.c b/src/c-unchop.c index 4d1da6cf5..9b7a92fcb 100644 --- a/src/c-unchop.c +++ b/src/c-unchop.c @@ -17,7 +17,7 @@ r_obj* list_unchop(r_obj* xs, const struct name_repair_opts* name_repair, struct vctrs_arg* p_error_arg, struct r_lazy error_call) { - vec_check_list(xs, p_error_arg, error_call); + obj_check_list(xs, p_error_arg, error_call); if (indices == r_null) { return vec_c(xs, ptype, name_spec, name_repair, p_error_arg, error_call); @@ -25,7 +25,7 @@ r_obj* list_unchop(r_obj* xs, // Apply size/type checking to `indices` before possibly early exiting from // having a `NULL` common type or needing to apply a fallback - vec_check_list(indices, vec_args.indices, error_call); + obj_check_list(indices, vec_args.indices, error_call); r_ssize xs_size = vec_size(xs); diff --git a/src/empty.c b/src/empty.c index d9c21b5a8..6f941cd12 100644 --- a/src/empty.c +++ b/src/empty.c @@ -8,7 +8,7 @@ r_obj* vctrs_list_drop_empty(r_obj* x) { static r_obj* list_drop_empty(r_obj* x) { - if (!vec_is_list(x)) { + if (!obj_is_list(x)) { r_abort("`x` must be a list."); } diff --git a/src/expand.c b/src/expand.c index a2914e978..e3b7172be 100644 --- a/src/expand.c +++ b/src/expand.c @@ -29,7 +29,7 @@ r_obj* vec_expand_grid(r_obj* xs, enum vctrs_expand_vary vary, const struct name_repair_opts* p_name_repair_opts, struct r_lazy error_call) { - vec_check_list(xs, vec_args.empty, error_call); + obj_check_list(xs, vec_args.empty, error_call); if (vec_any_missing(xs)) { // Drop `NULL`s before any other checks diff --git a/src/init.c b/src/init.c index 75cb9505f..ae454f2a2 100644 --- a/src/init.c +++ b/src/init.c @@ -92,7 +92,7 @@ extern SEXP vctrs_validate_name_repair_arg(SEXP); extern SEXP vctrs_validate_minimal_names(SEXP, SEXP); extern r_obj* ffi_vec_as_names(r_obj*, r_obj*, r_obj*, r_obj*); extern r_obj* ffi_is_partial(r_obj*); -extern SEXP vctrs_is_list(SEXP); +extern r_obj* ffi_obj_is_list(r_obj*); extern SEXP vctrs_try_catch_callback(SEXP, SEXP); extern r_obj* ffi_is_coercible(r_obj*, r_obj*, r_obj*, r_obj*); extern r_obj* ffi_as_subscript(r_obj*, r_obj*, r_obj*, r_obj*, r_obj*); @@ -275,7 +275,7 @@ static const R_CallMethodDef CallEntries[] = { {"vctrs_validate_minimal_names", (DL_FUNC) &vctrs_validate_minimal_names, 2}, {"ffi_vec_as_names", (DL_FUNC) &ffi_vec_as_names, 4}, {"ffi_is_partial", (DL_FUNC) &ffi_is_partial, 1}, - {"vctrs_is_list", (DL_FUNC) &vctrs_is_list, 1}, + {"ffi_obj_is_list", (DL_FUNC) &ffi_obj_is_list, 1}, {"vctrs_try_catch_callback", (DL_FUNC) &vctrs_try_catch_callback, 2}, {"ffi_is_coercible", (DL_FUNC) &ffi_is_coercible, 4}, {"ffi_as_subscript", (DL_FUNC) &ffi_as_subscript, 5}, diff --git a/src/size.c b/src/size.c index 61712c421..cc6668bfe 100644 --- a/src/size.c +++ b/src/size.c @@ -81,7 +81,7 @@ r_obj* ffi_list_sizes(r_obj* x, r_obj* frame) { } r_obj* list_sizes(r_obj* x, const struct vec_error_opts* opts) { - if (!vec_is_list(x)) { + if (!obj_is_list(x)) { r_abort_lazy_call(opts->call, "%s must be a list, not %s.", r_c_str_format_error_arg("x"), @@ -114,7 +114,7 @@ r_obj* list_sizes(r_obj* x, const struct vec_error_opts* opts) { r_obj* ffi_list_all_size(r_obj* xs, r_obj* ffi_size, r_obj* frame) { // This is an internal error - vec_check_list(xs, vec_args.x, (struct r_lazy) {.x = frame, .env = r_null }); + obj_check_list(xs, vec_args.x, (struct r_lazy) {.x = frame, .env = r_null }); r_ssize size = r_arg_as_ssize(ffi_size, "size"); diff --git a/src/type-info.c b/src/type-info.c index a9323f99e..592369ae5 100644 --- a/src/type-info.c +++ b/src/type-info.c @@ -90,11 +90,11 @@ enum vctrs_type vec_proxy_typeof(r_obj* x) { // [[ register() ]] -r_obj* vctrs_is_list(r_obj* x) { - return r_lgl(vec_is_list(x)); +r_obj* ffi_obj_is_list(r_obj* x) { + return r_lgl(obj_is_list(x)); } -bool vec_is_list(r_obj* x) { +bool obj_is_list(r_obj* x) { // Require `x` to be a list internally if (r_typeof(x) != R_TYPE_list) { return false; @@ -127,7 +127,7 @@ bool obj_is_vector(r_obj* x) { // [[ register() ]] r_obj* ffi_list_all_vectors(r_obj* x, r_obj* frame) { - vec_check_list(x, vec_args.x, (struct r_lazy) { frame, r_null }); + obj_check_list(x, vec_args.x, (struct r_lazy) { frame, r_null }); return r_lgl(list_all_vectors(x)); } diff --git a/src/type-info.h b/src/type-info.h index 867699a68..e2d461b10 100644 --- a/src/type-info.h +++ b/src/type-info.h @@ -65,7 +65,7 @@ enum vctrs_type vec_typeof(r_obj* x); enum vctrs_type vec_proxy_typeof(r_obj* x); const char* vec_type_as_str(enum vctrs_type type); -bool vec_is_list(r_obj* x); +bool obj_is_list(r_obj* x); bool obj_is_vector(r_obj* x); bool list_all_vectors(r_obj* x); diff --git a/tests/testthat/_snaps/assert.md b/tests/testthat/_snaps/assert.md index a691e0f8d..7208e13f3 100644 --- a/tests/testthat/_snaps/assert.md +++ b/tests/testthat/_snaps/assert.md @@ -294,25 +294,25 @@ Error in `list_all_vectors()`: ! `x` must be a list, not an environment. -# vec_check_list() works +# obj_check_list() works Code - my_function <- (function(my_arg) vec_check_list(my_arg)) + my_function <- (function(my_arg) obj_check_list(my_arg)) (expect_error(my_function(env()))) Output Error in `my_function()`: ! `my_arg` must be a list, not an environment. -# vec_check_list() uses a special error when `arg` is the empty string (#1604) +# obj_check_list() uses a special error when `arg` is the empty string (#1604) Code - vec_check_list(1, arg = "") + obj_check_list(1, arg = "") Condition Error: ! Input must be a list, not the number 1. -# vec_check_list() and list_check_all_vectors() work +# obj_check_list() and list_check_all_vectors() work Code my_function <- (function(my_arg) list_check_all_vectors(my_arg)) diff --git a/tests/testthat/_snaps/lifecycle-deprecated.md b/tests/testthat/_snaps/lifecycle-deprecated.md index 055e8949f..de52eb0b6 100644 --- a/tests/testthat/_snaps/lifecycle-deprecated.md +++ b/tests/testthat/_snaps/lifecycle-deprecated.md @@ -20,3 +20,19 @@ Output [1] FALSE TRUE +# vec_check_list() still works + + Code + vec_check_list(1) + Condition + Error: + ! `1` must be a list, not the number 1. + +--- + + Code + my_check(1) + Condition + Error in `my_check()`: + ! `x` must be a list, not the number 1. + diff --git a/tests/testthat/test-assert.R b/tests/testthat/test-assert.R index 445eebd88..4443b7387 100644 --- a/tests/testthat/test-assert.R +++ b/tests/testthat/test-assert.R @@ -72,15 +72,15 @@ test_that("bare lists are vectors", { test_that("S3 lists are not vectors by default", { expect_false(obj_is_vector(foobar())) - expect_false(vec_is_list(foobar())) + expect_false(obj_is_list(foobar())) local_foobar_proxy() # TODO: These seem inconsistent. - # Should we require that S3 list proxies satisfy `vec_is_list()`? + # Should we require that S3 list proxies satisfy `obj_is_list()`? # (i.e. unclass themselves or explicitly inherit from `"list"`?) expect_true(obj_is_vector(foobar())) - expect_false(vec_is_list(foobar())) + expect_false(obj_is_list(foobar())) }) test_that("data frames and records are vectors", { @@ -323,69 +323,69 @@ test_that("vec_check_size() validates `size`", { }) }) -# vec_is_list ----------------------------------------------------------- +# obj_is_list ----------------------------------------------------------- test_that("bare lists are lists", { - expect_true(vec_is_list(list())) + expect_true(obj_is_list(list())) }) test_that("AsIs lists are lists (#1463)", { - expect_true(vec_is_list(I(list()))) - expect_true(vec_is_list(I(list_of(1)))) - expect_false(vec_is_list(I(double()))) + expect_true(obj_is_list(I(list()))) + expect_true(obj_is_list(I(list_of(1)))) + expect_false(obj_is_list(I(double()))) }) test_that("list_of are lists", { - expect_true(vec_is_list(new_list_of())) + expect_true(obj_is_list(new_list_of())) }) test_that("Vectors with a non-VECSXP type are not lists", { - expect_false(vec_is_list(1)) - expect_false(vec_is_list("a")) - expect_false(vec_is_list(quote(name))) + expect_false(obj_is_list(1)) + expect_false(obj_is_list("a")) + expect_false(obj_is_list(quote(name))) }) test_that("explicitly classed lists are lists", { x <- structure(list(), class = "list") - expect_true(vec_is_list(x)) - expect_true(vec_is_list(subclass(x))) + expect_true(obj_is_list(x)) + expect_true(obj_is_list(subclass(x))) }) test_that("explicit inheritance must be in the base class", { x <- structure(1:2, class = c("list", "foobar")) - expect_false(vec_is_list(x)) + expect_false(obj_is_list(x)) }) test_that("POSIXlt are not considered a list", { - expect_false(vec_is_list(as.POSIXlt(new_datetime()))) + expect_false(obj_is_list(as.POSIXlt(new_datetime()))) }) test_that("rcrd types are not lists", { - expect_false(vec_is_list(new_rcrd(list(x = 1)))) + expect_false(obj_is_list(new_rcrd(list(x = 1)))) }) test_that("scalars are not lists", { - expect_false(vec_is_list(foobar())) + expect_false(obj_is_list(foobar())) }) test_that("S3 types can't lie about their internal representation", { x <- structure(1:2, class = c("foobar", "list")) - expect_false(vec_is_list(x)) + expect_false(obj_is_list(x)) }) test_that("data frames of all types are not lists", { - expect_false(vec_is_list(data.frame())) - expect_false(vec_is_list(subclass(data.frame()))) - expect_false(vec_is_list(tibble::tibble())) + expect_false(obj_is_list(data.frame())) + expect_false(obj_is_list(subclass(data.frame()))) + expect_false(obj_is_list(tibble::tibble())) }) test_that("S3 list with non-list proxy is still a list (#1208)", { x <- structure(list(), class = c("foobar", "list")) local_methods(vec_proxy.foobar = function(x) 1) # This used to be an error (#1003) - # expect_error(vec_is_list(x), "`x` inherits") - expect_true(vec_is_list(x)) + # expect_error(obj_is_list(x), "`x` inherits") + expect_true(obj_is_list(x)) }) test_that("list-rcrds with data frame proxies are considered lists (#1208)", { @@ -403,7 +403,7 @@ test_that("list-rcrds with data frame proxies are considered lists (#1208)", { } ) - expect_true(vec_is_list(x)) + expect_true(obj_is_list(x)) }) test_that("list_all_vectors() works", { @@ -413,22 +413,22 @@ test_that("list_all_vectors() works", { expect_snapshot((expect_error(list_all_vectors(env())))) }) -test_that("vec_check_list() works", { - expect_null(vec_check_list(list(1))) - expect_null(vec_check_list(list_of(1))) +test_that("obj_check_list() works", { + expect_null(obj_check_list(list(1))) + expect_null(obj_check_list(list_of(1))) expect_snapshot({ - my_function <- function(my_arg) vec_check_list(my_arg) + my_function <- function(my_arg) obj_check_list(my_arg) (expect_error(my_function(env()))) }) }) -test_that("vec_check_list() uses a special error when `arg` is the empty string (#1604)", { +test_that("obj_check_list() uses a special error when `arg` is the empty string (#1604)", { expect_snapshot(error = TRUE, { - vec_check_list(1, arg = "") + obj_check_list(1, arg = "") }) }) -test_that("vec_check_list() and list_check_all_vectors() work", { +test_that("obj_check_list() and list_check_all_vectors() work", { expect_null(list_check_all_vectors(list())) expect_null(list_check_all_vectors(list(1, mtcars))) expect_snapshot({ diff --git a/tests/testthat/test-lifecycle-deprecated.R b/tests/testthat/test-lifecycle-deprecated.R index 7d53594a7..226a1633e 100644 --- a/tests/testthat/test-lifecycle-deprecated.R +++ b/tests/testthat/test-lifecycle-deprecated.R @@ -39,3 +39,19 @@ test_that("vec_equal_na() still works", { c(FALSE, TRUE, FALSE, TRUE) ) }) + +test_that("vec_is_list() still works", { + expect_false(vec_is_list(1)) + expect_true(vec_is_list(list())) +}) + +test_that("vec_check_list() still works", { + my_check <- function(x) vec_check_list(x) + + expect_snapshot(error = TRUE, { + vec_check_list(1) + }) + expect_snapshot(error = TRUE, { + my_check(1) + }) +}) diff --git a/vignettes/s3-vector.Rmd b/vignettes/s3-vector.Rmd index a444c4688..79434c849 100644 --- a/vignettes/s3-vector.Rmd +++ b/vignettes/s3-vector.Rmd @@ -15,11 +15,14 @@ knitr::opts_chunk$set( set.seed(1014) ``` -This vignette shows you how to create your own S3 vector classes. It focuses on the aspects of making a vector class that every class needs to worry about; you'll also need to provide methods that actually make the vector useful. +This vignette shows you how to create your own S3 vector classes. +It focuses on the aspects of making a vector class that every class needs to worry about; you'll also need to provide methods that actually make the vector useful. -I assume that you're already familiar with the basic machinery of S3, and the vocabulary I use in Advanced R: constructor, helper, and validator. If not, I recommend reading at least the first two sections of [the S3 chapter](https://adv-r.hadley.nz/s3.html) of _Advanced R_. +I assume that you're already familiar with the basic machinery of S3, and the vocabulary I use in Advanced R: constructor, helper, and validator. +If not, I recommend reading at least the first two sections of [the S3 chapter](https://adv-r.hadley.nz/s3.html) of *Advanced R*. -This article refers to "vectors of numbers" as *double vectors*. Here, "double" stands for ["double precision floating point number"](https://en.wikipedia.org/wiki/Double-precision_floating-point_format), see also `double()`. +This article refers to "vectors of numbers" as *double vectors*. +Here, "double" stands for ["double precision floating point number"](https://en.wikipedia.org/wiki/Double-precision_floating-point_format), see also `double()`. ```{r setup} library(vctrs) @@ -29,45 +32,57 @@ library(zeallot) This vignette works through five big topics: -* The basics of creating a new vector class with vctrs. -* The coercion and casting system. -* The record and list-of types. -* Equality and comparison proxies. -* Arithmetic operators. +- The basics of creating a new vector class with vctrs. +- The coercion and casting system. +- The record and list-of types. +- Equality and comparison proxies. +- Arithmetic operators. They're collectively demonstrated with a number of simple S3 classes: -* Percent: a double vector that prints as a percentage. This illustrates the basic mechanics of class creation, coercion, and casting. +- Percent: a double vector that prints as a percentage. + This illustrates the basic mechanics of class creation, coercion, and casting. -* Decimal: a double vector that always prints with a fixed number of decimal places. This class has an attribute which needs a little extra care in casts and coercions. +- Decimal: a double vector that always prints with a fixed number of decimal places. + This class has an attribute which needs a little extra care in casts and coercions. -* Cached sum: a double vector that caches the total sum in an attribute. The attribute depends on the data, so needs extra care. +- Cached sum: a double vector that caches the total sum in an attribute. + The attribute depends on the data, so needs extra care. -* Rational: a pair of integer vectors that defines a rational number like `2 / 3`. This introduces you to the record style, and to the equality and comparison operators. It also needs special handling for `+`, `-`, and friends. +- Rational: a pair of integer vectors that defines a rational number like `2 / 3`. + This introduces you to the record style, and to the equality and comparison operators. + It also needs special handling for `+`, `-`, and friends. -* Polynomial: a list of integer vectors that define polynomials like `1 + x - x^3`. Sorting such vectors correctly requires a custom equality method. +- Polynomial: a list of integer vectors that define polynomials like `1 + x - x^3`. + Sorting such vectors correctly requires a custom equality method. -* Meter: a numeric vector with meter units. This is the simplest possible class with interesting algebraic properties. - -* Period and frequency: a pair of classes represent a period, or it's inverse, frequency. This allows us to explore more arithmetic operators. +- Meter: a numeric vector with meter units. + This is the simplest possible class with interesting algebraic properties. +- Period and frequency: a pair of classes represent a period, or it's inverse, frequency. + This allows us to explore more arithmetic operators. ## Basics -In this section you'll learn how to create a new vctrs class by calling `new_vctr()`. This creates an object with class `vctrs_vctr` which has a number of methods. These are designed to make your life as easy as possible. For example: - -* The `print()` and `str()` methods are defined in terms of `format()` so you get a pleasant, consistent display as soon as you've made your `format()` method. +In this section you'll learn how to create a new vctrs class by calling `new_vctr()`. +This creates an object with class `vctrs_vctr` which has a number of methods. +These are designed to make your life as easy as possible. +For example: -* You can immediately put your new vector class in a data frame because `as.data.frame.vctrs_vctr()` does the right thing. +- The `print()` and `str()` methods are defined in terms of `format()` so you get a pleasant, consistent display as soon as you've made your `format()` method. -* Subsetting (`[`, `[[`, and `$`), `length<-`, and `rep()` methods automatically preserve attributes because they use `vec_restore()`. A default `vec_restore()` works for all classes where the attributes are data-independent, and can easily be customised when the attributes do depend on the data. +- You can immediately put your new vector class in a data frame because `as.data.frame.vctrs_vctr()` does the right thing. -* Default subset-assignment methods (`[<-`, `[[<-`, and `$<-`) follow the principle that the new values should be coerced to match the existing vector. This gives predictable behaviour and clear error messages. +- Subsetting (`[`, `[[`, and `$`), `length<-`, and `rep()` methods automatically preserve attributes because they use `vec_restore()`. + A default `vec_restore()` works for all classes where the attributes are data-independent, and can easily be customised when the attributes do depend on the data. +- Default subset-assignment methods (`[<-`, `[[<-`, and `$<-`) follow the principle that the new values should be coerced to match the existing vector. + This gives predictable behaviour and clear error messages. ### Percent class -In this section, I'll show you how to make a `percent` class, i.e., a double vector that is printed as a percentage. We start by defining a low-level [constructor](https://adv-r.hadley.nz/s3.html#s3-constrcutor) to check types and/or sizes and call `new_vctr()`. +In this section, I'll show you how to make a `percent` class, i.e., a double vector that is printed as a percentage. +We start by defining a low-level [constructor](https://adv-r.hadley.nz/s3.html#s3-constrcutor) to check types and/or sizes and call `new_vctr()`. `percent` is built on a double vector of any length and doesn't have any attributes. @@ -85,9 +100,12 @@ x str(x) ``` -Note that we prefix the name of the class with the name of the package. This prevents conflicting definitions between packages. For packages that implement only one class (such as [blob](https://blob.tidyverse.org/)), it's fine to use the package name without prefix as the class name. +Note that we prefix the name of the class with the name of the package. +This prevents conflicting definitions between packages. +For packages that implement only one class (such as [blob](https://blob.tidyverse.org/)), it's fine to use the package name without prefix as the class name. -We then follow up with a user friendly [helper](https://adv-r.hadley.nz/s3.html#helpers). Here we'll use `vec_cast()` to allow it to accept anything coercible to a double: +We then follow up with a user friendly [helper](https://adv-r.hadley.nz/s3.html#helpers). +Here we'll use `vec_cast()` to allow it to accept anything coercible to a double: ```{r} percent <- function(x = double()) { @@ -96,7 +114,8 @@ percent <- function(x = double()) { } ``` -Before you go on, check that user-friendly constructor returns a zero-length vector when called with no arguments. This makes it easy to use as a prototype. +Before you go on, check that user-friendly constructor returns a zero-length vector when called with no arguments. +This makes it easy to use as a prototype. ```{r} new_percent() @@ -111,10 +130,11 @@ is_percent <- function(x) { } ``` - ### `format()` method -The first method for every class should almost always be a `format()` method. This should return a character vector the same length as `x`. The easiest way to do this is to rely on one of R's low-level formatting functions like `formatC()`: +The first method for every class should almost always be a `format()` method. +This should return a character vector the same length as `x`. +The easiest way to do this is to rely on one of R's low-level formatting functions like `formatC()`: ```{r} format.vctrs_percent <- function(x, ...) { @@ -135,7 +155,7 @@ s3_register("base::format", "vctrs_percent") x ``` -(Note the use of `vec_data()` so `format()` doesn't get stuck in an infinite loop, and that I take a little care to not convert `NA` to `"NA"`; this leads to better printing.) +(Note the use of `vec_data()` so `format()` doesn't get stuck in an infinite loop, and that I take a little care to not convert `NA` to `"NA"`; this leads to better printing.) The format method is also used by data frames, tibbles, and `str()`: @@ -143,7 +163,8 @@ The format method is also used by data frames, tibbles, and `str()`: data.frame(x) ``` -For optimal display, I recommend also defining an abbreviated type name, which should be 4-5 letters for commonly used vectors. This is used in tibbles and in `str()`: +For optimal display, I recommend also defining an abbreviated type name, which should be 4-5 letters for commonly used vectors. +This is used in tibbles and in `str()`: ```{r} vec_ptype_abbr.vctrs_percent <- function(x, ...) { @@ -155,36 +176,44 @@ tibble::tibble(x) str(x) ``` -If you need more control over printing in tibbles, implement a method for `pillar::pillar_shaft()`. See `vignette("pillar", package = "vctrs")` for details. - +If you need more control over printing in tibbles, implement a method for `pillar::pillar_shaft()`. +See `vignette("pillar", package = "vctrs")` for details. ## Casting and coercion -The next set of methods you are likely to need are those related to coercion and casting. Coercion and casting are two sides of the same coin: changing the prototype of an existing object. When the change happens _implicitly_ (e.g in `c()`) we call it __coercion__; when the change happens _explicitly_ (e.g. with `as.integer(x)`), we call it __casting__. +The next set of methods you are likely to need are those related to coercion and casting. +Coercion and casting are two sides of the same coin: changing the prototype of an existing object. +When the change happens *implicitly* (e.g in `c()`) we call it **coercion**; when the change happens *explicitly* (e.g. with `as.integer(x)`), we call it **casting**. -One of the main goals of vctrs is to put coercion and casting on a robust theoretical footing so it's possible to make accurate predictions about what (e.g.) `c(x, y)` should do when `x` and `y` have different prototypes. vctrs achieves this goal through two generics: +One of the main goals of vctrs is to put coercion and casting on a robust theoretical footing so it's possible to make accurate predictions about what (e.g.) `c(x, y)` should do when `x` and `y` have different prototypes. +vctrs achieves this goal through two generics: -* `vec_ptype2(x, y)` defines possible set of coercions. It returns a prototype if `x` and `y` can be safely coerced to the same prototype; otherwise it returns an error. The set of automatic coercions is usually quite small because too many tend to make code harder to reason about and silently propagate mistakes. - -* `vec_cast(x, to)` defines the possible sets of casts. It returns `x` translated to have prototype `to`, or throws an error if the conversion isn't possible. The set of possible casts is a superset of possible coercions because they're requested explicitly. +- `vec_ptype2(x, y)` defines possible set of coercions. + It returns a prototype if `x` and `y` can be safely coerced to the same prototype; otherwise it returns an error. + The set of automatic coercions is usually quite small because too many tend to make code harder to reason about and silently propagate mistakes. +- `vec_cast(x, to)` defines the possible sets of casts. + It returns `x` translated to have prototype `to`, or throws an error if the conversion isn't possible. + The set of possible casts is a superset of possible coercions because they're requested explicitly. ### Double dispatch -Both generics use __[double dispatch](https://en.wikipedia.org/wiki/Double_dispatch)__ which means that the implementation is selected based on the class of two arguments, not just one. S3 does not natively support double dispatch, so we implement our own dispatch mechanism. In practice, this means: - -- You end up with method names with two classes, like `vec_ptype2.foo.bar()`. +Both generics use [**double dispatch**](https://en.wikipedia.org/wiki/Double_dispatch) which means that the implementation is selected based on the class of two arguments, not just one. +S3 does not natively support double dispatch, so we implement our own dispatch mechanism. +In practice, this means: -- You don't need to implement default methods (they would never be called if you do). +- You end up with method names with two classes, like `vec_ptype2.foo.bar()`. -- You can't call `NextMethod()`. +- You don't need to implement default methods (they would never be called if you do). +- You can't call `NextMethod()`. ### Percent class {#percent} We'll make our percent class coercible back and forth with double vectors. -`vec_ptype2()` provides a user friendly error message if the coercion doesn't exist and makes sure `NA` is handled in a standard way. `NA` is technically a logical vector, but we want to stand in for a missing value of any type. +`vec_ptype2()` provides a user friendly error message if the coercion doesn't exist and makes sure `NA` is handled in a standard way. +`NA` is technically a logical vector, but we want to stand in for a missing value of any type. ```{r, error = TRUE} vec_ptype2("bogus", percent()) @@ -198,15 +227,20 @@ By default and in simple cases, an object of the same class is compatible with i vec_ptype2(percent(), percent()) ``` -However this only works if the attributes for both objects are the same. Also the default methods are a bit slower. It is always a good idea to provide an explicit coercion method for the case of identical classes. So we'll start by saying that a `vctrs_percent` combined with a `vctrs_percent` yields a `vctrs_percent`, which we indicate by returning a prototype generated by the constructor. +However this only works if the attributes for both objects are the same. +Also the default methods are a bit slower. +It is always a good idea to provide an explicit coercion method for the case of identical classes. +So we'll start by saying that a `vctrs_percent` combined with a `vctrs_percent` yields a `vctrs_percent`, which we indicate by returning a prototype generated by the constructor. ```{r} vec_ptype2.vctrs_percent.vctrs_percent <- function(x, y, ...) new_percent() ``` -Next we define methods that say that combining a `percent` and double should yield a `double`. We avoid returning a `percent` here because errors in the scale (1 vs. 0.01) are more obvious with raw numbers. +Next we define methods that say that combining a `percent` and double should yield a `double`. +We avoid returning a `percent` here because errors in the scale (1 vs. 0.01) are more obvious with raw numbers. -Because double dispatch is a bit of a hack, we need to provide two methods. It's your responsibility to ensure that each member of the pair returns the same result: if they don't you will get weird and unpredictable behaviour. +Because double dispatch is a bit of a hack, we need to provide two methods. +It's your responsibility to ensure that each member of the pair returns the same result: if they don't you will get weird and unpredictable behaviour. The double dispatch mechanism requires us to refer to the underlying type, `double`, in the method name. If we implemented `vec_ptype2.vctrs_percent.numeric()`, it would never be called. @@ -222,15 +256,21 @@ We can check that we've implemented this correctly with `vec_ptype_show()`: vec_ptype_show(percent(), double(), percent()) ``` -The `vec_ptype2()` methods define which input is the richer type that vctrs should coerce to. However, they don't perform any conversion. This is the job of `vec_cast()`, which we implement next. We'll provide a method to cast a percent to a percent: +The `vec_ptype2()` methods define which input is the richer type that vctrs should coerce to. +However, they don't perform any conversion. +This is the job of `vec_cast()`, which we implement next. +We'll provide a method to cast a percent to a percent: ```{r} vec_cast.vctrs_percent.vctrs_percent <- function(x, to, ...) x ``` -And then for converting back and forth between doubles. To convert a double to a percent we use the `percent()` helper (not the constructor; this is unvalidated user input). To convert a `percent` to a double, we strip the attributes. +And then for converting back and forth between doubles. +To convert a double to a percent we use the `percent()` helper (not the constructor; this is unvalidated user input). +To convert a `percent` to a double, we strip the attributes. -Note that for historical reasons the order of argument in the signature is the opposite as for `vec_ptype2()`. The class for `to` comes first, and the class for `x` comes second. +Note that for historical reasons the order of argument in the signature is the opposite as for `vec_ptype2()`. +The class for `to` comes first, and the class for `x` comes second. Again, the double dispatch mechanism requires us to refer to the underlying type, `double`, in the method name. Implementing `vec_cast.vctrs_percent.numeric()` has no effect. @@ -261,7 +301,8 @@ x[[3]] <- 0.5 x ``` -You'll also get mostly correct behaviour for `c()`. The exception is when you use `c()` with a base R class: +You'll also get mostly correct behaviour for `c()`. +The exception is when you use `c()` with a base R class: ```{r, error = TRUE} # Correct @@ -282,7 +323,9 @@ as_percent <- function(x) { } ``` -Occasionally, it is useful to provide conversions that go beyond what's allowed in casting. For example, we could offer a parsing method for character vectors. In this case, `as_percent()` should be generic, the default method should cast, and then additional methods should implement more flexible conversion: +Occasionally, it is useful to provide conversions that go beyond what's allowed in casting. +For example, we could offer a parsing method for character vectors. +In this case, `as_percent()` should be generic, the default method should cast, and then additional methods should implement more flexible conversion: ```{r} as_percent <- function(x, ...) { @@ -299,13 +342,14 @@ as_percent.character <- function(x) { } ``` - - ### Decimal class -Now that you've seen the basics with a very simple S3 class, we'll gradually explore more complicated scenarios. This section creates a `decimal` class that prints with the specified number of decimal places. This is very similar to `percent` but now the class needs an attribute: the number of decimal places to display (an integer vector of length 1). +Now that you've seen the basics with a very simple S3 class, we'll gradually explore more complicated scenarios. +This section creates a `decimal` class that prints with the specified number of decimal places. +This is very similar to `percent` but now the class needs an attribute: the number of decimal places to display (an integer vector of length 1). -We start off as before, defining a low-level constructor, a user-friendly constructor, a `format()` method, and a `vec_ptype_abbr()`. Note that additional object attributes are simply passed along to `new_vctr()`: +We start off as before, defining a low-level constructor, a user-friendly constructor, a `format()` method, and a `vec_ptype_abbr()`. +Note that additional object attributes are simply passed along to `new_vctr()`: ```{r} new_decimal <- function(x = double(), digits = 2L) { @@ -341,9 +385,11 @@ x <- decimal(runif(10), 1L) x ``` -Note that I provide a little helper to extract the `digits` attribute. This makes the code a little easier to read and should not be exported. +Note that I provide a little helper to extract the `digits` attribute. +This makes the code a little easier to read and should not be exported. -By default, vctrs assumes that attributes are independent of the data and so are automatically preserved. You'll see what to do if the attributes are data dependent in the next section. +By default, vctrs assumes that attributes are independent of the data and so are automatically preserved. +You'll see what to do if the attributes are data dependent in the next section. ```{r} x[1:2] @@ -360,7 +406,9 @@ vec_ptype_full.vctrs_decimal <- function(x, ...) { x ``` -Now consider `vec_cast()` and `vec_ptype2()`. Casting and coercing from one decimal to another requires a little thought as the values of the `digits` attribute might be different, and we need some way to reconcile them. Here I've decided to chose the maximum of the two; other reasonable options are to take the value from the left-hand side or throw an error. +Now consider `vec_cast()` and `vec_ptype2()`. +Casting and coercing from one decimal to another requires a little thought as the values of the `digits` attribute might be different, and we need some way to reconcile them. +Here I've decided to chose the maximum of the two; other reasonable options are to take the value from the left-hand side or throw an error. ```{r} vec_ptype2.vctrs_decimal.vctrs_decimal <- function(x, y, ...) { @@ -373,7 +421,8 @@ vec_cast.vctrs_decimal.vctrs_decimal <- function(x, to, ...) { vec_c(decimal(1/100, digits = 3), decimal(2/100, digits = 2)) ``` -Finally, I can implement coercion to and from other types, like doubles. When automatically coercing, I choose the richer type (i.e., the decimal). +Finally, I can implement coercion to and from other types, like doubles. +When automatically coercing, I choose the richer type (i.e., the decimal). ```{r} vec_ptype2.vctrs_decimal.double <- function(x, y, ...) x @@ -386,7 +435,9 @@ vec_c(decimal(1, digits = 1), pi) vec_c(pi, decimal(1, digits = 1)) ``` -If type `x` has greater resolution than `y`, there will be some inputs that lose precision. These should generate errors using `stop_lossy_cast()`. You can see that in action when casting from doubles to integers; only some doubles can become integers without losing resolution. +If type `x` has greater resolution than `y`, there will be some inputs that lose precision. +These should generate errors using `stop_lossy_cast()`. +You can see that in action when casting from doubles to integers; only some doubles can become integers without losing resolution. ```{r, error = TRUE} vec_cast(c(1, 2, 10), to = integer()) @@ -394,10 +445,11 @@ vec_cast(c(1, 2, 10), to = integer()) vec_cast(c(1.5, 2, 10.5), to = integer()) ``` - ### Cached sum class {#cached-sum} -The next level up in complexity is an object that has data-dependent attributes. To explore this idea we'll create a vector that caches the sum of its values. As usual, we start with low-level and user-friendly constructors: +The next level up in complexity is an object that has data-dependent attributes. +To explore this idea we'll create a vector that caches the sum of its values. +As usual, we start with low-level and user-friendly constructors: ```{r} new_cached_sum <- function(x = double(), sum = 0L) { @@ -418,7 +470,8 @@ cached_sum <- function(x) { } ``` -For this class, we can use the default `format()` method, and instead, we'll customise the `obj_print_footer()` method. This is a good place to display user facing attributes. +For this class, we can use the default `format()` method, and instead, we'll customise the `obj_print_footer()` method. +This is a good place to display user facing attributes. ```{r} obj_print_footer.vctrs_cached_sum <- function(x, ...) { @@ -429,7 +482,8 @@ x <- cached_sum(runif(10)) x ``` -We'll also override `sum()` and `mean()` to use the attribute. This is easiest to do with `vec_math()`, which you'll learn about later. +We'll also override `sum()` and `mean()` to use the attribute. +This is easiest to do with `vec_math()`, which you'll learn about later. ```{r} vec_math.vctrs_cached_sum <- function(.fn, .x, ...) { @@ -444,13 +498,15 @@ vec_math.vctrs_cached_sum <- function(.fn, .x, ...) { sum(x) ``` -As mentioned above, vctrs assumes that attributes are independent of the data. This means that when we take advantage of the default methods, they'll work, but return the incorrect result: +As mentioned above, vctrs assumes that attributes are independent of the data. +This means that when we take advantage of the default methods, they'll work, but return the incorrect result: ```{r} x[1:2] ``` -To fix this, you need to provide a `vec_restore()` method. Note that this method dispatches on the `to` argument. +To fix this, you need to provide a `vec_restore()` method. +Note that this method dispatches on the `to` argument. ```{r} vec_restore.vctrs_cached_sum <- function(x, to, ..., i = NULL) { @@ -460,14 +516,20 @@ vec_restore.vctrs_cached_sum <- function(x, to, ..., i = NULL) { x[1] ``` -This works because most of the vctrs methods dispatch to the underlying base function by first stripping off extra attributes with `vec_data()` and then reapplying them again with `vec_restore()`. The default `vec_restore()` method copies over all attributes, which is not appropriate when the attributes depend on the data. - -Note that `vec_restore.class` is subtly different from `vec_cast.class.class()`. `vec_restore()` is used when restoring attributes that have been lost; `vec_cast()` is used for coercions. This is easier to understand with a concrete example. Imagine factors were implemented with `new_vctr()`. `vec_restore.factor()` would restore attributes back to an integer vector, but you would not want to allow manually casting an integer to a factor with `vec_cast()`. +This works because most of the vctrs methods dispatch to the underlying base function by first stripping off extra attributes with `vec_data()` and then reapplying them again with `vec_restore()`. +The default `vec_restore()` method copies over all attributes, which is not appropriate when the attributes depend on the data. +Note that `vec_restore.class` is subtly different from `vec_cast.class.class()`. +`vec_restore()` is used when restoring attributes that have been lost; `vec_cast()` is used for coercions. +This is easier to understand with a concrete example. +Imagine factors were implemented with `new_vctr()`. +`vec_restore.factor()` would restore attributes back to an integer vector, but you would not want to allow manually casting an integer to a factor with `vec_cast()`. ## Record-style objects -Record-style objects use a list of equal-length vectors to represent individual components of the object. The best example of this is `POSIXlt`, which underneath the hood is a list of 11 fields like year, month, and day. Record-style classes override `length()` and subsetting methods to conceal this implementation detail. +Record-style objects use a list of equal-length vectors to represent individual components of the object. +The best example of this is `POSIXlt`, which underneath the hood is a list of 11 fields like year, month, and day. +Record-style classes override `length()` and subsetting methods to conceal this implementation detail. ```{r} x <- as.POSIXlt(ISOdatetime(2020, 1, 1, 0, 0, 1:3)) @@ -482,12 +544,13 @@ unclass(x)[[1]] # the first component, the number of seconds vctrs makes it easy to create new record-style classes using `new_rcrd()`, which has a wide selection of default methods. - ### Rational class -A fraction, or rational number, can be represented by a pair of integer vectors representing the numerator (the number on top) and the denominator (the number on bottom), where the length of each vector must be the same. To represent such a data structure we turn to a new base data type: the record (or rcrd for short). +A fraction, or rational number, can be represented by a pair of integer vectors representing the numerator (the number on top) and the denominator (the number on bottom), where the length of each vector must be the same. +To represent such a data structure we turn to a new base data type: the record (or rcrd for short). -As usual we start with low-level and user-friendly constructors. The low-level constructor calls `new_rcrd()`, which needs a named list of equal-length vectors. +As usual we start with low-level and user-friendly constructors. +The low-level constructor calls `new_rcrd()`, which needs a named list of equal-length vectors. ```{r} new_rational <- function(n = integer(), d = integer()) { @@ -515,7 +578,8 @@ rational <- function(n = integer(), d = integer()) { x <- rational(1, 1:10) ``` -Behind the scenes, `x` is a named list with two elements. But those details are hidden so that it behaves like a vector: +Behind the scenes, `x` is a named list with two elements. +But those details are hidden so that it behaves like a vector: ```{r} names(x) @@ -529,7 +593,8 @@ fields(x) field(x, "n") ``` -Notice that we can't `print()` or `str()` the new rational vector `x` yet. Printing causes an error: +Notice that we can't `print()` or `str()` the new rational vector `x` yet. +Printing causes an error: ```{r, error = TRUE} x @@ -537,7 +602,8 @@ x str(x) ``` -This is because we haven't defined how our class can be printed from the underlying data. Note that if you want to look under the hood during development, you can always call `vec_data(x)`. +This is because we haven't defined how our class can be printed from the underlying data. +Note that if you want to look under the hood during development, you can always call `vec_data(x)`. ```{r} vec_data(x) @@ -545,7 +611,8 @@ vec_data(x) str(vec_data(x)) ``` -It is generally best to define a formatting method early in the development of a class. The format method defines how to display the class so that it can be printed in the normal way: +It is generally best to define a formatting method early in the development of a class. +The format method defines how to display the class so that it can be printed in the normal way: ```{r} format.vctrs_rational <- function(x, ...) { @@ -570,7 +637,8 @@ vctrs uses the `format()` method in `str()`, hiding the underlying implementatio str(x) ``` -For `rational`, `vec_ptype2()` and `vec_cast()` follow the same pattern as `percent()`. We allow coercion from integer and to doubles. +For `rational`, `vec_ptype2()` and `vec_cast()` follow the same pattern as `percent()`. +We allow coercion from integer and to doubles. ```{r} vec_ptype2.vctrs_rational.vctrs_rational <- function(x, y, ...) new_rational() @@ -584,12 +652,13 @@ vec_cast.vctrs_rational.integer <- function(x, to, ...) rational(x, 1) vec_c(rational(1, 2), 1L, NA) ``` - ### Decimal2 class -The previous implementation of `decimal` was built on top of doubles. This is a bad idea because decimal vectors are typically used when you care about precise values (i.e., dollars and cents in a bank account), and double values suffer from floating point problems. +The previous implementation of `decimal` was built on top of doubles. +This is a bad idea because decimal vectors are typically used when you care about precise values (i.e., dollars and cents in a bank account), and double values suffer from floating point problems. -A better implementation of a decimal class would be to use pair of integers, one for the value to the left of the decimal point, and the other for the value to the right (divided by a `scale`). The following code is a very quick sketch of how you might start creating such a class: +A better implementation of a decimal class would be to use pair of integers, one for the value to the left of the decimal point, and the other for the value to the right (divided by a `scale`). +The following code is a very quick sketch of how you might start creating such a class: ```{r} new_decimal2 <- function(l, r, scale = 2L) { @@ -625,37 +694,45 @@ format.vctrs_decimal2 <- function(x, ...) { decimal2(10, c(0, 5, 99)) ``` - ## Equality and comparison -vctrs provides four "proxy" generics. Two of these let you control how your class determines equality and comparison: +vctrs provides four "proxy" generics. +Two of these let you control how your class determines equality and comparison: -* `vec_proxy_equal()` returns a data vector suitable for comparison. It underpins `==`, `!=`, `unique()`, `anyDuplicated()`, and `is.na()`. +- `vec_proxy_equal()` returns a data vector suitable for comparison. + It underpins `==`, `!=`, `unique()`, `anyDuplicated()`, and `is.na()`. -* `vec_proxy_compare()` specifies how to compare the elements of your vector. This proxy is used in `<`, `<=`, `>=`, `>`, `min()`, `max()`, `median()`, and `quantile()`. +- `vec_proxy_compare()` specifies how to compare the elements of your vector. + This proxy is used in `<`, `<=`, `>=`, `>`, `min()`, `max()`, `median()`, and `quantile()`. Two other proxy generic are used for sorting for unordered data types and for accessing the raw data for exotic storage formats: -* `vec_proxy_order()` specifies how to sort the elements of your vector. It is used in `xtfrm()`, which in turn is called by the `order()` and `sort()` functions. +- `vec_proxy_order()` specifies how to sort the elements of your vector. + It is used in `xtfrm()`, which in turn is called by the `order()` and `sort()` functions. - This proxy was added to implement the behaviour of lists, which are sortable (their order proxy sorts by first occurrence) but not comparable (comparison operators cause an error). Its default implementation for other classes calls `vec_proxy_compare()` and you normally don't need to implement this proxy. + This proxy was added to implement the behaviour of lists, which are sortable (their order proxy sorts by first occurrence) but not comparable (comparison operators cause an error). + Its default implementation for other classes calls `vec_proxy_compare()` and you normally don't need to implement this proxy. -* `vec_proxy()` returns the actual data of a vector. This is useful when you store the data in a field of your class. Most of the time, you shouldn't need to implement `vec_proxy()`. +- `vec_proxy()` returns the actual data of a vector. + This is useful when you store the data in a field of your class. + Most of the time, you shouldn't need to implement `vec_proxy()`. The default behavior is as follows: -- `vec_proxy_equal()` calls `vec_proxy()` -- `vec_proxy_compare()` calls `vec_proxy_equal()` -- `vec_proxy_order()` calls `vec_proxy_compare()` - -You should only implement these proxies when some preprocessing on the data is needed to make elements comparable. In that case, defining these methods will get you a lot of behaviour for relatively little work. +- `vec_proxy_equal()` calls `vec_proxy()` +- `vec_proxy_compare()` calls `vec_proxy_equal()` +- `vec_proxy_order()` calls `vec_proxy_compare()` -These proxy functions should always return a simple object (either a bare vector or a data frame) that possesses the same properties as your class. This permits efficient implementation of the vctrs internals because it allows dispatch to happen once in R, and then efficient computations can be written in C. +You should only implement these proxies when some preprocessing on the data is needed to make elements comparable. +In that case, defining these methods will get you a lot of behaviour for relatively little work. +These proxy functions should always return a simple object (either a bare vector or a data frame) that possesses the same properties as your class. +This permits efficient implementation of the vctrs internals because it allows dispatch to happen once in R, and then efficient computations can be written in C. ### Rational class -Let's explore these ideas by with the rational class we started on above. By default, `vec_proxy()` converts a record to a data frame, and the default comparison works column by column: +Let's explore these ideas by with the rational class we started on above. +By default, `vec_proxy()` converts a record to a data frame, and the default comparison works column by column: ```{r} x <- rational(c(1, 2, 1, 2), c(1, 1, 2, 2)) @@ -666,7 +743,8 @@ vec_proxy(x) x == rational(1, 1) ``` -This makes sense as a default but isn't correct here because `rational(1, 1)` represents the same number as `rational(2, 2)`, so they should be equal. We can fix that by implementing a `vec_proxy_equal()` method that divides `n` and `d` by their greatest common divisor: +This makes sense as a default but isn't correct here because `rational(1, 1)` represents the same number as `rational(2, 2)`, so they should be equal. +We can fix that by implementing a `vec_proxy_equal()` method that divides `n` and `d` by their greatest common divisor: ```{r} # Thanks to Matthew Lundberg: https://stackoverflow.com/a/21504113/16632 @@ -718,10 +796,11 @@ sort(x) (We could have used the same approach in `vec_proxy_equal()`, but when working with floating point numbers it's not necessarily true that `x == y` implies that `d * x == d * y`.) - ### Polynomial class -A related problem occurs if we build our vector on top of a list. The following code defines a polynomial class that represents polynomials (like `1 + 3x - 2x^2`) using a list of integer vectors (like `c(1, 3, -2)`). Note the use of `new_list_of()` in the constructor. +A related problem occurs if we build our vector on top of a list. +The following code defines a polynomial class that represents polynomials (like `1 + 3x - 2x^2`) using a list of integer vectors (like `c(1, 3, -2)`). +Note the use of `new_list_of()` in the constructor. ```{r} poly <- function(...) { @@ -775,17 +854,19 @@ p[[2]] The class implements the list interface: ```{r} -vec_is_list(p) +obj_is_list(p) ``` This is fine for the internal implementation of this class but it would be more appropriate if it behaved like an atomic vector rather than a list. - #### Make an atomic polynomial vector -An atomic vector is a vector like integer or character for which `[[` returns the same type. Unlike lists, you can't reach inside an atomic vector. +An atomic vector is a vector like integer or character for which `[[` returns the same type. +Unlike lists, you can't reach inside an atomic vector. -To make the polynomial class an atomic vector, we'll wrap the internal `list_of()` class within a record vector. Usually records are used because they can store several fields of data for each observation. Here we have only one, but we use the class anyway to inherit its atomicity. +To make the polynomial class an atomic vector, we'll wrap the internal `list_of()` class within a record vector. +Usually records are used because they can store several fields of data for each observation. +Here we have only one, but we use the class anyway to inherit its atomicity. ```{r} poly <- function(...) { @@ -798,17 +879,19 @@ format.vctrs_poly <- function(x, ...) { } ``` -The new `format()` method delegates to the one we wrote for the internal list. The vector looks just like before: +The new `format()` method delegates to the one we wrote for the internal list. +The vector looks just like before: ```{r} p <- poly(1, c(1, 0, 0, 0, 2), c(1, 0, 1)) p ``` -Making the class atomic means that `vec_is_list()` now returns `FALSE`. This prevents recursive algorithms that traverse lists from reaching too far inside the polynomial internals. +Making the class atomic means that `obj_is_list()` now returns `FALSE`. +This prevents recursive algorithms that traverse lists from reaching too far inside the polynomial internals. ```{r} -vec_is_list(p) +obj_is_list(p) ``` Most importantly, it prevents users from reaching into the internals with `[[`: @@ -817,7 +900,6 @@ Most importantly, it prevents users from reaching into the internals with `[[`: p[[2]] ``` - #### Implementing equality and comparison Equality works out of the box because we can tell if two integer vectors are equal: @@ -852,7 +934,8 @@ vec_proxy_compare.vctrs_poly <- function(x, ...) { p < p[2] ``` -Often, this is sufficient to also implement `sort()`. However, for lists, there is already a default `vec_proxy_order()` method that sorts by first occurrence: +Often, this is sufficient to also implement `sort()`. +However, for lists, there is already a default `vec_proxy_order()` method that sorts by first occurrence: ```{r} sort(p) @@ -869,16 +952,18 @@ vec_proxy_order.vctrs_poly <- function(x, ...) { sort(p) ``` - ## Arithmetic vctrs also provides two mathematical generics that allow you to define a broad swath of mathematical behaviour at once: -* `vec_math(fn, x, ...)` specifies the behaviour of mathematical functions like `abs()`, `sum()`, and `mean()`. (Note that `var()` and `sd()` can't be overridden, see `?vec_math()` for the complete list supported by `vec_math()`.) +- `vec_math(fn, x, ...)` specifies the behaviour of mathematical functions like `abs()`, `sum()`, and `mean()`. + (Note that `var()` and `sd()` can't be overridden, see `?vec_math()` for the complete list supported by `vec_math()`.) -* `vec_arith(op, x, y)` specifies the behaviour of the arithmetic operations like `+`, `-`, and `%%`. (See `?vec_arith()` for the complete list.) +- `vec_arith(op, x, y)` specifies the behaviour of the arithmetic operations like `+`, `-`, and `%%`. + (See `?vec_arith()` for the complete list.) -Both generics define the behaviour for multiple functions because `sum.vctrs_vctr(x)` calls `vec_math.vctrs_vctr("sum", x)`, and `x + y` calls `vec_math.x_class.y_class("+", x, y)`. They're accompanied by `vec_math_base()` and `vec_arith_base()` which make it easy to call the underlying base R functions. +Both generics define the behaviour for multiple functions because `sum.vctrs_vctr(x)` calls `vec_math.vctrs_vctr("sum", x)`, and `x + y` calls `vec_math.x_class.y_class("+", x, y)`. +They're accompanied by `vec_math_base()` and `vec_arith_base()` which make it easy to call the underlying base R functions. `vec_arith()` uses double dispatch and needs the following standard boilerplate: @@ -891,11 +976,15 @@ vec_arith.MYCLASS.default <- function(op, x, y, ...) { } ``` -Correctly exporting `vec_arith()` methods from a package is currently a little awkward. See the instructions in the Arithmetic section of the "Implementing a vctrs S3 class in a package" section below. +Correctly exporting `vec_arith()` methods from a package is currently a little awkward. +See the instructions in the Arithmetic section of the "Implementing a vctrs S3 class in a package" section below. ### Cached sum class -I showed an example of `vec_math()` to define `sum()` and `mean()` methods for `cached_sum`. Now let's talk about exactly how it works. Most `vec_math()` functions will have a similar form. You use a switch statement to handle the methods that you care about and fall back to `vec_math_base()` for those that you don't care about. +I showed an example of `vec_math()` to define `sum()` and `mean()` methods for `cached_sum`. +Now let's talk about exactly how it works. +Most `vec_math()` functions will have a similar form. +You use a switch statement to handle the methods that you care about and fall back to `vec_math_base()` for those that you don't care about. ```{r} vec_math.vctrs_cached_sum <- function(.fn, .x, ...) { @@ -907,7 +996,6 @@ vec_math.vctrs_cached_sum <- function(.fn, .x, ...) { } ``` - ### Meter class To explore the infix arithmetic operators exposed by `vec_arith()` I'll create a new class that represents a measurement in `meter`s: @@ -946,11 +1034,14 @@ meter(10) + meter(1) meter(10) * 3 ``` -To allow these infix functions to work, we'll need to provide `vec_arith()` generic. But before we do that, let's think about what combinations of inputs we should support: +To allow these infix functions to work, we'll need to provide `vec_arith()` generic. +But before we do that, let's think about what combinations of inputs we should support: -* It makes sense to add and subtract meters: that yields another meter. We can divide a meter by another meter (yielding a unitless number), but we can't multiply meters (because that would yield an area). +- It makes sense to add and subtract meters: that yields another meter. + We can divide a meter by another meter (yielding a unitless number), but we can't multiply meters (because that would yield an area). -* For a combination of meter and number multiplication and division by a number are acceptable. Addition and subtraction don't make much sense as we, strictly speaking, are dealing with objects of different nature. +- For a combination of meter and number multiplication and division by a number are acceptable. + Addition and subtraction don't make much sense as we, strictly speaking, are dealing with objects of different nature. `vec_arith()` is another function that uses double dispatch, so as usual we start with a template. @@ -963,7 +1054,8 @@ vec_arith.vctrs_meter.default <- function(op, x, y, ...) { } ``` -Then write the method for two meter objects. We use a switch statement to cover the cases we care about and `stop_incompatible_op()` to throw an informative error message for everything else. +Then write the method for two meter objects. +We use a switch statement to cover the cases we care about and `stop_incompatible_op()` to throw an informative error message for everything else. ```{r, error = TRUE} vec_arith.vctrs_meter.vctrs_meter <- function(op, x, y, ...) { @@ -982,7 +1074,9 @@ meter(10) / meter(1) meter(10) * meter(1) ``` -Next we write the pair of methods for arithmetic with a meter and a number. These are almost identical, but while `meter(10) / 2` makes sense, `2 / meter(10)` does not (and neither do addition and subtraction). To support both doubles and integers as operands, we dispatch over `numeric` here instead of `double`. +Next we write the pair of methods for arithmetic with a meter and a number. +These are almost identical, but while `meter(10) / 2` makes sense, `2 / meter(10)` does not (and neither do addition and subtraction). +To support both doubles and integers as operands, we dispatch over `numeric` here instead of `double`. ```{r, error = TRUE} vec_arith.vctrs_meter.numeric <- function(op, x, y, ...) { @@ -1023,40 +1117,44 @@ vec_arith.vctrs_meter.MISSING <- function(op, x, y, ...) { +meter(1) ``` - ## Implementing a vctrs S3 class in a package Defining S3 methods interactively is fine for iteration and exploration, but if your class lives in a package, you need to do a few more things: -* Register the S3 methods by listing them in the `NAMESPACE` file. - -* Create documentation around your methods, for the sake of your user and to satisfy `R CMD check`. +- Register the S3 methods by listing them in the `NAMESPACE` file. -Let's assume that the `percent` class is implemented in the pizza package in the file `R/percent.R`. Here we walk through the major sections of this hypothetical file. You've seen all of this code before, but now it's augmented by the roxygen2 directives that produce the correct `NAMESPACE` entries and help topics. +- Create documentation around your methods, for the sake of your user and to satisfy `R CMD check`. +Let's assume that the `percent` class is implemented in the pizza package in the file `R/percent.R`. +Here we walk through the major sections of this hypothetical file. +You've seen all of this code before, but now it's augmented by the roxygen2 directives that produce the correct `NAMESPACE` entries and help topics. ### Getting started -First, the pizza package needs to include vctrs in the `Imports` section of its `DESCRIPTION` (perhaps by calling `usethis::use_package("vctrs")`. While vctrs is under very active development, it probably makes sense to state a minimum version. +First, the pizza package needs to include vctrs in the `Imports` section of its `DESCRIPTION` (perhaps by calling `usethis::use_package("vctrs")`. +While vctrs is under very active development, it probably makes sense to state a minimum version. -``` -Imports: - a_package, - another_package, - ... - vctrs (>= x.y.z), - ... -``` + Imports: + a_package, + another_package, + ... + vctrs (>= x.y.z), + ... -Then we make all vctrs functions available within the pizza package by including the directive `#' @import vctrs` somewhere. Usually, it's not good practice to `@import` the entire namespace of a package, but vctrs is deliberately designed with this use case in mind. +Then we make all vctrs functions available within the pizza package by including the directive `#' @import vctrs` somewhere. +Usually, it's not good practice to `@import` the entire namespace of a package, but vctrs is deliberately designed with this use case in mind. -Where should we put `#' @import vctrs`? There are two natural locations: +Where should we put `#' @import vctrs`? +There are two natural locations: -* With package-level docs in `R/pizza-doc.R`. You can use `usethis::use_package_doc()` to initiate this package-level documentation. +- With package-level docs in `R/pizza-doc.R`. + You can use `usethis::use_package_doc()` to initiate this package-level documentation. -* In `R/percent.R`. This makes the most sense when the vctrs S3 class is a modest and self-contained part of the overall package. +- In `R/percent.R`. This makes the most sense when the vctrs S3 class is a modest and self-contained part of the overall package. -We also must use one of these locations to dump some internal documentation that's needed to avoid `R CMD check` complaints. We don't expect any human to ever read this documentation. Here's how this dummy documentation should look, combined with the `#' @import vctrs` directive described above. +We also must use one of these locations to dump some internal documentation that's needed to avoid `R CMD check` complaints. +We don't expect any human to ever read this documentation. +Here's how this dummy documentation should look, combined with the `#' @import vctrs` directive described above. ```{r eval = FALSE} #' Internal vctrs methods @@ -1073,7 +1171,6 @@ Remember to call `devtools::document()` regularly, as you develop, to regenerate From this point on, the code shown is expected to appear in `R/percent.R`. - ### Low-level and user-friendly constructors Next we add our constructor: @@ -1087,7 +1184,8 @@ new_percent <- function(x = double()) { } ``` -Note that the name of the package must be included in the class name (`pizza_percent`), but it does not need to be included in the constructor name. You do not need to export the constructor, unless you want people to extend your class. +Note that the name of the package must be included in the class name (`pizza_percent`), but it does not need to be included in the constructor name. +You do not need to export the constructor, unless you want people to extend your class. We can also add a call to `setOldClass()` for compatibility with S4: @@ -1096,7 +1194,8 @@ We can also add a call to `setOldClass()` for compatibility with S4: methods::setOldClass(c("pizza_percent", "vctrs_vctr")) ``` -Because we've used a function from the methods package, you'll also need to add methods to `Imports`, with (e.g.) `usethis::use_package("methods")`. This is a "free" dependency because methods is bundled with every R install. +Because we've used a function from the methods package, you'll also need to add methods to `Imports`, with (e.g.) `usethis::use_package("methods")`. +This is a "free" dependency because methods is bundled with every R install. Next we implement, export, and document a user-friendly helper: `percent()`. @@ -1119,10 +1218,10 @@ percent <- function(x = double()) { (Again note that the package name will appear in the class, but does not need to occur in the function, because we can already do `pizza::percent()`; it would be redundant to have `pizza::pizza_percent()`.) - ### Other helpers -It's a good idea to provide a function that tests if an object is of this class. If you do so, it makes sense to document it with the user-friendly constructor `percent()`: +It's a good idea to provide a function that tests if an object is of this class. +If you do so, it makes sense to document it with the user-friendly constructor `percent()`: ```{r} #' @export @@ -1140,7 +1239,8 @@ You'll also need to update the `percent()` documentation to reflect that `x` now #' * For `is_percent()`: An object to test. ``` -Next we provide the key methods to make printing work. These are S3 methods, so they don't need to be documented, but they do need to be exported. +Next we provide the key methods to make printing work. +These are S3 methods, so they don't need to be documented, but they do need to be exported. ```{r eval = FALSE} #' @export @@ -1157,7 +1257,6 @@ vec_ptype_abbr.pizza_percent <- function(x, ...) { } ``` - Finally, we implement methods for `vec_ptype2()` and `vec_cast()`. ```{r, eval = FALSE} @@ -1176,7 +1275,9 @@ vec_cast.double.pizza_percent <- function(x, to, ...) vec_data(x) ### Arithmetic -Writing double dispatch methods for `vec_arith()` is currently more awkward than writing them for `vec_ptype2()` or `vec_cast()`. We plan to improve this in the future. For now, you can use the following instructions. +Writing double dispatch methods for `vec_arith()` is currently more awkward than writing them for `vec_ptype2()` or `vec_cast()`. +We plan to improve this in the future. +For now, you can use the following instructions. If you define a new type and want to write `vec_arith()` methods for it, you'll need to provide a new single dispatch S3 generic for it of the following form: @@ -1188,7 +1289,8 @@ vec_arith.my_type <- function(op, x, y, ...) { } ``` -Note that this actually functions as both an S3 method for `vec_arith()` and an S3 generic called `vec_arith.my_type()` that dispatches off `y`. roxygen2 only recognizes it as an S3 generic, so you have to register the S3 method part of this with an explicit `@method` call. +Note that this actually functions as both an S3 method for `vec_arith()` and an S3 generic called `vec_arith.my_type()` that dispatches off `y`. +roxygen2 only recognizes it as an S3 generic, so you have to register the S3 method part of this with an explicit `@method` call. After that, you can define double dispatch methods, but you still need an explicit `@method` tag to ensure it is registered with the correct generic: @@ -1212,31 +1314,39 @@ vec_arith.integer.my_type <- function(op, x, y, ...) { } ``` -vctrs provides the hybrid S3 generics/methods for most of the base R types, like `vec_arith.integer()`. If you don't fully import vctrs with `@import vctrs`, then you will need to explicitly import the generic you are registering double dispatch methods for with `@importFrom vctrs vec_arith.integer`. +vctrs provides the hybrid S3 generics/methods for most of the base R types, like `vec_arith.integer()`. +If you don't fully import vctrs with `@import vctrs`, then you will need to explicitly import the generic you are registering double dispatch methods for with `@importFrom vctrs vec_arith.integer`. ### Testing -It's good practice to test your new class. Specific recommendations: +It's good practice to test your new class. +Specific recommendations: -* `R/percent.R` is the type of file where you really do want 100% test coverage. You can use `devtools::test_coverage_file()` to check this. +- `R/percent.R` is the type of file where you really do want 100% test coverage. + You can use `devtools::test_coverage_file()` to check this. -* Make sure to test behaviour with zero-length inputs and missing values. +- Make sure to test behaviour with zero-length inputs and missing values. -* Use `testthat::verify_output()` to test your format method. Customised printing is often a primary motivation for creating your own S3 class in the first place, so this will alert you to unexpected changes in your printed output. Read more about `verify_output()` in the [testthat v2.3.0 blog post](https://www.tidyverse.org/blog/2019/11/testthat-2-3-0/); it's an example of a so-called [golden test](https://ro-che.info/articles/2017-12-04-golden-tests). +- Use `testthat::verify_output()` to test your format method. + Customised printing is often a primary motivation for creating your own S3 class in the first place, so this will alert you to unexpected changes in your printed output. + Read more about `verify_output()` in the [testthat v2.3.0 blog post](https://www.tidyverse.org/blog/2019/11/testthat-2-3-0/); it's an example of a so-called [golden test](https://ro-che.info/articles/2017-12-04-golden-tests). -* Check for method symmetry; use `expect_s3_class()`, probably with `exact = TRUE`, to ensure that `vec_c(x, y)` and `vec_c(y, x)` return the same type of output for the important `x`s and `y`s in your domain. +- Check for method symmetry; use `expect_s3_class()`, probably with `exact = TRUE`, to ensure that `vec_c(x, y)` and `vec_c(y, x)` return the same type of output for the important `x`s and `y`s in your domain. -* Use `testthat::expect_error()` to check that inputs that can't be combined fail with an error. Here, you should be generally checking the class of the error, not its message. Relevant classes include `vctrs_error_assert_ptype`, `vctrs_error_assert_size`, and `vctrs_error_incompatible_type`. +- Use `testthat::expect_error()` to check that inputs that can't be combined fail with an error. + Here, you should be generally checking the class of the error, not its message. + Relevant classes include `vctrs_error_assert_ptype`, `vctrs_error_assert_size`, and `vctrs_error_incompatible_type`. ```{r, eval = FALSE} expect_error(vec_c(1, "a"), class = "vctrs_error_incompatible_type") ``` -If your tests pass when run by `devtools::test()`, but fail when run in `R CMD check`, it is very likely to reflect a problem with S3 method registration. Carefully check your roxygen2 comments and the generated `NAMESPACE`. - +If your tests pass when run by `devtools::test()`, but fail when run in `R CMD check`, it is very likely to reflect a problem with S3 method registration. +Carefully check your roxygen2 comments and the generated `NAMESPACE`. ### Existing classes -Before you build your own class, you might want to consider using, or subclassing existing classes. You can check [awesome-vctrs](https://github.com/krlmlr/awesome-vctrs) for a curated list of R vector classes, some of which are built with vctrs. +Before you build your own class, you might want to consider using, or subclassing existing classes. +You can check [awesome-vctrs](https://github.com/krlmlr/awesome-vctrs) for a curated list of R vector classes, some of which are built with vctrs. If you've built or extended a class, consider adding it to that list so other people can use it. From e6544423d335e52b655ddb24332e92c6bf47bc98 Mon Sep 17 00:00:00 2001 From: DavisVaughan Date: Mon, 6 Mar 2023 10:03:07 -0500 Subject: [PATCH 243/312] Require R >=3.5.0 --- DESCRIPTION | 2 +- NEWS.md | 4 ++++ 2 files changed, 5 insertions(+), 1 deletion(-) diff --git a/DESCRIPTION b/DESCRIPTION index 9cf251bc5..1155153a1 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -27,7 +27,7 @@ License: MIT + file LICENSE URL: https://vctrs.r-lib.org/ BugReports: https://github.com/r-lib/vctrs/issues Depends: - R (>= 3.3) + R (>= 3.5.0) Imports: cli (>= 3.4.0), glue, diff --git a/NEWS.md b/NEWS.md index 020f23076..cb4be0452 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,5 +1,9 @@ # vctrs (development version) +* R >=3.5.0 is now explicitly required. This is in line with the tidyverse + policy of supporting the [5 most recent versions of + R](https://www.tidyverse.org/blog/2019/04/r-version-support/). + * `vec_is_list()` and `vec_check_list()` have been renamed to `obj_is_list()` and `obj_check_list()`, in line with the new `obj_is_vector()` helper. The old functions have been silently deprecated, but an official deprecation From 530363d45eedb99afdcd2727f19a220a6868d3df Mon Sep 17 00:00:00 2001 From: DavisVaughan Date: Mon, 6 Mar 2023 10:08:01 -0500 Subject: [PATCH 244/312] Add `release_extra_revdeps()`. Closes #1769. --- R/vctrs-package.R | 6 ++++++ 1 file changed, 6 insertions(+) diff --git a/R/vctrs-package.R b/R/vctrs-package.R index 98c1db53d..c10c20ac4 100644 --- a/R/vctrs-package.R +++ b/R/vctrs-package.R @@ -10,3 +10,9 @@ #' @import rlang #' @useDynLib vctrs, .registration = TRUE "_PACKAGE" + +release_extra_revdeps <- function() { + # Extra revdeps to run before release. + # Recognized by `usethis::use_release_issue()`. + c("dplyr", "tidyr", "purrr") +} From 1dfcc3e1affeae2f3518d7ef17579cb3ae34a174 Mon Sep 17 00:00:00 2001 From: Davis Vaughan Date: Mon, 6 Mar 2023 11:41:42 -0500 Subject: [PATCH 245/312] Update style in `slice-chop.c` (#1807) --- R/slice-chop.R | 4 +- src/decl/slice-chop-decl.h | 7 + src/init.c | 8 +- src/slice-chop.c | 310 ++++++++++++++++++++----------------- src/vctrs.h | 2 +- 5 files changed, 179 insertions(+), 152 deletions(-) create mode 100644 src/decl/slice-chop-decl.h diff --git a/R/slice-chop.R b/R/slice-chop.R index d9be9b2e3..f9c1ca198 100644 --- a/R/slice-chop.R +++ b/R/slice-chop.R @@ -90,7 +90,7 @@ #' ave(breaks, wool, FUN = mean) #' ) vec_chop <- function(x, indices = NULL) { - .Call(vctrs_chop, x, indices) + .Call(ffi_vec_chop, x, indices) } #' @rdname vec_chop @@ -110,5 +110,5 @@ list_unchop <- function(x, # Exposed for testing (`starts` is 0-based) vec_chop_seq <- function(x, starts, sizes, increasings = TRUE) { args <- vec_recycle_common(starts, sizes, increasings) - .Call(vctrs_chop_seq, x, args[[1]], args[[2]], args[[3]]) + .Call(ffi_vec_chop_seq, x, args[[1]], args[[2]], args[[3]]) } diff --git a/src/decl/slice-chop-decl.h b/src/decl/slice-chop-decl.h new file mode 100644 index 000000000..1647263c0 --- /dev/null +++ b/src/decl/slice-chop-decl.h @@ -0,0 +1,7 @@ +static r_obj* vec_chop_base(r_obj* x, r_obj* indices, struct vctrs_chop_info info); + +static r_obj* chop(r_obj* x, r_obj* indices, struct vctrs_chop_info info); +static r_obj* chop_shaped(r_obj* x, r_obj* indices, struct vctrs_chop_info info); +static r_obj* chop_df(r_obj* x, r_obj* indices, struct vctrs_chop_info info); +static r_obj* chop_fallback(r_obj* x, r_obj* indices, struct vctrs_chop_info info); +static r_obj* chop_fallback_shaped(r_obj* x, r_obj* indices, struct vctrs_chop_info info); diff --git a/src/init.c b/src/init.c index ae454f2a2..51169115a 100644 --- a/src/init.c +++ b/src/init.c @@ -50,9 +50,9 @@ extern r_obj* ffi_cast(r_obj*, r_obj*, r_obj*); extern r_obj* ffi_as_location(r_obj*, r_obj*, r_obj*, r_obj*, r_obj*, r_obj*, r_obj*, r_obj*); extern r_obj* ffi_slice(r_obj*, r_obj*, r_obj*); extern r_obj* ffi_init(r_obj*, r_obj*, r_obj*); -extern SEXP vctrs_chop(SEXP, SEXP); +extern r_obj* ffi_vec_chop(r_obj*, r_obj*); extern r_obj* ffi_list_unchop(r_obj*, r_obj*, r_obj*, r_obj*, r_obj*, r_obj*); -extern SEXP vctrs_chop_seq(SEXP, SEXP, SEXP, SEXP); +extern r_obj* ffi_vec_chop_seq(r_obj*, r_obj*, r_obj*, r_obj*); extern r_obj* ffi_slice_seq(r_obj*, r_obj*, r_obj*, r_obj*); extern r_obj* ffi_slice_rep(r_obj*, r_obj*, r_obj*); extern r_obj* ffi_vec_restore(r_obj*, r_obj*); @@ -229,9 +229,9 @@ static const R_CallMethodDef CallEntries[] = { {"ffi_as_location", (DL_FUNC) &ffi_as_location, 8}, {"ffi_slice", (DL_FUNC) &ffi_slice, 3}, {"ffi_init", (DL_FUNC) &ffi_init, 3}, - {"vctrs_chop", (DL_FUNC) &vctrs_chop, 2}, + {"ffi_vec_chop", (DL_FUNC) &ffi_vec_chop, 2}, {"ffi_list_unchop", (DL_FUNC) &ffi_list_unchop, 6}, - {"vctrs_chop_seq", (DL_FUNC) &vctrs_chop_seq, 4}, + {"ffi_vec_chop_seq", (DL_FUNC) &ffi_vec_chop_seq, 4}, {"ffi_slice_seq", (DL_FUNC) &ffi_slice_seq, 4}, {"ffi_slice_rep", (DL_FUNC) &ffi_slice_rep, 3}, {"ffi_vec_restore", (DL_FUNC) &ffi_vec_restore, 2}, diff --git a/src/slice-chop.c b/src/slice-chop.c index d924b3925..9f105b8a1 100644 --- a/src/slice-chop.c +++ b/src/slice-chop.c @@ -2,6 +2,7 @@ #include "type-data-frame.h" /* + * @member shelter The shelter to protect the entire chop info. * @member proxy_info The result of `vec_proxy_info(x)`. * @member index The current index value. If `indices` are provided, this is * the i-th element of indices. For the default of `indices = NULL`, this @@ -14,29 +15,32 @@ * @member out The list container for the result. */ struct vctrs_chop_info { + r_obj* shelter; + struct vctrs_proxy_info proxy_info; - SEXP index; + + r_obj* index; int* p_index; bool has_indices; - R_len_t out_size; - SEXP out; + + r_ssize out_size; + r_obj* out; }; -#define PROTECT_CHOP_INFO(info, n) do { \ - KEEP((info)->proxy_info.shelter); \ - KEEP((info)->index); \ - KEEP((info)->out); \ - *n += 3; \ - } while (0) \ +#include "decl/slice-chop-decl.h" + +// ----------------------------------------------------------------------------- static -struct vctrs_chop_info init_chop_info(r_obj* x, r_obj* indices) { +struct vctrs_chop_info new_chop_info(r_obj* x, r_obj* indices) { struct vctrs_chop_info info; + info.shelter = KEEP(r_alloc_list(3)); info.proxy_info = vec_proxy_info(x); - KEEP(info.proxy_info.shelter); + r_list_poke(info.shelter, 0, info.proxy_info.shelter); - info.index = KEEP(r_int(0)); + info.index = r_int(0); + r_list_poke(info.shelter, 1, info.index); info.p_index = r_int_begin(info.index); if (indices == r_null) { @@ -48,84 +52,73 @@ struct vctrs_chop_info init_chop_info(r_obj* x, r_obj* indices) { } info.out = r_alloc_list(info.out_size); + r_list_poke(info.shelter, 2, info.out); - FREE(2); + FREE(1); return info; } // ----------------------------------------------------------------------------- -static SEXP chop(SEXP x, SEXP indices, struct vctrs_chop_info info); -static SEXP chop_shaped(SEXP x, SEXP indices, struct vctrs_chop_info info); -static SEXP chop_df(SEXP x, SEXP indices, struct vctrs_chop_info info); -static SEXP chop_fallback(SEXP x, SEXP indices, struct vctrs_chop_info info); -static SEXP chop_fallback_shaped(SEXP x, SEXP indices, struct vctrs_chop_info info); - -static SEXP vec_chop_base(SEXP x, SEXP indices, struct vctrs_chop_info info); - -// [[ register() ]] -SEXP vctrs_chop_seq(SEXP x, SEXP starts, SEXP sizes, SEXP increasings) { - int* p_starts = INTEGER(starts); - int* p_sizes = INTEGER(sizes); - int* p_increasings = LOGICAL(increasings); +r_obj* ffi_vec_chop_seq(r_obj* x, r_obj* starts, r_obj* sizes, r_obj* increasings) { + int* v_starts = r_int_begin(starts); + int* v_sizes = r_int_begin(sizes); + int* v_increasings = r_lgl_begin(increasings); - int n = Rf_length(starts); + const r_ssize n = r_length(starts); - SEXP indices = PROTECT(Rf_allocVector(VECSXP, n)); + r_obj* indices = KEEP(r_alloc_list(n)); - for (int i = 0; i < n; ++i) { - SEXP index = compact_seq(p_starts[i], p_sizes[i], p_increasings[i]); - SET_VECTOR_ELT(indices, i, index); + for (r_ssize i = 0; i < n; ++i) { + r_obj* index = compact_seq(v_starts[i], v_sizes[i], v_increasings[i]); + r_list_poke(indices, i, index); } - SEXP out = PROTECT(vec_chop(x, indices)); + r_obj* out = KEEP(vec_chop(x, indices)); - UNPROTECT(2); + FREE(2); return out; } -// [[ register() ]] -SEXP vctrs_chop(SEXP x, SEXP indices) { - R_len_t n = vec_size(x); - SEXP names = PROTECT(vec_names(x)); +r_obj* ffi_vec_chop(r_obj* x, r_obj* indices) { + const r_ssize n = vec_size(x); + r_obj* names = KEEP(vec_names(x)); - indices = PROTECT(vec_as_indices(indices, n, names)); + indices = KEEP(vec_as_indices(indices, n, names)); - SEXP out = PROTECT(vec_chop(x, indices)); + r_obj* out = KEEP(vec_chop(x, indices)); - UNPROTECT(3); + FREE(3); return out; } // [[ include("vctrs.h") ]] -SEXP vec_chop(SEXP x, SEXP indices) { - int nprot = 0; - - struct vctrs_chop_info info = init_chop_info(x, indices); - PROTECT_CHOP_INFO(&info, &nprot); +r_obj* vec_chop(r_obj* x, r_obj* indices) { + struct vctrs_chop_info info = new_chop_info(x, indices); + KEEP(info.shelter); - SEXP out = PROTECT_N(vec_chop_base(x, indices, info), &nprot); + r_obj* out = vec_chop_base(x, indices, info); - UNPROTECT(nprot); + FREE(1); return out; } -static SEXP vec_chop_base(SEXP x, SEXP indices, struct vctrs_chop_info info) { +static r_obj* vec_chop_base(r_obj* x, r_obj* indices, struct vctrs_chop_info info) { struct vctrs_proxy_info proxy_info = info.proxy_info; // Fallback to `[` if the class doesn't implement a proxy. This is // to be maximally compatible with existing classes. if (vec_requires_fallback(x, proxy_info)) { if (proxy_info.type == VCTRS_TYPE_scalar) { - Rf_errorcall(R_NilValue, "Can't slice a scalar"); + r_abort_lazy_call(r_lazy_null, "Can't slice a scalar"); } if (info.has_indices) { - for (int i = 0; i < info.out_size; ++i) { - SEXP index = VECTOR_ELT(indices, i); + for (r_ssize i = 0; i < info.out_size; ++i) { + r_obj* index = r_list_get(indices, i); if (is_compact(index)) { - SET_VECTOR_ELT(indices, i, compact_materialize(index)); + r_list_poke(indices, i, compact_materialize(index)); } } } @@ -160,13 +153,18 @@ static SEXP vec_chop_base(SEXP x, SEXP indices, struct vctrs_chop_info info) { } } -static SEXP chop(SEXP x, SEXP indices, struct vctrs_chop_info info) { - SEXP proxy = info.proxy_info.proxy; - SEXP names = PROTECT(Rf_getAttrib(proxy, R_NamesSymbol)); +static r_obj* chop(r_obj* x, r_obj* indices, struct vctrs_chop_info info) { + r_obj* proxy = info.proxy_info.proxy; + r_obj* names = KEEP(r_names(proxy)); + + r_obj* const* v_indices = NULL; + if (info.has_indices) { + v_indices = r_list_cbegin(indices); + } - for (R_len_t i = 0; i < info.out_size; ++i) { + for (r_ssize i = 0; i < info.out_size; ++i) { if (info.has_indices) { - info.index = VECTOR_ELT(indices, i); + info.index = v_indices[i]; } else { ++(*info.p_index); } @@ -176,50 +174,57 @@ static SEXP chop(SEXP x, SEXP indices, struct vctrs_chop_info info) { // This is a heuristic and we should also be on the lookout for cases where // we chop to create a small amount of large ALTREP objects that are // quickly discarded (#1450). - SEXP elt = PROTECT(vec_slice_base( + r_obj* elt = KEEP(vec_slice_base( info.proxy_info.type, proxy, info.index, VCTRS_MATERIALIZE_true )); - if (names != R_NilValue) { - SEXP elt_names = PROTECT(slice_names(names, info.index)); + if (names != r_null) { + r_obj* elt_names = slice_names(names, info.index); r_attrib_poke_names(elt, elt_names); - UNPROTECT(1); } elt = vec_restore(elt, x, vec_owned(elt)); + r_list_poke(info.out, i, elt); - SET_VECTOR_ELT(info.out, i, elt); - UNPROTECT(1); + FREE(1); } - UNPROTECT(1); + FREE(1); return info.out; } -static SEXP chop_df(SEXP x, SEXP indices, struct vctrs_chop_info info) { - SEXP proxy = info.proxy_info.proxy; +static r_obj* chop_df(r_obj* x, r_obj* indices, struct vctrs_chop_info info) { + r_obj* proxy = info.proxy_info.proxy; + r_obj* const* v_proxy = r_list_cbegin(proxy); - int n_cols = Rf_length(proxy); + const r_ssize n_cols = r_length(proxy); - SEXP col_names = PROTECT(Rf_getAttrib(proxy, R_NamesSymbol)); - SEXP row_names = PROTECT(df_rownames(proxy)); + r_obj* col_names = KEEP(r_names(proxy)); + r_obj* row_names = KEEP(df_rownames(proxy)); - bool has_row_names = TYPEOF(row_names) == STRSXP; + bool has_row_names = r_typeof(row_names) == R_TYPE_character; + + r_obj* const* v_out = r_list_cbegin(info.out); + + r_obj* const* v_indices = NULL; + if (info.has_indices) { + v_indices = r_list_cbegin(indices); + } // Pre-load the `out` container with empty bare data frames - for (R_len_t i = 0; i < info.out_size; ++i) { - SEXP elt = Rf_allocVector(VECSXP, n_cols); - SET_VECTOR_ELT(info.out, i, elt); + for (r_ssize i = 0; i < info.out_size; ++i) { + r_obj* elt = r_alloc_list(n_cols); + r_list_poke(info.out, i, elt); - Rf_setAttrib(elt, R_NamesSymbol, col_names); + r_attrib_poke_names(elt, col_names); r_ssize size = -1; if (info.has_indices) { - info.index = VECTOR_ELT(indices, i); + info.index = v_indices[i]; size = vec_subscript_size(info.index); } else { ++(*info.p_index); @@ -229,136 +234,150 @@ static SEXP chop_df(SEXP x, SEXP indices, struct vctrs_chop_info info) { init_data_frame(elt, size); if (has_row_names) { - SEXP elt_row_names = slice_rownames(row_names, info.index); - Rf_setAttrib(elt, R_RowNamesSymbol, elt_row_names); + r_obj* elt_row_names = slice_rownames(row_names, info.index); + r_attrib_poke(elt, R_RowNamesSymbol, elt_row_names); } } - // Split each column according to the indices, and then assign the results + // Chop each column according to the indices, and then assign the results // into the appropriate data frame column in the `out` list - for (int i = 0; i < n_cols; ++i) { - SEXP col = VECTOR_ELT(proxy, i); - SEXP split = PROTECT(vec_chop(col, indices)); - - for (int j = 0; j < info.out_size; ++j) { - SEXP elt = VECTOR_ELT(info.out, j); - SET_VECTOR_ELT(elt, i, VECTOR_ELT(split, j)); + for (r_ssize i = 0; i < n_cols; ++i) { + r_obj* col = v_proxy[i]; + r_obj* col_chopped = KEEP(vec_chop(col, indices)); + r_obj* const* v_col_chopped = r_list_cbegin(col_chopped); + + for (r_ssize j = 0; j < info.out_size; ++j) { + r_obj* elt = v_out[j]; + r_list_poke(elt, i, v_col_chopped[j]); } - UNPROTECT(1); + FREE(1); } // Restore each data frame - for (int i = 0; i < info.out_size; ++i) { - SEXP elt = VECTOR_ELT(info.out, i); + for (r_ssize i = 0; i < info.out_size; ++i) { + r_obj* elt = v_out[i]; elt = vec_restore(elt, x, vec_owned(elt)); - SET_VECTOR_ELT(info.out, i, elt); + r_list_poke(info.out, i, elt); } - UNPROTECT(2); + FREE(2); return info.out; } -static SEXP chop_shaped(SEXP x, SEXP indices, struct vctrs_chop_info info) { - SEXP proxy = info.proxy_info.proxy; - SEXP dim_names = PROTECT(Rf_getAttrib(proxy, R_DimNamesSymbol)); +static r_obj* chop_shaped(r_obj* x, r_obj* indices, struct vctrs_chop_info info) { + r_obj* proxy = info.proxy_info.proxy; + r_obj* dim_names = KEEP(r_dim_names(proxy)); + + r_obj* row_names = r_null; + if (dim_names != r_null) { + row_names = r_list_get(dim_names, 0); + } - SEXP row_names = R_NilValue; - if (dim_names != R_NilValue) { - row_names = VECTOR_ELT(dim_names, 0); + r_obj* const* v_indices = NULL; + if (info.has_indices) { + v_indices = r_list_cbegin(indices); } - for (R_len_t i = 0; i < info.out_size; ++i) { + for (r_ssize i = 0; i < info.out_size; ++i) { if (info.has_indices) { - info.index = VECTOR_ELT(indices, i); + info.index = v_indices[i]; } else { ++(*info.p_index); } - SEXP elt = PROTECT(vec_slice_shaped(info.proxy_info.type, proxy, info.index)); - - if (dim_names != R_NilValue) { - if (row_names != R_NilValue) { - SEXP new_dim_names = PROTECT(Rf_shallow_duplicate(dim_names)); - SEXP new_row_names = PROTECT(slice_names(row_names, info.index)); - - SET_VECTOR_ELT(new_dim_names, 0, new_row_names); - Rf_setAttrib(elt, R_DimNamesSymbol, new_dim_names); - UNPROTECT(2); + r_obj* elt = KEEP(vec_slice_shaped(info.proxy_info.type, proxy, info.index)); + + if (dim_names != r_null) { + if (row_names != r_null) { + // Required to slice row names to the right size before poking to avoid + // erroring on the dimnames length check in `Rf_setAttrib()` + r_obj* new_dim_names = KEEP(r_clone(dim_names)); + r_obj* new_row_names = slice_names(row_names, info.index); + r_list_poke(new_dim_names, 0, new_row_names); + r_attrib_poke_dim_names(elt, new_dim_names); + FREE(1); } else { - Rf_setAttrib(elt, R_DimNamesSymbol, dim_names); + r_attrib_poke_dim_names(elt, dim_names); } } elt = vec_restore(elt, x, vec_owned(elt)); + r_list_poke(info.out, i, elt); - SET_VECTOR_ELT(info.out, i, elt); - UNPROTECT(1); + FREE(1); } - UNPROTECT(1); + FREE(1); return info.out; } -static SEXP chop_fallback(SEXP x, SEXP indices, struct vctrs_chop_info info) { +static r_obj* chop_fallback(r_obj* x, r_obj* indices, struct vctrs_chop_info info) { // Evaluate in a child of the global environment to allow dispatch // to custom functions. We define `[` to point to its base // definition to ensure consistent look-up. This is the same logic // as in `vctrs_dispatch_n()`, reimplemented here to allow repeated // evaluations in a loop. - SEXP env = PROTECT(r_new_environment(R_GlobalEnv)); - Rf_defineVar(syms_x, x, env); - Rf_defineVar(syms_i, info.index, env); + r_obj* env = KEEP(r_new_environment(r_envs.global)); + r_env_poke(env, syms_x, x); + r_env_poke(env, syms_i, info.index); // Construct call with symbols, not values, for performance. // TODO - Remove once bit64 is updated on CRAN. Special casing integer64 // objects to ensure correct slicing with `NA_integer_`. - SEXP call; + r_obj* call; if (is_integer64(x)) { - call = PROTECT(Rf_lang3(syms.vec_slice_dispatch_integer64, syms_x, syms_i)); - Rf_defineVar(syms.vec_slice_dispatch_integer64, fns.vec_slice_dispatch_integer64, env); + call = KEEP(r_call3(syms.vec_slice_dispatch_integer64, syms_x, syms_i)); + r_env_poke(env, syms.vec_slice_dispatch_integer64, fns.vec_slice_dispatch_integer64); } else { - call = PROTECT(Rf_lang3(syms_bracket, syms_x, syms_i)); - Rf_defineVar(syms_bracket, fns_bracket, env); + call = KEEP(r_call3(syms_bracket, syms_x, syms_i)); + r_env_poke(env, syms_bracket, fns_bracket); } - for (R_len_t i = 0; i < info.out_size; ++i) { - if (info.has_indices) { - info.index = VECTOR_ELT(indices, i); + r_obj* const* v_indices = NULL; + if (info.has_indices) { + v_indices = r_list_cbegin(indices); + } + for (r_ssize i = 0; i < info.out_size; ++i) { + if (info.has_indices) { + info.index = v_indices[i]; // Update `i` binding with the new index value - Rf_defineVar(syms_i, info.index, env); + r_env_poke(env, syms_i, info.index); } else { ++(*info.p_index); } - SEXP elt = PROTECT(Rf_eval(call, env)); + r_obj* elt = KEEP(r_eval(call, env)); if (!vec_is_restored(elt, x)) { elt = vec_restore(elt, x, vec_owned(elt)); } - SET_VECTOR_ELT(info.out, i, elt); - UNPROTECT(1); + r_list_poke(info.out, i, elt); + FREE(1); } - UNPROTECT(2); + FREE(2); return info.out; } static r_obj* chop_fallback_shaped(r_obj* x, r_obj* indices, struct vctrs_chop_info info) { - for (R_len_t i = 0; i < info.out_size; ++i) { + r_obj* const* v_indices = NULL; + if (info.has_indices) { + v_indices = r_list_cbegin(indices); + } + + for (r_ssize i = 0; i < info.out_size; ++i) { if (info.has_indices) { - info.index = VECTOR_ELT(indices, i); + info.index = v_indices[i]; } else { ++(*info.p_index); } // `vec_slice_fallback()` will also `vec_restore()` for us - r_obj* elt = PROTECT(vec_slice_fallback(x, info.index)); - - SET_VECTOR_ELT(info.out, i, elt); - UNPROTECT(1); + r_obj* elt = vec_slice_fallback(x, info.index); + r_list_poke(info.out, i, elt); } return info.out; @@ -366,18 +385,19 @@ static r_obj* chop_fallback_shaped(r_obj* x, r_obj* indices, struct vctrs_chop_i // ----------------------------------------------------------------------------- -SEXP vec_as_indices(SEXP indices, r_ssize n, SEXP names) { - if (indices == R_NilValue) { +r_obj* vec_as_indices(r_obj* indices, r_ssize n, r_obj* names) { + if (indices == r_null) { return indices; } - if (TYPEOF(indices) != VECSXP) { - Rf_errorcall(R_NilValue, "`indices` must be a list of index values, or `NULL`."); + if (r_typeof(indices) != R_TYPE_list) { + r_abort_lazy_call(r_lazy_null, "`indices` must be a list of index values, or `NULL`."); } - indices = PROTECT(r_clone_referenced(indices)); + indices = KEEP(r_clone_referenced(indices)); - r_ssize size = vec_size(indices); + const r_ssize size = r_length(indices); + r_obj* const* v_indices = r_list_cbegin(indices); // Restrict index values to positive integer locations const struct location_opts opts = { @@ -392,12 +412,12 @@ SEXP vec_as_indices(SEXP indices, r_ssize n, SEXP names) { .loc_zero = LOC_ZERO_ERROR }; - for (int i = 0; i < size; ++i) { - SEXP index = VECTOR_ELT(indices, i); + for (r_ssize i = 0; i < size; ++i) { + r_obj* index = v_indices[i]; index = vec_as_location_opts(index, n, names, &opts); - SET_VECTOR_ELT(indices, i, index); + r_list_poke(indices, i, index); } - UNPROTECT(1); + FREE(1); return indices; } diff --git a/src/vctrs.h b/src/vctrs.h index 0de83938c..61f5b4a33 100644 --- a/src/vctrs.h +++ b/src/vctrs.h @@ -77,7 +77,7 @@ SEXP vec_proxy_equal(SEXP x); SEXP vec_proxy_compare(SEXP x); SEXP vec_proxy_order(SEXP x); SEXP vec_proxy_unwrap(SEXP x); -SEXP vec_chop(SEXP x, SEXP indices); +r_obj* vec_chop(r_obj* x, r_obj* indices); SEXP vec_slice_shaped(enum vctrs_type type, SEXP x, SEXP index); bool vec_requires_fallback(SEXP x, struct vctrs_proxy_info info); r_obj* vec_ptype(r_obj* x, struct vctrs_arg* x_arg, struct r_lazy call); From 7e4edb4424b764635d33c5d45ef98db5602f28b6 Mon Sep 17 00:00:00 2001 From: DavisVaughan Date: Mon, 6 Mar 2023 14:12:15 -0500 Subject: [PATCH 246/312] Update revdepcheck results --- revdep/README.md | 168 +- revdep/cran.md | 120 +- revdep/failures.md | 8414 +++++++++++++++++++++++++++++++++++++++++++- revdep/problems.md | 236 +- 4 files changed, 8885 insertions(+), 53 deletions(-) diff --git a/revdep/README.md b/revdep/README.md index 77762c863..f0ac49b78 100644 --- a/revdep/README.md +++ b/revdep/README.md @@ -1,10 +1,166 @@ # Revdeps -## Failed to check (3) +## Failed to check (149) -|package |version |error |warning |note | -|:-------------|:-------|:-----|:-------|:----| -|NA |? | | | | -|tidybayes |? | | | | -|tidyposterior |? | | | | +|package |version |error |warning |note | +|:---------------------|:-------|:-----|:-------|:----| +|accept |? | | | | +|ADAM |? | | | | +|admiraldev |? | | | | +|afex |? | | | | +|AGread |? | | | | +|ags |? | | | | +|AMARETTO |? | | | | +|amplican |? | | | | +|arulesViz |1.5-1 |1 | | | +|autoTS |? | | | | +|azuremlsdk |1.10.0 |1 | | | +|bayesian |0.0.9 |1 | |1 | +|bayesmodels |? | | | | +|bayesnec |2.1.0.2 |1 | |1 | +|bayesplot |? | | | | +|BayesPostEst |? | | | | +|bayesrules |? | | | | +|beadplexr |? | | | | +|BiplotML |1.1.0 |1 | | | +|blocs |? | | | | +|breathtestcore |? | | | | +|brendaDb |? | | | | +|broom.helpers |? | | | | +|broom.mixed |? | | | | +|BUSpaRse |? | | | | +|cattonum |? | | | | +|ceRNAnetsim |? | | | | +|ChineseNames |? | | | | +|cinaR |? | | | | +|clustermole |? | | | | +|cmstatr |0.9.1 |1 | | | +|COMPASS |? | | | | +|conflicted |1.2.0 |1 | | | +|cort |? | | | | +|covidmx |? | | | | +|CRE |? | | | | +|ctDNAtools |? | | | | +|CytoML |? | | | | +|D2MCS |? | | | | +|datawizard |? | | | | +|DeLorean |? | | | | +|DepecheR |? | | | | +|destiny |? | | | | +|DiffBind |? | | | | +|diffman |? | | | | +|diffrprojects |? | | | | +|dynfrail |? | | | | +|embed |? | | | | +|EpiForsk |? | | | | +|epiphy |? | | | | +|epitopeR |? | | | | +|escalation |? | | | | +|EScvtmle |? | | | | +|ESTER |0.2.0 |1 | | | +|evaluator |? | | | | +|expstudies |? | | | | +|fable.prophet |? | | | | +|FAMetA |0.1.5 |1 | | | +|finnts |? | | | | +|fipe |? | | | | +|foieGras |? | | | | +|forceR |? | | | | +|FSelectorRcpp |? | | | | +|genekitr |? | | | | +|geocmeans |? | | | | +|ggPMX |? | | | | +|ggstatsplot |? | | | | +|healthyR.ai |? | | | | +|healthyR.ts |? | | | | +|healthyverse |? | | | | +|historicalborrowlong |? | | | | +|immcp |? | | | | +|ImputeRobust |? | | | | +|INSPECTumours |0.1.0 |1 | | | +|intRinsic |? | | | | +|IPDFileCheck |0.7.5 |1 | | | +|IRexamples |? | | | | +|irtQ |? | | | | +|IsoCorrectoR |? | | | | +|journalabbr |? | | | | +|l1spectral |0.99.6 |1 | | | +|lifeR |? | | | | +|loon.ggplot |? | | | | +|loon.shiny |? | | | | +|MACP |? | | | | +|mafs |? | | | | +|MantaID |? | | | | +|marginaleffects |? | | | | +|MazamaCoreUtils |0.4.13 |1 | | | +|mbRes |? | | | | +|merTools |? | | | | +|microservices |? | | | | +|modeltime |? | | | | +|modeltime.ensemble |? | | | | +|modeltime.gluonts |? | | | | +|modeltime.h2o |? | | | | +|modeltime.resample |? | | | | +|moexer |? | | | | +|mpower |? | | | | +|multibiasmeta |? | | | | +|NetFACS |0.5.0 |1 | | | +|nlmixr2extra |? | | | | +|nlmixr2plot |? | | | | +|nlmixr2rpt |? | | | | +|numbat |? | | | | +|OBL |? | | | | +|OlinkAnalyze |? | | | | +|OncoBayes2 |0.8-8 |1 | | | +|openai |? | | | | +|OutliersO3 |0.6.3 |1 | | | +|pathwayTMB |? | | | | +|peramo |? | | | | +|performanceEstimation |? | | | | +|planningML |1.0.0 |1 | | | +|Platypus |? | | | | +|PLSiMCpp |? | | | | +|promotionImpact |? | | | | +|prqlr |? | | | | +|PsychWordVec |? | | | | +|RBesT |? | | | | +|rcssci |? | | | | +|rdss |? | | | | +|report |? | | | | +|RevGadgets |? | | | | +|Rigma |0.2.1 |1 | | | +|Robyn |? | | | | +|RVA |? | | | | +|SAMtool |? | | | | +|scGate |? | | | | +|SCpubr |? | | | | +|shinyHugePlot |? | | | | +|sjPlot |? | | | | +|sknifedatar |? | | | | +|SpaDES.tools |? | | | | +|statsExpressions |? | | | | +|stortingscrape |? | | | | +|tame |? | | | | +|tidybayes |? | | | | +|tidyposterior |? | | | | +|tidySEM |? | | | | +|tidytags |? | | | | +|timetk |? | | | | +|tinyarray |? | | | | +|tipmap |? | | | | +|vivid |? | | | | +|wearables |0.8.1 |1 | | | +|webSDM |? | | | | +|wrappedtools |? | | | | +|xpose.nlmixr2 |? | | | | + +## New problems (5) + +|package |version |error |warning |note | +|:--------------|:-------|:------|:-------|:----| +|[dplyr](problems.md#dplyr)|1.1.0 |__+1__ | |1 | +|[GenomeAdmixR](problems.md#genomeadmixr)|2.1.7 |__+1__ | |2 | +|[photosynthesis](problems.md#photosynthesis)|2.1.1 |__+1__ | |2 | +|[portalr](problems.md#portalr)|0.3.11 |__+1__ | | | +|[rlang](problems.md#rlang)|1.0.6 |__+1__ | |1 | diff --git a/revdep/cran.md b/revdep/cran.md index 597743524..a40b46321 100644 --- a/revdep/cran.md +++ b/revdep/cran.md @@ -1,13 +1,123 @@ ## revdepcheck results -We checked 217 reverse dependencies (216 from CRAN + 1 from Bioconductor), comparing R CMD check results across CRAN and dev versions of this package. +We checked 4238 reverse dependencies (4183 from CRAN + 55 from Bioconductor), comparing R CMD check results across CRAN and dev versions of this package. - * We saw 0 new problems - * We failed to check 2 packages + * We saw 5 new problems + * We failed to check 94 packages Issues with CRAN packages are summarised below. +### New problems +(This reports the first line of each new failure) + +* dplyr + checking tests ... ERROR + +* GenomeAdmixR + checking tests ... ERROR + +* photosynthesis + checking tests ... ERROR + +* portalr + checking tests ... ERROR + +* rlang + checking tests ... ERROR + ### Failed to check -* tidybayes (NA) -* tidyposterior (NA) +* accept (NA) +* admiraldev (NA) +* afex (NA) +* arulesViz (NA) +* autoTS (NA) +* azuremlsdk (NA) +* bayesian (NA) +* bayesnec (NA) +* bayesplot (NA) +* BayesPostEst (NA) +* bayesrules (NA) +* beadplexr (NA) +* BiplotML (NA) +* blocs (NA) +* breathtestcore (NA) +* broom.helpers (NA) +* broom.mixed (NA) +* ChineseNames (NA) +* cinaR (NA) +* clustermole (NA) +* cmstatr (NA) +* conflicted (NA) +* CRE (NA) +* datawizard (NA) +* embed (NA) +* escalation (NA) +* ESTER (NA) +* fable.prophet (NA) +* FAMetA (NA) +* finnts (NA) +* FSelectorRcpp (NA) +* genekitr (NA) +* geocmeans (NA) +* ggPMX (NA) +* ggstatsplot (NA) +* healthyR.ai (NA) +* healthyR.ts (NA) +* healthyverse (NA) +* historicalborrowlong (NA) +* immcp (NA) +* ImputeRobust (NA) +* INSPECTumours (NA) +* IPDFileCheck (NA) +* IRexamples (NA) +* l1spectral (NA) +* loon.ggplot (NA) +* loon.shiny (NA) +* MACP (NA) +* marginaleffects (NA) +* MazamaCoreUtils (NA) +* merTools (NA) +* modeltime (NA) +* modeltime.ensemble (NA) +* modeltime.gluonts (NA) +* modeltime.h2o (NA) +* modeltime.resample (NA) +* mpower (NA) +* multibiasmeta (NA) +* NetFACS (NA) +* nlmixr2extra (NA) +* nlmixr2plot (NA) +* nlmixr2rpt (NA) +* numbat (NA) +* OlinkAnalyze (NA) +* OncoBayes2 (NA) +* OutliersO3 (NA) +* pathwayTMB (NA) +* performanceEstimation (NA) +* planningML (NA) +* Platypus (NA) +* promotionImpact (NA) +* PsychWordVec (NA) +* RBesT (NA) +* rdss (NA) +* report (NA) +* Rigma (NA) +* Robyn (NA) +* RVA (NA) +* SAMtool (NA) +* SCpubr (NA) +* sjPlot (NA) +* sknifedatar (NA) +* SpaDES.tools (NA) +* statsExpressions (NA) +* tidybayes (NA) +* tidyposterior (NA) +* tidySEM (NA) +* timetk (NA) +* tinyarray (NA) +* tipmap (NA) +* vivid (NA) +* wearables (NA) +* webSDM (NA) +* xpose.nlmixr2 (NA) diff --git a/revdep/failures.md b/revdep/failures.md index 0e4698947..851519c93 100644 --- a/revdep/failures.md +++ b/revdep/failures.md @@ -1,13 +1,8144 @@ -# NA +# accept + +
+ +* Version: 1.0.0 +* GitHub: NA +* Source code: https://github.com/cran/accept +* Date/Publication: 2023-02-06 20:52:31 UTC +* Number of recursive dependencies: 97 + +Run `revdepcheck::cloud_details(, "accept")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/accept/new/accept.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘accept/DESCRIPTION’ ... OK +* this is package ‘accept’ version ‘1.0.0’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... 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 ‘accept’ can be installed ... ERROR +Installation failed. +See ‘/tmp/workdir/accept/new/accept.Rcheck/00install.out’ for details. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/accept/old/accept.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘accept/DESCRIPTION’ ... OK +* this is package ‘accept’ version ‘1.0.0’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... 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 ‘accept’ can be installed ... ERROR +Installation failed. +See ‘/tmp/workdir/accept/old/accept.Rcheck/00install.out’ for details. +* DONE +Status: 1 ERROR + + + + + +``` +# ADAM + +
+ +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/ADAM +* Number of recursive dependencies: 94 + +Run `revdepcheck::cloud_details(, "ADAM")` for more info + +
+ +## Error before installation + +### Devel + +``` + + + + + + +``` +### CRAN + +``` + + + + + + +``` +# admiraldev + +
+ +* Version: 0.2.0 +* GitHub: https://github.com/pharmaverse/admiraldev +* Source code: https://github.com/cran/admiraldev +* Date/Publication: 2022-12-01 00:10:02 UTC +* Number of recursive dependencies: 122 + +Run `revdepcheck::cloud_details(, "admiraldev")` for more info + +
+ +## Error before installation + +### Devel + +``` + + + + + + +``` +### CRAN + +``` + + + + + + +``` +# afex + +
+ +* Version: 1.2-1 +* GitHub: https://github.com/singmann/afex +* Source code: https://github.com/cran/afex +* Date/Publication: 2023-01-09 08:40:11 UTC +* Number of recursive dependencies: 224 + +Run `revdepcheck::cloud_details(, "afex")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/afex/new/afex.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘afex/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘afex’ version ‘1.2-1’ +* package encoding: UTF-8 +* checking package namespace information ... OK +... + ‘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’... OK + ‘assumptions_of_ANOVAs.Rmd’ using ‘UTF-8’... OK + ‘introduction-mixed-models.pdf.asis’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 1 NOTE + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/afex/old/afex.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘afex/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘afex’ version ‘1.2-1’ +* package encoding: UTF-8 +* checking package namespace information ... OK +... + ‘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’... OK + ‘assumptions_of_ANOVAs.Rmd’ using ‘UTF-8’... OK + ‘introduction-mixed-models.pdf.asis’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 1 NOTE + + + + + +``` +# AGread + +
+ +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/AGread +* Number of recursive dependencies: 164 + +Run `revdepcheck::cloud_details(, "AGread")` for more info + +
+ +## Error before installation + +### Devel + +``` + + + + + + +``` +### CRAN + +``` + + + + + + +``` +# ags + +
+ +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/ags +* Number of recursive dependencies: 54 + +Run `revdepcheck::cloud_details(, "ags")` for more info + +
+ +## Error before installation + +### Devel + +``` + + + + + + +``` +### CRAN + +``` + + + + + + +``` +# AMARETTO + +
+ +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/AMARETTO +* Number of recursive dependencies: 155 + +Run `revdepcheck::cloud_details(, "AMARETTO")` for more info + +
+ +## Error before installation + +### Devel + +``` + + + + + + +``` +### CRAN + +``` + + + + + + +``` +# amplican + +
+ +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/amplican +* Number of recursive dependencies: 116 + +Run `revdepcheck::cloud_details(, "amplican")` for more info + +
+ +## Error before installation + +### Devel + +``` + + + + + + +``` +### CRAN + +``` + + + + + + +``` +# arulesViz + +
+ +* Version: 1.5-1 +* GitHub: https://github.com/mhahsler/arulesViz +* Source code: https://github.com/cran/arulesViz +* Date/Publication: 2021-11-19 17:40:07 UTC +* Number of recursive dependencies: 111 + +Run `revdepcheck::cloud_details(, "arulesViz")` for more info + +
+ +## In both + +* checking whether package ‘arulesViz’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/arulesViz/new/arulesViz.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘arulesViz’ ... +** package ‘arulesViz’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** inst +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + there is no package called ‘R6’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Execution halted +ERROR: lazy loading failed for package ‘arulesViz’ +* removing ‘/tmp/workdir/arulesViz/new/arulesViz.Rcheck/arulesViz’ + + +``` +### CRAN + +``` +* installing *source* package ‘arulesViz’ ... +** package ‘arulesViz’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** inst +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + there is no package called ‘R6’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Execution halted +ERROR: lazy loading failed for package ‘arulesViz’ +* removing ‘/tmp/workdir/arulesViz/old/arulesViz.Rcheck/arulesViz’ + + +``` +# autoTS + +
+ +* Version: 0.9.11 +* GitHub: https://github.com/vivienroussez/autots +* Source code: https://github.com/cran/autoTS +* Date/Publication: 2020-06-05 12:20:06 UTC +* Number of recursive dependencies: 116 + +Run `revdepcheck::cloud_details(, "autoTS")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/autoTS/new/autoTS.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘autoTS/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘autoTS’ version ‘0.9.11’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘prophet’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/autoTS/old/autoTS.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘autoTS/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘autoTS’ version ‘0.9.11’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘prophet’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# azuremlsdk + +
+ +* Version: 1.10.0 +* GitHub: https://github.com/azure/azureml-sdk-for-r +* Source code: https://github.com/cran/azuremlsdk +* Date/Publication: 2020-09-22 15:40:07 UTC +* Number of recursive dependencies: 91 + +Run `revdepcheck::cloud_details(, "azuremlsdk")` for more info + +
+ +## In both + +* checking whether package ‘azuremlsdk’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/azuremlsdk/new/azuremlsdk.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘azuremlsdk’ ... +** package ‘azuremlsdk’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** inst +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + there is no package called ‘Rcpp’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Execution halted +ERROR: lazy loading failed for package ‘azuremlsdk’ +* removing ‘/tmp/workdir/azuremlsdk/new/azuremlsdk.Rcheck/azuremlsdk’ + + +``` +### CRAN + +``` +* installing *source* package ‘azuremlsdk’ ... +** package ‘azuremlsdk’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** inst +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + there is no package called ‘Rcpp’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Execution halted +ERROR: lazy loading failed for package ‘azuremlsdk’ +* removing ‘/tmp/workdir/azuremlsdk/old/azuremlsdk.Rcheck/azuremlsdk’ + + +``` +# bayesian + +
+ +* Version: 0.0.9 +* GitHub: https://github.com/hsbadr/bayesian +* Source code: https://github.com/cran/bayesian +* Date/Publication: 2022-06-16 23:00:02 UTC +* Number of recursive dependencies: 187 + +Run `revdepcheck::cloud_details(, "bayesian")` for more info + +
+ +## In both + +* checking whether package ‘bayesian’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/bayesian/new/bayesian.Rcheck/00install.out’ for details. + ``` + +* checking package dependencies ... NOTE + ``` + Package suggested but not available for checking: ‘rstan’ + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘bayesian’ ... +** package ‘bayesian’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** inst +** byte-compile and prepare package for lazy loading +Error: package or namespace load failed for ‘brms’ in loadNamespace(j <- imp[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): + there is no package called ‘rstan’ +Execution halted +ERROR: lazy loading failed for package ‘bayesian’ +* removing ‘/tmp/workdir/bayesian/new/bayesian.Rcheck/bayesian’ + + +``` +### CRAN + +``` +* installing *source* package ‘bayesian’ ... +** package ‘bayesian’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** inst +** byte-compile and prepare package for lazy loading +Error: package or namespace load failed for ‘brms’ in loadNamespace(j <- imp[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): + there is no package called ‘rstan’ +Execution halted +ERROR: lazy loading failed for package ‘bayesian’ +* removing ‘/tmp/workdir/bayesian/old/bayesian.Rcheck/bayesian’ + + +``` +# bayesmodels + +
+ +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/bayesmodels +* Number of recursive dependencies: 259 + +Run `revdepcheck::cloud_details(, "bayesmodels")` for more info + +
+ +## Error before installation + +### Devel + +``` + + + + + + +``` +### CRAN + +``` + + + + + + +``` +# bayesnec + +
+ +* Version: 2.1.0.2 +* GitHub: https://github.com/open-aims/bayesnec +* Source code: https://github.com/cran/bayesnec +* Date/Publication: 2023-02-21 00:30:03 UTC +* Number of recursive dependencies: 133 + +Run `revdepcheck::cloud_details(, "bayesnec")` for more info + +
+ +## In both + +* checking whether package ‘bayesnec’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/bayesnec/new/bayesnec.Rcheck/00install.out’ for details. + ``` + +* checking package dependencies ... NOTE + ``` + Package suggested but not available for checking: ‘rstan’ + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘bayesnec’ ... +** package ‘bayesnec’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** data +*** moving datasets to lazyload DB +Warning: namespace ‘rstan’ is not available and has been replaced +by .GlobalEnv when processing object ‘manec_example’ +Warning: namespace ‘brms’ is not available and has been replaced +by .GlobalEnv when processing object ‘manec_example’ +... +by .GlobalEnv when processing object ‘manec_example’ +Warning: namespace ‘rstan’ is not available and has been replaced +by .GlobalEnv when processing object ‘manec_example’ +** inst +** byte-compile and prepare package for lazy loading +Error: package or namespace load failed for ‘brms’ in loadNamespace(j <- imp[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): + there is no package called ‘rstan’ +Execution halted +ERROR: lazy loading failed for package ‘bayesnec’ +* removing ‘/tmp/workdir/bayesnec/new/bayesnec.Rcheck/bayesnec’ + + +``` +### CRAN + +``` +* installing *source* package ‘bayesnec’ ... +** package ‘bayesnec’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** data +*** moving datasets to lazyload DB +Warning: namespace ‘rstan’ is not available and has been replaced +by .GlobalEnv when processing object ‘manec_example’ +Warning: namespace ‘brms’ is not available and has been replaced +by .GlobalEnv when processing object ‘manec_example’ +... +by .GlobalEnv when processing object ‘manec_example’ +Warning: namespace ‘rstan’ is not available and has been replaced +by .GlobalEnv when processing object ‘manec_example’ +** inst +** byte-compile and prepare package for lazy loading +Error: package or namespace load failed for ‘brms’ in loadNamespace(j <- imp[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): + there is no package called ‘rstan’ +Execution halted +ERROR: lazy loading failed for package ‘bayesnec’ +* removing ‘/tmp/workdir/bayesnec/old/bayesnec.Rcheck/bayesnec’ + + +``` +# bayesplot + +
+ +* Version: 1.10.0 +* GitHub: https://github.com/stan-dev/bayesplot +* Source code: https://github.com/cran/bayesplot +* Date/Publication: 2022-11-16 22:00:08 UTC +* Number of recursive dependencies: 127 + +Run `revdepcheck::cloud_details(, "bayesplot")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/bayesplot/new/bayesplot.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘bayesplot/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘bayesplot’ version ‘1.10.0’ +* package encoding: UTF-8 +* checking package namespace information ... 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 + ‘graphical-ppcs.Rmd’ using ‘UTF-8’... OK + ‘plotting-mcmc-draws.Rmd’ using ‘UTF-8’... OK + ‘visual-mcmc-diagnostics.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 2 NOTEs + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/bayesplot/old/bayesplot.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘bayesplot/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘bayesplot’ version ‘1.10.0’ +* package encoding: UTF-8 +* checking package namespace information ... 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 + ‘graphical-ppcs.Rmd’ using ‘UTF-8’... OK + ‘plotting-mcmc-draws.Rmd’ using ‘UTF-8’... OK + ‘visual-mcmc-diagnostics.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 2 NOTEs + + + + + +``` +# BayesPostEst + +
+ +* Version: 0.3.2 +* GitHub: https://github.com/ShanaScogin/BayesPostEst +* Source code: https://github.com/cran/BayesPostEst +* Date/Publication: 2021-11-11 08:10:05 UTC +* Number of recursive dependencies: 159 + +Run `revdepcheck::cloud_details(, "BayesPostEst")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/BayesPostEst/new/BayesPostEst.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘BayesPostEst/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘BayesPostEst’ version ‘0.3.2’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘rstanarm’ + +Package suggested but not available for checking: ‘rstan’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/BayesPostEst/old/BayesPostEst.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘BayesPostEst/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘BayesPostEst’ version ‘0.3.2’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘rstanarm’ + +Package suggested but not available for checking: ‘rstan’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# bayesrules + +
+ +* Version: 0.0.2 +* GitHub: https://github.com/bayes-rules/bayesrules +* Source code: https://github.com/cran/bayesrules +* Date/Publication: 2021-09-25 04:30:07 UTC +* Number of recursive dependencies: 135 + +Run `revdepcheck::cloud_details(, "bayesrules")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/bayesrules/new/bayesrules.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘bayesrules/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘bayesrules’ version ‘0.0.2’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘rstanarm’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/bayesrules/old/bayesrules.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘bayesrules/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘bayesrules’ version ‘0.0.2’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘rstanarm’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# beadplexr + +
+ +* Version: 0.4.1 +* GitHub: NA +* Source code: https://github.com/cran/beadplexr +* Date/Publication: 2022-03-05 13:50:02 UTC +* Number of recursive dependencies: 127 + +Run `revdepcheck::cloud_details(, "beadplexr")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/beadplexr/new/beadplexr.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘beadplexr/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘beadplexr’ version ‘0.4.1’ +* package encoding: UTF-8 +* checking package namespace information ... 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 + ‘cba_macsplex_example.Rmd’ using ‘UTF-8’... OK + ‘legendplex_analysis.Rmd’ using ‘UTF-8’... OK + ‘preparing_flow_data.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 1 NOTE + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/beadplexr/old/beadplexr.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘beadplexr/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘beadplexr’ version ‘0.4.1’ +* package encoding: UTF-8 +* checking package namespace information ... 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 + ‘cba_macsplex_example.Rmd’ using ‘UTF-8’... OK + ‘legendplex_analysis.Rmd’ using ‘UTF-8’... OK + ‘preparing_flow_data.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 1 NOTE + + + + + +``` +# BiplotML + +
+ +* Version: 1.1.0 +* GitHub: https://github.com/jgbabativam/BiplotML +* Source code: https://github.com/cran/BiplotML +* Date/Publication: 2022-04-22 21:20:02 UTC +* Number of recursive dependencies: 88 + +Run `revdepcheck::cloud_details(, "BiplotML")` for more info + +
+ +## In both + +* checking whether package ‘BiplotML’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/BiplotML/new/BiplotML.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘BiplotML’ ... +** package ‘BiplotML’ 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 ‘shapes’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): + there is no package called ‘htmlwidgets’ +Execution halted +ERROR: lazy loading failed for package ‘BiplotML’ +* removing ‘/tmp/workdir/BiplotML/new/BiplotML.Rcheck/BiplotML’ + + +``` +### CRAN + +``` +* installing *source* package ‘BiplotML’ ... +** package ‘BiplotML’ 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 ‘shapes’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): + there is no package called ‘htmlwidgets’ +Execution halted +ERROR: lazy loading failed for package ‘BiplotML’ +* removing ‘/tmp/workdir/BiplotML/old/BiplotML.Rcheck/BiplotML’ + + +``` +# blocs + +
+ +* Version: 0.1.0 +* GitHub: NA +* Source code: https://github.com/cran/blocs +* Date/Publication: 2022-11-23 11:20:06 UTC +* Number of recursive dependencies: 161 + +Run `revdepcheck::cloud_details(, "blocs")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/blocs/new/blocs.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘blocs/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘blocs’ version ‘0.1.0’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required and available but unsuitable version: ‘mgcv’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/blocs/old/blocs.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘blocs/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘blocs’ version ‘0.1.0’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required and available but unsuitable version: ‘mgcv’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# breathtestcore + +
+ +* Version: 0.8.6 +* GitHub: https://github.com/dmenne/breathtestcore +* Source code: https://github.com/cran/breathtestcore +* Date/Publication: 2023-02-13 14:00:07 UTC +* Number of recursive dependencies: 119 + +Run `revdepcheck::cloud_details(, "breathtestcore")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/breathtestcore/new/breathtestcore.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘breathtestcore/DESCRIPTION’ ... OK +* this is package ‘breathtestcore’ version ‘0.8.6’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... NOTE +... +* 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 + ‘data_formats.Rmd’ using ‘UTF-8’... OK + ‘methods_and_concepts.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 2 NOTEs + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/breathtestcore/old/breathtestcore.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘breathtestcore/DESCRIPTION’ ... OK +* this is package ‘breathtestcore’ version ‘0.8.6’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... NOTE +... +* 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 + ‘data_formats.Rmd’ using ‘UTF-8’... OK + ‘methods_and_concepts.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 2 NOTEs + + + + + +``` +# brendaDb + +
+ +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/brendaDb +* Number of recursive dependencies: 120 + +Run `revdepcheck::cloud_details(, "brendaDb")` for more info + +
+ +## Error before installation + +### Devel + +``` + + + + + + +``` +### CRAN + +``` + + + + + + +``` +# broom.helpers + +
+ +* Version: 1.12.0 +* GitHub: https://github.com/larmarange/broom.helpers +* Source code: https://github.com/cran/broom.helpers +* Date/Publication: 2023-02-09 17:00:02 UTC +* Number of recursive dependencies: 226 + +Run `revdepcheck::cloud_details(, "broom.helpers")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/broom.helpers/new/broom.helpers.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘broom.helpers/DESCRIPTION’ ... OK +* this is package ‘broom.helpers’ version ‘1.12.0’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... NOTE +... +* 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 ... NONE + ‘tidy.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 1 NOTE + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/broom.helpers/old/broom.helpers.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘broom.helpers/DESCRIPTION’ ... OK +* this is package ‘broom.helpers’ version ‘1.12.0’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... NOTE +... +* 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 ... NONE + ‘tidy.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 1 NOTE + + + + + +``` +# broom.mixed + +
+ +* Version: 0.2.9.4 +* GitHub: https://github.com/bbolker/broom.mixed +* Source code: https://github.com/cran/broom.mixed +* Date/Publication: 2022-04-17 17:42:29 UTC +* Number of recursive dependencies: 164 + +Run `revdepcheck::cloud_details(, "broom.mixed")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/broom.mixed/new/broom.mixed.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘broom.mixed/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘broom.mixed’ version ‘0.2.9.4’ +* package encoding: UTF-8 +* checking package namespace information ... 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 + ‘broom_mixed_intro.rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 2 NOTEs + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/broom.mixed/old/broom.mixed.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘broom.mixed/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘broom.mixed’ version ‘0.2.9.4’ +* package encoding: UTF-8 +* checking package namespace information ... 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 + ‘broom_mixed_intro.rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 2 NOTEs + + + + + +``` +# BUSpaRse + +
+ +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/BUSpaRse +* Number of recursive dependencies: 157 + +Run `revdepcheck::cloud_details(, "BUSpaRse")` for more info + +
+ +## Error before installation + +### Devel + +``` + + + + + + +``` +### CRAN + +``` + + + + + + +``` +# cattonum + +
+ +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/cattonum +* Number of recursive dependencies: 78 + +Run `revdepcheck::cloud_details(, "cattonum")` for more info + +
+ +## Error before installation + +### Devel + +``` + + + + + + +``` +### CRAN + +``` + + + + + + +``` +# ceRNAnetsim + +
+ +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/ceRNAnetsim +* Number of recursive dependencies: 99 + +Run `revdepcheck::cloud_details(, "ceRNAnetsim")` for more info + +
+ +## Error before installation + +### Devel + +``` + + + + + + +``` +### CRAN + +``` + + + + + + +``` +# ChineseNames + +
+ +* Version: 1.1.1 +* GitHub: https://github.com/psychbruce/ChineseNames +* Source code: https://github.com/cran/ChineseNames +* Date/Publication: 2021-11-29 16:40:02 UTC +* Number of recursive dependencies: 156 + +Run `revdepcheck::cloud_details(, "ChineseNames")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/ChineseNames/new/ChineseNames.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘ChineseNames/DESCRIPTION’ ... OK +* this is package ‘ChineseNames’ version ‘1.1.1’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘bruceR’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/ChineseNames/old/ChineseNames.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘ChineseNames/DESCRIPTION’ ... OK +* this is package ‘ChineseNames’ version ‘1.1.1’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘bruceR’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# cinaR + +
+ +* Version: 0.2.3 +* GitHub: https://github.com/eonurk/cinaR +* Source code: https://github.com/cran/cinaR +* Date/Publication: 2022-05-18 14:00:09 UTC +* Number of recursive dependencies: 178 + +Run `revdepcheck::cloud_details(, "cinaR")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/cinaR/new/cinaR.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘cinaR/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘cinaR’ version ‘0.2.3’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘ChIPseeker’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/cinaR/old/cinaR.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘cinaR/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘cinaR’ version ‘0.2.3’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘ChIPseeker’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# clustermole + +
+ +* Version: 1.1.0 +* GitHub: https://github.com/igordot/clustermole +* Source code: https://github.com/cran/clustermole +* Date/Publication: 2021-01-26 06:40:02 UTC +* Number of recursive dependencies: 149 + +Run `revdepcheck::cloud_details(, "clustermole")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/clustermole/new/clustermole.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘clustermole/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘clustermole’ version ‘1.1.0’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Packages required but not available: 'GSVA', 'singscore' + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/clustermole/old/clustermole.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘clustermole/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘clustermole’ version ‘1.1.0’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Packages required but not available: 'GSVA', 'singscore' + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# cmstatr + +
+ +* Version: 0.9.1 +* GitHub: https://github.com/cmstatr/cmstatr +* Source code: https://github.com/cran/cmstatr +* Date/Publication: 2021-09-30 16:50:02 UTC +* Number of recursive dependencies: 86 + +Run `revdepcheck::cloud_details(, "cmstatr")` for more info + +
+ +## In both + +* checking whether package ‘cmstatr’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/cmstatr/new/cmstatr.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘cmstatr’ ... +** package ‘cmstatr’ 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 ‘scales’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Execution halted +ERROR: lazy loading failed for package ‘cmstatr’ +* removing ‘/tmp/workdir/cmstatr/new/cmstatr.Rcheck/cmstatr’ + + +``` +### CRAN + +``` +* installing *source* package ‘cmstatr’ ... +** package ‘cmstatr’ 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 ‘scales’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Execution halted +ERROR: lazy loading failed for package ‘cmstatr’ +* removing ‘/tmp/workdir/cmstatr/old/cmstatr.Rcheck/cmstatr’ + + +``` +# COMPASS + +
+ +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/COMPASS +* Number of recursive dependencies: 151 + +Run `revdepcheck::cloud_details(, "COMPASS")` for more info + +
+ +## Error before installation + +### Devel + +``` + + + + + + +``` +### CRAN + +``` + + + + + + +``` +# conflicted + +
+ +* Version: 1.2.0 +* GitHub: https://github.com/r-lib/conflicted +* Source code: https://github.com/cran/conflicted +* Date/Publication: 2023-02-01 08:20:06 UTC +* Number of recursive dependencies: 49 + +Run `revdepcheck::cloud_details(, "conflicted")` for more info + +
+ +## In both + +* checking whether package ‘conflicted’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/conflicted/new/conflicted.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘conflicted’ ... +** package ‘conflicted’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** byte-compile and prepare package for lazy loading +** help +*** installing help indices +** building package indices +** testing if installed package can be loaded from temporary location +Error: package or namespace load failed for ‘conflicted’: + .onLoad failed in loadNamespace() for 'conflicted', details: + call: loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) + error: there is no package called ‘cachem’ +Error: loading failed +Execution halted +ERROR: loading failed +* removing ‘/tmp/workdir/conflicted/new/conflicted.Rcheck/conflicted’ + + +``` +### CRAN + +``` +* installing *source* package ‘conflicted’ ... +** package ‘conflicted’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** byte-compile and prepare package for lazy loading +** help +*** installing help indices +** building package indices +** testing if installed package can be loaded from temporary location +Error: package or namespace load failed for ‘conflicted’: + .onLoad failed in loadNamespace() for 'conflicted', details: + call: loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) + error: there is no package called ‘cachem’ +Error: loading failed +Execution halted +ERROR: loading failed +* removing ‘/tmp/workdir/conflicted/old/conflicted.Rcheck/conflicted’ + + +``` +# cort + +
+ +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/cort +* Number of recursive dependencies: 75 + +Run `revdepcheck::cloud_details(, "cort")` for more info + +
+ +## Error before installation + +### Devel + +``` + + + + + + +``` +### CRAN + +``` + + + + + + +``` +# covidmx + +
+ +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/covidmx +* Number of recursive dependencies: 150 + +Run `revdepcheck::cloud_details(, "covidmx")` for more info + +
+ +## Error before installation + +### Devel + +``` + + + + + + +``` +### CRAN + +``` + + + + + + +``` +# CRE + +
+ +* Version: 0.2.0 +* GitHub: https://github.com/NSAPH-Software/CRE +* Source code: https://github.com/cran/CRE +* Date/Publication: 2023-01-19 20:20:02 UTC +* Number of recursive dependencies: 141 + +Run `revdepcheck::cloud_details(, "CRE")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/CRE/new/CRE.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘CRE/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘CRE’ version ‘0.2.0’ +* package encoding: UTF-8 +* checking package namespace information ... 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 + ‘CRE.Rmd’ using ‘UTF-8’... OK + ‘Contribution.Rmd’ using ‘UTF-8’... OK + ‘Testing-the-Package.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 1 NOTE + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/CRE/old/CRE.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘CRE/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘CRE’ version ‘0.2.0’ +* package encoding: UTF-8 +* checking package namespace information ... 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 + ‘CRE.Rmd’ using ‘UTF-8’... OK + ‘Contribution.Rmd’ using ‘UTF-8’... OK + ‘Testing-the-Package.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 1 NOTE + + + + + +``` +# ctDNAtools + +
+ +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/ctDNAtools +* Number of recursive dependencies: 143 + +Run `revdepcheck::cloud_details(, "ctDNAtools")` for more info + +
+ +## Error before installation + +### Devel + +``` + + + + + + +``` +### CRAN + +``` + + + + + + +``` +# CytoML + +
+ +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/CytoML +* Number of recursive dependencies: 105 + +Run `revdepcheck::cloud_details(, "CytoML")` for more info + +
+ +## Error before installation + +### Devel + +``` + + + + + + +``` +### CRAN + +``` + + + + + + +``` +# D2MCS + +
+ +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/D2MCS +* Number of recursive dependencies: 179 + +Run `revdepcheck::cloud_details(, "D2MCS")` for more info + +
+ +## Error before installation + +### Devel + +``` + + + + + + +``` +### CRAN + +``` + + + + + + +``` +# datawizard + +
+ +* Version: 0.6.5 +* GitHub: https://github.com/easystats/datawizard +* Source code: https://github.com/cran/datawizard +* Date/Publication: 2022-12-14 23:50:02 UTC +* Number of recursive dependencies: 191 + +Run `revdepcheck::cloud_details(, "datawizard")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/datawizard/new/datawizard.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘datawizard/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘datawizard’ version ‘0.6.5’ +* package encoding: UTF-8 +* checking package namespace information ... 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 + ‘selection_syntax.Rmd’ using ‘UTF-8’... OK + ‘standardize_data.Rmd’ using ‘UTF-8’... OK + ‘tidyverse_translation.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 1 NOTE + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/datawizard/old/datawizard.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘datawizard/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘datawizard’ version ‘0.6.5’ +* package encoding: UTF-8 +* checking package namespace information ... 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 + ‘selection_syntax.Rmd’ using ‘UTF-8’... OK + ‘standardize_data.Rmd’ using ‘UTF-8’... OK + ‘tidyverse_translation.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 1 NOTE + + + + + +``` +# DeLorean + +
+ +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/DeLorean +* Number of recursive dependencies: 120 + +Run `revdepcheck::cloud_details(, "DeLorean")` for more info + +
+ +## Error before installation + +### Devel + +``` + + + + + + +``` +### CRAN + +``` + + + + + + +``` +# DepecheR + +
+ +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/DepecheR +* Number of recursive dependencies: 116 + +Run `revdepcheck::cloud_details(, "DepecheR")` for more info + +
+ +## Error before installation + +### Devel + +``` + + + + + + +``` +### CRAN + +``` + + + + + + +``` +# destiny + +
+ +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/destiny +* Number of recursive dependencies: 243 + +Run `revdepcheck::cloud_details(, "destiny")` for more info + +
+ +## Error before installation + +### Devel + +``` + + + + + + +``` +### CRAN + +``` + + + + + + +``` +# DiffBind + +
+ +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/DiffBind +* Number of recursive dependencies: 158 + +Run `revdepcheck::cloud_details(, "DiffBind")` for more info + +
+ +## Error before installation + +### Devel + +``` + + + + + + +``` +### CRAN + +``` + + + + + + +``` +# diffman + +
+ +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/diffman +* Number of recursive dependencies: 125 + +Run `revdepcheck::cloud_details(, "diffman")` for more info + +
+ +## Error before installation + +### Devel + +``` + + + + + + +``` +### CRAN + +``` + + + + + + +``` +# diffrprojects + +
+ +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/diffrprojects +* Number of recursive dependencies: 65 + +Run `revdepcheck::cloud_details(, "diffrprojects")` for more info + +
+ +## Error before installation + +### Devel + +``` + + + + + + +``` +### CRAN + +``` + + + + + + +``` +# dynfrail + +
+ +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/dynfrail +* Number of recursive dependencies: 57 + +Run `revdepcheck::cloud_details(, "dynfrail")` for more info + +
+ +## Error before installation + +### Devel + +``` + + + + + + +``` +### CRAN + +``` + + + + + + +``` +# embed + +
+ +* Version: 1.0.0 +* GitHub: https://github.com/tidymodels/embed +* Source code: https://github.com/cran/embed +* Date/Publication: 2022-07-02 16:50:02 UTC +* Number of recursive dependencies: 183 + +Run `revdepcheck::cloud_details(, "embed")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/embed/new/embed.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘embed/DESCRIPTION’ ... OK +* this is package ‘embed’ version ‘1.0.0’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... NOTE +... + i In index: 1. + i With name: x3. + Caused by error in `.f()`: + ! The package "rstanarm" is required. + + [ FAIL 1 | WARN 2 | SKIP 56 | PASS 162 ] + Error: Test failures + Execution halted +* DONE +Status: 1 ERROR, 2 NOTEs + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/embed/old/embed.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘embed/DESCRIPTION’ ... OK +* this is package ‘embed’ version ‘1.0.0’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... NOTE +... + i In index: 1. + i With name: x3. + Caused by error in `.f()`: + ! The package `rstanarm` is required. + + [ FAIL 1 | WARN 2 | SKIP 56 | PASS 162 ] + Error: Test failures + Execution halted +* DONE +Status: 1 ERROR, 2 NOTEs + + + + + +``` +# EpiForsk + +
+ +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/EpiForsk +* Number of recursive dependencies: 76 + +Run `revdepcheck::cloud_details(, "EpiForsk")` for more info + +
+ +## Error before installation + +### Devel + +``` + + + + + + +``` +### CRAN + +``` + + + + + + +``` +# epiphy + +
+ +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/epiphy +* Number of recursive dependencies: 91 + +Run `revdepcheck::cloud_details(, "epiphy")` for more info + +
+ +## Error before installation + +### Devel + +``` + + + + + + +``` +### CRAN + +``` + + + + + + +``` +# epitopeR + +
+ +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/epitopeR +* Number of recursive dependencies: 160 + +Run `revdepcheck::cloud_details(, "epitopeR")` for more info + +
+ +## Error before installation + +### Devel + +``` + + + + + + +``` +### CRAN + +``` + + + + + + +``` +# escalation + +
+ +* Version: 0.1.4 +* GitHub: NA +* Source code: https://github.com/cran/escalation +* Date/Publication: 2020-10-18 21:40:06 UTC +* Number of recursive dependencies: 127 + +Run `revdepcheck::cloud_details(, "escalation")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/escalation/new/escalation.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘escalation/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘escalation’ version ‘0.1.4’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘trialr’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/escalation/old/escalation.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘escalation/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘escalation’ version ‘0.1.4’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘trialr’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# EScvtmle + +
+ +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/EScvtmle +* Number of recursive dependencies: 78 + +Run `revdepcheck::cloud_details(, "EScvtmle")` for more info + +
+ +## Error before installation + +### Devel + +``` + + + + + + +``` +### CRAN + +``` + + + + + + +``` +# ESTER + +
+ +* Version: 0.2.0 +* GitHub: https://github.com/lnalborczyk/ESTER +* Source code: https://github.com/cran/ESTER +* Date/Publication: 2017-12-10 14:21:14 UTC +* Number of recursive dependencies: 137 + +Run `revdepcheck::cloud_details(, "ESTER")` for more info + +
+ +## In both + +* checking whether package ‘ESTER’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/ESTER/new/ESTER.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘ESTER’ ... +** package ‘ESTER’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** inst +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- imp[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + there is no package called ‘rstan’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Execution halted +ERROR: lazy loading failed for package ‘ESTER’ +* removing ‘/tmp/workdir/ESTER/new/ESTER.Rcheck/ESTER’ + + +``` +### CRAN + +``` +* installing *source* package ‘ESTER’ ... +** package ‘ESTER’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** inst +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- imp[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + there is no package called ‘rstan’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Execution halted +ERROR: lazy loading failed for package ‘ESTER’ +* removing ‘/tmp/workdir/ESTER/old/ESTER.Rcheck/ESTER’ + + +``` +# evaluator + +
+ +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/evaluator +* Number of recursive dependencies: 146 + +Run `revdepcheck::cloud_details(, "evaluator")` for more info + +
+ +## Error before installation + +### Devel + +``` + + + + + + +``` +### CRAN + +``` + + + + + + +``` +# expstudies + +
+ +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/expstudies +* Number of recursive dependencies: 59 + +Run `revdepcheck::cloud_details(, "expstudies")` for more info + +
+ +## Error before installation + +### Devel + +``` + + + + + + +``` +### CRAN + +``` + + + + + + +``` +# 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: 108 + +Run `revdepcheck::cloud_details(, "fable.prophet")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/fable.prophet/new/fable.prophet.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘fable.prophet/DESCRIPTION’ ... OK +* this is package ‘fable.prophet’ version ‘0.1.0’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘prophet’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/fable.prophet/old/fable.prophet.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘fable.prophet/DESCRIPTION’ ... OK +* this is package ‘fable.prophet’ version ‘0.1.0’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘prophet’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# FAMetA + +
+ +* Version: 0.1.5 +* GitHub: NA +* Source code: https://github.com/cran/FAMetA +* Date/Publication: 2023-01-11 09:33:11 UTC +* Number of recursive dependencies: 90 + +Run `revdepcheck::cloud_details(, "FAMetA")` for more info + +
+ +## In both + +* checking whether package ‘FAMetA’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/FAMetA/new/FAMetA.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘FAMetA’ ... +** package ‘FAMetA’ 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 ‘LipidMS’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): + there is no package called ‘readMzXmlData’ +Execution halted +ERROR: lazy loading failed for package ‘FAMetA’ +* removing ‘/tmp/workdir/FAMetA/new/FAMetA.Rcheck/FAMetA’ + + +``` +### CRAN + +``` +* installing *source* package ‘FAMetA’ ... +** package ‘FAMetA’ 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 ‘LipidMS’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): + there is no package called ‘readMzXmlData’ +Execution halted +ERROR: lazy loading failed for package ‘FAMetA’ +* removing ‘/tmp/workdir/FAMetA/old/FAMetA.Rcheck/FAMetA’ + + +``` +# finnts + +
+ +* Version: 0.2.2 +* GitHub: https://github.com/microsoft/finnts +* Source code: https://github.com/cran/finnts +* Date/Publication: 2023-02-12 00:40:02 UTC +* Number of recursive dependencies: 210 + +Run `revdepcheck::cloud_details(, "finnts")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/finnts/new/finnts.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘finnts/DESCRIPTION’ ... OK +* this is package ‘finnts’ version ‘0.2.2’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... OK +... + ‘best-model-selection.Rmd’ using ‘UTF-8’... OK + ‘external-regressors.Rmd’ using ‘UTF-8’... OK + ‘feature-engineering.Rmd’ using ‘UTF-8’... OK + ‘finnts.Rmd’ using ‘UTF-8’... OK + ‘hierarchical-forecasting.Rmd’ using ‘UTF-8’... OK + ‘models-used-in-finnts.Rmd’ using ‘UTF-8’... OK + ‘parallel-processing.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: OK + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/finnts/old/finnts.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘finnts/DESCRIPTION’ ... OK +* this is package ‘finnts’ version ‘0.2.2’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... OK +... + ‘best-model-selection.Rmd’ using ‘UTF-8’... OK + ‘external-regressors.Rmd’ using ‘UTF-8’... OK + ‘feature-engineering.Rmd’ using ‘UTF-8’... OK + ‘finnts.Rmd’ using ‘UTF-8’... OK + ‘hierarchical-forecasting.Rmd’ using ‘UTF-8’... OK + ‘models-used-in-finnts.Rmd’ using ‘UTF-8’... OK + ‘parallel-processing.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: OK + + + + + +``` +# fipe + +
+ +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/fipe +* Number of recursive dependencies: 69 + +Run `revdepcheck::cloud_details(, "fipe")` for more info + +
+ +## Error before installation + +### Devel + +``` + + + + + + +``` +### CRAN + +``` + + + + + + +``` +# foieGras + +
+ +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/foieGras +* Number of recursive dependencies: 134 + +Run `revdepcheck::cloud_details(, "foieGras")` for more info + +
+ +## Error before installation + +### Devel + +``` + + + + + + +``` +### CRAN + +``` + + + + + + +``` +# forceR + +
+ +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/forceR +* Number of recursive dependencies: 86 + +Run `revdepcheck::cloud_details(, "forceR")` for more info + +
+ +## Error before installation + +### Devel + +``` + + + + + + +``` +### CRAN + +``` + + + + + + +``` +# FSelectorRcpp + +
+ +* Version: 0.3.8 +* GitHub: https://github.com/mi2-warsaw/FSelectorRcpp +* Source code: https://github.com/cran/FSelectorRcpp +* Date/Publication: 2021-01-14 15:00:02 UTC +* Number of recursive dependencies: 157 + +Run `revdepcheck::cloud_details(, "FSelectorRcpp")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/FSelectorRcpp/new/FSelectorRcpp.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘FSelectorRcpp/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘FSelectorRcpp’ version ‘0.3.8’ +* package encoding: UTF-8 +* checking package namespace information ... 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 + ‘benchmarks_discretize.Rmd’ using ‘UTF-8’... OK + ‘get_started.Rmd’ using ‘UTF-8’... OK + ‘integer-variables.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 3 NOTEs + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/FSelectorRcpp/old/FSelectorRcpp.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘FSelectorRcpp/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘FSelectorRcpp’ version ‘0.3.8’ +* package encoding: UTF-8 +* checking package namespace information ... 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 + ‘benchmarks_discretize.Rmd’ using ‘UTF-8’... OK + ‘get_started.Rmd’ using ‘UTF-8’... OK + ‘integer-variables.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 3 NOTEs + + + + + +``` +# genekitr + +
+ +* Version: 1.1.3 +* GitHub: https://github.com/GangLiLab/genekitr +* Source code: https://github.com/cran/genekitr +* Date/Publication: 2023-03-01 09:00:02 UTC +* Number of recursive dependencies: 206 + +Run `revdepcheck::cloud_details(, "genekitr")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/genekitr/new/genekitr.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘genekitr/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘genekitr’ version ‘1.1.3’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘clusterProfiler’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/genekitr/old/genekitr.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘genekitr/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘genekitr’ version ‘1.1.3’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘clusterProfiler’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# geocmeans + +
+ +* Version: 0.3.3 +* GitHub: https://github.com/JeremyGelb/geocmeans +* Source code: https://github.com/cran/geocmeans +* Date/Publication: 2023-02-07 01:02:31 UTC +* Number of recursive dependencies: 197 + +Run `revdepcheck::cloud_details(, "geocmeans")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/geocmeans/new/geocmeans.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘geocmeans/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘geocmeans’ version ‘0.3.3’ +* package encoding: UTF-8 +* checking package namespace information ... OK +... +--- finished re-building ‘rasters.Rmd’ + +SUMMARY: processing the following file failed: + ‘introduction.Rmd’ + +Error: Vignette re-building failed. +Execution halted + +* DONE +Status: 2 ERRORs, 1 WARNING, 1 NOTE + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/geocmeans/old/geocmeans.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘geocmeans/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘geocmeans’ version ‘0.3.3’ +* package encoding: UTF-8 +* checking package namespace information ... OK +... +--- finished re-building ‘rasters.Rmd’ + +SUMMARY: processing the following file failed: + ‘introduction.Rmd’ + +Error: Vignette re-building failed. +Execution halted + +* DONE +Status: 2 ERRORs, 1 WARNING, 1 NOTE + + + + + +``` +# ggPMX + +
+ +* Version: 1.2.8 +* GitHub: https://github.com/ggPMXdevelopment/ggPMX +* Source code: https://github.com/cran/ggPMX +* Date/Publication: 2022-06-17 23:10:02 UTC +* Number of recursive dependencies: 177 + +Run `revdepcheck::cloud_details(, "ggPMX")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/ggPMX/new/ggPMX.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘ggPMX/DESCRIPTION’ ... OK +* this is package ‘ggPMX’ version ‘1.2.8’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... NOTE +... + [ FAIL 1 | WARN 14 | SKIP 8 | PASS 327 ] + 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 ... NONE + ‘ggPMX-guide.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 1 ERROR, 2 NOTEs + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/ggPMX/old/ggPMX.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘ggPMX/DESCRIPTION’ ... OK +* this is package ‘ggPMX’ version ‘1.2.8’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... NOTE +... + [ FAIL 1 | WARN 14 | SKIP 8 | PASS 327 ] + 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 ... NONE + ‘ggPMX-guide.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 1 ERROR, 2 NOTEs + + + + + +``` +# ggstatsplot + +
+ +* Version: 0.11.0 +* GitHub: https://github.com/IndrajeetPatil/ggstatsplot +* Source code: https://github.com/cran/ggstatsplot +* Date/Publication: 2023-02-15 15:30:02 UTC +* Number of recursive dependencies: 169 + +Run `revdepcheck::cloud_details(, "ggstatsplot")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/ggstatsplot/new/ggstatsplot.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘ggstatsplot/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘ggstatsplot’ version ‘0.11.0’ +* package encoding: UTF-8 +* checking package namespace information ... 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 + ‘additional.Rmd’ using ‘UTF-8’... OK + ‘ggstatsplot.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 1 NOTE + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/ggstatsplot/old/ggstatsplot.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘ggstatsplot/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘ggstatsplot’ version ‘0.11.0’ +* package encoding: UTF-8 +* checking package namespace information ... 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 + ‘additional.Rmd’ using ‘UTF-8’... OK + ‘ggstatsplot.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 1 NOTE + + + + + +``` +# healthyR.ai + +
+ +* Version: 0.0.12 +* GitHub: https://github.com/spsanderson/healthyR.ai +* Source code: https://github.com/cran/healthyR.ai +* Date/Publication: 2023-02-01 18:40:06 UTC +* Number of recursive dependencies: 189 + +Run `revdepcheck::cloud_details(, "healthyR.ai")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/healthyR.ai/new/healthyR.ai.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘healthyR.ai/DESCRIPTION’ ... OK +* this is package ‘healthyR.ai’ version ‘0.0.12’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... 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 + ‘auto-kmeans.Rmd’ using ‘UTF-8’... OK + ‘getting-started.Rmd’ using ‘UTF-8’... OK + ‘kmeans-umap.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: OK + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/healthyR.ai/old/healthyR.ai.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘healthyR.ai/DESCRIPTION’ ... OK +* this is package ‘healthyR.ai’ version ‘0.0.12’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... 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 + ‘auto-kmeans.Rmd’ using ‘UTF-8’... OK + ‘getting-started.Rmd’ using ‘UTF-8’... OK + ‘kmeans-umap.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: OK + + + + + +``` +# healthyR.ts + +
+ +* Version: 0.2.7 +* GitHub: https://github.com/spsanderson/healthyR.ts +* Source code: https://github.com/cran/healthyR.ts +* Date/Publication: 2023-01-28 14:50:02 UTC +* Number of recursive dependencies: 191 + +Run `revdepcheck::cloud_details(, "healthyR.ts")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/healthyR.ts/new/healthyR.ts.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘healthyR.ts/DESCRIPTION’ ... OK +* this is package ‘healthyR.ts’ version ‘0.2.7’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... 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 + ‘using-tidy-fft.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 1 NOTE + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/healthyR.ts/old/healthyR.ts.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘healthyR.ts/DESCRIPTION’ ... OK +* this is package ‘healthyR.ts’ version ‘0.2.7’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... 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 + ‘using-tidy-fft.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 1 NOTE + + + + + +``` +# healthyverse + +
+ +* Version: 1.0.3 +* GitHub: https://github.com/spsanderson/healthyverse +* Source code: https://github.com/cran/healthyverse +* Date/Publication: 2023-02-21 20:40:02 UTC +* Number of recursive dependencies: 207 + +Run `revdepcheck::cloud_details(, "healthyverse")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/healthyverse/new/healthyverse.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘healthyverse/DESCRIPTION’ ... OK +* this is package ‘healthyverse’ version ‘1.0.3’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... 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 +* DONE +Status: 1 NOTE + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/healthyverse/old/healthyverse.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘healthyverse/DESCRIPTION’ ... OK +* this is package ‘healthyverse’ version ‘1.0.3’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... 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 +* DONE +Status: 1 NOTE + + + + + +``` +# historicalborrowlong + +
+ +* Version: 0.0.5 +* GitHub: https://github.com/wlandau/historicalborrowlong +* Source code: https://github.com/cran/historicalborrowlong +* Date/Publication: 2022-09-13 10:20:06 UTC +* Number of recursive dependencies: 107 + +Run `revdepcheck::cloud_details(, "historicalborrowlong")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/historicalborrowlong/new/historicalborrowlong.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘historicalborrowlong/DESCRIPTION’ ... OK +* this is package ‘historicalborrowlong’ version ‘0.0.5’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Packages required but not available: 'rstan', 'trialr' + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/historicalborrowlong/old/historicalborrowlong.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘historicalborrowlong/DESCRIPTION’ ... OK +* this is package ‘historicalborrowlong’ version ‘0.0.5’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Packages required but not available: 'rstan', 'trialr' + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# immcp + +
+ +* Version: 1.0.3 +* GitHub: https://github.com/YuanlongHu/immcp +* Source code: https://github.com/cran/immcp +* Date/Publication: 2022-05-12 05:50:02 UTC +* Number of recursive dependencies: 194 + +Run `revdepcheck::cloud_details(, "immcp")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/immcp/new/immcp.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘immcp/DESCRIPTION’ ... OK +* this is package ‘immcp’ version ‘1.0.3’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘clusterProfiler’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/immcp/old/immcp.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘immcp/DESCRIPTION’ ... OK +* this is package ‘immcp’ version ‘1.0.3’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘clusterProfiler’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# ImputeRobust + +
+ +* Version: 1.3-1 +* GitHub: NA +* Source code: https://github.com/cran/ImputeRobust +* Date/Publication: 2018-11-30 12:10:03 UTC +* Number of recursive dependencies: 41 + +Run `revdepcheck::cloud_details(, "ImputeRobust")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/ImputeRobust/new/ImputeRobust.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘ImputeRobust/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘ImputeRobust’ version ‘1.3-1’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘extremevalues’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/ImputeRobust/old/ImputeRobust.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘ImputeRobust/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘ImputeRobust’ version ‘1.3-1’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘extremevalues’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# INSPECTumours + +
+ +* Version: 0.1.0 +* GitHub: NA +* Source code: https://github.com/cran/INSPECTumours +* Date/Publication: 2022-05-06 12:10:02 UTC +* Number of recursive dependencies: 175 + +Run `revdepcheck::cloud_details(, "INSPECTumours")` for more info + +
+ +## In both + +* checking whether package ‘INSPECTumours’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/INSPECTumours/new/INSPECTumours.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘INSPECTumours’ ... +** package ‘INSPECTumours’ 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 <- imp[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + there is no package called ‘rstan’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Execution halted +ERROR: lazy loading failed for package ‘INSPECTumours’ +* removing ‘/tmp/workdir/INSPECTumours/new/INSPECTumours.Rcheck/INSPECTumours’ + + +``` +### CRAN + +``` +* installing *source* package ‘INSPECTumours’ ... +** package ‘INSPECTumours’ 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 <- imp[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + there is no package called ‘rstan’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Execution halted +ERROR: lazy loading failed for package ‘INSPECTumours’ +* removing ‘/tmp/workdir/INSPECTumours/old/INSPECTumours.Rcheck/INSPECTumours’ + + +``` +# intRinsic + +
+ +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/intRinsic +* Number of recursive dependencies: 64 + +Run `revdepcheck::cloud_details(, "intRinsic")` for more info + +
+ +## Error before installation + +### Devel + +``` + + + + + + +``` +### CRAN + +``` + + + + + + +``` +# IPDFileCheck + +
+ +* Version: 0.7.5 +* GitHub: NA +* Source code: https://github.com/cran/IPDFileCheck +* Date/Publication: 2022-02-01 08:00:10 UTC +* Number of recursive dependencies: 150 + +Run `revdepcheck::cloud_details(, "IPDFileCheck")` for more info + +
+ +## In both + +* checking whether package ‘IPDFileCheck’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/IPDFileCheck/new/IPDFileCheck.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘IPDFileCheck’ ... +** package ‘IPDFileCheck’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** inst +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + there is no package called ‘tibble’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Execution halted +ERROR: lazy loading failed for package ‘IPDFileCheck’ +* removing ‘/tmp/workdir/IPDFileCheck/new/IPDFileCheck.Rcheck/IPDFileCheck’ + + +``` +### CRAN + +``` +* installing *source* package ‘IPDFileCheck’ ... +** package ‘IPDFileCheck’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** inst +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + there is no package called ‘tibble’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Execution halted +ERROR: lazy loading failed for package ‘IPDFileCheck’ +* removing ‘/tmp/workdir/IPDFileCheck/old/IPDFileCheck.Rcheck/IPDFileCheck’ + + +``` +# IRexamples + +
+ +* Version: 0.0.2 +* GitHub: https://github.com/vinhdizzo/IRexamples +* Source code: https://github.com/cran/IRexamples +* Date/Publication: 2022-08-15 07:10:19 UTC +* Number of recursive dependencies: 184 + +Run `revdepcheck::cloud_details(, "IRexamples")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/IRexamples/new/IRexamples.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘IRexamples/DESCRIPTION’ ... OK +* this is package ‘IRexamples’ version ‘0.0.2’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘rstanarm’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/IRexamples/old/IRexamples.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘IRexamples/DESCRIPTION’ ... OK +* this is package ‘IRexamples’ version ‘0.0.2’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘rstanarm’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# irtQ + +
+ +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/irtQ +* Number of recursive dependencies: 59 + +Run `revdepcheck::cloud_details(, "irtQ")` for more info + +
+ +## Error before installation + +### Devel + +``` + + + + + + +``` +### CRAN + +``` + + + + + + +``` +# IsoCorrectoR + +
+ +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/IsoCorrectoR +* Number of recursive dependencies: 70 + +Run `revdepcheck::cloud_details(, "IsoCorrectoR")` for more info + +
+ +## Error before installation + +### Devel + +``` + + + + + + +``` +### CRAN + +``` + + + + + + +``` +# journalabbr + +
+ +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/journalabbr +* Number of recursive dependencies: 72 + +Run `revdepcheck::cloud_details(, "journalabbr")` for more info + +
+ +## Error before installation + +### Devel + +``` + + + + + + +``` +### CRAN + +``` + + + + + + +``` +# l1spectral + +
+ +* Version: 0.99.6 +* GitHub: NA +* Source code: https://github.com/cran/l1spectral +* Date/Publication: 2022-01-26 17:12:46 UTC +* Number of recursive dependencies: 83 + +Run `revdepcheck::cloud_details(, "l1spectral")` for more info + +
+ +## In both + +* checking whether package ‘l1spectral’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/l1spectral/new/l1spectral.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘l1spectral’ ... +** package ‘l1spectral’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +g++ -std=gnu++14 -I"/opt/R/4.1.1/lib/R/include" -DNDEBUG -I'/opt/R/4.1.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.1.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +g++ -std=gnu++14 -I"/opt/R/4.1.1/lib/R/include" -DNDEBUG -I'/opt/R/4.1.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.1.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c grahm_schmidtCpp.cpp -o grahm_schmidtCpp.o +g++ -std=gnu++14 -shared -L/opt/R/4.1.1/lib/R/lib -L/usr/local/lib -o l1spectral.so RcppExports.o grahm_schmidtCpp.o -llapack -lblas -lgfortran -lm -lquadmath -L/opt/R/4.1.1/lib/R/lib -lR +installing to /tmp/workdir/l1spectral/new/l1spectral.Rcheck/00LOCK-l1spectral/00new/l1spectral/libs +** 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]]) : + there is no package called ‘pROC’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Execution halted +ERROR: lazy loading failed for package ‘l1spectral’ +* removing ‘/tmp/workdir/l1spectral/new/l1spectral.Rcheck/l1spectral’ + + +``` +### CRAN + +``` +* installing *source* package ‘l1spectral’ ... +** package ‘l1spectral’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +g++ -std=gnu++14 -I"/opt/R/4.1.1/lib/R/include" -DNDEBUG -I'/opt/R/4.1.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.1.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +g++ -std=gnu++14 -I"/opt/R/4.1.1/lib/R/include" -DNDEBUG -I'/opt/R/4.1.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.1.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c grahm_schmidtCpp.cpp -o grahm_schmidtCpp.o +g++ -std=gnu++14 -shared -L/opt/R/4.1.1/lib/R/lib -L/usr/local/lib -o l1spectral.so RcppExports.o grahm_schmidtCpp.o -llapack -lblas -lgfortran -lm -lquadmath -L/opt/R/4.1.1/lib/R/lib -lR +installing to /tmp/workdir/l1spectral/old/l1spectral.Rcheck/00LOCK-l1spectral/00new/l1spectral/libs +** 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]]) : + there is no package called ‘pROC’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Execution halted +ERROR: lazy loading failed for package ‘l1spectral’ +* removing ‘/tmp/workdir/l1spectral/old/l1spectral.Rcheck/l1spectral’ + + +``` +# lifeR + +
+ +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/lifeR +* Number of recursive dependencies: 92 + +Run `revdepcheck::cloud_details(, "lifeR")` for more info + +
+ +## Error before installation + +### Devel + +``` + + + + + + +``` +### CRAN + +``` + + + + + + +``` +# loon.ggplot + +
+ +* Version: 1.3.3 +* GitHub: https://github.com/great-northern-diver/loon.ggplot +* Source code: https://github.com/cran/loon.ggplot +* Date/Publication: 2022-11-12 22:30:02 UTC +* Number of recursive dependencies: 104 + +Run `revdepcheck::cloud_details(, "loon.ggplot")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/loon.ggplot/new/loon.ggplot.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘loon.ggplot/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘loon.ggplot’ version ‘1.3.3’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘loon’ + +Package suggested but not available for checking: ‘zenplots’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/loon.ggplot/old/loon.ggplot.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘loon.ggplot/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘loon.ggplot’ version ‘1.3.3’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘loon’ + +Package suggested but not available for checking: ‘zenplots’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# loon.shiny + +
+ +* Version: 1.0.3 +* GitHub: NA +* Source code: https://github.com/cran/loon.shiny +* Date/Publication: 2022-10-08 15:30:02 UTC +* Number of recursive dependencies: 136 + +Run `revdepcheck::cloud_details(, "loon.shiny")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/loon.shiny/new/loon.shiny.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘loon.shiny/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘loon.shiny’ version ‘1.0.3’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Packages required but not available: 'loon', 'loon.ggplot' + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/loon.shiny/old/loon.shiny.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘loon.shiny/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘loon.shiny’ version ‘1.0.3’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Packages required but not available: 'loon', 'loon.ggplot' + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# MACP + +
+ +* Version: 0.1.0 +* GitHub: https://github.com/mrbakhsh/MACP +* Source code: https://github.com/cran/MACP +* Date/Publication: 2023-02-28 17:32:30 UTC +* Number of recursive dependencies: 235 + +Run `revdepcheck::cloud_details(, "MACP")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/MACP/new/MACP.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘MACP/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘MACP’ version ‘0.1.0’ +* package encoding: UTF-8 +* checking package namespace information ... 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 + ‘MACP_tutorial.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 3 NOTEs + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/MACP/old/MACP.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘MACP/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘MACP’ version ‘0.1.0’ +* package encoding: UTF-8 +* checking package namespace information ... 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 + ‘MACP_tutorial.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 3 NOTEs + + + + + +``` +# mafs + +
+ +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/mafs +* Number of recursive dependencies: 90 + +Run `revdepcheck::cloud_details(, "mafs")` for more info + +
+ +## Error before installation + +### Devel + +``` + + + + + + +``` +### CRAN + +``` + + + + + + +``` +# MantaID + +
+ +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/MantaID +* Number of recursive dependencies: 152 + +Run `revdepcheck::cloud_details(, "MantaID")` for more info + +
+ +## Error before installation + +### Devel + +``` + + + + + + +``` +### CRAN + +``` + + + + + + +``` +# marginaleffects + +
+ +* Version: 0.10.0 +* GitHub: https://github.com/vincentarelbundock/marginaleffects +* Source code: https://github.com/cran/marginaleffects +* Date/Publication: 2023-02-22 09:00:02 UTC +* Number of recursive dependencies: 366 + +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.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘marginaleffects/DESCRIPTION’ ... OK +* this is package ‘marginaleffects’ version ‘0.10.0’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... NOTE +... +* checking Rd \usage sections ... OK +* checking Rd contents ... OK +* checking for unstated dependencies in examples ... OK +* checking examples ... OK +* checking for unstated dependencies in ‘tests’ ... OK +* checking tests ... OK + Running ‘spelling.R’ + Running ‘tinytest.R’ +* DONE +Status: 1 NOTE + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/marginaleffects/old/marginaleffects.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘marginaleffects/DESCRIPTION’ ... OK +* this is package ‘marginaleffects’ version ‘0.10.0’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... NOTE +... +* checking Rd \usage sections ... OK +* checking Rd contents ... OK +* checking for unstated dependencies in examples ... OK +* checking examples ... OK +* checking for unstated dependencies in ‘tests’ ... OK +* checking tests ... OK + Running ‘spelling.R’ + Running ‘tinytest.R’ +* DONE +Status: 1 NOTE + + + + + +``` +# MazamaCoreUtils + +
+ +* Version: 0.4.13 +* GitHub: https://github.com/MazamaScience/MazamaCoreUtils +* Source code: https://github.com/cran/MazamaCoreUtils +* Date/Publication: 2022-08-24 23:12:34 UTC +* Number of recursive dependencies: 108 + +Run `revdepcheck::cloud_details(, "MazamaCoreUtils")` for more info + +
+ +## In both + +* checking whether package ‘MazamaCoreUtils’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/MazamaCoreUtils/new/MazamaCoreUtils.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘MazamaCoreUtils’ ... +** package ‘MazamaCoreUtils’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** inst +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + there is no package called ‘formatR’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Execution halted +ERROR: lazy loading failed for package ‘MazamaCoreUtils’ +* removing ‘/tmp/workdir/MazamaCoreUtils/new/MazamaCoreUtils.Rcheck/MazamaCoreUtils’ + + +``` +### CRAN + +``` +* installing *source* package ‘MazamaCoreUtils’ ... +** package ‘MazamaCoreUtils’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** inst +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + there is no package called ‘formatR’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Execution halted +ERROR: lazy loading failed for package ‘MazamaCoreUtils’ +* removing ‘/tmp/workdir/MazamaCoreUtils/old/MazamaCoreUtils.Rcheck/MazamaCoreUtils’ + + +``` +# mbRes + +
+ +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/mbRes +* Number of recursive dependencies: 40 + +Run `revdepcheck::cloud_details(, "mbRes")` for more info + +
+ +## Error before installation + +### Devel + +``` + + + + + + +``` +### CRAN + +``` + + + + + + +``` +# merTools + +
+ +* Version: 0.5.2 +* GitHub: NA +* Source code: https://github.com/cran/merTools +* Date/Publication: 2020-06-23 10:30:12 UTC +* Number of recursive dependencies: 143 + +Run `revdepcheck::cloud_details(, "merTools")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/merTools/new/merTools.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘merTools/DESCRIPTION’ ... OK +* this is package ‘merTools’ version ‘0.5.2’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... NOTE +... +* checking for unstated dependencies in vignettes ... OK +* checking package vignettes in ‘inst/doc’ ... OK +* checking running R code from vignettes ... NONE + ‘Using_predictInterval.Rmd’ using ‘UTF-8’... OK + ‘imputation.Rmd’ using ‘UTF-8’... OK + ‘marginal_effects.Rmd’ using ‘UTF-8’... OK + ‘merToolsIntro.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 1 NOTE + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/merTools/old/merTools.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘merTools/DESCRIPTION’ ... OK +* this is package ‘merTools’ version ‘0.5.2’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... NOTE +... +* checking for unstated dependencies in vignettes ... OK +* checking package vignettes in ‘inst/doc’ ... OK +* checking running R code from vignettes ... NONE + ‘Using_predictInterval.Rmd’ using ‘UTF-8’... OK + ‘imputation.Rmd’ using ‘UTF-8’... OK + ‘marginal_effects.Rmd’ using ‘UTF-8’... OK + ‘merToolsIntro.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 1 NOTE + + + + + +``` +# microservices + +
+ +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/microservices +* Number of recursive dependencies: 70 + +Run `revdepcheck::cloud_details(, "microservices")` for more info + +
+ +## Error before installation + +### Devel + +``` + + + + + + +``` +### CRAN + +``` + + + + + + +``` +# modeltime + +
+ +* Version: 1.2.5 +* GitHub: https://github.com/business-science/modeltime +* Source code: https://github.com/cran/modeltime +* Date/Publication: 2023-02-07 19:32:30 UTC +* Number of recursive dependencies: 253 + +Run `revdepcheck::cloud_details(, "modeltime")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/modeltime/new/modeltime.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘modeltime/DESCRIPTION’ ... OK +* this is package ‘modeltime’ version ‘1.2.5’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘prophet’ + +Package suggested but not available for checking: ‘rstan’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/modeltime/old/modeltime.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘modeltime/DESCRIPTION’ ... OK +* this is package ‘modeltime’ version ‘1.2.5’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘prophet’ + +Package suggested but not available for checking: ‘rstan’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# modeltime.ensemble + +
+ +* Version: 1.0.2 +* GitHub: https://github.com/business-science/modeltime.ensemble +* Source code: https://github.com/cran/modeltime.ensemble +* Date/Publication: 2022-10-18 23:02:40 UTC +* Number of recursive dependencies: 223 + +Run `revdepcheck::cloud_details(, "modeltime.ensemble")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/modeltime.ensemble/new/modeltime.ensemble.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘modeltime.ensemble/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘modeltime.ensemble’ version ‘1.0.2’ +* package encoding: UTF-8 +* checking package namespace information ... OK +... +--- finished re-building ‘recursive-ensembles.Rmd’ + +SUMMARY: processing the following file failed: + ‘getting-started-with-modeltime-ensemble.Rmd’ + +Error: Vignette re-building failed. +Execution halted + +* DONE +Status: 1 ERROR, 1 WARNING, 1 NOTE + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/modeltime.ensemble/old/modeltime.ensemble.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘modeltime.ensemble/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘modeltime.ensemble’ version ‘1.0.2’ +* package encoding: UTF-8 +* checking package namespace information ... OK +... +--- finished re-building ‘recursive-ensembles.Rmd’ + +SUMMARY: processing the following file failed: + ‘getting-started-with-modeltime-ensemble.Rmd’ + +Error: Vignette re-building failed. +Execution halted + +* DONE +Status: 1 ERROR, 1 WARNING, 1 NOTE + + + + + +``` +# modeltime.gluonts + +
+ +* Version: 0.1.0 +* GitHub: https://github.com/business-science/modeltime.gluonts +* Source code: https://github.com/cran/modeltime.gluonts +* Date/Publication: 2020-11-30 09:40:02 UTC +* Number of recursive dependencies: 214 + +Run `revdepcheck::cloud_details(, "modeltime.gluonts")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/modeltime.gluonts/new/modeltime.gluonts.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘modeltime.gluonts/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘modeltime.gluonts’ version ‘0.1.0’ +* package encoding: UTF-8 +* checking package namespace information ... 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 + ‘getting-started.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 1 NOTE + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/modeltime.gluonts/old/modeltime.gluonts.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘modeltime.gluonts/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘modeltime.gluonts’ version ‘0.1.0’ +* package encoding: UTF-8 +* checking package namespace information ... 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 + ‘getting-started.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 1 NOTE + + + + + +``` +# modeltime.h2o + +
+ +* Version: 0.1.1 +* GitHub: https://github.com/business-science/modeltime.h2o +* Source code: https://github.com/cran/modeltime.h2o +* Date/Publication: 2021-04-05 14:40:03 UTC +* Number of recursive dependencies: 214 + +Run `revdepcheck::cloud_details(, "modeltime.h2o")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/modeltime.h2o/new/modeltime.h2o.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘modeltime.h2o/DESCRIPTION’ ... OK +* this is package ‘modeltime.h2o’ version ‘0.1.1’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... OK +... +* checking for code/documentation mismatches ... OK +* checking Rd \usage sections ... OK +* checking Rd contents ... OK +* checking for unstated dependencies in examples ... 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/modeltime.h2o/old/modeltime.h2o.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘modeltime.h2o/DESCRIPTION’ ... OK +* this is package ‘modeltime.h2o’ version ‘0.1.1’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... OK +... +* checking for code/documentation mismatches ... OK +* checking Rd \usage sections ... OK +* checking Rd contents ... OK +* checking for unstated dependencies in examples ... OK +* checking examples ... OK +* checking for unstated dependencies in ‘tests’ ... OK +* checking tests ... OK + Running ‘testthat.R’ +* DONE +Status: OK + + + + + +``` +# modeltime.resample + +
+ +* Version: 0.2.2 +* GitHub: https://github.com/business-science/modeltime.resample +* Source code: https://github.com/cran/modeltime.resample +* Date/Publication: 2022-10-18 03:00:06 UTC +* Number of recursive dependencies: 221 + +Run `revdepcheck::cloud_details(, "modeltime.resample")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/modeltime.resample/new/modeltime.resample.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘modeltime.resample/DESCRIPTION’ ... OK +* this is package ‘modeltime.resample’ version ‘0.2.2’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... OK +... +--- failed re-building ‘panel-data.Rmd’ + +SUMMARY: processing the following file failed: + ‘panel-data.Rmd’ + +Error: Vignette re-building failed. +Execution halted + +* DONE +Status: 1 ERROR, 1 WARNING, 1 NOTE + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/modeltime.resample/old/modeltime.resample.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘modeltime.resample/DESCRIPTION’ ... OK +* this is package ‘modeltime.resample’ version ‘0.2.2’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... OK +... +--- failed re-building ‘panel-data.Rmd’ + +SUMMARY: processing the following file failed: + ‘panel-data.Rmd’ + +Error: Vignette re-building failed. +Execution halted + +* DONE +Status: 1 ERROR, 1 WARNING, 1 NOTE + + + + + +``` +# moexer + +
+ +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/moexer +* Number of recursive dependencies: 86 + +Run `revdepcheck::cloud_details(, "moexer")` for more info + +
+ +## Error before installation + +### Devel + +``` + + + + + + +``` +### CRAN + +``` + + + + + + +``` +# mpower + +
+ +* Version: 0.1.0 +* GitHub: NA +* Source code: https://github.com/cran/mpower +* Date/Publication: 2022-09-21 08:50:05 UTC +* Number of recursive dependencies: 132 + +Run `revdepcheck::cloud_details(, "mpower")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/mpower/new/mpower.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘mpower/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘mpower’ version ‘0.1.0’ +* package encoding: UTF-8 +* checking package namespace information ... 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 + +``` +* using log directory ‘/tmp/workdir/mpower/old/mpower.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘mpower/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘mpower’ version ‘0.1.0’ +* package encoding: UTF-8 +* checking package namespace information ... 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 + + + + + +``` +# multibiasmeta + +
+ +* Version: 0.1.0 +* GitHub: https://github.com/mathurlabstanford/multibiasmeta +* Source code: https://github.com/cran/multibiasmeta +* Date/Publication: 2023-02-08 09:40:02 UTC +* Number of recursive dependencies: 99 + +Run `revdepcheck::cloud_details(, "multibiasmeta")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/multibiasmeta/new/multibiasmeta.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘multibiasmeta/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘multibiasmeta’ version ‘0.1.0’ +* package encoding: UTF-8 +* checking package namespace information ... OK +... +--- failed re-building ‘tutorial.Rmd’ + +SUMMARY: processing the following file failed: + ‘tutorial.Rmd’ + +Error: Vignette re-building failed. +Execution halted + +* DONE +Status: 1 WARNING, 1 NOTE + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/multibiasmeta/old/multibiasmeta.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘multibiasmeta/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘multibiasmeta’ version ‘0.1.0’ +* package encoding: UTF-8 +* checking package namespace information ... OK +... +--- failed re-building ‘tutorial.Rmd’ + +SUMMARY: processing the following file failed: + ‘tutorial.Rmd’ + +Error: Vignette re-building failed. +Execution halted + +* DONE +Status: 1 WARNING, 1 NOTE + + + + + +``` +# 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: 99 + +Run `revdepcheck::cloud_details(, "NetFACS")` for more info + +
+ +## In both + +* checking whether package ‘NetFACS’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/NetFACS/new/NetFACS.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘NetFACS’ ... +** package ‘NetFACS’ 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 ‘R6’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Execution halted +ERROR: lazy loading failed for package ‘NetFACS’ +* removing ‘/tmp/workdir/NetFACS/new/NetFACS.Rcheck/NetFACS’ + + +``` +### CRAN + +``` +* installing *source* package ‘NetFACS’ ... +** package ‘NetFACS’ 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 ‘R6’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Execution halted +ERROR: lazy loading failed for package ‘NetFACS’ +* removing ‘/tmp/workdir/NetFACS/old/NetFACS.Rcheck/NetFACS’ + + +``` +# nlmixr2extra + +
+ +* Version: 2.0.8 +* GitHub: https://github.com/nlmixr2/nlmixr2extra +* Source code: https://github.com/cran/nlmixr2extra +* Date/Publication: 2022-10-22 22:32:34 UTC +* Number of recursive dependencies: 203 + +Run `revdepcheck::cloud_details(, "nlmixr2extra")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/nlmixr2extra/new/nlmixr2extra.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘nlmixr2extra/DESCRIPTION’ ... OK +* this is package ‘nlmixr2extra’ version ‘2.0.8’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Packages required but not available: 'nlmixr2est', 'symengine' + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/nlmixr2extra/old/nlmixr2extra.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘nlmixr2extra/DESCRIPTION’ ... OK +* this is package ‘nlmixr2extra’ version ‘2.0.8’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Packages required but not available: 'nlmixr2est', 'symengine' + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# nlmixr2plot + +
+ +* Version: 2.0.7 +* GitHub: https://github.com/nlmixr2/nlmixr2plot +* Source code: https://github.com/cran/nlmixr2plot +* Date/Publication: 2022-10-20 03:12:36 UTC +* Number of recursive dependencies: 166 + +Run `revdepcheck::cloud_details(, "nlmixr2plot")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/nlmixr2plot/new/nlmixr2plot.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘nlmixr2plot/DESCRIPTION’ ... OK +* this is package ‘nlmixr2plot’ version ‘2.0.7’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Packages required but not available: 'nlmixr2est', 'nlmixr2extra' + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/nlmixr2plot/old/nlmixr2plot.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘nlmixr2plot/DESCRIPTION’ ... OK +* this is package ‘nlmixr2plot’ version ‘2.0.7’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Packages required but not available: 'nlmixr2est', 'nlmixr2extra' + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# nlmixr2rpt + +
+ +* Version: 0.1.0 +* GitHub: https://github.com/nlmixr2/nlmixr2rpt +* Source code: https://github.com/cran/nlmixr2rpt +* Date/Publication: 2022-12-05 10:40:02 UTC +* Number of recursive dependencies: 221 + +Run `revdepcheck::cloud_details(, "nlmixr2rpt")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/nlmixr2rpt/new/nlmixr2rpt.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘nlmixr2rpt/DESCRIPTION’ ... OK +* this is package ‘nlmixr2rpt’ version ‘0.1.0’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Packages required but not available: 'nlmixr2extra', 'xpose.nlmixr2' + +Package suggested but not available for checking: ‘nlmixr2’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/nlmixr2rpt/old/nlmixr2rpt.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘nlmixr2rpt/DESCRIPTION’ ... OK +* this is package ‘nlmixr2rpt’ version ‘0.1.0’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Packages required but not available: 'nlmixr2extra', 'xpose.nlmixr2' + +Package suggested but not available for checking: ‘nlmixr2’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# numbat + +
+ +* Version: 1.2.2 +* GitHub: https://github.com/kharchenkolab/numbat +* Source code: https://github.com/cran/numbat +* Date/Publication: 2023-02-14 18:20:02 UTC +* Number of recursive dependencies: 132 + +Run `revdepcheck::cloud_details(, "numbat")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/numbat/new/numbat.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘numbat/DESCRIPTION’ ... OK +* this is package ‘numbat’ version ‘1.2.2’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Packages required but not available: 'ggtree', 'scistreer' + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/numbat/old/numbat.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘numbat/DESCRIPTION’ ... OK +* this is package ‘numbat’ version ‘1.2.2’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Packages required but not available: 'ggtree', 'scistreer' + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# OBL + +
+ +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/OBL +* Number of recursive dependencies: 73 + +Run `revdepcheck::cloud_details(, "OBL")` for more info + +
+ +## Error before installation + +### Devel + +``` + + + + + + +``` +### CRAN + +``` + + + + + + +``` +# OlinkAnalyze + +
+ +* Version: 3.3.1 +* GitHub: NA +* Source code: https://github.com/cran/OlinkAnalyze +* Date/Publication: 2023-02-27 20:22:30 UTC +* Number of recursive dependencies: 202 + +Run `revdepcheck::cloud_details(, "OlinkAnalyze")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/OlinkAnalyze/new/OlinkAnalyze.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘OlinkAnalyze/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘OlinkAnalyze’ version ‘3.3.1’ +* package encoding: UTF-8 +* checking package namespace information ... 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 + ‘Vignett.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 1 NOTE + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/OlinkAnalyze/old/OlinkAnalyze.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘OlinkAnalyze/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘OlinkAnalyze’ version ‘3.3.1’ +* package encoding: UTF-8 +* checking package namespace information ... 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 + ‘Vignett.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 1 NOTE + + + + + +``` +# OncoBayes2 + +
+ +* Version: 0.8-8 +* GitHub: NA +* Source code: https://github.com/cran/OncoBayes2 +* Date/Publication: 2023-03-03 22:50:15 UTC +* Number of recursive dependencies: 100 + +Run `revdepcheck::cloud_details(, "OncoBayes2")` for more info + +
+ +## In both + +* checking whether package ‘OncoBayes2’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/OncoBayes2/new/OncoBayes2.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘OncoBayes2’ ... +** package ‘OncoBayes2’ successfully unpacked and MD5 sums checked +** using staged installation +Info: Found int division at 'string', line 82, column 14 to column 21: + current / base +Values will be rounded towards zero. If rounding is not desired you can write +the division as + current * 1.0 / base +If rounding is intended please use the integer division operator %/%. +Info: Found int division at 'string', line 175, column 14 to column 36: +... +/opt/R/4.1.1/lib/R/site-library/RcppEigen/include/Eigen/src/Core/ProductEvaluators.h:251:23: required from ‘static void Eigen::internal::generic_product_impl::evalTo(Dst&, const Lhs&, const Rhs&) [with Dst = Eigen::Matrix; Lhs = Eigen::Product, const Eigen::CwiseNullaryOp, const Eigen::Matrix >, const Eigen::Transpose > >, Eigen::Matrix, 0>; Rhs = Eigen::Matrix]’ +/opt/R/4.1.1/lib/R/site-library/RcppEigen/include/Eigen/src/Core/ProductEvaluators.h:124:75: required from ‘Eigen::internal::product_evaluator, ProductTag, LhsShape, RhsShape>::product_evaluator(const XprType&) [with Lhs = Eigen::Product, const Eigen::CwiseNullaryOp, const Eigen::Matrix >, const Eigen::Transpose > >, Eigen::Matrix, 0>; Rhs = Eigen::Matrix; int Options = 0; int ProductTag = 6; LhsShape = Eigen::DenseShape; RhsShape = Eigen::DenseShape; typename Eigen::internal::traits::Rhs>::Scalar = double; typename Eigen::internal::traits::Lhs>::Scalar = double; Eigen::internal::product_evaluator, ProductTag, LhsShape, RhsShape>::XprType = Eigen::Product, const Eigen::CwiseNullaryOp, const Eigen::Matrix >, const Eigen::Transpose > >, Eigen::Matrix, 0>, Eigen::Matrix, 0>]’ +/opt/R/4.1.1/lib/R/site-library/RcppEigen/include/Eigen/src/Core/ProductEvaluators.h:35:90: required from ‘Eigen::internal::evaluator >::evaluator(const XprType&) [with Lhs = Eigen::Product, const Eigen::CwiseNullaryOp, const Eigen::Matrix >, const Eigen::Transpose > >, Eigen::Matrix, 0>; Rhs = Eigen::Matrix; int Options = 0; Eigen::internal::evaluator >::XprType = Eigen::Product, const Eigen::CwiseNullaryOp, const Eigen::Matrix >, const Eigen::Transpose > >, Eigen::Matrix, 0>, Eigen::Matrix, 0>]’ +/opt/R/4.1.1/lib/R/site-library/RcppEigen/include/Eigen/src/Core/Product.h:132:22: required from ‘Eigen::internal::dense_product_base::operator const Scalar() const [with Lhs = Eigen::Product, const Eigen::CwiseNullaryOp, const Eigen::Matrix >, const Eigen::Transpose > >, Eigen::Matrix, 0>; Rhs = Eigen::Matrix; int Option = 0; Eigen::internal::dense_product_base::Scalar = double]’ +/opt/R/4.1.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_blrm_exnex_namespace::model_blrm_exnex; BaseRNG = boost::random::additive_combine_engine, boost::random::linear_congruential_engine >]’ +/opt/R/4.1.1/lib/R/site-library/StanHeaders/include/src/stan/mcmc/hmc/hamiltonians/dense_e_metric.hpp:21:10: required from here +/opt/R/4.1.1/lib/R/site-library/RcppEigen/include/Eigen/src/Core/DenseCoeffsBase.h:55:30: warning: ignoring attributes on template argument ‘Eigen::internal::packet_traits::type’ {aka ‘__vector(2) double’} [-Wignored-attributes] +make: *** [/opt/R/4.1.1/lib/R/etc/Makeconf:175: stanExports_blrm_exnex.o] Error 1 +ERROR: compilation failed for package ‘OncoBayes2’ +* removing ‘/tmp/workdir/OncoBayes2/new/OncoBayes2.Rcheck/OncoBayes2’ + + +``` +### CRAN + +``` +* installing *source* package ‘OncoBayes2’ ... +** package ‘OncoBayes2’ successfully unpacked and MD5 sums checked +** using staged installation +Info: Found int division at 'string', line 82, column 14 to column 21: + current / base +Values will be rounded towards zero. If rounding is not desired you can write +the division as + current * 1.0 / base +If rounding is intended please use the integer division operator %/%. +Info: Found int division at 'string', line 175, column 14 to column 36: +... +/opt/R/4.1.1/lib/R/site-library/RcppEigen/include/Eigen/src/Core/ProductEvaluators.h:251:23: required from ‘static void Eigen::internal::generic_product_impl::evalTo(Dst&, const Lhs&, const Rhs&) [with Dst = Eigen::Matrix; Lhs = Eigen::Product, const Eigen::CwiseNullaryOp, const Eigen::Matrix >, const Eigen::Transpose > >, Eigen::Matrix, 0>; Rhs = Eigen::Matrix]’ +/opt/R/4.1.1/lib/R/site-library/RcppEigen/include/Eigen/src/Core/ProductEvaluators.h:124:75: required from ‘Eigen::internal::product_evaluator, ProductTag, LhsShape, RhsShape>::product_evaluator(const XprType&) [with Lhs = Eigen::Product, const Eigen::CwiseNullaryOp, const Eigen::Matrix >, const Eigen::Transpose > >, Eigen::Matrix, 0>; Rhs = Eigen::Matrix; int Options = 0; int ProductTag = 6; LhsShape = Eigen::DenseShape; RhsShape = Eigen::DenseShape; typename Eigen::internal::traits::Rhs>::Scalar = double; typename Eigen::internal::traits::Lhs>::Scalar = double; Eigen::internal::product_evaluator, ProductTag, LhsShape, RhsShape>::XprType = Eigen::Product, const Eigen::CwiseNullaryOp, const Eigen::Matrix >, const Eigen::Transpose > >, Eigen::Matrix, 0>, Eigen::Matrix, 0>]’ +/opt/R/4.1.1/lib/R/site-library/RcppEigen/include/Eigen/src/Core/ProductEvaluators.h:35:90: required from ‘Eigen::internal::evaluator >::evaluator(const XprType&) [with Lhs = Eigen::Product, const Eigen::CwiseNullaryOp, const Eigen::Matrix >, const Eigen::Transpose > >, Eigen::Matrix, 0>; Rhs = Eigen::Matrix; int Options = 0; Eigen::internal::evaluator >::XprType = Eigen::Product, const Eigen::CwiseNullaryOp, const Eigen::Matrix >, const Eigen::Transpose > >, Eigen::Matrix, 0>, Eigen::Matrix, 0>]’ +/opt/R/4.1.1/lib/R/site-library/RcppEigen/include/Eigen/src/Core/Product.h:132:22: required from ‘Eigen::internal::dense_product_base::operator const Scalar() const [with Lhs = Eigen::Product, const Eigen::CwiseNullaryOp, const Eigen::Matrix >, const Eigen::Transpose > >, Eigen::Matrix, 0>; Rhs = Eigen::Matrix; int Option = 0; Eigen::internal::dense_product_base::Scalar = double]’ +/opt/R/4.1.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_blrm_exnex_namespace::model_blrm_exnex; BaseRNG = boost::random::additive_combine_engine, boost::random::linear_congruential_engine >]’ +/opt/R/4.1.1/lib/R/site-library/StanHeaders/include/src/stan/mcmc/hmc/hamiltonians/dense_e_metric.hpp:21:10: required from here +/opt/R/4.1.1/lib/R/site-library/RcppEigen/include/Eigen/src/Core/DenseCoeffsBase.h:55:30: warning: ignoring attributes on template argument ‘Eigen::internal::packet_traits::type’ {aka ‘__vector(2) double’} [-Wignored-attributes] +make: *** [/opt/R/4.1.1/lib/R/etc/Makeconf:175: stanExports_blrm_exnex.o] Error 1 +ERROR: compilation failed for package ‘OncoBayes2’ +* removing ‘/tmp/workdir/OncoBayes2/old/OncoBayes2.Rcheck/OncoBayes2’ + + +``` +# openai + +
+ +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/openai +* Number of recursive dependencies: 43 + +Run `revdepcheck::cloud_details(, "openai")` for more info + +
+ +## Error before installation + +### Devel + +``` + + + + + + +``` +### CRAN + +``` + + + + + + +``` +# 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: 133 + +Run `revdepcheck::cloud_details(, "OutliersO3")` for more info + +
+ +## In both + +* checking whether package ‘OutliersO3’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/OutliersO3/new/OutliersO3.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘OutliersO3’ ... +** package ‘OutliersO3’ 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 ‘tidyselect’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Execution halted +ERROR: lazy loading failed for package ‘OutliersO3’ +* removing ‘/tmp/workdir/OutliersO3/new/OutliersO3.Rcheck/OutliersO3’ + + +``` +### CRAN + +``` +* installing *source* package ‘OutliersO3’ ... +** package ‘OutliersO3’ 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 ‘tidyselect’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Execution halted +ERROR: lazy loading failed for package ‘OutliersO3’ +* removing ‘/tmp/workdir/OutliersO3/old/OutliersO3.Rcheck/OutliersO3’ + + +``` +# pathwayTMB + +
+ +* Version: 0.1.3 +* GitHub: NA +* Source code: https://github.com/cran/pathwayTMB +* Date/Publication: 2022-08-09 13:50:02 UTC +* Number of recursive dependencies: 221 + +Run `revdepcheck::cloud_details(, "pathwayTMB")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/pathwayTMB/new/pathwayTMB.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘pathwayTMB/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘pathwayTMB’ version ‘0.1.3’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘clusterProfiler’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/pathwayTMB/old/pathwayTMB.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘pathwayTMB/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘pathwayTMB’ version ‘0.1.3’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘clusterProfiler’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# peramo + +
+ +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/peramo +* Number of recursive dependencies: 17 + +Run `revdepcheck::cloud_details(, "peramo")` for more info + +
+ +## Error before installation + +### Devel + +``` + + + + + + +``` +### CRAN + +``` + + + + + + +``` +# performanceEstimation + +
+ +* Version: 1.1.0 +* GitHub: https://github.com/ltorgo/performanceEstimation +* Source code: https://github.com/cran/performanceEstimation +* Date/Publication: 2016-10-13 20:37:05 +* Number of recursive dependencies: 131 + +Run `revdepcheck::cloud_details(, "performanceEstimation")` for more info + +
+ +## Error before installation + +### Devel + +``` + + + + + + +``` +### CRAN + +``` + + + + + + +``` +# planningML + +
+ +* Version: 1.0.0 +* GitHub: NA +* Source code: https://github.com/cran/planningML +* Date/Publication: 2022-11-08 10:20:02 UTC +* Number of recursive dependencies: 156 + +Run `revdepcheck::cloud_details(, "planningML")` for more info + +
+ +## In both + +* checking whether package ‘planningML’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/planningML/new/planningML.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘planningML’ ... +** package ‘planningML’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** inst +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + there is no package called ‘tidyr’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Execution halted +ERROR: lazy loading failed for package ‘planningML’ +* removing ‘/tmp/workdir/planningML/new/planningML.Rcheck/planningML’ + + +``` +### CRAN + +``` +* installing *source* package ‘planningML’ ... +** package ‘planningML’ successfully unpacked and MD5 sums checked +** using staged installation +** R +** inst +** byte-compile and prepare package for lazy loading +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + there is no package called ‘tidyr’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Execution halted +ERROR: lazy loading failed for package ‘planningML’ +* removing ‘/tmp/workdir/planningML/old/planningML.Rcheck/planningML’ + + +``` +# Platypus + +
+ +* Version: 3.4.1 +* GitHub: NA +* Source code: https://github.com/cran/Platypus +* Date/Publication: 2022-08-15 07:20:20 UTC +* Number of recursive dependencies: 356 + +Run `revdepcheck::cloud_details(, "Platypus")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/Platypus/new/Platypus.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘Platypus/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘Platypus’ version ‘3.4.1’ +* package encoding: UTF-8 +* checking package namespace information ... OK +... +* checking package dependencies ... ERROR +Package required but not available: ‘ggtree’ + +Packages suggested but not available for checking: + 'Matrix.utils', 'monocle3', 'ProjecTILs', 'SeuratWrappers' + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/Platypus/old/Platypus.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘Platypus/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘Platypus’ version ‘3.4.1’ +* package encoding: UTF-8 +* checking package namespace information ... OK +... +* checking package dependencies ... ERROR +Package required but not available: ‘ggtree’ + +Packages suggested but not available for checking: + 'Matrix.utils', 'monocle3', 'ProjecTILs', 'SeuratWrappers' + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# PLSiMCpp + +
+ +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/PLSiMCpp +* Number of recursive dependencies: 10 + +Run `revdepcheck::cloud_details(, "PLSiMCpp")` for more info + +
+ +## Error before installation + +### Devel + +``` + + + + + + +``` +### CRAN + +``` + + + + + + +``` +# promotionImpact + +
+ +* Version: 0.1.5 +* GitHub: https://github.com/ncsoft/promotionImpact +* Source code: https://github.com/cran/promotionImpact +* Date/Publication: 2021-04-13 15:00:05 UTC +* Number of recursive dependencies: 122 + +Run `revdepcheck::cloud_details(, "promotionImpact")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/promotionImpact/new/promotionImpact.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘promotionImpact/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘promotionImpact’ version ‘0.1.5’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘prophet’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/promotionImpact/old/promotionImpact.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘promotionImpact/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘promotionImpact’ version ‘0.1.5’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘prophet’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# prqlr + +
+ +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/prqlr +* Number of recursive dependencies: 66 + +Run `revdepcheck::cloud_details(, "prqlr")` for more info + +
+ +## Error before installation + +### Devel + +``` + + + + + + +``` +### CRAN + +``` + + + + + + +``` +# PsychWordVec + +
+ +* Version: 0.3.2 +* GitHub: https://github.com/psychbruce/PsychWordVec +* Source code: https://github.com/cran/PsychWordVec +* Date/Publication: 2023-03-04 16:20:02 UTC +* Number of recursive dependencies: 231 + +Run `revdepcheck::cloud_details(, "PsychWordVec")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/PsychWordVec/new/PsychWordVec.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘PsychWordVec/DESCRIPTION’ ... OK +* this is package ‘PsychWordVec’ version ‘0.3.2’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘bruceR’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/PsychWordVec/old/PsychWordVec.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘PsychWordVec/DESCRIPTION’ ... OK +* this is package ‘PsychWordVec’ version ‘0.3.2’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘bruceR’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# RBesT + +
+ +* Version: 1.6-6 +* GitHub: https://github.com/Novartis/RBesT +* Source code: https://github.com/cran/RBesT +* Date/Publication: 2023-03-03 18:20:02 UTC +* Number of recursive dependencies: 131 + +Run `revdepcheck::cloud_details(, "RBesT")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/RBesT/new/RBesT.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘RBesT/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘RBesT’ version ‘1.6-6’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘rstan’ + +Package suggested but not available for checking: ‘rstanarm’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/RBesT/old/RBesT.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘RBesT/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘RBesT’ version ‘1.6-6’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘rstan’ + +Package suggested but not available for checking: ‘rstanarm’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# rcssci + +
+ +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/rcssci +* Number of recursive dependencies: 139 + +Run `revdepcheck::cloud_details(, "rcssci")` for more info + +
+ +## Error before installation + +### Devel + +``` + + + + + + +``` +### CRAN + +``` + + + + + + +``` +# rdss + +
+ +* Version: 1.0.0 +* GitHub: NA +* Source code: https://github.com/cran/rdss +* Date/Publication: 2023-01-17 17:40:02 UTC +* Number of recursive dependencies: 207 + +Run `revdepcheck::cloud_details(, "rdss")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/rdss/new/rdss.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘rdss/DESCRIPTION’ ... OK +* this is package ‘rdss’ version ‘1.0.0’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... NOTE +... +* 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 + +``` +* using log directory ‘/tmp/workdir/rdss/old/rdss.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘rdss/DESCRIPTION’ ... OK +* this is package ‘rdss’ version ‘1.0.0’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... NOTE +... +* 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 + + + + + +``` +# report + +
+ +* Version: 0.5.6 +* GitHub: https://github.com/easystats/report +* Source code: https://github.com/cran/report +* Date/Publication: 2023-02-05 20:42:31 UTC +* Number of recursive dependencies: 156 + +Run `revdepcheck::cloud_details(, "report")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/report/new/report.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘report/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘report’ version ‘0.5.6’ +* package encoding: UTF-8 +* checking package namespace information ... OK +... +* checking for unstated dependencies in vignettes ... OK +* checking package vignettes in ‘inst/doc’ ... OK +* checking running R code from vignettes ... NONE + ‘cite_packages.Rmd’ using ‘UTF-8’... OK + ‘new_models.Rmd’ using ‘UTF-8’... OK + ‘report.Rmd’ using ‘UTF-8’... OK + ‘report_table.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 1 NOTE + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/report/old/report.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘report/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘report’ version ‘0.5.6’ +* package encoding: UTF-8 +* checking package namespace information ... OK +... +* checking for unstated dependencies in vignettes ... OK +* checking package vignettes in ‘inst/doc’ ... OK +* checking running R code from vignettes ... NONE + ‘cite_packages.Rmd’ using ‘UTF-8’... OK + ‘new_models.Rmd’ using ‘UTF-8’... OK + ‘report.Rmd’ using ‘UTF-8’... OK + ‘report_table.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 1 NOTE + + + + + +``` +# RevGadgets + +
+ +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/RevGadgets +* Number of recursive dependencies: 125 + +Run `revdepcheck::cloud_details(, "RevGadgets")` for more info + +
+ +## Error before installation + +### Devel + +``` + + + + + + +``` +### CRAN + +``` + + + + + + +``` +# Rigma + +
+ +* Version: 0.2.1 +* GitHub: https://github.com/AleKoure/Rigma +* Source code: https://github.com/cran/Rigma +* Date/Publication: 2022-11-27 22:00:06 UTC +* Number of recursive dependencies: 71 + +Run `revdepcheck::cloud_details(, "Rigma")` for more info + +
+ +## In both + +* checking whether package ‘Rigma’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/Rigma/new/Rigma.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘Rigma’ ... +** package ‘Rigma’ 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 ‘sass’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Execution halted +ERROR: lazy loading failed for package ‘Rigma’ +* removing ‘/tmp/workdir/Rigma/new/Rigma.Rcheck/Rigma’ + + +``` +### CRAN + +``` +* installing *source* package ‘Rigma’ ... +** package ‘Rigma’ 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 ‘sass’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Execution halted +ERROR: lazy loading failed for package ‘Rigma’ +* removing ‘/tmp/workdir/Rigma/old/Rigma.Rcheck/Rigma’ + + +``` +# Robyn + +
+ +* Version: 3.9.0 +* GitHub: https://github.com/facebookexperimental/Robyn +* Source code: https://github.com/cran/Robyn +* Date/Publication: 2023-02-08 08:12:37 UTC +* Number of recursive dependencies: 139 + +Run `revdepcheck::cloud_details(, "Robyn")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/Robyn/new/Robyn.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘Robyn/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘Robyn’ version ‘3.9.0’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘prophet’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/Robyn/old/Robyn.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘Robyn/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘Robyn’ version ‘3.9.0’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘prophet’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# RVA + +
+ +* Version: 0.0.5 +* GitHub: https://github.com/THERMOSTATS/RVA +* Source code: https://github.com/cran/RVA +* Date/Publication: 2021-11-01 21:40:02 UTC +* Number of recursive dependencies: 208 + +Run `revdepcheck::cloud_details(, "RVA")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/RVA/new/RVA.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘RVA/DESCRIPTION’ ... OK +* this is package ‘RVA’ version ‘0.0.5’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘clusterProfiler’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/RVA/old/RVA.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘RVA/DESCRIPTION’ ... OK +* this is package ‘RVA’ version ‘0.0.5’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘clusterProfiler’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# SAMtool + +
+ +* Version: 1.5.1 +* GitHub: https://github.com/Blue-Matter/SAMtool +* Source code: https://github.com/cran/SAMtool +* Date/Publication: 2023-02-08 23:20:02 UTC +* Number of recursive dependencies: 183 + +Run `revdepcheck::cloud_details(, "SAMtool")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/SAMtool/new/SAMtool.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘SAMtool/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘SAMtool’ version ‘1.5.1’ +* package encoding: UTF-8 +* checking package namespace information ... OK +... +* checking line endings in C/C++/Fortran sources/headers ... OK +* checking line endings in Makefiles ... OK +* checking compilation flags in Makevars ... 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 +* DONE +Status: 2 NOTEs + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/SAMtool/old/SAMtool.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘SAMtool/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘SAMtool’ version ‘1.5.1’ +* package encoding: UTF-8 +* checking package namespace information ... OK +... +* checking line endings in C/C++/Fortran sources/headers ... OK +* checking line endings in Makefiles ... OK +* checking compilation flags in Makevars ... 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 +* DONE +Status: 2 NOTEs + + + + + +``` +# scGate + +
+ +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/scGate +* Number of recursive dependencies: 173 + +Run `revdepcheck::cloud_details(, "scGate")` for more info + +
+ +## Error before installation + +### Devel + +``` + + + + + + +``` +### CRAN + +``` + + + + + + +``` +# SCpubr + +
+ +* Version: 1.1.2 +* GitHub: https://github.com/enblacar/SCpubr +* Source code: https://github.com/cran/SCpubr +* Date/Publication: 2023-01-18 12:20:02 UTC +* Number of recursive dependencies: 290 + +Run `revdepcheck::cloud_details(, "SCpubr")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/SCpubr/new/SCpubr.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘SCpubr/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘SCpubr’ version ‘1.1.2’ +* package encoding: UTF-8 +* checking package namespace information ... 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: 1 WARNING, 2 NOTEs + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/SCpubr/old/SCpubr.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘SCpubr/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘SCpubr’ version ‘1.1.2’ +* package encoding: UTF-8 +* checking package namespace information ... 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: 1 WARNING, 2 NOTEs + + + + + +``` +# shinyHugePlot + +
+ +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/shinyHugePlot +* Number of recursive dependencies: 97 + +Run `revdepcheck::cloud_details(, "shinyHugePlot")` for more info + +
+ +## Error before installation + +### Devel + +``` + + + + + + +``` +### CRAN + +``` + + + + + + +``` +# sjPlot + +
+ +* Version: 2.8.12 +* GitHub: https://github.com/strengejacke/sjPlot +* Source code: https://github.com/cran/sjPlot +* Date/Publication: 2022-11-19 22:20:02 UTC +* Number of recursive dependencies: 186 + +Run `revdepcheck::cloud_details(, "sjPlot")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/sjPlot/new/sjPlot.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘sjPlot/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘sjPlot’ version ‘2.8.12’ +* package encoding: UTF-8 +* checking package namespace information ... 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 +* checking re-building of vignette outputs ... OK +* DONE +Status: 1 NOTE + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/sjPlot/old/sjPlot.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘sjPlot/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘sjPlot’ version ‘2.8.12’ +* package encoding: UTF-8 +* checking package namespace information ... 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 +* checking re-building of vignette outputs ... OK +* DONE +Status: 1 NOTE + + + + + +``` +# sknifedatar + +
+ +* Version: 0.1.2 +* GitHub: https://github.com/rafzamb/sknifedatar +* Source code: https://github.com/cran/sknifedatar +* Date/Publication: 2021-06-01 08:00:02 UTC +* Number of recursive dependencies: 180 + +Run `revdepcheck::cloud_details(, "sknifedatar")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/sknifedatar/new/sknifedatar.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘sknifedatar/DESCRIPTION’ ... OK +* this is package ‘sknifedatar’ version ‘0.1.2’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... 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 ‘spelling.R’ +* DONE +Status: OK + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/sknifedatar/old/sknifedatar.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘sknifedatar/DESCRIPTION’ ... OK +* this is package ‘sknifedatar’ version ‘0.1.2’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... 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 ‘spelling.R’ +* DONE +Status: OK + + + + + +``` +# SpaDES.tools + +
+ +* Version: 1.0.1 +* GitHub: https://github.com/PredictiveEcology/SpaDES.tools +* Source code: https://github.com/cran/SpaDES.tools +* Date/Publication: 2023-01-05 15:20:19 UTC +* Number of recursive dependencies: 117 + +Run `revdepcheck::cloud_details(, "SpaDES.tools")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/SpaDES.tools/new/SpaDES.tools.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘SpaDES.tools/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘SpaDES.tools’ version ‘1.0.1’ +* package encoding: UTF-8 +* checking package namespace information ... 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 +* checking for unstated dependencies in ‘tests’ ... OK +* checking tests ... OK + Running ‘test-all.R’ +* DONE +Status: 1 NOTE + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/SpaDES.tools/old/SpaDES.tools.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘SpaDES.tools/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘SpaDES.tools’ version ‘1.0.1’ +* package encoding: UTF-8 +* checking package namespace information ... 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 +* checking for unstated dependencies in ‘tests’ ... OK +* checking tests ... OK + Running ‘test-all.R’ +* DONE +Status: 1 NOTE + + + + + +``` +# statsExpressions + +
+ +* Version: 1.5.0 +* GitHub: https://github.com/IndrajeetPatil/statsExpressions +* Source code: https://github.com/cran/statsExpressions +* Date/Publication: 2023-02-19 14:30:02 UTC +* Number of recursive dependencies: 152 + +Run `revdepcheck::cloud_details(, "statsExpressions")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/statsExpressions/new/statsExpressions.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘statsExpressions/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘statsExpressions’ version ‘1.5.0’ +* package encoding: UTF-8 +* checking package namespace information ... OK +... + 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 ... NONE + ‘statsExpressions.Rmd’ using ‘UTF-8’... OK + ‘stats_details.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 1 ERROR, 1 NOTE + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/statsExpressions/old/statsExpressions.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘statsExpressions/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘statsExpressions’ version ‘1.5.0’ +* package encoding: UTF-8 +* checking package namespace information ... OK +... + 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 ... NONE + ‘statsExpressions.Rmd’ using ‘UTF-8’... OK + ‘stats_details.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 1 ERROR, 1 NOTE + + + + + +``` +# stortingscrape + +
+ +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/stortingscrape +* Number of recursive dependencies: 61 + +Run `revdepcheck::cloud_details(, "stortingscrape")` for more info + +
+ +## Error before installation + +### Devel + +``` + + + + + + +``` +### CRAN + +``` + + + + + + +``` +# tame + +
+ +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/tame +* Number of recursive dependencies: 65 + +Run `revdepcheck::cloud_details(, "tame")` for more info + +
+ +## Error before installation + +### Devel + +``` + + + + + + +``` +### CRAN + +``` + + + + + + +``` +# tidybayes + +
+ +* Version: 3.0.3 +* GitHub: https://github.com/mjskay/tidybayes +* Source code: https://github.com/cran/tidybayes +* Date/Publication: 2023-02-04 09:10:02 UTC +* Number of recursive dependencies: 200 + +Run `revdepcheck::cloud_details(, "tidybayes")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/tidybayes/new/tidybayes.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘tidybayes/DESCRIPTION’ ... OK +* this is package ‘tidybayes’ version ‘3.0.3’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... NOTE +... +* checking package vignettes in ‘inst/doc’ ... OK +* checking running R code from vignettes ... NONE + ‘tidy-brms.Rmd’ using ‘UTF-8’... OK + ‘tidy-posterior.Rmd’ using ‘UTF-8’... OK + ‘tidy-rstanarm.Rmd’ using ‘UTF-8’... OK + ‘tidybayes-residuals.Rmd’ using ‘UTF-8’... OK + ‘tidybayes.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 2 NOTEs + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/tidybayes/old/tidybayes.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘tidybayes/DESCRIPTION’ ... OK +* this is package ‘tidybayes’ version ‘3.0.3’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... NOTE +... +* checking package vignettes in ‘inst/doc’ ... OK +* checking running R code from vignettes ... NONE + ‘tidy-brms.Rmd’ using ‘UTF-8’... OK + ‘tidy-posterior.Rmd’ using ‘UTF-8’... OK + ‘tidy-rstanarm.Rmd’ using ‘UTF-8’... OK + ‘tidybayes-residuals.Rmd’ using ‘UTF-8’... OK + ‘tidybayes.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 2 NOTEs + + + + + +``` +# tidyposterior + +
+ +* Version: 1.0.0 +* GitHub: https://github.com/tidymodels/tidyposterior +* Source code: https://github.com/cran/tidyposterior +* Date/Publication: 2022-06-23 20:20:02 UTC +* Number of recursive dependencies: 170 + +Run `revdepcheck::cloud_details(, "tidyposterior")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/tidyposterior/new/tidyposterior.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘tidyposterior/DESCRIPTION’ ... OK +* this is package ‘tidyposterior’ version ‘1.0.0’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘rstanarm’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/tidyposterior/old/tidyposterior.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘tidyposterior/DESCRIPTION’ ... OK +* this is package ‘tidyposterior’ version ‘1.0.0’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘rstanarm’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# tidySEM + +
+ +* Version: 0.2.3 +* GitHub: https://github.com/cjvanlissa/tidySEM +* Source code: https://github.com/cran/tidySEM +* Date/Publication: 2022-04-14 17:50:02 UTC +* Number of recursive dependencies: 171 + +Run `revdepcheck::cloud_details(, "tidySEM")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/tidySEM/new/tidySEM.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘tidySEM/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘tidySEM’ version ‘0.2.3’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘blavaan’ + +Package suggested but not available for checking: ‘umx’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/tidySEM/old/tidySEM.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘tidySEM/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘tidySEM’ version ‘0.2.3’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘blavaan’ + +Package suggested but not available for checking: ‘umx’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# tidytags
* Version: NA * GitHub: NA -* Source code: https://github.com/cran/NA -* Number of recursive dependencies: 0 +* Source code: https://github.com/cran/tidytags +* Number of recursive dependencies: 122 + +Run `revdepcheck::cloud_details(, "tidytags")` for more info + +
+ +## Error before installation + +### Devel + +``` + + + + + + +``` +### CRAN + +``` + + + + + + +``` +# timetk + +
+ +* Version: 2.8.2 +* GitHub: https://github.com/business-science/timetk +* Source code: https://github.com/cran/timetk +* Date/Publication: 2022-11-17 19:30:02 UTC +* Number of recursive dependencies: 226 + +Run `revdepcheck::cloud_details(, "timetk")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/timetk/new/timetk.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘timetk/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘timetk’ version ‘2.8.2’ +* package encoding: UTF-8 +* checking package namespace information ... OK +... + Error in library(robets) : there is no package called 'robets' + Execution halted +* checking for unstated dependencies in vignettes ... OK +* checking package vignettes in ‘inst/doc’ ... OK +* checking running R code from vignettes ... NONE + ‘TK04_Plotting_Time_Series.Rmd’ using ‘UTF-8’... OK + ‘TK07_Time_Series_Data_Wrangling.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 1 ERROR, 2 NOTEs + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/timetk/old/timetk.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘timetk/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘timetk’ version ‘2.8.2’ +* package encoding: UTF-8 +* checking package namespace information ... OK +... + Error in library(robets) : there is no package called 'robets' + Execution halted +* checking for unstated dependencies in vignettes ... OK +* checking package vignettes in ‘inst/doc’ ... OK +* checking running R code from vignettes ... NONE + ‘TK04_Plotting_Time_Series.Rmd’ using ‘UTF-8’... OK + ‘TK07_Time_Series_Data_Wrangling.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 1 ERROR, 2 NOTEs + + + + + +``` +# tinyarray + +
+ +* Version: 2.2.9 +* GitHub: https://github.com/xjsun1221/tinyarray +* Source code: https://github.com/cran/tinyarray +* Date/Publication: 2023-03-04 07:40:02 UTC +* Number of recursive dependencies: 228 + +Run `revdepcheck::cloud_details(, "tinyarray")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/tinyarray/new/tinyarray.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘tinyarray/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘tinyarray’ version ‘2.2.9’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘clusterProfiler’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/tinyarray/old/tinyarray.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘tinyarray/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘tinyarray’ version ‘2.2.9’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘clusterProfiler’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# tipmap + +
+ +* Version: 0.3.9 +* GitHub: NA +* Source code: https://github.com/cran/tipmap +* Date/Publication: 2022-12-07 21:50:02 UTC +* Number of recursive dependencies: 96 -Run `cloud_details(, "NA")` for more info +Run `revdepcheck::cloud_details(, "tipmap")` for more info
@@ -16,7 +8147,23 @@ Run `cloud_details(, "NA")` for more info ### Devel ``` +* using log directory ‘/tmp/workdir/tipmap/new/tipmap.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘tipmap/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘tipmap’ version ‘0.3.9’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘RBesT’ +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR @@ -26,24 +8173,40 @@ Run `cloud_details(, "NA")` for more info ### CRAN ``` +* using log directory ‘/tmp/workdir/tipmap/old/tipmap.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘tipmap/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘tipmap’ version ‘0.3.9’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘RBesT’ +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR ``` -# tidybayes +# vivid
-* Version: 3.0.2 -* GitHub: https://github.com/mjskay/tidybayes -* Source code: https://github.com/cran/tidybayes -* Date/Publication: 2022-01-05 06:10:02 UTC +* Version: 0.2.5 +* GitHub: NA +* Source code: https://github.com/cran/vivid +* Date/Publication: 2023-02-13 16:40:02 UTC * Number of recursive dependencies: 206 -Run `cloud_details(, "tidybayes")` for more info +Run `revdepcheck::cloud_details(, "vivid")` for more info
@@ -52,27 +8215,27 @@ Run `cloud_details(, "tidybayes")` for more info ### Devel ``` -* using log directory ‘/tmp/workdir/tidybayes/new/tidybayes.Rcheck’ +* using log directory ‘/tmp/workdir/vivid/new/vivid.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘tidybayes/DESCRIPTION’ ... OK -* this is package ‘tidybayes’ version ‘3.0.2’ +* checking for file ‘vivid/DESCRIPTION’ ... OK +* this is package ‘vivid’ version ‘0.2.5’ * package encoding: UTF-8 * checking package namespace information ... OK * checking package dependencies ... NOTE ... +* 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 - ‘tidy-brms.Rmd’ using ‘UTF-8’... OK - ‘tidy-posterior.Rmd’ using ‘UTF-8’... OK - ‘tidy-rstanarm.Rmd’ using ‘UTF-8’... OK - ‘tidybayes-residuals.Rmd’ using ‘UTF-8’... OK - ‘tidybayes.Rmd’ using ‘UTF-8’... OK + ‘vivid.Rmd’ using ‘UTF-8’... OK + ‘vividQStart.Rmd’ using ‘UTF-8’... OK * checking re-building of vignette outputs ... OK * DONE -Status: 2 NOTEs +Status: 1 NOTE @@ -82,44 +8245,106 @@ Status: 2 NOTEs ### CRAN ``` -* using log directory ‘/tmp/workdir/tidybayes/old/tidybayes.Rcheck’ +* using log directory ‘/tmp/workdir/vivid/old/vivid.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘tidybayes/DESCRIPTION’ ... OK -* this is package ‘tidybayes’ version ‘3.0.2’ +* checking for file ‘vivid/DESCRIPTION’ ... OK +* this is package ‘vivid’ version ‘0.2.5’ * package encoding: UTF-8 * checking package namespace information ... OK * checking package dependencies ... NOTE ... +* 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 - ‘tidy-brms.Rmd’ using ‘UTF-8’... OK - ‘tidy-posterior.Rmd’ using ‘UTF-8’... OK - ‘tidy-rstanarm.Rmd’ using ‘UTF-8’... OK - ‘tidybayes-residuals.Rmd’ using ‘UTF-8’... OK - ‘tidybayes.Rmd’ using ‘UTF-8’... OK + ‘vivid.Rmd’ using ‘UTF-8’... OK + ‘vividQStart.Rmd’ using ‘UTF-8’... OK * checking re-building of vignette outputs ... OK * DONE -Status: 2 NOTEs +Status: 1 NOTE ``` -# tidyposterior +# wearables
-* Version: 1.0.0 -* GitHub: https://github.com/tidymodels/tidyposterior -* Source code: https://github.com/cran/tidyposterior -* Date/Publication: 2022-06-23 20:20:02 UTC -* Number of recursive dependencies: 170 +* Version: 0.8.1 +* GitHub: NA +* Source code: https://github.com/cran/wearables +* Date/Publication: 2021-12-20 15:20:02 UTC +* Number of recursive dependencies: 122 + +Run `revdepcheck::cloud_details(, "wearables")` for more info + +
+ +## In both + +* checking whether package ‘wearables’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/wearables/new/wearables.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘wearables’ ... +** package ‘wearables’ 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 ‘rstan’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Execution halted +ERROR: lazy loading failed for package ‘wearables’ +* removing ‘/tmp/workdir/wearables/new/wearables.Rcheck/wearables’ + + +``` +### CRAN + +``` +* installing *source* package ‘wearables’ ... +** package ‘wearables’ 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 ‘rstan’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Execution halted +ERROR: lazy loading failed for package ‘wearables’ +* removing ‘/tmp/workdir/wearables/old/wearables.Rcheck/wearables’ + -Run `cloud_details(, "tidyposterior")` for more info +``` +# webSDM + +
+ +* Version: 1.1-1 +* GitHub: https://github.com/giopogg/webSDM +* Source code: https://github.com/cran/webSDM +* Date/Publication: 2022-11-25 12:40:02 UTC +* Number of recursive dependencies: 190 + +Run `revdepcheck::cloud_details(, "webSDM")` for more info
@@ -128,13 +8353,13 @@ Run `cloud_details(, "tidyposterior")` for more info ### Devel ``` -* using log directory ‘/tmp/workdir/tidyposterior/new/tidyposterior.Rcheck’ +* using log directory ‘/tmp/workdir/webSDM/new/webSDM.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘tidyposterior/DESCRIPTION’ ... OK -* this is package ‘tidyposterior’ version ‘1.0.0’ +* checking for file ‘webSDM/DESCRIPTION’ ... OK +* this is package ‘webSDM’ version ‘1.1-1’ * package encoding: UTF-8 * checking package namespace information ... OK * checking package dependencies ... ERROR @@ -153,13 +8378,13 @@ Status: 1 ERROR ### CRAN ``` -* using log directory ‘/tmp/workdir/tidyposterior/old/tidyposterior.Rcheck’ +* using log directory ‘/tmp/workdir/webSDM/old/webSDM.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘tidyposterior/DESCRIPTION’ ... OK -* this is package ‘tidyposterior’ version ‘1.0.0’ +* checking for file ‘webSDM/DESCRIPTION’ ... OK +* this is package ‘webSDM’ version ‘1.1-1’ * package encoding: UTF-8 * checking package namespace information ... OK * checking package dependencies ... ERROR @@ -174,4 +8399,111 @@ Status: 1 ERROR +``` +# wrappedtools + +
+ +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/wrappedtools +* Number of recursive dependencies: 96 + +Run `revdepcheck::cloud_details(, "wrappedtools")` for more info + +
+ +## Error before installation + +### Devel + +``` + + + + + + +``` +### CRAN + +``` + + + + + + +``` +# xpose.nlmixr2 + +
+ +* Version: 0.4.0 +* GitHub: NA +* Source code: https://github.com/cran/xpose.nlmixr2 +* Date/Publication: 2022-06-08 09:10:02 UTC +* Number of recursive dependencies: 161 + +Run `revdepcheck::cloud_details(, "xpose.nlmixr2")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/xpose.nlmixr2/new/xpose.nlmixr2.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘xpose.nlmixr2/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘xpose.nlmixr2’ version ‘0.4.0’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘nlmixr2est’ + +Package suggested but not available for checking: ‘nlmixr2’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/xpose.nlmixr2/old/xpose.nlmixr2.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘xpose.nlmixr2/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘xpose.nlmixr2’ version ‘0.4.0’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘nlmixr2est’ + +Package suggested but not available for checking: ‘nlmixr2’ + +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 9a2073633..53fb5db1c 100644 --- a/revdep/problems.md +++ b/revdep/problems.md @@ -1 +1,235 @@ -*Wow, no problems at all. :)* \ No newline at end of file +# dplyr + +
+ +* Version: 1.1.0 +* GitHub: https://github.com/tidyverse/dplyr +* Source code: https://github.com/cran/dplyr +* Date/Publication: 2023-01-29 22:50:02 UTC +* Number of recursive dependencies: 95 + +Run `revdepcheck::cloud_details(, "dplyr")` for more info + +
+ +## Newly broken + +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Last 13 lines of output: + • Can't use 'en_US' locale (2) + • On CRAN (305) + + ══ Failed tests ════════════════════════════════════════════════════════════════ + ── Failure ('test-filter.R:301'): hybrid function row_number does not trigger warning in filter (#3750) ── + `out` is not TRUE + + `actual`: FALSE + `expected`: TRUE + ── Failure ('test-join-by.R:236'): nicely catches missing arguments when wrapped ── + `fn(a)` did not throw the expected error. + + [ FAIL 2 | WARN 270 | SKIP 311 | PASS 2742 ] + Error: Test failures + Execution halted + ``` + +## In both + +* checking data for non-ASCII characters ... NOTE + ``` + Note: found 4 marked UTF-8 strings + ``` + +# GenomeAdmixR + +
+ +* Version: 2.1.7 +* GitHub: https://github.com/thijsjanzen/GenomeAdmixR +* Source code: https://github.com/cran/GenomeAdmixR +* Date/Publication: 2022-03-01 21:10:15 UTC +* Number of recursive dependencies: 104 + +Run `revdepcheck::cloud_details(, "GenomeAdmixR")` for more info + +
+ +## Newly broken + +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Last 13 lines of output: + | | 0% + | + |=================================== | 50% + | + |======================================================================| 100%[ FAIL 1 | WARN 0 | SKIP 0 | PASS 454 ] + + ══ Failed tests ════════════════════════════════════════════════════════════════ + ── Failure ('test-simulate_admixture_data.R:202'): simulate_admixture_data_recombination_map ── + `all_j` not equal to `expected_num_j`. + 1/1 mismatches + [1] 71 - 100 == -29 + + [ FAIL 1 | WARN 0 | SKIP 0 | PASS 454 ] + Error: Test failures + Execution halted + ``` + +## In both + +* checking installed package size ... NOTE + ``` + installed size is 11.9Mb + sub-directories of 1Mb or more: + doc 2.0Mb + libs 9.3Mb + ``` + +* checking dependencies in R code ... NOTE + ``` + Namespace in Imports field not imported from: ‘methods’ + All declared Imports should be used. + ``` + +# photosynthesis + +
+ +* Version: 2.1.1 +* GitHub: https://github.com/cdmuir/photosynthesis +* Source code: https://github.com/cran/photosynthesis +* Date/Publication: 2022-11-19 19:40:09 UTC +* Number of recursive dependencies: 135 + +Run `revdepcheck::cloud_details(, "photosynthesis")` for more info + +
+ +## Newly broken + +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Last 13 lines of output: + Expected `{ ... }` to run without any conditions. + ℹ Actually got a : + Condition: + `flatten()` is deprecated as of rlang 1.1.0. ℹ Please use + `purrr::list_flatten()` or `purrr::list_c()`. + ── Failure ('test-fit_aq_response2.R:44'): .vars argument renames variables ──── + Expected `{ ... }` to run without any conditions. + ℹ Actually got a : + Condition: + `flatten()` is deprecated as of rlang 1.1.0. ℹ Please use + `purrr::list_flatten()` or `purrr::list_c()`. + + [ FAIL 6 | WARN 2 | SKIP 0 | PASS 320 ] + Error: Test failures + Execution halted + ``` + +## In both + +* checking installed package size ... NOTE + ``` + installed size is 7.1Mb + sub-directories of 1Mb or more: + doc 6.1Mb + ``` + +* checking data for non-ASCII characters ... NOTE + ``` + Note: found 13 marked UTF-8 strings + ``` + +# portalr + +
+ +* Version: 0.3.11 +* GitHub: https://github.com/weecology/portalr +* Source code: https://github.com/cran/portalr +* Date/Publication: 2022-12-01 17:40:02 UTC +* Number of recursive dependencies: 106 + +Run `revdepcheck::cloud_details(, "portalr")` for more info + +
+ +## Newly broken + +* checking tests ... ERROR + ``` + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Last 13 lines of output: + Backtrace: + ▆ + 1. ├─portalr::bait_presence_absence(path = portal_data_path, level = "plot") at test-10-summarize_ants.R:49:2 + 2. │ ├─compute_presence(bait, level) %>% as.data.frame() + 3. │ └─portalr:::compute_presence(bait, level) + 4. │ └─... %>% ... + 5. ├─base::as.data.frame(.) + 6. ├─tidyr::complete(., !!!grouping, fill = list(presence = 0)) + 7. ├─dplyr::mutate(., presence = 1) + 8. ├─dplyr::distinct(.) + 9. └─dplyr::select(., !!!grouping) + + [ FAIL 12 | WARN 43 | SKIP 42 | PASS 17 ] + Error: Test failures + Execution halted + ``` + +# rlang + +
+ +* Version: 1.0.6 +* GitHub: https://github.com/r-lib/rlang +* Source code: https://github.com/cran/rlang +* Date/Publication: 2022-09-24 05:40:02 UTC +* Number of recursive dependencies: 68 + +Run `revdepcheck::cloud_details(, "rlang")` for more info + +
+ +## Newly broken + +* checking tests ... ERROR + ``` + Running ‘sink.R’ + Running ‘testthat.R’ + Running the tests in ‘tests/testthat.R’ failed. + Last 13 lines of output: + 12. ├─base::namespaceImportFrom(...) + 13. │ └─base::asNamespace(ns) + 14. └─base::loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) + 15. ├─base::namespaceImportFrom(...) + 16. │ └─base::asNamespace(ns) + 17. └─base::loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) + 18. ├─base::namespaceImportFrom(...) + 19. │ └─base::asNamespace(ns) + 20. └─base::loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) + 21. ├─base::namespaceImport(...) + 22. └─base::loadNamespace(i, c(lib.loc, .libPaths()), versionCheck = vI[[i]]) + + [ FAIL 2 | WARN 2 | SKIP 235 | PASS 3661 ] + Error: Test failures + Execution halted + ``` + +## In both + +* checking package dependencies ... NOTE + ``` + Package which this enhances but not available for checking: ‘winch’ + ``` + From 38d54298f231ec31ce1d2f4c7446b48375d8b490 Mon Sep 17 00:00:00 2001 From: DavisVaughan Date: Mon, 6 Mar 2023 14:26:55 -0500 Subject: [PATCH 247/312] Update funder to Posit --- DESCRIPTION | 4 ++-- man/vctrs-package.Rd | 2 +- 2 files changed, 3 insertions(+), 3 deletions(-) diff --git a/DESCRIPTION b/DESCRIPTION index 1155153a1..29761431e 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -17,8 +17,8 @@ Authors@R: person(given = "data.table team", role = "cph", comment = "Radix sort based on data.table's forder() and their contribution to R's order()"), - person(given = "RStudio", - role = "cph")) + person(given = "Posit, PBC", + role = c("cph", "fnd"))) Description: Defines new notions of prototype and size that are used to provide tools for consistent and well-founded type-coercion and size-recycling, and are in turn connected to ideas of type- and diff --git a/man/vctrs-package.Rd b/man/vctrs-package.Rd index 076582eb6..1af8e5cef 100644 --- a/man/vctrs-package.Rd +++ b/man/vctrs-package.Rd @@ -33,7 +33,7 @@ Authors: Other contributors: \itemize{ \item data.table team (Radix sort based on data.table's forder() and their contribution to R's order()) [copyright holder] - \item RStudio [copyright holder] + \item Posit, PBC [copyright holder, funder] } } From 358f7a5fea9f1c16e73c6e9e610603cf4a9cdd3c Mon Sep 17 00:00:00 2001 From: DavisVaughan Date: Mon, 6 Mar 2023 14:27:50 -0500 Subject: [PATCH 248/312] Update to Posit emails --- DESCRIPTION | 6 +++--- man/vctrs-package.Rd | 6 +++--- 2 files changed, 6 insertions(+), 6 deletions(-) diff --git a/DESCRIPTION b/DESCRIPTION index 29761431e..9d9e0df67 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -5,15 +5,15 @@ Authors@R: c(person(given = "Hadley", family = "Wickham", role = "aut", - email = "hadley@rstudio.com"), + email = "hadley@posit.co"), person(given = "Lionel", family = "Henry", role = c("aut", "cre"), - email = "lionel@rstudio.com"), + email = "lionel@posit.co"), person(given = "Davis", family = "Vaughan", role = "aut", - email = "davis@rstudio.com"), + email = "davis@posit.co"), person(given = "data.table team", role = "cph", comment = "Radix sort based on data.table's forder() and their contribution to R's order()"), diff --git a/man/vctrs-package.Rd b/man/vctrs-package.Rd index 1af8e5cef..c35d1c2fd 100644 --- a/man/vctrs-package.Rd +++ b/man/vctrs-package.Rd @@ -22,12 +22,12 @@ Useful links: } \author{ -\strong{Maintainer}: Lionel Henry \email{lionel@rstudio.com} +\strong{Maintainer}: Lionel Henry \email{lionel@posit.co} Authors: \itemize{ - \item Hadley Wickham \email{hadley@rstudio.com} - \item Davis Vaughan \email{davis@rstudio.com} + \item Hadley Wickham \email{hadley@posit.co} + \item Davis Vaughan \email{davis@posit.co} } Other contributors: From ff4d88cc00a0afb07dd775d13289e434bab7bdc3 Mon Sep 17 00:00:00 2001 From: DavisVaughan Date: Mon, 6 Mar 2023 14:28:32 -0500 Subject: [PATCH 249/312] `use_mit_license()` --- LICENSE | 2 +- LICENSE.md | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/LICENSE b/LICENSE index 6ace6b615..a0952ae33 100644 --- a/LICENSE +++ b/LICENSE @@ -1,2 +1,2 @@ -YEAR: 2020 +YEAR: 2023 COPYRIGHT HOLDER: vctrs authors diff --git a/LICENSE.md b/LICENSE.md index ba578d06b..84a46566b 100644 --- a/LICENSE.md +++ b/LICENSE.md @@ -1,6 +1,6 @@ # MIT License -Copyright (c) 2020 vctrs authors +Copyright (c) 2023 vctrs authors Permission is hereby granted, free of charge, to any person obtaining a copy of this software and associated documentation files (the "Software"), to deal From 57966d8072ae23196422a01efeab491d89eb469c Mon Sep 17 00:00:00 2001 From: DavisVaughan Date: Mon, 6 Mar 2023 14:29:27 -0500 Subject: [PATCH 250/312] `use_tidy_coc()` --- .github/CODE_OF_CONDUCT.md | 126 +++++++++++++++++++++++++++++++++++++ 1 file changed, 126 insertions(+) create mode 100644 .github/CODE_OF_CONDUCT.md diff --git a/.github/CODE_OF_CONDUCT.md b/.github/CODE_OF_CONDUCT.md new file mode 100644 index 000000000..3ac34c82d --- /dev/null +++ b/.github/CODE_OF_CONDUCT.md @@ -0,0 +1,126 @@ +# Contributor Covenant Code of Conduct + +## Our Pledge + +We as members, contributors, and leaders pledge to make participation in our +community a harassment-free experience for everyone, regardless of age, body +size, visible or invisible disability, ethnicity, sex characteristics, gender +identity and expression, level of experience, education, socio-economic status, +nationality, personal appearance, race, caste, color, religion, or sexual +identity and orientation. + +We pledge to act and interact in ways that contribute to an open, welcoming, +diverse, inclusive, and healthy community. + +## Our Standards + +Examples of behavior that contributes to a positive environment for our +community include: + +* Demonstrating empathy and kindness toward other people +* Being respectful of differing opinions, viewpoints, and experiences +* Giving and gracefully accepting constructive feedback +* Accepting responsibility and apologizing to those affected by our mistakes, + and learning from the experience +* Focusing on what is best not just for us as individuals, but for the overall + community + +Examples of unacceptable behavior include: + +* The use of sexualized language or imagery, and sexual attention or advances of + any kind +* Trolling, insulting or derogatory comments, and personal or political attacks +* Public or private harassment +* Publishing others' private information, such as a physical or email address, + without their explicit permission +* Other conduct which could reasonably be considered inappropriate in a + professional setting + +## Enforcement Responsibilities + +Community leaders are responsible for clarifying and enforcing our standards of +acceptable behavior and will take appropriate and fair corrective action in +response to any behavior that they deem inappropriate, threatening, offensive, +or harmful. + +Community leaders have the right and responsibility to remove, edit, or reject +comments, commits, code, wiki edits, issues, and other contributions that are +not aligned to this Code of Conduct, and will communicate reasons for moderation +decisions when appropriate. + +## Scope + +This Code of Conduct applies within all community spaces, and also applies when +an individual is officially representing the community in public spaces. +Examples of representing our community include using an official e-mail address, +posting via an official social media account, or acting as an appointed +representative at an online or offline event. + +## Enforcement + +Instances of abusive, harassing, or otherwise unacceptable behavior may be +reported to the community leaders responsible for enforcement at codeofconduct@posit.co. +All complaints will be reviewed and investigated promptly and fairly. + +All community leaders are obligated to respect the privacy and security of the +reporter of any incident. + +## Enforcement Guidelines + +Community leaders will follow these Community Impact Guidelines in determining +the consequences for any action they deem in violation of this Code of Conduct: + +### 1. Correction + +**Community Impact**: Use of inappropriate language or other behavior deemed +unprofessional or unwelcome in the community. + +**Consequence**: A private, written warning from community leaders, providing +clarity around the nature of the violation and an explanation of why the +behavior was inappropriate. A public apology may be requested. + +### 2. Warning + +**Community Impact**: A violation through a single incident or series of +actions. + +**Consequence**: A warning with consequences for continued behavior. No +interaction with the people involved, including unsolicited interaction with +those enforcing the Code of Conduct, for a specified period of time. This +includes avoiding interactions in community spaces as well as external channels +like social media. Violating these terms may lead to a temporary or permanent +ban. + +### 3. Temporary Ban + +**Community Impact**: A serious violation of community standards, including +sustained inappropriate behavior. + +**Consequence**: A temporary ban from any sort of interaction or public +communication with the community for a specified period of time. No public or +private interaction with the people involved, including unsolicited interaction +with those enforcing the Code of Conduct, is allowed during this period. +Violating these terms may lead to a permanent ban. + +### 4. Permanent Ban + +**Community Impact**: Demonstrating a pattern of violation of community +standards, including sustained inappropriate behavior, harassment of an +individual, or aggression toward or disparagement of classes of individuals. + +**Consequence**: A permanent ban from any sort of public interaction within the +community. + +## Attribution + +This Code of Conduct is adapted from the [Contributor Covenant][homepage], +version 2.1, available at +. + +Community Impact Guidelines were inspired by +[Mozilla's code of conduct enforcement ladder][https://github.com/mozilla/inclusion]. + +For answers to common questions about this code of conduct, see the FAQ at +. Translations are available at . + +[homepage]: https://www.contributor-covenant.org From 880351cf6be8e46c6b6f746469391e5a7efbdecc Mon Sep 17 00:00:00 2001 From: DavisVaughan Date: Mon, 6 Mar 2023 14:34:44 -0500 Subject: [PATCH 251/312] `use_tidy_logo()` --- README.Rmd | 2 +- README.md | 2 +- man/figures/logo.png | Bin 83644 -> 66548 bytes 3 files changed, 2 insertions(+), 2 deletions(-) diff --git a/README.Rmd b/README.Rmd index 39c84b5f5..9ba2a042e 100644 --- a/README.Rmd +++ b/README.Rmd @@ -13,7 +13,7 @@ knitr::opts_chunk$set( ) ``` -# vctrs +# vctrs [![Coverage status](https://codecov.io/gh/r-lib/vctrs/branch/main/graph/badge.svg)](https://codecov.io/github/r-lib/vctrs?branch=master) diff --git a/README.md b/README.md index ac5668012..bea655040 100644 --- a/README.md +++ b/README.md @@ -1,7 +1,7 @@ -# vctrs +# vctrs diff --git a/man/figures/logo.png b/man/figures/logo.png index fa8b2b8b776822e0e34d04a3905951570d07a054..2665bb7e5d0eec4cd5cf78ee35dc528be7245eba 100644 GIT binary patch literal 66548 zcmW(+by$;M8zx6ix*G&UQc~#>5GAD>k?tPNND)Cm=@!YsXhw`i5s(ro2V;P=u+a_Q ze&4k}-o^Fqob#M>?)!f3=e$Y!x|%>zW>Op+9N-HrbwlhGgM))hM-0HeLqc2_uonVn z6&)2EoW_r2H}-_s&zufghB`Pnp?o+v(Q!C9SJtt5?$nf zws_x7XnEGrm=t#Z7>8OC*ERza^<4Ym4Gq_~JxT(cEv374xri#upyXFeJNOGtdR{c= zw-2=zZvu%h5b8)O0nLH)3YEJs)Cwg*_N+BS!Tp8a!AYt2BERIVE=ONhgm^NF?hDxk zAqvKOWBm2i%RD`oT$LkQjB%f)j|$*-*wy(bOL_lFJ^L|5u;*!Cu|a-2nm=Du7$vB6 z`7v7br2sIFlU0_-LP3HPSN>}_$&mL8fqQB$wrDc`J4B&kxo{T=0`Ee?3EM4NQgtBl z0nweJ;oZZu^cwyidibioC1?6`6oty21T>UG+$kD+8%+65Xpz3JnCdl3m3WO2GuBtn zx$(5G6Z3v^*l{n4us-yqR@__azi7^Hy|H%M`>H;xC&kM2@Fa27Si`cacVnghL(Qn+rg21mJ=D$j+ zNAh@(oj@clTs6ju2)Rkzb;?F`A@XAd&nBH(PkW?XA}X>{^jnsvoh8mnytMDVUSd6- zGOPO09%mF_8({HL!;ssX4Zh#IrF_@(d964$*l-+1$e`y94u@ff6rA4LNBB^U_);eQ zhWUqe-MKd%e0;Kje$z$f=*#CDL9V~On&K<+ammhiYr3{I!epLgsIDOk%;>{+9JrS( zTI~3XotiKPq)!MF2|VRnJYF1vXX)&t808!`&u_yM*z_WS^>d#LDaj$;8Rr6mF|DJ%LZ_maR6yvCAale9R0DC{XRDdc>A)FDd;t{L_!KQt?$O0G4~AV%1fo0@D7|>$O;W`S(3?I}WQ>7WTs}zaCB2~* z6GGrU@nS}{QA8MmjM0K}(p@h=>4uUYJ?Ss3Q7h5#rKKO`{wrNGur+^oOPnauw)6ht z=Y;k+Q}KT*RqhlXo>!ek0YM1P_lm=V?w>Od{!W^R39{9LcHTWac@XG z(P~PF2MdodW1LZhBW*!Xy#Yv;)J8e5+ZIrSYd|Cdz^m+X zmbqN|CKn;7)Z8|UzY@0}w(UIYCc>yXS{WThAW!kj2I#!S41xQC=0TM*WkQ|LF$wjK z{wy*;^ll<4kYt50k_<$LM?sJ+8h)?4@@KLD8%g{&bZIf6YB~q2@~EvQ$-l5UYrH=X z;l*Es(hvae>)?8zcm8WDDDg!^+CA$~^`=alG7|2I3nxLGV6Q25MfaMu%I-Fce}#rIT`029fl+Nauc(8R4$xW?`(-& zQXlZf(NqSUGLiIIL3C-GqLX zp17=kdhX{Z2RT$0-iLyV3GYM<54?4}>w#8+q=(E+eNq@dYjf0o423gkJt=3HCMU7-hCqz<%yp`z}B46zd zK#-?QPm**5QdNlw89gGKdb*$`F$cd3g>7TY}BGiCIdj% zJUd(#_|Y4I(ZC}!@lKv_aF@#hDiJxN^rE9k;VUjl|cRSZ@zbAy7Jus4r_mMOWN8q z{n?we9JUk_XhL>iVrOt&MX-ajJ_|hHyG+y@(Cmtr1YE}-%wTZ5&Y&_v-}{I%>Hrsc zzr8}x_w8F>JH^NfSs3zP=+rVhC?D#H756ISk>7J*UHU#P8j6GW%;l;HroWGNj|IM!D4^E6s+6`M; zms~&mC8`@C)eX_S%75R~xwq;GBkSuWh@`NXrB}k@lM^m7>Mw(_T-rm*qk5cP@Lysr z;rB$FR~U^THgir7ax{bK3>L)a5fg>Y(ODjclif(pI=%{k=8Ezl3(=%{Sj_ zMhb-U;+~a|+TQEfMYn162!Kjy+J9KAcy{|k9KpfN$hm7xF?4-1F|i` zs~_Q|v$*D6+T?^hZTi-AG|CRT$u^L&A*G~vF`|TXNn@B{u`g`Hfy78mJ(<6?atSRf zY>SY&Qk9IoH+l=UB15JsMe$)<7sm|u-49rcSi&LD1F+~VDFN>4>7NHT??2y&|46Tr z0Y5PND-4FQ6&PcnyW?_gtydCzeO-J#mq7!F%Wth)0nU=$#k~2rcWfBBrE+XnD#QoD z{C6hJjZP{zKoqRJM)c&bK{V*3*^ zpOW`xzs>Ak!ZHt;ihtLVKe69d;c*Cy&TfDCHaYm;V;GpsN7V360adBuBvm~HKyT{yL&x}h(ioEI|NSLlj1j=V4+yf8UCU{vrz@q#9dHeD#kM3LkuP}O>#vmog z>IOind;DAuYRdxmBSY@xt8>F*FZlE9@2hQv@4`_X0y+|xqxZK&uv4uMh{jL&w(mo& z@db+1%bP=R8;l1%`pH_JMOdKgz`<AD7qN><%{M*s1y zzcNUuSeqgov)D@pMR+*j8~&*H>8-~vgq2!tPl7(hgqsnH$`GOR4EmiUyQe3Vp24y6 z-!&=8Hr_J5|Fn}%jkL}=;L-6pweMb{(AZ73v*=E*OlNbj{r3GCH}v&J=KcA{r7N}e zSr++=zbk-wLM`GUy%&EucrJ_oGJ`r4;TgJO-T)huK|z_g?D0N9Xnq<}A6AM1Fw$E?KlI2&tvHZ+dNX6fGbc8^KY|eT z`NY2$V$K0NDa9($Q$Ru}ohBn+Te-wkHlWWpq7I2Envy(3$3yQ$ehlLawB8@wU(0eB zZScz_NM8@BZBzcK*w+}f#gA0sCi+r}4pp!QNlC{AOL?&LAvzn}MMw8%PW;$Fh>26^ z%*n6I^Hj2Sr09Q$HfiHRJgDBhz8%CW85=NKA()Rt0vsMZ=2e|pH+)|VD4M0ZM;^yS zog%A`;_o*y1$qvL9?7NX1qpk15-DE%uJ^@M+q&QV!M~BkIQJ>_u*2;+mfX@jvz=R? zu7+ZQa2UG%ZBQR z;G=eVsu)>vP(KwAS3wbdGyHK$=FS84a_21*!74-O!_qE| z0ir0tQSUz!%@J650FYSpc2!aIAYMwq3{>LOFFb^=PIzn4w^PBV33u8fEisXQ<~jkY z-m(qUE)^-1F{O93olvgm(81T8te=N1w0}GVp6wqfi78lKR3^CI*vnT$@US=kn`Zwc zdV3YsSU5-Tglrf3NmYd0YbFRFgw~(w9m17ze?*3 zwXBWF4n$cyf9?y#G`WHnY2lupZe&P=!}u8GSxp|3TJt)#8?G+oXU=K%VKwvJsmh#8 z7ynq%y!ole6GYjk)`+lPE1_o}3%c7e!_ zjHL^>dQX~R3(%OIuEY1fh&=u&r}ohFoYjNedpM|F1kN`4MM|cm&bepfdE4{9e>?c# zKGq;Px#JX6CX5|9JCE(w1NZSL!U3`Aea6o6&EAo?=ib2?hSj><_6F|lS_0E?%Gybu z17L+%TJ1m)tMSH&S{BM`&a^1Cs{>Qr`~0X&Z`X14V2@E<1+vE9XfD8`zpIF(w3I1pH^Niuet+lvr+1b=e{Q_{7FH#7vwf^WDJGxu_N~}hV&&$e z&ny>_(NHo;9W`Q4bwK|;W&0_|?5n+E!lL6uLm5&;uwo+RTHgCg;8tH^(Vdb2s9zl; z{|?Kby>%4cmZbBTbIiBaZzL=Oh>pU&!Ljcc?FCAk1zPw~0*Wp_E_-jVOT^8n&V0ve78@a;tp8}P>{$ajB1WU{Zuypgdcw*|bKQ8PS;`QE>JGjX@T)S zgi>qW)OT;^Bxvnqk*auGUtQ}1SJWQs(gr$4fN{CuFKR}Qy^CtwW zIZ`c2!uQ8?_t=h|P}cSQscqf5B^uYC9IQbd@ffJTAT|rHLk24(6Obo>of2_bJ6{Mn z{aVR)dS=>xj{o(uBr63D6Tv^^oaSTK1=yE2Iz#hre??u7CbW~jp#&5xGp zl%J0c_Vf-ZYw828rc7vhU{MIyJ8?Lq>~<+sMbR^{oe*8uyjf1IT6I}ZHxU(B2z~V- zK=%8MA<5v>VMNmUV||A#R9_LUUp#YmB^g&0_5AT5JLpu%q~&f_QgRIG^-$uzY+2!g z-=_7#KX6#@_PeM;zpY3O&#wWlW?cE$&-YXpFzQP!XLLI$(xllE-;@ZxuPoKu%!~{y zx&Di3<7kS>t}wNLGXIfYasMvUOahV{P^l+E|GBLNXA7&`Ie*8}T!SjE8f%pJUm5ogiIk`y9 z6SJcgr;fes<#I%9!PFTds? zrThM5CCd&9BRCxt%u!O<)gKRw=ssh{KqKFI5_q3fy7zS*JgXI7JiDid%h;(B`k2+> zJkXh8WY$`5R}_qwO=^!{zi5Yk6u~<~?+hQ~P1xA%FnZT;NlsISjz>ze31{{FJh2M| z+EsK>B{-s2X3rfE8ewseG9KJ9*QV*G=s??;>tn}?ni^M z(JW{H*m&vEFZ3*9v5T_5{Q-R6XGK5!7^_{Ep@e9_94@-^q4%PjJ5mow3sRh$69U7|Q94fy>B8tLbHb{=Q~2 z%}K!Uvm=zWU%VSyv(o7f%r|7~(zkFG9XJqHM>!G%!s1q3)WJVxFB}^)BAXH5V3(6t zRQ}$HpCHOJD#wNlJIz?IsL)9PAPC7Dwfd$Cbs8Fs`pBDku z{5pS^t`Lwp1+wi^>JSN5Sk29wNZFa3Vysw@dZzRschvp|ZyO>ceI^#e#|H&rsBZgD zamOpCgyd@YuG)@?;f)ENHG$T{fs4Ii(FyDR2S?(+jxl?5a5tuvYBfq!qIUTvrG<-y zWI$U}gc&vt)gqFEfBV&V$SIsc&==%nV^|VetUH%3-|_6# zfUIV^uigeYg01k8ZT{WmfuV?c92pX{REZU^egWlg*;e}8)Lji%?R~jbrrRt>rZt!a&CRB)`VT`>b{<8o{!Gzr1@4L)>qbFRoj67~QA~Ba3((h35LhVD&HQqQ9TWCUob6vsq%#ogBgY@1p$7QEs3P0K5>pep!l!G%(Ps zwXBNsV+R%z#tf3=j&FoF%G4CNNa;T*j!Xrzz3=v(UYtI*DUUvhkepE^!-I>x8Jm() z-)5Dd-f@Oys^u0TL#YR)CkwpJ|6!K74Cvoz`9jdh~XHL)p7^9 z=`o!VJhV}|XCSUj0_=2F7=-q-6t<%*jaDJv%ogON>+2NR-hUykVEV?d4W}pBRCqP( zm{?~J(~NV`Q;#DZK*^j}9cuek{Ua|`=SXQ1Zjd*6y?cGeDt96lP4fdM?tv-^zr~w` zwx_6Z*U&Q9A|p~7@emGC-@}^c0fO|IlczV)$_ctcI%*5j zs`L8EgMjX3-&Fbb!t(IU^HjZcxd-6a&qIs+N)~-dd6fu2%jK+4{CX<}xcdkm;=EPB zoRh`ddHm2zmHvm+DqZ@_{_E{~mfByOUk5|NgfahEL|ln~yN zU@N*#Z%Qmr#FN`EPF^#M;~)%&*mt~q3uYVKJzKX9li%w{Jo&mp0H2C8Z9|9B!E13V zXpplj9m|*jETVglLxkcIDqvVeQ3(B@Bg?im@K+wnP~uAY(VQ4JyTY&buONXJTYbT> z;1&t9@mnD(Lcd4Ru`Wy`TvJmR{NiOq6YC$DpSfho1s(0`s5#%4f|4dq={=-4B-BiC zuJ*NH7=G3yBfP;a>3u84PXS~q%wSD}Y_lK4l2Lv%gBKgzvKuYj_$Zo(iiGh>4R>(K zkSR%><}vA*FW!We*^s|NOei7Dst=MyTp$ZZ*Vv^hQ^zSK@TtnAFo#yI$$nI7DYRJL z*f0C^^b`=;`tFlu-^h4uh5bWAt(Dgg8fSecWPsiQZSyhNEQv56qrgV%swZMT0pr(< z83m#?=>LxrklH#twe~xREA!wj6YIQ#fGIx7NRCRdbpM)md~SS(pUv!J?7ocbRz*G2 znpC@D|ACXFL8%p><}NkXw*`)kB|mirotL?8W{nc0Jl3@*;aB=-Y0+Pwc~}VeWtxQF z;xtIZ(m!_9U}Z}GBNWTRaj-xw7P2Em?Xp1-)P0hcgRfq&)`#4Px z51zn+cqrlqCSbQcnIrTAWVKe*0Ez^o*Q^B8 zz0Zi~@t6ocJa`DgU>Hp+kHZ5(AM8kDMnej2@O15&dQG@|n6+Tw6CnRja z!@A#x5Z;0TJl#mDdW(Tz7J{OesAmK{Wa9dzpZ5p<=mESDDmKGv;mv`e^JFj&)mbXX z*=f3Z3h(O)D4XN+;mEo8;Bn%=%$WCW4j&bpNs*}+o9_K%^w@GiASvSjDY=3$ZY-LJ z{OlVO+XOf7?_CiUN=gFuU;ZQmT*q!?Zz-KBek%i5|I7?SJr!8xo(<0K$p5Nar_c8F zBLkJQf?vPxhM}w3m&s=4+VG^Hl{?)@McHSbwM3%fZh6RU2Z+U09VP#gi4J-<1P_9; z&i*Uh^?Z)YuHg-KKWCE0MBjE@y<6lnOjvwWPOxH{cFArCU<)=-UckS0VLl05l)vhG znk;CHlv9jF%YruKQ~sM3l6o7GL=>*L{@`(+e>!-@?@iqt?NX6!_tE!NYl+A0_<^Bi z?oH)8w^kOC_jFW!d2E_9b^3j226zdog&x1`&d+*WtYLE)BbIcPr(3|eD8S34Ey9J0 ziFJw(>AHX5r~Sr9@ysf9tg=x0!^h9RBHqcG;Q7&aRa9dl%})53Y|K z2wZUqTfJ8)QNP6kC122~|J4Auv#2nn)L$U+ldZmub7e&+lF~o`e-{5*L>w~(MI5(H zCZ*5E$;kS4Jb~}3u?&tmt#%IvhHjjqtRo@=SUDl{p)kqr;Ez)E2cdWg2OdJSVxOm_ zM!*XAf0L!0Hjg+7P_HaNi0nx;tR&$A$33Pzr3X{WAQt!(F-W-Jku5s=?Asg*S z5Z>9DU%PfBY;VO+Jlx0Ckd(;OwEnhxY?Cw6?mk8tPFurW_>$rsoX;D_DpiHWCW$d~R-N@i)=zhfz-mO%8D#>`ksA0nuS zZP_;l+x1oK)e(zUaAH|kotwlwtE=r_Fw+nSWH)We0R0;XQCKYER_o`bl zVE&v^Mk$C*C33jUjAKX|MCHj@M^^6=YudyG-xcu{2FYozvGfaiE5IT3v-EJ-iX>qJ zJK0vR>eR}op(&}Oc+%@2iU#VemruxrU-9p)U*l?>@&w@Xq#FzPHAT3X#M~htepF~k zi7)4No|r6kw=l9PXWFYzzztYBnDdbMw~W=lfdg8#ZT7DGaL=|;gFs=BCEJoUbf+7u z=?}+Y#K=}P^mv?>SASSoolc)!D+wb&{5K2xlb6m_N`oCQ$38hha%LMQ}ykLKf7s(O&jip|nogi*69Vw&s26LI3xx6h_9FZEvxbEguKnEU0 z1op<+$7j-A4K_WJrjZMKCidh<^>K1RSH>U(EssG+ru*{d6cIrao#DL`;&ZyI=_FKN`CquTtpPiVt@8|CI<0gg3$&^-&7>k^;XS8D5fZVUorD-bltHfo0 zf1AyfPwrsG$$C&xY5?hSW64Wpe_4`CufZKl|1x8ILH=$kXw*0n_Hi6V#QnJbjpWM@ z+{$sTfdlCQW9k8MhT3$_`?8EOHkIdmsP5UoP;d3Ll?TVnAj^_vS`;mV0Jw1#3SXuc)nSWq&&9o@~_a2GY@4v6@^^XAu!my@9 zoou%)Xs@=fgn&Hu)|Ff>P4`=l?PLGIHb&kC_sv+Sj1^(AYnglKQ`UJVjuA{>sey>j z=HMNYB`NfBWYEuCSd%+ z35qrCzsuO}z7G2D)WDLgN~F73xAE?=ggu0i+~kp+*sE7+<59DmrhW&%NHg;iD_l8w zeJy#*AhQaTHAGpRp_9_6q{KEJFf3K~mk*w#PSVA#^76U~Sc0u|XI1R#&+y}j;=bU4 zKvdvX@e&>gfn&*5H7%PrM`)#2&_D%uFOY}fAZIBWvDLBjX{;F%IBCCcY7u4gA5ZGc z<=rRXCAi$VXS~We3F60nWNJNOJtC!)@)`GuC4btK&rL(Hu`vMmU{U7BS)*5KQI4Zq z59^zfgVq|eh1v;D3l)u3-`cj;moHW+L!|=PFavdo!PZ3cfx9Pdwwro2LRVig(5;p~ zH8a;84G(bD%)kwDEIgSlRDGE{@?)14L)pq{?<_AOl?RRe?YIb3D5qA~)~BzBb8R0V z_a~XZZ6Au$PgZ)|5jK`YrxL!LKyyS(;0b2MO1D0P^4RLp$4*n#Sdi5>6}eQ7(}o0M(7!u_HQ!G%N;zN6 zYN^_RHwjm^fJifr7renAV?O>inOBgUEpAP?RFxTE2T5QO5X-d{=W}Ct-cGx zD-?cVsQomDpryBq&rbd{6-#m+v#T$^@pt^MPIRgt?%tx#P^Z z17ohKSC+<3+w6V2>;o=9TgPDr*@;wRg}zEs?`vs9D*qb{wvxiM0;htnVlGSux{yJ0 zt_I=-FQw4cl-#wHCGki-YzESIoIZWpF13G|>@?oRnRhrD#67CKnAtY+c8zxI!B%}O zrz7S26I>mN^%9*LAjf1jF%xEL)!-^LBOE<@EL8WIgqdz>fLk~6NiA-HIsmr^4Y|?^ z^&b%kh_35QHzX#opUl^C2&ACe;}||*`>s#3TN20(0hiGr^=#87rBJ|+b`qE-bI|Ii z!7(hXsK0yb|Lmo)*SuH&{<5T)FxgDg6cB&qyxJ5ZStBJs`P}2Qr+DEv=2px`fR~o%^;BOFpigdKP~UEKBQFWZ>%*~ut&@#_KHT1ou^2f`sKq0 z8j@Nw^5rRCH>soKmlx1PbcnsEQ2mqN$fiJHi+kf~Qw{kfs>v$HhdNkqzW?}PrKr$a z2>a7Oym^C;FH*o6u_ro(ZsXq`_{$N2|6=*b5F&-C!K#03v~hb)G`2%?sHHiHArg|G zx&)(jTG@pxn2O`=ONKMd79;;D64s~hs>%qHD`XiZ52!RekZ-E9wpF8V2iVMkv89$w z84^(#BXZ6Z{Sdxi;mRB&uhCYY?O`ig{VL(0NXUT)|LqJ3G7?R2>Xu?y%J_^7_V0UL z#6_*;lMm_ug>;P^X{?GpYqZHSsri|(VR#do+2>g@OszHZU7R4H^fg4P-Pv0Sq0t3e zzlFRSr%TtZ%S3b(@MEmVCzGkWU%qgEAVlC|U#?mw;6-U~6-W(%P;^CoHd`Tfs$rRF z18rl7v4+;;z+N=hO$p&{$`3pl9d~c~)+*-iDR3y} zD@1`-^7>gCX*FtIetY6BD+ddlL1dy9szY`I8FplAjNaF~ooJJ^d43^L;dAu`t#JC2 zIbxxe*N3^?-kcWJ9%m{Fu`vc1gl$(%P+BWZ%kqsYH?Qa9+PsNy7`pl{CZVvM6?2}; z(YnF7}A_Cmb6s-k4pOgY|QnU*QYVJ4{X(6h$5N%m#CH&a)x@1n99!X9T7aGIdBJ z6vOs?)%<&l%X#antVw|5AM77WFpdc2u?@G8KlsO_PMl-;STOMuqAz%NJfE;C<4Ydj zLKlRil;rNHm5lbKy~2vmcCDXW7xB#QLN7;4jfDE%=;&o>!b}@DbBAkAE@oNgeeS-R z#QIWmR2o0W@(ZZ`U_<8>aRGB=S;hBF8=vE*KApZWho-(D5N}~ObHIlk(?OP$6!kra zI)*})3v3b;CK|X;GIvv}ZNz*?2W6)K_ziQ>J0{QUtz|Z)SqPe`e zpwuS14z}5p&VCy)3t4mjf1bm=SIwToP^jhgF9-L|<3*f~XMdhxHQa}{^gQV*+w^Mq z0vd^(RdTpwV~*whKtW+*okTGsai=|(JWhIvXQ6Kr$V^QKnjQ&0?I2t-)NQ1@n7Y(b zmkzU2b9WEp9(_~2Nb(O!_3!RUt%p(`ox{q3Vo}%|nM>6a?^~2mLi+A^x8H|*bYCrp z$-;@}n-x1M&OeRe?JNW#ChCnVVRg?1wxZ|UZuZNZn5zB(z#ndW-<+!3wsB5N0!!lu zm)eqg3=^xS+Rh3ESKg&oxNaw;RzNtY9%S+w&Q2fRV)zRNh=GIR(?FV1Z^{J`f;^~0 z4qt*R^>!#hu}2hT01g8?gg|E=i;C7VU)-_kxn~ax8Y-09>ykk0`B@+9`RM>**&rsZ zn7-lj@bDELOza~HzsiDRk(Nhds={nchqM|^WC~g8Gg4>h1Acl5Gb?C@=$x^llM=09 z4t<_IR~)AkWDnM2xKZfvx;-`4R3MIyFdO6Uc-lQ%h)1cFv_-W0$8FU|o5oEtZTI`= zNzKL=Xk;9l^RO9%ZG;;|;PAR!eSw2hPn`Ww#*bGNk#%vl^=n^tut#x{p>{tXS;M?}|l@GND{ZnThYnuk*3-EfC zsk9nZSct4Y^9o>X1hL9d4Yzm(9^~N}UF|LuhQ?~tX_VOv2eO7w#+FncbjopgJ*y80 zuq=;|%3zY5;mdDZ?Cz$BF1Io^w&aYSnl2yCARbhe2?*_aeG%E$#i7$!0HKzw8THMy z9ja^blbhkA@KChN_qQ9P_oSdC(>J1GhNVU}!>w`r`sNA)ptOdz_O9JJbJ{|1v6^`32 zv>jny%pQlN05Vn6*R+c)^!v}3=Jq`yGY}TQp;62$J(;8c=E0`VFiK)Pj!KitoH2t5 zI-iHcI(EYj4}S?{aD%WKN#|{}#&W4m{Y;e%X1QUlpdxhGO#FpV zruug1@CIG9E8=Td=#&l(Y_)1Sj-x6OJflpkqu}vM!mo&+=;NNGatvK_5--iyU#`EZ z38+Vo3{%S&Lnu+wthG5h;-9#3M=14pUsPl~qJC|o$&6@|xKh~bd#y!!4FZFZAWx05d=wL`w%9PHD8D2mvTbcRU z0dt9wZ-->AW+;1PYn-Loci}opNw*qRwNIH9#XPS<`SFvsF1PJ{Qnh2U0m{uDKVOMj z2>qA4GZZbq6t_Rz=P1}1FgC865*D&2KP%6%#5^&yCS41Ct~0l%s2a*vE{pg^^5xcm znrk`I_m2Pnht)Jc+UGu$UjEvrAnsMuPb|o7HGgvDu zd#p(R1S_onW99hT%TFV#C}}lWW(1XheO_Oi4H2;_tkkc0V*xndU(uCi(sW^7SL}lcXqTrGv>%dX6%c)r<70!b$JRfaVl?gv@|!% zVg(omvj4U{$_KjJA-U@ObhEL?@H8TlYUj5v=}XD1iYG;ppbx#E#nQhaSUSE5%`LG3 z&X`%>m7dY;-8k3@=oDhdm9?Iy^G#J z-C2j9j$C&*uLL#i3?%?}iy{yh4vHM}AIHT#r_xxA9PYV#gs+ersI>A)=a9xW0yKVo zJVrR7CyWB@hAxM>Feu#)>ZzZjqwZ(ss{k?J14*U3B{kMO#$>}h0Qljj7wKB%oWxTB zg-Ebs&)pJF_~j4#&gSY?qF)p=atR?vrTDMLg^#`OkAp*ChTnu}DKq!p{X*xoUOoz- zNcH}p%3f1@cCpqvt9~R2$`X+r} zlRVvU{ZQy&ez2_6m(TGuXGBP)f}+>NglILaF1Fp=yrk1;KJI*G`lLo<=h*|@Ze0;m z)I~1DgT?FAsS5@ams}V=8sIkhSz%KbpZf4ie(jE|iI9d+uHEp3m_uy$wD~jW@bo7J z*WbH8l&SUjw49nxC@7B9CKU$eiz8fa6M9p3@)BH`L53;JUO~tz*U{-X%BRqkX%FGC zHzoD?#h0a;xeL+@i?!wIGl5u+sBonIIDFy00($SvuE40$v)Z`F+`YUbMyb+Lm%JP? z*Aeg*vg1%=S%=HQOms$$O*1&n1%3;dc8fKrM*mJ1x2xj+K6sw;X)HTwksb)kr06vN zE%fWIO)gRm=uP_ryuA&c4v^H*#GVc!?YX&lz!!9OIFa}X?(acbU+Ts`%TQS@s1zvx}(V=0iP!Xcy&(iYoK})}B zV_Htzxul!0$@w10yq%ycKdZBXUD>B8&KISX9DR~0so!5$OPN^-WQczDRp3B~k2q1E z1eL$wee-IfPG4wVYk{v^8;JO&663l(6Bto&1)GnfQ<4OO^P|s?hde%&-gyOm zcpx^FzdCwCJ=6TM{S;7CR`YvhoG*ZFJk{YL_Cb|b`3D{ag^189Lxdrz5ZYxiv6!P!8{c3$3x2oku#h01c#Yq6zhPo6C zUME~^|7NZ44K}u(_e;I{MV|6az_`1?rXRGie|&?TnKyKD;xMP z2BNy%rMh>+!073!*(%c-t4`VBjh*KY4w&$b>VrWm(l(LDjNjDpW+Z)?fnPghZ7Vk3pYV}C}DB^CMBb;GId^(^|E$sWn$QDO(feIEu zBGJ9w+O1#UJ#HgJR`U+__JqT}Pdr&Bk7bwQ1|!T57A2USKBQR{*`OA71cjiqQ&NRH zm#hh{X}aG-c2{p16WIH&kK`&ZX3)KZYir`V-KAOjYfk`x(2xtH0_}S`(hm97_kMOG zT~sJ17HVPN=-kmaL&kq+i`cp!QqxN`KhsDE!@6_$!UDx75!gd5PH1SPqWqJ=zaHR9 z;aH179^$uYkIouzP>xmrf=h^`EhAI^d$w@rl;>h{LGug*>A{wHS$xZGJh;*9FAur z9fCr$27Zyw`Z3{*wT%di_@9nSswxW*ERc2Y1n0MN``M5HmyIR_d2*jOzj?UEcYRKt zHfdTdBX2eDEMS@p4WT4>`x>ChzNFD(wpIAi>0K@$0crpVTg5C;?6F+t7pPWouc$tX zEVx!{+cNnTmG){Zg= z-V7^U;-bTS-mm=<|CVV50Ta39AdFZS8=vO=hc_t}Y^5Z>mX}@fD&_(a-dzNh$dZ-} z2ggXTMftD8sTYBcNxak-)8RIRfdS<-S^^>K+vazBuoXLBr_?p=RP4M~xPI;I+CID9 z(f#%X$?)5VD_hi1(Da9>@M{5jl5kt$Kwj!0YF|m6GLt&PdZR(t`DLg5mzsQ`Le+mk z*iw=V6N|RQLiXzRAq2~+0-srE1$A3&>Zve46xIWrX~MT=kN>`Z&^2th3*Yl<7oxrU zVYf_mvinZ)#R5JVm=A?Iuqg`h;3s?O*mFG^Li&w4vQ^6=BlPqYQCBlXk7c}*oT#0Hmj==?HO!S-NYZtos#~u zhEiK?y>Ey!bx)#M|8F1CUPO0ukkz#2_8;?@&m`D>!q$BCB%Y3vvKjmAE`eE1sXr=y zaO=!{g*4FEt;}h6p+OeEAy|_k@$7+N&C~F$On;#|BVsq+f~A7p5PyGArYa*Nb^kVAA=p{;3)2MMT+s9&dBpqrN$o=96a^zedkWxGJJYansPT37 z0JqU7UmJzQ!it&@)$sdj7anVwfmQ#Q#&q1aR$-+&+R=iiVRYEg18RtR&iiz!pL78~ z@z4z-;ws(#9D}DDGvflOhuYSBfz<}1Y&am7>o%)ObHPT1siC384| zZ}Ve*2S414Oew1r@eTCLTJuX?8zr4JObTUuzVUnaX$s)-O)jTPM9BOF=XKCWs>!$8 z%-fZa-t4!0v5uCUyjawXDl_?*u-_E;3H_L+Gu3Oj?1!NJ!byy%*>gpx#O30;9^YQby-LH6LdP!~gJKGH4;iVOag{BkYa>bhSgca3?3lTg4!Mwl4 zcxIAw_sIr-3Q_)HHkpr8haM!EQ`lf1cH1+EbjY)z;uAGQDvFNU`5rA9n;dOy3o0zq z(sXGwuKWH2u?~utNiCakPxL4GW*pKNREp|K$icqiWM!yxe=pisV*_sdju+V6%&MY) z`FqrHNdvp)LX1a@nZ{{IvKjDtr9O6>cg@KtOm3ZAzNje|&ooTZs7pYHuJ%MMiG4j@ z%Y1h9ZSHjB>)OrIN5yY5A6LdO7msco%E&)_{3R!;)d?XJq*rsXp#9SMhsJlfPHKsS zW}ti)^9;&ee|GSX$H}rlu~*C1n^Y-HNW>J^7=)GB_#Ykw9^MU0{1i5xmfU!)H6#?H z{L3di4L8ocf1DH8iZFTiHC@ZWDfCMSjB-4DDh7K@=eoXVeKeq`#GpLAxU%u-a|cHg z*CaN&jE+C`B}@q~pxl>d6uONKW&|a@{1bzTiBCLOc+&ev&#?bu9H&(^(B4yF+R_i1 z8&~?|7@9wMO&uCpOhNY{WMDx0~7lX zedyD_FLzhve=}^Yh7IQwiTeFJQH9`=QI&u4d}?z+c{V78EV)eAx+$Ta2EI8buXc;? zeBrGZ6ZRk#oCZIimfV8=O)r8NVuU6QZHo-t_$vR$(N#u8*{xBf8w5$|6ow9I5Rgu( zp}UdpRFIJV5QYXt7*d9k4(aahl#~u>yvMs1zgVys-Z*DJyAE|nleb159ZI8pwMKH_ z?=7wGzt}M7gv7>sM=G7e$U9Yh%)Ktn3mU&!sHJS^HCOyZkz# zv=1Vl_;lE8(T)_jO4UsDkQjr+SyObAKeSIUB}j6|TkkjDv@=d;kQ!^M7UkCdMiq*e z*LEGcGGr*Ky{T1tBN(wP9!8>`sJ1Bf_ZM|fWD^F`%UNxOcWYCw$`B=aqmfNP2M6ak zBj_?*V27>Ip0E1gEE}q(#XkM17bkv6Qd%VGbpo85FG$b$q2x~RkR&dX?XrQ~SAX-u z0NZ6T_!VY3*1m>}=;~z=)N!g*XT&JYBAAutu(1wO7BL=$((jo8rf~LWwtsVYG^6x> zbZ^=sDt@HpnG~;yDBTmp=(AOu*&%kc%BD{<_rIufGq%FEZ=U89TE&FW{1`Tyx;zz2 zbtqObw@>efOx`#By*Ca%*>9Gh=(`t;>)yzmc1IGjm7p|AcH zlLutRONx%1RJj5S<-BRd-?4J}aRKQ6dUT!D@KeKrO>SL-c&`Q3}djfrWd(AO3e zYy%M27uPja(VedQbj_+NGZJex%#6|>oEMC8N>5v$qZ$Z)vKLCHZS7M0gFOn~=D;8B zh5x1sLdT!4SIAO8WitQg%CUWMI}!9x2pVxzFgc$9$}Uf;#mL;=Eu3hFIZu7Bu}3_h zE^#0qz#>I!KC3EnygJ-3j+baOIrVR9jB-tiHyQ@+ih?Lwb_%Dn79;mc=dkXd07R8G zn3VZt=PVp@fAs!_^Y87|&%xdu1mdawB>$g7%JtdcZPc8bi3d;oi=@519<{DDrDhO^~Et$boyvC{?=`5 zoq}6aZcDN3on+-Bk3|pznK^wU@PqdRp+^e4d56rdeEBBnNN-&#q1j~V;Y8A3W3$9J zK4?fYT;k`G=Bmu6qLyXaUORHKlyv8}pXe67h31EJfOxvaj6X%x3zH&qAP-~M!(D5^ z)L$!D+qyle{n4TnxLP!ArwuWx7weo_a{ncDbf{MCGAq=565?&Q>djm1>uH{l-S|eL z@B*RM5^t}6-KyT8+36Et0_R_YT$0mr{>54{l1ILqC(PXZY~_T*&qf z^AajQ5R#*R;rBsHF{z~qO;4|cTiB41dUEerwK5qp39Jh%51m;}KZf?OmD$pb%fc>< z_(kIpFVY$Z(2Yx>3%dB)lr7H1)+Ks>$-Mujxj$Kam9Qi_kav~f_ISq2)#8;N0XdaP z@CpdZf5CG&b|ld_S!*DQ6Noe_<>#N@EAQDUYJ4|~4VZ9h0N*(Wb)kN6ZQW#g>!vZCQXPoPDC0Y|A}c z{^&)oThNM_zYdc@QHm?pVEvX@h!zV*po&bCj00}M>)Nvt$Aa+0qn;ydqH$|~u#;a= zk!|%w3j$nMtadZ)!2jb|E0Bk0<1*$ITz} zyPA8>SB?7TaCdz$!HFd?*5~y*@5{Vi;;w&!d}VwfuJ5eVdg&VM2WsZapbAp9=)mf+g?@>Q3)#BWef=S^bGrXBr`x~Eu|dUH{_%~@ zD^Iu3=;dcaBP%zX6kv)tuf`7iTVpvzq4p!rlTAwfRm~rHYs^b$ zO4O4ZQwH~v$1o9?d9Hk3IGtix{KT|DR?O~wTp==sVF9;n zaZa8t3-uWuyP-I#HIAWumkfrS!6Xl(41-UPGfApEQ>o^Q8tT7-{sh+iG2~3qZcK|H ziV!QQ-%={>=(R2PRMXdu&{C`|!r;0%ldlDFV!2PV>P^D0bY=oEb_=A$5*e4LWg8(c96stSOr^Zc zm#)$7D4x~VfzQ2K8162G{KCTJrz782&-)$v z*vdb7jvAkx!Qe^-5(0uhKN$`@6N;4=K#tf{}Ml+@YawpW=1(#=*kO zF!W2tR|Ajhk-;53gJS75i0S8Kl=TEe=>imFopEGfdh;l4J>v;1ejAD6AfDG9$>Kn; z!oC-79@@{oQ@(wDJ;jf|T=($~4`;3ZX?cqe>Ic2aYH}>tB8+g@k5rEq_psAr+HZRZ)9-B`V9 zCRWaSbaH6gQ^ zF-%r*vttjB@u6~7sg1QWG$*Xijmu#-f{q2KvjmhV;8dU)X#J^UAt zj;;L>PjX_8n;aJG7f>eNm5zK^XtgQ&QIq-fdb1iE3BaXqxyQ%i`2ZTdF{d16`NdwU?!_zFpVfR@wV7m!@u4tz7zErgn2n+Wj! z_e83m*{E2vT=(XB$QlbCxjVx6ROp9ezD)i5jU^otl9b|92)_d^9Pjgbm2#O}jkblq zLr&`IZQ7T|L>7i;fy}VAo%i?T?1O9BdA1cvnEP7}WV(BKdm;tamMj~Lnu`2S2hU@! z5izFh#oE<5^0|7s>-A~5(l24LmG3RGAd}~`O#Sbe!fY@KtvhNQ{qXtTL@2TB;dY5oCFZM?nOfp7I&fsUT!a`ZixXqwWUr#fp&WUK69 zuN_2?TNF)vZMZ7a`s++YI^q3dQh50>lJlJ1-`BHPcM@>IsQ*JCdy6yA6J?9$|Xhzf%vSwiOZo zi2gm)fh`It0<#RXbd_i)OJp%uS5hqx<@^3GKc$6Dzv}8%iH&;c8?gQdNzS8dLD&Z# zDqnr((iQTtrIVsV(-Xl zd+$zqrfC7iem?FbZMLGvYOe7;%$DZhKdKxdAJ`VGS!r^Sq`=Rxj7bzLCbTA1nP*O5 zMF#q+{f>nbKw87YL$&`@^w`;Te2??&n_t$Q1CyVkb?c|X&LuqxX*7HH_4S2mS^av#}cG@CHnD9QmBT_fp zObqC)=WiGS);D3X@zHPyguj_AgBW|KgIH{`hu>ew%RFj%aYyLK`{$EmerM)eWp}$5 zlve(U6A5Pz8p$BbMt>qgLo4`o&*`CV+~61_@_Cw_uIk1A)M;zv!tkjUrr&NOnYnvM zVW$=rL#GzXX+(H3aJ#Wnjg%n5+ZJxYf7MOtvOiTfsV@EZX@P9WVf%ObV&OO`_D5iQ*&X{j&tM< zo|wA$oOS%iU+DZL(=XAz3!{qMe3~KrIFoJBy}&9!xzH4Mx^B`F8E`W|bj2-RH?*V~ zV$dQrR7>_^-+E{6b?-}SXVy_=m%uj-8v6v7E>%=3yfH`hGwi9Kogt~;Jj^UUXu{jO z`^9L-WZQs}p@4ZznMn`TXvog)AOsl`XZTmbDS^T4Fu$J}Ze#JkBQ<0`FcK359`-NC z;uPGpXOiCRUKphzc_;Qv@T-|C`ju?jZ}H;|mXeh&EZcBpoKCZNyRW-vNLTjMuH)p% zkaL>2jajmWMhsMt@;jhZqS?8v`2Ho#>s-$N%wt7xa$vdWX7puphl%8&tcOYtcCDsb z%>PwK+RE4$x{3y>r@Wee@0Qt=xRFQTvAKALPwtdgC3Er2r9?@WJ($>73zw(FOUu6P zW$wK3WHoK8U?0gEznT5{m+J9WFlS>0SyY6uqx)UbcssQmdVt<2aLM)MCyf)#xlszR zaHd?hXZAK6x8X(HHqN{&w>M6IUf{GY95;r&B#e(|`CAl0AGTuK*;b*_*f>EoP;#X5 z8GLmH2s*z}ZlM49chzM5pkXlCUD#nOTFLc2dbRtH0k~)QmZnMs+QdKB>vUfBj0vV3 zFzXwE9DvqO{M#sFfFTIKT(gaXeLcJ(8#7zE10(5-A!-o~v9nnp%r6j=PGK4xh~89t zbvAGKUtYS~{7G*F2L1>&=t70QgFEWTuFR{jw()p^$>2gn3i zgP&Tq(BRK&{MBEQ4|@U@w@5y=XKa;t zSFUOgg?x!qmbe3c7K4> zRCmQAHq||zfN;HTdpRoEkR<67gis5C9lF>vJUoGJV`TXc?ljXi55IW!c+T3ss6BuZ zqPeE6Y#j{|emrP$aog_jytvdX9=O4V7C*-_ADAC`vxQ|*oi+P~A`pObh8cX^GJ1EOe1|qv6>YZZHAYEqA?W#JG)iiK?zjG{`n*~#fTT+rR zKyxJJ^Nm-AYg;%wM6CWTf8RgoLS<_)`?9GglI&pcvr-SYC)MmZYYK3>a(V!uW;<$X z?dO)hafTIc4Ws=^&Jf%bu&TDB^L?usYY_f#qxMJiEoq`kwLPHAlTi&2qI_;(f+bG* z>?u-Ifyy~r70V?_eN)i89t1lRq0B(9%9QF1Nu(2-IjUFAuk z8`)-ma@D$yNc$vIChkg0>8DGcW>GeZS#hJfO59eo!ane}jRBsVKr5EWD+rlsfXio( z)YMZinQ+wzk0+{=u7MwCS6lkjAN!DFaeU7A4R@~3lJ0yTi;eGZlqL8)p6Wv1C(}Ub zPX~kp3!h54CS|N-hShCmSv!7NN4wVuNix;@<=eS_QH(vV8KTLh(_sQ%DcA$G5yV(~ z4JJZ?p7z>~;O;8jAZbBueGiApyoY+KI6PGu{(Fkp9JecKo{j^)Ivp5G@pEOix5o8- zrW~->uRH>D>OK8FTk(cCEz%}y{4^=m;(-3+?@M)XCcl~#yFV_$E3$CdV)>0I&X#n! zXg@xgwbvLS1?D7hC(ZrBV|L2TdYumRa0YqDy>M5rz^lGLEpllP=ieX=*UJZ9vhtY| zBl+TT=c_UO+P&|cu}Nj_tZ3lz1pyP^&5x}6xL+zmQ1B@=`*DrA%z}$m2z*O4ZCk#H zWSxYR&Di1sv4f%@*U}IT9+=&B<#)11D^ESw122U%U*DpZz(j(XXqW)Q4iU#MCU>}| zyncIzHi~Zmdl~-382`7eK;i4*MEfQpy|NNAHRq>%%c{AQI|1c63`z0TjsY~L?`;HW z@Cy8{^2nLI?P6}nag+Ao6vtFe9Z3nQuBZFFtM6}~OI|FQoA^4At_JQ=#>5bo%14Om z%80P)*o5c~udAbRWrhgeRvY;g9o;>RbBGHh(BMcNkJH64TPt0eDxL++ST>n@)7+x| z7NdF8z($f`x_E=6%N_w{-i$e$v-7qq9sbnGHe4xhO8G4vXU40h`~g{kQ?XK1 zF0@Ji^{}ImP@D*mYYRHZ_RdNxqc1;O7n^;xev019gB#}# zkEg-VJ*&|r(8?>2j?Qdo;iocBD`}1yCXb0NOLJCR)h>6>t`X~(9UfftuAx@LGS_^H1VQM_={-t| zYe6X~&{;c9?P&}UR0KJ>!s&j1mdbGIH`|Z_UNeu2U+iE5I-Nrny^(ypmjQO^$-u)s zWI%yCw_bic|79mYNuI*t^-;{X6svHVv3ZfG_qnO{|Y{p#jaM_x%#krvg8kCaVG@9$Ouh%azrG1f}meF~&NY&_R z;!~8t&Fq;wu>;|;4$MP_Q~?NgK~xT&_lq*DC&*cCQPgM|CJt0}Ga^SetlB!7{9;G7 zmaTkr$?HJ^II(*41468xG2^*7fLw^r$%1Q?oVSGpdprH!>e{oHi)bvGLLPvjP57K< zH?k>_kTepRb3&G*i<31ofE=*f*kkrST3pn>pY(U&&er)aceZE73_u7-fO3?ue;&WI zXZireq7T^_#4saPEB0Y*b*w!vn0upojvHoe&YxoQB>BGB@k0#M18lj9T~5Gqv^m!L zEcm{ZsQFf zO(_aWuGZQtOsUtgB)U*ru8CeFc4GsaMM}QKO#S#RIx4b(=!B4m{kQ34lpN@l<$X?h zgwYIW*cal7Z}kN?6fY`_ln4~mjP<^;Sf0;4Eb18*yB@e4lh37>DUROGNrN@4301Y$Dr@ zk~dLZ=5FBE+U`tXnXhh%{CFn^77F1N|G$JyJx#txQO02WjD15=YKzhIUYiN!Q{l6S z;uKE=c6qbx3F7bkrMqU?RkgjUqgFmB@agFKeTdou+&-nrio+fIhqRv5mU>uBu}RJ& zNty2#hZ?>+YaI42pEkTkEI@bM>W<4g2fSME_Jx^k&rmM0 z)SPpG(IIXtJ^qd7tO4QYD*bG!m=eBsQ))WmEW{KJUigGGOYz&H0?kU#%727HbrcW( z^`U5dcROz9A;Fe-e^IvCe6?=v9dCUdRerd2^2YQzGQ=~+M>500zM;$VDq&(VbF0Ru z{N%B6@L+YilP|#;dXu8HtOS3C=Kta}*#JuPP58B*muSaqmB3)j^uO+l-w#VCS%`{A%_FV91QKp)=N!g^^*Ci+03K7B%MubC zy>`uz35Wy=U(|Uj6nMGU>LoyQJ^y$;@_co>BqmXtN?l8zQ6=*+2PI)iGM?aMW}KB% zWjiq^Z^l2>=6SOt;ka>(S;wuyJH0n*s0F)9IKzIVJhHet->_5+DJ ze#i*K#dLd9YjUaX{Rb}bAGnajHkB)a-!F6sZ12Vn-_&!frFFYcArf=r{jp4env8WnJ+d)VG+elB}$S zs+N_#(=Esetep6(qTf*_XjJH>qG&pBg5#4pPG$I`o!gs&1J6Nz@#v$^pafIQ3GQZ& z;g%-GAROny+V^gknA!V+oBzLcxF8qrPb0XX$*dZT&L_U!axKo5cZZ~d0FXA zYTsv-?wkFj01!9VWSbtxm9fsl5kqwa_m86p{dE9+BQ8zJ`aaH&eFg!T@i1%h*f@?B zyhHWM>U;g3+DsPX>Rjk>Zn-_Nr0~_7z z0@7u*56)pZuVyfN3`|Mtx65`*YF3vx?v@NDIp|P2DrP||xvLo4G#Wl7_13;;&gM?a zf3ID9Lerdh>ohc10!F27IWx?|#g|`tA9Ks`#$;FA06scxZoapv7vb*buFoMUGQj#m z$gAe!7r(YSA7cIFoyQZo`PZGUD#rNoVi^%*#P#6!migWUx{99WX3quX?e=p{q%(rO z9a;68MGA6nd)f2p>lR%prR(b<_TV)SyKnf$P>;99vx$wv<66r1>w*cq;?*6Ackl)N!(vb{~JbljYSYEY-3on*A;g!LAi^Qnxpxum~OnDuGNLsTZQynus zJ;Vo`!B8yKr;~!;)>OUB=SkGXo3lIb(1e5ib3kUbi`&zPOM|W|M18G6VKizZb4wu8 zlx%xp2tq1S8K&W3#563)pdg~J~S?>fNzOf_?lirgj0-YA#-RtVD=RD;tK`FVdDDN+SUlAmv z8)X}8=d?V$qZy{<|0u0Rj)Eo- z!`cvm2TG@JK@8L3&!9OQ;6I+LjY70vE8x@QWLUZ*@}=nn!0S|sh12c->t@nGYEU^c z+=Y+=N`|#_F-}Nm%br6yIz@SFKzQ-I*r-HhYGJ$z=oqX}g_Gx)mS~oBY8JQGnTWL~ zw7PPcK1^^@3a)i96>k(|hERu;KsE>c(};YMPKQC;<@$HxtM9qt`m~wAUlIoVCCDGF z>?&eF*A%|m5Z&8BtEeJo7 z_-SqN##cvN!6EeJSY8}mVRJ#Dqm%P6^B(C?Qo?s+Y*v$>m~tHn$gk~mRTSwgU*WIv zb!_50=gpj4$B?SKZEx@zOl>j1AT7E*kgXFo*^?k<+ZdIR?-ee#T+8WtWWxCq??m9% z&F<9qA7YYZA5SvnZ%#H#ttQ;Un8~PAJpP6}ea#g2#rX7kCWZwwFaadZyK5_{f9TB- zUBy{k7MaJ`)TX-3$5s_Rq&Uy-tS)3h8|U>oWd-LX7GzD;u|R?>Z0!)Ag;jUSF1raN zz|()E8?tSp^9~r;7c_SMvGs8M_64v2R^|;IKBi3y#U+%g5qP!M8ZJd_NeVO~Y=kB> z8?KbflZn&XLF5tC;{OeKlIj+aisuxRLb|clkJtBly?KA?Z6y4B;3*v8*bsCWh$6;( zK%)8iwzKq?+n}%x(=aU1(>+3a$!v8*BY+M0UXH4+LIrqGdj=@0-omv{uUATUuFsEY zEdAhN2<#(Cp}t)+1EwQh4g?Uu{=~5G;QFrb0dCGKcb@e-LTan(n99DNK$b7i1#~Ez zl;b8YRgM0XeWWWRo*NqyvL_P(cG)+=1!|^78%wZ2!!G?cvo8bh1%7H{5_>zO%l*Gi z>*#PfaI0TDnGLt~e85i^3(o-KXK`t>eNAH_l3k!Ao42bBxx#|Pz8_s1D4ZgTC<(OC zi;c6oIW4DJTkE3jRU0`eTovseGUD5Jq`Qz7tSJMHKSs?qTt*!9R&Cv-gF{>-!u3sG zJO|->PNhFhAqF9@t!*7oLGjbK}OGC&{*6 zeN4(HMB@@`iF|xy_fH;op=<(P`VjrMuYH~~uDX$CLM^aYxW0L%D8F?Z1%!WXTuD4L zwCHrC(q2q5*5>0&Wb3k{O3k83#b2JVbEQc#P@{0qM+6dUJ|@D2`H@bSHSY%7xIGX7fdlAFvIhMt8FX*Sxm0k62i; z*2&iBOOcRAQ%YRd#bQhJ%9E?v_PD>`7dPhl^X~Yms(59X`7}EjG!JRKk9G<4!3&eM}1Vm$Q=z!T9E3r0Ls&rN^jY>)a=SJN#&jx9v17j)Id75bh(493QJ z@`)@Br&3c`T5)$f9;@@zJ?R}`H`m|s{S(#lk9-E!G>_-`T`Ac);^hW!8l9CBE5XJ! zvmkpn?4?QUN6Z4#CT9sJ0PSypbnUJfemR|x{GZ~y)dUZxD%V=Q(i;Mlr^faI6hrxz zfyXcp;D*3KeB7CNhQTk2mZ3PL+0f%402TH`mK^Hy$7Ru7%&0Kf6zHHfMOR%52gpoy zEQ!bOs1NVY!S2=u%-SUIoIYldIA5!i12LwT4zCo8NiuCKhjDvOGJnlwUSDT&=m~Fx z1B925IHdW~F-wSVkSO8690W&MAk$-BU%ELsH)oVk!bL(1@xSOj^*+Xc)AqbLHd>Q^ zzZ;ArW7}(&0>H8hb@ujVbxd z+{XX(xAnc8F-+}3+{*&-5tRAC&VAEOR3JS7%!;}CW(EAgbzL9eozUqd6-@6beSWfU zjWnvGFW7eRh=28NdWC)VYt7e?Hdi|F&P)-n_j|R1YW_a zDJA(5cIvOE>D8P=ZqNARV8X<9(?xQAHL=$xYN)2Nezl=;924AV@%~upFflpaPIqd6 zd^cAJ0OUOr+n}fbZLDbMxiN=lOmUv_j=0_{O9wl8N6A;S=wdwvICE~F}IWsSzk!)m^1I@!GWzVIJ z+90H-4oon$Bw8a~wvAbc*&L;$_+ais9_5N?+w>kKI5udh{JD-d_G~-YThFj}qn>9_ z*}`f4HkYvjA4;#P-mj9azJFlX^6<;?e}}(%Js=@*Ei}B?i!d_)GZ9}bkkU_AbQFB* z2!Ekc$7}E72fBc36J5jP=%R#H29n6}ISQ8GM=7bh$Glb~L=!%oAvTN%dM=?Jr*l(4iHv(lNv)f?g!7>|Ion%p<_Hv3;B(j`ybt>1^B_( z!>ekWU5vpV6|2g|+s^C1bg`cJ8N{HxX*l)ETz5Qh;C^W6=1uaj#t4KFxY&!R3|4=D zay;{m8#6CR2@WS9lPka%Pj6SbDq=jEw!q%@mxUXg8imSHF_3fDX>V<8p?bT}SXD?4 zYv+X|YRiywC2J~<>JWBsR2f($z$+Tjh5eipmql$FeEt%o7RFGDiViMWL;=JD(5)Of zwZdt8(L&^QgQ6+2NMObI@j2J^`8pkKe! z#9GSQg5VO65E1BHS(c$(njAd{d`hkk{LOAe8I5a&imj4Rw#E~vC2NP7ce~Lc3G|UZ$Q}_e~B*)DYzv% zr|*qG4B*jFLad6o+E8c$Pd(PP7x)lL%xUSK>7UvjHhyNC-)Z@cj z0GxS~7kjLQXI?4JzXpTr5GJ2%% z;e%px+gh1rHTYM2|D0kTNj7I&R7M~$LHq|jp2+p=fYRIhD=|B@Le^{CQ`xmT+Liq% zN%@(9wwItNEk|2s2NA+O*1NVIAV*H2kOY}(@byC7Yx2E}cE9*Kv4PRq!Of3$H%S)J z)7~P(&Y5~M0@>-`>3rh}@t8_2un*H`L|&D_ua*y0)+1EIc8%LA*nl`!E{e z4Evt9oFA-=kAlj?v$1t^gbGMvyG8Y zoibuvjx*HLG&$sM9xB&yiypL#;`bMenipuROyWCOSs6t}kEj7-!ZF@yVDa8)l-S`^`i{`JUyJlg!x%ITV-<;-i2`TreK&+y@fw}0 z`dI!e&<=QJ6YIpFeMw#S|}P-fT`Q@#uHna z32fNyO+w+-ypd4W64-N%mf#;YrRKY4`XZM`RI4tLDyO+@bT*)I`gybX$Fx0=3a|}i z9Q05>umI~6`1s9_kI%O<2Ev(;f9lZe^^|m2G~Yhr90&1t&S_*k5FsBd&5U-%Q>UEk zfCi}bdl)eZw8R&r3X=_uCUHT3nYQm%PH_B}9G2r(+*->HoJJgM>b0fX%FgglDW+|o z3dasnye69e{P7Fkm#5i?x|7%c=Vb~YD^MLi_uDHQR2km(z3nqWyXDJIA~6keCyoE@ z;YSGLZ*7ocf0OpHs33G8Q!uzx@bTSZi4jzeJ`P5OQT;X_tRgwScB1|DvSmlb20w%O zj3I2CA~|@~9=qV^g}!`?=h0rRSNp;RJ4$^v^o`w$HLV8yMD@U6%#CNtuhmRnp#qAF ziUgWIJuA-3fnw}KD?HZwOfA4!=9R(@45 za`ua2fSPv#iO4^=NnF$E#@}f>E-knE-07oW$*oGE1;2N7aTs#)_0D;4+r{tXi)M`r zb_PGNX>fQZ!HwdSq1#dVAmhyndY#uF`8|}02QHrsYe&^icjL+|Nb9G*mJ_Z$vg@ef zXtGaIRYy3RF;1{Sy4!?wuV^!fK{o<}n5&+SZoNp-PRk}AN>1Su#@BU3An4wq#yyw1 z;i#_qpUPbG#kMTa4x~lAvN}Qs=o|RUu+nQ-zD>R_|a6Gl1Lrl!1?zeT&g)A^+LdxuB+Rs*)kf`LSm>d4Nn?tamQW7$cLr-D=EVJH~@ z!fc<*-Hy(%0E*Ppi{K+o_1j&+ioC*ey}hTm=8A$HLP@3Vz;+az_iek=nW`?WQ<1%- ziZoqf<*!||@#3xTbg$_Z*9yS)bdd?&-Cqr5+# zcqbTGPJSoLfB}C;$;xVRX^n8@^o#c-WtPLUIJ1FGXxw})cDh+1t&D(!1(i4`pdO>! zno>|>pK(yPrNEh1B@^*3cIOK?uYp^pb?)DCuyg*1*8fYU9? zv-oE62X}|EH4@JTD+UdlO#wb%UdpFie@(HwYqfu4N(UHIqNVA7U)K=YG!w<6*A z4ud77th|8AN_ZkJ^Hxea;t{>)2OYiDBlPviWDQ|9CyUjWaA!=ssv{f zpBDn#uA7;<>GSc>i}~uj1V9YM+%zh6STE3N^IR@)i&#hrO!ic4)@v3TA>2nFpJ`&o z#3Tvdf7K7BSAm9_*|c{3nj!=pTGtAKG7t8;ShxdmPljW27u{-TmNC?SFjcJV$4Od} zgj2Ish9(ZwPCT={t=xEJ8f-xdTD1~2t2B#FZ|}5(Ova)U@u;B1R1MO9;A$C$ z?C0yn!p#OAyJB#qFH?|#NJ7NstH=?5_NZximW=^BsA7$N2tX6|3y$jE!jeYA$d%o5 z(bi2D0^0Xk=jf5O6?bP-Z-MV=9QJc80b;^*)324hF;LDYVNSCatBBx}QLA9YgA)vcthk_hT| zvO+~Ux7=GfdG26BV1vnsK@ib@U=b(z@JAjL0>7eu?~4!E2Z@zO*9^slVpLz%S37P(k}_Blkwj#ZQ~dli+u&tJ6mMmCZOIU( z1Fl|ZiP|@N3`jirBkpqB50xWP?yjVS16mBEf4ZN9glNK!(Dn3Ze>?Wk4Vdm!bi92@ zph1;BgAjYUG(__1QZ62Cn9)7w#a0AKMg+CGB_m(r%)}>n(GAat@qpW@QvA^Y6KIO4 zbQvWmNVmSTOK}maOVuJxspriu)UF-xKpK?FQ_-T!sb6m#8$L^XMHBEf%)X>;{6-n5EHq2Jf5Oa)XEcmTw#@Y z0{O?a4$V%e!Ase-D;X~TDr)gLQt}~0!1GzFg?RNc^>Qq4fPaGN z_ucJ8-MgMcbHd8L1sQQm4Z3>CzoZuLpdIbx)tY#MruGB4PPX8%4V!kg}ZLfHU( zJ@^UkVA(Bi_DC+3a@{F@Y1V;y5OaYrm|3ZK%+OFgima?ya4x>hO(s-vdp{^}K8FiX!t*WIj?eKKJ z+|*jQGl4H#hU^p=(UAOEK{0Ic_p9PqtZdME$XG385K6R@GS^}W;z|rzVxlro<`IS~ zob$GJx&oURfXusK#bVv=*=^?pyiZg)ltP^d=7q5;SZ|8Rj5|X7Ww|qh3kK#@#__JvH8W$EW z`8~CE`o${KOvCmIm$Dn1sf^=44&ohWB z_NbZ!>=6D-n|*8Fx6Zo%w(pf{>!v&iAhf1DIWyIsb-vOO!rrNWIrDveJUNl5e_GD) z<{~Ei?T^h*(bO}imu-$C5y6NZ6yb43dvL5JGOct81{BkBSJ{OcpfUUDi0 zH?z?vz&29txQNmqo$UeDE*JZ$tvmQOOhA=Q1a#*vT74(VaBiRFuA zpma_w%25yHTYPe^$^f?Z9%fy95%i>#>Ar;UIrehbeq~w~gjcv_C?twbLZoRZJe@by zmU9f&IB*1d=I8jjK$>~Mf6E$t{Fge~vOcPUdTg(Je?P>C{XLMPZnaIOY1Wr#2ARww z1-tcMBm^1pW%g4Frw`Ck0N9C|B3_a>T1}Ej-cCO>`vgW@C8%qSds^gvR8C+TKM)p3 z#+*I2OR{moEj|wGSIc%$!OcEAdK#-O*umZ4@|R$fVHvENO#G_g0b4(`)JiTb`LE$3 zh`HAKpVQ)3%s&@{pF0z}9VXc}NhcPLv&?0yvsTKi(j=qIx_HKbKv{Zi#=bopJvT`; zxXhnx*ZLBTDYJH=bcyArX5P8^6TGRqV0ReTd#lgatW;U1s~Ip&Ge3S8;5bnF$xay3 ztn&MnYF;5^1l;?;*8KgiJ(B>{{+#hFs}u8(E;*4M)e6t%8LG&VMUx)|PoRD4sWc71 z$(5SlkM5 zKN#D}pCIj_zk8u}UQ@{IYV_r}**_;7CX#{J4B(UrVhyc8lBvc~(mGcgn>cy3PTaUM zz?Xf5S!$O-77=01`rqGy)GOYx)QwIezUDtG#7b}xsl4dL6oF0F+LX9$+KW$-C;jT(*h+OonS}Y2zL4ln10KpYwKk zXu9dkiua?mM51>m$o=m9vik)}G!6?GolkOW%E(J&u?+DLi*}APflZ$-<3KlU@6d&L zuhYLeN>GH|dUcB`HoFPLG!L(WK5(wvDRRH7X>9p>eWq`BAg|QGtEKsrfY1~4j|An} zHI4v8R|GBf?cRD>9Ui^l0O_YF`Se|d2B^-Jk8l6qb;&|K>F4qyd*jKI4^I@|NNKN) zy%b-@nR(?jVFTRQb~;>z)h@BrPA5LDerWT<-TJABR2JdgccqLb&P;bERKMy7o5 zjYzUB0B2jckG9e^^17v9gK9P5X{&=Svn{ zG>-`aa_84FqC&woAk;bP`Zq-CpK}iE|LLYBW2rTuC@7%60B9&R*jX)E(9_%X9wMIh zMD*Iqv{JYG3rdr+=p@sw{^4T!;NVOACT?IX)zW3Pq6AX52c2bA62H#6}d4ezs136S>(fx~PoAq^HEb*Lg znqI)2q3!|=txnZ-eW7;2?-m0ww~G4sB#^ZaX2fZvzkLwy=YB&tpFF&>{PDuGaGYOC z9U6KA#|ke=;AX$jlYW?U3HB3P&uGnn+mrER3z%+#6Qa2cvD>a zg~Ux&dC9y!PfeUnej1L!y61595*TlYf2$-~T3Y*ey65D9j@spUAi_1__rd~?FR>NK zPYx1|wH>Hk0=X4CW^UGP{{W-SHZa<_-Vf2g!NjNg@AG=A&=n2!)TxxH}H_j zIZMH9uKK36|nUqNQD%UFBZbuc%7`}BY$Ma1Gq<|;T(^FHd!&G1Je z86lIlt>VB%?nVOKJXt+E6^`V=8A2Vs=Ow}y+=Q%Ie9OvB^sz1xR_w_&J zYkR`iN1pBBu&Q(+Y6Zzk5%cH#?-w@IrCGTvE2Qe$JRX}qjXmVn^kQZ!y5|2 z2Dad@$Cf0oP)!(PuNKyaCh5Vlf& z{}j4L%r8%_|CUuZy@L$c$2K%h57poGGJF(mN_J9d??$p2HXdMvNRMEBwjX__G?uW;7JZu?Wt z6+K(a(vBE)74BD4{Y^CNXYDm!fxVcNNT|)@S3w2;qv#rg*-}I?@7oq)PYwEnKdAg`8$bJoWOr;P@Hl zX)1U^Tj*%$k?9EwgfGjCEMI-Em!uS9ma)PM+{qfO4u4W8pSIqy(S zU}oJ{`8DD`+ir0vXI>>M>8t>Cp(z&JwN?5UFy`ZW2IvrDf7alDWaGu@OMZP2cI3Od z1O-fbSv|LgIGg=aABUp<#(Rx0?S^_ezTLq}d;zdz8LU7!RBfifYJZYf8-@5^edVXqb)!lvC z;6`MCp1{VOb$T2v;#B1f>sTT%3b?1)e*PdAeqQ7>^8aMkzB*bPGu#_b#T4`}|Ni%i z*U3o7+@_R_nM?@F{FzS6MV(bNhf8o22eMXqMe(=Qug$En5GLy)%;I9&omYZ*6dJzn zx}R&Mf^C-f<*`G5$B`1s2LH(A{~{$ev1ObFTwy~_|Kw4R)YmBRT4$Gc#?5uP85XipOA+|Jpp&hLCW^pQSGhngad(xXOB5nVrPSI zP0Z$*kc#fJt=6ycvVX2W8ok#4%4`Rt0b(Lp6&TX@g|B(>gbLrinwkx1jO>H$VCP0% zcl1a$=mj{OjgPslk-;=5V{sDaoyo8{vhpuXJem}Gsc=pli|Ng6?WoD2w&6oOP@`gp}#g_xjvX7tCzbVpwa>7g&kEd09o#R?)A0OZROV z=@;q&%TeuaE6 z<$0bmmKe5p!xm0~Nv)9Sb%$AV4k0Qlp(EIIyIN-Wua)o+?=?h?>gX{gMV}H0@%FWV z&bxga!JFo>blzQ+vI4%)H3=%@ zkYFEBryb?>u+RF|JEFbSIl4JaG5GmqB=XOAZKj z69ar+d>-EVU*8WO*%|C2$RM4}wC{{kL#|URiGB8FKbo%*4V@NTb#<8FsS_*}%N24S zpL*@vC_|~B`|gbena52js>993e8VGcT#P$$71gs1n0Neyd(C3v3RU|#a=kNR?6_`o zxHhCTp*)&sA`N8dIzvunInR*GXv3}7Tyn}X;Ejh!GA)2*{mG7jPX znMz^@qc0rHZ3%bsQ&ih)Rp<*doKtJ9xIUDa5v_xy%Q)nEO;y|A>KDn)m#k6SKMGhZ zwVgh`gr4j3G1ZtSVS%r*{^<#4AH*Zx9P^EiLVb4g-Ud5nsdKjDM(rJK_!NpqDQ&Qi zs%SvsK;$#zE-{VYg`w&^yLp@Zik^ zV(FjsH(~Zkq4kOBa*!#oQYDa=>TghWJ`kix(6s zgh&p%IYTyQf~sSOy(rP5GpQdmP`!@bHrjh8`ai{|YP4Q&mibq%9TrxwO=cx{)Xg^i zk8WKiG*j0~A-s<7?d?~r-){O7klhuJZc`Toy=>DmXQx!{#u%-b0xwIeehBgpH4GM; z|9SVm9<*@W06|G&4>D24+e;)pCgJr#m!>>?={nWtf4=rdHYr>Sl|Li*kcojrqVbe?nW1{#qP%*oq7ttxd$ z^Epgwss7HCUp` zIEc0urq{L71>E>7Gw*(Mb%&OH`Qh&kF-fx9(uA0W!)Xw~vxR$fpq!U;G)zm2cam_w zHEe<411-L^-kKVVK1}bht04~#J-zn&`jx5T_pOfzNVktVj4XC&9yvjMREpI-y(!bO zoGW5^@k9jnG?6Zas-abN@6gMVF5}GGgIvPOQoDh{$6ScYo=+25H{;|y(QJ)*O{`|q zsj3jqb%(ZkSm0VaMvz;f$K>{K#nFuxEQU<>WlY9992pz*RPTV^oZnR()w1v&xWF>P zEGpAko=A{;7%s*5r|^af4pdHQceXx%2E&yZoan?U}?vnYbu zdUWZ=$UCr!PR(Qg$mg{MTBi#GAn6*1_VnpOihC zth(bg*eCYxxObX@Dq+R7bqrbJz;(#BIoj%FSCjbKe`O|zpx7!#sWIvB;G4K4e~FD= zfIal{kHI0^S-77+F81tYdc_})c6RQ}O&yhL_q0lt=ivc|mwfX17=qh8#RK{ymL8v| z=^D8LiVo&wo(M(3su%*C^?f~x1oS_AKK4+c+t-^nUwsHIEzL!1F}Uf7BKMLa!GEhz zqo}C$orZg*JXaU?rbG<&a2WLX(oc^RRrK194#r$(yy@MncvXmqnNF5{Yg^XMtlPW1 zdPSIADO4E9!0ZUH4mH50iwJ2!Zfq)pJc$%8hsH>on~ z(2(sE5-e5)mg1^q@H(Y}yoh8|!t1k9V=L$D{f}^3%Qb8j;!D=PE+y1f*=I7^YiLl$ z7e$3{+5{uKuX`-;tiXPX3K)4EgQz`w^D5w2gj--2TzwvU_|6nv_!1w6d41g5YiL`# zwFWrs1{}@pfEJBLu-bxp&iG0)rtCyU()-~Au8I)barPL}G*kwr5nXiIJrY*U|0>%? z3Ra-Q)h$7LtAn;|$LV=oRS>n`n*`9p}j2$x89^G@tBuR3a_{+%GokWMVl-OSGFi>pj@dq)Y9vZ zbtNO?F|Vh2yaK;ejT+{8i6_1RY9t>jSfjoN6_j{o0d8&P{GjSl#+|)m`s&y0-Lp&N z*wz?=Ymqn)IB{ptkXQE;^5)yOe9Eb%YEv983~6}D`VuND<|+2M?fwe0FyM49UmCue zZGw^^o|RP7l(YCL&%@pB;uW{0kS3HWq>$iIT!|1%aXYpfNHn@XNJyBK5m!z35|}mV z2tOS^<9`#1gKqJ%#4lQT4)z#V9HEsU!n2=G{dVV_r-nFeS0lpLtSIh8OecX zR(pZh#XLIEJiM+~NW9P<7@tlIGn=0;p=G`$$TK@22fuA=jNKLy=;ml3_%)xfnb$Nd zm@)M#8V$h)_^uEk{P?n%6c~*MZpQ3`soxWe=-KOj3k)9Sp6irFfXbu$Rcpejs_-h1 zfYnOIayKZ{u`J-}zw^!Z`uc6ak=td0FK4Z^;CdRqypFM0 zDuT^lzTs{sp9IEN{m1W4sSaC8c?dKjZY&Z3Zh$;WRIAAbSYrdnt<3?pT!EyqOU)my zC^wROaHG*u$ce-R6#CZAUV(&dx`WJ)uvy1?1VA%6Q+^j3QGETfz7#Quux_;F4U;O$E&0 z%_pz`3Qaa@#wx;rAJmEt9E{GeeZjzMg}?Iq#n$Upps_lBS`u9R0_u0uHRfaH8sl}6 z+vou+lAnO!3s5p{WFudw<#2_V%{akSrDrt8Vb~){*i=`t_hj>?=SVi#$1YDi%hDnP zvX}6fWFarX_K&=@^Hx zb6%eMUHS~p(wNsXS9QNr9X^beHzKu18U(ZJ$(w>Yf7=Tm>*Oxen}Qq8AcnO@_NBMNZR~}pebI7Q z=D9<9@IZ@;ObV_|WPShDiGM1O#?Glg$lb_wHRD)7UmsK%1^mMbAW9<-ktJv>bxcf^ zFMaB5TRP)TA!mQdEcanOdsPcByZw&e$CANOt}c%^4lNv~kKhT}XTNffm@-ZwPPd} zhEpt_)4bF8MGqrc;vlr=(=ta{61VAM3+z7e8m?!rHb53w&%-V`r@2l`X;Y(Ip8uM6 z*8yP+-1OSPKPKtHw=qMk)@VBuEEQ;D3uP3YYAAlMsTT1aZyb8ZJzky4IGG+=<;gag z)xk9|V9VkDA6_`JOx_JaLAg97Ctw>(S720L`%=MWu&P4Qp6@M+c+>aquPEFBa7Tro zL>KxJj49PgN{wMvK-+(>tk9HRbvyDNx8o=Hc>)Jp<~Qb;86)BDxHai|o=--i^NKum zsd?cV7zIOD)&J0;A6*f(|L{!3>ua3^Y61bfjMuXu3NYM;Fv@p(T1KMQ)|hfDf)81v z4r+liM7&8FNu-p^<^?)c#Z-N}iY~SnM)Nv|&U2~BU-hO;GhGLkNB^~hJ%ve-48;*C z?1`&3OZ-|5lUApz90(EWk!c)A@YD6*Hfv|;=lCV%^H3=2zrDW^71!@ zLvR{cXk1rLS2E7hQ3W=}Q@OP<$>k0HNrEmxgRb@Pq3-Q&X`du01H(m;DPP78r| zi9(N4wwB7p&oV3uC4m)yMlDX=rCk5|IV?8ec~Rv^mtWhoElejcLy6w9$E za{EA*l*ZVz2BJf%4O_!j3){OP%28d{{WRP|dZF9d3tVT}&DJor!ou!t6s(VR5Gjvi z9l30h+;BTbTY_C1S$jkurM9y@{KL=m`Z-(m2e=ffg#~PJu_8UYyNwD}lJ)IT%hmzA z>zVp)L&qu!1h6rFEtjUvk=I&=hq|lOg=Dx0PLU#fol5_NTRhST2y19ZhI+{Ur(o4z zE$$_QY*d=V_x&D1?&3wX#7BJ^k)Nsfg4_FhEf&m%MwHt2P|H1BKjgr>Qlzu}|FZmT z#)ygel3!%T$87K=tYMe=C?igzG6RlExjr(yF=D>#cD#}q=OmVXnW6DdWSneetbMrZ zpbM3dLX(ZFu`=l!vv=vSPRO0PUCQ}&^XhX8sK1j&2bQjouC-33YK5=eDcE|**s(Mm z_u(X;l6NfM0>L@j3^q`)|2p8Sj*ldrhCLv@0d_1KdzPh1&&Y;aOqUyAt!}fN(@)~t#h8wFZ+f3{PNZ5b0P5%|bp9jrD>P92PN;a_{(+BN%My2`G$<)dpiTj@w! z?uD9v|vE5gZ;nh3{ zZyul*n>CK)N;d#FgOmG}YPYsZRLY_7d6O7XjMKWdhPc(OVcQsCGZi`OZBMb^H{5@M zrJb1cS#6s~Ze2kE_|}`>-W0Rr{e-}CyQ^KQUQG#1K=RGBy z<;xV)vCqj4E9K{xWp26hd8)$r?-+@(pEXNEZjAoG$+W0+{?9>h#gR}!wlSX6o4Vo! z==y->$J7T6B_91aMUg7pv%xsA3?>I@`O&q^x$x@Hw1fOdb4! zam#vb@U5RyGR{If&S6l{B?OTo_@n}MK2@xPy@bJ>-^{vFfzj0YC{!helN5MCrjOx- z*+_GR5wi(MI?xt7%M3pH=ah*k&XX7mwTmI-FJ-i9?KrOPO;&-2$|+kyfJsBha==A! zJtaJ+oXQo@vA@=^AJ;K*v}vHN23C=WpG^A9`(?H^R7tY=3qRh_9ac(~TB_Nta^|4q zcJL3Y-IdoD%*~9f3t|x^j z7voC(8+!el3G18CH*m*CJ5M{|z~GKnIa8kM$Rf1sgN zB3m$F70NfUt&Vd4l?0JPbX8DAInXi5@U5!{JeI!P^%hI1CfxX z<---6NPmjOmRhihJpY%9!W^oXD%hb45oL+np3K+N8M;@oJf4{uS1)1QatRz@fgbx1 zEAWD&zv(#?@cvPH?bcV~F4^NXG^VCPYX8(CJZ%edy(u-w4DM9l8%;ThF$f`4q&PKk z7q_x655tUt#k-KFkjFTz9G7>Rt~V%0gfXfK$F47z*uil=TY6H_3fS8vr;;6c6l9z% zU9Ja4%baw|DN_v<0@Jq4s}>1yrppp6y4q{wu3>nRa2cEQ147Q>peMm->0yz(`aEo_ z?U!`)rrCt@kMBx_EoGD$=Z%Tie)b0j%T4nB&K42LAyj_9-tb6HsM1-z|2DY5`0fD+zZ|!=!|8(eUR=q!#n_YwT@AuS~9k$8wPOm zjqGXD9Bvk2F2$zPo253Z)d`*~qWFcCyq!TiyEF#mZnFFK1o|CB)U)s`-l#tTVlOk% zNph0jXY*`Nik^_pPkZb@H@1^yDw(D~xM4WVXz6lB?LUe1rj72)WTR)S4Wk9&;*}i2 zBrq5D)RPxGvz-v;_}GDvf@5!7B)glPb|Iz=T;@H&*?cho669w^1GB>9(FLp<(6Pw; zN^S35wd8$dw{&F6N`f5;u%yfqjX9S1WcmFH9^)NtE+`?*F2{~uM2Rk@8ji4i|7#S) z7_YZkrpEClBR7p+Q4Tv*Zn|izo>dVR09Es-#Jm%m6>BlUrkqH zdj+B9hNb3M%rb)jjTX4YA9@QLhHKe^5q>@|8~8yLzSkS7455LlYbLm_KX$%gr+Q}V z4eq~fIylZcrpijMa%@d6N}#^ea>S#Q=;(ZL^>fTkf5dq7#iM2nKB?8k6+F?iIWFdM zx3jRAmAvze4EyWlr}fuYV7p}Xb;Q*47{p1Op>;3l<_jU4;{BSZyWEJZp=)|=E_D%j z>=wGaT)od(`I66I*rg-KyXEx&GqMIV2>FHFKQnQUmpSpgseuVgGcN}&cx0JEi>&y5 z9w4^h!ij~f3*jp0Bkd#9e|6w9FUDoCPpp zeg^HLHBz{pU-37T!`&%JNALDR< zi)*a-(rEiVG)-vKcl=PDBc6CE9*DS1dW;Vh3-a`yL05)09O5m=2O8`(iOWgYd1g?u6&!-fd zA5vVb!3^*XVZOT6-JTW}+iqS&G{5Ej4v8JCG?DC5Y#ubedwXjp6vMuqoGUr+&k&#z zpU`3~zf9;qXBkxmLlL{=-R^Qu+EH^iX{rjt==e}$Nx~1a^7}y$IYVdyJ=3o!T2f;1 zWa=$pukStTK$9)kL5~rv&SZ+i4O%7pAsiWpNxkWKiC?FUzB}Y;6a(giT8k5yO;F@@^t);V7zDushH~I+S z1+$LB>e%E-di(41FD!0{EjG7=Pu0mwPGVh@vru-rZ+htxQR;rcx2{~XE|vd>!$Z+g zl5oikiI-rQsExw`JM%A))GIElq1g{>4=T3d*RTWB18Xzu5n>Tbj}+gDE{%NwdeV+Y zhE0PhoD{pY2uh>sed5kQh^H5q7b9}`@>jWe9L}-uk9`j1%j1{Az%9X*Az++H>DRE7fHS@YIB)nDVmyw{g?h+D=PqIk9vAE(`B|2{x;&WX8RFMwh;@847 zs!lmoN=R7knC5+VK(&C`gY+;0FrjWA#$V;_BpqiDb#z%&t0I!b*~q_bSHm89@SUW~ z7kxOPB0DsMJ@>x*9zN~JZBZ|0oY{bi9-fDIJ)M)}mP+abWZBV=TD+`)k}8pcEx2Oh zS`sERwDWWkO7^FHPe?1i{-hK$&l+B|`@59*4?%7~;|4Q^dk#p=7)xFAFr`Pcj8KU1 z?3*@gnOQjVuq*Zzbhj~iEpZo1KBEYk~<@H^za}^+Si zl=-~efB}F;?i%}b_t(ju2*I+;xHAnM#+Knt3%)r^P{hmISRAa1oqQW8zgLbf66ab( z-aQn@)X^k2%r6R$@QOm)a1^?-Oup2zv0+mU9!xi5PQyiAQk?#_fJ&Kq09eYsTQtf5 zw)lAzEJ-OHFvQB`m_bN${$k)Zi4gzeraNYQe4k8CJHKN>j6d8B z<>c-I#r#&xjINhko_%L`@aGtQw4LL)XNHSDJ%37gZH0A?+@Sl7|L=s#R1E_W z_XJiwL8kQx2|Z)_c-G1?j*XuOL&>5ek^JQvx!pdVk>_6A>b1xqckx65INEA2Wn!_`#O`l0+%eC~M7{^Ywak~&nS4V_a2VcW; za7qqqYUCitrBI0m$6~a>pX7**sYFLUdj8H+kOFWA{FC#89e0>nOd8F6)Qm$lr|7^g z4fu&WvUWRtO2Sj(fcxn>~yP#pG$lWSOg^5n`RT$U}Z@S-@T>U(O)FzA;UpT%G5v|%x zke=zbgKmdG0DUZ3J(bt%Yb8HyS!Xuh<-oJ3CN=PU3`DK)K&u+2I2&a4hu{H`xxjm3 zEmzH6pL&eYbITBG{gSYjF zYnzz?u=%^-ew>=>F3iNWN&$2zfRgpjayhX`auKIY(WO2J&g&RfrKUZkyPm2Zpk`K)&2Otz` zuwqo?Hagz&PxOoPY4x(QxTkEqlYW@kzOC-gJ+8tpZ%AwJ#^|4EqnrZn2*vbbM~`>Y z9$Q`Qp@d26pM63m+ki&ZAeM?;RxX%jGv#~lu zu>N%WHQ$RO=`X{9+Vr_;{uD>nuJ-A_LXb#LGysGL!mm7J3O|m4Z>ofMu+T)6a}|1N z>Akm8#O>uMq;sW{t2KAA`X8M_3A1%JYb6`1zg4-J=ZZ;U#*B-Q8Idslg<%5RSWnHP z`}6T~$|z)ktgy0E6^GTd31r5mn0;@euXD4Wy)#m+u{M07K`mWvt6XU}5UsMTvgsNI z#y(uxVw=0AD^9mzEF^nt3uZd4lb6{{%@UoPRrrSTi-VA})^Blw+*E zdl?)g+5$~VwN9O1Pd9YxBFcTc4UiC{H^^gaz4JIjuDUFwX0Pv&k9{QkP^h`nRR#Ur zo|C-cR8Ym2@ullyqLM7r;-o+i>%qh)0VuFe%Bcz8n7ZDUp$#=~kn7E*CD_oINqQ^f z&z;I>WXa*CuH?ZTUo{Y^P21Oo8|k+bC*2;Wl@kPPln~>};vu!_>df-xoOtBYc3(SU z7H7t11K2hi&+0yucs12^qjrlRiso2|Hv=k~ZYv1$7Y73aG!(o968{{X5fRIp0|$B34Ga`6{IXAnPH{^+6(!JtY9S69OMn?s!u>B(j6-Bg8YIDaxxg`6Z#TIpP^p^ z?OBIoC?NrQ2MCeu{#YhieZZO$T){v$^jdL3@kuqiiwr9 zecb=E@-)x|*>2HEwWsrf*D;;rOzZA2p&60h0x>9#uQtxApU}xVy*zj+@&q|}@kHW~ zS!rk|6jluv>RL~qf(0$ku{zZ`HRHt2wesUXQP>Irpk6-DtIjIXHzl2<_`doOA$5LvsfajvD3 z*cNGnv(%}$;9hU99RGrya5xQ&lszQ)`m%>^=xrLx!bc*{U_6E(N4LD(ibDY{mi2vE z1D#ZogO1Cf_ih;p*kL3=?kS|cfh@RA_RfFL2-~~`S-8^1!|;ybP{^x`3j1Q%u$L^(w#QZ|i_NW(p%vGCHzPEmsjea; zgih95jfOmafqzYtTi4WWXah-4<^L34>iss)Heiz8w*3=TM*?E6KsHIZTx zgAi2ncV(m0_bhNj`Hv+6^gKvOxQ1Mds(Syms52G91WY#LbXEeAOp0Kk+2=aUr*>n# zK*uq39}XV`K*Uth|2(N#@{hry=X2Vc4~zZTB4AWBbjP^b=zn~Fh1W>B6R|o^g;TU{ z5P7bqv4(Mr(|uBUWLwQOX3)32_s6D;2bJ%1_4e6AC5(KYs8kSduttOVWKC=%)muj7rV6zRz8B8%BYJnM zJ-p75$?J_`H3y8ilOak1V3TT4U@1%t#-j|eJt$#GLbX|RE#{)6=g4-Ls#RyDO(-Hn zU>vhd-yc*6QABUw=xnE{azSpSIjh(!wiOzLME8f!?c52KUgF#?j>D7i{gDn*jt40D zrbbLAc!U>FtnJ>7H1yr?QdH@64z z4Iqz0^Xeu5F$2;Q_1c)$>lsMQF4lO4tO97FMxIUD>%wYh=&Xcw%C@j@^K1KK!afDx z=Ezz)hcgX(hBsdY9qVyi?JSZ%i{P7sB^E%$0P!@2>&3^~%>1WLy8YSfWrD&p-53+| z#j%1v1!^}b_S_d7bDS~{>2~ff35wD)9NEYwvT%Fnz>z2Nwo5pwP77YzWT@-OqI~=G zCL|Xr)}dW5^$PYsMa?VP-~LnMReh-7LHI8wWM^F{wYpAm)sx9kljqd79;pq5D7Bkw zeLMrA_axW>MGkE(A;Nc$2v6F9@^Z9bmOv(|9M#B#R77byk-C}9|0-a&CioX`EzGX& z1a*cs`Laz&cHJcsIBQ}_jwEq(lNAhEl}h^V_rFMAU)G{{1HHrRx;dm>& z$>a;FOpVdw2!@K+1E_rjaf-SqV`>q{)n@P6m|!K7Pfug-I)2e~aHW>&unm_82IsA} zGGzSgzhu5pfbKVXSccJ;%-!}qq!~rU@p)Lq`}&b>Gh?8;e|E{FAm4xIf5p6#rQ0jb z-!OKdlhcDK^n;(jzDYZO)6%9!qU8;}=dLX!UH=*c34Ynu&?{irD`oYy5U{sP;9A2J zhkZ#TB`MLdy}JWFuTE(}u=a}d$5@SsESWzkT3F|xaK!oeZ_{G0c%Kci`q6R#BbdGS zd-%8;LtH%hzUyubRAfdpm6YxKkrdX8d1=S{SBSP)?!khgHPE|T``lkGyV!9==;>-} zsy;Xyb7zRgc|?Wftib80?_HAG8M;9#iVNdSE@x{MlBD&pQd}oV7JaP zTgWoyARzU_0L*7{JlyBzfVF-GwPAo)Mrn&_eaqM`cV#G|U38&V8RgKJ2rWk(bSt7q zq@S6fpKbhAEna4Ao$FDUWToc4@VL%Px*jqk9kzMyb3hH1|8@|w0 zKM*G@M0wHb6`Pp++ulPr@(jFKSDAvS=JkW}pe`V;A&kI!Avl+IzH(B_zA0`$&j$aa z4On?)a4c>etCZl9&84Bz0$cCKSSE%=I~>rf)^`@zK~8AJTb~mV zQso~TVVB+;y={p_V*t?5sYVWrp0+-lDd}E|%+nM7?Eq7+p6XvZ6BP8yPn(G3deDcq zndj$yy@$|t?8=)@cdsGY|KxvFvzTqrA#G(EGCt4gN9*hJAoFz;<)NY5aPR4YJFZHy za_NTWXS#ttYw;DPb^F&~3#L9kuP20vgc;#9l^^c>K(d=+s_ZDQmrHhb#1FFB%=^_+ z2SM#ktA?T+!MOKTs?d*9zmVq*PiUT9-O6KBU0-1h==x`<{^-+95yWcfNvy zYJSQaWceWnCpTDu+YoO5gT67kGk71}ka|?^n%0v-q17>D_+zaTkL=<6c}0_tK6Z$Q zP9zy2QhBsr7I4Y?^sQSYXr&fQ#q0|~$^f99?S7dOEgR`+KU(_fDx5VO2;r0N=;$45LhCY;L@JptI_>?duhx2!z| zCL=JI4yzUW-T-5kZksCCqEzvRDmC$b025Fw4888G^QY%5F^>=Dt66mI0kwDhFgF+J zX=oMqVFHsf?;sBO3R>64uB&r_;VW-{V6eh2Y{*61ypyO+O(n#|0=aj))UQ=4s?`5` zHNA%(eNEx+)<`>0sFd#bE@!0}NMLR$QJM=tk-lgXC?Nd;6!)284KwH0GpxTEOCm3A z(W~l1I(iayHvk+F+(^)ki49)2tW6-~vR$lT1^{{C92krd1DYu!(Y%$f`$$0|NO@Pa zbO2pk??fR!rlJd?zaL(4OrDPGd&pTbZv25AqCei2Efxrdu%2h|JAXI(cbvXL!Pu@} z4H8kbDV?pBTC-8Q`5~^*O2^7uTTQ!zg)z>t5v;NMhmS}nEn&ky_!p1a)?EdLg|JTys)f)NT**|=W_JGTDGkq6+Gpd;=9CjX250F!*AA);iiL*w z^6*M0%#RaKbC>-ryJ6q)hSm;=w0N28n~8hA{ch?Xl8GGj^VQK|c6Bn``3VkeX3bR$ zDK+q)P3aMmbGH5TQ>z_4l(NmU(IQP)=%qb`$Z2(YMC%W)2in{@lvb*B$OFuBlM-6Mjl;5zD^NXh9gl1KO zLK9d^e3_&whkIs@#1?adjgko`G_Y#U1 zVfPC}H>bc{p4piOgK}8Kwm z;Lb|@$G0yBkri81>r;xt%OSu<+1zgSUJ?f9VY#ft)<|uj;pcZ0rJqb0tp?*!5oAgr z{FnaOF4kvyFhAwL+u!{E#a9z%CcSiDz66;$vb~=SS$|*LP9@7^C=QpzuQ@SM-3z=J z>rIb<_D}xGa8BjRl`OyrKe9UZcd*R+e z>;tA216*CyHm-s+6(mjVRi3r5%89J9!T*g=UG0EuzIBOY`qE?9+h_}?mMoFD8iVUV zLY|K`P4*9gj#pm?!kJj!L%R#B>KIu?4y1(OfE+jlzX$nv95Tl_z=kg_&&R zb#f9b4*TyA>Q_e3KJbvzn#621YG?yzaA&0X6H1xCw~9E+W25uy1`}yym zRh7|~8oyj`sglbavZZEjgLAXYBL`wS)Y;Y{iOv*UdrYPw;P*rVf&=}hBv&&|`)jJr zItW}j0DyJtKuC3LM`nQ<==;Sx`ob2xv_6I)&G1|o016X-k%C6&KLdVr81G4^o{Yz< zOj;`vrQFV;_>1M zN<*ueyKF;MBgZ4Ph-%Q1tGz_9cI(?=h5AB#g1I#(Q|-21saD(i!kzb2fk2+viblwn zXaAfG@fP}ruEq|8Z1*1u{BktJhhx2lT0D~g58cqNSMtqaCt{B-ziAN0uBlJ&f)JXo zzGEIKZ-Vr5rL+e)O29>{9NvK!X!oa8sx^fr&5k&>0&h)+=DY_dRKFotNP9E+hAd5!ceiLj8 z(ZoO%VTisqin@Gjv20Ff*5*0?7?IcZJ}4w75$2!Ssu13KcTQfJVczRtj%3DU*Dys- zmjJ4{;~cv2gn*i=7&)?mIw*D3TEcABJ153uo?({pP*;~FC|qO^B@bCwEJM>=axa-O zOweDVyu&+xG-_pebpnyDgcM8=3SJaeQ$?BdE8Em=Pe6PAETDID@neRqjaxx`n>uJJ-Uw@{fcwo)$?l2Mkt%sN5hZn5xg5)=GM&hCwXfxtxPtaY%^h`Ty|? z=>HX18g9uJg+nGM7_p4bb7H~sD8BZXb=2=z!Aw`Q$eTR=Mbt}8@3SQ$EfVwMGO=o4 z|9)$n&-{K-hsEIO?LGr!ByO)i1Fr~2lHQR2!Q8CR3M2Lf_3Dm95pp1QkhT$DuTV*T z!c$`fh$c`yY^&l27-b;Y%TD?z4P z5$E^Y1T%&>)!|1~6QjWhJ1= zS>DUDzC|GjOlzBEX#~726{Al#d%$Q05(U7*gxwm4oZ~^aXupa9Nu-Nm4sM_hM;NOU zHjJ$1(!ZNHiUiPY^Yt^7QSUwnHzHt$4H0j0cF0=j5XeiNCmql6p3Zlxti8u!7aYI8 z9h~Lacal3) z2W?epZ>x!;A1nX;5coL$>3^3CKj|bKtbeS0p$vBO+}n8}gHaa}B$|>=sv3XuouP1y zt)pz0|B2^^)b){*PYvTYrk%yu@_DFS5SQfIZ0m~!_^EY4|5%CGJ&?Rxjb?46dCH7G5r2*J0 z2!8J=mx=*cRICXMqrgX)uMZuRf^M!*ldkPtlyW{yTk|ADK97w_y^lTb#=laEpe$zw zCbh0l`cF=z5=ygl>65384jy9I5{dB2+88FXQMKEPXP?XUNm?RhxwV~? zEiH7#G$no$b7KKM+EggX?1MINzn{y;8Y$ef~h<; zT|-HvgwW0aphb_nhjBI}1L`gVnoa!U8Gn?8J5RFuoDdvEhyn>yib1|36#XfWBu!+Y zWGVPj(fOE2u1@}9^Lr11gaT=;gn~9~Eq+_Z2!fa}OSJEiyzReoi($hlMm}5<0l_UG zKtR9%hqB{rh`0%n(Sa?%@1r{mhGYzXpx86DiP@HYR!js@L45(c8N2+72^F~Q#`0GC zj+j#P7bfLf24_zmT@bDGEAcY! zK?=k@``u_C!YVErlx%YYIvK--J)bYVLm#%XNFj{s4|$dbV{85wE6JYzG5)`6N~skF zDFI)_rGNT-zY@UU>gq8d?sI;jyR4zf-?Rt)e0x^J)_3RqjXdF$%O!6*TueZ2%Wdz7 zlZ~gy!IeR-ZLe0oY6?vyZ>ouTlOp7o`B%HZB82)UnYtO`HCIUt+}Q?GY#eQ}g({M&<^$vg zaID_KpjU*%{Xgl6Cft|76~*8{Jl_Ez^$ox@P>6SDU(6+2z_+liP6Z07XokfWpVxPD z3Z#@N&~c`s*N zXP1f-Tnv2;PzMR#uu_eP#l>9-kUVN)A?nvBQpy%kE$nL^+fg{zI$B~4|HRoSf~p!? z9ulkZ%S!OOpXGy&^x=n{n1aDAjo#ZByYETy`2U9SE~&lVW&Z8g|964=@0_sLj__p* z%GkgAP1KkRgG#jm`y085jh<3f820`3fP?`ie4DHOFr?1VI~rbk>@HqT`selaT!Pzhs`EW{I!u*_uKUrB^A_ z8GwD=(w}$QvR0{Mx2Rc%DSstn*8$mHFZgdpN$eafhvW@kYyH0@3l-$nJ7k>9R#^#T zl*>ztdRoyAdOYnK6BGUE-+Dup2N7)!HF(X4nja#o-%`wTT8GxP@&w#;Ggj_aTg9oW zQ{$ysk&yk{J)9DNBHOUIli+m?7)H@prM4*v)PQ-{>}-F=jg26fjNLs-irl@Z>+Nx8 zqa-wF&C5gie_0n;%jm(4N0UXF(j~W}Ma9v8L~Eo{#pHCfvPjO&{Y&Bi;eRp<7vv;{ z;zjf$t1aEoNfH{E_rVxi@3G6%9}K6S-(zQ5kVa|{rvwoBF)L~`A{p5Jg1{k=B1`+f zrAKN(R0~R37k(7vdt_TJZvJMCL7gHJLnBdzlSmn5IwrdGi(tO7DC%!&_378!WgxyU zh?xKBwUI#4byxczOjYLZm;dTItDv}=XbWS(2@b(+aCe8`9^Bo7yIb%80RjZ~5L`ll z;O-8=T|;npzy060`*5qM;)N+@=A7=cd+)WrRT;6_K-yVZ>%Td#+i_3$dc9*Q)Y7z> zK9>4PK~^muuBUVUji)^M3ev(p^UQmURdsiv`G1q`(2CQzJm1?9nHtXXnCbo7N_8LY z;I8wOO$e(ZRl6~xcWBN_#)E|ea2Si;^$xoF;cmfq!m~R(Eg@|?3Tkv56A}3vm)-e9 zYi5e)gS(hi8eTwWVy=`&_|M^R4dTPx-{s3Cf{y3f`>o4*mSmnMRT$mrQhm1CYN^^q z3tOR{_9)auxJ7Z;<(schCt)OSztvz?-&epb){Gd=4ePWf9-l;v*Mx~<1A zXhjR0IaaSguCKm&l)Y!>-LZLy_pX-zo`!l1U_wg zUV+0&*T!cR{Re~FLD8I|uQIw#SIZsCXOG#}on&5)xzCnR(zGJxn~%mR8%$>dpE}@) zpZ4|=mqMY}F-iG6e}6J$H4igqVrrOSY-x1$%N8eE_``wVBtAm?bhw5k$N_Iej>7`4 z$Np!aSAg$!^NGduj)Q+5Q?H%b^o|@w!5jVCRHZ`q`m7W0C!sn&GhE@>v9@p!o9UA@ zA?)=TKR4@d%+Ga-%xiW5Ur9Fj2LqUDGm2j$zoCs4+hL7KCy<5@O?FFZITsT6PK}Ms zJqkvri;I1>OoNL9ce}BO^m7*ad>#GxXcc$Dp33yKRSCD|Yl@Ka--D_XS0IssR9GY! z(lz3=Mw86N7hslHWCM)Mk)Xk0m4dvIxn4wNdbZHhGnm*5CgQF;H+U&KQv}-YNKVW+ zwg3M1I>C5r12GdQh3ce)Bm5GN^ReX30iy%`c3JqW{Zyu$3LS6Btiw5>&wt>FwdJu* zVPW8PYP)A5GcdFaX!$cRu<#W;^>|=dA6>2k-Or(AJkVp|j7*&ZhUS?l6L)OAB@Hij4-{-&cVz>w`jG>OhRkmjN6EfC1{^NmjE!g0#U-n|*6 z3EHbghzj#C^4*3n_5KWiGQd=~aW5{{?IvvG=M}-|RWGJ?CY&0HZsC1$ZUd&g!Yu3K z@Df>2|2{`DgcivI;lruU{g=Uz$C(F@^JNSZ*#1@czCouw$G1$dry|T* zRv3eqo$Jtnuy;g=4`x^Gk)qxz!UNrC8_9Ycv82(iUMwR$=$ia&t7EZ#`WnY{wyoPD z-i7NN2(O5LM*>zX$bzAk-_&Y!vtPv-0j;l@nMJn5bQ_@TGzLsyvOvX_4R&i`^X|EI z+^i*$HVR3Wo@&ITW#}LQXAqvU+kU?Qa6esb``wRXV*|gd@bFz2%qoq=nJ47l;=Xl63OQnqSMbHf@V)F)*dl-@MG_m$jDp z=DXUBXd`qn$(CLP0o;whD7ZHtJd;?t)AZ@zq@!DCB5{4S#L=}7!}%z{;W%4pHMhvZ z^Esj%Vg}=qyf6P%F-#Tbe4(Eb9-)Zi)&bF@pRS$}sK3p^7UzY1>%o#B6ag@1xO;}Z*72|S1OE;M9DHj$|al}B@2 z(c6rg_9GxW!2y1eEvn7r_PXT~X z8p^)ub)UsX?_mlDZ?>~8*C&HK+c)qb7J(}DE!W7lbkR6*E}I905&13;3354t!sCqA zR;ADs5DTTAI2tMXlT&z(BRZ)%ZM^8E2qXqy*{hST9~y~0EBaM6$t|PXwEZA-FV7)T zpthPB-sg|TvQAs(i-PV+pjsBI50MMdB zD%{P7Y_yXVeREJ>y|lq*@y!f$?W2aPWh+{L0X86T2>s*1Js2VeZyx|h{gDx+US4$_ z|ITCrw~P+hZDbeT&wG)s0^bRMAnC12CQx9aCw&h8EQu-}5mClK7d_Mel9rf&&pMcLrpJTedMMOQo3%CtN1( z>T)IN(dYGo(5X!{68qa!Y^79%nU+O`p|8|b0OiLPuV8uoL1mGB7hEe!F6WdnG0W9o-F*$8MVOf)7}Qo<_RXGXXAc=hCk5a+q(BXo|iR` z^YHS_{J)R(qvolX&|z`)_OUZ+i%vF2^_%vBa|F?(SeCByQ2Fkn@_cbszE5Y?=u_*< zLr$&!G2wj`8-*z~;>a_3BL7m9eEPOk(%p+%-;HQ4Q<^I(DK(g zeFF9N<;}em)5sdThn>={7lpqbzM4Xp@wa^BXoiAPc|i>Q#j#0TE=}=d1L=n(MWriB zIjqcOO=P2|72XIexv5N~bK0Q4n0Rx; z{^zsHX|o(wfwBMQkUgc~&KyI}JuylJoxX>`MNdihea6y2w6i;ZOEGuSVpFR+tpjRho2D%C zc%?W9tSl=BkJFV1m0~0{c4wmGYMK~$Pbyru@-czp6HI!~92K~GF2n4^$dM7Ss?6Ok zWXUFkc*gLJTgHyl(H=N4Zxr1*`R9~4F!R+KKoFlZP!##r(`a#5wh!Qw;}|BV6Yg(p z_BwcR=3PKe6bMUUtWR@TCuquz@BI!Z!3^C z!?zr}YsHFw0b+Pk)gE>^p0J9j3Of6pOz75{T;Nk3Nr}xFB_Bfe%4DNK#C(WF_~ zmg%tWRgzD8!HiGN8j>NG9VLAs0#AdXf>2QRhJHu1`7d<2ex&ZbF24l57nL2W4rjASaM%}+UcNK6yV)oPxM?tpSZm4P<_^6nt!@+|+Qo_mPsbghsR_uodlSk1iv z)=K~?#k?&dQ}FH=vdBz%n7L?~ zG@=q+-n8*QzBD{ zmX?KvrkEzK#Sks##eMtk+dMjkQzPJ&X}dY=TfqI?OnQVCny9HMMOI4Zim_6ey6A*m zZ>SBIf6PajXOBN!Cr90F(Y$5vpxr23E5*47%MA3c;T}bnO$+s*$9#Nok-G{G6*aq$ zU4I1zxmq9!%K>%Y$r+Jz4zalXKai6ATi7(!(9B<}zOU4FtZg)cHd)t+J`M6@tzk0i zP;0_`XTAHzgS9%~oESw49YsTp>uuujjBE(m{Sn2uq29maO9gQ*QRnvecnpx{t?8t= zYU`TJQZ212T~LjxTBMOGZ2OXe<>m|^Z(tZCdbJhUJcabK?POSJP=&O*R6bf7n>fG)bQcEd<^`Y8x1(tr-*tF({D>U18-?WT`2EQOEFP+;aC2 z?a*!$tBdV|zFcF4M49$GCC7<35ce9ptGsQz?-H&3dovP<}LCp#@h*0utL86ttzEWuO2N&FPARn z*AdwV|CFDUJH}c>Z$oq42kR!hq@WtcV|icsp^Af!*0=q}(U=onTqbOv^q9WCN*a4T zaW+SvG?V`MJPuG5blQsI5s2c3NukNTACMSF)T$FdJ=U0f{Us^72mf!3r%)OI*OY#x zogROv_NqzM_u_5zcf%ccGhj)Jvcyt_Zy~N-9rRSMad^Vy-SKI0JS_bN;>UP;v7`O- zTp~B%GdRigo?E3GGSn|HdZ)zBmu$?G3sSm^Au%?N2m%J}3M^{FcVrVeO6DKIT(A?D zdnc%uThr5nHKUA9t3NtuyEfZkuiT|dG%~I%w!q0TS^uyV2$%E>$@{Zx6RaH3I9sCC zS&??5WQh~*^BHl?xT+Nv$9dttP2)xrR8*>h3?C-n`G*bCX8slBap8J zpJlU)t2XAp%#%N#yJiI!>!+e{EEeV_%Pj}96~p#UqNmnLii;Vg88D^iE$o*IRm$AF zJVSqvae(3^8W(%|0w&k!jnHC^{VlFUYR6eY&|T+p(C(}EfRXi=hL)G8qV_)-#LJw8a z`kQ$$Vf;)~r#Pbj;}M~QCxozAa_b$5>nCaK*W53qt!KRu!0h|kCOA^4&(E^HWMN+3 zs~&$`*g+c%^7C#tVNQ)#J5lJ8jTF3^@V-sdM`2-YMKCk(?EhjxmDmA-w76XaJ3+BA z?28Tt5v;N=)inGw6DGzX2KnRV)+a7@JTkR5m@!Q30$(ivkMNOpxebE&`)=d-_4yIn`^0*!t7f&vQtI%?NW;MlC7DO7$-{>;WyC(ofI05B{5>+FwNJk`%JY|FP@^wn z!Vll-E*L+~`Ct!&wL>uS5b>hXuKpXzh?zWzg>XL49wL3lr|cO9FE7c_kT3K|`^zcq zDLDsLE|tUDMlJp5ta|x*qmgw$IU&?bXnroH z&0z?N)(0$Ibfm)gs7@Bk0<1l!ax=mTq7d2&x~uEn|M)OKJUI3qb9)#}DLn9X@#1c| zN4A#~qx5Tid<7(cLN3s^1^YiIBS0smz_4zfjMGIm2A2({6)Cmr><-t^Mb+NJCufB3 z+y&E%qoA|QFs^>Wp*rl3##4CKr)GNQsHw5vW1#h;Rtp$X7Qhj?@xL&<v(0)5iWm0cm|XL1r~OKSZQvmI_(qCzX3~ zfHG=53}qXkLVgL>`sS~X#8ZOC**36 zx*YD7s`Vd|(W-#p^90f@^u#Zf0=X~aM&D!;VW(I9UqE``Wfv9zn^P!+9Bjsrpk|k1 z$lTrn*cgItu>Ng*qjx}dr8xEv6a7igI}F01&9CwT`4>;yN$wu~dZLs$2+T-3uD^#O zwNslobBi^8J7;ZpAm$arWf@OYn9qm3&8!Zs)cpGQwMcsV^(gf9Nj)|9*?9eoTJtgP z)U9Lo(l9faOsFzyJy`U%ynVYl^*iSMfPi|wu|j`rZV7iqalnLTb`jKp;H=@h{ncl3 zO2!zqImcVGz!9?xaCPzb!CCiYhC~6TEF$|3fjouH3W?CQ?qvSi<_4@ zirRPIq@5YUGD=AyAz>e=%tJ{xqjP77qZ0_757Gf5j_b}G{HdW{pGN>qWTKFp?U$+# z(5l9(bZ##XG|BR@vtwAwxfxqc(*?o$y;zG5ND^9MEjfpIa3}C(Mb%DanGySJwK{pT z*pDKTRD=jLEr0_R?>%Y)&}HG}<>Ht<=r+xyu%_x=aj_4=QCi&UNU?jfTGkC!#pXT~!ZJCEJ97P1QeKW=T* z>%RxGe19(wJDFH%vt1H(6IZs9oEcpPdmH65f2V~TQxFr??m|1VSOHoXyvg^vyebly z2Y8KfW1G*gP{6_)mh#g9iM>_2uo7KSe`IL+`WN=3;FqF}2|e_=sx?iuH@6B;YiS*`1DU z`#3+Duucf`1Q*GEPMO?}t#zxgJ{*i@fII!iJBbqo>*q^Ac93V&gk#H6vh_P5mW_@< zcpou7_noz8Y3FPUz+%bFTinEXT|Aj@6K9>|t5jY7^Q&$3a|t(Cl%Cc|bP4Us;R9Y* zK9`bQnRrxZ3nz3SNaB*BY%we{;+3Q61`w?j-tn=`05rX_| zvtxtr6RY!0GFXcCw|rVy)FxUs`R69Q>+h#?ERB-5dy)+@QC{zz0;l3{Pw$@EhdNu7 z8HsX#`a!*c?5FxqJTv4x;s;DTlNpx(vC~HJwo>PNb3*v;H#4)RzJA?@m`tW2zINI# ztH6<$PC07$r94;I(} zJ{_pz?Zj0blMpp?^gJP1?Q_pcvJ$* zL-Y2PrP&X4Q%X~`iOW)r%nBzwopl_=V*jBZdYnEtGjwgj^m8>H2FmdBFaz-Z4BX*% zUNtKjt3`s$lSb3n!a_b~Y1oku>BjV~)*=HJdNw^*Z9&D-Td&O=ULHn@S%!|S=My6P zG7tJ99jD;PaOw2&GQoDa)M5FQE*g2t*Ef7I#(U;H;Gj|9Sip0#s1#sreXxFeo&a4x zVp}^)hEhtFU?bF*r&CtrRF+!h{-tS$vYzoJ);Zh>UVL2)kDC0W&{-EO8CD3kl7jvS zl6;`9Y^l6&+V5D7W*Qgoj<2t}izQo>Ci!=Wa>P`YNOt}w`}9T9(*_-FU4UH2@97OUAF4e*s#=+Gr`5*%i*W=wkwA8rz`J6F_l)Cb@Jg_kY6lue=B=VZ(YJMJB^DBs|Jhx)7&AWw-t zZ316#lc!zmEi3cIOQB`e`dCe!YN3YPF9TDS+dT;hzN!hJ467c4_bhz3F^yu@@g+W9 zvGAm(QSI-|D7?PD6sn=AKc8VHslscXGI zflvC@C$Yv>o7u0O3)n&Zw}ihn%Uho|$Y*Co4zr4#! zM)k1zO%YyBfrnolbb}5PsM=ot9u;1PuXuI^U7m_gOg+9HCk5IEDUaVuf-}}ILdTHA z>n*EFtH;_o$zh5$cL(BHGu$@TkJFJ5e+L@-a92U9`bVvhS-E!r>&2)+aHPb+o&rJu z#G7d3l{yMvJ|eZmI!R~O1}upwV)Q!ttwQ8DqN}z?1V+mF1+e}D{r1S1G3&$XO0bKE z{2)^8t({fe?PKlc4dS)E@V!wAshws&KL0*QlPT!?JXigjC_fP2skML^y zyiQSq%s}T$qm<-WjvZI*a+~PkLfyVfq)d_qRqW=u=xEjdVs98P_4iYWxBI@8&Q0y?owG zzxCXxA>8=v@g82PD;2JW*}eo&30C(>n*}BInlW5>-3jDird@$vRU)q%*+X6vW%?rA zHT)E5$#?{YYoVvvisYv*x)CovHBOi8ZT>qPjm=?16iOHh2O$KmPGn5buL{$#~V@zA^|_&mQCHiAU&%V>!cOvq|wf@pTH_~;s-BxVoXlV$5y5|{+={ILE4>W6aCwx@b*T^nAaa+r1U{y%Ul_%4@ijoBdpsAx7Qt%8 zj*`hYi`8!a*nVmZ^v03@!I=x#QKH;;Vxoi7@I#z#pYs>$p#;@JKnlU-nDArz|>pp z(j835$ajOcp3{d!{QZ&Bit!$*<-GiX)$xE~=1)$@PWSE5|GJXEaROf~@jO7qGS~V; z+*D@Nf3V3KCLkAyiA29~xyTm-e9w`=_t9S|)ahm#xof*BTMl(nl(emhr4oS7?;M~Y z0s1n@eAS?_d3@A0{JziubZWMP^~3V%El@nf=4A4wd+n$!9E9CucJ;)?c__PQ^J>wl zv5J8@^-rk8O3t#CDL?H}bT^HbDfUm*>|5bovfwLG1uSc7xf&M(E2oz^+ULfAfpM}l zD0s}?7MLbr7B!Oie5iDRY3cDb(hEcXPEd<{lPEA!NSQUfW=Jca9%kK53a_3} z&@!h(|J_U1C){WX!O;4Yu%kFQ6+c3INjU0>&nh;2_71pd#K&f@?&#_66{}9`*~?pu zPGdFg%)JNPnlzYy_}FIq&Lv=F6D2{|PeMQ&>Mix8M%1xE_S=v)y_DnCl^1C|yli-Byi>UvK@jwB? zW-Z&RKwtL}*qj4oCT{J~pImmK7nct^<6$db?tI=mz3w3N?H=M*OyS8xXzWF{NV1-t zb2h~&P&=AcDR+^7WAHk+-jWb`rLy^-MUk;7CM_+jlB}|z@sn!~O3N;cOD2g6Lptvm z^gdrZB>j%XLb&Na3!un;=$f@;SzVEw<^~4aKdDhu%OvPw3-12w#X4oR**|~PYg$q1 zQybf=*&$xPl}aGkS9aYRgfb7MAD*Rg%Ff(*XmhYtq9A0OA~Mh8?Mv1Vv0o3VlJC^2 z8gdG_763MAJ|8pCOCJTN_ttJ;V&{SoNX#b0V$@*vPf3X54S9I}aCV24O4vJ;oBSy7 zH`?Qjc*JW}n_BKAgfOnnQu~6ZYGUijF87M+Ix1WAE12Q6z%0TWNjdkwuu?C zxFN7k`mvbe)~ocmh)bs#V6F*@_Uz_}jz&?1w)z&)EB2_bHePpr8T+-|Kiy@$ilpO{ z`awI-g8neVxq&yVr_Bs89ElnNZzE4fdDY<$4nc1@h5sx^=w_x!(ET{S-@Q!)1pBw& zXv%)mm`d~^tO@WA0M!Z?Gy1$8MF#|e^U%^mEI2u`HiTMrc)t0+-)Ejm{Tm8n)ic9P zz!&i+bDVJ47GSP&eRBr*#)_=ni!llnjw#;%uDFzi1>^yKpOcKKrl}APk2l!iBYWI( z1=Um08#@Mz68GY8h(o2LVanG)u{nv3e|{ep-R%E42JI&WhKZbCB9w)__*!f0I>4j` zv%*?R>So_%tg=I+Kb7X=@d9vy04>h{q7%#4|V`8=E`FrU3cMMve${r z@rRU%oi}q3aX5Zlb)SR3d_>EdAOWqU&WiEU4tQt;5VCBefKlAG?8$;8l5`qHRYoWj{ly zD&U$dU@CshtM48*JJ>51Vfesu!}`Pti+`o%ArqxE$Qzl*pb)gNJrL9u9EL-3~L=3d=xm_QsMGr_V-% zeH7leCWZkM$iPyPuPK$YbN=-e(|`-{9|be~dq_p(n?z(eZ_ZL%sl+>O&4ky*c+zO& z2jvdx`$W8*)u5+UD(lNtXAzK=GG6umCOD?kSh`W}=?CQe+i8J(PNX$AAjy8)N@4rP z({2Bcurt%Zs*(v#79oguRwwYu+Ovz-i^tI1$83?@lu6^=BZhLr4bn5IuPM|~>|Z&UpUvbjZLw{2P>t(R zxF1@!L2`-Ca+z8ce+a56;qXe#Ozru11J(7 zKMf^(z+%sqFYFrDBURD_+8_BHc;kRWmQ*K4wNhQadMfzIn&AU!Or>Cn#|JoT&$^gn ze*pGo-f9$qT~!640BO?$5h|ML=v7RYOD(lbO!&@R&n1C#%Ju&KRErJjiJ72NMp8}Nuz-<}hAa8*U zHMt-%;+I3b_IQQK9&&L!639iI=p(ItIZRDPhpI}yo+KjU@rgt_bM(P!GA$NNhs zy*OrW}Rx9IX}Y3rQnNy(q)_n=(S$bev>`oDx>ie zAwM)|`aPZ#MGA08u)BFi}g4c$F&9k35(N$l6T;Yr8fAE_Z7!*T zm;6iv_@lJ75r9}S>R^J)1BMGA2C%N{iwP@HbO;kCpx+QrH3`>-Tk0Jj9nK6xXHVF< z@#=jK5UFkd78Sk}S5M1X5XRE4b_(-EW z`W3yVO`=U>lv|}%X8PgWIO!`gqCF+WYfCdQ@s#WB2@@xbCnn9)sjB^@X%SF6>RT_~ zPPei{qHMd|Dw`PnJvupV*GCdHTwMmi8}RiriZ&Wafjs$g^BQfldjr`H+k$`^3&pdH z9WwhqVY7D=I(QVu^`4<>H$h%fg&S=^`>Ta%D#KIaC1`|zcptDX9z|^VSfGHZo{s>j z93*8@Xjjx$>)|Z?(`%xBJMT!fbW>lGa(b;G7n%-Q76hgz>e+`I44CYk8!uhNJ zzTD0`uv73xN|dSLNEu*$?s8Z)D3#+lL{^XxAHR+8&hvW}Uh~613y!_l`E29!fRp=mV)nWCZJOcNgXJ_xTf~n@#EkIw?J?P0YaV zE&K;p<#9B{4q^+5!dpn8%jkY7%>ffX{g3LrWzf(aOE;V^h;y3QKYq$$8J`8b8p@@t zZmr|3ia=Kh2RVvaxu6r9Ku%m85=VBl*))y4;rDIW1H{5K^$GoK6_n|@lB%&UJp9y3 z7Pa>uAP)@B0QWYus`O3-01A44gGswpJ;tZng(U_y?zOSMA2aOR#Y$}{8tiofy0X;1 zu=&a~kk82^f}WoD)*lx>_IPd)P^$KbCss98Jr=q)Ws&VEDFI(tAwbyFqg>Y~ zeFsTYvXJir6IsNYy%M1y14~zTf>S6B95{9uohDRl8V76GIvqXI%NW?Xr-s~$2l##S z;%&z)tQo`?Dgtt zEn6A(ZrK@c;)wyY&U3$rUgDn_7C+dDK6a4^vEEglvSroV?2o zu#EJ^sdGm2!o(@R#Cwym(##I$(a-VZZy zv(00R=&9_79!F{^z^3d;A7jlEGJ1>;NIbZ3<%jc_-<0scRnbX%{jr{MI`rSJKs51` z*)h5$_?p8yj_&fb@K>vd@n!a-PDgcexrZf6tg5c`B5%&WT4m*g&yn7sy~21Xl_Me? z1#|{ibHY5XN|>!;L5t~Jd>-zf{*z4u@!7vsC6L-UGPX!OZEh&!YahngFxTWBfYz|s z$zYFs-Tx%u2*{;0u$uA5iE@>C+Z$^l56##hz|&?a?;xM&QcjJls9(TmuM-O2se%*W zq?Sue{)>M+T=-4dZoVwi%G9+knHY$<@JSi=R?tO+#4G?|{5t3r|E~O%)M)kMxOu+~ zBp>Xaw~6{cnVcF29o-E|BI8A5 zd(@;3x=9t)t*SlOkf|XI+ITb|&2Dt|z#XV@ww0>b!qZYc@=UNa<;1?4)T@apZ{VHu z2;a?FnLtriyqL9?ceADlD2(0=+4G<}&6?YRv?`+?=J#}GvO z-=;+(G~uP7A)LGJ+N$<@|Mg-wC&$~;qwN7d@bUL@(3;D0@PuebD!>8)#f^F3Zx}%J zl~;^&zc|Ye^lknQ2Z>v_DaITG^aHZ8clz6yeiy|vjR5P zIYV2^-TZ%;9HWq2O!AT1(@2xh{`zW&*M#7Kgo#2+REh0B+uJ%fU^xJ4q-l+HtHMIz zsFe#7N`vmtMy<>F0015`cb=f$U5gaCV;T=4Y|QPw=lUd?f9V!v&nk-0ddBJWptRg^ zH$Zm$pzwMyoBZne?07@lGMzvhPj;k!`@wy)nH1>CL1-=-GHyP7AzUZQ`fXH%1)w4J za~T4yUq2UfmM=eDb}e5lvJoJ+LmLR5nG7RKp-VMVU@2UT-}|^5Ztmq{W)$^AYU8I9 zj#TGVRyV7FDJ@7xHr1#v{2xH|l(<<@^3ygSeB!;-9ob`n&%Y7RnGg z0#pP9XDM@LQQ@u^RB>I1v!v0Y7jNDQK!VBS&id0^-eq)4JR|Mm7a#lr0rcrzU+A4VL`IfG7_$|PSZZ+BmJf`_iO!3us%B~*Hpaj77k z@HqSX8sxW&g{6rTd49U)!`FVnK5ijmYie1Wmd7S$qe<~DjhQl<@*}Qp0xmOfLoD~> z$vJ$dTgH)kgRHBCL46O!&4oKKH1LIUyvJvvjq^4K&pKn~Of1tS;!@wJ(fO22WLy}V zhbRsT3Z_L)QcNT3F@Ov`oPk887+O*~fd%$4mOAYhidep*GsGO}Z_3uj9QlQTx1c(Yy(FN^}N_3$2}X<>@{n+v3KT1r(|5pb zijmVzZj;1^1_~gwp05+7YPIy%Rw2d0Q$jm2ji*R2lwBhEhj1)hn{HILleheK)*tth zqr8~xRQ@6?kiCb=uGI5it&Je0-|$0nNP8@lCu zsr57B(OSoY-D`nu&-c2h1HPfJm6m#QPZ))MRuB3#tk{%6nwEC@GDX59OC$UgVo({j z^|Zc_FPaO^mgrRM8phtAKXxkLmNuIS=eF-uRFPk9Md@vimnfcn-$qzrA)|~zK^)J- zsQDmfVDR}gV4guMh6w$m!FU*h;Ay*n_AA%CicKmNrT?Y+JKx2`JxsQ_Pe^=nB|`J? zv7U_b(HE*NCSFaZ+NKh_#lJXv3bZP5&d4otr6)O%x@>}RuKFIr=UJs7a3A6%1o_&P zj175d_$pQGVkRH|%6~Ub{{@})DGAlQhbT*+9v?5$nEhqMgAMD97x{yN!z4#KUX3!< zmfQ4ue(^a*e0(T(m>u`LlgV4F5 z^6w*B6i5_tq(qfV5wcKM(2Xb?+$rzgz8gZw-9s>WBI8BJrDBrqqE8N-#dGlM-49xXGZ0((Ez~cO51$7Oz)YY4LRgKH{hHY-;{Q?h~hbjHjcBph*4>c6+c>~Yvn+^U? zeozswD+6JfPi)Y|7+g0gP<4jC@H#6O!k3{0y1rb~4>(C2GCIqKKKVdFK~cL)>9|{% zx?2jEyIO)@P#kO=oXl+Chev~*Ux1TSfP;;ZjZJ`!?Nknz^#8oT!O6nL%IE)oK@Lvk zcklv&|Neuzla;%dsjDTFn1z#>CApk~skNn=rKyFF%aElI_#-GesSlD>;wB;g1CXmw AL;wH) literal 83644 zcmZsD1yo$iwk_@s!9BP&?(PH$E&&<~4#C~s-5r9vy9W&}L4!9M+#P=BocrGU)?@6k zrOQ^;uBtibTHO)KN;0TOgh&t&5U6splB(eI1q1}-2Lw3q)kdWS9{2?5q$(p0Q8Pt+ z1inGEm(_8CfI!Cndq6^DX5)hsj9aQ}J8LT{@SE7#vKW1}Gd5*$x3veShJX-s=LcWf znmQYiyW84)bK-XwqWmWXKlu9ZV*n-jKS`Xeg($TZmB}US98Jl&SU6c&DTR^9$;kyB zznbx@N=pAHJNQnB(!$x;Y^ntbqStCTB~t|7qU;k?Zd_|7QEgs(&jJ1a}R;grljEvz?>5ot=%a*x$Y*m$Nl8 zH&rz?`syJF_`g&9PfG>=7RmqF(b5!b>tBn6*#rUq&$Iue7XB?TmT(CuAXUAe1E#N6RF#GLhDhMVPt1EEbtL3&fo6c=EH&ete*9R03FK2YWJsl&T1uTAh?x|d|={Bz%K(#Yp z+-`o35`kw2yvdXaK{}E*nvBG*)#!IdPQ=6z^|m(a89Z1fjD;~Ima9v?k&AHLi{yFi z=Z%bp*^oAv`oC1_19pfC=(dOxQ9n7Cbfx7Z*! zYq34I%AHW^7Ew#c8{hkrnj+s=w~bVxkN<6mfF&sKd(78Y6^SW?3XqM`r{WdR2l{s< z`EUCGQm+$a>||+T*4?;9KsBUnrM}iTv|mqsT4$Y?^c+45ZsX-@y+MRnuWP6G-kW-6 zXP|byx9$vu5>&1~+08A2(L4`yK@})=Q3P8$__pP$^eKjeIV%choo4bYT5il;R`zA@ z8Ks|dRwvCoG+kwtY zS9H?9Hkk*r*u?xU*X!=jo4LO)IC)KC-&v9Qw5>F?p^DL<%1L_@RS3|&k$(Ep(oAQ`EF7oKJ-Rj?#2;& zJ{k1nBMyx~lUno6yHa2!CmM$wcDV~SOe?~ zy~Lj$d?_@J$qK-ZH2bieZ^y4TVcG28%NI(kEw&X~j1zR>1&I@CGaNU*M~RTqJ8Zu& za(Di|mW0FA?7*|Dz+n)ybd=d0PPi^#<{g@h*$-ZE|zM_6w)sg7Xm0n<^uKKCRG z%5k%`Kc`b)uV7JhDaxHb8xJqpk+?rKzGoTPn<`Tu=ozfUTlE4Y(SD&kgp8Wv$&6)r zEpXZWR+&=w)nQ**nsW#)Am-NPGeO$e>kF^CRE<#;`euqUJM>-rpxUGRJ3`%NI62TX ztgQv1Aw4w%)TFR{i^q|1Wk>A3e~q3#%I3@DrCee)X_Z7a{cbnupZ6|^Td;lAFd%+h z^B&N=((t0CJTuLV^Qp|<$i;>O&#=IqHelA>q**;qm!Lc3D%r`MZU815npQ@Kh1k^L zu?g%X-$I9j};W7w;eSNRNDZIF5v2KwuQjVM)UnIaMS)o__f)&?I`)r&H)KE*
}}\preformatted{list_unchop(vec_chop(x, indices), indices) == x +\if{html}{\out{
}}\preformatted{list_unchop(vec_chop(x, indices = indices), indices = indices) == x }\if{html}{\out{
}} } \section{Dependencies of \code{vec_chop()}}{ @@ -112,15 +124,20 @@ holds: \examples{ vec_chop(1:5) -vec_chop(1:5, list(1, 1:2)) -vec_chop(mtcars, list(1:3, 4:6)) + +# These two are equivalent +vec_chop(1:5, indices = list(1:2, 3:5)) +vec_chop(1:5, sizes = c(2, 3)) + +# Can also be used on data frames +vec_chop(mtcars, indices = list(1:3, 4:6)) # If `indices` selects every value in `x` exactly once, # in any order, then `list_unchop()` inverts `vec_chop()` x <- c("a", "b", "c", "d") indices <- list(2, c(3, 1), 4) -vec_chop(x, indices) -list_unchop(vec_chop(x, indices), indices = indices) +vec_chop(x, indices = indices) +list_unchop(vec_chop(x, indices = indices), indices = indices) # When unchopping, size 1 elements of `x` are recycled # to the size of the corresponding index @@ -135,7 +152,7 @@ list_unchop(lst, indices = list(c(3, 2), c(1, 4)), name_spec = "{outer}_{inner}" # `vec_chop()` and `list_unchop()` in combination with `vec_group_loc()` ave2 <- function(.x, .by, .f, ...) { indices <- vec_group_loc(.by)$loc - chopped <- vec_chop(.x, indices) + chopped <- vec_chop(.x, indices = indices) out <- lapply(chopped, .f, ...) list_unchop(out, indices = indices) } @@ -149,4 +166,20 @@ identical( ave2(breaks, wool, mean), ave(breaks, wool, FUN = mean) ) + +# If you know your input is sorted and you'd like to split on the groups, +# `vec_run_sizes()` can be efficiently combined with `sizes` +df <- data_frame( + g = c(2, 5, 5, 6, 6, 6, 6, 8, 9, 9), + x = 1:10 +) +vec_chop(df, sizes = vec_run_sizes(df$g)) + +# If you have a list of homogeneous vectors, sometimes it can be useful to +# unchop, apply a function to the flattened vector, and then rechop according +# to the original indices. This can be done efficiently with `list_sizes()`. +x <- list(c(1, 2, 1), c(3, 1), 5, double()) +x_flat <- list_unchop(x) +x_flat <- x_flat + max(x_flat) +vec_chop(x_flat, sizes = list_sizes(x)) } diff --git a/man/vec_unchop.Rd b/man/vec_unchop.Rd index f132cef83..cad8ec9c2 100644 --- a/man/vec_unchop.Rd +++ b/man/vec_unchop.Rd @@ -16,7 +16,8 @@ vec_unchop( \item{x}{A vector} \item{indices}{For \code{vec_chop()}, a list of positive integer vectors to -slice \code{x} with, or \code{NULL}. If \code{NULL}, \code{x} is split into its individual +slice \code{x} with, or \code{NULL}. Can't be used if \code{sizes} is already specified. +If both \code{indices} and \code{sizes} are \code{NULL}, \code{x} is split into its individual elements, equivalent to using an \code{indices} of \code{as.list(vec_seq_along(x))}. For \code{list_unchop()}, a list of positive integer vectors specifying the @@ -52,8 +53,9 @@ See the \link[=name_spec]{name specification topic}.} } \value{ \itemize{ -\item \code{vec_chop()}: A list of size \code{vec_size(indices)} or, if \code{indices == NULL}, -\code{vec_size(x)}. +\item \code{vec_chop()}: A list where each element has the same type as \code{x}. The size +of the list is equal to \code{vec_size(indices)}, \code{vec_size(sizes)}, or +\code{vec_size(x)} depending on whether or not \code{indices} or \code{sizes} is provided. \item \code{list_unchop()}: A vector of type \code{vec_ptype_common(!!!x)}, or \code{ptype}, if specified. The size is computed as \code{vec_size_common(!!!indices)} unless the indices are \code{NULL}, in which case the size is \code{vec_size_common(!!!x)}. diff --git a/src/bind.c b/src/bind.c index 335574c24..e13cb4bbf 100644 --- a/src/bind.c +++ b/src/bind.c @@ -304,7 +304,7 @@ r_obj* as_df_row_impl(r_obj* x, // Remove names first as they are promoted to data frame column names x = KEEP(vec_set_names(x, r_null)); - x = KEEP(vec_chop(x, r_null)); + x = KEEP(vec_chop_unsafe(x, r_null, r_null)); r_attrib_poke_names(x, nms); x = new_data_frame(x, 1); diff --git a/src/c-unchop.c b/src/c-unchop.c index 9b7a92fcb..7fc650460 100644 --- a/src/c-unchop.c +++ b/src/c-unchop.c @@ -85,7 +85,7 @@ r_obj* list_unchop(r_obj* xs, out_size += r_length(r_list_get(indices, i)); } - r_obj* locs = KEEP(vec_as_indices(indices, out_size, r_null)); + r_obj* locs = KEEP(list_as_locations(indices, out_size, r_null)); r_obj* proxy = vec_proxy_recurse(ptype); r_keep_loc proxy_pi; @@ -254,7 +254,7 @@ r_obj* list_unchop_fallback(r_obj* ptype, r_list_poke(xs, i, vec_recycle_fallback(x, index_size, p_x_arg, error_call)); } - indices = KEEP(vec_as_indices(indices, out_size, r_null)); + indices = KEEP(list_as_locations(indices, out_size, r_null)); r_obj* out = r_null; if (homogeneous) { diff --git a/src/callables.c b/src/callables.c index f4459b302..adab03a7c 100644 --- a/src/callables.c +++ b/src/callables.c @@ -19,7 +19,7 @@ SEXP exp_vec_cast(SEXP x, SEXP to) { } SEXP exp_vec_chop(SEXP x, SEXP indices) { - return vec_chop(x, indices); + return vec_chop_unsafe(x, indices, r_null); } SEXP exp_vec_slice_impl(SEXP x, SEXP subscript) { diff --git a/src/decl/slice-chop-decl.h b/src/decl/slice-chop-decl.h index 1647263c0..5a84a765e 100644 --- a/src/decl/slice-chop-decl.h +++ b/src/decl/slice-chop-decl.h @@ -1,7 +1,25 @@ -static r_obj* vec_chop_base(r_obj* x, r_obj* indices, struct vctrs_chop_info info); +static +r_obj* vec_chop_base(r_obj* x, + struct vctrs_proxy_info info, + struct vctrs_chop_indices* p_indices); -static r_obj* chop(r_obj* x, r_obj* indices, struct vctrs_chop_info info); -static r_obj* chop_shaped(r_obj* x, r_obj* indices, struct vctrs_chop_info info); -static r_obj* chop_df(r_obj* x, r_obj* indices, struct vctrs_chop_info info); -static r_obj* chop_fallback(r_obj* x, r_obj* indices, struct vctrs_chop_info info); -static r_obj* chop_fallback_shaped(r_obj* x, r_obj* indices, struct vctrs_chop_info info); +static +r_obj* chop(r_obj* x, + struct vctrs_proxy_info info, + struct vctrs_chop_indices* p_indices); +static +r_obj* chop_shaped(r_obj* x, + struct vctrs_proxy_info info, + struct vctrs_chop_indices* p_indices); +static +r_obj* chop_df(r_obj* x, + struct vctrs_proxy_info info, + struct vctrs_chop_indices* p_indices); + +static +r_obj* chop_fallback(r_obj* x, struct vctrs_chop_indices* p_indices); +static +r_obj* chop_fallback_shaped(r_obj* x, struct vctrs_chop_indices* p_indices); + +static +r_obj* vec_as_chop_sizes(r_obj* sizes, r_ssize size); diff --git a/src/globals.c b/src/globals.c index 772e4998a..fdb9572ba 100644 --- a/src/globals.c +++ b/src/globals.c @@ -78,6 +78,7 @@ void vctrs_init_globals(r_obj* ns) { INIT_ARG(value); INIT_ARG(x); INIT_ARG(indices); + INIT_ARG(sizes); // Lazy args --------------------------------------------------------- INIT_LAZY_ARG_2(dot_name_repair, ".name_repair"); diff --git a/src/globals.h b/src/globals.h index b2a6e501d..4e2ecebb7 100644 --- a/src/globals.h +++ b/src/globals.h @@ -53,6 +53,7 @@ struct vec_args { struct vctrs_arg* value; struct vctrs_arg* x; struct vctrs_arg* indices; + struct vctrs_arg* sizes; }; struct lazy_args { diff --git a/src/init.c b/src/init.c index 51169115a..bb6bf7f09 100644 --- a/src/init.c +++ b/src/init.c @@ -50,7 +50,7 @@ extern r_obj* ffi_cast(r_obj*, r_obj*, r_obj*); extern r_obj* ffi_as_location(r_obj*, r_obj*, r_obj*, r_obj*, r_obj*, r_obj*, r_obj*, r_obj*); extern r_obj* ffi_slice(r_obj*, r_obj*, r_obj*); extern r_obj* ffi_init(r_obj*, r_obj*, r_obj*); -extern r_obj* ffi_vec_chop(r_obj*, r_obj*); +extern r_obj* ffi_vec_chop(r_obj*, r_obj*, r_obj*); extern r_obj* ffi_list_unchop(r_obj*, r_obj*, r_obj*, r_obj*, r_obj*, r_obj*); extern r_obj* ffi_vec_chop_seq(r_obj*, r_obj*, r_obj*, r_obj*); extern r_obj* ffi_slice_seq(r_obj*, r_obj*, r_obj*, r_obj*); @@ -229,7 +229,7 @@ static const R_CallMethodDef CallEntries[] = { {"ffi_as_location", (DL_FUNC) &ffi_as_location, 8}, {"ffi_slice", (DL_FUNC) &ffi_slice, 3}, {"ffi_init", (DL_FUNC) &ffi_init, 3}, - {"ffi_vec_chop", (DL_FUNC) &ffi_vec_chop, 2}, + {"ffi_vec_chop", (DL_FUNC) &ffi_vec_chop, 3}, {"ffi_list_unchop", (DL_FUNC) &ffi_list_unchop, 6}, {"ffi_vec_chop_seq", (DL_FUNC) &ffi_vec_chop_seq, 4}, {"ffi_slice_seq", (DL_FUNC) &ffi_slice_seq, 4}, diff --git a/src/slice-chop.c b/src/slice-chop.c index 9f105b8a1..a48a7eab7 100644 --- a/src/slice-chop.c +++ b/src/slice-chop.c @@ -2,29 +2,60 @@ #include "type-data-frame.h" /* - * @member shelter The shelter to protect the entire chop info. - * @member proxy_info The result of `vec_proxy_info(x)`. - * @member index The current index value. If `indices` are provided, this is - * the i-th element of indices. For the default of `indices = NULL`, this - * starts at 0 and is incremented by 1 repeatedly through `p_index`. - * @member p_index A pointer to increment the `index` value for the default - * case. - * @member has_indices Whether indices were provided. - * @member out_size The size of `out`. Will be `vec_size(x)` in the default - * case, otherwise will be `vec_size(indices)`. - * @member out The list container for the result. + * Index manager/generator for chopping purposes + * + * There are 3 types of possible indices: + * - If `indices = NULL, sizes = NULL`, then we use a sequential size 1 index + * that just increments by 1 from `0` to `vec_size(x) - 1`. + * - If `indices` is supplied, then each element of `indices` is an integer + * vector of locations to chop with. + * - If `sizes` is supplied, then each element of `sizes` is the size of the + * current slice to chop. The sizes are accumulated in order to get the + * start location of the next slice. + * + * - Generate the next index with `indices_next()`. + * - Generate the output size with `indices_out_size()`. + * + * @member shelter The shelter to protect the entire chop indices manager. + * @member indices, v_indices + * - If `NULL`, then `indices` aren't being used. `v_indices` is set to + * `NULL`. + * - Otherwise, a list of integer vector indices to chop with. `v_indices` is + * set to `r_list_cbegin(indices)`. + * @member sizes, v_sizes + * - If `NULL`, then `sizes` aren't being used. `v_sizes` is set to `NULL`. + * - Otherwise, an integer vector of sequential sizes to chop with. `v_sizes` + * is set to `r_int_cbegin(sizes)`. + * @member index, p_index + * - If neither `indices` nor `sizes` are provided, `index` is a scalar + * integer vector that starts at 0 and is incremented by 1 at every + * iteration. `p_index` points to `r_int_begin(index)` and is used to + * perform the increment. + * - If `indices` is provided, this is set to the i-th element of `indices` + * at each iteration, and `p_index` is set to `NULL`. + * - If `sizes` is provided, this is a compact-seq representing the i-th + * slice. `p_index` points to `r_int_begin(index)` and is used to updated + * the compact-seq at each iteration. + * @member has_indices Whether or not `indices` was provided. + * @member has_sizes Whether or not `sizes` was provided. + * @member loc The current iteration value. */ -struct vctrs_chop_info { +struct vctrs_chop_indices { r_obj* shelter; - struct vctrs_proxy_info proxy_info; + r_obj* indices; + r_obj* const* v_indices; + + r_obj* sizes; + const int* v_sizes; r_obj* index; int* p_index; + bool has_indices; + bool has_sizes; - r_ssize out_size; - r_obj* out; + r_ssize loc; }; #include "decl/slice-chop-decl.h" @@ -32,30 +63,83 @@ struct vctrs_chop_info { // ----------------------------------------------------------------------------- static -struct vctrs_chop_info new_chop_info(r_obj* x, r_obj* indices) { - struct vctrs_chop_info info; - info.shelter = KEEP(r_alloc_list(3)); +struct vctrs_chop_indices* new_chop_indices(r_obj* x, r_obj* indices, r_obj* sizes) { + r_obj* shelter = KEEP(r_alloc_list(4)); + + r_obj* self = r_alloc_raw(sizeof(struct vctrs_chop_indices)); + r_list_poke(shelter, 0, self); + + struct vctrs_chop_indices* p_indices = r_raw_begin(self); + p_indices->shelter = shelter; + + p_indices->indices = indices; + r_list_poke(p_indices->shelter, 1, p_indices->indices); + p_indices->has_indices = p_indices->indices != r_null; + + p_indices->sizes = sizes; + r_list_poke(p_indices->shelter, 2, p_indices->sizes); + p_indices->has_sizes = p_indices->sizes != r_null; + + if (p_indices->has_indices) { + p_indices->v_indices = r_list_cbegin(p_indices->indices); + p_indices->v_sizes = NULL; + p_indices->index = r_null; + r_list_poke(p_indices->shelter, 3, p_indices->index); + p_indices->p_index = NULL; + } else if (p_indices->has_sizes) { + p_indices->v_indices = NULL; + p_indices->v_sizes = r_int_cbegin(p_indices->sizes); + p_indices->index = compact_seq(0, 0, true); + r_list_poke(p_indices->shelter, 3, p_indices->index); + p_indices->p_index = r_int_begin(p_indices->index); + } else { + p_indices->v_indices = NULL; + p_indices->v_sizes = NULL; + p_indices->index = r_int(0); + r_list_poke(p_indices->shelter, 3, p_indices->index); + p_indices->p_index = r_int_begin(p_indices->index); + } - info.proxy_info = vec_proxy_info(x); - r_list_poke(info.shelter, 0, info.proxy_info.shelter); + p_indices->loc = 0; - info.index = r_int(0); - r_list_poke(info.shelter, 1, info.index); - info.p_index = r_int_begin(info.index); + FREE(1); + return p_indices; +} - if (indices == r_null) { - info.out_size = vec_size(x); - info.has_indices = false; +/* + * Generate the next `index` + * + * You can assume that the returned `index` is always protected by `p_indices`, + * so the caller doesn't need to protect it. + */ +static inline +r_obj* indices_next(struct vctrs_chop_indices* p_indices) { + const r_ssize loc = p_indices->loc; + ++(p_indices->loc); + + if (p_indices->has_indices) { + return p_indices->v_indices[loc]; + } else if (p_indices->has_sizes) { + const r_ssize start = p_indices->p_index[0] + p_indices->p_index[1]; + const r_ssize size = p_indices->v_sizes[loc]; + const bool increasing = true; + init_compact_seq(p_indices->p_index, start, size, increasing); + return p_indices->index; } else { - info.out_size = vec_size(indices); - info.has_indices = true; + *p_indices->p_index = loc + 1; + return p_indices->index; } +} - info.out = r_alloc_list(info.out_size); - r_list_poke(info.shelter, 2, info.out); - - FREE(1); - return info; +static inline +r_ssize indices_out_size(struct vctrs_chop_indices* p_indices, r_obj* x) { + if (p_indices->has_indices) { + return r_length(p_indices->indices); + } else if (p_indices->has_sizes) { + return r_length(p_indices->sizes); + } else { + return vec_size(x); + } } // ----------------------------------------------------------------------------- @@ -74,63 +158,73 @@ r_obj* ffi_vec_chop_seq(r_obj* x, r_obj* starts, r_obj* sizes, r_obj* increasing r_list_poke(indices, i, index); } - r_obj* out = KEEP(vec_chop(x, indices)); + r_obj* out = KEEP(vec_chop_unsafe(x, indices, r_null)); FREE(2); return out; } -r_obj* ffi_vec_chop(r_obj* x, r_obj* indices) { +r_obj* ffi_vec_chop(r_obj* x, r_obj* indices, r_obj* sizes) { + return vec_chop(x, indices, sizes); +} + +r_obj* vec_chop(r_obj* x, r_obj* indices, r_obj* sizes) { const r_ssize n = vec_size(x); r_obj* names = KEEP(vec_names(x)); - indices = KEEP(vec_as_indices(indices, n, names)); + if (indices != r_null && sizes != r_null) { + r_abort_lazy_call(r_lazy_null, "Can't supply both `indices` and `sizes`."); + } - r_obj* out = KEEP(vec_chop(x, indices)); + if (indices != r_null) { + indices = list_as_locations(indices, n, names); + } + KEEP(indices); + + if (sizes != r_null) { + sizes = vec_as_chop_sizes(sizes, n); + } + KEEP(sizes); + + r_obj* out = vec_chop_unsafe(x, indices, sizes); FREE(3); return out; } -// [[ include("vctrs.h") ]] -r_obj* vec_chop(r_obj* x, r_obj* indices) { - struct vctrs_chop_info info = new_chop_info(x, indices); +// Performance variant that doesn't check the types or values of `indices` / `sizes` +r_obj* vec_chop_unsafe(r_obj* x, r_obj* indices, r_obj* sizes) { + struct vctrs_proxy_info info = vec_proxy_info(x); KEEP(info.shelter); - r_obj* out = vec_chop_base(x, indices, info); + struct vctrs_chop_indices* p_indices = new_chop_indices(x, indices, sizes); + KEEP(p_indices->shelter); - FREE(1); + r_obj* out = vec_chop_base(x, info, p_indices); + + FREE(2); return out; } -static r_obj* vec_chop_base(r_obj* x, r_obj* indices, struct vctrs_chop_info info) { - struct vctrs_proxy_info proxy_info = info.proxy_info; - - // Fallback to `[` if the class doesn't implement a proxy. This is - // to be maximally compatible with existing classes. - if (vec_requires_fallback(x, proxy_info)) { - if (proxy_info.type == VCTRS_TYPE_scalar) { +static +r_obj* vec_chop_base(r_obj* x, + struct vctrs_proxy_info info, + struct vctrs_chop_indices* p_indices) { + if (vec_requires_fallback(x, info)) { + // Fallback to `[` if the class doesn't implement a proxy. This is + // to be maximally compatible with existing classes. + if (info.type == VCTRS_TYPE_scalar) { r_abort_lazy_call(r_lazy_null, "Can't slice a scalar"); } - if (info.has_indices) { - for (r_ssize i = 0; i < info.out_size; ++i) { - r_obj* index = r_list_get(indices, i); - - if (is_compact(index)) { - r_list_poke(indices, i, compact_materialize(index)); - } - } - } - if (has_dim(x)) { - return chop_fallback_shaped(x, indices, info); + return chop_fallback_shaped(x, p_indices); + } else { + return chop_fallback(x, p_indices); } - - return chop_fallback(x, indices, info); } - switch (proxy_info.type) { + switch (info.type) { case VCTRS_TYPE_logical: case VCTRS_TYPE_integer: case VCTRS_TYPE_double: @@ -139,35 +233,33 @@ static r_obj* vec_chop_base(r_obj* x, r_obj* indices, struct vctrs_chop_info inf case VCTRS_TYPE_raw: case VCTRS_TYPE_list: { if (has_dim(x)) { - return chop_shaped(x, indices, info); + return chop_shaped(x, info, p_indices); + } else { + return chop(x, info, p_indices); } - - return chop(x, indices, info); } case VCTRS_TYPE_dataframe: { - return chop_df(x, indices, info); + return chop_df(x, info, p_indices); } default: obj_check_vector(x, vec_args.empty, r_lazy_null); - stop_unimplemented_vctrs_type("vec_chop_base", proxy_info.type); + stop_unimplemented_vctrs_type("vec_chop_base", info.type); } } -static r_obj* chop(r_obj* x, r_obj* indices, struct vctrs_chop_info info) { - r_obj* proxy = info.proxy_info.proxy; +static +r_obj* chop(r_obj* x, + struct vctrs_proxy_info info, + struct vctrs_chop_indices* p_indices) { + r_obj* proxy = info.proxy; r_obj* names = KEEP(r_names(proxy)); + const enum vctrs_type type = info.type; - r_obj* const* v_indices = NULL; - if (info.has_indices) { - v_indices = r_list_cbegin(indices); - } + const r_ssize out_size = indices_out_size(p_indices, proxy); + r_obj* out = KEEP(r_alloc_list(out_size)); - for (r_ssize i = 0; i < info.out_size; ++i) { - if (info.has_indices) { - info.index = v_indices[i]; - } else { - ++(*info.p_index); - } + for (r_ssize i = 0; i < out_size; ++i) { + r_obj* index = indices_next(p_indices); // Always materialize ALTREP vectors when chopping to avoid inefficiently // creating a large amount of small ALTREP objects that are used downstream. @@ -175,29 +267,32 @@ static r_obj* chop(r_obj* x, r_obj* indices, struct vctrs_chop_info info) { // we chop to create a small amount of large ALTREP objects that are // quickly discarded (#1450). r_obj* elt = KEEP(vec_slice_base( - info.proxy_info.type, + type, proxy, - info.index, + index, VCTRS_MATERIALIZE_true )); if (names != r_null) { - r_obj* elt_names = slice_names(names, info.index); + r_obj* elt_names = slice_names(names, index); r_attrib_poke_names(elt, elt_names); } elt = vec_restore(elt, x, vec_owned(elt)); - r_list_poke(info.out, i, elt); + r_list_poke(out, i, elt); FREE(1); } - FREE(1); - return info.out; + FREE(2); + return out; } -static r_obj* chop_df(r_obj* x, r_obj* indices, struct vctrs_chop_info info) { - r_obj* proxy = info.proxy_info.proxy; +static +r_obj* chop_df(r_obj* x, + struct vctrs_proxy_info info, + struct vctrs_chop_indices* p_indices) { + r_obj* proxy = info.proxy; r_obj* const* v_proxy = r_list_cbegin(proxy); const r_ssize n_cols = r_length(proxy); @@ -205,48 +300,41 @@ static r_obj* chop_df(r_obj* x, r_obj* indices, struct vctrs_chop_info info) { r_obj* col_names = KEEP(r_names(proxy)); r_obj* row_names = KEEP(df_rownames(proxy)); - bool has_row_names = r_typeof(row_names) == R_TYPE_character; + const bool has_row_names = r_typeof(row_names) == R_TYPE_character; - r_obj* const* v_out = r_list_cbegin(info.out); - - r_obj* const* v_indices = NULL; - if (info.has_indices) { - v_indices = r_list_cbegin(indices); - } + const r_ssize out_size = indices_out_size(p_indices, proxy); + r_obj* out = KEEP(r_alloc_list(out_size)); + r_obj* const* v_out = r_list_cbegin(out); // Pre-load the `out` container with empty bare data frames - for (r_ssize i = 0; i < info.out_size; ++i) { + for (r_ssize i = 0; i < out_size; ++i) { r_obj* elt = r_alloc_list(n_cols); - r_list_poke(info.out, i, elt); + r_list_poke(out, i, elt); r_attrib_poke_names(elt, col_names); - r_ssize size = -1; - - if (info.has_indices) { - info.index = v_indices[i]; - size = vec_subscript_size(info.index); - } else { - ++(*info.p_index); - size = 1; - } + r_obj* index = indices_next(p_indices); + const r_ssize size = vec_subscript_size(index); init_data_frame(elt, size); if (has_row_names) { - r_obj* elt_row_names = slice_rownames(row_names, info.index); - r_attrib_poke(elt, R_RowNamesSymbol, elt_row_names); + r_obj* elt_row_names = slice_rownames(row_names, index); + r_attrib_poke(elt, r_syms.row_names, elt_row_names); } } + r_obj* indices = p_indices->indices; + r_obj* sizes = p_indices->sizes; + // Chop each column according to the indices, and then assign the results // into the appropriate data frame column in the `out` list for (r_ssize i = 0; i < n_cols; ++i) { r_obj* col = v_proxy[i]; - r_obj* col_chopped = KEEP(vec_chop(col, indices)); + r_obj* col_chopped = KEEP(vec_chop_unsafe(col, indices, sizes)); r_obj* const* v_col_chopped = r_list_cbegin(col_chopped); - for (r_ssize j = 0; j < info.out_size; ++j) { + for (r_ssize j = 0; j < out_size; ++j) { r_obj* elt = v_out[j]; r_list_poke(elt, i, v_col_chopped[j]); } @@ -255,18 +343,23 @@ static r_obj* chop_df(r_obj* x, r_obj* indices, struct vctrs_chop_info info) { } // Restore each data frame - for (r_ssize i = 0; i < info.out_size; ++i) { + for (r_ssize i = 0; i < out_size; ++i) { r_obj* elt = v_out[i]; elt = vec_restore(elt, x, vec_owned(elt)); - r_list_poke(info.out, i, elt); + r_list_poke(out, i, elt); } - FREE(2); - return info.out; + FREE(3); + return out; } -static r_obj* chop_shaped(r_obj* x, r_obj* indices, struct vctrs_chop_info info) { - r_obj* proxy = info.proxy_info.proxy; +static +r_obj* chop_shaped(r_obj* x, + struct vctrs_proxy_info info, + struct vctrs_chop_indices* p_indices) { + r_obj* proxy = info.proxy; + const enum vctrs_type type = info.type; + r_obj* dim_names = KEEP(r_dim_names(proxy)); r_obj* row_names = r_null; @@ -274,26 +367,20 @@ static r_obj* chop_shaped(r_obj* x, r_obj* indices, struct vctrs_chop_info info) row_names = r_list_get(dim_names, 0); } - r_obj* const* v_indices = NULL; - if (info.has_indices) { - v_indices = r_list_cbegin(indices); - } + const r_ssize out_size = indices_out_size(p_indices, proxy); + r_obj* out = KEEP(r_alloc_list(out_size)); - for (r_ssize i = 0; i < info.out_size; ++i) { - if (info.has_indices) { - info.index = v_indices[i]; - } else { - ++(*info.p_index); - } + for (r_ssize i = 0; i < out_size; ++i) { + r_obj* index = indices_next(p_indices); - r_obj* elt = KEEP(vec_slice_shaped(info.proxy_info.type, proxy, info.index)); + r_obj* elt = KEEP(vec_slice_shaped(type, proxy, index)); if (dim_names != r_null) { if (row_names != r_null) { // Required to slice row names to the right size before poking to avoid // erroring on the dimnames length check in `Rf_setAttrib()` r_obj* new_dim_names = KEEP(r_clone(dim_names)); - r_obj* new_row_names = slice_names(row_names, info.index); + r_obj* new_row_names = slice_names(row_names, index); r_list_poke(new_dim_names, 0, new_row_names); r_attrib_poke_dim_names(elt, new_dim_names); FREE(1); @@ -303,16 +390,17 @@ static r_obj* chop_shaped(r_obj* x, r_obj* indices, struct vctrs_chop_info info) } elt = vec_restore(elt, x, vec_owned(elt)); - r_list_poke(info.out, i, elt); + r_list_poke(out, i, elt); FREE(1); } - FREE(1); - return info.out; + FREE(2); + return out; } -static r_obj* chop_fallback(r_obj* x, r_obj* indices, struct vctrs_chop_info info) { +static +r_obj* chop_fallback(r_obj* x, struct vctrs_chop_indices* p_indices) { // Evaluate in a child of the global environment to allow dispatch // to custom functions. We define `[` to point to its base // definition to ensure consistent look-up. This is the same logic @@ -320,7 +408,6 @@ static r_obj* chop_fallback(r_obj* x, r_obj* indices, struct vctrs_chop_info inf // evaluations in a loop. r_obj* env = KEEP(r_new_environment(r_envs.global)); r_env_poke(env, syms_x, x); - r_env_poke(env, syms_i, info.index); // Construct call with symbols, not values, for performance. // TODO - Remove once bit64 is updated on CRAN. Special casing integer64 @@ -334,19 +421,19 @@ static r_obj* chop_fallback(r_obj* x, r_obj* indices, struct vctrs_chop_info inf r_env_poke(env, syms_bracket, fns_bracket); } - r_obj* const* v_indices = NULL; - if (info.has_indices) { - v_indices = r_list_cbegin(indices); - } + const r_ssize out_size = indices_out_size(p_indices, x); + r_obj* out = KEEP(r_alloc_list(out_size)); - for (r_ssize i = 0; i < info.out_size; ++i) { - if (info.has_indices) { - info.index = v_indices[i]; - // Update `i` binding with the new index value - r_env_poke(env, syms_i, info.index); - } else { - ++(*info.p_index); + for (r_ssize i = 0; i < out_size; ++i) { + r_obj* index = indices_next(p_indices); + + if (is_compact(index)) { + index = compact_materialize(index); } + KEEP(index); + + // Update `i` binding with the new index value + r_env_poke(env, syms_i, index); r_obj* elt = KEEP(r_eval(call, env)); @@ -354,42 +441,41 @@ static r_obj* chop_fallback(r_obj* x, r_obj* indices, struct vctrs_chop_info inf elt = vec_restore(elt, x, vec_owned(elt)); } - r_list_poke(info.out, i, elt); - FREE(1); + r_list_poke(out, i, elt); + FREE(2); } - FREE(2); - return info.out; + FREE(3); + return out; } -static r_obj* chop_fallback_shaped(r_obj* x, r_obj* indices, struct vctrs_chop_info info) { - r_obj* const* v_indices = NULL; - if (info.has_indices) { - v_indices = r_list_cbegin(indices); - } +static +r_obj* chop_fallback_shaped(r_obj* x, struct vctrs_chop_indices* p_indices) { + const r_ssize out_size = indices_out_size(p_indices, x); + r_obj* out = KEEP(r_alloc_list(out_size)); - for (r_ssize i = 0; i < info.out_size; ++i) { - if (info.has_indices) { - info.index = v_indices[i]; - } else { - ++(*info.p_index); + for (r_ssize i = 0; i < out_size; ++i) { + r_obj* index = indices_next(p_indices); + + if (is_compact(index)) { + index = compact_materialize(index); } + KEEP(index); // `vec_slice_fallback()` will also `vec_restore()` for us - r_obj* elt = vec_slice_fallback(x, info.index); - r_list_poke(info.out, i, elt); + r_obj* elt = vec_slice_fallback(x, index); + r_list_poke(out, i, elt); + + FREE(1); } - return info.out; + FREE(1); + return out; } // ----------------------------------------------------------------------------- -r_obj* vec_as_indices(r_obj* indices, r_ssize n, r_obj* names) { - if (indices == r_null) { - return indices; - } - +r_obj* list_as_locations(r_obj* indices, r_ssize n, r_obj* names) { if (r_typeof(indices) != R_TYPE_list) { r_abort_lazy_call(r_lazy_null, "`indices` must be a list of index values, or `NULL`."); } @@ -421,3 +507,40 @@ r_obj* vec_as_indices(r_obj* indices, r_ssize n, r_obj* names) { FREE(1); return indices; } + +static +r_obj* vec_as_chop_sizes(r_obj* sizes, r_ssize size) { + sizes = KEEP(vec_cast( + sizes, + r_globals.empty_int, + vec_args.sizes, + vec_args.empty, + r_lazy_null + )); + + const r_ssize n_sizes = r_length(sizes); + const int* v_sizes = r_int_cbegin(sizes); + + r_ssize total = 0; + + for (r_ssize i = 0; i < n_sizes; ++i) { + const int elt = v_sizes[i]; + + if (elt == r_globals.na_int) { + r_abort_lazy_call(r_lazy_null, "`sizes` can't contain missing values."); + } else if (elt < 0) { + r_abort_lazy_call(r_lazy_null, "`sizes` can't contain negative sizes."); + } else if (elt > size) { + r_abort_lazy_call(r_lazy_null, "`sizes` can't contain sizes larger than %i.", size); + } + + total += elt; + } + + if (total != size) { + r_abort_lazy_call(r_lazy_null, "`sizes` must sum to size %i, not size %i.", size, total); + } + + FREE(1); + return sizes; +} diff --git a/src/slice-chop.h b/src/slice-chop.h index 1ee008450..f5b20c698 100644 --- a/src/slice-chop.h +++ b/src/slice-chop.h @@ -3,8 +3,10 @@ #include "vctrs-core.h" +r_obj* vec_chop(r_obj* x, r_obj* indices, r_obj* sizes); +r_obj* vec_chop_unsafe(r_obj*, r_obj* indices, r_obj* sizes); -r_obj* vec_as_indices(r_obj* indices, r_ssize n, r_obj* names); +r_obj* list_as_locations(r_obj* indices, r_ssize n, r_obj* names); #endif diff --git a/src/split.c b/src/split.c index 6977c0ef8..fde68cace 100644 --- a/src/split.c +++ b/src/split.c @@ -10,7 +10,7 @@ SEXP vec_split(SEXP x, SEXP by) { SEXP indices = VECTOR_ELT(out, 1); - SEXP val = vec_chop(x, indices); + SEXP val = vec_chop_unsafe(x, indices, r_null); SET_VECTOR_ELT(out, 1, val); SEXP names = PROTECT(Rf_getAttrib(out, R_NamesSymbol)); diff --git a/src/utils.c b/src/utils.c index a4cd4033c..3ba8823a9 100644 --- a/src/utils.c +++ b/src/utils.c @@ -822,7 +822,7 @@ r_obj* list_pluck(r_obj* xs, r_ssize i) { SEXP compact_seq_attrib = NULL; // p[0] = Start value -// p[1] = Sequence size. Always >= 1. +// p[1] = Sequence size. Always >= 0. // p[2] = Step size to increment/decrement `start` with void init_compact_seq(int* p, R_len_t start, R_len_t size, bool increasing) { int step = increasing ? 1 : -1; diff --git a/src/vctrs.h b/src/vctrs.h index 61f5b4a33..bedce903d 100644 --- a/src/vctrs.h +++ b/src/vctrs.h @@ -77,7 +77,6 @@ SEXP vec_proxy_equal(SEXP x); SEXP vec_proxy_compare(SEXP x); SEXP vec_proxy_order(SEXP x); SEXP vec_proxy_unwrap(SEXP x); -r_obj* vec_chop(r_obj* x, r_obj* indices); SEXP vec_slice_shaped(enum vctrs_type type, SEXP x, SEXP index); bool vec_requires_fallback(SEXP x, struct vctrs_proxy_info info); r_obj* vec_ptype(r_obj* x, struct vctrs_arg* x_arg, struct r_lazy call); diff --git a/tests/testthat/_snaps/c.md b/tests/testthat/_snaps/c.md index 06e9e6d60..90f15bfc5 100644 --- a/tests/testthat/_snaps/c.md +++ b/tests/testthat/_snaps/c.md @@ -256,13 +256,13 @@ }) with_memory_prof(list_unchop(make_list_of(1000))) Output - [1] 111KB + [1] 103KB Code with_memory_prof(list_unchop(make_list_of(2000))) Output - [1] 220KB + [1] 205KB Code with_memory_prof(list_unchop(make_list_of(4000))) Output - [1] 439KB + [1] 408KB diff --git a/tests/testthat/_snaps/slice-chop.md b/tests/testthat/_snaps/slice-chop.md index bcbf31621..0f1b4d4ef 100644 --- a/tests/testthat/_snaps/slice-chop.md +++ b/tests/testthat/_snaps/slice-chop.md @@ -1,3 +1,121 @@ +# `indices` are validated + + Code + vec_chop(1, indices = 1) + Condition + Error: + ! `indices` must be a list of index values, or `NULL`. + +--- + + Code + (expect_error(vec_chop(1, indices = list(1.5)), class = "vctrs_error_subscript_type") + ) + Output + + Error: + ! Can't subset elements. + x Can't convert from to due to loss of precision. + +--- + + Code + (expect_error(vec_chop(1, indices = list(2)), class = "vctrs_error_subscript_oob") + ) + Output + + Error: + ! Can't subset elements past the end. + i Location 2 doesn't exist. + i There is only 1 element. + +# `sizes` are validated + + Code + vec_chop("a", sizes = "a") + Condition + Error: + ! Can't convert `sizes` to . + +--- + + Code + vec_chop("a", sizes = 2) + Condition + Error: + ! `sizes` can't contain sizes larger than 1. + +--- + + Code + vec_chop("a", sizes = -1) + Condition + Error: + ! `sizes` can't contain negative sizes. + +--- + + Code + vec_chop("a", sizes = NA_integer_) + Condition + Error: + ! `sizes` can't contain missing values. + +--- + + Code + vec_chop("a", sizes = c(1, 1)) + Condition + Error: + ! `sizes` must sum to size 1, not size 2. + +# can't use both `indices` and `sizes` + + Code + vec_chop(1, indices = list(1), sizes = 1) + Condition + Error: + ! Can't supply both `indices` and `sizes`. + +# `vec_chop(x, indices)` backwards compatible behavior works + + Code + vec_chop(1:2, 1) + Condition + Error: + ! `indices` must be a list of index values, or `NULL`. + +--- + + Code + vec_chop(1, list(1), sizes = 1) + Condition + Error: + ! Can't supply both `indices` and `sizes`. + +--- + + Code + vec_chop(1, list(1), 2) + Condition + Error in `vec_chop()`: + ! `...` must be empty. + x Problematic arguments: + * ..1 = list(1) + * ..2 = 2 + i Did you forget to name an argument? + +--- + + Code + vec_chop(1, list(1), indices = list(1)) + Condition + Error in `vec_chop()`: + ! `...` must be empty. + x Problematic argument: + * ..1 = list(1) + i Did you forget to name an argument? + # `x` must be a list Code @@ -143,12 +261,14 @@ # list_unchop() can repair names quietly Code - res <- list_unchop(vec_chop(x, indices), indices = indices, name_repair = "unique_quiet") + res <- list_unchop(vec_chop(x, indices = indices), indices = indices, + name_repair = "unique_quiet") --- Code - res <- list_unchop(vec_chop(x, indices), indices = indices, name_repair = "universal_quiet") + res <- list_unchop(vec_chop(x, indices = indices), indices = indices, + name_repair = "universal_quiet") # list_unchop() errors on unsupported location values diff --git a/tests/testthat/test-slice-chop.R b/tests/testthat/test-slice-chop.R index 63ada09cf..30a9b3a7b 100644 --- a/tests/testthat/test-slice-chop.R +++ b/tests/testthat/test-slice-chop.R @@ -63,6 +63,10 @@ test_that("vec_chop() keeps data frame row names for data frames with 0 columns out <- vec_chop(x, indices = list(c(2, NA), 3)) out <- lapply(out, rownames) expect_identical(out, list(c("r2", "...2"), "r3")) + + out <- vec_chop(x, sizes = c(1, 2, 0)) + out <- lapply(out, rownames) + expect_identical(out, list("r1", c("r2", "r3"), character())) }) test_that("data frames with 0 columns retain the right number of rows (#1722)", { @@ -76,7 +80,19 @@ test_that("data frames with 0 columns retain the right number of rows (#1722)", expect_identical( vec_chop(x, indices = list(c(1, 3, 2), c(3, NA))), - list(data_frame(.size = 3), data_frame(.size = 2)) + list( + data_frame(.size = 3), + data_frame(.size = 2) + ) + ) + + expect_identical( + vec_chop(x, sizes = c(3, 1, 0)), + list( + data_frame(.size = 3), + data_frame(.size = 1), + data_frame(.size = 0) + ) ) }) @@ -106,6 +122,12 @@ test_that("vec_chop() doesn't restore when attributes have already been restored result <- vec_chop(foobar(NA))[[1]] expect_equal(result, structure("dispatched", foo = "bar")) + + result <- vec_chop(foobar(NA), indices = list(1))[[1]] + expect_equal(result, structure("dispatched", foo = "bar")) + + result <- vec_chop(foobar(NA), sizes = 1)[[1]] + expect_equal(result, structure("dispatched", foo = "bar")) }) test_that("vec_chop() does not restore when attributes have not been restored by `[`", { @@ -116,82 +138,165 @@ test_that("vec_chop() does not restore when attributes have not been restored by result <- vec_chop(foobar(NA))[[1]] expect_equal(result, "dispatched") + + result <- vec_chop(foobar(NA), indices = list(1))[[1]] + expect_equal(result, "dispatched") + + result <- vec_chop(foobar(NA), sizes = 1)[[1]] + expect_equal(result, "dispatched") }) test_that("vec_chop() falls back to `[` for shaped objects with no proxy", { x <- foobar(1) dim(x) <- c(1, 1) + result <- vec_chop(x)[[1]] expect_equal(result, x) + + result <- vec_chop(x, indices = list(1))[[1]] + expect_equal(result, x) + + result <- vec_chop(x, sizes = 1)[[1]] + expect_equal(result, x) }) test_that("`indices` are validated", { - expect_error(vec_chop(1, 1), "`indices` must be a list of index values, or `NULL`") - expect_error(vec_chop(1, list(1.5)), class = "vctrs_error_subscript_type") - expect_error(vec_chop(1, list(2)), class = "vctrs_error_subscript_oob") + expect_snapshot(error = TRUE, { + vec_chop(1, indices = 1) + }) + expect_snapshot({ + (expect_error(vec_chop(1, indices = list(1.5)), class = "vctrs_error_subscript_type")) + }) + expect_snapshot({ + (expect_error(vec_chop(1, indices = list(2)), class = "vctrs_error_subscript_oob")) + }) +}) + +test_that("`sizes` are validated", { + expect_snapshot(error = TRUE, { + vec_chop("a", sizes = "a") + }) + expect_snapshot(error = TRUE, { + vec_chop("a", sizes = 2) + }) + expect_snapshot(error = TRUE, { + vec_chop("a", sizes = -1) + }) + expect_snapshot(error = TRUE, { + vec_chop("a", sizes = NA_integer_) + }) + expect_snapshot(error = TRUE, { + vec_chop("a", sizes = c(1, 1)) + }) +}) + +test_that("can't use both `indices` and `sizes`", { + expect_snapshot(error = TRUE, { + vec_chop(1, indices = list(1), sizes = 1) + }) +}) + +test_that("`sizes` allows `0`", { + expect_identical( + vec_chop(c("a", "b"), sizes = c(1, 0, 0, 1, 0)), + list("a", character(), character(), "b", character()) + ) }) test_that("size 0 `indices` list is allowed", { - expect_equal(vec_chop(1, list()), list()) + expect_equal(vec_chop(1, indices = list()), list()) }) test_that("individual index values of size 0 are allowed", { - expect_equal(vec_chop(1, list(integer())), list(numeric())) + expect_equal(vec_chop(1, indices = list(integer())), list(numeric())) + + df <- data.frame(a = 1, b = "1") + expect_equal(vec_chop(df, indices = list(integer())), list(vec_ptype(df))) +}) + +test_that("individual index values of `NULL` are allowed", { + expect_equal(vec_chop(1, indices = list(NULL)), list(numeric())) df <- data.frame(a = 1, b = "1") - expect_equal(vec_chop(df, list(integer())), list(vec_ptype(df))) + expect_equal(vec_chop(df, indices = list(NULL)), list(vec_ptype(df))) }) -test_that("data frame row names are kept when `indices` are used", { +test_that("data frame row names are kept when `indices` or `sizes` are used", { x <- data_frame(x = 1:2, y = c("a", "b")) rownames(x) <- c("r1", "r2") - result <- lapply(vec_chop(x, list(1, 1:2)), rownames) + + result <- lapply(vec_chop(x, indices = list(1, 1:2)), rownames) expect_equal(result, list("r1", c("r1", "r2"))) + + result <- lapply(vec_chop(x, sizes = c(1, 0, 1)), rownames) + expect_equal(result, list("r1", character(), "r2")) }) -test_that("vec_chop(, indices =) can be equivalent to the default", { +test_that("vec_chop(, indices/sizes =) can be equivalent to the default", { x <- 1:5 + indices <- as.list(vec_seq_along(x)) - expect_equal(vec_chop(x, indices), vec_chop(x)) + expect_equal(vec_chop(x, indices = indices), vec_chop(x)) + + sizes <- vec_rep(1L, times = vec_size(x)) + expect_equal(vec_chop(x, sizes = sizes), vec_chop(x)) }) -test_that("vec_chop(, indices =) can be equivalent to the default", { +test_that("vec_chop(, indices/sizes =) can be equivalent to the default", { x <- data.frame(x = 1:5) + indices <- as.list(vec_seq_along(x)) - expect_equal(vec_chop(x, indices), vec_chop(x)) + expect_equal(vec_chop(x, indices = indices), vec_chop(x)) + + sizes <- vec_rep(1L, times = vec_size(x)) + expect_equal(vec_chop(x, sizes = sizes), vec_chop(x)) }) -test_that("vec_chop(, indices =) can be equivalent to the default", { +test_that("vec_chop(, indices/sizes =) can be equivalent to the default", { x <- array(1:8, c(2, 2, 2)) + indices <- as.list(vec_seq_along(x)) - expect_equal(vec_chop(x, indices), vec_chop(x)) + expect_equal(vec_chop(x, indices = indices), vec_chop(x)) + + sizes <- vec_rep(1L, times = vec_size(x)) + expect_equal(vec_chop(x, sizes = sizes), vec_chop(x)) }) test_that("`indices` cannot use names", { x <- set_names(1:3, c("a", "b", "c")) - expect_error(vec_chop(x, list("a", c("b", "c"))), class = "vctrs_error_subscript_type") + expect_error(vec_chop(x, indices = list("a", c("b", "c"))), class = "vctrs_error_subscript_type") x <- array(1:4, c(2, 2), dimnames = list(c("r1", "r2"))) - expect_error(vec_chop(x, list("r1")), class = "vctrs_error_subscript_type") + expect_error(vec_chop(x, indices = list("r1")), class = "vctrs_error_subscript_type") x <- data.frame(x = 1, row.names = "r1") - expect_error(vec_chop(x, list("r1")), class = "vctrs_error_subscript_type") + expect_error(vec_chop(x, indices = list("r1")), class = "vctrs_error_subscript_type") }) -test_that("fallback method with `indices` works", { +test_that("fallback method with `indices` and `sizes` works", { fctr <- factor(c("a", "b")) + indices <- list(1, c(1, 2)) + sizes <- c(1, 0, 1) expect_equal( - vec_chop(fctr, indices), + vec_chop(fctr, indices = indices), map(indices, vec_slice, x = fctr) ) + expect_equal( + vec_chop(fctr, sizes = sizes), + list(vec_slice(fctr, 1), vec_slice(fctr, 0), vec_slice(fctr, 2)) + ) }) -test_that("vec_chop() falls back to `[` for shaped objects with no proxy when indices are provided", { +test_that("vec_chop() falls back to `[` for shaped objects with no proxy when `indices` or `sizes` are provided", { x <- foobar(1) dim(x) <- c(1, 1) - result <- vec_chop(x, list(1))[[1]] + + result <- vec_chop(x, indices = list(1))[[1]] + expect_equal(result, x) + + result <- vec_chop(x, sizes = 1)[[1]] expect_equal(result, x) }) @@ -239,6 +344,30 @@ test_that("ALTREP objects always generate materialized chops (#1450)", { expect_identical(result, expect) }) +test_that("`vec_chop(x, indices)` backwards compatible behavior works", { + # No issues here + expect_identical( + vec_chop(1:2, list(1, 2)), + vec_chop(1:2, indices = list(1, 2)) + ) + + # Errors still talk about `indices` + expect_snapshot(error = TRUE, { + vec_chop(1:2, 1) + }) + expect_snapshot(error = TRUE, { + vec_chop(1, list(1), sizes = 1) + }) + + # These cases aren't allowed because they weren't possible previously either + expect_snapshot(error = TRUE, { + vec_chop(1, list(1), 2) + }) + expect_snapshot(error = TRUE, { + vec_chop(1, list(1), indices = list(1)) + }) +}) + # vec_chop + compact_seq -------------------------------------------------- # `start` is 0-based @@ -622,14 +751,14 @@ test_that("list_unchop() can repair names quietly", { x <- c(x = "a", x = "b", x = "c") indices <- list(2, c(3, 1)) expect_snapshot({ - res <- list_unchop(vec_chop(x, indices), indices = indices, name_repair = "unique_quiet") + res <- list_unchop(vec_chop(x, indices = indices), indices = indices, name_repair = "unique_quiet") }) expect_named(res, c("x...1", "x...2", "x...3")) x <- c("if" = "a", "in" = "b", "for" = "c") indices <- list(2, c(3, 1)) expect_snapshot({ - res <- list_unchop(vec_chop(x, indices), indices = indices, name_repair = "universal_quiet") + res <- list_unchop(vec_chop(x, indices = indices), indices = indices, name_repair = "universal_quiet") }) expect_named(res, c(".if", ".in", ".for")) }) diff --git a/tests/testthat/test-slice.R b/tests/testthat/test-slice.R index 02939d748..3d8fe076f 100644 --- a/tests/testthat/test-slice.R +++ b/tests/testthat/test-slice.R @@ -690,7 +690,7 @@ test_that("vec_slice() restores unrestored but named foreign classes", { expect_identical(vec_slice(x, 1), x) expect_identical(vec_chop(x), list(x)) - expect_identical(vec_chop(x, list(1)), list(x)) + expect_identical(vec_chop(x, indices = list(1)), list(x)) expect_identical(vec_ptype(x), foobar(named(dbl()))) expect_identical(vec_ptype(x), foobar(named(dbl()))) expect_identical(vec_ptype_common(x, x), foobar(named(dbl()))) diff --git a/tests/testthat/test-type-integer64.R b/tests/testthat/test-type-integer64.R index 82a36a151..c92a0b618 100644 --- a/tests/testthat/test-type-integer64.R +++ b/tests/testthat/test-type-integer64.R @@ -116,7 +116,7 @@ test_that("can chop integer64 objects with `NA_integer_` indices", { bit64::as.integer64(1) ) - expect_identical(vec_chop(x, idx), expect) + expect_identical(vec_chop(x, indices = idx), expect) dim(x) <- c(4, 2) expect <- list( @@ -126,7 +126,7 @@ test_that("can chop integer64 objects with `NA_integer_` indices", { dim(expect[[1]]) <- c(1, 2) dim(expect[[2]]) <- c(1, 2) - expect_identical(vec_chop(x, idx), expect) + expect_identical(vec_chop(x, indices = idx), expect) dim(x) <- c(2, 2, 2) expect <- list( @@ -136,7 +136,7 @@ test_that("can chop integer64 objects with `NA_integer_` indices", { dim(expect[[1]]) <- c(1, 2, 2) dim(expect[[2]]) <- c(1, 2, 2) - expect_identical(vec_chop(x, idx), expect) + expect_identical(vec_chop(x, indices = idx), expect) }) test_that("equality proxy converts atomic input to data frames of doubles", { From 0dea6caae799b026d32bbc974859d29ae3626bfc Mon Sep 17 00:00:00 2001 From: DavisVaughan Date: Thu, 9 Mar 2023 09:56:22 -0500 Subject: [PATCH 260/312] Use efficient `vec_chop(sizes =)` in numeric-version proxy --- R/type-misc.R | 12 +----------- 1 file changed, 1 insertion(+), 11 deletions(-) diff --git a/R/type-misc.R b/R/type-misc.R index 13c06d237..fb1c5cae9 100644 --- a/R/type-misc.R +++ b/R/type-misc.R @@ -53,17 +53,7 @@ proxy_equal_numeric_version <- function(x, error_call = caller_env()) { # Transpose with combination of `vec_interleave()` and `vec_chop()` x <- vec_interleave(!!!x, .ptype = integer()) - - # TODO: `vec_chop(sizes = vec_rep(size, times = max))` - index <- seq_len(size) - indices <- vector("list", length = max) - - for (i in seq_len(max)) { - indices[[i]] <- index - index <- index + size - } - - out <- vec_chop(x, indices = indices) + out <- vec_chop(x, sizes = vec_rep(size, times = max)) n_zeros <- N_COMPONENTS - max From 4f52e114008d8c49606b969fc9d675137c8faf41 Mon Sep 17 00:00:00 2001 From: Davis Vaughan Date: Wed, 15 Mar 2023 08:38:55 -0400 Subject: [PATCH 261/312] Update rlang C lib (#1815) * Update rlang C lib * Remove usage of `r_list_all_of()` * Update snapshot test with latest rlang C lib * Remove old unused `r_new_environment()` This is now rlang's `r_alloc_environment()` * Remove `r_new_environment()` in favor of `r_alloc_empty_environment()` * NEWS bullet * Remove NEWS bullet * Add a TODO --- src/names.c | 2 +- src/order-collate.c | 2 +- src/rlang-rcc.cpp | 1 - src/rlang/attrib.c | 3 +- src/rlang/c-utils.h | 20 ++++++ src/rlang/decl/env-decl.h | 2 + src/rlang/env.c | 9 +++ src/rlang/env.h | 9 +++ src/rlang/globals.c | 3 + src/rlang/globals.h | 3 + src/rlang/node.c | 11 +-- src/rlang/rlang.c | 6 ++ src/rlang/rlang.hpp | 3 + src/rlang/vec-lgl.c | 114 ++++++++++++++++++-------------- src/rlang/vec.h | 2 +- src/slice-chop.c | 2 +- src/type-info.c | 15 ++++- src/utils.c | 19 +----- src/utils.h | 7 -- tests/testthat/_snaps/assert.md | 5 +- tests/testthat/test-assert.R | 4 -- 21 files changed, 148 insertions(+), 94 deletions(-) delete mode 100644 src/rlang-rcc.cpp diff --git a/src/names.c b/src/names.c index 5373e01c7..5f0890849 100644 --- a/src/names.c +++ b/src/names.c @@ -122,7 +122,7 @@ r_obj* vec_as_custom_names(r_obj* names, const struct name_repair_opts* opts) { // Don't use vctrs dispatch utils because we match argument positionally r_obj* call = KEEP(r_call2(syms_repair, syms_names)); - r_obj* mask = KEEP(r_new_environment(R_GlobalEnv)); + r_obj* mask = KEEP(r_alloc_empty_environment(R_GlobalEnv)); r_env_poke(mask, syms_repair, opts->fn); r_env_poke(mask, syms_names, names); r_obj* out = KEEP(r_eval(call, mask)); diff --git a/src/order-collate.c b/src/order-collate.c index 8ae333a9f..312b094d9 100644 --- a/src/order-collate.c +++ b/src/order-collate.c @@ -44,7 +44,7 @@ SEXP chr_apply(SEXP x, SEXP chr_proxy_collate) { // Don't use vctrs dispatch utils because we match argument positionally SEXP call = PROTECT(Rf_lang2(syms_chr_proxy_collate, syms_x)); - SEXP mask = PROTECT(r_new_environment(R_GlobalEnv)); + SEXP mask = PROTECT(r_alloc_empty_environment(R_GlobalEnv)); Rf_defineVar(syms_chr_proxy_collate, chr_proxy_collate, mask); Rf_defineVar(syms_x, x, mask); diff --git a/src/rlang-rcc.cpp b/src/rlang-rcc.cpp deleted file mode 100644 index a45951dbd..000000000 --- a/src/rlang-rcc.cpp +++ /dev/null @@ -1 +0,0 @@ -#include "rlang/cpp/rlang.cpp" diff --git a/src/rlang/attrib.c b/src/rlang/attrib.c index 105ae99c3..98580346b 100644 --- a/src/rlang/attrib.c +++ b/src/rlang/attrib.c @@ -78,7 +78,7 @@ r_obj* r_attrs_zap_at(r_obj* attrs, r_obj* node, r_obj* value) { return attrs; } r_obj* r_clone2(r_obj* x) { - r_obj* attrs = r_attrib(x); + r_obj* attrs = KEEP(r_attrib(x)); // Prevent attributes from being cloned r_poke_attrib(x, r_null); @@ -86,6 +86,7 @@ r_obj* r_clone2(r_obj* x) { r_poke_attrib(x, attrs); r_poke_attrib(out, attrs); + FREE(1); return out; } diff --git a/src/rlang/c-utils.h b/src/rlang/c-utils.h index fbb5b7ff6..601e69f68 100644 --- a/src/rlang/c-utils.h +++ b/src/rlang/c-utils.h @@ -23,6 +23,26 @@ void* r_shelter_deref(r_obj* x); +// Allow integers up to 2^52, same as R_XLEN_T_MAX when long vector +// support is enabled +#define RLANG_MAX_DOUBLE_INT 4503599627370496 +#define RLANG_MIN_DOUBLE_INT -4503599627370496 + +static inline +bool r_dbl_is_whole(double x) { + if (x > RLANG_MAX_DOUBLE_INT || x < RLANG_MIN_DOUBLE_INT) { + return false; + } + + // C99 guarantees existence of the int_least_N_t types, even on + // machines that don't support arithmetic on width N: + if (x != (int_least64_t) x) { + return false; + } + + return true; +} + // Adapted from CERT C coding standards static inline intmax_t r__intmax_add(intmax_t x, intmax_t y) { diff --git a/src/rlang/decl/env-decl.h b/src/rlang/decl/env-decl.h index 839300196..f3d1bcabc 100644 --- a/src/rlang/decl/env-decl.h +++ b/src/rlang/decl/env-decl.h @@ -2,6 +2,7 @@ r_obj* eval_with_x(r_obj* call, r_obj* x); r_obj* eval_with_xy(r_obj* call, r_obj* x, r_obj* y); r_obj* eval_with_xyz(r_obj* call, r_obj* x, r_obj* y, r_obj* z); +#if R_VERSION < R_Version(4, 1, 0) static r_obj* new_env_call; @@ -10,6 +11,7 @@ r_obj* new_env__parent_node; static r_obj* new_env__size_node; +#endif static r_obj* exists_call; diff --git a/src/rlang/env.c b/src/rlang/env.c index 00d5f7208..c37040c51 100644 --- a/src/rlang/env.c +++ b/src/rlang/env.c @@ -41,6 +41,7 @@ r_obj* rlang_ns_get(const char* name) { r_obj* r_alloc_environment(r_ssize size, r_obj* parent) { +#if R_VERSION < R_Version(4, 1, 0) parent = parent ? parent : r_envs.empty; r_node_poke_car(new_env__parent_node, parent); @@ -53,6 +54,10 @@ r_obj* r_alloc_environment(r_ssize size, r_obj* parent) { r_node_poke_car(new_env__parent_node, r_null); return env; +#else + const int hash = 1; + return R_NewEnv(parent, hash, size); +#endif } @@ -287,11 +292,13 @@ void r_init_rlang_ns_env(void) { } void r_init_library_env(void) { +#if R_VERSION < R_Version(4, 1, 0) new_env_call = r_parse_eval("as.call(list(new.env, TRUE, NULL, NULL))", r_envs.base); r_preserve(new_env_call); new_env__parent_node = r_node_cddr(new_env_call); new_env__size_node = r_node_cdr(new_env__parent_node); +#endif env2list_call = r_parse("as.list.environment(x, all.names = TRUE)"); r_preserve(env2list_call); @@ -316,6 +323,7 @@ void r_init_library_env(void) { r_obj* rlang_ns_env = NULL; r_obj* r_methods_ns_env = NULL; +#if R_VERSION < R_Version(4, 1, 0) static r_obj* new_env_call = NULL; @@ -324,6 +332,7 @@ r_obj* new_env__parent_node = NULL; static r_obj* new_env__size_node = NULL; +#endif static r_obj* exists_call = NULL; diff --git a/src/rlang/env.h b/src/rlang/env.h index a2758d3cc..49fc76fa0 100644 --- a/src/rlang/env.h +++ b/src/rlang/env.h @@ -81,6 +81,15 @@ r_obj* r_base_ns_get(const char* name); r_obj* r_alloc_environment(r_ssize size, r_obj* parent); +static inline +r_obj* r_alloc_empty_environment(r_obj* parent) { + // Non-hashed environment. + // Very fast and useful when you aren't getting/setting from the result. + r_obj* env = Rf_allocSExp(R_TYPE_environment); + r_env_poke_parent(env, parent); + return env; +} + r_obj* r_env_as_list(r_obj* x); r_obj* r_list_as_environment(r_obj* x, r_obj* parent); r_obj* r_env_clone(r_obj* env, r_obj* parent); diff --git a/src/rlang/globals.c b/src/rlang/globals.c index 123ed720a..2472a8053 100644 --- a/src/rlang/globals.c +++ b/src/rlang/globals.c @@ -58,6 +58,7 @@ void r_init_library_globals(r_obj* ns) { void r_init_library_globals_syms(void) { r_syms.abort = r_sym("abort"); r_syms.arg = r_sym("arg"); + r_syms.brace = R_BraceSymbol; r_syms.brackets = R_BracketSymbol; r_syms.brackets2 = R_Bracket2Symbol; r_syms.call = r_sym("call"); @@ -88,9 +89,11 @@ void r_init_library_globals_syms(void) { r_syms.dot_x = r_sym(".x"); r_syms.dot_y = r_sym(".y"); r_syms.function = r_sym("function"); + r_syms.srcfile = r_sym("srcfile"); r_syms.srcref = r_sym("srcref"); r_syms.tilde = r_sym("~"); r_syms.w = r_sym("w"); + r_syms.wholeSrcref = r_sym("wholeSrcref"); r_syms.x = r_sym("x"); r_syms.y = r_sym("y"); r_syms.z = r_sym("z"); diff --git a/src/rlang/globals.h b/src/rlang/globals.h index 89faf36dc..fa9e379f5 100644 --- a/src/rlang/globals.h +++ b/src/rlang/globals.h @@ -42,6 +42,7 @@ struct r_globals_strs { struct r_globals_syms { r_obj* abort; r_obj* arg; + r_obj* brace; r_obj* brackets; r_obj* brackets2; r_obj* call; @@ -67,6 +68,7 @@ struct r_globals_syms { r_obj* options; r_obj* colon2; r_obj* colon3; + r_obj* srcfile; r_obj* srcref; r_obj* dim; r_obj* dim_names; @@ -76,6 +78,7 @@ struct r_globals_syms { r_obj* unbound; r_obj* w; r_obj* warning; + r_obj* wholeSrcref; r_obj* x; r_obj* y; r_obj* z; diff --git a/src/rlang/node.c b/src/rlang/node.c index b08265875..c733b67ef 100644 --- a/src/rlang/node.c +++ b/src/rlang/node.c @@ -28,10 +28,11 @@ r_obj* r_new_pairlist(const struct r_pair* args, } -// Shallow copy of a node tree +// Shallow copy of a node tree. Other objects are not cloned. r_obj* r_node_tree_clone(r_obj* x) { - if (r_typeof(x) != R_TYPE_pairlist) { - r_abort("Internal error: Expected node tree for shallow copy"); + enum r_type type = r_typeof(x); + if (type != R_TYPE_pairlist && type != R_TYPE_call) { + return x; } x = KEEP(r_clone(x)); @@ -39,7 +40,9 @@ r_obj* r_node_tree_clone(r_obj* x) { r_obj* rest = x; while (rest != r_null) { r_obj* head = r_node_car(rest); - if (r_typeof(head) == R_TYPE_pairlist) { + enum r_type head_type = r_typeof(head); + + if (head_type == R_TYPE_pairlist || head_type == R_TYPE_call) { r_node_poke_car(rest, r_node_tree_clone(head)); } rest = r_node_cdr(rest); diff --git a/src/rlang/rlang.c b/src/rlang/rlang.c index 9fcc9db62..935cd9ef3 100644 --- a/src/rlang/rlang.c +++ b/src/rlang/rlang.c @@ -40,10 +40,16 @@ r_ssize r_arg_as_ssize(r_obj* n, const char* arg) { if (r_length(n) != 1) { goto invalid; } + double out = r_dbl_get(n, 0); + if (out > R_SSIZE_MAX) { r_abort("`%s` is too large a number.", arg); } + if (out != (int_least64_t) out) { + r_abort("`%s` must be a whole number, not a decimal number.", arg); + } + return (r_ssize) floor(out); } diff --git a/src/rlang/rlang.hpp b/src/rlang/rlang.hpp index 97b88fac0..5ad5f1bf5 100644 --- a/src/rlang/rlang.hpp +++ b/src/rlang/rlang.hpp @@ -3,6 +3,9 @@ #include +#define R_NO_REMAP +#include + extern "C" { #include } diff --git a/src/rlang/vec-lgl.c b/src/rlang/vec-lgl.c index 2adb34816..346c91ab2 100644 --- a/src/rlang/vec-lgl.c +++ b/src/rlang/vec-lgl.c @@ -1,24 +1,25 @@ #include "rlang.h" +#include r_ssize r_lgl_sum(r_obj* x, bool na_true) { if (r_typeof(x) != R_TYPE_logical) { r_abort("Internal error: Excepted logical vector in `r_lgl_sum()`"); } - r_ssize n = r_length(x); + const r_ssize n = r_length(x); + const int* v_x = r_lgl_cbegin(x); + // This can't overflow since `sum` is necessarily smaller or equal + // to the vector length expressed in `r_ssize` r_ssize sum = 0; - const int* p_x = r_lgl_cbegin(x); - for (r_ssize i = 0; i < n; ++i) { - // This can't overflow since `sum` is necessarily smaller or equal - // to the vector length expressed in `r_ssize`. - int x_i = p_x[i]; - - if (na_true && x_i) { - sum += 1; - } else if (x_i == 1) { - sum += 1; + if (na_true) { + for (r_ssize i = 0; i < n; ++i) { + sum += (bool) v_x[i]; + } + } else { + for (r_ssize i = 0; i < n; ++i) { + sum += (v_x[i] == 1); } } @@ -35,60 +36,71 @@ r_obj* r_lgl_which(r_obj* x, bool na_propagate) { const r_ssize n = r_length(x); const int* v_x = r_lgl_cbegin(x); - r_obj* names = r_names(x); - const bool has_names = names != r_null; - r_obj* const* v_names = NULL; - if (has_names) { - v_names = r_chr_cbegin(names); - } - - const r_ssize which_n = r_lgl_sum(x, na_propagate); + const r_ssize out_n = r_lgl_sum(x, na_propagate); - if (which_n > INT_MAX) { + if (out_n > INT_MAX) { r_stop_internal("Can't fit result in an integer vector."); } - r_obj* which = KEEP(r_alloc_integer(which_n)); - int* v_which = r_int_begin(which); - - r_obj* which_names = r_null; - if (has_names) { - which_names = r_alloc_character(which_n); - r_attrib_poke_names(which, which_names); - } + r_obj* out = KEEP(r_alloc_integer(out_n)); + int* v_out = r_int_begin(out); - r_ssize j = 0; + r_obj* names = r_names(x); + const bool has_names = (names != r_null); if (na_propagate) { - for (r_ssize i = 0; i < n; ++i) { - const int elt = v_x[i]; - - if (elt != 0) { - v_which[j] = (elt == r_globals.na_lgl) ? r_globals.na_int : i + 1; - - if (has_names) { - r_chr_poke(which_names, j, v_names[i]); - } - - ++j; + if (has_names) { + // Mark `NA` locations with negative location for extracting names later + for (r_ssize i = 0, j = 0; i < n && j < out_n; ++i) { + const int x_elt = v_x[i]; + const bool missing = x_elt == r_globals.na_lgl; + const int elt = missing * (-i - 1) + !missing * x_elt * (i + 1); + v_out[j] = elt; + j += (bool) elt; + } + } else { + for (r_ssize i = 0, j = 0; i < n && j < out_n; ++i) { + const int x_elt = v_x[i]; + const bool missing = x_elt == r_globals.na_lgl; + const int elt = missing * r_globals.na_int + !missing * x_elt * (i + 1); + v_out[j] = elt; + j += (bool) elt; } } } else { - for (r_ssize i = 0; i < n; ++i) { - const int elt = v_x[i]; - - if (elt == 1) { - v_which[j] = i + 1; - - if (has_names) { - r_chr_poke(which_names, j, v_names[i]); - } + for (r_ssize i = 0, j = 0; i < n && j < out_n; ++i) { + const int x_elt = v_x[i]; + v_out[j] = i + 1; + j += (x_elt == 1); + } + } - ++j; + if (has_names) { + r_obj* const* v_names = r_chr_cbegin(names); + + r_obj* out_names = r_alloc_character(out_n); + r_attrib_poke_names(out, out_names); + + if (na_propagate) { + // `v_out` contains negative locations which tells you the location of the + // name to extract while also serving as a signal of where `NA`s should go + // in the finalized output + for (r_ssize i = 0; i < out_n; ++i) { + const int loc = v_out[i]; + const int abs_loc = abs(loc); + const bool same = (loc == abs_loc); + v_out[i] = same * loc + !same * r_globals.na_int; + r_chr_poke(out_names, i, v_names[abs_loc - 1]); + } + } else { + // `v_out` doesn't contain `NA`, so we can use the locations directly + for (r_ssize i = 0; i < out_n; ++i) { + const int loc = v_out[i] - 1; + r_chr_poke(out_names, i, v_names[loc]); } } } FREE(1); - return which; + return out; } diff --git a/src/rlang/vec.h b/src/rlang/vec.h index 33392dff9..46db7b02a 100644 --- a/src/rlang/vec.h +++ b/src/rlang/vec.h @@ -363,7 +363,7 @@ int r_as_int(r_obj* x) { static inline double r_arg_as_double(r_obj* x, const char* arg) { // TODO: Coercion of int and lgl values - if (!_r_is_double(x, 1, 1)) { + if (!_r_is_double(x, 1, -1)) { r_abort("`%s` must be a single double value.", arg); } return r_dbl_get(x, 0); diff --git a/src/slice-chop.c b/src/slice-chop.c index a48a7eab7..1def91a81 100644 --- a/src/slice-chop.c +++ b/src/slice-chop.c @@ -406,7 +406,7 @@ r_obj* chop_fallback(r_obj* x, struct vctrs_chop_indices* p_indices) { // definition to ensure consistent look-up. This is the same logic // as in `vctrs_dispatch_n()`, reimplemented here to allow repeated // evaluations in a loop. - r_obj* env = KEEP(r_new_environment(r_envs.global)); + r_obj* env = KEEP(r_alloc_empty_environment(r_envs.global)); r_env_poke(env, syms_x, x); // Construct call with symbols, not values, for performance. diff --git a/src/type-info.c b/src/type-info.c index 592369ae5..492216339 100644 --- a/src/type-info.c +++ b/src/type-info.c @@ -135,7 +135,20 @@ bool list_all_vectors(r_obj* x) { if (r_typeof(x) != R_TYPE_list) { r_stop_unexpected_type(r_typeof(x)); } - return r_list_all_of(x, &obj_is_vector); + + // TODO: Use `r_list_all_of(x, &obj_is_vector)` when we add it back in + const r_ssize size = r_length(x); + r_obj* const* v_x = r_list_cbegin(x); + + for (r_ssize i = 0; i < size; ++i) { + r_obj* elt = v_x[i]; + + if (!obj_is_vector(elt)) { + return false; + } + } + + return true; } diff --git a/src/utils.c b/src/utils.c index 3ba8823a9..fd4a8c0d4 100644 --- a/src/utils.c +++ b/src/utils.c @@ -205,7 +205,7 @@ SEXP vctrs_dispatch6(SEXP fn_sym, SEXP fn, } static SEXP vctrs_eval_mask_n_impl(SEXP fn_sym, SEXP fn, SEXP* syms, SEXP* args, SEXP env) { - SEXP mask = PROTECT(r_new_environment(env)); + SEXP mask = PROTECT(r_alloc_empty_environment(env)); if (fn_sym != R_NilValue) { Rf_defineVar(fn_sym, fn, mask); @@ -1179,23 +1179,6 @@ static SEXP new_env_call = NULL; static SEXP new_env__parent_node = NULL; static SEXP new_env__size_node = NULL; -#if 0 -SEXP r_new_environment(SEXP parent, R_len_t size) { - parent = parent ? parent : R_EmptyEnv; - SETCAR(new_env__parent_node, parent); - - size = size ? size : 29; - SETCAR(new_env__size_node, Rf_ScalarInteger(size)); - - SEXP env = Rf_eval(new_env_call, R_BaseEnv); - - // Free for gc - SETCAR(new_env__parent_node, R_NilValue); - - return env; -} -#endif - // [[ include("utils.h") ]] SEXP r_protect(SEXP x) { return Rf_lang2(fns_quote, x); diff --git a/src/utils.h b/src/utils.h index 3cdb1dc6b..6988ef5ce 100644 --- a/src/utils.h +++ b/src/utils.h @@ -256,13 +256,6 @@ SEXP r_new_list(R_len_t n) { return Rf_allocVector(VECSXP, n); } -static inline -SEXP r_new_environment(SEXP parent) { - SEXP env = Rf_allocSExp(ENVSXP); - SET_ENCLOS(env, parent); - return env; -} - SEXP r_protect(SEXP x); bool r_is_number(SEXP x); bool r_is_positive_number(SEXP x); diff --git a/tests/testthat/_snaps/assert.md b/tests/testthat/_snaps/assert.md index 7208e13f3..68817682a 100644 --- a/tests/testthat/_snaps/assert.md +++ b/tests/testthat/_snaps/assert.md @@ -280,10 +280,9 @@ Code vec_check_size(1, size = 1.5) - abort("`vec_check_size()` should error for us") Condition - Error: - ! `vec_check_size()` should error for us + Error in `vec_check_size()`: + ! `size` must be a whole number, not a decimal number. # list_all_vectors() works diff --git a/tests/testthat/test-assert.R b/tests/testthat/test-assert.R index 4443b7387..ed4dab876 100644 --- a/tests/testthat/test-assert.R +++ b/tests/testthat/test-assert.R @@ -314,12 +314,8 @@ test_that("vec_check_size() validates `size`", { expect_snapshot(error = TRUE, { vec_check_size(1, size = c(1L, 2L)) }) - - # TODO: This should be an error, and we want to know when it changes - # https://github.com/r-lib/rlang/issues/1562 expect_snapshot(error = TRUE, { vec_check_size(1, size = 1.5) - abort("`vec_check_size()` should error for us") }) }) From 42def44ff078d157867949da75a1ba1358fea957 Mon Sep 17 00:00:00 2001 From: DavisVaughan Date: Wed, 15 Mar 2023 08:39:54 -0400 Subject: [PATCH 262/312] Remove rlang Remote --- DESCRIPTION | 4 +--- 1 file changed, 1 insertion(+), 3 deletions(-) diff --git a/DESCRIPTION b/DESCRIPTION index 4f29e93af..0e71448ab 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -32,7 +32,7 @@ Imports: cli (>= 3.4.0), glue, lifecycle (>= 1.0.3), - rlang (>= 1.0.6.9000) + rlang (>= 1.1.0) Suggests: bit64, covr, @@ -57,5 +57,3 @@ Roxygen: list(markdown = TRUE) RoxygenNote: 7.2.3 Config/testthat/edition: 3 Config/Needs/website: tidyverse/tidytemplate -Remotes: - r-lib/rlang From 84438d8f5f6be2532652fa3cd3c2e9ff94f8cf23 Mon Sep 17 00:00:00 2001 From: DavisVaughan Date: Wed, 15 Mar 2023 08:41:49 -0400 Subject: [PATCH 263/312] Update rendered docs with CRAN tibble's error calls --- man/faq-error-scalar-type.Rd | 4 ++-- man/vector_recycling_rules.Rd | 2 +- 2 files changed, 3 insertions(+), 3 deletions(-) diff --git a/man/faq-error-scalar-type.Rd b/man/faq-error-scalar-type.Rd index a6dd0b4b1..0ec78d028 100644 --- a/man/faq-error-scalar-type.Rd +++ b/man/faq-error-scalar-type.Rd @@ -10,13 +10,13 @@ a scalar object as column in a data frame: \if{html}{\out{
}}\preformatted{fn <- function() NULL tibble::tibble(x = fn) -#> Error: +#> Error in `tibble::tibble()`: #> ! All columns in a tibble must be vectors. #> x Column `x` is a function. fit <- lm(1:3 ~ 1) tibble::tibble(x = fit) -#> Error: +#> Error in `tibble::tibble()`: #> ! All columns in a tibble must be vectors. #> x Column `x` is a `lm` object. }\if{html}{\out{
}} diff --git a/man/vector_recycling_rules.Rd b/man/vector_recycling_rules.Rd index 5abb2944a..269c89d84 100644 --- a/man/vector_recycling_rules.Rd +++ b/man/vector_recycling_rules.Rd @@ -37,7 +37,7 @@ If vectors aren't size 1, they must all be the same size. Otherwise, an error is thrown: \if{html}{\out{
}}\preformatted{tibble(x = 1:3, y = 4:7) -#> Error: +#> Error in `tibble()`: #> ! Tibble columns must have compatible sizes. #> * Size 3: Existing data. #> * Size 4: Column `y`. From f15891754408720f808ea1472871741d2b5f3941 Mon Sep 17 00:00:00 2001 From: DavisVaughan Date: Wed, 15 Mar 2023 10:21:37 -0400 Subject: [PATCH 264/312] Update revdep results (all false alarms) --- revdep/README.md | 438 +- revdep/cran.md | 327 +- revdep/failures.md | 14223 ++++++++++++++++++++++++++++++++++--------- revdep/problems.md | 206 +- 4 files changed, 11939 insertions(+), 3255 deletions(-) diff --git a/revdep/README.md b/revdep/README.md index f0ac49b78..c1629dace 100644 --- a/revdep/README.md +++ b/revdep/README.md @@ -1,166 +1,286 @@ # Revdeps -## Failed to check (149) +## Failed to check (271) -|package |version |error |warning |note | -|:---------------------|:-------|:-----|:-------|:----| -|accept |? | | | | -|ADAM |? | | | | -|admiraldev |? | | | | -|afex |? | | | | -|AGread |? | | | | -|ags |? | | | | -|AMARETTO |? | | | | -|amplican |? | | | | -|arulesViz |1.5-1 |1 | | | -|autoTS |? | | | | -|azuremlsdk |1.10.0 |1 | | | -|bayesian |0.0.9 |1 | |1 | -|bayesmodels |? | | | | -|bayesnec |2.1.0.2 |1 | |1 | -|bayesplot |? | | | | -|BayesPostEst |? | | | | -|bayesrules |? | | | | -|beadplexr |? | | | | -|BiplotML |1.1.0 |1 | | | -|blocs |? | | | | -|breathtestcore |? | | | | -|brendaDb |? | | | | -|broom.helpers |? | | | | -|broom.mixed |? | | | | -|BUSpaRse |? | | | | -|cattonum |? | | | | -|ceRNAnetsim |? | | | | -|ChineseNames |? | | | | -|cinaR |? | | | | -|clustermole |? | | | | -|cmstatr |0.9.1 |1 | | | -|COMPASS |? | | | | -|conflicted |1.2.0 |1 | | | -|cort |? | | | | -|covidmx |? | | | | -|CRE |? | | | | -|ctDNAtools |? | | | | -|CytoML |? | | | | -|D2MCS |? | | | | -|datawizard |? | | | | -|DeLorean |? | | | | -|DepecheR |? | | | | -|destiny |? | | | | -|DiffBind |? | | | | -|diffman |? | | | | -|diffrprojects |? | | | | -|dynfrail |? | | | | -|embed |? | | | | -|EpiForsk |? | | | | -|epiphy |? | | | | -|epitopeR |? | | | | -|escalation |? | | | | -|EScvtmle |? | | | | -|ESTER |0.2.0 |1 | | | -|evaluator |? | | | | -|expstudies |? | | | | -|fable.prophet |? | | | | -|FAMetA |0.1.5 |1 | | | -|finnts |? | | | | -|fipe |? | | | | -|foieGras |? | | | | -|forceR |? | | | | -|FSelectorRcpp |? | | | | -|genekitr |? | | | | -|geocmeans |? | | | | -|ggPMX |? | | | | -|ggstatsplot |? | | | | -|healthyR.ai |? | | | | -|healthyR.ts |? | | | | -|healthyverse |? | | | | -|historicalborrowlong |? | | | | -|immcp |? | | | | -|ImputeRobust |? | | | | -|INSPECTumours |0.1.0 |1 | | | -|intRinsic |? | | | | -|IPDFileCheck |0.7.5 |1 | | | -|IRexamples |? | | | | -|irtQ |? | | | | -|IsoCorrectoR |? | | | | -|journalabbr |? | | | | -|l1spectral |0.99.6 |1 | | | -|lifeR |? | | | | -|loon.ggplot |? | | | | -|loon.shiny |? | | | | -|MACP |? | | | | -|mafs |? | | | | -|MantaID |? | | | | -|marginaleffects |? | | | | -|MazamaCoreUtils |0.4.13 |1 | | | -|mbRes |? | | | | -|merTools |? | | | | -|microservices |? | | | | -|modeltime |? | | | | -|modeltime.ensemble |? | | | | -|modeltime.gluonts |? | | | | -|modeltime.h2o |? | | | | -|modeltime.resample |? | | | | -|moexer |? | | | | -|mpower |? | | | | -|multibiasmeta |? | | | | -|NetFACS |0.5.0 |1 | | | -|nlmixr2extra |? | | | | -|nlmixr2plot |? | | | | -|nlmixr2rpt |? | | | | -|numbat |? | | | | -|OBL |? | | | | -|OlinkAnalyze |? | | | | -|OncoBayes2 |0.8-8 |1 | | | -|openai |? | | | | -|OutliersO3 |0.6.3 |1 | | | -|pathwayTMB |? | | | | -|peramo |? | | | | -|performanceEstimation |? | | | | -|planningML |1.0.0 |1 | | | -|Platypus |? | | | | -|PLSiMCpp |? | | | | -|promotionImpact |? | | | | -|prqlr |? | | | | -|PsychWordVec |? | | | | -|RBesT |? | | | | -|rcssci |? | | | | -|rdss |? | | | | -|report |? | | | | -|RevGadgets |? | | | | -|Rigma |0.2.1 |1 | | | -|Robyn |? | | | | -|RVA |? | | | | -|SAMtool |? | | | | -|scGate |? | | | | -|SCpubr |? | | | | -|shinyHugePlot |? | | | | -|sjPlot |? | | | | -|sknifedatar |? | | | | -|SpaDES.tools |? | | | | -|statsExpressions |? | | | | -|stortingscrape |? | | | | -|tame |? | | | | -|tidybayes |? | | | | -|tidyposterior |? | | | | -|tidySEM |? | | | | -|tidytags |? | | | | -|timetk |? | | | | -|tinyarray |? | | | | -|tipmap |? | | | | -|vivid |? | | | | -|wearables |0.8.1 |1 | | | -|webSDM |? | | | | -|wrappedtools |? | | | | -|xpose.nlmixr2 |? | | | | +|package |version |error |warning |note | +|:--------------------|:-------|:-----|:-------|:----| +|abmR |? | | | | +|abstr |? | | | | +|accept |? | | | | +|ADAM |? | | | | +|afex |? | | | | +|AGread |? | | | | +|agridat |? | | | | +|ags |? | | | | +|AMARETTO |? | | | | +|amplican |? | | | | +|autoTS |? | | | | +|bangladesh |? | | | | +|bayesian |? | | | | +|bayesmodels |? | | | | +|bayesnec |? | | | | +|bayesplot |? | | | | +|BayesPostEst |? | | | | +|bayesrules |? | | | | +|bdl |? | | | | +|beadplexr |? | | | | +|BiodiversityR |? | | | | +|blocs |? | | | | +|breathtestcore |? | | | | +|brendaDb |? | | | | +|broom.helpers |? | | | | +|broom.mixed |? | | | | +|BUSpaRse |? | | | | +|cancensus |? | | | | +|cattonum |? | | | | +|CCAMLRGIS |? | | | | +|ceRNAnetsim |? | | | | +|ChineseNames |? | | | | +|choroplethr |3.7.1 |1 | | | +|cinaR |? | | | | +|COMPASS |? | | | | +|CoordinateCleaner |2.0-20 |1 | | | +|CopernicusMarine |? | | | | +|cort |? | | | | +|covidmx |? | | | | +|CRE |? | | | | +|ctDNAtools |? | | | | +|cubble |? | | | | +|cxr |? | | | | +|cyclestreets |? | | | | +|CytoML |? | | | | +|D2MCS |? | | | | +|datawizard |? | | | | +|dbmss |? | | | | +|DeLorean |? | | | | +|DepecheR |? | | | | +|destiny |? | | | | +|DiffBind |? | | | | +|diffman |? | | | | +|diffrprojects |? | | | | +|dycdtools |? | | | | +|dynamicSDM |? | | | | +|dynfrail |? | | | | +|edbuildmapr |? | | | | +|EFDR |? | | | | +|embed |? | | | | +|EnvExpInd |? | | | | +|EpiForsk |? | | | | +|epiphy |? | | | | +|epitopeR |? | | | | +|escalation |? | | | | +|EScvtmle |? | | | | +|eSDM |? | | | | +|ESTER |? | | | | +|evaluator |? | | | | +|expstudies |? | | | | +|fable.prophet |? | | | | +|FAMetA |0.1.5 |1 | | | +|fgdr |? | | | | +|finnts |? | | | | +|fipe |? | | | | +|foieGras |? | | | | +|forceR |? | | | | +|FORTLS |? | | | | +|FRK |? | | | | +|fsr |? | | | | +|genekitr |? | | | | +|geocmeans |? | | | | +|GeodesiCL |1.0.0 |1 | | | +|ggchangepoint |? | | | | +|ggOceanMaps |? | | | | +|ggPMX |? | | | | +|ggseqplot |? | | | | +|ggspatial |? | | | | +|ggstatsplot |? | | | | +|glottospace |? | | | | +|GPSeqClus |? | | | | +|GREENeR |? | | | | +|gtfs2gps |? | | | | +|gumboot |? | | | | +|gwavr |? | | | | +|GWPR.light |? | | | | +|happign |? | | | | +|healthyR.ai |? | | | | +|healthyR.ts |? | | | | +|healthyverse |? | | | | +|himach |? | | | | +|historicalborrowlong |? | | | | +|HYPEtools |? | | | | +|hypsoLoop |? | | | | +|immcp |? | | | | +|ImputeRobust |? | | | | +|incidence2 |1.2.3 |1 | | | +|INSPECTumours |? | | | | +|intRinsic |? | | | | +|intSDM |1.0.5 |1 | |1 | +|IRexamples |? | | | | +|irtQ |? | | | | +|IsoCorrectoR |? | | | | +|itsdm |? | | | | +|journalabbr |? | | | | +|jpgrid |? | | | | +|jpmesh |? | | | | +|lifeR |? | | | | +|loon.ggplot |? | | | | +|loon.shiny |? | | | | +|MACP |? | | | | +|mafs |? | | | | +|MainExistingDatasets |? | | | | +|MantaID |? | | | | +|manydata |0.8.2 |1 | | | +|mapboxapi |? | | | | +|mapme.biodiversity |? | | | | +|mapping |? | | | | +|mapsapi |? | | | | +|mapscanner |? | | | | +|marginaleffects |? | | | | +|MarketMatching |? | | | | +|MazamaSpatialPlots |? | | | | +|mbRes |? | | | | +|merTools |? | | | | +|meteoland |? | | | | +|microservices |? | | | | +|modeltime |? | | | | +|modeltime.ensemble |? | | | | +|modeltime.gluonts |? | | | | +|modeltime.h2o |? | | | | +|modeltime.resample |? | | | | +|moexer |? | | | | +|motif |? | | | | +|mpower |? | | | | +|MSclassifR |? | | | | +|multibiasmeta |? | | | | +|naturaList |? | | | | +|ncdfgeom |? | | | | +|nhdplusTools |? | | | | +|nhdR |? | | | | +|nlmixr2extra |? | | | | +|nlmixr2plot |? | | | | +|nlmixr2rpt |? | | | | +|numbat |? | | | | +|OBL |? | | | | +|occCite |? | | | | +|occUncertain |0.1.0 |1 | | | +|oceanexplorer |? | | | | +|oceanis |? | | | | +|ohsome |? | | | | +|OlinkAnalyze |? | | | | +|OpenLand |? | | | | +|palaeoSig |? | | | | +|panelr |? | | | | +|pathwayTMB |? | | | | +|pct |? | | | | +|peramo |? | | | | +|photosynthesis |? | | | | +|Platypus |? | | | | +|PLSiMCpp |? | | | | +|PoolTestR |? | | | | +|PopGenHelpR |? | | | | +|ppcSpatial |? | | | | +|prioriactions |? | | | | +|promotionImpact |? | | | | +|prqlr |? | | | | +|PSS.Health |0.6.1 |1 | | | +|PsychWordVec |? | | | | +|rangeModelMetadata |? | | | | +|rbenvo |? | | | | +|RBesT |? | | | | +|rcontroll |? | | | | +|rcssci |? | | | | +|RCzechia |? | | | | +|rdss |? | | | | +|redist |? | | | | +|remap |? | | | | +|report |? | | | | +|RevGadgets |? | | | | +|rGhanaCensus |? | | | | +|rnaturalearth |? | | | | +|roads |? | | | | +|Robyn |? | | | | +|Rsagacmd |? | | | | +|rsinaica |? | | | | +|rstac |? | | | | +|RVA |? | | | | +|saeSim |0.11.0 |1 | | | +|SAMtool |? | | | | +|sandwichr |? | | | | +|scGate |? | | | | +|SCpubr |? | | | | +|SDGdetector |2.7.1 |1 | | | +|SDLfilter |? | | | | +|sdmApp |? | | | | +|sf |? | | | | +|sfdep |? | | | | +|sfnetworks |? | | | | +|sftime |? | | | | +|ShellChron |? | | | | +|shinyHugePlot |? | | | | +|simodels |? | | | | +|simplevis |? | | | | +|sits |? | | | | +|sjPlot |? | | | | +|sjstats |? | | | | +|sknifedatar |? | | | | +|slendr |? | | | | +|sociome |2.1.0 |1 | |1 | +|SpaDES.tools |? | | | | +|SPARTAAS |1.1.0 |1 | | | +|spatgeom |? | | | | +|SpatialEpi |1.2.8 |1 | | | +|SpatialKDE |? | | | | +|spatialrisk |? | | | | +|spatialsample |? | | | | +|spDates |? | | | | +|spectacles |0.5-3 |1 | | | +|spnaf |? | | | | +|spNetwork |? | | | | +|spqdep |? | | | | +|spup |? | | | | +|stars |? | | | | +|starsTileServer |? | | | | +|stats19 |? | | | | +|statsExpressions |? | | | | +|stortingscrape |? | | | | +|stplanr |? | | | | +|stppSim |? | | | | +|stxplore |? | | | | +|SUNGEO |? | | | | +|swfscAirDAS |0.2.3 |1 | | | +|SWTools |? | | | | +|tame |? | | | | +|telemac |? | | | | +|tidybayes |? | | | | +|tidyposterior |? | | | | +|tidySEM |? | | | | +|tidytags |? | | | | +|tilemaps |? | | | | +|timetk |? | | | | +|tinyarray |? | | | | +|tipmap |? | | | | +|tmap |? | | | | +|trackdf |? | | | | +|trending |? | | | | +|TUFLOWR |? | | | | +|VancouvR |? | | | | +|vivid |? | | | | +|wallace |? | | | | +|waterquality |? | | | | +|Wats |? | | | | +|waves |0.2.4 |1 | | | +|wdpar |? | | | | +|wearables |0.8.1 |1 | | | +|webSDM |? | | | | +|wrappedtools |? | | | | +|xpose.nlmixr2 |? | | | | +|zipcodeR |0.3.5 |1 | | | +|zonebuilder |? | | | | -## New problems (5) +## New problems (3) -|package |version |error |warning |note | -|:--------------|:-------|:------|:-------|:----| -|[dplyr](problems.md#dplyr)|1.1.0 |__+1__ | |1 | -|[GenomeAdmixR](problems.md#genomeadmixr)|2.1.7 |__+1__ | |2 | -|[photosynthesis](problems.md#photosynthesis)|2.1.1 |__+1__ | |2 | +|package |version |error |warning |note | +|:---------|:-------|:------|:-------|:----| +|[openalexR](problems.md#openalexr)|1.0.0 | |__+1__ | | |[portalr](problems.md#portalr)|0.3.11 |__+1__ | | | -|[rlang](problems.md#rlang)|1.0.6 |__+1__ | |1 | +|[rapbase](problems.md#rapbase)|1.24.0 |__+1__ | | | diff --git a/revdep/cran.md b/revdep/cran.md index a40b46321..701585682 100644 --- a/revdep/cran.md +++ b/revdep/cran.md @@ -1,123 +1,238 @@ ## revdepcheck results -We checked 4238 reverse dependencies (4183 from CRAN + 55 from Bioconductor), comparing R CMD check results across CRAN and dev versions of this package. +We checked 4257 reverse dependencies (4201 from CRAN + 56 from Bioconductor), comparing R CMD check results across CRAN and dev versions of this package. - * We saw 5 new problems - * We failed to check 94 packages + * We saw 3 new problems + * We failed to check 215 packages Issues with CRAN packages are summarised below. ### New problems (This reports the first line of each new failure) -* dplyr - checking tests ... ERROR - -* GenomeAdmixR - checking tests ... ERROR - -* photosynthesis - checking tests ... ERROR +* openalexR + checking re-building of vignette outputs ... WARNING * portalr checking tests ... ERROR -* rlang +* rapbase checking tests ... ERROR ### Failed to check -* accept (NA) -* admiraldev (NA) -* afex (NA) -* arulesViz (NA) -* autoTS (NA) -* azuremlsdk (NA) -* bayesian (NA) -* bayesnec (NA) -* bayesplot (NA) -* BayesPostEst (NA) -* bayesrules (NA) -* beadplexr (NA) -* BiplotML (NA) -* blocs (NA) -* breathtestcore (NA) -* broom.helpers (NA) -* broom.mixed (NA) -* ChineseNames (NA) -* cinaR (NA) -* clustermole (NA) -* cmstatr (NA) -* conflicted (NA) -* CRE (NA) -* datawizard (NA) -* embed (NA) -* escalation (NA) -* ESTER (NA) -* fable.prophet (NA) -* FAMetA (NA) -* finnts (NA) -* FSelectorRcpp (NA) -* genekitr (NA) -* geocmeans (NA) -* ggPMX (NA) -* ggstatsplot (NA) -* healthyR.ai (NA) -* healthyR.ts (NA) -* healthyverse (NA) -* historicalborrowlong (NA) -* immcp (NA) -* ImputeRobust (NA) -* INSPECTumours (NA) -* IPDFileCheck (NA) -* IRexamples (NA) -* l1spectral (NA) -* loon.ggplot (NA) -* loon.shiny (NA) -* MACP (NA) -* marginaleffects (NA) -* MazamaCoreUtils (NA) -* merTools (NA) -* modeltime (NA) -* modeltime.ensemble (NA) -* modeltime.gluonts (NA) -* modeltime.h2o (NA) -* modeltime.resample (NA) -* mpower (NA) -* multibiasmeta (NA) -* NetFACS (NA) -* nlmixr2extra (NA) -* nlmixr2plot (NA) -* nlmixr2rpt (NA) -* numbat (NA) -* OlinkAnalyze (NA) -* OncoBayes2 (NA) -* OutliersO3 (NA) -* pathwayTMB (NA) -* performanceEstimation (NA) -* planningML (NA) -* Platypus (NA) -* promotionImpact (NA) -* PsychWordVec (NA) -* RBesT (NA) -* rdss (NA) -* report (NA) -* Rigma (NA) -* Robyn (NA) -* RVA (NA) -* SAMtool (NA) -* SCpubr (NA) -* sjPlot (NA) -* sknifedatar (NA) -* SpaDES.tools (NA) -* statsExpressions (NA) -* tidybayes (NA) -* tidyposterior (NA) -* tidySEM (NA) -* timetk (NA) -* tinyarray (NA) -* tipmap (NA) -* vivid (NA) -* wearables (NA) -* webSDM (NA) -* xpose.nlmixr2 (NA) +* abmR (NA) +* abstr (NA) +* accept (NA) +* afex (NA) +* agridat (NA) +* autoTS (NA) +* bangladesh (NA) +* bayesian (NA) +* bayesnec (NA) +* bayesplot (NA) +* BayesPostEst (NA) +* bayesrules (NA) +* bdl (NA) +* beadplexr (NA) +* BiodiversityR (NA) +* blocs (NA) +* breathtestcore (NA) +* broom.helpers (NA) +* broom.mixed (NA) +* cancensus (NA) +* CCAMLRGIS (NA) +* ChineseNames (NA) +* choroplethr (NA) +* cinaR (NA) +* CoordinateCleaner (NA) +* CopernicusMarine (NA) +* CRE (NA) +* cubble (NA) +* cxr (NA) +* cyclestreets (NA) +* datawizard (NA) +* dbmss (NA) +* dycdtools (NA) +* dynamicSDM (NA) +* edbuildmapr (NA) +* EFDR (NA) +* embed (NA) +* EnvExpInd (NA) +* escalation (NA) +* eSDM (NA) +* ESTER (NA) +* fable.prophet (NA) +* FAMetA (NA) +* fgdr (NA) +* finnts (NA) +* FORTLS (NA) +* FRK (NA) +* fsr (NA) +* genekitr (NA) +* geocmeans (NA) +* GeodesiCL (NA) +* ggchangepoint (NA) +* ggOceanMaps (NA) +* ggPMX (NA) +* ggspatial (NA) +* ggstatsplot (NA) +* glottospace (NA) +* GPSeqClus (NA) +* GREENeR (NA) +* gtfs2gps (NA) +* gumboot (NA) +* gwavr (NA) +* GWPR.light (NA) +* happign (NA) +* healthyR.ai (NA) +* healthyR.ts (NA) +* healthyverse (NA) +* himach (NA) +* historicalborrowlong (NA) +* HYPEtools (NA) +* hypsoLoop (NA) +* immcp (NA) +* ImputeRobust (NA) +* incidence2 (NA) +* INSPECTumours (NA) +* intSDM (NA) +* IRexamples (NA) +* itsdm (NA) +* jpgrid (NA) +* jpmesh (NA) +* loon.ggplot (NA) +* loon.shiny (NA) +* MACP (NA) +* MainExistingDatasets (NA) +* manydata (NA) +* mapboxapi (NA) +* mapme.biodiversity (NA) +* mapping (NA) +* mapsapi (NA) +* mapscanner (NA) +* marginaleffects (NA) +* MarketMatching (NA) +* MazamaSpatialPlots (NA) +* merTools (NA) +* meteoland (NA) +* modeltime (NA) +* modeltime.ensemble (NA) +* modeltime.gluonts (NA) +* modeltime.h2o (NA) +* modeltime.resample (NA) +* motif (NA) +* mpower (NA) +* MSclassifR (NA) +* multibiasmeta (NA) +* naturaList (NA) +* ncdfgeom (NA) +* nhdplusTools (NA) +* nhdR (NA) +* nlmixr2extra (NA) +* nlmixr2plot (NA) +* nlmixr2rpt (NA) +* numbat (NA) +* occCite (NA) +* occUncertain (NA) +* oceanexplorer (NA) +* oceanis (NA) +* ohsome (NA) +* OlinkAnalyze (NA) +* OpenLand (NA) +* palaeoSig (NA) +* panelr (NA) +* pathwayTMB (NA) +* pct (NA) +* photosynthesis (NA) +* Platypus (NA) +* PoolTestR (NA) +* PopGenHelpR (NA) +* ppcSpatial (NA) +* prioriactions (NA) +* promotionImpact (NA) +* PSS.Health (NA) +* PsychWordVec (NA) +* rangeModelMetadata (NA) +* rbenvo (NA) +* RBesT (NA) +* rcontroll (NA) +* RCzechia (NA) +* rdss (NA) +* redist (NA) +* remap (NA) +* report (NA) +* rGhanaCensus (NA) +* rnaturalearth (NA) +* roads (NA) +* Robyn (NA) +* Rsagacmd (NA) +* rsinaica (NA) +* rstac (NA) +* RVA (NA) +* saeSim (NA) +* SAMtool (NA) +* sandwichr (NA) +* SCpubr (NA) +* SDGdetector (NA) +* SDLfilter (NA) +* sdmApp (NA) +* sf (NA) +* sfdep (NA) +* sfnetworks (NA) +* sftime (NA) +* ShellChron (NA) +* simodels (NA) +* simplevis (NA) +* sits (NA) +* sjPlot (NA) +* sjstats (NA) +* sknifedatar (NA) +* slendr (NA) +* sociome (NA) +* SpaDES.tools (NA) +* SPARTAAS (NA) +* spatgeom (NA) +* SpatialEpi (NA) +* SpatialKDE (NA) +* spatialrisk (NA) +* spatialsample (NA) +* spDates (NA) +* spectacles (NA) +* spnaf (NA) +* spNetwork (NA) +* spqdep (NA) +* spup (NA) +* stars (NA) +* starsTileServer (NA) +* stats19 (NA) +* statsExpressions (NA) +* stplanr (NA) +* stppSim (NA) +* stxplore (NA) +* SUNGEO (NA) +* swfscAirDAS (NA) +* SWTools (NA) +* telemac (NA) +* tidybayes (NA) +* tidyposterior (NA) +* tidySEM (NA) +* tilemaps (NA) +* timetk (NA) +* tinyarray (NA) +* tipmap (NA) +* tmap (NA) +* trackdf (NA) +* trending (NA) +* TUFLOWR (NA) +* VancouvR (NA) +* vivid (NA) +* wallace (NA) +* waterquality (NA) +* waves (NA) +* wdpar (NA) +* wearables (NA) +* webSDM (NA) +* xpose.nlmixr2 (NA) +* zipcodeR (NA) +* zonebuilder (NA) diff --git a/revdep/failures.md b/revdep/failures.md index 851519c93..61355b43c 100644 --- a/revdep/failures.md +++ b/revdep/failures.md @@ -1,3 +1,139 @@ +# abmR + +
+ +* Version: 1.0.8 +* GitHub: NA +* Source code: https://github.com/cran/abmR +* Date/Publication: 2023-01-16 01:20:02 UTC +* Number of recursive dependencies: 162 + +Run `revdepcheck::cloud_details(, "abmR")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/abmR/new/abmR.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘abmR/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘abmR’ version ‘1.0.8’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘sf’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/abmR/old/abmR.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘abmR/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘abmR’ version ‘1.0.8’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘sf’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# abstr + +
+ +* Version: 0.4.1 +* GitHub: https://github.com/a-b-street/abstr +* Source code: https://github.com/cran/abstr +* Date/Publication: 2021-11-30 08:10:05 UTC +* Number of recursive dependencies: 125 + +Run `revdepcheck::cloud_details(, "abstr")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/abstr/new/abstr.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘abstr/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘abstr’ version ‘0.4.1’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Packages required but not available: 'lwgeom', 'sf' + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/abstr/old/abstr.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘abstr/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘abstr’ version ‘0.4.1’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Packages required but not available: 'lwgeom', 'sf' + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` # accept
@@ -108,42 +244,6 @@ Run `revdepcheck::cloud_details(, "ADAM")` for more info -``` -# admiraldev - -
- -* Version: 0.2.0 -* GitHub: https://github.com/pharmaverse/admiraldev -* Source code: https://github.com/cran/admiraldev -* Date/Publication: 2022-12-01 00:10:02 UTC -* Number of recursive dependencies: 122 - -Run `revdepcheck::cloud_details(, "admiraldev")` for more info - -
- -## Error before installation - -### Devel - -``` - - - - - - -``` -### CRAN - -``` - - - - - - ``` # afex @@ -228,7 +328,7 @@ Status: 1 NOTE * Version: NA * GitHub: NA * Source code: https://github.com/cran/AGread -* Number of recursive dependencies: 164 +* Number of recursive dependencies: 157 Run `revdepcheck::cloud_details(, "AGread")` for more info @@ -256,16 +356,17 @@ Run `revdepcheck::cloud_details(, "AGread")` for more info ``` -# ags +# agridat
-* Version: NA -* GitHub: NA -* Source code: https://github.com/cran/ags -* Number of recursive dependencies: 54 +* Version: 1.21 +* GitHub: https://github.com/kwstat/agridat +* Source code: https://github.com/cran/agridat +* Date/Publication: 2022-06-15 08:30:07 UTC +* Number of recursive dependencies: 257 -Run `revdepcheck::cloud_details(, "ags")` for more info +Run `revdepcheck::cloud_details(, "agridat")` for more info
@@ -274,7 +375,27 @@ Run `revdepcheck::cloud_details(, "ags")` for more info ### Devel ``` - +* using log directory ‘/tmp/workdir/agridat/new/agridat.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘agridat/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘agridat’ version ‘1.21’ +* package encoding: UTF-8 +* checking package namespace information ... OK +... +* checking for unstated dependencies in vignettes ... OK +* checking package vignettes in ‘inst/doc’ ... OK +* checking running R code from vignettes ... NONE + ‘agridat_data.Rmd’ using ‘UTF-8’... OK + ‘agridat_examples.Rmd’ using ‘UTF-8’... OK + ‘agridat_intro.Rmd’ using ‘UTF-8’... OK + ‘agridat_uniformity.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: OK @@ -284,23 +405,43 @@ Run `revdepcheck::cloud_details(, "ags")` for more info ### CRAN ``` - +* using log directory ‘/tmp/workdir/agridat/old/agridat.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘agridat/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘agridat’ version ‘1.21’ +* package encoding: UTF-8 +* checking package namespace information ... OK +... +* checking for unstated dependencies in vignettes ... OK +* checking package vignettes in ‘inst/doc’ ... OK +* checking running R code from vignettes ... NONE + ‘agridat_data.Rmd’ using ‘UTF-8’... OK + ‘agridat_examples.Rmd’ using ‘UTF-8’... OK + ‘agridat_intro.Rmd’ using ‘UTF-8’... OK + ‘agridat_uniformity.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: OK ``` -# AMARETTO +# ags
* Version: NA * GitHub: NA -* Source code: https://github.com/cran/AMARETTO -* Number of recursive dependencies: 155 +* Source code: https://github.com/cran/ags +* Number of recursive dependencies: 54 -Run `revdepcheck::cloud_details(, "AMARETTO")` for more info +Run `revdepcheck::cloud_details(, "ags")` for more info
@@ -326,16 +467,16 @@ Run `revdepcheck::cloud_details(, "AMARETTO")` for more info ``` -# amplican +# AMARETTO
* Version: NA * GitHub: NA -* Source code: https://github.com/cran/amplican -* Number of recursive dependencies: 116 +* Source code: https://github.com/cran/AMARETTO +* Number of recursive dependencies: 155 -Run `revdepcheck::cloud_details(, "amplican")` for more info +Run `revdepcheck::cloud_details(, "AMARETTO")` for more info
@@ -361,63 +502,38 @@ Run `revdepcheck::cloud_details(, "amplican")` for more info ``` -# arulesViz +# amplican
-* Version: 1.5-1 -* GitHub: https://github.com/mhahsler/arulesViz -* Source code: https://github.com/cran/arulesViz -* Date/Publication: 2021-11-19 17:40:07 UTC -* Number of recursive dependencies: 111 +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/amplican +* Number of recursive dependencies: 116 -Run `revdepcheck::cloud_details(, "arulesViz")` for more info +Run `revdepcheck::cloud_details(, "amplican")` for more info
-## In both - -* checking whether package ‘arulesViz’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/arulesViz/new/arulesViz.Rcheck/00install.out’ for details. - ``` - -## Installation +## Error before installation ### Devel ``` -* installing *source* package ‘arulesViz’ ... -** package ‘arulesViz’ successfully unpacked and MD5 sums checked -** using staged installation -** R -** inst -** byte-compile and prepare package for lazy loading -Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - there is no package called ‘R6’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart -Execution halted -ERROR: lazy loading failed for package ‘arulesViz’ -* removing ‘/tmp/workdir/arulesViz/new/arulesViz.Rcheck/arulesViz’ + + + + ``` ### CRAN ``` -* installing *source* package ‘arulesViz’ ... -** package ‘arulesViz’ successfully unpacked and MD5 sums checked -** using staged installation -** R -** inst -** byte-compile and prepare package for lazy loading -Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - there is no package called ‘R6’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart -Execution halted -ERROR: lazy loading failed for package ‘arulesViz’ -* removing ‘/tmp/workdir/arulesViz/old/arulesViz.Rcheck/arulesViz’ + + + + ``` @@ -489,63 +605,69 @@ Status: 1 ERROR ``` -# azuremlsdk +# bangladesh
-* Version: 1.10.0 -* GitHub: https://github.com/azure/azureml-sdk-for-r -* Source code: https://github.com/cran/azuremlsdk -* Date/Publication: 2020-09-22 15:40:07 UTC -* Number of recursive dependencies: 91 +* Version: 1.0.0 +* GitHub: NA +* Source code: https://github.com/cran/bangladesh +* Date/Publication: 2022-10-28 16:30:05 UTC +* Number of recursive dependencies: 94 -Run `revdepcheck::cloud_details(, "azuremlsdk")` for more info +Run `revdepcheck::cloud_details(, "bangladesh")` for more info
-## In both - -* checking whether package ‘azuremlsdk’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/azuremlsdk/new/azuremlsdk.Rcheck/00install.out’ for details. - ``` - -## Installation +## Error before installation ### Devel ``` -* installing *source* package ‘azuremlsdk’ ... -** package ‘azuremlsdk’ successfully unpacked and MD5 sums checked -** using staged installation -** R -** inst -** byte-compile and prepare package for lazy loading -Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - there is no package called ‘Rcpp’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart -Execution halted -ERROR: lazy loading failed for package ‘azuremlsdk’ -* removing ‘/tmp/workdir/azuremlsdk/new/azuremlsdk.Rcheck/azuremlsdk’ - - -``` -### CRAN - +* using log directory ‘/tmp/workdir/bangladesh/new/bangladesh.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘bangladesh/DESCRIPTION’ ... OK +* this is package ‘bangladesh’ version ‘1.0.0’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘sf’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + ``` -* installing *source* package ‘azuremlsdk’ ... -** package ‘azuremlsdk’ successfully unpacked and MD5 sums checked -** using staged installation -** R -** inst -** byte-compile and prepare package for lazy loading -Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - there is no package called ‘Rcpp’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart -Execution halted -ERROR: lazy loading failed for package ‘azuremlsdk’ -* removing ‘/tmp/workdir/azuremlsdk/old/azuremlsdk.Rcheck/azuremlsdk’ +### CRAN + +``` +* using log directory ‘/tmp/workdir/bangladesh/old/bangladesh.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘bangladesh/DESCRIPTION’ ... OK +* this is package ‘bangladesh’ version ‘1.0.0’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘sf’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + ``` @@ -563,52 +685,61 @@ Run `revdepcheck::cloud_details(, "bayesian")` for more info
-## In both +## Error before installation -* checking whether package ‘bayesian’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/bayesian/new/bayesian.Rcheck/00install.out’ for details. - ``` +### Devel -* checking package dependencies ... NOTE - ``` - Package suggested but not available for checking: ‘rstan’ - ``` +``` +* using log directory ‘/tmp/workdir/bayesian/new/bayesian.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘bayesian/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘bayesian’ version ‘0.0.9’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘brms’ + +Package suggested but not available for checking: ‘rstan’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR -## Installation -### Devel -``` -* installing *source* package ‘bayesian’ ... -** package ‘bayesian’ successfully unpacked and MD5 sums checked -** using staged installation -** R -** inst -** byte-compile and prepare package for lazy loading -Error: package or namespace load failed for ‘brms’ in loadNamespace(j <- imp[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): - there is no package called ‘rstan’ -Execution halted -ERROR: lazy loading failed for package ‘bayesian’ -* removing ‘/tmp/workdir/bayesian/new/bayesian.Rcheck/bayesian’ ``` ### CRAN ``` -* installing *source* package ‘bayesian’ ... -** package ‘bayesian’ successfully unpacked and MD5 sums checked -** using staged installation -** R -** inst -** byte-compile and prepare package for lazy loading -Error: package or namespace load failed for ‘brms’ in loadNamespace(j <- imp[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): - there is no package called ‘rstan’ -Execution halted -ERROR: lazy loading failed for package ‘bayesian’ -* removing ‘/tmp/workdir/bayesian/old/bayesian.Rcheck/bayesian’ +* using log directory ‘/tmp/workdir/bayesian/old/bayesian.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘bayesian/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘bayesian’ version ‘0.0.9’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘brms’ + +Package suggested but not available for checking: ‘rstan’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + ``` @@ -661,72 +792,59 @@ Run `revdepcheck::cloud_details(, "bayesnec")` for more info

@nZs+xvG3Nt4fVA=-KHHo ztT$Td_;$f%2Dc7MFT7E4g~kjxy>xaYQ%aqmP1{ro+fMYjr7fO_Rt zPaIt2nIi`w?yB>tfadqyR~;s1cM(lwuGC15XiK!=tdaHoPQnJo{tq@?3Pu+Rm-(e$ zNRTA1;+w#+p^S0`>gUT(eD_{qXg+rcLz4|d>&ce^vbFk~I)C3Bf$>&Wb^%!vAVV4FtP0QEFtztQi(oYI?ywXa3?^in8Y#_fB;eyj=}>YgIvsMbau zpZVWj$U`S#%FQodxwV!8*;JAhb9ke_P_KLdbq$X{*rJxDXsQzh8i&g40wD;mKBHcnt@>ZQ!fdmn5k??9!*7hWB0J36a~ESc3t@;)2H~p&lCWT8irO| zgv(F55Sq;T@Dk*35W_-RY}!k|)%2W&)$U@f$LM1`qT+ZD|p4#zo8BX$vOGM@hBfWo_ z`a&c@dC3ir+Y4JDnMsZzPx2(!LkV}GZ!x%)`lB31!pJE%yt&Un&~v8V7Lf133OV%H zP)Z-Mr)k#vO<-7jITvR!UOwuX#+KQ{2Z4M>wK#~)Et)r-!EY&V&PUSCjCIV3@2lRR z->u2xD+d0E-N=)BOras#2$o%R{`gFDP*oxo6l}on`K1q2;R*;N=%&mkcGC%$Pff~f zfTTeDn{ri0N~}@BSVV)EY?v#4W457(LXU7%WcIR{m5H}3$C8^YnR}7CFv!UV2U}gT zeW~V3v%YIbQ(6?av`t!%<3%^;sRdJE80=R>&NRGaUZz22^3ytHE>IUID1^q~<0|FZ zIJd{cd=@NLpb>@}6Jz;R?mpy#sv=&-~v;kU*UL#-E}KAfX3_>eOh0 zjA&2BwK9)K4*q-|8w%YN@x0-XkUmE9rgK~IZHg)dFNpT4aNjTW5_#4xrpUw>p5)V$ z>*TaHlcPFx`J+X%e60As;3h$NP~!vUeYbt>68D=_;EA6d!s*oGkejS_IcLYHz9W9U zq3WfJ9%5g%cQo?l%3Mg5Q*IBh=K9ID9pTqJk1B2wzn`~gv&{9 zq)}X_vj6h5Y59QJ(a$<%J%7c5DgwJPUgk_??C=n~4b$a^JM~X=>AZ@RVb#6<8Vm*y z{zjz$pM}tj`}&;HV^eW=52Cs$U8R=B6?>4t;#Y=tgTB^xpTmRw=He4>`BFDNn?Fwt zho5q2^A903IrAUuV)xwdgg@sxE_~HyA7F)4Qu-3tkV8t@HMfn*oLEsZ5)uQGl76UA z5McqumvDHtLTYG=B7>)tG;;}}>{`m`r90SbjXmo=Cm+Z}KOgtf%}c9!};fcI>-cL*aG>&*Rx2=i}*+EG_${1@jmi>D81HRKNB5 z4D^P_zy3By>;uz=eMq%l@OGdqib~LVQlK*#LGDyKtM#_7S8{Q%yl9>rsM}&wK7fG} zmQ%rikkb9juyN+4_)h)6gVeVfoy@oO=Jpk_JFnq#*sX^v3i1B%;EnZ3pV@*X>r&>% zNri9%p2gO_Vlz1<^OBtdsCv%n7GeF>%8? z5QR;_F>#qy6iP)XJmdX_^ z81iCgtwnf9PV%L9-?4a;zus@j0egSXXcS-sy^(=RYh0y!uXg)blRzd_{~BV`@~vG- zr^Zkl0o&22xrEUOxd)fl4yMJP;5+kYfH=r>?6eT$BEM7y=RF%q-DHSR-HkF;R8z$} zY8ex2Tpyp2!WkAmz0faO5psOU{5WeN;1J*%ZHTp=L zJo?VSOTtI^^XKS!6CNzqH&hvK#5IF2aM`4|o~o zUH=+ckm-^5lQ+SAUn4uPasfwQBjb>3Q1m+?qg?zFX4H`OcWmXs$avWk0m*ENM!#sw zj1IFMHQt#0!Z0+U{Bc}G+m|^)SI=^M`=*@9RHDsp1kI;;`%kZuEC!pJyRO`xV*xqg z1*Rjo`4z+ClrX+@GLf~4`r3>mS!r(lRSJX177(BgWkd#B--@khDUHL=l*jXXvXGlW zaN#O(?f!RYo*J5wyq}qd(3_>J5D<%Vk<-W6e#Fz;=fFsRkiIN``?Idnr{BaG+4f%x-P-i$)chyyuqD0aNAUhUs@ z;r((CLJ_~=0-;`k+F^C*>-Ewu`*S2V+Yl9xe<$p1{$6Qzb#*^{l2OX(_#B3z14JVe zwm}|n$_mH(^gF5h)`{$OW+yyp3SZDn!E>+S&RPVUnUG>2GBxl4MtB_F z?~;J^sr_lf)#q&Z_eLX|T9r5c@RJhD^}w*DH+m!MIPa39Pp}S$@Z*v;%cR@ORD$840A~(-b9nQ8)7Q>%s3ZVTo{eHs}*+9&hyFf&-W0 z*);ttdQ$wX?{K~o?*VU@95kM~HNdZ>a$Vsl?&h3K!RurKgr&Qs7iPl2I_moTOu^M` z4<#4h-9uSeUh8>~86Q=xft8HEEN`{Z?7~Ne0y?2d3a)7t+o1DK?RES%qV>v@Z08MsyFCB>cFBruN~|xSOmzM= z#(T&BfCR0CifmfbvA1p~Gv$j9YS*=ByWmZA=ZE-Yr=&Qah6fRv+Z8TfDbAV)SaxSi+35jX^Sznrn@T~5-aRO6rKf*vg)GE z166v^iBR%=krjJ^Z|TNQOGm|**y0_;O_~XN33jY(@q^=8<@iXLmhR)@_wKAJi*W}F3&?{k-De)KPupe4$O~fg!DuYA&m^N!HWDCuAx}Ci+JOyf3_Up3 zFb^Nbjfsx*L=1LN@NzSvJM|zO{nJ{vFhB&rK3VI?R>o*V+zZ48TPCTu@knyaXvyNZ_^#G+F@hz}>BP}&*tZvFkV#fhj+gD;XB*#BZ#AOD(T zGVOgyMHbBg>E?2N`5f9igYLzL!kgJTG5)Xw2aZ?uG5xgE0VSn z_@iJiNMuoxxW7%@&G z-uR^86^K-_h@m{BELl7;`&!(^`i~($P3Q%NoW$0^Kq5TJy?m{m2T!x^(bgw+>-Gir z&hJ6qZFT2X5a>J2P+Pgk740-|xlFt;G_ccjc_B^j|odr7gN?AcQ*nls{E`DhdI_oZNs zRj{j8lNPSSsR!4?x>FwHEksAPz$p=r1-?9k5f zJjc4TJF=r1#sgp6;cLj~1J}c|IDV$DEsYUKO{vH)Z30&m?7)5bJ}21C_?tAWHi$6C zBKME=jue~MdaR62X!_DVTm+~XgP#QxqH-6aXuKtm?9mCyrG@r6sU0*-V2@@X;v&)U?bvE@1Wp!#=7(G`uqIL%c%6$t_}Cwo8%xAvmV11WCgYHKxPcI zma;3ILE;=f%zo*acoZ9Utptvg|B+fEWSGtdN)--&TS%9|9|K_ zTPb}+B_X417@WTX6Rt_XT=JI3?srju3d{i2ig@=g7iJchs#P##Ur)BPI8JWuG8^hS z{hju*KdE@-XA*@`9pHB2P2PLFFJi&sbD6ORwy*(-n#bGqh;4|`j9p= z{TgM%(%Pe!Nk1SnRLFY`AOk60-9PdGiL@5JCsIPi(6gl$5&nzf_JX%y@P96H?OrJ| zw;vgoFDK?P0(4p|gknYBqIzG<-qUt{@_e|iO_r2yB2+Zy;`5GQJkD@RLPKgi_nvtS ze=okPg2hFc@fUWz{jjAeVO9~s@U)OEoy9J0o+e&`aap=h3x~no$FVxtxgW`qqmVh# z7|jh108VB#SaX~T+Tw}Qs7Mc3?|%lS{nXUgYp0YB5*}Bc_1QaXgSX13r;`!k=k19NeSzW!h?4j3 zKKdTkGy??s(@&l(D9hQ7_UGM=ox8x5r!jO_+~OP1!Ip{6$xPc#u-ZHaYIyh$`>1V4KvA!#)5W21NinHGm%530T-FG?Q3?#^uk$9OYmGQ7pEP!*TEN=bE+6LLcoS2~`&aZksuMrV}U z0~tDcicf_alLj`u?%!`0HvJs!cRrs_e1*$k_G>Lwb(=QpkENKd(Rr=PoGEFKenmOK zq|UN?uXp?5?zZRTLe`IGWmL~A1V17mG~pqb7s1F5d=72a3oecfCD@5~V&_H>feJ0^ zjrg9dXWSJbt3FnZNx=MY`$v^Eh;bSjUp!ouJVtG7UT`aU`>e+Q01RrB@yK1mlJQV< z=ywF`aYRr)EjJ3qr@9mDumTlM49VJNmV=o^{uGtRC!N7oCkDyDKOdQzo5_3NygE9V z8Q0Vlco?y5UL|DVwhCU93w;zBMe#aLonVUABGI3wf$rsimUbd=N?ZRPG?uFMcF4%H z`Sv!wRsXi>T~mh|sw+OXGCgE=#Gf=)Bf?#zH|Ij}&TwKQoUSFWwC#I^x@L)gxQQ@E=abcPe;UZxq_n0a!y!%Kv`X zfX)pfb2X9|;}_6%Zm=WJSiIrv=q_uz&>A&-zibSWD6U*&UTLW-J+%|Qe7GU=QjG z{SUC`(++%v8xPW=`2OL1gn;iUF73;iNseKS7#TG325m?1@>7e_7$S)mf zF&msI$|C6u#^sVHX+q!8n0~)kTPN$_JW~rXt7>V*AIVK!j*fEPs}H7xLEgtqj;2yi zW(>)9{D~z#0th`l^j~o;G1b(5Jr=2Zq2=kZR0DPQJ`cVcyd-&@`y5jZq{9k#^1=-D zUIX!}0@`z84E@M?qO9f_MJ{~i6<2Bv@q#vo<^Du%=QC`_)4Qj+uuFI0eJEUnvPKGg z*XYAVL$*$6reaPhh+Y7#yd{WUNGz-VET zrJ)=8%T}3nff2!uvW-J|EF*s%Lpy)9Dc)^M;ePe#?r!o%sre_Xt~GWuxbC0TL|%ql z1RgsX^X)6`j*#-dqnzfki(7_=hl)RKw|b@l-u{Gwy^dsLi)j6+?FoG$q;J_=tXX5c zEo_a}OCy(ZnC*Y2(1Cf(8upn6catZ5g>K(^Fg(W~-I~QdHIu^?vvC4PoZJ|i?e)Hj zp_r<(#9v5n?RHV($G}lRrh(v_{A>TZTqHRAyOHpOlj|q8%&@DCV!q%h$r+Z~U&kA< zBEU@_xs(p*NOLvBjBQr^#h^eM7?wUXDT5YPD=nL&;LA|8=0 z8}aSSD{Dt#p8D)%$9EM}Qd{>-Pcwl8q`3*}&v2$1v|8L6SC7PK+DubMua`{wJY2vq zwmm<+#y6LD^5QF*b{mKLvvsGcm;u}3xkuoTKchDDjme|eIag?>?Z|WLhw+fSghay( z10N^LZ(n9;!&ICEh*)Y`hm;I_m7$vY2-olqm4|=yjPmDpb|zESC2~^2w|7RY*Qs(! zL4Pq64F&6j-@;imxvHr4m1!b4WYf{Xm_`i(#(~K33t73G4MUPr9AcTHTvx6IWM$fN z7abIkUz^-c8!x^Z_svv7;=}$^Z&`r(%)9=&4#4(Qk=Myn9f@^SwVVl?RqxJkq-1}0 z-xj&3uu;xc#9QGm2G>*r52X!8i%ZFI%#`Et6M?R#JZ#Rs4MkS1pHn^OqdwzO&)sL_ zj2*IkZsDn_g#{(Qx5ArfDFCgF_%S^^>)6=YI$56X{Zn4W=2Zpyn`C+RJ3Ec-yI^RD zMVDUDcqX2PfUs0_Dz%gboM$uG{$zbxlg);dd#S~pni(B><_BqHI%!PE0av5syhfj@t=l;~vqf$~gV^8qZdwc7`&dVBUR8)my)W^XqQX5X=B2mMX#myo< zsh1$+^<0EHpm^bb)KKEh5)>4xQ#hbASqqiAZ**gZt9Y}oNArGt;p5|RntJ~Fllg+t zsGJf-P;L9gs)_T6Y(5GO43YC)Xfwynnr9Z=d@o{dv4;Tt8gDWeE!6=*NXJfmOzP!9 zU2LBC{l!E8q_9-WKT=^;QgFl1yze~#%nePE zQQ6_4femH)1}^VgFi-6s89~rd&&3V68*N28sZ2WLBXQ_s8*12d>&a<4ESVvt{AtsO zHu!evKwIA73G|#kZFGYS#vfu`aEiww6YHNM4K!~yLpVJrcW`{O;!0uXaBOUX5em>S=Q-^>w zN9?`T|2bG;K=wfS!1i|<F|}>0M3&{S3cR-@H@$S@0^s2%Qz`L`c)gm*ZkM=DKkv zm@B9D;eBzRrJdh@vR1(eruVA&bBq$6->Yu#YX|K{=1N3^9ZFlnp38f?yqTFVuH74L zJ)^Y1)Q9hvj${nKCIr7zxwrd+jLkg)q9KD=nN%aMXidAg*EJz{u&2U_c(+xSXX*YJ zx}iVhnoGd6sdCCAT4Jq#Ci46@bt&%A)(J@`#ac#=Az*V$5|=87VQRrxBn<8 znJO@!wvvs9W@X_BC{!WQ&hD!(t5%}5M~P7w!?6OAd1us9a<1``gQ)cjwmc z!a7C7`+?~5yKv?;^onBbQ-s#fn+YDr_9p{rt_`#Ssd*CU&TqIH+82<|#-*4m%P-IH zZlol^{;B>*QeEbzT@l8IO&tl0q1juX5KS|j`d*zZl^Db*uCaFrmu2bGw;yvZK>a}Q0>E8+W zaH8+~2CMWs9VlqrevQ8cneROuW^*oN^w?oeS}Wa+{&440n%E&+?2D$=S|SfwWGO#C znOtlI(4kDIf8wdJWwLGeba?)$*4R5Y*S^&sw$I=uDzkSc?laEMTei=e8x@%CH2xwk zL4JbV-sAMVBZN{DcDaStVmyI_dVUzX1=G(N7)k>3X`C%Mr8!|a3l-!MOZ*3_%0g64 z)nAQV@}r=ULbRukHsk zN%7OQQPVqlQ2{96AuNP~{8nDhNxx7!9s%$0FAKz**$}H8`-FKAQT$M_82*8xKpj_YJg+ptQr$BQ{Gr+nM;FfuyUH`2lxp*3stVaAECTXs#=_*y@3 z#%D<0#uXmxY|p=~0}O1G8JZ0FLEqIcc1Qr^1g;pQFsRk+nykSZ#q)NLMJg(v&Jv@S zU^EpYSSpt`D~8O29v+~Hw*&<=^b1I-+eGgOurkwbM8SZ_P;;;JA3`Tt5Fq#)+A@OB zH<#ER)XRsjO_GYCv~^KricIJNIY1s7M@p6v0=d**HZ~WSp;M`KJJ#1%BCn(QREd;|npb8QX$dxX^3ww6?6erK=z(0dZ}lWgJGq1zr<5FzX9FrT8+cv)yo zSQkuWpRCK3WW?p8c`)n8Q2J>GgYCC}e(Fz^^voAh{SbBuxnoYPQ!6LT6qU0wo*_Gmnye|b2xh?gz!QIo^n&4RmdW0wkTYRwpR!sxfRTIDax zd5?r&tuAsR(hldILykIdKA%tcz#btHCjCi#nqg~VlC0FD2+L@mdMN4lFMxaBoPfkK z&Jl8@2h|unql!Z|s#jBmw*B#;VS&7Jrg7^Gbo_2jAA9*jsy}--@VuhWKIFUj`=kYs zSpGOShu-8f@FfTEyPOWW6N2LSyfYqZbzNB)qg)_^Mla_J z8+!Nvk5HNY7FM-iR$`=38|{HPDVh_5nOXQL?XzO;smIh&`)-KxyL`!mzJTZc55WaX ze4BISlQ;XYLhQV0Y1UdzW4BAy{j9&5*6wdV&PB>mHofo%6J#-sAq;2fzvBT`dknp_ zm>${UoP51+|T$yF=m+?>9*{Gieb3?g5-jZSHt#$VAFZv#-+2JY ztP~P>tcEq$m^XfSJVpV~FUpFOxBM*LH_QGfA{;E*Hf7D{Ys+=X<|T&y)H%jKed}uO zw4h5s6>>;mc#HVDp-Lk3Tc`bck!vO`t=0$RPfV1FSw%11=z)8X{~d0ab)l~h0To|^ zb))t!xLeFW|6I`hatzrXDVQDC_iosFr%fAlTf61K4lGv}g6V>w5(*h^h-i=v zp&bEh-rqR_5?LX4S4a`kxi01$`*`aV-dhQ-^BNnPD#cdo{f+Rkd1H-JRCG6H4!Mh6p{PIVKfGPv|nIlM0PvNr&-Sky0FtS7Y&fpxn2YeeS=+^bnlnipNif2mr{;4t<}D9c!Qu%)bMraqk3x@L`iEOM zB*3yI8^u!8C7#s&l%y?%`qY5~;!?q{=Kk?`$!wUI#c73 zHT>cjURZ@arXRic4` zp-)}EOk~ia(S8O<_&DNDRd%qWOfK|v)QHmRSP+ZK+(0 z8C}~{6Hj!(l&*|LhqAp5_Co-{F}qf1`Hwbk`MVdh#JCr&{n}oht6L5%KYt2GzZ=(! zlUk!|e{`CCOM-_lCe_VPD;=4AmpT=g-2TY24-#NA4d$rNhHQKu^O${2?{^swMT>r{ zi8mRM-j&}JWYLFZx+f!wKZ3+RpCRBKlr9n!s76mH<(PC1(CQ)*X z(TMp_H1Lzw7;)GA-{1#L2^KbZWqC(v0q#6x#mPX_HB*&Nojz86e(KUNbBDojS@?ZH zJS2jG>pzB@MVzKl>>S+R6%Vnj6;AjyjBcwsnVgCf(YAi*z@l?9WeAKl?~glptygZvRG2Ec=hfZP*C z5=U?Z)z(=YQkIAnC=SHSXhWIp!;PCngaU@Z&hakLO>#u{IO{2?P~nbn1B8T4xs`Di z+0-QS5vc>Rot?qV6f0sOUVa*~(I0X^!W9x4?*gE|Or@xZ%FfEm0$s+%Mj^jgeY#+& zVm?EgyC-N)Y#~~zCTDHHbfN~mpA(ujdz9RE#ERv1b~w^@reCW~BcIwbj{TW9$PoJB!kE|t4KCX8XNF!2;v{?{0Ek=_;1h6X3g!Rfr9NbF+w=3W z!%nQ_ISa~=12s2PD7K5}k0uo_$WUj@GSXKSRW1TYX0YODZ#kSbSi+CZ%n})HT+9rP z(T`1mv$+y}o=}*4=u4GLG1^o0cQOO*QbM;BR*Gv;n8k zqFv_n-Mo%gGc@Ya@GCXG9sxE_-8kGIxfzQ={}tyF5>RN5lM?9&|4wBZ*O<#v&G5`j zviG)iSaG-i7s4bFvl*LQlA|O_VVGqRWUGrX0d$0~2LgxC61o;lUvMu#=IVN}e%yE~xkbzDB>JJ{^k3(m_N<+Tzr zjv}K%WK-e2do)+J3?4}7pjCyfV5%+G1( zCepj-n9n-17*oo^GSWDw0AkV(qAeBAP}4&~Vf$XhdP6)8V8un{MMEe_u`MM0zdh2} zGs#pRfV^^%_nmc4BjGsx!J(mI^Txj7f{5nd8gjw({yt6+e($>>~IGUgkSb(ow~(9b8xd-xL~$tlQ>xd*?( zIv~OtxKZ)!x`d_fp0WNc22(>J{l{aHiu5_>TJAdhALrK`#=lHyngxFCp;ou=GyGy= zjkKkuZDM}`;v;vq#**z}A`3nz;~=GPNgEj_-hRW+2@!)-(EXqhd2alA3?fBsFv!ZW zf$IKsL~NM?M=@>;Cp5-PM)_GOhR7s@bn(PFbT&c?dcOoBT`vNnEoYw9rz;uadmFWM zT>(Mjp7k3fw`5+{H7Uamtr03;zlI7Ga!MbUeuOJg-p4Y32?dC^l3V2;=G>S-hGZzz zNvDbc@cG%HN(UIl z35jjaJ)Jmd=IA(f{gtG{RTbnY*#0`LSW&S;uO+RTwfgS!A&q~TuozNB6x?0fPit$yDB_8ByY)R{e~p$ZG1*{r<-EON1|rd_-Ca31 zToo593VuR54JYU#6n6PbD5@*wFfuGn`rDIzs>LNan$}l+J*7az{ts`2xOAb1?Uw5f znbo*t!#gM>v$6*%G;nS3s2GK$99A!Y|6*^O$Bq8xUgXRw19_FihVN-nC++@_XjPQl z_NRT`2WMy8+s04kO3|Y++D!(1V}af9Q-{f;luvz0PSnxIj^o522eW{}kI|F%Q*Kkn zoy2JG3g7@l7H#|i>2rhUeItUwo#3ZADl#Gc41gI?{>(2`vUGes_AJ$FLufYSN`uf@B7m`md&)L06qG}IRdX0{Tg@s5Rc z3x4yx!&%?QVaTfMA>)vvStESAUZrK$SjPF6SW@Iy;Ms}TXHF$8V^kE1WSe<$bYyr` zm^NCzWo*uD;|Nponn%a_%c%o_@vF=OXlX#+;8j=n$M{k_UPNr1ASyYOj0Mvi!oum7 zC*|t^QKstYdT;Vtrjo&QL1||KV9)EqwXN_!BT_RXZavXlJ4; z1ul~W*#S*^6+`xt5rQ{^^hbU8tUQ)^!q0dpGJ*K(ALUo#qaiSmLw!$%{5j!6o=C@iDIyGpCDeGrFJA zupksX{5k@}7T61{XdZ^_=;a|}f3QCdkKr*~TgvnLlLk{cvIIecaXUtD-Q^QbaKE~F zkw!weF?672Og7Dz3`x#_Kpd)k@GRY4$UoqLKkVDNz|5R#_v8pLVZ&u@a^oBy9c^PW zmMV^`= zs(8Nk_ew7n`Lt~qkP_+gM@DeK84ZC;WZnly{^Vf7wqOxmXtiO&T09xbrV|+0@Bk7K z81eMX?}Ps3-T+C+(xC?8Z+{m|hF!m~-<=X9LNV6-_%Y@f5j!oxhx_q#$&{Ew;VN!i z4SP>nDRPq7qvOGSu*(G&sJ>@T{;!)%6*^#)N7Rd^RM2* z)?0vg$U2~K7;)Io#+(9*HeE1bUErs^*2B5K5Hyq_f)b7A* zDbUl{^7uC3K<{)l*yCFsc8{n#Z^T=sWNtL;kF0$X|I=g{K|o=V=htyPolrGj4$IG@ z)XpAXWor{c{;V0kUpKH*6M^3rU#5_3DQez$v#}@Z4bM)L5SbayM!+o(hTR;9J&+(` zHd@BeWcyrqN!`}0o`&^Fiw!vXOpYrHLMh>#R@S)Y_(-xLi62r?BGasaZ2cV(%L0T- zpWuo|-VTm>lly8lbDalW<-=wY`Mb*z$rMw-o@sC@zRIQDPXjsjGoObef`F1SE!xS1 zSdz7W!5=C#g{d;oVgvqtwe@K{lhrn6TdhG*cTO6UWs(e;0A(C8LDJbiRA`nxKXhp1 zVfSLSsZnJ1V{ufZgoKg^TV$xxzUZlSwl)rgioizCnsy&yl`$SGaJr9AfU;2c(A zmjy1xK>!bz}oa)jv4BT#zD4%hG8C8Tb>= zTpHAf24XrQZgUR%;hFeVnDJKdVmqQWvgYzF$6foiJP*a3fjK4lptDShi@Drq-&CW++mf1 zY{ed;~y3eXBy{Fu%bo$!gmrkyG#*9lsZ>K83609wnBd1Y#-bTz< zAZ>;<|AE${r`Kni`1?bykz)TC8ihKQV*+X6$fzR!b20Q~R(d`O#UCYuL88DpL5V== z%h0bs5_%Bi3qj-aG}f5gw6g= zF=q8>>GO0tS!RZVJ|K>(OlvQ;{Z8dvkNqa^y$Io>VY3S-*HBGF(4byS5zu1v`ZNn0 zX_jt@=Ej2*-&B`Grz1T8H2lTY2C@MhrN%UQgaiiZL=njHVtB*rIZrTJk>4Rvw;p4( zU~N7n+S4E+)<6mCYp#{j%jOn8#v{2;z$%=9mGXZ&KB9q@q$pR01xZ~ZcL}`tECCEH z7T@e>aaoxTt!DSH@$afVjo-8_zshgY~L{tuhI4Q(0(B>|77K9g41hp*~GlOV+^0 z?-7y7v332t|EseMS*M9*V`19AfLs6ilhox`7 zu%EP$0yW}04y5y>>mdep1 zL-NIMosixJEchQ8#1SjQQfO$90;Xn`Z~}vl1H)=f4SeC3N#_sn5FCOTryTJWZQ5_5<_MP2XRE8k@1oW zc#M+41$tFhia1X!#Sb(p=-D1fOPmwuBt15r^5}ErSx1c&LU2177|zIg#Fn;I4@mB#KBI?D?+ zFuh(jL}D2rxRRL^w8VIwJnsoVHr|lsbOrJ@SQ0vvv2qF1D@&3XGOL883SM5!04dbS z%==C2a{@lJA+27 zHO9r{01PDShL5m;dnsF|O=V8t;I;R_Ss8|bE^5k}zAHYWYz8-31Lic!V{lyk^y@at z;>E4<;5QD-HxCX=PrfLV1AV$d9gjre&=jm!Td{0H(}1}tfcAlj@FVRFQlr+kHO~(& zpvJ9Vuvi*;R>FuEsrxz4IhzcP<-|cSS2B}=78~z;{(R$gVcngHv9P~6p1a!wQ!XMI zb3Uss1MOPi&sh1;6e$wV1V zHjFhcSdf+R;b9r>8^G5-+&nF$is7Hf_V!B) zj`u9iOlp4TvUnfZGN%DfEZW_`(4>6-I;`{EzDmb@?|bm5wBe+M;=~ZP$ic}9Sg21M z;v8nKI3i4sG{ff6lHwV`oB_t6B&=>glKF?SLONPoIyDo`=7#QN($u|J<_gU?{0t`* z7LZ_Wkd?ua4aRB^C{@OuwehMxtJL3IB%WaN8MtF9B|>Z(ttf91J3s=ELJ_LL=TlT! zHF7%iJehffAc0{TFCZ6$V$(Q>7uV6%A-U#u8O=7x^2J^9>W#~!cR`zc`|$&^_bD8p zRgWQz8FbLnX$*ALzzgMoF&+*b<&oE{=?01!xn+4L98pd3G=_l=VZ-$mkhE7#+J=+V$H~Ry^3SL8Tl%XMLCVl+81UfWemGZ&JCM0jaZB7rtD}!vm|g= zN?vS2!+Pl0@ZnN-O>y~>EhQpT&iNWkdg^Hw9LiB={NO(3f%zInC> zV*WWWzQD#tw2tbU9ENfOQ!JbSra`0H6&Z*^s@bODieU2Dk#$?uV zoV?N4Dh=(OQp{oI6^4U0ZJ>dOp2LfY%V?=iVb_c?7#EtnCDhcIImLIxL$|M5vq09u zpq_r}w0!l+J{(Ghvyle+^<;%PoKVQ-GsEdd?`ScxYlIdwD_CV>%X68lV?M_XnIs9n!02k02&+~+)&{WV|#{zxe&TUNHn(q#*< zM6e>KZ~`Hg-RlPHJgAJaT))d%SUgpb{)w$uufzs*({ew~^UcGKGP9%T`=INaMEMwZTwIZXWE#dpkC zsqYcG=}cpDz7AXQ)Gu5nEoe4Z8ar_KcSha@C)uVgz4FB46Y^)D_!f*G%bs#*rfE%# zuM4aA3g&nwm(v^+6JOKXNIh<4^cKofF2JeWqZUZx6j7RIm?ZhQ4C)m{VnJ+tLF`Mg zRie%T7moTNr(Z?f&!yLiYazzW7iO^PNg`xW)kA%Xm_QKK$7ElIjtXuF&X>insJYg(^%$a;ftJdRYUw&A;`TY|SWtQ_wuY zKG6sIvVZTOeB$2@O5Y?-X2>^UI}i+97f=hcs@GW}`Z8=&I{h+O zK<%YafGgP$orsoTyw(IK>`@D(aY!4ro?*hL<8q23u_QKTk`BS3DO!Lxw*hxHd8mfj zRfHFD5@+1ZqDflR!=v1XD^jR&^Q%aYaC0-7HF#;%Km*}W!VC)j9Qr|XR*ya)m^9o* ztQBo(!NdR#JHQxOiSql%m}rj;_~GHuS-fO=HK#BokEYXtZAv>jc?x_p44LsI7vtsg zw0E>(y(*e(^jso5Yi6AhWSeGmaB+E?CKL}ngV{oApm@Aiq^YqPo>c62%#|@LWbGBq z=N-p+wBtCm3p!X>xm_w}BIPhzfyHn5Y!%CA=OPE5lQfCN3JdV@Yi@4D zbC=}bA3B27NJZ(ajLY!AX>%-!?(J-Lr{p`}dvisWCd-dD%OXFDP>sucOzPSeXj+!{exN)vu4U6-UV3vov&|@!P%@#VO?oE&eU1hj(_+YI! z3nLlBAIXUfqsyv&#|5MIu9Z+EkI)rO+9|RCg4dug+81vJcn^F#X($o7%5l4@T9$A^!2(sTV-`8Mk4Us z%!ASXJ}pc$*x#wWy#@IO4|oY%reYGoLad4HYHQM+6q)u>eEfz+C)Eqy)HEk`%@Z;@ zG$K>@2ozEJ=jCPi5LW_>JYsFiA)5NOF8G3)FjSP6^=o_3G7%ZajvIY2VA>Y_4H+6Q zYF;{)#wIKB{nswTN3G6!gqVV@n;r;9a^0@FX@x z+i}w>x&G=kvIbt{ghm1NK448x2}0E#>6W&oCb8V*! zjq>X4YviVD*30T;z0%&+qD^)>V8$jU+ILLyckfs$-+p39{`SOKS=`>GZt@bF z(l`lRz0yoXV60la16+;G5R;?=KezE(F%3i51D9^RK4=`9QOS%lUpmGyg~zz#mhG}( z%`)w~u|G+}IdpOmC#?@_Gj|d-2hOiDNkUkvCrWQ{BPLUnnp)(|-~B4tzImZbMbpYDEzY~Qj@jRdOBdA$al(=fbGeeOXybaq6( z?+v%(PUs^;N4qkHDf{3@PGc*Mkkq$7V3gsJ&f&>P@%F?ax8*y>Ye1 z@w&q&u4t?w3dmAN;L(Si^kfQeg@R0oLfxeoI|sC^M)R2YOdE& zqtVeRIXgOw))u=V*gB`V4yP()q^+SOx4mLDp0l81z_ZqW0i)63B0W{X`UIlKLuTlP z?etQEF^eV~yBb`A$PapkUS|v)u|__H+W(eys4(u{s^02<`P^gj*wInxt(%qcv!`UH z?}W?_q6S{jnU@=`>6ULi)+A{CNE0^UDq*miP3butQe5FV5XK_RZ}diNDYtx0tddyt z-Q{Ge;fb74o8T%P#YIZM_n-$%1d2KuoGhrpa%eUlJ3B0oJ#|nG*g1n(^K9R^T)z4E zK{S~#NgM_^gMv$oPz}gsekn0$NxY3XXp$;d34 z&7GYxBn|Sx@4r>PA4b^Q4bLVotJ4{wA(~(PB12dA0yr*^j$D2UFElpVP(BS?`$ic0 zRxmb*f=P$i40j$6F3$E@ys$&w|CT#t_3~cja5j(*N1-6GCDOC7T^cdp7g;7h^Uk~E z)*H5{9Glp5;H597ox>n&(Mo7Tzq%g|pB@xQ>Y6W|4t@D>=e**?jXKo8vl%$A&>UX1 z67QGq9mRl0h>oHE%Pnxq=o_=^acX#4-g4VgS%#e{2L~px(4o;d@z6z~)$8$}Xnhzj zNAi5gCgp3(7JMG^jfM(}1r6Bf=D2TNQ$fz)qjB}JR{7r7Z`Zv2m(M;TUxVXnaeYxH z`cBF8*&{N`<44B^C41=L5c+B&cVXWiPSfM8j|LcV0b63yJ55IhFD=lT3PlaY5FJ5< z;<^w5D&s^#JYg8M39iynT%-hi4;mmwJ*GkC;31vEQ5AU{$@q;&_TwWpuIk+w+?EY1 z)Dgk4y*lo?fZ$F83m^@mv8ho;FtzTwEvvN&Nd+`Sj>mrE(S7*pPHPjYmHowBvwY}X zcgcI-@dhAcWZ zOkcV#M}uDSoHvuQ+AKrq%&TTN`|HSKY`N=k@vF`lK+$c^Pv3ndtQTq=tXkt;X!%u={{M|(IvC+ zplMUuu3gkml1~$2)l#QFhN`3hr$C6#!)-8?i3H74`M3xKd=DBRMm^?3mrPSO8U_uDhQaH|@iX$!!%w5XcpL>|M7_nF zMb!xp@7k4%vs;rVw1?1hQ>xY)jy#QKx7qs z9hkd}e0|L=8>O{1FQ30}AM6Bkr_tINpPJS8U^ZOGFf8(&`91#vjUQL=*udgPf@O&{ za085Y7$-Ym1WWFDiB%nB8TJ7l9EL@BPiMyBY^H zost{iQQL9zYT0*uRA#2o|8Y%ej18ACOu!xR%*8~clBT4Pn3k!6Lq+vx4D~Rc0QaB) zV$@@)#KC~!Ep2a~m6K>jKZ<7bwOco6p`_qK%r(At(@OakYL7;E<8#Akerg{DUrV_4 zTjBH?#^z+NS-(VYoMjw0X0wz-OJ#UMSA5}{vJgA}moXf36ypZp{MH^R)Yr=ic%gsw?XSYS zNgj)1uU~n1zdW|@q~zgn9E2yBYg6eFU(|-74GjHE&caL1Hk!Sdj?L?rt0$bKr(uwv z`1Dugn|SV#(Frx^^(%TXjFOYhtFBT98s%ubgD~(v`{Wno3txXq7U2MD`U-|o!yh}C zldnB|Kt8kUVQFisla35Lqr;;nup;djuPCov0Zw5JLNRa z`fb4mc2h9Q6L4VhNENoJ`|+{d!F9fymdHW0T0ilv)AFlt*#aZNe$X&H?6_kLmmf_S z>4h$~?l^M578JW~<7ldPV0ihhZ`dNsmbJ@+4<3?#`08Ql#z+YlLQI@FDzmJ4M^W=? zix25SRQX$PUXG@a$o_rDWXsjd<+V31lTSQw5bb_08tyS;!!Tkt)A)r+-iv)fxWz9^ z2|@a+;NT|4YxOWhLbTySo+a4?c#Z-db3#dYu=rJ-#Y5L;8e}&L>>FM^q|IAbyKKE` zmDD$3GD`)^y>M0y$8?z%7G8R5&%lVTfsrrhG)v3a++oxA8;|bSOy{`mB!-FJ@`hW~ z%gnE;t9ifpm2b(1|M*{|9cRCG%#Gvg4*vo?*ZSqfTdaeJyHLT5pW~ADxqItMqg>YfFR8a87_cl5N}8=-yX@@O&=Ct{Q9w^BkQbNn6JPU4UH1v4`Bkk~NbtGW&M)7QQLK zAxb2TBhti9LuLpwX#ws*1Ef$2SGgeN1d+LH)^#D}_p`(>rsM+UZljq>kQ}XR+PQZCpkkeR7_Udcb%eGBx zRiAslXZ9bJKmO$X7~F?GEGs*Cvd>O*Fa!7$Hhmwi^~DBiXsfZ`TEqv3?}vtPhKEJl zCcP@h5A|~b{V@9T6*T<^;JtPQffGhr;H562Sr}gA^LaUJ^|zn>4><@U?yO88P4H-< z>0OTx7aJBc&FG8SW&FM~-FL0Q;oi;i^#>2jLx;y@ z3(iVnpOvkg39J+5aGuU$@p^Zl;!4YH(-nzdnX|-8aQ9<{a<@jj-2e5!rY`BJBo2TEWX!c zCuvNO(|#geB5V9H7~>cwQp`+oESU#ap^t-?s}3qH5E`xjp+S<*KRT{B`-y+*B(eQ0 zFRXw`_tW^OJn+qZSQ>{WA{`@%ELpi! zR$y$o6SaH;n(9p21j3AuVMQCNGNz&GD~S_xc`z6bXI|wo-`P2@hS58`W@9&;clFwp z>_qDWSt=*aVjn9UnKFPy`Zuj^MXkI_PM;o=FMaE{bYc>89Sn?9W7&_L!hX>3+v`+I zH89qYLHXmu>J&_@HK4PUYYueW7bRdCWAeSd?Q-q4E9LN^LCmsxQfu)77DJ5Fc>7TE zVkZwZURI!~E4#Y8TRwUJA$k1K!zi%$qCjTp(hj-vnnf~%p%YFq)5Q+-N@IG8^GZ`s z(sZ_|^@#@HVI%3|ReHp{fUFN0t5kAIkE5l?MA@{N#MoqKu7q)0tk*m{sM2iq(2z|t z8Z&Jg@Q2!nb6nX6oxuP;o6nqp!HZwdv+yE+)pE@%j zUwh;LX6L}b;jJyhk3e1(TU44cNHl{{!xK(Dg2sKmA2qe}1acpqr}iC%!J#QXHjV?S zVYDc%{E%=~5I;tfcpf&f`2nKmnJo^EJHP*Jcgv5w{(2eCV6Uk9PU%^(T$Zg`CS40L zW5`ZS(Nv!&4d+Y$3&GQxkIM!*(t>%<96I6<(Z&sn;dw60lLz{x7mhx9(N7O@WC7D$ zr3fe8I((F|&KLdCVSKE0FKBpp`|p2nw$BI-kY2{IV}J1Z+m0}lSi6L_?WBl9@RP3oFQ4k2fbS1$#&x9bhLHI zr@pXHo__K;`fhC2iEQ7xM7Atzld&?+M&+;)YGRI=aZxf;mlQGk#{7!|;9)*Pf|$aa z;QEA7i4J%HNF6CO(yMxmvM{=UY-&3W%(r0f@VDW#+Y2WSFTPY>oF%nw%_7~2flW}Z z^W?d(J(x_fWy4C9b4^)#WS>Hx5C>|&fixwn7PWf=S7rD)eyUIQ!z-IF&!KjMds@HB z(Nj3lbKcJE3nvjrSg3-s&ShSO`5OQB?@z#pk83Dq z4?jFhFv;VC?|P&B=6}9N?)k18u^&^9Og41Nf@RBO@$x0ojNzv|jKj5R&iPQ6lfh|_ znC-+366)c79-hm{)>R!i_qS6H9meV*POt4~!Ni^k8H8hM1dgm%U$2FyrDeon^vPRlfAS9*z#uhf4*Yx_@l};@-y?0|b z49+y-1_(nq@R>&5gytkKr|&F=gGSNc)%+m?3#}M3)zw5i@qd)fp^1e6UF3k&jB!hCX zWW`dQUy1NAz?W0v$#=K`5*VR{HcSjWG-H)G;m5Z_S1)9x$ z{p0fJ@GPcPHp&gxt$}Z7M!xv4IJ?PRPieTNcQjcWg$v!7$YLG*&znQMth3Ix(tE=2`T4xdEOU zuhSPjkU_EqGzI3+jB3G5_)@+}{_b;6VmnN1pNWTBwQ_;nv9(9~W^!n9aNTeZjF?U7 zWP*n)0KO#na_Ry5JPEE*&r6i$M`F)~@fwAUj&BJRjA5fXY-+|DWj0rj=JP6@2I-7|HS6vt4@*62)*_~xPT=d?0&gUTj(9l(<`}Cv z29o1-c)?e|#dL58iZumW6YiOqG=(cA>BD4_cI=P#Z(n^({^+khtsZDT6Z`d)p$-mv ztXsWIe)yid<-h;bo8^}4Hp*0eoAfSSjOm4~x)qSihb!Q*H3_CB#4w>QTst zUynlPA~j;}otuG2(p=W+?9Cf9m^7RaS9wEJ(EOyslX?lp8)%9_pCCgRkp%_Sr}bme{$~;IdGg!<5@IAF?k(dV|psX zX@-0}zUZKhVj{Q_evvq)E&1>!iK21R5p@>hitX@Ff9C#g%dh_K|B?H?x?6@vQFF5v zWB&@5>rT)+|DpGOue|Y9TV*QWEIo_4lE*C8NHkw&2}dr!+aYSBgL3QeKu`~*f|e(?Gp*|2dDTBQB*z@w+(xZ-xQW|D>)FpQ3QF@+Ya zdfn+bWdBz`)~2@i8_{7=ek(Sj8z|PvrX|htrZ--LJSxcNzVN7=Ju{?zX_haBi}ZI7ogy1lJ<;Ds~ZB+B49Q$(QrRI%W3B0^gQ(;y$&rv~k6i-njQeck3& zn9z?tFqR)~Ub7gpq?W2qzAPI5x1TsD#VJgjz?YK4FR%vFG}jl$4;FF~mfNJmLg;hB z>lr%!f&@M*F!gj7smpz;QXfYb8cJCR=?OoL8C^{nW8U}lLHW?fJ}DphgHOn3?)$pd z$P{OHf(Fkion2@;|InLXBR5>VTBfl1-U7_GW)sfkt5biu?)u?z&MO%39F~Og$k3}c zVt+AAUHsObGqN3a!2WN4KboyDo*lPsKo_fwNjMnug>mQ0=z8J3)3}TQqpN`IoWvL~ zMv$}|nC+1)qG_7IGvK; zRsFKM`$c3}_O9F4$SRD3jp54!9Xbx#jWbZOrLBDWbB|(-aZ0Y2yG=8)>{1ZeA24Bii z40&|bRpi0PF_Q`fl^2`Q9RIv}BPMLXvs%X2`UWh=;{pSB9X@{g|7Y(#pyWKSGtFDo zsj90w=bX?0x*Iu@009tS6oW`5O4KS?PV1So|*IupNGfiRH(sJP%CdNM~vQU6AtyA$|({?RQ`WO@wiq77eo zypPCinDoj1Q}&zx`G@xJfBz}_!3*z#&KijL#~fW6J)1Fmc=vh>lc|U$lJCcw`=_y? zeMJsOS*L&-3d9ak2fdPttgP%5yFs(Emm3FdSusTon8huvJ$C=5LV`;HJ8|;5ox0KQ z0!tzC?UMwQR5PyNpPwL>Ht|8bkS+_KppBC12oc>3i)5~d=mJ=`arTvmSEA*EcJN@m zy>ztI)~EWMLQ%{h4s%>{@Tc9p1?+Ie(hM8ImlN_vs#_~?4yMJa<}s({m1o>_*HYU7 z;G><28x=c?-~9XjVPZ-Je1h$heQRb%Zl7`)0BaEF>h7ZO0=%>@)MsU}Bi2xV z&HlrmzH0ydFJH1Q0(DAHMS&Yj@r$cVbC^pWhf<0-5ue}$|1rP9^*F{!YMW&~L;CE5 zY$cFLO-Z#&nTEWgD4&{W{`H_v*AcjCX=c&-pwUv`cAlcXS6JjJ0!+%4dl(x(Ca``# zA`l1aL6(cOM2wny6Yy2gN}6{pj_5oK_*WmQu~L{mjvi~U=iX~Xz97cq2a0@a$Ro5y zKm9;>A!fk$OSGj~KBt9MdMCKn*wBC#AjJFX`s^fl*8u+T{W~jd^Ah-ZCZLwVANFG& z#KYU;SOk<_LK8>ilq;FPMc$nE&b-fOpZ*MlR|Czt$c!Gwj85@TjDPYnky%lNMy9zy z9i{mhmO+t0DFy7&O%Yj@9r`e(LI|r6M=GFCqV2||rXFht4W%u*pMtzh+XPdgST9uE zAC?xt44*knbhqxc`wbuHU$an!6czXaLUd2k%J(XZV9CJUKSdEsHh7yCko00SH%O@1x`9IN0 z=9aSsZ_ayfR_Nz{VbPnsT=>r1D+LS0;p8Kjb)v4xu3T?%JBmhFiGfc6(%w!QaaGgGoiUMKC2X;YBMVyuEMWF?ANWTVP zWPyn8iQN@+YbdZwb)ELi8+Bmcfuur^r{7B3>0gbLBPi5pF+T+Sn1BC1YK&rEcy*9IfZ#)>~$#pJISY8+-kt)wd2Hl@C*Nrz93_aC1kDLedNl2DIgdHmgypd+)NcU6k`tUg_`HS9UH({ zD-{tr-r5zF_CJ4NtNq9CzG;;iSylmJX|R8Q;0SCdM6XqAEVd6H@3XGk1d-81#&WQ) zp8y$EOKe{D<#?cRZ=z@_Kl#{H>Q;lWWW+)suB(+9Hwk!GEDv#f9y1%4h>XR@t>+GP zga%2^%0OGCI7W|xbhPQvp!Kt03GydjS8&@PskTW3TjMi7`mW%PqO#bN{Lka2``|9= zXZ9yjw9i6^a#7L#Bx%7MV312Ib8&$t?A(|I>r)6gNY;9!*cwo+z z)kNDg8h8{|`CKA)d(L&aiY4YU0gHe=de2fT%m}#XnnL6<8{#41Qk93(#5b+I^Mq*j zY2?Ymm$R=Hoip#>@}os>-t@IapU>=7frv4*aAJ7EK`T4DdS(T4 z^2X`FBKtA7UAn*tDdckGl>;%8cHqo)J9zZG`;8`cwCLgS2e;Yp{>uF}3FBdh1udME ziRF?@iwv4nrDxl?FWp+g@NI$6DP3A&>A5+Uh~^VkRu`-)mmU_GXpl@oq{91E5D_#% zu4lv`l5+BGA_$if`^(DD1%wjet8xZQdz+``Y~6!tp~YoV&D9BgitjU=X9$e&^9 z1%*~rUSg$7O01}&*ueo?CSqKUTyR27L~Vn(B~7G7;;>2_%O`?->wC8Ftp0IcAq*JstV>EUfKJTubl2~w;YO!jB?p^I3?n-O%)c}$amZsQ8|*SYfCJ>h9WlE)3gY{6 zL*0Ta>Lk_fN`U3Rj#4KqcR_qs2^2@fqlH@$-bc3-*tTs;G1G_bhp(IiV?JTQ=@A?1 zYQqhopB0QZTH#pp+-;HxEf-V)HwkbgbFujT-8@n_Jbp~%8!+)@kn_y5gXh|zVwrNQ z_$X~8#$nfsV`UD;2kjj~>iJCWG&+{&<|f(W_bs)jU#Yczs#21fL<4S8a}Z$0lhYK3 zYed`~oHuc1pGKZ6d^!7S(V6o8Ek9cH=1pH)^!dEKDqt7FhxI3q+xe?)u3%l-Qvwn# zyNiBZ(8)7=CkvCi4YX2Jwa9B%(LsMN>9$Ot{q+k6Xva}v%U$6=_ne6>^wO6f*=frw zitOO=S_=A`tsRqFDLWzHvKY(C(mYqtFKzw@-+cxCtwbz?erJmNFxeX+q8mUsG|3{l z!5G`NX@&hJg&86gkhV)B{U?8_v5BAz0F$_3xkHP$TTck4y7Q-l`2F3JF?P?k)piF3 z{U4mFvx6rt*(C}wM7AdlD{9`X^d$QaJ61WaEO&&NVU{a$w!Rfa(KKa^5es7R8T`y% zOPhf=7BQd9XDBl*7M9MM<#|qM&cP%pE5$=bAp^5nER?kuI&2>~U&rm-)9pG6iupnT zPoxV0MraY>MBD`7<<%27ga%crP_c*@j@b<5&V8%1ZP(6fkZoi392BrOL_`-G0^i(f zlcK>vo`ks%he7)>rdnsE#oaK<72$%4;`4Ii5-MqA z5!+QSD}`ri(3#z;G7@KV5T8>_nG*C?3M|qIq7BniN5U$zHJCbWr@?NENkpj{-B=x8 z0i$m`zKe!hea^&BBNuxbGynhj>o+iS(b9|fuyj2xOsLu7w#YT=rJf~HIw>>02r&N= z_^q1M1W&|9uj`VSN zA#yJN@P8x0E09;Djr?H!#c8&pD2a9{WK!Du?PBu~=0B9cDRIOnGPs9Rw(rO_cfa7P zu~09ZQ~mh9%wd`0T&xpdJXYK*2;I@T{ZQJ35Wpm~vB=q*dPi;R(o}l@l$FXtUwHMj zohO=|9VZsa7N~F$)cB$Gr#Fn`PS?g=YP29&6~cq==1qM)$^H;r9G80 z^8q0hBS#AqIVD7%B_L6MvxypB<%?4&g6PDQjrewR`eFCipY-A0V2q+7E^=H-%Y%E$B?F-4UWuR0^h(aWWf*<;@y=rP%FuEztVBi zK%?n#t4-%1;ngDd!x#607rtPr-Z5*Tu2u`UKL5FFtV#}frQj95uMkmG1(Ft|Jtu@? z7caNl0L29H__^EGm5>ikgci8XF1A4FOJ-sW6L+i^)0y;<(ngUgJOr44q1ZkXfmF(8 zRS;7!O3}`CaDdfC0ekp?)r`H@UIs&P()0kACl+PzC0DPGv0f{zE#BZCK^5BUa>I^wzIWcIe+{AAu4^Wp60^WI+k z=1t$Z>5ch6p0`hZFYHRk6hb;n5r=AJwMnx?C%Pzj8rv|VNUaGv88Knq*Jl4HAmvgm z;G~maxY&2_oc;U%{5ST>TL;m&18!gQ^U1S6T=YZ~wK|4sP31!iyDh$|%=ig=@!eDQ zgXiCYi&>17B0)n?7j5yFj7$Tkk(IlTE<(|3k+A8S=SQ_Q3YssPjMS)G59u-y*U9I; z)iLHDQv1E$*lK_DS1;OM{CK}5O%7WZWt0lQ{oI7tT@R@vY+|Q<@k>WwJSk02uq73_ zn6=|Bcr{7@YJGXKRaX^B*N_H`v<)>{p-c?+BD}pb>=%5fg-?-T9!`J>glSuESqc%|V-Kz*-5O_a?>XmUM!7!9Gf6>(#AVgh;`SNFl9Lk9rUi8_h!ruRKW6s2 z-_8FM`$unHwJr4n_TaW+D+M|jpeA@VWlkTE9~%Px6->_}A{}8)luwrmH|{x{{9~BX zJMUg$%}s>jG4a-{&U2L+fBOzpAoN=b~Fkx)-GLZwKOzu7lFVb>Wt@te33)^Z2wC85+Mgk7sosl zXogt#@fQXKw{O%T-oY7)bAP}Wm zxgSzz0*$B!ftT+7{9VQ=wk8wKCxTFa{G-$M&>h{jY2z|mR+(eJbpN!yap;D%0jbQS zB10;Fl9T7KmYWi^H#x})%)MpHi|y6dj=Bn!El|^j$csIDpuw_9Xa_Yp+=I#5hdGVe zBGbxkdVjG%Mn7<$xfk>PEP8Y1<=ne-&*uGT?&<8uvrpXNwHo$gs-~m84jn#gKLntl zt_^O4nXH9DXl@2!N5IEZn(UURJaZJ8oa302?P%f@(mbh@Bpy6;#$GsZ9-gV7l>prn zah-f$-M9e)J?%Y1kf$-}0fs2b?UDb85QxLemHV-8F=d8X1XI%|>?f}sv1i{oP5aAC z*A_+Y*)T=mH#!F#I3?K|iLQ$x_pQAr?5|!q>ijG5G*jVB8U?eB$tg6Nn>p-1>IU?I ztO~Fg2$t6qY%-+;uikoKW^Pi!r1P{_IlW+<9T zsB0o+eA1MN8jGKoVhC1tm*Y-E1IqyFqZT}kfZbOR-u!}OAd*+?`S%-KwVQIs!)=(& z;PHw0hZ%OOSCLwnDVE&Z}ElWtBMlGg~nrkz=pf^%mBPMSlkx#$ z=iRGp&8j@u36g9d{Z0>F?xB$rbURG!32u&$Lgv9SOzC~K_CI}fn{D2>+@5{$s6Fx6 z2HU=^+(ofpJOb|&LY&B?W;D35Jo*u0RyY?1yye+(`g7M8JxBgs^ybXVxp(KD&HK^Z z)7g(_pUi$H0T#bg585L!5V9f_Axtrn8ceRWzg@vAIvuD}h5VL}+St9U4w2SL(_*s^+O{M?G9L?( z+_j5+c3!0W+;txT6qUNgv5zjkC-YfBoCGvQK7t$_K55UM{xOGhju!JrFUPq7pv(r@ z#{`yy`ZuM)NHWdha+&C9h=+D!1*0spYo$c;N z^tq4v?$uD@6clD!D~rzi^?i0vd64;C>Tt|*D^!o$M)VjD*O|?7m!y4lEgDC+PZk0F zJ58=V5fF&2*MN5 zz|04ohfHb?;*R6u7n0~(ZJNe>=1BZU+OMP9$x&tI*qvyIBUEOrT-gtxKZQnHLHoi( zE3NqC4SW4av-Q9=oPmumlPnYP!imOSTYj|8w(nSO>sOcA_kMWPe(jrEZP$)UXHLIK zz$+&$)0xhipkZb}cmPBXUYPt$)=JPXC2jfJW&MH#l=FStaglwez3%rb*4XxMBj~o=F`| z(otdM@*E=baw*!#(T>@@+g4Dx5J%eRIwgaJ#2H}K#E;Da6EHN2_Ep-5>(b@~m>7^! zKZ3)e+d-QV6Jk!RTP-b~W*08BJ4Txz0FNjUohV?Xg=c#tF+R?4X58K4fINWGL4YL> za&b6!Ef!S$DOe_LuX}jQ&0Qx8Grx%)>uf>eL?&o*euCY=oUSLJlL-*N4(MP?N}}Dh zwb%;sQtZtGSM6Nuh-CxpkoL%==>4rDjaF8cW1Hy}a~?p*Q$IXx-+pqd-M72SnOpnM zcUVq(j+>wntwO+uAi*^08{V8bKh4lvo+@w7`(Wnj+&gp6Zu#p4A1`>Z@aue}$t%`P z{r3;H>89}z`=Aumn1C1BqNftQKYZttY}%Iud7SffT^FK1i|$7|j=skZwb1{aHjX1r z4 zFWip_ENa~5wtiQj;DLE{az=o)U^~sL{Sh@5KuJ(ozgyJQli6d%#c6Ovci9hKz2NA8 z<0kr{2A-jST_n7bOO41`RDeBk%sKMPTCk(t8K{17{q2>M z?<8`jUl8plR3g!y%z5XP!2?N18q$a zE-P}#Q^G*ZxD^X7i{D3ryO_`jr{I{;AfsMOOGnM;h%YP&j%;p0A-W#N;^fONHeX)3 zdF8AtSF0#l2*5_bJ7skpFcZ>-BrhL2&E_o4<@y1DlHD3Gt12wi1z(>zyf)iqYb`ix7l)%%P zi2wjV07*naR3Va^^J)}iCfsu3EqarebMMSOi(cGY8UYF1Oz*5J)KnRVZjjA(K4`oLQgSMnpgi3Lk6si1;=;Fl`AJqZAJK#0Fk zL#FN2=z!zHJ<0`#Mka0TibC5-@1Pe>^w?iNbHuLDiLYvTmVNt+YwXUYlosMU_~=-^ z=kRswhD&$#szUoEc%}c~aHs8g_cT==adhdcu?nDxt5BL2#TqnA+Fqr8JUnnPmknA5`3cCLAp)*G#knP6>s3Mr99>l}@> zKYsRu6@J0O38BLqN*IWZAkJ5B6PW|7eGa^X7*UoDt&3qD%#V!_vLzxb4mfV3}x zpGdoubjNu`yw%pwWkhmtiI~m~+M*!i_U`*v>=KHpI3EU0Ubl6CO9#*Fh4f!ENt$g= zSST*>QSTne%(ITMI3SW4#C2AP^1mCvumbnr1&Z&}=_=_K>yF9DCEo0{h12tL=$Zx%T@9T8Ql3u!{0j+X?ed8u^zBKe;MtdjPb^K05W76v%%U@U0bI+x%i-;XuV%leCksAW z@M6K&Zol~Sjer6^B3Ts0lW23mve^=_`(^FY=-IRhd^Co9mBi6ufO!;5= z(wZ3!%+C}V(}|4B8~_8F92>UN*9U+~wpme8n$-XV?}P(6p43GtfcG;k6ZWUi9JRxT zE?ah1(4P4GD*KNQF1Hunu7ieU#5S)lwJJ~p@tDca@4s$GKd6VMHrbwdu!_nLIv&I( zSyC=!0IYHeso4Y_fLzWGog;$_#c<)P1!J?|qXjP(eC_s&PvHo-$v%g?60rpCDIF)X z9cxB6EmK#(jMCd1vOPy`kUfckq=E+km0|L~EzH$K(mzv3vlvdqs3GA^rZA@$(uz{b zY?Vq)f}Q5gch1}SE8Pw^K8o;;lL8W*ta!2%_>v<0WZGAOEPjgss|S}%=osWmuuKJZ z<;y#3A{FYY>=H}NFSq3UQVS)dIzF#&@2;@V-CxY26g8o_uL3Qo3~dVLfe^GQF_X~h zpnXrCX>_K>nwnf^m5)(9p}b{I3K2Q4-~Q_LdVB8q!wy1s-|k9#j7apkbJv}Ty>m0Q zqbxH4YB8UAyWUPyYq=D^`HB0N*)+cIM0~R24RW=_oNR<|8oP!gEfm9ruNF+h1s^SV zvEXaBUwk@8K#^K+>`c)<{_hl#;*7*tsBv-uYK%KU72C!kxSg8^CS5)|2hg_wF+IJ* zpb&}SkaAU(kMl)N2=A0(}L($rC{GzW>H03&0yB z{ve0c;=;zEmJ*aLl1O(a=1%eB|9t%5ef&Odf8!T!1n?7Mh|ap)F9O^%;k9j*X_ij& z@hMU?*_1wBg9CiuIVf_13Dz+XvI5$~2rk=!`K+RbOyW5cn9gzZR`x@t5Q?EVA8q`^ z!z^$s&Bv(!jW%0%b`1e%v-IX96{ejuw0XKNBbd2M}Ziam5smCFoWy4Yba9%!;Njh&eA()tkzb|%0Sm`(Bj zjP`X~LYRilqtkZwd?V-+NZxC5TmiGg1QTu_>80qI{IRMoh{S`ZK12HGlsl0iJ!BLl z*tn+1a_~76G*3(n+EXu{u`8F_VSLE9uk0+hen{WE@COBns>z&I4<-T8f zS(%-E@)2LY{n4jx1f2GzG6*+KQDe3Jkr-7i%?6+WVhWssV4i!AG+?e`qN3qK___Hx z$>d&*hVS^lyr%$|_K}#DVH0ry0HP4lJ+RCwD>Lo%=@$FZ-s=Q$scynoP9QZU(^mxW zPG~{POv`*0YG!@_>Xw7eL8Yw z3+pL+OmcYZKYi|ub+ZsH2}aA@VI`3JU~@arlH38h0rs^84=^0Uo7@LGw8?GntC23223fDaMB$7NJRihG?3(300PT z^`0fbiSzB^#ddq|##TOMu9n2|0_wh&nk(}{;FV#rG#S8u_ z7^N#?WzMU!#UO2MX@G0rxOa&?^uP-D{g+=oW8Z)Kiutg7ePg{g*xJZ9TpW7tcv>CQ zX?=3I4-MM|uw%lm(?sh%X;W1#_wwA*mROCqG6+lSD-j5e?JZO`M z5HC7Go$9R2&OVvDfZNYLBO{C1pUHf$)RS8uO9gUcr!mk1zfoZl)>E5dro zs$-+nNE5`8%s6z_PdV~jK}3LA7^Hy}AeIm-Se%^{W54{^3cKTuGD=kY?Qeg4%w9j) z>a5-HV5bcG6SXY9nE$#~e9&t`!2e5VSD4loKY{ zI5<-=>uHm=4s|rxQ1ca5g$7IWfI`JA`4a+MZ@h8BIq4fV6xlZ)uCmJ9M7VNetYOe= z&%b<%I@=MudwZolus$DKKbDpz2yr$*4-ha8@98x0JRzQy+1V%V9B%*lY>j|R9f6h- zWYSO3zEVd8%*)c!EX-$>2u|7|NYn=@^hiK^YJLx+feW&rFG7oU(n4i`*Ag1-s|Azv z(argG=baS@%n(F$=jq=IT@EFlWrtR)RDz zivxnI$Az8|TU(k$tD1FIfeC-+OtXFW*%NjF3ZVQ1dJ%WQ9NT=&MqB8v+1ZTrQkxnr zbBZ25qJ<%`MhlPP=O#lZbD?bn_R3}l%Gd}=buZ*+@vM3d?l`zuW`&?c=@;^m%DFQmF-%QZEYmY6DfXh zxM?A_fU`MGj1O~L^G5H`?SExHM~n6ao$MocRYR}eEc!A@IBG98+Xq+rEuDz8&`x?Y zM5-u12jCF$+=~Ajht^a6wGkz9|LRQJNmZTFO+SK&u9=`tN(|j6`zX8t7a^8SiU}PX zrA%J2aftmSQe{U_>XVqzIxzECT-(n4=NecGoC&QvItDe)cedo&7amy)l@jCt@7CFO zU&4wdWtHw3##L>!VdQJ1{hI3?JTcNsmWSoag9`V|B1qUH(k91Tu&{BES?URs9G_~( z&NNwdb&2bhv>y)X$#L?$ME=J6f{s5Z!XYF)DYPN1D#@I1F{bd_2d`OCaW)lBm^zpv z+cBHf%Hs9+uGwG0MHCl%%)a>e7JKNv8dpnv1WvAO5HK#}E{lNknV9Z{EdfxgR)X8x zXL|%B1j0Ror}w3%!%>}xs~2mP<#ZdQP+4%veKaFTq+(9dUInZOIl=V|p+R;s*l5W3 zp?giGFu$dL)OIXObttP4ezAz?>RJXZD^B=kYIzCjdH{$_Lu8*oU{yTcBBC2Xdn>3F ztt@i$lH+{nhAc#aWtjY=tGuGSh1t?O4zmXfi)8yD(nDorZj`}!?d@~6??SiHbIp|~ z_II?{ILsbnV69~pdnlBcCX*AJ0J1~1Zmz1y2_DZSB+5?#?si%jlCKn+AD?O*w(Zy2 zY-v@YZCILVZ=IxQAI85Byt^@&+k#_G!rZ93U!Bn~i$hYr&zeJVb`Y55qmOK+(0u?L z=@99rLi+}TSwe57|FWkZEa*}D0z&*K4tr?)w4I~UBLlu^t!x@3mQg4@MKUHK{?K8% z{lTYw1ejM5-#5~2!H4-g7)E$=60M{J;$J`Qh|b_Mn*`Ls}&Q8>W9Z6 z01P3(>eJwOw44y%N~>tGQIUmm%;a{N$HFrw=NFsEA6w|q@TCo^PmVNNI|FFy&wg~; z8eyQ%iI4cZg9L{|&SY){n*mq2Q(&?}BggXw!B?i2Ew`lN<>t??G+$1sL!&5w6eAV_ zXG#xHaiL%q%=P#cP4vVmf{9>Vc^bYjfhR)vF$|~@>I#cRV41YsWW^X|5W-YA`6(TI z4Z^QMR-C);T486d4cMRm^#RPCZdKm8jZPt4gr!CT;%**D)x8MT)Z-M4|jw zS#cwny#@HcD#X7IlT1yL2Su?GjqHPnuGU^Z(P}vfv^}Agcch)7{2o{&F;z8}r9tJZ zCQ_)Qsv$9WiegCh0j}w{%jxn3Y2oPR&NTw@j8BO`A|rTaAd$GEBhxYVnmkq*@@VAG5&&JxCyBOY38UsU0OPc# z5VfY57O!+q*n96?K+AeTxva6H?Njzge|yy4hY&ym`76-zC_;E(|2ZIVe)}p&m<%9q zLn?j{ZdygmK;2?yiyvgO+}=JbBM=E(C6Z#KCYB-?5AABk(Z0L3l#<)^5oB$JNF6Ti z7`VFndffaY`Xr;!QT68Kra*HvZ5>?$_N!l5O@U3&-ltdZPY&Y>`spi$!WowELWeUU zB06b138I2c*vIO~AjVP=+zSFJ4eS6JN+Zp;ov{+6WMnd{SVu}RkWVF1Zjp6QCt3=o z_;((yagfN)j$XTXq1i1ADIyMJKV!I|>dQP%T2`5$2&1cjBl8xBnVatY<~*S7*PCnx-acN^^4A0Hy6G-&tT zzY?Z|4Cs95p~{N+1QkpHzt2V~evlByv(Q9}AB5HttnIcCe-;E-rgM}bBc3dUe8^t< zGu^Q)-KuMf@oT584tg7pH0IcltI-uXol-L*L(PR*RsQcNoLE~olvo8cv&W7#+K={K zrwa)R3i$AFI~1_6NUD{n$QNC~0oqrQV^QA($N?*AE#_4LFof85X(YvroN!6lb)I0e z3GT`*_2rgRcwcTl$`hN(u&jdF=9j*-)@oMdx{iha?Wtqd)S^Din#u&Ul$JvI3DPW9 z4+YU&n(9Mta_pU3N-Q4BckS{t`U7>?*~>IBBSNQsNXgjgK9yN1xWz>f@`8mv){)zt zp%u#m52V|=>RdZZ7jqAoO*3HCkh}2%b+-nya`d!L%3^M&` z1W*kHVtsxTjF?cLdf|MlLs=zJbq8Vz7D)-O0!0WfRe9RnqJf1eMd3_n zsvaZ;Dv}WV5ti(T29^Np9Odtdh6i_2gcTCt05P1Ygd}Q;J@)X1JiB{G73UFS?^Bm7 zqR4BbKqy6H%%%*D77Z6fmRA2z-`aiM{qer__8I7NVE@ldwB0)@>^omsXTSbvwQX9S z<8Yy!kcW=bp)OXvPeHvXqL)S&yQ3Go9K5oUR*eVx%qKJ2g~(@MkX)FAe*&(p z2~6ps?lwy&xNzdeupNcXG7YDC_vRv!?UR;6Tab_?+W&Z=)?R(}gj?NGQv8JM%_^5< z+n4XDv`M;=t7)=K5#greRffpIaa$A5-Ox|tGnX?Z5EM@!C;{P(XP)&CZ5Bi~uYfEF z{D@btcSXuwK{AVAUwyq?Utp9*2tM;Hgf;>9483GmQB*&qJ+3#5uN;Ek8c5=JClBVR zG@q0MD%HhvR5Y*S6RrZp5fQWza=?7aeJ_G(7BW$&FbMGR%N4It6;V=Nv5mwg+oUJf zzIA`4eQpL4`4XwBr}s9vK2t?lrH-JGBg(&aiacs5>&3?yn6WP&>#~HiBeo=U+*TvB z6%~2#2<6&xiukva?5?}qL36DxYv>MHEdE9k_{}8pXRWd`=P^$jm?JIPTp!gv#a+S{PK*LXsii}%MKC9vF?Nc)X zP7C5sI&wLLBao4e@W$Haid5=+i=64%O;q_@eYXp;PO9O!%vk(Sq57uK)E*+nh52ce zxO%|o_u7x&xJVv%(gKqaBDyhz*9D3&SzXG~Nf8=VS{31S2f>6+1bn2AR0}K+2kO_Q znIycj4&qo?lp+#`Rsyi#u8BA+A@cp$y~}M0sH*11etYSy3wEw$ls;psIs&{wFid%6 z?N`MXKkXK??%{vFJrD@)YU>#dAFk{6Ae5egE_%Fj-Z|7hR^ltHSc;a-LHlyT?Z7Dq zNQ93tlz#`gC1X&8YS)0v*d3F!qa+9ejI53(0c_1HbjEr+0#Watvj%J!UTw{$Az z)T2rQ9IxMyNl~xf&u=NTO`9sgw; zQdMz8kw?8g+p;nbOEtw#pKq~dpqPna`ehB!$c+i7K44;)Nk;2>=>gp_9%Eae;ra3- zt0}HXv2)PaKK1fBx^RqHHVcVJ03;8CX!EixA5F*etgU^(PSHdN)y}tv zjN%ceg?&h&5Lijzt_4*~B;OW8(f|8YLXCikNrRtSy>0SYNqyw?4qq7{sNkbSF%iOT z{1ok1N0J7X=D)3p-FW;W|Is~FYBFAaFO_P6tO9(=7<*`Qp{-tB>a5FA^1BD9*X^ch znM!qWO-0okK4c4AOC`hX7RKV?{AV5k%F5Ph3b%$;em6W5Bb(&Wr25L$s zG3Bp5Om+$I7-sODtMXmToD<-ayFqYiKZ00_H(E@q3bKv^_!z?He)Nt)``mpi9dc{` zfjWEot$H^v38T4E-AO2TM9x0|t!)Vr^yPH>?4ZHgNx0Pml<_L~8;OLgCCg1#<*WeH zBLWi_O*uA9;7Lhuv{)XFzc_F&F#^YKT(P3$8@7_Dv6>?n73VM@6}D;pwB30*hiG&c zO#KtK0uy&H&5_moNpvJJK;6cu5{Z;0_K}8SG+8cPsUoY(1n{)%K!&~c-c=JZ{Hm3O zwi#3U#Pxp5q5DG!T&T>H5`^~X^%1+?e$4LQT48I}Rnoqt(iLRC4ypVIYe{N;JVCO6 zt4#3{@z(0)R#a9w7YMkml7I2!Smvt&SIYSk>j=;}L{?jMe!$kPDUDdQ2x~{jfL%aw zh@*U(g*}G3s~%1*gOhewRfgTOs|MdUmOQJGC#KgmD5{{?W50bI3c zc=pafB9UAh=!($J3WcQ>MV@J5Ozbn-ok3bzAS&UdU9Q$Cz`0Xf{7fapZe@_qI@T+w zR-Zd@m1iXZlT5>}9i^!F?b98$A6A2YDm|wyj zVeKSL931PEE zP%!7$xKq9T=NDiE6hU^Sg39?q>k6|v6WwEXGe?ra2B;h`NZH_}tGI4(Qzc^+PEzHT zKxDd&+Vj;#L3;H9kwh+UG<47#DVzK+=_U1-nj*aks!17)xh7`w21T+Q6<~ykN&$dK zbR%Kk@>fU6OT__9@^}Mi{RB+vRs<5658=g_a?Er= zk-07cyx3s6O{HgGjjG>s#7b2`zsd^H|8C)s|Nn7YtZMVsCPi1O(7PtS?Cvqb;iJIR z;^4FLX6i{R%2pEJM zpC7+DmvedXL>H^+QHQHuwk*>!(9oqPZrGbAS}fj|?y%Q!Ff)wsm;m@KEUAkua;%6p z{B9u?b*v>LC)%CH9 zTH3O7agnd&J8|~XD<^CjL=@9@$&@#6?C&`e7I#zA+J$$5@)|Rv zpU5$SEXqzF!j{YWHxlripUX+0o^f zrA(-sS8!KyCS~GcLM#^2>MDwm0CQC4Cl9yj-{@nWi9hqH{)yeWp};=4Fkl0n3>wb3 z_;vLgU7#LH&v+5&Nzf@1y-7C0z$Sn)5p*)0D4$BB4mFQi(TS^06L)myC{{yU2*L&1q_!a)*^C)#NPV{Ywh8OH`p$IcLm;`Njj^` zES5trw#;DxN?582@jKok)#Ue`wY%?L1L(x-(q36qH|?iK>pmK)r35lrX#6&eNiD{H zX=9P~IsRU5oLlnd4aDuI|1?HmHgH9ioDVRB+MBfDzkX|H30VmGEg!s0RwC%u;8V5j zn6~PiNb_={xe4A#uik<}x@>;XV1KyxhJCq)X7dyZ24o5RPI6I@ju>7V~)~ zbOZ+trxw2M7y>I%>Y!`adI2|k~`w;iv>?&E9uK1j< zE)67~74uUQ--|!%1!*O%tP(;&8UwIrRHGG-*7evOn=xnT=Ki-YoU$;T47WmD=bC_5 zW}}s}?JhWo>d?yP$SaH8a+fD;lk;rpR{j+m{a0ESbD((pVf>FBt;%71fF6T>zLY)Yl_D#>Gc^))QFjTBtOIsAIvTIbbty@=N zO%%b@w!(EqhGY~CHbGqF$%m?}q9Vgio@}-s6`5T7AOm_y_t4IU$xnz9dx90z1;q%xe607oCCzMY``$n{I1W7du zQDlz}kRj8T3wJn8Ad)UeMZPQ<;piWagZ|^XJ@DXKyJzb%``zbjt#N;|r2-URO{WG? z@f4S2+YW+H8_>!(8qvy^I;<8L=5=Z}MTqBPKkuSJ3yZStj!oru@mdf0HVC{(imT3e zyqC0=f&pAZ5Y3%Ofa8Z?S*6LhY^|XXdK`9-kZoLFL_1Un1NL6B<8T{gk%mY?lgp%5 zkjw2y0WKD$+X1eH6XNIgN*Yh88>~P@ot3_s##Iw|Xg4lW3~`#h?_IKrQi#{7ojqII z<`!+8Z{KjpzH#3YtAV@x!i6^b;XCz2cw#UZD@48Ui5*{PW7c({LnIJ+O!59-> zpWSA5%0)W>x5FcIQ0)0wQaB1Swf79$ipm_)qf@gAP@%X;yn}_WL`P@dDOpOi> zQ;if)Z`Djk|GB&@!}2M#9))MRk4lj@8V0N^VS<~H58^A{4%d>{#{bbpP2oR8Dl@PM z2!zE`7aD|b`h&U-%cH`nv@9EV=YUhU{=+(z;*43w-l@ch3}aSk(;kz zTGWivXx`p_ZX*yeovCVb4ZMmh2%4#7G{zp;Twv?hm)JSL69>?&s^1-?82`;f*SUu= zw7DI#FK;gas8I_4bB{gs3cY%{zhaS8XluvjG6XmbLq~(Fr~}Unu0W-NkVA-tX8smk zM1be21W-MQ6agReB-nB~la!Uxa)n^lx-}(^bNaP6&)84kigefTQvB->9AojzaNYF*@yRgNXJ*Aj}ctA(kCg0`GSX>T3B zVWnWRmo5beK0FF7=#XVXs;wlw218M753AucTG;3Jn-3HFDE?3(&77CPfZ0hx`~YQ( z#f9m>?Q%(!119epwuXUeOGye4t)_Z|mDT0jwAyJ=(&+sZE8l|Qy#3#FUot9AlwFG!?t z*Y(g{Zo-NzFUOLDIIo?C;6HlllpUmiLIeQQxRpb#Hyk^w)4W)BVWlr`Wuog^mER^X zoB+y;GCq7?h}%~dAeAw8{9FrGF28ksyNUe>-s$G%f+3z0;5$G6tJ`z)lXr~_OokCI z57il-34WvtbSuc>lhAyR?hE0TAbH4z3Az@`%GF2P#TCo)fma66gwS7tl!>7MlscbN zwhRXIS&dGTcm3p1>0SvF0Xb13{DA;O$uSp+PufuQLeA@Yat zi3wAT4C3Q)O@^m=dq`*$7z4eKmAZ_!>9>6PF};{|d{EH;HgeW1Euf~}~p(c2-#*IpJq$7|=Q}<@#2u)US_ux3(gM z*h`+n^B=v`X(>P-N1)1?=%WF*x_`L29r1S~RYb&fI0s)&i7S}#53kOS`+#415>wqg-iQFJ zn&~)}#uOl?a0vVaDbPt(+W}Bnw9N^yzw*KDD{9JjCB(;uYcF?r;QR5!vQmw?L^nBG zCjIO-UwGY{k&{$sK_%T2iB31NS{0LrTY@P)0^IB@<$^(asE$*SGzwLTiW*|45M-=k zCC7na+li}vcIJGu^|Vp&fFR}2IbG!3@;L&avXZF+xrDFW&+4k)Hwl;wegrTULH4j} zPBS2Wz#h|>?5F9DSPH;n^;)_-@cKVJbJ8-W$E*zVx(X<00X?0rLmS#nc~?>ryh`}S z4vL93m+(3WW@NU_UiR%Lf4>pXa7xQ0q8Vk*x>7tQvbIRhS8z$9&R~hvW~YN9fSoG| zdXhG}0Z8XhUa7NtmZjO|jpZ(*@%!&wv+u0SvIp*6NvFU`v>`-v;1jZGIm61J9_el-Dm@PJ2hxSwywf^|1MG+}S;tGDwov=;g&Nf9;MXgiDqs3+k)il)S)7fXE(0$D{}a30l4lS-U}dKsF= zk3f_9{gECrD!3NZZIqn$#kwXd1v4#n{X#zfomcA3+S@G$ZN3~KURsjL0u{2l&M^XK z@FW2?L9IKJTH4r|ENJ7~c)o^zi{vp{hUNw+ zuAz)jMfOByoFce;b1BD;wf(eK83onn8R;Q9jQ>lDM?xWASwUMZ9x6|j_78%$?x(C( z{LfF`zZ7Eia)=lQ9aE%w6`dh?HZnwo1hmP+tq3no4dz%gJ}j!eaO7OwFacEwa7X3QYfL~oKtAvQ3A0ZG_d&OlzsU~0k$mlh;jfT(2e@Dva> zHHZ?_jg^$Zg~I(kp)gRkW~(S7P)3ff6fEqY9qX{Rdi)^Il$BTHI$U=;(ad^mq#^n< zDZnK&3P;Fk1()ET4R9^E_}ec&;Rr|(MbSllBh!{wm}-}6FVcQC4st{C`(+X;7g_-=L0=W>pMf?8s zrPD(uo&Z$5shVTd70WA{EU8awb^?^l(q%=qnofiV zi9kkM&@(0w4Q!5A5OLnl!LW2 z1H@qEEHBT7f-}>$(%ZHEYKO}!i-vO?-zS~iUv6rmb>NFX`_c(}@(Y_B4>b{XdkzMK zr{8UGq-MK!RNJ;~r7Q}m_U8V}b`n!Rn+YTY*D&sYz#sBy6s^?6xSei_-v3Yjui_&K zAed?|T(ke{zx-?4ao1)_|E}3@{mx&)1Jz;Gn7Gs636%2{!=%gkmZjL*HRZr1hiu>R zW@m1%qt~xeh0V=fbikxZJnWNiqM6@3)kfYGlJ#Dd-a$(PKq3w;Harna2L_OXWHCA^ zQ|-kc&WDq2Sb|1AR+$q~KgDyu6KLZT%!U<`XmBgW<~^A1vyezSJN)?FYc}lMEx;_h#5?+V$j zWd(`hy!>=eb7Qxsv3nE}Y&dC^P7>%LYDUjV@q+y$!kiA#HRa9_`d~6z7y^K$gx-sb zv#g7#od^N^G*VVolFS0PYO!B85D19NEn~8);6XUmaU6M9E{HHSlag8v;3O$IV9&h* zXEfas<00wJB)Y5!b`{Xg%6y3Lh(~n-t!wC`1d^NAM(>-R=2n`r<(U90bhHBTHEHc6 z+-om1S~41V85(^#wU|L}%K2t)FfhI(f@QiEmu}KPN2AobQ6E3L3&!TN`a*tgkU)p1 zYo7ep!}j>&57?=5m#w5I&%XYp-S9GZ+sW&LR#;k!-&q7SkAM!E=_{YBfu#``MQ2MoUa-vWZ7r-)cz zYU;D3@CY#&aQ;|(&gVsN)%_!hV~cMsL?MLwBJJK)?NW?y@3~+vkRpn~#Lpo`xq&o~ z%>IL?n$63+og$Vq){A12iMu$^`!P2?s)3cN(nAcD8|gVF5Y$;RG$JU7LBTl_8YMSp zLL+5zS7YMBalsTX>DxUq)!U!k-ZK%qE89OEuB^=QjIi9C2K?ZA zhnsoG&UQ~*QE55BqdZpt|1gF3>(-S3#%Q%yKWK5|wxJ@~Rzg~*e!c+d-|O# zj)-mwS8SMeBjdniHOXbY#Sn~AP;(dlZ(^d~-h*a#0G~B>9Bww^F7kU_c_PA_NcWGP zX&QpVj`8)+RngR}m~$Mm=TQ>-YDp0h!;yuVNPnb_Ye;PkkJ~}ojmA%f+`{1mn7Qm4 z8GPcq9MPU~H(jn7Gg|e-8?iFdnA_(rwtMxHnSnsB2S^gQ}inIm9KUh6(t2 zJI1ne?V$1uLbDe8w$o@=(w<_-cEQ?4U>IYL~GR$hWuUW$vb7eIS2SlF5> zgqYS9U2VOz)R=HQT&h35akfcgQ8gN8(JvM~!ibYa2 zy&_NdQ}{6DOSMe!xpzT!H$pCW4=q;Wh)W$dPjEArK$^_k0SY8?@u%0UEV7>75f=Sc14!(&qg=nabkt9A)0x*10fxl` z0UqR9H&ta3=Sj8NOKsK$+eiEarH{CzQg)hWj_Hzfm%Bl3QAqhcaS>YC+=Uy{Ytg{n8zp4 z+^Q}rNQtp+2x5Tr&}Ev!KmA&*TR`I+5uFfEXkSu7nm;Of5MxI_HM-SMx2{=TLIFds z9XQuvsRS`G3UG^j7D!FA$%JHhwbVE}AME@pTr-~?K61sLdcDrZ$a18{fvtuXN*i1i zR+{anY_`x*-W&lil;jzM0G?nh$9C2tbM>d$B55RbYe;u6;eKk}*Hapsm7Qi6xz1*+ zfCOrmBh^bG$T6UgV!??gM=i4-+MaN1dXaa?;`hX4Rc_yow%kPqC!C)W=YavzqvlGd zFryWXRwCK8bfAXvCPc_0;nhVrUl`4$@O*%@QX2@U6(F;+$;UM|bXgB0k|5qJqRX>d z*qNpChkzaPo-4P)<`-Bag$3bq?-bg1oazs#O)$d_5eQN1NEUp|bMm@C(gsGS=t|cM zZ&8zVw{>EQODhL3<>52RNOKT4b$-atN2j991pQN%V z!$zRCz0@@Up;@9!H_4=y52Gz=Qr}KD&D}d6!gA?iw>|l_t@g{`c>*%IYzp8RzW|g- z#4!HdZ~wqNX+g^_USfU(PTeT)S(9U10ZKFg*m-X6HB08+c0tkf(4Fu%6XR&0Pu4TE z`y7V7)DIDz8p=n26EMIqFNIka?M@&IGaXiptt)e^oV@=zQa-iNL#2pohk4|KeyJbV zP6G7A?h4zneW|N1dgHBg_T0fn%2!zkXjDH+np4$EDj)14CA%E%a{)qbH1^mD3ULVU zk`nE3i-&w_w~)^b!N)#}6m1|QnEZZHSp6`KY{2~!{-KVbTN488CvYr9r}V1$wi2MI zP0lO9%E-4qNOvIZ^X4VR?up4R+p?YL@UC!-PmM}FHOulm2?_Cb`XVMN88u^oCItL< z+HxVNBXXv*Qq0T9b74JIhbvzg23adej>| z!4SwB)D<@=js2Y`v0q7;e~F5;3AdlTuFi=NVv_^Zq7Z|xoQC-p!%e!xs&x1QXs;_R zfJ)HHMA!pCzso_S%2?gJ-OAS%$^I))L4qayj2@YI&9ORgmgs%JI5M4Gv;0J-jiO8rw=60{5(T zpH02A`$TXCWHy60R^KAcA8pED_`obnh~ZAP-5X1AyOQk?klY^p)&LRg2y4ca6%il# z+C$ZFYUR_`r_X-;@@YGGsh3m~)1ScFuzDg%tF!RO1JPC6(pA7HD?svHxz=rGc|-zY z^i3j=rTKeH%k(4ewDV_~&#u1{S(^bUnb%<{=8-170>cPc3=5!;$fJ^OM70eQ1?;+oqB|vC|BK`W^+D%$G44Wv1q`YF6X~K|fIdjV6^gogf+~^olwz z%uUoqGghXr3h;>}i&1Zk(0*o8jvYDE!hn@S+(l0IL^FA`DOR3z(nqN-l_XI4T%;{} zrM0y7*_G?uoU6U8Zm>FV)4um+y*1*u z@7z(tqa3q6)!qPwbG8Z2E`ly143E(Fh%kV36M1dN<}a5(v-vZ&2{ku`@Lp@4vful! ze_^;~EOr6=^S}B%7T{Q_#76D<(Q6jmy}?p4b6qbjm~ZS0TZ#ed1nuCVYj%z-z!YP5 z&x#DYa|^s@#1BuyHmMY0I_*+MV75?k{9Laff{_SZL)2Ey5C+}Qx7Ga)`eRoAl07Z7^;x8Ep5OElp-ic&1 zw5h4Lc-rQQd60!UVQ}C1M1SNPYL2k*dn7ZwoM7yB_-S*@_LBidX|uK83L(v@*3fHV2~3Ck(m25 zL0zL6cc>5hGm}yx%Bu;UC@tJS1vyUlwpzI8CI}r9l2Bne_;Cf49|jWy20MhH z_E`O;R%cojmq1JaEl&yNa!q9x1rg*3@o5GaupfgQ>H!dvK{{j^<&evlMZN#GVCkg{?6Ud9o=i+{oeCdPtJG8&O5EW zqs#vIFJ1&=oN1{Aq>Tt%sq^HfC26*MXN`5@X8mMOJ)j(dR#jSK2&=Yg!RTeC{h$^`0A_pz&;Q@#@9=^BA!GXyX zh4;VT;(g)GvwLFIT}^_iUckvr#=2`=wq?tNm6BQsBs6e>sCrgYMa{&_G3D4SW(4bI ziE|etjT&i7+G9R~U`cRQeQ>&oelTSOi1O|IGe9bd?x~;BcrRdX_Uj_g((a2k355a$ zs;vxRPDl%9CuiFmha2&aC>f;9={9=e?59z64uD8ls4o_gP`4<7@HaSK zCLj?{T(Y&pJN^Ba&)T297 z|J}GJ?H%3r`~TmM?9~2N+x*x@SRAQTiz7>cR^9=Jn(BNHesIkWkyZFoHI26Ku5w&f zSg=%;4Y+!7Uzj3%gjS}lgBD77rM>VEBcKfG*oi`qfb1&B2H6EPSBt_$s^8XAk@T$x zD(PNW;8-GGfBU>^BMKEW4DAZICVv0`KmbWZK~#O#uim>|YMiYOfXqV{Zxzcp`eWR% z7@&qeV3k^=h5>}c@>-UmvluytzuP)Zq=>~Q@^I@A81cy5SGr6KlTx6=Pbx=%(FbV_(vIGNZ>4q(r*NU7!l+D!ynHIlZ-&8TQr*z~`8_iXN(; zlJkWbkefz?5fa)(X1O%$D5i8W=QBY5?j6`HzxKp7yK76i)luv)Of=b_1~d(y-7!)E zL~$vG_+A>2gVuo(NXPS0hnYdZV~9BW4_-cF-=+|v6nJGF>9ZT}b=g{4RTg2Qmr@C% z{!Nd7_Bw$1cj+(p+2=t5Rg(Z)K%~Ep%E?Kgz`Wk}6ZsATLP+MOM_E56;-T;1y0!33 ze@f|lG@&K9K{Rg4IZ`un#x?~$S9?9{<_+dyTJB>`L@ z^4d-W_>0@}VQ)+al+$L?F!wG{3t?X{ z=xH07_LQW>I=JExzU2v`(G+4t%w06KTY22zab?QW>SFa;w@Y`-J&&Aop+ zX8SOq`4!bg=BMaDP1Ll-z)>`giS7#Z8Niza*nNx3l5n%>rpf0?PD!@fc5X({L&O*$ zIG-JZk0{9Mt6Z(iH9Jsxh<0hSG;$qmj!X$e>ENbyC4XkGy> z-Hyn4yE~%`_!MjsUNJuQ4^G&%D`0lX$N%ep^O*g{uYcXX`R%*y$f-J4>9v3V5&L)l z>d$R8eBNFHSBapWl=EGZqdMPJF6XP#yfm0CzV*d5G#yK{_uj8{&{<}Ny|%xe7%F}q zxMQ{boWQzqK_doJ^T5F&VP#SJC``MZL~!ssHW1jkl79F3{XAjUJ!`D1+y_k>3~TfKvA*8y_e_Z!=3l)Q^>gyDFf&l5*QfQpfYTv9dADG*d5 z4U4P|49yIVR9InYZux@hg(@OynKTZ3!QeVUM!5BT4Tyxek!bHSLh{8W0#o$aHMoTo zZ4*b4B8m##M|{XzjYvd@Ju+c9P6ENHcwn11Fm;!cGAJWT*vmc}Ajb>BlO@-{39SNe zm>M$0C6JB_YsPO;)r#P2{gkg=g~g*1L6xbMO(5Y^x2%TROsHbDjx0(g^FhTe@4Q=U&+NTsBtGz62VFZAR|1H?JC0Q*)|vwN<%sB~8R6ph&WT{YE6`;G8eSBrO| zyLC@Y&h}s1KIBQ<)ipX19vTk=e)M{-K|Z&kGTkMX8ymWzx|yQAiZ8O_VRE|_gcgdf z;S|25syZa3;xp2!sN#AdM^q{%f5M|GC6HMI>LZNC)#4z~_DPDgWuka!9ImP)ms3;m z@`pJVydTL86AL78lq|3atr@)BglZD)nFOQG5J*wZ57&x38qiFvhKSjZk1_LmXa3;F z$Zr#?M@lk`9e_@n8`==!Y;wlAmV-Zj18|4}R0_JON~FE9-TCU-S*dPpV&$)}rGWM- zBW9rLCUvt2g~?l|;C3(;a|@mF$1HG?;$L7%*7-{VCubztww)X8^N-yJ>JBEA@?skv z9Hh<3IXKU%?0I4?Bdd%*KC+ti2TObTIq>oVa6gb>>Ft^y9fAB`?`Xwwg3SfQA>0Z0Dy@X}m%&_L@c)zd9`JSF^}YA^9G#=R_m;ee zyyca|@y>J-Ac+$~ftE7DbNjTn_qp(tj{B-Z;Zh3pKBX-bZh-=UK%9iw&LED5;>3=( z;~{xTvW8{ty>+Cc`~Lj?k`t#1ad?0R`cICJbR_-f@4G+W&o@8AuHYUtk!WyD4svl7 zGdcnRFOxm#l1npQ-CUf^C$jk59KkG46BiVdte8o!Zv=E7M|9z2@y3Y7MNgs!?+vb+ zbZ3=_z#{A6u|Jg=k`Xv%%iBQ;&77XgqJoc@+VRDveuvgl+){(4JVM61@;q5fER8b$ z()JSMSQbrwZmJb!#sRq-vI{g##A1oX6&5+E;7F(m4WzoZ1B2)xzv0rZUgLZC3k{j8 zyl~k*_33-<{qMUCuH}9!T{Oqtzs#%*2bDZ_{Iosy!ePsvl5PGJx_wx%Baz9}*@Jf9 zriDDb2zwk#n!8s`vBgXB?F-t2tF=HDnc#t-h!kBp4c#mm zi)dN^#hRi0N-*jNe70d`imkhO7NHd(5oo5Z&z`Y!ltr^aeGRb>VWx*$5nk%Yu9;>c z5q8b3X8#gk)n{WVb&W(OS_XCMQaG@BA#XoGIW&^C#1Ifi4+kx_j5jC%w=58W`bx zn}LjquE$e6ZfsD0FL>mTe{5`IPaqwXQVNSdpPg$lv95_tsK07~<5kQD_4EjZ@IKI4 z9n6;L;6gfa7ljcWqUWwabGRz5TG=f8Pyu`-Zt7 zbxu3(qkPa?*~u~7muRki#J1C4oIpF<9L8zPfihP;%jvYRl`vjLjps9oyN=@xG!8v1t`kdGUBzMUdM6ak#M!-<-qev(RGe+kzj)MEtXN`q zZCqhz&R=pptU|MGduF%&-RGaOskG&(X+R`(N*p#1hM~xrLJc<7_RwiGAFI29hJ%ZE zVOw9kXu~8$m$Dv|l|G9Ac9ZeV^ACaB^#pm>3v~ zJBgryNYW(pA^h8PI&}1sp-`f1gbNu2DI>V0*zUVYbam1+-Jy3X^PK?5H8OEnX>r;I zIX~Bp6iK2(nDQisgC7SIy|lEK`AXR~71yZ^P%AX>iR8N*s`FL zt}jx^=X5WTl^pEqV4O;#Rd$R!V)#2ZmD+}zrds8br-(y|y-^I(xRV)S&k}R%brY1# z;>Nfe&kfPd&&Ac-U)gIh&mOh+-Lt~(y0rxN>6E=z*9$(Hast`Nc;ewWG_@Y;Yqfn) z*Y<$$skJ#%guTvj6DBsUp9vl}-)a~CAJNpM2N(1KsavQM0AN<0zvvD>HFVqDw-jLHC{0m3h|kzC8bpbXH><6KTy zGgPy68EjdoYXtB0dy4qE@XM8_SPNS3u_Wt65}=6?qpTSLFO(#8L9zQ&{>BNetS)gb z=&gXlOFV;EsvYu9M}y$)0SDzk%(!WFK7;&V-2_{3rJ>6XAFs8?k2Tw>LOS2rxAF_> z4IU}T9 z*4#M5l`54TzVXI6(9}S<07Oz~EFX%hgs!zDJe;GzAH@@%7l|Ptxha{F1sAYFN6o6lJizJA$zJzBA znMS$bSoqjPOfZO1ax=Z~ES*t7$h0XGa*17qmYiciVI@{K7ONYMN^q`n9Q(R+ah5G- zY*2be4A(wryLMl+GS-R;Q~3#yU4Xlm06PW~6pYrWBMjiYUE=j^6i*5# zl1>teKunZ1ku4PQ`r;+i-NkI#S!Z+O8CJ#vq*2FG_$Q6{AcdGCIXTW*?gVhgu{2#L z7SQx#k2>Jg`3yW9}?FPl-pdm|&Kj*3gRELp&p^E{i+D zL(&a-qfn@>rx&r z{R&1HB)(6RU&c%Fd=a7c-MILS_4XiDgqRYk|pETsyqi5;>Z%R zxzJGZ!a1rvQQTTOPqi#|sc8b?ykR!5(B;KE`((Ff1jKj=AVv+YekT3RNt|=%03IuO zCn<>6r!#OY1p0L^?5&@9psTvv(ZQky$sEVJB!S$X)Yw!9>5|4QD$1}2W@lI#Rq-aZ(aHCPBokeaZ;f}*CPbKLz1%4rIx-pvY z_M!L9cN$K@-HpZWq64T?)?4v5R6nAo?I!lZ7V|d}>@Xco#NEV8>KF--@s28T0Wkn!)QO?eg0+`VH@INT#Uwp%s~5&M8w#?y-;cE!BekZ zHOF9?op<9!v{_wEt(7iaMC?1{Ad^4&$+J`ghAp+I*!;{j zlAEhVytpWVa#NA>I8)P-;CLRjXQ0D5)i6lnG1fIHlolnDe@MlphBKUmWC~VK_g3H` zNY)5Dl5EJ&cpTae@4YFXcz3p2J9|;qI~cFSRA8F|QK8seHGu)tKFS({Af=6W=3L&l zahu^NaVDh41oT41MP1`EQbNCXW012d{q> z7$iQ30L3CPlq;YfMY(FR`19@5M{8?aZTX56o05|NbtfG?Tt#q{`KF_S(-kHqcCNT=_1qBJ9g zIf5n~;>Pu(>3b2HZUkE-Wpc?CbE`1lO^Is=61*|sb}{sEhN-`*HEb$F!%HBvyBW8& z4CrP~IvHvNJ=9MkN!f1ak}Jj*w~^6huX%&cKe!{pwOnUF8mOsHM)DO z#MkY&%)(m$5K#lS7amV}ZMU@mlS?KKk$^iUGKI-gc-%A$;?F093vW0V}+LkZ>8|pN|RxV#?fAX~_ZMeL`mfW<^Mo|0-T>DrgWi)=i zdifOBZ>#4ixZp18vaePFgn?l+M36a*K+mIk5I`AMoQGKhV<15P7=VXJTv^rJJFvPM zoc-YX>3B2@&IbAQ0+crgt9qeMVm-x>zoA7@2H*;cCYof6putLp%2RWS?)5eQ_Fr+q z5>8={S=g?jUw{<}@BlHetfQ=|EG#)=S0Z(l7{as=6BHW&^US0QvAQ&$$sz!jC_dM) z{tkfRI}8atjj@)G;D(qE(c4GN#af6-!I%N<9fep?&r!!v7^`FI{_`*2xG&!Fyy-?l zOMy<2&+SSZybt5g%ZCp}B-usUn@US(*i?$k0SfC1=7m5RP--8`qa*q7@gtNrmnGzt z$V={pK3Cgan42-m#kG*k5KG4xC$7(`dk5@mAEi+MA%5l6i*}Kk^VB>Vy%F+cCDX9p zaU{J`dDz)tTq95f+7u3GPU|4uAxft8BK#8WPK3G#p{~B-gTMEjeTW9>RV$}i1szKl zIBo`*Y+sN}rrdF5%H@(OSu~L>lVwvUlad&k^iEjM#5*5kcgfJWRO3zutrTwJ58gS) zzQ4U3k08z^XtE}0#-5|qSpbToWDq`g*?qedo)KNSS*X4ye4p~NQ zf7L4gN@Hc%K506+aK6j#e`u3^^P3;AiVF->FR!vM{KdyzyW6p2r!0YWFnbxjwE@^d zkA5Gpg`bw!e7JsyjlKk4vxq^1Ku<0Sx_axPtP-Ym0-=ZP?`y zCXj<})x5($Iw47nVp`U$vb@4QM-#uR?md8^2%=d0#Plw^E|-}e@p1T_wXV}x^B-K9 zN8(ZjiRle^0=xE9+ktXsdEq^#VO(&jthc4r!8pSxW}) zDbXTGrCP?61QNZh7fZ_x^#oditydJUSkPN;fE8LSCJ<*wPt@XO6c7vN*;Yz3)m@CG zKwYbhg(u|*;8Tbd6mzE%Z>M0j<(4P#z%({8gR(?!E_m(<|3=AgWy6Lh{==(=(vj1qTxQM`AoZtkWvDKq8k~jeo|cjpO7&XP<|c{ z>7kKX_I=!QKNKzr*_aonF;P^+trFf4tor&a%yq~b$HFS|-0?Q6X*ghaZY%-uC90To zdtvt(d-CO%7+%dp3bK>A#P0>PIjW@)0{taLuh1 z3G!7arCgCofz~^JqnD6L$|{OIA(8#7A%9g}6B*kay8|YLxKfm;l>jC(1Xiu_VIfA z!Ojcz=#is#$IK*KK#V+fYBrV`LV-CswuXCt?jpm|vC6d!P8WnVj>!QDSON8Odl_ui zl}W0pWTseIR(T@6|79}RI(>mQ%Fi_0nhhnkY2!+Jbn8yy`#8JreYcS9?X@jm_?DeN zS!auGoNZ(98*84gN+>Poi2}he63n&`<_B6AcWF+$TTZ zkCTBG7T&cS^8NK~tlz5^nEkTWVo==5f2db?fb)%E4Fu5cYVsc-yeplOXsZYjiplAO zSPQQ)0ip~=bdiRMWG*!`0$Lo(oL!noB9eAWSuQEbvvF}Wp03U@0ufYoMgpu{P7o_R z#65Bb5jk?__4-9{qT29$NeBg4Xt8QKz<_hxUHUpg7DP!D-w25nA8s^VA&baHPh*mx zA6m_E_?kt?t)>F)+_|A{!RjVx=h9^CQUB;f+`D3BX*Ys)GK11InravxkF^slf++~_ zeC8q@qOd=Vz@S1cjJqh9WF(d{YEl`X1TgIgBgOTh2&+enS25~hILrd(9D?jO7U51u zLr3#IhX(#NYZth4s;g~wT>BuF{Kva1X&k4_kqwLCNG8D^r7pSVT1?zqHFQX0Yayg? z{16l>kG!T5Y-dC7Ho5{O8_hPvn()0!CLreo72AVfrWNy_GBM??sq!Rh$&)usSmTynf$= zSkb1FVfTK1mrrDg1;b1Pvv~}fog1#S+mvExVRP%rZg)eU!r&-@96HD{Vo`Jv$_%@j z8?L$D<)YJs;o`(3ZoFJ~m6ViF>tlg*;t=mIt8?}11q-KI9fk9M*?Y-u1U;1yL$;hm znk$1%WXj{gdy9)YHI;09Al)rMCwK_=km7BUBmg zb*vHa!>H{$+r!ZFHk+LjV+*m$0=v(H!CzLn32Sp6#L{Un#g|yPYMw}hi6R-7Ot^9< z$iHj`n{!n2#(4&L{ng(*Y@0T1M2KE-&w0hlrA)sF*!Cx$w4&L|A#BJnU#drrK0-(o zi$=Veyh8#c-4&Dv9|vU>Bs>W~bu@_845G|NM)2MU!%AQQ)%~cr2nz;_qXoq|kI^fe zHqOBvjkj|ss;7x}H8?vrn)Luzl@fZ&)dc)>@c@j;#?&PzYp7m7Rgys`z-o>OQ<{Jk`Nig3XfBh3?!miuk;vgO>J1= zY0iz_4eezL!Yd&j;eq&YS8x{J_6B)B@Pu0zA*-MZ9m2gxBo62R)Gasb&P{2yn9T7h zdV9lYA3p*hcRmE~uTv6}ZpDO4E-mH+dE(uNP)8{4=0ONEn@AaG7EsaWv1~Xp`ZX_TudrC)~~@C!r>*os3n_BvU?vsSrw} z=_aE;>;~MteB$t4N?xjMcQ7r_Wyxi^iMNGJ6DA={);=KPtnxa5HjEFcscCgJ z`wC*^D}5w%;>ZyYrU=EPP)JBGuSfb#8Ehr-4EpUv71jzR_s{TerD-FBU9bN~v+)PW@(jhJAk ze~X1Mc?MVC`5n33t~}ygi!SzaONz^5H7U@ zSxGOK!Iq1SfL~Krmb)R#!2d(a9Z=r+;$Q#R8d;d1{P+X*^ppS9-hcO(xyT_~aPxG! zj1b;zH56o86H_MdyQz?8I2EBBw5MM<>oD`lK7Dzm0dV111lYAhrx{3 zl7sk@yJp#v#dI`b?RJ3B+I6bMka6?VjnvZuV+L5}5LjkCYbj@WTC!Ss;*3Th8o72C zUo(kPiC9+}WU;^HCc)MEK}bdW6wr7V@(EFZcQhX<3Pjb}jxn1iOUMp1ldA||lAFwM zpvqo8cG)fgJW7qk>ITShw6-zcWm0g#TPt)yeq0FhR_CCdzG2h(OMpeHp@DCn1;%X= z=z*t!Q6({rr#m)sl5f9UTfOJ8$v;={>nklS4K_A5hPyg1ok>lZ_85^{4=(G1U~E!C zL|lSDIzDN%2iI}_tSny=?#e}6o&j7u#WdoLmN2?9#`OrWJF*-m4lKb#0f@cw3hjK^ zZa6roDfWFrw6+L>6p4pMngnuV`V?Ebmr6jmCMp9Vgsydvhv#636!PVE3t5&-ynE(y zk4?#7XgF@$7;&zsXB9sU^<$;T7z=M|Ohpe;-;M>vlZYly#9GF~rzICq@vG|2LX2IY z%jGo)@Xo;*b`Z*){`PhlJOJ+_XeUor;rg-IRA)v}Y5IB+$+c`4JPHd^Z00n=1Sm=u za2|_^`R7kdwYdd}b|b{%3Dh*tPz&wr>~@^iGvVM8M^`N_kl=+H;FbU~D2T;qW{m48 zox}Mn*4ffQ&$i)qCOhw-gv8KHNbRHXVjB59K@Wu#i(%fCW?pHQvq~5~wSCHa!6ii^ zcp!Q>THN{qi$EeLoko}4J9k($Va+JYu4kallIgmNQX3x~LD6Zr^W-8nEz1SpJl9!} zy)Rv`LkxFM50WfwZFKx(TFgY`G(>oTYKYF`T)f6G0vL5V%vUx#&(~ijgS);F~C?) ztMxY4o3Iok^ea1}cjUnh=*F5lP3VsM=6^U3?zw06nT&|1=*ZpYGF}C5=k(d8aC>)O zI5^T5K-v07`r2Dr-(NuG{L!WA-AA>z37I7a&L-hC+sxM`{?5*4=ntrRB_*NgXTIp@ zIA2uUqU6lHh+2&C-2C`ZL1CJ&y`|T8j`C7G3tYnG+OrTeq)NNH?#)?Hl3LMPP}I|U zNE(%ZTuI}mIVCY7;n6W@ZjiM=P~Y+xQXK9j!A8JYEUsOUMJOc^g(WBJ<`_3ia6d&1 zf2FR?nxQUH*T*0NtjX#_a3c+L(7x6|%Ac08A+WSUL4^mqnND zJWxc2e=c$ElKI7!3MfJMMj!%}CZ@v{5)B4dtdHmt2Ne`P$oF2o+-CfGx>FFr%ooGnzqjdT9~CpX%}nE*v3S?z|Y@ISKAx zkbM=|tNZHhz{_VXgHS{q#nH6KX~IDh%3;HTOw*w4_yk6~G8*LB{k5zOGRfjG>+t$` z#cZl>tbRbT%b=EBw4j*Ag+3TU8EM1l*i$si|LB==yV41u2ORVeR$HtYBW>yhMrg>k z>z=5B5kpJf7=y7j5@i*1N(x){P-2QuhZ%}^h-c}Zn@S0j8`q-idLtu7bUIB1*+mvh z14}q21x{(GhUqE)04$^%*Uol$fBpIKN-$DLY89Jw$(@(LB9^>Sas3L3a2aP!eSo4&eQG0ZYOAdSZW`= zf0;#LNzT&TuOa4Fu!1%48V^Gn9^wHiQXBF=Rr6hJ-2ixvxinmUErslldF@4Xibn)cJ~ z{{B5v;v>JXzwDp(dVhq*wsjcUtxj+!_Vh*pp8TkcU%-djjHGYfI(BmVUuy?@7yq~C zKYr>$!)I^ZIByp7b^W=?m4sCz{>b>G2pv^7$g_}~-1Tf+fPP=rdl&(ZqjxthkYY!f zCRZ}Am_Fn@d-r*NFy87t08+NX1y=s-Ebu~VpxX}9 z@Ets6x87E2_ugJ&kL@^RSD^M!g(5WsFku|l#4sg^F^78vY(l+LSnqN$yxoCu@YFm+R5il;@TOOX>hsYFE?Oqp^*oi0YJwzPKJ zxyn|nCc%|Q^*~9lnUL#G!-Zeb(!=NNu5Y@!g~k%_y9o@|N=QMvB)D{gX;FHeU?@U; z%|Y~xqfoT*=_H>*P@xvYxt?h;k_fDEhGulNU1rdPG7RKZx6c9n@vwyKt0PQWlow|O zFjnfkTgk%jf#P*fMLWdmtZBTR-qtI4LK0q$b|slfD5PiUgix-pGR3&j16*@H^g@3;1I~OJv`DSEs>sA*JUn9KwF}Lw;wu%Z#qHpb%y@8st?}wWX{^-P| zeZxQ9^amS965?X!jgAK5Pu8^i6C+6f^!4~h2YY;qSKrOWND*m^pgg3mqC{E(E8(=7 zkrQjh3?b|5>bDBO?V7w0LbE!6f_tFcwCmZNmg9F>NgB@*mylrnELO#sb7$qlU##v@HY8bHGNpvMufi_P{3hg?K(KS z^s}@yGO)PL=g!sH{)5oYzymha&wd%mCZP~ZWEP1l5%JBPolB+{q?14`Y?@XPP2w(v zQeZ)Ts!b*gPltpp-8#vf7lLrR zchh`g#00k<8yh=q``#*7hY#THD=8@NB^oNFC=_tRklz*;Cb|+)T1LFpqClQ}{Y1McW1jpJ@WaL0S-7>2Qlwjkv9m zdkawm_fQEc39V)TN5jb_29H<(M7<0L=!f=b>GV{4|HfHV5vDj#=hUfs+p+7M?K?+n zCy##ZLdNl=C)r7c=QW@tg2P>2ygT92dv)@OMeOeI8~^c?ztdvUWJ)mToiM=V7<|m< z4n&6NVhYA&6h)9L>BxwW`1>`>G9LcDMOm+CPZP2?UQtoO*}V0}lK6$&c-fY9qqb$- z|EZi~5#N4zY3qmPZ~d!-!{d(!d_$j2iV1$09-zpGxXWSsTgOI0p>t83<=b72!jr!JOJ96cFBO z=h5mOh^OtzNV8xbFRLLt9kd%)&9(>bm}5T#2i=1}#*$Q0pS8m>6L-tH=z+RKlH7AF zoOAW$?qOx(s8OjVnFD86FR;DuJx7;SL%XfMxx^MOV$lKhd}7xHD{H8+<$wz`I8IF? zDP-qV-*&K55Ne5VR*BnKGne&jL;)m9*i16nS!9b!=!{y`(rb<2u;rHbP>=1V1lEOj zpu}B|EIXb<056V5Wz%6Tz4wl}4r!&7Lx`UpIZ+Qhb=*WO zFw54!g{7$oZMfP`?>ui+aE|3C_{mZeE4Md!E;Dhn17T>#ZqaMqE9nCgZo+-0tpE;i zJQR4jRGYsHW?bWNHA@IrfqMu}K!`uQg-9&Fvhczj4564BV8oc8mtZ&3DWuW2su)yW zY_k0%!H%;o5^$ySxo6G9=W60mpS$Q}!AUvq&na+@;WnMuRpHbp5>#yypX+Dtqsi}a zuN*5QzF0)i4;@gX&UIw4_tCVRysv!z{*qIl=dVBYt)s!*#?rAZTcD_WhwYsN*!%M> zzVNqMvRn4<4QyHWQg~&Q?-W1y$Q@sN<;Mfv{eKaal(8xl-|S}^0>PsbF3$Ao)%@a9 z;6cf9q8mb6oremvEE9k z40k|=hC7!LpJ6Y&TI)KN=FQ8so3N6vGD9hqn8;<-MZqI0i~H_e>9@QB1epgZcUu-! z3rvAs0s@)IdH(ptN@8NPJPeBu-agxYu%jF#57=7b&QK49LxkT$=P17OTtp8?PG%l& zK^Dj3JXWJPy}}t;u%tj8^ja(9OJ2p2G2e#<2u)jDexTBJk{#8Y*%30Rb)cC>;PV~} zw}aJ%0v5}hjBuyoiYMXDClPatq%b}n*O@xA8Ue({lE=ca6fuWF@Tq;(p3n% z(GT5jwUp}$z}61{$#n6y1Xi&s@p6E7hoW*`j|5r3A7WpWg60(|V=GXF@bHa|YG4?l zVu0I@VpY8Dno+kzPGq&AcvRS(H;2p9uve zV2&2>Bo2B&IB1lwgmp3zru(GL2{7mDE>420Wv}1GHJ4I%Uwa|gICWgy0s%(i0@@D- z<`o3^i~IlSp`UACxc&Yz{$ia^fQ{?hu1|m`_O)f*I?#&azHcA<>)^vneWB<7a@F&j zA1~is|6=nWve-UH*{MkVmkd0nx~VJq1upu;K0PbxC7gy4GVuqEjmO!EQ*~B6HHSn@ zF2kn~5QxB(2nlslia@|zCy}dLzQcvejmDBXD-W-5e`^9AFY(rl8@PAhS$lBvO|V5w zGbMIL;B8Vbu71}g%!qBn%DOm{`_{*CLX3h?0e{jxO2`GL4F}ev&sLzt1Ga#~$OngK z*$=Sve!%c*ZqTCjl!Vvz=G-wUY^Sxo#EX=IVm`TqV(C!!HJ{|m70CC#@lz6JD_U&T zs(Ek-&$0q&g?_%j7BB-10d)IlQ-VlX;SfdXen9@60Na7+xcasZqrvMMO{4H34P?3@DSRUJ2&-%V=}8WN&I;N+E3+X}D1sp+))CR~ zeDQ+43}YpyNjoC@rrI&AwM!g=xVjctDPZLqB*5CIN}eiTNzv%}IdSFpuQu{bxW|*; zm{YK1>p`-!kG^oh60oH4Srf4}mS+9rfq=OC9- zwQaqWB^ICXIL+=)9cZvi^__O-E%RM-g=)>a_Fbgkw#&_eios2mf{XwO6cc7p9WQw# zI)vs#jZ?Y^hiSqf_U*>Pp1D$MsSL!P2W#kDXn^t{36yo#)=o!SBpLPO6vnawAym06 z8Y`>zQpMWyN<3#pm~ypu_Vh4V3@e`lY_%Dz`dLb8H>{jxEx=Ist2dU#euc)4afst0 z2$2G~t^x4mL6SvL#LzyusbOWpQKI@9K>(28c$6g(Iph~~uNnYwsB1`70ypgsWuW?S zFPY^rSY=i^MvN(M7)?^mXp(ws=%plt;>n_+LK79m;-Phd;pBLDEmYB@AXNWX15FI) z7mQ3HEa0AvWV!q3Oq8(h&eD1c$$NY(cRr)}COi@zAB#Z~2$U2W?gz{e{uf_z>Q@i` z&)XYyU)QeP63EDyJHGYXORwAN>hC5uZ2T{`RczfluH@F{&5uV^l$gKq$#3A7RHRZsznw-sK!W{YH;4f_5d+RPGJdLVon)Ox9s1% z&o_L}zMTLnZsu!&AmZZVVdjWt@is#Kj!*y-O+u)SFwH^OZj0{5%Nz|!cjnM*DNn~)_Xsw zJ!Rp=DWw+B-f+Nr2vz3Nl6mhfGwo*PF9|Vs0R{5xt_pjp9MB87g>-7jg0xBt$g@y~ zo2xT(euD^bB3{O_MFnK_M{VzkD?Am(pYR$0e?91rvB3zYdN5_8pMm22oM%6u4Nzkr zf{8_JETe&#P+VMmM1FoQt@7j_M#r9xjEec#o-f?;Z*?y}+Gks~_%~-{_@8_38)Fp} zTRpjd!*aUbFWk^$$XckfLeyY2RZzIy6fm}j0f{eL+T&&c&(67QHI3BcNJb2Iz=T0I*DY#?cww*a zwCNbQJ&JK7VEP+mF(l$jH}wbYrG4d0lV54;K;EeTd6Y7b+}ufWxe%u=OYpjRe2as* zYmlpsd+%#@TDh0SkeFM{f{L;qKYhY}|AFPS$3YTK9e3-?H4JHEfE?GYYnPyobjwpv zW?Q#(a+45~Cs1Y_0e5b>LgF417Ias2|j>Bb_5r`9;sQ&6~M zP;XWTP(S=z?A*oPI!{MlfJITlO!a)h359Y><-FwTHTRF()*V&$m$!{FNg>_3JMjRJ zmYMKg@n^*NQI^LHtwS(u9DTLL3NY6H<@OmieFh_1nYwZ4a3#sGAuC3h1j8M~%J;&x zokp{WS^%#lXc(i$?Qy1gY^M{nO2AH)Op}Lz7tfG)GW@Av)=?ns5WiPo-80F&t5c{0 zZ)rOH;WsVLr3#SG`T5Cqx7jNUPuqK;3#&?BIm%g3PIVP2&QrN9LDv=l06+jqL_t(Z zar)$YEXuEndixrbN&uxW1oi-VwoH^yjFO7P$ZAIMUbyOf?OrH9^@>N+e;OGT49CXD zp`RnHuczl|O?~Ize)0a9PkK)j!QDL9w{^<{;jPzb>&fT+?%q*BztT;x%)qf@$0V$l zwcysc=-#nUqulQ3bG4Ll&Z47)V+d8$ikAKKz4LAUqGC9U zEA5F_YAjm-dN_IeFJE+ZNeT0{g7r3s<2sa8R^3tj#Udb2%qes=$HHX4efWVJ2oVzO z#XYp-(ZQ4@)Dh^f{>Bg{KmlWMsUs1( zCK5=wWOX;uDtDt1rE!K-{w@A{X8U5*q z$Z$aDFSUp47yy<}E=sZc-@n{Wm)F~)&!4qoGUlmRK+!5GQ?7=Q1bEa0%1}}) zQe9^#2wk!;1S$ea1HnD zMDI$<@wmNBJ@}k1=Nt({fU>7u#sT~PR>au1u<&jYdFiLV6+HIshvjB*Wxty3|F;Ex z(`k%P2(KSOjyQH~Cv*VzwZg)UKl24g{~MgTp8}K}sSL874HwL9caem9TEbJSj3ZYs zh8k&NY=#{HYrJ^zG=_ucSP`I$j!xpafI+O)Z&|L?AH$3@-dCIBTg}CQF z+xoLZ_Mr!Evh{0cIZOP)@kZc#S>9^pv}Fl2+0d~`Ogv|o*>nrVbMvql&Qfc{hul8B z)FhBc0st>$^D4NUZ(-c0N-00xb^?mkXqyYjMw#Eow!OxAN5N;6?I@8}ubPTQg&wRY zY-b@KknqaoTnHoQO2&rBiXEjS*fB=0ZRfZhKSAWeLFudLs{ryXV~=FuWI{M3-IK5g%RZN+O=x~ zWn~%Tb#+^-`N1F4w)hzB#(zn7#htWJLFY3jt)*w{1X)%`)<-2J^?t@;DXXbWoj+G^ z%U8~{C3LVn4ZJb~dQpvVQNQK&!Ye0F%*EuYJ&Rk4+VB7ZoRAl5mF<4pzrTW(#!_34 zD_sq7T^M3`(W5$7nnaRdkgwN;RdqU=<%zYrY*Yz=@D3n3%$GgbR%Cqw3ko|1? z5!-z4O1llqHcW$aU8jFS~<#UDskmDw}|u=N5F4Yo?tR*;KnfhZDu>MSaS zP4ceW=CjEC_Qba1j!p6NpS-~>?A^5b?P-Rb0C0nZY{m@SS2~c|+F(1644 zC{-XuCzn-yxe?j1PM}rh=Fz(GDk*7s{2jlCZkID7fmCE7cxng3>Ut@Oi3DDRiDG{t z4qq`!MN+pkN2-8qz%mC0Rj-A=O1wO-rersApV zAHuKs3zA&(5Gc$?*r7joC;?ei&Gc1=keKab$ow4zs6TH$t{d>mS74YNAs$j;ez-H) zxq;UOubi-8GHNc~!S$A+(2ScX`b#sDvu*bYCKOJG7@h+ES|;y3f3(3es3R)YbmV{d za~g)OO^FW)m4wIbS^{uYol79(?#dM;F{Jn&#WV!leqIX0&g)=KeD0WifcC~sx6OlI z<~2s6cF=1~gFCL7=xIfZs(owFv_8}EB)m>&uO3Sv5RO54LyhQu<}^tO$PyNSAZqLz zv~O%ZVVhR8LfH?H8El_Vo4NW2}!dmQ&oNlgl*(m2xJ*Hez#{o;-pfQp~qkwVC|*SN^VB_8Z!^pgYU-l2DVFx+4)P*#F9N`jZHMAl=QH8OOKA z%+TuPk4j^rUEyqt$(aJg&u0(6uf)Y(+n*~(&>Ac?OqR9&q75`$B%W(?2`Z;%-74S! zSFemO^cgSjqlvE(0vGoYbH`*CTT=d1SoEXlvklruK6n!v*6h1KJqAP%p5Y;Y?Txi0 z&%kDrKyv%y?~yEC`c}eh+D>oyv=}91?cEtmLM%6e5S;4lwFjof zVNn-AnwMq`4U}?@)Bw__WfDY_7YnjDv3PzgiMp8bX>k-{O3WX!j*16kK!j+Rw_NI2 zn%!mnWZ4AHkWy4!C}GnKD(6k`805ZcW9>VOC=1yJPP>&CZl@Dc5g3l(Jq(iE8wA5B zY9l53)Ss=ym7uPzAj4t<<97SXLR+$A2K!U&-C;*xtF?n?+o=sxE(0#CzFM7&sFf0M z$<_1i(HJY{hLi!}*7zV1G)TB5(3;1jB_c~L8eO5gq*z3nc>Y48RqwcO#b;C^j z=s#!SeHg+4XMssHG0ZL_7@afCmpWy(wE^rXotkJ5ZN3q>Uyps`@e>vehB(xI*?LK4 zsTI(bd$<(O3QDlFggJ~XAq(8Ooq9_8)LBP_4dGJuRgK(I7_r3GHB8%kXmx?DTQB#i z$^Lam1%0g^{81KLq<{K*F&Dc1=s1%CEEg96mH@eg`-EU2-2eoSwab$ETn!u`I)Sv+)tHIXzq4p6yBA18KRu^ z$p@EOE)x`=e&&pooo+V5Eaw8dk)gn8W! z)g^0_;JFtIR>CD$R57v`CDe{M%tU}>dX6)3iDf-6T)5&a;=+YfSh(~zpStXb1=Q8F zkck{CR?cy4o^5yyD_72TvG)E0=N(I=GQe^VRFdHaI|^QT13lm||N0|~9Zl}{9y?@P zVO+UyT7u1{{;M)nb`GT~RzN#M1!^cMhuf>FnSpQIOtGIR-c-I~2_r{WEGc68W3qLV zSd(Sf(Cx>bI&R0{`!0+HI70unqp%??((?|eV+l`3&s5J=G)p2aaL?Y|BbsBlAAMN) z7O>ux%vOqQM2;(j!T8-G6-m;Bl2@Jg&H2~>>3PqK≻ z)O?A4kL|{s|mK#L938Cq#}OJm2nL-q7YRF3PZZ1xbwdWRN$+>Vv*Gx6ow;Tzu#R z)H@6|m=rfc!xNF<$ok0&I?`?loqI{>qKkK8@i#blbys2ZVX z0TDthp%Nnw#e=*_UpSq?p(m}Nu*kB0vfL6v37}j}384hg2_o8GG`6W^bW7$Hy7^FL z`zn}0g^g#2BBXb5A-~7kBQ|6o>`PWeFh4IA)-iSUSP8xO!h0vF#Xg*?EFr^1j)`HS z0XzEF9cS$hk?E~nh-Z@ok}6~`!E8|j%y1g)8Y09Otd+bG7En_FTkNTw=jd@B@>n7} zX%K<6M49;rN^((j{m3&BuXD-FA}4rfA*Sy|i6p^fLCVaEk^(dx1nkhIK}MrouqmlE zWPH<59zZu~kWi_pbYVZ|7zvD%Sy$D~R`%*8+jgPbHWo0YgWB^I%2>^W92)b3s&n{( z2&xjUMo!0)rfNu#HD(7Q8RA!X&$uT^Jl|XzDDn~5Jep?Ic9{atwU|%z+@uUCKZP$< zb%dwS$PWb2(m#6YSkI1%wy)cdUi?Q8!xZAkE|-@_Zk{_AYS;f*;nlhPhYPSyf^EFK zeCvqNT>56~5C1RSsQ+>6mc2hE;rHhe5y20|$HoUv!-jeMwM(OS-I*S-Vqu=I9y--5 z9*BVP(Zo;^K4%FhETF8Q>VuvuN@>DpaRgcT zLWl6u*Ibm#h*SIZ2XHO1!Wt3VPJ9`m(1M@0wGN}em_PKs#g??Yf*90;X5yF-o`mh- z!AthDeKoG$m(Jw)zGgMvL;2eW031Iv3P6eah6Vheni^?Sm`&9VIp9gM>#4vJM}TCG zkepK}qeg>#1V>&_E6V9_b~V@%KrMfG_dKRv6j=^U2vUGt5*w&1;^rywLyX-4yn+xm zQNB`gD+UA>*gTgkbfE%gH-twuh^G+_0W~EKE=;5MnV#o7kY9p$Itxo;OPl6yb<;Lj z#n86;#;)30`!zU;8V-pdt;Nr ze$Q=krOV2;I5$Nncgx?ra_9P``G3XO&>LbjjUk!gE=*e{TNqG@z{Q$aLJ8mGOMmCZ zfgV)Oiv?AZ@GPMdP6_CQC6wSPMpR~W7~vb{>uzQoE6K5L{bDk*-3|`f#{v}%D9_#r zpew^5h@?k2qJ&I&VOc=g2G0_b!tyL4KfsA~4g2o*^gHZJE`KB-iGD#_#)j+4iQH$m6HGtH3DZZu7gt13(!`q&b=yafFen*60?wu$tVi$?>{q)zjrpx+Va=cbz;S z!y-x6Io3r`R+oE2c6VvE-FC}dHPor2VrOBOD zOXoO~82d;-;n3LfnW?r6M#@aw*lyx(C8!1{xs}X@bb(Pb>V9f!7W5NO3=6#N=cnx_ zv{fzwNYbxtwUib2TD{PDB)JN)u6a305WdrS1_&gIHKVnlJ0yP3}I11yx%_>3WTT)`bpA6IH9{LgkJ0?p&aDJ z|4txPrf`-}){;kota^);1@FoaoP~>{c@Gk!y7@f=EsjxgA^ohS^9t-I`!8D|bf__q zw@1^2Fb;bqs~v%1hbsL@h_sxXAhEC{ToZyd`I##bx!-jrhVoOSg-E!>rh=sMMcJcI zzh)mJu3oe##|?1%$=*w}%OU#wjcZD1XKFj`i(|v;U=p}Q7T8PrcsJ4$Vtp-Gr+A>C z{>0_yYsw}K)I8Uhq}zH34f?zhF)=Z%g z4`p$&Mw1j{ts!f`(>Zgd&i2s_RY^02N|bvfP`IZYp0{!X+U7>B(T(VyHUcb=Q6=(jErsYNr=K6C&5t3Ck_N&F9=J!cm>heqH93HFCDVb1Sj!5~0{NG|E5 zrW5(*vWo6A_dSC-6f^Rf2AsKHkPtYS4}wgb7DX3KES)7kr$w)@D2q{=Ahc)#*C>}H zIDv<-h$0G50!7FvH5zDGxMES&BJq2XD+HK#edYvM@A_VXr{BQ>%PNU&F+^=ADW?F! zwl_3CKpUgjZ0o*SxTXjPi0?*#J+cGW^61zr*w=)=`TB}szk)~llwp_krBNX^DaAD? zteBQ$ciuYR#pTcLEQjcxDTv&d|NEvQ8t;p7t9@81I+Rc%Yi^!PJ(R)eM;eGHq5Z*A z2$LWRfxY&W2Q%hjA&F++t<>vpo}28DSJjN;Imdmg_r+oFrE$bU}6SwST0j#y~7T!$OZm5BW3l_o%FMrRop(cb)Q>EW ziwXYO%dghn`@+diONkg7qfiH2xi8=>6Y1PZp>eL}ge6qZr-N)d%jH=|CrIvdxuggK z3r-9W0{6#5Iober$5@7DD z6I!{mvb6d@yXM`!^qIFQK2_G##gWjpCgv8p*~|q=e*5TyG(Ql#?b>s}o<3M-*^yXb zAfWv;T8LcDYkrt)t(@E;!i%+?Y^aFIW=3yzJ~-rPn~f!X@B>TSu=VG5p0aHx+UT?i z*lkO*ZCUA52hLDNc;~K@02&7Dj$0Sgv=Bq7i3Wvzl`w7g(tv?tf- zZi3?WzuY^|X3xpDZO@&y1Lr%LMhNQ$7EhD<3P@nBT9ixga-p;EV#GLnyv7b+V6GME zm^c*F0Ln^P;%Edj6NZe!%y`QtWu8OgNs}BR@kFF!m2sC#ErC{DTis7bk5yUO$rd}% z;eD{7&|k{$ww8?p?pVcP;RnE(Hs$6(8P`ToAIy;y%=-1xxf09P&@8|@db^XN!N ziw{-}oTD-L;kGcfhE`aPT z%bq!W*)sW=<~2!Bg~?Vsxr-32l~hT$oskbOv=Q$z!RUb;?i;op`G#D z<4+&94*_6Vzjmf`|9^h`isg{)bxJ|k#v%^!w__y0oE4VkMR-*Q6){1S$lNk>tt%Yu z5<2&8THvy~yZ4^6|9z<0ZpezU_pP1EWCysGxpZZm)#tmff*C*L0vg*6*c}{O*R5uO zebD#3NPlcx3=EkZLz(nQkYzn%L1s8bxxVT)rb$)^kV1C15qBLKvb!0Z;xS^70S7lN zMvPr2n(R0k?-{h}A?L1%enw8BW8284vnf3-9)&{Z74DOSQ0G=d*OTT_HMaIyJ0onS zQ;nE4Bgb-b(`-FmYo(>bb{{{lpssutGXDk`LYQbcPLTne3RWOM{ehlym`aa@27A6# zzUv>nHorH7Y-R4D{C52FTVsK*y`AH}qvSu9PNeZS|8seKM_b#&G$?!~)YYEdTXTj+ zg~n0FrVuzPCFu#Q1XcgJO_HV0C%@N+`b;kg0mXl{>qTR|Qi^6+H%x}bX+isg58do) zso(qQQ5H9B5JOB4xLjoejn%IMO0OHcP1djP)pNT5N8kGe*;0>l#lf`BAx)r`t2%gNW0&g6VKU+2?xFEOQhXf!=B-U5y&Yc-gxbDU z_KiP!Lz~~HP!GgYzh#?3!{5T~5&QNdkAxp5tzWWsZNxVoSUz;A?B8CUvihS>4tKXk zk*QrY*560MwA%-ZMJOB!QE3_BrG(GKOBRopvswtUdv`9cgxIsna>22_AIp?9$}=coO#m z%a$KQEbC*^AsO*F5^DnJT;hHlI@f9!L6!A)!5#w43IEemZvz*rR}Ua$s~qa1&gx|Jk^zl;^0Jf@Od5@Oi{%uy=b#~R;au#n6l zzMKYUb{l-qHJu?##>G@URhu%rBEXM?NI=4?aUmhhTBWGP8-VbSY*oJ=v}?6`h- zu;wrZhph8Kvdv4us+TUFV)e8QrV_huTr(4v%Or#jeruWz)D2V$VS>s<5?Iyj`#@6F z)wbGe2<*!Tt85p_WgoEBbKKJ&u-1`E!cntcG9|&5EG!0U+G#JJYP5KRIFFf211%81 zLxA8P9U?)cG7?Ofrh;3%=c)1La{SU--G>&1A-pF&bv6-FxRe8-DtvRX6)Ag+603 zjYNvH8D*n#6in=tYs~)Oju|!|g7Q;Ll-yBv(LM{Fyrd)xLij%0{zAFK6L0zCP3~0p z?yqu$=E4LI$f8S$u+)X6W*{xIcw+&fMBAf#YpoL2jSXu`5Ly^8KuqDNxGk5#XESDG zIuw>-YBf@55`(&wx}nplVaR#|u5CTZu*>Qp2DK$cB}*Rz>uP2|l>tH+o=^}bjUi&} zoD3#VP)cZmfpSpE$uRerHqha=%P#Xjs4|v9kA##lN@n5ggjD!#;_cA+=JN0Es{FD& z_0SK!v-6q`wmg7Tzf1PV$-jTEy8Rd=}JFW^@=FaSjs~BFLgbxCh8V zZny?ZEBWPdXt7Rynav#&w;V;FlxvvpVMe2QJ_Y`%PDhP1m&p%BwD{G~>ef#FDv=tg z7Ol!TelWl-^vQl`!&F;=>v{fsi@kcZ#vZ(T5wm_$xlc{D6>6KURo(X4yJk6;_}KAU zd;T~sGE_HUWE}8BF?S?XJMuojY(ZH&1`R9aH<}4*$odZA)@!;&QE@8CCXiL2%H*yK zm#uNC&GHgzz&4+$w|$4I?M1Tair+85)71-$Mi7dnB>#xTBane1#<@b!AWk%4+Z7u4 zxZgb-Z~ZdS36~cUwdKHkIV4!YzwqLJD~M>wv(SfQaF9X zR(#ygAh*9iLF*$i5%x(+>}>^ER!C(jQSi8NkXYi(gbdddKXq!h&7YU&5yPKtv2-k- zD0pOvT}_zsiC03p_6)D*J7t&Ul50T=9n_BkQGanhrL8CS)!~8$ZPn^I_Q0kR`@y!; zG$`OsyZWi&>JHoeHy6=4G~Es9k`UehzEbMBLEFc$^B0a>vF3rWeSAT>n>OFlGGKd- zT(%5^*PBg?<->aRg#r-3(Ob*i%mhs}7v_>Y&{7(5t_-m-#OkS4myYgW6io`fv<4nL zbis~rKSIRDU7F*>yK1l+k6H+PScAtAHsFsqZJ4k`E_(XJ z1cnB(+i_Uwkou)X>^Cw*2RUa7?t>gaB!lU~45<5lAQ=7CV^92f#mnsLQ}9sb=6-5y z%S8Fn9pHE9pWht|{O=x0*?1#kQ`fFti#7fO>+bko3-gb+C8kV0KqjkzZ0!_WQ?k^` zSh;9ZLj2Z(jHpWx<=V+rjg3!WJ`kM2y*=_ICg8 zPVV|Xkc#2BO1x=al9Dx%pqb*C@pSlHi)A1%B@o}|rp8-E6>Oe37b14QZE>cpT|L*q z65DA3T)K3+bAz8DgT3=a3&4jci^o-c-};$Q;KbWb2=)Z#(DZ?3kXdSuS2O$!u*Wyd z&9e1?F4n9lw#D=FZ3@XNk=Lp1P}2><2&WiBdg=GQ!o&s55)xx%59OQkrXiGFG!qZ7 z;ftJg-zzpt&BtfV$DJpfA$#W3_LJZ1q0J_$x+3~iFL|7{s|2@YW z2w;Z9qB1_**%XGk1?FV{7n}maulK-<{&3})?fVg(5Ee)uiKQG1;65H>2wB1#TxmxUD>vBf`r2Jy_jghrB;h=O3Elu#6GcO6 z6qLBf&O(Ss0ks6u_-ru0drw}mn`b3MWLM&pjk=x+3)6uU_Sh58oU+#t(j4O07CN6c zEXuScOe#3>TD|?_o*J9YsFLZ~akgSkx~*H9Z>yIT+0sRY)V|XZNHyV$ORC4=&SU6T zMz6S;LbcG@sBgBCPNlE>es|gGmLe@d;dfDuBn??5hB9j)65DFwRmvFGHDIDr*4TOh>{ZIv0 z(qQuc))tO^rt{dIO5NAe(oY2+d+eUDc+0Q*KL3{f;_tiwPd*n}W4YC~)*@=k%0|1p zE}ckEoBh~W7}$^50t7imb$-59qU$ZJv4mJwm>*JBii)Gp6z=59wByYtBVAOSWo>+2 zPi9!n2W}*%Tthc%Mu+%ijR59Ff9tF8d-r3TPb zH1AVxnn4@lAPkY`n+F`6QEi-FizV&~%FUJCT-Kg@i*j@fDNG>L6vFN?Mt_z9AjwLG zI_Gk@zPWcaX0$gj)Y;}A?r7{C9q#}8fG_aLOVvAHA=tj^Z8bK2O*i~M#rB^@fW4<# z2K$;Uvf36){2d+J`f#gvrzB5(ZrnE}ODv15X%Z4(39N~-Qe zj`UL-&ZpcHYbTleqpY#;*WP>|gxJ-F--R)dtIj^u-|ARHNMH$A;$9?_G$@;a$GFmr z5uxYxHEOI=m~A_ARu(ZVR5HlBI&WTj`JDa5GZ!rpw|^R3%u}(jH)7FlTw3G^>Llbj zB%#z|r-=$zn0$B^`kPnb%lg^gD*G|`=PZ=bI;ILP!Hrex;px*g_RQW&d$yv}mK7%0 zI^ytV2mzkiUu$VVGUb8PP?J4bUh6W;)28LPW`rd8tS(R<>Sr)nLOh8vu15q4z!=es z$Qvg;Sq9S#D1QR8d`Y6MUpZx*64dBRhiU?&%=8O)HQHcX!{bA}tskp7_uP*=Ix2y> zc+az@<~er6GyYGs{SGFvuIK4F8XrVV4}RLjxT>GS65PPL3c|nu z%d)eb?mj6F7AvKAoBh#EuC$a5YHIhXR!S#zFlQFphSEIy8H+g+Hp?gyHQtOR26c@I zX8AUT!3iv!Ix~cXvZC)+Qx4VBEaR05WrX|`R+*52b zDGAA4mL-4XNUfc^!XyMnx@19cw*)sil3wL=7n*6}A7L^h&GYalr&2c_VldkOrqSdU zV2!FVuUS3SHS51X6738S$8^X9lW5H7WpcDEIGdQOBtn95C&3?mvynds`U6iQ6Va;WASjVl`t##n1}r_G%yR8hJ$0A^_I zgG3Ghu3YKxM5odOpv3LU@pCDj7B82qEBIVl)&OmP%ED@{tw*-URI<6%+ zXk$*$Fmrfn7!H;l=eGy%n&;?lG+0cXL;`3eC&ht+Dz+lHq(l+ZL#IvyojM|w6Y;<^ zFPyROkj-ucNyYRM*Gw>kUE_Ra&!%JR(P&u!Ctfhn{ZW+(yz0s=~z z5nVK5B0-4JO*FczIq93WiOC-4WX~s9F03-r+rWUs6sFfZ zzm%Q+M`-*=7nvm?9Z8kkp!F^R{F18t}(1tV^>r zz2@(a!;Ji|mQ3QcEF&7PLiDg3jLU?=Iz3PbQ{v;~C;?wlRws$zohPGqIVBH>C*z}1 zFrpUOLjsS1<7hUuy9(YXWq4$&hoOBs;9P`diV?Tr+@AFqUFc* zi)v6*RYe5u@&7|=qtE>Rb#N`VkD*4FsGEelw6u7Tw0d_+^2GIFzGxh?7&}D~d$f6-9Y)JIu*28nCK*AzoSZcCA-c)i zHHh`%l9nEYj&i4L-F{s59IBP)x0Xr%=vW#|qk$^c$cBAQG6N2+&aeH9yOi~J(=`zM z3n$6M+*Ak$-Po_5l=V9*3`|ky!)isU1w}msg~iiSW%~3na^hs8Y(3PVY%qh2>Iau? zD3*+Ql=+p)g`_j!lHJD|#On4#c1VLpm?2~FN2)`_u9gxc83jl+n{!0QS)TZ$kS8w1 zWkn~uX63~7WoM^7(bpCD;`*=5dei&rPlIYt(y$+`t*W9wlg|8QeV_kAQ|J*tWaB2m zwVgFdw<;>uRr9ECB72LQMBpK6(%T6P+$4xXa$y4)=xTLn%BMzY*)Wzi!BEO$hnWOB zX4&jad1FrvX&|QI$jNA~8z5-)Fvi`8zqw&N8AVLKyozDg9f)7z(#ISYOmVM~y9Y|i z%r_6EiLoe6j6rE4m9dq2^6CsWT4%3xc~$b&ha_$_a6@$?ylL4?#Nv2w@Hw78;FEji zq+stk#mL-jW#*d&daA8^z^GX)zADW~wq{aCcM+W49VcZctS6-asvOQJ=z~FO>X2S| z_%90l@l@X_=uGuxi{MVCEYS8!9?FL0;R_AQd$oa_dcK zd{57y4o?&>ZV_)CZMG7lQ$sj$IGvbZYblWw9^ByX@jqIS>`>O3aXEPMxYq&dPJ0vf zab^X$p4!JqD{!`2rrtj;XW1Q;ct4=YHH-9`eHC}z$S4a#X?IK}ax&xcr3-Pr{815d z&s~eq!3xW-*CGs0$2L09CEciKSftV_g6Af9O|VkmY8t5lJ3zpyo|Ep-sdSIWoC#P} znn+I@(sEL_J(c~@olP~LwU%w5e%-d?gp?rgr|3<^Aa)RJH=*FU^7i@6j-9wG9FlA4 z7EfTO-hlS>tA|>dA-iPym^fL)xM%{MXWhAvAFmPbZeWrv2n&!RN8tq(0G=6uR_Nqn z6PKKd$i7=_@gfeEks3k3Z?@efv;=gRE1sT3MG-zIDc>NDw3IUc}}64rl>xNaw&1^RPU*cIpsl zqF_Oe0sT+POE)MaRT5DrgTqHo1L$u7M8OVBN?Tj)li$C7)YOw;DkKuE0~mZLct$bv z^^1dAbRuZ6$@!xVxZ-F@t^90Tm0V8%esW2U6fBy=SSZFQKdLgv8z8h)3oF?P0Hvo5 zxMD3%hE1T#`c2nZWpjL7m~L4(o{>_r6l2?Yf*my`1fmLXh6?P%!{*WkURenlbl;6F zD$m!ByprnUVI4V9j@42#eQcNTG z;RtM8)TFGG8Sm$pj+Glor`1_u)7BDW>3QwkT-*m-jEy?v-F=m^^B6Eua*9M3sj@br z+A#rd$7=|jG26Yk0ahfA&69zcQIZA%>u>MUo!uc%zqA)d5tQ1Fdg(fSf?c@E_*%W+ zZD$;&qcFPZZq;aJH%4{D0;Ca$Oh}Dr4n|22#8&Nq+r9pe zhvf@*FNU#{D^2K2#e*B305nmxh|>T$DAJRWQo{lO8lFri7+$S5ilu9|ln@)Y&)8PZwNw6uBDTbgS=#&7F#ZH}?iUFKn zcDTK4=@f&ZR>#2NcTbD=V1vObr$^Ch!_Kw074KjI7nBo$h=Dq_v?@-z*fF)?)}9lDv+2wCNOuys3_G{P2h?%Il>807M;R z^;(!c%@EynjH4DTikQlPA>W4OM?q$UEMJm`l18eb==qq}Zhos&4%c)`1`Vu!#zWfS zRy?wfqN2cQdzh~t=QZz`GYZDkIP*O99*T)WbRCELb-*hBSnikkbfsfFgCM2ahEibY zc}mlR6kxz7X8ufbO&LyuPW*$wL#j`+?&e3Zwuy2Olzn(D6Tl((!$S7ys&k=UH5q&~kVg$`v}UYyr8mz6e*$KkWd%fRBRU)%lWR+UlYR zYG9=%J|`<*dE>5vxGyc5JN6rSlQL2m$LfX{9E4$zmKNjGd1~p&25Ca;m&$dwb+HEOcq723Z-j1O&elr zRPH8l`y^5t(3!d+KS>r|I}sZa2Wf6dN{?4DUb1B7>^xbvD4&bNNh3!S!EPO5R;`*| z0a9kIVGS#YQIx?Yvja!Mwe`__nwOJ^_Ed_Th6{Y69@Pt&MFD)4^?8Ousfdqr587=2 zu1M@@;5*sTeU|0__g-K7lP8LQgODxIx7BM|Lq)yW!F%q~eY9J40DrV~8tGBiv2{hb zNvw6XOiS1CM%zp4alvMvtaT&(lZIVq28&qOD;})Ht zIvsH`NVmBGEJa>=jC^{|7(f%5?D`Q>2}`LMnVh}l1SjL22bfLI1mN-MV4kQXukvmq zL3It1BCE%+dNVszTZ{Z&M`V!+$r5H~SJu&tDH#SRf}JLsQ#8!Nm}Gac`?6!J9+#%+ zLkAooif0X6tYe*F#c)U(kEy6ED4(KPmkm!d7_kxCu?}X;+O7-?uC;@anE=PaLVVVwDFq z2nir}B#kFJ);^r_;?SG^n-x=xaki4;Ljd~KB4*FNa@n}QiMlr0kO36Q6^TZ(+K{$F zA=I>c4Z?G?W~yW>yk0)pdW6qkeEpcz!OPyk!w@g%9BV{r^T{2nDi=ux7MX)ZNlxyNT}nwsyTl=@8|-GpWOiQ#ZJ0uvzsG=G z=+7(4McI(SooxJ%09V~|X3Y>>I3s5>yomPC3tjwK6uQl)>ony5$(D{CMWe)4(z(k`3%T)lPFuUF^vT*gIA1-iYH7)RC}) zI>HfBcul5Eh3Rw{>(O11^%EU^@Ot6%w$-s~cWV8s5gfvs#6$4XM+=qHO?#-SBIWBH z9UD&#tyTe-l`88D^6lIOv~OL|3fMdF1ufgiPa+-G95QIg<>+`D=nY5G_rJh#?cA!$H1W4Rz`^GXZ&DDc=J=F~}CV5Y*!?d=W8 z(f67Kte99dtxWT(uiHWm1E)Trmh~W=73idA^)xH-lgf&1O=hLIsEOChJ2$<9kr&VY z?FFp>Wr}@Vv=u-VqCmV(>SF_{-qvDWLwtPK`*!(fc9!}99r@AC3x!rL9_v{!eJlQEzvM4eUV#k7W>)Ykh ziiY!7@423?vr~Tc`@JxXdL??mC;s}=;FDXaYf;8PFIw$e+Jh02$PGEQBVh&kf*zTlpDcH*oG0bw&GHn!%)0ybp-0_aeKOeJTC4CdvI+W7 zmi00kp#O6E)LRF1O-YsM))x@CMf_(U7h?tN9r$9b>hNn~&*5b+)B0E*E(kAkIP{Bs z=QG7EFS(93et*K4lm$0lH{O{$Aud?o(Bt_1h6BzS`Du>puFI3kN>Ek^&uQ?guW_+`M!gI#y$ioK0;_yX@XyCA-TyrNTcTkK8p=k}&(){AQ_?p>vhtMt&6})j(T4 znqJL@rf3Cm$q(PXjUo#SwN` zQtu|}_8{%D-ta(IJ2o~wnsbvC1d6dfeXO!_>z`{dp79zgySXKjs&|dshmsP7mIC^E5|&o!|AstB0v^iGGrD zRGMY!j8W(+kCSw|%s%eehil+}qoF)V=eh?R^YW`x<<{jhP^oN_r~d0Ol)Zoi+Z&|2 zw#-<8;#$EAL2}ly5W3OEFDY}JG;)qvV`Gf-LlkP08#k56TgO^u9KOrC<71j2_kVT) zE(rtj)bI9(f&;yl<*Rdd*OW<5{izz}zmEs{5`S4+yN*{rfV})h zNwB0f;LMD1J7-UbmxXgD!1qnUxgdzMLb>eNUx&YM2(dWOTx^u7(Lq@-7v};7%Wt9W zto0s{R$0vuFTh?H1y$r@1s8cvGr7!nO|V{4Kv2djG}>h-;{YUKjC8KzMG;1M~9 zw~=}$&&EM8HqH}1c(^*;&^_oLPkG$h(Kw07RLH@qPDyuzt^yW0 zfQz9Tf~&;su)M8`$LVf7Kzd9R8}4u>bicPxc1YC5J@TnfEtK1qPm^A7*1HjsgBls= z=?S?@Dtp{X$l?riwQdad_C8X&>pzX&GWD&&iF>{4Or5WPn|)lm6|e*N(yjG5XHvYc zrqzs)UBIh>Q9CpsZj<{r-dS|pHUQY!|0lV-Cdgr}%cPyix%mlVTEqn;- z7Sh_e?9j8Wo*?xgqqgBCl)#o8>h?(=%pjGi2^nI&xn`L2D^^*dmjS;4LJhqZW2tP$ zMQW000C|NklKLN-F58N?RvT$g4<+VewikfAVvqw5=%B8RVl+j#P z(R6Jzoqrf*5XMDn{B0~qvvV;;%aCgSK=`vu#s>>-xLVPf(%u?wC@y~Qi65&*0$cq{ z#q)wr_vQn&ZIAY^|I!Y9)@o>eEyoSs+Ya23m+`Xw)(+syw)7us(v-tx-Yxp%i!d4>#T1UR&`{e|^Q` zemrvnJ?%=q)zbHz1|?50E)#U0-8xrB=XxjE^P^Se+cpiIhG8QeoIaE^y1i zQ$RC+lA7H4OCXP?wjDxIdF`>#2n&6s|H=;FEBzDtp!Ww5WX^;8-TTipy2ehvDa#eG zzJ?mcmt8JT94Z****Hrm;h-D2yI+I?j-S=kY^m2fY~1n(E$+wTK0AOv9-q?(zDpzP z({kJaxWbHi#^>EQ+Yt(@N!uFDhJjJ8wZhKFPM_X-(7cf0=cbb;8u`k2(83``;hG75E?7W#fsz0j1FZ0000 Date: Mon, 6 Mar 2023 14:35:40 -0500 Subject: [PATCH 252/312] Specify `pak::pak()` for installing the dev version --- README.Rmd | 4 ++-- README.md | 4 ++-- 2 files changed, 4 insertions(+), 4 deletions(-) diff --git a/README.Rmd b/README.Rmd index 9ba2a042e..2c0cc726a 100644 --- a/README.Rmd +++ b/README.Rmd @@ -51,8 +51,8 @@ install.packages("vctrs") Alternatively, if you need the development version, install it with: ```{r, eval = FALSE} -# install.packages("devtools") -devtools::install_github("r-lib/vctrs") +# install.packages("pak") +pak::pak("r-lib/vctrs") ``` ## Usage diff --git a/README.md b/README.md index bea655040..4d9365bf8 100644 --- a/README.md +++ b/README.md @@ -52,8 +52,8 @@ install.packages("vctrs") Alternatively, if you need the development version, install it with: ``` r -# install.packages("devtools") -devtools::install_github("r-lib/vctrs") +# install.packages("pak") +pak::pak("r-lib/vctrs") ``` ## Usage From 3f3587233f0f0121cdde8d5c0680079503525f98 Mon Sep 17 00:00:00 2001 From: DavisVaughan Date: Mon, 6 Mar 2023 14:59:59 -0500 Subject: [PATCH 253/312] Remove `SystemRequirements` for `C++11` --- DESCRIPTION | 2 -- 1 file changed, 2 deletions(-) diff --git a/DESCRIPTION b/DESCRIPTION index 9d9e0df67..821a8a803 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -51,8 +51,6 @@ Suggests: zeallot VignetteBuilder: knitr -SystemRequirements: - C++11 Encoding: UTF-8 Language: en-GB Roxygen: list(markdown = TRUE) From 3ff3f858dccea7ca7fdd81c1a1d0c724a6edbbb1 Mon Sep 17 00:00:00 2001 From: DavisVaughan Date: Mon, 6 Mar 2023 15:01:55 -0500 Subject: [PATCH 254/312] Review NEWS --- NEWS.md | 36 ++++++++++++++++++------------------ 1 file changed, 18 insertions(+), 18 deletions(-) diff --git a/NEWS.md b/NEWS.md index cb4be0452..bd42cd2dd 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,40 +1,40 @@ # vctrs (development version) -* R >=3.5.0 is now explicitly required. This is in line with the tidyverse - policy of supporting the [5 most recent versions of - R](https://www.tidyverse.org/blog/2019/04/r-version-support/). +* New `vec_run_sizes()` for computing the size of each run within a vector. It + is identical to the `times` column from `vec_unrep()`, but is faster if you + don't need the run key (#1210). + +* New `obj_is_vector()`, `obj_check_vector()`, and `vec_check_size()` validation + helpers. We believe these are a better approach to vector validation than + `vec_assert()` and `vec_is()`, which have been marked as questioning because + the semantics of their `ptype` arguments are hard to define and can often be + replaced by `vec_cast()` or a type predicate function like + `rlang::is_logical()` (#1784). * `vec_is_list()` and `vec_check_list()` have been renamed to `obj_is_list()` and `obj_check_list()`, in line with the new `obj_is_vector()` helper. The old functions have been silently deprecated, but an official deprecation process will start in the next vctrs release (#1803). -* `vec_locate_matches()` has changed its default `needles_arg` and - `haystack_arg` values from `""` to `"needles"` and `"haystack"`, respectively. - This generally generates more informative error messages (#1792). - * `vec_locate_matches()` gains a new `relationship` argument that holistically handles multiple matches between `needles` and `haystack`. In particular, `relationship = "many-to-one"` replaces `multiple = "error"` and `multiple = "warning"`, which have been removed from the documentation and silently soft-deprecated. Official deprecation for those options will start in a future release (#1791). + +* `vec_locate_matches()` has changed its default `needles_arg` and + `haystack_arg` values from `""` to `"needles"` and `"haystack"`, respectively. + This generally generates more informative error messages (#1792). * `vec_slice()` has gained an `error_call` argument (#1785). -* New `obj_is_vector()`, `obj_check_vector()`, and `vec_check_size()` validation - helpers. We believe these are a better approach to vector validation than - `vec_assert()` and `vec_is()`, which have been marked as questioning because - the semantics of their `ptype` arguments are hard to define and can often be - replaced by `vec_cast()` or a type predicate function like - `rlang::is_logical()` (#1784). - * The `numeric_version` type from base R is now better supported in equality, comparison, and order based operations (tidyverse/dplyr#6680). - -* New `vec_run_sizes()` for computing the size of each run within a vector. It - is identical to the `times` column from `vec_unrep()`, but is faster if you - don't need the run key (#1210). + +* R >=3.5.0 is now explicitly required. This is in line with the tidyverse + policy of supporting the [5 most recent versions of + R](https://www.tidyverse.org/blog/2019/04/r-version-support/). # vctrs 0.5.2 From bdea1ceda10e3cb187ac2aa154d0180254cc270c Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Wed, 8 Mar 2023 09:37:47 +0100 Subject: [PATCH 255/312] Fix S3 method inconsistency for CRAN checks MIME-Version: 1.0 Content-Type: text/plain; charset=UTF-8 Content-Transfer-Encoding: 8bit Version: 0.5.2 Check: S3 generic/method consistency Result: WARN cnd_header: function(cnd, ...) cnd_header.vctrs_error_subscript_type: function(cnd) cnd_body: function(cnd, ...) cnd_body.vctrs_error_subscript_type: function(cnd) See section ‘Generic functions and methods’ in the ‘Writing R Extensions’ manual. Flavor: r-devel-linux-x86_64-debian-gcc --- R/subscript.R | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/R/subscript.R b/R/subscript.R index 5ffcd9993..3d267b930 100644 --- a/R/subscript.R +++ b/R/subscript.R @@ -174,7 +174,7 @@ new_error_subscript_type <- function(i, } #' @export -cnd_header.vctrs_error_subscript_type <- function(cnd) { +cnd_header.vctrs_error_subscript_type <- function(cnd, ...) { arg <- cnd[["subscript_arg"]] if (is_subscript_arg(arg)) { with <- glue::glue(" with {format_subscript_arg(arg)}") @@ -192,7 +192,7 @@ cnd_header.vctrs_error_subscript_type <- function(cnd) { } } #' @export -cnd_body.vctrs_error_subscript_type <- function(cnd) { +cnd_body.vctrs_error_subscript_type <- function(cnd, ...) { arg <- cnd_subscript_arg(cnd) type <- obj_type_friendly(cnd$i) expected_types <- cnd_subscript_expected_types(cnd) From 95b25458ba8ba3ba1a25497398b40de3e36fd1d6 Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Wed, 8 Mar 2023 15:01:01 +0100 Subject: [PATCH 256/312] Update logo --- man/figures/logo.png | Bin 66548 -> 66548 bytes 1 file changed, 0 insertions(+), 0 deletions(-) diff --git a/man/figures/logo.png b/man/figures/logo.png index 2665bb7e5d0eec4cd5cf78ee35dc528be7245eba..392e347a58d451a69a8df2168608ade78d5db3c1 100644 GIT binary patch delta 99 zcmey;&hn+5WkMAP2Oonfi?r5@#-^=JjDMJ1EkX=UtPBjSj7_wGq=CVq>s2lc3=FCz nt`Q|Ei6yC4x%nxXX_X8{21drZ20(Q2nuQozS{WN#85w9B7+4t?y!RB9V_;xV oEpd$~Nl7e8waU#;$xN$cFfuSQ)-?bkbPe-F)-IZUn3>TK01z=9EdT%j From aea901deec022e53a656c4e2921d06a8850f27ec Mon Sep 17 00:00:00 2001 From: Lionel Henry Date: Wed, 8 Mar 2023 15:02:21 +0100 Subject: [PATCH 257/312] Refer to "Posit Software" --- DESCRIPTION | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/DESCRIPTION b/DESCRIPTION index 821a8a803..4f29e93af 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -17,7 +17,7 @@ Authors@R: person(given = "data.table team", role = "cph", comment = "Radix sort based on data.table's forder() and their contribution to R's order()"), - person(given = "Posit, PBC", + person(given = "Posit Software, PBC", role = c("cph", "fnd"))) Description: Defines new notions of prototype and size that are used to provide tools for consistent and well-founded type-coercion From 469411a94ec1673912857a933681c2d873888345 Mon Sep 17 00:00:00 2001 From: DavisVaughan Date: Wed, 8 Mar 2023 09:58:49 -0500 Subject: [PATCH 258/312] Redocument with updated company name --- man/vctrs-package.Rd | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/man/vctrs-package.Rd b/man/vctrs-package.Rd index c35d1c2fd..e4279f1fa 100644 --- a/man/vctrs-package.Rd +++ b/man/vctrs-package.Rd @@ -33,7 +33,7 @@ Authors: Other contributors: \itemize{ \item data.table team (Radix sort based on data.table's forder() and their contribution to R's order()) [copyright holder] - \item Posit, PBC [copyright holder, funder] + \item Posit Software, PBC [copyright holder, funder] } } From daf24ece62b3ea421544a8646bc6962770b369ef Mon Sep 17 00:00:00 2001 From: Davis Vaughan Date: Thu, 9 Mar 2023 09:34:09 -0500 Subject: [PATCH 259/312] Implement `vec_chop(sizes = )` (#1813) * Fix typo in `init_compact_seq()` docs * Implement `sizes` for `vec_chop()` * Update `exp_vec_chop()` callable to use `vec_chop_unsafe()` * NEWS bullet * Specify `indices =` explicitly everywhere * Move the `...` to the right place With silent backwards compatible behavior for now * NEWS bullet --- NEWS.md | 10 + R/slice-chop.R | 79 ++++- R/type-misc.R | 2 +- man/vec_chop.Rd | 55 +++- man/vec_unchop.Rd | 8 +- src/bind.c | 2 +- src/c-unchop.c | 4 +- src/callables.c | 2 +- src/decl/slice-chop-decl.h | 30 +- src/globals.c | 1 + src/globals.h | 1 + src/init.c | 4 +- src/slice-chop.c | 455 +++++++++++++++++---------- src/slice-chop.h | 4 +- src/split.c | 2 +- src/utils.c | 2 +- src/vctrs.h | 1 - tests/testthat/_snaps/c.md | 6 +- tests/testthat/_snaps/slice-chop.md | 124 +++++++- tests/testthat/test-slice-chop.R | 177 +++++++++-- tests/testthat/test-slice.R | 2 +- tests/testthat/test-type-integer64.R | 6 +- 22 files changed, 736 insertions(+), 241 deletions(-) diff --git a/NEWS.md b/NEWS.md index bd42cd2dd..946a82f0a 100644 --- a/NEWS.md +++ b/NEWS.md @@ -4,6 +4,11 @@ is identical to the `times` column from `vec_unrep()`, but is faster if you don't need the run key (#1210). +* New `sizes` argument to `vec_chop()` which allows you to partition a vector + using an integer vector describing the size of each expected slice. It is + particularly useful in combination with `vec_run_sizes()` and `list_sizes()` + (#1210, #1598). + * New `obj_is_vector()`, `obj_check_vector()`, and `vec_check_size()` validation helpers. We believe these are a better approach to vector validation than `vec_assert()` and `vec_is()`, which have been marked as questioning because @@ -27,6 +32,11 @@ `haystack_arg` values from `""` to `"needles"` and `"haystack"`, respectively. This generally generates more informative error messages (#1792). +* `vec_chop()` has gained empty `...` between `x` and the optional `indices` + argument. For backwards compatibility, supplying `vec_chop(x, indices)` + without naming `indices` still silently works, but will be deprecated in a + future release (#1813). + * `vec_slice()` has gained an `error_call` argument (#1785). * The `numeric_version` type from base R is now better supported in equality, diff --git a/R/slice-chop.R b/R/slice-chop.R index f9c1ca198..7e6bc6648 100644 --- a/R/slice-chop.R +++ b/R/slice-chop.R @@ -16,7 +16,7 @@ #' holds: #' #' ``` -#' list_unchop(vec_chop(x, indices), indices) == x +#' list_unchop(vec_chop(x, indices = indices), indices = indices) == x #' ``` #' #' @inheritParams rlang::args_dots_empty @@ -24,7 +24,8 @@ #' #' @param x A vector #' @param indices For `vec_chop()`, a list of positive integer vectors to -#' slice `x` with, or `NULL`. If `NULL`, `x` is split into its individual +#' slice `x` with, or `NULL`. Can't be used if `sizes` is already specified. +#' If both `indices` and `sizes` are `NULL`, `x` is split into its individual #' elements, equivalent to using an `indices` of `as.list(vec_seq_along(x))`. #' #' For `list_unchop()`, a list of positive integer vectors specifying the @@ -32,12 +33,22 @@ #' the size of the corresponding index vector. The size of `indices` must #' match the size of `x`. If `NULL`, `x` is combined in the order it is #' provided in, which is equivalent to using [vec_c()]. +#' @param sizes An integer vector of non-negative sizes representing sequential +#' indices to slice `x` with, or `NULL`. Can't be used if `indices` is already +#' specified. +#' +#' For example, `sizes = c(2, 4)` is equivalent to `indices = list(1:2, 3:6)`, +#' but is typically faster. +#' +#' `sum(sizes)` must be equal to `vec_size(x)`, i.e. `sizes` must completely +#' partition `x`, but an individual size is allowed to be `0`. #' @param ptype If `NULL`, the default, the output type is determined by #' computing the common type across all elements of `x`. Alternatively, you #' can supply `ptype` to give the output a known type. #' @return -#' - `vec_chop()`: A list of size `vec_size(indices)` or, if `indices == NULL`, -#' `vec_size(x)`. +#' - `vec_chop()`: A list where each element has the same type as `x`. The size +#' of the list is equal to `vec_size(indices)`, `vec_size(sizes)`, or +#' `vec_size(x)` depending on whether or not `indices` or `sizes` is provided. #' #' - `list_unchop()`: A vector of type `vec_ptype_common(!!!x)`, or `ptype`, if #' specified. The size is computed as `vec_size_common(!!!indices)` unless @@ -52,15 +63,20 @@ #' @export #' @examples #' vec_chop(1:5) -#' vec_chop(1:5, list(1, 1:2)) -#' vec_chop(mtcars, list(1:3, 4:6)) +#' +#' # These two are equivalent +#' vec_chop(1:5, indices = list(1:2, 3:5)) +#' vec_chop(1:5, sizes = c(2, 3)) +#' +#' # Can also be used on data frames +#' vec_chop(mtcars, indices = list(1:3, 4:6)) #' #' # If `indices` selects every value in `x` exactly once, #' # in any order, then `list_unchop()` inverts `vec_chop()` #' x <- c("a", "b", "c", "d") #' indices <- list(2, c(3, 1), 4) -#' vec_chop(x, indices) -#' list_unchop(vec_chop(x, indices), indices = indices) +#' vec_chop(x, indices = indices) +#' list_unchop(vec_chop(x, indices = indices), indices = indices) #' #' # When unchopping, size 1 elements of `x` are recycled #' # to the size of the corresponding index @@ -75,7 +91,7 @@ #' # `vec_chop()` and `list_unchop()` in combination with `vec_group_loc()` #' ave2 <- function(.x, .by, .f, ...) { #' indices <- vec_group_loc(.by)$loc -#' chopped <- vec_chop(.x, indices) +#' chopped <- vec_chop(.x, indices = indices) #' out <- lapply(chopped, .f, ...) #' list_unchop(out, indices = indices) #' } @@ -89,8 +105,49 @@ #' ave2(breaks, wool, mean), #' ave(breaks, wool, FUN = mean) #' ) -vec_chop <- function(x, indices = NULL) { - .Call(ffi_vec_chop, x, indices) +#' +#' # If you know your input is sorted and you'd like to split on the groups, +#' # `vec_run_sizes()` can be efficiently combined with `sizes` +#' df <- data_frame( +#' g = c(2, 5, 5, 6, 6, 6, 6, 8, 9, 9), +#' x = 1:10 +#' ) +#' vec_chop(df, sizes = vec_run_sizes(df$g)) +#' +#' # If you have a list of homogeneous vectors, sometimes it can be useful to +#' # unchop, apply a function to the flattened vector, and then rechop according +#' # to the original indices. This can be done efficiently with `list_sizes()`. +#' x <- list(c(1, 2, 1), c(3, 1), 5, double()) +#' x_flat <- list_unchop(x) +#' x_flat <- x_flat + max(x_flat) +#' vec_chop(x_flat, sizes = list_sizes(x)) +vec_chop <- function(x, ..., indices = NULL, sizes = NULL) { + if (!missing(...)) { + indices <- check_dots_chop(..., indices = indices) + } + .Call(ffi_vec_chop, x, indices, sizes) +} + +check_dots_chop <- function(..., indices = NULL, call = caller_env()) { + if (!is_null(indices)) { + # Definitely can't supply both `indices` and `...` + check_dots_empty0(..., call = call) + } + + if (dots_n(...) != 1L) { + # Backwards compatible case doesn't allow for length >1 `...`. + # This must be an error case. + check_dots_empty0(..., call = call) + } + + # TODO: Soft-deprecate this after dplyr/tidyr have updated all `vec_chop()` + # calls to be explicit about `indices =` + + # Assume this is an old style `vec_chop(x, indices)` call, before we + # added the `...` + indices <- list(...)[[1L]] + + indices } #' @rdname vec_chop diff --git a/R/type-misc.R b/R/type-misc.R index 56399d690..13c06d237 100644 --- a/R/type-misc.R +++ b/R/type-misc.R @@ -63,7 +63,7 @@ proxy_equal_numeric_version <- function(x, error_call = caller_env()) { index <- index + size } - out <- vec_chop(x, indices) + out <- vec_chop(x, indices = indices) n_zeros <- N_COMPONENTS - max diff --git a/man/vec_chop.Rd b/man/vec_chop.Rd index 6422e2233..d612edb9c 100644 --- a/man/vec_chop.Rd +++ b/man/vec_chop.Rd @@ -5,7 +5,7 @@ \alias{list_unchop} \title{Chopping} \usage{ -vec_chop(x, indices = NULL) +vec_chop(x, ..., indices = NULL, sizes = NULL) list_unchop( x, @@ -22,8 +22,11 @@ list_unchop( \arguments{ \item{x}{A vector} +\item{...}{These dots are for future extensions and must be empty.} + \item{indices}{For \code{vec_chop()}, a list of positive integer vectors to -slice \code{x} with, or \code{NULL}. If \code{NULL}, \code{x} is split into its individual +slice \code{x} with, or \code{NULL}. Can't be used if \code{sizes} is already specified. +If both \code{indices} and \code{sizes} are \code{NULL}, \code{x} is split into its individual elements, equivalent to using an \code{indices} of \code{as.list(vec_seq_along(x))}. For \code{list_unchop()}, a list of positive integer vectors specifying the @@ -32,7 +35,15 @@ the size of the corresponding index vector. The size of \code{indices} must match the size of \code{x}. If \code{NULL}, \code{x} is combined in the order it is provided in, which is equivalent to using \code{\link[=vec_c]{vec_c()}}.} -\item{...}{These dots are for future extensions and must be empty.} +\item{sizes}{An integer vector of non-negative sizes representing sequential +indices to slice \code{x} with, or \code{NULL}. Can't be used if \code{indices} is already +specified. + +For example, \code{sizes = c(2, 4)} is equivalent to \code{indices = list(1:2, 3:6)}, +but is typically faster. + +\code{sum(sizes)} must be equal to \code{vec_size(x)}, i.e. \code{sizes} must completely +partition \code{x}, but an individual size is allowed to be \code{0}.} \item{ptype}{If \code{NULL}, the default, the output type is determined by computing the common type across all elements of \code{x}. Alternatively, you @@ -70,8 +81,9 @@ mentioned in error messages as the source of the error. See the } \value{ \itemize{ -\item \code{vec_chop()}: A list of size \code{vec_size(indices)} or, if \code{indices == NULL}, -\code{vec_size(x)}. +\item \code{vec_chop()}: A list where each element has the same type as \code{x}. The size +of the list is equal to \code{vec_size(indices)}, \code{vec_size(sizes)}, or +\code{vec_size(x)} depending on whether or not \code{indices} or \code{sizes} is provided. \item \code{list_unchop()}: A vector of type \code{vec_ptype_common(!!!x)}, or \code{ptype}, if specified. The size is computed as \code{vec_size_common(!!!indices)} unless the indices are \code{NULL}, in which case the size is \code{vec_size_common(!!!x)}. @@ -93,7 +105,7 @@ If \code{indices} selects every value in \code{x} exactly once, in any order, th \code{list_unchop()} is the inverse of \code{vec_chop()} and the following invariant holds: -\if{html}{\out{

-## In both +## Error before installation -* checking whether package ‘bayesnec’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/bayesnec/new/bayesnec.Rcheck/00install.out’ for details. - ``` +### Devel -* checking package dependencies ... NOTE - ``` - Package suggested but not available for checking: ‘rstan’ - ``` +``` +* using log directory ‘/tmp/workdir/bayesnec/new/bayesnec.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘bayesnec/DESCRIPTION’ ... OK +* this is package ‘bayesnec’ version ‘2.1.0.2’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘brms’ + +Package suggested but not available for checking: ‘rstan’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR -## Installation -### Devel -``` -* installing *source* package ‘bayesnec’ ... -** package ‘bayesnec’ successfully unpacked and MD5 sums checked -** using staged installation -** R -** data -*** moving datasets to lazyload DB -Warning: namespace ‘rstan’ is not available and has been replaced -by .GlobalEnv when processing object ‘manec_example’ -Warning: namespace ‘brms’ is not available and has been replaced -by .GlobalEnv when processing object ‘manec_example’ -... -by .GlobalEnv when processing object ‘manec_example’ -Warning: namespace ‘rstan’ is not available and has been replaced -by .GlobalEnv when processing object ‘manec_example’ -** inst -** byte-compile and prepare package for lazy loading -Error: package or namespace load failed for ‘brms’ in loadNamespace(j <- imp[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): - there is no package called ‘rstan’ -Execution halted -ERROR: lazy loading failed for package ‘bayesnec’ -* removing ‘/tmp/workdir/bayesnec/new/bayesnec.Rcheck/bayesnec’ ``` ### CRAN ``` -* installing *source* package ‘bayesnec’ ... -** package ‘bayesnec’ successfully unpacked and MD5 sums checked -** using staged installation -** R -** data -*** moving datasets to lazyload DB -Warning: namespace ‘rstan’ is not available and has been replaced -by .GlobalEnv when processing object ‘manec_example’ -Warning: namespace ‘brms’ is not available and has been replaced -by .GlobalEnv when processing object ‘manec_example’ -... -by .GlobalEnv when processing object ‘manec_example’ -Warning: namespace ‘rstan’ is not available and has been replaced -by .GlobalEnv when processing object ‘manec_example’ -** inst -** byte-compile and prepare package for lazy loading -Error: package or namespace load failed for ‘brms’ in loadNamespace(j <- imp[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): - there is no package called ‘rstan’ -Execution halted -ERROR: lazy loading failed for package ‘bayesnec’ -* removing ‘/tmp/workdir/bayesnec/old/bayesnec.Rcheck/bayesnec’ +* using log directory ‘/tmp/workdir/bayesnec/old/bayesnec.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘bayesnec/DESCRIPTION’ ... OK +* this is package ‘bayesnec’ version ‘2.1.0.2’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘brms’ + +Package suggested but not available for checking: ‘rstan’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + ``` @@ -836,7 +954,7 @@ Run `revdepcheck::cloud_details(, "BayesPostEst")` for more info * package encoding: UTF-8 * checking package namespace information ... OK * checking package dependencies ... ERROR -Package required but not available: ‘rstanarm’ +Packages required but not available: 'rstanarm', 'brms' Package suggested but not available for checking: ‘rstan’ @@ -864,7 +982,7 @@ Status: 1 ERROR * package encoding: UTF-8 * checking package namespace information ... OK * checking package dependencies ... ERROR -Package required but not available: ‘rstanarm’ +Packages required but not available: 'rstanarm', 'brms' Package suggested but not available for checking: ‘rstan’ @@ -945,6 +1063,74 @@ Status: 1 ERROR +``` +# 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: 145 + +Run `revdepcheck::cloud_details(, "bdl")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/bdl/new/bdl.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘bdl/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘bdl’ version ‘1.0.5’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘sf’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/bdl/old/bdl.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘bdl/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘bdl’ version ‘1.0.5’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘sf’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + ``` # beadplexr @@ -1022,65 +1208,79 @@ Status: 1 NOTE ``` -# BiplotML +# BiodiversityR
-* Version: 1.1.0 -* GitHub: https://github.com/jgbabativam/BiplotML -* Source code: https://github.com/cran/BiplotML -* Date/Publication: 2022-04-22 21:20:02 UTC -* Number of recursive dependencies: 88 +* Version: 2.15-1 +* GitHub: NA +* Source code: https://github.com/cran/BiodiversityR +* Date/Publication: 2023-01-06 10:00:30 UTC +* Number of recursive dependencies: 300 -Run `revdepcheck::cloud_details(, "BiplotML")` for more info +Run `revdepcheck::cloud_details(, "BiodiversityR")` for more info
-## In both - -* checking whether package ‘BiplotML’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/BiplotML/new/BiplotML.Rcheck/00install.out’ for details. - ``` - -## Installation +## Error before installation ### Devel ``` -* installing *source* package ‘BiplotML’ ... -** package ‘BiplotML’ 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 ‘shapes’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): - there is no package called ‘htmlwidgets’ -Execution halted -ERROR: lazy loading failed for package ‘BiplotML’ -* removing ‘/tmp/workdir/BiplotML/new/BiplotML.Rcheck/BiplotML’ +* using log directory ‘/tmp/workdir/BiodiversityR/new/BiodiversityR.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘BiodiversityR/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘BiodiversityR’ version ‘2.15-1’ +* checking package namespace information ... OK +* checking package dependencies ... NOTE +... +* 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: 2 NOTEs + + + ``` ### CRAN ``` -* installing *source* package ‘BiplotML’ ... -** package ‘BiplotML’ 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 ‘shapes’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): - there is no package called ‘htmlwidgets’ -Execution halted -ERROR: lazy loading failed for package ‘BiplotML’ -* removing ‘/tmp/workdir/BiplotML/old/BiplotML.Rcheck/BiplotML’ +* using log directory ‘/tmp/workdir/BiodiversityR/old/BiodiversityR.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘BiodiversityR/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘BiodiversityR’ version ‘2.15-1’ +* checking package namespace information ... OK +* checking package dependencies ... NOTE +... +* 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: 2 NOTEs + + + ``` @@ -1450,16 +1650,17 @@ Run `revdepcheck::cloud_details(, "BUSpaRse")` for more info ``` -# cattonum +# cancensus
-* Version: NA -* GitHub: NA -* Source code: https://github.com/cran/cattonum -* Number of recursive dependencies: 78 +* Version: 0.5.5 +* GitHub: https://github.com/mountainMath/cancensus +* Source code: https://github.com/cran/cancensus +* Date/Publication: 2023-01-23 08:40:06 UTC +* Number of recursive dependencies: 117 -Run `revdepcheck::cloud_details(, "cattonum")` for more info +Run `revdepcheck::cloud_details(, "cancensus")` for more info
@@ -1468,7 +1669,27 @@ Run `revdepcheck::cloud_details(, "cattonum")` for more info ### Devel ``` - +* using log directory ‘/tmp/workdir/cancensus/new/cancensus.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘cancensus/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘cancensus’ version ‘0.5.5’ +* package encoding: UTF-8 +* checking package namespace information ... OK +... + ‘Making_maps_with_cancensus.Rmd’ using ‘UTF-8’... OK + ‘Taxfiler_Data.Rmd’ using ‘UTF-8’... OK + ‘cancensus.Rmd’ using ‘UTF-8’... OK + ‘data_discovery.Rmd’ using ‘UTF-8’... OK + ‘intersecting_geometries.Rmd’ using ‘UTF-8’... OK + ‘statcan_attribute_files.Rmd’ using ‘UTF-8’... OK + ‘statcan_wds.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 3 NOTEs @@ -1478,23 +1699,43 @@ Run `revdepcheck::cloud_details(, "cattonum")` for more info ### CRAN ``` - +* using log directory ‘/tmp/workdir/cancensus/old/cancensus.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘cancensus/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘cancensus’ version ‘0.5.5’ +* package encoding: UTF-8 +* checking package namespace information ... OK +... + ‘Making_maps_with_cancensus.Rmd’ using ‘UTF-8’... OK + ‘Taxfiler_Data.Rmd’ using ‘UTF-8’... OK + ‘cancensus.Rmd’ using ‘UTF-8’... OK + ‘data_discovery.Rmd’ using ‘UTF-8’... OK + ‘intersecting_geometries.Rmd’ using ‘UTF-8’... OK + ‘statcan_attribute_files.Rmd’ using ‘UTF-8’... OK + ‘statcan_wds.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 3 NOTEs ``` -# ceRNAnetsim +# cattonum
* Version: NA * GitHub: NA -* Source code: https://github.com/cran/ceRNAnetsim -* Number of recursive dependencies: 99 +* Source code: https://github.com/cran/cattonum +* Number of recursive dependencies: 78 -Run `revdepcheck::cloud_details(, "ceRNAnetsim")` for more info +Run `revdepcheck::cloud_details(, "cattonum")` for more info
@@ -1520,17 +1761,17 @@ Run `revdepcheck::cloud_details(, "ceRNAnetsim")` for more info ``` -# ChineseNames +# CCAMLRGIS
-* Version: 1.1.1 -* GitHub: https://github.com/psychbruce/ChineseNames -* Source code: https://github.com/cran/ChineseNames -* Date/Publication: 2021-11-29 16:40:02 UTC -* Number of recursive dependencies: 156 +* Version: 4.0.4 +* GitHub: https://github.com/ccamlr/CCAMLRGIS +* Source code: https://github.com/cran/CCAMLRGIS +* Date/Publication: 2023-02-07 04:12:37 UTC +* Number of recursive dependencies: 72 -Run `revdepcheck::cloud_details(, "ChineseNames")` for more info +Run `revdepcheck::cloud_details(, "CCAMLRGIS")` for more info
@@ -1539,17 +1780,18 @@ Run `revdepcheck::cloud_details(, "ChineseNames")` for more info ### Devel ``` -* using log directory ‘/tmp/workdir/ChineseNames/new/ChineseNames.Rcheck’ +* using log directory ‘/tmp/workdir/CCAMLRGIS/new/CCAMLRGIS.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘ChineseNames/DESCRIPTION’ ... OK -* this is package ‘ChineseNames’ version ‘1.1.1’ +* checking for file ‘CCAMLRGIS/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘CCAMLRGIS’ version ‘4.0.4’ * package encoding: UTF-8 * checking package namespace information ... OK * checking package dependencies ... ERROR -Package required but not available: ‘bruceR’ +Package required but not available: ‘sf’ See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ manual. @@ -1564,17 +1806,18 @@ Status: 1 ERROR ### CRAN ``` -* using log directory ‘/tmp/workdir/ChineseNames/old/ChineseNames.Rcheck’ +* using log directory ‘/tmp/workdir/CCAMLRGIS/old/CCAMLRGIS.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘ChineseNames/DESCRIPTION’ ... OK -* this is package ‘ChineseNames’ version ‘1.1.1’ +* checking for file ‘CCAMLRGIS/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘CCAMLRGIS’ version ‘4.0.4’ * package encoding: UTF-8 * checking package namespace information ... OK * checking package dependencies ... ERROR -Package required but not available: ‘bruceR’ +Package required but not available: ‘sf’ See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ manual. @@ -1586,17 +1829,16 @@ Status: 1 ERROR ``` -# cinaR +# ceRNAnetsim
-* Version: 0.2.3 -* GitHub: https://github.com/eonurk/cinaR -* Source code: https://github.com/cran/cinaR -* Date/Publication: 2022-05-18 14:00:09 UTC -* Number of recursive dependencies: 178 +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/ceRNAnetsim +* Number of recursive dependencies: 99 -Run `revdepcheck::cloud_details(, "cinaR")` for more info +Run `revdepcheck::cloud_details(, "ceRNAnetsim")` for more info
@@ -1605,23 +1847,7 @@ Run `revdepcheck::cloud_details(, "cinaR")` for more info ### Devel ``` -* using log directory ‘/tmp/workdir/cinaR/new/cinaR.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘cinaR/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘cinaR’ version ‘0.2.3’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘ChIPseeker’ -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR @@ -1631,40 +1857,24 @@ Status: 1 ERROR ### CRAN ``` -* using log directory ‘/tmp/workdir/cinaR/old/cinaR.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘cinaR/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘cinaR’ version ‘0.2.3’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘ChIPseeker’ -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR ``` -# clustermole +# ChineseNames
-* Version: 1.1.0 -* GitHub: https://github.com/igordot/clustermole -* Source code: https://github.com/cran/clustermole -* Date/Publication: 2021-01-26 06:40:02 UTC -* Number of recursive dependencies: 149 +* Version: 1.1.1 +* GitHub: https://github.com/psychbruce/ChineseNames +* Source code: https://github.com/cran/ChineseNames +* Date/Publication: 2021-11-29 16:40:02 UTC +* Number of recursive dependencies: 151 -Run `revdepcheck::cloud_details(, "clustermole")` for more info +Run `revdepcheck::cloud_details(, "ChineseNames")` for more info
@@ -1673,18 +1883,17 @@ Run `revdepcheck::cloud_details(, "clustermole")` for more info ### Devel ``` -* using log directory ‘/tmp/workdir/clustermole/new/clustermole.Rcheck’ +* using log directory ‘/tmp/workdir/ChineseNames/new/ChineseNames.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘clustermole/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘clustermole’ version ‘1.1.0’ +* checking for file ‘ChineseNames/DESCRIPTION’ ... OK +* this is package ‘ChineseNames’ version ‘1.1.1’ * package encoding: UTF-8 * checking package namespace information ... OK * checking package dependencies ... ERROR -Packages required but not available: 'GSVA', 'singscore' +Package required but not available: ‘bruceR’ See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ manual. @@ -1699,18 +1908,17 @@ Status: 1 ERROR ### CRAN ``` -* using log directory ‘/tmp/workdir/clustermole/old/clustermole.Rcheck’ +* using log directory ‘/tmp/workdir/ChineseNames/old/ChineseNames.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘clustermole/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘clustermole’ version ‘1.1.0’ +* checking for file ‘ChineseNames/DESCRIPTION’ ... OK +* this is package ‘ChineseNames’ version ‘1.1.1’ * package encoding: UTF-8 * checking package namespace information ... OK * checking package dependencies ... ERROR -Packages required but not available: 'GSVA', 'singscore' +Package required but not available: ‘bruceR’ See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ manual. @@ -1722,26 +1930,26 @@ Status: 1 ERROR ``` -# cmstatr +# choroplethr
-* Version: 0.9.1 -* GitHub: https://github.com/cmstatr/cmstatr -* Source code: https://github.com/cran/cmstatr -* Date/Publication: 2021-09-30 16:50:02 UTC -* Number of recursive dependencies: 86 +* Version: 3.7.1 +* GitHub: NA +* Source code: https://github.com/cran/choroplethr +* Date/Publication: 2022-10-05 07:10:06 UTC +* Number of recursive dependencies: 127 -Run `revdepcheck::cloud_details(, "cmstatr")` for more info +Run `revdepcheck::cloud_details(, "choroplethr")` for more info
## In both -* checking whether package ‘cmstatr’ can be installed ... ERROR +* checking whether package ‘choroplethr’ can be installed ... ERROR ``` Installation failed. - See ‘/tmp/workdir/cmstatr/new/cmstatr.Rcheck/00install.out’ for details. + See ‘/tmp/workdir/choroplethr/new/choroplethr.Rcheck/00install.out’ for details. ``` ## Installation @@ -1749,40 +1957,104 @@ Run `revdepcheck::cloud_details(, "cmstatr")` for more info ### Devel ``` -* installing *source* package ‘cmstatr’ ... -** package ‘cmstatr’ successfully unpacked and MD5 sums checked +* installing *source* package ‘choroplethr’ ... +** package ‘choroplethr’ 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 ‘scales’ + there is no package called ‘sf’ Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart Execution halted -ERROR: lazy loading failed for package ‘cmstatr’ -* removing ‘/tmp/workdir/cmstatr/new/cmstatr.Rcheck/cmstatr’ +ERROR: lazy loading failed for package ‘choroplethr’ +* removing ‘/tmp/workdir/choroplethr/new/choroplethr.Rcheck/choroplethr’ ``` ### CRAN ``` -* installing *source* package ‘cmstatr’ ... -** package ‘cmstatr’ successfully unpacked and MD5 sums checked +* installing *source* package ‘choroplethr’ ... +** package ‘choroplethr’ 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 ‘scales’ + there is no package called ‘sf’ Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart Execution halted -ERROR: lazy loading failed for package ‘cmstatr’ -* removing ‘/tmp/workdir/cmstatr/old/cmstatr.Rcheck/cmstatr’ +ERROR: lazy loading failed for package ‘choroplethr’ +* removing ‘/tmp/workdir/choroplethr/old/choroplethr.Rcheck/choroplethr’ + + +``` +# cinaR + +
+ +* Version: 0.2.3 +* GitHub: https://github.com/eonurk/cinaR +* Source code: https://github.com/cran/cinaR +* Date/Publication: 2022-05-18 14:00:09 UTC +* Number of recursive dependencies: 178 + +Run `revdepcheck::cloud_details(, "cinaR")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/cinaR/new/cinaR.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘cinaR/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘cinaR’ version ‘0.2.3’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘ChIPseeker’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/cinaR/old/cinaR.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘cinaR/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘cinaR’ version ‘0.2.3’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘ChIPseeker’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + ``` @@ -1821,26 +2093,26 @@ Run `revdepcheck::cloud_details(, "COMPASS")` for more info ``` -# conflicted +# CoordinateCleaner
-* Version: 1.2.0 -* GitHub: https://github.com/r-lib/conflicted -* Source code: https://github.com/cran/conflicted -* Date/Publication: 2023-02-01 08:20:06 UTC -* Number of recursive dependencies: 49 +* Version: 2.0-20 +* GitHub: https://github.com/ropensci/CoordinateCleaner +* Source code: https://github.com/cran/CoordinateCleaner +* Date/Publication: 2021-10-21 17:10:05 UTC +* Number of recursive dependencies: 115 -Run `revdepcheck::cloud_details(, "conflicted")` for more info +Run `revdepcheck::cloud_details(, "CoordinateCleaner")` for more info
## In both -* checking whether package ‘conflicted’ can be installed ... ERROR +* checking whether package ‘CoordinateCleaner’ can be installed ... ERROR ``` Installation failed. - See ‘/tmp/workdir/conflicted/new/conflicted.Rcheck/00install.out’ for details. + See ‘/tmp/workdir/CoordinateCleaner/new/CoordinateCleaner.Rcheck/00install.out’ for details. ``` ## Installation @@ -1848,59 +2120,54 @@ Run `revdepcheck::cloud_details(, "conflicted")` for more info ### Devel ``` -* installing *source* package ‘conflicted’ ... -** package ‘conflicted’ successfully unpacked and MD5 sums checked +* installing *source* package ‘CoordinateCleaner’ ... +** package ‘CoordinateCleaner’ 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 -** help -*** installing help indices -** building package indices -** testing if installed package can be loaded from temporary location -Error: package or namespace load failed for ‘conflicted’: - .onLoad failed in loadNamespace() for 'conflicted', details: - call: loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) - error: there is no package called ‘cachem’ -Error: loading failed +Error in loadNamespace(i, c(lib.loc, .libPaths()), versionCheck = vI[[i]]) : + there is no package called ‘sf’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart Execution halted -ERROR: loading failed -* removing ‘/tmp/workdir/conflicted/new/conflicted.Rcheck/conflicted’ +ERROR: lazy loading failed for package ‘CoordinateCleaner’ +* removing ‘/tmp/workdir/CoordinateCleaner/new/CoordinateCleaner.Rcheck/CoordinateCleaner’ ``` ### CRAN ``` -* installing *source* package ‘conflicted’ ... -** package ‘conflicted’ successfully unpacked and MD5 sums checked +* installing *source* package ‘CoordinateCleaner’ ... +** package ‘CoordinateCleaner’ 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 -** help -*** installing help indices -** building package indices -** testing if installed package can be loaded from temporary location -Error: package or namespace load failed for ‘conflicted’: - .onLoad failed in loadNamespace() for 'conflicted', details: - call: loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) - error: there is no package called ‘cachem’ -Error: loading failed +Error in loadNamespace(i, c(lib.loc, .libPaths()), versionCheck = vI[[i]]) : + there is no package called ‘sf’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart Execution halted -ERROR: loading failed -* removing ‘/tmp/workdir/conflicted/old/conflicted.Rcheck/conflicted’ +ERROR: lazy loading failed for package ‘CoordinateCleaner’ +* removing ‘/tmp/workdir/CoordinateCleaner/old/CoordinateCleaner.Rcheck/CoordinateCleaner’ ``` -# cort +# CopernicusMarine
-* Version: NA -* GitHub: NA -* Source code: https://github.com/cran/cort -* Number of recursive dependencies: 75 +* Version: 0.0.6 +* GitHub: https://github.com/pepijn-devries/CopernicusMarine +* Source code: https://github.com/cran/CopernicusMarine +* Date/Publication: 2023-01-30 13:50:02 UTC +* Number of recursive dependencies: 113 -Run `revdepcheck::cloud_details(, "cort")` for more info +Run `revdepcheck::cloud_details(, "CopernicusMarine")` for more info
@@ -1909,7 +2176,23 @@ Run `revdepcheck::cloud_details(, "cort")` for more info ### Devel ``` +* using log directory ‘/tmp/workdir/CopernicusMarine/new/CopernicusMarine.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘CopernicusMarine/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘CopernicusMarine’ version ‘0.0.6’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘sf’ +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR @@ -1919,10 +2202,61 @@ Run `revdepcheck::cloud_details(, "cort")` for more info ### CRAN ``` +* using log directory ‘/tmp/workdir/CopernicusMarine/old/CopernicusMarine.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘CopernicusMarine/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘CopernicusMarine’ version ‘0.0.6’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘sf’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# cort + +
+ +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/cort +* Number of recursive dependencies: 75 + +Run `revdepcheck::cloud_details(, "cort")` for more info + +
+ +## Error before installation + +### Devel + +``` + + + + + + +``` +### CRAN + +``` + - ``` @@ -2072,16 +2406,17 @@ Run `revdepcheck::cloud_details(, "ctDNAtools")` for more info ``` -# CytoML +# cubble
-* Version: NA -* GitHub: NA -* Source code: https://github.com/cran/CytoML -* Number of recursive dependencies: 105 +* Version: 0.2.0 +* GitHub: https://github.com/huizezhang-sherry/cubble +* Source code: https://github.com/cran/cubble +* Date/Publication: 2022-11-17 12:30:02 UTC +* Number of recursive dependencies: 132 -Run `revdepcheck::cloud_details(, "CytoML")` for more info +Run `revdepcheck::cloud_details(, "cubble")` for more info
@@ -2090,42 +2425,24 @@ Run `revdepcheck::cloud_details(, "CytoML")` for more info ### Devel ``` +* using log directory ‘/tmp/workdir/cubble/new/cubble.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘cubble/DESCRIPTION’ ... OK +* this is package ‘cubble’ version ‘0.2.0’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘sf’ +Package suggested but not available for checking: ‘ozmaps’ - - - - -``` -### CRAN - -``` - - - - - - -``` -# D2MCS - -
- -* Version: NA -* GitHub: NA -* Source code: https://github.com/cran/D2MCS -* Number of recursive dependencies: 179 - -Run `revdepcheck::cloud_details(, "D2MCS")` for more info - -
- -## Error before installation - -### Devel - -``` - +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR @@ -2135,24 +2452,41 @@ Run `revdepcheck::cloud_details(, "D2MCS")` for more info ### CRAN ``` +* using log directory ‘/tmp/workdir/cubble/old/cubble.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘cubble/DESCRIPTION’ ... OK +* this is package ‘cubble’ version ‘0.2.0’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘sf’ +Package suggested but not available for checking: ‘ozmaps’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR ``` -# datawizard +# cxr
-* Version: 0.6.5 -* GitHub: https://github.com/easystats/datawizard -* Source code: https://github.com/cran/datawizard -* Date/Publication: 2022-12-14 23:50:02 UTC -* Number of recursive dependencies: 191 +* Version: 1.0.0 +* GitHub: https://github.com/RadicalCommEcol/cxr +* Source code: https://github.com/cran/cxr +* Date/Publication: 2021-04-16 09:20:02 UTC +* Number of recursive dependencies: 128 -Run `revdepcheck::cloud_details(, "datawizard")` for more info +Run `revdepcheck::cloud_details(, "cxr")` for more info
@@ -2161,27 +2495,27 @@ Run `revdepcheck::cloud_details(, "datawizard")` for more info ### Devel ``` -* using log directory ‘/tmp/workdir/datawizard/new/datawizard.Rcheck’ +* using log directory ‘/tmp/workdir/cxr/new/cxr.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘datawizard/DESCRIPTION’ ... OK +* checking for file ‘cxr/DESCRIPTION’ ... OK * checking extension type ... Package -* this is package ‘datawizard’ version ‘0.6.5’ +* this is package ‘cxr’ version ‘1.0.0’ * package encoding: UTF-8 * checking package namespace information ... 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 - ‘selection_syntax.Rmd’ using ‘UTF-8’... OK - ‘standardize_data.Rmd’ using ‘UTF-8’... OK - ‘tidyverse_translation.Rmd’ using ‘UTF-8’... OK + ‘V1_Getting_started.Rmd’ using ‘UTF-8’... OK + ‘V2_Data_formats.Rmd’ using ‘UTF-8’... OK + ‘V3_Coexistence_metrics.Rmd’ using ‘UTF-8’... OK + ‘V4_Models.Rmd’ using ‘UTF-8’... OK + ‘V5_Abundance_projections.Rmd’ using ‘UTF-8’... OK * checking re-building of vignette outputs ... OK * DONE -Status: 1 NOTE +Status: OK @@ -2191,43 +2525,44 @@ Status: 1 NOTE ### CRAN ``` -* using log directory ‘/tmp/workdir/datawizard/old/datawizard.Rcheck’ +* using log directory ‘/tmp/workdir/cxr/old/cxr.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘datawizard/DESCRIPTION’ ... OK +* checking for file ‘cxr/DESCRIPTION’ ... OK * checking extension type ... Package -* this is package ‘datawizard’ version ‘0.6.5’ +* this is package ‘cxr’ version ‘1.0.0’ * package encoding: UTF-8 * checking package namespace information ... 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 - ‘selection_syntax.Rmd’ using ‘UTF-8’... OK - ‘standardize_data.Rmd’ using ‘UTF-8’... OK - ‘tidyverse_translation.Rmd’ using ‘UTF-8’... OK + ‘V1_Getting_started.Rmd’ using ‘UTF-8’... OK + ‘V2_Data_formats.Rmd’ using ‘UTF-8’... OK + ‘V3_Coexistence_metrics.Rmd’ using ‘UTF-8’... OK + ‘V4_Models.Rmd’ using ‘UTF-8’... OK + ‘V5_Abundance_projections.Rmd’ using ‘UTF-8’... OK * checking re-building of vignette outputs ... OK * DONE -Status: 1 NOTE +Status: OK ``` -# DeLorean +# cyclestreets
-* Version: NA -* GitHub: NA -* Source code: https://github.com/cran/DeLorean -* Number of recursive dependencies: 120 +* Version: 0.6.0 +* GitHub: https://github.com/cyclestreets/cyclestreets-r +* Source code: https://github.com/cran/cyclestreets +* Date/Publication: 2023-02-17 09:30:06 UTC +* Number of recursive dependencies: 67 -Run `revdepcheck::cloud_details(, "DeLorean")` for more info +Run `revdepcheck::cloud_details(, "cyclestreets")` for more info
@@ -2236,7 +2571,23 @@ Run `revdepcheck::cloud_details(, "DeLorean")` for more info ### Devel ``` +* using log directory ‘/tmp/workdir/cyclestreets/new/cyclestreets.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘cyclestreets/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘cyclestreets’ version ‘0.6.0’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘sf’ +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR @@ -2246,23 +2597,39 @@ Run `revdepcheck::cloud_details(, "DeLorean")` for more info ### CRAN ``` +* using log directory ‘/tmp/workdir/cyclestreets/old/cyclestreets.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘cyclestreets/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘cyclestreets’ version ‘0.6.0’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘sf’ +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR ``` -# DepecheR +# CytoML
* Version: NA * GitHub: NA -* Source code: https://github.com/cran/DepecheR -* Number of recursive dependencies: 116 +* Source code: https://github.com/cran/CytoML +* Number of recursive dependencies: 105 -Run `revdepcheck::cloud_details(, "DepecheR")` for more info +Run `revdepcheck::cloud_details(, "CytoML")` for more info
@@ -2288,16 +2655,16 @@ Run `revdepcheck::cloud_details(, "DepecheR")` for more info ``` -# destiny +# D2MCS
* Version: NA * GitHub: NA -* Source code: https://github.com/cran/destiny -* Number of recursive dependencies: 243 +* Source code: https://github.com/cran/D2MCS +* Number of recursive dependencies: 179 -Run `revdepcheck::cloud_details(, "destiny")` for more info +Run `revdepcheck::cloud_details(, "D2MCS")` for more info
@@ -2323,16 +2690,17 @@ Run `revdepcheck::cloud_details(, "destiny")` for more info ``` -# DiffBind +# datawizard
-* Version: NA -* GitHub: NA -* Source code: https://github.com/cran/DiffBind -* Number of recursive dependencies: 158 +* Version: 0.6.5 +* GitHub: https://github.com/easystats/datawizard +* Source code: https://github.com/cran/datawizard +* Date/Publication: 2022-12-14 23:50:02 UTC +* Number of recursive dependencies: 186 -Run `revdepcheck::cloud_details(, "DiffBind")` for more info +Run `revdepcheck::cloud_details(, "datawizard")` for more info
@@ -2341,7 +2709,27 @@ Run `revdepcheck::cloud_details(, "DiffBind")` for more info ### Devel ``` - +* using log directory ‘/tmp/workdir/datawizard/new/datawizard.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘datawizard/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘datawizard’ version ‘0.6.5’ +* package encoding: UTF-8 +* checking package namespace information ... 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 + ‘selection_syntax.Rmd’ using ‘UTF-8’... OK + ‘standardize_data.Rmd’ using ‘UTF-8’... OK + ‘tidyverse_translation.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 1 NOTE @@ -2351,23 +2739,44 @@ Run `revdepcheck::cloud_details(, "DiffBind")` for more info ### CRAN ``` - +* using log directory ‘/tmp/workdir/datawizard/old/datawizard.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘datawizard/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘datawizard’ version ‘0.6.5’ +* package encoding: UTF-8 +* checking package namespace information ... 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 + ‘selection_syntax.Rmd’ using ‘UTF-8’... OK + ‘standardize_data.Rmd’ using ‘UTF-8’... OK + ‘tidyverse_translation.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 1 NOTE ``` -# diffman +# dbmss
-* Version: NA -* GitHub: NA -* Source code: https://github.com/cran/diffman -* Number of recursive dependencies: 125 +* Version: 2.8-0 +* GitHub: https://github.com/EricMarcon/dbmss +* Source code: https://github.com/cran/dbmss +* Date/Publication: 2023-01-06 15:10:05 UTC +* Number of recursive dependencies: 120 -Run `revdepcheck::cloud_details(, "diffman")` for more info +Run `revdepcheck::cloud_details(, "dbmss")` for more info
@@ -2376,33 +2785,73 @@ Run `revdepcheck::cloud_details(, "diffman")` for more info ### Devel ``` +* using log directory ‘/tmp/workdir/dbmss/new/dbmss.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘dbmss/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘dbmss’ version ‘2.8-0’ +* package encoding: UTF-8 +* checking package namespace information ... 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 + ‘dbmss.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 1 ERROR + + - - - -``` -### CRAN - -``` - - - - - - ``` -# diffrprojects +### CRAN + +``` +* using log directory ‘/tmp/workdir/dbmss/old/dbmss.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘dbmss/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘dbmss’ version ‘2.8-0’ +* package encoding: UTF-8 +* checking package namespace information ... 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 + ‘dbmss.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 1 ERROR + + + + + +``` +# DeLorean
* Version: NA * GitHub: NA -* Source code: https://github.com/cran/diffrprojects -* Number of recursive dependencies: 65 +* Source code: https://github.com/cran/DeLorean +* Number of recursive dependencies: 120 -Run `revdepcheck::cloud_details(, "diffrprojects")` for more info +Run `revdepcheck::cloud_details(, "DeLorean")` for more info
@@ -2428,16 +2877,16 @@ Run `revdepcheck::cloud_details(, "diffrprojects")` for more info ``` -# dynfrail +# DepecheR
* Version: NA * GitHub: NA -* Source code: https://github.com/cran/dynfrail -* Number of recursive dependencies: 57 +* Source code: https://github.com/cran/DepecheR +* Number of recursive dependencies: 116 -Run `revdepcheck::cloud_details(, "dynfrail")` for more info +Run `revdepcheck::cloud_details(, "DepecheR")` for more info
@@ -2463,17 +2912,16 @@ Run `revdepcheck::cloud_details(, "dynfrail")` for more info ``` -# embed +# destiny
-* Version: 1.0.0 -* GitHub: https://github.com/tidymodels/embed -* Source code: https://github.com/cran/embed -* Date/Publication: 2022-07-02 16:50:02 UTC -* Number of recursive dependencies: 183 +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/destiny +* Number of recursive dependencies: 243 -Run `revdepcheck::cloud_details(, "embed")` for more info +Run `revdepcheck::cloud_details(, "destiny")` for more info
@@ -2482,27 +2930,7 @@ Run `revdepcheck::cloud_details(, "embed")` for more info ### Devel ``` -* using log directory ‘/tmp/workdir/embed/new/embed.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘embed/DESCRIPTION’ ... OK -* this is package ‘embed’ version ‘1.0.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... NOTE -... - i In index: 1. - i With name: x3. - Caused by error in `.f()`: - ! The package "rstanarm" is required. - - [ FAIL 1 | WARN 2 | SKIP 56 | PASS 162 ] - Error: Test failures - Execution halted -* DONE -Status: 1 ERROR, 2 NOTEs + @@ -2512,43 +2940,23 @@ Status: 1 ERROR, 2 NOTEs ### CRAN ``` -* using log directory ‘/tmp/workdir/embed/old/embed.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘embed/DESCRIPTION’ ... OK -* this is package ‘embed’ version ‘1.0.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... NOTE -... - i In index: 1. - i With name: x3. - Caused by error in `.f()`: - ! The package `rstanarm` is required. - - [ FAIL 1 | WARN 2 | SKIP 56 | PASS 162 ] - Error: Test failures - Execution halted -* DONE -Status: 1 ERROR, 2 NOTEs + ``` -# EpiForsk +# DiffBind
* Version: NA * GitHub: NA -* Source code: https://github.com/cran/EpiForsk -* Number of recursive dependencies: 76 +* Source code: https://github.com/cran/DiffBind +* Number of recursive dependencies: 158 -Run `revdepcheck::cloud_details(, "EpiForsk")` for more info +Run `revdepcheck::cloud_details(, "DiffBind")` for more info
@@ -2574,16 +2982,16 @@ Run `revdepcheck::cloud_details(, "EpiForsk")` for more info ``` -# epiphy +# diffman
* Version: NA * GitHub: NA -* Source code: https://github.com/cran/epiphy -* Number of recursive dependencies: 91 +* Source code: https://github.com/cran/diffman +* Number of recursive dependencies: 125 -Run `revdepcheck::cloud_details(, "epiphy")` for more info +Run `revdepcheck::cloud_details(, "diffman")` for more info
@@ -2609,16 +3017,16 @@ Run `revdepcheck::cloud_details(, "epiphy")` for more info ``` -# epitopeR +# diffrprojects
* Version: NA * GitHub: NA -* Source code: https://github.com/cran/epitopeR -* Number of recursive dependencies: 160 +* Source code: https://github.com/cran/diffrprojects +* Number of recursive dependencies: 65 -Run `revdepcheck::cloud_details(, "epitopeR")` for more info +Run `revdepcheck::cloud_details(, "diffrprojects")` for more info
@@ -2644,17 +3052,17 @@ Run `revdepcheck::cloud_details(, "epitopeR")` for more info ``` -# escalation +# dycdtools
-* Version: 0.1.4 -* GitHub: NA -* Source code: https://github.com/cran/escalation -* Date/Publication: 2020-10-18 21:40:06 UTC -* Number of recursive dependencies: 127 +* Version: 0.4.3 +* GitHub: https://github.com/SongyanYu/dycdtools +* Source code: https://github.com/cran/dycdtools +* Date/Publication: 2022-11-22 00:40:02 UTC +* Number of recursive dependencies: 89 -Run `revdepcheck::cloud_details(, "escalation")` for more info +Run `revdepcheck::cloud_details(, "dycdtools")` for more info
@@ -2663,21 +3071,25 @@ Run `revdepcheck::cloud_details(, "escalation")` for more info ### Devel ``` -* using log directory ‘/tmp/workdir/escalation/new/escalation.Rcheck’ +* using log directory ‘/tmp/workdir/dycdtools/new/dycdtools.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘escalation/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘escalation’ version ‘0.1.4’ +* checking for file ‘dycdtools/DESCRIPTION’ ... OK +* this is package ‘dycdtools’ version ‘0.4.3’ * package encoding: UTF-8 * checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘trialr’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. +* checking package dependencies ... 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 ‘dycdtools’ can be installed ... ERROR +Installation failed. +See ‘/tmp/workdir/dycdtools/new/dycdtools.Rcheck/00install.out’ for details. * DONE Status: 1 ERROR @@ -2689,21 +3101,25 @@ Status: 1 ERROR ### CRAN ``` -* using log directory ‘/tmp/workdir/escalation/old/escalation.Rcheck’ +* using log directory ‘/tmp/workdir/dycdtools/old/dycdtools.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘escalation/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘escalation’ version ‘0.1.4’ +* checking for file ‘dycdtools/DESCRIPTION’ ... OK +* this is package ‘dycdtools’ version ‘0.4.3’ * package encoding: UTF-8 * checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘trialr’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. +* checking package dependencies ... 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 ‘dycdtools’ can be installed ... ERROR +Installation failed. +See ‘/tmp/workdir/dycdtools/old/dycdtools.Rcheck/00install.out’ for details. * DONE Status: 1 ERROR @@ -2712,16 +3128,17 @@ Status: 1 ERROR ``` -# EScvtmle +# dynamicSDM
-* Version: NA -* GitHub: NA -* Source code: https://github.com/cran/EScvtmle -* Number of recursive dependencies: 78 +* Version: 1.1 +* GitHub: https://github.com/r-a-dobson/dynamicSDM +* Source code: https://github.com/cran/dynamicSDM +* Date/Publication: 2023-02-27 13:22:30 UTC +* Number of recursive dependencies: 156 -Run `revdepcheck::cloud_details(, "EScvtmle")` for more info +Run `revdepcheck::cloud_details(, "dynamicSDM")` for more info
@@ -2730,7 +3147,22 @@ Run `revdepcheck::cloud_details(, "EScvtmle")` for more info ### Devel ``` +* using log directory ‘/tmp/workdir/dynamicSDM/new/dynamicSDM.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘dynamicSDM/DESCRIPTION’ ... OK +* this is package ‘dynamicSDM’ version ‘1.1’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘sf’ +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR @@ -2740,83 +3172,74 @@ Run `revdepcheck::cloud_details(, "EScvtmle")` for more info ### CRAN ``` +* using log directory ‘/tmp/workdir/dynamicSDM/old/dynamicSDM.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘dynamicSDM/DESCRIPTION’ ... OK +* this is package ‘dynamicSDM’ version ‘1.1’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘sf’ +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR ``` -# ESTER +# dynfrail
-* Version: 0.2.0 -* GitHub: https://github.com/lnalborczyk/ESTER -* Source code: https://github.com/cran/ESTER -* Date/Publication: 2017-12-10 14:21:14 UTC -* Number of recursive dependencies: 137 +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/dynfrail +* Number of recursive dependencies: 57 -Run `revdepcheck::cloud_details(, "ESTER")` for more info +Run `revdepcheck::cloud_details(, "dynfrail")` for more info
-## In both - -* checking whether package ‘ESTER’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/ESTER/new/ESTER.Rcheck/00install.out’ for details. - ``` - -## Installation +## Error before installation ### Devel ``` -* installing *source* package ‘ESTER’ ... -** package ‘ESTER’ successfully unpacked and MD5 sums checked -** using staged installation -** R -** inst -** byte-compile and prepare package for lazy loading -Error in loadNamespace(j <- imp[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - there is no package called ‘rstan’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart -Execution halted -ERROR: lazy loading failed for package ‘ESTER’ -* removing ‘/tmp/workdir/ESTER/new/ESTER.Rcheck/ESTER’ + + + + ``` ### CRAN ``` -* installing *source* package ‘ESTER’ ... -** package ‘ESTER’ successfully unpacked and MD5 sums checked -** using staged installation -** R -** inst -** byte-compile and prepare package for lazy loading -Error in loadNamespace(j <- imp[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - there is no package called ‘rstan’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart -Execution halted -ERROR: lazy loading failed for package ‘ESTER’ -* removing ‘/tmp/workdir/ESTER/old/ESTER.Rcheck/ESTER’ + + + + ``` -# evaluator +# edbuildmapr
-* Version: NA -* GitHub: NA -* Source code: https://github.com/cran/evaluator -* Number of recursive dependencies: 146 +* Version: 0.3.1 +* GitHub: https://github.com/EdBuild/edbuildmapr +* Source code: https://github.com/cran/edbuildmapr +* Date/Publication: 2021-06-15 06:00:02 UTC +* Number of recursive dependencies: 98 -Run `revdepcheck::cloud_details(, "evaluator")` for more info +Run `revdepcheck::cloud_details(, "edbuildmapr")` for more info
@@ -2825,7 +3248,23 @@ Run `revdepcheck::cloud_details(, "evaluator")` for more info ### Devel ``` +* using log directory ‘/tmp/workdir/edbuildmapr/new/edbuildmapr.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘edbuildmapr/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘edbuildmapr’ version ‘0.3.1’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘sf’ +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR @@ -2835,23 +3274,40 @@ Run `revdepcheck::cloud_details(, "evaluator")` for more info ### CRAN ``` +* using log directory ‘/tmp/workdir/edbuildmapr/old/edbuildmapr.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘edbuildmapr/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘edbuildmapr’ version ‘0.3.1’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘sf’ +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR ``` -# expstudies +# EFDR
-* Version: NA -* GitHub: NA -* Source code: https://github.com/cran/expstudies -* Number of recursive dependencies: 59 +* Version: 1.2 +* GitHub: https://github.com/andrewzm/EFDR +* Source code: https://github.com/cran/EFDR +* Date/Publication: 2021-04-18 05:50:03 UTC +* Number of recursive dependencies: 105 -Run `revdepcheck::cloud_details(, "expstudies")` for more info +Run `revdepcheck::cloud_details(, "EFDR")` for more info
@@ -2860,7 +3316,27 @@ Run `revdepcheck::cloud_details(, "expstudies")` for more info ### Devel ``` - +* using log directory ‘/tmp/workdir/EFDR/new/EFDR.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘EFDR/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘EFDR’ version ‘1.2’ +* package encoding: UTF-8 +* checking package namespace information ... 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 + ‘EFDR_documents.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: OK @@ -2870,24 +3346,44 @@ Run `revdepcheck::cloud_details(, "expstudies")` for more info ### CRAN ``` - +* using log directory ‘/tmp/workdir/EFDR/old/EFDR.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘EFDR/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘EFDR’ version ‘1.2’ +* package encoding: UTF-8 +* checking package namespace information ... 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 + ‘EFDR_documents.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: OK ``` -# fable.prophet +# embed
-* 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: 108 +* Version: 1.0.0 +* GitHub: https://github.com/tidymodels/embed +* Source code: https://github.com/cran/embed +* Date/Publication: 2022-07-02 16:50:02 UTC +* Number of recursive dependencies: 183 -Run `revdepcheck::cloud_details(, "fable.prophet")` for more info +Run `revdepcheck::cloud_details(, "embed")` for more info
@@ -2896,22 +3392,27 @@ Run `revdepcheck::cloud_details(, "fable.prophet")` for more info ### Devel ``` -* using log directory ‘/tmp/workdir/fable.prophet/new/fable.prophet.Rcheck’ +* using log directory ‘/tmp/workdir/embed/new/embed.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘fable.prophet/DESCRIPTION’ ... OK -* this is package ‘fable.prophet’ version ‘0.1.0’ +* checking for file ‘embed/DESCRIPTION’ ... OK +* this is package ‘embed’ version ‘1.0.0’ * package encoding: UTF-8 * checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘prophet’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. +* checking package dependencies ... NOTE +... + i In index: 1. + i With name: x3. + Caused by error in `.f()`: + ! The package "rstanarm" is required. + + [ FAIL 1 | WARN 2 | SKIP 56 | PASS 162 ] + Error: Test failures + Execution halted * DONE -Status: 1 ERROR +Status: 1 ERROR, 2 NOTEs @@ -2921,101 +3422,44 @@ Status: 1 ERROR ### CRAN ``` -* using log directory ‘/tmp/workdir/fable.prophet/old/fable.prophet.Rcheck’ +* using log directory ‘/tmp/workdir/embed/old/embed.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘fable.prophet/DESCRIPTION’ ... OK -* this is package ‘fable.prophet’ version ‘0.1.0’ +* checking for file ‘embed/DESCRIPTION’ ... OK +* this is package ‘embed’ version ‘1.0.0’ * package encoding: UTF-8 * checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘prophet’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. +* checking package dependencies ... NOTE +... + i In index: 1. + i With name: x3. + Caused by error in `.f()`: + ! The package "rstanarm" is required. + + [ FAIL 1 | WARN 2 | SKIP 56 | PASS 162 ] + Error: Test failures + Execution halted * DONE -Status: 1 ERROR - - - - - -``` -# FAMetA - -
- -* Version: 0.1.5 -* GitHub: NA -* Source code: https://github.com/cran/FAMetA -* Date/Publication: 2023-01-11 09:33:11 UTC -* Number of recursive dependencies: 90 - -Run `revdepcheck::cloud_details(, "FAMetA")` for more info - -
- -## In both - -* checking whether package ‘FAMetA’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/FAMetA/new/FAMetA.Rcheck/00install.out’ for details. - ``` - -## Installation - -### Devel - -``` -* installing *source* package ‘FAMetA’ ... -** package ‘FAMetA’ 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 ‘LipidMS’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): - there is no package called ‘readMzXmlData’ -Execution halted -ERROR: lazy loading failed for package ‘FAMetA’ -* removing ‘/tmp/workdir/FAMetA/new/FAMetA.Rcheck/FAMetA’ +Status: 1 ERROR, 2 NOTEs -``` -### CRAN -``` -* installing *source* package ‘FAMetA’ ... -** package ‘FAMetA’ 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 ‘LipidMS’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): - there is no package called ‘readMzXmlData’ -Execution halted -ERROR: lazy loading failed for package ‘FAMetA’ -* removing ‘/tmp/workdir/FAMetA/old/FAMetA.Rcheck/FAMetA’ ``` -# finnts +# EnvExpInd
-* Version: 0.2.2 -* GitHub: https://github.com/microsoft/finnts -* Source code: https://github.com/cran/finnts -* Date/Publication: 2023-02-12 00:40:02 UTC -* Number of recursive dependencies: 210 +* Version: 0.1.0 +* GitHub: https://github.com/Spatial-R/EnvExpInd +* Source code: https://github.com/cran/EnvExpInd +* Date/Publication: 2020-10-23 15:50:02 UTC +* Number of recursive dependencies: 67 -Run `revdepcheck::cloud_details(, "finnts")` for more info +Run `revdepcheck::cloud_details(, "EnvExpInd")` for more info
@@ -3024,24 +3468,24 @@ Run `revdepcheck::cloud_details(, "finnts")` for more info ### Devel ``` -* using log directory ‘/tmp/workdir/finnts/new/finnts.Rcheck’ +* using log directory ‘/tmp/workdir/EnvExpInd/new/EnvExpInd.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘finnts/DESCRIPTION’ ... OK -* this is package ‘finnts’ version ‘0.2.2’ +* checking for file ‘EnvExpInd/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘EnvExpInd’ version ‘0.1.0’ * package encoding: UTF-8 * checking package namespace information ... OK -* checking package dependencies ... OK ... - ‘best-model-selection.Rmd’ using ‘UTF-8’... OK - ‘external-regressors.Rmd’ using ‘UTF-8’... OK - ‘feature-engineering.Rmd’ using ‘UTF-8’... OK - ‘finnts.Rmd’ using ‘UTF-8’... OK - ‘hierarchical-forecasting.Rmd’ using ‘UTF-8’... OK - ‘models-used-in-finnts.Rmd’ using ‘UTF-8’... OK - ‘parallel-processing.Rmd’ using ‘UTF-8’... 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 + ‘environment_exposure.Rmd’ using ‘UTF-8’... OK * checking re-building of vignette outputs ... OK * DONE Status: OK @@ -3054,24 +3498,24 @@ Status: OK ### CRAN ``` -* using log directory ‘/tmp/workdir/finnts/old/finnts.Rcheck’ +* using log directory ‘/tmp/workdir/EnvExpInd/old/EnvExpInd.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘finnts/DESCRIPTION’ ... OK -* this is package ‘finnts’ version ‘0.2.2’ +* checking for file ‘EnvExpInd/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘EnvExpInd’ version ‘0.1.0’ * package encoding: UTF-8 * checking package namespace information ... OK -* checking package dependencies ... OK ... - ‘best-model-selection.Rmd’ using ‘UTF-8’... OK - ‘external-regressors.Rmd’ using ‘UTF-8’... OK - ‘feature-engineering.Rmd’ using ‘UTF-8’... OK - ‘finnts.Rmd’ using ‘UTF-8’... OK - ‘hierarchical-forecasting.Rmd’ using ‘UTF-8’... OK - ‘models-used-in-finnts.Rmd’ using ‘UTF-8’... OK - ‘parallel-processing.Rmd’ using ‘UTF-8’... 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 + ‘environment_exposure.Rmd’ using ‘UTF-8’... OK * checking re-building of vignette outputs ... OK * DONE Status: OK @@ -3081,16 +3525,16 @@ Status: OK ``` -# fipe +# EpiForsk
* Version: NA * GitHub: NA -* Source code: https://github.com/cran/fipe -* Number of recursive dependencies: 69 +* Source code: https://github.com/cran/EpiForsk +* Number of recursive dependencies: 76 -Run `revdepcheck::cloud_details(, "fipe")` for more info +Run `revdepcheck::cloud_details(, "EpiForsk")` for more info
@@ -3116,16 +3560,16 @@ Run `revdepcheck::cloud_details(, "fipe")` for more info ``` -# foieGras +# epiphy
* Version: NA * GitHub: NA -* Source code: https://github.com/cran/foieGras -* Number of recursive dependencies: 134 +* Source code: https://github.com/cran/epiphy +* Number of recursive dependencies: 91 -Run `revdepcheck::cloud_details(, "foieGras")` for more info +Run `revdepcheck::cloud_details(, "epiphy")` for more info
@@ -3151,16 +3595,7693 @@ Run `revdepcheck::cloud_details(, "foieGras")` for more info ``` -# forceR +# epitopeR
* Version: NA * GitHub: NA -* Source code: https://github.com/cran/forceR +* Source code: https://github.com/cran/epitopeR +* Number of recursive dependencies: 160 + +Run `revdepcheck::cloud_details(, "epitopeR")` for more info + +
+ +## Error before installation + +### Devel + +``` + + + + + + +``` +### CRAN + +``` + + + + + + +``` +# escalation + +
+ +* Version: 0.1.4 +* GitHub: NA +* Source code: https://github.com/cran/escalation +* Date/Publication: 2020-10-18 21:40:06 UTC +* Number of recursive dependencies: 127 + +Run `revdepcheck::cloud_details(, "escalation")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/escalation/new/escalation.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘escalation/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘escalation’ version ‘0.1.4’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘trialr’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/escalation/old/escalation.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘escalation/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘escalation’ version ‘0.1.4’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘trialr’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# EScvtmle + +
+ +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/EScvtmle +* Number of recursive dependencies: 78 + +Run `revdepcheck::cloud_details(, "EScvtmle")` for more info + +
+ +## Error before installation + +### Devel + +``` + + + + + + +``` +### CRAN + +``` + + + + + + +``` +# eSDM + +
+ +* Version: 0.3.7 +* GitHub: https://github.com/smwoodman/eSDM +* Source code: https://github.com/cran/eSDM +* Date/Publication: 2021-05-04 04:50:08 UTC +* Number of recursive dependencies: 130 + +Run `revdepcheck::cloud_details(, "eSDM")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/eSDM/new/eSDM.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘eSDM/DESCRIPTION’ ... OK +* this is package ‘eSDM’ version ‘0.3.7’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘sf’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/eSDM/old/eSDM.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘eSDM/DESCRIPTION’ ... OK +* this is package ‘eSDM’ version ‘0.3.7’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘sf’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# ESTER + +
+ +* Version: 0.2.0 +* GitHub: https://github.com/lnalborczyk/ESTER +* Source code: https://github.com/cran/ESTER +* Date/Publication: 2017-12-10 14:21:14 UTC +* Number of recursive dependencies: 137 + +Run `revdepcheck::cloud_details(, "ESTER")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/ESTER/new/ESTER.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘ESTER/DESCRIPTION’ ... OK +* this is package ‘ESTER’ version ‘0.2.0’ +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘brms’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/ESTER/old/ESTER.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘ESTER/DESCRIPTION’ ... OK +* this is package ‘ESTER’ version ‘0.2.0’ +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘brms’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# evaluator + +
+ +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/evaluator +* Number of recursive dependencies: 146 + +Run `revdepcheck::cloud_details(, "evaluator")` for more info + +
+ +## Error before installation + +### Devel + +``` + + + + + + +``` +### CRAN + +``` + + + + + + +``` +# expstudies + +
+ +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/expstudies +* Number of recursive dependencies: 59 + +Run `revdepcheck::cloud_details(, "expstudies")` for more info + +
+ +## Error before installation + +### Devel + +``` + + + + + + +``` +### CRAN + +``` + + + + + + +``` +# 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: 108 + +Run `revdepcheck::cloud_details(, "fable.prophet")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/fable.prophet/new/fable.prophet.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘fable.prophet/DESCRIPTION’ ... OK +* this is package ‘fable.prophet’ version ‘0.1.0’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘prophet’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/fable.prophet/old/fable.prophet.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘fable.prophet/DESCRIPTION’ ... OK +* this is package ‘fable.prophet’ version ‘0.1.0’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘prophet’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# FAMetA + +
+ +* Version: 0.1.5 +* GitHub: NA +* Source code: https://github.com/cran/FAMetA +* Date/Publication: 2023-01-11 09:33:11 UTC +* Number of recursive dependencies: 90 + +Run `revdepcheck::cloud_details(, "FAMetA")` for more info + +
+ +## In both + +* checking whether package ‘FAMetA’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/FAMetA/new/FAMetA.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘FAMetA’ ... +** package ‘FAMetA’ 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 ‘LipidMS’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): + there is no package called ‘readMzXmlData’ +Execution halted +ERROR: lazy loading failed for package ‘FAMetA’ +* removing ‘/tmp/workdir/FAMetA/new/FAMetA.Rcheck/FAMetA’ + + +``` +### CRAN + +``` +* installing *source* package ‘FAMetA’ ... +** package ‘FAMetA’ 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 ‘LipidMS’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): + there is no package called ‘readMzXmlData’ +Execution halted +ERROR: lazy loading failed for package ‘FAMetA’ +* removing ‘/tmp/workdir/FAMetA/old/FAMetA.Rcheck/FAMetA’ + + +``` +# fgdr + +
+ +* Version: 1.1.1 +* GitHub: https://github.com/uribo/fgdr +* Source code: https://github.com/cran/fgdr +* Date/Publication: 2022-02-22 05:00:02 UTC +* Number of recursive dependencies: 123 + +Run `revdepcheck::cloud_details(, "fgdr")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/fgdr/new/fgdr.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘fgdr/DESCRIPTION’ ... OK +* this is package ‘fgdr’ version ‘1.1.1’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘sf’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/fgdr/old/fgdr.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘fgdr/DESCRIPTION’ ... OK +* this is package ‘fgdr’ version ‘1.1.1’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘sf’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# finnts + +
+ +* Version: 0.2.2 +* GitHub: https://github.com/microsoft/finnts +* Source code: https://github.com/cran/finnts +* Date/Publication: 2023-02-12 00:40:02 UTC +* Number of recursive dependencies: 210 + +Run `revdepcheck::cloud_details(, "finnts")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/finnts/new/finnts.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘finnts/DESCRIPTION’ ... OK +* this is package ‘finnts’ version ‘0.2.2’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... OK +... + ‘best-model-selection.Rmd’ using ‘UTF-8’... OK + ‘external-regressors.Rmd’ using ‘UTF-8’... OK + ‘feature-engineering.Rmd’ using ‘UTF-8’... OK + ‘finnts.Rmd’ using ‘UTF-8’... OK + ‘hierarchical-forecasting.Rmd’ using ‘UTF-8’... OK + ‘models-used-in-finnts.Rmd’ using ‘UTF-8’... OK + ‘parallel-processing.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: OK + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/finnts/old/finnts.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘finnts/DESCRIPTION’ ... OK +* this is package ‘finnts’ version ‘0.2.2’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... OK +... + ‘best-model-selection.Rmd’ using ‘UTF-8’... OK + ‘external-regressors.Rmd’ using ‘UTF-8’... OK + ‘feature-engineering.Rmd’ using ‘UTF-8’... OK + ‘finnts.Rmd’ using ‘UTF-8’... OK + ‘hierarchical-forecasting.Rmd’ using ‘UTF-8’... OK + ‘models-used-in-finnts.Rmd’ using ‘UTF-8’... OK + ‘parallel-processing.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: OK + + + + + +``` +# fipe + +
+ +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/fipe +* Number of recursive dependencies: 69 + +Run `revdepcheck::cloud_details(, "fipe")` for more info + +
+ +## Error before installation + +### Devel + +``` + + + + + + +``` +### CRAN + +``` + + + + + + +``` +# foieGras + +
+ +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/foieGras +* Number of recursive dependencies: 134 + +Run `revdepcheck::cloud_details(, "foieGras")` for more info + +
+ +## Error before installation + +### Devel + +``` + + + + + + +``` +### CRAN + +``` + + + + + + +``` +# forceR + +
+ +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/forceR +* Number of recursive dependencies: 86 + +Run `revdepcheck::cloud_details(, "forceR")` for more info + +
+ +## Error before installation + +### Devel + +``` + + + + + + +``` +### CRAN + +``` + + + + + + +``` +# FORTLS + +
+ +* Version: 1.2.0 +* GitHub: https://github.com/Molina-Valero/FORTLS +* Source code: https://github.com/cran/FORTLS +* Date/Publication: 2023-01-08 16:50:05 UTC +* Number of recursive dependencies: 176 + +Run `revdepcheck::cloud_details(, "FORTLS")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/FORTLS/new/FORTLS.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘FORTLS/DESCRIPTION’ ... OK +* this is package ‘FORTLS’ version ‘1.2.0’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘sf’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/FORTLS/old/FORTLS.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘FORTLS/DESCRIPTION’ ... OK +* this is package ‘FORTLS’ version ‘1.2.0’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘sf’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# FRK + +
+ +* Version: 2.1.5 +* GitHub: https://github.com/andrewzm/FRK +* Source code: https://github.com/cran/FRK +* Date/Publication: 2023-02-01 10:20:02 UTC +* Number of recursive dependencies: 156 + +Run `revdepcheck::cloud_details(, "FRK")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/FRK/new/FRK.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘FRK/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘FRK’ version ‘2.1.5’ +* package encoding: UTF-8 +* checking package namespace information ... OK +... +--- failed re-building ‘FRK_non-Gaussian.Rnw’ + +SUMMARY: processing the following files failed: + ‘FRK_intro.Rnw’ ‘FRK_non-Gaussian.Rnw’ + +Error: Vignette re-building failed. +Execution halted + +* DONE +Status: 1 ERROR, 1 WARNING, 2 NOTEs + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/FRK/old/FRK.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘FRK/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘FRK’ version ‘2.1.5’ +* package encoding: UTF-8 +* checking package namespace information ... OK +... +--- failed re-building ‘FRK_non-Gaussian.Rnw’ + +SUMMARY: processing the following files failed: + ‘FRK_intro.Rnw’ ‘FRK_non-Gaussian.Rnw’ + +Error: Vignette re-building failed. +Execution halted + +* DONE +Status: 1 ERROR, 1 WARNING, 2 NOTEs + + + + + +``` +# fsr + +
+ +* Version: 1.0.2 +* GitHub: https://github.com/accarniel/fsr +* Source code: https://github.com/cran/fsr +* Date/Publication: 2022-07-05 02:50:02 UTC +* Number of recursive dependencies: 71 + +Run `revdepcheck::cloud_details(, "fsr")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/fsr/new/fsr.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘fsr/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘fsr’ version ‘1.0.2’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Packages required but not available: 'sf', 'lwgeom' + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/fsr/old/fsr.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘fsr/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘fsr’ version ‘1.0.2’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Packages required but not available: 'sf', 'lwgeom' + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# genekitr + +
+ +* Version: 1.1.3 +* GitHub: https://github.com/GangLiLab/genekitr +* Source code: https://github.com/cran/genekitr +* Date/Publication: 2023-03-01 09:00:02 UTC +* Number of recursive dependencies: 206 + +Run `revdepcheck::cloud_details(, "genekitr")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/genekitr/new/genekitr.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘genekitr/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘genekitr’ version ‘1.1.3’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘clusterProfiler’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/genekitr/old/genekitr.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘genekitr/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘genekitr’ version ‘1.1.3’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘clusterProfiler’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# geocmeans + +
+ +* Version: 0.3.3 +* GitHub: https://github.com/JeremyGelb/geocmeans +* Source code: https://github.com/cran/geocmeans +* Date/Publication: 2023-02-07 01:02:31 UTC +* Number of recursive dependencies: 197 + +Run `revdepcheck::cloud_details(, "geocmeans")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/geocmeans/new/geocmeans.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘geocmeans/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘geocmeans’ version ‘0.3.3’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘sf’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/geocmeans/old/geocmeans.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘geocmeans/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘geocmeans’ version ‘0.3.3’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘sf’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# GeodesiCL + +
+ +* Version: 1.0.0 +* GitHub: https://github.com/diegoalarc/GeodesiCL +* Source code: https://github.com/cran/GeodesiCL +* Date/Publication: 2021-05-25 12:20:02 UTC +* Number of recursive dependencies: 129 + +Run `revdepcheck::cloud_details(, "GeodesiCL")` for more info + +
+ +## In both + +* checking whether package ‘GeodesiCL’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/GeodesiCL/new/GeodesiCL.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘GeodesiCL’ ... +** package ‘GeodesiCL’ 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 ‘sf’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Execution halted +ERROR: lazy loading failed for package ‘GeodesiCL’ +* removing ‘/tmp/workdir/GeodesiCL/new/GeodesiCL.Rcheck/GeodesiCL’ + + +``` +### CRAN + +``` +* installing *source* package ‘GeodesiCL’ ... +** package ‘GeodesiCL’ 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 ‘sf’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Execution halted +ERROR: lazy loading failed for package ‘GeodesiCL’ +* removing ‘/tmp/workdir/GeodesiCL/old/GeodesiCL.Rcheck/GeodesiCL’ + + +``` +# ggchangepoint + +
+ +* Version: 0.1.0 +* GitHub: NA +* Source code: https://github.com/cran/ggchangepoint +* Date/Publication: 2022-02-24 08:20:04 UTC +* Number of recursive dependencies: 81 + +Run `revdepcheck::cloud_details(, "ggchangepoint")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/ggchangepoint/new/ggchangepoint.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘ggchangepoint/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘ggchangepoint’ version ‘0.1.0’ +* package encoding: UTF-8 +* checking package namespace information ... 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 + ‘introduction.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: OK + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/ggchangepoint/old/ggchangepoint.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘ggchangepoint/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘ggchangepoint’ version ‘0.1.0’ +* package encoding: UTF-8 +* checking package namespace information ... 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 + ‘introduction.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: OK + + + + + +``` +# ggOceanMaps + +
+ +* Version: 1.3.4 +* GitHub: https://github.com/MikkoVihtakari/ggOceanMaps +* Source code: https://github.com/cran/ggOceanMaps +* Date/Publication: 2022-09-26 11:50:02 UTC +* Number of recursive dependencies: 92 + +Run `revdepcheck::cloud_details(, "ggOceanMaps")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/ggOceanMaps/new/ggOceanMaps.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘ggOceanMaps/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘ggOceanMaps’ version ‘1.3.4’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘sf’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/ggOceanMaps/old/ggOceanMaps.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘ggOceanMaps/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘ggOceanMaps’ version ‘1.3.4’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘sf’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# ggPMX + +
+ +* Version: 1.2.8 +* GitHub: https://github.com/ggPMXdevelopment/ggPMX +* Source code: https://github.com/cran/ggPMX +* Date/Publication: 2022-06-17 23:10:02 UTC +* Number of recursive dependencies: 174 + +Run `revdepcheck::cloud_details(, "ggPMX")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/ggPMX/new/ggPMX.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘ggPMX/DESCRIPTION’ ... OK +* this is package ‘ggPMX’ version ‘1.2.8’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... NOTE +... + [ FAIL 1 | WARN 14 | SKIP 8 | PASS 327 ] + 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 ... NONE + ‘ggPMX-guide.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 1 ERROR, 2 NOTEs + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/ggPMX/old/ggPMX.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘ggPMX/DESCRIPTION’ ... OK +* this is package ‘ggPMX’ version ‘1.2.8’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... NOTE +... + [ FAIL 1 | WARN 14 | SKIP 8 | PASS 327 ] + 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 ... NONE + ‘ggPMX-guide.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 1 ERROR, 2 NOTEs + + + + + +``` +# ggseqplot + +
+ +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/ggseqplot +* Number of recursive dependencies: 130 + +Run `revdepcheck::cloud_details(, "ggseqplot")` for more info + +
+ +## Error before installation + +### Devel + +``` + + + + + + +``` +### CRAN + +``` + + + + + + +``` +# ggspatial + +
+ +* Version: 1.1.7 +* GitHub: https://github.com/paleolimbot/ggspatial +* Source code: https://github.com/cran/ggspatial +* Date/Publication: 2022-11-24 10:00:02 UTC +* Number of recursive dependencies: 105 + +Run `revdepcheck::cloud_details(, "ggspatial")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/ggspatial/new/ggspatial.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘ggspatial/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘ggspatial’ version ‘1.1.7’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘sf’ + +Package suggested but not available for checking: ‘lwgeom’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/ggspatial/old/ggspatial.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘ggspatial/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘ggspatial’ version ‘1.1.7’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘sf’ + +Package suggested but not available for checking: ‘lwgeom’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# ggstatsplot + +
+ +* Version: 0.11.0 +* GitHub: https://github.com/IndrajeetPatil/ggstatsplot +* Source code: https://github.com/cran/ggstatsplot +* Date/Publication: 2023-02-15 15:30:02 UTC +* Number of recursive dependencies: 169 + +Run `revdepcheck::cloud_details(, "ggstatsplot")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/ggstatsplot/new/ggstatsplot.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘ggstatsplot/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘ggstatsplot’ version ‘0.11.0’ +* package encoding: UTF-8 +* checking package namespace information ... 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 + ‘additional.Rmd’ using ‘UTF-8’... OK + ‘ggstatsplot.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 1 NOTE + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/ggstatsplot/old/ggstatsplot.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘ggstatsplot/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘ggstatsplot’ version ‘0.11.0’ +* package encoding: UTF-8 +* checking package namespace information ... 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 + ‘additional.Rmd’ using ‘UTF-8’... OK + ‘ggstatsplot.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 1 NOTE + + + + + +``` +# glottospace + +
+ +* Version: 0.0.112 +* GitHub: https://github.com/SietzeN/glottospace +* Source code: https://github.com/cran/glottospace +* Date/Publication: 2022-04-12 12:42:29 UTC +* Number of recursive dependencies: 141 + +Run `revdepcheck::cloud_details(, "glottospace")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/glottospace/new/glottospace.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘glottospace/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘glottospace’ version ‘0.0.112’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘sf’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/glottospace/old/glottospace.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘glottospace/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘glottospace’ version ‘0.0.112’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘sf’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# GPSeqClus + +
+ +* Version: 1.3.0 +* GitHub: NA +* Source code: https://github.com/cran/GPSeqClus +* Date/Publication: 2022-08-09 14:20:08 UTC +* Number of recursive dependencies: 103 + +Run `revdepcheck::cloud_details(, "GPSeqClus")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/GPSeqClus/new/GPSeqClus.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘GPSeqClus/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘GPSeqClus’ version ‘1.3.0’ +* package encoding: UTF-8 +* checking package namespace information ... 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 ‘GPSeqClus’ can be installed ... ERROR +Installation failed. +See ‘/tmp/workdir/GPSeqClus/new/GPSeqClus.Rcheck/00install.out’ for details. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/GPSeqClus/old/GPSeqClus.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘GPSeqClus/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘GPSeqClus’ version ‘1.3.0’ +* package encoding: UTF-8 +* checking package namespace information ... 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 ‘GPSeqClus’ can be installed ... ERROR +Installation failed. +See ‘/tmp/workdir/GPSeqClus/old/GPSeqClus.Rcheck/00install.out’ for details. +* DONE +Status: 1 ERROR + + + + + +``` +# GREENeR + +
+ +* Version: 0.1.1 +* GitHub: https://github.com/calfarog/GREENeR +* Source code: https://github.com/cran/GREENeR +* Date/Publication: 2022-09-07 12:10:02 UTC +* Number of recursive dependencies: 133 + +Run `revdepcheck::cloud_details(, "GREENeR")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/GREENeR/new/GREENeR.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘GREENeR/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘GREENeR’ version ‘0.1.1’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘sf’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/GREENeR/old/GREENeR.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘GREENeR/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘GREENeR’ version ‘0.1.1’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘sf’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# gtfs2gps + +
+ +* Version: 2.1-0 +* GitHub: https://github.com/ipeaGIT/gtfs2gps +* Source code: https://github.com/cran/gtfs2gps +* Date/Publication: 2022-08-16 18:00:02 UTC +* Number of recursive dependencies: 88 + +Run `revdepcheck::cloud_details(, "gtfs2gps")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/gtfs2gps/new/gtfs2gps.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘gtfs2gps/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘gtfs2gps’ version ‘2.1-0’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Packages required but not available: 'sf', 'lwgeom' + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/gtfs2gps/old/gtfs2gps.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘gtfs2gps/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘gtfs2gps’ version ‘2.1-0’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Packages required but not available: 'sf', 'lwgeom' + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# gumboot + +
+ +* Version: 1.0.0 +* GitHub: NA +* Source code: https://github.com/cran/gumboot +* Date/Publication: 2021-08-06 08:10:01 UTC +* Number of recursive dependencies: 101 + +Run `revdepcheck::cloud_details(, "gumboot")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/gumboot/new/gumboot.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘gumboot/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘gumboot’ version ‘1.0.0’ +* package encoding: UTF-8 +* checking package namespace information ... 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 ‘gumboot’ can be installed ... ERROR +Installation failed. +See ‘/tmp/workdir/gumboot/new/gumboot.Rcheck/00install.out’ for details. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/gumboot/old/gumboot.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘gumboot/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘gumboot’ version ‘1.0.0’ +* package encoding: UTF-8 +* checking package namespace information ... 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 ‘gumboot’ can be installed ... ERROR +Installation failed. +See ‘/tmp/workdir/gumboot/old/gumboot.Rcheck/00install.out’ for details. +* DONE +Status: 1 ERROR + + + + + +``` +# gwavr + +
+ +* Version: 0.2.0 +* GitHub: https://github.com/joshualerickson/gwavr +* Source code: https://github.com/cran/gwavr +* Date/Publication: 2022-03-28 21:30:02 UTC +* Number of recursive dependencies: 140 + +Run `revdepcheck::cloud_details(, "gwavr")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/gwavr/new/gwavr.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘gwavr/DESCRIPTION’ ... OK +* this is package ‘gwavr’ version ‘0.2.0’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Packages required but not available: 'nhdplusTools', 'sf' + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/gwavr/old/gwavr.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘gwavr/DESCRIPTION’ ... OK +* this is package ‘gwavr’ version ‘0.2.0’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Packages required but not available: 'nhdplusTools', 'sf' + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# GWPR.light + +
+ +* Version: 0.2.1 +* GitHub: https://github.com/MichaelChaoLi-cpu/GWPR.light +* Source code: https://github.com/cran/GWPR.light +* Date/Publication: 2022-06-21 11:00:13 UTC +* Number of recursive dependencies: 129 + +Run `revdepcheck::cloud_details(, "GWPR.light")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/GWPR.light/new/GWPR.light.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘GWPR.light/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘GWPR.light’ version ‘0.2.1’ +* package encoding: UTF-8 +* checking package namespace information ... 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 ‘GWPR.light’ can be installed ... ERROR +Installation failed. +See ‘/tmp/workdir/GWPR.light/new/GWPR.light.Rcheck/00install.out’ for details. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/GWPR.light/old/GWPR.light.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘GWPR.light/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘GWPR.light’ version ‘0.2.1’ +* package encoding: UTF-8 +* checking package namespace information ... 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 ‘GWPR.light’ can be installed ... ERROR +Installation failed. +See ‘/tmp/workdir/GWPR.light/old/GWPR.light.Rcheck/00install.out’ for details. +* DONE +Status: 1 ERROR + + + + + +``` +# happign + +
+ +* Version: 0.1.8 +* GitHub: https://github.com/paul-carteron/happign +* Source code: https://github.com/cran/happign +* Date/Publication: 2023-01-30 20:50:02 UTC +* Number of recursive dependencies: 121 + +Run `revdepcheck::cloud_details(, "happign")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/happign/new/happign.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘happign/DESCRIPTION’ ... OK +* this is package ‘happign’ version ‘0.1.8’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘sf’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/happign/old/happign.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘happign/DESCRIPTION’ ... OK +* this is package ‘happign’ version ‘0.1.8’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘sf’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# healthyR.ai + +
+ +* Version: 0.0.12 +* GitHub: https://github.com/spsanderson/healthyR.ai +* Source code: https://github.com/cran/healthyR.ai +* Date/Publication: 2023-02-01 18:40:06 UTC +* Number of recursive dependencies: 189 + +Run `revdepcheck::cloud_details(, "healthyR.ai")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/healthyR.ai/new/healthyR.ai.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘healthyR.ai/DESCRIPTION’ ... OK +* this is package ‘healthyR.ai’ version ‘0.0.12’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... 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 + ‘auto-kmeans.Rmd’ using ‘UTF-8’... OK + ‘getting-started.Rmd’ using ‘UTF-8’... OK + ‘kmeans-umap.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: OK + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/healthyR.ai/old/healthyR.ai.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘healthyR.ai/DESCRIPTION’ ... OK +* this is package ‘healthyR.ai’ version ‘0.0.12’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... 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 + ‘auto-kmeans.Rmd’ using ‘UTF-8’... OK + ‘getting-started.Rmd’ using ‘UTF-8’... OK + ‘kmeans-umap.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: OK + + + + + +``` +# healthyR.ts + +
+ +* Version: 0.2.7 +* GitHub: https://github.com/spsanderson/healthyR.ts +* Source code: https://github.com/cran/healthyR.ts +* Date/Publication: 2023-01-28 14:50:02 UTC +* Number of recursive dependencies: 191 + +Run `revdepcheck::cloud_details(, "healthyR.ts")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/healthyR.ts/new/healthyR.ts.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘healthyR.ts/DESCRIPTION’ ... OK +* this is package ‘healthyR.ts’ version ‘0.2.7’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... 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 + ‘using-tidy-fft.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 1 NOTE + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/healthyR.ts/old/healthyR.ts.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘healthyR.ts/DESCRIPTION’ ... OK +* this is package ‘healthyR.ts’ version ‘0.2.7’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... 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 + ‘using-tidy-fft.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 1 NOTE + + + + + +``` +# healthyverse + +
+ +* Version: 1.0.3 +* GitHub: https://github.com/spsanderson/healthyverse +* Source code: https://github.com/cran/healthyverse +* Date/Publication: 2023-02-21 20:40:02 UTC +* Number of recursive dependencies: 207 + +Run `revdepcheck::cloud_details(, "healthyverse")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/healthyverse/new/healthyverse.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘healthyverse/DESCRIPTION’ ... OK +* this is package ‘healthyverse’ version ‘1.0.3’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... 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 +* DONE +Status: 1 NOTE + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/healthyverse/old/healthyverse.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘healthyverse/DESCRIPTION’ ... OK +* this is package ‘healthyverse’ version ‘1.0.3’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... 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 +* DONE +Status: 1 NOTE + + + + + +``` +# himach + +
+ +* Version: 0.3.1 +* GitHub: https://github.com/david6marsh/himach +* Source code: https://github.com/cran/himach +* Date/Publication: 2022-12-05 09:30:02 UTC +* Number of recursive dependencies: 108 + +Run `revdepcheck::cloud_details(, "himach")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/himach/new/himach.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘himach/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘himach’ version ‘0.3.1’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Packages required but not available: 'lwgeom', 'sf' + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/himach/old/himach.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘himach/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘himach’ version ‘0.3.1’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Packages required but not available: 'lwgeom', 'sf' + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# historicalborrowlong + +
+ +* Version: 0.0.5 +* GitHub: https://github.com/wlandau/historicalborrowlong +* Source code: https://github.com/cran/historicalborrowlong +* Date/Publication: 2022-09-13 10:20:06 UTC +* Number of recursive dependencies: 107 + +Run `revdepcheck::cloud_details(, "historicalborrowlong")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/historicalborrowlong/new/historicalborrowlong.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘historicalborrowlong/DESCRIPTION’ ... OK +* this is package ‘historicalborrowlong’ version ‘0.0.5’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Packages required but not available: 'rstan', 'trialr' + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/historicalborrowlong/old/historicalborrowlong.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘historicalborrowlong/DESCRIPTION’ ... OK +* this is package ‘historicalborrowlong’ version ‘0.0.5’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Packages required but not available: 'rstan', 'trialr' + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# HYPEtools + +
+ +* Version: 1.2.0 +* GitHub: https://github.com/rcapell/HYPEtools +* Source code: https://github.com/cran/HYPEtools +* Date/Publication: 2023-02-10 08:50:06 UTC +* Number of recursive dependencies: 174 + +Run `revdepcheck::cloud_details(, "HYPEtools")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/HYPEtools/new/HYPEtools.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘HYPEtools/DESCRIPTION’ ... OK +* this is package ‘HYPEtools’ version ‘1.2.0’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘sf’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/HYPEtools/old/HYPEtools.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘HYPEtools/DESCRIPTION’ ... OK +* this is package ‘HYPEtools’ version ‘1.2.0’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘sf’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# 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: 109 + +Run `revdepcheck::cloud_details(, "hypsoLoop")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/hypsoLoop/new/hypsoLoop.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘hypsoLoop/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘hypsoLoop’ version ‘0.2.0’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘sf’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/hypsoLoop/old/hypsoLoop.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘hypsoLoop/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘hypsoLoop’ version ‘0.2.0’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘sf’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# immcp + +
+ +* Version: 1.0.3 +* GitHub: https://github.com/YuanlongHu/immcp +* Source code: https://github.com/cran/immcp +* Date/Publication: 2022-05-12 05:50:02 UTC +* Number of recursive dependencies: 194 + +Run `revdepcheck::cloud_details(, "immcp")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/immcp/new/immcp.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘immcp/DESCRIPTION’ ... OK +* this is package ‘immcp’ version ‘1.0.3’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘clusterProfiler’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/immcp/old/immcp.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘immcp/DESCRIPTION’ ... OK +* this is package ‘immcp’ version ‘1.0.3’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘clusterProfiler’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# ImputeRobust + +
+ +* Version: 1.3-1 +* GitHub: NA +* Source code: https://github.com/cran/ImputeRobust +* Date/Publication: 2018-11-30 12:10:03 UTC +* Number of recursive dependencies: 41 + +Run `revdepcheck::cloud_details(, "ImputeRobust")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/ImputeRobust/new/ImputeRobust.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘ImputeRobust/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘ImputeRobust’ version ‘1.3-1’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘extremevalues’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/ImputeRobust/old/ImputeRobust.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘ImputeRobust/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘ImputeRobust’ version ‘1.3-1’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘extremevalues’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# incidence2 + +
+ +* Version: 1.2.3 +* GitHub: https://github.com/reconverse/incidence2 +* Source code: https://github.com/cran/incidence2 +* Date/Publication: 2021-11-07 22:00:02 UTC +* Number of recursive dependencies: 87 + +Run `revdepcheck::cloud_details(, "incidence2")` for more info + +
+ +## In both + +* checking whether package ‘incidence2’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/incidence2/new/incidence2.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘incidence2’ ... +** package ‘incidence2’ 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 : The `x` argument of `as_tibble()` can't be missing as of tibble 3.0.0. +Error: unable to load R code in package ‘incidence2’ +Execution halted +ERROR: lazy loading failed for package ‘incidence2’ +* removing ‘/tmp/workdir/incidence2/new/incidence2.Rcheck/incidence2’ + + +``` +### CRAN + +``` +* installing *source* package ‘incidence2’ ... +** package ‘incidence2’ 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 : The `x` argument of `as_tibble()` can't be missing as of tibble 3.0.0. +Error: unable to load R code in package ‘incidence2’ +Execution halted +ERROR: lazy loading failed for package ‘incidence2’ +* removing ‘/tmp/workdir/incidence2/old/incidence2.Rcheck/incidence2’ + + +``` +# INSPECTumours + +
+ +* Version: 0.1.0 +* GitHub: NA +* Source code: https://github.com/cran/INSPECTumours +* Date/Publication: 2022-05-06 12:10:02 UTC +* Number of recursive dependencies: 175 + +Run `revdepcheck::cloud_details(, "INSPECTumours")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/INSPECTumours/new/INSPECTumours.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘INSPECTumours/DESCRIPTION’ ... OK +* this is package ‘INSPECTumours’ version ‘0.1.0’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘brms’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/INSPECTumours/old/INSPECTumours.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘INSPECTumours/DESCRIPTION’ ... OK +* this is package ‘INSPECTumours’ version ‘0.1.0’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘brms’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# intRinsic + +
+ +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/intRinsic +* Number of recursive dependencies: 64 + +Run `revdepcheck::cloud_details(, "intRinsic")` for more info + +
+ +## Error before installation + +### Devel + +``` + + + + + + +``` +### CRAN + +``` + + + + + + +``` +# intSDM + +
+ +* Version: 1.0.5 +* GitHub: NA +* Source code: https://github.com/cran/intSDM +* Date/Publication: 2023-02-17 09:00:02 UTC +* Number of recursive dependencies: 154 + +Run `revdepcheck::cloud_details(, "intSDM")` for more info + +
+ +## In both + +* checking whether package ‘intSDM’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/intSDM/new/intSDM.Rcheck/00install.out’ for details. + ``` + +* checking package dependencies ... NOTE + ``` + Package suggested but not available for checking: ‘sf’ + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘intSDM’ ... +** package ‘intSDM’ 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 ‘PointedSDMs’ in loadNamespace(i, c(lib.loc, .libPaths()), versionCheck = vI[[i]]): + there is no package called ‘sf’ +Execution halted +ERROR: lazy loading failed for package ‘intSDM’ +* removing ‘/tmp/workdir/intSDM/new/intSDM.Rcheck/intSDM’ + + +``` +### CRAN + +``` +* installing *source* package ‘intSDM’ ... +** package ‘intSDM’ 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 ‘PointedSDMs’ in loadNamespace(i, c(lib.loc, .libPaths()), versionCheck = vI[[i]]): + there is no package called ‘sf’ +Execution halted +ERROR: lazy loading failed for package ‘intSDM’ +* removing ‘/tmp/workdir/intSDM/old/intSDM.Rcheck/intSDM’ + + +``` +# IRexamples + +
+ +* Version: 0.0.2 +* GitHub: https://github.com/vinhdizzo/IRexamples +* Source code: https://github.com/cran/IRexamples +* Date/Publication: 2022-08-15 07:10:19 UTC +* Number of recursive dependencies: 184 + +Run `revdepcheck::cloud_details(, "IRexamples")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/IRexamples/new/IRexamples.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘IRexamples/DESCRIPTION’ ... OK +* this is package ‘IRexamples’ version ‘0.0.2’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Packages required but not available: 'rstanarm', 'sf' + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/IRexamples/old/IRexamples.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘IRexamples/DESCRIPTION’ ... OK +* this is package ‘IRexamples’ version ‘0.0.2’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Packages required but not available: 'rstanarm', 'sf' + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# irtQ + +
+ +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/irtQ +* Number of recursive dependencies: 59 + +Run `revdepcheck::cloud_details(, "irtQ")` for more info + +
+ +## Error before installation + +### Devel + +``` + + + + + + +``` +### CRAN + +``` + + + + + + +``` +# IsoCorrectoR + +
+ +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/IsoCorrectoR +* Number of recursive dependencies: 70 + +Run `revdepcheck::cloud_details(, "IsoCorrectoR")` for more info + +
+ +## Error before installation + +### Devel + +``` + + + + + + +``` +### CRAN + +``` + + + + + + +``` +# itsdm + +
+ +* Version: 0.2.0 +* GitHub: https://github.com/LLeiSong/itsdm +* Source code: https://github.com/cran/itsdm +* Date/Publication: 2023-01-15 14:30:08 UTC +* Number of recursive dependencies: 84 + +Run `revdepcheck::cloud_details(, "itsdm")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/itsdm/new/itsdm.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘itsdm/DESCRIPTION’ ... OK +* this is package ‘itsdm’ version ‘0.2.0’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘sf’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/itsdm/old/itsdm.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘itsdm/DESCRIPTION’ ... OK +* this is package ‘itsdm’ version ‘0.2.0’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘sf’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# journalabbr + +
+ +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/journalabbr +* Number of recursive dependencies: 72 + +Run `revdepcheck::cloud_details(, "journalabbr")` for more info + +
+ +## Error before installation + +### Devel + +``` + + + + + + +``` +### CRAN + +``` + + + + + + +``` +# jpgrid + +
+ +* Version: 0.3.0 +* GitHub: https://github.com/UchidaMizuki/jpgrid +* Source code: https://github.com/cran/jpgrid +* Date/Publication: 2023-02-11 08:50:06 UTC +* Number of recursive dependencies: 57 + +Run `revdepcheck::cloud_details(, "jpgrid")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/jpgrid/new/jpgrid.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘jpgrid/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘jpgrid’ version ‘0.3.0’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘sf’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/jpgrid/old/jpgrid.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘jpgrid/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘jpgrid’ version ‘0.3.0’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘sf’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# jpmesh + +
+ +* Version: 2.1.0 +* GitHub: https://github.com/uribo/jpmesh +* Source code: https://github.com/cran/jpmesh +* Date/Publication: 2022-01-10 03:32:41 UTC +* Number of recursive dependencies: 108 + +Run `revdepcheck::cloud_details(, "jpmesh")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/jpmesh/new/jpmesh.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘jpmesh/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘jpmesh’ version ‘2.1.0’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘sf’ + +Package suggested but not available for checking: ‘lwgeom’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/jpmesh/old/jpmesh.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘jpmesh/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘jpmesh’ version ‘2.1.0’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘sf’ + +Package suggested but not available for checking: ‘lwgeom’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# lifeR + +
+ +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/lifeR +* Number of recursive dependencies: 92 + +Run `revdepcheck::cloud_details(, "lifeR")` for more info + +
+ +## Error before installation + +### Devel + +``` + + + + + + +``` +### CRAN + +``` + + + + + + +``` +# loon.ggplot + +
+ +* Version: 1.3.3 +* GitHub: https://github.com/great-northern-diver/loon.ggplot +* Source code: https://github.com/cran/loon.ggplot +* Date/Publication: 2022-11-12 22:30:02 UTC +* Number of recursive dependencies: 104 + +Run `revdepcheck::cloud_details(, "loon.ggplot")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/loon.ggplot/new/loon.ggplot.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘loon.ggplot/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘loon.ggplot’ version ‘1.3.3’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘loon’ + +Package suggested but not available for checking: ‘zenplots’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/loon.ggplot/old/loon.ggplot.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘loon.ggplot/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘loon.ggplot’ version ‘1.3.3’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘loon’ + +Package suggested but not available for checking: ‘zenplots’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# loon.shiny + +
+ +* Version: 1.0.3 +* GitHub: NA +* Source code: https://github.com/cran/loon.shiny +* Date/Publication: 2022-10-08 15:30:02 UTC +* Number of recursive dependencies: 136 + +Run `revdepcheck::cloud_details(, "loon.shiny")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/loon.shiny/new/loon.shiny.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘loon.shiny/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘loon.shiny’ version ‘1.0.3’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Packages required but not available: 'loon', 'loon.ggplot' + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/loon.shiny/old/loon.shiny.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘loon.shiny/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘loon.shiny’ version ‘1.0.3’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Packages required but not available: 'loon', 'loon.ggplot' + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# MACP + +
+ +* Version: 0.1.0 +* GitHub: https://github.com/mrbakhsh/MACP +* Source code: https://github.com/cran/MACP +* Date/Publication: 2023-02-28 17:32:30 UTC +* Number of recursive dependencies: 231 + +Run `revdepcheck::cloud_details(, "MACP")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/MACP/new/MACP.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘MACP/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘MACP’ version ‘0.1.0’ +* package encoding: UTF-8 +* checking package namespace information ... 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 + ‘MACP_tutorial.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 3 NOTEs + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/MACP/old/MACP.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘MACP/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘MACP’ version ‘0.1.0’ +* package encoding: UTF-8 +* checking package namespace information ... 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 + ‘MACP_tutorial.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 3 NOTEs + + + + + +``` +# mafs + +
+ +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/mafs +* Number of recursive dependencies: 90 + +Run `revdepcheck::cloud_details(, "mafs")` for more info + +
+ +## Error before installation + +### Devel + +``` + + + + + + +``` +### CRAN + +``` + + + + + + +``` +# MainExistingDatasets + +
+ +* Version: 1.0.1 +* GitHub: NA +* Source code: https://github.com/cran/MainExistingDatasets +* Date/Publication: 2022-06-27 14:10:02 UTC +* Number of recursive dependencies: 131 + +Run `revdepcheck::cloud_details(, "MainExistingDatasets")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/MainExistingDatasets/new/MainExistingDatasets.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘MainExistingDatasets/DESCRIPTION’ ... OK +* this is package ‘MainExistingDatasets’ version ‘1.0.1’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘sf’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/MainExistingDatasets/old/MainExistingDatasets.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘MainExistingDatasets/DESCRIPTION’ ... OK +* this is package ‘MainExistingDatasets’ version ‘1.0.1’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘sf’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# MantaID + +
+ +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/MantaID +* Number of recursive dependencies: 152 + +Run `revdepcheck::cloud_details(, "MantaID")` for more info + +
+ +## Error before installation + +### Devel + +``` + + + + + + +``` +### CRAN + +``` + + + + + + +``` +# manydata + +
+ +* Version: 0.8.2 +* GitHub: https://github.com/globalgov/manydata +* Source code: https://github.com/cran/manydata +* Date/Publication: 2022-11-19 13:00:10 UTC +* Number of recursive dependencies: 169 + +Run `revdepcheck::cloud_details(, "manydata")` for more info + +
+ +## In both + +* checking whether package ‘manydata’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/manydata/new/manydata.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘manydata’ ... +** package ‘manydata’ 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 ‘sf’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Execution halted +ERROR: lazy loading failed for package ‘manydata’ +* removing ‘/tmp/workdir/manydata/new/manydata.Rcheck/manydata’ + + +``` +### CRAN + +``` +* installing *source* package ‘manydata’ ... +** package ‘manydata’ 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 ‘sf’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Execution halted +ERROR: lazy loading failed for package ‘manydata’ +* removing ‘/tmp/workdir/manydata/old/manydata.Rcheck/manydata’ + + +``` +# mapboxapi + +
+ +* Version: 0.5 +* GitHub: NA +* Source code: https://github.com/cran/mapboxapi +* Date/Publication: 2022-09-15 16:06:12 UTC +* Number of recursive dependencies: 154 + +Run `revdepcheck::cloud_details(, "mapboxapi")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/mapboxapi/new/mapboxapi.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘mapboxapi/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘mapboxapi’ version ‘0.5’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘sf’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/mapboxapi/old/mapboxapi.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘mapboxapi/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘mapboxapi’ version ‘0.5’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘sf’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# mapme.biodiversity + +
+ +* Version: 0.3.0 +* GitHub: https://github.com/mapme-initiative/mapme.biodiversity +* Source code: https://github.com/cran/mapme.biodiversity +* Date/Publication: 2023-01-21 14:10:02 UTC +* Number of recursive dependencies: 131 + +Run `revdepcheck::cloud_details(, "mapme.biodiversity")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/mapme.biodiversity/new/mapme.biodiversity.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘mapme.biodiversity/DESCRIPTION’ ... OK +* this is package ‘mapme.biodiversity’ version ‘0.3.0’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘sf’ + +Package suggested but not available for checking: ‘lwgeom’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/mapme.biodiversity/old/mapme.biodiversity.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘mapme.biodiversity/DESCRIPTION’ ... OK +* this is package ‘mapme.biodiversity’ version ‘0.3.0’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘sf’ + +Package suggested but not available for checking: ‘lwgeom’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# mapping + +
+ +* Version: 1.3 +* GitHub: https://github.com/serafinialessio/mapping +* Source code: https://github.com/cran/mapping +* Date/Publication: 2021-07-22 17:40:02 UTC +* Number of recursive dependencies: 147 + +Run `revdepcheck::cloud_details(, "mapping")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/mapping/new/mapping.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘mapping/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘mapping’ version ‘1.3’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘sf’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/mapping/old/mapping.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘mapping/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘mapping’ version ‘1.3’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘sf’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# mapsapi + +
+ +* Version: 0.5.3 +* GitHub: https://github.com/michaeldorman/mapsapi +* Source code: https://github.com/cran/mapsapi +* Date/Publication: 2022-01-13 13:22:41 UTC +* Number of recursive dependencies: 89 + +Run `revdepcheck::cloud_details(, "mapsapi")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/mapsapi/new/mapsapi.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘mapsapi/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘mapsapi’ version ‘0.5.3’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘sf’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/mapsapi/old/mapsapi.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘mapsapi/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘mapsapi’ version ‘0.5.3’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘sf’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# mapscanner + +
+ +* Version: 0.0.6 +* GitHub: https://github.com/ropensci/mapscanner +* Source code: https://github.com/cran/mapscanner +* Date/Publication: 2021-11-25 23:10:03 UTC +* Number of recursive dependencies: 143 + +Run `revdepcheck::cloud_details(, "mapscanner")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/mapscanner/new/mapscanner.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘mapscanner/DESCRIPTION’ ... OK +* this is package ‘mapscanner’ version ‘0.0.6’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘sf’ + +Package suggested but not available for checking: ‘lwgeom’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/mapscanner/old/mapscanner.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘mapscanner/DESCRIPTION’ ... OK +* this is package ‘mapscanner’ version ‘0.0.6’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘sf’ + +Package suggested but not available for checking: ‘lwgeom’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# marginaleffects + +
+ +* Version: 0.11.0 +* GitHub: https://github.com/vincentarelbundock/marginaleffects +* Source code: https://github.com/cran/marginaleffects +* Date/Publication: 2023-03-10 10:10:02 UTC +* Number of recursive dependencies: 366 + +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.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘marginaleffects/DESCRIPTION’ ... OK +* this is package ‘marginaleffects’ version ‘0.11.0’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... NOTE +... +* 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.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘marginaleffects/DESCRIPTION’ ... OK +* this is package ‘marginaleffects’ version ‘0.11.0’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... NOTE +... +* 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 + + + + + +``` +# MarketMatching + +
+ +* Version: 1.2.0 +* GitHub: NA +* Source code: https://github.com/cran/MarketMatching +* Date/Publication: 2021-01-08 20:10:02 UTC +* Number of recursive dependencies: 73 + +Run `revdepcheck::cloud_details(, "MarketMatching")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/MarketMatching/new/MarketMatching.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘MarketMatching/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘MarketMatching’ version ‘1.2.0’ +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Packages required but not available: 'CausalImpact', 'bsts', 'Boom' + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/MarketMatching/old/MarketMatching.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘MarketMatching/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘MarketMatching’ version ‘1.2.0’ +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Packages required but not available: 'CausalImpact', 'bsts', 'Boom' + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# MazamaSpatialPlots + +
+ +* Version: 0.2.0 +* GitHub: https://github.com/MazamaScience/MazamaSpatialPlots +* Source code: https://github.com/cran/MazamaSpatialPlots +* Date/Publication: 2022-11-15 21:00:08 UTC +* Number of recursive dependencies: 180 + +Run `revdepcheck::cloud_details(, "MazamaSpatialPlots")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/MazamaSpatialPlots/new/MazamaSpatialPlots.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘MazamaSpatialPlots/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘MazamaSpatialPlots’ version ‘0.2.0’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘sf’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/MazamaSpatialPlots/old/MazamaSpatialPlots.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘MazamaSpatialPlots/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘MazamaSpatialPlots’ version ‘0.2.0’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘sf’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# mbRes + +
+ +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/mbRes +* Number of recursive dependencies: 40 + +Run `revdepcheck::cloud_details(, "mbRes")` for more info + +
+ +## Error before installation + +### Devel + +``` + + + + + + +``` +### CRAN + +``` + + + + + + +``` +# merTools + +
+ +* Version: 0.5.2 +* GitHub: NA +* Source code: https://github.com/cran/merTools +* Date/Publication: 2020-06-23 10:30:12 UTC +* Number of recursive dependencies: 143 + +Run `revdepcheck::cloud_details(, "merTools")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/merTools/new/merTools.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘merTools/DESCRIPTION’ ... OK +* this is package ‘merTools’ version ‘0.5.2’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... NOTE +... +* checking for unstated dependencies in vignettes ... OK +* checking package vignettes in ‘inst/doc’ ... OK +* checking running R code from vignettes ... NONE + ‘Using_predictInterval.Rmd’ using ‘UTF-8’... OK + ‘imputation.Rmd’ using ‘UTF-8’... OK + ‘marginal_effects.Rmd’ using ‘UTF-8’... OK + ‘merToolsIntro.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 1 NOTE + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/merTools/old/merTools.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘merTools/DESCRIPTION’ ... OK +* this is package ‘merTools’ version ‘0.5.2’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... NOTE +... +* checking for unstated dependencies in vignettes ... OK +* checking package vignettes in ‘inst/doc’ ... OK +* checking running R code from vignettes ... NONE + ‘Using_predictInterval.Rmd’ using ‘UTF-8’... OK + ‘imputation.Rmd’ using ‘UTF-8’... OK + ‘marginal_effects.Rmd’ using ‘UTF-8’... OK + ‘merToolsIntro.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 1 NOTE + + + + + +``` +# meteoland + +
+ +* Version: 2.0.0 +* GitHub: NA +* Source code: https://github.com/cran/meteoland +* Date/Publication: 2023-02-17 22:20:02 UTC +* Number of recursive dependencies: 155 + +Run `revdepcheck::cloud_details(, "meteoland")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/meteoland/new/meteoland.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘meteoland/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘meteoland’ version ‘2.0.0’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘sf’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/meteoland/old/meteoland.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘meteoland/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘meteoland’ version ‘2.0.0’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘sf’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# microservices + +
+ +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/microservices +* Number of recursive dependencies: 70 + +Run `revdepcheck::cloud_details(, "microservices")` for more info + +
+ +## Error before installation + +### Devel + +``` + + + + + + +``` +### CRAN + +``` + + + + + + +``` +# modeltime + +
+ +* Version: 1.2.5 +* GitHub: https://github.com/business-science/modeltime +* Source code: https://github.com/cran/modeltime +* Date/Publication: 2023-02-07 19:32:30 UTC +* Number of recursive dependencies: 253 + +Run `revdepcheck::cloud_details(, "modeltime")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/modeltime/new/modeltime.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘modeltime/DESCRIPTION’ ... OK +* this is package ‘modeltime’ version ‘1.2.5’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘prophet’ + +Package suggested but not available for checking: ‘rstan’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/modeltime/old/modeltime.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘modeltime/DESCRIPTION’ ... OK +* this is package ‘modeltime’ version ‘1.2.5’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘prophet’ + +Package suggested but not available for checking: ‘rstan’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# modeltime.ensemble + +
+ +* Version: 1.0.2 +* GitHub: https://github.com/business-science/modeltime.ensemble +* Source code: https://github.com/cran/modeltime.ensemble +* Date/Publication: 2022-10-18 23:02:40 UTC +* Number of recursive dependencies: 223 + +Run `revdepcheck::cloud_details(, "modeltime.ensemble")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/modeltime.ensemble/new/modeltime.ensemble.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘modeltime.ensemble/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘modeltime.ensemble’ version ‘1.0.2’ +* package encoding: UTF-8 +* checking package namespace information ... OK +... +--- finished re-building ‘recursive-ensembles.Rmd’ + +SUMMARY: processing the following file failed: + ‘getting-started-with-modeltime-ensemble.Rmd’ + +Error: Vignette re-building failed. +Execution halted + +* DONE +Status: 1 ERROR, 1 WARNING, 1 NOTE + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/modeltime.ensemble/old/modeltime.ensemble.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘modeltime.ensemble/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘modeltime.ensemble’ version ‘1.0.2’ +* package encoding: UTF-8 +* checking package namespace information ... OK +... +--- finished re-building ‘recursive-ensembles.Rmd’ + +SUMMARY: processing the following file failed: + ‘getting-started-with-modeltime-ensemble.Rmd’ + +Error: Vignette re-building failed. +Execution halted + +* DONE +Status: 1 ERROR, 1 WARNING, 1 NOTE + + + + + +``` +# modeltime.gluonts + +
+ +* Version: 0.1.0 +* GitHub: https://github.com/business-science/modeltime.gluonts +* Source code: https://github.com/cran/modeltime.gluonts +* Date/Publication: 2020-11-30 09:40:02 UTC +* Number of recursive dependencies: 214 + +Run `revdepcheck::cloud_details(, "modeltime.gluonts")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/modeltime.gluonts/new/modeltime.gluonts.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘modeltime.gluonts/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘modeltime.gluonts’ version ‘0.1.0’ +* package encoding: UTF-8 +* checking package namespace information ... 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 + ‘getting-started.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 1 NOTE + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/modeltime.gluonts/old/modeltime.gluonts.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘modeltime.gluonts/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘modeltime.gluonts’ version ‘0.1.0’ +* package encoding: UTF-8 +* checking package namespace information ... 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 + ‘getting-started.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 1 NOTE + + + + + +``` +# modeltime.h2o + +
+ +* Version: 0.1.1 +* GitHub: https://github.com/business-science/modeltime.h2o +* Source code: https://github.com/cran/modeltime.h2o +* Date/Publication: 2021-04-05 14:40:03 UTC +* Number of recursive dependencies: 214 + +Run `revdepcheck::cloud_details(, "modeltime.h2o")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/modeltime.h2o/new/modeltime.h2o.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘modeltime.h2o/DESCRIPTION’ ... OK +* this is package ‘modeltime.h2o’ version ‘0.1.1’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... OK +... +* checking for code/documentation mismatches ... OK +* checking Rd \usage sections ... OK +* checking Rd contents ... OK +* checking for unstated dependencies in examples ... 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/modeltime.h2o/old/modeltime.h2o.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘modeltime.h2o/DESCRIPTION’ ... OK +* this is package ‘modeltime.h2o’ version ‘0.1.1’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... OK +... +* checking for code/documentation mismatches ... OK +* checking Rd \usage sections ... OK +* checking Rd contents ... OK +* checking for unstated dependencies in examples ... OK +* checking examples ... OK +* checking for unstated dependencies in ‘tests’ ... OK +* checking tests ... OK + Running ‘testthat.R’ +* DONE +Status: OK + + + + + +``` +# modeltime.resample + +
+ +* Version: 0.2.2 +* GitHub: https://github.com/business-science/modeltime.resample +* Source code: https://github.com/cran/modeltime.resample +* Date/Publication: 2022-10-18 03:00:06 UTC +* Number of recursive dependencies: 221 + +Run `revdepcheck::cloud_details(, "modeltime.resample")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/modeltime.resample/new/modeltime.resample.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘modeltime.resample/DESCRIPTION’ ... OK +* this is package ‘modeltime.resample’ version ‘0.2.2’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... OK +... +--- failed re-building ‘panel-data.Rmd’ + +SUMMARY: processing the following file failed: + ‘panel-data.Rmd’ + +Error: Vignette re-building failed. +Execution halted + +* DONE +Status: 1 ERROR, 1 WARNING, 1 NOTE + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/modeltime.resample/old/modeltime.resample.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘modeltime.resample/DESCRIPTION’ ... OK +* this is package ‘modeltime.resample’ version ‘0.2.2’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... OK +... +--- failed re-building ‘panel-data.Rmd’ + +SUMMARY: processing the following file failed: + ‘panel-data.Rmd’ + +Error: Vignette re-building failed. +Execution halted + +* DONE +Status: 1 ERROR, 1 WARNING, 1 NOTE + + + + + +``` +# moexer + +
+ +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/moexer +* Number of recursive dependencies: 86 + +Run `revdepcheck::cloud_details(, "moexer")` for more info + +
+ +## Error before installation + +### Devel + +``` + + + + + + +``` +### CRAN + +``` + + + + + + +``` +# motif + +
+ +* Version: 0.5.2 +* GitHub: https://github.com/Nowosad/motif +* Source code: https://github.com/cran/motif +* Date/Publication: 2022-06-07 05:10:02 UTC * Number of recursive dependencies: 86 -Run `revdepcheck::cloud_details(, "forceR")` for more info +Run `revdepcheck::cloud_details(, "motif")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/motif/new/motif.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘motif/DESCRIPTION’ ... OK +* this is package ‘motif’ version ‘0.5.2’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘sf’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/motif/old/motif.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘motif/DESCRIPTION’ ... OK +* this is package ‘motif’ version ‘0.5.2’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘sf’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# mpower + +
+ +* Version: 0.1.0 +* GitHub: NA +* Source code: https://github.com/cran/mpower +* Date/Publication: 2022-09-21 08:50:05 UTC +* Number of recursive dependencies: 132 + +Run `revdepcheck::cloud_details(, "mpower")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/mpower/new/mpower.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘mpower/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘mpower’ version ‘0.1.0’ +* package encoding: UTF-8 +* checking package namespace information ... 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 + +``` +* using log directory ‘/tmp/workdir/mpower/old/mpower.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘mpower/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘mpower’ version ‘0.1.0’ +* package encoding: UTF-8 +* checking package namespace information ... 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 + + + + + +``` +# MSclassifR + +
+ +* Version: 0.3.1 +* GitHub: https://github.com/agodmer/MSclassifR_examples +* Source code: https://github.com/cran/MSclassifR +* Date/Publication: 2022-09-29 06:10:12 UTC +* Number of recursive dependencies: 227 + +Run `revdepcheck::cloud_details(, "MSclassifR")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/MSclassifR/new/MSclassifR.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘MSclassifR/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘MSclassifR’ version ‘0.3.1’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘VSURF’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/MSclassifR/old/MSclassifR.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘MSclassifR/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘MSclassifR’ version ‘0.3.1’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘VSURF’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# multibiasmeta + +
+ +* Version: 0.1.0 +* GitHub: https://github.com/mathurlabstanford/multibiasmeta +* Source code: https://github.com/cran/multibiasmeta +* Date/Publication: 2023-02-08 09:40:02 UTC +* Number of recursive dependencies: 99 + +Run `revdepcheck::cloud_details(, "multibiasmeta")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/multibiasmeta/new/multibiasmeta.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘multibiasmeta/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘multibiasmeta’ version ‘0.1.0’ +* package encoding: UTF-8 +* checking package namespace information ... OK +... +--- failed re-building ‘tutorial.Rmd’ + +SUMMARY: processing the following file failed: + ‘tutorial.Rmd’ + +Error: Vignette re-building failed. +Execution halted + +* DONE +Status: 1 WARNING, 1 NOTE + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/multibiasmeta/old/multibiasmeta.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘multibiasmeta/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘multibiasmeta’ version ‘0.1.0’ +* package encoding: UTF-8 +* checking package namespace information ... OK +... +--- failed re-building ‘tutorial.Rmd’ + +SUMMARY: processing the following file failed: + ‘tutorial.Rmd’ + +Error: Vignette re-building failed. +Execution halted + +* DONE +Status: 1 WARNING, 1 NOTE + + + + + +``` +# naturaList + +
+ +* Version: 0.5.0 +* GitHub: https://github.com/avrodrigues/naturaList +* Source code: https://github.com/cran/naturaList +* Date/Publication: 2022-04-20 13:30:02 UTC +* Number of recursive dependencies: 129 + +Run `revdepcheck::cloud_details(, "naturaList")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/naturaList/new/naturaList.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘naturaList/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘naturaList’ version ‘0.5.0’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘sf’ + +Package suggested but not available for checking: ‘lwgeom’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/naturaList/old/naturaList.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘naturaList/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘naturaList’ version ‘0.5.0’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘sf’ + +Package suggested but not available for checking: ‘lwgeom’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# ncdfgeom + +
+ +* Version: 1.1.4 +* GitHub: https://github.com/USGS-R/ncdfgeom +* Source code: https://github.com/cran/ncdfgeom +* Date/Publication: 2022-11-08 22:40:02 UTC +* Number of recursive dependencies: 90 + +Run `revdepcheck::cloud_details(, "ncdfgeom")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/ncdfgeom/new/ncdfgeom.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘ncdfgeom/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘ncdfgeom’ version ‘1.1.4’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘sf’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/ncdfgeom/old/ncdfgeom.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘ncdfgeom/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘ncdfgeom’ version ‘1.1.4’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘sf’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# nhdplusTools + +
+ +* Version: 0.6.2 +* GitHub: https://github.com/doi-usgs/nhdplusTools +* Source code: https://github.com/cran/nhdplusTools +* Date/Publication: 2023-03-10 09:40:14 UTC +* Number of recursive dependencies: 167 + +Run `revdepcheck::cloud_details(, "nhdplusTools")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/nhdplusTools/new/nhdplusTools.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘nhdplusTools/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘nhdplusTools’ version ‘0.6.2’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘sf’ + +Package suggested but not available for checking: ‘lwgeom’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/nhdplusTools/old/nhdplusTools.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘nhdplusTools/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘nhdplusTools’ version ‘0.6.2’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘sf’ + +Package suggested but not available for checking: ‘lwgeom’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# nhdR + +
+ +* Version: 0.5.9 +* GitHub: https://github.com/jsta/nhdR +* Source code: https://github.com/cran/nhdR +* Date/Publication: 2022-10-09 02:10:02 UTC +* Number of recursive dependencies: 104 + +Run `revdepcheck::cloud_details(, "nhdR")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/nhdR/new/nhdR.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘nhdR/DESCRIPTION’ ... OK +* this is package ‘nhdR’ version ‘0.5.9’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘sf’ + +Package suggested but not available for checking: ‘lwgeom’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/nhdR/old/nhdR.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘nhdR/DESCRIPTION’ ... OK +* this is package ‘nhdR’ version ‘0.5.9’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘sf’ + +Package suggested but not available for checking: ‘lwgeom’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# nlmixr2extra + +
+ +* Version: 2.0.8 +* GitHub: https://github.com/nlmixr2/nlmixr2extra +* Source code: https://github.com/cran/nlmixr2extra +* Date/Publication: 2022-10-22 22:32:34 UTC +* Number of recursive dependencies: 203 + +Run `revdepcheck::cloud_details(, "nlmixr2extra")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/nlmixr2extra/new/nlmixr2extra.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘nlmixr2extra/DESCRIPTION’ ... OK +* this is package ‘nlmixr2extra’ version ‘2.0.8’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Packages required but not available: 'nlmixr2est', 'symengine' + +Package suggested but not available for checking: ‘brms’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/nlmixr2extra/old/nlmixr2extra.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘nlmixr2extra/DESCRIPTION’ ... OK +* this is package ‘nlmixr2extra’ version ‘2.0.8’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Packages required but not available: 'nlmixr2est', 'symengine' + +Package suggested but not available for checking: ‘brms’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# nlmixr2plot + +
+ +* Version: 2.0.7 +* GitHub: https://github.com/nlmixr2/nlmixr2plot +* Source code: https://github.com/cran/nlmixr2plot +* Date/Publication: 2022-10-20 03:12:36 UTC +* Number of recursive dependencies: 163 + +Run `revdepcheck::cloud_details(, "nlmixr2plot")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/nlmixr2plot/new/nlmixr2plot.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘nlmixr2plot/DESCRIPTION’ ... OK +* this is package ‘nlmixr2plot’ version ‘2.0.7’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Packages required but not available: 'nlmixr2est', 'nlmixr2extra' + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/nlmixr2plot/old/nlmixr2plot.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘nlmixr2plot/DESCRIPTION’ ... OK +* this is package ‘nlmixr2plot’ version ‘2.0.7’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Packages required but not available: 'nlmixr2est', 'nlmixr2extra' + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# nlmixr2rpt + +
+ +* Version: 0.1.0 +* GitHub: https://github.com/nlmixr2/nlmixr2rpt +* Source code: https://github.com/cran/nlmixr2rpt +* Date/Publication: 2022-12-05 10:40:02 UTC +* Number of recursive dependencies: 218 + +Run `revdepcheck::cloud_details(, "nlmixr2rpt")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/nlmixr2rpt/new/nlmixr2rpt.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘nlmixr2rpt/DESCRIPTION’ ... OK +* this is package ‘nlmixr2rpt’ version ‘0.1.0’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Packages required but not available: 'nlmixr2extra', 'xpose.nlmixr2' + +Package suggested but not available for checking: ‘nlmixr2’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/nlmixr2rpt/old/nlmixr2rpt.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘nlmixr2rpt/DESCRIPTION’ ... OK +* this is package ‘nlmixr2rpt’ version ‘0.1.0’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Packages required but not available: 'nlmixr2extra', 'xpose.nlmixr2' + +Package suggested but not available for checking: ‘nlmixr2’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# numbat + +
+ +* Version: 1.2.2 +* GitHub: https://github.com/kharchenkolab/numbat +* Source code: https://github.com/cran/numbat +* Date/Publication: 2023-02-14 18:20:02 UTC +* Number of recursive dependencies: 132 + +Run `revdepcheck::cloud_details(, "numbat")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/numbat/new/numbat.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘numbat/DESCRIPTION’ ... OK +* this is package ‘numbat’ version ‘1.2.2’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Packages required but not available: 'ggtree', 'scistreer' + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/numbat/old/numbat.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘numbat/DESCRIPTION’ ... OK +* this is package ‘numbat’ version ‘1.2.2’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Packages required but not available: 'ggtree', 'scistreer' + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# OBL + +
+ +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/OBL +* Number of recursive dependencies: 73 + +Run `revdepcheck::cloud_details(, "OBL")` for more info + +
+ +## Error before installation + +### Devel + +``` + + + + + + +``` +### CRAN + +``` + + + + + + +``` +# occCite + +
+ +* Version: 0.5.6 +* GitHub: https://github.com/ropensci/occCite +* Source code: https://github.com/cran/occCite +* Date/Publication: 2022-08-05 11:40:02 UTC +* Number of recursive dependencies: 176 + +Run `revdepcheck::cloud_details(, "occCite")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/occCite/new/occCite.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘occCite/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘occCite’ version ‘0.5.6’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘BIEN’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/occCite/old/occCite.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘occCite/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘occCite’ version ‘0.5.6’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘BIEN’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# occUncertain + +
+ +* Version: 0.1.0 +* GitHub: https://github.com/mlammens/occUncertain +* Source code: https://github.com/cran/occUncertain +* Date/Publication: 2023-01-20 10:10:06 UTC +* Number of recursive dependencies: 103 + +Run `revdepcheck::cloud_details(, "occUncertain")` for more info + +
+ +## In both + +* checking whether package ‘occUncertain’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/occUncertain/new/occUncertain.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘occUncertain’ ... +** package ‘occUncertain’ 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 ‘ConR’ in loadNamespace(i, c(lib.loc, .libPaths()), versionCheck = vI[[i]]): + there is no package called ‘sf’ +Execution halted +ERROR: lazy loading failed for package ‘occUncertain’ +* removing ‘/tmp/workdir/occUncertain/new/occUncertain.Rcheck/occUncertain’ + + +``` +### CRAN + +``` +* installing *source* package ‘occUncertain’ ... +** package ‘occUncertain’ 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 ‘ConR’ in loadNamespace(i, c(lib.loc, .libPaths()), versionCheck = vI[[i]]): + there is no package called ‘sf’ +Execution halted +ERROR: lazy loading failed for package ‘occUncertain’ +* removing ‘/tmp/workdir/occUncertain/old/occUncertain.Rcheck/occUncertain’ + + +``` +# oceanexplorer + +
+ +* Version: 0.0.2 +* GitHub: https://github.com/UtrechtUniversity/oceanexplorer +* Source code: https://github.com/cran/oceanexplorer +* Date/Publication: 2022-09-15 09:10:08 UTC +* Number of recursive dependencies: 158 + +Run `revdepcheck::cloud_details(, "oceanexplorer")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/oceanexplorer/new/oceanexplorer.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘oceanexplorer/DESCRIPTION’ ... OK +* this is package ‘oceanexplorer’ version ‘0.0.2’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘sf’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/oceanexplorer/old/oceanexplorer.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘oceanexplorer/DESCRIPTION’ ... OK +* this is package ‘oceanexplorer’ version ‘0.0.2’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘sf’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# oceanis + +
+ +* Version: 1.8.5 +* GitHub: https://github.com/insee-psar-at/oceanis-package +* Source code: https://github.com/cran/oceanis +* Date/Publication: 2022-07-13 13:10:02 UTC +* Number of recursive dependencies: 117 + +Run `revdepcheck::cloud_details(, "oceanis")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/oceanis/new/oceanis.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘oceanis/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘oceanis’ version ‘1.8.5’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Packages required but not available: 'sf', 'lwgeom' + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/oceanis/old/oceanis.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘oceanis/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘oceanis’ version ‘1.8.5’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Packages required but not available: 'sf', 'lwgeom' + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# ohsome + +
+ +* Version: 0.2.1 +* GitHub: https://github.com/GIScience/ohsome-r +* Source code: https://github.com/cran/ohsome +* Date/Publication: 2023-02-22 14:50:02 UTC +* Number of recursive dependencies: 150 + +Run `revdepcheck::cloud_details(, "ohsome")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/ohsome/new/ohsome.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘ohsome/DESCRIPTION’ ... OK +* this is package ‘ohsome’ version ‘0.2.1’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘sf’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/ohsome/old/ohsome.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘ohsome/DESCRIPTION’ ... OK +* this is package ‘ohsome’ version ‘0.2.1’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘sf’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# OlinkAnalyze + +
+ +* Version: 3.3.1 +* GitHub: NA +* Source code: https://github.com/cran/OlinkAnalyze +* Date/Publication: 2023-02-27 20:22:30 UTC +* Number of recursive dependencies: 202 + +Run `revdepcheck::cloud_details(, "OlinkAnalyze")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/OlinkAnalyze/new/OlinkAnalyze.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘OlinkAnalyze/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘OlinkAnalyze’ version ‘3.3.1’ +* package encoding: UTF-8 +* checking package namespace information ... 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 + ‘Vignett.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 1 NOTE + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/OlinkAnalyze/old/OlinkAnalyze.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘OlinkAnalyze/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘OlinkAnalyze’ version ‘3.3.1’ +* package encoding: UTF-8 +* checking package namespace information ... 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 + ‘Vignett.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 1 NOTE + + + + + +``` +# OpenLand + +
+ +* Version: 1.0.2 +* GitHub: https://github.com/reginalexavier/OpenLand +* Source code: https://github.com/cran/OpenLand +* Date/Publication: 2021-11-02 07:20:02 UTC +* Number of recursive dependencies: 121 + +Run `revdepcheck::cloud_details(, "OpenLand")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/OpenLand/new/OpenLand.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘OpenLand/DESCRIPTION’ ... OK +* this is package ‘OpenLand’ version ‘1.0.2’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... 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 + ‘openland_vignette.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: OK + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/OpenLand/old/OpenLand.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘OpenLand/DESCRIPTION’ ... OK +* this is package ‘OpenLand’ version ‘1.0.2’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... 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 + ‘openland_vignette.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: OK + + + + + +``` +# palaeoSig + +
+ +* Version: 2.1-3 +* GitHub: https://github.com/richardjtelford/palaeoSig +* Source code: https://github.com/cran/palaeoSig +* Date/Publication: 2023-03-10 09:30:02 UTC +* Number of recursive dependencies: 104 + +Run `revdepcheck::cloud_details(, "palaeoSig")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/palaeoSig/new/palaeoSig.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘palaeoSig/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘palaeoSig’ version ‘2.1-3’ +* package encoding: UTF-8 +* checking package namespace information ... OK +... +--- failed re-building ‘randomTF-spatial.Rmd’ + +SUMMARY: processing the following files failed: + ‘h-block-crossvalidation.Rmd’ ‘randomTF-spatial.Rmd’ + +Error: Vignette re-building failed. +Execution halted + +* DONE +Status: 1 ERROR, 1 WARNING, 1 NOTE + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/palaeoSig/old/palaeoSig.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘palaeoSig/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘palaeoSig’ version ‘2.1-3’ +* package encoding: UTF-8 +* checking package namespace information ... OK +... +--- failed re-building ‘randomTF-spatial.Rmd’ + +SUMMARY: processing the following files failed: + ‘h-block-crossvalidation.Rmd’ ‘randomTF-spatial.Rmd’ + +Error: Vignette re-building failed. +Execution halted + +* DONE +Status: 1 ERROR, 1 WARNING, 1 NOTE + + + + + +``` +# panelr + +
+ +* Version: 0.7.7 +* GitHub: https://github.com/jacob-long/panelr +* Source code: https://github.com/cran/panelr +* Date/Publication: 2023-02-09 16:00:02 UTC +* Number of recursive dependencies: 169 + +Run `revdepcheck::cloud_details(, "panelr")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/panelr/new/panelr.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘panelr/DESCRIPTION’ ... OK +* this is package ‘panelr’ version ‘0.7.7’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... NOTE +... + 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 ... NONE + ‘reshape.Rmd’ using ‘UTF-8’... OK + ‘wbm.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 1 ERROR, 2 NOTEs + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/panelr/old/panelr.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘panelr/DESCRIPTION’ ... OK +* this is package ‘panelr’ version ‘0.7.7’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... NOTE +... + 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 ... NONE + ‘reshape.Rmd’ using ‘UTF-8’... OK + ‘wbm.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 1 ERROR, 2 NOTEs + + + + + +``` +# pathwayTMB + +
+ +* Version: 0.1.3 +* GitHub: NA +* Source code: https://github.com/cran/pathwayTMB +* Date/Publication: 2022-08-09 13:50:02 UTC +* Number of recursive dependencies: 221 + +Run `revdepcheck::cloud_details(, "pathwayTMB")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/pathwayTMB/new/pathwayTMB.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘pathwayTMB/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘pathwayTMB’ version ‘0.1.3’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘clusterProfiler’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/pathwayTMB/old/pathwayTMB.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘pathwayTMB/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘pathwayTMB’ version ‘0.1.3’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘clusterProfiler’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# pct + +
+ +* Version: 0.9.8 +* GitHub: https://github.com/ITSLeeds/pct +* Source code: https://github.com/cran/pct +* Date/Publication: 2023-02-16 00:30:02 UTC +* Number of recursive dependencies: 138 + +Run `revdepcheck::cloud_details(, "pct")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/pct/new/pct.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘pct/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘pct’ version ‘0.9.8’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘sf’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/pct/old/pct.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘pct/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘pct’ version ‘0.9.8’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘sf’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# peramo + +
+ +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/peramo +* Number of recursive dependencies: 17 + +Run `revdepcheck::cloud_details(, "peramo")` for more info + +
+ +## Error before installation + +### Devel + +``` + + + + + + +``` +### CRAN + +``` + + + + + + +``` +# photosynthesis + +
+ +* Version: 2.1.1 +* GitHub: https://github.com/cdmuir/photosynthesis +* Source code: https://github.com/cran/photosynthesis +* Date/Publication: 2022-11-19 19:40:09 UTC +* Number of recursive dependencies: 135 + +Run `revdepcheck::cloud_details(, "photosynthesis")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/photosynthesis/new/photosynthesis.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘photosynthesis/DESCRIPTION’ ... OK +* this is package ‘photosynthesis’ version ‘2.1.1’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... NOTE +... + ‘mesophyll-conductance.Rmd’ using ‘UTF-8’... OK + ‘modeling-recommendations.Rmd’ using ‘UTF-8’... OK + ‘photosynthesis-introduction.Rmd’ using ‘UTF-8’... OK + ‘pressure-volume.Rmd’ using ‘UTF-8’... OK + ‘sensitivity-analysis.Rmd’ using ‘UTF-8’... OK + ‘stomatal-conductance.Rmd’ using ‘UTF-8’... OK + ‘temperature-response.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 1 ERROR, 4 NOTEs + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/photosynthesis/old/photosynthesis.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘photosynthesis/DESCRIPTION’ ... OK +* this is package ‘photosynthesis’ version ‘2.1.1’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... NOTE +... + ‘mesophyll-conductance.Rmd’ using ‘UTF-8’... OK + ‘modeling-recommendations.Rmd’ using ‘UTF-8’... OK + ‘photosynthesis-introduction.Rmd’ using ‘UTF-8’... OK + ‘pressure-volume.Rmd’ using ‘UTF-8’... OK + ‘sensitivity-analysis.Rmd’ using ‘UTF-8’... OK + ‘stomatal-conductance.Rmd’ using ‘UTF-8’... OK + ‘temperature-response.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 1 ERROR, 4 NOTEs + + + + + +``` +# Platypus + +
+ +* Version: 3.4.1 +* GitHub: NA +* Source code: https://github.com/cran/Platypus +* Date/Publication: 2022-08-15 07:20:20 UTC +* Number of recursive dependencies: 356 + +Run `revdepcheck::cloud_details(, "Platypus")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/Platypus/new/Platypus.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘Platypus/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘Platypus’ version ‘3.4.1’ +* package encoding: UTF-8 +* checking package namespace information ... OK +... +* checking package dependencies ... ERROR +Package required but not available: ‘ggtree’ + +Packages suggested but not available for checking: + 'Matrix.utils', 'monocle3', 'ProjecTILs', 'SeuratWrappers' + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/Platypus/old/Platypus.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘Platypus/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘Platypus’ version ‘3.4.1’ +* package encoding: UTF-8 +* checking package namespace information ... OK +... +* checking package dependencies ... ERROR +Package required but not available: ‘ggtree’ + +Packages suggested but not available for checking: + 'Matrix.utils', 'monocle3', 'ProjecTILs', 'SeuratWrappers' + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# PLSiMCpp + +
+ +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/PLSiMCpp +* Number of recursive dependencies: 10 + +Run `revdepcheck::cloud_details(, "PLSiMCpp")` for more info + +
+ +## Error before installation + +### Devel + +``` + + + + + + +``` +### CRAN + +``` + + + + + + +``` +# PoolTestR + +
+ +* Version: 0.1.3 +* GitHub: https://github.com/AngusMcLure/PoolTestR +* Source code: https://github.com/cran/PoolTestR +* Date/Publication: 2022-07-01 07:30:02 UTC +* Number of recursive dependencies: 132 + +Run `revdepcheck::cloud_details(, "PoolTestR")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/PoolTestR/new/PoolTestR.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘PoolTestR/DESCRIPTION’ ... OK +* this is package ‘PoolTestR’ version ‘0.1.3’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Packages required but not available: 'rstan', 'brms' + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/PoolTestR/old/PoolTestR.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘PoolTestR/DESCRIPTION’ ... OK +* this is package ‘PoolTestR’ version ‘0.1.3’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Packages required but not available: 'rstan', 'brms' + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# PopGenHelpR + +
+ +* Version: 1.0.0 +* GitHub: https://github.com/kfarleigh/PopGenHelpR +* Source code: https://github.com/cran/PopGenHelpR +* Date/Publication: 2023-02-13 08:40:05 UTC +* Number of recursive dependencies: 187 + +Run `revdepcheck::cloud_details(, "PopGenHelpR")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/PopGenHelpR/new/PopGenHelpR.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘PopGenHelpR/DESCRIPTION’ ... OK +* this is package ‘PopGenHelpR’ version ‘1.0.0’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... 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 + ‘PopGenHelpR_vignette.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: OK + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/PopGenHelpR/old/PopGenHelpR.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘PopGenHelpR/DESCRIPTION’ ... OK +* this is package ‘PopGenHelpR’ version ‘1.0.0’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... 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 + ‘PopGenHelpR_vignette.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: OK + + + + + +``` +# ppcSpatial + +
+ +* Version: 0.2.0 +* GitHub: https://github.com/MYaseen208/ppcSpatial +* Source code: https://github.com/cran/ppcSpatial +* Date/Publication: 2018-03-07 15:54:23 UTC +* Number of recursive dependencies: 118 + +Run `revdepcheck::cloud_details(, "ppcSpatial")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/ppcSpatial/new/ppcSpatial.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘ppcSpatial/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘ppcSpatial’ version ‘0.2.0’ +* checking package namespace information ... OK +* checking package dependencies ... 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 ‘ppcSpatial’ can be installed ... ERROR +Installation failed. +See ‘/tmp/workdir/ppcSpatial/new/ppcSpatial.Rcheck/00install.out’ for details. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/ppcSpatial/old/ppcSpatial.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘ppcSpatial/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘ppcSpatial’ version ‘0.2.0’ +* checking package namespace information ... OK +* checking package dependencies ... 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 ‘ppcSpatial’ can be installed ... ERROR +Installation failed. +See ‘/tmp/workdir/ppcSpatial/old/ppcSpatial.Rcheck/00install.out’ for details. +* DONE +Status: 1 ERROR + + + + + +``` +# prioriactions + +
+ +* Version: 0.4.1 +* GitHub: https://github.com/prioriactions/prioriactions +* Source code: https://github.com/cran/prioriactions +* Date/Publication: 2022-08-16 13:30:02 UTC +* Number of recursive dependencies: 130 + +Run `revdepcheck::cloud_details(, "prioriactions")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/prioriactions/new/prioriactions.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘prioriactions/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘prioriactions’ version ‘0.4.1’ +* package encoding: UTF-8 +* checking package namespace information ... OK +... +* checking for unstated dependencies in vignettes ... OK +* checking package vignettes in ‘inst/doc’ ... OK +* checking running R code from vignettes ... NONE + ‘objectives.Rmd’ using ‘UTF-8’... OK + ‘sensitivities.Rmd’ using ‘UTF-8’... OK + ‘MitchellRiver.Rmd’ using ‘UTF-8’... OK + ‘prioriactions.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 2 NOTEs + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/prioriactions/old/prioriactions.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘prioriactions/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘prioriactions’ version ‘0.4.1’ +* package encoding: UTF-8 +* checking package namespace information ... OK +... +* checking for unstated dependencies in vignettes ... OK +* checking package vignettes in ‘inst/doc’ ... OK +* checking running R code from vignettes ... NONE + ‘objectives.Rmd’ using ‘UTF-8’... OK + ‘sensitivities.Rmd’ using ‘UTF-8’... OK + ‘MitchellRiver.Rmd’ using ‘UTF-8’... OK + ‘prioriactions.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 2 NOTEs + + + + + +``` +# promotionImpact + +
+ +* Version: 0.1.5 +* GitHub: https://github.com/ncsoft/promotionImpact +* Source code: https://github.com/cran/promotionImpact +* Date/Publication: 2021-04-13 15:00:05 UTC +* Number of recursive dependencies: 122 + +Run `revdepcheck::cloud_details(, "promotionImpact")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/promotionImpact/new/promotionImpact.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘promotionImpact/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘promotionImpact’ version ‘0.1.5’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘prophet’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/promotionImpact/old/promotionImpact.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘promotionImpact/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘promotionImpact’ version ‘0.1.5’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘prophet’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# prqlr + +
+ +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/prqlr +* Number of recursive dependencies: 66 + +Run `revdepcheck::cloud_details(, "prqlr")` for more info + +
+ +## Error before installation + +### Devel + +``` + + + + + + +``` +### CRAN + +``` + + + + + + +``` +# PSS.Health + +
+ +* Version: 0.6.1 +* GitHub: NA +* Source code: https://github.com/cran/PSS.Health +* Date/Publication: 2023-02-01 17:50:11 UTC +* Number of recursive dependencies: 187 + +Run `revdepcheck::cloud_details(, "PSS.Health")` for more info + +
+ +## In both + +* checking whether package ‘PSS.Health’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/PSS.Health/new/PSS.Health.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘PSS.Health’ ... +** package ‘PSS.Health’ 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 ‘sf’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Execution halted +ERROR: lazy loading failed for package ‘PSS.Health’ +* removing ‘/tmp/workdir/PSS.Health/new/PSS.Health.Rcheck/PSS.Health’ + + +``` +### CRAN + +``` +* installing *source* package ‘PSS.Health’ ... +** package ‘PSS.Health’ 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 ‘sf’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Execution halted +ERROR: lazy loading failed for package ‘PSS.Health’ +* removing ‘/tmp/workdir/PSS.Health/old/PSS.Health.Rcheck/PSS.Health’ + + +``` +# PsychWordVec + +
+ +* Version: 0.3.2 +* GitHub: https://github.com/psychbruce/PsychWordVec +* Source code: https://github.com/cran/PsychWordVec +* Date/Publication: 2023-03-04 16:20:02 UTC +* Number of recursive dependencies: 228 + +Run `revdepcheck::cloud_details(, "PsychWordVec")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/PsychWordVec/new/PsychWordVec.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘PsychWordVec/DESCRIPTION’ ... OK +* this is package ‘PsychWordVec’ version ‘0.3.2’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘bruceR’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/PsychWordVec/old/PsychWordVec.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘PsychWordVec/DESCRIPTION’ ... OK +* this is package ‘PsychWordVec’ version ‘0.3.2’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘bruceR’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# rangeModelMetadata + +
+ +* Version: 0.1.4 +* GitHub: NA +* Source code: https://github.com/cran/rangeModelMetadata +* Date/Publication: 2021-06-11 08:40:02 UTC +* Number of recursive dependencies: 192 + +Run `revdepcheck::cloud_details(, "rangeModelMetadata")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/rangeModelMetadata/new/rangeModelMetadata.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘rangeModelMetadata/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘rangeModelMetadata’ version ‘0.1.4’ +* package encoding: UTF-8 +* checking package namespace information ... 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 + ‘rmm_Multispecies.Rmd’ using ‘UTF-8’... OK + ‘rmm_directory.Rmd’ using ‘UTF-8’... OK + ‘rmm_vignette.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 3 NOTEs + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/rangeModelMetadata/old/rangeModelMetadata.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘rangeModelMetadata/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘rangeModelMetadata’ version ‘0.1.4’ +* package encoding: UTF-8 +* checking package namespace information ... 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 + ‘rmm_Multispecies.Rmd’ using ‘UTF-8’... OK + ‘rmm_directory.Rmd’ using ‘UTF-8’... OK + ‘rmm_vignette.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 3 NOTEs + + + + + +``` +# rbenvo + +
+ +* Version: 1.0.5 +* GitHub: https://github.com/apeterson91/rbenvo +* Source code: https://github.com/cran/rbenvo +* Date/Publication: 2020-11-18 10:40:02 UTC +* Number of recursive dependencies: 104 + +Run `revdepcheck::cloud_details(, "rbenvo")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/rbenvo/new/rbenvo.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘rbenvo/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘rbenvo’ version ‘1.0.5’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘sf’ + +Package suggested but not available for checking: ‘lwgeom’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/rbenvo/old/rbenvo.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘rbenvo/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘rbenvo’ version ‘1.0.5’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘sf’ + +Package suggested but not available for checking: ‘lwgeom’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# RBesT + +
+ +* Version: 1.6-6 +* GitHub: https://github.com/Novartis/RBesT +* Source code: https://github.com/cran/RBesT +* Date/Publication: 2023-03-03 18:20:02 UTC +* Number of recursive dependencies: 131 + +Run `revdepcheck::cloud_details(, "RBesT")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/RBesT/new/RBesT.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘RBesT/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘RBesT’ version ‘1.6-6’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘rstan’ + +Package suggested but not available for checking: ‘rstanarm’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/RBesT/old/RBesT.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘RBesT/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘RBesT’ version ‘1.6-6’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘rstan’ + +Package suggested but not available for checking: ‘rstanarm’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +# rcontroll + +
+ +* Version: 0.1.0 +* GitHub: https://github.com/sylvainschmitt/rcontroll +* Source code: https://github.com/cran/rcontroll +* Date/Publication: 2023-02-11 15:20:02 UTC +* Number of recursive dependencies: 128 + +Run `revdepcheck::cloud_details(, "rcontroll")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/rcontroll/new/rcontroll.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘rcontroll/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘rcontroll’ version ‘0.1.0’ +* package encoding: UTF-8 +* checking package namespace information ... 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 ‘rcontroll’ can be installed ... ERROR +Installation failed. +See ‘/tmp/workdir/rcontroll/new/rcontroll.Rcheck/00install.out’ for details. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/rcontroll/old/rcontroll.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘rcontroll/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘rcontroll’ version ‘0.1.0’ +* package encoding: UTF-8 +* checking package namespace information ... 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 ‘rcontroll’ can be installed ... ERROR +Installation failed. +See ‘/tmp/workdir/rcontroll/old/rcontroll.Rcheck/00install.out’ for details. +* DONE +Status: 1 ERROR + + + + + +``` +# rcssci + +
+ +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/rcssci +* Number of recursive dependencies: 136 + +Run `revdepcheck::cloud_details(, "rcssci")` for more info + +
+ +## Error before installation + +### Devel + +``` + + + + + + +``` +### CRAN + +``` + + + + + + +``` +# RCzechia + +
+ +* Version: 1.11.1 +* GitHub: https://github.com/jlacko/RCzechia +* Source code: https://github.com/cran/RCzechia +* Date/Publication: 2023-03-05 06:40:07 UTC +* Number of recursive dependencies: 139 + +Run `revdepcheck::cloud_details(, "RCzechia")` for more info
@@ -3169,7 +11290,25 @@ Run `revdepcheck::cloud_details(, "forceR")` for more info ### Devel ``` +* using log directory ‘/tmp/workdir/RCzechia/new/RCzechia.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘RCzechia/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘RCzechia’ version ‘1.11.1’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘sf’ +Package suggested but not available for checking: ‘lwgeom’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR @@ -3178,25 +11317,43 @@ Run `revdepcheck::cloud_details(, "forceR")` for more info ``` ### CRAN -``` +``` +* using log directory ‘/tmp/workdir/RCzechia/old/RCzechia.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘RCzechia/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘RCzechia’ version ‘1.11.1’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘sf’ + +Package suggested but not available for checking: ‘lwgeom’ +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR ``` -# FSelectorRcpp +# rdss
-* Version: 0.3.8 -* GitHub: https://github.com/mi2-warsaw/FSelectorRcpp -* Source code: https://github.com/cran/FSelectorRcpp -* Date/Publication: 2021-01-14 15:00:02 UTC -* Number of recursive dependencies: 157 +* Version: 1.0.0 +* GitHub: NA +* Source code: https://github.com/cran/rdss +* Date/Publication: 2023-01-17 17:40:02 UTC +* Number of recursive dependencies: 207 -Run `revdepcheck::cloud_details(, "FSelectorRcpp")` for more info +Run `revdepcheck::cloud_details(, "rdss")` for more info
@@ -3205,27 +11362,27 @@ Run `revdepcheck::cloud_details(, "FSelectorRcpp")` for more info ### Devel ``` -* using log directory ‘/tmp/workdir/FSelectorRcpp/new/FSelectorRcpp.Rcheck’ +* using log directory ‘/tmp/workdir/rdss/new/rdss.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘FSelectorRcpp/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘FSelectorRcpp’ version ‘0.3.8’ +* checking for file ‘rdss/DESCRIPTION’ ... OK +* this is package ‘rdss’ version ‘1.0.0’ * package encoding: UTF-8 * checking package namespace information ... OK +* checking package dependencies ... NOTE ... +* 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’ -* checking for unstated dependencies in vignettes ... OK -* checking package vignettes in ‘inst/doc’ ... OK -* checking running R code from vignettes ... NONE - ‘benchmarks_discretize.Rmd’ using ‘UTF-8’... OK - ‘get_started.Rmd’ using ‘UTF-8’... OK - ‘integer-variables.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK * DONE -Status: 3 NOTEs +Status: 1 NOTE @@ -3235,44 +11392,44 @@ Status: 3 NOTEs ### CRAN ``` -* using log directory ‘/tmp/workdir/FSelectorRcpp/old/FSelectorRcpp.Rcheck’ +* using log directory ‘/tmp/workdir/rdss/old/rdss.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘FSelectorRcpp/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘FSelectorRcpp’ version ‘0.3.8’ +* checking for file ‘rdss/DESCRIPTION’ ... OK +* this is package ‘rdss’ version ‘1.0.0’ * package encoding: UTF-8 * checking package namespace information ... OK +* checking package dependencies ... NOTE ... +* 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’ -* checking for unstated dependencies in vignettes ... OK -* checking package vignettes in ‘inst/doc’ ... OK -* checking running R code from vignettes ... NONE - ‘benchmarks_discretize.Rmd’ using ‘UTF-8’... OK - ‘get_started.Rmd’ using ‘UTF-8’... OK - ‘integer-variables.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK * DONE -Status: 3 NOTEs +Status: 1 NOTE ``` -# genekitr +# redist
-* Version: 1.1.3 -* GitHub: https://github.com/GangLiLab/genekitr -* Source code: https://github.com/cran/genekitr -* Date/Publication: 2023-03-01 09:00:02 UTC -* Number of recursive dependencies: 206 +* Version: 4.0.1 +* GitHub: https://github.com/alarm-redist/redist +* Source code: https://github.com/cran/redist +* Date/Publication: 2022-06-16 06:20:07 UTC +* Number of recursive dependencies: 147 -Run `revdepcheck::cloud_details(, "genekitr")` for more info +Run `revdepcheck::cloud_details(, "redist")` for more info
@@ -3281,18 +11438,19 @@ Run `revdepcheck::cloud_details(, "genekitr")` for more info ### Devel ``` -* using log directory ‘/tmp/workdir/genekitr/new/genekitr.Rcheck’ +* using log directory ‘/tmp/workdir/redist/new/redist.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘genekitr/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘genekitr’ version ‘1.1.3’ +* checking for file ‘redist/DESCRIPTION’ ... OK +* this is package ‘redist’ version ‘4.0.1’ * package encoding: UTF-8 * checking package namespace information ... OK * checking package dependencies ... ERROR -Package required but not available: ‘clusterProfiler’ +Package required but not available: ‘sf’ + +Package suggested but not available for checking: ‘lwgeom’ See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ manual. @@ -3307,18 +11465,19 @@ Status: 1 ERROR ### CRAN ``` -* using log directory ‘/tmp/workdir/genekitr/old/genekitr.Rcheck’ +* using log directory ‘/tmp/workdir/redist/old/redist.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘genekitr/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘genekitr’ version ‘1.1.3’ +* checking for file ‘redist/DESCRIPTION’ ... OK +* this is package ‘redist’ version ‘4.0.1’ * package encoding: UTF-8 * checking package namespace information ... OK * checking package dependencies ... ERROR -Package required but not available: ‘clusterProfiler’ +Package required but not available: ‘sf’ + +Package suggested but not available for checking: ‘lwgeom’ See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ manual. @@ -3330,17 +11489,17 @@ Status: 1 ERROR ``` -# geocmeans +# remap
-* Version: 0.3.3 -* GitHub: https://github.com/JeremyGelb/geocmeans -* Source code: https://github.com/cran/geocmeans -* Date/Publication: 2023-02-07 01:02:31 UTC -* Number of recursive dependencies: 197 +* Version: 0.3.0 +* GitHub: https://github.com/jadonwagstaff/remap +* Source code: https://github.com/cran/remap +* Date/Publication: 2022-08-12 23:10:02 UTC +* Number of recursive dependencies: 67 -Run `revdepcheck::cloud_details(, "geocmeans")` for more info +Run `revdepcheck::cloud_details(, "remap")` for more info
@@ -3349,27 +11508,25 @@ Run `revdepcheck::cloud_details(, "geocmeans")` for more info ### Devel ``` -* using log directory ‘/tmp/workdir/geocmeans/new/geocmeans.Rcheck’ +* using log directory ‘/tmp/workdir/remap/new/remap.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘geocmeans/DESCRIPTION’ ... OK +* checking for file ‘remap/DESCRIPTION’ ... OK * checking extension type ... Package -* this is package ‘geocmeans’ version ‘0.3.3’ +* this is package ‘remap’ version ‘0.3.0’ * package encoding: UTF-8 * checking package namespace information ... OK -... ---- finished re-building ‘rasters.Rmd’ - -SUMMARY: processing the following file failed: - ‘introduction.Rmd’ +* checking package dependencies ... ERROR +Package required but not available: ‘sf’ -Error: Vignette re-building failed. -Execution halted +Package suggested but not available for checking: ‘lwgeom’ +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. * DONE -Status: 2 ERRORs, 1 WARNING, 1 NOTE +Status: 1 ERROR @@ -3379,44 +11536,42 @@ Status: 2 ERRORs, 1 WARNING, 1 NOTE ### CRAN ``` -* using log directory ‘/tmp/workdir/geocmeans/old/geocmeans.Rcheck’ +* using log directory ‘/tmp/workdir/remap/old/remap.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘geocmeans/DESCRIPTION’ ... OK +* checking for file ‘remap/DESCRIPTION’ ... OK * checking extension type ... Package -* this is package ‘geocmeans’ version ‘0.3.3’ +* this is package ‘remap’ version ‘0.3.0’ * package encoding: UTF-8 * checking package namespace information ... OK -... ---- finished re-building ‘rasters.Rmd’ - -SUMMARY: processing the following file failed: - ‘introduction.Rmd’ +* checking package dependencies ... ERROR +Package required but not available: ‘sf’ -Error: Vignette re-building failed. -Execution halted +Package suggested but not available for checking: ‘lwgeom’ +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. * DONE -Status: 2 ERRORs, 1 WARNING, 1 NOTE +Status: 1 ERROR ``` -# ggPMX +# report
-* Version: 1.2.8 -* GitHub: https://github.com/ggPMXdevelopment/ggPMX -* Source code: https://github.com/cran/ggPMX -* Date/Publication: 2022-06-17 23:10:02 UTC -* Number of recursive dependencies: 177 +* Version: 0.5.6 +* GitHub: https://github.com/easystats/report +* Source code: https://github.com/cran/report +* Date/Publication: 2023-02-05 20:42:31 UTC +* Number of recursive dependencies: 156 -Run `revdepcheck::cloud_details(, "ggPMX")` for more info +Run `revdepcheck::cloud_details(, "report")` for more info
@@ -3425,27 +11580,27 @@ Run `revdepcheck::cloud_details(, "ggPMX")` for more info ### Devel ``` -* using log directory ‘/tmp/workdir/ggPMX/new/ggPMX.Rcheck’ +* using log directory ‘/tmp/workdir/report/new/report.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘ggPMX/DESCRIPTION’ ... OK -* this is package ‘ggPMX’ version ‘1.2.8’ +* checking for file ‘report/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘report’ version ‘0.5.6’ * package encoding: UTF-8 * checking package namespace information ... OK -* checking package dependencies ... NOTE ... - [ FAIL 1 | WARN 14 | SKIP 8 | PASS 327 ] - 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 ... NONE - ‘ggPMX-guide.Rmd’ using ‘UTF-8’... OK + ‘cite_packages.Rmd’ using ‘UTF-8’... OK + ‘new_models.Rmd’ using ‘UTF-8’... OK + ‘report.Rmd’ using ‘UTF-8’... OK + ‘report_table.Rmd’ using ‘UTF-8’... OK * checking re-building of vignette outputs ... OK * DONE -Status: 1 ERROR, 2 NOTEs +Status: 1 NOTE @@ -3455,44 +11610,43 @@ Status: 1 ERROR, 2 NOTEs ### CRAN ``` -* using log directory ‘/tmp/workdir/ggPMX/old/ggPMX.Rcheck’ +* using log directory ‘/tmp/workdir/report/old/report.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘ggPMX/DESCRIPTION’ ... OK -* this is package ‘ggPMX’ version ‘1.2.8’ +* checking for file ‘report/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘report’ version ‘0.5.6’ * package encoding: UTF-8 * checking package namespace information ... OK -* checking package dependencies ... NOTE ... - [ FAIL 1 | WARN 14 | SKIP 8 | PASS 327 ] - 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 ... NONE - ‘ggPMX-guide.Rmd’ using ‘UTF-8’... OK + ‘cite_packages.Rmd’ using ‘UTF-8’... OK + ‘new_models.Rmd’ using ‘UTF-8’... OK + ‘report.Rmd’ using ‘UTF-8’... OK + ‘report_table.Rmd’ using ‘UTF-8’... OK * checking re-building of vignette outputs ... OK * DONE -Status: 1 ERROR, 2 NOTEs +Status: 1 NOTE ``` -# ggstatsplot +# RevGadgets
-* Version: 0.11.0 -* GitHub: https://github.com/IndrajeetPatil/ggstatsplot -* Source code: https://github.com/cran/ggstatsplot -* Date/Publication: 2023-02-15 15:30:02 UTC -* Number of recursive dependencies: 169 +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/RevGadgets +* Number of recursive dependencies: 125 -Run `revdepcheck::cloud_details(, "ggstatsplot")` for more info +Run `revdepcheck::cloud_details(, "RevGadgets")` for more info
@@ -3501,27 +11655,7 @@ Run `revdepcheck::cloud_details(, "ggstatsplot")` for more info ### Devel ``` -* using log directory ‘/tmp/workdir/ggstatsplot/new/ggstatsplot.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘ggstatsplot/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘ggstatsplot’ version ‘0.11.0’ -* package encoding: UTF-8 -* checking package namespace information ... 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 - ‘additional.Rmd’ using ‘UTF-8’... OK - ‘ggstatsplot.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: 1 NOTE + @@ -3531,44 +11665,24 @@ Status: 1 NOTE ### CRAN ``` -* using log directory ‘/tmp/workdir/ggstatsplot/old/ggstatsplot.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘ggstatsplot/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘ggstatsplot’ version ‘0.11.0’ -* package encoding: UTF-8 -* checking package namespace information ... 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 - ‘additional.Rmd’ using ‘UTF-8’... OK - ‘ggstatsplot.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: 1 NOTE + ``` -# healthyR.ai +# rGhanaCensus
-* Version: 0.0.12 -* GitHub: https://github.com/spsanderson/healthyR.ai -* Source code: https://github.com/cran/healthyR.ai -* Date/Publication: 2023-02-01 18:40:06 UTC -* Number of recursive dependencies: 189 +* Version: 0.1.0 +* GitHub: https://github.com/ktemadarko/rGhanaCensus +* Source code: https://github.com/cran/rGhanaCensus +* Date/Publication: 2022-01-13 20:02:43 UTC +* Number of recursive dependencies: 94 -Run `revdepcheck::cloud_details(, "healthyR.ai")` for more info +Run `revdepcheck::cloud_details(, "rGhanaCensus")` for more info
@@ -3577,27 +11691,27 @@ Run `revdepcheck::cloud_details(, "healthyR.ai")` for more info ### Devel ``` -* using log directory ‘/tmp/workdir/healthyR.ai/new/healthyR.ai.Rcheck’ +* using log directory ‘/tmp/workdir/rGhanaCensus/new/rGhanaCensus.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘healthyR.ai/DESCRIPTION’ ... OK -* this is package ‘healthyR.ai’ version ‘0.0.12’ +* checking for file ‘rGhanaCensus/DESCRIPTION’ ... OK +* this is package ‘rGhanaCensus’ version ‘0.1.0’ * package encoding: UTF-8 * checking package namespace information ... OK -* checking package dependencies ... OK +* checking package dependencies ... NOTE ... -* checking examples ... OK -* checking for unstated dependencies in vignettes ... OK -* checking package vignettes in ‘inst/doc’ ... OK -* checking running R code from vignettes ... NONE - ‘auto-kmeans.Rmd’ using ‘UTF-8’... OK - ‘getting-started.Rmd’ using ‘UTF-8’... OK - ‘kmeans-umap.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK +--- failed re-building ‘Create_map_displaying_Ghana_2019_School_Attendance_Indicators.Rmd’ + +SUMMARY: processing the following file failed: + ‘Create_map_displaying_Ghana_2019_School_Attendance_Indicators.Rmd’ + +Error: Vignette re-building failed. +Execution halted + * DONE -Status: OK +Status: 1 WARNING, 1 NOTE @@ -3607,44 +11721,44 @@ Status: OK ### CRAN ``` -* using log directory ‘/tmp/workdir/healthyR.ai/old/healthyR.ai.Rcheck’ +* using log directory ‘/tmp/workdir/rGhanaCensus/old/rGhanaCensus.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘healthyR.ai/DESCRIPTION’ ... OK -* this is package ‘healthyR.ai’ version ‘0.0.12’ +* checking for file ‘rGhanaCensus/DESCRIPTION’ ... OK +* this is package ‘rGhanaCensus’ version ‘0.1.0’ * package encoding: UTF-8 * checking package namespace information ... OK -* checking package dependencies ... OK +* checking package dependencies ... NOTE ... -* checking examples ... OK -* checking for unstated dependencies in vignettes ... OK -* checking package vignettes in ‘inst/doc’ ... OK -* checking running R code from vignettes ... NONE - ‘auto-kmeans.Rmd’ using ‘UTF-8’... OK - ‘getting-started.Rmd’ using ‘UTF-8’... OK - ‘kmeans-umap.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK +--- failed re-building ‘Create_map_displaying_Ghana_2019_School_Attendance_Indicators.Rmd’ + +SUMMARY: processing the following file failed: + ‘Create_map_displaying_Ghana_2019_School_Attendance_Indicators.Rmd’ + +Error: Vignette re-building failed. +Execution halted + * DONE -Status: OK +Status: 1 WARNING, 1 NOTE ``` -# healthyR.ts +# rnaturalearth
-* Version: 0.2.7 -* GitHub: https://github.com/spsanderson/healthyR.ts -* Source code: https://github.com/cran/healthyR.ts -* Date/Publication: 2023-01-28 14:50:02 UTC -* Number of recursive dependencies: 191 +* Version: 0.3.2 +* GitHub: https://github.com/ropensci/rnaturalearth +* Source code: https://github.com/cran/rnaturalearth +* Date/Publication: 2023-01-23 07:50:02 UTC +* Number of recursive dependencies: 157 -Run `revdepcheck::cloud_details(, "healthyR.ts")` for more info +Run `revdepcheck::cloud_details(, "rnaturalearth")` for more info
@@ -3653,27 +11767,22 @@ Run `revdepcheck::cloud_details(, "healthyR.ts")` for more info ### Devel ``` -* using log directory ‘/tmp/workdir/healthyR.ts/new/healthyR.ts.Rcheck’ +* using log directory ‘/tmp/workdir/rnaturalearth/new/rnaturalearth.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘healthyR.ts/DESCRIPTION’ ... OK -* this is package ‘healthyR.ts’ version ‘0.2.7’ +* checking for file ‘rnaturalearth/DESCRIPTION’ ... OK +* this is package ‘rnaturalearth’ version ‘0.3.2’ * package encoding: UTF-8 * checking package namespace information ... OK -* checking package dependencies ... 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 - ‘using-tidy-fft.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘sf’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. * DONE -Status: 1 NOTE +Status: 1 ERROR @@ -3683,44 +11792,39 @@ Status: 1 NOTE ### CRAN ``` -* using log directory ‘/tmp/workdir/healthyR.ts/old/healthyR.ts.Rcheck’ +* using log directory ‘/tmp/workdir/rnaturalearth/old/rnaturalearth.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘healthyR.ts/DESCRIPTION’ ... OK -* this is package ‘healthyR.ts’ version ‘0.2.7’ +* checking for file ‘rnaturalearth/DESCRIPTION’ ... OK +* this is package ‘rnaturalearth’ version ‘0.3.2’ * package encoding: UTF-8 * checking package namespace information ... OK -* checking package dependencies ... 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 - ‘using-tidy-fft.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘sf’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. * DONE -Status: 1 NOTE +Status: 1 ERROR ``` -# healthyverse +# roads
-* Version: 1.0.3 -* GitHub: https://github.com/spsanderson/healthyverse -* Source code: https://github.com/cran/healthyverse -* Date/Publication: 2023-02-21 20:40:02 UTC -* Number of recursive dependencies: 207 +* Version: 1.1.0 +* GitHub: https://github.com/LandSciTech/roads +* Source code: https://github.com/cran/roads +* Date/Publication: 2023-02-02 16:10:02 UTC +* Number of recursive dependencies: 111 -Run `revdepcheck::cloud_details(, "healthyverse")` for more info +Run `revdepcheck::cloud_details(, "roads")` for more info
@@ -3729,27 +11833,22 @@ Run `revdepcheck::cloud_details(, "healthyverse")` for more info ### Devel ``` -* using log directory ‘/tmp/workdir/healthyverse/new/healthyverse.Rcheck’ +* using log directory ‘/tmp/workdir/roads/new/roads.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘healthyverse/DESCRIPTION’ ... OK -* this is package ‘healthyverse’ version ‘1.0.3’ +* checking for file ‘roads/DESCRIPTION’ ... OK +* this is package ‘roads’ version ‘1.1.0’ * package encoding: UTF-8 * checking package namespace information ... OK -* checking package dependencies ... 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 package dependencies ... ERROR +Package required but not available: ‘sf’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. * DONE -Status: 1 NOTE +Status: 1 ERROR @@ -3759,44 +11858,39 @@ Status: 1 NOTE ### CRAN ``` -* using log directory ‘/tmp/workdir/healthyverse/old/healthyverse.Rcheck’ +* using log directory ‘/tmp/workdir/roads/old/roads.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘healthyverse/DESCRIPTION’ ... OK -* this is package ‘healthyverse’ version ‘1.0.3’ +* checking for file ‘roads/DESCRIPTION’ ... OK +* this is package ‘roads’ version ‘1.1.0’ * package encoding: UTF-8 * checking package namespace information ... OK -* checking package dependencies ... 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 package dependencies ... ERROR +Package required but not available: ‘sf’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. * DONE -Status: 1 NOTE +Status: 1 ERROR ``` -# historicalborrowlong +# Robyn
-* Version: 0.0.5 -* GitHub: https://github.com/wlandau/historicalborrowlong -* Source code: https://github.com/cran/historicalborrowlong -* Date/Publication: 2022-09-13 10:20:06 UTC -* Number of recursive dependencies: 107 +* Version: 3.9.0 +* GitHub: https://github.com/facebookexperimental/Robyn +* Source code: https://github.com/cran/Robyn +* Date/Publication: 2023-02-08 08:12:37 UTC +* Number of recursive dependencies: 139 -Run `revdepcheck::cloud_details(, "historicalborrowlong")` for more info +Run `revdepcheck::cloud_details(, "Robyn")` for more info
@@ -3805,17 +11899,18 @@ Run `revdepcheck::cloud_details(, "historicalborrowlong")` for more info ### Devel ``` -* using log directory ‘/tmp/workdir/historicalborrowlong/new/historicalborrowlong.Rcheck’ +* using log directory ‘/tmp/workdir/Robyn/new/Robyn.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘historicalborrowlong/DESCRIPTION’ ... OK -* this is package ‘historicalborrowlong’ version ‘0.0.5’ +* checking for file ‘Robyn/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘Robyn’ version ‘3.9.0’ * package encoding: UTF-8 * checking package namespace information ... OK * checking package dependencies ... ERROR -Packages required but not available: 'rstan', 'trialr' +Package required but not available: ‘prophet’ See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ manual. @@ -3830,17 +11925,18 @@ Status: 1 ERROR ### CRAN ``` -* using log directory ‘/tmp/workdir/historicalborrowlong/old/historicalborrowlong.Rcheck’ +* using log directory ‘/tmp/workdir/Robyn/old/Robyn.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘historicalborrowlong/DESCRIPTION’ ... OK -* this is package ‘historicalborrowlong’ version ‘0.0.5’ +* checking for file ‘Robyn/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘Robyn’ version ‘3.9.0’ * package encoding: UTF-8 * checking package namespace information ... OK * checking package dependencies ... ERROR -Packages required but not available: 'rstan', 'trialr' +Package required but not available: ‘prophet’ See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ manual. @@ -3852,17 +11948,17 @@ Status: 1 ERROR ``` -# immcp +# Rsagacmd
-* Version: 1.0.3 -* GitHub: https://github.com/YuanlongHu/immcp -* Source code: https://github.com/cran/immcp -* Date/Publication: 2022-05-12 05:50:02 UTC -* Number of recursive dependencies: 194 +* Version: 0.2.0 +* GitHub: https://github.com/stevenpawley/Rsagacmd +* Source code: https://github.com/cran/Rsagacmd +* Date/Publication: 2022-04-04 04:10:02 UTC +* Number of recursive dependencies: 70 -Run `revdepcheck::cloud_details(, "immcp")` for more info +Run `revdepcheck::cloud_details(, "Rsagacmd")` for more info
@@ -3871,17 +11967,18 @@ Run `revdepcheck::cloud_details(, "immcp")` for more info ### Devel ``` -* using log directory ‘/tmp/workdir/immcp/new/immcp.Rcheck’ +* using log directory ‘/tmp/workdir/Rsagacmd/new/Rsagacmd.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘immcp/DESCRIPTION’ ... OK -* this is package ‘immcp’ version ‘1.0.3’ +* checking for file ‘Rsagacmd/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘Rsagacmd’ version ‘0.2.0’ * package encoding: UTF-8 * checking package namespace information ... OK * checking package dependencies ... ERROR -Package required but not available: ‘clusterProfiler’ +Package required but not available: ‘sf’ See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ manual. @@ -3896,17 +11993,18 @@ Status: 1 ERROR ### CRAN ``` -* using log directory ‘/tmp/workdir/immcp/old/immcp.Rcheck’ +* using log directory ‘/tmp/workdir/Rsagacmd/old/Rsagacmd.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘immcp/DESCRIPTION’ ... OK -* this is package ‘immcp’ version ‘1.0.3’ +* checking for file ‘Rsagacmd/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘Rsagacmd’ version ‘0.2.0’ * package encoding: UTF-8 * checking package namespace information ... OK * checking package dependencies ... ERROR -Package required but not available: ‘clusterProfiler’ +Package required but not available: ‘sf’ See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ manual. @@ -3918,17 +12016,17 @@ Status: 1 ERROR ``` -# ImputeRobust +# rsinaica
-* Version: 1.3-1 -* GitHub: NA -* Source code: https://github.com/cran/ImputeRobust -* Date/Publication: 2018-11-30 12:10:03 UTC -* Number of recursive dependencies: 41 +* Version: 0.6.1 +* GitHub: https://github.com/diegovalle/rsinaica +* Source code: https://github.com/cran/rsinaica +* Date/Publication: 2019-02-04 21:10:03 UTC +* Number of recursive dependencies: 126 -Run `revdepcheck::cloud_details(, "ImputeRobust")` for more info +Run `revdepcheck::cloud_details(, "rsinaica")` for more info
@@ -3937,23 +12035,27 @@ Run `revdepcheck::cloud_details(, "ImputeRobust")` for more info ### Devel ``` -* using log directory ‘/tmp/workdir/ImputeRobust/new/ImputeRobust.Rcheck’ +* using log directory ‘/tmp/workdir/rsinaica/new/rsinaica.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘ImputeRobust/DESCRIPTION’ ... OK +* checking for file ‘rsinaica/DESCRIPTION’ ... OK * checking extension type ... Package -* this is package ‘ImputeRobust’ version ‘1.3-1’ +* this is package ‘rsinaica’ version ‘0.6.1’ * package encoding: UTF-8 * checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘extremevalues’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. +... +* checking data for non-ASCII characters ... NOTE + Note: found 467 marked UTF-8 strings +* 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 ERROR +Status: 1 NOTE @@ -3963,103 +12065,120 @@ Status: 1 ERROR ### CRAN ``` -* using log directory ‘/tmp/workdir/ImputeRobust/old/ImputeRobust.Rcheck’ +* using log directory ‘/tmp/workdir/rsinaica/old/rsinaica.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘ImputeRobust/DESCRIPTION’ ... OK +* checking for file ‘rsinaica/DESCRIPTION’ ... OK * checking extension type ... Package -* this is package ‘ImputeRobust’ version ‘1.3-1’ +* this is package ‘rsinaica’ version ‘0.6.1’ * package encoding: UTF-8 * checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘extremevalues’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. +... +* checking data for non-ASCII characters ... NOTE + Note: found 467 marked UTF-8 strings +* 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 ERROR +Status: 1 NOTE ``` -# INSPECTumours +# rstac
-* Version: 0.1.0 -* GitHub: NA -* Source code: https://github.com/cran/INSPECTumours -* Date/Publication: 2022-05-06 12:10:02 UTC -* Number of recursive dependencies: 175 +* Version: 0.9.2-2 +* GitHub: https://github.com/brazil-data-cube/rstac +* Source code: https://github.com/cran/rstac +* Date/Publication: 2023-02-01 18:00:02 UTC +* Number of recursive dependencies: 115 -Run `revdepcheck::cloud_details(, "INSPECTumours")` for more info +Run `revdepcheck::cloud_details(, "rstac")` for more info
-## In both - -* checking whether package ‘INSPECTumours’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/INSPECTumours/new/INSPECTumours.Rcheck/00install.out’ for details. - ``` - -## Installation +## Error before installation ### Devel ``` -* installing *source* package ‘INSPECTumours’ ... -** package ‘INSPECTumours’ 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 <- imp[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - there is no package called ‘rstan’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +* using log directory ‘/tmp/workdir/rstac/new/rstac.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘rstac/DESCRIPTION’ ... OK +* this is package ‘rstac’ version ‘0.9.2-2’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... NOTE +... +--- failed re-building ‘rstac-03-cql2-mpc.Rmd’ + +SUMMARY: processing the following file failed: + ‘rstac-03-cql2-mpc.Rmd’ + +Error: Vignette re-building failed. Execution halted -ERROR: lazy loading failed for package ‘INSPECTumours’ -* removing ‘/tmp/workdir/INSPECTumours/new/INSPECTumours.Rcheck/INSPECTumours’ + +* DONE +Status: 1 WARNING, 1 NOTE + + + ``` ### CRAN ``` -* installing *source* package ‘INSPECTumours’ ... -** package ‘INSPECTumours’ 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 <- imp[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - there is no package called ‘rstan’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +* using log directory ‘/tmp/workdir/rstac/old/rstac.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘rstac/DESCRIPTION’ ... OK +* this is package ‘rstac’ version ‘0.9.2-2’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... NOTE +... +--- failed re-building ‘rstac-03-cql2-mpc.Rmd’ + +SUMMARY: processing the following file failed: + ‘rstac-03-cql2-mpc.Rmd’ + +Error: Vignette re-building failed. Execution halted -ERROR: lazy loading failed for package ‘INSPECTumours’ -* removing ‘/tmp/workdir/INSPECTumours/old/INSPECTumours.Rcheck/INSPECTumours’ + +* DONE +Status: 1 WARNING, 1 NOTE + + + ``` -# intRinsic +# RVA
-* Version: NA -* GitHub: NA -* Source code: https://github.com/cran/intRinsic -* Number of recursive dependencies: 64 +* Version: 0.0.5 +* GitHub: https://github.com/THERMOSTATS/RVA +* Source code: https://github.com/cran/RVA +* Date/Publication: 2021-11-01 21:40:02 UTC +* Number of recursive dependencies: 208 -Run `revdepcheck::cloud_details(, "intRinsic")` for more info +Run `revdepcheck::cloud_details(, "RVA")` for more info
@@ -4068,7 +12187,22 @@ Run `revdepcheck::cloud_details(, "intRinsic")` for more info ### Devel ``` +* using log directory ‘/tmp/workdir/RVA/new/RVA.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘RVA/DESCRIPTION’ ... OK +* this is package ‘RVA’ version ‘0.0.5’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘clusterProfiler’ +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR @@ -4078,33 +12212,48 @@ Run `revdepcheck::cloud_details(, "intRinsic")` for more info ### CRAN ``` +* using log directory ‘/tmp/workdir/RVA/old/RVA.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘RVA/DESCRIPTION’ ... OK +* this is package ‘RVA’ version ‘0.0.5’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘clusterProfiler’ +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR ``` -# IPDFileCheck +# saeSim
-* Version: 0.7.5 -* GitHub: NA -* Source code: https://github.com/cran/IPDFileCheck -* Date/Publication: 2022-02-01 08:00:10 UTC -* Number of recursive dependencies: 150 +* Version: 0.11.0 +* GitHub: https://github.com/wahani/saeSim +* Source code: https://github.com/cran/saeSim +* Date/Publication: 2022-02-07 16:40:02 UTC +* Number of recursive dependencies: 97 -Run `revdepcheck::cloud_details(, "IPDFileCheck")` for more info +Run `revdepcheck::cloud_details(, "saeSim")` for more info
## In both -* checking whether package ‘IPDFileCheck’ can be installed ... ERROR +* checking whether package ‘saeSim’ can be installed ... ERROR ``` Installation failed. - See ‘/tmp/workdir/IPDFileCheck/new/IPDFileCheck.Rcheck/00install.out’ for details. + See ‘/tmp/workdir/saeSim/new/saeSim.Rcheck/00install.out’ for details. ``` ## Installation @@ -4112,50 +12261,50 @@ Run `revdepcheck::cloud_details(, "IPDFileCheck")` for more info ### Devel ``` -* installing *source* package ‘IPDFileCheck’ ... -** package ‘IPDFileCheck’ successfully unpacked and MD5 sums checked +* installing *source* package ‘saeSim’ ... +** package ‘saeSim’ successfully unpacked and MD5 sums checked ** using staged installation ** R ** inst ** byte-compile and prepare package for lazy loading -Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - there is no package called ‘tibble’ +Error in loadNamespace(i, c(lib.loc, .libPaths()), versionCheck = vI[[i]]) : + there is no package called ‘sf’ Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart Execution halted -ERROR: lazy loading failed for package ‘IPDFileCheck’ -* removing ‘/tmp/workdir/IPDFileCheck/new/IPDFileCheck.Rcheck/IPDFileCheck’ +ERROR: lazy loading failed for package ‘saeSim’ +* removing ‘/tmp/workdir/saeSim/new/saeSim.Rcheck/saeSim’ ``` ### CRAN ``` -* installing *source* package ‘IPDFileCheck’ ... -** package ‘IPDFileCheck’ successfully unpacked and MD5 sums checked +* installing *source* package ‘saeSim’ ... +** package ‘saeSim’ successfully unpacked and MD5 sums checked ** using staged installation ** R ** inst ** byte-compile and prepare package for lazy loading -Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - there is no package called ‘tibble’ +Error in loadNamespace(i, c(lib.loc, .libPaths()), versionCheck = vI[[i]]) : + there is no package called ‘sf’ Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart Execution halted -ERROR: lazy loading failed for package ‘IPDFileCheck’ -* removing ‘/tmp/workdir/IPDFileCheck/old/IPDFileCheck.Rcheck/IPDFileCheck’ +ERROR: lazy loading failed for package ‘saeSim’ +* removing ‘/tmp/workdir/saeSim/old/saeSim.Rcheck/saeSim’ ``` -# IRexamples +# SAMtool
-* Version: 0.0.2 -* GitHub: https://github.com/vinhdizzo/IRexamples -* Source code: https://github.com/cran/IRexamples -* Date/Publication: 2022-08-15 07:10:19 UTC -* Number of recursive dependencies: 184 +* Version: 1.5.1 +* GitHub: https://github.com/Blue-Matter/SAMtool +* Source code: https://github.com/cran/SAMtool +* Date/Publication: 2023-02-08 23:20:02 UTC +* Number of recursive dependencies: 178 -Run `revdepcheck::cloud_details(, "IRexamples")` for more info +Run `revdepcheck::cloud_details(, "SAMtool")` for more info
@@ -4164,22 +12313,27 @@ Run `revdepcheck::cloud_details(, "IRexamples")` for more info ### Devel ``` -* using log directory ‘/tmp/workdir/IRexamples/new/IRexamples.Rcheck’ +* using log directory ‘/tmp/workdir/SAMtool/new/SAMtool.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘IRexamples/DESCRIPTION’ ... OK -* this is package ‘IRexamples’ version ‘0.0.2’ +* checking for file ‘SAMtool/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘SAMtool’ version ‘1.5.1’ * package encoding: UTF-8 * checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘rstanarm’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. +... +* checking line endings in C/C++/Fortran sources/headers ... OK +* checking line endings in Makefiles ... OK +* checking compilation flags in Makevars ... 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 * DONE -Status: 1 ERROR +Status: 2 NOTEs @@ -4189,38 +12343,44 @@ Status: 1 ERROR ### CRAN ``` -* using log directory ‘/tmp/workdir/IRexamples/old/IRexamples.Rcheck’ +* using log directory ‘/tmp/workdir/SAMtool/old/SAMtool.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘IRexamples/DESCRIPTION’ ... OK -* this is package ‘IRexamples’ version ‘0.0.2’ +* checking for file ‘SAMtool/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘SAMtool’ version ‘1.5.1’ * package encoding: UTF-8 * checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘rstanarm’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. +... +* checking line endings in C/C++/Fortran sources/headers ... OK +* checking line endings in Makefiles ... OK +* checking compilation flags in Makevars ... 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 * DONE -Status: 1 ERROR +Status: 2 NOTEs ``` -# irtQ +# sandwichr
-* Version: NA -* GitHub: NA -* Source code: https://github.com/cran/irtQ -* Number of recursive dependencies: 59 +* Version: 1.0.3 +* GitHub: https://github.com/linyuehzzz/sandwich_spatial_interpolator +* Source code: https://github.com/cran/sandwichr +* Date/Publication: 2023-01-09 08:10:05 UTC +* Number of recursive dependencies: 143 -Run `revdepcheck::cloud_details(, "irtQ")` for more info +Run `revdepcheck::cloud_details(, "sandwichr")` for more info
@@ -4229,7 +12389,22 @@ Run `revdepcheck::cloud_details(, "irtQ")` for more info ### Devel ``` +* using log directory ‘/tmp/workdir/sandwichr/new/sandwichr.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘sandwichr/DESCRIPTION’ ... OK +* this is package ‘sandwichr’ version ‘1.0.3’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Packages required but not available: 'sf', 'lwgeom' +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR @@ -4239,23 +12414,38 @@ Run `revdepcheck::cloud_details(, "irtQ")` for more info ### CRAN ``` +* using log directory ‘/tmp/workdir/sandwichr/old/sandwichr.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘sandwichr/DESCRIPTION’ ... OK +* this is package ‘sandwichr’ version ‘1.0.3’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Packages required but not available: 'sf', 'lwgeom' +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR ``` -# IsoCorrectoR +# scGate
* Version: NA * GitHub: NA -* Source code: https://github.com/cran/IsoCorrectoR -* Number of recursive dependencies: 70 +* Source code: https://github.com/cran/scGate +* Number of recursive dependencies: 173 -Run `revdepcheck::cloud_details(, "IsoCorrectoR")` for more info +Run `revdepcheck::cloud_details(, "scGate")` for more info
@@ -4281,16 +12471,17 @@ Run `revdepcheck::cloud_details(, "IsoCorrectoR")` for more info ``` -# journalabbr +# SCpubr
-* Version: NA -* GitHub: NA -* Source code: https://github.com/cran/journalabbr -* Number of recursive dependencies: 72 +* Version: 1.1.2 +* GitHub: https://github.com/enblacar/SCpubr +* Source code: https://github.com/cran/SCpubr +* Date/Publication: 2023-01-18 12:20:02 UTC +* Number of recursive dependencies: 290 -Run `revdepcheck::cloud_details(, "journalabbr")` for more info +Run `revdepcheck::cloud_details(, "SCpubr")` for more info
@@ -4299,7 +12490,27 @@ Run `revdepcheck::cloud_details(, "journalabbr")` for more info ### Devel ``` - +* using log directory ‘/tmp/workdir/SCpubr/new/SCpubr.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘SCpubr/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘SCpubr’ version ‘1.1.2’ +* package encoding: UTF-8 +* checking package namespace information ... 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: 1 WARNING, 2 NOTEs @@ -4309,33 +12520,53 @@ Run `revdepcheck::cloud_details(, "journalabbr")` for more info ### CRAN ``` - +* using log directory ‘/tmp/workdir/SCpubr/old/SCpubr.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘SCpubr/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘SCpubr’ version ‘1.1.2’ +* package encoding: UTF-8 +* checking package namespace information ... 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: 1 WARNING, 2 NOTEs ``` -# l1spectral +# SDGdetector
-* Version: 0.99.6 +* Version: 2.7.1 * GitHub: NA -* Source code: https://github.com/cran/l1spectral -* Date/Publication: 2022-01-26 17:12:46 UTC -* Number of recursive dependencies: 83 +* Source code: https://github.com/cran/SDGdetector +* Date/Publication: 2023-02-22 20:20:06 UTC +* Number of recursive dependencies: 74 -Run `revdepcheck::cloud_details(, "l1spectral")` for more info +Run `revdepcheck::cloud_details(, "SDGdetector")` for more info
## In both -* checking whether package ‘l1spectral’ can be installed ... ERROR +* checking whether package ‘SDGdetector’ can be installed ... ERROR ``` Installation failed. - See ‘/tmp/workdir/l1spectral/new/l1spectral.Rcheck/00install.out’ for details. + See ‘/tmp/workdir/SDGdetector/new/SDGdetector.Rcheck/00install.out’ for details. ``` ## Installation @@ -4343,97 +12574,54 @@ Run `revdepcheck::cloud_details(, "l1spectral")` for more info ### Devel ``` -* installing *source* package ‘l1spectral’ ... -** package ‘l1spectral’ successfully unpacked and MD5 sums checked -** using staged installation -** libs -g++ -std=gnu++14 -I"/opt/R/4.1.1/lib/R/include" -DNDEBUG -I'/opt/R/4.1.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.1.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o -g++ -std=gnu++14 -I"/opt/R/4.1.1/lib/R/include" -DNDEBUG -I'/opt/R/4.1.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.1.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c grahm_schmidtCpp.cpp -o grahm_schmidtCpp.o -g++ -std=gnu++14 -shared -L/opt/R/4.1.1/lib/R/lib -L/usr/local/lib -o l1spectral.so RcppExports.o grahm_schmidtCpp.o -llapack -lblas -lgfortran -lm -lquadmath -L/opt/R/4.1.1/lib/R/lib -lR -installing to /tmp/workdir/l1spectral/new/l1spectral.Rcheck/00LOCK-l1spectral/00new/l1spectral/libs -** 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]]) : - there is no package called ‘pROC’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart -Execution halted -ERROR: lazy loading failed for package ‘l1spectral’ -* removing ‘/tmp/workdir/l1spectral/new/l1spectral.Rcheck/l1spectral’ - - -``` -### CRAN - -``` -* installing *source* package ‘l1spectral’ ... -** package ‘l1spectral’ successfully unpacked and MD5 sums checked +* installing *source* package ‘SDGdetector’ ... +** package ‘SDGdetector’ successfully unpacked and MD5 sums checked ** using staged installation -** libs -g++ -std=gnu++14 -I"/opt/R/4.1.1/lib/R/include" -DNDEBUG -I'/opt/R/4.1.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.1.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o -g++ -std=gnu++14 -I"/opt/R/4.1.1/lib/R/include" -DNDEBUG -I'/opt/R/4.1.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.1.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c grahm_schmidtCpp.cpp -o grahm_schmidtCpp.o -g++ -std=gnu++14 -shared -L/opt/R/4.1.1/lib/R/lib -L/usr/local/lib -o l1spectral.so RcppExports.o grahm_schmidtCpp.o -llapack -lblas -lgfortran -lm -lquadmath -L/opt/R/4.1.1/lib/R/lib -lR -installing to /tmp/workdir/l1spectral/old/l1spectral.Rcheck/00LOCK-l1spectral/00new/l1spectral/libs ** R ** data *** moving datasets to lazyload DB +** inst ** byte-compile and prepare package for lazy loading -Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - there is no package called ‘pROC’ +Error in loadNamespace(i, c(lib.loc, .libPaths()), versionCheck = vI[[i]]) : + there is no package called ‘sf’ Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart Execution halted -ERROR: lazy loading failed for package ‘l1spectral’ -* removing ‘/tmp/workdir/l1spectral/old/l1spectral.Rcheck/l1spectral’ - - -``` -# lifeR - -
- -* Version: NA -* GitHub: NA -* Source code: https://github.com/cran/lifeR -* Number of recursive dependencies: 92 - -Run `revdepcheck::cloud_details(, "lifeR")` for more info - -
- -## Error before installation - -### Devel - -``` - - - - +ERROR: lazy loading failed for package ‘SDGdetector’ +* removing ‘/tmp/workdir/SDGdetector/new/SDGdetector.Rcheck/SDGdetector’ ``` ### CRAN ``` - - - - +* installing *source* package ‘SDGdetector’ ... +** package ‘SDGdetector’ 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 ‘sf’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Execution halted +ERROR: lazy loading failed for package ‘SDGdetector’ +* removing ‘/tmp/workdir/SDGdetector/old/SDGdetector.Rcheck/SDGdetector’ ``` -# loon.ggplot +# SDLfilter
-* Version: 1.3.3 -* GitHub: https://github.com/great-northern-diver/loon.ggplot -* Source code: https://github.com/cran/loon.ggplot -* Date/Publication: 2022-11-12 22:30:02 UTC -* Number of recursive dependencies: 104 +* Version: 2.3.1 +* GitHub: https://github.com/TakahiroShimada/SDLfilter +* Source code: https://github.com/cran/SDLfilter +* Date/Publication: 2023-01-16 08:00:06 UTC +* Number of recursive dependencies: 96 -Run `revdepcheck::cloud_details(, "loon.ggplot")` for more info +Run `revdepcheck::cloud_details(, "SDLfilter")` for more info
@@ -4442,20 +12630,18 @@ Run `revdepcheck::cloud_details(, "loon.ggplot")` for more info ### Devel ``` -* using log directory ‘/tmp/workdir/loon.ggplot/new/loon.ggplot.Rcheck’ +* using log directory ‘/tmp/workdir/SDLfilter/new/SDLfilter.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘loon.ggplot/DESCRIPTION’ ... OK +* checking for file ‘SDLfilter/DESCRIPTION’ ... OK * checking extension type ... Package -* this is package ‘loon.ggplot’ version ‘1.3.3’ +* this is package ‘SDLfilter’ version ‘2.3.1’ * package encoding: UTF-8 * checking package namespace information ... OK * checking package dependencies ... ERROR -Package required but not available: ‘loon’ - -Package suggested but not available for checking: ‘zenplots’ +Package required but not available: ‘sf’ See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ manual. @@ -4470,20 +12656,18 @@ Status: 1 ERROR ### CRAN ``` -* using log directory ‘/tmp/workdir/loon.ggplot/old/loon.ggplot.Rcheck’ +* using log directory ‘/tmp/workdir/SDLfilter/old/SDLfilter.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘loon.ggplot/DESCRIPTION’ ... OK +* checking for file ‘SDLfilter/DESCRIPTION’ ... OK * checking extension type ... Package -* this is package ‘loon.ggplot’ version ‘1.3.3’ +* this is package ‘SDLfilter’ version ‘2.3.1’ * package encoding: UTF-8 * checking package namespace information ... OK * checking package dependencies ... ERROR -Package required but not available: ‘loon’ - -Package suggested but not available for checking: ‘zenplots’ +Package required but not available: ‘sf’ See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ manual. @@ -4495,17 +12679,17 @@ Status: 1 ERROR ``` -# loon.shiny +# sdmApp
-* Version: 1.0.3 -* GitHub: NA -* Source code: https://github.com/cran/loon.shiny -* Date/Publication: 2022-10-08 15:30:02 UTC -* Number of recursive dependencies: 136 +* Version: 0.0.2 +* GitHub: https://github.com/Abson-dev/sdmApp +* Source code: https://github.com/cran/sdmApp +* Date/Publication: 2021-07-07 08:30:02 UTC +* Number of recursive dependencies: 169 -Run `revdepcheck::cloud_details(, "loon.shiny")` for more info +Run `revdepcheck::cloud_details(, "sdmApp")` for more info
@@ -4514,23 +12698,27 @@ Run `revdepcheck::cloud_details(, "loon.shiny")` for more info ### Devel ``` -* using log directory ‘/tmp/workdir/loon.shiny/new/loon.shiny.Rcheck’ +* using log directory ‘/tmp/workdir/sdmApp/new/sdmApp.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘loon.shiny/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘loon.shiny’ version ‘1.0.3’ +* checking for file ‘sdmApp/DESCRIPTION’ ... OK +* this is package ‘sdmApp’ version ‘0.0.2’ * package encoding: UTF-8 * checking package namespace information ... OK -* checking package dependencies ... ERROR -Packages required but not available: 'loon', 'loon.ggplot' - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. +* checking package dependencies ... NOTE +... +* 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 + ‘sdmApp.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK * DONE -Status: 1 ERROR +Status: 2 NOTEs @@ -4540,40 +12728,44 @@ Status: 1 ERROR ### CRAN ``` -* using log directory ‘/tmp/workdir/loon.shiny/old/loon.shiny.Rcheck’ +* using log directory ‘/tmp/workdir/sdmApp/old/sdmApp.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘loon.shiny/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘loon.shiny’ version ‘1.0.3’ +* checking for file ‘sdmApp/DESCRIPTION’ ... OK +* this is package ‘sdmApp’ version ‘0.0.2’ * package encoding: UTF-8 * checking package namespace information ... OK -* checking package dependencies ... ERROR -Packages required but not available: 'loon', 'loon.ggplot' - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. +* checking package dependencies ... NOTE +... +* 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 + ‘sdmApp.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK * DONE -Status: 1 ERROR +Status: 2 NOTEs ``` -# MACP +# sf
-* Version: 0.1.0 -* GitHub: https://github.com/mrbakhsh/MACP -* Source code: https://github.com/cran/MACP -* Date/Publication: 2023-02-28 17:32:30 UTC -* Number of recursive dependencies: 235 +* Version: 1.0-10 +* GitHub: https://github.com/r-spatial/sf +* Source code: https://github.com/cran/sf +* Date/Publication: 2023-03-12 16:10:02 UTC +* Number of recursive dependencies: 157 -Run `revdepcheck::cloud_details(, "MACP")` for more info +Run `revdepcheck::cloud_details(, "sf")` for more info
@@ -4582,27 +12774,27 @@ Run `revdepcheck::cloud_details(, "MACP")` for more info ### Devel ``` -* using log directory ‘/tmp/workdir/MACP/new/MACP.Rcheck’ +* using log directory ‘/tmp/workdir/sf/new/sf.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘MACP/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘MACP’ version ‘0.1.0’ +* checking for file ‘sf/DESCRIPTION’ ... OK +* this is package ‘sf’ version ‘1.0-10’ * package encoding: UTF-8 * checking package namespace information ... OK +* checking package dependencies ... NOTE ... -* 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 - ‘MACP_tutorial.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... 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 ‘sf’ can be installed ... ERROR +Installation failed. +See ‘/tmp/workdir/sf/new/sf.Rcheck/00install.out’ for details. * DONE -Status: 3 NOTEs +Status: 1 ERROR, 1 NOTE @@ -4612,43 +12804,44 @@ Status: 3 NOTEs ### CRAN ``` -* using log directory ‘/tmp/workdir/MACP/old/MACP.Rcheck’ +* using log directory ‘/tmp/workdir/sf/old/sf.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘MACP/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘MACP’ version ‘0.1.0’ +* checking for file ‘sf/DESCRIPTION’ ... OK +* this is package ‘sf’ version ‘1.0-10’ * package encoding: UTF-8 * checking package namespace information ... OK +* checking package dependencies ... NOTE ... -* 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 - ‘MACP_tutorial.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... 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 ‘sf’ can be installed ... ERROR +Installation failed. +See ‘/tmp/workdir/sf/old/sf.Rcheck/00install.out’ for details. * DONE -Status: 3 NOTEs +Status: 1 ERROR, 1 NOTE ``` -# mafs +# sfdep
-* Version: NA -* GitHub: NA -* Source code: https://github.com/cran/mafs -* Number of recursive dependencies: 90 +* Version: 0.2.3 +* GitHub: https://github.com/josiahparry/sfdep +* Source code: https://github.com/cran/sfdep +* Date/Publication: 2023-01-11 06:30:02 UTC +* Number of recursive dependencies: 99 -Run `revdepcheck::cloud_details(, "mafs")` for more info +Run `revdepcheck::cloud_details(, "sfdep")` for more info
@@ -4657,7 +12850,22 @@ Run `revdepcheck::cloud_details(, "mafs")` for more info ### Devel ``` +* using log directory ‘/tmp/workdir/sfdep/new/sfdep.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘sfdep/DESCRIPTION’ ... OK +* this is package ‘sfdep’ version ‘0.2.3’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘sf’ +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR @@ -4667,23 +12875,39 @@ Run `revdepcheck::cloud_details(, "mafs")` for more info ### CRAN ``` +* using log directory ‘/tmp/workdir/sfdep/old/sfdep.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘sfdep/DESCRIPTION’ ... OK +* this is package ‘sfdep’ version ‘0.2.3’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘sf’ +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR ``` -# MantaID +# sfnetworks
-* Version: NA -* GitHub: NA -* Source code: https://github.com/cran/MantaID -* Number of recursive dependencies: 152 +* Version: 0.6.2 +* GitHub: https://github.com/luukvdmeer/sfnetworks +* Source code: https://github.com/cran/sfnetworks +* Date/Publication: 2023-02-26 19:00:02 UTC +* Number of recursive dependencies: 105 -Run `revdepcheck::cloud_details(, "MantaID")` for more info +Run `revdepcheck::cloud_details(, "sfnetworks")` for more info
@@ -4692,7 +12916,22 @@ Run `revdepcheck::cloud_details(, "MantaID")` for more info ### Devel ``` +* using log directory ‘/tmp/workdir/sfnetworks/new/sfnetworks.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘sfnetworks/DESCRIPTION’ ... OK +* this is package ‘sfnetworks’ version ‘0.6.2’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Packages required but not available: 'lwgeom', 'sf' +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR @@ -4702,24 +12941,39 @@ Run `revdepcheck::cloud_details(, "MantaID")` for more info ### CRAN ``` +* using log directory ‘/tmp/workdir/sfnetworks/old/sfnetworks.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘sfnetworks/DESCRIPTION’ ... OK +* this is package ‘sfnetworks’ version ‘0.6.2’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Packages required but not available: 'lwgeom', 'sf' +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR ``` -# marginaleffects +# sftime
-* Version: 0.10.0 -* GitHub: https://github.com/vincentarelbundock/marginaleffects -* Source code: https://github.com/cran/marginaleffects -* Date/Publication: 2023-02-22 09:00:02 UTC -* Number of recursive dependencies: 366 +* Version: 0.2-0 +* GitHub: NA +* Source code: https://github.com/cran/sftime +* Date/Publication: 2022-03-17 08:50:01 UTC +* Number of recursive dependencies: 79 -Run `revdepcheck::cloud_details(, "marginaleffects")` for more info +Run `revdepcheck::cloud_details(, "sftime")` for more info
@@ -4728,27 +12982,23 @@ Run `revdepcheck::cloud_details(, "marginaleffects")` for more info ### Devel ``` -* using log directory ‘/tmp/workdir/marginaleffects/new/marginaleffects.Rcheck’ +* using log directory ‘/tmp/workdir/sftime/new/sftime.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘marginaleffects/DESCRIPTION’ ... OK -* this is package ‘marginaleffects’ version ‘0.10.0’ +* checking for file ‘sftime/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘sftime’ version ‘0.2-0’ * package encoding: UTF-8 * checking package namespace information ... OK -* checking package dependencies ... NOTE -... -* checking Rd \usage sections ... OK -* checking Rd contents ... OK -* checking for unstated dependencies in examples ... OK -* checking examples ... OK -* checking for unstated dependencies in ‘tests’ ... OK -* checking tests ... OK - Running ‘spelling.R’ - Running ‘tinytest.R’ +* checking package dependencies ... ERROR +Package required but not available: ‘sf’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. * DONE -Status: 1 NOTE +Status: 1 ERROR @@ -4758,103 +13008,105 @@ Status: 1 NOTE ### CRAN ``` -* using log directory ‘/tmp/workdir/marginaleffects/old/marginaleffects.Rcheck’ +* using log directory ‘/tmp/workdir/sftime/old/sftime.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘marginaleffects/DESCRIPTION’ ... OK -* this is package ‘marginaleffects’ version ‘0.10.0’ +* checking for file ‘sftime/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘sftime’ version ‘0.2-0’ * package encoding: UTF-8 * checking package namespace information ... OK -* checking package dependencies ... NOTE -... -* checking Rd \usage sections ... OK -* checking Rd contents ... OK -* checking for unstated dependencies in examples ... OK -* checking examples ... OK -* checking for unstated dependencies in ‘tests’ ... OK -* checking tests ... OK - Running ‘spelling.R’ - Running ‘tinytest.R’ +* checking package dependencies ... ERROR +Package required but not available: ‘sf’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. * DONE -Status: 1 NOTE +Status: 1 ERROR ``` -# MazamaCoreUtils +# ShellChron
-* Version: 0.4.13 -* GitHub: https://github.com/MazamaScience/MazamaCoreUtils -* Source code: https://github.com/cran/MazamaCoreUtils -* Date/Publication: 2022-08-24 23:12:34 UTC -* Number of recursive dependencies: 108 +* Version: 0.4.0 +* GitHub: https://github.com/nielsjdewinter/ShellChron +* Source code: https://github.com/cran/ShellChron +* Date/Publication: 2021-07-05 12:40:02 UTC +* Number of recursive dependencies: 118 + +Run `revdepcheck::cloud_details(, "ShellChron")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/ShellChron/new/ShellChron.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘ShellChron/DESCRIPTION’ ... OK +* this is package ‘ShellChron’ version ‘0.4.0’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘rtop’ -Run `revdepcheck::cloud_details(, "MazamaCoreUtils")` for more info +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR -
-## In both -* checking whether package ‘MazamaCoreUtils’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/MazamaCoreUtils/new/MazamaCoreUtils.Rcheck/00install.out’ for details. - ``` -## Installation -### Devel +``` +### CRAN ``` -* installing *source* package ‘MazamaCoreUtils’ ... -** package ‘MazamaCoreUtils’ successfully unpacked and MD5 sums checked -** using staged installation -** R -** inst -** byte-compile and prepare package for lazy loading -Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - there is no package called ‘formatR’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart -Execution halted -ERROR: lazy loading failed for package ‘MazamaCoreUtils’ -* removing ‘/tmp/workdir/MazamaCoreUtils/new/MazamaCoreUtils.Rcheck/MazamaCoreUtils’ +* using log directory ‘/tmp/workdir/ShellChron/old/ShellChron.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘ShellChron/DESCRIPTION’ ... OK +* this is package ‘ShellChron’ version ‘0.4.0’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘rtop’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR -``` -### CRAN -``` -* installing *source* package ‘MazamaCoreUtils’ ... -** package ‘MazamaCoreUtils’ successfully unpacked and MD5 sums checked -** using staged installation -** R -** inst -** byte-compile and prepare package for lazy loading -Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - there is no package called ‘formatR’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart -Execution halted -ERROR: lazy loading failed for package ‘MazamaCoreUtils’ -* removing ‘/tmp/workdir/MazamaCoreUtils/old/MazamaCoreUtils.Rcheck/MazamaCoreUtils’ ``` -# mbRes +# shinyHugePlot
* Version: NA * GitHub: NA -* Source code: https://github.com/cran/mbRes -* Number of recursive dependencies: 40 +* Source code: https://github.com/cran/shinyHugePlot +* Number of recursive dependencies: 97 -Run `revdepcheck::cloud_details(, "mbRes")` for more info +Run `revdepcheck::cloud_details(, "shinyHugePlot")` for more info
@@ -4880,17 +13132,17 @@ Run `revdepcheck::cloud_details(, "mbRes")` for more info ``` -# merTools +# simodels
-* Version: 0.5.2 -* GitHub: NA -* Source code: https://github.com/cran/merTools -* Date/Publication: 2020-06-23 10:30:12 UTC -* Number of recursive dependencies: 143 +* Version: 0.0.5 +* GitHub: https://github.com/robinlovelace/simodels +* Source code: https://github.com/cran/simodels +* Date/Publication: 2022-08-31 21:10:02 UTC +* Number of recursive dependencies: 97 -Run `revdepcheck::cloud_details(, "merTools")` for more info +Run `revdepcheck::cloud_details(, "simodels")` for more info
@@ -4899,27 +13151,22 @@ Run `revdepcheck::cloud_details(, "merTools")` for more info ### Devel ``` -* using log directory ‘/tmp/workdir/merTools/new/merTools.Rcheck’ +* using log directory ‘/tmp/workdir/simodels/new/simodels.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘merTools/DESCRIPTION’ ... OK -* this is package ‘merTools’ version ‘0.5.2’ +* checking for file ‘simodels/DESCRIPTION’ ... OK +* this is package ‘simodels’ version ‘0.0.5’ * package encoding: UTF-8 * checking package namespace information ... OK -* checking package dependencies ... NOTE -... -* checking for unstated dependencies in vignettes ... OK -* checking package vignettes in ‘inst/doc’ ... OK -* checking running R code from vignettes ... NONE - ‘Using_predictInterval.Rmd’ using ‘UTF-8’... OK - ‘imputation.Rmd’ using ‘UTF-8’... OK - ‘marginal_effects.Rmd’ using ‘UTF-8’... OK - ‘merToolsIntro.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘sf’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. * DONE -Status: 1 NOTE +Status: 1 ERROR @@ -4929,43 +13176,39 @@ Status: 1 NOTE ### CRAN ``` -* using log directory ‘/tmp/workdir/merTools/old/merTools.Rcheck’ +* using log directory ‘/tmp/workdir/simodels/old/simodels.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘merTools/DESCRIPTION’ ... OK -* this is package ‘merTools’ version ‘0.5.2’ +* checking for file ‘simodels/DESCRIPTION’ ... OK +* this is package ‘simodels’ version ‘0.0.5’ * package encoding: UTF-8 * checking package namespace information ... OK -* checking package dependencies ... NOTE -... -* checking for unstated dependencies in vignettes ... OK -* checking package vignettes in ‘inst/doc’ ... OK -* checking running R code from vignettes ... NONE - ‘Using_predictInterval.Rmd’ using ‘UTF-8’... OK - ‘imputation.Rmd’ using ‘UTF-8’... OK - ‘marginal_effects.Rmd’ using ‘UTF-8’... OK - ‘merToolsIntro.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘sf’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. * DONE -Status: 1 NOTE +Status: 1 ERROR ``` -# microservices +# simplevis
-* Version: NA -* GitHub: NA -* Source code: https://github.com/cran/microservices -* Number of recursive dependencies: 70 +* Version: 7.0.0 +* GitHub: https://github.com/StatisticsNZ/simplevis +* Source code: https://github.com/cran/simplevis +* Date/Publication: 2023-01-29 20:00:02 UTC +* Number of recursive dependencies: 122 -Run `revdepcheck::cloud_details(, "microservices")` for more info +Run `revdepcheck::cloud_details(, "simplevis")` for more info
@@ -4974,7 +13217,23 @@ Run `revdepcheck::cloud_details(, "microservices")` for more info ### Devel ``` +* using log directory ‘/tmp/workdir/simplevis/new/simplevis.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘simplevis/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘simplevis’ version ‘7.0.0’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘sf’ +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR @@ -4984,24 +13243,40 @@ Run `revdepcheck::cloud_details(, "microservices")` for more info ### CRAN ``` +* using log directory ‘/tmp/workdir/simplevis/old/simplevis.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘simplevis/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘simplevis’ version ‘7.0.0’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘sf’ +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR ``` -# modeltime +# sits
-* Version: 1.2.5 -* GitHub: https://github.com/business-science/modeltime -* Source code: https://github.com/cran/modeltime -* Date/Publication: 2023-02-07 19:32:30 UTC -* Number of recursive dependencies: 253 +* Version: 1.2.0 +* GitHub: https://github.com/e-sensing/sits +* Source code: https://github.com/cran/sits +* Date/Publication: 2022-11-16 19:20:07 UTC +* Number of recursive dependencies: 204 -Run `revdepcheck::cloud_details(, "modeltime")` for more info +Run `revdepcheck::cloud_details(, "sits")` for more info
@@ -5010,19 +13285,18 @@ Run `revdepcheck::cloud_details(, "modeltime")` for more info ### Devel ``` -* using log directory ‘/tmp/workdir/modeltime/new/modeltime.Rcheck’ +* using log directory ‘/tmp/workdir/sits/new/sits.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘modeltime/DESCRIPTION’ ... OK -* this is package ‘modeltime’ version ‘1.2.5’ +* checking for file ‘sits/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘sits’ version ‘1.2.0’ * package encoding: UTF-8 * checking package namespace information ... OK * checking package dependencies ... ERROR -Package required but not available: ‘prophet’ - -Package suggested but not available for checking: ‘rstan’ +Package required but not available: ‘sf’ See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ manual. @@ -5037,19 +13311,18 @@ Status: 1 ERROR ### CRAN ``` -* using log directory ‘/tmp/workdir/modeltime/old/modeltime.Rcheck’ +* using log directory ‘/tmp/workdir/sits/old/sits.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘modeltime/DESCRIPTION’ ... OK -* this is package ‘modeltime’ version ‘1.2.5’ +* checking for file ‘sits/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘sits’ version ‘1.2.0’ * package encoding: UTF-8 * checking package namespace information ... OK * checking package dependencies ... ERROR -Package required but not available: ‘prophet’ - -Package suggested but not available for checking: ‘rstan’ +Package required but not available: ‘sf’ See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ manual. @@ -5061,17 +13334,17 @@ Status: 1 ERROR ``` -# modeltime.ensemble +# sjPlot
-* Version: 1.0.2 -* GitHub: https://github.com/business-science/modeltime.ensemble -* Source code: https://github.com/cran/modeltime.ensemble -* Date/Publication: 2022-10-18 23:02:40 UTC -* Number of recursive dependencies: 223 +* Version: 2.8.13 +* GitHub: https://github.com/strengejacke/sjPlot +* Source code: https://github.com/cran/sjPlot +* Date/Publication: 2023-03-13 17:10:10 UTC +* Number of recursive dependencies: 186 -Run `revdepcheck::cloud_details(, "modeltime.ensemble")` for more info +Run `revdepcheck::cloud_details(, "sjPlot")` for more info
@@ -5080,27 +13353,27 @@ Run `revdepcheck::cloud_details(, "modeltime.ensemble")` for more info ### Devel ``` -* using log directory ‘/tmp/workdir/modeltime.ensemble/new/modeltime.ensemble.Rcheck’ +* using log directory ‘/tmp/workdir/sjPlot/new/sjPlot.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘modeltime.ensemble/DESCRIPTION’ ... OK +* checking for file ‘sjPlot/DESCRIPTION’ ... OK * checking extension type ... Package -* this is package ‘modeltime.ensemble’ version ‘1.0.2’ +* this is package ‘sjPlot’ version ‘2.8.13’ * package encoding: UTF-8 * checking package namespace information ... OK ... ---- finished re-building ‘recursive-ensembles.Rmd’ - -SUMMARY: processing the following file failed: - ‘getting-started-with-modeltime-ensemble.Rmd’ - -Error: Vignette re-building failed. -Execution halted - + ‘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 +* checking re-building of vignette outputs ... OK * DONE -Status: 1 ERROR, 1 WARNING, 1 NOTE +Status: 1 NOTE @@ -5110,44 +13383,44 @@ Status: 1 ERROR, 1 WARNING, 1 NOTE ### CRAN ``` -* using log directory ‘/tmp/workdir/modeltime.ensemble/old/modeltime.ensemble.Rcheck’ +* using log directory ‘/tmp/workdir/sjPlot/old/sjPlot.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘modeltime.ensemble/DESCRIPTION’ ... OK +* checking for file ‘sjPlot/DESCRIPTION’ ... OK * checking extension type ... Package -* this is package ‘modeltime.ensemble’ version ‘1.0.2’ +* this is package ‘sjPlot’ version ‘2.8.13’ * package encoding: UTF-8 * checking package namespace information ... OK ... ---- finished re-building ‘recursive-ensembles.Rmd’ - -SUMMARY: processing the following file failed: - ‘getting-started-with-modeltime-ensemble.Rmd’ - -Error: Vignette re-building failed. -Execution halted - + ‘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 +* checking re-building of vignette outputs ... OK * DONE -Status: 1 ERROR, 1 WARNING, 1 NOTE +Status: 1 NOTE ``` -# modeltime.gluonts +# sjstats
-* Version: 0.1.0 -* GitHub: https://github.com/business-science/modeltime.gluonts -* Source code: https://github.com/cran/modeltime.gluonts -* Date/Publication: 2020-11-30 09:40:02 UTC -* Number of recursive dependencies: 214 +* Version: 0.18.2 +* GitHub: https://github.com/strengejacke/sjstats +* Source code: https://github.com/cran/sjstats +* Date/Publication: 2022-11-19 22:10:02 UTC +* Number of recursive dependencies: 166 -Run `revdepcheck::cloud_details(, "modeltime.gluonts")` for more info +Run `revdepcheck::cloud_details(, "sjstats")` for more info
@@ -5156,27 +13429,27 @@ Run `revdepcheck::cloud_details(, "modeltime.gluonts")` for more info ### Devel ``` -* using log directory ‘/tmp/workdir/modeltime.gluonts/new/modeltime.gluonts.Rcheck’ +* using log directory ‘/tmp/workdir/sjstats/new/sjstats.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘modeltime.gluonts/DESCRIPTION’ ... OK +* checking for file ‘sjstats/DESCRIPTION’ ... OK * checking extension type ... Package -* this is package ‘modeltime.gluonts’ version ‘0.1.0’ +* this is package ‘sjstats’ version ‘0.18.2’ * package encoding: UTF-8 * checking package namespace information ... 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 * 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 - ‘getting-started.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK * DONE -Status: 1 NOTE +Status: 2 NOTEs @@ -5186,44 +13459,44 @@ Status: 1 NOTE ### CRAN ``` -* using log directory ‘/tmp/workdir/modeltime.gluonts/old/modeltime.gluonts.Rcheck’ +* using log directory ‘/tmp/workdir/sjstats/old/sjstats.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘modeltime.gluonts/DESCRIPTION’ ... OK +* checking for file ‘sjstats/DESCRIPTION’ ... OK * checking extension type ... Package -* this is package ‘modeltime.gluonts’ version ‘0.1.0’ +* this is package ‘sjstats’ version ‘0.18.2’ * package encoding: UTF-8 * checking package namespace information ... 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 * 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 - ‘getting-started.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK * DONE -Status: 1 NOTE +Status: 2 NOTEs ``` -# modeltime.h2o +# sknifedatar
-* Version: 0.1.1 -* GitHub: https://github.com/business-science/modeltime.h2o -* Source code: https://github.com/cran/modeltime.h2o -* Date/Publication: 2021-04-05 14:40:03 UTC -* Number of recursive dependencies: 214 +* Version: 0.1.2 +* GitHub: https://github.com/rafzamb/sknifedatar +* Source code: https://github.com/cran/sknifedatar +* Date/Publication: 2021-06-01 08:00:02 UTC +* Number of recursive dependencies: 180 -Run `revdepcheck::cloud_details(, "modeltime.h2o")` for more info +Run `revdepcheck::cloud_details(, "sknifedatar")` for more info
@@ -5232,25 +13505,25 @@ Run `revdepcheck::cloud_details(, "modeltime.h2o")` for more info ### Devel ``` -* using log directory ‘/tmp/workdir/modeltime.h2o/new/modeltime.h2o.Rcheck’ +* using log directory ‘/tmp/workdir/sknifedatar/new/sknifedatar.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘modeltime.h2o/DESCRIPTION’ ... OK -* this is package ‘modeltime.h2o’ version ‘0.1.1’ +* checking for file ‘sknifedatar/DESCRIPTION’ ... OK +* this is package ‘sknifedatar’ version ‘0.1.2’ * package encoding: UTF-8 * checking package namespace information ... OK * checking package dependencies ... 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 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’ + Running ‘spelling.R’ * DONE Status: OK @@ -5262,25 +13535,25 @@ Status: OK ### CRAN ``` -* using log directory ‘/tmp/workdir/modeltime.h2o/old/modeltime.h2o.Rcheck’ +* using log directory ‘/tmp/workdir/sknifedatar/old/sknifedatar.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘modeltime.h2o/DESCRIPTION’ ... OK -* this is package ‘modeltime.h2o’ version ‘0.1.1’ +* checking for file ‘sknifedatar/DESCRIPTION’ ... OK +* this is package ‘sknifedatar’ version ‘0.1.2’ * package encoding: UTF-8 * checking package namespace information ... OK * checking package dependencies ... 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 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’ + Running ‘spelling.R’ * DONE Status: OK @@ -5289,17 +13562,17 @@ Status: OK ``` -# modeltime.resample +# slendr
-* Version: 0.2.2 -* GitHub: https://github.com/business-science/modeltime.resample -* Source code: https://github.com/cran/modeltime.resample -* Date/Publication: 2022-10-18 03:00:06 UTC -* Number of recursive dependencies: 221 +* Version: 0.5.1 +* GitHub: https://github.com/bodkan/slendr +* Source code: https://github.com/cran/slendr +* Date/Publication: 2023-03-09 19:40:02 UTC +* Number of recursive dependencies: 129 -Run `revdepcheck::cloud_details(, "modeltime.resample")` for more info +Run `revdepcheck::cloud_details(, "slendr")` for more info
@@ -5308,27 +13581,22 @@ Run `revdepcheck::cloud_details(, "modeltime.resample")` for more info ### Devel ``` -* using log directory ‘/tmp/workdir/modeltime.resample/new/modeltime.resample.Rcheck’ +* using log directory ‘/tmp/workdir/slendr/new/slendr.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘modeltime.resample/DESCRIPTION’ ... OK -* this is package ‘modeltime.resample’ version ‘0.2.2’ +* checking for file ‘slendr/DESCRIPTION’ ... OK +* this is package ‘slendr’ version ‘0.5.1’ * package encoding: UTF-8 * checking package namespace information ... OK -* checking package dependencies ... OK -... ---- failed re-building ‘panel-data.Rmd’ - -SUMMARY: processing the following file failed: - ‘panel-data.Rmd’ - -Error: Vignette re-building failed. -Execution halted +* checking package dependencies ... ERROR +Package required but not available: ‘sf’ +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. * DONE -Status: 1 ERROR, 1 WARNING, 1 NOTE +Status: 1 ERROR @@ -5338,79 +13606,106 @@ Status: 1 ERROR, 1 WARNING, 1 NOTE ### CRAN ``` -* using log directory ‘/tmp/workdir/modeltime.resample/old/modeltime.resample.Rcheck’ +* using log directory ‘/tmp/workdir/slendr/old/slendr.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘modeltime.resample/DESCRIPTION’ ... OK -* this is package ‘modeltime.resample’ version ‘0.2.2’ +* checking for file ‘slendr/DESCRIPTION’ ... OK +* this is package ‘slendr’ version ‘0.5.1’ * package encoding: UTF-8 * checking package namespace information ... OK -* checking package dependencies ... OK -... ---- failed re-building ‘panel-data.Rmd’ - -SUMMARY: processing the following file failed: - ‘panel-data.Rmd’ - -Error: Vignette re-building failed. -Execution halted +* checking package dependencies ... ERROR +Package required but not available: ‘sf’ +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. * DONE -Status: 1 ERROR, 1 WARNING, 1 NOTE +Status: 1 ERROR ``` -# moexer +# sociome
-* Version: NA -* GitHub: NA -* Source code: https://github.com/cran/moexer -* Number of recursive dependencies: 86 +* Version: 2.1.0 +* GitHub: https://github.com/NikKrieger/sociome +* Source code: https://github.com/cran/sociome +* Date/Publication: 2021-10-21 09:10:01 UTC +* Number of recursive dependencies: 97 -Run `revdepcheck::cloud_details(, "moexer")` for more info +Run `revdepcheck::cloud_details(, "sociome")` for more info
-## Error before installation - -### Devel +## In both -``` +* checking whether package ‘sociome’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/sociome/new/sociome.Rcheck/00install.out’ for details. + ``` +* checking package dependencies ... NOTE + ``` + Package suggested but not available for checking: ‘sf’ + ``` +## Installation +### Devel +``` +* installing *source* package ‘sociome’ ... +** package ‘sociome’ 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 ‘sf’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Execution halted +ERROR: lazy loading failed for package ‘sociome’ +* removing ‘/tmp/workdir/sociome/new/sociome.Rcheck/sociome’ ``` ### CRAN ``` - - - - +* installing *source* package ‘sociome’ ... +** package ‘sociome’ 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 ‘sf’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Execution halted +ERROR: lazy loading failed for package ‘sociome’ +* removing ‘/tmp/workdir/sociome/old/sociome.Rcheck/sociome’ ``` -# mpower +# SpaDES.tools
-* Version: 0.1.0 -* GitHub: NA -* Source code: https://github.com/cran/mpower -* Date/Publication: 2022-09-21 08:50:05 UTC -* Number of recursive dependencies: 132 +* Version: 1.0.1 +* GitHub: https://github.com/PredictiveEcology/SpaDES.tools +* Source code: https://github.com/cran/SpaDES.tools +* Date/Publication: 2023-01-05 15:20:19 UTC +* Number of recursive dependencies: 117 -Run `revdepcheck::cloud_details(, "mpower")` for more info +Run `revdepcheck::cloud_details(, "SpaDES.tools")` for more info
@@ -5419,25 +13714,25 @@ Run `revdepcheck::cloud_details(, "mpower")` for more info ### Devel ``` -* using log directory ‘/tmp/workdir/mpower/new/mpower.Rcheck’ +* using log directory ‘/tmp/workdir/SpaDES.tools/new/SpaDES.tools.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘mpower/DESCRIPTION’ ... OK +* checking for file ‘SpaDES.tools/DESCRIPTION’ ... OK * checking extension type ... Package -* this is package ‘mpower’ version ‘0.1.0’ +* this is package ‘SpaDES.tools’ version ‘1.0.1’ * package encoding: UTF-8 * checking package namespace information ... 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 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 * checking for unstated dependencies in ‘tests’ ... OK * checking tests ... OK - Running ‘testthat.R’ + Running ‘test-all.R’ * DONE Status: 1 NOTE @@ -5449,25 +13744,25 @@ Status: 1 NOTE ### CRAN ``` -* using log directory ‘/tmp/workdir/mpower/old/mpower.Rcheck’ +* using log directory ‘/tmp/workdir/SpaDES.tools/old/SpaDES.tools.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘mpower/DESCRIPTION’ ... OK +* checking for file ‘SpaDES.tools/DESCRIPTION’ ... OK * checking extension type ... Package -* this is package ‘mpower’ version ‘0.1.0’ +* this is package ‘SpaDES.tools’ version ‘1.0.1’ * package encoding: UTF-8 * checking package namespace information ... 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 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 * checking for unstated dependencies in ‘tests’ ... OK * checking tests ... OK - Running ‘testthat.R’ + Running ‘test-all.R’ * DONE Status: 1 NOTE @@ -5476,102 +13771,26 @@ Status: 1 NOTE ``` -# multibiasmeta - -
- -* Version: 0.1.0 -* GitHub: https://github.com/mathurlabstanford/multibiasmeta -* Source code: https://github.com/cran/multibiasmeta -* Date/Publication: 2023-02-08 09:40:02 UTC -* Number of recursive dependencies: 99 - -Run `revdepcheck::cloud_details(, "multibiasmeta")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/multibiasmeta/new/multibiasmeta.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘multibiasmeta/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘multibiasmeta’ version ‘0.1.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -... ---- failed re-building ‘tutorial.Rmd’ - -SUMMARY: processing the following file failed: - ‘tutorial.Rmd’ - -Error: Vignette re-building failed. -Execution halted - -* DONE -Status: 1 WARNING, 1 NOTE - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/multibiasmeta/old/multibiasmeta.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘multibiasmeta/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘multibiasmeta’ version ‘0.1.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -... ---- failed re-building ‘tutorial.Rmd’ - -SUMMARY: processing the following file failed: - ‘tutorial.Rmd’ - -Error: Vignette re-building failed. -Execution halted - -* DONE -Status: 1 WARNING, 1 NOTE - - - - - -``` -# NetFACS +# SPARTAAS
-* Version: 0.5.0 +* Version: 1.1.0 * GitHub: NA -* Source code: https://github.com/cran/NetFACS -* Date/Publication: 2022-12-06 17:32:35 UTC -* Number of recursive dependencies: 99 +* Source code: https://github.com/cran/SPARTAAS +* Date/Publication: 2021-10-22 14:30:02 UTC +* Number of recursive dependencies: 184 -Run `revdepcheck::cloud_details(, "NetFACS")` for more info +Run `revdepcheck::cloud_details(, "SPARTAAS")` for more info
## In both -* checking whether package ‘NetFACS’ can be installed ... ERROR +* checking whether package ‘SPARTAAS’ can be installed ... ERROR ``` Installation failed. - See ‘/tmp/workdir/NetFACS/new/NetFACS.Rcheck/00install.out’ for details. + See ‘/tmp/workdir/SPARTAAS/new/SPARTAAS.Rcheck/00install.out’ for details. ``` ## Installation @@ -5579,54 +13798,54 @@ Run `revdepcheck::cloud_details(, "NetFACS")` for more info ### Devel ``` -* installing *source* package ‘NetFACS’ ... -** package ‘NetFACS’ successfully unpacked and MD5 sums checked +* installing *source* package ‘SPARTAAS’ ... +** package ‘SPARTAAS’ 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 ‘R6’ +Error in loadNamespace(i, c(lib.loc, .libPaths()), versionCheck = vI[[i]]) : + there is no package called ‘sf’ Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart Execution halted -ERROR: lazy loading failed for package ‘NetFACS’ -* removing ‘/tmp/workdir/NetFACS/new/NetFACS.Rcheck/NetFACS’ +ERROR: lazy loading failed for package ‘SPARTAAS’ +* removing ‘/tmp/workdir/SPARTAAS/new/SPARTAAS.Rcheck/SPARTAAS’ ``` ### CRAN ``` -* installing *source* package ‘NetFACS’ ... -** package ‘NetFACS’ successfully unpacked and MD5 sums checked +* installing *source* package ‘SPARTAAS’ ... +** package ‘SPARTAAS’ 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 ‘R6’ +Error in loadNamespace(i, c(lib.loc, .libPaths()), versionCheck = vI[[i]]) : + there is no package called ‘sf’ Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart Execution halted -ERROR: lazy loading failed for package ‘NetFACS’ -* removing ‘/tmp/workdir/NetFACS/old/NetFACS.Rcheck/NetFACS’ +ERROR: lazy loading failed for package ‘SPARTAAS’ +* removing ‘/tmp/workdir/SPARTAAS/old/SPARTAAS.Rcheck/SPARTAAS’ ``` -# nlmixr2extra +# spatgeom
-* Version: 2.0.8 -* GitHub: https://github.com/nlmixr2/nlmixr2extra -* Source code: https://github.com/cran/nlmixr2extra -* Date/Publication: 2022-10-22 22:32:34 UTC -* Number of recursive dependencies: 203 +* Version: 0.2.0 +* GitHub: https://github.com/maikol-solis/spatgeom +* Source code: https://github.com/cran/spatgeom +* Date/Publication: 2023-02-14 19:00:02 UTC +* Number of recursive dependencies: 81 -Run `revdepcheck::cloud_details(, "nlmixr2extra")` for more info +Run `revdepcheck::cloud_details(, "spatgeom")` for more info
@@ -5635,17 +13854,18 @@ Run `revdepcheck::cloud_details(, "nlmixr2extra")` for more info ### Devel ``` -* using log directory ‘/tmp/workdir/nlmixr2extra/new/nlmixr2extra.Rcheck’ +* using log directory ‘/tmp/workdir/spatgeom/new/spatgeom.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘nlmixr2extra/DESCRIPTION’ ... OK -* this is package ‘nlmixr2extra’ version ‘2.0.8’ +* checking for file ‘spatgeom/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘spatgeom’ version ‘0.2.0’ * package encoding: UTF-8 * checking package namespace information ... OK * checking package dependencies ... ERROR -Packages required but not available: 'nlmixr2est', 'symengine' +Packages required but not available: 'sf', 'lwgeom' See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ manual. @@ -5660,17 +13880,18 @@ Status: 1 ERROR ### CRAN ``` -* using log directory ‘/tmp/workdir/nlmixr2extra/old/nlmixr2extra.Rcheck’ +* using log directory ‘/tmp/workdir/spatgeom/old/spatgeom.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘nlmixr2extra/DESCRIPTION’ ... OK -* this is package ‘nlmixr2extra’ version ‘2.0.8’ +* checking for file ‘spatgeom/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘spatgeom’ version ‘0.2.0’ * package encoding: UTF-8 * checking package namespace information ... OK * checking package dependencies ... ERROR -Packages required but not available: 'nlmixr2est', 'symengine' +Packages required but not available: 'sf', 'lwgeom' See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ manual. @@ -5682,17 +13903,91 @@ Status: 1 ERROR ``` -# nlmixr2plot +# SpatialEpi
-* Version: 2.0.7 -* GitHub: https://github.com/nlmixr2/nlmixr2plot -* Source code: https://github.com/cran/nlmixr2plot -* Date/Publication: 2022-10-20 03:12:36 UTC -* Number of recursive dependencies: 166 +* Version: 1.2.8 +* GitHub: https://github.com/rudeboybert/SpatialEpi +* Source code: https://github.com/cran/SpatialEpi +* Date/Publication: 2023-02-22 00:50:04 UTC +* Number of recursive dependencies: 86 + +Run `revdepcheck::cloud_details(, "SpatialEpi")` for more info + +
+ +## In both + +* checking whether package ‘SpatialEpi’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/SpatialEpi/new/SpatialEpi.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘SpatialEpi’ ... +** package ‘SpatialEpi’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +g++ -std=gnu++14 -I"/opt/R/4.1.1/lib/R/include" -DNDEBUG -I'/opt/R/4.1.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.1.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +g++ -std=gnu++14 -I"/opt/R/4.1.1/lib/R/include" -DNDEBUG -I'/opt/R/4.1.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.1.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c bayes_cluster.cpp -o bayes_cluster.o +g++ -std=gnu++14 -I"/opt/R/4.1.1/lib/R/include" -DNDEBUG -I'/opt/R/4.1.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.1.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c cluster_detection.cpp -o cluster_detection.o +g++ -std=gnu++14 -shared -L/opt/R/4.1.1/lib/R/lib -L/usr/local/lib -o SpatialEpi.so RcppExports.o bayes_cluster.o cluster_detection.o -L/opt/R/4.1.1/lib/R/lib -lR +installing to /tmp/workdir/SpatialEpi/new/SpatialEpi.Rcheck/00LOCK-SpatialEpi/00new/SpatialEpi/libs +** 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 ‘sf’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Execution halted +ERROR: lazy loading failed for package ‘SpatialEpi’ +* removing ‘/tmp/workdir/SpatialEpi/new/SpatialEpi.Rcheck/SpatialEpi’ + + +``` +### CRAN + +``` +* installing *source* package ‘SpatialEpi’ ... +** package ‘SpatialEpi’ successfully unpacked and MD5 sums checked +** using staged installation +** libs +g++ -std=gnu++14 -I"/opt/R/4.1.1/lib/R/include" -DNDEBUG -I'/opt/R/4.1.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.1.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o +g++ -std=gnu++14 -I"/opt/R/4.1.1/lib/R/include" -DNDEBUG -I'/opt/R/4.1.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.1.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c bayes_cluster.cpp -o bayes_cluster.o +g++ -std=gnu++14 -I"/opt/R/4.1.1/lib/R/include" -DNDEBUG -I'/opt/R/4.1.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.1.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c cluster_detection.cpp -o cluster_detection.o +g++ -std=gnu++14 -shared -L/opt/R/4.1.1/lib/R/lib -L/usr/local/lib -o SpatialEpi.so RcppExports.o bayes_cluster.o cluster_detection.o -L/opt/R/4.1.1/lib/R/lib -lR +installing to /tmp/workdir/SpatialEpi/old/SpatialEpi.Rcheck/00LOCK-SpatialEpi/00new/SpatialEpi/libs +** 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 ‘sf’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Execution halted +ERROR: lazy loading failed for package ‘SpatialEpi’ +* removing ‘/tmp/workdir/SpatialEpi/old/SpatialEpi.Rcheck/SpatialEpi’ -Run `revdepcheck::cloud_details(, "nlmixr2plot")` for more info + +``` +# SpatialKDE + +
+ +* Version: 0.8.2 +* GitHub: https://github.com/JanCaha/SpatialKDE +* Source code: https://github.com/cran/SpatialKDE +* Date/Publication: 2023-02-18 15:10:02 UTC +* Number of recursive dependencies: 112 + +Run `revdepcheck::cloud_details(, "SpatialKDE")` for more info
@@ -5701,17 +13996,18 @@ Run `revdepcheck::cloud_details(, "nlmixr2plot")` for more info ### Devel ``` -* using log directory ‘/tmp/workdir/nlmixr2plot/new/nlmixr2plot.Rcheck’ +* using log directory ‘/tmp/workdir/SpatialKDE/new/SpatialKDE.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘nlmixr2plot/DESCRIPTION’ ... OK -* this is package ‘nlmixr2plot’ version ‘2.0.7’ +* checking for file ‘SpatialKDE/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘SpatialKDE’ version ‘0.8.2’ * package encoding: UTF-8 * checking package namespace information ... OK * checking package dependencies ... ERROR -Packages required but not available: 'nlmixr2est', 'nlmixr2extra' +Package required but not available: ‘sf’ See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ manual. @@ -5726,17 +14022,18 @@ Status: 1 ERROR ### CRAN ``` -* using log directory ‘/tmp/workdir/nlmixr2plot/old/nlmixr2plot.Rcheck’ +* using log directory ‘/tmp/workdir/SpatialKDE/old/SpatialKDE.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘nlmixr2plot/DESCRIPTION’ ... OK -* this is package ‘nlmixr2plot’ version ‘2.0.7’ +* checking for file ‘SpatialKDE/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘SpatialKDE’ version ‘0.8.2’ * package encoding: UTF-8 * checking package namespace information ... OK * checking package dependencies ... ERROR -Packages required but not available: 'nlmixr2est', 'nlmixr2extra' +Package required but not available: ‘sf’ See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ manual. @@ -5748,17 +14045,17 @@ Status: 1 ERROR ``` -# nlmixr2rpt +# spatialrisk
-* Version: 0.1.0 -* GitHub: https://github.com/nlmixr2/nlmixr2rpt -* Source code: https://github.com/cran/nlmixr2rpt -* Date/Publication: 2022-12-05 10:40:02 UTC -* Number of recursive dependencies: 221 +* Version: 0.7.0 +* GitHub: https://github.com/mharinga/spatialrisk +* Source code: https://github.com/cran/spatialrisk +* Date/Publication: 2021-11-10 15:30:02 UTC +* Number of recursive dependencies: 134 -Run `revdepcheck::cloud_details(, "nlmixr2rpt")` for more info +Run `revdepcheck::cloud_details(, "spatialrisk")` for more info
@@ -5767,19 +14064,18 @@ Run `revdepcheck::cloud_details(, "nlmixr2rpt")` for more info ### Devel ``` -* using log directory ‘/tmp/workdir/nlmixr2rpt/new/nlmixr2rpt.Rcheck’ +* using log directory ‘/tmp/workdir/spatialrisk/new/spatialrisk.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘nlmixr2rpt/DESCRIPTION’ ... OK -* this is package ‘nlmixr2rpt’ version ‘0.1.0’ +* checking for file ‘spatialrisk/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘spatialrisk’ version ‘0.7.0’ * package encoding: UTF-8 * checking package namespace information ... OK * checking package dependencies ... ERROR -Packages required but not available: 'nlmixr2extra', 'xpose.nlmixr2' - -Package suggested but not available for checking: ‘nlmixr2’ +Package required but not available: ‘sf’ See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ manual. @@ -5794,19 +14090,18 @@ Status: 1 ERROR ### CRAN ``` -* using log directory ‘/tmp/workdir/nlmixr2rpt/old/nlmixr2rpt.Rcheck’ +* using log directory ‘/tmp/workdir/spatialrisk/old/spatialrisk.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘nlmixr2rpt/DESCRIPTION’ ... OK -* this is package ‘nlmixr2rpt’ version ‘0.1.0’ +* checking for file ‘spatialrisk/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘spatialrisk’ version ‘0.7.0’ * package encoding: UTF-8 * checking package namespace information ... OK * checking package dependencies ... ERROR -Packages required but not available: 'nlmixr2extra', 'xpose.nlmixr2' - -Package suggested but not available for checking: ‘nlmixr2’ +Package required but not available: ‘sf’ See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ manual. @@ -5818,17 +14113,17 @@ Status: 1 ERROR ``` -# numbat +# spatialsample
-* Version: 1.2.2 -* GitHub: https://github.com/kharchenkolab/numbat -* Source code: https://github.com/cran/numbat -* Date/Publication: 2023-02-14 18:20:02 UTC -* Number of recursive dependencies: 132 +* Version: 0.3.0 +* GitHub: https://github.com/tidymodels/spatialsample +* Source code: https://github.com/cran/spatialsample +* Date/Publication: 2023-01-17 16:10:02 UTC +* Number of recursive dependencies: 106 -Run `revdepcheck::cloud_details(, "numbat")` for more info +Run `revdepcheck::cloud_details(, "spatialsample")` for more info
@@ -5837,17 +14132,19 @@ Run `revdepcheck::cloud_details(, "numbat")` for more info ### Devel ``` -* using log directory ‘/tmp/workdir/numbat/new/numbat.Rcheck’ +* using log directory ‘/tmp/workdir/spatialsample/new/spatialsample.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘numbat/DESCRIPTION’ ... OK -* this is package ‘numbat’ version ‘1.2.2’ +* checking for file ‘spatialsample/DESCRIPTION’ ... OK +* this is package ‘spatialsample’ version ‘0.3.0’ * package encoding: UTF-8 * checking package namespace information ... OK * checking package dependencies ... ERROR -Packages required but not available: 'ggtree', 'scistreer' +Package required but not available: ‘sf’ + +Package suggested but not available for checking: ‘lwgeom’ See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ manual. @@ -5862,17 +14159,19 @@ Status: 1 ERROR ### CRAN ``` -* using log directory ‘/tmp/workdir/numbat/old/numbat.Rcheck’ +* using log directory ‘/tmp/workdir/spatialsample/old/spatialsample.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘numbat/DESCRIPTION’ ... OK -* this is package ‘numbat’ version ‘1.2.2’ +* checking for file ‘spatialsample/DESCRIPTION’ ... OK +* this is package ‘spatialsample’ version ‘0.3.0’ * package encoding: UTF-8 * checking package namespace information ... OK * checking package dependencies ... ERROR -Packages required but not available: 'ggtree', 'scistreer' +Package required but not available: ‘sf’ + +Package suggested but not available for checking: ‘lwgeom’ See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ manual. @@ -5884,52 +14183,17 @@ Status: 1 ERROR ``` -# OBL - -
- -* Version: NA -* GitHub: NA -* Source code: https://github.com/cran/OBL -* Number of recursive dependencies: 73 - -Run `revdepcheck::cloud_details(, "OBL")` for more info - -
- -## Error before installation - -### Devel - -``` - - - - - - -``` -### CRAN - -``` - - - - - - -``` -# OlinkAnalyze +# spDates
-* Version: 3.3.1 +* Version: 1.1 * GitHub: NA -* Source code: https://github.com/cran/OlinkAnalyze -* Date/Publication: 2023-02-27 20:22:30 UTC -* Number of recursive dependencies: 202 +* Source code: https://github.com/cran/spDates +* Date/Publication: 2022-10-09 10:30:02 UTC +* Number of recursive dependencies: 82 -Run `revdepcheck::cloud_details(, "OlinkAnalyze")` for more info +Run `revdepcheck::cloud_details(, "spDates")` for more info
@@ -5938,27 +14202,27 @@ Run `revdepcheck::cloud_details(, "OlinkAnalyze")` for more info ### Devel ``` -* using log directory ‘/tmp/workdir/OlinkAnalyze/new/OlinkAnalyze.Rcheck’ +* using log directory ‘/tmp/workdir/spDates/new/spDates.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘OlinkAnalyze/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘OlinkAnalyze’ version ‘3.3.1’ +* checking for file ‘spDates/DESCRIPTION’ ... OK +* this is package ‘spDates’ version ‘1.1’ * package encoding: UTF-8 * checking package namespace information ... OK +* checking package dependencies ... 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 - ‘Vignett.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... 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 ‘spDates’ can be installed ... ERROR +Installation failed. +See ‘/tmp/workdir/spDates/new/spDates.Rcheck/00install.out’ for details. * DONE -Status: 1 NOTE +Status: 1 ERROR @@ -5968,166 +14232,53 @@ Status: 1 NOTE ### CRAN ``` -* using log directory ‘/tmp/workdir/OlinkAnalyze/old/OlinkAnalyze.Rcheck’ +* using log directory ‘/tmp/workdir/spDates/old/spDates.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘OlinkAnalyze/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘OlinkAnalyze’ version ‘3.3.1’ +* checking for file ‘spDates/DESCRIPTION’ ... OK +* this is package ‘spDates’ version ‘1.1’ * package encoding: UTF-8 * checking package namespace information ... OK +* checking package dependencies ... 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 - ‘Vignett.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: 1 NOTE - - - - - -``` -# OncoBayes2 - -
- -* Version: 0.8-8 -* GitHub: NA -* Source code: https://github.com/cran/OncoBayes2 -* Date/Publication: 2023-03-03 22:50:15 UTC -* Number of recursive dependencies: 100 - -Run `revdepcheck::cloud_details(, "OncoBayes2")` for more info - -
- -## In both - -* checking whether package ‘OncoBayes2’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/OncoBayes2/new/OncoBayes2.Rcheck/00install.out’ for details. - ``` - -## Installation - -### Devel - -``` -* installing *source* package ‘OncoBayes2’ ... -** package ‘OncoBayes2’ successfully unpacked and MD5 sums checked -** using staged installation -Info: Found int division at 'string', line 82, column 14 to column 21: - current / base -Values will be rounded towards zero. If rounding is not desired you can write -the division as - current * 1.0 / base -If rounding is intended please use the integer division operator %/%. -Info: Found int division at 'string', line 175, column 14 to column 36: -... -/opt/R/4.1.1/lib/R/site-library/RcppEigen/include/Eigen/src/Core/ProductEvaluators.h:251:23: required from ‘static void Eigen::internal::generic_product_impl::evalTo(Dst&, const Lhs&, const Rhs&) [with Dst = Eigen::Matrix; Lhs = Eigen::Product, const Eigen::CwiseNullaryOp, const Eigen::Matrix >, const Eigen::Transpose > >, Eigen::Matrix, 0>; Rhs = Eigen::Matrix]’ -/opt/R/4.1.1/lib/R/site-library/RcppEigen/include/Eigen/src/Core/ProductEvaluators.h:124:75: required from ‘Eigen::internal::product_evaluator, ProductTag, LhsShape, RhsShape>::product_evaluator(const XprType&) [with Lhs = Eigen::Product, const Eigen::CwiseNullaryOp, const Eigen::Matrix >, const Eigen::Transpose > >, Eigen::Matrix, 0>; Rhs = Eigen::Matrix; int Options = 0; int ProductTag = 6; LhsShape = Eigen::DenseShape; RhsShape = Eigen::DenseShape; typename Eigen::internal::traits::Rhs>::Scalar = double; typename Eigen::internal::traits::Lhs>::Scalar = double; Eigen::internal::product_evaluator, ProductTag, LhsShape, RhsShape>::XprType = Eigen::Product, const Eigen::CwiseNullaryOp, const Eigen::Matrix >, const Eigen::Transpose > >, Eigen::Matrix, 0>, Eigen::Matrix, 0>]’ -/opt/R/4.1.1/lib/R/site-library/RcppEigen/include/Eigen/src/Core/ProductEvaluators.h:35:90: required from ‘Eigen::internal::evaluator >::evaluator(const XprType&) [with Lhs = Eigen::Product, const Eigen::CwiseNullaryOp, const Eigen::Matrix >, const Eigen::Transpose > >, Eigen::Matrix, 0>; Rhs = Eigen::Matrix; int Options = 0; Eigen::internal::evaluator >::XprType = Eigen::Product, const Eigen::CwiseNullaryOp, const Eigen::Matrix >, const Eigen::Transpose > >, Eigen::Matrix, 0>, Eigen::Matrix, 0>]’ -/opt/R/4.1.1/lib/R/site-library/RcppEigen/include/Eigen/src/Core/Product.h:132:22: required from ‘Eigen::internal::dense_product_base::operator const Scalar() const [with Lhs = Eigen::Product, const Eigen::CwiseNullaryOp, const Eigen::Matrix >, const Eigen::Transpose > >, Eigen::Matrix, 0>; Rhs = Eigen::Matrix; int Option = 0; Eigen::internal::dense_product_base::Scalar = double]’ -/opt/R/4.1.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_blrm_exnex_namespace::model_blrm_exnex; BaseRNG = boost::random::additive_combine_engine, boost::random::linear_congruential_engine >]’ -/opt/R/4.1.1/lib/R/site-library/StanHeaders/include/src/stan/mcmc/hmc/hamiltonians/dense_e_metric.hpp:21:10: required from here -/opt/R/4.1.1/lib/R/site-library/RcppEigen/include/Eigen/src/Core/DenseCoeffsBase.h:55:30: warning: ignoring attributes on template argument ‘Eigen::internal::packet_traits::type’ {aka ‘__vector(2) double’} [-Wignored-attributes] -make: *** [/opt/R/4.1.1/lib/R/etc/Makeconf:175: stanExports_blrm_exnex.o] Error 1 -ERROR: compilation failed for package ‘OncoBayes2’ -* removing ‘/tmp/workdir/OncoBayes2/new/OncoBayes2.Rcheck/OncoBayes2’ - - -``` -### CRAN - -``` -* installing *source* package ‘OncoBayes2’ ... -** package ‘OncoBayes2’ successfully unpacked and MD5 sums checked -** using staged installation -Info: Found int division at 'string', line 82, column 14 to column 21: - current / base -Values will be rounded towards zero. If rounding is not desired you can write -the division as - current * 1.0 / base -If rounding is intended please use the integer division operator %/%. -Info: Found int division at 'string', line 175, column 14 to column 36: -... -/opt/R/4.1.1/lib/R/site-library/RcppEigen/include/Eigen/src/Core/ProductEvaluators.h:251:23: required from ‘static void Eigen::internal::generic_product_impl::evalTo(Dst&, const Lhs&, const Rhs&) [with Dst = Eigen::Matrix; Lhs = Eigen::Product, const Eigen::CwiseNullaryOp, const Eigen::Matrix >, const Eigen::Transpose > >, Eigen::Matrix, 0>; Rhs = Eigen::Matrix]’ -/opt/R/4.1.1/lib/R/site-library/RcppEigen/include/Eigen/src/Core/ProductEvaluators.h:124:75: required from ‘Eigen::internal::product_evaluator, ProductTag, LhsShape, RhsShape>::product_evaluator(const XprType&) [with Lhs = Eigen::Product, const Eigen::CwiseNullaryOp, const Eigen::Matrix >, const Eigen::Transpose > >, Eigen::Matrix, 0>; Rhs = Eigen::Matrix; int Options = 0; int ProductTag = 6; LhsShape = Eigen::DenseShape; RhsShape = Eigen::DenseShape; typename Eigen::internal::traits::Rhs>::Scalar = double; typename Eigen::internal::traits::Lhs>::Scalar = double; Eigen::internal::product_evaluator, ProductTag, LhsShape, RhsShape>::XprType = Eigen::Product, const Eigen::CwiseNullaryOp, const Eigen::Matrix >, const Eigen::Transpose > >, Eigen::Matrix, 0>, Eigen::Matrix, 0>]’ -/opt/R/4.1.1/lib/R/site-library/RcppEigen/include/Eigen/src/Core/ProductEvaluators.h:35:90: required from ‘Eigen::internal::evaluator >::evaluator(const XprType&) [with Lhs = Eigen::Product, const Eigen::CwiseNullaryOp, const Eigen::Matrix >, const Eigen::Transpose > >, Eigen::Matrix, 0>; Rhs = Eigen::Matrix; int Options = 0; Eigen::internal::evaluator >::XprType = Eigen::Product, const Eigen::CwiseNullaryOp, const Eigen::Matrix >, const Eigen::Transpose > >, Eigen::Matrix, 0>, Eigen::Matrix, 0>]’ -/opt/R/4.1.1/lib/R/site-library/RcppEigen/include/Eigen/src/Core/Product.h:132:22: required from ‘Eigen::internal::dense_product_base::operator const Scalar() const [with Lhs = Eigen::Product, const Eigen::CwiseNullaryOp, const Eigen::Matrix >, const Eigen::Transpose > >, Eigen::Matrix, 0>; Rhs = Eigen::Matrix; int Option = 0; Eigen::internal::dense_product_base::Scalar = double]’ -/opt/R/4.1.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_blrm_exnex_namespace::model_blrm_exnex; BaseRNG = boost::random::additive_combine_engine, boost::random::linear_congruential_engine >]’ -/opt/R/4.1.1/lib/R/site-library/StanHeaders/include/src/stan/mcmc/hmc/hamiltonians/dense_e_metric.hpp:21:10: required from here -/opt/R/4.1.1/lib/R/site-library/RcppEigen/include/Eigen/src/Core/DenseCoeffsBase.h:55:30: warning: ignoring attributes on template argument ‘Eigen::internal::packet_traits::type’ {aka ‘__vector(2) double’} [-Wignored-attributes] -make: *** [/opt/R/4.1.1/lib/R/etc/Makeconf:175: stanExports_blrm_exnex.o] Error 1 -ERROR: compilation failed for package ‘OncoBayes2’ -* removing ‘/tmp/workdir/OncoBayes2/old/OncoBayes2.Rcheck/OncoBayes2’ - - -``` -# openai - -
- -* Version: NA -* GitHub: NA -* Source code: https://github.com/cran/openai -* Number of recursive dependencies: 43 - -Run `revdepcheck::cloud_details(, "openai")` for more info - -
- -## Error before installation - -### Devel - -``` - - - - - - -``` -### CRAN - -``` - +* 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 ‘spDates’ can be installed ... ERROR +Installation failed. +See ‘/tmp/workdir/spDates/old/spDates.Rcheck/00install.out’ for details. +* DONE +Status: 1 ERROR ``` -# OutliersO3 +# spectacles
-* 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: 133 +* Version: 0.5-3 +* GitHub: https://github.com/pierreroudier/spectacles +* Source code: https://github.com/cran/spectacles +* Date/Publication: 2021-01-11 08:00:02 UTC +* Number of recursive dependencies: 140 -Run `revdepcheck::cloud_details(, "OutliersO3")` for more info +Run `revdepcheck::cloud_details(, "spectacles")` for more info
## In both -* checking whether package ‘OutliersO3’ can be installed ... ERROR +* checking whether package ‘spectacles’ can be installed ... ERROR ``` Installation failed. - See ‘/tmp/workdir/OutliersO3/new/OutliersO3.Rcheck/00install.out’ for details. + See ‘/tmp/workdir/spectacles/new/spectacles.Rcheck/00install.out’ for details. ``` ## Installation @@ -6135,54 +14286,54 @@ Run `revdepcheck::cloud_details(, "OutliersO3")` for more info ### Devel ``` -* installing *source* package ‘OutliersO3’ ... -** package ‘OutliersO3’ successfully unpacked and MD5 sums checked +* installing *source* package ‘spectacles’ ... +** package ‘spectacles’ 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 ‘tidyselect’ +Error in loadNamespace(i, c(lib.loc, .libPaths()), versionCheck = vI[[i]]) : + there is no package called ‘sf’ Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart Execution halted -ERROR: lazy loading failed for package ‘OutliersO3’ -* removing ‘/tmp/workdir/OutliersO3/new/OutliersO3.Rcheck/OutliersO3’ +ERROR: lazy loading failed for package ‘spectacles’ +* removing ‘/tmp/workdir/spectacles/new/spectacles.Rcheck/spectacles’ ``` ### CRAN ``` -* installing *source* package ‘OutliersO3’ ... -** package ‘OutliersO3’ successfully unpacked and MD5 sums checked +* installing *source* package ‘spectacles’ ... +** package ‘spectacles’ 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 ‘tidyselect’ +Error in loadNamespace(i, c(lib.loc, .libPaths()), versionCheck = vI[[i]]) : + there is no package called ‘sf’ Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart Execution halted -ERROR: lazy loading failed for package ‘OutliersO3’ -* removing ‘/tmp/workdir/OutliersO3/old/OutliersO3.Rcheck/OutliersO3’ +ERROR: lazy loading failed for package ‘spectacles’ +* removing ‘/tmp/workdir/spectacles/old/spectacles.Rcheck/spectacles’ ``` -# pathwayTMB +# spnaf
-* Version: 0.1.3 +* Version: 0.2.1 * GitHub: NA -* Source code: https://github.com/cran/pathwayTMB -* Date/Publication: 2022-08-09 13:50:02 UTC -* Number of recursive dependencies: 221 +* Source code: https://github.com/cran/spnaf +* Date/Publication: 2022-08-25 08:20:02 UTC +* Number of recursive dependencies: 100 -Run `revdepcheck::cloud_details(, "pathwayTMB")` for more info +Run `revdepcheck::cloud_details(, "spnaf")` for more info
@@ -6191,18 +14342,18 @@ Run `revdepcheck::cloud_details(, "pathwayTMB")` for more info ### Devel ``` -* using log directory ‘/tmp/workdir/pathwayTMB/new/pathwayTMB.Rcheck’ +* using log directory ‘/tmp/workdir/spnaf/new/spnaf.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘pathwayTMB/DESCRIPTION’ ... OK +* checking for file ‘spnaf/DESCRIPTION’ ... OK * checking extension type ... Package -* this is package ‘pathwayTMB’ version ‘0.1.3’ +* this is package ‘spnaf’ version ‘0.2.1’ * package encoding: UTF-8 * checking package namespace information ... OK * checking package dependencies ... ERROR -Package required but not available: ‘clusterProfiler’ +Package required but not available: ‘sf’ See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ manual. @@ -6217,18 +14368,18 @@ Status: 1 ERROR ### CRAN ``` -* using log directory ‘/tmp/workdir/pathwayTMB/old/pathwayTMB.Rcheck’ +* using log directory ‘/tmp/workdir/spnaf/old/spnaf.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘pathwayTMB/DESCRIPTION’ ... OK +* checking for file ‘spnaf/DESCRIPTION’ ... OK * checking extension type ... Package -* this is package ‘pathwayTMB’ version ‘0.1.3’ +* this is package ‘spnaf’ version ‘0.2.1’ * package encoding: UTF-8 * checking package namespace information ... OK * checking package dependencies ... ERROR -Package required but not available: ‘clusterProfiler’ +Package required but not available: ‘sf’ See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ manual. @@ -6240,16 +14391,17 @@ Status: 1 ERROR ``` -# peramo +# spNetwork
-* Version: NA -* GitHub: NA -* Source code: https://github.com/cran/peramo -* Number of recursive dependencies: 17 +* Version: 0.4.3.6 +* GitHub: https://github.com/JeremyGelb/spNetwork +* Source code: https://github.com/cran/spNetwork +* Date/Publication: 2022-11-11 08:10:02 UTC +* Number of recursive dependencies: 149 -Run `revdepcheck::cloud_details(, "peramo")` for more info +Run `revdepcheck::cloud_details(, "spNetwork")` for more info
@@ -6258,7 +14410,23 @@ Run `revdepcheck::cloud_details(, "peramo")` for more info ### Devel ``` +* using log directory ‘/tmp/workdir/spNetwork/new/spNetwork.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘spNetwork/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘spNetwork’ version ‘0.4.3.6’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘sf’ +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR @@ -6268,24 +14436,40 @@ Run `revdepcheck::cloud_details(, "peramo")` for more info ### CRAN ``` +* using log directory ‘/tmp/workdir/spNetwork/old/spNetwork.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘spNetwork/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘spNetwork’ version ‘0.4.3.6’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘sf’ +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR ``` -# performanceEstimation +# spqdep
-* Version: 1.1.0 -* GitHub: https://github.com/ltorgo/performanceEstimation -* Source code: https://github.com/cran/performanceEstimation -* Date/Publication: 2016-10-13 20:37:05 -* Number of recursive dependencies: 131 +* Version: 0.1.2 +* GitHub: NA +* Source code: https://github.com/cran/spqdep +* Date/Publication: 2022-03-28 16:20:02 UTC +* Number of recursive dependencies: 102 -Run `revdepcheck::cloud_details(, "performanceEstimation")` for more info +Run `revdepcheck::cloud_details(, "spqdep")` for more info
@@ -6294,7 +14478,23 @@ Run `revdepcheck::cloud_details(, "performanceEstimation")` for more info ### Devel ``` +* using log directory ‘/tmp/workdir/spqdep/new/spqdep.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘spqdep/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘spqdep’ version ‘0.1.2’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Packages required but not available: 'sf', 'lwgeom' +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR @@ -6304,84 +14504,182 @@ Run `revdepcheck::cloud_details(, "performanceEstimation")` for more info ### CRAN ``` +* using log directory ‘/tmp/workdir/spqdep/old/spqdep.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘spqdep/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘spqdep’ version ‘0.1.2’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Packages required but not available: 'sf', 'lwgeom' +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR ``` -# planningML +# spup
-* Version: 1.0.0 +* Version: 1.3-2 * GitHub: NA -* Source code: https://github.com/cran/planningML -* Date/Publication: 2022-11-08 10:20:02 UTC -* Number of recursive dependencies: 156 +* Source code: https://github.com/cran/spup +* Date/Publication: 2020-04-30 22:20:06 UTC +* Number of recursive dependencies: 99 -Run `revdepcheck::cloud_details(, "planningML")` for more info +Run `revdepcheck::cloud_details(, "spup")` for more info
-## In both +## Error before installation -* checking whether package ‘planningML’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/planningML/new/planningML.Rcheck/00install.out’ for details. - ``` +### Devel -## Installation +``` +* using log directory ‘/tmp/workdir/spup/new/spup.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘spup/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘spup’ version ‘1.3-2’ +* package encoding: UTF-8 +* checking package namespace information ... OK +... +* checking for unstated dependencies in vignettes ... OK +* checking package vignettes in ‘inst/doc’ ... OK +* checking running R code from vignettes ... NONE + ‘CN_v2.Rmd’ using ‘UTF-8’... OK + ‘DEM_v3.Rmd’ using ‘UTF-8’... OK + ‘ExternalModel_v2.Rmd’ using ‘UTF-8’... OK + ‘Rotterdam.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 1 NOTE + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/spup/old/spup.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘spup/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘spup’ version ‘1.3-2’ +* package encoding: UTF-8 +* checking package namespace information ... OK +... +* checking for unstated dependencies in vignettes ... OK +* checking package vignettes in ‘inst/doc’ ... OK +* checking running R code from vignettes ... NONE + ‘CN_v2.Rmd’ using ‘UTF-8’... OK + ‘DEM_v3.Rmd’ using ‘UTF-8’... OK + ‘ExternalModel_v2.Rmd’ using ‘UTF-8’... OK + ‘Rotterdam.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 1 NOTE + + + + + +``` +# stars + +
+ +* Version: 0.6-0 +* GitHub: https://github.com/r-spatial/stars +* Source code: https://github.com/cran/stars +* Date/Publication: 2022-11-21 13:10:02 UTC +* Number of recursive dependencies: 153 + +Run `revdepcheck::cloud_details(, "stars")` for more info + +
+ +## Error before installation ### Devel ``` -* installing *source* package ‘planningML’ ... -** package ‘planningML’ successfully unpacked and MD5 sums checked -** using staged installation -** R -** inst -** byte-compile and prepare package for lazy loading -Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - there is no package called ‘tidyr’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart -Execution halted -ERROR: lazy loading failed for package ‘planningML’ -* removing ‘/tmp/workdir/planningML/new/planningML.Rcheck/planningML’ +* using log directory ‘/tmp/workdir/stars/new/stars.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘stars/DESCRIPTION’ ... OK +* this is package ‘stars’ version ‘0.6-0’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Packages required but not available: 'sf', 'lwgeom' + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + ``` ### CRAN ``` -* installing *source* package ‘planningML’ ... -** package ‘planningML’ successfully unpacked and MD5 sums checked -** using staged installation -** R -** inst -** byte-compile and prepare package for lazy loading -Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - there is no package called ‘tidyr’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart -Execution halted -ERROR: lazy loading failed for package ‘planningML’ -* removing ‘/tmp/workdir/planningML/old/planningML.Rcheck/planningML’ +* using log directory ‘/tmp/workdir/stars/old/stars.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘stars/DESCRIPTION’ ... OK +* this is package ‘stars’ version ‘0.6-0’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Packages required but not available: 'sf', 'lwgeom' + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + ``` -# Platypus +# starsTileServer
-* Version: 3.4.1 +* Version: 0.1.1 * GitHub: NA -* Source code: https://github.com/cran/Platypus -* Date/Publication: 2022-08-15 07:20:20 UTC -* Number of recursive dependencies: 356 +* Source code: https://github.com/cran/starsTileServer +* Date/Publication: 2022-08-22 21:50:02 UTC +* Number of recursive dependencies: 126 -Run `revdepcheck::cloud_details(, "Platypus")` for more info +Run `revdepcheck::cloud_details(, "starsTileServer")` for more info
@@ -6390,22 +14688,17 @@ Run `revdepcheck::cloud_details(, "Platypus")` for more info ### Devel ``` -* using log directory ‘/tmp/workdir/Platypus/new/Platypus.Rcheck’ +* using log directory ‘/tmp/workdir/starsTileServer/new/starsTileServer.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘Platypus/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘Platypus’ version ‘3.4.1’ +* checking for file ‘starsTileServer/DESCRIPTION’ ... OK +* this is package ‘starsTileServer’ version ‘0.1.1’ * package encoding: UTF-8 * checking package namespace information ... OK -... * checking package dependencies ... ERROR -Package required but not available: ‘ggtree’ - -Packages suggested but not available for checking: - 'Matrix.utils', 'monocle3', 'ProjecTILs', 'SeuratWrappers' +Package required but not available: ‘sf’ See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ manual. @@ -6420,22 +14713,17 @@ Status: 1 ERROR ### CRAN ``` -* using log directory ‘/tmp/workdir/Platypus/old/Platypus.Rcheck’ +* using log directory ‘/tmp/workdir/starsTileServer/old/starsTileServer.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘Platypus/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘Platypus’ version ‘3.4.1’ +* checking for file ‘starsTileServer/DESCRIPTION’ ... OK +* this is package ‘starsTileServer’ version ‘0.1.1’ * package encoding: UTF-8 * checking package namespace information ... OK -... * checking package dependencies ... ERROR -Package required but not available: ‘ggtree’ - -Packages suggested but not available for checking: - 'Matrix.utils', 'monocle3', 'ProjecTILs', 'SeuratWrappers' +Package required but not available: ‘sf’ See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ manual. @@ -6447,16 +14735,17 @@ Status: 1 ERROR ``` -# PLSiMCpp +# stats19
-* Version: NA -* GitHub: NA -* Source code: https://github.com/cran/PLSiMCpp -* Number of recursive dependencies: 10 +* Version: 2.0.1 +* GitHub: https://github.com/ropensci/stats19 +* Source code: https://github.com/cran/stats19 +* Date/Publication: 2022-11-17 12:00:06 UTC +* Number of recursive dependencies: 164 -Run `revdepcheck::cloud_details(, "PLSiMCpp")` for more info +Run `revdepcheck::cloud_details(, "stats19")` for more info
@@ -6465,7 +14754,22 @@ Run `revdepcheck::cloud_details(, "PLSiMCpp")` for more info ### Devel ``` +* using log directory ‘/tmp/workdir/stats19/new/stats19.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘stats19/DESCRIPTION’ ... OK +* this is package ‘stats19’ version ‘2.0.1’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘sf’ +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR @@ -6475,24 +14779,39 @@ Run `revdepcheck::cloud_details(, "PLSiMCpp")` for more info ### CRAN ``` +* using log directory ‘/tmp/workdir/stats19/old/stats19.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘stats19/DESCRIPTION’ ... OK +* this is package ‘stats19’ version ‘2.0.1’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘sf’ +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR ``` -# promotionImpact +# statsExpressions
-* Version: 0.1.5 -* GitHub: https://github.com/ncsoft/promotionImpact -* Source code: https://github.com/cran/promotionImpact -* Date/Publication: 2021-04-13 15:00:05 UTC -* Number of recursive dependencies: 122 +* Version: 1.5.0 +* GitHub: https://github.com/IndrajeetPatil/statsExpressions +* Source code: https://github.com/cran/statsExpressions +* Date/Publication: 2023-02-19 14:30:02 UTC +* Number of recursive dependencies: 152 -Run `revdepcheck::cloud_details(, "promotionImpact")` for more info +Run `revdepcheck::cloud_details(, "statsExpressions")` for more info
@@ -6501,23 +14820,27 @@ Run `revdepcheck::cloud_details(, "promotionImpact")` for more info ### Devel ``` -* using log directory ‘/tmp/workdir/promotionImpact/new/promotionImpact.Rcheck’ +* using log directory ‘/tmp/workdir/statsExpressions/new/statsExpressions.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘promotionImpact/DESCRIPTION’ ... OK +* checking for file ‘statsExpressions/DESCRIPTION’ ... OK * checking extension type ... Package -* this is package ‘promotionImpact’ version ‘0.1.5’ +* this is package ‘statsExpressions’ version ‘1.5.0’ * package encoding: UTF-8 * checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘prophet’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. +... + 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 ... NONE + ‘statsExpressions.Rmd’ using ‘UTF-8’... OK + ‘stats_details.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK * DONE -Status: 1 ERROR +Status: 1 ERROR, 1 NOTE @@ -6527,39 +14850,43 @@ Status: 1 ERROR ### CRAN ``` -* using log directory ‘/tmp/workdir/promotionImpact/old/promotionImpact.Rcheck’ +* using log directory ‘/tmp/workdir/statsExpressions/old/statsExpressions.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘promotionImpact/DESCRIPTION’ ... OK +* checking for file ‘statsExpressions/DESCRIPTION’ ... OK * checking extension type ... Package -* this is package ‘promotionImpact’ version ‘0.1.5’ +* this is package ‘statsExpressions’ version ‘1.5.0’ * package encoding: UTF-8 * checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘prophet’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. +... + 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 ... NONE + ‘statsExpressions.Rmd’ using ‘UTF-8’... OK + ‘stats_details.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK * DONE -Status: 1 ERROR +Status: 1 ERROR, 1 NOTE ``` -# prqlr +# stortingscrape
* Version: NA * GitHub: NA -* Source code: https://github.com/cran/prqlr -* Number of recursive dependencies: 66 +* Source code: https://github.com/cran/stortingscrape +* Number of recursive dependencies: 61 -Run `revdepcheck::cloud_details(, "prqlr")` for more info +Run `revdepcheck::cloud_details(, "stortingscrape")` for more info
@@ -6585,17 +14912,17 @@ Run `revdepcheck::cloud_details(, "prqlr")` for more info ``` -# PsychWordVec +# stplanr
-* Version: 0.3.2 -* GitHub: https://github.com/psychbruce/PsychWordVec -* Source code: https://github.com/cran/PsychWordVec -* Date/Publication: 2023-03-04 16:20:02 UTC -* Number of recursive dependencies: 231 +* Version: 1.0.2 +* GitHub: https://github.com/ropensci/stplanr +* Source code: https://github.com/cran/stplanr +* Date/Publication: 2022-11-08 12:40:02 UTC +* Number of recursive dependencies: 166 -Run `revdepcheck::cloud_details(, "PsychWordVec")` for more info +Run `revdepcheck::cloud_details(, "stplanr")` for more info
@@ -6604,17 +14931,18 @@ Run `revdepcheck::cloud_details(, "PsychWordVec")` for more info ### Devel ``` -* using log directory ‘/tmp/workdir/PsychWordVec/new/PsychWordVec.Rcheck’ +* using log directory ‘/tmp/workdir/stplanr/new/stplanr.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘PsychWordVec/DESCRIPTION’ ... OK -* this is package ‘PsychWordVec’ version ‘0.3.2’ +* checking for file ‘stplanr/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘stplanr’ version ‘1.0.2’ * package encoding: UTF-8 * checking package namespace information ... OK * checking package dependencies ... ERROR -Package required but not available: ‘bruceR’ +Packages required but not available: 'lwgeom', 'sf' See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ manual. @@ -6629,17 +14957,18 @@ Status: 1 ERROR ### CRAN ``` -* using log directory ‘/tmp/workdir/PsychWordVec/old/PsychWordVec.Rcheck’ +* using log directory ‘/tmp/workdir/stplanr/old/stplanr.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘PsychWordVec/DESCRIPTION’ ... OK -* this is package ‘PsychWordVec’ version ‘0.3.2’ +* checking for file ‘stplanr/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘stplanr’ version ‘1.0.2’ * package encoding: UTF-8 * checking package namespace information ... OK * checking package dependencies ... ERROR -Package required but not available: ‘bruceR’ +Packages required but not available: 'lwgeom', 'sf' See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ manual. @@ -6651,17 +14980,17 @@ Status: 1 ERROR ``` -# RBesT +# stppSim
-* Version: 1.6-6 -* GitHub: https://github.com/Novartis/RBesT -* Source code: https://github.com/cran/RBesT -* Date/Publication: 2023-03-03 18:20:02 UTC -* Number of recursive dependencies: 131 +* Version: 1.2.7 +* GitHub: https://github.com/Manalytics/stppSim +* Source code: https://github.com/cran/stppSim +* Date/Publication: 2022-08-11 10:30:02 UTC +* Number of recursive dependencies: 128 -Run `revdepcheck::cloud_details(, "RBesT")` for more info +Run `revdepcheck::cloud_details(, "stppSim")` for more info
@@ -6670,20 +14999,18 @@ Run `revdepcheck::cloud_details(, "RBesT")` for more info ### Devel ``` -* using log directory ‘/tmp/workdir/RBesT/new/RBesT.Rcheck’ +* using log directory ‘/tmp/workdir/stppSim/new/stppSim.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘RBesT/DESCRIPTION’ ... OK +* checking for file ‘stppSim/DESCRIPTION’ ... OK * checking extension type ... Package -* this is package ‘RBesT’ version ‘1.6-6’ +* this is package ‘stppSim’ version ‘1.2.7’ * package encoding: UTF-8 * checking package namespace information ... OK * checking package dependencies ... ERROR -Package required but not available: ‘rstan’ - -Package suggested but not available for checking: ‘rstanarm’ +Package required but not available: ‘sf’ See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ manual. @@ -6698,20 +15025,18 @@ Status: 1 ERROR ### CRAN ``` -* using log directory ‘/tmp/workdir/RBesT/old/RBesT.Rcheck’ +* using log directory ‘/tmp/workdir/stppSim/old/stppSim.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘RBesT/DESCRIPTION’ ... OK +* checking for file ‘stppSim/DESCRIPTION’ ... OK * checking extension type ... Package -* this is package ‘RBesT’ version ‘1.6-6’ +* this is package ‘stppSim’ version ‘1.2.7’ * package encoding: UTF-8 * checking package namespace information ... OK * checking package dependencies ... ERROR -Package required but not available: ‘rstan’ - -Package suggested but not available for checking: ‘rstanarm’ +Package required but not available: ‘sf’ See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ manual. @@ -6723,52 +15048,17 @@ Status: 1 ERROR ``` -# rcssci - -
- -* Version: NA -* GitHub: NA -* Source code: https://github.com/cran/rcssci -* Number of recursive dependencies: 139 - -Run `revdepcheck::cloud_details(, "rcssci")` for more info - -
- -## Error before installation - -### Devel - -``` - - - - - - -``` -### CRAN - -``` - - - - - - -``` -# rdss +# stxplore
-* Version: 1.0.0 +* Version: 0.1.0 * GitHub: NA -* Source code: https://github.com/cran/rdss -* Date/Publication: 2023-01-17 17:40:02 UTC -* Number of recursive dependencies: 207 +* Source code: https://github.com/cran/stxplore +* Date/Publication: 2023-02-03 10:10:02 UTC +* Number of recursive dependencies: 102 -Run `revdepcheck::cloud_details(, "rdss")` for more info +Run `revdepcheck::cloud_details(, "stxplore")` for more info
@@ -6777,27 +15067,27 @@ Run `revdepcheck::cloud_details(, "rdss")` for more info ### Devel ``` -* using log directory ‘/tmp/workdir/rdss/new/rdss.Rcheck’ +* using log directory ‘/tmp/workdir/stxplore/new/stxplore.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘rdss/DESCRIPTION’ ... OK -* this is package ‘rdss’ version ‘1.0.0’ +* checking for file ‘stxplore/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘stxplore’ version ‘0.1.0’ * package encoding: UTF-8 * checking package namespace information ... OK -* checking package dependencies ... NOTE ... -* 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’ +* 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 ‘stxplore’ can be installed ... ERROR +Installation failed. +See ‘/tmp/workdir/stxplore/new/stxplore.Rcheck/00install.out’ for details. * DONE -Status: 1 NOTE +Status: 1 ERROR @@ -6807,44 +15097,44 @@ Status: 1 NOTE ### CRAN ``` -* using log directory ‘/tmp/workdir/rdss/old/rdss.Rcheck’ +* using log directory ‘/tmp/workdir/stxplore/old/stxplore.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘rdss/DESCRIPTION’ ... OK -* this is package ‘rdss’ version ‘1.0.0’ +* checking for file ‘stxplore/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘stxplore’ version ‘0.1.0’ * package encoding: UTF-8 * checking package namespace information ... OK -* checking package dependencies ... NOTE ... -* 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’ +* 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 ‘stxplore’ can be installed ... ERROR +Installation failed. +See ‘/tmp/workdir/stxplore/old/stxplore.Rcheck/00install.out’ for details. * DONE -Status: 1 NOTE +Status: 1 ERROR ``` -# report +# SUNGEO
-* Version: 0.5.6 -* GitHub: https://github.com/easystats/report -* Source code: https://github.com/cran/report -* Date/Publication: 2023-02-05 20:42:31 UTC -* Number of recursive dependencies: 156 +* Version: 0.2.292 +* GitHub: NA +* Source code: https://github.com/cran/SUNGEO +* Date/Publication: 2022-08-18 14:20:02 UTC +* Number of recursive dependencies: 109 -Run `revdepcheck::cloud_details(, "report")` for more info +Run `revdepcheck::cloud_details(, "SUNGEO")` for more info
@@ -6853,82 +15143,23 @@ Run `revdepcheck::cloud_details(, "report")` for more info ### Devel ``` -* using log directory ‘/tmp/workdir/report/new/report.Rcheck’ +* using log directory ‘/tmp/workdir/SUNGEO/new/SUNGEO.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘report/DESCRIPTION’ ... OK +* checking for file ‘SUNGEO/DESCRIPTION’ ... OK * checking extension type ... Package -* this is package ‘report’ version ‘0.5.6’ +* this is package ‘SUNGEO’ version ‘0.2.292’ * package encoding: UTF-8 * checking package namespace information ... OK -... -* checking for unstated dependencies in vignettes ... OK -* checking package vignettes in ‘inst/doc’ ... OK -* checking running R code from vignettes ... NONE - ‘cite_packages.Rmd’ using ‘UTF-8’... OK - ‘new_models.Rmd’ using ‘UTF-8’... OK - ‘report.Rmd’ using ‘UTF-8’... OK - ‘report_table.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: 1 NOTE - - - - - -``` -### CRAN +* checking package dependencies ... ERROR +Package required but not available: ‘sf’ -``` -* using log directory ‘/tmp/workdir/report/old/report.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘report/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘report’ version ‘0.5.6’ -* package encoding: UTF-8 -* checking package namespace information ... OK -... -* checking for unstated dependencies in vignettes ... OK -* checking package vignettes in ‘inst/doc’ ... OK -* checking running R code from vignettes ... NONE - ‘cite_packages.Rmd’ using ‘UTF-8’... OK - ‘new_models.Rmd’ using ‘UTF-8’... OK - ‘report.Rmd’ using ‘UTF-8’... OK - ‘report_table.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. * DONE -Status: 1 NOTE - - - - - -``` -# RevGadgets - -
- -* Version: NA -* GitHub: NA -* Source code: https://github.com/cran/RevGadgets -* Number of recursive dependencies: 125 - -Run `revdepcheck::cloud_details(, "RevGadgets")` for more info - -
- -## Error before installation - -### Devel - -``` - +Status: 1 ERROR @@ -6938,33 +15169,49 @@ Run `revdepcheck::cloud_details(, "RevGadgets")` for more info ### CRAN ``` +* using log directory ‘/tmp/workdir/SUNGEO/old/SUNGEO.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘SUNGEO/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘SUNGEO’ version ‘0.2.292’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘sf’ +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR ``` -# Rigma +# swfscAirDAS
-* Version: 0.2.1 -* GitHub: https://github.com/AleKoure/Rigma -* Source code: https://github.com/cran/Rigma -* Date/Publication: 2022-11-27 22:00:06 UTC -* Number of recursive dependencies: 71 +* Version: 0.2.3 +* GitHub: https://github.com/smwoodman/swfscAirDAS +* Source code: https://github.com/cran/swfscAirDAS +* Date/Publication: 2022-06-02 03:00:02 UTC +* Number of recursive dependencies: 105 -Run `revdepcheck::cloud_details(, "Rigma")` for more info +Run `revdepcheck::cloud_details(, "swfscAirDAS")` for more info
## In both -* checking whether package ‘Rigma’ can be installed ... ERROR +* checking whether package ‘swfscAirDAS’ can be installed ... ERROR ``` Installation failed. - See ‘/tmp/workdir/Rigma/new/Rigma.Rcheck/00install.out’ for details. + See ‘/tmp/workdir/swfscAirDAS/new/swfscAirDAS.Rcheck/00install.out’ for details. ``` ## Installation @@ -6972,50 +15219,50 @@ Run `revdepcheck::cloud_details(, "Rigma")` for more info ### Devel ``` -* installing *source* package ‘Rigma’ ... -** package ‘Rigma’ successfully unpacked and MD5 sums checked +* installing *source* package ‘swfscAirDAS’ ... +** package ‘swfscAirDAS’ 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 ‘sass’ +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + there is no package called ‘sf’ Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart Execution halted -ERROR: lazy loading failed for package ‘Rigma’ -* removing ‘/tmp/workdir/Rigma/new/Rigma.Rcheck/Rigma’ +ERROR: lazy loading failed for package ‘swfscAirDAS’ +* removing ‘/tmp/workdir/swfscAirDAS/new/swfscAirDAS.Rcheck/swfscAirDAS’ ``` ### CRAN ``` -* installing *source* package ‘Rigma’ ... -** package ‘Rigma’ successfully unpacked and MD5 sums checked +* installing *source* package ‘swfscAirDAS’ ... +** package ‘swfscAirDAS’ 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 ‘sass’ +Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : + there is no package called ‘sf’ Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart Execution halted -ERROR: lazy loading failed for package ‘Rigma’ -* removing ‘/tmp/workdir/Rigma/old/Rigma.Rcheck/Rigma’ +ERROR: lazy loading failed for package ‘swfscAirDAS’ +* removing ‘/tmp/workdir/swfscAirDAS/old/swfscAirDAS.Rcheck/swfscAirDAS’ ``` -# Robyn +# SWTools
-* Version: 3.9.0 -* GitHub: https://github.com/facebookexperimental/Robyn -* Source code: https://github.com/cran/Robyn -* Date/Publication: 2023-02-08 08:12:37 UTC -* Number of recursive dependencies: 139 +* Version: 0.2.4 +* GitHub: https://github.com/matt-s-gibbs/swtools +* Source code: https://github.com/cran/SWTools +* Date/Publication: 2022-07-04 06:20:02 UTC +* Number of recursive dependencies: 110 -Run `revdepcheck::cloud_details(, "Robyn")` for more info +Run `revdepcheck::cloud_details(, "SWTools")` for more info
@@ -7024,18 +15271,18 @@ Run `revdepcheck::cloud_details(, "Robyn")` for more info ### Devel ``` -* using log directory ‘/tmp/workdir/Robyn/new/Robyn.Rcheck’ +* using log directory ‘/tmp/workdir/SWTools/new/SWTools.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘Robyn/DESCRIPTION’ ... OK +* checking for file ‘SWTools/DESCRIPTION’ ... OK * checking extension type ... Package -* this is package ‘Robyn’ version ‘3.9.0’ +* this is package ‘SWTools’ version ‘0.2.4’ * package encoding: UTF-8 * checking package namespace information ... OK * checking package dependencies ... ERROR -Package required but not available: ‘prophet’ +Package required but not available: ‘sf’ See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ manual. @@ -7050,18 +15297,18 @@ Status: 1 ERROR ### CRAN ``` -* using log directory ‘/tmp/workdir/Robyn/old/Robyn.Rcheck’ +* using log directory ‘/tmp/workdir/SWTools/old/SWTools.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘Robyn/DESCRIPTION’ ... OK +* checking for file ‘SWTools/DESCRIPTION’ ... OK * checking extension type ... Package -* this is package ‘Robyn’ version ‘3.9.0’ +* this is package ‘SWTools’ version ‘0.2.4’ * package encoding: UTF-8 * checking package namespace information ... OK * checking package dependencies ... ERROR -Package required but not available: ‘prophet’ +Package required but not available: ‘sf’ See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ manual. @@ -7073,17 +15320,16 @@ Status: 1 ERROR ``` -# RVA +# tame
-* Version: 0.0.5 -* GitHub: https://github.com/THERMOSTATS/RVA -* Source code: https://github.com/cran/RVA -* Date/Publication: 2021-11-01 21:40:02 UTC -* Number of recursive dependencies: 208 +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/tame +* Number of recursive dependencies: 65 -Run `revdepcheck::cloud_details(, "RVA")` for more info +Run `revdepcheck::cloud_details(, "tame")` for more info
@@ -7092,17 +15338,54 @@ Run `revdepcheck::cloud_details(, "RVA")` for more info ### Devel ``` -* using log directory ‘/tmp/workdir/RVA/new/RVA.Rcheck’ + + + + + + +``` +### CRAN + +``` + + + + + + +``` +# telemac + +
+ +* Version: 0.1.1 +* GitHub: https://github.com/tpilz/telemac +* Source code: https://github.com/cran/telemac +* Date/Publication: 2022-02-07 15:50:02 UTC +* Number of recursive dependencies: 147 + +Run `revdepcheck::cloud_details(, "telemac")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/telemac/new/telemac.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘RVA/DESCRIPTION’ ... OK -* this is package ‘RVA’ version ‘0.0.5’ +* checking for file ‘telemac/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘telemac’ version ‘0.1.1’ * package encoding: UTF-8 * checking package namespace information ... OK * checking package dependencies ... ERROR -Package required but not available: ‘clusterProfiler’ +Package required but not available: ‘sf’ See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ manual. @@ -7117,17 +15400,18 @@ Status: 1 ERROR ### CRAN ``` -* using log directory ‘/tmp/workdir/RVA/old/RVA.Rcheck’ +* using log directory ‘/tmp/workdir/telemac/old/telemac.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘RVA/DESCRIPTION’ ... OK -* this is package ‘RVA’ version ‘0.0.5’ +* checking for file ‘telemac/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘telemac’ version ‘0.1.1’ * package encoding: UTF-8 * checking package namespace information ... OK * checking package dependencies ... ERROR -Package required but not available: ‘clusterProfiler’ +Package required but not available: ‘sf’ See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ manual. @@ -7139,17 +15423,17 @@ Status: 1 ERROR ``` -# SAMtool +# tidybayes
-* Version: 1.5.1 -* GitHub: https://github.com/Blue-Matter/SAMtool -* Source code: https://github.com/cran/SAMtool -* Date/Publication: 2023-02-08 23:20:02 UTC -* Number of recursive dependencies: 183 +* Version: 3.0.4 +* GitHub: https://github.com/mjskay/tidybayes +* Source code: https://github.com/cran/tidybayes +* Date/Publication: 2023-03-14 04:30:02 UTC +* Number of recursive dependencies: 200 -Run `revdepcheck::cloud_details(, "SAMtool")` for more info +Run `revdepcheck::cloud_details(, "tidybayes")` for more info
@@ -7158,25 +15442,25 @@ Run `revdepcheck::cloud_details(, "SAMtool")` for more info ### Devel ``` -* using log directory ‘/tmp/workdir/SAMtool/new/SAMtool.Rcheck’ +* using log directory ‘/tmp/workdir/tidybayes/new/tidybayes.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘SAMtool/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘SAMtool’ version ‘1.5.1’ +* checking for file ‘tidybayes/DESCRIPTION’ ... OK +* this is package ‘tidybayes’ version ‘3.0.4’ * package encoding: UTF-8 * checking package namespace information ... OK +* checking package dependencies ... NOTE ... -* checking line endings in C/C++/Fortran sources/headers ... OK -* checking line endings in Makefiles ... OK -* checking compilation flags in Makevars ... 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 package vignettes in ‘inst/doc’ ... OK +* checking running R code from vignettes ... NONE + ‘tidy-brms.Rmd’ using ‘UTF-8’... OK + ‘tidy-posterior.Rmd’ using ‘UTF-8’... OK + ‘tidy-rstanarm.Rmd’ using ‘UTF-8’... OK + ‘tidybayes-residuals.Rmd’ using ‘UTF-8’... OK + ‘tidybayes.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK * DONE Status: 2 NOTEs @@ -7188,25 +15472,25 @@ Status: 2 NOTEs ### CRAN ``` -* using log directory ‘/tmp/workdir/SAMtool/old/SAMtool.Rcheck’ +* using log directory ‘/tmp/workdir/tidybayes/old/tidybayes.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘SAMtool/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘SAMtool’ version ‘1.5.1’ +* checking for file ‘tidybayes/DESCRIPTION’ ... OK +* this is package ‘tidybayes’ version ‘3.0.4’ * package encoding: UTF-8 * checking package namespace information ... OK +* checking package dependencies ... NOTE ... -* checking line endings in C/C++/Fortran sources/headers ... OK -* checking line endings in Makefiles ... OK -* checking compilation flags in Makevars ... 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 package vignettes in ‘inst/doc’ ... OK +* checking running R code from vignettes ... NONE + ‘tidy-brms.Rmd’ using ‘UTF-8’... OK + ‘tidy-posterior.Rmd’ using ‘UTF-8’... OK + ‘tidy-rstanarm.Rmd’ using ‘UTF-8’... OK + ‘tidybayes-residuals.Rmd’ using ‘UTF-8’... OK + ‘tidybayes.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK * DONE Status: 2 NOTEs @@ -7215,16 +15499,17 @@ Status: 2 NOTEs ``` -# scGate +# tidyposterior
-* Version: NA -* GitHub: NA -* Source code: https://github.com/cran/scGate -* Number of recursive dependencies: 173 +* Version: 1.0.0 +* GitHub: https://github.com/tidymodels/tidyposterior +* Source code: https://github.com/cran/tidyposterior +* Date/Publication: 2022-06-23 20:20:02 UTC +* Number of recursive dependencies: 170 -Run `revdepcheck::cloud_details(, "scGate")` for more info +Run `revdepcheck::cloud_details(, "tidyposterior")` for more info
@@ -7233,7 +15518,22 @@ Run `revdepcheck::cloud_details(, "scGate")` for more info ### Devel ``` +* using log directory ‘/tmp/workdir/tidyposterior/new/tidyposterior.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘tidyposterior/DESCRIPTION’ ... OK +* this is package ‘tidyposterior’ version ‘1.0.0’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘rstanarm’ +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR @@ -7243,24 +15543,39 @@ Run `revdepcheck::cloud_details(, "scGate")` for more info ### CRAN ``` +* using log directory ‘/tmp/workdir/tidyposterior/old/tidyposterior.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘tidyposterior/DESCRIPTION’ ... OK +* this is package ‘tidyposterior’ version ‘1.0.0’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘rstanarm’ +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR ``` -# SCpubr +# tidySEM
-* Version: 1.1.2 -* GitHub: https://github.com/enblacar/SCpubr -* Source code: https://github.com/cran/SCpubr -* Date/Publication: 2023-01-18 12:20:02 UTC -* Number of recursive dependencies: 290 +* Version: 0.2.3 +* GitHub: https://github.com/cjvanlissa/tidySEM +* Source code: https://github.com/cran/tidySEM +* Date/Publication: 2022-04-14 17:50:02 UTC +* Number of recursive dependencies: 171 -Run `revdepcheck::cloud_details(, "SCpubr")` for more info +Run `revdepcheck::cloud_details(, "tidySEM")` for more info
@@ -7269,27 +15584,25 @@ Run `revdepcheck::cloud_details(, "SCpubr")` for more info ### Devel ``` -* using log directory ‘/tmp/workdir/SCpubr/new/SCpubr.Rcheck’ +* using log directory ‘/tmp/workdir/tidySEM/new/tidySEM.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘SCpubr/DESCRIPTION’ ... OK +* checking for file ‘tidySEM/DESCRIPTION’ ... OK * checking extension type ... Package -* this is package ‘SCpubr’ version ‘1.1.2’ +* this is package ‘tidySEM’ version ‘0.2.3’ * package encoding: UTF-8 * checking package namespace information ... 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 +* checking package dependencies ... ERROR +Package required but not available: ‘blavaan’ + +Package suggested but not available for checking: ‘umx’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. * DONE -Status: 1 WARNING, 2 NOTEs +Status: 1 ERROR @@ -7299,43 +15612,41 @@ Status: 1 WARNING, 2 NOTEs ### CRAN ``` -* using log directory ‘/tmp/workdir/SCpubr/old/SCpubr.Rcheck’ +* using log directory ‘/tmp/workdir/tidySEM/old/tidySEM.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘SCpubr/DESCRIPTION’ ... OK +* checking for file ‘tidySEM/DESCRIPTION’ ... OK * checking extension type ... Package -* this is package ‘SCpubr’ version ‘1.1.2’ +* this is package ‘tidySEM’ version ‘0.2.3’ * package encoding: UTF-8 * checking package namespace information ... 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 +* checking package dependencies ... ERROR +Package required but not available: ‘blavaan’ + +Package suggested but not available for checking: ‘umx’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. * DONE -Status: 1 WARNING, 2 NOTEs +Status: 1 ERROR ``` -# shinyHugePlot +# tidytags
* Version: NA * GitHub: NA -* Source code: https://github.com/cran/shinyHugePlot -* Number of recursive dependencies: 97 +* Source code: https://github.com/cran/tidytags +* Number of recursive dependencies: 122 -Run `revdepcheck::cloud_details(, "shinyHugePlot")` for more info +Run `revdepcheck::cloud_details(, "tidytags")` for more info
@@ -7361,17 +15672,17 @@ Run `revdepcheck::cloud_details(, "shinyHugePlot")` for more info ``` -# sjPlot +# tilemaps
-* Version: 2.8.12 -* GitHub: https://github.com/strengejacke/sjPlot -* Source code: https://github.com/cran/sjPlot -* Date/Publication: 2022-11-19 22:20:02 UTC -* Number of recursive dependencies: 186 +* 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: 73 -Run `revdepcheck::cloud_details(, "sjPlot")` for more info +Run `revdepcheck::cloud_details(, "tilemaps")` for more info
@@ -7380,27 +15691,22 @@ Run `revdepcheck::cloud_details(, "sjPlot")` for more info ### Devel ``` -* using log directory ‘/tmp/workdir/sjPlot/new/sjPlot.Rcheck’ +* using log directory ‘/tmp/workdir/tilemaps/new/tilemaps.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘sjPlot/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘sjPlot’ version ‘2.8.12’ +* checking for file ‘tilemaps/DESCRIPTION’ ... OK +* this is package ‘tilemaps’ version ‘0.2.0’ * package encoding: UTF-8 * checking package namespace information ... 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 -* checking re-building of vignette outputs ... OK +* checking package dependencies ... ERROR +Packages required but not available: 'lwgeom', 'sf' + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. * DONE -Status: 1 NOTE +Status: 1 ERROR @@ -7410,44 +15716,39 @@ Status: 1 NOTE ### CRAN ``` -* using log directory ‘/tmp/workdir/sjPlot/old/sjPlot.Rcheck’ +* using log directory ‘/tmp/workdir/tilemaps/old/tilemaps.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘sjPlot/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘sjPlot’ version ‘2.8.12’ +* checking for file ‘tilemaps/DESCRIPTION’ ... OK +* this is package ‘tilemaps’ version ‘0.2.0’ * package encoding: UTF-8 * checking package namespace information ... 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 -* checking re-building of vignette outputs ... OK +* checking package dependencies ... ERROR +Packages required but not available: 'lwgeom', 'sf' + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. * DONE -Status: 1 NOTE +Status: 1 ERROR ``` -# sknifedatar +# timetk
-* Version: 0.1.2 -* GitHub: https://github.com/rafzamb/sknifedatar -* Source code: https://github.com/cran/sknifedatar -* Date/Publication: 2021-06-01 08:00:02 UTC -* Number of recursive dependencies: 180 +* Version: 2.8.2 +* GitHub: https://github.com/business-science/timetk +* Source code: https://github.com/cran/timetk +* Date/Publication: 2022-11-17 19:30:02 UTC +* Number of recursive dependencies: 226 -Run `revdepcheck::cloud_details(, "sknifedatar")` for more info +Run `revdepcheck::cloud_details(, "timetk")` for more info
@@ -7456,27 +15757,27 @@ Run `revdepcheck::cloud_details(, "sknifedatar")` for more info ### Devel ``` -* using log directory ‘/tmp/workdir/sknifedatar/new/sknifedatar.Rcheck’ +* using log directory ‘/tmp/workdir/timetk/new/timetk.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘sknifedatar/DESCRIPTION’ ... OK -* this is package ‘sknifedatar’ version ‘0.1.2’ +* checking for file ‘timetk/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘timetk’ version ‘2.8.2’ * package encoding: UTF-8 * checking package namespace information ... OK -* checking package dependencies ... 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 ‘spelling.R’ + Error in library(robets) : there is no package called 'robets' + Execution halted +* checking for unstated dependencies in vignettes ... OK +* checking package vignettes in ‘inst/doc’ ... OK +* checking running R code from vignettes ... NONE + ‘TK04_Plotting_Time_Series.Rmd’ using ‘UTF-8’... OK + ‘TK07_Time_Series_Data_Wrangling.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK * DONE -Status: OK +Status: 1 ERROR, 2 NOTEs @@ -7486,44 +15787,44 @@ Status: OK ### CRAN ``` -* using log directory ‘/tmp/workdir/sknifedatar/old/sknifedatar.Rcheck’ +* using log directory ‘/tmp/workdir/timetk/old/timetk.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘sknifedatar/DESCRIPTION’ ... OK -* this is package ‘sknifedatar’ version ‘0.1.2’ +* checking for file ‘timetk/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘timetk’ version ‘2.8.2’ * package encoding: UTF-8 * checking package namespace information ... OK -* checking package dependencies ... 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 ‘spelling.R’ + Error in library(robets) : there is no package called 'robets' + Execution halted +* checking for unstated dependencies in vignettes ... OK +* checking package vignettes in ‘inst/doc’ ... OK +* checking running R code from vignettes ... NONE + ‘TK04_Plotting_Time_Series.Rmd’ using ‘UTF-8’... OK + ‘TK07_Time_Series_Data_Wrangling.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK * DONE -Status: OK +Status: 1 ERROR, 2 NOTEs ``` -# SpaDES.tools +# tinyarray
-* Version: 1.0.1 -* GitHub: https://github.com/PredictiveEcology/SpaDES.tools -* Source code: https://github.com/cran/SpaDES.tools -* Date/Publication: 2023-01-05 15:20:19 UTC -* Number of recursive dependencies: 117 +* Version: 2.2.9 +* GitHub: https://github.com/xjsun1221/tinyarray +* Source code: https://github.com/cran/tinyarray +* Date/Publication: 2023-03-04 07:40:02 UTC +* Number of recursive dependencies: 228 -Run `revdepcheck::cloud_details(, "SpaDES.tools")` for more info +Run `revdepcheck::cloud_details(, "tinyarray")` for more info
@@ -7532,27 +15833,23 @@ Run `revdepcheck::cloud_details(, "SpaDES.tools")` for more info ### Devel ``` -* using log directory ‘/tmp/workdir/SpaDES.tools/new/SpaDES.tools.Rcheck’ +* using log directory ‘/tmp/workdir/tinyarray/new/tinyarray.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘SpaDES.tools/DESCRIPTION’ ... OK +* checking for file ‘tinyarray/DESCRIPTION’ ... OK * checking extension type ... Package -* this is package ‘SpaDES.tools’ version ‘1.0.1’ +* this is package ‘tinyarray’ version ‘2.2.9’ * package encoding: UTF-8 * checking package namespace information ... 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 -* checking for unstated dependencies in ‘tests’ ... OK -* checking tests ... OK - Running ‘test-all.R’ +* checking package dependencies ... ERROR +Package required but not available: ‘clusterProfiler’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. * DONE -Status: 1 NOTE +Status: 1 ERROR @@ -7562,44 +15859,40 @@ Status: 1 NOTE ### CRAN ``` -* using log directory ‘/tmp/workdir/SpaDES.tools/old/SpaDES.tools.Rcheck’ +* using log directory ‘/tmp/workdir/tinyarray/old/tinyarray.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘SpaDES.tools/DESCRIPTION’ ... OK +* checking for file ‘tinyarray/DESCRIPTION’ ... OK * checking extension type ... Package -* this is package ‘SpaDES.tools’ version ‘1.0.1’ +* this is package ‘tinyarray’ version ‘2.2.9’ * package encoding: UTF-8 * checking package namespace information ... 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 -* checking for unstated dependencies in ‘tests’ ... OK -* checking tests ... OK - Running ‘test-all.R’ +* checking package dependencies ... ERROR +Package required but not available: ‘clusterProfiler’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. * DONE -Status: 1 NOTE +Status: 1 ERROR ``` -# statsExpressions +# tipmap
-* Version: 1.5.0 -* GitHub: https://github.com/IndrajeetPatil/statsExpressions -* Source code: https://github.com/cran/statsExpressions -* Date/Publication: 2023-02-19 14:30:02 UTC -* Number of recursive dependencies: 152 +* Version: 0.3.9 +* GitHub: NA +* Source code: https://github.com/cran/tipmap +* Date/Publication: 2022-12-07 21:50:02 UTC +* Number of recursive dependencies: 96 -Run `revdepcheck::cloud_details(, "statsExpressions")` for more info +Run `revdepcheck::cloud_details(, "tipmap")` for more info
@@ -7608,27 +15901,23 @@ Run `revdepcheck::cloud_details(, "statsExpressions")` for more info ### Devel ``` -* using log directory ‘/tmp/workdir/statsExpressions/new/statsExpressions.Rcheck’ +* using log directory ‘/tmp/workdir/tipmap/new/tipmap.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘statsExpressions/DESCRIPTION’ ... OK +* checking for file ‘tipmap/DESCRIPTION’ ... OK * checking extension type ... Package -* this is package ‘statsExpressions’ version ‘1.5.0’ +* this is package ‘tipmap’ version ‘0.3.9’ * package encoding: UTF-8 * checking package namespace information ... OK -... - 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 ... NONE - ‘statsExpressions.Rmd’ using ‘UTF-8’... OK - ‘stats_details.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘RBesT’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. * DONE -Status: 1 ERROR, 1 NOTE +Status: 1 ERROR @@ -7638,43 +15927,40 @@ Status: 1 ERROR, 1 NOTE ### CRAN ``` -* using log directory ‘/tmp/workdir/statsExpressions/old/statsExpressions.Rcheck’ +* using log directory ‘/tmp/workdir/tipmap/old/tipmap.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘statsExpressions/DESCRIPTION’ ... OK +* checking for file ‘tipmap/DESCRIPTION’ ... OK * checking extension type ... Package -* this is package ‘statsExpressions’ version ‘1.5.0’ +* this is package ‘tipmap’ version ‘0.3.9’ * package encoding: UTF-8 * checking package namespace information ... OK -... - 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 ... NONE - ‘statsExpressions.Rmd’ using ‘UTF-8’... OK - ‘stats_details.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘RBesT’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. * DONE -Status: 1 ERROR, 1 NOTE +Status: 1 ERROR ``` -# stortingscrape +# tmap
-* Version: NA -* GitHub: NA -* Source code: https://github.com/cran/stortingscrape -* Number of recursive dependencies: 61 +* Version: 3.3-3 +* GitHub: https://github.com/r-tmap/tmap +* Source code: https://github.com/cran/tmap +* Date/Publication: 2022-03-02 08:50:02 UTC +* Number of recursive dependencies: 158 -Run `revdepcheck::cloud_details(, "stortingscrape")` for more info +Run `revdepcheck::cloud_details(, "tmap")` for more info
@@ -7683,7 +15969,23 @@ Run `revdepcheck::cloud_details(, "stortingscrape")` for more info ### Devel ``` +* using log directory ‘/tmp/workdir/tmap/new/tmap.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘tmap/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘tmap’ version ‘3.3-3’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘sf’ +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR @@ -7693,23 +15995,40 @@ Run `revdepcheck::cloud_details(, "stortingscrape")` for more info ### CRAN ``` +* using log directory ‘/tmp/workdir/tmap/old/tmap.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘tmap/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘tmap’ version ‘3.3-3’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘sf’ +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR ``` -# tame +# trackdf
-* Version: NA -* GitHub: NA -* Source code: https://github.com/cran/tame -* Number of recursive dependencies: 65 +* Version: 0.3.1 +* GitHub: https://github.com/swarm-lab/trackdf +* Source code: https://github.com/cran/trackdf +* Date/Publication: 2023-01-23 00:50:02 UTC +* Number of recursive dependencies: 150 -Run `revdepcheck::cloud_details(, "tame")` for more info +Run `revdepcheck::cloud_details(, "trackdf")` for more info
@@ -7718,7 +16037,25 @@ Run `revdepcheck::cloud_details(, "tame")` for more info ### Devel ``` +* using log directory ‘/tmp/workdir/trackdf/new/trackdf.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘trackdf/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘trackdf’ version ‘0.3.1’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘sf’ +Package suggested but not available for checking: ‘moveVis’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR @@ -7728,24 +16065,42 @@ Run `revdepcheck::cloud_details(, "tame")` for more info ### CRAN ``` +* using log directory ‘/tmp/workdir/trackdf/old/trackdf.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘trackdf/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘trackdf’ version ‘0.3.1’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘sf’ + +Package suggested but not available for checking: ‘moveVis’ +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR ``` -# tidybayes +# trending
-* Version: 3.0.3 -* GitHub: https://github.com/mjskay/tidybayes -* Source code: https://github.com/cran/tidybayes -* Date/Publication: 2023-02-04 09:10:02 UTC -* Number of recursive dependencies: 200 +* Version: 0.0.3 +* GitHub: https://github.com/reconhub/trending +* Source code: https://github.com/cran/trending +* Date/Publication: 2021-04-19 09:10:02 UTC +* Number of recursive dependencies: 142 -Run `revdepcheck::cloud_details(, "tidybayes")` for more info +Run `revdepcheck::cloud_details(, "trending")` for more info
@@ -7754,24 +16109,24 @@ Run `revdepcheck::cloud_details(, "tidybayes")` for more info ### Devel ``` -* using log directory ‘/tmp/workdir/tidybayes/new/tidybayes.Rcheck’ +* using log directory ‘/tmp/workdir/trending/new/trending.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘tidybayes/DESCRIPTION’ ... OK -* this is package ‘tidybayes’ version ‘3.0.3’ +* checking for file ‘trending/DESCRIPTION’ ... OK +* this is package ‘trending’ version ‘0.0.3’ * package encoding: UTF-8 * checking package namespace information ... OK * checking package dependencies ... NOTE ... +* 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 - ‘tidy-brms.Rmd’ using ‘UTF-8’... OK - ‘tidy-posterior.Rmd’ using ‘UTF-8’... OK - ‘tidy-rstanarm.Rmd’ using ‘UTF-8’... OK - ‘tidybayes-residuals.Rmd’ using ‘UTF-8’... OK - ‘tidybayes.Rmd’ using ‘UTF-8’... OK + ‘Introduction.Rmd’ using ‘UTF-8’... OK + ‘prediction_intervals.Rmd’ using ‘UTF-8’... OK * checking re-building of vignette outputs ... OK * DONE Status: 2 NOTEs @@ -7784,24 +16139,24 @@ Status: 2 NOTEs ### CRAN ``` -* using log directory ‘/tmp/workdir/tidybayes/old/tidybayes.Rcheck’ +* using log directory ‘/tmp/workdir/trending/old/trending.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘tidybayes/DESCRIPTION’ ... OK -* this is package ‘tidybayes’ version ‘3.0.3’ +* checking for file ‘trending/DESCRIPTION’ ... OK +* this is package ‘trending’ version ‘0.0.3’ * package encoding: UTF-8 * checking package namespace information ... OK * checking package dependencies ... NOTE ... +* 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 - ‘tidy-brms.Rmd’ using ‘UTF-8’... OK - ‘tidy-posterior.Rmd’ using ‘UTF-8’... OK - ‘tidy-rstanarm.Rmd’ using ‘UTF-8’... OK - ‘tidybayes-residuals.Rmd’ using ‘UTF-8’... OK - ‘tidybayes.Rmd’ using ‘UTF-8’... OK + ‘Introduction.Rmd’ using ‘UTF-8’... OK + ‘prediction_intervals.Rmd’ using ‘UTF-8’... OK * checking re-building of vignette outputs ... OK * DONE Status: 2 NOTEs @@ -7811,17 +16166,17 @@ Status: 2 NOTEs ``` -# tidyposterior +# TUFLOWR
-* Version: 1.0.0 -* GitHub: https://github.com/tidymodels/tidyposterior -* Source code: https://github.com/cran/tidyposterior -* Date/Publication: 2022-06-23 20:20:02 UTC -* Number of recursive dependencies: 170 +* Version: 0.1.0 +* GitHub: NA +* Source code: https://github.com/cran/TUFLOWR +* Date/Publication: 2021-10-18 14:30:05 UTC +* Number of recursive dependencies: 74 -Run `revdepcheck::cloud_details(, "tidyposterior")` for more info +Run `revdepcheck::cloud_details(, "TUFLOWR")` for more info
@@ -7830,22 +16185,27 @@ Run `revdepcheck::cloud_details(, "tidyposterior")` for more info ### Devel ``` -* using log directory ‘/tmp/workdir/tidyposterior/new/tidyposterior.Rcheck’ +* using log directory ‘/tmp/workdir/TUFLOWR/new/TUFLOWR.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘tidyposterior/DESCRIPTION’ ... OK -* this is package ‘tidyposterior’ version ‘1.0.0’ +* checking for file ‘TUFLOWR/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘TUFLOWR’ version ‘0.1.0’ * package encoding: UTF-8 * checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘rstanarm’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. +... +* checking Rd metadata ... OK +* checking Rd cross-references ... 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 examples ... OK * DONE -Status: 1 ERROR +Status: OK @@ -7855,39 +16215,44 @@ Status: 1 ERROR ### CRAN ``` -* using log directory ‘/tmp/workdir/tidyposterior/old/tidyposterior.Rcheck’ +* using log directory ‘/tmp/workdir/TUFLOWR/old/TUFLOWR.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘tidyposterior/DESCRIPTION’ ... OK -* this is package ‘tidyposterior’ version ‘1.0.0’ +* checking for file ‘TUFLOWR/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘TUFLOWR’ version ‘0.1.0’ * package encoding: UTF-8 * checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘rstanarm’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. +... +* checking Rd metadata ... OK +* checking Rd cross-references ... 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 examples ... OK * DONE -Status: 1 ERROR +Status: OK ``` -# tidySEM +# VancouvR
-* Version: 0.2.3 -* GitHub: https://github.com/cjvanlissa/tidySEM -* Source code: https://github.com/cran/tidySEM -* Date/Publication: 2022-04-14 17:50:02 UTC -* Number of recursive dependencies: 171 +* Version: 0.1.7 +* GitHub: https://github.com/mountainMath/VancouvR +* Source code: https://github.com/cran/VancouvR +* Date/Publication: 2021-10-21 04:30:02 UTC +* Number of recursive dependencies: 86 -Run `revdepcheck::cloud_details(, "tidySEM")` for more info +Run `revdepcheck::cloud_details(, "VancouvR")` for more info
@@ -7896,20 +16261,20 @@ Run `revdepcheck::cloud_details(, "tidySEM")` for more info ### Devel ``` -* using log directory ‘/tmp/workdir/tidySEM/new/tidySEM.Rcheck’ +* using log directory ‘/tmp/workdir/VancouvR/new/VancouvR.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘tidySEM/DESCRIPTION’ ... OK +* checking for file ‘VancouvR/DESCRIPTION’ ... OK * checking extension type ... Package -* this is package ‘tidySEM’ version ‘0.2.3’ +* this is package ‘VancouvR’ version ‘0.1.7’ * package encoding: UTF-8 * checking package namespace information ... OK * checking package dependencies ... ERROR -Package required but not available: ‘blavaan’ +Package required but not available: ‘sf’ -Package suggested but not available for checking: ‘umx’ +Package suggested but not available for checking: ‘lwgeom’ See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ manual. @@ -7924,20 +16289,20 @@ Status: 1 ERROR ### CRAN ``` -* using log directory ‘/tmp/workdir/tidySEM/old/tidySEM.Rcheck’ +* using log directory ‘/tmp/workdir/VancouvR/old/VancouvR.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘tidySEM/DESCRIPTION’ ... OK +* checking for file ‘VancouvR/DESCRIPTION’ ... OK * checking extension type ... Package -* this is package ‘tidySEM’ version ‘0.2.3’ +* this is package ‘VancouvR’ version ‘0.1.7’ * package encoding: UTF-8 * checking package namespace information ... OK * checking package dependencies ... ERROR -Package required but not available: ‘blavaan’ +Package required but not available: ‘sf’ -Package suggested but not available for checking: ‘umx’ +Package suggested but not available for checking: ‘lwgeom’ See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ manual. @@ -7949,16 +16314,17 @@ Status: 1 ERROR ``` -# tidytags +# vivid
-* Version: NA +* Version: 0.2.5 * GitHub: NA -* Source code: https://github.com/cran/tidytags -* Number of recursive dependencies: 122 +* Source code: https://github.com/cran/vivid +* Date/Publication: 2023-02-13 16:40:02 UTC +* Number of recursive dependencies: 206 -Run `revdepcheck::cloud_details(, "tidytags")` for more info +Run `revdepcheck::cloud_details(, "vivid")` for more info
@@ -7967,7 +16333,27 @@ Run `revdepcheck::cloud_details(, "tidytags")` for more info ### Devel ``` - +* using log directory ‘/tmp/workdir/vivid/new/vivid.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘vivid/DESCRIPTION’ ... OK +* this is package ‘vivid’ version ‘0.2.5’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... NOTE +... +* 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 + ‘vivid.Rmd’ using ‘UTF-8’... OK + ‘vividQStart.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 1 NOTE @@ -7977,24 +16363,44 @@ Run `revdepcheck::cloud_details(, "tidytags")` for more info ### CRAN ``` - +* using log directory ‘/tmp/workdir/vivid/old/vivid.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘vivid/DESCRIPTION’ ... OK +* this is package ‘vivid’ version ‘0.2.5’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... NOTE +... +* 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 + ‘vivid.Rmd’ using ‘UTF-8’... OK + ‘vividQStart.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 1 NOTE ``` -# timetk +# wallace
-* Version: 2.8.2 -* GitHub: https://github.com/business-science/timetk -* Source code: https://github.com/cran/timetk -* Date/Publication: 2022-11-17 19:30:02 UTC -* Number of recursive dependencies: 226 +* Version: 2.0.4 +* GitHub: NA +* Source code: https://github.com/cran/wallace +* Date/Publication: 2023-03-14 08:20:02 UTC +* Number of recursive dependencies: 282 -Run `revdepcheck::cloud_details(, "timetk")` for more info +Run `revdepcheck::cloud_details(, "wallace")` for more info
@@ -8003,27 +16409,27 @@ Run `revdepcheck::cloud_details(, "timetk")` for more info ### Devel ``` -* using log directory ‘/tmp/workdir/timetk/new/timetk.Rcheck’ +* using log directory ‘/tmp/workdir/wallace/new/wallace.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘timetk/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘timetk’ version ‘2.8.2’ +* checking for file ‘wallace/DESCRIPTION’ ... OK +* this is package ‘wallace’ version ‘2.0.4’ * package encoding: UTF-8 * checking package namespace information ... OK +* checking package dependencies ... NOTE ... - Error in library(robets) : there is no package called 'robets' - Execution halted -* checking for unstated dependencies in vignettes ... OK -* checking package vignettes in ‘inst/doc’ ... OK -* checking running R code from vignettes ... NONE - ‘TK04_Plotting_Time_Series.Rmd’ using ‘UTF-8’... OK - ‘TK07_Time_Series_Data_Wrangling.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK +* checking for code/documentation mismatches ... OK +* checking Rd \usage sections ... OK +* checking Rd contents ... OK +* checking for unstated dependencies in examples ... OK +* checking examples ... OK +* checking for unstated dependencies in ‘tests’ ... OK +* checking tests ... OK + Running ‘testthat.R’ * DONE -Status: 1 ERROR, 2 NOTEs +Status: 1 NOTE @@ -8033,44 +16439,44 @@ Status: 1 ERROR, 2 NOTEs ### CRAN ``` -* using log directory ‘/tmp/workdir/timetk/old/timetk.Rcheck’ +* using log directory ‘/tmp/workdir/wallace/old/wallace.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘timetk/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘timetk’ version ‘2.8.2’ +* checking for file ‘wallace/DESCRIPTION’ ... OK +* this is package ‘wallace’ version ‘2.0.4’ * package encoding: UTF-8 * checking package namespace information ... OK +* checking package dependencies ... NOTE ... - Error in library(robets) : there is no package called 'robets' - Execution halted -* checking for unstated dependencies in vignettes ... OK -* checking package vignettes in ‘inst/doc’ ... OK -* checking running R code from vignettes ... NONE - ‘TK04_Plotting_Time_Series.Rmd’ using ‘UTF-8’... OK - ‘TK07_Time_Series_Data_Wrangling.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK +* checking for code/documentation mismatches ... OK +* checking Rd \usage sections ... OK +* checking Rd contents ... OK +* checking for unstated dependencies in examples ... OK +* checking examples ... OK +* checking for unstated dependencies in ‘tests’ ... OK +* checking tests ... OK + Running ‘testthat.R’ * DONE -Status: 1 ERROR, 2 NOTEs +Status: 1 NOTE ``` -# tinyarray +# waterquality
-* Version: 2.2.9 -* GitHub: https://github.com/xjsun1221/tinyarray -* Source code: https://github.com/cran/tinyarray -* Date/Publication: 2023-03-04 07:40:02 UTC -* Number of recursive dependencies: 228 +* Version: 0.3.0 +* GitHub: https://github.com/RAJohansen/waterquality +* Source code: https://github.com/cran/waterquality +* Date/Publication: 2022-02-09 16:50:02 UTC +* Number of recursive dependencies: 151 -Run `revdepcheck::cloud_details(, "tinyarray")` for more info +Run `revdepcheck::cloud_details(, "waterquality")` for more info
@@ -8079,23 +16485,27 @@ Run `revdepcheck::cloud_details(, "tinyarray")` for more info ### Devel ``` -* using log directory ‘/tmp/workdir/tinyarray/new/tinyarray.Rcheck’ +* using log directory ‘/tmp/workdir/waterquality/new/waterquality.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘tinyarray/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘tinyarray’ version ‘2.2.9’ +* checking for file ‘waterquality/DESCRIPTION’ ... OK +* this is package ‘waterquality’ version ‘0.3.0’ * package encoding: UTF-8 * checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘clusterProfiler’ +* checking package dependencies ... NOTE +... +--- failed re-building ‘waterquality_vignette.Rmd’ + +SUMMARY: processing the following file failed: + ‘waterquality_vignette.Rmd’ + +Error: Vignette re-building failed. +Execution halted -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. * DONE -Status: 1 ERROR +Status: 1 WARNING, 2 NOTEs @@ -8105,40 +16515,43 @@ Status: 1 ERROR ### CRAN ``` -* using log directory ‘/tmp/workdir/tinyarray/old/tinyarray.Rcheck’ +* using log directory ‘/tmp/workdir/waterquality/old/waterquality.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘tinyarray/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘tinyarray’ version ‘2.2.9’ +* checking for file ‘waterquality/DESCRIPTION’ ... OK +* this is package ‘waterquality’ version ‘0.3.0’ * package encoding: UTF-8 * checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘clusterProfiler’ +* checking package dependencies ... NOTE +... +--- failed re-building ‘waterquality_vignette.Rmd’ + +SUMMARY: processing the following file failed: + ‘waterquality_vignette.Rmd’ + +Error: Vignette re-building failed. +Execution halted -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. * DONE -Status: 1 ERROR +Status: 1 WARNING, 2 NOTEs ``` -# tipmap +# Wats
-* Version: 0.3.9 +* Version: NA * GitHub: NA -* Source code: https://github.com/cran/tipmap -* Date/Publication: 2022-12-07 21:50:02 UTC -* Number of recursive dependencies: 96 +* Source code: https://github.com/cran/Wats +* Number of recursive dependencies: 122 -Run `revdepcheck::cloud_details(, "tipmap")` for more info +Run `revdepcheck::cloud_details(, "Wats")` for more info
@@ -8147,23 +16560,7 @@ Run `revdepcheck::cloud_details(, "tipmap")` for more info ### Devel ``` -* using log directory ‘/tmp/workdir/tipmap/new/tipmap.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘tipmap/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘tipmap’ version ‘0.3.9’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘RBesT’ -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR @@ -8173,40 +16570,88 @@ Status: 1 ERROR ### CRAN ``` -* using log directory ‘/tmp/workdir/tipmap/old/tipmap.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘tipmap/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘tipmap’ version ‘0.3.9’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘RBesT’ -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR ``` -# vivid +# waves
-* Version: 0.2.5 -* GitHub: NA -* Source code: https://github.com/cran/vivid -* Date/Publication: 2023-02-13 16:40:02 UTC -* Number of recursive dependencies: 206 +* Version: 0.2.4 +* GitHub: https://github.com/GoreLab/waves +* Source code: https://github.com/cran/waves +* Date/Publication: 2022-03-29 21:50:02 UTC +* Number of recursive dependencies: 165 -Run `revdepcheck::cloud_details(, "vivid")` for more info +Run `revdepcheck::cloud_details(, "waves")` for more info + +
+ +## In both + +* checking whether package ‘waves’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/waves/new/waves.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘waves’ ... +** package ‘waves’ 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 ‘sf’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Execution halted +ERROR: lazy loading failed for package ‘waves’ +* removing ‘/tmp/workdir/waves/new/waves.Rcheck/waves’ + + +``` +### CRAN + +``` +* installing *source* package ‘waves’ ... +** package ‘waves’ 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 ‘sf’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Execution halted +ERROR: lazy loading failed for package ‘waves’ +* removing ‘/tmp/workdir/waves/old/waves.Rcheck/waves’ + + +``` +# wdpar + +
+ +* Version: 1.3.4 +* GitHub: https://github.com/prioritizr/wdpar +* Source code: https://github.com/cran/wdpar +* Date/Publication: 2023-02-24 08:40:02 UTC +* Number of recursive dependencies: 108 + +Run `revdepcheck::cloud_details(, "wdpar")` for more info
@@ -8215,27 +16660,25 @@ Run `revdepcheck::cloud_details(, "vivid")` for more info ### Devel ``` -* using log directory ‘/tmp/workdir/vivid/new/vivid.Rcheck’ +* using log directory ‘/tmp/workdir/wdpar/new/wdpar.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘vivid/DESCRIPTION’ ... OK -* this is package ‘vivid’ version ‘0.2.5’ +* checking for file ‘wdpar/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘wdpar’ version ‘1.3.4’ * package encoding: UTF-8 * checking package namespace information ... OK -* checking package dependencies ... NOTE -... -* 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 - ‘vivid.Rmd’ using ‘UTF-8’... OK - ‘vividQStart.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK +* checking package dependencies ... ERROR +Packages required but not available: 'sf', 'lwgeom' + +Package suggested but not available for checking: ‘prepr’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. * DONE -Status: 1 NOTE +Status: 1 ERROR @@ -8245,27 +16688,25 @@ Status: 1 NOTE ### CRAN ``` -* using log directory ‘/tmp/workdir/vivid/old/vivid.Rcheck’ +* using log directory ‘/tmp/workdir/wdpar/old/wdpar.Rcheck’ * using R version 4.1.1 (2021-08-10) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘vivid/DESCRIPTION’ ... OK -* this is package ‘vivid’ version ‘0.2.5’ +* checking for file ‘wdpar/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘wdpar’ version ‘1.3.4’ * package encoding: UTF-8 * checking package namespace information ... OK -* checking package dependencies ... NOTE -... -* 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 - ‘vivid.Rmd’ using ‘UTF-8’... OK - ‘vividQStart.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK +* checking package dependencies ... ERROR +Packages required but not available: 'sf', 'lwgeom' + +Package suggested but not available for checking: ‘prepr’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. * DONE -Status: 1 NOTE +Status: 1 ERROR @@ -8338,10 +16779,10 @@ ERROR: lazy loading failed for package ‘wearables’
-* Version: 1.1-1 +* Version: 1.1-3 * GitHub: https://github.com/giopogg/webSDM * Source code: https://github.com/cran/webSDM -* Date/Publication: 2022-11-25 12:40:02 UTC +* Date/Publication: 2023-03-14 13:50:02 UTC * Number of recursive dependencies: 190 Run `revdepcheck::cloud_details(, "webSDM")` for more info @@ -8359,11 +16800,11 @@ Run `revdepcheck::cloud_details(, "webSDM")` for more info * using session charset: UTF-8 * using option ‘--no-manual’ * checking for file ‘webSDM/DESCRIPTION’ ... OK -* this is package ‘webSDM’ version ‘1.1-1’ +* this is package ‘webSDM’ version ‘1.1-3’ * package encoding: UTF-8 * checking package namespace information ... OK * checking package dependencies ... ERROR -Package required but not available: ‘rstanarm’ +Packages required but not available: 'brms', 'rstanarm' See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ manual. @@ -8384,11 +16825,11 @@ Status: 1 ERROR * using session charset: UTF-8 * using option ‘--no-manual’ * checking for file ‘webSDM/DESCRIPTION’ ... OK -* this is package ‘webSDM’ version ‘1.1-1’ +* this is package ‘webSDM’ version ‘1.1-3’ * package encoding: UTF-8 * checking package namespace information ... OK * checking package dependencies ... ERROR -Package required but not available: ‘rstanarm’ +Packages required but not available: 'brms', 'rstanarm' See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ manual. @@ -8443,7 +16884,7 @@ Run `revdepcheck::cloud_details(, "wrappedtools")` for more info * GitHub: NA * Source code: https://github.com/cran/xpose.nlmixr2 * Date/Publication: 2022-06-08 09:10:02 UTC -* Number of recursive dependencies: 161 +* Number of recursive dependencies: 158 Run `revdepcheck::cloud_details(, "xpose.nlmixr2")` for more info @@ -8506,4 +16947,138 @@ Status: 1 ERROR +``` +# zipcodeR + +
+ +* Version: 0.3.5 +* GitHub: https://github.com/gavinrozzi/zipcodeR +* Source code: https://github.com/cran/zipcodeR +* Date/Publication: 2022-10-03 22:00:02 UTC +* Number of recursive dependencies: 99 + +Run `revdepcheck::cloud_details(, "zipcodeR")` for more info + +
+ +## In both + +* checking whether package ‘zipcodeR’ can be installed ... ERROR + ``` + Installation failed. + See ‘/tmp/workdir/zipcodeR/new/zipcodeR.Rcheck/00install.out’ for details. + ``` + +## Installation + +### Devel + +``` +* installing *source* package ‘zipcodeR’ ... +** package ‘zipcodeR’ 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 ‘sf’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Execution halted +ERROR: lazy loading failed for package ‘zipcodeR’ +* removing ‘/tmp/workdir/zipcodeR/new/zipcodeR.Rcheck/zipcodeR’ + + +``` +### CRAN + +``` +* installing *source* package ‘zipcodeR’ ... +** package ‘zipcodeR’ 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 ‘sf’ +Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart +Execution halted +ERROR: lazy loading failed for package ‘zipcodeR’ +* removing ‘/tmp/workdir/zipcodeR/old/zipcodeR.Rcheck/zipcodeR’ + + +``` +# zonebuilder + +
+ +* Version: 0.0.2 +* GitHub: https://github.com/zonebuilders/zonebuilder +* Source code: https://github.com/cran/zonebuilder +* Date/Publication: 2021-07-12 22:30:02 UTC +* Number of recursive dependencies: 126 + +Run `revdepcheck::cloud_details(, "zonebuilder")` for more info + +
+ +## Error before installation + +### Devel + +``` +* using log directory ‘/tmp/workdir/zonebuilder/new/zonebuilder.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘zonebuilder/DESCRIPTION’ ... OK +* this is package ‘zonebuilder’ version ‘0.0.2’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘sf’ + +Package suggested but not available for checking: ‘lwgeom’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. +* DONE +Status: 1 ERROR + + + + + +``` +### CRAN + +``` +* using log directory ‘/tmp/workdir/zonebuilder/old/zonebuilder.Rcheck’ +* using R version 4.1.1 (2021-08-10) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘zonebuilder/DESCRIPTION’ ... OK +* this is package ‘zonebuilder’ version ‘0.0.2’ +* package encoding: UTF-8 +* checking package namespace information ... OK +* checking package dependencies ... ERROR +Package required but not available: ‘sf’ + +Package suggested but not available for checking: ‘lwgeom’ + +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 53fb5db1c..893b53f87 100644 --- a/revdep/problems.md +++ b/revdep/problems.md @@ -1,152 +1,34 @@ -# dplyr +# openalexR
-* Version: 1.1.0 -* GitHub: https://github.com/tidyverse/dplyr -* Source code: https://github.com/cran/dplyr -* Date/Publication: 2023-01-29 22:50:02 UTC -* Number of recursive dependencies: 95 +* Version: 1.0.0 +* GitHub: https://github.com/massimoaria/openalexR +* Source code: https://github.com/cran/openalexR +* Date/Publication: 2022-10-06 10:40:02 UTC +* Number of recursive dependencies: 78 -Run `revdepcheck::cloud_details(, "dplyr")` for more info +Run `revdepcheck::cloud_details(, "openalexR")` for more info
## Newly broken -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Last 13 lines of output: - • Can't use 'en_US' locale (2) - • On CRAN (305) - - ══ Failed tests ════════════════════════════════════════════════════════════════ - ── Failure ('test-filter.R:301'): hybrid function row_number does not trigger warning in filter (#3750) ── - `out` is not TRUE - - `actual`: FALSE - `expected`: TRUE - ── Failure ('test-join-by.R:236'): nicely catches missing arguments when wrapped ── - `fn(a)` did not throw the expected error. - - [ FAIL 2 | WARN 270 | SKIP 311 | PASS 2742 ] - Error: Test failures - Execution halted - ``` - -## In both - -* checking data for non-ASCII characters ... NOTE - ``` - Note: found 4 marked UTF-8 strings - ``` - -# GenomeAdmixR - -
- -* Version: 2.1.7 -* GitHub: https://github.com/thijsjanzen/GenomeAdmixR -* Source code: https://github.com/cran/GenomeAdmixR -* Date/Publication: 2022-03-01 21:10:15 UTC -* Number of recursive dependencies: 104 - -Run `revdepcheck::cloud_details(, "GenomeAdmixR")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Last 13 lines of output: - | | 0% - | - |=================================== | 50% - | - |======================================================================| 100%[ FAIL 1 | WARN 0 | SKIP 0 | PASS 454 ] - - ══ Failed tests ════════════════════════════════════════════════════════════════ - ── Failure ('test-simulate_admixture_data.R:202'): simulate_admixture_data_recombination_map ── - `all_j` not equal to `expected_num_j`. - 1/1 mismatches - [1] 71 - 100 == -29 - - [ FAIL 1 | WARN 0 | SKIP 0 | PASS 454 ] - Error: Test failures - Execution halted - ``` - -## In both - -* checking installed package size ... NOTE - ``` - installed size is 11.9Mb - sub-directories of 1Mb or more: - doc 2.0Mb - libs 9.3Mb - ``` - -* checking dependencies in R code ... NOTE - ``` - Namespace in Imports field not imported from: ‘methods’ - All declared Imports should be used. - ``` - -# photosynthesis - -
- -* Version: 2.1.1 -* GitHub: https://github.com/cdmuir/photosynthesis -* Source code: https://github.com/cran/photosynthesis -* Date/Publication: 2022-11-19 19:40:09 UTC -* Number of recursive dependencies: 135 - -Run `revdepcheck::cloud_details(, "photosynthesis")` for more info - -
- -## Newly broken - -* checking tests ... ERROR - ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Last 13 lines of output: - Expected `{ ... }` to run without any conditions. - ℹ Actually got a : - Condition: - `flatten()` is deprecated as of rlang 1.1.0. ℹ Please use - `purrr::list_flatten()` or `purrr::list_c()`. - ── Failure ('test-fit_aq_response2.R:44'): .vars argument renames variables ──── - Expected `{ ... }` to run without any conditions. - ℹ Actually got a : - Condition: - `flatten()` is deprecated as of rlang 1.1.0. ℹ Please use - `purrr::list_flatten()` or `purrr::list_c()`. - - [ FAIL 6 | WARN 2 | SKIP 0 | PASS 320 ] - Error: Test failures - Execution halted +* checking re-building of vignette outputs ... WARNING ``` - -## In both - -* checking installed package size ... NOTE - ``` - installed size is 7.1Mb - sub-directories of 1Mb or more: - doc 6.1Mb - ``` - -* checking data for non-ASCII characters ... NOTE - ``` - Note: found 13 marked UTF-8 strings + Error(s) in re-building vignettes: + ... + --- re-building ‘A_Brief_Introduction_to_openalexR.Rmd’ using rmarkdown + Quitting from lines 260-269 (A_Brief_Introduction_to_openalexR.Rmd) + Error: processing vignette 'A_Brief_Introduction_to_openalexR.Rmd' failed with diagnostics: + $ operator is invalid for atomic vectors + --- failed re-building ‘A_Brief_Introduction_to_openalexR.Rmd’ + + SUMMARY: processing the following file failed: + ‘A_Brief_Introduction_to_openalexR.Rmd’ + + Error: Vignette re-building failed. + Execution halted ``` # portalr @@ -187,17 +69,17 @@ Run `revdepcheck::cloud_details(, "portalr")` for more info Execution halted ``` -# rlang +# rapbase
-* Version: 1.0.6 -* GitHub: https://github.com/r-lib/rlang -* Source code: https://github.com/cran/rlang -* Date/Publication: 2022-09-24 05:40:02 UTC -* Number of recursive dependencies: 68 +* Version: 1.24.0 +* GitHub: https://github.com/Rapporteket/rapbase +* Source code: https://github.com/cran/rapbase +* Date/Publication: 2023-02-27 10:22:31 UTC +* Number of recursive dependencies: 110 -Run `revdepcheck::cloud_details(, "rlang")` for more info +Run `revdepcheck::cloud_details(, "rapbase")` for more info
@@ -205,31 +87,23 @@ Run `revdepcheck::cloud_details(, "rlang")` for more info * checking tests ... ERROR ``` - Running ‘sink.R’ Running ‘testthat.R’ Running the tests in ‘tests/testthat.R’ failed. Last 13 lines of output: - 12. ├─base::namespaceImportFrom(...) - 13. │ └─base::asNamespace(ns) - 14. └─base::loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) - 15. ├─base::namespaceImportFrom(...) - 16. │ └─base::asNamespace(ns) - 17. └─base::loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) - 18. ├─base::namespaceImportFrom(...) - 19. │ └─base::asNamespace(ns) - 20. └─base::loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) - 21. ├─base::namespaceImport(...) - 22. └─base::loadNamespace(i, c(lib.loc, .libPaths()), versionCheck = vI[[i]]) + ══ Failed tests ════════════════════════════════════════════════════════════════ + ── Failure ('test-github.R:6:3'): contributors are provided ──────────────────── + class(getGithub("contributors", "rapbase")) not equal to "character". + 1/1 mismatches + x[1]: "NULL" + y[1]: "character" + ── Failure ('test-github.R:10:3'): key can be provided ───────────────────────── + grepl("ssh-rsa", getGithub("keys", "areedv")) is not TRUE + + `actual`: + `expected`: TRUE - [ FAIL 2 | WARN 2 | SKIP 235 | PASS 3661 ] + [ FAIL 2 | WARN 0 | SKIP 37 | PASS 246 ] Error: Test failures Execution halted ``` -## In both - -* checking package dependencies ... NOTE - ``` - Package which this enhances but not available for checking: ‘winch’ - ``` - From fd3d55068be638ba1141b44a3fae0a2e192dbcea Mon Sep 17 00:00:00 2001 From: DavisVaughan Date: Wed, 15 Mar 2023 10:37:47 -0400 Subject: [PATCH 265/312] Update codecov badge --- README.Rmd | 2 +- README.md | 4 ++-- 2 files changed, 3 insertions(+), 3 deletions(-) diff --git a/README.Rmd b/README.Rmd index 2c0cc726a..a9c57b211 100644 --- a/README.Rmd +++ b/README.Rmd @@ -16,7 +16,7 @@ knitr::opts_chunk$set( # vctrs
-[![Coverage status](https://codecov.io/gh/r-lib/vctrs/branch/main/graph/badge.svg)](https://codecov.io/github/r-lib/vctrs?branch=master) +[![Codecov test coverage](https://codecov.io/gh/r-lib/vctrs/branch/main/graph/badge.svg)](https://app.codecov.io/gh/r-lib/vctrs?branch=main) ![Lifecycle: maturing](https://img.shields.io/badge/lifecycle-maturing-blue.svg) [![R-CMD-check](https://github.com/r-lib/vctrs/actions/workflows/R-CMD-check.yaml/badge.svg)](https://github.com/r-lib/vctrs/actions/workflows/R-CMD-check.yaml) diff --git a/README.md b/README.md index 4d9365bf8..7e85255cd 100644 --- a/README.md +++ b/README.md @@ -5,8 +5,8 @@ -[![Coverage -status](https://codecov.io/gh/r-lib/vctrs/branch/main/graph/badge.svg)](https://codecov.io/github/r-lib/vctrs?branch=master) +[![Codecov test +coverage](https://codecov.io/gh/r-lib/vctrs/branch/main/graph/badge.svg)](https://app.codecov.io/gh/r-lib/vctrs?branch=main) ![Lifecycle: maturing](https://img.shields.io/badge/lifecycle-maturing-blue.svg) [![R-CMD-check](https://github.com/r-lib/vctrs/actions/workflows/R-CMD-check.yaml/badge.svg)](https://github.com/r-lib/vctrs/actions/workflows/R-CMD-check.yaml) From dcf57e96086ebc3f6fdfa3f356cdda4cb19ce346 Mon Sep 17 00:00:00 2001 From: Davis Vaughan Date: Thu, 16 Mar 2023 09:03:11 -0400 Subject: [PATCH 266/312] RC 0.6.0 (#1816) * Update `cran-comments.md` * Increment version number to 0.6.0 * Mention that we fixed the CRAN check failures * Swap to self as maintainer * CRAN-SUBMISSION * Delete CRAN-SUBMISSION --- DESCRIPTION | 6 +++--- NEWS.md | 2 +- cran-comments.md | 12 +++++++++++- man/vctrs-package.Rd | 4 ++-- src/version.c | 2 +- 5 files changed, 18 insertions(+), 8 deletions(-) diff --git a/DESCRIPTION b/DESCRIPTION index 0e71448ab..c604dbd72 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -1,6 +1,6 @@ Package: vctrs Title: Vector Helpers -Version: 0.5.2.9000 +Version: 0.6.0 Authors@R: c(person(given = "Hadley", family = "Wickham", @@ -8,11 +8,11 @@ Authors@R: email = "hadley@posit.co"), person(given = "Lionel", family = "Henry", - role = c("aut", "cre"), + role = "aut", email = "lionel@posit.co"), person(given = "Davis", family = "Vaughan", - role = "aut", + role = c("aut", "cre"), email = "davis@posit.co"), person(given = "data.table team", role = "cph", diff --git a/NEWS.md b/NEWS.md index 946a82f0a..6920473fa 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,4 +1,4 @@ -# vctrs (development version) +# vctrs 0.6.0 * New `vec_run_sizes()` for computing the size of each run within a vector. It is identical to the `times` column from `vec_unrep()`, but is faster if you diff --git a/cran-comments.md b/cran-comments.md index 1ea825650..53957236c 100644 --- a/cran-comments.md +++ b/cran-comments.md @@ -1 +1,11 @@ -This is a patch release with no expected breakage of any reverse dependencies. +This is a minor release with no expected breakage of any reverse dependencies. + +We fixed the CRAN check result failures, in particular: +- We removed `SystemRequirements: C++11`. +- We fixed the S3 method inconsistencies for `cnd_header()` and `cnd_body()`. + +The following reverse dependencies showed up in our checks, but we believe they are false alarms: +- GenomeAdmixR: Can't reproduce locally. +- portalr: A common failing package that we see. Likely related to a failed download. +- openalexR: A common failing package that we see. Likely related to a failed download. +- rapbase: Likely related to a failed download from GitHub. diff --git a/man/vctrs-package.Rd b/man/vctrs-package.Rd index e4279f1fa..487bcfa60 100644 --- a/man/vctrs-package.Rd +++ b/man/vctrs-package.Rd @@ -22,12 +22,12 @@ Useful links: } \author{ -\strong{Maintainer}: Lionel Henry \email{lionel@posit.co} +\strong{Maintainer}: Davis Vaughan \email{davis@posit.co} Authors: \itemize{ \item Hadley Wickham \email{hadley@posit.co} - \item Davis Vaughan \email{davis@posit.co} + \item Lionel Henry \email{lionel@posit.co} } Other contributors: diff --git a/src/version.c b/src/version.c index 6146e60c2..f4ea36420 100644 --- a/src/version.c +++ b/src/version.c @@ -1,7 +1,7 @@ #define R_NO_REMAP #include -const char* vctrs_version = "0.5.2.9000"; +const char* vctrs_version = "0.6.0"; /** * This file records the expected package version in the shared From 186daf7b12d766c32c0ede7259dbf31cf27546f6 Mon Sep 17 00:00:00 2001 From: DavisVaughan Date: Thu, 16 Mar 2023 09:05:07 -0400 Subject: [PATCH 267/312] Increment version number to 0.6.0.9000 --- DESCRIPTION | 2 +- NEWS.md | 2 ++ src/version.c | 2 +- 3 files changed, 4 insertions(+), 2 deletions(-) diff --git a/DESCRIPTION b/DESCRIPTION index c604dbd72..83d8a323b 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -1,6 +1,6 @@ Package: vctrs Title: Vector Helpers -Version: 0.6.0 +Version: 0.6.0.9000 Authors@R: c(person(given = "Hadley", family = "Wickham", diff --git a/NEWS.md b/NEWS.md index 6920473fa..601f003ad 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,3 +1,5 @@ +# vctrs (development version) + # vctrs 0.6.0 * New `vec_run_sizes()` for computing the size of each run within a vector. It diff --git a/src/version.c b/src/version.c index f4ea36420..f37dd8303 100644 --- a/src/version.c +++ b/src/version.c @@ -1,7 +1,7 @@ #define R_NO_REMAP #include -const char* vctrs_version = "0.6.0"; +const char* vctrs_version = "0.6.0.9000"; /** * This file records the expected package version in the shared From fe1f2ee450d2a8f0969cf9fa01642e0fba3dd89f Mon Sep 17 00:00:00 2001 From: Davis Vaughan Date: Fri, 17 Mar 2023 09:52:51 -0400 Subject: [PATCH 268/312] Fix sf `c()` test now that `c.sfc()` requires identical crs (#1817) * Fix sf `c()` test now that `c.sfc()` requires identical crs * NEWS bullet --- NEWS.md | 2 ++ tests/testthat/_snaps/type-sf.md | 8 ++++++++ tests/testthat/test-type-sf.R | 26 ++++++++++++++++++-------- 3 files changed, 28 insertions(+), 8 deletions(-) create mode 100644 tests/testthat/_snaps/type-sf.md diff --git a/NEWS.md b/NEWS.md index 601f003ad..e171659d2 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,5 +1,7 @@ # vctrs (development version) +* Fixed a test related to `c.sfc()` changes in sf 1.0-10 (#1817). + # vctrs 0.6.0 * New `vec_run_sizes()` for computing the size of each run within a vector. It diff --git a/tests/testthat/_snaps/type-sf.md b/tests/testthat/_snaps/type-sf.md new file mode 100644 index 000000000..bf214d42b --- /dev/null +++ b/tests/testthat/_snaps/type-sf.md @@ -0,0 +1,8 @@ +# `crs` attributes of `sfc` vectors must be the same + + Code + vctrs::vec_c(x, y) + Condition + Error: + ! arguments have different crs + diff --git a/tests/testthat/test-type-sf.R b/tests/testthat/test-type-sf.R index 59740e20d..055a2c358 100644 --- a/tests/testthat/test-type-sf.R +++ b/tests/testthat/test-type-sf.R @@ -12,8 +12,9 @@ testthat_import_from("sf", c( "st_multipoint" )) -# Need recent version to work around restore bug for sfc lists -skip_if_not_installed("sf", "0.9-4") +# Need recent version to work around restore bug for sfc lists and changes +# to `c.sfc()` +skip_if_not_installed("sf", "1.0-11") test_that("sf has a ptype2 method", { sfc1 = st_sfc(st_point(1:2), st_point(3:4)) @@ -213,22 +214,31 @@ test_that("`precision` and `crs` attributes of `sfc` vectors are restored", { expect_identical(st_crs(x), st_crs(out)) }) -test_that("`precision` and `crs` attributes of `sfc` vectors are combined", { +test_that("`precision` attributes of `sfc` vectors are combined", { x = st_sfc(st_point(c(pi, pi)), precision = 1e-4, crs = 3857) y = st_sfc(st_point(c(0, 0)), precision = 1e-4, crs = 3857) out = vctrs::vec_c(x, y) expect_identical(st_precision(x), st_precision(out)) - expect_identical(st_crs(x), st_crs(out)) - # These used to be errors before we fell back to c() + # These used to be errors before we fell back to c() y = st_sfc(st_point(c(0, 0)), precision = 1e-2, crs = 3857) expect_identical(vctrs::vec_c(x, y), c(x, y)) # expect_error(vctrs::vec_c(x, y), "precisions not equal") +}) - y = st_sfc(st_point(c(0, 0)), precision = 1e-4, crs = 4326) - expect_identical(vctrs::vec_c(x, y), c(x, y)) - # expect_error(vctrs::vec_c(x, y), "coordinate reference systems not equal") +test_that("`crs` attributes of `sfc` vectors must be the same", { + x = st_sfc(st_point(c(pi, pi)), precision = 1e-4, crs = 3857) + y = st_sfc(st_point(c(0, 0)), precision = 1e-4, crs = 3857) + + out = vctrs::vec_c(x, y) + expect_identical(st_crs(x), st_crs(out)) + + # Error on different `crs` comes from sf as of 1.0-10 + y = st_sfc(st_point(c(0, 0)), precision = 1e-4, crs = 4326) + expect_snapshot(error = TRUE, { + vctrs::vec_c(x, y) + }) }) test_that("`vec_locate_matches()` works with `sfc` vectors", { From 310daf4de8d5c0ee056c9ca3bf29b75832c027b2 Mon Sep 17 00:00:00 2001 From: Davis Vaughan Date: Fri, 17 Mar 2023 11:43:49 -0400 Subject: [PATCH 269/312] Skip sf and data.table tests on CRAN (#1818) * Move data.table logic to `type-data-table.R` * Skip sf and data.table tests on CRAN --- R/type-data-table.R | 45 +++++++++++++++++ R/type-misc.R | 49 ------------------ tests/testthat/_snaps/type-data-table.md | 12 +++++ tests/testthat/_snaps/type-misc.md | 12 ----- tests/testthat/test-type-data-table.R | 64 ++++++++++++++++++++++++ tests/testthat/test-type-misc.R | 63 ----------------------- tests/testthat/test-type-sf.R | 7 ++- 7 files changed, 127 insertions(+), 125 deletions(-) create mode 100644 R/type-data-table.R create mode 100644 tests/testthat/_snaps/type-data-table.md create mode 100644 tests/testthat/test-type-data-table.R diff --git a/R/type-data-table.R b/R/type-data-table.R new file mode 100644 index 000000000..abc097e27 --- /dev/null +++ b/R/type-data-table.R @@ -0,0 +1,45 @@ +delayedAssign("as.data.table", { + if (is_installed("data.table")) { + env_get(ns_env("data.table"), "as.data.table") + } else { + function(...) abort("`data.table` must be installed.") + } +}) + +dt_ptype2 <- function(x, y, ...) { + as.data.table(df_ptype2(x, y, ...)) +} +dt_cast <- function(x, to, ...) { + as.data.table(df_cast(x, to, ...)) +} + +#' @export +vec_ptype2.data.table.data.table <- function(x, y, ...) { + dt_ptype2(x, y, ...) +} +#' @export +vec_ptype2.data.table.data.frame <- function(x, y, ...) { + dt_ptype2(x, y, ...) +} +#' @export +vec_ptype2.data.frame.data.table <- function(x, y, ...) { + dt_ptype2(x, y, ...) +} + +#' @export +vec_cast.data.table.data.table <- function(x, to, ...) { + dt_cast(x, to, ...) +} +#' @export +vec_cast.data.table.data.frame <- function(x, to, ...) { + dt_cast(x, to, ...) +} +#' @export +vec_cast.data.frame.data.table <- function(x, to, ...) { + df_cast(x, to, ...) +} + +#' @export +vec_ptype_abbr.data.table <- function(x, ...) { + "dt" +} diff --git a/R/type-misc.R b/R/type-misc.R index fb1c5cae9..258d0957b 100644 --- a/R/type-misc.R +++ b/R/type-misc.R @@ -186,52 +186,3 @@ vec_cast.double.exclude <- function(x, to, ...) { vec_cast.exclude.double <- function(x, to, ..., x_arg = "", to_arg = "") { stop_incompatible_cast(x, to, x_arg = x_arg, to_arg = to_arg) } - - -# `data.table` ------------------------------------------------------- - -delayedAssign("as.data.table", { - if (is_installed("data.table")) { - env_get(ns_env("data.table"), "as.data.table") - } else { - function(...) abort("`data.table` must be installed.") - } -}) - -dt_ptype2 <- function(x, y, ...) { - as.data.table(df_ptype2(x, y, ...)) -} -dt_cast <- function(x, to, ...) { - as.data.table(df_cast(x, to, ...)) -} - -#' @export -vec_ptype2.data.table.data.table <- function(x, y, ...) { - dt_ptype2(x, y, ...) -} -#' @export -vec_ptype2.data.table.data.frame <- function(x, y, ...) { - dt_ptype2(x, y, ...) -} -#' @export -vec_ptype2.data.frame.data.table <- function(x, y, ...) { - dt_ptype2(x, y, ...) -} - -#' @export -vec_cast.data.table.data.table <- function(x, to, ...) { - dt_cast(x, to, ...) -} -#' @export -vec_cast.data.table.data.frame <- function(x, to, ...) { - dt_cast(x, to, ...) -} -#' @export -vec_cast.data.frame.data.table <- function(x, to, ...) { - df_cast(x, to, ...) -} - -#' @export -vec_ptype_abbr.data.table <- function(x, ...) { - "dt" -} diff --git a/tests/testthat/_snaps/type-data-table.md b/tests/testthat/_snaps/type-data-table.md new file mode 100644 index 000000000..ba0833783 --- /dev/null +++ b/tests/testthat/_snaps/type-data-table.md @@ -0,0 +1,12 @@ +# data table has formatting methods + + Code + dt <- data.table(x = 1, y = 2, z = 3) + vec_ptype_abbr(dt) + Output + [1] "dt[,3]" + Code + vec_ptype_full(dt) + Output + [1] "data.table<\n x: double\n y: double\n z: double\n>" + diff --git a/tests/testthat/_snaps/type-misc.md b/tests/testthat/_snaps/type-misc.md index 185491613..f7a48905d 100644 --- a/tests/testthat/_snaps/type-misc.md +++ b/tests/testthat/_snaps/type-misc.md @@ -6,15 +6,3 @@ Error in `vec_proxy_equal()`: ! `x` can't contain more than 8 version components. -# data table has formatting methods - - Code - dt <- data.table(x = 1, y = 2, z = 3) - vec_ptype_abbr(dt) - Output - [1] "dt[,3]" - Code - vec_ptype_full(dt) - Output - [1] "data.table<\n x: double\n y: double\n z: double\n>" - diff --git a/tests/testthat/test-type-data-table.R b/tests/testthat/test-type-data-table.R new file mode 100644 index 000000000..fdb2af034 --- /dev/null +++ b/tests/testthat/test-type-data-table.R @@ -0,0 +1,64 @@ +# Never run on CRAN, even if they have data.table, because we don't regularly +# check these on CI and we don't want a change in data.table to force a CRAN +# failure for vctrs. +skip_on_cran() + +# Avoids adding `data.table` to Suggests. +# These tests are only run on the devs' machines. +testthat_import_from("data.table", "data.table") + +test_that("common type of data.table and data.frame is data.table", { + expect_identical( + vec_ptype2(data.table(x = TRUE), data.table(y = 2)), + data.table(x = lgl(), y = dbl()) + ) + expect_identical( + vec_ptype2(data.table(x = TRUE), data.frame(y = 2)), + data.table(x = lgl(), y = dbl()) + ) + expect_identical( + vec_ptype2(data.frame(y = 2), data.table(x = TRUE)), + data.table(y = dbl(), x = lgl()) + ) + + expect_identical( + vec_cast(data.table(y = 2), data.table(x = TRUE, y = 1L)), + data.table(x = NA, y = 2L) + ) + expect_identical( + vec_cast(data.frame(y = 2), data.table(x = TRUE, y = 1L)), + data.table(x = NA, y = 2L) + ) + expect_identical( + vec_cast(data.table(y = 2), data.frame(x = TRUE, y = 1L)), + data.frame(x = NA, y = 2L) + ) +}) + +test_that("data.table and tibble do not have a common type", { + expect_equal( + vec_ptype_common(data.table(x = TRUE), tibble(y = 2)), + tibble(x = lgl(), y = dbl()) + ) + expect_equal( + vec_ptype_common(tibble(y = 2), data.table(x = TRUE)), + tibble(y = dbl(), x = lgl()) + ) + + expect_identical( + vec_cast(data.table(y = 2), tibble(x = TRUE, y = 1L)), + tibble(x = lgl(NA), y = 2L) + ) + expect_identical( + vec_cast(tibble(y = 2), data.table(x = TRUE, y = 1L)), + data_frame(x = lgl(NA), y = 2L) + ) +}) + +test_that("data table has formatting methods", { + expect_snapshot({ + dt <- data.table(x = 1, y = 2, z = 3) + vec_ptype_abbr(dt) + vec_ptype_full(dt) + }) +}) diff --git a/tests/testthat/test-type-misc.R b/tests/testthat/test-type-misc.R index bc407c42c..1712cf475 100644 --- a/tests/testthat/test-type-misc.R +++ b/tests/testthat/test-type-misc.R @@ -163,69 +163,6 @@ test_that("`package_version` and `R_system_version` use the `numeric_version` pr expect_identical(vec_proxy_equal(z), vec_proxy_equal(x)) }) -test_that("common type of data.table and data.frame is data.table", { - # As data.table is not in Suggests, these checks are only run on the - # devs' machines - testthat_import_from("data.table", "data.table") - - expect_identical( - vec_ptype2(data.table(x = TRUE), data.table(y = 2)), - data.table(x = lgl(), y = dbl()) - ) - expect_identical( - vec_ptype2(data.table(x = TRUE), data.frame(y = 2)), - data.table(x = lgl(), y = dbl()) - ) - expect_identical( - vec_ptype2(data.frame(y = 2), data.table(x = TRUE)), - data.table(y = dbl(), x = lgl()) - ) - - expect_identical( - vec_cast(data.table(y = 2), data.table(x = TRUE, y = 1L)), - data.table(x = NA, y = 2L) - ) - expect_identical( - vec_cast(data.frame(y = 2), data.table(x = TRUE, y = 1L)), - data.table(x = NA, y = 2L) - ) - expect_identical( - vec_cast(data.table(y = 2), data.frame(x = TRUE, y = 1L)), - data.frame(x = NA, y = 2L) - ) -}) - -test_that("data.table and tibble do not have a common type", { - testthat_import_from("data.table", "data.table") - - expect_equal( - vec_ptype_common(data.table(x = TRUE), tibble(y = 2)), - tibble(x = lgl(), y = dbl()) - ) - expect_equal( - vec_ptype_common(tibble(y = 2), data.table(x = TRUE)), - tibble(y = dbl(), x = lgl()) - ) - - expect_identical( - vec_cast(data.table(y = 2), tibble(x = TRUE, y = 1L)), - tibble(x = lgl(NA), y = 2L) - ) - expect_identical( - vec_cast(tibble(y = 2), data.table(x = TRUE, y = 1L)), - data_frame(x = lgl(NA), y = 2L) - ) -}) - -test_that("data table has formatting methods", { - testthat_import_from("data.table", "data.table") - expect_snapshot({ - dt <- data.table(x = 1, y = 2, z = 3) - vec_ptype_abbr(dt) - vec_ptype_full(dt) - }) -}) - test_that("can slice `ts` vectors", { x <- ts(1:3) expect_identical(vec_ptype(x), x[0]) diff --git a/tests/testthat/test-type-sf.R b/tests/testthat/test-type-sf.R index 055a2c358..3a020fa08 100644 --- a/tests/testthat/test-type-sf.R +++ b/tests/testthat/test-type-sf.R @@ -1,5 +1,10 @@ +# Never run on CRAN, even if they have sf, because we don't regularly +# check these on CI and we don't want a change in sf to force a CRAN +# failure for vctrs. +skip_on_cran() -# Avoids adding `sf` to Suggests +# Avoids adding `sf` to Suggests. +# These tests are only run on the devs' machines. testthat_import_from("sf", c( "st_sf", "st_sfc", From c185ecd4e34fd4bf98aaaf5061195e5fb079704e Mon Sep 17 00:00:00 2001 From: DavisVaughan Date: Fri, 17 Mar 2023 11:49:18 -0400 Subject: [PATCH 270/312] Add GitHub URL --- DESCRIPTION | 2 +- man/vctrs-package.Rd | 1 + 2 files changed, 2 insertions(+), 1 deletion(-) diff --git a/DESCRIPTION b/DESCRIPTION index 83d8a323b..a6860a5f8 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -24,7 +24,7 @@ Description: Defines new notions of prototype and size that are and size-recycling, and are in turn connected to ideas of type- and size-stability useful for analysing function interfaces. License: MIT + file LICENSE -URL: https://vctrs.r-lib.org/ +URL: https://vctrs.r-lib.org/, https://github.com/r-lib/vctrs BugReports: https://github.com/r-lib/vctrs/issues Depends: R (>= 3.5.0) diff --git a/man/vctrs-package.Rd b/man/vctrs-package.Rd index 487bcfa60..676f39bd7 100644 --- a/man/vctrs-package.Rd +++ b/man/vctrs-package.Rd @@ -17,6 +17,7 @@ size-stability useful for analysing function interfaces. Useful links: \itemize{ \item \url{https://vctrs.r-lib.org/} + \item \url{https://github.com/r-lib/vctrs} \item Report bugs at \url{https://github.com/r-lib/vctrs/issues} } From 273d2dadae2c6353e14ff75d335f876106fe3f97 Mon Sep 17 00:00:00 2001 From: DavisVaughan Date: Fri, 17 Mar 2023 11:50:20 -0400 Subject: [PATCH 271/312] `use_tidy_description()` --- DESCRIPTION | 38 ++++++++++++++------------------------ 1 file changed, 14 insertions(+), 24 deletions(-) diff --git a/DESCRIPTION b/DESCRIPTION index a6860a5f8..5fe509af1 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -1,27 +1,17 @@ Package: vctrs Title: Vector Helpers Version: 0.6.0.9000 -Authors@R: - c(person(given = "Hadley", - family = "Wickham", - role = "aut", - email = "hadley@posit.co"), - person(given = "Lionel", - family = "Henry", - role = "aut", - email = "lionel@posit.co"), - person(given = "Davis", - family = "Vaughan", - role = c("aut", "cre"), - email = "davis@posit.co"), - person(given = "data.table team", - role = "cph", - comment = "Radix sort based on data.table's forder() and their contribution to R's order()"), - person(given = "Posit Software, PBC", - role = c("cph", "fnd"))) -Description: Defines new notions of prototype and size that are - used to provide tools for consistent and well-founded type-coercion - and size-recycling, and are in turn connected to ideas of type- and +Authors@R: c( + person("Hadley", "Wickham", , "hadley@posit.co", role = "aut"), + person("Lionel", "Henry", , "lionel@posit.co", role = "aut"), + person("Davis", "Vaughan", , "davis@posit.co", role = c("aut", "cre")), + person("data.table team", role = "cph", + comment = "Radix sort based on data.table's forder() and their contribution to R's order()"), + person("Posit Software, PBC", role = c("cph", "fnd")) + ) +Description: Defines new notions of prototype and size that are used to + provide tools for consistent and well-founded type-coercion and + size-recycling, and are in turn connected to ideas of type- and size-stability useful for analysing function interfaces. License: MIT + file LICENSE URL: https://vctrs.r-lib.org/, https://github.com/r-lib/vctrs @@ -45,15 +35,15 @@ Suggests: rmarkdown, testthat (>= 3.0.0), tibble (>= 3.1.3), + waldo (>= 0.2.0), withr, xml2, - waldo (>= 0.2.0), zeallot VignetteBuilder: knitr +Config/Needs/website: tidyverse/tidytemplate +Config/testthat/edition: 3 Encoding: UTF-8 Language: en-GB Roxygen: list(markdown = TRUE) RoxygenNote: 7.2.3 -Config/testthat/edition: 3 -Config/Needs/website: tidyverse/tidytemplate From f810b9ebf790aeae3e2b9be3a3af60b3c5c40331 Mon Sep 17 00:00:00 2001 From: Davis Vaughan Date: Wed, 22 Mar 2023 11:00:16 -0400 Subject: [PATCH 272/312] RC 0.6.1 (#1820) * Update `cran-comments.md` * Increment version number to 0.6.1 * CRAN-SUBMISSION * Delete CRAN-SUBMISSION --- DESCRIPTION | 2 +- NEWS.md | 2 +- cran-comments.md | 12 ++---------- src/version.c | 2 +- 4 files changed, 5 insertions(+), 13 deletions(-) diff --git a/DESCRIPTION b/DESCRIPTION index 5fe509af1..1e7e398df 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -1,6 +1,6 @@ Package: vctrs Title: Vector Helpers -Version: 0.6.0.9000 +Version: 0.6.1 Authors@R: c( person("Hadley", "Wickham", , "hadley@posit.co", role = "aut"), person("Lionel", "Henry", , "lionel@posit.co", role = "aut"), diff --git a/NEWS.md b/NEWS.md index e171659d2..d259315a7 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,4 +1,4 @@ -# vctrs (development version) +# vctrs 0.6.1 * Fixed a test related to `c.sfc()` changes in sf 1.0-10 (#1817). diff --git a/cran-comments.md b/cran-comments.md index 53957236c..de2aae033 100644 --- a/cran-comments.md +++ b/cran-comments.md @@ -1,11 +1,3 @@ -This is a minor release with no expected breakage of any reverse dependencies. +This is a patch release with no expected breakage of any reverse dependencies. -We fixed the CRAN check result failures, in particular: -- We removed `SystemRequirements: C++11`. -- We fixed the S3 method inconsistencies for `cnd_header()` and `cnd_body()`. - -The following reverse dependencies showed up in our checks, but we believe they are false alarms: -- GenomeAdmixR: Can't reproduce locally. -- portalr: A common failing package that we see. Likely related to a failed download. -- openalexR: A common failing package that we see. Likely related to a failed download. -- rapbase: Likely related to a failed download from GitHub. +We fixed the failing tests related to sf. diff --git a/src/version.c b/src/version.c index f37dd8303..e4c74782e 100644 --- a/src/version.c +++ b/src/version.c @@ -1,7 +1,7 @@ #define R_NO_REMAP #include -const char* vctrs_version = "0.6.0.9000"; +const char* vctrs_version = "0.6.1"; /** * This file records the expected package version in the shared From af29ad75632c30c45ad99301918d95e9b396f3b3 Mon Sep 17 00:00:00 2001 From: DavisVaughan Date: Wed, 22 Mar 2023 11:01:29 -0400 Subject: [PATCH 273/312] Increment version number to 0.6.1.9000 --- DESCRIPTION | 2 +- NEWS.md | 2 ++ src/version.c | 2 +- 3 files changed, 4 insertions(+), 2 deletions(-) diff --git a/DESCRIPTION b/DESCRIPTION index 1e7e398df..de3781742 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -1,6 +1,6 @@ Package: vctrs Title: Vector Helpers -Version: 0.6.1 +Version: 0.6.1.9000 Authors@R: c( person("Hadley", "Wickham", , "hadley@posit.co", role = "aut"), person("Lionel", "Henry", , "lionel@posit.co", role = "aut"), diff --git a/NEWS.md b/NEWS.md index d259315a7..a260cfc99 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,3 +1,5 @@ +# vctrs (development version) + # vctrs 0.6.1 * Fixed a test related to `c.sfc()` changes in sf 1.0-10 (#1817). diff --git a/src/version.c b/src/version.c index e4c74782e..a43271232 100644 --- a/src/version.c +++ b/src/version.c @@ -1,7 +1,7 @@ #define R_NO_REMAP #include -const char* vctrs_version = "0.6.1"; +const char* vctrs_version = "0.6.1.9000"; /** * This file records the expected package version in the shared From 77f56221f8d70504f28ba0a1144d4ebd9c24f6d6 Mon Sep 17 00:00:00 2001 From: Michael Chirico Date: Fri, 14 Apr 2023 02:56:28 -0400 Subject: [PATCH 274/312] Sync declaration and implementation signatures (#1827) And rename `class` to `cls` to avoid clashes with C++ keyword --- src/c.c | 10 ++--- src/decl/utils-dispatch-decl.h | 2 +- src/proxy-restore.c | 8 ++-- src/utils-dispatch.c | 12 +++--- src/utils.c | 74 +++++++++++++++++----------------- src/utils.h | 6 +-- 6 files changed, 56 insertions(+), 56 deletions(-) diff --git a/src/c.c b/src/c.c index 4265bb000..8d2062825 100644 --- a/src/c.c +++ b/src/c.c @@ -202,10 +202,10 @@ bool needs_vec_c_fallback(r_obj* ptype) { } // Suboptimal: Prevent infinite recursion through `vctrs_vctr` method - r_obj* class = r_attrib_get(ptype, syms_fallback_class); - class = r_chr_get(class, r_length(class) - 1); + r_obj* cls = r_attrib_get(ptype, syms_fallback_class); + cls = r_chr_get(cls, r_length(cls) - 1); - return class != strings_vctrs_vctr; + return cls != strings_vctrs_vctr; } bool needs_vec_c_homogeneous_fallback(r_obj* xs, r_obj* ptype) { @@ -272,8 +272,8 @@ r_obj* vec_c_fallback(r_obj* ptype, const struct name_repair_opts* name_repair, struct vctrs_arg* p_error_arg, struct r_lazy error_call) { - r_obj* class = KEEP(r_attrib_get(ptype, syms_fallback_class)); - bool implements_c = class_implements_base_c(class); + r_obj* cls = KEEP(r_attrib_get(ptype, syms_fallback_class)); + bool implements_c = class_implements_base_c(cls); FREE(1); if (implements_c) { diff --git a/src/decl/utils-dispatch-decl.h b/src/decl/utils-dispatch-decl.h index 743d558e6..1dd631cdd 100644 --- a/src/decl/utils-dispatch-decl.h +++ b/src/decl/utils-dispatch-decl.h @@ -1,7 +1,7 @@ enum vctrs_class_type class_type(r_obj* x); static -enum vctrs_class_type class_type_impl(r_obj* class); +enum vctrs_class_type class_type_impl(r_obj* cls); static const char* class_type_as_str(enum vctrs_class_type type); diff --git a/src/proxy-restore.c b/src/proxy-restore.c index 7e1ec67f3..b6cd48bab 100644 --- a/src/proxy-restore.c +++ b/src/proxy-restore.c @@ -80,7 +80,7 @@ r_obj* vec_restore_default(r_obj* x, r_obj* to, enum vctrs_owned owned) { // Shouldn't matter for GNU R but other R implementations might have checks. // Also record class to set it later with `r_attrib_poke()`. This restores // the OBJECT bit and is likely more compatible with other implementations. - r_obj* class = r_null; + r_obj* cls = r_null; { r_obj* node = attrib; @@ -94,7 +94,7 @@ r_obj* vec_restore_default(r_obj* x, r_obj* to, enum vctrs_owned owned) { tag == r_syms.dim_names || tag == r_syms.class_ || tag == r_syms.row_names) { if (tag == r_syms.class_) { - class = r_node_car(node); + cls = r_node_car(node); } if (prev == r_null) { @@ -144,8 +144,8 @@ r_obj* vec_restore_default(r_obj* x, r_obj* to, enum vctrs_owned owned) { FREE(1); } - if (class != r_null) { - r_attrib_poke(x, r_syms.class_, class); + if (cls != r_null) { + r_attrib_poke(x, r_syms.class_, cls); } if (is_s4) { diff --git a/src/utils-dispatch.c b/src/utils-dispatch.c index cb5d03217..7c86dd7d2 100644 --- a/src/utils-dispatch.c +++ b/src/utils-dispatch.c @@ -12,24 +12,24 @@ enum vctrs_class_type class_type(r_obj* x) { return VCTRS_CLASS_none; } - r_obj* class = KEEP(r_class(x)); + r_obj* cls = KEEP(r_class(x)); // Avoid corrupt objects where `x` is an object, but the class is NULL - if (class == r_null) { + if (cls == r_null) { FREE(1); return VCTRS_CLASS_none; } - enum vctrs_class_type type = class_type_impl(class); + enum vctrs_class_type type = class_type_impl(cls); FREE(1); return type; } static -enum vctrs_class_type class_type_impl(r_obj* class) { - int n = r_length(class); - r_obj* const* p = r_chr_cbegin(class); +enum vctrs_class_type class_type_impl(r_obj* cls) { + int n = r_length(cls); + r_obj* const* p = r_chr_cbegin(cls); // First check for bare types for which we know how many strings are // the classes composed of diff --git a/src/utils.c b/src/utils.c index fd4a8c0d4..5a7d1313b 100644 --- a/src/utils.c +++ b/src/utils.c @@ -35,7 +35,7 @@ static SEXP syms_as_data_frame2 = NULL; static SEXP fns_as_data_frame2 = NULL; -static SEXP vctrs_eval_mask_n_impl(SEXP fn_sym, SEXP fn, SEXP* syms, SEXP* args, SEXP mask); +static SEXP vctrs_eval_mask_n_impl(SEXP fn_sym, SEXP fn, SEXP* syms, SEXP* args, SEXP env); /** * Evaluate with masked arguments @@ -440,11 +440,11 @@ inline void never_reached(const char* fn) { static char s3_buf[200]; -SEXP s3_paste_method_sym(const char* generic, const char* class) { +SEXP s3_paste_method_sym(const char* generic, const char* cls) { int gen_len = strlen(generic); - int class_len = strlen(class); + int cls_len = strlen(cls); int dot_len = 1; - if (gen_len + class_len + dot_len >= sizeof(s3_buf)) { + if (gen_len + cls_len + dot_len >= sizeof(s3_buf)) { r_stop_internal("Generic or class name is too long."); } @@ -452,15 +452,15 @@ SEXP s3_paste_method_sym(const char* generic, const char* class) { memcpy(buf, generic, gen_len); buf += gen_len; *buf = '.'; ++buf; - memcpy(buf, class, class_len); buf += class_len; + memcpy(buf, cls, cls_len); buf += cls_len; *buf = '\0'; return Rf_install(s3_buf); } // First check in global env, then in method table -SEXP s3_get_method(const char* generic, const char* class, SEXP table) { - SEXP sym = s3_paste_method_sym(generic, class); +SEXP s3_get_method(const char* generic, const char* cls, SEXP table) { + SEXP sym = s3_paste_method_sym(generic, cls); return s3_sym_get_method(sym, table); } SEXP s3_sym_get_method(SEXP sym, SEXP table) { @@ -483,15 +483,15 @@ SEXP vctrs_s3_find_method(SEXP generic, SEXP x, SEXP table) { } // [[ register() ]] -r_obj* ffi_s3_get_method(r_obj* generic, r_obj* class, r_obj* table) { +r_obj* ffi_s3_get_method(r_obj* generic, r_obj* cls, r_obj* table) { if (!r_is_string(generic)) { r_stop_internal("`generic` must be a string"); } - if (!r_is_string(class)) { - r_stop_internal("`class` must be a string"); + if (!r_is_string(cls)) { + r_stop_internal("`cls` must be a string"); } return s3_get_method(r_chr_get_c_string(generic, 0), - r_chr_get_c_string(class, 0), + r_chr_get_c_string(cls, 0), table); } @@ -501,25 +501,25 @@ SEXP s3_find_method(const char* generic, SEXP x, SEXP table) { return R_NilValue; } - SEXP class = PROTECT(Rf_getAttrib(x, R_ClassSymbol)); - SEXP method = s3_class_find_method(generic, class, table); + SEXP cls = PROTECT(Rf_getAttrib(x, R_ClassSymbol)); + SEXP method = s3_class_find_method(generic, cls, table); UNPROTECT(1); return method; } // [[ include("utils.h") ]] -SEXP s3_class_find_method(const char* generic, SEXP class, SEXP table) { +SEXP s3_class_find_method(const char* generic, SEXP cls, SEXP table) { // Avoid corrupt objects where `x` is an OBJECT(), but the class is NULL - if (class == R_NilValue) { + if (cls == R_NilValue) { return R_NilValue; } - SEXP const* p_class = STRING_PTR_RO(class); - int n_class = Rf_length(class); + SEXP const* p_cls = STRING_PTR_RO(cls); + int n_cls = Rf_length(cls); - for (int i = 0; i < n_class; ++i) { - SEXP method = s3_get_method(generic, CHAR(p_class[i]), table); + for (int i = 0; i < n_cls; ++i) { + SEXP method = s3_get_method(generic, CHAR(p_cls[i]), table); if (method != R_NilValue) { return method; } @@ -530,28 +530,28 @@ SEXP s3_class_find_method(const char* generic, SEXP class, SEXP table) { // [[ include("utils.h") ]] SEXP s3_get_class(SEXP x) { - SEXP class = R_NilValue; + SEXP cls = R_NilValue; if (OBJECT(x)) { - class = Rf_getAttrib(x, R_ClassSymbol); + cls = Rf_getAttrib(x, R_ClassSymbol); } // This handles unclassed objects as well as gremlins objects where // `x` is an OBJECT(), but the class is NULL - if (class == R_NilValue) { - class = s3_bare_class(x); + if (cls == R_NilValue) { + cls = s3_bare_class(x); } - if (!Rf_length(class)) { + if (!Rf_length(cls)) { r_stop_internal("Class must have length."); } - return class; + return cls; } SEXP s3_get_class0(SEXP x) { - SEXP class = PROTECT(s3_get_class(x)); - SEXP out = STRING_ELT(class, 0); + SEXP cls = PROTECT(s3_get_class(x)); + SEXP out = STRING_ELT(cls, 0); UNPROTECT(1); return out; } @@ -586,9 +586,9 @@ SEXP s3_find_method2(const char* generic, SEXP x, SEXP table, SEXP* method_sym_out) { - SEXP class = PROTECT(s3_get_class0(x)); + SEXP cls = PROTECT(s3_get_class0(x)); - SEXP method_sym = s3_paste_method_sym(generic, CHAR(class)); + SEXP method_sym = s3_paste_method_sym(generic, CHAR(cls)); SEXP method = s3_sym_get_method(method_sym, table); if (method == R_NilValue) { @@ -621,8 +621,8 @@ SEXP s3_bare_class(SEXP x) { } } -static SEXP s4_get_method(const char* class, SEXP table) { - SEXP sym = Rf_install(class); +static SEXP s4_get_method(const char* cls, SEXP table) { + SEXP sym = Rf_install(cls); SEXP method = r_env_get(table, sym); if (r_is_function(method)) { @@ -638,20 +638,20 @@ SEXP s4_find_method(SEXP x, SEXP table) { return R_NilValue; } - SEXP class = PROTECT(Rf_getAttrib(x, R_ClassSymbol)); - SEXP out = s4_class_find_method(class, table); + SEXP cls = PROTECT(Rf_getAttrib(x, R_ClassSymbol)); + SEXP out = s4_class_find_method(cls, table); UNPROTECT(1); return out; } -SEXP s4_class_find_method(SEXP class, SEXP table) { +SEXP s4_class_find_method(SEXP cls, SEXP table) { // Avoid corrupt objects where `x` is an OBJECT(), but the class is NULL - if (class == R_NilValue) { + if (cls == R_NilValue) { return R_NilValue; } - SEXP const* p_class = STRING_PTR_RO(class); - int n_class = Rf_length(class); + SEXP const* p_class = STRING_PTR_RO(cls); + int n_class = Rf_length(cls); for (int i = 0; i < n_class; ++i) { SEXP method = s4_get_method(CHAR(p_class[i]), table); diff --git a/src/utils.h b/src/utils.h index 6988ef5ce..af39487a5 100644 --- a/src/utils.h +++ b/src/utils.h @@ -137,7 +137,7 @@ SEXP chr_resize(SEXP x, r_ssize x_size, r_ssize size); SEXP s3_get_method(const char* generic, const char* cls, SEXP table); SEXP s3_sym_get_method(SEXP sym, SEXP table); SEXP s3_find_method(const char* generic, SEXP x, SEXP table); -SEXP s3_class_find_method(const char* generic, SEXP class, SEXP table); +SEXP s3_class_find_method(const char* generic, SEXP cls, SEXP table); SEXP s3_get_class(SEXP x); SEXP s3_find_method_xy(const char* generic, SEXP x, @@ -151,7 +151,7 @@ SEXP s3_find_method2(const char* generic, SEXP s3_paste_method_sym(const char* generic, const char* cls); SEXP s3_bare_class(SEXP x); SEXP s4_find_method(SEXP x, SEXP table); -SEXP s4_class_find_method(SEXP class, SEXP table); +SEXP s4_class_find_method(SEXP cls, SEXP table); bool vec_implements_ptype2(SEXP x); SEXP r_env_get(SEXP env, SEXP sym); @@ -166,7 +166,7 @@ SEXP list_first_non_null(SEXP xs, R_len_t* non_null_i); bool list_is_homogeneously_classed(SEXP xs); // Destructive compacting -SEXP node_compact_d(SEXP xs); +SEXP node_compact_d(SEXP node); void never_reached(const char* fn) __attribute__((noreturn)); From d27033e02cd619449b8a27d737d5843392e06b67 Mon Sep 17 00:00:00 2001 From: Hadley Wickham Date: Fri, 14 Apr 2023 13:07:35 -0500 Subject: [PATCH 275/312] Test fixes for dev waldo (#1829) * Test fixes for dev waldo Which now actually compares the imaginary part of complex numbers, and flags NaN and NA_real_ as different * Just test type and missingness in weird `as.complex(NA_real_)` case In case it changes in base R in the future * NEWS bullet * Link to r-devel post --------- Co-authored-by: DavisVaughan --- NEWS.md | 2 ++ tests/testthat/test-set.R | 2 +- tests/testthat/test-type-bare.R | 27 +++++++++++++++++++-------- 3 files changed, 22 insertions(+), 9 deletions(-) diff --git a/NEWS.md b/NEWS.md index a260cfc99..c746cc977 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,5 +1,7 @@ # vctrs (development version) +* Fixed tests to maintain compatibility with the next version of waldo (#1829). + # vctrs 0.6.1 * Fixed a test related to `c.sfc()` changes in sf 1.0-10 (#1817). diff --git a/tests/testthat/test-set.R b/tests/testthat/test-set.R index 737ea2657..5ad9cc209 100644 --- a/tests/testthat/test-set.R +++ b/tests/testthat/test-set.R @@ -288,7 +288,7 @@ test_that("works with complex missing values", { imaginary = c(NA_real_, NaN, NA_real_, NaN) ) expect_identical(vec_set_symmetric_difference(na, na), complex()) - expect_identical(vec_set_symmetric_difference(na[-2], na[-4]), na[c(2, 4)]) + expect_identical(vec_set_symmetric_difference(na[-2], na[-4]), na[c(4, 2)]) }) test_that("works correctly with unspecified logical vectors", { diff --git a/tests/testthat/test-type-bare.R b/tests/testthat/test-type-bare.R index 7b6dd6048..64613b554 100644 --- a/tests/testthat/test-type-bare.R +++ b/tests/testthat/test-type-bare.R @@ -243,25 +243,36 @@ test_that("safe casts to complex works", { }) test_that("NA casts work as expected", { - exp <- cpl(NA) - to <- cpl() + expect_equal(vec_cast(lgl(NA), cpl()), NA_complex_) + expect_equal(vec_cast(int(NA), cpl()), NA_complex_) - expect_equal(vec_cast(lgl(NA), to), exp) - expect_equal(vec_cast(int(NA), to), exp) - expect_equal(vec_cast(dbl(NA), to), exp) + # TODO: Use our own cast routines here? + # `as.complex(NA_real_)` and `Rf_CoerceVector(NA_real_)` coerce to + # `complex(real = NA_real_, imaginary = 0)` for some reason, but this may + # change in the future https://stat.ethz.ch/pipermail/r-devel/2023-April/082545.html + # expect_equal(vec_cast(dbl(NA), cpl()), NA_complex_) + expect_type(vec_cast(dbl(NA), cpl()), "complex") + expect_identical(is.na(vec_cast(dbl(NA), cpl())), TRUE) # This used to be allowed - expect_error(vec_cast(list(NA), to), class = "vctrs_error_incompatible_type") + expect_error(vec_cast(list(NA), cpl()), class = "vctrs_error_incompatible_type") }) test_that("Shaped NA casts work as expected", { mat <- matrix - exp_mat <- mat(cpl(NA)) + exp_mat <- mat(NA_complex_) to_mat <- matrix(cpl()) expect_equal(vec_cast(mat(lgl(NA)), to_mat), exp_mat) expect_equal(vec_cast(mat(int(NA)), to_mat), exp_mat) - expect_equal(vec_cast(mat(dbl(NA)), to_mat), exp_mat) + + # TODO: Use our own cast routines here? + # `as.complex(NA_real_)` and `Rf_CoerceVector(NA_real_)` coerce to + # `complex(real = NA_real_, imaginary = 0)` for some reason, but this may + # change in the future https://stat.ethz.ch/pipermail/r-devel/2023-April/082545.html + # expect_equal(vec_cast(mat(dbl(NA)), to_mat), exp_mat) + expect_type(vec_cast(mat(dbl(NA)), to_mat), "complex") + expect_identical(is.na(vec_cast(mat(dbl(NA)), to_mat)), matrix(TRUE)) # This used to be allowed expect_error(vec_cast(mat(list(NA)), to_mat), class = "vctrs_error_incompatible_type") From 7c8efcb3dab8f9437eb3dc4bcbdc072c3e1946b6 Mon Sep 17 00:00:00 2001 From: DavisVaughan Date: Wed, 19 Apr 2023 09:31:29 -0400 Subject: [PATCH 276/312] Regenerate docs with CRAN versions of everything --- man/howto-faq-fix-scalar-type-error.Rd | 2 +- man/vector_recycling_rules.Rd | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/man/howto-faq-fix-scalar-type-error.Rd b/man/howto-faq-fix-scalar-type-error.Rd index eafdfddac..91f51cd3a 100644 --- a/man/howto-faq-fix-scalar-type-error.Rd +++ b/man/howto-faq-fix-scalar-type-error.Rd @@ -70,7 +70,7 @@ vctrs::obj_check_vector(my_df) This is problematic as many tidyverse functions won’t work properly: \if{html}{\out{
}}\preformatted{dplyr::slice(my_df, 1) -#> Error in `eval_select_impl()`: +#> Error in `vec_slice()`: #> ! `x` must be a vector, not a object. }\if{html}{\out{
}} diff --git a/man/vector_recycling_rules.Rd b/man/vector_recycling_rules.Rd index 269c89d84..b922747e9 100644 --- a/man/vector_recycling_rules.Rd +++ b/man/vector_recycling_rules.Rd @@ -30,7 +30,7 @@ This includes vectors of size 0: \if{html}{\out{
}}\preformatted{tibble(x = integer(), y = 1L) #> # A tibble: 0 x 2 -#> # ... with 2 variables: x , y +#> # i 2 variables: x , y }\if{html}{\out{
}} If vectors aren't size 1, they must all be the same size. Otherwise, an error From 482a6e480b5cf355663009142da49d5f8876b391 Mon Sep 17 00:00:00 2001 From: Davis Vaughan Date: Wed, 19 Apr 2023 14:18:37 -0400 Subject: [PATCH 277/312] Fix CRAN warning due to S3 conditional registration (#1832) * Manually register problematic methods * Change S3 `.` to an `_` to avoid CRAN warning on R >=4.3.0 * NEWS bullet --- NEWS.md | 3 ++ R/cast.R | 2 +- R/type-data-frame.R | 2 +- R/type-dplyr.R | 44 ++++++++++++------------ R/type-sf.R | 22 ++++++------ R/type-tibble.R | 12 +++---- R/zzz.R | 82 ++++++++++++++++++++++----------------------- 7 files changed, 85 insertions(+), 82 deletions(-) diff --git a/NEWS.md b/NEWS.md index c746cc977..bcfdead5e 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,5 +1,8 @@ # vctrs (development version) +* Fixed conditional S3 registration to avoid a CRAN check NOTE that appears in + R >=4.3.0 (#1832). + * Fixed tests to maintain compatibility with the next version of waldo (#1829). # vctrs 0.6.1 diff --git a/R/cast.R b/R/cast.R index d32e4fb17..9afce2035 100644 --- a/R/cast.R +++ b/R/cast.R @@ -240,6 +240,6 @@ is_bare_df <- function(x) { inherits_only(x, "data.frame") || inherits_only(x, c("tbl_df", "tbl", "data.frame")) } -is_informative_error.vctrs_error_cast_lossy <- function(x, ...) { +is_informative_error_vctrs_error_cast_lossy <- function(x, ...) { FALSE } diff --git a/R/type-data-frame.R b/R/type-data-frame.R index 2a57a4324..025850309 100644 --- a/R/type-data-frame.R +++ b/R/type-data-frame.R @@ -382,7 +382,7 @@ df_lossy_cast <- function(out, ) } -is_informative_error.vctrs_error_cast_lossy_dropped <- function(x, ...) { +is_informative_error_vctrs_error_cast_lossy_dropped <- function(x, ...) { FALSE } diff --git a/R/type-dplyr.R b/R/type-dplyr.R index 44a6ddcc1..ebbb5e294 100644 --- a/R/type-dplyr.R +++ b/R/type-dplyr.R @@ -8,7 +8,7 @@ group_intersect <- function(x, new) { intersect(dplyr::group_vars(x), names(new)) } -vec_restore.grouped_df <- function(x, to, ...) { +vec_restore_grouped_df <- function(x, to, ...) { vars <- group_intersect(to, x) drop <- dplyr::group_by_drop_default(to) dplyr::grouped_df(x, vars, drop = drop) @@ -17,21 +17,21 @@ vec_restore.grouped_df <- function(x, to, ...) { # `vec_ptype2()` ----------------------------------------------------- -vec_ptype2.grouped_df.grouped_df <- function(x, y, ...) { +vec_ptype2_grouped_df_grouped_df <- function(x, y, ...) { gdf_ptype2(x, y, ...) } -vec_ptype2.grouped_df.data.frame <- function(x, y, ...) { +vec_ptype2_grouped_df_data.frame <- function(x, y, ...) { gdf_ptype2(x, y, ...) } -vec_ptype2.data.frame.grouped_df <- function(x, y, ...) { +vec_ptype2_data.frame_grouped_df <- function(x, y, ...) { gdf_ptype2(x, y, ...) } -vec_ptype2.grouped_df.tbl_df <- function(x, y, ...) { +vec_ptype2_grouped_df_tbl_df <- function(x, y, ...) { gdf_ptype2(x, y, ...) } -vec_ptype2.tbl_df.grouped_df <- function(x, y, ...) { +vec_ptype2_tbl_df_grouped_df <- function(x, y, ...) { gdf_ptype2(x, y, ...) } @@ -50,21 +50,21 @@ gdf_ptype2 <- function(x, y, ...) { # `vec_cast()` ------------------------------------------------------- -vec_cast.grouped_df.grouped_df <- function(x, to, ...) { +vec_cast_grouped_df_grouped_df <- function(x, to, ...) { gdf_cast(x, to, ...) } -vec_cast.grouped_df.data.frame <- function(x, to, ...) { +vec_cast_grouped_df_data.frame <- function(x, to, ...) { gdf_cast(x, to, ...) } -vec_cast.data.frame.grouped_df <- function(x, to, ...) { +vec_cast_data.frame_grouped_df <- function(x, to, ...) { df_cast(x, to, ...) } -vec_cast.grouped_df.tbl_df <- function(x, to, ...) { +vec_cast_grouped_df_tbl_df <- function(x, to, ...) { gdf_cast(x, to, ...) } -vec_cast.tbl_df.grouped_df <- function(x, to, ...) { +vec_cast_tbl_df_grouped_df <- function(x, to, ...) { tib_cast(x, to, ...) } @@ -80,28 +80,28 @@ gdf_cast <- function(x, to, ...) { ### `rowwise` -------------------------------------------------------- -vec_restore.rowwise_df <- function(x, to, ...) { +vec_restore_rowwise_df <- function(x, to, ...) { dplyr::rowwise(x) } # `vec_ptype2()` ----------------------------------------------------- -vec_ptype2.rowwise_df.rowwise_df <- function(x, y, ...) { +vec_ptype2_rowwise_df_rowwise_df <- function(x, y, ...) { rww_ptype2(x, y, ...) } -vec_ptype2.rowwise_df.data.frame <- function(x, y, ...) { +vec_ptype2_rowwise_df_data.frame <- function(x, y, ...) { rww_ptype2(x, y, ...) } -vec_ptype2.data.frame.rowwise_df <- function(x, y, ...) { +vec_ptype2_data.frame_rowwise_df <- function(x, y, ...) { rww_ptype2(x, y, ...) } -vec_ptype2.rowwise_df.tbl_df <- function(x, y, ...) { +vec_ptype2_rowwise_df_tbl_df <- function(x, y, ...) { rww_ptype2(x, y, ...) } -vec_ptype2.tbl_df.rowwise_df <- function(x, y, ...) { +vec_ptype2_tbl_df_rowwise_df <- function(x, y, ...) { rww_ptype2(x, y, ...) } @@ -112,21 +112,21 @@ rww_ptype2 <- function(x, y, ...) { # `vec_cast()` ------------------------------------------------------- -vec_cast.rowwise_df.rowwise_df <- function(x, to, ...) { +vec_cast_rowwise_df_rowwise_df <- function(x, to, ...) { rww_cast(x, to, ...) } -vec_cast.rowwise_df.data.frame <- function(x, to, ...) { +vec_cast_rowwise_df_data.frame <- function(x, to, ...) { rww_cast(x, to, ...) } -vec_cast.data.frame.rowwise_df <- function(x, to, ...) { +vec_cast_data.frame_rowwise_df <- function(x, to, ...) { df_cast(x, to, ...) } -vec_cast.rowwise_df.tbl_df <- function(x, to, ...) { +vec_cast_rowwise_df_tbl_df <- function(x, to, ...) { rww_cast(x, to, ...) } -vec_cast.tbl_df.rowwise_df <- function(x, to, ...) { +vec_cast_tbl_df_rowwise_df <- function(x, to, ...) { tib_cast(x, to, ...) } diff --git a/R/type-sf.R b/R/type-sf.R index d64dc9c48..2954dea59 100644 --- a/R/type-sf.R +++ b/R/type-sf.R @@ -17,11 +17,11 @@ sf_env = env() local(envir = sf_env, { # Registered at load-time (same for all other methods) -vec_proxy.sf = function(x, ...) { +vec_proxy_sf = function(x, ...) { x } -vec_restore.sf = function(x, to, ...) { +vec_restore_sf = function(x, to, ...) { sfc_name = attr(to, "sf_column") crs = st_crs(to) prec = st_precision(to) @@ -76,22 +76,22 @@ sf_ptype2 = function(x, y, ...) { ) } -vec_ptype2.sf.sf = function(x, y, ...) { +vec_ptype2_sf_sf = function(x, y, ...) { sf_ptype2(x, y, ...) } -vec_ptype2.sf.data.frame = function(x, y, ...) { +vec_ptype2_sf_data.frame = function(x, y, ...) { sf_ptype2(x, y, ...) } -vec_ptype2.data.frame.sf = function(x, y, ...) { +vec_ptype2_data.frame_sf = function(x, y, ...) { sf_ptype2(x, y, ...) } # Maybe we should not have these methods, but they are currently # required to avoid the base-df fallback -vec_ptype2.sf.tbl_df = function(x, y, ...) { +vec_ptype2_sf_tbl_df = function(x, y, ...) { new_data_frame(sf_ptype2(x, y, ...)) } -vec_ptype2.tbl_df.sf = function(x, y, ...) { +vec_ptype2_tbl_df_sf = function(x, y, ...) { new_data_frame(sf_ptype2(x, y, ...)) } @@ -118,17 +118,17 @@ sf_cast = function(x, to, ...) { ) } -vec_cast.sf.sf = function(x, to, ...) { +vec_cast_sf_sf = function(x, to, ...) { sf_cast(x, to, ...) } -vec_cast.sf.data.frame = function(x, to, ...) { +vec_cast_sf_data.frame = function(x, to, ...) { sf_cast(x, to, ...) } -vec_cast.data.frame.sf = function(x, to, ...) { +vec_cast_data.frame_sf = function(x, to, ...) { df_cast(x, to, ...) } -vec_proxy_order.sfc <- function(x, ...) { +vec_proxy_order_sfc <- function(x, ...) { # These are list columns, so they need to use the order-by-appearance proxy # that is defined by `vec_proxy_order.list()` x <- unstructure(x) diff --git a/R/type-tibble.R b/R/type-tibble.R index 4a2759d4a..6241f1313 100644 --- a/R/type-tibble.R +++ b/R/type-tibble.R @@ -40,22 +40,22 @@ df_as_tibble <- function(df) { # Conditionally registered in .onLoad() -vec_ptype2.tbl_df.tbl_df <- function(x, y, ...) { +vec_ptype2_tbl_df_tbl_df <- function(x, y, ...) { vec_ptype2_dispatch_native(x, y, ...) } -vec_ptype2.tbl_df.data.frame <- function(x, y, ...) { +vec_ptype2_tbl_df_data.frame <- function(x, y, ...) { vec_ptype2_dispatch_native(x, y, ...) } -vec_ptype2.data.frame.tbl_df <- function(x, y, ...) { +vec_ptype2_data.frame_tbl_df <- function(x, y, ...) { vec_ptype2_dispatch_native(x, y, ...) } -vec_cast.tbl_df.tbl_df <- function(x, to, ...) { +vec_cast_tbl_df_tbl_df <- function(x, to, ...) { vec_cast_dispatch_native(x, to, ...) } -vec_cast.data.frame.tbl_df <- function(x, to, ...) { +vec_cast_data.frame_tbl_df <- function(x, to, ...) { vec_cast_dispatch_native(x, to, ...) } -vec_cast.tbl_df.data.frame <- function(x, to, ...) { +vec_cast_tbl_df_data.frame <- function(x, to, ...) { vec_cast_dispatch_native(x, to, ...) } diff --git a/R/zzz.R b/R/zzz.R index fa521f5f4..989fb07bc 100644 --- a/R/zzz.R +++ b/R/zzz.R @@ -7,8 +7,8 @@ run_on_load() on_package_load("testthat", { - s3_register("testthat::is_informative_error", "vctrs_error_cast_lossy") - s3_register("testthat::is_informative_error", "vctrs_error_cast_lossy_dropped") + s3_register("testthat::is_informative_error", "vctrs_error_cast_lossy", is_informative_error_vctrs_error_cast_lossy) + s3_register("testthat::is_informative_error", "vctrs_error_cast_lossy_dropped", is_informative_error_vctrs_error_cast_lossy_dropped) }) s3_register("generics::as.factor", "vctrs_vctr") @@ -18,57 +18,57 @@ # Remove once tibble has implemented the methods on_package_load("tibble", { if (!env_has(ns_env("tibble"), "vec_ptype2.tbl_df.tbl_df")) { - s3_register("vctrs::vec_ptype2", "tbl_df.tbl_df") - s3_register("vctrs::vec_ptype2", "tbl_df.data.frame") - s3_register("vctrs::vec_ptype2", "data.frame.tbl_df") + s3_register("vctrs::vec_ptype2", "tbl_df.tbl_df", vec_ptype2_tbl_df_tbl_df) + s3_register("vctrs::vec_ptype2", "tbl_df.data.frame", vec_ptype2_tbl_df_data.frame) + s3_register("vctrs::vec_ptype2", "data.frame.tbl_df", vec_ptype2_data.frame_tbl_df) } if (!env_has(ns_env("tibble"), "vec_cast.tbl_df.tbl_df")) { - s3_register("vctrs::vec_cast", "tbl_df.tbl_df") - s3_register("vctrs::vec_cast", "tbl_df.data.frame") - s3_register("vctrs::vec_cast", "data.frame.tbl_df") + s3_register("vctrs::vec_cast", "tbl_df.tbl_df", vec_cast_tbl_df_tbl_df) + s3_register("vctrs::vec_cast", "tbl_df.data.frame", vec_cast_tbl_df_data.frame) + s3_register("vctrs::vec_cast", "data.frame.tbl_df", vec_cast_data.frame_tbl_df) } }) on_package_load("dplyr", { if (!env_has(ns_env("dplyr"), "vec_restore.grouped_df")) { - s3_register("vctrs::vec_restore", "grouped_df") + s3_register("vctrs::vec_restore", "grouped_df", vec_restore_grouped_df) } if (!env_has(ns_env("dplyr"), "vec_ptype2.grouped_df.grouped_df")) { - s3_register("vctrs::vec_ptype2", "grouped_df.grouped_df") - s3_register("vctrs::vec_ptype2", "grouped_df.data.frame") - s3_register("vctrs::vec_ptype2", "grouped_df.tbl_df") - s3_register("vctrs::vec_ptype2", "data.frame.grouped_df") - s3_register("vctrs::vec_ptype2", "tbl_df.grouped_df") + s3_register("vctrs::vec_ptype2", "grouped_df.grouped_df", vec_ptype2_grouped_df_grouped_df) + s3_register("vctrs::vec_ptype2", "grouped_df.data.frame", vec_ptype2_grouped_df_data.frame) + s3_register("vctrs::vec_ptype2", "grouped_df.tbl_df", vec_ptype2_grouped_df_tbl_df) + s3_register("vctrs::vec_ptype2", "data.frame.grouped_df", vec_ptype2_data.frame_grouped_df) + s3_register("vctrs::vec_ptype2", "tbl_df.grouped_df", vec_ptype2_tbl_df_grouped_df) } if (!env_has(ns_env("dplyr"), "vec_cast.grouped_df.grouped_df")) { - s3_register("vctrs::vec_cast", "grouped_df.grouped_df") - s3_register("vctrs::vec_cast", "grouped_df.data.frame") - s3_register("vctrs::vec_cast", "grouped_df.tbl_df") - s3_register("vctrs::vec_cast", "data.frame.grouped_df") - s3_register("vctrs::vec_cast", "tbl_df.grouped_df") + s3_register("vctrs::vec_cast", "grouped_df.grouped_df", vec_cast_grouped_df_grouped_df) + s3_register("vctrs::vec_cast", "grouped_df.data.frame", vec_cast_grouped_df_data.frame) + s3_register("vctrs::vec_cast", "grouped_df.tbl_df", vec_cast_grouped_df_tbl_df) + s3_register("vctrs::vec_cast", "data.frame.grouped_df", vec_cast_data.frame_grouped_df) + s3_register("vctrs::vec_cast", "tbl_df.grouped_df", vec_cast_tbl_df_grouped_df) } if (!env_has(ns_env("dplyr"), "vec_restore.rowwise_df")) { - s3_register("vctrs::vec_restore", "rowwise_df") + s3_register("vctrs::vec_restore", "rowwise_df", vec_restore_rowwise_df) } if (!env_has(ns_env("dplyr"), "vec_ptype2.rowwise_df.rowwise_df")) { - s3_register("vctrs::vec_ptype2", "rowwise_df.rowwise_df") - s3_register("vctrs::vec_ptype2", "rowwise_df.data.frame") - s3_register("vctrs::vec_ptype2", "rowwise_df.tbl_df") - s3_register("vctrs::vec_ptype2", "data.frame.rowwise_df") - s3_register("vctrs::vec_ptype2", "tbl_df.rowwise_df") + s3_register("vctrs::vec_ptype2", "rowwise_df.rowwise_df", vec_ptype2_rowwise_df_rowwise_df) + s3_register("vctrs::vec_ptype2", "rowwise_df.data.frame", vec_ptype2_rowwise_df_data.frame) + s3_register("vctrs::vec_ptype2", "rowwise_df.tbl_df", vec_ptype2_rowwise_df_tbl_df) + s3_register("vctrs::vec_ptype2", "data.frame.rowwise_df", vec_ptype2_data.frame_rowwise_df) + s3_register("vctrs::vec_ptype2", "tbl_df.rowwise_df", vec_ptype2_tbl_df_rowwise_df) } if (!env_has(ns_env("dplyr"), "vec_cast.rowwise_df.rowwise_df")) { - s3_register("vctrs::vec_cast", "rowwise_df.rowwise_df") - s3_register("vctrs::vec_cast", "rowwise_df.data.frame") - s3_register("vctrs::vec_cast", "rowwise_df.tbl_df") - s3_register("vctrs::vec_cast", "data.frame.rowwise_df") - s3_register("vctrs::vec_cast", "tbl_df.rowwise_df") + s3_register("vctrs::vec_cast", "rowwise_df.rowwise_df", vec_cast_rowwise_df_rowwise_df) + s3_register("vctrs::vec_cast", "rowwise_df.data.frame", vec_cast_rowwise_df_data.frame) + s3_register("vctrs::vec_cast", "rowwise_df.tbl_df", vec_cast_rowwise_df_tbl_df) + s3_register("vctrs::vec_cast", "data.frame.rowwise_df", vec_cast_data.frame_rowwise_df) + s3_register("vctrs::vec_cast", "tbl_df.rowwise_df", vec_cast_tbl_df_rowwise_df) } }) @@ -76,21 +76,21 @@ import_from("sf", sf_deps, env = sf_env) if (!env_has(ns_env("sf"), "vec_restore.sf")) { - s3_register("vctrs::vec_proxy", "sf") - s3_register("vctrs::vec_restore", "sf") + s3_register("vctrs::vec_proxy", "sf", vec_proxy_sf) + s3_register("vctrs::vec_restore", "sf", vec_restore_sf) } if (!env_has(ns_env("sf"), "vec_ptype2.sf.sf")) { - s3_register("vctrs::vec_ptype2", "sf.sf") - s3_register("vctrs::vec_ptype2", "sf.data.frame") - s3_register("vctrs::vec_ptype2", "data.frame.sf") - s3_register("vctrs::vec_ptype2", "sf.tbl_df") - s3_register("vctrs::vec_ptype2", "tbl_df.sf") - s3_register("vctrs::vec_cast", "sf.sf") - s3_register("vctrs::vec_cast", "sf.data.frame") - s3_register("vctrs::vec_cast", "data.frame.sf") + s3_register("vctrs::vec_ptype2", "sf.sf", vec_ptype2_sf_sf) + s3_register("vctrs::vec_ptype2", "sf.data.frame", vec_ptype2_sf_data.frame) + s3_register("vctrs::vec_ptype2", "data.frame.sf", vec_ptype2_data.frame_sf) + s3_register("vctrs::vec_ptype2", "sf.tbl_df", vec_ptype2_sf_tbl_df) + s3_register("vctrs::vec_ptype2", "tbl_df.sf", vec_ptype2_tbl_df_sf) + s3_register("vctrs::vec_cast", "sf.sf", vec_cast_sf_sf) + s3_register("vctrs::vec_cast", "sf.data.frame", vec_cast_sf_data.frame) + s3_register("vctrs::vec_cast", "data.frame.sf", vec_cast_data.frame_sf) } if (!env_has(ns_env("sf"), "vec_proxy_order.sfc")) { - s3_register("vctrs::vec_proxy_order", "sfc") + s3_register("vctrs::vec_proxy_order", "sfc", vec_proxy_order_sfc) } }) From 9455e2ed016dbfed4f4638d21d6edcfe670d2bab Mon Sep 17 00:00:00 2001 From: Davis Vaughan Date: Wed, 19 Apr 2023 16:00:30 -0400 Subject: [PATCH 278/312] RC 0.6.2 (#1831) * Update cran comments * Increment version number to 0.6.2 * CRAN-SUBMISSION * CRAN-SUBMISSION * Delete CRAN-SUBMISSION --- DESCRIPTION | 2 +- NEWS.md | 2 +- cran-comments.md | 2 +- src/version.c | 2 +- 4 files changed, 4 insertions(+), 4 deletions(-) diff --git a/DESCRIPTION b/DESCRIPTION index de3781742..d79fb8de6 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -1,6 +1,6 @@ Package: vctrs Title: Vector Helpers -Version: 0.6.1.9000 +Version: 0.6.2 Authors@R: c( person("Hadley", "Wickham", , "hadley@posit.co", role = "aut"), person("Lionel", "Henry", , "lionel@posit.co", role = "aut"), diff --git a/NEWS.md b/NEWS.md index bcfdead5e..9e7cc5be5 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,4 +1,4 @@ -# vctrs (development version) +# vctrs 0.6.2 * Fixed conditional S3 registration to avoid a CRAN check NOTE that appears in R >=4.3.0 (#1832). diff --git a/cran-comments.md b/cran-comments.md index de2aae033..5831e7cf8 100644 --- a/cran-comments.md +++ b/cran-comments.md @@ -1,3 +1,3 @@ This is a patch release with no expected breakage of any reverse dependencies. -We fixed the failing tests related to sf. +We are maintaining compatibility with an upcoming release of waldo. diff --git a/src/version.c b/src/version.c index a43271232..8340f3b38 100644 --- a/src/version.c +++ b/src/version.c @@ -1,7 +1,7 @@ #define R_NO_REMAP #include -const char* vctrs_version = "0.6.1.9000"; +const char* vctrs_version = "0.6.2"; /** * This file records the expected package version in the shared From c27b6988bd2f02aa970b6d14a640eccb299e03bb Mon Sep 17 00:00:00 2001 From: DavisVaughan Date: Wed, 19 Apr 2023 16:01:31 -0400 Subject: [PATCH 279/312] Increment version number to 0.6.2.9000 --- DESCRIPTION | 2 +- NEWS.md | 2 ++ src/version.c | 2 +- 3 files changed, 4 insertions(+), 2 deletions(-) diff --git a/DESCRIPTION b/DESCRIPTION index d79fb8de6..b3fee10f3 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -1,6 +1,6 @@ Package: vctrs Title: Vector Helpers -Version: 0.6.2 +Version: 0.6.2.9000 Authors@R: c( person("Hadley", "Wickham", , "hadley@posit.co", role = "aut"), person("Lionel", "Henry", , "lionel@posit.co", role = "aut"), diff --git a/NEWS.md b/NEWS.md index 9e7cc5be5..e16b80dfd 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,3 +1,5 @@ +# vctrs (development version) + # vctrs 0.6.2 * Fixed conditional S3 registration to avoid a CRAN check NOTE that appears in diff --git a/src/version.c b/src/version.c index 8340f3b38..779c08a37 100644 --- a/src/version.c +++ b/src/version.c @@ -1,7 +1,7 @@ #define R_NO_REMAP #include -const char* vctrs_version = "0.6.2"; +const char* vctrs_version = "0.6.2.9000"; /** * This file records the expected package version in the shared From 8af47522399e449e16dbddb1c9b4676c2c143c5f Mon Sep 17 00:00:00 2001 From: Davis Vaughan Date: Thu, 27 Apr 2023 11:25:54 -0400 Subject: [PATCH 280/312] Use alternate `any_multiple_needles` detection (#1835) * Use alternate `any_multiple_needles` detection We can't use the simple `loc < size_needles` check to see if we are in the "extra" match section. When a filter is involved, that isn't enough because we could have filtered out a match that occurred before the extra matches, so the extra match could actually be the first one. * NEWS bullet --- NEWS.md | 3 ++ src/match.c | 22 +++++++++++--- tests/testthat/_snaps/match.md | 10 +++++++ tests/testthat/test-match.R | 53 ++++++++++++++++++++++++++++++++++ 4 files changed, 84 insertions(+), 4 deletions(-) diff --git a/NEWS.md b/NEWS.md index e16b80dfd..dfc849654 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,5 +1,8 @@ # vctrs (development version) +* Fixed a rare `vec_locate_matches()` bug that could occur when using a max/min + `filter` (tidyverse/dplyr#6835). + # vctrs 0.6.2 * Fixed conditional S3 registration to avoid a CRAN check NOTE that appears in diff --git a/src/match.c b/src/match.c index 548e846df..caad346da 100644 --- a/src/match.c +++ b/src/match.c @@ -1684,6 +1684,9 @@ r_obj* expand_compact_indices(const int* v_o_haystack, multiple == VCTRS_MULTIPLE_error || multiple == VCTRS_MULTIPLE_warning; + // Used to enforce `check_multiple_needles` + r_ssize loc_needles_previous = r_globals.na_int; + bool check_multiple_haystack = false; switch (relationship) { // Expecting `haystack` can match any number of `needles` @@ -1824,11 +1827,22 @@ r_obj* expand_compact_indices(const int* v_o_haystack, } if (check_multiple_needles) { - if (loc < size_needles) { - any_multiple_needles = size_match > 1; - } else { - // Guaranteed second match if in the "extra" matches section + if (size_match > 1) { + // Easy, obvious, case. + // This containment group had >1 matches for this `needle` so we + // immediately handle multiple `needles` matches. any_multiple_needles = true; + } else if (loc_needles == loc_needles_previous) { + // We've recorded a match for this `needle` before. Remember that + // `needles` are processed in increasing order across all containment + // groups due to `v_o_loc_needles` so this simple tracking of the + // previous `needle` works. + any_multiple_needles = true; + } else { + // There was exactly 1 match for the `needle` in this containment group, + // and we've never recorded a match for this `needle` before. + // In that case we record that we've seen it for the next iteration. + loc_needles_previous = loc_needles; } if (any_multiple_needles) { diff --git a/tests/testthat/_snaps/match.md b/tests/testthat/_snaps/match.md index 37d0077dc..ee88db809 100644 --- a/tests/testthat/_snaps/match.md +++ b/tests/testthat/_snaps/match.md @@ -424,6 +424,16 @@ ! Each value of `needles` can match at most 1 value from `haystack`. x Location 1 of `needles` matches multiple values. +# `relationship` errors when we have >1 size 1 matches across containers (tidyverse/dplyr#6835) + + Code + vec_locate_matches(x, y, condition = c("<=", ">="), filter = c("none", "none"), + relationship = "one-to-one") + Condition + Error in `vec_locate_matches()`: + ! Each value of `needles` can match at most 1 value from `haystack`. + x Location 1 of `needles` matches multiple values. + # `relationship` errors respect argument tags and error call Code diff --git a/tests/testthat/test-match.R b/tests/testthat/test-match.R index ca8c52ccc..963e7edc4 100644 --- a/tests/testthat/test-match.R +++ b/tests/testthat/test-match.R @@ -1312,6 +1312,59 @@ test_that("`relationship` still errors if `filter` hasn't removed all multiple m expect_identical(out$haystack, c(2L, 2L)) }) +test_that("`relationship` errors when we have >1 size 1 matches across containers (tidyverse/dplyr#6835)", { + # Carefully designed to ensure we get 2 nested containment groups that split + # up the rows of `y`, but each of the nested containment groups contain exactly + # 1 match, so `size_match` in `expand_compact_indices()` won't ever be >1 + x <- data_frame(a = 1L, b = 5L) + y <- data_frame(a = c(1L, 2L), b = c(4L, 3L)) + + expect_snapshot(error = TRUE, { + vec_locate_matches( + x, + y, + condition = c("<=", ">="), + filter = c("none", "none"), + relationship = "one-to-one" + ) + }) +}) + +test_that("`relationship` doesn't error when the first match from a different container gets filtered out (tidyverse/dplyr#6835)", { + # Carefully designed to ensure we get 2 nested containment groups that split + # up the rows of `y`. Row 1 (processed first) doesn't hold the minimum `b` + # value, so it gets filtered out. Row 2 is in the "extra" matches section + # but is actually the first (and only) real match, so we don't want to error + # on it. + x <- data_frame(a = 1L, b = 5L) + y <- data_frame(a = c(1L, 2L), b = c(4L, 3L)) + + out <- vec_locate_matches( + x, + y, + condition = c("<=", ">="), + filter = c("none", "min"), + relationship = "one-to-one" + ) + expect_identical(out$needles, 1L) + expect_identical(out$haystack, 2L) + + # Similar to the above example, but with a `max` filter. Row 1 doesn't hold + # the max `c` value so it is filtered out even though it is a `>=` match. + x <- data_frame(a = 1L, b = 5L, c = 3L) + y <- data_frame(a = c(1L, 2L), b = c(4L, 3L), c = c(1L, 2L)) + + out <- vec_locate_matches( + x, + y, + condition = c("<=", ">=", ">="), + filter = c("none", "none", "max"), + relationship = "one-to-one" + ) + expect_identical(out$needles, 1L) + expect_identical(out$haystack, 2L) +}) + test_that("`relationship` errors respect argument tags and error call", { expect_snapshot({ (expect_error(vec_locate_matches(1L, c(1L, 1L), relationship = "one-to-one", needles_arg = "foo", haystack_arg = "bar", error_call = call("fn")))) From ae010ea72dbeaae79828147e4b24bd1402ba4ef7 Mon Sep 17 00:00:00 2001 From: Davis Vaughan Date: Tue, 9 May 2023 09:35:30 -0400 Subject: [PATCH 281/312] Unconditionally clone in `df_proxy()` (#1838) * Unconditionally clone in `df_proxy()` * NEWS bullet --- NEWS.md | 4 ++++ src/proxy.c | 5 ++++- tests/testthat/test-set.R | 14 ++++++++++++++ 3 files changed, 22 insertions(+), 1 deletion(-) diff --git a/NEWS.md b/NEWS.md index dfc849654..65f015612 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,5 +1,9 @@ # vctrs (development version) +* Fixed an issue where `vec_set_*()` used with data frames could accidentally + return an object with the type of the proxy rather than the type of the + original inputs (#1837). + * Fixed a rare `vec_locate_matches()` bug that could occur when using a max/min `filter` (tidyverse/dplyr#6835). diff --git a/src/proxy.c b/src/proxy.c index d7bd89865..b17ea8365 100644 --- a/src/proxy.c +++ b/src/proxy.c @@ -215,7 +215,10 @@ r_obj* vec_proxy_order_invoke(r_obj* x, r_obj* method) { static inline r_obj* df_proxy(r_obj* x, enum vctrs_proxy_kind kind) { - x = KEEP(r_clone_referenced(x)); + // Always clone to avoid modifying the original object, even if it is one + // we freshly created in C, because we often work with both the proxy and the + // original object within the same function (#1837) + x = KEEP(r_clone(x)); switch (kind) { case VCTRS_PROXY_KIND_equal: DF_PROXY(vec_proxy_equal); break; diff --git a/tests/testthat/test-set.R b/tests/testthat/test-set.R index 5ad9cc209..7eb47287e 100644 --- a/tests/testthat/test-set.R +++ b/tests/testthat/test-set.R @@ -341,6 +341,20 @@ test_that("works with rcrds", { # common ------------------------------------------------------------------ +test_that("works with package version columns of data frames (#1837)", { + package_frame <- function(x) { + data_frame(version = package_version(x)) + } + + x <- package_frame(c("4.0", "2.0")) + y <- package_frame(c("1.0", "3.0" ,"4.0")) + + expect_identical(vec_set_intersect(x, y), package_frame("4.0")) + expect_identical(vec_set_difference(x, y), package_frame("2.0")) + expect_identical(vec_set_union(x, y), package_frame(c("4.0", "2.0", "1.0", "3.0"))) + expect_identical(vec_set_symmetric_difference(x, y), package_frame(c("2.0", "1.0", "3.0"))) +}) + test_that("errors nicely if common type can't be taken", { expect_snapshot(error = TRUE, { vec_set_intersect(1, "x") From b4dd85237ee8feab09e0eb634ac57bf26469bf91 Mon Sep 17 00:00:00 2001 From: DavisVaughan Date: Wed, 7 Jun 2023 16:53:59 -0400 Subject: [PATCH 282/312] Allow user supplied `row.names` to fully override `n` --- R/type-data-frame.R | 9 ++++---- man/new_data_frame.Rd | 10 ++++----- src/decl/type-data-frame-decl.h | 3 --- src/type-data-frame.c | 32 +++++++++++---------------- tests/testthat/test-type-data-frame.R | 12 ++++++++-- 5 files changed, 32 insertions(+), 34 deletions(-) diff --git a/R/type-data-frame.R b/R/type-data-frame.R index 025850309..12d29cbbd 100644 --- a/R/type-data-frame.R +++ b/R/type-data-frame.R @@ -16,12 +16,11 @@ #' @param n Number of rows. If `NULL`, will be computed from the length of #' the first element of `x`. #' @param ...,class Additional arguments for creating subclasses. -#' The `"names"` and `"row.names"` attributes override input in `x` and `n`, -#' respectively: #' -#' - `"names"` is used if provided, overriding existing names in `x` -#' - `"row.names"` is used if provided, if `n` is provided it must be -#' consistent. +#' The following attributes have special behavior: +#' - `"names"` is preferred if provided, overriding existing names in `x`. +#' - `"row.names"` is preferred if provided, overriding both `n` and the size +#' implied by `x`. #' #' @export #' @examples diff --git a/man/new_data_frame.Rd b/man/new_data_frame.Rd index 59c1e64ca..48192ab2e 100644 --- a/man/new_data_frame.Rd +++ b/man/new_data_frame.Rd @@ -15,12 +15,12 @@ equal.} the first element of \code{x}.} \item{..., class}{Additional arguments for creating subclasses. -The \code{"names"} and \code{"row.names"} attributes override input in \code{x} and \code{n}, -respectively: + +The following attributes have special behavior: \itemize{ -\item \code{"names"} is used if provided, overriding existing names in \code{x} -\item \code{"row.names"} is used if provided, if \code{n} is provided it must be -consistent. +\item \code{"names"} is preferred if provided, overriding existing names in \code{x}. +\item \code{"row.names"} is preferred if provided, overriding both \code{n} and the size +implied by \code{x}. }} } \description{ diff --git a/src/decl/type-data-frame-decl.h b/src/decl/type-data-frame-decl.h index e9677c2db..52521b281 100644 --- a/src/decl/type-data-frame-decl.h +++ b/src/decl/type-data-frame-decl.h @@ -4,9 +4,6 @@ static r_obj* fns_df_lossy_cast; static r_obj* new_compact_rownames(r_ssize n); -static -r_ssize df_size_from_list(r_obj* x, r_obj* n); - static r_ssize df_size_from_n(r_obj* n); diff --git a/src/type-data-frame.c b/src/type-data-frame.c index d8d099db0..1e4c2d8de 100644 --- a/src/type-data-frame.c +++ b/src/type-data-frame.c @@ -50,7 +50,6 @@ r_obj* ffi_new_data_frame(r_obj* args) { bool has_names = false; bool has_rownames = false; - r_ssize size = df_size_from_list(x, n); r_obj* out = KEEP(r_clone_referenced(x)); @@ -68,11 +67,12 @@ r_obj* ffi_new_data_frame(r_obj* args) { } if (tag == r_syms.row_names) { - // "row.names" is checked for consistency with n (if provided) - if (size != rownames_size(r_node_car(node)) && n != r_null) { - r_abort_call(r_null, "`n` and `row.names` must be consistent."); - } - + // We used to validate a user supplied `n` against a user supplied + // `row.names`, but that requires extracting out the `rownames_size()`, + // which can materialize ALTREP row name objects and is prohibitively + // expensive (tidyverse/dplyr#6596). So instead we say that user supplied + // `row.names` overrides both the implied size of `x` and a user supplied + // `n`, even if they are incompatible. has_rownames = true; continue; } @@ -96,6 +96,13 @@ r_obj* ffi_new_data_frame(r_obj* args) { } if (!has_rownames) { + // Data frame size is determined in the following order: + // - By `row.names`, if provided, which will already be in `attrib` + // - By `n`, if provided (this is fully overriden by `row.names`) + // - By `x`, if neither `n` nor `row.names` is provided, where `x` could be + // a data frame with its own row names attribute or a bare list + const r_ssize size = n != r_null ? df_size_from_n(n) : df_raw_size(x); + r_obj* rn = KEEP(new_compact_rownames(size)); attrib = r_new_node(rn, attrib); r_node_poke_tag(attrib, r_syms.row_names); @@ -125,19 +132,6 @@ r_obj* ffi_new_data_frame(r_obj* args) { return out; } -static -r_ssize df_size_from_list(r_obj* x, r_obj* n) { - if (n == r_null) { - if (is_data_frame(x)) { - return df_size(x); - } else { - return df_raw_size_from_list(x); - } - } else { - return df_size_from_n(n); - } -} - static r_ssize df_size_from_n(r_obj* n) { if (r_typeof(n) != R_TYPE_integer || r_length(n) != 1) { diff --git a/tests/testthat/test-type-data-frame.R b/tests/testthat/test-type-data-frame.R index df4de80e9..2f5b0a535 100644 --- a/tests/testthat/test-type-data-frame.R +++ b/tests/testthat/test-type-data-frame.R @@ -305,8 +305,6 @@ test_that("attributes with special names are merged", { -3L ) - expect_error(new_data_frame(list(), n = 1L, row.names = 1:3), ".") - expect_identical( .row_names_info(new_data_frame(list(), n = 3L, row.names = 1:3)), 3L @@ -339,6 +337,16 @@ test_that("n and row.names (#894)", { ) }) +test_that("`row.names` completely overrides `n` and the implied size of `x`, even if incompatible (tidyverse/dplyr#6596)", { + row_names <- c(NA, -3L) + + df <- new_data_frame(list(), n = 2L, row.names = row_names) + expect_identical(.row_names_info(df, type = 0L), row_names) + + df <- new_data_frame(list(x = 1:2), row.names = row_names) + expect_identical(.row_names_info(df, type = 0L), row_names) +}) + test_that("`x` must be a list", { expect_snapshot((expect_error( new_data_frame(1), From a77743ac40269f4ab3313f4ff880a4b8133d36a0 Mon Sep 17 00:00:00 2001 From: DavisVaughan Date: Wed, 7 Jun 2023 16:54:25 -0400 Subject: [PATCH 283/312] NEWS bullet --- NEWS.md | 7 +++++++ 1 file changed, 7 insertions(+) diff --git a/NEWS.md b/NEWS.md index 65f015612..ab1fbee4f 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,5 +1,12 @@ # vctrs (development version) +* Fixed an issue where certain ALTREP row names were being materialized when + passed to `new_data_frame()`. We've fixed this by removing a safeguard in + `new_data_frame()` that performed a compatibility check when both `n` and + `row.names` were provided. Because this is a low level function designed for + performance, it is up to the caller to ensure these inputs are compatible + (tidyverse/dplyr#6596). + * Fixed an issue where `vec_set_*()` used with data frames could accidentally return an object with the type of the proxy rather than the type of the original inputs (#1837). From 56cfa19777fa4f2c305050b50acce8df6684e695 Mon Sep 17 00:00:00 2001 From: DavisVaughan Date: Wed, 14 Jun 2023 11:31:29 -0400 Subject: [PATCH 284/312] Implement a "lazy character" ALTREP class to test with This materializes itself whenever any property of the underlying vector is required, so it works nicely as a test here where the ALTREP `Length()` method used to be called. --- R/altrep-lazy-character.R | 28 +++ src/altrep-lazy-character.c | 139 +++++++++++ src/init.c | 324 +++++++++++++------------- tests/testthat/test-type-data-frame.R | 18 ++ 4 files changed, 351 insertions(+), 158 deletions(-) create mode 100644 R/altrep-lazy-character.R create mode 100644 src/altrep-lazy-character.c diff --git a/R/altrep-lazy-character.R b/R/altrep-lazy-character.R new file mode 100644 index 000000000..71b2df911 --- /dev/null +++ b/R/altrep-lazy-character.R @@ -0,0 +1,28 @@ +#' Lazy character vector +#' +#' `new_lazy_character()` takes a function with no arguments which must return +#' a character vector of arbitrary length. The function will be evaluated +#' exactly once whenever any properties of the character vector are required +#' (including the length or any vector elements). +#' +#' A "real" production level implementation might work more like +#' `carrier::crate()`, where the function is isolated and users must explicitly +#' provide any data required to evaluate the function, since the time of +#' evaluation is unknown. +#' +#' As of June 2023, running `x <- new_lazy_character(~ c("x", "y"))` in the +#' RStudio console will call the ALTREP length method, which materializes the +#' object. Doing this in a terminal session running R does not, so it is an +#' RStudio issue. This doesn't affect tests run within a `test_that()` block. +#' +#' @param fn A function with no arguments returning a character vector. +#' +#' @noRd +new_lazy_character <- function(fn) { + fn <- as_function(fn) + .Call(ffi_altrep_new_lazy_character, fn) +} + +lazy_character_is_materialized <- function(x) { + .Call(ffi_altrep_lazy_character_is_materialized, x) +} diff --git a/src/altrep-lazy-character.c b/src/altrep-lazy-character.c new file mode 100644 index 000000000..7dc5efaec --- /dev/null +++ b/src/altrep-lazy-character.c @@ -0,0 +1,139 @@ +#include "vctrs.h" +#include "altrep.h" + +#if (!HAS_ALTREP) + +#include + +void vctrs_init_altrep_lazy_character(DllInfo* dll) { } + +r_obj* ffi_altrep_lazy_character_is_materialized(r_obj* x) { + r_stop_internal("Need R 3.5+ for Altrep support."); + return r_null; +} + +r_obj* ffi_altrep_new_lazy_character(r_obj* fn) { + r_stop_internal("Need R 3.5+ for Altrep support."); + return r_null; +} + +#else + +// Initialised at load time +R_altrep_class_t altrep_lazy_character_class; + +r_obj* ffi_altrep_lazy_character_is_materialized(r_obj* x) { + return r_lgl(R_altrep_data2(x) != r_null); +} + +r_obj* ffi_altrep_new_lazy_character(r_obj* fn) { + r_obj* out = R_new_altrep(altrep_lazy_character_class, fn, r_null); + r_mark_shared(out); + return out; +} + +// ----------------------------------------------------------------------------- +// ALTVEC + +r_obj* altrep_lazy_character_Materialize(r_obj* vec) { + r_obj* out = R_altrep_data2(vec); + if (out != r_null) { + return out; + } + + r_obj* fn = R_altrep_data1(vec); + r_obj* call = KEEP(r_new_call(fn, r_null)); + + // `fn()` evaluated in the global environment + out = r_eval(call, r_envs.global); + + if (r_typeof(out) != R_TYPE_character) { + r_stop_internal("`fn` must evaluate to a character vector."); + } + + R_set_altrep_data2(vec, out); + + UNPROTECT(1); + return out; +} + +void* altrep_lazy_character_Dataptr(r_obj* vec, Rboolean writeable) { + return STDVEC_DATAPTR(altrep_lazy_character_Materialize(vec)); +} + +const void* altrep_lazy_character_Dataptr_or_null(r_obj* vec) { + r_obj* out = R_altrep_data2(vec); + + if (out == r_null) { + return NULL; + } else { + return STDVEC_DATAPTR(out); + } +} + +// ----------------------------------------------------------------------------- +// ALTREP + +R_xlen_t altrep_lazy_character_Length(r_obj* vec) { + r_obj* out = R_altrep_data2(vec); + + if (out == r_null) { + out = altrep_lazy_character_Materialize(vec); + } + + return r_length(out); +} + +// What gets printed when .Internal(inspect()) is used +Rboolean altrep_lazy_character_Inspect(r_obj* x, + int pre, + int deep, + int pvec, + void (*inspect_subtree)(r_obj*, int, int, int)) { + Rprintf("vctrs_altrep_lazy_character (materialized=%s)\n", + R_altrep_data2(x) != r_null ? "T" : "F"); + return TRUE; +} + +// ----------------------------------------------------------------------------- +// ALTSTRING + +r_obj* altrep_lazy_character_Elt(r_obj* vec, R_xlen_t i) { + r_obj* out = R_altrep_data2(vec); + + if (out == r_null) { + out = altrep_lazy_character_Materialize(vec); + } + + return STRING_ELT(out, i); +} + +void altrep_lazy_character_Set_elt(r_obj* vec, R_xlen_t i, r_obj* value) { + r_obj* out = R_altrep_data2(vec); + + if (out == r_null) { + out = altrep_lazy_character_Materialize(vec); + } + + SET_STRING_ELT(out, i, value); +} + +// ----------------------------------------------------------------------------- + +void vctrs_init_altrep_lazy_character(DllInfo* dll) { + altrep_lazy_character_class = R_make_altstring_class("altrep_lazy_character", "vctrs", dll); + + // ALTVEC + R_set_altvec_Dataptr_method(altrep_lazy_character_class, altrep_lazy_character_Dataptr); + R_set_altvec_Dataptr_or_null_method(altrep_lazy_character_class, altrep_lazy_character_Dataptr_or_null); + + // ALTREP + R_set_altrep_Length_method(altrep_lazy_character_class, altrep_lazy_character_Length); + R_set_altrep_Inspect_method(altrep_lazy_character_class, altrep_lazy_character_Inspect); + + // ALTSTRING + R_set_altstring_Elt_method(altrep_lazy_character_class, altrep_lazy_character_Elt); + R_set_altstring_Set_elt_method(altrep_lazy_character_class, altrep_lazy_character_Set_elt); +} + +#endif // R version >= 3.5.0 diff --git a/src/init.c b/src/init.c index bb6bf7f09..9b338e3df 100644 --- a/src/init.c +++ b/src/init.c @@ -184,166 +184,173 @@ SEXP vctrs_init_library(SEXP); // Defined in altrep-rle.h extern SEXP altrep_rle_Make(SEXP); extern SEXP altrep_rle_is_materialized(SEXP); -void vctrs_init_altrep_rle(DllInfo* dll); +void vctrs_init_altrep_rle(DllInfo*); + +// Defined in altrep-lazy-character.c +extern r_obj* ffi_altrep_new_lazy_character(r_obj*); +extern r_obj* ffi_altrep_lazy_character_is_materialized(r_obj*); +extern r_obj* vctrs_init_altrep_lazy_character(DllInfo*); static const R_CallMethodDef CallEntries[] = { - {"vctrs_list_get", (DL_FUNC) &vctrs_list_get, 2}, - {"vctrs_list_set", (DL_FUNC) &vctrs_list_set, 3}, - {"vctrs_field_get", (DL_FUNC) &vctrs_field_get, 2}, - {"vctrs_field_set", (DL_FUNC) &vctrs_field_set, 3}, - {"vctrs_fields", (DL_FUNC) &vctrs_fields, 1}, - {"vctrs_n_fields", (DL_FUNC) &vctrs_n_fields, 1}, - {"vctrs_hash", (DL_FUNC) &vctrs_hash, 1}, - {"vctrs_hash_object", (DL_FUNC) &vctrs_hash_object, 1}, - {"vctrs_equal_object", (DL_FUNC) &vctrs_equal_object, 2}, - {"vctrs_unique_loc", (DL_FUNC) &vctrs_unique_loc, 1}, - {"vctrs_duplicated", (DL_FUNC) &vctrs_duplicated, 1}, - {"vctrs_duplicated_any", (DL_FUNC) &vctrs_duplicated_any, 1}, - {"vctrs_count", (DL_FUNC) &vctrs_count, 1}, - {"vctrs_id", (DL_FUNC) &vctrs_id, 1}, - {"vctrs_n_distinct", (DL_FUNC) &vctrs_n_distinct, 1}, - {"vctrs_split", (DL_FUNC) &vec_split, 2}, - {"vctrs_group_id", (DL_FUNC) &vctrs_group_id, 1}, - {"vctrs_group_rle", (DL_FUNC) &vctrs_group_rle, 1}, - {"vctrs_group_loc", (DL_FUNC) &vec_group_loc, 1}, - {"ffi_size", (DL_FUNC) &ffi_size, 2}, - {"ffi_list_sizes", (DL_FUNC) &ffi_list_sizes, 2}, - {"vctrs_dim", (DL_FUNC) &vctrs_dim, 1}, - {"vctrs_dim_n", (DL_FUNC) &vctrs_dim_n, 1}, - {"vctrs_is_unspecified", (DL_FUNC) &vctrs_is_unspecified, 1}, - {"vctrs_equal", (DL_FUNC) &vctrs_equal, 3}, - {"ffi_vec_detect_missing", (DL_FUNC) &ffi_vec_detect_missing, 1}, - {"ffi_vec_any_missing", (DL_FUNC) &ffi_vec_any_missing, 1}, - {"ffi_vec_compare", (DL_FUNC) &ffi_vec_compare, 3}, - {"vctrs_match", (DL_FUNC) &vctrs_match, 4}, - {"vctrs_in", (DL_FUNC) &vctrs_in, 4}, - {"vctrs_typeof", (DL_FUNC) &vctrs_typeof, 2}, - {"vctrs_init_library", (DL_FUNC) &vctrs_init_library, 1}, - {"ffi_obj_is_vector", (DL_FUNC) &ffi_obj_is_vector, 1}, - {"ffi_obj_check_vector", (DL_FUNC) &ffi_obj_check_vector, 2}, - {"ffi_vec_check_size", (DL_FUNC) &ffi_vec_check_size, 3}, - {"ffi_ptype2", (DL_FUNC) &ffi_ptype2, 3}, - {"ffi_typeof2", (DL_FUNC) &ffi_typeof2, 2}, - {"ffi_typeof2_s3", (DL_FUNC) &ffi_typeof2_s3, 2}, - {"ffi_cast", (DL_FUNC) &ffi_cast, 3}, - {"ffi_as_location", (DL_FUNC) &ffi_as_location, 8}, - {"ffi_slice", (DL_FUNC) &ffi_slice, 3}, - {"ffi_init", (DL_FUNC) &ffi_init, 3}, - {"ffi_vec_chop", (DL_FUNC) &ffi_vec_chop, 3}, - {"ffi_list_unchop", (DL_FUNC) &ffi_list_unchop, 6}, - {"ffi_vec_chop_seq", (DL_FUNC) &ffi_vec_chop_seq, 4}, - {"ffi_slice_seq", (DL_FUNC) &ffi_slice_seq, 4}, - {"ffi_slice_rep", (DL_FUNC) &ffi_slice_rep, 3}, - {"ffi_vec_restore", (DL_FUNC) &ffi_vec_restore, 2}, - {"ffi_vec_restore_recurse", (DL_FUNC) &ffi_vec_restore_recurse, 2}, - {"ffi_vec_restore_default", (DL_FUNC) &ffi_vec_restore_default, 2}, - {"ffi_vec_proxy", (DL_FUNC) &vec_proxy, 1}, - {"ffi_vec_proxy_recurse", (DL_FUNC) &vec_proxy_recurse, 1}, - {"vctrs_proxy_equal", (DL_FUNC) &vec_proxy_equal, 1}, - {"vctrs_proxy_compare", (DL_FUNC) &vec_proxy_compare, 1}, - {"vctrs_proxy_order", (DL_FUNC) &vec_proxy_order, 1}, - {"ffi_df_proxy", (DL_FUNC) &ffi_df_proxy, 2}, - {"vctrs_unspecified", (DL_FUNC) &vctrs_unspecified, 1}, - {"ffi_ptype", (DL_FUNC) &ffi_ptype, 3}, - {"vctrs_ptype_finalise", (DL_FUNC) &vec_ptype_finalise, 1}, - {"ffi_minimal_names", (DL_FUNC) &ffi_minimal_names, 1}, - {"ffi_unique_names", (DL_FUNC) &ffi_unique_names, 2}, - {"ffi_as_minimal_names", (DL_FUNC) &ffi_as_minimal_names, 1}, - {"vctrs_names", (DL_FUNC) &vec_names, 1}, - {"vctrs_is_unique_names", (DL_FUNC) &vctrs_is_unique_names, 1}, - {"vctrs_as_unique_names", (DL_FUNC) &vctrs_as_unique_names, 2}, - {"vctrs_set_names", (DL_FUNC) &vec_set_names, 2}, - {"ffi_df_cast_opts", (DL_FUNC) &ffi_df_cast_opts, 4}, - {"ffi_df_ptype2_opts", (DL_FUNC) &ffi_df_ptype2_opts, 4}, - {"ffi_type_info", (DL_FUNC) &ffi_type_info, 1}, - {"ffi_proxy_info", (DL_FUNC) &ffi_proxy_info, 1}, - {"ffi_class_type", (DL_FUNC) &ffi_class_type, 1}, - {"ffi_vec_bare_df_restore", (DL_FUNC) &ffi_vec_bare_df_restore, 2}, - {"ffi_recycle", (DL_FUNC) &ffi_recycle, 3}, - {"ffi_assign", (DL_FUNC) &ffi_assign, 4}, - {"ffi_assign_seq", (DL_FUNC) &ffi_assign_seq, 5}, - {"vctrs_set_attributes", (DL_FUNC) &vctrs_set_attributes, 2}, - {"ffi_as_df_row", (DL_FUNC) &ffi_as_df_row, 3}, - {"ffi_outer_names", (DL_FUNC) &ffi_outer_names, 3}, - {"vctrs_df_size", (DL_FUNC) &vctrs_df_size, 1}, - {"ffi_as_df_col", (DL_FUNC) &ffi_as_df_col, 3}, - {"ffi_apply_name_spec", (DL_FUNC) &ffi_apply_name_spec, 4}, - {"ffi_unset_s4", (DL_FUNC) &ffi_unset_s4, 1}, - {"vctrs_altrep_rle_Make", (DL_FUNC) &altrep_rle_Make, 1}, - {"vctrs_altrep_rle_is_materialized", (DL_FUNC) &altrep_rle_is_materialized, 1}, - {"vctrs_validate_name_repair_arg", (DL_FUNC) &vctrs_validate_name_repair_arg, 1}, - {"vctrs_validate_minimal_names", (DL_FUNC) &vctrs_validate_minimal_names, 2}, - {"ffi_vec_as_names", (DL_FUNC) &ffi_vec_as_names, 4}, - {"ffi_is_partial", (DL_FUNC) &ffi_is_partial, 1}, - {"ffi_obj_is_list", (DL_FUNC) &ffi_obj_is_list, 1}, - {"vctrs_try_catch_callback", (DL_FUNC) &vctrs_try_catch_callback, 2}, - {"ffi_is_coercible", (DL_FUNC) &ffi_is_coercible, 4}, - {"ffi_as_subscript", (DL_FUNC) &ffi_as_subscript, 5}, - {"ffi_as_subscript_result", (DL_FUNC) &ffi_as_subscript_result, 5}, - {"ffi_df_flatten_info", (DL_FUNC) &ffi_df_flatten_info, 1}, - {"ffi_df_flatten", (DL_FUNC) &df_flatten, 1}, - {"vctrs_linked_version", (DL_FUNC) &vctrs_linked_version, 0}, - {"ffi_tib_ptype2", (DL_FUNC) &ffi_tib_ptype2, 5}, - {"ffi_tib_cast", (DL_FUNC) &ffi_tib_cast, 5}, - {"ffi_assign_params", (DL_FUNC) &ffi_assign_params, 4}, - {"vctrs_has_dim", (DL_FUNC) &vctrs_has_dim, 1}, - {"ffi_vec_rep", (DL_FUNC) &ffi_vec_rep, 3}, - {"ffi_vec_rep_each", (DL_FUNC) &ffi_vec_rep_each, 3}, - {"vctrs_maybe_shared_col", (DL_FUNC) &vctrs_maybe_shared_col, 2}, - {"vctrs_new_df_unshared_col", (DL_FUNC) &vctrs_new_df_unshared_col, 0}, - {"ffi_vec_shaped_ptype", (DL_FUNC) &ffi_vec_shaped_ptype, 4}, - {"ffi_vec_shape2", (DL_FUNC) &ffi_vec_shape2, 3}, - {"vctrs_new_date", (DL_FUNC) &vctrs_new_date, 1}, - {"vctrs_date_validate", (DL_FUNC) &vctrs_date_validate, 1}, - {"vctrs_new_datetime", (DL_FUNC) &vctrs_new_datetime, 2}, - {"vctrs_datetime_validate", (DL_FUNC) &vctrs_datetime_validate, 1}, - {"ffi_ptype2_opts", (DL_FUNC) &ffi_ptype2_opts, 4}, - {"vctrs_s3_find_method", (DL_FUNC) &vctrs_s3_find_method, 3}, - {"vctrs_implements_ptype2", (DL_FUNC) &vctrs_implements_ptype2, 1}, - {"ffi_ptype2_dispatch_native", (DL_FUNC) &ffi_ptype2_dispatch_native, 4}, - {"ffi_cast_dispatch_native", (DL_FUNC) &ffi_cast_dispatch_native, 6}, - {"vctrs_fast_c", (DL_FUNC) &vctrs_fast_c, 2}, - {"ffi_data_frame", (DL_FUNC) &ffi_data_frame, 4}, - {"ffi_df_list", (DL_FUNC) &ffi_df_list, 5}, - {"ffi_vec_detect_run_bounds", (DL_FUNC) &ffi_vec_detect_run_bounds, 3}, - {"ffi_vec_locate_run_bounds", (DL_FUNC) &ffi_vec_locate_run_bounds, 3}, - {"ffi_vec_identify_runs", (DL_FUNC) &ffi_vec_identify_runs, 2}, - {"ffi_vec_run_sizes", (DL_FUNC) &ffi_vec_run_sizes, 2}, - {"vctrs_slice_complete", (DL_FUNC) &vctrs_slice_complete, 1}, - {"vctrs_locate_complete", (DL_FUNC) &vctrs_locate_complete, 1}, - {"vctrs_detect_complete", (DL_FUNC) &vctrs_detect_complete, 1}, - {"vctrs_normalize_encoding", (DL_FUNC) &vctrs_normalize_encoding, 1}, - {"vctrs_order", (DL_FUNC) &vctrs_order, 5}, - {"vctrs_locate_sorted_groups", (DL_FUNC) &vctrs_locate_sorted_groups, 5}, - {"vctrs_order_info", (DL_FUNC) &vctrs_order_info, 6}, - {"ffi_vec_unrep", (DL_FUNC) &ffi_vec_unrep, 2}, - {"vctrs_fill_missing", (DL_FUNC) &vctrs_fill_missing, 3}, - {"ffi_chr_paste_prefix", (DL_FUNC) &ffi_chr_paste_prefix, 3}, - {"vctrs_rank", (DL_FUNC) &vctrs_rank, 7}, - {"vctrs_integer64_proxy", (DL_FUNC) &vctrs_integer64_proxy, 1}, - {"vctrs_integer64_restore", (DL_FUNC) &vctrs_integer64_restore, 1}, - {"vctrs_list_drop_empty", (DL_FUNC) &vctrs_list_drop_empty, 1}, - {"vctrs_is_altrep", (DL_FUNC) &vctrs_is_altrep, 1}, - {"ffi_interleave_indices", (DL_FUNC) &ffi_interleave_indices, 2}, - {"ffi_compute_nesting_container_info", (DL_FUNC) &ffi_compute_nesting_container_info, 2}, - {"ffi_locate_matches", (DL_FUNC) &ffi_locate_matches, 14}, - {"ffi_interval_groups", (DL_FUNC) &ffi_interval_groups, 4}, - {"ffi_interval_locate_groups", (DL_FUNC) &ffi_interval_locate_groups, 4}, - {"ffi_interval_complement", (DL_FUNC) &ffi_interval_complement, 4}, - {"ffi_interval_locate_containers", (DL_FUNC) &ffi_interval_locate_containers, 2}, - {"ffi_check_list", (DL_FUNC) &ffi_check_list, 2}, - {"ffi_list_all_vectors", (DL_FUNC) &ffi_list_all_vectors, 2}, - {"ffi_list_check_all_vectors", (DL_FUNC) &ffi_list_check_all_vectors, 2}, - {"ffi_as_short_length", (DL_FUNC) &ffi_as_short_length, 2}, - {"ffi_s3_get_method", (DL_FUNC) &ffi_s3_get_method, 3}, - {"ffi_list_all_size", (DL_FUNC) &ffi_list_all_size, 3}, - {"ffi_list_check_all_size", (DL_FUNC) &ffi_list_check_all_size, 3}, - {"ffi_vec_set_intersect", (DL_FUNC) &ffi_vec_set_intersect, 4}, - {"ffi_vec_set_difference", (DL_FUNC) &ffi_vec_set_difference, 4}, - {"ffi_vec_set_union", (DL_FUNC) &ffi_vec_set_union, 4}, - {"ffi_vec_set_symmetric_difference", (DL_FUNC) &ffi_vec_set_symmetric_difference, 4}, - {"ffi_vec_expand_grid", (DL_FUNC) &ffi_vec_expand_grid, 4}, - {"ffi_exp_vec_cast", (DL_FUNC) &exp_vec_cast, 2}, + {"vctrs_list_get", (DL_FUNC) &vctrs_list_get, 2}, + {"vctrs_list_set", (DL_FUNC) &vctrs_list_set, 3}, + {"vctrs_field_get", (DL_FUNC) &vctrs_field_get, 2}, + {"vctrs_field_set", (DL_FUNC) &vctrs_field_set, 3}, + {"vctrs_fields", (DL_FUNC) &vctrs_fields, 1}, + {"vctrs_n_fields", (DL_FUNC) &vctrs_n_fields, 1}, + {"vctrs_hash", (DL_FUNC) &vctrs_hash, 1}, + {"vctrs_hash_object", (DL_FUNC) &vctrs_hash_object, 1}, + {"vctrs_equal_object", (DL_FUNC) &vctrs_equal_object, 2}, + {"vctrs_unique_loc", (DL_FUNC) &vctrs_unique_loc, 1}, + {"vctrs_duplicated", (DL_FUNC) &vctrs_duplicated, 1}, + {"vctrs_duplicated_any", (DL_FUNC) &vctrs_duplicated_any, 1}, + {"vctrs_count", (DL_FUNC) &vctrs_count, 1}, + {"vctrs_id", (DL_FUNC) &vctrs_id, 1}, + {"vctrs_n_distinct", (DL_FUNC) &vctrs_n_distinct, 1}, + {"vctrs_split", (DL_FUNC) &vec_split, 2}, + {"vctrs_group_id", (DL_FUNC) &vctrs_group_id, 1}, + {"vctrs_group_rle", (DL_FUNC) &vctrs_group_rle, 1}, + {"vctrs_group_loc", (DL_FUNC) &vec_group_loc, 1}, + {"ffi_size", (DL_FUNC) &ffi_size, 2}, + {"ffi_list_sizes", (DL_FUNC) &ffi_list_sizes, 2}, + {"vctrs_dim", (DL_FUNC) &vctrs_dim, 1}, + {"vctrs_dim_n", (DL_FUNC) &vctrs_dim_n, 1}, + {"vctrs_is_unspecified", (DL_FUNC) &vctrs_is_unspecified, 1}, + {"vctrs_equal", (DL_FUNC) &vctrs_equal, 3}, + {"ffi_vec_detect_missing", (DL_FUNC) &ffi_vec_detect_missing, 1}, + {"ffi_vec_any_missing", (DL_FUNC) &ffi_vec_any_missing, 1}, + {"ffi_vec_compare", (DL_FUNC) &ffi_vec_compare, 3}, + {"vctrs_match", (DL_FUNC) &vctrs_match, 4}, + {"vctrs_in", (DL_FUNC) &vctrs_in, 4}, + {"vctrs_typeof", (DL_FUNC) &vctrs_typeof, 2}, + {"vctrs_init_library", (DL_FUNC) &vctrs_init_library, 1}, + {"ffi_obj_is_vector", (DL_FUNC) &ffi_obj_is_vector, 1}, + {"ffi_obj_check_vector", (DL_FUNC) &ffi_obj_check_vector, 2}, + {"ffi_vec_check_size", (DL_FUNC) &ffi_vec_check_size, 3}, + {"ffi_ptype2", (DL_FUNC) &ffi_ptype2, 3}, + {"ffi_typeof2", (DL_FUNC) &ffi_typeof2, 2}, + {"ffi_typeof2_s3", (DL_FUNC) &ffi_typeof2_s3, 2}, + {"ffi_cast", (DL_FUNC) &ffi_cast, 3}, + {"ffi_as_location", (DL_FUNC) &ffi_as_location, 8}, + {"ffi_slice", (DL_FUNC) &ffi_slice, 3}, + {"ffi_init", (DL_FUNC) &ffi_init, 3}, + {"ffi_vec_chop", (DL_FUNC) &ffi_vec_chop, 3}, + {"ffi_list_unchop", (DL_FUNC) &ffi_list_unchop, 6}, + {"ffi_vec_chop_seq", (DL_FUNC) &ffi_vec_chop_seq, 4}, + {"ffi_slice_seq", (DL_FUNC) &ffi_slice_seq, 4}, + {"ffi_slice_rep", (DL_FUNC) &ffi_slice_rep, 3}, + {"ffi_vec_restore", (DL_FUNC) &ffi_vec_restore, 2}, + {"ffi_vec_restore_recurse", (DL_FUNC) &ffi_vec_restore_recurse, 2}, + {"ffi_vec_restore_default", (DL_FUNC) &ffi_vec_restore_default, 2}, + {"ffi_vec_proxy", (DL_FUNC) &vec_proxy, 1}, + {"ffi_vec_proxy_recurse", (DL_FUNC) &vec_proxy_recurse, 1}, + {"vctrs_proxy_equal", (DL_FUNC) &vec_proxy_equal, 1}, + {"vctrs_proxy_compare", (DL_FUNC) &vec_proxy_compare, 1}, + {"vctrs_proxy_order", (DL_FUNC) &vec_proxy_order, 1}, + {"ffi_df_proxy", (DL_FUNC) &ffi_df_proxy, 2}, + {"vctrs_unspecified", (DL_FUNC) &vctrs_unspecified, 1}, + {"ffi_ptype", (DL_FUNC) &ffi_ptype, 3}, + {"vctrs_ptype_finalise", (DL_FUNC) &vec_ptype_finalise, 1}, + {"ffi_minimal_names", (DL_FUNC) &ffi_minimal_names, 1}, + {"ffi_unique_names", (DL_FUNC) &ffi_unique_names, 2}, + {"ffi_as_minimal_names", (DL_FUNC) &ffi_as_minimal_names, 1}, + {"vctrs_names", (DL_FUNC) &vec_names, 1}, + {"vctrs_is_unique_names", (DL_FUNC) &vctrs_is_unique_names, 1}, + {"vctrs_as_unique_names", (DL_FUNC) &vctrs_as_unique_names, 2}, + {"vctrs_set_names", (DL_FUNC) &vec_set_names, 2}, + {"ffi_df_cast_opts", (DL_FUNC) &ffi_df_cast_opts, 4}, + {"ffi_df_ptype2_opts", (DL_FUNC) &ffi_df_ptype2_opts, 4}, + {"ffi_type_info", (DL_FUNC) &ffi_type_info, 1}, + {"ffi_proxy_info", (DL_FUNC) &ffi_proxy_info, 1}, + {"ffi_class_type", (DL_FUNC) &ffi_class_type, 1}, + {"ffi_vec_bare_df_restore", (DL_FUNC) &ffi_vec_bare_df_restore, 2}, + {"ffi_recycle", (DL_FUNC) &ffi_recycle, 3}, + {"ffi_assign", (DL_FUNC) &ffi_assign, 4}, + {"ffi_assign_seq", (DL_FUNC) &ffi_assign_seq, 5}, + {"vctrs_set_attributes", (DL_FUNC) &vctrs_set_attributes, 2}, + {"ffi_as_df_row", (DL_FUNC) &ffi_as_df_row, 3}, + {"ffi_outer_names", (DL_FUNC) &ffi_outer_names, 3}, + {"vctrs_df_size", (DL_FUNC) &vctrs_df_size, 1}, + {"ffi_as_df_col", (DL_FUNC) &ffi_as_df_col, 3}, + {"ffi_apply_name_spec", (DL_FUNC) &ffi_apply_name_spec, 4}, + {"ffi_unset_s4", (DL_FUNC) &ffi_unset_s4, 1}, + {"vctrs_altrep_rle_Make", (DL_FUNC) &altrep_rle_Make, 1}, + {"vctrs_altrep_rle_is_materialized", (DL_FUNC) &altrep_rle_is_materialized, 1}, + {"ffi_altrep_new_lazy_character", (DL_FUNC) &ffi_altrep_new_lazy_character, 1}, + {"ffi_altrep_lazy_character_is_materialized", (DL_FUNC) &ffi_altrep_lazy_character_is_materialized, 1}, + {"vctrs_validate_name_repair_arg", (DL_FUNC) &vctrs_validate_name_repair_arg, 1}, + {"vctrs_validate_minimal_names", (DL_FUNC) &vctrs_validate_minimal_names, 2}, + {"ffi_vec_as_names", (DL_FUNC) &ffi_vec_as_names, 4}, + {"ffi_is_partial", (DL_FUNC) &ffi_is_partial, 1}, + {"ffi_obj_is_list", (DL_FUNC) &ffi_obj_is_list, 1}, + {"vctrs_try_catch_callback", (DL_FUNC) &vctrs_try_catch_callback, 2}, + {"ffi_is_coercible", (DL_FUNC) &ffi_is_coercible, 4}, + {"ffi_as_subscript", (DL_FUNC) &ffi_as_subscript, 5}, + {"ffi_as_subscript_result", (DL_FUNC) &ffi_as_subscript_result, 5}, + {"ffi_df_flatten_info", (DL_FUNC) &ffi_df_flatten_info, 1}, + {"ffi_df_flatten", (DL_FUNC) &df_flatten, 1}, + {"vctrs_linked_version", (DL_FUNC) &vctrs_linked_version, 0}, + {"ffi_tib_ptype2", (DL_FUNC) &ffi_tib_ptype2, 5}, + {"ffi_tib_cast", (DL_FUNC) &ffi_tib_cast, 5}, + {"ffi_assign_params", (DL_FUNC) &ffi_assign_params, 4}, + {"vctrs_has_dim", (DL_FUNC) &vctrs_has_dim, 1}, + {"ffi_vec_rep", (DL_FUNC) &ffi_vec_rep, 3}, + {"ffi_vec_rep_each", (DL_FUNC) &ffi_vec_rep_each, 3}, + {"vctrs_maybe_shared_col", (DL_FUNC) &vctrs_maybe_shared_col, 2}, + {"vctrs_new_df_unshared_col", (DL_FUNC) &vctrs_new_df_unshared_col, 0}, + {"ffi_vec_shaped_ptype", (DL_FUNC) &ffi_vec_shaped_ptype, 4}, + {"ffi_vec_shape2", (DL_FUNC) &ffi_vec_shape2, 3}, + {"vctrs_new_date", (DL_FUNC) &vctrs_new_date, 1}, + {"vctrs_date_validate", (DL_FUNC) &vctrs_date_validate, 1}, + {"vctrs_new_datetime", (DL_FUNC) &vctrs_new_datetime, 2}, + {"vctrs_datetime_validate", (DL_FUNC) &vctrs_datetime_validate, 1}, + {"ffi_ptype2_opts", (DL_FUNC) &ffi_ptype2_opts, 4}, + {"vctrs_s3_find_method", (DL_FUNC) &vctrs_s3_find_method, 3}, + {"vctrs_implements_ptype2", (DL_FUNC) &vctrs_implements_ptype2, 1}, + {"ffi_ptype2_dispatch_native", (DL_FUNC) &ffi_ptype2_dispatch_native, 4}, + {"ffi_cast_dispatch_native", (DL_FUNC) &ffi_cast_dispatch_native, 6}, + {"vctrs_fast_c", (DL_FUNC) &vctrs_fast_c, 2}, + {"ffi_data_frame", (DL_FUNC) &ffi_data_frame, 4}, + {"ffi_df_list", (DL_FUNC) &ffi_df_list, 5}, + {"ffi_vec_detect_run_bounds", (DL_FUNC) &ffi_vec_detect_run_bounds, 3}, + {"ffi_vec_locate_run_bounds", (DL_FUNC) &ffi_vec_locate_run_bounds, 3}, + {"ffi_vec_identify_runs", (DL_FUNC) &ffi_vec_identify_runs, 2}, + {"ffi_vec_run_sizes", (DL_FUNC) &ffi_vec_run_sizes, 2}, + {"vctrs_slice_complete", (DL_FUNC) &vctrs_slice_complete, 1}, + {"vctrs_locate_complete", (DL_FUNC) &vctrs_locate_complete, 1}, + {"vctrs_detect_complete", (DL_FUNC) &vctrs_detect_complete, 1}, + {"vctrs_normalize_encoding", (DL_FUNC) &vctrs_normalize_encoding, 1}, + {"vctrs_order", (DL_FUNC) &vctrs_order, 5}, + {"vctrs_locate_sorted_groups", (DL_FUNC) &vctrs_locate_sorted_groups, 5}, + {"vctrs_order_info", (DL_FUNC) &vctrs_order_info, 6}, + {"ffi_vec_unrep", (DL_FUNC) &ffi_vec_unrep, 2}, + {"vctrs_fill_missing", (DL_FUNC) &vctrs_fill_missing, 3}, + {"ffi_chr_paste_prefix", (DL_FUNC) &ffi_chr_paste_prefix, 3}, + {"vctrs_rank", (DL_FUNC) &vctrs_rank, 7}, + {"vctrs_integer64_proxy", (DL_FUNC) &vctrs_integer64_proxy, 1}, + {"vctrs_integer64_restore", (DL_FUNC) &vctrs_integer64_restore, 1}, + {"vctrs_list_drop_empty", (DL_FUNC) &vctrs_list_drop_empty, 1}, + {"vctrs_is_altrep", (DL_FUNC) &vctrs_is_altrep, 1}, + {"ffi_interleave_indices", (DL_FUNC) &ffi_interleave_indices, 2}, + {"ffi_compute_nesting_container_info", (DL_FUNC) &ffi_compute_nesting_container_info, 2}, + {"ffi_locate_matches", (DL_FUNC) &ffi_locate_matches, 14}, + {"ffi_interval_groups", (DL_FUNC) &ffi_interval_groups, 4}, + {"ffi_interval_locate_groups", (DL_FUNC) &ffi_interval_locate_groups, 4}, + {"ffi_interval_complement", (DL_FUNC) &ffi_interval_complement, 4}, + {"ffi_interval_locate_containers", (DL_FUNC) &ffi_interval_locate_containers, 2}, + {"ffi_check_list", (DL_FUNC) &ffi_check_list, 2}, + {"ffi_list_all_vectors", (DL_FUNC) &ffi_list_all_vectors, 2}, + {"ffi_list_check_all_vectors", (DL_FUNC) &ffi_list_check_all_vectors, 2}, + {"ffi_as_short_length", (DL_FUNC) &ffi_as_short_length, 2}, + {"ffi_s3_get_method", (DL_FUNC) &ffi_s3_get_method, 3}, + {"ffi_list_all_size", (DL_FUNC) &ffi_list_all_size, 3}, + {"ffi_list_check_all_size", (DL_FUNC) &ffi_list_check_all_size, 3}, + {"ffi_vec_set_intersect", (DL_FUNC) &ffi_vec_set_intersect, 4}, + {"ffi_vec_set_difference", (DL_FUNC) &ffi_vec_set_difference, 4}, + {"ffi_vec_set_union", (DL_FUNC) &ffi_vec_set_union, 4}, + {"ffi_vec_set_symmetric_difference", (DL_FUNC) &ffi_vec_set_symmetric_difference, 4}, + {"ffi_vec_expand_grid", (DL_FUNC) &ffi_vec_expand_grid, 4}, + {"ffi_exp_vec_cast", (DL_FUNC) &exp_vec_cast, 2}, {NULL, NULL, 0} }; @@ -401,6 +408,7 @@ export void R_init_vctrs(DllInfo *dll) // Altrep classes vctrs_init_altrep_rle(dll); + vctrs_init_altrep_lazy_character(dll); } diff --git a/tests/testthat/test-type-data-frame.R b/tests/testthat/test-type-data-frame.R index 2f5b0a535..fb1ebafe4 100644 --- a/tests/testthat/test-type-data-frame.R +++ b/tests/testthat/test-type-data-frame.R @@ -347,6 +347,24 @@ test_that("`row.names` completely overrides `n` and the implied size of `x`, eve expect_identical(.row_names_info(df, type = 0L), row_names) }) +test_that("ALTREP `row.names` are not materialized by `new_data_frame()` (tidyverse/dplyr#6596)", { + skip_if(getRversion() <= "3.5.0") + + # We are careful in `new_data_frame()` to not call the `Dataptr()` or + # `Length()` ALTREP methods, both of which would materialize our lazy + # character here + row_names <- new_lazy_character(~ c("a", "b")) + + x <- new_data_frame(list(), row.names = row_names) + expect_false(lazy_character_is_materialized(.row_names_info(x, type = 0L))) + + x <- new_data_frame(list(x = 1:2), row.names = row_names) + expect_false(lazy_character_is_materialized(.row_names_info(x, type = 0L))) + + x <- new_data_frame(list(), n = 2L, row.names = row_names) + expect_false(lazy_character_is_materialized(.row_names_info(x, type = 0L))) +}) + test_that("`x` must be a list", { expect_snapshot((expect_error( new_data_frame(1), From acafad5025d6a34d3d86925852a172348e025679 Mon Sep 17 00:00:00 2001 From: Davis Vaughan Date: Thu, 15 Jun 2023 10:27:21 -0400 Subject: [PATCH 285/312] RC 0.6.3 (#1850) * Revdep results Two false positives * Update `cran-comments.md` * Increment version number to 0.6.3 * CRAN-SUBMISSION * CRAN-SUBMISSION --- DESCRIPTION | 2 +- NEWS.md | 2 +- cran-comments.md | 2 - revdep/README.md | 324 +- revdep/cran.md | 239 +- revdep/failures.md | 16279 ++----------------------------------------- revdep/problems.md | 125 +- src/version.c | 2 +- 8 files changed, 538 insertions(+), 16437 deletions(-) diff --git a/DESCRIPTION b/DESCRIPTION index b3fee10f3..43be7730d 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -1,6 +1,6 @@ Package: vctrs Title: Vector Helpers -Version: 0.6.2.9000 +Version: 0.6.3 Authors@R: c( person("Hadley", "Wickham", , "hadley@posit.co", role = "aut"), person("Lionel", "Henry", , "lionel@posit.co", role = "aut"), diff --git a/NEWS.md b/NEWS.md index ab1fbee4f..8071b9a3a 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,4 +1,4 @@ -# vctrs (development version) +# vctrs 0.6.3 * Fixed an issue where certain ALTREP row names were being materialized when passed to `new_data_frame()`. We've fixed this by removing a safeguard in diff --git a/cran-comments.md b/cran-comments.md index 5831e7cf8..1ea825650 100644 --- a/cran-comments.md +++ b/cran-comments.md @@ -1,3 +1 @@ This is a patch release with no expected breakage of any reverse dependencies. - -We are maintaining compatibility with an upcoming release of waldo. diff --git a/revdep/README.md b/revdep/README.md index c1629dace..bdb44cdd7 100644 --- a/revdep/README.md +++ b/revdep/README.md @@ -1,286 +1,54 @@ # Revdeps -## Failed to check (271) +## Failed to check (40) -|package |version |error |warning |note | -|:--------------------|:-------|:-----|:-------|:----| -|abmR |? | | | | -|abstr |? | | | | -|accept |? | | | | -|ADAM |? | | | | -|afex |? | | | | -|AGread |? | | | | -|agridat |? | | | | -|ags |? | | | | -|AMARETTO |? | | | | -|amplican |? | | | | -|autoTS |? | | | | -|bangladesh |? | | | | -|bayesian |? | | | | -|bayesmodels |? | | | | -|bayesnec |? | | | | -|bayesplot |? | | | | -|BayesPostEst |? | | | | -|bayesrules |? | | | | -|bdl |? | | | | -|beadplexr |? | | | | -|BiodiversityR |? | | | | -|blocs |? | | | | -|breathtestcore |? | | | | -|brendaDb |? | | | | -|broom.helpers |? | | | | -|broom.mixed |? | | | | -|BUSpaRse |? | | | | -|cancensus |? | | | | -|cattonum |? | | | | -|CCAMLRGIS |? | | | | -|ceRNAnetsim |? | | | | -|ChineseNames |? | | | | -|choroplethr |3.7.1 |1 | | | -|cinaR |? | | | | -|COMPASS |? | | | | -|CoordinateCleaner |2.0-20 |1 | | | -|CopernicusMarine |? | | | | -|cort |? | | | | -|covidmx |? | | | | -|CRE |? | | | | -|ctDNAtools |? | | | | -|cubble |? | | | | -|cxr |? | | | | -|cyclestreets |? | | | | -|CytoML |? | | | | -|D2MCS |? | | | | -|datawizard |? | | | | -|dbmss |? | | | | -|DeLorean |? | | | | -|DepecheR |? | | | | -|destiny |? | | | | -|DiffBind |? | | | | -|diffman |? | | | | -|diffrprojects |? | | | | -|dycdtools |? | | | | -|dynamicSDM |? | | | | -|dynfrail |? | | | | -|edbuildmapr |? | | | | -|EFDR |? | | | | -|embed |? | | | | -|EnvExpInd |? | | | | -|EpiForsk |? | | | | -|epiphy |? | | | | -|epitopeR |? | | | | -|escalation |? | | | | -|EScvtmle |? | | | | -|eSDM |? | | | | -|ESTER |? | | | | -|evaluator |? | | | | -|expstudies |? | | | | -|fable.prophet |? | | | | -|FAMetA |0.1.5 |1 | | | -|fgdr |? | | | | -|finnts |? | | | | -|fipe |? | | | | -|foieGras |? | | | | -|forceR |? | | | | -|FORTLS |? | | | | -|FRK |? | | | | -|fsr |? | | | | -|genekitr |? | | | | -|geocmeans |? | | | | -|GeodesiCL |1.0.0 |1 | | | -|ggchangepoint |? | | | | -|ggOceanMaps |? | | | | -|ggPMX |? | | | | -|ggseqplot |? | | | | -|ggspatial |? | | | | -|ggstatsplot |? | | | | -|glottospace |? | | | | -|GPSeqClus |? | | | | -|GREENeR |? | | | | -|gtfs2gps |? | | | | -|gumboot |? | | | | -|gwavr |? | | | | -|GWPR.light |? | | | | -|happign |? | | | | -|healthyR.ai |? | | | | -|healthyR.ts |? | | | | -|healthyverse |? | | | | -|himach |? | | | | -|historicalborrowlong |? | | | | -|HYPEtools |? | | | | -|hypsoLoop |? | | | | -|immcp |? | | | | -|ImputeRobust |? | | | | -|incidence2 |1.2.3 |1 | | | -|INSPECTumours |? | | | | -|intRinsic |? | | | | -|intSDM |1.0.5 |1 | |1 | -|IRexamples |? | | | | -|irtQ |? | | | | -|IsoCorrectoR |? | | | | -|itsdm |? | | | | -|journalabbr |? | | | | -|jpgrid |? | | | | -|jpmesh |? | | | | -|lifeR |? | | | | -|loon.ggplot |? | | | | -|loon.shiny |? | | | | -|MACP |? | | | | -|mafs |? | | | | -|MainExistingDatasets |? | | | | -|MantaID |? | | | | -|manydata |0.8.2 |1 | | | -|mapboxapi |? | | | | -|mapme.biodiversity |? | | | | -|mapping |? | | | | -|mapsapi |? | | | | -|mapscanner |? | | | | -|marginaleffects |? | | | | -|MarketMatching |? | | | | -|MazamaSpatialPlots |? | | | | -|mbRes |? | | | | -|merTools |? | | | | -|meteoland |? | | | | -|microservices |? | | | | -|modeltime |? | | | | -|modeltime.ensemble |? | | | | -|modeltime.gluonts |? | | | | -|modeltime.h2o |? | | | | -|modeltime.resample |? | | | | -|moexer |? | | | | -|motif |? | | | | -|mpower |? | | | | -|MSclassifR |? | | | | -|multibiasmeta |? | | | | -|naturaList |? | | | | -|ncdfgeom |? | | | | -|nhdplusTools |? | | | | -|nhdR |? | | | | -|nlmixr2extra |? | | | | -|nlmixr2plot |? | | | | -|nlmixr2rpt |? | | | | -|numbat |? | | | | -|OBL |? | | | | -|occCite |? | | | | -|occUncertain |0.1.0 |1 | | | -|oceanexplorer |? | | | | -|oceanis |? | | | | -|ohsome |? | | | | -|OlinkAnalyze |? | | | | -|OpenLand |? | | | | -|palaeoSig |? | | | | -|panelr |? | | | | -|pathwayTMB |? | | | | -|pct |? | | | | -|peramo |? | | | | -|photosynthesis |? | | | | -|Platypus |? | | | | -|PLSiMCpp |? | | | | -|PoolTestR |? | | | | -|PopGenHelpR |? | | | | -|ppcSpatial |? | | | | -|prioriactions |? | | | | -|promotionImpact |? | | | | -|prqlr |? | | | | -|PSS.Health |0.6.1 |1 | | | -|PsychWordVec |? | | | | -|rangeModelMetadata |? | | | | -|rbenvo |? | | | | -|RBesT |? | | | | -|rcontroll |? | | | | -|rcssci |? | | | | -|RCzechia |? | | | | -|rdss |? | | | | -|redist |? | | | | -|remap |? | | | | -|report |? | | | | -|RevGadgets |? | | | | -|rGhanaCensus |? | | | | -|rnaturalearth |? | | | | -|roads |? | | | | -|Robyn |? | | | | -|Rsagacmd |? | | | | -|rsinaica |? | | | | -|rstac |? | | | | -|RVA |? | | | | -|saeSim |0.11.0 |1 | | | -|SAMtool |? | | | | -|sandwichr |? | | | | -|scGate |? | | | | -|SCpubr |? | | | | -|SDGdetector |2.7.1 |1 | | | -|SDLfilter |? | | | | -|sdmApp |? | | | | -|sf |? | | | | -|sfdep |? | | | | -|sfnetworks |? | | | | -|sftime |? | | | | -|ShellChron |? | | | | -|shinyHugePlot |? | | | | -|simodels |? | | | | -|simplevis |? | | | | -|sits |? | | | | -|sjPlot |? | | | | -|sjstats |? | | | | -|sknifedatar |? | | | | -|slendr |? | | | | -|sociome |2.1.0 |1 | |1 | -|SpaDES.tools |? | | | | -|SPARTAAS |1.1.0 |1 | | | -|spatgeom |? | | | | -|SpatialEpi |1.2.8 |1 | | | -|SpatialKDE |? | | | | -|spatialrisk |? | | | | -|spatialsample |? | | | | -|spDates |? | | | | -|spectacles |0.5-3 |1 | | | -|spnaf |? | | | | -|spNetwork |? | | | | -|spqdep |? | | | | -|spup |? | | | | -|stars |? | | | | -|starsTileServer |? | | | | -|stats19 |? | | | | -|statsExpressions |? | | | | -|stortingscrape |? | | | | -|stplanr |? | | | | -|stppSim |? | | | | -|stxplore |? | | | | -|SUNGEO |? | | | | -|swfscAirDAS |0.2.3 |1 | | | -|SWTools |? | | | | -|tame |? | | | | -|telemac |? | | | | -|tidybayes |? | | | | -|tidyposterior |? | | | | -|tidySEM |? | | | | -|tidytags |? | | | | -|tilemaps |? | | | | -|timetk |? | | | | -|tinyarray |? | | | | -|tipmap |? | | | | -|tmap |? | | | | -|trackdf |? | | | | -|trending |? | | | | -|TUFLOWR |? | | | | -|VancouvR |? | | | | -|vivid |? | | | | -|wallace |? | | | | -|waterquality |? | | | | -|Wats |? | | | | -|waves |0.2.4 |1 | | | -|wdpar |? | | | | -|wearables |0.8.1 |1 | | | -|webSDM |? | | | | -|wrappedtools |? | | | | -|xpose.nlmixr2 |? | | | | -|zipcodeR |0.3.5 |1 | | | -|zonebuilder |? | | | | +|package |version |error |warning |note | +|:--------------|:-------|:-----|:-------|:----| +|ADAM |? | | | | +|AGread |? | | | | +|AMARETTO |? | | | | +|amplican |? | | | | +|anomalize |? | | | | +|bayesmodels |? | | | | +|BMTME |? | | | | +|brendaDb |? | | | | +|BUSpaRse |? | | | | +|cattonum |? | | | | +|ceRNAnetsim |? | | | | +|COMPASS |? | | | | +|cort |? | | | | +|ctDNAtools |? | | | | +|CytoML |? | | | | +|datastructures |? | | | | +|DeLorean |? | | | | +|DepecheR |? | | | | +|destiny |? | | | | +|DiffBind |? | | | | +|diffman |? | | | | +|diffrprojects |? | | | | +|dynfrail |? | | | | +|epiphy |? | | | | +|evaluator |? | | | | +|expstudies |? | | | | +|fipe |? | | | | +|foieGras |? | | | | +|ImputeRobust |? | | | | +|IsoCorrectoR |? | | | | +|loon.ggplot |? | | | | +|loon.shiny |? | | | | +|mafs |? | | | | +|MarketMatching |? | | | | +|modeltime.h2o |? | | | | +|Platypus |? | | | | +|SCtools |? | | | | +|sknifedatar |? | | | | +|tidyfit |? | | | | +|vivid |? | | | | -## New problems (3) +## New problems (2) |package |version |error |warning |note | |:---------|:-------|:------|:-------|:----| -|[openalexR](problems.md#openalexr)|1.0.0 | |__+1__ | | -|[portalr](problems.md#portalr)|0.3.11 |__+1__ | | | -|[rapbase](problems.md#rapbase)|1.24.0 |__+1__ | | | +|[covidcast](problems.md#covidcast)|0.5.0 |__+1__ | |1 | +|[scGOclust](problems.md#scgoclust)|0.1.0 |__+1__ | | | diff --git a/revdep/cran.md b/revdep/cran.md index 701585682..00a530d0f 100644 --- a/revdep/cran.md +++ b/revdep/cran.md @@ -1,238 +1,27 @@ ## revdepcheck results -We checked 4257 reverse dependencies (4201 from CRAN + 56 from Bioconductor), comparing R CMD check results across CRAN and dev versions of this package. +We checked 4392 reverse dependencies (4359 from CRAN + 33 from Bioconductor), comparing R CMD check results across CRAN and dev versions of this package. - * We saw 3 new problems - * We failed to check 215 packages + * We saw 2 new problems + * We failed to check 7 packages Issues with CRAN packages are summarised below. ### New problems (This reports the first line of each new failure) -* openalexR - checking re-building of vignette outputs ... WARNING +* covidcast + checking re-building of vignette outputs ... ERROR -* portalr - checking tests ... ERROR - -* rapbase - checking tests ... ERROR +* scGOclust + checking re-building of vignette outputs ... ERROR ### Failed to check -* abmR (NA) -* abstr (NA) -* accept (NA) -* afex (NA) -* agridat (NA) -* autoTS (NA) -* bangladesh (NA) -* bayesian (NA) -* bayesnec (NA) -* bayesplot (NA) -* BayesPostEst (NA) -* bayesrules (NA) -* bdl (NA) -* beadplexr (NA) -* BiodiversityR (NA) -* blocs (NA) -* breathtestcore (NA) -* broom.helpers (NA) -* broom.mixed (NA) -* cancensus (NA) -* CCAMLRGIS (NA) -* ChineseNames (NA) -* choroplethr (NA) -* cinaR (NA) -* CoordinateCleaner (NA) -* CopernicusMarine (NA) -* CRE (NA) -* cubble (NA) -* cxr (NA) -* cyclestreets (NA) -* datawizard (NA) -* dbmss (NA) -* dycdtools (NA) -* dynamicSDM (NA) -* edbuildmapr (NA) -* EFDR (NA) -* embed (NA) -* EnvExpInd (NA) -* escalation (NA) -* eSDM (NA) -* ESTER (NA) -* fable.prophet (NA) -* FAMetA (NA) -* fgdr (NA) -* finnts (NA) -* FORTLS (NA) -* FRK (NA) -* fsr (NA) -* genekitr (NA) -* geocmeans (NA) -* GeodesiCL (NA) -* ggchangepoint (NA) -* ggOceanMaps (NA) -* ggPMX (NA) -* ggspatial (NA) -* ggstatsplot (NA) -* glottospace (NA) -* GPSeqClus (NA) -* GREENeR (NA) -* gtfs2gps (NA) -* gumboot (NA) -* gwavr (NA) -* GWPR.light (NA) -* happign (NA) -* healthyR.ai (NA) -* healthyR.ts (NA) -* healthyverse (NA) -* himach (NA) -* historicalborrowlong (NA) -* HYPEtools (NA) -* hypsoLoop (NA) -* immcp (NA) -* ImputeRobust (NA) -* incidence2 (NA) -* INSPECTumours (NA) -* intSDM (NA) -* IRexamples (NA) -* itsdm (NA) -* jpgrid (NA) -* jpmesh (NA) -* loon.ggplot (NA) -* loon.shiny (NA) -* MACP (NA) -* MainExistingDatasets (NA) -* manydata (NA) -* mapboxapi (NA) -* mapme.biodiversity (NA) -* mapping (NA) -* mapsapi (NA) -* mapscanner (NA) -* marginaleffects (NA) -* MarketMatching (NA) -* MazamaSpatialPlots (NA) -* merTools (NA) -* meteoland (NA) -* modeltime (NA) -* modeltime.ensemble (NA) -* modeltime.gluonts (NA) -* modeltime.h2o (NA) -* modeltime.resample (NA) -* motif (NA) -* mpower (NA) -* MSclassifR (NA) -* multibiasmeta (NA) -* naturaList (NA) -* ncdfgeom (NA) -* nhdplusTools (NA) -* nhdR (NA) -* nlmixr2extra (NA) -* nlmixr2plot (NA) -* nlmixr2rpt (NA) -* numbat (NA) -* occCite (NA) -* occUncertain (NA) -* oceanexplorer (NA) -* oceanis (NA) -* ohsome (NA) -* OlinkAnalyze (NA) -* OpenLand (NA) -* palaeoSig (NA) -* panelr (NA) -* pathwayTMB (NA) -* pct (NA) -* photosynthesis (NA) -* Platypus (NA) -* PoolTestR (NA) -* PopGenHelpR (NA) -* ppcSpatial (NA) -* prioriactions (NA) -* promotionImpact (NA) -* PSS.Health (NA) -* PsychWordVec (NA) -* rangeModelMetadata (NA) -* rbenvo (NA) -* RBesT (NA) -* rcontroll (NA) -* RCzechia (NA) -* rdss (NA) -* redist (NA) -* remap (NA) -* report (NA) -* rGhanaCensus (NA) -* rnaturalearth (NA) -* roads (NA) -* Robyn (NA) -* Rsagacmd (NA) -* rsinaica (NA) -* rstac (NA) -* RVA (NA) -* saeSim (NA) -* SAMtool (NA) -* sandwichr (NA) -* SCpubr (NA) -* SDGdetector (NA) -* SDLfilter (NA) -* sdmApp (NA) -* sf (NA) -* sfdep (NA) -* sfnetworks (NA) -* sftime (NA) -* ShellChron (NA) -* simodels (NA) -* simplevis (NA) -* sits (NA) -* sjPlot (NA) -* sjstats (NA) -* sknifedatar (NA) -* slendr (NA) -* sociome (NA) -* SpaDES.tools (NA) -* SPARTAAS (NA) -* spatgeom (NA) -* SpatialEpi (NA) -* SpatialKDE (NA) -* spatialrisk (NA) -* spatialsample (NA) -* spDates (NA) -* spectacles (NA) -* spnaf (NA) -* spNetwork (NA) -* spqdep (NA) -* spup (NA) -* stars (NA) -* starsTileServer (NA) -* stats19 (NA) -* statsExpressions (NA) -* stplanr (NA) -* stppSim (NA) -* stxplore (NA) -* SUNGEO (NA) -* swfscAirDAS (NA) -* SWTools (NA) -* telemac (NA) -* tidybayes (NA) -* tidyposterior (NA) -* tidySEM (NA) -* tilemaps (NA) -* timetk (NA) -* tinyarray (NA) -* tipmap (NA) -* tmap (NA) -* trackdf (NA) -* trending (NA) -* TUFLOWR (NA) -* VancouvR (NA) -* vivid (NA) -* wallace (NA) -* waterquality (NA) -* waves (NA) -* wdpar (NA) -* wearables (NA) -* webSDM (NA) -* xpose.nlmixr2 (NA) -* zipcodeR (NA) -* zonebuilder (NA) +* ImputeRobust (NA) +* loon.ggplot (NA) +* loon.shiny (NA) +* MarketMatching (NA) +* Platypus (NA) +* tidyfit (NA) +* vivid (NA) diff --git a/revdep/failures.md b/revdep/failures.md index 61355b43c..debeab535 100644 --- a/revdep/failures.md +++ b/revdep/failures.md @@ -1,14 +1,13 @@ -# abmR +# ADAM
-* Version: 1.0.8 +* Version: NA * GitHub: NA -* Source code: https://github.com/cran/abmR -* Date/Publication: 2023-01-16 01:20:02 UTC -* Number of recursive dependencies: 162 +* Source code: https://github.com/cran/ADAM +* Number of recursive dependencies: 95 -Run `revdepcheck::cloud_details(, "abmR")` for more info +Run `revdepcheck::cloud_details(, "ADAM")` for more info
@@ -17,23 +16,7 @@ Run `revdepcheck::cloud_details(, "abmR")` for more info ### Devel ``` -* using log directory ‘/tmp/workdir/abmR/new/abmR.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘abmR/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘abmR’ version ‘1.0.8’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR @@ -43,40 +26,23 @@ Status: 1 ERROR ### CRAN ``` -* using log directory ‘/tmp/workdir/abmR/old/abmR.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘abmR/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘abmR’ version ‘1.0.8’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR ``` -# abstr +# AGread
-* Version: 0.4.1 -* GitHub: https://github.com/a-b-street/abstr -* Source code: https://github.com/cran/abstr -* Date/Publication: 2021-11-30 08:10:05 UTC -* Number of recursive dependencies: 125 +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/AGread +* Number of recursive dependencies: 91 -Run `revdepcheck::cloud_details(, "abstr")` for more info +Run `revdepcheck::cloud_details(, "AGread")` for more info
@@ -85,23 +51,7 @@ Run `revdepcheck::cloud_details(, "abstr")` for more info ### Devel ``` -* using log directory ‘/tmp/workdir/abstr/new/abstr.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘abstr/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘abstr’ version ‘0.4.1’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Packages required but not available: 'lwgeom', 'sf' -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR @@ -111,40 +61,23 @@ Status: 1 ERROR ### CRAN ``` -* using log directory ‘/tmp/workdir/abstr/old/abstr.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘abstr/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘abstr’ version ‘0.4.1’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Packages required but not available: 'lwgeom', 'sf' -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR ``` -# accept +# AMARETTO
-* Version: 1.0.0 +* Version: NA * GitHub: NA -* Source code: https://github.com/cran/accept -* Date/Publication: 2023-02-06 20:52:31 UTC -* Number of recursive dependencies: 97 +* Source code: https://github.com/cran/AMARETTO +* Number of recursive dependencies: 155 -Run `revdepcheck::cloud_details(, "accept")` for more info +Run `revdepcheck::cloud_details(, "AMARETTO")` for more info
@@ -153,27 +86,7 @@ Run `revdepcheck::cloud_details(, "accept")` for more info ### Devel ``` -* using log directory ‘/tmp/workdir/accept/new/accept.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘accept/DESCRIPTION’ ... OK -* this is package ‘accept’ version ‘1.0.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... 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 ‘accept’ can be installed ... ERROR -Installation failed. -See ‘/tmp/workdir/accept/new/accept.Rcheck/00install.out’ for details. -* DONE -Status: 1 ERROR + @@ -183,43 +96,23 @@ Status: 1 ERROR ### CRAN ``` -* using log directory ‘/tmp/workdir/accept/old/accept.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘accept/DESCRIPTION’ ... OK -* this is package ‘accept’ version ‘1.0.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... 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 ‘accept’ can be installed ... ERROR -Installation failed. -See ‘/tmp/workdir/accept/old/accept.Rcheck/00install.out’ for details. -* DONE -Status: 1 ERROR + ``` -# ADAM +# amplican
* Version: NA * GitHub: NA -* Source code: https://github.com/cran/ADAM -* Number of recursive dependencies: 94 +* Source code: https://github.com/cran/amplican +* Number of recursive dependencies: 117 -Run `revdepcheck::cloud_details(, "ADAM")` for more info +Run `revdepcheck::cloud_details(, "amplican")` for more info
@@ -245,17 +138,16 @@ Run `revdepcheck::cloud_details(, "ADAM")` for more info ``` -# afex +# anomalize
-* Version: 1.2-1 -* GitHub: https://github.com/singmann/afex -* Source code: https://github.com/cran/afex -* Date/Publication: 2023-01-09 08:40:11 UTC -* Number of recursive dependencies: 224 +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/anomalize +* Number of recursive dependencies: 205 -Run `revdepcheck::cloud_details(, "afex")` for more info +Run `revdepcheck::cloud_details(, "anomalize")` for more info
@@ -264,27 +156,7 @@ Run `revdepcheck::cloud_details(, "afex")` for more info ### Devel ``` -* using log directory ‘/tmp/workdir/afex/new/afex.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘afex/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘afex’ version ‘1.2-1’ -* package encoding: UTF-8 -* checking package namespace information ... OK -... - ‘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’... OK - ‘assumptions_of_ANOVAs.Rmd’ using ‘UTF-8’... OK - ‘introduction-mixed-models.pdf.asis’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: 1 NOTE + @@ -294,43 +166,23 @@ Status: 1 NOTE ### CRAN ``` -* using log directory ‘/tmp/workdir/afex/old/afex.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘afex/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘afex’ version ‘1.2-1’ -* package encoding: UTF-8 -* checking package namespace information ... OK -... - ‘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’... OK - ‘assumptions_of_ANOVAs.Rmd’ using ‘UTF-8’... OK - ‘introduction-mixed-models.pdf.asis’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: 1 NOTE + ``` -# AGread +# bayesmodels
* Version: NA * GitHub: NA -* Source code: https://github.com/cran/AGread -* Number of recursive dependencies: 157 +* Source code: https://github.com/cran/bayesmodels +* Number of recursive dependencies: 261 -Run `revdepcheck::cloud_details(, "AGread")` for more info +Run `revdepcheck::cloud_details(, "bayesmodels")` for more info
@@ -356,17 +208,16 @@ Run `revdepcheck::cloud_details(, "AGread")` for more info ``` -# agridat +# BMTME
-* Version: 1.21 -* GitHub: https://github.com/kwstat/agridat -* Source code: https://github.com/cran/agridat -* Date/Publication: 2022-06-15 08:30:07 UTC -* Number of recursive dependencies: 257 +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/BMTME +* Number of recursive dependencies: 64 -Run `revdepcheck::cloud_details(, "agridat")` for more info +Run `revdepcheck::cloud_details(, "BMTME")` for more info
@@ -375,27 +226,7 @@ Run `revdepcheck::cloud_details(, "agridat")` for more info ### Devel ``` -* using log directory ‘/tmp/workdir/agridat/new/agridat.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘agridat/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘agridat’ version ‘1.21’ -* package encoding: UTF-8 -* checking package namespace information ... OK -... -* checking for unstated dependencies in vignettes ... OK -* checking package vignettes in ‘inst/doc’ ... OK -* checking running R code from vignettes ... NONE - ‘agridat_data.Rmd’ using ‘UTF-8’... OK - ‘agridat_examples.Rmd’ using ‘UTF-8’... OK - ‘agridat_intro.Rmd’ using ‘UTF-8’... OK - ‘agridat_uniformity.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: OK + @@ -405,43 +236,23 @@ Status: OK ### CRAN ``` -* using log directory ‘/tmp/workdir/agridat/old/agridat.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘agridat/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘agridat’ version ‘1.21’ -* package encoding: UTF-8 -* checking package namespace information ... OK -... -* checking for unstated dependencies in vignettes ... OK -* checking package vignettes in ‘inst/doc’ ... OK -* checking running R code from vignettes ... NONE - ‘agridat_data.Rmd’ using ‘UTF-8’... OK - ‘agridat_examples.Rmd’ using ‘UTF-8’... OK - ‘agridat_intro.Rmd’ using ‘UTF-8’... OK - ‘agridat_uniformity.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: OK + ``` -# ags +# brendaDb
* Version: NA * GitHub: NA -* Source code: https://github.com/cran/ags -* Number of recursive dependencies: 54 +* Source code: https://github.com/cran/brendaDb +* Number of recursive dependencies: 120 -Run `revdepcheck::cloud_details(, "ags")` for more info +Run `revdepcheck::cloud_details(, "brendaDb")` for more info
@@ -467,16 +278,16 @@ Run `revdepcheck::cloud_details(, "ags")` for more info ``` -# AMARETTO +# BUSpaRse
* Version: NA * GitHub: NA -* Source code: https://github.com/cran/AMARETTO -* Number of recursive dependencies: 155 +* Source code: https://github.com/cran/BUSpaRse +* Number of recursive dependencies: 157 -Run `revdepcheck::cloud_details(, "AMARETTO")` for more info +Run `revdepcheck::cloud_details(, "BUSpaRse")` for more info
@@ -502,16 +313,16 @@ Run `revdepcheck::cloud_details(, "AMARETTO")` for more info ``` -# amplican +# cattonum
* Version: NA * GitHub: NA -* Source code: https://github.com/cran/amplican -* Number of recursive dependencies: 116 +* Source code: https://github.com/cran/cattonum +* Number of recursive dependencies: 79 -Run `revdepcheck::cloud_details(, "amplican")` for more info +Run `revdepcheck::cloud_details(, "cattonum")` for more info
@@ -537,17 +348,16 @@ Run `revdepcheck::cloud_details(, "amplican")` for more info ``` -# autoTS +# ceRNAnetsim
-* Version: 0.9.11 -* GitHub: https://github.com/vivienroussez/autots -* Source code: https://github.com/cran/autoTS -* Date/Publication: 2020-06-05 12:20:06 UTC -* Number of recursive dependencies: 116 +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/ceRNAnetsim +* Number of recursive dependencies: 100 -Run `revdepcheck::cloud_details(, "autoTS")` for more info +Run `revdepcheck::cloud_details(, "ceRNAnetsim")` for more info
@@ -556,23 +366,7 @@ Run `revdepcheck::cloud_details(, "autoTS")` for more info ### Devel ``` -* using log directory ‘/tmp/workdir/autoTS/new/autoTS.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘autoTS/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘autoTS’ version ‘0.9.11’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘prophet’ -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR @@ -582,40 +376,23 @@ Status: 1 ERROR ### CRAN ``` -* using log directory ‘/tmp/workdir/autoTS/old/autoTS.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘autoTS/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘autoTS’ version ‘0.9.11’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘prophet’ -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR ``` -# bangladesh +# COMPASS
-* Version: 1.0.0 +* Version: NA * GitHub: NA -* Source code: https://github.com/cran/bangladesh -* Date/Publication: 2022-10-28 16:30:05 UTC -* Number of recursive dependencies: 94 +* Source code: https://github.com/cran/COMPASS +* Number of recursive dependencies: 151 -Run `revdepcheck::cloud_details(, "bangladesh")` for more info +Run `revdepcheck::cloud_details(, "COMPASS")` for more info
@@ -624,22 +401,7 @@ Run `revdepcheck::cloud_details(, "bangladesh")` for more info ### Devel ``` -* using log directory ‘/tmp/workdir/bangladesh/new/bangladesh.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘bangladesh/DESCRIPTION’ ... OK -* this is package ‘bangladesh’ version ‘1.0.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR @@ -649,39 +411,23 @@ Status: 1 ERROR ### CRAN ``` -* using log directory ‘/tmp/workdir/bangladesh/old/bangladesh.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘bangladesh/DESCRIPTION’ ... OK -* this is package ‘bangladesh’ version ‘1.0.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR ``` -# bayesian +# cort
-* Version: 0.0.9 -* GitHub: https://github.com/hsbadr/bayesian -* Source code: https://github.com/cran/bayesian -* Date/Publication: 2022-06-16 23:00:02 UTC -* Number of recursive dependencies: 187 +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/cort +* Number of recursive dependencies: 76 -Run `revdepcheck::cloud_details(, "bayesian")` for more info +Run `revdepcheck::cloud_details(, "cort")` for more info
@@ -690,25 +436,7 @@ Run `revdepcheck::cloud_details(, "bayesian")` for more info ### Devel ``` -* using log directory ‘/tmp/workdir/bayesian/new/bayesian.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘bayesian/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘bayesian’ version ‘0.0.9’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘brms’ - -Package suggested but not available for checking: ‘rstan’ -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR @@ -718,41 +446,23 @@ Status: 1 ERROR ### CRAN ``` -* using log directory ‘/tmp/workdir/bayesian/old/bayesian.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘bayesian/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘bayesian’ version ‘0.0.9’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘brms’ - -Package suggested but not available for checking: ‘rstan’ -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR ``` -# bayesmodels +# ctDNAtools
* Version: NA * GitHub: NA -* Source code: https://github.com/cran/bayesmodels -* Number of recursive dependencies: 259 +* Source code: https://github.com/cran/ctDNAtools +* Number of recursive dependencies: 144 -Run `revdepcheck::cloud_details(, "bayesmodels")` for more info +Run `revdepcheck::cloud_details(, "ctDNAtools")` for more info
@@ -778,14491 +488,16 @@ Run `revdepcheck::cloud_details(, "bayesmodels")` for more info ``` -# bayesnec +# CytoML
-* Version: 2.1.0.2 -* GitHub: https://github.com/open-aims/bayesnec -* Source code: https://github.com/cran/bayesnec -* Date/Publication: 2023-02-21 00:30:03 UTC -* Number of recursive dependencies: 133 - -Run `revdepcheck::cloud_details(, "bayesnec")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/bayesnec/new/bayesnec.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘bayesnec/DESCRIPTION’ ... OK -* this is package ‘bayesnec’ version ‘2.1.0.2’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘brms’ - -Package suggested but not available for checking: ‘rstan’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/bayesnec/old/bayesnec.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘bayesnec/DESCRIPTION’ ... OK -* this is package ‘bayesnec’ version ‘2.1.0.2’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘brms’ - -Package suggested but not available for checking: ‘rstan’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# bayesplot - -
- -* Version: 1.10.0 -* GitHub: https://github.com/stan-dev/bayesplot -* Source code: https://github.com/cran/bayesplot -* Date/Publication: 2022-11-16 22:00:08 UTC -* Number of recursive dependencies: 127 - -Run `revdepcheck::cloud_details(, "bayesplot")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/bayesplot/new/bayesplot.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘bayesplot/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘bayesplot’ version ‘1.10.0’ -* package encoding: UTF-8 -* checking package namespace information ... 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 - ‘graphical-ppcs.Rmd’ using ‘UTF-8’... OK - ‘plotting-mcmc-draws.Rmd’ using ‘UTF-8’... OK - ‘visual-mcmc-diagnostics.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: 2 NOTEs - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/bayesplot/old/bayesplot.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘bayesplot/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘bayesplot’ version ‘1.10.0’ -* package encoding: UTF-8 -* checking package namespace information ... 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 - ‘graphical-ppcs.Rmd’ using ‘UTF-8’... OK - ‘plotting-mcmc-draws.Rmd’ using ‘UTF-8’... OK - ‘visual-mcmc-diagnostics.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: 2 NOTEs - - - - - -``` -# BayesPostEst - -
- -* Version: 0.3.2 -* GitHub: https://github.com/ShanaScogin/BayesPostEst -* Source code: https://github.com/cran/BayesPostEst -* Date/Publication: 2021-11-11 08:10:05 UTC -* Number of recursive dependencies: 159 - -Run `revdepcheck::cloud_details(, "BayesPostEst")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/BayesPostEst/new/BayesPostEst.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘BayesPostEst/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘BayesPostEst’ version ‘0.3.2’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Packages required but not available: 'rstanarm', 'brms' - -Package suggested but not available for checking: ‘rstan’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/BayesPostEst/old/BayesPostEst.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘BayesPostEst/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘BayesPostEst’ version ‘0.3.2’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Packages required but not available: 'rstanarm', 'brms' - -Package suggested but not available for checking: ‘rstan’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# bayesrules - -
- -* Version: 0.0.2 -* GitHub: https://github.com/bayes-rules/bayesrules -* Source code: https://github.com/cran/bayesrules -* Date/Publication: 2021-09-25 04:30:07 UTC -* Number of recursive dependencies: 135 - -Run `revdepcheck::cloud_details(, "bayesrules")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/bayesrules/new/bayesrules.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘bayesrules/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘bayesrules’ version ‘0.0.2’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘rstanarm’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/bayesrules/old/bayesrules.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘bayesrules/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘bayesrules’ version ‘0.0.2’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘rstanarm’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# 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: 145 - -Run `revdepcheck::cloud_details(, "bdl")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/bdl/new/bdl.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘bdl/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘bdl’ version ‘1.0.5’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/bdl/old/bdl.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘bdl/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘bdl’ version ‘1.0.5’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# beadplexr - -
- -* Version: 0.4.1 -* GitHub: NA -* Source code: https://github.com/cran/beadplexr -* Date/Publication: 2022-03-05 13:50:02 UTC -* Number of recursive dependencies: 127 - -Run `revdepcheck::cloud_details(, "beadplexr")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/beadplexr/new/beadplexr.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘beadplexr/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘beadplexr’ version ‘0.4.1’ -* package encoding: UTF-8 -* checking package namespace information ... 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 - ‘cba_macsplex_example.Rmd’ using ‘UTF-8’... OK - ‘legendplex_analysis.Rmd’ using ‘UTF-8’... OK - ‘preparing_flow_data.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: 1 NOTE - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/beadplexr/old/beadplexr.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘beadplexr/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘beadplexr’ version ‘0.4.1’ -* package encoding: UTF-8 -* checking package namespace information ... 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 - ‘cba_macsplex_example.Rmd’ using ‘UTF-8’... OK - ‘legendplex_analysis.Rmd’ using ‘UTF-8’... OK - ‘preparing_flow_data.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: 1 NOTE - - - - - -``` -# BiodiversityR - -
- -* Version: 2.15-1 -* GitHub: NA -* Source code: https://github.com/cran/BiodiversityR -* Date/Publication: 2023-01-06 10:00:30 UTC -* Number of recursive dependencies: 300 - -Run `revdepcheck::cloud_details(, "BiodiversityR")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/BiodiversityR/new/BiodiversityR.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘BiodiversityR/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘BiodiversityR’ version ‘2.15-1’ -* checking package namespace information ... OK -* checking package dependencies ... NOTE -... -* 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: 2 NOTEs - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/BiodiversityR/old/BiodiversityR.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘BiodiversityR/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘BiodiversityR’ version ‘2.15-1’ -* checking package namespace information ... OK -* checking package dependencies ... NOTE -... -* 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: 2 NOTEs - - - - - -``` -# blocs - -
- -* Version: 0.1.0 -* GitHub: NA -* Source code: https://github.com/cran/blocs -* Date/Publication: 2022-11-23 11:20:06 UTC -* Number of recursive dependencies: 161 - -Run `revdepcheck::cloud_details(, "blocs")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/blocs/new/blocs.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘blocs/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘blocs’ version ‘0.1.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required and available but unsuitable version: ‘mgcv’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/blocs/old/blocs.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘blocs/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘blocs’ version ‘0.1.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required and available but unsuitable version: ‘mgcv’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# breathtestcore - -
- -* Version: 0.8.6 -* GitHub: https://github.com/dmenne/breathtestcore -* Source code: https://github.com/cran/breathtestcore -* Date/Publication: 2023-02-13 14:00:07 UTC -* Number of recursive dependencies: 119 - -Run `revdepcheck::cloud_details(, "breathtestcore")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/breathtestcore/new/breathtestcore.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘breathtestcore/DESCRIPTION’ ... OK -* this is package ‘breathtestcore’ version ‘0.8.6’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... NOTE -... -* 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 - ‘data_formats.Rmd’ using ‘UTF-8’... OK - ‘methods_and_concepts.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: 2 NOTEs - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/breathtestcore/old/breathtestcore.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘breathtestcore/DESCRIPTION’ ... OK -* this is package ‘breathtestcore’ version ‘0.8.6’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... NOTE -... -* 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 - ‘data_formats.Rmd’ using ‘UTF-8’... OK - ‘methods_and_concepts.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: 2 NOTEs - - - - - -``` -# brendaDb - -
- -* Version: NA -* GitHub: NA -* Source code: https://github.com/cran/brendaDb -* Number of recursive dependencies: 120 - -Run `revdepcheck::cloud_details(, "brendaDb")` for more info - -
- -## Error before installation - -### Devel - -``` - - - - - - -``` -### CRAN - -``` - - - - - - -``` -# broom.helpers - -
- -* Version: 1.12.0 -* GitHub: https://github.com/larmarange/broom.helpers -* Source code: https://github.com/cran/broom.helpers -* Date/Publication: 2023-02-09 17:00:02 UTC -* Number of recursive dependencies: 226 - -Run `revdepcheck::cloud_details(, "broom.helpers")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/broom.helpers/new/broom.helpers.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘broom.helpers/DESCRIPTION’ ... OK -* this is package ‘broom.helpers’ version ‘1.12.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... NOTE -... -* 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 ... NONE - ‘tidy.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: 1 NOTE - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/broom.helpers/old/broom.helpers.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘broom.helpers/DESCRIPTION’ ... OK -* this is package ‘broom.helpers’ version ‘1.12.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... NOTE -... -* 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 ... NONE - ‘tidy.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: 1 NOTE - - - - - -``` -# broom.mixed - -
- -* Version: 0.2.9.4 -* GitHub: https://github.com/bbolker/broom.mixed -* Source code: https://github.com/cran/broom.mixed -* Date/Publication: 2022-04-17 17:42:29 UTC -* Number of recursive dependencies: 164 - -Run `revdepcheck::cloud_details(, "broom.mixed")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/broom.mixed/new/broom.mixed.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘broom.mixed/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘broom.mixed’ version ‘0.2.9.4’ -* package encoding: UTF-8 -* checking package namespace information ... 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 - ‘broom_mixed_intro.rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: 2 NOTEs - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/broom.mixed/old/broom.mixed.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘broom.mixed/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘broom.mixed’ version ‘0.2.9.4’ -* package encoding: UTF-8 -* checking package namespace information ... 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 - ‘broom_mixed_intro.rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: 2 NOTEs - - - - - -``` -# BUSpaRse - -
- -* Version: NA -* GitHub: NA -* Source code: https://github.com/cran/BUSpaRse -* Number of recursive dependencies: 157 - -Run `revdepcheck::cloud_details(, "BUSpaRse")` for more info - -
- -## Error before installation - -### Devel - -``` - - - - - - -``` -### CRAN - -``` - - - - - - -``` -# cancensus - -
- -* Version: 0.5.5 -* GitHub: https://github.com/mountainMath/cancensus -* Source code: https://github.com/cran/cancensus -* Date/Publication: 2023-01-23 08:40:06 UTC -* Number of recursive dependencies: 117 - -Run `revdepcheck::cloud_details(, "cancensus")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/cancensus/new/cancensus.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘cancensus/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘cancensus’ version ‘0.5.5’ -* package encoding: UTF-8 -* checking package namespace information ... OK -... - ‘Making_maps_with_cancensus.Rmd’ using ‘UTF-8’... OK - ‘Taxfiler_Data.Rmd’ using ‘UTF-8’... OK - ‘cancensus.Rmd’ using ‘UTF-8’... OK - ‘data_discovery.Rmd’ using ‘UTF-8’... OK - ‘intersecting_geometries.Rmd’ using ‘UTF-8’... OK - ‘statcan_attribute_files.Rmd’ using ‘UTF-8’... OK - ‘statcan_wds.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: 3 NOTEs - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/cancensus/old/cancensus.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘cancensus/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘cancensus’ version ‘0.5.5’ -* package encoding: UTF-8 -* checking package namespace information ... OK -... - ‘Making_maps_with_cancensus.Rmd’ using ‘UTF-8’... OK - ‘Taxfiler_Data.Rmd’ using ‘UTF-8’... OK - ‘cancensus.Rmd’ using ‘UTF-8’... OK - ‘data_discovery.Rmd’ using ‘UTF-8’... OK - ‘intersecting_geometries.Rmd’ using ‘UTF-8’... OK - ‘statcan_attribute_files.Rmd’ using ‘UTF-8’... OK - ‘statcan_wds.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: 3 NOTEs - - - - - -``` -# cattonum - -
- -* Version: NA -* GitHub: NA -* Source code: https://github.com/cran/cattonum -* Number of recursive dependencies: 78 - -Run `revdepcheck::cloud_details(, "cattonum")` for more info - -
- -## Error before installation - -### Devel - -``` - - - - - - -``` -### CRAN - -``` - - - - - - -``` -# CCAMLRGIS - -
- -* Version: 4.0.4 -* GitHub: https://github.com/ccamlr/CCAMLRGIS -* Source code: https://github.com/cran/CCAMLRGIS -* Date/Publication: 2023-02-07 04:12:37 UTC -* Number of recursive dependencies: 72 - -Run `revdepcheck::cloud_details(, "CCAMLRGIS")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/CCAMLRGIS/new/CCAMLRGIS.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘CCAMLRGIS/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘CCAMLRGIS’ version ‘4.0.4’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/CCAMLRGIS/old/CCAMLRGIS.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘CCAMLRGIS/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘CCAMLRGIS’ version ‘4.0.4’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# ceRNAnetsim - -
- -* Version: NA -* GitHub: NA -* Source code: https://github.com/cran/ceRNAnetsim -* Number of recursive dependencies: 99 - -Run `revdepcheck::cloud_details(, "ceRNAnetsim")` for more info - -
- -## Error before installation - -### Devel - -``` - - - - - - -``` -### CRAN - -``` - - - - - - -``` -# ChineseNames - -
- -* Version: 1.1.1 -* GitHub: https://github.com/psychbruce/ChineseNames -* Source code: https://github.com/cran/ChineseNames -* Date/Publication: 2021-11-29 16:40:02 UTC -* Number of recursive dependencies: 151 - -Run `revdepcheck::cloud_details(, "ChineseNames")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/ChineseNames/new/ChineseNames.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘ChineseNames/DESCRIPTION’ ... OK -* this is package ‘ChineseNames’ version ‘1.1.1’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘bruceR’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/ChineseNames/old/ChineseNames.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘ChineseNames/DESCRIPTION’ ... OK -* this is package ‘ChineseNames’ version ‘1.1.1’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘bruceR’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# choroplethr - -
- -* Version: 3.7.1 -* GitHub: NA -* Source code: https://github.com/cran/choroplethr -* Date/Publication: 2022-10-05 07:10:06 UTC -* Number of recursive dependencies: 127 - -Run `revdepcheck::cloud_details(, "choroplethr")` for more info - -
- -## In both - -* checking whether package ‘choroplethr’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/choroplethr/new/choroplethr.Rcheck/00install.out’ for details. - ``` - -## Installation - -### Devel - -``` -* installing *source* package ‘choroplethr’ ... -** package ‘choroplethr’ successfully unpacked and MD5 sums checked -** using staged installation -** R -** data -** byte-compile and prepare package for lazy loading -Error in loadNamespace(i, c(lib.loc, .libPaths()), versionCheck = vI[[i]]) : - there is no package called ‘sf’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart -Execution halted -ERROR: lazy loading failed for package ‘choroplethr’ -* removing ‘/tmp/workdir/choroplethr/new/choroplethr.Rcheck/choroplethr’ - - -``` -### CRAN - -``` -* installing *source* package ‘choroplethr’ ... -** package ‘choroplethr’ successfully unpacked and MD5 sums checked -** using staged installation -** R -** data -** byte-compile and prepare package for lazy loading -Error in loadNamespace(i, c(lib.loc, .libPaths()), versionCheck = vI[[i]]) : - there is no package called ‘sf’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart -Execution halted -ERROR: lazy loading failed for package ‘choroplethr’ -* removing ‘/tmp/workdir/choroplethr/old/choroplethr.Rcheck/choroplethr’ - - -``` -# cinaR - -
- -* Version: 0.2.3 -* GitHub: https://github.com/eonurk/cinaR -* Source code: https://github.com/cran/cinaR -* Date/Publication: 2022-05-18 14:00:09 UTC -* Number of recursive dependencies: 178 - -Run `revdepcheck::cloud_details(, "cinaR")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/cinaR/new/cinaR.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘cinaR/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘cinaR’ version ‘0.2.3’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘ChIPseeker’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/cinaR/old/cinaR.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘cinaR/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘cinaR’ version ‘0.2.3’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘ChIPseeker’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# COMPASS - -
- -* Version: NA -* GitHub: NA -* Source code: https://github.com/cran/COMPASS -* Number of recursive dependencies: 151 - -Run `revdepcheck::cloud_details(, "COMPASS")` for more info - -
- -## Error before installation - -### Devel - -``` - - - - - - -``` -### CRAN - -``` - - - - - - -``` -# CoordinateCleaner - -
- -* Version: 2.0-20 -* GitHub: https://github.com/ropensci/CoordinateCleaner -* Source code: https://github.com/cran/CoordinateCleaner -* Date/Publication: 2021-10-21 17:10:05 UTC -* Number of recursive dependencies: 115 - -Run `revdepcheck::cloud_details(, "CoordinateCleaner")` for more info - -
- -## In both - -* checking whether package ‘CoordinateCleaner’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/CoordinateCleaner/new/CoordinateCleaner.Rcheck/00install.out’ for details. - ``` - -## Installation - -### Devel - -``` -* installing *source* package ‘CoordinateCleaner’ ... -** package ‘CoordinateCleaner’ 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 ‘sf’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart -Execution halted -ERROR: lazy loading failed for package ‘CoordinateCleaner’ -* removing ‘/tmp/workdir/CoordinateCleaner/new/CoordinateCleaner.Rcheck/CoordinateCleaner’ - - -``` -### CRAN - -``` -* installing *source* package ‘CoordinateCleaner’ ... -** package ‘CoordinateCleaner’ 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 ‘sf’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart -Execution halted -ERROR: lazy loading failed for package ‘CoordinateCleaner’ -* removing ‘/tmp/workdir/CoordinateCleaner/old/CoordinateCleaner.Rcheck/CoordinateCleaner’ - - -``` -# CopernicusMarine - -
- -* Version: 0.0.6 -* GitHub: https://github.com/pepijn-devries/CopernicusMarine -* Source code: https://github.com/cran/CopernicusMarine -* Date/Publication: 2023-01-30 13:50:02 UTC -* Number of recursive dependencies: 113 - -Run `revdepcheck::cloud_details(, "CopernicusMarine")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/CopernicusMarine/new/CopernicusMarine.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘CopernicusMarine/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘CopernicusMarine’ version ‘0.0.6’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/CopernicusMarine/old/CopernicusMarine.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘CopernicusMarine/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘CopernicusMarine’ version ‘0.0.6’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# cort - -
- -* Version: NA -* GitHub: NA -* Source code: https://github.com/cran/cort -* Number of recursive dependencies: 75 - -Run `revdepcheck::cloud_details(, "cort")` for more info - -
- -## Error before installation - -### Devel - -``` - - - - - - -``` -### CRAN - -``` - - - - - - -``` -# covidmx - -
- -* Version: NA -* GitHub: NA -* Source code: https://github.com/cran/covidmx -* Number of recursive dependencies: 150 - -Run `revdepcheck::cloud_details(, "covidmx")` for more info - -
- -## Error before installation - -### Devel - -``` - - - - - - -``` -### CRAN - -``` - - - - - - -``` -# CRE - -
- -* Version: 0.2.0 -* GitHub: https://github.com/NSAPH-Software/CRE -* Source code: https://github.com/cran/CRE -* Date/Publication: 2023-01-19 20:20:02 UTC -* Number of recursive dependencies: 141 - -Run `revdepcheck::cloud_details(, "CRE")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/CRE/new/CRE.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘CRE/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘CRE’ version ‘0.2.0’ -* package encoding: UTF-8 -* checking package namespace information ... 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 - ‘CRE.Rmd’ using ‘UTF-8’... OK - ‘Contribution.Rmd’ using ‘UTF-8’... OK - ‘Testing-the-Package.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: 1 NOTE - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/CRE/old/CRE.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘CRE/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘CRE’ version ‘0.2.0’ -* package encoding: UTF-8 -* checking package namespace information ... 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 - ‘CRE.Rmd’ using ‘UTF-8’... OK - ‘Contribution.Rmd’ using ‘UTF-8’... OK - ‘Testing-the-Package.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: 1 NOTE - - - - - -``` -# ctDNAtools - -
- -* Version: NA -* GitHub: NA -* Source code: https://github.com/cran/ctDNAtools -* Number of recursive dependencies: 143 - -Run `revdepcheck::cloud_details(, "ctDNAtools")` for more info - -
- -## Error before installation - -### Devel - -``` - - - - - - -``` -### CRAN - -``` - - - - - - -``` -# cubble - -
- -* Version: 0.2.0 -* GitHub: https://github.com/huizezhang-sherry/cubble -* Source code: https://github.com/cran/cubble -* Date/Publication: 2022-11-17 12:30:02 UTC -* Number of recursive dependencies: 132 - -Run `revdepcheck::cloud_details(, "cubble")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/cubble/new/cubble.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘cubble/DESCRIPTION’ ... OK -* this is package ‘cubble’ version ‘0.2.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -Package suggested but not available for checking: ‘ozmaps’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/cubble/old/cubble.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘cubble/DESCRIPTION’ ... OK -* this is package ‘cubble’ version ‘0.2.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -Package suggested but not available for checking: ‘ozmaps’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# cxr - -
- -* Version: 1.0.0 -* GitHub: https://github.com/RadicalCommEcol/cxr -* Source code: https://github.com/cran/cxr -* Date/Publication: 2021-04-16 09:20:02 UTC -* Number of recursive dependencies: 128 - -Run `revdepcheck::cloud_details(, "cxr")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/cxr/new/cxr.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘cxr/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘cxr’ version ‘1.0.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -... -* checking package vignettes in ‘inst/doc’ ... OK -* checking running R code from vignettes ... NONE - ‘V1_Getting_started.Rmd’ using ‘UTF-8’... OK - ‘V2_Data_formats.Rmd’ using ‘UTF-8’... OK - ‘V3_Coexistence_metrics.Rmd’ using ‘UTF-8’... OK - ‘V4_Models.Rmd’ using ‘UTF-8’... OK - ‘V5_Abundance_projections.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: OK - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/cxr/old/cxr.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘cxr/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘cxr’ version ‘1.0.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -... -* checking package vignettes in ‘inst/doc’ ... OK -* checking running R code from vignettes ... NONE - ‘V1_Getting_started.Rmd’ using ‘UTF-8’... OK - ‘V2_Data_formats.Rmd’ using ‘UTF-8’... OK - ‘V3_Coexistence_metrics.Rmd’ using ‘UTF-8’... OK - ‘V4_Models.Rmd’ using ‘UTF-8’... OK - ‘V5_Abundance_projections.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: OK - - - - - -``` -# cyclestreets - -
- -* Version: 0.6.0 -* GitHub: https://github.com/cyclestreets/cyclestreets-r -* Source code: https://github.com/cran/cyclestreets -* Date/Publication: 2023-02-17 09:30:06 UTC -* Number of recursive dependencies: 67 - -Run `revdepcheck::cloud_details(, "cyclestreets")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/cyclestreets/new/cyclestreets.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘cyclestreets/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘cyclestreets’ version ‘0.6.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/cyclestreets/old/cyclestreets.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘cyclestreets/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘cyclestreets’ version ‘0.6.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# CytoML - -
- -* Version: NA -* GitHub: NA -* Source code: https://github.com/cran/CytoML -* Number of recursive dependencies: 105 - -Run `revdepcheck::cloud_details(, "CytoML")` for more info - -
- -## Error before installation - -### Devel - -``` - - - - - - -``` -### CRAN - -``` - - - - - - -``` -# D2MCS - -
- -* Version: NA -* GitHub: NA -* Source code: https://github.com/cran/D2MCS -* Number of recursive dependencies: 179 - -Run `revdepcheck::cloud_details(, "D2MCS")` for more info - -
- -## Error before installation - -### Devel - -``` - - - - - - -``` -### CRAN - -``` - - - - - - -``` -# datawizard - -
- -* Version: 0.6.5 -* GitHub: https://github.com/easystats/datawizard -* Source code: https://github.com/cran/datawizard -* Date/Publication: 2022-12-14 23:50:02 UTC -* Number of recursive dependencies: 186 - -Run `revdepcheck::cloud_details(, "datawizard")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/datawizard/new/datawizard.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘datawizard/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘datawizard’ version ‘0.6.5’ -* package encoding: UTF-8 -* checking package namespace information ... 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 - ‘selection_syntax.Rmd’ using ‘UTF-8’... OK - ‘standardize_data.Rmd’ using ‘UTF-8’... OK - ‘tidyverse_translation.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: 1 NOTE - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/datawizard/old/datawizard.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘datawizard/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘datawizard’ version ‘0.6.5’ -* package encoding: UTF-8 -* checking package namespace information ... 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 - ‘selection_syntax.Rmd’ using ‘UTF-8’... OK - ‘standardize_data.Rmd’ using ‘UTF-8’... OK - ‘tidyverse_translation.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: 1 NOTE - - - - - -``` -# dbmss - -
- -* Version: 2.8-0 -* GitHub: https://github.com/EricMarcon/dbmss -* Source code: https://github.com/cran/dbmss -* Date/Publication: 2023-01-06 15:10:05 UTC -* Number of recursive dependencies: 120 - -Run `revdepcheck::cloud_details(, "dbmss")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/dbmss/new/dbmss.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘dbmss/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘dbmss’ version ‘2.8-0’ -* package encoding: UTF-8 -* checking package namespace information ... 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 - ‘dbmss.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/dbmss/old/dbmss.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘dbmss/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘dbmss’ version ‘2.8-0’ -* package encoding: UTF-8 -* checking package namespace information ... 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 - ‘dbmss.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: 1 ERROR - - - - - -``` -# DeLorean - -
- -* Version: NA -* GitHub: NA -* Source code: https://github.com/cran/DeLorean -* Number of recursive dependencies: 120 - -Run `revdepcheck::cloud_details(, "DeLorean")` for more info - -
- -## Error before installation - -### Devel - -``` - - - - - - -``` -### CRAN - -``` - - - - - - -``` -# DepecheR - -
- -* Version: NA -* GitHub: NA -* Source code: https://github.com/cran/DepecheR -* Number of recursive dependencies: 116 - -Run `revdepcheck::cloud_details(, "DepecheR")` for more info - -
- -## Error before installation - -### Devel - -``` - - - - - - -``` -### CRAN - -``` - - - - - - -``` -# destiny - -
- -* Version: NA -* GitHub: NA -* Source code: https://github.com/cran/destiny -* Number of recursive dependencies: 243 - -Run `revdepcheck::cloud_details(, "destiny")` for more info - -
- -## Error before installation - -### Devel - -``` - - - - - - -``` -### CRAN - -``` - - - - - - -``` -# DiffBind - -
- -* Version: NA -* GitHub: NA -* Source code: https://github.com/cran/DiffBind -* Number of recursive dependencies: 158 - -Run `revdepcheck::cloud_details(, "DiffBind")` for more info - -
- -## Error before installation - -### Devel - -``` - - - - - - -``` -### CRAN - -``` - - - - - - -``` -# diffman - -
- -* Version: NA -* GitHub: NA -* Source code: https://github.com/cran/diffman -* Number of recursive dependencies: 125 - -Run `revdepcheck::cloud_details(, "diffman")` for more info - -
- -## Error before installation - -### Devel - -``` - - - - - - -``` -### CRAN - -``` - - - - - - -``` -# diffrprojects - -
- -* Version: NA -* GitHub: NA -* Source code: https://github.com/cran/diffrprojects -* Number of recursive dependencies: 65 - -Run `revdepcheck::cloud_details(, "diffrprojects")` for more info - -
- -## Error before installation - -### Devel - -``` - - - - - - -``` -### CRAN - -``` - - - - - - -``` -# dycdtools - -
- -* Version: 0.4.3 -* GitHub: https://github.com/SongyanYu/dycdtools -* Source code: https://github.com/cran/dycdtools -* Date/Publication: 2022-11-22 00:40:02 UTC -* Number of recursive dependencies: 89 - -Run `revdepcheck::cloud_details(, "dycdtools")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/dycdtools/new/dycdtools.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘dycdtools/DESCRIPTION’ ... OK -* this is package ‘dycdtools’ version ‘0.4.3’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... 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 ‘dycdtools’ can be installed ... ERROR -Installation failed. -See ‘/tmp/workdir/dycdtools/new/dycdtools.Rcheck/00install.out’ for details. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/dycdtools/old/dycdtools.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘dycdtools/DESCRIPTION’ ... OK -* this is package ‘dycdtools’ version ‘0.4.3’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... 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 ‘dycdtools’ can be installed ... ERROR -Installation failed. -See ‘/tmp/workdir/dycdtools/old/dycdtools.Rcheck/00install.out’ for details. -* DONE -Status: 1 ERROR - - - - - -``` -# dynamicSDM - -
- -* Version: 1.1 -* GitHub: https://github.com/r-a-dobson/dynamicSDM -* Source code: https://github.com/cran/dynamicSDM -* Date/Publication: 2023-02-27 13:22:30 UTC -* Number of recursive dependencies: 156 - -Run `revdepcheck::cloud_details(, "dynamicSDM")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/dynamicSDM/new/dynamicSDM.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘dynamicSDM/DESCRIPTION’ ... OK -* this is package ‘dynamicSDM’ version ‘1.1’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/dynamicSDM/old/dynamicSDM.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘dynamicSDM/DESCRIPTION’ ... OK -* this is package ‘dynamicSDM’ version ‘1.1’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# dynfrail - -
- -* Version: NA -* GitHub: NA -* Source code: https://github.com/cran/dynfrail -* Number of recursive dependencies: 57 - -Run `revdepcheck::cloud_details(, "dynfrail")` for more info - -
- -## Error before installation - -### Devel - -``` - - - - - - -``` -### CRAN - -``` - - - - - - -``` -# edbuildmapr - -
- -* Version: 0.3.1 -* GitHub: https://github.com/EdBuild/edbuildmapr -* Source code: https://github.com/cran/edbuildmapr -* Date/Publication: 2021-06-15 06:00:02 UTC -* Number of recursive dependencies: 98 - -Run `revdepcheck::cloud_details(, "edbuildmapr")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/edbuildmapr/new/edbuildmapr.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘edbuildmapr/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘edbuildmapr’ version ‘0.3.1’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/edbuildmapr/old/edbuildmapr.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘edbuildmapr/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘edbuildmapr’ version ‘0.3.1’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# EFDR - -
- -* Version: 1.2 -* GitHub: https://github.com/andrewzm/EFDR -* Source code: https://github.com/cran/EFDR -* Date/Publication: 2021-04-18 05:50:03 UTC -* Number of recursive dependencies: 105 - -Run `revdepcheck::cloud_details(, "EFDR")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/EFDR/new/EFDR.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘EFDR/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘EFDR’ version ‘1.2’ -* package encoding: UTF-8 -* checking package namespace information ... 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 - ‘EFDR_documents.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: OK - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/EFDR/old/EFDR.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘EFDR/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘EFDR’ version ‘1.2’ -* package encoding: UTF-8 -* checking package namespace information ... 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 - ‘EFDR_documents.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: OK - - - - - -``` -# embed - -
- -* Version: 1.0.0 -* GitHub: https://github.com/tidymodels/embed -* Source code: https://github.com/cran/embed -* Date/Publication: 2022-07-02 16:50:02 UTC -* Number of recursive dependencies: 183 - -Run `revdepcheck::cloud_details(, "embed")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/embed/new/embed.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘embed/DESCRIPTION’ ... OK -* this is package ‘embed’ version ‘1.0.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... NOTE -... - i In index: 1. - i With name: x3. - Caused by error in `.f()`: - ! The package "rstanarm" is required. - - [ FAIL 1 | WARN 2 | SKIP 56 | PASS 162 ] - Error: Test failures - Execution halted -* DONE -Status: 1 ERROR, 2 NOTEs - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/embed/old/embed.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘embed/DESCRIPTION’ ... OK -* this is package ‘embed’ version ‘1.0.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... NOTE -... - i In index: 1. - i With name: x3. - Caused by error in `.f()`: - ! The package "rstanarm" is required. - - [ FAIL 1 | WARN 2 | SKIP 56 | PASS 162 ] - Error: Test failures - Execution halted -* DONE -Status: 1 ERROR, 2 NOTEs - - - - - -``` -# EnvExpInd - -
- -* Version: 0.1.0 -* GitHub: https://github.com/Spatial-R/EnvExpInd -* Source code: https://github.com/cran/EnvExpInd -* Date/Publication: 2020-10-23 15:50:02 UTC -* Number of recursive dependencies: 67 - -Run `revdepcheck::cloud_details(, "EnvExpInd")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/EnvExpInd/new/EnvExpInd.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘EnvExpInd/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘EnvExpInd’ version ‘0.1.0’ -* package encoding: UTF-8 -* checking package namespace information ... 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 - ‘environment_exposure.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: OK - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/EnvExpInd/old/EnvExpInd.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘EnvExpInd/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘EnvExpInd’ version ‘0.1.0’ -* package encoding: UTF-8 -* checking package namespace information ... 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 - ‘environment_exposure.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: OK - - - - - -``` -# EpiForsk - -
- -* Version: NA -* GitHub: NA -* Source code: https://github.com/cran/EpiForsk -* Number of recursive dependencies: 76 - -Run `revdepcheck::cloud_details(, "EpiForsk")` for more info - -
- -## Error before installation - -### Devel - -``` - - - - - - -``` -### CRAN - -``` - - - - - - -``` -# epiphy - -
- -* Version: NA -* GitHub: NA -* Source code: https://github.com/cran/epiphy -* Number of recursive dependencies: 91 - -Run `revdepcheck::cloud_details(, "epiphy")` for more info - -
- -## Error before installation - -### Devel - -``` - - - - - - -``` -### CRAN - -``` - - - - - - -``` -# epitopeR - -
- -* Version: NA -* GitHub: NA -* Source code: https://github.com/cran/epitopeR -* Number of recursive dependencies: 160 - -Run `revdepcheck::cloud_details(, "epitopeR")` for more info - -
- -## Error before installation - -### Devel - -``` - - - - - - -``` -### CRAN - -``` - - - - - - -``` -# escalation - -
- -* Version: 0.1.4 -* GitHub: NA -* Source code: https://github.com/cran/escalation -* Date/Publication: 2020-10-18 21:40:06 UTC -* Number of recursive dependencies: 127 - -Run `revdepcheck::cloud_details(, "escalation")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/escalation/new/escalation.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘escalation/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘escalation’ version ‘0.1.4’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘trialr’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/escalation/old/escalation.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘escalation/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘escalation’ version ‘0.1.4’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘trialr’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# EScvtmle - -
- -* Version: NA -* GitHub: NA -* Source code: https://github.com/cran/EScvtmle -* Number of recursive dependencies: 78 - -Run `revdepcheck::cloud_details(, "EScvtmle")` for more info - -
- -## Error before installation - -### Devel - -``` - - - - - - -``` -### CRAN - -``` - - - - - - -``` -# eSDM - -
- -* Version: 0.3.7 -* GitHub: https://github.com/smwoodman/eSDM -* Source code: https://github.com/cran/eSDM -* Date/Publication: 2021-05-04 04:50:08 UTC -* Number of recursive dependencies: 130 - -Run `revdepcheck::cloud_details(, "eSDM")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/eSDM/new/eSDM.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘eSDM/DESCRIPTION’ ... OK -* this is package ‘eSDM’ version ‘0.3.7’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/eSDM/old/eSDM.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘eSDM/DESCRIPTION’ ... OK -* this is package ‘eSDM’ version ‘0.3.7’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# ESTER - -
- -* Version: 0.2.0 -* GitHub: https://github.com/lnalborczyk/ESTER -* Source code: https://github.com/cran/ESTER -* Date/Publication: 2017-12-10 14:21:14 UTC -* Number of recursive dependencies: 137 - -Run `revdepcheck::cloud_details(, "ESTER")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/ESTER/new/ESTER.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘ESTER/DESCRIPTION’ ... OK -* this is package ‘ESTER’ version ‘0.2.0’ -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘brms’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/ESTER/old/ESTER.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘ESTER/DESCRIPTION’ ... OK -* this is package ‘ESTER’ version ‘0.2.0’ -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘brms’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# evaluator - -
- -* Version: NA -* GitHub: NA -* Source code: https://github.com/cran/evaluator -* Number of recursive dependencies: 146 - -Run `revdepcheck::cloud_details(, "evaluator")` for more info - -
- -## Error before installation - -### Devel - -``` - - - - - - -``` -### CRAN - -``` - - - - - - -``` -# expstudies - -
- -* Version: NA -* GitHub: NA -* Source code: https://github.com/cran/expstudies -* Number of recursive dependencies: 59 - -Run `revdepcheck::cloud_details(, "expstudies")` for more info - -
- -## Error before installation - -### Devel - -``` - - - - - - -``` -### CRAN - -``` - - - - - - -``` -# 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: 108 - -Run `revdepcheck::cloud_details(, "fable.prophet")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/fable.prophet/new/fable.prophet.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘fable.prophet/DESCRIPTION’ ... OK -* this is package ‘fable.prophet’ version ‘0.1.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘prophet’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/fable.prophet/old/fable.prophet.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘fable.prophet/DESCRIPTION’ ... OK -* this is package ‘fable.prophet’ version ‘0.1.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘prophet’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# FAMetA - -
- -* Version: 0.1.5 -* GitHub: NA -* Source code: https://github.com/cran/FAMetA -* Date/Publication: 2023-01-11 09:33:11 UTC -* Number of recursive dependencies: 90 - -Run `revdepcheck::cloud_details(, "FAMetA")` for more info - -
- -## In both - -* checking whether package ‘FAMetA’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/FAMetA/new/FAMetA.Rcheck/00install.out’ for details. - ``` - -## Installation - -### Devel - -``` -* installing *source* package ‘FAMetA’ ... -** package ‘FAMetA’ 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 ‘LipidMS’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): - there is no package called ‘readMzXmlData’ -Execution halted -ERROR: lazy loading failed for package ‘FAMetA’ -* removing ‘/tmp/workdir/FAMetA/new/FAMetA.Rcheck/FAMetA’ - - -``` -### CRAN - -``` -* installing *source* package ‘FAMetA’ ... -** package ‘FAMetA’ 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 ‘LipidMS’ in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]): - there is no package called ‘readMzXmlData’ -Execution halted -ERROR: lazy loading failed for package ‘FAMetA’ -* removing ‘/tmp/workdir/FAMetA/old/FAMetA.Rcheck/FAMetA’ - - -``` -# fgdr - -
- -* Version: 1.1.1 -* GitHub: https://github.com/uribo/fgdr -* Source code: https://github.com/cran/fgdr -* Date/Publication: 2022-02-22 05:00:02 UTC -* Number of recursive dependencies: 123 - -Run `revdepcheck::cloud_details(, "fgdr")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/fgdr/new/fgdr.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘fgdr/DESCRIPTION’ ... OK -* this is package ‘fgdr’ version ‘1.1.1’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/fgdr/old/fgdr.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘fgdr/DESCRIPTION’ ... OK -* this is package ‘fgdr’ version ‘1.1.1’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# finnts - -
- -* Version: 0.2.2 -* GitHub: https://github.com/microsoft/finnts -* Source code: https://github.com/cran/finnts -* Date/Publication: 2023-02-12 00:40:02 UTC -* Number of recursive dependencies: 210 - -Run `revdepcheck::cloud_details(, "finnts")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/finnts/new/finnts.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘finnts/DESCRIPTION’ ... OK -* this is package ‘finnts’ version ‘0.2.2’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... OK -... - ‘best-model-selection.Rmd’ using ‘UTF-8’... OK - ‘external-regressors.Rmd’ using ‘UTF-8’... OK - ‘feature-engineering.Rmd’ using ‘UTF-8’... OK - ‘finnts.Rmd’ using ‘UTF-8’... OK - ‘hierarchical-forecasting.Rmd’ using ‘UTF-8’... OK - ‘models-used-in-finnts.Rmd’ using ‘UTF-8’... OK - ‘parallel-processing.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: OK - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/finnts/old/finnts.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘finnts/DESCRIPTION’ ... OK -* this is package ‘finnts’ version ‘0.2.2’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... OK -... - ‘best-model-selection.Rmd’ using ‘UTF-8’... OK - ‘external-regressors.Rmd’ using ‘UTF-8’... OK - ‘feature-engineering.Rmd’ using ‘UTF-8’... OK - ‘finnts.Rmd’ using ‘UTF-8’... OK - ‘hierarchical-forecasting.Rmd’ using ‘UTF-8’... OK - ‘models-used-in-finnts.Rmd’ using ‘UTF-8’... OK - ‘parallel-processing.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: OK - - - - - -``` -# fipe - -
- -* Version: NA -* GitHub: NA -* Source code: https://github.com/cran/fipe -* Number of recursive dependencies: 69 - -Run `revdepcheck::cloud_details(, "fipe")` for more info - -
- -## Error before installation - -### Devel - -``` - - - - - - -``` -### CRAN - -``` - - - - - - -``` -# foieGras - -
- -* Version: NA -* GitHub: NA -* Source code: https://github.com/cran/foieGras -* Number of recursive dependencies: 134 - -Run `revdepcheck::cloud_details(, "foieGras")` for more info - -
- -## Error before installation - -### Devel - -``` - - - - - - -``` -### CRAN - -``` - - - - - - -``` -# forceR - -
- -* Version: NA -* GitHub: NA -* Source code: https://github.com/cran/forceR -* Number of recursive dependencies: 86 - -Run `revdepcheck::cloud_details(, "forceR")` for more info - -
- -## Error before installation - -### Devel - -``` - - - - - - -``` -### CRAN - -``` - - - - - - -``` -# FORTLS - -
- -* Version: 1.2.0 -* GitHub: https://github.com/Molina-Valero/FORTLS -* Source code: https://github.com/cran/FORTLS -* Date/Publication: 2023-01-08 16:50:05 UTC -* Number of recursive dependencies: 176 - -Run `revdepcheck::cloud_details(, "FORTLS")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/FORTLS/new/FORTLS.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘FORTLS/DESCRIPTION’ ... OK -* this is package ‘FORTLS’ version ‘1.2.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/FORTLS/old/FORTLS.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘FORTLS/DESCRIPTION’ ... OK -* this is package ‘FORTLS’ version ‘1.2.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# FRK - -
- -* Version: 2.1.5 -* GitHub: https://github.com/andrewzm/FRK -* Source code: https://github.com/cran/FRK -* Date/Publication: 2023-02-01 10:20:02 UTC -* Number of recursive dependencies: 156 - -Run `revdepcheck::cloud_details(, "FRK")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/FRK/new/FRK.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘FRK/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘FRK’ version ‘2.1.5’ -* package encoding: UTF-8 -* checking package namespace information ... OK -... ---- failed re-building ‘FRK_non-Gaussian.Rnw’ - -SUMMARY: processing the following files failed: - ‘FRK_intro.Rnw’ ‘FRK_non-Gaussian.Rnw’ - -Error: Vignette re-building failed. -Execution halted - -* DONE -Status: 1 ERROR, 1 WARNING, 2 NOTEs - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/FRK/old/FRK.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘FRK/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘FRK’ version ‘2.1.5’ -* package encoding: UTF-8 -* checking package namespace information ... OK -... ---- failed re-building ‘FRK_non-Gaussian.Rnw’ - -SUMMARY: processing the following files failed: - ‘FRK_intro.Rnw’ ‘FRK_non-Gaussian.Rnw’ - -Error: Vignette re-building failed. -Execution halted - -* DONE -Status: 1 ERROR, 1 WARNING, 2 NOTEs - - - - - -``` -# fsr - -
- -* Version: 1.0.2 -* GitHub: https://github.com/accarniel/fsr -* Source code: https://github.com/cran/fsr -* Date/Publication: 2022-07-05 02:50:02 UTC -* Number of recursive dependencies: 71 - -Run `revdepcheck::cloud_details(, "fsr")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/fsr/new/fsr.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘fsr/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘fsr’ version ‘1.0.2’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Packages required but not available: 'sf', 'lwgeom' - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/fsr/old/fsr.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘fsr/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘fsr’ version ‘1.0.2’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Packages required but not available: 'sf', 'lwgeom' - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# genekitr - -
- -* Version: 1.1.3 -* GitHub: https://github.com/GangLiLab/genekitr -* Source code: https://github.com/cran/genekitr -* Date/Publication: 2023-03-01 09:00:02 UTC -* Number of recursive dependencies: 206 - -Run `revdepcheck::cloud_details(, "genekitr")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/genekitr/new/genekitr.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘genekitr/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘genekitr’ version ‘1.1.3’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘clusterProfiler’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/genekitr/old/genekitr.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘genekitr/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘genekitr’ version ‘1.1.3’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘clusterProfiler’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# geocmeans - -
- -* Version: 0.3.3 -* GitHub: https://github.com/JeremyGelb/geocmeans -* Source code: https://github.com/cran/geocmeans -* Date/Publication: 2023-02-07 01:02:31 UTC -* Number of recursive dependencies: 197 - -Run `revdepcheck::cloud_details(, "geocmeans")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/geocmeans/new/geocmeans.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘geocmeans/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘geocmeans’ version ‘0.3.3’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/geocmeans/old/geocmeans.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘geocmeans/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘geocmeans’ version ‘0.3.3’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# GeodesiCL - -
- -* Version: 1.0.0 -* GitHub: https://github.com/diegoalarc/GeodesiCL -* Source code: https://github.com/cran/GeodesiCL -* Date/Publication: 2021-05-25 12:20:02 UTC -* Number of recursive dependencies: 129 - -Run `revdepcheck::cloud_details(, "GeodesiCL")` for more info - -
- -## In both - -* checking whether package ‘GeodesiCL’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/GeodesiCL/new/GeodesiCL.Rcheck/00install.out’ for details. - ``` - -## Installation - -### Devel - -``` -* installing *source* package ‘GeodesiCL’ ... -** package ‘GeodesiCL’ 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 ‘sf’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart -Execution halted -ERROR: lazy loading failed for package ‘GeodesiCL’ -* removing ‘/tmp/workdir/GeodesiCL/new/GeodesiCL.Rcheck/GeodesiCL’ - - -``` -### CRAN - -``` -* installing *source* package ‘GeodesiCL’ ... -** package ‘GeodesiCL’ 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 ‘sf’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart -Execution halted -ERROR: lazy loading failed for package ‘GeodesiCL’ -* removing ‘/tmp/workdir/GeodesiCL/old/GeodesiCL.Rcheck/GeodesiCL’ - - -``` -# ggchangepoint - -
- -* Version: 0.1.0 -* GitHub: NA -* Source code: https://github.com/cran/ggchangepoint -* Date/Publication: 2022-02-24 08:20:04 UTC -* Number of recursive dependencies: 81 - -Run `revdepcheck::cloud_details(, "ggchangepoint")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/ggchangepoint/new/ggchangepoint.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘ggchangepoint/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘ggchangepoint’ version ‘0.1.0’ -* package encoding: UTF-8 -* checking package namespace information ... 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 - ‘introduction.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: OK - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/ggchangepoint/old/ggchangepoint.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘ggchangepoint/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘ggchangepoint’ version ‘0.1.0’ -* package encoding: UTF-8 -* checking package namespace information ... 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 - ‘introduction.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: OK - - - - - -``` -# ggOceanMaps - -
- -* Version: 1.3.4 -* GitHub: https://github.com/MikkoVihtakari/ggOceanMaps -* Source code: https://github.com/cran/ggOceanMaps -* Date/Publication: 2022-09-26 11:50:02 UTC -* Number of recursive dependencies: 92 - -Run `revdepcheck::cloud_details(, "ggOceanMaps")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/ggOceanMaps/new/ggOceanMaps.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘ggOceanMaps/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘ggOceanMaps’ version ‘1.3.4’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/ggOceanMaps/old/ggOceanMaps.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘ggOceanMaps/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘ggOceanMaps’ version ‘1.3.4’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# ggPMX - -
- -* Version: 1.2.8 -* GitHub: https://github.com/ggPMXdevelopment/ggPMX -* Source code: https://github.com/cran/ggPMX -* Date/Publication: 2022-06-17 23:10:02 UTC -* Number of recursive dependencies: 174 - -Run `revdepcheck::cloud_details(, "ggPMX")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/ggPMX/new/ggPMX.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘ggPMX/DESCRIPTION’ ... OK -* this is package ‘ggPMX’ version ‘1.2.8’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... NOTE -... - [ FAIL 1 | WARN 14 | SKIP 8 | PASS 327 ] - 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 ... NONE - ‘ggPMX-guide.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: 1 ERROR, 2 NOTEs - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/ggPMX/old/ggPMX.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘ggPMX/DESCRIPTION’ ... OK -* this is package ‘ggPMX’ version ‘1.2.8’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... NOTE -... - [ FAIL 1 | WARN 14 | SKIP 8 | PASS 327 ] - 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 ... NONE - ‘ggPMX-guide.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: 1 ERROR, 2 NOTEs - - - - - -``` -# ggseqplot - -
- -* Version: NA -* GitHub: NA -* Source code: https://github.com/cran/ggseqplot -* Number of recursive dependencies: 130 - -Run `revdepcheck::cloud_details(, "ggseqplot")` for more info - -
- -## Error before installation - -### Devel - -``` - - - - - - -``` -### CRAN - -``` - - - - - - -``` -# ggspatial - -
- -* Version: 1.1.7 -* GitHub: https://github.com/paleolimbot/ggspatial -* Source code: https://github.com/cran/ggspatial -* Date/Publication: 2022-11-24 10:00:02 UTC -* Number of recursive dependencies: 105 - -Run `revdepcheck::cloud_details(, "ggspatial")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/ggspatial/new/ggspatial.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘ggspatial/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘ggspatial’ version ‘1.1.7’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -Package suggested but not available for checking: ‘lwgeom’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/ggspatial/old/ggspatial.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘ggspatial/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘ggspatial’ version ‘1.1.7’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -Package suggested but not available for checking: ‘lwgeom’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# ggstatsplot - -
- -* Version: 0.11.0 -* GitHub: https://github.com/IndrajeetPatil/ggstatsplot -* Source code: https://github.com/cran/ggstatsplot -* Date/Publication: 2023-02-15 15:30:02 UTC -* Number of recursive dependencies: 169 - -Run `revdepcheck::cloud_details(, "ggstatsplot")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/ggstatsplot/new/ggstatsplot.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘ggstatsplot/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘ggstatsplot’ version ‘0.11.0’ -* package encoding: UTF-8 -* checking package namespace information ... 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 - ‘additional.Rmd’ using ‘UTF-8’... OK - ‘ggstatsplot.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: 1 NOTE - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/ggstatsplot/old/ggstatsplot.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘ggstatsplot/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘ggstatsplot’ version ‘0.11.0’ -* package encoding: UTF-8 -* checking package namespace information ... 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 - ‘additional.Rmd’ using ‘UTF-8’... OK - ‘ggstatsplot.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: 1 NOTE - - - - - -``` -# glottospace - -
- -* Version: 0.0.112 -* GitHub: https://github.com/SietzeN/glottospace -* Source code: https://github.com/cran/glottospace -* Date/Publication: 2022-04-12 12:42:29 UTC -* Number of recursive dependencies: 141 - -Run `revdepcheck::cloud_details(, "glottospace")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/glottospace/new/glottospace.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘glottospace/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘glottospace’ version ‘0.0.112’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/glottospace/old/glottospace.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘glottospace/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘glottospace’ version ‘0.0.112’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# GPSeqClus - -
- -* Version: 1.3.0 -* GitHub: NA -* Source code: https://github.com/cran/GPSeqClus -* Date/Publication: 2022-08-09 14:20:08 UTC -* Number of recursive dependencies: 103 - -Run `revdepcheck::cloud_details(, "GPSeqClus")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/GPSeqClus/new/GPSeqClus.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘GPSeqClus/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘GPSeqClus’ version ‘1.3.0’ -* package encoding: UTF-8 -* checking package namespace information ... 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 ‘GPSeqClus’ can be installed ... ERROR -Installation failed. -See ‘/tmp/workdir/GPSeqClus/new/GPSeqClus.Rcheck/00install.out’ for details. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/GPSeqClus/old/GPSeqClus.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘GPSeqClus/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘GPSeqClus’ version ‘1.3.0’ -* package encoding: UTF-8 -* checking package namespace information ... 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 ‘GPSeqClus’ can be installed ... ERROR -Installation failed. -See ‘/tmp/workdir/GPSeqClus/old/GPSeqClus.Rcheck/00install.out’ for details. -* DONE -Status: 1 ERROR - - - - - -``` -# GREENeR - -
- -* Version: 0.1.1 -* GitHub: https://github.com/calfarog/GREENeR -* Source code: https://github.com/cran/GREENeR -* Date/Publication: 2022-09-07 12:10:02 UTC -* Number of recursive dependencies: 133 - -Run `revdepcheck::cloud_details(, "GREENeR")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/GREENeR/new/GREENeR.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘GREENeR/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘GREENeR’ version ‘0.1.1’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/GREENeR/old/GREENeR.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘GREENeR/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘GREENeR’ version ‘0.1.1’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# gtfs2gps - -
- -* Version: 2.1-0 -* GitHub: https://github.com/ipeaGIT/gtfs2gps -* Source code: https://github.com/cran/gtfs2gps -* Date/Publication: 2022-08-16 18:00:02 UTC -* Number of recursive dependencies: 88 - -Run `revdepcheck::cloud_details(, "gtfs2gps")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/gtfs2gps/new/gtfs2gps.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘gtfs2gps/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘gtfs2gps’ version ‘2.1-0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Packages required but not available: 'sf', 'lwgeom' - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/gtfs2gps/old/gtfs2gps.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘gtfs2gps/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘gtfs2gps’ version ‘2.1-0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Packages required but not available: 'sf', 'lwgeom' - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# gumboot - -
- -* Version: 1.0.0 -* GitHub: NA -* Source code: https://github.com/cran/gumboot -* Date/Publication: 2021-08-06 08:10:01 UTC -* Number of recursive dependencies: 101 - -Run `revdepcheck::cloud_details(, "gumboot")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/gumboot/new/gumboot.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘gumboot/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘gumboot’ version ‘1.0.0’ -* package encoding: UTF-8 -* checking package namespace information ... 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 ‘gumboot’ can be installed ... ERROR -Installation failed. -See ‘/tmp/workdir/gumboot/new/gumboot.Rcheck/00install.out’ for details. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/gumboot/old/gumboot.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘gumboot/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘gumboot’ version ‘1.0.0’ -* package encoding: UTF-8 -* checking package namespace information ... 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 ‘gumboot’ can be installed ... ERROR -Installation failed. -See ‘/tmp/workdir/gumboot/old/gumboot.Rcheck/00install.out’ for details. -* DONE -Status: 1 ERROR - - - - - -``` -# gwavr - -
- -* Version: 0.2.0 -* GitHub: https://github.com/joshualerickson/gwavr -* Source code: https://github.com/cran/gwavr -* Date/Publication: 2022-03-28 21:30:02 UTC -* Number of recursive dependencies: 140 - -Run `revdepcheck::cloud_details(, "gwavr")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/gwavr/new/gwavr.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘gwavr/DESCRIPTION’ ... OK -* this is package ‘gwavr’ version ‘0.2.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Packages required but not available: 'nhdplusTools', 'sf' - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/gwavr/old/gwavr.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘gwavr/DESCRIPTION’ ... OK -* this is package ‘gwavr’ version ‘0.2.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Packages required but not available: 'nhdplusTools', 'sf' - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# GWPR.light - -
- -* Version: 0.2.1 -* GitHub: https://github.com/MichaelChaoLi-cpu/GWPR.light -* Source code: https://github.com/cran/GWPR.light -* Date/Publication: 2022-06-21 11:00:13 UTC -* Number of recursive dependencies: 129 - -Run `revdepcheck::cloud_details(, "GWPR.light")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/GWPR.light/new/GWPR.light.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘GWPR.light/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘GWPR.light’ version ‘0.2.1’ -* package encoding: UTF-8 -* checking package namespace information ... 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 ‘GWPR.light’ can be installed ... ERROR -Installation failed. -See ‘/tmp/workdir/GWPR.light/new/GWPR.light.Rcheck/00install.out’ for details. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/GWPR.light/old/GWPR.light.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘GWPR.light/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘GWPR.light’ version ‘0.2.1’ -* package encoding: UTF-8 -* checking package namespace information ... 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 ‘GWPR.light’ can be installed ... ERROR -Installation failed. -See ‘/tmp/workdir/GWPR.light/old/GWPR.light.Rcheck/00install.out’ for details. -* DONE -Status: 1 ERROR - - - - - -``` -# happign - -
- -* Version: 0.1.8 -* GitHub: https://github.com/paul-carteron/happign -* Source code: https://github.com/cran/happign -* Date/Publication: 2023-01-30 20:50:02 UTC -* Number of recursive dependencies: 121 - -Run `revdepcheck::cloud_details(, "happign")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/happign/new/happign.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘happign/DESCRIPTION’ ... OK -* this is package ‘happign’ version ‘0.1.8’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/happign/old/happign.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘happign/DESCRIPTION’ ... OK -* this is package ‘happign’ version ‘0.1.8’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# healthyR.ai - -
- -* Version: 0.0.12 -* GitHub: https://github.com/spsanderson/healthyR.ai -* Source code: https://github.com/cran/healthyR.ai -* Date/Publication: 2023-02-01 18:40:06 UTC -* Number of recursive dependencies: 189 - -Run `revdepcheck::cloud_details(, "healthyR.ai")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/healthyR.ai/new/healthyR.ai.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘healthyR.ai/DESCRIPTION’ ... OK -* this is package ‘healthyR.ai’ version ‘0.0.12’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... 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 - ‘auto-kmeans.Rmd’ using ‘UTF-8’... OK - ‘getting-started.Rmd’ using ‘UTF-8’... OK - ‘kmeans-umap.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: OK - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/healthyR.ai/old/healthyR.ai.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘healthyR.ai/DESCRIPTION’ ... OK -* this is package ‘healthyR.ai’ version ‘0.0.12’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... 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 - ‘auto-kmeans.Rmd’ using ‘UTF-8’... OK - ‘getting-started.Rmd’ using ‘UTF-8’... OK - ‘kmeans-umap.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: OK - - - - - -``` -# healthyR.ts - -
- -* Version: 0.2.7 -* GitHub: https://github.com/spsanderson/healthyR.ts -* Source code: https://github.com/cran/healthyR.ts -* Date/Publication: 2023-01-28 14:50:02 UTC -* Number of recursive dependencies: 191 - -Run `revdepcheck::cloud_details(, "healthyR.ts")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/healthyR.ts/new/healthyR.ts.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘healthyR.ts/DESCRIPTION’ ... OK -* this is package ‘healthyR.ts’ version ‘0.2.7’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... 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 - ‘using-tidy-fft.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: 1 NOTE - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/healthyR.ts/old/healthyR.ts.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘healthyR.ts/DESCRIPTION’ ... OK -* this is package ‘healthyR.ts’ version ‘0.2.7’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... 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 - ‘using-tidy-fft.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: 1 NOTE - - - - - -``` -# healthyverse - -
- -* Version: 1.0.3 -* GitHub: https://github.com/spsanderson/healthyverse -* Source code: https://github.com/cran/healthyverse -* Date/Publication: 2023-02-21 20:40:02 UTC -* Number of recursive dependencies: 207 - -Run `revdepcheck::cloud_details(, "healthyverse")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/healthyverse/new/healthyverse.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘healthyverse/DESCRIPTION’ ... OK -* this is package ‘healthyverse’ version ‘1.0.3’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... 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 -* DONE -Status: 1 NOTE - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/healthyverse/old/healthyverse.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘healthyverse/DESCRIPTION’ ... OK -* this is package ‘healthyverse’ version ‘1.0.3’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... 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 -* DONE -Status: 1 NOTE - - - - - -``` -# himach - -
- -* Version: 0.3.1 -* GitHub: https://github.com/david6marsh/himach -* Source code: https://github.com/cran/himach -* Date/Publication: 2022-12-05 09:30:02 UTC -* Number of recursive dependencies: 108 - -Run `revdepcheck::cloud_details(, "himach")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/himach/new/himach.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘himach/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘himach’ version ‘0.3.1’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Packages required but not available: 'lwgeom', 'sf' - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/himach/old/himach.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘himach/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘himach’ version ‘0.3.1’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Packages required but not available: 'lwgeom', 'sf' - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# historicalborrowlong - -
- -* Version: 0.0.5 -* GitHub: https://github.com/wlandau/historicalborrowlong -* Source code: https://github.com/cran/historicalborrowlong -* Date/Publication: 2022-09-13 10:20:06 UTC -* Number of recursive dependencies: 107 - -Run `revdepcheck::cloud_details(, "historicalborrowlong")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/historicalborrowlong/new/historicalborrowlong.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘historicalborrowlong/DESCRIPTION’ ... OK -* this is package ‘historicalborrowlong’ version ‘0.0.5’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Packages required but not available: 'rstan', 'trialr' - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/historicalborrowlong/old/historicalborrowlong.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘historicalborrowlong/DESCRIPTION’ ... OK -* this is package ‘historicalborrowlong’ version ‘0.0.5’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Packages required but not available: 'rstan', 'trialr' - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# HYPEtools - -
- -* Version: 1.2.0 -* GitHub: https://github.com/rcapell/HYPEtools -* Source code: https://github.com/cran/HYPEtools -* Date/Publication: 2023-02-10 08:50:06 UTC -* Number of recursive dependencies: 174 - -Run `revdepcheck::cloud_details(, "HYPEtools")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/HYPEtools/new/HYPEtools.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘HYPEtools/DESCRIPTION’ ... OK -* this is package ‘HYPEtools’ version ‘1.2.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/HYPEtools/old/HYPEtools.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘HYPEtools/DESCRIPTION’ ... OK -* this is package ‘HYPEtools’ version ‘1.2.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# 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: 109 - -Run `revdepcheck::cloud_details(, "hypsoLoop")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/hypsoLoop/new/hypsoLoop.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘hypsoLoop/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘hypsoLoop’ version ‘0.2.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/hypsoLoop/old/hypsoLoop.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘hypsoLoop/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘hypsoLoop’ version ‘0.2.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# immcp - -
- -* Version: 1.0.3 -* GitHub: https://github.com/YuanlongHu/immcp -* Source code: https://github.com/cran/immcp -* Date/Publication: 2022-05-12 05:50:02 UTC -* Number of recursive dependencies: 194 - -Run `revdepcheck::cloud_details(, "immcp")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/immcp/new/immcp.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘immcp/DESCRIPTION’ ... OK -* this is package ‘immcp’ version ‘1.0.3’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘clusterProfiler’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/immcp/old/immcp.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘immcp/DESCRIPTION’ ... OK -* this is package ‘immcp’ version ‘1.0.3’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘clusterProfiler’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# ImputeRobust - -
- -* Version: 1.3-1 -* GitHub: NA -* Source code: https://github.com/cran/ImputeRobust -* Date/Publication: 2018-11-30 12:10:03 UTC -* Number of recursive dependencies: 41 - -Run `revdepcheck::cloud_details(, "ImputeRobust")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/ImputeRobust/new/ImputeRobust.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘ImputeRobust/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘ImputeRobust’ version ‘1.3-1’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘extremevalues’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/ImputeRobust/old/ImputeRobust.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘ImputeRobust/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘ImputeRobust’ version ‘1.3-1’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘extremevalues’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# incidence2 - -
- -* Version: 1.2.3 -* GitHub: https://github.com/reconverse/incidence2 -* Source code: https://github.com/cran/incidence2 -* Date/Publication: 2021-11-07 22:00:02 UTC -* Number of recursive dependencies: 87 - -Run `revdepcheck::cloud_details(, "incidence2")` for more info - -
- -## In both - -* checking whether package ‘incidence2’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/incidence2/new/incidence2.Rcheck/00install.out’ for details. - ``` - -## Installation - -### Devel - -``` -* installing *source* package ‘incidence2’ ... -** package ‘incidence2’ 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 : The `x` argument of `as_tibble()` can't be missing as of tibble 3.0.0. -Error: unable to load R code in package ‘incidence2’ -Execution halted -ERROR: lazy loading failed for package ‘incidence2’ -* removing ‘/tmp/workdir/incidence2/new/incidence2.Rcheck/incidence2’ - - -``` -### CRAN - -``` -* installing *source* package ‘incidence2’ ... -** package ‘incidence2’ 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 : The `x` argument of `as_tibble()` can't be missing as of tibble 3.0.0. -Error: unable to load R code in package ‘incidence2’ -Execution halted -ERROR: lazy loading failed for package ‘incidence2’ -* removing ‘/tmp/workdir/incidence2/old/incidence2.Rcheck/incidence2’ - - -``` -# INSPECTumours - -
- -* Version: 0.1.0 -* GitHub: NA -* Source code: https://github.com/cran/INSPECTumours -* Date/Publication: 2022-05-06 12:10:02 UTC -* Number of recursive dependencies: 175 - -Run `revdepcheck::cloud_details(, "INSPECTumours")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/INSPECTumours/new/INSPECTumours.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘INSPECTumours/DESCRIPTION’ ... OK -* this is package ‘INSPECTumours’ version ‘0.1.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘brms’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/INSPECTumours/old/INSPECTumours.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘INSPECTumours/DESCRIPTION’ ... OK -* this is package ‘INSPECTumours’ version ‘0.1.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘brms’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# intRinsic - -
- -* Version: NA -* GitHub: NA -* Source code: https://github.com/cran/intRinsic -* Number of recursive dependencies: 64 - -Run `revdepcheck::cloud_details(, "intRinsic")` for more info - -
- -## Error before installation - -### Devel - -``` - - - - - - -``` -### CRAN - -``` - - - - - - -``` -# intSDM - -
- -* Version: 1.0.5 -* GitHub: NA -* Source code: https://github.com/cran/intSDM -* Date/Publication: 2023-02-17 09:00:02 UTC -* Number of recursive dependencies: 154 - -Run `revdepcheck::cloud_details(, "intSDM")` for more info - -
- -## In both - -* checking whether package ‘intSDM’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/intSDM/new/intSDM.Rcheck/00install.out’ for details. - ``` - -* checking package dependencies ... NOTE - ``` - Package suggested but not available for checking: ‘sf’ - ``` - -## Installation - -### Devel - -``` -* installing *source* package ‘intSDM’ ... -** package ‘intSDM’ 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 ‘PointedSDMs’ in loadNamespace(i, c(lib.loc, .libPaths()), versionCheck = vI[[i]]): - there is no package called ‘sf’ -Execution halted -ERROR: lazy loading failed for package ‘intSDM’ -* removing ‘/tmp/workdir/intSDM/new/intSDM.Rcheck/intSDM’ - - -``` -### CRAN - -``` -* installing *source* package ‘intSDM’ ... -** package ‘intSDM’ 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 ‘PointedSDMs’ in loadNamespace(i, c(lib.loc, .libPaths()), versionCheck = vI[[i]]): - there is no package called ‘sf’ -Execution halted -ERROR: lazy loading failed for package ‘intSDM’ -* removing ‘/tmp/workdir/intSDM/old/intSDM.Rcheck/intSDM’ - - -``` -# IRexamples - -
- -* Version: 0.0.2 -* GitHub: https://github.com/vinhdizzo/IRexamples -* Source code: https://github.com/cran/IRexamples -* Date/Publication: 2022-08-15 07:10:19 UTC -* Number of recursive dependencies: 184 - -Run `revdepcheck::cloud_details(, "IRexamples")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/IRexamples/new/IRexamples.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘IRexamples/DESCRIPTION’ ... OK -* this is package ‘IRexamples’ version ‘0.0.2’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Packages required but not available: 'rstanarm', 'sf' - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/IRexamples/old/IRexamples.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘IRexamples/DESCRIPTION’ ... OK -* this is package ‘IRexamples’ version ‘0.0.2’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Packages required but not available: 'rstanarm', 'sf' - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# irtQ - -
- -* Version: NA -* GitHub: NA -* Source code: https://github.com/cran/irtQ -* Number of recursive dependencies: 59 - -Run `revdepcheck::cloud_details(, "irtQ")` for more info - -
- -## Error before installation - -### Devel - -``` - - - - - - -``` -### CRAN - -``` - - - - - - -``` -# IsoCorrectoR - -
- -* Version: NA -* GitHub: NA -* Source code: https://github.com/cran/IsoCorrectoR -* Number of recursive dependencies: 70 - -Run `revdepcheck::cloud_details(, "IsoCorrectoR")` for more info - -
- -## Error before installation - -### Devel - -``` - - - - - - -``` -### CRAN - -``` - - - - - - -``` -# itsdm - -
- -* Version: 0.2.0 -* GitHub: https://github.com/LLeiSong/itsdm -* Source code: https://github.com/cran/itsdm -* Date/Publication: 2023-01-15 14:30:08 UTC -* Number of recursive dependencies: 84 - -Run `revdepcheck::cloud_details(, "itsdm")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/itsdm/new/itsdm.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘itsdm/DESCRIPTION’ ... OK -* this is package ‘itsdm’ version ‘0.2.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/itsdm/old/itsdm.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘itsdm/DESCRIPTION’ ... OK -* this is package ‘itsdm’ version ‘0.2.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# journalabbr - -
- -* Version: NA -* GitHub: NA -* Source code: https://github.com/cran/journalabbr -* Number of recursive dependencies: 72 - -Run `revdepcheck::cloud_details(, "journalabbr")` for more info - -
- -## Error before installation - -### Devel - -``` - - - - - - -``` -### CRAN - -``` - - - - - - -``` -# jpgrid - -
- -* Version: 0.3.0 -* GitHub: https://github.com/UchidaMizuki/jpgrid -* Source code: https://github.com/cran/jpgrid -* Date/Publication: 2023-02-11 08:50:06 UTC -* Number of recursive dependencies: 57 - -Run `revdepcheck::cloud_details(, "jpgrid")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/jpgrid/new/jpgrid.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘jpgrid/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘jpgrid’ version ‘0.3.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/jpgrid/old/jpgrid.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘jpgrid/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘jpgrid’ version ‘0.3.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# jpmesh - -
- -* Version: 2.1.0 -* GitHub: https://github.com/uribo/jpmesh -* Source code: https://github.com/cran/jpmesh -* Date/Publication: 2022-01-10 03:32:41 UTC -* Number of recursive dependencies: 108 - -Run `revdepcheck::cloud_details(, "jpmesh")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/jpmesh/new/jpmesh.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘jpmesh/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘jpmesh’ version ‘2.1.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -Package suggested but not available for checking: ‘lwgeom’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/jpmesh/old/jpmesh.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘jpmesh/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘jpmesh’ version ‘2.1.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -Package suggested but not available for checking: ‘lwgeom’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# lifeR - -
- -* Version: NA -* GitHub: NA -* Source code: https://github.com/cran/lifeR -* Number of recursive dependencies: 92 - -Run `revdepcheck::cloud_details(, "lifeR")` for more info - -
- -## Error before installation - -### Devel - -``` - - - - - - -``` -### CRAN - -``` - - - - - - -``` -# loon.ggplot - -
- -* Version: 1.3.3 -* GitHub: https://github.com/great-northern-diver/loon.ggplot -* Source code: https://github.com/cran/loon.ggplot -* Date/Publication: 2022-11-12 22:30:02 UTC -* Number of recursive dependencies: 104 - -Run `revdepcheck::cloud_details(, "loon.ggplot")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/loon.ggplot/new/loon.ggplot.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘loon.ggplot/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘loon.ggplot’ version ‘1.3.3’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘loon’ - -Package suggested but not available for checking: ‘zenplots’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/loon.ggplot/old/loon.ggplot.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘loon.ggplot/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘loon.ggplot’ version ‘1.3.3’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘loon’ - -Package suggested but not available for checking: ‘zenplots’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# loon.shiny - -
- -* Version: 1.0.3 -* GitHub: NA -* Source code: https://github.com/cran/loon.shiny -* Date/Publication: 2022-10-08 15:30:02 UTC -* Number of recursive dependencies: 136 - -Run `revdepcheck::cloud_details(, "loon.shiny")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/loon.shiny/new/loon.shiny.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘loon.shiny/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘loon.shiny’ version ‘1.0.3’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Packages required but not available: 'loon', 'loon.ggplot' - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/loon.shiny/old/loon.shiny.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘loon.shiny/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘loon.shiny’ version ‘1.0.3’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Packages required but not available: 'loon', 'loon.ggplot' - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# MACP - -
- -* Version: 0.1.0 -* GitHub: https://github.com/mrbakhsh/MACP -* Source code: https://github.com/cran/MACP -* Date/Publication: 2023-02-28 17:32:30 UTC -* Number of recursive dependencies: 231 - -Run `revdepcheck::cloud_details(, "MACP")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/MACP/new/MACP.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘MACP/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘MACP’ version ‘0.1.0’ -* package encoding: UTF-8 -* checking package namespace information ... 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 - ‘MACP_tutorial.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: 3 NOTEs - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/MACP/old/MACP.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘MACP/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘MACP’ version ‘0.1.0’ -* package encoding: UTF-8 -* checking package namespace information ... 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 - ‘MACP_tutorial.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: 3 NOTEs - - - - - -``` -# mafs - -
- -* Version: NA -* GitHub: NA -* Source code: https://github.com/cran/mafs -* Number of recursive dependencies: 90 - -Run `revdepcheck::cloud_details(, "mafs")` for more info - -
- -## Error before installation - -### Devel - -``` - - - - - - -``` -### CRAN - -``` - - - - - - -``` -# MainExistingDatasets - -
- -* Version: 1.0.1 -* GitHub: NA -* Source code: https://github.com/cran/MainExistingDatasets -* Date/Publication: 2022-06-27 14:10:02 UTC -* Number of recursive dependencies: 131 - -Run `revdepcheck::cloud_details(, "MainExistingDatasets")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/MainExistingDatasets/new/MainExistingDatasets.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘MainExistingDatasets/DESCRIPTION’ ... OK -* this is package ‘MainExistingDatasets’ version ‘1.0.1’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/MainExistingDatasets/old/MainExistingDatasets.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘MainExistingDatasets/DESCRIPTION’ ... OK -* this is package ‘MainExistingDatasets’ version ‘1.0.1’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# MantaID - -
- -* Version: NA -* GitHub: NA -* Source code: https://github.com/cran/MantaID -* Number of recursive dependencies: 152 - -Run `revdepcheck::cloud_details(, "MantaID")` for more info - -
- -## Error before installation - -### Devel - -``` - - - - - - -``` -### CRAN - -``` - - - - - - -``` -# manydata - -
- -* Version: 0.8.2 -* GitHub: https://github.com/globalgov/manydata -* Source code: https://github.com/cran/manydata -* Date/Publication: 2022-11-19 13:00:10 UTC -* Number of recursive dependencies: 169 - -Run `revdepcheck::cloud_details(, "manydata")` for more info - -
- -## In both - -* checking whether package ‘manydata’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/manydata/new/manydata.Rcheck/00install.out’ for details. - ``` - -## Installation - -### Devel - -``` -* installing *source* package ‘manydata’ ... -** package ‘manydata’ 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 ‘sf’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart -Execution halted -ERROR: lazy loading failed for package ‘manydata’ -* removing ‘/tmp/workdir/manydata/new/manydata.Rcheck/manydata’ - - -``` -### CRAN - -``` -* installing *source* package ‘manydata’ ... -** package ‘manydata’ 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 ‘sf’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart -Execution halted -ERROR: lazy loading failed for package ‘manydata’ -* removing ‘/tmp/workdir/manydata/old/manydata.Rcheck/manydata’ - - -``` -# mapboxapi - -
- -* Version: 0.5 -* GitHub: NA -* Source code: https://github.com/cran/mapboxapi -* Date/Publication: 2022-09-15 16:06:12 UTC -* Number of recursive dependencies: 154 - -Run `revdepcheck::cloud_details(, "mapboxapi")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/mapboxapi/new/mapboxapi.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘mapboxapi/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘mapboxapi’ version ‘0.5’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/mapboxapi/old/mapboxapi.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘mapboxapi/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘mapboxapi’ version ‘0.5’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# mapme.biodiversity - -
- -* Version: 0.3.0 -* GitHub: https://github.com/mapme-initiative/mapme.biodiversity -* Source code: https://github.com/cran/mapme.biodiversity -* Date/Publication: 2023-01-21 14:10:02 UTC -* Number of recursive dependencies: 131 - -Run `revdepcheck::cloud_details(, "mapme.biodiversity")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/mapme.biodiversity/new/mapme.biodiversity.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘mapme.biodiversity/DESCRIPTION’ ... OK -* this is package ‘mapme.biodiversity’ version ‘0.3.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -Package suggested but not available for checking: ‘lwgeom’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/mapme.biodiversity/old/mapme.biodiversity.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘mapme.biodiversity/DESCRIPTION’ ... OK -* this is package ‘mapme.biodiversity’ version ‘0.3.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -Package suggested but not available for checking: ‘lwgeom’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# mapping - -
- -* Version: 1.3 -* GitHub: https://github.com/serafinialessio/mapping -* Source code: https://github.com/cran/mapping -* Date/Publication: 2021-07-22 17:40:02 UTC -* Number of recursive dependencies: 147 - -Run `revdepcheck::cloud_details(, "mapping")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/mapping/new/mapping.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘mapping/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘mapping’ version ‘1.3’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/mapping/old/mapping.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘mapping/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘mapping’ version ‘1.3’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# mapsapi - -
- -* Version: 0.5.3 -* GitHub: https://github.com/michaeldorman/mapsapi -* Source code: https://github.com/cran/mapsapi -* Date/Publication: 2022-01-13 13:22:41 UTC -* Number of recursive dependencies: 89 - -Run `revdepcheck::cloud_details(, "mapsapi")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/mapsapi/new/mapsapi.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘mapsapi/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘mapsapi’ version ‘0.5.3’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/mapsapi/old/mapsapi.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘mapsapi/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘mapsapi’ version ‘0.5.3’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# mapscanner - -
- -* Version: 0.0.6 -* GitHub: https://github.com/ropensci/mapscanner -* Source code: https://github.com/cran/mapscanner -* Date/Publication: 2021-11-25 23:10:03 UTC -* Number of recursive dependencies: 143 - -Run `revdepcheck::cloud_details(, "mapscanner")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/mapscanner/new/mapscanner.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘mapscanner/DESCRIPTION’ ... OK -* this is package ‘mapscanner’ version ‘0.0.6’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -Package suggested but not available for checking: ‘lwgeom’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/mapscanner/old/mapscanner.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘mapscanner/DESCRIPTION’ ... OK -* this is package ‘mapscanner’ version ‘0.0.6’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -Package suggested but not available for checking: ‘lwgeom’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# marginaleffects - -
- -* Version: 0.11.0 -* GitHub: https://github.com/vincentarelbundock/marginaleffects -* Source code: https://github.com/cran/marginaleffects -* Date/Publication: 2023-03-10 10:10:02 UTC -* Number of recursive dependencies: 366 - -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.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘marginaleffects/DESCRIPTION’ ... OK -* this is package ‘marginaleffects’ version ‘0.11.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... NOTE -... -* 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.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘marginaleffects/DESCRIPTION’ ... OK -* this is package ‘marginaleffects’ version ‘0.11.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... NOTE -... -* 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 - - - - - -``` -# MarketMatching - -
- -* Version: 1.2.0 -* GitHub: NA -* Source code: https://github.com/cran/MarketMatching -* Date/Publication: 2021-01-08 20:10:02 UTC -* Number of recursive dependencies: 73 - -Run `revdepcheck::cloud_details(, "MarketMatching")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/MarketMatching/new/MarketMatching.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘MarketMatching/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘MarketMatching’ version ‘1.2.0’ -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Packages required but not available: 'CausalImpact', 'bsts', 'Boom' - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/MarketMatching/old/MarketMatching.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘MarketMatching/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘MarketMatching’ version ‘1.2.0’ -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Packages required but not available: 'CausalImpact', 'bsts', 'Boom' - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# MazamaSpatialPlots - -
- -* Version: 0.2.0 -* GitHub: https://github.com/MazamaScience/MazamaSpatialPlots -* Source code: https://github.com/cran/MazamaSpatialPlots -* Date/Publication: 2022-11-15 21:00:08 UTC -* Number of recursive dependencies: 180 - -Run `revdepcheck::cloud_details(, "MazamaSpatialPlots")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/MazamaSpatialPlots/new/MazamaSpatialPlots.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘MazamaSpatialPlots/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘MazamaSpatialPlots’ version ‘0.2.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/MazamaSpatialPlots/old/MazamaSpatialPlots.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘MazamaSpatialPlots/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘MazamaSpatialPlots’ version ‘0.2.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# mbRes - -
- -* Version: NA -* GitHub: NA -* Source code: https://github.com/cran/mbRes -* Number of recursive dependencies: 40 - -Run `revdepcheck::cloud_details(, "mbRes")` for more info - -
- -## Error before installation - -### Devel - -``` - - - - - - -``` -### CRAN - -``` - - - - - - -``` -# merTools - -
- -* Version: 0.5.2 -* GitHub: NA -* Source code: https://github.com/cran/merTools -* Date/Publication: 2020-06-23 10:30:12 UTC -* Number of recursive dependencies: 143 - -Run `revdepcheck::cloud_details(, "merTools")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/merTools/new/merTools.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘merTools/DESCRIPTION’ ... OK -* this is package ‘merTools’ version ‘0.5.2’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... NOTE -... -* checking for unstated dependencies in vignettes ... OK -* checking package vignettes in ‘inst/doc’ ... OK -* checking running R code from vignettes ... NONE - ‘Using_predictInterval.Rmd’ using ‘UTF-8’... OK - ‘imputation.Rmd’ using ‘UTF-8’... OK - ‘marginal_effects.Rmd’ using ‘UTF-8’... OK - ‘merToolsIntro.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: 1 NOTE - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/merTools/old/merTools.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘merTools/DESCRIPTION’ ... OK -* this is package ‘merTools’ version ‘0.5.2’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... NOTE -... -* checking for unstated dependencies in vignettes ... OK -* checking package vignettes in ‘inst/doc’ ... OK -* checking running R code from vignettes ... NONE - ‘Using_predictInterval.Rmd’ using ‘UTF-8’... OK - ‘imputation.Rmd’ using ‘UTF-8’... OK - ‘marginal_effects.Rmd’ using ‘UTF-8’... OK - ‘merToolsIntro.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: 1 NOTE - - - - - -``` -# meteoland - -
- -* Version: 2.0.0 -* GitHub: NA -* Source code: https://github.com/cran/meteoland -* Date/Publication: 2023-02-17 22:20:02 UTC -* Number of recursive dependencies: 155 - -Run `revdepcheck::cloud_details(, "meteoland")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/meteoland/new/meteoland.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘meteoland/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘meteoland’ version ‘2.0.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/meteoland/old/meteoland.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘meteoland/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘meteoland’ version ‘2.0.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# microservices - -
- -* Version: NA -* GitHub: NA -* Source code: https://github.com/cran/microservices -* Number of recursive dependencies: 70 - -Run `revdepcheck::cloud_details(, "microservices")` for more info - -
- -## Error before installation - -### Devel - -``` - - - - - - -``` -### CRAN - -``` - - - - - - -``` -# modeltime - -
- -* Version: 1.2.5 -* GitHub: https://github.com/business-science/modeltime -* Source code: https://github.com/cran/modeltime -* Date/Publication: 2023-02-07 19:32:30 UTC -* Number of recursive dependencies: 253 - -Run `revdepcheck::cloud_details(, "modeltime")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/modeltime/new/modeltime.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘modeltime/DESCRIPTION’ ... OK -* this is package ‘modeltime’ version ‘1.2.5’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘prophet’ - -Package suggested but not available for checking: ‘rstan’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/modeltime/old/modeltime.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘modeltime/DESCRIPTION’ ... OK -* this is package ‘modeltime’ version ‘1.2.5’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘prophet’ - -Package suggested but not available for checking: ‘rstan’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# modeltime.ensemble - -
- -* Version: 1.0.2 -* GitHub: https://github.com/business-science/modeltime.ensemble -* Source code: https://github.com/cran/modeltime.ensemble -* Date/Publication: 2022-10-18 23:02:40 UTC -* Number of recursive dependencies: 223 - -Run `revdepcheck::cloud_details(, "modeltime.ensemble")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/modeltime.ensemble/new/modeltime.ensemble.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘modeltime.ensemble/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘modeltime.ensemble’ version ‘1.0.2’ -* package encoding: UTF-8 -* checking package namespace information ... OK -... ---- finished re-building ‘recursive-ensembles.Rmd’ - -SUMMARY: processing the following file failed: - ‘getting-started-with-modeltime-ensemble.Rmd’ - -Error: Vignette re-building failed. -Execution halted - -* DONE -Status: 1 ERROR, 1 WARNING, 1 NOTE - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/modeltime.ensemble/old/modeltime.ensemble.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘modeltime.ensemble/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘modeltime.ensemble’ version ‘1.0.2’ -* package encoding: UTF-8 -* checking package namespace information ... OK -... ---- finished re-building ‘recursive-ensembles.Rmd’ - -SUMMARY: processing the following file failed: - ‘getting-started-with-modeltime-ensemble.Rmd’ - -Error: Vignette re-building failed. -Execution halted - -* DONE -Status: 1 ERROR, 1 WARNING, 1 NOTE - - - - - -``` -# modeltime.gluonts - -
- -* Version: 0.1.0 -* GitHub: https://github.com/business-science/modeltime.gluonts -* Source code: https://github.com/cran/modeltime.gluonts -* Date/Publication: 2020-11-30 09:40:02 UTC -* Number of recursive dependencies: 214 - -Run `revdepcheck::cloud_details(, "modeltime.gluonts")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/modeltime.gluonts/new/modeltime.gluonts.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘modeltime.gluonts/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘modeltime.gluonts’ version ‘0.1.0’ -* package encoding: UTF-8 -* checking package namespace information ... 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 - ‘getting-started.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: 1 NOTE - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/modeltime.gluonts/old/modeltime.gluonts.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘modeltime.gluonts/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘modeltime.gluonts’ version ‘0.1.0’ -* package encoding: UTF-8 -* checking package namespace information ... 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 - ‘getting-started.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: 1 NOTE - - - - - -``` -# modeltime.h2o - -
- -* Version: 0.1.1 -* GitHub: https://github.com/business-science/modeltime.h2o -* Source code: https://github.com/cran/modeltime.h2o -* Date/Publication: 2021-04-05 14:40:03 UTC -* Number of recursive dependencies: 214 - -Run `revdepcheck::cloud_details(, "modeltime.h2o")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/modeltime.h2o/new/modeltime.h2o.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘modeltime.h2o/DESCRIPTION’ ... OK -* this is package ‘modeltime.h2o’ version ‘0.1.1’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... OK -... -* checking for code/documentation mismatches ... OK -* checking Rd \usage sections ... OK -* checking Rd contents ... OK -* checking for unstated dependencies in examples ... 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/modeltime.h2o/old/modeltime.h2o.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘modeltime.h2o/DESCRIPTION’ ... OK -* this is package ‘modeltime.h2o’ version ‘0.1.1’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... OK -... -* checking for code/documentation mismatches ... OK -* checking Rd \usage sections ... OK -* checking Rd contents ... OK -* checking for unstated dependencies in examples ... OK -* checking examples ... OK -* checking for unstated dependencies in ‘tests’ ... OK -* checking tests ... OK - Running ‘testthat.R’ -* DONE -Status: OK - - - - - -``` -# modeltime.resample - -
- -* Version: 0.2.2 -* GitHub: https://github.com/business-science/modeltime.resample -* Source code: https://github.com/cran/modeltime.resample -* Date/Publication: 2022-10-18 03:00:06 UTC -* Number of recursive dependencies: 221 - -Run `revdepcheck::cloud_details(, "modeltime.resample")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/modeltime.resample/new/modeltime.resample.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘modeltime.resample/DESCRIPTION’ ... OK -* this is package ‘modeltime.resample’ version ‘0.2.2’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... OK -... ---- failed re-building ‘panel-data.Rmd’ - -SUMMARY: processing the following file failed: - ‘panel-data.Rmd’ - -Error: Vignette re-building failed. -Execution halted - -* DONE -Status: 1 ERROR, 1 WARNING, 1 NOTE - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/modeltime.resample/old/modeltime.resample.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘modeltime.resample/DESCRIPTION’ ... OK -* this is package ‘modeltime.resample’ version ‘0.2.2’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... OK -... ---- failed re-building ‘panel-data.Rmd’ - -SUMMARY: processing the following file failed: - ‘panel-data.Rmd’ - -Error: Vignette re-building failed. -Execution halted - -* DONE -Status: 1 ERROR, 1 WARNING, 1 NOTE - - - - - -``` -# moexer - -
- -* Version: NA -* GitHub: NA -* Source code: https://github.com/cran/moexer -* Number of recursive dependencies: 86 - -Run `revdepcheck::cloud_details(, "moexer")` for more info - -
- -## Error before installation - -### Devel - -``` - - - - - - -``` -### CRAN - -``` - - - - - - -``` -# motif - -
- -* Version: 0.5.2 -* GitHub: https://github.com/Nowosad/motif -* Source code: https://github.com/cran/motif -* Date/Publication: 2022-06-07 05:10:02 UTC -* Number of recursive dependencies: 86 - -Run `revdepcheck::cloud_details(, "motif")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/motif/new/motif.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘motif/DESCRIPTION’ ... OK -* this is package ‘motif’ version ‘0.5.2’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/motif/old/motif.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘motif/DESCRIPTION’ ... OK -* this is package ‘motif’ version ‘0.5.2’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# mpower - -
- -* Version: 0.1.0 -* GitHub: NA -* Source code: https://github.com/cran/mpower -* Date/Publication: 2022-09-21 08:50:05 UTC -* Number of recursive dependencies: 132 - -Run `revdepcheck::cloud_details(, "mpower")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/mpower/new/mpower.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘mpower/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘mpower’ version ‘0.1.0’ -* package encoding: UTF-8 -* checking package namespace information ... 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 - -``` -* using log directory ‘/tmp/workdir/mpower/old/mpower.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘mpower/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘mpower’ version ‘0.1.0’ -* package encoding: UTF-8 -* checking package namespace information ... 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 - - - - - -``` -# MSclassifR - -
- -* Version: 0.3.1 -* GitHub: https://github.com/agodmer/MSclassifR_examples -* Source code: https://github.com/cran/MSclassifR -* Date/Publication: 2022-09-29 06:10:12 UTC -* Number of recursive dependencies: 227 - -Run `revdepcheck::cloud_details(, "MSclassifR")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/MSclassifR/new/MSclassifR.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘MSclassifR/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘MSclassifR’ version ‘0.3.1’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘VSURF’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/MSclassifR/old/MSclassifR.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘MSclassifR/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘MSclassifR’ version ‘0.3.1’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘VSURF’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# multibiasmeta - -
- -* Version: 0.1.0 -* GitHub: https://github.com/mathurlabstanford/multibiasmeta -* Source code: https://github.com/cran/multibiasmeta -* Date/Publication: 2023-02-08 09:40:02 UTC -* Number of recursive dependencies: 99 - -Run `revdepcheck::cloud_details(, "multibiasmeta")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/multibiasmeta/new/multibiasmeta.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘multibiasmeta/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘multibiasmeta’ version ‘0.1.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -... ---- failed re-building ‘tutorial.Rmd’ - -SUMMARY: processing the following file failed: - ‘tutorial.Rmd’ - -Error: Vignette re-building failed. -Execution halted - -* DONE -Status: 1 WARNING, 1 NOTE - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/multibiasmeta/old/multibiasmeta.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘multibiasmeta/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘multibiasmeta’ version ‘0.1.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -... ---- failed re-building ‘tutorial.Rmd’ - -SUMMARY: processing the following file failed: - ‘tutorial.Rmd’ - -Error: Vignette re-building failed. -Execution halted - -* DONE -Status: 1 WARNING, 1 NOTE - - - - - -``` -# naturaList - -
- -* Version: 0.5.0 -* GitHub: https://github.com/avrodrigues/naturaList -* Source code: https://github.com/cran/naturaList -* Date/Publication: 2022-04-20 13:30:02 UTC -* Number of recursive dependencies: 129 - -Run `revdepcheck::cloud_details(, "naturaList")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/naturaList/new/naturaList.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘naturaList/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘naturaList’ version ‘0.5.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -Package suggested but not available for checking: ‘lwgeom’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/naturaList/old/naturaList.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘naturaList/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘naturaList’ version ‘0.5.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -Package suggested but not available for checking: ‘lwgeom’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# ncdfgeom - -
- -* Version: 1.1.4 -* GitHub: https://github.com/USGS-R/ncdfgeom -* Source code: https://github.com/cran/ncdfgeom -* Date/Publication: 2022-11-08 22:40:02 UTC -* Number of recursive dependencies: 90 - -Run `revdepcheck::cloud_details(, "ncdfgeom")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/ncdfgeom/new/ncdfgeom.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘ncdfgeom/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘ncdfgeom’ version ‘1.1.4’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/ncdfgeom/old/ncdfgeom.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘ncdfgeom/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘ncdfgeom’ version ‘1.1.4’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# nhdplusTools - -
- -* Version: 0.6.2 -* GitHub: https://github.com/doi-usgs/nhdplusTools -* Source code: https://github.com/cran/nhdplusTools -* Date/Publication: 2023-03-10 09:40:14 UTC -* Number of recursive dependencies: 167 - -Run `revdepcheck::cloud_details(, "nhdplusTools")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/nhdplusTools/new/nhdplusTools.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘nhdplusTools/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘nhdplusTools’ version ‘0.6.2’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -Package suggested but not available for checking: ‘lwgeom’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/nhdplusTools/old/nhdplusTools.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘nhdplusTools/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘nhdplusTools’ version ‘0.6.2’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -Package suggested but not available for checking: ‘lwgeom’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# nhdR - -
- -* Version: 0.5.9 -* GitHub: https://github.com/jsta/nhdR -* Source code: https://github.com/cran/nhdR -* Date/Publication: 2022-10-09 02:10:02 UTC -* Number of recursive dependencies: 104 - -Run `revdepcheck::cloud_details(, "nhdR")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/nhdR/new/nhdR.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘nhdR/DESCRIPTION’ ... OK -* this is package ‘nhdR’ version ‘0.5.9’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -Package suggested but not available for checking: ‘lwgeom’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/nhdR/old/nhdR.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘nhdR/DESCRIPTION’ ... OK -* this is package ‘nhdR’ version ‘0.5.9’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -Package suggested but not available for checking: ‘lwgeom’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# nlmixr2extra - -
- -* Version: 2.0.8 -* GitHub: https://github.com/nlmixr2/nlmixr2extra -* Source code: https://github.com/cran/nlmixr2extra -* Date/Publication: 2022-10-22 22:32:34 UTC -* Number of recursive dependencies: 203 - -Run `revdepcheck::cloud_details(, "nlmixr2extra")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/nlmixr2extra/new/nlmixr2extra.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘nlmixr2extra/DESCRIPTION’ ... OK -* this is package ‘nlmixr2extra’ version ‘2.0.8’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Packages required but not available: 'nlmixr2est', 'symengine' - -Package suggested but not available for checking: ‘brms’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/nlmixr2extra/old/nlmixr2extra.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘nlmixr2extra/DESCRIPTION’ ... OK -* this is package ‘nlmixr2extra’ version ‘2.0.8’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Packages required but not available: 'nlmixr2est', 'symengine' - -Package suggested but not available for checking: ‘brms’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# nlmixr2plot - -
- -* Version: 2.0.7 -* GitHub: https://github.com/nlmixr2/nlmixr2plot -* Source code: https://github.com/cran/nlmixr2plot -* Date/Publication: 2022-10-20 03:12:36 UTC -* Number of recursive dependencies: 163 - -Run `revdepcheck::cloud_details(, "nlmixr2plot")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/nlmixr2plot/new/nlmixr2plot.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘nlmixr2plot/DESCRIPTION’ ... OK -* this is package ‘nlmixr2plot’ version ‘2.0.7’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Packages required but not available: 'nlmixr2est', 'nlmixr2extra' - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/nlmixr2plot/old/nlmixr2plot.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘nlmixr2plot/DESCRIPTION’ ... OK -* this is package ‘nlmixr2plot’ version ‘2.0.7’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Packages required but not available: 'nlmixr2est', 'nlmixr2extra' - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# nlmixr2rpt - -
- -* Version: 0.1.0 -* GitHub: https://github.com/nlmixr2/nlmixr2rpt -* Source code: https://github.com/cran/nlmixr2rpt -* Date/Publication: 2022-12-05 10:40:02 UTC -* Number of recursive dependencies: 218 - -Run `revdepcheck::cloud_details(, "nlmixr2rpt")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/nlmixr2rpt/new/nlmixr2rpt.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘nlmixr2rpt/DESCRIPTION’ ... OK -* this is package ‘nlmixr2rpt’ version ‘0.1.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Packages required but not available: 'nlmixr2extra', 'xpose.nlmixr2' - -Package suggested but not available for checking: ‘nlmixr2’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/nlmixr2rpt/old/nlmixr2rpt.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘nlmixr2rpt/DESCRIPTION’ ... OK -* this is package ‘nlmixr2rpt’ version ‘0.1.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Packages required but not available: 'nlmixr2extra', 'xpose.nlmixr2' - -Package suggested but not available for checking: ‘nlmixr2’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# numbat - -
- -* Version: 1.2.2 -* GitHub: https://github.com/kharchenkolab/numbat -* Source code: https://github.com/cran/numbat -* Date/Publication: 2023-02-14 18:20:02 UTC -* Number of recursive dependencies: 132 - -Run `revdepcheck::cloud_details(, "numbat")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/numbat/new/numbat.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘numbat/DESCRIPTION’ ... OK -* this is package ‘numbat’ version ‘1.2.2’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Packages required but not available: 'ggtree', 'scistreer' - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/numbat/old/numbat.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘numbat/DESCRIPTION’ ... OK -* this is package ‘numbat’ version ‘1.2.2’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Packages required but not available: 'ggtree', 'scistreer' - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# OBL - -
- -* Version: NA -* GitHub: NA -* Source code: https://github.com/cran/OBL -* Number of recursive dependencies: 73 - -Run `revdepcheck::cloud_details(, "OBL")` for more info - -
- -## Error before installation - -### Devel - -``` - - - - - - -``` -### CRAN - -``` - - - - - - -``` -# occCite - -
- -* Version: 0.5.6 -* GitHub: https://github.com/ropensci/occCite -* Source code: https://github.com/cran/occCite -* Date/Publication: 2022-08-05 11:40:02 UTC -* Number of recursive dependencies: 176 - -Run `revdepcheck::cloud_details(, "occCite")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/occCite/new/occCite.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘occCite/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘occCite’ version ‘0.5.6’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘BIEN’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/occCite/old/occCite.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘occCite/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘occCite’ version ‘0.5.6’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘BIEN’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# occUncertain - -
- -* Version: 0.1.0 -* GitHub: https://github.com/mlammens/occUncertain -* Source code: https://github.com/cran/occUncertain -* Date/Publication: 2023-01-20 10:10:06 UTC -* Number of recursive dependencies: 103 - -Run `revdepcheck::cloud_details(, "occUncertain")` for more info - -
- -## In both - -* checking whether package ‘occUncertain’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/occUncertain/new/occUncertain.Rcheck/00install.out’ for details. - ``` - -## Installation - -### Devel - -``` -* installing *source* package ‘occUncertain’ ... -** package ‘occUncertain’ 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 ‘ConR’ in loadNamespace(i, c(lib.loc, .libPaths()), versionCheck = vI[[i]]): - there is no package called ‘sf’ -Execution halted -ERROR: lazy loading failed for package ‘occUncertain’ -* removing ‘/tmp/workdir/occUncertain/new/occUncertain.Rcheck/occUncertain’ - - -``` -### CRAN - -``` -* installing *source* package ‘occUncertain’ ... -** package ‘occUncertain’ 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 ‘ConR’ in loadNamespace(i, c(lib.loc, .libPaths()), versionCheck = vI[[i]]): - there is no package called ‘sf’ -Execution halted -ERROR: lazy loading failed for package ‘occUncertain’ -* removing ‘/tmp/workdir/occUncertain/old/occUncertain.Rcheck/occUncertain’ - - -``` -# oceanexplorer - -
- -* Version: 0.0.2 -* GitHub: https://github.com/UtrechtUniversity/oceanexplorer -* Source code: https://github.com/cran/oceanexplorer -* Date/Publication: 2022-09-15 09:10:08 UTC -* Number of recursive dependencies: 158 - -Run `revdepcheck::cloud_details(, "oceanexplorer")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/oceanexplorer/new/oceanexplorer.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘oceanexplorer/DESCRIPTION’ ... OK -* this is package ‘oceanexplorer’ version ‘0.0.2’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/oceanexplorer/old/oceanexplorer.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘oceanexplorer/DESCRIPTION’ ... OK -* this is package ‘oceanexplorer’ version ‘0.0.2’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# oceanis - -
- -* Version: 1.8.5 -* GitHub: https://github.com/insee-psar-at/oceanis-package -* Source code: https://github.com/cran/oceanis -* Date/Publication: 2022-07-13 13:10:02 UTC -* Number of recursive dependencies: 117 - -Run `revdepcheck::cloud_details(, "oceanis")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/oceanis/new/oceanis.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘oceanis/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘oceanis’ version ‘1.8.5’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Packages required but not available: 'sf', 'lwgeom' - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/oceanis/old/oceanis.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘oceanis/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘oceanis’ version ‘1.8.5’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Packages required but not available: 'sf', 'lwgeom' - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# ohsome - -
- -* Version: 0.2.1 -* GitHub: https://github.com/GIScience/ohsome-r -* Source code: https://github.com/cran/ohsome -* Date/Publication: 2023-02-22 14:50:02 UTC -* Number of recursive dependencies: 150 - -Run `revdepcheck::cloud_details(, "ohsome")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/ohsome/new/ohsome.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘ohsome/DESCRIPTION’ ... OK -* this is package ‘ohsome’ version ‘0.2.1’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/ohsome/old/ohsome.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘ohsome/DESCRIPTION’ ... OK -* this is package ‘ohsome’ version ‘0.2.1’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# OlinkAnalyze - -
- -* Version: 3.3.1 -* GitHub: NA -* Source code: https://github.com/cran/OlinkAnalyze -* Date/Publication: 2023-02-27 20:22:30 UTC -* Number of recursive dependencies: 202 - -Run `revdepcheck::cloud_details(, "OlinkAnalyze")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/OlinkAnalyze/new/OlinkAnalyze.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘OlinkAnalyze/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘OlinkAnalyze’ version ‘3.3.1’ -* package encoding: UTF-8 -* checking package namespace information ... 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 - ‘Vignett.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: 1 NOTE - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/OlinkAnalyze/old/OlinkAnalyze.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘OlinkAnalyze/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘OlinkAnalyze’ version ‘3.3.1’ -* package encoding: UTF-8 -* checking package namespace information ... 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 - ‘Vignett.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: 1 NOTE - - - - - -``` -# OpenLand - -
- -* Version: 1.0.2 -* GitHub: https://github.com/reginalexavier/OpenLand -* Source code: https://github.com/cran/OpenLand -* Date/Publication: 2021-11-02 07:20:02 UTC -* Number of recursive dependencies: 121 - -Run `revdepcheck::cloud_details(, "OpenLand")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/OpenLand/new/OpenLand.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘OpenLand/DESCRIPTION’ ... OK -* this is package ‘OpenLand’ version ‘1.0.2’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... 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 - ‘openland_vignette.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: OK - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/OpenLand/old/OpenLand.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘OpenLand/DESCRIPTION’ ... OK -* this is package ‘OpenLand’ version ‘1.0.2’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... 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 - ‘openland_vignette.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: OK - - - - - -``` -# palaeoSig - -
- -* Version: 2.1-3 -* GitHub: https://github.com/richardjtelford/palaeoSig -* Source code: https://github.com/cran/palaeoSig -* Date/Publication: 2023-03-10 09:30:02 UTC -* Number of recursive dependencies: 104 - -Run `revdepcheck::cloud_details(, "palaeoSig")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/palaeoSig/new/palaeoSig.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘palaeoSig/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘palaeoSig’ version ‘2.1-3’ -* package encoding: UTF-8 -* checking package namespace information ... OK -... ---- failed re-building ‘randomTF-spatial.Rmd’ - -SUMMARY: processing the following files failed: - ‘h-block-crossvalidation.Rmd’ ‘randomTF-spatial.Rmd’ - -Error: Vignette re-building failed. -Execution halted - -* DONE -Status: 1 ERROR, 1 WARNING, 1 NOTE - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/palaeoSig/old/palaeoSig.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘palaeoSig/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘palaeoSig’ version ‘2.1-3’ -* package encoding: UTF-8 -* checking package namespace information ... OK -... ---- failed re-building ‘randomTF-spatial.Rmd’ - -SUMMARY: processing the following files failed: - ‘h-block-crossvalidation.Rmd’ ‘randomTF-spatial.Rmd’ - -Error: Vignette re-building failed. -Execution halted - -* DONE -Status: 1 ERROR, 1 WARNING, 1 NOTE - - - - - -``` -# panelr - -
- -* Version: 0.7.7 -* GitHub: https://github.com/jacob-long/panelr -* Source code: https://github.com/cran/panelr -* Date/Publication: 2023-02-09 16:00:02 UTC -* Number of recursive dependencies: 169 - -Run `revdepcheck::cloud_details(, "panelr")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/panelr/new/panelr.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘panelr/DESCRIPTION’ ... OK -* this is package ‘panelr’ version ‘0.7.7’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... NOTE -... - 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 ... NONE - ‘reshape.Rmd’ using ‘UTF-8’... OK - ‘wbm.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: 1 ERROR, 2 NOTEs - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/panelr/old/panelr.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘panelr/DESCRIPTION’ ... OK -* this is package ‘panelr’ version ‘0.7.7’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... NOTE -... - 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 ... NONE - ‘reshape.Rmd’ using ‘UTF-8’... OK - ‘wbm.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: 1 ERROR, 2 NOTEs - - - - - -``` -# pathwayTMB - -
- -* Version: 0.1.3 -* GitHub: NA -* Source code: https://github.com/cran/pathwayTMB -* Date/Publication: 2022-08-09 13:50:02 UTC -* Number of recursive dependencies: 221 - -Run `revdepcheck::cloud_details(, "pathwayTMB")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/pathwayTMB/new/pathwayTMB.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘pathwayTMB/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘pathwayTMB’ version ‘0.1.3’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘clusterProfiler’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/pathwayTMB/old/pathwayTMB.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘pathwayTMB/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘pathwayTMB’ version ‘0.1.3’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘clusterProfiler’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# pct - -
- -* Version: 0.9.8 -* GitHub: https://github.com/ITSLeeds/pct -* Source code: https://github.com/cran/pct -* Date/Publication: 2023-02-16 00:30:02 UTC -* Number of recursive dependencies: 138 - -Run `revdepcheck::cloud_details(, "pct")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/pct/new/pct.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘pct/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘pct’ version ‘0.9.8’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/pct/old/pct.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘pct/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘pct’ version ‘0.9.8’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# peramo - -
- -* Version: NA -* GitHub: NA -* Source code: https://github.com/cran/peramo -* Number of recursive dependencies: 17 - -Run `revdepcheck::cloud_details(, "peramo")` for more info - -
- -## Error before installation - -### Devel - -``` - - - - - - -``` -### CRAN - -``` - - - - - - -``` -# photosynthesis - -
- -* Version: 2.1.1 -* GitHub: https://github.com/cdmuir/photosynthesis -* Source code: https://github.com/cran/photosynthesis -* Date/Publication: 2022-11-19 19:40:09 UTC -* Number of recursive dependencies: 135 - -Run `revdepcheck::cloud_details(, "photosynthesis")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/photosynthesis/new/photosynthesis.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘photosynthesis/DESCRIPTION’ ... OK -* this is package ‘photosynthesis’ version ‘2.1.1’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... NOTE -... - ‘mesophyll-conductance.Rmd’ using ‘UTF-8’... OK - ‘modeling-recommendations.Rmd’ using ‘UTF-8’... OK - ‘photosynthesis-introduction.Rmd’ using ‘UTF-8’... OK - ‘pressure-volume.Rmd’ using ‘UTF-8’... OK - ‘sensitivity-analysis.Rmd’ using ‘UTF-8’... OK - ‘stomatal-conductance.Rmd’ using ‘UTF-8’... OK - ‘temperature-response.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: 1 ERROR, 4 NOTEs - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/photosynthesis/old/photosynthesis.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘photosynthesis/DESCRIPTION’ ... OK -* this is package ‘photosynthesis’ version ‘2.1.1’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... NOTE -... - ‘mesophyll-conductance.Rmd’ using ‘UTF-8’... OK - ‘modeling-recommendations.Rmd’ using ‘UTF-8’... OK - ‘photosynthesis-introduction.Rmd’ using ‘UTF-8’... OK - ‘pressure-volume.Rmd’ using ‘UTF-8’... OK - ‘sensitivity-analysis.Rmd’ using ‘UTF-8’... OK - ‘stomatal-conductance.Rmd’ using ‘UTF-8’... OK - ‘temperature-response.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: 1 ERROR, 4 NOTEs - - - - - -``` -# Platypus - -
- -* Version: 3.4.1 -* GitHub: NA -* Source code: https://github.com/cran/Platypus -* Date/Publication: 2022-08-15 07:20:20 UTC -* Number of recursive dependencies: 356 - -Run `revdepcheck::cloud_details(, "Platypus")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/Platypus/new/Platypus.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘Platypus/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘Platypus’ version ‘3.4.1’ -* package encoding: UTF-8 -* checking package namespace information ... OK -... -* checking package dependencies ... ERROR -Package required but not available: ‘ggtree’ - -Packages suggested but not available for checking: - 'Matrix.utils', 'monocle3', 'ProjecTILs', 'SeuratWrappers' - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/Platypus/old/Platypus.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘Platypus/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘Platypus’ version ‘3.4.1’ -* package encoding: UTF-8 -* checking package namespace information ... OK -... -* checking package dependencies ... ERROR -Package required but not available: ‘ggtree’ - -Packages suggested but not available for checking: - 'Matrix.utils', 'monocle3', 'ProjecTILs', 'SeuratWrappers' - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# PLSiMCpp - -
- -* Version: NA -* GitHub: NA -* Source code: https://github.com/cran/PLSiMCpp -* Number of recursive dependencies: 10 - -Run `revdepcheck::cloud_details(, "PLSiMCpp")` for more info - -
- -## Error before installation - -### Devel - -``` - - - - - - -``` -### CRAN - -``` - - - - - - -``` -# PoolTestR - -
- -* Version: 0.1.3 -* GitHub: https://github.com/AngusMcLure/PoolTestR -* Source code: https://github.com/cran/PoolTestR -* Date/Publication: 2022-07-01 07:30:02 UTC -* Number of recursive dependencies: 132 - -Run `revdepcheck::cloud_details(, "PoolTestR")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/PoolTestR/new/PoolTestR.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘PoolTestR/DESCRIPTION’ ... OK -* this is package ‘PoolTestR’ version ‘0.1.3’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Packages required but not available: 'rstan', 'brms' - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/PoolTestR/old/PoolTestR.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘PoolTestR/DESCRIPTION’ ... OK -* this is package ‘PoolTestR’ version ‘0.1.3’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Packages required but not available: 'rstan', 'brms' - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# PopGenHelpR - -
- -* Version: 1.0.0 -* GitHub: https://github.com/kfarleigh/PopGenHelpR -* Source code: https://github.com/cran/PopGenHelpR -* Date/Publication: 2023-02-13 08:40:05 UTC -* Number of recursive dependencies: 187 - -Run `revdepcheck::cloud_details(, "PopGenHelpR")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/PopGenHelpR/new/PopGenHelpR.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘PopGenHelpR/DESCRIPTION’ ... OK -* this is package ‘PopGenHelpR’ version ‘1.0.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... 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 - ‘PopGenHelpR_vignette.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: OK - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/PopGenHelpR/old/PopGenHelpR.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘PopGenHelpR/DESCRIPTION’ ... OK -* this is package ‘PopGenHelpR’ version ‘1.0.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... 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 - ‘PopGenHelpR_vignette.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: OK - - - - - -``` -# ppcSpatial - -
- -* Version: 0.2.0 -* GitHub: https://github.com/MYaseen208/ppcSpatial -* Source code: https://github.com/cran/ppcSpatial -* Date/Publication: 2018-03-07 15:54:23 UTC -* Number of recursive dependencies: 118 - -Run `revdepcheck::cloud_details(, "ppcSpatial")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/ppcSpatial/new/ppcSpatial.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘ppcSpatial/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘ppcSpatial’ version ‘0.2.0’ -* checking package namespace information ... OK -* checking package dependencies ... 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 ‘ppcSpatial’ can be installed ... ERROR -Installation failed. -See ‘/tmp/workdir/ppcSpatial/new/ppcSpatial.Rcheck/00install.out’ for details. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/ppcSpatial/old/ppcSpatial.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘ppcSpatial/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘ppcSpatial’ version ‘0.2.0’ -* checking package namespace information ... OK -* checking package dependencies ... 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 ‘ppcSpatial’ can be installed ... ERROR -Installation failed. -See ‘/tmp/workdir/ppcSpatial/old/ppcSpatial.Rcheck/00install.out’ for details. -* DONE -Status: 1 ERROR - - - - - -``` -# prioriactions - -
- -* Version: 0.4.1 -* GitHub: https://github.com/prioriactions/prioriactions -* Source code: https://github.com/cran/prioriactions -* Date/Publication: 2022-08-16 13:30:02 UTC -* Number of recursive dependencies: 130 - -Run `revdepcheck::cloud_details(, "prioriactions")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/prioriactions/new/prioriactions.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘prioriactions/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘prioriactions’ version ‘0.4.1’ -* package encoding: UTF-8 -* checking package namespace information ... OK -... -* checking for unstated dependencies in vignettes ... OK -* checking package vignettes in ‘inst/doc’ ... OK -* checking running R code from vignettes ... NONE - ‘objectives.Rmd’ using ‘UTF-8’... OK - ‘sensitivities.Rmd’ using ‘UTF-8’... OK - ‘MitchellRiver.Rmd’ using ‘UTF-8’... OK - ‘prioriactions.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: 2 NOTEs - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/prioriactions/old/prioriactions.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘prioriactions/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘prioriactions’ version ‘0.4.1’ -* package encoding: UTF-8 -* checking package namespace information ... OK -... -* checking for unstated dependencies in vignettes ... OK -* checking package vignettes in ‘inst/doc’ ... OK -* checking running R code from vignettes ... NONE - ‘objectives.Rmd’ using ‘UTF-8’... OK - ‘sensitivities.Rmd’ using ‘UTF-8’... OK - ‘MitchellRiver.Rmd’ using ‘UTF-8’... OK - ‘prioriactions.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: 2 NOTEs - - - - - -``` -# promotionImpact - -
- -* Version: 0.1.5 -* GitHub: https://github.com/ncsoft/promotionImpact -* Source code: https://github.com/cran/promotionImpact -* Date/Publication: 2021-04-13 15:00:05 UTC -* Number of recursive dependencies: 122 - -Run `revdepcheck::cloud_details(, "promotionImpact")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/promotionImpact/new/promotionImpact.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘promotionImpact/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘promotionImpact’ version ‘0.1.5’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘prophet’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/promotionImpact/old/promotionImpact.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘promotionImpact/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘promotionImpact’ version ‘0.1.5’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘prophet’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# prqlr - -
- -* Version: NA -* GitHub: NA -* Source code: https://github.com/cran/prqlr -* Number of recursive dependencies: 66 - -Run `revdepcheck::cloud_details(, "prqlr")` for more info - -
- -## Error before installation - -### Devel - -``` - - - - - - -``` -### CRAN - -``` - - - - - - -``` -# PSS.Health - -
- -* Version: 0.6.1 -* GitHub: NA -* Source code: https://github.com/cran/PSS.Health -* Date/Publication: 2023-02-01 17:50:11 UTC -* Number of recursive dependencies: 187 - -Run `revdepcheck::cloud_details(, "PSS.Health")` for more info - -
- -## In both - -* checking whether package ‘PSS.Health’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/PSS.Health/new/PSS.Health.Rcheck/00install.out’ for details. - ``` - -## Installation - -### Devel - -``` -* installing *source* package ‘PSS.Health’ ... -** package ‘PSS.Health’ 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 ‘sf’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart -Execution halted -ERROR: lazy loading failed for package ‘PSS.Health’ -* removing ‘/tmp/workdir/PSS.Health/new/PSS.Health.Rcheck/PSS.Health’ - - -``` -### CRAN - -``` -* installing *source* package ‘PSS.Health’ ... -** package ‘PSS.Health’ 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 ‘sf’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart -Execution halted -ERROR: lazy loading failed for package ‘PSS.Health’ -* removing ‘/tmp/workdir/PSS.Health/old/PSS.Health.Rcheck/PSS.Health’ - - -``` -# PsychWordVec - -
- -* Version: 0.3.2 -* GitHub: https://github.com/psychbruce/PsychWordVec -* Source code: https://github.com/cran/PsychWordVec -* Date/Publication: 2023-03-04 16:20:02 UTC -* Number of recursive dependencies: 228 - -Run `revdepcheck::cloud_details(, "PsychWordVec")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/PsychWordVec/new/PsychWordVec.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘PsychWordVec/DESCRIPTION’ ... OK -* this is package ‘PsychWordVec’ version ‘0.3.2’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘bruceR’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/PsychWordVec/old/PsychWordVec.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘PsychWordVec/DESCRIPTION’ ... OK -* this is package ‘PsychWordVec’ version ‘0.3.2’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘bruceR’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# rangeModelMetadata - -
- -* Version: 0.1.4 -* GitHub: NA -* Source code: https://github.com/cran/rangeModelMetadata -* Date/Publication: 2021-06-11 08:40:02 UTC -* Number of recursive dependencies: 192 - -Run `revdepcheck::cloud_details(, "rangeModelMetadata")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/rangeModelMetadata/new/rangeModelMetadata.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘rangeModelMetadata/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘rangeModelMetadata’ version ‘0.1.4’ -* package encoding: UTF-8 -* checking package namespace information ... 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 - ‘rmm_Multispecies.Rmd’ using ‘UTF-8’... OK - ‘rmm_directory.Rmd’ using ‘UTF-8’... OK - ‘rmm_vignette.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: 3 NOTEs - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/rangeModelMetadata/old/rangeModelMetadata.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘rangeModelMetadata/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘rangeModelMetadata’ version ‘0.1.4’ -* package encoding: UTF-8 -* checking package namespace information ... 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 - ‘rmm_Multispecies.Rmd’ using ‘UTF-8’... OK - ‘rmm_directory.Rmd’ using ‘UTF-8’... OK - ‘rmm_vignette.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: 3 NOTEs - - - - - -``` -# rbenvo - -
- -* Version: 1.0.5 -* GitHub: https://github.com/apeterson91/rbenvo -* Source code: https://github.com/cran/rbenvo -* Date/Publication: 2020-11-18 10:40:02 UTC -* Number of recursive dependencies: 104 - -Run `revdepcheck::cloud_details(, "rbenvo")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/rbenvo/new/rbenvo.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘rbenvo/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘rbenvo’ version ‘1.0.5’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -Package suggested but not available for checking: ‘lwgeom’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/rbenvo/old/rbenvo.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘rbenvo/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘rbenvo’ version ‘1.0.5’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -Package suggested but not available for checking: ‘lwgeom’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# RBesT - -
- -* Version: 1.6-6 -* GitHub: https://github.com/Novartis/RBesT -* Source code: https://github.com/cran/RBesT -* Date/Publication: 2023-03-03 18:20:02 UTC -* Number of recursive dependencies: 131 - -Run `revdepcheck::cloud_details(, "RBesT")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/RBesT/new/RBesT.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘RBesT/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘RBesT’ version ‘1.6-6’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘rstan’ - -Package suggested but not available for checking: ‘rstanarm’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/RBesT/old/RBesT.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘RBesT/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘RBesT’ version ‘1.6-6’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘rstan’ - -Package suggested but not available for checking: ‘rstanarm’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# rcontroll - -
- -* Version: 0.1.0 -* GitHub: https://github.com/sylvainschmitt/rcontroll -* Source code: https://github.com/cran/rcontroll -* Date/Publication: 2023-02-11 15:20:02 UTC -* Number of recursive dependencies: 128 - -Run `revdepcheck::cloud_details(, "rcontroll")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/rcontroll/new/rcontroll.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘rcontroll/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘rcontroll’ version ‘0.1.0’ -* package encoding: UTF-8 -* checking package namespace information ... 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 ‘rcontroll’ can be installed ... ERROR -Installation failed. -See ‘/tmp/workdir/rcontroll/new/rcontroll.Rcheck/00install.out’ for details. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/rcontroll/old/rcontroll.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘rcontroll/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘rcontroll’ version ‘0.1.0’ -* package encoding: UTF-8 -* checking package namespace information ... 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 ‘rcontroll’ can be installed ... ERROR -Installation failed. -See ‘/tmp/workdir/rcontroll/old/rcontroll.Rcheck/00install.out’ for details. -* DONE -Status: 1 ERROR - - - - - -``` -# rcssci - -
- -* Version: NA -* GitHub: NA -* Source code: https://github.com/cran/rcssci -* Number of recursive dependencies: 136 - -Run `revdepcheck::cloud_details(, "rcssci")` for more info - -
- -## Error before installation - -### Devel - -``` - - - - - - -``` -### CRAN - -``` - - - - - - -``` -# RCzechia - -
- -* Version: 1.11.1 -* GitHub: https://github.com/jlacko/RCzechia -* Source code: https://github.com/cran/RCzechia -* Date/Publication: 2023-03-05 06:40:07 UTC -* Number of recursive dependencies: 139 - -Run `revdepcheck::cloud_details(, "RCzechia")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/RCzechia/new/RCzechia.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘RCzechia/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘RCzechia’ version ‘1.11.1’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -Package suggested but not available for checking: ‘lwgeom’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/RCzechia/old/RCzechia.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘RCzechia/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘RCzechia’ version ‘1.11.1’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -Package suggested but not available for checking: ‘lwgeom’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# rdss - -
- -* Version: 1.0.0 -* GitHub: NA -* Source code: https://github.com/cran/rdss -* Date/Publication: 2023-01-17 17:40:02 UTC -* Number of recursive dependencies: 207 - -Run `revdepcheck::cloud_details(, "rdss")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/rdss/new/rdss.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘rdss/DESCRIPTION’ ... OK -* this is package ‘rdss’ version ‘1.0.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... NOTE -... -* 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 - -``` -* using log directory ‘/tmp/workdir/rdss/old/rdss.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘rdss/DESCRIPTION’ ... OK -* this is package ‘rdss’ version ‘1.0.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... NOTE -... -* 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 - - - - - -``` -# redist - -
- -* Version: 4.0.1 -* GitHub: https://github.com/alarm-redist/redist -* Source code: https://github.com/cran/redist -* Date/Publication: 2022-06-16 06:20:07 UTC -* Number of recursive dependencies: 147 - -Run `revdepcheck::cloud_details(, "redist")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/redist/new/redist.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘redist/DESCRIPTION’ ... OK -* this is package ‘redist’ version ‘4.0.1’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -Package suggested but not available for checking: ‘lwgeom’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/redist/old/redist.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘redist/DESCRIPTION’ ... OK -* this is package ‘redist’ version ‘4.0.1’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -Package suggested but not available for checking: ‘lwgeom’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# remap - -
- -* Version: 0.3.0 -* GitHub: https://github.com/jadonwagstaff/remap -* Source code: https://github.com/cran/remap -* Date/Publication: 2022-08-12 23:10:02 UTC -* Number of recursive dependencies: 67 - -Run `revdepcheck::cloud_details(, "remap")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/remap/new/remap.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘remap/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘remap’ version ‘0.3.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -Package suggested but not available for checking: ‘lwgeom’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/remap/old/remap.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘remap/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘remap’ version ‘0.3.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -Package suggested but not available for checking: ‘lwgeom’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# report - -
- -* Version: 0.5.6 -* GitHub: https://github.com/easystats/report -* Source code: https://github.com/cran/report -* Date/Publication: 2023-02-05 20:42:31 UTC -* Number of recursive dependencies: 156 - -Run `revdepcheck::cloud_details(, "report")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/report/new/report.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘report/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘report’ version ‘0.5.6’ -* package encoding: UTF-8 -* checking package namespace information ... OK -... -* checking for unstated dependencies in vignettes ... OK -* checking package vignettes in ‘inst/doc’ ... OK -* checking running R code from vignettes ... NONE - ‘cite_packages.Rmd’ using ‘UTF-8’... OK - ‘new_models.Rmd’ using ‘UTF-8’... OK - ‘report.Rmd’ using ‘UTF-8’... OK - ‘report_table.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: 1 NOTE - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/report/old/report.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘report/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘report’ version ‘0.5.6’ -* package encoding: UTF-8 -* checking package namespace information ... OK -... -* checking for unstated dependencies in vignettes ... OK -* checking package vignettes in ‘inst/doc’ ... OK -* checking running R code from vignettes ... NONE - ‘cite_packages.Rmd’ using ‘UTF-8’... OK - ‘new_models.Rmd’ using ‘UTF-8’... OK - ‘report.Rmd’ using ‘UTF-8’... OK - ‘report_table.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: 1 NOTE - - - - - -``` -# RevGadgets - -
- -* Version: NA -* GitHub: NA -* Source code: https://github.com/cran/RevGadgets -* Number of recursive dependencies: 125 - -Run `revdepcheck::cloud_details(, "RevGadgets")` for more info - -
- -## Error before installation - -### Devel - -``` - - - - - - -``` -### CRAN - -``` - - - - - - -``` -# rGhanaCensus - -
- -* Version: 0.1.0 -* GitHub: https://github.com/ktemadarko/rGhanaCensus -* Source code: https://github.com/cran/rGhanaCensus -* Date/Publication: 2022-01-13 20:02:43 UTC -* Number of recursive dependencies: 94 - -Run `revdepcheck::cloud_details(, "rGhanaCensus")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/rGhanaCensus/new/rGhanaCensus.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘rGhanaCensus/DESCRIPTION’ ... OK -* this is package ‘rGhanaCensus’ version ‘0.1.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... NOTE -... ---- failed re-building ‘Create_map_displaying_Ghana_2019_School_Attendance_Indicators.Rmd’ - -SUMMARY: processing the following file failed: - ‘Create_map_displaying_Ghana_2019_School_Attendance_Indicators.Rmd’ - -Error: Vignette re-building failed. -Execution halted - -* DONE -Status: 1 WARNING, 1 NOTE - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/rGhanaCensus/old/rGhanaCensus.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘rGhanaCensus/DESCRIPTION’ ... OK -* this is package ‘rGhanaCensus’ version ‘0.1.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... NOTE -... ---- failed re-building ‘Create_map_displaying_Ghana_2019_School_Attendance_Indicators.Rmd’ - -SUMMARY: processing the following file failed: - ‘Create_map_displaying_Ghana_2019_School_Attendance_Indicators.Rmd’ - -Error: Vignette re-building failed. -Execution halted - -* DONE -Status: 1 WARNING, 1 NOTE - - - - - -``` -# rnaturalearth - -
- -* Version: 0.3.2 -* GitHub: https://github.com/ropensci/rnaturalearth -* Source code: https://github.com/cran/rnaturalearth -* Date/Publication: 2023-01-23 07:50:02 UTC -* Number of recursive dependencies: 157 - -Run `revdepcheck::cloud_details(, "rnaturalearth")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/rnaturalearth/new/rnaturalearth.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘rnaturalearth/DESCRIPTION’ ... OK -* this is package ‘rnaturalearth’ version ‘0.3.2’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/rnaturalearth/old/rnaturalearth.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘rnaturalearth/DESCRIPTION’ ... OK -* this is package ‘rnaturalearth’ version ‘0.3.2’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# roads - -
- -* Version: 1.1.0 -* GitHub: https://github.com/LandSciTech/roads -* Source code: https://github.com/cran/roads -* Date/Publication: 2023-02-02 16:10:02 UTC -* Number of recursive dependencies: 111 - -Run `revdepcheck::cloud_details(, "roads")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/roads/new/roads.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘roads/DESCRIPTION’ ... OK -* this is package ‘roads’ version ‘1.1.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/roads/old/roads.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘roads/DESCRIPTION’ ... OK -* this is package ‘roads’ version ‘1.1.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# Robyn - -
- -* Version: 3.9.0 -* GitHub: https://github.com/facebookexperimental/Robyn -* Source code: https://github.com/cran/Robyn -* Date/Publication: 2023-02-08 08:12:37 UTC -* Number of recursive dependencies: 139 - -Run `revdepcheck::cloud_details(, "Robyn")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/Robyn/new/Robyn.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘Robyn/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘Robyn’ version ‘3.9.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘prophet’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/Robyn/old/Robyn.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘Robyn/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘Robyn’ version ‘3.9.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘prophet’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# Rsagacmd - -
- -* Version: 0.2.0 -* GitHub: https://github.com/stevenpawley/Rsagacmd -* Source code: https://github.com/cran/Rsagacmd -* Date/Publication: 2022-04-04 04:10:02 UTC -* Number of recursive dependencies: 70 - -Run `revdepcheck::cloud_details(, "Rsagacmd")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/Rsagacmd/new/Rsagacmd.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘Rsagacmd/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘Rsagacmd’ version ‘0.2.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/Rsagacmd/old/Rsagacmd.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘Rsagacmd/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘Rsagacmd’ version ‘0.2.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# rsinaica - -
- -* Version: 0.6.1 -* GitHub: https://github.com/diegovalle/rsinaica -* Source code: https://github.com/cran/rsinaica -* Date/Publication: 2019-02-04 21:10:03 UTC -* Number of recursive dependencies: 126 - -Run `revdepcheck::cloud_details(, "rsinaica")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/rsinaica/new/rsinaica.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘rsinaica/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘rsinaica’ version ‘0.6.1’ -* package encoding: UTF-8 -* checking package namespace information ... OK -... -* checking data for non-ASCII characters ... NOTE - Note: found 467 marked UTF-8 strings -* 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 - -``` -* using log directory ‘/tmp/workdir/rsinaica/old/rsinaica.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘rsinaica/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘rsinaica’ version ‘0.6.1’ -* package encoding: UTF-8 -* checking package namespace information ... OK -... -* checking data for non-ASCII characters ... NOTE - Note: found 467 marked UTF-8 strings -* 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 - - - - - -``` -# rstac - -
- -* Version: 0.9.2-2 -* GitHub: https://github.com/brazil-data-cube/rstac -* Source code: https://github.com/cran/rstac -* Date/Publication: 2023-02-01 18:00:02 UTC -* Number of recursive dependencies: 115 - -Run `revdepcheck::cloud_details(, "rstac")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/rstac/new/rstac.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘rstac/DESCRIPTION’ ... OK -* this is package ‘rstac’ version ‘0.9.2-2’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... NOTE -... ---- failed re-building ‘rstac-03-cql2-mpc.Rmd’ - -SUMMARY: processing the following file failed: - ‘rstac-03-cql2-mpc.Rmd’ - -Error: Vignette re-building failed. -Execution halted - -* DONE -Status: 1 WARNING, 1 NOTE - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/rstac/old/rstac.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘rstac/DESCRIPTION’ ... OK -* this is package ‘rstac’ version ‘0.9.2-2’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... NOTE -... ---- failed re-building ‘rstac-03-cql2-mpc.Rmd’ - -SUMMARY: processing the following file failed: - ‘rstac-03-cql2-mpc.Rmd’ - -Error: Vignette re-building failed. -Execution halted - -* DONE -Status: 1 WARNING, 1 NOTE - - - - - -``` -# RVA - -
- -* Version: 0.0.5 -* GitHub: https://github.com/THERMOSTATS/RVA -* Source code: https://github.com/cran/RVA -* Date/Publication: 2021-11-01 21:40:02 UTC -* Number of recursive dependencies: 208 - -Run `revdepcheck::cloud_details(, "RVA")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/RVA/new/RVA.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘RVA/DESCRIPTION’ ... OK -* this is package ‘RVA’ version ‘0.0.5’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘clusterProfiler’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/RVA/old/RVA.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘RVA/DESCRIPTION’ ... OK -* this is package ‘RVA’ version ‘0.0.5’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘clusterProfiler’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# saeSim - -
- -* Version: 0.11.0 -* GitHub: https://github.com/wahani/saeSim -* Source code: https://github.com/cran/saeSim -* Date/Publication: 2022-02-07 16:40:02 UTC -* Number of recursive dependencies: 97 - -Run `revdepcheck::cloud_details(, "saeSim")` for more info - -
- -## In both - -* checking whether package ‘saeSim’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/saeSim/new/saeSim.Rcheck/00install.out’ for details. - ``` - -## Installation - -### Devel - -``` -* installing *source* package ‘saeSim’ ... -** package ‘saeSim’ 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 ‘sf’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart -Execution halted -ERROR: lazy loading failed for package ‘saeSim’ -* removing ‘/tmp/workdir/saeSim/new/saeSim.Rcheck/saeSim’ - - -``` -### CRAN - -``` -* installing *source* package ‘saeSim’ ... -** package ‘saeSim’ 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 ‘sf’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart -Execution halted -ERROR: lazy loading failed for package ‘saeSim’ -* removing ‘/tmp/workdir/saeSim/old/saeSim.Rcheck/saeSim’ - - -``` -# SAMtool - -
- -* Version: 1.5.1 -* GitHub: https://github.com/Blue-Matter/SAMtool -* Source code: https://github.com/cran/SAMtool -* Date/Publication: 2023-02-08 23:20:02 UTC -* Number of recursive dependencies: 178 - -Run `revdepcheck::cloud_details(, "SAMtool")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/SAMtool/new/SAMtool.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘SAMtool/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘SAMtool’ version ‘1.5.1’ -* package encoding: UTF-8 -* checking package namespace information ... OK -... -* checking line endings in C/C++/Fortran sources/headers ... OK -* checking line endings in Makefiles ... OK -* checking compilation flags in Makevars ... 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 -* DONE -Status: 2 NOTEs - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/SAMtool/old/SAMtool.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘SAMtool/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘SAMtool’ version ‘1.5.1’ -* package encoding: UTF-8 -* checking package namespace information ... OK -... -* checking line endings in C/C++/Fortran sources/headers ... OK -* checking line endings in Makefiles ... OK -* checking compilation flags in Makevars ... 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 -* DONE -Status: 2 NOTEs - - - - - -``` -# sandwichr - -
- -* Version: 1.0.3 -* GitHub: https://github.com/linyuehzzz/sandwich_spatial_interpolator -* Source code: https://github.com/cran/sandwichr -* Date/Publication: 2023-01-09 08:10:05 UTC -* Number of recursive dependencies: 143 - -Run `revdepcheck::cloud_details(, "sandwichr")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/sandwichr/new/sandwichr.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘sandwichr/DESCRIPTION’ ... OK -* this is package ‘sandwichr’ version ‘1.0.3’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Packages required but not available: 'sf', 'lwgeom' - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/sandwichr/old/sandwichr.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘sandwichr/DESCRIPTION’ ... OK -* this is package ‘sandwichr’ version ‘1.0.3’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Packages required but not available: 'sf', 'lwgeom' - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# scGate - -
- -* Version: NA -* GitHub: NA -* Source code: https://github.com/cran/scGate -* Number of recursive dependencies: 173 - -Run `revdepcheck::cloud_details(, "scGate")` for more info - -
- -## Error before installation - -### Devel - -``` - - - - - - -``` -### CRAN - -``` - - - - - - -``` -# SCpubr - -
- -* Version: 1.1.2 -* GitHub: https://github.com/enblacar/SCpubr -* Source code: https://github.com/cran/SCpubr -* Date/Publication: 2023-01-18 12:20:02 UTC -* Number of recursive dependencies: 290 - -Run `revdepcheck::cloud_details(, "SCpubr")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/SCpubr/new/SCpubr.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘SCpubr/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘SCpubr’ version ‘1.1.2’ -* package encoding: UTF-8 -* checking package namespace information ... 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: 1 WARNING, 2 NOTEs - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/SCpubr/old/SCpubr.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘SCpubr/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘SCpubr’ version ‘1.1.2’ -* package encoding: UTF-8 -* checking package namespace information ... 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: 1 WARNING, 2 NOTEs - - - - - -``` -# SDGdetector - -
- -* Version: 2.7.1 -* GitHub: NA -* Source code: https://github.com/cran/SDGdetector -* Date/Publication: 2023-02-22 20:20:06 UTC -* Number of recursive dependencies: 74 - -Run `revdepcheck::cloud_details(, "SDGdetector")` for more info - -
- -## In both - -* checking whether package ‘SDGdetector’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/SDGdetector/new/SDGdetector.Rcheck/00install.out’ for details. - ``` - -## Installation - -### Devel - -``` -* installing *source* package ‘SDGdetector’ ... -** package ‘SDGdetector’ 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 ‘sf’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart -Execution halted -ERROR: lazy loading failed for package ‘SDGdetector’ -* removing ‘/tmp/workdir/SDGdetector/new/SDGdetector.Rcheck/SDGdetector’ - - -``` -### CRAN - -``` -* installing *source* package ‘SDGdetector’ ... -** package ‘SDGdetector’ 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 ‘sf’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart -Execution halted -ERROR: lazy loading failed for package ‘SDGdetector’ -* removing ‘/tmp/workdir/SDGdetector/old/SDGdetector.Rcheck/SDGdetector’ - - -``` -# SDLfilter - -
- -* Version: 2.3.1 -* GitHub: https://github.com/TakahiroShimada/SDLfilter -* Source code: https://github.com/cran/SDLfilter -* Date/Publication: 2023-01-16 08:00:06 UTC -* Number of recursive dependencies: 96 - -Run `revdepcheck::cloud_details(, "SDLfilter")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/SDLfilter/new/SDLfilter.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘SDLfilter/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘SDLfilter’ version ‘2.3.1’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/SDLfilter/old/SDLfilter.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘SDLfilter/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘SDLfilter’ version ‘2.3.1’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# sdmApp - -
- -* Version: 0.0.2 -* GitHub: https://github.com/Abson-dev/sdmApp -* Source code: https://github.com/cran/sdmApp -* Date/Publication: 2021-07-07 08:30:02 UTC -* Number of recursive dependencies: 169 - -Run `revdepcheck::cloud_details(, "sdmApp")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/sdmApp/new/sdmApp.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘sdmApp/DESCRIPTION’ ... OK -* this is package ‘sdmApp’ version ‘0.0.2’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... NOTE -... -* 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 - ‘sdmApp.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: 2 NOTEs - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/sdmApp/old/sdmApp.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘sdmApp/DESCRIPTION’ ... OK -* this is package ‘sdmApp’ version ‘0.0.2’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... NOTE -... -* 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 - ‘sdmApp.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: 2 NOTEs - - - - - -``` -# sf - -
- -* Version: 1.0-10 -* GitHub: https://github.com/r-spatial/sf -* Source code: https://github.com/cran/sf -* Date/Publication: 2023-03-12 16:10:02 UTC -* Number of recursive dependencies: 157 - -Run `revdepcheck::cloud_details(, "sf")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/sf/new/sf.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘sf/DESCRIPTION’ ... OK -* this is package ‘sf’ version ‘1.0-10’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... NOTE -... -* 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 ‘sf’ can be installed ... ERROR -Installation failed. -See ‘/tmp/workdir/sf/new/sf.Rcheck/00install.out’ for details. -* DONE -Status: 1 ERROR, 1 NOTE - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/sf/old/sf.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘sf/DESCRIPTION’ ... OK -* this is package ‘sf’ version ‘1.0-10’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... NOTE -... -* 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 ‘sf’ can be installed ... ERROR -Installation failed. -See ‘/tmp/workdir/sf/old/sf.Rcheck/00install.out’ for details. -* DONE -Status: 1 ERROR, 1 NOTE - - - - - -``` -# sfdep - -
- -* Version: 0.2.3 -* GitHub: https://github.com/josiahparry/sfdep -* Source code: https://github.com/cran/sfdep -* Date/Publication: 2023-01-11 06:30:02 UTC -* Number of recursive dependencies: 99 - -Run `revdepcheck::cloud_details(, "sfdep")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/sfdep/new/sfdep.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘sfdep/DESCRIPTION’ ... OK -* this is package ‘sfdep’ version ‘0.2.3’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/sfdep/old/sfdep.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘sfdep/DESCRIPTION’ ... OK -* this is package ‘sfdep’ version ‘0.2.3’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# sfnetworks - -
- -* Version: 0.6.2 -* GitHub: https://github.com/luukvdmeer/sfnetworks -* Source code: https://github.com/cran/sfnetworks -* Date/Publication: 2023-02-26 19:00:02 UTC -* Number of recursive dependencies: 105 - -Run `revdepcheck::cloud_details(, "sfnetworks")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/sfnetworks/new/sfnetworks.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘sfnetworks/DESCRIPTION’ ... OK -* this is package ‘sfnetworks’ version ‘0.6.2’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Packages required but not available: 'lwgeom', 'sf' - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/sfnetworks/old/sfnetworks.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘sfnetworks/DESCRIPTION’ ... OK -* this is package ‘sfnetworks’ version ‘0.6.2’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Packages required but not available: 'lwgeom', 'sf' - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# sftime - -
- -* Version: 0.2-0 -* GitHub: NA -* Source code: https://github.com/cran/sftime -* Date/Publication: 2022-03-17 08:50:01 UTC -* Number of recursive dependencies: 79 - -Run `revdepcheck::cloud_details(, "sftime")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/sftime/new/sftime.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘sftime/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘sftime’ version ‘0.2-0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/sftime/old/sftime.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘sftime/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘sftime’ version ‘0.2-0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# ShellChron - -
- -* Version: 0.4.0 -* GitHub: https://github.com/nielsjdewinter/ShellChron -* Source code: https://github.com/cran/ShellChron -* Date/Publication: 2021-07-05 12:40:02 UTC -* Number of recursive dependencies: 118 - -Run `revdepcheck::cloud_details(, "ShellChron")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/ShellChron/new/ShellChron.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘ShellChron/DESCRIPTION’ ... OK -* this is package ‘ShellChron’ version ‘0.4.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘rtop’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/ShellChron/old/ShellChron.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘ShellChron/DESCRIPTION’ ... OK -* this is package ‘ShellChron’ version ‘0.4.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘rtop’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# shinyHugePlot - -
- -* Version: NA -* GitHub: NA -* Source code: https://github.com/cran/shinyHugePlot -* Number of recursive dependencies: 97 - -Run `revdepcheck::cloud_details(, "shinyHugePlot")` for more info - -
- -## Error before installation - -### Devel - -``` - - - - - - -``` -### CRAN - -``` - - - - - - -``` -# simodels - -
- -* Version: 0.0.5 -* GitHub: https://github.com/robinlovelace/simodels -* Source code: https://github.com/cran/simodels -* Date/Publication: 2022-08-31 21:10:02 UTC -* Number of recursive dependencies: 97 - -Run `revdepcheck::cloud_details(, "simodels")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/simodels/new/simodels.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘simodels/DESCRIPTION’ ... OK -* this is package ‘simodels’ version ‘0.0.5’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/simodels/old/simodels.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘simodels/DESCRIPTION’ ... OK -* this is package ‘simodels’ version ‘0.0.5’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# simplevis - -
- -* Version: 7.0.0 -* GitHub: https://github.com/StatisticsNZ/simplevis -* Source code: https://github.com/cran/simplevis -* Date/Publication: 2023-01-29 20:00:02 UTC -* Number of recursive dependencies: 122 - -Run `revdepcheck::cloud_details(, "simplevis")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/simplevis/new/simplevis.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘simplevis/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘simplevis’ version ‘7.0.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/simplevis/old/simplevis.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘simplevis/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘simplevis’ version ‘7.0.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# sits - -
- -* Version: 1.2.0 -* GitHub: https://github.com/e-sensing/sits -* Source code: https://github.com/cran/sits -* Date/Publication: 2022-11-16 19:20:07 UTC -* Number of recursive dependencies: 204 - -Run `revdepcheck::cloud_details(, "sits")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/sits/new/sits.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘sits/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘sits’ version ‘1.2.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/sits/old/sits.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘sits/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘sits’ version ‘1.2.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# sjPlot - -
- -* Version: 2.8.13 -* GitHub: https://github.com/strengejacke/sjPlot -* Source code: https://github.com/cran/sjPlot -* Date/Publication: 2023-03-13 17:10:10 UTC -* Number of recursive dependencies: 186 - -Run `revdepcheck::cloud_details(, "sjPlot")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/sjPlot/new/sjPlot.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘sjPlot/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘sjPlot’ version ‘2.8.13’ -* package encoding: UTF-8 -* checking package namespace information ... 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 -* checking re-building of vignette outputs ... OK -* DONE -Status: 1 NOTE - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/sjPlot/old/sjPlot.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘sjPlot/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘sjPlot’ version ‘2.8.13’ -* package encoding: UTF-8 -* checking package namespace information ... 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 -* checking re-building of vignette outputs ... OK -* DONE -Status: 1 NOTE - - - - - -``` -# sjstats - -
- -* Version: 0.18.2 -* GitHub: https://github.com/strengejacke/sjstats -* Source code: https://github.com/cran/sjstats -* Date/Publication: 2022-11-19 22:10:02 UTC -* Number of recursive dependencies: 166 - -Run `revdepcheck::cloud_details(, "sjstats")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/sjstats/new/sjstats.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘sjstats/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘sjstats’ version ‘0.18.2’ -* package encoding: UTF-8 -* checking package namespace information ... 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 -* checking for unstated dependencies in ‘tests’ ... OK -* checking tests ... OK - Running ‘testthat.R’ -* DONE -Status: 2 NOTEs - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/sjstats/old/sjstats.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘sjstats/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘sjstats’ version ‘0.18.2’ -* package encoding: UTF-8 -* checking package namespace information ... 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 -* checking for unstated dependencies in ‘tests’ ... OK -* checking tests ... OK - Running ‘testthat.R’ -* DONE -Status: 2 NOTEs - - - - - -``` -# sknifedatar - -
- -* Version: 0.1.2 -* GitHub: https://github.com/rafzamb/sknifedatar -* Source code: https://github.com/cran/sknifedatar -* Date/Publication: 2021-06-01 08:00:02 UTC -* Number of recursive dependencies: 180 - -Run `revdepcheck::cloud_details(, "sknifedatar")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/sknifedatar/new/sknifedatar.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘sknifedatar/DESCRIPTION’ ... OK -* this is package ‘sknifedatar’ version ‘0.1.2’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... 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 ‘spelling.R’ -* DONE -Status: OK - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/sknifedatar/old/sknifedatar.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘sknifedatar/DESCRIPTION’ ... OK -* this is package ‘sknifedatar’ version ‘0.1.2’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... 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 ‘spelling.R’ -* DONE -Status: OK - - - - - -``` -# slendr - -
- -* Version: 0.5.1 -* GitHub: https://github.com/bodkan/slendr -* Source code: https://github.com/cran/slendr -* Date/Publication: 2023-03-09 19:40:02 UTC -* Number of recursive dependencies: 129 - -Run `revdepcheck::cloud_details(, "slendr")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/slendr/new/slendr.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘slendr/DESCRIPTION’ ... OK -* this is package ‘slendr’ version ‘0.5.1’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/slendr/old/slendr.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘slendr/DESCRIPTION’ ... OK -* this is package ‘slendr’ version ‘0.5.1’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# sociome - -
- -* Version: 2.1.0 -* GitHub: https://github.com/NikKrieger/sociome -* Source code: https://github.com/cran/sociome -* Date/Publication: 2021-10-21 09:10:01 UTC -* Number of recursive dependencies: 97 - -Run `revdepcheck::cloud_details(, "sociome")` for more info - -
- -## In both - -* checking whether package ‘sociome’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/sociome/new/sociome.Rcheck/00install.out’ for details. - ``` - -* checking package dependencies ... NOTE - ``` - Package suggested but not available for checking: ‘sf’ - ``` - -## Installation - -### Devel - -``` -* installing *source* package ‘sociome’ ... -** package ‘sociome’ 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 ‘sf’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart -Execution halted -ERROR: lazy loading failed for package ‘sociome’ -* removing ‘/tmp/workdir/sociome/new/sociome.Rcheck/sociome’ - - -``` -### CRAN - -``` -* installing *source* package ‘sociome’ ... -** package ‘sociome’ 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 ‘sf’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart -Execution halted -ERROR: lazy loading failed for package ‘sociome’ -* removing ‘/tmp/workdir/sociome/old/sociome.Rcheck/sociome’ - - -``` -# SpaDES.tools - -
- -* Version: 1.0.1 -* GitHub: https://github.com/PredictiveEcology/SpaDES.tools -* Source code: https://github.com/cran/SpaDES.tools -* Date/Publication: 2023-01-05 15:20:19 UTC -* Number of recursive dependencies: 117 - -Run `revdepcheck::cloud_details(, "SpaDES.tools")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/SpaDES.tools/new/SpaDES.tools.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘SpaDES.tools/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘SpaDES.tools’ version ‘1.0.1’ -* package encoding: UTF-8 -* checking package namespace information ... 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 -* checking for unstated dependencies in ‘tests’ ... OK -* checking tests ... OK - Running ‘test-all.R’ -* DONE -Status: 1 NOTE - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/SpaDES.tools/old/SpaDES.tools.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘SpaDES.tools/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘SpaDES.tools’ version ‘1.0.1’ -* package encoding: UTF-8 -* checking package namespace information ... 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 -* checking for unstated dependencies in ‘tests’ ... OK -* checking tests ... OK - Running ‘test-all.R’ -* DONE -Status: 1 NOTE - - - - - -``` -# SPARTAAS - -
- -* Version: 1.1.0 -* GitHub: NA -* Source code: https://github.com/cran/SPARTAAS -* Date/Publication: 2021-10-22 14:30:02 UTC -* Number of recursive dependencies: 184 - -Run `revdepcheck::cloud_details(, "SPARTAAS")` for more info - -
- -## In both - -* checking whether package ‘SPARTAAS’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/SPARTAAS/new/SPARTAAS.Rcheck/00install.out’ for details. - ``` - -## Installation - -### Devel - -``` -* installing *source* package ‘SPARTAAS’ ... -** package ‘SPARTAAS’ 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 ‘sf’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart -Execution halted -ERROR: lazy loading failed for package ‘SPARTAAS’ -* removing ‘/tmp/workdir/SPARTAAS/new/SPARTAAS.Rcheck/SPARTAAS’ - - -``` -### CRAN - -``` -* installing *source* package ‘SPARTAAS’ ... -** package ‘SPARTAAS’ 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 ‘sf’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart -Execution halted -ERROR: lazy loading failed for package ‘SPARTAAS’ -* removing ‘/tmp/workdir/SPARTAAS/old/SPARTAAS.Rcheck/SPARTAAS’ - - -``` -# spatgeom - -
- -* Version: 0.2.0 -* GitHub: https://github.com/maikol-solis/spatgeom -* Source code: https://github.com/cran/spatgeom -* Date/Publication: 2023-02-14 19:00:02 UTC -* Number of recursive dependencies: 81 - -Run `revdepcheck::cloud_details(, "spatgeom")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/spatgeom/new/spatgeom.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘spatgeom/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘spatgeom’ version ‘0.2.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Packages required but not available: 'sf', 'lwgeom' - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/spatgeom/old/spatgeom.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘spatgeom/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘spatgeom’ version ‘0.2.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Packages required but not available: 'sf', 'lwgeom' - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# SpatialEpi - -
- -* Version: 1.2.8 -* GitHub: https://github.com/rudeboybert/SpatialEpi -* Source code: https://github.com/cran/SpatialEpi -* Date/Publication: 2023-02-22 00:50:04 UTC -* Number of recursive dependencies: 86 - -Run `revdepcheck::cloud_details(, "SpatialEpi")` for more info - -
- -## In both - -* checking whether package ‘SpatialEpi’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/SpatialEpi/new/SpatialEpi.Rcheck/00install.out’ for details. - ``` - -## Installation - -### Devel - -``` -* installing *source* package ‘SpatialEpi’ ... -** package ‘SpatialEpi’ successfully unpacked and MD5 sums checked -** using staged installation -** libs -g++ -std=gnu++14 -I"/opt/R/4.1.1/lib/R/include" -DNDEBUG -I'/opt/R/4.1.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.1.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o -g++ -std=gnu++14 -I"/opt/R/4.1.1/lib/R/include" -DNDEBUG -I'/opt/R/4.1.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.1.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c bayes_cluster.cpp -o bayes_cluster.o -g++ -std=gnu++14 -I"/opt/R/4.1.1/lib/R/include" -DNDEBUG -I'/opt/R/4.1.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.1.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c cluster_detection.cpp -o cluster_detection.o -g++ -std=gnu++14 -shared -L/opt/R/4.1.1/lib/R/lib -L/usr/local/lib -o SpatialEpi.so RcppExports.o bayes_cluster.o cluster_detection.o -L/opt/R/4.1.1/lib/R/lib -lR -installing to /tmp/workdir/SpatialEpi/new/SpatialEpi.Rcheck/00LOCK-SpatialEpi/00new/SpatialEpi/libs -** 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 ‘sf’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart -Execution halted -ERROR: lazy loading failed for package ‘SpatialEpi’ -* removing ‘/tmp/workdir/SpatialEpi/new/SpatialEpi.Rcheck/SpatialEpi’ - - -``` -### CRAN - -``` -* installing *source* package ‘SpatialEpi’ ... -** package ‘SpatialEpi’ successfully unpacked and MD5 sums checked -** using staged installation -** libs -g++ -std=gnu++14 -I"/opt/R/4.1.1/lib/R/include" -DNDEBUG -I'/opt/R/4.1.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.1.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c RcppExports.cpp -o RcppExports.o -g++ -std=gnu++14 -I"/opt/R/4.1.1/lib/R/include" -DNDEBUG -I'/opt/R/4.1.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.1.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c bayes_cluster.cpp -o bayes_cluster.o -g++ -std=gnu++14 -I"/opt/R/4.1.1/lib/R/include" -DNDEBUG -I'/opt/R/4.1.1/lib/R/site-library/Rcpp/include' -I'/opt/R/4.1.1/lib/R/site-library/RcppArmadillo/include' -I/usr/local/include -fpic -g -O2 -c cluster_detection.cpp -o cluster_detection.o -g++ -std=gnu++14 -shared -L/opt/R/4.1.1/lib/R/lib -L/usr/local/lib -o SpatialEpi.so RcppExports.o bayes_cluster.o cluster_detection.o -L/opt/R/4.1.1/lib/R/lib -lR -installing to /tmp/workdir/SpatialEpi/old/SpatialEpi.Rcheck/00LOCK-SpatialEpi/00new/SpatialEpi/libs -** 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 ‘sf’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart -Execution halted -ERROR: lazy loading failed for package ‘SpatialEpi’ -* removing ‘/tmp/workdir/SpatialEpi/old/SpatialEpi.Rcheck/SpatialEpi’ - - -``` -# SpatialKDE - -
- -* Version: 0.8.2 -* GitHub: https://github.com/JanCaha/SpatialKDE -* Source code: https://github.com/cran/SpatialKDE -* Date/Publication: 2023-02-18 15:10:02 UTC -* Number of recursive dependencies: 112 - -Run `revdepcheck::cloud_details(, "SpatialKDE")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/SpatialKDE/new/SpatialKDE.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘SpatialKDE/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘SpatialKDE’ version ‘0.8.2’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/SpatialKDE/old/SpatialKDE.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘SpatialKDE/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘SpatialKDE’ version ‘0.8.2’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# spatialrisk - -
- -* Version: 0.7.0 -* GitHub: https://github.com/mharinga/spatialrisk -* Source code: https://github.com/cran/spatialrisk -* Date/Publication: 2021-11-10 15:30:02 UTC -* Number of recursive dependencies: 134 - -Run `revdepcheck::cloud_details(, "spatialrisk")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/spatialrisk/new/spatialrisk.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘spatialrisk/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘spatialrisk’ version ‘0.7.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/spatialrisk/old/spatialrisk.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘spatialrisk/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘spatialrisk’ version ‘0.7.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# spatialsample - -
- -* Version: 0.3.0 -* GitHub: https://github.com/tidymodels/spatialsample -* Source code: https://github.com/cran/spatialsample -* Date/Publication: 2023-01-17 16:10:02 UTC -* Number of recursive dependencies: 106 - -Run `revdepcheck::cloud_details(, "spatialsample")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/spatialsample/new/spatialsample.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘spatialsample/DESCRIPTION’ ... OK -* this is package ‘spatialsample’ version ‘0.3.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -Package suggested but not available for checking: ‘lwgeom’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/spatialsample/old/spatialsample.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘spatialsample/DESCRIPTION’ ... OK -* this is package ‘spatialsample’ version ‘0.3.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -Package suggested but not available for checking: ‘lwgeom’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# spDates - -
- -* Version: 1.1 -* GitHub: NA -* Source code: https://github.com/cran/spDates -* Date/Publication: 2022-10-09 10:30:02 UTC -* Number of recursive dependencies: 82 - -Run `revdepcheck::cloud_details(, "spDates")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/spDates/new/spDates.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘spDates/DESCRIPTION’ ... OK -* this is package ‘spDates’ version ‘1.1’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... 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 ‘spDates’ can be installed ... ERROR -Installation failed. -See ‘/tmp/workdir/spDates/new/spDates.Rcheck/00install.out’ for details. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/spDates/old/spDates.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘spDates/DESCRIPTION’ ... OK -* this is package ‘spDates’ version ‘1.1’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... 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 ‘spDates’ can be installed ... ERROR -Installation failed. -See ‘/tmp/workdir/spDates/old/spDates.Rcheck/00install.out’ for details. -* DONE -Status: 1 ERROR - - - - - -``` -# spectacles - -
- -* Version: 0.5-3 -* GitHub: https://github.com/pierreroudier/spectacles -* Source code: https://github.com/cran/spectacles -* Date/Publication: 2021-01-11 08:00:02 UTC -* Number of recursive dependencies: 140 - -Run `revdepcheck::cloud_details(, "spectacles")` for more info - -
- -## In both - -* checking whether package ‘spectacles’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/spectacles/new/spectacles.Rcheck/00install.out’ for details. - ``` - -## Installation - -### Devel - -``` -* installing *source* package ‘spectacles’ ... -** package ‘spectacles’ 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 ‘sf’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart -Execution halted -ERROR: lazy loading failed for package ‘spectacles’ -* removing ‘/tmp/workdir/spectacles/new/spectacles.Rcheck/spectacles’ - - -``` -### CRAN - -``` -* installing *source* package ‘spectacles’ ... -** package ‘spectacles’ 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 ‘sf’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart -Execution halted -ERROR: lazy loading failed for package ‘spectacles’ -* removing ‘/tmp/workdir/spectacles/old/spectacles.Rcheck/spectacles’ - - -``` -# spnaf - -
- -* Version: 0.2.1 -* GitHub: NA -* Source code: https://github.com/cran/spnaf -* Date/Publication: 2022-08-25 08:20:02 UTC -* Number of recursive dependencies: 100 - -Run `revdepcheck::cloud_details(, "spnaf")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/spnaf/new/spnaf.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘spnaf/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘spnaf’ version ‘0.2.1’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/spnaf/old/spnaf.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘spnaf/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘spnaf’ version ‘0.2.1’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# spNetwork - -
- -* Version: 0.4.3.6 -* GitHub: https://github.com/JeremyGelb/spNetwork -* Source code: https://github.com/cran/spNetwork -* Date/Publication: 2022-11-11 08:10:02 UTC -* Number of recursive dependencies: 149 - -Run `revdepcheck::cloud_details(, "spNetwork")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/spNetwork/new/spNetwork.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘spNetwork/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘spNetwork’ version ‘0.4.3.6’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/spNetwork/old/spNetwork.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘spNetwork/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘spNetwork’ version ‘0.4.3.6’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# spqdep - -
- -* Version: 0.1.2 -* GitHub: NA -* Source code: https://github.com/cran/spqdep -* Date/Publication: 2022-03-28 16:20:02 UTC -* Number of recursive dependencies: 102 - -Run `revdepcheck::cloud_details(, "spqdep")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/spqdep/new/spqdep.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘spqdep/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘spqdep’ version ‘0.1.2’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Packages required but not available: 'sf', 'lwgeom' - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/spqdep/old/spqdep.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘spqdep/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘spqdep’ version ‘0.1.2’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Packages required but not available: 'sf', 'lwgeom' - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# spup - -
- -* Version: 1.3-2 -* GitHub: NA -* Source code: https://github.com/cran/spup -* Date/Publication: 2020-04-30 22:20:06 UTC -* Number of recursive dependencies: 99 - -Run `revdepcheck::cloud_details(, "spup")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/spup/new/spup.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘spup/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘spup’ version ‘1.3-2’ -* package encoding: UTF-8 -* checking package namespace information ... OK -... -* checking for unstated dependencies in vignettes ... OK -* checking package vignettes in ‘inst/doc’ ... OK -* checking running R code from vignettes ... NONE - ‘CN_v2.Rmd’ using ‘UTF-8’... OK - ‘DEM_v3.Rmd’ using ‘UTF-8’... OK - ‘ExternalModel_v2.Rmd’ using ‘UTF-8’... OK - ‘Rotterdam.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: 1 NOTE - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/spup/old/spup.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘spup/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘spup’ version ‘1.3-2’ -* package encoding: UTF-8 -* checking package namespace information ... OK -... -* checking for unstated dependencies in vignettes ... OK -* checking package vignettes in ‘inst/doc’ ... OK -* checking running R code from vignettes ... NONE - ‘CN_v2.Rmd’ using ‘UTF-8’... OK - ‘DEM_v3.Rmd’ using ‘UTF-8’... OK - ‘ExternalModel_v2.Rmd’ using ‘UTF-8’... OK - ‘Rotterdam.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: 1 NOTE - - - - - -``` -# stars - -
- -* Version: 0.6-0 -* GitHub: https://github.com/r-spatial/stars -* Source code: https://github.com/cran/stars -* Date/Publication: 2022-11-21 13:10:02 UTC -* Number of recursive dependencies: 153 - -Run `revdepcheck::cloud_details(, "stars")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/stars/new/stars.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘stars/DESCRIPTION’ ... OK -* this is package ‘stars’ version ‘0.6-0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Packages required but not available: 'sf', 'lwgeom' - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/stars/old/stars.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘stars/DESCRIPTION’ ... OK -* this is package ‘stars’ version ‘0.6-0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Packages required but not available: 'sf', 'lwgeom' - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# starsTileServer - -
- -* Version: 0.1.1 -* GitHub: NA -* Source code: https://github.com/cran/starsTileServer -* Date/Publication: 2022-08-22 21:50:02 UTC -* Number of recursive dependencies: 126 - -Run `revdepcheck::cloud_details(, "starsTileServer")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/starsTileServer/new/starsTileServer.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘starsTileServer/DESCRIPTION’ ... OK -* this is package ‘starsTileServer’ version ‘0.1.1’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/starsTileServer/old/starsTileServer.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘starsTileServer/DESCRIPTION’ ... OK -* this is package ‘starsTileServer’ version ‘0.1.1’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# stats19 - -
- -* Version: 2.0.1 -* GitHub: https://github.com/ropensci/stats19 -* Source code: https://github.com/cran/stats19 -* Date/Publication: 2022-11-17 12:00:06 UTC -* Number of recursive dependencies: 164 - -Run `revdepcheck::cloud_details(, "stats19")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/stats19/new/stats19.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘stats19/DESCRIPTION’ ... OK -* this is package ‘stats19’ version ‘2.0.1’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/stats19/old/stats19.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘stats19/DESCRIPTION’ ... OK -* this is package ‘stats19’ version ‘2.0.1’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# statsExpressions - -
- -* Version: 1.5.0 -* GitHub: https://github.com/IndrajeetPatil/statsExpressions -* Source code: https://github.com/cran/statsExpressions -* Date/Publication: 2023-02-19 14:30:02 UTC -* Number of recursive dependencies: 152 - -Run `revdepcheck::cloud_details(, "statsExpressions")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/statsExpressions/new/statsExpressions.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘statsExpressions/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘statsExpressions’ version ‘1.5.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -... - 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 ... NONE - ‘statsExpressions.Rmd’ using ‘UTF-8’... OK - ‘stats_details.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: 1 ERROR, 1 NOTE - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/statsExpressions/old/statsExpressions.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘statsExpressions/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘statsExpressions’ version ‘1.5.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -... - 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 ... NONE - ‘statsExpressions.Rmd’ using ‘UTF-8’... OK - ‘stats_details.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: 1 ERROR, 1 NOTE - - - - - -``` -# stortingscrape - -
- -* Version: NA -* GitHub: NA -* Source code: https://github.com/cran/stortingscrape -* Number of recursive dependencies: 61 - -Run `revdepcheck::cloud_details(, "stortingscrape")` for more info - -
- -## Error before installation - -### Devel - -``` - - - - - - -``` -### CRAN - -``` - - - - - - -``` -# stplanr - -
- -* Version: 1.0.2 -* GitHub: https://github.com/ropensci/stplanr -* Source code: https://github.com/cran/stplanr -* Date/Publication: 2022-11-08 12:40:02 UTC -* Number of recursive dependencies: 166 - -Run `revdepcheck::cloud_details(, "stplanr")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/stplanr/new/stplanr.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘stplanr/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘stplanr’ version ‘1.0.2’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Packages required but not available: 'lwgeom', 'sf' - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/stplanr/old/stplanr.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘stplanr/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘stplanr’ version ‘1.0.2’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Packages required but not available: 'lwgeom', 'sf' - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# stppSim - -
- -* Version: 1.2.7 -* GitHub: https://github.com/Manalytics/stppSim -* Source code: https://github.com/cran/stppSim -* Date/Publication: 2022-08-11 10:30:02 UTC -* Number of recursive dependencies: 128 - -Run `revdepcheck::cloud_details(, "stppSim")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/stppSim/new/stppSim.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘stppSim/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘stppSim’ version ‘1.2.7’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/stppSim/old/stppSim.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘stppSim/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘stppSim’ version ‘1.2.7’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# stxplore - -
- -* Version: 0.1.0 -* GitHub: NA -* Source code: https://github.com/cran/stxplore -* Date/Publication: 2023-02-03 10:10:02 UTC -* Number of recursive dependencies: 102 - -Run `revdepcheck::cloud_details(, "stxplore")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/stxplore/new/stxplore.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘stxplore/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘stxplore’ version ‘0.1.0’ -* package encoding: UTF-8 -* checking package namespace information ... 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 ‘stxplore’ can be installed ... ERROR -Installation failed. -See ‘/tmp/workdir/stxplore/new/stxplore.Rcheck/00install.out’ for details. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/stxplore/old/stxplore.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘stxplore/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘stxplore’ version ‘0.1.0’ -* package encoding: UTF-8 -* checking package namespace information ... 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 ‘stxplore’ can be installed ... ERROR -Installation failed. -See ‘/tmp/workdir/stxplore/old/stxplore.Rcheck/00install.out’ for details. -* DONE -Status: 1 ERROR - - - - - -``` -# SUNGEO - -
- -* Version: 0.2.292 -* GitHub: NA -* Source code: https://github.com/cran/SUNGEO -* Date/Publication: 2022-08-18 14:20:02 UTC -* Number of recursive dependencies: 109 - -Run `revdepcheck::cloud_details(, "SUNGEO")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/SUNGEO/new/SUNGEO.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘SUNGEO/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘SUNGEO’ version ‘0.2.292’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/SUNGEO/old/SUNGEO.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘SUNGEO/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘SUNGEO’ version ‘0.2.292’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# swfscAirDAS - -
- -* Version: 0.2.3 -* GitHub: https://github.com/smwoodman/swfscAirDAS -* Source code: https://github.com/cran/swfscAirDAS -* Date/Publication: 2022-06-02 03:00:02 UTC -* Number of recursive dependencies: 105 - -Run `revdepcheck::cloud_details(, "swfscAirDAS")` for more info - -
- -## In both - -* checking whether package ‘swfscAirDAS’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/swfscAirDAS/new/swfscAirDAS.Rcheck/00install.out’ for details. - ``` - -## Installation - -### Devel - -``` -* installing *source* package ‘swfscAirDAS’ ... -** package ‘swfscAirDAS’ successfully unpacked and MD5 sums checked -** using staged installation -** R -** inst -** byte-compile and prepare package for lazy loading -Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - there is no package called ‘sf’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart -Execution halted -ERROR: lazy loading failed for package ‘swfscAirDAS’ -* removing ‘/tmp/workdir/swfscAirDAS/new/swfscAirDAS.Rcheck/swfscAirDAS’ - - -``` -### CRAN - -``` -* installing *source* package ‘swfscAirDAS’ ... -** package ‘swfscAirDAS’ successfully unpacked and MD5 sums checked -** using staged installation -** R -** inst -** byte-compile and prepare package for lazy loading -Error in loadNamespace(j <- i[[1L]], c(lib.loc, .libPaths()), versionCheck = vI[[j]]) : - there is no package called ‘sf’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart -Execution halted -ERROR: lazy loading failed for package ‘swfscAirDAS’ -* removing ‘/tmp/workdir/swfscAirDAS/old/swfscAirDAS.Rcheck/swfscAirDAS’ - - -``` -# SWTools - -
- -* Version: 0.2.4 -* GitHub: https://github.com/matt-s-gibbs/swtools -* Source code: https://github.com/cran/SWTools -* Date/Publication: 2022-07-04 06:20:02 UTC -* Number of recursive dependencies: 110 +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/CytoML +* Number of recursive dependencies: 106 -Run `revdepcheck::cloud_details(, "SWTools")` for more info +Run `revdepcheck::cloud_details(, "CytoML")` for more info
@@ -15271,23 +506,7 @@ Run `revdepcheck::cloud_details(, "SWTools")` for more info ### Devel ``` -* using log directory ‘/tmp/workdir/SWTools/new/SWTools.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘SWTools/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘SWTools’ version ‘0.2.4’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR @@ -15297,39 +516,23 @@ Status: 1 ERROR ### CRAN ``` -* using log directory ‘/tmp/workdir/SWTools/old/SWTools.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘SWTools/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘SWTools’ version ‘0.2.4’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR ``` -# tame +# datastructures
* Version: NA * GitHub: NA -* Source code: https://github.com/cran/tame -* Number of recursive dependencies: 65 +* Source code: https://github.com/cran/datastructures +* Number of recursive dependencies: 62 -Run `revdepcheck::cloud_details(, "tame")` for more info +Run `revdepcheck::cloud_details(, "datastructures")` for more info
@@ -15355,17 +558,16 @@ Run `revdepcheck::cloud_details(, "tame")` for more info ``` -# telemac +# DeLorean
-* Version: 0.1.1 -* GitHub: https://github.com/tpilz/telemac -* Source code: https://github.com/cran/telemac -* Date/Publication: 2022-02-07 15:50:02 UTC -* Number of recursive dependencies: 147 +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/DeLorean +* Number of recursive dependencies: 121 -Run `revdepcheck::cloud_details(, "telemac")` for more info +Run `revdepcheck::cloud_details(, "DeLorean")` for more info
@@ -15374,23 +576,7 @@ Run `revdepcheck::cloud_details(, "telemac")` for more info ### Devel ``` -* using log directory ‘/tmp/workdir/telemac/new/telemac.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘telemac/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘telemac’ version ‘0.1.1’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR @@ -15400,116 +586,23 @@ Status: 1 ERROR ### CRAN ``` -* using log directory ‘/tmp/workdir/telemac/old/telemac.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘telemac/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘telemac’ version ‘0.1.1’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR - - - - - -``` -# tidybayes - -
- -* Version: 3.0.4 -* GitHub: https://github.com/mjskay/tidybayes -* Source code: https://github.com/cran/tidybayes -* Date/Publication: 2023-03-14 04:30:02 UTC -* Number of recursive dependencies: 200 - -Run `revdepcheck::cloud_details(, "tidybayes")` for more info - -
- -## Error before installation - -### Devel - -``` -* using log directory ‘/tmp/workdir/tidybayes/new/tidybayes.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘tidybayes/DESCRIPTION’ ... OK -* this is package ‘tidybayes’ version ‘3.0.4’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... NOTE -... -* checking package vignettes in ‘inst/doc’ ... OK -* checking running R code from vignettes ... NONE - ‘tidy-brms.Rmd’ using ‘UTF-8’... OK - ‘tidy-posterior.Rmd’ using ‘UTF-8’... OK - ‘tidy-rstanarm.Rmd’ using ‘UTF-8’... OK - ‘tidybayes-residuals.Rmd’ using ‘UTF-8’... OK - ‘tidybayes.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: 2 NOTEs - - - - - -``` -### CRAN -``` -* using log directory ‘/tmp/workdir/tidybayes/old/tidybayes.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘tidybayes/DESCRIPTION’ ... OK -* this is package ‘tidybayes’ version ‘3.0.4’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... NOTE -... -* checking package vignettes in ‘inst/doc’ ... OK -* checking running R code from vignettes ... NONE - ‘tidy-brms.Rmd’ using ‘UTF-8’... OK - ‘tidy-posterior.Rmd’ using ‘UTF-8’... OK - ‘tidy-rstanarm.Rmd’ using ‘UTF-8’... OK - ‘tidybayes-residuals.Rmd’ using ‘UTF-8’... OK - ‘tidybayes.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: 2 NOTEs ``` -# tidyposterior +# DepecheR
-* Version: 1.0.0 -* GitHub: https://github.com/tidymodels/tidyposterior -* Source code: https://github.com/cran/tidyposterior -* Date/Publication: 2022-06-23 20:20:02 UTC -* Number of recursive dependencies: 170 +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/DepecheR +* Number of recursive dependencies: 117 -Run `revdepcheck::cloud_details(, "tidyposterior")` for more info +Run `revdepcheck::cloud_details(, "DepecheR")` for more info
@@ -15518,22 +611,7 @@ Run `revdepcheck::cloud_details(, "tidyposterior")` for more info ### Devel ``` -* using log directory ‘/tmp/workdir/tidyposterior/new/tidyposterior.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘tidyposterior/DESCRIPTION’ ... OK -* this is package ‘tidyposterior’ version ‘1.0.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘rstanarm’ -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR @@ -15543,39 +621,23 @@ Status: 1 ERROR ### CRAN ``` -* using log directory ‘/tmp/workdir/tidyposterior/old/tidyposterior.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘tidyposterior/DESCRIPTION’ ... OK -* this is package ‘tidyposterior’ version ‘1.0.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘rstanarm’ -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR ``` -# tidySEM +# destiny
-* Version: 0.2.3 -* GitHub: https://github.com/cjvanlissa/tidySEM -* Source code: https://github.com/cran/tidySEM -* Date/Publication: 2022-04-14 17:50:02 UTC -* Number of recursive dependencies: 171 +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/destiny +* Number of recursive dependencies: 243 -Run `revdepcheck::cloud_details(, "tidySEM")` for more info +Run `revdepcheck::cloud_details(, "destiny")` for more info
@@ -15584,25 +646,7 @@ Run `revdepcheck::cloud_details(, "tidySEM")` for more info ### Devel ``` -* using log directory ‘/tmp/workdir/tidySEM/new/tidySEM.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘tidySEM/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘tidySEM’ version ‘0.2.3’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘blavaan’ - -Package suggested but not available for checking: ‘umx’ -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR @@ -15612,41 +656,23 @@ Status: 1 ERROR ### CRAN ``` -* using log directory ‘/tmp/workdir/tidySEM/old/tidySEM.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘tidySEM/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘tidySEM’ version ‘0.2.3’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘blavaan’ - -Package suggested but not available for checking: ‘umx’ -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR ``` -# tidytags +# DiffBind
* Version: NA * GitHub: NA -* Source code: https://github.com/cran/tidytags -* Number of recursive dependencies: 122 +* Source code: https://github.com/cran/DiffBind +* Number of recursive dependencies: 159 -Run `revdepcheck::cloud_details(, "tidytags")` for more info +Run `revdepcheck::cloud_details(, "DiffBind")` for more info
@@ -15672,17 +698,16 @@ Run `revdepcheck::cloud_details(, "tidytags")` for more info ``` -# tilemaps +# diffman
-* 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: 73 +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/diffman +* Number of recursive dependencies: 126 -Run `revdepcheck::cloud_details(, "tilemaps")` for more info +Run `revdepcheck::cloud_details(, "diffman")` for more info
@@ -15691,22 +716,7 @@ Run `revdepcheck::cloud_details(, "tilemaps")` for more info ### Devel ``` -* using log directory ‘/tmp/workdir/tilemaps/new/tilemaps.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘tilemaps/DESCRIPTION’ ... OK -* this is package ‘tilemaps’ version ‘0.2.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Packages required but not available: 'lwgeom', 'sf' -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR @@ -15716,39 +726,23 @@ Status: 1 ERROR ### CRAN ``` -* using log directory ‘/tmp/workdir/tilemaps/old/tilemaps.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘tilemaps/DESCRIPTION’ ... OK -* this is package ‘tilemaps’ version ‘0.2.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Packages required but not available: 'lwgeom', 'sf' -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR ``` -# timetk +# diffrprojects
-* Version: 2.8.2 -* GitHub: https://github.com/business-science/timetk -* Source code: https://github.com/cran/timetk -* Date/Publication: 2022-11-17 19:30:02 UTC -* Number of recursive dependencies: 226 +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/diffrprojects +* Number of recursive dependencies: 66 -Run `revdepcheck::cloud_details(, "timetk")` for more info +Run `revdepcheck::cloud_details(, "diffrprojects")` for more info
@@ -15756,75 +750,34 @@ Run `revdepcheck::cloud_details(, "timetk")` for more info ### Devel -``` -* using log directory ‘/tmp/workdir/timetk/new/timetk.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘timetk/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘timetk’ version ‘2.8.2’ -* package encoding: UTF-8 -* checking package namespace information ... OK -... - Error in library(robets) : there is no package called 'robets' - Execution halted -* checking for unstated dependencies in vignettes ... OK -* checking package vignettes in ‘inst/doc’ ... OK -* checking running R code from vignettes ... NONE - ‘TK04_Plotting_Time_Series.Rmd’ using ‘UTF-8’... OK - ‘TK07_Time_Series_Data_Wrangling.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: 1 ERROR, 2 NOTEs - - - - - -``` -### CRAN - -``` -* using log directory ‘/tmp/workdir/timetk/old/timetk.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘timetk/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘timetk’ version ‘2.8.2’ -* package encoding: UTF-8 -* checking package namespace information ... OK -... - Error in library(robets) : there is no package called 'robets' - Execution halted -* checking for unstated dependencies in vignettes ... OK -* checking package vignettes in ‘inst/doc’ ... OK -* checking running R code from vignettes ... NONE - ‘TK04_Plotting_Time_Series.Rmd’ using ‘UTF-8’... OK - ‘TK07_Time_Series_Data_Wrangling.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: 1 ERROR, 2 NOTEs +``` + + + + + + +``` +### CRAN + +``` + ``` -# tinyarray +# dynfrail
-* Version: 2.2.9 -* GitHub: https://github.com/xjsun1221/tinyarray -* Source code: https://github.com/cran/tinyarray -* Date/Publication: 2023-03-04 07:40:02 UTC -* Number of recursive dependencies: 228 +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/dynfrail +* Number of recursive dependencies: 57 -Run `revdepcheck::cloud_details(, "tinyarray")` for more info +Run `revdepcheck::cloud_details(, "dynfrail")` for more info
@@ -15833,23 +786,7 @@ Run `revdepcheck::cloud_details(, "tinyarray")` for more info ### Devel ``` -* using log directory ‘/tmp/workdir/tinyarray/new/tinyarray.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘tinyarray/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘tinyarray’ version ‘2.2.9’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘clusterProfiler’ -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR @@ -15859,40 +796,23 @@ Status: 1 ERROR ### CRAN ``` -* using log directory ‘/tmp/workdir/tinyarray/old/tinyarray.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘tinyarray/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘tinyarray’ version ‘2.2.9’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘clusterProfiler’ -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR ``` -# tipmap +# epiphy
-* Version: 0.3.9 +* Version: NA * GitHub: NA -* Source code: https://github.com/cran/tipmap -* Date/Publication: 2022-12-07 21:50:02 UTC -* Number of recursive dependencies: 96 +* Source code: https://github.com/cran/epiphy +* Number of recursive dependencies: 92 -Run `revdepcheck::cloud_details(, "tipmap")` for more info +Run `revdepcheck::cloud_details(, "epiphy")` for more info
@@ -15901,23 +821,7 @@ Run `revdepcheck::cloud_details(, "tipmap")` for more info ### Devel ``` -* using log directory ‘/tmp/workdir/tipmap/new/tipmap.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘tipmap/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘tipmap’ version ‘0.3.9’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘RBesT’ -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR @@ -15927,40 +831,23 @@ Status: 1 ERROR ### CRAN ``` -* using log directory ‘/tmp/workdir/tipmap/old/tipmap.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘tipmap/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘tipmap’ version ‘0.3.9’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘RBesT’ -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR ``` -# tmap +# evaluator
-* Version: 3.3-3 -* GitHub: https://github.com/r-tmap/tmap -* Source code: https://github.com/cran/tmap -* Date/Publication: 2022-03-02 08:50:02 UTC -* Number of recursive dependencies: 158 +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/evaluator +* Number of recursive dependencies: 146 -Run `revdepcheck::cloud_details(, "tmap")` for more info +Run `revdepcheck::cloud_details(, "evaluator")` for more info
@@ -15969,23 +856,7 @@ Run `revdepcheck::cloud_details(, "tmap")` for more info ### Devel ``` -* using log directory ‘/tmp/workdir/tmap/new/tmap.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘tmap/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘tmap’ version ‘3.3-3’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR @@ -15995,40 +866,23 @@ Status: 1 ERROR ### CRAN ``` -* using log directory ‘/tmp/workdir/tmap/old/tmap.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘tmap/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘tmap’ version ‘3.3-3’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR ``` -# trackdf +# expstudies
-* Version: 0.3.1 -* GitHub: https://github.com/swarm-lab/trackdf -* Source code: https://github.com/cran/trackdf -* Date/Publication: 2023-01-23 00:50:02 UTC -* Number of recursive dependencies: 150 +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/expstudies +* Number of recursive dependencies: 60 -Run `revdepcheck::cloud_details(, "trackdf")` for more info +Run `revdepcheck::cloud_details(, "expstudies")` for more info
@@ -16037,25 +891,7 @@ Run `revdepcheck::cloud_details(, "trackdf")` for more info ### Devel ``` -* using log directory ‘/tmp/workdir/trackdf/new/trackdf.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘trackdf/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘trackdf’ version ‘0.3.1’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -Package suggested but not available for checking: ‘moveVis’ -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR @@ -16065,42 +901,23 @@ Status: 1 ERROR ### CRAN ``` -* using log directory ‘/tmp/workdir/trackdf/old/trackdf.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘trackdf/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘trackdf’ version ‘0.3.1’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -Package suggested but not available for checking: ‘moveVis’ -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR ``` -# trending +# fipe
-* Version: 0.0.3 -* GitHub: https://github.com/reconhub/trending -* Source code: https://github.com/cran/trending -* Date/Publication: 2021-04-19 09:10:02 UTC -* Number of recursive dependencies: 142 +* Version: NA +* GitHub: NA +* Source code: https://github.com/cran/fipe +* Number of recursive dependencies: 70 -Run `revdepcheck::cloud_details(, "trending")` for more info +Run `revdepcheck::cloud_details(, "fipe")` for more info
@@ -16109,27 +926,7 @@ Run `revdepcheck::cloud_details(, "trending")` for more info ### Devel ``` -* using log directory ‘/tmp/workdir/trending/new/trending.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘trending/DESCRIPTION’ ... OK -* this is package ‘trending’ version ‘0.0.3’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... NOTE -... -* 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 - ‘Introduction.Rmd’ using ‘UTF-8’... OK - ‘prediction_intervals.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: 2 NOTEs + @@ -16139,44 +936,23 @@ Status: 2 NOTEs ### CRAN ``` -* using log directory ‘/tmp/workdir/trending/old/trending.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘trending/DESCRIPTION’ ... OK -* this is package ‘trending’ version ‘0.0.3’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... NOTE -... -* 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 - ‘Introduction.Rmd’ using ‘UTF-8’... OK - ‘prediction_intervals.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: 2 NOTEs + ``` -# TUFLOWR +# foieGras
-* Version: 0.1.0 +* Version: NA * GitHub: NA -* Source code: https://github.com/cran/TUFLOWR -* Date/Publication: 2021-10-18 14:30:05 UTC -* Number of recursive dependencies: 74 +* Source code: https://github.com/cran/foieGras +* Number of recursive dependencies: 135 -Run `revdepcheck::cloud_details(, "TUFLOWR")` for more info +Run `revdepcheck::cloud_details(, "foieGras")` for more info
@@ -16185,27 +961,7 @@ Run `revdepcheck::cloud_details(, "TUFLOWR")` for more info ### Devel ``` -* using log directory ‘/tmp/workdir/TUFLOWR/new/TUFLOWR.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘TUFLOWR/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘TUFLOWR’ version ‘0.1.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -... -* checking Rd metadata ... OK -* checking Rd cross-references ... 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 examples ... OK -* DONE -Status: OK + @@ -16215,44 +971,24 @@ Status: OK ### CRAN ``` -* using log directory ‘/tmp/workdir/TUFLOWR/old/TUFLOWR.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘TUFLOWR/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘TUFLOWR’ version ‘0.1.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -... -* checking Rd metadata ... OK -* checking Rd cross-references ... 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 examples ... OK -* DONE -Status: OK + ``` -# VancouvR +# ImputeRobust
-* Version: 0.1.7 -* GitHub: https://github.com/mountainMath/VancouvR -* Source code: https://github.com/cran/VancouvR -* Date/Publication: 2021-10-21 04:30:02 UTC +* Version: 1.3-1 +* GitHub: NA +* Source code: https://github.com/cran/ImputeRobust +* Date/Publication: 2018-11-30 12:10:03 UTC * Number of recursive dependencies: 86 -Run `revdepcheck::cloud_details(, "VancouvR")` for more info +Run `revdepcheck::cloud_details(, "ImputeRobust")` for more info
@@ -16261,20 +997,18 @@ Run `revdepcheck::cloud_details(, "VancouvR")` for more info ### Devel ``` -* using log directory ‘/tmp/workdir/VancouvR/new/VancouvR.Rcheck’ -* using R version 4.1.1 (2021-08-10) +* using log directory ‘/tmp/workdir/ImputeRobust/new/ImputeRobust.Rcheck’ +* using R version 4.2.1 (2022-06-23) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘VancouvR/DESCRIPTION’ ... OK +* checking for file ‘ImputeRobust/DESCRIPTION’ ... OK * checking extension type ... Package -* this is package ‘VancouvR’ version ‘0.1.7’ +* this is package ‘ImputeRobust’ version ‘1.3-1’ * package encoding: UTF-8 * checking package namespace information ... OK * checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -Package suggested but not available for checking: ‘lwgeom’ +Package required but not available: ‘extremevalues’ See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ manual. @@ -16289,20 +1023,18 @@ Status: 1 ERROR ### CRAN ``` -* using log directory ‘/tmp/workdir/VancouvR/old/VancouvR.Rcheck’ -* using R version 4.1.1 (2021-08-10) +* using log directory ‘/tmp/workdir/ImputeRobust/old/ImputeRobust.Rcheck’ +* using R version 4.2.1 (2022-06-23) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘VancouvR/DESCRIPTION’ ... OK +* checking for file ‘ImputeRobust/DESCRIPTION’ ... OK * checking extension type ... Package -* this is package ‘VancouvR’ version ‘0.1.7’ +* this is package ‘ImputeRobust’ version ‘1.3-1’ * package encoding: UTF-8 * checking package namespace information ... OK * checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -Package suggested but not available for checking: ‘lwgeom’ +Package required but not available: ‘extremevalues’ See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ manual. @@ -16314,17 +1046,16 @@ Status: 1 ERROR ``` -# vivid +# IsoCorrectoR
-* Version: 0.2.5 +* Version: NA * GitHub: NA -* Source code: https://github.com/cran/vivid -* Date/Publication: 2023-02-13 16:40:02 UTC -* Number of recursive dependencies: 206 +* Source code: https://github.com/cran/IsoCorrectoR +* Number of recursive dependencies: 71 -Run `revdepcheck::cloud_details(, "vivid")` for more info +Run `revdepcheck::cloud_details(, "IsoCorrectoR")` for more info
@@ -16333,27 +1064,7 @@ Run `revdepcheck::cloud_details(, "vivid")` for more info ### Devel ``` -* using log directory ‘/tmp/workdir/vivid/new/vivid.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘vivid/DESCRIPTION’ ... OK -* this is package ‘vivid’ version ‘0.2.5’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... NOTE -... -* 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 - ‘vivid.Rmd’ using ‘UTF-8’... OK - ‘vividQStart.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: 1 NOTE + @@ -16363,44 +1074,24 @@ Status: 1 NOTE ### CRAN ``` -* using log directory ‘/tmp/workdir/vivid/old/vivid.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘vivid/DESCRIPTION’ ... OK -* this is package ‘vivid’ version ‘0.2.5’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... NOTE -... -* 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 - ‘vivid.Rmd’ using ‘UTF-8’... OK - ‘vividQStart.Rmd’ using ‘UTF-8’... OK -* checking re-building of vignette outputs ... OK -* DONE -Status: 1 NOTE + ``` -# wallace +# loon.ggplot
-* Version: 2.0.4 -* GitHub: NA -* Source code: https://github.com/cran/wallace -* Date/Publication: 2023-03-14 08:20:02 UTC -* Number of recursive dependencies: 282 +* Version: 1.3.3 +* GitHub: https://github.com/great-northern-diver/loon.ggplot +* Source code: https://github.com/cran/loon.ggplot +* Date/Publication: 2022-11-12 22:30:02 UTC +* Number of recursive dependencies: 105 -Run `revdepcheck::cloud_details(, "wallace")` for more info +Run `revdepcheck::cloud_details(, "loon.ggplot")` for more info
@@ -16409,27 +1100,25 @@ Run `revdepcheck::cloud_details(, "wallace")` for more info ### Devel ``` -* using log directory ‘/tmp/workdir/wallace/new/wallace.Rcheck’ -* using R version 4.1.1 (2021-08-10) +* using log directory ‘/tmp/workdir/loon.ggplot/new/loon.ggplot.Rcheck’ +* using R version 4.2.1 (2022-06-23) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘wallace/DESCRIPTION’ ... OK -* this is package ‘wallace’ version ‘2.0.4’ +* checking for file ‘loon.ggplot/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘loon.ggplot’ version ‘1.3.3’ * package encoding: UTF-8 * checking package namespace information ... OK -* checking package dependencies ... NOTE -... -* checking for code/documentation mismatches ... OK -* checking Rd \usage sections ... OK -* checking Rd contents ... OK -* checking for unstated dependencies in examples ... OK -* checking examples ... OK -* checking for unstated dependencies in ‘tests’ ... OK -* checking tests ... OK - Running ‘testthat.R’ +* checking package dependencies ... ERROR +Package required but not available: ‘loon’ + +Package suggested but not available for checking: ‘zenplots’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. * DONE -Status: 1 NOTE +Status: 1 ERROR @@ -16439,44 +1128,42 @@ Status: 1 NOTE ### CRAN ``` -* using log directory ‘/tmp/workdir/wallace/old/wallace.Rcheck’ -* using R version 4.1.1 (2021-08-10) +* using log directory ‘/tmp/workdir/loon.ggplot/old/loon.ggplot.Rcheck’ +* using R version 4.2.1 (2022-06-23) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘wallace/DESCRIPTION’ ... OK -* this is package ‘wallace’ version ‘2.0.4’ +* checking for file ‘loon.ggplot/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘loon.ggplot’ version ‘1.3.3’ * package encoding: UTF-8 * checking package namespace information ... OK -* checking package dependencies ... NOTE -... -* checking for code/documentation mismatches ... OK -* checking Rd \usage sections ... OK -* checking Rd contents ... OK -* checking for unstated dependencies in examples ... OK -* checking examples ... OK -* checking for unstated dependencies in ‘tests’ ... OK -* checking tests ... OK - Running ‘testthat.R’ +* checking package dependencies ... ERROR +Package required but not available: ‘loon’ + +Package suggested but not available for checking: ‘zenplots’ + +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. * DONE -Status: 1 NOTE +Status: 1 ERROR ``` -# waterquality +# loon.shiny
-* Version: 0.3.0 -* GitHub: https://github.com/RAJohansen/waterquality -* Source code: https://github.com/cran/waterquality -* Date/Publication: 2022-02-09 16:50:02 UTC -* Number of recursive dependencies: 151 +* Version: 1.0.3 +* GitHub: NA +* Source code: https://github.com/cran/loon.shiny +* Date/Publication: 2022-10-08 15:30:02 UTC +* Number of recursive dependencies: 136 -Run `revdepcheck::cloud_details(, "waterquality")` for more info +Run `revdepcheck::cloud_details(, "loon.shiny")` for more info
@@ -16485,27 +1172,23 @@ Run `revdepcheck::cloud_details(, "waterquality")` for more info ### Devel ``` -* using log directory ‘/tmp/workdir/waterquality/new/waterquality.Rcheck’ -* using R version 4.1.1 (2021-08-10) +* using log directory ‘/tmp/workdir/loon.shiny/new/loon.shiny.Rcheck’ +* using R version 4.2.1 (2022-06-23) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘waterquality/DESCRIPTION’ ... OK -* this is package ‘waterquality’ version ‘0.3.0’ +* checking for file ‘loon.shiny/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘loon.shiny’ version ‘1.0.3’ * package encoding: UTF-8 * checking package namespace information ... OK -* checking package dependencies ... NOTE -... ---- failed re-building ‘waterquality_vignette.Rmd’ - -SUMMARY: processing the following file failed: - ‘waterquality_vignette.Rmd’ - -Error: Vignette re-building failed. -Execution halted +* checking package dependencies ... ERROR +Packages required but not available: 'loon', 'loon.ggplot' +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. * DONE -Status: 1 WARNING, 2 NOTEs +Status: 1 ERROR @@ -16515,43 +1198,39 @@ Status: 1 WARNING, 2 NOTEs ### CRAN ``` -* using log directory ‘/tmp/workdir/waterquality/old/waterquality.Rcheck’ -* using R version 4.1.1 (2021-08-10) +* using log directory ‘/tmp/workdir/loon.shiny/old/loon.shiny.Rcheck’ +* using R version 4.2.1 (2022-06-23) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘waterquality/DESCRIPTION’ ... OK -* this is package ‘waterquality’ version ‘0.3.0’ +* checking for file ‘loon.shiny/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘loon.shiny’ version ‘1.0.3’ * package encoding: UTF-8 * checking package namespace information ... OK -* checking package dependencies ... NOTE -... ---- failed re-building ‘waterquality_vignette.Rmd’ - -SUMMARY: processing the following file failed: - ‘waterquality_vignette.Rmd’ - -Error: Vignette re-building failed. -Execution halted +* checking package dependencies ... ERROR +Packages required but not available: 'loon', 'loon.ggplot' +See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ +manual. * DONE -Status: 1 WARNING, 2 NOTEs +Status: 1 ERROR ``` -# Wats +# mafs
* Version: NA * GitHub: NA -* Source code: https://github.com/cran/Wats -* Number of recursive dependencies: 122 +* Source code: https://github.com/cran/mafs +* Number of recursive dependencies: 90 -Run `revdepcheck::cloud_details(, "Wats")` for more info +Run `revdepcheck::cloud_details(, "mafs")` for more info
@@ -16577,81 +1256,17 @@ Run `revdepcheck::cloud_details(, "Wats")` for more info ``` -# waves - -
- -* Version: 0.2.4 -* GitHub: https://github.com/GoreLab/waves -* Source code: https://github.com/cran/waves -* Date/Publication: 2022-03-29 21:50:02 UTC -* Number of recursive dependencies: 165 - -Run `revdepcheck::cloud_details(, "waves")` for more info - -
- -## In both - -* checking whether package ‘waves’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/waves/new/waves.Rcheck/00install.out’ for details. - ``` - -## Installation - -### Devel - -``` -* installing *source* package ‘waves’ ... -** package ‘waves’ 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 ‘sf’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart -Execution halted -ERROR: lazy loading failed for package ‘waves’ -* removing ‘/tmp/workdir/waves/new/waves.Rcheck/waves’ - - -``` -### CRAN - -``` -* installing *source* package ‘waves’ ... -** package ‘waves’ 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 ‘sf’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart -Execution halted -ERROR: lazy loading failed for package ‘waves’ -* removing ‘/tmp/workdir/waves/old/waves.Rcheck/waves’ - - -``` -# wdpar +# MarketMatching
-* Version: 1.3.4 -* GitHub: https://github.com/prioritizr/wdpar -* Source code: https://github.com/cran/wdpar -* Date/Publication: 2023-02-24 08:40:02 UTC -* Number of recursive dependencies: 108 +* Version: 1.2.0 +* GitHub: NA +* Source code: https://github.com/cran/MarketMatching +* Date/Publication: 2021-01-08 20:10:02 UTC +* Number of recursive dependencies: 74 -Run `revdepcheck::cloud_details(, "wdpar")` for more info +Run `revdepcheck::cloud_details(, "MarketMatching")` for more info
@@ -16660,20 +1275,17 @@ Run `revdepcheck::cloud_details(, "wdpar")` for more info ### Devel ``` -* using log directory ‘/tmp/workdir/wdpar/new/wdpar.Rcheck’ -* using R version 4.1.1 (2021-08-10) +* using log directory ‘/tmp/workdir/MarketMatching/new/MarketMatching.Rcheck’ +* using R version 4.2.1 (2022-06-23) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘wdpar/DESCRIPTION’ ... OK +* checking for file ‘MarketMatching/DESCRIPTION’ ... OK * checking extension type ... Package -* this is package ‘wdpar’ version ‘1.3.4’ -* package encoding: UTF-8 +* this is package ‘MarketMatching’ version ‘1.2.0’ * checking package namespace information ... OK * checking package dependencies ... ERROR -Packages required but not available: 'sf', 'lwgeom' - -Package suggested but not available for checking: ‘prepr’ +Packages required but not available: 'CausalImpact', 'bsts', 'Boom' See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ manual. @@ -16688,20 +1300,17 @@ Status: 1 ERROR ### CRAN ``` -* using log directory ‘/tmp/workdir/wdpar/old/wdpar.Rcheck’ -* using R version 4.1.1 (2021-08-10) +* using log directory ‘/tmp/workdir/MarketMatching/old/MarketMatching.Rcheck’ +* using R version 4.2.1 (2022-06-23) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘wdpar/DESCRIPTION’ ... OK +* checking for file ‘MarketMatching/DESCRIPTION’ ... OK * checking extension type ... Package -* this is package ‘wdpar’ version ‘1.3.4’ -* package encoding: UTF-8 +* this is package ‘MarketMatching’ version ‘1.2.0’ * checking package namespace information ... OK * checking package dependencies ... ERROR -Packages required but not available: 'sf', 'lwgeom' - -Package suggested but not available for checking: ‘prepr’ +Packages required but not available: 'CausalImpact', 'bsts', 'Boom' See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ manual. @@ -16713,79 +1322,52 @@ Status: 1 ERROR ``` -# wearables +# modeltime.h2o
-* Version: 0.8.1 +* Version: NA * GitHub: NA -* Source code: https://github.com/cran/wearables -* Date/Publication: 2021-12-20 15:20:02 UTC -* Number of recursive dependencies: 122 +* Source code: https://github.com/cran/modeltime.h2o +* Number of recursive dependencies: 218 -Run `revdepcheck::cloud_details(, "wearables")` for more info +Run `revdepcheck::cloud_details(, "modeltime.h2o")` for more info
-## In both - -* checking whether package ‘wearables’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/wearables/new/wearables.Rcheck/00install.out’ for details. - ``` - -## Installation +## Error before installation ### Devel ``` -* installing *source* package ‘wearables’ ... -** package ‘wearables’ 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 ‘rstan’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart -Execution halted -ERROR: lazy loading failed for package ‘wearables’ -* removing ‘/tmp/workdir/wearables/new/wearables.Rcheck/wearables’ + + + + ``` ### CRAN ``` -* installing *source* package ‘wearables’ ... -** package ‘wearables’ 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 ‘rstan’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart -Execution halted -ERROR: lazy loading failed for package ‘wearables’ -* removing ‘/tmp/workdir/wearables/old/wearables.Rcheck/wearables’ + + + + ``` -# webSDM +# Platypus
-* Version: 1.1-3 -* GitHub: https://github.com/giopogg/webSDM -* Source code: https://github.com/cran/webSDM -* Date/Publication: 2023-03-14 13:50:02 UTC -* Number of recursive dependencies: 190 +* Version: 3.4.1 +* GitHub: NA +* Source code: https://github.com/cran/Platypus +* Date/Publication: 2022-08-15 07:20:20 UTC +* Number of recursive dependencies: 354 -Run `revdepcheck::cloud_details(, "webSDM")` for more info +Run `revdepcheck::cloud_details(, "Platypus")` for more info
@@ -16794,22 +1376,27 @@ Run `revdepcheck::cloud_details(, "webSDM")` for more info ### Devel ``` -* using log directory ‘/tmp/workdir/webSDM/new/webSDM.Rcheck’ -* using R version 4.1.1 (2021-08-10) +* using log directory ‘/tmp/workdir/Platypus/new/Platypus.Rcheck’ +* using R version 4.2.1 (2022-06-23) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘webSDM/DESCRIPTION’ ... OK -* this is package ‘webSDM’ version ‘1.1-3’ +* checking for file ‘Platypus/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘Platypus’ version ‘3.4.1’ * package encoding: UTF-8 * checking package namespace information ... OK -* checking package dependencies ... ERROR -Packages required but not available: 'brms', 'rstanarm' - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. +... +* 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 + ‘PlatypusV3_agedCNS.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK * DONE -Status: 1 ERROR +Status: 3 WARNINGs, 2 NOTEs @@ -16819,38 +1406,43 @@ Status: 1 ERROR ### CRAN ``` -* using log directory ‘/tmp/workdir/webSDM/old/webSDM.Rcheck’ -* using R version 4.1.1 (2021-08-10) +* using log directory ‘/tmp/workdir/Platypus/old/Platypus.Rcheck’ +* using R version 4.2.1 (2022-06-23) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘webSDM/DESCRIPTION’ ... OK -* this is package ‘webSDM’ version ‘1.1-3’ +* checking for file ‘Platypus/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘Platypus’ version ‘3.4.1’ * package encoding: UTF-8 * checking package namespace information ... OK -* checking package dependencies ... ERROR -Packages required but not available: 'brms', 'rstanarm' - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. +... +* 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 + ‘PlatypusV3_agedCNS.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK * DONE -Status: 1 ERROR +Status: 3 WARNINGs, 2 NOTEs ``` -# wrappedtools +# SCtools
* Version: NA * GitHub: NA -* Source code: https://github.com/cran/wrappedtools -* Number of recursive dependencies: 96 +* Source code: https://github.com/cran/SCtools +* Number of recursive dependencies: 93 -Run `revdepcheck::cloud_details(, "wrappedtools")` for more info +Run `revdepcheck::cloud_details(, "SCtools")` for more info
@@ -16876,17 +1468,16 @@ Run `revdepcheck::cloud_details(, "wrappedtools")` for more info ``` -# xpose.nlmixr2 +# sknifedatar
-* Version: 0.4.0 +* Version: NA * GitHub: NA -* Source code: https://github.com/cran/xpose.nlmixr2 -* Date/Publication: 2022-06-08 09:10:02 UTC -* Number of recursive dependencies: 158 +* Source code: https://github.com/cran/sknifedatar +* Number of recursive dependencies: 213 -Run `revdepcheck::cloud_details(, "xpose.nlmixr2")` for more info +Run `revdepcheck::cloud_details(, "sknifedatar")` for more info
@@ -16895,25 +1486,7 @@ Run `revdepcheck::cloud_details(, "xpose.nlmixr2")` for more info ### Devel ``` -* using log directory ‘/tmp/workdir/xpose.nlmixr2/new/xpose.nlmixr2.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘xpose.nlmixr2/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘xpose.nlmixr2’ version ‘0.4.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘nlmixr2est’ - -Package suggested but not available for checking: ‘nlmixr2’ -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR @@ -16923,106 +1496,100 @@ Status: 1 ERROR ### CRAN ``` -* using log directory ‘/tmp/workdir/xpose.nlmixr2/old/xpose.nlmixr2.Rcheck’ -* using R version 4.1.1 (2021-08-10) -* using platform: x86_64-pc-linux-gnu (64-bit) -* using session charset: UTF-8 -* using option ‘--no-manual’ -* checking for file ‘xpose.nlmixr2/DESCRIPTION’ ... OK -* checking extension type ... Package -* this is package ‘xpose.nlmixr2’ version ‘0.4.0’ -* package encoding: UTF-8 -* checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘nlmixr2est’ - -Package suggested but not available for checking: ‘nlmixr2’ -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. -* DONE -Status: 1 ERROR ``` -# zipcodeR +# tidyfit
-* Version: 0.3.5 -* GitHub: https://github.com/gavinrozzi/zipcodeR -* Source code: https://github.com/cran/zipcodeR -* Date/Publication: 2022-10-03 22:00:02 UTC -* Number of recursive dependencies: 99 +* Version: 0.6.4 +* GitHub: https://github.com/jpfitzinger/tidyfit +* Source code: https://github.com/cran/tidyfit +* Date/Publication: 2023-05-20 15:40:02 UTC +* Number of recursive dependencies: 165 -Run `revdepcheck::cloud_details(, "zipcodeR")` for more info +Run `revdepcheck::cloud_details(, "tidyfit")` for more info
-## In both - -* checking whether package ‘zipcodeR’ can be installed ... ERROR - ``` - Installation failed. - See ‘/tmp/workdir/zipcodeR/new/zipcodeR.Rcheck/00install.out’ for details. - ``` - -## Installation +## Error before installation ### Devel ``` -* installing *source* package ‘zipcodeR’ ... -** package ‘zipcodeR’ 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 ‘sf’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart -Execution halted -ERROR: lazy loading failed for package ‘zipcodeR’ -* removing ‘/tmp/workdir/zipcodeR/new/zipcodeR.Rcheck/zipcodeR’ +* using log directory ‘/tmp/workdir/tidyfit/new/tidyfit.Rcheck’ +* using R version 4.2.1 (2022-06-23) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘tidyfit/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘tidyfit’ version ‘0.6.4’ +* package encoding: UTF-8 +* checking package namespace information ... OK +... + ‘Flowchart.Rmd’ using ‘UTF-8’... OK + ‘Predicting_Boston_House_Prices.Rmd’ using ‘UTF-8’... OK + ‘Bootstrapping_Confidence_Intervals.Rmd’ using ‘UTF-8’... OK + ‘Feature_Selection.Rmd’ using ‘UTF-8’... OK + ‘Multinomial_Classification.Rmd’ using ‘UTF-8’... OK + ‘Rolling_Window_Time_Series_Regression.Rmd’ using ‘UTF-8’... OK + ‘Time-varying_parameters_vs_rolling_windows.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 2 ERRORs, 1 NOTE + + + ``` ### CRAN ``` -* installing *source* package ‘zipcodeR’ ... -** package ‘zipcodeR’ 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 ‘sf’ -Calls: ... loadNamespace -> withRestarts -> withOneRestart -> doWithOneRestart -Execution halted -ERROR: lazy loading failed for package ‘zipcodeR’ -* removing ‘/tmp/workdir/zipcodeR/old/zipcodeR.Rcheck/zipcodeR’ +* using log directory ‘/tmp/workdir/tidyfit/old/tidyfit.Rcheck’ +* using R version 4.2.1 (2022-06-23) +* using platform: x86_64-pc-linux-gnu (64-bit) +* using session charset: UTF-8 +* using option ‘--no-manual’ +* checking for file ‘tidyfit/DESCRIPTION’ ... OK +* checking extension type ... Package +* this is package ‘tidyfit’ version ‘0.6.4’ +* package encoding: UTF-8 +* checking package namespace information ... OK +... + ‘Flowchart.Rmd’ using ‘UTF-8’... OK + ‘Predicting_Boston_House_Prices.Rmd’ using ‘UTF-8’... OK + ‘Bootstrapping_Confidence_Intervals.Rmd’ using ‘UTF-8’... OK + ‘Feature_Selection.Rmd’ using ‘UTF-8’... OK + ‘Multinomial_Classification.Rmd’ using ‘UTF-8’... OK + ‘Rolling_Window_Time_Series_Regression.Rmd’ using ‘UTF-8’... OK + ‘Time-varying_parameters_vs_rolling_windows.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK +* DONE +Status: 2 ERRORs, 1 NOTE + + + ``` -# zonebuilder +# vivid
-* Version: 0.0.2 -* GitHub: https://github.com/zonebuilders/zonebuilder -* Source code: https://github.com/cran/zonebuilder -* Date/Publication: 2021-07-12 22:30:02 UTC -* Number of recursive dependencies: 126 +* Version: 0.2.7 +* GitHub: NA +* Source code: https://github.com/cran/vivid +* Date/Publication: 2023-04-11 13:50:02 UTC +* Number of recursive dependencies: 209 -Run `revdepcheck::cloud_details(, "zonebuilder")` for more info +Run `revdepcheck::cloud_details(, "vivid")` for more info
@@ -17031,24 +1598,27 @@ Run `revdepcheck::cloud_details(, "zonebuilder")` for more info ### Devel ``` -* using log directory ‘/tmp/workdir/zonebuilder/new/zonebuilder.Rcheck’ -* using R version 4.1.1 (2021-08-10) +* using log directory ‘/tmp/workdir/vivid/new/vivid.Rcheck’ +* using R version 4.2.1 (2022-06-23) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘zonebuilder/DESCRIPTION’ ... OK -* this is package ‘zonebuilder’ version ‘0.0.2’ +* checking for file ‘vivid/DESCRIPTION’ ... OK +* this is package ‘vivid’ version ‘0.2.7’ * package encoding: UTF-8 * checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -Package suggested but not available for checking: ‘lwgeom’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. +* checking package dependencies ... NOTE +... +* 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 + ‘vividVignette.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK * DONE -Status: 1 ERROR +Status: 1 NOTE @@ -17058,24 +1628,27 @@ Status: 1 ERROR ### CRAN ``` -* using log directory ‘/tmp/workdir/zonebuilder/old/zonebuilder.Rcheck’ -* using R version 4.1.1 (2021-08-10) +* using log directory ‘/tmp/workdir/vivid/old/vivid.Rcheck’ +* using R version 4.2.1 (2022-06-23) * using platform: x86_64-pc-linux-gnu (64-bit) * using session charset: UTF-8 * using option ‘--no-manual’ -* checking for file ‘zonebuilder/DESCRIPTION’ ... OK -* this is package ‘zonebuilder’ version ‘0.0.2’ +* checking for file ‘vivid/DESCRIPTION’ ... OK +* this is package ‘vivid’ version ‘0.2.7’ * package encoding: UTF-8 * checking package namespace information ... OK -* checking package dependencies ... ERROR -Package required but not available: ‘sf’ - -Package suggested but not available for checking: ‘lwgeom’ - -See section ‘The DESCRIPTION file’ in the ‘Writing R Extensions’ -manual. +* checking package dependencies ... NOTE +... +* 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 + ‘vividVignette.Rmd’ using ‘UTF-8’... OK +* checking re-building of vignette outputs ... OK * DONE -Status: 1 ERROR +Status: 1 NOTE diff --git a/revdep/problems.md b/revdep/problems.md index 893b53f87..415cc3651 100644 --- a/revdep/problems.md +++ b/revdep/problems.md @@ -1,109 +1,82 @@ -# openalexR +# covidcast
-* Version: 1.0.0 -* GitHub: https://github.com/massimoaria/openalexR -* Source code: https://github.com/cran/openalexR -* Date/Publication: 2022-10-06 10:40:02 UTC -* Number of recursive dependencies: 78 +* Version: 0.5.0 +* GitHub: https://github.com/cmu-delphi/covidcast +* Source code: https://github.com/cran/covidcast +* Date/Publication: 2023-06-01 20:10:02 UTC +* Number of recursive dependencies: 93 -Run `revdepcheck::cloud_details(, "openalexR")` for more info +Run `revdepcheck::cloud_details(, "covidcast")` for more info
## Newly broken -* checking re-building of vignette outputs ... WARNING +* checking re-building of vignette outputs ... ERROR ``` Error(s) in re-building vignettes: - ... - --- re-building ‘A_Brief_Introduction_to_openalexR.Rmd’ using rmarkdown - Quitting from lines 260-269 (A_Brief_Introduction_to_openalexR.Rmd) - Error: processing vignette 'A_Brief_Introduction_to_openalexR.Rmd' failed with diagnostics: - $ operator is invalid for atomic vectors - --- failed re-building ‘A_Brief_Introduction_to_openalexR.Rmd’ + --- re-building ‘correlation-utils.Rmd’ using rmarkdown + --- finished re-building ‘correlation-utils.Rmd’ - SUMMARY: processing the following file failed: - ‘A_Brief_Introduction_to_openalexR.Rmd’ + --- re-building ‘covidcast.Rmd’ using rmarkdown + --- finished re-building ‘covidcast.Rmd’ + + --- re-building ‘external-data.Rmd’ using rmarkdown + --- finished re-building ‘external-data.Rmd’ + + ... + ℹ In index: 1. + Caused by error in `match.arg()`: + ! 'arg' should be one of "day", "week" + --- failed re-building ‘plotting-signals.Rmd’ + + SUMMARY: processing the following files failed: + ‘multi-signals.Rmd’ ‘plotting-signals.Rmd’ Error: Vignette re-building failed. Execution halted ``` -# portalr - -
- -* Version: 0.3.11 -* GitHub: https://github.com/weecology/portalr -* Source code: https://github.com/cran/portalr -* Date/Publication: 2022-12-01 17:40:02 UTC -* Number of recursive dependencies: 106 - -Run `revdepcheck::cloud_details(, "portalr")` for more info - -
+## In both -## Newly broken - -* checking tests ... ERROR +* checking data for non-ASCII characters ... NOTE ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Last 13 lines of output: - Backtrace: - ▆ - 1. ├─portalr::bait_presence_absence(path = portal_data_path, level = "plot") at test-10-summarize_ants.R:49:2 - 2. │ ├─compute_presence(bait, level) %>% as.data.frame() - 3. │ └─portalr:::compute_presence(bait, level) - 4. │ └─... %>% ... - 5. ├─base::as.data.frame(.) - 6. ├─tidyr::complete(., !!!grouping, fill = list(presence = 0)) - 7. ├─dplyr::mutate(., presence = 1) - 8. ├─dplyr::distinct(.) - 9. └─dplyr::select(., !!!grouping) - - [ FAIL 12 | WARN 43 | SKIP 42 | PASS 17 ] - Error: Test failures - Execution halted + Note: found 20 marked UTF-8 strings ``` -# rapbase +# scGOclust
-* Version: 1.24.0 -* GitHub: https://github.com/Rapporteket/rapbase -* Source code: https://github.com/cran/rapbase -* Date/Publication: 2023-02-27 10:22:31 UTC -* Number of recursive dependencies: 110 +* Version: 0.1.0 +* GitHub: https://github.com/YY-SONG0718/scGOclust +* Source code: https://github.com/cran/scGOclust +* Date/Publication: 2023-06-01 11:50:05 UTC +* Number of recursive dependencies: 211 -Run `revdepcheck::cloud_details(, "rapbase")` for more info +Run `revdepcheck::cloud_details(, "scGOclust")` for more info
## Newly broken -* checking tests ... ERROR +* checking re-building of vignette outputs ... ERROR ``` - Running ‘testthat.R’ - Running the tests in ‘tests/testthat.R’ failed. - Last 13 lines of output: - ══ Failed tests ════════════════════════════════════════════════════════════════ - ── Failure ('test-github.R:6:3'): contributors are provided ──────────────────── - class(getGithub("contributors", "rapbase")) not equal to "character". - 1/1 mismatches - x[1]: "NULL" - y[1]: "character" - ── Failure ('test-github.R:10:3'): key can be provided ───────────────────────── - grepl("ssh-rsa", getGithub("keys", "areedv")) is not TRUE - - `actual`: - `expected`: TRUE - - [ FAIL 2 | WARN 0 | SKIP 37 | PASS 246 ] - Error: Test failures - Execution halted + Error(s) in re-building vignettes: + ... + --- re-building ‘scGOclust_mouse_fly_gut_vignette.Rmd’ using rmarkdown + + Quitting from lines 37-46 [load_input] (scGOclust_mouse_fly_gut_vignette.Rmd) + Error: processing vignette 'scGOclust_mouse_fly_gut_vignette.Rmd' failed with diagnostics: + Timeout was reached: [www.ensembl.org:443] Operation timed out after 10001 milliseconds with 0 bytes received + --- failed re-building ‘scGOclust_mouse_fly_gut_vignette.Rmd’ + + SUMMARY: processing the following file failed: + ‘scGOclust_mouse_fly_gut_vignette.Rmd’ + + Error: Vignette re-building failed. + Execution halted ``` diff --git a/src/version.c b/src/version.c index 779c08a37..a5ea12b12 100644 --- a/src/version.c +++ b/src/version.c @@ -1,7 +1,7 @@ #define R_NO_REMAP #include -const char* vctrs_version = "0.6.2.9000"; +const char* vctrs_version = "0.6.3"; /** * This file records the expected package version in the shared From e88a3e28822fa5bf925048e6bd0b10315f7bd9af Mon Sep 17 00:00:00 2001 From: DavisVaughan Date: Thu, 15 Jun 2023 10:28:53 -0400 Subject: [PATCH 286/312] Increment version number to 0.6.3.9000 --- DESCRIPTION | 2 +- NEWS.md | 2 ++ src/version.c | 2 +- 3 files changed, 4 insertions(+), 2 deletions(-) diff --git a/DESCRIPTION b/DESCRIPTION index 43be7730d..5a70584ea 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -1,6 +1,6 @@ Package: vctrs Title: Vector Helpers -Version: 0.6.3 +Version: 0.6.3.9000 Authors@R: c( person("Hadley", "Wickham", , "hadley@posit.co", role = "aut"), person("Lionel", "Henry", , "lionel@posit.co", role = "aut"), diff --git a/NEWS.md b/NEWS.md index 8071b9a3a..64c58c221 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,3 +1,5 @@ +# vctrs (development version) + # vctrs 0.6.3 * Fixed an issue where certain ALTREP row names were being materialized when diff --git a/src/version.c b/src/version.c index a5ea12b12..806ba8e51 100644 --- a/src/version.c +++ b/src/version.c @@ -1,7 +1,7 @@ #define R_NO_REMAP #include -const char* vctrs_version = "0.6.3"; +const char* vctrs_version = "0.6.3.9000"; /** * This file records the expected package version in the shared From f4c8f777672ee91fc837b4246e765adf43ddf574 Mon Sep 17 00:00:00 2001 From: Davis Vaughan Date: Thu, 10 Aug 2023 14:56:00 -0400 Subject: [PATCH 287/312] Fix `vec_order_info()` when there are zero columns (#1866) * Push a group size in the 0 column early exit case * NEWS bullet --- NEWS.md | 16 +++++++++------- src/order.c | 3 +++ tests/testthat/test-order.R | 23 +++++++++++++++++++++++ tests/testthat/test-rank.R | 16 ++++++++++++++++ 4 files changed, 51 insertions(+), 7 deletions(-) diff --git a/NEWS.md b/NEWS.md index 64c58c221..c94ce406e 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,5 +1,7 @@ # vctrs (development version) +* Fixed an issue with `vec_rank()` and 0-column data frames (#1863). + # vctrs 0.6.3 * Fixed an issue where certain ALTREP row names were being materialized when @@ -56,7 +58,7 @@ `multiple = "warning"`, which have been removed from the documentation and silently soft-deprecated. Official deprecation for those options will start in a future release (#1791). - + * `vec_locate_matches()` has changed its default `needles_arg` and `haystack_arg` values from `""` to `"needles"` and `"haystack"`, respectively. This generally generates more informative error messages (#1792). @@ -70,7 +72,7 @@ * The `numeric_version` type from base R is now better supported in equality, comparison, and order based operations (tidyverse/dplyr#6680). - + * R >=3.5.0 is now explicitly required. This is in line with the tidyverse policy of supporting the [5 most recent versions of R](https://www.tidyverse.org/blog/2019/04/r-version-support/). @@ -79,7 +81,7 @@ * New `vec_expand_grid()`, which is a lower level helper that is similar to `tidyr::expand_grid()` (#1325). - + * New `vec_set_intersect()`, `vec_set_difference()`, `vec_set_union()`, and `vec_set_symmetric_difference()` which compute set operations like `intersect()`, `setdiff()`, and `union()`, but the vctrs variants don't strip @@ -146,7 +148,7 @@ like specifying `repair = "unique", quiet = TRUE`. When the `"*_quiet"` options are used, any setting of `quiet` is silently overridden (@jennybc, #1629). - + `"unique_quiet"` and `"universal_quiet"` are also newly accepted for the name repair argument of several other functions that do not expose a `quiet` argument: `data_frame()`, `df_list()`, `vec_c()`, `list_unchop()`, @@ -464,11 +466,11 @@ to implement, but if your class has a static prototype, you might consider implementing a custom `vec_ptype()` method that returns a constant to improve performance in some cases (such as common type imputation). - + * New `vec_detect_complete()`, inspired by `stats::complete.cases()`. For most vectors, this is identical to `!vec_equal_na()`. For data frames and matrices, this detects rows that only contain non-missing values. - + * `vec_order()` can now order complex vectors (#1330). * Removed dependency on digest in favor of `rlang::hash()`. @@ -477,7 +479,7 @@ when used as a data frame column (#1318). * `register_s3()` is now licensed with the "unlicense" which makes it very - clear that it's fine to copy and paste into your own package + clear that it's fine to copy and paste into your own package (@maxheld83, #1254). # vctrs 0.3.6 diff --git a/src/order.c b/src/order.c index cb7e48783..51d06151d 100644 --- a/src/order.c +++ b/src/order.c @@ -3971,6 +3971,9 @@ void df_order_internal(SEXP x, // Special case no columns if (n_cols == 0) { init_order(p_order); + if (size != 0) { + groups_size_maybe_push(size, p_group_infos); + } return; } diff --git a/tests/testthat/test-order.R b/tests/testthat/test-order.R index d64cd5ebb..97aafc583 100644 --- a/tests/testthat/test-order.R +++ b/tests/testthat/test-order.R @@ -1275,6 +1275,29 @@ test_that("Indistinct NA and NaN are reported in the same group", { expect_identical(info[[3]], 2L) }) +# ------------------------------------------------------------------------------ +# `vec_order_info()` + +test_that("Zero column data frames with >0 rows work (#1863)", { + # All rows are treated as being from the same group + x <- data_frame(.size = 5) + info <- vec_order_info(x) + + expect_identical(info[[1]], 1:5) # Order + expect_identical(info[[2]], 5L) # Group sizes + expect_identical(info[[3]], 5L) # Max group size +}) + +test_that("Zero column data frames with exactly 0 rows work (#1863)", { + # This is a particularly special case, since we don't actually push a group size + x <- data_frame(.size = 0L) + info <- vec_order_info(x) + + expect_identical(info[[1]], integer()) + expect_identical(info[[2]], integer()) + expect_identical(info[[3]], 0L) +}) + # ------------------------------------------------------------------------------ # vec_sort diff --git a/tests/testthat/test-rank.R b/tests/testthat/test-rank.R index d1744bd8f..558173e8a 100644 --- a/tests/testthat/test-rank.R +++ b/tests/testthat/test-rank.R @@ -63,6 +63,22 @@ test_that("works with data frames", { expect_identical(vec_rank(df, ties = "sequential"), c(2L, 3L, 1L, 4L, 5L)) }) +test_that("works with data frames with 0 columns and >0 rows (#1863)", { + # All rows are treated as being from the same group + df <- data_frame(.size = 5) + + expect_identical(vec_rank(df, ties = "min"), c(1L, 1L, 1L, 1L, 1L)) + expect_identical(vec_rank(df, ties = "sequential"), c(1L, 2L, 3L, 4L, 5L)) + expect_identical(vec_rank(df, ties = "sequential", direction = "desc"), c(1L, 2L, 3L, 4L, 5L)) +}) + +test_that("works with data frames with 0 columns and 0 rows (#1863)", { + df <- data_frame(.size = 0) + + expect_identical(vec_rank(df, ties = "min"), integer()) + expect_identical(vec_rank(df, ties = "sequential"), integer()) +}) + test_that("can control the direction per column", { df <- data_frame( x = c(1, 2, 1, 2, 2), From 363aa08aa12be6afabfb9d2dc0f2832734488b5e Mon Sep 17 00:00:00 2001 From: Davis Vaughan Date: Fri, 11 Aug 2023 11:51:22 -0400 Subject: [PATCH 288/312] Update rlang C library (#1868) --- src/rlang/globals.c | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/rlang/globals.c b/src/rlang/globals.c index 2472a8053..fa8ffac85 100644 --- a/src/rlang/globals.c +++ b/src/rlang/globals.c @@ -28,7 +28,7 @@ void r_init_library_globals(r_obj* ns) { r_globals.na_lgl = NA_LOGICAL; r_globals.na_int = NA_INTEGER; r_globals.na_dbl = NA_REAL; - r_globals.na_cpl = (r_complex) { NA_REAL, NA_REAL }; + r_globals.na_cpl = (r_complex) { .r = NA_REAL, .i = NA_REAL }; r_globals.na_str = NA_STRING; r_preserve_global(r_chrs.empty_string = r_chr("")); From 94da308819e345804ad4df9ba386bd7161e30c95 Mon Sep 17 00:00:00 2001 From: Davis Vaughan Date: Fri, 11 Aug 2023 11:51:32 -0400 Subject: [PATCH 289/312] Use member names when initializing (#1867) --- src/type-complex.h | 8 ++++---- 1 file changed, 4 insertions(+), 4 deletions(-) diff --git a/src/type-complex.h b/src/type-complex.h index 94fb919a6..93521e414 100644 --- a/src/type-complex.h +++ b/src/type-complex.h @@ -24,18 +24,18 @@ r_complex cpl_normalise_missing(r_complex x) { case VCTRS_DBL_number: switch (i_type) { case VCTRS_DBL_number: return x; - case VCTRS_DBL_missing: return (r_complex) {na, na}; - case VCTRS_DBL_nan: return (r_complex) {nan, nan}; + case VCTRS_DBL_missing: return (r_complex) { .r = na, .i = na}; + case VCTRS_DBL_nan: return (r_complex) { .r = nan, .i = nan}; } case VCTRS_DBL_missing: switch (i_type) { - case VCTRS_DBL_number: return (r_complex) {na, na}; + case VCTRS_DBL_number: return (r_complex) { .r = na, .i = na}; case VCTRS_DBL_missing: return x; case VCTRS_DBL_nan: return x; } case VCTRS_DBL_nan: switch (i_type) { - case VCTRS_DBL_number: return (r_complex) {nan, nan}; + case VCTRS_DBL_number: return (r_complex) { .r = nan, .i = nan}; case VCTRS_DBL_missing: return x; case VCTRS_DBL_nan: return x; } From fc09bc3476e2ea64472480e35adfb254d35e4f9d Mon Sep 17 00:00:00 2001 From: Davis Vaughan Date: Fri, 11 Aug 2023 11:55:05 -0400 Subject: [PATCH 290/312] Update to R 4.3 way of printing empty factors --- man/theory-faq-coercion.Rd | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/man/theory-faq-coercion.Rd b/man/theory-faq-coercion.Rd index 62273f4a9..606acd748 100644 --- a/man/theory-faq-coercion.Rd +++ b/man/theory-faq-coercion.Rd @@ -92,7 +92,7 @@ character vectors than to round numbers: \if{html}{\out{
}}\preformatted{# Two factors are compatible vec_ptype2(factor("a"), factor("b")) -#> factor(0) +#> factor() #> Levels: a b # Factors are compatible with a character @@ -141,11 +141,11 @@ the inputs are permuted. This is not always possible, for example factor levels are aggregated in order: \if{html}{\out{
}}\preformatted{vec_ptype2(factor(c("a", "c")), factor("b")) -#> factor(0) +#> factor() #> Levels: a c b vec_ptype2(factor("b"), factor(c("a", "c"))) -#> factor(0) +#> factor() #> Levels: b a c }\if{html}{\out{
}} From 5dad33620c8f5e72400ee1d0ea86be8ec3ad5fe5 Mon Sep 17 00:00:00 2001 From: Davis Vaughan Date: Mon, 14 Aug 2023 09:17:05 -0400 Subject: [PATCH 291/312] Add a class to the `vec_locate_matches()` overflow error (#1869) * Class the `vec_locate_matches()` overflow error * NEWS bullet --- NEWS.md | 3 +++ R/match.R | 24 +++++++++++++++++++++++- src/decl/match-decl.h | 2 +- src/match.c | 24 +++++++++++++++++------- src/utils.c | 2 ++ src/utils.h | 1 + tests/testthat/_snaps/match.md | 6 +++--- tests/testthat/test-match.R | 2 +- 8 files changed, 51 insertions(+), 13 deletions(-) diff --git a/NEWS.md b/NEWS.md index c94ce406e..6a344f21b 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,5 +1,8 @@ # vctrs (development version) +* Added a class to the `vec_locate_matches()` error that is thrown when an + overflow would otherwise occur (#1845). + * Fixed an issue with `vec_rank()` and 0-column data frames (#1863). # vctrs 0.6.3 diff --git a/R/match.R b/R/match.R index edf7cc1e1..faa4b59a0 100644 --- a/R/match.R +++ b/R/match.R @@ -356,8 +356,9 @@ compute_nesting_container_info <- function(x, condition) { # ------------------------------------------------------------------------------ -stop_matches <- function(class = NULL, ..., call = caller_env()) { +stop_matches <- function(message = NULL, class = NULL, ..., call = caller_env()) { stop_vctrs( + message = message, class = c(class, "vctrs_error_matches"), ..., call = call @@ -375,6 +376,27 @@ warn_matches <- function(message, class = NULL, ..., call = caller_env()) { # ------------------------------------------------------------------------------ +stop_matches_overflow <- function(size, call) { + size <- format(size, scientific = FALSE) + + # Pre-generating the message in this case because we want to use + # `.internal = TRUE` and that doesn't work with lazy messages + message <- c( + "Match procedure results in an allocation larger than 2^31-1 elements.", + i = glue::glue("Attempted allocation size was {size}.") + ) + + stop_matches( + message = message, + class = "vctrs_error_matches_overflow", + size = size, + call = call, + .internal = TRUE + ) +} + +# ------------------------------------------------------------------------------ + stop_matches_nothing <- function(i, needles_arg, haystack_arg, call) { stop_matches( class = "vctrs_error_matches_nothing", diff --git a/src/decl/match-decl.h b/src/decl/match-decl.h index e2e12868e..51d897986 100644 --- a/src/decl/match-decl.h +++ b/src/decl/match-decl.h @@ -214,7 +214,7 @@ static inline r_ssize midpoint(r_ssize lhs, r_ssize rhs); static inline -void stop_matches_overflow(double size); +void stop_matches_overflow(double size, struct r_lazy call); static inline void stop_matches_nothing(r_ssize i, diff --git a/src/match.c b/src/match.c index caad346da..61faff2a5 100644 --- a/src/match.c +++ b/src/match.c @@ -1637,7 +1637,7 @@ r_obj* expand_compact_indices(const int* v_o_haystack, if (dbl_size_out > R_LEN_T_MAX) { // TODO: Update this after a switch to long vector support - stop_matches_overflow(dbl_size_out); + stop_matches_overflow(dbl_size_out, error_call); } size_out = r_double_as_ssize(dbl_size_out); @@ -2654,12 +2654,22 @@ r_ssize midpoint(r_ssize lhs, r_ssize rhs) { // ----------------------------------------------------------------------------- static inline -void stop_matches_overflow(double size) { - r_stop_internal( - "Match procedure results in an allocation larger than 2^31-1 elements. " - "Attempted allocation size was %.0lf.", - size - ); +void stop_matches_overflow(double size, struct r_lazy call) { + r_obj* syms[3] = { + syms_size, + syms_call, + NULL + }; + r_obj* args[3] = { + KEEP(r_dbl(size)), + KEEP(r_lazy_eval_protect(call)), + NULL + }; + + r_obj* ffi_call = KEEP(r_call_n(syms_stop_matches_overflow, syms, args)); + Rf_eval(ffi_call, vctrs_ns_env); + + never_reached("stop_matches_overflow"); } static inline diff --git a/src/utils.c b/src/utils.c index 5a7d1313b..e8b0810fd 100644 --- a/src/utils.c +++ b/src/utils.c @@ -1584,6 +1584,7 @@ SEXP syms_s3_fallback = NULL; SEXP syms_stop_incompatible_type = NULL; SEXP syms_stop_incompatible_size = NULL; SEXP syms_stop_assert_size = NULL; +SEXP syms_stop_matches_overflow = NULL; SEXP syms_stop_matches_nothing = NULL; SEXP syms_stop_matches_remaining = NULL; SEXP syms_stop_matches_incomplete = NULL; @@ -1865,6 +1866,7 @@ void vctrs_init_utils(SEXP ns) { syms_stop_incompatible_type = Rf_install("stop_incompatible_type"); syms_stop_incompatible_size = Rf_install("stop_incompatible_size"); syms_stop_assert_size = Rf_install("stop_assert_size"); + syms_stop_matches_overflow = Rf_install("stop_matches_overflow"); syms_stop_matches_nothing = Rf_install("stop_matches_nothing"); syms_stop_matches_remaining = Rf_install("stop_matches_remaining"); syms_stop_matches_incomplete = Rf_install("stop_matches_incomplete"); diff --git a/src/utils.h b/src/utils.h index af39487a5..4b67cce45 100644 --- a/src/utils.h +++ b/src/utils.h @@ -486,6 +486,7 @@ extern SEXP syms_s3_fallback; extern SEXP syms_stop_incompatible_type; extern SEXP syms_stop_incompatible_size; extern SEXP syms_stop_assert_size; +extern SEXP syms_stop_matches_overflow; extern SEXP syms_stop_matches_nothing; extern SEXP syms_stop_matches_remaining; extern SEXP syms_stop_matches_incomplete; diff --git a/tests/testthat/_snaps/match.md b/tests/testthat/_snaps/match.md index ee88db809..ab3470328 100644 --- a/tests/testthat/_snaps/match.md +++ b/tests/testthat/_snaps/match.md @@ -670,10 +670,10 @@ Code (expect_error(vec_locate_matches(1:1e+07, 1:1e+07, condition = ">="))) Output - + Error in `vec_locate_matches()`: - ! Match procedure results in an allocation larger than 2^31-1 elements. Attempted allocation size was 50000005000000. - i In file 'match.c' at line . + ! Match procedure results in an allocation larger than 2^31-1 elements. + i Attempted allocation size was 50000005000000. i This is an internal error that was detected in the vctrs package. Please report it at with a reprex () and the full backtrace. diff --git a/tests/testthat/test-match.R b/tests/testthat/test-match.R index 963e7edc4..32fa43fb7 100644 --- a/tests/testthat/test-match.R +++ b/tests/testthat/test-match.R @@ -1791,7 +1791,7 @@ test_that("potential overflow on large output size is caught informatively", { # intermediate `r_ssize` will be too large skip_if(.Machine$sizeof.pointer < 8L, message = "No long vector support") - expect_snapshot(transform = scrub_internal_error_line_number, { + expect_snapshot({ (expect_error(vec_locate_matches(1:1e7, 1:1e7, condition = ">="))) }) }) From 8bbd8c4a69a9b3e2c42aa752c5339f949562af96 Mon Sep 17 00:00:00 2001 From: George Stagg Date: Thu, 17 Aug 2023 14:42:05 +0100 Subject: [PATCH 292/312] Make vctrs_init_altrep_lazy_character consistent (#1872) Required for Wasm compatability. --- src/init.c | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/init.c b/src/init.c index 9b338e3df..3f92af630 100644 --- a/src/init.c +++ b/src/init.c @@ -189,7 +189,7 @@ void vctrs_init_altrep_rle(DllInfo*); // Defined in altrep-lazy-character.c extern r_obj* ffi_altrep_new_lazy_character(r_obj*); extern r_obj* ffi_altrep_lazy_character_is_materialized(r_obj*); -extern r_obj* vctrs_init_altrep_lazy_character(DllInfo*); +extern void vctrs_init_altrep_lazy_character(DllInfo*); static const R_CallMethodDef CallEntries[] = { {"vctrs_list_get", (DL_FUNC) &vctrs_list_get, 2}, From 9552ebc3eb32463e5f700f2e698c1662fda3424b Mon Sep 17 00:00:00 2001 From: Davis Vaughan Date: Mon, 9 Oct 2023 14:36:04 -0400 Subject: [PATCH 293/312] Update complex tests for R-devel (4.4.0) (#1883) * Update complex tests * NEWS bullet --- NEWS.md | 3 +++ tests/testthat/helper-vctrs.R | 12 +++++++++ tests/testthat/test-slice-assign.R | 4 +-- tests/testthat/test-slice.R | 2 +- tests/testthat/test-type-bare.R | 42 +++++++++++++++++++++++------- 5 files changed, 50 insertions(+), 13 deletions(-) diff --git a/NEWS.md b/NEWS.md index 6a344f21b..4727ce794 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,5 +1,8 @@ # vctrs (development version) +* Fixed an issue with complex vector tests related to changes in R-devel + (#1883). + * Added a class to the `vec_locate_matches()` error that is thrown when an overflow would otherwise occur (#1845). diff --git a/tests/testthat/helper-vctrs.R b/tests/testthat/helper-vctrs.R index 98f8fe793..3c013c6de 100644 --- a/tests/testthat/helper-vctrs.R +++ b/tests/testthat/helper-vctrs.R @@ -56,3 +56,15 @@ expect_equal <- function(object, expected, ..., raw2 <- function(...) { as.raw(list_unchop(list2(...), ptype = integer())) } +cpl2 <- function(...) { + # R 4.4.0 changed `as.complex(NA_real/integer/logical)` so that it always uses + # a `0` in the imaginary slot. While this is reasonable, it is annoying for + # comparison purposes in tests, where we typically propagate the `NA`. As of + # rlang 1.1.1, `cpl()` inherits this behavior change so we have a custom version + # here that works the same on all R versions. + # https://github.com/wch/r-source/commit/1a2aea9ac3c216fea718f33f712764afc34f6ee8 + out <- list2(...) + out <- as.complex(out) + out[is.na(out)] <- complex(real = NA_real_, imaginary = NA_real_) + out +} diff --git a/tests/testthat/test-slice-assign.R b/tests/testthat/test-slice-assign.R index d2c56ecfd..86fe6766e 100644 --- a/tests/testthat/test-slice-assign.R +++ b/tests/testthat/test-slice-assign.R @@ -681,7 +681,7 @@ test_that("can assign shaped base vectors with compact seqs", { expect_identical(vec_assign_seq(mat(lgl(1, 0, 1)), NA, start, size, increasing), mat(lgl(1, NA, NA))) expect_identical(vec_assign_seq(mat(int(1, 2, 3)), NA, start, size, increasing), mat(int(1, NA, NA))) expect_identical(vec_assign_seq(mat(dbl(1, 2, 3)), NA, start, size, increasing), mat(dbl(1, NA, NA))) - expect_identical(vec_assign_seq(mat(cpl(1, 2, 3)), NA, start, size, increasing), mat(cpl(1, NA, NA))) + expect_identical(vec_assign_seq(mat(cpl2(1, 2, 3)), NA, start, size, increasing), mat(cpl2(1, NA, NA))) expect_identical(vec_assign_seq(mat(chr("1", "2", "3")), NA, start, size, increasing), mat(chr("1", NA, NA))) expect_identical(vec_assign_seq(mat(raw2(1, 2, 3)), raw2(1), start, size, increasing), mat(raw2(1, 1, 1))) expect_identical(vec_assign_seq(mat(list(1, 2, 3)), NA, start, size, increasing), mat(list(1, NULL, NULL))) @@ -695,7 +695,7 @@ test_that("can assign shaped base vectors with decreasing compact seqs", { expect_identical(vec_assign_seq(mat(lgl(1, 0, 1)), NA, start, size, increasing), mat(lgl(1, NA, NA))) expect_identical(vec_assign_seq(mat(int(1, 2, 3)), NA, start, size, increasing), mat(int(1, NA, NA))) expect_identical(vec_assign_seq(mat(dbl(1, 2, 3)), NA, start, size, increasing), mat(dbl(1, NA, NA))) - expect_identical(vec_assign_seq(mat(cpl(1, 2, 3)), NA, start, size, increasing), mat(cpl(1, NA, NA))) + expect_identical(vec_assign_seq(mat(cpl2(1, 2, 3)), NA, start, size, increasing), mat(cpl2(1, NA, NA))) expect_identical(vec_assign_seq(mat(chr("1", "2", "3")), NA, start, size, increasing), mat(chr("1", NA, NA))) expect_identical(vec_assign_seq(mat(raw2(1, 2, 3)), raw2(1), start, size, increasing), mat(raw2(1, 1, 1))) expect_identical(vec_assign_seq(mat(list(1, 2, 3)), NA, start, size, increasing), mat(list(1, NULL, NULL))) diff --git a/tests/testthat/test-slice.R b/tests/testthat/test-slice.R index 3d8fe076f..e397be9dc 100644 --- a/tests/testthat/test-slice.R +++ b/tests/testthat/test-slice.R @@ -38,7 +38,7 @@ test_that("can subset with missing indices", { expect_identical(vec_slice(lgl(1, 0, 1), i), lgl(0, NA)) expect_identical(vec_slice(int(1, 2, 3), i), int(2, NA)) expect_identical(vec_slice(dbl(1, 2, 3), i), dbl(2, NA)) - expect_identical(vec_slice(cpl(1, 2, 3), i), cpl(2, NA)) + expect_identical(vec_slice(cpl2(1, 2, 3), i), cpl2(2, NA)) expect_identical(vec_slice(chr("1", "2", "3"), i), c("2", NA)) expect_identical(vec_slice(raw2(1, 2, 3), i), raw2(2, 0)) expect_identical(vec_slice(list(1, 2, 3), i), list(2, NULL)) diff --git a/tests/testthat/test-type-bare.R b/tests/testthat/test-type-bare.R index 64613b554..a1f8913b2 100644 --- a/tests/testthat/test-type-bare.R +++ b/tests/testthat/test-type-bare.R @@ -243,13 +243,27 @@ test_that("safe casts to complex works", { }) test_that("NA casts work as expected", { + # This goes through a special path for expect_equal(vec_cast(lgl(NA), cpl()), NA_complex_) - expect_equal(vec_cast(int(NA), cpl()), NA_complex_) # TODO: Use our own cast routines here? - # `as.complex(NA_real_)` and `Rf_CoerceVector(NA_real_)` coerce to - # `complex(real = NA_real_, imaginary = 0)` for some reason, but this may - # change in the future https://stat.ethz.ch/pipermail/r-devel/2023-April/082545.html + # It isn't great that this logical `NA` cast returns a different `NA` + # than the one above with just `lgl(NA)` (which is seen as unspecified). i.e. + # check the `Im()` slot between the two in R >=4.4.0. We can fix this with our + # own cast routines rather than using `vec_coerce_bare()`. + expect_type(vec_cast(lgl(NA, TRUE), cpl()), "complex") + expect_identical(is.na(vec_cast(lgl(NA, TRUE), cpl())), c(TRUE, FALSE)) + + # TODO: Use our own cast routines here? + # `as.complex(NA/NA_real_/NA_integer_)` and `Rf_CoerceVector(NA/NA_real_/NA_integer_)` + # have gone back and forth about what they return in the `Im()` slot. In some + # R versions they return `0` and in others they return `NA_real_`. + # https://stat.ethz.ch/pipermail/r-devel/2023-April/082545.html + # https://stat.ethz.ch/pipermail/r-devel/2023-September/082864.html + # expect_equal(vec_cast(int(NA), cpl()), NA_complex_) + expect_type(vec_cast(int(NA), cpl()), "complex") + expect_identical(is.na(vec_cast(int(NA), cpl())), TRUE) + # expect_equal(vec_cast(dbl(NA), cpl()), NA_complex_) expect_type(vec_cast(dbl(NA), cpl()), "complex") expect_identical(is.na(vec_cast(dbl(NA), cpl())), TRUE) @@ -263,13 +277,21 @@ test_that("Shaped NA casts work as expected", { exp_mat <- mat(NA_complex_) to_mat <- matrix(cpl()) - expect_equal(vec_cast(mat(lgl(NA)), to_mat), exp_mat) - expect_equal(vec_cast(mat(int(NA)), to_mat), exp_mat) - # TODO: Use our own cast routines here? - # `as.complex(NA_real_)` and `Rf_CoerceVector(NA_real_)` coerce to - # `complex(real = NA_real_, imaginary = 0)` for some reason, but this may - # change in the future https://stat.ethz.ch/pipermail/r-devel/2023-April/082545.html + # `as.complex(NA/NA_real_/NA_integer_)` and `Rf_CoerceVector(NA/NA_real_/NA_integer_)` + # have gone back and forth about what they return in the `Im()` slot. In some + # R versions they return `0` and in others they return `NA_real_`. + # https://stat.ethz.ch/pipermail/r-devel/2023-April/082545.html + # https://stat.ethz.ch/pipermail/r-devel/2023-September/082864.html + + # expect_equal(vec_cast(mat(lgl(NA)), to_mat), exp_mat) + expect_type(vec_cast(mat(lgl(NA)), to_mat), "complex") + expect_identical(is.na(vec_cast(mat(lgl(NA)), to_mat)), matrix(TRUE)) + + # expect_equal(vec_cast(mat(int(NA)), to_mat), exp_mat) + expect_type(vec_cast(mat(int(NA)), to_mat), "complex") + expect_identical(is.na(vec_cast(mat(int(NA)), to_mat)), matrix(TRUE)) + # expect_equal(vec_cast(mat(dbl(NA)), to_mat), exp_mat) expect_type(vec_cast(mat(dbl(NA)), to_mat), "complex") expect_identical(is.na(vec_cast(mat(dbl(NA)), to_mat)), matrix(TRUE)) From e16c2bed75be08ea3c2659082de2a7819bcf94ae Mon Sep 17 00:00:00 2001 From: Davis Vaughan Date: Tue, 10 Oct 2023 15:00:51 -0400 Subject: [PATCH 294/312] ALTREP list performance fix: Never clone in `vec_clone_referenced()` when `owned` (#1884) * Never clone when `owned` * NEWS bullet * Add number --- NEWS.md | 3 +++ src/owned.h | 9 +-------- src/slice-assign.c | 8 +++++--- 3 files changed, 9 insertions(+), 11 deletions(-) diff --git a/NEWS.md b/NEWS.md index 4727ce794..7e3f486dc 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,5 +1,8 @@ # vctrs (development version) +* Fixed a performance issue with `vec_c()` and ALTREP vectors (in particular, + the new ALTREP list vectors in R-devel) (#1884). + * Fixed an issue with complex vector tests related to changes in R-devel (#1883). diff --git a/src/owned.h b/src/owned.h index 419b73fc6..3d8d2268a 100644 --- a/src/owned.h +++ b/src/owned.h @@ -11,15 +11,8 @@ static inline enum vctrs_owned vec_owned(SEXP x) { } // Wrapper around `r_clone_referenced()` that only attempts to clone if -// we indicate that we don't own `x`, or if `x` is ALTREP. -// If `x` is ALTREP, we must unconditionally clone it before dereferencing, -// otherwise we get a pointer into the ALTREP internals rather than into the -// object it truly represents. +// we indicate that we don't own `x` static inline SEXP vec_clone_referenced(SEXP x, const enum vctrs_owned owned) { - if (ALTREP(x)) { - return r_clone_referenced(x); - } - if (owned == VCTRS_OWNED_false) { return r_clone_referenced(x); } else { diff --git a/src/slice-assign.c b/src/slice-assign.c index ab340c9cd..9508f0abe 100644 --- a/src/slice-assign.c +++ b/src/slice-assign.c @@ -98,9 +98,11 @@ r_obj* vec_assign_switch(r_obj* proxy, // on a number of factors. // // - If a fallback is required, the `proxy` is duplicated at the R level. -// - If `owned` is `VCTRS_OWNED_true`, the `proxy` is typically not duplicated. -// However, if it is an ALTREP object, it is duplicated because we need to be -// able to assign into the object it represents, not the ALTREP r_obj* itself. +// - If `owned` is `VCTRS_OWNED_true`, the `proxy` is not duplicated. If the +// `proxy` happens to be an ALTREP object, materialization will be forced when +// we do the actual assignment, but this should really only happen with +// cheap-to-materialize ALTREP "wrapper" objects since we've claimed that we +// "own" the `proxy`. // - If `owned` is `VCTRS_OWNED_false`, the `proxy` is only // duplicated if it is referenced, i.e. `MAYBE_REFERENCED()` returns `true`. // From 883737a38020e0827abc20271a153804ae4ac906 Mon Sep 17 00:00:00 2001 From: Chao Cheng <413557584@qq.com> Date: Wed, 11 Oct 2023 03:06:41 +0800 Subject: [PATCH 295/312] Fix a typo in type-size.Rmd (#1852) --- vignettes/type-size.Rmd | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/vignettes/type-size.Rmd b/vignettes/type-size.Rmd index ff3ceee44..008ee7709 100644 --- a/vignettes/type-size.Rmd +++ b/vignettes/type-size.Rmd @@ -325,7 +325,7 @@ vec_size_common(integer(), 1) vctrs obeys a stricter set of recycling rules than base R. Vectors of size 1 are recycled to any other size. All other size combinations will generate an error. This strictness prevents common mistakes like `dest == c("IAH", "HOU"))`, at the cost of occasionally requiring an explicit calls to `rep()`. -```{r, echo = FALSE, fig.cap="Summary of vctrs recycling rules. X indicates n error"} +```{r, echo = FALSE, fig.cap="Summary of vctrs recycling rules. X indicates an error"} knitr::include_graphics("../man/figures/sizes-recycling.png", dpi = 300) ``` From 5852e42be5a42f2f9e7dc0b7ebcd6291daeb5b8e Mon Sep 17 00:00:00 2001 From: Michael Sumner Date: Wed, 11 Oct 2023 06:07:11 +1100 Subject: [PATCH 296/312] update s3-vector.Rmd: possessive 'its' (#1848) very minor, few cases of its/it's --- vignettes/s3-vector.Rmd | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/vignettes/s3-vector.Rmd b/vignettes/s3-vector.Rmd index 79434c849..dce4b1620 100644 --- a/vignettes/s3-vector.Rmd +++ b/vignettes/s3-vector.Rmd @@ -59,7 +59,7 @@ They're collectively demonstrated with a number of simple S3 classes: - Meter: a numeric vector with meter units. This is the simplest possible class with interesting algebraic properties. -- Period and frequency: a pair of classes represent a period, or it's inverse, frequency. +- Period and frequency: a pair of classes represent a period, or its inverse, frequency. This allows us to explore more arithmetic operators. ## Basics @@ -147,7 +147,7 @@ format.vctrs_percent <- function(x, ...) { ```{r, include = FALSE} # As of R 3.5, print.vctr can not find format.percent since it's not in -# it's lexical environment. We fix that problem by manually registering. +# its lexical environment. We fix that problem by manually registering. s3_register("base::format", "vctrs_percent") ``` From c5a8276ba0f8624d15a1214839a2476c282633f1 Mon Sep 17 00:00:00 2001 From: Etienne Bacher <52219252+etiennebacher@users.noreply.github.com> Date: Tue, 10 Oct 2023 19:08:54 +0000 Subject: [PATCH 297/312] Typo in developer FAQ (#1836) * Typo in developer FAQ * Document --------- Co-authored-by: Davis Vaughan --- man/faq/developer/howto-coercion.Rmd | 2 +- man/howto-faq-coercion.Rd | 4 ++-- 2 files changed, 3 insertions(+), 3 deletions(-) diff --git a/man/faq/developer/howto-coercion.Rmd b/man/faq/developer/howto-coercion.Rmd index a0da823aa..102e597e0 100644 --- a/man/faq/developer/howto-coercion.Rmd +++ b/man/faq/developer/howto-coercion.Rmd @@ -168,7 +168,7 @@ knitr_local_registration("vctrs::vec_ptype2", "double.my_natural") Most of the time, inputs are incompatible because they have different classes for which no `vec_ptype2()` method is implemented. More rarely, inputs could be incompatible because of their attributes. In that case incompatibility is signalled by calling `stop_incompatible_type()`. -In the following example, we implement a self-self ptype2 method for a hypothetical subclass of `` that has stricter combination semantics. The method throws when the levels of the two factors are not compatible. +In the following example, we implement a self-self ptype2 method for a hypothetical subclass of `` that has stricter combination semantics. The method throws an error when the levels of the two factors are not compatible. ```{r, eval = FALSE} #' @export diff --git a/man/howto-faq-coercion.Rd b/man/howto-faq-coercion.Rd index a5fffa849..d034050eb 100644 --- a/man/howto-faq-coercion.Rd +++ b/man/howto-faq-coercion.Rd @@ -180,8 +180,8 @@ incompatibility is signalled by calling \code{stop_incompatible_type()}. In the following example, we implement a self-self ptype2 method for a hypothetical subclass of \verb{} that has stricter combination -semantics. The method throws when the levels of the two factors are not -compatible. +semantics. The method throws an error when the levels of the two factors +are not compatible. \if{html}{\out{
}}\preformatted{#' @export vec_ptype2.my_strict_factor.my_strict_factor <- function(x, y, ..., x_arg = "", y_arg = "") \{ From e2291d0e4e8033b718731e132205b598774e63e8 Mon Sep 17 00:00:00 2001 From: Davis Vaughan Date: Wed, 11 Oct 2023 09:53:47 -0400 Subject: [PATCH 298/312] Make vector recycling rules its own FAQ (#1885) * Make vector recycling rules its own FAQ * Add in extra new line * Use manual pkgdown redirects --- R/bind.R | 2 +- R/faq-developer.R | 11 +++ R/recycle.R | 74 +------------------ R/rep.R | 2 +- R/size.R | 2 +- R/slice-interleave.R | 2 +- R/type-data-frame.R | 2 +- _pkgdown.yml | 7 ++ man/data_frame.Rd | 2 +- man/df_list.Rd | 2 +- man/faq/developer/theory-recycling.Rmd | 59 +++++++++++++++ ...cling_rules.Rd => theory-faq-recycling.Rd} | 42 +++++------ man/vec-rep.Rd | 2 +- man/vec_bind.Rd | 2 +- man/vec_interleave.Rd | 2 +- man/vec_recycle.Rd | 2 +- man/vec_size.Rd | 2 +- 17 files changed, 109 insertions(+), 108 deletions(-) create mode 100644 man/faq/developer/theory-recycling.Rmd rename man/{vector_recycling_rules.Rd => theory-faq-recycling.Rd} (75%) diff --git a/R/bind.R b/R/bind.R index 45a1b295b..296a689e3 100644 --- a/R/bind.R +++ b/R/bind.R @@ -187,7 +187,7 @@ vec_rbind <- fn_inline_formals(vec_rbind, ".name_repair") #' @rdname vec_bind #' @param .size If, `NULL`, the default, will determine the number of rows in #' `vec_cbind()` output by using the tidyverse [recycling -#' rules][vector_recycling_rules]. +#' rules][theory-faq-recycling]. #' #' Alternatively, specify the desired number of rows, and any inputs of length #' 1 will be recycled appropriately. diff --git a/R/faq-developer.R b/R/faq-developer.R index b1fc0c98e..b9f2ec6b3 100644 --- a/R/faq-developer.R +++ b/R/faq-developer.R @@ -12,6 +12,17 @@ NULL #' @name theory-faq-coercion NULL +# Also see the `redirects:` section in `_pkgdown.yml` +# for `vector_recycling_rules.html` + +#' FAQ - How does recycling work in vctrs and the tidyverse? +#' +#' @includeRmd man/faq/developer/theory-recycling.Rmd description +#' +#' @name theory-faq-recycling +#' @aliases vector_recycling_rules +NULL + #' FAQ - How to implement ptype2 and cast methods? #' #' @includeRmd man/faq/developer/howto-coercion.Rmd description diff --git a/R/recycle.R b/R/recycle.R index d7e7bbf93..6c8a69fe7 100644 --- a/R/recycle.R +++ b/R/recycle.R @@ -1,80 +1,8 @@ -#' Recycling rules used by r-lib and the tidyverse -#' -#' @description -#' Recycling describes the concept of repeating elements of one vector to match -#' the size of another. There are two rules that underlie the "tidyverse" -#' recycling rules: -#' -#' - Vectors of size 1 will be recycled to the size of any other vector -#' -#' - Otherwise, all vectors must have the same size -#' -#' @section Examples: -#' -#' ```{r, warning = FALSE, message = FALSE, include = FALSE} -#' library(tibble) -#' ``` -#' -#' Vectors of size 1 are recycled to the size of any other vector: -#' -#' ```{r, comment = "#>"} -#' tibble(x = 1:3, y = 1L) -#' ``` -#' -#' This includes vectors of size 0: -#' -#' ```{r, comment = "#>"} -#' tibble(x = integer(), y = 1L) -#' ``` -#' -#' If vectors aren't size 1, they must all be the same size. Otherwise, an error -#' is thrown: -#' -#' ```{r, comment = "#>", error = TRUE} -#' tibble(x = 1:3, y = 4:7) -#' ``` -#' -#' @section vctrs backend: -#' -#' Packages in r-lib and the tidyverse generally use [vec_size_common()] and -#' [vec_recycle_common()] as the backends for handling recycling rules. -#' -#' - `vec_size_common()` returns the common size of multiple vectors, after -#' applying the recycling rules -#' -#' - `vec_recycle_common()` goes one step further, and actually recycles the -#' vectors to their common size -#' -#' ```{r, comment = "#>", error = TRUE} -#' vec_size_common(1:3, "x") -#' -#' vec_recycle_common(1:3, "x") -#' -#' vec_size_common(1:3, c("x", "y")) -#' ``` -#' -#' @section Base R recycling rules: -#' -#' The recycling rules described here are stricter than the ones generally used -#' by base R, which are: -#' -#' - If any vector is length 0, the output will be length 0 -#' -#' - Otherwise, the output will be length `max(length_x, length_y)`, and a -#' warning will be thrown if the length of the longer vector is not an integer -#' multiple of the length of the shorter vector. -#' -#' We explore the base R rules in detail in `vignette("type-size")`. -#' -#' @name vector_recycling_rules -#' @keywords internal -NULL - #' Vector recycling #' #' `vec_recycle(x, size)` recycles a single vector to a given size. #' `vec_recycle_common(...)` recycles multiple vectors to their common size. All -#' functions obey the [vctrs recycling rules][vector_recycling_rules], and will +#' functions obey the [vctrs recycling rules][theory-faq-recycling], and will #' throw an error if recycling is not possible. See [vec_size()] for the precise #' definition of size. #' diff --git a/R/rep.R b/R/rep.R index ac08a1719..7ff9b1003 100644 --- a/R/rep.R +++ b/R/rep.R @@ -36,7 +36,7 @@ #' the entire vector. #' #' For `vec_rep_each()`, an integer vector of the number of times to repeat -#' each element of `x`. `times` will be [recycled][vector_recycling_rules] to +#' each element of `x`. `times` will be [recycled][theory-faq-recycling] to #' the size of `x`. #' @param x_arg,times_arg Argument names for errors. #' diff --git a/R/size.R b/R/size.R index 1ee03f75e..46d287c5c 100644 --- a/R/size.R +++ b/R/size.R @@ -19,7 +19,7 @@ #' to `vec_size()` as [lengths()] is to [length()]. #' #' @seealso [vec_slice()] for a variation of `[` compatible with `vec_size()`, -#' and [vec_recycle()] to [recycle][vector_recycling_rules] vectors to common +#' and [vec_recycle()] to [recycle][theory-faq-recycling] vectors to common #' length. #' @section Invariants: #' * `vec_size(dataframe)` == `vec_size(dataframe[[i]])` diff --git a/R/slice-interleave.R b/R/slice-interleave.R index dd26557ac..0ebf91e95 100644 --- a/R/slice-interleave.R +++ b/R/slice-interleave.R @@ -20,7 +20,7 @@ #' @inheritParams vec_c #' #' @param ... Vectors to interleave. These will be -#' [recycled][vector_recycling_rules] to a common size. +#' [recycled][theory-faq-recycling] to a common size. #' #' @export #' @examples diff --git a/R/type-data-frame.R b/R/type-data-frame.R index 12d29cbbd..b06b3a371 100644 --- a/R/type-data-frame.R +++ b/R/type-data-frame.R @@ -39,7 +39,7 @@ new_data_frame <- fn_inline_formals(new_data_frame, "x") #' #' @section Properties: #' -#' - Inputs are [recycled][vector_recycling_rules] to a common size with +#' - Inputs are [recycled][theory-faq-recycling] to a common size with #' [vec_recycle_common()]. #' #' - With the exception of data frames, inputs are not modified in any way. diff --git a/_pkgdown.yml b/_pkgdown.yml index 812117b9f..6f4073c2a 100644 --- a/_pkgdown.yml +++ b/_pkgdown.yml @@ -131,3 +131,10 @@ reference: - vec_names - vec_as_location - vec_as_subscript + +# Needed to generate a `vector_recycling_rules` page, since it is an `@alias` +# but pkgdown doesn't currently generate pages for aliases. Other packages +# link to this old page name, so we don't want it to disappear. +# https://github.com/r-lib/pkgdown/issues/1876 +redirects: + - ["reference/vector_recycling_rules.html", "reference/theory-faq-recycling.html"] diff --git a/man/data_frame.Rd b/man/data_frame.Rd index 36fae58e7..334e30679 100644 --- a/man/data_frame.Rd +++ b/man/data_frame.Rd @@ -44,7 +44,7 @@ repair for convenience and performance. \section{Properties}{ \itemize{ -\item Inputs are \link[=vector_recycling_rules]{recycled} to a common size with +\item Inputs are \link[=theory-faq-recycling]{recycled} to a common size with \code{\link[=vec_recycle_common]{vec_recycle_common()}}. \item With the exception of data frames, inputs are not modified in any way. Character vectors are never converted to factors, and lists are stored diff --git a/man/df_list.Rd b/man/df_list.Rd index 91f6f2ae3..1ea4117f9 100644 --- a/man/df_list.Rd +++ b/man/df_list.Rd @@ -41,7 +41,7 @@ a helper function for data frame subclasses. \section{Properties}{ \itemize{ -\item Inputs are \link[=vector_recycling_rules]{recycled} to a common size with +\item Inputs are \link[=theory-faq-recycling]{recycled} to a common size with \code{\link[=vec_recycle_common]{vec_recycle_common()}}. \item With the exception of data frames, inputs are not modified in any way. Character vectors are never converted to factors, and lists are stored diff --git a/man/faq/developer/theory-recycling.Rmd b/man/faq/developer/theory-recycling.Rmd new file mode 100644 index 000000000..14046cf98 --- /dev/null +++ b/man/faq/developer/theory-recycling.Rmd @@ -0,0 +1,59 @@ + +```{r, child = "../setup.Rmd", include = FALSE} +``` + +Recycling describes the concept of repeating elements of one vector to match the size of another. There are two rules that underlie the "tidyverse" recycling rules: + +- Vectors of size 1 will be recycled to the size of any other vector + +- Otherwise, all vectors must have the same size + +# Examples + +```{r, warning = FALSE, message = FALSE, include = FALSE} +library(tibble) +``` + +Vectors of size 1 are recycled to the size of any other vector: + +```{r} +tibble(x = 1:3, y = 1L) +``` + +This includes vectors of size 0: + +```{r} +tibble(x = integer(), y = 1L) +``` + +If vectors aren't size 1, they must all be the same size. Otherwise, an error is thrown: + +```{r, error = TRUE} +tibble(x = 1:3, y = 4:7) +``` + +# vctrs backend + +Packages in r-lib and the tidyverse generally use [vec_size_common()] and [vec_recycle_common()] as the backends for handling recycling rules. + +- `vec_size_common()` returns the common size of multiple vectors, after applying the recycling rules + +- `vec_recycle_common()` goes one step further, and actually recycles the vectors to their common size + +```{r, error = TRUE} +vec_size_common(1:3, "x") + +vec_recycle_common(1:3, "x") + +vec_size_common(1:3, c("x", "y")) +``` + +# Base R recycling rules + +The recycling rules described here are stricter than the ones generally used by base R, which are: + +- If any vector is length 0, the output will be length 0 + +- Otherwise, the output will be length `max(length_x, length_y)`, and a warning will be thrown if the length of the longer vector is not an integer multiple of the length of the shorter vector. + +We explore the base R rules in detail in `vignette("type-size")`. diff --git a/man/vector_recycling_rules.Rd b/man/theory-faq-recycling.Rd similarity index 75% rename from man/vector_recycling_rules.Rd rename to man/theory-faq-recycling.Rd index b922747e9..a4f9f6961 100644 --- a/man/vector_recycling_rules.Rd +++ b/man/theory-faq-recycling.Rd @@ -1,20 +1,19 @@ % Generated by roxygen2: do not edit by hand -% Please edit documentation in R/recycle.R -\name{vector_recycling_rules} +% Please edit documentation in R/faq-developer.R +\name{theory-faq-recycling} +\alias{theory-faq-recycling} \alias{vector_recycling_rules} -\title{Recycling rules used by r-lib and the tidyverse} +\title{FAQ - How does recycling work in vctrs and the tidyverse?} \description{ -Recycling describes the concept of repeating elements of one vector to match -the size of another. There are two rules that underlie the "tidyverse" -recycling rules: +Recycling describes the concept of repeating elements of one vector to +match the size of another. There are two rules that underlie the +“tidyverse” recycling rules: \itemize{ \item Vectors of size 1 will be recycled to the size of any other vector \item Otherwise, all vectors must have the same size } } \section{Examples}{ - - Vectors of size 1 are recycled to the size of any other vector: \if{html}{\out{
}}\preformatted{tibble(x = 1:3, y = 1L) @@ -33,8 +32,8 @@ This includes vectors of size 0: #> # i 2 variables: x , y }\if{html}{\out{
}} -If vectors aren't size 1, they must all be the same size. Otherwise, an error -is thrown: +If vectors aren’t size 1, they must all be the same size. Otherwise, an +error is thrown: \if{html}{\out{
}}\preformatted{tibble(x = 1:3, y = 4:7) #> Error in `tibble()`: @@ -46,15 +45,15 @@ is thrown: } \section{vctrs backend}{ - - -Packages in r-lib and the tidyverse generally use \code{\link[=vec_size_common]{vec_size_common()}} and -\code{\link[=vec_recycle_common]{vec_recycle_common()}} as the backends for handling recycling rules. +Packages in r-lib and the tidyverse generally use +\code{\link[=vec_size_common]{vec_size_common()}} and +\code{\link[=vec_recycle_common]{vec_recycle_common()}} as the backends for +handling recycling rules. \itemize{ \item \code{vec_size_common()} returns the common size of multiple vectors, after applying the recycling rules -\item \code{vec_recycle_common()} goes one step further, and actually recycles the -vectors to their common size +\item \code{vec_recycle_common()} goes one step further, and actually recycles +the vectors to their common size } \if{html}{\out{
}}\preformatted{vec_size_common(1:3, "x") @@ -74,18 +73,15 @@ vec_size_common(1:3, c("x", "y")) } \section{Base R recycling rules}{ - - -The recycling rules described here are stricter than the ones generally used -by base R, which are: +The recycling rules described here are stricter than the ones generally +used by base R, which are: \itemize{ \item If any vector is length 0, the output will be length 0 \item Otherwise, the output will be length \code{max(length_x, length_y)}, and a -warning will be thrown if the length of the longer vector is not an integer -multiple of the length of the shorter vector. +warning will be thrown if the length of the longer vector is not an +integer multiple of the length of the shorter vector. } We explore the base R rules in detail in \code{vignette("type-size")}. } -\keyword{internal} diff --git a/man/vec-rep.Rd b/man/vec-rep.Rd index 2f19c0507..f893ff78e 100644 --- a/man/vec-rep.Rd +++ b/man/vec-rep.Rd @@ -34,7 +34,7 @@ vec_unrep(x) the entire vector. For \code{vec_rep_each()}, an integer vector of the number of times to repeat -each element of \code{x}. \code{times} will be \link[=vector_recycling_rules]{recycled} to +each element of \code{x}. \code{times} will be \link[=theory-faq-recycling]{recycled} to the size of \code{x}.} \item{...}{These dots are for future extensions and must be empty.} diff --git a/man/vec_bind.Rd b/man/vec_bind.Rd index e20f6a628..fff4ae2d7 100644 --- a/man/vec_bind.Rd +++ b/man/vec_bind.Rd @@ -81,7 +81,7 @@ mentioned in error messages as the source of the error. See the \code{call} argument of \code{\link[rlang:abort]{abort()}} for more information.} \item{.size}{If, \code{NULL}, the default, will determine the number of rows in -\code{vec_cbind()} output by using the tidyverse \link[=vector_recycling_rules]{recycling rules}. +\code{vec_cbind()} output by using the tidyverse \link[=theory-faq-recycling]{recycling rules}. Alternatively, specify the desired number of rows, and any inputs of length 1 will be recycled appropriately.} diff --git a/man/vec_interleave.Rd b/man/vec_interleave.Rd index 5cc415027..bd4ce678f 100644 --- a/man/vec_interleave.Rd +++ b/man/vec_interleave.Rd @@ -14,7 +14,7 @@ vec_interleave( } \arguments{ \item{...}{Vectors to interleave. These will be -\link[=vector_recycling_rules]{recycled} to a common size.} +\link[=theory-faq-recycling]{recycled} to a common size.} \item{.ptype}{If \code{NULL}, the default, the output type is determined by computing the common type across all elements of \code{...}. diff --git a/man/vec_recycle.Rd b/man/vec_recycle.Rd index 71091fa7f..fcfe6111c 100644 --- a/man/vec_recycle.Rd +++ b/man/vec_recycle.Rd @@ -39,7 +39,7 @@ origin of a problem.} \description{ \code{vec_recycle(x, size)} recycles a single vector to a given size. \code{vec_recycle_common(...)} recycles multiple vectors to their common size. All -functions obey the \link[=vector_recycling_rules]{vctrs recycling rules}, and will +functions obey the \link[=theory-faq-recycling]{vctrs recycling rules}, and will throw an error if recycling is not possible. See \code{\link[=vec_size]{vec_size()}} for the precise definition of size. } diff --git a/man/vec_size.Rd b/man/vec_size.Rd index 6a257f4c1..472a3c1ba 100644 --- a/man/vec_size.Rd +++ b/man/vec_size.Rd @@ -119,6 +119,6 @@ list_sizes(list("a", 1:5, letters)) } \seealso{ \code{\link[=vec_slice]{vec_slice()}} for a variation of \code{[} compatible with \code{vec_size()}, -and \code{\link[=vec_recycle]{vec_recycle()}} to \link[=vector_recycling_rules]{recycle} vectors to common +and \code{\link[=vec_recycle]{vec_recycle()}} to \link[=theory-faq-recycling]{recycle} vectors to common length. } From 44bd44baa1c6ebdb42f0e5b3df80dd608da3c072 Mon Sep 17 00:00:00 2001 From: Davis Vaughan Date: Thu, 12 Oct 2023 10:38:09 -0400 Subject: [PATCH 299/312] Fix doc typos detected by CRAN --- R/conditions.R | 1 - R/subscript.R | 2 +- man/vctrs-conditions.Rd | 2 -- man/vec_as_subscript.Rd | 2 +- 4 files changed, 2 insertions(+), 5 deletions(-) diff --git a/R/conditions.R b/R/conditions.R index 6b68fbfa0..9dbe56f82 100644 --- a/R/conditions.R +++ b/R/conditions.R @@ -7,7 +7,6 @@ #' #' @inheritParams rlang::args_error_context #' @param x,y,to Vectors -#' @param subclass Use if you want to further customize the class. #' @param ...,class Only use these fields when creating a subclass. #' @param x_arg,y_arg,to_arg Argument names for `x`, `y`, and `to`. Used in #' error messages to inform the user about the locations of incompatible diff --git a/R/subscript.R b/R/subscript.R index 3d267b930..0bf9a6c89 100644 --- a/R/subscript.R +++ b/R/subscript.R @@ -10,7 +10,7 @@ #' #' @inheritParams vec_as_location #' -#' @param logical,location,character How to handle logical, numeric, +#' @param logical,numeric,character How to handle logical, numeric, #' and character subscripts. #' #' If `"cast"` and the subscript is not one of the three base types diff --git a/man/vctrs-conditions.Rd b/man/vctrs-conditions.Rd index 69faf4cec..e7d6816f7 100644 --- a/man/vctrs-conditions.Rd +++ b/man/vctrs-conditions.Rd @@ -86,8 +86,6 @@ mentioned in error messages as the source of the error. See the \item{x_ptype, to_ptype}{Suppress only the casting errors where \code{x} or \code{to} match these \link[=vec_ptype]{prototypes}.} - -\item{subclass}{Use if you want to further customize the class.} } \value{ \verb{stop_incompatible_*()} unconditionally raise an error of class diff --git a/man/vec_as_subscript.Rd b/man/vec_as_subscript.Rd index d427b0175..c10aceb85 100644 --- a/man/vec_as_subscript.Rd +++ b/man/vec_as_subscript.Rd @@ -32,7 +32,7 @@ locations or names of the observations to get/set. Specify \item{...}{These dots are for future extensions and must be empty.} -\item{logical, location, character}{How to handle logical, numeric, +\item{logical, numeric, character}{How to handle logical, numeric, and character subscripts. If \code{"cast"} and the subscript is not one of the three base types From b9d46bf67080f387de62f7bed116c277f6baddfd Mon Sep 17 00:00:00 2001 From: Davis Vaughan Date: Thu, 12 Oct 2023 10:43:15 -0400 Subject: [PATCH 300/312] Increment version number to 0.6.4 --- DESCRIPTION | 2 +- NEWS.md | 2 +- src/version.c | 2 +- 3 files changed, 3 insertions(+), 3 deletions(-) diff --git a/DESCRIPTION b/DESCRIPTION index 5a70584ea..153b7339f 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -1,6 +1,6 @@ Package: vctrs Title: Vector Helpers -Version: 0.6.3.9000 +Version: 0.6.4 Authors@R: c( person("Hadley", "Wickham", , "hadley@posit.co", role = "aut"), person("Lionel", "Henry", , "lionel@posit.co", role = "aut"), diff --git a/NEWS.md b/NEWS.md index 7e3f486dc..a9e0972e3 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,4 +1,4 @@ -# vctrs (development version) +# vctrs 0.6.4 * Fixed a performance issue with `vec_c()` and ALTREP vectors (in particular, the new ALTREP list vectors in R-devel) (#1884). diff --git a/src/version.c b/src/version.c index 806ba8e51..0a0a80bdd 100644 --- a/src/version.c +++ b/src/version.c @@ -1,7 +1,7 @@ #define R_NO_REMAP #include -const char* vctrs_version = "0.6.3.9000"; +const char* vctrs_version = "0.6.4"; /** * This file records the expected package version in the shared From 0e389890d4c733172161df9cfc70f3c77969b4de Mon Sep 17 00:00:00 2001 From: Davis Vaughan Date: Thu, 12 Oct 2023 11:19:43 -0400 Subject: [PATCH 301/312] CRAN-SUBMISSION --- CRAN-SUBMISSION | 3 +++ 1 file changed, 3 insertions(+) create mode 100644 CRAN-SUBMISSION diff --git a/CRAN-SUBMISSION b/CRAN-SUBMISSION new file mode 100644 index 000000000..6d69a7651 --- /dev/null +++ b/CRAN-SUBMISSION @@ -0,0 +1,3 @@ +Version: 0.6.4 +Date: 2023-10-12 15:19:31 UTC +SHA: b9d46bf67080f387de62f7bed116c277f6baddfd From 3d890b2013e7d444376eeb5b502249c6c46cbceb Mon Sep 17 00:00:00 2001 From: Davis Vaughan Date: Fri, 13 Oct 2023 09:08:32 -0400 Subject: [PATCH 302/312] Delete CRAN-SUBMISSION --- CRAN-SUBMISSION | 3 --- 1 file changed, 3 deletions(-) delete mode 100644 CRAN-SUBMISSION diff --git a/CRAN-SUBMISSION b/CRAN-SUBMISSION deleted file mode 100644 index 6d69a7651..000000000 --- a/CRAN-SUBMISSION +++ /dev/null @@ -1,3 +0,0 @@ -Version: 0.6.4 -Date: 2023-10-12 15:19:31 UTC -SHA: b9d46bf67080f387de62f7bed116c277f6baddfd From a0f6aa65ee32e10a1298bf9890822e0543568aba Mon Sep 17 00:00:00 2001 From: Davis Vaughan Date: Fri, 13 Oct 2023 09:09:50 -0400 Subject: [PATCH 303/312] Increment version number to 0.6.4.9000 --- DESCRIPTION | 2 +- NEWS.md | 2 ++ src/version.c | 2 +- 3 files changed, 4 insertions(+), 2 deletions(-) diff --git a/DESCRIPTION b/DESCRIPTION index 153b7339f..b97311513 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -1,6 +1,6 @@ Package: vctrs Title: Vector Helpers -Version: 0.6.4 +Version: 0.6.4.9000 Authors@R: c( person("Hadley", "Wickham", , "hadley@posit.co", role = "aut"), person("Lionel", "Henry", , "lionel@posit.co", role = "aut"), diff --git a/NEWS.md b/NEWS.md index a9e0972e3..b68964db0 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,3 +1,5 @@ +# vctrs (development version) + # vctrs 0.6.4 * Fixed a performance issue with `vec_c()` and ALTREP vectors (in particular, diff --git a/src/version.c b/src/version.c index 0a0a80bdd..6580b4cdd 100644 --- a/src/version.c +++ b/src/version.c @@ -1,7 +1,7 @@ #define R_NO_REMAP #include -const char* vctrs_version = "0.6.4"; +const char* vctrs_version = "0.6.4.9000"; /** * This file records the expected package version in the shared From 19f16352c8e4815ae673c7a4109230b51502ada2 Mon Sep 17 00:00:00 2001 From: Davis Vaughan Date: Thu, 2 Nov 2023 09:53:12 -0400 Subject: [PATCH 304/312] Allow `NULL` dimnames to propagate through `new_table()` (#1889) * Allow `NULL` dimnames * NEWS bullet * No need for `zap_dimnames()` anymore --- NEWS.md | 2 ++ R/type-table.R | 2 -- tests/testthat/helper-size.R | 5 ----- tests/testthat/test-type-table.R | 22 +++++++++++++++------- 4 files changed, 17 insertions(+), 14 deletions(-) diff --git a/NEWS.md b/NEWS.md index b68964db0..e7836bfd0 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,5 +1,7 @@ # vctrs (development version) +* Fixed tests related to changes to `dim<-()` in R-devel (#1889). + # vctrs 0.6.4 * Fixed a performance issue with `vec_c()` and ALTREP vectors (in particular, diff --git a/R/type-table.R b/R/type-table.R index 79574f88c..a70035015 100644 --- a/R/type-table.R +++ b/R/type-table.R @@ -48,8 +48,6 @@ new_table <- function(x = integer(), dim = NULL, dimnames = NULL) { abort("`dim` must be an integer vector.") } - dimnames <- dimnames %||% vec_init(list(), length(dim)) - n_elements <- prod(dim) n_x <- length(x) diff --git a/tests/testthat/helper-size.R b/tests/testthat/helper-size.R index 3b58680d1..75464e7cd 100644 --- a/tests/testthat/helper-size.R +++ b/tests/testthat/helper-size.R @@ -2,8 +2,3 @@ expect_size <- function(object, n) { expect_identical(vec_size(object), vec_cast(n, int())) } - -zap_dimnames <- function(x) { - attr(x, "dimnames") <- NULL - x -} diff --git a/tests/testthat/test-type-table.R b/tests/testthat/test-type-table.R index 0e29b23a3..a79827d37 100644 --- a/tests/testthat/test-type-table.R +++ b/tests/testthat/test-type-table.R @@ -18,34 +18,42 @@ test_that("can find a common type among tables with identical dimensions", { tab1 <- new_table() tab2 <- new_table(1:2, dim = c(1L, 2L, 1L)) - expect_identical(vec_ptype2(tab1, tab1), zap_dimnames(new_table())) - expect_identical(vec_ptype2(tab2, tab2), zap_dimnames(new_table(dim = c(0L, 2L, 1L)))) + expect_identical(vec_ptype2(tab1, tab1), new_table()) + expect_identical(vec_ptype2(tab2, tab2), new_table(dim = c(0L, 2L, 1L))) }) test_that("size is not considered in the ptype", { x <- new_table(1:2, dim = 2L) y <- new_table(1:3, dim = 3L) - expect_identical(vec_ptype2(x, y), zap_dimnames(new_table())) + expect_identical(vec_ptype2(x, y), new_table()) }) test_that("vec_ptype2() can broadcast table shapes", { x <- new_table(dim = c(0L, 1L)) y <- new_table(dim = c(0L, 2L)) - expect_identical(vec_ptype2(x, y), zap_dimnames(new_table(dim = c(0L, 2L)))) + expect_identical(vec_ptype2(x, y), new_table(dim = c(0L, 2L))) x <- new_table(dim = c(0L, 1L, 3L)) y <- new_table(dim = c(0L, 2L, 1L)) - expect_identical(vec_ptype2(x, y), zap_dimnames(new_table(dim = c(0L, 2L, 3L)))) + expect_identical(vec_ptype2(x, y), new_table(dim = c(0L, 2L, 3L))) +}) + +test_that("vec_ptype2() never propagates dimnames", { + x <- new_table(dim = c(0L, 1L), dimnames = list(character(), "x1")) + y <- new_table(dim = c(0L, 2L), dimnames = list(character(), c("y1", "y2"))) + + expect_null(dimnames(vec_ptype2(x, x))) + expect_null(dimnames(vec_ptype2(x, y))) }) test_that("implicit axes are broadcast", { x <- new_table(dim = c(0L, 2L)) y <- new_table(dim = c(0L, 1L, 3L)) - expect_identical(vec_ptype2(x, y), zap_dimnames(new_table(dim = c(0L, 2L, 3L)))) + expect_identical(vec_ptype2(x, y), new_table(dim = c(0L, 2L, 3L))) }) test_that("errors on non-broadcastable dimensions", { @@ -80,7 +88,7 @@ test_that("common types have symmetry when mixed with unspecified input", { test_that("`table` delegates coercion", { expect_identical( vec_ptype2(new_table(1), new_table(FALSE)), - zap_dimnames(new_table(double())) + new_table(double()) ) expect_error( vec_ptype2(new_table(1), new_table("")), From fc315189ac1b0b3156a4d0761e9c4902126a120a Mon Sep 17 00:00:00 2001 From: Davis Vaughan Date: Fri, 1 Dec 2023 10:08:33 -0500 Subject: [PATCH 305/312] Fix usage of C level format token (#1897) * Use the correct format string for `R_xlen_t` * NEWS bullet --- NEWS.md | 2 ++ src/altrep-rle.c | 2 +- src/vctrs-core.h | 10 ++++++++++ 3 files changed, 13 insertions(+), 1 deletion(-) diff --git a/NEWS.md b/NEWS.md index e7836bfd0..788e4fd51 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,5 +1,7 @@ # vctrs (development version) +* Internal changes requested by CRAN around C level format strings (#1896). + * Fixed tests related to changes to `dim<-()` in R-devel (#1889). # vctrs 0.6.4 diff --git a/src/altrep-rle.c b/src/altrep-rle.c index 6f56a7022..1b712dbc1 100644 --- a/src/altrep-rle.c +++ b/src/altrep-rle.c @@ -59,7 +59,7 @@ Rboolean altrep_rle_Inspect(SEXP x, int deep, int pvec, void (*inspect_subtree)(SEXP, int, int, int)) { - Rprintf("vctrs_altrep_rle (len=%d, materialized=%s)\n", + Rprintf("vctrs_altrep_rle (len=%" R_PRIdXLEN_T ", materialized=%s)\n", altrep_rle_Length(x), R_altrep_data2(x) != R_NilValue ? "T" : "F"); return TRUE; diff --git a/src/vctrs-core.h b/src/vctrs-core.h index 6ce64dd9a..f02c10b9a 100644 --- a/src/vctrs-core.h +++ b/src/vctrs-core.h @@ -108,5 +108,15 @@ enum vctrs_dbl dbl_classify(double x); #define VECTOR_PTR_RO(x) ((const SEXP*) DATAPTR_RO(x)) +// Likely supplied in R 4.4.0 +// https://github.com/wch/r-source/commit/38403c9c347dd5426da6009573b087188ec6be04 +#ifndef R_PRIdXLEN_T +# ifdef LONG_VECTOR_SUPPORT +# define R_PRIdXLEN_T "td" +# else +# define R_PRIdXLEN_T "d" +# endif +#endif + #endif From 11f1c1c43c32583aeaa87438c6a6b6b440b95bb2 Mon Sep 17 00:00:00 2001 From: Davis Vaughan Date: Fri, 1 Dec 2023 10:15:02 -0500 Subject: [PATCH 306/312] Increment version number to 0.6.5 --- DESCRIPTION | 2 +- NEWS.md | 2 +- src/version.c | 2 +- 3 files changed, 3 insertions(+), 3 deletions(-) diff --git a/DESCRIPTION b/DESCRIPTION index b97311513..8d1c4c881 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -1,6 +1,6 @@ Package: vctrs Title: Vector Helpers -Version: 0.6.4.9000 +Version: 0.6.5 Authors@R: c( person("Hadley", "Wickham", , "hadley@posit.co", role = "aut"), person("Lionel", "Henry", , "lionel@posit.co", role = "aut"), diff --git a/NEWS.md b/NEWS.md index 788e4fd51..48107b5bd 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,4 +1,4 @@ -# vctrs (development version) +# vctrs 0.6.5 * Internal changes requested by CRAN around C level format strings (#1896). diff --git a/src/version.c b/src/version.c index 6580b4cdd..7946cd3ca 100644 --- a/src/version.c +++ b/src/version.c @@ -1,7 +1,7 @@ #define R_NO_REMAP #include -const char* vctrs_version = "0.6.4.9000"; +const char* vctrs_version = "0.6.5"; /** * This file records the expected package version in the shared From 8bf5ba59bae73705f460ef326b725023cff46efa Mon Sep 17 00:00:00 2001 From: Davis Vaughan Date: Mon, 4 Dec 2023 08:45:34 -0500 Subject: [PATCH 307/312] Increment version number to 0.6.5.9000 --- DESCRIPTION | 2 +- NEWS.md | 2 ++ src/version.c | 2 +- 3 files changed, 4 insertions(+), 2 deletions(-) diff --git a/DESCRIPTION b/DESCRIPTION index 8d1c4c881..4a175f1c5 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -1,6 +1,6 @@ Package: vctrs Title: Vector Helpers -Version: 0.6.5 +Version: 0.6.5.9000 Authors@R: c( person("Hadley", "Wickham", , "hadley@posit.co", role = "aut"), person("Lionel", "Henry", , "lionel@posit.co", role = "aut"), diff --git a/NEWS.md b/NEWS.md index 48107b5bd..2cb290516 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,3 +1,5 @@ +# vctrs (development version) + # vctrs 0.6.5 * Internal changes requested by CRAN around C level format strings (#1896). diff --git a/src/version.c b/src/version.c index 7946cd3ca..4edec49e4 100644 --- a/src/version.c +++ b/src/version.c @@ -1,7 +1,7 @@ #define R_NO_REMAP #include -const char* vctrs_version = "0.6.5"; +const char* vctrs_version = "0.6.5.9000"; /** * This file records the expected package version in the shared From d75f0080099dfeba2ef34f6471c09d0ad23e336d Mon Sep 17 00:00:00 2001 From: Hadley Wickham Date: Tue, 30 Apr 2024 21:55:41 +1200 Subject: [PATCH 308/312] Update favicons (#1932) --- pkgdown/favicon/apple-touch-icon-120x120.png | Bin 0 -> 18291 bytes pkgdown/favicon/apple-touch-icon-152x152.png | Bin 0 -> 26499 bytes pkgdown/favicon/apple-touch-icon-180x180.png | Bin 0 -> 35191 bytes pkgdown/favicon/apple-touch-icon-60x60.png | Bin 0 -> 6415 bytes pkgdown/favicon/apple-touch-icon-76x76.png | Bin 0 -> 9081 bytes pkgdown/favicon/apple-touch-icon.png | Bin 0 -> 35191 bytes pkgdown/favicon/favicon-16x16.png | Bin 0 -> 1349 bytes pkgdown/favicon/favicon-32x32.png | Bin 0 -> 2709 bytes pkgdown/favicon/favicon.ico | Bin 0 -> 15086 bytes 9 files changed, 0 insertions(+), 0 deletions(-) create mode 100644 pkgdown/favicon/apple-touch-icon-120x120.png create mode 100644 pkgdown/favicon/apple-touch-icon-152x152.png create mode 100644 pkgdown/favicon/apple-touch-icon-180x180.png create mode 100644 pkgdown/favicon/apple-touch-icon-60x60.png create mode 100644 pkgdown/favicon/apple-touch-icon-76x76.png create mode 100644 pkgdown/favicon/apple-touch-icon.png create mode 100644 pkgdown/favicon/favicon-16x16.png create mode 100644 pkgdown/favicon/favicon-32x32.png create mode 100644 pkgdown/favicon/favicon.ico diff --git a/pkgdown/favicon/apple-touch-icon-120x120.png b/pkgdown/favicon/apple-touch-icon-120x120.png new file mode 100644 index 0000000000000000000000000000000000000000..df7455138694db9761efc38bf5cb535267c22679 GIT binary patch literal 18291 zcmV+LKo7r(P)004R>004l5008;`004mK004C`008P>0026e000+ooVrmw00006 zVoOIv0RI600RN!9r;`8x00(qQO+^Rj1RWC~Fw6}T>Hq*n6iGxuRCwCmy=Rmp*>#xt zg-h?Vva-DQ)!vLZ0EX}+A<-KV5+Trm)X{2JD=wwg@=zPycU5Hr3PJGlQO)dro&{Mnq;rzAx^5@7;Uf4T*QL z3?Kd>5CXshd`t-OzW~z+@t+Xp6v)=X^cNoVWxk~%J?IN~t7Q1_4}m192yqM{J|*D$ z5h92X7Kp0|@i~F`Qz1Fyk|?q`{iO$e$#03g>i`cQ{$W6t!0ZQp8X-O|pa&tE+T8dn zppFoy5aQFo*FY+Q#p2a3KIotDrpmhp@bHlz16L|hXg3MfxG8DIS^kI zLVQLDP6NjB?7K&s-|>J)j{Yd3(a$V3;Q67a~;9|NI)WOM@`7eagjA^Jf`w`%EK!`=J3D&Tnpp9b+PPytw; z|JsB8>Gv$}D8M5pejE%7WXX>Z-w*tv5aKvOsMlaZ(`4T-+}+~=L8KB?xfJcu11b~bX>^W7qEE5M^C{sACqU_DG@0QFIX@a_T;H)$>6CTK$323CK8fMAl{D_#c9Vip4PypAtfR3?TwH!n;qnZ`dqfKkf~{ z-4zR%0e&0!Qy>oCeY5>t13dQdPlKd_sPBgH{-F?}=T>+(Y2bHFbFUxwCcxb*b>Jl$ zX8UVE3BG%v-*Uj?kA4En)RAN*gy082`~pH87D6c3HT5RA*9KJg1D9+2n;+PJw7lof zTLgEn;ONS7=2O)ODc+MNm@NUCf`@@ABr#-irZnzO{ z^Y5KB_vY!)TMKuu#DG5peh*j##9ImaEdf0K=qCV40dY_W@$(>l2+<7V-3jjP%re{~ z-2F87+JD>?+*>~Lriuwn0lx|SIgo<4#%#Z-fX5&E#~?`{L^neG6o^jI{AWO5lVtgQAbt<{4TN~40hc}PzIW=w-NEH1xHmZ} z8vow`E_=4!441bFTp^GYC8YTypNOXr_k$Bp{47Ya zjAf1q#Lpr4F$AsGfx)e2d5;#}>|fq%V(%&JcORO&`!x?5Zc}8{j^+(Y(Y9c}BuW3r z=1$>z-}|dy|7Dw(bmf zkCWm}iRs=I+?!xNAh-yy1zQOn{~kW__uofXM~J`p>I@R1{PfALZ$?6{PrrC3_CnC_ zto`R78NTPQziSPic=8tj3j`jPmp@E1j3%R3D&fGnZ7yf}RU z!a*11ijHYnbVl4R5Z}L(E^&J3L2qZ~CbqDYT{b;H}zF0#7y4t<0 zZxzsWD`M*Ur>sihFP&}u|J*2MJAV3`b=v%sZyfOC)1PAUJ-;YPNFzdse~S>GM~ELs z2=87X;&uRUxBq6i?A>;qz^wzP{WMqH2=@*#UEXeRn<8l%swYS&?8h)n%9T2Pj}3=i zV>3}kk|ktCk%T3NLHt|Q?f?A6-~7)%KJm|f!{_KK&^GFP8W? z@N)v4>bgl+o0pwb znMzd$0kYf}DoKi}*~1-=`??1YKXsz}D?jriNB-X*pYXl(rFET;c5Ami$LpEs10epr z5aJ-hx(-*|1KeA*bRW3Q_t%y7I;gu39*A3+y-ndlBga8;dT{y!_&iQZ>KfJb?{ojNTYF#(>J;%NpEQAH1A+R+@!MB0S zO#ttxx!ig)T!V9~$=xM!|8T|I8g4^16%@B0PauG*DiljKT0$<;*$U}o8bwtQ2ozOA zb@@=;0U`q<3=c%PJeQy)U~{BF+TO|EJ7D%|+-*Ej`@y^s{@(V#oi^|J%-+V|1t@O1 zmUj)@UA`KcCrB{tqo$k4ibN#r=KSS#Dv3=Tz5v1!D4K>n+=0y-4F@>|MZp z{jlH7$J{O4o38U62p360ad>d}g82O|a``H%A~UzRLt#5cJrl<=bS%q4(KOt_0OKR= zT%F${ximv%dx=V^!d6};SFGJTU~vtgwLjdOHF>ukZwL2wru`bAdojyn1i$WqmzKEwzbJ%wicj!U9E>814;GD%V-Mxs-6xg?l4W-t3`WY-tgYqJ(%l#=iY%8`@#VG3#}NX&`HMWX+DE$fUCs=C3SKTDyu~NF#)WRj*-IOISu7 zvtHi!Ja;jQ-V4CG4)=Cu`G(Q<9&NuXxVJ)ir-l9QS|qss2hH zjzlBIYZ*FbrGQb&VU!E^0r-XilXac{1d%k&tc*-3wF4s1(r)Y0UC{c(R1JxpBpAtJsHm`6uz|hv}$8OhH+se}tu%jCmsyB=`qB1_(!R$%~k5k2AQ;<{* zNmj0Zk7Z(3O6a-teQNMcgPwggcQ2otw%uz?_ipm2_8%y}{o%s(0E5Hlr>)h;)=r6Z zwt~Z^P&WjM!_D|uC#8zPM!bL!peQo3q9RH1^_H-(Kg-+eQS)GHNrx;Pp6|T~1+`7B-towPw;1bkY{_Fm)wHy_m<) z^+vc*YW{1AB+E#u4cX>E*6jP9@eYm-so74}Z8VqtwVB(&-Tlb^aK&x6?}2wOa3zpc z6km>y;G^)f*(#;-^wIh;3z&uuv5VOIVB#hFM%mva>XgWf~ZLEhw`0 z#-uw%#UAd!(|-U@{~=VTci&U)3s|-_?g~qi&RbY=H>gXgeKk0WMC(sOQpX!5}`b9lK5A+2^m4TbZF6U&Gbq#564w zSw@l-Bw5AgZ^1Kol%4~Jc;w_DCk}NmzZ~MP?iH}RccO8}ZLeZhi^IC^tiot zbDQlq!388)L6Mt{Z3!&XWUuD#?w4o|EG!EoP*fE~Rgo1LAq1vjAcVl?bTT~H!_kR; z&R(2FR#j9@Yupf06SEMF!H%XOLBl<0S*V(ZqG=$3Wi;lbmiZ=`cOg(5PHZh*boR94 z^*TwX^9ZAkqN=!Ec4iiK*qEQE9GkfeT1b+FB+F>NAog$_|Tw+j;)r zFV1mzynWx(?hDu(?P>s4HR`zpmG}yn#_eI=^8PO2N)mx^kna8->~ zqd_!{)~*iPJKL}!H1;lkVn@z*x^^nUIkY$;Hfo^o&;PQoO^tw*(KrcPL9cY?LB9UQbX_ff;2Gw%q zjRTe>G;a`Bq>ItvHYydJO3gxX`)O+rQ>&X?xw1wnHcLI5VAru^nijGIn#+r)_W+@u zejYwK%=$)}sf+VS@f8-$?7aj2(9=T*BrZ(5sAZEFg*19TeQSoszG1&R!xcgx0S>o| zANYay^S;Lp^M$Xz#2@_LpOf0!MgR`CoA*BRIG_Bfk8 z73P;Wv1=+Gmy_*8js(L5yB*x?ckO;~_s)r{r4pAe&9b(cWU#lL!J%H3XBRMZozCtKCP(^+r?O1V zEHgUV#}9wsQ|P+EZ~oyI`S!Cflgnh#Y&HU+AiA#eyv@!}{rE>2>WT95*(?0SzOEFaoI5IHH3LRLs9}Pt1*Q-G9JM) zO-{dhh3xEE${P!qwK9^;ek}lTdqv$xF3iNaFtbA@SK;VH8+{{#I6H{Pp##IXeO{by7vtlDbVNf;&91VO$Z+z=7_BVv8_(i_bBA z<^rp;^W-yGgn;%)khZoKWJP9sEyl*;3iWF3jlmTH#qPx3(nV)a8;UBE$S4q#DrL;DKRVyO_vLxSef!V%*7h`4S z*Gs%`c7sH!z{AIS3H1%*i1r|<+Wv5_|FUa8@OE$;FC~Pq$fYx!Ie(Q(wa$?PgS2); z2}D{rdTyn}1T)sSqWf-`fc67reUnpVRlCgQI-+uWr z?X5vR`4b=FU;Xoc#8b~ajwcYff4D**X*TTPPFlM=a5!vK>n1{2^tAi9G9O2;>)14z zTFt`!dr3>H4amJ4xV4yclp;V_lZwH3JKGKPK3>4?aHGie(8F*0Q8CC7yqE zg-4EdGdMZMT&;}I>(tU)h#Tgud*SlBaCckXFm$$Jo1DEg&-hR`$Bs_0lgiN%4e_OK zoo0O{hRf}wTC1a}DgnP2)u!FRPBiDXw>I+a8-BMNu`G*xCc~+3pJI7&jl)ML`Phe_ z;PDd^{MZkC53^SnDQ0t6hH>wvT9Qy*J{+xG^z}wbXR8FfHoP7iiz{iiR%6JThNgB> ztJM*fi7gn#J9vcQBZn9nYUBKLoYBEBvP?7g>bk4u4FNte5kZknPq}krgGVM}% z^mq^Ty3Uf`NG+*l;_NM=a-HMrM}~GaUs!@-F2}hGGkolWk8)_dk959_ZkoJy_6pf# z3cc=SWj)Tx!y_C!Jjx3%v{NfrFq-|Xs;bv4#_kkMQIv)=M3#}{+Z!ucQLsB4=(Rd4 zv-2dj;-s?$`nsbG^t90u39%^4nD^AI*S;KkC`zEclW@qx>~fmP;V|i3m8;WBls6V} zMZ3^cnYwPGc>>scVfqgp;^1T#7q7-iX3C5XhEWs+Nm01&k9&iFzxC1rHk(3Qs~?}& z&Q5xpg?WSCt{~4mHG-}iteFPZ{8{u|l15>-o8XGqhugf-(W_PFW|x>-+F*RRhc4Y< zX?2^cSLUgfOIVi4%dcJLnJ16()WZi@S${uY|HezC6DjNtJE4{k@r`Xt#S+C*1p#z* zM(G;t!|nATDavg%+~IOEdUz6>%|>iBh9v}cyA4^EsnvCKUBACTq!6eMH}*&m-M#IU zszzg*s&M||8kyx;YN;5W_HGnK#t<@&wtiY8evTdPV|r$j)%i6XZVw1hG!;qFnniBz z{xbIWMY|jgFNzEUy%7?z4QkmmXU?zi_dj}sXPz44tGa<@)F~`nz$m0aSU0&a?*wi?f_KG>pe-=dZpr%l5_=rfyKPDx7}x0$=#b5I^>@r}^Yhe26C=I>7c$ z8n4HN$K&GHfAh~c_sTgImt$n}B_2O9j^F!n);AOU%~xJRRn#)lBsbinii~c_grgBo9PVIYCBf{uOH>nUD18%HLZHatKQ_AKMqT!>C$2R!mKmJ=1$u!SAeS+@x7J51(RH}6rR<@|u>gcr^7tT)c z=YRJ+AAHYAhWk63E?0$ACeQTz8u3J?;p1(>P9!r_sx=-uGK#E7uN_)6oh3lIuPbtFV0cgUZI|eV{hp~v)cd(O_ez~(#pnGmgzH> z$j_a@((8D-h7p#9tjM>$$@U$4ydL1^pTCH(z#k6q_#-2{@5vEfKITb z?{)Cdi6LIrb%dc)T)vD^%ComGzTw3_a6uqRf_k;ar8AfK)r~k3kl2n>uU4=90KHmc zZGMqIO{RG6xmSs_wqUc{D3{9Y#FHep;#A9JwpQ2pga7`QeCxT_@VH%Mvw5~+Tdd5^ z^U@2iQ7V=x7YYa=$fweL;V-_z%P*g&r6q)_DrB>HHrF>v#}m{l_u+?@BvelTXKOdT zy{)9O6~>1e^XpV{k2_Mcq1kNMG=;-s5mKol7f(05RF(J&nkR^58d#PzEUVEF&B#yP ztg*Ga&d$abk}M%i3)8$Y`+rv}^?IGu);5`)1hS$uB1xu&b<3Rk9{4IMwop5vj!uFB zH`ziJk5gr1J5MQ_#VF+)aD8EHPAAcbo0<6?&b~H9cJ?fl%|)zw4PhAw!)TajRY6iz zXr}GRYGY-hEfmElWE({h?*(vWd%2nSQzhQg#?op#mAXaPuM$4g&gJ<88}R}@j|0P~ zbMm1vUeR@gsZ(0Jid8M&1KhnW|2nBQO>MSJ6Vuq^*1O3}3ClvS)%M+g<0%EEu4Cx> zT^)Z%5dy{G!V&4BtEUY`mI(Qr#FHheHG^s{jW7*d?E`qbM;IOMAeE``+L<{rv*#(r zX0htk>+L24mf2VYPIK&_*j+f=`*C%R;OrcxmfD0@fB&|Zv#+DWs@JgeI`v$FQhc4| z)dYU8le1S6q%#E`I@pG8fWxkk%+`<)oOpPW;OGfl9Ye@A$GyY7N0B7y+Q0kRf78MD zcKm)K%V_=xo@f_6ok2Wq8yh=CECHEJ5u;kd9%{osdV<3zCmHMwk;;@QCgN1%%T2}D zd%p-w(`>BrmlZU308jrx!iSz<11H`q+v6FK53UyLnbttwMEYo!IIo2$Pne zo9V?27pG#hN1V8w8WTgU%r2*KITVgPJV{{m1kR2DB-M63KkEj#?@|#0S#w}-=_1%$=8>3pKzdN+=CB5$ILSdQc*&T}8F;>=k=1`f5)Xw3D4szbqv2?v*>W%u|ujE}zS(4DajltE(a65LpjZ3pD zsH%*FM7a*m)*c22q73x4@an}ay4$^2M#B${b@MpEygtaX*>JS=5%N1ZcBq>|vC6a0 zO|!hXPFs7+zL)g+h0uh+s1&K~tg*J-&tPAaaKOpZQk?R7mX|YGc9MBc9_>drTDdg4 z!;$eQ`ia9_GE9VJP>ru5j7B!dyHiiQ(I(mWrlhJWJ{Gsa^pVBKuyC!QEl|~wlXo)!t!c@>GM}8tS?|~%#%uX?0Z@J z2mI~M#&tIbPPOzFxvdzn%^n8&BCO8^D6LLY&ulYODI-fVA9~*;EkOrMt0@M00_gf7 zrj4dcb0^jag}p5v3g<)EZ4F<^H9EXQ z$B-lmqm-kb*~YAvsV3H0Uf$xVC&RRMcT-w#p|~;y0v0`9raOZ~TD%PO1SyuPOpLTr zuODH~G|3r8W3(sUCOOJ)vPg=CBhrnpvzMN(Fy}7E$i{cDyIgo&Hj3pkN5)&ZI={uj z#Y_jsj5_&Dj-6zIfx&jR7kjB}FH=p%D6GwL;bNG_ z9vfq2BTHM08@o;Bv6KDiy1}AR2g_^(Cz_d&?;epFZprR3#wPkPEm)jgrJmWw=N}~C zbKrH`nO%%CbM_MXxw9ZF6h%f+cveE}buXxMd0>Lg$6XLT(>d@G5L%IapGhYoiU>guHw>!7qUO=V-A zcreOxM~IHj2xq1?8R+nG@=zxqc<%&X)=gF|6ES<5dMZj`-}t_OUpO5@AaH0B?GYE_BW+BKb+Vl-vk}je%U9?h z>>#;1Ks_BtFJ>vN&oFzXh4!`}-R(i97n3A26&^d*&HJ7jFbGb z@<1ClO{P8SXK8r^A)p#x!K@T0#n-t!9pRx9L&TFMHsd+I_>C!!9_-?Y$3{8hw6p37 zP+Y!DWqY}~I^E)(s?C}wfUA3)!SO-Hhgvy19j9tYxFT(wIMl^JPlzvmW17PHeA5M4 zMN$-GRl{c28o39m15f_}Lah;wA0I?FOkQ|#n&jdPlA>XD`WwqvRITZ*d=moxsv?6d zqZ@U~>sQHFiey*XS!?Ma*w#*WZyN_EI{4r-2bk-Nvc5V@YHJJ2&`D(~Y;0$l7z}YL zktDad$#*g-jvgQ71MeBIe~9c-n9}+TdM?q-40#7hv%hq<5706&%)yBc^2HiU z>sb_4<={vgey^R)c%E!3OFa|EtTzG|lGIokXtUd}ECH&MzVQ(bj<&L~mE+R6t7PXd zQrTL<**@44|jqj zQ7Kp0nu$_gccK?ESoI2eK80DU5c3B}4z>}Cmq}-K=!m!&=?^iks%#}1ef8*IE8CmB z#0we9+bf(oZAa4-#)qTW9~j8m~D7;-t2{6Z?dQ^FRtz}dPatc zw0J314A!^v^mh2@h7cj6hm6I`ugI!Np*Z9bbsj>NM5V<{fK4Jy2<8N;;x_1p7ys80#dNDHHTL(Nvk<4j*TywkVeB z1bt!R@ho~igITX4YjzxwE<6K==^UTr;6x|!M3EQ2bA{yW1xhPZjTwezHWXAeYG7HW z)hGtSwSpyx8M zH(tx!$pySG;6%EDVVJZ<1GIO9Sq(;!?at=f85&ND)HeC87_p5$2Kpnc&xWq`AEotK zis5$BTVqtKI**5*@K`IQipiDv9VSNGh_w2+6bzA`4>w$) z*#yFTn@p#KKykWpc8<_KG(=BVh>J5jJa)7Tn@!<`m*-i&JcU)S&=NU>ghU~mN0MYb z{RasQ9puolaXQ-kT$ zVO9#T&+?>w0b7+KreU(Vm12CX2Uj>s!5zRT<*xl$vz(_IUuAizpQoQbOlwas#q|#A z*&XWH9gIQ-t5#;o>7udG^3l}a^T)vDw(oHbv zp4(0#ZxuA6NzEy%tf|O$C$>Nf zj%Xi_)*kGUu0~et=|8$Rz_s)ymVm^z#({|*!fmaj0}*QJ>;0oJb!y2CG8-GjcX}Bd zYG-S)pX&As_3RFoQKy<{xG|@uT6prwNwyMBW)~C8&#cnY;-jZK0>a|)W1XBjFL7xu zMSF{r zCK^^2#eN=rbewQ^FXi%GIG8Jv7r@x(}2YQ$sYGHOc#oTg=o(>=3_Z;P7D9DyCOlf6`Y9iKfuD{V0fA=E0 zbKZ`@MoIm_D03?rP9EyO>9lcmdYR(VC8|4X*n&|Uz5qV2ldY93Lwzlb^aYuj-)8pW z74nN05xR~m7(&@~QyO&y)-C63GHyJ(0nnTt!o!Cd=nd1;6{1q9Gd&X{9CYt{>30Yh zx|;PfB(`=6j10BmYH6e7Yr(9R8?j4aAq<^bVx2@RMmF2cz+fkdr9P@VtLTLc2!WnY zQ(m88{%VAd_8`MU9h}`*p}2gR(%KbDp*AvGqvZ2to_TVN-ZnQi-GQ!Kc$_lteQKOb zEq>O;t2$BI&JiK`ElA6UOThE+LbF57cWvxtYeRKp=v6!EK%Rp;2Ua&HGY$9bD+9? z2uVRg(AOQLHQZR{a^~Cu@%2p#JKHz|!FvbXcIaUMEJ-C-HqlgxP zS*u_*y)(6JlBJadM-TTC=dJ_ z&Ut%B2Wbg=DOYrCTI0rFUfQCPSjW_B*jqYrb`H}L4bvX+kjs~O@x>W-<}OoOzDzw6 zM+mF&tcGS4BfS}DxK@=&k{W($UkGRW0G{4)T02^ahCQf?%%v+aR_B%}tj|$PtW!^I zQT5(O%FdIIk2h{6z%VRYf^Lo-?j;y>Q!11w70OgfCFcZyAjt{~ii*vqFgo1H>8Tyo zwzdd(67+Za8R%;v^ns&XzS7Ft(g20+7}aEqdTOgtv$0-jI7u1>K;8tj0!gvqi1rff z8{xos7dB0%T!HOm3BSiqa$^&-n8g|G#XESI{sWUdc5;B(#UwAjaEa{Pc}iE)nt0jb?BlJ4+%Sqaz0Y(lCQ%Ub&l(Oi#R0Hz-S!NU!O;b5>ppDlq zZ4uv2vbnUv`ExFM``bA@(aFgpy(}yzSz6vAxv@!kXPsIi))>8)3yns5!&)t43pD1u z;|B)m=?oCt&U0yYhr{Dh7MFLZm-5&nU3j~OnLIj1e@_@81WT(4@+-3xmoH=PsU;~% zGP2h2Lz||BQL7;=vylzb(uuQkgmB*wqvL&awE2lAioA3##_`Ga#-KI6)=YtFEV|oU zzw({{ufO!w#s#Sw_E0;S;RA$29;AlUC{Soqo3a`96OER89^Z2kt6h)RA^>eCPA(>B6 z*;pW6uk!6ujg5Go10zwqE|vbiFvEkbB+^5yuEa^iHYo4J8vWEYt=4aGChP}SQZyW` z-S~PNabDf9c<$9z3Z*)ueXVS#%G4~GXm2k^CZZHebzVLn!|%0YS%N|)gL!SO){QkL zWzCM=p;2#EmkmxlLT68uv5^ie%i`kYRn`}lDX!0BRtoq>j$v6ND5~15Ix9EwCEf_& z<~JBZU>L=my_VTwb1TC@e>?-_V7LW=%<4uOzsJtW;{#L=^s>H@CbqgsZmX%)sm(oo^&PZYmeB$c zT)mTwOb!wWd3g54d3JX4`1~FMJ}2{+x9RQlGcgcmaV5d*)m1E6rN6V6e6dC~pTVdW zZ&(~Anif&EIk4L`bi*Rj*1~9i2)9#ZelgC{+zR=%c`BO=)H87ur?;^P!4fE{+%(D8 zuDRKH-w)u%mrR5BRm-SK8TYCMO)?nJh`P+eYZEnQ@@V;r39;oNi_L$BjdEL=_-95U!j)T#ML=Wz-K4ElSeP4v1)q;KeCMG^x|wEz#eMH<+Rh&Gc{}tH(!G(7Myt4Exz5VaYS-SpTWl8#~ zRjd4LA)WcLe7@A$*3m*N7)6fFHO$@~2e?trQ;n}Q-IozsI@-uDc`0u!TpJi5HR>Nb zS~pqMG`c#14D^IJdv<~Cjd}E94#n<3b-2--E^KZO9>1SQP7V@naZ#!?p7H0jtEg(@ zj@AtmmtEn5PYf`fPLPmHm#m1F+OJoR)OPe(rkJt5pKI|z&KoVv>P%oL@SDP)_I;LrhFE<5Q| z9=(u37dsmtz+##=wCQfh zP*r79wmHtBD4(Tf{*928j3h~{EIoTa8Vsw;-vY1>f8zVlfs$0_E6id}#YHRg> zz!`3H7u~)aeZ-Q~$bn97UUy#(cCfY3M|FFddS<8D2R2p%Hr$vqT)rIU>8B3T-WFhP zrABFW3aeT{(zM2tN1PsJ^M~0Z;z{d_g}F61jAv|CLl5_CO2Hjv;*A zBlL~-Gcp*ZRyWBNs?06!ur)J9VeSliK6zukD{*~gi7<3(HDe_l^8UW%Y5o1Bt6yB5 zc+W3!<+)GudZN7U5kP$YJM{d(ubF@InIB$`rE6ccBz0kZBi&xj?6lQ$Dfxzhgb-M! zfoykRxx$Q%bdbpDl+wFZYprX=t%ccGvSDd%6t|y|;SRRbb*hPxU zO`#*|qpv4IM^8JQ1ARn#`|)@7;ce^U(T9c^><#n$t846}N@xxzqZ0!>`N$v_XLdMu zZh`#r70R(Wj7kAnv*YX>X5hd$4u_3}tBdHlB#vk={*e>(A3n;7hsTJ7J@;m1bx561Bv7({p7x!n)$K!ddDAw3^8KXLf;g9k=4pZ{f!oric!c=TAN`Z*h)uxh>3$k6q7sX`4qL(7R{P|=!GoB zrAurp8n0<8k3Kv~z1qQ4dW-VL0=47@&|Fy`j53``l1$_{e0YG~t{|7^k}Ry|5JnYh zMN~z?<#7=X`x)qqFge_V-L7F67A~hsE?=Xo%}dblz~j>B@A6{_*xD(f+8Tj-+3v!u z77>=f+1gDg=p~b{Av?VIMotj!XlG))hk)P3>PD88jU1J71&70iBFpHOgd@^}Y;zzf zY9nJqwV`M>Bt@xOy8gUT%6{6aSDu}F{;QSl|M}6o#dU8QyjSMG`8&M!Tfc@wSMsuE zKUL2qp2xCepbv2EYOyd4WQQBc6J~U{gY9&cN@}MOgt(^hQlo@$y#lI@n&RcaL>KwG zLMdNF&nFv^tKBuh^(tn$K+RGpnRX5x=tkJQ95^qh|6+D&;CWIRmH5 z!GVz|vMiHH=PB*P$Su#1Szji(lO>iih$Skt1f6(X8kPlD7ZQ{zH715yFfGw2c`U%| z*68U9)795WTVF5Xo_>5CJ-GZq271H9;zfjFXY$|xljEHfN_D2@k|eV=6h+42(C~R2 z^mYX(R|SD+l&;}ndPYa+9UG;8eAtTi^;|M-{(mRjE&rBk{zBx5A2eS4FMscz;ocYE zT}f?TVrThP5%BkJ1K$MB13{n*Nzz0!?L@d*={PLHXtE1kaZ{=ZtZK0_H&?ah4N<`|1=*TL zp(+^aZ9M5DUxiwwhE=a3D=L~V#Nc2fd{-#eSl!4H^g9^r2~(`-T(}a)?Xq!sKEe7{ zo@&iNQ6xfsC%v5kCPvygIMz;Es~4Zw&iG&pxgn?QKCuCxn>CZpWSaxCT4Zx8gXVN{XtJ|W*2(V1C}kV{nQChk z19!Nvx!mN+7H6m9Obmv2|N9PdxjjNQQ$W=eIy*v4jzrl`6bXmiRO%KjAvd~i5b)ah z&{Kn`szM~}p-`+*s?@P83)2!L(q&Sa3LQ}|Zl{-OwZ`mv3RRH__+12iP8@a>!;q;8 zi)ziJRHk z2~?L4Nto9vw=1fKs%dC;J2tlm!%`>~YrN-)QKnl%AWUppqYR^_Dk!Rqsx)$n8x;@) zHdW@Kqun^{DwZXv>n4d*k%8_2NDVW5>hv}nkN^F{eQyd}c#Co)Mo;`CMmeuK+xm~Wd&WNHY#;pC@K9Tzt3ANW zrxy|R3aX-@+Eg@6L)-J$X18IpX$KG|du<#Vi*okz2ItSt zk=t5Fbq9#{_3`l0Zoc#CGNodPV8};ThoAng5Q?hebSNyYrty32Tvd`}1q%W5Q*nWlwdnCOOyuGhIb zzs=}i1X+TG)fDwgg?goe(JYo?=mw^)H=e6tH6AE6d9a`M_7+w)3S@WURJWJW^C_(6 z8f8qgQC7cajKE+&NHS+HZ!kF=CKPb-(%BeOSJuccU8Ndd#WQ$>o(>=BT#Ztxf@K&~ z>H@=(v4kL#E&_s}&p}Jb!@^pQw%%?6-XU5-9=u*VvLsQi)JdoFtS%QQ*2K2Y=lqk$ zkN14;KmOCdnLYe{6Bb;2OW?j`fC0Y#FOD=Jin1jA<1hTg)&F#=s+&KOD^`E*+|!4o8#A4-wUtY)MQ0VRq5(+wz6@|6UoL(*DPFuCoXNpUgzKCAQZ+!W8SXub`Tix`)8<-~D ztNihQ`8WL9ul*YK_Qz6+!}VNob^7JX){;xlr+dw6(QejCShWhGS-#1tmO)miC_ctU zJE#kdT(;P(5_jE+-z@lsFb#}S9@8|*)@^ilhUw^TBUMqb1UMpHM8=Qt=%ZuEl8npQ zcoG@HnYrMyu{AJ9I?$b>1;)Wg06+h(dd6p70iGAjsN)VQ%8R0Cu`sN^iPmYFW!Gc zzFh(D%G&9_L@Cs)((?40B&%P?GG>6Ngw!EPlCoQ`N?0bAUd7TpNKQZFqn*TaCe=c= zk<4e_TEAJCI%YYKWm;rvHv0M^w6?dBHQl&dyLj}G5!zZkSVFM0p26+XSlcSH5ig*~ z5^k>>hs%Z2u5fg+jh>DmhG8*1zr*x=g1PxEW~Sy@xO|n^%oPgBBz9kbk-;d7i(BkW zy+(2I0=3k3vQnx4!Dg0U-po|KkWXjwD=+?2mcISpzuV3I)|=?t$-;%t1JF14J%#Mj zl|Ks%OuPX6B=AXKgy!g8FXkw(Uu7v2p|c~%mRpEL)u&5q;>k*g^@cC3rh!3c|M8J5;_w1(Uq9*Y73Rh2M|MxX9=Y3!uSoSoXl zrYW4gyvfqa4&7~D26{r2Y8K^kyg9d#0^jzXU z*xcS}qh2#t7QXf%n-_S%fOjREStgrV7J=YEf(GQ%fDegoVH!4}*Dy5?Hcx=zp$@h) zI<-Ouvr<4(ZKxhUwm=j|v=?XRFrMBCd_5xsqU{V1L>U{5AOsDNLNL(nXK_8t%jY-9 zmvmY~Zro0d*`*Xy^C<#82Tq5^^o1F+tMhE`6wn-Y4o-C82((a^+{jKZj+PGkhPqdL z9_O!LncMzXTYvjo&qp8szRL7VpCgxDe$dSdybbFn^bI_-`_d1548*4-MLX{58c|!0 zJjK)RJxU^7=KM=%sBEt^7E=4dI0GSkp&;Rw0O7Egpx;SXyPrx`=gQnR#Zry2p;oem zI!=ei<+%jiZ9XC)C+o2kbF*udOBEb}7M^@~fR)t*m%jZhg~bcld|}+Z2k00X=E&iG z3{&FbbSzUW)&IJuJNVgu^K-{8Tw2%7@9VKW=;pgc9!MX2C)wln%puJG0rIycMg2JN z3B6Y9pPt*1P8{wgH8DwjV32UgOE~Po>v15<66K0crBcV|wo$3-eB=2Uw%0b1Z4Pw9 z;-l{yXMH=*k+D`X*%B{)XPU(FVq@7!pq2LSc5F6<*y<*=#5#H|g;B_$7jx+OB)N39 zdh(%(=N~>X@aZpnYw_8gtX}DT8!uLWTbStENj9@gHoHRi!#|i8X8n|J=*aW#XpbC; zhWdIte6I14HUa?;Hk(2&UuAVO&%$b!e6h~ta4SBqoo}65Vk;KMs+Y03JPZ%D)7kFF zVOP1jnBx59Rnl{p$j_a|tQ2u|4s+<(IQe3gg$tJ`txPwjYnF*wD_KS%bJ-Hozgx+v z|L*C*;Dx{a#%bgHfBSn6x~c9cZ{J(*Ciy@9Zi!Uha2y+NdGE}^&Od2waldzYqu`jC z-@!6X6q}vyb{~%)>%!x<@wFG1Sl!5gQ701iaO6N2LBEri&#t1#f|0=}r!TCrcK$UA z^XJe45xO3FhNs_ih*w^nW9d6zr?_-+Hy*tK;tz!ozgthl78RFQ#CFa-=q9-9Fv!D6O7ru7o)xZD2u^$}l3H`$QX6{g}rYqw^VMh8xC<=V*0{2{?&_T)cdCmHDX|WJyAi1SgO5pjWHcLXh2k?Uc$o$&C%_sZE5T=aHnp z13m-NX-Sfdt>Qe~{e#CIxV&Qk12Fr`{QD!n%zygka(blO@jDgadDiQ3{Pg5-2!65 zSXkVqyc4S%<-#c;#AhUluOg%(5_imAe7nj!#zfyv{_6{yAW3SyW*n~@)~5<3{bRX8 z&EMDQCts{Fx01#*1&lJkH1 zPagD7cvIzF2Y6S$_uqeqk%?aIwQqdq;newW{bD7)@)0b{N5j{>0Q?^CN2Rr?4Ohn~ zt7|Vj=u3V}VDvdfPW551OI_Wny>jz92wt>{QnJmaB^>EX>4U6ba`-PAZc)PV*mhnoa6Eg2ys>@D9TUE%t_@^00ScnE@KN5BNI!L z6ay0=M1VBIWCJ6!R3OXP)X2ol#2my2%YaCrN-hBE7ZG&wLN%2D0000ywJQsNcfc9TO8tQN{O^_5Rgwh$ z2i`?SUIP9Ih6Ib8wc`tw4+MlcwagDuHILQvclUUz6|ZHakGVeYya1@N*9Sm5Xgb?Q z;=4)#hRm$6SNFE{<5w&Ee-rwM=(wS-DzT%z0YyQ}jd(0yZmGvzTf=+SEW zBcb%9oNInTP|$rMo4Ek0^aoV>$lDJ8*7JJ8lh(yIEU9kiQ!BY%ck;n$Nc+I2t-7|L z5O&|=>8;E8H<9Q&zuaDUby}bwo^&ES$P@WV268I~9TA;2=oaC6tv45OXhJq+_-?<) zqet->`YRc zqo4p+v)vrj*c*0)KQc8&&}#rvbMu#pYTQ>w;_Jf^NsJwfht;LanP*qT<$u?gqKVX_ zj#(Jn;UaJ7V#v^QTtE23hb{_V$A0as`T@~Vw#Ui+NIW2S8kITBdr-rtYQFc<#(lDj zKxScIDTbg6L+-*rxu%9;uI1GdF#+Jw+$=jtE?o`QM6T$duGgR(MWMVeUJkb|$FDe( zYly(d`lAJqJyBn=i$y2~BW#+tZgJ~z=WanQE&2fih!FhH2FZf8pkyXCo?al%snC}H zMP9-xVGu)JC-u4`PXfKbfGzH2(VI|^a?}tpzh*`eA0_QBtTEVA_eeVRgwFBp-_M% zbMC|2 zTw`CclYd}{{n%DOKgVGL1Rn)%uYTCNb%St&zLWdG5BkH}p)ed+bl>?IOoh{uA@&xN zJ|9XaQuB)u_o7_-phc`dpnMwkH<{q&Lo-A6K>CoDLX#oR2>lI^&whc7H>*7t3VG6p z6pliF6&<-GttVj_NJOJCRHgHWsD-3~+Ra4Y zErAsXMBn^X>vP4qbiwR)3zHHc4CjZ|3duvJF(c&i{|i8%1%cY(-ddn$`3bH%1aH>d zYbvtcF8rfYKXM%U&JAx^wpX7A;ijN_VBfyR!#~vqKIB7Az{;ldr9=3^P<-$PL88x{ zJGk1vZfv)knYYS1Z%oSiE4Bi<4=H+^RCRi9TOU@OMX-bf@_gwbGWni^$rIqNH+ti! z1}Q`~aDI0$_`9|kU3Uj9U2-s7+$EhaKRN8Ieudp;4){dKf;>ZmHYL;QeGq)1YAp=G z#*Ub#d?G;46+sa0-P{h!L{+RK`mMVMbdP1;+=cdrXaxZL3|rkUc;MeeAMHue$xLU2 z;segT@4_KvpdH1?{V*v$5F-Yscy@dTT%&!P=rV2aSa#pTY)Z6RbaIB&oUScFHZ zM}skZC4I$MCo9T;xmH96&%Qmeh;xn%?|#>DzmApx{sGr<3xA&N)vrXY?2}tiOjnTg z)0^(##(hwMpXKy!@ppeX3b9>WD&N#e7hMsrN56}KckAlR={9IfG`OWHU(cHDRZRF+ z)HkN9+&~(S&+y4dl-hU2H+u4~Vi8p2e#Cw5K_lypH5V*v9awrT_!k!d_u%NYaJfy$ z>htgpbIG$O$;W_Gg-d_?K?r>i3D+lTX=iS{?wv@PIr(ONRmV5J}lR34MIqzAS@V`}`LN zorpXIxeW^N4|8x5JA*S_OKG34ZJj@NAamGg3oto#HdJ&t_aXs=-aUk)5$m;N#jIZs zdg%i%{O`Df3PHlmME5VwJ#TSa^M&P?L*b+zCv-|`u;cah006Eq+?f>57@)NkT5la{ z=^ZVa8?p`Q$0cDkf9HAiMFd&|LOk|L2^?kaEafPcD%Ew*$HTPXJ5ih<>tjms*a5TO z>5RA2ayaU8V2K|Txv}m8H~Etlx+3M3oeeOXJaU8E?Q!Bt0Uh#jPH!F4zz1y};O293 z5ls%*x_rlll#YrbjLCZuzs~RiCJ33tcy+X&EJ4E9 z)Jb1tC!2ZyvYz`Fm7Z{iL9N>RuUQO#-tA5p9DLr#5$}FJtki`&={;}w^#)q_eKD1R zD-JLaix9?*xa^_R15bbrseZ%9=cO-9*A&4vve-3foai)|h?vn&M@P88cx>wDK|`jS z3e367&yLTFV|(v+Cz_|452pmhkGBrR6+c51x9#*?$Wdsq>FtQiLHR;nO7t;6@Qa%R zAd|o;)z=W@cL{^%9TNR(?UGl#Gy0%?f0W<;lRN@FkDk7p{3p2_8-|!F&MFBO2*X2= zEx4`JpV8oTSftm#Ugg{8bL>+0i|zsvbGG2s*>px~&kGsp(+t|5K2(9*dGbhdu}?Sj z9{62N^xam7{o=2UCX4Xv%9(b)&)(*RPUG+0IMvy&8?eEyjEXDQ`7J${fQ(ax z+)qeMNa^|@OoYN0@jsZNI(EStpngY~^dAuF>RNgg6d}^Q&F^~(9oHc84|(V7v5}b> zx}u%gX@Qx#OW9zOx4~(0iZawG$Mt}_7OEd73df`FE*Td$-OkQyz)$;J3Ae|N{oCV@ z9$9Bc?p8M_s*C>g*1c2jAlY@ZSNI>)A}XAJMX(K6q#1TgHvb+U;U-e!U&PgSul(7p zPcS3UR;Gs8>#zHSmr3l=zOnAvkw5q-?|GK~>h^@C_cr(0d}wlsSQ|Y3QE5ZNHx(iB zMh=k5z-a&V`GCB{1o03*zp(M>w!Q2-FvJ+QUeM+SRSVr%1K$b}PmMhpjv0dvgt_)m z)3L+asEr5{pf-VI%GHP4A(zP;VUxxrx00SSu_kw-Ulx8o_s#vtG4Ov#e`ofaSNu?W z)%;lL79@Ge5&zd`;g3rmfG!O8W)b*AhHiWZ4wbwx7c@p!i#-3B7~M}THallKIG3vO z+7!D1+faBc1`wR+6bT4ME2t^^hWK3KZ3s`F08kH{k(*uC)WCq zDjY+Iknl64lpBQ@vYz_r6otJU5TSHaWq7`?;n8 zdfS;)aaIiP;WlKFD;IeJSSMz4-~Q?!LN(lU)bgQgU3L^&BXhhRUHY!K(Xj4R>jf>k zI}5SU4x|>PJdqGHHmeF^akU+Xf{7}pv?2X#i0yyL5;y@7j&?V1nXZ@3s9e_kKJ?RD z5!6FxXp9ua=x_nCbk3{c9T>ePY;kDwm>t`G`o~^>)4R`g?Y#B&dxyc3Loe(v_=*Dw z#2<(uK~L|5P3=IbF_NE6)}r@kf*Vs2aYmQnH1uFyfYOvF&(1I0tR?Iv{nfLoxvZWzRg;s;(|5FD@L; z|GKnf?b?z1j%+(gh+V%Z2V?Bkp#!1q1}Je+wh__{7!1{Jc$y0*Tq9&Atr5m49pK)-G9TesH<-hIW$`+q84Ai?e+UuqoMSM%h0fetLgA#&qXd z+F;p4UAov1s&}yC)q1B;^G`En`_W~#yBuUFvbSoRVB8&`uOqc6unathI+(rs;T=!S z(^^AD9XYO<%4)+IGOb98wYIs|w9IbUVOKyhupQj%3MP3y4t3t2B!_L>t%K(d=PyTb z5PH87aByhQMUh}+hJ&%c+o`Eba@$o;1LnTk8~;qM*l2(|(F>4E}DKs%^l+F8-DrsweKa6KC$ z3r2wII#L8!MA$CyRr*C^joT(ybubFEK&5z&6R7=e=s=Ma8V>n`k#3F(B3Il)4a=Iz z8U0)kfO}oma?P7BT(JEscsu~@xGe&&X13d9CmbKIFRwhJ%bM|8FIvxmm!A%i)PZN$ z`EZm!3PiEB^HPr>t3|v`o{t?VE4$$#&vY^Ao+e zo0@swZk#osl_5YT#_aYGYy;fn-t=s`xK;0MjI+fKafro1b@Jf*Fd^g#>jpQif$VJYPbwL(ugb@D8ofkpkzC9oW_$9X`(A#A5-atK5|j}O*X5eQO?99{b7~Cts)E^b(ss? z4px4i;Z5Qy@5kUiRK_NvD0ld!$?0yCY7%ttnct&ADxZ~tmBkXsGm6pgDzuvO^iK0m zae-#!#PFQxqR|iN2=I|%(0bWlYuhyP8tMX+N2zR=4rz$tb?xmx&m|sMegNJ#5dV-g zba`8s^4o=H2K0CBfQixrb@e;VD-`_)LZlW#fEs1*i6jXKa)SjUC9=}$X%70y>t$Iu zohmbO=0Zy=o7TK5#Kgr-ZkSjz_?XeQtEq&&&7SI0fmhr8C;qyh9cU7-LkJ7d?|S-b zf8lIlfY$;|aRE0m<$D3Ol)ZJAkF(UBs{BszS0uueGNN3%w0!Ku99kk_))foggYqjF zS?ZyACBrc*t2LFd5sBerJPxTy9m%{fJ!neS7mzAD4=Xn=>e!%@fSsI~))uE5ASgg| zmgBH7G;`VQmK4r!*%r6sW&a~FzRT~gNQf4LG$pQK*UTR!z}|f+kJvT>0Sz`)f{c?P z<-q=qAx3j#Rm+1w^mjkMytyP>RLtI^7gk-Uu1rl`mdVv+l7)>BVzQUU z2fSwyd~Tt^b!+K?*5fAI8a>#BMoeA47ZeVeYwF?fkC#(SGcGz`)eKlFG}eY%b2=J_ zk)aF9>gW{fP#HevsAE9Vc6&E!X=Yj>_3{J)*d}A! zponBEj)v6#T7DTnb3Nx6eP8<;#T>ybC{4~^ZvlR+0W$R+(GF+2fT^yaCHJ6c{$AHO z0JrYzna?Hg-2KL2BRSGNKsM2=Qy)#ghs=N_!hzVj2-C~kK0T9+I6=urv{5O`k|Bgz zc7g%Bj-QcQqVH6hMJ}@}0jBxfVgCd?^Lg)f2_fUq#+wt&Mw|Mu7eeI{;|2YEjzz_& z!mnuSBLqf_ck3I@mc|%cHZ;9wpaIem+MGcx%FBCsN0!;2JyRA z-N3%x#Uisd`3L3a6KhsaIUOW(&+@;7OGP6F{;~3)lxdU>(&LhBGOtZ%HsbtN8i-CR zPfPgsNFL7P{tl|?9!JNfVL6*tXukKN__Vb_dTB(HgSk7$Pi!Du8U@HEv?<$_f7?&0 zaGVqHJQob+naYeatSBKXE8eSxcLa&s_) zOf~N5s-6yyg2NMfT^}ncKX1RG0r8sKQ?_8%oFL?_g;WAI&JbBYfScu;C;DPX$f*z} z9HfLYV3U}_fq3ngweON#{%ghQ1s(btqRWNF2%ssZoP3;341suUxY?FkM(o}L0S@{P zCWfhun3$NdI<~xo8?olI9Z`2RT&fwYgtMBB zaiXZt*D@l_vs}SKQL7+gOPJev#@?7iPVP~p{KQnGy?X6RE0$?eDO6!lX4ah1wc}>r z5wv9bYD3yt$I-2o7&%KyOi`+)I}#N}9DyDgiWuIR)zMEJmDs#00$suVw?q4q znwToxw=fL`Pu*-)FeYQ&pa#jT++g<$5DemT}--ukf1HE$K3?Ejh5^Hy<~*5!m!vLJ~NZOp^jCu*S>oJbJRqNBh)`J=-AtlXWHK=Tl%x z>fKXLpo#RqJ3|DL5f0SZG3lir-i4lK@d)(QK^N*}=pU?}vC*N$-Y#E%J(=X{c@Os= zNZgvfI)cdk82pNQPDDwJJj05NtI6egz2MyW^k!4Z$Y6W|hvwV(o0^;B_Xy^t3=3b{ zAC=RYIg-Ch*b>S-UbS)3%ZmAbdn<8Sz7cH@i#w~ zxmV-Pc{-nmdH+0$I3rTTbE4&Fq2+jFB;;eyM#R}Tn=ybGb&19#z+`gPnkX#{9L^k( zeRVUxfcom>Y^7R-ZR6lMu}z$Krv6z*X(~=P2nfnLUr?S;(wLr8pd{ecRJAhtc@>=H zPB^t|3{~RPt!+fSFb?c->ABCSJ!a0+AO_lLtI3)vWc9Eqb}JRzm*$dv9BxgNI<#7t;8uG z$rx@>B;8pK#L(dS`8K-MHF37imTwsFo+LgoQKMATI`A@pTejxipEQE0KuvI=IAcp_ zo1()b9r8wsDqoy#@C_>tmSqw^Ys0Nhcx8$X@}vDr)kT$`Lj9%pnKUBN%zZ=;8_?md!G7j-i{4~Kqvid zULCQO^dSWpK7M598kx8H%!-1}QHnxd5E2Qz&KG>s{`=|~3*R7S)iB3hur9;uWpFjV zyj}Re3s@)^4AwJ*4TljNgAtH=Q$Tn!wdaQK^fnq{yGhfS9OnKfY>CaD00&0@IRyrA zFVf=ZRCf2VOwF2PYylNB$kzlBdEUseN|GA0myIFB>;gZq`K~7u(rLv&kMXDGqPnF-&O*K60swIXfflQEkEh=1LBaDaMRKaXb2H+ zpCaGEL%)Q1>T2op3X?sxT7|iTn?RT?W97SBI^c zZh1d-vkgDg7aFf%?iyNsgG!{viVbP8*P_NIN57&PWvjAIHZO`oM=h>v5sQ4qlo6Zj z^w=eMtD_!(Mm#|wkx?$?c4ddV|2rbaZNXD^%vjo!r; z749r=%j&h(c8R2oKGrYf)VAXV`ejZZa~wm{S(M2L&W6?@En5QN=s}yd8Si`02#|+N z)5;9L(=+gm$y58ANjAG#CU4#_W36$b>B%dtAJl z38gXnIRJ+;N33!FNbHIkssi%WavkDow*B@v^PR)_7)NHs>EE&a^9N}(`E>$RYnC9o z9GYYWbd=Y!zdGa{+E`M>a|~5WEA-82gg_&0)D$zfaB0xJtLM8%l6IpdTAva`kK*2# zT;MIk`VfYWxT3JhRD(<@9$Y%$9hUUt-gIn!=pOm^OBRMrDTE``bPO>B86pTHt+-9FbHgi^bda>31b(f) zCH%(@5677LRF7+p!Rxv3p5n)YS<2FvKgLGg$174#c*57&J}(W531^de)~n*NXl(D_+A@HT$Xip0u)cwcWL)AAV3@rhlcyCk+ z#LAdCX-p!Kvi|o-qf7Vh+R$xJFnpvi>8qN$xnI%G?qy1Yv#VrHbI+Gqqla^%?ZkX4 zhTwyKoF&q=1W;E}8GPt?_PX?PvqYiJet!|cBKP-ybB?Ga#2{rs;w-}9dfUxzhv3P3 z0m%~ij*Y%%5)OG9+-NYzN-!k=)w@Z+4*nwdri1yT`+zQHm`+<1i?ZogH89uzWx9){ ze_oMzpD0JLPsspn>v~er`Fxdl-v@GhT{rKEL;`_YT>^>jdXVkzk*LTp<$}e-!Y*|_p;IXc3!y$pXv?u zaCc3tU-NUOM1_HqB^FioyWP|;o&8yp;G^~-*EO*;xXFDRtw|mC%7b4v)tLjSB0Muz zO9R$-DwL3=#^ZfVNzX}bg+ALNn2=iY0f3 zZFq-S8xig*LGW^rrBwTvpkHU=zpyfxnNl_IUhJh?2F9uaB3j|Q>|FCw;mKYR=G4sx zk@t<;eRH0tD{8ikM24z`t5*({YltH2@YJoW!ej$*j;QQR<)H?e?bgBzHxZi$2NJ>ygkvYz}g|@B-_xn()#SBWcs?-YsSxiH77N`=( zl9$UqTlZki+r;Ofj8({fg@KQ&pUtvLu0uf!wBiWxmcj3Q?rGiUlu2~3&D5xx+OKG+ zw8bWvxJO6zuyS>o(rXp{YH-vJMSW9o>a)M!!pp-eZU1c;&G+#TAsjl3-#u2R3JBWE zuj#=9IeNU_w^%I_{k3-0vCFpP>8%qt(aYSF>PjqJu%)<&4`}hl;EX*p6jl_tM<9Bp zM7kY6A_+F-8{K&?gn8G$8TvM)g0t4VDX1q#ZbO)(MQC3cKD&cG^fO#zjXWFK!K8bn z>6Cl?!#CXsTU}J$40&7>Ng_cE16ARkO(1@|h}&E{(_nB`S9%n=c@K(qH0o5z*P;6Y zWqIe_mq(0zd?xctg0zHo1#WGo`pv1|CSS{-MQ-}8s$$GF?7aB`8%DE)jU8&q{Q5)F zI)8}`yoUQTn^?dmprO8XY^VY$2IZlk%#TTt*?E7AVN%DJ-y~n-+wIM`1^&_a6>mFM z#!au+Z}pV+v#5!Uz9*!)se$=Ien%a`;ZmyUzw}BrEoYNr>ij#&q!9FleAC;~B_^ge zz4$r{r7@#~L%0)YGUVdrr94mP;37-Way9po=h^>qYgpAx8aJIvM^y;oXb;!I)SsC7 z(2spwlj`$#_0GleX2@!aBwmLUfQN2D=c#(w16-N`)-sSB_j-N}%h;G&p2A=l6L5BN zqL&cZEdaejub4}CP|>_6c}SA^u&TEtMN0}%&HpqM(#wYOZHUr7r)#V(xbVrBbkpPY zTZL=|ezsf7k*JesmhSfFD_yQdgVv7ov{1jae^^~0aw4_SD%ZVa=Fh4?>OiwJ+sevo zJpV_`I_dc9e1<}30v(cUr5Q9#4qd)br&yJuK)V&&{VVCj7_$|I8k}X}&FRsBy^;D5 zGk)xGPJN#}O8;xk>4xUknEcbV!zU3+n8fmY2~5j64rpi@q zM}n^Uz>p4vl;XCPvUVf(G!$nSgD`eHjkGQUUAaboeheR7+?_DK4$c@D|ojr9C;h9ryWoI;LpwrS-93w@7zh^row@0@X zEUop{kq{;m*7P`K+~3QqsT=unDq2zXkc>etxq_4Rv>vzM9{Oa@+sSC;xVwa(!%8@z zk`0qDk_knjI5*=JN7<+v`Mnj)oeDw*hEB#2hP{eav%4n?+CNV-eXgUKonIzs_(*~m ziqs!H#K73y>heI@qf^bs@mGpAyZ3a#l4A`Fz3ki#B7SDE=1uMA>pq6ZgpZp)QVa$9 z9Q=bq7s`oN31n^#p4Itc3C)`V3f-07M7e9mD|Qg1hkS_BPj=>-T&sWO6t#JT9^ANA zxMAZnRB!}U9|h_UL=GJ>ac6|tgCjK1B^^mu1PqI z1HEj>FaWKx+IEF1HS>otSB@HZZ4I!3Q8+JZ-@=OGJZ(p}MZiM9h&_OHNs}bM`{-%O zA)6)eSGKS$iTQ7x&OKmaMsl%pgp@3!7!%Qx$B|{ADP5jPKdZ3KBl%!gy;8Eso8;H6 z`8ZsXI*yF`uO!3Mzh)~N&7ji3F38NT2nSn%I#Sbx@#IsYK}tVNjARQ%6o-pd+KOj5 zO>^11hY)&o*If)|aIoH^S(8kI1DfUGEup7eGi|TdtvJrCWeeh&YK4W`aWy9)b?}z0 ztyFV2sBh%g8>v|>o@|Vs@~76??bvGLx(yU;*t&jqTA%i%S2{=6zTJ+rxEl7xC-|vc z*-UT|J!hSXFk7GpFm5_o&c>}j7{Zb*gfoGG5(0Nl$uzU`#X3VQnC#=#w4x~3BFQMP z>tpx#HN!>~oH?l?$cUwM5HuwGAsX+j3%~7JLY1rvQ2w5Wr^))Wf`JL|tLEASCyzrYMgbYUJcHE4Abf6`T>BQ~JC*YKJ z_4g}f65XTA@Z*KN5uu^BRu!L@W3pt~;G0T9pI(*?lB>R8m$d!*JSPk6^CV%RxL~KN zU#yna-oH`D{@^4Sc(m=vhk$xWwz8t9;TuzaI!-trtsXH?o9) zSekMiGhHp>)R_ibyLg4mikpzf3tq7?eCEo?ICxLM(fYR@pIqB&{;!IBd#3Xsn?vm{ zFwJ)E8`z1bF%K`-CE*B)S>$YfA!kq2Wp!PQVNE4)E>OK}v)^Gm_XV791?6J?jG9w2 zFld%`c8}~tQY&U3S(tT+*-yv{VC*cgj|(_E#bbd$Ja*a$YhnoSh4qNdu9-D9k3E+J zW@HM-=7Oy_;s6~5mTe>7hS7DWP&(i~eM*K_J8&0mSAIVNIp+GQjFm%v=fyS<2rwqH ztJJXLU+$`47;|i@Hd~>Os%UC-zyw!4a*60xg(vE$24c|Yz=ePRj_~A}wR9rokr>Z1rTTCS-ko?}YiogV8@hgZ=snq$fj8ruw`MBMt^>1E661$gNR;q57%e&uhMkESwcM% z{Z3YjC4L4-iF_$L59-YJY=SML7B5MEjD=DTzJRNLOBFOxMR0U+D2|o}z`|E=&;1EZ z`>bC(b$jpl2lS~edic#Yh5%k;;jq&S%6O%})sAGctgIQd*jHf0$2KjP;==zZk}x1IB@1Rla1!JMRdNA zCQG)?)YR`0Em9IwCR0(LWpX60G{-4y6=U5R_v#*AHq1&6#hI|~%O>T1_2`~87c|&Q zC=?g)YK&`0UE=XIN|yp68xnFYwSR4i4gIb)IR^ZC33Awwp_XxKpup@JRCOEt!H8irEslGdk=5BQ@L-H%vZx|$q2Ls0EqJ}dRiqq^ znn23lsM#8!FnFQV7+Z6+=24}Z1D{Mj$zXH_QPQ$XVeg1hWVd_^q-2n#XaAcn?l4WC zfnBg?bhMCHZr*sa4g)A}^9<)!p*!(fcZMmGs0?l7Blr%3B{LkJq?f*F>R1+FqU{0Y zSAapLX)%6RBu*?GzjIckUR*OZr=KhS5Ed~wFp?OPpSeL%f0}W$YE*wB8cluu2+RxH zwJiT>|LsSK$<5n$Zmmp%f+nBX#WB|j>roQpM;`HRI>Q9tI9Es;B|nF1dp#DV@{ICrWg6hc>Hb)( zfF|?goK|O4cUwr0J*K>RJT(h)p{{(RdUZ3^83&6*o_|(dq$sJNkaSns?Of*Vzr#bz zsb6_bd=304HgNmgyJUXNQw4&=Zz;F2k6i5wa=zDS55r? zNkBxMS*M)gU)!dbguiI%RjaHo4_4Y1NG1*z_=!Qr4yX#sP2;sW_=OGcs%J!Nu74rd z?%Pww2rz2BkLP)ClME9Uly-0s-dSe}M?+)h`fci3_)~zef5tUt_ghsHZ>9Nt;2fCV zEJp?ta33nBl(oEQYcVx6>gDNI2QirBvo&a$fBp!w5wzla76KRhG%6&$eIYsL28zBL zIi=G>w^7^cuaXQZXj3T}^KB%aIHACIr9# z7!WeYEoLQBCk9DAJRQq~Nz(*%I=V$RSXfvwY&eLEEKurD@8E`daJ1MRXw-#M7lvXz zH59_YKPC|4@BX_s+QksA$^O;H!I~vPBq4E^um*e$!(%SPl zR`&0rrX`cUD09_L8f_v2RT*Jo!OpD}esOF(cIP$nrU&!K1i9*K7>^hEc>mAzhC^IS z>>KHFc>dq8>%;7cC!#9<;8DFdysM9w5wwR{S6yzRIo43hZ5$6QcENxh2A3Ff4~h(V zA1r_z9(G=LfU)KYRNm~ZJaCLbmF${${$Anpkp5K?-dL|KLF$r&*FRrU$Y3v0mC9$J z1odh)oqRlyMTcI&W*<({ie$~wouuA??DtoFvhE3V@cZ@Qp7k%DiCNc_SAOX3b^eQQ z7GIW0E%VQ|)nc78*CdR^jb+vX-H6?0O7}H$K50_nk4eT*#hZ|HJ-Evvv)I5GfTbfq_|&TW9LzKDOqrBU=|D z@ND{e6ck245W(J~X71T0QlvC!y`bFbmtmI~y|l#Zm6zKT`|UX@bE{{)@&;#P+j;up zkj(!AqNa!B;AWr2nqJaopYQx0c4=hYL^uSk%B4YFu#V&7jK1q#`yuXL$^J-=`S&qC z0R3h8gJU!;_xKqqs$dqtQA=oMdwb9>=0Y?w8WlBNk)O#$PnwucPKRazR?)g&R*}Cq zL^r0?%=f^#rENoy&vH-C-SVnIN!2O-qS;P8Q~OWNv&uNV#&|R zm|LZUTXMMWDhsDrvGAcAeQHJBizPi5VTP(;5v30`(Y|-N0?$tOL&Y$yMWO z9uxbyeP1AQz0I>Wb6D)NQR*-v^59GwJ8*`9E9dDi%4+8IF_;mp!|v_5RPe8?a!4hJ z(KehAs4+Ch(~=%wa`FmF{QZq_!W_Ed*Veg6@_M7io~8QGd+0xJ+KR5Q(@jXeEdu!>O;3?`3a7fF9(s1NX?=L&*})iq8d(E}wG(Lf^jW z$Bl_F{bV65B9N!BXK-myB_ST~Ez`6-OueFhP0N|QoxnJ^ z?4l;VXl-UUT`PYWa|p2juxC^C$$5|3i5Co);M`+wi)iPq3FsL!OoW(defNc;gNoEvqPi z5s#~FTA<$Vwjs9LahfmtT*Xv%t(#)%i@aXsptkR)Fh266!a^d&bp1ooM&J7AtF}>A zPo1@5$Ii=o$S4!k&^Faj{V(Z*2Y6q+Ogf#+Bcb=cx@`OdTO^kbzv#8qN7xi zr`siJQ|@$Y__7JI)E z$9Z8I7=@BheZ3-eLQ^lM={{d*z!QCXp{iCN*!r?2-!kCX1Oc4f|1MO2jIiH6s*AUH zJRJf~7gMk#De2Un3JbfdZ>JLaCt%Zg+OPXuL%2TaG3;(!eq_KsG~{dZ#Nrhf;nM1qpS zy;$X<9hCM}+W4v z%1A%v$W|kh^n^BATJKg(5iMzrYUTo|(DxfN4bS>oeOurqW$+4M_ z0LaikO98Z7@%cdkQJl)92dy)!wN>i$ZyTa4hiBhX(cLrsLjHFduo7Gyf7FD=>`A!}Pw!)%>Ne@CXRJUANevvBn zBA5u{b@xoR(Zsc^o|w^T+i4bxeb~M&$1h%!8myb>z{Tj$IXAB=x8ny$E0_5%pYlyefXLCxD7}WaP=7A0U;($9n&S|3S8cxi={Ib)z0p!GgpN16`9RCY_vKt7! zCmh*tm>Nq4|1_p;Lo>UFYh^IYg(G_0Lqv*m2jE|=IOID?LuUi=pT)B8jWfrJb>;0_ zh}IY(z`A!q9r<->uE{HVrQKhT{d*$pR6Hw2{h}@|u;K!?A!tizsCDY2Y}D3v_-fnh z-jpDv{3k*lTs@*vy#_(ZArBqP!jIye2t4j`a%ujD)~pqP#UXJ>+mk1Z_}+RL#)14r zjw?@Wm1FAj18`mh+yHFj+ksv6g)OzQz|1UjqTk;c7jM;RCFd&{?!W|{^^}I23U{aa zV77c-KT|yV505)*zeSE<@A4o->Iqm`gY0mIuFwY6nL`FrS9IQljWsCB&!xsXzw8p~ zS4kW2jVKxXPJkrK^)vphN85i|GEf=5t`Hyz&H@ra)*5xO55Sk+8hH*8i29Sh%!!>- z5+es5DJ~Kt*MX|3b}n5*W1i7B<3I&ZtOgzM+9{t=p`ZbHgga9LLg`&)oGG~)hn-!4 z`(#hBGSMNd*P>cj=?PvUS6{w!U#doA7jmwFbxuf$GxY0&Ipf6K9vN%&UmE^28*j#N zBk_LmrhFEb)lPnbPTFGBH zn*q48@R2Zd1=|sfl;dGD&qtf(2yx1N%PdwU9KPUSwU!`O-Kut~%TVWghW(NNlUf7f z;aC8@ND?$?fJK4z+OW-H@UnnEmeTe8vgLyfiV9Aq24T*cH+lx8tQ}ehXG1t(<9!Uu z{Z*V0?@;nFOoKDQSZ451vRF&AAvD-FWXv--VG zu})uQq{gL3mVIH(NfBamC1kqX?4u7B6kZ?i!Sz@%ZiXrS(T2|1ZFWUu@DnfiRT1O> zepuVnz(g>qp2ZsQP>Zzgnp~B{>1vfU*L1$yF?h>Nd4%L5<$8_V!$XFNJvYUvRg5|3JV;#B3u{F21u&`or1k*|1TDk7M))PCHbl%((!NkwgKS}DbbCJ zLd&^rFihx*BrmsDHitq(_xChTv8aSl7M&4yJz?_LSS2@TZm;VF{zqQd<9+Kcf_OqG z(oor;w~pKcLYDu%s9L(Oq;JHDKIN5WoJA&i8jo-jyyK<4E3A0^v!NOH*=(d`9K-(F zvJG)GT#sCz6U_6HV1iTRlnQm2G_xyVP4!m_SQiOAeuxS?Dur{WIvBLKboR`#p8pB_hoYeD*0P zwUn_qvzf1i*_yKKbuLz?i>#Dj46l@|77wb!U%YCE1m&dnPf}31U>s{I#5qD|{jkJ4 zjxcT_+g5sATgUqL;K1y(N>mnV5#`7zi~Pr)MO58tlxt?t>-avg$r7t)P5uNn)>(e57^$bTTPlP`tyeT&X@z<>H|!X0q54yXQ?Z#!o>TB>bbGx@v44;eq-tA@apC-DF3IpEJu-zi4st=Ou@ES-rvBZ}-!F#>6j! zP@W-xS9s_3<)()j4p+=9c&a2GZ)VoV;o6|;=lgjcaoR5b8=Q}`ND!f2n3JrG8>x8T z;^&*FKB1UkVZ%6hYZp>@*wAGU29z3QXBXqK!)5xBO*6&QP@42~iE-|&b&-oi(^qh1 z`BYW{^<2fIP-Ot%w(9n+eyg!bN%K~_q~>}TK2geBKJmJAb(>pKD#XCfeP;Fe$Z+ud zkAOhmc5a&fm=jBB=?6-xLFj+vlqrOnpbsQORHh7O#CcS4(CnJM*`Kp-qP5Q=hD_Gr0 zkG#o9qa5--FCJL#CI++GTZPSze`fwaw#;bP8_5>C@aFs>5Plr7}%U zppGq)9@ZSdsLkQ(XfRLd*k6b<4B&ioK*3=|qS))qLAA zdn%z!2^9S0k8Sb`9v{DXL=@{VNCl!#Xy)gXfw}gKUFqF|!SCZv8qlxR0Hs^&7(xy0 z5(2(@0~@ab+3NQSM-p+dY5{5b9uuLkJ`_(eeaiqis8uzo5&VkiN>J*<`o+ZAHXWJj z1>bDeuQ7qw-{yfO3n1v5=}up}K$uaSXoDF0S=1Djx0O{r4W8wZL=DN|)2pgY#pxCp zk~)qBibX*5OH3@Wb4#y5B>SVUU94}wA~siBgLAvn*b7hV#40e8y8Dd6>;>HwZNz++ ziSE;MT=Yk#YyRd53COg_hFY-_a*Qc0wpt)rfv|7kQ%vfBNKylromgQ|RjaJj7;0ZG zC^3&@d!aW%SvbyJ9Tn{rw0}%qSD4vD?`2Z~ zE8TpWNV>TpGwB6T4}kNU%5ql?h~x|m7Jk995Otq%IO}NB=cC6%O6?Ebx#e;3w!&fS zvy8E+9iZ~X+`7u3UmT%HQs*C8-ty{G9!5hwOCoMI1h)Q+=$d8#kNmRgx{BR%m=tHh zJ39DACjMcC|Cz`@Cay4LPY%5TsOT6b^fVy0FU}@1967|B*5K=$a(auCeb0PAIMZfd zpCuNDbczJrH#E5mR)MKs+OW_g5jeB=`)O3vH=dZ?h3_A9J(UQ}R@E7fPBUv|UeMbeG8ErEr{oJZA}4d*A#k>_`pi9jkFiS=Jc-&xz)3G^+`Ad^eb{9lemO%Jg!Mxq4hH^WDKY6pSZar8raeu?HB&snK4JGgxgY`-%EbN+N}5AJ z-B4L&w$YfjIZ$3YF=tX(%^z>(sZ2c6x*t519fr?T0hzDevU$eZ$gO$`YA47xa@EC=Hpi=x|csT$IQ6g54CRKD)b{tCz@5q5ACv+oQ*%Ku~BIZ zY*7MJatxrwS5?pnzi%(+C47$SCNh6fm?M7&H6Cpy&hfu$Xz{y4k-6qG!Lwp;|c^> z_}$_@_EFH>TzEJy-rFgz6!}h6_I+Sc&7qF5oaTb={S8i%jOWKmA~`boaHS%6cJV}Zs;f1>=V z9qMlSHm9qbV8EoOu8yrg&AFe`{|;QAVFsnZ1Yt{sKBcw|jCfZo4_>v-73~IWBJPNh zDHvh45kdnwmN&%@aI&z=6P>r}$J1fLf5SsoY+ z&hg#jK{CeuUxxecs#RjNtI8>bP5f1#&G6j_EpqYm-J1m^YF`IJiw|OiGqhknTsgD8Y$poq%0tuX-53+&vZJ=nB)KFQacM4fvs;d#?$Vs9iV82 z5T1gv5Hc{G-gB5Ab;p-@7`PpnZmjPnLPMk_!ZqN|%U2GeA%NVM9oSR9EXl(Wf`1vT zf5}9JF5g0)EqW&C@fx+HRoC<0AmXn8BVXT~3$Kpqq}87^_HQx${l5 z4O2se6x5HQe5m)L0U>WOgnV{r#=yX-qQR)>ohw;9OtmLuwoaq*@8<3~4xo^jR0+1m ztpZ@|7m7+cFKBUplFB3+q+1At$)xn84FX{-$E@zZ^Te!Kq&P|jhumKdtg&QjdR+H& z04Art8ahpLldW6eBv#gHev{R=VOL6mq)NOuBKl#UBy0CY`%}8M%UAm)lFC*ltA~)d zSE;RFT%Y`R-jq#2}$T>y+uF4Yqmi5+u4pfj z?7gAFT2)D^!Oqwvw)C+E0PhnR67nL`AojUkev5U({3eRKpo+l8u=i9!8)-)L_OeP} zh>xI}rqtzNkV7_U;oQ8-)V=q8@OvYXh|7yrLaf)d3vBN~Z5aomj0q2jnLpn{xPRwf zKb_Pdb_!$P35~~0Mj9kV6e5^>?m7N30;ngoX2Q1W@g$2p5E}9pm8b3CvAK$m+o$_B z_7Vu-*$X3o8fn5lGzZTreQERpE>WPC<%kR^GyaX=&0+@Z0sA@IOxXmUb{$&E{NgJClP8}ohL7rgg<5s_V8xDa*D4RKB$d%fkC%NvL4@_3}(Zf}kT z@>ok``X>#-Q-;~Il`yM!3r`?d1xdE+h%o*q&<_x2i2$5iD}^;n5jBZA2S#w0mlM{4 zf;{&NWy0PCh;})HFiB^^)5%O6<;yGJ9=-Pjfc?JY?ZqF7Hv(PPzBtF-6ZZerFL!vp z&_5##wf-MtY{0B$j8C$^!&x-M%RK`R=)N0{AjR;=JXY%v zH$aW+kF*5D9P8suzMq4EFMc0D$do%KFhD`=DS=b@HOB}!ys<}P(oi+H>K>`2-nY;5 zmN&E+KifgvlOW3%^=nEbGSttc!OX@Dp;_x+0v59-?C+EeMK=4fW!i8ad?qsDYX5D;~J!&*fm~e_lmM}C? zFD36E#;bTD=%w0^lv;sI=DcEo%)-^N1xe2M!d#z)O{UC}++zGFW|h80eZAP!$OF8$ z6U>0w;E>W&f_(r+f~o?L^&#%mS&m750#Mgey&#~bm2U1GKK&_8tnTDOZ(KRvQDH*E zNjaKM8RY@30{kHBC|*Fthq4yg>n{nX#>>CKw9gFh%U{0Y#JZp{*G@iowCI|QJu535nxHQPA4zi zu}IgacoF0veqI<%o8HfedY;nM0dfWNiPLT+cKN?|axNQ!xT9B}BaDWJ1unwUX;lS; z|8}LBW#aVx6s5DXVf+tFo;zJ(V1ih=;EW;cwy%{4l{ZTj&1|{6^{PKnhetjC3aFX^ zxyj)cC%$w%z+Bz(KV{m!u%=_m{nLw~ z9z)0Wy`oYon`DWC1l6jsjFe*Ic;}9O_iPb!Hp~L^hs=%(VQh%H*-b114oS{U7)2ph)46N>rd6P~4d+90<=3P6AHFt> ziM&D;;CW{wr$&%qMrw#j zX&-z7yC7?c&52(Brz&LL?$IFCebK@h5vpTSgcOON1GBuH$i6iuXIz+0eMp9}ls%z; zhI_roYi{eu*DEUZMiY^D7M5mbXbQJ@A6+wJ2L+S4j$jlkBxsMKR&Ru_tN_c<&xFHB zs0BEZl?!mLKfO?j2!e$6#cir|hk#v$R13&L@1@RJO^mshXGr4Y5qZ^hW`)|NI-%0oRA2v9QMe)k!x+a01!-P}%;_Z9}Mh#!XXR~p#V|(blas(X3!U0bI zRi=$QxN996JTrn=!OM6np;qws=fBYmO3iUcYRI%4ELl8(wWab!euyf53Q=up<0hGeeJ$9w) zIGsNrxM7B_Uy#iC)%iov0c!Z6BggcG`EA(9$&Acnz~aUgDPIE>=F18yO`oF8qd^mJjX-Hhf_gx@t$!;j`UUHqPtvI(-E zVwT%qtm$?E$vvnWxDPWEaXkGnDL(9GzTBk9pu_`Uc(tVYyXVyDH~pVL=Gim9CaFe< z`@fDK$rs>X=u!#%riSR+`}o0rk7&mxJ%lV^m6X9O{w?$7$AIFYF!-K9YL5kvnj|@E zHvWVN7B}))QW)$0&xx{!6f*;~MzxOkqM@qc$m3~!Yfk+q<9}qLJr9FRk7KUmPw-D% z?J3=txvO>1jvuWnCyX-a_aQur01*d2yzK`N%x2TB!(LivrfFSDjlwR(;G}4u%y;J}B>ZO%mP1c*ALE8m{Mi)4HS%ja3ml{Z(eGa^#kr6*RLa)RQ*S9`4(+dYYD95)h)gO!8 z$UdoKyJ?&`iT>g|eF{n{^(XBHoTR=9zi3qkhkKqhp_;uTwC5NK9h_*t4_e`csV%m< zG-E&StU5aU=C*$z_gwkp9RyDa=edoCD!vBx>u-!HdmCi&@vAzvegUzuR?*QjXSCn9 zEk70ab~+9V{}tv9(gq^H6a+ST{xkvZP#ejw4s$L34k@A|sf*mF*;`pwh_c4@eTFNQp4v4em*|MVPU`G*%vP(7H7p+o z)DMl&$mu~LK#;1Mdct-`nL{l*Ayj6XQPk*1hpaJkJHN~k_uXrAb^Y_0S1FOU=5ok5v6ihKA)QgY#VL>dv={y#476oOt+uq ze@7`aTjz25Jw}w2h=M0RZ5BPQJhTdbP9m1HFdmO}#<#$P(Tj!9 z1W?N+NxJlgt&o4k`B_5;R0~@N%ENbEpY~E?K*cn2r?5q#J!ogFGP?)NifU5jsSpEj z=XI^6zQMW4^-F;5j!5eg3alW#cG*CJ7$Ayp8A{{hjzB|R0O2Iw!Xu4vpYZ|4fSic` zB^2rpmX_-CaYqB{7}g{m$HH*LZK9s2`-=J{=^oAca;x-5hgx5@w$w+x=B68Uxa<9i zQ)T6=^PT9x{}2+70ZVaGs0bXs*_R6SUksPk7yHau1@M$fQ|F!MCOcu60foJSrR0PJ zz*8|LE5^}EVkETlDS3c^v_Ed;D2H`a=D&u(7=+H@Nzk zKUffR0$JZU7O-|Na}EU#YIaiMWX-Uz$`9Sl(gMYNQ@&Z{Eds+vt(qLU?yK4|nT4d!aA9|YIGKgV z-K|1%KNwL?FaN=u!dH9QJL|ON-Nxq#=rt@Iiockdib;kURO`CeKmFfpW8BV904jWt-yThuyYaoqd$3zSrK!V{_lX zBlY{T4f)~@mz0}1UcsALVuRUL0E|j|kirZ+P``MH*#!lZj8|Z8I7Sy~5mrikW28S> z8CwWvOfia>>tXJ3j8K~R^@?=4SQ!Uka$1j9g}Bsx_Kiqwuvb8hSr@jp zAfS#?%%pMg?$8W)rm8n)h3sClOgdrYMN02YYwL?N1HX*2Yh%j$gC^_xUBT$Mv(JdQ z3+2EYSLw$7dP3x#9Tx-RjS2=1^x;D0=`u~g&B5i?KN;Z+L^>`eNa&iH&%`tS6;f;xoc3Jn` z&dov+cqb$Kf<4~`71N}rXm~3&=)Vj+!ZQ*Y7_~@JnqX{e-6_LZ@RV@{(OYKu0M({d zfmJ0@T-Yy1tPttA19cDk5?no<>%l#cNfx)|Jozm7fI@F_7rwI81m`K&}$;gv7 z9@;G*VOl3)*YDOy!MgzSsw)L)0l-KpUfPts#PB#XvS{!1JuoZ!tiF%<;^928_*^F7 z#`BE}b+FCCNHL4Q3xRe$Y;BiwW>Zb6qtnmP&-SO z4C=m$xG7n|`G=g61emE-ljn*$24;Uf-@Kky$E!Elr9EZ{lEK7J0t@?Gw>z;ZGc2(q@@48Z0`(Y2k1%r?unoo5a2|jI_lQ` zuB5(o5bXqPX8dhc9lM?Q2taN#Dkb{IIH{W~KKAU~I^S=K^gY*Wq4M~|l^4KZRnqfR z$w6b*_p=!zT1D;_Q#Hvhl*G!3{az<69w_qevPsuDXuCYLYn$z{R@;5l`DroB+>x0H z;@&`#TC7F~!bMT;Dv%ys5eSaNGHIymSapmYNW{u4gzo&`j6L{7dThyjh`c*jUyhG^ zQV~7fM$d#gR*S%i{TEPL5kI`==c3C!TigRf*unS27d_vzZpQEYU$+*XF7MU&<84s1 zO=ag5Ykq!sydLJg&kQ|BGCq`p;8PoYahGm3oIR^*8N6*0BSY_ERr*nrDoJM_rhk_r z8c>sy>S9VX$O<(N^z*3{MKgbEa!VS?PeOg`DoMWbu4!r)ym)gUU3<)1sB zo$V<)9eg9MW!V33<6h?eRh<9bNF+`4MW>T1FY@>xC);;IfcsIse1rfDhTKBtP2uq*;s+qIKx zK@OVd3?Xyd_HNMJr>*Vsj+tT3aNTTUS?iv(aUUZ^NpO>YZz;wZ{f$~xT3UQ=OI%UkXBw)KYo4%v~nU2CKvwlsR@B`mw3 z(|Y)1J}G(W3jS@RRdz)1(UXy%?;M%)&^;L_C}sX#@@kW<@zaAwruxj`!Zb#4307wy z#eU9x>}Y@D%)aIX?7=(m^Z_lwKzT!1VZ1K7)DLVd@u#ahu_5NyOQ7raHQXPLzjDOM`{r$QuFoHMnB89i@_U)^-Yu!!(8C(Tu z^N87#0E+AKcKii`_CRp+hIRYD|H8wi!>CWKYtO&2p7^(qJShq??{Ge}3M80*gL-7J zAo3D-xwLZy{z8V$Q_;ZF#?sSP!rI*yc*79j6AUk0Deg|u;w?^bcPsAh?rtsa4#AxgtQ2bq?(Qx>|Kuc_Z1VDC z-^|=QcQ#5@Sr+3x>3aYGfFUm@^%Zt({{M-J40{!sMCODY5G^H?BmjVh1hi*kB-m$a zQ@O870Dw0=01y}o06fA@1?~d?ZtMWSp%DNemh2NhBg7Vk066vIGTD&CNmQ zda5R#u6Mm0>z+=i?n-N_55cFE2l@G;YB~>>`cJ1XJ+28alu^^$4HMvl0!h>$pgaj& z00B)8W*6pW0iX@;X?6bX-nn46?CZ~jCqz*tPS@MIK=YttM4U~XbuC0+44PzWWYkrJ z3tQ9+5T}jKdL(F34B>VwbsF%JX|@YCL{<&NL%l%jQ$Zt^M#Ub`QvfvMZ05kf3Pd_0 zz}Z|3oCx%K z+dcDJq1r<+5Jk9-NX=>rARtEpenj4s4eUkg3dHs&YD+-ms($-8WWUZQ@!VRRc_qoX zd3qyu-!8U_Rqczs@An%VRe-bxAYV>cr;Rj(dnFIPMmF*YUiNWB$!x2gLs`X@d`6?W z4=)~Kj{jzMyHMc2LUo6t4C_zSZ1>m@DKTh}+8?feIxrKS_t>m~f&C0{Gon}g?wKRf za2ThKTK;7jQeb`bGG-aL8saIQ9!P$kLhb*q-x^!+9L~sK5dyN=WzDG*iswgdc>k=2 z-5Ug~r2*RB-ctFmWNe^F!aAbcKJO?n2p}Pp^hLTCjAWxmJ^9-zY4_s8kjeMDj?mY| zLu-P-hy5&g?#Q~V`;|PbLnz?d*)UzD88*R)NE8c-cEGa|&5%mq*eUmi6+=CVC+)tj z8!Z*;9+XY3u*BEDGU^(@-BW+$W9T-Q_*vrM-YY4!yb%?mKjFOq%@8`OwTJ2{5%~1z z#Avn0?kZ#HvGM&TSzjHzW61tA^d%+X$;EFI*3vO)&@uqotP$0pe25K!C=~m#mQ*v6 zweu#*%7V9q9`dS(_=+L_hyt?as za5g+V13jz4J&uJH3?rM#!Hb1s_reQ@VD~^<&hALSdbA6F9M%bfC-vxC*<9YBDE<>q z9a#KVcW=jAJ;!TW4@H3Mq!_W@n(A+Tb<{%%fT)^vZ(*a=NsHZ}my-$bQtPxmnY~W) zMLt{?%CiFEn;3aVC~)X`1uKH&vI6Bgsmvd9rE$s>^+I8QwVev-r+$AItI0)Zf7ivO zu@NCwbq|y>;Jll)swK!V_+Dd$bN=-CxJ~pFaxt{?4Q-!Jp`Pc5g5?8+;J71W%87n|JNX-~>>$RLt#hY^%b1wR?$z$MA&GB!29V;4#tx z6?1^=efP}Ej&*L0cw2@%Bm3!9$p|3lzfK!m7jo~4%8B)FwEjT;1by0%+-SAYZlXh^ z9@+{$DbDhMF7h5AIKsWb-y;;F7kn}bU;_AEZyKTib*L?tSdMa6J%64Nfk9a$t4Ao4 zA$c4&tu?*ovJiiJU)Ec=U48PtlS?ah$29u$h(0kC1Ej|SLe)2MgvX`1-aw#yGV3u7 z;u{KfFJi6)>PZNvw+{+z?0!LB89#rAkou2ao?&G!4)?dz1)$txtP2{w6e2vK;LgYv zyb=^5hYrB+O&D}OqKR8ok(}4>4-Ga3Vr7#EwRw%XP$KWLp80WdUpbg;1wSkX1)#AE zV%3sdBB1P-sJy|qo9FFGJSzp=$Dk%5eOEu>=5j~k0?D!rofi5PE?H$n4u_0F8hu|> z{}}LG-P(&0gA=rSJPzR225WYo@V>`gAfOym5sOp#?Gp9b2V~2fH&Od5_n}LU=_!Rr z*jTt{Q$76!C&coIDNlC!LC)|p+rA*(BiH)9@QNAT-e4gXCWv0~0R#{>83GMuBFjR> zA?ki0tKA4`O81IFJQY}X%~>8jH-JnkZR1hB1Ol+0M`tA2=9AJ&V!>4i;8=zG|9^;~ z#*sW1z&1qbiN>B)it9uGLslbD0w2m#Z|^j?#P%6apG~QvQW!qclbKgO%Ti-Ss&Lke zB?XE;9<$NNmrF)+q59)2ObCiF|6tDS?(G%(-x5|EMD+OlGA&j+RazaNE^Kxq8F0sdHg99NVM%C~q($11S-i`?-!J0_WLh?JjrL& z$RW*{0ZewEIx!t13scYuzrVWF7M{I@Zz8%j+qbZ{P^ov=R36{@N0IkUr{6eXS6>!q zlPIWwP%^fm2IS3_odtz^V&vK~HVn*by?o4&{a2N>(f=@qwOjLNq^0VOB>Is;N7I{% z0Wx<-F*BO~CiqDya4X$yfQ@$O9ZhH_Uh_F(-?Mno%cox@WWDaQU@BhWJ8X7Gf!`rS zM=4mlaki1w)z-6r10od*o^OW6_t^BH=?|B0&qTdvWySuzm_LqP4L$TxqZlQ9F*0hd zq(f1KQUBc>HS7HirYQ7nPH8)-(Feb8FonuylN1C!6w!`f){~;XQLv`J7OSNBU$H&k z53jvWiQ&dLHe*jq_Xc=>^ZJ9re>1Q~FXD_TFDGi2FMA$J%0k6_VQ&at$d3fbZoWf!ISjLvQ=&uFy)40S(Z z@cM4FYR&hy9zudBhnrkngiOcS16cmCw0CFCRzsNmMx~_jI^Lpi*F!GqwfeU6w!6dN z&#N-D&HuW&rW7xjEg90BuYfg!vS_B=X zA0vT5V_4*wA_Y3>iEd(F*n=ri6XnB_%%YU1qiH6@FfL;@3Lk|GeViZpUdwvfYFT%D zZVj_BMU$?)s!1R3GhVsk3tk1qQSaZaYvF7L;6}y>^>rjaWe$elvugkux%?oTKH{tG`dcve9&h_bpc`u|1G{7O+j=L6Xvs0? zuyvBEm_$tVe}i%)pH?WYckKmrUof%{mNgBirMi8=Iq*<0W!HF8;}D}yi# zh`82=Pq|~`HSS_%6~7hQPPINUnwq}+t7+4Ue*=ph%RYa`Kka_hR^Fq_As;n-ga9}( z=cxS&`=>Y3+)fvM0}*`?u26n;dIWoIO+#;QP;0txt|>RD9gvzphYm)o@5V%eb%eKH zRJu@sK(lH8bU(P{DCz;{eM~#WIT=(5K}u>ujPr%3m|THfEaK7^^YMnM?3zcu-M7iN z=jj@Ur<007u|Ea9SEE!9v7)$z2?4K;A=DVph>?aPc>={9m}|Qc{@7q)M6g}gDg{^= zbr+hgyNr<87AR+zizfGHa57ej-O=Z&|7xw_qzn(dYOR3Vxcm8?jH(~ppK*3*ew1~H zvA`IvV!~)e8**x;A7Wu8XELxX)bzz|gP%=4`MR#5dM#J*d>%rb`>>2PeS2L5@Y}o! zK>058;0k}?hG-~_4V@{3aPK)783Z^oWP1EtJO*5023}#apH&Yah@yhq?{+zYmwDtx zTZ{~dbR=&d)DUo<;lwVi0yRMi#nzdnO2D5SocKG3d7KDy5~!;9B#X`IAB=GCeUgj) zHB``FCdT@kdVLPh-gJB1Z!|6r#U5;*MDzUM9)}bHh=BOy&ZPGrg6^47UGydd_-I-Y z{$CE^_h6yC!MwtiN$^sGo)H@i6~1iEfD8QD(ZtgU@B>hnsc17wVj+At(xSBImNO_QiSmBNS1_WtOXm1E%NE_mO3l-- zA+OSt7_*kplVD9Zf-WkyBoRL(g%0Z@t#|#(oZjANBC?ae^;jO)?kHCa35_1?j&GaC zE6DD4%_v-3G!y>V(#c7FaH&R!hJ7kbls^~tOPDy*&ACJf%XH7wYMXIdqw4L6W*TFE zGLB`(Z(?mIU~Wyv<4ynM_wfx4o2S1cJZcsUF{)W!Tl{!JGIO+6?-$~gQwnv6KgP6Z zJx-alUuvwwLfXxPTm~71N1StuZJ()lwvC$-z{xenZlV<<(uPXZ` znaRPLt}$9QrgKC%+I=!XiG)&!=AxN`;=27FWXoF3pDu3AEQAM^S2_-{;4=Fu0;xYT zMT>=QqTwVUB>}TEEdy1wzRWDMM!w;?%k;9eP%TvCDxBGkKYjy`MGr|>0<7&6Y zsmvv6P>AHi0VT)r_mpG5*1C7}s*W_+*_lPB5kh;K>Rcb4qS9*8Tu#aCGD#B0dp zl5oP0=*v_S-~ap-sYzq7oJj52IMmd18B;=9X4coLfg2EkwIeqa@_fMTaWG$rIw2KG zt8Pnw`+DAmB`#*P=HRj99-I{s=mqI<&&1jcx@!%5Fiyfh8xF4lG30nnM1ySZDfrF? zVSdQ}E!i?VeD=+Wyq(X`V#bEEoS;Dv zgWPppMu0qs7A`ro@^`MNpj4fs^VR}sh)w?LKNcA`49l6%l9K$lJyZ5?YM6+BG;;Z-P&mWPw))yS@;=~vRh)X|%Oxcs; zs1emGDXI;~s`N)WylY7|mXm1wTQ*iPE z=Y6KUF_qH|_xPqg>D`K~&2HSFJ<43ITBK}{7g37miyhzFs!*nfz#v7H zzjr@NsCcqDa5924w(t?*=QobLR-tC!kd_#H#5fIuVHQfW)&wh}4%z?>9H-cX5 zV}g(Qr_xh=jS8@AcDsYU+N2ZUudssT{>Vu5imfx?ps7~6kCno2bK*RPhuQ1!FZ9iW z$^0>4yPHWNH*=htnN!Q5_D@~fJ`o{%4gvXGUxOlfNrI^!{{r57i2Zzc4qIEW`)FqZ zJQoOHQzZhjMKnXn9A4Pb!+L4&XK`nFq-GE3R6DV#Cg3aD#KOaTx_J7LT_YMnzcq$? z{YcnqPG>jK64dq`ccM}L1N>02sDYntkWG+1q$?vAcTJV;-e*$gR*Fu@d7g*vHJ?D6$&iFlQ~Qat*+27PEFL~jnLo{ zMb07J2KfLZ6TNiXPyCq4$E6)=>UMhTiv;PKIp8S*_Db7pw3wwlWYk3i!t@;*E7w5N zQ?{G#1pa0tuKxPZCA6((*xh$xsF|Q&qjw0q6x5HYm)rpZL&Jg9kE#eb_yq-uOo~-p z)ESt6j`WDbqm22NTEk4UP{lE1W@taE8wPr^$dx%d-)QDLl*sfp$IdctXouStC{UA= zjqaP~AlPk1&AS{&3fl2tx%&ic!F%?4AY7%piITURD6?Oo2KpiICa}QQQI8*;-#*C? z1z$hWcPOR~w;;nu1sQKF)s7eK`}-c?T>oW1u*;nr4TpT8b+i=@KucpFmi1Z|l9|YbJON0<|@*AmkfVy(sAga@|sc^PwBP4A_$w>Vz9TeyNE@9K;G zwKQ6dkdtdX{Gc8@WGeAPiG~ENUh{C~B+IIDpsyYfw28Gj9lND~$t99zZpQfgX;DjG z+^1px=BQnyl-fxV!DnWWM3_T7hJt$KeY@XRh`;#GiUBO0@^4^aM`*J61mduE7jOOq z+xj?#B2SuMd8Yj_6TgI_-gEnk#y#u^CIgEYaYKT_ewObyaQ9pjUnnMXF@$FsTGux( zz`w)Sxy5APb4{Gg-3!|&QY@r}u&7<_KFdR*lg`c(1dFc>F85m> zl_@ABlFe$@SWW+(N^9aH$*U#d@AT(OzzuLV#I5#}kW(?;yg0F+!7s^XkqD*Gf(ZFV z%=Fx=+fIJRP&loSWwtr=K2i9MHB#X&k0jzd(UAk16x@)*<5aW&?*?5|pCwX_Qj?N^ zC}m&2ck36=^XNFJ(A;M9of~)~7Xib9_tC+h`@;(ZpTe^_{-7ugDJ7K7_dhFA3^q~#z#E+Es1xz>w61{88a_=AI zKYV7{%So-G2(=FeZp;xV&Phl*Jz9lpj;`NAHDYb@CEPGX@`sgyPUIWOlb-6xM~hmX z<`v#7N>1C@ug8eDg`m1`P!L9qXO$rDfO~6diUXT?@=yd47Z%)Ah)Qq*vc<)@w2-Dw z8`PtlGC6ejY6A=DJVNq5M8a5cIq6q3~E%*Kez+jPKu_39N)`06U_+ZlcAr^opSre z;Na;ZQ|1!woiF$%e+=C}(OCz)+!3er%%AZ3`fc4F`SszV0S={|&t^03_ zPFcxxVA~afQC%FX&%l(3!k)C8%_+?7xq?39|Q0vqtHp`Ti`=M00#vjGG?Qxi>!aX zdQcT!>u+UI9PHyW9xpqqZ z{LNZjqxAd9`Vt{5dvzbOFPayqvNh6;>v|>Kw$aia3bm&mD&530NvT&$HpdT$6nBSz zo5AltX53RzVduczOXIWD(XM1an!9uR?SuS-8W*-xRn4oxOBM`u=Eth}AjseU*+wx2 zR-jjtvqF-2a1wjR1x~n&j=F~N3{`z=myEGjngM81P%OUBZS!jfdP&MwC>;%U@RyE} z!%fZ;T?&o4NZ{7bMiLh~oyKMSjYKNMW+9O;JA(7N2#COBj;~qxL4j3XW;!NTjFT5! zqa2+gigQ18D@=)zqoiV0`NxcmzSi;KNU{qjo4c4G(jaEAt(kZ^z-{mYIY~wsWJxF} zXmQ^gE%T8@Qt(}uQ?%U{ArjU|O==??lNi)!qZ0g6;o<2#Vm*J^ddst%f9P%uP0n+;p*`vz#l zt{xq023{jg?FCLQj(UPq78Aqy&?;VGQM1FxBg?=!$=?}gn97?oP}Gkbj;cnv;7fN{CF2mSgfd0mCdkpi)&43% zFed?LItb1CDCtlpyOs`_syx;rL#vcBiLVu$}y_Ty2xt_0!)k1fL9hr<*LX@ZLZ2^K!u! ziXUO7RWUwrKC-nKys zisnEU@4dKngOkwFuE7 zOp11?R8>A<*Pd6+dtUO|80&VN z?IJu()rv0|<80y#KwC0W`7HTKKoXvH8LHPu7(RnVdY>ge313Sb7V z7gVXD^$yuLS0umWtG%(uD0@!+f${Yn+-^<5g#?!wLnf6kxYLkw)P3IrR9(B>;pLc> zRbiZbfhucB-+uY(cDTdY`T++ujF^hb*o6hH5Bk8PsX4LVIW^oQn@KuBi`aGXO7S{J z)$@Dh1jPNDKylE`n?U2&<`oSyXS#JU3OwTHekG@O?B0Hr55n`3IHQdh5y6OqG~{P1 zJQ~IVh8tq9v$kD#x8{|$NI)G6Pj7go^hDr0i1YsK3Zqglv}n;`u3GcskzlJi%p0$q zui`2GtLD0@N&@O~E71~|Gg6eU9v2;m{?o_PN$2NC8F2?XtX4T02}heRFYOXO2G=;d zvv~z?Cl@i8`sa&@$<(ZF)!gk`6KNfMS}QFm@GynMH<{8dn<8JI1w4IfrOV8cJMSnf z6X471A^z84+e zqz2*Qsq(3_l)oD24{|EPOcl0>atyTB$jDj_Q?qu>kqpJK1X@%n(_d111HU6u<|~E2 zF&`eGt0UjcM1Hi2epE;{BcE7xe~mXaC8f6rSQpjgv8U_l`lRK^=5(|x!c=A3Y~!Y` zUp8m;wRWMwKEkMP)O9a`y|+Ca8?(hE%b`lT4cgB;Ir$>;Q5+4fG4>eCo==RvP+SWR#T`9^b7(C|wUelE?^>1%<#r45zQFULBiO=Gw%gY)rbnpRBfU|?! z+XmmzhIp7r$}=urXl^}c(bl$jr~m%apda0H89&HA>qidjDb&!!_!nwlP!zeTsQ~;2 zdyrG48U64@7L0z=8&PG-_FW8qvA#-ecVHhFZr zYT~k<{HMH#__gSr@3=8-18T~ad}SP^qk(R*Cd;f|&M%N)%zUk*Gf*t|xSLWp8D_#{xbztd0^9vQl4pWCYKaK2i_RZy@cMhJ0Q>cvs0<@v`=#v1D%pe5wS z+qtCX5qJSFkYUchC{b9e8R*8Ot9 z14n#;khBdjf(_egdP81H5SE-Y^H7%(4k4B26igOh)L^>#Bw8TTvbuAwp6evO_qzr@ z-JDJyzMz(!-7WzhEX9vG#`$GN!8(DGK9^)O%XLdJj(-1I@n0UCMb($yuGr;D8oQXA z^0A1tZY_wtKsYP@DoAIf>?64d_t2(pIvEu6^*b75-}JBkX5!5u;+d{J$Vu<@+~58H zVa3yD)LUq7lMI9ho3BjGNQ<7U@6K?OS+W|;u(m-REZq(XrV$MCLj%nqKUkDhDf#L) z39ln_E4t#H*DtGzO%+OH2f6sVpJRCL-zIBqo_6MYgmHL7X!!W-HAR_2pBKx?lWoqQ zV&uy|>G&ECP79J~QSBqoOb|h5J^wl@l-n=a5yGOd)GGe%Lp%l8>BJ%FOG_N$n1S)v znga{VF!Rp1`XKC}qIbcj5$~|#F8?lnY&<~Ka;QmG8coD;n0+hU`v*jz&`?|#H zF#TU*O#}g%d^Q#x1hTZ?aZox4iKB1r7B8FMJ%u7+Qf2Kfqm4eS3~&8RQOg$#NNq7m z+ZpEhcY~a6Eb6YOdwH1DV)dRinKmsxSw76`1ZwVbK#efCeXgD?C6X=8=~^1LiF6PHi~yw6MVgYyuyZ7sCxfA+Ecfx6xD zO(%p&SiiQmT}WUgsB)Lr(Se)Wb3LhxlE1%oZ(I;~8(<0?uS#&)Z-Jz0X=Zgh$7uDw z2=+cWz9z1{c59XM{wuE>$TCG4Gy7&G3KeM^4GEfz`6$nr&s837s+hoV@PpOnhO)vl zPWmbsZZ4daugj?1^@m!KSenAbG4$y~q33I4p5D=gYS`&nnTqjThsE*ixB zqnkNfV+c^JwQMsVj^dU%^!a@R{U)McC8Tf3cDCHZbMKO~Lp_kFAfGmUVuMOloSH9; zG#XTt&AMm@iGfLYZPJuf+1Q!k@}SxE#~QCME%c)LTYXaLpYa5e8`$T)bE^0(tTk=W zy+x3_MSq!u4QqImEAbL+J!cL6bom^*#i6e6Iw3(Y%o=?8bb*9Wo_(0#(sV%mr7^a$ zqP%i9UQadEe%>22-lYvO+$8M*0E5E5y2 zh=6`O(f6Bul4c^5)G)Ikx`Lt8pAZ}4EW+fKvac*xr#nKqBL0D@eWMxqLX(#^QH#K+ zOWl0`(aGooQL279VxU#(Z(;<5LG}ZzmH79)Ds(yWxC#u;c4QOWYU%{ie%Bu~@x!cW zB`oX^N8PQ|nXU!(vEelqRW;m7-ln+i`J6A>DI}*!)UN?Oo`kH)X1?4}#Y`;Kyiwt9 zn`&Yc5A=(UH5}yx`vgRM1Gb%|)bj1uNI~pDMe=6Q>FXcyF=eCe&UIrgWD}V$l*xyK z4KEI7g|t2^jJBLEOr4O2NG ziA~esujHqdUs27#+r$J$*M;$q&mjlqUObpiL)E z(0iTzrnr2-O}EBT7`k6^Ez2UG1k~4m{i$o;{;MJZ=P%im5o2`v7;dDD0Do4o>LHAI z@w2B7a8s;yH%gX#hv{+yhh{0J{h1`kLq?l+{=R{CaqJ+yNmjfCAna|8`2+oOHkyS?1Hvc!|iE5j-fC- z0mZq^lbc}tjhTsQQx83|3UJNBXsr?9Cq<8*yBWwnYm;J#drAK!Mr=1Lka(y*(=^F#2`jVfA+m< zVeSezK%SROf+c4rh0szfmBP8+O;HtCm;fjH*mbl&UG%<870jIeXd`%1_(Le9mptPu zc%dFVE#jJ7rZRn=Ml_wwHot#^f!o0Tt%M{Pj>>kJbj|<7?{^rkOz)d^Q`jGwvX&!s zi$7|~7t~s71|ww?iU}XuL8|7)6+?xcFmWn!-nK|O1*WO1cvQi<X-=89sM883#*N z3_~(t2ss^w`ka^LUN+)%@pV?;08v=UA_#)zASmv#RH_;6SQ5g=U80FkJJ!8%^(?zu zq$}+yd-q`MQOr_ymI#H`6Yqvr>AL#$-F*tn5SvFewSnX+lCY5Q5uD1tDf7Vp@?cAKw;Go#V$s_s{J8OsKxdlbi zMdJGfWo9WvE`#2;we9xte2yfrvCx!wVD^1YC zCfcISzS7u1HkN`A)2&@~P(#gWSaJ-kXYG{&w1Xxi;F|7+mjDuVvI2(d9sy_OpY*%Y z;0ZG>@wG0|y}Rv=u;V}1%@s9w4S=AO3JO)eM>9Y!l##Jgy#3CRKK2Ur9F|&qSed5W zFVz8JV*dEae*?I^PX#^0D+5fUm@2sMP!2HAPp50XerKLJyLq_vSle01Lt=sKPUU%l z{i#Ns=@>!`3R;HE{a*|NLbTSpe*fKOuaLr5(%8R#WT{JSck_wwctTUZMCzQRkKYpR z(T%@xIFf^BO{YnZ>IAXvUR7;e1flcWC-`80p|OHi z6yJ-7&%PU3^0*Cv498t-4|Fr>qJ`FW_p-i&l0lXlbpdDoIOFA&`jub;*(LNZ6O`q{ zx9i8UfF>VTz=r1feDsG;-Sd0@c8&nr;Sz20Bixj^l|b?c|FRhC%pciG?G_w(L{vV)2IveSDWHejbeo4ylBe666a-cr16uPy|8zX4w^qTQW& z`dT~LbnYEz6yOZX()iVijy%doL1`qy6cJwZbcN07RSI*ixnpZMCd{6LvCdPyB4^%) z>K%AB3`Wd1P?4dOGQGVde1woeJ5bO+PISRi`8ueKrh0;qq! zmZ~ad?_^5IbLASoS|uqV5`PKPX67wdN4f44Id&lPnLz;Jiv;4L(%A}%>KmJID;NFU zgsg#7jJ@Jc5B&t0?_kvne9N@sWOu6TKsGdI~cz1K(6e&Q!F>MeSW%q*%60+|Mx!Qz=@wQ?>;G(G+vz7G++N z;_pXBH$Ido5mC6Pn+g~uqfPh05+<|MCsTo1Yx$OL&S|Uv{5qLE*vZTjiq>ogFW=7% zX{HQ*<0mUn)>Qo==Iw$iBD%e~^|&hbCm+uKPM6I3OG$PanUb?dEjSBrtIM@Uyyx%k zN|ah-1@#$}QI)B!-LH43;j>Q9%OguR)5S`Mv*MtI8h>pGBRTSX7o@f+&Ba#5=rz#i z#&~WHbnYsbgXRG}8}ZT04!YADYwkFuPkIvkHGo%93vogo+`mBgUaEmuwV-Ts8nZx* zty{+LopN1TLZD|xH$r2T@%iA6sFZDNhIn)?p8WMVg$b5V83!3!`=8c^%Lzo7R#2KM zj(E5#X&pOSSKHggQ3GsJ*Y|0z&8CoG_wh^z5*oN=itHQzjk(vQW2qhD7fmtsrXBWK zTrB^4=K3lX&n7A|k_It9Wz!@fiFVqQi*H*qlw4FdXy*?y7pg{O`)R31eA5UKc`fI@ zLvR!+dS6_V;omEsOess%dM$Mhf;expP8kW~nDgTm&5|Zg$aubVoBx>1gFx+mKxeVz zw{D5zsb~`O)|VPMrYNUr$R(=mjqU`|D{YD6E(zHkLz})|{6^(%7Xb1hf2t7FW&c9W zrEGMK-47<-@cf}wu&35o*Wdu(*UGNP6RVq~$vylM#wlwN-oa&9^5^&p+Lj?8NU?W3 zYuq>vxKiLzrlR`5hrd@-)Sc)mF--(&v|e*xk~4l7afGIa_gs=N2>f38S(6PhOy zkE!wa!EpY>!>wf8F=O&^ZF94NMmG-*>VRdO14HcIvhG}yd*@mNJqzFn`YoG|h} zEg~XqVVBysWE@jpYyrXmjJp*HV#&^MW6 zm>j8EaZ|5IwoF9L&Mj|bm0W>9C+z2*3uz)a1#3to^F}{WOaK}{SKXo@2vW1H3u6!U zD{Q3?QbOqyQpj`GJ1j9>4)?K#UC@*uhL`4N^rPuo@#aRYOqn;daaO?(zuu#aep@jt zpRsnU_pv7wVy(Qvw2V)1ffc;aHBd8HaKe(D@7H`Bv)F`%hOdaqyq4Yj8oHd~!B{Zf4u%gi`P*kc_bdg~T>({cw8eA^r{%nM6SnbCeVTVFpSMt9l0tbj%DyvV;v~K2?K5J3;E1i`bW{6x zn)LuluslR%svlPFW8)QT7VqO~j;Z*QWKz0aqpFklZ(+>5{H28l%&xZ|(B^V;<-e8x z$keO6`VB$ry1vF|`<}Z?0Qt2~5dYcZM$`fn?sPmU5o_mjk>!hsBk4J%MJ$ppjU_F> zpGJ@Wx5Jlf`uHmX_7I&YOa@scE!_7vQ=%ilI^Ud2Nv+gh?Z_T&9@-^-KX{~mQA~;@ zAXqzh^lzq;2?SQm{ypTB8dD}~)%x_j%OW$ zJ>;MG`-GX&XtLI2T8o_Cl4Mfl*x_F=ti+$1r6S|N>H%ryocH$d!2D5%&c!hR$dytd!F|50vjx`3C{?6r3-5gR3e?lYp zq_0z~#x$dsW2&kneSvg)b8)*G`~g(;eiYd_WJ_~~qy=7vb2M)m*YNdw^2YaI&~sG9Hy*A`0bP#^ zhH_3;~H%>{-`Bn-OPf2%SL32CKw_*teoc*U(A z`guPHRJ#uzsX;-<%bN>ZS#hoI(sv;&bk%S&-LcE%sw_Mo({sr4mA4Y;XSPUyI{oFf zvj$zmh3qOV>U((;G3dz19jOUyqC)aO+|3i_7)A650T1uwnHgdUHkP0FpQ*)q9Kxx* zlNQE_zTM+~Ml8XBskhoXwk}%^a8+xA92maYQrw$m-%pBcai?=BY4B$}Pih2ySJ_@K zT9Bk_HN?UB7ereNud5^!k8+Jgqy0hHayBuhV(aCYxH&>=*4ne0 z)-P%LK~`cgKv{jIa;ASJ+@-9m@Gg@2JshukT2onK2dewO!c zLD%JuTCO%(P`JJZ*f9Qv>WIM#L?mg%!dzm|7$UUC+uFU@rZ2LL6>Xy@;sK+qR)<7H z4Jdg~inwXB=}nnKv%g080T%eI>E?DU^8DL-LUq%BD(9UZ^*ziWs)$M&R&I~NZk)1$ zBs_}y; zT=>lPJvZGtzaQXVo`s<>{foKklhPG(!8o3Yaf4R$nlyCLe@{4I^tYOnPMe)=;#M$suEpJ0j6{{<FpEgrA%|fh#@c{I}i}3u|@fGs%QULmVY6Jm{of92_G11=TCoMGa0${_b4!!;K~H zE6AZwCfQu6aK=#=4?WN(QO1Q+?Lm6W( zo9FCXSy zsui=z>q^aB9)#WVml0Ov^t}9zlkT&yt3$99OJB|zTT0~Pn7OH3{K+5AHXD8!tc}Qo zA3k^JR&!1|!d%W`b0u?svk@#ZDyyp(tl9)opB|YwUhT@wd-r4_NmjxU&fS@j|SeifKqEN=Fkb&<0W(^ zTmDiX$^r@Ry3MaXAA_)Au@5%FjwEhNl~~nEH=T(^KAEzQ{ir?Sfr?DAz|okH5}f&Ve2mTaS*rLI*_o?1x4=$bkR%!rpV2%9DOVDrNQ z*%f}3{uH^gkN%n+b`eNgdySzuD`U+-0+0>A{IlTTf`2ao%XxPnd*Xrjs>+S&MikmJ z{PMsFD_d`O;|o%oC>mX?f6^zP`)N2?BD2{HkMl`iZ+C)?(%hS6DzAg-E<-5Q_RjNA zJ>r|J?EU5y3I}Th5@eP5guQ&H4WbRZGaC!rQRa&YYJhvPD(7(6x00a}I9QrhrtZjn zy?R zXNg-7bIs2-X0i1>|LD%~U`aXyrOoYxC-({j0*wV%It_~rnP>I7_a50_J`Ff063mkc z))iYjOx_zA(NvIn)5hczORB^r5|eH|S2)wlY<=(O7`e$|zCP68TOo@6kE3f2tE}td z(}c;kZQD(@ZQHgr={D75O*Pqe&1BoQZTFq``}00ePu=#}XYI9q+NP^8X3{RU-RkxQ zl(>=cZbFZUR;wr#GS5a4Aw5E7Zkpi(5TxrT2Z{3cxrlLzm3&Y8z*$kJ!glDxD`dD?0t_srJ|yQjIB zuyT%F>o?IP2vq9{d?J!9&C&(mF~)gke6C-qQcvF7rOrCpf(jdXYR5)*?S$$6-#S>s z?j`)BH3VRp=LyKoVayDX=ZTB}L4|6uq;=B^UAWnuRl}1It_h}b zH329)GE+t9pF;sdqYd*8Xv1D(tyC|UCl>D>7x-M)QzVg=F~%&2TCj0utaFit9^|C7 z`|N6p9nrg=2?>xv;;jq+E*@*z8LAchRmr6v3~h1c)O(upVPiaLUkwh zeqVy|hFueLW&qT_dYHX(5{ALYh5)<#_LN$L*xY0xo^jPW{M22f9-5gwNSLF0y6;)k zHrT5uV#igo=$Q?zZKI+O2VWC@M$?bZof4b{ z;FWJ~m_b55hKyX)5J^v8y{h5sB45#D3FQF8=Yz@;otvz;kL{!WY>oCm76fwpB%5X6 z(ITFi=Cg3S5Qmoy&1L#y9+Fxmkk?%dvb;c#mWOk+EoEbZrX?RBsi8#CM;Tm}xi`IS zb6#WQS)GYgO`R18q+M^MQszxEpZB5qWim&(7F)b5LJH^U;nq1dii4L+h|6&)w6|BQ z*Tt2|cM`q~A{AlFM0y{({NM;gra%^lkvPV}>Rf8suGRVYnWy6dGde$%l6IS5j1C}h zM}Ub-ThBh<78Xkp2@T=Z>$y_=q!R4gK)%~6<+%n{@#2OP#QJ*`QcZk*1R7&xLlr8F zwckalGXSxyR&QE*lPGpK$a&rqzV9URP0loNo*b_uY7d(FVK5S;RoFQZ2dD`&JWAJ< z#nQ{h?vq0FqWEk>*bv9g+mpgP?uC)*ss2$m2Kx3G^A^|czcG_zfRlF^OP9WqL))Mf z73MTHo*a-GUO&eau&+|a(5bhr3mz)QsZ=&P%Y_Elg_z#e^14S;0PUvWsO%)+?^(9L zD1OJ`;Ck%@2M5{2GR(2K(Lli%ECG7M3xwx9XY9pSh)|TT%g%swnXCW@kx0t**&?S_ z?^mNrq{HN1X_6?sC8^)zxwuTDU>SXa0z~P&?_IkqdpHxt+NL zlDcC++XSQZ0I3Yl;`6NivX4;#!rMSIczIN1FnH~rjNyq)qM69S&Qm&`u|on(YHNOu z>1dHEa&i6M@9PvAaPmLR-U9j|4|QOGiQuHkNv?Oj_+l`12o;-0ikM5DJ#%+#m<4!g zj2%iR${ok2=?{)8HwxN)hzbnuy5RXtoD34-2M3z;DRysGX&Ao^ntEl>`s%ZIKNM>j zloQEPi3(L7^U^&-X%ru?NDllx=hkb!>~w3~K_Z3RrEVLT78R}7%Vej+@Ok!r35Trk zASmA~m_7ke#@d#Z-y0`+L#UF77DEXASCFDhGGBBT63_{xr>&Y0+OipoLGY>-53Sx@ zlY3IX$i77~PapB}CNjlVSmD_VnUJB}Iu~3F|M*TkO6$XZu0e+=?|kzFkz^_jOq^qT zR`BBLHTIckY&aWT9b=uZkX-BZ#M!XUMx?{{tB^L&7%#wZrT`ACeQq`}yE6cE3D=pL zc07%NNz|d(ty)yhZEtj{`;-Hw_q9HN_i}YiEzaMIE4eC`geeAGkTUgIj!NTL>sIRR zUCT?`AAuN8NcS&mIn}*69B#EUy&m`)HwZi+=QOd8el6Xs&hs(UMfFKj2gGc#f{p!g9r#IlcQA(WAY;Mu^UMf>k-i%HKOfJ z*vql!`Omd7d~Yd06R}QoIF?GI`RG_InT!P0)6{I#mA?m7AY4?T55G7X8W3Z`IaxM| zl+Pai^-7#H#4lK8`OiR<<>>5K8(vi5^s$Fsw14$*PYTplI4a5E4!2*PjFH-~5XvFS zzl_3w@vL5bbtd`E8riWfC_itIEtBOC4NwSjHe1lifx>V`#F*tWJsFu?@7wrl=SwQ` z#S@RB;E&CIO4KWMFG^}r0s#eqR)A8RJx>m_D=Eq2NFb?$C_1${; z6H2X>gpl*|Rs;+($jQXBHfwDk<&hLovH_yhW~)+z9vdX5SVGY9;6*#bRbp9v(eYZB zu91(=4pC^EMSZ6rSa5IzcYHk=mg(1zbOxb?S<>CpMNq}v5 z+%4^t3!M6Ng;ywE+5J?wPq6q`0IE3PM@^le`$;gEI>sW9Y-~n7KzGS#%!kOPO2e+c zy_$K)o$2Pt?CTpr9KR(Hrc{Ic{(`#tH-l#)QRn|!$N z4qL0Qi8zCEH1pjZl?ZCAc#=w-&DdyldLb+ z<4wt3tjrhT|FY_5s29X5)6Kw*3EiGyjJV0KF8tX9U3_ZB=LsKaBz_W8(Tg#z5 zg$x3;ctKIlYr`C!gDU|?b!9nlO%XXQvK@Er>6;ALW~?;UptPkeC^omQ^6-z{Vl7BO zn4s2)ZKL$^T=i-K5lUB<)6FRMpvB?r@_ zG3=oz8|`ghnNm?>JLu&iB6yDMlz%a?H4RtIUmkt*E zl2j@O!;^XeZJ20BAY0FRyD)m-5~N4KhW-7q=c9eOKdRW5x_p4$hKMM-8e{`H+gN%! zy>?wv+!?QzG3s!aNUlxY-|Azt`mM4|Lh+_JPj3YPXdER5y&9}BD7N5+u5al=J_7XD zR!vZTx0Tw_w&GC9>iDifOdQb}AmU+E@ZP)cHs{;8uzwja^o!9n)KfE8a8T=!3bEcmxMMu;qmhNu(fh%2ebj#L^d^k1@AFh(* zQ$Fy!DSF+0_VL^CLSjXQT8j(W*pXBg0MkFM#LVu=5?nCN1FhKAdUFalYxdS#6n?8+ z+9Tt)k|$B>VCv2{`p_9zjYSI5w_qCSbrH#}$(G~ugj#mCS?i6ijKL;?uB$PK-B#?t zyBmGnWZL(hj#a-E>)#L}RoN#{ZUjU|$J(05T?|4@l7_NwdhIKi_Sa7V zcGWqhQ_VMmmrgK1)J)bZ{dF6+Re zs^*{H>c8=LyM>v_9RkGrvrFo8A+2La^WR}IQNR6Lwhm8*u{XOf9N5AL14md`dV(mX zTj>h9W=3#K2WP#h_&q}G(&Xto0E2e3kNB(-V+ouZd*3tWMKTMMX)SuQ<4l@P9dJr6 zBw@s+-UAY^kqdR=gABKKhK*TEi5)w;`?A~1-A28u;d}|pHzg)w$)p`llXs!zX4$y# zZBto1PmAdmhCu=$t}ufItV-z3oaEW?u4hKk!wJ~?I+2cnmyG=?aJgMVCuyCQu)Eri zC@8TZBy?!)m`QNP;n?jT`as!0zMHH+r%$ZRTXt;#k8?LR4CZx52GbFwwAw zNgkCskG7XC()7bZ?cLVxOxdM5kPqHZNBIMtU%+BA<$6!aF8Fc zS9ic<(C$8-u4PsOTfpnO)H#D7)TC9M_2AGIi)yH-N3Rv-O77>q&rc4f4ogR4qIa`k zUE1=FGs_fQh+6b>jU$3+93D#1?N z-?{&&I^z7t@1x@w1iTB%#y~>xsVpV#U{d5!Ke=Q05=-L>srr+oKaKRozHFBIITx@+`2s(eG+ZRWf#e9_@Sj# zaRI<1u?otY09cn6W3-~?GcP`C$;E_vIyQ(kCC0_Et7pzDqqPt=LbA#lsSU3;_-)y_ zK`KOx{W~ooIW7!yyV7>0Y>XP5_)EBVTlpi7nntZJ0WxA@Sv!r*GJ&XZ$M2xA}*m<|+r>BV{Wf^_CzE>#SKFAJrIs$u zw(No4jpV44YC(>L8$DWqLB65hcZ5N&&lOn1*B%xS0m1gV23)y7)O=~XUY`U}fwJ3m zQOPg#{X7UIIJQ54$D6p zHs+$4qc(1`UFrnsW}LXQ2WD+yq7Ic|xlSmcO0^`rb#{dp$>3+n0b7I)7$nv31V##Z zE$Ty-t6C{?r`i7{gg!|kA}bVev!8=v+uiKL=@wJ1lVJhI;<#$Uggttr)3xCHX+v|} z4#T^UXH7!HD179hA$quWZK#<+c4!oHJ^FKK0{O1c7rr@|XAQMkeh2gbH-43{uuE#D{jhKY%?{ zP^@d?>@#VOTP`zsY$MDLiCU(f*4IeDNai3n2+-ewo1FYl;IPrwCShsh>R8*qW|Hk? z7G8P{5m_|L?->xAp!X}&6SiWX%?+1K>l|32v&3WeQLXHV!@q4Ti*a=$mzg}IKgl5( zuw8Y_RC)owk%<|#OzqmimRX`_^?oUbj~+Ki4?uz)ap7r=!zPk%PsXC*^MncU346Hx zD4vve@uM8|UDWV?yg}`piRP=N6^dUjvp0MH6PGpUb6gSvc)`;+C!i?mit{>stbz29 zcuOu^SO05v(N=bO#QMu1MTV$v%%G;o*iLa^C?9|m-PaYCKZ zU)0n|wiaQ+{lv%uCbIF(UDyG%YiDuYM@JGGDnhi{apnTIVFg_094xy^c(aDZ?w?Iw zZc!W! z%<`HRy*vXvAP2?EuAE{K%W4sT!!&Ju6@OjEFQlx236&cArNf{e13)YiI3Tp{NnWM6 zV4UN2=Z>@H0XT)u7pHHA7FmFWG|=K#R4M*s7J+06#JEPhNNL=(!_4U9w0`I1g4)so z2)$`3QZgMD}#uK+}sJjmkF;{+GPQY zI)9)8y8JBQm$d`kjM9|8lO=&}v$+n1xq-$O z_=Ng^0`m$T`DT{H;x10TY9S~;T za$D~Y2CsY2d1~voA1;cYgR|{Y+&Qgn++<^r-#1{Raa1`$Y8!xw9=^zte3-)Pi|3grjC}v zvWkFj8o3Z4@;60o+&v(Y@|uD*i<@`sNh-@=bMGC`8^~uUuw@1CGE7Z8w>E*Fe^bZu zBvc_(wH5FQ_V2Fo;YJZO;1F^I*%TT#{++PvN&JTbH#PC~d`)Fn@W9hC7nfMXII;Jn zO?9$EU%#wlEnNE$7hn-1Pd7U-0+~j#E;Wr8+R}|NYT%?f3{89ByE)DzUyaBJ*#sWt zfUUQ^KS2F94@3_1`Sth6I7RamKWzjR`iTbpbgqpdOL)wv!YU z>J1vqs};MkU*BYEZf?=^iRo%cm+|y@MnfA^rAMyDDw{Dp+$hwybd~k3fpvZ=iwN!U zMVd6qx{F@BdA&A>f=g7#QCN-g2n=cF_9MwzOs|(S^nt&7D{+Dry1gY8CRmutz0PMF z+>ZB9doc_-oy`4DQX$}`%D^GM(up5aj(~|tH&-SKuVboJNgJ{FWZTqabv|fs>+3#Y z^Vh!grceThK;HG>iMg!I>2?EG)1kefd~lZJt6*GzGE`zk+pKW`O@0(MK>0BX;_jYQ zl5$;Wa`WR1*5G@Z>2{wZir**dt&Wu-B#Anck!P%43t%r14+Gwu;O)?(>0h$O$cijH z3Hy5qBq3nQe6HpWn+#JWa{%mxg=Op+QHc96(CiIv-ISYm`_R%&XM>> zFNzHt8{Sf6PZJhOYjcef2)M!~Ryx+TrgFBcAdj z%#D;JTTai?ggdsVEiNtPyydP+AW38OFZ(wLKY+E2zZK{$!iqAv|F(4SWf0%a>cL$S zN_%@l1rFf5&W2e4u(QbA7|F+N6(Lo$dh;JAWg45jO&sB&0_Z>Ssm|%t1!5Xul+)Sw z43WaoGn3>-zhnjfJ+Ml9ciaoC(Ez!oCM?&5B!g^M+J4pI!5`vpdTm_;e2X_1TVC2b zTV5e5m9mxQ#I}Ou;y{eq&Dk=`*MMZrO>MK*DKN0~U%Ef%PFvWZo2Q-5-voy*f)upp z^#l>ciyXCpz6dz~!;p`*sR1-ofnYpA8cJKQ^mZiE_E(HLR2-{>H)OrGc)TUF!V|xY zKGUCK8;8Yca{oVFQ=L>AoUq;yiB2^u2o)O14#l!vOJ;7=Jsk3dmN@Wb-eVD`KcvbI zdW%8 z`5Ti~aXpJWO+=npY@I$k{jyZnC7Fn)xw^JIB9!5l0Q z4spR=<1d_%k;}DVSg3XEbnpb7SmAVR0Va+r7f0pwa0cy9HrOMR9bQN~KcZ2of78%} zr=S;qbM-?fGBR3=i(~Dsi78=!D31hSv4NDcA-vR-V_T48qG_Pk}kAhAxt{AwBq+sh`>LH&Yh z1Sd(|H0^ra>7$>rcp?{DC`I1W0EdD;9%+nFBM+`w=zCw8IG9*qbMXUQI)CT3zD{Fz z$StvdpEg?|Rk(lu{U^G+XuE6~sKSOiBcjaq=}qu!KsK6W1h>E4FO|aZB52A8vL`P=JD{uMQHf43sj|idbSwW*b1RJ%9=8nY!}pw4UGH zCGBuR(P>{JVR1vBWKS~OX;Pri0shTBV7mlt?g7p37}Kw# z1zYTSj+cH4V0zSO2btmywN2W$T^$sUMu&B{YHSz5=V1TtM0)1D5(;{llyKod`9FW`^dzTJJpEJA22Rb*EMd1Cn^d=3Qnf%b zegdu{RO}p5ZkHcYyuGTH1IPCa{|#5kBEyA$5yGO#{pDi&(sio}Y*7`n@lB~Q_RdFT z*IMgkniDMnN@d~g$(1+i2hnPS&twi7y2wYrnq1TrmMlerVY}ymyznKpypp z_(ZnN-EDWj8aQpEu9~e8X;Rv+#W)bB)W<+`AE`$rx`dQKQdMa<<6`{?oS0w-7-RwM4?JBs09AANWE0K<$FuD1NLh5g z_e7~78TK6t;tO>68sgpIWV~{v=kXmpy7qvJ5p&Ht;t{BLnGak;)}MD>d;)*;dLFCD z>(M6|$bWp)iD{TK(~BX z0XP0Csv0%`LLPy4yT)V-W}OV1=8Tv@J=lwC7rx> zAEfgCa`hxM%w~p(&q2b?>#kq|MsIccFd_92)n$Pn`5ONo#$0s@@t z=2vDU{7<+|SEx=~?gy^3fX7pf>c{88d7Y!@7#fpn=yNB04rJ#;{!5iR29nnL#&!fC zk0^k2@cdQWz|SHgPcPAcBa~3yn6vys9A)8wDV)5O#$!#UZ3UnWzc zec*RTi1H{|*e-9L&ll}Svf~`rvTsUXNiN1CnB_CI*!%DDV)O ztL5ofPdP4dH8d?>jiE4&UwE0P0i-$WdE@;)ZJvrvoZ$o!L zs+wyAcJN=5y;-WjaH85KgErC|)D>S3D<;J_)q!Pqt08}23yoGiS3qvB;=A5$%;$^Y zdt~$H>E|Gx$dBBzIo@uw<%Q$zyfhW9=-(1ML+bvIn7G4uJAwd?igCq7S5eh(&CWN5 zKUCAC(kFGWR{Fr-)$VS*!bFJ28`&ij+2VIs(>VVzwk_5P?h*lV^*Np)tqh@=A6Q7KXL2Ik*7+ z==baJD+gVR?aqZa!H4H1yiR>#hJ4hmMNZaa`muogVc?gDD_D7$D=HXcL;N^4GE`sxKG zj%=0E@!vYX1p-3@oTvAfpnyg7&d>}WQ#-CY(*s_H{dbMKeO z(0|Lv8-xOM8a9hKa|=iPY-{NZF4t%5!*U@3_RtI&9^mg2An(bwUKS+GS#N2pisVR=yt-%92p?|RxX1~Llxf26f(e~$oYl8?!i1Ggwp4yHvadEq{i;`9uRnuWq|CHi>Xwp7hB`~;L zp@StRfdL5CIH7s=XH6t|OT*XV&;9!Bv&ZC$Ym%Fr&)Y$;vp~HXNBBY@+B@(w^nr*b zioBS-Z?8_Pv-p^9!^8 z1q=?@EFNQEDHqUOj6TU}Zoe=D5aYWz=y-UqOI@pHH;Z z(BP`3hPIY{$RFZwq||xXXa&-M{5dfpk9zZE1HV4Ty~1I&e!3ibR78U#j6CmY?SZWy z3!snN6LJ-h@X`9Q$hrN#7}`JxaELJHn3=Hl4wLbSfW@@~^UtJ))g!%`bkCtG=YSG- z(RK!H#$=p^9d(?06+%3Yv@?!`xj5V0_a}mFtSMJ*LxmYPUOUcDxp3Fbz%Z%r48g_9m#*?`{ z%zo*XLWJrdGStP+Terp6e(O8ct-v@wJXHP)Fg;CUi-Li_3L+(2<{Z$lGkPvKSt=4G zVa6nGgKOYpeTEzHFv2_XuSPN%OPF$ScH^26DimM~G~A*VeC;1QI?-$XD^duihea(L zL`qdn-X~||hCU9_bj_n{x+T*W>AzSwc?&28CDhH`^vRH?q6WVLt$sSbtjmrPu6D|? z8v;~BI1q^f=}tc?Jc|y(mukPh?-FJt03;6dg8D^T4s6{k5ag-b)G5L$YG-Pm1vknn z?0&=eKEyz}PX5A~X~tI$Y%*@nU5~Cl75MnJ?-NBK^i`Zs8||`crw;$HgZ@}QxyN}- zLTS4%|B67`(i*UE5lczH7$+E}ti)n31v#Cy1De##9_IkO)tpPlHK&c2%Fo^15aJr7 z{PfPD9?!t+LdOr)MA5+)8)m;wL!A%MyftRHeH=82N+S9BkF0i4Y!pyta5Oo#lpvrs zF@*^?DU6%7HEps*f_d?sy2JiZ5BwsEm{&qe6%Vgkf^dY32%7G_;Oyj?J8gPu6L4@W z#hO0i!5s(v1NO?-yf1}C;Xg6Lc&>^9?$>x7O@n41S?&BiWi%&$YSDNon{oTQ{qSO! z>f~_3lePyh*Y_0FnMYlhi1R3rE?hAOLQ;BULR~6DA;Lr*NUfQfnHe%)Z_VviNmCJ> z&3O9(J_SEb>bEUy57=n1!)D**e^G4>O6US9A~BZJyP`+H(vn7E%Awerp2aiGjyQ`TpO;5xHeWu{XzKIGXzCHT*mE5d+zPOs~p9BodT*?z>Mr_bt zeoO=+5Eoenm?R5z3|f;Bsv&#$p@`Y9~y-@7!^9w++2bOAjeH{nvH0)a2{INv*1xJpcnCDro?Fe>^AO!k=I z$f~SSZr#v&bf4F4MWS&pJKK?{+OMLQ3v|8o2m>f(Z3)p&YY({#Mzw2eR6to~X{4jq ztxuc;?_y{1!=>_H!Z3Em#Z9kv%5R~oL}>!kf{NzZ`XAzMZu*5fm!TD?@=rYM2}@G3 z9nRM2`yzO=F0$bq>LMv-X5FI;L{~InA;1VezNdw%FJDl~+IC>Trms28jw7$Eq}IBA znYo#xU-o(OCUdHrSF-Zl8+dh=6ttEEdDk|!{%%@?___Bd=#Hn1pg*mVMN``LafPgEhp&Qcrga8@ySUpC3?%-flFScRlr>AQFr@ zch2_UXY`#kG2`yX0k==6D*LVu3e!>hi2hN7gf~{vMGx#lPV$9E-sS#lSBeUkCCPS z#tV1Frym`tgDf&P)o$8;boREP|6m$)3EuSQWlz{_Sya@@q5cha(4n<67tG}8TrYI_ zMF`Q4zzcUu`|!%@7t5(Q?LN6|xw=Ks?ASOJvr4Z6ol^Ji4f~l!#}4<>ddeVIf*A$! z-o!hyLD*-6N`{IncjP!cr zo*zpw-o>+PVqceHf)FEi&twi)UqqOQNiWTeXLIYXSJu8?rXFX6qUsboj=rmKNjYmB zscAJ=!3#wX2|>4_sInPj7B1j(Wnq?U(+_oH?K^T>tDOD9D-dc^DOx#QIKyn^xlSY> zUOXvx^)RoVvX}wA*26OB9CIDM)n&TcZLb@;dB^3rj^?xUTo8CCtB60e$@RT@^o_En z{IBEJ>aRlJZ~V-myVM%h$L^8wPLBZz)g8Yq%*e&t6Cc`oZK0>HAC8n??EfgNJ7ozt zr7Je}A#+`zW8+1+zC2M^FRU)DgF}z@ov^RlcUmhX<~w-p)?K&`rg-0CIZSd*-K#TZ z;Sbc=UC6NNa0ho9q*D$X+?MR{em8iJ+ClnV!gzVDQmgn{>7B#N(W5Ek`D3)16zESA z%%?a!Gv>CB$pOh3(9!ml_KL=u6{HnyNgDF@c`=^c(D))H%gszWQHJFY0WoR{_!CNw zZq`ju*hS&yd|D|0T`^^~f?X79tt}=Bu$}D?hg=t!z;BW&o|ROk2mxyr`#XOY5F$(< zuMVK^5a0puqj|HguXO72;+TB>sDolAemL3Xn!T`NzY@b$ z%QqgU#cJSRMNVfBA?q%A9f9`bstUB`Nv6&QfE;>}iNW>pfmEVkF9Ys0TxEop>-yls z%uy&>=!myGajP^*8&S@}3rL=cPUg(`TK1^5z|s6wesPV(vaQOYO9MkqUO0i|_b3oc z#of}Gp0aO*jTxmC6l|H!Vuo}cjLTp?bKb!_$aiRD>IF`n#MNWjGBDHXG&wws#Jw$_QNu%5v&pnOkEUi zMfjN!T{Z&Y9_2MRxG3oP(_`^3`*|FR%-2OwgZ;Nrj~a$=vkfdjSjFZ)W(N4)9%jf0 z>rjY6By;Q$F&ucg4EuD=4TIk*r&s%j#n-QT(Ls+@RaX!D6u9cCkcJE3QW?3mdf3_; zUY`~TetG})@oZz``~K6-&dj3CWkA)Bx{ow6lBFX9s=XTeOqJGf;}!Z!P8QzEIBN^w zkuLC^0?xr6;Q?oIe6*hsWt1o>=zf9(xmCuvoP{>4Cy(Q{*Cn5eR1&72j3~y9j>I4T zS|)^^TE5>qf5kQWsKRUF`Aqt>r(<{B##?WtbF{4;GrXaQ2++QVoY*h-ube(|diowA z(-|X#DxT6Ip)W72&KcZNg}|{6xy{S0u1-m~fK3FtKJ0Qz`}ixSO+-cMUF!q}LSAZ; z?XzD-EV4GvKm?rm?dHl2b{AvG>DW=MEGc{Ak8l+j099nR>>yfWZKBJFl6TGxz535N zD^ABsT6w*;CnMgkv{y4H_W;0z0mF6)ClmkzrQym>ALHn?>+hY6W2{hALrX)a-ZCWY zZ;6HY)GM~m^qhE>B9foj$F##C%t#AK7ODDOr#sty3lU6izcn}LZss*pcu!aFDg^2x_YawGGI$v)r6t&jN}$38C0pI54x zm{J`fLj+%Mgx*Wz(PVPrf%513c}?{7D*5xlS6q7fv(?_s03-%3#K(gFzHBt*X=FlA zFGqTRhB>F#+1unIy)NS7L76) zFBAUOmp@%o z&h^xQ-=)=3B)w?2qe`V`Yn@uY%IVC7Hg-x0=ujl^Eg7qzo7QX-@AIhJr}S|bh|;)t zo2~X=Ltgm_TrIY^Kl!nJ`(=VFjOEdz#0D=5K~~L4jzattsyla zn#G-E?m{k6x^kdsm|387Oez~9*E2Z{Zq52_)~aoF#v+3g2(fZf5>23J69|=AFO(~v zYiGyP_sIrvxy@db2VZ5{P(PH*K2H$6tq^h8kV zk6S!AT&(&S(wuk?D7N%}U+{asUH4!zdt5Py46hyDB*AZ{cNXRI@k0^$9YK0js?2D( zsGpw^YQ53j6gzD_rQbRFyY9ec1;!E&?&p#TV+HsM;obK{uYLJ&rVi#_xWmEc3p^+b zKH!!cvNH}Yb;r!A+p-fzb4?3)0gj#}uZaJoGu?WJFYBy>h!$QCYuMR2{dkuQ%q$sO zqmv3Z6Z7gC;Ed#ye z)+|Q|7)I`9BpG=a*^dZ!M8$#YW7y!JiT}{mi(k~g+TrOZ6B-zR@K#~>an8)-%)gFD z*JGC@2}dT?9i)H;KJa5VVn}o!4F*^yqJR_bOPqXfg zk2`O-DA2~T3Rz(4IMwD5g3=(B_0wE=hP`S-Z+k2XMq}ZGev#d2ZK;0U+NW_<_ZSF| zQXpU38};ee(oXT-M~GtT^h&d2lDip!x=)XCx-f0TyZUszlnW)}8Rh#pJ2W?yy3z)J-_~feP!x!%fW4gY9Tk$&;^vR0xgKLeFyQ@z5sKmz67CMO zUkwvAfIWqkocyEBvM`CFDEitd~@Ea(B_5#l&k8 z_`vk5VB0dq_2*5r1&;wj*UPXdKCc^e{pF&$?p-eX$$oK0VOH4zmTyCkOr`+?tVL%? z=@53A-|?22sPF-_6>h3nQXS*;JWd`RhB=Ss;1mLt!3u1lW7eL%-@(19tAhP$;?%%C z>hzUz83)etf-pTMi6Kj^zJq1Ck(Cs1zgv!RNaw2cpk zMxsBQTl5~A?E__B=0XE4_76c09yD)q9T#vup{-P($?1b#HiNvL7=L}*v`2C| z)t622e5&o!KjM^H|C&QC6W&o{gOnW6~H^$rs6Bp(?&)1-s5& z)A|OtYV9=7L8X82Fjdp3hLJ6>=(d9dMXe@pr&+#Fm(sH-AlA_ynORLFf=*z2dL$Ly zRt97ncOa%@(#Wxriy46D^<*-!m{!I>^pVl_xl%=nqYr^=Pqu=nXQoH zG!$x|UU5JxH@?@xoM7zYlUyhl58c8d?7Zi3~F=l;p}0ggj9lgxn4_3Cc_8^zsdnj?fdv`84A9SN(?Rm{2P>t3ye zhA%9_$ZZh9KN&AsH=j13m=S8|#T>uLU+rGYoULt$dvpeurE6t`w$DzS7?& zzV=dhE5S!)l(F&7gs&bJXw{>HD)ZMWkPee`5#W;(-m50y!9Vn;DW+m)j?{XRiyL?T zTj~#~7q7F2m_9EdTqA^6{jSUo<-5AXHzQAeCW;QZAnR^{6(cu^m7X>3YRuoerxsDz zPaiIa$&;I>JZ54|%NU>fU=~)XiyEtVNL@*z5wAL0Yc)1 zgWf|Flpq^*@p*U!p3;=q(Z#rK0`>Ple2S` z&G1$kv2EUk#w6YY>Pxd&=6#Ze1A&`8mOY>LUHb*{n2Lc^WW9{$g4#S-CwM9%lPxhd zrcCp#B`;0`bp6C{qgZ*ye>V~s(Gg@g2v(<%wl2Sk2CIb^Ilk z89x!0tLFQ|rBT?SGTL|rKfnTWmU*eR5`6f)NKcsn$*5C~tUD}2|GTbX|IblkXs=!U zr=;~W++$%byP{%ErCaNU9+!0+>iCr=_xSa>E)(jTx49_CwC88jOn=!xOjo*41 zRJeF`!T3%P+~5#F4u8Mlv8cZ$?up$%Dmg0*G$FbF)VAfe7th!kA_}zoUcBxjiLSH$ z&;vJkkw0rd?(;5{M_tI<0uh7v@W|3Y0g4-6as%xiYEHXlg2aA?`nKupxF>9=0iv#a zS}v*TU(_k+B4Cou9GuCAN6Qo@_5pis|DK1xj;5m`$eSKEk(Yv)UGycV<%*Lw=CZMj zR3%};8tBg(Q}ygOcYdL}pZ-+lI@*IeGn z8D($holVM$y-13DkgtdvKEyR)+3Vn>{!wF5z5%uVY!#R%VPI-P($BG45ds^8q#frItQ( z))c4CmLqx}ilb0^>e6^{f&5*-9$nTwhdYB(SM7%+zZSq}?)Dp+NW@GF5k$tCoR^#SscZQKFg9aN6ZH^)wxis6DBTR@#{-6gEwpe*p?xtUBxrntfChCK+C{bR=hqf+l(lV$3oAZ??AjiVRbIl8y}fwF zu_}MQjdlvphi%1WTRKawSB*~E4&$6DrlR}4Ca8#uG)Td?+qo`TrH|i_f6yw#AxEB|TnfW4)tidksN^U}(>c(*#yMU; zmHzhHboHdyVnkDf2XAn$B%xrkvg*F(S7@^5bZdzvibVhgvXvo?WEy=XpzMV-M^7J`IF&4^t|0qp$)E?lVX6`e~}e@`c=^j3hI>sC(2!@qC1{ zqwdu0kZ#qg&U=sJ03j>xoW7-QpMHEsd>$5bAZxaFgw=6oN3Q$EoS{e@vS` z2=%fU3OVVXev|T&j7JZUSCHUgyNR_tMCz|~1I zqyNs2y9c=Gb}eV;%pmcCjiyG&zkNHB5&s9YvGlWZ3?7b-#SDAKjQVDNyt1V=3iWjn z+SSBRJzhzjdam+F-yR-rhLTjxii%4Va>exZoeV_4Njjn&zUqepKOu(7@^E=!ZY0~z z!qP10VNCnzK3n%Gk6svSzxrTG)NWnx*lXK^_W{_HhfP@3yMO%q=XkB-7?I1?@yTJCKe}r9h-G)VRyWij8f~xHBYp3%Je#I`hd>hrP*J)YI#r2z6+;}9R!G1O(J|a@X zO_4?2o@hoSSF{N>;~AiLR(DSF@3CC_>v)1TJQ8=#IC4cP=_u@VdA|b=MwH z(^a*G#9~a1VE|K8Q~C=x zL{s4+Uhr+LJuSmx;KXwT8^z?Ov&Nc)eh>p$?W@>?Cq|nSj2aqra^w3rCo$96Hm1gf zGQF%U$z`VRnq?ECmgG@X=*CX6A#M3d<0)CSb{JGCZO+lhcHxx~_D6$mt!~woT!GZ_ zLhXzaiGDq|UE>Bj^1JfdQ+WIzQO#iN-EVdu$9RtvlR|gBF-YEyKU1BIRaJrgFv=vj8;)F-%oAQByP|$;~sTms!cz5d?vFo0t8&QtaE=NnL3&JzF3i4KO}a zU}|a!b#c@b9&`X#utQ{v7~99IAPp4$&Uo;Ob&KfCg4*+Tv9y(6g`&rRfg%h?*+2jc7+ zPU3RG_{BW4=?Zn#V6Zn#e@~Pn#}}v+*3k0lOH)!UO=;zKJ!#InDotrzCJiIlxM{m5o7&Fh-01^rWa?9kg04#DUj|EO|q zeD%QxKKq_$rWZ@^FIOACb<1^IcEloHX+B+KYJQz+-2lNwIN)YDH>WG_5! ziSy$b)b%`SZV|omf@spV!E7j~`K6XDN8sF;?PRC-4Ja;AI;=KU|D~dsk4L+QYsc>Y zgU!DDD~hWxg+B*NPk)`af8h7+uYUXaY;LW5L@rg&7;?#Pn|in4_V~Iw!W`J$&Drr) z7U!JFQ)*_mC2TiaZC$itth(cxwoC-c*IchQPe($Y&+OXS^_gO^cKY@khnipd@Se@S zaedG{SR4Jcpl}q_Q-FJad*tKK*~4 z)El^5wiJvm1benU=uHhhaQwN2X(Zj^!e=)7@~&8}7W6O3ZGUx`h2@Itop)>-*gMkw z!6%-b{ZM*pW>}uTASz2!Ez_y}lYX@T{6G+;`=n6xIJT`_Jp0|vzMLzbs|EcEaqGvP zK$P5WQc9oy0pKAZ1H7!^l2>_Yt`_vGK>y$!?723` z*y(x?j?n#XoRPm@!0Dnft`_pE!~X(yDc70~_P5ah001R)MObuXVRU6WV{&C-bY%cC zFfuePFf=VPIaDz@Ix{jlH83kMFgh?We}6U40000bbVXQnWMOn=I&E)cX=ZrK74o@*vVhA{(j7}FT~f=^NJ}>h!qSVRg!E64MnJklx}>DLr9_;{X6ckO08lzfj070Pq0<0PI`*W2FNCRIXV~TK_AA16Na4 z06hIqzOPl=WRQpb@4V zg(#{}QTmL>_}M2%K-#P{RwNPnQy9=2pSdjtB8Z9Ls^eo`)ZWeddcW-EV?tsF_D*KN*pDeboRw;oM{FhP|n{>c^>AxWjE+;wvt; zL6NM};%ywrfuv%6|MRtW;W`X^{)PUAbJd{Zg7evv%IZv9FjnL<^rjr>8ejh28(FP{ zCvP002#VL!a4%Llx{J0(NTy+m4O8%!JG{2({`Mlb}OQ*)Jj$9c#uAl^EC zxEz;fIH~Pa{Jx+&xdDlR6861`U@%bf9p2++2JN;QuL+5_#{tSlQtyP2KG>G`K+8>Y zF9WNLzkIo5v|upUneH3F$@$e)ouE2OL9jwC$*#qi4gQqax>s*5eSiJr=V(4AepdEy z+Uqzyw9E`p1+G6?fQ;ZTf1i~DhqinAP$44PMgUkUZ0M(~P=*%!Eepo>gk6cz2iZ1#2P$^#=1W*|?5@eLQ7inRX$Vx|0FNHhk?S$Pmh4s! zeidH|J^LlHJ}|s~-)lM4qkv+ArJa0Nu%u7a_gVp~idn&i`92C!TBd=0ecSGhIz~nE z7AD<%T6>almUb4OClFg0H>8Huurz7rSa=D`Y0rmH67iUM`F;{6fLy3yPJD-d=*)f< z9`yRK=H-Shw*Oa(n5ppY4VDpSme*1!O2Rd-IXsPcexEbo>7FHoAXWj+9ue28$)`?I z89M{Eto&x5*2O36({1sL4aUMg^>HyfK2;qZ#i`8QIBU}QWc5h?vi zf0VM6x+P!prTd(<(2)evE#q`UPiodh?u+3Of@+hWR+Ur@bi=J*P+Uw((5t1+A@fC1 zzNham|HbBdks93R$6vm)1`g49sS+v_GMP30!QcAXXvCq(3#L6~-)swIn(U;SV zDqTFW9>ct@epqg<^xFGI*qlV3l5xec?Pn~lzlFIvGT7xHBrqu*YYEz;i+N_?EkW_;E zA$v0>RIQhb!oD~^&>S~kQ!@Nr8;eqc-|yu<@|R>Tx{2$||9-2%MrvipB4eMFkblq9 zb~od{yGw6r(rpaT%sncsgW%T=DtMm&pKi`e@HGEQPhaZP#Bh~!TlsLy+FLU}PH1&m zVWuB`#bf3&YhW;naozuJkp4QD#<6L`VHE*=-eqALh@Ff{ctP(+&q{)=@4Bbv7Hc^^ z@hfi8_m!UG&*!6&1EZr%OQKyBM+Y~1WN)V2s_|=QewO>!vwDgA*-U;@`)~NOtK&_V zpgVHP&nelT%WfCj{ZY#mQeCxq#1Sd#lr`X4c=e)|hL{Spwo{aV_c`i$^GNJB)t09& zsp3~zAwEbS7S9g^jE>psOUVVE#Mob#YeJ{P+_!DbX8BgxEfB8Ab1MJ21;epleSS^; zAFE8%35eo6?rx|#l=?u2$5zf>sR)+A={c-ZyV#@&SbVT+rq#!UsVVUR@3u>88rlOb z-OGi7CSba$(WZfZ{vM8v9^8RL4oag~U7TppK%FqFu{g+Kv!EH8Dx`-u~mQ*$Iy{xprQUqef3wonHfbpO5CaL@ZBUMeeQEMCdxQ|+IY9(qBxI{os7)% zyaNBk!$X4K&bWcC@>!yRM5ZC#Nvb9$jF_0Lb*8&L&J9{RI-&E0XTQ(?HjXcNX{2es zD$RFTB!WuV*U?G+^n62GL@ScCcRB91&-Tzyl&EK{$wLQkI;R8mfokpr(d76y{uOj} zn(Y^K(F$SJcf5kf^PRh%pC$%@TQeza`R0X3SMu=cx?EA$0FQJp|!A&8`c`WoisY&d+Z6pb0yF)xkz>V19!94 zF>8n{b1T>q0$+sw_A5KEi|glogFOub4*lKWwA>ovnS&5 zxpt#=c|PU_hpKeEi4>2x6mQV3+R{fj?%SFJ-|3i!W*+BNHAOBzKCe@tYY@QZ6;nR> zaSk#jKz^<`#!9QqvHZ&`e_`?s#;#w9lR4|h23t9H{Wyq3$(%Bh?2Zm0XRlVm+3 zH49-?vn>bGP*~=2AaO7gGLg+|sr6%vMspI+)fld^&{~;2lelzRPK+r+j8`FCAZzKG zdoV-GQ==O~@Q&iZsQo$!>K<_6bpi2Nmn02!V>8NmqlG`hdl;+UOA<0aJ^<$JN9Kxd!7Ln4lfAxW{<&^-6PFW99YZm7%9s#%uko6& z5;*egv7y%L4XgZy2SNOBQc_Ci z-D10ni}N!{#uj;}0E;#HgahqabcWh|>QQ0g0)HKrX*t!PiQd5PSVn_ev0uME1(sXr z7Bqzf-1h-2lo&>xgahk9`k>t0V@x?Vm++Px(yWmsJQh7vENdRRK%@A>VK&fB+g#uVWWGMf*ypS z?jGZUaZ@LBa2ucWbrh*~K<}pt^Ztv%+@v*oc%G30G|1kWX`4bg0|quyQ!-;%&L<_E z;94pl8xtSxdY`YuIvh{5o_n^z%clr)V<8CtI_jYy&wS>vpQK@fVOs8)?cA0BVw6#| z>(SQS!p0M;k~1O<9pEK>0Vrzt9X@!p@zZ|3Unu$_pZllC^u}c&bU{RBYyxv`a?-VF zasd2i(qo%|YUPoat$;0mLhVxQ3m0hMwWRa@Nn`T;PgVFD5FK#a`HK5pZJ>B0&`{^_ zwf2aDb92IvXf1diP)A4Beds6k0GLx^dT=#k!zV^2#doMXgTZ55FsbmTzN?OCedQEsJi8aj$L)SvT zi3YD)CX6}O{(!2C4fGh8#e=)$z3TA|f=KqTtqX1L#>r_Tw%CycVjfnQHxC|-?q|qVvFiuf9G>R!P1>=g|3j~C7m!_ zoeTz2Q5=i^;g*~AWbe(WD=LD+K1?>9D3W7sdvan6U6LDAG6Q2*HPyPEYOT=N;#bR^ z1CfM11^nnp^`HvOz)_8zA6{Lsh%;2czRPk%yR)Q@e0XeKcK^zv5(`9>(f{0xKxOXy z=YR8U*=>1%=t3ENUG7;u0RhRO&1t&OwIBs3j>>=f;-&NIr;#ItMTY4#H0zr&PoceQ zmPeze12qKbPclvJS!OlBO4bWR0t5bouSLLN^VTi4qcwqV#S@DPGY-lL`d<-(Z zJUZ8_-?b6Gdx}Tdkg%|L%$75~cf4zH5HE)D2;7OMlT~I8w35sl)MD#JE*U7S-SHy) z>5=zAnJd4?bo~VuvT}#_c~#J#bl<=H7*X-0puP2@s3V4t9`9oPXX*5v*oxTs^yeM( zu~)qDvBX4`s954+HMuXnEORZsKKS_5qO%GC4(W}-VgFSmni#8&?ImB(1!U)WjHs() zoo-T*rpNL7Jo1n|JlG9lN#)|sAi7e~a<>c6v(i#Ga=lePZrho@5#3+!*t4>Gw9yr#ZnjrP?o2bv#g6u}_;F9PE+H>SlqM{YZd|EZn&Y_^s1eW#2uG5s^ z(Q)$5px%}vDl0mho1E3X?t+qH6`y*p{fS#8{nni>Mi`y?rI&h9FJ665oeds*%$4T* z2AksQ^1-x|jXFf|WTvH>6gGOCfeswHReDJL(5`H?!l7{0KdEhUhOQrn=uM zSzoH}HsK8PRIOjxBqnE%zJnmYWeyCVec8j&k3r4kqg7~B(6RlWWnqf^DO*yydVL$3 ztn9rg@RD3AXUeoLSQRC3IQ-Mk?Y(JlfyvczKyi)b;_%8h18RxONg?#IvZ2=CNC*7y6 zLMH48@(w^v@x5>kanA4yUHnoO0jLB_xgQu&_9BWCZOCJz&Ov5V8wddfVAF`T){(jkiUwfKsx|JvCKi%-Bjv5My3FVP8GTyCM#zd>?e1k^KGo zVXf_Q<`&kx*sS`!q{#T_C0D6xk90WCP@%04_5Pk!Q$up}vgVz!$@5VqR~zdow=0aJ zll#=pUp8>Ve{X@pg%O2yn*L?!m|!RJl2>UHr=m_?_$U@DesE!tv1=n;BlI2Hx*NZw z*srZzjeD1}k+XJ&#`4u^X^9VPx4#Qaq)D%=Ubg&xe1M1CV|+Yoc*C$T?Y$d!qNLn> zB3M^w3KH8>EVFOi@!oTA$Uo@-g9br(p@SK)-ty~29c{U(wplH88=C9oh^Zqcnz*S6 zp-7Rb(BAyj5zj9NIGyucp%x%zzZac*)L}Y0i0vJXTifJz2g!iV+|l+wob)*hE~vfK z;75grCtZR2F7#($CJ`Eu#G+n-NbN)2ybUoi25m3wdu~huH z+r$vrZ{H8EMXT(qk1EK_a&iCpx5}SAp2*sryFKZ^Pd;1*oVF7_y*EQxy?uccp{ z41tG9#G?&$jtNKQ_kyP8=#SE&m)9-0GXD;RWL0#P>5pDg)MG=Zj zE)p7ngDTqGGaMK}11saDtY`%PGG< zR}6$sFW#LsQsO_jO%VUtc+#!PHD24&*L4?AL9-FG$_X1W3@!)shaY&YY*HWYDkL#W zPN_8w!Ghvra+dkojEbF75+2t8WZ~fi*MwTe219QTsQnV!)UFo%^hKNx@Q3Z&)ir9R zE-xyjK}+9TBfS|{e3t?r24oL5=DIpkYqwLsj!(}$9>z7$fh)OOcPMtKM(ru}phho8 zug9h7EG#U-4tY3HECK=o%0r7T`9H%ByW|##+B7^17a18CgE&6vG6bHNTtC@x7mu{w zhf7{C1nk%D?%O`G6EkC7t^_A9zzs5A^?ST|`g7>5if?+r%5R!;rhMA;USTJUE_eq* zac~f&l+0yAHaPCoaw{^{QZ}L~#SEL2WfMI$YB_8Fy?NjQpC|jomKo$Oo-v={v9i#- zpCM$O;UBSDZ6~;#tHOpCv5_U}ii{?6@wh6Vg?Y@y=~>_MCb=FiRvSHqU;VCWAY^vN zJKTYf)!jYEXFj<-H*jRQyFE33JT`9?)~SD#)iMl7=HhD)v^akVez;koryHeW>55lg zX!nQi{@**F-BZ!f6JhCTEoS9z{SN?82vm?4BFGCB)%|w|0#GqQAut3Y27#;{(OmsM zg!e88dmG>XKOwOyU-cisz)#oEQ`^#;$<^J(#@@-A$n#tbP(+U9a$=Wz0z;n~* z;`;e!Xc)Go4Zvi@=d;2mVM{+@O%L=8_t5p=4uzg1%9MJ&42THKaCoQk#-5gJ^cl-YP5`_$;oMJU0f zGjoYe3-$=}f?!;Dhmp%iN$_w@C@Snp?ss;~q+w8esUNWNCZe> z1X59SVRwvDehA*Glo(iH=kd}@PM3|o1V#jUj7As%jr2Jt}WJ8EH8V(Zu*VD;q;%*Q~5r(ATK!A@;CmsuGrVrbt zEIpo#9?wu9tMg2fFgA=j5;}3#FfSa_R$UZ*F_Qkdg&O?W z)Kgp2s*_0T4e-VbG76xXYQ-L9zV`GRghYfwOgo&QGlrlO7&c^lobM19qT6ijdfK!*dO--X>J{co}jrc0`;SZR{AMb#t_!&OiEN(<5& z6x&AYF4K+Ct^itpk%C|B{}-fy7v=?^3sA&xC6j{aO8fXjDj&yALmQWix@OoOnz4iK zJ-U7|nBaLbf|~OsXP05hg}FLGxn}&l%ekOM)=sDwSCQY=d5-(u=I7k_fUg8fYeEt*n{D_Oi!K1W`$-Dp!JXU@ zmGt$AbGWA=Rie8_n$jh)>9jT1?j);$YzJc_9|AU<^`GT1obSt6oiCo3D-EdGYp`t> zN_rYvZd0aFCK5_nXIW6wCZp{6>&FL z|6#rJ`IhGIV>ivq^8(hh62?a=YJ=PJ1?EccTPp=B>!j~eO50|%;tXNT#z^%=w7*Fd zY)$I)g(T!_tFz`(lxaC-J{E6YEf1H<_4@%Y&{(Jg9;vi_JGa=%{o$>fQ!Qp!+lJ5M zCG)zF8L|9N3b3*2MTs~9Rr*X@f6#lU>6Ctw&$7usH8_uI!LhJ*xBDwrUpj&1#Z6Q* zBi5JjI;;(M$>VP5d&pK}ZC`E}nnDbTCkVf-H$gUek}vc?1J)k&zJGHd*Z8Q?uH5(R zZnkK94((-Iaq4?32Z&BdQiA|)-!H$4Ivr$YN&hYDc%uT|S@3?K0@qr}L0k za`wL151(}V#G3{!D#1>lh%_$)Hp7!wLI7mrZqN~ayrQIN*@btV1Cf|l%hzobY_9B; zb4C#YD{wvh`FNV;_uSx~J?yO;D|#@9OMG-1BH{BfxM)c0Yb5z04Wr)$`Jn>&ShBP} z-~5|_BLz<$$QETKRmpnxp|vxS#VQ1Al`e(Euv^s7f$XP{!}Kt*4-`{+2J>HThD}zm z<{(%V{~J@$5G-zTzNMDRe{uQ5_X+vmz~k`%@LH!<2T-LwpKB3LFr*{0rY5dOEmDsY z4M7IO>b&cd7^3rB)1z?Rq2<=seT4c@O!}W5pVu~etKD&0@?2Mylm!$ibS}%Y@8AOK zGp+P+LD9RbtMiuA-<vH6qhaZsGqQ(0h}C3G zP4$=$S2Ey_2@<6Kk(hM9$cFJEET;A+i~VZMV7{_BOL(P%Zq0;@stkA{u7G2_T4+$e zBv8z~MQ`E>mlvQL-07`)oEsX>wvDkvID!ije=m&@{JMB8jL^QNsJlrQKu#6vaimPX z6Mf%joODoI)Gu+Y#(B0Je{8HZDOT>ah41S_j?+aKelUSOj~LS=>le@WNNItY!Mq;mK!TpgKS`8PiBS->OYioZb>!|UpTX_S`K*s`?6!f z5m23V86=U>YjnG=>};{5JkYB1(~$*+Romi+8XJo_As5XlciviM{*&!GM_3kGNoJbG ztixL0AJXR(srG0K%zbFy|biLc6LR`BY(`SQcY&)P5``>4LYd!qua z;^?glnnHbCzk__;Qj&T2KpOh}mqrC~eid-fZn6;P!9U;&yn> z{W-FwaPWeeRY6<+()i55Fu7C^v~iQIvhdHE{|^W2K81b^bbniw#(~2HJA3)2Me?%? z?)QlW^7{*?)>Yt7)z7@)v|q`fx4#e+RM|T#(XIzsD%#Q{+08$k_T1h?dxhkB+QZ@S zIJb||>ytnOe!e8K>pH6my!wV;Vf!D#LYBz`gHx&92?t zIGL7eDma2q+=$8@3Ti=;XObB`)5t}2ywdvZG~+y+iX+ z$z{|sY!|O><4-qfHaNJ}6C}(7PP-%X-k@8o9+Xrg?f4vC9Y}kojGG^vwn~Xo?r%n( zZ6^DBa#2NJ9H1bUeiWt!Z(%52Hu;4ju(LgFIt z2UU1{E&&4&0qo88n_%{S4F#^!DlD#rweh7xb#5N%n&8GSs*1>@`=o*a^`ZEkFG!z9 zVl%UHOpo{EIBs!fAjZQ@WAT26qc44%p@Vf0Hi#Yna#NGqvk1*@_RF1F0=4+C+1Z+6 z!bGoXo^L9R_|1pTyV$cHUNqyEJx!&!gm1-~7&BhdwZK?hV{3L<25+T_ewL9dg7^xV zZ(t>M*Eyph2s`)vy|_w;OV-pjXL2Uh>l>d;X)a|j784kIPDwF5!fhxlhCS}F58+KL z!wz+DB_(yWRdSCcG5)i)Eov%^=y{|qnQ+%MHd1<-M3w&{1O|$ZuFUdk(tiV*IZGzR z_3Pzi%P+i=A|~E@;eMwxlJT65s2S7k=D?@kllF?!_y>QwT5~k!@(TGn2uL}23=Sd# z7gl_X$Qpp{GN~;oe96ma73;-$k5ILAfKoI;y_I*qps*2Nt9?B)^ZMAmv4}i&T6Jfm zpInu&tF?{G2SAfXp?AB%t8*P>^jL3*zYk|l=e&V7F#neoQFy#y7UK4VC?|u3l^=fB zWKrtfnF}4f-%9V070%ss?R-*Sds_2{*flLAX4J>E)rRz3LV3sf_UpJr1<@iBvW969 zIXg{%;5UCxOS8ak0Z4q@4H_3KCtoX!?Huvyd|kyY?j3x52Gq=>tMLEyYc{?ehWbnA zz6n~KCX`PwE`Zl(7$F3l{@F2^h0^2Tsj3;ND;a6N*C`>2M8wZ*ck`xyt61Ia+N-4> zoi67ZWhTXzHx?Qud)XHtC(rxtuSmon`83Z`L%@uO|8ov^@tw*F2bJbFkCKOb0S1ZD z5GrNUq{oXG+W@!HxJ(^{eY8T}(bU#&aT0=Bp$!Ku^qSOw_lpCleg0!z?(ominCW{X zLeT1SoR@|QuXg=o$Fxjz_Tk{l>G}?BD>k7tb^^>?;$lmCKZM80F4CMFH+UfKp0{Uj&rEvkg6D&6(9nDsoJbhY7%EcA@!|>))sOv6$f=s6p}X&0zEZVUCzGqR`5g}Sb2zE8J)Sh zUBd;L8d^uZe|u(CcFP+x8d-S!nqXk{qU`JrG&+IQa>7Wg?eoa7_+R>Fwf49%eJVyV zNp{rrlVs(16iVDjDio*Y{I5@R!OFO7>y~Xu^ENa^#WOWkZ^LOxRFh(us>gG7{q^-_ zm95g6>zbN)dE+7G7ymjI#;z^UJWbJd=ZYaDndgQf3W9O;T1ux)r!A{0crPc~q^&B@ z?tqT()aOZ4Q z0(;{PgMq^thk~w8MtueX8%>zwzkFc*PH4(h#~Bz*rS@g=n%e02PsHv4TjR}X>v3Sh zziMwAsg5#@l^TdgH*OY(Dk_VLfL)XSg*_Hvi{*Yfe92^tsNNpBtUv7Vt^JH{Wh~Zz zUX1s6e}9b9;1vqU$OLBo#FX=?o~*SXdMaan&-wV(?cvwP^fWX5YrFqa)Vw+U|_ zQuJKF*#9Clw3QlLikPBKdcEQ~# z@&|_$(rFAU9IUq|ZLvjvAL_hZ1H`o$hXpTLOYISTvpb@jQ*T}T_+4Ccu8mI2clwZk zdPG>B@D{Y=1ir0`-d(gfAsv05HB{m zRWP;;zM!l(4>)coL8zD5T~YZ+_Vkj`joCU#RizC!3QX)vS>Ri!+Mz_OF1s; zx4V6X&i;Y|_CT5E7*Y#seiKLbS>|aKydxWRC~-M1o18V@0u-rE zMP7vjyNTt8-_XxVw&ZuKSS9%RMRkqAk!!vZ`!TTxJ~y;=!FX|6C+ox+Vp>u+P47`d zzlsjrTvr z>-oC=t{FwoS?(AACgj<#0?M^2DC4Jq8HX+<2B3z6>DwjDqu~T#EOctKUxDexW3_}G^_g&8WWxg^5KrL zbKM$Zr6;&1!VwhoKluSc(xF<4Kjl5^NZ*1HFeSK6-d^&U z_t2YUDd>nq!0Cp$>!H7%Ke3T**@iAsO=2YT_y*>{~{%UIn$EPn?#%1^2PCb9e2`P6VdPutY}eUrDpjUM zA87&6@t=K zs#hf6B7@Vo!o!M~XC0QL9zuQ3(fn}SjOkJps%vUv*hK)r=B}pA2xdE*el?!bIt;mw z-CNhZbr9Gz9GC6-3oVa;ij7N9UJBFV#X;|mu9nkoaY=OiUzlNB?JExqk#lFInU2ou zfBt+W=v@1?OtED6cRc5U3*1>6aTBjB8!I3=1wYl&BB4_xbiGn%Y~@7RsIh^67wp^8 z2;q5?0P=s?*NTsDFWoH(|UlZtW z(rx(S;%!>DQ9JzO%&xE<{*L_{>@yHt%%>#{uPhHMYg(0&f0!av1nyZ;oY0iOi<5sQ z(^*c?K>wZ4spwVNEjNZx_KTHRoA*H18Pi#}h^<`w`rW)!jE%(!Jdp1nS~)1@u+89+n`suKK4Z9@ z=jQL4f?5k!KC0|Gkz6*8;se2eh~e!CQ(zha{FCroy{k1_%BV61Ywsho8)%0~r^|3C z`jxdU#IJZ<-QJ6I8+rxDWNGj_+5*+|!z&61SCDY%%#My+rdfX*l#eItjt}@JPA_VW zFO6Hj<}9<6*s#wr*8kbc@tK%9B(v6VtWPEZhHaQ$m2^&s6eCj)>c``ymfKIC%ULtt zQCrmp;si2xX$5jBqU4%T_QKc#$-vyC^vApen%loH=w27z54{p9cTFCBww}qt{0~a6 z-cnCisTDA)=(X}G>UXyAcJei!)rx8TN9cmRCe4;5Gxnc3PPEMDZ}zV2mW;zI zeW-&f*XmzV3fqU|^^_^lEc$^(r%E_DT&oMpe$b7*aw6pZZKl9&k0VM}!2nD0)vuH8 zp8`yy?3$$7ZBG|J8+8)aeyKDi?D&%wxkNay{Q-wP2`52nFn5VC!;hag+v) z;VzJU$3VHUq?uo4Q-&p(C}sTHpGjVtkn6ds^6n46jOzdFV~MN`8wwjF_iSaZsR~jG z$wQI&RLVjeNmaoqGnUX+W>;$AXM@Q?)W7Rdu+4b-b@7)cRdPS@)snIN{F~Ea2)h+B ziJE2p4c-`jlqP36P(pEb%D}ziJGa2lHJhAE?ZSUjV87r|eI3s;D>Bm5X5efkG^v59 z(&0p`Jy%-kmo$}`S@Fa{VVg$dsEvJZ!9cv{qrk@Qyw_#gV`McPHb|h4ZdFTQibWjD z5Dz>fi|VXpPKz@oKSrUV_RFk~dEj2B6u#T3S-m+7&5ZjO-80?uax}uq^13V81DD~S z{7$g8L+QV2rE>c$t5yb*lPE;WlPA$?B}I-hPC1_w9QE*$Mp7AgaPT2K)MgAvA2le& zDEb|ccuwh(w&@|Hw7FALyy5Zojds?KCN3^{thxTb;}c-|`dxdYn}6hQp{|REXH*PK z2gS4#qq~ZshQhV^2Wm{-*&c<=SW^|46%{}7w&p#`vyO(xZn!2ThRdw-7`gl?=yTi4 zi6~6T;qWrDM>I6!Q@-Mor&RW-yUE>!$3cYcQBZPW=t(LtV3(?7kkVG#m^^bnudby& zK)Pvp-Kw001{Ox0ZPk8EXu+4dGuNDyaWJUV-vx?FbenPAdzXEN=-09k`?jsCw$J#Q z+oy6NGEL0HUsGNF{3qa=t{PHiHj1adwk$UTmxEDs-(A1ssOUOwnw(q?v$dj%VWS)6 z?hjvjCn6xHtchDS)_;vR?pkb1!1uN{D_7CO6tmpMWLfmH#J)aCwLf zZ*XDxB62u0zexRD1SnqJ{N7+@CN}V8Tf)cu@!mN#GS*%IU$8kwF45mV?3w8WRlc;Z zZr0T&adK`Q*@Hf8jPzsSsXtBk>6P>2gDUKuf!^`PP))&Z9ez?u{%9S|Q&MrBCWf@U zMy1zC_R`&?*`nIFI2SIj6I-+~%+Ild_*>2?O6icpp^ z|0T*(EwCA#>D#RZ2~#kns84ZIOdsMr=h(SvGNz2HCGA_7vh>;k!^@7fzM7|~<9@h$ zTNx8FXQ>y{&!ZZjFy^nEVG|iiZV*f~!<{!q=DzRm{8cn4P~OLWBt8z#33|AFLCEVr`2 zwT5JZ&DUCL~QTQ`fZo_oS5 zJy83TvIX^p3}wm8=a2S;iZ-Zzcz${wcr+a{z;^>F22q?FgJp1c3&l|t+=j8v2UA$}*C$^iSJC>E&`cJ&jiis4OH~(3xH+9{%Ixd$wqs)d}N7-T@ zec!dnftzk!2|KmEi&K$NBXZ`|meox!NpisWXfv8rsp8WrAC-9fjR8vD8nK0|zC0_X zxP7U?42;(O^0V*YClN9454EAcqlkzcq@Z2ft2sxEnWE zj)y50`)NImVEyhFd}k7$$=?sEyOd4+fG7{iZzrci*t(C&%|_x;(>$J-JD!bS_xzC6 z)y82DEi4z5mbF`L$eyYbdetS8mJZ0K2fF@QQUwk?27gZ(NR?eKtR(387lY@>ilDdj zb}MTUbL9l*LK%7SZ}Xxj1AnHsruhKds3=lQx|Def3(JLz!}ZL6p7s$^nCn?O*(FC` zEZuD#bn#@Vb--{O1S^31aif7x=LXabmuZQpdCzSxvfnqHPj}D!YDDaBBt$%)C*8j9 zE6GBkv`lK`XYq6V6hl{;h8E)UvP*<6}0%~wz2l!#@p@) z*jodSUAYf#9`QT~#3#EV8c$Oa1kJMI;3hrv^?2FLl`=aP* zgjhQQ|Ag{~g_Cx9($1*VLSAD_1L=+=*aB=(*V)pV74naQc(O0AAd0_@mpV3~J z@leF$%0xg~UH0=;-kfzw(}xrMc)H;7nA^X*45_{?=Kkl{w{;|^iQ&zaMz`bX^shKn zDbMSzZ*3I(4b8Wfa^wnG6;I=XrS*rc#16tU3D3nN>~ea~gF>5T?)%gHt+7lXIOnCu zNVLAq0Deg|u;w?^bcPsAh?rtsa4#AxgtQ2bq?(Qx>|Kuc_Z1VDC z-^|=QcQ#5@Sr+3x>3aYGfFUm@^%Zt({{M-J40{!sMCODY5G^H?BmjVh1hi*kB-m$a zQ@O870Dw0=01y}o06fA@1?~d?ZtMWSp%DNemyD5(l-43L+SQ1|?I{Nj;l?&ZFQ;$Q2xn&W%GRmC*%bZ8?s zw*?oBD90iPk0=gLjf_8zYW-RF^lN|I4%5#xd}b#1&)>h2NhBg7Vk066vIGTD&CNmQ zda5R#u6Mm0>z+=i?n-N_55cFE2l@G;YB~>>`cJ1XJ+28alu^^$4HMvl0!h>$pgaj& z00B)8W*6pW0iX@;X?6bX-nn46?CZ~jCqz*tPS@MIK=YttM4U~XbuC0+44PzWWYkrJ z3tQ9+5T}jKdL(F34B>VwbsF%JX|@YCL{<&NL%l%jQ$Zt^M#Ub`QvfvMZ05kf3Pd_0 zz}Z|3oCx%K z+dcDJq1r<+5Jk9-NX=>rARtEpenj4s4eUkg3dHs&YD+-ms($-8WWUZQ@!VRRc_qoX zd3qyu-!8U_Rqczs@An%VRe-bxAYV>cr;Rj(dnFIPMmF*YUiNWB$!x2gLs`X@d`6?W z4=)~Kj{jzMyHMc2LUo6t4C_zSZ1>m@DKTh}+8?feIxrKS_t>m~f&C0{Gon}g?wKRf za2ThKTK;7jQeb`bGG-aL8saIQ9!P$kLhb*q-x^!+9L~sK5dyN=WzDG*iswgdc>k=2 z-5Ug~r2*RB-ctFmWNe^F!aAbcKJO?n2p}Pp^hLTCjAWxmJ^9-zY4_s8kjeMDj?mY| zLu-P-hy5&g?#Q~V`;|PbLnz?d*)UzD88*R)NE8c-cEGa|&5%mq*eUmi6+=CVC+)tj z8!Z*;9+XY3u*BEDGU^(@-BW+$W9T-Q_*vrM-YY4!yb%?mKjFOq%@8`OwTJ2{5%~1z z#Avn0?kZ#HvGM&TSzjHzW61tA^d%+X$;EFI*3vO)&@uqotP$0pe25K!C=~m#mQ*v6 zweu#*%7V9q9`dS(_=+L_hyt?as za5g+V13jz4J&uJH3?rM#!Hb1s_reQ@VD~^<&hALSdbA6F9M%bfC-vxC*<9YBDE<>q z9a#KVcW=jAJ;!TW4@H3Mq!_W@n(A+Tb<{%%fT)^vZ(*a=NsHZ}my-$bQtPxmnY~W) zMLt{?%CiFEn;3aVC~)X`1uKH&vI6Bgsmvd9rE$s>^+I8QwVev-r+$AItI0)Zf7ivO zu@NCwbq|y>;Jll)swK!V_+Dd$bN=-CxJ~pFaxt{?4Q-!Jp`Pc5g5?8+;J71W%87n|JNX-~>>$RLt#hY^%b1wR?$z$MA&GB!29V;4#tx z6?1^=efP}Ej&*L0cw2@%Bm3!9$p|3lzfK!m7jo~4%8B)FwEjT;1by0%+-SAYZlXh^ z9@+{$DbDhMF7h5AIKsWb-y;;F7kn}bU;_AEZyKTib*L?tSdMa6J%64Nfk9a$t4Ao4 zA$c4&tu?*ovJiiJU)Ec=U48PtlS?ah$29u$h(0kC1Ej|SLe)2MgvX`1-aw#yGV3u7 z;u{KfFJi6)>PZNvw+{+z?0!LB89#rAkou2ao?&G!4)?dz1)$txtP2{w6e2vK;LgYv zyb=^5hYrB+O&D}OqKR8ok(}4>4-Ga3Vr7#EwRw%XP$KWLp80WdUpbg;1wSkX1)#AE zV%3sdBB1P-sJy|qo9FFGJSzp=$Dk%5eOEu>=5j~k0?D!rofi5PE?H$n4u_0F8hu|> z{}}LG-P(&0gA=rSJPzR225WYo@V>`gAfOym5sOp#?Gp9b2V~2fH&Od5_n}LU=_!Rr z*jTt{Q$76!C&coIDNlC!LC)|p+rA*(BiH)9@QNAT-e4gXCWv0~0R#{>83GMuBFjR> zA?ki0tKA4`O81IFJQY}X%~>8jH-JnkZR1hB1Ol+0M`tA2=9AJ&V!>4i;8=zG|9^;~ z#*sW1z&1qbiN>B)it9uGLslbD0w2m#Z|^j?#P%6apG~QvQW!qclbKgO%Ti-Ss&Lke zB?XE;9<$NNmrF)+q59)2ObCiF|6tDS?(G%(-x5|EMD+OlGA&j+RazaNE^Kxq8F0sdHg99NVM%C~q($11S-i`?-!J0_WLh?JjrL& z$RW*{0ZewEIx!t13scYuzrVWF7M{I@Zz8%j+qbZ{P^ov=R36{@N0IkUr{6eXS6>!q zlPIWwP%^fm2IS3_odtz^V&vK~HVn*by?o4&{a2N>(f=@qwOjLNq^0VOB>Is;N7I{% z0Wx<-F*BO~CiqDya4X$yfQ@$O9ZhH_Uh_F(-?Mno%cox@WWDaQU@BhWJ8X7Gf!`rS zM=4mlaki1w)z-6r10od*o^OW6_t^BH=?|B0&qTdvWySuzm_LqP4L$TxqZlQ9F*0hd zq(f1KQUBc>HS7HirYQ7nPH8)-(Feb8FonuylN1C!6w!`f){~;XQLv`J7OSNBU$H&k z53jvWiQ&dLHe*jq_Xc=>^ZJ9re>1Q~FXD_TFDGi2FMA$J%0k6_VQ&at$d3fbZoWf!ISjLvQ=&uFy)40S(Z z@cM4FYR&hy9zudBhnrkngiOcS16cmCw0CFCRzsNmMx~_jI^Lpi*F!GqwfeU6w!6dN z&#N-D&HuW&rW7xjEg90BuYfg!vS_B=X zA0vT5V_4*wA_Y3>iEd(F*n=ri6XnB_%%YU1qiH6@FfL;@3Lk|GeViZpUdwvfYFT%D zZVj_BMU$?)s!1R3GhVsk3tk1qQSaZaYvF7L;6}y>^>rjaWe$elvugkux%?oTKH{tG`dcve9&h_bpc`u|1G{7O+j=L6Xvs0? zuyvBEm_$tVe}i%)pH?WYckKmrUof%{mNgBirMi8=Iq*<0W!HF8;}D}yi# zh`82=Pq|~`HSS_%6~7hQPPINUnwq}+t7+4Ue*=ph%RYa`Kka_hR^Fq_As;n-ga9}( z=cxS&`=>Y3+)fvM0}*`?u26n;dIWoIO+#;QP;0txt|>RD9gvzphYm)o@5V%eb%eKH zRJu@sK(lH8bU(P{DCz;{eM~#WIT=(5K}u>ujPr%3m|THfEaK7^^YMnM?3zcu-M7iN z=jj@Ur<007u|Ea9SEE!9v7)$z2?4K;A=DVph>?aPc>={9m}|Qc{@7q)M6g}gDg{^= zbr+hgyNr<87AR+zizfGHa57ej-O=Z&|7xw_qzn(dYOR3Vxcm8?jH(~ppK*3*ew1~H zvA`IvV!~)e8**x;A7Wu8XELxX)bzz|gP%=4`MR#5dM#J*d>%rb`>>2PeS2L5@Y}o! zK>058;0k}?hG-~_4V@{3aPK)783Z^oWP1EtJO*5023}#apH&Yah@yhq?{+zYmwDtx zTZ{~dbR=&d)DUo<;lwVi0yRMi#nzdnO2D5SocKG3d7KDy5~!;9B#X`IAB=GCeUgj) zHB``FCdT@kdVLPh-gJB1Z!|6r#U5;*MDzUM9)}bHh=BOy&ZPGrg6^47UGydd_-I-Y z{$CE^_h6yC!MwtiN$^sGo)H@i6~1iEfD8QD(ZtgU@B>hnsc17wVj+At(xSBImNO_QiSmBNS1_WtOXm1E%NE_mO3l-- zA+OSt7_*kplVD9Zf-WkyBoRL(g%0Z@t#|#(oZjANBC?ae^;jO)?kHCa35_1?j&GaC zE6DD4%_v-3G!y>V(#c7FaH&R!hJ7kbls^~tOPDy*&ACJf%XH7wYMXIdqw4L6W*TFE zGLB`(Z(?mIU~Wyv<4ynM_wfx4o2S1cJZcsUF{)W!Tl{!JGIO+6?-$~gQwnv6KgP6Z zJx-alUuvwwLfXxPTm~71N1StuZJ()lwvC$-z{xenZlV<<(uPXZ` znaRPLt}$9QrgKC%+I=!XiG)&!=AxN`;=27FWXoF3pDu3AEQAM^S2_-{;4=Fu0;xYT zMT>=QqTwVUB>}TEEdy1wzRWDMM!w;?%k;9eP%TvCDxBGkKYjy`MGr|>0<7&6Y zsmvv6P>AHi0VT)r_mpG5*1C7}s*W_+*_lPB5kh;K>Rcb4qS9*8Tu#aCGD#B0dp zl5oP0=*v_S-~ap-sYzq7oJj52IMmd18B;=9X4coLfg2EkwIeqa@_fMTaWG$rIw2KG zt8Pnw`+DAmB`#*P=HRj99-I{s=mqI<&&1jcx@!%5Fiyfh8xF4lG30nnM1ySZDfrF? zVSdQ}E!i?VeD=+Wyq(X`V#bEEoS;Dv zgWPppMu0qs7A`ro@^`MNpj4fs^VR}sh)w?LKNcA`49l6%l9K$lJyZ5?YM6+BG;;Z-P&mWPw))yS@;=~vRh)X|%Oxcs; zs1emGDXI;~s`N)WylY7|mXm1wTQ*iPE z=Y6KUF_qH|_xPqg>D`K~&2HSFJ<43ITBK}{7g37miyhzFs!*nfz#v7H zzjr@NsCcqDa5924w(t?*=QobLR-tC!kd_#H#5fIuVHQfW)&wh}4%z?>9H-cX5 zV}g(Qr_xh=jS8@AcDsYU+N2ZUudssT{>Vu5imfx?ps7~6kCno2bK*RPhuQ1!FZ9iW z$^0>4yPHWNH*=htnN!Q5_D@~fJ`o{%4gvXGUxOlfNrI^!{{r57i2Zzc4qIEW`)FqZ zJQoOHQzZhjMKnXn9A4Pb!+L4&XK`nFq-GE3R6DV#Cg3aD#KOaTx_J7LT_YMnzcq$? z{YcnqPG>jK64dq`ccM}L1N>02sDYntkWG+1q$?vAcTJV;-e*$gR*Fu@d7g*vHJ?D6$&iFlQ~Qat*+27PEFL~jnLo{ zMb07J2KfLZ6TNiXPyCq4$E6)=>UMhTiv;PKIp8S*_Db7pw3wwlWYk3i!t@;*E7w5N zQ?{G#1pa0tuKxPZCA6((*xh$xsF|Q&qjw0q6x5HYm)rpZL&Jg9kE#eb_yq-uOo~-p z)ESt6j`WDbqm22NTEk4UP{lE1W@taE8wPr^$dx%d-)QDLl*sfp$IdctXouStC{UA= zjqaP~AlPk1&AS{&3fl2tx%&ic!F%?4AY7%piITURD6?Oo2KpiICa}QQQI8*;-#*C? z1z$hWcPOR~w;;nu1sQKF)s7eK`}-c?T>oW1u*;nr4TpT8b+i=@KucpFmi1Z|l9|YbJON0<|@*AmkfVy(sAga@|sc^PwBP4A_$w>Vz9TeyNE@9K;G zwKQ6dkdtdX{Gc8@WGeAPiG~ENUh{C~B+IIDpsyYfw28Gj9lND~$t99zZpQfgX;DjG z+^1px=BQnyl-fxV!DnWWM3_T7hJt$KeY@XRh`;#GiUBO0@^4^aM`*J61mduE7jOOq z+xj?#B2SuMd8Yj_6TgI_-gEnk#y#u^CIgEYaYKT_ewObyaQ9pjUnnMXF@$FsTGux( zz`w)Sxy5APb4{Gg-3!|&QY@r}u&7<_KFdR*lg`c(1dFc>F85m> zl_@ABlFe$@SWW+(N^9aH$*U#d@AT(OzzuLV#I5#}kW(?;yg0F+!7s^XkqD*Gf(ZFV z%=Fx=+fIJRP&loSWwtr=K2i9MHB#X&k0jzd(UAk16x@)*<5aW&?*?5|pCwX_Qj?N^ zC}m&2ck36=^XNFJ(A;M9of~)~7Xib9_tC+h`@;(ZpTe^_{-7ugDJ7K7_dhFA3^q~#z#E+Es1xz>w61{88a_=AI zKYV7{%So-G2(=FeZp;xV&Phl*Jz9lpj;`NAHDYb@CEPGX@`sgyPUIWOlb-6xM~hmX z<`v#7N>1C@ug8eDg`m1`P!L9qXO$rDfO~6diUXT?@=yd47Z%)Ah)Qq*vc<)@w2-Dw z8`PtlGC6ejY6A=DJVNq5M8a5cIq6q3~E%*Kez+jPKu_39N)`06U_+ZlcAr^opSre z;Na;ZQ|1!woiF$%e+=C}(OCz)+!3er%%AZ3`fc4F`SszV0S={|&t^03_ zPFcxxVA~afQC%FX&%l(3!k)C8%_+?7xq?39|Q0vqtHp`Ti`=M00#vjGG?Qxi>!aX zdQcT!>u+UI9PHyW9xpqqZ z{LNZjqxAd9`Vt{5dvzbOFPayqvNh6;>v|>Kw$aia3bm&mD&530NvT&$HpdT$6nBSz zo5AltX53RzVduczOXIWD(XM1an!9uR?SuS-8W*-xRn4oxOBM`u=Eth}AjseU*+wx2 zR-jjtvqF-2a1wjR1x~n&j=F~N3{`z=myEGjngM81P%OUBZS!jfdP&MwC>;%U@RyE} z!%fZ;T?&o4NZ{7bMiLh~oyKMSjYKNMW+9O;JA(7N2#COBj;~qxL4j3XW;!NTjFT5! zqa2+gigQ18D@=)zqoiV0`NxcmzSi;KNU{qjo4c4G(jaEAt(kZ^z-{mYIY~wsWJxF} zXmQ^gE%T8@Qt(}uQ?%U{ArjU|O==??lNi)!qZ0g6;o<2#Vm*J^ddst%f9P%uP0n+;p*`vz#l zt{xq023{jg?FCLQj(UPq78Aqy&?;VGQM1FxBg?=!$=?}gn97?oP}Gkbj;cnv;7fN{CF2mSgfd0mCdkpi)&43% zFed?LItb1CDCtlpyOs`_syx;rL#vcBiLVu$}y_Ty2xt_0!)k1fL9hr<*LX@ZLZ2^K!u! ziXUO7RWUwrKC-nKys zisnEU@4dKngOkwFuE7 zOp11?R8>A<*Pd6+dtUO|80&VN z?IJu()rv0|<80y#KwC0W`7HTKKoXvH8LHPu7(RnVdY>ge313Sb7V z7gVXD^$yuLS0umWtG%(uD0@!+f${Yn+-^<5g#?!wLnf6kxYLkw)P3IrR9(B>;pLc> zRbiZbfhucB-+uY(cDTdY`T++ujF^hb*o6hH5Bk8PsX4LVIW^oQn@KuBi`aGXO7S{J z)$@Dh1jPNDKylE`n?U2&<`oSyXS#JU3OwTHekG@O?B0Hr55n`3IHQdh5y6OqG~{P1 zJQ~IVh8tq9v$kD#x8{|$NI)G6Pj7go^hDr0i1YsK3Zqglv}n;`u3GcskzlJi%p0$q zui`2GtLD0@N&@O~E71~|Gg6eU9v2;m{?o_PN$2NC8F2?XtX4T02}heRFYOXO2G=;d zvv~z?Cl@i8`sa&@$<(ZF)!gk`6KNfMS}QFm@GynMH<{8dn<8JI1w4IfrOV8cJMSnf z6X471A^z84+e zqz2*Qsq(3_l)oD24{|EPOcl0>atyTB$jDj_Q?qu>kqpJK1X@%n(_d111HU6u<|~E2 zF&`eGt0UjcM1Hi2epE;{BcE7xe~mXaC8f6rSQpjgv8U_l`lRK^=5(|x!c=A3Y~!Y` zUp8m;wRWMwKEkMP)O9a`y|+Ca8?(hE%b`lT4cgB;Ir$>;Q5+4fG4>eCo==RvP+SWR#T`9^b7(C|wUelE?^>1%<#r45zQFULBiO=Gw%gY)rbnpRBfU|?! z+XmmzhIp7r$}=urXl^}c(bl$jr~m%apda0H89&HA>qidjDb&!!_!nwlP!zeTsQ~;2 zdyrG48U64@7L0z=8&PG-_FW8qvA#-ecVHhFZr zYT~k<{HMH#__gSr@3=8-18T~ad}SP^qk(R*Cd;f|&M%N)%zUk*Gf*t|xSLWp8D_#{xbztd0^9vQl4pWCYKaK2i_RZy@cMhJ0Q>cvs0<@v`=#v1D%pe5wS z+qtCX5qJSFkYUchC{b9e8R*8Ot9 z14n#;khBdjf(_egdP81H5SE-Y^H7%(4k4B26igOh)L^>#Bw8TTvbuAwp6evO_qzr@ z-JDJyzMz(!-7WzhEX9vG#`$GN!8(DGK9^)O%XLdJj(-1I@n0UCMb($yuGr;D8oQXA z^0A1tZY_wtKsYP@DoAIf>?64d_t2(pIvEu6^*b75-}JBkX5!5u;+d{J$Vu<@+~58H zVa3yD)LUq7lMI9ho3BjGNQ<7U@6K?OS+W|;u(m-REZq(XrV$MCLj%nqKUkDhDf#L) z39ln_E4t#H*DtGzO%+OH2f6sVpJRCL-zIBqo_6MYgmHL7X!!W-HAR_2pBKx?lWoqQ zV&uy|>G&ECP79J~QSBqoOb|h5J^wl@l-n=a5yGOd)GGe%Lp%l8>BJ%FOG_N$n1S)v znga{VF!Rp1`XKC}qIbcj5$~|#F8?lnY&<~Ka;QmG8coD;n0+hU`v*jz&`?|#H zF#TU*O#}g%d^Q#x1hTZ?aZox4iKB1r7B8FMJ%u7+Qf2Kfqm4eS3~&8RQOg$#NNq7m z+ZpEhcY~a6Eb6YOdwH1DV)dRinKmsxSw76`1ZwVbK#efCeXgD?C6X=8=~^1LiF6PHi~yw6MVgYyuyZ7sCxfA+Ecfx6xD zO(%p&SiiQmT}WUgsB)Lr(Se)Wb3LhxlE1%oZ(I;~8(<0?uS#&)Z-Jz0X=Zgh$7uDw z2=+cWz9z1{c59XM{wuE>$TCG4Gy7&G3KeM^4GEfz`6$nr&s837s+hoV@PpOnhO)vl zPWmbsZZ4daugj?1^@m!KSenAbG4$y~q33I4p5D=gYS`&nnTqjThsE*ixB zqnkNfV+c^JwQMsVj^dU%^!a@R{U)McC8Tf3cDCHZbMKO~Lp_kFAfGmUVuMOloSH9; zG#XTt&AMm@iGfLYZPJuf+1Q!k@}SxE#~QCME%c)LTYXaLpYa5e8`$T)bE^0(tTk=W zy+x3_MSq!u4QqImEAbL+J!cL6bom^*#i6e6Iw3(Y%o=?8bb*9Wo_(0#(sV%mr7^a$ zqP%i9UQadEe%>22-lYvO+$8M*0E5E5y2 zh=6`O(f6Bul4c^5)G)Ikx`Lt8pAZ}4EW+fKvac*xr#nKqBL0D@eWMxqLX(#^QH#K+ zOWl0`(aGooQL279VxU#(Z(;<5LG}ZzmH79)Ds(yWxC#u;c4QOWYU%{ie%Bu~@x!cW zB`oX^N8PQ|nXU!(vEelqRW;m7-ln+i`J6A>DI}*!)UN?Oo`kH)X1?4}#Y`;Kyiwt9 zn`&Yc5A=(UH5}yx`vgRM1Gb%|)bj1uNI~pDMe=6Q>FXcyF=eCe&UIrgWD}V$l*xyK z4KEI7g|t2^jJBLEOr4O2NG ziA~esujHqdUs27#+r$J$*M;$q&mjlqUObpiL)E z(0iTzrnr2-O}EBT7`k6^Ez2UG1k~4m{i$o;{;MJZ=P%im5o2`v7;dDD0Do4o>LHAI z@w2B7a8s;yH%gX#hv{+yhh{0J{h1`kLq?l+{=R{CaqJ+yNmjfCAna|8`2+oOHkyS?1Hvc!|iE5j-fC- z0mZq^lbc}tjhTsQQx83|3UJNBXsr?9Cq<8*yBWwnYm;J#drAK!Mr=1Lka(y*(=^F#2`jVfA+m< zVeSezK%SROf+c4rh0szfmBP8+O;HtCm;fjH*mbl&UG%<870jIeXd`%1_(Le9mptPu zc%dFVE#jJ7rZRn=Ml_wwHot#^f!o0Tt%M{Pj>>kJbj|<7?{^rkOz)d^Q`jGwvX&!s zi$7|~7t~s71|ww?iU}XuL8|7)6+?xcFmWn!-nK|O1*WO1cvQi<X-=89sM883#*N z3_~(t2ss^w`ka^LUN+)%@pV?;08v=UA_#)zASmv#RH_;6SQ5g=U80FkJJ!8%^(?zu zq$}+yd-q`MQOr_ymI#H`6Yqvr>AL#$-F*tn5SvFewSnX+lCY5Q5uD1tDf7Vp@?cAKw;Go#V$s_s{J8OsKxdlbi zMdJGfWo9WvE`#2;we9xte2yfrvCx!wVD^1YC zCfcISzS7u1HkN`A)2&@~P(#gWSaJ-kXYG{&w1Xxi;F|7+mjDuVvI2(d9sy_OpY*%Y z;0ZG>@wG0|y}Rv=u;V}1%@s9w4S=AO3JO)eM>9Y!l##Jgy#3CRKK2Ur9F|&qSed5W zFVz8JV*dEae*?I^PX#^0D+5fUm@2sMP!2HAPp50XerKLJyLq_vSle01Lt=sKPUU%l z{i#Ns=@>!`3R;HE{a*|NLbTSpe*fKOuaLr5(%8R#WT{JSck_wwctTUZMCzQRkKYpR z(T%@xIFf^BO{YnZ>IAXvUR7;e1flcWC-`80p|OHi z6yJ-7&%PU3^0*Cv498t-4|Fr>qJ`FW_p-i&l0lXlbpdDoIOFA&`jub;*(LNZ6O`q{ zx9i8UfF>VTz=r1feDsG;-Sd0@c8&nr;Sz20Bixj^l|b?c|FRhC%pciG?G_w(L{vV)2IveSDWHejbeo4ylBe666a-cr16uPy|8zX4w^qTQW& z`dT~LbnYEz6yOZX()iVijy%doL1`qy6cJwZbcN07RSI*ixnpZMCd{6LvCdPyB4^%) z>K%AB3`Wd1P?4dOGQGVde1woeJ5bO+PISRi`8ueKrh0;qq! zmZ~ad?_^5IbLASoS|uqV5`PKPX67wdN4f44Id&lPnLz;Jiv;4L(%A}%>KmJID;NFU zgsg#7jJ@Jc5B&t0?_kvne9N@sWOu6TKsGdI~cz1K(6e&Q!F>MeSW%q*%60+|Mx!Qz=@wQ?>;G(G+vz7G++N z;_pXBH$Ido5mC6Pn+g~uqfPh05+<|MCsTo1Yx$OL&S|Uv{5qLE*vZTjiq>ogFW=7% zX{HQ*<0mUn)>Qo==Iw$iBD%e~^|&hbCm+uKPM6I3OG$PanUb?dEjSBrtIM@Uyyx%k zN|ah-1@#$}QI)B!-LH43;j>Q9%OguR)5S`Mv*MtI8h>pGBRTSX7o@f+&Ba#5=rz#i z#&~WHbnYsbgXRG}8}ZT04!YADYwkFuPkIvkHGo%93vogo+`mBgUaEmuwV-Ts8nZx* zty{+LopN1TLZD|xH$r2T@%iA6sFZDNhIn)?p8WMVg$b5V83!3!`=8c^%Lzo7R#2KM zj(E5#X&pOSSKHggQ3GsJ*Y|0z&8CoG_wh^z5*oN=itHQzjk(vQW2qhD7fmtsrXBWK zTrB^4=K3lX&n7A|k_It9Wz!@fiFVqQi*H*qlw4FdXy*?y7pg{O`)R31eA5UKc`fI@ zLvR!+dS6_V;omEsOess%dM$Mhf;expP8kW~nDgTm&5|Zg$aubVoBx>1gFx+mKxeVz zw{D5zsb~`O)|VPMrYNUr$R(=mjqU`|D{YD6E(zHkLz})|{6^(%7Xb1hf2t7FW&c9W zrEGMK-47<-@cf}wu&35o*Wdu(*UGNP6RVq~$vylM#wlwN-oa&9^5^&p+Lj?8NU?W3 zYuq>vxKiLzrlR`5hrd@-)Sc)mF--(&v|e*xk~4l7afGIa_gs=N2>f38S(6PhOy zkE!wa!EpY>!>wf8F=O&^ZF94NMmG-*>VRdO14HcIvhG}yd*@mNJqzFn`YoG|h} zEg~XqVVBysWE@jpYyrXmjJp*HV#&^MW6 zm>j8EaZ|5IwoF9L&Mj|bm0W>9C+z2*3uz)a1#3to^F}{WOaK}{SKXo@2vW1H3u6!U zD{Q3?QbOqyQpj`GJ1j9>4)?K#UC@*uhL`4N^rPuo@#aRYOqn;daaO?(zuu#aep@jt zpRsnU_pv7wVy(Qvw2V)1ffc;aHBd8HaKe(D@7H`Bv)F`%hOdaqyq4Yj8oHd~!B{Zf4u%gi`P*kc_bdg~T>({cw8eA^r{%nM6SnbCeVTVFpSMt9l0tbj%DyvV;v~K2?K5J3;E1i`bW{6x zn)LuluslR%svlPFW8)QT7VqO~j;Z*QWKz0aqpFklZ(+>5{H28l%&xZ|(B^V;<-e8x z$keO6`VB$ry1vF|`<}Z?0Qt2~5dYcZM$`fn?sPmU5o_mjk>!hsBk4J%MJ$ppjU_F> zpGJ@Wx5Jlf`uHmX_7I&YOa@scE!_7vQ=%ilI^Ud2Nv+gh?Z_T&9@-^-KX{~mQA~;@ zAXqzh^lzq;2?SQm{ypTB8dD}~)%x_j%OW$ zJ>;MG`-GX&XtLI2T8o_Cl4Mfl*x_F=ti+$1r6S|N>H%ryocH$d!2D5%&c!hR$dytd!F|50vjx`3C{?6r3-5gR3e?lYp zq_0z~#x$dsW2&kneSvg)b8)*G`~g(;eiYd_WJ_~~qy=7vb2M)m*YNdw^2YaI&~sG9Hy*A`0bP#^ zhH_3;~H%>{-`Bn-OPf2%SL32CKw_*teoc*U(A z`guPHRJ#uzsX;-<%bN>ZS#hoI(sv;&bk%S&-LcE%sw_Mo({sr4mA4Y;XSPUyI{oFf zvj$zmh3qOV>U((;G3dz19jOUyqC)aO+|3i_7)A650T1uwnHgdUHkP0FpQ*)q9Kxx* zlNQE_zTM+~Ml8XBskhoXwk}%^a8+xA92maYQrw$m-%pBcai?=BY4B$}Pih2ySJ_@K zT9Bk_HN?UB7ereNud5^!k8+Jgqy0hHayBuhV(aCYxH&>=*4ne0 z)-P%LK~`cgKv{jIa;ASJ+@-9m@Gg@2JshukT2onK2dewO!c zLD%JuTCO%(P`JJZ*f9Qv>WIM#L?mg%!dzm|7$UUC+uFU@rZ2LL6>Xy@;sK+qR)<7H z4Jdg~inwXB=}nnKv%g080T%eI>E?DU^8DL-LUq%BD(9UZ^*ziWs)$M&R&I~NZk)1$ zBs_}y; zT=>lPJvZGtzaQXVo`s<>{foKklhPG(!8o3Yaf4R$nlyCLe@{4I^tYOnPMe)=;#M$suEpJ0j6{{<FpEgrA%|fh#@c{I}i}3u|@fGs%QULmVY6Jm{of92_G11=TCoMGa0${_b4!!;K~H zE6AZwCfQu6aK=#=4?WN(QO1Q+?Lm6W( zo9FCXSy zsui=z>q^aB9)#WVml0Ov^t}9zlkT&yt3$99OJB|zTT0~Pn7OH3{K+5AHXD8!tc}Qo zA3k^JR&!1|!d%W`b0u?svk@#ZDyyp(tl9)opB|YwUhT@wd-r4_NmjxU&fS@j|SeifKqEN=Fkb&<0W(^ zTmDiX$^r@Ry3MaXAA_)Au@5%FjwEhNl~~nEH=T(^KAEzQ{ir?Sfr?DAz|okH5}f&Ve2mTaS*rLI*_o?1x4=$bkR%!rpV2%9DOVDrNQ z*%f}3{uH^gkN%n+b`eNgdySzuD`U+-0+0>A{IlTTf`2ao%XxPnd*Xrjs>+S&MikmJ z{PMsFD_d`O;|o%oC>mX?f6^zP`)N2?BD2{HkMl`iZ+C)?(%hS6DzAg-E<-5Q_RjNA zJ>r|J?EU5y3I}Th5@eP5guQ&H4WbRZGaC!rQRa&YYJhvPD(7(6x00a}I9QrhrtZjn zy?R zXNg-7bIs2-X0i1>|LD%~U`aXyrOoYxC-({j0*wV%It_~rnP>I7_a50_J`Ff063mkc z))iYjOx_zA(NvIn)5hczORB^r5|eH|S2)wlY<=(O7`e$|zCP68TOo@6kE3f2tE}td z(}c;kZQD(@ZQHgr={D75O*Pqe&1BoQZTFq``}00ePu=#}XYI9q+NP^8X3{RU-RkxQ zl(>=cZbFZUR;wr#GS5a4Aw5E7Zkpi(5TxrT2Z{3cxrlLzm3&Y8z*$kJ!glDxD`dD?0t_srJ|yQjIB zuyT%F>o?IP2vq9{d?J!9&C&(mF~)gke6C-qQcvF7rOrCpf(jdXYR5)*?S$$6-#S>s z?j`)BH3VRp=LyKoVayDX=ZTB}L4|6uq;=B^UAWnuRl}1It_h}b zH329)GE+t9pF;sdqYd*8Xv1D(tyC|UCl>D>7x-M)QzVg=F~%&2TCj0utaFit9^|C7 z`|N6p9nrg=2?>xv;;jq+E*@*z8LAchRmr6v3~h1c)O(upVPiaLUkwh zeqVy|hFueLW&qT_dYHX(5{ALYh5)<#_LN$L*xY0xo^jPW{M22f9-5gwNSLF0y6;)k zHrT5uV#igo=$Q?zZKI+O2VWC@M$?bZof4b{ z;FWJ~m_b55hKyX)5J^v8y{h5sB45#D3FQF8=Yz@;otvz;kL{!WY>oCm76fwpB%5X6 z(ITFi=Cg3S5Qmoy&1L#y9+Fxmkk?%dvb;c#mWOk+EoEbZrX?RBsi8#CM;Tm}xi`IS zb6#WQS)GYgO`R18q+M^MQszxEpZB5qWim&(7F)b5LJH^U;nq1dii4L+h|6&)w6|BQ z*Tt2|cM`q~A{AlFM0y{({NM;gra%^lkvPV}>Rf8suGRVYnWy6dGde$%l6IS5j1C}h zM}Ub-ThBh<78Xkp2@T=Z>$y_=q!R4gK)%~6<+%n{@#2OP#QJ*`QcZk*1R7&xLlr8F zwckalGXSxyR&QE*lPGpK$a&rqzV9URP0loNo*b_uY7d(FVK5S;RoFQZ2dD`&JWAJ< z#nQ{h?vq0FqWEk>*bv9g+mpgP?uC)*ss2$m2Kx3G^A^|czcG_zfRlF^OP9WqL))Mf z73MTHo*a-GUO&eau&+|a(5bhr3mz)QsZ=&P%Y_Elg_z#e^14S;0PUvWsO%)+?^(9L zD1OJ`;Ck%@2M5{2GR(2K(Lli%ECG7M3xwx9XY9pSh)|TT%g%swnXCW@kx0t**&?S_ z?^mNrq{HN1X_6?sC8^)zxwuTDU>SXa0z~P&?_IkqdpHxt+NL zlDcC++XSQZ0I3Yl;`6NivX4;#!rMSIczIN1FnH~rjNyq)qM69S&Qm&`u|on(YHNOu z>1dHEa&i6M@9PvAaPmLR-U9j|4|QOGiQuHkNv?Oj_+l`12o;-0ikM5DJ#%+#m<4!g zj2%iR${ok2=?{)8HwxN)hzbnuy5RXtoD34-2M3z;DRysGX&Ao^ntEl>`s%ZIKNM>j zloQEPi3(L7^U^&-X%ru?NDllx=hkb!>~w3~K_Z3RrEVLT78R}7%Vej+@Ok!r35Trk zASmA~m_7ke#@d#Z-y0`+L#UF77DEXASCFDhGGBBT63_{xr>&Y0+OipoLGY>-53Sx@ zlY3IX$i77~PapB}CNjlVSmD_VnUJB}Iu~3F|M*TkO6$XZu0e+=?|kzFkz^_jOq^qT zR`BBLHTIckY&aWT9b=uZkX-BZ#M!XUMx?{{tB^L&7%#wZrT`ACeQq`}yE6cE3D=pL zc07%NNz|d(ty)yhZEtj{`;-Hw_q9HN_i}YiEzaMIE4eC`geeAGkTUgIj!NTL>sIRR zUCT?`AAuN8NcS&mIn}*69B#EUy&m`)HwZi+=QOd8el6Xs&hs(UMfFKj2gGc#f{p!g9r#IlcQA(WAY;Mu^UMf>k-i%HKOfJ z*vql!`Omd7d~Yd06R}QoIF?GI`RG_InT!P0)6{I#mA?m7AY4?T55G7X8W3Z`IaxM| zl+Pai^-7#H#4lK8`OiR<<>>5K8(vi5^s$Fsw14$*PYTplI4a5E4!2*PjFH-~5XvFS zzl_3w@vL5bbtd`E8riWfC_itIEtBOC4NwSjHe1lifx>V`#F*tWJsFu?@7wrl=SwQ` z#S@RB;E&CIO4KWMFG^}r0s#eqR)A8RJx>m_D=Eq2NFb?$C_1${; z6H2X>gpl*|Rs;+($jQXBHfwDk<&hLovH_yhW~)+z9vdX5SVGY9;6*#bRbp9v(eYZB zu91(=4pC^EMSZ6rSa5IzcYHk=mg(1zbOxb?S<>CpMNq}v5 z+%4^t3!M6Ng;ywE+5J?wPq6q`0IE3PM@^le`$;gEI>sW9Y-~n7KzGS#%!kOPO2e+c zy_$K)o$2Pt?CTpr9KR(Hrc{Ic{(`#tH-l#)QRn|!$N z4qL0Qi8zCEH1pjZl?ZCAc#=w-&DdyldLb+ z<4wt3tjrhT|FY_5s29X5)6Kw*3EiGyjJV0KF8tX9U3_ZB=LsKaBz_W8(Tg#z5 zg$x3;ctKIlYr`C!gDU|?b!9nlO%XXQvK@Er>6;ALW~?;UptPkeC^omQ^6-z{Vl7BO zn4s2)ZKL$^T=i-K5lUB<)6FRMpvB?r@_ zG3=oz8|`ghnNm?>JLu&iB6yDMlz%a?H4RtIUmkt*E zl2j@O!;^XeZJ20BAY0FRyD)m-5~N4KhW-7q=c9eOKdRW5x_p4$hKMM-8e{`H+gN%! zy>?wv+!?QzG3s!aNUlxY-|Azt`mM4|Lh+_JPj3YPXdER5y&9}BD7N5+u5al=J_7XD zR!vZTx0Tw_w&GC9>iDifOdQb}AmU+E@ZP)cHs{;8uzwja^o!9n)KfE8a8T=!3bEcmxMMu;qmhNu(fh%2ebj#L^d^k1@AFh(* zQ$Fy!DSF+0_VL^CLSjXQT8j(W*pXBg0MkFM#LVu=5?nCN1FhKAdUFalYxdS#6n?8+ z+9Tt)k|$B>VCv2{`p_9zjYSI5w_qCSbrH#}$(G~ugj#mCS?i6ijKL;?uB$PK-B#?t zyBmGnWZL(hj#a-E>)#L}RoN#{ZUjU|$J(05T?|4@l7_NwdhIKi_Sa7V zcGWqhQ_VMmmrgK1)J)bZ{dF6+Re zs^*{H>c8=LyM>v_9RkGrvrFo8A+2La^WR}IQNR6Lwhm8*u{XOf9N5AL14md`dV(mX zTj>h9W=3#K2WP#h_&q}G(&Xto0E2e3kNB(-V+ouZd*3tWMKTMMX)SuQ<4l@P9dJr6 zBw@s+-UAY^kqdR=gABKKhK*TEi5)w;`?A~1-A28u;d}|pHzg)w$)p`llXs!zX4$y# zZBto1PmAdmhCu=$t}ufItV-z3oaEW?u4hKk!wJ~?I+2cnmyG=?aJgMVCuyCQu)Eri zC@8TZBy?!)m`QNP;n?jT`as!0zMHH+r%$ZRTXt;#k8?LR4CZx52GbFwwAw zNgkCskG7XC()7bZ?cLVxOxdM5kPqHZNBIMtU%+BA<$6!aF8Fc zS9ic<(C$8-u4PsOTfpnO)H#D7)TC9M_2AGIi)yH-N3Rv-O77>q&rc4f4ogR4qIa`k zUE1=FGs_fQh+6b>jU$3+93D#1?N z-?{&&I^z7t@1x@w1iTB%#y~>xsVpV#U{d5!Ke=Q05=-L>srr+oKaKRozHFBIITx@+`2s(eG+ZRWf#e9_@Sj# zaRI<1u?otY09cn6W3-~?GcP`C$;E_vIyQ(kCC0_Et7pzDqqPt=LbA#lsSU3;_-)y_ zK`KOx{W~ooIW7!yyV7>0Y>XP5_)EBVTlpi7nntZJ0WxA@Sv!r*GJ&XZ$M2xA}*m<|+r>BV{Wf^_CzE>#SKFAJrIs$u zw(No4jpV44YC(>L8$DWqLB65hcZ5N&&lOn1*B%xS0m1gV23)y7)O=~XUY`U}fwJ3m zQOPg#{X7UIIJQ54$D6p zHs+$4qc(1`UFrnsW}LXQ2WD+yq7Ic|xlSmcO0^`rb#{dp$>3+n0b7I)7$nv31V##Z zE$Ty-t6C{?r`i7{gg!|kA}bVev!8=v+uiKL=@wJ1lVJhI;<#$Uggttr)3xCHX+v|} z4#T^UXH7!HD179hA$quWZK#<+c4!oHJ^FKK0{O1c7rr@|XAQMkeh2gbH-43{uuE#D{jhKY%?{ zP^@d?>@#VOTP`zsY$MDLiCU(f*4IeDNai3n2+-ewo1FYl;IPrwCShsh>R8*qW|Hk? z7G8P{5m_|L?->xAp!X}&6SiWX%?+1K>l|32v&3WeQLXHV!@q4Ti*a=$mzg}IKgl5( zuw8Y_RC)owk%<|#OzqmimRX`_^?oUbj~+Ki4?uz)ap7r=!zPk%PsXC*^MncU346Hx zD4vve@uM8|UDWV?yg}`piRP=N6^dUjvp0MH6PGpUb6gSvc)`;+C!i?mit{>stbz29 zcuOu^SO05v(N=bO#QMu1MTV$v%%G;o*iLa^C?9|m-PaYCKZ zU)0n|wiaQ+{lv%uCbIF(UDyG%YiDuYM@JGGDnhi{apnTIVFg_094xy^c(aDZ?w?Iw zZc!W! z%<`HRy*vXvAP2?EuAE{K%W4sT!!&Ju6@OjEFQlx236&cArNf{e13)YiI3Tp{NnWM6 zV4UN2=Z>@H0XT)u7pHHA7FmFWG|=K#R4M*s7J+06#JEPhNNL=(!_4U9w0`I1g4)so z2)$`3QZgMD}#uK+}sJjmkF;{+GPQY zI)9)8y8JBQm$d`kjM9|8lO=&}v$+n1xq-$O z_=Ng^0`m$T`DT{H;x10TY9S~;T za$D~Y2CsY2d1~voA1;cYgR|{Y+&Qgn++<^r-#1{Raa1`$Y8!xw9=^zte3-)Pi|3grjC}v zvWkFj8o3Z4@;60o+&v(Y@|uD*i<@`sNh-@=bMGC`8^~uUuw@1CGE7Z8w>E*Fe^bZu zBvc_(wH5FQ_V2Fo;YJZO;1F^I*%TT#{++PvN&JTbH#PC~d`)Fn@W9hC7nfMXII;Jn zO?9$EU%#wlEnNE$7hn-1Pd7U-0+~j#E;Wr8+R}|NYT%?f3{89ByE)DzUyaBJ*#sWt zfUUQ^KS2F94@3_1`Sth6I7RamKWzjR`iTbpbgqpdOL)wv!YU z>J1vqs};MkU*BYEZf?=^iRo%cm+|y@MnfA^rAMyDDw{Dp+$hwybd~k3fpvZ=iwN!U zMVd6qx{F@BdA&A>f=g7#QCN-g2n=cF_9MwzOs|(S^nt&7D{+Dry1gY8CRmutz0PMF z+>ZB9doc_-oy`4DQX$}`%D^GM(up5aj(~|tH&-SKuVboJNgJ{FWZTqabv|fs>+3#Y z^Vh!grceThK;HG>iMg!I>2?EG)1kefd~lZJt6*GzGE`zk+pKW`O@0(MK>0BX;_jYQ zl5$;Wa`WR1*5G@Z>2{wZir**dt&Wu-B#Anck!P%43t%r14+Gwu;O)?(>0h$O$cijH z3Hy5qBq3nQe6HpWn+#JWa{%mxg=Op+QHc96(CiIv-ISYm`_R%&XM>> zFNzHt8{Sf6PZJhOYjcef2)M!~Ryx+TrgFBcAdj z%#D;JTTai?ggdsVEiNtPyydP+AW38OFZ(wLKY+E2zZK{$!iqAv|F(4SWf0%a>cL$S zN_%@l1rFf5&W2e4u(QbA7|F+N6(Lo$dh;JAWg45jO&sB&0_Z>Ssm|%t1!5Xul+)Sw z43WaoGn3>-zhnjfJ+Ml9ciaoC(Ez!oCM?&5B!g^M+J4pI!5`vpdTm_;e2X_1TVC2b zTV5e5m9mxQ#I}Ou;y{eq&Dk=`*MMZrO>MK*DKN0~U%Ef%PFvWZo2Q-5-voy*f)upp z^#l>ciyXCpz6dz~!;p`*sR1-ofnYpA8cJKQ^mZiE_E(HLR2-{>H)OrGc)TUF!V|xY zKGUCK8;8Yca{oVFQ=L>AoUq;yiB2^u2o)O14#l!vOJ;7=Jsk3dmN@Wb-eVD`KcvbI zdW%8 z`5Ti~aXpJWO+=npY@I$k{jyZnC7Fn)xw^JIB9!5l0Q z4spR=<1d_%k;}DVSg3XEbnpb7SmAVR0Va+r7f0pwa0cy9HrOMR9bQN~KcZ2of78%} zr=S;qbM-?fGBR3=i(~Dsi78=!D31hSv4NDcA-vR-V_T48qG_Pk}kAhAxt{AwBq+sh`>LH&Yh z1Sd(|H0^ra>7$>rcp?{DC`I1W0EdD;9%+nFBM+`w=zCw8IG9*qbMXUQI)CT3zD{Fz z$StvdpEg?|Rk(lu{U^G+XuE6~sKSOiBcjaq=}qu!KsK6W1h>E4FO|aZB52A8vL`P=JD{uMQHf43sj|idbSwW*b1RJ%9=8nY!}pw4UGH zCGBuR(P>{JVR1vBWKS~OX;Pri0shTBV7mlt?g7p37}Kw# z1zYTSj+cH4V0zSO2btmywN2W$T^$sUMu&B{YHSz5=V1TtM0)1D5(;{llyKod`9FW`^dzTJJpEJA22Rb*EMd1Cn^d=3Qnf%b zegdu{RO}p5ZkHcYyuGTH1IPCa{|#5kBEyA$5yGO#{pDi&(sio}Y*7`n@lB~Q_RdFT z*IMgkniDMnN@d~g$(1+i2hnPS&twi7y2wYrnq1TrmMlerVY}ymyznKpypp z_(ZnN-EDWj8aQpEu9~e8X;Rv+#W)bB)W<+`AE`$rx`dQKQdMa<<6`{?oS0w-7-RwM4?JBs09AANWE0K<$FuD1NLh5g z_e7~78TK6t;tO>68sgpIWV~{v=kXmpy7qvJ5p&Ht;t{BLnGak;)}MD>d;)*;dLFCD z>(M6|$bWp)iD{TK(~BX z0XP0Csv0%`LLPy4yT)V-W}OV1=8Tv@J=lwC7rx> zAEfgCa`hxM%w~p(&q2b?>#kq|MsIccFd_92)n$Pn`5ONo#$0s@@t z=2vDU{7<+|SEx=~?gy^3fX7pf>c{88d7Y!@7#fpn=yNB04rJ#;{!5iR29nnL#&!fC zk0^k2@cdQWz|SHgPcPAcBa~3yn6vys9A)8wDV)5O#$!#UZ3UnWzc zec*RTi1H{|*e-9L&ll}Svf~`rvTsUXNiN1CnB_CI*!%DDV)O ztL5ofPdP4dH8d?>jiE4&UwE0P0i-$WdE@;)ZJvrvoZ$o!L zs+wyAcJN=5y;-WjaH85KgErC|)D>S3D<;J_)q!Pqt08}23yoGiS3qvB;=A5$%;$^Y zdt~$H>E|Gx$dBBzIo@uw<%Q$zyfhW9=-(1ML+bvIn7G4uJAwd?igCq7S5eh(&CWN5 zKUCAC(kFGWR{Fr-)$VS*!bFJ28`&ij+2VIs(>VVzwk_5P?h*lV^*Np)tqh@=A6Q7KXL2Ik*7+ z==baJD+gVR?aqZa!H4H1yiR>#hJ4hmMNZaa`muogVc?gDD_D7$D=HXcL;N^4GE`sxKG zj%=0E@!vYX1p-3@oTvAfpnyg7&d>}WQ#-CY(*s_H{dbMKeO z(0|Lv8-xOM8a9hKa|=iPY-{NZF4t%5!*U@3_RtI&9^mg2An(bwUKS+GS#N2pisVR=yt-%92p?|RxX1~Llxf26f(e~$oYl8?!i1Ggwp4yHvadEq{i;`9uRnuWq|CHi>Xwp7hB`~;L zp@StRfdL5CIH7s=XH6t|OT*XV&;9!Bv&ZC$Ym%Fr&)Y$;vp~HXNBBY@+B@(w^nr*b zioBS-Z?8_Pv-p^9!^8 z1q=?@EFNQEDHqUOj6TU}Zoe=D5aYWz=y-UqOI@pHH;Z z(BP`3hPIY{$RFZwq||xXXa&-M{5dfpk9zZE1HV4Ty~1I&e!3ibR78U#j6CmY?SZWy z3!snN6LJ-h@X`9Q$hrN#7}`JxaELJHn3=Hl4wLbSfW@@~^UtJ))g!%`bkCtG=YSG- z(RK!H#$=p^9d(?06+%3Yv@?!`xj5V0_a}mFtSMJ*LxmYPUOUcDxp3Fbz%Z%r48g_9m#*?`{ z%zo*XLWJrdGStP+Terp6e(O8ct-v@wJXHP)Fg;CUi-Li_3L+(2<{Z$lGkPvKSt=4G zVa6nGgKOYpeTEzHFv2_XuSPN%OPF$ScH^26DimM~G~A*VeC;1QI?-$XD^duihea(L zL`qdn-X~||hCU9_bj_n{x+T*W>AzSwc?&28CDhH`^vRH?q6WVLt$sSbtjmrPu6D|? z8v;~BI1q^f=}tc?Jc|y(mukPh?-FJt03;6dg8D^T4s6{k5ag-b)G5L$YG-Pm1vknn z?0&=eKEyz}PX5A~X~tI$Y%*@nU5~Cl75MnJ?-NBK^i`Zs8||`crw;$HgZ@}QxyN}- zLTS4%|B67`(i*UE5lczH7$+E}ti)n31v#Cy1De##9_IkO)tpPlHK&c2%Fo^15aJr7 z{PfPD9?!t+LdOr)MA5+)8)m;wL!A%MyftRHeH=82N+S9BkF0i4Y!pyta5Oo#lpvrs zF@*^?DU6%7HEps*f_d?sy2JiZ5BwsEm{&qe6%Vgkf^dY32%7G_;Oyj?J8gPu6L4@W z#hO0i!5s(v1NO?-yf1}C;Xg6Lc&>^9?$>x7O@n41S?&BiWi%&$YSDNon{oTQ{qSO! z>f~_3lePyh*Y_0FnMYlhi1R3rE?hAOLQ;BULR~6DA;Lr*NUfQfnHe%)Z_VviNmCJ> z&3O9(J_SEb>bEUy57=n1!)D**e^G4>O6US9A~BZJyP`+H(vn7E%Awerp2aiGjyQ`TpO;5xHeWu{XzKIGXzCHT*mE5d+zPOs~p9BodT*?z>Mr_bt zeoO=+5Eoenm?R5z3|f;Bsv&#$p@`Y9~y-@7!^9w++2bOAjeH{nvH0)a2{INv*1xJpcnCDro?Fe>^AO!k=I z$f~SSZr#v&bf4F4MWS&pJKK?{+OMLQ3v|8o2m>f(Z3)p&YY({#Mzw2eR6to~X{4jq ztxuc;?_y{1!=>_H!Z3Em#Z9kv%5R~oL}>!kf{NzZ`XAzMZu*5fm!TD?@=rYM2}@G3 z9nRM2`yzO=F0$bq>LMv-X5FI;L{~InA;1VezNdw%FJDl~+IC>Trms28jw7$Eq}IBA znYo#xU-o(OCUdHrSF-Zl8+dh=6ttEEdDk|!{%%@?___Bd=#Hn1pg*mVMN``LafPgEhp&Qcrga8@ySUpC3?%-flFScRlr>AQFr@ zch2_UXY`#kG2`yX0k==6D*LVu3e!>hi2hN7gf~{vMGx#lPV$9E-sS#lSBeUkCCPS z#tV1Frym`tgDf&P)o$8;boREP|6m$)3EuSQWlz{_Sya@@q5cha(4n<67tG}8TrYI_ zMF`Q4zzcUu`|!%@7t5(Q?LN6|xw=Ks?ASOJvr4Z6ol^Ji4f~l!#}4<>ddeVIf*A$! z-o!hyLD*-6N`{IncjP!cr zo*zpw-o>+PVqceHf)FEi&twi)UqqOQNiWTeXLIYXSJu8?rXFX6qUsboj=rmKNjYmB zscAJ=!3#wX2|>4_sInPj7B1j(Wnq?U(+_oH?K^T>tDOD9D-dc^DOx#QIKyn^xlSY> zUOXvx^)RoVvX}wA*26OB9CIDM)n&TcZLb@;dB^3rj^?xUTo8CCtB60e$@RT@^o_En z{IBEJ>aRlJZ~V-myVM%h$L^8wPLBZz)g8Yq%*e&t6Cc`oZK0>HAC8n??EfgNJ7ozt zr7Je}A#+`zW8+1+zC2M^FRU)DgF}z@ov^RlcUmhX<~w-p)?K&`rg-0CIZSd*-K#TZ z;Sbc=UC6NNa0ho9q*D$X+?MR{em8iJ+ClnV!gzVDQmgn{>7B#N(W5Ek`D3)16zESA z%%?a!Gv>CB$pOh3(9!ml_KL=u6{HnyNgDF@c`=^c(D))H%gszWQHJFY0WoR{_!CNw zZq`ju*hS&yd|D|0T`^^~f?X79tt}=Bu$}D?hg=t!z;BW&o|ROk2mxyr`#XOY5F$(< zuMVK^5a0puqj|HguXO72;+TB>sDolAemL3Xn!T`NzY@b$ z%QqgU#cJSRMNVfBA?q%A9f9`bstUB`Nv6&QfE;>}iNW>pfmEVkF9Ys0TxEop>-yls z%uy&>=!myGajP^*8&S@}3rL=cPUg(`TK1^5z|s6wesPV(vaQOYO9MkqUO0i|_b3oc z#of}Gp0aO*jTxmC6l|H!Vuo}cjLTp?bKb!_$aiRD>IF`n#MNWjGBDHXG&wws#Jw$_QNu%5v&pnOkEUi zMfjN!T{Z&Y9_2MRxG3oP(_`^3`*|FR%-2OwgZ;Nrj~a$=vkfdjSjFZ)W(N4)9%jf0 z>rjY6By;Q$F&ucg4EuD=4TIk*r&s%j#n-QT(Ls+@RaX!D6u9cCkcJE3QW?3mdf3_; zUY`~TetG})@oZz``~K6-&dj3CWkA)Bx{ow6lBFX9s=XTeOqJGf;}!Z!P8QzEIBN^w zkuLC^0?xr6;Q?oIe6*hsWt1o>=zf9(xmCuvoP{>4Cy(Q{*Cn5eR1&72j3~y9j>I4T zS|)^^TE5>qf5kQWsKRUF`Aqt>r(<{B##?WtbF{4;GrXaQ2++QVoY*h-ube(|diowA z(-|X#DxT6Ip)W72&KcZNg}|{6xy{S0u1-m~fK3FtKJ0Qz`}ixSO+-cMUF!q}LSAZ; z?XzD-EV4GvKm?rm?dHl2b{AvG>DW=MEGc{Ak8l+j099nR>>yfWZKBJFl6TGxz535N zD^ABsT6w*;CnMgkv{y4H_W;0z0mF6)ClmkzrQym>ALHn?>+hY6W2{hALrX)a-ZCWY zZ;6HY)GM~m^qhE>B9foj$F##C%t#AK7ODDOr#sty3lU6izcn}LZss*pcu!aFDg^2x_YawGGI$v)r6t&jN}$38C0pI54x zm{J`fLj+%Mgx*Wz(PVPrf%513c}?{7D*5xlS6q7fv(?_s03-%3#K(gFzHBt*X=FlA zFGqTRhB>F#+1unIy)NS7L76) zFBAUOmp@%o z&h^xQ-=)=3B)w?2qe`V`Yn@uY%IVC7Hg-x0=ujl^Eg7qzo7QX-@AIhJr}S|bh|;)t zo2~X=Ltgm_TrIY^Kl!nJ`(=VFjOEdz#0D=5K~~L4jzattsyla zn#G-E?m{k6x^kdsm|387Oez~9*E2Z{Zq52_)~aoF#v+3g2(fZf5>23J69|=AFO(~v zYiGyP_sIrvxy@db2VZ5{P(PH*K2H$6tq^h8kV zk6S!AT&(&S(wuk?D7N%}U+{asUH4!zdt5Py46hyDB*AZ{cNXRI@k0^$9YK0js?2D( zsGpw^YQ53j6gzD_rQbRFyY9ec1;!E&?&p#TV+HsM;obK{uYLJ&rVi#_xWmEc3p^+b zKH!!cvNH}Yb;r!A+p-fzb4?3)0gj#}uZaJoGu?WJFYBy>h!$QCYuMR2{dkuQ%q$sO zqmv3Z6Z7gC;Ed#ye z)+|Q|7)I`9BpG=a*^dZ!M8$#YW7y!JiT}{mi(k~g+TrOZ6B-zR@K#~>an8)-%)gFD z*JGC@2}dT?9i)H;KJa5VVn}o!4F*^yqJR_bOPqXfg zk2`O-DA2~T3Rz(4IMwD5g3=(B_0wE=hP`S-Z+k2XMq}ZGev#d2ZK;0U+NW_<_ZSF| zQXpU38};ee(oXT-M~GtT^h&d2lDip!x=)XCx-f0TyZUszlnW)}8Rh#pJ2W?yy3z)J-_~feP!x!%fW4gY9Tk$&;^vR0xgKLeFyQ@z5sKmz67CMO zUkwvAfIWqkocyEBvM`CFDEitd~@Ea(B_5#l&k8 z_`vk5VB0dq_2*5r1&;wj*UPXdKCc^e{pF&$?p-eX$$oK0VOH4zmTyCkOr`+?tVL%? z=@53A-|?22sPF-_6>h3nQXS*;JWd`RhB=Ss;1mLt!3u1lW7eL%-@(19tAhP$;?%%C z>hzUz83)etf-pTMi6Kj^zJq1Ck(Cs1zgv!RNaw2cpk zMxsBQTl5~A?E__B=0XE4_76c09yD)q9T#vup{-P($?1b#HiNvL7=L}*v`2C| z)t622e5&o!KjM^H|C&QC6W&o{gOnW6~H^$rs6Bp(?&)1-s5& z)A|OtYV9=7L8X82Fjdp3hLJ6>=(d9dMXe@pr&+#Fm(sH-AlA_ynORLFf=*z2dL$Ly zRt97ncOa%@(#Wxriy46D^<*-!m{!I>^pVl_xl%=nqYr^=Pqu=nXQoH zG!$x|UU5JxH@?@xoM7zYlUyhl58c8d?7Zi3~F=l;p}0ggj9lgxn4_3Cc_8^zsdnj?fdv`84A9SN(?Rm{2P>t3ye zhA%9_$ZZh9KN&AsH=j13m=S8|#T>uLU+rGYoULt$dvpeurE6t`w$DzS7?& zzV=dhE5S!)l(F&7gs&bJXw{>HD)ZMWkPee`5#W;(-m50y!9Vn;DW+m)j?{XRiyL?T zTj~#~7q7F2m_9EdTqA^6{jSUo<-5AXHzQAeCW;QZAnR^{6(cu^m7X>3YRuoerxsDz zPaiIa$&;I>JZ54|%NU>fU=~)XiyEtVNL@*z5wAL0Yc)1 zgWf|Flpq^*@p*U!p3;=q(Z#rK0`>Ple2S` z&G1$kv2EUk#w6YY>Pxd&=6#Ze1A&`8mOY>LUHb*{n2Lc^WW9{$g4#S-CwM9%lPxhd zrcCp#B`;0`bp6C{qgZ*ye>V~s(Gg@g2v(<%wl2Sk2CIb^Ilk z89x!0tLFQ|rBT?SGTL|rKfnTWmU*eR5`6f)NKcsn$*5C~tUD}2|GTbX|IblkXs=!U zr=;~W++$%byP{%ErCaNU9+!0+>iCr=_xSa>E)(jTx49_CwC88jOn=!xOjo*41 zRJeF`!T3%P+~5#F4u8Mlv8cZ$?up$%Dmg0*G$FbF)VAfe7th!kA_}zoUcBxjiLSH$ z&;vJkkw0rd?(;5{M_tI<0uh7v@W|3Y0g4-6as%xiYEHXlg2aA?`nKupxF>9=0iv#a zS}v*TU(_k+B4Cou9GuCAN6Qo@_5pis|DK1xj;5m`$eSKEk(Yv)UGycV<%*Lw=CZMj zR3%};8tBg(Q}ygOcYdL}pZ-+lI@*IeGn z8D($holVM$y-13DkgtdvKEyR)+3Vn>{!wF5z5%uVY!#R%VPI-P($BG45ds^8q#frItQ( z))c4CmLqx}ilb0^>e6^{f&5*-9$nTwhdYB(SM7%+zZSq}?)Dp+NW@GF5k$tCoR^#SscZQKFg9aN6ZH^)wxis6DBTR@#{-6gEwpe*p?xtUBxrntfChCK+C{bR=hqf+l(lV$3oAZ??AjiVRbIl8y}fwF zu_}MQjdlvphi%1WTRKawSB*~E4&$6DrlR}4Ca8#uG)Td?+qo`TrH|i_f6yw#AxEB|TnfW4)tidksN^U}(>c(*#yMU; zmHzhHboHdyVnkDf2XAn$B%xrkvg*F(S7@^5bZdzvibVhgvXvo?WEy=XpzMV-M^7J`IF&4^t|0qp$)E?lVX6`e~}e@`c=^j3hI>sC(2!@qC1{ zqwdu0kZ#qg&U=sJ03j>xoW7-QpMHEsd>$5bAZxaFgw=6oN3Q$EoS{e@vS` z2=%fU3OVVXev|T&j7JZUSCHUgyNR_tMCz|~1I zqyNs2y9c=Gb}eV;%pmcCjiyG&zkNHB5&s9YvGlWZ3?7b-#SDAKjQVDNyt1V=3iWjn z+SSBRJzhzjdam+F-yR-rhLTjxii%4Va>exZoeV_4Njjn&zUqepKOu(7@^E=!ZY0~z z!qP10VNCnzK3n%Gk6svSzxrTG)NWnx*lXK^_W{_HhfP@3yMO%q=XkB-7?I1?@yTJCKe}r9h-G)VRyWij8f~xHBYp3%Je#I`hd>hrP*J)YI#r2z6+;}9R!G1O(J|a@X zO_4?2o@hoSSF{N>;~AiLR(DSF@3CC_>v)1TJQ8=#IC4cP=_u@VdA|b=MwH z(^a*G#9~a1VE|K8Q~C=x zL{s4+Uhr+LJuSmx;KXwT8^z?Ov&Nc)eh>p$?W@>?Cq|nSj2aqra^w3rCo$96Hm1gf zGQF%U$z`VRnq?ECmgG@X=*CX6A#M3d<0)CSb{JGCZO+lhcHxx~_D6$mt!~woT!GZ_ zLhXzaiGDq|UE>Bj^1JfdQ+WIzQO#iN-EVdu$9RtvlR|gBF-YEyKU1BIRaJrgFv=vj8;)F-%oAQByP|$;~sTms!cz5d?vFo0t8&QtaE=NnL3&JzF3i4KO}a zU}|a!b#c@b9&`X#utQ{v7~99IAPp4$&Uo;Ob&KfCg4*+Tv9y(6g`&rRfg%h?*+2jc7+ zPU3RG_{BW4=?Zn#V6Zn#e@~Pn#}}v+*3k0lOH)!UO=;zKJ!#InDotrzCJiIlxM{m5o7&Fh-01^rWa?9kg04#DUj|EO|q zeD%QxKKq_$rWZ@^FIOACb<1^IcEloHX+B+KYJQz+-2lNwIN)YDH>WG_5! ziSy$b)b%`SZV|omf@spV!E7j~`K6XDN8sF;?PRC-4Ja;AI;=KU|D~dsk4L+QYsc>Y zgU!DDD~hWxg+B*NPk)`af8h7+uYUXaY;LW5L@rg&7;?#Pn|in4_V~Iw!W`J$&Drr) z7U!JFQ)*_mC2TiaZC$itth(cxwoC-c*IchQPe($Y&+OXS^_gO^cKY@khnipd@Se@S zaedG{SR4Jcpl}q_Q-FJad*tKK*~4 z)El^5wiJvm1benU=uHhhaQwN2X(Zj^!e=)7@~&8}7W6O3ZGUx`h2@Itop)>-*gMkw z!6%-b{ZM*pW>}uTASz2!Ez_y}lYX@T{6G+;`=n6xIJT`_Jp0|vzMLzbs|EcEaqGvP zK$P5WQc9oy0pKAZ1H7!^l2>_Yt`_vGK>y$!?723` z*y(x?j?n#XoRPm@!0Dnft`_pE!~X(yDc70~_P5ah001R)MObuXVRU6WV{&C-bY%cC zFfuePFf=VPIaDz@Ix{jlH8CqNFgh?W*$6&+0000bbVXQnWMOn=I&E)cX=ZrK74o@14Ba#1H&(%P{RubhEf9thF1v;3|2E37{m+a>)={#ha4^I zR1J#+HRC9Cy}+1`ZGqLRdry4_30fxlRjhI?Sgd9e3zW4Au9MdZbZ2GKIh0CuO zt++0$;Aj`s=AAbuxMsCa=~Azv#T8o~mu`F#Qor6Qsn0oOB2c5UmY=SEmGC-*U<7ZHVd`1jkdCjF|i19P3np2*x{7e7umkuCx5o8Zh)M; zgO*7|M9XI1(j{)0(>-!#hc;~rtzB*Cm=25=&&@!gSaTf=HsWz9H}JmpAO!+Q6u=?<}-0hKHA7hNn| zdL?!0;j|ei{{R1fU3W_cFqkq+g8V>96&^_^GX$7@4*mYM z$Bjwq@+o22n-@f}VUQe)@8RFS_PR5P6x{lEEmKgn|JCyjMHbg1`|O!5R0XaBZDLIF zc6T`;yDR(@ki%Z$>Fdh=f<;zX!Q#-h**AdF{GKk3ArhC96BwA>5(NVd3pv%;I1%%q7^lT%rXZr*q*Dze#lb5YUMDWM^j7Lr%4n3{Yx`dnPZ&Be8KOKFMZmoMF2 z#-F_#{xn_MRK)Deru?|;)T&prnr`iCy7Y@pIGD}&^ODeLSC36Qc&_f&7fIvvv-6BMm%Q8aldq4*?;N+7UQ|qUbolO+mz$pI zt>ejiryaH~DmEZ$N7~z6U!`qqB=_tw&%0%lfBIVP?eaHww%$HI{or|fg@S*drdEG@ zce`Fe!$M_BW4E=A&7%hk54-odxw#(y@PVoJ@Ns!*@%lFvPDw(|3|ICyozz^J`BKtJ z!Hl6PKPHQ7-^Ojg&{8dNjVMV;EJ?LWE=mPb3`PbwMpmX~+6D$z z1_m8f};Gi%$!t(lFEWqh0KDIWCn(c zIgdZ_a1@4VXq@stea7=?5CgL^w_Y;0u(GiCWD#az1(ybs!zs+ln?n>%-?(z($eAND hN7zp{cr5VJV|XPlSn|oqbSlsa22WQ%mvv4FO#lkv?SKFP literal 0 HcmV?d00001 diff --git a/pkgdown/favicon/favicon-32x32.png b/pkgdown/favicon/favicon-32x32.png new file mode 100644 index 0000000000000000000000000000000000000000..84c074e99020b25df1420940969228d2f39311d5 GIT binary patch literal 2709 zcmV;G3TpL004R>004l5008;`004mK004C`008P>0026e000+ooVrmw00006 zVoOIv0RI600RN!9r;`8x00(qQO+^Rj1RWC~IknNNP5=N2Hc3Q5R9M5UmsxCF)fvZs z=ib>op2cH(#@me7#B1V^&DnsE5K^ED0z^R(N*fR$1&|6A;sq56sfyHAMJ>Ek(3Z9e zAWESj1kyyLBnS~gLJ}J%c5TPIV~@w{EFRCyz32474vCutlB(zBuKIr8`akyyZg4HW z=|>=h6;p0jO1`M18Ar;Oq-lI9G);E5e{@6k#Pz;dvtm2C#fFiYtyWS#sg(IJQsygZ zqNE%`$~TmfuS=VwUrQzF={ofPaiF$o2WBRN&@?|%?odkZQqo+6G?|Bklqe+?O0_B_ zUqSIMf@zeZxBKw_=0M%rN0DY4gvdh5yOosBDrv4on!36iuH^htp_Bqt8l{c^F9V+f z>F;vlst(kyeFTKiG0oLVna?OGw<*(bULLiQ=GEY!)I~GXz`MXJKr5iG=7_c+>J5*x z;?cJdny5g^-Ac*5O3H_nXA&Eh+}s+dg$=1{yX#g)&kgbf1#u zb|uZHl{9OWX$U1vFfYO{rrn%}&qseHd?CbQl`9|k$?4#-)xV8h=-yjgyCnXXUEAsJ zJ&L7aG^JU#Drr8Ck~bqwE2aTgh0D2!uM>_^ShHMOeyDV%kxswf`Ss}sCoT;C zs;}qB=X+YGu_$SxkUo^$jWm}l(?BhN{x^KC>)|@!fKrOATt8WEH<8GM!yBsFmR(Tj z_~|=c_vkV`Yf+{-*9%J8FM*8(@VRK`;c6bPz8`*Z(ok=p$-%VaHMCZw`?ADTc zVG$-4Wg2sxFyCD2YAKhO!PSky(JlDP%8{l)mdi=Fy_vDr;}m!TB;u23%FLh)gN3P| zAFqq&7vb^}TwRX?N?~<4@dS!6tu8#p<;+B*7|A&C{&teXJy>kH#h_`VCq__4;?kJS z!-W8WKq?TLz@l5QJ8UdztmAA;JIQ1c5a_x_CY?b_xuE{p{z5XshBcL7xU&jV4gIrb?^X6DNwk)}zgteCp`MGOy*QrA$8$K@nrD%P!8 z$`{95@OfRt;z^`w^5Nb?jD;fzF|Ti$MzCQS?pz;3Ehm}iZl`+FT}%%2^4V*@!Ic-l zk`XqNX_G~3)-ydkM5O)nTz%)oB{~(QzF{$S4T~u%4DivuPiSlFA~(lHWF&$s%g*HZ zB&B7=3uRR)?A|jNbbD5fT-2#-YYy0bZXqM7R23Q9snXqq73pT}5ag0{Bvc)f1Q%7aL$zD<8#RULMh zn}N2o_{taKE3aX4c!W%18e6t!u17tE%NXqF%=Y-aJG1lret)QxaBmNp_`GB)7#WGs z-qyvLuUoO%ZOkN+bawO*jmBs@+kvhL!Xpt{o7*rl8H51MmPO;8_h6)EnGO$=m1U#% z)N$<2Y+~WzK2NA>k2Tw4h>F^6#Kt53+B@z!Qnh|_z1Qm`GBCiY_upi8d;}o`N-2~A zAwWunxGdL~Ki4!dcP%Bkm9=bq^hv@a<2dYA&K>%InaOc#w%$iNIrEt-H~-G`Od@Fs zu2_#UGnl4iIx0TN)-onazAL8WS_mG+zLulH!P+h-r0~KQ7Jz=p@)UbkBB8@H- zlaVnp=`{J3HMrc_d~@tmhMT`6+h2sGX!T~4(3y=4;PSY@@29V;4}WPn4R_s7$B};$ z9~rm;a?R0~l0Z!(p~mGHnKbQ(_v5c#LTS@R1P~eMXS}Nwi>Am#C(tTFJ{lUUNQ4JC zv-fRWd46nJPK;z6cR`R1J07QK*;<5d{eJOL3acxJx=mZLXS;|`O=DyX3Q9|f4tCRZ z^Z?Q@5Sl(WXhK8Jsop{&mdLhRtviR#9QR8E@v%|Hy4naVu0yj}DP4LK7MGXk=m^G4 zd~V#Xk`W~|%GYhCY{@dZPM^Z=@!=^9f)KPH{0GuBD5$#$tIOM0+H~t4Uqy|fS8sTb zL^PhAUsANwVt4qBjETQ;F@r59(H$(2ZWVegF+^3<&sEGS zI!j7}`$pT&Tu4PHD|14XdFez{jI^D>T@+$!pqGK>Q@9FC7&`Y2!(APCf)$|K2-VlK z>gLtBy)L8#yTeW(R6?+RDS4$82#~rx>x^d4ejz>`{Y5xD*}40}BfR~~Cl<jJHu|$R(Z`ME{;Qd1+rvCW*H@+O&|Hu2;lz-`4_^QMG;{IN$7MJL!PIfe% z_~8AYMTffY4%9R{ZSEYp{`DaauaAliTS!Hxsav-eEH=`~Bp$Du(cw`nRx8P=iKyoE zzBh6q^1G_W+Lq|Vw0iUDrYlA4yT&?Lu$ELR>U6krf9S|9c(!KieNExEW<3>~rhLt< zEWdR<3XRCvG&YN1{K7Efqmhio<~TaqdG6(r^IeB^rzd^>^H;AaWZx@q<(0RC)j?uB z64>y>b3ZPss@jz?sdRg?NhXrmZ94xx-GZ(Ob^hpqa~11udnLH?mcN}lH!$_cT>&1u zt?@hUU-!@H^Y6Cvz?O3H*1`T7t3^B&jic|@Y1jU^xUzdpItDY*;sNz z_WlEz$~17Z6ebw}001R)MObuXVRU6WV{&C-bY%cCFfuePFf=VPIaDz@Ix{jlH8(3T zFgh?Wy4VXr0000bbVXQnWMOn=I&E)cX=ZrK74o@Lg+igO-t%2Wq4<#3RJe=ZlU`IP%6Nk|@8KhgC@yhb{u|xB{oMcG-Zjs(MHFVZ8Q@@95H7Bcd9c6K z|C*nkW}NBUBVYZw;CR~ihEI6=SEnn(f$t7V(FxUMj<>}Bg8$HMGIx7F;Y0rCJ_uFZzzi6qZW*(?NddL1bzJK38 zHxTPm9k6eXAKEvip|dduH|sO;+0imwU7v`S86G%S8G_Y`Hpq1$Pv!@Ib$q_>x{Ir$ z^=gu>UU*(`{n&ecGvu`wtkl)CsF#(tnrdH^_!@Q7)oeWMG}YiSP7^tf@8H6kIQ;qS zGTh%g3-7n&;qLZq+}|?`x3=fuN_8BzW;>$9Ya&ipMtof0HnGt1tv81M*xAqe`>`Si z)i~p^8O~bjckM^1A@W^q99EWMrgl$e_x4D z*S74_`{($5*D&1!8#A0K10m?xkcia@)|l;Yj2Rw=sL%7jrPa}tcSEFFjmPd;9{6Zq z5k5IQ4@b-V&^+B4*Ve`2+WL6h+nxpL4esrnfzJALTwWFNkHe+jyE|$Ut^RU#BR#>h z{j4F8J=BSFZ!I3h5T;Gz8mYLpi9ho118=F&cqdrT> z1Wqmv#o6T%xJn)Va9;_2e{wOpb`|05iWuB&o{n2vGjOjt4<8?#gX?t}I5^uw;?=b+ z3!k4{^dUM2{_St;hpQIaZ+L{`+n(F1W-+vIaJ+dGeK?Y-Br8W}56UX4-ya3{1 z4HqqScG-IOnRb8klhKHgu9u7-4cuxkcxZkb9wiGTmf`lRdw1-8F^Qckq3j(hFET>qp% zgE2R)HPjw>>yDDLTp436eUam6b*xIX1@A#H@o^igL7tf5(wZ1-NU_E&uPLa__P}-8 zp4;`)&_VjQtxiDO+9Y%~&!j#V;qtl!+}WOs>O@QAIZeQ+C84O{vrRKRabD_yiMi@~AUp153{fb(k;Q66lJeY1VAG};QDI-2tR=ZWh%;w)^N2d{aK z*TlY3|F0K?TWmLd>+Q*d;XpZgHGHzx`TeB<*h1X%-6l&}7e4e_O%e{z50vt8b89Bf zu8PObS>Do~-=Iy|oNkW;v%P31r{hLlI_PJmO%nFWX^cAPueiGRJeP^MwmBWws-tmZ zLmV!yj70mIC~Pb6l=li7T%FjEeJxsyP=TZ23t*yA^mY^p6RV} zY*A>t@Rw(oN8(6%5YAMF@vJoZ96QqDUF@9UhU1Gu5o@B2LidR{zak3fmxbU|WhCuk z66*52knLnZeHbO}seqX})VpX8K--I&OgH-IS-8F_8S4@)7-vM_;`$UMnvW-*BT+$K zv=n+F!E79==@SJ!H|x?+>Te`)Y|$S!d_XL?BHU2ry(Piz2j&GL&Qu2>lg6Mi&lQX# z`HUL<{&-3MC1EBg^fW|UbqYS%nU5~YOGAM-VvNT@=!TNkec|r=S>P0II2NtTWAN#r zIoOcyB4x9E(=?n~8X@s74>6TG=ccUz2fj1MNnhHr^Q&S&`ECg_&=>&!^1$&bw0G^4 zF)8=)^rt5)!jWOGPr1|pbpjo<+b0)?;5L2e-EEX3+QQNRV~BGE+vzzaA+V06%G|a$#*kdy=It zgl}DwWG8KW3E#b~&`0X%rIisjnm!nF@4)b z>hY-sev;pF{N6>|${1W+mn?ZI;18dojT7`INtSw2ekfN1;78{gmF@W+?STfP!PpSz z>EExei=!`%!mWl(G%{W}LwaAQtr50D#0gJJ^S-!=X9fP3)~8B)b(=Bw;qnkk^XaY= z(YZAX`{xEoxs5T=k?_Y+CWudqwTAit_&b)ksWfHVwKtF^m)9rbe04IGM_b@fsW&dK z4C~hE#SzGK(3dj#v^4JvyYjO=c~=o_O+A{yGs4laB?Czox(GAWrVkIt@p6A0UmS+D ziB{4UMN!AB2|sy00RF4hu_`B*gtm)#McDEA!6umLIT;|@J+I&ENERiuoi&Q?XWY)o?)0KdK3n<|ULOxrsd z7v9>OBx81AA2aMH&>pEvJ0on35@ta+;cLWq`I)hX$N{>q3tP%1@9DOy;=1y8yCw0wOmZvgzw`7SC~H>bB>W*pYJ zIR)*s%fb#gjS)UX1NK}3{%(6of967;oEQa1tx@nc(8J=~G;FSzk4%3LB)d6aeR&CH zCx&B2R4_az=wLxs3N|j9i)r4j@*NLh@3yBR)(|%D-p)eg^W54jH{7P(TNGxFVxK8E z#2P@4UvKeyM{@xDf4R6?rL#V*{rEgD#*SH-P5)~%W0ShvdQNMfv&K%e&@$KfvLw-6k zPO3?B!iSXE=2^bjl*SmSDhy|qMc_b*C*$1!#&N=CtG93sfd5`yl1j(Q;Pz`9lZmsL zj0If?zq7zWO9M(An71R`!U*S&?#1~dyHGv15N8hV!mQXZSdMrL&f24Kq^VBwrYM0j z+tL7+abu9=YKMc3o49J>t~XA~*$;W3CS_IR{9Vj%-dpI$7|{z0LyTF+NWmfIdhYaj z0{+45=gpc}l}`?ow2L?)Kz}sv9R)Y8{y2#EuskD~bge^qdIHYuZ${gZ-Kd#&h|<(pw4XkXBo`Z;+S7!V>gD8@IrIF7bXVd)xFpT?mxbWNUHQ1fI?O)C z!oGT%Sf9q6lfEH~xe;}!Wy+f)2GIYTo9k81u8eI@v(8ATTE7(cZ(qZOS)Cytg7AKFsaPnX}&9l*HIKgmLer7RJs4 z;6GaIq*CHJk@3SA_|m6%>yGY&gJw4$h=YJX+Qt+<2D+3fO+;84!)Kx%cN1g=cp=rp zfwbO^wWWpfw`f~4%8orkObwCY?}yil=;wirX$DMfboj8 ztW|8ua-xrmZ)whV9RPo#nT`sdmGJvdcsvdwrtMy|Ny1L{*iCENYVkSV$(p<|lyR)c z;lvX9DtE?XgVMf-A0h_dl_?xgck<0unmNkHATxEW? zDZ>R0wBL*yTXtlc4uC&$ina>#igx0_T(uhqKk~tcvgD#P~bn6q{WgX!iIUbCSN2>m-*8IAk01QI-bqp&t%Tv`fzw2g*=6Yf2)&K2R2nJw;x) zusjs+RfJ-9o^8vQyORdM&)DeIM01_<#6iZ&KN*LfSm{~#Aao$jZUSzx7IM2Wn{h-a zs*`N6v&aW`8q&9Z{rRy0^^>Vqxi^gu{ew$&HC6w9J*tr9$9(@97LVSWvn`O&kM!9#`N#Hw&%Q8o8{`QHsn_? z_l5OwpW{t+)M8D>&5btJ{#@V?Ci$S%%LiX2AD#dQW!(KZn)m-r_{F6$Hg`YVk(+UO zS-`Nz!TPA*C`UtLOvX*7ZLOn!_}{)b_|vuu9K3}r(XI~ULm&S}UOXiZUl5;4=7U;~ zg6(OpQ;vQ~efEr)qJ4@ud`BN5`Op^!5$`<*9R5zYcW{|=J#+t}KaP~6*O}u_W2|w9 zI6MfXPIt!{rPuUS-@J&6xGqKQ}x-<^Aj#yg-{YjyP1&M}Mi*X~uh>Fzzm9F8%gTdGEjb8RGB~ zeS-^eXk+fMpEk*edGvso<$1sbJSYYf3g8>H?)|G*yZ2K=yLa&$*Y^rVvDm*+DAdIM zkwWncv6pbZi2DNp40qn9P*^GyUx}SlCLf9Y7yo~EB_2w=lz1xf?xlm0E=oEH+Q_A( zqmr)QSax6Urn{KaQs=Vb>YdZ#EZ6h+cYb-;ON`r{vz#WiF`hZPDB8{pxH=$qe;#M` zeaAO{z4*f2#td!d&{gauf4P@E-Xb3(99D3j`Jtq z=eimq!Qvg}fgbp9Z!!C&MG&<~F*9+P{ffG5=Wm+}+>f%~>_#oY3 zBI_y|a;7H7Wis=&aox37*1qS5a5jSTG@|b+YWshDZz<m?MuSVBNhZ3{nsFH49Rt!lcr!U#+3 zoD+l#DP>L?WA? z8Q*=gIoov~`Dfl22FBm7uS#~jdXO{~GdKs!LwRN}b`^WGUJ`|kte>}4Mc^oV|Dtzt zlCu&*9%4*&W$o39bum#xYb^A|?YgO8za8hQqL6H(kKoDLawcYLo*TrRPty!9k)IsV z`SlyWRKn1b=cwAYGP-kRl7sB4iP?l$)A87x>5OGDR@ji~E@g}|g#s_uMfJwW9*oGx z8KcR?{vqN>H!&l(Yjyx?GF)ZPF3X8M3!W=xMCJyWgSBL=NpWbMYG=@!GoGysQRSJP zB0ec+zee=-iu_D*VRa07mw@Y=r(u1%D*`8uWv#M%=0bUH-(BQ(i=(W`8}?i{BX(k8 zAoh@khvu_KLYT$#+c}T1Ak4gVW2S5G`F}l8qPjfJrZe7L7snQbLCib}JreUyXI3R( zhL@Oc`0-x8$nQmLa&Tb;?rcqyIwE>xV%B6yv<>Zso~+k#hNjiztr5NFU#|35-C5|~ zd4hA04f$T!#kx!f=fK4LL!_~oy?99HzW5IISQ1)vq*l}6!+Xy+QXQsR7GlBZh)pE|bSqwk~%*uJKcYbj3c zYQ)T#a0D4o=J#c?Usbnkq3ro=TfJ1$Ny!7D3qpQQuS&!n+N4#SRiceUQ<1-@i?kXH zd$afaPxln4u1i}Pf!w5GfmmrfqShVmka zb2lyGybt@Tfku;hWuRL=)vzknRrYObb3A3={k^4Ov<gysuA_!jkdT?aVO7yK+JBL-~s`(pIGp>J+tg0fV4}s9y~VLr=}>ap(5^ zP4p(}3;fvoN|gQI%6JF%fkwC1rI_~O&l(Qj)z?{Dl{I?O0ipC&y)e+8OBj0eLc+lFmGzds zxDNJN+9K--oQ2KA8Ok1GLovU1E`|j*DzD8c8u&#NF^|S|~9w_>ze*IvO z^<>JUoPT%%7)Y~!HO%n4{QkC#up>)je{>F;wN(w)B^R(p|3?W!Pfb-3v(r1#JEcPP{eE!xOR_Fuo~1H)&mVU>~&|CYbw2{0J*5_Q6n zcKR%Bc0~NG0EH%z91v9<$+ZzQ~-(J=NCWbXlmycNL7s8FOII9Df;a zZlA@Ne@zN!Nn^3IBtYa~-*SfXcxj-iBi}KE^R>e{dv#+KpAmC2&9i)Ph;yOK6CIIY zWkBDgi8Mz;oS=WHp6ZOnkycp5#n|s+#Jl5OXZ|*#Jj}9d9b-XpX45QxBw8Ev#%jV& z3!hSz?97?85Y%vfd8UuC$cH*Y4acc+zG6gOwrdyvz6k5m-QdN1M*Ph~|2Q~kvJUpn z4Pt%5UE)^}W7}b;F;aD5gw+Vnk#}w8EV!rc7{)8w@SidXq2|U2voJvbV_flF_^ZV+ z_7XQiBhsLQdAKU`_YqAqeY!#n$I01}oM1oHRW88%bk2&G6>~-`7qgRNA#%b96FnSR z6wVyllktXm#{`vOs%ujnM$d?ex$>YJQ<5b-hXoTP&?CK5Ol2U<#BU*v1j;jgQv%D&@p z_8f1B7)Qhw0uB*Vh`36``r;kRC7zGBG{BLCVc_iX#Vr~3uX8?ODBt16Sm`~&@tyFA zz3=E3kH|dmow45@C=U~VGvV-$i%WWIyzG67UR65nd6%%|;vK@537mW2ctAKhDGN!n zd`%x&$08o1X$zOo7XPWwJAO~wJD<<1E9L%iJKyml>1oIK;xuj8ar$WsK09= Date: Tue, 14 May 2024 11:25:13 -0400 Subject: [PATCH 309/312] Allow `NULL` in `vec_detect_complete()` (#1916) * Allow `NULL` in `vec_detect_complete()` And better detect `NULL` columns and df-cols in data frames * NEWS bullet * Snapshot tests for `vec_rank(NULL)` * Tweak `.gitignore` --- .gitignore | 2 ++ NEWS.md | 3 +++ src/complete.c | 24 ++++++++++++++++++++++-- tests/testthat/_snaps/complete.md | 16 ++++++++++++++++ tests/testthat/_snaps/rank.md | 16 ++++++++++++++++ tests/testthat/test-complete.R | 19 +++++++++++++++++++ tests/testthat/test-rank.R | 9 +++++++++ 7 files changed, 87 insertions(+), 2 deletions(-) create mode 100644 tests/testthat/_snaps/complete.md diff --git a/.gitignore b/.gitignore index 014c1b316..10ec9a9ad 100644 --- a/.gitignore +++ b/.gitignore @@ -7,3 +7,5 @@ docs .clangd launch.json .vscode/ +.cache/ +compile_commands.json diff --git a/NEWS.md b/NEWS.md index 2cb290516..fc859b73c 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,5 +1,8 @@ # vctrs (development version) +* `vec_detect_complete(NULL)` now returns `logical()`, consistent with + `vec_detect_missing(NULL)` (#1916). + # vctrs 0.6.5 * Internal changes requested by CRAN around C level format strings (#1896). diff --git a/src/complete.c b/src/complete.c index 1723f0c21..db7a47970 100644 --- a/src/complete.c +++ b/src/complete.c @@ -89,7 +89,8 @@ void vec_detect_complete_switch(SEXP x, R_len_t size, int* p_out) { case VCTRS_TYPE_raw: raw_detect_complete(x, size, p_out); break; case VCTRS_TYPE_list: list_detect_complete(x, size, p_out); break; case VCTRS_TYPE_dataframe: df_detect_complete(x, size, p_out); break; - case VCTRS_TYPE_scalar: r_stop_internal("Can't detect missing values in scalars."); + case VCTRS_TYPE_null: break; + case VCTRS_TYPE_scalar: stop_scalar_type(x, vec_args.empty, r_lazy_null); default: stop_unimplemented_vctrs_type("vec_detect_complete", vec_proxy_typeof(x)); } } @@ -169,12 +170,31 @@ void list_detect_complete(SEXP x, R_len_t size, int* p_out) { // ----------------------------------------------------------------------------- +static inline void col_detect_complete_switch(SEXP x, R_len_t size, int* p_out); + static inline void df_detect_complete(SEXP x, R_len_t size, int* p_out) { r_ssize n_cols = r_length(x); const SEXP* p_x = VECTOR_PTR_RO(x); for (r_ssize i = 0; i < n_cols; ++i) { - vec_detect_complete_switch(p_x[i], size, p_out); + col_detect_complete_switch(p_x[i], size, p_out); + } +} + +static inline +void col_detect_complete_switch(SEXP x, R_len_t size, int* p_out) { + switch (vec_proxy_typeof(x)) { + case VCTRS_TYPE_logical: lgl_detect_complete(x, size, p_out); break; + case VCTRS_TYPE_integer: int_detect_complete(x, size, p_out); break; + case VCTRS_TYPE_double: dbl_detect_complete(x, size, p_out); break; + case VCTRS_TYPE_complex: cpl_detect_complete(x, size, p_out); break; + case VCTRS_TYPE_character: chr_detect_complete(x, size, p_out); break; + case VCTRS_TYPE_raw: raw_detect_complete(x, size, p_out); break; + case VCTRS_TYPE_list: list_detect_complete(x, size, p_out); break; + case VCTRS_TYPE_dataframe: r_stop_internal("Data frame columns should have been flattened by now."); + case VCTRS_TYPE_null: r_abort("Unexpected `NULL` column found in a data frame."); + case VCTRS_TYPE_scalar: stop_scalar_type(x, vec_args.empty, r_lazy_null); + default: stop_unimplemented_vctrs_type("vec_detect_complete", vec_proxy_typeof(x)); } } diff --git a/tests/testthat/_snaps/complete.md b/tests/testthat/_snaps/complete.md new file mode 100644 index 000000000..954f505fa --- /dev/null +++ b/tests/testthat/_snaps/complete.md @@ -0,0 +1,16 @@ +# catches `NULL` data frame columns + + Code + vec_detect_complete(df) + Condition + Error in `vec_detect_complete()`: + ! Unexpected `NULL` column found in a data frame. + +# catches scalar objects + + Code + vec_detect_complete(lm(1 ~ 1)) + Condition + Error in `vec_size()`: + ! `x` must be a vector, not a object. + diff --git a/tests/testthat/_snaps/rank.md b/tests/testthat/_snaps/rank.md index cc7ceef89..589704f58 100644 --- a/tests/testthat/_snaps/rank.md +++ b/tests/testthat/_snaps/rank.md @@ -1,3 +1,19 @@ +# `x` must not be `NULL` (#1823) + + Code + vec_rank(NULL) + Condition + Error: + ! This type is not supported by `vec_order()`. + +--- + + Code + vec_rank(NULL, incomplete = "na") + Condition + Error: + ! This type is not supported by `vec_order()`. + # `ties` is validated Code diff --git a/tests/testthat/test-complete.R b/tests/testthat/test-complete.R index 0ca0ca4a6..12f4ccfde 100644 --- a/tests/testthat/test-complete.R +++ b/tests/testthat/test-complete.R @@ -113,3 +113,22 @@ test_that("works with arrays", { expect_identical(vec_detect_complete(x), c(TRUE, FALSE)) expect_identical(vec_detect_complete(y), c(TRUE, FALSE)) }) + +test_that("works with `NULL`", { + # Consistent with `vec_detect_missing()` + expect_identical(vec_detect_complete(NULL), logical()) +}) + +test_that("catches `NULL` data frame columns", { + df <- new_data_frame(list(x = integer(), y = NULL), n = 0L) + + expect_snapshot(error = TRUE, { + vec_detect_complete(df) + }) +}) + +test_that("catches scalar objects", { + expect_snapshot(error = TRUE, { + vec_detect_complete(lm(1 ~ 1)) + }) +}) diff --git a/tests/testthat/test-rank.R b/tests/testthat/test-rank.R index 558173e8a..866d0625d 100644 --- a/tests/testthat/test-rank.R +++ b/tests/testthat/test-rank.R @@ -141,6 +141,15 @@ test_that("`x` must be a vector", { expect_error(vec_rank(identity), class = "vctrs_error_scalar_type") }) +test_that("`x` must not be `NULL` (#1823)", { + expect_snapshot(error = TRUE, { + vec_rank(NULL) + }) + expect_snapshot(error = TRUE, { + vec_rank(NULL, incomplete = "na") + }) +}) + test_that("`ties` is validated", { expect_snapshot(error = TRUE, vec_rank(1, ties = "foo")) expect_snapshot(error = TRUE, vec_rank(1, ties = 1)) From 920903d95fb405a5ac6c56c35a2c544c5aa3fa3b Mon Sep 17 00:00:00 2001 From: Hadley Wickham Date: Tue, 14 May 2024 10:31:33 -0500 Subject: [PATCH 310/312] Use parallel tests (#1846) --- DESCRIPTION | 1 + 1 file changed, 1 insertion(+) diff --git a/DESCRIPTION b/DESCRIPTION index 4a175f1c5..b99430bd4 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -43,6 +43,7 @@ VignetteBuilder: knitr Config/Needs/website: tidyverse/tidytemplate Config/testthat/edition: 3 +Config/testthat/parallel: true Encoding: UTF-8 Language: en-GB Roxygen: list(markdown = TRUE) From cf0e08bab3fb9b9bc1dc32514ddc67dc6e656284 Mon Sep 17 00:00:00 2001 From: Davis Vaughan Date: Tue, 27 Aug 2024 10:29:40 -0400 Subject: [PATCH 311/312] Redocument with CRAN roxygen2 Add missing export tag noted by roxygen2 --- DESCRIPTION | 2 +- NAMESPACE | 1 + R/type-vctr.R | 2 ++ man/howto-faq-coercion-data-frame.Rd | 9 +++++---- 4 files changed, 9 insertions(+), 5 deletions(-) diff --git a/DESCRIPTION b/DESCRIPTION index b99430bd4..8299b5bd5 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -47,4 +47,4 @@ Config/testthat/parallel: true Encoding: UTF-8 Language: en-GB Roxygen: list(markdown = TRUE) -RoxygenNote: 7.2.3 +RoxygenNote: 7.3.2 diff --git a/NAMESPACE b/NAMESPACE index 85dd9fe84..8d02a50b0 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -122,6 +122,7 @@ S3method(cnd_header,vctrs_error_subscript_type) S3method(diff,vctrs_vctr) S3method(duplicated,vctrs_sclr) S3method(duplicated,vctrs_vctr) +S3method(format,hidden) S3method(format,vctrs_bytes) S3method(format,vctrs_group_rle) S3method(format,vctrs_list_of) diff --git a/R/type-vctr.R b/R/type-vctr.R index 9770bb9d4..57c964355 100644 --- a/R/type-vctr.R +++ b/R/type-vctr.R @@ -750,6 +750,8 @@ new_hidden <- function(x = double()) { stopifnot(is.numeric(x)) new_vctr(vec_cast(x, double()), class = "hidden", inherit_base_type = FALSE) } + +#' @export format.hidden <- function(x, ...) rep("xxx", length(x)) local_hidden <- function(frame = caller_env()) { diff --git a/man/howto-faq-coercion-data-frame.Rd b/man/howto-faq-coercion-data-frame.Rd index 9e94c7d33..bea380699 100644 --- a/man/howto-faq-coercion-data-frame.Rd +++ b/man/howto-faq-coercion-data-frame.Rd @@ -153,10 +153,11 @@ With these methods vctrs is now able to combine data tables with data frames: \if{html}{\out{
}}\preformatted{vec_cbind(data.frame(x = 1:3), data.table(y = "foo")) -#> x y -#> 1: 1 foo -#> 2: 2 foo -#> 3: 3 foo +#> x y +#> +#> 1: 1 foo +#> 2: 2 foo +#> 3: 3 foo }\if{html}{\out{
}} } From 8d98911aa64e36dbc249cbc8802618638fd0c603 Mon Sep 17 00:00:00 2001 From: Davis Vaughan Date: Tue, 27 Aug 2024 10:31:42 -0400 Subject: [PATCH 312/312] Add `vec_init()` example with lists for tidyverse/dplyr#7076 --- R/slice.R | 5 +++++ man/vec_init.Rd | 5 +++++ 2 files changed, 10 insertions(+) diff --git a/R/slice.R b/R/slice.R index 0c017d42e..c05c33eb1 100644 --- a/R/slice.R +++ b/R/slice.R @@ -235,7 +235,12 @@ vec_index <- function(x, i, ...) { #' @examples #' vec_init(1:10, 3) #' vec_init(Sys.Date(), 5) +#' +#' # The "missing" value for a data frame is a row that is entirely missing #' vec_init(mtcars, 2) +#' +#' # The "missing" value for a list is `NULL` +#' vec_init(list(), 3) vec_init <- function(x, n = 1L) { .Call(ffi_init, x, n, environment()) } diff --git a/man/vec_init.Rd b/man/vec_init.Rd index 4110c15f5..1e217ea76 100644 --- a/man/vec_init.Rd +++ b/man/vec_init.Rd @@ -24,5 +24,10 @@ Initialize a vector \examples{ vec_init(1:10, 3) vec_init(Sys.Date(), 5) + +# The "missing" value for a data frame is a row that is entirely missing vec_init(mtcars, 2) + +# The "missing" value for a list is `NULL` +vec_init(list(), 3) }