facets: manage yaxis2 correctly

This commit is contained in:
pvictor 2022-12-01 11:51:52 +01:00
parent f50e0064c2
commit e848debf0a
3 changed files with 43 additions and 28 deletions

View File

@ -99,6 +99,7 @@ importFrom(rlang,"%||%")
importFrom(rlang,as_label) importFrom(rlang,as_label)
importFrom(rlang,eval_tidy) importFrom(rlang,eval_tidy)
importFrom(rlang,is_function) importFrom(rlang,is_function)
importFrom(rlang,is_list)
importFrom(rlang,is_named) importFrom(rlang,is_named)
importFrom(rlang,is_null) importFrom(rlang,is_null)
importFrom(rlang,quos) importFrom(rlang,quos)

View File

@ -38,7 +38,7 @@ n_facet <- function(l) {
Reduce(`*`, l) Reduce(`*`, l)
} }
#' @importFrom rlang %||% #' @importFrom rlang %||% is_list is_named
set_scale <- function(ax, values, scales = c("fixed", "free", "free_y", "free_x"), axis = c("x", "y")) { set_scale <- function(ax, values, scales = c("fixed", "free", "free_y", "free_x"), axis = c("x", "y")) {
if (is.null(scales)) if (is.null(scales))
return(ax) return(ax)
@ -66,30 +66,41 @@ set_scale <- function(ax, values, scales = c("fixed", "free", "free_y", "free_x"
"y" = "yaxis" "y" = "yaxis"
) )
this_axis <- ax$x$ax_opts[[waxis]]
if (is_list(this_axis) & !is_named(this_axis)) {
this_axis <- this_axis[[1]]
yaxis2 <- TRUE
} else {
yaxis2 <- FALSE
}
if (scales == "fixed") { if (scales == "fixed") {
ax$x$ax_opts[[waxis]]$min <- ax$x$ax_opts[[waxis]]$min %||% fmt(range_vals[1]) this_axis$min <- this_axis$min %||% fmt(range_vals[1])
ax$x$ax_opts[[waxis]]$max <- ax$x$ax_opts[[waxis]]$max %||% fmt(range_vals[2]) this_axis$max <- this_axis$max %||% fmt(range_vals[2])
} else if (scales == "free") { } else if (scales == "free") {
ax$x$ax_opts[[waxis]]$min <- NULL this_axis$min <- NULL
ax$x$ax_opts[[waxis]]$max <- NULL this_axis$max <- NULL
} else if (scales == "free_x") { } else if (scales == "free_x") {
if (axis == "y") { if (axis == "y") {
ax$x$ax_opts[[waxis]]$min <- ax$x$ax_opts[[waxis]]$min %||% fmt(range_vals[1]) this_axis$min <- this_axis$min %||% fmt(range_vals[1])
ax$x$ax_opts[[waxis]]$max <- ax$x$ax_opts[[waxis]]$max %||% fmt(range_vals[2]) this_axis$max <- this_axis$max %||% fmt(range_vals[2])
} else { } else {
ax$x$ax_opts[[waxis]]$min <- NULL this_axis$min <- NULL
ax$x$ax_opts[[waxis]]$max <- NULL this_axis$max <- NULL
} }
} else if (scales == "free_y") { } else if (scales == "free_y") {
if (axis == "x") { if (axis == "x") {
ax$x$ax_opts[[waxis]]$min <- ax$x$ax_opts[[waxis]]$min %||% fmt(range_vals[1]) this_axis$min <- this_axis$min %||% fmt(range_vals[1])
ax$x$ax_opts[[waxis]]$max <- ax$x$ax_opts[[waxis]]$max %||% fmt(range_vals[2]) this_axis$max <- this_axis$max %||% fmt(range_vals[2])
} else { } else {
ax$x$ax_opts[[waxis]]$min <- NULL this_axis$min <- NULL
ax$x$ax_opts[[waxis]]$max <- NULL this_axis$max <- NULL
} }
} }
if (yaxis2) {
ax$x$ax_opts[[waxis]][[1]] <- this_axis
} else {
ax$x$ax_opts[[waxis]] <- this_axis
}
return(ax) return(ax)
} }

View File

@ -5,7 +5,10 @@ null_or_empty <- function(x) {
dropNullsOrEmpty <- function(x) { dropNullsOrEmpty <- function(x) {
x[!vapply(x, null_or_empty, FUN.VALUE = logical(1))] clss <- class(x)
x <- x[!vapply(x, null_or_empty, FUN.VALUE = logical(1))]
class(x) <- clss
return(x)
} }
dropNulls <- function(x) { dropNulls <- function(x) {