From 4b3ad43efd8220d59466f44c96149ddc432699da Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Sat, 24 Jul 2021 15:55:47 +0200 Subject: [PATCH 001/147] Consistent definition of options and their defaults --- NAMESPACE | 1 + R/aaa-options.R | 58 +++++++++++++++++++++++++++++++++++++++ R/options.R | 63 +++++++++++++++++++++++++++++++++++++++++++ R/pillar-package.R | 24 ----------------- man/pillar-package.Rd | 27 ------------------- man/pillar_options.Rd | 56 ++++++++++++++++++++++++++++++++++++++ 6 files changed, 178 insertions(+), 51 deletions(-) create mode 100644 R/aaa-options.R create mode 100644 R/options.R create mode 100644 man/pillar_options.Rd diff --git a/NAMESPACE b/NAMESPACE index 83d77dec4..c900a98eb 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -130,6 +130,7 @@ export(num) export(obj_sum) export(pillar) export(pillar_component) +export(pillar_options) export(pillar_shaft) export(set_char_opts) export(set_num_opts) diff --git a/R/aaa-options.R b/R/aaa-options.R new file mode 100644 index 000000000..6fbdb0be0 --- /dev/null +++ b/R/aaa-options.R @@ -0,0 +1,58 @@ +make_option_impl <- function(name, default, env = caller_env()) { + option_name <- paste0(utils::packageName(env), ".", name) + + # Do not change the structure of this expression, + # it is used in options_usage() + getter_body <- expr(getOption(!!option_name, default = !!default)) + + setter_body <- expr( + if (local) { + out <- !!call2("local_options", !!option_name := sym("value"), env = sym("env")) + invisible(out[[1]]) + } else { + out <- !!call2("options", !!option_name := sym("value")) + invisible(out[[1]]) + } + ) + + body <- expr({ + if (missing(value)) { + if (!missing(local)) { + abort("Can't pass `local` argument if `value` is missing.") + } + !!getter_body + } else !!setter_body + }) + + args <- pairlist2(value = , local = FALSE, env = quote(caller_env())) + + getter_name <- paste0(utils::packageName(env), "_option_get_", name) + assign(getter_name, new_function(list(), getter_body, env = env), env) + setter_name <- paste0(utils::packageName(env), "_option_set_", name) + assign(setter_name, new_function(args, setter_body, env = env), env) + + new_function(args, body, env = env) +} + +option_usage <- function(env = caller_env()) { + pkg_name <- utils::packageName(env) + options <- get(paste0(pkg_name, "_options"), env) + first_option <- names(options)[[1]] + + first_option_getter <- get(paste0(pkg_name, "_option_get_", first_option), env) + first_option_default <- expr_deparse(body(first_option_getter)[[3]]) + + c( + "@details", + paste0( + 'These options can also be queried via [getOption()] and set via [options()] by prefixing them with `', + pkg_name, '.` (the package name and a dot). Example: `', pkg_name, '_options$', first_option, + '()` is equivalent to `getOption("', pkg_name, '.', first_option, + '", default = ', first_option_default, ')`.' + ), + "@usage", + paste0('pillar_options$bold(value, local = FALSE) # same as: options(', pkg_name, ".", first_option, " = value)"), + "", + paste0('pillar_options$bold() # similar to: getOption("', pkg_name, ".", first_option, '")') + ) +} diff --git a/R/options.R b/R/options.R new file mode 100644 index 000000000..bbbb927d5 --- /dev/null +++ b/R/options.R @@ -0,0 +1,63 @@ +#' Package options +#' +#' Options that affect display of tibble-like output. +#' +#' All options are available via the `pillar_options` list. +#' The elements of this list are combined getter/setter functions. +#' Calling a function without arguments returns the current value, +#' by providing an argument the current value is set and the old value +#' is returned, invisibly. +#' Setting `local = TRUE` enables the option for the duration of the +#' current stack frame via [rlang::local_options()]. +#' +#' @eval option_usage() +#' +#' @export +#' @section Options: +pillar_options <- list( + # pillar_option_get_bold + # pillar_option_set_bold + bold = make_option_impl("bold", FALSE), + #' - `bold`: Use bold font, e.g. for column headers? This currently + #' defaults to `FALSE`, because many terminal fonts have poor support for + #' bold fonts. + # pillar_option_get_subtle + # pillar_option_set_subtle + subtle = make_option_impl("subtle", TRUE), + #' - `subtle`: Use subtle style, e.g. for row numbers and data types? + #' Default: `TRUE`. + # pillar_option_get_subtle_num + # pillar_option_set_subtle_num + subtle_num = make_option_impl("subtle_num", FALSE), + #' - `subtle_num`: Use subtle style for insignificant digits? Default: + #' `FALSE`, is also affected by the `subtle` option. + #' - `neg`: Highlight negative numbers? Default: `TRUE`. + # pillar_option_get_neg + # pillar_option_set_neg + neg = make_option_impl("neg", TRUE), + #' - `sigfig`: The number of significant digits that will be printed and + #' highlighted, default: `3`. Set the `subtle` option to `FALSE` to + #' turn off highlighting of significant digits. + # pillar_option_get_sigfig + # pillar_option_set_sigfig + sigfig = make_option_impl("sigfig", 3L), + #' - `min_title_chars`: The minimum number of characters for the column + #' title, default: `15`. Column titles may be truncated up to that width to + #' save horizontal space. Set to `Inf` to turn off truncation of column + #' titles. + # pillar_option_get_min_title_chars + # pillar_option_set_min_title_chars + min_title_chars = make_option_impl("min_title_chars", 15L), + #' - `min_chars`: The minimum number of characters wide to + #' display character columns, default: `3`. Character columns may be + #' truncated up to that width to save horizontal space. Set to `Inf` to + #' turn off truncation of character columns. + # pillar_option_get_min_chars + # pillar_option_set_min_chars + min_chars = make_option_impl("min_chars", 3L), + #' - `max_dec_width`: The maximum allowed width for decimal notation, + #' default 13. + # pillar_option_get_max_dec_width + # pillar_option_set_max_dec_width + max_dec_width = make_option_impl("max_dec_width", 13L) +) diff --git a/R/pillar-package.R b/R/pillar-package.R index 3d24e05d6..72067083a 100644 --- a/R/pillar-package.R +++ b/R/pillar-package.R @@ -11,30 +11,6 @@ #' See [pillar()] for formatting a single column, #' and [print.tbl()] for formatting data-frame-like objects. #' -#' @section Package options: -#' -#' - `pillar.bold`: Use bold font, e.g. for column headers? This currently -#' defaults to `FALSE`, because many terminal fonts have poor support for -#' bold fonts. -#' - `pillar.subtle`: Use subtle style, e.g. for row numbers and data types? -#' Default: `TRUE`. -#' - `pillar.subtle_num`: Use subtle style for insignificant digits? Default: -#' `FALSE`, is also affected by the `pillar.subtle` option. -#' - `pillar.neg`: Highlight negative numbers? Default: `TRUE`. -#' - `pillar.sigfig`: The number of significant digits that will be printed and -#' highlighted, default: `3`. Set the `pillar.subtle` option to `FALSE` to -#' turn off highlighting of significant digits. -#' - `pillar.min_title_chars`: The minimum number of characters for the column -#' title, default: `15`. Column titles may be truncated up to that width to -#' save horizontal space. Set to `Inf` to turn off truncation of column -#' titles. -#' - `pillar.min_chars`: The minimum number of characters wide to -#' display character columns, default: `0`. Character columns may be -#' truncated up to that width to save horizontal space. Set to `Inf` to -#' turn off truncation of character columns. -#' - `pillar.max_dec_width`: The maximum allowed width for decimal notation, -#' default 13. -#' #' @examples #' pillar(1:3) #' pillar(c(1, 2, 3)) diff --git a/man/pillar-package.Rd b/man/pillar-package.Rd index 301d38a09..6f6437e1b 100644 --- a/man/pillar-package.Rd +++ b/man/pillar-package.Rd @@ -15,33 +15,6 @@ Provides various generics for making every aspect of the display customizable. See \code{\link[=pillar]{pillar()}} for formatting a single column, and \code{\link[=print.tbl]{print.tbl()}} for formatting data-frame-like objects. } -\section{Package options}{ - -\itemize{ -\item \code{pillar.bold}: Use bold font, e.g. for column headers? This currently -defaults to \code{FALSE}, because many terminal fonts have poor support for -bold fonts. -\item \code{pillar.subtle}: Use subtle style, e.g. for row numbers and data types? -Default: \code{TRUE}. -\item \code{pillar.subtle_num}: Use subtle style for insignificant digits? Default: -\code{FALSE}, is also affected by the \code{pillar.subtle} option. -\item \code{pillar.neg}: Highlight negative numbers? Default: \code{TRUE}. -\item \code{pillar.sigfig}: The number of significant digits that will be printed and -highlighted, default: \code{3}. Set the \code{pillar.subtle} option to \code{FALSE} to -turn off highlighting of significant digits. -\item \code{pillar.min_title_chars}: The minimum number of characters for the column -title, default: \code{15}. Column titles may be truncated up to that width to -save horizontal space. Set to \code{Inf} to turn off truncation of column -titles. -\item \code{pillar.min_chars}: The minimum number of characters wide to -display character columns, default: \code{0}. Character columns may be -truncated up to that width to save horizontal space. Set to \code{Inf} to -turn off truncation of character columns. -\item \code{pillar.max_dec_width}: The maximum allowed width for decimal notation, -default 13. -} -} - \examples{ pillar(1:3) pillar(c(1, 2, 3)) diff --git a/man/pillar_options.Rd b/man/pillar_options.Rd new file mode 100644 index 000000000..26403482c --- /dev/null +++ b/man/pillar_options.Rd @@ -0,0 +1,56 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/options.R +\docType{data} +\name{pillar_options} +\alias{pillar_options} +\title{Package options} +\format{ +An object of class \code{list} of length 8. +} +\usage{ +pillar_options$bold(value, local = FALSE) # same as: options(pillar.bold = value) + +pillar_options$bold() # similar to: getOption("pillar.bold") +} +\description{ +Options that affect display of tibble-like output. +} +\details{ +All options are available via the \code{pillar_options} list. +The elements of this list are combined getter/setter functions. +Calling a function without arguments returns the current value, +by providing an argument the current value is set and the old value +is returned, invisibly. +Setting \code{local = TRUE} enables the option for the duration of the +current stack frame via \code{\link[rlang:local_options]{rlang::local_options()}}. + +These options can also be queried via \code{\link[=getOption]{getOption()}} and set via \code{\link[=options]{options()}} by prefixing them with \code{pillar.} (the package name and a dot). Example: \code{pillar_options$bold()} is equivalent to \code{getOption("pillar.bold", default = FALSE)}. +} +\section{Options}{ + +\itemize{ +\item \code{bold}: Use bold font, e.g. for column headers? This currently +defaults to \code{FALSE}, because many terminal fonts have poor support for +bold fonts. +\item \code{subtle}: Use subtle style, e.g. for row numbers and data types? +Default: \code{TRUE}. +\item \code{subtle_num}: Use subtle style for insignificant digits? Default: +\code{FALSE}, is also affected by the \code{subtle} option. +\item \code{neg}: Highlight negative numbers? Default: \code{TRUE}. +\item \code{sigfig}: The number of significant digits that will be printed and +highlighted, default: \code{3}. Set the \code{subtle} option to \code{FALSE} to +turn off highlighting of significant digits. +\item \code{min_title_chars}: The minimum number of characters for the column +title, default: \code{15}. Column titles may be truncated up to that width to +save horizontal space. Set to \code{Inf} to turn off truncation of column +titles. +\item \code{min_chars}: The minimum number of characters wide to +display character columns, default: \code{0}. Character columns may be +truncated up to that width to save horizontal space. Set to \code{Inf} to +turn off truncation of character columns. +\item \code{max_dec_width}: The maximum allowed width for decimal notation, +default 13. +} +} + +\keyword{datasets} From 9addc020dce7de2b1836dc6b66b0dfc6e791c391 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Sat, 24 Jul 2021 16:01:20 +0200 Subject: [PATCH 002/147] Use getters --- R/shaft-.R | 6 +++--- R/styles.R | 10 +++++----- R/title.R | 2 +- 3 files changed, 9 insertions(+), 9 deletions(-) diff --git a/R/shaft-.R b/R/shaft-.R index c93e69d66..3567740e8 100644 --- a/R/shaft-.R +++ b/R/shaft-.R @@ -145,7 +145,7 @@ pillar_shaft_number <- function(x, sigfig, digits, notation, fixed_exponent) { } } if (is.null(sigfig)) { - sigfig <- getOption("pillar.sigfig", 3) + sigfig <- pillar_option_get_sigfig() if (!is.numeric(sigfig) || length(sigfig) != 1 || sigfig < 1L) { inform("Option pillar.sigfig must be a positive number greater or equal 1. Resetting to 1.") sigfig <- 1L @@ -157,7 +157,7 @@ pillar_shaft_number <- function(x, sigfig, digits, notation, fixed_exponent) { dec <- split_decimal(x, sigfig = sigfig, digits = digits) sci <- split_decimal(x, sigfig = sigfig, digits = digits, sci_mod = 1, fixed_exponent = fixed_exponent) - max_dec_width <- getOption("pillar.max_dec_width", 13) + max_dec_width <- pillar_option_get_max_dec_width() dec_width <- get_width(dec) "!!!!!!DEBUG `v(dec_width)`" @@ -281,7 +281,7 @@ pillar_shaft.character <- function(x, ..., min_width = NULL) { # determine width based on width of characters in the vector if (is.null(min_chars)) { - min_chars <- getOption("pillar.min_chars", 3L) + min_chars <- pillar_option_get_min_chars() if (!is.numeric(min_chars) || length(min_chars) != 1 || min_chars < 3L) { inform("Option pillar.min_chars must be a nonnegative number greater or equal 3. Resetting to 3.") min_chars <- 3L diff --git a/R/styles.R b/R/styles.R index dd9f784e5..a26e2bbef 100644 --- a/R/styles.R +++ b/R/styles.R @@ -23,7 +23,7 @@ keep_empty <- function(fun) { #' style_subtle("text") style_subtle <- keep_empty(function(x) { force(x) - if (isTRUE(getOption("pillar.subtle", TRUE))) { + if (isTRUE(pillar_option_get_subtle())) { crayon_grey_0.6(x) } else { x @@ -39,7 +39,7 @@ style_subtle <- keep_empty(function(x) { #' @examples #' style_subtle_num(0.01 * 1:3, c(TRUE, FALSE, TRUE)) style_subtle_num <- function(x, negative) { - if (isTRUE(getOption("pillar.subtle_num", FALSE))) { + if (isTRUE(pillar_option_get_subtle_num())) { style_subtle(x) } else { ifelse(negative, style_neg(x), x) @@ -48,7 +48,7 @@ style_subtle_num <- function(x, negative) { style_hint <- keep_empty(function(x) { force(x) - if (isTRUE(getOption("pillar.subtle", TRUE))) { + if (isTRUE(pillar_option_get_subtle())) { crayon_grey_0.8(x) } else { x @@ -67,7 +67,7 @@ style_spark_na <- function(x) { #' @examples #' style_bold("Petal.Width") style_bold <- keep_empty(function(x) { - if (isTRUE(getOption("pillar.bold", FALSE))) { + if (isTRUE(pillar_option_get_bold())) { crayon_bold(x) } else { x @@ -90,7 +90,7 @@ style_na <- function(x) { #' @examples #' style_neg("123") style_neg <- keep_empty(function(x) { - if (isTRUE(getOption("pillar.neg", TRUE))) { + if (isTRUE(pillar_option_get_neg())) { crayon_red(x) } else { x diff --git a/R/title.R b/R/title.R index 6096986c4..7764e52b1 100644 --- a/R/title.R +++ b/R/title.R @@ -33,7 +33,7 @@ new_pillar_title <- function(x, ...) { } get_min_title_width <- function(width) { - title_chars <- getOption("pillar.min_title_chars", 15) + title_chars <- pillar_option_get_min_title_chars() if (!is.numeric(title_chars) || length(title_chars) != 1 || title_chars < 0) { stop("Option pillar.min_title_chars must be a nonnegative number", call. = FALSE) } From 6defa883dfd436339b3cb0bcf4aa806045429b16 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Sat, 24 Jul 2021 16:07:37 +0200 Subject: [PATCH 003/147] Link to options page --- _pkgdown.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/_pkgdown.yml b/_pkgdown.yml index 23c8d0779..2a18b5eae 100644 --- a/_pkgdown.yml +++ b/_pkgdown.yml @@ -61,7 +61,7 @@ navbar: href: index.html options: text: Options - href: "reference/pillar-package.html#package-options" + href: "reference/pillar_options.html" reference: text: Reference href: reference/index.html From 1082a097f9c6d3fe95c73ab6f9b6f2792dcf9f9c Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Sat, 24 Jul 2021 16:08:24 +0200 Subject: [PATCH 004/147] Add to reference --- _pkgdown.yml | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/_pkgdown.yml b/_pkgdown.yml index 2a18b5eae..a4fdb0c66 100644 --- a/_pkgdown.yml +++ b/_pkgdown.yml @@ -28,7 +28,7 @@ reference: - format_type_sum - title: Styling desc: > - For consistent output of different data types. + For consistent output. contents: - starts_with("style_") - align @@ -36,13 +36,14 @@ reference: - new_ornament - new_pillar_title - new_pillar_type + - dim_desc - title: Vector classes contents: - num - char - title: Miscellaneous contents: - - dim_desc + - options - pillar-package navbar: From 4c7e3d3d6898d3a9b3167905e4d39aedd83af18b Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Sat, 24 Jul 2021 16:33:08 +0200 Subject: [PATCH 005/147] More flexibility --- R/aaa-options.R | 23 ++++++++--------------- R/options.R | 42 ++++++++++++++++++++++++++++++++---------- man/pillar_options.Rd | 10 +++++++--- 3 files changed, 47 insertions(+), 28 deletions(-) diff --git a/R/aaa-options.R b/R/aaa-options.R index 6fbdb0be0..eb9521949 100644 --- a/R/aaa-options.R +++ b/R/aaa-options.R @@ -1,9 +1,12 @@ -make_option_impl <- function(name, default, env = caller_env()) { - option_name <- paste0(utils::packageName(env), ".", name) +make_option_impl <- function(getter, option_name = NULL, env = caller_env()) { + getter_body <- enexpr(getter) - # Do not change the structure of this expression, - # it is used in options_usage() - getter_body <- expr(getOption(!!option_name, default = !!default)) + if (is.null(option_name)) { + # Assuming that the call is getOption() + option_name <- getter_body[[2]] + stopifnot(is.character(option_name)) + } + name <- sub(paste0(utils::packageName(env), "."), "", option_name, fixed = TRUE) setter_body <- expr( if (local) { @@ -39,17 +42,7 @@ option_usage <- function(env = caller_env()) { options <- get(paste0(pkg_name, "_options"), env) first_option <- names(options)[[1]] - first_option_getter <- get(paste0(pkg_name, "_option_get_", first_option), env) - first_option_default <- expr_deparse(body(first_option_getter)[[3]]) - c( - "@details", - paste0( - 'These options can also be queried via [getOption()] and set via [options()] by prefixing them with `', - pkg_name, '.` (the package name and a dot). Example: `', pkg_name, '_options$', first_option, - '()` is equivalent to `getOption("', pkg_name, '.', first_option, - '", default = ', first_option_default, ')`.' - ), "@usage", paste0('pillar_options$bold(value, local = FALSE) # same as: options(', pkg_name, ".", first_option, " = value)"), "", diff --git a/R/options.R b/R/options.R index bbbb927d5..89ee714d4 100644 --- a/R/options.R +++ b/R/options.R @@ -10,54 +10,76 @@ #' Setting `local = TRUE` enables the option for the duration of the #' current stack frame via [rlang::local_options()]. #' +#' These options can also be queried via [getOption()] and set via [options()] +#' by prefixing them with `pillar.` (the package name and a dot). +#' Example: for an option `foo`, +#' `pillar_options$foo(value)` is equivalent to +#' `options(pillar.foo = value)`. +#' #' @eval option_usage() #' #' @export -#' @section Options: -pillar_options <- list( +#' @section Options for the pillar package: +pillar_options <- list2( # pillar_option_get_bold # pillar_option_set_bold - bold = make_option_impl("bold", FALSE), + bold = make_option_impl( + getOption("pillar.bold", default = FALSE) + ), #' - `bold`: Use bold font, e.g. for column headers? This currently #' defaults to `FALSE`, because many terminal fonts have poor support for #' bold fonts. # pillar_option_get_subtle # pillar_option_set_subtle - subtle = make_option_impl("subtle", TRUE), + subtle = make_option_impl( + getOption("pillar.subtle", default = TRUE) + ), #' - `subtle`: Use subtle style, e.g. for row numbers and data types? #' Default: `TRUE`. # pillar_option_get_subtle_num # pillar_option_set_subtle_num - subtle_num = make_option_impl("subtle_num", FALSE), + subtle_num = make_option_impl( + getOption("pillar.subtle_num", default = FALSE) + ), #' - `subtle_num`: Use subtle style for insignificant digits? Default: #' `FALSE`, is also affected by the `subtle` option. #' - `neg`: Highlight negative numbers? Default: `TRUE`. # pillar_option_get_neg # pillar_option_set_neg - neg = make_option_impl("neg", TRUE), + neg = make_option_impl( + getOption("pillar.neg", default = TRUE) + ), #' - `sigfig`: The number of significant digits that will be printed and #' highlighted, default: `3`. Set the `subtle` option to `FALSE` to #' turn off highlighting of significant digits. # pillar_option_get_sigfig # pillar_option_set_sigfig - sigfig = make_option_impl("sigfig", 3L), + sigfig = make_option_impl( + getOption("pillar.sigfig", default = 3L) + ), #' - `min_title_chars`: The minimum number of characters for the column #' title, default: `15`. Column titles may be truncated up to that width to #' save horizontal space. Set to `Inf` to turn off truncation of column #' titles. # pillar_option_get_min_title_chars # pillar_option_set_min_title_chars - min_title_chars = make_option_impl("min_title_chars", 15L), + min_title_chars = make_option_impl( + getOption("pillar.min_title_chars", default = 15L) + ), #' - `min_chars`: The minimum number of characters wide to #' display character columns, default: `3`. Character columns may be #' truncated up to that width to save horizontal space. Set to `Inf` to #' turn off truncation of character columns. # pillar_option_get_min_chars # pillar_option_set_min_chars - min_chars = make_option_impl("min_chars", 3L), + min_chars = make_option_impl( + getOption("pillar.min_chars", default = 3L) + ), #' - `max_dec_width`: The maximum allowed width for decimal notation, #' default 13. # pillar_option_get_max_dec_width # pillar_option_set_max_dec_width - max_dec_width = make_option_impl("max_dec_width", 13L) + max_dec_width = make_option_impl( + getOption("pillar.max_dec_width", default = 13L) + ), ) diff --git a/man/pillar_options.Rd b/man/pillar_options.Rd index 26403482c..71e253458 100644 --- a/man/pillar_options.Rd +++ b/man/pillar_options.Rd @@ -24,9 +24,13 @@ is returned, invisibly. Setting \code{local = TRUE} enables the option for the duration of the current stack frame via \code{\link[rlang:local_options]{rlang::local_options()}}. -These options can also be queried via \code{\link[=getOption]{getOption()}} and set via \code{\link[=options]{options()}} by prefixing them with \code{pillar.} (the package name and a dot). Example: \code{pillar_options$bold()} is equivalent to \code{getOption("pillar.bold", default = FALSE)}. +These options can also be queried via \code{\link[=getOption]{getOption()}} and set via \code{\link[=options]{options()}} +by prefixing them with \code{pillar.} (the package name and a dot). +Example: for an option \code{foo}, +\code{pillar_options$foo(value)} is equivalent to +\code{options(pillar.foo = value)}. } -\section{Options}{ +\section{Options for the pillar package}{ \itemize{ \item \code{bold}: Use bold font, e.g. for column headers? This currently @@ -45,7 +49,7 @@ title, default: \code{15}. Column titles may be truncated up to that width to save horizontal space. Set to \code{Inf} to turn off truncation of column titles. \item \code{min_chars}: The minimum number of characters wide to -display character columns, default: \code{0}. Character columns may be +display character columns, default: \code{3}. Character columns may be truncated up to that width to save horizontal space. Set to \code{Inf} to turn off truncation of character columns. \item \code{max_dec_width}: The maximum allowed width for decimal notation, From eec201167f54bd6ecbb89ce85098165b911a7808 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Sat, 24 Jul 2021 16:56:13 +0200 Subject: [PATCH 006/147] Support arbitrary code for the getter --- R/aaa-options.R | 25 +++++++++++++++-------- R/options.R | 53 +++++++++++++++++++++++++++++-------------------- R/shaft-.R | 16 +++------------ R/styles.R | 10 +++++----- R/title.R | 2 +- 5 files changed, 57 insertions(+), 49 deletions(-) diff --git a/R/aaa-options.R b/R/aaa-options.R index eb9521949..b4dbed194 100644 --- a/R/aaa-options.R +++ b/R/aaa-options.R @@ -7,13 +7,22 @@ make_option_impl <- function(getter, option_name = NULL, env = caller_env()) { stopifnot(is.character(option_name)) } name <- sub(paste0(utils::packageName(env), "."), "", option_name, fixed = TRUE) + getter_name <- paste0("get_", utils::packageName(env), "_option_", name) + local_setter_name <- paste0("local_", utils::packageName(env), "_option_", name) + setter_name <- paste0("set_", utils::packageName(env), "_option_", name) + + local_setter_body <- expr( + { + !!call2("local_options", !!option_name := sym("value"), .frame = sym("env")) + !!call2(getter_name) + invisible(out[[1]]) + } + ) setter_body <- expr( - if (local) { - out <- !!call2("local_options", !!option_name := sym("value"), env = sym("env")) - invisible(out[[1]]) - } else { + { out <- !!call2("options", !!option_name := sym("value")) + !!call2(getter_name) invisible(out[[1]]) } ) @@ -24,15 +33,15 @@ make_option_impl <- function(getter, option_name = NULL, env = caller_env()) { abort("Can't pass `local` argument if `value` is missing.") } !!getter_body - } else !!setter_body + } else if (local) !!local_setter_body + else !!setter_body }) args <- pairlist2(value = , local = FALSE, env = quote(caller_env())) - getter_name <- paste0(utils::packageName(env), "_option_get_", name) assign(getter_name, new_function(list(), getter_body, env = env), env) - setter_name <- paste0(utils::packageName(env), "_option_set_", name) - assign(setter_name, new_function(args, setter_body, env = env), env) + assign(local_setter_name, new_function(args, local_setter_body, env = env), env) + assign(setter_name, new_function(pairlist2(value = ), setter_body, env = env), env) new_function(args, body, env = env) } diff --git a/R/options.R b/R/options.R index 89ee714d4..12450736c 100644 --- a/R/options.R +++ b/R/options.R @@ -21,48 +21,53 @@ #' @export #' @section Options for the pillar package: pillar_options <- list2( - # pillar_option_get_bold - # pillar_option_set_bold + # get_pillar_option_bold + # set_pillar_option_bold bold = make_option_impl( getOption("pillar.bold", default = FALSE) ), #' - `bold`: Use bold font, e.g. for column headers? This currently #' defaults to `FALSE`, because many terminal fonts have poor support for #' bold fonts. - # pillar_option_get_subtle - # pillar_option_set_subtle + # get_pillar_option_subtle + # set_pillar_option_subtle subtle = make_option_impl( getOption("pillar.subtle", default = TRUE) ), #' - `subtle`: Use subtle style, e.g. for row numbers and data types? #' Default: `TRUE`. - # pillar_option_get_subtle_num - # pillar_option_set_subtle_num + # get_pillar_option_subtle_num + # set_pillar_option_subtle_num subtle_num = make_option_impl( getOption("pillar.subtle_num", default = FALSE) ), #' - `subtle_num`: Use subtle style for insignificant digits? Default: #' `FALSE`, is also affected by the `subtle` option. #' - `neg`: Highlight negative numbers? Default: `TRUE`. - # pillar_option_get_neg - # pillar_option_set_neg + # get_pillar_option_neg + # set_pillar_option_neg neg = make_option_impl( getOption("pillar.neg", default = TRUE) ), #' - `sigfig`: The number of significant digits that will be printed and #' highlighted, default: `3`. Set the `subtle` option to `FALSE` to #' turn off highlighting of significant digits. - # pillar_option_get_sigfig - # pillar_option_set_sigfig - sigfig = make_option_impl( - getOption("pillar.sigfig", default = 3L) - ), + # get_pillar_option_sigfig + # set_pillar_option_sigfig + sigfig = make_option_impl(option_name = "pillar.sigfig", { + sigfig <- getOption("pillar.sigfig", default = 3L) + if (!is.numeric(sigfig) || length(sigfig) != 1 || sigfig < 1L) { + inform("Option pillar.sigfig must be a positive number greater or equal 1. Resetting to 3.") + set_pillar_option_sigfig(3L) + } + sigfig + }), #' - `min_title_chars`: The minimum number of characters for the column #' title, default: `15`. Column titles may be truncated up to that width to #' save horizontal space. Set to `Inf` to turn off truncation of column #' titles. - # pillar_option_get_min_title_chars - # pillar_option_set_min_title_chars + # get_pillar_option_min_title_chars + # set_pillar_option_min_title_chars min_title_chars = make_option_impl( getOption("pillar.min_title_chars", default = 15L) ), @@ -70,15 +75,19 @@ pillar_options <- list2( #' display character columns, default: `3`. Character columns may be #' truncated up to that width to save horizontal space. Set to `Inf` to #' turn off truncation of character columns. - # pillar_option_get_min_chars - # pillar_option_set_min_chars - min_chars = make_option_impl( - getOption("pillar.min_chars", default = 3L) - ), + # get_pillar_option_min_chars + # set_pillar_option_min_chars + min_chars = make_option_impl(option_name = "pillar.min_chars", { + min_chars <- getOption("pillar.min_chars", default = 3L) + if (!is.numeric(min_chars) || length(min_chars) != 1 || min_chars < 3L) { + inform("Option pillar.min_chars must be a nonnegative number greater or equal 3. Resetting to 3.") + set_pillar_option_min_chars(3L) + } + }), #' - `max_dec_width`: The maximum allowed width for decimal notation, #' default 13. - # pillar_option_get_max_dec_width - # pillar_option_set_max_dec_width + # get_pillar_option_max_dec_width + # set_pillar_option_max_dec_width max_dec_width = make_option_impl( getOption("pillar.max_dec_width", default = 13L) ), diff --git a/R/shaft-.R b/R/shaft-.R index 3567740e8..00b3f13e0 100644 --- a/R/shaft-.R +++ b/R/shaft-.R @@ -145,19 +145,14 @@ pillar_shaft_number <- function(x, sigfig, digits, notation, fixed_exponent) { } } if (is.null(sigfig)) { - sigfig <- pillar_option_get_sigfig() - if (!is.numeric(sigfig) || length(sigfig) != 1 || sigfig < 1L) { - inform("Option pillar.sigfig must be a positive number greater or equal 1. Resetting to 1.") - sigfig <- 1L - options(pillar.sigfig = sigfig) - } + sigfig <- get_pillar_option_sigfig() } if (is.null(notation) || notation == "fit") { dec <- split_decimal(x, sigfig = sigfig, digits = digits) sci <- split_decimal(x, sigfig = sigfig, digits = digits, sci_mod = 1, fixed_exponent = fixed_exponent) - max_dec_width <- pillar_option_get_max_dec_width() + max_dec_width <- get_pillar_option_max_dec_width() dec_width <- get_width(dec) "!!!!!!DEBUG `v(dec_width)`" @@ -281,12 +276,7 @@ pillar_shaft.character <- function(x, ..., min_width = NULL) { # determine width based on width of characters in the vector if (is.null(min_chars)) { - min_chars <- pillar_option_get_min_chars() - if (!is.numeric(min_chars) || length(min_chars) != 1 || min_chars < 3L) { - inform("Option pillar.min_chars must be a nonnegative number greater or equal 3. Resetting to 3.") - min_chars <- 3L - options(pillar.min_chars = min_chars) - } + min_chars <- get_pillar_option_min_chars() } pillar_shaft(new_vertical(out), ..., min_width = min_chars, na_indent = na_indent, shorten = pillar_attr$shorten) diff --git a/R/styles.R b/R/styles.R index a26e2bbef..cdb183440 100644 --- a/R/styles.R +++ b/R/styles.R @@ -23,7 +23,7 @@ keep_empty <- function(fun) { #' style_subtle("text") style_subtle <- keep_empty(function(x) { force(x) - if (isTRUE(pillar_option_get_subtle())) { + if (isTRUE(get_pillar_option_subtle())) { crayon_grey_0.6(x) } else { x @@ -39,7 +39,7 @@ style_subtle <- keep_empty(function(x) { #' @examples #' style_subtle_num(0.01 * 1:3, c(TRUE, FALSE, TRUE)) style_subtle_num <- function(x, negative) { - if (isTRUE(pillar_option_get_subtle_num())) { + if (isTRUE(get_pillar_option_subtle_num())) { style_subtle(x) } else { ifelse(negative, style_neg(x), x) @@ -48,7 +48,7 @@ style_subtle_num <- function(x, negative) { style_hint <- keep_empty(function(x) { force(x) - if (isTRUE(pillar_option_get_subtle())) { + if (isTRUE(get_pillar_option_subtle())) { crayon_grey_0.8(x) } else { x @@ -67,7 +67,7 @@ style_spark_na <- function(x) { #' @examples #' style_bold("Petal.Width") style_bold <- keep_empty(function(x) { - if (isTRUE(pillar_option_get_bold())) { + if (isTRUE(get_pillar_option_bold())) { crayon_bold(x) } else { x @@ -90,7 +90,7 @@ style_na <- function(x) { #' @examples #' style_neg("123") style_neg <- keep_empty(function(x) { - if (isTRUE(pillar_option_get_neg())) { + if (isTRUE(get_pillar_option_neg())) { crayon_red(x) } else { x diff --git a/R/title.R b/R/title.R index 7764e52b1..370412752 100644 --- a/R/title.R +++ b/R/title.R @@ -33,7 +33,7 @@ new_pillar_title <- function(x, ...) { } get_min_title_width <- function(width) { - title_chars <- pillar_option_get_min_title_chars() + title_chars <- get_pillar_option_min_title_chars() if (!is.numeric(title_chars) || length(title_chars) != 1 || title_chars < 0) { stop("Option pillar.min_title_chars must be a nonnegative number", call. = FALSE) } From dd182689f5927506e1882e1671efc67bbb579e0d Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Sat, 24 Jul 2021 17:14:15 +0200 Subject: [PATCH 007/147] Add tests --- R/aaa-options.R | 2 +- R/options.R | 7 +- tests/testthat/test-options.R | 120 ++++++++++++++++++++++++++++++++++ 3 files changed, 126 insertions(+), 3 deletions(-) create mode 100644 tests/testthat/test-options.R diff --git a/R/aaa-options.R b/R/aaa-options.R index b4dbed194..b64a7fa25 100644 --- a/R/aaa-options.R +++ b/R/aaa-options.R @@ -13,7 +13,7 @@ make_option_impl <- function(getter, option_name = NULL, env = caller_env()) { local_setter_body <- expr( { - !!call2("local_options", !!option_name := sym("value"), .frame = sym("env")) + out <- !!call2("local_options", !!option_name := sym("value"), .frame = sym("env")) !!call2(getter_name) invisible(out[[1]]) } diff --git a/R/options.R b/R/options.R index 12450736c..6057ed53d 100644 --- a/R/options.R +++ b/R/options.R @@ -58,7 +58,8 @@ pillar_options <- list2( sigfig <- getOption("pillar.sigfig", default = 3L) if (!is.numeric(sigfig) || length(sigfig) != 1 || sigfig < 1L) { inform("Option pillar.sigfig must be a positive number greater or equal 1. Resetting to 3.") - set_pillar_option_sigfig(3L) + sigfig <- 3L + set_pillar_option_sigfig(sigfig) } sigfig }), @@ -81,8 +82,10 @@ pillar_options <- list2( min_chars <- getOption("pillar.min_chars", default = 3L) if (!is.numeric(min_chars) || length(min_chars) != 1 || min_chars < 3L) { inform("Option pillar.min_chars must be a nonnegative number greater or equal 3. Resetting to 3.") - set_pillar_option_min_chars(3L) + min_chars <- 3L + set_pillar_option_min_chars(min_chars) } + min_chars }), #' - `max_dec_width`: The maximum allowed width for decimal notation, #' default 13. diff --git a/tests/testthat/test-options.R b/tests/testthat/test-options.R new file mode 100644 index 000000000..eade4f493 --- /dev/null +++ b/tests/testthat/test-options.R @@ -0,0 +1,120 @@ +test_that("bold", { + value <- 0L + + orig <- get_pillar_option_bold() + old <- set_pillar_option_bold(value) + expect_equal(get_pillar_option_bold(), value) + expect_equal(set_pillar_option_bold(old), value) + + local({ + expect_equal(local_pillar_option_bold(value), old) + expect_equal(get_pillar_option_bold(), value) + }) + expect_equal(get_pillar_option_bold(), orig) +}) + +test_that("subtle", { + value <- 0L + + orig <- get_pillar_option_subtle() + old <- set_pillar_option_subtle(value) + expect_equal(get_pillar_option_subtle(), value) + expect_equal(set_pillar_option_subtle(old), value) + + local({ + expect_equal(local_pillar_option_subtle(value), old) + expect_equal(get_pillar_option_subtle(), value) + }) + expect_equal(get_pillar_option_subtle(), orig) +}) + +test_that("subtle_num", { + value <- 0L + + orig <- get_pillar_option_subtle_num() + old <- set_pillar_option_subtle_num(value) + expect_equal(get_pillar_option_subtle_num(), value) + expect_equal(set_pillar_option_subtle_num(old), value) + + local({ + expect_equal(local_pillar_option_subtle_num(value), old) + expect_equal(get_pillar_option_subtle_num(), value) + }) + expect_equal(get_pillar_option_subtle_num(), orig) +}) + +test_that("neg", { + value <- 0L + + orig <- get_pillar_option_neg() + old <- set_pillar_option_neg(value) + expect_equal(get_pillar_option_neg(), value) + expect_equal(set_pillar_option_neg(old), value) + + local({ + expect_equal(local_pillar_option_neg(value), old) + expect_equal(get_pillar_option_neg(), value) + }) + expect_equal(get_pillar_option_neg(), orig) +}) + +test_that("sigfig", { + value <- 5L + + orig <- get_pillar_option_sigfig() + old <- set_pillar_option_sigfig(value) + expect_equal(get_pillar_option_sigfig(), value) + expect_equal(set_pillar_option_sigfig(old), value) + + local({ + expect_equal(local_pillar_option_sigfig(value), old) + expect_equal(get_pillar_option_sigfig(), value) + }) + expect_equal(get_pillar_option_sigfig(), orig) +}) + +test_that("min_title_chars", { + value <- 12L + + orig <- get_pillar_option_min_title_chars() + old <- set_pillar_option_min_title_chars(value) + expect_equal(get_pillar_option_min_title_chars(), value) + expect_equal(set_pillar_option_min_title_chars(old), value) + + local({ + expect_equal(local_pillar_option_min_title_chars(value), old) + expect_equal(get_pillar_option_min_title_chars(), value) + }) + expect_equal(get_pillar_option_min_title_chars(), orig) +}) + +test_that("min_chars", { + value <- 5L + + orig <- get_pillar_option_min_chars() + old <- set_pillar_option_min_chars(value) + expect_equal(get_pillar_option_min_chars(), value) + expect_equal(set_pillar_option_min_chars(old), value) + + local({ + expect_equal(local_pillar_option_min_chars(value), old) + expect_equal(get_pillar_option_min_chars(), value) + }) + expect_equal(get_pillar_option_min_chars(), orig) +}) + +test_that("max_dec_width", { + value <- 0L + + orig <- get_pillar_option_max_dec_width() + old <- set_pillar_option_max_dec_width(value) + expect_equal(get_pillar_option_max_dec_width(), value) + expect_equal(set_pillar_option_max_dec_width(old), value) + + local({ + expect_equal(local_pillar_option_max_dec_width(value), old) + expect_equal(get_pillar_option_max_dec_width(), value) + }) + expect_equal(get_pillar_option_max_dec_width(), orig) +}) + From 0567b1f4be282cc8010c72f919705dc502e4b3b8 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Sat, 24 Jul 2021 17:33:33 +0200 Subject: [PATCH 008/147] Fix interface --- R/aaa-options.R | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/R/aaa-options.R b/R/aaa-options.R index b64a7fa25..0fe39fb66 100644 --- a/R/aaa-options.R +++ b/R/aaa-options.R @@ -40,8 +40,8 @@ make_option_impl <- function(getter, option_name = NULL, env = caller_env()) { args <- pairlist2(value = , local = FALSE, env = quote(caller_env())) assign(getter_name, new_function(list(), getter_body, env = env), env) - assign(local_setter_name, new_function(args, local_setter_body, env = env), env) - assign(setter_name, new_function(pairlist2(value = ), setter_body, env = env), env) + assign(local_setter_name, new_function(args[c(1, 3)], local_setter_body, env = env), env) + assign(setter_name, new_function(args[1], setter_body, env = env), env) new_function(args, body, env = env) } From 6669591ca6175e0f2b23512216fa7c70abf537ee Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Sat, 24 Jul 2021 17:34:18 +0200 Subject: [PATCH 009/147] Explicit examples, for CRAN --- R/aaa-options.R | 13 ------------- R/options.R | 21 +++++++++++++++++++-- man/pillar_options.Rd | 24 +++++++++++++++++++++--- 3 files changed, 40 insertions(+), 18 deletions(-) diff --git a/R/aaa-options.R b/R/aaa-options.R index 0fe39fb66..611f814ef 100644 --- a/R/aaa-options.R +++ b/R/aaa-options.R @@ -45,16 +45,3 @@ make_option_impl <- function(getter, option_name = NULL, env = caller_env()) { new_function(args, body, env = env) } - -option_usage <- function(env = caller_env()) { - pkg_name <- utils::packageName(env) - options <- get(paste0(pkg_name, "_options"), env) - first_option <- names(options)[[1]] - - c( - "@usage", - paste0('pillar_options$bold(value, local = FALSE) # same as: options(', pkg_name, ".", first_option, " = value)"), - "", - paste0('pillar_options$bold() # similar to: getOption("', pkg_name, ".", first_option, '")') - ) -} diff --git a/R/options.R b/R/options.R index 6057ed53d..cb03fd1c2 100644 --- a/R/options.R +++ b/R/options.R @@ -16,9 +16,26 @@ #' `pillar_options$foo(value)` is equivalent to #' `options(pillar.foo = value)`. #' -#' @eval option_usage() -#' #' @export +#' @examples +#' # Default setting: +#' pillar_options$sigfig() +#' pillar(1.234567) +#' +#' # Change for the duration of the session: +#' old <- pillar_options$sigfig(6) +#' pillar(1.234567) +#' +#' # Change back to the original value: +#' pillar_options$sigfig(old) +#' pillar(1.234567) +#' +#' # Local scope: +#' local({ +#' pillar_options$sigfig(6, local = TRUE) +#' pillar(1.234567) +#' }) +#' pillar(1.234567) #' @section Options for the pillar package: pillar_options <- list2( # get_pillar_option_bold diff --git a/man/pillar_options.Rd b/man/pillar_options.Rd index 71e253458..26c543f6d 100644 --- a/man/pillar_options.Rd +++ b/man/pillar_options.Rd @@ -8,9 +8,7 @@ An object of class \code{list} of length 8. } \usage{ -pillar_options$bold(value, local = FALSE) # same as: options(pillar.bold = value) - -pillar_options$bold() # similar to: getOption("pillar.bold") +pillar_options } \description{ Options that affect display of tibble-like output. @@ -57,4 +55,24 @@ default 13. } } +\examples{ +# Default setting: +pillar_options$sigfig() +pillar(1.234567) + +# Change for the duration of the session: +old <- pillar_options$sigfig(6) +pillar(1.234567) + +# Change back to the original value: +pillar_options$sigfig(old) +pillar(1.234567) + +# Local scope: +local({ + pillar_options$sigfig(6, local = TRUE) + pillar(1.234567) +}) +pillar(1.234567) +} \keyword{datasets} From 16187db928e866922af6596673bc8922a489fb55 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Sat, 24 Jul 2021 17:34:22 +0200 Subject: [PATCH 010/147] Tweak tests --- tests/testthat/test-options.R | 80 ++++++++++++++++++++++++++++------- 1 file changed, 64 insertions(+), 16 deletions(-) diff --git a/tests/testthat/test-options.R b/tests/testthat/test-options.R index eade4f493..71d3a2bd2 100644 --- a/tests/testthat/test-options.R +++ b/tests/testthat/test-options.R @@ -2,12 +2,18 @@ test_that("bold", { value <- 0L orig <- get_pillar_option_bold() + expect_identical(orig, pillar_options$bold()) + old <- set_pillar_option_bold(value) expect_equal(get_pillar_option_bold(), value) - expect_equal(set_pillar_option_bold(old), value) + expect_equal(expect_invisible(set_pillar_option_bold(old)), value) + + old <- pillar_options$bold(value) + expect_equal(pillar_options$bold(), value) + expect_equal(expect_invisible(pillar_options$bold(old)), value) local({ - expect_equal(local_pillar_option_bold(value), old) + expect_equal(expect_invisible(local_pillar_option_bold(value)), old) expect_equal(get_pillar_option_bold(), value) }) expect_equal(get_pillar_option_bold(), orig) @@ -17,12 +23,18 @@ test_that("subtle", { value <- 0L orig <- get_pillar_option_subtle() + expect_identical(orig, pillar_options$subtle()) + old <- set_pillar_option_subtle(value) expect_equal(get_pillar_option_subtle(), value) - expect_equal(set_pillar_option_subtle(old), value) + expect_equal(expect_invisible(set_pillar_option_subtle(old)), value) + + old <- pillar_options$subtle(value) + expect_equal(pillar_options$subtle(), value) + expect_equal(expect_invisible(pillar_options$subtle(old)), value) local({ - expect_equal(local_pillar_option_subtle(value), old) + expect_equal(expect_invisible(local_pillar_option_subtle(value)), old) expect_equal(get_pillar_option_subtle(), value) }) expect_equal(get_pillar_option_subtle(), orig) @@ -32,12 +44,18 @@ test_that("subtle_num", { value <- 0L orig <- get_pillar_option_subtle_num() + expect_identical(orig, pillar_options$subtle_num()) + old <- set_pillar_option_subtle_num(value) expect_equal(get_pillar_option_subtle_num(), value) - expect_equal(set_pillar_option_subtle_num(old), value) + expect_equal(expect_invisible(set_pillar_option_subtle_num(old)), value) + + old <- pillar_options$subtle_num(value) + expect_equal(pillar_options$subtle_num(), value) + expect_equal(expect_invisible(pillar_options$subtle_num(old)), value) local({ - expect_equal(local_pillar_option_subtle_num(value), old) + expect_equal(expect_invisible(local_pillar_option_subtle_num(value)), old) expect_equal(get_pillar_option_subtle_num(), value) }) expect_equal(get_pillar_option_subtle_num(), orig) @@ -47,12 +65,18 @@ test_that("neg", { value <- 0L orig <- get_pillar_option_neg() + expect_identical(orig, pillar_options$neg()) + old <- set_pillar_option_neg(value) expect_equal(get_pillar_option_neg(), value) - expect_equal(set_pillar_option_neg(old), value) + expect_equal(expect_invisible(set_pillar_option_neg(old)), value) + + old <- pillar_options$neg(value) + expect_equal(pillar_options$neg(), value) + expect_equal(expect_invisible(pillar_options$neg(old)), value) local({ - expect_equal(local_pillar_option_neg(value), old) + expect_equal(expect_invisible(local_pillar_option_neg(value)), old) expect_equal(get_pillar_option_neg(), value) }) expect_equal(get_pillar_option_neg(), orig) @@ -62,12 +86,18 @@ test_that("sigfig", { value <- 5L orig <- get_pillar_option_sigfig() + expect_identical(orig, pillar_options$sigfig()) + old <- set_pillar_option_sigfig(value) expect_equal(get_pillar_option_sigfig(), value) - expect_equal(set_pillar_option_sigfig(old), value) + expect_equal(expect_invisible(set_pillar_option_sigfig(old)), value) + + old <- pillar_options$sigfig(value) + expect_equal(pillar_options$sigfig(), value) + expect_equal(expect_invisible(pillar_options$sigfig(old)), value) local({ - expect_equal(local_pillar_option_sigfig(value), old) + expect_equal(expect_invisible(local_pillar_option_sigfig(value)), old) expect_equal(get_pillar_option_sigfig(), value) }) expect_equal(get_pillar_option_sigfig(), orig) @@ -77,12 +107,18 @@ test_that("min_title_chars", { value <- 12L orig <- get_pillar_option_min_title_chars() + expect_identical(orig, pillar_options$min_title_chars()) + old <- set_pillar_option_min_title_chars(value) expect_equal(get_pillar_option_min_title_chars(), value) - expect_equal(set_pillar_option_min_title_chars(old), value) + expect_equal(expect_invisible(set_pillar_option_min_title_chars(old)), value) + + old <- pillar_options$min_title_chars(value) + expect_equal(pillar_options$min_title_chars(), value) + expect_equal(expect_invisible(pillar_options$min_title_chars(old)), value) local({ - expect_equal(local_pillar_option_min_title_chars(value), old) + expect_equal(expect_invisible(local_pillar_option_min_title_chars(value)), old) expect_equal(get_pillar_option_min_title_chars(), value) }) expect_equal(get_pillar_option_min_title_chars(), orig) @@ -92,12 +128,18 @@ test_that("min_chars", { value <- 5L orig <- get_pillar_option_min_chars() + expect_identical(orig, pillar_options$min_chars()) + old <- set_pillar_option_min_chars(value) expect_equal(get_pillar_option_min_chars(), value) - expect_equal(set_pillar_option_min_chars(old), value) + expect_equal(expect_invisible(set_pillar_option_min_chars(old)), value) + + old <- pillar_options$min_chars(value) + expect_equal(pillar_options$min_chars(), value) + expect_equal(expect_invisible(pillar_options$min_chars(old)), value) local({ - expect_equal(local_pillar_option_min_chars(value), old) + expect_equal(expect_invisible(local_pillar_option_min_chars(value)), old) expect_equal(get_pillar_option_min_chars(), value) }) expect_equal(get_pillar_option_min_chars(), orig) @@ -107,12 +149,18 @@ test_that("max_dec_width", { value <- 0L orig <- get_pillar_option_max_dec_width() + expect_identical(orig, pillar_options$max_dec_width()) + old <- set_pillar_option_max_dec_width(value) expect_equal(get_pillar_option_max_dec_width(), value) - expect_equal(set_pillar_option_max_dec_width(old), value) + expect_equal(expect_invisible(set_pillar_option_max_dec_width(old)), value) + + old <- pillar_options$max_dec_width(value) + expect_equal(pillar_options$max_dec_width(), value) + expect_equal(expect_invisible(pillar_options$max_dec_width(old)), value) local({ - expect_equal(local_pillar_option_max_dec_width(value), old) + expect_equal(expect_invisible(local_pillar_option_max_dec_width(value)), old) expect_equal(get_pillar_option_max_dec_width(), value) }) expect_equal(get_pillar_option_max_dec_width(), orig) From 449cc398628385be8bae0c5fb6956efdddf103d7 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Sat, 24 Jul 2021 17:37:55 +0200 Subject: [PATCH 011/147] Fix R CMD check warning --- R/aaa-options.R | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/R/aaa-options.R b/R/aaa-options.R index 611f814ef..d4615b643 100644 --- a/R/aaa-options.R +++ b/R/aaa-options.R @@ -28,7 +28,7 @@ make_option_impl <- function(getter, option_name = NULL, env = caller_env()) { ) body <- expr({ - if (missing(value)) { + if (missing(!!sym("value"))) { if (!missing(local)) { abort("Can't pass `local` argument if `value` is missing.") } From 6fe5904343a2a083864eb05ad6ad005bf1053bc6 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Sat, 24 Jul 2021 18:02:49 +0200 Subject: [PATCH 012/147] - Avoid mangling of duplicate column names in footer (#332). Closes #332. --- R/ctl_colonnade.R | 2 +- tests/testthat/_snaps/tbl-format-footer.md | 24 ++++++++++------------ 2 files changed, 12 insertions(+), 14 deletions(-) diff --git a/R/ctl_colonnade.R b/R/ctl_colonnade.R index dfb41a85e..9292e91c4 100644 --- a/R/ctl_colonnade.R +++ b/R/ctl_colonnade.R @@ -56,7 +56,7 @@ ctl_colonnade <- function(x, has_row_id = TRUE, width = NULL, controller = new_t out <- map(flat_tiers, format_colonnade_tier_2) - extra_cols <- x[seq2(length(pillars) + 1L, nc)] + extra_cols <- as.list(x)[seq2(length(pillars) + 1L, nc)] new_colonnade_body(out, extra_cols = extra_cols) } diff --git a/tests/testthat/_snaps/tbl-format-footer.md b/tests/testthat/_snaps/tbl-format-footer.md index 8f91e1b86..f3eb98026 100644 --- a/tests/testthat/_snaps/tbl-format-footer.md +++ b/tests/testthat/_snaps/tbl-format-footer.md @@ -66,17 +66,15 @@ # p , q , r , s , t , u , v , # w , x , y , z , a , b , c , # d , e , f , g , h , i , j , - # k , l.1 , m.1 , n.1 , o.1 , p.1 , - # q.1 , r.1 , s.1 , t.1 , u.1 , v.1 , - # w.1 , x.1 , y.1 , z.1 , a.1 , b.1 , - # c.1 , d.1 , e.1 , f.1 , g.1 , h.1 , - # i.1 , j.1 , k.1 , l.2 , m.2 , n.2 , - # o.2 , p.2 , q.2 , r.2 , s.2 , t.2 , - # u.2 , v.2 , w.2 , x.2 , y.2 , z.2 , - # a.2 , b.2 , c.2 , d.2 , e.2 , f.2 , - # g.2 , h.2 , i.2 , j.2 , k.2 , l.3 , - # m.3 , n.3 , o.3 , p.3 , q.3 , r.3 , - # s.3 , t.3 , u.3 , v.3 , w.3 , x.3 , - # y.3 , z.3 , a.3 , b.3 , c.3 , d.3 , - # e.3 , f.3 , g.3 , ... + # k , l , m , n , o , p , q , + # r , s , t , u , v , w , x , + # y , z , a , b , c , d , e , + # f , g , h , i , j , k , l , + # m , n , o , p , q , r , s , + # t , u , v , w , x , y , z , + # a , b , c , d , e , f , g , + # h , i , j , k , l , m , n , + # o , p , q , r , s , t , u , + # v , w , x , y , z , a , b , + # c , d , e , f , g , ... From 401354a4354dc675e8f89c4576d646605eca5ada Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Sat, 24 Jul 2021 18:17:56 +0200 Subject: [PATCH 013/147] Tweak with examplesIf --- R/type.R | 7 +++++++ man/format_type_sum.Rd | 6 ++++++ 2 files changed, 13 insertions(+) diff --git a/R/type.R b/R/type.R index dafe22f72..130b2aa6e 100644 --- a/R/type.R +++ b/R/type.R @@ -76,6 +76,13 @@ format_full_pillar_type <- function(x) { #' type_sum.accel <- function(x) { #' I("kg m/s^2") #' } +#' +#' @examplesIf Sys.getenv("IN_PKGDOWN") != "" +#' # Necessary in pkgdown +#' registerS3method("type_sum", "accel", type_sum.accel) +#' +#' @examples +#' #' accel <- structure(9.81, class = "accel") #' pillar(accel) format_type_sum <- function(x, width, ...) { diff --git a/man/format_type_sum.Rd b/man/format_type_sum.Rd index edd96c341..29da87557 100644 --- a/man/format_type_sum.Rd +++ b/man/format_type_sum.Rd @@ -40,6 +40,12 @@ pillar(1) type_sum.accel <- function(x) { I("kg m/s^2") } + +\dontshow{if (Sys.getenv("IN_PKGDOWN") != "") (if (getRversion() >= "3.4") withAutoprint else force)(\{ # examplesIf} +# Necessary in pkgdown +registerS3method("type_sum", "accel", type_sum.accel) +\dontshow{\}) # examplesIf} + accel <- structure(9.81, class = "accel") pillar(accel) } From c6585f6cc2c6f33d0280263e80d0cf6a69931d6b Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Sat, 24 Jul 2021 18:37:59 +0200 Subject: [PATCH 014/147] Hack: full-fledged method in pkgdown --- R/type.R | 11 +++++------ R/zzz.R | 5 +++++ man/format_type_sum.Rd | 5 ----- 3 files changed, 10 insertions(+), 11 deletions(-) diff --git a/R/type.R b/R/type.R index 130b2aa6e..ea974e21b 100644 --- a/R/type.R +++ b/R/type.R @@ -77,12 +77,6 @@ format_full_pillar_type <- function(x) { #' I("kg m/s^2") #' } #' -#' @examplesIf Sys.getenv("IN_PKGDOWN") != "" -#' # Necessary in pkgdown -#' registerS3method("type_sum", "accel", type_sum.accel) -#' -#' @examples -#' #' accel <- structure(9.81, class = "accel") #' pillar(accel) format_type_sum <- function(x, width, ...) { @@ -93,6 +87,11 @@ format_type_sum <- function(x, width, ...) { UseMethod("format_type_sum") } +# https://github.com/r-lib/pkgdown/issues/1540 +type_sum.accel <- function(x) { + I("kg m/s^2") +} + #' @export #' @rdname format_type_sum format_type_sum.default <- function(x, width, ...) { diff --git a/R/zzz.R b/R/zzz.R index 3e464b5a1..2ba70d656 100644 --- a/R/zzz.R +++ b/R/zzz.R @@ -58,6 +58,11 @@ NULL debug_info() } + # https://github.com/r-lib/pkgdown/issues/1540 + if (Sys.getenv("IN_PKGDOWN") != "") { + register_s3_method("pillar", "type_sum", "accel") + } + invisible() } diff --git a/man/format_type_sum.Rd b/man/format_type_sum.Rd index 29da87557..2864f31ee 100644 --- a/man/format_type_sum.Rd +++ b/man/format_type_sum.Rd @@ -41,11 +41,6 @@ type_sum.accel <- function(x) { I("kg m/s^2") } -\dontshow{if (Sys.getenv("IN_PKGDOWN") != "") (if (getRversion() >= "3.4") withAutoprint else force)(\{ # examplesIf} -# Necessary in pkgdown -registerS3method("type_sum", "accel", type_sum.accel) -\dontshow{\}) # examplesIf} - accel <- structure(9.81, class = "accel") pillar(accel) } From afbccf1c456aa3b44e0df0b9678f5346ee234f06 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Sun, 25 Jul 2021 06:07:24 +0200 Subject: [PATCH 015/147] Show total width next to tier width in tests --- tests/testthat/_snaps/ctl_colonnade_1.md | 90 ++++++++++++++++-------- tests/testthat/_snaps/ctl_colonnade_2.md | 90 ++++++++++++++++-------- tests/testthat/test-ctl_colonnade_1.R | 63 ++++++++--------- tests/testthat/test-ctl_colonnade_2.R | 59 ++++++++-------- 4 files changed, 180 insertions(+), 122 deletions(-) diff --git a/tests/testthat/_snaps/ctl_colonnade_1.md b/tests/testthat/_snaps/ctl_colonnade_1.md index f55fa8bcb..300cfdd46 100644 --- a/tests/testthat/_snaps/ctl_colonnade_1.md +++ b/tests/testthat/_snaps/ctl_colonnade_1.md @@ -1,11 +1,13 @@ # strings with varying widths Code - options(width = 59) ctl_colonnade(df_str[c(12L, 33L, 36L, 7L, 41L, 3L, 18L, 23L, 13L, 44L, 14L, 16L, 25L, 21L, 19L, 45L, 43L, 29L, 1L, 30L, 22L, 27L, 15L, 47L, 28L, 31L, 10L, 50L, 4L, 40L, 42L, 8L, 6L, 9L, 24L, 48L, 38L, 37L, 34L, 49L, 46L, 2L, 32L, 35L, - 39L, 11L, 17L, 5L, 26L, 20L)], width = 1382) + 39L, 11L, 17L, 5L, 26L, 20L)], width = { + options(width = 59) + 1382 + }) Output $body `12` `33` @@ -85,11 +87,13 @@ named list() Code - options(width = 54) ctl_colonnade(df_str[c(40L, 28L, 7L, 16L, 48L, 6L, 21L, 1L, 20L, 17L, 47L, 45L, 29L, 41L, 49L, 34L, 4L, 39L, 18L, 36L, 26L, 38L, 10L, 8L, 5L, 15L, 44L, 24L, 46L, 14L, 25L, 27L, 3L, 37L, 35L, 12L, 9L, 13L, 22L, 33L, 42L, 11L, 19L, 50L, - 23L, 30L, 32L, 2L, 43L, 31L)], width = 837) + 23L, 30L, 32L, 2L, 43L, 31L)], width = { + options(width = 54) + 837 + }) Output $body `40` @@ -145,11 +149,13 @@ named list() Code - options(width = 32) ctl_colonnade(df_str[c(47L, 42L, 4L, 46L, 9L, 34L, 19L, 39L, 8L, 32L, 36L, 12L, 29L, 5L, 15L, 11L, 31L, 27L, 33L, 28L, 43L, 6L, 13L, 22L, 14L, 16L, 35L, 50L, 38L, 7L, 23L, 45L, 40L, 3L, 2L, 24L, 41L, 10L, 30L, 25L, 17L, 26L, 48L, 37L, - 49L, 1L, 18L, 21L, 44L, 20L)], width = 455) + 49L, 1L, 18L, 21L, 44L, 20L)], width = { + options(width = 32) + 455 + }) Output $body `47` @@ -202,11 +208,13 @@ named list() Code - options(width = 55) ctl_colonnade(df_str[c(41L, 4L, 25L, 31L, 8L, 22L, 19L, 10L, 29L, 21L, 34L, 5L, 26L, 36L, 47L, 46L, 2L, 24L, 27L, 39L, 28L, 43L, 32L, 30L, 48L, 44L, 6L, 20L, 13L, 15L, 18L, 42L, 9L, 12L, 37L, 45L, 16L, 40L, 11L, 14L, 38L, 1L, 7L, 3L, - 23L, 35L, 50L, 17L, 49L, 33L)], width = 855) + 23L, 35L, 50L, 17L, 49L, 33L)], width = { + options(width = 55) + 855 + }) Output $body `41` `4` @@ -262,11 +270,13 @@ named list() Code - options(width = 54) ctl_colonnade(df_str[c(27L, 22L, 9L, 23L, 16L, 19L, 25L, 31L, 44L, 1L, 28L, 46L, 12L, 20L, 43L, 37L, 5L, 2L, 18L, 41L, 26L, 33L, 11L, 49L, 24L, 35L, 4L, 47L, 30L, 7L, 34L, 3L, 32L, 42L, 10L, 45L, 38L, 39L, 48L, 14L, 6L, 17L, 36L, 50L, - 40L, 13L, 8L, 21L, 15L, 29L)], width = 552) + 40L, 13L, 8L, 21L, 15L, 29L)], width = { + options(width = 54) + 552 + }) Output $body `27` `22` @@ -307,11 +317,13 @@ named list() Code - options(width = 49) ctl_colonnade(df_str[c(32L, 24L, 18L, 25L, 26L, 13L, 33L, 2L, 50L, 38L, 37L, 16L, 27L, 9L, 28L, 49L, 34L, 15L, 17L, 35L, 22L, 47L, 3L, 21L, 23L, 41L, 5L, 1L, 14L, 46L, 30L, 31L, 44L, 4L, 7L, 40L, 43L, 12L, 29L, 8L, 36L, 45L, 11L, - 20L, 10L, 6L, 19L, 48L, 39L, 42L)], width = 1031) + 20L, 10L, 6L, 19L, 48L, 39L, 42L)], width = { + options(width = 49) + 1031 + }) Output $body `32` @@ -385,11 +397,13 @@ named list() Code - options(width = 38) ctl_colonnade(df_str[c(44L, 34L, 49L, 9L, 15L, 16L, 1L, 10L, 40L, 29L, 26L, 22L, 4L, 43L, 20L, 17L, 46L, 33L, 35L, 32L, 2L, 12L, 8L, 37L, 23L, 39L, 7L, 18L, 36L, 42L, 6L, 30L, 19L, 25L, 5L, 21L, 47L, 50L, 28L, 11L, 31L, 14L, 24L, 27L, - 45L, 41L, 38L, 3L, 13L, 48L)], width = 429) + 45L, 41L, 38L, 3L, 13L, 48L)], width = { + options(width = 38) + 429 + }) Output $body `44` @@ -433,11 +447,13 @@ named list() Code - options(width = 54) ctl_colonnade(df_str[c(21L, 26L, 8L, 22L, 41L, 24L, 13L, 5L, 47L, 37L, 4L, 42L, 19L, 34L, 11L, 43L, 38L, 3L, 33L, 20L, 31L, 2L, 18L, 48L, 27L, 44L, 9L, 35L, 30L, 6L, 49L, 10L, 1L, 16L, 46L, 29L, 12L, 14L, 45L, 36L, 15L, 39L, 50L, 23L, - 17L, 28L, 7L, 32L, 40L, 25L)], width = 633) + 17L, 28L, 7L, 32L, 40L, 25L)], width = { + options(width = 54) + 633 + }) Output $body `21` `26` @@ -481,11 +497,13 @@ named list() Code - options(width = 39) ctl_colonnade(df_str[c(23L, 49L, 13L, 37L, 3L, 25L, 36L, 4L, 9L, 7L, 27L, 48L, 12L, 10L, 50L, 14L, 38L, 39L, 46L, 22L, 28L, 8L, 21L, 44L, 32L, 40L, 31L, 1L, 29L, 34L, 35L, 33L, 19L, 15L, 41L, 20L, 47L, 18L, 16L, 45L, 6L, 5L, 24L, 26L, - 43L, 11L, 42L, 30L, 17L, 2L)], width = 1496) + 43L, 11L, 42L, 30L, 17L, 2L)], width = { + options(width = 39) + 1496 + }) Output $body `23` @@ -610,11 +628,13 @@ named list() Code - options(width = 31) ctl_colonnade(df_str[c(45L, 14L, 49L, 24L, 22L, 31L, 42L, 18L, 16L, 47L, 25L, 4L, 37L, 8L, 26L, 21L, 50L, 5L, 41L, 30L, 2L, 33L, 34L, 3L, 44L, 19L, 43L, 6L, 32L, 29L, 20L, 1L, 13L, 11L, 40L, 12L, 48L, 23L, 9L, 15L, 46L, 36L, 27L, 35L, - 28L, 10L, 7L, 39L, 17L, 38L)], width = 493) + 28L, 10L, 7L, 39L, 17L, 38L)], width = { + options(width = 31) + 493 + }) Output $body `45` @@ -670,11 +690,13 @@ named list() Code - options(width = 52) ctl_colonnade(df_str[c(38L, 46L, 17L, 11L, 24L, 18L, 16L, 39L, 50L, 42L, 6L, 13L, 37L, 29L, 41L, 47L, 9L, 33L, 44L, 31L, 45L, 36L, 28L, 5L, 10L, 30L, 20L, 1L, 14L, 43L, 49L, 23L, 26L, 21L, 32L, 19L, 34L, 15L, 48L, 4L, 7L, 35L, 40L, - 8L, 22L, 3L, 25L, 12L, 27L, 2L)], width = 1130) + 8L, 22L, 3L, 25L, 12L, 27L, 2L)], width = { + options(width = 52) + 1130 + }) Output $body `38` @@ -748,11 +770,13 @@ named list() Code - options(width = 58) ctl_colonnade(df_str[c(17L, 28L, 29L, 27L, 20L, 31L, 43L, 30L, 32L, 48L, 10L, 50L, 13L, 12L, 36L, 21L, 46L, 33L, 25L, 35L, 1L, 5L, 16L, 34L, 18L, 42L, 3L, 11L, 40L, 26L, 37L, 7L, 39L, 6L, 4L, 19L, 8L, 45L, 14L, 24L, 23L, 2L, 47L, 9L, - 49L, 41L, 38L, 22L, 44L, 15L)], width = 1310) + 49L, 41L, 38L, 22L, 44L, 15L)], width = { + options(width = 58) + 1310 + }) Output $body `17` `28` @@ -829,11 +853,13 @@ named list() Code - options(width = 47) ctl_colonnade(df_str[c(1L, 26L, 20L, 12L, 49L, 16L, 24L, 4L, 15L, 47L, 8L, 11L, 14L, 50L, 17L, 2L, 44L, 30L, 36L, 45L, 25L, 38L, 18L, 29L, 5L, 13L, 3L, 23L, 48L, 40L, 34L, 22L, 39L, 33L, 27L, 7L, 19L, 10L, 37L, 6L, 35L, 46L, 31L, 41L, - 43L, 28L, 42L, 32L, 21L, 9L)], width = 484) + 43L, 28L, 42L, 32L, 21L, 9L)], width = { + options(width = 47) + 484 + }) Output $body `1` `26` @@ -874,11 +900,13 @@ named list() Code - options(width = 55) ctl_colonnade(df_str[c(6L, 49L, 26L, 45L, 25L, 15L, 31L, 20L, 21L, 44L, 23L, 48L, 37L, 36L, 5L, 43L, 11L, 14L, 13L, 39L, 16L, 12L, 4L, 18L, 42L, 3L, 10L, 28L, 40L, 24L, 29L, 17L, 35L, 47L, 2L, 38L, 34L, 9L, 7L, 8L, 50L, 33L, 32L, - 27L, 46L, 19L, 22L, 41L, 30L, 1L)], width = 779) + 27L, 46L, 19L, 22L, 41L, 30L, 1L)], width = { + options(width = 55) + 779 + }) Output $body `6` @@ -931,11 +959,13 @@ named list() Code - options(width = 46) ctl_colonnade(df_str[c(38L, 42L, 41L, 10L, 40L, 11L, 27L, 9L, 17L, 37L, 46L, 13L, 36L, 18L, 31L, 20L, 39L, 12L, 44L, 33L, 50L, 34L, 26L, 32L, 23L, 30L, 29L, 21L, 4L, 49L, 19L, 25L, 3L, 6L, 15L, 14L, 43L, 48L, 8L, 22L, 1L, 2L, 45L, - 35L, 16L, 5L, 47L, 28L, 24L, 7L)], width = 694) + 35L, 16L, 5L, 47L, 28L, 24L, 7L)], width = { + options(width = 46) + 694 + }) Output $body `38` diff --git a/tests/testthat/_snaps/ctl_colonnade_2.md b/tests/testthat/_snaps/ctl_colonnade_2.md index 720114da3..adf72173c 100644 --- a/tests/testthat/_snaps/ctl_colonnade_2.md +++ b/tests/testthat/_snaps/ctl_colonnade_2.md @@ -1,11 +1,13 @@ # strings with varying widths Code - options(width = 54) ctl_colonnade(df_str[c(28L, 34L, 16L, 29L, 47L, 25L, 42L, 27L, 44L, 20L, 14L, 36L, 43L, 41L, 26L, 45L, 22L, 9L, 13L, 32L, 31L, 12L, 19L, 48L, 49L, 35L, 3L, 11L, 23L, 24L, 40L, 15L, 38L, 10L, 46L, 5L, 50L, 18L, 21L, 6L, 30L, 2L, 7L, - 1L, 4L, 8L, 17L, 33L, 39L, 37L)], width = 516) + 1L, 4L, 8L, 17L, 33L, 39L, 37L)], width = { + options(width = 54) + 516 + }) Output $body `28` @@ -43,11 +45,13 @@ named list() Code - options(width = 42) ctl_colonnade(df_str[c(28L, 41L, 12L, 29L, 13L, 43L, 24L, 50L, 48L, 35L, 44L, 21L, 33L, 45L, 47L, 34L, 25L, 14L, 18L, 23L, 7L, 3L, 42L, 36L, 11L, 2L, 20L, 31L, 1L, 4L, 38L, 9L, 27L, 40L, 32L, 17L, 6L, 49L, 16L, 19L, 15L, 22L, 39L, - 10L, 46L, 5L, 30L, 8L, 26L, 37L)], width = 1365) + 10L, 46L, 5L, 30L, 8L, 26L, 37L)], width = { + options(width = 42) + 1365 + }) Output $body `28` @@ -154,11 +158,13 @@ named list() Code - options(width = 39) ctl_colonnade(df_str[c(40L, 17L, 13L, 23L, 22L, 2L, 18L, 3L, 29L, 45L, 14L, 19L, 33L, 37L, 47L, 43L, 44L, 10L, 31L, 27L, 34L, 35L, 41L, 21L, 4L, 25L, 38L, 48L, 9L, 24L, 26L, 39L, 20L, 36L, 42L, 16L, 6L, 11L, 7L, 12L, 1L, 46L, 15L, 5L, 8L, - 50L, 32L, 30L, 49L, 28L)], width = 934) + 50L, 32L, 30L, 49L, 28L)], width = { + options(width = 39) + 934 + }) Output $body `40` @@ -238,11 +244,13 @@ named list() Code - options(width = 32) ctl_colonnade(df_str[c(11L, 36L, 17L, 14L, 31L, 35L, 23L, 13L, 6L, 44L, 45L, 22L, 21L, 18L, 33L, 10L, 43L, 2L, 46L, 34L, 3L, 19L, 1L, 38L, 9L, 37L, 5L, 8L, 25L, 49L, 27L, 29L, 15L, 39L, 24L, 40L, 48L, 26L, 47L, 42L, 41L, 12L, 28L, - 30L, 7L, 16L, 4L, 50L, 20L, 32L)], width = 565) + 30L, 7L, 16L, 4L, 50L, 20L, 32L)], width = { + options(width = 32) + 565 + }) Output $body `11` @@ -304,11 +312,13 @@ named list() Code - options(width = 35) ctl_colonnade(df_str[c(18L, 46L, 11L, 43L, 31L, 47L, 48L, 44L, 50L, 15L, 28L, 33L, 13L, 4L, 22L, 3L, 37L, 32L, 40L, 9L, 25L, 16L, 45L, 23L, 21L, 6L, 49L, 36L, 27L, 38L, 14L, 34L, 8L, 24L, 29L, 1L, 12L, 2L, 20L, 17L, 35L, 5L, 19L, - 30L, 7L, 26L, 42L, 41L, 39L, 10L)], width = 1121) + 30L, 7L, 26L, 42L, 41L, 39L, 10L)], width = { + options(width = 35) + 1121 + }) Output $body `18` @@ -415,11 +425,13 @@ named list() Code - options(width = 32) ctl_colonnade(df_str[c(43L, 1L, 3L, 15L, 28L, 12L, 46L, 34L, 31L, 7L, 11L, 4L, 44L, 8L, 9L, 5L, 36L, 22L, 17L, 39L, 18L, 45L, 37L, 13L, 29L, 6L, 30L, 16L, 20L, 10L, 19L, 26L, 33L, 40L, 35L, 48L, 38L, 25L, 2L, 47L, 42L, 41L, 27L, 14L, - 21L, 24L, 50L, 49L, 23L, 32L)], width = 446) + 21L, 24L, 50L, 49L, 23L, 32L)], width = { + options(width = 32) + 446 + }) Output $body `43` @@ -469,11 +481,13 @@ named list() Code - options(width = 31) ctl_colonnade(df_str[c(37L, 46L, 21L, 3L, 16L, 39L, 34L, 33L, 10L, 17L, 19L, 36L, 45L, 49L, 11L, 50L, 14L, 29L, 44L, 13L, 30L, 38L, 32L, 40L, 42L, 1L, 31L, 41L, 7L, 23L, 35L, 28L, 6L, 25L, 2L, 9L, 12L, 15L, 5L, 18L, 20L, 27L, 43L, 8L, - 47L, 4L, 48L, 24L, 26L, 22L)], width = 1166) + 47L, 4L, 48L, 24L, 26L, 22L)], width = { + options(width = 31) + 1166 + }) Output $body `37` @@ -595,11 +609,13 @@ named list() Code - options(width = 58) ctl_colonnade(df_str[c(31L, 39L, 40L, 30L, 10L, 21L, 9L, 16L, 46L, 25L, 15L, 24L, 3L, 50L, 35L, 1L, 12L, 34L, 48L, 4L, 29L, 23L, 37L, 36L, 28L, 43L, 11L, 17L, 32L, 8L, 41L, 13L, 44L, 7L, 38L, 26L, 33L, 20L, 19L, 2L, 18L, 49L, 27L, - 47L, 22L, 14L, 6L, 5L, 45L, 42L)], width = 546) + 47L, 22L, 14L, 6L, 5L, 45L, 42L)], width = { + options(width = 58) + 546 + }) Output $body `31` @@ -637,11 +653,13 @@ named list() Code - options(width = 57) ctl_colonnade(df_str[c(43L, 21L, 41L, 48L, 22L, 25L, 2L, 8L, 1L, 24L, 6L, 39L, 38L, 20L, 49L, 45L, 47L, 12L, 9L, 13L, 36L, 26L, 44L, 11L, 46L, 28L, 7L, 18L, 50L, 16L, 29L, 30L, 4L, 23L, 17L, 40L, 33L, 14L, 27L, 19L, 34L, 32L, 3L, 37L, - 15L, 10L, 5L, 35L, 31L, 42L)], width = 1035) + 15L, 10L, 5L, 35L, 31L, 42L)], width = { + options(width = 57) + 1035 + }) Output $body `43` @@ -706,11 +724,13 @@ named list() Code - options(width = 33) ctl_colonnade(df_str[c(40L, 6L, 25L, 5L, 26L, 17L, 19L, 2L, 11L, 34L, 45L, 24L, 22L, 44L, 35L, 7L, 4L, 49L, 1L, 36L, 12L, 41L, 39L, 13L, 48L, 27L, 18L, 30L, 42L, 28L, 3L, 46L, 21L, 20L, 16L, 29L, 50L, 10L, 9L, 8L, 47L, 31L, 14L, 38L, - 33L, 32L, 43L, 23L, 15L, 37L)], width = 1217) + 33L, 32L, 43L, 23L, 15L, 37L)], width = { + options(width = 33) + 1217 + }) Output $body `40` @@ -829,11 +849,13 @@ named list() Code - options(width = 32) ctl_colonnade(df_str[c(43L, 23L, 22L, 11L, 6L, 26L, 48L, 17L, 7L, 42L, 36L, 21L, 35L, 50L, 13L, 19L, 29L, 8L, 15L, 4L, 2L, 27L, 49L, 47L, 30L, 31L, 25L, 28L, 46L, 12L, 32L, 39L, 24L, 10L, 45L, 5L, 37L, 14L, 40L, 20L, 41L, 44L, 33L, 18L, - 38L, 3L, 1L, 34L, 16L, 9L)], width = 770) + 38L, 3L, 1L, 34L, 16L, 9L)], width = { + options(width = 32) + 770 + }) Output $body `43` @@ -916,11 +938,13 @@ named list() Code - options(width = 46) ctl_colonnade(df_str[c(5L, 24L, 43L, 46L, 35L, 39L, 18L, 26L, 8L, 27L, 2L, 50L, 6L, 14L, 29L, 47L, 9L, 16L, 36L, 4L, 13L, 41L, 3L, 28L, 37L, 33L, 38L, 31L, 34L, 19L, 42L, 32L, 1L, 45L, 15L, 7L, 11L, 49L, 23L, 12L, 48L, 20L, 21L, 44L, - 25L, 10L, 22L, 30L, 40L, 17L)], width = 1439) + 25L, 10L, 22L, 30L, 40L, 17L)], width = { + options(width = 46) + 1439 + }) Output $body `5` `24` @@ -1024,11 +1048,13 @@ named list() Code - options(width = 52) ctl_colonnade(df_str[c(7L, 44L, 19L, 21L, 18L, 35L, 23L, 50L, 33L, 37L, 25L, 26L, 10L, 39L, 2L, 47L, 42L, 14L, 9L, 41L, 45L, 6L, 4L, 11L, 24L, 43L, 32L, 3L, 38L, 5L, 49L, 27L, 17L, 8L, 22L, 40L, 12L, 15L, 1L, 28L, 31L, 29L, 13L, - 48L, 34L, 36L, 30L, 20L, 16L, 46L)], width = 1065) + 48L, 34L, 36L, 30L, 20L, 16L, 46L)], width = { + options(width = 52) + 1065 + }) Output $body `7` @@ -1099,11 +1125,13 @@ named list() Code - options(width = 35) ctl_colonnade(df_str[c(38L, 18L, 23L, 36L, 35L, 20L, 44L, 19L, 13L, 41L, 31L, 7L, 11L, 29L, 2L, 14L, 26L, 46L, 40L, 45L, 9L, 34L, 33L, 22L, 1L, 17L, 28L, 10L, 21L, 30L, 47L, 49L, 6L, 12L, 4L, 25L, 32L, 15L, 43L, 24L, 48L, 3L, 37L, - 50L, 42L, 39L, 16L, 8L, 27L, 5L)], width = 393) + 50L, 42L, 39L, 16L, 8L, 27L, 5L)], width = { + options(width = 35) + 393 + }) Output $body `38` @@ -1147,11 +1175,13 @@ named list() Code - options(width = 41) ctl_colonnade(df_str[c(22L, 9L, 11L, 26L, 19L, 16L, 32L, 25L, 1L, 30L, 31L, 6L, 24L, 10L, 39L, 21L, 50L, 7L, 29L, 12L, 46L, 43L, 15L, 35L, 20L, 40L, 49L, 38L, 36L, 48L, 34L, 3L, 8L, 4L, 27L, 42L, 44L, 33L, 45L, 18L, 5L, 2L, 13L, 47L, - 28L, 17L, 37L, 14L, 41L, 23L)], width = 999) + 28L, 17L, 37L, 14L, 41L, 23L)], width = { + options(width = 41) + 999 + }) Output $body `22` `9` diff --git a/tests/testthat/test-ctl_colonnade_1.R b/tests/testthat/test-ctl_colonnade_1.R index 041b3621c..c7390a253 100644 --- a/tests/testthat/test-ctl_colonnade_1.R +++ b/tests/testthat/test-ctl_colonnade_1.R @@ -4,36 +4,35 @@ test_that("strings with varying widths", { # Generated by data-raw/create-chr-tests.R # nolint start expect_snapshot({ - options(width = 59) - ctl_colonnade(df_str[c(12L, 33L, 36L, 7L, 41L, 3L, 18L, 23L, 13L, 44L, 14L, 16L, 25L, 21L, 19L, 45L, 43L, 29L, 1L, 30L, 22L, 27L, 15L, 47L, 28L, 31L, 10L, 50L, 4L, 40L, 42L, 8L, 6L, 9L, 24L, 48L, 38L, 37L, 34L, 49L, 46L, 2L, 32L, 35L, 39L, 11L, 17L, 5L, 26L, 20L)], width = 1382) - options(width = 54) - ctl_colonnade(df_str[c(40L, 28L, 7L, 16L, 48L, 6L, 21L, 1L, 20L, 17L, 47L, 45L, 29L, 41L, 49L, 34L, 4L, 39L, 18L, 36L, 26L, 38L, 10L, 8L, 5L, 15L, 44L, 24L, 46L, 14L, 25L, 27L, 3L, 37L, 35L, 12L, 9L, 13L, 22L, 33L, 42L, 11L, 19L, 50L, 23L, 30L, 32L, 2L, 43L, 31L)], width = 837) - options(width = 32) - ctl_colonnade(df_str[c(47L, 42L, 4L, 46L, 9L, 34L, 19L, 39L, 8L, 32L, 36L, 12L, 29L, 5L, 15L, 11L, 31L, 27L, 33L, 28L, 43L, 6L, 13L, 22L, 14L, 16L, 35L, 50L, 38L, 7L, 23L, 45L, 40L, 3L, 2L, 24L, 41L, 10L, 30L, 25L, 17L, 26L, 48L, 37L, 49L, 1L, 18L, 21L, 44L, 20L)], width = 455) - options(width = 55) - ctl_colonnade(df_str[c(41L, 4L, 25L, 31L, 8L, 22L, 19L, 10L, 29L, 21L, 34L, 5L, 26L, 36L, 47L, 46L, 2L, 24L, 27L, 39L, 28L, 43L, 32L, 30L, 48L, 44L, 6L, 20L, 13L, 15L, 18L, 42L, 9L, 12L, 37L, 45L, 16L, 40L, 11L, 14L, 38L, 1L, 7L, 3L, 23L, 35L, 50L, 17L, 49L, 33L)], width = 855) - options(width = 54) - ctl_colonnade(df_str[c(27L, 22L, 9L, 23L, 16L, 19L, 25L, 31L, 44L, 1L, 28L, 46L, 12L, 20L, 43L, 37L, 5L, 2L, 18L, 41L, 26L, 33L, 11L, 49L, 24L, 35L, 4L, 47L, 30L, 7L, 34L, 3L, 32L, 42L, 10L, 45L, 38L, 39L, 48L, 14L, 6L, 17L, 36L, 50L, 40L, 13L, 8L, 21L, 15L, 29L)], width = 552) - options(width = 49) - ctl_colonnade(df_str[c(32L, 24L, 18L, 25L, 26L, 13L, 33L, 2L, 50L, 38L, 37L, 16L, 27L, 9L, 28L, 49L, 34L, 15L, 17L, 35L, 22L, 47L, 3L, 21L, 23L, 41L, 5L, 1L, 14L, 46L, 30L, 31L, 44L, 4L, 7L, 40L, 43L, 12L, 29L, 8L, 36L, 45L, 11L, 20L, 10L, 6L, 19L, 48L, 39L, 42L)], width = 1031) - options(width = 38) - ctl_colonnade(df_str[c(44L, 34L, 49L, 9L, 15L, 16L, 1L, 10L, 40L, 29L, 26L, 22L, 4L, 43L, 20L, 17L, 46L, 33L, 35L, 32L, 2L, 12L, 8L, 37L, 23L, 39L, 7L, 18L, 36L, 42L, 6L, 30L, 19L, 25L, 5L, 21L, 47L, 50L, 28L, 11L, 31L, 14L, 24L, 27L, 45L, 41L, 38L, 3L, 13L, 48L)], width = 429) - options(width = 54) - ctl_colonnade(df_str[c(21L, 26L, 8L, 22L, 41L, 24L, 13L, 5L, 47L, 37L, 4L, 42L, 19L, 34L, 11L, 43L, 38L, 3L, 33L, 20L, 31L, 2L, 18L, 48L, 27L, 44L, 9L, 35L, 30L, 6L, 49L, 10L, 1L, 16L, 46L, 29L, 12L, 14L, 45L, 36L, 15L, 39L, 50L, 23L, 17L, 28L, 7L, 32L, 40L, 25L)], width = 633) - options(width = 39) - ctl_colonnade(df_str[c(23L, 49L, 13L, 37L, 3L, 25L, 36L, 4L, 9L, 7L, 27L, 48L, 12L, 10L, 50L, 14L, 38L, 39L, 46L, 22L, 28L, 8L, 21L, 44L, 32L, 40L, 31L, 1L, 29L, 34L, 35L, 33L, 19L, 15L, 41L, 20L, 47L, 18L, 16L, 45L, 6L, 5L, 24L, 26L, 43L, 11L, 42L, 30L, 17L, 2L)], width = 1496) - options(width = 31) - ctl_colonnade(df_str[c(45L, 14L, 49L, 24L, 22L, 31L, 42L, 18L, 16L, 47L, 25L, 4L, 37L, 8L, 26L, 21L, 50L, 5L, 41L, 30L, 2L, 33L, 34L, 3L, 44L, 19L, 43L, 6L, 32L, 29L, 20L, 1L, 13L, 11L, 40L, 12L, 48L, 23L, 9L, 15L, 46L, 36L, 27L, 35L, 28L, 10L, 7L, 39L, 17L, 38L)], width = 493) - options(width = 52) - ctl_colonnade(df_str[c(38L, 46L, 17L, 11L, 24L, 18L, 16L, 39L, 50L, 42L, 6L, 13L, 37L, 29L, 41L, 47L, 9L, 33L, 44L, 31L, 45L, 36L, 28L, 5L, 10L, 30L, 20L, 1L, 14L, 43L, 49L, 23L, 26L, 21L, 32L, 19L, 34L, 15L, 48L, 4L, 7L, 35L, 40L, 8L, 22L, 3L, 25L, 12L, 27L, 2L)], width = 1130) - options(width = 58) - ctl_colonnade(df_str[c(17L, 28L, 29L, 27L, 20L, 31L, 43L, 30L, 32L, 48L, 10L, 50L, 13L, 12L, 36L, 21L, 46L, 33L, 25L, 35L, 1L, 5L, 16L, 34L, 18L, 42L, 3L, 11L, 40L, 26L, 37L, 7L, 39L, 6L, 4L, 19L, 8L, 45L, 14L, 24L, 23L, 2L, 47L, 9L, 49L, 41L, 38L, 22L, 44L, 15L)], width = 1310) - options(width = 47) - ctl_colonnade(df_str[c(1L, 26L, 20L, 12L, 49L, 16L, 24L, 4L, 15L, 47L, 8L, 11L, 14L, 50L, 17L, 2L, 44L, 30L, 36L, 45L, 25L, 38L, 18L, 29L, 5L, 13L, 3L, 23L, 48L, 40L, 34L, 22L, 39L, 33L, 27L, 7L, 19L, 10L, 37L, 6L, 35L, 46L, 31L, 41L, 43L, 28L, 42L, 32L, 21L, 9L)], width = 484) - options(width = 55) - ctl_colonnade(df_str[c(6L, 49L, 26L, 45L, 25L, 15L, 31L, 20L, 21L, 44L, 23L, 48L, 37L, 36L, 5L, 43L, 11L, 14L, 13L, 39L, 16L, 12L, 4L, 18L, 42L, 3L, 10L, 28L, 40L, 24L, 29L, 17L, 35L, 47L, 2L, 38L, 34L, 9L, 7L, 8L, 50L, 33L, 32L, 27L, 46L, 19L, 22L, 41L, 30L, 1L)], width = 779) - options(width = 46) - ctl_colonnade(df_str[c(38L, 42L, 41L, 10L, 40L, 11L, 27L, 9L, 17L, 37L, 46L, 13L, 36L, 18L, 31L, 20L, 39L, 12L, 44L, 33L, 50L, 34L, 26L, 32L, 23L, 30L, 29L, 21L, 4L, 49L, 19L, 25L, 3L, 6L, 15L, 14L, 43L, 48L, 8L, 22L, 1L, 2L, 45L, 35L, 16L, 5L, 47L, 28L, 24L, 7L)], width = 694) - }) + ctl_colonnade(df_str[c(12L, 33L, 36L, 7L, 41L, 3L, 18L, 23L, 13L, 44L, 14L, 16L, 25L, 21L, 19L, 45L, 43L, 29L, 1L, 30L, 22L, 27L, 15L, 47L, 28L, 31L, 10L, 50L, 4L, 40L, 42L, 8L, 6L, 9L, 24L, 48L, 38L, 37L, 34L, 49L, 46L, 2L, 32L, 35L, 39L, 11L, 17L, 5L, 26L, 20L)], width = { options(width = 59); 1382 }) + + ctl_colonnade(df_str[c(40L, 28L, 7L, 16L, 48L, 6L, 21L, 1L, 20L, 17L, 47L, 45L, 29L, 41L, 49L, 34L, 4L, 39L, 18L, 36L, 26L, 38L, 10L, 8L, 5L, 15L, 44L, 24L, 46L, 14L, 25L, 27L, 3L, 37L, 35L, 12L, 9L, 13L, 22L, 33L, 42L, 11L, 19L, 50L, 23L, 30L, 32L, 2L, 43L, 31L)], width = { options(width = 54); 837 }) + + ctl_colonnade(df_str[c(47L, 42L, 4L, 46L, 9L, 34L, 19L, 39L, 8L, 32L, 36L, 12L, 29L, 5L, 15L, 11L, 31L, 27L, 33L, 28L, 43L, 6L, 13L, 22L, 14L, 16L, 35L, 50L, 38L, 7L, 23L, 45L, 40L, 3L, 2L, 24L, 41L, 10L, 30L, 25L, 17L, 26L, 48L, 37L, 49L, 1L, 18L, 21L, 44L, 20L)], width = { options(width = 32); 455 }) + + ctl_colonnade(df_str[c(41L, 4L, 25L, 31L, 8L, 22L, 19L, 10L, 29L, 21L, 34L, 5L, 26L, 36L, 47L, 46L, 2L, 24L, 27L, 39L, 28L, 43L, 32L, 30L, 48L, 44L, 6L, 20L, 13L, 15L, 18L, 42L, 9L, 12L, 37L, 45L, 16L, 40L, 11L, 14L, 38L, 1L, 7L, 3L, 23L, 35L, 50L, 17L, 49L, 33L)], width = { options(width = 55); 855 }) + + ctl_colonnade(df_str[c(27L, 22L, 9L, 23L, 16L, 19L, 25L, 31L, 44L, 1L, 28L, 46L, 12L, 20L, 43L, 37L, 5L, 2L, 18L, 41L, 26L, 33L, 11L, 49L, 24L, 35L, 4L, 47L, 30L, 7L, 34L, 3L, 32L, 42L, 10L, 45L, 38L, 39L, 48L, 14L, 6L, 17L, 36L, 50L, 40L, 13L, 8L, 21L, 15L, 29L)], width = { options(width = 54); 552 }) + + ctl_colonnade(df_str[c(32L, 24L, 18L, 25L, 26L, 13L, 33L, 2L, 50L, 38L, 37L, 16L, 27L, 9L, 28L, 49L, 34L, 15L, 17L, 35L, 22L, 47L, 3L, 21L, 23L, 41L, 5L, 1L, 14L, 46L, 30L, 31L, 44L, 4L, 7L, 40L, 43L, 12L, 29L, 8L, 36L, 45L, 11L, 20L, 10L, 6L, 19L, 48L, 39L, 42L)], width = { options(width = 49); 1031 }) + + ctl_colonnade(df_str[c(44L, 34L, 49L, 9L, 15L, 16L, 1L, 10L, 40L, 29L, 26L, 22L, 4L, 43L, 20L, 17L, 46L, 33L, 35L, 32L, 2L, 12L, 8L, 37L, 23L, 39L, 7L, 18L, 36L, 42L, 6L, 30L, 19L, 25L, 5L, 21L, 47L, 50L, 28L, 11L, 31L, 14L, 24L, 27L, 45L, 41L, 38L, 3L, 13L, 48L)], width = { options(width = 38); 429 }) + + ctl_colonnade(df_str[c(21L, 26L, 8L, 22L, 41L, 24L, 13L, 5L, 47L, 37L, 4L, 42L, 19L, 34L, 11L, 43L, 38L, 3L, 33L, 20L, 31L, 2L, 18L, 48L, 27L, 44L, 9L, 35L, 30L, 6L, 49L, 10L, 1L, 16L, 46L, 29L, 12L, 14L, 45L, 36L, 15L, 39L, 50L, 23L, 17L, 28L, 7L, 32L, 40L, 25L)], width = { options(width = 54); 633 }) + + ctl_colonnade(df_str[c(23L, 49L, 13L, 37L, 3L, 25L, 36L, 4L, 9L, 7L, 27L, 48L, 12L, 10L, 50L, 14L, 38L, 39L, 46L, 22L, 28L, 8L, 21L, 44L, 32L, 40L, 31L, 1L, 29L, 34L, 35L, 33L, 19L, 15L, 41L, 20L, 47L, 18L, 16L, 45L, 6L, 5L, 24L, 26L, 43L, 11L, 42L, 30L, 17L, 2L)], width = { options(width = 39); 1496 }) + + ctl_colonnade(df_str[c(45L, 14L, 49L, 24L, 22L, 31L, 42L, 18L, 16L, 47L, 25L, 4L, 37L, 8L, 26L, 21L, 50L, 5L, 41L, 30L, 2L, 33L, 34L, 3L, 44L, 19L, 43L, 6L, 32L, 29L, 20L, 1L, 13L, 11L, 40L, 12L, 48L, 23L, 9L, 15L, 46L, 36L, 27L, 35L, 28L, 10L, 7L, 39L, 17L, 38L)], width = { options(width = 31); 493 }) + + ctl_colonnade(df_str[c(38L, 46L, 17L, 11L, 24L, 18L, 16L, 39L, 50L, 42L, 6L, 13L, 37L, 29L, 41L, 47L, 9L, 33L, 44L, 31L, 45L, 36L, 28L, 5L, 10L, 30L, 20L, 1L, 14L, 43L, 49L, 23L, 26L, 21L, 32L, 19L, 34L, 15L, 48L, 4L, 7L, 35L, 40L, 8L, 22L, 3L, 25L, 12L, 27L, 2L)], width = { options(width = 52); 1130 }) + + ctl_colonnade(df_str[c(17L, 28L, 29L, 27L, 20L, 31L, 43L, 30L, 32L, 48L, 10L, 50L, 13L, 12L, 36L, 21L, 46L, 33L, 25L, 35L, 1L, 5L, 16L, 34L, 18L, 42L, 3L, 11L, 40L, 26L, 37L, 7L, 39L, 6L, 4L, 19L, 8L, 45L, 14L, 24L, 23L, 2L, 47L, 9L, 49L, 41L, 38L, 22L, 44L, 15L)], width = { options(width = 58); 1310 }) + + ctl_colonnade(df_str[c(1L, 26L, 20L, 12L, 49L, 16L, 24L, 4L, 15L, 47L, 8L, 11L, 14L, 50L, 17L, 2L, 44L, 30L, 36L, 45L, 25L, 38L, 18L, 29L, 5L, 13L, 3L, 23L, 48L, 40L, 34L, 22L, 39L, 33L, 27L, 7L, 19L, 10L, 37L, 6L, 35L, 46L, 31L, 41L, 43L, 28L, 42L, 32L, 21L, 9L)], width = { options(width = 47); 484 }) + + ctl_colonnade(df_str[c(6L, 49L, 26L, 45L, 25L, 15L, 31L, 20L, 21L, 44L, 23L, 48L, 37L, 36L, 5L, 43L, 11L, 14L, 13L, 39L, 16L, 12L, 4L, 18L, 42L, 3L, 10L, 28L, 40L, 24L, 29L, 17L, 35L, 47L, 2L, 38L, 34L, 9L, 7L, 8L, 50L, 33L, 32L, 27L, 46L, 19L, 22L, 41L, 30L, 1L)], width = { options(width = 55); 779 }) + + ctl_colonnade(df_str[c(38L, 42L, 41L, 10L, 40L, 11L, 27L, 9L, 17L, 37L, 46L, 13L, 36L, 18L, 31L, 20L, 39L, 12L, 44L, 33L, 50L, 34L, 26L, 32L, 23L, 30L, 29L, 21L, 4L, 49L, 19L, 25L, 3L, 6L, 15L, 14L, 43L, 48L, 8L, 22L, 1L, 2L, 45L, 35L, 16L, 5L, 47L, 28L, 24L, 7L)], width = { options(width = 46); 694 }) + }) # nolint end -}) + }) diff --git a/tests/testthat/test-ctl_colonnade_2.R b/tests/testthat/test-ctl_colonnade_2.R index e36d47f18..782141ff6 100644 --- a/tests/testthat/test-ctl_colonnade_2.R +++ b/tests/testthat/test-ctl_colonnade_2.R @@ -4,36 +4,35 @@ test_that("strings with varying widths", { # Generated by data-raw/create-chr-tests.R # nolint start expect_snapshot({ - options(width = 54) - ctl_colonnade(df_str[c(28L, 34L, 16L, 29L, 47L, 25L, 42L, 27L, 44L, 20L, 14L, 36L, 43L, 41L, 26L, 45L, 22L, 9L, 13L, 32L, 31L, 12L, 19L, 48L, 49L, 35L, 3L, 11L, 23L, 24L, 40L, 15L, 38L, 10L, 46L, 5L, 50L, 18L, 21L, 6L, 30L, 2L, 7L, 1L, 4L, 8L, 17L, 33L, 39L, 37L)], width = 516) - options(width = 42) - ctl_colonnade(df_str[c(28L, 41L, 12L, 29L, 13L, 43L, 24L, 50L, 48L, 35L, 44L, 21L, 33L, 45L, 47L, 34L, 25L, 14L, 18L, 23L, 7L, 3L, 42L, 36L, 11L, 2L, 20L, 31L, 1L, 4L, 38L, 9L, 27L, 40L, 32L, 17L, 6L, 49L, 16L, 19L, 15L, 22L, 39L, 10L, 46L, 5L, 30L, 8L, 26L, 37L)], width = 1365) - options(width = 39) - ctl_colonnade(df_str[c(40L, 17L, 13L, 23L, 22L, 2L, 18L, 3L, 29L, 45L, 14L, 19L, 33L, 37L, 47L, 43L, 44L, 10L, 31L, 27L, 34L, 35L, 41L, 21L, 4L, 25L, 38L, 48L, 9L, 24L, 26L, 39L, 20L, 36L, 42L, 16L, 6L, 11L, 7L, 12L, 1L, 46L, 15L, 5L, 8L, 50L, 32L, 30L, 49L, 28L)], width = 934) - options(width = 32) - ctl_colonnade(df_str[c(11L, 36L, 17L, 14L, 31L, 35L, 23L, 13L, 6L, 44L, 45L, 22L, 21L, 18L, 33L, 10L, 43L, 2L, 46L, 34L, 3L, 19L, 1L, 38L, 9L, 37L, 5L, 8L, 25L, 49L, 27L, 29L, 15L, 39L, 24L, 40L, 48L, 26L, 47L, 42L, 41L, 12L, 28L, 30L, 7L, 16L, 4L, 50L, 20L, 32L)], width = 565) - options(width = 35) - ctl_colonnade(df_str[c(18L, 46L, 11L, 43L, 31L, 47L, 48L, 44L, 50L, 15L, 28L, 33L, 13L, 4L, 22L, 3L, 37L, 32L, 40L, 9L, 25L, 16L, 45L, 23L, 21L, 6L, 49L, 36L, 27L, 38L, 14L, 34L, 8L, 24L, 29L, 1L, 12L, 2L, 20L, 17L, 35L, 5L, 19L, 30L, 7L, 26L, 42L, 41L, 39L, 10L)], width = 1121) - options(width = 32) - ctl_colonnade(df_str[c(43L, 1L, 3L, 15L, 28L, 12L, 46L, 34L, 31L, 7L, 11L, 4L, 44L, 8L, 9L, 5L, 36L, 22L, 17L, 39L, 18L, 45L, 37L, 13L, 29L, 6L, 30L, 16L, 20L, 10L, 19L, 26L, 33L, 40L, 35L, 48L, 38L, 25L, 2L, 47L, 42L, 41L, 27L, 14L, 21L, 24L, 50L, 49L, 23L, 32L)], width = 446) - options(width = 31) - ctl_colonnade(df_str[c(37L, 46L, 21L, 3L, 16L, 39L, 34L, 33L, 10L, 17L, 19L, 36L, 45L, 49L, 11L, 50L, 14L, 29L, 44L, 13L, 30L, 38L, 32L, 40L, 42L, 1L, 31L, 41L, 7L, 23L, 35L, 28L, 6L, 25L, 2L, 9L, 12L, 15L, 5L, 18L, 20L, 27L, 43L, 8L, 47L, 4L, 48L, 24L, 26L, 22L)], width = 1166) - options(width = 58) - ctl_colonnade(df_str[c(31L, 39L, 40L, 30L, 10L, 21L, 9L, 16L, 46L, 25L, 15L, 24L, 3L, 50L, 35L, 1L, 12L, 34L, 48L, 4L, 29L, 23L, 37L, 36L, 28L, 43L, 11L, 17L, 32L, 8L, 41L, 13L, 44L, 7L, 38L, 26L, 33L, 20L, 19L, 2L, 18L, 49L, 27L, 47L, 22L, 14L, 6L, 5L, 45L, 42L)], width = 546) - options(width = 57) - ctl_colonnade(df_str[c(43L, 21L, 41L, 48L, 22L, 25L, 2L, 8L, 1L, 24L, 6L, 39L, 38L, 20L, 49L, 45L, 47L, 12L, 9L, 13L, 36L, 26L, 44L, 11L, 46L, 28L, 7L, 18L, 50L, 16L, 29L, 30L, 4L, 23L, 17L, 40L, 33L, 14L, 27L, 19L, 34L, 32L, 3L, 37L, 15L, 10L, 5L, 35L, 31L, 42L)], width = 1035) - options(width = 33) - ctl_colonnade(df_str[c(40L, 6L, 25L, 5L, 26L, 17L, 19L, 2L, 11L, 34L, 45L, 24L, 22L, 44L, 35L, 7L, 4L, 49L, 1L, 36L, 12L, 41L, 39L, 13L, 48L, 27L, 18L, 30L, 42L, 28L, 3L, 46L, 21L, 20L, 16L, 29L, 50L, 10L, 9L, 8L, 47L, 31L, 14L, 38L, 33L, 32L, 43L, 23L, 15L, 37L)], width = 1217) - options(width = 32) - ctl_colonnade(df_str[c(43L, 23L, 22L, 11L, 6L, 26L, 48L, 17L, 7L, 42L, 36L, 21L, 35L, 50L, 13L, 19L, 29L, 8L, 15L, 4L, 2L, 27L, 49L, 47L, 30L, 31L, 25L, 28L, 46L, 12L, 32L, 39L, 24L, 10L, 45L, 5L, 37L, 14L, 40L, 20L, 41L, 44L, 33L, 18L, 38L, 3L, 1L, 34L, 16L, 9L)], width = 770) - options(width = 46) - ctl_colonnade(df_str[c(5L, 24L, 43L, 46L, 35L, 39L, 18L, 26L, 8L, 27L, 2L, 50L, 6L, 14L, 29L, 47L, 9L, 16L, 36L, 4L, 13L, 41L, 3L, 28L, 37L, 33L, 38L, 31L, 34L, 19L, 42L, 32L, 1L, 45L, 15L, 7L, 11L, 49L, 23L, 12L, 48L, 20L, 21L, 44L, 25L, 10L, 22L, 30L, 40L, 17L)], width = 1439) - options(width = 52) - ctl_colonnade(df_str[c(7L, 44L, 19L, 21L, 18L, 35L, 23L, 50L, 33L, 37L, 25L, 26L, 10L, 39L, 2L, 47L, 42L, 14L, 9L, 41L, 45L, 6L, 4L, 11L, 24L, 43L, 32L, 3L, 38L, 5L, 49L, 27L, 17L, 8L, 22L, 40L, 12L, 15L, 1L, 28L, 31L, 29L, 13L, 48L, 34L, 36L, 30L, 20L, 16L, 46L)], width = 1065) - options(width = 35) - ctl_colonnade(df_str[c(38L, 18L, 23L, 36L, 35L, 20L, 44L, 19L, 13L, 41L, 31L, 7L, 11L, 29L, 2L, 14L, 26L, 46L, 40L, 45L, 9L, 34L, 33L, 22L, 1L, 17L, 28L, 10L, 21L, 30L, 47L, 49L, 6L, 12L, 4L, 25L, 32L, 15L, 43L, 24L, 48L, 3L, 37L, 50L, 42L, 39L, 16L, 8L, 27L, 5L)], width = 393) - options(width = 41) - ctl_colonnade(df_str[c(22L, 9L, 11L, 26L, 19L, 16L, 32L, 25L, 1L, 30L, 31L, 6L, 24L, 10L, 39L, 21L, 50L, 7L, 29L, 12L, 46L, 43L, 15L, 35L, 20L, 40L, 49L, 38L, 36L, 48L, 34L, 3L, 8L, 4L, 27L, 42L, 44L, 33L, 45L, 18L, 5L, 2L, 13L, 47L, 28L, 17L, 37L, 14L, 41L, 23L)], width = 999) + ctl_colonnade(df_str[c(28L, 34L, 16L, 29L, 47L, 25L, 42L, 27L, 44L, 20L, 14L, 36L, 43L, 41L, 26L, 45L, 22L, 9L, 13L, 32L, 31L, 12L, 19L, 48L, 49L, 35L, 3L, 11L, 23L, 24L, 40L, 15L, 38L, 10L, 46L, 5L, 50L, 18L, 21L, 6L, 30L, 2L, 7L, 1L, 4L, 8L, 17L, 33L, 39L, 37L)], width = { options(width = 54); 516 }) + + ctl_colonnade(df_str[c(28L, 41L, 12L, 29L, 13L, 43L, 24L, 50L, 48L, 35L, 44L, 21L, 33L, 45L, 47L, 34L, 25L, 14L, 18L, 23L, 7L, 3L, 42L, 36L, 11L, 2L, 20L, 31L, 1L, 4L, 38L, 9L, 27L, 40L, 32L, 17L, 6L, 49L, 16L, 19L, 15L, 22L, 39L, 10L, 46L, 5L, 30L, 8L, 26L, 37L)], width = { options(width = 42); 1365 }) + + ctl_colonnade(df_str[c(40L, 17L, 13L, 23L, 22L, 2L, 18L, 3L, 29L, 45L, 14L, 19L, 33L, 37L, 47L, 43L, 44L, 10L, 31L, 27L, 34L, 35L, 41L, 21L, 4L, 25L, 38L, 48L, 9L, 24L, 26L, 39L, 20L, 36L, 42L, 16L, 6L, 11L, 7L, 12L, 1L, 46L, 15L, 5L, 8L, 50L, 32L, 30L, 49L, 28L)], width = { options(width = 39); 934 }) + + ctl_colonnade(df_str[c(11L, 36L, 17L, 14L, 31L, 35L, 23L, 13L, 6L, 44L, 45L, 22L, 21L, 18L, 33L, 10L, 43L, 2L, 46L, 34L, 3L, 19L, 1L, 38L, 9L, 37L, 5L, 8L, 25L, 49L, 27L, 29L, 15L, 39L, 24L, 40L, 48L, 26L, 47L, 42L, 41L, 12L, 28L, 30L, 7L, 16L, 4L, 50L, 20L, 32L)], width = { options(width = 32); 565 }) + + ctl_colonnade(df_str[c(18L, 46L, 11L, 43L, 31L, 47L, 48L, 44L, 50L, 15L, 28L, 33L, 13L, 4L, 22L, 3L, 37L, 32L, 40L, 9L, 25L, 16L, 45L, 23L, 21L, 6L, 49L, 36L, 27L, 38L, 14L, 34L, 8L, 24L, 29L, 1L, 12L, 2L, 20L, 17L, 35L, 5L, 19L, 30L, 7L, 26L, 42L, 41L, 39L, 10L)], width = { options(width = 35); 1121 }) + + ctl_colonnade(df_str[c(43L, 1L, 3L, 15L, 28L, 12L, 46L, 34L, 31L, 7L, 11L, 4L, 44L, 8L, 9L, 5L, 36L, 22L, 17L, 39L, 18L, 45L, 37L, 13L, 29L, 6L, 30L, 16L, 20L, 10L, 19L, 26L, 33L, 40L, 35L, 48L, 38L, 25L, 2L, 47L, 42L, 41L, 27L, 14L, 21L, 24L, 50L, 49L, 23L, 32L)], width = { options(width = 32); 446 }) + + ctl_colonnade(df_str[c(37L, 46L, 21L, 3L, 16L, 39L, 34L, 33L, 10L, 17L, 19L, 36L, 45L, 49L, 11L, 50L, 14L, 29L, 44L, 13L, 30L, 38L, 32L, 40L, 42L, 1L, 31L, 41L, 7L, 23L, 35L, 28L, 6L, 25L, 2L, 9L, 12L, 15L, 5L, 18L, 20L, 27L, 43L, 8L, 47L, 4L, 48L, 24L, 26L, 22L)], width = { options(width = 31); 1166 }) + + ctl_colonnade(df_str[c(31L, 39L, 40L, 30L, 10L, 21L, 9L, 16L, 46L, 25L, 15L, 24L, 3L, 50L, 35L, 1L, 12L, 34L, 48L, 4L, 29L, 23L, 37L, 36L, 28L, 43L, 11L, 17L, 32L, 8L, 41L, 13L, 44L, 7L, 38L, 26L, 33L, 20L, 19L, 2L, 18L, 49L, 27L, 47L, 22L, 14L, 6L, 5L, 45L, 42L)], width = { options(width = 58); 546 }) + + ctl_colonnade(df_str[c(43L, 21L, 41L, 48L, 22L, 25L, 2L, 8L, 1L, 24L, 6L, 39L, 38L, 20L, 49L, 45L, 47L, 12L, 9L, 13L, 36L, 26L, 44L, 11L, 46L, 28L, 7L, 18L, 50L, 16L, 29L, 30L, 4L, 23L, 17L, 40L, 33L, 14L, 27L, 19L, 34L, 32L, 3L, 37L, 15L, 10L, 5L, 35L, 31L, 42L)], width = { options(width = 57); 1035 }) + + ctl_colonnade(df_str[c(40L, 6L, 25L, 5L, 26L, 17L, 19L, 2L, 11L, 34L, 45L, 24L, 22L, 44L, 35L, 7L, 4L, 49L, 1L, 36L, 12L, 41L, 39L, 13L, 48L, 27L, 18L, 30L, 42L, 28L, 3L, 46L, 21L, 20L, 16L, 29L, 50L, 10L, 9L, 8L, 47L, 31L, 14L, 38L, 33L, 32L, 43L, 23L, 15L, 37L)], width = { options(width = 33); 1217 }) + + ctl_colonnade(df_str[c(43L, 23L, 22L, 11L, 6L, 26L, 48L, 17L, 7L, 42L, 36L, 21L, 35L, 50L, 13L, 19L, 29L, 8L, 15L, 4L, 2L, 27L, 49L, 47L, 30L, 31L, 25L, 28L, 46L, 12L, 32L, 39L, 24L, 10L, 45L, 5L, 37L, 14L, 40L, 20L, 41L, 44L, 33L, 18L, 38L, 3L, 1L, 34L, 16L, 9L)], width = { options(width = 32); 770 }) + + ctl_colonnade(df_str[c(5L, 24L, 43L, 46L, 35L, 39L, 18L, 26L, 8L, 27L, 2L, 50L, 6L, 14L, 29L, 47L, 9L, 16L, 36L, 4L, 13L, 41L, 3L, 28L, 37L, 33L, 38L, 31L, 34L, 19L, 42L, 32L, 1L, 45L, 15L, 7L, 11L, 49L, 23L, 12L, 48L, 20L, 21L, 44L, 25L, 10L, 22L, 30L, 40L, 17L)], width = { options(width = 46); 1439 }) + + ctl_colonnade(df_str[c(7L, 44L, 19L, 21L, 18L, 35L, 23L, 50L, 33L, 37L, 25L, 26L, 10L, 39L, 2L, 47L, 42L, 14L, 9L, 41L, 45L, 6L, 4L, 11L, 24L, 43L, 32L, 3L, 38L, 5L, 49L, 27L, 17L, 8L, 22L, 40L, 12L, 15L, 1L, 28L, 31L, 29L, 13L, 48L, 34L, 36L, 30L, 20L, 16L, 46L)], width = { options(width = 52); 1065 }) + + ctl_colonnade(df_str[c(38L, 18L, 23L, 36L, 35L, 20L, 44L, 19L, 13L, 41L, 31L, 7L, 11L, 29L, 2L, 14L, 26L, 46L, 40L, 45L, 9L, 34L, 33L, 22L, 1L, 17L, 28L, 10L, 21L, 30L, 47L, 49L, 6L, 12L, 4L, 25L, 32L, 15L, 43L, 24L, 48L, 3L, 37L, 50L, 42L, 39L, 16L, 8L, 27L, 5L)], width = { options(width = 35); 393 }) + + ctl_colonnade(df_str[c(22L, 9L, 11L, 26L, 19L, 16L, 32L, 25L, 1L, 30L, 31L, 6L, 24L, 10L, 39L, 21L, 50L, 7L, 29L, 12L, 46L, 43L, 15L, 35L, 20L, 40L, 49L, 38L, 36L, 48L, 34L, 3L, 8L, 4L, 27L, 42L, 44L, 33L, 45L, 18L, 5L, 2L, 13L, 47L, 28L, 17L, 37L, 14L, 41L, 23L)], width = { options(width = 41); 999 }) }) # nolint end }) From 5aec658e14bfc5ad996874e12ea391a170e92262 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Sun, 25 Jul 2021 05:55:07 +0200 Subject: [PATCH 016/147] Simplify --- R/multi.R | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/R/multi.R b/R/multi.R index 5f099bd74..3a7cb830d 100644 --- a/R/multi.R +++ b/R/multi.R @@ -383,7 +383,7 @@ colonnade_compute_tiered_col_widths_df <- function(max_widths, min_widths, tier_ #' agree. min_fit_rev <- distribute_pillars_rev(col_df$min_widths, tier_widths) - cut_point <- max(min(which(c(max_fit$tier == min_fit_rev$tier))), 1L) + cut_point <- max(min(which(max_fit$tier == min_fit_rev$tier)), 1L) cut_point_tier <- max_fit$tier[[cut_point]] min_fit_cut <- distribute_pillars_offset( From 65c02f2cc0719e770d2a7e024b7be5dabfeba0b3 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Sun, 25 Jul 2021 10:31:14 +0200 Subject: [PATCH 017/147] Add tests for helpers --- tests/testthat/_snaps/multi.md | 47 ++++++++++++++++++++++++++++++++++ tests/testthat/test-multi.R | 10 ++++++++ 2 files changed, 57 insertions(+) create mode 100644 tests/testthat/_snaps/multi.md create mode 100644 tests/testthat/test-multi.R diff --git a/tests/testthat/_snaps/multi.md b/tests/testthat/_snaps/multi.md new file mode 100644 index 000000000..6ed719cd2 --- /dev/null +++ b/tests/testthat/_snaps/multi.md @@ -0,0 +1,47 @@ +# distribute_pillars() + + Code + distribute_pillars(1:3, 10) + Output + id width tier + 1 1 1 1 + 2 2 2 1 + 3 3 3 1 + Code + distribute_pillars(1:3, 5) + Output + id width tier + 1 1 1 1 + 2 2 2 1 + 3 3 3 0 + Code + distribute_pillars(1:3, c(5, 5)) + Output + id width tier + 1 1 1 1 + 2 2 2 1 + 3 3 3 2 + Code + distribute_pillars(1:5, 7:9) + Output + id width tier + 1 1 1 1 + 2 2 2 1 + 3 3 3 2 + 4 4 4 2 + 5 5 5 3 + Code + distribute_pillars(3:5, 8:10) + Output + id width tier + 1 1 3 1 + 2 2 4 1 + 3 3 5 2 + Code + distribute_pillars(5:3, 9:8) + Output + id width tier + 1 1 5 1 + 2 2 4 2 + 3 3 3 2 + diff --git a/tests/testthat/test-multi.R b/tests/testthat/test-multi.R new file mode 100644 index 000000000..4be51f339 --- /dev/null +++ b/tests/testthat/test-multi.R @@ -0,0 +1,10 @@ +test_that("distribute_pillars()", { + expect_snapshot({ + distribute_pillars(1:3, 10) + distribute_pillars(1:3, 5) + distribute_pillars(1:3, c(5, 5)) + distribute_pillars(1:5, 7:9) + distribute_pillars(3:5, 8:10) + distribute_pillars(5:3, 9:8) + }) +}) From 6242ba51d709c4144c9df604f82fff9f4229dc22 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Sun, 25 Jul 2021 10:37:31 +0200 Subject: [PATCH 018/147] Add more tests, currently suboptimal results --- tests/testthat/_snaps/multi.md | 27 +++++++++++++++++++++++++++ tests/testthat/test-multi.R | 8 ++++++++ 2 files changed, 35 insertions(+) diff --git a/tests/testthat/_snaps/multi.md b/tests/testthat/_snaps/multi.md index 6ed719cd2..b491969f4 100644 --- a/tests/testthat/_snaps/multi.md +++ b/tests/testthat/_snaps/multi.md @@ -1,3 +1,30 @@ +# colonnade_compute_tiered_col_widths_df() + + Code + colonnade_compute_tiered_col_widths_df(rep(30, 4), rep(15, 4), rep(60, 4)) + Output + id width tier + 1 1 30 1 + 2 2 30 2 + 3 3 30 3 + 4 4 30 4 + Code + colonnade_compute_tiered_col_widths_df(rep(30, 4), rep(15, 4), rep(60, 3)) + Output + id width tier max_widths + 1 1 30 1 30 + 2 2 30 2 30 + 3 3 15 3 30 + 4 4 15 3 30 + Code + colonnade_compute_tiered_col_widths_df(rep(30, 4), rep(15, 4), rep(60, 2)) + Output + id width tier max_widths + 1 1 15 1 30 + 2 2 15 1 30 + 3 3 15 1 30 + 4 4 15 2 30 + # distribute_pillars() Code diff --git a/tests/testthat/test-multi.R b/tests/testthat/test-multi.R index 4be51f339..ca11dcc9d 100644 --- a/tests/testthat/test-multi.R +++ b/tests/testthat/test-multi.R @@ -1,3 +1,11 @@ +test_that("colonnade_compute_tiered_col_widths_df()", { + expect_snapshot({ + colonnade_compute_tiered_col_widths_df(rep(30, 4), rep(15, 4), rep(60, 4)) + colonnade_compute_tiered_col_widths_df(rep(30, 4), rep(15, 4), rep(60, 3)) + colonnade_compute_tiered_col_widths_df(rep(30, 4), rep(15, 4), rep(60, 2)) + }) +}) + test_that("distribute_pillars()", { expect_snapshot({ distribute_pillars(1:3, 10) From f4712cdd2cb260ff18f696d1b6557349186cfc28 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Sun, 25 Jul 2021 11:40:49 +0200 Subject: [PATCH 019/147] More tests --- tests/testthat/_snaps/multi.md | 32 ++++++++++++++++++++++++++++++++ tests/testthat/test-multi.R | 3 +++ 2 files changed, 35 insertions(+) diff --git a/tests/testthat/_snaps/multi.md b/tests/testthat/_snaps/multi.md index b491969f4..e2b397329 100644 --- a/tests/testthat/_snaps/multi.md +++ b/tests/testthat/_snaps/multi.md @@ -24,6 +24,38 @@ 2 2 15 1 30 3 3 15 1 30 4 4 15 2 30 + Code + colonnade_compute_tiered_col_widths_df(rep(30, 5), rep(15, 5), rep(60, 3)) + Output + id width tier max_widths + 1 1 30 1 30 + 2 2 15 2 30 + 3 3 15 2 30 + 4 4 15 2 30 + 5 5 15 3 30 + Code + colonnade_compute_tiered_col_widths_df(rep(30, 5), rep(15, 5), rep(60, 4)) + Output + id width tier max_widths + 1 1 30 1 30 + 2 2 30 2 30 + 3 3 30 3 30 + 4 4 15 4 30 + 5 5 15 4 30 + Code + colonnade_compute_tiered_col_widths_df(rep(30, 10), rep(15, 10), rep(60, 5)) + Output + id width tier max_widths + 1 1 30 1 30 + 2 2 30 2 30 + 3 3 15 3 30 + 4 4 15 3 30 + 5 5 15 3 30 + 6 6 15 4 30 + 7 7 15 4 30 + 8 8 15 4 30 + 9 9 15 5 30 + 10 10 15 5 30 # distribute_pillars() diff --git a/tests/testthat/test-multi.R b/tests/testthat/test-multi.R index ca11dcc9d..bb1574557 100644 --- a/tests/testthat/test-multi.R +++ b/tests/testthat/test-multi.R @@ -3,6 +3,9 @@ test_that("colonnade_compute_tiered_col_widths_df()", { colonnade_compute_tiered_col_widths_df(rep(30, 4), rep(15, 4), rep(60, 4)) colonnade_compute_tiered_col_widths_df(rep(30, 4), rep(15, 4), rep(60, 3)) colonnade_compute_tiered_col_widths_df(rep(30, 4), rep(15, 4), rep(60, 2)) + colonnade_compute_tiered_col_widths_df(rep(30, 5), rep(15, 5), rep(60, 3)) + colonnade_compute_tiered_col_widths_df(rep(30, 5), rep(15, 5), rep(60, 4)) + colonnade_compute_tiered_col_widths_df(rep(30, 10), rep(15, 10), rep(60, 5)) }) }) From abd0e5268d4d824c53d64cf96acde013314447a2 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Sun, 25 Jul 2021 15:20:54 +0200 Subject: [PATCH 020/147] Plan --- TODO.md | 35 +++++++++++++++++++++++++++++++++++ 1 file changed, 35 insertions(+) diff --git a/TODO.md b/TODO.md index 837e8d065..1b502a2ca 100644 --- a/TODO.md +++ b/TODO.md @@ -2,6 +2,41 @@ ## Next steps +- new branch: tier 0 -> missing from table? + - defer if possible + +- f-greedy: rethink implementation of `colonnade_compute_tiered_col_widths_df()` + - idea: fitting functions also indicate horizontal position within the tier? + This allows for a precise cutoff + + - fit min reverse + - no fit? fit min, return + - iterate over tiers + - fit max + - conflict with fit min reverse? break + - + + - start populating first tier + - fit? + + - how many free tiers do we have available? + - at least one? + - populate those with the maximum width + - recursive call for the remaining tiers + - none? + - populate first tier with maximum width, check through lookup if + - + + - shortcut: discrete fit with minimum width; if no fit, try to still fit with maximum width in a second step + + + - remove special case of "all pillars fit", we still want to reorganize/ + - for how many columns can we guarantee maximum width? + - current implementation answers that approximately, we know the tiers that we can close + - second step: close tiers (except last), try to fit remaining with a recursive call + + + - revdepcheck for adding ellipsis to methods - Milestone: From 4a8ea370e7085abd84264b833e17d1f081ec631d Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Sun, 25 Jul 2021 15:23:16 +0200 Subject: [PATCH 021/147] More tests --- tests/testthat/_snaps/multi.md | 47 ++++++++++++++++++++++++++++++++++ tests/testthat/test-multi.R | 11 ++++++++ 2 files changed, 58 insertions(+) diff --git a/tests/testthat/_snaps/multi.md b/tests/testthat/_snaps/multi.md index e2b397329..e3959d950 100644 --- a/tests/testthat/_snaps/multi.md +++ b/tests/testthat/_snaps/multi.md @@ -104,3 +104,50 @@ 2 2 4 2 3 3 3 2 +# distribute_pillars_rev() + + Code + distribute_pillars_rev(1:3, 10) + Output + id width tier + 1 1 1 1 + 2 2 2 1 + 3 3 3 1 + Code + distribute_pillars_rev(1:3, 5) + Output + id width tier + 1 1 1 2 + 2 2 2 2 + 3 3 3 1 + Code + distribute_pillars_rev(1:3, c(5, 5)) + Output + id width tier + 1 1 1 1 + 2 2 2 1 + 3 3 3 2 + Code + distribute_pillars_rev(1:5, 7:9) + Output + id width tier + 1 1 1 1 + 2 2 2 1 + 3 3 3 2 + 4 4 4 2 + 5 5 5 3 + Code + distribute_pillars_rev(3:5, 8:10) + Output + id width tier + 1 1 3 2 + 2 2 4 3 + 3 3 5 3 + Code + distribute_pillars_rev(5:3, 9:8) + Output + id width tier + 1 1 5 1 + 2 2 4 2 + 3 3 3 2 + diff --git a/tests/testthat/test-multi.R b/tests/testthat/test-multi.R index bb1574557..2e354ffdc 100644 --- a/tests/testthat/test-multi.R +++ b/tests/testthat/test-multi.R @@ -19,3 +19,14 @@ test_that("distribute_pillars()", { distribute_pillars(5:3, 9:8) }) }) + +test_that("distribute_pillars_rev()", { + expect_snapshot({ + distribute_pillars_rev(1:3, 10) + distribute_pillars_rev(1:3, 5) + distribute_pillars_rev(1:3, c(5, 5)) + distribute_pillars_rev(1:5, 7:9) + distribute_pillars_rev(3:5, 8:10) + distribute_pillars_rev(5:3, 9:8) + }) +}) From 9aac22091c083b987d466b35d617b2731c5c9b90 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Sun, 25 Jul 2021 15:40:55 +0200 Subject: [PATCH 022/147] Hidden pillars use NA as tier --- R/multi.R | 14 ++++++++------ tests/testthat/_snaps/format_multi.md | 28 +++++++++++++++++++++++++++ tests/testthat/_snaps/multi.md | 6 +++--- 3 files changed, 39 insertions(+), 9 deletions(-) diff --git a/R/multi.R b/R/multi.R index 3a7cb830d..b6b41121b 100644 --- a/R/multi.R +++ b/R/multi.R @@ -157,7 +157,7 @@ squeeze_impl <- function(x, width = NULL, ...) { } col_widths <- colonnade_get_width(x, width, rowid_width) - col_widths_shown <- col_widths[col_widths$tier != 0, ] + col_widths_shown <- col_widths[!is.na(col_widths$tier), ] indexes <- split(seq_along(col_widths_shown$tier), col_widths_shown$tier) out <- map(indexes, function(i) { @@ -307,7 +307,7 @@ colonnade_get_width <- function(x, width, rowid_width) { init_cols <- min(length(x$data), sum(floor((tier_widths + 1L) / (MIN_PILLAR_WIDTH + 1L)))) capitals <- map2(x$data[seq_len(init_cols)], x$names[seq_len(init_cols)], pillar_capital) init_col_widths_df <- colonnade_compute_tiered_col_widths(capitals, tier_widths) - pillar_shown <- init_col_widths_df$id[init_col_widths_df$tier != 0L] + pillar_shown <- init_col_widths_df$id[!is.na(init_col_widths_df$tier)] if (length(pillar_shown) < init_cols) { # (Include one more pillar to indicate that the data is too wide.) pillar_shown <- c(pillar_shown, pillar_shown[length(pillar_shown)] + 1L) @@ -342,7 +342,7 @@ colonnade_compute_tiered_col_widths <- function(pillars, tier_widths) { max_tier_width <- max(tier_widths) max_widths <- pmin(map_int(map(pillars, get_widths), max), max_tier_width) - min_widths <- map_int(map(pillars, get_min_widths), max) + min_widths <- pmin(map_int(map(pillars, get_min_widths), max), max_widths) ret <- colonnade_compute_tiered_col_widths_df(max_widths, min_widths, tier_widths) ret$pillar <- pillars @@ -406,7 +406,7 @@ colonnade_compute_tiered_col_widths_df <- function(max_widths, min_widths, tier_ #' @usage NULL #' @aliases NULL distribute_pillars <- function(widths, tier_widths) { - tier <- integer(length(widths)) + tier <- rep(NA_integer_, length(widths)) current_tier <- 1L current_x <- 0L @@ -454,7 +454,7 @@ distribute_pillars_offset <- function(widths, tier_widths, all_pillars_fit <- function(tier_df) { rows <- nrow(tier_df) - rows == 0 || tier_df$tier[[nrow(tier_df)]] != 0 + rows == 0 || !anyNA(tier_df$tier[[nrow(tier_df)]]) } #' @rdname colonnade @@ -464,7 +464,9 @@ colonnade_distribute_space_df <- function(col_widths_df, tier_widths) { "!!!!!DEBUG colonnade_distribute_space_df(`v(tier_widths)`)" col_widths_split <- split(col_widths_df, col_widths_df$tier) - if (any(col_widths_df$tier == 0)) tier_widths <- c(NA, tier_widths) + if (anyNA(col_widths_df$tier)) { + tier_widths <- c(NA, tier_widths) + } tier_widths <- tier_widths[seq_along(col_widths_split)] col_widths_apply <- map2(col_widths_split, tier_widths, function(x, width) { x$width <- x$width + colonnade_distribute_space(x$width, x$max_widths, width) diff --git a/tests/testthat/_snaps/format_multi.md b/tests/testthat/_snaps/format_multi.md index 129cfcbdf..0c337dc20 100644 --- a/tests/testthat/_snaps/format_multi.md +++ b/tests/testthat/_snaps/format_multi.md @@ -76,9 +76,37 @@ 3 3.23 Code colonnade(x, width = 13) + Output + column_zer~ + + 1 1.23 + 2 2.23 + 3 3.23 + Code colonnade(x, width = 14) + Output + column_zero~ + + 1 1.23 + 2 2.23 + 3 3.23 + Code colonnade(x, width = 15) + Output + column_zero_~ + + 1 1.23 + 2 2.23 + 3 3.23 + Code colonnade(x, width = 16) + Output + column_zero_o~ + + 1 1.23 + 2 2.23 + 3 3.23 + Code colonnade(x, width = 17) Output column_zero_one diff --git a/tests/testthat/_snaps/multi.md b/tests/testthat/_snaps/multi.md index e3959d950..a6e48f685 100644 --- a/tests/testthat/_snaps/multi.md +++ b/tests/testthat/_snaps/multi.md @@ -72,7 +72,7 @@ id width tier 1 1 1 1 2 2 2 1 - 3 3 3 0 + 3 3 3 NA Code distribute_pillars(1:3, c(5, 5)) Output @@ -117,8 +117,8 @@ distribute_pillars_rev(1:3, 5) Output id width tier - 1 1 1 2 - 2 2 2 2 + 1 1 1 NA + 2 2 2 NA 3 3 3 1 Code distribute_pillars_rev(1:3, c(5, 5)) From d88ad5a38cb5a996ba4a903e008f598852643bdf Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Sun, 25 Jul 2021 15:41:14 +0200 Subject: [PATCH 023/147] Done --- TODO.md | 3 --- 1 file changed, 3 deletions(-) diff --git a/TODO.md b/TODO.md index 1b502a2ca..0c4a4f099 100644 --- a/TODO.md +++ b/TODO.md @@ -2,9 +2,6 @@ ## Next steps -- new branch: tier 0 -> missing from table? - - defer if possible - - f-greedy: rethink implementation of `colonnade_compute_tiered_col_widths_df()` - idea: fitting functions also indicate horizontal position within the tier? This allows for a precise cutoff From d533aa2d0be6d5215294e76b023895558ac6821e Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Sun, 25 Jul 2021 16:12:56 +0200 Subject: [PATCH 024/147] safe_is_na() and safe_any_na() --- R/multi.R | 8 ++++---- 1 file changed, 4 insertions(+), 4 deletions(-) diff --git a/R/multi.R b/R/multi.R index b6b41121b..db158e4fe 100644 --- a/R/multi.R +++ b/R/multi.R @@ -157,7 +157,7 @@ squeeze_impl <- function(x, width = NULL, ...) { } col_widths <- colonnade_get_width(x, width, rowid_width) - col_widths_shown <- col_widths[!is.na(col_widths$tier), ] + col_widths_shown <- col_widths[!safe_is_na(col_widths$tier), ] indexes <- split(seq_along(col_widths_shown$tier), col_widths_shown$tier) out <- map(indexes, function(i) { @@ -307,7 +307,7 @@ colonnade_get_width <- function(x, width, rowid_width) { init_cols <- min(length(x$data), sum(floor((tier_widths + 1L) / (MIN_PILLAR_WIDTH + 1L)))) capitals <- map2(x$data[seq_len(init_cols)], x$names[seq_len(init_cols)], pillar_capital) init_col_widths_df <- colonnade_compute_tiered_col_widths(capitals, tier_widths) - pillar_shown <- init_col_widths_df$id[!is.na(init_col_widths_df$tier)] + pillar_shown <- init_col_widths_df$id[!safe_is_na(init_col_widths_df$tier)] if (length(pillar_shown) < init_cols) { # (Include one more pillar to indicate that the data is too wide.) pillar_shown <- c(pillar_shown, pillar_shown[length(pillar_shown)] + 1L) @@ -454,7 +454,7 @@ distribute_pillars_offset <- function(widths, tier_widths, all_pillars_fit <- function(tier_df) { rows <- nrow(tier_df) - rows == 0 || !anyNA(tier_df$tier[[nrow(tier_df)]]) + rows == 0 || !safe_any_na(tier_df$tier[[nrow(tier_df)]]) } #' @rdname colonnade @@ -464,7 +464,7 @@ colonnade_distribute_space_df <- function(col_widths_df, tier_widths) { "!!!!!DEBUG colonnade_distribute_space_df(`v(tier_widths)`)" col_widths_split <- split(col_widths_df, col_widths_df$tier) - if (anyNA(col_widths_df$tier)) { + if (safe_any_na(col_widths_df$tier)) { tier_widths <- c(NA, tier_widths) } tier_widths <- tier_widths[seq_along(col_widths_split)] From 70643dc0164213adb326bb155116dddc57dc743b Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Sun, 25 Jul 2021 16:17:44 +0200 Subject: [PATCH 025/147] Work around failures in R 3.4 --- R/utils.R | 12 ++++++++++++ 1 file changed, 12 insertions(+) diff --git a/R/utils.R b/R/utils.R index 72f740849..3e52c1307 100644 --- a/R/utils.R +++ b/R/utils.R @@ -112,3 +112,15 @@ v <- function(x) { expr <- rlang::expr_deparse(substitute(x), width = Inf) paste0(expr, " = ", rlang::expr_deparse(x, width = 80)[[1]]) } + +# Needed for R 3.4 and earlier +safe_is_na <- function(x) { + if (is.null(x)) { + return(logical()) + } + is.na(x) +} + +safe_any_na <- function(x) { + anyNA(x) +} From c2cffda31902a5f72dc86173e0591a09d4cddfc3 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Sun, 25 Jul 2021 16:28:50 +0200 Subject: [PATCH 026/147] Remove unused --- R/multi.R | 3 --- 1 file changed, 3 deletions(-) diff --git a/R/multi.R b/R/multi.R index db158e4fe..e301e25ae 100644 --- a/R/multi.R +++ b/R/multi.R @@ -464,9 +464,6 @@ colonnade_distribute_space_df <- function(col_widths_df, tier_widths) { "!!!!!DEBUG colonnade_distribute_space_df(`v(tier_widths)`)" col_widths_split <- split(col_widths_df, col_widths_df$tier) - if (safe_any_na(col_widths_df$tier)) { - tier_widths <- c(NA, tier_widths) - } tier_widths <- tier_widths[seq_along(col_widths_split)] col_widths_apply <- map2(col_widths_split, tier_widths, function(x, width) { x$width <- x$width + colonnade_distribute_space(x$width, x$max_widths, width) From a48ffcbcd7c1f0d791fde66f324e05632a9388e7 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Sun, 25 Jul 2021 16:00:23 +0200 Subject: [PATCH 027/147] Add offset column to output of distribute_pillars() and distribute_pillars_rev() --- R/multi.R | 24 ++++- tests/testthat/_snaps/multi.md | 180 ++++++++++++++++----------------- 2 files changed, 110 insertions(+), 94 deletions(-) diff --git a/R/multi.R b/R/multi.R index e301e25ae..64e3ac753 100644 --- a/R/multi.R +++ b/R/multi.R @@ -407,6 +407,7 @@ colonnade_compute_tiered_col_widths_df <- function(max_widths, min_widths, tier_ #' @aliases NULL distribute_pillars <- function(widths, tier_widths) { tier <- rep(NA_integer_, length(widths)) + offset <- rep(NA_integer_, length(widths)) current_tier <- 1L current_x <- 0L @@ -428,16 +429,31 @@ distribute_pillars <- function(widths, tier_widths) { } tier[[i]] <- current_tier - current_x <- current_x + widths[[i]] + 1L + current_x <- current_x + widths[[i]] + offset[[i]] <- current_x + current_x <- current_x + 1L } - data_frame(id = seq_along(widths), width = widths, tier = tier) + data_frame(id = seq_along(widths), width = widths, tier = tier, offset = offset) } distribute_pillars_rev <- function(widths, tier_widths) { ret <- distribute_pillars(rev(widths), rev(tier_widths)) - ret[2:3] <- ret[rev(seq_along(widths)), 2:3] - ret$tier <- length(tier_widths) + 1L - ret$tier + ret[2:4] <- ret[rev(seq_along(widths)), 2:4] + tier <- length(tier_widths) + 1L - ret$tier + ret$tier <- tier + + splits <- unname(split(seq_along(tier), tier)) + tier_widths <- tier_widths[seq_along(splits)] + + new_offset <- unlist(map2(splits, tier_widths, function(.x, .y) { + offsets <- ret$offset[.x] + new_offset <- max(offsets) - offsets + new_offset - max(new_offset) + .y + })) + + ret$offset <- c(new_offset, rep(NA_integer_, sum(is.na(tier)))) + ret } diff --git a/tests/testthat/_snaps/multi.md b/tests/testthat/_snaps/multi.md index a6e48f685..79dbe7e84 100644 --- a/tests/testthat/_snaps/multi.md +++ b/tests/testthat/_snaps/multi.md @@ -3,151 +3,151 @@ Code colonnade_compute_tiered_col_widths_df(rep(30, 4), rep(15, 4), rep(60, 4)) Output - id width tier - 1 1 30 1 - 2 2 30 2 - 3 3 30 3 - 4 4 30 4 + id width tier offset + 1 1 30 1 30 + 2 2 30 2 30 + 3 3 30 3 30 + 4 4 30 4 30 Code colonnade_compute_tiered_col_widths_df(rep(30, 4), rep(15, 4), rep(60, 3)) Output - id width tier max_widths - 1 1 30 1 30 - 2 2 30 2 30 - 3 3 15 3 30 - 4 4 15 3 30 + id width tier offset max_widths + 1 1 30 1 30 30 + 2 2 30 2 30 30 + 3 3 15 3 15 30 + 4 4 15 3 31 30 Code colonnade_compute_tiered_col_widths_df(rep(30, 4), rep(15, 4), rep(60, 2)) Output - id width tier max_widths - 1 1 15 1 30 - 2 2 15 1 30 - 3 3 15 1 30 - 4 4 15 2 30 + id width tier offset max_widths + 1 1 15 1 15 30 + 2 2 15 1 31 30 + 3 3 15 1 47 30 + 4 4 15 2 15 30 Code colonnade_compute_tiered_col_widths_df(rep(30, 5), rep(15, 5), rep(60, 3)) Output - id width tier max_widths - 1 1 30 1 30 - 2 2 15 2 30 - 3 3 15 2 30 - 4 4 15 2 30 - 5 5 15 3 30 + id width tier offset max_widths + 1 1 30 1 30 30 + 2 2 15 2 15 30 + 3 3 15 2 31 30 + 4 4 15 2 47 30 + 5 5 15 3 15 30 Code colonnade_compute_tiered_col_widths_df(rep(30, 5), rep(15, 5), rep(60, 4)) Output - id width tier max_widths - 1 1 30 1 30 - 2 2 30 2 30 - 3 3 30 3 30 - 4 4 15 4 30 - 5 5 15 4 30 + id width tier offset max_widths + 1 1 30 1 30 30 + 2 2 30 2 30 30 + 3 3 30 3 30 30 + 4 4 15 4 15 30 + 5 5 15 4 31 30 Code colonnade_compute_tiered_col_widths_df(rep(30, 10), rep(15, 10), rep(60, 5)) Output - id width tier max_widths - 1 1 30 1 30 - 2 2 30 2 30 - 3 3 15 3 30 - 4 4 15 3 30 - 5 5 15 3 30 - 6 6 15 4 30 - 7 7 15 4 30 - 8 8 15 4 30 - 9 9 15 5 30 - 10 10 15 5 30 + id width tier offset max_widths + 1 1 30 1 30 30 + 2 2 30 2 30 30 + 3 3 15 3 15 30 + 4 4 15 3 31 30 + 5 5 15 3 47 30 + 6 6 15 4 15 30 + 7 7 15 4 31 30 + 8 8 15 4 47 30 + 9 9 15 5 15 30 + 10 10 15 5 31 30 # distribute_pillars() Code distribute_pillars(1:3, 10) Output - id width tier - 1 1 1 1 - 2 2 2 1 - 3 3 3 1 + id width tier offset + 1 1 1 1 1 + 2 2 2 1 4 + 3 3 3 1 8 Code distribute_pillars(1:3, 5) Output - id width tier - 1 1 1 1 - 2 2 2 1 - 3 3 3 NA + id width tier offset + 1 1 1 1 1 + 2 2 2 1 4 + 3 3 3 NA NA Code distribute_pillars(1:3, c(5, 5)) Output - id width tier - 1 1 1 1 - 2 2 2 1 - 3 3 3 2 + id width tier offset + 1 1 1 1 1 + 2 2 2 1 4 + 3 3 3 2 3 Code distribute_pillars(1:5, 7:9) Output - id width tier - 1 1 1 1 - 2 2 2 1 - 3 3 3 2 - 4 4 4 2 - 5 5 5 3 + id width tier offset + 1 1 1 1 1 + 2 2 2 1 4 + 3 3 3 2 3 + 4 4 4 2 8 + 5 5 5 3 5 Code distribute_pillars(3:5, 8:10) Output - id width tier - 1 1 3 1 - 2 2 4 1 - 3 3 5 2 + id width tier offset + 1 1 3 1 3 + 2 2 4 1 8 + 3 3 5 2 5 Code distribute_pillars(5:3, 9:8) Output - id width tier - 1 1 5 1 - 2 2 4 2 - 3 3 3 2 + id width tier offset + 1 1 5 1 5 + 2 2 4 2 4 + 3 3 3 2 8 # distribute_pillars_rev() Code distribute_pillars_rev(1:3, 10) Output - id width tier - 1 1 1 1 - 2 2 2 1 - 3 3 3 1 + id width tier offset + 1 1 1 1 5 + 2 2 2 1 7 + 3 3 3 1 10 Code distribute_pillars_rev(1:3, 5) Output - id width tier - 1 1 1 NA - 2 2 2 NA - 3 3 3 1 + id width tier offset + 1 1 1 NA 5 + 2 2 2 NA NA + 3 3 3 1 NA Code distribute_pillars_rev(1:3, c(5, 5)) Output - id width tier - 1 1 1 1 - 2 2 2 1 - 3 3 3 2 + id width tier offset + 1 1 1 1 3 + 2 2 2 1 5 + 3 3 3 2 5 Code distribute_pillars_rev(1:5, 7:9) Output - id width tier - 1 1 1 1 - 2 2 2 1 - 3 3 3 2 - 4 4 4 2 - 5 5 5 3 + id width tier offset + 1 1 1 1 5 + 2 2 2 1 7 + 3 3 3 2 4 + 4 4 4 2 8 + 5 5 5 3 9 Code distribute_pillars_rev(3:5, 8:10) Output - id width tier - 1 1 3 2 - 2 2 4 3 - 3 3 5 3 + id width tier offset + 1 1 3 2 8 + 2 2 4 3 4 + 3 3 5 3 9 Code distribute_pillars_rev(5:3, 9:8) Output - id width tier - 1 1 5 1 - 2 2 4 2 - 3 3 3 2 + id width tier offset + 1 1 5 1 9 + 2 2 4 2 3 + 3 3 3 2 8 From 0878abe17131507e7a086cd8258700948e90ce57 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Sun, 25 Jul 2021 11:55:46 +0200 Subject: [PATCH 028/147] SNAPSHOT: slightly happier, some failing corner cases --- R/multi.R | 45 ++++++-- tests/testthat/_snaps/ctl_colonnade_1.md | 108 +++++++++---------- tests/testthat/_snaps/ctl_colonnade_2.md | 36 +++---- tests/testthat/_snaps/format_multi_fuzz.md | 108 +++++++++---------- tests/testthat/_snaps/format_multi_fuzz_2.md | 36 +++---- tests/testthat/_snaps/multi.md | 16 +-- 6 files changed, 186 insertions(+), 163 deletions(-) diff --git a/R/multi.R b/R/multi.R index 64e3ac753..9dd825201 100644 --- a/R/multi.R +++ b/R/multi.R @@ -377,24 +377,34 @@ colonnade_compute_tiered_col_widths_df <- function(max_widths, min_widths, tier_ } #' Otherwise, some tiers from the start - #' will contain pillars with their maximum width, and the remaining tiers - #' contain pillars with their minimum width. + #' will contain pillars with their maximum width, + #' one tier will contain some pillars with maximum and some with minimum width, + #' and the remaining tiers contain pillars with their minimum width only. + #' #' We determine the cut point where minimum and maximum assignment #' agree. + #' This is the "mixed" tier which is refined later on. min_fit_rev <- distribute_pillars_rev(col_df$min_widths, tier_widths) - cut_point <- max(min(which(max_fit$tier == min_fit_rev$tier)), 1L) - cut_point_tier <- max_fit$tier[[cut_point]] + cut_point_optimistic <- max(which(max_fit$tier == min_fit_rev$tier), 1L) + tier_mix_fit <- min_fit_rev$tier[[cut_point_optimistic]] + + balance_idx <- which(min_fit_rev$tier == tier_mix_fit & (max_fit$tier >= tier_mix_fit | max_fit$tier == 0)) + cut_point <- min(balance_idx) + + # FIXME: inline distribute_pillars_offset, more fine-grained around cut point + + max_fit_cut <- max_fit[seq_len(cut_point - 1L), ] min_fit_cut <- distribute_pillars_offset( col_df$min_widths, tier_widths, - cut_point, - cut_point_tier + widths_offset = cut_point, + tier_widths_offset = tier_mix_fit ) combined_fit <- rbind( - max_fit[seq_len(cut_point - 1L), ], + max_fit_cut, min_fit_cut ) @@ -459,10 +469,23 @@ distribute_pillars_rev <- function(widths, tier_widths) { distribute_pillars_offset <- function(widths, tier_widths, widths_offset, tier_widths_offset) { - fit_cut <- distribute_pillars( - widths[seq2(widths_offset, length(widths))], - tier_widths[seq2(tier_widths_offset, length(tier_widths))] - ) + tier_widths <- tier_widths[seq2(tier_widths_offset, length(tier_widths))] + if (length(tier_widths) == 0) { + # Work around corner case + return(distribute_pillars(integer(), integer())) + } + + widths <- widths[seq2(widths_offset, length(widths))] + fit_cut <- distribute_pillars(widths, tier_widths) + add_pillars_offset(fit_cut, widths_offset, tier_widths_offset) +} + +add_pillars_offset <- function(fit_cut, widths_offset, tier_widths_offset) { + if (tier_widths_offset == 1) { + # Work around corner case + return(fit_cut) + } + fit_cut$id <- fit_cut$id + (widths_offset - 1L) fit_cut$tier <- fit_cut$tier + (tier_widths_offset - 1L) fit_cut diff --git a/tests/testthat/_snaps/ctl_colonnade_1.md b/tests/testthat/_snaps/ctl_colonnade_1.md index 300cfdd46..533b04828 100644 --- a/tests/testthat/_snaps/ctl_colonnade_1.md +++ b/tests/testthat/_snaps/ctl_colonnade_1.md @@ -380,18 +380,18 @@ `23` 1 AbcdefghijAbcdefghijAbc - `41` `5` `1` `14` `46` `30` `31` `44` - - 1 Abcd~ Abcde A Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ - `4` `7` `40` `43` `12` `29` `8` `36` + `41` `5` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijA Abcde + `1` `14` `46` `30` `31` `44` `4` `7` - 1 Abcd Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ - `45` `11` `20` `10` `6` `19` `48` `39` + 1 A Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd Abcd~ + `40` `43` `12` `29` `8` `36` `45` `11` 1 Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ - `42` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAb + `20` `10` `6` `19` `48` `39` `42` + + 1 Abcde~ Abcde~ Abcdef Abcd~ Abcde~ Abcde~ Abcde~ $extra_cols named list() @@ -418,30 +418,30 @@ `9` `15` 1 Abcdefghi AbcdefghijAbcde - `16` `1` `10` `40` `29` `26` + `16` `1` `10` + + 1 AbcdefghijAbcdef A Abcdefghij + `40` `29` `26` `22` `4` `43` - 1 Abcde~ A Abcd~ Abcd~ Abcd~ Abcd~ - `22` `4` `43` `20` `17` `46` + 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd Abcd~ + `20` `17` `46` `33` `35` `32` - 1 Abcde~ Abcd Abcd~ Abcd~ Abcd~ Abcd~ - `33` `35` `32` `2` `12` `8` - - 1 Abcde~ Abcd~ Abcd~ Ab Abcd~ Abcd~ - `37` `23` `39` `7` `18` `36` + 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ + `2` `12` `8` `37` `23` `39` + + 1 Ab Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ + `7` `18` `36` `42` `6` `30` 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ - `42` `6` `30` `19` `25` `5` + `19` `25` `5` `21` `47` `50` - 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ Abcde - `21` `47` `50` `28` `11` `31` + 1 Abcde~ Abcd~ Abcde Abcd~ Abcd~ Abcd~ + `28` `11` `31` `14` `24` `27` 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ - `14` `24` `27` `45` `41` `38` + `45` `41` `38` `3` `13` `48` - 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ - `3` `13` `48` - - 1 Abc Abcdefgh~ AbcdefghijAbcdefghi~ + 1 Abcde~ Abcd~ Abcd~ Abc Abcd~ Abcd~ $extra_cols named list() @@ -874,27 +874,27 @@ `16` `24` 1 AbcdefghijAbcdef AbcdefghijAbcdefghijAbcd - `4` `15` `47` `8` `11` `14` `50` - - 1 Abcd Abcde~ Abcdef~ Abcd~ Abcd~ Abcd~ Abcde~ - `17` `2` `44` `30` `36` `45` `25` - - 1 Abcde~ Ab Abcde~ Abcde~ Abcde~ Abcd~ Abcd~ - `38` `18` `29` `5` `13` `3` `23` - - 1 Abcdef~ Abcde~ Abcde~ Abcde Abcd~ Abc Abcd~ - `48` `40` `34` `22` `39` `33` `27` + `4` `15` + + 1 Abcd AbcdefghijAbcde + `47` `8` `11` `14` `50` `17` `2` + + 1 Abcdef~ Abcde~ Abcd~ Abcd~ Abcde~ Abcd~ Ab + `44` `30` `36` `45` `25` `38` `18` 1 Abcde~ Abcde~ Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ - `7` `19` `10` `37` `6` `35` `46` - - 1 Abcde~ Abcde~ Abcd~ Abcde~ Abcd~ Abcd~ Abcde~ - `31` `41` `43` `28` `42` `32` `21` + `29` `5` `13` `3` `23` `48` `40` + + 1 Abcde~ Abcde Abcde~ Abc Abcd~ Abcde~ Abcde~ + `34` `22` `39` `33` `27` `7` `19` 1 Abcde~ Abcde~ Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ - `9` - - 1 Abcdefghi + `10` `37` `6` `35` `46` `31` `41` + + 1 Abcde~ Abcde~ Abcdef Abcde~ Abcd~ Abcd~ Abcd~ + `43` `28` `42` `32` `21` `9` + + 1 Abcdefg~ Abcdef~ Abcdefg~ Abcde~ Abcde~ Abcd~ $extra_cols named list() @@ -939,21 +939,21 @@ `48` 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbcdefgh - `37` `36` `5` `43` `11` `14` `13` `39` `16` - - 1 Abcd~ Abcd~ Abcde Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ - `12` `4` `18` `42` `3` `10` `28` `40` `24` + `37` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefg + `36` `5` `43` `11` `14` `13` `39` `16` `12` `4` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdef Abcde Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd + `18` `42` `3` `10` `28` `40` `24` `29` `17` - 1 Abcd~ Abcd Abcd~ Abcd~ Abc Abcd~ Abcd~ Abcd~ Abcd~ - `29` `17` `35` `47` `2` `38` `34` `9` `7` + 1 Abcd~ Abcd~ Abc Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ + `35` `47` `2` `38` `34` `9` `7` `8` `50` - 1 Abcd~ Abcd~ Abcd~ Abcd~ Ab Abcd~ Abcd~ Abcd~ Abcd~ - `8` `50` `33` `32` `27` `46` `19` `22` `41` + 1 Abcd~ Abcd~ Ab Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ + `33` `32` `27` `46` `19` `22` `41` `30` `1` - 1 Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ - `30` `1` - - 1 AbcdefghijAbcdefghijAbcdefghij A + 1 Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ A $extra_cols named list() diff --git a/tests/testthat/_snaps/ctl_colonnade_2.md b/tests/testthat/_snaps/ctl_colonnade_2.md index adf72173c..54f884608 100644 --- a/tests/testthat/_snaps/ctl_colonnade_2.md +++ b/tests/testthat/_snaps/ctl_colonnade_2.md @@ -707,18 +707,18 @@ `26` 1 AbcdefghijAbcdefghijAbcdef - `44` `11` `46` `28` `7` `18` `50` `16` `29` + `44` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbcd + `11` `46` `28` `7` `18` `50` `16` `29` `30` 1 Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ - `30` `4` `23` `17` `40` `33` `14` `27` `19` + `4` `23` `17` `40` `33` `14` `27` `19` `34` + + 1 Abcd Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ + `32` `3` `37` `15` `10` `5` `35` `31` `42` - 1 Abcde~ Abcd Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ - `34` `32` `3` `37` `15` `10` `5` `35` `31` - - 1 Abcde~ Abcde~ Abc Abcd~ Abcd~ Abcd~ Abcde Abcd~ Abcd~ - `42` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAb + 1 Abcde~ Abc Abcde~ Abcd~ Abcd~ Abcde Abcd~ Abcd~ Abcd~ $extra_cols named list() @@ -835,15 +835,15 @@ `50` 1 AbcdefghijAbcdefghijAbcdefghij~ - `10` `9` `8` `47` `31` + `10` `9` `8` + + 1 Abcdefghij Abcdefghi Abcdefgh + `47` `31` `14` `38` `33` 1 Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ - `14` `38` `33` `32` `43` + `32` `43` `23` `15` `37` 1 Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ - `23` `15` `37` - - 1 Abcdefghi~ Abcdefg~ Abcdefghij~ $extra_cols named list() @@ -1037,12 +1037,12 @@ `48` 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbc~ - `20` `21` `44` `25` `10` `22` `30` + `20` `21` + + 1 AbcdefghijAbcdefghij AbcdefghijAbcdefghijA + `44` `25` `10` `22` `30` `40` `17` 1 Abcde~ Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ - `40` `17` - - 1 AbcdefghijAbcdefghijAbcdefghi~ AbcdefghijAb~ $extra_cols named list() diff --git a/tests/testthat/_snaps/format_multi_fuzz.md b/tests/testthat/_snaps/format_multi_fuzz.md index bb5db2dab..2970709b6 100644 --- a/tests/testthat/_snaps/format_multi_fuzz.md +++ b/tests/testthat/_snaps/format_multi_fuzz.md @@ -342,18 +342,18 @@ `23` 1 AbcdefghijAbcdefghijAbc - `41` `5` `1` `14` `46` `30` `31` `44` - - 1 Abcd~ Abcde A Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ - `4` `7` `40` `43` `12` `29` `8` `36` + `41` `5` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijA Abcde + `1` `14` `46` `30` `31` `44` `4` `7` - 1 Abcd Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ - `45` `11` `20` `10` `6` `19` `48` `39` + 1 A Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd Abcd~ + `40` `43` `12` `29` `8` `36` `45` `11` 1 Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ - `42` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAb + `20` `10` `6` `19` `48` `39` `42` + + 1 Abcde~ Abcde~ Abcdef Abcd~ Abcde~ Abcde~ Abcde~ Code options(width = 38) colonnade(df_str[c(44L, 34L, 49L, 9L, 15L, 16L, 1L, 10L, 40L, 29L, 26L, 22L, 4L, @@ -373,30 +373,30 @@ `9` `15` 1 Abcdefghi AbcdefghijAbcde - `16` `1` `10` `40` `29` `26` + `16` `1` `10` + + 1 AbcdefghijAbcdef A Abcdefghij + `40` `29` `26` `22` `4` `43` - 1 Abcde~ A Abcd~ Abcd~ Abcd~ Abcd~ - `22` `4` `43` `20` `17` `46` + 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd Abcd~ + `20` `17` `46` `33` `35` `32` - 1 Abcde~ Abcd Abcd~ Abcd~ Abcd~ Abcd~ - `33` `35` `32` `2` `12` `8` - - 1 Abcde~ Abcd~ Abcd~ Ab Abcd~ Abcd~ - `37` `23` `39` `7` `18` `36` + 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ + `2` `12` `8` `37` `23` `39` + + 1 Ab Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ + `7` `18` `36` `42` `6` `30` 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ - `42` `6` `30` `19` `25` `5` + `19` `25` `5` `21` `47` `50` - 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ Abcde - `21` `47` `50` `28` `11` `31` + 1 Abcde~ Abcd~ Abcde Abcd~ Abcd~ Abcd~ + `28` `11` `31` `14` `24` `27` 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ - `14` `24` `27` `45` `41` `38` + `45` `41` `38` `3` `13` `48` - 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ - `3` `13` `48` - - 1 Abc Abcdefgh~ AbcdefghijAbcdefghi~ + 1 Abcde~ Abcd~ Abcd~ Abc Abcd~ Abcd~ Code options(width = 54) colonnade(df_str[c(21L, 26L, 8L, 22L, 41L, 24L, 13L, 5L, 47L, 37L, 4L, 42L, 19L, @@ -787,27 +787,27 @@ `16` `24` 1 AbcdefghijAbcdef AbcdefghijAbcdefghijAbcd - `4` `15` `47` `8` `11` `14` `50` - - 1 Abcd Abcde~ Abcdef~ Abcd~ Abcd~ Abcd~ Abcde~ - `17` `2` `44` `30` `36` `45` `25` - - 1 Abcde~ Ab Abcde~ Abcde~ Abcde~ Abcd~ Abcd~ - `38` `18` `29` `5` `13` `3` `23` - - 1 Abcdef~ Abcde~ Abcde~ Abcde Abcd~ Abc Abcd~ - `48` `40` `34` `22` `39` `33` `27` + `4` `15` + + 1 Abcd AbcdefghijAbcde + `47` `8` `11` `14` `50` `17` `2` + + 1 Abcdef~ Abcde~ Abcd~ Abcd~ Abcde~ Abcd~ Ab + `44` `30` `36` `45` `25` `38` `18` 1 Abcde~ Abcde~ Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ - `7` `19` `10` `37` `6` `35` `46` - - 1 Abcde~ Abcde~ Abcd~ Abcde~ Abcd~ Abcd~ Abcde~ - `31` `41` `43` `28` `42` `32` `21` + `29` `5` `13` `3` `23` `48` `40` + + 1 Abcde~ Abcde Abcde~ Abc Abcd~ Abcde~ Abcde~ + `34` `22` `39` `33` `27` `7` `19` 1 Abcde~ Abcde~ Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ - `9` - - 1 Abcdefghi + `10` `37` `6` `35` `46` `31` `41` + + 1 Abcde~ Abcde~ Abcdef Abcde~ Abcd~ Abcd~ Abcd~ + `43` `28` `42` `32` `21` `9` + + 1 Abcdefg~ Abcdef~ Abcdefg~ Abcde~ Abcde~ Abcd~ Code options(width = 55) colonnade(df_str[c(6L, 49L, 26L, 45L, 25L, 15L, 31L, 20L, 21L, 44L, 23L, 48L, @@ -845,21 +845,21 @@ `48` 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbcdefgh - `37` `36` `5` `43` `11` `14` `13` `39` `16` - - 1 Abcd~ Abcd~ Abcde Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ - `12` `4` `18` `42` `3` `10` `28` `40` `24` + `37` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefg + `36` `5` `43` `11` `14` `13` `39` `16` `12` `4` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdef Abcde Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd + `18` `42` `3` `10` `28` `40` `24` `29` `17` - 1 Abcd~ Abcd Abcd~ Abcd~ Abc Abcd~ Abcd~ Abcd~ Abcd~ - `29` `17` `35` `47` `2` `38` `34` `9` `7` + 1 Abcd~ Abcd~ Abc Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ + `35` `47` `2` `38` `34` `9` `7` `8` `50` - 1 Abcd~ Abcd~ Abcd~ Abcd~ Ab Abcd~ Abcd~ Abcd~ Abcd~ - `8` `50` `33` `32` `27` `46` `19` `22` `41` + 1 Abcd~ Abcd~ Ab Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ + `33` `32` `27` `46` `19` `22` `41` `30` `1` - 1 Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ - `30` `1` - - 1 AbcdefghijAbcdefghijAbcdefghij A + 1 Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ A Code options(width = 46) colonnade(df_str[c(38L, 42L, 41L, 10L, 40L, 11L, 27L, 9L, 17L, 37L, 46L, 13L, diff --git a/tests/testthat/_snaps/format_multi_fuzz_2.md b/tests/testthat/_snaps/format_multi_fuzz_2.md index 8d092afa0..e2e4c8e00 100644 --- a/tests/testthat/_snaps/format_multi_fuzz_2.md +++ b/tests/testthat/_snaps/format_multi_fuzz_2.md @@ -648,18 +648,18 @@ `26` 1 AbcdefghijAbcdefghijAbcdef - `44` `11` `46` `28` `7` `18` `50` `16` `29` + `44` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbcd + `11` `46` `28` `7` `18` `50` `16` `29` `30` 1 Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ - `30` `4` `23` `17` `40` `33` `14` `27` `19` + `4` `23` `17` `40` `33` `14` `27` `19` `34` + + 1 Abcd Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ + `32` `3` `37` `15` `10` `5` `35` `31` `42` - 1 Abcde~ Abcd Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ - `34` `32` `3` `37` `15` `10` `5` `35` `31` - - 1 Abcde~ Abcde~ Abc Abcd~ Abcd~ Abcd~ Abcde Abcd~ Abcd~ - `42` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAb + 1 Abcde~ Abc Abcde~ Abcd~ Abcd~ Abcde Abcd~ Abcd~ Abcd~ Code options(width = 33) colonnade(df_str[c(40L, 6L, 25L, 5L, 26L, 17L, 19L, 2L, 11L, 34L, 45L, 24L, 22L, @@ -769,15 +769,15 @@ `50` 1 AbcdefghijAbcdefghijAbcdefghij~ - `10` `9` `8` `47` `31` + `10` `9` `8` + + 1 Abcdefghij Abcdefghi Abcdefgh + `47` `31` `14` `38` `33` 1 Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ - `14` `38` `33` `32` `43` + `32` `43` `23` `15` `37` 1 Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ - `23` `15` `37` - - 1 Abcdefghi~ Abcdefg~ Abcdefghij~ Code options(width = 32) colonnade(df_str[c(43L, 23L, 22L, 11L, 6L, 26L, 48L, 17L, 7L, 42L, 36L, 21L, @@ -957,12 +957,12 @@ `48` 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbc~ - `20` `21` `44` `25` `10` `22` `30` + `20` `21` + + 1 AbcdefghijAbcdefghij AbcdefghijAbcdefghijA + `44` `25` `10` `22` `30` `40` `17` 1 Abcde~ Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ - `40` `17` - - 1 AbcdefghijAbcdefghijAbcdefghi~ AbcdefghijAb~ Code options(width = 52) colonnade(df_str[c(7L, 44L, 19L, 21L, 18L, 35L, 23L, 50L, 33L, 37L, 25L, 26L, diff --git a/tests/testthat/_snaps/multi.md b/tests/testthat/_snaps/multi.md index 79dbe7e84..fbee805b4 100644 --- a/tests/testthat/_snaps/multi.md +++ b/tests/testthat/_snaps/multi.md @@ -20,19 +20,19 @@ colonnade_compute_tiered_col_widths_df(rep(30, 4), rep(15, 4), rep(60, 2)) Output id width tier offset max_widths - 1 1 15 1 15 30 - 2 2 15 1 31 30 - 3 3 15 1 47 30 - 4 4 15 2 15 30 + 1 1 30 1 30 30 + 2 2 15 2 15 30 + 3 3 15 2 31 30 + 4 4 15 2 47 30 Code colonnade_compute_tiered_col_widths_df(rep(30, 5), rep(15, 5), rep(60, 3)) Output id width tier offset max_widths 1 1 30 1 30 30 - 2 2 15 2 15 30 - 3 3 15 2 31 30 - 4 4 15 2 47 30 - 5 5 15 3 15 30 + 2 2 30 2 30 30 + 3 3 15 3 15 30 + 4 4 15 3 31 30 + 5 5 15 3 47 30 Code colonnade_compute_tiered_col_widths_df(rep(30, 5), rep(15, 5), rep(60, 4)) Output From 413ad37f43caa4f05788070a3842d983abeea737 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Sun, 25 Jul 2021 17:08:55 +0200 Subject: [PATCH 029/147] Precise cut points --- R/multi.R | 30 +- TODO.md | 32 - tests/testthat/_snaps/ctl_colonnade_1.md | 402 +++++------- tests/testthat/_snaps/ctl_colonnade_2.md | 640 +++++++------------ tests/testthat/_snaps/format_multi_fuzz.md | 402 +++++------- tests/testthat/_snaps/format_multi_fuzz_2.md | 640 +++++++------------ tests/testthat/_snaps/multi.md | 36 +- 7 files changed, 802 insertions(+), 1380 deletions(-) diff --git a/R/multi.R b/R/multi.R index 9dd825201..d40ab8074 100644 --- a/R/multi.R +++ b/R/multi.R @@ -386,29 +386,23 @@ colonnade_compute_tiered_col_widths_df <- function(max_widths, min_widths, tier_ #' This is the "mixed" tier which is refined later on. min_fit_rev <- distribute_pillars_rev(col_df$min_widths, tier_widths) - cut_point_optimistic <- max(which(max_fit$tier == min_fit_rev$tier), 1L) - tier_mix_fit <- min_fit_rev$tier[[cut_point_optimistic]] + cut_point <- max(which.max(max_fit$tier == min_fit_rev$tier & max_fit$offset <= min_fit_rev$offset), 0) + tier_mix_fit <- min_fit_rev$tier[[cut_point]] - balance_idx <- which(min_fit_rev$tier == tier_mix_fit & (max_fit$tier >= tier_mix_fit | max_fit$tier == 0)) - cut_point <- min(balance_idx) + max_fit_cut <- max_fit[seq_len(cut_point), ] + min_fit_cut <- min_fit_rev[seq2(cut_point + 1L, nrow(min_fit_rev)), ] - # FIXME: inline distribute_pillars_offset, more fine-grained around cut point + #min_fit_cut <- distribute_pillars_offset( + # col_df$min_widths, + # tier_widths, + # widths_offset = cut_point, + # tier_widths_offset = tier_mix_fit + #) - max_fit_cut <- max_fit[seq_len(cut_point - 1L), ] - - min_fit_cut <- distribute_pillars_offset( - col_df$min_widths, - tier_widths, - widths_offset = cut_point, - tier_widths_offset = tier_mix_fit - ) - - combined_fit <- rbind( - max_fit_cut, - min_fit_cut - ) + combined_fit <- rbind(max_fit_cut, min_fit_cut) combined_fit$max_widths <- col_df$max_widths + combined_fit$offsets <- NULL combined_fit } diff --git a/TODO.md b/TODO.md index 0c4a4f099..837e8d065 100644 --- a/TODO.md +++ b/TODO.md @@ -2,38 +2,6 @@ ## Next steps -- f-greedy: rethink implementation of `colonnade_compute_tiered_col_widths_df()` - - idea: fitting functions also indicate horizontal position within the tier? - This allows for a precise cutoff - - - fit min reverse - - no fit? fit min, return - - iterate over tiers - - fit max - - conflict with fit min reverse? break - - - - - start populating first tier - - fit? - - - how many free tiers do we have available? - - at least one? - - populate those with the maximum width - - recursive call for the remaining tiers - - none? - - populate first tier with maximum width, check through lookup if - - - - - shortcut: discrete fit with minimum width; if no fit, try to still fit with maximum width in a second step - - - - remove special case of "all pillars fit", we still want to reorganize/ - - for how many columns can we guarantee maximum width? - - current implementation answers that approximately, we know the tiers that we can close - - second step: close tiers (except last), try to fit remaining with a recursive call - - - - revdepcheck for adding ellipsis to methods - Milestone: diff --git a/tests/testthat/_snaps/ctl_colonnade_1.md b/tests/testthat/_snaps/ctl_colonnade_1.md index 533b04828..54a58f966 100644 --- a/tests/testthat/_snaps/ctl_colonnade_1.md +++ b/tests/testthat/_snaps/ctl_colonnade_1.md @@ -76,12 +76,12 @@ `37` 1 AbcdefghijAbcdefghijAbcdefghijAbcdefg - `34` `49` `46` `2` `32` `35` `39` `11` `17` - - 1 Abcde~ Abcde~ Abcde~ Ab Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ - `5` `26` `20` - - 1 Abcde AbcdefghijAbcdefghijAbcdef AbcdefghijAbcdefghij + `34` `49` `46` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcd Abcdefghij~ Abcdefghi~ + `2` `32` `35` `39` `11` `17` `5` `26` `20` + + 1 Ab Abcde~ Abcde~ Abcde~ Abcde~ Abcd~ Abcde Abcd~ Abcd~ $extra_cols named list() @@ -129,21 +129,21 @@ `49` 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbcdefghi - `34` `4` `39` `18` `36` `26` `38` `10` - - 1 Abcde~ Abcd Abcdef~ Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ - `8` `5` `15` `44` `24` `46` `14` `25` - - 1 Abcde~ Abcde Abcde~ Abcdef~ Abcd~ Abcde~ Abcd~ Abcd~ - `27` `3` `37` `35` `12` `9` `13` `22` - - 1 Abcde~ Abc Abcdef~ Abcdef~ Abcd~ Abcd~ Abcd~ Abcd~ - `33` `42` `11` `19` `50` `23` `30` `32` - - 1 Abcde~ Abcde~ Abcde~ Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ - `2` `43` `31` - - 1 Ab AbcdefghijAbcdefghijAbcde~ AbcdefghijAbcdefgh~ + `34` `4` `39` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcd Abcd Abcdefghij~ + `18` `36` `26` `38` `10` `8` `5` `15` + + 1 Abcde~ Abcdef~ Abcde~ Abcde~ Abcd~ Abcd~ Abcde Abcd~ + `44` `24` `46` `14` `25` `27` `3` `37` + + 1 Abcdef~ Abcde~ Abcdef~ Abcd~ Abcd~ Abcd~ Abc Abcd~ + `35` `12` `9` `13` `22` `33` `42` `11` + + 1 Abcdef~ Abcde~ Abcd~ Abcd~ Abcd~ Abcde~ Abcde~ Abcd~ + `19` `50` `23` `30` `32` `2` `43` `31` + + 1 Abcde~ Abcdef~ Abcde~ Abcde~ Abcd~ Ab Abcd~ Abcd~ $extra_cols named list() @@ -161,48 +161,36 @@ `47` 1 AbcdefghijAbcdefghijAbcdefghi~ - `42` - - 1 AbcdefghijAbcdefghijAbcdefghi~ - `4` - - 1 Abcd - `46` - - 1 AbcdefghijAbcdefghijAbcdefghi~ - `9` - - 1 Abcdefghi - `34` - - 1 AbcdefghijAbcdefghijAbcdefghi~ - `19` `39` `8` `32` `36` + `42` `4` `46` `9` + + 1 Abcdefgh~ Abcd Abcdefg~ Abcd~ + `34` `19` `39` `8` `32` 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ - `12` `29` `5` `15` `11` + `36` `12` `29` `5` `15` - 1 Abcde~ Abcd~ Abcde Abcd~ Abcd~ - `31` `27` `33` `28` `43` + 1 Abcde~ Abcd~ Abcd~ Abcde Abcd~ + `11` `31` `27` `33` `28` 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ - `6` `13` `22` `14` `16` + `43` `6` `13` `22` `14` - 1 Abcdef Abcd~ Abcd~ Abcd~ Abcd~ - `35` `50` `38` `7` `23` + 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ + `16` `35` `50` `38` `7` 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ - `45` `40` `3` `2` `24` + `23` `45` `40` `3` `2` - 1 Abcde~ Abcd~ Abc Ab Abcd~ - `41` `10` `30` `25` `17` + 1 Abcde~ Abcd~ Abcd~ Abc Ab + `24` `41` `10` `30` `25` 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ - `26` `48` `37` `49` `1` + `17` `26` `48` `37` `49` - 1 Abcde~ Abcd~ Abcd~ Abcd~ A - `18` `21` `44` `20` - - 1 Abcdef~ Abcdef~ Abcdef~ Abcde~ + 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ + `1` `18` `21` `44` `20` + + 1 A Abcde~ Abcd~ Abcd~ Abcd~ $extra_cols named list() @@ -253,18 +241,18 @@ `39` 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghi - `28` `43` `32` `30` `48` `44` `6` `20` `13` + `28` `43` `32` + + 1 AbcdefghijAbcdefghijAbcdefgh AbcdefghijAb~ Abcdefghi~ + `30` `48` `44` `6` `20` `13` `15` `18` `42` 1 Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ - `15` `18` `42` `9` `12` `37` `45` `16` `40` + `9` `12` `37` `45` `16` `40` `11` `14` `38` 1 Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ - `11` `14` `38` `1` `7` `3` `23` `35` `50` + `1` `7` `3` `23` `35` `50` `17` `49` `33` - 1 Abcd~ Abcd~ Abcd~ A Abcd~ Abc Abcd~ Abcd~ Abcd~ - `17` `49` `33` - - 1 Abcdefghij~ AbcdefghijAbcdefghijAb~ AbcdefghijAbcdef~ + 1 A Abcd~ Abc Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ $extra_cols named list() @@ -279,39 +267,30 @@ }) Output $body - `27` `22` - - 1 AbcdefghijAbcdefghijAbcdefg AbcdefghijAbcdefghijAb - `9` `23` `16` - - 1 Abcdefghi AbcdefghijAbcdefghijAbc AbcdefghijAbcdef - `19` `25` - - 1 AbcdefghijAbcdefghi AbcdefghijAbcdefghijAbcde - `31` - - 1 AbcdefghijAbcdefghijAbcdefghijA - `44` `1` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbcd A - `28` - - 1 AbcdefghijAbcdefghijAbcdefgh - `46` `12` `20` `43` `37` `5` `2` `18` - - 1 Abcdef~ Abcde~ Abcd~ Abcde~ Abcde~ Abcde Ab Abcd~ - `41` `26` `33` `11` `49` `24` `35` `4` - - 1 Abcde~ Abcde~ Abcde~ Abcde~ Abcde~ Abcd~ Abcd~ Abcd - `47` `30` `7` `34` `3` `32` `42` `10` - - 1 Abcdef~ Abcde~ Abcde~ Abcd~ Abc Abcd~ Abcde~ Abcd~ - `45` `38` `39` `48` `14` `6` `17` `36` - - 1 Abcde~ Abcde~ Abcde~ Abcdef~ Abcd~ Abcd~ Abcd~ Abcd~ - `50` `40` `13` `8` `21` `15` `29` - - 1 Abcdefgh~ Abcdefg~ Abcde~ Abcde~ Abcde~ Abcd~ Abcde~ + `27` + + 1 AbcdefghijAbcdefghijAbcdefg + `22` + + 1 AbcdefghijAbcdefghijAb + `9` `23` `16` `19` `25` `31` `44` `1` + + 1 Abcde~ Abcde~ Abcde~ Abcde~ Abcd~ Abcd~ Abcde~ A + `28` `46` `12` `20` `43` `37` `5` `2` + + 1 Abcde~ Abcdef~ Abcd~ Abcd~ Abcde~ Abcde~ Abcde Ab + `18` `41` `26` `33` `11` `49` `24` `35` + + 1 Abcde~ Abcde~ Abcde~ Abcde~ Abcd~ Abcde~ Abcd~ Abcd~ + `4` `47` `30` `7` `34` `3` `32` `42` + + 1 Abcd Abcdef~ Abcde~ Abcde~ Abcd~ Abc Abcd~ Abcde~ + `10` `45` `38` `39` `48` `14` `6` `17` + + 1 Abcde~ Abcdef~ Abcde~ Abcd~ Abcde~ Abcd~ Abcd~ Abcd~ + `36` `50` `40` `13` `8` `21` `15` `29` + + 1 Abcde~ Abcdef~ Abcdef~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ $extra_cols named list() @@ -380,18 +359,18 @@ `23` 1 AbcdefghijAbcdefghijAbc - `41` `5` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijA Abcde - `1` `14` `46` `30` `31` `44` `4` `7` + `41` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijA + `5` `1` `14` `46` `30` `31` `44` `4` - 1 A Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd Abcd~ - `40` `43` `12` `29` `8` `36` `45` `11` + 1 Abcde A Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd + `7` `40` `43` `12` `29` `8` `36` `45` + + 1 Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ + `11` `20` `10` `6` `19` `48` `39` `42` 1 Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ - `20` `10` `6` `19` `48` `39` `42` - - 1 Abcde~ Abcde~ Abcdef Abcd~ Abcde~ Abcde~ Abcde~ $extra_cols named list() @@ -477,21 +456,21 @@ `42` 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAb - `19` `34` `11` `43` `38` `3` `33` `20` - - 1 Abcde~ Abcde~ Abcde~ Abcde~ Abcde~ Abc Abcd~ Abcd~ - `31` `2` `18` `48` `27` `44` `9` `35` - - 1 Abcde~ Ab Abcde~ Abcdef~ Abcd~ Abcde~ Abcd~ Abcd~ - `30` `6` `49` `10` `1` `16` `46` `29` - - 1 Abcde~ Abcdef Abcdef~ Abcd~ A Abcd~ Abcde~ Abcd~ - `12` `14` `45` `36` `15` `39` `50` `23` - - 1 Abcde~ Abcde~ Abcdef~ Abcd~ Abcd~ Abcd~ Abcde~ Abcd~ - `17` `28` `7` `32` `40` `25` - - 1 Abcdef~ Abcdefgh~ Abcde~ Abcdefg~ Abcdefghi~ Abcdef~ + `19` `34` `11` `43` `38` `3` + + 1 AbcdefghijAbcdefghi Abcde~ Abcde~ Abcde~ Abcd~ Abc + `33` `20` `31` `2` `18` `48` `27` `44` + + 1 Abcde~ Abcde~ Abcde~ Ab Abcd~ Abcde~ Abcd~ Abcde~ + `9` `35` `30` `6` `49` `10` `1` `16` + + 1 Abcde~ Abcdef~ Abcde~ Abcd~ Abcde~ Abcd~ A Abcd~ + `46` `29` `12` `14` `45` `36` `15` `39` + + 1 Abcdef~ Abcde~ Abcde~ Abcd~ Abcde~ Abcd~ Abcd~ Abcd~ + `50` `23` `17` `28` `7` `32` `40` `25` + + 1 Abcdef~ Abcde~ Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ $extra_cols named list() @@ -640,51 +619,36 @@ `45` 1 AbcdefghijAbcdefghijAbcdefgh~ - `14` - - 1 AbcdefghijAbcd - `49` - - 1 AbcdefghijAbcdefghijAbcdefgh~ - `24` - - 1 AbcdefghijAbcdefghijAbcd - `22` - - 1 AbcdefghijAbcdefghijAb - `31` - - 1 AbcdefghijAbcdefghijAbcdefgh~ - `42` - - 1 AbcdefghijAbcdefghijAbcdefgh~ - `18` `16` `47` `25` `4` - - 1 Abcd~ Abcd~ Abcd~ Abcd~ Abcd - `37` `8` `26` `21` `50` + `14` `49` `24` `22` + + 1 Abcde~ Abcdefg~ Abcde~ Abcde~ + `31` `42` `18` `16` `47` 1 Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ - `5` `41` `30` `2` `33` + `25` `4` `37` `8` `26` + + 1 Abcd~ Abcd Abcd~ Abcd~ Abcd~ + `21` `50` `5` `41` `30` + + 1 Abcd~ Abcd~ Abcde Abcd~ Abcd~ + `2` `33` `34` `3` `44` - 1 Abcde Abcd~ Abcd~ Ab Abcd~ - `34` `3` `44` `19` `43` + 1 Ab Abcd~ Abcd~ Abc Abcd~ + `19` `43` `6` `32` `29` - 1 Abcd~ Abc Abcd~ Abcd~ Abcd~ - `6` `32` `29` `20` `1` + 1 Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ + `20` `1` `13` `11` `40` - 1 Abcd~ Abcd~ Abcd~ Abcd~ A - `13` `11` `40` `12` `48` + 1 Abcd~ A Abcd~ Abcd~ Abcd~ + `12` `48` `23` `9` `15` 1 Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ - `23` `9` `15` `46` `36` + `46` `36` `27` `35` `28` 1 Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ - `27` `35` `28` `10` `7` + `10` `7` `39` `17` `38` 1 Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ - `39` `17` `38` - - 1 Abcdefghi~ Abcdefg~ Abcdefgh~ $extra_cols named list() @@ -753,18 +717,18 @@ `36` 1 AbcdefghijAbcdefghijAbcdefghijAbcdef - `28` `5` `10` `30` `20` `1` `14` `43` + `28` `5` `10` `30` + + 1 AbcdefghijAbcdefghijAbcdefgh Abcde Abcde~ Abcdefg~ + `20` `1` `14` `43` `49` `23` `26` `21` - 1 Abcde~ Abcde Abcde~ Abcde~ Abcd~ A Abcd~ Abcd~ - `49` `23` `26` `21` `32` `19` `34` `15` + 1 Abcde~ A Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ + `32` `19` `34` `15` `48` `4` `7` `35` - 1 Abcde~ Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ - `48` `4` `7` `35` `40` `8` `22` `3` - - 1 Abcde~ Abcd Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ Abc - `25` `12` `27` `2` - - 1 AbcdefghijAbcdef~ Abcdefg~ AbcdefghijAbcdef~ Ab + 1 Abcde~ Abcde~ Abcde~ Abcd~ Abcd~ Abcd Abcd~ Abcd~ + `40` `8` `22` `3` `25` `12` `27` `2` + + 1 Abcdef~ Abcde~ Abcd~ Abc Abcd~ Abcd~ Abcd~ Ab $extra_cols named list() @@ -839,15 +803,15 @@ `42` `3` 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAb Abc - `11` `40` `26` `37` `7` `39` `6` `4` `19` - - 1 Abcde~ Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd Abcd~ - `8` `45` `14` `24` `23` `2` `47` `9` `49` - - 1 Abcde~ Abcde~ Abcde~ Abcd~ Abcd~ Ab Abcd~ Abcd~ Abcd~ - `41` `38` `22` `44` `15` - - 1 AbcdefghijAb~ AbcdefghijA~ Abcdefg~ AbcdefghijA~ Abcdef~ + `11` `40` `26` `37` `7` + + 1 AbcdefghijA AbcdefghijAbc~ Abcdefghi~ AbcdefghijA~ Abcd~ + `39` `6` `4` `19` `8` `45` `14` `24` `23` + + 1 Abcde~ Abcdef Abcd Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ + `2` `47` `9` `49` `41` `38` `22` `44` `15` + + 1 Ab Abcde~ Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ $extra_cols named list() @@ -874,27 +838,27 @@ `16` `24` 1 AbcdefghijAbcdef AbcdefghijAbcdefghijAbcd - `4` `15` - - 1 Abcd AbcdefghijAbcde - `47` `8` `11` `14` `50` `17` `2` - - 1 Abcdef~ Abcde~ Abcd~ Abcd~ Abcde~ Abcd~ Ab - `44` `30` `36` `45` `25` `38` `18` + `4` + + 1 Abcd + `15` `47` `8` `11` `14` `50` `17` + + 1 Abcde~ Abcdef~ Abcd~ Abcd~ Abcd~ Abcde~ Abcd~ + `2` `44` `30` `36` `45` `25` `38` + + 1 Ab Abcde~ Abcde~ Abcde~ Abcde~ Abcd~ Abcd~ + `18` `29` `5` `13` `3` `23` `48` + + 1 Abcde~ Abcde~ Abcde Abcde~ Abc Abcd~ Abcde~ + `40` `34` `22` `39` `33` `27` `7` 1 Abcde~ Abcde~ Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ - `29` `5` `13` `3` `23` `48` `40` - - 1 Abcde~ Abcde Abcde~ Abc Abcd~ Abcde~ Abcde~ - `34` `22` `39` `33` `27` `7` `19` + `19` `10` `37` `6` `35` `46` `31` + + 1 Abcde~ Abcde~ Abcde~ Abcd~ Abcd~ Abcde~ Abcd~ + `41` `43` `28` `42` `32` `21` `9` 1 Abcde~ Abcde~ Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ - `10` `37` `6` `35` `46` `31` `41` - - 1 Abcde~ Abcde~ Abcdef Abcde~ Abcd~ Abcd~ Abcd~ - `43` `28` `42` `32` `21` `9` - - 1 Abcdefg~ Abcdef~ Abcdefg~ Abcde~ Abcde~ Abcd~ $extra_cols named list() @@ -939,12 +903,12 @@ `48` 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbcdefgh - `37` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefg - `36` `5` `43` `11` `14` `13` `39` `16` `12` `4` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdef Abcde Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd + `37` `36` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefg AbcdefghijAbcd~ + `5` `43` `11` `14` `13` `39` `16` `12` `4` + + 1 Abcde Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd `18` `42` `3` `10` `28` `40` `24` `29` `17` 1 Abcd~ Abcd~ Abc Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ @@ -971,51 +935,27 @@ `38` 1 AbcdefghijAbcdefghijAbcdefghijAbcdefgh - `42` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAb - `41` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijA - `10` - - 1 Abcdefghij - `40` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghij - `11` `27` - - 1 AbcdefghijA AbcdefghijAbcdefghijAbcdefg - `9` `17` - - 1 Abcdefghi AbcdefghijAbcdefg - `37` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefg - `46` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbc~ - `13` - - 1 AbcdefghijAbc - `36` `18` `31` `20` `39` `12` `44` + `42` `41` `10` `40` `11` `27` `9` 1 Abcde~ Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ - `33` `50` `34` `26` `32` `23` `30` + `17` `37` `46` `13` `36` `18` `31` 1 Abcde~ Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ - `29` `21` `4` `49` `19` `25` `3` + `20` `39` `12` `44` `33` `50` `34` + + 1 Abcde~ Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ + `26` `32` `23` `30` `29` `21` `4` + + 1 Abcde~ Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ Abcd + `49` `19` `25` `3` `6` `15` `14` + + 1 Abcdef~ Abcde~ Abcd~ Abc Abcd~ Abcd~ Abcd~ + `43` `48` `8` `22` `1` `2` `45` + + 1 Abcde~ Abcde~ Abcde~ Abcd~ A Ab Abcd~ + `35` `16` `5` `47` `28` `24` `7` - 1 Abcde~ Abcde~ Abcd Abcde~ Abcd~ Abcd~ Abc - `6` `15` `14` `43` `48` `8` `22` - - 1 Abcdef Abcde~ Abcd~ Abcd~ Abcde~ Abcd~ Abcd~ - `1` `2` `45` `35` `16` `5` `47` - - 1 A Ab Abcde~ Abcde~ Abcde~ Abcde Abcd~ - `28` `24` `7` - - 1 AbcdefghijAbcdefghi~ AbcdefghijAbcde~ Abcde~ + 1 Abcde~ Abcde~ Abcde Abcde~ Abcd~ Abcd~ Abcd~ $extra_cols named list() diff --git a/tests/testthat/_snaps/ctl_colonnade_2.md b/tests/testthat/_snaps/ctl_colonnade_2.md index 54f884608..c862e0454 100644 --- a/tests/testthat/_snaps/ctl_colonnade_2.md +++ b/tests/testthat/_snaps/ctl_colonnade_2.md @@ -22,24 +22,24 @@ `47` 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbcdefg - `25` `42` `27` `44` `20` `14` `36` `43` - - 1 Abcde~ Abcde~ Abcde~ Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ - `41` `26` `45` `22` `9` `13` `32` `31` - - 1 Abcdef~ Abcde~ Abcdef~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ - `12` `19` `48` `49` `35` `3` `11` `23` - - 1 Abcde~ Abcde~ Abcdef~ Abcde~ Abcd~ Abc Abcd~ Abcd~ - `24` `40` `15` `38` `10` `46` `5` `50` - - 1 Abcde~ Abcde~ Abcde~ Abcd~ Abcd~ Abcde~ Abcde Abcde~ - `18` `21` `6` `30` `2` `7` `1` `4` - - 1 Abcdef~ Abcde~ Abcd~ Abcdef~ Ab Abcd~ A Abcd - `8` `17` `33` `39` `37` - - 1 Abcde~ Abcdefg~ Abcdefghij~ AbcdefghijA~ Abcdefghij~ + `25` `42` `27` `44` `20` + + 1 AbcdefghijAbcdefghijAbcde Abcde~ Abcde~ Abcde~ Abcd~ + `14` `36` `43` `41` `26` `45` `22` `9` + + 1 Abcde~ Abcde~ Abcde~ Abcde~ Abcd~ Abcde~ Abcd~ Abcd~ + `13` `32` `31` `12` `19` `48` `49` `35` + + 1 Abcde~ Abcde~ Abcde~ Abcd~ Abcd~ Abcde~ Abcde~ Abcd~ + `3` `11` `23` `24` `40` `15` `38` `10` + + 1 Abc Abcde~ Abcde~ Abcde~ Abcde~ Abcd~ Abcde~ Abcd~ + `46` `5` `50` `18` `21` `6` `30` `2` + + 1 Abcdef~ Abcde Abcdef~ Abcde~ Abcd~ Abcd~ Abcd~ Ab + `7` `1` `4` `8` `17` `33` `39` `37` + + 1 Abcde~ A Abcd Abcde~ Abcd~ Abcde~ Abcde~ Abcde~ $extra_cols named list() @@ -147,12 +147,12 @@ `16` `19` 1 AbcdefghijAbcdef AbcdefghijAbcdefghi - `15` `22` `39` `10` `46` `5` - - 1 Abcde~ Abcde~ Abcdef~ Abcd~ Abcde~ Abcde - `30` `8` `26` `37` - - 1 Abcdefghij~ Abcde~ Abcdefgh~ Abcdefghij~ + `15` `22` `39` `10` + + 1 AbcdefghijAbcde Abcdefg~ Abcdefgh~ Abcd~ + `46` `5` `30` `8` `26` `37` + + 1 Abcdef~ Abcde Abcdef~ Abcd~ Abcd~ Abcde~ $extra_cols named list() @@ -224,21 +224,21 @@ `41` 1 AbcdefghijAbcdefghijAbcdefghijAbcdef~ - `21` `4` `25` `38` `48` `9` - - 1 Abcde~ Abcd Abcde~ Abcd~ Abcd~ Abcd~ - `24` `26` `39` `20` `36` `42` + `21` `4` `25` + + 1 AbcdefghijAbcdefghijA Abcd Abcdefgh~ + `38` `48` `9` `24` `26` `39` 1 Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ - `16` `6` `11` `7` `12` `1` + `20` `36` `42` `16` `6` `11` - 1 Abcde~ Abcdef Abcd~ Abcd~ Abcd~ A - `46` `15` `5` `8` `50` `32` + 1 Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ + `7` `12` `1` `46` `15` `5` + + 1 Abcde~ Abcd~ A Abcde~ Abcd~ Abcde + `8` `50` `32` `30` `49` `28` - 1 Abcde~ Abcde~ Abcde Abcd~ Abcd~ Abcd~ - `30` `49` `28` - - 1 AbcdefghijA~ AbcdefghijAb~ Abcdefghi~ + 1 Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ $extra_cols named list() @@ -256,57 +256,36 @@ `11` 1 AbcdefghijA - `36` - - 1 AbcdefghijAbcdefghijAbcdefghi~ - `17` - - 1 AbcdefghijAbcdefg - `14` - - 1 AbcdefghijAbcd - `31` - - 1 AbcdefghijAbcdefghijAbcdefghi~ - `35` - - 1 AbcdefghijAbcdefghijAbcdefghi~ - `23` - - 1 AbcdefghijAbcdefghijAbc - `13` `6` - - 1 AbcdefghijAbc Abcdef - `44` - - 1 AbcdefghijAbcdefghijAbcdefghi~ - `45` - - 1 AbcdefghijAbcdefghijAbcdefghi~ - `22` `21` `18` `33` `10` + `36` `17` `14` `31` + + 1 Abcdefg~ Abcdef~ Abcd~ Abcdef~ + `35` `23` `13` `6` `44` 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ - `43` `2` `46` `34` `3` + `45` `22` `21` `18` `33` - 1 Abcde~ Ab Abcd~ Abcd~ Abc - `19` `1` `38` `9` `37` + 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ + `10` `43` `2` `46` `34` - 1 Abcde~ A Abcd~ Abcd~ Abcd~ - `5` `8` `25` `49` `27` + 1 Abcde~ Abcd~ Ab Abcd~ Abcd~ + `3` `19` `1` `38` `9` - 1 Abcde Abcde~ Abcd~ Abcd~ Abcd~ - `29` `15` `39` `24` `40` + 1 Abc Abcde~ A Abcd~ Abcd~ + `37` `5` `8` `25` `49` + + 1 Abcde~ Abcde Abcd~ Abcd~ Abcd~ + `27` `29` `15` `39` `24` 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ - `48` `26` `47` `42` `41` + `40` `48` `26` `47` `42` 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ - `12` `28` `30` `7` `16` + `41` `12` `28` `30` `7` 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ - `4` `50` `20` `32` - - 1 Abcd Abcdefg~ Abcdef~ Abcdef~ + `16` `4` `50` `20` `32` + + 1 Abcde~ Abcd Abcd~ Abcd~ Abcd~ $extra_cols named list() @@ -408,18 +387,18 @@ `34` 1 AbcdefghijAbcdefghijAbcdefghijAb~ - `8` `24` `29` `1` `12` - - 1 Abcde~ Abcdef~ Abcde~ A Abcd~ - `2` `20` `17` `35` `5` - - 1 Ab Abcdef~ Abcd~ Abcdef~ Abcde - `19` `30` `7` `26` `42` - - 1 Abcde~ Abcdef~ Abcd~ Abcd~ Abcde~ - `41` `39` `10` - - 1 AbcdefghijAb~ AbcdefghijA~ Abcde~ + `8` `24` `29` + + 1 Abcdefgh Abcdefghij~ AbcdefghijA~ + `1` `12` `2` `20` `17` + + 1 A Abcde~ Ab Abcdef~ Abcde~ + `35` `5` `19` `30` `7` + + 1 Abcdef~ Abcde Abcde~ Abcde~ Abcd~ + `26` `42` `41` `39` `10` + + 1 Abcde~ Abcde~ Abcde~ Abcde~ Abcd~ $extra_cols named list() @@ -437,45 +416,36 @@ `43` 1 AbcdefghijAbcdefghijAbcdefghi~ - `1` `3` `15` - - 1 A Abc AbcdefghijAbcde - `28` - - 1 AbcdefghijAbcdefghijAbcdefgh - `12` - - 1 AbcdefghijAb - `46` - - 1 AbcdefghijAbcdefghijAbcdefghi~ - `34` `31` `7` `11` `4` + `1` `3` `15` `28` + + 1 A Abc Abcdefg~ Abcdefgh~ + `12` `46` `34` `31` `7` - 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd - `44` `8` `9` `5` `36` + 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ + `11` `4` `44` `8` `9` - 1 Abcde~ Abcd~ Abcd~ Abcde Abcd~ - `22` `17` `39` `18` `45` + 1 Abcde~ Abcd Abcd~ Abcd~ Abcd~ + `5` `36` `22` `17` `39` + + 1 Abcde Abcde~ Abcd~ Abcd~ Abcd~ + `18` `45` `37` `13` `29` 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ - `37` `13` `29` `6` `30` + `6` `30` `16` `20` `10` - 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ - `16` `20` `10` `19` `26` + 1 Abcdef Abcd~ Abcd~ Abcd~ Abcd~ + `19` `26` `33` `40` `35` 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ - `33` `40` `35` `48` `38` + `48` `38` `25` `2` `47` - 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ - `25` `2` `47` `42` `41` + 1 Abcde~ Abcd~ Abcd~ Ab Abcd~ + `42` `41` `27` `14` `21` - 1 Abcde~ Ab Abcd~ Abcd~ Abcd~ - `27` `14` `21` `24` `50` + 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ + `24` `50` `49` `23` `32` 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ - `49` `23` `32` - - 1 Abcdefghi~ Abcdefgh~ Abcdefgh~ $extra_cols named list() @@ -493,117 +463,36 @@ `37` 1 AbcdefghijAbcdefghijAbcdefgh~ - `46` - - 1 AbcdefghijAbcdefghijAbcdefgh~ - `21` `3` - - 1 AbcdefghijAbcdefghijA Abc - `16` - - 1 AbcdefghijAbcdef - `39` - - 1 AbcdefghijAbcdefghijAbcdefgh~ - `34` - - 1 AbcdefghijAbcdefghijAbcdefgh~ - `33` - - 1 AbcdefghijAbcdefghijAbcdefgh~ - `10` `17` - - 1 Abcdefghij AbcdefghijAbcdefg - `19` - - 1 AbcdefghijAbcdefghi - `36` - - 1 AbcdefghijAbcdefghijAbcdefgh~ - `45` - - 1 AbcdefghijAbcdefghijAbcdefgh~ - `49` - - 1 AbcdefghijAbcdefghijAbcdefgh~ - `11` - - 1 AbcdefghijA - `50` - - 1 AbcdefghijAbcdefghijAbcdefgh~ - `14` - - 1 AbcdefghijAbcd - `29` - - 1 AbcdefghijAbcdefghijAbcdefghi - `44` - - 1 AbcdefghijAbcdefghijAbcdefgh~ - `13` - - 1 AbcdefghijAbc - `30` - - 1 AbcdefghijAbcdefghijAbcdefgh~ - `38` - - 1 AbcdefghijAbcdefghijAbcdefgh~ - `32` - - 1 AbcdefghijAbcdefghijAbcdefgh~ - `40` - - 1 AbcdefghijAbcdefghijAbcdefgh~ - `42` - - 1 AbcdefghijAbcdefghijAbcdefgh~ - `1` - - 1 A - `31` - - 1 AbcdefghijAbcdefghijAbcdefgh~ - `41` - - 1 AbcdefghijAbcdefghijAbcdefgh~ - `7` - - 1 Abcdefg - `23` - - 1 AbcdefghijAbcdefghijAbc - `35` - - 1 AbcdefghijAbcdefghijAbcdefgh~ - `28` - - 1 AbcdefghijAbcdefghijAbcdefgh - `6` - - 1 Abcdef - `25` - - 1 AbcdefghijAbcdefghijAbcde - `2` `9` `12` - - 1 Ab Abcdefghi AbcdefghijAb - `15` `5` - - 1 AbcdefghijAbcde Abcde - `18` - - 1 AbcdefghijAbcdefgh - `20` - - 1 AbcdefghijAbcdefghij - `27` `43` `8` `47` `4` + `46` `21` `3` `16` + + 1 Abcdefg~ Abcdef~ Abc Abcde~ + `39` `34` `33` `10` `17` + + 1 Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ + `19` `36` `45` `49` `11` + + 1 Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ + `50` `14` `29` `44` `13` + + 1 Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ + `30` `38` `32` `40` `42` + + 1 Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ + `1` `31` `41` `7` `23` - 1 Abcd~ Abcd~ Abcd~ Abcd~ Abcd - `48` `24` `26` `22` - - 1 Abcdef~ Abcdef~ Abcde~ Abcde~ + 1 A Abcd~ Abcd~ Abcd~ Abcd~ + `35` `28` `6` `25` `2` + + 1 Abcd~ Abcd~ Abcd~ Abcd~ Ab + `9` `12` `15` `5` `18` + + 1 Abcd~ Abcd~ Abcd~ Abcde Abcd~ + `20` `27` `43` `8` `47` + + 1 Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ + `4` `48` `24` `26` `22` + + 1 Abcd Abcd~ Abcd~ Abcd~ Abcd~ $extra_cols named list() @@ -621,33 +510,24 @@ `31` 1 AbcdefghijAbcdefghijAbcdefghijA - `39` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghi - `40` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghij - `30` `10` - - 1 AbcdefghijAbcdefghijAbcdefghij Abcdefghij - `21` `9` `16` - - 1 AbcdefghijAbcdefghijA Abcdefghi AbcdefghijAbcdef - `46` `25` `15` `24` `3` `50` `35` `1` `12` + `39` `40` `30` `10` + + 1 AbcdefghijAbcdef~ AbcdefghijAbcdef~ AbcdefghijAb~ Abcde~ + `21` `9` `16` `46` `25` `15` `24` `3` `50` - 1 Abcde~ Abcde~ Abcde~ Abcd~ Abc Abcd~ Abcd~ A Abcd~ - `34` `48` `4` `29` `23` `37` `36` `28` `43` - - 1 Abcde~ Abcde~ Abcd Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ - `11` `17` `32` `8` `41` `13` `44` `7` `38` + 1 Abcde~ Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ Abc Abcd~ + `35` `1` `12` `34` `48` `4` `29` `23` `37` + + 1 Abcde~ A Abcde~ Abcde~ Abcd~ Abcd Abcd~ Abcd~ Abcd~ + `36` `28` `43` `11` `17` `32` `8` `41` `13` 1 Abcde~ Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ - `26` `33` `20` `19` `2` `18` `49` `27` `47` + `44` `7` `38` `26` `33` `20` `19` `2` `18` + + 1 Abcde~ Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ Ab Abcd~ + `49` `27` `47` `22` `14` `6` `5` `45` `42` - 1 Abcde~ Abcde~ Abcde~ Abcd~ Ab Abcd~ Abcd~ Abcd~ Abcd~ - `22` `14` `6` `5` `45` `42` - - 1 Abcdefgh~ Abcdef~ Abcd~ Abcde AbcdefghijAb~ AbcdefghijA~ + 1 Abcde~ Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ Abcde Abcd~ Abcd~ $extra_cols named list() @@ -861,78 +741,36 @@ `43` 1 AbcdefghijAbcdefghijAbcdefghi~ - `23` - - 1 AbcdefghijAbcdefghijAbc - `22` - - 1 AbcdefghijAbcdefghijAb - `11` `6` - - 1 AbcdefghijA Abcdef - `26` - - 1 AbcdefghijAbcdefghijAbcdef - `48` - - 1 AbcdefghijAbcdefghijAbcdefghi~ - `17` `7` - - 1 AbcdefghijAbcdefg Abcdefg - `42` - - 1 AbcdefghijAbcdefghijAbcdefghi~ - `36` - - 1 AbcdefghijAbcdefghijAbcdefghi~ - `21` - - 1 AbcdefghijAbcdefghijA - `35` - - 1 AbcdefghijAbcdefghijAbcdefghi~ - `50` - - 1 AbcdefghijAbcdefghijAbcdefghi~ - `13` - - 1 AbcdefghijAbc - `19` - - 1 AbcdefghijAbcdefghi - `29` - - 1 AbcdefghijAbcdefghijAbcdefghi - `8` `15` `4` - - 1 Abcdefgh AbcdefghijAbcde Abcd - `2` - - 1 Ab - `27` - - 1 AbcdefghijAbcdefghijAbcdefg - `49` - - 1 AbcdefghijAbcdefghijAbcdefghi~ - `47` `30` `31` `25` `28` + `23` `22` `11` `6` + + 1 Abcdefg~ Abcdefg~ Abcde~ Abcd~ + `26` `48` `17` `7` `42` 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ - `46` `12` `32` `39` `24` + `36` `21` `35` `50` `13` 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ - `10` `45` `5` `37` `14` + `19` `29` `8` `15` `4` + + 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd + `2` `27` `49` `47` `30` + + 1 Ab Abcde~ Abcd~ Abcd~ Abcd~ + `31` `25` `28` `46` `12` - 1 Abcde~ Abcd~ Abcde Abcd~ Abcd~ - `40` `20` `41` `44` `33` + 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ + `32` `39` `24` `10` `45` 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ - `18` `38` `3` `1` `34` + `5` `37` `14` `40` `20` + + 1 Abcde Abcde~ Abcd~ Abcd~ Abcd~ + `41` `44` `33` `18` `38` - 1 Abcde~ Abcd~ Abc A Abcd~ - `16` `9` - - 1 AbcdefghijAbcdef Abcdefghi + 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ + `3` `1` `34` `16` `9` + + 1 Abc A Abcde~ Abcd~ Abcd~ $extra_cols named list() @@ -1108,18 +946,18 @@ `45` 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbcde - `6` `4` `11` `24` `43` `32` `3` `38` - - 1 Abcdef Abcd Abcde~ Abcde~ Abcd~ Abcd~ Abc Abcd~ - `5` `49` `27` `17` `8` `22` `40` `12` - - 1 Abcde Abcde~ Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ - `15` `1` `28` `31` `29` `13` `48` `34` - - 1 Abcde~ A Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ - `36` `30` `20` `16` `46` - - 1 Abcdefghij~ Abcdefghi~ Abcdef~ Abcde~ AbcdefghijA~ + `6` `4` `11` `24` `43` + + 1 Abcdef Abcd Abcdef~ Abcdefghij~ AbcdefghijAbcdef~ + `32` `3` `38` `5` `49` `27` `17` `8` + + 1 Abcde~ Abc Abcde~ Abcde Abcde~ Abcd~ Abcd~ Abcd~ + `22` `40` `12` `15` `1` `28` `31` `29` + + 1 Abcde~ Abcde~ Abcde~ Abcd~ A Abcd~ Abcd~ Abcd~ + `13` `48` `34` `36` `30` `20` `16` `46` + + 1 Abcde~ Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ $extra_cols named list() @@ -1137,39 +975,36 @@ `38` 1 AbcdefghijAbcdefghijAbcdefghijAb~ - `18` - - 1 AbcdefghijAbcdefgh - `23` `36` `35` `20` `44` - - 1 Abcde~ Abcde~ Abcde~ Abcde~ Abcd~ - `19` `13` `41` `31` `7` - - 1 Abcde~ Abcde~ Abcde~ Abcde~ Abcd~ - `11` `29` `2` `14` `26` + `18` `23` `36` `35` + + 1 Abcdef~ Abcdef~ Abcdefg~ Abcdefg~ + `20` `44` `19` `13` `41` - 1 Abcde~ Abcdef~ Ab Abcd~ Abcde~ - `46` `40` `45` `9` `34` + 1 Abcde~ Abcdef~ Abcd~ Abcd~ Abcde~ + `31` `7` `11` `29` `2` + + 1 Abcdef~ Abcde~ Abcd~ Abcde~ Ab + `14` `26` `46` `40` `45` 1 Abcde~ Abcde~ Abcde~ Abcde~ Abcd~ - `33` `22` `1` `17` `28` - - 1 Abcdef~ Abcde~ A Abcd~ Abcde~ - `10` `21` `30` `47` `49` - - 1 Abcde~ Abcde~ Abcd~ Abcde~ Abcde~ - `6` `12` `4` `25` `32` - - 1 Abcdef Abcde~ Abcd Abcde~ Abcde~ - `15` `43` `24` `48` `3` + `9` `34` `33` `22` `1` + + 1 Abcde~ Abcdef~ Abcde~ Abcd~ A + `17` `28` `10` `21` `30` + + 1 Abcde~ Abcdef~ Abcd~ Abcd~ Abcde~ + `47` `49` `6` `12` `4` + + 1 Abcdef~ Abcdef~ Abcd~ Abcd~ Abcd + `25` `32` `15` `43` `24` - 1 Abcde~ Abcdef~ Abcd~ Abcde~ Abc - `37` `50` `42` `39` `16` - - 1 Abcde~ Abcde~ Abcde~ Abcde~ Abcd~ - `8` `27` `5` - - 1 Abcdef~ AbcdefghijAbcdefgh~ Abcde + 1 Abcde~ Abcdef~ Abcd~ Abcde~ Abcd~ + `48` `3` `37` `50` `42` + + 1 Abcde~ Abc Abcde~ Abcde~ Abcde~ + `39` `16` `8` `27` `5` + + 1 Abcdef~ Abcde~ Abcd~ Abcde~ Abcde $extra_cols named list() @@ -1184,81 +1019,36 @@ }) Output $body - `22` `9` - - 1 AbcdefghijAbcdefghijAb Abcdefghi - `11` `26` - - 1 AbcdefghijA AbcdefghijAbcdefghijAbcdef - `19` `16` - - 1 AbcdefghijAbcdefghi AbcdefghijAbcdef - `32` - - 1 AbcdefghijAbcdefghijAbcdefghijAb - `25` `1` - - 1 AbcdefghijAbcdefghijAbcde A - `30` - - 1 AbcdefghijAbcdefghijAbcdefghij - `31` `6` - - 1 AbcdefghijAbcdefghijAbcdefghijA Abcdef - `24` `10` - - 1 AbcdefghijAbcdefghijAbcd Abcdefghij - `39` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghi - `21` - - 1 AbcdefghijAbcdefghijA - `50` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefgh~ - `7` `29` - - 1 Abcdefg AbcdefghijAbcdefghijAbcdefghi - `12` - - 1 AbcdefghijAb - `46` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefgh~ - `43` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefgh~ - `15` - - 1 AbcdefghijAbcde - `35` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcde - `20` - - 1 AbcdefghijAbcdefghij - `40` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefgh~ - `49` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefgh~ - `38` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefgh - `36` `48` `34` `3` `8` `4` + `22` + + 1 AbcdefghijAbcdefghijAb + `9` + + 1 Abcdefghi + `11` `26` `19` `16` `32` `25` + + 1 Abcde~ Abcde~ Abcde~ Abcd~ Abcde~ Abcd~ + `1` `30` `31` `6` `24` `10` + + 1 A Abcdef~ Abcde~ Abcd~ Abcde~ Abcd~ + `39` `21` `50` `7` `29` `12` - 1 Abcdef~ Abcde~ Abcde~ Abc Abcd~ Abcd - `27` `42` `44` `33` `45` `18` + 1 Abcdef~ Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ + `46` `43` `15` `35` `20` `40` 1 Abcde~ Abcde~ Abcde~ Abcde~ Abcd~ Abcd~ - `5` `2` `13` `47` `28` `17` - - 1 Abcde Ab Abcde~ Abcdef~ Abcde~ Abcd~ - `37` `14` `41` `23` - - 1 Abcdefghij~ Abcdef~ Abcdefghi~ Abcdefg~ + `49` `38` `36` `48` `34` `3` + + 1 Abcde~ Abcde~ Abcde~ Abcde~ Abcd~ Abc + `8` `4` `27` `42` `44` `33` + + 1 Abcde~ Abcd Abcde~ Abcde~ Abcde~ Abcd~ + `45` `18` `5` `2` `13` `47` + + 1 Abcdef~ Abcde~ Abcde Ab Abcd~ Abcde~ + `28` `17` `37` `14` `41` `23` + + 1 Abcde~ Abcde~ Abcde~ Abcd~ Abcde~ Abcd~ $extra_cols named list() diff --git a/tests/testthat/_snaps/format_multi_fuzz.md b/tests/testthat/_snaps/format_multi_fuzz.md index 2970709b6..909b2daea 100644 --- a/tests/testthat/_snaps/format_multi_fuzz.md +++ b/tests/testthat/_snaps/format_multi_fuzz.md @@ -73,12 +73,12 @@ `37` 1 AbcdefghijAbcdefghijAbcdefghijAbcdefg - `34` `49` `46` `2` `32` `35` `39` `11` `17` - - 1 Abcde~ Abcde~ Abcde~ Ab Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ - `5` `26` `20` - - 1 Abcde AbcdefghijAbcdefghijAbcdef AbcdefghijAbcdefghij + `34` `49` `46` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcd Abcdefghij~ Abcdefghi~ + `2` `32` `35` `39` `11` `17` `5` `26` `20` + + 1 Ab Abcde~ Abcde~ Abcde~ Abcde~ Abcd~ Abcde Abcd~ Abcd~ Code options(width = 54) colonnade(df_str[c(40L, 28L, 7L, 16L, 48L, 6L, 21L, 1L, 20L, 17L, 47L, 45L, 29L, @@ -119,21 +119,21 @@ `49` 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbcdefghi - `34` `4` `39` `18` `36` `26` `38` `10` - - 1 Abcde~ Abcd Abcdef~ Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ - `8` `5` `15` `44` `24` `46` `14` `25` - - 1 Abcde~ Abcde Abcde~ Abcdef~ Abcd~ Abcde~ Abcd~ Abcd~ - `27` `3` `37` `35` `12` `9` `13` `22` - - 1 Abcde~ Abc Abcdef~ Abcdef~ Abcd~ Abcd~ Abcd~ Abcd~ - `33` `42` `11` `19` `50` `23` `30` `32` - - 1 Abcde~ Abcde~ Abcde~ Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ - `2` `43` `31` - - 1 Ab AbcdefghijAbcdefghijAbcde~ AbcdefghijAbcdefgh~ + `34` `4` `39` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcd Abcd Abcdefghij~ + `18` `36` `26` `38` `10` `8` `5` `15` + + 1 Abcde~ Abcdef~ Abcde~ Abcde~ Abcd~ Abcd~ Abcde Abcd~ + `44` `24` `46` `14` `25` `27` `3` `37` + + 1 Abcdef~ Abcde~ Abcdef~ Abcd~ Abcd~ Abcd~ Abc Abcd~ + `35` `12` `9` `13` `22` `33` `42` `11` + + 1 Abcdef~ Abcde~ Abcd~ Abcd~ Abcd~ Abcde~ Abcde~ Abcd~ + `19` `50` `23` `30` `32` `2` `43` `31` + + 1 Abcde~ Abcdef~ Abcde~ Abcde~ Abcd~ Ab Abcd~ Abcd~ Code options(width = 32) colonnade(df_str[c(47L, 42L, 4L, 46L, 9L, 34L, 19L, 39L, 8L, 32L, 36L, 12L, 29L, @@ -144,48 +144,36 @@ `47` 1 AbcdefghijAbcdefghijAbcdefghi~ - `42` - - 1 AbcdefghijAbcdefghijAbcdefghi~ - `4` - - 1 Abcd - `46` - - 1 AbcdefghijAbcdefghijAbcdefghi~ - `9` - - 1 Abcdefghi - `34` - - 1 AbcdefghijAbcdefghijAbcdefghi~ - `19` `39` `8` `32` `36` + `42` `4` `46` `9` + + 1 Abcdefgh~ Abcd Abcdefg~ Abcd~ + `34` `19` `39` `8` `32` 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ - `12` `29` `5` `15` `11` + `36` `12` `29` `5` `15` - 1 Abcde~ Abcd~ Abcde Abcd~ Abcd~ - `31` `27` `33` `28` `43` + 1 Abcde~ Abcd~ Abcd~ Abcde Abcd~ + `11` `31` `27` `33` `28` 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ - `6` `13` `22` `14` `16` + `43` `6` `13` `22` `14` - 1 Abcdef Abcd~ Abcd~ Abcd~ Abcd~ - `35` `50` `38` `7` `23` + 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ + `16` `35` `50` `38` `7` 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ - `45` `40` `3` `2` `24` + `23` `45` `40` `3` `2` - 1 Abcde~ Abcd~ Abc Ab Abcd~ - `41` `10` `30` `25` `17` + 1 Abcde~ Abcd~ Abcd~ Abc Ab + `24` `41` `10` `30` `25` 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ - `26` `48` `37` `49` `1` + `17` `26` `48` `37` `49` - 1 Abcde~ Abcd~ Abcd~ Abcd~ A - `18` `21` `44` `20` - - 1 Abcdef~ Abcdef~ Abcdef~ Abcde~ + 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ + `1` `18` `21` `44` `20` + + 1 A Abcde~ Abcd~ Abcd~ Abcd~ Code options(width = 55) colonnade(df_str[c(41L, 4L, 25L, 31L, 8L, 22L, 19L, 10L, 29L, 21L, 34L, 5L, 26L, @@ -229,18 +217,18 @@ `39` 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghi - `28` `43` `32` `30` `48` `44` `6` `20` `13` + `28` `43` `32` + + 1 AbcdefghijAbcdefghijAbcdefgh AbcdefghijAb~ Abcdefghi~ + `30` `48` `44` `6` `20` `13` `15` `18` `42` 1 Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ - `15` `18` `42` `9` `12` `37` `45` `16` `40` + `9` `12` `37` `45` `16` `40` `11` `14` `38` 1 Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ - `11` `14` `38` `1` `7` `3` `23` `35` `50` + `1` `7` `3` `23` `35` `50` `17` `49` `33` - 1 Abcd~ Abcd~ Abcd~ A Abcd~ Abc Abcd~ Abcd~ Abcd~ - `17` `49` `33` - - 1 Abcdefghij~ AbcdefghijAbcdefghijAb~ AbcdefghijAbcdef~ + 1 A Abcd~ Abc Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Code options(width = 54) colonnade(df_str[c(27L, 22L, 9L, 23L, 16L, 19L, 25L, 31L, 44L, 1L, 28L, 46L, @@ -248,39 +236,30 @@ 30L, 7L, 34L, 3L, 32L, 42L, 10L, 45L, 38L, 39L, 48L, 14L, 6L, 17L, 36L, 50L, 40L, 13L, 8L, 21L, 15L, 29L)], width = 552) Output - `27` `22` - - 1 AbcdefghijAbcdefghijAbcdefg AbcdefghijAbcdefghijAb - `9` `23` `16` - - 1 Abcdefghi AbcdefghijAbcdefghijAbc AbcdefghijAbcdef - `19` `25` - - 1 AbcdefghijAbcdefghi AbcdefghijAbcdefghijAbcde - `31` - - 1 AbcdefghijAbcdefghijAbcdefghijA - `44` `1` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbcd A - `28` - - 1 AbcdefghijAbcdefghijAbcdefgh - `46` `12` `20` `43` `37` `5` `2` `18` - - 1 Abcdef~ Abcde~ Abcd~ Abcde~ Abcde~ Abcde Ab Abcd~ - `41` `26` `33` `11` `49` `24` `35` `4` - - 1 Abcde~ Abcde~ Abcde~ Abcde~ Abcde~ Abcd~ Abcd~ Abcd - `47` `30` `7` `34` `3` `32` `42` `10` - - 1 Abcdef~ Abcde~ Abcde~ Abcd~ Abc Abcd~ Abcde~ Abcd~ - `45` `38` `39` `48` `14` `6` `17` `36` - - 1 Abcde~ Abcde~ Abcde~ Abcdef~ Abcd~ Abcd~ Abcd~ Abcd~ - `50` `40` `13` `8` `21` `15` `29` - - 1 Abcdefgh~ Abcdefg~ Abcde~ Abcde~ Abcde~ Abcd~ Abcde~ + `27` + + 1 AbcdefghijAbcdefghijAbcdefg + `22` + + 1 AbcdefghijAbcdefghijAb + `9` `23` `16` `19` `25` `31` `44` `1` + + 1 Abcde~ Abcde~ Abcde~ Abcde~ Abcd~ Abcd~ Abcde~ A + `28` `46` `12` `20` `43` `37` `5` `2` + + 1 Abcde~ Abcdef~ Abcd~ Abcd~ Abcde~ Abcde~ Abcde Ab + `18` `41` `26` `33` `11` `49` `24` `35` + + 1 Abcde~ Abcde~ Abcde~ Abcde~ Abcd~ Abcde~ Abcd~ Abcd~ + `4` `47` `30` `7` `34` `3` `32` `42` + + 1 Abcd Abcdef~ Abcde~ Abcde~ Abcd~ Abc Abcd~ Abcde~ + `10` `45` `38` `39` `48` `14` `6` `17` + + 1 Abcde~ Abcdef~ Abcde~ Abcd~ Abcde~ Abcd~ Abcd~ Abcd~ + `36` `50` `40` `13` `8` `21` `15` `29` + + 1 Abcde~ Abcdef~ Abcdef~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Code options(width = 49) colonnade(df_str[c(32L, 24L, 18L, 25L, 26L, 13L, 33L, 2L, 50L, 38L, 37L, 16L, @@ -342,18 +321,18 @@ `23` 1 AbcdefghijAbcdefghijAbc - `41` `5` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijA Abcde - `1` `14` `46` `30` `31` `44` `4` `7` + `41` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijA + `5` `1` `14` `46` `30` `31` `44` `4` - 1 A Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd Abcd~ - `40` `43` `12` `29` `8` `36` `45` `11` + 1 Abcde A Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd + `7` `40` `43` `12` `29` `8` `36` `45` + + 1 Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ + `11` `20` `10` `6` `19` `48` `39` `42` 1 Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ - `20` `10` `6` `19` `48` `39` `42` - - 1 Abcde~ Abcde~ Abcdef Abcd~ Abcde~ Abcde~ Abcde~ Code options(width = 38) colonnade(df_str[c(44L, 34L, 49L, 9L, 15L, 16L, 1L, 10L, 40L, 29L, 26L, 22L, 4L, @@ -425,21 +404,21 @@ `42` 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAb - `19` `34` `11` `43` `38` `3` `33` `20` - - 1 Abcde~ Abcde~ Abcde~ Abcde~ Abcde~ Abc Abcd~ Abcd~ - `31` `2` `18` `48` `27` `44` `9` `35` - - 1 Abcde~ Ab Abcde~ Abcdef~ Abcd~ Abcde~ Abcd~ Abcd~ - `30` `6` `49` `10` `1` `16` `46` `29` - - 1 Abcde~ Abcdef Abcdef~ Abcd~ A Abcd~ Abcde~ Abcd~ - `12` `14` `45` `36` `15` `39` `50` `23` - - 1 Abcde~ Abcde~ Abcdef~ Abcd~ Abcd~ Abcd~ Abcde~ Abcd~ - `17` `28` `7` `32` `40` `25` - - 1 Abcdef~ Abcdefgh~ Abcde~ Abcdefg~ Abcdefghi~ Abcdef~ + `19` `34` `11` `43` `38` `3` + + 1 AbcdefghijAbcdefghi Abcde~ Abcde~ Abcde~ Abcd~ Abc + `33` `20` `31` `2` `18` `48` `27` `44` + + 1 Abcde~ Abcde~ Abcde~ Ab Abcd~ Abcde~ Abcd~ Abcde~ + `9` `35` `30` `6` `49` `10` `1` `16` + + 1 Abcde~ Abcdef~ Abcde~ Abcd~ Abcde~ Abcd~ A Abcd~ + `46` `29` `12` `14` `45` `36` `15` `39` + + 1 Abcdef~ Abcde~ Abcde~ Abcd~ Abcde~ Abcd~ Abcd~ Abcd~ + `50` `23` `17` `28` `7` `32` `40` `25` + + 1 Abcdef~ Abcde~ Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ Code options(width = 39) colonnade(df_str[c(23L, 49L, 13L, 37L, 3L, 25L, 36L, 4L, 9L, 7L, 27L, 48L, 12L, @@ -574,51 +553,36 @@ `45` 1 AbcdefghijAbcdefghijAbcdefgh~ - `14` - - 1 AbcdefghijAbcd - `49` - - 1 AbcdefghijAbcdefghijAbcdefgh~ - `24` - - 1 AbcdefghijAbcdefghijAbcd - `22` - - 1 AbcdefghijAbcdefghijAb - `31` - - 1 AbcdefghijAbcdefghijAbcdefgh~ - `42` - - 1 AbcdefghijAbcdefghijAbcdefgh~ - `18` `16` `47` `25` `4` - - 1 Abcd~ Abcd~ Abcd~ Abcd~ Abcd - `37` `8` `26` `21` `50` + `14` `49` `24` `22` + + 1 Abcde~ Abcdefg~ Abcde~ Abcde~ + `31` `42` `18` `16` `47` 1 Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ - `5` `41` `30` `2` `33` + `25` `4` `37` `8` `26` + + 1 Abcd~ Abcd Abcd~ Abcd~ Abcd~ + `21` `50` `5` `41` `30` + + 1 Abcd~ Abcd~ Abcde Abcd~ Abcd~ + `2` `33` `34` `3` `44` - 1 Abcde Abcd~ Abcd~ Ab Abcd~ - `34` `3` `44` `19` `43` + 1 Ab Abcd~ Abcd~ Abc Abcd~ + `19` `43` `6` `32` `29` - 1 Abcd~ Abc Abcd~ Abcd~ Abcd~ - `6` `32` `29` `20` `1` + 1 Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ + `20` `1` `13` `11` `40` - 1 Abcd~ Abcd~ Abcd~ Abcd~ A - `13` `11` `40` `12` `48` + 1 Abcd~ A Abcd~ Abcd~ Abcd~ + `12` `48` `23` `9` `15` 1 Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ - `23` `9` `15` `46` `36` + `46` `36` `27` `35` `28` 1 Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ - `27` `35` `28` `10` `7` + `10` `7` `39` `17` `38` 1 Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ - `39` `17` `38` - - 1 Abcdefghi~ Abcdefg~ Abcdefgh~ Code options(width = 52) colonnade(df_str[c(38L, 46L, 17L, 11L, 24L, 18L, 16L, 39L, 50L, 42L, 6L, 13L, @@ -680,18 +644,18 @@ `36` 1 AbcdefghijAbcdefghijAbcdefghijAbcdef - `28` `5` `10` `30` `20` `1` `14` `43` + `28` `5` `10` `30` + + 1 AbcdefghijAbcdefghijAbcdefgh Abcde Abcde~ Abcdefg~ + `20` `1` `14` `43` `49` `23` `26` `21` - 1 Abcde~ Abcde Abcde~ Abcde~ Abcd~ A Abcd~ Abcd~ - `49` `23` `26` `21` `32` `19` `34` `15` + 1 Abcde~ A Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ + `32` `19` `34` `15` `48` `4` `7` `35` - 1 Abcde~ Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ - `48` `4` `7` `35` `40` `8` `22` `3` - - 1 Abcde~ Abcd Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ Abc - `25` `12` `27` `2` - - 1 AbcdefghijAbcdef~ Abcdefg~ AbcdefghijAbcdef~ Ab + 1 Abcde~ Abcde~ Abcde~ Abcd~ Abcd~ Abcd Abcd~ Abcd~ + `40` `8` `22` `3` `25` `12` `27` `2` + + 1 Abcdef~ Abcde~ Abcd~ Abc Abcd~ Abcd~ Abcd~ Ab Code options(width = 58) colonnade(df_str[c(17L, 28L, 29L, 27L, 20L, 31L, 43L, 30L, 32L, 48L, 10L, 50L, @@ -759,15 +723,15 @@ `42` `3` 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAb Abc - `11` `40` `26` `37` `7` `39` `6` `4` `19` - - 1 Abcde~ Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd Abcd~ - `8` `45` `14` `24` `23` `2` `47` `9` `49` - - 1 Abcde~ Abcde~ Abcde~ Abcd~ Abcd~ Ab Abcd~ Abcd~ Abcd~ - `41` `38` `22` `44` `15` - - 1 AbcdefghijAb~ AbcdefghijA~ Abcdefg~ AbcdefghijA~ Abcdef~ + `11` `40` `26` `37` `7` + + 1 AbcdefghijA AbcdefghijAbc~ Abcdefghi~ AbcdefghijA~ Abcd~ + `39` `6` `4` `19` `8` `45` `14` `24` `23` + + 1 Abcde~ Abcdef Abcd Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ + `2` `47` `9` `49` `41` `38` `22` `44` `15` + + 1 Ab Abcde~ Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Code options(width = 47) colonnade(df_str[c(1L, 26L, 20L, 12L, 49L, 16L, 24L, 4L, 15L, 47L, 8L, 11L, 14L, @@ -787,27 +751,27 @@ `16` `24` 1 AbcdefghijAbcdef AbcdefghijAbcdefghijAbcd - `4` `15` - - 1 Abcd AbcdefghijAbcde - `47` `8` `11` `14` `50` `17` `2` - - 1 Abcdef~ Abcde~ Abcd~ Abcd~ Abcde~ Abcd~ Ab - `44` `30` `36` `45` `25` `38` `18` + `4` + + 1 Abcd + `15` `47` `8` `11` `14` `50` `17` + + 1 Abcde~ Abcdef~ Abcd~ Abcd~ Abcd~ Abcde~ Abcd~ + `2` `44` `30` `36` `45` `25` `38` + + 1 Ab Abcde~ Abcde~ Abcde~ Abcde~ Abcd~ Abcd~ + `18` `29` `5` `13` `3` `23` `48` + + 1 Abcde~ Abcde~ Abcde Abcde~ Abc Abcd~ Abcde~ + `40` `34` `22` `39` `33` `27` `7` 1 Abcde~ Abcde~ Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ - `29` `5` `13` `3` `23` `48` `40` - - 1 Abcde~ Abcde Abcde~ Abc Abcd~ Abcde~ Abcde~ - `34` `22` `39` `33` `27` `7` `19` + `19` `10` `37` `6` `35` `46` `31` + + 1 Abcde~ Abcde~ Abcde~ Abcd~ Abcd~ Abcde~ Abcd~ + `41` `43` `28` `42` `32` `21` `9` 1 Abcde~ Abcde~ Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ - `10` `37` `6` `35` `46` `31` `41` - - 1 Abcde~ Abcde~ Abcdef Abcde~ Abcd~ Abcd~ Abcd~ - `43` `28` `42` `32` `21` `9` - - 1 Abcdefg~ Abcdef~ Abcdefg~ Abcde~ Abcde~ Abcd~ Code options(width = 55) colonnade(df_str[c(6L, 49L, 26L, 45L, 25L, 15L, 31L, 20L, 21L, 44L, 23L, 48L, @@ -845,12 +809,12 @@ `48` 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbcdefgh - `37` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefg - `36` `5` `43` `11` `14` `13` `39` `16` `12` `4` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdef Abcde Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd + `37` `36` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefg AbcdefghijAbcd~ + `5` `43` `11` `14` `13` `39` `16` `12` `4` + + 1 Abcde Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd `18` `42` `3` `10` `28` `40` `24` `29` `17` 1 Abcd~ Abcd~ Abc Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ @@ -870,49 +834,25 @@ `38` 1 AbcdefghijAbcdefghijAbcdefghijAbcdefgh - `42` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAb - `41` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijA - `10` - - 1 Abcdefghij - `40` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghij - `11` `27` - - 1 AbcdefghijA AbcdefghijAbcdefghijAbcdefg - `9` `17` - - 1 Abcdefghi AbcdefghijAbcdefg - `37` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefg - `46` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbc~ - `13` - - 1 AbcdefghijAbc - `36` `18` `31` `20` `39` `12` `44` + `42` `41` `10` `40` `11` `27` `9` 1 Abcde~ Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ - `33` `50` `34` `26` `32` `23` `30` + `17` `37` `46` `13` `36` `18` `31` 1 Abcde~ Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ - `29` `21` `4` `49` `19` `25` `3` + `20` `39` `12` `44` `33` `50` `34` + + 1 Abcde~ Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ + `26` `32` `23` `30` `29` `21` `4` + + 1 Abcde~ Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ Abcd + `49` `19` `25` `3` `6` `15` `14` + + 1 Abcdef~ Abcde~ Abcd~ Abc Abcd~ Abcd~ Abcd~ + `43` `48` `8` `22` `1` `2` `45` + + 1 Abcde~ Abcde~ Abcde~ Abcd~ A Ab Abcd~ + `35` `16` `5` `47` `28` `24` `7` - 1 Abcde~ Abcde~ Abcd Abcde~ Abcd~ Abcd~ Abc - `6` `15` `14` `43` `48` `8` `22` - - 1 Abcdef Abcde~ Abcd~ Abcd~ Abcde~ Abcd~ Abcd~ - `1` `2` `45` `35` `16` `5` `47` - - 1 A Ab Abcde~ Abcde~ Abcde~ Abcde Abcd~ - `28` `24` `7` - - 1 AbcdefghijAbcdefghi~ AbcdefghijAbcde~ Abcde~ + 1 Abcde~ Abcde~ Abcde Abcde~ Abcd~ Abcd~ Abcd~ diff --git a/tests/testthat/_snaps/format_multi_fuzz_2.md b/tests/testthat/_snaps/format_multi_fuzz_2.md index e2e4c8e00..a8811444b 100644 --- a/tests/testthat/_snaps/format_multi_fuzz_2.md +++ b/tests/testthat/_snaps/format_multi_fuzz_2.md @@ -19,24 +19,24 @@ `47` 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbcdefg - `25` `42` `27` `44` `20` `14` `36` `43` - - 1 Abcde~ Abcde~ Abcde~ Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ - `41` `26` `45` `22` `9` `13` `32` `31` - - 1 Abcdef~ Abcde~ Abcdef~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ - `12` `19` `48` `49` `35` `3` `11` `23` - - 1 Abcde~ Abcde~ Abcdef~ Abcde~ Abcd~ Abc Abcd~ Abcd~ - `24` `40` `15` `38` `10` `46` `5` `50` - - 1 Abcde~ Abcde~ Abcde~ Abcd~ Abcd~ Abcde~ Abcde Abcde~ - `18` `21` `6` `30` `2` `7` `1` `4` - - 1 Abcdef~ Abcde~ Abcd~ Abcdef~ Ab Abcd~ A Abcd - `8` `17` `33` `39` `37` - - 1 Abcde~ Abcdefg~ Abcdefghij~ AbcdefghijA~ Abcdefghij~ + `25` `42` `27` `44` `20` + + 1 AbcdefghijAbcdefghijAbcde Abcde~ Abcde~ Abcde~ Abcd~ + `14` `36` `43` `41` `26` `45` `22` `9` + + 1 Abcde~ Abcde~ Abcde~ Abcde~ Abcd~ Abcde~ Abcd~ Abcd~ + `13` `32` `31` `12` `19` `48` `49` `35` + + 1 Abcde~ Abcde~ Abcde~ Abcd~ Abcd~ Abcde~ Abcde~ Abcd~ + `3` `11` `23` `24` `40` `15` `38` `10` + + 1 Abc Abcde~ Abcde~ Abcde~ Abcde~ Abcd~ Abcde~ Abcd~ + `46` `5` `50` `18` `21` `6` `30` `2` + + 1 Abcdef~ Abcde Abcdef~ Abcde~ Abcd~ Abcd~ Abcd~ Ab + `7` `1` `4` `8` `17` `33` `39` `37` + + 1 Abcde~ A Abcd Abcde~ Abcd~ Abcde~ Abcde~ Abcde~ Code options(width = 42) colonnade(df_str[c(28L, 41L, 12L, 29L, 13L, 43L, 24L, 50L, 48L, 35L, 44L, 21L, @@ -137,12 +137,12 @@ `16` `19` 1 AbcdefghijAbcdef AbcdefghijAbcdefghi - `15` `22` `39` `10` `46` `5` - - 1 Abcde~ Abcde~ Abcdef~ Abcd~ Abcde~ Abcde - `30` `8` `26` `37` - - 1 Abcdefghij~ Abcde~ Abcdefgh~ Abcdefghij~ + `15` `22` `39` `10` + + 1 AbcdefghijAbcde Abcdefg~ Abcdefgh~ Abcd~ + `46` `5` `30` `8` `26` `37` + + 1 Abcdef~ Abcde Abcdef~ Abcd~ Abcd~ Abcde~ Code options(width = 39) colonnade(df_str[c(40L, 17L, 13L, 23L, 22L, 2L, 18L, 3L, 29L, 45L, 14L, 19L, @@ -207,21 +207,21 @@ `41` 1 AbcdefghijAbcdefghijAbcdefghijAbcdef~ - `21` `4` `25` `38` `48` `9` - - 1 Abcde~ Abcd Abcde~ Abcd~ Abcd~ Abcd~ - `24` `26` `39` `20` `36` `42` + `21` `4` `25` + + 1 AbcdefghijAbcdefghijA Abcd Abcdefgh~ + `38` `48` `9` `24` `26` `39` 1 Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ - `16` `6` `11` `7` `12` `1` + `20` `36` `42` `16` `6` `11` - 1 Abcde~ Abcdef Abcd~ Abcd~ Abcd~ A - `46` `15` `5` `8` `50` `32` + 1 Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ + `7` `12` `1` `46` `15` `5` + + 1 Abcde~ Abcd~ A Abcde~ Abcd~ Abcde + `8` `50` `32` `30` `49` `28` - 1 Abcde~ Abcde~ Abcde Abcd~ Abcd~ Abcd~ - `30` `49` `28` - - 1 AbcdefghijA~ AbcdefghijAb~ Abcdefghi~ + 1 Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ Code options(width = 32) colonnade(df_str[c(11L, 36L, 17L, 14L, 31L, 35L, 23L, 13L, 6L, 44L, 45L, 22L, @@ -232,57 +232,36 @@ `11` 1 AbcdefghijA - `36` - - 1 AbcdefghijAbcdefghijAbcdefghi~ - `17` - - 1 AbcdefghijAbcdefg - `14` - - 1 AbcdefghijAbcd - `31` - - 1 AbcdefghijAbcdefghijAbcdefghi~ - `35` - - 1 AbcdefghijAbcdefghijAbcdefghi~ - `23` - - 1 AbcdefghijAbcdefghijAbc - `13` `6` - - 1 AbcdefghijAbc Abcdef - `44` - - 1 AbcdefghijAbcdefghijAbcdefghi~ - `45` - - 1 AbcdefghijAbcdefghijAbcdefghi~ - `22` `21` `18` `33` `10` + `36` `17` `14` `31` + + 1 Abcdefg~ Abcdef~ Abcd~ Abcdef~ + `35` `23` `13` `6` `44` 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ - `43` `2` `46` `34` `3` + `45` `22` `21` `18` `33` - 1 Abcde~ Ab Abcd~ Abcd~ Abc - `19` `1` `38` `9` `37` + 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ + `10` `43` `2` `46` `34` - 1 Abcde~ A Abcd~ Abcd~ Abcd~ - `5` `8` `25` `49` `27` + 1 Abcde~ Abcd~ Ab Abcd~ Abcd~ + `3` `19` `1` `38` `9` - 1 Abcde Abcde~ Abcd~ Abcd~ Abcd~ - `29` `15` `39` `24` `40` + 1 Abc Abcde~ A Abcd~ Abcd~ + `37` `5` `8` `25` `49` + + 1 Abcde~ Abcde Abcd~ Abcd~ Abcd~ + `27` `29` `15` `39` `24` 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ - `48` `26` `47` `42` `41` + `40` `48` `26` `47` `42` 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ - `12` `28` `30` `7` `16` + `41` `12` `28` `30` `7` 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ - `4` `50` `20` `32` - - 1 Abcd Abcdefg~ Abcdef~ Abcdef~ + `16` `4` `50` `20` `32` + + 1 Abcde~ Abcd Abcd~ Abcd~ Abcd~ Code options(width = 35) colonnade(df_str[c(18L, 46L, 11L, 43L, 31L, 47L, 48L, 44L, 50L, 15L, 28L, 33L, @@ -377,18 +356,18 @@ `34` 1 AbcdefghijAbcdefghijAbcdefghijAb~ - `8` `24` `29` `1` `12` - - 1 Abcde~ Abcdef~ Abcde~ A Abcd~ - `2` `20` `17` `35` `5` - - 1 Ab Abcdef~ Abcd~ Abcdef~ Abcde - `19` `30` `7` `26` `42` - - 1 Abcde~ Abcdef~ Abcd~ Abcd~ Abcde~ - `41` `39` `10` - - 1 AbcdefghijAb~ AbcdefghijA~ Abcde~ + `8` `24` `29` + + 1 Abcdefgh Abcdefghij~ AbcdefghijA~ + `1` `12` `2` `20` `17` + + 1 A Abcde~ Ab Abcdef~ Abcde~ + `35` `5` `19` `30` `7` + + 1 Abcdef~ Abcde Abcde~ Abcde~ Abcd~ + `26` `42` `41` `39` `10` + + 1 Abcde~ Abcde~ Abcde~ Abcde~ Abcd~ Code options(width = 32) colonnade(df_str[c(43L, 1L, 3L, 15L, 28L, 12L, 46L, 34L, 31L, 7L, 11L, 4L, 44L, @@ -399,45 +378,36 @@ `43` 1 AbcdefghijAbcdefghijAbcdefghi~ - `1` `3` `15` - - 1 A Abc AbcdefghijAbcde - `28` - - 1 AbcdefghijAbcdefghijAbcdefgh - `12` - - 1 AbcdefghijAb - `46` - - 1 AbcdefghijAbcdefghijAbcdefghi~ - `34` `31` `7` `11` `4` + `1` `3` `15` `28` + + 1 A Abc Abcdefg~ Abcdefgh~ + `12` `46` `34` `31` `7` - 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd - `44` `8` `9` `5` `36` + 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ + `11` `4` `44` `8` `9` - 1 Abcde~ Abcd~ Abcd~ Abcde Abcd~ - `22` `17` `39` `18` `45` + 1 Abcde~ Abcd Abcd~ Abcd~ Abcd~ + `5` `36` `22` `17` `39` + + 1 Abcde Abcde~ Abcd~ Abcd~ Abcd~ + `18` `45` `37` `13` `29` 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ - `37` `13` `29` `6` `30` + `6` `30` `16` `20` `10` - 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ - `16` `20` `10` `19` `26` + 1 Abcdef Abcd~ Abcd~ Abcd~ Abcd~ + `19` `26` `33` `40` `35` 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ - `33` `40` `35` `48` `38` + `48` `38` `25` `2` `47` - 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ - `25` `2` `47` `42` `41` + 1 Abcde~ Abcd~ Abcd~ Ab Abcd~ + `42` `41` `27` `14` `21` - 1 Abcde~ Ab Abcd~ Abcd~ Abcd~ - `27` `14` `21` `24` `50` + 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ + `24` `50` `49` `23` `32` 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ - `49` `23` `32` - - 1 Abcdefghi~ Abcdefgh~ Abcdefgh~ Code options(width = 31) colonnade(df_str[c(37L, 46L, 21L, 3L, 16L, 39L, 34L, 33L, 10L, 17L, 19L, 36L, @@ -448,117 +418,36 @@ `37` 1 AbcdefghijAbcdefghijAbcdefgh~ - `46` - - 1 AbcdefghijAbcdefghijAbcdefgh~ - `21` `3` - - 1 AbcdefghijAbcdefghijA Abc - `16` - - 1 AbcdefghijAbcdef - `39` - - 1 AbcdefghijAbcdefghijAbcdefgh~ - `34` - - 1 AbcdefghijAbcdefghijAbcdefgh~ - `33` - - 1 AbcdefghijAbcdefghijAbcdefgh~ - `10` `17` - - 1 Abcdefghij AbcdefghijAbcdefg - `19` - - 1 AbcdefghijAbcdefghi - `36` - - 1 AbcdefghijAbcdefghijAbcdefgh~ - `45` - - 1 AbcdefghijAbcdefghijAbcdefgh~ - `49` - - 1 AbcdefghijAbcdefghijAbcdefgh~ - `11` - - 1 AbcdefghijA - `50` - - 1 AbcdefghijAbcdefghijAbcdefgh~ - `14` - - 1 AbcdefghijAbcd - `29` - - 1 AbcdefghijAbcdefghijAbcdefghi - `44` - - 1 AbcdefghijAbcdefghijAbcdefgh~ - `13` - - 1 AbcdefghijAbc - `30` - - 1 AbcdefghijAbcdefghijAbcdefgh~ - `38` - - 1 AbcdefghijAbcdefghijAbcdefgh~ - `32` - - 1 AbcdefghijAbcdefghijAbcdefgh~ - `40` - - 1 AbcdefghijAbcdefghijAbcdefgh~ - `42` - - 1 AbcdefghijAbcdefghijAbcdefgh~ - `1` - - 1 A - `31` - - 1 AbcdefghijAbcdefghijAbcdefgh~ - `41` - - 1 AbcdefghijAbcdefghijAbcdefgh~ - `7` - - 1 Abcdefg - `23` - - 1 AbcdefghijAbcdefghijAbc - `35` - - 1 AbcdefghijAbcdefghijAbcdefgh~ - `28` - - 1 AbcdefghijAbcdefghijAbcdefgh - `6` - - 1 Abcdef - `25` - - 1 AbcdefghijAbcdefghijAbcde - `2` `9` `12` - - 1 Ab Abcdefghi AbcdefghijAb - `15` `5` - - 1 AbcdefghijAbcde Abcde - `18` - - 1 AbcdefghijAbcdefgh - `20` - - 1 AbcdefghijAbcdefghij - `27` `43` `8` `47` `4` + `46` `21` `3` `16` + + 1 Abcdefg~ Abcdef~ Abc Abcde~ + `39` `34` `33` `10` `17` + + 1 Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ + `19` `36` `45` `49` `11` + + 1 Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ + `50` `14` `29` `44` `13` + + 1 Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ + `30` `38` `32` `40` `42` + + 1 Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ + `1` `31` `41` `7` `23` - 1 Abcd~ Abcd~ Abcd~ Abcd~ Abcd - `48` `24` `26` `22` - - 1 Abcdef~ Abcdef~ Abcde~ Abcde~ + 1 A Abcd~ Abcd~ Abcd~ Abcd~ + `35` `28` `6` `25` `2` + + 1 Abcd~ Abcd~ Abcd~ Abcd~ Ab + `9` `12` `15` `5` `18` + + 1 Abcd~ Abcd~ Abcd~ Abcde Abcd~ + `20` `27` `43` `8` `47` + + 1 Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ + `4` `48` `24` `26` `22` + + 1 Abcd Abcd~ Abcd~ Abcd~ Abcd~ Code options(width = 58) colonnade(df_str[c(31L, 39L, 40L, 30L, 10L, 21L, 9L, 16L, 46L, 25L, 15L, 24L, @@ -569,33 +458,24 @@ `31` 1 AbcdefghijAbcdefghijAbcdefghijA - `39` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghi - `40` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghij - `30` `10` - - 1 AbcdefghijAbcdefghijAbcdefghij Abcdefghij - `21` `9` `16` - - 1 AbcdefghijAbcdefghijA Abcdefghi AbcdefghijAbcdef - `46` `25` `15` `24` `3` `50` `35` `1` `12` + `39` `40` `30` `10` + + 1 AbcdefghijAbcdef~ AbcdefghijAbcdef~ AbcdefghijAb~ Abcde~ + `21` `9` `16` `46` `25` `15` `24` `3` `50` - 1 Abcde~ Abcde~ Abcde~ Abcd~ Abc Abcd~ Abcd~ A Abcd~ - `34` `48` `4` `29` `23` `37` `36` `28` `43` - - 1 Abcde~ Abcde~ Abcd Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ - `11` `17` `32` `8` `41` `13` `44` `7` `38` + 1 Abcde~ Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ Abc Abcd~ + `35` `1` `12` `34` `48` `4` `29` `23` `37` + + 1 Abcde~ A Abcde~ Abcde~ Abcd~ Abcd Abcd~ Abcd~ Abcd~ + `36` `28` `43` `11` `17` `32` `8` `41` `13` 1 Abcde~ Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ - `26` `33` `20` `19` `2` `18` `49` `27` `47` + `44` `7` `38` `26` `33` `20` `19` `2` `18` + + 1 Abcde~ Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ Ab Abcd~ + `49` `27` `47` `22` `14` `6` `5` `45` `42` - 1 Abcde~ Abcde~ Abcde~ Abcd~ Ab Abcd~ Abcd~ Abcd~ Abcd~ - `22` `14` `6` `5` `45` `42` - - 1 Abcdefgh~ Abcdef~ Abcd~ Abcde AbcdefghijAb~ AbcdefghijA~ + 1 Abcde~ Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ Abcde Abcd~ Abcd~ Code options(width = 57) colonnade(df_str[c(43L, 21L, 41L, 48L, 22L, 25L, 2L, 8L, 1L, 24L, 6L, 39L, 38L, @@ -788,78 +668,36 @@ `43` 1 AbcdefghijAbcdefghijAbcdefghi~ - `23` - - 1 AbcdefghijAbcdefghijAbc - `22` - - 1 AbcdefghijAbcdefghijAb - `11` `6` - - 1 AbcdefghijA Abcdef - `26` - - 1 AbcdefghijAbcdefghijAbcdef - `48` - - 1 AbcdefghijAbcdefghijAbcdefghi~ - `17` `7` - - 1 AbcdefghijAbcdefg Abcdefg - `42` - - 1 AbcdefghijAbcdefghijAbcdefghi~ - `36` - - 1 AbcdefghijAbcdefghijAbcdefghi~ - `21` - - 1 AbcdefghijAbcdefghijA - `35` - - 1 AbcdefghijAbcdefghijAbcdefghi~ - `50` - - 1 AbcdefghijAbcdefghijAbcdefghi~ - `13` - - 1 AbcdefghijAbc - `19` - - 1 AbcdefghijAbcdefghi - `29` - - 1 AbcdefghijAbcdefghijAbcdefghi - `8` `15` `4` - - 1 Abcdefgh AbcdefghijAbcde Abcd - `2` - - 1 Ab - `27` - - 1 AbcdefghijAbcdefghijAbcdefg - `49` - - 1 AbcdefghijAbcdefghijAbcdefghi~ - `47` `30` `31` `25` `28` + `23` `22` `11` `6` + + 1 Abcdefg~ Abcdefg~ Abcde~ Abcd~ + `26` `48` `17` `7` `42` 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ - `46` `12` `32` `39` `24` + `36` `21` `35` `50` `13` 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ - `10` `45` `5` `37` `14` + `19` `29` `8` `15` `4` + + 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd + `2` `27` `49` `47` `30` + + 1 Ab Abcde~ Abcd~ Abcd~ Abcd~ + `31` `25` `28` `46` `12` - 1 Abcde~ Abcd~ Abcde Abcd~ Abcd~ - `40` `20` `41` `44` `33` + 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ + `32` `39` `24` `10` `45` 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ - `18` `38` `3` `1` `34` + `5` `37` `14` `40` `20` + + 1 Abcde Abcde~ Abcd~ Abcd~ Abcd~ + `41` `44` `33` `18` `38` - 1 Abcde~ Abcd~ Abc A Abcd~ - `16` `9` - - 1 AbcdefghijAbcdef Abcdefghi + 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ + `3` `1` `34` `16` `9` + + 1 Abc A Abcde~ Abcd~ Abcd~ Code options(width = 46) colonnade(df_str[c(5L, 24L, 43L, 46L, 35L, 39L, 18L, 26L, 8L, 27L, 2L, 50L, 6L, @@ -1021,18 +859,18 @@ `45` 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbcde - `6` `4` `11` `24` `43` `32` `3` `38` - - 1 Abcdef Abcd Abcde~ Abcde~ Abcd~ Abcd~ Abc Abcd~ - `5` `49` `27` `17` `8` `22` `40` `12` - - 1 Abcde Abcde~ Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ - `15` `1` `28` `31` `29` `13` `48` `34` - - 1 Abcde~ A Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ - `36` `30` `20` `16` `46` - - 1 Abcdefghij~ Abcdefghi~ Abcdef~ Abcde~ AbcdefghijA~ + `6` `4` `11` `24` `43` + + 1 Abcdef Abcd Abcdef~ Abcdefghij~ AbcdefghijAbcdef~ + `32` `3` `38` `5` `49` `27` `17` `8` + + 1 Abcde~ Abc Abcde~ Abcde Abcde~ Abcd~ Abcd~ Abcd~ + `22` `40` `12` `15` `1` `28` `31` `29` + + 1 Abcde~ Abcde~ Abcde~ Abcd~ A Abcd~ Abcd~ Abcd~ + `13` `48` `34` `36` `30` `20` `16` `46` + + 1 Abcde~ Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Code options(width = 35) colonnade(df_str[c(38L, 18L, 23L, 36L, 35L, 20L, 44L, 19L, 13L, 41L, 31L, 7L, @@ -1043,39 +881,36 @@ `38` 1 AbcdefghijAbcdefghijAbcdefghijAb~ - `18` - - 1 AbcdefghijAbcdefgh - `23` `36` `35` `20` `44` - - 1 Abcde~ Abcde~ Abcde~ Abcde~ Abcd~ - `19` `13` `41` `31` `7` - - 1 Abcde~ Abcde~ Abcde~ Abcde~ Abcd~ - `11` `29` `2` `14` `26` + `18` `23` `36` `35` + + 1 Abcdef~ Abcdef~ Abcdefg~ Abcdefg~ + `20` `44` `19` `13` `41` - 1 Abcde~ Abcdef~ Ab Abcd~ Abcde~ - `46` `40` `45` `9` `34` + 1 Abcde~ Abcdef~ Abcd~ Abcd~ Abcde~ + `31` `7` `11` `29` `2` + + 1 Abcdef~ Abcde~ Abcd~ Abcde~ Ab + `14` `26` `46` `40` `45` 1 Abcde~ Abcde~ Abcde~ Abcde~ Abcd~ - `33` `22` `1` `17` `28` - - 1 Abcdef~ Abcde~ A Abcd~ Abcde~ - `10` `21` `30` `47` `49` - - 1 Abcde~ Abcde~ Abcd~ Abcde~ Abcde~ - `6` `12` `4` `25` `32` - - 1 Abcdef Abcde~ Abcd Abcde~ Abcde~ - `15` `43` `24` `48` `3` + `9` `34` `33` `22` `1` + + 1 Abcde~ Abcdef~ Abcde~ Abcd~ A + `17` `28` `10` `21` `30` + + 1 Abcde~ Abcdef~ Abcd~ Abcd~ Abcde~ + `47` `49` `6` `12` `4` + + 1 Abcdef~ Abcdef~ Abcd~ Abcd~ Abcd + `25` `32` `15` `43` `24` - 1 Abcde~ Abcdef~ Abcd~ Abcde~ Abc - `37` `50` `42` `39` `16` - - 1 Abcde~ Abcde~ Abcde~ Abcde~ Abcd~ - `8` `27` `5` - - 1 Abcdef~ AbcdefghijAbcdefgh~ Abcde + 1 Abcde~ Abcdef~ Abcd~ Abcde~ Abcd~ + `48` `3` `37` `50` `42` + + 1 Abcde~ Abc Abcde~ Abcde~ Abcde~ + `39` `16` `8` `27` `5` + + 1 Abcdef~ Abcde~ Abcd~ Abcde~ Abcde Code options(width = 41) colonnade(df_str[c(22L, 9L, 11L, 26L, 19L, 16L, 32L, 25L, 1L, 30L, 31L, 6L, 24L, @@ -1083,79 +918,34 @@ 48L, 34L, 3L, 8L, 4L, 27L, 42L, 44L, 33L, 45L, 18L, 5L, 2L, 13L, 47L, 28L, 17L, 37L, 14L, 41L, 23L)], width = 999) Output - `22` `9` - - 1 AbcdefghijAbcdefghijAb Abcdefghi - `11` `26` - - 1 AbcdefghijA AbcdefghijAbcdefghijAbcdef - `19` `16` - - 1 AbcdefghijAbcdefghi AbcdefghijAbcdef - `32` - - 1 AbcdefghijAbcdefghijAbcdefghijAb - `25` `1` - - 1 AbcdefghijAbcdefghijAbcde A - `30` - - 1 AbcdefghijAbcdefghijAbcdefghij - `31` `6` - - 1 AbcdefghijAbcdefghijAbcdefghijA Abcdef - `24` `10` - - 1 AbcdefghijAbcdefghijAbcd Abcdefghij - `39` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghi - `21` - - 1 AbcdefghijAbcdefghijA - `50` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefgh~ - `7` `29` - - 1 Abcdefg AbcdefghijAbcdefghijAbcdefghi - `12` - - 1 AbcdefghijAb - `46` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefgh~ - `43` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefgh~ - `15` - - 1 AbcdefghijAbcde - `35` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcde - `20` - - 1 AbcdefghijAbcdefghij - `40` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefgh~ - `49` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefgh~ - `38` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefgh - `36` `48` `34` `3` `8` `4` + `22` + + 1 AbcdefghijAbcdefghijAb + `9` + + 1 Abcdefghi + `11` `26` `19` `16` `32` `25` + + 1 Abcde~ Abcde~ Abcde~ Abcd~ Abcde~ Abcd~ + `1` `30` `31` `6` `24` `10` + + 1 A Abcdef~ Abcde~ Abcd~ Abcde~ Abcd~ + `39` `21` `50` `7` `29` `12` - 1 Abcdef~ Abcde~ Abcde~ Abc Abcd~ Abcd - `27` `42` `44` `33` `45` `18` + 1 Abcdef~ Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ + `46` `43` `15` `35` `20` `40` 1 Abcde~ Abcde~ Abcde~ Abcde~ Abcd~ Abcd~ - `5` `2` `13` `47` `28` `17` - - 1 Abcde Ab Abcde~ Abcdef~ Abcde~ Abcd~ - `37` `14` `41` `23` - - 1 Abcdefghij~ Abcdef~ Abcdefghi~ Abcdefg~ + `49` `38` `36` `48` `34` `3` + + 1 Abcde~ Abcde~ Abcde~ Abcde~ Abcd~ Abc + `8` `4` `27` `42` `44` `33` + + 1 Abcde~ Abcd Abcde~ Abcde~ Abcde~ Abcd~ + `45` `18` `5` `2` `13` `47` + + 1 Abcdef~ Abcde~ Abcde Ab Abcd~ Abcde~ + `28` `17` `37` `14` `41` `23` + + 1 Abcde~ Abcde~ Abcde~ Abcd~ Abcde~ Abcd~ diff --git a/tests/testthat/_snaps/multi.md b/tests/testthat/_snaps/multi.md index fbee805b4..79f388049 100644 --- a/tests/testthat/_snaps/multi.md +++ b/tests/testthat/_snaps/multi.md @@ -14,25 +14,25 @@ id width tier offset max_widths 1 1 30 1 30 30 2 2 30 2 30 30 - 3 3 15 3 15 30 - 4 4 15 3 31 30 + 3 3 30 3 30 30 + 4 4 15 3 60 30 Code colonnade_compute_tiered_col_widths_df(rep(30, 4), rep(15, 4), rep(60, 2)) Output id width tier offset max_widths 1 1 30 1 30 30 - 2 2 15 2 15 30 - 3 3 15 2 31 30 - 4 4 15 2 47 30 + 2 2 15 2 28 30 + 3 3 15 2 44 30 + 4 4 15 2 60 30 Code colonnade_compute_tiered_col_widths_df(rep(30, 5), rep(15, 5), rep(60, 3)) Output id width tier offset max_widths 1 1 30 1 30 30 2 2 30 2 30 30 - 3 3 15 3 15 30 - 4 4 15 3 31 30 - 5 5 15 3 47 30 + 3 3 15 3 28 30 + 4 4 15 3 44 30 + 5 5 15 3 60 30 Code colonnade_compute_tiered_col_widths_df(rep(30, 5), rep(15, 5), rep(60, 4)) Output @@ -40,22 +40,22 @@ 1 1 30 1 30 30 2 2 30 2 30 30 3 3 30 3 30 30 - 4 4 15 4 15 30 - 5 5 15 4 31 30 + 4 4 30 4 30 30 + 5 5 15 4 60 30 Code colonnade_compute_tiered_col_widths_df(rep(30, 10), rep(15, 10), rep(60, 5)) Output id width tier offset max_widths 1 1 30 1 30 30 2 2 30 2 30 30 - 3 3 15 3 15 30 - 4 4 15 3 31 30 - 5 5 15 3 47 30 - 6 6 15 4 15 30 - 7 7 15 4 31 30 - 8 8 15 4 47 30 - 9 9 15 5 15 30 - 10 10 15 5 31 30 + 3 3 30 3 30 30 + 4 4 15 3 60 30 + 5 5 15 4 28 30 + 6 6 15 4 44 30 + 7 7 15 4 60 30 + 8 8 15 5 28 30 + 9 9 15 5 44 30 + 10 10 15 5 60 30 # distribute_pillars() From 697f4ddf94475b1c9d137dbc5d45f11e8f5c7e52 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Sun, 25 Jul 2021 17:20:42 +0200 Subject: [PATCH 030/147] More precision --- R/multi.R | 15 +- tests/testthat/_snaps/ctl_colonnade_1.md | 120 ++++-- tests/testthat/_snaps/ctl_colonnade_2.md | 384 ++++++++++++++----- tests/testthat/_snaps/format_multi_fuzz.md | 120 ++++-- tests/testthat/_snaps/format_multi_fuzz_2.md | 384 ++++++++++++++----- 5 files changed, 781 insertions(+), 242 deletions(-) diff --git a/R/multi.R b/R/multi.R index d40ab8074..0f84675c8 100644 --- a/R/multi.R +++ b/R/multi.R @@ -386,19 +386,18 @@ colonnade_compute_tiered_col_widths_df <- function(max_widths, min_widths, tier_ #' This is the "mixed" tier which is refined later on. min_fit_rev <- distribute_pillars_rev(col_df$min_widths, tier_widths) - cut_point <- max(which.max(max_fit$tier == min_fit_rev$tier & max_fit$offset <= min_fit_rev$offset), 0) + cut_point <- which(max_fit$tier == min_fit_rev$tier & max_fit$offset <= min_fit_rev$offset) + if (length(cut_point) == 0) { + cut_point <- which.max(max_fit$tier == min_fit_rev$tier) - 1L + } else { + cut_point <- cut_point[[1]] + } + tier_mix_fit <- min_fit_rev$tier[[cut_point]] max_fit_cut <- max_fit[seq_len(cut_point), ] min_fit_cut <- min_fit_rev[seq2(cut_point + 1L, nrow(min_fit_rev)), ] - #min_fit_cut <- distribute_pillars_offset( - # col_df$min_widths, - # tier_widths, - # widths_offset = cut_point, - # tier_widths_offset = tier_mix_fit - #) - combined_fit <- rbind(max_fit_cut, min_fit_cut) combined_fit$max_widths <- col_df$max_widths diff --git a/tests/testthat/_snaps/ctl_colonnade_1.md b/tests/testthat/_snaps/ctl_colonnade_1.md index 54a58f966..4710c9b04 100644 --- a/tests/testthat/_snaps/ctl_colonnade_1.md +++ b/tests/testthat/_snaps/ctl_colonnade_1.md @@ -161,12 +161,24 @@ `47` 1 AbcdefghijAbcdefghijAbcdefghi~ - `42` `4` `46` `9` - - 1 Abcdefgh~ Abcd Abcdefg~ Abcd~ - `34` `19` `39` `8` `32` - - 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ + `42` + + 1 AbcdefghijAbcdefghijAbcdefghi~ + `4` + + 1 Abcd + `46` + + 1 AbcdefghijAbcdefghijAbcdefghi~ + `9` + + 1 Abcdefghi + `34` + + 1 AbcdefghijAbcdefghijAbcdefghi~ + `19` `39` `8` `32` + + 1 Abcdef~ Abcdefg~ Abcd~ Abcdef~ `36` `12` `29` `5` `15` 1 Abcde~ Abcd~ Abcd~ Abcde Abcd~ @@ -267,18 +279,27 @@ }) Output $body - `27` - - 1 AbcdefghijAbcdefghijAbcdefg - `22` - - 1 AbcdefghijAbcdefghijAb - `9` `23` `16` `19` `25` `31` `44` `1` - - 1 Abcde~ Abcde~ Abcde~ Abcde~ Abcd~ Abcd~ Abcde~ A - `28` `46` `12` `20` `43` `37` `5` `2` - - 1 Abcde~ Abcdef~ Abcd~ Abcd~ Abcde~ Abcde~ Abcde Ab + `27` `22` + + 1 AbcdefghijAbcdefghijAbcdefg AbcdefghijAbcdefghijAb + `9` `23` `16` + + 1 Abcdefghi AbcdefghijAbcdefghijAbc AbcdefghijAbcdef + `19` `25` + + 1 AbcdefghijAbcdefghi AbcdefghijAbcdefghijAbcde + `31` + + 1 AbcdefghijAbcdefghijAbcdefghijA + `44` `1` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbcd A + `28` + + 1 AbcdefghijAbcdefghijAbcdefgh + `46` `12` `20` `43` `37` `5` `2` + + 1 Abcdefgh~ Abcde~ Abcde~ Abcdefg~ Abcdef~ Abcde Ab `18` `41` `26` `33` `11` `49` `24` `35` 1 Abcde~ Abcde~ Abcde~ Abcde~ Abcd~ Abcde~ Abcd~ Abcd~ @@ -619,12 +640,27 @@ `45` 1 AbcdefghijAbcdefghijAbcdefgh~ - `14` `49` `24` `22` - - 1 Abcde~ Abcdefg~ Abcde~ Abcde~ - `31` `42` `18` `16` `47` - - 1 Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ + `14` + + 1 AbcdefghijAbcd + `49` + + 1 AbcdefghijAbcdefghijAbcdefgh~ + `24` + + 1 AbcdefghijAbcdefghijAbcd + `22` + + 1 AbcdefghijAbcdefghijAb + `31` + + 1 AbcdefghijAbcdefghijAbcdefgh~ + `42` + + 1 AbcdefghijAbcdefghijAbcdefgh~ + `18` `16` `47` + + 1 Abcdefgh~ Abcdef~ Abcdefghij~ `25` `4` `37` `8` `26` 1 Abcd~ Abcd Abcd~ Abcd~ Abcd~ @@ -935,12 +971,36 @@ `38` 1 AbcdefghijAbcdefghijAbcdefghijAbcdefgh - `42` `41` `10` `40` `11` `27` `9` - - 1 Abcde~ Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ - `17` `37` `46` `13` `36` `18` `31` - - 1 Abcde~ Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ + `42` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAb + `41` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijA + `10` + + 1 Abcdefghij + `40` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghij + `11` `27` + + 1 AbcdefghijA AbcdefghijAbcdefghijAbcdefg + `9` `17` + + 1 Abcdefghi AbcdefghijAbcdefg + `37` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefg + `46` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbc~ + `13` + + 1 AbcdefghijAbc + `36` `18` `31` + + 1 AbcdefghijAbcdef~ Abcdefghi~ AbcdefghijAbcd~ `20` `39` `12` `44` `33` `50` `34` 1 Abcde~ Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ diff --git a/tests/testthat/_snaps/ctl_colonnade_2.md b/tests/testthat/_snaps/ctl_colonnade_2.md index c862e0454..934f61106 100644 --- a/tests/testthat/_snaps/ctl_colonnade_2.md +++ b/tests/testthat/_snaps/ctl_colonnade_2.md @@ -256,15 +256,36 @@ `11` 1 AbcdefghijA - `36` `17` `14` `31` - - 1 Abcdefg~ Abcdef~ Abcd~ Abcdef~ - `35` `23` `13` `6` `44` - - 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ - `45` `22` `21` `18` `33` - - 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ + `36` + + 1 AbcdefghijAbcdefghijAbcdefghi~ + `17` + + 1 AbcdefghijAbcdefg + `14` + + 1 AbcdefghijAbcd + `31` + + 1 AbcdefghijAbcdefghijAbcdefghi~ + `35` + + 1 AbcdefghijAbcdefghijAbcdefghi~ + `23` + + 1 AbcdefghijAbcdefghijAbc + `13` `6` + + 1 AbcdefghijAbc Abcdef + `44` + + 1 AbcdefghijAbcdefghijAbcdefghi~ + `45` + + 1 AbcdefghijAbcdefghijAbcdefghi~ + `22` `21` `18` `33` + + 1 Abcdef~ Abcdef~ Abcde~ Abcdef~ `10` `43` `2` `46` `34` 1 Abcde~ Abcd~ Ab Abcd~ Abcd~ @@ -416,12 +437,21 @@ `43` 1 AbcdefghijAbcdefghijAbcdefghi~ - `1` `3` `15` `28` - - 1 A Abc Abcdefg~ Abcdefgh~ - `12` `46` `34` `31` `7` - - 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ + `1` `3` `15` + + 1 A Abc AbcdefghijAbcde + `28` + + 1 AbcdefghijAbcdefghijAbcdefgh + `12` + + 1 AbcdefghijAb + `46` + + 1 AbcdefghijAbcdefghijAbcdefghi~ + `34` `31` `7` + + 1 AbcdefghijA~ Abcdefghij~ Abcd~ `11` `4` `44` `8` `9` 1 Abcde~ Abcd Abcd~ Abcd~ Abcd~ @@ -463,33 +493,114 @@ `37` 1 AbcdefghijAbcdefghijAbcdefgh~ - `46` `21` `3` `16` - - 1 Abcdefg~ Abcdef~ Abc Abcde~ - `39` `34` `33` `10` `17` - - 1 Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ - `19` `36` `45` `49` `11` - - 1 Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ - `50` `14` `29` `44` `13` - - 1 Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ - `30` `38` `32` `40` `42` - - 1 Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ - `1` `31` `41` `7` `23` - - 1 A Abcd~ Abcd~ Abcd~ Abcd~ - `35` `28` `6` `25` `2` - - 1 Abcd~ Abcd~ Abcd~ Abcd~ Ab - `9` `12` `15` `5` `18` - - 1 Abcd~ Abcd~ Abcd~ Abcde Abcd~ - `20` `27` `43` `8` `47` - - 1 Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ + `46` + + 1 AbcdefghijAbcdefghijAbcdefgh~ + `21` `3` + + 1 AbcdefghijAbcdefghijA Abc + `16` + + 1 AbcdefghijAbcdef + `39` + + 1 AbcdefghijAbcdefghijAbcdefgh~ + `34` + + 1 AbcdefghijAbcdefghijAbcdefgh~ + `33` + + 1 AbcdefghijAbcdefghijAbcdefgh~ + `10` `17` + + 1 Abcdefghij AbcdefghijAbcdefg + `19` + + 1 AbcdefghijAbcdefghi + `36` + + 1 AbcdefghijAbcdefghijAbcdefgh~ + `45` + + 1 AbcdefghijAbcdefghijAbcdefgh~ + `49` + + 1 AbcdefghijAbcdefghijAbcdefgh~ + `11` + + 1 AbcdefghijA + `50` + + 1 AbcdefghijAbcdefghijAbcdefgh~ + `14` + + 1 AbcdefghijAbcd + `29` + + 1 AbcdefghijAbcdefghijAbcdefghi + `44` + + 1 AbcdefghijAbcdefghijAbcdefgh~ + `13` + + 1 AbcdefghijAbc + `30` + + 1 AbcdefghijAbcdefghijAbcdefgh~ + `38` + + 1 AbcdefghijAbcdefghijAbcdefgh~ + `32` + + 1 AbcdefghijAbcdefghijAbcdefgh~ + `40` + + 1 AbcdefghijAbcdefghijAbcdefgh~ + `42` + + 1 AbcdefghijAbcdefghijAbcdefgh~ + `1` + + 1 A + `31` + + 1 AbcdefghijAbcdefghijAbcdefgh~ + `41` + + 1 AbcdefghijAbcdefghijAbcdefgh~ + `7` + + 1 Abcdefg + `23` + + 1 AbcdefghijAbcdefghijAbc + `35` + + 1 AbcdefghijAbcdefghijAbcdefgh~ + `28` + + 1 AbcdefghijAbcdefghijAbcdefgh + `6` + + 1 Abcdef + `25` + + 1 AbcdefghijAbcdefghijAbcde + `2` `9` `12` + + 1 Ab Abcdefghi AbcdefghijAb + `15` `5` + + 1 AbcdefghijAbcde Abcde + `18` + + 1 AbcdefghijAbcdefgh + `20` + + 1 AbcdefghijAbcdefghij + `27` `43` `8` `47` + + 1 Abcdef~ Abcdef~ Abcde~ Abcde~ `4` `48` `24` `26` `22` 1 Abcd Abcd~ Abcd~ Abcd~ Abcd~ @@ -510,12 +621,21 @@ `31` 1 AbcdefghijAbcdefghijAbcdefghijA - `39` `40` `30` `10` - - 1 AbcdefghijAbcdef~ AbcdefghijAbcdef~ AbcdefghijAb~ Abcde~ - `21` `9` `16` `46` `25` `15` `24` `3` `50` - - 1 Abcde~ Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ Abc Abcd~ + `39` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghi + `40` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghij + `30` `10` + + 1 AbcdefghijAbcdefghijAbcdefghij Abcdefghij + `21` `9` `16` + + 1 AbcdefghijAbcdefghijA Abcdefghi AbcdefghijAbcdef + `46` `25` `15` `24` `3` `50` + + 1 AbcdefghijA~ Abcdefgh~ Abcde~ Abcdef~ Abc AbcdefghijA~ `35` `1` `12` `34` `48` `4` `29` `23` `37` 1 Abcde~ A Abcde~ Abcde~ Abcd~ Abcd Abcd~ Abcd~ Abcd~ @@ -741,21 +861,63 @@ `43` 1 AbcdefghijAbcdefghijAbcdefghi~ - `23` `22` `11` `6` - - 1 Abcdefg~ Abcdefg~ Abcde~ Abcd~ - `26` `48` `17` `7` `42` - - 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ - `36` `21` `35` `50` `13` - - 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ - `19` `29` `8` `15` `4` - - 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd - `2` `27` `49` `47` `30` - - 1 Ab Abcde~ Abcd~ Abcd~ Abcd~ + `23` + + 1 AbcdefghijAbcdefghijAbc + `22` + + 1 AbcdefghijAbcdefghijAb + `11` `6` + + 1 AbcdefghijA Abcdef + `26` + + 1 AbcdefghijAbcdefghijAbcdef + `48` + + 1 AbcdefghijAbcdefghijAbcdefghi~ + `17` `7` + + 1 AbcdefghijAbcdefg Abcdefg + `42` + + 1 AbcdefghijAbcdefghijAbcdefghi~ + `36` + + 1 AbcdefghijAbcdefghijAbcdefghi~ + `21` + + 1 AbcdefghijAbcdefghijA + `35` + + 1 AbcdefghijAbcdefghijAbcdefghi~ + `50` + + 1 AbcdefghijAbcdefghijAbcdefghi~ + `13` + + 1 AbcdefghijAbc + `19` + + 1 AbcdefghijAbcdefghi + `29` + + 1 AbcdefghijAbcdefghijAbcdefghi + `8` `15` `4` + + 1 Abcdefgh AbcdefghijAbcde Abcd + `2` + + 1 Ab + `27` + + 1 AbcdefghijAbcdefghijAbcdefg + `49` + + 1 AbcdefghijAbcdefghijAbcdefghi~ + `47` `30` + + 1 AbcdefghijAbcd~ AbcdefghijAbc~ `31` `25` `28` `46` `12` 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ @@ -975,9 +1137,12 @@ `38` 1 AbcdefghijAbcdefghijAbcdefghijAb~ - `18` `23` `36` `35` - - 1 Abcdef~ Abcdef~ Abcdefg~ Abcdefg~ + `18` + + 1 AbcdefghijAbcdefgh + `23` `36` `35` + + 1 Abcdefgh~ Abcdefghij~ Abcdefghij~ `20` `44` `19` `13` `41` 1 Abcde~ Abcdef~ Abcd~ Abcd~ Abcde~ @@ -1019,27 +1184,72 @@ }) Output $body - `22` - - 1 AbcdefghijAbcdefghijAb - `9` - - 1 Abcdefghi - `11` `26` `19` `16` `32` `25` - - 1 Abcde~ Abcde~ Abcde~ Abcd~ Abcde~ Abcd~ - `1` `30` `31` `6` `24` `10` - - 1 A Abcdef~ Abcde~ Abcd~ Abcde~ Abcd~ - `39` `21` `50` `7` `29` `12` - - 1 Abcdef~ Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ - `46` `43` `15` `35` `20` `40` - - 1 Abcde~ Abcde~ Abcde~ Abcde~ Abcd~ Abcd~ - `49` `38` `36` `48` `34` `3` - - 1 Abcde~ Abcde~ Abcde~ Abcde~ Abcd~ Abc + `22` `9` + + 1 AbcdefghijAbcdefghijAb Abcdefghi + `11` `26` + + 1 AbcdefghijA AbcdefghijAbcdefghijAbcdef + `19` `16` + + 1 AbcdefghijAbcdefghi AbcdefghijAbcdef + `32` + + 1 AbcdefghijAbcdefghijAbcdefghijAb + `25` `1` + + 1 AbcdefghijAbcdefghijAbcde A + `30` + + 1 AbcdefghijAbcdefghijAbcdefghij + `31` `6` + + 1 AbcdefghijAbcdefghijAbcdefghijA Abcdef + `24` `10` + + 1 AbcdefghijAbcdefghijAbcd Abcdefghij + `39` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghi + `21` + + 1 AbcdefghijAbcdefghijA + `50` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefgh~ + `7` `29` + + 1 Abcdefg AbcdefghijAbcdefghijAbcdefghi + `12` + + 1 AbcdefghijAb + `46` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefgh~ + `43` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefgh~ + `15` + + 1 AbcdefghijAbcde + `35` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcde + `20` + + 1 AbcdefghijAbcdefghij + `40` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefgh~ + `49` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefgh~ + `38` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefgh + `36` `48` `34` `3` + + 1 Abcdefghij~ Abcdefghij~ Abcdefgh~ Abc `8` `4` `27` `42` `44` `33` 1 Abcde~ Abcd Abcde~ Abcde~ Abcde~ Abcd~ diff --git a/tests/testthat/_snaps/format_multi_fuzz.md b/tests/testthat/_snaps/format_multi_fuzz.md index 909b2daea..a98694e4f 100644 --- a/tests/testthat/_snaps/format_multi_fuzz.md +++ b/tests/testthat/_snaps/format_multi_fuzz.md @@ -144,12 +144,24 @@ `47` 1 AbcdefghijAbcdefghijAbcdefghi~ - `42` `4` `46` `9` - - 1 Abcdefgh~ Abcd Abcdefg~ Abcd~ - `34` `19` `39` `8` `32` - - 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ + `42` + + 1 AbcdefghijAbcdefghijAbcdefghi~ + `4` + + 1 Abcd + `46` + + 1 AbcdefghijAbcdefghijAbcdefghi~ + `9` + + 1 Abcdefghi + `34` + + 1 AbcdefghijAbcdefghijAbcdefghi~ + `19` `39` `8` `32` + + 1 Abcdef~ Abcdefg~ Abcd~ Abcdef~ `36` `12` `29` `5` `15` 1 Abcde~ Abcd~ Abcd~ Abcde Abcd~ @@ -236,18 +248,27 @@ 30L, 7L, 34L, 3L, 32L, 42L, 10L, 45L, 38L, 39L, 48L, 14L, 6L, 17L, 36L, 50L, 40L, 13L, 8L, 21L, 15L, 29L)], width = 552) Output - `27` - - 1 AbcdefghijAbcdefghijAbcdefg - `22` - - 1 AbcdefghijAbcdefghijAb - `9` `23` `16` `19` `25` `31` `44` `1` - - 1 Abcde~ Abcde~ Abcde~ Abcde~ Abcd~ Abcd~ Abcde~ A - `28` `46` `12` `20` `43` `37` `5` `2` - - 1 Abcde~ Abcdef~ Abcd~ Abcd~ Abcde~ Abcde~ Abcde Ab + `27` `22` + + 1 AbcdefghijAbcdefghijAbcdefg AbcdefghijAbcdefghijAb + `9` `23` `16` + + 1 Abcdefghi AbcdefghijAbcdefghijAbc AbcdefghijAbcdef + `19` `25` + + 1 AbcdefghijAbcdefghi AbcdefghijAbcdefghijAbcde + `31` + + 1 AbcdefghijAbcdefghijAbcdefghijA + `44` `1` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbcd A + `28` + + 1 AbcdefghijAbcdefghijAbcdefgh + `46` `12` `20` `43` `37` `5` `2` + + 1 Abcdefgh~ Abcde~ Abcde~ Abcdefg~ Abcdef~ Abcde Ab `18` `41` `26` `33` `11` `49` `24` `35` 1 Abcde~ Abcde~ Abcde~ Abcde~ Abcd~ Abcde~ Abcd~ Abcd~ @@ -553,12 +574,27 @@ `45` 1 AbcdefghijAbcdefghijAbcdefgh~ - `14` `49` `24` `22` - - 1 Abcde~ Abcdefg~ Abcde~ Abcde~ - `31` `42` `18` `16` `47` - - 1 Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ + `14` + + 1 AbcdefghijAbcd + `49` + + 1 AbcdefghijAbcdefghijAbcdefgh~ + `24` + + 1 AbcdefghijAbcdefghijAbcd + `22` + + 1 AbcdefghijAbcdefghijAb + `31` + + 1 AbcdefghijAbcdefghijAbcdefgh~ + `42` + + 1 AbcdefghijAbcdefghijAbcdefgh~ + `18` `16` `47` + + 1 Abcdefgh~ Abcdef~ Abcdefghij~ `25` `4` `37` `8` `26` 1 Abcd~ Abcd Abcd~ Abcd~ Abcd~ @@ -834,12 +870,36 @@ `38` 1 AbcdefghijAbcdefghijAbcdefghijAbcdefgh - `42` `41` `10` `40` `11` `27` `9` - - 1 Abcde~ Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ - `17` `37` `46` `13` `36` `18` `31` - - 1 Abcde~ Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ + `42` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAb + `41` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijA + `10` + + 1 Abcdefghij + `40` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghij + `11` `27` + + 1 AbcdefghijA AbcdefghijAbcdefghijAbcdefg + `9` `17` + + 1 Abcdefghi AbcdefghijAbcdefg + `37` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefg + `46` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbc~ + `13` + + 1 AbcdefghijAbc + `36` `18` `31` + + 1 AbcdefghijAbcdef~ Abcdefghi~ AbcdefghijAbcd~ `20` `39` `12` `44` `33` `50` `34` 1 Abcde~ Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ diff --git a/tests/testthat/_snaps/format_multi_fuzz_2.md b/tests/testthat/_snaps/format_multi_fuzz_2.md index a8811444b..859368a8b 100644 --- a/tests/testthat/_snaps/format_multi_fuzz_2.md +++ b/tests/testthat/_snaps/format_multi_fuzz_2.md @@ -232,15 +232,36 @@ `11` 1 AbcdefghijA - `36` `17` `14` `31` - - 1 Abcdefg~ Abcdef~ Abcd~ Abcdef~ - `35` `23` `13` `6` `44` - - 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ - `45` `22` `21` `18` `33` - - 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ + `36` + + 1 AbcdefghijAbcdefghijAbcdefghi~ + `17` + + 1 AbcdefghijAbcdefg + `14` + + 1 AbcdefghijAbcd + `31` + + 1 AbcdefghijAbcdefghijAbcdefghi~ + `35` + + 1 AbcdefghijAbcdefghijAbcdefghi~ + `23` + + 1 AbcdefghijAbcdefghijAbc + `13` `6` + + 1 AbcdefghijAbc Abcdef + `44` + + 1 AbcdefghijAbcdefghijAbcdefghi~ + `45` + + 1 AbcdefghijAbcdefghijAbcdefghi~ + `22` `21` `18` `33` + + 1 Abcdef~ Abcdef~ Abcde~ Abcdef~ `10` `43` `2` `46` `34` 1 Abcde~ Abcd~ Ab Abcd~ Abcd~ @@ -378,12 +399,21 @@ `43` 1 AbcdefghijAbcdefghijAbcdefghi~ - `1` `3` `15` `28` - - 1 A Abc Abcdefg~ Abcdefgh~ - `12` `46` `34` `31` `7` - - 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ + `1` `3` `15` + + 1 A Abc AbcdefghijAbcde + `28` + + 1 AbcdefghijAbcdefghijAbcdefgh + `12` + + 1 AbcdefghijAb + `46` + + 1 AbcdefghijAbcdefghijAbcdefghi~ + `34` `31` `7` + + 1 AbcdefghijA~ Abcdefghij~ Abcd~ `11` `4` `44` `8` `9` 1 Abcde~ Abcd Abcd~ Abcd~ Abcd~ @@ -418,33 +448,114 @@ `37` 1 AbcdefghijAbcdefghijAbcdefgh~ - `46` `21` `3` `16` - - 1 Abcdefg~ Abcdef~ Abc Abcde~ - `39` `34` `33` `10` `17` - - 1 Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ - `19` `36` `45` `49` `11` - - 1 Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ - `50` `14` `29` `44` `13` - - 1 Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ - `30` `38` `32` `40` `42` - - 1 Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ - `1` `31` `41` `7` `23` - - 1 A Abcd~ Abcd~ Abcd~ Abcd~ - `35` `28` `6` `25` `2` - - 1 Abcd~ Abcd~ Abcd~ Abcd~ Ab - `9` `12` `15` `5` `18` - - 1 Abcd~ Abcd~ Abcd~ Abcde Abcd~ - `20` `27` `43` `8` `47` - - 1 Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ + `46` + + 1 AbcdefghijAbcdefghijAbcdefgh~ + `21` `3` + + 1 AbcdefghijAbcdefghijA Abc + `16` + + 1 AbcdefghijAbcdef + `39` + + 1 AbcdefghijAbcdefghijAbcdefgh~ + `34` + + 1 AbcdefghijAbcdefghijAbcdefgh~ + `33` + + 1 AbcdefghijAbcdefghijAbcdefgh~ + `10` `17` + + 1 Abcdefghij AbcdefghijAbcdefg + `19` + + 1 AbcdefghijAbcdefghi + `36` + + 1 AbcdefghijAbcdefghijAbcdefgh~ + `45` + + 1 AbcdefghijAbcdefghijAbcdefgh~ + `49` + + 1 AbcdefghijAbcdefghijAbcdefgh~ + `11` + + 1 AbcdefghijA + `50` + + 1 AbcdefghijAbcdefghijAbcdefgh~ + `14` + + 1 AbcdefghijAbcd + `29` + + 1 AbcdefghijAbcdefghijAbcdefghi + `44` + + 1 AbcdefghijAbcdefghijAbcdefgh~ + `13` + + 1 AbcdefghijAbc + `30` + + 1 AbcdefghijAbcdefghijAbcdefgh~ + `38` + + 1 AbcdefghijAbcdefghijAbcdefgh~ + `32` + + 1 AbcdefghijAbcdefghijAbcdefgh~ + `40` + + 1 AbcdefghijAbcdefghijAbcdefgh~ + `42` + + 1 AbcdefghijAbcdefghijAbcdefgh~ + `1` + + 1 A + `31` + + 1 AbcdefghijAbcdefghijAbcdefgh~ + `41` + + 1 AbcdefghijAbcdefghijAbcdefgh~ + `7` + + 1 Abcdefg + `23` + + 1 AbcdefghijAbcdefghijAbc + `35` + + 1 AbcdefghijAbcdefghijAbcdefgh~ + `28` + + 1 AbcdefghijAbcdefghijAbcdefgh + `6` + + 1 Abcdef + `25` + + 1 AbcdefghijAbcdefghijAbcde + `2` `9` `12` + + 1 Ab Abcdefghi AbcdefghijAb + `15` `5` + + 1 AbcdefghijAbcde Abcde + `18` + + 1 AbcdefghijAbcdefgh + `20` + + 1 AbcdefghijAbcdefghij + `27` `43` `8` `47` + + 1 Abcdef~ Abcdef~ Abcde~ Abcde~ `4` `48` `24` `26` `22` 1 Abcd Abcd~ Abcd~ Abcd~ Abcd~ @@ -458,12 +569,21 @@ `31` 1 AbcdefghijAbcdefghijAbcdefghijA - `39` `40` `30` `10` - - 1 AbcdefghijAbcdef~ AbcdefghijAbcdef~ AbcdefghijAb~ Abcde~ - `21` `9` `16` `46` `25` `15` `24` `3` `50` - - 1 Abcde~ Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ Abc Abcd~ + `39` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghi + `40` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghij + `30` `10` + + 1 AbcdefghijAbcdefghijAbcdefghij Abcdefghij + `21` `9` `16` + + 1 AbcdefghijAbcdefghijA Abcdefghi AbcdefghijAbcdef + `46` `25` `15` `24` `3` `50` + + 1 AbcdefghijA~ Abcdefgh~ Abcde~ Abcdef~ Abc AbcdefghijA~ `35` `1` `12` `34` `48` `4` `29` `23` `37` 1 Abcde~ A Abcde~ Abcde~ Abcd~ Abcd Abcd~ Abcd~ Abcd~ @@ -668,21 +788,63 @@ `43` 1 AbcdefghijAbcdefghijAbcdefghi~ - `23` `22` `11` `6` - - 1 Abcdefg~ Abcdefg~ Abcde~ Abcd~ - `26` `48` `17` `7` `42` - - 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ - `36` `21` `35` `50` `13` - - 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ - `19` `29` `8` `15` `4` - - 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd - `2` `27` `49` `47` `30` - - 1 Ab Abcde~ Abcd~ Abcd~ Abcd~ + `23` + + 1 AbcdefghijAbcdefghijAbc + `22` + + 1 AbcdefghijAbcdefghijAb + `11` `6` + + 1 AbcdefghijA Abcdef + `26` + + 1 AbcdefghijAbcdefghijAbcdef + `48` + + 1 AbcdefghijAbcdefghijAbcdefghi~ + `17` `7` + + 1 AbcdefghijAbcdefg Abcdefg + `42` + + 1 AbcdefghijAbcdefghijAbcdefghi~ + `36` + + 1 AbcdefghijAbcdefghijAbcdefghi~ + `21` + + 1 AbcdefghijAbcdefghijA + `35` + + 1 AbcdefghijAbcdefghijAbcdefghi~ + `50` + + 1 AbcdefghijAbcdefghijAbcdefghi~ + `13` + + 1 AbcdefghijAbc + `19` + + 1 AbcdefghijAbcdefghi + `29` + + 1 AbcdefghijAbcdefghijAbcdefghi + `8` `15` `4` + + 1 Abcdefgh AbcdefghijAbcde Abcd + `2` + + 1 Ab + `27` + + 1 AbcdefghijAbcdefghijAbcdefg + `49` + + 1 AbcdefghijAbcdefghijAbcdefghi~ + `47` `30` + + 1 AbcdefghijAbcd~ AbcdefghijAbc~ `31` `25` `28` `46` `12` 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ @@ -881,9 +1043,12 @@ `38` 1 AbcdefghijAbcdefghijAbcdefghijAb~ - `18` `23` `36` `35` - - 1 Abcdef~ Abcdef~ Abcdefg~ Abcdefg~ + `18` + + 1 AbcdefghijAbcdefgh + `23` `36` `35` + + 1 Abcdefgh~ Abcdefghij~ Abcdefghij~ `20` `44` `19` `13` `41` 1 Abcde~ Abcdef~ Abcd~ Abcd~ Abcde~ @@ -918,27 +1083,72 @@ 48L, 34L, 3L, 8L, 4L, 27L, 42L, 44L, 33L, 45L, 18L, 5L, 2L, 13L, 47L, 28L, 17L, 37L, 14L, 41L, 23L)], width = 999) Output - `22` - - 1 AbcdefghijAbcdefghijAb - `9` - - 1 Abcdefghi - `11` `26` `19` `16` `32` `25` - - 1 Abcde~ Abcde~ Abcde~ Abcd~ Abcde~ Abcd~ - `1` `30` `31` `6` `24` `10` - - 1 A Abcdef~ Abcde~ Abcd~ Abcde~ Abcd~ - `39` `21` `50` `7` `29` `12` - - 1 Abcdef~ Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ - `46` `43` `15` `35` `20` `40` - - 1 Abcde~ Abcde~ Abcde~ Abcde~ Abcd~ Abcd~ - `49` `38` `36` `48` `34` `3` - - 1 Abcde~ Abcde~ Abcde~ Abcde~ Abcd~ Abc + `22` `9` + + 1 AbcdefghijAbcdefghijAb Abcdefghi + `11` `26` + + 1 AbcdefghijA AbcdefghijAbcdefghijAbcdef + `19` `16` + + 1 AbcdefghijAbcdefghi AbcdefghijAbcdef + `32` + + 1 AbcdefghijAbcdefghijAbcdefghijAb + `25` `1` + + 1 AbcdefghijAbcdefghijAbcde A + `30` + + 1 AbcdefghijAbcdefghijAbcdefghij + `31` `6` + + 1 AbcdefghijAbcdefghijAbcdefghijA Abcdef + `24` `10` + + 1 AbcdefghijAbcdefghijAbcd Abcdefghij + `39` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghi + `21` + + 1 AbcdefghijAbcdefghijA + `50` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefgh~ + `7` `29` + + 1 Abcdefg AbcdefghijAbcdefghijAbcdefghi + `12` + + 1 AbcdefghijAb + `46` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefgh~ + `43` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefgh~ + `15` + + 1 AbcdefghijAbcde + `35` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcde + `20` + + 1 AbcdefghijAbcdefghij + `40` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefgh~ + `49` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefgh~ + `38` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefgh + `36` `48` `34` `3` + + 1 Abcdefghij~ Abcdefghij~ Abcdefgh~ Abc `8` `4` `27` `42` `44` `33` 1 Abcde~ Abcd Abcde~ Abcde~ Abcde~ Abcd~ From 949b95d0081a7c930c01c970b613830db27afac8 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Sun, 25 Jul 2021 17:39:39 +0200 Subject: [PATCH 031/147] A bit more precise, mistakes again --- R/multi.R | 10 +++--- tests/testthat/_snaps/ctl_colonnade_1.md | 36 ++++++++++---------- tests/testthat/_snaps/ctl_colonnade_2.md | 6 ++-- tests/testthat/_snaps/format_multi_fuzz.md | 36 ++++++++++---------- tests/testthat/_snaps/format_multi_fuzz_2.md | 6 ++-- 5 files changed, 48 insertions(+), 46 deletions(-) diff --git a/R/multi.R b/R/multi.R index 0f84675c8..569c6e544 100644 --- a/R/multi.R +++ b/R/multi.R @@ -386,11 +386,13 @@ colonnade_compute_tiered_col_widths_df <- function(max_widths, min_widths, tier_ #' This is the "mixed" tier which is refined later on. min_fit_rev <- distribute_pillars_rev(col_df$min_widths, tier_widths) - cut_point <- which(max_fit$tier == min_fit_rev$tier & max_fit$offset <= min_fit_rev$offset) - if (length(cut_point) == 0) { - cut_point <- which.max(max_fit$tier == min_fit_rev$tier) - 1L + cut_point_tier <- max_fit$tier[max(which(max_fit$tier == min_fit_rev$tier))] + cut_point_candidates <- which(max_fit$tier == cut_point_tier) + cut_point_candidate_idx <- which(max_fit$offset[cut_point_candidates] <= min_fit_rev$offset[cut_point_candidates]) + if (length(cut_point_candidate_idx) > 0) { + cut_point <- cut_point_candidates[max(cut_point_candidate_idx)] } else { - cut_point <- cut_point[[1]] + cut_point <- cut_point_candidates[[1]] - 1L } tier_mix_fit <- min_fit_rev$tier[[cut_point]] diff --git a/tests/testthat/_snaps/ctl_colonnade_1.md b/tests/testthat/_snaps/ctl_colonnade_1.md index 4710c9b04..45cbfe5f4 100644 --- a/tests/testthat/_snaps/ctl_colonnade_1.md +++ b/tests/testthat/_snaps/ctl_colonnade_1.md @@ -380,12 +380,12 @@ `23` 1 AbcdefghijAbcdefghijAbc - `41` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijA - `5` `1` `14` `46` `30` `31` `44` `4` - - 1 Abcde A Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd + `41` `5` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijA Abcde + `1` `14` `46` `30` `31` `44` `4` + + 1 A Abcde~ Abcdef~ Abcde~ Abcde~ Abcde~ Abcd `7` `40` `43` `12` `29` `8` `36` `45` 1 Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ @@ -874,12 +874,12 @@ `16` `24` 1 AbcdefghijAbcdef AbcdefghijAbcdefghijAbcd - `4` - - 1 Abcd - `15` `47` `8` `11` `14` `50` `17` - - 1 Abcde~ Abcdef~ Abcd~ Abcd~ Abcd~ Abcde~ Abcd~ + `4` `15` + + 1 Abcd AbcdefghijAbcde + `47` `8` `11` `14` `50` `17` + + 1 Abcdefgh~ Abcde~ Abcde~ Abcd~ Abcdefg~ Abcde~ `2` `44` `30` `36` `45` `25` `38` 1 Ab Abcde~ Abcde~ Abcde~ Abcde~ Abcd~ Abcd~ @@ -939,12 +939,12 @@ `48` 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbcdefgh - `37` `36` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefg AbcdefghijAbcd~ - `5` `43` `11` `14` `13` `39` `16` `12` `4` - - 1 Abcde Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd + `37` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefg + `36` `5` `43` `11` `14` `13` `39` `16` `12` `4` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdef Abcde Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd `18` `42` `3` `10` `28` `40` `24` `29` `17` 1 Abcd~ Abcd~ Abc Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ diff --git a/tests/testthat/_snaps/ctl_colonnade_2.md b/tests/testthat/_snaps/ctl_colonnade_2.md index 934f61106..f0c03a8fa 100644 --- a/tests/testthat/_snaps/ctl_colonnade_2.md +++ b/tests/testthat/_snaps/ctl_colonnade_2.md @@ -1108,9 +1108,9 @@ `45` 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbcde - `6` `4` `11` `24` `43` - - 1 Abcdef Abcd Abcdef~ Abcdefghij~ AbcdefghijAbcdef~ + `6` `4` `11` `24` `43` + + 1 Abcdef Abcd AbcdefghijA Abcdefghi~ AbcdefghijAbc~ `32` `3` `38` `5` `49` `27` `17` `8` 1 Abcde~ Abc Abcde~ Abcde Abcde~ Abcd~ Abcd~ Abcd~ diff --git a/tests/testthat/_snaps/format_multi_fuzz.md b/tests/testthat/_snaps/format_multi_fuzz.md index a98694e4f..464e0f8a0 100644 --- a/tests/testthat/_snaps/format_multi_fuzz.md +++ b/tests/testthat/_snaps/format_multi_fuzz.md @@ -342,12 +342,12 @@ `23` 1 AbcdefghijAbcdefghijAbc - `41` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijA - `5` `1` `14` `46` `30` `31` `44` `4` - - 1 Abcde A Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd + `41` `5` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijA Abcde + `1` `14` `46` `30` `31` `44` `4` + + 1 A Abcde~ Abcdef~ Abcde~ Abcde~ Abcde~ Abcd `7` `40` `43` `12` `29` `8` `36` `45` 1 Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ @@ -787,12 +787,12 @@ `16` `24` 1 AbcdefghijAbcdef AbcdefghijAbcdefghijAbcd - `4` - - 1 Abcd - `15` `47` `8` `11` `14` `50` `17` - - 1 Abcde~ Abcdef~ Abcd~ Abcd~ Abcd~ Abcde~ Abcd~ + `4` `15` + + 1 Abcd AbcdefghijAbcde + `47` `8` `11` `14` `50` `17` + + 1 Abcdefgh~ Abcde~ Abcde~ Abcd~ Abcdefg~ Abcde~ `2` `44` `30` `36` `45` `25` `38` 1 Ab Abcde~ Abcde~ Abcde~ Abcde~ Abcd~ Abcd~ @@ -845,12 +845,12 @@ `48` 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbcdefgh - `37` `36` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefg AbcdefghijAbcd~ - `5` `43` `11` `14` `13` `39` `16` `12` `4` - - 1 Abcde Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd + `37` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefg + `36` `5` `43` `11` `14` `13` `39` `16` `12` `4` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdef Abcde Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd `18` `42` `3` `10` `28` `40` `24` `29` `17` 1 Abcd~ Abcd~ Abc Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ diff --git a/tests/testthat/_snaps/format_multi_fuzz_2.md b/tests/testthat/_snaps/format_multi_fuzz_2.md index 859368a8b..13aa139d9 100644 --- a/tests/testthat/_snaps/format_multi_fuzz_2.md +++ b/tests/testthat/_snaps/format_multi_fuzz_2.md @@ -1021,9 +1021,9 @@ `45` 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbcde - `6` `4` `11` `24` `43` - - 1 Abcdef Abcd Abcdef~ Abcdefghij~ AbcdefghijAbcdef~ + `6` `4` `11` `24` `43` + + 1 Abcdef Abcd AbcdefghijA Abcdefghi~ AbcdefghijAbc~ `32` `3` `38` `5` `49` `27` `17` `8` 1 Abcde~ Abc Abcde~ Abcde Abcde~ Abcd~ Abcd~ Abcd~ From 75af0da0f4f7026ca56225f2ac77d639e9a36f48 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Sun, 25 Jul 2021 17:41:10 +0200 Subject: [PATCH 032/147] Finally? --- R/multi.R | 2 +- tests/testthat/_snaps/ctl_colonnade_1.md | 36 +++++++++++----------- tests/testthat/_snaps/format_multi_fuzz.md | 36 +++++++++++----------- 3 files changed, 37 insertions(+), 37 deletions(-) diff --git a/R/multi.R b/R/multi.R index 569c6e544..29fcf6713 100644 --- a/R/multi.R +++ b/R/multi.R @@ -386,7 +386,7 @@ colonnade_compute_tiered_col_widths_df <- function(max_widths, min_widths, tier_ #' This is the "mixed" tier which is refined later on. min_fit_rev <- distribute_pillars_rev(col_df$min_widths, tier_widths) - cut_point_tier <- max_fit$tier[max(which(max_fit$tier == min_fit_rev$tier))] + cut_point_tier <- max_fit$tier[min(which(max_fit$tier == min_fit_rev$tier))] cut_point_candidates <- which(max_fit$tier == cut_point_tier) cut_point_candidate_idx <- which(max_fit$offset[cut_point_candidates] <= min_fit_rev$offset[cut_point_candidates]) if (length(cut_point_candidate_idx) > 0) { diff --git a/tests/testthat/_snaps/ctl_colonnade_1.md b/tests/testthat/_snaps/ctl_colonnade_1.md index 45cbfe5f4..4710c9b04 100644 --- a/tests/testthat/_snaps/ctl_colonnade_1.md +++ b/tests/testthat/_snaps/ctl_colonnade_1.md @@ -380,12 +380,12 @@ `23` 1 AbcdefghijAbcdefghijAbc - `41` `5` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijA Abcde - `1` `14` `46` `30` `31` `44` `4` - - 1 A Abcde~ Abcdef~ Abcde~ Abcde~ Abcde~ Abcd + `41` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijA + `5` `1` `14` `46` `30` `31` `44` `4` + + 1 Abcde A Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd `7` `40` `43` `12` `29` `8` `36` `45` 1 Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ @@ -874,12 +874,12 @@ `16` `24` 1 AbcdefghijAbcdef AbcdefghijAbcdefghijAbcd - `4` `15` - - 1 Abcd AbcdefghijAbcde - `47` `8` `11` `14` `50` `17` - - 1 Abcdefgh~ Abcde~ Abcde~ Abcd~ Abcdefg~ Abcde~ + `4` + + 1 Abcd + `15` `47` `8` `11` `14` `50` `17` + + 1 Abcde~ Abcdef~ Abcd~ Abcd~ Abcd~ Abcde~ Abcd~ `2` `44` `30` `36` `45` `25` `38` 1 Ab Abcde~ Abcde~ Abcde~ Abcde~ Abcd~ Abcd~ @@ -939,12 +939,12 @@ `48` 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbcdefgh - `37` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefg - `36` `5` `43` `11` `14` `13` `39` `16` `12` `4` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdef Abcde Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd + `37` `36` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefg AbcdefghijAbcd~ + `5` `43` `11` `14` `13` `39` `16` `12` `4` + + 1 Abcde Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd `18` `42` `3` `10` `28` `40` `24` `29` `17` 1 Abcd~ Abcd~ Abc Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ diff --git a/tests/testthat/_snaps/format_multi_fuzz.md b/tests/testthat/_snaps/format_multi_fuzz.md index 464e0f8a0..a98694e4f 100644 --- a/tests/testthat/_snaps/format_multi_fuzz.md +++ b/tests/testthat/_snaps/format_multi_fuzz.md @@ -342,12 +342,12 @@ `23` 1 AbcdefghijAbcdefghijAbc - `41` `5` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijA Abcde - `1` `14` `46` `30` `31` `44` `4` - - 1 A Abcde~ Abcdef~ Abcde~ Abcde~ Abcde~ Abcd + `41` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijA + `5` `1` `14` `46` `30` `31` `44` `4` + + 1 Abcde A Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd `7` `40` `43` `12` `29` `8` `36` `45` 1 Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ @@ -787,12 +787,12 @@ `16` `24` 1 AbcdefghijAbcdef AbcdefghijAbcdefghijAbcd - `4` `15` - - 1 Abcd AbcdefghijAbcde - `47` `8` `11` `14` `50` `17` - - 1 Abcdefgh~ Abcde~ Abcde~ Abcd~ Abcdefg~ Abcde~ + `4` + + 1 Abcd + `15` `47` `8` `11` `14` `50` `17` + + 1 Abcde~ Abcdef~ Abcd~ Abcd~ Abcd~ Abcde~ Abcd~ `2` `44` `30` `36` `45` `25` `38` 1 Ab Abcde~ Abcde~ Abcde~ Abcde~ Abcd~ Abcd~ @@ -845,12 +845,12 @@ `48` 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbcdefgh - `37` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefg - `36` `5` `43` `11` `14` `13` `39` `16` `12` `4` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdef Abcde Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd + `37` `36` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefg AbcdefghijAbcd~ + `5` `43` `11` `14` `13` `39` `16` `12` `4` + + 1 Abcde Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd `18` `42` `3` `10` `28` `40` `24` `29` `17` 1 Abcd~ Abcd~ Abc Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ From af74a34925caeddfe3a2c8267012cedaf2c68668 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Sun, 25 Jul 2021 17:45:37 +0200 Subject: [PATCH 033/147] Remove dead --- R/multi.R | 2 -- 1 file changed, 2 deletions(-) diff --git a/R/multi.R b/R/multi.R index 29fcf6713..5c98ba150 100644 --- a/R/multi.R +++ b/R/multi.R @@ -395,8 +395,6 @@ colonnade_compute_tiered_col_widths_df <- function(max_widths, min_widths, tier_ cut_point <- cut_point_candidates[[1]] - 1L } - tier_mix_fit <- min_fit_rev$tier[[cut_point]] - max_fit_cut <- max_fit[seq_len(cut_point), ] min_fit_cut <- min_fit_rev[seq2(cut_point + 1L, nrow(min_fit_rev)), ] From f2155957a06565766dab6ece190640e062f4c2ed Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Sun, 25 Jul 2021 17:56:35 +0200 Subject: [PATCH 034/147] Comments --- R/multi.R | 22 +++++++++++++++++----- 1 file changed, 17 insertions(+), 5 deletions(-) diff --git a/R/multi.R b/R/multi.R index 5c98ba150..1a24ca244 100644 --- a/R/multi.R +++ b/R/multi.R @@ -381,27 +381,39 @@ colonnade_compute_tiered_col_widths_df <- function(max_widths, min_widths, tier_ #' one tier will contain some pillars with maximum and some with minimum width, #' and the remaining tiers contain pillars with their minimum width only. #' - #' We determine the cut point where minimum and maximum assignment - #' agree. - #' This is the "mixed" tier which is refined later on. + #' For this, we compute a "reverse minimum assignment". min_fit_rev <- distribute_pillars_rev(col_df$min_widths, tier_widths) + #' + #' We determine the cut point where minimum and maximum assignment + #' agree. + #' The following strategy is applied: + #' + #' 1. First, we determine the tier in which the cut point lies. + #' This is the first instance of a column that ends up in the same tier + #' for both minimum and maximum assignment. cut_point_tier <- max_fit$tier[min(which(max_fit$tier == min_fit_rev$tier))] + #' 2. A set of candidate cut points is derived. cut_point_candidates <- which(max_fit$tier == cut_point_tier) + #' 3. We consult the column offsets. The last column where the minimum assignment + #' has a greater or equal offset than the maximum assignment is our latest + #' cut point. cut_point_candidate_idx <- which(max_fit$offset[cut_point_candidates] <= min_fit_rev$offset[cut_point_candidates]) if (length(cut_point_candidate_idx) > 0) { cut_point <- cut_point_candidates[max(cut_point_candidate_idx)] } else { + #' If no such column exists, the cut point is the column just before our + #' first candidate. cut_point <- cut_point_candidates[[1]] - 1L } + #' 4. Finally, we combine maximum and minimum reverse fits at the cut point. + #' We don't need to redistribute anything here. max_fit_cut <- max_fit[seq_len(cut_point), ] min_fit_cut <- min_fit_rev[seq2(cut_point + 1L, nrow(min_fit_rev)), ] - combined_fit <- rbind(max_fit_cut, min_fit_cut) combined_fit$max_widths <- col_df$max_widths - combined_fit$offsets <- NULL combined_fit } From 093f3aa3ae6ca59011d5261434845e5f8ec86655 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Sun, 25 Jul 2021 17:59:04 +0200 Subject: [PATCH 035/147] Extract function --- R/multi.R | 15 +++++++++++---- 1 file changed, 11 insertions(+), 4 deletions(-) diff --git a/R/multi.R b/R/multi.R index 1a24ca244..9528ca7d0 100644 --- a/R/multi.R +++ b/R/multi.R @@ -384,6 +384,16 @@ colonnade_compute_tiered_col_widths_df <- function(max_widths, min_widths, tier_ #' For this, we compute a "reverse minimum assignment". min_fit_rev <- distribute_pillars_rev(col_df$min_widths, tier_widths) + combined_fit <- combine_pillar_distributions(max_fit, min_fit_rev, tier_widths) + + combined_fit$max_widths <- col_df$max_widths + combined_fit +} + +#' @rdname colonnade +#' @usage NULL +#' @aliases NULL +combine_pillar_distributions <- function(max_fit, min_fit_rev, tier_widths) { #' #' We determine the cut point where minimum and maximum assignment #' agree. @@ -411,10 +421,7 @@ colonnade_compute_tiered_col_widths_df <- function(max_widths, min_widths, tier_ #' We don't need to redistribute anything here. max_fit_cut <- max_fit[seq_len(cut_point), ] min_fit_cut <- min_fit_rev[seq2(cut_point + 1L, nrow(min_fit_rev)), ] - combined_fit <- rbind(max_fit_cut, min_fit_cut) - - combined_fit$max_widths <- col_df$max_widths - combined_fit + rbind(max_fit_cut, min_fit_cut) } #' @rdname colonnade From 9fa755752601d19454d0b19f093a1456fc69af8e Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Sun, 25 Jul 2021 18:09:14 +0200 Subject: [PATCH 036/147] Document --- R/multi.R | 2 +- man/colonnade.Rd | 22 ++++++++++++++++++++-- 2 files changed, 21 insertions(+), 3 deletions(-) diff --git a/R/multi.R b/R/multi.R index 9528ca7d0..195475567 100644 --- a/R/multi.R +++ b/R/multi.R @@ -394,7 +394,7 @@ colonnade_compute_tiered_col_widths_df <- function(max_widths, min_widths, tier_ #' @usage NULL #' @aliases NULL combine_pillar_distributions <- function(max_fit, min_fit_rev, tier_widths) { - #' + #' @details #' We determine the cut point where minimum and maximum assignment #' agree. #' The following strategy is applied: diff --git a/man/colonnade.Rd b/man/colonnade.Rd index c296992ce..55dc051d8 100644 --- a/man/colonnade.Rd +++ b/man/colonnade.Rd @@ -49,10 +49,28 @@ Otherwise, if the maximum width is too wide, the same test is carried out with the minimum width. If this is still too wide, this is the resulting fit. Otherwise, some tiers from the start -will contain pillars with their maximum width, and the remaining tiers -contain pillars with their minimum width. +will contain pillars with their maximum width, +one tier will contain some pillars with maximum and some with minimum width, +and the remaining tiers contain pillars with their minimum width only. + +For this, we compute a "reverse minimum assignment". + We determine the cut point where minimum and maximum assignment agree. +The following strategy is applied: +\enumerate{ +\item First, we determine the tier in which the cut point lies. +This is the first instance of a column that ends up in the same tier +for both minimum and maximum assignment. +\item A set of candidate cut points is derived. +\item We consult the column offsets. The last column where the minimum assignment +has a greater or equal offset than the maximum assignment is our latest +cut point. +If no such column exists, the cut point is the column just before our +first candidate. +\item Finally, we combine maximum and minimum reverse fits at the cut point. +We don't need to redistribute anything here. +} Fitting pillars into tiers is very similar to a word-wrapping algorithm. In a loop, new tiers are opened if the current tier overflows. From 92b5f2e8fe791c8c67de92ba1c9402a75c2c9c64 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Sat, 24 Jul 2021 18:55:54 +0200 Subject: [PATCH 037/147] Extract align_impl() --- R/ctl_pillar_component.R | 8 ++++---- R/extent.R | 4 ++++ 2 files changed, 8 insertions(+), 4 deletions(-) diff --git a/R/ctl_pillar_component.R b/R/ctl_pillar_component.R index 3701356aa..8ce3770e8 100644 --- a/R/ctl_pillar_component.R +++ b/R/ctl_pillar_component.R @@ -101,11 +101,11 @@ pillar_get_min_widths <- function(x) { } pillar_format_parts_2 <- function(x, width) { - "!!!!!DEBUG pillar_format_parts_2(`v(width)`)" - formatted <- map(x, function(.x) format(.x[[1]], width = width)) - alignment <- attr(formatted[["data"]], "align", exact = TRUE) %||% "left" + align <- attr(formatted[["data"]], "align", exact = TRUE) %||% "left" - align(unlist(formatted), width = width, align = alignment) + flat <- unlist(formatted) + extent <- get_extent(flat) + align_impl(flat, width, align, " ", extent) } diff --git a/R/extent.R b/R/extent.R index 975e4cb1e..e6956dce2 100644 --- a/R/extent.R +++ b/R/extent.R @@ -55,6 +55,10 @@ align <- function(x, width = NULL, align = c("left", "right"), space = " ") { if (is.null(width)) { width <- max(extent) } + align_impl(x, width, align, space, extent) +} + +align_impl <- function(x, width, align, space, extent) { spaces <- pmax(width - extent, 0L) if (align == "left") { paste0(x, strrep(space, spaces)) From e40de6f0f7f2f7443e8c42b92d6e7381d259e67a Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Sun, 25 Jul 2021 03:54:40 +0200 Subject: [PATCH 038/147] Richer interface --- R/ctl_colonnade.R | 12 +++++++----- R/ctl_pillar.R | 2 +- R/ctl_pillar_component.R | 10 ++++++++-- 3 files changed, 16 insertions(+), 8 deletions(-) diff --git a/R/ctl_colonnade.R b/R/ctl_colonnade.R index 9292e91c4..babb50e3c 100644 --- a/R/ctl_colonnade.R +++ b/R/ctl_colonnade.R @@ -44,14 +44,16 @@ ctl_colonnade <- function(x, has_row_id = TRUE, width = NULL, controller = new_t col_widths <- vec_rbind(col_widths_rowid, col_widths) } + col_widths$formatted <- map2( + col_widths$pillar, col_widths$width, + pillar_format_parts_2 + ) + tiers <- split(seq_len(nrow(col_widths)), col_widths$tier) flat_tiers <- map(tiers, function(tier) { - map2( - col_widths$pillar[tier], - col_widths$width[tier], - pillar_format_parts_2 - ) + formatted <- col_widths$formatted[tier] + map(formatted, function(.x) .x$aligned[[1]]) }) out <- map(flat_tiers, format_colonnade_tier_2) diff --git a/R/ctl_pillar.R b/R/ctl_pillar.R index 9aaff966d..1acec5689 100644 --- a/R/ctl_pillar.R +++ b/R/ctl_pillar.R @@ -173,7 +173,7 @@ format.pillar <- function(x, width = NULL, ...) { width <- sum(widths) - length(widths) + 1L } - new_vertical(pillar_format_parts_2(x, width)) + new_vertical(pillar_format_parts_2(x, width)$aligned[[1]]) } #' @export diff --git a/R/ctl_pillar_component.R b/R/ctl_pillar_component.R index 8ce3770e8..4b8e30eb6 100644 --- a/R/ctl_pillar_component.R +++ b/R/ctl_pillar_component.R @@ -54,7 +54,7 @@ pillar_component <- function(x) { } get_cell_widths <- function(x) { - # FIXME: Choose different name to avoid confusion with get_width()? + # FIXME: Choose different name to avoid confusion with get_width()? attr(x, "width", exact = TRUE) } @@ -101,11 +101,17 @@ pillar_get_min_widths <- function(x) { } pillar_format_parts_2 <- function(x, width) { + # Code is repeated in ctl_colonnade formatted <- map(x, function(.x) format(.x[[1]], width = width)) align <- attr(formatted[["data"]], "align", exact = TRUE) %||% "left" flat <- unlist(formatted) extent <- get_extent(flat) - align_impl(flat, width, align, " ", extent) + aligned <- align_impl(flat, width, align, " ", extent) + + new_tbl(list( + formatted = list(formatted), align = align, flat = list(flat), + max_extent = max(extent), aligned = list(aligned) + )) } From 53b9e42c4fecbeb0659378416680823325ed0834 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Sun, 25 Jul 2021 04:24:53 +0200 Subject: [PATCH 039/147] Extract function --- R/ctl_colonnade.R | 33 +++++++++++++++++++++------------ 1 file changed, 21 insertions(+), 12 deletions(-) diff --git a/R/ctl_colonnade.R b/R/ctl_colonnade.R index babb50e3c..63ee38bd2 100644 --- a/R/ctl_colonnade.R +++ b/R/ctl_colonnade.R @@ -86,28 +86,37 @@ colonnade_get_width_2 <- function(compound_pillar, tier_widths) { "!!!!!DEBUG colonnade_get_width_2(`v(tier_widths)`)" #' @details - #' Pillars may be distributed over multiple tiers if - #' `width > getOption("width")`. In this case each tier is at most - #' `getOption("width")` characters wide. The very first step of formatting - #' is to determine how many tiers are shown at most, and the width of each - #' tier. - col_widths_df <- colonnade_compute_tiered_col_widths_2(compound_pillar, tier_widths) + #' Each pillar indiacates its maximum and minimum width. + min_max_widths <- colonnade_get_min_max_widths(compound_pillar) + #' + #' Pillars may be distributed over multiple tiers according to their width + #' if `width > getOption("width")`. + #' In this case each tier is at most `getOption("width")` characters wide. + #' The very first step of formatting is to determine + #' how many tiers are shown at most, + #' and the width of each tier. + col_widths_df <- colonnade_compute_tiered_col_widths_2(compound_pillar, min_max_widths, tier_widths) #' Remaining space is then distributed proportionally to pillars that do not #' use their desired width. colonnade_distribute_space_df(col_widths_df, tier_widths) } -colonnade_compute_tiered_col_widths_2 <- function(compound_pillar, tier_widths) { +colonnade_get_min_max_widths <- function(compound_pillar) { + max_width <- exec(pmax, !!!unname(map(compound_pillar, get_cell_widths))) + min_width <- exec(pmax, !!!unname(map(compound_pillar, get_cell_min_widths))) + + new_tbl(list(min_width = min_width, max_width = max_width)) +} + +colonnade_compute_tiered_col_widths_2 <- function(compound_pillar, min_max_widths, tier_widths) { "!!!!!DEBUG colonnade_compute_tiered_col_widths_2(`v(tier_widths)`)" max_tier_width <- max(tier_widths) - max_widths <- exec(pmax, !!!unname(map(compound_pillar, get_cell_widths))) - max_widths <- pmin(max_widths, max_tier_width) - - min_widths <- exec(pmax, !!!unname(map(compound_pillar, get_cell_min_widths))) - min_widths <- pmin(min_widths, max_tier_width) + # Safety: + max_widths <- pmin(min_max_widths$max_width, max_tier_width) + min_widths <- pmin(min_max_widths$min_width, max_tier_width) ret <- colonnade_compute_tiered_col_widths_df(max_widths, min_widths, tier_widths) From d95ff3a2b1d99d2fa7490ec64b98c772520a1e0a Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Sun, 25 Jul 2021 04:27:38 +0200 Subject: [PATCH 040/147] Move responsibility --- R/ctl_colonnade.R | 8 +------- R/multi.R | 6 ++++++ 2 files changed, 7 insertions(+), 7 deletions(-) diff --git a/R/ctl_colonnade.R b/R/ctl_colonnade.R index 63ee38bd2..0df726fbe 100644 --- a/R/ctl_colonnade.R +++ b/R/ctl_colonnade.R @@ -112,13 +112,7 @@ colonnade_get_min_max_widths <- function(compound_pillar) { colonnade_compute_tiered_col_widths_2 <- function(compound_pillar, min_max_widths, tier_widths) { "!!!!!DEBUG colonnade_compute_tiered_col_widths_2(`v(tier_widths)`)" - max_tier_width <- max(tier_widths) - - # Safety: - max_widths <- pmin(min_max_widths$max_width, max_tier_width) - min_widths <- pmin(min_max_widths$min_width, max_tier_width) - - ret <- colonnade_compute_tiered_col_widths_df(max_widths, min_widths, tier_widths) + ret <- colonnade_compute_tiered_col_widths_df(min_max_widths$max_width, min_max_widths$min_width, tier_widths) pillars <- map(ret$id, get_sub_pillar, x = compound_pillar) ret$pillar <- pillars diff --git a/R/multi.R b/R/multi.R index 195475567..52efee7cd 100644 --- a/R/multi.R +++ b/R/multi.R @@ -355,6 +355,12 @@ colonnade_compute_tiered_col_widths <- function(pillars, tier_widths) { colonnade_compute_tiered_col_widths_df <- function(max_widths, min_widths, tier_widths) { "!!!!!DEBUG colonnade_compute_tiered_col_widths_df(`v(tier_widths)`)" + max_tier_width <- max(tier_widths) + + # Safety: + max_widths <- pmin(max_widths, max_tier_width) + min_widths <- pmin(min_widths, max_tier_width) + id <- seq_along(max_widths) col_df <- data.frame(id, max_widths, min_widths, row.names = NULL) From c59d173119cf5afebbd13bcf15514ab5f21621f9 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Sun, 25 Jul 2021 04:48:14 +0200 Subject: [PATCH 041/147] Inline function --- R/ctl_colonnade.R | 21 +++++++++------------ 1 file changed, 9 insertions(+), 12 deletions(-) diff --git a/R/ctl_colonnade.R b/R/ctl_colonnade.R index 0df726fbe..aeed8a880 100644 --- a/R/ctl_colonnade.R +++ b/R/ctl_colonnade.R @@ -95,11 +95,18 @@ colonnade_get_width_2 <- function(compound_pillar, tier_widths) { #' The very first step of formatting is to determine #' how many tiers are shown at most, #' and the width of each tier. - col_widths_df <- colonnade_compute_tiered_col_widths_2(compound_pillar, min_max_widths, tier_widths) + col_widths_df <- colonnade_compute_tiered_col_widths_df(min_max_widths$max_width, min_max_widths$min_width, tier_widths) + # col_widths_df <- data.frame(id = numeric(), widths = numeric(), tier = numeric()) + + pillars <- map(col_widths_df$id, get_sub_pillar, x = compound_pillar) + col_widths_df$pillar <- pillars #' Remaining space is then distributed proportionally to pillars that do not #' use their desired width. - colonnade_distribute_space_df(col_widths_df, tier_widths) + out <- colonnade_distribute_space_df(col_widths_df, tier_widths) + # out <- data.frame(id = numeric(), widths = numeric(), tier = numeric()) + + new_tbl(out) } colonnade_get_min_max_widths <- function(compound_pillar) { @@ -108,13 +115,3 @@ colonnade_get_min_max_widths <- function(compound_pillar) { new_tbl(list(min_width = min_width, max_width = max_width)) } - -colonnade_compute_tiered_col_widths_2 <- function(compound_pillar, min_max_widths, tier_widths) { - "!!!!!DEBUG colonnade_compute_tiered_col_widths_2(`v(tier_widths)`)" - - ret <- colonnade_compute_tiered_col_widths_df(min_max_widths$max_width, min_max_widths$min_width, tier_widths) - - pillars <- map(ret$id, get_sub_pillar, x = compound_pillar) - ret$pillar <- pillars - new_tbl(ret) -} From ea705f32aa2989deb50a333d0580ed6aa42c6f12 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Sun, 25 Jul 2021 04:50:05 +0200 Subject: [PATCH 042/147] Defer --- R/ctl_colonnade.R | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/R/ctl_colonnade.R b/R/ctl_colonnade.R index aeed8a880..b4583f82c 100644 --- a/R/ctl_colonnade.R +++ b/R/ctl_colonnade.R @@ -98,14 +98,14 @@ colonnade_get_width_2 <- function(compound_pillar, tier_widths) { col_widths_df <- colonnade_compute_tiered_col_widths_df(min_max_widths$max_width, min_max_widths$min_width, tier_widths) # col_widths_df <- data.frame(id = numeric(), widths = numeric(), tier = numeric()) - pillars <- map(col_widths_df$id, get_sub_pillar, x = compound_pillar) - col_widths_df$pillar <- pillars - #' Remaining space is then distributed proportionally to pillars that do not #' use their desired width. out <- colonnade_distribute_space_df(col_widths_df, tier_widths) # out <- data.frame(id = numeric(), widths = numeric(), tier = numeric()) + # FIXME: Defer split of compound pillars + out$pillar <- map(out$id, get_sub_pillar, x = compound_pillar) + new_tbl(out) } From 0e94c5bec839f2312ff433f6a26b02845f049250 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Sun, 25 Jul 2021 05:13:37 +0200 Subject: [PATCH 043/147] Defer formatting of rowid --- R/ctl_colonnade.R | 19 ++++++------------- 1 file changed, 6 insertions(+), 13 deletions(-) diff --git a/R/ctl_colonnade.R b/R/ctl_colonnade.R index b4583f82c..518119bba 100644 --- a/R/ctl_colonnade.R +++ b/R/ctl_colonnade.R @@ -31,19 +31,6 @@ ctl_colonnade <- function(x, has_row_id = TRUE, width = NULL, controller = new_t compound_pillar <- combine_pillars(pillars) col_widths <- colonnade_get_width_2(compound_pillar, tier_widths) - if (!is.null(rowid)) { - rowid_pillar <- rowidformat2(rowid, names(pillars[[1]]), has_star = identical(has_row_id, "*")) - - col_widths_rowid <- as_tbl(data_frame( - tier = unique(col_widths$tier), - id = 0L, - width = rowid_width, - pillar = list(rowid_pillar) - )) - - col_widths <- vec_rbind(col_widths_rowid, col_widths) - } - col_widths$formatted <- map2( col_widths$pillar, col_widths$width, pillar_format_parts_2 @@ -56,6 +43,12 @@ ctl_colonnade <- function(x, has_row_id = TRUE, width = NULL, controller = new_t map(formatted, function(.x) .x$aligned[[1]]) }) + if (!is.null(rowid)) { + rowid_pillar <- rowidformat2(rowid, names(pillars[[1]]), has_star = identical(has_row_id, "*")) + rowid_formatted <- list(pillar_format_parts_2(rowid_pillar, rowid_width)$aligned[[1]]) + flat_tiers <- map(flat_tiers, function(.x) c(rowid_formatted, .x)) + } + out <- map(flat_tiers, format_colonnade_tier_2) extra_cols <- as.list(x)[seq2(length(pillars) + 1L, nc)] From 0f6a8d3b778f067d83f60366256bf0f96e8df930 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Sun, 25 Jul 2021 19:00:04 +0200 Subject: [PATCH 044/147] All pillars show with their true extent --- R/ctl_pillar_component.R | 2 +- tests/testthat/_snaps/format_character.md | 12 ++++----- tests/testthat/_snaps/format_list_of.md | 10 ++++---- tests/testthat/_snaps/format_survival.md | 28 ++++++++++----------- tests/testthat/_snaps/format_unspecified.md | 8 +++--- tests/testthat/_snaps/type_sum.md | 10 ++++---- 6 files changed, 35 insertions(+), 35 deletions(-) diff --git a/R/ctl_pillar_component.R b/R/ctl_pillar_component.R index 4b8e30eb6..cbcac87a0 100644 --- a/R/ctl_pillar_component.R +++ b/R/ctl_pillar_component.R @@ -108,7 +108,7 @@ pillar_format_parts_2 <- function(x, width) { flat <- unlist(formatted) extent <- get_extent(flat) - aligned <- align_impl(flat, width, align, " ", extent) + aligned <- align_impl(flat, min(width, max(extent)), align, " ", extent) new_tbl(list( formatted = list(formatted), align = align, flat = list(flat), diff --git a/tests/testthat/_snaps/format_character.md b/tests/testthat/_snaps/format_character.md index c7086e02b..ed944a973 100644 --- a/tests/testthat/_snaps/format_character.md +++ b/tests/testthat/_snaps/format_character.md @@ -68,16 +68,16 @@ pillar(add_special(c("\t")), width = 10) Output - - "\t" - + + "\t" + Code pillar(add_special(c("a\nb")), width = 10) Output - - "a\nb" - + + "a\nb" + Code pillar(add_special(c("a\001b")), width = 10) Output diff --git a/tests/testthat/_snaps/format_list_of.md b/tests/testthat/_snaps/format_list_of.md index df4737299..0ca86d542 100644 --- a/tests/testthat/_snaps/format_list_of.md +++ b/tests/testthat/_snaps/format_list_of.md @@ -4,9 +4,9 @@ pillar(v, width = 15) Output - > - [1] - [3] + > + [1] + [3] --- @@ -14,6 +14,6 @@ pillar(v, width = 30) Output - > - SC + > + SC diff --git a/tests/testthat/_snaps/format_survival.md b/tests/testthat/_snaps/format_survival.md index 6c12394b7..b61c2babf 100644 --- a/tests/testthat/_snaps/format_survival.md +++ b/tests/testthat/_snaps/format_survival.md @@ -4,13 +4,13 @@ pillar(x, width = 20) Output - - 306 - 455 - 1010+ - 210 - 883 - 1022+ + + 306 + 455 + 1010+ + 210 + 883 + 1022+ --- @@ -18,11 +18,11 @@ pillar(x, width = 20) Output - - 306:2 - 455:2 - 1010+ - 210:2 - 883:2 - 1022+ + + 306:2 + 455:2 + 1010+ + 210:2 + 883:2 + 1022+ diff --git a/tests/testthat/_snaps/format_unspecified.md b/tests/testthat/_snaps/format_unspecified.md index 63d1a03aa..050179403 100644 --- a/tests/testthat/_snaps/format_unspecified.md +++ b/tests/testthat/_snaps/format_unspecified.md @@ -4,8 +4,8 @@ pillar(vctrs::unspecified(3), width = 10) Output - - . - . - . + + . + . + . diff --git a/tests/testthat/_snaps/type_sum.md b/tests/testthat/_snaps/type_sum.md index 9d593da0c..956f1b015 100644 --- a/tests/testthat/_snaps/type_sum.md +++ b/tests/testthat/_snaps/type_sum.md @@ -14,9 +14,9 @@ new_tbl(new_tbl(list(foo = foo, bar = bar))) Output # A data frame: 3 x 2 - foo bar - AsIs SC - 1 2011 2011 - 2 2012 2012 - 3 2013 2013 + foo bar + AsIs SC + 1 2011 2011 + 2 2012 2012 + 3 2013 2013 From 07e91c4e742caac3e7f65a912ca03a8d72663df7 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Sun, 25 Jul 2021 18:22:43 +0200 Subject: [PATCH 045/147] Combine loops --- R/ctl_colonnade.R | 10 ++++++++-- 1 file changed, 8 insertions(+), 2 deletions(-) diff --git a/R/ctl_colonnade.R b/R/ctl_colonnade.R index 518119bba..e628107d1 100644 --- a/R/ctl_colonnade.R +++ b/R/ctl_colonnade.R @@ -39,8 +39,14 @@ ctl_colonnade <- function(x, has_row_id = TRUE, width = NULL, controller = new_t tiers <- split(seq_len(nrow(col_widths)), col_widths$tier) flat_tiers <- map(tiers, function(tier) { - formatted <- col_widths$formatted[tier] - map(formatted, function(.x) .x$aligned[[1]]) + formatted <- map2( + col_widths$pillar[tier], col_widths$width[tier], + pillar_format_parts_2 + ) + + map(formatted, function(.x) { + .x$aligned[[1]] + }) }) if (!is.null(rowid)) { From 0186885dc47d76899dadd270ac87278b576b60e0 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Sun, 25 Jul 2021 18:40:31 +0200 Subject: [PATCH 046/147] Two passes, fixes reprex --- R/ctl_colonnade.R | 36 ++++++++++++++++++++++++++++-------- 1 file changed, 28 insertions(+), 8 deletions(-) diff --git a/R/ctl_colonnade.R b/R/ctl_colonnade.R index e628107d1..985332492 100644 --- a/R/ctl_colonnade.R +++ b/R/ctl_colonnade.R @@ -39,14 +39,10 @@ ctl_colonnade <- function(x, has_row_id = TRUE, width = NULL, controller = new_t tiers <- split(seq_len(nrow(col_widths)), col_widths$tier) flat_tiers <- map(tiers, function(tier) { - formatted <- map2( - col_widths$pillar[tier], col_widths$width[tier], - pillar_format_parts_2 - ) - - map(formatted, function(.x) { - .x$aligned[[1]] - }) + pillars <- col_widths$pillar[tier] + widths <- col_widths$width[tier] + max_widths <- col_widths$max_widths[tier] + pillar_format_tier(pillars, widths, max_widths) }) if (!is.null(rowid)) { @@ -61,6 +57,30 @@ ctl_colonnade <- function(x, has_row_id = TRUE, width = NULL, controller = new_t new_colonnade_body(out, extra_cols = extra_cols) } +pillar_format_tier <- function(pillars, widths, max_widths) { + # First pass: formatting with the allocated width + formatted <- map2(pillars, widths, pillar_format_parts_2) + + extents <- map_int(formatted, `[[`, "max_extent") + extra <- sum(widths - extents) + + # Second pass: trying to use the remaining width, starting at the left + col_idx <- 1 + while (extra > 0 && col_idx <= length(pillars)) { + new_formatted <- pillar_format_parts_2(pillars[[col_idx]], min(widths[[col_idx]] + extra, max_widths[[col_idx]])) + delta <- new_formatted$max_extent - formatted[[col_idx]]$max_extent + if (delta > 0) { + extra <- extra - delta + formatted[[col_idx]] <- new_formatted + } + col_idx <- col_idx + 1L + } + + map(formatted, function(.x) { + .x$aligned[[1]] + }) +} + format_colonnade_tier_2 <- function(x) { "!!!!!DEBUG format_colonnade_tier_2(`v(x)`)" From 5c589cf65d9223c924991f06c209a6de7d782ac3 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Mon, 26 Jul 2021 03:56:37 +0200 Subject: [PATCH 047/147] Add test --- tests/testthat/_snaps/ctl_colonnade.md | 18 +++++++++++ tests/testthat/test-ctl_colonnade.R | 42 ++++++++++++++++++++++++++ 2 files changed, 60 insertions(+) diff --git a/tests/testthat/_snaps/ctl_colonnade.md b/tests/testthat/_snaps/ctl_colonnade.md index 2a70e5337..fcd34f973 100644 --- a/tests/testthat/_snaps/ctl_colonnade.md +++ b/tests/testthat/_snaps/ctl_colonnade.md @@ -807,3 +807,21 @@ named list() +# filling unused width (#331) + + Code + data + Output + # A data frame: 1 x 3 + month sentences blah + + 1 January a b c d e f g h i j k l m n o p q r s t u v w x y z A B C D E F G H I~ + Code + options(width = 60) + print(data) + Output + # A data frame: 1 x 3 + month sentences blah + + 1 January a b c d~ A B C D E F G H I J K L M N O P Q R S T~ + diff --git a/tests/testthat/test-ctl_colonnade.R b/tests/testthat/test-ctl_colonnade.R index 14bc21b68..c40765a13 100644 --- a/tests/testthat/test-ctl_colonnade.R +++ b/tests/testthat/test-ctl_colonnade.R @@ -159,3 +159,45 @@ test_that("matrix columns (empty)", { ) }) }) + +test_that("filling unused width (#331)", { + new_foo <- function(x = character()) { + vctrs::vec_assert(x, character()) + vctrs::new_vctr(x, class = "foo") + } + + data <- new_tbl(list( + month = month.name[1], + sentences = new_foo(paste(letters, collapse = " ")), + blah = paste(LETTERS, collapse = " ") + )) + + pillar_shaft.foo <- function(x, ...) { + full <- format(x) + trunc <- format(paste0(substr(x, 1, 7), cli::symbol$continue)) + pillar::new_pillar_shaft( + list(full = full, trunc = trunc), + width = pillar::get_max_extent(full), + min_width = pillar::get_max_extent(trunc), + class = "pillar_shaft_foo" + ) + } + + format.pillar_shaft_foo <- function(x, width, ...) { + if (pillar::get_max_extent(x$full) <= width) { + ornament <- x$full + } else { + ornament <- x$trunc + } + + pillar::new_ornament(ornament, align = "left") + } + + local_methods(pillar_shaft.foo = pillar_shaft.foo, format.pillar_shaft_foo = format.pillar_shaft_foo) + + expect_snapshot({ + data + options(width = 60) + print(data) + }) +}) From c6a4f747d47f48771d1e0e6d332ab9ff76fa405a Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Mon, 26 Jul 2021 04:09:40 +0200 Subject: [PATCH 048/147] Type --- R/ctl_colonnade.R | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/R/ctl_colonnade.R b/R/ctl_colonnade.R index 985332492..ae467cd29 100644 --- a/R/ctl_colonnade.R +++ b/R/ctl_colonnade.R @@ -65,7 +65,7 @@ pillar_format_tier <- function(pillars, widths, max_widths) { extra <- sum(widths - extents) # Second pass: trying to use the remaining width, starting at the left - col_idx <- 1 + col_idx <- 1L while (extra > 0 && col_idx <= length(pillars)) { new_formatted <- pillar_format_parts_2(pillars[[col_idx]], min(widths[[col_idx]] + extra, max_widths[[col_idx]])) delta <- new_formatted$max_extent - formatted[[col_idx]]$max_extent From cfd520efb423cad4b74d90079858b4ca4fe71a42 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Mon, 26 Jul 2021 04:14:00 +0200 Subject: [PATCH 049/147] Only compress affected columns --- R/ctl_colonnade.R | 7 +++++-- 1 file changed, 5 insertions(+), 2 deletions(-) diff --git a/R/ctl_colonnade.R b/R/ctl_colonnade.R index ae467cd29..a24147912 100644 --- a/R/ctl_colonnade.R +++ b/R/ctl_colonnade.R @@ -65,8 +65,11 @@ pillar_format_tier <- function(pillars, widths, max_widths) { extra <- sum(widths - extents) # Second pass: trying to use the remaining width, starting at the left - col_idx <- 1L - while (extra > 0 && col_idx <= length(pillars)) { + for (col_idx in which(widths < max_widths)) { + if (extra <= 0) { + break + } + new_formatted <- pillar_format_parts_2(pillars[[col_idx]], min(widths[[col_idx]] + extra, max_widths[[col_idx]])) delta <- new_formatted$max_extent - formatted[[col_idx]]$max_extent if (delta > 0) { From 9278b214b85b94cd190caa32b56e66b75fb5f3d1 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Mon, 26 Jul 2021 04:18:17 +0200 Subject: [PATCH 050/147] Avoid extra work --- R/ctl_colonnade.R | 5 ----- 1 file changed, 5 deletions(-) diff --git a/R/ctl_colonnade.R b/R/ctl_colonnade.R index a24147912..dd986f8da 100644 --- a/R/ctl_colonnade.R +++ b/R/ctl_colonnade.R @@ -31,11 +31,6 @@ ctl_colonnade <- function(x, has_row_id = TRUE, width = NULL, controller = new_t compound_pillar <- combine_pillars(pillars) col_widths <- colonnade_get_width_2(compound_pillar, tier_widths) - col_widths$formatted <- map2( - col_widths$pillar, col_widths$width, - pillar_format_parts_2 - ) - tiers <- split(seq_len(nrow(col_widths)), col_widths$tier) flat_tiers <- map(tiers, function(tier) { From 2d544782b0e35d270c30b31731184fb406cf2b73 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Mon, 26 Jul 2021 04:22:42 +0200 Subject: [PATCH 051/147] Shortcut --- R/ctl_colonnade.R | 23 ++++++++++++----------- 1 file changed, 12 insertions(+), 11 deletions(-) diff --git a/R/ctl_colonnade.R b/R/ctl_colonnade.R index dd986f8da..eb1989c38 100644 --- a/R/ctl_colonnade.R +++ b/R/ctl_colonnade.R @@ -60,18 +60,19 @@ pillar_format_tier <- function(pillars, widths, max_widths) { extra <- sum(widths - extents) # Second pass: trying to use the remaining width, starting at the left - for (col_idx in which(widths < max_widths)) { - if (extra <= 0) { - break + if (extra > 0) { + for (col_idx in which(widths < max_widths)) { + new_formatted <- pillar_format_parts_2(pillars[[col_idx]], min(widths[[col_idx]] + extra, max_widths[[col_idx]])) + delta <- new_formatted$max_extent - formatted[[col_idx]]$max_extent + if (delta > 0) { + formatted[[col_idx]] <- new_formatted + extra <- extra - delta + if (extra <= 0) { + break + } + } + col_idx <- col_idx + 1L } - - new_formatted <- pillar_format_parts_2(pillars[[col_idx]], min(widths[[col_idx]] + extra, max_widths[[col_idx]])) - delta <- new_formatted$max_extent - formatted[[col_idx]]$max_extent - if (delta > 0) { - extra <- extra - delta - formatted[[col_idx]] <- new_formatted - } - col_idx <- col_idx + 1L } map(formatted, function(.x) { From 6772fc6513404c091695ba6c022f539b091b3bf5 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Mon, 26 Jul 2021 05:23:01 +0200 Subject: [PATCH 052/147] Document default obj_sum() method --- R/type-sum.R | 7 ++++--- man/type_sum.Rd | 6 ++++-- 2 files changed, 8 insertions(+), 5 deletions(-) diff --git a/R/type-sum.R b/R/type-sum.R index a67142e40..bddf79334 100644 --- a/R/type-sum.R +++ b/R/type-sum.R @@ -64,11 +64,12 @@ vec_ptype_abbr.pillar_empty_col <- function(x, ...) { } #' @description -#' `obj_sum()` also includes the size of the object if [vctrs::vec_is()] -#' is `TRUE`. +#' `obj_sum()` also includes the size (but not the shape) of the object +#' if [vctrs::vec_is()] is `TRUE`. #' It should always return a string (a character vector of length one). +#' The default method forwards to [vctrs::vec_ptype_abbr()] as of pillar v1.6.1, +#' previous versions forwarded to [type_sum()]. #' -#' @keywords internal #' @examples #' obj_sum(1:10) #' obj_sum(matrix(1:10)) diff --git a/man/type_sum.Rd b/man/type_sum.Rd index 935f838df..c3d9737b0 100644 --- a/man/type_sum.Rd +++ b/man/type_sum.Rd @@ -21,9 +21,11 @@ and variants have been implemented.} occur in a data frame should return a string with four or less characters. For most inputs, the argument is forwarded to \code{\link[vctrs:vec_ptype_full]{vctrs::vec_ptype_abbr()}}. -\code{obj_sum()} also includes the size of the object if \code{\link[vctrs:vec_assert]{vctrs::vec_is()}} -is \code{TRUE}. +\code{obj_sum()} also includes the size (but not the shape) of the object +if \code{\link[vctrs:vec_assert]{vctrs::vec_is()}} is \code{TRUE}. It should always return a string (a character vector of length one). +The default method forwards to \code{\link[vctrs:vec_ptype_full]{vctrs::vec_ptype_abbr()}} as of pillar v1.6.1, +previous versions forwarded to \code{\link[=type_sum]{type_sum()}}. \code{size_sum()} is called by \code{obj_sum()} to format the size of the object. It should always return a string (a character vector of length one), From bef9d314ed748480e25e7e120e17841d3c88f67d Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Mon, 26 Jul 2021 05:25:32 +0200 Subject: [PATCH 053/147] Detail --- R/type-sum.R | 5 +++-- man/type_sum.Rd | 5 +++-- 2 files changed, 6 insertions(+), 4 deletions(-) diff --git a/R/type-sum.R b/R/type-sum.R index bddf79334..71f28da67 100644 --- a/R/type-sum.R +++ b/R/type-sum.R @@ -67,8 +67,9 @@ vec_ptype_abbr.pillar_empty_col <- function(x, ...) { #' `obj_sum()` also includes the size (but not the shape) of the object #' if [vctrs::vec_is()] is `TRUE`. #' It should always return a string (a character vector of length one). -#' The default method forwards to [vctrs::vec_ptype_abbr()] as of pillar v1.6.1, -#' previous versions forwarded to [type_sum()]. +#' As of pillar v1.6.1, the default method forwards to [vctrs::vec_ptype_abbr()] +#' for vectors and to [type_sum()] for other objects. +#' Previous versions always forwarded to [type_sum()]. #' #' @examples #' obj_sum(1:10) diff --git a/man/type_sum.Rd b/man/type_sum.Rd index c3d9737b0..02ea368fd 100644 --- a/man/type_sum.Rd +++ b/man/type_sum.Rd @@ -24,8 +24,9 @@ For most inputs, the argument is forwarded to \code{\link[vctrs:vec_ptype_full]{ \code{obj_sum()} also includes the size (but not the shape) of the object if \code{\link[vctrs:vec_assert]{vctrs::vec_is()}} is \code{TRUE}. It should always return a string (a character vector of length one). -The default method forwards to \code{\link[vctrs:vec_ptype_full]{vctrs::vec_ptype_abbr()}} as of pillar v1.6.1, -previous versions forwarded to \code{\link[=type_sum]{type_sum()}}. +As of pillar v1.6.1, the default method forwards to \code{\link[vctrs:vec_ptype_full]{vctrs::vec_ptype_abbr()}} +for vectors and to \code{\link[=type_sum]{type_sum()}} for other objects. +Previous versions always forwarded to \code{\link[=type_sum]{type_sum()}}. \code{size_sum()} is called by \code{obj_sum()} to format the size of the object. It should always return a string (a character vector of length one), From e69b655b60a5565b4ae87a04837b7a2388b1d527 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Mon, 26 Jul 2021 05:54:17 +0200 Subject: [PATCH 054/147] Bump version to 1.6.1.9003 --- DESCRIPTION | 2 +- NEWS.md | 9 +++++++++ 2 files changed, 10 insertions(+), 1 deletion(-) diff --git a/DESCRIPTION b/DESCRIPTION index bcdf9d87d..be791668e 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -1,6 +1,6 @@ Package: pillar Title: Coloured Formatting for Columns -Version: 1.6.1.9002 +Version: 1.6.1.9003 Authors@R: c(person(given = "Kirill", family = "M\u00fcller", diff --git a/NEWS.md b/NEWS.md index 96c914ae9..1e664ae1b 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,5 +1,14 @@ +# pillar 1.6.1.9003 + +- `obj_sum()` no longer calls `type_sum()` for vectors since pillar v1.6.1, this is now documented (#321). +- If a column doesn't make use of all horizontal width offered to it, the excess width is distributed over other columns (#331). +- All pillars are shown with their true horizontal extent, irrespective of the indicated `width`. This simplifies the implementation of custom `pillar_shaft()` methods (#347). +- Improved allocation of free space in multi-tier tables with `getOption("tibble.width") > getOption("width")` (#344). +- Avoid mangling of duplicate column names in footer (#332). + + # pillar 1.6.1.9002 - Using `attr(exact = TRUE)` everywhere. From 3fa9f32770c3700726e9ddb382bef8410be7eb89 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Mon, 26 Jul 2021 06:00:27 +0200 Subject: [PATCH 055/147] Link to options page --- R/pillar-package.R | 7 ++++--- man/pillar-package.Rd | 12 +++--------- 2 files changed, 7 insertions(+), 12 deletions(-) diff --git a/R/pillar-package.R b/R/pillar-package.R index 72067083a..f6067e237 100644 --- a/R/pillar-package.R +++ b/R/pillar-package.R @@ -7,9 +7,10 @@ #' using the full range of colours provided by modern terminals. #' Provides various generics for making every aspect of the display customizable. #' -#' @details -#' See [pillar()] for formatting a single column, -#' and [print.tbl()] for formatting data-frame-like objects. +#' @seealso +#' - [pillar()] for formatting a single column, +#' - [print.tbl()] for formatting data-frame-like objects, +#' - [pillar_options] for a list of package options. #' #' @examples #' pillar(1:3) diff --git a/man/pillar-package.Rd b/man/pillar-package.Rd index 6f6437e1b..7ded9af2c 100644 --- a/man/pillar-package.Rd +++ b/man/pillar-package.Rd @@ -11,10 +11,6 @@ Formats tabular data in columns or rows using the full range of colours provided by modern terminals. Provides various generics for making every aspect of the display customizable. } -\details{ -See \code{\link[=pillar]{pillar()}} for formatting a single column, -and \code{\link[=print.tbl]{print.tbl()}} for formatting data-frame-like objects. -} \examples{ pillar(1:3) pillar(c(1, 2, 3)) @@ -22,13 +18,11 @@ pillar(factor(letters[1:3]), title = "letters") colonnade(iris[1:3, ]) } \seealso{ -Useful links: \itemize{ - \item \url{https://pillar.r-lib.org/} - \item \url{https://github.com/r-lib/pillar} - \item Report bugs at \url{https://github.com/r-lib/pillar/issues} +\item \code{\link[=pillar]{pillar()}} for formatting a single column, +\item \code{\link[=print.tbl]{print.tbl()}} for formatting data-frame-like objects, +\item \link{pillar_options} for a list of package options. } - } \author{ \strong{Maintainer}: Kirill Müller \email{krlmlr+r@mailbox.org} From fd6387a15c7564206a2697fc7cb2a59c7b09d304 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Mon, 26 Jul 2021 06:02:13 +0200 Subject: [PATCH 056/147] Reword --- R/options.R | 4 ++-- man/pillar_options.Rd | 4 ++-- 2 files changed, 4 insertions(+), 4 deletions(-) diff --git a/R/options.R b/R/options.R index cb03fd1c2..d44904e49 100644 --- a/R/options.R +++ b/R/options.R @@ -10,8 +10,8 @@ #' Setting `local = TRUE` enables the option for the duration of the #' current stack frame via [rlang::local_options()]. #' -#' These options can also be queried via [getOption()] and set via [options()] -#' by prefixing them with `pillar.` (the package name and a dot). +#' These options can also be set via [options()] and queried via [getOption()]. +#' For this, add a `pillar.` prefix (the package name and a dot) to the option name. #' Example: for an option `foo`, #' `pillar_options$foo(value)` is equivalent to #' `options(pillar.foo = value)`. diff --git a/man/pillar_options.Rd b/man/pillar_options.Rd index 26c543f6d..c07219df6 100644 --- a/man/pillar_options.Rd +++ b/man/pillar_options.Rd @@ -22,8 +22,8 @@ is returned, invisibly. Setting \code{local = TRUE} enables the option for the duration of the current stack frame via \code{\link[rlang:local_options]{rlang::local_options()}}. -These options can also be queried via \code{\link[=getOption]{getOption()}} and set via \code{\link[=options]{options()}} -by prefixing them with \code{pillar.} (the package name and a dot). +These options can also be set via \code{\link[=options]{options()}} and queried via \code{\link[=getOption]{getOption()}}. +For this, add a \code{pillar.} prefix (the package name and a dot) to the option name. Example: for an option \code{foo}, \code{pillar_options$foo(value)} is equivalent to \code{options(pillar.foo = value)}. From e870f9b1f0cb40383aaa4b53667eff2a787ef95d Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Mon, 26 Jul 2021 06:05:45 +0200 Subject: [PATCH 057/147] Remove boilerplate, now in tests --- R/options.R | 16 ---------------- 1 file changed, 16 deletions(-) diff --git a/R/options.R b/R/options.R index d44904e49..dafab81ac 100644 --- a/R/options.R +++ b/R/options.R @@ -38,39 +38,29 @@ #' pillar(1.234567) #' @section Options for the pillar package: pillar_options <- list2( - # get_pillar_option_bold - # set_pillar_option_bold bold = make_option_impl( getOption("pillar.bold", default = FALSE) ), #' - `bold`: Use bold font, e.g. for column headers? This currently #' defaults to `FALSE`, because many terminal fonts have poor support for #' bold fonts. - # get_pillar_option_subtle - # set_pillar_option_subtle subtle = make_option_impl( getOption("pillar.subtle", default = TRUE) ), #' - `subtle`: Use subtle style, e.g. for row numbers and data types? #' Default: `TRUE`. - # get_pillar_option_subtle_num - # set_pillar_option_subtle_num subtle_num = make_option_impl( getOption("pillar.subtle_num", default = FALSE) ), #' - `subtle_num`: Use subtle style for insignificant digits? Default: #' `FALSE`, is also affected by the `subtle` option. #' - `neg`: Highlight negative numbers? Default: `TRUE`. - # get_pillar_option_neg - # set_pillar_option_neg neg = make_option_impl( getOption("pillar.neg", default = TRUE) ), #' - `sigfig`: The number of significant digits that will be printed and #' highlighted, default: `3`. Set the `subtle` option to `FALSE` to #' turn off highlighting of significant digits. - # get_pillar_option_sigfig - # set_pillar_option_sigfig sigfig = make_option_impl(option_name = "pillar.sigfig", { sigfig <- getOption("pillar.sigfig", default = 3L) if (!is.numeric(sigfig) || length(sigfig) != 1 || sigfig < 1L) { @@ -84,8 +74,6 @@ pillar_options <- list2( #' title, default: `15`. Column titles may be truncated up to that width to #' save horizontal space. Set to `Inf` to turn off truncation of column #' titles. - # get_pillar_option_min_title_chars - # set_pillar_option_min_title_chars min_title_chars = make_option_impl( getOption("pillar.min_title_chars", default = 15L) ), @@ -93,8 +81,6 @@ pillar_options <- list2( #' display character columns, default: `3`. Character columns may be #' truncated up to that width to save horizontal space. Set to `Inf` to #' turn off truncation of character columns. - # get_pillar_option_min_chars - # set_pillar_option_min_chars min_chars = make_option_impl(option_name = "pillar.min_chars", { min_chars <- getOption("pillar.min_chars", default = 3L) if (!is.numeric(min_chars) || length(min_chars) != 1 || min_chars < 3L) { @@ -106,8 +92,6 @@ pillar_options <- list2( }), #' - `max_dec_width`: The maximum allowed width for decimal notation, #' default 13. - # get_pillar_option_max_dec_width - # set_pillar_option_max_dec_width max_dec_width = make_option_impl( getOption("pillar.max_dec_width", default = 13L) ), From 0aff0f8562b98290e77d9abb135bcb6dfe67c1a3 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Mon, 26 Jul 2021 06:07:35 +0200 Subject: [PATCH 058/147] REVERT ME: unexport --- NAMESPACE | 1 - R/options.R | 25 ++++++++----------------- man/pillar_options.Rd | 24 ++++++++---------------- 3 files changed, 16 insertions(+), 34 deletions(-) diff --git a/NAMESPACE b/NAMESPACE index c900a98eb..83d77dec4 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -130,7 +130,6 @@ export(num) export(obj_sum) export(pillar) export(pillar_component) -export(pillar_options) export(pillar_shaft) export(set_char_opts) export(set_num_opts) diff --git a/R/options.R b/R/options.R index dafab81ac..b80192493 100644 --- a/R/options.R +++ b/R/options.R @@ -2,37 +2,28 @@ #' #' Options that affect display of tibble-like output. #' -#' All options are available via the `pillar_options` list. -#' The elements of this list are combined getter/setter functions. -#' Calling a function without arguments returns the current value, -#' by providing an argument the current value is set and the old value -#' is returned, invisibly. -#' Setting `local = TRUE` enables the option for the duration of the -#' current stack frame via [rlang::local_options()]. -#' -#' These options can also be set via [options()] and queried via [getOption()]. +#' These options can be set via [options()] and queried via [getOption()]. #' For this, add a `pillar.` prefix (the package name and a dot) to the option name. -#' Example: for an option `foo`, -#' `pillar_options$foo(value)` is equivalent to -#' `options(pillar.foo = value)`. +#' Example: for an option `foo`, use `options(pillar.foo = value)` to set it +#' and `getOption("pillar.foo")` to retrieve the current value (`NULL` means +#' that the default is used). #' -#' @export #' @examples #' # Default setting: -#' pillar_options$sigfig() +#' getOption("pillar.sigfig") #' pillar(1.234567) #' #' # Change for the duration of the session: -#' old <- pillar_options$sigfig(6) +#' old <- options(pillar.sigfig = 6) #' pillar(1.234567) #' #' # Change back to the original value: -#' pillar_options$sigfig(old) +#' options(old) #' pillar(1.234567) #' #' # Local scope: #' local({ -#' pillar_options$sigfig(6, local = TRUE) +#' rlang::local_options(pillar.sigfig = 6) #' pillar(1.234567) #' }) #' pillar(1.234567) diff --git a/man/pillar_options.Rd b/man/pillar_options.Rd index c07219df6..992d7c540 100644 --- a/man/pillar_options.Rd +++ b/man/pillar_options.Rd @@ -14,19 +14,11 @@ pillar_options Options that affect display of tibble-like output. } \details{ -All options are available via the \code{pillar_options} list. -The elements of this list are combined getter/setter functions. -Calling a function without arguments returns the current value, -by providing an argument the current value is set and the old value -is returned, invisibly. -Setting \code{local = TRUE} enables the option for the duration of the -current stack frame via \code{\link[rlang:local_options]{rlang::local_options()}}. - -These options can also be set via \code{\link[=options]{options()}} and queried via \code{\link[=getOption]{getOption()}}. +These options can be set via \code{\link[=options]{options()}} and queried via \code{\link[=getOption]{getOption()}}. For this, add a \code{pillar.} prefix (the package name and a dot) to the option name. -Example: for an option \code{foo}, -\code{pillar_options$foo(value)} is equivalent to -\code{options(pillar.foo = value)}. +Example: for an option \code{foo}, use \code{options(pillar.foo = value)} to set it +and \code{getOption("pillar.foo")} to retrieve the current value (\code{NULL} means +that the default is used). } \section{Options for the pillar package}{ @@ -57,20 +49,20 @@ default 13. \examples{ # Default setting: -pillar_options$sigfig() +getOption("pillar.sigfig") pillar(1.234567) # Change for the duration of the session: -old <- pillar_options$sigfig(6) +old <- options(pillar.sigfig = 6) pillar(1.234567) # Change back to the original value: -pillar_options$sigfig(old) +options(old) pillar(1.234567) # Local scope: local({ - pillar_options$sigfig(6, local = TRUE) + rlang::local_options(pillar.sigfig = 6) pillar(1.234567) }) pillar(1.234567) From c6c335eda0e97d4b01948d295ccd1f1dbf37588d Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Mon, 26 Jul 2021 06:21:48 +0200 Subject: [PATCH 059/147] Tweak reference index --- _pkgdown.yml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/_pkgdown.yml b/_pkgdown.yml index a4fdb0c66..52d2b9634 100644 --- a/_pkgdown.yml +++ b/_pkgdown.yml @@ -43,7 +43,7 @@ reference: - char - title: Miscellaneous contents: - - options + - pillar_options - pillar-package navbar: From 019d653a725b8f43f2faac064b0e50658d7dd4cd Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Tue, 27 Jul 2021 04:03:32 +0200 Subject: [PATCH 060/147] Tweak --- R/options.R | 4 ++-- man/pillar_options.Rd | 4 ++-- 2 files changed, 4 insertions(+), 4 deletions(-) diff --git a/R/options.R b/R/options.R index b80192493..ce6b17c6d 100644 --- a/R/options.R +++ b/R/options.R @@ -5,8 +5,8 @@ #' These options can be set via [options()] and queried via [getOption()]. #' For this, add a `pillar.` prefix (the package name and a dot) to the option name. #' Example: for an option `foo`, use `options(pillar.foo = value)` to set it -#' and `getOption("pillar.foo")` to retrieve the current value (`NULL` means -#' that the default is used). +#' and `getOption("pillar.foo")` to retrieve the current value. +#' An option value of `NULL` means that the default is used. #' #' @examples #' # Default setting: diff --git a/man/pillar_options.Rd b/man/pillar_options.Rd index 992d7c540..f68d94fb8 100644 --- a/man/pillar_options.Rd +++ b/man/pillar_options.Rd @@ -17,8 +17,8 @@ Options that affect display of tibble-like output. These options can be set via \code{\link[=options]{options()}} and queried via \code{\link[=getOption]{getOption()}}. For this, add a \code{pillar.} prefix (the package name and a dot) to the option name. Example: for an option \code{foo}, use \code{options(pillar.foo = value)} to set it -and \code{getOption("pillar.foo")} to retrieve the current value (\code{NULL} means -that the default is used). +and \code{getOption("pillar.foo")} to retrieve the current value. +An option value of \code{NULL} means that the default is used. } \section{Options for the pillar package}{ From b06fe455fad5e04f4e91827d4c9750234d97a328 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Tue, 27 Jul 2021 04:20:09 +0200 Subject: [PATCH 061/147] Avoid format if the object is not exported --- R/options.R | 2 ++ man/pillar_options.Rd | 3 --- 2 files changed, 2 insertions(+), 3 deletions(-) diff --git a/R/options.R b/R/options.R index ce6b17c6d..b63a7b5f6 100644 --- a/R/options.R +++ b/R/options.R @@ -8,6 +8,8 @@ #' and `getOption("pillar.foo")` to retrieve the current value. #' An option value of `NULL` means that the default is used. #' +#' @format NULL +#' #' @examples #' # Default setting: #' getOption("pillar.sigfig") diff --git a/man/pillar_options.Rd b/man/pillar_options.Rd index f68d94fb8..e194f2638 100644 --- a/man/pillar_options.Rd +++ b/man/pillar_options.Rd @@ -4,9 +4,6 @@ \name{pillar_options} \alias{pillar_options} \title{Package options} -\format{ -An object of class \code{list} of length 8. -} \usage{ pillar_options } From 18a737fecf937f7483fe71c67aa5baf2751c76c5 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Tue, 27 Jul 2021 05:05:58 +0200 Subject: [PATCH 062/147] Add max_footer_lines option --- R/options.R | 6 ++++++ R/tbl-format-footer.R | 6 ++++-- 2 files changed, 10 insertions(+), 2 deletions(-) diff --git a/R/options.R b/R/options.R index b63a7b5f6..9327f6349 100644 --- a/R/options.R +++ b/R/options.R @@ -88,4 +88,10 @@ pillar_options <- list2( max_dec_width = make_option_impl( getOption("pillar.max_dec_width", default = 13L) ), + #' - `max_footer_lines`: The maximum number of lines in the footer, + #' default: `7`. Set to `Inf` to turn off truncation of footer lines, + #' the `max_extra_cols` option still limits the number of columns printed. + max_footer_lines = make_option_impl( + getOption("pillar.max_footer_lines", default = 7L) + ), ) diff --git a/R/tbl-format-footer.R b/R/tbl-format-footer.R index a3071a8d3..b0368dfbc 100644 --- a/R/tbl-format-footer.R +++ b/R/tbl-format-footer.R @@ -116,8 +116,10 @@ wrap_footer <- function(footer, setup) { # When asking for width = 80, use at most 79 characters max_extent <- setup$width - 1L - # FIXME: Make n_tiers configurable - tier_widths <- get_footer_tier_widths(footer, max_extent, n_tiers = Inf) + tier_widths <- get_footer_tier_widths( + footer, max_extent, + get_pillar_option_max_footer_lines() + ) # show optuput even if too wide widths <- pmin(get_extent(footer), max_extent - 4L) From 3d2d395a7debe49db5fad9a4720f7b9b60fe1635 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Tue, 27 Jul 2021 05:13:57 +0200 Subject: [PATCH 063/147] Reset all options when test starts --- tests/testthat/setup.R | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/tests/testthat/setup.R b/tests/testthat/setup.R index 50bd3d55c..a622aac94 100644 --- a/tests/testthat/setup.R +++ b/tests/testthat/setup.R @@ -6,4 +6,4 @@ rlang::with_options( ) # Override .Rprofile -options(pillar.bold = FALSE) +walk(pillar_options, do.call, list(NULL)) From 502222547babf7473cf22bb54d507facda49264d Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Tue, 27 Jul 2021 05:22:31 +0200 Subject: [PATCH 064/147] Fix ellipsis --- R/tbl-format-footer.R | 4 ++-- tests/testthat/_snaps/tbl-format-footer.md | 7 +------ 2 files changed, 3 insertions(+), 8 deletions(-) diff --git a/R/tbl-format-footer.R b/R/tbl-format-footer.R index b0368dfbc..1a6db9887 100644 --- a/R/tbl-format-footer.R +++ b/R/tbl-format-footer.R @@ -126,9 +126,9 @@ wrap_footer <- function(footer, setup) { wrap <- colonnade_compute_tiered_col_widths_df(widths, widths, tier_widths) # truncate output that doesn't fit - wrap <- wrap[wrap$tier != 0, ] + truncated <- anyNA(wrap$tier) split <- split(footer[wrap$id], wrap$tier) - if (nrow(wrap) < length(footer) && length(split) > 0) { + if (truncated && length(split) > 0) { split[[length(split)]] <- c(split[[length(split)]], cli::symbol$ellipsis) } split <- imap(split, function(x, y) c("#", if (y == 1) cli::symbol$ellipsis else " ", x)) diff --git a/tests/testthat/_snaps/tbl-format-footer.md b/tests/testthat/_snaps/tbl-format-footer.md index f3eb98026..741b7a86e 100644 --- a/tests/testthat/_snaps/tbl-format-footer.md +++ b/tests/testthat/_snaps/tbl-format-footer.md @@ -16,12 +16,7 @@ # i , j , # k , l , # m , n , - # o , p , - # q , r , - # s , t , - # u , v , - # w , x , - # y , z  + # o , p , ... # wrapping column names with spaces in the footer From 6aaa2afcb1f0488d564d88d8c9986215a6c27e7a Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Tue, 27 Jul 2021 05:14:18 +0200 Subject: [PATCH 065/147] Add test --- tests/testthat/_snaps/tbl-format-footer.md | 150 +++++++++++++++++++-- tests/testthat/test-tbl-format-footer.R | 24 ++++ 2 files changed, 165 insertions(+), 9 deletions(-) diff --git a/tests/testthat/_snaps/tbl-format-footer.md b/tests/testthat/_snaps/tbl-format-footer.md index 741b7a86e..723d04e2f 100644 --- a/tests/testthat/_snaps/tbl-format-footer.md +++ b/tests/testthat/_snaps/tbl-format-footer.md @@ -63,13 +63,145 @@ # d , e , f , g , h , i , j , # k , l , m , n , o , p , q , # r , s , t , u , v , w , x , - # y , z , a , b , c , d , e , - # f , g , h , i , j , k , l , - # m , n , o , p , q , r , s , - # t , u , v , w , x , y , z , - # a , b , c , d , e , f , g , - # h , i , j , k , l , m , n , - # o , p , q , r , s , t , u , - # v , w , x , y , z , a , b , - # c , d , e , f , g , ... + # y , z , a , b , c , d , ... + +# max_footer_lines option + + Code + new_footer_tbl("") + Output + # A data frame: 1 x 52 + aa ba ab bb ac bc ad bd ae be af bf ag + + 1 1 2 3 4 5 6 7 8 9 10 11 12 13 + # ... with 39 more variables: bg , ah , bh , ai , bi , + # aj , bj , ak , bk , al , bl , am , + # bm , an , bn , ao , bo , ap , bp , + # aq , bq , ar , br , as , bs , at , + # bt , au , bu , av , bv , aw , bw , + # ax , bx , ay , by , az , bz + Code + new_footer_tbl("prefix_") + Output + # A data frame: 1 x 52 + prefix_aa prefix_ba prefix_ab prefix_bb prefix_ac prefix_bc prefix_ad + + 1 1 2 3 4 5 6 7 + # ... with 45 more variables: prefix_bd , prefix_ae , + # prefix_be , prefix_af , prefix_bf , prefix_ag , + # prefix_bg , prefix_ah , prefix_bh , prefix_ai , + # prefix_bi , prefix_aj , prefix_bj , prefix_ak , + # prefix_bk , prefix_al , prefix_bl , prefix_am , + # prefix_bm , prefix_an , prefix_bn , prefix_ao , + # prefix_bo , prefix_ap , prefix_bp , prefix_aq , ... + Code + new_footer_tbl("a_very_long_prefix_") + Output + # A data frame: 1 x 52 + a_very_long_prefix_aa a_very_long_prefix_ba a_very_long_pref~ a_very_long_pre~ + + 1 1 2 3 4 + # ... with 48 more variables: a_very_long_prefix_ac , + # a_very_long_prefix_bc , a_very_long_prefix_ad , + # a_very_long_prefix_bd , a_very_long_prefix_ae , + # a_very_long_prefix_be , a_very_long_prefix_af , + # a_very_long_prefix_bf , a_very_long_prefix_ag , + # a_very_long_prefix_bg , a_very_long_prefix_ah , + # a_very_long_prefix_bh , a_very_long_prefix_ai , ... + Code + set_pillar_option_max_footer_lines(3) + new_footer_tbl("") + Output + # A data frame: 1 x 52 + aa ba ab bb ac bc ad bd ae be af bf ag + + 1 1 2 3 4 5 6 7 8 9 10 11 12 13 + # ... with 39 more variables: bg , ah , bh , ai , bi , + # aj , bj , ak , bk , al , bl , am , + # bm , an , bn , ao , bo , ap , bp , ... + Code + new_footer_tbl("prefix_") + Output + # A data frame: 1 x 52 + prefix_aa prefix_ba prefix_ab prefix_bb prefix_ac prefix_bc prefix_ad + + 1 1 2 3 4 5 6 7 + # ... with 45 more variables: prefix_bd , prefix_ae , + # prefix_be , prefix_af , prefix_bf , prefix_ag , + # prefix_bg , prefix_ah , prefix_bh , prefix_ai , ... + Code + new_footer_tbl("a_very_long_prefix_") + Output + # A data frame: 1 x 52 + a_very_long_prefix_aa a_very_long_prefix_ba a_very_long_pref~ a_very_long_pre~ + + 1 1 2 3 4 + # ... with 48 more variables: a_very_long_prefix_ac , + # a_very_long_prefix_bc , a_very_long_prefix_ad , + # a_very_long_prefix_bd , a_very_long_prefix_ae , ... + Code + set_pillar_option_max_footer_lines(Inf) + new_footer_tbl("") + Output + # A data frame: 1 x 52 + aa ba ab bb ac bc ad bd ae be af bf ag + + 1 1 2 3 4 5 6 7 8 9 10 11 12 13 + # ... with 39 more variables: bg , ah , bh , ai , bi , + # aj , bj , ak , bk , al , bl , am , + # bm , an , bn , ao , bo , ap , bp , + # aq , bq , ar , br , as , bs , at , + # bt , au , bu , av , bv , aw , bw , + # ax , bx , ay , by , az , bz + Code + new_footer_tbl("prefix_") + Output + # A data frame: 1 x 52 + prefix_aa prefix_ba prefix_ab prefix_bb prefix_ac prefix_bc prefix_ad + + 1 1 2 3 4 5 6 7 + # ... with 45 more variables: prefix_bd , prefix_ae , + # prefix_be , prefix_af , prefix_bf , prefix_ag , + # prefix_bg , prefix_ah , prefix_bh , prefix_ai , + # prefix_bi , prefix_aj , prefix_bj , prefix_ak , + # prefix_bk , prefix_al , prefix_bl , prefix_am , + # prefix_bm , prefix_an , prefix_bn , prefix_ao , + # prefix_bo , prefix_ap , prefix_bp , prefix_aq , + # prefix_bq , prefix_ar , prefix_br , prefix_as , + # prefix_bs , prefix_at , prefix_bt , prefix_au , + # prefix_bu , prefix_av , prefix_bv , prefix_aw , + # prefix_bw , prefix_ax , prefix_bx , prefix_ay , + # prefix_by , prefix_az , prefix_bz + Code + new_footer_tbl("a_very_long_prefix_") + Output + # A data frame: 1 x 52 + a_very_long_prefix_aa a_very_long_prefix_ba a_very_long_pref~ a_very_long_pre~ + + 1 1 2 3 4 + # ... with 48 more variables: a_very_long_prefix_ac , + # a_very_long_prefix_bc , a_very_long_prefix_ad , + # a_very_long_prefix_bd , a_very_long_prefix_ae , + # a_very_long_prefix_be , a_very_long_prefix_af , + # a_very_long_prefix_bf , a_very_long_prefix_ag , + # a_very_long_prefix_bg , a_very_long_prefix_ah , + # a_very_long_prefix_bh , a_very_long_prefix_ai , + # a_very_long_prefix_bi , a_very_long_prefix_aj , + # a_very_long_prefix_bj , a_very_long_prefix_ak , + # a_very_long_prefix_bk , a_very_long_prefix_al , + # a_very_long_prefix_bl , a_very_long_prefix_am , + # a_very_long_prefix_bm , a_very_long_prefix_an , + # a_very_long_prefix_bn , a_very_long_prefix_ao , + # a_very_long_prefix_bo , a_very_long_prefix_ap , + # a_very_long_prefix_bp , a_very_long_prefix_aq , + # a_very_long_prefix_bq , a_very_long_prefix_ar , + # a_very_long_prefix_br , a_very_long_prefix_as , + # a_very_long_prefix_bs , a_very_long_prefix_at , + # a_very_long_prefix_bt , a_very_long_prefix_au , + # a_very_long_prefix_bu , a_very_long_prefix_av , + # a_very_long_prefix_bv , a_very_long_prefix_aw , + # a_very_long_prefix_bw , a_very_long_prefix_ax , + # a_very_long_prefix_bx , a_very_long_prefix_ay , + # a_very_long_prefix_by , a_very_long_prefix_az , + # a_very_long_prefix_bz diff --git a/tests/testthat/test-tbl-format-footer.R b/tests/testthat/test-tbl-format-footer.R index 71b7c6ed0..47505c08b 100644 --- a/tests/testthat/test-tbl-format-footer.R +++ b/tests/testthat/test-tbl-format-footer.R @@ -25,3 +25,27 @@ test_that("overflow", { )) }) }) + +test_that("max_footer_lines option", { + new_footer_tbl <- function(prefix) { + names <- outer(letters[1:2], letters, paste0) + x <- setNames(as.list(seq_along(names)), paste0(prefix, names)) + new_tbl(x) + } + + expect_snapshot({ + new_footer_tbl("") + new_footer_tbl("prefix_") + new_footer_tbl("a_very_long_prefix_") + + set_pillar_option_max_footer_lines(3) + new_footer_tbl("") + new_footer_tbl("prefix_") + new_footer_tbl("a_very_long_prefix_") + + set_pillar_option_max_footer_lines(Inf) + new_footer_tbl("") + new_footer_tbl("prefix_") + new_footer_tbl("a_very_long_prefix_") + }) +}) From f9690548c8ce01ad765716dd87b9b29bfa7d0c89 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Mon, 26 Jul 2021 05:53:24 +0200 Subject: [PATCH 066/147] FSI and LRO --- R/ctl_colonnade.R | 8 +++++++- 1 file changed, 7 insertions(+), 1 deletion(-) diff --git a/R/ctl_colonnade.R b/R/ctl_colonnade.R index eb1989c38..109dcdaa8 100644 --- a/R/ctl_colonnade.R +++ b/R/ctl_colonnade.R @@ -80,6 +80,10 @@ pillar_format_tier <- function(pillars, widths, max_widths) { }) } +# Reference: https://www.w3.org/International/questions/qa-bidi-unicode-controls +fsi <- function(...) paste0("\u2068", ..., "\u2069") +lro <- function(...) paste0("\u202d", ..., "\u202c") + format_colonnade_tier_2 <- function(x) { "!!!!!DEBUG format_colonnade_tier_2(`v(x)`)" @@ -87,7 +91,9 @@ format_colonnade_tier_2 <- function(x) { return(character()) } - exec(paste, !!!x) + x <- map(x, fsi) + out <- exec(paste, !!!x) + lro(out) } new_colonnade_body <- function(x, extra_cols) { From 401c3cd1fda901b8c4e51dec345eb24d11521844 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Tue, 27 Jul 2021 05:42:42 +0200 Subject: [PATCH 067/147] Add bidi option --- R/ctl_colonnade.R | 23 +++++++++++++++-------- R/options.R | 9 +++++++++ 2 files changed, 24 insertions(+), 8 deletions(-) diff --git a/R/ctl_colonnade.R b/R/ctl_colonnade.R index 109dcdaa8..820792365 100644 --- a/R/ctl_colonnade.R +++ b/R/ctl_colonnade.R @@ -46,7 +46,7 @@ ctl_colonnade <- function(x, has_row_id = TRUE, width = NULL, controller = new_t flat_tiers <- map(flat_tiers, function(.x) c(rowid_formatted, .x)) } - out <- map(flat_tiers, format_colonnade_tier_2) + out <- map(flat_tiers, format_colonnade_tier_2, bidi = get_pillar_option_bidi()) extra_cols <- as.list(x)[seq2(length(pillars) + 1L, nc)] new_colonnade_body(out, extra_cols = extra_cols) @@ -81,19 +81,26 @@ pillar_format_tier <- function(pillars, widths, max_widths) { } # Reference: https://www.w3.org/International/questions/qa-bidi-unicode-controls -fsi <- function(...) paste0("\u2068", ..., "\u2069") -lro <- function(...) paste0("\u202d", ..., "\u202c") +fsi <- function(x) { + paste0("\u2068", x, "\u2069") +} -format_colonnade_tier_2 <- function(x) { - "!!!!!DEBUG format_colonnade_tier_2(`v(x)`)" +lro <- function(x) { + paste0("\u202d", x, "\u202c") +} +format_colonnade_tier_2 <- function(x, bidi = FALSE) { if (length(x) == 0) { return(character()) } - x <- map(x, fsi) - out <- exec(paste, !!!x) - lro(out) + if (bidi) { + x <- map(x, fsi) + out <- exec(paste, !!!x) + lro(out) + } else { + exec(paste, !!!x) + } } new_colonnade_body <- function(x, extra_cols) { diff --git a/R/options.R b/R/options.R index 9327f6349..af10c5266 100644 --- a/R/options.R +++ b/R/options.R @@ -94,4 +94,13 @@ pillar_options <- list2( max_footer_lines = make_option_impl( getOption("pillar.max_footer_lines", default = 7L) ), + #' - `bidi`: Set to `TRUE` for experimental support for bidirectional scripts. + #' Default: `FALSE`. When this option is set, "left right override" + #' and "first strong isolate" + #' [Unicode controls](https://www.w3.org/International/questions/qa-bidi-unicode-controls) + #' are inserted to ensure that text appears in its intended direction + #' and that the column headings correspond to the correct columns. + bidi = make_option_impl( + getOption("pillar.bidi", default = FALSE) + ), ) From e5f13cf6b6000f4ef62db07f5ad6904679bec4d5 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Wed, 28 Jul 2021 04:20:02 +0200 Subject: [PATCH 068/147] Bump version to 1.6.1.9004 --- DESCRIPTION | 2 +- NEWS.md | 7 +++++++ 2 files changed, 8 insertions(+), 1 deletion(-) diff --git a/DESCRIPTION b/DESCRIPTION index be791668e..62b61b61f 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -1,6 +1,6 @@ Package: pillar Title: Coloured Formatting for Columns -Version: 1.6.1.9003 +Version: 1.6.1.9004 Authors@R: c(person(given = "Kirill", family = "M\u00fcller", diff --git a/NEWS.md b/NEWS.md index 1e664ae1b..24cd10e6d 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,5 +1,12 @@ +# pillar 1.6.1.9004 + +- New `pillar.bidi` option. When active, control characters are inserted to improve display of data with right-to-left text (#333). +- The new `pillar.max_footer_lines` option (default: 7) allows controlling the maximum number of footer lines shown. It is applied in addition to the existing `tibble.max_extra_cols` option (#263). +- Consistent definition of all options in one place, with internal accessors (#339). + + # pillar 1.6.1.9003 - `obj_sum()` no longer calls `type_sum()` for vectors since pillar v1.6.1, this is now documented (#321). From c72aeaa4ee1432457764a92267c419fbcfa72a41 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Wed, 28 Jul 2021 04:44:37 +0200 Subject: [PATCH 069/147] Create pillar options for existing tibble options --- R/glimpse.R | 4 ++-- R/options.R | 32 ++++++++++++++++++++++++--- R/tibble-opt.R | 50 ++++++++++++++----------------------------- man/pillar_options.Rd | 28 +++++++++++++++++++++++- 4 files changed, 74 insertions(+), 40 deletions(-) diff --git a/R/glimpse.R b/R/glimpse.R index d8a97c1d5..ce8aa8dfe 100644 --- a/R/glimpse.R +++ b/R/glimpse.R @@ -34,10 +34,10 @@ glimpse <- function(x, width = NULL, ...) { #' @export glimpse.tbl <- function(x, width = NULL, ...) { - width <- get_width_glimpse(width) - if (!is.finite(width)) { + if (!is.null(width) && !is.finite(width)) { abort("`width` must be finite.") } + width <- get_width_glimpse(width) cli::cat_line("Rows: ", big_mark(nrow(x))) diff --git a/R/options.R b/R/options.R index af10c5266..318956333 100644 --- a/R/options.R +++ b/R/options.R @@ -31,6 +31,30 @@ #' pillar(1.234567) #' @section Options for the pillar package: pillar_options <- list2( + #' - `print_max`: Maximum number of rows printed, default: `20`. + #' Set to \code{Inf} to always print all rows. + #' For compatibility reasons, `getOption("tibble.print_max")` and + #' `getOption("dplyr.print_max")` are also consulted, + #' this will be soft-deprecated in pillar v2.0.0. + print_max = make_option_impl( + getOption("pillar.print_max", default = tibble_opt("print_max", 20L)) + ), + #' - `print_min`: Number of rows printed if the table has more than + #' `print_max` rows, default: `10`. + #' For compatibility reasons, `getOption("tibble.print_min")` and + #' `getOption("dplyr.print_min")` are also consulted, + #' this will be soft-deprecated in pillar v2.0.0.. + print_min = make_option_impl( + getOption("pillar.print_min", default = tibble_opt("print_min", 10L)) + ), + #' - `width`: `tibble.width`: Output width. Default: `NULL` + #' (use `getOption("width")`). + #' For compatibility reasons, `getOption("tibble.width")` and + #' `getOption("dplyr.width")` are also consulted, + #' this will be soft-deprecated in pillar v2.0.0.. + width = make_option_impl( + getOption("pillar.width", default = tibble_opt("width", getOption("width"))) + ), bold = make_option_impl( getOption("pillar.bold", default = FALSE) ), @@ -84,13 +108,15 @@ pillar_options <- list2( min_chars }), #' - `max_dec_width`: The maximum allowed width for decimal notation, - #' default 13. + #' default: `13`. max_dec_width = make_option_impl( getOption("pillar.max_dec_width", default = 13L) ), #' - `max_footer_lines`: The maximum number of lines in the footer, - #' default: `7`. Set to `Inf` to turn off truncation of footer lines, - #' the `max_extra_cols` option still limits the number of columns printed. + #' default: `7`. Set to `Inf` to turn off truncation of footer lines. + #' The legacy `getOption("tibble.max_extra_cols")` option + #' still limits the number of columns printed, + #' this will be soft-deprecated in pillar v2.0.0. max_footer_lines = make_option_impl( getOption("pillar.max_footer_lines", default = 7L) ), diff --git a/R/tibble-opt.R b/R/tibble-opt.R index 12a7116c1..a6ec66a04 100644 --- a/R/tibble-opt.R +++ b/R/tibble-opt.R @@ -1,28 +1,17 @@ -## user-facing docs kept in `formatting` topic; see utils-format.R -## Exception: tibble.view_max, in `tibble-package` -op.tibble <- list( - tibble.print_max = 20L, - tibble.print_min = 10L, - tibble.width = NULL, - tibble.max_extra_cols = 100L -) - -tibble_opt <- function(x, dplyr = TRUE) { +tibble_opt <- function(x, default = op.tibble[[x]]) { x_tibble <- paste0("tibble.", x) res <- getOption(x_tibble) if (!is.null(res)) { return(res) } - if (dplyr) { - x_dplyr <- paste0("dplyr.", x) - res <- getOption(x_dplyr) - if (!is.null(res)) { - return(res) - } + x_dplyr <- paste0("dplyr.", x) + res <- getOption(x_dplyr) + if (!is.null(res)) { + return(res) } - op.tibble[[x_tibble]] + default } get_width_print <- function(width) { @@ -30,25 +19,17 @@ get_width_print <- function(width) { return(width) } - width <- tibble_opt("width") - if (!is.null(width)) { - return(width) - } - - getOption("width") + get_pillar_option_width() } get_width_glimpse <- function(width) { - if (!is.null(width)) { - return(width) - } + width <- get_width_print(width) - width <- tibble_opt("width") - if (!is.null(width) && is.finite(width)) { - return(width) + if (is.finite(width)) { + width + } else { + getOption("width") } - - getOption("width") } get_n_print <- function(n, rows) { @@ -56,17 +37,18 @@ get_n_print <- function(n, rows) { return(n) } - if (is.na(rows) || rows > tibble_opt("print_max")) { - tibble_opt("print_min") + if (is.na(rows) || rows > get_pillar_option_print_max()) { + get_pillar_option_print_min() } else { rows } } get_max_extra_cols <- function(max_extra_cols) { + # FIXME: Deprecate if (!is.null(max_extra_cols) && max_extra_cols >= 0) { return(max_extra_cols) } - tibble_opt("max_extra_cols") + tibble_opt("max_extra_cols", 100L) } diff --git a/man/pillar_options.Rd b/man/pillar_options.Rd index e194f2638..1204bbc64 100644 --- a/man/pillar_options.Rd +++ b/man/pillar_options.Rd @@ -20,6 +20,21 @@ An option value of \code{NULL} means that the default is used. \section{Options for the pillar package}{ \itemize{ +\item \code{print_max}: Maximum number of rows printed, default: \code{20}. +Set to \code{Inf} to always print all rows. +For compatibility reasons, \code{getOption("tibble.print_max")} and +\code{getOption("dplyr.print_max")} are also consulted, +this will be soft-deprecated in pillar v2.0.0. +\item \code{print_min}: Number of rows printed if the table has more than +\code{print_max} rows, default: \code{10}. +For compatibility reasons, \code{getOption("tibble.print_min")} and +\code{getOption("dplyr.print_min")} are also consulted, +this will be soft-deprecated in pillar v2.0.0.. +\item \code{width}: \code{tibble.width}: Output width. Default: \code{NULL} +(use \code{getOption("width")}). +For compatibility reasons, \code{getOption("tibble.width")} and +\code{getOption("dplyr.width")} are also consulted, +this will be soft-deprecated in pillar v2.0.0.. \item \code{bold}: Use bold font, e.g. for column headers? This currently defaults to \code{FALSE}, because many terminal fonts have poor support for bold fonts. @@ -40,7 +55,18 @@ display character columns, default: \code{3}. Character columns may be truncated up to that width to save horizontal space. Set to \code{Inf} to turn off truncation of character columns. \item \code{max_dec_width}: The maximum allowed width for decimal notation, -default 13. +default: \code{13}. +\item \code{max_footer_lines}: The maximum number of lines in the footer, +default: \code{7}. Set to \code{Inf} to turn off truncation of footer lines. +The legacy \code{getOption("tibble.max_extra_cols")} option +still limits the number of columns printed, +this will be soft-deprecated in pillar v2.0.0. +\item \code{bidi}: Set to \code{TRUE} for experimental support for bidirectional scripts. +Default: \code{FALSE}. When this option is set, "left right override" +and "first strong isolate" +\href{https://www.w3.org/International/questions/qa-bidi-unicode-controls}{Unicode controls} +are inserted to ensure that text appears in its intended direction +and that the column headings correspond to the correct columns. } } From cf7d6f10b9c9fb8d1cae7ae630a154ff09fccc43 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Wed, 28 Jul 2021 04:57:51 +0200 Subject: [PATCH 070/147] Link to pillar_options --- R/glimpse.R | 5 +++-- R/options.R | 4 +++- R/styles.R | 12 +++++++----- R/tbl-format.R | 10 ++++------ man/format_tbl.Rd | 10 ++++------ man/glimpse.Rd | 5 +++-- man/pillar_options.Rd | 4 +++- man/style_subtle.Rd | 12 +++++++----- 8 files changed, 34 insertions(+), 28 deletions(-) diff --git a/R/glimpse.R b/R/glimpse.R index ce8aa8dfe..2d6acb014 100644 --- a/R/glimpse.R +++ b/R/glimpse.R @@ -16,8 +16,9 @@ #' `data.frames`, and a default method that calls [str()]. #' #' @param x An object to glimpse at. -#' @param width Width of output: defaults to the setting of the option -#' `tibble.width` (if finite) or the width of the console. +#' @param width Width of output: defaults to the setting of the +#' [`width` option][pillar_options] (if finite) +#' or the width of the console. #' @param ... Unused, for extensibility. #' @return x original x is (invisibly) returned, allowing `glimpse()` to be #' used within a data pipe line. diff --git a/R/options.R b/R/options.R index 318956333..f90614ba0 100644 --- a/R/options.R +++ b/R/options.R @@ -49,9 +49,11 @@ pillar_options <- list2( ), #' - `width`: `tibble.width`: Output width. Default: `NULL` #' (use `getOption("width")`). + #' This can be larger than `getOption("width")`, in this case the output + #' of the table's body is distributed over multiple tiers for wide tables. #' For compatibility reasons, `getOption("tibble.width")` and #' `getOption("dplyr.width")` are also consulted, - #' this will be soft-deprecated in pillar v2.0.0.. + #' this will be soft-deprecated in pillar v2.0.0. width = make_option_impl( getOption("pillar.width", default = tibble_opt("width", getOption("width"))) ), diff --git a/R/styles.R b/R/styles.R index cdb183440..69a1afd5f 100644 --- a/R/styles.R +++ b/R/styles.R @@ -14,7 +14,7 @@ keep_empty <- function(fun) { #' Functions that allow implementers of formatters for custom data types to #' maintain a consistent style with the default data types. #' -#' `style_subtle()` is affected by the `pillar.subtle` option. +#' `style_subtle()` is affected by the [`pillar.subtle` option][pillar_options]. #' #' @param x The character vector to style. #' @export @@ -32,8 +32,9 @@ style_subtle <- keep_empty(function(x) { #' @rdname style_subtle #' @details -#' `style_subtle_num()` is affected by the `pillar.subtle_num` option, which is -#' `FALSE` by default. +#' `style_subtle_num()` is affected by the +#' [`pillar.subtle_num` option][pillar_options], +#' which is `FALSE` by default. #' #' @export #' @examples @@ -60,7 +61,8 @@ style_spark_na <- function(x) { } #' @details -#' `style_bold()` is affected by the `pillar.bold` option. +#' `style_bold()` is affected by the [`pillar.bold` option][pillar_options], +#' which is `FALSE` by default. #' #' @rdname style_subtle #' @export @@ -83,7 +85,7 @@ style_na <- function(x) { } #' @details -#' `style_neg()` is affected by the `pillar.neg` option. +#' `style_neg()` is affected by the [`pillar.neg` option][pillar_options]. #' #' @rdname style_subtle #' @export diff --git a/R/tbl-format.R b/R/tbl-format.R index 886f87f99..d9354299b 100644 --- a/R/tbl-format.R +++ b/R/tbl-format.R @@ -25,13 +25,11 @@ #' @param x Object to format or print. #' @param ... Passed on to [tbl_format_setup()]. #' @param n Number of rows to show. If `NULL`, the default, will print all rows -#' if less than option `tibble.print_max`. Otherwise, will print -#' `tibble.print_min` rows. +#' if less than the [`print_max` option][pillar_options]. +#' Otherwise, will print as many rows as specified by the +#' [`print_min` option][pillar_options]. #' @param width Width of text output to generate. This defaults to `NULL`, which -#' means use `getOption("tibble.width")` or (if also `NULL`) -#' `getOption("width")`; the latter displays only the columns that fit on one -#' screen. You can also set `options(tibble.width = Inf)` to override this -#' default and always print all columns. +#' means use the [`width` option][pillar_options]. #' @param n_extra Number of extra columns to print abbreviated information for, #' if the width is too small for the entire tibble. If `NULL`, the default, #' the value of the [`tibble.max_extra_cols`][tibble::tibble-package] option is used. diff --git a/man/format_tbl.Rd b/man/format_tbl.Rd index 944eb0b81..678f1b539 100644 --- a/man/format_tbl.Rd +++ b/man/format_tbl.Rd @@ -14,16 +14,14 @@ \item{x}{Object to format or print.} \item{width}{Width of text output to generate. This defaults to \code{NULL}, which -means use \code{getOption("tibble.width")} or (if also \code{NULL}) -\code{getOption("width")}; the latter displays only the columns that fit on one -screen. You can also set \code{options(tibble.width = Inf)} to override this -default and always print all columns.} +means use the \link[=pillar_options]{\code{width} option}.} \item{...}{Passed on to \code{\link[=tbl_format_setup]{tbl_format_setup()}}.} \item{n}{Number of rows to show. If \code{NULL}, the default, will print all rows -if less than option \code{tibble.print_max}. Otherwise, will print -\code{tibble.print_min} rows.} +if less than the \link[=pillar_options]{\code{print_max} option}. +Otherwise, will print as many rows as specified by the +\link[=pillar_options]{\code{print_min} option}.} \item{n_extra}{Number of extra columns to print abbreviated information for, if the width is too small for the entire tibble. If \code{NULL}, the default, diff --git a/man/glimpse.Rd b/man/glimpse.Rd index b2b61774d..5a311ead9 100644 --- a/man/glimpse.Rd +++ b/man/glimpse.Rd @@ -9,8 +9,9 @@ glimpse(x, width = NULL, ...) \arguments{ \item{x}{An object to glimpse at.} -\item{width}{Width of output: defaults to the setting of the option -\code{tibble.width} (if finite) or the width of the console.} +\item{width}{Width of output: defaults to the setting of the +\link[=pillar_options]{\code{width} option} (if finite) +or the width of the console.} \item{...}{Unused, for extensibility.} } diff --git a/man/pillar_options.Rd b/man/pillar_options.Rd index 1204bbc64..0f361dc28 100644 --- a/man/pillar_options.Rd +++ b/man/pillar_options.Rd @@ -32,9 +32,11 @@ For compatibility reasons, \code{getOption("tibble.print_min")} and this will be soft-deprecated in pillar v2.0.0.. \item \code{width}: \code{tibble.width}: Output width. Default: \code{NULL} (use \code{getOption("width")}). +This can be larger than \code{getOption("width")}, in this case the output +of the table's body is distributed over multiple tiers for wide tables. For compatibility reasons, \code{getOption("tibble.width")} and \code{getOption("dplyr.width")} are also consulted, -this will be soft-deprecated in pillar v2.0.0.. +this will be soft-deprecated in pillar v2.0.0. \item \code{bold}: Use bold font, e.g. for column headers? This currently defaults to \code{FALSE}, because many terminal fonts have poor support for bold fonts. diff --git a/man/style_subtle.Rd b/man/style_subtle.Rd index c1117c358..0e18faff4 100644 --- a/man/style_subtle.Rd +++ b/man/style_subtle.Rd @@ -32,14 +32,16 @@ Functions that allow implementers of formatters for custom data types to maintain a consistent style with the default data types. } \details{ -\code{style_subtle()} is affected by the \code{pillar.subtle} option. +\code{style_subtle()} is affected by the \link[=pillar_options]{\code{pillar.subtle} option}. -\code{style_subtle_num()} is affected by the \code{pillar.subtle_num} option, which is -\code{FALSE} by default. +\code{style_subtle_num()} is affected by the +\link[=pillar_options]{\code{pillar.subtle_num} option}, +which is \code{FALSE} by default. -\code{style_bold()} is affected by the \code{pillar.bold} option. +\code{style_bold()} is affected by the \link[=pillar_options]{\code{pillar.bold} option}, +which is \code{FALSE} by default. -\code{style_neg()} is affected by the \code{pillar.neg} option. +\code{style_neg()} is affected by the \link[=pillar_options]{\code{pillar.neg} option}. } \examples{ style_num( From ea5ced61ca8a27398531cf8e3419259f4192ba1b Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Wed, 28 Jul 2021 05:00:25 +0200 Subject: [PATCH 071/147] Cleanup --- R/options.R | 2 +- man/pillar_options.Rd | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/R/options.R b/R/options.R index f90614ba0..85e309ac4 100644 --- a/R/options.R +++ b/R/options.R @@ -47,7 +47,7 @@ pillar_options <- list2( print_min = make_option_impl( getOption("pillar.print_min", default = tibble_opt("print_min", 10L)) ), - #' - `width`: `tibble.width`: Output width. Default: `NULL` + #' - `width`: Output width. Default: `NULL` #' (use `getOption("width")`). #' This can be larger than `getOption("width")`, in this case the output #' of the table's body is distributed over multiple tiers for wide tables. diff --git a/man/pillar_options.Rd b/man/pillar_options.Rd index 0f361dc28..db5b56710 100644 --- a/man/pillar_options.Rd +++ b/man/pillar_options.Rd @@ -30,7 +30,7 @@ this will be soft-deprecated in pillar v2.0.0. For compatibility reasons, \code{getOption("tibble.print_min")} and \code{getOption("dplyr.print_min")} are also consulted, this will be soft-deprecated in pillar v2.0.0.. -\item \code{width}: \code{tibble.width}: Output width. Default: \code{NULL} +\item \code{width}: Output width. Default: \code{NULL} (use \code{getOption("width")}). This can be larger than \code{getOption("width")}, in this case the output of the table's body is distributed over multiple tiers for wide tables. From 711d94e7abfab36748fa00fe809f140b858140ff Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Wed, 28 Jul 2021 05:07:49 +0200 Subject: [PATCH 072/147] Reorg --- R/options.R | 20 ++++++++++++++------ man/pillar_options.Rd | 10 +++++----- 2 files changed, 19 insertions(+), 11 deletions(-) diff --git a/R/options.R b/R/options.R index 85e309ac4..6ca97b894 100644 --- a/R/options.R +++ b/R/options.R @@ -57,22 +57,30 @@ pillar_options <- list2( width = make_option_impl( getOption("pillar.width", default = tibble_opt("width", getOption("width"))) ), - bold = make_option_impl( - getOption("pillar.bold", default = FALSE) + #' - `max_footer_lines`: The maximum number of lines in the footer, + #' default: `7`. Set to `Inf` to turn off truncation of footer lines. + #' The legacy `getOption("tibble.max_extra_cols")` option + #' still limits the number of columns printed, + #' this will be soft-deprecated in pillar v2.0.0. + max_footer_lines = make_option_impl( + getOption("pillar.max_footer_lines", default = 7L) ), #' - `bold`: Use bold font, e.g. for column headers? This currently #' defaults to `FALSE`, because many terminal fonts have poor support for #' bold fonts. - subtle = make_option_impl( - getOption("pillar.subtle", default = TRUE) + bold = make_option_impl( + getOption("pillar.bold", default = FALSE) ), #' - `subtle`: Use subtle style, e.g. for row numbers and data types? #' Default: `TRUE`. - subtle_num = make_option_impl( - getOption("pillar.subtle_num", default = FALSE) + subtle = make_option_impl( + getOption("pillar.subtle", default = TRUE) ), #' - `subtle_num`: Use subtle style for insignificant digits? Default: #' `FALSE`, is also affected by the `subtle` option. + subtle_num = make_option_impl( + getOption("pillar.subtle_num", default = FALSE) + ), #' - `neg`: Highlight negative numbers? Default: `TRUE`. neg = make_option_impl( getOption("pillar.neg", default = TRUE) diff --git a/man/pillar_options.Rd b/man/pillar_options.Rd index db5b56710..4f89a4a67 100644 --- a/man/pillar_options.Rd +++ b/man/pillar_options.Rd @@ -37,6 +37,11 @@ of the table's body is distributed over multiple tiers for wide tables. For compatibility reasons, \code{getOption("tibble.width")} and \code{getOption("dplyr.width")} are also consulted, this will be soft-deprecated in pillar v2.0.0. +\item \code{max_footer_lines}: The maximum number of lines in the footer, +default: \code{7}. Set to \code{Inf} to turn off truncation of footer lines. +The legacy \code{getOption("tibble.max_extra_cols")} option +still limits the number of columns printed, +this will be soft-deprecated in pillar v2.0.0. \item \code{bold}: Use bold font, e.g. for column headers? This currently defaults to \code{FALSE}, because many terminal fonts have poor support for bold fonts. @@ -58,11 +63,6 @@ truncated up to that width to save horizontal space. Set to \code{Inf} to turn off truncation of character columns. \item \code{max_dec_width}: The maximum allowed width for decimal notation, default: \code{13}. -\item \code{max_footer_lines}: The maximum number of lines in the footer, -default: \code{7}. Set to \code{Inf} to turn off truncation of footer lines. -The legacy \code{getOption("tibble.max_extra_cols")} option -still limits the number of columns printed, -this will be soft-deprecated in pillar v2.0.0. \item \code{bidi}: Set to \code{TRUE} for experimental support for bidirectional scripts. Default: \code{FALSE}. When this option is set, "left right override" and "first strong isolate" From 8e166c6d91cd47c169b3f38293a1485fb3c688a4 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Wed, 28 Jul 2021 05:19:03 +0200 Subject: [PATCH 073/147] Tweak link --- R/tbl-format-setup.R | 6 ++++-- man/tbl_format_setup.Rd | 6 ++++-- 2 files changed, 8 insertions(+), 4 deletions(-) diff --git a/R/tbl-format-setup.R b/R/tbl-format-setup.R index ae0b3b268..e6a7f0ca3 100644 --- a/R/tbl-format-setup.R +++ b/R/tbl-format-setup.R @@ -43,11 +43,13 @@ #' Extra arguments to [print.tbl()] or [format.tbl()]. #' @param n #' Actual number of rows to print. -#' No [option]s should be considered by implementations of this method. +#' No [option][pillar_option]s should be considered +#' by implementations of this method. #' @param max_extra_cols #' Number of columns to print abbreviated information for, #' if the width is too small for the entire tibble. -#' No [option]s should be considered by implementations of this method. +#' No [option][pillar_option]s should be considered +#' by implementations of this method. #' #' @return #' An object that can be passed as `setup` argument to diff --git a/man/tbl_format_setup.Rd b/man/tbl_format_setup.Rd index 049a5a6f3..bbf52790d 100644 --- a/man/tbl_format_setup.Rd +++ b/man/tbl_format_setup.Rd @@ -18,11 +18,13 @@ This argument is mandatory for all implementations of this method.} \item{...}{Extra arguments to \code{\link[=print.tbl]{print.tbl()}} or \code{\link[=format.tbl]{format.tbl()}}.} \item{n}{Actual number of rows to print. -No \link{option}s should be considered by implementations of this method.} +No \link[=pillar_option]{option}s should be considered +by implementations of this method.} \item{max_extra_cols}{Number of columns to print abbreviated information for, if the width is too small for the entire tibble. -No \link{option}s should be considered by implementations of this method.} +No \link[=pillar_option]{option}s should be considered +by implementations of this method.} } \value{ An object that can be passed as \code{setup} argument to From 9cdd824c8d333d85bbe92aec497e1195b7dcacf2 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Wed, 28 Jul 2021 05:20:16 +0200 Subject: [PATCH 074/147] Remove dead --- R/tibble-opt.R | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/R/tibble-opt.R b/R/tibble-opt.R index a6ec66a04..70cf7a8b9 100644 --- a/R/tibble-opt.R +++ b/R/tibble-opt.R @@ -1,4 +1,4 @@ -tibble_opt <- function(x, default = op.tibble[[x]]) { +tibble_opt <- function(x, default) { x_tibble <- paste0("tibble.", x) res <- getOption(x_tibble) if (!is.null(res)) { From 459da52ce2e8b126704c204ce32450a8099b64e1 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Wed, 28 Jul 2021 05:20:55 +0200 Subject: [PATCH 075/147] Integrate max_extra_cols --- R/options.R | 20 +++++++++----------- R/tbl-format.R | 4 ++-- R/tibble-opt.R | 2 +- man/format_tbl.Rd | 4 ++-- man/pillar_options.Rd | 9 ++++++--- 5 files changed, 20 insertions(+), 19 deletions(-) diff --git a/R/options.R b/R/options.R index 6ca97b894..66fed35ca 100644 --- a/R/options.R +++ b/R/options.R @@ -59,12 +59,18 @@ pillar_options <- list2( ), #' - `max_footer_lines`: The maximum number of lines in the footer, #' default: `7`. Set to `Inf` to turn off truncation of footer lines. - #' The legacy `getOption("tibble.max_extra_cols")` option - #' still limits the number of columns printed, - #' this will be soft-deprecated in pillar v2.0.0. + #' The `max_extra_cols` option still limits + #' the number of columns printed. max_footer_lines = make_option_impl( getOption("pillar.max_footer_lines", default = 7L) ), + #' - `max_extra_cols`: The maximum number of columns printed in the footer, + #' default: `100`. Set to `Inf` to show all columns. + #' Set the more predictable `max_footer_lines` to control the number + #' of footer lines instead. + max_extra_cols = make_option_impl( + getOption("pillar.max_extra_cols", default = tibble_opt("max_extra_cols", 100L)) + ), #' - `bold`: Use bold font, e.g. for column headers? This currently #' defaults to `FALSE`, because many terminal fonts have poor support for #' bold fonts. @@ -122,14 +128,6 @@ pillar_options <- list2( max_dec_width = make_option_impl( getOption("pillar.max_dec_width", default = 13L) ), - #' - `max_footer_lines`: The maximum number of lines in the footer, - #' default: `7`. Set to `Inf` to turn off truncation of footer lines. - #' The legacy `getOption("tibble.max_extra_cols")` option - #' still limits the number of columns printed, - #' this will be soft-deprecated in pillar v2.0.0. - max_footer_lines = make_option_impl( - getOption("pillar.max_footer_lines", default = 7L) - ), #' - `bidi`: Set to `TRUE` for experimental support for bidirectional scripts. #' Default: `FALSE`. When this option is set, "left right override" #' and "first strong isolate" diff --git a/R/tbl-format.R b/R/tbl-format.R index d9354299b..8dec92e26 100644 --- a/R/tbl-format.R +++ b/R/tbl-format.R @@ -31,8 +31,8 @@ #' @param width Width of text output to generate. This defaults to `NULL`, which #' means use the [`width` option][pillar_options]. #' @param n_extra Number of extra columns to print abbreviated information for, -#' if the width is too small for the entire tibble. If `NULL`, the default, -#' the value of the [`tibble.max_extra_cols`][tibble::tibble-package] option is used. +#' if the width is too small for the entire tibble. If `NULL`, +#' the [`max_extra_cols` option][pillar_options] is used. #' #' @name format_tbl #' @export diff --git a/R/tibble-opt.R b/R/tibble-opt.R index 70cf7a8b9..7165c4aa8 100644 --- a/R/tibble-opt.R +++ b/R/tibble-opt.R @@ -50,5 +50,5 @@ get_max_extra_cols <- function(max_extra_cols) { return(max_extra_cols) } - tibble_opt("max_extra_cols", 100L) + get_pillar_option_max_extra_cols() } diff --git a/man/format_tbl.Rd b/man/format_tbl.Rd index 678f1b539..abe81d59f 100644 --- a/man/format_tbl.Rd +++ b/man/format_tbl.Rd @@ -24,8 +24,8 @@ Otherwise, will print as many rows as specified by the \link[=pillar_options]{\code{print_min} option}.} \item{n_extra}{Number of extra columns to print abbreviated information for, -if the width is too small for the entire tibble. If \code{NULL}, the default, -the value of the \code{\link[tibble:tibble-package]{tibble.max_extra_cols}} option is used.} +if the width is too small for the entire tibble. If \code{NULL}, +the \link[=pillar_options]{\code{max_extra_cols} option} is used.} } \description{ These functions and methods are responsible for printing objects diff --git a/man/pillar_options.Rd b/man/pillar_options.Rd index 4f89a4a67..5d02a24b3 100644 --- a/man/pillar_options.Rd +++ b/man/pillar_options.Rd @@ -39,9 +39,12 @@ For compatibility reasons, \code{getOption("tibble.width")} and this will be soft-deprecated in pillar v2.0.0. \item \code{max_footer_lines}: The maximum number of lines in the footer, default: \code{7}. Set to \code{Inf} to turn off truncation of footer lines. -The legacy \code{getOption("tibble.max_extra_cols")} option -still limits the number of columns printed, -this will be soft-deprecated in pillar v2.0.0. +The \code{max_extra_cols} option still limits +the number of columns printed. +\item \code{max_extra_cols}: The maximum number of columns printed in the footer, +default: \code{100}. Set to \code{Inf} to show all columns. +Set the more predictable \code{max_footer_lines} to control the number +of footer lines instead. \item \code{bold}: Use bold font, e.g. for column headers? This currently defaults to \code{FALSE}, because many terminal fonts have poor support for bold fonts. From 5d6c175a9920f754cc8b348a528f20a8d504fe22 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Wed, 28 Jul 2021 05:21:16 +0200 Subject: [PATCH 076/147] table -> tibble --- R/options.R | 2 +- man/pillar_options.Rd | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/R/options.R b/R/options.R index 66fed35ca..bb8a58f3c 100644 --- a/R/options.R +++ b/R/options.R @@ -50,7 +50,7 @@ pillar_options <- list2( #' - `width`: Output width. Default: `NULL` #' (use `getOption("width")`). #' This can be larger than `getOption("width")`, in this case the output - #' of the table's body is distributed over multiple tiers for wide tables. + #' of the table's body is distributed over multiple tiers for wide tibbles. #' For compatibility reasons, `getOption("tibble.width")` and #' `getOption("dplyr.width")` are also consulted, #' this will be soft-deprecated in pillar v2.0.0. diff --git a/man/pillar_options.Rd b/man/pillar_options.Rd index 5d02a24b3..8f793b4b6 100644 --- a/man/pillar_options.Rd +++ b/man/pillar_options.Rd @@ -33,7 +33,7 @@ this will be soft-deprecated in pillar v2.0.0.. \item \code{width}: Output width. Default: \code{NULL} (use \code{getOption("width")}). This can be larger than \code{getOption("width")}, in this case the output -of the table's body is distributed over multiple tiers for wide tables. +of the table's body is distributed over multiple tiers for wide tibbles. For compatibility reasons, \code{getOption("tibble.width")} and \code{getOption("dplyr.width")} are also consulted, this will be soft-deprecated in pillar v2.0.0. From 6fc4ab264324961eb897887333f7a5c31d47a61a Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Wed, 28 Jul 2021 05:23:27 +0200 Subject: [PATCH 077/147] Double dot --- R/options.R | 2 +- man/pillar_options.Rd | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/R/options.R b/R/options.R index bb8a58f3c..96a4f7e37 100644 --- a/R/options.R +++ b/R/options.R @@ -43,7 +43,7 @@ pillar_options <- list2( #' `print_max` rows, default: `10`. #' For compatibility reasons, `getOption("tibble.print_min")` and #' `getOption("dplyr.print_min")` are also consulted, - #' this will be soft-deprecated in pillar v2.0.0.. + #' this will be soft-deprecated in pillar v2.0.0. print_min = make_option_impl( getOption("pillar.print_min", default = tibble_opt("print_min", 10L)) ), diff --git a/man/pillar_options.Rd b/man/pillar_options.Rd index 8f793b4b6..c601a9dfc 100644 --- a/man/pillar_options.Rd +++ b/man/pillar_options.Rd @@ -29,7 +29,7 @@ this will be soft-deprecated in pillar v2.0.0. \code{print_max} rows, default: \code{10}. For compatibility reasons, \code{getOption("tibble.print_min")} and \code{getOption("dplyr.print_min")} are also consulted, -this will be soft-deprecated in pillar v2.0.0.. +this will be soft-deprecated in pillar v2.0.0. \item \code{width}: Output width. Default: \code{NULL} (use \code{getOption("width")}). This can be larger than \code{getOption("width")}, in this case the output From c27e2e92f11c08c528c7dbdeb691618ada0a1b4a Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Wed, 28 Jul 2021 05:28:38 +0200 Subject: [PATCH 078/147] Fix link text --- R/glimpse.R | 2 +- R/styles.R | 6 +++--- R/tbl-format.R | 8 ++++---- man/format_tbl.Rd | 8 ++++---- man/glimpse.Rd | 2 +- man/style_subtle.Rd | 6 +++--- 6 files changed, 16 insertions(+), 16 deletions(-) diff --git a/R/glimpse.R b/R/glimpse.R index 2d6acb014..e8f612987 100644 --- a/R/glimpse.R +++ b/R/glimpse.R @@ -17,7 +17,7 @@ #' #' @param x An object to glimpse at. #' @param width Width of output: defaults to the setting of the -#' [`width` option][pillar_options] (if finite) +#' `width` [option][pillar_options] (if finite) #' or the width of the console. #' @param ... Unused, for extensibility. #' @return x original x is (invisibly) returned, allowing `glimpse()` to be diff --git a/R/styles.R b/R/styles.R index 69a1afd5f..b282e32ae 100644 --- a/R/styles.R +++ b/R/styles.R @@ -14,7 +14,7 @@ keep_empty <- function(fun) { #' Functions that allow implementers of formatters for custom data types to #' maintain a consistent style with the default data types. #' -#' `style_subtle()` is affected by the [`pillar.subtle` option][pillar_options]. +#' `style_subtle()` is affected by the `pillar.subtle` [option][pillar_options]. #' #' @param x The character vector to style. #' @export @@ -33,7 +33,7 @@ style_subtle <- keep_empty(function(x) { #' @rdname style_subtle #' @details #' `style_subtle_num()` is affected by the -#' [`pillar.subtle_num` option][pillar_options], +#' `pillar.subtle_num` [option][pillar_options], #' which is `FALSE` by default. #' #' @export @@ -61,7 +61,7 @@ style_spark_na <- function(x) { } #' @details -#' `style_bold()` is affected by the [`pillar.bold` option][pillar_options], +#' `style_bold()` is affected by the `pillar.bold` [option][pillar_options], #' which is `FALSE` by default. #' #' @rdname style_subtle diff --git a/R/tbl-format.R b/R/tbl-format.R index 8dec92e26..e4ccccb41 100644 --- a/R/tbl-format.R +++ b/R/tbl-format.R @@ -25,14 +25,14 @@ #' @param x Object to format or print. #' @param ... Passed on to [tbl_format_setup()]. #' @param n Number of rows to show. If `NULL`, the default, will print all rows -#' if less than the [`print_max` option][pillar_options]. +#' if less than the `print_max` [option][pillar_options]. #' Otherwise, will print as many rows as specified by the -#' [`print_min` option][pillar_options]. +#' `print_min` [option][pillar_options]. #' @param width Width of text output to generate. This defaults to `NULL`, which -#' means use the [`width` option][pillar_options]. +#' means use the `width` [option][pillar_options]. #' @param n_extra Number of extra columns to print abbreviated information for, #' if the width is too small for the entire tibble. If `NULL`, -#' the [`max_extra_cols` option][pillar_options] is used. +#' the `max_extra_cols` [option][pillar_options] is used. #' #' @name format_tbl #' @export diff --git a/man/format_tbl.Rd b/man/format_tbl.Rd index abe81d59f..6d170f70d 100644 --- a/man/format_tbl.Rd +++ b/man/format_tbl.Rd @@ -14,18 +14,18 @@ \item{x}{Object to format or print.} \item{width}{Width of text output to generate. This defaults to \code{NULL}, which -means use the \link[=pillar_options]{\code{width} option}.} +means use the \code{width} \link[=pillar_options]{option}.} \item{...}{Passed on to \code{\link[=tbl_format_setup]{tbl_format_setup()}}.} \item{n}{Number of rows to show. If \code{NULL}, the default, will print all rows -if less than the \link[=pillar_options]{\code{print_max} option}. +if less than the \code{print_max} \link[=pillar_options]{option}. Otherwise, will print as many rows as specified by the -\link[=pillar_options]{\code{print_min} option}.} +\code{print_min} \link[=pillar_options]{option}.} \item{n_extra}{Number of extra columns to print abbreviated information for, if the width is too small for the entire tibble. If \code{NULL}, -the \link[=pillar_options]{\code{max_extra_cols} option} is used.} +the \code{max_extra_cols} \link[=pillar_options]{option} is used.} } \description{ These functions and methods are responsible for printing objects diff --git a/man/glimpse.Rd b/man/glimpse.Rd index 5a311ead9..e5f306f11 100644 --- a/man/glimpse.Rd +++ b/man/glimpse.Rd @@ -10,7 +10,7 @@ glimpse(x, width = NULL, ...) \item{x}{An object to glimpse at.} \item{width}{Width of output: defaults to the setting of the -\link[=pillar_options]{\code{width} option} (if finite) +\code{width} \link[=pillar_options]{option} (if finite) or the width of the console.} \item{...}{Unused, for extensibility.} diff --git a/man/style_subtle.Rd b/man/style_subtle.Rd index 0e18faff4..6b9dda8c8 100644 --- a/man/style_subtle.Rd +++ b/man/style_subtle.Rd @@ -32,13 +32,13 @@ Functions that allow implementers of formatters for custom data types to maintain a consistent style with the default data types. } \details{ -\code{style_subtle()} is affected by the \link[=pillar_options]{\code{pillar.subtle} option}. +\code{style_subtle()} is affected by the \code{pillar.subtle} \link[=pillar_options]{option}. \code{style_subtle_num()} is affected by the -\link[=pillar_options]{\code{pillar.subtle_num} option}, +\code{pillar.subtle_num} \link[=pillar_options]{option}, which is \code{FALSE} by default. -\code{style_bold()} is affected by the \link[=pillar_options]{\code{pillar.bold} option}, +\code{style_bold()} is affected by the \code{pillar.bold} \link[=pillar_options]{option}, which is \code{FALSE} by default. \code{style_neg()} is affected by the \link[=pillar_options]{\code{pillar.neg} option}. From a09f5e67a393584433e824e3bb0e9495ef098f79 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Wed, 28 Jul 2021 05:43:21 +0200 Subject: [PATCH 079/147] Fix link text --- R/styles.R | 2 +- man/style_subtle.Rd | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/R/styles.R b/R/styles.R index b282e32ae..1d7d514d7 100644 --- a/R/styles.R +++ b/R/styles.R @@ -85,7 +85,7 @@ style_na <- function(x) { } #' @details -#' `style_neg()` is affected by the [`pillar.neg` option][pillar_options]. +#' `style_neg()` is affected by the `pillar.neg` [option][pillar_options]. #' #' @rdname style_subtle #' @export diff --git a/man/style_subtle.Rd b/man/style_subtle.Rd index 6b9dda8c8..75c7d134b 100644 --- a/man/style_subtle.Rd +++ b/man/style_subtle.Rd @@ -41,7 +41,7 @@ which is \code{FALSE} by default. \code{style_bold()} is affected by the \code{pillar.bold} \link[=pillar_options]{option}, which is \code{FALSE} by default. -\code{style_neg()} is affected by the \link[=pillar_options]{\code{pillar.neg} option}. +\code{style_neg()} is affected by the \code{pillar.neg} \link[=pillar_options]{option}. } \examples{ style_num( From 6c5128d5cef48e884739b9e965cf281e00f339f5 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Wed, 28 Jul 2021 05:44:39 +0200 Subject: [PATCH 080/147] Remove prefix --- R/styles.R | 6 +++--- man/style_subtle.Rd | 6 +++--- 2 files changed, 6 insertions(+), 6 deletions(-) diff --git a/R/styles.R b/R/styles.R index 1d7d514d7..c14e8c431 100644 --- a/R/styles.R +++ b/R/styles.R @@ -14,7 +14,7 @@ keep_empty <- function(fun) { #' Functions that allow implementers of formatters for custom data types to #' maintain a consistent style with the default data types. #' -#' `style_subtle()` is affected by the `pillar.subtle` [option][pillar_options]. +#' `style_subtle()` is affected by the `subtle` [option][pillar_options]. #' #' @param x The character vector to style. #' @export @@ -33,7 +33,7 @@ style_subtle <- keep_empty(function(x) { #' @rdname style_subtle #' @details #' `style_subtle_num()` is affected by the -#' `pillar.subtle_num` [option][pillar_options], +#' `subtle_num` [option][pillar_options], #' which is `FALSE` by default. #' #' @export @@ -61,7 +61,7 @@ style_spark_na <- function(x) { } #' @details -#' `style_bold()` is affected by the `pillar.bold` [option][pillar_options], +#' `style_bold()` is affected by the `bold` [option][pillar_options], #' which is `FALSE` by default. #' #' @rdname style_subtle diff --git a/man/style_subtle.Rd b/man/style_subtle.Rd index 75c7d134b..db3ec6bbe 100644 --- a/man/style_subtle.Rd +++ b/man/style_subtle.Rd @@ -32,13 +32,13 @@ Functions that allow implementers of formatters for custom data types to maintain a consistent style with the default data types. } \details{ -\code{style_subtle()} is affected by the \code{pillar.subtle} \link[=pillar_options]{option}. +\code{style_subtle()} is affected by the \code{subtle} \link[=pillar_options]{option}. \code{style_subtle_num()} is affected by the -\code{pillar.subtle_num} \link[=pillar_options]{option}, +\code{subtle_num} \link[=pillar_options]{option}, which is \code{FALSE} by default. -\code{style_bold()} is affected by the \code{pillar.bold} \link[=pillar_options]{option}, +\code{style_bold()} is affected by the \code{bold} \link[=pillar_options]{option}, which is \code{FALSE} by default. \code{style_neg()} is affected by the \code{pillar.neg} \link[=pillar_options]{option}. From 4e27a79d7f535c2eb87fec18df35295819ea0bfd Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Wed, 28 Jul 2021 06:09:10 +0200 Subject: [PATCH 081/147] Fix link --- R/tbl-format-setup.R | 4 ++-- man/tbl_format_setup.Rd | 4 ++-- 2 files changed, 4 insertions(+), 4 deletions(-) diff --git a/R/tbl-format-setup.R b/R/tbl-format-setup.R index e6a7f0ca3..12107b640 100644 --- a/R/tbl-format-setup.R +++ b/R/tbl-format-setup.R @@ -43,12 +43,12 @@ #' Extra arguments to [print.tbl()] or [format.tbl()]. #' @param n #' Actual number of rows to print. -#' No [option][pillar_option]s should be considered +#' No [options][pillar_options] should be considered #' by implementations of this method. #' @param max_extra_cols #' Number of columns to print abbreviated information for, #' if the width is too small for the entire tibble. -#' No [option][pillar_option]s should be considered +#' No [options][pillar_options] should be considered #' by implementations of this method. #' #' @return diff --git a/man/tbl_format_setup.Rd b/man/tbl_format_setup.Rd index bbf52790d..c810feacd 100644 --- a/man/tbl_format_setup.Rd +++ b/man/tbl_format_setup.Rd @@ -18,12 +18,12 @@ This argument is mandatory for all implementations of this method.} \item{...}{Extra arguments to \code{\link[=print.tbl]{print.tbl()}} or \code{\link[=format.tbl]{format.tbl()}}.} \item{n}{Actual number of rows to print. -No \link[=pillar_option]{option}s should be considered +No \link[=pillar_options]{options} should be considered by implementations of this method.} \item{max_extra_cols}{Number of columns to print abbreviated information for, if the width is too small for the entire tibble. -No \link[=pillar_option]{option}s should be considered +No \link[=pillar_options]{options} should be considered by implementations of this method.} } \value{ From cb82b4d5669c0b098c6c609ff60fece4b9853c2a Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Wed, 28 Jul 2021 06:29:10 +0200 Subject: [PATCH 082/147] Fix typo --- R/num.R | 4 ++-- man/num.Rd | 4 ++-- 2 files changed, 4 insertions(+), 4 deletions(-) diff --git a/R/num.R b/R/num.R index c9901d051..c35423bc5 100644 --- a/R/num.R +++ b/R/num.R @@ -40,9 +40,9 @@ #' using exponents that are a multiple of three. #' - `"si"`: Use SI notation, prefixes between `1e-24` and `1e24` are supported. #' @param fixed_exponent -#' Use the same fixed_exponent for all numbers in scientific, engineering or SI notation. +#' Use the same exponent for all numbers in scientific, engineering or SI notation. #' `-Inf` uses the smallest, `+Inf` the largest fixed_exponent present in the data. -#' The default is to use varying fixed_exponents. +#' The default is to use varying exponents. #' @export #' @examples #' # Display as a vector diff --git a/man/num.Rd b/man/num.Rd index b78b13a24..3b630dd60 100644 --- a/man/num.Rd +++ b/man/num.Rd @@ -60,9 +60,9 @@ using exponents that are a multiple of three. \item \code{"si"}: Use SI notation, prefixes between \code{1e-24} and \code{1e24} are supported. }} -\item{fixed_exponent}{Use the same fixed_exponent for all numbers in scientific, engineering or SI notation. +\item{fixed_exponent}{Use the same exponent for all numbers in scientific, engineering or SI notation. \code{-Inf} uses the smallest, \code{+Inf} the largest fixed_exponent present in the data. -The default is to use varying fixed_exponents.} +The default is to use varying exponents.} } \description{ \ifelse{html}{\href{https://lifecycle.r-lib.org/articles/stages.html#experimental}{\figure{lifecycle-experimental.svg}{options: alt='[Experimental]'}}}{\strong{[Experimental]}} From b47826e5dca6a3fb1fd7f5aa0e65abf391b8c93d Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Wed, 28 Jul 2021 06:41:48 +0200 Subject: [PATCH 083/147] num() gains extra_sigfig argument --- R/num.R | 34 ++++++++++++++++++++++++++++++---- R/shaft-.R | 11 ++++++++--- R/sigfig.R | 13 +++++++++++++ man/num.Rd | 17 +++++++++++++++-- tests/testthat/_snaps/num.md | 11 +++++++++++ tests/testthat/test-num.R | 8 ++++++++ 6 files changed, 85 insertions(+), 9 deletions(-) diff --git a/R/num.R b/R/num.R index c35423bc5..45e10aa04 100644 --- a/R/num.R +++ b/R/num.R @@ -43,6 +43,9 @@ #' Use the same exponent for all numbers in scientific, engineering or SI notation. #' `-Inf` uses the smallest, `+Inf` the largest fixed_exponent present in the data. #' The default is to use varying exponents. +#' @param extra_sigfig +#' If `TRUE`, increase the number of significant digits if the data consists of +#' similar numbers with subtle differences. #' @export #' @examples #' # Display as a vector @@ -97,11 +100,20 @@ #' scilarge = num(10^(-7:6) * 123, notation = "sci", fixed_exponent = 3), #' scimax = num(10^(-7:6) * 123, notation = "sci", fixed_exponent = Inf) #' ) +#' +#' #' Extra significant digits +#' tibble::tibble( +#' default = num(100 + 1:3 * 0.001), +#' extra1 = num(100 + 1:3 * 0.001, extra_sigfig = TRUE), +#' extra2 = num(100 + 1:3 * 0.0001, extra_sigfig = TRUE), +#' extra3 = num(10000 + 1:3 * 0.00001, extra_sigfig = TRUE) +#' ) num <- function(x, ..., sigfig = NULL, digits = NULL, label = NULL, scale = NULL, notation = c("fit", "dec", "sci", "eng", "si"), - fixed_exponent = NULL) { + fixed_exponent = NULL, + extra_sigfig = NULL) { stopifnot(is.numeric(x)) check_dots_empty() @@ -121,7 +133,8 @@ num <- function(x, ..., label = label, scale = scale, notation = notation, - fixed_exponent = fixed_exponent + fixed_exponent = fixed_exponent, + extra_sigfig = extra_sigfig ) # FIXME: Include class(x) to support subclassing/mixin? @@ -234,7 +247,8 @@ set_num_opts <- function(x, ..., sigfig = NULL, digits = NULL, label = NULL, scale = NULL, notation = c("fit", "dec", "sci", "eng", "si"), - fixed_exponent = NULL) { + fixed_exponent = NULL, + extra_sigfig = NULL) { check_dots_empty() @@ -254,6 +268,10 @@ set_num_opts <- function(x, ..., abort("Must set `label` if `scale` is provided.") } + if (!is.null(digits) && !is.null(extra_sigfig)) { + abort("Incompatible arguments: `extra_sigfig` and `digits`.") + } + pillar_attr <- structure( list( sigfig = sigfig, @@ -261,7 +279,8 @@ set_num_opts <- function(x, ..., label = label, scale = scale, notation = notation, - fixed_exponent = fixed_exponent + fixed_exponent = fixed_exponent, + extra_sigfig = extra_sigfig ), class = c("pillar_num_attr", "pillar_vctr_attr", "tibble_vec_attr") ) @@ -281,6 +300,7 @@ format.pillar_num_attr <- function(x, ...) { sigfig <- x$sigfig digits <- x$digits label <- x$label + extra_sigfig <- x$extra_sigfig if (!is.null(digits)) { if (digits >= 0) { @@ -290,6 +310,12 @@ format.pillar_num_attr <- function(x, ...) { } } else if (!is.null(sigfig)) { out <- paste0(class, ":", sigfig) + + if (isTRUE(extra_sigfig)) { + out <- paste0(out, "*") + } + } else if (isTRUE(extra_sigfig)) { + out <- paste0(class, "*") } else { out <- class } diff --git a/R/shaft-.R b/R/shaft-.R index 00b3f13e0..d45db3013 100644 --- a/R/shaft-.R +++ b/R/shaft-.R @@ -134,11 +134,12 @@ pillar_shaft.numeric <- function(x, ..., sigfig = NULL) { sigfig %||% pillar_attr$sigfig, pillar_attr$digits, pillar_attr$notation, - pillar_attr$fixed_exponent + pillar_attr$fixed_exponent, + pillar_attr$extra_sigfig ) } -pillar_shaft_number <- function(x, sigfig, digits, notation, fixed_exponent) { +pillar_shaft_number <- function(x, sigfig, digits, notation, fixed_exponent, extra_sigfig) { if (!is.null(digits)) { if (!is.numeric(digits) || length(digits) != 1) { abort("`digits` must be a number.") @@ -148,6 +149,10 @@ pillar_shaft_number <- function(x, sigfig, digits, notation, fixed_exponent) { sigfig <- get_pillar_option_sigfig() } + if (isTRUE(extra_sigfig)) { + sigfig <- sigfig + compute_extra_sigfig(x) + } + if (is.null(notation) || notation == "fit") { dec <- split_decimal(x, sigfig = sigfig, digits = digits) sci <- split_decimal(x, sigfig = sigfig, digits = digits, sci_mod = 1, fixed_exponent = fixed_exponent) @@ -202,7 +207,7 @@ pillar_shaft_number <- function(x, sigfig, digits, notation, fixed_exponent) { # registered in .onLoad() pillar_shaft.integer64 <- function(x, ..., sigfig = NULL) { - pillar_shaft_number(x, sigfig, digits = NULL, notation = NULL, fixed_exponent = NULL) + pillar_shaft_number(x, sigfig, digits = NULL, notation = NULL, fixed_exponent = NULL, extra_sigfig = NULL) } # registered in .onLoad() diff --git a/R/sigfig.R b/R/sigfig.R index a271f41af..74f5d792e 100644 --- a/R/sigfig.R +++ b/R/sigfig.R @@ -236,6 +236,19 @@ compute_min_sigfig <- function(x) { ret } +compute_extra_sigfig <- function(x) { + x <- sort(abs(x)) + delta <- diff(x) + x <- x[-1] + + keep <- which((delta != 0) & is.finite(delta)) + if (length(keep) == 0) { + return(0) + } + + ceiling(log10(max(x[keep] / delta[keep]))) - 1 +} + LOG_10 <- log(10) compute_exp <- function(x, sigfig, digits) { diff --git a/man/num.Rd b/man/num.Rd index 3b630dd60..e121350f8 100644 --- a/man/num.Rd +++ b/man/num.Rd @@ -13,7 +13,8 @@ num( label = NULL, scale = NULL, notation = c("fit", "dec", "sci", "eng", "si"), - fixed_exponent = NULL + fixed_exponent = NULL, + extra_sigfig = NULL ) set_num_opts( @@ -24,7 +25,8 @@ set_num_opts( label = NULL, scale = NULL, notation = c("fit", "dec", "sci", "eng", "si"), - fixed_exponent = NULL + fixed_exponent = NULL, + extra_sigfig = NULL ) } \arguments{ @@ -63,6 +65,9 @@ using exponents that are a multiple of three. \item{fixed_exponent}{Use the same exponent for all numbers in scientific, engineering or SI notation. \code{-Inf} uses the smallest, \code{+Inf} the largest fixed_exponent present in the data. The default is to use varying exponents.} + +\item{extra_sigfig}{If \code{TRUE}, increase the number of significant digits if the data consists of +similar numbers with subtle differences.} } \description{ \ifelse{html}{\href{https://lifecycle.r-lib.org/articles/stages.html#experimental}{\figure{lifecycle-experimental.svg}{options: alt='[Experimental]'}}}{\strong{[Experimental]}} @@ -135,6 +140,14 @@ tibble::tibble( scilarge = num(10^(-7:6) * 123, notation = "sci", fixed_exponent = 3), scimax = num(10^(-7:6) * 123, notation = "sci", fixed_exponent = Inf) ) + +#' Extra significant digits +tibble::tibble( + default = num(100 + 1:3 * 0.001), + extra1 = num(100 + 1:3 * 0.001, extra_sigfig = TRUE), + extra2 = num(100 + 1:3 * 0.0001, extra_sigfig = TRUE), + extra3 = num(10000 + 1:3 * 0.00001, extra_sigfig = TRUE) +) \dontshow{\}) # examplesIf} } \seealso{ diff --git a/tests/testthat/_snaps/num.md b/tests/testthat/_snaps/num.md index d186864ca..39489c9bf 100644 --- a/tests/testthat/_snaps/num.md +++ b/tests/testthat/_snaps/num.md @@ -115,6 +115,17 @@ 12 1230000000 e-3 1230 e3 1.23 M 13 12300000000 e-3 12300 e3 12.3 M 14 123000000000 e-3 123000 e3 123 M + Code + tibble::tibble(default = num(100 + 1:3 * 0.001), extra1 = num(100 + 1:3 * 0.001, + extra_sigfig = TRUE), extra2 = num(100 + 1:3 * 1e-04, extra_sigfig = TRUE), + extra3 = num(10000 + 1:3 * 1e-05, extra_sigfig = TRUE)) + Output + # A tibble: 3 x 4 + default extra1 extra2 extra3 + + 1 100. 100.001 100.0001 10000.00001 + 2 100. 100.002 100.0002 10000.00002 + 3 100. 100.003 100.0003 10000.00003 # many digits diff --git a/tests/testthat/test-num.R b/tests/testthat/test-num.R index f5c095ad3..8ebbb669d 100644 --- a/tests/testthat/test-num.R +++ b/tests/testthat/test-num.R @@ -47,6 +47,14 @@ test_that("output test", { scilarge = num(10^(-7:6) * 123, notation = "eng", fixed_exponent = 3), scimax = num(10^(-7:6) * 123, notation = "si", fixed_exponent = Inf) ) + + # Extra significant figures + tibble::tibble( + default = num(100 + 1:3 * 0.001), + extra1 = num(100 + 1:3 * 0.001, extra_sigfig = TRUE), + extra2 = num(100 + 1:3 * 0.0001, extra_sigfig = TRUE), + extra3 = num(10000 + 1:3 * 0.00001, extra_sigfig = TRUE) + ) }) }) From 86f3b1e412137653cdecd29d211ab389b2a4d5c5 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Wed, 28 Jul 2021 17:06:23 +0200 Subject: [PATCH 084/147] Tweak docs --- R/num.R | 2 +- man/num.Rd | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/R/num.R b/R/num.R index 45e10aa04..721eab59f 100644 --- a/R/num.R +++ b/R/num.R @@ -45,7 +45,7 @@ #' The default is to use varying exponents. #' @param extra_sigfig #' If `TRUE`, increase the number of significant digits if the data consists of -#' similar numbers with subtle differences. +#' numbers of the same magnitude with subtle differences. #' @export #' @examples #' # Display as a vector diff --git a/man/num.Rd b/man/num.Rd index e121350f8..b40ccb28c 100644 --- a/man/num.Rd +++ b/man/num.Rd @@ -67,7 +67,7 @@ using exponents that are a multiple of three. The default is to use varying exponents.} \item{extra_sigfig}{If \code{TRUE}, increase the number of significant digits if the data consists of -similar numbers with subtle differences.} +numbers of the same magnitude with subtle differences.} } \description{ \ifelse{html}{\href{https://lifecycle.r-lib.org/articles/stages.html#experimental}{\figure{lifecycle-experimental.svg}{options: alt='[Experimental]'}}}{\strong{[Experimental]}} From 310c59efc15cfeae1dabe3bd1634d9abae2c3f9b Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Wed, 28 Jul 2021 17:07:25 +0200 Subject: [PATCH 085/147] Bump version to 1.6.1.9005 --- DESCRIPTION | 2 +- NEWS.md | 6 ++++++ 2 files changed, 7 insertions(+), 1 deletion(-) diff --git a/DESCRIPTION b/DESCRIPTION index 62b61b61f..63eb62216 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -1,6 +1,6 @@ Package: pillar Title: Coloured Formatting for Columns -Version: 1.6.1.9004 +Version: 1.6.1.9005 Authors@R: c(person(given = "Kirill", family = "M\u00fcller", diff --git a/NEWS.md b/NEWS.md index 24cd10e6d..b48444e0c 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,5 +1,11 @@ +# pillar 1.6.1.9005 + +- `num()` gains `extra_sigfig` argument to automatically show more significant figures for numbers of the same magnitude with subtle differences (#97). +- Options `pillar.print_max`, `pillar.print_min`, `pillar.width` and `pillar.max_extra_cols` are now queried before the corresponding `tibble.` or `dplyr.` options are consulted, the latter will be soft-deprecated in pillar v2.0.0 (#353). + + # pillar 1.6.1.9004 - New `pillar.bidi` option. When active, control characters are inserted to improve display of data with right-to-left text (#333). From 5370d59282f29884de7e0c550be9d917d97fa0e4 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Wed, 28 Jul 2021 17:08:09 +0200 Subject: [PATCH 086/147] TODO --- TODO.md | 10 +++++++--- 1 file changed, 7 insertions(+), 3 deletions(-) diff --git a/TODO.md b/TODO.md index 837e8d065..3850d0278 100644 --- a/TODO.md +++ b/TODO.md @@ -2,14 +2,18 @@ ## Next steps -- revdepcheck for adding ellipsis to methods +- Pass `max_footer_lines` to `print.tbl()`, rethink option name +- Test all options - Milestone: +- CRAN release +- triage issues + + +- revdepcheck for adding ellipsis to methods - Focus columns at their native position, with ... or subtle vertical pipe inbetween (1 char wide) - Get extra width? -- Discuss: - - Add convenience arguments to `print.tbl()`? - Breaking changes - Wide character + list column: why does the character column take up all the space? - `tibble(a = strrep("1234567890", 100), b = list(tibble(a = letters)))` From 61b18c3990f47592c7eb34826965ed2641d1155f Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Wed, 28 Jul 2021 19:26:35 +0200 Subject: [PATCH 087/147] Combine files --- R/options.R | 55 ++++++++++++++++++++++++++++++++ R/tibble-opt.R | 54 ------------------------------- tests/testthat/test-options.R | 27 ++++++++++++++++ tests/testthat/test-tibble-opt.R | 27 ---------------- 4 files changed, 82 insertions(+), 81 deletions(-) delete mode 100644 R/tibble-opt.R delete mode 100644 tests/testthat/test-tibble-opt.R diff --git a/R/options.R b/R/options.R index 96a4f7e37..df4775613 100644 --- a/R/options.R +++ b/R/options.R @@ -138,3 +138,58 @@ pillar_options <- list2( getOption("pillar.bidi", default = FALSE) ), ) + +tibble_opt <- function(x, default) { + x_tibble <- paste0("tibble.", x) + res <- getOption(x_tibble) + if (!is.null(res)) { + return(res) + } + + x_dplyr <- paste0("dplyr.", x) + res <- getOption(x_dplyr) + if (!is.null(res)) { + return(res) + } + + default +} + +get_width_print <- function(width) { + if (!is.null(width)) { + return(width) + } + + get_pillar_option_width() +} + +get_width_glimpse <- function(width) { + width <- get_width_print(width) + + if (is.finite(width)) { + width + } else { + getOption("width") + } +} + +get_n_print <- function(n, rows) { + if (!is.null(n) && n >= 0) { + return(n) + } + + if (is.na(rows) || rows > get_pillar_option_print_max()) { + get_pillar_option_print_min() + } else { + rows + } +} + +get_max_extra_cols <- function(max_extra_cols) { + # FIXME: Deprecate + if (!is.null(max_extra_cols) && max_extra_cols >= 0) { + return(max_extra_cols) + } + + get_pillar_option_max_extra_cols() +} diff --git a/R/tibble-opt.R b/R/tibble-opt.R deleted file mode 100644 index 7165c4aa8..000000000 --- a/R/tibble-opt.R +++ /dev/null @@ -1,54 +0,0 @@ -tibble_opt <- function(x, default) { - x_tibble <- paste0("tibble.", x) - res <- getOption(x_tibble) - if (!is.null(res)) { - return(res) - } - - x_dplyr <- paste0("dplyr.", x) - res <- getOption(x_dplyr) - if (!is.null(res)) { - return(res) - } - - default -} - -get_width_print <- function(width) { - if (!is.null(width)) { - return(width) - } - - get_pillar_option_width() -} - -get_width_glimpse <- function(width) { - width <- get_width_print(width) - - if (is.finite(width)) { - width - } else { - getOption("width") - } -} - -get_n_print <- function(n, rows) { - if (!is.null(n) && n >= 0) { - return(n) - } - - if (is.na(rows) || rows > get_pillar_option_print_max()) { - get_pillar_option_print_min() - } else { - rows - } -} - -get_max_extra_cols <- function(max_extra_cols) { - # FIXME: Deprecate - if (!is.null(max_extra_cols) && max_extra_cols >= 0) { - return(max_extra_cols) - } - - get_pillar_option_max_extra_cols() -} diff --git a/tests/testthat/test-options.R b/tests/testthat/test-options.R index 71d3a2bd2..7e750925c 100644 --- a/tests/testthat/test-options.R +++ b/tests/testthat/test-options.R @@ -166,3 +166,30 @@ test_that("max_dec_width", { expect_equal(get_pillar_option_max_dec_width(), orig) }) +test_that("print.tbl ignores max.print option", { + trees2 <- as_tbl(trees) + expect_output( + withr::with_options(list(max.print = 3), print(trees2)), + capture_output(print(trees2)), + fixed = TRUE + ) +}) + +test_that("print.tbl uses tibble.width option", { + mtcars2 <- as_tbl(mtcars) + expect_output( + withr::with_options(list(tibble.width = 40, dplyr.width = 50, width = 60), print(mtcars2)), + capture_output(print(mtcars2, width = 40)), + fixed = TRUE + ) + expect_output( + withr::with_options(list(dplyr.width = 50, width = 60), print(mtcars2)), + capture_output(print(mtcars2, width = 50)), + fixed = TRUE + ) + expect_output( + withr::with_options(list(width = 60), print(mtcars2)), + capture_output(print(mtcars2, width = 60)), + fixed = TRUE + ) +}) diff --git a/tests/testthat/test-tibble-opt.R b/tests/testthat/test-tibble-opt.R deleted file mode 100644 index 3b4c0f6a4..000000000 --- a/tests/testthat/test-tibble-opt.R +++ /dev/null @@ -1,27 +0,0 @@ -test_that("print.tbl ignores max.print option", { - trees2 <- as_tbl(trees) - expect_output( - withr::with_options(list(max.print = 3), print(trees2)), - capture_output(print(trees2)), - fixed = TRUE - ) -}) - -test_that("print.tbl uses tibble.width option", { - mtcars2 <- as_tbl(mtcars) - expect_output( - withr::with_options(list(tibble.width = 40, dplyr.width = 50, width = 60), print(mtcars2)), - capture_output(print(mtcars2, width = 40)), - fixed = TRUE - ) - expect_output( - withr::with_options(list(dplyr.width = 50, width = 60), print(mtcars2)), - capture_output(print(mtcars2, width = 50)), - fixed = TRUE - ) - expect_output( - withr::with_options(list(width = 60), print(mtcars2)), - capture_output(print(mtcars2, width = 60)), - fixed = TRUE - ) -}) From 48a090739544cf93223d70ea815946c05c705f5d Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Wed, 28 Jul 2021 19:29:09 +0200 Subject: [PATCH 088/147] get_max_footer_lines() --- R/options.R | 9 ++++++++- 1 file changed, 8 insertions(+), 1 deletion(-) diff --git a/R/options.R b/R/options.R index df4775613..bac6e24c8 100644 --- a/R/options.R +++ b/R/options.R @@ -186,10 +186,17 @@ get_n_print <- function(n, rows) { } get_max_extra_cols <- function(max_extra_cols) { - # FIXME: Deprecate if (!is.null(max_extra_cols) && max_extra_cols >= 0) { return(max_extra_cols) } get_pillar_option_max_extra_cols() } + +get_max_footer_lines <- function(max_footer_lines) { + if (!is.null(max_footer_lines) && max_footer_lines >= 0) { + return(max_footer_lines) + } + + get_pillar_option_max_footer_lines() +} From 2316ca1940843bd1170bc4b1112c5a70241eb0aa Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Wed, 28 Jul 2021 19:30:59 +0200 Subject: [PATCH 089/147] tbl_format_setup(max_footer_lines = ) --- R/tbl-format-footer.R | 2 +- R/tbl-format-setup.R | 23 ++++++++++++++++------- man/new_tbl_format_setup.Rd | 5 ++++- man/tbl_format_setup.Rd | 11 +++++++++-- 4 files changed, 30 insertions(+), 11 deletions(-) diff --git a/R/tbl-format-footer.R b/R/tbl-format-footer.R index 1a6db9887..63961fa0b 100644 --- a/R/tbl-format-footer.R +++ b/R/tbl-format-footer.R @@ -118,7 +118,7 @@ wrap_footer <- function(footer, setup) { tier_widths <- get_footer_tier_widths( footer, max_extent, - get_pillar_option_max_footer_lines() + setup$max_footer_lines ) # show optuput even if too wide diff --git a/R/tbl-format-setup.R b/R/tbl-format-setup.R index 12107b640..367332ba5 100644 --- a/R/tbl-format-setup.R +++ b/R/tbl-format-setup.R @@ -58,7 +58,8 @@ #' @examplesIf rlang::is_installed("palmerpenguins") #' tbl_format_setup(palmerpenguins::penguins) tbl_format_setup <- function(x, width = NULL, ..., - n = NULL, max_extra_cols = NULL) { + n = NULL, max_extra_cols = NULL, + max_footer_lines = NULL) { "!!!!DEBUG tbl_format_setup()" width <- get_width_print(width) @@ -66,15 +67,19 @@ tbl_format_setup <- function(x, width = NULL, ..., n <- get_n_print(n, nrow(x)) max_extra_cols <- get_max_extra_cols(max_extra_cols) + max_footer_lines <- get_max_footer_lines(max_footer_lines) # Calls UseMethod("tbl_format_setup"), # allows using default values in S3 dispatch - out <- tbl_format_setup_(x, width, ..., n = n, max_extra_cols = max_extra_cols) + out <- tbl_format_setup_( + x, width, ..., + n = n, max_extra_cols = max_extra_cols, max_footer_lines = max_footer_lines + ) return(out) UseMethod("tbl_format_setup") } -tbl_format_setup_ <- function(x, width, ..., n, max_extra_cols) { +tbl_format_setup_ <- function(x, width, ..., n, max_extra_cols, max_footer_lines) { UseMethod("tbl_format_setup") } @@ -86,7 +91,7 @@ tbl_format_setup_ <- function(x, width, ..., n, max_extra_cols) { #' @rdname tbl_format_setup #' @export tbl_format_setup.tbl <- function(x, width, ..., - n, max_extra_cols) { + n, max_extra_cols, max_footer_lines) { "!!!!DEBUG tbl_format_setup.tbl()" # Number of rows @@ -150,7 +155,8 @@ tbl_format_setup.tbl <- function(x, width, ..., rows_missing = rows_missing, rows_total = rows, extra_cols = extra_cols, - extra_cols_total = extra_cols_total + extra_cols_total = extra_cols_total, + max_footer_lines = max_footer_lines ) } @@ -179,11 +185,13 @@ tbl_format_setup.tbl <- function(x, width, ..., #' as a character vector of formatted column names and types. #' @param extra_cols_total The total number of columns, may be larger than #' `length(extra_cols)`. +#' @param max_footer_lines The maximum number of lines in the footer. #' #' @keywords internal new_tbl_format_setup <- function(x, df, width, tbl_sum, body, rows_missing, rows_total, - extra_cols, extra_cols_total) { + extra_cols, extra_cols_total, + max_footer_lines) { trunc_info <- list( x = x, df = df, @@ -193,7 +201,8 @@ new_tbl_format_setup <- function(x, df, width, tbl_sum, body, rows_missing = rows_missing, rows_total = rows_total, extra_cols = extra_cols, - extra_cols_total = extra_cols_total + extra_cols_total = extra_cols_total, + max_footer_lines = max_footer_lines ) structure(trunc_info, class = "pillar_tbl_format_setup") diff --git a/man/new_tbl_format_setup.Rd b/man/new_tbl_format_setup.Rd index fe6b9b5cb..e34a31aa5 100644 --- a/man/new_tbl_format_setup.Rd +++ b/man/new_tbl_format_setup.Rd @@ -13,7 +13,8 @@ new_tbl_format_setup( rows_missing, rows_total, extra_cols, - extra_cols_total + extra_cols_total, + max_footer_lines ) } \arguments{ @@ -40,6 +41,8 @@ as a character vector of formatted column names and types.} \item{extra_cols_total}{The total number of columns, may be larger than \code{length(extra_cols)}.} + +\item{max_footer_lines}{The maximum number of lines in the footer.} } \description{ The object returned from the default method of \code{\link[=tbl_format_setup]{tbl_format_setup()}} diff --git a/man/tbl_format_setup.Rd b/man/tbl_format_setup.Rd index c810feacd..c5588fdcc 100644 --- a/man/tbl_format_setup.Rd +++ b/man/tbl_format_setup.Rd @@ -5,9 +5,16 @@ \alias{tbl_format_setup.tbl} \title{Set up formatting} \usage{ -tbl_format_setup(x, width = NULL, ..., n = NULL, max_extra_cols = NULL) +tbl_format_setup( + x, + width = NULL, + ..., + n = NULL, + max_extra_cols = NULL, + max_footer_lines = NULL +) -\method{tbl_format_setup}{tbl}(x, width, ..., n, max_extra_cols) +\method{tbl_format_setup}{tbl}(x, width, ..., n, max_extra_cols, max_footer_lines) } \arguments{ \item{x}{An object.} From ef360797ba785ad65cd89727e76fc27f2522bd34 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Wed, 28 Jul 2021 19:38:47 +0200 Subject: [PATCH 090/147] format.tbl() and print.tbl() gain max_footer_lines and max_extra_cols argument, deprecate n_extra argument --- R/tbl-format-setup.R | 4 ++++ R/tbl-format.R | 52 +++++++++++++++++++++++++++++++++++++---- man/format_tbl.Rd | 26 +++++++++++++++++---- man/tbl_format_setup.Rd | 4 ++++ 4 files changed, 77 insertions(+), 9 deletions(-) diff --git a/R/tbl-format-setup.R b/R/tbl-format-setup.R index 367332ba5..9be0f80e6 100644 --- a/R/tbl-format-setup.R +++ b/R/tbl-format-setup.R @@ -50,6 +50,10 @@ #' if the width is too small for the entire tibble. #' No [options][pillar_options] should be considered #' by implementations of this method. +#' @param max_footer_lines +#' Maximum number of lines for the footer. +#' No [options][pillar_options] should be considered +#' by implementations of this method. #' #' @return #' An object that can be passed as `setup` argument to diff --git a/R/tbl-format.R b/R/tbl-format.R index e4ccccb41..64caf6e73 100644 --- a/R/tbl-format.R +++ b/R/tbl-format.R @@ -30,24 +30,65 @@ #' `print_min` [option][pillar_options]. #' @param width Width of text output to generate. This defaults to `NULL`, which #' means use the `width` [option][pillar_options]. -#' @param n_extra Number of extra columns to print abbreviated information for, +#' @param max_extra_cols Number of extra columns to print abbreviated information for, #' if the width is too small for the entire tibble. If `NULL`, #' the `max_extra_cols` [option][pillar_options] is used. +#' The previously defined `n_extra` argument is soft-deprecated. +#' @param max_footer_lines Maximum number of footer lines. If `NULL`, +#' the `max_footer_lines` [option][pillar_options] is used. #' #' @name format_tbl #' @export #' @examples #' print(vctrs::new_data_frame(list(a = 1), class = "tbl")) -print.tbl <- function(x, width = NULL, ..., n = NULL, n_extra = NULL) { - writeLines(format(x, width = width, ..., n = n, n_extra = n_extra)) +print.tbl <- function(x, width = NULL, ..., n = NULL, max_extra_cols = NULL, + max_footer_lines = NULL) { + print_tbl( + x, width, ..., + n = n, max_extra_cols = max_extra_cols, max_footer_lines = max_footer_lines + ) +} + +print_tbl <- function(x, width = NULL, ..., + n_extra = NULL, + n = NULL, max_extra_cols = NULL, max_footer_lines = NULL) { + + if (!is.null(n_extra)) { + deprecate_soft("1.6.2", "pillar::print(n_extra = )", "pillar::print(max_extra_cols = )") + if (is.null(max_extra_cols)) { + max_extra_cols <- n_extra + } + } + + writeLines(format( + x, width = width, ..., + n = n, max_extra_cols = max_extra_cols, max_footer_lines = max_footer_lines + )) invisible(x) } #' @export #' @rdname format_tbl -format.tbl <- function(x, width = NULL, ..., n = NULL, n_extra = NULL) { +format.tbl <- function(x, width = NULL, ..., + n = NULL, max_extra_cols = NULL, max_footer_lines = NULL) { + format_tbl( + x, width, ..., + n = n, max_extra_cols = max_extra_cols, max_footer_lines = max_footer_lines + ) +} + +format_tbl <- function(x, width = NULL, ..., + n_extra = NULL, + n = NULL, max_extra_cols = NULL, max_footer_lines = NULL) { check_dots_empty(action = signal) + if (!is.null(n_extra)) { + deprecate_soft("1.6.2", "pillar::format(n_extra = )", "pillar::format(max_extra_cols = )") + if (is.null(max_extra_cols)) { + max_extra_cols <- n_extra + } + } + # Reset local cache for each new output force(x) num_colors(forget = TRUE) @@ -55,7 +96,8 @@ format.tbl <- function(x, width = NULL, ..., n = NULL, n_extra = NULL) { setup <- tbl_format_setup(x, width = width, ..., n = n, - max_extra_cols = n_extra + max_extra_cols = max_extra_cols, + max_footer_lines = max_footer_lines ) header <- tbl_format_header(x, setup) diff --git a/man/format_tbl.Rd b/man/format_tbl.Rd index 6d170f70d..982805dff 100644 --- a/man/format_tbl.Rd +++ b/man/format_tbl.Rd @@ -6,9 +6,23 @@ \alias{format.tbl} \title{Formatting of tbl objects} \usage{ -\method{print}{tbl}(x, width = NULL, ..., n = NULL, n_extra = NULL) +\method{print}{tbl}( + x, + width = NULL, + ..., + n = NULL, + max_extra_cols = NULL, + max_footer_lines = NULL +) -\method{format}{tbl}(x, width = NULL, ..., n = NULL, n_extra = NULL) +\method{format}{tbl}( + x, + width = NULL, + ..., + n = NULL, + max_extra_cols = NULL, + max_footer_lines = NULL +) } \arguments{ \item{x}{Object to format or print.} @@ -23,9 +37,13 @@ if less than the \code{print_max} \link[=pillar_options]{option}. Otherwise, will print as many rows as specified by the \code{print_min} \link[=pillar_options]{option}.} -\item{n_extra}{Number of extra columns to print abbreviated information for, +\item{max_extra_cols}{Number of extra columns to print abbreviated information for, if the width is too small for the entire tibble. If \code{NULL}, -the \code{max_extra_cols} \link[=pillar_options]{option} is used.} +the \code{max_extra_cols} \link[=pillar_options]{option} is used. +The previously defined \code{n_extra} argument is soft-deprecated.} + +\item{max_footer_lines}{Maximum number of footer lines. If \code{NULL}, +the \code{max_footer_lines} \link[=pillar_options]{option} is used.} } \description{ These functions and methods are responsible for printing objects diff --git a/man/tbl_format_setup.Rd b/man/tbl_format_setup.Rd index c5588fdcc..f60dd8e66 100644 --- a/man/tbl_format_setup.Rd +++ b/man/tbl_format_setup.Rd @@ -32,6 +32,10 @@ by implementations of this method.} if the width is too small for the entire tibble. No \link[=pillar_options]{options} should be considered by implementations of this method.} + +\item{max_footer_lines}{Maximum number of lines for the footer. +No \link[=pillar_options]{options} should be considered +by implementations of this method.} } \value{ An object that can be passed as \code{setup} argument to From 8dc2881b37850b61b97954a369a6d45857d75710 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Wed, 28 Jul 2021 20:04:12 +0200 Subject: [PATCH 091/147] Refine tests --- tests/testthat/_snaps/tbl-format-footer.md | 67 +++++++--------------- tests/testthat/test-tbl-format-footer.R | 52 ++++++++++++----- 2 files changed, 59 insertions(+), 60 deletions(-) diff --git a/tests/testthat/_snaps/tbl-format-footer.md b/tests/testthat/_snaps/tbl-format-footer.md index 723d04e2f..f5610e50e 100644 --- a/tests/testthat/_snaps/tbl-format-footer.md +++ b/tests/testthat/_snaps/tbl-format-footer.md @@ -68,12 +68,9 @@ # max_footer_lines option Code - new_footer_tbl("") + tbl_format_footer(tbl_format_setup(new_footer_tbl(""))) Output - # A data frame: 1 x 52 - aa ba ab bb ac bc ad bd ae be af bf ag - - 1 1 2 3 4 5 6 7 8 9 10 11 12 13 + # ... with 39 more variables: bg , ah , bh , ai , bi , # aj , bj , ak , bk , al , bl , am , # bm , an , bn , ao , bo , ap , bp , @@ -81,12 +78,9 @@ # bt , au , bu , av , bv , aw , bw , # ax , bx , ay , by , az , bz Code - new_footer_tbl("prefix_") + tbl_format_footer(tbl_format_setup(new_footer_tbl("prefix_"))) Output - # A data frame: 1 x 52 - prefix_aa prefix_ba prefix_ab prefix_bb prefix_ac prefix_bc prefix_ad - - 1 1 2 3 4 5 6 7 + # ... with 45 more variables: prefix_bd , prefix_ae , # prefix_be , prefix_af , prefix_bf , prefix_ag , # prefix_bg , prefix_ah , prefix_bh , prefix_ai , @@ -95,12 +89,9 @@ # prefix_bm , prefix_an , prefix_bn , prefix_ao , # prefix_bo , prefix_ap , prefix_bp , prefix_aq , ... Code - new_footer_tbl("a_very_long_prefix_") + tbl_format_footer(tbl_format_setup(new_footer_tbl("a_very_long_prefix_"))) Output - # A data frame: 1 x 52 - a_very_long_prefix_aa a_very_long_prefix_ba a_very_long_pref~ a_very_long_pre~ - - 1 1 2 3 4 + # ... with 48 more variables: a_very_long_prefix_ac , # a_very_long_prefix_bc , a_very_long_prefix_ad , # a_very_long_prefix_bd , a_very_long_prefix_ae , @@ -109,44 +100,31 @@ # a_very_long_prefix_bg , a_very_long_prefix_ah , # a_very_long_prefix_bh , a_very_long_prefix_ai , ... Code - set_pillar_option_max_footer_lines(3) - new_footer_tbl("") + tbl_format_footer(tbl_format_setup(new_footer_tbl(""), max_footer_lines = 3)) Output - # A data frame: 1 x 52 - aa ba ab bb ac bc ad bd ae be af bf ag - - 1 1 2 3 4 5 6 7 8 9 10 11 12 13 + # ... with 39 more variables: bg , ah , bh , ai , bi , # aj , bj , ak , bk , al , bl , am , # bm , an , bn , ao , bo , ap , bp , ... Code - new_footer_tbl("prefix_") + tbl_format_footer(tbl_format_setup(new_footer_tbl("prefix_"), max_footer_lines = 3)) Output - # A data frame: 1 x 52 - prefix_aa prefix_ba prefix_ab prefix_bb prefix_ac prefix_bc prefix_ad - - 1 1 2 3 4 5 6 7 + # ... with 45 more variables: prefix_bd , prefix_ae , # prefix_be , prefix_af , prefix_bf , prefix_ag , # prefix_bg , prefix_ah , prefix_bh , prefix_ai , ... Code - new_footer_tbl("a_very_long_prefix_") + tbl_format_footer(tbl_format_setup(new_footer_tbl("a_very_long_prefix_"), + max_footer_lines = 3)) Output - # A data frame: 1 x 52 - a_very_long_prefix_aa a_very_long_prefix_ba a_very_long_pref~ a_very_long_pre~ - - 1 1 2 3 4 + # ... with 48 more variables: a_very_long_prefix_ac , # a_very_long_prefix_bc , a_very_long_prefix_ad , # a_very_long_prefix_bd , a_very_long_prefix_ae , ... Code - set_pillar_option_max_footer_lines(Inf) - new_footer_tbl("") + tbl_format_footer(tbl_format_setup(new_footer_tbl(""), max_footer_lines = Inf)) Output - # A data frame: 1 x 52 - aa ba ab bb ac bc ad bd ae be af bf ag - - 1 1 2 3 4 5 6 7 8 9 10 11 12 13 + # ... with 39 more variables: bg , ah , bh , ai , bi , # aj , bj , ak , bk , al , bl , am , # bm , an , bn , ao , bo , ap , bp , @@ -154,12 +132,9 @@ # bt , au , bu , av , bv , aw , bw , # ax , bx , ay , by , az , bz Code - new_footer_tbl("prefix_") + tbl_format_footer(tbl_format_setup(new_footer_tbl("prefix_"), max_footer_lines = Inf)) Output - # A data frame: 1 x 52 - prefix_aa prefix_ba prefix_ab prefix_bb prefix_ac prefix_bc prefix_ad - - 1 1 2 3 4 5 6 7 + # ... with 45 more variables: prefix_bd , prefix_ae , # prefix_be , prefix_af , prefix_bf , prefix_ag , # prefix_bg , prefix_ah , prefix_bh , prefix_ai , @@ -173,12 +148,10 @@ # prefix_bw , prefix_ax , prefix_bx , prefix_ay , # prefix_by , prefix_az , prefix_bz Code - new_footer_tbl("a_very_long_prefix_") + tbl_format_footer(tbl_format_setup(new_footer_tbl("a_very_long_prefix_"), + max_footer_lines = Inf)) Output - # A data frame: 1 x 52 - a_very_long_prefix_aa a_very_long_prefix_ba a_very_long_pref~ a_very_long_pre~ - - 1 1 2 3 4 + # ... with 48 more variables: a_very_long_prefix_ac , # a_very_long_prefix_bc , a_very_long_prefix_ad , # a_very_long_prefix_bd , a_very_long_prefix_ae , diff --git a/tests/testthat/test-tbl-format-footer.R b/tests/testthat/test-tbl-format-footer.R index 47505c08b..3560be802 100644 --- a/tests/testthat/test-tbl-format-footer.R +++ b/tests/testthat/test-tbl-format-footer.R @@ -33,19 +33,45 @@ test_that("max_footer_lines option", { new_tbl(x) } + expect_identical( + local({ + local_pillar_option_max_footer_lines(3) + tbl_format_footer(tbl_format_setup(new_footer_tbl(""))) + }), + tbl_format_footer( + tbl_format_setup(new_footer_tbl(""), max_footer_lines = 3) + ) + ) + expect_snapshot({ - new_footer_tbl("") - new_footer_tbl("prefix_") - new_footer_tbl("a_very_long_prefix_") - - set_pillar_option_max_footer_lines(3) - new_footer_tbl("") - new_footer_tbl("prefix_") - new_footer_tbl("a_very_long_prefix_") - - set_pillar_option_max_footer_lines(Inf) - new_footer_tbl("") - new_footer_tbl("prefix_") - new_footer_tbl("a_very_long_prefix_") + tbl_format_footer( + tbl_format_setup(new_footer_tbl("")) + ) + tbl_format_footer( + tbl_format_setup(new_footer_tbl("prefix_")) + ) + tbl_format_footer( + tbl_format_setup(new_footer_tbl("a_very_long_prefix_")) + ) + + tbl_format_footer( + tbl_format_setup(new_footer_tbl(""), max_footer_lines = 3) + ) + tbl_format_footer( + tbl_format_setup(new_footer_tbl("prefix_"), max_footer_lines = 3) + ) + tbl_format_footer( + tbl_format_setup(new_footer_tbl("a_very_long_prefix_"), max_footer_lines = 3) + ) + + tbl_format_footer( + tbl_format_setup(new_footer_tbl(""), max_footer_lines = Inf) + ) + tbl_format_footer( + tbl_format_setup(new_footer_tbl("prefix_"), max_footer_lines = Inf) + ) + tbl_format_footer( + tbl_format_setup(new_footer_tbl("a_very_long_prefix_"), max_footer_lines = Inf) + ) }) }) From 5a638f3833b5ce8244a3c4be1f670ea96438834b Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Wed, 28 Jul 2021 20:11:26 +0200 Subject: [PATCH 092/147] Pass user_env to deprecate_soft() --- R/tbl-format.R | 10 ++++++++-- 1 file changed, 8 insertions(+), 2 deletions(-) diff --git a/R/tbl-format.R b/R/tbl-format.R index 64caf6e73..9364a301f 100644 --- a/R/tbl-format.R +++ b/R/tbl-format.R @@ -54,7 +54,10 @@ print_tbl <- function(x, width = NULL, ..., n = NULL, max_extra_cols = NULL, max_footer_lines = NULL) { if (!is.null(n_extra)) { - deprecate_soft("1.6.2", "pillar::print(n_extra = )", "pillar::print(max_extra_cols = )") + deprecate_soft( + "1.6.2", "pillar::print(n_extra = )", "pillar::print(max_extra_cols = )", + user_env = caller_env(2) + ) if (is.null(max_extra_cols)) { max_extra_cols <- n_extra } @@ -83,7 +86,10 @@ format_tbl <- function(x, width = NULL, ..., check_dots_empty(action = signal) if (!is.null(n_extra)) { - deprecate_soft("1.6.2", "pillar::format(n_extra = )", "pillar::format(max_extra_cols = )") + deprecate_soft( + "1.6.2", "pillar::format(n_extra = )", "pillar::format(max_extra_cols = )", + user_env = caller_env(2) + ) if (is.null(max_extra_cols)) { max_extra_cols <- n_extra } From 2903bbb37c5558ee985e5dc778d357037fcd3a0a Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Thu, 29 Jul 2021 04:00:35 +0200 Subject: [PATCH 093/147] Add test --- tests/testthat/_snaps/tbl-format.md | 58 +++++++++++++++++++++++++++++ tests/testthat/test-tbl-format.R | 6 +++ 2 files changed, 64 insertions(+) diff --git a/tests/testthat/_snaps/tbl-format.md b/tests/testthat/_snaps/tbl-format.md index 89b9dcdde..eee0cc52f 100644 --- a/tests/testthat/_snaps/tbl-format.md +++ b/tests/testthat/_snaps/tbl-format.md @@ -143,6 +143,64 @@ 30 19.7 6 145 175 3.62 2.77 15.5 0 1 5 6 31 15 8 301 335 3.54 3.57 14.6 0 1 5 8 32 21.4 4 121 109 4.11 2.78 18.6 1 1 4 2 + Code + print(as_tbl(mtcars), width = 40, n_extra = 1) + Warning + The `n_extra` argument of `print()` is deprecated as of pillar 1.6.2. + Please use the `max_extra_cols` argument instead. + Output + # A data frame: 32 x 11 + mpg cyl disp hp drat wt + * + 1 21 6 160 110 3.9 2.62 + 2 21 6 160 110 3.9 2.88 + 3 22.8 4 108 93 3.85 2.32 + 4 21.4 6 258 110 3.08 3.22 + 5 18.7 8 360 175 3.15 3.44 + 6 18.1 6 225 105 2.76 3.46 + 7 14.3 8 360 245 3.21 3.57 + 8 24.4 4 147. 62 3.69 3.19 + 9 22.8 4 141. 95 3.92 3.15 + 10 19.2 6 168. 123 3.92 3.44 + # ... with 22 more rows, and 5 more + # variable: qsec , ... + Code + print(as_tbl(mtcars), width = 40, max_extra_cols = 1) + Output + # A data frame: 32 x 11 + mpg cyl disp hp drat wt + * + 1 21 6 160 110 3.9 2.62 + 2 21 6 160 110 3.9 2.88 + 3 22.8 4 108 93 3.85 2.32 + 4 21.4 6 258 110 3.08 3.22 + 5 18.7 8 360 175 3.15 3.44 + 6 18.1 6 225 105 2.76 3.46 + 7 14.3 8 360 245 3.21 3.57 + 8 24.4 4 147. 62 3.69 3.19 + 9 22.8 4 141. 95 3.92 3.15 + 10 19.2 6 168. 123 3.92 3.44 + # ... with 22 more rows, and 5 more + # variable: qsec , ... + Code + print(as_tbl(mtcars), width = 30, max_footer_lines = 3) + Output + # A data frame: 32 x 11 + mpg cyl disp hp + * + 1 21 6 160 110 + 2 21 6 160 110 + 3 22.8 4 108 93 + 4 21.4 6 258 110 + 5 18.7 8 360 175 + 6 18.1 6 225 105 + 7 14.3 8 360 245 + 8 24.4 4 147. 62 + 9 22.8 4 141. 95 + 10 19.2 6 168. 123 + # ... with 22 more rows, and + # 7 more variables: + # drat , wt , ... Code rlang::with_options(tibble.print_min = 5, as_tbl(mtcars)) Output diff --git a/tests/testthat/test-tbl-format.R b/tests/testthat/test-tbl-format.R index ac549e691..61d80b44c 100644 --- a/tests/testthat/test-tbl-format.R +++ b/tests/testthat/test-tbl-format.R @@ -24,6 +24,12 @@ test_that("print() output", { print(as_tbl(mtcars), n = 100) + print(as_tbl(mtcars), width = 40, n_extra = 1) + + print(as_tbl(mtcars), width = 40, max_extra_cols = 1) + + print(as_tbl(mtcars), width = 30, max_footer_lines = 3) + rlang::with_options( tibble.print_min = 5, as_tbl(mtcars) From d926dd47d1c87f0d700b3c4152c9e7582cba1ecf Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Thu, 29 Jul 2021 04:42:55 +0200 Subject: [PATCH 094/147] Add tests for options --- tests/testthat/test-options.R | 126 ++++++++++++++++++++++++++++++++++ 1 file changed, 126 insertions(+) diff --git a/tests/testthat/test-options.R b/tests/testthat/test-options.R index 7e750925c..148718ffe 100644 --- a/tests/testthat/test-options.R +++ b/tests/testthat/test-options.R @@ -1,3 +1,108 @@ +test_that("print_max", { + value <- 15L + + orig <- get_pillar_option_print_max() + expect_identical(orig, pillar_options$print_max()) + + old <- set_pillar_option_print_max(value) + expect_equal(get_pillar_option_print_max(), value) + expect_equal(expect_invisible(set_pillar_option_print_max(old)), value) + + old <- pillar_options$print_max(value) + expect_equal(pillar_options$print_max(), value) + expect_equal(expect_invisible(pillar_options$print_max(old)), value) + + local({ + expect_equal(expect_invisible(local_pillar_option_print_max(value)), old) + expect_equal(get_pillar_option_print_max(), value) + }) + expect_equal(get_pillar_option_print_max(), orig) +}) + +test_that("print_min", { + value <- 5L + + orig <- get_pillar_option_print_min() + expect_identical(orig, pillar_options$print_min()) + + old <- set_pillar_option_print_min(value) + expect_equal(get_pillar_option_print_min(), value) + expect_equal(expect_invisible(set_pillar_option_print_min(old)), value) + + old <- pillar_options$print_min(value) + expect_equal(pillar_options$print_min(), value) + expect_equal(expect_invisible(pillar_options$print_min(old)), value) + + local({ + expect_equal(expect_invisible(local_pillar_option_print_min(value)), old) + expect_equal(get_pillar_option_print_min(), value) + }) + expect_equal(get_pillar_option_print_min(), orig) +}) + +test_that("width", { + value <- 160L + + orig <- get_pillar_option_width() + expect_identical(orig, pillar_options$width()) + + old <- set_pillar_option_width(value) + expect_equal(get_pillar_option_width(), value) + expect_equal(expect_invisible(set_pillar_option_width(old)), value) + + old <- pillar_options$width(value) + expect_equal(pillar_options$width(), value) + expect_equal(expect_invisible(pillar_options$width(old)), value) + + local({ + expect_equal(expect_invisible(local_pillar_option_width(value)), old) + expect_equal(get_pillar_option_width(), value) + }) + expect_equal(get_pillar_option_width(), orig) +}) + +test_that("max_footer_lines", { + value <- 15L + + orig <- get_pillar_option_max_footer_lines() + expect_identical(orig, pillar_options$max_footer_lines()) + + old <- set_pillar_option_max_footer_lines(value) + expect_equal(get_pillar_option_max_footer_lines(), value) + expect_equal(expect_invisible(set_pillar_option_max_footer_lines(old)), value) + + old <- pillar_options$max_footer_lines(value) + expect_equal(pillar_options$max_footer_lines(), value) + expect_equal(expect_invisible(pillar_options$max_footer_lines(old)), value) + + local({ + expect_equal(expect_invisible(local_pillar_option_max_footer_lines(value)), old) + expect_equal(get_pillar_option_max_footer_lines(), value) + }) + expect_equal(get_pillar_option_max_footer_lines(), orig) +}) + +test_that("max_extra_cols", { + value <- 30L + + orig <- get_pillar_option_max_extra_cols() + expect_identical(orig, pillar_options$max_extra_cols()) + + old <- set_pillar_option_max_extra_cols(value) + expect_equal(get_pillar_option_max_extra_cols(), value) + expect_equal(expect_invisible(set_pillar_option_max_extra_cols(old)), value) + + old <- pillar_options$max_extra_cols(value) + expect_equal(pillar_options$max_extra_cols(), value) + expect_equal(expect_invisible(pillar_options$max_extra_cols(old)), value) + + local({ + expect_equal(expect_invisible(local_pillar_option_max_extra_cols(value)), old) + expect_equal(get_pillar_option_max_extra_cols(), value) + }) + expect_equal(get_pillar_option_max_extra_cols(), orig) +}) + test_that("bold", { value <- 0L @@ -166,6 +271,27 @@ test_that("max_dec_width", { expect_equal(get_pillar_option_max_dec_width(), orig) }) +test_that("bidi", { + value <- TRUE + + orig <- get_pillar_option_bidi() + expect_identical(orig, pillar_options$bidi()) + + old <- set_pillar_option_bidi(value) + expect_equal(get_pillar_option_bidi(), value) + expect_equal(expect_invisible(set_pillar_option_bidi(old)), value) + + old <- pillar_options$bidi(value) + expect_equal(pillar_options$bidi(), value) + expect_equal(expect_invisible(pillar_options$bidi(old)), value) + + local({ + expect_equal(expect_invisible(local_pillar_option_bidi(value)), old) + expect_equal(get_pillar_option_bidi(), value) + }) + expect_equal(get_pillar_option_bidi(), orig) +}) + test_that("print.tbl ignores max.print option", { trees2 <- as_tbl(trees) expect_output( From 9bea43f24898eb531d68e0143992fab0f505275c Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Thu, 29 Jul 2021 05:13:10 +0200 Subject: [PATCH 095/147] Bump version to 1.6.1.9006 --- DESCRIPTION | 2 +- NEWS.md | 6 ++++++ 2 files changed, 7 insertions(+), 1 deletion(-) diff --git a/DESCRIPTION b/DESCRIPTION index 63eb62216..14e0259da 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -1,6 +1,6 @@ Package: pillar Title: Coloured Formatting for Columns -Version: 1.6.1.9005 +Version: 1.6.1.9006 Authors@R: c(person(given = "Kirill", family = "M\u00fcller", diff --git a/NEWS.md b/NEWS.md index b48444e0c..3ed7eda88 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,5 +1,11 @@ +# pillar 1.6.1.9006 + +- `print.tbl()` and `format.tbl()` support the `max_extra_cols` and `max_footer_lines` arguments that override the corresponding options (#360). +- `print.tbl()` and `format.tbl()` maps the now deprecated `n_extra` argument to `max_extra_cols` for consistency (#360). + + # pillar 1.6.1.9005 - `num()` gains `extra_sigfig` argument to automatically show more significant figures for numbers of the same magnitude with subtle differences (#97). From 37ac91733d3a8c6529beb1ff8f5f3ba4594def9c Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Thu, 29 Jul 2021 05:13:37 +0200 Subject: [PATCH 096/147] Bump version to 1.6.2 --- DESCRIPTION | 2 +- NEWS.md | 5 +++++ 2 files changed, 6 insertions(+), 1 deletion(-) diff --git a/DESCRIPTION b/DESCRIPTION index 14e0259da..989ddb7ba 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -1,6 +1,6 @@ Package: pillar Title: Coloured Formatting for Columns -Version: 1.6.1.9006 +Version: 1.6.2 Authors@R: c(person(given = "Kirill", family = "M\u00fcller", diff --git a/NEWS.md b/NEWS.md index 3ed7eda88..ecd2a4814 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,5 +1,10 @@ +# pillar 1.6.2 + +- Same as previous version. + + # pillar 1.6.1.9006 - `print.tbl()` and `format.tbl()` support the `max_extra_cols` and `max_footer_lines` arguments that override the corresponding options (#360). From abb691cf54af861667b710d548b21ebbbfd3f839 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Thu, 29 Jul 2021 05:13:40 +0200 Subject: [PATCH 097/147] Update CRAN comments --- cran-comments.md | 15 ++++++++++----- 1 file changed, 10 insertions(+), 5 deletions(-) diff --git a/cran-comments.md b/cran-comments.md index 5032e2d28..03e661ef4 100644 --- a/cran-comments.md +++ b/cran-comments.md @@ -1,4 +1,4 @@ -pillar 1.6.1 +pillar 1.6.2 ## Cran Repository Policy @@ -6,10 +6,15 @@ pillar 1.6.1 ## R CMD check results -- [x] Checked locally, R 4.0.5 -- [x] Checked on CI system, R 4.0.5 -- [x] Checked on win-builder, R devel +- [x] Checked locally, R 4.1.0 +- [ ] Checked on CI system, R 4.1.0 +- [ ] Checked on win-builder, R devel + +Check the boxes above after successful execution and remove this line. Then run `fledge::release()`. ## Current CRAN check results -- [x] Checked on 2021-05-16, no problems found. +- [x] Checked on 2021-07-29, problems found: https://cran.r-project.org/web/checks/check_results_pillar.html +- [ ] WARN: r-release-macos-arm64 + +Check results at: https://cran.r-project.org/web/checks/check_results_pillar.html From 52918178c6d0f1b0f91e1d069cb3cdcdb6ef93fc Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Thu, 29 Jul 2021 05:13:44 +0200 Subject: [PATCH 098/147] Bump version to 1.6.2.9000 --- DESCRIPTION | 2 +- NEWS.md | 5 +++++ 2 files changed, 6 insertions(+), 1 deletion(-) diff --git a/DESCRIPTION b/DESCRIPTION index 989ddb7ba..cf37f81e9 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -1,6 +1,6 @@ Package: pillar Title: Coloured Formatting for Columns -Version: 1.6.2 +Version: 1.6.2.9000 Authors@R: c(person(given = "Kirill", family = "M\u00fcller", diff --git a/NEWS.md b/NEWS.md index ecd2a4814..262d86b90 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,5 +1,10 @@ +# pillar 1.6.2.9000 + +- Same as previous version. + + # pillar 1.6.2 - Same as previous version. From 231e398e5ffa15fec966b6c87bf40ea5c7d5f958 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Thu, 29 Jul 2021 05:24:33 +0200 Subject: [PATCH 099/147] NEWS and CRAN comments --- NEWS.md | 47 +++++++++++++++++------------------------------ cran-comments.md | 10 +++------- 2 files changed, 20 insertions(+), 37 deletions(-) diff --git a/NEWS.md b/NEWS.md index ecd2a4814..9d19ee5d7 100644 --- a/NEWS.md +++ b/NEWS.md @@ -2,53 +2,40 @@ # pillar 1.6.2 -- Same as previous version. +## Options - -# pillar 1.6.1.9006 - -- `print.tbl()` and `format.tbl()` support the `max_extra_cols` and `max_footer_lines` arguments that override the corresponding options (#360). -- `print.tbl()` and `format.tbl()` maps the now deprecated `n_extra` argument to `max_extra_cols` for consistency (#360). - - -# pillar 1.6.1.9005 - -- `num()` gains `extra_sigfig` argument to automatically show more significant figures for numbers of the same magnitude with subtle differences (#97). - Options `pillar.print_max`, `pillar.print_min`, `pillar.width` and `pillar.max_extra_cols` are now queried before the corresponding `tibble.` or `dplyr.` options are consulted, the latter will be soft-deprecated in pillar v2.0.0 (#353). - - -# pillar 1.6.1.9004 - - New `pillar.bidi` option. When active, control characters are inserted to improve display of data with right-to-left text (#333). - The new `pillar.max_footer_lines` option (default: 7) allows controlling the maximum number of footer lines shown. It is applied in addition to the existing `tibble.max_extra_cols` option (#263). -- Consistent definition of all options in one place, with internal accessors (#339). - -# pillar 1.6.1.9003 +## Formatting -- `obj_sum()` no longer calls `type_sum()` for vectors since pillar v1.6.1, this is now documented (#321). - If a column doesn't make use of all horizontal width offered to it, the excess width is distributed over other columns (#331). -- All pillars are shown with their true horizontal extent, irrespective of the indicated `width`. This simplifies the implementation of custom `pillar_shaft()` methods (#347). - Improved allocation of free space in multi-tier tables with `getOption("tibble.width") > getOption("width")` (#344). -- Avoid mangling of duplicate column names in footer (#332). +- All pillars are shown with their true horizontal extent, irrespective of the indicated `width`. This simplifies the implementation of custom `pillar_shaft()` methods (#347). +## Features -# pillar 1.6.1.9002 +- `num()` gains `extra_sigfig` argument to automatically show more significant figures for numbers of the same magnitude with subtle differences (#97). +- `print.tbl()` and `format.tbl()` support the `max_extra_cols` and `max_footer_lines` arguments that override the corresponding options (#360). +- `print.tbl()` and `format.tbl()` maps the now deprecated `n_extra` argument to `max_extra_cols` for consistency (#360). -- Using `attr(exact = TRUE)` everywhere. -- `is_vector_s3()` is no longer generic (#181). +## Bug fixes +- Avoid mangling of duplicate column names in footer (#332). +- Fix warning with zero of type `bit64::integer64()` (#319). -# pillar 1.6.1.9001 +## Documentation -- Fix internal logic around `vec_proxy()` and `vec_restore()` (#316). -- Fix warning with zero of type `bit64::integer64()` (#319). +- All package options are now documented in `?pillar_options` (#339). +- `obj_sum()` no longer calls `type_sum()` for vectors since pillar v1.6.1, this is now documented (#321). - Fix documentation on usage of `vctrs::vec_proxy()` and `vctrs::vec_restore()` (#322). +## Internal -# pillar 1.6.1.9000 - -- Same as previous version. +- Using `attr(exact = TRUE)` everywhere. +- `is_vector_s3()` is no longer generic (#181). +- Fix internal logic around `vec_proxy()` and `vec_restore()` (#316). # pillar 1.6.1 diff --git a/cran-comments.md b/cran-comments.md index 03e661ef4..5f1b8fbee 100644 --- a/cran-comments.md +++ b/cran-comments.md @@ -7,14 +7,10 @@ pillar 1.6.2 ## R CMD check results - [x] Checked locally, R 4.1.0 -- [ ] Checked on CI system, R 4.1.0 -- [ ] Checked on win-builder, R devel - -Check the boxes above after successful execution and remove this line. Then run `fledge::release()`. +- [x] Checked on CI system, R 4.1.0 +- [x] Checked on win-builder, R devel ## Current CRAN check results - [x] Checked on 2021-07-29, problems found: https://cran.r-project.org/web/checks/check_results_pillar.html -- [ ] WARN: r-release-macos-arm64 - -Check results at: https://cran.r-project.org/web/checks/check_results_pillar.html +- [x] WARN: r-release-macos-arm64: Insufficient pandoc version From 1058bda2280666278172f84535ab9cd67f8a6d42 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Thu, 29 Jul 2021 05:39:32 +0200 Subject: [PATCH 100/147] REVERT ME: Remove formattable from remotes --- DESCRIPTION | 2 -- 1 file changed, 2 deletions(-) diff --git a/DESCRIPTION b/DESCRIPTION index 989ddb7ba..001752aa1 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -60,5 +60,3 @@ Config/testthat/start-first: ctl_colonnade, ctl_colonnade_1, ctl_colonnade_2 -Remotes: - renkun-ken/formattable#154 From d5abc03b77db555682f0244ff66f6c1ea1b20e4b Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Thu, 29 Jul 2021 06:12:14 +0200 Subject: [PATCH 101/147] apt update --- .github/workflows/R-CMD-check-dev.yaml | 1 + .github/workflows/R-CMD-check.yaml | 1 + .github/workflows/pkgdown.yaml | 1 + .github/workflows/revdep.yaml | 1 + .github/workflows/test-coverage.yaml | 1 + 5 files changed, 5 insertions(+) diff --git a/.github/workflows/R-CMD-check-dev.yaml b/.github/workflows/R-CMD-check-dev.yaml index b7bdd9301..4696dcea5 100644 --- a/.github/workflows/R-CMD-check-dev.yaml +++ b/.github/workflows/R-CMD-check-dev.yaml @@ -241,6 +241,7 @@ jobs: - name: Install system dependencies if: runner.os == 'Linux' run: | + sudo apt-get update -y while read -r cmd do eval sudo $cmd diff --git a/.github/workflows/R-CMD-check.yaml b/.github/workflows/R-CMD-check.yaml index ea27b8d6b..f5f61cc1b 100644 --- a/.github/workflows/R-CMD-check.yaml +++ b/.github/workflows/R-CMD-check.yaml @@ -118,6 +118,7 @@ jobs: - name: Install system dependencies if: runner.os == 'Linux' run: | + sudo apt-get update -y while read -r cmd do eval sudo $cmd diff --git a/.github/workflows/pkgdown.yaml b/.github/workflows/pkgdown.yaml index 246ebc62d..2ef0bdf5e 100644 --- a/.github/workflows/pkgdown.yaml +++ b/.github/workflows/pkgdown.yaml @@ -92,6 +92,7 @@ jobs: - name: Install system dependencies if: runner.os == 'Linux' run: | + sudo apt-get update -y while read -r cmd do eval sudo $cmd diff --git a/.github/workflows/revdep.yaml b/.github/workflows/revdep.yaml index 59f0aed9b..628cba17b 100644 --- a/.github/workflows/revdep.yaml +++ b/.github/workflows/revdep.yaml @@ -112,6 +112,7 @@ jobs: - name: Install system dependencies if: runner.os == 'Linux' run: | + sudo apt-get update -y Rscript -e 'writeLines(remotes::system_requirements("ubuntu", "18.04")); package <- "${{ matrix.package }}"; deps <- tools::package_dependencies(package, which = "Suggests")[[1]]; lapply(c(package, deps), function(x) { writeLines(remotes::system_requirements("ubuntu", "18.04", package = x)) })' | sort | uniq > .github/deps.sh cat .github/deps.sh sudo sh < .github/deps.sh diff --git a/.github/workflows/test-coverage.yaml b/.github/workflows/test-coverage.yaml index 555737cd2..1bd2592e5 100644 --- a/.github/workflows/test-coverage.yaml +++ b/.github/workflows/test-coverage.yaml @@ -66,6 +66,7 @@ jobs: - name: Install system dependencies if: runner.os == 'Linux' run: | + sudo apt-get update -y while read -r cmd do eval sudo $cmd From 2a3b52b144480d92f2c17e8d50b1b587fe790176 Mon Sep 17 00:00:00 2001 From: Romain Francois Date: Tue, 21 Sep 2021 12:04:33 +0200 Subject: [PATCH 102/147] importFrom lifecycle ... instead of import lifecycle --- NAMESPACE | 3 ++- R/zzz.R | 2 +- 2 files changed, 3 insertions(+), 2 deletions(-) diff --git a/NAMESPACE b/NAMESPACE index 83d77dec4..4bcf165eb 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -148,10 +148,11 @@ export(tbl_format_setup) export(tbl_sum) export(type_sum) import(ellipsis) -import(lifecycle) import(rlang) importFrom(fansi,strip_sgr) importFrom(fansi,substr2_ctl) +importFrom(lifecycle,badge) +importFrom(lifecycle,deprecate_soft) importFrom(utf8,utf8_width) importFrom(utils,head) importFrom(utils,str) diff --git a/R/zzz.R b/R/zzz.R index 2ba70d656..b242d2014 100644 --- a/R/zzz.R +++ b/R/zzz.R @@ -2,7 +2,7 @@ #' @import rlang #' @import ellipsis -#' @import lifecycle +#' @importFrom lifecycle badge deprecate_soft #' @importFrom vctrs data_frame #' @importFrom vctrs new_data_frame #' @importFrom vctrs obj_print_footer From bd0d47f40bb7abe414eab019352202a0a3702df4 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Sun, 26 Sep 2021 11:29:08 +0200 Subject: [PATCH 103/147] Don't need badge --- DESCRIPTION | 2 +- NAMESPACE | 1 - R/zzz.R | 2 +- 3 files changed, 2 insertions(+), 3 deletions(-) diff --git a/DESCRIPTION b/DESCRIPTION index ba17cb7b2..bd4effca8 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -50,7 +50,7 @@ VignetteBuilder: knitr Encoding: UTF-8 Roxygen: list(markdown = TRUE) -RoxygenNote: 7.1.1.9001 +RoxygenNote: 7.1.2 Config/testthat/edition: 3 Config/testthat/parallel: true Config/testthat/start-first: diff --git a/NAMESPACE b/NAMESPACE index 4bcf165eb..a4d1a739e 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -151,7 +151,6 @@ import(ellipsis) import(rlang) importFrom(fansi,strip_sgr) importFrom(fansi,substr2_ctl) -importFrom(lifecycle,badge) importFrom(lifecycle,deprecate_soft) importFrom(utf8,utf8_width) importFrom(utils,head) diff --git a/R/zzz.R b/R/zzz.R index b242d2014..567bd8638 100644 --- a/R/zzz.R +++ b/R/zzz.R @@ -2,7 +2,7 @@ #' @import rlang #' @import ellipsis -#' @importFrom lifecycle badge deprecate_soft +#' @importFrom lifecycle deprecate_soft #' @importFrom vctrs data_frame #' @importFrom vctrs new_data_frame #' @importFrom vctrs obj_print_footer From 7c661f11ff5043528c75ac885a9853cacdc4e915 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Sun, 26 Sep 2021 11:29:59 +0200 Subject: [PATCH 104/147] Bump version to 1.6.2.9001 --- DESCRIPTION | 2 +- NEWS.md | 5 +++++ 2 files changed, 6 insertions(+), 1 deletion(-) diff --git a/DESCRIPTION b/DESCRIPTION index bd4effca8..cd9dfa5e7 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -1,6 +1,6 @@ Package: pillar Title: Coloured Formatting for Columns -Version: 1.6.2.9000 +Version: 1.6.2.9001 Authors@R: c(person(given = "Kirill", family = "M\u00fcller", diff --git a/NEWS.md b/NEWS.md index c47d9a177..30a61a61b 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,5 +1,10 @@ +# pillar 1.6.2.9001 + +- Avoid blanket import for lifecycle package for compatibility with upcoming rlang (#368, @romainfrancois). + + # pillar 1.6.2.9000 - Same as previous version. From 24750a6a441f4f1aa2384c867c0eeead62ff739c Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Sun, 26 Sep 2021 11:31:40 +0200 Subject: [PATCH 105/147] Check dev versions also for CRAN release --- .github/workflows/R-CMD-check-dev.yaml | 2 ++ 1 file changed, 2 insertions(+) diff --git a/.github/workflows/R-CMD-check-dev.yaml b/.github/workflows/R-CMD-check-dev.yaml index 4696dcea5..4e92fb978 100644 --- a/.github/workflows/R-CMD-check-dev.yaml +++ b/.github/workflows/R-CMD-check-dev.yaml @@ -6,6 +6,8 @@ on: push: paths: - ".github/workflows/R-CMD-check-dev.yaml" + branches: + - "cran-*" name: rcc dev From f4529545bbd2621345c76670085d84a477eece97 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Sun, 26 Sep 2021 12:26:13 +0200 Subject: [PATCH 106/147] Bump version to 1.6.3 --- DESCRIPTION | 2 +- NEWS.md | 5 +++++ 2 files changed, 6 insertions(+), 1 deletion(-) diff --git a/DESCRIPTION b/DESCRIPTION index cd9dfa5e7..0f286f3e3 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -1,6 +1,6 @@ Package: pillar Title: Coloured Formatting for Columns -Version: 1.6.2.9001 +Version: 1.6.3 Authors@R: c(person(given = "Kirill", family = "M\u00fcller", diff --git a/NEWS.md b/NEWS.md index 30a61a61b..2d18ee567 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,5 +1,10 @@ +# pillar 1.6.3 + +- Same as previous version. + + # pillar 1.6.2.9001 - Avoid blanket import for lifecycle package for compatibility with upcoming rlang (#368, @romainfrancois). From a286866e496b200a443410cb866a116b94a93fd2 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Sun, 26 Sep 2021 12:26:16 +0200 Subject: [PATCH 107/147] Update CRAN comments --- cran-comments.md | 17 ++++++++++------- 1 file changed, 10 insertions(+), 7 deletions(-) diff --git a/cran-comments.md b/cran-comments.md index 5f1b8fbee..acd70000e 100644 --- a/cran-comments.md +++ b/cran-comments.md @@ -1,16 +1,19 @@ -pillar 1.6.2 +pillar 1.6.3 ## Cran Repository Policy -- [x] Reviewed CRP last edited 2021-04-25. +- [ ] Reviewed CRP last edited 2021-09-25. + +See changes at https://github.com/eddelbuettel/crp/compare/master@%7B2021-04-25%7D...master@%7B2021-09-25%7D ## R CMD check results -- [x] Checked locally, R 4.1.0 -- [x] Checked on CI system, R 4.1.0 -- [x] Checked on win-builder, R devel +- [x] Checked locally, R 4.1.1 +- [ ] Checked on CI system, R 4.1.1 +- [ ] Checked on win-builder, R devel + +Check the boxes above after successful execution and remove this line. Then run `fledge::release()`. ## Current CRAN check results -- [x] Checked on 2021-07-29, problems found: https://cran.r-project.org/web/checks/check_results_pillar.html -- [x] WARN: r-release-macos-arm64: Insufficient pandoc version +- [x] Checked on 2021-09-26, no problems found. From ed5a1c9988b572ee7c89c21b7763d6bb08b2d671 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Sun, 26 Sep 2021 12:26:20 +0200 Subject: [PATCH 108/147] Bump version to 1.6.3.9000 --- DESCRIPTION | 2 +- NEWS.md | 5 +++++ 2 files changed, 6 insertions(+), 1 deletion(-) diff --git a/DESCRIPTION b/DESCRIPTION index 0f286f3e3..10f13fd9b 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -1,6 +1,6 @@ Package: pillar Title: Coloured Formatting for Columns -Version: 1.6.3 +Version: 1.6.3.9000 Authors@R: c(person(given = "Kirill", family = "M\u00fcller", diff --git a/NEWS.md b/NEWS.md index 2d18ee567..7a0447b52 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,5 +1,10 @@ +# pillar 1.6.3.9000 + +- Same as previous version. + + # pillar 1.6.3 - Same as previous version. From 136d50f795aec864215194bf51b8c01012499988 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Sun, 26 Sep 2021 14:13:43 +0200 Subject: [PATCH 109/147] Oops --- .github/workflows/R-CMD-check-dev.yaml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.github/workflows/R-CMD-check-dev.yaml b/.github/workflows/R-CMD-check-dev.yaml index 4e92fb978..1001bbb48 100644 --- a/.github/workflows/R-CMD-check-dev.yaml +++ b/.github/workflows/R-CMD-check-dev.yaml @@ -6,7 +6,7 @@ on: push: paths: - ".github/workflows/R-CMD-check-dev.yaml" - branches: + branches: - "cran-*" name: rcc dev From c1f7644324f39d0e1c0ff3ecaa3ed74074df9e7f Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Sun, 26 Sep 2021 14:14:14 +0200 Subject: [PATCH 110/147] NEWS and CRAN comments --- NEWS.md | 10 ---------- cran-comments.md | 10 +++------- 2 files changed, 3 insertions(+), 17 deletions(-) diff --git a/NEWS.md b/NEWS.md index 2d18ee567..3aff3726c 100644 --- a/NEWS.md +++ b/NEWS.md @@ -2,19 +2,9 @@ # pillar 1.6.3 -- Same as previous version. - - -# pillar 1.6.2.9001 - - Avoid blanket import for lifecycle package for compatibility with upcoming rlang (#368, @romainfrancois). -# pillar 1.6.2.9000 - -- Same as previous version. - - # pillar 1.6.2 ## Options diff --git a/cran-comments.md b/cran-comments.md index acd70000e..a507e33bd 100644 --- a/cran-comments.md +++ b/cran-comments.md @@ -2,17 +2,13 @@ pillar 1.6.3 ## Cran Repository Policy -- [ ] Reviewed CRP last edited 2021-09-25. - -See changes at https://github.com/eddelbuettel/crp/compare/master@%7B2021-04-25%7D...master@%7B2021-09-25%7D +- [x] Reviewed CRP last edited 2021-09-25. ## R CMD check results - [x] Checked locally, R 4.1.1 -- [ ] Checked on CI system, R 4.1.1 -- [ ] Checked on win-builder, R devel - -Check the boxes above after successful execution and remove this line. Then run `fledge::release()`. +- [x] Checked on CI system, R 4.1.1 +- [x] Checked on win-builder, R devel ## Current CRAN check results From 427350cba9eeccb75d7dae65bfec03087e522eb7 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Sun, 26 Sep 2021 14:14:58 +0200 Subject: [PATCH 111/147] Revert "Oops" This reverts commit 136d50f795aec864215194bf51b8c01012499988. --- .github/workflows/R-CMD-check-dev.yaml | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.github/workflows/R-CMD-check-dev.yaml b/.github/workflows/R-CMD-check-dev.yaml index 1001bbb48..4e92fb978 100644 --- a/.github/workflows/R-CMD-check-dev.yaml +++ b/.github/workflows/R-CMD-check-dev.yaml @@ -6,7 +6,7 @@ on: push: paths: - ".github/workflows/R-CMD-check-dev.yaml" - branches: + branches: - "cran-*" name: rcc dev From 6825afa1f8d835ceeb456ffc5c2b43661128e7cf Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Sun, 26 Sep 2021 14:15:10 +0200 Subject: [PATCH 112/147] Two --- .github/workflows/R-CMD-check-dev.yaml | 1 + 1 file changed, 1 insertion(+) diff --git a/.github/workflows/R-CMD-check-dev.yaml b/.github/workflows/R-CMD-check-dev.yaml index 4e92fb978..b4eee442a 100644 --- a/.github/workflows/R-CMD-check-dev.yaml +++ b/.github/workflows/R-CMD-check-dev.yaml @@ -6,6 +6,7 @@ on: push: paths: - ".github/workflows/R-CMD-check-dev.yaml" + push: branches: - "cran-*" From 3a77427569926262652142ec100d6fdda5d709fd Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Sun, 26 Sep 2021 14:15:53 +0200 Subject: [PATCH 113/147] One --- .github/workflows/R-CMD-check-dev.yaml | 3 --- 1 file changed, 3 deletions(-) diff --git a/.github/workflows/R-CMD-check-dev.yaml b/.github/workflows/R-CMD-check-dev.yaml index b4eee442a..374d1cace 100644 --- a/.github/workflows/R-CMD-check-dev.yaml +++ b/.github/workflows/R-CMD-check-dev.yaml @@ -3,9 +3,6 @@ on: schedule: - cron: '5 0 * * *' - push: - paths: - - ".github/workflows/R-CMD-check-dev.yaml" push: branches: - "cran-*" From 94e9e619a29387b3446b3a503905eab6d2ceaa6d Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Sun, 17 Oct 2021 07:15:16 +0200 Subject: [PATCH 114/147] - Avoid nested backtick blocks in vignette. --- vignettes/numbers.Rmd | 32 ++++++++++++++++---------------- 1 file changed, 16 insertions(+), 16 deletions(-) diff --git a/vignettes/numbers.Rmd b/vignettes/numbers.Rmd index 0b0f88b01..5aa2b6cb1 100644 --- a/vignettes/numbers.Rmd +++ b/vignettes/numbers.Rmd @@ -127,7 +127,7 @@ FIXME ### units -```{r numbers-17} +xxx{r numbers-17} library(units) set_units.pillar_num <- function(x, ...) { @@ -150,11 +150,11 @@ tibble( digits_int = set_num_opts(km, digits = 4) + m, sci_ext = set_units(num(1:3, notation = "sci"), m) + km ) -``` +xxx ### formattable -```{r numbers-18, error = TRUE} +xxx{r numbers-18, error = TRUE} library(formattable) pillar_shaft.formattable <- function(x, ...) { @@ -198,11 +198,11 @@ tibble( percent = num_percent(1:3 * 0.1 + 0.001), scientific = num_scientific(1:3 * 0.1 + 0.001) ) -``` +xxx ### scales -```{r numbers-scales, error = TRUE} +xxx{r numbers-scales, error = TRUE} library(scales) x <- num(1:10 / 100, label = "%", scale = 100) @@ -213,11 +213,11 @@ x < 0 x < 0L scales::cscale(x, scales::rescale_pal()) -``` +xxx ### ggplot2 -```{r numbers-19} +xxx{r numbers-19} library(ggplot2) scale_type.pillar_num <- function(x, ...) { @@ -227,13 +227,13 @@ scale_type.pillar_num <- function(x, ...) { data.frame(x = x, y = 1:10) %>% ggplot(aes(x = x, y = y)) %>% + geom_point() -``` +xxx ## Rule-based decoration -```{r} +xxx{r} library(dplyr) data_units <- @@ -243,25 +243,25 @@ data_units <- data_units %>% mutate(bill_area = bill_length_mm * bill_depth_mm, .after = island) -``` +xxx -```{r eval = FALSE} +xxx{r eval = FALSE} data_decor <- data_units %>% decorate(year, digits = 0) %>% decorate(where(is.numeric), digits = 3) -``` +xxx -```{r eval = FALSE} +xxx{r eval = FALSE} data_decor %>% mutate(bill_area = bill_length_mm * bill_depth_mm, .after = island) -``` +xxx -```{r echo = FALSE} +xxx{r echo = FALSE} data_units %>% mutate(bill_area = bill_length_mm * bill_depth_mm, .after = island) %>% mutate(across(year, set_num_opts, digits = 0)) %>% mutate(across(where(is.numeric), set_num_opts, digits = 3)) -``` +xxx ````` From 917f280988e4f9751baf6c6a4b53e9e6bca48cb0 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Sun, 17 Oct 2021 07:20:27 +0200 Subject: [PATCH 115/147] - `num()` requires an integerish `digits` argument (#362). Closes #362. --- R/num.R | 1 + 1 file changed, 1 insertion(+) diff --git a/R/num.R b/R/num.R index 721eab59f..75c01c31c 100644 --- a/R/num.R +++ b/R/num.R @@ -116,6 +116,7 @@ num <- function(x, ..., extra_sigfig = NULL) { stopifnot(is.numeric(x)) + stopifnot(is.null(digits) || is_integerish(digits)) check_dots_empty() # FIXME: math and arith should also work for integers From 4e68b21da9a72ef589393ff1f51f76f68da9c961 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Sun, 17 Oct 2021 07:33:48 +0200 Subject: [PATCH 116/147] df_all -> df_all() --- tests/testthat/_snaps/ctl_colonnade.md | 16 ++++++++-------- tests/testthat/_snaps/format_multi.md | 16 ++++++++-------- tests/testthat/_snaps/glimpse.md | 6 +++--- tests/testthat/_snaps/tbl-format-body.md | 4 ++-- tests/testthat/helper-output.R | 4 ++-- tests/testthat/test-ctl_colonnade.R | 16 ++++++++-------- tests/testthat/test-format_multi.R | 16 ++++++++-------- tests/testthat/test-glimpse.R | 6 +++--- tests/testthat/test-tbl-format-body.R | 4 ++-- 9 files changed, 44 insertions(+), 44 deletions(-) diff --git a/tests/testthat/_snaps/ctl_colonnade.md b/tests/testthat/_snaps/ctl_colonnade.md index fcd34f973..049f8c29c 100644 --- a/tests/testthat/_snaps/ctl_colonnade.md +++ b/tests/testthat/_snaps/ctl_colonnade.md @@ -111,7 +111,7 @@ Code - ctl_colonnade(df_all, width = 30) + ctl_colonnade(df_all(), width = 30) Output $body a b c d @@ -165,7 +165,7 @@ Code - ctl_colonnade(df_all, width = 300) + ctl_colonnade(df_all(), width = 300) Output $body a b c d e f g h @@ -184,7 +184,7 @@ Code options(width = 70) - ctl_colonnade(df_all, width = 300) + ctl_colonnade(df_all(), width = 300) Output $body a b c d e f g @@ -203,7 +203,7 @@ Code options(width = 60) - ctl_colonnade(df_all, width = 300) + ctl_colonnade(df_all(), width = 300) Output $body a b c d e f @@ -222,7 +222,7 @@ Code options(width = 50) - ctl_colonnade(df_all, width = 300) + ctl_colonnade(df_all(), width = 300) Output $body a b c d e f @@ -241,7 +241,7 @@ Code options(width = 40) - ctl_colonnade(df_all, width = 300) + ctl_colonnade(df_all(), width = 300) Output $body a b c d e @@ -265,7 +265,7 @@ Code options(width = 30) - ctl_colonnade(df_all, width = 300) + ctl_colonnade(df_all(), width = 300) Output $body a b c d @@ -294,7 +294,7 @@ Code options(width = 20) - ctl_colonnade(df_all, width = 300) + ctl_colonnade(df_all(), width = 300) Output $body a b c diff --git a/tests/testthat/_snaps/format_multi.md b/tests/testthat/_snaps/format_multi.md index 0c337dc20..df587163b 100644 --- a/tests/testthat/_snaps/format_multi.md +++ b/tests/testthat/_snaps/format_multi.md @@ -385,7 +385,7 @@ 2 4.9 3 4.7 Code - colonnade(df_all, width = 30) + colonnade(df_all(), width = 30) Output a b c d @@ -393,7 +393,7 @@ 2 2.5 2 FALSE b 3 NA NA NA Code - colonnade(df_all, width = 300) + colonnade(df_all(), width = 300) Output a b c d e f g h @@ -407,7 +407,7 @@ 3 Code options(width = 70) - colonnade(df_all, width = 300) + colonnade(df_all(), width = 300) Output a b c d e f g @@ -421,7 +421,7 @@ 3 Code options(width = 60) - colonnade(df_all, width = 300) + colonnade(df_all(), width = 300) Output a b c d e f @@ -435,7 +435,7 @@ 3 NA Code options(width = 50) - colonnade(df_all, width = 300) + colonnade(df_all(), width = 300) Output a b c d e f @@ -449,7 +449,7 @@ 3 NA Code options(width = 40) - colonnade(df_all, width = 300) + colonnade(df_all(), width = 300) Output a b c d e @@ -468,7 +468,7 @@ 3 Code options(width = 30) - colonnade(df_all, width = 300) + colonnade(df_all(), width = 300) Output a b c d @@ -492,7 +492,7 @@ 3 Code options(width = 20) - colonnade(df_all, width = 300) + colonnade(df_all(), width = 300) Output a b c diff --git a/tests/testthat/_snaps/glimpse.md b/tests/testthat/_snaps/glimpse.md index ec0bf2c30..700cee001 100644 --- a/tests/testthat/_snaps/glimpse.md +++ b/tests/testthat/_snaps/glimpse.md @@ -141,7 +141,7 @@ $ `mean(x)` 5 $ `var(x)` 3 Code - glimpse(as_tbl(df_all), width = 70L) + glimpse(as_tbl(df_all()), width = 70L) Output Rows: 3 Columns: 9 @@ -156,7 +156,7 @@ $ i [1, <2, 3>], [<4, 5, 6>], [NA] Code # options(tibble.width = 50) - withr::with_options(list(tibble.width = 50), glimpse(as_tbl(df_all))) + withr::with_options(list(tibble.width = 50), glimpse(as_tbl(df_all()))) Output Rows: 3 Columns: 9 @@ -171,7 +171,7 @@ $ i [1, <2, 3>], [<4, 5, 6>], [NA] Code # options(tibble.width = 35) - withr::with_options(list(tibble.width = 35), glimpse(as_tbl(df_all))) + withr::with_options(list(tibble.width = 35), glimpse(as_tbl(df_all()))) Output Rows: 3 Columns: 9 diff --git a/tests/testthat/_snaps/tbl-format-body.md b/tests/testthat/_snaps/tbl-format-body.md index c1e74c1b7..dc23b4c0a 100644 --- a/tests/testthat/_snaps/tbl-format-body.md +++ b/tests/testthat/_snaps/tbl-format-body.md @@ -2,7 +2,7 @@ Code # Various column types - tbl_format_body(tbl_format_setup(df_all, width = 30)) + tbl_format_body(tbl_format_setup(df_all(), width = 30)) Output a b c d @@ -11,7 +11,7 @@ 2 2.5 2 FALSE b 3 NA NA NA Code - tbl_format_body(tbl_format_setup(df_all, width = 300)) + tbl_format_body(tbl_format_setup(df_all(), width = 300)) Output a b c d e f g h diff --git a/tests/testthat/helper-output.R b/tests/testthat/helper-output.R index 7e8c9c9f0..92b8f24ed 100644 --- a/tests/testthat/helper-output.R +++ b/tests/testthat/helper-output.R @@ -3,7 +3,7 @@ show_output_in_terminal <- function() { } # A data frame with all major types -df_all <- new_tbl(list( +df_all <- function() new_tbl(list( a = c(1, 2.5, NA), b = c(1:2, NA), c = c(T, F, NA), @@ -17,7 +17,7 @@ df_all <- new_tbl(list( # A data frame with strings of varying lengths long_str <- strrep("Abcdefghij", 5) -df_str <- map(rlang::set_names(1:50), function(i) substr(long_str, 1, i)) +df_str <- purrr::map(rlang::set_names(1:50), function(i) substr(long_str, 1, i)) #' `add_special()` is not exported, and used only for initializing default #' values to `expect_pillar_output()`. diff --git a/tests/testthat/test-ctl_colonnade.R b/tests/testthat/test-ctl_colonnade.R index c40765a13..acd10ec4c 100644 --- a/tests/testthat/test-ctl_colonnade.R +++ b/tests/testthat/test-ctl_colonnade.R @@ -12,20 +12,20 @@ test_that("tests from tibble", { ctl_colonnade(mtcars[1:8, ], has_row_id = "*", width = 30) ctl_colonnade(iris[1:5, ], width = 30) ctl_colonnade(iris[1:3, ], width = 20) - ctl_colonnade(df_all, width = 30) - ctl_colonnade(df_all, width = 300) + ctl_colonnade(df_all(), width = 30) + ctl_colonnade(df_all(), width = 300) options(width = 70) - ctl_colonnade(df_all, width = 300) + ctl_colonnade(df_all(), width = 300) options(width = 60) - ctl_colonnade(df_all, width = 300) + ctl_colonnade(df_all(), width = 300) options(width = 50) - ctl_colonnade(df_all, width = 300) + ctl_colonnade(df_all(), width = 300) options(width = 40) - ctl_colonnade(df_all, width = 300) + ctl_colonnade(df_all(), width = 300) options(width = 30) - ctl_colonnade(df_all, width = 300) + ctl_colonnade(df_all(), width = 300) options(width = 20) - ctl_colonnade(df_all, width = 300) + ctl_colonnade(df_all(), width = 300) ctl_colonnade(list(`\n` = c("\n", '"'), `\r` = factor(c("\n", "\n"))), width = 30) ctl_colonnade(list(a = c("", " ", "a ", " a")), width = 30) ctl_colonnade(list("mean(x)" = 5, "var(x)" = 3), width = 30) diff --git a/tests/testthat/test-format_multi.R b/tests/testthat/test-format_multi.R index 258b96b86..029bc5a14 100644 --- a/tests/testthat/test-format_multi.R +++ b/tests/testthat/test-format_multi.R @@ -102,20 +102,20 @@ test_that("tests from tibble", { colonnade(mtcars[1:8, ], has_row_id = "*", width = 30) colonnade(iris[1:5, ], width = 30) colonnade(iris[1:3, ], width = 20) - colonnade(df_all, width = 30) - colonnade(df_all, width = 300) + colonnade(df_all(), width = 30) + colonnade(df_all(), width = 300) options(width = 70) - colonnade(df_all, width = 300) + colonnade(df_all(), width = 300) options(width = 60) - colonnade(df_all, width = 300) + colonnade(df_all(), width = 300) options(width = 50) - colonnade(df_all, width = 300) + colonnade(df_all(), width = 300) options(width = 40) - colonnade(df_all, width = 300) + colonnade(df_all(), width = 300) options(width = 30) - colonnade(df_all, width = 300) + colonnade(df_all(), width = 300) options(width = 20) - colonnade(df_all, width = 300) + colonnade(df_all(), width = 300) colonnade(list(`\n` = c("\n", '"'), `\r` = factor("\n")), width = 30) colonnade(list(a = c("", " ", "a ", " a")), width = 30) colonnade(list("mean(x)" = 5, "var(x)" = 3), width = 30) diff --git a/tests/testthat/test-glimpse.R b/tests/testthat/test-glimpse.R index b34782653..a5d760ed8 100644 --- a/tests/testthat/test-glimpse.R +++ b/tests/testthat/test-glimpse.R @@ -70,18 +70,18 @@ test_that("output test for glimpse()", { df <- tibble::tibble(!!!set_names(c(5, 3), c("mean(x)", "var(x)"))) glimpse(df, width = 28) - glimpse(as_tbl(df_all), width = 70L) + glimpse(as_tbl(df_all()), width = 70L) "options(tibble.width = 50)" withr::with_options( list(tibble.width = 50), - glimpse(as_tbl(df_all)) + glimpse(as_tbl(df_all())) ) "options(tibble.width = 35)" withr::with_options( list(tibble.width = 35), - glimpse(as_tbl(df_all)) + glimpse(as_tbl(df_all())) ) "non-tibble" diff --git a/tests/testthat/test-tbl-format-body.R b/tests/testthat/test-tbl-format-body.R index 5397fffe3..54b4ba1ca 100644 --- a/tests/testthat/test-tbl-format-body.R +++ b/tests/testthat/test-tbl-format-body.R @@ -1,9 +1,9 @@ test_that("tbl_format_body() results", { expect_snapshot({ "Various column types" - tbl_format_body(tbl_format_setup(df_all, width = 30)) + tbl_format_body(tbl_format_setup(df_all(), width = 30)) - tbl_format_body(tbl_format_setup(df_all, width = 300)) + tbl_format_body(tbl_format_setup(df_all(), width = 300)) "POSIXct and POSIXlt" df <- new_tbl(list(x = as.POSIXct("2016-01-01 12:34:56 GMT") + 1:12)) From 2c741920917a9a1191cdf70fd40545d7e1c93b7a Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Sun, 17 Oct 2021 07:34:34 +0200 Subject: [PATCH 117/147] Switch to edition 2 for running old function --- R/testthat.R | 1 + 1 file changed, 1 insertion(+) diff --git a/R/testthat.R b/R/testthat.R index 7066e5456..09ce62a5e 100644 --- a/R/testthat.R +++ b/R/testthat.R @@ -63,6 +63,7 @@ expect_known_display <- function(object, file, ..., width = 80L, crayon = TRUE) num_colors(forget = TRUE) }) + testthat::local_edition(2) testthat::expect_known_output(print(eval_tidy(object)), file, update = TRUE, width = width) } # nocov end From 913f8c8595f7b0dd80116c02eac716682f3c62e6 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Sun, 17 Oct 2021 07:35:17 +0200 Subject: [PATCH 118/147] Remove extra_cols() example --- R/multi.R | 2 -- man/extra_cols.Rd | 3 --- 2 files changed, 5 deletions(-) diff --git a/R/multi.R b/R/multi.R index 52efee7cd..027b58b0e 100644 --- a/R/multi.R +++ b/R/multi.R @@ -245,8 +245,6 @@ knit_print_squeezed_colonnade_tier <- function(x) { #' @inheritParams ellipsis::dots_used #' @keywords internal #' @export -#' @examples -#' extra_cols(squeeze(colonnade(list(a = 1:3, b = 4:6), width = 8))) extra_cols <- function(x, ...) { deprecate_soft("1.5.0", "pillar::extra_cols()") diff --git a/man/extra_cols.Rd b/man/extra_cols.Rd index c16c0de5f..e9b75dbc2 100644 --- a/man/extra_cols.Rd +++ b/man/extra_cols.Rd @@ -23,7 +23,4 @@ Formatting a \link{colonnade} object may lead to some columns being omitted due to width restrictions. This method returns a character vector that describes each of the omitted columns. } -\examples{ -extra_cols(squeeze(colonnade(list(a = 1:3, b = 4:6), width = 8))) -} \keyword{internal} From 8e1fd059bb79214ea62822f415e6760416c9b0d6 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Sun, 17 Oct 2021 07:37:49 +0200 Subject: [PATCH 119/147] Remove squeeze() example --- R/multi.R | 4 ---- man/squeeze.Rd | 5 ----- 2 files changed, 9 deletions(-) diff --git a/R/multi.R b/R/multi.R index 027b58b0e..d8ca22166 100644 --- a/R/multi.R +++ b/R/multi.R @@ -124,10 +124,6 @@ new_empty_col_sentinel <- function(type) { #' #' @keywords internal #' @export -#' @examples -#' long_string <- list(paste(letters, collapse = " ")) -#' squeeze(colonnade(long_string), width = 40) -#' squeeze(colonnade(long_string), width = 20) squeeze <- function(x, width = NULL, ...) { deprecate_soft("1.5.0", "pillar::squeeze()") diff --git a/man/squeeze.Rd b/man/squeeze.Rd index e0807547c..eddcf715c 100644 --- a/man/squeeze.Rd +++ b/man/squeeze.Rd @@ -12,9 +12,4 @@ It returns an object suitable for printing and formatting at a fixed width with additional information about omitted columns, which can be retrieved via \code{\link[=extra_cols]{extra_cols()}}. } -\examples{ -long_string <- list(paste(letters, collapse = " ")) -squeeze(colonnade(long_string), width = 40) -squeeze(colonnade(long_string), width = 20) -} \keyword{internal} From 3bb46dd774e83576dd6a448e482ee059c0e1a3bc Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Sun, 17 Oct 2021 07:50:44 +0200 Subject: [PATCH 120/147] Recent updates - Reduce parallelism - Also check dev on cran-* branches - Update hash key for dev - Remove R 3.3 --- .github/workflows/R-CMD-check-dev.yaml | 4 ++-- .github/workflows/R-CMD-check.yaml | 6 +----- 2 files changed, 3 insertions(+), 7 deletions(-) diff --git a/.github/workflows/R-CMD-check-dev.yaml b/.github/workflows/R-CMD-check-dev.yaml index 374d1cace..36c91df42 100644 --- a/.github/workflows/R-CMD-check-dev.yaml +++ b/.github/workflows/R-CMD-check-dev.yaml @@ -235,8 +235,8 @@ jobs: uses: actions/cache@v2 with: path: ${{ env.R_LIBS_USER }} - key: ubuntu-18.04-r-dev-release-${{ matrix.package }}-${{steps.date.outputs.date}} - restore-keys: ubuntu-18.04-r-dev-release-${{ matrix.package }}- + key: ubuntu-18.04-r-dev-release-${{ matrix.package }}-1-${{steps.date.outputs.date}} + restore-keys: ubuntu-18.04-r-dev-release-${{ matrix.package }}-1- - name: Install system dependencies if: runner.os == 'Linux' diff --git a/.github/workflows/R-CMD-check.yaml b/.github/workflows/R-CMD-check.yaml index f5f61cc1b..d15825871 100644 --- a/.github/workflows/R-CMD-check.yaml +++ b/.github/workflows/R-CMD-check.yaml @@ -33,7 +33,7 @@ jobs: fail-fast: false # Ensure that the "cancel" workflow gets a chance to run quickly, even if we just pushed # Need to figure out how to smoke-test - max-parallel: 6 + max-parallel: 5 matrix: config: - { os: macOS-latest, r: 'release' } @@ -56,10 +56,6 @@ jobs: - {os: ubuntu-, os-version: 18.04, r: '3.4', rspm: "https://packagemanager.rstudio.com/cran/__linux__/bionic/latest"} # End custom: R 3.4 - # Begin custom: R 3.3 - - {os: ubuntu-, os-version: 18.04, r: '3.3', rspm: "https://packagemanager.rstudio.com/cran/__linux__/bionic/latest"} - # End custom: R 3.3 - # Begin custom: matrix elements # End custom: matrix elements env: From 1f59eff626dc50975a70545c5d6be4186f164794 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Sun, 17 Oct 2021 11:07:02 +0200 Subject: [PATCH 121/147] Remove dead code --- R/multi.R | 24 ------------------------ 1 file changed, 24 deletions(-) diff --git a/R/multi.R b/R/multi.R index 52efee7cd..e0f76a247 100644 --- a/R/multi.R +++ b/R/multi.R @@ -485,30 +485,6 @@ distribute_pillars_rev <- function(widths, tier_widths) { ret } -distribute_pillars_offset <- function(widths, tier_widths, - widths_offset, tier_widths_offset) { - tier_widths <- tier_widths[seq2(tier_widths_offset, length(tier_widths))] - if (length(tier_widths) == 0) { - # Work around corner case - return(distribute_pillars(integer(), integer())) - } - - widths <- widths[seq2(widths_offset, length(widths))] - fit_cut <- distribute_pillars(widths, tier_widths) - add_pillars_offset(fit_cut, widths_offset, tier_widths_offset) -} - -add_pillars_offset <- function(fit_cut, widths_offset, tier_widths_offset) { - if (tier_widths_offset == 1) { - # Work around corner case - return(fit_cut) - } - - fit_cut$id <- fit_cut$id + (widths_offset - 1L) - fit_cut$tier <- fit_cut$tier + (tier_widths_offset - 1L) - fit_cut -} - all_pillars_fit <- function(tier_df) { rows <- nrow(tier_df) rows == 0 || !safe_any_na(tier_df$tier[[nrow(tier_df)]]) From ba23e1341ea14e6e9d40e78f4d2aac5925dba6b2 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Sun, 17 Oct 2021 11:11:50 +0200 Subject: [PATCH 122/147] offset -> offset_after --- R/multi.R | 18 ++-- tests/testthat/_snaps/multi.md | 180 ++++++++++++++++----------------- 2 files changed, 99 insertions(+), 99 deletions(-) diff --git a/R/multi.R b/R/multi.R index e0f76a247..0df09bf0b 100644 --- a/R/multi.R +++ b/R/multi.R @@ -414,7 +414,7 @@ combine_pillar_distributions <- function(max_fit, min_fit_rev, tier_widths) { #' 3. We consult the column offsets. The last column where the minimum assignment #' has a greater or equal offset than the maximum assignment is our latest #' cut point. - cut_point_candidate_idx <- which(max_fit$offset[cut_point_candidates] <= min_fit_rev$offset[cut_point_candidates]) + cut_point_candidate_idx <- which(max_fit$offset_after[cut_point_candidates] <= min_fit_rev$offset_after[cut_point_candidates]) if (length(cut_point_candidate_idx) > 0) { cut_point <- cut_point_candidates[max(cut_point_candidate_idx)] } else { @@ -435,7 +435,7 @@ combine_pillar_distributions <- function(max_fit, min_fit_rev, tier_widths) { #' @aliases NULL distribute_pillars <- function(widths, tier_widths) { tier <- rep(NA_integer_, length(widths)) - offset <- rep(NA_integer_, length(widths)) + offset_after <- rep(NA_integer_, length(widths)) current_tier <- 1L current_x <- 0L @@ -458,11 +458,11 @@ distribute_pillars <- function(widths, tier_widths) { tier[[i]] <- current_tier current_x <- current_x + widths[[i]] - offset[[i]] <- current_x + offset_after[[i]] <- current_x current_x <- current_x + 1L } - data_frame(id = seq_along(widths), width = widths, tier = tier, offset = offset) + data_frame(id = seq_along(widths), width = widths, tier = tier, offset_after = offset_after) } distribute_pillars_rev <- function(widths, tier_widths) { @@ -474,13 +474,13 @@ distribute_pillars_rev <- function(widths, tier_widths) { splits <- unname(split(seq_along(tier), tier)) tier_widths <- tier_widths[seq_along(splits)] - new_offset <- unlist(map2(splits, tier_widths, function(.x, .y) { - offsets <- ret$offset[.x] - new_offset <- max(offsets) - offsets - new_offset - max(new_offset) + .y + new_offset_after <- unlist(map2(splits, tier_widths, function(.x, .y) { + offset_afters <- ret$offset_after[.x] + new_offset_after <- max(offset_afters) - offset_afters + new_offset_after - max(new_offset_after) + .y })) - ret$offset <- c(new_offset, rep(NA_integer_, sum(is.na(tier)))) + ret$offset_after <- c(new_offset_after, rep(NA_integer_, sum(is.na(tier)))) ret } diff --git a/tests/testthat/_snaps/multi.md b/tests/testthat/_snaps/multi.md index 79f388049..c236d6a51 100644 --- a/tests/testthat/_snaps/multi.md +++ b/tests/testthat/_snaps/multi.md @@ -3,151 +3,151 @@ Code colonnade_compute_tiered_col_widths_df(rep(30, 4), rep(15, 4), rep(60, 4)) Output - id width tier offset - 1 1 30 1 30 - 2 2 30 2 30 - 3 3 30 3 30 - 4 4 30 4 30 + id width tier offset_after + 1 1 30 1 30 + 2 2 30 2 30 + 3 3 30 3 30 + 4 4 30 4 30 Code colonnade_compute_tiered_col_widths_df(rep(30, 4), rep(15, 4), rep(60, 3)) Output - id width tier offset max_widths - 1 1 30 1 30 30 - 2 2 30 2 30 30 - 3 3 30 3 30 30 - 4 4 15 3 60 30 + id width tier offset_after max_widths + 1 1 30 1 30 30 + 2 2 30 2 30 30 + 3 3 30 3 30 30 + 4 4 15 3 60 30 Code colonnade_compute_tiered_col_widths_df(rep(30, 4), rep(15, 4), rep(60, 2)) Output - id width tier offset max_widths - 1 1 30 1 30 30 - 2 2 15 2 28 30 - 3 3 15 2 44 30 - 4 4 15 2 60 30 + id width tier offset_after max_widths + 1 1 30 1 30 30 + 2 2 15 2 28 30 + 3 3 15 2 44 30 + 4 4 15 2 60 30 Code colonnade_compute_tiered_col_widths_df(rep(30, 5), rep(15, 5), rep(60, 3)) Output - id width tier offset max_widths - 1 1 30 1 30 30 - 2 2 30 2 30 30 - 3 3 15 3 28 30 - 4 4 15 3 44 30 - 5 5 15 3 60 30 + id width tier offset_after max_widths + 1 1 30 1 30 30 + 2 2 30 2 30 30 + 3 3 15 3 28 30 + 4 4 15 3 44 30 + 5 5 15 3 60 30 Code colonnade_compute_tiered_col_widths_df(rep(30, 5), rep(15, 5), rep(60, 4)) Output - id width tier offset max_widths - 1 1 30 1 30 30 - 2 2 30 2 30 30 - 3 3 30 3 30 30 - 4 4 30 4 30 30 - 5 5 15 4 60 30 + id width tier offset_after max_widths + 1 1 30 1 30 30 + 2 2 30 2 30 30 + 3 3 30 3 30 30 + 4 4 30 4 30 30 + 5 5 15 4 60 30 Code colonnade_compute_tiered_col_widths_df(rep(30, 10), rep(15, 10), rep(60, 5)) Output - id width tier offset max_widths - 1 1 30 1 30 30 - 2 2 30 2 30 30 - 3 3 30 3 30 30 - 4 4 15 3 60 30 - 5 5 15 4 28 30 - 6 6 15 4 44 30 - 7 7 15 4 60 30 - 8 8 15 5 28 30 - 9 9 15 5 44 30 - 10 10 15 5 60 30 + id width tier offset_after max_widths + 1 1 30 1 30 30 + 2 2 30 2 30 30 + 3 3 30 3 30 30 + 4 4 15 3 60 30 + 5 5 15 4 28 30 + 6 6 15 4 44 30 + 7 7 15 4 60 30 + 8 8 15 5 28 30 + 9 9 15 5 44 30 + 10 10 15 5 60 30 # distribute_pillars() Code distribute_pillars(1:3, 10) Output - id width tier offset - 1 1 1 1 1 - 2 2 2 1 4 - 3 3 3 1 8 + id width tier offset_after + 1 1 1 1 1 + 2 2 2 1 4 + 3 3 3 1 8 Code distribute_pillars(1:3, 5) Output - id width tier offset - 1 1 1 1 1 - 2 2 2 1 4 - 3 3 3 NA NA + id width tier offset_after + 1 1 1 1 1 + 2 2 2 1 4 + 3 3 3 NA NA Code distribute_pillars(1:3, c(5, 5)) Output - id width tier offset - 1 1 1 1 1 - 2 2 2 1 4 - 3 3 3 2 3 + id width tier offset_after + 1 1 1 1 1 + 2 2 2 1 4 + 3 3 3 2 3 Code distribute_pillars(1:5, 7:9) Output - id width tier offset - 1 1 1 1 1 - 2 2 2 1 4 - 3 3 3 2 3 - 4 4 4 2 8 - 5 5 5 3 5 + id width tier offset_after + 1 1 1 1 1 + 2 2 2 1 4 + 3 3 3 2 3 + 4 4 4 2 8 + 5 5 5 3 5 Code distribute_pillars(3:5, 8:10) Output - id width tier offset - 1 1 3 1 3 - 2 2 4 1 8 - 3 3 5 2 5 + id width tier offset_after + 1 1 3 1 3 + 2 2 4 1 8 + 3 3 5 2 5 Code distribute_pillars(5:3, 9:8) Output - id width tier offset - 1 1 5 1 5 - 2 2 4 2 4 - 3 3 3 2 8 + id width tier offset_after + 1 1 5 1 5 + 2 2 4 2 4 + 3 3 3 2 8 # distribute_pillars_rev() Code distribute_pillars_rev(1:3, 10) Output - id width tier offset - 1 1 1 1 5 - 2 2 2 1 7 - 3 3 3 1 10 + id width tier offset_after + 1 1 1 1 5 + 2 2 2 1 7 + 3 3 3 1 10 Code distribute_pillars_rev(1:3, 5) Output - id width tier offset - 1 1 1 NA 5 - 2 2 2 NA NA - 3 3 3 1 NA + id width tier offset_after + 1 1 1 NA 5 + 2 2 2 NA NA + 3 3 3 1 NA Code distribute_pillars_rev(1:3, c(5, 5)) Output - id width tier offset - 1 1 1 1 3 - 2 2 2 1 5 - 3 3 3 2 5 + id width tier offset_after + 1 1 1 1 3 + 2 2 2 1 5 + 3 3 3 2 5 Code distribute_pillars_rev(1:5, 7:9) Output - id width tier offset - 1 1 1 1 5 - 2 2 2 1 7 - 3 3 3 2 4 - 4 4 4 2 8 - 5 5 5 3 9 + id width tier offset_after + 1 1 1 1 5 + 2 2 2 1 7 + 3 3 3 2 4 + 4 4 4 2 8 + 5 5 5 3 9 Code distribute_pillars_rev(3:5, 8:10) Output - id width tier offset - 1 1 3 2 8 - 2 2 4 3 4 - 3 3 5 3 9 + id width tier offset_after + 1 1 3 2 8 + 2 2 4 3 4 + 3 3 5 3 9 Code distribute_pillars_rev(5:3, 9:8) Output - id width tier offset - 1 1 5 1 9 - 2 2 4 2 3 - 3 3 3 2 8 + id width tier offset_after + 1 1 5 1 9 + 2 2 4 2 3 + 3 3 3 2 8 From 6b06899d32f623ca29d3edd61e29c9276696c407 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Sun, 17 Oct 2021 11:15:58 +0200 Subject: [PATCH 123/147] Flip column order --- R/multi.R | 2 +- tests/testthat/_snaps/multi.md | 180 ++++++++++++++++----------------- 2 files changed, 91 insertions(+), 91 deletions(-) diff --git a/R/multi.R b/R/multi.R index 0df09bf0b..e59f8ee09 100644 --- a/R/multi.R +++ b/R/multi.R @@ -462,7 +462,7 @@ distribute_pillars <- function(widths, tier_widths) { current_x <- current_x + 1L } - data_frame(id = seq_along(widths), width = widths, tier = tier, offset_after = offset_after) + data_frame(id = seq_along(widths), tier = tier, width = widths, offset_after = offset_after) } distribute_pillars_rev <- function(widths, tier_widths) { diff --git a/tests/testthat/_snaps/multi.md b/tests/testthat/_snaps/multi.md index c236d6a51..5586b8752 100644 --- a/tests/testthat/_snaps/multi.md +++ b/tests/testthat/_snaps/multi.md @@ -3,151 +3,151 @@ Code colonnade_compute_tiered_col_widths_df(rep(30, 4), rep(15, 4), rep(60, 4)) Output - id width tier offset_after - 1 1 30 1 30 - 2 2 30 2 30 - 3 3 30 3 30 - 4 4 30 4 30 + id tier width offset_after + 1 1 1 30 30 + 2 2 2 30 30 + 3 3 3 30 30 + 4 4 4 30 30 Code colonnade_compute_tiered_col_widths_df(rep(30, 4), rep(15, 4), rep(60, 3)) Output - id width tier offset_after max_widths - 1 1 30 1 30 30 - 2 2 30 2 30 30 - 3 3 30 3 30 30 - 4 4 15 3 60 30 + id tier width offset_after max_widths + 1 1 1 30 30 30 + 2 2 2 30 30 30 + 3 3 3 30 30 30 + 4 4 3 15 60 30 Code colonnade_compute_tiered_col_widths_df(rep(30, 4), rep(15, 4), rep(60, 2)) Output - id width tier offset_after max_widths - 1 1 30 1 30 30 - 2 2 15 2 28 30 - 3 3 15 2 44 30 - 4 4 15 2 60 30 + id tier width offset_after max_widths + 1 1 1 30 30 30 + 2 2 2 15 28 30 + 3 3 2 15 44 30 + 4 4 2 15 60 30 Code colonnade_compute_tiered_col_widths_df(rep(30, 5), rep(15, 5), rep(60, 3)) Output - id width tier offset_after max_widths - 1 1 30 1 30 30 - 2 2 30 2 30 30 - 3 3 15 3 28 30 - 4 4 15 3 44 30 - 5 5 15 3 60 30 + id tier width offset_after max_widths + 1 1 1 30 30 30 + 2 2 2 30 30 30 + 3 3 3 15 28 30 + 4 4 3 15 44 30 + 5 5 3 15 60 30 Code colonnade_compute_tiered_col_widths_df(rep(30, 5), rep(15, 5), rep(60, 4)) Output - id width tier offset_after max_widths - 1 1 30 1 30 30 - 2 2 30 2 30 30 - 3 3 30 3 30 30 - 4 4 30 4 30 30 - 5 5 15 4 60 30 + id tier width offset_after max_widths + 1 1 1 30 30 30 + 2 2 2 30 30 30 + 3 3 3 30 30 30 + 4 4 4 30 30 30 + 5 5 4 15 60 30 Code colonnade_compute_tiered_col_widths_df(rep(30, 10), rep(15, 10), rep(60, 5)) Output - id width tier offset_after max_widths - 1 1 30 1 30 30 - 2 2 30 2 30 30 - 3 3 30 3 30 30 - 4 4 15 3 60 30 - 5 5 15 4 28 30 - 6 6 15 4 44 30 - 7 7 15 4 60 30 - 8 8 15 5 28 30 - 9 9 15 5 44 30 - 10 10 15 5 60 30 + id tier width offset_after max_widths + 1 1 1 30 30 30 + 2 2 2 30 30 30 + 3 3 3 30 30 30 + 4 4 3 15 60 30 + 5 5 4 15 28 30 + 6 6 4 15 44 30 + 7 7 4 15 60 30 + 8 8 5 15 28 30 + 9 9 5 15 44 30 + 10 10 5 15 60 30 # distribute_pillars() Code distribute_pillars(1:3, 10) Output - id width tier offset_after - 1 1 1 1 1 - 2 2 2 1 4 - 3 3 3 1 8 + id tier width offset_after + 1 1 1 1 1 + 2 2 1 2 4 + 3 3 1 3 8 Code distribute_pillars(1:3, 5) Output - id width tier offset_after - 1 1 1 1 1 - 2 2 2 1 4 - 3 3 3 NA NA + id tier width offset_after + 1 1 1 1 1 + 2 2 1 2 4 + 3 3 NA 3 NA Code distribute_pillars(1:3, c(5, 5)) Output - id width tier offset_after - 1 1 1 1 1 - 2 2 2 1 4 - 3 3 3 2 3 + id tier width offset_after + 1 1 1 1 1 + 2 2 1 2 4 + 3 3 2 3 3 Code distribute_pillars(1:5, 7:9) Output - id width tier offset_after - 1 1 1 1 1 - 2 2 2 1 4 - 3 3 3 2 3 - 4 4 4 2 8 - 5 5 5 3 5 + id tier width offset_after + 1 1 1 1 1 + 2 2 1 2 4 + 3 3 2 3 3 + 4 4 2 4 8 + 5 5 3 5 5 Code distribute_pillars(3:5, 8:10) Output - id width tier offset_after - 1 1 3 1 3 - 2 2 4 1 8 - 3 3 5 2 5 + id tier width offset_after + 1 1 1 3 3 + 2 2 1 4 8 + 3 3 2 5 5 Code distribute_pillars(5:3, 9:8) Output - id width tier offset_after - 1 1 5 1 5 - 2 2 4 2 4 - 3 3 3 2 8 + id tier width offset_after + 1 1 1 5 5 + 2 2 2 4 4 + 3 3 2 3 8 # distribute_pillars_rev() Code distribute_pillars_rev(1:3, 10) Output - id width tier offset_after - 1 1 1 1 5 - 2 2 2 1 7 - 3 3 3 1 10 + id tier width offset_after + 1 1 1 1 5 + 2 2 1 2 7 + 3 3 1 3 10 Code distribute_pillars_rev(1:3, 5) Output - id width tier offset_after - 1 1 1 NA 5 - 2 2 2 NA NA - 3 3 3 1 NA + id tier width offset_after + 1 1 NA 1 5 + 2 2 NA 2 NA + 3 3 1 3 NA Code distribute_pillars_rev(1:3, c(5, 5)) Output - id width tier offset_after - 1 1 1 1 3 - 2 2 2 1 5 - 3 3 3 2 5 + id tier width offset_after + 1 1 1 1 3 + 2 2 1 2 5 + 3 3 2 3 5 Code distribute_pillars_rev(1:5, 7:9) Output - id width tier offset_after - 1 1 1 1 5 - 2 2 2 1 7 - 3 3 3 2 4 - 4 4 4 2 8 - 5 5 5 3 9 + id tier width offset_after + 1 1 1 1 5 + 2 2 1 2 7 + 3 3 2 3 4 + 4 4 2 4 8 + 5 5 3 5 9 Code distribute_pillars_rev(3:5, 8:10) Output - id width tier offset_after - 1 1 3 2 8 - 2 2 4 3 4 - 3 3 5 3 9 + id tier width offset_after + 1 1 2 3 8 + 2 2 3 4 4 + 3 3 3 5 9 Code distribute_pillars_rev(5:3, 9:8) Output - id width tier offset_after - 1 1 5 1 9 - 2 2 4 2 3 - 3 3 3 2 8 + id tier width offset_after + 1 1 1 5 9 + 2 2 2 4 3 + 3 3 2 3 8 From 468dcc86fe9503a984b1c89d4df6024ee0546e70 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Sun, 17 Oct 2021 11:43:34 +0200 Subject: [PATCH 124/147] Add tests for tricky corner cases --- tests/testthat/_snaps/multi.md | 42 ++++++++++++++++++++++++++++++++++ tests/testthat/test-multi.R | 6 +++++ 2 files changed, 48 insertions(+) diff --git a/tests/testthat/_snaps/multi.md b/tests/testthat/_snaps/multi.md index 5586b8752..aba6e535e 100644 --- a/tests/testthat/_snaps/multi.md +++ b/tests/testthat/_snaps/multi.md @@ -56,6 +56,48 @@ 8 8 5 15 28 30 9 9 5 15 44 30 10 10 5 15 60 30 + Code + colonnade_compute_tiered_col_widths_df(c(6, 5, 10), c(5, 5, 10), 21) + Output + id tier width offset_after + 1 1 1 5 5 + 2 2 1 5 11 + 3 3 NA 10 NA + Code + colonnade_compute_tiered_col_widths_df(c(6, 5, 10), c(5, 5, 10), 22) + Output + id tier width offset_after max_widths + 1 1 1 6 6 6 + 2 2 1 5 12 5 + 3 3 1 10 22 10 + Code + colonnade_compute_tiered_col_widths_df(c(6, 5, 10), c(5, 5, 10), 23) + Output + id tier width offset_after + 1 1 1 6 6 + 2 2 1 5 12 + 3 3 1 10 23 + Code + colonnade_compute_tiered_col_widths_df(c(5, 6, 10), c(5, 5, 10), 21) + Output + id tier width offset_after + 1 1 1 5 5 + 2 2 1 5 11 + 3 3 NA 10 NA + Code + colonnade_compute_tiered_col_widths_df(c(5, 6, 10), c(5, 5, 10), 22) + Output + id tier width offset_after max_widths + 1 1 1 5 5 5 + 2 2 1 6 12 6 + 3 3 1 10 22 10 + Code + colonnade_compute_tiered_col_widths_df(c(5, 6, 10), c(5, 5, 10), 23) + Output + id tier width offset_after + 1 1 1 5 5 + 2 2 1 6 12 + 3 3 1 10 23 # distribute_pillars() diff --git a/tests/testthat/test-multi.R b/tests/testthat/test-multi.R index 2e354ffdc..8ce4e3db7 100644 --- a/tests/testthat/test-multi.R +++ b/tests/testthat/test-multi.R @@ -6,6 +6,12 @@ test_that("colonnade_compute_tiered_col_widths_df()", { colonnade_compute_tiered_col_widths_df(rep(30, 5), rep(15, 5), rep(60, 3)) colonnade_compute_tiered_col_widths_df(rep(30, 5), rep(15, 5), rep(60, 4)) colonnade_compute_tiered_col_widths_df(rep(30, 10), rep(15, 10), rep(60, 5)) + colonnade_compute_tiered_col_widths_df(c(6, 5, 10), c(5, 5, 10), 21) + colonnade_compute_tiered_col_widths_df(c(6, 5, 10), c(5, 5, 10), 22) + colonnade_compute_tiered_col_widths_df(c(6, 5, 10), c(5, 5, 10), 23) + colonnade_compute_tiered_col_widths_df(c(5, 6, 10), c(5, 5, 10), 21) + colonnade_compute_tiered_col_widths_df(c(5, 6, 10), c(5, 5, 10), 22) + colonnade_compute_tiered_col_widths_df(c(5, 6, 10), c(5, 5, 10), 23) }) }) From 77978a41461b264ac8d206428678a2631c40a580 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Sun, 17 Oct 2021 11:33:19 +0200 Subject: [PATCH 125/147] Fix computation of offsets by recomputing from scratch --- R/multi.R | 3 +-- tests/testthat/_snaps/multi.md | 20 ++++++++++---------- 2 files changed, 11 insertions(+), 12 deletions(-) diff --git a/R/multi.R b/R/multi.R index e59f8ee09..b1130f833 100644 --- a/R/multi.R +++ b/R/multi.R @@ -475,8 +475,7 @@ distribute_pillars_rev <- function(widths, tier_widths) { tier_widths <- tier_widths[seq_along(splits)] new_offset_after <- unlist(map2(splits, tier_widths, function(.x, .y) { - offset_afters <- ret$offset_after[.x] - new_offset_after <- max(offset_afters) - offset_afters + new_offset_after <- cumsum(ret$width[.x] + 1) new_offset_after - max(new_offset_after) + .y })) diff --git a/tests/testthat/_snaps/multi.md b/tests/testthat/_snaps/multi.md index aba6e535e..d5fdc5ed5 100644 --- a/tests/testthat/_snaps/multi.md +++ b/tests/testthat/_snaps/multi.md @@ -67,8 +67,8 @@ colonnade_compute_tiered_col_widths_df(c(6, 5, 10), c(5, 5, 10), 22) Output id tier width offset_after max_widths - 1 1 1 6 6 6 - 2 2 1 5 12 5 + 1 1 1 5 5 6 + 2 2 1 5 11 5 3 3 1 10 22 10 Code colonnade_compute_tiered_col_widths_df(c(6, 5, 10), c(5, 5, 10), 23) @@ -89,7 +89,7 @@ Output id tier width offset_after max_widths 1 1 1 5 5 5 - 2 2 1 6 12 6 + 2 2 1 5 11 6 3 3 1 10 22 10 Code colonnade_compute_tiered_col_widths_df(c(5, 6, 10), c(5, 5, 10), 23) @@ -152,8 +152,8 @@ distribute_pillars_rev(1:3, 10) Output id tier width offset_after - 1 1 1 1 5 - 2 2 1 2 7 + 1 1 1 1 3 + 2 2 1 2 6 3 3 1 3 10 Code distribute_pillars_rev(1:3, 5) @@ -166,16 +166,16 @@ distribute_pillars_rev(1:3, c(5, 5)) Output id tier width offset_after - 1 1 1 1 3 + 1 1 1 1 2 2 2 1 2 5 3 3 2 3 5 Code distribute_pillars_rev(1:5, 7:9) Output id tier width offset_after - 1 1 1 1 5 + 1 1 1 1 4 2 2 1 2 7 - 3 3 2 3 4 + 3 3 2 3 3 4 4 2 4 8 5 5 3 5 9 Code @@ -183,13 +183,13 @@ Output id tier width offset_after 1 1 2 3 8 - 2 2 3 4 4 + 2 2 3 4 3 3 3 3 5 9 Code distribute_pillars_rev(5:3, 9:8) Output id tier width offset_after 1 1 1 5 9 - 2 2 2 4 3 + 2 2 2 4 4 3 3 2 3 8 From f50a3f095f76a61720c4f4da9fde3d6a49324ee9 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Sun, 17 Oct 2021 11:59:26 +0200 Subject: [PATCH 126/147] Content moved --- _pkgdown.yml | 4 -- vignettes/digits.Rmd | 131 +----------------------------------------- vignettes/numbers.Rmd | 108 +--------------------------------- 3 files changed, 4 insertions(+), 239 deletions(-) diff --git a/_pkgdown.yml b/_pkgdown.yml index 52d2b9634..a930ebb48 100644 --- a/_pkgdown.yml +++ b/_pkgdown.yml @@ -75,10 +75,6 @@ navbar: articles: text: Articles menu: - - text: Controlling display of numbers - href: articles/numbers.html - - text: "Significant figures and scientific notation" - href: articles/digits.html - text: Custom formatting href: articles/extending.html - text: 'Printing a tibble: Control and data flow' diff --git a/vignettes/digits.Rmd b/vignettes/digits.Rmd index 2167ab6aa..be13332ab 100644 --- a/vignettes/digits.Rmd +++ b/vignettes/digits.Rmd @@ -1,135 +1,10 @@ --- -title: "Significant figures and scientific notation" +title: "Comparison with data frames" output: html_vignette vignette: > - %\VignetteIndexEntry{Significant figures and scientific notation} + %\VignetteIndexEntry{Comparison with data frames} %\VignetteEngine{knitr::rmarkdown} %\VignetteEncoding{UTF-8} --- -```{r, include = FALSE} -knitr::opts_chunk$set( - collapse = TRUE, - comment = "#>" -) -``` - -```{r setup} -library(pillar) -``` - -Base R offers the `"digits"` and `"scipen"` options to control the number of significant digits and the switch to scientific notation. -For pillar, the options `"pillar.sigfig"` and `"pillar.max_dec_width"` fulfill a similar purpose. -This vignette showcases similarities and differences. -See `?"pillar-package"` for an overview over all options. - -## Digits - -### Basic differences - -The default for `getOption("digits")` is 7, whereas the `"pillar.sigfig"` option defaults to 3. -In the default setting, pillar prints the first three digits only (i.e. the digits that represent > 99.9% of the value of the number). -Another difference is that pillar will show at most the specified number of significant digits, even if space is available. -The rationale is to allow a quick glance over the most significant digits of a number, without spending too much horizontal space and without distraction from insignificant digits. - -```{r} -options(digits = 3) -c(1.2345, 12.345, 123.45, 1234.5, 12345) -pillar(c(1.2345, 12.345, 123.45, 1234.5, 12345)) -``` - -### Terminal zeros - -Terminal zeros are only shown in pillar if there is a nonzero value past the significant digits shown. -This is in contrast to base R where terminal zeros are always shown if there is space, but hidden if the value is too insignificant: - -```{r} -c(1, 1.00001) -pillar(c(1, 1.00001)) -``` - -### Trailing dot - -A trailing decimal separator is shown if there is a fractional part but the integer part already exceeds the significant digits. -The presence of the decimal separator does **not** indicate that the number is larger, only that there exists a nonzero fractional part: - -```{r} -c(123, 123.45, 567.89) -pillar(c(123, 123.45, 567.89)) -``` - -### Showing more digits - -To show more significant digits, set the `"pillar.sigfig"` option to a larger value: - -```{r} -options(digits = 7) -options(pillar.sigfig = 7) -c(1.2345, 12.345, 123.45, 1234.5, 12345) -pillar(c(1.2345, 12.345, 123.45, 1234.5, 12345)) -``` - -Setting `"pillar.sigfig"` to a larger value will not enhance the display with digits deemed insignificant: - -```{r} -options(digits = 7) -options(pillar.sigfig = 7) -c(1.2345, 12.3456, 123.4567, 1234.5678, 12345.6789) -pillar(c(1.2345, 12.3456, 123.4567, 1234.5678, 12345.6789)) -``` - -### Fixed number of digits - -To show a fixed number of decimal digits, use `num()` with a `digits` argument: - -```{r} -num(c(1.2345, 12.345, 123.45, 1234.5, 12345), digits = 2) -``` - -See `vignette("numbers")` for details. - -## Scientific notation - -### When is it used? - -Both base R and pillar switch to scientific notation when the decimal representation becomes too wide. -The larger `getOption("scipen")`, the stronger the resistance to switching to scientific notation. -The default `0` seems to be anchored at 13 digits for the integer part. - -```{r} -123456789012 -123456789012.3 -1234567890123 -1234567890123.4 -options(scipen = 1) -1234567890123 -12345678901234 -12345678901234.5 -``` - -The `"pillar.max_dec_width"` option is similar, it indicates the width that must be exceeded for a switch to scientific notation to happen. -This width includes the decimal separator. - -```{r} -pillar(123456789012) -pillar(123456789012.3) -pillar(1234567890123) -pillar(1234567890123.4) -options(pillar.max_dec_width = 14) -pillar(1234567890123) -pillar(12345678901234) -pillar(12345678901234.5) -``` - -### Enforce notation - -To avoid switching to scientific notation, set the `"pillar.max_dec_width"` option to a large value. -Note that if the required width is not available to show the column, it will not be shown at all in this case. -The `notation` argument to `num()` offers more options: - -```{r} -num(12345678901234567, notation = "dec") -num(12345678901234567, notation = "sci") -num(12345678901234567, notation = "eng") -num(12345678901234567, notation = "si") -``` +This content has moved to `vignette("digits", packages = "tibble)`. diff --git a/vignettes/numbers.Rmd b/vignettes/numbers.Rmd index 5aa2b6cb1..fd355f4b9 100644 --- a/vignettes/numbers.Rmd +++ b/vignettes/numbers.Rmd @@ -7,113 +7,7 @@ vignette: > %\VignetteEncoding{UTF-8} --- -```{r numbers-1, include = FALSE} -knitr::opts_chunk$set( - collapse = TRUE, - cache = TRUE, - comment = "#>" -) -``` - -Tibbles print numbers with three significant digits by default, switching to scientific notation if the available space is too small. -Underlines are used to highlight groups of three digits. -This display works for many, but not for all use cases. - -```{r numbers-2} -library(pillar) -library(tibble) -``` - -## Per-column number formatting - -The new `num()` constructor allows creating vectors that behave like numbers but allow customizing their display. - -```{r numbers-5} -num(-1:3, notation = "sci") - -tibble( - x4 = num(8:12 * 100 + 0.5, digits = 4), - x1 = num(8:12 * 100 + 0.5, digits = -1), - usd = num(8:12 * 100 + 0.5, digits = 2, label = "USD"), - percent = num(8:12 / 100 + 0.0005, label = "%", scale = 100), - eng = num(10^(-3:1), notation = "eng", fixed_exponent = -Inf), - si = num(10^(-3:1) * 123, notation = "si") -) -``` - - -## Computing on `num` - -Formatting numbers is useful for presentation of results. -If defined early on in the analysis, the formatting options survive most operations. -It is worth defining output options that suit your data once early on in the process, to benefit from the formatting throughout the analysis. -We are working on seamlessly applying this formatting to the final presentation (plots, tables, ...). - - -### Arithmetics - -```{r numbers-13} -num(1) + 2 -1 + num(2) -1L + num(2) -num(3.23456, sigfig = 4) - num(2) -num(4, sigfig = 2) * num(3, digits = 2) -num(3, digits = 2) * num(4, sigfig = 2) --num(2) -``` - -### Mathematics - -```{r numbers-15} -min(num(1:3, label = "$")) -mean(num(1:3, notation = "eng")) -sin(num(1:3, label = "%", scale = 100)) -``` - -### Recovery - -The `var()` function is one of the examples where the formatting is lost: - -```{r numbers-16} -x <- num(c(1, 2, 4), notation = "eng") -var(x) -``` - -One way to recover is to apply `num()` to the result: - -```{r numbers-16a} -num(var(x), notation = "eng") -``` - -For automatic recovery, we can also define our version of `var()`, or even overwrite the base implementation. -Note that this pattern is still experimental and may be subject to change: - -```{r numbers-16b} -var_ <- function(x, ...) { - out <- var(vctrs::vec_proxy(x), ...) - vctrs::vec_restore(out, x) -} -var_(x) -``` - -This pattern can be applied to all functions that lose the formatting. -The `make_restore()` function defined below is a function factory that consumes a function and returns a derived function: - -```{r numbers-16c} -make_restore <- function(fun) { - force(fun) - function(x, ...) { - out <- fun(vctrs::vec_proxy(x), ...) - vctrs::vec_restore(out, x) - } -} - -var_ <- make_restore(var) -sd_ <- make_restore(sd) - -var_(x) -sd_(x) -``` +This content has moved to `vignette("numbes", packages = "tibble)`. `````{asis echo = FALSE} From 67b2de56958101db7c2363349e362b27b5e36632 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Sun, 17 Oct 2021 12:14:05 +0200 Subject: [PATCH 127/147] Link to tibble::formatting --- R/tbl-format.R | 40 ++-------------------------------------- _pkgdown.yml | 1 - man/format_tbl.Rd | 47 ++--------------------------------------------- 3 files changed, 4 insertions(+), 84 deletions(-) diff --git a/R/tbl-format.R b/R/tbl-format.R index 9364a301f..0361a2d99 100644 --- a/R/tbl-format.R +++ b/R/tbl-format.R @@ -1,46 +1,10 @@ #' Formatting of tbl objects #' -#' @description -#' These functions and methods are responsible for printing objects -#' of the `"tbl"` class, which includes [tibble][tibble::tibble]s -#' and dbplyr lazy tables. -#' See [tibble::formatting] for user level documentation, -#' and `vignette("customization")` for details. -#' -#' While it is possible to implement a custom [format()] or [print()] method -#' for your tibble-like objects, it should never be necessary -#' if your class inherits from `"tbl"`. -#' In this case, the default methods offer many customization options -#' at every level of detail. -#' This means you only need to override or extend implementations for the parts -#' that need change. -#' -#' The output uses color and highlighting according to the `"cli.num_colors"` option. -#' Set it to `1` to suppress colored and highlighted output. -#' -#' @seealso -#' -#' - [tbl_format_setup()] for preparing an object for formatting -#' -#' @param x Object to format or print. -#' @param ... Passed on to [tbl_format_setup()]. -#' @param n Number of rows to show. If `NULL`, the default, will print all rows -#' if less than the `print_max` [option][pillar_options]. -#' Otherwise, will print as many rows as specified by the -#' `print_min` [option][pillar_options]. -#' @param width Width of text output to generate. This defaults to `NULL`, which -#' means use the `width` [option][pillar_options]. -#' @param max_extra_cols Number of extra columns to print abbreviated information for, -#' if the width is too small for the entire tibble. If `NULL`, -#' the `max_extra_cols` [option][pillar_options] is used. -#' The previously defined `n_extra` argument is soft-deprecated. -#' @param max_footer_lines Maximum number of footer lines. If `NULL`, -#' the `max_footer_lines` [option][pillar_options] is used. +#' See [tibble::formatting] for details. #' #' @name format_tbl #' @export -#' @examples -#' print(vctrs::new_data_frame(list(a = 1), class = "tbl")) +#' @keywords internal print.tbl <- function(x, width = NULL, ..., n = NULL, max_extra_cols = NULL, max_footer_lines = NULL) { print_tbl( diff --git a/_pkgdown.yml b/_pkgdown.yml index a930ebb48..6b4ef3224 100644 --- a/_pkgdown.yml +++ b/_pkgdown.yml @@ -6,7 +6,6 @@ reference: Override or extend these methods if you want to customize the appearance of your tibble-like object. contents: - - format_tbl - tbl_format_setup - tbl_format_header - tbl_format_body diff --git a/man/format_tbl.Rd b/man/format_tbl.Rd index 982805dff..d21f85029 100644 --- a/man/format_tbl.Rd +++ b/man/format_tbl.Rd @@ -24,50 +24,7 @@ max_footer_lines = NULL ) } -\arguments{ -\item{x}{Object to format or print.} - -\item{width}{Width of text output to generate. This defaults to \code{NULL}, which -means use the \code{width} \link[=pillar_options]{option}.} - -\item{...}{Passed on to \code{\link[=tbl_format_setup]{tbl_format_setup()}}.} - -\item{n}{Number of rows to show. If \code{NULL}, the default, will print all rows -if less than the \code{print_max} \link[=pillar_options]{option}. -Otherwise, will print as many rows as specified by the -\code{print_min} \link[=pillar_options]{option}.} - -\item{max_extra_cols}{Number of extra columns to print abbreviated information for, -if the width is too small for the entire tibble. If \code{NULL}, -the \code{max_extra_cols} \link[=pillar_options]{option} is used. -The previously defined \code{n_extra} argument is soft-deprecated.} - -\item{max_footer_lines}{Maximum number of footer lines. If \code{NULL}, -the \code{max_footer_lines} \link[=pillar_options]{option} is used.} -} \description{ -These functions and methods are responsible for printing objects -of the \code{"tbl"} class, which includes \link[tibble:tibble]{tibble}s -and dbplyr lazy tables. -See \link[tibble:formatting]{tibble::formatting} for user level documentation, -and \code{vignette("customization")} for details. - -While it is possible to implement a custom \code{\link[=format]{format()}} or \code{\link[=print]{print()}} method -for your tibble-like objects, it should never be necessary -if your class inherits from \code{"tbl"}. -In this case, the default methods offer many customization options -at every level of detail. -This means you only need to override or extend implementations for the parts -that need change. - -The output uses color and highlighting according to the \code{"cli.num_colors"} option. -Set it to \code{1} to suppress colored and highlighted output. -} -\examples{ -print(vctrs::new_data_frame(list(a = 1), class = "tbl")) -} -\seealso{ -\itemize{ -\item \code{\link[=tbl_format_setup]{tbl_format_setup()}} for preparing an object for formatting -} +See \link[tibble:formatting]{tibble::formatting} for details. } +\keyword{internal} From c2e3704612cbc6879a3e8e3357125d95874655c0 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Sun, 17 Oct 2021 12:19:15 +0200 Subject: [PATCH 128/147] Explicit quotes --- tests/testthat/helper-output.R | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/tests/testthat/helper-output.R b/tests/testthat/helper-output.R index 92b8f24ed..c42d360ce 100644 --- a/tests/testthat/helper-output.R +++ b/tests/testthat/helper-output.R @@ -3,7 +3,7 @@ show_output_in_terminal <- function() { } # A data frame with all major types -df_all <- function() new_tbl(list( +df_all <- function() pillar:::new_tbl(list( a = c(1, 2.5, NA), b = c(1:2, NA), c = c(T, F, NA), @@ -17,7 +17,7 @@ df_all <- function() new_tbl(list( # A data frame with strings of varying lengths long_str <- strrep("Abcdefghij", 5) -df_str <- purrr::map(rlang::set_names(1:50), function(i) substr(long_str, 1, i)) +df_str <- pillar:::map(rlang::set_names(1:50), function(i) substr(long_str, 1, i)) #' `add_special()` is not exported, and used only for initializing default #' values to `expect_pillar_output()`. From ca387a77c7acd886b37f1d79d0f86b1cbc9c44bd Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Sun, 17 Oct 2021 12:20:26 +0200 Subject: [PATCH 129/147] Revert "df_all -> df_all()" This reverts commit 4e68b21da9a72ef589393ff1f51f76f68da9c961. --- tests/testthat/_snaps/ctl_colonnade.md | 16 ++++++++-------- tests/testthat/_snaps/format_multi.md | 16 ++++++++-------- tests/testthat/_snaps/glimpse.md | 6 +++--- tests/testthat/_snaps/tbl-format-body.md | 4 ++-- tests/testthat/helper-output.R | 2 +- tests/testthat/test-ctl_colonnade.R | 16 ++++++++-------- tests/testthat/test-format_multi.R | 16 ++++++++-------- tests/testthat/test-glimpse.R | 6 +++--- tests/testthat/test-tbl-format-body.R | 4 ++-- 9 files changed, 43 insertions(+), 43 deletions(-) diff --git a/tests/testthat/_snaps/ctl_colonnade.md b/tests/testthat/_snaps/ctl_colonnade.md index 049f8c29c..fcd34f973 100644 --- a/tests/testthat/_snaps/ctl_colonnade.md +++ b/tests/testthat/_snaps/ctl_colonnade.md @@ -111,7 +111,7 @@ Code - ctl_colonnade(df_all(), width = 30) + ctl_colonnade(df_all, width = 30) Output $body a b c d @@ -165,7 +165,7 @@ Code - ctl_colonnade(df_all(), width = 300) + ctl_colonnade(df_all, width = 300) Output $body a b c d e f g h @@ -184,7 +184,7 @@ Code options(width = 70) - ctl_colonnade(df_all(), width = 300) + ctl_colonnade(df_all, width = 300) Output $body a b c d e f g @@ -203,7 +203,7 @@ Code options(width = 60) - ctl_colonnade(df_all(), width = 300) + ctl_colonnade(df_all, width = 300) Output $body a b c d e f @@ -222,7 +222,7 @@ Code options(width = 50) - ctl_colonnade(df_all(), width = 300) + ctl_colonnade(df_all, width = 300) Output $body a b c d e f @@ -241,7 +241,7 @@ Code options(width = 40) - ctl_colonnade(df_all(), width = 300) + ctl_colonnade(df_all, width = 300) Output $body a b c d e @@ -265,7 +265,7 @@ Code options(width = 30) - ctl_colonnade(df_all(), width = 300) + ctl_colonnade(df_all, width = 300) Output $body a b c d @@ -294,7 +294,7 @@ Code options(width = 20) - ctl_colonnade(df_all(), width = 300) + ctl_colonnade(df_all, width = 300) Output $body a b c diff --git a/tests/testthat/_snaps/format_multi.md b/tests/testthat/_snaps/format_multi.md index df587163b..0c337dc20 100644 --- a/tests/testthat/_snaps/format_multi.md +++ b/tests/testthat/_snaps/format_multi.md @@ -385,7 +385,7 @@ 2 4.9 3 4.7 Code - colonnade(df_all(), width = 30) + colonnade(df_all, width = 30) Output a b c d @@ -393,7 +393,7 @@ 2 2.5 2 FALSE b 3 NA NA NA Code - colonnade(df_all(), width = 300) + colonnade(df_all, width = 300) Output a b c d e f g h @@ -407,7 +407,7 @@ 3 Code options(width = 70) - colonnade(df_all(), width = 300) + colonnade(df_all, width = 300) Output a b c d e f g @@ -421,7 +421,7 @@ 3 Code options(width = 60) - colonnade(df_all(), width = 300) + colonnade(df_all, width = 300) Output a b c d e f @@ -435,7 +435,7 @@ 3 NA Code options(width = 50) - colonnade(df_all(), width = 300) + colonnade(df_all, width = 300) Output a b c d e f @@ -449,7 +449,7 @@ 3 NA Code options(width = 40) - colonnade(df_all(), width = 300) + colonnade(df_all, width = 300) Output a b c d e @@ -468,7 +468,7 @@ 3 Code options(width = 30) - colonnade(df_all(), width = 300) + colonnade(df_all, width = 300) Output a b c d @@ -492,7 +492,7 @@ 3 Code options(width = 20) - colonnade(df_all(), width = 300) + colonnade(df_all, width = 300) Output a b c diff --git a/tests/testthat/_snaps/glimpse.md b/tests/testthat/_snaps/glimpse.md index 700cee001..ec0bf2c30 100644 --- a/tests/testthat/_snaps/glimpse.md +++ b/tests/testthat/_snaps/glimpse.md @@ -141,7 +141,7 @@ $ `mean(x)` 5 $ `var(x)` 3 Code - glimpse(as_tbl(df_all()), width = 70L) + glimpse(as_tbl(df_all), width = 70L) Output Rows: 3 Columns: 9 @@ -156,7 +156,7 @@ $ i [1, <2, 3>], [<4, 5, 6>], [NA] Code # options(tibble.width = 50) - withr::with_options(list(tibble.width = 50), glimpse(as_tbl(df_all()))) + withr::with_options(list(tibble.width = 50), glimpse(as_tbl(df_all))) Output Rows: 3 Columns: 9 @@ -171,7 +171,7 @@ $ i [1, <2, 3>], [<4, 5, 6>], [NA] Code # options(tibble.width = 35) - withr::with_options(list(tibble.width = 35), glimpse(as_tbl(df_all()))) + withr::with_options(list(tibble.width = 35), glimpse(as_tbl(df_all))) Output Rows: 3 Columns: 9 diff --git a/tests/testthat/_snaps/tbl-format-body.md b/tests/testthat/_snaps/tbl-format-body.md index dc23b4c0a..c1e74c1b7 100644 --- a/tests/testthat/_snaps/tbl-format-body.md +++ b/tests/testthat/_snaps/tbl-format-body.md @@ -2,7 +2,7 @@ Code # Various column types - tbl_format_body(tbl_format_setup(df_all(), width = 30)) + tbl_format_body(tbl_format_setup(df_all, width = 30)) Output a b c d @@ -11,7 +11,7 @@ 2 2.5 2 FALSE b 3 NA NA NA Code - tbl_format_body(tbl_format_setup(df_all(), width = 300)) + tbl_format_body(tbl_format_setup(df_all, width = 300)) Output a b c d e f g h diff --git a/tests/testthat/helper-output.R b/tests/testthat/helper-output.R index c42d360ce..6a9e4a3ec 100644 --- a/tests/testthat/helper-output.R +++ b/tests/testthat/helper-output.R @@ -3,7 +3,7 @@ show_output_in_terminal <- function() { } # A data frame with all major types -df_all <- function() pillar:::new_tbl(list( +df_all <- pillar:::new_tbl(list( a = c(1, 2.5, NA), b = c(1:2, NA), c = c(T, F, NA), diff --git a/tests/testthat/test-ctl_colonnade.R b/tests/testthat/test-ctl_colonnade.R index acd10ec4c..c40765a13 100644 --- a/tests/testthat/test-ctl_colonnade.R +++ b/tests/testthat/test-ctl_colonnade.R @@ -12,20 +12,20 @@ test_that("tests from tibble", { ctl_colonnade(mtcars[1:8, ], has_row_id = "*", width = 30) ctl_colonnade(iris[1:5, ], width = 30) ctl_colonnade(iris[1:3, ], width = 20) - ctl_colonnade(df_all(), width = 30) - ctl_colonnade(df_all(), width = 300) + ctl_colonnade(df_all, width = 30) + ctl_colonnade(df_all, width = 300) options(width = 70) - ctl_colonnade(df_all(), width = 300) + ctl_colonnade(df_all, width = 300) options(width = 60) - ctl_colonnade(df_all(), width = 300) + ctl_colonnade(df_all, width = 300) options(width = 50) - ctl_colonnade(df_all(), width = 300) + ctl_colonnade(df_all, width = 300) options(width = 40) - ctl_colonnade(df_all(), width = 300) + ctl_colonnade(df_all, width = 300) options(width = 30) - ctl_colonnade(df_all(), width = 300) + ctl_colonnade(df_all, width = 300) options(width = 20) - ctl_colonnade(df_all(), width = 300) + ctl_colonnade(df_all, width = 300) ctl_colonnade(list(`\n` = c("\n", '"'), `\r` = factor(c("\n", "\n"))), width = 30) ctl_colonnade(list(a = c("", " ", "a ", " a")), width = 30) ctl_colonnade(list("mean(x)" = 5, "var(x)" = 3), width = 30) diff --git a/tests/testthat/test-format_multi.R b/tests/testthat/test-format_multi.R index 029bc5a14..258b96b86 100644 --- a/tests/testthat/test-format_multi.R +++ b/tests/testthat/test-format_multi.R @@ -102,20 +102,20 @@ test_that("tests from tibble", { colonnade(mtcars[1:8, ], has_row_id = "*", width = 30) colonnade(iris[1:5, ], width = 30) colonnade(iris[1:3, ], width = 20) - colonnade(df_all(), width = 30) - colonnade(df_all(), width = 300) + colonnade(df_all, width = 30) + colonnade(df_all, width = 300) options(width = 70) - colonnade(df_all(), width = 300) + colonnade(df_all, width = 300) options(width = 60) - colonnade(df_all(), width = 300) + colonnade(df_all, width = 300) options(width = 50) - colonnade(df_all(), width = 300) + colonnade(df_all, width = 300) options(width = 40) - colonnade(df_all(), width = 300) + colonnade(df_all, width = 300) options(width = 30) - colonnade(df_all(), width = 300) + colonnade(df_all, width = 300) options(width = 20) - colonnade(df_all(), width = 300) + colonnade(df_all, width = 300) colonnade(list(`\n` = c("\n", '"'), `\r` = factor("\n")), width = 30) colonnade(list(a = c("", " ", "a ", " a")), width = 30) colonnade(list("mean(x)" = 5, "var(x)" = 3), width = 30) diff --git a/tests/testthat/test-glimpse.R b/tests/testthat/test-glimpse.R index a5d760ed8..b34782653 100644 --- a/tests/testthat/test-glimpse.R +++ b/tests/testthat/test-glimpse.R @@ -70,18 +70,18 @@ test_that("output test for glimpse()", { df <- tibble::tibble(!!!set_names(c(5, 3), c("mean(x)", "var(x)"))) glimpse(df, width = 28) - glimpse(as_tbl(df_all()), width = 70L) + glimpse(as_tbl(df_all), width = 70L) "options(tibble.width = 50)" withr::with_options( list(tibble.width = 50), - glimpse(as_tbl(df_all())) + glimpse(as_tbl(df_all)) ) "options(tibble.width = 35)" withr::with_options( list(tibble.width = 35), - glimpse(as_tbl(df_all())) + glimpse(as_tbl(df_all)) ) "non-tibble" diff --git a/tests/testthat/test-tbl-format-body.R b/tests/testthat/test-tbl-format-body.R index 54b4ba1ca..5397fffe3 100644 --- a/tests/testthat/test-tbl-format-body.R +++ b/tests/testthat/test-tbl-format-body.R @@ -1,9 +1,9 @@ test_that("tbl_format_body() results", { expect_snapshot({ "Various column types" - tbl_format_body(tbl_format_setup(df_all(), width = 30)) + tbl_format_body(tbl_format_setup(df_all, width = 30)) - tbl_format_body(tbl_format_setup(df_all(), width = 300)) + tbl_format_body(tbl_format_setup(df_all, width = 300)) "POSIXct and POSIXlt" df <- new_tbl(list(x = as.POSIXct("2016-01-01 12:34:56 GMT") + 1:12)) From 54a760386c7c1cbdcfcc3f5ad7ae3e7a2ceff851 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Sun, 17 Oct 2021 12:37:22 +0200 Subject: [PATCH 130/147] Bump version to 1.6.3.9001 --- DESCRIPTION | 2 +- NEWS.md | 7 +++++++ 2 files changed, 8 insertions(+), 1 deletion(-) diff --git a/DESCRIPTION b/DESCRIPTION index 10f13fd9b..9fd525a38 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -1,6 +1,6 @@ Package: pillar Title: Coloured Formatting for Columns -Version: 1.6.3.9000 +Version: 1.6.3.9001 Authors@R: c(person(given = "Kirill", family = "M\u00fcller", diff --git a/NEWS.md b/NEWS.md index 51f90694c..e18f63d17 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,5 +1,12 @@ +# pillar 1.6.3.9001 + +- Fix printing for some tibbles where a fixed-width column is followed by a column with variable width (#366). +- `num()` requires an integerish `digits` argument (#362). +- Avoid nested backtick blocks in vignette. +- Link to tibble vignettes and documentation pages. + # pillar 1.6.3.9000 - Same as previous version. From 0f31cb6ac9eba097c53b38790b6636b42c1f1921 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Sun, 17 Oct 2021 13:46:21 +0200 Subject: [PATCH 131/147] Remove colonnade() and related code --- NAMESPACE | 7 - R/multi.R | 327 +------ R/shaft-.R | 5 - R/type-sum.R | 5 - R/zzz.R | 2 - man/colonnade.Rd | 52 +- man/extra_cols.Rd | 16 +- man/squeeze.Rd | 5 +- tests/testthat/_snaps/format_multi.md | 899 ------------------ tests/testthat/_snaps/zzx-format_character.md | 23 - tests/testthat/test-format_multi.R | 267 ------ tests/testthat/test-format_multi_fuzz.R | 39 - tests/testthat/test-format_multi_fuzz_2.R | 39 - tests/testthat/test-zzx-format_character.R | 10 - 14 files changed, 14 insertions(+), 1682 deletions(-) delete mode 100644 tests/testthat/_snaps/zzx-format_character.md delete mode 100644 tests/testthat/test-format_multi_fuzz.R delete mode 100644 tests/testthat/test-format_multi_fuzz_2.R diff --git a/NAMESPACE b/NAMESPACE index a4d1a739e..5c5a5d861 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -3,13 +3,11 @@ S3method(as_tbl,data.frame) S3method(ctl_new_compound_pillar,tbl) S3method(ctl_new_pillar,tbl) -S3method(extra_cols,pillar_squeezed_colonnade) S3method(format,pillar) S3method(format,pillar_1e) S3method(format,pillar_capital) S3method(format,pillar_char) S3method(format,pillar_char_attr) -S3method(format,pillar_colonnade) S3method(format,pillar_continuation_shaft) S3method(format,pillar_num) S3method(format,pillar_num_attr) @@ -20,7 +18,6 @@ S3method(format,pillar_rif_type) S3method(format,pillar_shaft) S3method(format,pillar_shaft_decimal) S3method(format,pillar_shaft_simple) -S3method(format,pillar_squeezed_colonnade) S3method(format,pillar_tbl_format_setup) S3method(format,pillar_title) S3method(format,pillar_type) @@ -48,7 +45,6 @@ S3method(pillar_shaft,factor) S3method(pillar_shaft,list) S3method(pillar_shaft,logical) S3method(pillar_shaft,numeric) -S3method(pillar_shaft,pillar_empty_col) S3method(pillar_shaft,pillar_vctr) S3method(pillar_shaft,pillar_vertical) S3method(pillar_shaft,vctrs_list_of) @@ -57,10 +53,8 @@ S3method(pillar_shaft,vctrs_vctr) S3method(print,compound_pillar) S3method(print,pillar) S3method(print,pillar_1e) -S3method(print,pillar_colonnade) S3method(print,pillar_ornament) S3method(print,pillar_shaft) -S3method(print,pillar_squeezed_colonnade) S3method(print,pillar_tbl_format_setup) S3method(print,pillar_vctr) S3method(print,pillar_vctr_attr) @@ -107,7 +101,6 @@ S3method(vec_ptype_abbr,pillar_num) S3method(vec_ptype_full,pillar_vctr) export(align) export(char) -export(colonnade) export(ctl_new_compound_pillar) export(ctl_new_pillar) export(dim_desc) diff --git a/R/multi.R b/R/multi.R index b416c28d0..3bc97cc57 100644 --- a/R/multi.R +++ b/R/multi.R @@ -1,322 +1,21 @@ -#' Format multiple vectors in a tabular display -#' -#' @description -#' The vectors are formatted to fit horizontally into a user-supplied number of -#' characters per row. -#' -#' The `colonnade()` function doesn't process the input but returns an object -#' with a [format()] and a [print()] method. -#' The implementations call [squeeze()] to create [pillar] objects and fit them to a given width. -#' -#' @param x A list, which can contain matrices or data frames. -#' If named, the names will be used as title for the pillars. Non-syntactic names -#' will be escaped. -#' @param has_row_id Include a column indicating row IDs? Pass `"*"` to mark -#' the row ID column with a star. -#' @param width Default width of the entire output, optional. -#' @inheritParams ellipsis::dots_empty -#' @keywords internal -#' @export -#' @examples -#' colonnade(list(a = 1:3, b = letters[1:3])) -#' -#' long_string <- list(paste(letters, collapse = " ")) -#' colonnade(long_string, width = 20) -#' colonnade(long_string, has_row_id = FALSE, width = 20) -#' -#' # The width can also be overridden when calling format() or print(): -#' print(colonnade(long_string), width = 20) -#' -#' # If width is larger than getOption("width"), multiple tiers are created: -#' colonnade(rep(long_string, 4), width = Inf) -colonnade <- function(x, has_row_id = TRUE, width = NULL, ...) { - if (!missing(...)) { - check_dots_empty(action = warn) - } - - # Reset local cache for each new colonnade - num_colors(forget = TRUE) - - x <- flatten_colonnade(x) - ret <- new_data_frame(x, has_row_id = has_row_id, class = "pillar_colonnade") - ret <- set_width(ret, width) - ret -} - -flatten_colonnade <- function(x) { - out <- map2( - unname(x), - names2(x), - flatten_column - ) - - vec_rbind( - !!!out, - # .ptype = data_frame(names = list(), data = list()) - .ptype = data_frame(names = character(), data = list()) - ) -} - -flatten_column <- function(x, name) { - if (name != "") { - name <- tick_if_needed(name) - } - - if (is.data.frame(x)) { - flatten_df_column(x, name) - } else if (is.matrix(x) && !inherits(x, c("Surv", "Surv2"))) { - flatten_matrix_column(x, name) - } else { - # Length-one list, will be unlist()ed afterwards - # data_frame(names = list(name), data = list(x)) - data_frame(names = name, data = list(x)) - } -} - -flatten_df_column <- function(x, name) { - if (length(x) == 0) { - # data_frame(names = list(name), data = list(new_empty_col_sentinel(x))) - data_frame(names = name, data = list(new_empty_col_sentinel(x))) - } else { - x <- flatten_colonnade(unclass(x)) - # x$names <- map(x$names, function(.x) c(name, .x)) - x$names <- paste0("$", x$names) - x$names[[1]] <- paste0(name, x$names[[1]]) - x - } -} - -flatten_matrix_column <- function(x, name) { - if (ncol(x) == 0) { - data_frame( - # names = list(c(name, "[,0]")), - names = name, - data = list(new_empty_col_sentinel(x)) - ) - } else { - x_list <- map(seq_len(ncol(x)), function(i) x[, i]) - - idx <- colnames(x) - if (is.null(idx)) { - idx <- seq_along(x_list) - } else { - idx <- encodeString(idx, quote = '"') - } - - # names <- map(idx, function(.x) c(name, .x)) - names <- paste0("[,", idx, "]") - names[[1]] <- paste0(name, names[[1]]) - - data_frame(names = names, data = x_list) - } -} - -new_empty_col_sentinel <- function(type) { - structure(list(type), class = c("pillar_empty_col")) -} - #' Squeeze a colonnade to a fixed width #' -#' The `squeeze()` function usually doesn't need to be called manually. -#' It returns an object suitable for printing and formatting at a fixed width -#' with additional information about omitted columns, which can be retrieved -#' via [extra_cols()]. +#' Defunct. #' #' @keywords internal #' @export squeeze <- function(x, width = NULL, ...) { - deprecate_soft("1.5.0", "pillar::squeeze()") - - squeeze_impl(x, width, ...) -} - -squeeze_impl <- function(x, width = NULL, ...) { - # Shortcut for zero-height corner case - zero_height <- length(x$data) == 0L || length(x$data[[1]]) == 0L - if (zero_height) { - return(new_colonnade_squeezed(list(), colonnade = x, extra_cols = seq_along(x$data))) - } - - if (is.null(width)) { - width <- get_width(x) - } - - if (is.null(width)) { - width <- getOption("width") - } - - rowid <- get_rowid_from_colonnade(x) - if (is.null(rowid)) { - rowid_width <- 0 - } else { - rowid_width <- max(get_widths(rowid)) + 1L - } - - col_widths <- colonnade_get_width(x, width, rowid_width) - col_widths_shown <- col_widths[!safe_is_na(col_widths$tier), ] - indexes <- split(seq_along(col_widths_shown$tier), col_widths_shown$tier) - - out <- map(indexes, function(i) { - inner <- map2(col_widths_shown$pillar[i], col_widths_shown$width[i], pillar_format_parts) - if (!is.null(rowid)) { - inner <- c(list(pillar_format_parts(rowid, rowid_width - 1L)), inner) - } - inner - }) - - n_cols_shown <- nrow(col_widths_shown) - extra_cols <- seq2(n_cols_shown + 1L, length(x$data)) - new_colonnade_squeezed(out, colonnade = x, extra_cols = extra_cols) -} - -get_rowid_from_colonnade <- function(x) { - has_title <- any(x$names != "") - - has_row_id <- attr(x, "has_row_id", exact = TRUE) - if (!is_false(has_row_id) && length(x$data) > 0) { - rowid <- rowidformat( - length(x$data[[1]]), - has_star = identical(has_row_id, "*"), - has_title_row = has_title - ) - } else { - rowid <- NULL - } - - rowid -} - -new_colonnade_squeezed <- function(x, colonnade, extra_cols) { - formatted_tiers <- map(x, format_colonnade_tier) - formatted <- new_vertical(as.character(unlist(formatted_tiers))) - - structure( - list(formatted), - extra_cols = colonnade[extra_cols, ], - class = "pillar_squeezed_colonnade" - ) -} - -format_colonnade_tier <- function(x) { - "!!!!!DEBUG format_colonnade_tier(`v(x)`)" - - if (length(x) == 0) { - return(character()) - } - - unlist(pmap(unname(x), paste)) -} - -#' @export -format.pillar_squeezed_colonnade <- function(x, ...) { - x[[1]] -} - -#' @export -print.pillar_squeezed_colonnade <- function(x, ...) { - print(format(x, ...), ...) - invisible(x) -} - -# Method registration happens in .onLoad() -knit_print.pillar_squeezed_colonnade <- function(x, ...) { - unlist(map(x, knit_print_squeezed_colonnade_tier)) -} - -knit_print_squeezed_colonnade_tier <- function(x) { - # Hack - header <- map_chr(map(x, `[[`, "capital_format"), `[[`, "title_format") - col <- map(x, function(xx) c(xx[["capital_format"]][["type_format"]], xx[["shaft_format"]])) - - knitr::kable(as.data.frame(col), row.names = NA, col.names = header) + deprecate_stop("1.6.4", "pillar::squeeze()") } #' Retrieve information about columns that didn't fit the available width #' -#' Formatting a [colonnade] object may lead to some columns being omitted -#' due to width restrictions. This method returns a character vector that -#' describes each of the omitted columns. +#' Defunct. #' -#' @param x The result of [squeeze()] on a [colonnade] object -#' @inheritParams ellipsis::dots_used #' @keywords internal #' @export extra_cols <- function(x, ...) { - deprecate_soft("1.5.0", "pillar::extra_cols()") - - if (!missing(...)) { - check_dots_used(action = warn) - } - - UseMethod("extra_cols") -} - -#' @rdname extra_cols -#' @param n The number of extra columns to return; the returned vector will -#' always contain as many elements as there are extra columns, but elements -#' beyond `n` will be `NA`. -#' @export -extra_cols.pillar_squeezed_colonnade <- function(x, ..., n = Inf) { - extra_cols_impl(x, n) -} - -extra_cols_impl <- function(x, n = NULL) { - extra_cols <- attr(x, "extra_cols", exact = TRUE) - ret <- rep(NA_character_, length(extra_cols$data)) - - if (is.null(n)) { - n <- Inf - } - - idx <- seq_len(min(length(extra_cols$data), n)) - ret[idx] <- map2_chr(extra_cols$data[idx], extra_cols$names[idx], format_abbrev, space = NBSP) - ret -} - -#' @export -format.pillar_colonnade <- function(x, ...) { - format(squeeze_impl(x, ...)) -} - -#' @export -print.pillar_colonnade <- function(x, ...) { - print(format(x, ...)) -} - -#' @rdname colonnade -#' @usage NULL -#' @aliases NULL -colonnade_get_width <- function(x, width, rowid_width) { - #' @details - #' Pillars may be distributed over multiple tiers if - #' `width > getOption("width")`. In this case each tier is at most - #' `getOption("width")` characters wide. The very first step of formatting - #' is to determine how many tiers are shown at most, and the width of each - #' tier. - tier_widths <- get_tier_widths(width, length(x$data), rowid_width) - - #' - #' To avoid unnecessary computation for showing very wide colonnades, a first - #' pass tries to fit all capitals into the tiers. - init_cols <- min(length(x$data), sum(floor((tier_widths + 1L) / (MIN_PILLAR_WIDTH + 1L)))) - capitals <- map2(x$data[seq_len(init_cols)], x$names[seq_len(init_cols)], pillar_capital) - init_col_widths_df <- colonnade_compute_tiered_col_widths(capitals, tier_widths) - pillar_shown <- init_col_widths_df$id[!safe_is_na(init_col_widths_df$tier)] - if (length(pillar_shown) < init_cols) { - # (Include one more pillar to indicate that the data is too wide.) - pillar_shown <- c(pillar_shown, pillar_shown[length(pillar_shown)] + 1L) - } - - #' For each pillar whose capital fits, it is then decided in which tier it is - #' shown, if at all, and how much horizontal space it may use (either its - #' minimum or its maximum width). - shafts <- map(x$data[pillar_shown], pillar_shaft) - pillars <- map2(capitals[pillar_shown], shafts, new_pillar_1e) - col_widths_df <- colonnade_compute_tiered_col_widths(pillars, tier_widths) - - #' Remaining space is then distributed proportionally to pillars that do not - #' use their desired width. - colonnade_distribute_space_df(col_widths_df, tier_widths) + deprecate_stop("1.6.4", "pillar::extra_cols()") } get_tier_widths <- function(width, ncol, rowid_width, tier_width = getOption("width")) { @@ -332,18 +31,12 @@ get_tier_widths <- function(width, ncol, rowid_width, tier_width = getOption("wi widths[widths >= 1L] } -colonnade_compute_tiered_col_widths <- function(pillars, tier_widths) { - max_tier_width <- max(tier_widths) - - max_widths <- pmin(map_int(map(pillars, get_widths), max), max_tier_width) - min_widths <- pmin(map_int(map(pillars, get_min_widths), max), max_widths) - - ret <- colonnade_compute_tiered_col_widths_df(max_widths, min_widths, tier_widths) - ret$pillar <- pillars - ret -} - -#' @rdname colonnade +#' Distributing pillars over multiple tiers +#' +#' Documentation generated from inline code comments. +#' +#' @name colonnade +#' @keywords internal #' @usage NULL #' @aliases NULL colonnade_compute_tiered_col_widths_df <- function(max_widths, min_widths, tier_widths) { diff --git a/R/shaft-.R b/R/shaft-.R index d45db3013..6f48984da 100644 --- a/R/shaft-.R +++ b/R/shaft-.R @@ -71,11 +71,6 @@ pillar_shaft <- function(x, ...) { UseMethod("pillar_shaft") } -#' @export -pillar_shaft.pillar_empty_col <- function(x, ...) { - new_empty_shaft() -} - #' @param width Width for printing and formatting. #' @export #' @rdname pillar_shaft diff --git a/R/type-sum.R b/R/type-sum.R index 71f28da67..e097dca8c 100644 --- a/R/type-sum.R +++ b/R/type-sum.R @@ -58,11 +58,6 @@ type_sum.default <- function(x) { ) } -# Registered in .onLoad() -vec_ptype_abbr.pillar_empty_col <- function(x, ...) { - vec_ptype_abbr(x[[1]]) -} - #' @description #' `obj_sum()` also includes the size (but not the shape) of the object #' if [vctrs::vec_is()] is `TRUE`. diff --git a/R/zzz.R b/R/zzz.R index 567bd8638..e5999c77c 100644 --- a/R/zzz.R +++ b/R/zzz.R @@ -35,8 +35,6 @@ NULL # nolint end # Can't use vctrs::s3_register() here with vctrs 0.1.0 # https://github.com/r-lib/vctrs/pull/314 - register_s3_method("knitr", "knit_print", "pillar_squeezed_colonnade") - register_s3_method("vctrs", "vec_ptype_abbr", "pillar_empty_col") register_s3_method("bit64", "pillar_shaft", "integer64", gen_pkg = "pillar") register_s3_method("survival", "pillar_shaft", "Surv", gen_pkg = "pillar") register_s3_method("survival", "type_sum", "Surv", gen_pkg = "pillar") diff --git a/man/colonnade.Rd b/man/colonnade.Rd index 55dc051d8..157d1d7a0 100644 --- a/man/colonnade.Rd +++ b/man/colonnade.Rd @@ -1,46 +1,11 @@ % Generated by roxygen2: do not edit by hand % Please edit documentation in R/multi.R \name{colonnade} -\alias{colonnade} -\title{Format multiple vectors in a tabular display} -\usage{ -colonnade(x, has_row_id = TRUE, width = NULL, ...) -} -\arguments{ -\item{x}{A list, which can contain matrices or data frames. -If named, the names will be used as title for the pillars. Non-syntactic names -will be escaped.} - -\item{has_row_id}{Include a column indicating row IDs? Pass \code{"*"} to mark -the row ID column with a star.} - -\item{width}{Default width of the entire output, optional.} - -\item{...}{These dots are for future extensions and must be empty.} -} +\title{Distributing pillars over multiple tiers} \description{ -The vectors are formatted to fit horizontally into a user-supplied number of -characters per row. - -The \code{colonnade()} function doesn't process the input but returns an object -with a \code{\link[=format]{format()}} and a \code{\link[=print]{print()}} method. -The implementations call \code{\link[=squeeze]{squeeze()}} to create \link{pillar} objects and fit them to a given width. +Documentation generated from inline code comments. } \details{ -Pillars may be distributed over multiple tiers if -\code{width > getOption("width")}. In this case each tier is at most -\code{getOption("width")} characters wide. The very first step of formatting -is to determine how many tiers are shown at most, and the width of each -tier. - -To avoid unnecessary computation for showing very wide colonnades, a first -pass tries to fit all capitals into the tiers. -For each pillar whose capital fits, it is then decided in which tier it is -shown, if at all, and how much horizontal space it may use (either its -minimum or its maximum width). -Remaining space is then distributed proportionally to pillars that do not -use their desired width. - For fitting pillars in one or more tiers, first a check is made if all pillars fit with their maximum width (e.g., \code{option(tibble.width = Inf)} or narrow colonnade). @@ -87,17 +52,4 @@ rounded down. Any space remaining after rounding is distributed from left to right, one space per column. } -\examples{ -colonnade(list(a = 1:3, b = letters[1:3])) - -long_string <- list(paste(letters, collapse = " ")) -colonnade(long_string, width = 20) -colonnade(long_string, has_row_id = FALSE, width = 20) - -# The width can also be overridden when calling format() or print(): -print(colonnade(long_string), width = 20) - -# If width is larger than getOption("width"), multiple tiers are created: -colonnade(rep(long_string, 4), width = Inf) -} \keyword{internal} diff --git a/man/extra_cols.Rd b/man/extra_cols.Rd index e9b75dbc2..3c2ff3c6c 100644 --- a/man/extra_cols.Rd +++ b/man/extra_cols.Rd @@ -2,25 +2,11 @@ % Please edit documentation in R/multi.R \name{extra_cols} \alias{extra_cols} -\alias{extra_cols.pillar_squeezed_colonnade} \title{Retrieve information about columns that didn't fit the available width} \usage{ extra_cols(x, ...) - -\method{extra_cols}{pillar_squeezed_colonnade}(x, ..., n = Inf) -} -\arguments{ -\item{x}{The result of \code{\link[=squeeze]{squeeze()}} on a \link{colonnade} object} - -\item{...}{Arguments passed to methods.} - -\item{n}{The number of extra columns to return; the returned vector will -always contain as many elements as there are extra columns, but elements -beyond \code{n} will be \code{NA}.} } \description{ -Formatting a \link{colonnade} object may lead to some columns being omitted -due to width restrictions. This method returns a character vector that -describes each of the omitted columns. +Defunct. } \keyword{internal} diff --git a/man/squeeze.Rd b/man/squeeze.Rd index eddcf715c..4161fc4b6 100644 --- a/man/squeeze.Rd +++ b/man/squeeze.Rd @@ -7,9 +7,6 @@ squeeze(x, width = NULL, ...) } \description{ -The \code{squeeze()} function usually doesn't need to be called manually. -It returns an object suitable for printing and formatting at a fixed width -with additional information about omitted columns, which can be retrieved -via \code{\link[=extra_cols]{extra_cols()}}. +Defunct. } \keyword{internal} diff --git a/tests/testthat/_snaps/format_multi.md b/tests/testthat/_snaps/format_multi.md index 0c337dc20..54f029403 100644 --- a/tests/testthat/_snaps/format_multi.md +++ b/tests/testthat/_snaps/format_multi.md @@ -21,902 +21,3 @@ Output [1] "NA" -# output test - - Code - colonnade(x, width = 4) - colonnade(x, width = 5) - colonnade(x, width = 6) - colonnade(x, width = 7) - Output - colu~ - - 1 1.23 - 2 2.23 - 3 3.23 - Code - colonnade(x, width = 8) - Output - colum~ - - 1 1.23 - 2 2.23 - 3 3.23 - Code - colonnade(x, width = 9) - Output - column~ - - 1 1.23 - 2 2.23 - 3 3.23 - Code - colonnade(x, width = 10) - Output - column_~ - - 1 1.23 - 2 2.23 - 3 3.23 - Code - colonnade(x, width = 11) - Output - column_z~ - - 1 1.23 - 2 2.23 - 3 3.23 - Code - colonnade(x, width = 12) - Output - column_ze~ - - 1 1.23 - 2 2.23 - 3 3.23 - Code - colonnade(x, width = 13) - Output - column_zer~ - - 1 1.23 - 2 2.23 - 3 3.23 - Code - colonnade(x, width = 14) - Output - column_zero~ - - 1 1.23 - 2 2.23 - 3 3.23 - Code - colonnade(x, width = 15) - Output - column_zero_~ - - 1 1.23 - 2 2.23 - 3 3.23 - Code - colonnade(x, width = 16) - Output - column_zero_o~ - - 1 1.23 - 2 2.23 - 3 3.23 - Code - colonnade(x, width = 17) - Output - column_zero_one - - 1 1.23 - 2 2.23 - 3 3.23 - Code - colonnade(x, width = 18) - Output - column_zero_one - - 1 1.23 - 2 2.23 - 3 3.23 - Code - colonnade(x, width = 19) - Output - column_zero_one - - 1 1.23 - 2 2.23 - 3 3.23 - Code - colonnade(x, width = 20) - Output - column_zero_one - - 1 1.23 - 2 2.23 - 3 3.23 - Code - colonnade(x, width = 21) - Output - column_zero_one - - 1 1.23 - 2 2.23 - 3 3.23 - Code - colonnade(x, width = 22) - Output - column_zero_one - - 1 1.23 - 2 2.23 - 3 3.23 - Code - colonnade(x, width = 23) - Output - column_zero_one - - 1 1.23 - 2 2.23 - 3 3.23 - Code - colonnade(x, width = 24) - Output - column_zero_one col_02 - - 1 1.23 a - 2 2.23 b - 3 3.23 c - Code - colonnade(x, width = 25) - Output - column_zero_one col_02 - - 1 1.23 a - 2 2.23 b - 3 3.23 c - Code - colonnade(x, width = 26) - Output - column_zero_one col_02 - - 1 1.23 a - 2 2.23 b - 3 3.23 c - Code - colonnade(x, width = 27) - Output - column_zero_one col_02 - - 1 1.23 a - 2 2.23 b - 3 3.23 c - Code - colonnade(x, width = 28) - Output - column_zero_one col_02 - - 1 1.23 a - 2 2.23 b - 3 3.23 c - Code - colonnade(x, width = 29) - Output - column_zero_one col_02 - - 1 1.23 a - 2 2.23 b - 3 3.23 c - Code - colonnade(x, width = 30) - Output - column_zero_one col_02 - - 1 1.23 a - 2 2.23 b - 3 3.23 c - Code - colonnade(x, width = 31) - Output - column_zero_one col_02 col_03 - - 1 1.23 a a - 2 2.23 b b - 3 3.23 c c - Code - colonnade(x, width = 32) - Output - column_zero_one col_02 col_03 - - 1 1.23 a a - 2 2.23 b b - 3 3.23 c c - Code - colonnade(x, width = 33) - Output - column_zero_one col_02 col_03 - - 1 1.23 a a - 2 2.23 b b - 3 3.23 c c - Code - colonnade(x, width = 34) - Output - column_zero_one col_02 col_03 - - 1 1.23 a a - 2 2.23 b b - 3 3.23 c c - Code - colonnade(x, width = 35) - Output - column_zero_one col_02 col_03 - - 1 1.23 a a - 2 2.23 b b - 3 3.23 c c - Code - colonnade(x, width = 36) - Output - column_zero_one col_02 col_03 - - 1 1.23 a a - 2 2.23 b b - 3 3.23 c c - Code - colonnade(x, width = 37) - Output - column_zero_one col_02 col_03 - - 1 1.23 a a - 2 2.23 b b - 3 3.23 c c - Code - colonnade(x, width = 38) - Output - column_zero_one col_02 col_03 col_04 - - 1 1.23 a a a - 2 2.23 b b b - 3 3.23 c c c - Code - colonnade(x, width = 39) - Output - column_zero_one col_02 col_03 col_04 - - 1 1.23 a a a - 2 2.23 b b b - 3 3.23 c c c - Code - colonnade(x, width = Inf) - Output - column_zero_one col_02 col_03 col_04 - - 1 1.23 a a a - 2 2.23 b b b - 3 3.23 c c c - ---- - - Code - colonnade(rep(list(paste(letters, collapse = " ")), 4), width = Inf) - Output - - 1 a b c d e f g h i j k l m n o p q r s t u v w x y z - - 1 a b c d e f g h i j k l m n o p q r s t u v w x y z - - 1 a b c d e f g h i j k l m n o p q r s t u v w x y z - - 1 a b c d e f g h i j k l m n o p q r s t u v w x y z - ---- - - Code - new_vertical(extra_cols_impl(squeeze_impl(colonnade(x), width = 10))) - Output - col_02  - col_03  - col_04  - ---- - - Code - new_vertical(extra_cols_impl(squeeze_impl(colonnade(x), width = 20))) - Output - col_02  - col_03  - col_04  - ---- - - Code - new_vertical(extra_cols_impl(squeeze_impl(colonnade(x), width = 30))) - Output - col_03  - col_04  - ---- - - Code - new_vertical(extra_cols_impl(squeeze_impl(colonnade(x), width = 35))) - Output - col_04  - ---- - - Code - new_vertical(extra_cols_impl(squeeze_impl(colonnade(x), width = 40))) - -# tests from tibble - - Code - colonnade(mtcars[1:8, ], has_row_id = "*", width = 30) - Output - mpg cyl disp hp - * - 1 21 6 160 110 - 2 21 6 160 110 - 3 22.8 4 108 93 - 4 21.4 6 258 110 - 5 18.7 8 360 175 - 6 18.1 6 225 105 - 7 14.3 8 360 245 - 8 24.4 4 147. 62 - Code - colonnade(iris[1:5, ], width = 30) - Output - Sepal.Length Sepal.Width - - 1 5.1 3.5 - 2 4.9 3 - 3 4.7 3.2 - 4 4.6 3.1 - 5 5 3.6 - Code - colonnade(iris[1:3, ], width = 20) - Output - Sepal.Length - - 1 5.1 - 2 4.9 - 3 4.7 - Code - colonnade(df_all, width = 30) - Output - a b c d - - 1 1 1 TRUE a - 2 2.5 2 FALSE b - 3 NA NA NA - Code - colonnade(df_all, width = 300) - Output - a b c d e f g h - - 1 1 1 TRUE a a 2015-12-10 2015-12-09 10:51:35 - 2 2.5 2 FALSE b b 2015-12-11 2015-12-09 10:51:36 - 3 NA NA NA NA NA - i - - 1 - 2 - 3 - Code - options(width = 70) - colonnade(df_all, width = 300) - Output - a b c d e f g - - 1 1 1 TRUE a a 2015-12-10 2015-12-09 10:51:35 - 2 2.5 2 FALSE b b 2015-12-11 2015-12-09 10:51:36 - 3 NA NA NA NA NA - h i - - 1 - 2 - 3 - Code - options(width = 60) - colonnade(df_all, width = 300) - Output - a b c d e f - - 1 1 1 TRUE a a 2015-12-10 - 2 2.5 2 FALSE b b 2015-12-11 - 3 NA NA NA NA - g h i - - 1 2015-12-09 10:51:35 - 2 2015-12-09 10:51:36 - 3 NA - Code - options(width = 50) - colonnade(df_all, width = 300) - Output - a b c d e f - - 1 1 1 TRUE a a 2015-12-10 - 2 2.5 2 FALSE b b 2015-12-11 - 3 NA NA NA NA - g h i - - 1 2015-12-09 10:51:35 - 2 2015-12-09 10:51:36 - 3 NA - Code - options(width = 40) - colonnade(df_all, width = 300) - Output - a b c d e - - 1 1 1 TRUE a a - 2 2.5 2 FALSE b b - 3 NA NA NA - f g - - 1 2015-12-10 2015-12-09 10:51:35 - 2 2015-12-11 2015-12-09 10:51:36 - 3 NA NA - h i - - 1 - 2 - 3 - Code - options(width = 30) - colonnade(df_all, width = 300) - Output - a b c d - - 1 1 1 TRUE a - 2 2.5 2 FALSE b - 3 NA NA NA - e f - - 1 a 2015-12-10 - 2 b 2015-12-11 - 3 NA - g - - 1 2015-12-09 10:51:35 - 2 2015-12-09 10:51:36 - 3 NA - h i - - 1 - 2 - 3 - Code - options(width = 20) - colonnade(df_all, width = 300) - Output - a b c - - 1 1 1 TRUE - 2 2.5 2 FALSE - 3 NA NA NA - d e - - 1 a a - 2 b b - 3 - f - - 1 2015-12-10 - 2 2015-12-11 - 3 NA - g - - 1 2015-12-09 10:51:~ - 2 2015-12-09 10:51:~ - 3 NA - h - - 1 - 2 - 3 - i - - 1 - 2 - 3 - Code - colonnade(list(`\n` = c("\n", "\""), `\r` = factor("\n")), width = 30) - Output - `\n` `\r` - - 1 "\n" "\n" - 2 "\"" "\n" - Code - colonnade(list(a = c("", " ", "a ", " a")), width = 30) - Output - a - - 1 "" - 2 " " - 3 "a " - 4 " a" - Code - colonnade(list(`mean(x)` = 5, `var(x)` = 3), width = 30) - Output - `mean(x)` `var(x)` - - 1 5 3 - -# NA names - - Code - colonnade(x, width = 30) - Output - `NA` - - 1 1 4 - 2 2 5 - 3 3 6 - -# sep argument - - Code - colonnade(x, width = 30) - Output - sep - - 1 1 - 2 2 - 3 3 - Code - # dummy - -# color, options: UTF-8 is TRUE - - Code - crayon::has_color() - Output - [1] TRUE - Code - crayon::num_colors() - Output - [1] 16 - Code - has_color() - Output - [1] TRUE - Code - num_colors() - Output - [1] 16 - Code - style_na("NA") - Output - [1] "\033[31mNA\033[39m" - Code - style_neg("-1") - Output - [1] "\033[31m-1\033[39m" - ---- - - Code - style_na("NA") - Output - [1] "\033[31mNA\033[39m" - ---- - - Code - print(xf) - Output - x -  - 1 -0.001 - 2 0.01 - 3 -0.1 - 4 1 - 5 -10 - 6 100 - 7 -1000 - 8 10000 - 9 NA - Code - with_options(pillar.subtle_num = TRUE, print(xf)) - Output - x -  - 1 -0.001 - 2 0.01 - 3 -0.1 - 4 1 - 5 -10 - 6 100 - 7 -1000 - 8 10000 - 9 NA - Code - with_options(pillar.subtle = FALSE, print(xf)) - Output - x -  - 1 -0.001 - 2 0.01 - 3 -0.1 - 4 1 - 5 -10 - 6 100 - 7 -1000 - 8 10000 - 9 NA - Code - with_options(pillar.neg = FALSE, print(xf)) - Output - x -  - 1 -0.001 - 2 0.01 - 3 -0.1 - 4 1 - 5 -10 - 6 100 - 7 -1000 - 8 10000 - 9 NA - Code - with_options(pillar.subtle = FALSE, pillar.neg = FALSE, print(xf)) - Output - x -  - 1 -0.001 - 2 0.01 - 3 -0.1 - 4 1 - 5 -10 - 6 100 - 7 -1000 - 8 10000 - 9 NA - Code - with_options(pillar.bold = TRUE, print(xf)) - Output - x -  - 1 -0.001 - 2 0.01 - 3 -0.1 - 4 1 - 5 -10 - 6 100 - 7 -1000 - 8 10000 - 9 NA - ---- - - Code - colonnade(list(a_very_long_column_name = 0), width = 15) - Output - a_very_long_… -  - 1 0 - -# color, options: UTF-8 is FALSE - - Code - crayon::has_color() - Output - [1] TRUE - Code - crayon::num_colors() - Output - [1] 16 - Code - has_color() - Output - [1] TRUE - Code - num_colors() - Output - [1] 16 - Code - style_na("NA") - Output - [1] "\033[31mNA\033[39m" - Code - style_neg("-1") - Output - [1] "\033[31m-1\033[39m" - ---- - - Code - style_na("NA") - Output - [1] "\033[31mNA\033[39m" - ---- - - Code - print(xf) - Output - x -  - 1 -0.001 - 2 0.01 - 3 -0.1 - 4 1 - 5 -10 - 6 100 - 7 -1000 - 8 10000 - 9 NA - Code - with_options(pillar.subtle_num = TRUE, print(xf)) - Output - x -  - 1 -0.001 - 2 0.01 - 3 -0.1 - 4 1 - 5 -10 - 6 100 - 7 -1000 - 8 10000 - 9 NA - Code - with_options(pillar.subtle = FALSE, print(xf)) - Output - x -  - 1 -0.001 - 2 0.01 - 3 -0.1 - 4 1 - 5 -10 - 6 100 - 7 -1000 - 8 10000 - 9 NA - Code - with_options(pillar.neg = FALSE, print(xf)) - Output - x -  - 1 -0.001 - 2 0.01 - 3 -0.1 - 4 1 - 5 -10 - 6 100 - 7 -1000 - 8 10000 - 9 NA - Code - with_options(pillar.subtle = FALSE, pillar.neg = FALSE, print(xf)) - Output - x -  - 1 -0.001 - 2 0.01 - 3 -0.1 - 4 1 - 5 -10 - 6 100 - 7 -1000 - 8 10000 - 9 NA - Code - with_options(pillar.bold = TRUE, print(xf)) - Output - x -  - 1 -0.001 - 2 0.01 - 3 -0.1 - 4 1 - 5 -10 - 6 100 - 7 -1000 - 8 10000 - 9 NA - ---- - - Code - colonnade(list(a_very_long_column_name = 0), width = 15) - Output - a_very_long_~ -  - 1 0 - -# sanity check (2) - - Code - crayon::has_color() - Output - [1] FALSE - Code - crayon::num_colors() - Output - [1] 1 - Code - has_color() - Output - [1] FALSE - Code - num_colors() - Output - [1] 1 - Code - style_na("NA") - Output - [1] "NA" - -# tibble columns - - Code - colonnade(x, width = 30) - Output - a b$c $d - - 1 1 4 7 - 2 2 5 8 - 3 3 6 9 - -# tibble columns (nested) - - Code - colonnade(x, width = 40) - Output - a b$c $d $e$f $$g - - 1 1 4 7 10 13 - 2 2 5 8 11 14 - 3 3 6 9 12 15 - -# tibble columns (empty) - - Code - colonnade(x, width = 40) - Output - a b$c $d $e $f - - 1 1 4 7 10 - 2 2 5 8 11 - 3 3 6 9 12 - -# matrix columns (unnamed) - - Code - colonnade(x, width = 30) - Output - a b[,1] [,2] - - 1 1 4 7 - 2 2 5 8 - 3 3 6 9 - -# matrix columns (named) - - Code - colonnade(x, width = 30) - Output - a b[,"c"] [,"d"] - - 1 1 4 7 - 2 2 5 8 - 3 3 6 9 - -# matrix columns (empty) - - Code - colonnade(x, width = 30) - Output - a b c - - 1 1 4 - 2 2 5 - 3 3 6 - diff --git a/tests/testthat/_snaps/zzx-format_character.md b/tests/testthat/_snaps/zzx-format_character.md deleted file mode 100644 index 9ffcef8c6..000000000 --- a/tests/testthat/_snaps/zzx-format_character.md +++ /dev/null @@ -1,23 +0,0 @@ -# output test (not on Windows) - - Code - colonnade(chartype_frame(), width = 50) - Output - chars desc - - 1 "\u0001\u001f" C0 control code - 2 "\a\b\f\n\r\t" Named control code - 3 "abcdefuvwxyz" ASCII - 4 "\u0080\u009f" C1 control code - 5 " ¡¢£¤¥úûüýþÿ" Latin-1 - 6 "ĀāĂ㥹ĆćĈĉĊċ" Unicode - 7 "!"#$%&" Unicode wide - 8 "\u0e00\u2029" Unicode control - 9 "x­x​x‌x‍x‎x‏x͏xx󠀁x󠀠x󠇯x" Unicode ignorable - 10 "àáâãāa̅ăȧäảåa̋" Unicode mark - 11 "😀😁😂😃😄💃" Emoji - 12 "x\U0010ffffx" Unassigned - 13 "\xfd\xfe\xff" Invalid - 14 "\\" Backslash - 15 "\"" Quote - diff --git a/tests/testthat/test-format_multi.R b/tests/testthat/test-format_multi.R index 258b96b86..cf4eca383 100644 --- a/tests/testthat/test-format_multi.R +++ b/tests/testthat/test-format_multi.R @@ -12,270 +12,3 @@ test_that("sanity check (1)", { style_na("NA") }) }) - -test_that("output test", { - x <- list( - column_zero_one = 1:3 + 0.23, - col_02 = letters[1:3], - col_03 = factor(letters[1:3]), - col_04 = ordered(letters[1:3]) - ) - expect_snapshot({ - colonnade(x, width = 4) - colonnade(x, width = 5) - colonnade(x, width = 6) - colonnade(x, width = 7) - colonnade(x, width = 8) - colonnade(x, width = 9) - colonnade(x, width = 10) - colonnade(x, width = 11) - colonnade(x, width = 12) - colonnade(x, width = 13) - colonnade(x, width = 14) - colonnade(x, width = 15) - colonnade(x, width = 16) - colonnade(x, width = 17) - colonnade(x, width = 18) - colonnade(x, width = 19) - colonnade(x, width = 20) - colonnade(x, width = 21) - colonnade(x, width = 22) - colonnade(x, width = 23) - colonnade(x, width = 24) - colonnade(x, width = 25) - colonnade(x, width = 26) - colonnade(x, width = 27) - colonnade(x, width = 28) - colonnade(x, width = 29) - colonnade(x, width = 30) - colonnade(x, width = 31) - colonnade(x, width = 32) - colonnade(x, width = 33) - colonnade(x, width = 34) - colonnade(x, width = 35) - colonnade(x, width = 36) - colonnade(x, width = 37) - colonnade(x, width = 38) - colonnade(x, width = 39) - colonnade(x, width = Inf) - }) - - expect_snapshot({ - colonnade(rep(list(paste(letters, collapse = " ")), 4), width = Inf) - }) - - # Spurious warnings on Windows - suppressWarnings( - expect_snapshot({ - new_vertical(extra_cols_impl(squeeze_impl(colonnade(x), width = 10))) - }) - ) - - suppressWarnings( - expect_snapshot({ - new_vertical(extra_cols_impl(squeeze_impl(colonnade(x), width = 20))) - }) - ) - - suppressWarnings( - expect_snapshot({ - new_vertical(extra_cols_impl(squeeze_impl(colonnade(x), width = 30))) - }) - ) - - suppressWarnings( - expect_snapshot({ - new_vertical(extra_cols_impl(squeeze_impl(colonnade(x), width = 35))) - }) - ) - - expect_snapshot({ - new_vertical(extra_cols_impl(squeeze_impl(colonnade(x), width = 40))) - }) -}) - -test_that("tests from tibble", { - skip_if_not_installed("rlang", "0.4.11.9000") - local_options(width = 80) - - expect_snapshot({ - colonnade(mtcars[1:8, ], has_row_id = "*", width = 30) - colonnade(iris[1:5, ], width = 30) - colonnade(iris[1:3, ], width = 20) - colonnade(df_all, width = 30) - colonnade(df_all, width = 300) - options(width = 70) - colonnade(df_all, width = 300) - options(width = 60) - colonnade(df_all, width = 300) - options(width = 50) - colonnade(df_all, width = 300) - options(width = 40) - colonnade(df_all, width = 300) - options(width = 30) - colonnade(df_all, width = 300) - options(width = 20) - colonnade(df_all, width = 300) - colonnade(list(`\n` = c("\n", '"'), `\r` = factor("\n")), width = 30) - colonnade(list(a = c("", " ", "a ", " a")), width = 30) - colonnade(list("mean(x)" = 5, "var(x)" = 3), width = 30) - }) -}) - -test_that("empty", { - expect_equal( - format(colonnade(list(a = character(), b = logical()), width = 30)), - structure(character(), class = "pillar_vertical") - ) - expect_equal( - format(colonnade(iris[1:5, character()], width = 30)), - structure(character(), class = "pillar_vertical") - ) -}) - -test_that("NA names", { - x <- list(`NA` = 1:3, set_to_NA = 4:6) - names(x)[[2]] <- NA_character_ - expect_snapshot({ - colonnade(x, width = 30) - }) -}) - -test_that("sep argument", { - x <- list(sep = 1:3) - expect_snapshot({ - colonnade(x, width = 30) - "dummy" - }) -}) - -# Run opposite test to snapshot output but not alter it -if (!l10n_info()$`UTF-8`) { - test_that("color, options: UTF-8 is TRUE", { - skip("Symmetry") - }) -} - -test_that(paste0("color, options: UTF-8 is ", l10n_info()$`UTF-8`), { - local_colors() - expect_true(crayon::has_color()) - expect_equal(crayon::num_colors(), 16) - expect_true(has_color()) - expect_equal(num_colors(), 16) - - if (l10n_info()$`UTF-8`) { - local_utf8() - expect_true(cli::is_utf8_output()) - } - - expect_snapshot({ - crayon::has_color() - crayon::num_colors() - has_color() - num_colors() - style_na("NA") - style_neg("-1") - }) - - expect_snapshot({ - style_na("NA") - }) - - xf <- colonnade(list(x = c((10^(-3:4)) * c(-1, 1), NA))) - - expect_snapshot({ - print(xf) - with_options(pillar.subtle_num = TRUE, print(xf)) - with_options(pillar.subtle = FALSE, print(xf)) - with_options(pillar.neg = FALSE, print(xf)) - with_options(pillar.subtle = FALSE, pillar.neg = FALSE, print(xf)) - with_options(pillar.bold = TRUE, print(xf)) - }) - - expect_snapshot({ - colonnade(list(a_very_long_column_name = 0), width = 15) - }) -}) - -# Run opposite test to snapshot output but not alter it -if (l10n_info()$`UTF-8`) { - test_that("color, options: UTF-8 is FALSE", { - skip("Symmetry") - }) -} - -test_that("sanity check (2)", { - expect_false(crayon::has_color()) - expect_equal(crayon::num_colors(), 1) - expect_false(has_color()) - expect_equal(num_colors(), 1) - - expect_snapshot({ - crayon::has_color() - crayon::num_colors() - has_color() - num_colors() - style_na("NA") - }) -}) - -test_that("tibble columns", { - x <- list(a = 1:3, b = data.frame(c = 4:6, d = 7:9)) - expect_snapshot({ - colonnade(x, width = 30) - }) -}) - -test_that("tibble columns (nested)", { - x <- list( - a = 1:3, - b = structure( - list( - c = 4:6, d = 7:9, - e = data.frame(f = 10:12, g = 13:15) - ), - class = "data.frame" - ) - ) - expect_snapshot({ - colonnade(x, width = 40) - }) -}) - -test_that("tibble columns (empty)", { - x <- list( - a = 1:3, - b = structure( - list( - c = 4:6, d = 7:9, - e = data.frame(f = 10:12)[, 0], - f = 10:12 - ), - class = "data.frame" - ) - ) - expect_snapshot({ - colonnade(x, width = 40) - }) -}) - -test_that("matrix columns (unnamed)", { - x <- list(a = 1:3, b = matrix(4:9, ncol = 2)) - expect_snapshot({ - colonnade(x, width = 30) - }) -}) - -test_that("matrix columns (named)", { - x <- list(a = 1:3, b = matrix(4:9, ncol = 2, dimnames = list(NULL, c("c", "d")))) - expect_snapshot({ - colonnade(x, width = 30) - }) -}) - -test_that("matrix columns (empty)", { - x <- list(a = 1:3, b = matrix(4:6, ncol = 1)[, 0], c = 4:6) - expect_snapshot({ - colonnade(x, width = 30) - }) -}) diff --git a/tests/testthat/test-format_multi_fuzz.R b/tests/testthat/test-format_multi_fuzz.R deleted file mode 100644 index e5b55054c..000000000 --- a/tests/testthat/test-format_multi_fuzz.R +++ /dev/null @@ -1,39 +0,0 @@ -test_that("strings with varying widths", { - local_options(width = 80) - - # Generated by data-raw/create-chr-tests.R - # nolint start - expect_snapshot({ - options(width = 59) - colonnade(df_str[c(12L, 33L, 36L, 7L, 41L, 3L, 18L, 23L, 13L, 44L, 14L, 16L, 25L, 21L, 19L, 45L, 43L, 29L, 1L, 30L, 22L, 27L, 15L, 47L, 28L, 31L, 10L, 50L, 4L, 40L, 42L, 8L, 6L, 9L, 24L, 48L, 38L, 37L, 34L, 49L, 46L, 2L, 32L, 35L, 39L, 11L, 17L, 5L, 26L, 20L)], width = 1382) - options(width = 54) - colonnade(df_str[c(40L, 28L, 7L, 16L, 48L, 6L, 21L, 1L, 20L, 17L, 47L, 45L, 29L, 41L, 49L, 34L, 4L, 39L, 18L, 36L, 26L, 38L, 10L, 8L, 5L, 15L, 44L, 24L, 46L, 14L, 25L, 27L, 3L, 37L, 35L, 12L, 9L, 13L, 22L, 33L, 42L, 11L, 19L, 50L, 23L, 30L, 32L, 2L, 43L, 31L)], width = 837) - options(width = 32) - colonnade(df_str[c(47L, 42L, 4L, 46L, 9L, 34L, 19L, 39L, 8L, 32L, 36L, 12L, 29L, 5L, 15L, 11L, 31L, 27L, 33L, 28L, 43L, 6L, 13L, 22L, 14L, 16L, 35L, 50L, 38L, 7L, 23L, 45L, 40L, 3L, 2L, 24L, 41L, 10L, 30L, 25L, 17L, 26L, 48L, 37L, 49L, 1L, 18L, 21L, 44L, 20L)], width = 455) - options(width = 55) - colonnade(df_str[c(41L, 4L, 25L, 31L, 8L, 22L, 19L, 10L, 29L, 21L, 34L, 5L, 26L, 36L, 47L, 46L, 2L, 24L, 27L, 39L, 28L, 43L, 32L, 30L, 48L, 44L, 6L, 20L, 13L, 15L, 18L, 42L, 9L, 12L, 37L, 45L, 16L, 40L, 11L, 14L, 38L, 1L, 7L, 3L, 23L, 35L, 50L, 17L, 49L, 33L)], width = 855) - options(width = 54) - colonnade(df_str[c(27L, 22L, 9L, 23L, 16L, 19L, 25L, 31L, 44L, 1L, 28L, 46L, 12L, 20L, 43L, 37L, 5L, 2L, 18L, 41L, 26L, 33L, 11L, 49L, 24L, 35L, 4L, 47L, 30L, 7L, 34L, 3L, 32L, 42L, 10L, 45L, 38L, 39L, 48L, 14L, 6L, 17L, 36L, 50L, 40L, 13L, 8L, 21L, 15L, 29L)], width = 552) - options(width = 49) - colonnade(df_str[c(32L, 24L, 18L, 25L, 26L, 13L, 33L, 2L, 50L, 38L, 37L, 16L, 27L, 9L, 28L, 49L, 34L, 15L, 17L, 35L, 22L, 47L, 3L, 21L, 23L, 41L, 5L, 1L, 14L, 46L, 30L, 31L, 44L, 4L, 7L, 40L, 43L, 12L, 29L, 8L, 36L, 45L, 11L, 20L, 10L, 6L, 19L, 48L, 39L, 42L)], width = 1031) - options(width = 38) - colonnade(df_str[c(44L, 34L, 49L, 9L, 15L, 16L, 1L, 10L, 40L, 29L, 26L, 22L, 4L, 43L, 20L, 17L, 46L, 33L, 35L, 32L, 2L, 12L, 8L, 37L, 23L, 39L, 7L, 18L, 36L, 42L, 6L, 30L, 19L, 25L, 5L, 21L, 47L, 50L, 28L, 11L, 31L, 14L, 24L, 27L, 45L, 41L, 38L, 3L, 13L, 48L)], width = 429) - options(width = 54) - colonnade(df_str[c(21L, 26L, 8L, 22L, 41L, 24L, 13L, 5L, 47L, 37L, 4L, 42L, 19L, 34L, 11L, 43L, 38L, 3L, 33L, 20L, 31L, 2L, 18L, 48L, 27L, 44L, 9L, 35L, 30L, 6L, 49L, 10L, 1L, 16L, 46L, 29L, 12L, 14L, 45L, 36L, 15L, 39L, 50L, 23L, 17L, 28L, 7L, 32L, 40L, 25L)], width = 633) - options(width = 39) - colonnade(df_str[c(23L, 49L, 13L, 37L, 3L, 25L, 36L, 4L, 9L, 7L, 27L, 48L, 12L, 10L, 50L, 14L, 38L, 39L, 46L, 22L, 28L, 8L, 21L, 44L, 32L, 40L, 31L, 1L, 29L, 34L, 35L, 33L, 19L, 15L, 41L, 20L, 47L, 18L, 16L, 45L, 6L, 5L, 24L, 26L, 43L, 11L, 42L, 30L, 17L, 2L)], width = 1496) - options(width = 31) - colonnade(df_str[c(45L, 14L, 49L, 24L, 22L, 31L, 42L, 18L, 16L, 47L, 25L, 4L, 37L, 8L, 26L, 21L, 50L, 5L, 41L, 30L, 2L, 33L, 34L, 3L, 44L, 19L, 43L, 6L, 32L, 29L, 20L, 1L, 13L, 11L, 40L, 12L, 48L, 23L, 9L, 15L, 46L, 36L, 27L, 35L, 28L, 10L, 7L, 39L, 17L, 38L)], width = 493) - options(width = 52) - colonnade(df_str[c(38L, 46L, 17L, 11L, 24L, 18L, 16L, 39L, 50L, 42L, 6L, 13L, 37L, 29L, 41L, 47L, 9L, 33L, 44L, 31L, 45L, 36L, 28L, 5L, 10L, 30L, 20L, 1L, 14L, 43L, 49L, 23L, 26L, 21L, 32L, 19L, 34L, 15L, 48L, 4L, 7L, 35L, 40L, 8L, 22L, 3L, 25L, 12L, 27L, 2L)], width = 1130) - options(width = 58) - colonnade(df_str[c(17L, 28L, 29L, 27L, 20L, 31L, 43L, 30L, 32L, 48L, 10L, 50L, 13L, 12L, 36L, 21L, 46L, 33L, 25L, 35L, 1L, 5L, 16L, 34L, 18L, 42L, 3L, 11L, 40L, 26L, 37L, 7L, 39L, 6L, 4L, 19L, 8L, 45L, 14L, 24L, 23L, 2L, 47L, 9L, 49L, 41L, 38L, 22L, 44L, 15L)], width = 1310) - options(width = 47) - colonnade(df_str[c(1L, 26L, 20L, 12L, 49L, 16L, 24L, 4L, 15L, 47L, 8L, 11L, 14L, 50L, 17L, 2L, 44L, 30L, 36L, 45L, 25L, 38L, 18L, 29L, 5L, 13L, 3L, 23L, 48L, 40L, 34L, 22L, 39L, 33L, 27L, 7L, 19L, 10L, 37L, 6L, 35L, 46L, 31L, 41L, 43L, 28L, 42L, 32L, 21L, 9L)], width = 484) - options(width = 55) - colonnade(df_str[c(6L, 49L, 26L, 45L, 25L, 15L, 31L, 20L, 21L, 44L, 23L, 48L, 37L, 36L, 5L, 43L, 11L, 14L, 13L, 39L, 16L, 12L, 4L, 18L, 42L, 3L, 10L, 28L, 40L, 24L, 29L, 17L, 35L, 47L, 2L, 38L, 34L, 9L, 7L, 8L, 50L, 33L, 32L, 27L, 46L, 19L, 22L, 41L, 30L, 1L)], width = 779) - options(width = 46) - colonnade(df_str[c(38L, 42L, 41L, 10L, 40L, 11L, 27L, 9L, 17L, 37L, 46L, 13L, 36L, 18L, 31L, 20L, 39L, 12L, 44L, 33L, 50L, 34L, 26L, 32L, 23L, 30L, 29L, 21L, 4L, 49L, 19L, 25L, 3L, 6L, 15L, 14L, 43L, 48L, 8L, 22L, 1L, 2L, 45L, 35L, 16L, 5L, 47L, 28L, 24L, 7L)], width = 694) - }) - # nolint end -}) diff --git a/tests/testthat/test-format_multi_fuzz_2.R b/tests/testthat/test-format_multi_fuzz_2.R deleted file mode 100644 index 01e9aa0a0..000000000 --- a/tests/testthat/test-format_multi_fuzz_2.R +++ /dev/null @@ -1,39 +0,0 @@ -test_that("strings with varying widths", { - local_options(width = 80) - - # Generated by data-raw/create-chr-tests.R - # nolint start - expect_snapshot({ - options(width = 54) - colonnade(df_str[c(28L, 34L, 16L, 29L, 47L, 25L, 42L, 27L, 44L, 20L, 14L, 36L, 43L, 41L, 26L, 45L, 22L, 9L, 13L, 32L, 31L, 12L, 19L, 48L, 49L, 35L, 3L, 11L, 23L, 24L, 40L, 15L, 38L, 10L, 46L, 5L, 50L, 18L, 21L, 6L, 30L, 2L, 7L, 1L, 4L, 8L, 17L, 33L, 39L, 37L)], width = 516) - options(width = 42) - colonnade(df_str[c(28L, 41L, 12L, 29L, 13L, 43L, 24L, 50L, 48L, 35L, 44L, 21L, 33L, 45L, 47L, 34L, 25L, 14L, 18L, 23L, 7L, 3L, 42L, 36L, 11L, 2L, 20L, 31L, 1L, 4L, 38L, 9L, 27L, 40L, 32L, 17L, 6L, 49L, 16L, 19L, 15L, 22L, 39L, 10L, 46L, 5L, 30L, 8L, 26L, 37L)], width = 1365) - options(width = 39) - colonnade(df_str[c(40L, 17L, 13L, 23L, 22L, 2L, 18L, 3L, 29L, 45L, 14L, 19L, 33L, 37L, 47L, 43L, 44L, 10L, 31L, 27L, 34L, 35L, 41L, 21L, 4L, 25L, 38L, 48L, 9L, 24L, 26L, 39L, 20L, 36L, 42L, 16L, 6L, 11L, 7L, 12L, 1L, 46L, 15L, 5L, 8L, 50L, 32L, 30L, 49L, 28L)], width = 934) - options(width = 32) - colonnade(df_str[c(11L, 36L, 17L, 14L, 31L, 35L, 23L, 13L, 6L, 44L, 45L, 22L, 21L, 18L, 33L, 10L, 43L, 2L, 46L, 34L, 3L, 19L, 1L, 38L, 9L, 37L, 5L, 8L, 25L, 49L, 27L, 29L, 15L, 39L, 24L, 40L, 48L, 26L, 47L, 42L, 41L, 12L, 28L, 30L, 7L, 16L, 4L, 50L, 20L, 32L)], width = 565) - options(width = 35) - colonnade(df_str[c(18L, 46L, 11L, 43L, 31L, 47L, 48L, 44L, 50L, 15L, 28L, 33L, 13L, 4L, 22L, 3L, 37L, 32L, 40L, 9L, 25L, 16L, 45L, 23L, 21L, 6L, 49L, 36L, 27L, 38L, 14L, 34L, 8L, 24L, 29L, 1L, 12L, 2L, 20L, 17L, 35L, 5L, 19L, 30L, 7L, 26L, 42L, 41L, 39L, 10L)], width = 1121) - options(width = 32) - colonnade(df_str[c(43L, 1L, 3L, 15L, 28L, 12L, 46L, 34L, 31L, 7L, 11L, 4L, 44L, 8L, 9L, 5L, 36L, 22L, 17L, 39L, 18L, 45L, 37L, 13L, 29L, 6L, 30L, 16L, 20L, 10L, 19L, 26L, 33L, 40L, 35L, 48L, 38L, 25L, 2L, 47L, 42L, 41L, 27L, 14L, 21L, 24L, 50L, 49L, 23L, 32L)], width = 446) - options(width = 31) - colonnade(df_str[c(37L, 46L, 21L, 3L, 16L, 39L, 34L, 33L, 10L, 17L, 19L, 36L, 45L, 49L, 11L, 50L, 14L, 29L, 44L, 13L, 30L, 38L, 32L, 40L, 42L, 1L, 31L, 41L, 7L, 23L, 35L, 28L, 6L, 25L, 2L, 9L, 12L, 15L, 5L, 18L, 20L, 27L, 43L, 8L, 47L, 4L, 48L, 24L, 26L, 22L)], width = 1166) - options(width = 58) - colonnade(df_str[c(31L, 39L, 40L, 30L, 10L, 21L, 9L, 16L, 46L, 25L, 15L, 24L, 3L, 50L, 35L, 1L, 12L, 34L, 48L, 4L, 29L, 23L, 37L, 36L, 28L, 43L, 11L, 17L, 32L, 8L, 41L, 13L, 44L, 7L, 38L, 26L, 33L, 20L, 19L, 2L, 18L, 49L, 27L, 47L, 22L, 14L, 6L, 5L, 45L, 42L)], width = 546) - options(width = 57) - colonnade(df_str[c(43L, 21L, 41L, 48L, 22L, 25L, 2L, 8L, 1L, 24L, 6L, 39L, 38L, 20L, 49L, 45L, 47L, 12L, 9L, 13L, 36L, 26L, 44L, 11L, 46L, 28L, 7L, 18L, 50L, 16L, 29L, 30L, 4L, 23L, 17L, 40L, 33L, 14L, 27L, 19L, 34L, 32L, 3L, 37L, 15L, 10L, 5L, 35L, 31L, 42L)], width = 1035) - options(width = 33) - colonnade(df_str[c(40L, 6L, 25L, 5L, 26L, 17L, 19L, 2L, 11L, 34L, 45L, 24L, 22L, 44L, 35L, 7L, 4L, 49L, 1L, 36L, 12L, 41L, 39L, 13L, 48L, 27L, 18L, 30L, 42L, 28L, 3L, 46L, 21L, 20L, 16L, 29L, 50L, 10L, 9L, 8L, 47L, 31L, 14L, 38L, 33L, 32L, 43L, 23L, 15L, 37L)], width = 1217) - options(width = 32) - colonnade(df_str[c(43L, 23L, 22L, 11L, 6L, 26L, 48L, 17L, 7L, 42L, 36L, 21L, 35L, 50L, 13L, 19L, 29L, 8L, 15L, 4L, 2L, 27L, 49L, 47L, 30L, 31L, 25L, 28L, 46L, 12L, 32L, 39L, 24L, 10L, 45L, 5L, 37L, 14L, 40L, 20L, 41L, 44L, 33L, 18L, 38L, 3L, 1L, 34L, 16L, 9L)], width = 770) - options(width = 46) - colonnade(df_str[c(5L, 24L, 43L, 46L, 35L, 39L, 18L, 26L, 8L, 27L, 2L, 50L, 6L, 14L, 29L, 47L, 9L, 16L, 36L, 4L, 13L, 41L, 3L, 28L, 37L, 33L, 38L, 31L, 34L, 19L, 42L, 32L, 1L, 45L, 15L, 7L, 11L, 49L, 23L, 12L, 48L, 20L, 21L, 44L, 25L, 10L, 22L, 30L, 40L, 17L)], width = 1439) - options(width = 52) - colonnade(df_str[c(7L, 44L, 19L, 21L, 18L, 35L, 23L, 50L, 33L, 37L, 25L, 26L, 10L, 39L, 2L, 47L, 42L, 14L, 9L, 41L, 45L, 6L, 4L, 11L, 24L, 43L, 32L, 3L, 38L, 5L, 49L, 27L, 17L, 8L, 22L, 40L, 12L, 15L, 1L, 28L, 31L, 29L, 13L, 48L, 34L, 36L, 30L, 20L, 16L, 46L)], width = 1065) - options(width = 35) - colonnade(df_str[c(38L, 18L, 23L, 36L, 35L, 20L, 44L, 19L, 13L, 41L, 31L, 7L, 11L, 29L, 2L, 14L, 26L, 46L, 40L, 45L, 9L, 34L, 33L, 22L, 1L, 17L, 28L, 10L, 21L, 30L, 47L, 49L, 6L, 12L, 4L, 25L, 32L, 15L, 43L, 24L, 48L, 3L, 37L, 50L, 42L, 39L, 16L, 8L, 27L, 5L)], width = 393) - options(width = 41) - colonnade(df_str[c(22L, 9L, 11L, 26L, 19L, 16L, 32L, 25L, 1L, 30L, 31L, 6L, 24L, 10L, 39L, 21L, 50L, 7L, 29L, 12L, 46L, 43L, 15L, 35L, 20L, 40L, 49L, 38L, 36L, 48L, 34L, 3L, 8L, 4L, 27L, 42L, 44L, 33L, 45L, 18L, 5L, 2L, 13L, 47L, 28L, 17L, 37L, 14L, 41L, 23L)], width = 999) - }) - # nolint end -}) diff --git a/tests/testthat/test-zzx-format_character.R b/tests/testthat/test-zzx-format_character.R index 8bd33d73b..00b408bde 100644 --- a/tests/testthat/test-zzx-format_character.R +++ b/tests/testthat/test-zzx-format_character.R @@ -68,13 +68,3 @@ chartype_frame <- function() { data.frame(chars, desc, stringsAsFactors = FALSE) } - -test_that("output test (not on Windows)", { - skip_on_os("windows") - # Spurious warnings on Windows - suppressWarnings( - expect_snapshot({ - colonnade(chartype_frame(), width = 50) - }) - ) -}) From be65dca0212cbd1d09e0ca45a8fef0503f9dec49 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Sun, 17 Oct 2021 13:56:43 +0200 Subject: [PATCH 132/147] Remove old snaps --- tests/testthat/_snaps/format_multi_fuzz.md | 918 -------------- tests/testthat/_snaps/format_multi_fuzz_2.md | 1161 ------------------ 2 files changed, 2079 deletions(-) delete mode 100644 tests/testthat/_snaps/format_multi_fuzz.md delete mode 100644 tests/testthat/_snaps/format_multi_fuzz_2.md diff --git a/tests/testthat/_snaps/format_multi_fuzz.md b/tests/testthat/_snaps/format_multi_fuzz.md deleted file mode 100644 index a98694e4f..000000000 --- a/tests/testthat/_snaps/format_multi_fuzz.md +++ /dev/null @@ -1,918 +0,0 @@ -# strings with varying widths - - Code - options(width = 59) - colonnade(df_str[c(12L, 33L, 36L, 7L, 41L, 3L, 18L, 23L, 13L, 44L, 14L, 16L, - 25L, 21L, 19L, 45L, 43L, 29L, 1L, 30L, 22L, 27L, 15L, 47L, 28L, 31L, 10L, 50L, - 4L, 40L, 42L, 8L, 6L, 9L, 24L, 48L, 38L, 37L, 34L, 49L, 46L, 2L, 32L, 35L, - 39L, 11L, 17L, 5L, 26L, 20L)], width = 1382) - Output - `12` `33` - - 1 AbcdefghijAb AbcdefghijAbcdefghijAbcdefghijAbc - `36` `7` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdef Abcdefg - `41` `3` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijA Abc - `18` `23` `13` - - 1 AbcdefghijAbcdefgh AbcdefghijAbcdefghijAbc AbcdefghijAbc - `44` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbcd - `14` `16` `25` - - 1 AbcdefghijAbcd AbcdefghijAbcdef AbcdefghijAbcdefghijAbcde - `21` `19` - - 1 AbcdefghijAbcdefghijA AbcdefghijAbcdefghi - `45` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbcde - `43` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbc - `29` `1` - - 1 AbcdefghijAbcdefghijAbcdefghi A - `30` `22` - - 1 AbcdefghijAbcdefghijAbcdefghij AbcdefghijAbcdefghijAb - `27` `15` - - 1 AbcdefghijAbcdefghijAbcdefg AbcdefghijAbcde - `47` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbcdefg - `28` - - 1 AbcdefghijAbcdefghijAbcdefgh - `31` `10` - - 1 AbcdefghijAbcdefghijAbcdefghijA Abcdefghij - `50` `4` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbcdefghij Abcd - `40` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghij - `42` `8` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAb Abcdefgh - `6` `9` `24` - - 1 Abcdef Abcdefghi AbcdefghijAbcdefghijAbcd - `48` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbcdefgh - `38` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefgh - `37` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefg - `34` `49` `46` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcd Abcdefghij~ Abcdefghi~ - `2` `32` `35` `39` `11` `17` `5` `26` `20` - - 1 Ab Abcde~ Abcde~ Abcde~ Abcde~ Abcd~ Abcde Abcd~ Abcd~ - Code - options(width = 54) - colonnade(df_str[c(40L, 28L, 7L, 16L, 48L, 6L, 21L, 1L, 20L, 17L, 47L, 45L, 29L, - 41L, 49L, 34L, 4L, 39L, 18L, 36L, 26L, 38L, 10L, 8L, 5L, 15L, 44L, 24L, 46L, - 14L, 25L, 27L, 3L, 37L, 35L, 12L, 9L, 13L, 22L, 33L, 42L, 11L, 19L, 50L, 23L, - 30L, 32L, 2L, 43L, 31L)], width = 837) - Output - `40` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghij - `28` `7` - - 1 AbcdefghijAbcdefghijAbcdefgh Abcdefg - `16` - - 1 AbcdefghijAbcdef - `48` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbcdefgh - `6` `21` `1` - - 1 Abcdef AbcdefghijAbcdefghijA A - `20` `17` - - 1 AbcdefghijAbcdefghij AbcdefghijAbcdefg - `47` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbcdefg - `45` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbcde - `29` - - 1 AbcdefghijAbcdefghijAbcdefghi - `41` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijA - `49` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbcdefghi - `34` `4` `39` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcd Abcd Abcdefghij~ - `18` `36` `26` `38` `10` `8` `5` `15` - - 1 Abcde~ Abcdef~ Abcde~ Abcde~ Abcd~ Abcd~ Abcde Abcd~ - `44` `24` `46` `14` `25` `27` `3` `37` - - 1 Abcdef~ Abcde~ Abcdef~ Abcd~ Abcd~ Abcd~ Abc Abcd~ - `35` `12` `9` `13` `22` `33` `42` `11` - - 1 Abcdef~ Abcde~ Abcd~ Abcd~ Abcd~ Abcde~ Abcde~ Abcd~ - `19` `50` `23` `30` `32` `2` `43` `31` - - 1 Abcde~ Abcdef~ Abcde~ Abcde~ Abcd~ Ab Abcd~ Abcd~ - Code - options(width = 32) - colonnade(df_str[c(47L, 42L, 4L, 46L, 9L, 34L, 19L, 39L, 8L, 32L, 36L, 12L, 29L, - 5L, 15L, 11L, 31L, 27L, 33L, 28L, 43L, 6L, 13L, 22L, 14L, 16L, 35L, 50L, 38L, - 7L, 23L, 45L, 40L, 3L, 2L, 24L, 41L, 10L, 30L, 25L, 17L, 26L, 48L, 37L, 49L, - 1L, 18L, 21L, 44L, 20L)], width = 455) - Output - `47` - - 1 AbcdefghijAbcdefghijAbcdefghi~ - `42` - - 1 AbcdefghijAbcdefghijAbcdefghi~ - `4` - - 1 Abcd - `46` - - 1 AbcdefghijAbcdefghijAbcdefghi~ - `9` - - 1 Abcdefghi - `34` - - 1 AbcdefghijAbcdefghijAbcdefghi~ - `19` `39` `8` `32` - - 1 Abcdef~ Abcdefg~ Abcd~ Abcdef~ - `36` `12` `29` `5` `15` - - 1 Abcde~ Abcd~ Abcd~ Abcde Abcd~ - `11` `31` `27` `33` `28` - - 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ - `43` `6` `13` `22` `14` - - 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ - `16` `35` `50` `38` `7` - - 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ - `23` `45` `40` `3` `2` - - 1 Abcde~ Abcd~ Abcd~ Abc Ab - `24` `41` `10` `30` `25` - - 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ - `17` `26` `48` `37` `49` - - 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ - `1` `18` `21` `44` `20` - - 1 A Abcde~ Abcd~ Abcd~ Abcd~ - Code - options(width = 55) - colonnade(df_str[c(41L, 4L, 25L, 31L, 8L, 22L, 19L, 10L, 29L, 21L, 34L, 5L, 26L, - 36L, 47L, 46L, 2L, 24L, 27L, 39L, 28L, 43L, 32L, 30L, 48L, 44L, 6L, 20L, 13L, - 15L, 18L, 42L, 9L, 12L, 37L, 45L, 16L, 40L, 11L, 14L, 38L, 1L, 7L, 3L, 23L, - 35L, 50L, 17L, 49L, 33L)], width = 855) - Output - `41` `4` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijA Abcd - `25` - - 1 AbcdefghijAbcdefghijAbcde - `31` `8` - - 1 AbcdefghijAbcdefghijAbcdefghijA Abcdefgh - `22` `19` `10` - - 1 AbcdefghijAbcdefghijAb AbcdefghijAbcdefghi Abcdefghij - `29` `21` - - 1 AbcdefghijAbcdefghijAbcdefghi AbcdefghijAbcdefghijA - `34` `5` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcd Abcde - `26` - - 1 AbcdefghijAbcdefghijAbcdef - `36` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdef - `47` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbcdefg - `46` `2` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbcdef Ab - `24` `27` - - 1 AbcdefghijAbcdefghijAbcd AbcdefghijAbcdefghijAbcdefg - `39` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghi - `28` `43` `32` - - 1 AbcdefghijAbcdefghijAbcdefgh AbcdefghijAb~ Abcdefghi~ - `30` `48` `44` `6` `20` `13` `15` `18` `42` - - 1 Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ - `9` `12` `37` `45` `16` `40` `11` `14` `38` - - 1 Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ - `1` `7` `3` `23` `35` `50` `17` `49` `33` - - 1 A Abcd~ Abc Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ - Code - options(width = 54) - colonnade(df_str[c(27L, 22L, 9L, 23L, 16L, 19L, 25L, 31L, 44L, 1L, 28L, 46L, - 12L, 20L, 43L, 37L, 5L, 2L, 18L, 41L, 26L, 33L, 11L, 49L, 24L, 35L, 4L, 47L, - 30L, 7L, 34L, 3L, 32L, 42L, 10L, 45L, 38L, 39L, 48L, 14L, 6L, 17L, 36L, 50L, - 40L, 13L, 8L, 21L, 15L, 29L)], width = 552) - Output - `27` `22` - - 1 AbcdefghijAbcdefghijAbcdefg AbcdefghijAbcdefghijAb - `9` `23` `16` - - 1 Abcdefghi AbcdefghijAbcdefghijAbc AbcdefghijAbcdef - `19` `25` - - 1 AbcdefghijAbcdefghi AbcdefghijAbcdefghijAbcde - `31` - - 1 AbcdefghijAbcdefghijAbcdefghijA - `44` `1` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbcd A - `28` - - 1 AbcdefghijAbcdefghijAbcdefgh - `46` `12` `20` `43` `37` `5` `2` - - 1 Abcdefgh~ Abcde~ Abcde~ Abcdefg~ Abcdef~ Abcde Ab - `18` `41` `26` `33` `11` `49` `24` `35` - - 1 Abcde~ Abcde~ Abcde~ Abcde~ Abcd~ Abcde~ Abcd~ Abcd~ - `4` `47` `30` `7` `34` `3` `32` `42` - - 1 Abcd Abcdef~ Abcde~ Abcde~ Abcd~ Abc Abcd~ Abcde~ - `10` `45` `38` `39` `48` `14` `6` `17` - - 1 Abcde~ Abcdef~ Abcde~ Abcd~ Abcde~ Abcd~ Abcd~ Abcd~ - `36` `50` `40` `13` `8` `21` `15` `29` - - 1 Abcde~ Abcdef~ Abcdef~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ - Code - options(width = 49) - colonnade(df_str[c(32L, 24L, 18L, 25L, 26L, 13L, 33L, 2L, 50L, 38L, 37L, 16L, - 27L, 9L, 28L, 49L, 34L, 15L, 17L, 35L, 22L, 47L, 3L, 21L, 23L, 41L, 5L, 1L, - 14L, 46L, 30L, 31L, 44L, 4L, 7L, 40L, 43L, 12L, 29L, 8L, 36L, 45L, 11L, 20L, - 10L, 6L, 19L, 48L, 39L, 42L)], width = 1031) - Output - `32` - - 1 AbcdefghijAbcdefghijAbcdefghijAb - `24` `18` - - 1 AbcdefghijAbcdefghijAbcd AbcdefghijAbcdefgh - `25` - - 1 AbcdefghijAbcdefghijAbcde - `26` `13` - - 1 AbcdefghijAbcdefghijAbcdef AbcdefghijAbc - `33` `2` - - 1 AbcdefghijAbcdefghijAbcdefghijAbc Ab - `50` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbcdef~ - `38` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefgh - `37` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefg - `16` `27` - - 1 AbcdefghijAbcdef AbcdefghijAbcdefghijAbcdefg - `9` `28` - - 1 Abcdefghi AbcdefghijAbcdefghijAbcdefgh - `49` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbcdef~ - `34` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcd - `15` `17` - - 1 AbcdefghijAbcde AbcdefghijAbcdefg - `35` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcde - `22` - - 1 AbcdefghijAbcdefghijAb - `47` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbcdefg - `3` `21` - - 1 Abc AbcdefghijAbcdefghijA - `23` - - 1 AbcdefghijAbcdefghijAbc - `41` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijA - `5` `1` `14` `46` `30` `31` `44` `4` - - 1 Abcde A Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd - `7` `40` `43` `12` `29` `8` `36` `45` - - 1 Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ - `11` `20` `10` `6` `19` `48` `39` `42` - - 1 Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ - Code - options(width = 38) - colonnade(df_str[c(44L, 34L, 49L, 9L, 15L, 16L, 1L, 10L, 40L, 29L, 26L, 22L, 4L, - 43L, 20L, 17L, 46L, 33L, 35L, 32L, 2L, 12L, 8L, 37L, 23L, 39L, 7L, 18L, 36L, - 42L, 6L, 30L, 19L, 25L, 5L, 21L, 47L, 50L, 28L, 11L, 31L, 14L, 24L, 27L, 45L, - 41L, 38L, 3L, 13L, 48L)], width = 429) - Output - `44` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcde~ - `34` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcd - `49` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcde~ - `9` `15` - - 1 Abcdefghi AbcdefghijAbcde - `16` `1` `10` - - 1 AbcdefghijAbcdef A Abcdefghij - `40` `29` `26` `22` `4` `43` - - 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd Abcd~ - `20` `17` `46` `33` `35` `32` - - 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ - `2` `12` `8` `37` `23` `39` - - 1 Ab Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ - `7` `18` `36` `42` `6` `30` - - 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ - `19` `25` `5` `21` `47` `50` - - 1 Abcde~ Abcd~ Abcde Abcd~ Abcd~ Abcd~ - `28` `11` `31` `14` `24` `27` - - 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ - `45` `41` `38` `3` `13` `48` - - 1 Abcde~ Abcd~ Abcd~ Abc Abcd~ Abcd~ - Code - options(width = 54) - colonnade(df_str[c(21L, 26L, 8L, 22L, 41L, 24L, 13L, 5L, 47L, 37L, 4L, 42L, 19L, - 34L, 11L, 43L, 38L, 3L, 33L, 20L, 31L, 2L, 18L, 48L, 27L, 44L, 9L, 35L, 30L, - 6L, 49L, 10L, 1L, 16L, 46L, 29L, 12L, 14L, 45L, 36L, 15L, 39L, 50L, 23L, 17L, - 28L, 7L, 32L, 40L, 25L)], width = 633) - Output - `21` `26` - - 1 AbcdefghijAbcdefghijA AbcdefghijAbcdefghijAbcdef - `8` `22` - - 1 Abcdefgh AbcdefghijAbcdefghijAb - `41` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijA - `24` `13` `5` - - 1 AbcdefghijAbcdefghijAbcd AbcdefghijAbc Abcde - `47` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbcdefg - `37` `4` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefg Abcd - `42` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAb - `19` `34` `11` `43` `38` `3` - - 1 AbcdefghijAbcdefghi Abcde~ Abcde~ Abcde~ Abcd~ Abc - `33` `20` `31` `2` `18` `48` `27` `44` - - 1 Abcde~ Abcde~ Abcde~ Ab Abcd~ Abcde~ Abcd~ Abcde~ - `9` `35` `30` `6` `49` `10` `1` `16` - - 1 Abcde~ Abcdef~ Abcde~ Abcd~ Abcde~ Abcd~ A Abcd~ - `46` `29` `12` `14` `45` `36` `15` `39` - - 1 Abcdef~ Abcde~ Abcde~ Abcd~ Abcde~ Abcd~ Abcd~ Abcd~ - `50` `23` `17` `28` `7` `32` `40` `25` - - 1 Abcdef~ Abcde~ Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ - Code - options(width = 39) - colonnade(df_str[c(23L, 49L, 13L, 37L, 3L, 25L, 36L, 4L, 9L, 7L, 27L, 48L, 12L, - 10L, 50L, 14L, 38L, 39L, 46L, 22L, 28L, 8L, 21L, 44L, 32L, 40L, 31L, 1L, 29L, - 34L, 35L, 33L, 19L, 15L, 41L, 20L, 47L, 18L, 16L, 45L, 6L, 5L, 24L, 26L, 43L, - 11L, 42L, 30L, 17L, 2L)], width = 1496) - Output - `23` - - 1 AbcdefghijAbcdefghijAbc - `49` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdef~ - `13` - - 1 AbcdefghijAbc - `37` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefg - `3` `25` - - 1 Abc AbcdefghijAbcdefghijAbcde - `36` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdef - `4` `9` `7` - - 1 Abcd Abcdefghi Abcdefg - `27` - - 1 AbcdefghijAbcdefghijAbcdefg - `48` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdef~ - `12` `10` - - 1 AbcdefghijAb Abcdefghij - `50` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdef~ - `14` - - 1 AbcdefghijAbcd - `38` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdef~ - `39` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdef~ - `46` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdef~ - `22` - - 1 AbcdefghijAbcdefghijAb - `28` `8` - - 1 AbcdefghijAbcdefghijAbcdefgh Abcdefgh - `21` - - 1 AbcdefghijAbcdefghijA - `44` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdef~ - `32` - - 1 AbcdefghijAbcdefghijAbcdefghijAb - `40` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdef~ - `31` `1` - - 1 AbcdefghijAbcdefghijAbcdefghijA A - `29` - - 1 AbcdefghijAbcdefghijAbcdefghi - `34` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcd - `35` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcde - `33` - - 1 AbcdefghijAbcdefghijAbcdefghijAbc - `19` `15` - - 1 AbcdefghijAbcdefghi AbcdefghijAbcde - `41` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdef~ - `20` - - 1 AbcdefghijAbcdefghij - `47` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdef~ - `18` `16` - - 1 AbcdefghijAbcdefgh AbcdefghijAbcdef - `45` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdef~ - `6` `5` `24` - - 1 Abcdef Abcde AbcdefghijAbcdefghijAbcd - `26` - - 1 AbcdefghijAbcdefghijAbcdef - `43` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdef~ - `11` - - 1 AbcdefghijA - `42` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdef~ - `30` - - 1 AbcdefghijAbcdefghijAbcdefghij - `17` `2` - - 1 AbcdefghijAbcdefg Ab - Code - options(width = 31) - colonnade(df_str[c(45L, 14L, 49L, 24L, 22L, 31L, 42L, 18L, 16L, 47L, 25L, 4L, - 37L, 8L, 26L, 21L, 50L, 5L, 41L, 30L, 2L, 33L, 34L, 3L, 44L, 19L, 43L, 6L, - 32L, 29L, 20L, 1L, 13L, 11L, 40L, 12L, 48L, 23L, 9L, 15L, 46L, 36L, 27L, 35L, - 28L, 10L, 7L, 39L, 17L, 38L)], width = 493) - Output - `45` - - 1 AbcdefghijAbcdefghijAbcdefgh~ - `14` - - 1 AbcdefghijAbcd - `49` - - 1 AbcdefghijAbcdefghijAbcdefgh~ - `24` - - 1 AbcdefghijAbcdefghijAbcd - `22` - - 1 AbcdefghijAbcdefghijAb - `31` - - 1 AbcdefghijAbcdefghijAbcdefgh~ - `42` - - 1 AbcdefghijAbcdefghijAbcdefgh~ - `18` `16` `47` - - 1 Abcdefgh~ Abcdef~ Abcdefghij~ - `25` `4` `37` `8` `26` - - 1 Abcd~ Abcd Abcd~ Abcd~ Abcd~ - `21` `50` `5` `41` `30` - - 1 Abcd~ Abcd~ Abcde Abcd~ Abcd~ - `2` `33` `34` `3` `44` - - 1 Ab Abcd~ Abcd~ Abc Abcd~ - `19` `43` `6` `32` `29` - - 1 Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ - `20` `1` `13` `11` `40` - - 1 Abcd~ A Abcd~ Abcd~ Abcd~ - `12` `48` `23` `9` `15` - - 1 Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ - `46` `36` `27` `35` `28` - - 1 Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ - `10` `7` `39` `17` `38` - - 1 Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ - Code - options(width = 52) - colonnade(df_str[c(38L, 46L, 17L, 11L, 24L, 18L, 16L, 39L, 50L, 42L, 6L, 13L, - 37L, 29L, 41L, 47L, 9L, 33L, 44L, 31L, 45L, 36L, 28L, 5L, 10L, 30L, 20L, 1L, - 14L, 43L, 49L, 23L, 26L, 21L, 32L, 19L, 34L, 15L, 48L, 4L, 7L, 35L, 40L, 8L, - 22L, 3L, 25L, 12L, 27L, 2L)], width = 1130) - Output - `38` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefgh - `46` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbcdef - `17` `11` - - 1 AbcdefghijAbcdefg AbcdefghijA - `24` `18` - - 1 AbcdefghijAbcdefghijAbcd AbcdefghijAbcdefgh - `16` - - 1 AbcdefghijAbcdef - `39` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghi - `50` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbcdefghij - `42` `6` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAb Abcdef - `13` - - 1 AbcdefghijAbc - `37` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefg - `29` - - 1 AbcdefghijAbcdefghijAbcdefghi - `41` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijA - `47` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbcdefg - `9` `33` - - 1 Abcdefghi AbcdefghijAbcdefghijAbcdefghijAbc - `44` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbcd - `31` - - 1 AbcdefghijAbcdefghijAbcdefghijA - `45` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbcde - `36` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdef - `28` `5` `10` `30` - - 1 AbcdefghijAbcdefghijAbcdefgh Abcde Abcde~ Abcdefg~ - `20` `1` `14` `43` `49` `23` `26` `21` - - 1 Abcde~ A Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ - `32` `19` `34` `15` `48` `4` `7` `35` - - 1 Abcde~ Abcde~ Abcde~ Abcd~ Abcd~ Abcd Abcd~ Abcd~ - `40` `8` `22` `3` `25` `12` `27` `2` - - 1 Abcdef~ Abcde~ Abcd~ Abc Abcd~ Abcd~ Abcd~ Ab - Code - options(width = 58) - colonnade(df_str[c(17L, 28L, 29L, 27L, 20L, 31L, 43L, 30L, 32L, 48L, 10L, 50L, - 13L, 12L, 36L, 21L, 46L, 33L, 25L, 35L, 1L, 5L, 16L, 34L, 18L, 42L, 3L, 11L, - 40L, 26L, 37L, 7L, 39L, 6L, 4L, 19L, 8L, 45L, 14L, 24L, 23L, 2L, 47L, 9L, 49L, - 41L, 38L, 22L, 44L, 15L)], width = 1310) - Output - `17` `28` - - 1 AbcdefghijAbcdefg AbcdefghijAbcdefghijAbcdefgh - `29` - - 1 AbcdefghijAbcdefghijAbcdefghi - `27` `20` - - 1 AbcdefghijAbcdefghijAbcdefg AbcdefghijAbcdefghij - `31` - - 1 AbcdefghijAbcdefghijAbcdefghijA - `43` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbc - `30` - - 1 AbcdefghijAbcdefghijAbcdefghij - `32` - - 1 AbcdefghijAbcdefghijAbcdefghijAb - `48` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbcdefgh - `10` - - 1 Abcdefghij - `50` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbcdefghij - `13` `12` - - 1 AbcdefghijAbc AbcdefghijAb - `36` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdef - `21` - - 1 AbcdefghijAbcdefghijA - `46` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbcdef - `33` - - 1 AbcdefghijAbcdefghijAbcdefghijAbc - `25` - - 1 AbcdefghijAbcdefghijAbcde - `35` `1` `5` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcde A Abcde - `16` `34` - - 1 AbcdefghijAbcdef AbcdefghijAbcdefghijAbcdefghijAbcd - `18` - - 1 AbcdefghijAbcdefgh - `42` `3` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAb Abc - `11` `40` `26` `37` `7` - - 1 AbcdefghijA AbcdefghijAbc~ Abcdefghi~ AbcdefghijA~ Abcd~ - `39` `6` `4` `19` `8` `45` `14` `24` `23` - - 1 Abcde~ Abcdef Abcd Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ - `2` `47` `9` `49` `41` `38` `22` `44` `15` - - 1 Ab Abcde~ Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ - Code - options(width = 47) - colonnade(df_str[c(1L, 26L, 20L, 12L, 49L, 16L, 24L, 4L, 15L, 47L, 8L, 11L, 14L, - 50L, 17L, 2L, 44L, 30L, 36L, 45L, 25L, 38L, 18L, 29L, 5L, 13L, 3L, 23L, 48L, - 40L, 34L, 22L, 39L, 33L, 27L, 7L, 19L, 10L, 37L, 6L, 35L, 46L, 31L, 41L, 43L, - 28L, 42L, 32L, 21L, 9L)], width = 484) - Output - `1` `26` - - 1 A AbcdefghijAbcdefghijAbcdef - `20` `12` - - 1 AbcdefghijAbcdefghij AbcdefghijAb - `49` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbcd~ - `16` `24` - - 1 AbcdefghijAbcdef AbcdefghijAbcdefghijAbcd - `4` - - 1 Abcd - `15` `47` `8` `11` `14` `50` `17` - - 1 Abcde~ Abcdef~ Abcd~ Abcd~ Abcd~ Abcde~ Abcd~ - `2` `44` `30` `36` `45` `25` `38` - - 1 Ab Abcde~ Abcde~ Abcde~ Abcde~ Abcd~ Abcd~ - `18` `29` `5` `13` `3` `23` `48` - - 1 Abcde~ Abcde~ Abcde Abcde~ Abc Abcd~ Abcde~ - `40` `34` `22` `39` `33` `27` `7` - - 1 Abcde~ Abcde~ Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ - `19` `10` `37` `6` `35` `46` `31` - - 1 Abcde~ Abcde~ Abcde~ Abcd~ Abcd~ Abcde~ Abcd~ - `41` `43` `28` `42` `32` `21` `9` - - 1 Abcde~ Abcde~ Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ - Code - options(width = 55) - colonnade(df_str[c(6L, 49L, 26L, 45L, 25L, 15L, 31L, 20L, 21L, 44L, 23L, 48L, - 37L, 36L, 5L, 43L, 11L, 14L, 13L, 39L, 16L, 12L, 4L, 18L, 42L, 3L, 10L, 28L, - 40L, 24L, 29L, 17L, 35L, 47L, 2L, 38L, 34L, 9L, 7L, 8L, 50L, 33L, 32L, 27L, - 46L, 19L, 22L, 41L, 30L, 1L)], width = 779) - Output - `6` - - 1 Abcdef - `49` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbcdefghi - `26` - - 1 AbcdefghijAbcdefghijAbcdef - `45` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbcde - `25` `15` - - 1 AbcdefghijAbcdefghijAbcde AbcdefghijAbcde - `31` `20` - - 1 AbcdefghijAbcdefghijAbcdefghijA AbcdefghijAbcdefghij - `21` - - 1 AbcdefghijAbcdefghijA - `44` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbcd - `23` - - 1 AbcdefghijAbcdefghijAbc - `48` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbcdefgh - `37` `36` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefg AbcdefghijAbcd~ - `5` `43` `11` `14` `13` `39` `16` `12` `4` - - 1 Abcde Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd - `18` `42` `3` `10` `28` `40` `24` `29` `17` - - 1 Abcd~ Abcd~ Abc Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ - `35` `47` `2` `38` `34` `9` `7` `8` `50` - - 1 Abcd~ Abcd~ Ab Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ - `33` `32` `27` `46` `19` `22` `41` `30` `1` - - 1 Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ A - Code - options(width = 46) - colonnade(df_str[c(38L, 42L, 41L, 10L, 40L, 11L, 27L, 9L, 17L, 37L, 46L, 13L, - 36L, 18L, 31L, 20L, 39L, 12L, 44L, 33L, 50L, 34L, 26L, 32L, 23L, 30L, 29L, - 21L, 4L, 49L, 19L, 25L, 3L, 6L, 15L, 14L, 43L, 48L, 8L, 22L, 1L, 2L, 45L, 35L, - 16L, 5L, 47L, 28L, 24L, 7L)], width = 694) - Output - `38` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefgh - `42` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAb - `41` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijA - `10` - - 1 Abcdefghij - `40` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghij - `11` `27` - - 1 AbcdefghijA AbcdefghijAbcdefghijAbcdefg - `9` `17` - - 1 Abcdefghi AbcdefghijAbcdefg - `37` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefg - `46` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbc~ - `13` - - 1 AbcdefghijAbc - `36` `18` `31` - - 1 AbcdefghijAbcdef~ Abcdefghi~ AbcdefghijAbcd~ - `20` `39` `12` `44` `33` `50` `34` - - 1 Abcde~ Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ - `26` `32` `23` `30` `29` `21` `4` - - 1 Abcde~ Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ Abcd - `49` `19` `25` `3` `6` `15` `14` - - 1 Abcdef~ Abcde~ Abcd~ Abc Abcd~ Abcd~ Abcd~ - `43` `48` `8` `22` `1` `2` `45` - - 1 Abcde~ Abcde~ Abcde~ Abcd~ A Ab Abcd~ - `35` `16` `5` `47` `28` `24` `7` - - 1 Abcde~ Abcde~ Abcde Abcde~ Abcd~ Abcd~ Abcd~ - diff --git a/tests/testthat/_snaps/format_multi_fuzz_2.md b/tests/testthat/_snaps/format_multi_fuzz_2.md deleted file mode 100644 index 13aa139d9..000000000 --- a/tests/testthat/_snaps/format_multi_fuzz_2.md +++ /dev/null @@ -1,1161 +0,0 @@ -# strings with varying widths - - Code - options(width = 54) - colonnade(df_str[c(28L, 34L, 16L, 29L, 47L, 25L, 42L, 27L, 44L, 20L, 14L, 36L, - 43L, 41L, 26L, 45L, 22L, 9L, 13L, 32L, 31L, 12L, 19L, 48L, 49L, 35L, 3L, 11L, - 23L, 24L, 40L, 15L, 38L, 10L, 46L, 5L, 50L, 18L, 21L, 6L, 30L, 2L, 7L, 1L, 4L, - 8L, 17L, 33L, 39L, 37L)], width = 516) - Output - `28` - - 1 AbcdefghijAbcdefghijAbcdefgh - `34` `16` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcd AbcdefghijAbcdef - `29` - - 1 AbcdefghijAbcdefghijAbcdefghi - `47` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbcdefg - `25` `42` `27` `44` `20` - - 1 AbcdefghijAbcdefghijAbcde Abcde~ Abcde~ Abcde~ Abcd~ - `14` `36` `43` `41` `26` `45` `22` `9` - - 1 Abcde~ Abcde~ Abcde~ Abcde~ Abcd~ Abcde~ Abcd~ Abcd~ - `13` `32` `31` `12` `19` `48` `49` `35` - - 1 Abcde~ Abcde~ Abcde~ Abcd~ Abcd~ Abcde~ Abcde~ Abcd~ - `3` `11` `23` `24` `40` `15` `38` `10` - - 1 Abc Abcde~ Abcde~ Abcde~ Abcde~ Abcd~ Abcde~ Abcd~ - `46` `5` `50` `18` `21` `6` `30` `2` - - 1 Abcdef~ Abcde Abcdef~ Abcde~ Abcd~ Abcd~ Abcd~ Ab - `7` `1` `4` `8` `17` `33` `39` `37` - - 1 Abcde~ A Abcd Abcde~ Abcd~ Abcde~ Abcde~ Abcde~ - Code - options(width = 42) - colonnade(df_str[c(28L, 41L, 12L, 29L, 13L, 43L, 24L, 50L, 48L, 35L, 44L, 21L, - 33L, 45L, 47L, 34L, 25L, 14L, 18L, 23L, 7L, 3L, 42L, 36L, 11L, 2L, 20L, 31L, - 1L, 4L, 38L, 9L, 27L, 40L, 32L, 17L, 6L, 49L, 16L, 19L, 15L, 22L, 39L, 10L, - 46L, 5L, 30L, 8L, 26L, 37L)], width = 1365) - Output - `28` - - 1 AbcdefghijAbcdefghijAbcdefgh - `41` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghi~ - `12` - - 1 AbcdefghijAb - `29` - - 1 AbcdefghijAbcdefghijAbcdefghi - `13` - - 1 AbcdefghijAbc - `43` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghi~ - `24` - - 1 AbcdefghijAbcdefghijAbcd - `50` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghi~ - `48` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghi~ - `35` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcde - `44` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghi~ - `21` - - 1 AbcdefghijAbcdefghijA - `33` - - 1 AbcdefghijAbcdefghijAbcdefghijAbc - `45` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghi~ - `47` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghi~ - `34` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcd - `25` `14` - - 1 AbcdefghijAbcdefghijAbcde AbcdefghijAbcd - `18` - - 1 AbcdefghijAbcdefgh - `23` `7` `3` - - 1 AbcdefghijAbcdefghijAbc Abcdefg Abc - `42` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghi~ - `36` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdef - `11` `2` `20` - - 1 AbcdefghijA Ab AbcdefghijAbcdefghij - `31` `1` - - 1 AbcdefghijAbcdefghijAbcdefghijA A - `4` - - 1 Abcd - `38` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefgh - `9` `27` - - 1 Abcdefghi AbcdefghijAbcdefghijAbcdefg - `40` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghij - `32` - - 1 AbcdefghijAbcdefghijAbcdefghijAb - `17` `6` - - 1 AbcdefghijAbcdefg Abcdef - `49` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghi~ - `16` `19` - - 1 AbcdefghijAbcdef AbcdefghijAbcdefghi - `15` `22` `39` `10` - - 1 AbcdefghijAbcde Abcdefg~ Abcdefgh~ Abcd~ - `46` `5` `30` `8` `26` `37` - - 1 Abcdef~ Abcde Abcdef~ Abcd~ Abcd~ Abcde~ - Code - options(width = 39) - colonnade(df_str[c(40L, 17L, 13L, 23L, 22L, 2L, 18L, 3L, 29L, 45L, 14L, 19L, - 33L, 37L, 47L, 43L, 44L, 10L, 31L, 27L, 34L, 35L, 41L, 21L, 4L, 25L, 38L, 48L, - 9L, 24L, 26L, 39L, 20L, 36L, 42L, 16L, 6L, 11L, 7L, 12L, 1L, 46L, 15L, 5L, 8L, - 50L, 32L, 30L, 49L, 28L)], width = 934) - Output - `40` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdef~ - `17` `13` - - 1 AbcdefghijAbcdefg AbcdefghijAbc - `23` - - 1 AbcdefghijAbcdefghijAbc - `22` `2` - - 1 AbcdefghijAbcdefghijAb Ab - `18` `3` - - 1 AbcdefghijAbcdefgh Abc - `29` - - 1 AbcdefghijAbcdefghijAbcdefghi - `45` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdef~ - `14` `19` - - 1 AbcdefghijAbcd AbcdefghijAbcdefghi - `33` - - 1 AbcdefghijAbcdefghijAbcdefghijAbc - `37` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefg - `47` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdef~ - `43` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdef~ - `44` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdef~ - `10` - - 1 Abcdefghij - `31` - - 1 AbcdefghijAbcdefghijAbcdefghijA - `27` - - 1 AbcdefghijAbcdefghijAbcdefg - `34` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcd - `35` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcde - `41` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdef~ - `21` `4` `25` - - 1 AbcdefghijAbcdefghijA Abcd Abcdefgh~ - `38` `48` `9` `24` `26` `39` - - 1 Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ - `20` `36` `42` `16` `6` `11` - - 1 Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ - `7` `12` `1` `46` `15` `5` - - 1 Abcde~ Abcd~ A Abcde~ Abcd~ Abcde - `8` `50` `32` `30` `49` `28` - - 1 Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ - Code - options(width = 32) - colonnade(df_str[c(11L, 36L, 17L, 14L, 31L, 35L, 23L, 13L, 6L, 44L, 45L, 22L, - 21L, 18L, 33L, 10L, 43L, 2L, 46L, 34L, 3L, 19L, 1L, 38L, 9L, 37L, 5L, 8L, 25L, - 49L, 27L, 29L, 15L, 39L, 24L, 40L, 48L, 26L, 47L, 42L, 41L, 12L, 28L, 30L, 7L, - 16L, 4L, 50L, 20L, 32L)], width = 565) - Output - `11` - - 1 AbcdefghijA - `36` - - 1 AbcdefghijAbcdefghijAbcdefghi~ - `17` - - 1 AbcdefghijAbcdefg - `14` - - 1 AbcdefghijAbcd - `31` - - 1 AbcdefghijAbcdefghijAbcdefghi~ - `35` - - 1 AbcdefghijAbcdefghijAbcdefghi~ - `23` - - 1 AbcdefghijAbcdefghijAbc - `13` `6` - - 1 AbcdefghijAbc Abcdef - `44` - - 1 AbcdefghijAbcdefghijAbcdefghi~ - `45` - - 1 AbcdefghijAbcdefghijAbcdefghi~ - `22` `21` `18` `33` - - 1 Abcdef~ Abcdef~ Abcde~ Abcdef~ - `10` `43` `2` `46` `34` - - 1 Abcde~ Abcd~ Ab Abcd~ Abcd~ - `3` `19` `1` `38` `9` - - 1 Abc Abcde~ A Abcd~ Abcd~ - `37` `5` `8` `25` `49` - - 1 Abcde~ Abcde Abcd~ Abcd~ Abcd~ - `27` `29` `15` `39` `24` - - 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ - `40` `48` `26` `47` `42` - - 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ - `41` `12` `28` `30` `7` - - 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ - `16` `4` `50` `20` `32` - - 1 Abcde~ Abcd Abcd~ Abcd~ Abcd~ - Code - options(width = 35) - colonnade(df_str[c(18L, 46L, 11L, 43L, 31L, 47L, 48L, 44L, 50L, 15L, 28L, 33L, - 13L, 4L, 22L, 3L, 37L, 32L, 40L, 9L, 25L, 16L, 45L, 23L, 21L, 6L, 49L, 36L, - 27L, 38L, 14L, 34L, 8L, 24L, 29L, 1L, 12L, 2L, 20L, 17L, 35L, 5L, 19L, 30L, - 7L, 26L, 42L, 41L, 39L, 10L)], width = 1121) - Output - `18` - - 1 AbcdefghijAbcdefgh - `46` - - 1 AbcdefghijAbcdefghijAbcdefghijAb~ - `11` - - 1 AbcdefghijA - `43` - - 1 AbcdefghijAbcdefghijAbcdefghijAb~ - `31` - - 1 AbcdefghijAbcdefghijAbcdefghijA - `47` - - 1 AbcdefghijAbcdefghijAbcdefghijAb~ - `48` - - 1 AbcdefghijAbcdefghijAbcdefghijAb~ - `44` - - 1 AbcdefghijAbcdefghijAbcdefghijAb~ - `50` - - 1 AbcdefghijAbcdefghijAbcdefghijAb~ - `15` - - 1 AbcdefghijAbcde - `28` - - 1 AbcdefghijAbcdefghijAbcdefgh - `33` - - 1 AbcdefghijAbcdefghijAbcdefghijAbc - `13` `4` - - 1 AbcdefghijAbc Abcd - `22` `3` - - 1 AbcdefghijAbcdefghijAb Abc - `37` - - 1 AbcdefghijAbcdefghijAbcdefghijAb~ - `32` - - 1 AbcdefghijAbcdefghijAbcdefghijAb - `40` - - 1 AbcdefghijAbcdefghijAbcdefghijAb~ - `9` - - 1 Abcdefghi - `25` - - 1 AbcdefghijAbcdefghijAbcde - `16` - - 1 AbcdefghijAbcdef - `45` - - 1 AbcdefghijAbcdefghijAbcdefghijAb~ - `23` - - 1 AbcdefghijAbcdefghijAbc - `21` `6` - - 1 AbcdefghijAbcdefghijA Abcdef - `49` - - 1 AbcdefghijAbcdefghijAbcdefghijAb~ - `36` - - 1 AbcdefghijAbcdefghijAbcdefghijAb~ - `27` - - 1 AbcdefghijAbcdefghijAbcdefg - `38` - - 1 AbcdefghijAbcdefghijAbcdefghijAb~ - `14` - - 1 AbcdefghijAbcd - `34` - - 1 AbcdefghijAbcdefghijAbcdefghijAb~ - `8` `24` `29` - - 1 Abcdefgh Abcdefghij~ AbcdefghijA~ - `1` `12` `2` `20` `17` - - 1 A Abcde~ Ab Abcdef~ Abcde~ - `35` `5` `19` `30` `7` - - 1 Abcdef~ Abcde Abcde~ Abcde~ Abcd~ - `26` `42` `41` `39` `10` - - 1 Abcde~ Abcde~ Abcde~ Abcde~ Abcd~ - Code - options(width = 32) - colonnade(df_str[c(43L, 1L, 3L, 15L, 28L, 12L, 46L, 34L, 31L, 7L, 11L, 4L, 44L, - 8L, 9L, 5L, 36L, 22L, 17L, 39L, 18L, 45L, 37L, 13L, 29L, 6L, 30L, 16L, 20L, - 10L, 19L, 26L, 33L, 40L, 35L, 48L, 38L, 25L, 2L, 47L, 42L, 41L, 27L, 14L, 21L, - 24L, 50L, 49L, 23L, 32L)], width = 446) - Output - `43` - - 1 AbcdefghijAbcdefghijAbcdefghi~ - `1` `3` `15` - - 1 A Abc AbcdefghijAbcde - `28` - - 1 AbcdefghijAbcdefghijAbcdefgh - `12` - - 1 AbcdefghijAb - `46` - - 1 AbcdefghijAbcdefghijAbcdefghi~ - `34` `31` `7` - - 1 AbcdefghijA~ Abcdefghij~ Abcd~ - `11` `4` `44` `8` `9` - - 1 Abcde~ Abcd Abcd~ Abcd~ Abcd~ - `5` `36` `22` `17` `39` - - 1 Abcde Abcde~ Abcd~ Abcd~ Abcd~ - `18` `45` `37` `13` `29` - - 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ - `6` `30` `16` `20` `10` - - 1 Abcdef Abcd~ Abcd~ Abcd~ Abcd~ - `19` `26` `33` `40` `35` - - 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ - `48` `38` `25` `2` `47` - - 1 Abcde~ Abcd~ Abcd~ Ab Abcd~ - `42` `41` `27` `14` `21` - - 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ - `24` `50` `49` `23` `32` - - 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ - Code - options(width = 31) - colonnade(df_str[c(37L, 46L, 21L, 3L, 16L, 39L, 34L, 33L, 10L, 17L, 19L, 36L, - 45L, 49L, 11L, 50L, 14L, 29L, 44L, 13L, 30L, 38L, 32L, 40L, 42L, 1L, 31L, 41L, - 7L, 23L, 35L, 28L, 6L, 25L, 2L, 9L, 12L, 15L, 5L, 18L, 20L, 27L, 43L, 8L, 47L, - 4L, 48L, 24L, 26L, 22L)], width = 1166) - Output - `37` - - 1 AbcdefghijAbcdefghijAbcdefgh~ - `46` - - 1 AbcdefghijAbcdefghijAbcdefgh~ - `21` `3` - - 1 AbcdefghijAbcdefghijA Abc - `16` - - 1 AbcdefghijAbcdef - `39` - - 1 AbcdefghijAbcdefghijAbcdefgh~ - `34` - - 1 AbcdefghijAbcdefghijAbcdefgh~ - `33` - - 1 AbcdefghijAbcdefghijAbcdefgh~ - `10` `17` - - 1 Abcdefghij AbcdefghijAbcdefg - `19` - - 1 AbcdefghijAbcdefghi - `36` - - 1 AbcdefghijAbcdefghijAbcdefgh~ - `45` - - 1 AbcdefghijAbcdefghijAbcdefgh~ - `49` - - 1 AbcdefghijAbcdefghijAbcdefgh~ - `11` - - 1 AbcdefghijA - `50` - - 1 AbcdefghijAbcdefghijAbcdefgh~ - `14` - - 1 AbcdefghijAbcd - `29` - - 1 AbcdefghijAbcdefghijAbcdefghi - `44` - - 1 AbcdefghijAbcdefghijAbcdefgh~ - `13` - - 1 AbcdefghijAbc - `30` - - 1 AbcdefghijAbcdefghijAbcdefgh~ - `38` - - 1 AbcdefghijAbcdefghijAbcdefgh~ - `32` - - 1 AbcdefghijAbcdefghijAbcdefgh~ - `40` - - 1 AbcdefghijAbcdefghijAbcdefgh~ - `42` - - 1 AbcdefghijAbcdefghijAbcdefgh~ - `1` - - 1 A - `31` - - 1 AbcdefghijAbcdefghijAbcdefgh~ - `41` - - 1 AbcdefghijAbcdefghijAbcdefgh~ - `7` - - 1 Abcdefg - `23` - - 1 AbcdefghijAbcdefghijAbc - `35` - - 1 AbcdefghijAbcdefghijAbcdefgh~ - `28` - - 1 AbcdefghijAbcdefghijAbcdefgh - `6` - - 1 Abcdef - `25` - - 1 AbcdefghijAbcdefghijAbcde - `2` `9` `12` - - 1 Ab Abcdefghi AbcdefghijAb - `15` `5` - - 1 AbcdefghijAbcde Abcde - `18` - - 1 AbcdefghijAbcdefgh - `20` - - 1 AbcdefghijAbcdefghij - `27` `43` `8` `47` - - 1 Abcdef~ Abcdef~ Abcde~ Abcde~ - `4` `48` `24` `26` `22` - - 1 Abcd Abcd~ Abcd~ Abcd~ Abcd~ - Code - options(width = 58) - colonnade(df_str[c(31L, 39L, 40L, 30L, 10L, 21L, 9L, 16L, 46L, 25L, 15L, 24L, - 3L, 50L, 35L, 1L, 12L, 34L, 48L, 4L, 29L, 23L, 37L, 36L, 28L, 43L, 11L, 17L, - 32L, 8L, 41L, 13L, 44L, 7L, 38L, 26L, 33L, 20L, 19L, 2L, 18L, 49L, 27L, 47L, - 22L, 14L, 6L, 5L, 45L, 42L)], width = 546) - Output - `31` - - 1 AbcdefghijAbcdefghijAbcdefghijA - `39` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghi - `40` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghij - `30` `10` - - 1 AbcdefghijAbcdefghijAbcdefghij Abcdefghij - `21` `9` `16` - - 1 AbcdefghijAbcdefghijA Abcdefghi AbcdefghijAbcdef - `46` `25` `15` `24` `3` `50` - - 1 AbcdefghijA~ Abcdefgh~ Abcde~ Abcdef~ Abc AbcdefghijA~ - `35` `1` `12` `34` `48` `4` `29` `23` `37` - - 1 Abcde~ A Abcde~ Abcde~ Abcd~ Abcd Abcd~ Abcd~ Abcd~ - `36` `28` `43` `11` `17` `32` `8` `41` `13` - - 1 Abcde~ Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ - `44` `7` `38` `26` `33` `20` `19` `2` `18` - - 1 Abcde~ Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ Ab Abcd~ - `49` `27` `47` `22` `14` `6` `5` `45` `42` - - 1 Abcde~ Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ Abcde Abcd~ Abcd~ - Code - options(width = 57) - colonnade(df_str[c(43L, 21L, 41L, 48L, 22L, 25L, 2L, 8L, 1L, 24L, 6L, 39L, 38L, - 20L, 49L, 45L, 47L, 12L, 9L, 13L, 36L, 26L, 44L, 11L, 46L, 28L, 7L, 18L, 50L, - 16L, 29L, 30L, 4L, 23L, 17L, 40L, 33L, 14L, 27L, 19L, 34L, 32L, 3L, 37L, 15L, - 10L, 5L, 35L, 31L, 42L)], width = 1035) - Output - `43` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbc - `21` - - 1 AbcdefghijAbcdefghijA - `41` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijA - `48` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbcdefgh - `22` `25` `2` - - 1 AbcdefghijAbcdefghijAb AbcdefghijAbcdefghijAbcde Ab - `8` `1` `24` `6` - - 1 Abcdefgh A AbcdefghijAbcdefghijAbcd Abcdef - `39` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghi - `38` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefgh - `20` - - 1 AbcdefghijAbcdefghij - `49` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbcdefghi - `45` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbcde - `47` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbcdefg - `12` `9` `13` - - 1 AbcdefghijAb Abcdefghi AbcdefghijAbc - `36` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdef - `26` - - 1 AbcdefghijAbcdefghijAbcdef - `44` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbcd - `11` `46` `28` `7` `18` `50` `16` `29` `30` - - 1 Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ - `4` `23` `17` `40` `33` `14` `27` `19` `34` - - 1 Abcd Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ - `32` `3` `37` `15` `10` `5` `35` `31` `42` - - 1 Abcde~ Abc Abcde~ Abcd~ Abcd~ Abcde Abcd~ Abcd~ Abcd~ - Code - options(width = 33) - colonnade(df_str[c(40L, 6L, 25L, 5L, 26L, 17L, 19L, 2L, 11L, 34L, 45L, 24L, 22L, - 44L, 35L, 7L, 4L, 49L, 1L, 36L, 12L, 41L, 39L, 13L, 48L, 27L, 18L, 30L, 42L, - 28L, 3L, 46L, 21L, 20L, 16L, 29L, 50L, 10L, 9L, 8L, 47L, 31L, 14L, 38L, 33L, - 32L, 43L, 23L, 15L, 37L)], width = 1217) - Output - `40` - - 1 AbcdefghijAbcdefghijAbcdefghij~ - `6` - - 1 Abcdef - `25` `5` - - 1 AbcdefghijAbcdefghijAbcde Abcde - `26` - - 1 AbcdefghijAbcdefghijAbcdef - `17` - - 1 AbcdefghijAbcdefg - `19` `2` - - 1 AbcdefghijAbcdefghi Ab - `11` - - 1 AbcdefghijA - `34` - - 1 AbcdefghijAbcdefghijAbcdefghij~ - `45` - - 1 AbcdefghijAbcdefghijAbcdefghij~ - `24` - - 1 AbcdefghijAbcdefghijAbcd - `22` - - 1 AbcdefghijAbcdefghijAb - `44` - - 1 AbcdefghijAbcdefghijAbcdefghij~ - `35` - - 1 AbcdefghijAbcdefghijAbcdefghij~ - `7` `4` - - 1 Abcdefg Abcd - `49` - - 1 AbcdefghijAbcdefghijAbcdefghij~ - `1` - - 1 A - `36` - - 1 AbcdefghijAbcdefghijAbcdefghij~ - `12` - - 1 AbcdefghijAb - `41` - - 1 AbcdefghijAbcdefghijAbcdefghij~ - `39` - - 1 AbcdefghijAbcdefghijAbcdefghij~ - `13` - - 1 AbcdefghijAbc - `48` - - 1 AbcdefghijAbcdefghijAbcdefghij~ - `27` - - 1 AbcdefghijAbcdefghijAbcdefg - `18` - - 1 AbcdefghijAbcdefgh - `30` - - 1 AbcdefghijAbcdefghijAbcdefghij - `42` - - 1 AbcdefghijAbcdefghijAbcdefghij~ - `28` - - 1 AbcdefghijAbcdefghijAbcdefgh - `3` - - 1 Abc - `46` - - 1 AbcdefghijAbcdefghijAbcdefghij~ - `21` - - 1 AbcdefghijAbcdefghijA - `20` - - 1 AbcdefghijAbcdefghij - `16` - - 1 AbcdefghijAbcdef - `29` - - 1 AbcdefghijAbcdefghijAbcdefghi - `50` - - 1 AbcdefghijAbcdefghijAbcdefghij~ - `10` `9` `8` - - 1 Abcdefghij Abcdefghi Abcdefgh - `47` `31` `14` `38` `33` - - 1 Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ - `32` `43` `23` `15` `37` - - 1 Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ - Code - options(width = 32) - colonnade(df_str[c(43L, 23L, 22L, 11L, 6L, 26L, 48L, 17L, 7L, 42L, 36L, 21L, - 35L, 50L, 13L, 19L, 29L, 8L, 15L, 4L, 2L, 27L, 49L, 47L, 30L, 31L, 25L, 28L, - 46L, 12L, 32L, 39L, 24L, 10L, 45L, 5L, 37L, 14L, 40L, 20L, 41L, 44L, 33L, 18L, - 38L, 3L, 1L, 34L, 16L, 9L)], width = 770) - Output - `43` - - 1 AbcdefghijAbcdefghijAbcdefghi~ - `23` - - 1 AbcdefghijAbcdefghijAbc - `22` - - 1 AbcdefghijAbcdefghijAb - `11` `6` - - 1 AbcdefghijA Abcdef - `26` - - 1 AbcdefghijAbcdefghijAbcdef - `48` - - 1 AbcdefghijAbcdefghijAbcdefghi~ - `17` `7` - - 1 AbcdefghijAbcdefg Abcdefg - `42` - - 1 AbcdefghijAbcdefghijAbcdefghi~ - `36` - - 1 AbcdefghijAbcdefghijAbcdefghi~ - `21` - - 1 AbcdefghijAbcdefghijA - `35` - - 1 AbcdefghijAbcdefghijAbcdefghi~ - `50` - - 1 AbcdefghijAbcdefghijAbcdefghi~ - `13` - - 1 AbcdefghijAbc - `19` - - 1 AbcdefghijAbcdefghi - `29` - - 1 AbcdefghijAbcdefghijAbcdefghi - `8` `15` `4` - - 1 Abcdefgh AbcdefghijAbcde Abcd - `2` - - 1 Ab - `27` - - 1 AbcdefghijAbcdefghijAbcdefg - `49` - - 1 AbcdefghijAbcdefghijAbcdefghi~ - `47` `30` - - 1 AbcdefghijAbcd~ AbcdefghijAbc~ - `31` `25` `28` `46` `12` - - 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ - `32` `39` `24` `10` `45` - - 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ - `5` `37` `14` `40` `20` - - 1 Abcde Abcde~ Abcd~ Abcd~ Abcd~ - `41` `44` `33` `18` `38` - - 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ - `3` `1` `34` `16` `9` - - 1 Abc A Abcde~ Abcd~ Abcd~ - Code - options(width = 46) - colonnade(df_str[c(5L, 24L, 43L, 46L, 35L, 39L, 18L, 26L, 8L, 27L, 2L, 50L, 6L, - 14L, 29L, 47L, 9L, 16L, 36L, 4L, 13L, 41L, 3L, 28L, 37L, 33L, 38L, 31L, 34L, - 19L, 42L, 32L, 1L, 45L, 15L, 7L, 11L, 49L, 23L, 12L, 48L, 20L, 21L, 44L, 25L, - 10L, 22L, 30L, 40L, 17L)], width = 1439) - Output - `5` `24` - - 1 Abcde AbcdefghijAbcdefghijAbcd - `43` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbc - `46` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbc~ - `35` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcde - `39` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghi - `18` - - 1 AbcdefghijAbcdefgh - `26` `8` - - 1 AbcdefghijAbcdefghijAbcdef Abcdefgh - `27` `2` - - 1 AbcdefghijAbcdefghijAbcdefg Ab - `50` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbc~ - `6` `14` - - 1 Abcdef AbcdefghijAbcd - `29` - - 1 AbcdefghijAbcdefghijAbcdefghi - `47` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbc~ - `9` `16` - - 1 Abcdefghi AbcdefghijAbcdef - `36` `4` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdef Abcd - `13` - - 1 AbcdefghijAbc - `41` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijA - `3` `28` - - 1 Abc AbcdefghijAbcdefghijAbcdefgh - `37` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefg - `33` - - 1 AbcdefghijAbcdefghijAbcdefghijAbc - `38` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefgh - `31` - - 1 AbcdefghijAbcdefghijAbcdefghijA - `34` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcd - `19` - - 1 AbcdefghijAbcdefghi - `42` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAb - `32` `1` - - 1 AbcdefghijAbcdefghijAbcdefghijAb A - `45` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbc~ - `15` `7` `11` - - 1 AbcdefghijAbcde Abcdefg AbcdefghijA - `49` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbc~ - `23` `12` - - 1 AbcdefghijAbcdefghijAbc AbcdefghijAb - `48` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbc~ - `20` `21` - - 1 AbcdefghijAbcdefghij AbcdefghijAbcdefghijA - `44` `25` `10` `22` `30` `40` `17` - - 1 Abcde~ Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ - Code - options(width = 52) - colonnade(df_str[c(7L, 44L, 19L, 21L, 18L, 35L, 23L, 50L, 33L, 37L, 25L, 26L, - 10L, 39L, 2L, 47L, 42L, 14L, 9L, 41L, 45L, 6L, 4L, 11L, 24L, 43L, 32L, 3L, - 38L, 5L, 49L, 27L, 17L, 8L, 22L, 40L, 12L, 15L, 1L, 28L, 31L, 29L, 13L, 48L, - 34L, 36L, 30L, 20L, 16L, 46L)], width = 1065) - Output - `7` - - 1 Abcdefg - `44` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbcd - `19` `21` - - 1 AbcdefghijAbcdefghi AbcdefghijAbcdefghijA - `18` - - 1 AbcdefghijAbcdefgh - `35` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcde - `23` - - 1 AbcdefghijAbcdefghijAbc - `50` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbcdefghij - `33` - - 1 AbcdefghijAbcdefghijAbcdefghijAbc - `37` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefg - `25` - - 1 AbcdefghijAbcdefghijAbcde - `26` `10` - - 1 AbcdefghijAbcdefghijAbcdef Abcdefghij - `39` `2` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghi Ab - `47` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbcdefg - `42` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAb - `14` `9` - - 1 AbcdefghijAbcd Abcdefghi - `41` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijA - `45` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbcde - `6` `4` `11` `24` `43` - - 1 Abcdef Abcd AbcdefghijA Abcdefghi~ AbcdefghijAbc~ - `32` `3` `38` `5` `49` `27` `17` `8` - - 1 Abcde~ Abc Abcde~ Abcde Abcde~ Abcd~ Abcd~ Abcd~ - `22` `40` `12` `15` `1` `28` `31` `29` - - 1 Abcde~ Abcde~ Abcde~ Abcd~ A Abcd~ Abcd~ Abcd~ - `13` `48` `34` `36` `30` `20` `16` `46` - - 1 Abcde~ Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ - Code - options(width = 35) - colonnade(df_str[c(38L, 18L, 23L, 36L, 35L, 20L, 44L, 19L, 13L, 41L, 31L, 7L, - 11L, 29L, 2L, 14L, 26L, 46L, 40L, 45L, 9L, 34L, 33L, 22L, 1L, 17L, 28L, 10L, - 21L, 30L, 47L, 49L, 6L, 12L, 4L, 25L, 32L, 15L, 43L, 24L, 48L, 3L, 37L, 50L, - 42L, 39L, 16L, 8L, 27L, 5L)], width = 393) - Output - `38` - - 1 AbcdefghijAbcdefghijAbcdefghijAb~ - `18` - - 1 AbcdefghijAbcdefgh - `23` `36` `35` - - 1 Abcdefgh~ Abcdefghij~ Abcdefghij~ - `20` `44` `19` `13` `41` - - 1 Abcde~ Abcdef~ Abcd~ Abcd~ Abcde~ - `31` `7` `11` `29` `2` - - 1 Abcdef~ Abcde~ Abcd~ Abcde~ Ab - `14` `26` `46` `40` `45` - - 1 Abcde~ Abcde~ Abcde~ Abcde~ Abcd~ - `9` `34` `33` `22` `1` - - 1 Abcde~ Abcdef~ Abcde~ Abcd~ A - `17` `28` `10` `21` `30` - - 1 Abcde~ Abcdef~ Abcd~ Abcd~ Abcde~ - `47` `49` `6` `12` `4` - - 1 Abcdef~ Abcdef~ Abcd~ Abcd~ Abcd - `25` `32` `15` `43` `24` - - 1 Abcde~ Abcdef~ Abcd~ Abcde~ Abcd~ - `48` `3` `37` `50` `42` - - 1 Abcde~ Abc Abcde~ Abcde~ Abcde~ - `39` `16` `8` `27` `5` - - 1 Abcdef~ Abcde~ Abcd~ Abcde~ Abcde - Code - options(width = 41) - colonnade(df_str[c(22L, 9L, 11L, 26L, 19L, 16L, 32L, 25L, 1L, 30L, 31L, 6L, 24L, - 10L, 39L, 21L, 50L, 7L, 29L, 12L, 46L, 43L, 15L, 35L, 20L, 40L, 49L, 38L, 36L, - 48L, 34L, 3L, 8L, 4L, 27L, 42L, 44L, 33L, 45L, 18L, 5L, 2L, 13L, 47L, 28L, - 17L, 37L, 14L, 41L, 23L)], width = 999) - Output - `22` `9` - - 1 AbcdefghijAbcdefghijAb Abcdefghi - `11` `26` - - 1 AbcdefghijA AbcdefghijAbcdefghijAbcdef - `19` `16` - - 1 AbcdefghijAbcdefghi AbcdefghijAbcdef - `32` - - 1 AbcdefghijAbcdefghijAbcdefghijAb - `25` `1` - - 1 AbcdefghijAbcdefghijAbcde A - `30` - - 1 AbcdefghijAbcdefghijAbcdefghij - `31` `6` - - 1 AbcdefghijAbcdefghijAbcdefghijA Abcdef - `24` `10` - - 1 AbcdefghijAbcdefghijAbcd Abcdefghij - `39` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghi - `21` - - 1 AbcdefghijAbcdefghijA - `50` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefgh~ - `7` `29` - - 1 Abcdefg AbcdefghijAbcdefghijAbcdefghi - `12` - - 1 AbcdefghijAb - `46` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefgh~ - `43` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefgh~ - `15` - - 1 AbcdefghijAbcde - `35` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcde - `20` - - 1 AbcdefghijAbcdefghij - `40` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefgh~ - `49` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefgh~ - `38` - - 1 AbcdefghijAbcdefghijAbcdefghijAbcdefgh - `36` `48` `34` `3` - - 1 Abcdefghij~ Abcdefghij~ Abcdefgh~ Abc - `8` `4` `27` `42` `44` `33` - - 1 Abcde~ Abcd Abcde~ Abcde~ Abcde~ Abcd~ - `45` `18` `5` `2` `13` `47` - - 1 Abcdef~ Abcde~ Abcde Ab Abcd~ Abcde~ - `28` `17` `37` `14` `41` `23` - - 1 Abcde~ Abcde~ Abcde~ Abcd~ Abcde~ Abcd~ - From 49e56f5e9f2c5fc04ccb13eac8d81f1a5f850b48 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Sun, 17 Oct 2021 13:57:26 +0200 Subject: [PATCH 133/147] Avoid call --- R/pillar-package.R | 1 - man/pillar-package.Rd | 1 - 2 files changed, 2 deletions(-) diff --git a/R/pillar-package.R b/R/pillar-package.R index f6067e237..8d3b3afba 100644 --- a/R/pillar-package.R +++ b/R/pillar-package.R @@ -16,5 +16,4 @@ #' pillar(1:3) #' pillar(c(1, 2, 3)) #' pillar(factor(letters[1:3]), title = "letters") -#' colonnade(iris[1:3, ]) "_PACKAGE" diff --git a/man/pillar-package.Rd b/man/pillar-package.Rd index 7ded9af2c..46ffa7f66 100644 --- a/man/pillar-package.Rd +++ b/man/pillar-package.Rd @@ -15,7 +15,6 @@ Provides various generics for making every aspect of the display customizable. pillar(1:3) pillar(c(1, 2, 3)) pillar(factor(letters[1:3]), title = "letters") -colonnade(iris[1:3, ]) } \seealso{ \itemize{ From ec049ef128f47a9b090eeb4fffbfac4343837b73 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Sun, 17 Oct 2021 13:58:39 +0200 Subject: [PATCH 134/147] Change link to pillar_options --- R/styles.R | 2 +- man/style_subtle.Rd | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/R/styles.R b/R/styles.R index c14e8c431..1d488c08b 100644 --- a/R/styles.R +++ b/R/styles.R @@ -18,7 +18,7 @@ keep_empty <- function(fun) { #' #' @param x The character vector to style. #' @export -#' @seealso [pillar-package] for a list of options +#' @seealso [pillar_options] for a list of options #' @examples #' style_subtle("text") style_subtle <- keep_empty(function(x) { diff --git a/man/style_subtle.Rd b/man/style_subtle.Rd index db3ec6bbe..dc23f22be 100644 --- a/man/style_subtle.Rd +++ b/man/style_subtle.Rd @@ -60,5 +60,5 @@ style_na("NA") style_neg("123") } \seealso{ -\link{pillar-package} for a list of options +\link{pillar_options} for a list of options } From aedd4efe5f4149d4ee533bad45c2c4a8ef34ff5f Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Sun, 17 Oct 2021 14:04:43 +0200 Subject: [PATCH 135/147] Import deprecate_stop() --- NAMESPACE | 1 + R/zzz.R | 2 +- 2 files changed, 2 insertions(+), 1 deletion(-) diff --git a/NAMESPACE b/NAMESPACE index 5c5a5d861..a064c16e2 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -145,6 +145,7 @@ import(rlang) importFrom(fansi,strip_sgr) importFrom(fansi,substr2_ctl) importFrom(lifecycle,deprecate_soft) +importFrom(lifecycle,deprecate_stop) importFrom(utf8,utf8_width) importFrom(utils,head) importFrom(utils,str) diff --git a/R/zzz.R b/R/zzz.R index e5999c77c..b94e724f4 100644 --- a/R/zzz.R +++ b/R/zzz.R @@ -2,7 +2,7 @@ #' @import rlang #' @import ellipsis -#' @importFrom lifecycle deprecate_soft +#' @importFrom lifecycle deprecate_soft deprecate_stop #' @importFrom vctrs data_frame #' @importFrom vctrs new_data_frame #' @importFrom vctrs obj_print_footer From 6119d8f9e44a47ab249e020e4879ffe4f1610637 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Sun, 17 Oct 2021 14:13:58 +0200 Subject: [PATCH 136/147] Bump version to 1.6.3.9002 --- DESCRIPTION | 2 +- NEWS.md | 5 +++++ 2 files changed, 6 insertions(+), 1 deletion(-) diff --git a/DESCRIPTION b/DESCRIPTION index 9fd525a38..451431d5d 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -1,6 +1,6 @@ Package: pillar Title: Coloured Formatting for Columns -Version: 1.6.3.9001 +Version: 1.6.3.9002 Authors@R: c(person(given = "Kirill", family = "M\u00fcller", diff --git a/NEWS.md b/NEWS.md index e18f63d17..18f7a439e 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,5 +1,10 @@ +# pillar 1.6.3.9002 + +- `colonnade()` no longer exists, `squeeze()` and `extra_cols()` now raise an error (#272). + + # pillar 1.6.3.9001 - Fix printing for some tibbles where a fixed-width column is followed by a column with variable width (#366). From e2da371ea95cbd23511f1c345be285ba533d751d Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Sun, 17 Oct 2021 14:14:15 +0200 Subject: [PATCH 137/147] Bump version to 1.6.4 --- DESCRIPTION | 2 +- NEWS.md | 5 +++++ 2 files changed, 6 insertions(+), 1 deletion(-) diff --git a/DESCRIPTION b/DESCRIPTION index 451431d5d..383f19fdb 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -1,6 +1,6 @@ Package: pillar Title: Coloured Formatting for Columns -Version: 1.6.3.9002 +Version: 1.6.4 Authors@R: c(person(given = "Kirill", family = "M\u00fcller", diff --git a/NEWS.md b/NEWS.md index 18f7a439e..98a305d05 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,5 +1,10 @@ +# pillar 1.6.4 + +- Same as previous version. + + # pillar 1.6.3.9002 - `colonnade()` no longer exists, `squeeze()` and `extra_cols()` now raise an error (#272). From 156b0796e6e2f0b36f1ab026190364ce7715ae65 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Sun, 17 Oct 2021 14:14:22 +0200 Subject: [PATCH 138/147] Update CRAN comments --- cran-comments.md | 14 ++++++++++---- 1 file changed, 10 insertions(+), 4 deletions(-) diff --git a/cran-comments.md b/cran-comments.md index a507e33bd..5f7bf2366 100644 --- a/cran-comments.md +++ b/cran-comments.md @@ -1,4 +1,4 @@ -pillar 1.6.3 +pillar 1.6.4 ## Cran Repository Policy @@ -7,9 +7,15 @@ pillar 1.6.3 ## R CMD check results - [x] Checked locally, R 4.1.1 -- [x] Checked on CI system, R 4.1.1 -- [x] Checked on win-builder, R devel +- [ ] Checked on CI system, R 4.1.1 +- [ ] Checked on win-builder, R devel + +Check the boxes above after successful execution and remove this line. Then run `fledge::release()`. ## Current CRAN check results -- [x] Checked on 2021-09-26, no problems found. +- [x] Checked on 2021-10-17, problems found: https://cran.r-project.org/web/checks/check_results_pillar.html +- [ ] WARN: r-devel-linux-x86_64-debian-clang, r-devel-linux-x86_64-debian-gcc, r-patched-linux-x86_64, r-release-linux-x86_64 +- [ ] WARN: r-devel-linux-x86_64-fedora-clang, r-devel-linux-x86_64-fedora-gcc, r-devel-windows-x86_64, r-devel-windows-x86_64-gcc10-UCRT, r-release-windows-ix86+x86_64, r-oldrel-windows-ix86+x86_64 + +Check results at: https://cran.r-project.org/web/checks/check_results_pillar.html From 25b5ec825f2920f517036add110220ea1e58e8a6 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Sun, 17 Oct 2021 14:14:27 +0200 Subject: [PATCH 139/147] Bump version to 1.6.4.9000 --- DESCRIPTION | 2 +- NEWS.md | 5 +++++ 2 files changed, 6 insertions(+), 1 deletion(-) diff --git a/DESCRIPTION b/DESCRIPTION index 383f19fdb..4a22a2172 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -1,6 +1,6 @@ Package: pillar Title: Coloured Formatting for Columns -Version: 1.6.4 +Version: 1.6.4.9000 Authors@R: c(person(given = "Kirill", family = "M\u00fcller", diff --git a/NEWS.md b/NEWS.md index 98a305d05..a1ccb02f4 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,5 +1,10 @@ +# pillar 1.6.4.9000 + +- Same as previous version. + + # pillar 1.6.4 - Same as previous version. From 4128a468d8aa08d952c7da031a286261e18a87bb Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Sun, 17 Oct 2021 14:16:24 +0200 Subject: [PATCH 140/147] NEWS and CRAN comments --- NEWS.md | 17 ++++++----------- cran-comments.md | 11 +++-------- 2 files changed, 9 insertions(+), 19 deletions(-) diff --git a/NEWS.md b/NEWS.md index 98a305d05..4bc83e567 100644 --- a/NEWS.md +++ b/NEWS.md @@ -2,24 +2,19 @@ # pillar 1.6.4 -- Same as previous version. +## Bug fixes +- Fix printing for some tibbles where a fixed-width column is followed by a column with variable width (#366). +- Avoid nested backtick blocks in vignette. -# pillar 1.6.3.9002 +## Breaking changes - `colonnade()` no longer exists, `squeeze()` and `extra_cols()` now raise an error (#272). - - -# pillar 1.6.3.9001 - -- Fix printing for some tibbles where a fixed-width column is followed by a column with variable width (#366). - `num()` requires an integerish `digits` argument (#362). -- Avoid nested backtick blocks in vignette. -- Link to tibble vignettes and documentation pages. -# pillar 1.6.3.9000 +## Documentation -- Same as previous version. +- Link to tibble vignettes and documentation pages. # pillar 1.6.3 diff --git a/cran-comments.md b/cran-comments.md index 5f7bf2366..0bd49ec80 100644 --- a/cran-comments.md +++ b/cran-comments.md @@ -7,15 +7,10 @@ pillar 1.6.4 ## R CMD check results - [x] Checked locally, R 4.1.1 -- [ ] Checked on CI system, R 4.1.1 -- [ ] Checked on win-builder, R devel - -Check the boxes above after successful execution and remove this line. Then run `fledge::release()`. +- [x] Checked on CI system, R 4.1.1 +- [x] Checked on win-builder, R devel ## Current CRAN check results - [x] Checked on 2021-10-17, problems found: https://cran.r-project.org/web/checks/check_results_pillar.html -- [ ] WARN: r-devel-linux-x86_64-debian-clang, r-devel-linux-x86_64-debian-gcc, r-patched-linux-x86_64, r-release-linux-x86_64 -- [ ] WARN: r-devel-linux-x86_64-fedora-clang, r-devel-linux-x86_64-fedora-gcc, r-devel-windows-x86_64, r-devel-windows-x86_64-gcc10-UCRT, r-release-windows-ix86+x86_64, r-oldrel-windows-ix86+x86_64 - -Check results at: https://cran.r-project.org/web/checks/check_results_pillar.html +- [x] WARN: r-devel-linux-x86_64-debian-clang, r-devel-linux-x86_64-debian-gcc, r-patched-linux-x86_64, r-release-linux-x86_64, r-devel-linux-x86_64-fedora-clang, r-devel-linux-x86_64-fedora-gcc, r-devel-windows-x86_64, r-devel-windows-x86_64-gcc10-UCRT, r-release-windows-ix86+x86_64, r-oldrel-windows-ix86+x86_64: fixed vignette building errors From 0436e99b0ad93caeebeb2e8a48f034179c149db5 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Sun, 17 Oct 2021 14:19:44 +0200 Subject: [PATCH 141/147] Build-ignore --- .Rbuildignore | 1 + 1 file changed, 1 insertion(+) diff --git a/.Rbuildignore b/.Rbuildignore index 2b44321c9..e8eaf6193 100644 --- a/.Rbuildignore +++ b/.Rbuildignore @@ -25,3 +25,4 @@ ^\.lintr$ _cache$ ^\.vscode$ +^*\.html$ From f41d38383f876f943e68b5d715b3d0c82b1f4123 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Sun, 17 Oct 2021 14:22:22 +0200 Subject: [PATCH 142/147] Fix --- .Rbuildignore | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.Rbuildignore b/.Rbuildignore index e8eaf6193..2f42f71dc 100644 --- a/.Rbuildignore +++ b/.Rbuildignore @@ -25,4 +25,4 @@ ^\.lintr$ _cache$ ^\.vscode$ -^*\.html$ +\.html$ From fdf78f1296378f074bf5eb1656f20cc4bee522fe Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Sun, 17 Oct 2021 14:23:21 +0200 Subject: [PATCH 143/147] Now? --- .Rbuildignore | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.Rbuildignore b/.Rbuildignore index 2f42f71dc..3242e5cd2 100644 --- a/.Rbuildignore +++ b/.Rbuildignore @@ -25,4 +25,4 @@ ^\.lintr$ _cache$ ^\.vscode$ -\.html$ +^vignettes/.*\.html$ From 1e95a4bc261d6c8f3921661cf876dd1cb41c42cc Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Mon, 18 Oct 2021 21:11:07 +0200 Subject: [PATCH 144/147] Revert "Merge pull request #375 from r-lib/f-272-dead-code" This reverts commit f7f9aa34362ac117b065038ab0003988a00f4bd9, reversing changes made to 23e076755b35ef1e74f8003e89c39910bb136642. --- NAMESPACE | 8 +- R/multi.R | 327 ++++- R/pillar-package.R | 1 + R/shaft-.R | 5 + R/type-sum.R | 5 + R/zzz.R | 4 +- man/colonnade.Rd | 52 +- man/extra_cols.Rd | 16 +- man/pillar-package.Rd | 1 + man/squeeze.Rd | 5 +- tests/testthat/_snaps/format_multi.md | 899 +++++++++++++ tests/testthat/_snaps/format_multi_fuzz.md | 918 +++++++++++++ tests/testthat/_snaps/format_multi_fuzz_2.md | 1161 +++++++++++++++++ tests/testthat/_snaps/zzx-format_character.md | 23 + tests/testthat/test-format_multi.R | 267 ++++ tests/testthat/test-format_multi_fuzz.R | 39 + tests/testthat/test-format_multi_fuzz_2.R | 39 + tests/testthat/test-zzx-format_character.R | 10 + 18 files changed, 3764 insertions(+), 16 deletions(-) create mode 100644 tests/testthat/_snaps/format_multi_fuzz.md create mode 100644 tests/testthat/_snaps/format_multi_fuzz_2.md create mode 100644 tests/testthat/_snaps/zzx-format_character.md create mode 100644 tests/testthat/test-format_multi_fuzz.R create mode 100644 tests/testthat/test-format_multi_fuzz_2.R diff --git a/NAMESPACE b/NAMESPACE index a064c16e2..a4d1a739e 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -3,11 +3,13 @@ S3method(as_tbl,data.frame) S3method(ctl_new_compound_pillar,tbl) S3method(ctl_new_pillar,tbl) +S3method(extra_cols,pillar_squeezed_colonnade) S3method(format,pillar) S3method(format,pillar_1e) S3method(format,pillar_capital) S3method(format,pillar_char) S3method(format,pillar_char_attr) +S3method(format,pillar_colonnade) S3method(format,pillar_continuation_shaft) S3method(format,pillar_num) S3method(format,pillar_num_attr) @@ -18,6 +20,7 @@ S3method(format,pillar_rif_type) S3method(format,pillar_shaft) S3method(format,pillar_shaft_decimal) S3method(format,pillar_shaft_simple) +S3method(format,pillar_squeezed_colonnade) S3method(format,pillar_tbl_format_setup) S3method(format,pillar_title) S3method(format,pillar_type) @@ -45,6 +48,7 @@ S3method(pillar_shaft,factor) S3method(pillar_shaft,list) S3method(pillar_shaft,logical) S3method(pillar_shaft,numeric) +S3method(pillar_shaft,pillar_empty_col) S3method(pillar_shaft,pillar_vctr) S3method(pillar_shaft,pillar_vertical) S3method(pillar_shaft,vctrs_list_of) @@ -53,8 +57,10 @@ S3method(pillar_shaft,vctrs_vctr) S3method(print,compound_pillar) S3method(print,pillar) S3method(print,pillar_1e) +S3method(print,pillar_colonnade) S3method(print,pillar_ornament) S3method(print,pillar_shaft) +S3method(print,pillar_squeezed_colonnade) S3method(print,pillar_tbl_format_setup) S3method(print,pillar_vctr) S3method(print,pillar_vctr_attr) @@ -101,6 +107,7 @@ S3method(vec_ptype_abbr,pillar_num) S3method(vec_ptype_full,pillar_vctr) export(align) export(char) +export(colonnade) export(ctl_new_compound_pillar) export(ctl_new_pillar) export(dim_desc) @@ -145,7 +152,6 @@ import(rlang) importFrom(fansi,strip_sgr) importFrom(fansi,substr2_ctl) importFrom(lifecycle,deprecate_soft) -importFrom(lifecycle,deprecate_stop) importFrom(utf8,utf8_width) importFrom(utils,head) importFrom(utils,str) diff --git a/R/multi.R b/R/multi.R index 3bc97cc57..b416c28d0 100644 --- a/R/multi.R +++ b/R/multi.R @@ -1,21 +1,322 @@ +#' Format multiple vectors in a tabular display +#' +#' @description +#' The vectors are formatted to fit horizontally into a user-supplied number of +#' characters per row. +#' +#' The `colonnade()` function doesn't process the input but returns an object +#' with a [format()] and a [print()] method. +#' The implementations call [squeeze()] to create [pillar] objects and fit them to a given width. +#' +#' @param x A list, which can contain matrices or data frames. +#' If named, the names will be used as title for the pillars. Non-syntactic names +#' will be escaped. +#' @param has_row_id Include a column indicating row IDs? Pass `"*"` to mark +#' the row ID column with a star. +#' @param width Default width of the entire output, optional. +#' @inheritParams ellipsis::dots_empty +#' @keywords internal +#' @export +#' @examples +#' colonnade(list(a = 1:3, b = letters[1:3])) +#' +#' long_string <- list(paste(letters, collapse = " ")) +#' colonnade(long_string, width = 20) +#' colonnade(long_string, has_row_id = FALSE, width = 20) +#' +#' # The width can also be overridden when calling format() or print(): +#' print(colonnade(long_string), width = 20) +#' +#' # If width is larger than getOption("width"), multiple tiers are created: +#' colonnade(rep(long_string, 4), width = Inf) +colonnade <- function(x, has_row_id = TRUE, width = NULL, ...) { + if (!missing(...)) { + check_dots_empty(action = warn) + } + + # Reset local cache for each new colonnade + num_colors(forget = TRUE) + + x <- flatten_colonnade(x) + ret <- new_data_frame(x, has_row_id = has_row_id, class = "pillar_colonnade") + ret <- set_width(ret, width) + ret +} + +flatten_colonnade <- function(x) { + out <- map2( + unname(x), + names2(x), + flatten_column + ) + + vec_rbind( + !!!out, + # .ptype = data_frame(names = list(), data = list()) + .ptype = data_frame(names = character(), data = list()) + ) +} + +flatten_column <- function(x, name) { + if (name != "") { + name <- tick_if_needed(name) + } + + if (is.data.frame(x)) { + flatten_df_column(x, name) + } else if (is.matrix(x) && !inherits(x, c("Surv", "Surv2"))) { + flatten_matrix_column(x, name) + } else { + # Length-one list, will be unlist()ed afterwards + # data_frame(names = list(name), data = list(x)) + data_frame(names = name, data = list(x)) + } +} + +flatten_df_column <- function(x, name) { + if (length(x) == 0) { + # data_frame(names = list(name), data = list(new_empty_col_sentinel(x))) + data_frame(names = name, data = list(new_empty_col_sentinel(x))) + } else { + x <- flatten_colonnade(unclass(x)) + # x$names <- map(x$names, function(.x) c(name, .x)) + x$names <- paste0("$", x$names) + x$names[[1]] <- paste0(name, x$names[[1]]) + x + } +} + +flatten_matrix_column <- function(x, name) { + if (ncol(x) == 0) { + data_frame( + # names = list(c(name, "[,0]")), + names = name, + data = list(new_empty_col_sentinel(x)) + ) + } else { + x_list <- map(seq_len(ncol(x)), function(i) x[, i]) + + idx <- colnames(x) + if (is.null(idx)) { + idx <- seq_along(x_list) + } else { + idx <- encodeString(idx, quote = '"') + } + + # names <- map(idx, function(.x) c(name, .x)) + names <- paste0("[,", idx, "]") + names[[1]] <- paste0(name, names[[1]]) + + data_frame(names = names, data = x_list) + } +} + +new_empty_col_sentinel <- function(type) { + structure(list(type), class = c("pillar_empty_col")) +} + #' Squeeze a colonnade to a fixed width #' -#' Defunct. +#' The `squeeze()` function usually doesn't need to be called manually. +#' It returns an object suitable for printing and formatting at a fixed width +#' with additional information about omitted columns, which can be retrieved +#' via [extra_cols()]. #' #' @keywords internal #' @export squeeze <- function(x, width = NULL, ...) { - deprecate_stop("1.6.4", "pillar::squeeze()") + deprecate_soft("1.5.0", "pillar::squeeze()") + + squeeze_impl(x, width, ...) +} + +squeeze_impl <- function(x, width = NULL, ...) { + # Shortcut for zero-height corner case + zero_height <- length(x$data) == 0L || length(x$data[[1]]) == 0L + if (zero_height) { + return(new_colonnade_squeezed(list(), colonnade = x, extra_cols = seq_along(x$data))) + } + + if (is.null(width)) { + width <- get_width(x) + } + + if (is.null(width)) { + width <- getOption("width") + } + + rowid <- get_rowid_from_colonnade(x) + if (is.null(rowid)) { + rowid_width <- 0 + } else { + rowid_width <- max(get_widths(rowid)) + 1L + } + + col_widths <- colonnade_get_width(x, width, rowid_width) + col_widths_shown <- col_widths[!safe_is_na(col_widths$tier), ] + indexes <- split(seq_along(col_widths_shown$tier), col_widths_shown$tier) + + out <- map(indexes, function(i) { + inner <- map2(col_widths_shown$pillar[i], col_widths_shown$width[i], pillar_format_parts) + if (!is.null(rowid)) { + inner <- c(list(pillar_format_parts(rowid, rowid_width - 1L)), inner) + } + inner + }) + + n_cols_shown <- nrow(col_widths_shown) + extra_cols <- seq2(n_cols_shown + 1L, length(x$data)) + new_colonnade_squeezed(out, colonnade = x, extra_cols = extra_cols) +} + +get_rowid_from_colonnade <- function(x) { + has_title <- any(x$names != "") + + has_row_id <- attr(x, "has_row_id", exact = TRUE) + if (!is_false(has_row_id) && length(x$data) > 0) { + rowid <- rowidformat( + length(x$data[[1]]), + has_star = identical(has_row_id, "*"), + has_title_row = has_title + ) + } else { + rowid <- NULL + } + + rowid +} + +new_colonnade_squeezed <- function(x, colonnade, extra_cols) { + formatted_tiers <- map(x, format_colonnade_tier) + formatted <- new_vertical(as.character(unlist(formatted_tiers))) + + structure( + list(formatted), + extra_cols = colonnade[extra_cols, ], + class = "pillar_squeezed_colonnade" + ) +} + +format_colonnade_tier <- function(x) { + "!!!!!DEBUG format_colonnade_tier(`v(x)`)" + + if (length(x) == 0) { + return(character()) + } + + unlist(pmap(unname(x), paste)) +} + +#' @export +format.pillar_squeezed_colonnade <- function(x, ...) { + x[[1]] +} + +#' @export +print.pillar_squeezed_colonnade <- function(x, ...) { + print(format(x, ...), ...) + invisible(x) +} + +# Method registration happens in .onLoad() +knit_print.pillar_squeezed_colonnade <- function(x, ...) { + unlist(map(x, knit_print_squeezed_colonnade_tier)) +} + +knit_print_squeezed_colonnade_tier <- function(x) { + # Hack + header <- map_chr(map(x, `[[`, "capital_format"), `[[`, "title_format") + col <- map(x, function(xx) c(xx[["capital_format"]][["type_format"]], xx[["shaft_format"]])) + + knitr::kable(as.data.frame(col), row.names = NA, col.names = header) } #' Retrieve information about columns that didn't fit the available width #' -#' Defunct. +#' Formatting a [colonnade] object may lead to some columns being omitted +#' due to width restrictions. This method returns a character vector that +#' describes each of the omitted columns. #' +#' @param x The result of [squeeze()] on a [colonnade] object +#' @inheritParams ellipsis::dots_used #' @keywords internal #' @export extra_cols <- function(x, ...) { - deprecate_stop("1.6.4", "pillar::extra_cols()") + deprecate_soft("1.5.0", "pillar::extra_cols()") + + if (!missing(...)) { + check_dots_used(action = warn) + } + + UseMethod("extra_cols") +} + +#' @rdname extra_cols +#' @param n The number of extra columns to return; the returned vector will +#' always contain as many elements as there are extra columns, but elements +#' beyond `n` will be `NA`. +#' @export +extra_cols.pillar_squeezed_colonnade <- function(x, ..., n = Inf) { + extra_cols_impl(x, n) +} + +extra_cols_impl <- function(x, n = NULL) { + extra_cols <- attr(x, "extra_cols", exact = TRUE) + ret <- rep(NA_character_, length(extra_cols$data)) + + if (is.null(n)) { + n <- Inf + } + + idx <- seq_len(min(length(extra_cols$data), n)) + ret[idx] <- map2_chr(extra_cols$data[idx], extra_cols$names[idx], format_abbrev, space = NBSP) + ret +} + +#' @export +format.pillar_colonnade <- function(x, ...) { + format(squeeze_impl(x, ...)) +} + +#' @export +print.pillar_colonnade <- function(x, ...) { + print(format(x, ...)) +} + +#' @rdname colonnade +#' @usage NULL +#' @aliases NULL +colonnade_get_width <- function(x, width, rowid_width) { + #' @details + #' Pillars may be distributed over multiple tiers if + #' `width > getOption("width")`. In this case each tier is at most + #' `getOption("width")` characters wide. The very first step of formatting + #' is to determine how many tiers are shown at most, and the width of each + #' tier. + tier_widths <- get_tier_widths(width, length(x$data), rowid_width) + + #' + #' To avoid unnecessary computation for showing very wide colonnades, a first + #' pass tries to fit all capitals into the tiers. + init_cols <- min(length(x$data), sum(floor((tier_widths + 1L) / (MIN_PILLAR_WIDTH + 1L)))) + capitals <- map2(x$data[seq_len(init_cols)], x$names[seq_len(init_cols)], pillar_capital) + init_col_widths_df <- colonnade_compute_tiered_col_widths(capitals, tier_widths) + pillar_shown <- init_col_widths_df$id[!safe_is_na(init_col_widths_df$tier)] + if (length(pillar_shown) < init_cols) { + # (Include one more pillar to indicate that the data is too wide.) + pillar_shown <- c(pillar_shown, pillar_shown[length(pillar_shown)] + 1L) + } + + #' For each pillar whose capital fits, it is then decided in which tier it is + #' shown, if at all, and how much horizontal space it may use (either its + #' minimum or its maximum width). + shafts <- map(x$data[pillar_shown], pillar_shaft) + pillars <- map2(capitals[pillar_shown], shafts, new_pillar_1e) + col_widths_df <- colonnade_compute_tiered_col_widths(pillars, tier_widths) + + #' Remaining space is then distributed proportionally to pillars that do not + #' use their desired width. + colonnade_distribute_space_df(col_widths_df, tier_widths) } get_tier_widths <- function(width, ncol, rowid_width, tier_width = getOption("width")) { @@ -31,12 +332,18 @@ get_tier_widths <- function(width, ncol, rowid_width, tier_width = getOption("wi widths[widths >= 1L] } -#' Distributing pillars over multiple tiers -#' -#' Documentation generated from inline code comments. -#' -#' @name colonnade -#' @keywords internal +colonnade_compute_tiered_col_widths <- function(pillars, tier_widths) { + max_tier_width <- max(tier_widths) + + max_widths <- pmin(map_int(map(pillars, get_widths), max), max_tier_width) + min_widths <- pmin(map_int(map(pillars, get_min_widths), max), max_widths) + + ret <- colonnade_compute_tiered_col_widths_df(max_widths, min_widths, tier_widths) + ret$pillar <- pillars + ret +} + +#' @rdname colonnade #' @usage NULL #' @aliases NULL colonnade_compute_tiered_col_widths_df <- function(max_widths, min_widths, tier_widths) { diff --git a/R/pillar-package.R b/R/pillar-package.R index 8d3b3afba..f6067e237 100644 --- a/R/pillar-package.R +++ b/R/pillar-package.R @@ -16,4 +16,5 @@ #' pillar(1:3) #' pillar(c(1, 2, 3)) #' pillar(factor(letters[1:3]), title = "letters") +#' colonnade(iris[1:3, ]) "_PACKAGE" diff --git a/R/shaft-.R b/R/shaft-.R index 6f48984da..d45db3013 100644 --- a/R/shaft-.R +++ b/R/shaft-.R @@ -71,6 +71,11 @@ pillar_shaft <- function(x, ...) { UseMethod("pillar_shaft") } +#' @export +pillar_shaft.pillar_empty_col <- function(x, ...) { + new_empty_shaft() +} + #' @param width Width for printing and formatting. #' @export #' @rdname pillar_shaft diff --git a/R/type-sum.R b/R/type-sum.R index e097dca8c..71f28da67 100644 --- a/R/type-sum.R +++ b/R/type-sum.R @@ -58,6 +58,11 @@ type_sum.default <- function(x) { ) } +# Registered in .onLoad() +vec_ptype_abbr.pillar_empty_col <- function(x, ...) { + vec_ptype_abbr(x[[1]]) +} + #' @description #' `obj_sum()` also includes the size (but not the shape) of the object #' if [vctrs::vec_is()] is `TRUE`. diff --git a/R/zzz.R b/R/zzz.R index b94e724f4..567bd8638 100644 --- a/R/zzz.R +++ b/R/zzz.R @@ -2,7 +2,7 @@ #' @import rlang #' @import ellipsis -#' @importFrom lifecycle deprecate_soft deprecate_stop +#' @importFrom lifecycle deprecate_soft #' @importFrom vctrs data_frame #' @importFrom vctrs new_data_frame #' @importFrom vctrs obj_print_footer @@ -35,6 +35,8 @@ NULL # nolint end # Can't use vctrs::s3_register() here with vctrs 0.1.0 # https://github.com/r-lib/vctrs/pull/314 + register_s3_method("knitr", "knit_print", "pillar_squeezed_colonnade") + register_s3_method("vctrs", "vec_ptype_abbr", "pillar_empty_col") register_s3_method("bit64", "pillar_shaft", "integer64", gen_pkg = "pillar") register_s3_method("survival", "pillar_shaft", "Surv", gen_pkg = "pillar") register_s3_method("survival", "type_sum", "Surv", gen_pkg = "pillar") diff --git a/man/colonnade.Rd b/man/colonnade.Rd index 157d1d7a0..55dc051d8 100644 --- a/man/colonnade.Rd +++ b/man/colonnade.Rd @@ -1,11 +1,46 @@ % Generated by roxygen2: do not edit by hand % Please edit documentation in R/multi.R \name{colonnade} -\title{Distributing pillars over multiple tiers} +\alias{colonnade} +\title{Format multiple vectors in a tabular display} +\usage{ +colonnade(x, has_row_id = TRUE, width = NULL, ...) +} +\arguments{ +\item{x}{A list, which can contain matrices or data frames. +If named, the names will be used as title for the pillars. Non-syntactic names +will be escaped.} + +\item{has_row_id}{Include a column indicating row IDs? Pass \code{"*"} to mark +the row ID column with a star.} + +\item{width}{Default width of the entire output, optional.} + +\item{...}{These dots are for future extensions and must be empty.} +} \description{ -Documentation generated from inline code comments. +The vectors are formatted to fit horizontally into a user-supplied number of +characters per row. + +The \code{colonnade()} function doesn't process the input but returns an object +with a \code{\link[=format]{format()}} and a \code{\link[=print]{print()}} method. +The implementations call \code{\link[=squeeze]{squeeze()}} to create \link{pillar} objects and fit them to a given width. } \details{ +Pillars may be distributed over multiple tiers if +\code{width > getOption("width")}. In this case each tier is at most +\code{getOption("width")} characters wide. The very first step of formatting +is to determine how many tiers are shown at most, and the width of each +tier. + +To avoid unnecessary computation for showing very wide colonnades, a first +pass tries to fit all capitals into the tiers. +For each pillar whose capital fits, it is then decided in which tier it is +shown, if at all, and how much horizontal space it may use (either its +minimum or its maximum width). +Remaining space is then distributed proportionally to pillars that do not +use their desired width. + For fitting pillars in one or more tiers, first a check is made if all pillars fit with their maximum width (e.g., \code{option(tibble.width = Inf)} or narrow colonnade). @@ -52,4 +87,17 @@ rounded down. Any space remaining after rounding is distributed from left to right, one space per column. } +\examples{ +colonnade(list(a = 1:3, b = letters[1:3])) + +long_string <- list(paste(letters, collapse = " ")) +colonnade(long_string, width = 20) +colonnade(long_string, has_row_id = FALSE, width = 20) + +# The width can also be overridden when calling format() or print(): +print(colonnade(long_string), width = 20) + +# If width is larger than getOption("width"), multiple tiers are created: +colonnade(rep(long_string, 4), width = Inf) +} \keyword{internal} diff --git a/man/extra_cols.Rd b/man/extra_cols.Rd index 3c2ff3c6c..e9b75dbc2 100644 --- a/man/extra_cols.Rd +++ b/man/extra_cols.Rd @@ -2,11 +2,25 @@ % Please edit documentation in R/multi.R \name{extra_cols} \alias{extra_cols} +\alias{extra_cols.pillar_squeezed_colonnade} \title{Retrieve information about columns that didn't fit the available width} \usage{ extra_cols(x, ...) + +\method{extra_cols}{pillar_squeezed_colonnade}(x, ..., n = Inf) +} +\arguments{ +\item{x}{The result of \code{\link[=squeeze]{squeeze()}} on a \link{colonnade} object} + +\item{...}{Arguments passed to methods.} + +\item{n}{The number of extra columns to return; the returned vector will +always contain as many elements as there are extra columns, but elements +beyond \code{n} will be \code{NA}.} } \description{ -Defunct. +Formatting a \link{colonnade} object may lead to some columns being omitted +due to width restrictions. This method returns a character vector that +describes each of the omitted columns. } \keyword{internal} diff --git a/man/pillar-package.Rd b/man/pillar-package.Rd index 46ffa7f66..7ded9af2c 100644 --- a/man/pillar-package.Rd +++ b/man/pillar-package.Rd @@ -15,6 +15,7 @@ Provides various generics for making every aspect of the display customizable. pillar(1:3) pillar(c(1, 2, 3)) pillar(factor(letters[1:3]), title = "letters") +colonnade(iris[1:3, ]) } \seealso{ \itemize{ diff --git a/man/squeeze.Rd b/man/squeeze.Rd index 4161fc4b6..eddcf715c 100644 --- a/man/squeeze.Rd +++ b/man/squeeze.Rd @@ -7,6 +7,9 @@ squeeze(x, width = NULL, ...) } \description{ -Defunct. +The \code{squeeze()} function usually doesn't need to be called manually. +It returns an object suitable for printing and formatting at a fixed width +with additional information about omitted columns, which can be retrieved +via \code{\link[=extra_cols]{extra_cols()}}. } \keyword{internal} diff --git a/tests/testthat/_snaps/format_multi.md b/tests/testthat/_snaps/format_multi.md index 54f029403..0c337dc20 100644 --- a/tests/testthat/_snaps/format_multi.md +++ b/tests/testthat/_snaps/format_multi.md @@ -21,3 +21,902 @@ Output [1] "NA" +# output test + + Code + colonnade(x, width = 4) + colonnade(x, width = 5) + colonnade(x, width = 6) + colonnade(x, width = 7) + Output + colu~ + + 1 1.23 + 2 2.23 + 3 3.23 + Code + colonnade(x, width = 8) + Output + colum~ + + 1 1.23 + 2 2.23 + 3 3.23 + Code + colonnade(x, width = 9) + Output + column~ + + 1 1.23 + 2 2.23 + 3 3.23 + Code + colonnade(x, width = 10) + Output + column_~ + + 1 1.23 + 2 2.23 + 3 3.23 + Code + colonnade(x, width = 11) + Output + column_z~ + + 1 1.23 + 2 2.23 + 3 3.23 + Code + colonnade(x, width = 12) + Output + column_ze~ + + 1 1.23 + 2 2.23 + 3 3.23 + Code + colonnade(x, width = 13) + Output + column_zer~ + + 1 1.23 + 2 2.23 + 3 3.23 + Code + colonnade(x, width = 14) + Output + column_zero~ + + 1 1.23 + 2 2.23 + 3 3.23 + Code + colonnade(x, width = 15) + Output + column_zero_~ + + 1 1.23 + 2 2.23 + 3 3.23 + Code + colonnade(x, width = 16) + Output + column_zero_o~ + + 1 1.23 + 2 2.23 + 3 3.23 + Code + colonnade(x, width = 17) + Output + column_zero_one + + 1 1.23 + 2 2.23 + 3 3.23 + Code + colonnade(x, width = 18) + Output + column_zero_one + + 1 1.23 + 2 2.23 + 3 3.23 + Code + colonnade(x, width = 19) + Output + column_zero_one + + 1 1.23 + 2 2.23 + 3 3.23 + Code + colonnade(x, width = 20) + Output + column_zero_one + + 1 1.23 + 2 2.23 + 3 3.23 + Code + colonnade(x, width = 21) + Output + column_zero_one + + 1 1.23 + 2 2.23 + 3 3.23 + Code + colonnade(x, width = 22) + Output + column_zero_one + + 1 1.23 + 2 2.23 + 3 3.23 + Code + colonnade(x, width = 23) + Output + column_zero_one + + 1 1.23 + 2 2.23 + 3 3.23 + Code + colonnade(x, width = 24) + Output + column_zero_one col_02 + + 1 1.23 a + 2 2.23 b + 3 3.23 c + Code + colonnade(x, width = 25) + Output + column_zero_one col_02 + + 1 1.23 a + 2 2.23 b + 3 3.23 c + Code + colonnade(x, width = 26) + Output + column_zero_one col_02 + + 1 1.23 a + 2 2.23 b + 3 3.23 c + Code + colonnade(x, width = 27) + Output + column_zero_one col_02 + + 1 1.23 a + 2 2.23 b + 3 3.23 c + Code + colonnade(x, width = 28) + Output + column_zero_one col_02 + + 1 1.23 a + 2 2.23 b + 3 3.23 c + Code + colonnade(x, width = 29) + Output + column_zero_one col_02 + + 1 1.23 a + 2 2.23 b + 3 3.23 c + Code + colonnade(x, width = 30) + Output + column_zero_one col_02 + + 1 1.23 a + 2 2.23 b + 3 3.23 c + Code + colonnade(x, width = 31) + Output + column_zero_one col_02 col_03 + + 1 1.23 a a + 2 2.23 b b + 3 3.23 c c + Code + colonnade(x, width = 32) + Output + column_zero_one col_02 col_03 + + 1 1.23 a a + 2 2.23 b b + 3 3.23 c c + Code + colonnade(x, width = 33) + Output + column_zero_one col_02 col_03 + + 1 1.23 a a + 2 2.23 b b + 3 3.23 c c + Code + colonnade(x, width = 34) + Output + column_zero_one col_02 col_03 + + 1 1.23 a a + 2 2.23 b b + 3 3.23 c c + Code + colonnade(x, width = 35) + Output + column_zero_one col_02 col_03 + + 1 1.23 a a + 2 2.23 b b + 3 3.23 c c + Code + colonnade(x, width = 36) + Output + column_zero_one col_02 col_03 + + 1 1.23 a a + 2 2.23 b b + 3 3.23 c c + Code + colonnade(x, width = 37) + Output + column_zero_one col_02 col_03 + + 1 1.23 a a + 2 2.23 b b + 3 3.23 c c + Code + colonnade(x, width = 38) + Output + column_zero_one col_02 col_03 col_04 + + 1 1.23 a a a + 2 2.23 b b b + 3 3.23 c c c + Code + colonnade(x, width = 39) + Output + column_zero_one col_02 col_03 col_04 + + 1 1.23 a a a + 2 2.23 b b b + 3 3.23 c c c + Code + colonnade(x, width = Inf) + Output + column_zero_one col_02 col_03 col_04 + + 1 1.23 a a a + 2 2.23 b b b + 3 3.23 c c c + +--- + + Code + colonnade(rep(list(paste(letters, collapse = " ")), 4), width = Inf) + Output + + 1 a b c d e f g h i j k l m n o p q r s t u v w x y z + + 1 a b c d e f g h i j k l m n o p q r s t u v w x y z + + 1 a b c d e f g h i j k l m n o p q r s t u v w x y z + + 1 a b c d e f g h i j k l m n o p q r s t u v w x y z + +--- + + Code + new_vertical(extra_cols_impl(squeeze_impl(colonnade(x), width = 10))) + Output + col_02  + col_03  + col_04  + +--- + + Code + new_vertical(extra_cols_impl(squeeze_impl(colonnade(x), width = 20))) + Output + col_02  + col_03  + col_04  + +--- + + Code + new_vertical(extra_cols_impl(squeeze_impl(colonnade(x), width = 30))) + Output + col_03  + col_04  + +--- + + Code + new_vertical(extra_cols_impl(squeeze_impl(colonnade(x), width = 35))) + Output + col_04  + +--- + + Code + new_vertical(extra_cols_impl(squeeze_impl(colonnade(x), width = 40))) + +# tests from tibble + + Code + colonnade(mtcars[1:8, ], has_row_id = "*", width = 30) + Output + mpg cyl disp hp + * + 1 21 6 160 110 + 2 21 6 160 110 + 3 22.8 4 108 93 + 4 21.4 6 258 110 + 5 18.7 8 360 175 + 6 18.1 6 225 105 + 7 14.3 8 360 245 + 8 24.4 4 147. 62 + Code + colonnade(iris[1:5, ], width = 30) + Output + Sepal.Length Sepal.Width + + 1 5.1 3.5 + 2 4.9 3 + 3 4.7 3.2 + 4 4.6 3.1 + 5 5 3.6 + Code + colonnade(iris[1:3, ], width = 20) + Output + Sepal.Length + + 1 5.1 + 2 4.9 + 3 4.7 + Code + colonnade(df_all, width = 30) + Output + a b c d + + 1 1 1 TRUE a + 2 2.5 2 FALSE b + 3 NA NA NA + Code + colonnade(df_all, width = 300) + Output + a b c d e f g h + + 1 1 1 TRUE a a 2015-12-10 2015-12-09 10:51:35 + 2 2.5 2 FALSE b b 2015-12-11 2015-12-09 10:51:36 + 3 NA NA NA NA NA + i + + 1 + 2 + 3 + Code + options(width = 70) + colonnade(df_all, width = 300) + Output + a b c d e f g + + 1 1 1 TRUE a a 2015-12-10 2015-12-09 10:51:35 + 2 2.5 2 FALSE b b 2015-12-11 2015-12-09 10:51:36 + 3 NA NA NA NA NA + h i + + 1 + 2 + 3 + Code + options(width = 60) + colonnade(df_all, width = 300) + Output + a b c d e f + + 1 1 1 TRUE a a 2015-12-10 + 2 2.5 2 FALSE b b 2015-12-11 + 3 NA NA NA NA + g h i + + 1 2015-12-09 10:51:35 + 2 2015-12-09 10:51:36 + 3 NA + Code + options(width = 50) + colonnade(df_all, width = 300) + Output + a b c d e f + + 1 1 1 TRUE a a 2015-12-10 + 2 2.5 2 FALSE b b 2015-12-11 + 3 NA NA NA NA + g h i + + 1 2015-12-09 10:51:35 + 2 2015-12-09 10:51:36 + 3 NA + Code + options(width = 40) + colonnade(df_all, width = 300) + Output + a b c d e + + 1 1 1 TRUE a a + 2 2.5 2 FALSE b b + 3 NA NA NA + f g + + 1 2015-12-10 2015-12-09 10:51:35 + 2 2015-12-11 2015-12-09 10:51:36 + 3 NA NA + h i + + 1 + 2 + 3 + Code + options(width = 30) + colonnade(df_all, width = 300) + Output + a b c d + + 1 1 1 TRUE a + 2 2.5 2 FALSE b + 3 NA NA NA + e f + + 1 a 2015-12-10 + 2 b 2015-12-11 + 3 NA + g + + 1 2015-12-09 10:51:35 + 2 2015-12-09 10:51:36 + 3 NA + h i + + 1 + 2 + 3 + Code + options(width = 20) + colonnade(df_all, width = 300) + Output + a b c + + 1 1 1 TRUE + 2 2.5 2 FALSE + 3 NA NA NA + d e + + 1 a a + 2 b b + 3 + f + + 1 2015-12-10 + 2 2015-12-11 + 3 NA + g + + 1 2015-12-09 10:51:~ + 2 2015-12-09 10:51:~ + 3 NA + h + + 1 + 2 + 3 + i + + 1 + 2 + 3 + Code + colonnade(list(`\n` = c("\n", "\""), `\r` = factor("\n")), width = 30) + Output + `\n` `\r` + + 1 "\n" "\n" + 2 "\"" "\n" + Code + colonnade(list(a = c("", " ", "a ", " a")), width = 30) + Output + a + + 1 "" + 2 " " + 3 "a " + 4 " a" + Code + colonnade(list(`mean(x)` = 5, `var(x)` = 3), width = 30) + Output + `mean(x)` `var(x)` + + 1 5 3 + +# NA names + + Code + colonnade(x, width = 30) + Output + `NA` + + 1 1 4 + 2 2 5 + 3 3 6 + +# sep argument + + Code + colonnade(x, width = 30) + Output + sep + + 1 1 + 2 2 + 3 3 + Code + # dummy + +# color, options: UTF-8 is TRUE + + Code + crayon::has_color() + Output + [1] TRUE + Code + crayon::num_colors() + Output + [1] 16 + Code + has_color() + Output + [1] TRUE + Code + num_colors() + Output + [1] 16 + Code + style_na("NA") + Output + [1] "\033[31mNA\033[39m" + Code + style_neg("-1") + Output + [1] "\033[31m-1\033[39m" + +--- + + Code + style_na("NA") + Output + [1] "\033[31mNA\033[39m" + +--- + + Code + print(xf) + Output + x +  + 1 -0.001 + 2 0.01 + 3 -0.1 + 4 1 + 5 -10 + 6 100 + 7 -1000 + 8 10000 + 9 NA + Code + with_options(pillar.subtle_num = TRUE, print(xf)) + Output + x +  + 1 -0.001 + 2 0.01 + 3 -0.1 + 4 1 + 5 -10 + 6 100 + 7 -1000 + 8 10000 + 9 NA + Code + with_options(pillar.subtle = FALSE, print(xf)) + Output + x +  + 1 -0.001 + 2 0.01 + 3 -0.1 + 4 1 + 5 -10 + 6 100 + 7 -1000 + 8 10000 + 9 NA + Code + with_options(pillar.neg = FALSE, print(xf)) + Output + x +  + 1 -0.001 + 2 0.01 + 3 -0.1 + 4 1 + 5 -10 + 6 100 + 7 -1000 + 8 10000 + 9 NA + Code + with_options(pillar.subtle = FALSE, pillar.neg = FALSE, print(xf)) + Output + x +  + 1 -0.001 + 2 0.01 + 3 -0.1 + 4 1 + 5 -10 + 6 100 + 7 -1000 + 8 10000 + 9 NA + Code + with_options(pillar.bold = TRUE, print(xf)) + Output + x +  + 1 -0.001 + 2 0.01 + 3 -0.1 + 4 1 + 5 -10 + 6 100 + 7 -1000 + 8 10000 + 9 NA + +--- + + Code + colonnade(list(a_very_long_column_name = 0), width = 15) + Output + a_very_long_… +  + 1 0 + +# color, options: UTF-8 is FALSE + + Code + crayon::has_color() + Output + [1] TRUE + Code + crayon::num_colors() + Output + [1] 16 + Code + has_color() + Output + [1] TRUE + Code + num_colors() + Output + [1] 16 + Code + style_na("NA") + Output + [1] "\033[31mNA\033[39m" + Code + style_neg("-1") + Output + [1] "\033[31m-1\033[39m" + +--- + + Code + style_na("NA") + Output + [1] "\033[31mNA\033[39m" + +--- + + Code + print(xf) + Output + x +  + 1 -0.001 + 2 0.01 + 3 -0.1 + 4 1 + 5 -10 + 6 100 + 7 -1000 + 8 10000 + 9 NA + Code + with_options(pillar.subtle_num = TRUE, print(xf)) + Output + x +  + 1 -0.001 + 2 0.01 + 3 -0.1 + 4 1 + 5 -10 + 6 100 + 7 -1000 + 8 10000 + 9 NA + Code + with_options(pillar.subtle = FALSE, print(xf)) + Output + x +  + 1 -0.001 + 2 0.01 + 3 -0.1 + 4 1 + 5 -10 + 6 100 + 7 -1000 + 8 10000 + 9 NA + Code + with_options(pillar.neg = FALSE, print(xf)) + Output + x +  + 1 -0.001 + 2 0.01 + 3 -0.1 + 4 1 + 5 -10 + 6 100 + 7 -1000 + 8 10000 + 9 NA + Code + with_options(pillar.subtle = FALSE, pillar.neg = FALSE, print(xf)) + Output + x +  + 1 -0.001 + 2 0.01 + 3 -0.1 + 4 1 + 5 -10 + 6 100 + 7 -1000 + 8 10000 + 9 NA + Code + with_options(pillar.bold = TRUE, print(xf)) + Output + x +  + 1 -0.001 + 2 0.01 + 3 -0.1 + 4 1 + 5 -10 + 6 100 + 7 -1000 + 8 10000 + 9 NA + +--- + + Code + colonnade(list(a_very_long_column_name = 0), width = 15) + Output + a_very_long_~ +  + 1 0 + +# sanity check (2) + + Code + crayon::has_color() + Output + [1] FALSE + Code + crayon::num_colors() + Output + [1] 1 + Code + has_color() + Output + [1] FALSE + Code + num_colors() + Output + [1] 1 + Code + style_na("NA") + Output + [1] "NA" + +# tibble columns + + Code + colonnade(x, width = 30) + Output + a b$c $d + + 1 1 4 7 + 2 2 5 8 + 3 3 6 9 + +# tibble columns (nested) + + Code + colonnade(x, width = 40) + Output + a b$c $d $e$f $$g + + 1 1 4 7 10 13 + 2 2 5 8 11 14 + 3 3 6 9 12 15 + +# tibble columns (empty) + + Code + colonnade(x, width = 40) + Output + a b$c $d $e $f + + 1 1 4 7 10 + 2 2 5 8 11 + 3 3 6 9 12 + +# matrix columns (unnamed) + + Code + colonnade(x, width = 30) + Output + a b[,1] [,2] + + 1 1 4 7 + 2 2 5 8 + 3 3 6 9 + +# matrix columns (named) + + Code + colonnade(x, width = 30) + Output + a b[,"c"] [,"d"] + + 1 1 4 7 + 2 2 5 8 + 3 3 6 9 + +# matrix columns (empty) + + Code + colonnade(x, width = 30) + Output + a b c + + 1 1 4 + 2 2 5 + 3 3 6 + diff --git a/tests/testthat/_snaps/format_multi_fuzz.md b/tests/testthat/_snaps/format_multi_fuzz.md new file mode 100644 index 000000000..a98694e4f --- /dev/null +++ b/tests/testthat/_snaps/format_multi_fuzz.md @@ -0,0 +1,918 @@ +# strings with varying widths + + Code + options(width = 59) + colonnade(df_str[c(12L, 33L, 36L, 7L, 41L, 3L, 18L, 23L, 13L, 44L, 14L, 16L, + 25L, 21L, 19L, 45L, 43L, 29L, 1L, 30L, 22L, 27L, 15L, 47L, 28L, 31L, 10L, 50L, + 4L, 40L, 42L, 8L, 6L, 9L, 24L, 48L, 38L, 37L, 34L, 49L, 46L, 2L, 32L, 35L, + 39L, 11L, 17L, 5L, 26L, 20L)], width = 1382) + Output + `12` `33` + + 1 AbcdefghijAb AbcdefghijAbcdefghijAbcdefghijAbc + `36` `7` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdef Abcdefg + `41` `3` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijA Abc + `18` `23` `13` + + 1 AbcdefghijAbcdefgh AbcdefghijAbcdefghijAbc AbcdefghijAbc + `44` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbcd + `14` `16` `25` + + 1 AbcdefghijAbcd AbcdefghijAbcdef AbcdefghijAbcdefghijAbcde + `21` `19` + + 1 AbcdefghijAbcdefghijA AbcdefghijAbcdefghi + `45` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbcde + `43` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbc + `29` `1` + + 1 AbcdefghijAbcdefghijAbcdefghi A + `30` `22` + + 1 AbcdefghijAbcdefghijAbcdefghij AbcdefghijAbcdefghijAb + `27` `15` + + 1 AbcdefghijAbcdefghijAbcdefg AbcdefghijAbcde + `47` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbcdefg + `28` + + 1 AbcdefghijAbcdefghijAbcdefgh + `31` `10` + + 1 AbcdefghijAbcdefghijAbcdefghijA Abcdefghij + `50` `4` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbcdefghij Abcd + `40` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghij + `42` `8` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAb Abcdefgh + `6` `9` `24` + + 1 Abcdef Abcdefghi AbcdefghijAbcdefghijAbcd + `48` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbcdefgh + `38` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefgh + `37` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefg + `34` `49` `46` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcd Abcdefghij~ Abcdefghi~ + `2` `32` `35` `39` `11` `17` `5` `26` `20` + + 1 Ab Abcde~ Abcde~ Abcde~ Abcde~ Abcd~ Abcde Abcd~ Abcd~ + Code + options(width = 54) + colonnade(df_str[c(40L, 28L, 7L, 16L, 48L, 6L, 21L, 1L, 20L, 17L, 47L, 45L, 29L, + 41L, 49L, 34L, 4L, 39L, 18L, 36L, 26L, 38L, 10L, 8L, 5L, 15L, 44L, 24L, 46L, + 14L, 25L, 27L, 3L, 37L, 35L, 12L, 9L, 13L, 22L, 33L, 42L, 11L, 19L, 50L, 23L, + 30L, 32L, 2L, 43L, 31L)], width = 837) + Output + `40` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghij + `28` `7` + + 1 AbcdefghijAbcdefghijAbcdefgh Abcdefg + `16` + + 1 AbcdefghijAbcdef + `48` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbcdefgh + `6` `21` `1` + + 1 Abcdef AbcdefghijAbcdefghijA A + `20` `17` + + 1 AbcdefghijAbcdefghij AbcdefghijAbcdefg + `47` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbcdefg + `45` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbcde + `29` + + 1 AbcdefghijAbcdefghijAbcdefghi + `41` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijA + `49` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbcdefghi + `34` `4` `39` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcd Abcd Abcdefghij~ + `18` `36` `26` `38` `10` `8` `5` `15` + + 1 Abcde~ Abcdef~ Abcde~ Abcde~ Abcd~ Abcd~ Abcde Abcd~ + `44` `24` `46` `14` `25` `27` `3` `37` + + 1 Abcdef~ Abcde~ Abcdef~ Abcd~ Abcd~ Abcd~ Abc Abcd~ + `35` `12` `9` `13` `22` `33` `42` `11` + + 1 Abcdef~ Abcde~ Abcd~ Abcd~ Abcd~ Abcde~ Abcde~ Abcd~ + `19` `50` `23` `30` `32` `2` `43` `31` + + 1 Abcde~ Abcdef~ Abcde~ Abcde~ Abcd~ Ab Abcd~ Abcd~ + Code + options(width = 32) + colonnade(df_str[c(47L, 42L, 4L, 46L, 9L, 34L, 19L, 39L, 8L, 32L, 36L, 12L, 29L, + 5L, 15L, 11L, 31L, 27L, 33L, 28L, 43L, 6L, 13L, 22L, 14L, 16L, 35L, 50L, 38L, + 7L, 23L, 45L, 40L, 3L, 2L, 24L, 41L, 10L, 30L, 25L, 17L, 26L, 48L, 37L, 49L, + 1L, 18L, 21L, 44L, 20L)], width = 455) + Output + `47` + + 1 AbcdefghijAbcdefghijAbcdefghi~ + `42` + + 1 AbcdefghijAbcdefghijAbcdefghi~ + `4` + + 1 Abcd + `46` + + 1 AbcdefghijAbcdefghijAbcdefghi~ + `9` + + 1 Abcdefghi + `34` + + 1 AbcdefghijAbcdefghijAbcdefghi~ + `19` `39` `8` `32` + + 1 Abcdef~ Abcdefg~ Abcd~ Abcdef~ + `36` `12` `29` `5` `15` + + 1 Abcde~ Abcd~ Abcd~ Abcde Abcd~ + `11` `31` `27` `33` `28` + + 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ + `43` `6` `13` `22` `14` + + 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ + `16` `35` `50` `38` `7` + + 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ + `23` `45` `40` `3` `2` + + 1 Abcde~ Abcd~ Abcd~ Abc Ab + `24` `41` `10` `30` `25` + + 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ + `17` `26` `48` `37` `49` + + 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ + `1` `18` `21` `44` `20` + + 1 A Abcde~ Abcd~ Abcd~ Abcd~ + Code + options(width = 55) + colonnade(df_str[c(41L, 4L, 25L, 31L, 8L, 22L, 19L, 10L, 29L, 21L, 34L, 5L, 26L, + 36L, 47L, 46L, 2L, 24L, 27L, 39L, 28L, 43L, 32L, 30L, 48L, 44L, 6L, 20L, 13L, + 15L, 18L, 42L, 9L, 12L, 37L, 45L, 16L, 40L, 11L, 14L, 38L, 1L, 7L, 3L, 23L, + 35L, 50L, 17L, 49L, 33L)], width = 855) + Output + `41` `4` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijA Abcd + `25` + + 1 AbcdefghijAbcdefghijAbcde + `31` `8` + + 1 AbcdefghijAbcdefghijAbcdefghijA Abcdefgh + `22` `19` `10` + + 1 AbcdefghijAbcdefghijAb AbcdefghijAbcdefghi Abcdefghij + `29` `21` + + 1 AbcdefghijAbcdefghijAbcdefghi AbcdefghijAbcdefghijA + `34` `5` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcd Abcde + `26` + + 1 AbcdefghijAbcdefghijAbcdef + `36` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdef + `47` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbcdefg + `46` `2` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbcdef Ab + `24` `27` + + 1 AbcdefghijAbcdefghijAbcd AbcdefghijAbcdefghijAbcdefg + `39` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghi + `28` `43` `32` + + 1 AbcdefghijAbcdefghijAbcdefgh AbcdefghijAb~ Abcdefghi~ + `30` `48` `44` `6` `20` `13` `15` `18` `42` + + 1 Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ + `9` `12` `37` `45` `16` `40` `11` `14` `38` + + 1 Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ + `1` `7` `3` `23` `35` `50` `17` `49` `33` + + 1 A Abcd~ Abc Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ + Code + options(width = 54) + colonnade(df_str[c(27L, 22L, 9L, 23L, 16L, 19L, 25L, 31L, 44L, 1L, 28L, 46L, + 12L, 20L, 43L, 37L, 5L, 2L, 18L, 41L, 26L, 33L, 11L, 49L, 24L, 35L, 4L, 47L, + 30L, 7L, 34L, 3L, 32L, 42L, 10L, 45L, 38L, 39L, 48L, 14L, 6L, 17L, 36L, 50L, + 40L, 13L, 8L, 21L, 15L, 29L)], width = 552) + Output + `27` `22` + + 1 AbcdefghijAbcdefghijAbcdefg AbcdefghijAbcdefghijAb + `9` `23` `16` + + 1 Abcdefghi AbcdefghijAbcdefghijAbc AbcdefghijAbcdef + `19` `25` + + 1 AbcdefghijAbcdefghi AbcdefghijAbcdefghijAbcde + `31` + + 1 AbcdefghijAbcdefghijAbcdefghijA + `44` `1` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbcd A + `28` + + 1 AbcdefghijAbcdefghijAbcdefgh + `46` `12` `20` `43` `37` `5` `2` + + 1 Abcdefgh~ Abcde~ Abcde~ Abcdefg~ Abcdef~ Abcde Ab + `18` `41` `26` `33` `11` `49` `24` `35` + + 1 Abcde~ Abcde~ Abcde~ Abcde~ Abcd~ Abcde~ Abcd~ Abcd~ + `4` `47` `30` `7` `34` `3` `32` `42` + + 1 Abcd Abcdef~ Abcde~ Abcde~ Abcd~ Abc Abcd~ Abcde~ + `10` `45` `38` `39` `48` `14` `6` `17` + + 1 Abcde~ Abcdef~ Abcde~ Abcd~ Abcde~ Abcd~ Abcd~ Abcd~ + `36` `50` `40` `13` `8` `21` `15` `29` + + 1 Abcde~ Abcdef~ Abcdef~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ + Code + options(width = 49) + colonnade(df_str[c(32L, 24L, 18L, 25L, 26L, 13L, 33L, 2L, 50L, 38L, 37L, 16L, + 27L, 9L, 28L, 49L, 34L, 15L, 17L, 35L, 22L, 47L, 3L, 21L, 23L, 41L, 5L, 1L, + 14L, 46L, 30L, 31L, 44L, 4L, 7L, 40L, 43L, 12L, 29L, 8L, 36L, 45L, 11L, 20L, + 10L, 6L, 19L, 48L, 39L, 42L)], width = 1031) + Output + `32` + + 1 AbcdefghijAbcdefghijAbcdefghijAb + `24` `18` + + 1 AbcdefghijAbcdefghijAbcd AbcdefghijAbcdefgh + `25` + + 1 AbcdefghijAbcdefghijAbcde + `26` `13` + + 1 AbcdefghijAbcdefghijAbcdef AbcdefghijAbc + `33` `2` + + 1 AbcdefghijAbcdefghijAbcdefghijAbc Ab + `50` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbcdef~ + `38` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefgh + `37` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefg + `16` `27` + + 1 AbcdefghijAbcdef AbcdefghijAbcdefghijAbcdefg + `9` `28` + + 1 Abcdefghi AbcdefghijAbcdefghijAbcdefgh + `49` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbcdef~ + `34` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcd + `15` `17` + + 1 AbcdefghijAbcde AbcdefghijAbcdefg + `35` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcde + `22` + + 1 AbcdefghijAbcdefghijAb + `47` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbcdefg + `3` `21` + + 1 Abc AbcdefghijAbcdefghijA + `23` + + 1 AbcdefghijAbcdefghijAbc + `41` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijA + `5` `1` `14` `46` `30` `31` `44` `4` + + 1 Abcde A Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd + `7` `40` `43` `12` `29` `8` `36` `45` + + 1 Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ + `11` `20` `10` `6` `19` `48` `39` `42` + + 1 Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ + Code + options(width = 38) + colonnade(df_str[c(44L, 34L, 49L, 9L, 15L, 16L, 1L, 10L, 40L, 29L, 26L, 22L, 4L, + 43L, 20L, 17L, 46L, 33L, 35L, 32L, 2L, 12L, 8L, 37L, 23L, 39L, 7L, 18L, 36L, + 42L, 6L, 30L, 19L, 25L, 5L, 21L, 47L, 50L, 28L, 11L, 31L, 14L, 24L, 27L, 45L, + 41L, 38L, 3L, 13L, 48L)], width = 429) + Output + `44` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcde~ + `34` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcd + `49` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcde~ + `9` `15` + + 1 Abcdefghi AbcdefghijAbcde + `16` `1` `10` + + 1 AbcdefghijAbcdef A Abcdefghij + `40` `29` `26` `22` `4` `43` + + 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd Abcd~ + `20` `17` `46` `33` `35` `32` + + 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ + `2` `12` `8` `37` `23` `39` + + 1 Ab Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ + `7` `18` `36` `42` `6` `30` + + 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ + `19` `25` `5` `21` `47` `50` + + 1 Abcde~ Abcd~ Abcde Abcd~ Abcd~ Abcd~ + `28` `11` `31` `14` `24` `27` + + 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ + `45` `41` `38` `3` `13` `48` + + 1 Abcde~ Abcd~ Abcd~ Abc Abcd~ Abcd~ + Code + options(width = 54) + colonnade(df_str[c(21L, 26L, 8L, 22L, 41L, 24L, 13L, 5L, 47L, 37L, 4L, 42L, 19L, + 34L, 11L, 43L, 38L, 3L, 33L, 20L, 31L, 2L, 18L, 48L, 27L, 44L, 9L, 35L, 30L, + 6L, 49L, 10L, 1L, 16L, 46L, 29L, 12L, 14L, 45L, 36L, 15L, 39L, 50L, 23L, 17L, + 28L, 7L, 32L, 40L, 25L)], width = 633) + Output + `21` `26` + + 1 AbcdefghijAbcdefghijA AbcdefghijAbcdefghijAbcdef + `8` `22` + + 1 Abcdefgh AbcdefghijAbcdefghijAb + `41` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijA + `24` `13` `5` + + 1 AbcdefghijAbcdefghijAbcd AbcdefghijAbc Abcde + `47` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbcdefg + `37` `4` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefg Abcd + `42` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAb + `19` `34` `11` `43` `38` `3` + + 1 AbcdefghijAbcdefghi Abcde~ Abcde~ Abcde~ Abcd~ Abc + `33` `20` `31` `2` `18` `48` `27` `44` + + 1 Abcde~ Abcde~ Abcde~ Ab Abcd~ Abcde~ Abcd~ Abcde~ + `9` `35` `30` `6` `49` `10` `1` `16` + + 1 Abcde~ Abcdef~ Abcde~ Abcd~ Abcde~ Abcd~ A Abcd~ + `46` `29` `12` `14` `45` `36` `15` `39` + + 1 Abcdef~ Abcde~ Abcde~ Abcd~ Abcde~ Abcd~ Abcd~ Abcd~ + `50` `23` `17` `28` `7` `32` `40` `25` + + 1 Abcdef~ Abcde~ Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ + Code + options(width = 39) + colonnade(df_str[c(23L, 49L, 13L, 37L, 3L, 25L, 36L, 4L, 9L, 7L, 27L, 48L, 12L, + 10L, 50L, 14L, 38L, 39L, 46L, 22L, 28L, 8L, 21L, 44L, 32L, 40L, 31L, 1L, 29L, + 34L, 35L, 33L, 19L, 15L, 41L, 20L, 47L, 18L, 16L, 45L, 6L, 5L, 24L, 26L, 43L, + 11L, 42L, 30L, 17L, 2L)], width = 1496) + Output + `23` + + 1 AbcdefghijAbcdefghijAbc + `49` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdef~ + `13` + + 1 AbcdefghijAbc + `37` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefg + `3` `25` + + 1 Abc AbcdefghijAbcdefghijAbcde + `36` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdef + `4` `9` `7` + + 1 Abcd Abcdefghi Abcdefg + `27` + + 1 AbcdefghijAbcdefghijAbcdefg + `48` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdef~ + `12` `10` + + 1 AbcdefghijAb Abcdefghij + `50` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdef~ + `14` + + 1 AbcdefghijAbcd + `38` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdef~ + `39` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdef~ + `46` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdef~ + `22` + + 1 AbcdefghijAbcdefghijAb + `28` `8` + + 1 AbcdefghijAbcdefghijAbcdefgh Abcdefgh + `21` + + 1 AbcdefghijAbcdefghijA + `44` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdef~ + `32` + + 1 AbcdefghijAbcdefghijAbcdefghijAb + `40` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdef~ + `31` `1` + + 1 AbcdefghijAbcdefghijAbcdefghijA A + `29` + + 1 AbcdefghijAbcdefghijAbcdefghi + `34` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcd + `35` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcde + `33` + + 1 AbcdefghijAbcdefghijAbcdefghijAbc + `19` `15` + + 1 AbcdefghijAbcdefghi AbcdefghijAbcde + `41` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdef~ + `20` + + 1 AbcdefghijAbcdefghij + `47` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdef~ + `18` `16` + + 1 AbcdefghijAbcdefgh AbcdefghijAbcdef + `45` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdef~ + `6` `5` `24` + + 1 Abcdef Abcde AbcdefghijAbcdefghijAbcd + `26` + + 1 AbcdefghijAbcdefghijAbcdef + `43` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdef~ + `11` + + 1 AbcdefghijA + `42` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdef~ + `30` + + 1 AbcdefghijAbcdefghijAbcdefghij + `17` `2` + + 1 AbcdefghijAbcdefg Ab + Code + options(width = 31) + colonnade(df_str[c(45L, 14L, 49L, 24L, 22L, 31L, 42L, 18L, 16L, 47L, 25L, 4L, + 37L, 8L, 26L, 21L, 50L, 5L, 41L, 30L, 2L, 33L, 34L, 3L, 44L, 19L, 43L, 6L, + 32L, 29L, 20L, 1L, 13L, 11L, 40L, 12L, 48L, 23L, 9L, 15L, 46L, 36L, 27L, 35L, + 28L, 10L, 7L, 39L, 17L, 38L)], width = 493) + Output + `45` + + 1 AbcdefghijAbcdefghijAbcdefgh~ + `14` + + 1 AbcdefghijAbcd + `49` + + 1 AbcdefghijAbcdefghijAbcdefgh~ + `24` + + 1 AbcdefghijAbcdefghijAbcd + `22` + + 1 AbcdefghijAbcdefghijAb + `31` + + 1 AbcdefghijAbcdefghijAbcdefgh~ + `42` + + 1 AbcdefghijAbcdefghijAbcdefgh~ + `18` `16` `47` + + 1 Abcdefgh~ Abcdef~ Abcdefghij~ + `25` `4` `37` `8` `26` + + 1 Abcd~ Abcd Abcd~ Abcd~ Abcd~ + `21` `50` `5` `41` `30` + + 1 Abcd~ Abcd~ Abcde Abcd~ Abcd~ + `2` `33` `34` `3` `44` + + 1 Ab Abcd~ Abcd~ Abc Abcd~ + `19` `43` `6` `32` `29` + + 1 Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ + `20` `1` `13` `11` `40` + + 1 Abcd~ A Abcd~ Abcd~ Abcd~ + `12` `48` `23` `9` `15` + + 1 Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ + `46` `36` `27` `35` `28` + + 1 Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ + `10` `7` `39` `17` `38` + + 1 Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ + Code + options(width = 52) + colonnade(df_str[c(38L, 46L, 17L, 11L, 24L, 18L, 16L, 39L, 50L, 42L, 6L, 13L, + 37L, 29L, 41L, 47L, 9L, 33L, 44L, 31L, 45L, 36L, 28L, 5L, 10L, 30L, 20L, 1L, + 14L, 43L, 49L, 23L, 26L, 21L, 32L, 19L, 34L, 15L, 48L, 4L, 7L, 35L, 40L, 8L, + 22L, 3L, 25L, 12L, 27L, 2L)], width = 1130) + Output + `38` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefgh + `46` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbcdef + `17` `11` + + 1 AbcdefghijAbcdefg AbcdefghijA + `24` `18` + + 1 AbcdefghijAbcdefghijAbcd AbcdefghijAbcdefgh + `16` + + 1 AbcdefghijAbcdef + `39` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghi + `50` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbcdefghij + `42` `6` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAb Abcdef + `13` + + 1 AbcdefghijAbc + `37` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefg + `29` + + 1 AbcdefghijAbcdefghijAbcdefghi + `41` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijA + `47` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbcdefg + `9` `33` + + 1 Abcdefghi AbcdefghijAbcdefghijAbcdefghijAbc + `44` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbcd + `31` + + 1 AbcdefghijAbcdefghijAbcdefghijA + `45` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbcde + `36` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdef + `28` `5` `10` `30` + + 1 AbcdefghijAbcdefghijAbcdefgh Abcde Abcde~ Abcdefg~ + `20` `1` `14` `43` `49` `23` `26` `21` + + 1 Abcde~ A Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ + `32` `19` `34` `15` `48` `4` `7` `35` + + 1 Abcde~ Abcde~ Abcde~ Abcd~ Abcd~ Abcd Abcd~ Abcd~ + `40` `8` `22` `3` `25` `12` `27` `2` + + 1 Abcdef~ Abcde~ Abcd~ Abc Abcd~ Abcd~ Abcd~ Ab + Code + options(width = 58) + colonnade(df_str[c(17L, 28L, 29L, 27L, 20L, 31L, 43L, 30L, 32L, 48L, 10L, 50L, + 13L, 12L, 36L, 21L, 46L, 33L, 25L, 35L, 1L, 5L, 16L, 34L, 18L, 42L, 3L, 11L, + 40L, 26L, 37L, 7L, 39L, 6L, 4L, 19L, 8L, 45L, 14L, 24L, 23L, 2L, 47L, 9L, 49L, + 41L, 38L, 22L, 44L, 15L)], width = 1310) + Output + `17` `28` + + 1 AbcdefghijAbcdefg AbcdefghijAbcdefghijAbcdefgh + `29` + + 1 AbcdefghijAbcdefghijAbcdefghi + `27` `20` + + 1 AbcdefghijAbcdefghijAbcdefg AbcdefghijAbcdefghij + `31` + + 1 AbcdefghijAbcdefghijAbcdefghijA + `43` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbc + `30` + + 1 AbcdefghijAbcdefghijAbcdefghij + `32` + + 1 AbcdefghijAbcdefghijAbcdefghijAb + `48` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbcdefgh + `10` + + 1 Abcdefghij + `50` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbcdefghij + `13` `12` + + 1 AbcdefghijAbc AbcdefghijAb + `36` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdef + `21` + + 1 AbcdefghijAbcdefghijA + `46` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbcdef + `33` + + 1 AbcdefghijAbcdefghijAbcdefghijAbc + `25` + + 1 AbcdefghijAbcdefghijAbcde + `35` `1` `5` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcde A Abcde + `16` `34` + + 1 AbcdefghijAbcdef AbcdefghijAbcdefghijAbcdefghijAbcd + `18` + + 1 AbcdefghijAbcdefgh + `42` `3` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAb Abc + `11` `40` `26` `37` `7` + + 1 AbcdefghijA AbcdefghijAbc~ Abcdefghi~ AbcdefghijA~ Abcd~ + `39` `6` `4` `19` `8` `45` `14` `24` `23` + + 1 Abcde~ Abcdef Abcd Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ + `2` `47` `9` `49` `41` `38` `22` `44` `15` + + 1 Ab Abcde~ Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ + Code + options(width = 47) + colonnade(df_str[c(1L, 26L, 20L, 12L, 49L, 16L, 24L, 4L, 15L, 47L, 8L, 11L, 14L, + 50L, 17L, 2L, 44L, 30L, 36L, 45L, 25L, 38L, 18L, 29L, 5L, 13L, 3L, 23L, 48L, + 40L, 34L, 22L, 39L, 33L, 27L, 7L, 19L, 10L, 37L, 6L, 35L, 46L, 31L, 41L, 43L, + 28L, 42L, 32L, 21L, 9L)], width = 484) + Output + `1` `26` + + 1 A AbcdefghijAbcdefghijAbcdef + `20` `12` + + 1 AbcdefghijAbcdefghij AbcdefghijAb + `49` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbcd~ + `16` `24` + + 1 AbcdefghijAbcdef AbcdefghijAbcdefghijAbcd + `4` + + 1 Abcd + `15` `47` `8` `11` `14` `50` `17` + + 1 Abcde~ Abcdef~ Abcd~ Abcd~ Abcd~ Abcde~ Abcd~ + `2` `44` `30` `36` `45` `25` `38` + + 1 Ab Abcde~ Abcde~ Abcde~ Abcde~ Abcd~ Abcd~ + `18` `29` `5` `13` `3` `23` `48` + + 1 Abcde~ Abcde~ Abcde Abcde~ Abc Abcd~ Abcde~ + `40` `34` `22` `39` `33` `27` `7` + + 1 Abcde~ Abcde~ Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ + `19` `10` `37` `6` `35` `46` `31` + + 1 Abcde~ Abcde~ Abcde~ Abcd~ Abcd~ Abcde~ Abcd~ + `41` `43` `28` `42` `32` `21` `9` + + 1 Abcde~ Abcde~ Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ + Code + options(width = 55) + colonnade(df_str[c(6L, 49L, 26L, 45L, 25L, 15L, 31L, 20L, 21L, 44L, 23L, 48L, + 37L, 36L, 5L, 43L, 11L, 14L, 13L, 39L, 16L, 12L, 4L, 18L, 42L, 3L, 10L, 28L, + 40L, 24L, 29L, 17L, 35L, 47L, 2L, 38L, 34L, 9L, 7L, 8L, 50L, 33L, 32L, 27L, + 46L, 19L, 22L, 41L, 30L, 1L)], width = 779) + Output + `6` + + 1 Abcdef + `49` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbcdefghi + `26` + + 1 AbcdefghijAbcdefghijAbcdef + `45` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbcde + `25` `15` + + 1 AbcdefghijAbcdefghijAbcde AbcdefghijAbcde + `31` `20` + + 1 AbcdefghijAbcdefghijAbcdefghijA AbcdefghijAbcdefghij + `21` + + 1 AbcdefghijAbcdefghijA + `44` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbcd + `23` + + 1 AbcdefghijAbcdefghijAbc + `48` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbcdefgh + `37` `36` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefg AbcdefghijAbcd~ + `5` `43` `11` `14` `13` `39` `16` `12` `4` + + 1 Abcde Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd + `18` `42` `3` `10` `28` `40` `24` `29` `17` + + 1 Abcd~ Abcd~ Abc Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ + `35` `47` `2` `38` `34` `9` `7` `8` `50` + + 1 Abcd~ Abcd~ Ab Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ + `33` `32` `27` `46` `19` `22` `41` `30` `1` + + 1 Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ A + Code + options(width = 46) + colonnade(df_str[c(38L, 42L, 41L, 10L, 40L, 11L, 27L, 9L, 17L, 37L, 46L, 13L, + 36L, 18L, 31L, 20L, 39L, 12L, 44L, 33L, 50L, 34L, 26L, 32L, 23L, 30L, 29L, + 21L, 4L, 49L, 19L, 25L, 3L, 6L, 15L, 14L, 43L, 48L, 8L, 22L, 1L, 2L, 45L, 35L, + 16L, 5L, 47L, 28L, 24L, 7L)], width = 694) + Output + `38` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefgh + `42` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAb + `41` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijA + `10` + + 1 Abcdefghij + `40` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghij + `11` `27` + + 1 AbcdefghijA AbcdefghijAbcdefghijAbcdefg + `9` `17` + + 1 Abcdefghi AbcdefghijAbcdefg + `37` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefg + `46` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbc~ + `13` + + 1 AbcdefghijAbc + `36` `18` `31` + + 1 AbcdefghijAbcdef~ Abcdefghi~ AbcdefghijAbcd~ + `20` `39` `12` `44` `33` `50` `34` + + 1 Abcde~ Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ + `26` `32` `23` `30` `29` `21` `4` + + 1 Abcde~ Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ Abcd + `49` `19` `25` `3` `6` `15` `14` + + 1 Abcdef~ Abcde~ Abcd~ Abc Abcd~ Abcd~ Abcd~ + `43` `48` `8` `22` `1` `2` `45` + + 1 Abcde~ Abcde~ Abcde~ Abcd~ A Ab Abcd~ + `35` `16` `5` `47` `28` `24` `7` + + 1 Abcde~ Abcde~ Abcde Abcde~ Abcd~ Abcd~ Abcd~ + diff --git a/tests/testthat/_snaps/format_multi_fuzz_2.md b/tests/testthat/_snaps/format_multi_fuzz_2.md new file mode 100644 index 000000000..13aa139d9 --- /dev/null +++ b/tests/testthat/_snaps/format_multi_fuzz_2.md @@ -0,0 +1,1161 @@ +# strings with varying widths + + Code + options(width = 54) + colonnade(df_str[c(28L, 34L, 16L, 29L, 47L, 25L, 42L, 27L, 44L, 20L, 14L, 36L, + 43L, 41L, 26L, 45L, 22L, 9L, 13L, 32L, 31L, 12L, 19L, 48L, 49L, 35L, 3L, 11L, + 23L, 24L, 40L, 15L, 38L, 10L, 46L, 5L, 50L, 18L, 21L, 6L, 30L, 2L, 7L, 1L, 4L, + 8L, 17L, 33L, 39L, 37L)], width = 516) + Output + `28` + + 1 AbcdefghijAbcdefghijAbcdefgh + `34` `16` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcd AbcdefghijAbcdef + `29` + + 1 AbcdefghijAbcdefghijAbcdefghi + `47` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbcdefg + `25` `42` `27` `44` `20` + + 1 AbcdefghijAbcdefghijAbcde Abcde~ Abcde~ Abcde~ Abcd~ + `14` `36` `43` `41` `26` `45` `22` `9` + + 1 Abcde~ Abcde~ Abcde~ Abcde~ Abcd~ Abcde~ Abcd~ Abcd~ + `13` `32` `31` `12` `19` `48` `49` `35` + + 1 Abcde~ Abcde~ Abcde~ Abcd~ Abcd~ Abcde~ Abcde~ Abcd~ + `3` `11` `23` `24` `40` `15` `38` `10` + + 1 Abc Abcde~ Abcde~ Abcde~ Abcde~ Abcd~ Abcde~ Abcd~ + `46` `5` `50` `18` `21` `6` `30` `2` + + 1 Abcdef~ Abcde Abcdef~ Abcde~ Abcd~ Abcd~ Abcd~ Ab + `7` `1` `4` `8` `17` `33` `39` `37` + + 1 Abcde~ A Abcd Abcde~ Abcd~ Abcde~ Abcde~ Abcde~ + Code + options(width = 42) + colonnade(df_str[c(28L, 41L, 12L, 29L, 13L, 43L, 24L, 50L, 48L, 35L, 44L, 21L, + 33L, 45L, 47L, 34L, 25L, 14L, 18L, 23L, 7L, 3L, 42L, 36L, 11L, 2L, 20L, 31L, + 1L, 4L, 38L, 9L, 27L, 40L, 32L, 17L, 6L, 49L, 16L, 19L, 15L, 22L, 39L, 10L, + 46L, 5L, 30L, 8L, 26L, 37L)], width = 1365) + Output + `28` + + 1 AbcdefghijAbcdefghijAbcdefgh + `41` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghi~ + `12` + + 1 AbcdefghijAb + `29` + + 1 AbcdefghijAbcdefghijAbcdefghi + `13` + + 1 AbcdefghijAbc + `43` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghi~ + `24` + + 1 AbcdefghijAbcdefghijAbcd + `50` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghi~ + `48` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghi~ + `35` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcde + `44` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghi~ + `21` + + 1 AbcdefghijAbcdefghijA + `33` + + 1 AbcdefghijAbcdefghijAbcdefghijAbc + `45` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghi~ + `47` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghi~ + `34` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcd + `25` `14` + + 1 AbcdefghijAbcdefghijAbcde AbcdefghijAbcd + `18` + + 1 AbcdefghijAbcdefgh + `23` `7` `3` + + 1 AbcdefghijAbcdefghijAbc Abcdefg Abc + `42` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghi~ + `36` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdef + `11` `2` `20` + + 1 AbcdefghijA Ab AbcdefghijAbcdefghij + `31` `1` + + 1 AbcdefghijAbcdefghijAbcdefghijA A + `4` + + 1 Abcd + `38` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefgh + `9` `27` + + 1 Abcdefghi AbcdefghijAbcdefghijAbcdefg + `40` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghij + `32` + + 1 AbcdefghijAbcdefghijAbcdefghijAb + `17` `6` + + 1 AbcdefghijAbcdefg Abcdef + `49` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghi~ + `16` `19` + + 1 AbcdefghijAbcdef AbcdefghijAbcdefghi + `15` `22` `39` `10` + + 1 AbcdefghijAbcde Abcdefg~ Abcdefgh~ Abcd~ + `46` `5` `30` `8` `26` `37` + + 1 Abcdef~ Abcde Abcdef~ Abcd~ Abcd~ Abcde~ + Code + options(width = 39) + colonnade(df_str[c(40L, 17L, 13L, 23L, 22L, 2L, 18L, 3L, 29L, 45L, 14L, 19L, + 33L, 37L, 47L, 43L, 44L, 10L, 31L, 27L, 34L, 35L, 41L, 21L, 4L, 25L, 38L, 48L, + 9L, 24L, 26L, 39L, 20L, 36L, 42L, 16L, 6L, 11L, 7L, 12L, 1L, 46L, 15L, 5L, 8L, + 50L, 32L, 30L, 49L, 28L)], width = 934) + Output + `40` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdef~ + `17` `13` + + 1 AbcdefghijAbcdefg AbcdefghijAbc + `23` + + 1 AbcdefghijAbcdefghijAbc + `22` `2` + + 1 AbcdefghijAbcdefghijAb Ab + `18` `3` + + 1 AbcdefghijAbcdefgh Abc + `29` + + 1 AbcdefghijAbcdefghijAbcdefghi + `45` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdef~ + `14` `19` + + 1 AbcdefghijAbcd AbcdefghijAbcdefghi + `33` + + 1 AbcdefghijAbcdefghijAbcdefghijAbc + `37` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefg + `47` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdef~ + `43` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdef~ + `44` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdef~ + `10` + + 1 Abcdefghij + `31` + + 1 AbcdefghijAbcdefghijAbcdefghijA + `27` + + 1 AbcdefghijAbcdefghijAbcdefg + `34` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcd + `35` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcde + `41` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdef~ + `21` `4` `25` + + 1 AbcdefghijAbcdefghijA Abcd Abcdefgh~ + `38` `48` `9` `24` `26` `39` + + 1 Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ + `20` `36` `42` `16` `6` `11` + + 1 Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ + `7` `12` `1` `46` `15` `5` + + 1 Abcde~ Abcd~ A Abcde~ Abcd~ Abcde + `8` `50` `32` `30` `49` `28` + + 1 Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ + Code + options(width = 32) + colonnade(df_str[c(11L, 36L, 17L, 14L, 31L, 35L, 23L, 13L, 6L, 44L, 45L, 22L, + 21L, 18L, 33L, 10L, 43L, 2L, 46L, 34L, 3L, 19L, 1L, 38L, 9L, 37L, 5L, 8L, 25L, + 49L, 27L, 29L, 15L, 39L, 24L, 40L, 48L, 26L, 47L, 42L, 41L, 12L, 28L, 30L, 7L, + 16L, 4L, 50L, 20L, 32L)], width = 565) + Output + `11` + + 1 AbcdefghijA + `36` + + 1 AbcdefghijAbcdefghijAbcdefghi~ + `17` + + 1 AbcdefghijAbcdefg + `14` + + 1 AbcdefghijAbcd + `31` + + 1 AbcdefghijAbcdefghijAbcdefghi~ + `35` + + 1 AbcdefghijAbcdefghijAbcdefghi~ + `23` + + 1 AbcdefghijAbcdefghijAbc + `13` `6` + + 1 AbcdefghijAbc Abcdef + `44` + + 1 AbcdefghijAbcdefghijAbcdefghi~ + `45` + + 1 AbcdefghijAbcdefghijAbcdefghi~ + `22` `21` `18` `33` + + 1 Abcdef~ Abcdef~ Abcde~ Abcdef~ + `10` `43` `2` `46` `34` + + 1 Abcde~ Abcd~ Ab Abcd~ Abcd~ + `3` `19` `1` `38` `9` + + 1 Abc Abcde~ A Abcd~ Abcd~ + `37` `5` `8` `25` `49` + + 1 Abcde~ Abcde Abcd~ Abcd~ Abcd~ + `27` `29` `15` `39` `24` + + 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ + `40` `48` `26` `47` `42` + + 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ + `41` `12` `28` `30` `7` + + 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ + `16` `4` `50` `20` `32` + + 1 Abcde~ Abcd Abcd~ Abcd~ Abcd~ + Code + options(width = 35) + colonnade(df_str[c(18L, 46L, 11L, 43L, 31L, 47L, 48L, 44L, 50L, 15L, 28L, 33L, + 13L, 4L, 22L, 3L, 37L, 32L, 40L, 9L, 25L, 16L, 45L, 23L, 21L, 6L, 49L, 36L, + 27L, 38L, 14L, 34L, 8L, 24L, 29L, 1L, 12L, 2L, 20L, 17L, 35L, 5L, 19L, 30L, + 7L, 26L, 42L, 41L, 39L, 10L)], width = 1121) + Output + `18` + + 1 AbcdefghijAbcdefgh + `46` + + 1 AbcdefghijAbcdefghijAbcdefghijAb~ + `11` + + 1 AbcdefghijA + `43` + + 1 AbcdefghijAbcdefghijAbcdefghijAb~ + `31` + + 1 AbcdefghijAbcdefghijAbcdefghijA + `47` + + 1 AbcdefghijAbcdefghijAbcdefghijAb~ + `48` + + 1 AbcdefghijAbcdefghijAbcdefghijAb~ + `44` + + 1 AbcdefghijAbcdefghijAbcdefghijAb~ + `50` + + 1 AbcdefghijAbcdefghijAbcdefghijAb~ + `15` + + 1 AbcdefghijAbcde + `28` + + 1 AbcdefghijAbcdefghijAbcdefgh + `33` + + 1 AbcdefghijAbcdefghijAbcdefghijAbc + `13` `4` + + 1 AbcdefghijAbc Abcd + `22` `3` + + 1 AbcdefghijAbcdefghijAb Abc + `37` + + 1 AbcdefghijAbcdefghijAbcdefghijAb~ + `32` + + 1 AbcdefghijAbcdefghijAbcdefghijAb + `40` + + 1 AbcdefghijAbcdefghijAbcdefghijAb~ + `9` + + 1 Abcdefghi + `25` + + 1 AbcdefghijAbcdefghijAbcde + `16` + + 1 AbcdefghijAbcdef + `45` + + 1 AbcdefghijAbcdefghijAbcdefghijAb~ + `23` + + 1 AbcdefghijAbcdefghijAbc + `21` `6` + + 1 AbcdefghijAbcdefghijA Abcdef + `49` + + 1 AbcdefghijAbcdefghijAbcdefghijAb~ + `36` + + 1 AbcdefghijAbcdefghijAbcdefghijAb~ + `27` + + 1 AbcdefghijAbcdefghijAbcdefg + `38` + + 1 AbcdefghijAbcdefghijAbcdefghijAb~ + `14` + + 1 AbcdefghijAbcd + `34` + + 1 AbcdefghijAbcdefghijAbcdefghijAb~ + `8` `24` `29` + + 1 Abcdefgh Abcdefghij~ AbcdefghijA~ + `1` `12` `2` `20` `17` + + 1 A Abcde~ Ab Abcdef~ Abcde~ + `35` `5` `19` `30` `7` + + 1 Abcdef~ Abcde Abcde~ Abcde~ Abcd~ + `26` `42` `41` `39` `10` + + 1 Abcde~ Abcde~ Abcde~ Abcde~ Abcd~ + Code + options(width = 32) + colonnade(df_str[c(43L, 1L, 3L, 15L, 28L, 12L, 46L, 34L, 31L, 7L, 11L, 4L, 44L, + 8L, 9L, 5L, 36L, 22L, 17L, 39L, 18L, 45L, 37L, 13L, 29L, 6L, 30L, 16L, 20L, + 10L, 19L, 26L, 33L, 40L, 35L, 48L, 38L, 25L, 2L, 47L, 42L, 41L, 27L, 14L, 21L, + 24L, 50L, 49L, 23L, 32L)], width = 446) + Output + `43` + + 1 AbcdefghijAbcdefghijAbcdefghi~ + `1` `3` `15` + + 1 A Abc AbcdefghijAbcde + `28` + + 1 AbcdefghijAbcdefghijAbcdefgh + `12` + + 1 AbcdefghijAb + `46` + + 1 AbcdefghijAbcdefghijAbcdefghi~ + `34` `31` `7` + + 1 AbcdefghijA~ Abcdefghij~ Abcd~ + `11` `4` `44` `8` `9` + + 1 Abcde~ Abcd Abcd~ Abcd~ Abcd~ + `5` `36` `22` `17` `39` + + 1 Abcde Abcde~ Abcd~ Abcd~ Abcd~ + `18` `45` `37` `13` `29` + + 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ + `6` `30` `16` `20` `10` + + 1 Abcdef Abcd~ Abcd~ Abcd~ Abcd~ + `19` `26` `33` `40` `35` + + 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ + `48` `38` `25` `2` `47` + + 1 Abcde~ Abcd~ Abcd~ Ab Abcd~ + `42` `41` `27` `14` `21` + + 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ + `24` `50` `49` `23` `32` + + 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ + Code + options(width = 31) + colonnade(df_str[c(37L, 46L, 21L, 3L, 16L, 39L, 34L, 33L, 10L, 17L, 19L, 36L, + 45L, 49L, 11L, 50L, 14L, 29L, 44L, 13L, 30L, 38L, 32L, 40L, 42L, 1L, 31L, 41L, + 7L, 23L, 35L, 28L, 6L, 25L, 2L, 9L, 12L, 15L, 5L, 18L, 20L, 27L, 43L, 8L, 47L, + 4L, 48L, 24L, 26L, 22L)], width = 1166) + Output + `37` + + 1 AbcdefghijAbcdefghijAbcdefgh~ + `46` + + 1 AbcdefghijAbcdefghijAbcdefgh~ + `21` `3` + + 1 AbcdefghijAbcdefghijA Abc + `16` + + 1 AbcdefghijAbcdef + `39` + + 1 AbcdefghijAbcdefghijAbcdefgh~ + `34` + + 1 AbcdefghijAbcdefghijAbcdefgh~ + `33` + + 1 AbcdefghijAbcdefghijAbcdefgh~ + `10` `17` + + 1 Abcdefghij AbcdefghijAbcdefg + `19` + + 1 AbcdefghijAbcdefghi + `36` + + 1 AbcdefghijAbcdefghijAbcdefgh~ + `45` + + 1 AbcdefghijAbcdefghijAbcdefgh~ + `49` + + 1 AbcdefghijAbcdefghijAbcdefgh~ + `11` + + 1 AbcdefghijA + `50` + + 1 AbcdefghijAbcdefghijAbcdefgh~ + `14` + + 1 AbcdefghijAbcd + `29` + + 1 AbcdefghijAbcdefghijAbcdefghi + `44` + + 1 AbcdefghijAbcdefghijAbcdefgh~ + `13` + + 1 AbcdefghijAbc + `30` + + 1 AbcdefghijAbcdefghijAbcdefgh~ + `38` + + 1 AbcdefghijAbcdefghijAbcdefgh~ + `32` + + 1 AbcdefghijAbcdefghijAbcdefgh~ + `40` + + 1 AbcdefghijAbcdefghijAbcdefgh~ + `42` + + 1 AbcdefghijAbcdefghijAbcdefgh~ + `1` + + 1 A + `31` + + 1 AbcdefghijAbcdefghijAbcdefgh~ + `41` + + 1 AbcdefghijAbcdefghijAbcdefgh~ + `7` + + 1 Abcdefg + `23` + + 1 AbcdefghijAbcdefghijAbc + `35` + + 1 AbcdefghijAbcdefghijAbcdefgh~ + `28` + + 1 AbcdefghijAbcdefghijAbcdefgh + `6` + + 1 Abcdef + `25` + + 1 AbcdefghijAbcdefghijAbcde + `2` `9` `12` + + 1 Ab Abcdefghi AbcdefghijAb + `15` `5` + + 1 AbcdefghijAbcde Abcde + `18` + + 1 AbcdefghijAbcdefgh + `20` + + 1 AbcdefghijAbcdefghij + `27` `43` `8` `47` + + 1 Abcdef~ Abcdef~ Abcde~ Abcde~ + `4` `48` `24` `26` `22` + + 1 Abcd Abcd~ Abcd~ Abcd~ Abcd~ + Code + options(width = 58) + colonnade(df_str[c(31L, 39L, 40L, 30L, 10L, 21L, 9L, 16L, 46L, 25L, 15L, 24L, + 3L, 50L, 35L, 1L, 12L, 34L, 48L, 4L, 29L, 23L, 37L, 36L, 28L, 43L, 11L, 17L, + 32L, 8L, 41L, 13L, 44L, 7L, 38L, 26L, 33L, 20L, 19L, 2L, 18L, 49L, 27L, 47L, + 22L, 14L, 6L, 5L, 45L, 42L)], width = 546) + Output + `31` + + 1 AbcdefghijAbcdefghijAbcdefghijA + `39` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghi + `40` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghij + `30` `10` + + 1 AbcdefghijAbcdefghijAbcdefghij Abcdefghij + `21` `9` `16` + + 1 AbcdefghijAbcdefghijA Abcdefghi AbcdefghijAbcdef + `46` `25` `15` `24` `3` `50` + + 1 AbcdefghijA~ Abcdefgh~ Abcde~ Abcdef~ Abc AbcdefghijA~ + `35` `1` `12` `34` `48` `4` `29` `23` `37` + + 1 Abcde~ A Abcde~ Abcde~ Abcd~ Abcd Abcd~ Abcd~ Abcd~ + `36` `28` `43` `11` `17` `32` `8` `41` `13` + + 1 Abcde~ Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ + `44` `7` `38` `26` `33` `20` `19` `2` `18` + + 1 Abcde~ Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ Ab Abcd~ + `49` `27` `47` `22` `14` `6` `5` `45` `42` + + 1 Abcde~ Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ Abcde Abcd~ Abcd~ + Code + options(width = 57) + colonnade(df_str[c(43L, 21L, 41L, 48L, 22L, 25L, 2L, 8L, 1L, 24L, 6L, 39L, 38L, + 20L, 49L, 45L, 47L, 12L, 9L, 13L, 36L, 26L, 44L, 11L, 46L, 28L, 7L, 18L, 50L, + 16L, 29L, 30L, 4L, 23L, 17L, 40L, 33L, 14L, 27L, 19L, 34L, 32L, 3L, 37L, 15L, + 10L, 5L, 35L, 31L, 42L)], width = 1035) + Output + `43` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbc + `21` + + 1 AbcdefghijAbcdefghijA + `41` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijA + `48` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbcdefgh + `22` `25` `2` + + 1 AbcdefghijAbcdefghijAb AbcdefghijAbcdefghijAbcde Ab + `8` `1` `24` `6` + + 1 Abcdefgh A AbcdefghijAbcdefghijAbcd Abcdef + `39` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghi + `38` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefgh + `20` + + 1 AbcdefghijAbcdefghij + `49` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbcdefghi + `45` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbcde + `47` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbcdefg + `12` `9` `13` + + 1 AbcdefghijAb Abcdefghi AbcdefghijAbc + `36` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdef + `26` + + 1 AbcdefghijAbcdefghijAbcdef + `44` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbcd + `11` `46` `28` `7` `18` `50` `16` `29` `30` + + 1 Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ + `4` `23` `17` `40` `33` `14` `27` `19` `34` + + 1 Abcd Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ + `32` `3` `37` `15` `10` `5` `35` `31` `42` + + 1 Abcde~ Abc Abcde~ Abcd~ Abcd~ Abcde Abcd~ Abcd~ Abcd~ + Code + options(width = 33) + colonnade(df_str[c(40L, 6L, 25L, 5L, 26L, 17L, 19L, 2L, 11L, 34L, 45L, 24L, 22L, + 44L, 35L, 7L, 4L, 49L, 1L, 36L, 12L, 41L, 39L, 13L, 48L, 27L, 18L, 30L, 42L, + 28L, 3L, 46L, 21L, 20L, 16L, 29L, 50L, 10L, 9L, 8L, 47L, 31L, 14L, 38L, 33L, + 32L, 43L, 23L, 15L, 37L)], width = 1217) + Output + `40` + + 1 AbcdefghijAbcdefghijAbcdefghij~ + `6` + + 1 Abcdef + `25` `5` + + 1 AbcdefghijAbcdefghijAbcde Abcde + `26` + + 1 AbcdefghijAbcdefghijAbcdef + `17` + + 1 AbcdefghijAbcdefg + `19` `2` + + 1 AbcdefghijAbcdefghi Ab + `11` + + 1 AbcdefghijA + `34` + + 1 AbcdefghijAbcdefghijAbcdefghij~ + `45` + + 1 AbcdefghijAbcdefghijAbcdefghij~ + `24` + + 1 AbcdefghijAbcdefghijAbcd + `22` + + 1 AbcdefghijAbcdefghijAb + `44` + + 1 AbcdefghijAbcdefghijAbcdefghij~ + `35` + + 1 AbcdefghijAbcdefghijAbcdefghij~ + `7` `4` + + 1 Abcdefg Abcd + `49` + + 1 AbcdefghijAbcdefghijAbcdefghij~ + `1` + + 1 A + `36` + + 1 AbcdefghijAbcdefghijAbcdefghij~ + `12` + + 1 AbcdefghijAb + `41` + + 1 AbcdefghijAbcdefghijAbcdefghij~ + `39` + + 1 AbcdefghijAbcdefghijAbcdefghij~ + `13` + + 1 AbcdefghijAbc + `48` + + 1 AbcdefghijAbcdefghijAbcdefghij~ + `27` + + 1 AbcdefghijAbcdefghijAbcdefg + `18` + + 1 AbcdefghijAbcdefgh + `30` + + 1 AbcdefghijAbcdefghijAbcdefghij + `42` + + 1 AbcdefghijAbcdefghijAbcdefghij~ + `28` + + 1 AbcdefghijAbcdefghijAbcdefgh + `3` + + 1 Abc + `46` + + 1 AbcdefghijAbcdefghijAbcdefghij~ + `21` + + 1 AbcdefghijAbcdefghijA + `20` + + 1 AbcdefghijAbcdefghij + `16` + + 1 AbcdefghijAbcdef + `29` + + 1 AbcdefghijAbcdefghijAbcdefghi + `50` + + 1 AbcdefghijAbcdefghijAbcdefghij~ + `10` `9` `8` + + 1 Abcdefghij Abcdefghi Abcdefgh + `47` `31` `14` `38` `33` + + 1 Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ + `32` `43` `23` `15` `37` + + 1 Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ + Code + options(width = 32) + colonnade(df_str[c(43L, 23L, 22L, 11L, 6L, 26L, 48L, 17L, 7L, 42L, 36L, 21L, + 35L, 50L, 13L, 19L, 29L, 8L, 15L, 4L, 2L, 27L, 49L, 47L, 30L, 31L, 25L, 28L, + 46L, 12L, 32L, 39L, 24L, 10L, 45L, 5L, 37L, 14L, 40L, 20L, 41L, 44L, 33L, 18L, + 38L, 3L, 1L, 34L, 16L, 9L)], width = 770) + Output + `43` + + 1 AbcdefghijAbcdefghijAbcdefghi~ + `23` + + 1 AbcdefghijAbcdefghijAbc + `22` + + 1 AbcdefghijAbcdefghijAb + `11` `6` + + 1 AbcdefghijA Abcdef + `26` + + 1 AbcdefghijAbcdefghijAbcdef + `48` + + 1 AbcdefghijAbcdefghijAbcdefghi~ + `17` `7` + + 1 AbcdefghijAbcdefg Abcdefg + `42` + + 1 AbcdefghijAbcdefghijAbcdefghi~ + `36` + + 1 AbcdefghijAbcdefghijAbcdefghi~ + `21` + + 1 AbcdefghijAbcdefghijA + `35` + + 1 AbcdefghijAbcdefghijAbcdefghi~ + `50` + + 1 AbcdefghijAbcdefghijAbcdefghi~ + `13` + + 1 AbcdefghijAbc + `19` + + 1 AbcdefghijAbcdefghi + `29` + + 1 AbcdefghijAbcdefghijAbcdefghi + `8` `15` `4` + + 1 Abcdefgh AbcdefghijAbcde Abcd + `2` + + 1 Ab + `27` + + 1 AbcdefghijAbcdefghijAbcdefg + `49` + + 1 AbcdefghijAbcdefghijAbcdefghi~ + `47` `30` + + 1 AbcdefghijAbcd~ AbcdefghijAbc~ + `31` `25` `28` `46` `12` + + 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ + `32` `39` `24` `10` `45` + + 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ + `5` `37` `14` `40` `20` + + 1 Abcde Abcde~ Abcd~ Abcd~ Abcd~ + `41` `44` `33` `18` `38` + + 1 Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ + `3` `1` `34` `16` `9` + + 1 Abc A Abcde~ Abcd~ Abcd~ + Code + options(width = 46) + colonnade(df_str[c(5L, 24L, 43L, 46L, 35L, 39L, 18L, 26L, 8L, 27L, 2L, 50L, 6L, + 14L, 29L, 47L, 9L, 16L, 36L, 4L, 13L, 41L, 3L, 28L, 37L, 33L, 38L, 31L, 34L, + 19L, 42L, 32L, 1L, 45L, 15L, 7L, 11L, 49L, 23L, 12L, 48L, 20L, 21L, 44L, 25L, + 10L, 22L, 30L, 40L, 17L)], width = 1439) + Output + `5` `24` + + 1 Abcde AbcdefghijAbcdefghijAbcd + `43` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbc + `46` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbc~ + `35` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcde + `39` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghi + `18` + + 1 AbcdefghijAbcdefgh + `26` `8` + + 1 AbcdefghijAbcdefghijAbcdef Abcdefgh + `27` `2` + + 1 AbcdefghijAbcdefghijAbcdefg Ab + `50` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbc~ + `6` `14` + + 1 Abcdef AbcdefghijAbcd + `29` + + 1 AbcdefghijAbcdefghijAbcdefghi + `47` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbc~ + `9` `16` + + 1 Abcdefghi AbcdefghijAbcdef + `36` `4` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdef Abcd + `13` + + 1 AbcdefghijAbc + `41` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijA + `3` `28` + + 1 Abc AbcdefghijAbcdefghijAbcdefgh + `37` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefg + `33` + + 1 AbcdefghijAbcdefghijAbcdefghijAbc + `38` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefgh + `31` + + 1 AbcdefghijAbcdefghijAbcdefghijA + `34` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcd + `19` + + 1 AbcdefghijAbcdefghi + `42` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAb + `32` `1` + + 1 AbcdefghijAbcdefghijAbcdefghijAb A + `45` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbc~ + `15` `7` `11` + + 1 AbcdefghijAbcde Abcdefg AbcdefghijA + `49` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbc~ + `23` `12` + + 1 AbcdefghijAbcdefghijAbc AbcdefghijAb + `48` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbc~ + `20` `21` + + 1 AbcdefghijAbcdefghij AbcdefghijAbcdefghijA + `44` `25` `10` `22` `30` `40` `17` + + 1 Abcde~ Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ + Code + options(width = 52) + colonnade(df_str[c(7L, 44L, 19L, 21L, 18L, 35L, 23L, 50L, 33L, 37L, 25L, 26L, + 10L, 39L, 2L, 47L, 42L, 14L, 9L, 41L, 45L, 6L, 4L, 11L, 24L, 43L, 32L, 3L, + 38L, 5L, 49L, 27L, 17L, 8L, 22L, 40L, 12L, 15L, 1L, 28L, 31L, 29L, 13L, 48L, + 34L, 36L, 30L, 20L, 16L, 46L)], width = 1065) + Output + `7` + + 1 Abcdefg + `44` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbcd + `19` `21` + + 1 AbcdefghijAbcdefghi AbcdefghijAbcdefghijA + `18` + + 1 AbcdefghijAbcdefgh + `35` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcde + `23` + + 1 AbcdefghijAbcdefghijAbc + `50` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbcdefghij + `33` + + 1 AbcdefghijAbcdefghijAbcdefghijAbc + `37` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefg + `25` + + 1 AbcdefghijAbcdefghijAbcde + `26` `10` + + 1 AbcdefghijAbcdefghijAbcdef Abcdefghij + `39` `2` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghi Ab + `47` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbcdefg + `42` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAb + `14` `9` + + 1 AbcdefghijAbcd Abcdefghi + `41` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijA + `45` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghijAbcde + `6` `4` `11` `24` `43` + + 1 Abcdef Abcd AbcdefghijA Abcdefghi~ AbcdefghijAbc~ + `32` `3` `38` `5` `49` `27` `17` `8` + + 1 Abcde~ Abc Abcde~ Abcde Abcde~ Abcd~ Abcd~ Abcd~ + `22` `40` `12` `15` `1` `28` `31` `29` + + 1 Abcde~ Abcde~ Abcde~ Abcd~ A Abcd~ Abcd~ Abcd~ + `13` `48` `34` `36` `30` `20` `16` `46` + + 1 Abcde~ Abcde~ Abcde~ Abcd~ Abcd~ Abcd~ Abcd~ Abcd~ + Code + options(width = 35) + colonnade(df_str[c(38L, 18L, 23L, 36L, 35L, 20L, 44L, 19L, 13L, 41L, 31L, 7L, + 11L, 29L, 2L, 14L, 26L, 46L, 40L, 45L, 9L, 34L, 33L, 22L, 1L, 17L, 28L, 10L, + 21L, 30L, 47L, 49L, 6L, 12L, 4L, 25L, 32L, 15L, 43L, 24L, 48L, 3L, 37L, 50L, + 42L, 39L, 16L, 8L, 27L, 5L)], width = 393) + Output + `38` + + 1 AbcdefghijAbcdefghijAbcdefghijAb~ + `18` + + 1 AbcdefghijAbcdefgh + `23` `36` `35` + + 1 Abcdefgh~ Abcdefghij~ Abcdefghij~ + `20` `44` `19` `13` `41` + + 1 Abcde~ Abcdef~ Abcd~ Abcd~ Abcde~ + `31` `7` `11` `29` `2` + + 1 Abcdef~ Abcde~ Abcd~ Abcde~ Ab + `14` `26` `46` `40` `45` + + 1 Abcde~ Abcde~ Abcde~ Abcde~ Abcd~ + `9` `34` `33` `22` `1` + + 1 Abcde~ Abcdef~ Abcde~ Abcd~ A + `17` `28` `10` `21` `30` + + 1 Abcde~ Abcdef~ Abcd~ Abcd~ Abcde~ + `47` `49` `6` `12` `4` + + 1 Abcdef~ Abcdef~ Abcd~ Abcd~ Abcd + `25` `32` `15` `43` `24` + + 1 Abcde~ Abcdef~ Abcd~ Abcde~ Abcd~ + `48` `3` `37` `50` `42` + + 1 Abcde~ Abc Abcde~ Abcde~ Abcde~ + `39` `16` `8` `27` `5` + + 1 Abcdef~ Abcde~ Abcd~ Abcde~ Abcde + Code + options(width = 41) + colonnade(df_str[c(22L, 9L, 11L, 26L, 19L, 16L, 32L, 25L, 1L, 30L, 31L, 6L, 24L, + 10L, 39L, 21L, 50L, 7L, 29L, 12L, 46L, 43L, 15L, 35L, 20L, 40L, 49L, 38L, 36L, + 48L, 34L, 3L, 8L, 4L, 27L, 42L, 44L, 33L, 45L, 18L, 5L, 2L, 13L, 47L, 28L, + 17L, 37L, 14L, 41L, 23L)], width = 999) + Output + `22` `9` + + 1 AbcdefghijAbcdefghijAb Abcdefghi + `11` `26` + + 1 AbcdefghijA AbcdefghijAbcdefghijAbcdef + `19` `16` + + 1 AbcdefghijAbcdefghi AbcdefghijAbcdef + `32` + + 1 AbcdefghijAbcdefghijAbcdefghijAb + `25` `1` + + 1 AbcdefghijAbcdefghijAbcde A + `30` + + 1 AbcdefghijAbcdefghijAbcdefghij + `31` `6` + + 1 AbcdefghijAbcdefghijAbcdefghijA Abcdef + `24` `10` + + 1 AbcdefghijAbcdefghijAbcd Abcdefghij + `39` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefghi + `21` + + 1 AbcdefghijAbcdefghijA + `50` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefgh~ + `7` `29` + + 1 Abcdefg AbcdefghijAbcdefghijAbcdefghi + `12` + + 1 AbcdefghijAb + `46` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefgh~ + `43` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefgh~ + `15` + + 1 AbcdefghijAbcde + `35` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcde + `20` + + 1 AbcdefghijAbcdefghij + `40` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefgh~ + `49` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefgh~ + `38` + + 1 AbcdefghijAbcdefghijAbcdefghijAbcdefgh + `36` `48` `34` `3` + + 1 Abcdefghij~ Abcdefghij~ Abcdefgh~ Abc + `8` `4` `27` `42` `44` `33` + + 1 Abcde~ Abcd Abcde~ Abcde~ Abcde~ Abcd~ + `45` `18` `5` `2` `13` `47` + + 1 Abcdef~ Abcde~ Abcde Ab Abcd~ Abcde~ + `28` `17` `37` `14` `41` `23` + + 1 Abcde~ Abcde~ Abcde~ Abcd~ Abcde~ Abcd~ + diff --git a/tests/testthat/_snaps/zzx-format_character.md b/tests/testthat/_snaps/zzx-format_character.md new file mode 100644 index 000000000..9ffcef8c6 --- /dev/null +++ b/tests/testthat/_snaps/zzx-format_character.md @@ -0,0 +1,23 @@ +# output test (not on Windows) + + Code + colonnade(chartype_frame(), width = 50) + Output + chars desc + + 1 "\u0001\u001f" C0 control code + 2 "\a\b\f\n\r\t" Named control code + 3 "abcdefuvwxyz" ASCII + 4 "\u0080\u009f" C1 control code + 5 " ¡¢£¤¥úûüýþÿ" Latin-1 + 6 "ĀāĂ㥹ĆćĈĉĊċ" Unicode + 7 "!"#$%&" Unicode wide + 8 "\u0e00\u2029" Unicode control + 9 "x­x​x‌x‍x‎x‏x͏xx󠀁x󠀠x󠇯x" Unicode ignorable + 10 "àáâãāa̅ăȧäảåa̋" Unicode mark + 11 "😀😁😂😃😄💃" Emoji + 12 "x\U0010ffffx" Unassigned + 13 "\xfd\xfe\xff" Invalid + 14 "\\" Backslash + 15 "\"" Quote + diff --git a/tests/testthat/test-format_multi.R b/tests/testthat/test-format_multi.R index cf4eca383..258b96b86 100644 --- a/tests/testthat/test-format_multi.R +++ b/tests/testthat/test-format_multi.R @@ -12,3 +12,270 @@ test_that("sanity check (1)", { style_na("NA") }) }) + +test_that("output test", { + x <- list( + column_zero_one = 1:3 + 0.23, + col_02 = letters[1:3], + col_03 = factor(letters[1:3]), + col_04 = ordered(letters[1:3]) + ) + expect_snapshot({ + colonnade(x, width = 4) + colonnade(x, width = 5) + colonnade(x, width = 6) + colonnade(x, width = 7) + colonnade(x, width = 8) + colonnade(x, width = 9) + colonnade(x, width = 10) + colonnade(x, width = 11) + colonnade(x, width = 12) + colonnade(x, width = 13) + colonnade(x, width = 14) + colonnade(x, width = 15) + colonnade(x, width = 16) + colonnade(x, width = 17) + colonnade(x, width = 18) + colonnade(x, width = 19) + colonnade(x, width = 20) + colonnade(x, width = 21) + colonnade(x, width = 22) + colonnade(x, width = 23) + colonnade(x, width = 24) + colonnade(x, width = 25) + colonnade(x, width = 26) + colonnade(x, width = 27) + colonnade(x, width = 28) + colonnade(x, width = 29) + colonnade(x, width = 30) + colonnade(x, width = 31) + colonnade(x, width = 32) + colonnade(x, width = 33) + colonnade(x, width = 34) + colonnade(x, width = 35) + colonnade(x, width = 36) + colonnade(x, width = 37) + colonnade(x, width = 38) + colonnade(x, width = 39) + colonnade(x, width = Inf) + }) + + expect_snapshot({ + colonnade(rep(list(paste(letters, collapse = " ")), 4), width = Inf) + }) + + # Spurious warnings on Windows + suppressWarnings( + expect_snapshot({ + new_vertical(extra_cols_impl(squeeze_impl(colonnade(x), width = 10))) + }) + ) + + suppressWarnings( + expect_snapshot({ + new_vertical(extra_cols_impl(squeeze_impl(colonnade(x), width = 20))) + }) + ) + + suppressWarnings( + expect_snapshot({ + new_vertical(extra_cols_impl(squeeze_impl(colonnade(x), width = 30))) + }) + ) + + suppressWarnings( + expect_snapshot({ + new_vertical(extra_cols_impl(squeeze_impl(colonnade(x), width = 35))) + }) + ) + + expect_snapshot({ + new_vertical(extra_cols_impl(squeeze_impl(colonnade(x), width = 40))) + }) +}) + +test_that("tests from tibble", { + skip_if_not_installed("rlang", "0.4.11.9000") + local_options(width = 80) + + expect_snapshot({ + colonnade(mtcars[1:8, ], has_row_id = "*", width = 30) + colonnade(iris[1:5, ], width = 30) + colonnade(iris[1:3, ], width = 20) + colonnade(df_all, width = 30) + colonnade(df_all, width = 300) + options(width = 70) + colonnade(df_all, width = 300) + options(width = 60) + colonnade(df_all, width = 300) + options(width = 50) + colonnade(df_all, width = 300) + options(width = 40) + colonnade(df_all, width = 300) + options(width = 30) + colonnade(df_all, width = 300) + options(width = 20) + colonnade(df_all, width = 300) + colonnade(list(`\n` = c("\n", '"'), `\r` = factor("\n")), width = 30) + colonnade(list(a = c("", " ", "a ", " a")), width = 30) + colonnade(list("mean(x)" = 5, "var(x)" = 3), width = 30) + }) +}) + +test_that("empty", { + expect_equal( + format(colonnade(list(a = character(), b = logical()), width = 30)), + structure(character(), class = "pillar_vertical") + ) + expect_equal( + format(colonnade(iris[1:5, character()], width = 30)), + structure(character(), class = "pillar_vertical") + ) +}) + +test_that("NA names", { + x <- list(`NA` = 1:3, set_to_NA = 4:6) + names(x)[[2]] <- NA_character_ + expect_snapshot({ + colonnade(x, width = 30) + }) +}) + +test_that("sep argument", { + x <- list(sep = 1:3) + expect_snapshot({ + colonnade(x, width = 30) + "dummy" + }) +}) + +# Run opposite test to snapshot output but not alter it +if (!l10n_info()$`UTF-8`) { + test_that("color, options: UTF-8 is TRUE", { + skip("Symmetry") + }) +} + +test_that(paste0("color, options: UTF-8 is ", l10n_info()$`UTF-8`), { + local_colors() + expect_true(crayon::has_color()) + expect_equal(crayon::num_colors(), 16) + expect_true(has_color()) + expect_equal(num_colors(), 16) + + if (l10n_info()$`UTF-8`) { + local_utf8() + expect_true(cli::is_utf8_output()) + } + + expect_snapshot({ + crayon::has_color() + crayon::num_colors() + has_color() + num_colors() + style_na("NA") + style_neg("-1") + }) + + expect_snapshot({ + style_na("NA") + }) + + xf <- colonnade(list(x = c((10^(-3:4)) * c(-1, 1), NA))) + + expect_snapshot({ + print(xf) + with_options(pillar.subtle_num = TRUE, print(xf)) + with_options(pillar.subtle = FALSE, print(xf)) + with_options(pillar.neg = FALSE, print(xf)) + with_options(pillar.subtle = FALSE, pillar.neg = FALSE, print(xf)) + with_options(pillar.bold = TRUE, print(xf)) + }) + + expect_snapshot({ + colonnade(list(a_very_long_column_name = 0), width = 15) + }) +}) + +# Run opposite test to snapshot output but not alter it +if (l10n_info()$`UTF-8`) { + test_that("color, options: UTF-8 is FALSE", { + skip("Symmetry") + }) +} + +test_that("sanity check (2)", { + expect_false(crayon::has_color()) + expect_equal(crayon::num_colors(), 1) + expect_false(has_color()) + expect_equal(num_colors(), 1) + + expect_snapshot({ + crayon::has_color() + crayon::num_colors() + has_color() + num_colors() + style_na("NA") + }) +}) + +test_that("tibble columns", { + x <- list(a = 1:3, b = data.frame(c = 4:6, d = 7:9)) + expect_snapshot({ + colonnade(x, width = 30) + }) +}) + +test_that("tibble columns (nested)", { + x <- list( + a = 1:3, + b = structure( + list( + c = 4:6, d = 7:9, + e = data.frame(f = 10:12, g = 13:15) + ), + class = "data.frame" + ) + ) + expect_snapshot({ + colonnade(x, width = 40) + }) +}) + +test_that("tibble columns (empty)", { + x <- list( + a = 1:3, + b = structure( + list( + c = 4:6, d = 7:9, + e = data.frame(f = 10:12)[, 0], + f = 10:12 + ), + class = "data.frame" + ) + ) + expect_snapshot({ + colonnade(x, width = 40) + }) +}) + +test_that("matrix columns (unnamed)", { + x <- list(a = 1:3, b = matrix(4:9, ncol = 2)) + expect_snapshot({ + colonnade(x, width = 30) + }) +}) + +test_that("matrix columns (named)", { + x <- list(a = 1:3, b = matrix(4:9, ncol = 2, dimnames = list(NULL, c("c", "d")))) + expect_snapshot({ + colonnade(x, width = 30) + }) +}) + +test_that("matrix columns (empty)", { + x <- list(a = 1:3, b = matrix(4:6, ncol = 1)[, 0], c = 4:6) + expect_snapshot({ + colonnade(x, width = 30) + }) +}) diff --git a/tests/testthat/test-format_multi_fuzz.R b/tests/testthat/test-format_multi_fuzz.R new file mode 100644 index 000000000..e5b55054c --- /dev/null +++ b/tests/testthat/test-format_multi_fuzz.R @@ -0,0 +1,39 @@ +test_that("strings with varying widths", { + local_options(width = 80) + + # Generated by data-raw/create-chr-tests.R + # nolint start + expect_snapshot({ + options(width = 59) + colonnade(df_str[c(12L, 33L, 36L, 7L, 41L, 3L, 18L, 23L, 13L, 44L, 14L, 16L, 25L, 21L, 19L, 45L, 43L, 29L, 1L, 30L, 22L, 27L, 15L, 47L, 28L, 31L, 10L, 50L, 4L, 40L, 42L, 8L, 6L, 9L, 24L, 48L, 38L, 37L, 34L, 49L, 46L, 2L, 32L, 35L, 39L, 11L, 17L, 5L, 26L, 20L)], width = 1382) + options(width = 54) + colonnade(df_str[c(40L, 28L, 7L, 16L, 48L, 6L, 21L, 1L, 20L, 17L, 47L, 45L, 29L, 41L, 49L, 34L, 4L, 39L, 18L, 36L, 26L, 38L, 10L, 8L, 5L, 15L, 44L, 24L, 46L, 14L, 25L, 27L, 3L, 37L, 35L, 12L, 9L, 13L, 22L, 33L, 42L, 11L, 19L, 50L, 23L, 30L, 32L, 2L, 43L, 31L)], width = 837) + options(width = 32) + colonnade(df_str[c(47L, 42L, 4L, 46L, 9L, 34L, 19L, 39L, 8L, 32L, 36L, 12L, 29L, 5L, 15L, 11L, 31L, 27L, 33L, 28L, 43L, 6L, 13L, 22L, 14L, 16L, 35L, 50L, 38L, 7L, 23L, 45L, 40L, 3L, 2L, 24L, 41L, 10L, 30L, 25L, 17L, 26L, 48L, 37L, 49L, 1L, 18L, 21L, 44L, 20L)], width = 455) + options(width = 55) + colonnade(df_str[c(41L, 4L, 25L, 31L, 8L, 22L, 19L, 10L, 29L, 21L, 34L, 5L, 26L, 36L, 47L, 46L, 2L, 24L, 27L, 39L, 28L, 43L, 32L, 30L, 48L, 44L, 6L, 20L, 13L, 15L, 18L, 42L, 9L, 12L, 37L, 45L, 16L, 40L, 11L, 14L, 38L, 1L, 7L, 3L, 23L, 35L, 50L, 17L, 49L, 33L)], width = 855) + options(width = 54) + colonnade(df_str[c(27L, 22L, 9L, 23L, 16L, 19L, 25L, 31L, 44L, 1L, 28L, 46L, 12L, 20L, 43L, 37L, 5L, 2L, 18L, 41L, 26L, 33L, 11L, 49L, 24L, 35L, 4L, 47L, 30L, 7L, 34L, 3L, 32L, 42L, 10L, 45L, 38L, 39L, 48L, 14L, 6L, 17L, 36L, 50L, 40L, 13L, 8L, 21L, 15L, 29L)], width = 552) + options(width = 49) + colonnade(df_str[c(32L, 24L, 18L, 25L, 26L, 13L, 33L, 2L, 50L, 38L, 37L, 16L, 27L, 9L, 28L, 49L, 34L, 15L, 17L, 35L, 22L, 47L, 3L, 21L, 23L, 41L, 5L, 1L, 14L, 46L, 30L, 31L, 44L, 4L, 7L, 40L, 43L, 12L, 29L, 8L, 36L, 45L, 11L, 20L, 10L, 6L, 19L, 48L, 39L, 42L)], width = 1031) + options(width = 38) + colonnade(df_str[c(44L, 34L, 49L, 9L, 15L, 16L, 1L, 10L, 40L, 29L, 26L, 22L, 4L, 43L, 20L, 17L, 46L, 33L, 35L, 32L, 2L, 12L, 8L, 37L, 23L, 39L, 7L, 18L, 36L, 42L, 6L, 30L, 19L, 25L, 5L, 21L, 47L, 50L, 28L, 11L, 31L, 14L, 24L, 27L, 45L, 41L, 38L, 3L, 13L, 48L)], width = 429) + options(width = 54) + colonnade(df_str[c(21L, 26L, 8L, 22L, 41L, 24L, 13L, 5L, 47L, 37L, 4L, 42L, 19L, 34L, 11L, 43L, 38L, 3L, 33L, 20L, 31L, 2L, 18L, 48L, 27L, 44L, 9L, 35L, 30L, 6L, 49L, 10L, 1L, 16L, 46L, 29L, 12L, 14L, 45L, 36L, 15L, 39L, 50L, 23L, 17L, 28L, 7L, 32L, 40L, 25L)], width = 633) + options(width = 39) + colonnade(df_str[c(23L, 49L, 13L, 37L, 3L, 25L, 36L, 4L, 9L, 7L, 27L, 48L, 12L, 10L, 50L, 14L, 38L, 39L, 46L, 22L, 28L, 8L, 21L, 44L, 32L, 40L, 31L, 1L, 29L, 34L, 35L, 33L, 19L, 15L, 41L, 20L, 47L, 18L, 16L, 45L, 6L, 5L, 24L, 26L, 43L, 11L, 42L, 30L, 17L, 2L)], width = 1496) + options(width = 31) + colonnade(df_str[c(45L, 14L, 49L, 24L, 22L, 31L, 42L, 18L, 16L, 47L, 25L, 4L, 37L, 8L, 26L, 21L, 50L, 5L, 41L, 30L, 2L, 33L, 34L, 3L, 44L, 19L, 43L, 6L, 32L, 29L, 20L, 1L, 13L, 11L, 40L, 12L, 48L, 23L, 9L, 15L, 46L, 36L, 27L, 35L, 28L, 10L, 7L, 39L, 17L, 38L)], width = 493) + options(width = 52) + colonnade(df_str[c(38L, 46L, 17L, 11L, 24L, 18L, 16L, 39L, 50L, 42L, 6L, 13L, 37L, 29L, 41L, 47L, 9L, 33L, 44L, 31L, 45L, 36L, 28L, 5L, 10L, 30L, 20L, 1L, 14L, 43L, 49L, 23L, 26L, 21L, 32L, 19L, 34L, 15L, 48L, 4L, 7L, 35L, 40L, 8L, 22L, 3L, 25L, 12L, 27L, 2L)], width = 1130) + options(width = 58) + colonnade(df_str[c(17L, 28L, 29L, 27L, 20L, 31L, 43L, 30L, 32L, 48L, 10L, 50L, 13L, 12L, 36L, 21L, 46L, 33L, 25L, 35L, 1L, 5L, 16L, 34L, 18L, 42L, 3L, 11L, 40L, 26L, 37L, 7L, 39L, 6L, 4L, 19L, 8L, 45L, 14L, 24L, 23L, 2L, 47L, 9L, 49L, 41L, 38L, 22L, 44L, 15L)], width = 1310) + options(width = 47) + colonnade(df_str[c(1L, 26L, 20L, 12L, 49L, 16L, 24L, 4L, 15L, 47L, 8L, 11L, 14L, 50L, 17L, 2L, 44L, 30L, 36L, 45L, 25L, 38L, 18L, 29L, 5L, 13L, 3L, 23L, 48L, 40L, 34L, 22L, 39L, 33L, 27L, 7L, 19L, 10L, 37L, 6L, 35L, 46L, 31L, 41L, 43L, 28L, 42L, 32L, 21L, 9L)], width = 484) + options(width = 55) + colonnade(df_str[c(6L, 49L, 26L, 45L, 25L, 15L, 31L, 20L, 21L, 44L, 23L, 48L, 37L, 36L, 5L, 43L, 11L, 14L, 13L, 39L, 16L, 12L, 4L, 18L, 42L, 3L, 10L, 28L, 40L, 24L, 29L, 17L, 35L, 47L, 2L, 38L, 34L, 9L, 7L, 8L, 50L, 33L, 32L, 27L, 46L, 19L, 22L, 41L, 30L, 1L)], width = 779) + options(width = 46) + colonnade(df_str[c(38L, 42L, 41L, 10L, 40L, 11L, 27L, 9L, 17L, 37L, 46L, 13L, 36L, 18L, 31L, 20L, 39L, 12L, 44L, 33L, 50L, 34L, 26L, 32L, 23L, 30L, 29L, 21L, 4L, 49L, 19L, 25L, 3L, 6L, 15L, 14L, 43L, 48L, 8L, 22L, 1L, 2L, 45L, 35L, 16L, 5L, 47L, 28L, 24L, 7L)], width = 694) + }) + # nolint end +}) diff --git a/tests/testthat/test-format_multi_fuzz_2.R b/tests/testthat/test-format_multi_fuzz_2.R new file mode 100644 index 000000000..01e9aa0a0 --- /dev/null +++ b/tests/testthat/test-format_multi_fuzz_2.R @@ -0,0 +1,39 @@ +test_that("strings with varying widths", { + local_options(width = 80) + + # Generated by data-raw/create-chr-tests.R + # nolint start + expect_snapshot({ + options(width = 54) + colonnade(df_str[c(28L, 34L, 16L, 29L, 47L, 25L, 42L, 27L, 44L, 20L, 14L, 36L, 43L, 41L, 26L, 45L, 22L, 9L, 13L, 32L, 31L, 12L, 19L, 48L, 49L, 35L, 3L, 11L, 23L, 24L, 40L, 15L, 38L, 10L, 46L, 5L, 50L, 18L, 21L, 6L, 30L, 2L, 7L, 1L, 4L, 8L, 17L, 33L, 39L, 37L)], width = 516) + options(width = 42) + colonnade(df_str[c(28L, 41L, 12L, 29L, 13L, 43L, 24L, 50L, 48L, 35L, 44L, 21L, 33L, 45L, 47L, 34L, 25L, 14L, 18L, 23L, 7L, 3L, 42L, 36L, 11L, 2L, 20L, 31L, 1L, 4L, 38L, 9L, 27L, 40L, 32L, 17L, 6L, 49L, 16L, 19L, 15L, 22L, 39L, 10L, 46L, 5L, 30L, 8L, 26L, 37L)], width = 1365) + options(width = 39) + colonnade(df_str[c(40L, 17L, 13L, 23L, 22L, 2L, 18L, 3L, 29L, 45L, 14L, 19L, 33L, 37L, 47L, 43L, 44L, 10L, 31L, 27L, 34L, 35L, 41L, 21L, 4L, 25L, 38L, 48L, 9L, 24L, 26L, 39L, 20L, 36L, 42L, 16L, 6L, 11L, 7L, 12L, 1L, 46L, 15L, 5L, 8L, 50L, 32L, 30L, 49L, 28L)], width = 934) + options(width = 32) + colonnade(df_str[c(11L, 36L, 17L, 14L, 31L, 35L, 23L, 13L, 6L, 44L, 45L, 22L, 21L, 18L, 33L, 10L, 43L, 2L, 46L, 34L, 3L, 19L, 1L, 38L, 9L, 37L, 5L, 8L, 25L, 49L, 27L, 29L, 15L, 39L, 24L, 40L, 48L, 26L, 47L, 42L, 41L, 12L, 28L, 30L, 7L, 16L, 4L, 50L, 20L, 32L)], width = 565) + options(width = 35) + colonnade(df_str[c(18L, 46L, 11L, 43L, 31L, 47L, 48L, 44L, 50L, 15L, 28L, 33L, 13L, 4L, 22L, 3L, 37L, 32L, 40L, 9L, 25L, 16L, 45L, 23L, 21L, 6L, 49L, 36L, 27L, 38L, 14L, 34L, 8L, 24L, 29L, 1L, 12L, 2L, 20L, 17L, 35L, 5L, 19L, 30L, 7L, 26L, 42L, 41L, 39L, 10L)], width = 1121) + options(width = 32) + colonnade(df_str[c(43L, 1L, 3L, 15L, 28L, 12L, 46L, 34L, 31L, 7L, 11L, 4L, 44L, 8L, 9L, 5L, 36L, 22L, 17L, 39L, 18L, 45L, 37L, 13L, 29L, 6L, 30L, 16L, 20L, 10L, 19L, 26L, 33L, 40L, 35L, 48L, 38L, 25L, 2L, 47L, 42L, 41L, 27L, 14L, 21L, 24L, 50L, 49L, 23L, 32L)], width = 446) + options(width = 31) + colonnade(df_str[c(37L, 46L, 21L, 3L, 16L, 39L, 34L, 33L, 10L, 17L, 19L, 36L, 45L, 49L, 11L, 50L, 14L, 29L, 44L, 13L, 30L, 38L, 32L, 40L, 42L, 1L, 31L, 41L, 7L, 23L, 35L, 28L, 6L, 25L, 2L, 9L, 12L, 15L, 5L, 18L, 20L, 27L, 43L, 8L, 47L, 4L, 48L, 24L, 26L, 22L)], width = 1166) + options(width = 58) + colonnade(df_str[c(31L, 39L, 40L, 30L, 10L, 21L, 9L, 16L, 46L, 25L, 15L, 24L, 3L, 50L, 35L, 1L, 12L, 34L, 48L, 4L, 29L, 23L, 37L, 36L, 28L, 43L, 11L, 17L, 32L, 8L, 41L, 13L, 44L, 7L, 38L, 26L, 33L, 20L, 19L, 2L, 18L, 49L, 27L, 47L, 22L, 14L, 6L, 5L, 45L, 42L)], width = 546) + options(width = 57) + colonnade(df_str[c(43L, 21L, 41L, 48L, 22L, 25L, 2L, 8L, 1L, 24L, 6L, 39L, 38L, 20L, 49L, 45L, 47L, 12L, 9L, 13L, 36L, 26L, 44L, 11L, 46L, 28L, 7L, 18L, 50L, 16L, 29L, 30L, 4L, 23L, 17L, 40L, 33L, 14L, 27L, 19L, 34L, 32L, 3L, 37L, 15L, 10L, 5L, 35L, 31L, 42L)], width = 1035) + options(width = 33) + colonnade(df_str[c(40L, 6L, 25L, 5L, 26L, 17L, 19L, 2L, 11L, 34L, 45L, 24L, 22L, 44L, 35L, 7L, 4L, 49L, 1L, 36L, 12L, 41L, 39L, 13L, 48L, 27L, 18L, 30L, 42L, 28L, 3L, 46L, 21L, 20L, 16L, 29L, 50L, 10L, 9L, 8L, 47L, 31L, 14L, 38L, 33L, 32L, 43L, 23L, 15L, 37L)], width = 1217) + options(width = 32) + colonnade(df_str[c(43L, 23L, 22L, 11L, 6L, 26L, 48L, 17L, 7L, 42L, 36L, 21L, 35L, 50L, 13L, 19L, 29L, 8L, 15L, 4L, 2L, 27L, 49L, 47L, 30L, 31L, 25L, 28L, 46L, 12L, 32L, 39L, 24L, 10L, 45L, 5L, 37L, 14L, 40L, 20L, 41L, 44L, 33L, 18L, 38L, 3L, 1L, 34L, 16L, 9L)], width = 770) + options(width = 46) + colonnade(df_str[c(5L, 24L, 43L, 46L, 35L, 39L, 18L, 26L, 8L, 27L, 2L, 50L, 6L, 14L, 29L, 47L, 9L, 16L, 36L, 4L, 13L, 41L, 3L, 28L, 37L, 33L, 38L, 31L, 34L, 19L, 42L, 32L, 1L, 45L, 15L, 7L, 11L, 49L, 23L, 12L, 48L, 20L, 21L, 44L, 25L, 10L, 22L, 30L, 40L, 17L)], width = 1439) + options(width = 52) + colonnade(df_str[c(7L, 44L, 19L, 21L, 18L, 35L, 23L, 50L, 33L, 37L, 25L, 26L, 10L, 39L, 2L, 47L, 42L, 14L, 9L, 41L, 45L, 6L, 4L, 11L, 24L, 43L, 32L, 3L, 38L, 5L, 49L, 27L, 17L, 8L, 22L, 40L, 12L, 15L, 1L, 28L, 31L, 29L, 13L, 48L, 34L, 36L, 30L, 20L, 16L, 46L)], width = 1065) + options(width = 35) + colonnade(df_str[c(38L, 18L, 23L, 36L, 35L, 20L, 44L, 19L, 13L, 41L, 31L, 7L, 11L, 29L, 2L, 14L, 26L, 46L, 40L, 45L, 9L, 34L, 33L, 22L, 1L, 17L, 28L, 10L, 21L, 30L, 47L, 49L, 6L, 12L, 4L, 25L, 32L, 15L, 43L, 24L, 48L, 3L, 37L, 50L, 42L, 39L, 16L, 8L, 27L, 5L)], width = 393) + options(width = 41) + colonnade(df_str[c(22L, 9L, 11L, 26L, 19L, 16L, 32L, 25L, 1L, 30L, 31L, 6L, 24L, 10L, 39L, 21L, 50L, 7L, 29L, 12L, 46L, 43L, 15L, 35L, 20L, 40L, 49L, 38L, 36L, 48L, 34L, 3L, 8L, 4L, 27L, 42L, 44L, 33L, 45L, 18L, 5L, 2L, 13L, 47L, 28L, 17L, 37L, 14L, 41L, 23L)], width = 999) + }) + # nolint end +}) diff --git a/tests/testthat/test-zzx-format_character.R b/tests/testthat/test-zzx-format_character.R index 00b408bde..8bd33d73b 100644 --- a/tests/testthat/test-zzx-format_character.R +++ b/tests/testthat/test-zzx-format_character.R @@ -68,3 +68,13 @@ chartype_frame <- function() { data.frame(chars, desc, stringsAsFactors = FALSE) } + +test_that("output test (not on Windows)", { + skip_on_os("windows") + # Spurious warnings on Windows + suppressWarnings( + expect_snapshot({ + colonnade(chartype_frame(), width = 50) + }) + ) +}) From 068d4a4dbf07cfeb9f103b0b95ced5b1e8b3ff55 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Mon, 18 Oct 2021 22:08:10 +0200 Subject: [PATCH 145/147] Tweak NEWS --- NEWS.md | 1 - 1 file changed, 1 deletion(-) diff --git a/NEWS.md b/NEWS.md index 4bc83e567..355d486bc 100644 --- a/NEWS.md +++ b/NEWS.md @@ -9,7 +9,6 @@ ## Breaking changes -- `colonnade()` no longer exists, `squeeze()` and `extra_cols()` now raise an error (#272). - `num()` requires an integerish `digits` argument (#362). ## Documentation From 857915966751c85570a3bfc9db4ba26aff3ae6a8 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Mon, 25 Oct 2021 04:34:03 +0200 Subject: [PATCH 146/147] Sync changes --- - Mention main branch in all workflows - Run dev workflow on tags - Run dev workflow on Ubuntu 20.04 --- .github/workflows/R-CMD-check-dev.yaml | 10 ++++++---- .github/workflows/revdep.yaml | 2 +- 2 files changed, 7 insertions(+), 5 deletions(-) diff --git a/.github/workflows/R-CMD-check-dev.yaml b/.github/workflows/R-CMD-check-dev.yaml index 36c91df42..a819e0b3f 100644 --- a/.github/workflows/R-CMD-check-dev.yaml +++ b/.github/workflows/R-CMD-check-dev.yaml @@ -2,16 +2,18 @@ # Can't be run as part of commits on: schedule: - - cron: '5 0 * * *' + - cron: '5 0 * * *' # only run on main branch push: branches: - "cran-*" + tags: + - "v*" name: rcc dev jobs: matrix: - runs-on: ubuntu-18.04 + runs-on: ubuntu-20.04 outputs: matrix: ${{ steps.set-matrix.outputs.matrix }} @@ -235,8 +237,8 @@ jobs: uses: actions/cache@v2 with: path: ${{ env.R_LIBS_USER }} - key: ubuntu-18.04-r-dev-release-${{ matrix.package }}-1-${{steps.date.outputs.date}} - restore-keys: ubuntu-18.04-r-dev-release-${{ matrix.package }}-1- + key: ubuntu-20.04-r-dev-release-${{ matrix.package }}-1-${{steps.date.outputs.date}} + restore-keys: ubuntu-20.04-r-dev-release-${{ matrix.package }}-1- - name: Install system dependencies if: runner.os == 'Linux' diff --git a/.github/workflows/revdep.yaml b/.github/workflows/revdep.yaml index 628cba17b..a4b063fe0 100644 --- a/.github/workflows/revdep.yaml +++ b/.github/workflows/revdep.yaml @@ -2,7 +2,7 @@ on: push: branches: - - "revdep*" + - "revdep*" # never run automatically on main branch name: revdep From 810470a4996dc4b20ed45ed5791d60fd22c97e91 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Kirill=20M=C3=BCller?= Date: Mon, 25 Oct 2021 05:44:16 +0200 Subject: [PATCH 147/147] TODO --- TODO.md | 19 +++++++++++++++++-- 1 file changed, 17 insertions(+), 2 deletions(-) diff --git a/TODO.md b/TODO.md index 3850d0278..3cbb70221 100644 --- a/TODO.md +++ b/TODO.md @@ -8,27 +8,40 @@ - CRAN release - triage issues +- documentation cleanup from : + - relink digits vignette, shorten numbers vignette, replace ?num, ?char and print.tbl() with internal stubs +- expand list columns - revdepcheck for adding ellipsis to methods - Focus columns at their native position, with ... or subtle vertical pipe inbetween (1 char wide) + - Easiest if focus columns are moved to the beginning - Get extra width? - Breaking changes - Wide character + list column: why does the character column take up all the space? - `tibble(a = strrep("1234567890", 100), b = list(tibble(a = letters)))` + - Because the minimum character width is used here; this is just the default shaft. We can show only the type if there's lack of space and build a custom pillar shaft + - Abbreviate list columns at the left? - Redundant information goes up into the header - call `type_sum()` on the pillar shaft -- if it returns `NULL` (as in the default method) call it on the vector - Search for `new_pillar_type()` - Maybe it's easier to recompute in `type_sum()` and `vec_ptype_abbr()` - not sure, problems dealing with truncated vs. actual length - Avoid showing dimensions twice in `obj_sum()`, use `vec_ptype_abbr()` (with default handling of non-vctrs things) and not `type_sum()` + - Is this done already? - Shorter list columns: - - Abbreviate list columns at the left: +- Prototype - Multi-stage (hierarchical) output for packed data frames + - Challenging with tiers + - Show number of columns in the parent stage? + - If too wide; also show ellipsis + - Perhaps show column names in footer? + - Can we agree that a packed data frame never spans multiple tiers? - Show column names that are abbreviated in full - - Packed data frames and matrices: if too wide, show ellipsis + - With their index if non-consecutive - Tick column title in extra columns + - It should be? - Second backtick if column name is abbreviated, - Simplify matrix formatting to format like an array: - Show number of rows if known @@ -36,7 +49,9 @@ - `format_glimpse()` uses `pillar_shaft()` for numbers - Reduce minimum width to 1 - Show time zone for times: + - refer to clock? - Class for numbers of same magnitude but with subtle differences? + - Subtle coloring for repetitive parts? - Highlight equal parts of a string column - `shorten = "unique"`? - `shorten = "front"`: right-align?