From 2a3b1a6a0e4a0b29e08d52139132c3a04a7b3ed3 Mon Sep 17 00:00:00 2001 From: Steve Haroz Date: Wed, 4 Oct 2023 21:50:22 +0200 Subject: [PATCH 01/18] new `geom_label()` aesthetics and parameters --- R/geom-label.R | 17 ++++++++++++----- R/geom-text.R | 29 +++++++++++++++++++++++++++++ man/geom_text.Rd | 31 ++++++++++++++++++++++++++++++- 3 files changed, 71 insertions(+), 6 deletions(-) diff --git a/R/geom-label.R b/R/geom-label.R index 343a5ae28e..db3a990a46 100644 --- a/R/geom-label.R +++ b/R/geom-label.R @@ -2,7 +2,7 @@ #' @rdname geom_text #' @param label.padding Amount of padding around label. Defaults to 0.25 lines. #' @param label.r Radius of rounded corners. Defaults to 0.15 lines. -#' @param label.size Size of label border, in mm. +#' @param label.size `r lifecycle::badge("deprecated")` Please use `linewidth`. Size of label border, in mm. geom_label <- function(mapping = NULL, data = NULL, stat = "identity", position = "identity", ..., @@ -27,6 +27,10 @@ geom_label <- function(mapping = NULL, data = NULL, position <- position_nudge(nudge_x, nudge_y) } + if (!missing(label.size)) { + message("`label.size` is deprecated. Please use `linewidth` in the future.") + } + layer( data = data, mapping = mapping, @@ -58,7 +62,7 @@ GeomLabel <- ggproto("GeomLabel", Geom, default_aes = aes( colour = "black", fill = "white", size = 3.88, angle = 0, hjust = 0.5, vjust = 0.5, alpha = NA, family = "", fontface = 1, - lineheight = 1.2 + lineheight = 1.2, linetype = "solid", linewidth = 0.25 ), draw_panel = function(self, data, panel_params, coord, parse = FALSE, @@ -66,7 +70,9 @@ GeomLabel <- ggproto("GeomLabel", Geom, label.padding = unit(0.25, "lines"), label.r = unit(0.15, "lines"), label.size = 0.25, - size.unit = "mm") { + size.unit = "mm", + border_colour = NULL, + border_color = border_colour) { lab <- data$label if (parse) { lab <- parse_safe(as.character(lab)) @@ -102,9 +108,10 @@ GeomLabel <- ggproto("GeomLabel", Geom, lineheight = row$lineheight ), rect.gp = gpar( - col = if (isTRUE(all.equal(label.size, 0))) NA else row$colour, + col = ifelse(row$linewidth == 0, NA, border_colour %||% border_color %||% row$colour), fill = alpha(row$fill, row$alpha), - lwd = label.size * .pt + lty = row$linetype, + lwd = (row$linewidth %||% label.size) * .pt ) ) }) diff --git a/R/geom-text.R b/R/geom-text.R index 0f4ed1918e..08d6afa3c3 100644 --- a/R/geom-text.R +++ b/R/geom-text.R @@ -89,6 +89,35 @@ #' scale_colour_discrete(l = 40) #' p + geom_label(aes(fill = factor(cyl)), colour = "white", fontface = "bold") #' +#' # Add aesthetics to the border for geom_label +#' data.frame(x = 1:10, y = 1:10) |> +#' ggplot() + +#' geom_label(aes( +#' label=month.abb[x], +#' x=x, +#' y=y, +#' color = factor(x%%3), +#' linewidth = x%%2, +#' linetype = factor(x%%3)), +#' fill = NA) + +#' scale_linewidth(range=c(0.5, 1.5)) + +#' scale_linetype_manual(values=c("solid", "blank", "dotted")) +#' +#' # Override the border color +#' data.frame(x = 1:10, y = 1:10) |> +#' ggplot() + +#' geom_label(aes( +#' label=month.abb[x], +#' x=x, +#' y=y, +#' color = factor(x%%3), +#' linewidth=x%%2, +#' linetype=factor(x%%3)), +#' border_color = "red", +#' fill=NA) + +#' scale_linewidth(range=c(0.5, 1.5)) + +#' scale_linetype_manual(values=c("solid", "blank", "dotted")) +#' #' p + geom_text(aes(size = wt)) #' # Scale height of text, rather than sqrt(height) #' p + diff --git a/man/geom_text.Rd b/man/geom_text.Rd index f9dfe385a6..6ac02d4cd9 100644 --- a/man/geom_text.Rd +++ b/man/geom_text.Rd @@ -85,7 +85,7 @@ Cannot be jointly specified with \code{position}.} \item{label.r}{Radius of rounded corners. Defaults to 0.15 lines.} -\item{label.size}{Size of label border, in mm.} +\item{label.size}{\ifelse{html}{\href{https://lifecycle.r-lib.org/articles/stages.html#deprecated}{\figure{lifecycle-deprecated.svg}{options: alt='[Deprecated]'}}}{\strong{[Deprecated]}} Please use \code{linewidth}. Size of label border, in mm.} \item{size.unit}{How the \code{size} aesthetic is interpreted: as millimetres (\code{"mm"}, default), points (\code{"pt"}), centimetres (\code{"cm"}), inches (\code{"in"}), @@ -207,6 +207,35 @@ p + geom_text(aes(colour = factor(cyl))) + scale_colour_discrete(l = 40) p + geom_label(aes(fill = factor(cyl)), colour = "white", fontface = "bold") +# Add aesthetics to the border for geom_label +data.frame(x = 1:10, y = 1:10) |> +ggplot() + + geom_label(aes( + label=month.abb[x], + x=x, + y=y, + color = factor(x\%\%3), + linewidth = x\%\%2, + linetype = factor(x\%\%3)), + fill = NA) + +scale_linewidth(range=c(0.5, 1.5)) + +scale_linetype_manual(values=c("solid", "blank", "dotted")) + +# Override the border color +data.frame(x = 1:10, y = 1:10) |> +ggplot() + + geom_label(aes( + label=month.abb[x], + x=x, + y=y, + color = factor(x\%\%3), + linewidth=x\%\%2, + linetype=factor(x\%\%3)), + border_color = "red", + fill=NA) + +scale_linewidth(range=c(0.5, 1.5)) + +scale_linetype_manual(values=c("solid", "blank", "dotted")) + p + geom_text(aes(size = wt)) # Scale height of text, rather than sqrt(height) p + From 44297f78d4a49ee3d62b1dba79afc79cca8f2270 Mon Sep 17 00:00:00 2001 From: Steve Haroz Date: Wed, 4 Oct 2023 21:51:25 +0200 Subject: [PATCH 02/18] Make label's legend keys look like the labels --- R/legend-draw.R | 28 +++++++++++++++++++++++++--- 1 file changed, 25 insertions(+), 3 deletions(-) diff --git a/R/legend-draw.R b/R/legend-draw.R index 5f8c202f07..0c5ac005a6 100644 --- a/R/legend-draw.R +++ b/R/legend-draw.R @@ -252,9 +252,31 @@ draw_key_text <- function(data, params, size) { #' @export #' @rdname draw_key draw_key_label <- function(data, params, size) { - grobTree( - draw_key_rect(data, list()), - draw_key_text(data, list()) + if(is.null(data$label)) data$label <- "a" + if(is.null(data$label.r)) data$label.r <- unit(0.1, "snpc") + if(is.null(params$label.padding)) params$label.padding <- unit(0.25, "lines") + if(length(params$label.padding) == 1) params$label.padding[2:4] <- params$label.padding + + labelGrob( + label = data$label, + x = 0.5, + y = 0.5, + padding = params$label.padding, + r = data$label.r, + angle = data$angle %||% 0, + text.gp = gpar( + col = alpha(data$colour %||% "white", data$alpha), + fontfamily = data$family %||% "", + fontface = data$fontface %||% 1, + fontsize = (data$size %||% 3.88) * .pt + ), + rect.gp = gpar( + col = alpha(params$border_colour %||% params$border_color %||% "black", data$alpha), + fill = alpha(data$fill %||% "white", data$alpha), + lty = data$linetype, + lwd = (data$linewidth %||% params$label.size) * .pt + ), + vp = NULL ) } From a20925e28d3fc0737c58a8281a85375e7628ec4d Mon Sep 17 00:00:00 2001 From: Steve Haroz Date: Wed, 4 Oct 2023 23:09:46 +0200 Subject: [PATCH 03/18] Made an example compatible with old versions of R --- R/geom-text.R | 6 ++---- man/geom_text.Rd | 6 ++---- 2 files changed, 4 insertions(+), 8 deletions(-) diff --git a/R/geom-text.R b/R/geom-text.R index 08d6afa3c3..809946d22b 100644 --- a/R/geom-text.R +++ b/R/geom-text.R @@ -90,8 +90,7 @@ #' p + geom_label(aes(fill = factor(cyl)), colour = "white", fontface = "bold") #' #' # Add aesthetics to the border for geom_label -#' data.frame(x = 1:10, y = 1:10) |> -#' ggplot() + +#' ggplot(data.frame(x = 1:10, y = 1:10)) + #' geom_label(aes( #' label=month.abb[x], #' x=x, @@ -104,8 +103,7 @@ #' scale_linetype_manual(values=c("solid", "blank", "dotted")) #' #' # Override the border color -#' data.frame(x = 1:10, y = 1:10) |> -#' ggplot() + +#' ggplot(data.frame(x = 1:10, y = 1:10)) + #' geom_label(aes( #' label=month.abb[x], #' x=x, diff --git a/man/geom_text.Rd b/man/geom_text.Rd index 6ac02d4cd9..57ecd35157 100644 --- a/man/geom_text.Rd +++ b/man/geom_text.Rd @@ -208,8 +208,7 @@ p + geom_text(aes(colour = factor(cyl))) + p + geom_label(aes(fill = factor(cyl)), colour = "white", fontface = "bold") # Add aesthetics to the border for geom_label -data.frame(x = 1:10, y = 1:10) |> -ggplot() + +ggplot(data.frame(x = 1:10, y = 1:10)) + geom_label(aes( label=month.abb[x], x=x, @@ -222,8 +221,7 @@ scale_linewidth(range=c(0.5, 1.5)) + scale_linetype_manual(values=c("solid", "blank", "dotted")) # Override the border color -data.frame(x = 1:10, y = 1:10) |> -ggplot() + +ggplot(data.frame(x = 1:10, y = 1:10)) + geom_label(aes( label=month.abb[x], x=x, From 49b303e334e85927dadc5f96e62a93991a88dbaa Mon Sep 17 00:00:00 2001 From: Steve Haroz Date: Thu, 5 Oct 2023 11:15:02 +0200 Subject: [PATCH 04/18] fix `label.size` deprecated message Co-authored-by: Teun van den Brand <49372158+teunbrand@users.noreply.github.com> --- R/geom-label.R | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/R/geom-label.R b/R/geom-label.R index db3a990a46..2cbdfc54b8 100644 --- a/R/geom-label.R +++ b/R/geom-label.R @@ -27,8 +27,8 @@ geom_label <- function(mapping = NULL, data = NULL, position <- position_nudge(nudge_x, nudge_y) } - if (!missing(label.size)) { - message("`label.size` is deprecated. Please use `linewidth` in the future.") + if (lifecycle::is_present(label.size)) { + deprecate_warn0("3.5.0", "geom_label(label.size)", "geom_label(linewidth)") } layer( From 17b67e9ad39a36a0778d0e350d8b75281df9a9dd Mon Sep 17 00:00:00 2001 From: Steve Haroz Date: Thu, 5 Oct 2023 11:15:47 +0200 Subject: [PATCH 05/18] default for `geom_label`'s linetype Co-authored-by: Teun van den Brand <49372158+teunbrand@users.noreply.github.com> --- R/geom-label.R | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/R/geom-label.R b/R/geom-label.R index 2cbdfc54b8..05c261d33a 100644 --- a/R/geom-label.R +++ b/R/geom-label.R @@ -62,7 +62,7 @@ GeomLabel <- ggproto("GeomLabel", Geom, default_aes = aes( colour = "black", fill = "white", size = 3.88, angle = 0, hjust = 0.5, vjust = 0.5, alpha = NA, family = "", fontface = 1, - lineheight = 1.2, linetype = "solid", linewidth = 0.25 + lineheight = 1.2, linetype = 1, linewidth = 0.25 ), draw_panel = function(self, data, panel_params, coord, parse = FALSE, From 30021259dc7e61ede0494d237e91523e8cf78f0d Mon Sep 17 00:00:00 2001 From: Steve Haroz Date: Thu, 5 Oct 2023 13:01:34 +0200 Subject: [PATCH 06/18] added border_colour to `geom_label()` --- R/geom-label.R | 11 +++++++---- man/geom_text.Rd | 6 +++++- 2 files changed, 12 insertions(+), 5 deletions(-) diff --git a/R/geom-label.R b/R/geom-label.R index 05c261d33a..3b7eafbaea 100644 --- a/R/geom-label.R +++ b/R/geom-label.R @@ -3,6 +3,7 @@ #' @param label.padding Amount of padding around label. Defaults to 0.25 lines. #' @param label.r Radius of rounded corners. Defaults to 0.15 lines. #' @param label.size `r lifecycle::badge("deprecated")` Please use `linewidth`. Size of label border, in mm. +#' @param border_colour Colour of the label's border. If `NULL`, it will fall back to the text colour. geom_label <- function(mapping = NULL, data = NULL, stat = "identity", position = "identity", ..., @@ -13,9 +14,11 @@ geom_label <- function(mapping = NULL, data = NULL, label.r = unit(0.15, "lines"), label.size = 0.25, size.unit = "mm", + border_colour = NULL, na.rm = FALSE, show.legend = NA, - inherit.aes = TRUE) { + inherit.aes = TRUE, + border_color = border_colour) { if (!missing(nudge_x) || !missing(nudge_y)) { if (!missing(position)) { cli::cli_abort(c( @@ -45,6 +48,7 @@ geom_label <- function(mapping = NULL, data = NULL, label.r = label.r, label.size = label.size, size.unit = size.unit, + border_colour = border_colour %||% border_color, na.rm = na.rm, ... ) @@ -71,8 +75,7 @@ GeomLabel <- ggproto("GeomLabel", Geom, label.r = unit(0.15, "lines"), label.size = 0.25, size.unit = "mm", - border_colour = NULL, - border_color = border_colour) { + border_colour = NULL) { lab <- data$label if (parse) { lab <- parse_safe(as.character(lab)) @@ -108,7 +111,7 @@ GeomLabel <- ggproto("GeomLabel", Geom, lineheight = row$lineheight ), rect.gp = gpar( - col = ifelse(row$linewidth == 0, NA, border_colour %||% border_color %||% row$colour), + col = ifelse(row$linewidth == 0, NA, border_colour %||% row$colour), fill = alpha(row$fill, row$alpha), lty = row$linetype, lwd = (row$linewidth %||% label.size) * .pt diff --git a/man/geom_text.Rd b/man/geom_text.Rd index 57ecd35157..243f816450 100644 --- a/man/geom_text.Rd +++ b/man/geom_text.Rd @@ -18,9 +18,11 @@ geom_label( label.r = unit(0.15, "lines"), label.size = 0.25, size.unit = "mm", + border_colour = NULL, na.rm = FALSE, show.legend = NA, - inherit.aes = TRUE + inherit.aes = TRUE, + border_color = border_colour ) geom_text( @@ -91,6 +93,8 @@ Cannot be jointly specified with \code{position}.} (\code{"mm"}, default), points (\code{"pt"}), centimetres (\code{"cm"}), inches (\code{"in"}), or picas (\code{"pc"}).} +\item{border_colour}{Colour of the label's border. If \code{NULL}, it will fall back to the text colour.} + \item{na.rm}{If \code{FALSE}, the default, missing values are removed with a warning. If \code{TRUE}, missing values are silently removed.} From e85b646929d6b5e734d7f9e47404c942e0474cd8 Mon Sep 17 00:00:00 2001 From: Steve Haroz Date: Thu, 5 Oct 2023 13:02:26 +0200 Subject: [PATCH 07/18] geom_label example formatting --- R/geom-text.R | 26 +++++++++++++------------- man/geom_text.Rd | 26 +++++++++++++------------- 2 files changed, 26 insertions(+), 26 deletions(-) diff --git a/R/geom-text.R b/R/geom-text.R index 809946d22b..aaa8d16744 100644 --- a/R/geom-text.R +++ b/R/geom-text.R @@ -92,29 +92,29 @@ #' # Add aesthetics to the border for geom_label #' ggplot(data.frame(x = 1:10, y = 1:10)) + #' geom_label(aes( -#' label=month.abb[x], -#' x=x, -#' y=y, +#' label = month.abb[x], +#' x = x, +#' y = y, #' color = factor(x%%3), #' linewidth = x%%2, #' linetype = factor(x%%3)), #' fill = NA) + -#' scale_linewidth(range=c(0.5, 1.5)) + -#' scale_linetype_manual(values=c("solid", "blank", "dotted")) +#' scale_linewidth(range = c(0.5, 1.5)) + +#' scale_linetype_manual(values = c("solid", "blank", "dotted")) #' #' # Override the border color #' ggplot(data.frame(x = 1:10, y = 1:10)) + #' geom_label(aes( -#' label=month.abb[x], -#' x=x, -#' y=y, +#' label = month.abb[x], +#' x = x, +#' y = y, #' color = factor(x%%3), -#' linewidth=x%%2, -#' linetype=factor(x%%3)), +#' linewidth = x%%2, +#' linetype = factor(x%%3)), #' border_color = "red", -#' fill=NA) + -#' scale_linewidth(range=c(0.5, 1.5)) + -#' scale_linetype_manual(values=c("solid", "blank", "dotted")) +#' fill = NA) + +#' scale_linewidth(range = c(0.5, 1.5)) + +#' scale_linetype_manual(values = c("solid", "blank", "dotted")) #' #' p + geom_text(aes(size = wt)) #' # Scale height of text, rather than sqrt(height) diff --git a/man/geom_text.Rd b/man/geom_text.Rd index 243f816450..3fe9a959fc 100644 --- a/man/geom_text.Rd +++ b/man/geom_text.Rd @@ -214,29 +214,29 @@ p + geom_label(aes(fill = factor(cyl)), colour = "white", fontface = "bold") # Add aesthetics to the border for geom_label ggplot(data.frame(x = 1:10, y = 1:10)) + geom_label(aes( - label=month.abb[x], - x=x, - y=y, + label = month.abb[x], + x = x, + y = y, color = factor(x\%\%3), linewidth = x\%\%2, linetype = factor(x\%\%3)), fill = NA) + -scale_linewidth(range=c(0.5, 1.5)) + -scale_linetype_manual(values=c("solid", "blank", "dotted")) +scale_linewidth(range = c(0.5, 1.5)) + +scale_linetype_manual(values = c("solid", "blank", "dotted")) # Override the border color ggplot(data.frame(x = 1:10, y = 1:10)) + geom_label(aes( - label=month.abb[x], - x=x, - y=y, + label = month.abb[x], + x = x, + y = y, color = factor(x\%\%3), - linewidth=x\%\%2, - linetype=factor(x\%\%3)), + linewidth = x\%\%2, + linetype = factor(x\%\%3)), border_color = "red", - fill=NA) + -scale_linewidth(range=c(0.5, 1.5)) + -scale_linetype_manual(values=c("solid", "blank", "dotted")) + fill = NA) + +scale_linewidth(range = c(0.5, 1.5)) + +scale_linetype_manual(values = c("solid", "blank", "dotted")) p + geom_text(aes(size = wt)) # Scale height of text, rather than sqrt(height) From 95fa35e40db030fbfb305543645b0c3b6bade4e0 Mon Sep 17 00:00:00 2001 From: Steve Haroz Date: Thu, 5 Oct 2023 13:04:27 +0200 Subject: [PATCH 08/18] handle nulls more consistently --- R/legend-draw.R | 6 ++---- 1 file changed, 2 insertions(+), 4 deletions(-) diff --git a/R/legend-draw.R b/R/legend-draw.R index 0c5ac005a6..61cc3e7e27 100644 --- a/R/legend-draw.R +++ b/R/legend-draw.R @@ -252,17 +252,15 @@ draw_key_text <- function(data, params, size) { #' @export #' @rdname draw_key draw_key_label <- function(data, params, size) { - if(is.null(data$label)) data$label <- "a" - if(is.null(data$label.r)) data$label.r <- unit(0.1, "snpc") if(is.null(params$label.padding)) params$label.padding <- unit(0.25, "lines") if(length(params$label.padding) == 1) params$label.padding[2:4] <- params$label.padding labelGrob( - label = data$label, + label = data$label %||% "a", x = 0.5, y = 0.5, padding = params$label.padding, - r = data$label.r, + r = data$label.r %||% unit(0.1, "snpc"), angle = data$angle %||% 0, text.gp = gpar( col = alpha(data$colour %||% "white", data$alpha), From fe65bddf00a1650bbf3abd3a5e1397c73f7fef9f Mon Sep 17 00:00:00 2001 From: Steve Haroz Date: Thu, 5 Oct 2023 15:09:38 +0200 Subject: [PATCH 09/18] Dropping `line.size` from `GeomLabel` --- R/geom-label.R | 8 +++----- R/legend-draw.R | 2 +- man/geom_text.Rd | 4 ++-- man/ggsf.Rd | 2 +- 4 files changed, 7 insertions(+), 9 deletions(-) diff --git a/R/geom-label.R b/R/geom-label.R index 3b7eafbaea..f5c5539804 100644 --- a/R/geom-label.R +++ b/R/geom-label.R @@ -2,7 +2,7 @@ #' @rdname geom_text #' @param label.padding Amount of padding around label. Defaults to 0.25 lines. #' @param label.r Radius of rounded corners. Defaults to 0.15 lines. -#' @param label.size `r lifecycle::badge("deprecated")` Please use `linewidth`. Size of label border, in mm. +#' @param label.size `r lifecycle::badge("deprecated")` Please use `linewidth` to set the size of the border. #' @param border_colour Colour of the label's border. If `NULL`, it will fall back to the text colour. geom_label <- function(mapping = NULL, data = NULL, stat = "identity", position = "identity", @@ -12,7 +12,7 @@ geom_label <- function(mapping = NULL, data = NULL, nudge_y = 0, label.padding = unit(0.25, "lines"), label.r = unit(0.15, "lines"), - label.size = 0.25, + label.size = deprecated(), size.unit = "mm", border_colour = NULL, na.rm = FALSE, @@ -46,7 +46,6 @@ geom_label <- function(mapping = NULL, data = NULL, parse = parse, label.padding = label.padding, label.r = label.r, - label.size = label.size, size.unit = size.unit, border_colour = border_colour %||% border_color, na.rm = na.rm, @@ -73,7 +72,6 @@ GeomLabel <- ggproto("GeomLabel", Geom, na.rm = FALSE, label.padding = unit(0.25, "lines"), label.r = unit(0.15, "lines"), - label.size = 0.25, size.unit = "mm", border_colour = NULL) { lab <- data$label @@ -114,7 +112,7 @@ GeomLabel <- ggproto("GeomLabel", Geom, col = ifelse(row$linewidth == 0, NA, border_colour %||% row$colour), fill = alpha(row$fill, row$alpha), lty = row$linetype, - lwd = (row$linewidth %||% label.size) * .pt + lwd = row$linewidth * .pt ) ) }) diff --git a/R/legend-draw.R b/R/legend-draw.R index 61cc3e7e27..97477b00d0 100644 --- a/R/legend-draw.R +++ b/R/legend-draw.R @@ -272,7 +272,7 @@ draw_key_label <- function(data, params, size) { col = alpha(params$border_colour %||% params$border_color %||% "black", data$alpha), fill = alpha(data$fill %||% "white", data$alpha), lty = data$linetype, - lwd = (data$linewidth %||% params$label.size) * .pt + lwd = data$linewidth * .pt ), vp = NULL ) diff --git a/man/geom_text.Rd b/man/geom_text.Rd index 3fe9a959fc..a92165fb1a 100644 --- a/man/geom_text.Rd +++ b/man/geom_text.Rd @@ -16,7 +16,7 @@ geom_label( nudge_y = 0, label.padding = unit(0.25, "lines"), label.r = unit(0.15, "lines"), - label.size = 0.25, + label.size = deprecated(), size.unit = "mm", border_colour = NULL, na.rm = FALSE, @@ -87,7 +87,7 @@ Cannot be jointly specified with \code{position}.} \item{label.r}{Radius of rounded corners. Defaults to 0.15 lines.} -\item{label.size}{\ifelse{html}{\href{https://lifecycle.r-lib.org/articles/stages.html#deprecated}{\figure{lifecycle-deprecated.svg}{options: alt='[Deprecated]'}}}{\strong{[Deprecated]}} Please use \code{linewidth}. Size of label border, in mm.} +\item{label.size}{\ifelse{html}{\href{https://lifecycle.r-lib.org/articles/stages.html#deprecated}{\figure{lifecycle-deprecated.svg}{options: alt='[Deprecated]'}}}{\strong{[Deprecated]}} Please use \code{linewidth} to set the size of the border.} \item{size.unit}{How the \code{size} aesthetic is interpreted: as millimetres (\code{"mm"}, default), points (\code{"pt"}), centimetres (\code{"cm"}), inches (\code{"in"}), diff --git a/man/ggsf.Rd b/man/ggsf.Rd index fca4f896d3..17389f80e8 100644 --- a/man/ggsf.Rd +++ b/man/ggsf.Rd @@ -236,7 +236,7 @@ Cannot be jointly specified with \code{position}.} \item{label.r}{Radius of rounded corners. Defaults to 0.15 lines.} -\item{label.size}{Size of label border, in mm.} +\item{label.size}{\ifelse{html}{\href{https://lifecycle.r-lib.org/articles/stages.html#deprecated}{\figure{lifecycle-deprecated.svg}{options: alt='[Deprecated]'}}}{\strong{[Deprecated]}} Please use \code{linewidth} to set the size of the border.} \item{fun.geometry}{A function that takes a \code{sfc} object and returns a \code{sfc_POINT} with the same length as the input. If \code{NULL}, \code{function(x) sf::st_point_on_surface(sf::st_zm(x))} From 2c9300fca7f0035de853169aa4a5c4ef72cddfe5 Mon Sep 17 00:00:00 2001 From: Steve Haroz Date: Thu, 5 Oct 2023 22:07:33 +0200 Subject: [PATCH 10/18] Adding alias for `border_color` in docs --- R/geom-label.R | 1 + man/geom_text.Rd | 2 ++ 2 files changed, 3 insertions(+) diff --git a/R/geom-label.R b/R/geom-label.R index f5c5539804..4814f81cc0 100644 --- a/R/geom-label.R +++ b/R/geom-label.R @@ -4,6 +4,7 @@ #' @param label.r Radius of rounded corners. Defaults to 0.15 lines. #' @param label.size `r lifecycle::badge("deprecated")` Please use `linewidth` to set the size of the border. #' @param border_colour Colour of the label's border. If `NULL`, it will fall back to the text colour. +#' @param border_color An alias for `border_colour`. geom_label <- function(mapping = NULL, data = NULL, stat = "identity", position = "identity", ..., diff --git a/man/geom_text.Rd b/man/geom_text.Rd index a92165fb1a..f792958f6d 100644 --- a/man/geom_text.Rd +++ b/man/geom_text.Rd @@ -109,6 +109,8 @@ rather than combining with them. This is most useful for helper functions that define both data and aesthetics and shouldn't inherit behaviour from the default plot specification, e.g. \code{\link[=borders]{borders()}}.} +\item{border_color}{An alias for \code{border_colour}.} + \item{check_overlap}{If \code{TRUE}, text that overlaps previous text in the same layer will not be plotted. \code{check_overlap} happens at draw time and in the order of the data. Therefore data should be arranged by the label From d427ea4958ae18b03f54bdf6c93e2f3f074297bc Mon Sep 17 00:00:00 2001 From: Steve Haroz Date: Fri, 6 Oct 2023 08:13:35 +0200 Subject: [PATCH 11/18] example of how geom_label aesthetics might be used --- R/geom-text.R | 8 +++++++- man/geom_text.Rd | 8 +++++++- 2 files changed, 14 insertions(+), 2 deletions(-) diff --git a/R/geom-text.R b/R/geom-text.R index aaa8d16744..b652124f08 100644 --- a/R/geom-text.R +++ b/R/geom-text.R @@ -89,7 +89,13 @@ #' scale_colour_discrete(l = 40) #' p + geom_label(aes(fill = factor(cyl)), colour = "white", fontface = "bold") #' -#' # Add aesthetics to the border for geom_label +#' # Use geom_label's border aesthetics to add highlights +#' p + geom_label( +#' aes(fill = factor(cyl), linetype = qsec < 15), +#' border_colour = "black", color = "white", linewidth = 1) + +#' scale_linetype_manual(values=c("solid", "blank"), limits = TRUE, labels = "1/4 mi < 15s", name = NULL) +#' +#' # Multiple border aesthetics can be used #' ggplot(data.frame(x = 1:10, y = 1:10)) + #' geom_label(aes( #' label = month.abb[x], diff --git a/man/geom_text.Rd b/man/geom_text.Rd index f792958f6d..3a904ca054 100644 --- a/man/geom_text.Rd +++ b/man/geom_text.Rd @@ -213,7 +213,13 @@ p + geom_text(aes(colour = factor(cyl))) + scale_colour_discrete(l = 40) p + geom_label(aes(fill = factor(cyl)), colour = "white", fontface = "bold") -# Add aesthetics to the border for geom_label +# Use geom_label's border aesthetics to add highlights +p + geom_label( + aes(fill = factor(cyl), linetype = qsec < 15), + border_colour = "black", color = "white", linewidth = 1) + +scale_linetype_manual(values=c("solid", "blank"), limits = TRUE, labels = "1/4 mi < 15s", name = NULL) + +# Multiple border aesthetics can be used ggplot(data.frame(x = 1:10, y = 1:10)) + geom_label(aes( label = month.abb[x], From aac7112b7ced7f077e738e385ca956fd17da2b36 Mon Sep 17 00:00:00 2001 From: Steve Haroz Date: Fri, 6 Oct 2023 08:14:48 +0200 Subject: [PATCH 12/18] fixed legend inconsistent with `geom_label` --- R/legend-draw.R | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/R/legend-draw.R b/R/legend-draw.R index 97477b00d0..8172c72541 100644 --- a/R/legend-draw.R +++ b/R/legend-draw.R @@ -269,7 +269,7 @@ draw_key_label <- function(data, params, size) { fontsize = (data$size %||% 3.88) * .pt ), rect.gp = gpar( - col = alpha(params$border_colour %||% params$border_color %||% "black", data$alpha), + col = alpha(params$border_colour %||% params$border_color %||% data$colour %||% "black", data$alpha), fill = alpha(data$fill %||% "white", data$alpha), lty = data$linetype, lwd = data$linewidth * .pt From 1a8d145cecc4821f6af636007b50f2808ee5824c Mon Sep 17 00:00:00 2001 From: Steve Haroz Date: Mon, 9 Oct 2023 13:35:05 +0200 Subject: [PATCH 13/18] snake_case to dot.case --- R/geom-label.R | 14 +++++++------- R/geom-text.R | 4 ++-- R/legend-draw.R | 2 +- man/geom_text.Rd | 12 ++++++------ 4 files changed, 16 insertions(+), 16 deletions(-) diff --git a/R/geom-label.R b/R/geom-label.R index 4814f81cc0..9cbc60420b 100644 --- a/R/geom-label.R +++ b/R/geom-label.R @@ -3,8 +3,8 @@ #' @param label.padding Amount of padding around label. Defaults to 0.25 lines. #' @param label.r Radius of rounded corners. Defaults to 0.15 lines. #' @param label.size `r lifecycle::badge("deprecated")` Please use `linewidth` to set the size of the border. -#' @param border_colour Colour of the label's border. If `NULL`, it will fall back to the text colour. -#' @param border_color An alias for `border_colour`. +#' @param border.colour Colour of the label's border. If `NULL`, it will fall back to the text colour. +#' @param border.color An alias for `border.colour`. geom_label <- function(mapping = NULL, data = NULL, stat = "identity", position = "identity", ..., @@ -15,11 +15,11 @@ geom_label <- function(mapping = NULL, data = NULL, label.r = unit(0.15, "lines"), label.size = deprecated(), size.unit = "mm", - border_colour = NULL, + border.colour = NULL, na.rm = FALSE, show.legend = NA, inherit.aes = TRUE, - border_color = border_colour) { + border.color = border.colour) { if (!missing(nudge_x) || !missing(nudge_y)) { if (!missing(position)) { cli::cli_abort(c( @@ -48,7 +48,7 @@ geom_label <- function(mapping = NULL, data = NULL, label.padding = label.padding, label.r = label.r, size.unit = size.unit, - border_colour = border_colour %||% border_color, + border.colour = border.colour %||% border.color, na.rm = na.rm, ... ) @@ -74,7 +74,7 @@ GeomLabel <- ggproto("GeomLabel", Geom, label.padding = unit(0.25, "lines"), label.r = unit(0.15, "lines"), size.unit = "mm", - border_colour = NULL) { + border.colour = NULL) { lab <- data$label if (parse) { lab <- parse_safe(as.character(lab)) @@ -110,7 +110,7 @@ GeomLabel <- ggproto("GeomLabel", Geom, lineheight = row$lineheight ), rect.gp = gpar( - col = ifelse(row$linewidth == 0, NA, border_colour %||% row$colour), + col = ifelse(row$linewidth == 0, NA, border.colour %||% row$colour), fill = alpha(row$fill, row$alpha), lty = row$linetype, lwd = row$linewidth * .pt diff --git a/R/geom-text.R b/R/geom-text.R index b652124f08..1394efc7cc 100644 --- a/R/geom-text.R +++ b/R/geom-text.R @@ -92,7 +92,7 @@ #' # Use geom_label's border aesthetics to add highlights #' p + geom_label( #' aes(fill = factor(cyl), linetype = qsec < 15), -#' border_colour = "black", color = "white", linewidth = 1) + +#' border.colour = "black", color = "white", linewidth = 1) + #' scale_linetype_manual(values=c("solid", "blank"), limits = TRUE, labels = "1/4 mi < 15s", name = NULL) #' #' # Multiple border aesthetics can be used @@ -117,7 +117,7 @@ #' color = factor(x%%3), #' linewidth = x%%2, #' linetype = factor(x%%3)), -#' border_color = "red", +#' border.color = "red", #' fill = NA) + #' scale_linewidth(range = c(0.5, 1.5)) + #' scale_linetype_manual(values = c("solid", "blank", "dotted")) diff --git a/R/legend-draw.R b/R/legend-draw.R index 8172c72541..ebb3b3bfd7 100644 --- a/R/legend-draw.R +++ b/R/legend-draw.R @@ -269,7 +269,7 @@ draw_key_label <- function(data, params, size) { fontsize = (data$size %||% 3.88) * .pt ), rect.gp = gpar( - col = alpha(params$border_colour %||% params$border_color %||% data$colour %||% "black", data$alpha), + col = alpha(params$border.colour %||% params$border.color %||% data$colour %||% "black", data$alpha), fill = alpha(data$fill %||% "white", data$alpha), lty = data$linetype, lwd = data$linewidth * .pt diff --git a/man/geom_text.Rd b/man/geom_text.Rd index 3a904ca054..3a6ec69e7f 100644 --- a/man/geom_text.Rd +++ b/man/geom_text.Rd @@ -18,11 +18,11 @@ geom_label( label.r = unit(0.15, "lines"), label.size = deprecated(), size.unit = "mm", - border_colour = NULL, + border.colour = NULL, na.rm = FALSE, show.legend = NA, inherit.aes = TRUE, - border_color = border_colour + border.color = border.colour ) geom_text( @@ -93,7 +93,7 @@ Cannot be jointly specified with \code{position}.} (\code{"mm"}, default), points (\code{"pt"}), centimetres (\code{"cm"}), inches (\code{"in"}), or picas (\code{"pc"}).} -\item{border_colour}{Colour of the label's border. If \code{NULL}, it will fall back to the text colour.} +\item{border.colour}{Colour of the label's border. If \code{NULL}, it will fall back to the text colour.} \item{na.rm}{If \code{FALSE}, the default, missing values are removed with a warning. If \code{TRUE}, missing values are silently removed.} @@ -109,7 +109,7 @@ rather than combining with them. This is most useful for helper functions that define both data and aesthetics and shouldn't inherit behaviour from the default plot specification, e.g. \code{\link[=borders]{borders()}}.} -\item{border_color}{An alias for \code{border_colour}.} +\item{border.color}{An alias for \code{border.colour}.} \item{check_overlap}{If \code{TRUE}, text that overlaps previous text in the same layer will not be plotted. \code{check_overlap} happens at draw time and in @@ -216,7 +216,7 @@ p + geom_label(aes(fill = factor(cyl)), colour = "white", fontface = "bold") # Use geom_label's border aesthetics to add highlights p + geom_label( aes(fill = factor(cyl), linetype = qsec < 15), - border_colour = "black", color = "white", linewidth = 1) + + border.colour = "black", color = "white", linewidth = 1) + scale_linetype_manual(values=c("solid", "blank"), limits = TRUE, labels = "1/4 mi < 15s", name = NULL) # Multiple border aesthetics can be used @@ -241,7 +241,7 @@ ggplot(data.frame(x = 1:10, y = 1:10)) + color = factor(x\%\%3), linewidth = x\%\%2, linetype = factor(x\%\%3)), - border_color = "red", + border.color = "red", fill = NA) + scale_linewidth(range = c(0.5, 1.5)) + scale_linetype_manual(values = c("solid", "blank", "dotted")) From 4372d9996e9a0ca66d005f6076d4682e699ed430 Mon Sep 17 00:00:00 2001 From: Steve Haroz Date: Mon, 9 Oct 2023 13:53:22 +0200 Subject: [PATCH 14/18] simpler examples for `geom_label` --- R/geom-text.R | 35 +++++++---------------------------- man/geom_text.Rd | 35 +++++++---------------------------- 2 files changed, 14 insertions(+), 56 deletions(-) diff --git a/R/geom-text.R b/R/geom-text.R index 1394efc7cc..aaae5aa6a1 100644 --- a/R/geom-text.R +++ b/R/geom-text.R @@ -89,39 +89,18 @@ #' scale_colour_discrete(l = 40) #' p + geom_label(aes(fill = factor(cyl)), colour = "white", fontface = "bold") #' -#' # Use geom_label's border aesthetics to add highlights +#' # If border.color is NULL or not set, the border will use the text color +#' p + geom_label(aes(color = factor(cyl))) +#' +#' # Alternatively, border.color can have a static value +#' p + geom_label(aes(color = factor(cyl)), border.color = "black") +#' +#' # Use linetype and linewidth aesthetics to add highlights #' p + geom_label( #' aes(fill = factor(cyl), linetype = qsec < 15), #' border.colour = "black", color = "white", linewidth = 1) + #' scale_linetype_manual(values=c("solid", "blank"), limits = TRUE, labels = "1/4 mi < 15s", name = NULL) #' -#' # Multiple border aesthetics can be used -#' ggplot(data.frame(x = 1:10, y = 1:10)) + -#' geom_label(aes( -#' label = month.abb[x], -#' x = x, -#' y = y, -#' color = factor(x%%3), -#' linewidth = x%%2, -#' linetype = factor(x%%3)), -#' fill = NA) + -#' scale_linewidth(range = c(0.5, 1.5)) + -#' scale_linetype_manual(values = c("solid", "blank", "dotted")) -#' -#' # Override the border color -#' ggplot(data.frame(x = 1:10, y = 1:10)) + -#' geom_label(aes( -#' label = month.abb[x], -#' x = x, -#' y = y, -#' color = factor(x%%3), -#' linewidth = x%%2, -#' linetype = factor(x%%3)), -#' border.color = "red", -#' fill = NA) + -#' scale_linewidth(range = c(0.5, 1.5)) + -#' scale_linetype_manual(values = c("solid", "blank", "dotted")) -#' #' p + geom_text(aes(size = wt)) #' # Scale height of text, rather than sqrt(height) #' p + diff --git a/man/geom_text.Rd b/man/geom_text.Rd index 3a6ec69e7f..fbc3d5a5e7 100644 --- a/man/geom_text.Rd +++ b/man/geom_text.Rd @@ -213,39 +213,18 @@ p + geom_text(aes(colour = factor(cyl))) + scale_colour_discrete(l = 40) p + geom_label(aes(fill = factor(cyl)), colour = "white", fontface = "bold") -# Use geom_label's border aesthetics to add highlights +# If border.color is NULL or not set, the border will use the text color +p + geom_label(aes(color = factor(cyl))) + +# Alternatively, border.color can have a static value +p + geom_label(aes(color = factor(cyl)), border.color = "black") + +# Use linetype and linewidth aesthetics to add highlights p + geom_label( aes(fill = factor(cyl), linetype = qsec < 15), border.colour = "black", color = "white", linewidth = 1) + scale_linetype_manual(values=c("solid", "blank"), limits = TRUE, labels = "1/4 mi < 15s", name = NULL) -# Multiple border aesthetics can be used -ggplot(data.frame(x = 1:10, y = 1:10)) + - geom_label(aes( - label = month.abb[x], - x = x, - y = y, - color = factor(x\%\%3), - linewidth = x\%\%2, - linetype = factor(x\%\%3)), - fill = NA) + -scale_linewidth(range = c(0.5, 1.5)) + -scale_linetype_manual(values = c("solid", "blank", "dotted")) - -# Override the border color -ggplot(data.frame(x = 1:10, y = 1:10)) + - geom_label(aes( - label = month.abb[x], - x = x, - y = y, - color = factor(x\%\%3), - linewidth = x\%\%2, - linetype = factor(x\%\%3)), - border.color = "red", - fill = NA) + -scale_linewidth(range = c(0.5, 1.5)) + -scale_linetype_manual(values = c("solid", "blank", "dotted")) - p + geom_text(aes(size = wt)) # Scale height of text, rather than sqrt(height) p + From 6337d6614da26a48b7beaa78573632ae0e04d881 Mon Sep 17 00:00:00 2001 From: Steve Haroz Date: Tue, 10 Oct 2023 12:16:11 +0200 Subject: [PATCH 15/18] size -> width Co-authored-by: Teun van den Brand <49372158+teunbrand@users.noreply.github.com> --- R/geom-label.R | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/R/geom-label.R b/R/geom-label.R index 9cbc60420b..a7bc0a6b2c 100644 --- a/R/geom-label.R +++ b/R/geom-label.R @@ -2,7 +2,7 @@ #' @rdname geom_text #' @param label.padding Amount of padding around label. Defaults to 0.25 lines. #' @param label.r Radius of rounded corners. Defaults to 0.15 lines. -#' @param label.size `r lifecycle::badge("deprecated")` Please use `linewidth` to set the size of the border. +#' @param label.size `r lifecycle::badge("deprecated")` Please use `linewidth` to set the width of the border. #' @param border.colour Colour of the label's border. If `NULL`, it will fall back to the text colour. #' @param border.color An alias for `border.colour`. geom_label <- function(mapping = NULL, data = NULL, From 4ac30bcec19154e558ddb5a8bc855f52078b34a6 Mon Sep 17 00:00:00 2001 From: Steve Haroz Date: Tue, 10 Oct 2023 12:16:44 +0200 Subject: [PATCH 16/18] combine border.colour and border.color parameter docs Co-authored-by: Teun van den Brand <49372158+teunbrand@users.noreply.github.com> --- R/geom-label.R | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/R/geom-label.R b/R/geom-label.R index a7bc0a6b2c..59f76e7cb4 100644 --- a/R/geom-label.R +++ b/R/geom-label.R @@ -3,8 +3,7 @@ #' @param label.padding Amount of padding around label. Defaults to 0.25 lines. #' @param label.r Radius of rounded corners. Defaults to 0.15 lines. #' @param label.size `r lifecycle::badge("deprecated")` Please use `linewidth` to set the width of the border. -#' @param border.colour Colour of the label's border. If `NULL`, it will fall back to the text colour. -#' @param border.color An alias for `border.colour`. +#' @param border.colour,border.color Colour of the label's border. If `NULL` (default), it will fall back to the text colour. `border.color` is an alias. geom_label <- function(mapping = NULL, data = NULL, stat = "identity", position = "identity", ..., From 844a028c60275adda4589cfa82995e5e5848965b Mon Sep 17 00:00:00 2001 From: Steve Haroz Date: Tue, 10 Oct 2023 12:17:05 +0200 Subject: [PATCH 17/18] uk spelling in examples Co-authored-by: Teun van den Brand <49372158+teunbrand@users.noreply.github.com> --- R/geom-text.R | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/R/geom-text.R b/R/geom-text.R index aaae5aa6a1..2c56e1b547 100644 --- a/R/geom-text.R +++ b/R/geom-text.R @@ -90,10 +90,10 @@ #' p + geom_label(aes(fill = factor(cyl)), colour = "white", fontface = "bold") #' #' # If border.color is NULL or not set, the border will use the text color -#' p + geom_label(aes(color = factor(cyl))) +#' p + geom_label(aes(colour = factor(cyl))) #' #' # Alternatively, border.color can have a static value -#' p + geom_label(aes(color = factor(cyl)), border.color = "black") +#' p + geom_label(aes(colour = factor(cyl)), border.colour = "black") #' #' # Use linetype and linewidth aesthetics to add highlights #' p + geom_label( From d0b4bb55b16cf254319925ec59526eff5f6d08bd Mon Sep 17 00:00:00 2001 From: Steve Haroz Date: Tue, 10 Oct 2023 12:17:51 +0200 Subject: [PATCH 18/18] Update R/geom-text.R Co-authored-by: Teun van den Brand <49372158+teunbrand@users.noreply.github.com> --- R/geom-text.R | 10 ++++++---- 1 file changed, 6 insertions(+), 4 deletions(-) diff --git a/R/geom-text.R b/R/geom-text.R index 2c56e1b547..5e17740d16 100644 --- a/R/geom-text.R +++ b/R/geom-text.R @@ -96,10 +96,12 @@ #' p + geom_label(aes(colour = factor(cyl)), border.colour = "black") #' #' # Use linetype and linewidth aesthetics to add highlights -#' p + geom_label( -#' aes(fill = factor(cyl), linetype = qsec < 15), -#' border.colour = "black", color = "white", linewidth = 1) + -#' scale_linetype_manual(values=c("solid", "blank"), limits = TRUE, labels = "1/4 mi < 15s", name = NULL) +#' p + +#' geom_label( +#' aes(fill = factor(cyl), linetype = qsec < 15), +#' border.colour = "black", colour = "white" +#' ) + +#' scale_linetype_manual(values = c("solid", "blank"), limits = TRUE) #' #' p + geom_text(aes(size = wt)) #' # Scale height of text, rather than sqrt(height)