Skip to content

Commit fbebbaa

Browse files
authored
Make sure boxplot check doesn't polute other stats/geoms (#3800)
1 parent a9df27d commit fbebbaa

File tree

3 files changed

+29
-9
lines changed

3 files changed

+29
-9
lines changed

R/stat-boxplot.r

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -59,7 +59,9 @@ StatBoxplot <- ggproto("StatBoxplot", Stat,
5959
},
6060

6161
setup_params = function(data, params) {
62-
params$flipped_aes <- has_flipped_aes(data, params, main_is_orthogonal = TRUE, group_has_equal = TRUE)
62+
params$flipped_aes <- has_flipped_aes(data, params, main_is_orthogonal = TRUE,
63+
group_has_equal = TRUE,
64+
main_is_optional = TRUE)
6365
data <- flip_data(data, params$flipped_aes)
6466

6567
has_x <- !(is.null(data$x) && is.null(params$x))

R/utilities.r

Lines changed: 17 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -475,6 +475,10 @@ switch_orientation <- function(aesthetics) {
475475
#' will be the discrete-like one. Examples of `TRUE` is [stat_density()] and
476476
#' [stat_bin()], while examples of `FALSE` is [stat_ydensity()] and
477477
#' [stat_boxplot()]
478+
#' - `main_is_optional`: This argument controls the rare case of layers were the
479+
#' main direction is an optional aesthetic. This is only seen in
480+
#' [stat_boxplot()] where `x` is set to `0` if not given. If `TRUE` there will
481+
#' be a check for whether all `x` or all `y` are equal to `0`
478482
#'
479483
#' @param data The layer data
480484
#' @param params The parameters of the `Stat`/`Geom`. Only the `orientation`
@@ -491,6 +495,8 @@ switch_orientation <- function(aesthetics) {
491495
#' will only be flipped if `params$orientation == "y"`
492496
#' @param main_is_continuous If there is a discrete and continuous axis, does
493497
#' the continuous one correspond to the main orientation?
498+
#' @param main_is_optional Is the main axis aesthetic optional and, if not
499+
#' given, set to `0`
494500
#' @param flip Logical. Is the layer flipped.
495501
#'
496502
#' @return `has_flipped_aes()` returns `TRUE` if it detects a layer in the other
@@ -507,7 +513,8 @@ switch_orientation <- function(aesthetics) {
507513
#'
508514
has_flipped_aes <- function(data, params = list(), main_is_orthogonal = NA,
509515
range_is_orthogonal = NA, group_has_equal = FALSE,
510-
ambiguous = FALSE, main_is_continuous = FALSE) {
516+
ambiguous = FALSE, main_is_continuous = FALSE,
517+
main_is_optional = FALSE) {
511518
# Is orientation already encoded in data?
512519
if (!is.null(data$flipped_aes)) {
513520
not_na <- which(!is.na(data$flipped_aes))
@@ -591,12 +598,15 @@ has_flipped_aes <- function(data, params = list(), main_is_orthogonal = NA,
591598
if (xor(y_is_int, x_is_int)) {
592599
return(y_is_int != main_is_continuous)
593600
}
594-
# Is one of the axes a single value
595-
if (all(x == 1)) {
596-
return(main_is_continuous)
597-
}
598-
if (all(y == 1)) {
599-
return(!main_is_continuous)
601+
602+
if (main_is_optional) {
603+
# Is one of the axes all 0
604+
if (all(x == 0)) {
605+
return(main_is_continuous)
606+
}
607+
if (all(y == 0)) {
608+
return(!main_is_continuous)
609+
}
600610
}
601611

602612
y_diff <- diff(sort(y))

man/bidirection.Rd

Lines changed: 9 additions & 1 deletion
Some generated files are not rendered by default. Learn more about customizing how changed files appear on GitHub.

0 commit comments

Comments
 (0)