Skip to content

Commit 4706dda

Browse files
committed
only insert missing values to differentiate groups when it's relevant
1 parent 54ce776 commit 4706dda

File tree

4 files changed

+24
-7
lines changed

4 files changed

+24
-7
lines changed

R/plotly_build.R

Lines changed: 4 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -179,16 +179,13 @@ plotly_build.plotly <- function(p) {
179179
# are combined into a single grouping variable, .plotlyGroupIndex
180180
builtData <- arrange_safe(builtData, ".plotlyTraceIndex")
181181
isComplete <- complete.cases(builtData[names(builtData) %in% c("x", "y", "z")])
182-
# is grouping relevant for this geometry? (e.g., grouping doesn't effect a scatterplot)
183-
hasGrp <- inherits(trace, paste0("plotly_", c("segment", "path", "line", "polygon"))) ||
184-
(grepl("scatter", trace[["type"]]) && grepl("lines", trace[["mode"]]))
185182
# warn about missing values if groups aren't relevant for this trace type
186-
if (any(!isComplete) && !hasGrp) {
183+
if (any(!isComplete) && !has_group(trace)) {
187184
warning("Ignoring ", sum(!isComplete), " observations", call. = FALSE)
188185
}
189186
builtData[[".plotlyMissingIndex"]] <- cumsum(!isComplete)
190187
builtData <- builtData[isComplete, ]
191-
if (length(grps) && hasGrp && isTRUE(trace[["connectgaps"]])) {
188+
if (length(grps) && has_group(trace) && isTRUE(trace[["connectgaps"]])) {
192189
stop(
193190
"Can't use connectgaps=TRUE when data has group(s).", call. = FALSE
194191
)
@@ -229,7 +226,8 @@ plotly_build.plotly <- function(p) {
229226
traces <- lapply(traces, function(x) {
230227
d <- data.frame(x[names(x) %in% x$.plotlyVariableMapping], stringsAsFactors = FALSE)
231228
d <- group2NA(
232-
d, ".plotlyGroupIndex", ordered = if (inherits(x, "plotly_line")) "x",
229+
d, if (has_group(x)) ".plotlyGroupIndex",
230+
ordered = if (inherits(x, "plotly_line")) "x",
233231
retrace.first = inherits(x, "plotly_polygon")
234232
)
235233
for (i in x$.plotlyVariableMapping) {

R/utils.R

Lines changed: 6 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -47,6 +47,12 @@ getLevels <- function(x) {
4747
if (is.factor(x)) levels(x) else sort(unique(x))
4848
}
4949

50+
# is grouping relevant for this geometry? (e.g., grouping doesn't effect a scatterplot)
51+
has_group <- function(trace) {
52+
inherits(trace, paste0("plotly_", c("segment", "path", "line", "polygon"))) ||
53+
(grepl("scatter", trace[["type"]]) && grepl("lines", trace[["mode"]]))
54+
}
55+
5056
# currently implemented non-positional scales in plot_ly()
5157
npscales <- function() {
5258
c("color", "symbol", "linetype", "size", "split")

tests/testthat/test-ggplot-heatmap.R

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -46,7 +46,7 @@ test_that("geom_tile() scale_fill_gradient2()", {
4646
})
4747

4848
tidy_cor <- function(x) {
49-
co <- as.data.frame(cor(x))
49+
co <- as.data.frame(cor(x[vapply(x, is.numeric, logical(1))]))
5050
co$var1 <- row.names(co)
5151
tidyr::gather(co, var2, cor, -var1)
5252
}

tests/testthat/test-plotly-group.R

Lines changed: 13 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -52,3 +52,16 @@ test_that("Missing values are preserved for lines within a color variable", {
5252
# connectgaps makes sense in this case
5353
l <- expect_traces(add_lines(p3, connectgaps = TRUE), 5, "NAs-within-color2")
5454
})
55+
56+
m <- mtcars
57+
m$rowname <- rownames(mtcars)
58+
p <- m %>%
59+
dplyr::group_by_("rowname") %>%
60+
plot_ly(x = ~wt, y = ~mpg) %>%
61+
add_markers()
62+
63+
test_that("Groups are ignored if grouping is irrelevant for the geom", {
64+
l <- expect_traces(p, 1, "no-NAs-for-irrelevant-group")
65+
expect_length(l$data[[1]][["x"]], 32)
66+
expect_length(l$data[[1]][["y"]], 32)
67+
})

0 commit comments

Comments
 (0)