diff --git a/R/annotation-logticks.R b/R/annotation-logticks.R index aa03d472cf..600bd6ce7c 100644 --- a/R/annotation-logticks.R +++ b/R/annotation-logticks.R @@ -229,7 +229,7 @@ GeomLogticks <- ggproto("GeomLogticks", Geom, }, default_aes = aes( - colour = from_theme(ink), + colour = from_theme(colour %||% ink), linewidth = from_theme(linewidth), linetype = from_theme(linetype), alpha = 1 diff --git a/R/geom-.R b/R/geom-.R index 843bd4c11c..06f475d8b4 100644 --- a/R/geom-.R +++ b/R/geom-.R @@ -133,7 +133,7 @@ Geom <- ggproto("Geom", # Fill in missing aesthetics with their defaults missing_aes <- setdiff(names(default_aes), names(data)) default_aes <- default_aes[missing_aes] - themed_defaults <- eval_from_theme(default_aes, theme) + themed_defaults <- eval_from_theme(default_aes, theme, class(self)) default_aes[names(themed_defaults)] <- themed_defaults # Mark staged/scaled defaults as modifier (#6135) @@ -242,13 +242,33 @@ Geom <- ggproto("Geom", #' @rdname is_tests is.geom <- function(x) inherits(x, "Geom") -eval_from_theme <- function(aesthetics, theme) { +eval_from_theme <- function(aesthetics, theme, class = NULL) { themed <- is_themed_aes(aesthetics) if (!any(themed)) { return(aesthetics) } - settings <- calc_element("geom", theme) %||% .default_geom_element - lapply(aesthetics[themed], eval_tidy, data = settings) + + element <- calc_element("geom", theme) %||% .default_geom_element + class <- setdiff(class, c("Geom", "ggproto", "gg")) + + if (length(class) > 0) { + + # CamelCase to dot.case + class <- gsub("([A-Za-z])([A-Z])([a-z])", "\\1.\\2\\3", class) + class <- gsub("([a-z])([A-Z])", "\\1.\\2", class) + class <- to_lower_ascii(class) + + class <- class[class %in% names(theme)] + + # Inherit up to parent geom class + if (length(class) > 0) { + for (cls in rev(class)) { + element <- combine_elements(theme[[cls]], element) + } + } + } + + lapply(aesthetics[themed], eval_tidy, data = element) } #' Graphical units diff --git a/R/geom-abline.R b/R/geom-abline.R index 825d45faf8..d87dfdc58b 100644 --- a/R/geom-abline.R +++ b/R/geom-abline.R @@ -147,7 +147,7 @@ GeomAbline <- ggproto("GeomAbline", Geom, }, default_aes = aes( - colour = from_theme(ink), + colour = from_theme(colour %||% ink), linewidth = from_theme(linewidth), linetype = from_theme(linetype), alpha = NA diff --git a/R/geom-boxplot.R b/R/geom-boxplot.R index 96c6ed9d35..316dd6004b 100644 --- a/R/geom-boxplot.R +++ b/R/geom-boxplot.R @@ -395,8 +395,8 @@ GeomBoxplot <- ggproto("GeomBoxplot", Geom, draw_key = draw_key_boxplot, default_aes = aes( - weight = 1, colour = from_theme(col_mix(ink, paper, 0.2)), - fill = from_theme(paper), size = from_theme(pointsize), + weight = 1, colour = from_theme(colour %||% col_mix(ink, paper, 0.2)), + fill = from_theme(fill %||% paper), size = from_theme(pointsize), alpha = NA, shape = from_theme(pointshape), linetype = from_theme(bordertype), linewidth = from_theme(borderwidth), width = 0.9 diff --git a/R/geom-contour.R b/R/geom-contour.R index a73bc3a135..00cddd51e5 100644 --- a/R/geom-contour.R +++ b/R/geom-contour.R @@ -124,13 +124,7 @@ geom_contour_filled <- function(mapping = NULL, data = NULL, #' @export #' @include geom-path.R GeomContour <- ggproto("GeomContour", GeomPath, - default_aes = aes( - weight = 1, - colour = from_theme(accent), - linewidth = from_theme(linewidth), - linetype = from_theme(linetype), - alpha = NA - ) + default_aes = aes(weight = 1, !!!GeomPath$default_aes) ) #' @rdname ggplot2-ggproto diff --git a/R/geom-crossbar.R b/R/geom-crossbar.R index f1db25bab9..c8452b2e9a 100644 --- a/R/geom-crossbar.R +++ b/R/geom-crossbar.R @@ -79,8 +79,8 @@ GeomCrossbar <- ggproto("GeomCrossbar", Geom, }, default_aes = aes( - colour = from_theme(ink), - fill = NA, + colour = from_theme(colour %||% ink), + fill = from_theme(fill %||% NA), linewidth = from_theme(borderwidth), linetype = from_theme(bordertype), alpha = NA diff --git a/R/geom-curve.R b/R/geom-curve.R index e1c38d1cd4..23b2e551ed 100644 --- a/R/geom-curve.R +++ b/R/geom-curve.R @@ -41,13 +41,6 @@ geom_curve <- function(mapping = NULL, data = NULL, #' @export GeomCurve <- ggproto("GeomCurve", GeomSegment, - default_aes = aes( - colour = from_theme(ink), - linewidth = from_theme(linewidth), - linetype = from_theme(linetype), - alpha = NA - ), - draw_panel = function(data, panel_params, coord, curvature = 0.5, angle = 90, ncp = 5, arrow = NULL, arrow.fill = NULL, lineend = "butt", na.rm = FALSE) { diff --git a/R/geom-density.R b/R/geom-density.R index a4a7754f2e..bc9bfd7b81 100644 --- a/R/geom-density.R +++ b/R/geom-density.R @@ -92,8 +92,12 @@ geom_density <- function(mapping = NULL, data = NULL, #' @export #' @include geom-ribbon.R GeomDensity <- ggproto("GeomDensity", GeomArea, - default_aes = defaults( - aes(fill = NA, weight = 1, colour = from_theme(ink), alpha = NA), - GeomArea$default_aes + default_aes = aes( + colour = from_theme(colour %||% ink), + fill = from_theme(fill %||% NA), + weight = 1, + alpha = NA, + linewidth = from_theme(borderwidth), + linetype = from_theme(bordertype) ) ) diff --git a/R/geom-density2d.R b/R/geom-density2d.R index 832546b563..778cac80fe 100644 --- a/R/geom-density2d.R +++ b/R/geom-density2d.R @@ -107,7 +107,7 @@ geom_density2d <- geom_density_2d #' @export GeomDensity2d <- ggproto("GeomDensity2d", GeomPath, default_aes = aes( - colour = from_theme(accent), + colour = from_theme(colour %||% accent), linewidth = from_theme(linewidth), linetype = from_theme(linetype), alpha = NA diff --git a/R/geom-dotplot.R b/R/geom-dotplot.R index 09ebeb793e..e912c44877 100644 --- a/R/geom-dotplot.R +++ b/R/geom-dotplot.R @@ -189,8 +189,8 @@ GeomDotplot <- ggproto("GeomDotplot", Geom, non_missing_aes = c("size", "shape"), default_aes = aes( - colour = from_theme(ink), - fill = from_theme(ink), + colour = from_theme(colour %||% ink), + fill = from_theme(fill %||% ink), alpha = NA, stroke = from_theme(borderwidth * 2), linetype = from_theme(linetype), diff --git a/R/geom-errorbar.R b/R/geom-errorbar.R index 3e50c59877..f6102a04d6 100644 --- a/R/geom-errorbar.R +++ b/R/geom-errorbar.R @@ -59,7 +59,7 @@ geom_errorbarh <- function(mapping = NULL, data = NULL, GeomErrorbar <- ggproto("GeomErrorbar", Geom, default_aes = aes( - colour = from_theme(ink), + colour = from_theme(colour %||% ink), linewidth = from_theme(linewidth), linetype = from_theme(linetype), width = 0.9, diff --git a/R/geom-hex.R b/R/geom-hex.R index 5add9250c8..27db70f1d5 100644 --- a/R/geom-hex.R +++ b/R/geom-hex.R @@ -107,8 +107,8 @@ GeomHex <- ggproto("GeomHex", Geom, required_aes = c("x", "y"), default_aes = aes( - colour = NA, - fill = from_theme(col_mix(ink, paper)), + colour = from_theme(colour %||% NA), + fill = from_theme(fill %||% col_mix(ink, paper)), linewidth = from_theme(borderwidth), linetype = from_theme(bordertype), alpha = NA diff --git a/R/geom-hline.R b/R/geom-hline.R index 2650066183..0ebf2436fc 100644 --- a/R/geom-hline.R +++ b/R/geom-hline.R @@ -57,7 +57,7 @@ GeomHline <- ggproto("GeomHline", Geom, }, default_aes = aes( - colour = from_theme(ink), + colour = from_theme(colour %||% ink), linewidth = from_theme(linewidth), linetype = from_theme(linetype), alpha = NA diff --git a/R/geom-label.R b/R/geom-label.R index ae21a48df3..13c679ac17 100644 --- a/R/geom-label.R +++ b/R/geom-label.R @@ -62,7 +62,8 @@ GeomLabel <- ggproto("GeomLabel", Geom, required_aes = c("x", "y", "label"), default_aes = aes( - colour = from_theme(ink), fill = from_theme(paper), + colour = from_theme(colour %||% ink), + fill = from_theme(fill %||% paper), family = from_theme(family), size = from_theme(fontsize), angle = 0, diff --git a/R/geom-linerange.R b/R/geom-linerange.R index 71c0799971..acaefbc9b2 100644 --- a/R/geom-linerange.R +++ b/R/geom-linerange.R @@ -91,12 +91,7 @@ geom_linerange <- function(mapping = NULL, data = NULL, #' @export GeomLinerange <- ggproto("GeomLinerange", Geom, - default_aes = aes( - colour = from_theme(ink), - linewidth = from_theme(linewidth), - linetype = from_theme(linetype), - alpha = NA - ), + default_aes = GeomPath$default_aes, draw_key = draw_key_linerange, diff --git a/R/geom-point.R b/R/geom-point.R index 47f3fc6fc2..a46a3a3245 100644 --- a/R/geom-point.R +++ b/R/geom-point.R @@ -143,8 +143,11 @@ GeomPoint <- ggproto("GeomPoint", Geom, non_missing_aes = c("size", "shape", "colour"), default_aes = aes( shape = from_theme(pointshape), - colour = from_theme(ink), size = from_theme(pointsize), fill = NA, - alpha = NA, stroke = from_theme(borderwidth) + colour = from_theme(colour %||% ink), + fill = from_theme(fill %||% NA), + size = from_theme(pointsize), + alpha = NA, + stroke = from_theme(borderwidth) ), draw_panel = function(self, data, panel_params, coord, na.rm = FALSE) { diff --git a/R/geom-pointrange.R b/R/geom-pointrange.R index c13b6a813e..0ffa1bf51f 100644 --- a/R/geom-pointrange.R +++ b/R/geom-pointrange.R @@ -31,9 +31,9 @@ geom_pointrange <- function(mapping = NULL, data = NULL, #' @export GeomPointrange <- ggproto("GeomPointrange", Geom, default_aes = aes( - colour = from_theme(ink), size = from_theme(pointsize / 3), + colour = from_theme(colour %||% ink), size = from_theme(pointsize / 3), linewidth = from_theme(linewidth), linetype = from_theme(linetype), - shape = from_theme(pointshape), fill = NA, alpha = NA, + shape = from_theme(pointshape), fill = from_theme(fill %||% NA), alpha = NA, stroke = from_theme(borderwidth * 2) ), diff --git a/R/geom-polygon.R b/R/geom-polygon.R index a97d3c2194..8ffdd05e58 100644 --- a/R/geom-polygon.R +++ b/R/geom-polygon.R @@ -176,8 +176,8 @@ GeomPolygon <- ggproto("GeomPolygon", Geom, }, default_aes = aes( - colour = NA, - fill = from_theme(col_mix(ink, paper, 0.2)), + colour = from_theme(colour %||% NA), + fill = from_theme(fill %||% col_mix(ink, paper, 0.2)), linewidth = from_theme(borderwidth), linetype = from_theme(bordertype), alpha = NA, subgroup = NULL diff --git a/R/geom-quantile.R b/R/geom-quantile.R index 732ab62f8a..ecdf7f69fb 100644 --- a/R/geom-quantile.R +++ b/R/geom-quantile.R @@ -65,8 +65,8 @@ geom_quantile <- function(mapping = NULL, data = NULL, #' @export #' @include geom-path.R GeomQuantile <- ggproto("GeomQuantile", GeomPath, - default_aes = defaults( - aes(weight = 1, colour = from_theme(accent)), + default_aes = aes(!!!defaults( + aes(weight = 1, colour = from_theme(colour %||% accent)), GeomPath$default_aes - ) + )) ) diff --git a/R/geom-raster.R b/R/geom-raster.R index 94b1775373..3e3c58975b 100644 --- a/R/geom-raster.R +++ b/R/geom-raster.R @@ -44,7 +44,10 @@ geom_raster <- function(mapping = NULL, data = NULL, #' @usage NULL #' @export GeomRaster <- ggproto("GeomRaster", Geom, - default_aes = aes(fill = from_theme(col_mix(ink, paper, 0.2)), alpha = NA), + default_aes = aes( + fill = from_theme(fill %||% col_mix(ink, paper, 0.2)), + alpha = NA + ), non_missing_aes = c("fill", "xmin", "xmax", "ymin", "ymax"), required_aes = c("x", "y"), diff --git a/R/geom-rect.R b/R/geom-rect.R index 1765a2506a..9799f82cf2 100644 --- a/R/geom-rect.R +++ b/R/geom-rect.R @@ -29,7 +29,8 @@ geom_rect <- function(mapping = NULL, data = NULL, #' @export GeomRect <- ggproto("GeomRect", Geom, default_aes = aes( - colour = NA, fill = from_theme(col_mix(ink, paper, 0.35)), + colour = from_theme(colour %||% NA), + fill = from_theme(fill %||% col_mix(ink, paper, 0.35)), linewidth = from_theme(borderwidth), linetype = from_theme(bordertype), alpha = NA ), diff --git a/R/geom-ribbon.R b/R/geom-ribbon.R index 746684afbe..c34a9ddab8 100644 --- a/R/geom-ribbon.R +++ b/R/geom-ribbon.R @@ -96,12 +96,14 @@ geom_ribbon <- function(mapping = NULL, data = NULL, #' @usage NULL #' @export GeomRibbon <- ggproto("GeomRibbon", Geom, + default_aes = aes( - colour = NA, - fill = from_theme(col_mix(ink, paper, 0.2)), + colour = from_theme(colour %||% NA), + fill = from_theme(fill %||% col_mix(ink, paper, 0.2)), linewidth = from_theme(borderwidth), linetype = from_theme(bordertype), - alpha = NA), + alpha = NA + ), required_aes = c("x|y", "ymin|xmin", "ymax|xmax"), @@ -320,14 +322,6 @@ geom_area <- function(mapping = NULL, data = NULL, stat = "align", #' @export GeomArea <- ggproto("GeomArea", GeomRibbon, - default_aes = aes( - colour = NA, - fill = from_theme(col_mix(ink, paper, 0.2)), - linewidth = from_theme(borderwidth), - linetype = from_theme(bordertype), - alpha = NA - ), - required_aes = c("x", "y"), setup_params = function(data, params) { diff --git a/R/geom-rug.R b/R/geom-rug.R index 8992f1069d..bcc7adca7a 100644 --- a/R/geom-rug.R +++ b/R/geom-rug.R @@ -153,12 +153,7 @@ GeomRug <- ggproto("GeomRug", Geom, gTree(children = inject(gList(!!!rugs))) }, - default_aes = aes( - colour = from_theme(ink), - linewidth = from_theme(linewidth), - linetype = from_theme(linetype), - alpha = NA - ), + default_aes = GeomPath$default_aes, draw_key = draw_key_path, diff --git a/R/geom-segment.R b/R/geom-segment.R index 51de135b53..fb00f0481d 100644 --- a/R/geom-segment.R +++ b/R/geom-segment.R @@ -105,12 +105,7 @@ GeomSegment <- ggproto("GeomSegment", Geom, required_aes = c("x", "y", "xend|yend"), non_missing_aes = c("linetype", "linewidth"), - default_aes = aes( - colour = from_theme(ink), - linewidth = from_theme(linewidth), - linetype = from_theme(linetype), - alpha = NA - ), + default_aes = GeomPath$default_aes, draw_panel = function(self, data, panel_params, coord, arrow = NULL, arrow.fill = NULL, lineend = "butt", linejoin = "round", na.rm = FALSE) { diff --git a/R/geom-sf.R b/R/geom-sf.R index 5ba2b3d846..448329dd79 100644 --- a/R/geom-sf.R +++ b/R/geom-sf.R @@ -171,8 +171,8 @@ GeomSf <- ggproto("GeomSf", Geom, other_default <- modify_list( GeomPolygon$default_aes, aes( - fill = from_theme(col_mix(ink, paper, 0.9)), - colour = from_theme(col_mix(ink, paper, 0.35)), + fill = from_theme(fill %||% col_mix(ink, paper, 0.9)), + colour = from_theme(colour %||% col_mix(ink, paper, 0.35)), linewidth = from_theme(0.4 * borderwidth) ) ) diff --git a/R/geom-smooth.R b/R/geom-smooth.R index 08e1099df0..c386504fa8 100644 --- a/R/geom-smooth.R +++ b/R/geom-smooth.R @@ -169,8 +169,8 @@ GeomSmooth <- ggproto("GeomSmooth", Geom, optional_aes = c("ymin", "ymax"), default_aes = aes( - colour = from_theme(accent), - fill = from_theme(col_mix(ink, paper, 0.6)), + colour = from_theme(colour %||% accent), + fill = from_theme(fill %||% col_mix(ink, paper, 0.6)), linewidth = from_theme(2 * linewidth), linetype = from_theme(linetype), weight = 1, alpha = 0.4 diff --git a/R/geom-text.R b/R/geom-text.R index 7e7a1b8f81..7ea074fc60 100644 --- a/R/geom-text.R +++ b/R/geom-text.R @@ -190,7 +190,7 @@ GeomText <- ggproto("GeomText", Geom, non_missing_aes = "angle", default_aes = aes( - colour = from_theme(ink), + colour = from_theme(colour %||% ink), family = from_theme(family), size = from_theme(fontsize), angle = 0, hjust = 0.5, diff --git a/R/geom-tile.R b/R/geom-tile.R index 04ff0b71c2..fabf70a4a9 100644 --- a/R/geom-tile.R +++ b/R/geom-tile.R @@ -130,8 +130,8 @@ GeomTile <- ggproto("GeomTile", GeomRect, }, default_aes = aes( - fill = from_theme(col_mix(ink, paper, 0.2)), - colour = NA, + fill = from_theme(fill %||% col_mix(ink, paper, 0.2)), + colour = from_theme(colour %||% NA), linewidth = from_theme(0.4 * borderwidth), linetype = from_theme(bordertype), alpha = NA, width = 1, height = 1 diff --git a/R/geom-violin.R b/R/geom-violin.R index 1ad8c2172a..24d8fd07d9 100644 --- a/R/geom-violin.R +++ b/R/geom-violin.R @@ -230,8 +230,8 @@ GeomViolin <- ggproto("GeomViolin", Geom, default_aes = aes( weight = 1, - colour = from_theme(col_mix(ink, paper, 0.2)), - fill = from_theme(paper), + colour = from_theme(colour %||% col_mix(ink, paper, 0.2)), + fill = from_theme(fill %||% paper), linewidth = from_theme(borderwidth), linetype = from_theme(bordertype), alpha = NA, diff --git a/R/geom-vline.R b/R/geom-vline.R index a9a50e6ff3..23093fcbcd 100644 --- a/R/geom-vline.R +++ b/R/geom-vline.R @@ -56,12 +56,7 @@ GeomVline <- ggproto("GeomVline", Geom, GeomSegment$draw_panel(unique0(data), panel_params, coord, lineend = lineend) }, - default_aes = aes( - colour = from_theme(ink), - linewidth = from_theme(linewidth), - linetype = from_theme(linetype), - alpha = NA - ), + default_aes = GeomPath$default_aes, required_aes = "xintercept", diff --git a/R/theme-elements.R b/R/theme-elements.R index c3b6ded319..12ee5ed524 100644 --- a/R/theme-elements.R +++ b/R/theme-elements.R @@ -213,7 +213,9 @@ element_geom <- function( # text family = NULL, fontsize = NULL, # points - pointsize = NULL, pointshape = NULL) { + pointsize = NULL, pointshape = NULL, + + colour = NULL, color = NULL, fill = NULL) { if (!is.null(fontsize)) { fontsize <- fontsize / .pt @@ -227,7 +229,9 @@ element_geom <- function( linewidth = linewidth, borderwidth = borderwidth, linetype = linetype, bordertype = bordertype, family = family, fontsize = fontsize, - pointsize = pointsize, pointshape = pointshape + pointsize = pointsize, pointshape = pointshape, + colour = color %||% colour, + fill = fill ), class = c("element_geom", "element") ) @@ -238,7 +242,8 @@ element_geom <- function( linewidth = 0.5, borderwidth = 0.5, linetype = 1L, bordertype = 1L, family = "", fontsize = 11, - pointsize = 1.5, pointshape = 19 + pointsize = 1.5, pointshape = 19, + fill = NULL, colour = NULL ) #' @export diff --git a/R/theme.R b/R/theme.R index dfe986fc62..846ef8e1fc 100644 --- a/R/theme.R +++ b/R/theme.R @@ -574,8 +574,11 @@ check_theme <- function(theme, tree = get_element_tree(), call = caller_env()) { if (!is_theme_validate(theme)) { return() } + elnames <- names(theme) + elnames[startsWith(elnames, "geom.")] <- "geom" + mapply( - check_element, theme, names(theme), + check_element, theme, elnames, MoreArgs = list(element_tree = tree, call = call) ) } @@ -639,7 +642,10 @@ plot_theme <- function(x, default = get_theme()) { check_theme(theme) # Remove elements that are not registered - theme[setdiff(names(theme), names(get_element_tree()))] <- NULL + # We accept unregistered `geom.*` elements + remove <- setdiff(names(theme), names(get_element_tree())) + remove <- remove[!startsWith(remove, "geom.")] + theme[remove] <- NULL theme } @@ -754,6 +760,11 @@ calc_element <- function(element, theme, verbose = FALSE, skip_blank = FALSE, # if we have null properties, try to fill in from ggplot_global$theme_default el_out <- combine_elements(el_out, ggplot_global$theme_default[[element]]) nullprops <- vapply(el_out, is.null, logical(1)) + if (inherits(el_out, "element_geom")) { + # Geom elements are expected to have NULL fill/colour, so allow these + # to be missing + nullprops[c("colour", "fill")] <- FALSE + } if (!any(nullprops)) { return(el_out) # no null properties remaining, return element } diff --git a/R/utilities-help.R b/R/utilities-help.R index e97e7ad50e..15a8069d66 100644 --- a/R/utilities-help.R +++ b/R/utilities-help.R @@ -12,11 +12,10 @@ rd_aesthetics <- function(type, name, extra_note = NULL) { "@section Aesthetics:", paste0( "\\code{", type, "_", name, "()} ", - "understands the following aesthetics (required aesthetics are in bold):" + "understands the following aesthetics. Required aesthetics are displayed", + " in bold and defaults are displayed for optional aesthetics:" ), - "\\itemize{", - paste0(" \\item ", aes), - "}", + "\\tabular{rll}{", aes, "}", if (!is.null(extra_note)) paste0(extra_note, "\n"), "Learn more about setting these aesthetics in \\code{vignette(\"ggplot2-specs\")}." ) @@ -29,11 +28,34 @@ rd_aesthetics_item <- function(x) { optional_aes <- setdiff(x$aesthetics(), req_aes) all <- union(req, sort(optional_aes)) docs <- rd_match_docpage(all) + defaults <- rd_defaults(x, all) item <- ifelse(all %in% req, paste0("\\strong{\\code{", docs, "}}"), paste0("\\code{", docs, "}") ) + paste0(" \u2022 \\tab ", item, " \\tab ", defaults, " \\cr\\cr") +} + +rd_defaults <- function(layer, aesthetics) { + defaults <- layer$default_aes + + out <- rep("", length(aesthetics)) + + themed <- vapply(defaults, FUN.VALUE = logical(1), function(x) { + is_quosure(x) && quo_is_call(x, name = "from_theme") + }) + defaults <- lapply(defaults, quo_text) + defaults[themed] <- "via \\code{theme()}" + defaults[!themed] <- paste0("\\code{", defaults[!themed], "}") + + i <- intersect(aesthetics, names(defaults)) + out[match(i, aesthetics)] <- defaults[i] + empty <- !nzchar(out) + out[!empty] <- paste0("\u2192 ", out[!empty]) + out[empty] <- " " + out[empty & aesthetics == "group"] <- "\u2192 inferred" + out } rd_match_docpage <- function(aes) { diff --git a/man/element.Rd b/man/element.Rd index 99e56f0e94..84fe10fd20 100644 --- a/man/element.Rd +++ b/man/element.Rd @@ -83,7 +83,10 @@ element_geom( family = NULL, fontsize = NULL, pointsize = NULL, - pointshape = NULL + pointshape = NULL, + colour = NULL, + color = NULL, + fill = NULL ) rel(x) diff --git a/man/geom_bar.Rd b/man/geom_bar.Rd index 6c8c67cc19..1d19ff8f90 100644 --- a/man/geom_bar.Rd +++ b/man/geom_bar.Rd @@ -168,41 +168,41 @@ This geom treats each axis differently and, thus, can thus have two orientations \section{Aesthetics}{ -\code{geom_bar()} understands the following aesthetics (required aesthetics are in bold): -\itemize{ -\item \strong{\code{\link[=aes_position]{x}}} -\item \strong{\code{\link[=aes_position]{y}}} -\item \code{\link[=aes_colour_fill_alpha]{alpha}} -\item \code{\link[=aes_colour_fill_alpha]{colour}} -\item \code{\link[=aes_colour_fill_alpha]{fill}} -\item \code{\link[=aes_group_order]{group}} -\item \code{\link[=aes_linetype_size_shape]{linetype}} -\item \code{\link[=aes_linetype_size_shape]{linewidth}} -\item \code{width} +\code{geom_bar()} understands the following aesthetics. Required aesthetics are displayed in bold and defaults are displayed for optional aesthetics: +\tabular{rll}{ +• \tab \strong{\code{\link[=aes_position]{x}}} \tab \cr\cr +• \tab \strong{\code{\link[=aes_position]{y}}} \tab \cr\cr +• \tab \code{\link[=aes_colour_fill_alpha]{alpha}} \tab → \code{NA} \cr\cr +• \tab \code{\link[=aes_colour_fill_alpha]{colour}} \tab → via \code{theme()} \cr\cr +• \tab \code{\link[=aes_colour_fill_alpha]{fill}} \tab → via \code{theme()} \cr\cr +• \tab \code{\link[=aes_group_order]{group}} \tab → inferred \cr\cr +• \tab \code{\link[=aes_linetype_size_shape]{linetype}} \tab → via \code{theme()} \cr\cr +• \tab \code{\link[=aes_linetype_size_shape]{linewidth}} \tab → via \code{theme()} \cr\cr +• \tab \code{width} \tab → \code{0.9} \cr\cr } Learn more about setting these aesthetics in \code{vignette("ggplot2-specs")}. -\code{geom_col()} understands the following aesthetics (required aesthetics are in bold): -\itemize{ -\item \strong{\code{\link[=aes_position]{x}}} -\item \strong{\code{\link[=aes_position]{y}}} -\item \code{\link[=aes_colour_fill_alpha]{alpha}} -\item \code{\link[=aes_colour_fill_alpha]{colour}} -\item \code{\link[=aes_colour_fill_alpha]{fill}} -\item \code{\link[=aes_group_order]{group}} -\item \code{\link[=aes_linetype_size_shape]{linetype}} -\item \code{\link[=aes_linetype_size_shape]{linewidth}} -\item \code{width} +\code{geom_col()} understands the following aesthetics. Required aesthetics are displayed in bold and defaults are displayed for optional aesthetics: +\tabular{rll}{ +• \tab \strong{\code{\link[=aes_position]{x}}} \tab \cr\cr +• \tab \strong{\code{\link[=aes_position]{y}}} \tab \cr\cr +• \tab \code{\link[=aes_colour_fill_alpha]{alpha}} \tab → \code{NA} \cr\cr +• \tab \code{\link[=aes_colour_fill_alpha]{colour}} \tab → via \code{theme()} \cr\cr +• \tab \code{\link[=aes_colour_fill_alpha]{fill}} \tab → via \code{theme()} \cr\cr +• \tab \code{\link[=aes_group_order]{group}} \tab → inferred \cr\cr +• \tab \code{\link[=aes_linetype_size_shape]{linetype}} \tab → via \code{theme()} \cr\cr +• \tab \code{\link[=aes_linetype_size_shape]{linewidth}} \tab → via \code{theme()} \cr\cr +• \tab \code{width} \tab → \code{0.9} \cr\cr } Learn more about setting these aesthetics in \code{vignette("ggplot2-specs")}. -\code{stat_count()} understands the following aesthetics (required aesthetics are in bold): -\itemize{ -\item \strong{\code{\link[=aes_position]{x}} \emph{or} \code{\link[=aes_position]{y}}} -\item \code{\link[=aes_group_order]{group}} -\item \code{weight} +\code{stat_count()} understands the following aesthetics. Required aesthetics are displayed in bold and defaults are displayed for optional aesthetics: +\tabular{rll}{ +• \tab \strong{\code{\link[=aes_position]{x}} \emph{or} \code{\link[=aes_position]{y}}} \tab \cr\cr +• \tab \code{\link[=aes_group_order]{group}} \tab → inferred \cr\cr +• \tab \code{weight} \tab → \code{1} \cr\cr } Learn more about setting these aesthetics in \code{vignette("ggplot2-specs")}. } diff --git a/man/geom_bin_2d.Rd b/man/geom_bin_2d.Rd index dc0b9ce082..16b0fa4dad 100644 --- a/man/geom_bin_2d.Rd +++ b/man/geom_bin_2d.Rd @@ -156,13 +156,13 @@ in the presence of overplotting. } \section{Aesthetics}{ -\code{stat_bin_2d()} understands the following aesthetics (required aesthetics are in bold): -\itemize{ -\item \strong{\code{\link[=aes_position]{x}}} -\item \strong{\code{\link[=aes_position]{y}}} -\item \code{\link[=aes_colour_fill_alpha]{fill}} -\item \code{\link[=aes_group_order]{group}} -\item \code{weight} +\code{stat_bin_2d()} understands the following aesthetics. Required aesthetics are displayed in bold and defaults are displayed for optional aesthetics: +\tabular{rll}{ +• \tab \strong{\code{\link[=aes_position]{x}}} \tab \cr\cr +• \tab \strong{\code{\link[=aes_position]{y}}} \tab \cr\cr +• \tab \code{\link[=aes_colour_fill_alpha]{fill}} \tab → \code{after_stat(count)} \cr\cr +• \tab \code{\link[=aes_group_order]{group}} \tab → inferred \cr\cr +• \tab \code{weight} \tab → \code{1} \cr\cr } Learn more about setting these aesthetics in \code{vignette("ggplot2-specs")}. } diff --git a/man/geom_boxplot.Rd b/man/geom_boxplot.Rd index 5760caa71a..d96c576da0 100644 --- a/man/geom_boxplot.Rd +++ b/man/geom_boxplot.Rd @@ -223,24 +223,24 @@ See McGill et al. (1978) for more details. \section{Aesthetics}{ -\code{geom_boxplot()} understands the following aesthetics (required aesthetics are in bold): -\itemize{ -\item \strong{\code{\link[=aes_position]{x}} \emph{or} \code{\link[=aes_position]{y}}} -\item \strong{\code{lower} \emph{or} \code{xlower}} -\item \strong{\code{upper} \emph{or} \code{xupper}} -\item \strong{\code{middle} \emph{or} \code{xmiddle}} -\item \strong{\code{\link[=aes_position]{ymin}} \emph{or} \code{\link[=aes_position]{xmin}}} -\item \strong{\code{\link[=aes_position]{ymax}} \emph{or} \code{\link[=aes_position]{xmax}}} -\item \code{\link[=aes_colour_fill_alpha]{alpha}} -\item \code{\link[=aes_colour_fill_alpha]{colour}} -\item \code{\link[=aes_colour_fill_alpha]{fill}} -\item \code{\link[=aes_group_order]{group}} -\item \code{\link[=aes_linetype_size_shape]{linetype}} -\item \code{\link[=aes_linetype_size_shape]{linewidth}} -\item \code{\link[=aes_linetype_size_shape]{shape}} -\item \code{\link[=aes_linetype_size_shape]{size}} -\item \code{weight} -\item \code{width} +\code{geom_boxplot()} understands the following aesthetics. Required aesthetics are displayed in bold and defaults are displayed for optional aesthetics: +\tabular{rll}{ +• \tab \strong{\code{\link[=aes_position]{x}} \emph{or} \code{\link[=aes_position]{y}}} \tab \cr\cr +• \tab \strong{\code{lower} \emph{or} \code{xlower}} \tab \cr\cr +• \tab \strong{\code{upper} \emph{or} \code{xupper}} \tab \cr\cr +• \tab \strong{\code{middle} \emph{or} \code{xmiddle}} \tab \cr\cr +• \tab \strong{\code{\link[=aes_position]{ymin}} \emph{or} \code{\link[=aes_position]{xmin}}} \tab \cr\cr +• \tab \strong{\code{\link[=aes_position]{ymax}} \emph{or} \code{\link[=aes_position]{xmax}}} \tab \cr\cr +• \tab \code{\link[=aes_colour_fill_alpha]{alpha}} \tab → \code{NA} \cr\cr +• \tab \code{\link[=aes_colour_fill_alpha]{colour}} \tab → via \code{theme()} \cr\cr +• \tab \code{\link[=aes_colour_fill_alpha]{fill}} \tab → via \code{theme()} \cr\cr +• \tab \code{\link[=aes_group_order]{group}} \tab → inferred \cr\cr +• \tab \code{\link[=aes_linetype_size_shape]{linetype}} \tab → via \code{theme()} \cr\cr +• \tab \code{\link[=aes_linetype_size_shape]{linewidth}} \tab → via \code{theme()} \cr\cr +• \tab \code{\link[=aes_linetype_size_shape]{shape}} \tab → via \code{theme()} \cr\cr +• \tab \code{\link[=aes_linetype_size_shape]{size}} \tab → via \code{theme()} \cr\cr +• \tab \code{weight} \tab → \code{1} \cr\cr +• \tab \code{width} \tab → \code{0.9} \cr\cr } Learn more about setting these aesthetics in \code{vignette("ggplot2-specs")}. } diff --git a/man/geom_contour.Rd b/man/geom_contour.Rd index c42aec41c9..2336ec973f 100644 --- a/man/geom_contour.Rd +++ b/man/geom_contour.Rd @@ -204,54 +204,54 @@ using \code{\link[interp:interp]{interp::interp()}}, \code{\link[akima:bilinear] } \section{Aesthetics}{ -\code{geom_contour()} understands the following aesthetics (required aesthetics are in bold): -\itemize{ -\item \strong{\code{\link[=aes_position]{x}}} -\item \strong{\code{\link[=aes_position]{y}}} -\item \code{\link[=aes_colour_fill_alpha]{alpha}} -\item \code{\link[=aes_colour_fill_alpha]{colour}} -\item \code{\link[=aes_group_order]{group}} -\item \code{\link[=aes_linetype_size_shape]{linetype}} -\item \code{\link[=aes_linetype_size_shape]{linewidth}} -\item \code{weight} +\code{geom_contour()} understands the following aesthetics. Required aesthetics are displayed in bold and defaults are displayed for optional aesthetics: +\tabular{rll}{ +• \tab \strong{\code{\link[=aes_position]{x}}} \tab \cr\cr +• \tab \strong{\code{\link[=aes_position]{y}}} \tab \cr\cr +• \tab \code{\link[=aes_colour_fill_alpha]{alpha}} \tab → \code{NA} \cr\cr +• \tab \code{\link[=aes_colour_fill_alpha]{colour}} \tab → via \code{theme()} \cr\cr +• \tab \code{\link[=aes_group_order]{group}} \tab → inferred \cr\cr +• \tab \code{\link[=aes_linetype_size_shape]{linetype}} \tab → via \code{theme()} \cr\cr +• \tab \code{\link[=aes_linetype_size_shape]{linewidth}} \tab → via \code{theme()} \cr\cr +• \tab \code{weight} \tab → \code{1} \cr\cr } Learn more about setting these aesthetics in \code{vignette("ggplot2-specs")}. -\code{geom_contour_filled()} understands the following aesthetics (required aesthetics are in bold): -\itemize{ -\item \strong{\code{\link[=aes_position]{x}}} -\item \strong{\code{\link[=aes_position]{y}}} -\item \code{\link[=aes_colour_fill_alpha]{alpha}} -\item \code{\link[=aes_colour_fill_alpha]{colour}} -\item \code{\link[=aes_colour_fill_alpha]{fill}} -\item \code{\link[=aes_group_order]{group}} -\item \code{\link[=aes_linetype_size_shape]{linetype}} -\item \code{\link[=aes_linetype_size_shape]{linewidth}} -\item \code{subgroup} +\code{geom_contour_filled()} understands the following aesthetics. Required aesthetics are displayed in bold and defaults are displayed for optional aesthetics: +\tabular{rll}{ +• \tab \strong{\code{\link[=aes_position]{x}}} \tab \cr\cr +• \tab \strong{\code{\link[=aes_position]{y}}} \tab \cr\cr +• \tab \code{\link[=aes_colour_fill_alpha]{alpha}} \tab → \code{NA} \cr\cr +• \tab \code{\link[=aes_colour_fill_alpha]{colour}} \tab → via \code{theme()} \cr\cr +• \tab \code{\link[=aes_colour_fill_alpha]{fill}} \tab → via \code{theme()} \cr\cr +• \tab \code{\link[=aes_group_order]{group}} \tab → inferred \cr\cr +• \tab \code{\link[=aes_linetype_size_shape]{linetype}} \tab → via \code{theme()} \cr\cr +• \tab \code{\link[=aes_linetype_size_shape]{linewidth}} \tab → via \code{theme()} \cr\cr +• \tab \code{subgroup} \tab → \code{NULL} \cr\cr } Learn more about setting these aesthetics in \code{vignette("ggplot2-specs")}. -\code{stat_contour()} understands the following aesthetics (required aesthetics are in bold): -\itemize{ -\item \strong{\code{\link[=aes_position]{x}}} -\item \strong{\code{\link[=aes_position]{y}}} -\item \strong{\code{z}} -\item \code{\link[=aes_group_order]{group}} -\item \code{order} +\code{stat_contour()} understands the following aesthetics. Required aesthetics are displayed in bold and defaults are displayed for optional aesthetics: +\tabular{rll}{ +• \tab \strong{\code{\link[=aes_position]{x}}} \tab \cr\cr +• \tab \strong{\code{\link[=aes_position]{y}}} \tab \cr\cr +• \tab \strong{\code{z}} \tab \cr\cr +• \tab \code{\link[=aes_group_order]{group}} \tab → inferred \cr\cr +• \tab \code{order} \tab → \code{after_stat(level)} \cr\cr } Learn more about setting these aesthetics in \code{vignette("ggplot2-specs")}. -\code{stat_contour_filled()} understands the following aesthetics (required aesthetics are in bold): -\itemize{ -\item \strong{\code{\link[=aes_position]{x}}} -\item \strong{\code{\link[=aes_position]{y}}} -\item \strong{\code{z}} -\item \code{\link[=aes_colour_fill_alpha]{fill}} -\item \code{\link[=aes_group_order]{group}} -\item \code{order} +\code{stat_contour_filled()} understands the following aesthetics. Required aesthetics are displayed in bold and defaults are displayed for optional aesthetics: +\tabular{rll}{ +• \tab \strong{\code{\link[=aes_position]{x}}} \tab \cr\cr +• \tab \strong{\code{\link[=aes_position]{y}}} \tab \cr\cr +• \tab \strong{\code{z}} \tab \cr\cr +• \tab \code{\link[=aes_colour_fill_alpha]{fill}} \tab → \code{after_stat(level)} \cr\cr +• \tab \code{\link[=aes_group_order]{group}} \tab → inferred \cr\cr +• \tab \code{order} \tab → \code{after_stat(level)} \cr\cr } Learn more about setting these aesthetics in \code{vignette("ggplot2-specs")}. } diff --git a/man/geom_count.Rd b/man/geom_count.Rd index 1b925e7450..753ec70728 100644 --- a/man/geom_count.Rd +++ b/man/geom_count.Rd @@ -117,17 +117,17 @@ useful when you have discrete data and overplotting. } \section{Aesthetics}{ -\code{geom_point()} understands the following aesthetics (required aesthetics are in bold): -\itemize{ -\item \strong{\code{\link[=aes_position]{x}}} -\item \strong{\code{\link[=aes_position]{y}}} -\item \code{\link[=aes_colour_fill_alpha]{alpha}} -\item \code{\link[=aes_colour_fill_alpha]{colour}} -\item \code{\link[=aes_colour_fill_alpha]{fill}} -\item \code{\link[=aes_group_order]{group}} -\item \code{\link[=aes_linetype_size_shape]{shape}} -\item \code{\link[=aes_linetype_size_shape]{size}} -\item \code{stroke} +\code{geom_point()} understands the following aesthetics. Required aesthetics are displayed in bold and defaults are displayed for optional aesthetics: +\tabular{rll}{ +• \tab \strong{\code{\link[=aes_position]{x}}} \tab \cr\cr +• \tab \strong{\code{\link[=aes_position]{y}}} \tab \cr\cr +• \tab \code{\link[=aes_colour_fill_alpha]{alpha}} \tab → \code{NA} \cr\cr +• \tab \code{\link[=aes_colour_fill_alpha]{colour}} \tab → via \code{theme()} \cr\cr +• \tab \code{\link[=aes_colour_fill_alpha]{fill}} \tab → via \code{theme()} \cr\cr +• \tab \code{\link[=aes_group_order]{group}} \tab → inferred \cr\cr +• \tab \code{\link[=aes_linetype_size_shape]{shape}} \tab → via \code{theme()} \cr\cr +• \tab \code{\link[=aes_linetype_size_shape]{size}} \tab → via \code{theme()} \cr\cr +• \tab \code{stroke} \tab → via \code{theme()} \cr\cr } Learn more about setting these aesthetics in \code{vignette("ggplot2-specs")}. } diff --git a/man/geom_density.Rd b/man/geom_density.Rd index 58f6dae9e2..1cb1b80b07 100644 --- a/man/geom_density.Rd +++ b/man/geom_density.Rd @@ -169,17 +169,17 @@ This geom treats each axis differently and, thus, can thus have two orientations \section{Aesthetics}{ -\code{geom_density()} understands the following aesthetics (required aesthetics are in bold): -\itemize{ -\item \strong{\code{\link[=aes_position]{x}}} -\item \strong{\code{\link[=aes_position]{y}}} -\item \code{\link[=aes_colour_fill_alpha]{alpha}} -\item \code{\link[=aes_colour_fill_alpha]{colour}} -\item \code{\link[=aes_colour_fill_alpha]{fill}} -\item \code{\link[=aes_group_order]{group}} -\item \code{\link[=aes_linetype_size_shape]{linetype}} -\item \code{\link[=aes_linetype_size_shape]{linewidth}} -\item \code{weight} +\code{geom_density()} understands the following aesthetics. Required aesthetics are displayed in bold and defaults are displayed for optional aesthetics: +\tabular{rll}{ +• \tab \strong{\code{\link[=aes_position]{x}}} \tab \cr\cr +• \tab \strong{\code{\link[=aes_position]{y}}} \tab \cr\cr +• \tab \code{\link[=aes_colour_fill_alpha]{alpha}} \tab → \code{NA} \cr\cr +• \tab \code{\link[=aes_colour_fill_alpha]{colour}} \tab → via \code{theme()} \cr\cr +• \tab \code{\link[=aes_colour_fill_alpha]{fill}} \tab → via \code{theme()} \cr\cr +• \tab \code{\link[=aes_group_order]{group}} \tab → inferred \cr\cr +• \tab \code{\link[=aes_linetype_size_shape]{linetype}} \tab → via \code{theme()} \cr\cr +• \tab \code{\link[=aes_linetype_size_shape]{linewidth}} \tab → via \code{theme()} \cr\cr +• \tab \code{weight} \tab → \code{1} \cr\cr } Learn more about setting these aesthetics in \code{vignette("ggplot2-specs")}. } diff --git a/man/geom_density_2d.Rd b/man/geom_density_2d.Rd index f063cfdd4a..18e423d60e 100644 --- a/man/geom_density_2d.Rd +++ b/man/geom_density_2d.Rd @@ -174,30 +174,30 @@ bands. } \section{Aesthetics}{ -\code{geom_density_2d()} understands the following aesthetics (required aesthetics are in bold): -\itemize{ -\item \strong{\code{\link[=aes_position]{x}}} -\item \strong{\code{\link[=aes_position]{y}}} -\item \code{\link[=aes_colour_fill_alpha]{alpha}} -\item \code{\link[=aes_colour_fill_alpha]{colour}} -\item \code{\link[=aes_group_order]{group}} -\item \code{\link[=aes_linetype_size_shape]{linetype}} -\item \code{\link[=aes_linetype_size_shape]{linewidth}} +\code{geom_density_2d()} understands the following aesthetics. Required aesthetics are displayed in bold and defaults are displayed for optional aesthetics: +\tabular{rll}{ +• \tab \strong{\code{\link[=aes_position]{x}}} \tab \cr\cr +• \tab \strong{\code{\link[=aes_position]{y}}} \tab \cr\cr +• \tab \code{\link[=aes_colour_fill_alpha]{alpha}} \tab → \code{NA} \cr\cr +• \tab \code{\link[=aes_colour_fill_alpha]{colour}} \tab → via \code{theme()} \cr\cr +• \tab \code{\link[=aes_group_order]{group}} \tab → inferred \cr\cr +• \tab \code{\link[=aes_linetype_size_shape]{linetype}} \tab → via \code{theme()} \cr\cr +• \tab \code{\link[=aes_linetype_size_shape]{linewidth}} \tab → via \code{theme()} \cr\cr } Learn more about setting these aesthetics in \code{vignette("ggplot2-specs")}. -\code{geom_density_2d_filled()} understands the following aesthetics (required aesthetics are in bold): -\itemize{ -\item \strong{\code{\link[=aes_position]{x}}} -\item \strong{\code{\link[=aes_position]{y}}} -\item \code{\link[=aes_colour_fill_alpha]{alpha}} -\item \code{\link[=aes_colour_fill_alpha]{colour}} -\item \code{\link[=aes_colour_fill_alpha]{fill}} -\item \code{\link[=aes_group_order]{group}} -\item \code{\link[=aes_linetype_size_shape]{linetype}} -\item \code{\link[=aes_linetype_size_shape]{linewidth}} -\item \code{subgroup} +\code{geom_density_2d_filled()} understands the following aesthetics. Required aesthetics are displayed in bold and defaults are displayed for optional aesthetics: +\tabular{rll}{ +• \tab \strong{\code{\link[=aes_position]{x}}} \tab \cr\cr +• \tab \strong{\code{\link[=aes_position]{y}}} \tab \cr\cr +• \tab \code{\link[=aes_colour_fill_alpha]{alpha}} \tab → \code{NA} \cr\cr +• \tab \code{\link[=aes_colour_fill_alpha]{colour}} \tab → via \code{theme()} \cr\cr +• \tab \code{\link[=aes_colour_fill_alpha]{fill}} \tab → via \code{theme()} \cr\cr +• \tab \code{\link[=aes_group_order]{group}} \tab → inferred \cr\cr +• \tab \code{\link[=aes_linetype_size_shape]{linetype}} \tab → via \code{theme()} \cr\cr +• \tab \code{\link[=aes_linetype_size_shape]{linewidth}} \tab → via \code{theme()} \cr\cr +• \tab \code{subgroup} \tab → \code{NULL} \cr\cr } Learn more about setting these aesthetics in \code{vignette("ggplot2-specs")}. } diff --git a/man/geom_dotplot.Rd b/man/geom_dotplot.Rd index 5dbf0614db..b8b68c2146 100644 --- a/man/geom_dotplot.Rd +++ b/man/geom_dotplot.Rd @@ -160,18 +160,18 @@ to match the number of dots. } \section{Aesthetics}{ -\code{geom_dotplot()} understands the following aesthetics (required aesthetics are in bold): -\itemize{ -\item \strong{\code{\link[=aes_position]{x}}} -\item \strong{\code{\link[=aes_position]{y}}} -\item \code{\link[=aes_colour_fill_alpha]{alpha}} -\item \code{\link[=aes_colour_fill_alpha]{colour}} -\item \code{\link[=aes_colour_fill_alpha]{fill}} -\item \code{\link[=aes_group_order]{group}} -\item \code{\link[=aes_linetype_size_shape]{linetype}} -\item \code{stroke} -\item \code{weight} -\item \code{width} +\code{geom_dotplot()} understands the following aesthetics. Required aesthetics are displayed in bold and defaults are displayed for optional aesthetics: +\tabular{rll}{ +• \tab \strong{\code{\link[=aes_position]{x}}} \tab \cr\cr +• \tab \strong{\code{\link[=aes_position]{y}}} \tab \cr\cr +• \tab \code{\link[=aes_colour_fill_alpha]{alpha}} \tab → \code{NA} \cr\cr +• \tab \code{\link[=aes_colour_fill_alpha]{colour}} \tab → via \code{theme()} \cr\cr +• \tab \code{\link[=aes_colour_fill_alpha]{fill}} \tab → via \code{theme()} \cr\cr +• \tab \code{\link[=aes_group_order]{group}} \tab → inferred \cr\cr +• \tab \code{\link[=aes_linetype_size_shape]{linetype}} \tab → via \code{theme()} \cr\cr +• \tab \code{stroke} \tab → via \code{theme()} \cr\cr +• \tab \code{weight} \tab → \code{1} \cr\cr +• \tab \code{width} \tab → \code{0.9} \cr\cr } Learn more about setting these aesthetics in \code{vignette("ggplot2-specs")}. } diff --git a/man/geom_function.Rd b/man/geom_function.Rd index faf9d8552e..be0a23541d 100644 --- a/man/geom_function.Rd +++ b/man/geom_function.Rd @@ -141,15 +141,15 @@ drawn (by default) with a line. } \section{Aesthetics}{ -\code{geom_function()} understands the following aesthetics (required aesthetics are in bold): -\itemize{ -\item \strong{\code{\link[=aes_position]{x}}} -\item \strong{\code{\link[=aes_position]{y}}} -\item \code{\link[=aes_colour_fill_alpha]{alpha}} -\item \code{\link[=aes_colour_fill_alpha]{colour}} -\item \code{\link[=aes_group_order]{group}} -\item \code{\link[=aes_linetype_size_shape]{linetype}} -\item \code{\link[=aes_linetype_size_shape]{linewidth}} +\code{geom_function()} understands the following aesthetics. Required aesthetics are displayed in bold and defaults are displayed for optional aesthetics: +\tabular{rll}{ +• \tab \strong{\code{\link[=aes_position]{x}}} \tab \cr\cr +• \tab \strong{\code{\link[=aes_position]{y}}} \tab \cr\cr +• \tab \code{\link[=aes_colour_fill_alpha]{alpha}} \tab → \code{NA} \cr\cr +• \tab \code{\link[=aes_colour_fill_alpha]{colour}} \tab → via \code{theme()} \cr\cr +• \tab \code{\link[=aes_group_order]{group}} \tab → inferred \cr\cr +• \tab \code{\link[=aes_linetype_size_shape]{linetype}} \tab → via \code{theme()} \cr\cr +• \tab \code{\link[=aes_linetype_size_shape]{linewidth}} \tab → via \code{theme()} \cr\cr } Learn more about setting these aesthetics in \code{vignette("ggplot2-specs")}. } diff --git a/man/geom_hex.Rd b/man/geom_hex.Rd index da103b0e3c..bbe58dd8f5 100644 --- a/man/geom_hex.Rd +++ b/man/geom_hex.Rd @@ -134,27 +134,27 @@ the very regular alignment of \code{\link[=geom_bin_2d]{geom_bin_2d()}}. } \section{Aesthetics}{ -\code{geom_hex()} understands the following aesthetics (required aesthetics are in bold): -\itemize{ -\item \strong{\code{\link[=aes_position]{x}}} -\item \strong{\code{\link[=aes_position]{y}}} -\item \code{\link[=aes_colour_fill_alpha]{alpha}} -\item \code{\link[=aes_colour_fill_alpha]{colour}} -\item \code{\link[=aes_colour_fill_alpha]{fill}} -\item \code{\link[=aes_group_order]{group}} -\item \code{\link[=aes_linetype_size_shape]{linetype}} -\item \code{\link[=aes_linetype_size_shape]{linewidth}} +\code{geom_hex()} understands the following aesthetics. Required aesthetics are displayed in bold and defaults are displayed for optional aesthetics: +\tabular{rll}{ +• \tab \strong{\code{\link[=aes_position]{x}}} \tab \cr\cr +• \tab \strong{\code{\link[=aes_position]{y}}} \tab \cr\cr +• \tab \code{\link[=aes_colour_fill_alpha]{alpha}} \tab → \code{NA} \cr\cr +• \tab \code{\link[=aes_colour_fill_alpha]{colour}} \tab → via \code{theme()} \cr\cr +• \tab \code{\link[=aes_colour_fill_alpha]{fill}} \tab → via \code{theme()} \cr\cr +• \tab \code{\link[=aes_group_order]{group}} \tab → inferred \cr\cr +• \tab \code{\link[=aes_linetype_size_shape]{linetype}} \tab → via \code{theme()} \cr\cr +• \tab \code{\link[=aes_linetype_size_shape]{linewidth}} \tab → via \code{theme()} \cr\cr } Learn more about setting these aesthetics in \code{vignette("ggplot2-specs")}. -\code{stat_binhex()} understands the following aesthetics (required aesthetics are in bold): -\itemize{ -\item \strong{\code{\link[=aes_position]{x}}} -\item \strong{\code{\link[=aes_position]{y}}} -\item \code{\link[=aes_colour_fill_alpha]{fill}} -\item \code{\link[=aes_group_order]{group}} -\item \code{weight} +\code{stat_binhex()} understands the following aesthetics. Required aesthetics are displayed in bold and defaults are displayed for optional aesthetics: +\tabular{rll}{ +• \tab \strong{\code{\link[=aes_position]{x}}} \tab \cr\cr +• \tab \strong{\code{\link[=aes_position]{y}}} \tab \cr\cr +• \tab \code{\link[=aes_colour_fill_alpha]{fill}} \tab → \code{after_stat(count)} \cr\cr +• \tab \code{\link[=aes_group_order]{group}} \tab → inferred \cr\cr +• \tab \code{weight} \tab → \code{1} \cr\cr } Learn more about setting these aesthetics in \code{vignette("ggplot2-specs")}. } diff --git a/man/geom_jitter.Rd b/man/geom_jitter.Rd index 03ad3e8490..afcb05e39e 100644 --- a/man/geom_jitter.Rd +++ b/man/geom_jitter.Rd @@ -125,17 +125,17 @@ overplotting caused by discreteness in smaller datasets. } \section{Aesthetics}{ -\code{geom_point()} understands the following aesthetics (required aesthetics are in bold): -\itemize{ -\item \strong{\code{\link[=aes_position]{x}}} -\item \strong{\code{\link[=aes_position]{y}}} -\item \code{\link[=aes_colour_fill_alpha]{alpha}} -\item \code{\link[=aes_colour_fill_alpha]{colour}} -\item \code{\link[=aes_colour_fill_alpha]{fill}} -\item \code{\link[=aes_group_order]{group}} -\item \code{\link[=aes_linetype_size_shape]{shape}} -\item \code{\link[=aes_linetype_size_shape]{size}} -\item \code{stroke} +\code{geom_point()} understands the following aesthetics. Required aesthetics are displayed in bold and defaults are displayed for optional aesthetics: +\tabular{rll}{ +• \tab \strong{\code{\link[=aes_position]{x}}} \tab \cr\cr +• \tab \strong{\code{\link[=aes_position]{y}}} \tab \cr\cr +• \tab \code{\link[=aes_colour_fill_alpha]{alpha}} \tab → \code{NA} \cr\cr +• \tab \code{\link[=aes_colour_fill_alpha]{colour}} \tab → via \code{theme()} \cr\cr +• \tab \code{\link[=aes_colour_fill_alpha]{fill}} \tab → via \code{theme()} \cr\cr +• \tab \code{\link[=aes_group_order]{group}} \tab → inferred \cr\cr +• \tab \code{\link[=aes_linetype_size_shape]{shape}} \tab → via \code{theme()} \cr\cr +• \tab \code{\link[=aes_linetype_size_shape]{size}} \tab → via \code{theme()} \cr\cr +• \tab \code{stroke} \tab → via \code{theme()} \cr\cr } Learn more about setting these aesthetics in \code{vignette("ggplot2-specs")}. } diff --git a/man/geom_linerange.Rd b/man/geom_linerange.Rd index 0c77084236..e5208dce61 100644 --- a/man/geom_linerange.Rd +++ b/man/geom_linerange.Rd @@ -200,16 +200,16 @@ This geom treats each axis differently and, thus, can thus have two orientations \section{Aesthetics}{ -\code{geom_linerange()} understands the following aesthetics (required aesthetics are in bold): -\itemize{ -\item \strong{\code{\link[=aes_position]{x}} \emph{or} \code{\link[=aes_position]{y}}} -\item \strong{\code{\link[=aes_position]{ymin}} \emph{or} \code{\link[=aes_position]{xmin}}} -\item \strong{\code{\link[=aes_position]{ymax}} \emph{or} \code{\link[=aes_position]{xmax}}} -\item \code{\link[=aes_colour_fill_alpha]{alpha}} -\item \code{\link[=aes_colour_fill_alpha]{colour}} -\item \code{\link[=aes_group_order]{group}} -\item \code{\link[=aes_linetype_size_shape]{linetype}} -\item \code{\link[=aes_linetype_size_shape]{linewidth}} +\code{geom_linerange()} understands the following aesthetics. Required aesthetics are displayed in bold and defaults are displayed for optional aesthetics: +\tabular{rll}{ +• \tab \strong{\code{\link[=aes_position]{x}} \emph{or} \code{\link[=aes_position]{y}}} \tab \cr\cr +• \tab \strong{\code{\link[=aes_position]{ymin}} \emph{or} \code{\link[=aes_position]{xmin}}} \tab \cr\cr +• \tab \strong{\code{\link[=aes_position]{ymax}} \emph{or} \code{\link[=aes_position]{xmax}}} \tab \cr\cr +• \tab \code{\link[=aes_colour_fill_alpha]{alpha}} \tab → \code{NA} \cr\cr +• \tab \code{\link[=aes_colour_fill_alpha]{colour}} \tab → via \code{theme()} \cr\cr +• \tab \code{\link[=aes_group_order]{group}} \tab → inferred \cr\cr +• \tab \code{\link[=aes_linetype_size_shape]{linetype}} \tab → via \code{theme()} \cr\cr +• \tab \code{\link[=aes_linetype_size_shape]{linewidth}} \tab → via \code{theme()} \cr\cr } Note that \code{geom_pointrange()} also understands \code{size} for the size of the points. diff --git a/man/geom_map.Rd b/man/geom_map.Rd index 55c06b5b26..561a297161 100644 --- a/man/geom_map.Rd +++ b/man/geom_map.Rd @@ -107,16 +107,16 @@ it can be used in conjunction with \code{geom_sf()} layers and/or } \section{Aesthetics}{ -\code{geom_map()} understands the following aesthetics (required aesthetics are in bold): -\itemize{ -\item \strong{\code{map_id}} -\item \code{\link[=aes_colour_fill_alpha]{alpha}} -\item \code{\link[=aes_colour_fill_alpha]{colour}} -\item \code{\link[=aes_colour_fill_alpha]{fill}} -\item \code{\link[=aes_group_order]{group}} -\item \code{\link[=aes_linetype_size_shape]{linetype}} -\item \code{\link[=aes_linetype_size_shape]{linewidth}} -\item \code{subgroup} +\code{geom_map()} understands the following aesthetics. Required aesthetics are displayed in bold and defaults are displayed for optional aesthetics: +\tabular{rll}{ +• \tab \strong{\code{map_id}} \tab \cr\cr +• \tab \code{\link[=aes_colour_fill_alpha]{alpha}} \tab → \code{NA} \cr\cr +• \tab \code{\link[=aes_colour_fill_alpha]{colour}} \tab → via \code{theme()} \cr\cr +• \tab \code{\link[=aes_colour_fill_alpha]{fill}} \tab → via \code{theme()} \cr\cr +• \tab \code{\link[=aes_group_order]{group}} \tab → inferred \cr\cr +• \tab \code{\link[=aes_linetype_size_shape]{linetype}} \tab → via \code{theme()} \cr\cr +• \tab \code{\link[=aes_linetype_size_shape]{linewidth}} \tab → via \code{theme()} \cr\cr +• \tab \code{subgroup} \tab → \code{NULL} \cr\cr } Learn more about setting these aesthetics in \code{vignette("ggplot2-specs")}. } diff --git a/man/geom_path.Rd b/man/geom_path.Rd index 88913a5a7b..6d0f30ec8d 100644 --- a/man/geom_path.Rd +++ b/man/geom_path.Rd @@ -176,15 +176,15 @@ This geom treats each axis differently and, thus, can thus have two orientations \section{Aesthetics}{ -\code{geom_path()} understands the following aesthetics (required aesthetics are in bold): -\itemize{ -\item \strong{\code{\link[=aes_position]{x}}} -\item \strong{\code{\link[=aes_position]{y}}} -\item \code{\link[=aes_colour_fill_alpha]{alpha}} -\item \code{\link[=aes_colour_fill_alpha]{colour}} -\item \code{\link[=aes_group_order]{group}} -\item \code{\link[=aes_linetype_size_shape]{linetype}} -\item \code{\link[=aes_linetype_size_shape]{linewidth}} +\code{geom_path()} understands the following aesthetics. Required aesthetics are displayed in bold and defaults are displayed for optional aesthetics: +\tabular{rll}{ +• \tab \strong{\code{\link[=aes_position]{x}}} \tab \cr\cr +• \tab \strong{\code{\link[=aes_position]{y}}} \tab \cr\cr +• \tab \code{\link[=aes_colour_fill_alpha]{alpha}} \tab → \code{NA} \cr\cr +• \tab \code{\link[=aes_colour_fill_alpha]{colour}} \tab → via \code{theme()} \cr\cr +• \tab \code{\link[=aes_group_order]{group}} \tab → inferred \cr\cr +• \tab \code{\link[=aes_linetype_size_shape]{linetype}} \tab → via \code{theme()} \cr\cr +• \tab \code{\link[=aes_linetype_size_shape]{linewidth}} \tab → via \code{theme()} \cr\cr } Learn more about setting these aesthetics in \code{vignette("ggplot2-specs")}. } diff --git a/man/geom_point.Rd b/man/geom_point.Rd index ccf615e007..ea7975762d 100644 --- a/man/geom_point.Rd +++ b/man/geom_point.Rd @@ -138,17 +138,17 @@ Another technique is to make the points transparent (e.g. \section{Aesthetics}{ -\code{geom_point()} understands the following aesthetics (required aesthetics are in bold): -\itemize{ -\item \strong{\code{\link[=aes_position]{x}}} -\item \strong{\code{\link[=aes_position]{y}}} -\item \code{\link[=aes_colour_fill_alpha]{alpha}} -\item \code{\link[=aes_colour_fill_alpha]{colour}} -\item \code{\link[=aes_colour_fill_alpha]{fill}} -\item \code{\link[=aes_group_order]{group}} -\item \code{\link[=aes_linetype_size_shape]{shape}} -\item \code{\link[=aes_linetype_size_shape]{size}} -\item \code{stroke} +\code{geom_point()} understands the following aesthetics. Required aesthetics are displayed in bold and defaults are displayed for optional aesthetics: +\tabular{rll}{ +• \tab \strong{\code{\link[=aes_position]{x}}} \tab \cr\cr +• \tab \strong{\code{\link[=aes_position]{y}}} \tab \cr\cr +• \tab \code{\link[=aes_colour_fill_alpha]{alpha}} \tab → \code{NA} \cr\cr +• \tab \code{\link[=aes_colour_fill_alpha]{colour}} \tab → via \code{theme()} \cr\cr +• \tab \code{\link[=aes_colour_fill_alpha]{fill}} \tab → via \code{theme()} \cr\cr +• \tab \code{\link[=aes_group_order]{group}} \tab → inferred \cr\cr +• \tab \code{\link[=aes_linetype_size_shape]{shape}} \tab → via \code{theme()} \cr\cr +• \tab \code{\link[=aes_linetype_size_shape]{size}} \tab → via \code{theme()} \cr\cr +• \tab \code{stroke} \tab → via \code{theme()} \cr\cr } The \code{fill} aesthetic only applies to shapes 21-25. diff --git a/man/geom_polygon.Rd b/man/geom_polygon.Rd index 241490284a..1c76e21995 100644 --- a/man/geom_polygon.Rd +++ b/man/geom_polygon.Rd @@ -123,17 +123,17 @@ polygon. } \section{Aesthetics}{ -\code{geom_polygon()} understands the following aesthetics (required aesthetics are in bold): -\itemize{ -\item \strong{\code{\link[=aes_position]{x}}} -\item \strong{\code{\link[=aes_position]{y}}} -\item \code{\link[=aes_colour_fill_alpha]{alpha}} -\item \code{\link[=aes_colour_fill_alpha]{colour}} -\item \code{\link[=aes_colour_fill_alpha]{fill}} -\item \code{\link[=aes_group_order]{group}} -\item \code{\link[=aes_linetype_size_shape]{linetype}} -\item \code{\link[=aes_linetype_size_shape]{linewidth}} -\item \code{subgroup} +\code{geom_polygon()} understands the following aesthetics. Required aesthetics are displayed in bold and defaults are displayed for optional aesthetics: +\tabular{rll}{ +• \tab \strong{\code{\link[=aes_position]{x}}} \tab \cr\cr +• \tab \strong{\code{\link[=aes_position]{y}}} \tab \cr\cr +• \tab \code{\link[=aes_colour_fill_alpha]{alpha}} \tab → \code{NA} \cr\cr +• \tab \code{\link[=aes_colour_fill_alpha]{colour}} \tab → via \code{theme()} \cr\cr +• \tab \code{\link[=aes_colour_fill_alpha]{fill}} \tab → via \code{theme()} \cr\cr +• \tab \code{\link[=aes_group_order]{group}} \tab → inferred \cr\cr +• \tab \code{\link[=aes_linetype_size_shape]{linetype}} \tab → via \code{theme()} \cr\cr +• \tab \code{\link[=aes_linetype_size_shape]{linewidth}} \tab → via \code{theme()} \cr\cr +• \tab \code{subgroup} \tab → \code{NULL} \cr\cr } Learn more about setting these aesthetics in \code{vignette("ggplot2-specs")}. } diff --git a/man/geom_qq.Rd b/man/geom_qq.Rd index 88656bc53a..7915f29e47 100644 --- a/man/geom_qq.Rd +++ b/man/geom_qq.Rd @@ -172,22 +172,22 @@ points at specified quartiles of the theoretical and sample distributions. } \section{Aesthetics}{ -\code{stat_qq()} understands the following aesthetics (required aesthetics are in bold): -\itemize{ -\item \strong{\code{sample}} -\item \code{\link[=aes_group_order]{group}} -\item \code{\link[=aes_position]{x}} -\item \code{\link[=aes_position]{y}} +\code{stat_qq()} understands the following aesthetics. Required aesthetics are displayed in bold and defaults are displayed for optional aesthetics: +\tabular{rll}{ +• \tab \strong{\code{sample}} \tab \cr\cr +• \tab \code{\link[=aes_group_order]{group}} \tab → inferred \cr\cr +• \tab \code{\link[=aes_position]{x}} \tab → \code{after_stat(theoretical)} \cr\cr +• \tab \code{\link[=aes_position]{y}} \tab → \code{after_stat(sample)} \cr\cr } Learn more about setting these aesthetics in \code{vignette("ggplot2-specs")}. -\code{stat_qq_line()} understands the following aesthetics (required aesthetics are in bold): -\itemize{ -\item \strong{\code{sample}} -\item \code{\link[=aes_group_order]{group}} -\item \code{\link[=aes_position]{x}} -\item \code{\link[=aes_position]{y}} +\code{stat_qq_line()} understands the following aesthetics. Required aesthetics are displayed in bold and defaults are displayed for optional aesthetics: +\tabular{rll}{ +• \tab \strong{\code{sample}} \tab \cr\cr +• \tab \code{\link[=aes_group_order]{group}} \tab → inferred \cr\cr +• \tab \code{\link[=aes_position]{x}} \tab → \code{after_stat(x)} \cr\cr +• \tab \code{\link[=aes_position]{y}} \tab → \code{after_stat(y)} \cr\cr } Learn more about setting these aesthetics in \code{vignette("ggplot2-specs")}. } diff --git a/man/geom_quantile.Rd b/man/geom_quantile.Rd index 568c33e970..495e6b22cd 100644 --- a/man/geom_quantile.Rd +++ b/man/geom_quantile.Rd @@ -139,16 +139,16 @@ with lines. This is as a continuous analogue to \code{\link[=geom_boxplot]{geom_ } \section{Aesthetics}{ -\code{geom_quantile()} understands the following aesthetics (required aesthetics are in bold): -\itemize{ -\item \strong{\code{\link[=aes_position]{x}}} -\item \strong{\code{\link[=aes_position]{y}}} -\item \code{\link[=aes_colour_fill_alpha]{alpha}} -\item \code{\link[=aes_colour_fill_alpha]{colour}} -\item \code{\link[=aes_group_order]{group}} -\item \code{\link[=aes_linetype_size_shape]{linetype}} -\item \code{\link[=aes_linetype_size_shape]{linewidth}} -\item \code{weight} +\code{geom_quantile()} understands the following aesthetics. Required aesthetics are displayed in bold and defaults are displayed for optional aesthetics: +\tabular{rll}{ +• \tab \strong{\code{\link[=aes_position]{x}}} \tab \cr\cr +• \tab \strong{\code{\link[=aes_position]{y}}} \tab \cr\cr +• \tab \code{\link[=aes_colour_fill_alpha]{alpha}} \tab → \code{NA} \cr\cr +• \tab \code{\link[=aes_colour_fill_alpha]{colour}} \tab → via \code{theme()} \cr\cr +• \tab \code{\link[=aes_group_order]{group}} \tab → inferred \cr\cr +• \tab \code{\link[=aes_linetype_size_shape]{linetype}} \tab → via \code{theme()} \cr\cr +• \tab \code{\link[=aes_linetype_size_shape]{linewidth}} \tab → via \code{theme()} \cr\cr +• \tab \code{weight} \tab → \code{1} \cr\cr } Learn more about setting these aesthetics in \code{vignette("ggplot2-specs")}. } diff --git a/man/geom_ribbon.Rd b/man/geom_ribbon.Rd index d4f5a707e1..256e821e6b 100644 --- a/man/geom_ribbon.Rd +++ b/man/geom_ribbon.Rd @@ -180,17 +180,17 @@ This geom treats each axis differently and, thus, can thus have two orientations \section{Aesthetics}{ -\code{geom_ribbon()} understands the following aesthetics (required aesthetics are in bold): -\itemize{ -\item \strong{\code{\link[=aes_position]{x}} \emph{or} \code{\link[=aes_position]{y}}} -\item \strong{\code{\link[=aes_position]{ymin}} \emph{or} \code{\link[=aes_position]{xmin}}} -\item \strong{\code{\link[=aes_position]{ymax}} \emph{or} \code{\link[=aes_position]{xmax}}} -\item \code{\link[=aes_colour_fill_alpha]{alpha}} -\item \code{\link[=aes_colour_fill_alpha]{colour}} -\item \code{\link[=aes_colour_fill_alpha]{fill}} -\item \code{\link[=aes_group_order]{group}} -\item \code{\link[=aes_linetype_size_shape]{linetype}} -\item \code{\link[=aes_linetype_size_shape]{linewidth}} +\code{geom_ribbon()} understands the following aesthetics. Required aesthetics are displayed in bold and defaults are displayed for optional aesthetics: +\tabular{rll}{ +• \tab \strong{\code{\link[=aes_position]{x}} \emph{or} \code{\link[=aes_position]{y}}} \tab \cr\cr +• \tab \strong{\code{\link[=aes_position]{ymin}} \emph{or} \code{\link[=aes_position]{xmin}}} \tab \cr\cr +• \tab \strong{\code{\link[=aes_position]{ymax}} \emph{or} \code{\link[=aes_position]{xmax}}} \tab \cr\cr +• \tab \code{\link[=aes_colour_fill_alpha]{alpha}} \tab → \code{NA} \cr\cr +• \tab \code{\link[=aes_colour_fill_alpha]{colour}} \tab → via \code{theme()} \cr\cr +• \tab \code{\link[=aes_colour_fill_alpha]{fill}} \tab → via \code{theme()} \cr\cr +• \tab \code{\link[=aes_group_order]{group}} \tab → inferred \cr\cr +• \tab \code{\link[=aes_linetype_size_shape]{linetype}} \tab → via \code{theme()} \cr\cr +• \tab \code{\link[=aes_linetype_size_shape]{linewidth}} \tab → via \code{theme()} \cr\cr } Learn more about setting these aesthetics in \code{vignette("ggplot2-specs")}. } diff --git a/man/geom_rug.Rd b/man/geom_rug.Rd index b6508c7f9a..e77826c7e9 100644 --- a/man/geom_rug.Rd +++ b/man/geom_rug.Rd @@ -130,15 +130,15 @@ any data points under the default settings. } \section{Aesthetics}{ -\code{geom_rug()} understands the following aesthetics (required aesthetics are in bold): -\itemize{ -\item \code{\link[=aes_colour_fill_alpha]{alpha}} -\item \code{\link[=aes_colour_fill_alpha]{colour}} -\item \code{\link[=aes_group_order]{group}} -\item \code{\link[=aes_linetype_size_shape]{linetype}} -\item \code{\link[=aes_linetype_size_shape]{linewidth}} -\item \code{\link[=aes_position]{x}} -\item \code{\link[=aes_position]{y}} +\code{geom_rug()} understands the following aesthetics. Required aesthetics are displayed in bold and defaults are displayed for optional aesthetics: +\tabular{rll}{ +• \tab \code{\link[=aes_colour_fill_alpha]{alpha}} \tab → \code{NA} \cr\cr +• \tab \code{\link[=aes_colour_fill_alpha]{colour}} \tab → via \code{theme()} \cr\cr +• \tab \code{\link[=aes_group_order]{group}} \tab → inferred \cr\cr +• \tab \code{\link[=aes_linetype_size_shape]{linetype}} \tab → via \code{theme()} \cr\cr +• \tab \code{\link[=aes_linetype_size_shape]{linewidth}} \tab → via \code{theme()} \cr\cr +• \tab \code{\link[=aes_position]{x}} \tab \cr\cr +• \tab \code{\link[=aes_position]{y}} \tab \cr\cr } Learn more about setting these aesthetics in \code{vignette("ggplot2-specs")}. } diff --git a/man/geom_segment.Rd b/man/geom_segment.Rd index 392ba20669..8cddae4dc2 100644 --- a/man/geom_segment.Rd +++ b/man/geom_segment.Rd @@ -162,16 +162,16 @@ need to connect points across multiple cases. } \section{Aesthetics}{ -\code{geom_segment()} understands the following aesthetics (required aesthetics are in bold): -\itemize{ -\item \strong{\code{\link[=aes_position]{x}}} -\item \strong{\code{\link[=aes_position]{y}}} -\item \strong{\code{\link[=aes_position]{xend}} \emph{or} \code{\link[=aes_position]{yend}}} -\item \code{\link[=aes_colour_fill_alpha]{alpha}} -\item \code{\link[=aes_colour_fill_alpha]{colour}} -\item \code{\link[=aes_group_order]{group}} -\item \code{\link[=aes_linetype_size_shape]{linetype}} -\item \code{\link[=aes_linetype_size_shape]{linewidth}} +\code{geom_segment()} understands the following aesthetics. Required aesthetics are displayed in bold and defaults are displayed for optional aesthetics: +\tabular{rll}{ +• \tab \strong{\code{\link[=aes_position]{x}}} \tab \cr\cr +• \tab \strong{\code{\link[=aes_position]{y}}} \tab \cr\cr +• \tab \strong{\code{\link[=aes_position]{xend}} \emph{or} \code{\link[=aes_position]{yend}}} \tab \cr\cr +• \tab \code{\link[=aes_colour_fill_alpha]{alpha}} \tab → \code{NA} \cr\cr +• \tab \code{\link[=aes_colour_fill_alpha]{colour}} \tab → via \code{theme()} \cr\cr +• \tab \code{\link[=aes_group_order]{group}} \tab → inferred \cr\cr +• \tab \code{\link[=aes_linetype_size_shape]{linetype}} \tab → via \code{theme()} \cr\cr +• \tab \code{\link[=aes_linetype_size_shape]{linewidth}} \tab → via \code{theme()} \cr\cr } Learn more about setting these aesthetics in \code{vignette("ggplot2-specs")}. } diff --git a/man/geom_smooth.Rd b/man/geom_smooth.Rd index 6d89a61782..4a02999e73 100644 --- a/man/geom_smooth.Rd +++ b/man/geom_smooth.Rd @@ -196,19 +196,19 @@ This geom treats each axis differently and, thus, can thus have two orientations \section{Aesthetics}{ -\code{geom_smooth()} understands the following aesthetics (required aesthetics are in bold): -\itemize{ -\item \strong{\code{\link[=aes_position]{x}}} -\item \strong{\code{\link[=aes_position]{y}}} -\item \code{\link[=aes_colour_fill_alpha]{alpha}} -\item \code{\link[=aes_colour_fill_alpha]{colour}} -\item \code{\link[=aes_colour_fill_alpha]{fill}} -\item \code{\link[=aes_group_order]{group}} -\item \code{\link[=aes_linetype_size_shape]{linetype}} -\item \code{\link[=aes_linetype_size_shape]{linewidth}} -\item \code{weight} -\item \code{\link[=aes_position]{ymax}} -\item \code{\link[=aes_position]{ymin}} +\code{geom_smooth()} understands the following aesthetics. Required aesthetics are displayed in bold and defaults are displayed for optional aesthetics: +\tabular{rll}{ +• \tab \strong{\code{\link[=aes_position]{x}}} \tab \cr\cr +• \tab \strong{\code{\link[=aes_position]{y}}} \tab \cr\cr +• \tab \code{\link[=aes_colour_fill_alpha]{alpha}} \tab → \code{0.4} \cr\cr +• \tab \code{\link[=aes_colour_fill_alpha]{colour}} \tab → via \code{theme()} \cr\cr +• \tab \code{\link[=aes_colour_fill_alpha]{fill}} \tab → via \code{theme()} \cr\cr +• \tab \code{\link[=aes_group_order]{group}} \tab → inferred \cr\cr +• \tab \code{\link[=aes_linetype_size_shape]{linetype}} \tab → via \code{theme()} \cr\cr +• \tab \code{\link[=aes_linetype_size_shape]{linewidth}} \tab → via \code{theme()} \cr\cr +• \tab \code{weight} \tab → \code{1} \cr\cr +• \tab \code{\link[=aes_position]{ymax}} \tab \cr\cr +• \tab \code{\link[=aes_position]{ymin}} \tab \cr\cr } Learn more about setting these aesthetics in \code{vignette("ggplot2-specs")}. } diff --git a/man/geom_spoke.Rd b/man/geom_spoke.Rd index ea28f601c1..ffebfbe589 100644 --- a/man/geom_spoke.Rd +++ b/man/geom_spoke.Rd @@ -114,17 +114,17 @@ The angles start from east and increase counterclockwise. } \section{Aesthetics}{ -\code{geom_spoke()} understands the following aesthetics (required aesthetics are in bold): -\itemize{ -\item \strong{\code{\link[=aes_position]{x}}} -\item \strong{\code{\link[=aes_position]{y}}} -\item \strong{\code{angle}} -\item \strong{\code{radius}} -\item \code{\link[=aes_colour_fill_alpha]{alpha}} -\item \code{\link[=aes_colour_fill_alpha]{colour}} -\item \code{\link[=aes_group_order]{group}} -\item \code{\link[=aes_linetype_size_shape]{linetype}} -\item \code{\link[=aes_linetype_size_shape]{linewidth}} +\code{geom_spoke()} understands the following aesthetics. Required aesthetics are displayed in bold and defaults are displayed for optional aesthetics: +\tabular{rll}{ +• \tab \strong{\code{\link[=aes_position]{x}}} \tab \cr\cr +• \tab \strong{\code{\link[=aes_position]{y}}} \tab \cr\cr +• \tab \strong{\code{angle}} \tab \cr\cr +• \tab \strong{\code{radius}} \tab \cr\cr +• \tab \code{\link[=aes_colour_fill_alpha]{alpha}} \tab → \code{NA} \cr\cr +• \tab \code{\link[=aes_colour_fill_alpha]{colour}} \tab → via \code{theme()} \cr\cr +• \tab \code{\link[=aes_group_order]{group}} \tab → inferred \cr\cr +• \tab \code{\link[=aes_linetype_size_shape]{linetype}} \tab → via \code{theme()} \cr\cr +• \tab \code{\link[=aes_linetype_size_shape]{linewidth}} \tab → via \code{theme()} \cr\cr } Learn more about setting these aesthetics in \code{vignette("ggplot2-specs")}. } diff --git a/man/geom_text.Rd b/man/geom_text.Rd index ea698af3c1..4293217066 100644 --- a/man/geom_text.Rd +++ b/man/geom_text.Rd @@ -185,21 +185,21 @@ package. } \section{Aesthetics}{ -\code{geom_text()} understands the following aesthetics (required aesthetics are in bold): -\itemize{ -\item \strong{\code{\link[=aes_position]{x}}} -\item \strong{\code{\link[=aes_position]{y}}} -\item \strong{\code{label}} -\item \code{\link[=aes_colour_fill_alpha]{alpha}} -\item \code{angle} -\item \code{\link[=aes_colour_fill_alpha]{colour}} -\item \code{family} -\item \code{fontface} -\item \code{\link[=aes_group_order]{group}} -\item \code{hjust} -\item \code{lineheight} -\item \code{\link[=aes_linetype_size_shape]{size}} -\item \code{vjust} +\code{geom_text()} understands the following aesthetics. Required aesthetics are displayed in bold and defaults are displayed for optional aesthetics: +\tabular{rll}{ +• \tab \strong{\code{\link[=aes_position]{x}}} \tab \cr\cr +• \tab \strong{\code{\link[=aes_position]{y}}} \tab \cr\cr +• \tab \strong{\code{label}} \tab \cr\cr +• \tab \code{\link[=aes_colour_fill_alpha]{alpha}} \tab → \code{NA} \cr\cr +• \tab \code{angle} \tab → \code{0} \cr\cr +• \tab \code{\link[=aes_colour_fill_alpha]{colour}} \tab → via \code{theme()} \cr\cr +• \tab \code{family} \tab → via \code{theme()} \cr\cr +• \tab \code{fontface} \tab → \code{1} \cr\cr +• \tab \code{\link[=aes_group_order]{group}} \tab → inferred \cr\cr +• \tab \code{hjust} \tab → \code{0.5} \cr\cr +• \tab \code{lineheight} \tab → \code{1.2} \cr\cr +• \tab \code{\link[=aes_linetype_size_shape]{size}} \tab → via \code{theme()} \cr\cr +• \tab \code{vjust} \tab → \code{0.5} \cr\cr } Learn more about setting these aesthetics in \code{vignette("ggplot2-specs")}. } diff --git a/man/geom_tile.Rd b/man/geom_tile.Rd index 34b9bb30bc..d0638772b5 100644 --- a/man/geom_tile.Rd +++ b/man/geom_tile.Rd @@ -159,16 +159,16 @@ only after transformation that these aesthetics are applied. } \section{Aesthetics}{ -\code{geom_rect()} understands the following aesthetics (required aesthetics are in bold): -\itemize{ -\item \strong{\code{\link[=aes_position]{x}} \emph{or} \code{width} \emph{or} \code{\link[=aes_position]{xmin}} \emph{or} \code{\link[=aes_position]{xmax}}} -\item \strong{\code{\link[=aes_position]{y}} \emph{or} \code{height} \emph{or} \code{\link[=aes_position]{ymin}} \emph{or} \code{\link[=aes_position]{ymax}}} -\item \code{\link[=aes_colour_fill_alpha]{alpha}} -\item \code{\link[=aes_colour_fill_alpha]{colour}} -\item \code{\link[=aes_colour_fill_alpha]{fill}} -\item \code{\link[=aes_group_order]{group}} -\item \code{\link[=aes_linetype_size_shape]{linetype}} -\item \code{\link[=aes_linetype_size_shape]{linewidth}} +\code{geom_rect()} understands the following aesthetics. Required aesthetics are displayed in bold and defaults are displayed for optional aesthetics: +\tabular{rll}{ +• \tab \strong{\code{\link[=aes_position]{x}} \emph{or} \code{width} \emph{or} \code{\link[=aes_position]{xmin}} \emph{or} \code{\link[=aes_position]{xmax}}} \tab \cr\cr +• \tab \strong{\code{\link[=aes_position]{y}} \emph{or} \code{height} \emph{or} \code{\link[=aes_position]{ymin}} \emph{or} \code{\link[=aes_position]{ymax}}} \tab \cr\cr +• \tab \code{\link[=aes_colour_fill_alpha]{alpha}} \tab → \code{NA} \cr\cr +• \tab \code{\link[=aes_colour_fill_alpha]{colour}} \tab → via \code{theme()} \cr\cr +• \tab \code{\link[=aes_colour_fill_alpha]{fill}} \tab → via \code{theme()} \cr\cr +• \tab \code{\link[=aes_group_order]{group}} \tab → inferred \cr\cr +• \tab \code{\link[=aes_linetype_size_shape]{linetype}} \tab → via \code{theme()} \cr\cr +• \tab \code{\link[=aes_linetype_size_shape]{linewidth}} \tab → via \code{theme()} \cr\cr } \code{geom_tile()} understands only the \code{x}/\code{width} and \code{y}/\code{height} combinations. Note that \code{geom_raster()} ignores \code{colour}. diff --git a/man/geom_violin.Rd b/man/geom_violin.Rd index 7b923b68ab..590ebface6 100644 --- a/man/geom_violin.Rd +++ b/man/geom_violin.Rd @@ -185,18 +185,18 @@ This geom treats each axis differently and, thus, can thus have two orientations \section{Aesthetics}{ -\code{geom_violin()} understands the following aesthetics (required aesthetics are in bold): -\itemize{ -\item \strong{\code{\link[=aes_position]{x}}} -\item \strong{\code{\link[=aes_position]{y}}} -\item \code{\link[=aes_colour_fill_alpha]{alpha}} -\item \code{\link[=aes_colour_fill_alpha]{colour}} -\item \code{\link[=aes_colour_fill_alpha]{fill}} -\item \code{\link[=aes_group_order]{group}} -\item \code{\link[=aes_linetype_size_shape]{linetype}} -\item \code{\link[=aes_linetype_size_shape]{linewidth}} -\item \code{weight} -\item \code{width} +\code{geom_violin()} understands the following aesthetics. Required aesthetics are displayed in bold and defaults are displayed for optional aesthetics: +\tabular{rll}{ +• \tab \strong{\code{\link[=aes_position]{x}}} \tab \cr\cr +• \tab \strong{\code{\link[=aes_position]{y}}} \tab \cr\cr +• \tab \code{\link[=aes_colour_fill_alpha]{alpha}} \tab → \code{NA} \cr\cr +• \tab \code{\link[=aes_colour_fill_alpha]{colour}} \tab → via \code{theme()} \cr\cr +• \tab \code{\link[=aes_colour_fill_alpha]{fill}} \tab → via \code{theme()} \cr\cr +• \tab \code{\link[=aes_group_order]{group}} \tab → inferred \cr\cr +• \tab \code{\link[=aes_linetype_size_shape]{linetype}} \tab → via \code{theme()} \cr\cr +• \tab \code{\link[=aes_linetype_size_shape]{linewidth}} \tab → via \code{theme()} \cr\cr +• \tab \code{weight} \tab → \code{1} \cr\cr +• \tab \code{width} \tab → \code{0.9} \cr\cr } Learn more about setting these aesthetics in \code{vignette("ggplot2-specs")}. } diff --git a/man/position_dodge.Rd b/man/position_dodge.Rd index 5706e93e02..0f957b4182 100644 --- a/man/position_dodge.Rd +++ b/man/position_dodge.Rd @@ -48,9 +48,9 @@ can have variable widths. } \section{Aesthetics}{ -\code{position_dodge()} understands the following aesthetics (required aesthetics are in bold): -\itemize{ -\item \code{order} +\code{position_dodge()} understands the following aesthetics. Required aesthetics are displayed in bold and defaults are displayed for optional aesthetics: +\tabular{rll}{ +• \tab \code{order} \tab → \code{NULL} \cr\cr } Learn more about setting these aesthetics in \code{vignette("ggplot2-specs")}. } diff --git a/man/position_nudge.Rd b/man/position_nudge.Rd index 89b5a14326..07fcd63447 100644 --- a/man/position_nudge.Rd +++ b/man/position_nudge.Rd @@ -17,10 +17,10 @@ distance from what they're labelling. } \section{Aesthetics}{ -\code{position_nudge()} understands the following aesthetics (required aesthetics are in bold): -\itemize{ -\item \code{nudge_x} -\item \code{nudge_y} +\code{position_nudge()} understands the following aesthetics. Required aesthetics are displayed in bold and defaults are displayed for optional aesthetics: +\tabular{rll}{ +• \tab \code{nudge_x} \tab → \code{0} \cr\cr +• \tab \code{nudge_y} \tab → \code{0} \cr\cr } Learn more about setting these aesthetics in \code{vignette("ggplot2-specs")}. } diff --git a/man/stat_ecdf.Rd b/man/stat_ecdf.Rd index 8d92c51743..a341ce6543 100644 --- a/man/stat_ecdf.Rd +++ b/man/stat_ecdf.Rd @@ -134,11 +134,11 @@ this case, the ECDF is incremented by \code{weight / sum(weight)} instead of } \section{Aesthetics}{ -\code{stat_ecdf()} understands the following aesthetics (required aesthetics are in bold): -\itemize{ -\item \strong{\code{\link[=aes_position]{x}} \emph{or} \code{\link[=aes_position]{y}}} -\item \code{\link[=aes_group_order]{group}} -\item \code{weight} +\code{stat_ecdf()} understands the following aesthetics. Required aesthetics are displayed in bold and defaults are displayed for optional aesthetics: +\tabular{rll}{ +• \tab \strong{\code{\link[=aes_position]{x}} \emph{or} \code{\link[=aes_position]{y}}} \tab \cr\cr +• \tab \code{\link[=aes_group_order]{group}} \tab → inferred \cr\cr +• \tab \code{weight} \tab → \code{NULL} \cr\cr } Learn more about setting these aesthetics in \code{vignette("ggplot2-specs")}. } diff --git a/man/stat_ellipse.Rd b/man/stat_ellipse.Rd index 8ef16d92cc..fa4ecc9b05 100644 --- a/man/stat_ellipse.Rd +++ b/man/stat_ellipse.Rd @@ -127,12 +127,12 @@ The method for calculating the ellipses has been modified from } \section{Aesthetics}{ -\code{stat_ellipse()} understands the following aesthetics (required aesthetics are in bold): -\itemize{ -\item \strong{\code{\link[=aes_position]{x}}} -\item \strong{\code{\link[=aes_position]{y}}} -\item \code{\link[=aes_group_order]{group}} -\item \code{weight} +\code{stat_ellipse()} understands the following aesthetics. Required aesthetics are displayed in bold and defaults are displayed for optional aesthetics: +\tabular{rll}{ +• \tab \strong{\code{\link[=aes_position]{x}}} \tab \cr\cr +• \tab \strong{\code{\link[=aes_position]{y}}} \tab \cr\cr +• \tab \code{\link[=aes_group_order]{group}} \tab → inferred \cr\cr +• \tab \code{weight} \tab \cr\cr } Learn more about setting these aesthetics in \code{vignette("ggplot2-specs")}. } diff --git a/man/stat_manual.Rd b/man/stat_manual.Rd index f19a03128e..de64b21a31 100644 --- a/man/stat_manual.Rd +++ b/man/stat_manual.Rd @@ -120,9 +120,9 @@ every group. } \section{Aesthetics}{ -\code{stat_manual()} understands the following aesthetics (required aesthetics are in bold): -\itemize{ -\item \code{\link[=aes_group_order]{group}} +\code{stat_manual()} understands the following aesthetics. Required aesthetics are displayed in bold and defaults are displayed for optional aesthetics: +\tabular{rll}{ +• \tab \code{\link[=aes_group_order]{group}} \tab → inferred \cr\cr } Learn more about setting these aesthetics in \code{vignette("ggplot2-specs")}. diff --git a/man/stat_summary.Rd b/man/stat_summary.Rd index 3ebf979e54..20326b840f 100644 --- a/man/stat_summary.Rd +++ b/man/stat_summary.Rd @@ -186,11 +186,11 @@ This geom treats each axis differently and, thus, can thus have two orientations \section{Aesthetics}{ -\code{stat_summary()} understands the following aesthetics (required aesthetics are in bold): -\itemize{ -\item \strong{\code{\link[=aes_position]{x}}} -\item \strong{\code{\link[=aes_position]{y}}} -\item \code{\link[=aes_group_order]{group}} +\code{stat_summary()} understands the following aesthetics. Required aesthetics are displayed in bold and defaults are displayed for optional aesthetics: +\tabular{rll}{ +• \tab \strong{\code{\link[=aes_position]{x}}} \tab \cr\cr +• \tab \strong{\code{\link[=aes_position]{y}}} \tab \cr\cr +• \tab \code{\link[=aes_group_order]{group}} \tab → inferred \cr\cr } Learn more about setting these aesthetics in \code{vignette("ggplot2-specs")}. } diff --git a/man/stat_unique.Rd b/man/stat_unique.Rd index 137c99f180..717b49e36c 100644 --- a/man/stat_unique.Rd +++ b/man/stat_unique.Rd @@ -111,9 +111,9 @@ Remove duplicates } \section{Aesthetics}{ -\code{stat_unique()} understands the following aesthetics (required aesthetics are in bold): -\itemize{ -\item \code{\link[=aes_group_order]{group}} +\code{stat_unique()} understands the following aesthetics. Required aesthetics are displayed in bold and defaults are displayed for optional aesthetics: +\tabular{rll}{ +• \tab \code{\link[=aes_group_order]{group}} \tab → inferred \cr\cr } Learn more about setting these aesthetics in \code{vignette("ggplot2-specs")}. } diff --git a/tests/testthat/test-theme.R b/tests/testthat/test-theme.R index 8d74b4038f..d7472a71f7 100644 --- a/tests/testthat/test-theme.R +++ b/tests/testthat/test-theme.R @@ -710,6 +710,26 @@ test_that("margin_part() mechanics work as expected", { expect_equal(as.numeric(test), c(5.5, 5.5, 11, 5.5)) }) +test_that("geom elements are inherited correctly", { + + GeomFoo <- ggproto("GeomFoo", GeomPoint) + GeomBar <- ggproto("GeomBar", GeomFoo) + + p <- ggplot(data.frame(x = 1), aes(x, x)) + + stat_identity(geom = GeomBar) + + theme( + geom = element_geom(pointshape = 15), + geom.point = element_geom(borderwidth = 2, ink = "blue"), + geom.foo = element_geom(pointsize = 2), + geom.bar = element_geom(ink = "red") + ) + p <- layer_data(p) + expect_equal(p$shape, 15) + expect_equal(p$stroke, 2) + expect_equal(p$size, 2) + expect_equal(p$colour, "red") +}) + # Visual tests ------------------------------------------------------------ test_that("element_polygon() can render a grob", {