diff --git a/NAMESPACE b/NAMESPACE index 96959a985a..00c46a0bf0 100644 --- a/NAMESPACE +++ b/NAMESPACE @@ -458,6 +458,21 @@ export(is.facet) export(is.ggplot) export(is.ggproto) export(is.theme) +export(is_coord) +export(is_element) +export(is_facet) +export(is_geom) +export(is_ggplot) +export(is_ggproto) +export(is_guide) +export(is_guides) +export(is_layer) +export(is_mapping) +export(is_margin) +export(is_position) +export(is_scale) +export(is_stat) +export(is_theme) export(label_both) export(label_bquote) export(label_context) diff --git a/NEWS.md b/NEWS.md index a5988574f8..f139b4e263 100644 --- a/NEWS.md +++ b/NEWS.md @@ -1,5 +1,9 @@ # ggplot2 (development version) +* Standardised test functions for important classes: `is_ggproto()`, + `is_ggplot()`, `is_mapping()`, `is_layer()`, `is_geom()`, `is_stat()`, + `is_position()`, `is_coord()`, `is_facet()`, `is_scale()`, `is_guide()`, + `is_guides()`, `is_margin()`, `is_element()` and `is_theme()`. * New `get_labs()` function for retrieving completed plot labels (@teunbrand, #6008). * New `get_geom_defaults()` for retrieving resolved default aesthetics. diff --git a/R/aes.R b/R/aes.R index 4120657222..483cd85bad 100644 --- a/R/aes.R +++ b/R/aes.R @@ -102,6 +102,10 @@ aes <- function(x, y, ...) { rename_aes(aes) } +#' @export +#' @rdname is_tests +is_mapping <- function(x) inherits(x, "uneval") + # Wrap symbolic objects in quosures but pull out constants out of # quosures for backward-compatibility new_aesthetic <- function(x, env = globalenv()) { diff --git a/R/coord-.R b/R/coord-.R index dc7090c352..0f2c0f3ca2 100644 --- a/R/coord-.R +++ b/R/coord-.R @@ -204,11 +204,17 @@ Coord <- ggproto("Coord", } ) -#' Is this object a coordinate system? -#' -#' @export is.Coord -#' @keywords internal -is.Coord <- function(x) inherits(x, "Coord") +#' @export +#' @rdname is_tests +is_coord <- function(x) inheritS(x, "Coord") + +#' @export +#' @rdname is_tests +#' @usage is.Coord(x) # Deprecated +is.Coord <- function(x) { + deprecate_soft0("3.5.2", "is.Coord()", "is_coord()") + is_coord(x) +} # Renders an axis with the correct orientation or zeroGrob if no axis should be # generated diff --git a/R/coord-cartesian-.R b/R/coord-cartesian-.R index 74f46433db..35be78a285 100644 --- a/R/coord-cartesian-.R +++ b/R/coord-cartesian-.R @@ -159,7 +159,7 @@ view_scales_from_scale <- function(scale, coord_limits = NULL, expand = TRUE) { } panel_guides_grob <- function(guides, position, theme, labels = NULL) { - if (!inherits(guides, "Guides")) { + if (!is_guides(guides)) { return(zeroGrob()) } pair <- guides$get_position(position) diff --git a/R/facet-.R b/R/facet-.R index abdd373d05..533d8a2eaf 100644 --- a/R/facet-.R +++ b/R/facet-.R @@ -239,13 +239,17 @@ vars <- function(...) { quos(...) } +#' @export +#' @rdname is_tests +is_facet <- function(x) inherits(x, "Facet") -#' Is this object a faceting specification? -#' -#' @param x object to test -#' @keywords internal #' @export -is.facet <- function(x) inherits(x, "Facet") +#' @rdname is_tests +#' @usage is.facet(x) # Deprecated +is.facet <- function(x) { + deprecate_soft0("3.5.2", "is.facet()", "is_facet()") + is_facet(x) +} # A "special" value, currently not used but could be used to determine # if faceting is active @@ -324,7 +328,7 @@ as_facets_list <- function(x) { } validate_facets <- function(x) { - if (inherits(x, "uneval")) { + if (is_mapping(x)) { cli::cli_abort("Please use {.fn vars} to supply facet variables.") } # Native pipe have higher precedence than + so any type of gg object can be diff --git a/R/fortify.R b/R/fortify.R index b9cf025f2a..15d61c3fd0 100644 --- a/R/fortify.R +++ b/R/fortify.R @@ -82,7 +82,7 @@ fortify.default <- function(model, data, ...) { "or an object coercible by {{.fn fortify}}, or a valid ", "{{.cls data.frame}}-like object coercible by {{.fn as.data.frame}}" ) - if (inherits(model, "uneval")) { + if (is_mapping(model)) { msg <- c( glue(msg0, ", not {obj_type_friendly(model)}."), "i" = "Did you accidentally pass {.fn aes} to the {.arg data} argument?" diff --git a/R/geom-.R b/R/geom-.R index c1967a89c1..6ad6fb67fb 100644 --- a/R/geom-.R +++ b/R/geom-.R @@ -222,6 +222,9 @@ Geom <- ggproto("Geom", ) +#' @export +#' @rdname is_tests +is_geom <- function(x) inherits(x, "Geom") #' Graphical units #' diff --git a/R/ggproto.R b/R/ggproto.R index 48b1fcf96f..d7225dd7a7 100644 --- a/R/ggproto.R +++ b/R/ggproto.R @@ -52,7 +52,7 @@ #' self$x #' } #' ) -#' is.ggproto(Adder) +#' is_ggproto(Adder) #' #' Adder$add(10) #' Adder$add(10) @@ -88,7 +88,7 @@ ggproto <- function(`_class` = NULL, `_inherit` = NULL, ...) { super <- find_super() if (!is.null(super)) { - check_object(super, is.ggproto, "a {.cls ggproto} object", arg = "_inherit") + check_object(super, is_ggproto, "a {.cls ggproto} object", arg = "_inherit") e$super <- find_super class(e) <- c(`_class`, class(super)) } else { @@ -106,10 +106,17 @@ ggproto_parent <- function(parent, self) { structure(list(parent = parent, self = self), class = "ggproto_parent") } -#' @param x An object to test. #' @export -#' @rdname ggproto -is.ggproto <- function(x) inherits(x, "ggproto") +#' @rdname is_tests +is_ggproto <- function(x) inherits(x, "ggproto") + +#' @export +#' @rdname is_tests +#' @usage is.ggproto(x) # Deprecated +is.ggproto <- function(x) { + deprecate_soft0("3.5.2", "is.ggproto()", "is_ggproto()") + is_ggproto(x) +} fetch_ggproto <- function(x, name) { res <- NULL @@ -305,7 +312,7 @@ object_summaries <- function(x, exclude = NULL, flat = TRUE) { values <- vapply(obj_names, function(name) { obj <- x[[name]] if (is.function(obj)) "function" - else if (is.ggproto(obj)) format(obj, flat = flat) + else if (is_ggproto(obj)) format(obj, flat = flat) else if (is.environment(obj)) "environment" else if (is.null(obj)) "NULL" else if (is.atomic(obj)) trim(paste(as.character(obj), collapse = " ")) diff --git a/R/guide-.R b/R/guide-.R index 0a334c4580..1d31ddc957 100644 --- a/R/guide-.R +++ b/R/guide-.R @@ -50,7 +50,7 @@ new_guide <- function(..., available_aes = "any", super) { # Validate theme settings if (!is.null(params$theme)) { - check_object(params$theme, is.theme, what = "a {.cls theme} object") + check_object(params$theme, is_theme, what = "a {.cls theme} object") validate_theme(params$theme, call = caller_env()) params$direction <- params$direction %||% params$theme$legend.direction } @@ -66,6 +66,10 @@ new_guide <- function(..., available_aes = "any", super) { ) } +#' @export +#' @rdname is_tests +is_guide <- function(x) inherits(x, "Guide") + #' @section Guides: #' #' The `guide_*()` functions, such as `guide_legend()` return an object that @@ -377,10 +381,10 @@ Guide <- ggproto( # Renders tickmarks build_ticks = function(key, elements, params, position = params$position, length = elements$ticks_length) { - if (!inherits(elements, "element")) { + if (!is_element(elements)) { elements <- elements$ticks } - if (!inherits(elements, "element_line")) { + if (!is_element(elements, "line")) { return(zeroGrob()) } diff --git a/R/guide-axis.R b/R/guide-axis.R index 22cda82454..221c2de2ce 100644 --- a/R/guide-axis.R +++ b/R/guide-axis.R @@ -240,7 +240,7 @@ GuideAxis <- ggproto( override_elements = function(params, elements, theme) { label <- elements$text - if (!inherits(label, "element_text")) { + if (!is_element(label, "text")) { return(elements) } label_overrides <- axis_label_element_overrides( diff --git a/R/guide-legend.R b/R/guide-legend.R index ecf47b3089..6581c31556 100644 --- a/R/guide-legend.R +++ b/R/guide-legend.R @@ -787,7 +787,7 @@ deprecated_guide_args <- function( # Set as theme theme <- compact(theme) - if (!is.theme(theme)) { + if (!is_theme(theme)) { theme <- inject(theme(!!!theme)) } theme diff --git a/R/guides-.R b/R/guides-.R index 3ad66a4bf5..bd91989216 100644 --- a/R/guides-.R +++ b/R/guides-.R @@ -109,9 +109,13 @@ guides <- function(...) { NULL } +#' @export +#' @rdname is_tests +is_guides <- function(x) inherits(x, "Guides") + update_guides <- function(p, guides) { p <- plot_clone(p) - if (inherits(p$guides, "Guides")) { + if (is_guides(p$guides)) { old <- p$guides new <- ggproto(NULL, old) new$add(guides) @@ -151,7 +155,7 @@ Guides <- ggproto( if (is.null(guides)) { return(invisible()) } - if (inherits(guides, "Guides")) { + if (is_guides(guides)) { guides <- guides$guides } self$guides <- defaults(guides, self$guides) @@ -898,7 +902,7 @@ validate_guide <- function(guide) { guide <- fun() } } - if (inherits(guide, "Guide")) { + if (is_guide(guide)) { return(guide) } if (inherits(guide, "guide") && is.list(guide)) { diff --git a/R/layer.R b/R/layer.R index 7df5119aae..5bd949a4ed 100644 --- a/R/layer.R +++ b/R/layer.R @@ -199,7 +199,7 @@ layer <- function(geom = NULL, stat = NULL, } validate_mapping <- function(mapping, call = caller_env()) { - if (!inherits(mapping, "uneval")) { + if (!is_mapping(mapping)) { msg <- "{.arg mapping} must be created by {.fn aes}." # Native pipe have higher precedence than + so any type of gg object can be # expected here, not just ggplot @@ -462,7 +462,9 @@ Layer <- ggproto("Layer", NULL, } ) -is.layer <- function(x) inherits(x, "Layer") +#' @export +#' @rdname is_tests +is_layer <- function(x) inherits(x, "Layer") check_subclass <- function(x, subclass, argname = to_lower_ascii(subclass), diff --git a/R/margins.R b/R/margins.R index b563331002..6e3b1319ac 100644 --- a/R/margins.R +++ b/R/margins.R @@ -8,7 +8,10 @@ margin <- function(t = 0, r = 0, b = 0, l = 0, unit = "pt") { class(u) <- c("margin", class(u)) u } -is.margin <- function(x) { + +#' @export +#' @rdname is_tests +is_margin <- function(x) { inherits(x, "margin") } diff --git a/R/plot-build.R b/R/plot-build.R index 291841de90..de38e02675 100644 --- a/R/plot-build.R +++ b/R/plot-build.R @@ -272,7 +272,7 @@ ggplot_gtable.ggplot_built <- function(data) { plot_table <- gtable_add_rows(plot_table, theme$plot.margin[3]) plot_table <- gtable_add_cols(plot_table, theme$plot.margin[4], pos = 0) - if (inherits(theme$plot.background, "element")) { + if (is_element(theme$plot.background)) { plot_table <- gtable_add_grob(plot_table, element_render(theme, "plot.background"), t = 1, l = 1, b = -1, r = -1, name = "background", z = -Inf) diff --git a/R/plot-construction.R b/R/plot-construction.R index b6d83fe1f0..535b2e9563 100644 --- a/R/plot-construction.R +++ b/R/plot-construction.R @@ -51,9 +51,9 @@ # can be displayed in error messages e2name <- deparse(substitute(e2)) - if (is.theme(e1)) add_theme(e1, e2, e2name) - else if (is.ggplot(e1)) add_ggplot(e1, e2, e2name) - else if (is.ggproto(e1)) { + if (is_theme(e1)) add_theme(e1, e2, e2name) + else if (is_ggplot(e1)) add_ggplot(e1, e2, e2name) + else if (is_ggproto(e1)) { cli::cli_abort(c( "Cannot add {.cls ggproto} objects together.", "i" = "Did you forget to add this object to a {.cls ggplot} object?" diff --git a/R/plot.R b/R/plot.R index 0d1df80f98..b7d0dff6f4 100644 --- a/R/plot.R +++ b/R/plot.R @@ -111,7 +111,7 @@ ggplot <- function(data = NULL, mapping = aes(), ..., #' @export ggplot.default <- function(data = NULL, mapping = aes(), ..., environment = parent.frame()) { - if (!missing(mapping) && !inherits(mapping, "uneval")) { + if (!missing(mapping) && !is_mapping(mapping)) { cli::cli_abort(c( "{.arg mapping} must be created with {.fn aes}.", "x" = "You've supplied {.obj_type_friendly {mapping}}." @@ -156,11 +156,20 @@ plot_clone <- function(plot) { p } -#' Reports whether x is a ggplot object +#' Reports wether `x` is a type of object #' @param x An object to test #' @keywords internal #' @export -is.ggplot <- function(x) inherits(x, "ggplot") +#' @name is_tests +is_ggplot <- function(x) inherits(x, "ggplot") + +#' @export +#' @rdname is_tests +#' @usage is.ggplot(x) # Deprecated +is.ggplot <- function(x) { + deprecate_soft0("3.5.2", "is.ggplot", "is_ggplot") + is_ggplot(x) +} #' Explicitly draw plot #' diff --git a/R/position-.R b/R/position-.R index 559c6c68d0..c731f2b3cc 100644 --- a/R/position-.R +++ b/R/position-.R @@ -69,6 +69,10 @@ Position <- ggproto("Position", } ) +#' @export +#' @rdname is_tests +is_position <- function(x) inherits(x, "Position") + #' Convenience function to transform all position variables. #' #' @param trans_x,trans_y Transformation functions for x and y aesthetics. diff --git a/R/scale-.R b/R/scale-.R index 0b374d72ef..15c8ea1d5b 100644 --- a/R/scale-.R +++ b/R/scale-.R @@ -350,6 +350,10 @@ binned_scale <- function(aesthetics, scale_name = deprecated(), palette, name = ) } +#' @export +#' @rdname is_tests +is_scale <- function(x) inherits(x, "Scale") + #' @section Scales: #' #' All `scale_*` functions like [scale_x_continuous()] return a `Scale*` diff --git a/R/scale-colour.R b/R/scale-colour.R index 71255e2033..47f14063c3 100644 --- a/R/scale-colour.R +++ b/R/scale-colour.R @@ -197,7 +197,7 @@ scale_fill_binned <- function(..., # helper function to make sure that the provided scale is of the correct # type (i.e., is continuous and works with the provided aesthetic) check_scale_type <- function(scale, name, aesthetic, scale_is_discrete = FALSE, call = caller_env()) { - if (!is.ggproto(scale) || !inherits(scale, "Scale")) { + if (!is_ggproto(scale) || !is_scale(scale)) { cli::cli_abort(c( "The {.arg type} argument must return a continuous scale for the {.field {aesthetic}} aesthetic.", "x" = "The provided object is not a scale function." diff --git a/R/stat-.R b/R/stat-.R index 2d56937b06..186341eb78 100644 --- a/R/stat-.R +++ b/R/stat-.R @@ -218,3 +218,7 @@ Stat <- ggproto("Stat", } ) + +#' @export +#' @rdname is_tests +is_stat <- function(x) inherits(x, "Stat") diff --git a/R/theme-current.R b/R/theme-current.R index b56b2e1651..839a02371d 100644 --- a/R/theme-current.R +++ b/R/theme-current.R @@ -90,7 +90,7 @@ theme_get <- function() { #' @param new new theme (a list of theme elements) #' @export theme_set <- function(new) { - check_object(new, is.theme, "a {.cls theme} object") + check_object(new, is_theme, "a {.cls theme} object") old <- ggplot_global$theme_current ggplot_global$theme_current <- new invisible(old) @@ -111,7 +111,7 @@ theme_replace <- function(...) { #' @rdname theme_get #' @export "%+replace%" <- function(e1, e2) { - if (!is.theme(e1) || !is.theme(e2)) { + if (!is_theme(e1) || !is_theme(e2)) { cli::cli_abort("{.code %+replace%} requires two theme objects") } diff --git a/R/theme-elements.R b/R/theme-elements.R index b8e83c75e4..35ac8624f3 100644 --- a/R/theme-elements.R +++ b/R/theme-elements.R @@ -21,6 +21,8 @@ #' a blank element among its parents will cause this element to be blank as #' well. If `FALSE` any blank parent element will be ignored when #' calculating final element state. +#' @param type For testing elements: the type of element to expect. One of +#' `"blank"`, `"rect"`, `"line"` or `"text"`. #' @return An S3 object of class `element`, `rel`, or `margin`. #' @examples #' plot <- ggplot(mpg, aes(displ, hwy)) + geom_point() @@ -144,6 +146,22 @@ element_text <- function(family = NULL, face = NULL, colour = NULL, ) } +#' @export +#' @rdname element +is_element <- function(x, type = "any") { + switch( + type %||% "any", + any = inherits(x, "element"), + rect = inherits(x, "element_rect"), + line = inherits(x, "element_line"), + text = inherits(x, "element_text"), + blank = inherits(x, "element_blank"), + # TODO: ideally we accept more elements from extensions. We need to + # consider how this will work with S7 classes, where ggplot2 doesn't know + # about the extension's class objects. + FALSE + ) +} #' @export print.element <- function(x, ...) utils::str(x) diff --git a/R/theme.R b/R/theme.R index 3611af323e..e7bb9c0994 100644 --- a/R/theme.R +++ b/R/theme.R @@ -475,7 +475,7 @@ theme <- function(..., elements$panel.spacing.y <- elements$panel.margin.y elements$panel.margin.y <- NULL } - if (is.unit(elements$legend.margin) && !is.margin(elements$legend.margin)) { + if (is.unit(elements$legend.margin) && !is_margin(elements$legend.margin)) { cli::cli_warn(c( "{.var legend.margin} must be specified using {.fn margin}", "i" = "For the old behavior use {.var legend.spacing}" @@ -521,7 +521,7 @@ theme <- function(..., # If complete theme set all non-blank elements to inherit from blanks if (complete) { elements <- lapply(elements, function(el) { - if (inherits(el, "element") && !inherits(el, "element_blank")) { + if (is_element(el) && !is_element(el, "blank")) { el$inherit.blank <- TRUE } el @@ -821,7 +821,7 @@ combine_elements <- function(e1, e2) { } # If neither of e1 or e2 are element_* objects, return e1 - if (!inherits(e1, "element") && !inherits(e2, "element")) { + if (!is_element(e1) && !is_element(e2)) { return(e1) } @@ -864,11 +864,18 @@ is.subclass <- function(x, y) { !any(inheritance == 0) && length(setdiff(class(x), class(y))) > 0 } -#' Reports whether x is a theme object -#' @param x An object to test + #' @export -#' @keywords internal -is.theme <- function(x) inherits(x, "theme") +#' @rdname is_tests +is_theme <- function(x) inherits(x, "theme") + +#' @export +#' @rdname is_tests +#' @usage is.theme(x) # Deprecated +is.theme <- function(x) { + deprecate_soft0("3.5.2", "is.theme", "is_theme") + is_theme(x) +} #' @export `$.theme` <- function(x, ...) { diff --git a/man/element.Rd b/man/element.Rd index a3c27a259c..b76ccf0b50 100644 --- a/man/element.Rd +++ b/man/element.Rd @@ -5,6 +5,7 @@ \alias{element_rect} \alias{element_line} \alias{element_text} +\alias{is_element} \alias{rel} \alias{margin} \title{Theme elements} @@ -47,6 +48,8 @@ element_text( inherit.blank = FALSE ) +is_element(x, type = "any") + rel(x) margin(t = 0, r = 0, b = 0, l = 0, unit = "pt") @@ -97,6 +100,9 @@ is anchored.} \item{x}{A single number specifying size relative to parent element.} +\item{type}{For testing elements: the type of element to expect. One of +\code{"blank"}, \code{"rect"}, \code{"line"} or \code{"text"}.} + \item{t, r, b, l}{Dimensions of each margin. (To remember order, think trouble).} \item{unit}{Default units of dimensions. Defaults to "pt" so it diff --git a/man/ggproto.Rd b/man/ggproto.Rd index c00c2000f6..faeb7d70e2 100644 --- a/man/ggproto.Rd +++ b/man/ggproto.Rd @@ -3,14 +3,11 @@ \name{ggproto} \alias{ggproto} \alias{ggproto_parent} -\alias{is.ggproto} \title{Create a new ggproto object} \usage{ ggproto(`_class` = NULL, `_inherit` = NULL, ...) ggproto_parent(parent, self) - -is.ggproto(x) } \arguments{ \item{_class}{Class name to assign to the object. This is stored as the class @@ -24,8 +21,6 @@ inherit from any object.} functions that become methods of the class or regular objects.} \item{parent, self}{Access parent class \code{parent} of object \code{self}.} - -\item{x}{An object to test.} } \description{ Construct a new object with \code{ggproto()}, test with \code{is.ggproto()}, @@ -77,7 +72,7 @@ Adder <- ggproto("Adder", self$x } ) -is.ggproto(Adder) +is_ggproto(Adder) Adder$add(10) Adder$add(10) diff --git a/man/is.Coord.Rd b/man/is.Coord.Rd deleted file mode 100644 index 50b4520640..0000000000 --- a/man/is.Coord.Rd +++ /dev/null @@ -1,12 +0,0 @@ -% Generated by roxygen2: do not edit by hand -% Please edit documentation in R/coord-.R -\name{is.Coord} -\alias{is.Coord} -\title{Is this object a coordinate system?} -\usage{ -is.Coord(x) -} -\description{ -Is this object a coordinate system? -} -\keyword{internal} diff --git a/man/is.facet.Rd b/man/is.facet.Rd deleted file mode 100644 index bd8fc7b5ba..0000000000 --- a/man/is.facet.Rd +++ /dev/null @@ -1,15 +0,0 @@ -% Generated by roxygen2: do not edit by hand -% Please edit documentation in R/facet-.R -\name{is.facet} -\alias{is.facet} -\title{Is this object a faceting specification?} -\usage{ -is.facet(x) -} -\arguments{ -\item{x}{object to test} -} -\description{ -Is this object a faceting specification? -} -\keyword{internal} diff --git a/man/is.ggplot.Rd b/man/is.ggplot.Rd deleted file mode 100644 index 837bc9a919..0000000000 --- a/man/is.ggplot.Rd +++ /dev/null @@ -1,15 +0,0 @@ -% Generated by roxygen2: do not edit by hand -% Please edit documentation in R/plot.R -\name{is.ggplot} -\alias{is.ggplot} -\title{Reports whether x is a ggplot object} -\usage{ -is.ggplot(x) -} -\arguments{ -\item{x}{An object to test} -} -\description{ -Reports whether x is a ggplot object -} -\keyword{internal} diff --git a/man/is.theme.Rd b/man/is.theme.Rd deleted file mode 100644 index c7930a2e96..0000000000 --- a/man/is.theme.Rd +++ /dev/null @@ -1,15 +0,0 @@ -% Generated by roxygen2: do not edit by hand -% Please edit documentation in R/theme.R -\name{is.theme} -\alias{is.theme} -\title{Reports whether x is a theme object} -\usage{ -is.theme(x) -} -\arguments{ -\item{x}{An object to test} -} -\description{ -Reports whether x is a theme object -} -\keyword{internal} diff --git a/man/is_tests.Rd b/man/is_tests.Rd new file mode 100644 index 0000000000..d6846f1ca8 --- /dev/null +++ b/man/is_tests.Rd @@ -0,0 +1,72 @@ +% Generated by roxygen2: do not edit by hand +% Please edit documentation in R/ggproto.R, R/aes.R, R/geom-.R, R/coord-.R, +% R/facet-.R, R/stat-.R, R/guide-.R, R/layer.R, R/guides-.R, R/margins.R, +% R/plot.R, R/position-.R, R/scale-.R, R/theme.R +\name{is_ggproto} +\alias{is_ggproto} +\alias{is.ggproto} +\alias{is_mapping} +\alias{is_geom} +\alias{is_coord} +\alias{is.Coord} +\alias{is_facet} +\alias{is.facet} +\alias{is_stat} +\alias{is_guide} +\alias{is_layer} +\alias{is_guides} +\alias{is_margin} +\alias{is_tests} +\alias{is_ggplot} +\alias{is.ggplot} +\alias{is_position} +\alias{is_scale} +\alias{is_theme} +\alias{is.theme} +\title{Reports wether \code{x} is a type of object} +\usage{ +is_ggproto(x) + +is.ggproto(x) # Deprecated + +is_mapping(x) + +is_geom(x) + +is_coord(x) + +is.Coord(x) # Deprecated + +is_facet(x) + +is.facet(x) # Deprecated + +is_stat(x) + +is_guide(x) + +is_layer(x) + +is_guides(x) + +is_margin(x) + +is_ggplot(x) + +is.ggplot(x) # Deprecated + +is_position(x) + +is_scale(x) + +is_theme(x) + +is.theme(x) # Deprecated +} +\arguments{ +\item{x}{An object to test} +} +\description{ +Reports wether \code{x} is a type of object +} +\keyword{internal} diff --git a/tests/testthat/test-function-args.R b/tests/testthat/test-function-args.R index 2a78bf9f50..22b59a394f 100644 --- a/tests/testthat/test-function-args.R +++ b/tests/testthat/test-function-args.R @@ -22,7 +22,7 @@ test_that("geom_xxx and GeomXxx$draw arg defaults match", { lapply(geom_fun_names, function(geom_fun_name) { geom_fun <- ggplot2_ns[[geom_fun_name]] geom <- geom_fun()$geom - if (!inherits(geom, "Geom")) # for geoms that return more than one thing + if (!is_geom(geom)) # for geoms that return more than one thing return() fun_args <- formals(geom_fun) diff --git a/tests/testthat/test-theme.R b/tests/testthat/test-theme.R index 895d4cf9fc..6c2a2b5a68 100644 --- a/tests/testthat/test-theme.R +++ b/tests/testthat/test-theme.R @@ -19,10 +19,10 @@ test_that("modifying theme element properties with + operator works", { t <- theme_grey() + theme(axis.title.x = element_text(colour = 'red', margin = margin())) expect_identical(t$axis.title.x, element_text(colour = 'red', margin = margin(), vjust = 1)) # Make sure the theme class didn't change or get dropped - expect_true(is.theme(t)) + expect_s3_class(t, "theme") # Make sure the element class didn't change or get dropped - expect_true(inherits(t$axis.title.x, "element")) - expect_true(inherits(t$axis.title.x, "element_text")) + expect_s3_class(t$axis.title.x, "element") + expect_s3_class(t$axis.title.x, "element_text") # Modifying an intermediate node works t <- theme_grey() + theme(axis.title = element_text(colour = 'red')) @@ -103,7 +103,7 @@ test_that("replacing theme elements with %+replace% operator works", { t <- theme_grey() %+replace% theme(axis.title.x = element_text(colour = 'red')) expect_identical(t$axis.title.x, element_text(colour = 'red')) # Make sure the class didn't change or get dropped - expect_true(is.theme(t)) + expect_s3_class(t, "theme") # Changing an intermediate node works t <- theme_grey() %+replace% theme(axis.title = element_text(colour = 'red')) @@ -337,7 +337,7 @@ test_that("element tree can be modified", { test_that("all elements in complete themes have inherit.blank=TRUE", { inherit_blanks <- function(theme) { all(vapply(theme, function(el) { - if (inherits(el, "element") && !inherits(el, "element_blank")) { + if (is_element(el) && !is_element(el, "blank")) { el$inherit.blank } else { TRUE @@ -778,7 +778,7 @@ test_that("Legends can on all sides of the plot with custom justification", { test_that("Strips can render custom elements", { element_test <- function(...) { el <- element_text(...) - class(el) <- c('element_test', 'element_text', 'element') + class(el) <- c("element_test", "element_text", "element") el } element_grob.element_test <- function(element, label = "", x = NULL, y = NULL, ...) {