diff --git a/NEWS.md b/NEWS.md index cc03430779..b203c02895 100644 --- a/NEWS.md +++ b/NEWS.md @@ -20,6 +20,8 @@ not passed as the `name` argument (@teunbrand, #6623) * Fixed issue where vectorised `arrow()`s caused errors in drawing the legend glyphs (@teunbrand, #6594) +* Fixed regression where `NULL`-aesthetics contributed to plot labels too + insistently. Now they contribute only as fallback labels (@teunbrand, #6616) # ggplot2 4.0.0 diff --git a/R/aes-evaluation.R b/R/aes-evaluation.R index e29d0c5d25..f906d4bc2d 100644 --- a/R/aes-evaluation.R +++ b/R/aes-evaluation.R @@ -346,26 +346,6 @@ strip_stage <- function(expr) { } } -# Convert aesthetic mapping into text labels -make_labels <- function(mapping) { - default_label <- function(aesthetic, mapping) { - # e.g., geom_smooth(aes(colour = "loess")) or aes(y = NULL) - if (is.null(mapping) || is.atomic(mapping)) { - return(aesthetic) - } - mapping <- strip_stage(mapping) - mapping <- strip_dots(mapping, strip_pronoun = TRUE) - if (is_quosure(mapping) && quo_is_symbol(mapping)) { - name <- as_string(quo_get_expr(mapping)) - } else { - name <- quo_text(mapping) - name <- gsub("\n.*$", "...", name) - } - name - } - Map(default_label, names(mapping), mapping) -} - eval_aesthetics <- function(aesthetics, data, mask = NULL) { env <- child_env(base_env()) diff --git a/R/labels.R b/R/labels.R index a0991fed03..d5f7706d82 100644 --- a/R/labels.R +++ b/R/labels.R @@ -120,6 +120,26 @@ setup_plot_labels <- function(plot, layers, data) { labs(!!!defaults(plot_labels, labels)) } +# Convert aesthetic mapping into text labels +make_labels <- function(mapping) { + default_label <- function(aesthetic, mapping) { + # e.g., geom_smooth(aes(colour = "loess")) or aes(y = NULL) + if (is.null(mapping) || is.atomic(mapping)) { + return(structure(aesthetic, fallback = TRUE)) + } + mapping <- strip_stage(mapping) + mapping <- strip_dots(mapping, strip_pronoun = TRUE) + if (is_quosure(mapping) && quo_is_symbol(mapping)) { + name <- as_string(quo_get_expr(mapping)) + } else { + name <- quo_text(mapping) + name <- gsub("\n.*$", "...", name) + } + name + } + Map(default_label, names(mapping), mapping) +} + #' Modify axis, legend, and plot labels #' #' Good labels are critical for making your plots accessible to a wider diff --git a/tests/testthat/test-aes-calculated.R b/tests/testthat/test-aes-calculated.R index 2d389106cf..ee922ba005 100644 --- a/tests/testthat/test-aes-calculated.R +++ b/tests/testthat/test-aes-calculated.R @@ -45,9 +45,11 @@ test_that("make_labels() deparses mappings properly", { x_lab <- make_labels(aes(x = 2 * x * exp(`coef 1` * x^2) * 2 * x * exp(`coef 1` * x^2) * 2 * x))$x expect_length(x_lab, 1L) expect_match(x_lab, "...$") - # if the mapping is a literal or NULL, the aesthetics is used - expect_identical(make_labels(aes(x = 1)), list(x = "x")) - expect_identical(make_labels(aes(x = NULL)), list(x = "x")) + fallback <- list(x = structure("x", fallback = TRUE)) + # if the mapping is a literal or NULL, the aesthetics is used as fallback + expect_identical(make_labels(aes(x = 1)), fallback) + # NULL labels should only be used as fallback labels + expect_identical(make_labels(aes(x = NULL)), fallback) }) test_that("staged aesthetics warn appropriately for duplicated names", { diff --git a/tests/testthat/test-aes.R b/tests/testthat/test-aes.R index 8dd26d7a37..e2708eef6c 100644 --- a/tests/testthat/test-aes.R +++ b/tests/testthat/test-aes.R @@ -102,7 +102,8 @@ test_that("quosures are squashed when creating default label for a mapping", { test_that("labelling doesn't cause error if aesthetic is NULL", { p <- ggplot(mtcars) + aes(x = NULL) labels <- ggplot_build(p)@plot@labels - expect_identical(labels$x, "x") + # NULL labels should only be used as fallback labels + expect_identical(labels$x, structure("x", fallback = TRUE)) }) test_that("aes standardises aesthetic names", { diff --git a/tests/testthat/test-draw-key.R b/tests/testthat/test-draw-key.R index 223bfd6d5c..511077d0a1 100644 --- a/tests/testthat/test-draw-key.R +++ b/tests/testthat/test-draw-key.R @@ -110,7 +110,11 @@ test_that("keep_draw_key", { aes(colour = "line", alpha = "line"), show.legend = c("colour" = NA, alpha = TRUE) ) + - suppressWarnings(scale_alpha_discrete()) + suppressWarnings(scale_alpha_discrete()) + + guides( + alpha = guide_legend(order = 1), + colour = guide_legend(order = 2) + ) expect_doppelganger("appropriate colour key with alpha key as lines", p)