From 1276623d542412b8b6c59710effe5b0d0ae5594a Mon Sep 17 00:00:00 2001 From: Hadley Wickham Date: Mon, 12 Sep 2022 17:22:11 -0500 Subject: [PATCH] Rework simplification (#909) Introduce new `list_simplify()` which provides vctrs based simplifcation. This is used to power a new `list_transpose()` and `accumulate()`/`accumulate2()`. * Fixes #875 by introducing `list_transpose()` * Fixes #809 by allowing `accumulate()` to opt out of simplification. * Fixes #774 by aligning `accumulate()` and `accumulate2()` semantics. * Fixes #900 by concluding the flatten/simplification re-alignment. --- NAMESPACE | 2 + NEWS.md | 17 ++- R/coercion.R | 58 +++++----- R/list-simplify.R | 90 ++++++++++++++++ R/list-transpose.R | 136 ++++++++++++++++++++++++ R/reduce.R | 26 ++--- R/transpose.R | 30 ++++-- R/utils.R | 16 --- _pkgdown.yml | 4 +- man/accumulate.Rd | 22 +++- man/as_vector.Rd | 44 ++++---- man/lift.Rd | 9 +- man/list_simplify.Rd | 33 ++++++ man/list_transpose.Rd | 78 ++++++++++++++ man/transpose.Rd | 31 ++++-- tests/testthat/_snaps/coercion.md | 21 ++++ tests/testthat/_snaps/list-simplify.md | 66 ++++++++++++ tests/testthat/_snaps/list-transpose.md | 66 ++++++++++++ tests/testthat/_snaps/reduce.md | 8 ++ tests/testthat/_snaps/transpose.md | 9 ++ tests/testthat/test-coercion.R | 13 +++ tests/testthat/test-list-simplify.R | 38 +++++++ tests/testthat/test-list-transpose.R | 132 +++++++++++++++++++++++ tests/testthat/test-reduce.R | 22 ++-- tests/testthat/test-transpose.R | 37 +++++++ tests/testthat/test-utils.R | 24 ----- 26 files changed, 886 insertions(+), 146 deletions(-) create mode 100644 R/list-simplify.R create mode 100644 R/list-transpose.R create mode 100644 man/list_simplify.Rd create mode 100644 man/list_transpose.Rd create mode 100644 tests/testthat/_snaps/coercion.md create mode 100644 tests/testthat/_snaps/list-simplify.md create mode 100644 tests/testthat/_snaps/list-transpose.md create mode 100644 tests/testthat/_snaps/transpose.md create mode 100644 tests/testthat/test-list-simplify.R create mode 100644 tests/testthat/test-list-transpose.R diff --git a/NAMESPACE b/NAMESPACE index a643fa0d..1c0fc0bb 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -134,6 +134,8 @@ export(list_flatten) export(list_merge) export(list_modify) export(list_rbind) +export(list_simplify) +export(list_transpose) export(list_update) export(lmap) export(lmap_at) diff --git a/NEWS.md b/NEWS.md index 65ce6663..1654ca66 100644 --- a/NEWS.md +++ b/NEWS.md @@ -37,6 +37,13 @@ * `*_dfc()` and `*_dfr()` have been deprecated in favour of using the appropriate map function along with `list_rbind()` or `list_cbind()` (#912). +* `simplify()`, `simplify_all()`, and `as_vector()` have been deprecated in + favour of `list_simplify()`. It provides a more consistent definition of + simplification (#900). + +* `transpose()` has been deprecated in favour of `list_transpose()` (#875). + It has built-in simplification. + ### Deprecation next steps * `as_function()`, `at_depth()`, and the `...f` argument to `partial()` @@ -70,8 +77,14 @@ * New `list_c()`, `list_rbind()`, and `list_cbind()` make it easy to `c()`, `rbind()`, or `cbind()` all of the elements in a list. -* `accumulate()` now uses vctrs for simplifying the output. This - ensures a more principled and flexible coercion behaviour. +* New `list_simplify()` reduces a list of length-1 vectors to a simpler atomic + or S3 vector (#900). + +* New `list_transpose()` which automatically simplifies if possible (#875). + +* `accumulate()` and `accumulate2()` now both simplify the output if possible + using vctrs. New arguments `simplify` and `ptype` allow you to control the + details of simplification (#774, #809). ### Tidyverse consistency diff --git a/R/coercion.R b/R/coercion.R index fee9fdd1..2b0186a9 100644 --- a/R/coercion.R +++ b/R/coercion.R @@ -1,38 +1,35 @@ #' Coerce a list to a vector #' -#' `as_vector()` collapses a list of vectors into one vector. It -#' checks that the type of each vector is consistent with -#' `.type`. If the list can not be simplified, it throws an error. -#' `simplify` will simplify a vector if possible; `simplify_all` -#' will apply `simplify` to every element of a list. +#' @description +#' `r lifecycle::badge("deprecated")` #' -#' `.type` can be a vector mold specifying both the type and the -#' length of the vectors to be concatenated, such as `numeric(1)` -#' or `integer(4)`. Alternatively, it can be a string describing -#' the type, one of: "logical", "integer", "double", "complex", -#' "character" or "raw". +#' These functions are deprecated in favour of `list_simplify()`: +#' +#' * `as_vector(x)` is now `list_simplify(x)` +#' * `simplify(x)` is now `list_simplify(x, strict = FALSE)` +#' * `simplify_all(x)` is `map(x, list_simplify, strict = FALSE)` #' #' @param .x A list of vectors -#' @param .type A vector mold or a string describing the type of the -#' input vectors. The latter can be any of the types returned by -#' [typeof()], or "numeric" as a shorthand for either -#' "double" or "integer". +#' @param .type Can be a vector mold specifying both the type and the +#' length of the vectors to be concatenated, such as `numeric(1)` +#' or `integer(4)`. Alternatively, it can be a string describing +#' the type, one of: "logical", "integer", "double", "complex", +#' "character" or "raw". #' @export +#' @keywords internal #' @examples -#' # Supply the type either with a string: +#' # was #' as.list(letters) %>% as_vector("character") +#' # now +#' as.list(letters) %>% list_simplify(ptype = character()) #' -#' # Or with a vector mold: -#' as.list(letters) %>% as_vector(character(1)) -#' -#' # Vector molds are more flexible because they also specify the -#' # length of the concatenated vectors: +#' # was: #' list(1:2, 3:4, 5:6) %>% as_vector(integer(2)) -#' -#' # Note that unlike vapply(), as_vector() never adds dimension -#' # attributes. So when you specify a vector mold of size > 1, you -#' # always get a vector and not a matrix +#' # now: +#' list(1:2, 3:4, 5:6) %>% list_c(ptype = integer()) as_vector <- function(.x, .type = NULL) { + lifecycle::deprecate_warn("0.4.0", "as_vector()", "list_simplify()") + if (can_simplify(.x, .type)) { unlist(.x) } else { @@ -43,6 +40,7 @@ as_vector <- function(.x, .type = NULL) { #' @export #' @rdname as_vector simplify <- function(.x, .type = NULL) { + lifecycle::deprecate_warn("0.4.0", "as_vector()", "list_simplify()") if (can_simplify(.x, .type)) { unlist(.x) } else { @@ -53,7 +51,17 @@ simplify <- function(.x, .type = NULL) { #' @export #' @rdname as_vector simplify_all <- function(.x, .type = NULL) { - map(.x, simplify, .type = .type) + lifecycle::deprecate_warn("0.4.0", "as_vector()", I("map() + list_simplify()")) + + # Inline simplify to avoid double deprecation + simplify <- function(.x) { + if (can_simplify(.x, .type)) { + unlist(.x) + } else { + .x + } + } + map(.x, simplify) } diff --git a/R/list-simplify.R b/R/list-simplify.R new file mode 100644 index 00000000..aa98a37e --- /dev/null +++ b/R/list-simplify.R @@ -0,0 +1,90 @@ +#' Simplify a list to an atomic or S3 vector +#' +#' Simplification maintains a one-to-one correspondence between the input +#' and output, implying that each element of `x` must contain a vector of +#' length 1. If you don't want to maintain this correspondence, then you +#' probably want either [list_c()] or [list_flatten()]. +#' +#' @param x A list. +#' @param strict What should happen if simplification fails? If `TRUE`, +#' it will error. If `FALSE` and `ptype` is not supplied, it will return `x` +#' unchanged. +#' @param ptype An optional prototype to ensure that the output type is always +#' the same. +#' @returns A vector the same length as `x`. +#' @export +#' @examples +#' list_simplify(list(1, 2, 3)) +#' +#' try(list_simplify(list(1, 2, "x"))) +#' try(list_simplify(list(1, 2, 1:3))) +list_simplify <- function(x, strict = TRUE, ptype = NULL) { + if (!is_bool(strict)) { + cli::cli_abort( + "{.arg strict} must be `TRUE` or `FALSE`, not {.obj_type_friendly {strict}}." + ) + } + + simplify_impl(x, strict = strict, ptype = ptype) +} + +# Wrapper used by purrr functions that do automatic simplification +list_simplify_internal <- function(x, + simplify = NA, + ptype = NULL, + error_call = caller_env()) { + if (length(simplify) > 1 || !is.logical(simplify)) { + cli::cli_abort( + "{.arg simplify} must be `TRUE`, `FALSE`, or `NA`.", + arg = "simplify", + call = error_call + ) + } + if (!is.null(ptype) && isFALSE(simplify)) { + cli::cli_abort( + "Can't specify {.arg ptype} when `simplify = FALSE`.", + arg = "ptype", + call = error_call + ) + } + + if (isFALSE(simplify)) { + return(x) + } + + simplify_impl( + x, + strict = !is.na(simplify), + ptype = ptype, + error_call = error_call + ) +} + +simplify_impl <- function(x, + strict = TRUE, + ptype = NULL, + error_call = caller_env()) { + vec_check_list(x, call = error_call) + + can_simplify <- every(x, vec_is, size = 1) + + if (can_simplify) { + tryCatch( + # TODO: use `error_call` when available + list_unchop(x, ptype = ptype), + vctrs_error_incompatible_type = function(err) { + if (strict || !is.null(ptype)) { + cnd_signal(err) + } else { + x + } + } + ) + } else { + if (strict) { + cli::cli_abort("All elements must be length-1 vectors.", call = error_call) + } else { + x + } + } +} diff --git a/R/list-transpose.R b/R/list-transpose.R new file mode 100644 index 00000000..b2f0cd51 --- /dev/null +++ b/R/list-transpose.R @@ -0,0 +1,136 @@ +#' Transpose a list +#' +#' @description +#' `list_transpose()` turns a list-of-lists "inside-out". For instance it turns a pair of +#' lists into a list of pairs, or a list of pairs into a pair of lists. For +#' example, if you had a list of length `n` where each component had values `a` +#' and `b`, `list_transpose()` would make a list with elements `a` and +#' `b` that contained lists of length `n`. +#' +#' It's called transpose because `x[["a"]][["b"]]` is equivalent to +#' `list_transpose(x)[["b"]][["a"]]`, i.e. transposing a list flips the order of +#' indices in a similar way to transposing a matrix. +#' +#' @param x A list of vectors to transpose. +#' @param template A "template" that describes the output list. Can either be +#' a character vector (where elements are extracted by name), or an integer +#' vector (where elements are extracted by position). Defaults to the names +#' of the first element of `x`, or if they're not present, the integer +#' indices. +#' @param simplify Should the result be [simplified][list_simplify]? +#' * `TRUE`: simplify or die trying. +#' * `NA`: simplify if possible. +#' * `FALSE`: never try to simplify, always leaving as a list. +#' +#' Alternatively, a named list specifying the simplification by output +#' element. +#' @param ptype An optional vector prototype used to control the simplification. +#' Alternatively, a named list specifying the prototype by output element. +#' @param default A default value to use if a value is absent or `NULL`. +#' Alternatively, a named list specifying the default by output element. +#' @export +#' @examples +#' # list_transpose() is useful in conjunction with safely() +#' x <- list("a", 1, 2) +#' y <- x %>% map(safely(log)) +#' y %>% str() +#' # Put all the errors and results together +#' y %>% list_transpose() %>% str() +#' # Supply a default result to further simplify +#' y %>% list_transpose(default = list(result = NA)) %>% str() +#' +#' # list_transpose() will try to simplify by default: +#' x <- list(list(a = 1, b = 2), list(a = 3, b = 4), list(a = 5, b = 6)) +#' x %>% list_transpose() +#' # this makes list_tranpose() not completely symmetric +#' x %>% list_transpose() %>% list_transpose() +#' +#' # use simplify = FALSE to always return lists: +#' x %>% list_transpose(simplify = FALSE) %>% str() +#' x %>% +#' list_transpose(simplify = FALSE) %>% +#' list_transpose(simplify = FALSE) %>% str() +#' +#' # Provide an explicit template if you know which elements you want to extract +#' ll <- list( +#' list(x = 1, y = "one"), +#' list(z = "deux", x = 2) +#' ) +#' ll %>% list_transpose() +#' ll %>% list_transpose(template = c("x", "y", "z")) +#' ll %>% list_transpose(template = 1) +#' +#' # And specify a default if you want to simplify +#' ll %>% list_transpose(c("x", "y", "z"), default = NA) +list_transpose <- function(x, template = NULL, simplify = NA, ptype = NULL, default = NULL) { + vec_check_list(x) + + if (length(x) == 0) { + template <- integer() + } else { + template <- template %||% vec_index(x[[1]]) + } + + if (!is.character(template) && !is.numeric(template)) { + cli::cli_abort( + "{.arg template} must be a character or numeric vector, not {.obj_type_friendly {template}}.", + arg = template + ) + } + + simplify <- match_template(simplify, template) + default <- match_template(default, template) + ptype <- match_template(ptype, template) + + out <- rep_along(template, list()) + if (is.character(template)) { + names(out) <- template + } + + for (i in seq_along(template)) { + idx <- template[[i]] + res <- map(x, idx, .default = default[[i]]) + res <- list_simplify_internal(res, + simplify = simplify[[i]] %||% NA, + ptype = ptype[[i]] + ) + out[[i]] <- res + } + + out +} + +match_template <- function(x, template, error_arg = caller_arg(x), error_call = caller_env()) { + if (is.character(template)) { + if (is_bare_list(x) && is_named(x)) { + extra_names <- setdiff(names(x), template) + if (length(extra_names)) { + cli::cli_abort( + "{.arg {error_arg}} contains unknown names: {.str {extra_names}}.", + arg = error_arg, + call = error_call + ) + } + + out <- rep_named(template, list(NULL)) + out[names(x)] <- x + out + } else { + rep_named(template, list(x)) + } + } else if (is.numeric(template)) { + if (is_bare_list(x) && length(x) > 0) { + if (length(x) != length(template)) { + cli::cli_abort( + "Length of {.arg {error_arg}} ({length(x)}) and {.arg template} ({length(template)}) must be the same when transposing by position.", + call = error_call + ) + } + x + } else { + rep_along(template, list(x)) + } + } else { + abort("Invalid `template`", .internal = TRUE) + } +} diff --git a/R/reduce.R b/R/reduce.R index 62a76ae8..8f2b912a 100644 --- a/R/reduce.R +++ b/R/reduce.R @@ -342,11 +342,15 @@ seq_len2 <- function(start, end) { #' the accumulation, rather than using `.x[[1]]`. This is useful if #' you want to ensure that `reduce` returns a correct value when `.x` #' is empty. If missing, and `.x` is empty, will throw an error. -#' #' @param .dir The direction of accumulation as a string, one of #' `"forward"` (the default) or `"backward"`. See the section about #' direction below. -#' +#' @param .simplify If `NA`, the default, the accumulated list of +#' results is simplified to an atomic vector if possible. +#' If `TRUE`, the result is simplified, erroring if not possible. +#' If `FALSE`, the result is not simplified, always returning a list. +#' @param .ptype If `simplify` is `NA` or `TRUE`, optionally supply a vector +#' prototype to enforce the output type. #' @return A vector the same length of `.x` with the same names as `.x`. #' #' If `.init` is supplied, the length is extended by 1. If `.x` has @@ -454,26 +458,22 @@ seq_len2 <- function(start, end) { #' ggtitle("Simulations of a random walk with drift") #' } #' @export -accumulate <- function(.x, .f, ..., .init, .dir = c("forward", "backward")) { +accumulate <- function(.x, .f, ..., .init, .dir = c("forward", "backward"), .simplify = NA, .ptype = NULL) { .dir <- arg_match(.dir, c("forward", "backward")) .f <- as_mapper(.f, ...) res <- reduce_impl(.x, .f, ..., .init = .init, .dir = .dir, .acc = TRUE) names(res) <- accumulate_names(names(.x), .init, .dir) - # It would be unappropriate to simplify the result rowwise with - # `accumulate()` because it has invariants defined in terms of - # `length()` rather than `vec_size()` - if (some(res, is.data.frame)) { - res - } else { - vec_simplify(res) - } + res <- list_simplify_internal(res, .simplify, .ptype) + res } #' @rdname accumulate #' @export -accumulate2 <- function(.x, .y, .f, ..., .init) { - reduce2_impl(.x, .y, .f, ..., .init = .init, .acc = TRUE) +accumulate2 <- function(.x, .y, .f, ..., .init, .simplify = NA, .ptype = NULL) { + res <- reduce2_impl(.x, .y, .f, ..., .init = .init, .acc = TRUE) + res <- list_simplify_internal(res, .simplify, .ptype) + res } accumulate_names <- function(nms, init, dir) { diff --git a/R/transpose.R b/R/transpose.R index 360e000d..8bb890ea 100644 --- a/R/transpose.R +++ b/R/transpose.R @@ -1,5 +1,11 @@ #' Transpose a list. #' +#' @description +#' `r lifecycle::badge("deprecated")` +#' +#' Please use [list_transpose()] instead of `transpose()`. It has a better name, +#' and can now automatically simplify the output, as is commonly needed. +#' #' Transpose turns a list-of-lists "inside-out"; it turns a pair of lists into a #' list of pairs, or a list of pairs into pair of lists. For example, #' if you had a list of length n where each component had values `a` and @@ -17,24 +23,28 @@ #' @param .names For efficiency, `transpose()` bases the return structure on #' the first component of `.l` by default. Specify `.names` to override this. #' @return A list with indexing transposed compared to `.l`. +#' @keywords internal #' @export #' @examples -#' x <- rerun(5, x = runif(1), y = runif(5)) -#' x %>% str() +#' x <- map(1:5, ~ list(x = runif(1), y = runif(5))) +#' # was #' x %>% transpose() %>% str() -#' # Back to where we started -#' x %>% transpose() %>% transpose() %>% str() +#' # now +#' x %>% list_transpose(simplify = FALSE) %>% str() #' #' # transpose() is useful in conjunction with safely() & quietly() #' x <- list("a", 1, 2) #' y <- x %>% map(safely(log)) -#' y %>% str() +#' # was #' y %>% transpose() %>% str() +#' # now: +#' y %>% list_transpose() %>% str() #' -#' # Use simplify_all() to reduce to atomic vectors where possible +#' # Previously, output simplification required a call to another function #' x <- list(list(a = 1, b = 2), list(a = 3, b = 4), list(a = 5, b = 6)) -#' x %>% transpose() #' x %>% transpose() %>% simplify_all() +#' # Now can take advantage of automatic simplification +#' x %>% list_transpose() #' #' # Provide explicit component names to prevent loss of those that don't #' # appear in first component @@ -44,7 +54,13 @@ #' ) #' ll %>% transpose() #' nms <- ll %>% map(names) %>% reduce(union) +#' # was #' ll %>% transpose(.names = nms) +#' # now +#' ll %>% list_transpose(template = nms) +#' # and can supply default value +#' ll %>% list_transpose(template = nms, default = NA) transpose <- function(.l, .names = NULL) { + lifecycle::deprecate_warn("0.4.0", "transpose()", "list_transpose()") .Call(transpose_impl, .l, .names) } diff --git a/R/utils.R b/R/utils.R index d44429c6..70419165 100644 --- a/R/utils.R +++ b/R/utils.R @@ -182,19 +182,3 @@ friendly_type_of_element <- function(x) { abort("Expected a base vector type") ) } - - -vec_simplify <- function(x) { - if (!vctrs::vec_is_list(x)) { - return(x) - } - if (!every(x, ~ vctrs::vec_is(.x) && vctrs::vec_size(.x) == 1L)) { - return(x) - } - - tryCatch( - vctrs_error_incompatible_type = function(...) x, - vctrs::vec_c(!!!x) - ) -} - diff --git a/_pkgdown.yml b/_pkgdown.yml index ffc3712d..f3c4f6b9 100644 --- a/_pkgdown.yml +++ b/_pkgdown.yml @@ -84,8 +84,9 @@ reference: - list_c - list_flatten - list_modify + - list_simplify + - list_transpose - reduce - - transpose - title: Adverbs desc: > @@ -97,6 +98,5 @@ reference: - title: Misc contents: - array_tree - - as_vector - rate-helpers - progress_bars diff --git a/man/accumulate.Rd b/man/accumulate.Rd index 7b1e0ed5..9d0bed43 100644 --- a/man/accumulate.Rd +++ b/man/accumulate.Rd @@ -5,9 +5,17 @@ \alias{accumulate2} \title{Accumulate intermediate results of a vector reduction} \usage{ -accumulate(.x, .f, ..., .init, .dir = c("forward", "backward")) - -accumulate2(.x, .y, .f, ..., .init) +accumulate( + .x, + .f, + ..., + .init, + .dir = c("forward", "backward"), + .simplify = NA, + .ptype = NULL +) + +accumulate2(.x, .y, .f, ..., .init, .simplify = NA, .ptype = NULL) } \arguments{ \item{.x}{A list or atomic vector.} @@ -38,6 +46,14 @@ is empty. If missing, and \code{.x} is empty, will throw an error.} \code{"forward"} (the default) or \code{"backward"}. See the section about direction below.} +\item{.simplify}{If \code{NA}, the default, the accumulated list of +results is simplified to an atomic vector if possible. +If \code{TRUE}, the result is simplified, erroring if not possible. +If \code{FALSE}, the result is not simplified, always returning a list.} + +\item{.ptype}{If \code{simplify} is \code{NA} or \code{TRUE}, optionally supply a vector +prototype to enforce the output type.} + \item{.y}{For \code{accumulate2()} \code{.y} is the second argument of the pair. It needs to be 1 element shorter than the vector to be accumulated (\code{.x}). If \code{.init} is set, \code{.y} needs to be one element shorted than the diff --git a/man/as_vector.Rd b/man/as_vector.Rd index 84038d45..12e6ab5d 100644 --- a/man/as_vector.Rd +++ b/man/as_vector.Rd @@ -15,37 +15,31 @@ simplify_all(.x, .type = NULL) \arguments{ \item{.x}{A list of vectors} -\item{.type}{A vector mold or a string describing the type of the -input vectors. The latter can be any of the types returned by -\code{\link[=typeof]{typeof()}}, or "numeric" as a shorthand for either -"double" or "integer".} -} -\description{ -\code{as_vector()} collapses a list of vectors into one vector. It -checks that the type of each vector is consistent with -\code{.type}. If the list can not be simplified, it throws an error. -\code{simplify} will simplify a vector if possible; \code{simplify_all} -will apply \code{simplify} to every element of a list. -} -\details{ -\code{.type} can be a vector mold specifying both the type and the +\item{.type}{Can be a vector mold specifying both the type and the length of the vectors to be concatenated, such as \code{numeric(1)} or \code{integer(4)}. Alternatively, it can be a string describing the type, one of: "logical", "integer", "double", "complex", -"character" or "raw". +"character" or "raw".} +} +\description{ +\ifelse{html}{\href{https://lifecycle.r-lib.org/articles/stages.html#deprecated}{\figure{lifecycle-deprecated.svg}{options: alt='[Deprecated]'}}}{\strong{[Deprecated]}} + +These functions are deprecated in favour of \code{list_simplify()}: +\itemize{ +\item \code{as_vector(x)} is now \code{list_simplify(x)} +\item \code{simplify(x)} is now \code{list_simplify(x, strict = FALSE)} +\item \code{simplify_all(x)} is \code{map(x, list_simplify, strict = FALSE)} +} } \examples{ -# Supply the type either with a string: +# was as.list(letters) \%>\% as_vector("character") +# now +as.list(letters) \%>\% list_simplify(ptype = character()) -# Or with a vector mold: -as.list(letters) \%>\% as_vector(character(1)) - -# Vector molds are more flexible because they also specify the -# length of the concatenated vectors: +# was: list(1:2, 3:4, 5:6) \%>\% as_vector(integer(2)) - -# Note that unlike vapply(), as_vector() never adds dimension -# attributes. So when you specify a vector mold of size > 1, you -# always get a vector and not a matrix +# now: +list(1:2, 3:4, 5:6) \%>\% list_c(ptype = integer()) } +\keyword{internal} diff --git a/man/lift.Rd b/man/lift.Rd index 584bb649..b80e6132 100644 --- a/man/lift.Rd +++ b/man/lift.Rd @@ -35,10 +35,11 @@ name the parameters in the lifted function signature. This prevents matching of arguments by name and match by position instead.} -\item{.type}{A vector mold or a string describing the type of the -input vectors. The latter can be any of the types returned by -\code{\link[=typeof]{typeof()}}, or "numeric" as a shorthand for either -"double" or "integer".} +\item{.type}{Can be a vector mold specifying both the type and the +length of the vectors to be concatenated, such as \code{numeric(1)} +or \code{integer(4)}. Alternatively, it can be a string describing +the type, one of: "logical", "integer", "double", "complex", +"character" or "raw".} } \value{ A function. diff --git a/man/list_simplify.Rd b/man/list_simplify.Rd new file mode 100644 index 00000000..a113fb71 --- /dev/null +++ b/man/list_simplify.Rd @@ -0,0 +1,33 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/list-simplify.R +\name{list_simplify} +\alias{list_simplify} +\title{Simplify a list to an atomic or S3 vector} +\usage{ +list_simplify(x, strict = TRUE, ptype = NULL) +} +\arguments{ +\item{x}{A list.} + +\item{strict}{What should happen if simplification fails? If \code{TRUE}, +it will error. If \code{FALSE} and \code{ptype} is not supplied, it will return \code{x} +unchanged.} + +\item{ptype}{An optional prototype to ensure that the output type is always +the same.} +} +\value{ +A vector the same length as \code{x}. +} +\description{ +Simplification maintains a one-to-one correspondence between the input +and output, implying that each element of \code{x} must contain a vector of +length 1. If you don't want to maintain this correspondence, then you +probably want either \code{\link[=list_c]{list_c()}} or \code{\link[=list_flatten]{list_flatten()}}. +} +\examples{ +list_simplify(list(1, 2, 3)) + +try(list_simplify(list(1, 2, "x"))) +try(list_simplify(list(1, 2, 1:3))) +} diff --git a/man/list_transpose.Rd b/man/list_transpose.Rd new file mode 100644 index 00000000..ee0a5e11 --- /dev/null +++ b/man/list_transpose.Rd @@ -0,0 +1,78 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/list-transpose.R +\name{list_transpose} +\alias{list_transpose} +\title{Transpose a list} +\usage{ +list_transpose(x, template = NULL, simplify = NA, ptype = NULL, default = NULL) +} +\arguments{ +\item{x}{A list of vectors to transpose.} + +\item{template}{A "template" that describes the output list. Can either be +a character vector (where elements are extracted by name), or an integer +vector (where elements are extracted by position). Defaults to the names +of the first element of \code{x}, or if they're not present, the integer +indices.} + +\item{simplify}{Should the result be \link[=list_simplify]{simplified}? +\itemize{ +\item \code{TRUE}: simplify or die trying. +\item \code{NA}: simplify if possible. +\item \code{FALSE}: never try to simplify, always leaving as a list. +} + +Alternatively, a named list specifying the simplification by output +element.} + +\item{ptype}{An optional vector prototype used to control the simplification. +Alternatively, a named list specifying the prototype by output element.} + +\item{default}{A default value to use if a value is absent or \code{NULL}. +Alternatively, a named list specifying the default by output element.} +} +\description{ +\code{list_transpose()} turns a list-of-lists "inside-out". For instance it turns a pair of +lists into a list of pairs, or a list of pairs into a pair of lists. For +example, if you had a list of length \code{n} where each component had values \code{a} +and \code{b}, \code{list_transpose()} would make a list with elements \code{a} and +\code{b} that contained lists of length \code{n}. + +It's called transpose because \code{x[["a"]][["b"]]} is equivalent to +\code{list_transpose(x)[["b"]][["a"]]}, i.e. transposing a list flips the order of +indices in a similar way to transposing a matrix. +} +\examples{ +# list_transpose() is useful in conjunction with safely() +x <- list("a", 1, 2) +y <- x \%>\% map(safely(log)) +y \%>\% str() +# Put all the errors and results together +y \%>\% list_transpose() \%>\% str() +# Supply a default result to further simplify +y \%>\% list_transpose(default = list(result = NA)) \%>\% str() + +# list_transpose() will try to simplify by default: +x <- list(list(a = 1, b = 2), list(a = 3, b = 4), list(a = 5, b = 6)) +x \%>\% list_transpose() +# this makes list_tranpose() not completely symmetric +x \%>\% list_transpose() \%>\% list_transpose() + +# use simplify = FALSE to always return lists: +x \%>\% list_transpose(simplify = FALSE) \%>\% str() +x \%>\% + list_transpose(simplify = FALSE) \%>\% + list_transpose(simplify = FALSE) \%>\% str() + +# Provide an explicit template if you know which elements you want to extract +ll <- list( + list(x = 1, y = "one"), + list(z = "deux", x = 2) +) +ll \%>\% list_transpose() +ll \%>\% list_transpose(template = c("x", "y", "z")) +ll \%>\% list_transpose(template = 1) + +# And specify a default if you want to simplify +ll \%>\% list_transpose(c("x", "y", "z"), default = NA) +} diff --git a/man/transpose.Rd b/man/transpose.Rd index adc2d5ed..b523a4aa 100644 --- a/man/transpose.Rd +++ b/man/transpose.Rd @@ -18,35 +18,42 @@ the first component of \code{.l} by default. Specify \code{.names} to override t A list with indexing transposed compared to \code{.l}. } \description{ +\ifelse{html}{\href{https://lifecycle.r-lib.org/articles/stages.html#deprecated}{\figure{lifecycle-deprecated.svg}{options: alt='[Deprecated]'}}}{\strong{[Deprecated]}} + +Please use \code{\link[=list_transpose]{list_transpose()}} instead of \code{transpose()}. It has a better name, +and can now automatically simplify the output, as is commonly needed. + Transpose turns a list-of-lists "inside-out"; it turns a pair of lists into a list of pairs, or a list of pairs into pair of lists. For example, if you had a list of length n where each component had values \code{a} and \code{b}, \code{transpose()} would make a list with elements \code{a} and \code{b} that contained lists of length n. It's called transpose because \code{x[[1]][[2]]} is equivalent to \code{transpose(x)[[2]][[1]]}. -} -\details{ + Note that \code{transpose()} is its own inverse, much like the transpose operation on a matrix. You can get back the original input by transposing it twice. } \examples{ -x <- rerun(5, x = runif(1), y = runif(5)) -x \%>\% str() +x <- map(1:5, ~ list(x = runif(1), y = runif(5))) +# was x \%>\% transpose() \%>\% str() -# Back to where we started -x \%>\% transpose() \%>\% transpose() \%>\% str() +# now +x \%>\% list_transpose(simplify = FALSE) \%>\% str() # transpose() is useful in conjunction with safely() & quietly() x <- list("a", 1, 2) y <- x \%>\% map(safely(log)) -y \%>\% str() +# was y \%>\% transpose() \%>\% str() +# now: +y \%>\% list_transpose() \%>\% str() -# Use simplify_all() to reduce to atomic vectors where possible +# Previously, output simplification required a call to another function x <- list(list(a = 1, b = 2), list(a = 3, b = 4), list(a = 5, b = 6)) -x \%>\% transpose() x \%>\% transpose() \%>\% simplify_all() +# Now can take advantage of automatic simplification +x \%>\% list_transpose() # Provide explicit component names to prevent loss of those that don't # appear in first component @@ -56,5 +63,11 @@ ll <- list( ) ll \%>\% transpose() nms <- ll \%>\% map(names) \%>\% reduce(union) +# was ll \%>\% transpose(.names = nms) +# now +ll \%>\% list_transpose(template = nms) +# and can supply default value +ll \%>\% list_transpose(template = nms, default = NA) } +\keyword{internal} diff --git a/tests/testthat/_snaps/coercion.md b/tests/testthat/_snaps/coercion.md new file mode 100644 index 00000000..742c61aa --- /dev/null +++ b/tests/testthat/_snaps/coercion.md @@ -0,0 +1,21 @@ +# old simplification functions are deprecated + + Code + . <- as_vector(list(1, 2)) + Condition + Warning: + `as_vector()` was deprecated in purrr 0.4.0. + Please use `list_simplify()` instead. + Code + . <- simplify(list(1, 2)) + Condition + Warning: + `as_vector()` was deprecated in purrr 0.4.0. + Please use `list_simplify()` instead. + Code + . <- simplify_all(list(1, 2)) + Condition + Warning: + `as_vector()` was deprecated in purrr 0.4.0. + Please use map() + list_simplify() instead. + diff --git a/tests/testthat/_snaps/list-simplify.md b/tests/testthat/_snaps/list-simplify.md new file mode 100644 index 00000000..b4fee48a --- /dev/null +++ b/tests/testthat/_snaps/list-simplify.md @@ -0,0 +1,66 @@ +# ptype is enforced + + Code + list_simplify(list(1, 2), ptype = character()) + Condition + Error: + ! Can't convert to . + +--- + + Code + list_simplify(list(1, 2), ptype = character(), strict = FALSE) + Condition + Error: + ! Can't convert to . + +# strict simplification will error + + Code + list_simplify(list(1, "a")) + Condition + Error: + ! Can't combine `..1` and `..2` . + Code + list_simplify(list(1, 1:2)) + Condition + Error in `list_simplify()`: + ! All elements must be length-1 vectors. + Code + list_simplify(list(1, 2), ptype = character()) + Condition + Error: + ! Can't convert to . + +# validates inputs + + Code + list_simplify_internal(1:5) + Condition + Error: + ! `x` must be a list, not an integer vector. + +--- + + Code + list_simplify_internal(list(), simplify = 1) + Condition + Error: + ! `simplify` must be `TRUE`, `FALSE`, or `NA`. + +--- + + Code + list_simplify_internal(list(), simplify = FALSE, ptype = integer()) + Condition + Error: + ! Can't specify `ptype` when `simplify = FALSE`. + +--- + + Code + list_simplify(list(), strict = NA) + Condition + Error in `list_simplify()`: + ! `strict` must be `TRUE` or `FALSE`, not `NA`. + diff --git a/tests/testthat/_snaps/list-transpose.md b/tests/testthat/_snaps/list-transpose.md new file mode 100644 index 00000000..aa8b5ebf --- /dev/null +++ b/tests/testthat/_snaps/list-transpose.md @@ -0,0 +1,66 @@ +# integer template requires exact length of list() simplify etc + + Code + list_transpose(x, ptype = list()) + Condition + Error: + ! Can't convert to . + +--- + + Code + list_transpose(x, ptype = list(integer())) + Condition + Error in `list_transpose()`: + ! Length of `ptype` (1) and `template` (2) must be the same when transposing by position. + +# simplification fails silently unless requested + + Code + list_transpose(list(list(x = 1), list(x = "b")), simplify = TRUE) + Condition + Error: + ! Can't combine `..1` and `..2` . + Code + list_transpose(list(list(x = 1), list(x = 2:3)), simplify = TRUE) + Condition + Error in `list_transpose()`: + ! All elements must be length-1 vectors. + +# can supply `simplify` globally or individually + + Code + list_transpose(x, simplify = list(c = FALSE)) + Condition + Error in `list_transpose()`: + ! `simplify` contains unknown names: "c". + +# can supply `ptype` globally or individually + + Code + list_transpose(x, ptype = list(c = integer())) + Condition + Error in `list_transpose()`: + ! `ptype` contains unknown names: "c". + +# can supply `default` globally or individually + + Code + list_transpose(x, default = list(c = NA)) + Condition + Error in `list_transpose()`: + ! `default` contains unknown names: "c". + +# validates inputs + + Code + list_transpose(10) + Condition + Error in `list_transpose()`: + ! `x` must be a list, not a number. + Code + list_transpose(list(1), template = mean) + Condition + Error in `list_transpose()`: + ! `template` must be a character or numeric vector, not a function. + diff --git a/tests/testthat/_snaps/reduce.md b/tests/testthat/_snaps/reduce.md index b6990a10..f178ae9b 100644 --- a/tests/testthat/_snaps/reduce.md +++ b/tests/testthat/_snaps/reduce.md @@ -1,3 +1,11 @@ +# accumulate() does fail when simpification is required + + Code + accumulate(list(1, "a"), ~.y, .simplify = TRUE) + Condition + Error: + ! Can't combine `..1` and `..2` . + # right variants are retired Code diff --git a/tests/testthat/_snaps/transpose.md b/tests/testthat/_snaps/transpose.md new file mode 100644 index 00000000..6e86dcd2 --- /dev/null +++ b/tests/testthat/_snaps/transpose.md @@ -0,0 +1,9 @@ +# transpose() is deprecated + + Code + . <- transpose(list()) + Condition + Warning: + `transpose()` was deprecated in purrr 0.4.0. + Please use `list_transpose()` instead. + diff --git a/tests/testthat/test-coercion.R b/tests/testthat/test-coercion.R index ecf9aacb..44d634bc 100644 --- a/tests/testthat/test-coercion.R +++ b/tests/testthat/test-coercion.R @@ -1,8 +1,21 @@ +test_that("old simplification functions are deprecated", { + expect_snapshot({ + . <- as_vector(list(1, 2)) + . <- simplify(list(1, 2)) + . <- simplify_all(list(1, 2)) + }) +}) + + test_that("as_vector can be type-specifc", { + local_options(lifecycle_verbosity = "quiet") + expect_identical(as_vector(as.list(letters), "character"), letters) }) test_that("as_vector cannot coerce lists with zero-length elements", { + local_options(lifecycle_verbosity = "quiet") + x <- list(a = 1, b = c(list(), 3)) expect_error(as_vector(x)) expect_identical(x, simplify(x)) diff --git a/tests/testthat/test-list-simplify.R b/tests/testthat/test-list-simplify.R new file mode 100644 index 00000000..801b426e --- /dev/null +++ b/tests/testthat/test-list-simplify.R @@ -0,0 +1,38 @@ +test_that("simplifies using vctrs principles", { + expect_identical(list_simplify(list(1, 2L)), c(1, 2)) + expect_equal(list_simplify(list("x", factor("y"))), c("x", "y")) + + x <- list(data.frame(x = 1), data.frame(y = 2)) + expect_equal(list_simplify(x), data.frame(x = c(1, NA), y = c(NA, 2))) +}) + +test_that("ptype is enforced", { + expect_equal(list_simplify(list(1, 2), ptype = double()), c(1, 2)) + expect_snapshot(list_simplify(list(1, 2), ptype = character()), error = TRUE) + # even if `strict = FALSE` + expect_snapshot(list_simplify(list(1, 2), ptype = character(), strict = FALSE), error = TRUE) +}) + +test_that("strict simplification will error", { + expect_snapshot(error = TRUE, { + list_simplify(list(1, "a")) + list_simplify(list(1, 1:2)) + list_simplify(list(1, 2), ptype = character()) + }) +}) + +test_that("simplification requires length-1 vectors with common type", { + expect_equal(list_simplify(list(mean), strict = FALSE), list(mean)) + expect_equal(list_simplify(list(1, 2:3), strict = FALSE), list(1, 2:3)) + expect_equal(list_simplify(list(1, "a"), strict = FALSE), list(1, "a")) +}) + +# argument checking ------------------------------------------------------- + +test_that("validates inputs", { + expect_snapshot(list_simplify_internal(1:5), error = TRUE) + expect_snapshot(list_simplify_internal(list(), simplify = 1), error = TRUE) + expect_snapshot(list_simplify_internal(list(), simplify = FALSE, ptype = integer()), error = TRUE) + + expect_snapshot(list_simplify(list(), strict = NA), error = TRUE) +}) diff --git a/tests/testthat/test-list-transpose.R b/tests/testthat/test-list-transpose.R new file mode 100644 index 00000000..aabd5c3a --- /dev/null +++ b/tests/testthat/test-list-transpose.R @@ -0,0 +1,132 @@ +test_that("can transpose homogenous list", { + x <- list(x = list(a = 1, b = 2), y = list(a = 3, b = 4)) + out <- list_transpose(x) + expect_equal(out, list(a = c(x = 1, y = 3), b = c(x = 2, y = 4))) +}) + +test_that("transposing empty list returns empty list", { + expect_equal(list_transpose(list()), list()) +}) + +test_that("can use character template", { + x <- list(list(a = 1, b = 2), list(b = 3, c = 4)) + # Default: + expect_equal( + list_transpose(x, default = NA), + list(a = c(1, NA), b = c(2, 3)) + ) + + # Change order + expect_equal( + list_transpose(x, c("b", "a"), default = NA), + list(b = c(2, 3), a = c(1, NA)) + ) + # Remove + expect_equal( + list_transpose(x, "b", default = NA), + list(b = c(2, 3)) + ) + # Add + expect_equal( + list_transpose(x, c("a", "b", "c"), default = NA), + list(a = c(1, NA), b = c(2, 3), c = c(NA, 4)) + ) +}) + +test_that("can use integer template", { + x <- list(list(1, 2, 3), list(4, 5)) + # Default: + expect_equal( + list_transpose(x, default = NA), + list(c(1, 4), c(2, 5), c(3, NA)) + ) + + # Change order + expect_equal( + list_transpose(x, c(3, 2, 1), default = NA), + list(c(3, NA), c(2, 5), c(1, 4)) + ) + # Remove + expect_equal( + list_transpose(x, 2, default = NA), + list(c(2, 5)) + ) + # Add + expect_equal( + list_transpose(x, 1:4, default = NA), + list(c(1, 4), c(2, 5), c(3, NA), c(NA, NA)) + ) +}) + +test_that("integer template requires exact length of list() simplify etc", { + x <- list(list(1, 2), list(3, 4)) + + expect_snapshot(list_transpose(x, ptype = list()), error = TRUE) + expect_snapshot(list_transpose(x, ptype = list(integer())), error = TRUE) + expect_identical( + list_transpose(x, ptype = list(integer(), integer())), + list(c(1L, 3L), c(2L, 4L)) + ) +}) + +test_that("simplification fails silently unless requested", { + expect_equal( + list_transpose(list(list(x = 1), list(x = "b"))), + list(x = list(1, "b")) + ) + expect_equal( + list_transpose(list(list(x = 1), list(x = 2:3))), + list(x = list(1, 2:3)) + ) + + expect_snapshot(error = TRUE, { + list_transpose(list(list(x = 1), list(x = "b")), simplify = TRUE) + list_transpose(list(list(x = 1), list(x = 2:3)), simplify = TRUE) + }) +}) + +test_that("can supply `simplify` globally or individually", { + x <- list(list(a = 1, b = 2), list(a = 3, b = 4)) + expect_equal( + list_transpose(x, simplify = FALSE), + list(a = list(1, 3), b = list(2, 4)) + ) + expect_equal( + list_transpose(x, simplify = list(a = FALSE)), + list(a = list(1, 3), b = c(2, 4)) + ) + expect_snapshot(list_transpose(x, simplify = list(c = FALSE)), error = TRUE) +}) + +test_that("can supply `ptype` globally or individually", { + x <- list(list(a = 1, b = 2), list(a = 3, b = 4)) + expect_identical( + list_transpose(x, ptype = integer()), + list(a = c(1L, 3L), b = c(2L, 4L)) + ) + expect_identical( + list_transpose(x, ptype = list(a = integer())), + list(a = c(1L, 3L), b = c(2, 4)) + ) + expect_snapshot(list_transpose(x, ptype = list(c = integer())), error = TRUE) +}) + +test_that("can supply `default` globally or individually", { + x <- list(list(x = 1), list(y = "a")) + expect_equal( + list_transpose(x, c("x", "y"), default = NA), + list(x = c(1, NA), y = c(NA, "a")) + ) + expect_equal( + list_transpose(x, c("x", "y"), default = list(x = NA, y = "")), + list(x = c(1, NA), y = c("", "a")) + ) + expect_snapshot(list_transpose(x, default = list(c = NA)), error = TRUE) +}) + +test_that("validates inputs", { + expect_snapshot(error = TRUE, { + list_transpose(10) + list_transpose(list(1), template = mean) + }) +}) diff --git a/tests/testthat/test-reduce.R b/tests/testthat/test-reduce.R index e4e38166..9125d42b 100644 --- a/tests/testthat/test-reduce.R +++ b/tests/testthat/test-reduce.R @@ -113,22 +113,12 @@ test_that("accumulate() uses vctrs to simplify results", { test_that("accumulate() does not fail when input can't be simplified", { expect_identical(accumulate(list(1L, 2:3), ~ .y), list(1L, 2:3)) expect_identical(accumulate(list(1, "a"), ~ .y), list(1, "a")) - expect_identical(accumulate(1:3, ~ .y), 1:3) - expect_identical(accumulate(list(identity), ~ .y), list(identity)) - expect_identical(accumulate(mtcars, ~ .y), as.list(mtcars)) }) -test_that("accumulate() does not simplify data frame rowwise", { - out <- accumulate( - 1L, - ~ data.frame(new = .y), - .init = data.frame(new = 0L) - ) - exp <- list(data.frame(new = 0L), data.frame(new = 1L)) - expect_identical(out, exp) +test_that("accumulate() does fail when simpification is required", { + expect_snapshot(accumulate(list(1, "a"), ~ .y, .simplify = TRUE), error = TRUE) }) - # reduce2 ----------------------------------------------------------------- test_that("basic application works", { @@ -162,8 +152,8 @@ test_that("basic accumulate2() works", { paste2 <- function(x, y, sep) paste(x, y, sep = sep) x <- c("a", "b", "c") - expect_equal(accumulate2(x, c("-", "."), paste2), list("a", "a-b", "a-b.c")) - expect_equal(accumulate2(x, c(".", "-", "."), paste2, .init = "x"), list("x", "x.a", "x.a-b", "x.a-b.c")) + expect_equal(accumulate2(x, c("-", "."), paste2), c("a", "a-b", "a-b.c")) + expect_equal(accumulate2(x, c(".", "-", "."), paste2, .init = "x"), c("x", "x.a", "x.a-b", "x.a-b.c")) }) test_that("can terminate accumulate2() early", { @@ -177,8 +167,8 @@ test_that("can terminate accumulate2() early", { } x <- c("a", "b", "c") - expect_equal(accumulate2(x, c("-", "."), paste2), list("a", "a-b")) - expect_equal(accumulate2(x, c(".", "-", "."), paste2, .init = "x"), list("x", "x.a", "x.a-b")) + expect_equal(accumulate2(x, c("-", "."), paste2), c("a", "a-b")) + expect_equal(accumulate2(x, c(".", "-", "."), paste2, .init = "x"), c("x", "x.a", "x.a-b")) }) test_that("accumulate2() forces arguments (#643)", { diff --git a/tests/testthat/test-transpose.R b/tests/testthat/test-transpose.R index 4fc2b832..d557b5ef 100644 --- a/tests/testthat/test-transpose.R +++ b/tests/testthat/test-transpose.R @@ -1,48 +1,72 @@ +test_that("transpose() is deprecated", { + expect_snapshot(. <- transpose(list())) +}) + test_that("input must be a list", { + local_options(lifecycle_verbosity = "quiet") + expect_bad_type_error(transpose(1:3), "`.l` must be a list, not an integer vector") }) test_that("elements of input must be atomic vectors", { + local_options(lifecycle_verbosity = "quiet") + expect_bad_element_type_error(transpose(list(environment())), "Element 1 must be a vector, not an environment") expect_bad_element_type_error(transpose(list(list(), environment())), "Element 2 must be a vector, not an environment") }) test_that("empty list returns empty list", { + local_options(lifecycle_verbosity = "quiet") + expect_equal(transpose(list()), list()) }) test_that("transpose switches order of first & second idnex", { + local_options(lifecycle_verbosity = "quiet") + x <- list(list(1, 3), list(2, 4)) expect_equal(transpose(x), list(list(1, 2), list(3, 4))) }) test_that("inside names become outside names", { + local_options(lifecycle_verbosity = "quiet") + x <- list(list(x = 1), list(x = 2)) expect_equal(transpose(x), list(x = list(1, 2))) }) test_that("outside names become inside names", { + local_options(lifecycle_verbosity = "quiet") + x <- list(x = list(1, 3), y = list(2, 4)) expect_equal(transpose(x), list(list(x = 1, y = 2), list(x = 3, y = 4))) }) test_that("warns if element too short", { + local_options(lifecycle_verbosity = "quiet") + x <- list(list(1, 2), list(1)) expect_warning(out <- transpose(x), "Element 2 must be length 2, not 1") expect_equal(out, list(list(1, 1), list(2, NULL))) }) test_that("warns if element too long", { + local_options(lifecycle_verbosity = "quiet") + x <- list(list(1, 2), list(1, 2, 3)) expect_warning(out <- transpose(x), "Element 2 must be length 2, not 3") expect_equal(out, list(list(1, 1), list(2, 2))) }) test_that("can transpose list of lists of atomic vectors", { + local_options(lifecycle_verbosity = "quiet") + x <- list(list(TRUE, 1L, 1, "1")) expect_equal(transpose(x), list(list(TRUE), list(1L), list(1), list("1"))) }) test_that("can transpose lists of atomic vectors", { + local_options(lifecycle_verbosity = "quiet") + expect_equal(transpose(list(TRUE, FALSE)), list(list(TRUE, FALSE))) expect_equal(transpose(list(1L, 2L)), list(list(1L, 2L))) expect_equal(transpose(list(1, 2)), list(list(1, 2))) @@ -50,6 +74,8 @@ test_that("can transpose lists of atomic vectors", { }) test_that("can't transpose expressions", { + local_options(lifecycle_verbosity = "quiet") + expect_bad_type_error( transpose(list(expression(a))), "Transposed element must be a vector, not an expression vector" @@ -59,6 +85,8 @@ test_that("can't transpose expressions", { # Named based matching ---------------------------------------------------- test_that("can override default names", { + local_options(lifecycle_verbosity = "quiet") + x <- list( list(x = 1), list(y = 2, x = 1) @@ -72,6 +100,8 @@ test_that("can override default names", { }) test_that("if present, names are used", { + local_options(lifecycle_verbosity = "quiet") + x <- list( list(x = 1, y = 2), list(y = 2, x = 1) @@ -83,6 +113,8 @@ test_that("if present, names are used", { }) test_that("if missing elements, filled with NULL", { + local_options(lifecycle_verbosity = "quiet") + x <- list( list(x = 1, y = 2), list(x = 1) @@ -94,6 +126,8 @@ test_that("if missing elements, filled with NULL", { # Position based matching ------------------------------------------------- test_that("warning if too short", { + local_options(lifecycle_verbosity = "quiet") + x <- list( list(1, 2), list(1) @@ -103,6 +137,8 @@ test_that("warning if too short", { }) test_that("warning if too long", { + local_options(lifecycle_verbosity = "quiet") + x <- list( list(1), list(1, 2) @@ -110,3 +146,4 @@ test_that("warning if too long", { expect_warning(tx <- transpose(x), "must be length 1, not 2") expect_equal(tx, list(list(1, 1))) }) + diff --git a/tests/testthat/test-utils.R b/tests/testthat/test-utils.R index 6233e213..e4679a98 100644 --- a/tests/testthat/test-utils.R +++ b/tests/testthat/test-utils.R @@ -32,30 +32,6 @@ test_that("rdunif fails if a and b are not unit length numbers", { expect_error(rdunif(1000, c(2, 3), 2)) }) -test_that("vec_simplify() coerces atomic inputs", { - expect_identical( - vec_simplify(list(1, TRUE)), - c(1, 1) - ) - expect_identical( - vec_simplify(list("foo", factor("bar"))), - c("foo", "bar") - ) - expect_identical( - vec_simplify(list(data.frame(x = FALSE), data.frame(x = 1L))), - data.frame(x = 0:1) - ) -}) - -test_that("vec_simplify() ignores complex inputs", { - expect_identical(vec_simplify(list(1L, 2:3)), list(1L, 2:3)) - expect_identical(vec_simplify(list(1, "a")), list(1, "a")) - expect_identical(vec_simplify(1:3), 1:3) - expect_identical(vec_simplify(list(identity)), list(identity)) - expect_identical(vec_simplify(mtcars), mtcars) -}) - - # Lifecycle --------------------------------------------------------------- test_that("%@% is an infix attribute accessor", {