Skip to content

Commit c87bca1

Browse files
cpsievertclaude
andcommitted
Fix #2419, #2437: NA handling and subplot issues
- Fix #2419: When hovertemplate was present and .plotlyVariableMapping length happened to equal row count, traceify() incorrectly subsetted it like data, breaking group2NA() NA insertion for line gaps. Now saves .plotlyVariableMapping before traceify and restores after. - Fix #2437: subplot() with pie charts created NA-named layout attributes because pie charts lack cartesian axes. Now checks if axes exist before extracting; returns empty list for plots without axes. Co-Authored-By: Claude Opus 4.5 <noreply@anthropic.com>
1 parent 9401e32 commit c87bca1

File tree

4 files changed

+235
-8
lines changed

4 files changed

+235
-8
lines changed

NEWS.md

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -33,6 +33,8 @@ See the [plotly.js releases page](https://github.com/plotly/plotly.js/releases)
3333
* Closed #2467: `ggplotly()` now correctly shows legends and splits traces when scales have multiple aesthetics.
3434
* Closed #2407, #2187: `ggplotly()` now translates `legend.position` theme element to plotly layout (supports "bottom", "top", "left", and numeric positions).
3535
* Closed #2281: `ggplotly()` no longer drops legends when `geom_blank()` is present in the plot.
36+
* Closed #2419: `plot_ly()` with color mapping and `hovertemplate` no longer incorrectly connects line segments that should be separated by NA values.
37+
* Closed #2437: `subplot()` with pie charts no longer creates invalid "NA" layout attributes.
3638

3739
# plotly 4.11.0
3840

R/plotly_build.R

Lines changed: 15 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -273,9 +273,21 @@ plotly_build.plotly <- function(p, registerFrames = TRUE) {
273273
traces <- list()
274274
for (i in seq_along(dats)) {
275275
d <- dats[[i]]
276-
scaleAttrs <- names(d) %in% paste0(npscales(), "s")
277-
traces <- c(traces, traceify(d[!scaleAttrs], d$.plotlyTraceIndex))
278-
if (i == 1) traces[[1]] <- c(traces[[1]], d[scaleAttrs])
276+
# Save .plotlyVariableMapping before traceify - it's metadata (column names)
277+
# that shouldn't be subsetted like data columns. When its length happens to
278+
# equal the number of rows, traceify would incorrectly subset it. (#2419)
279+
variableMapping <- d$.plotlyVariableMapping
280+
# Exclude .plotlyVariableMapping from traceify input
281+
attrsToTraceify <- setdiff(names(d), ".plotlyVariableMapping")
282+
scaleAttrs <- attrsToTraceify %in% paste0(npscales(), "s")
283+
newTraces <- traceify(d[attrsToTraceify[!scaleAttrs]], d$.plotlyTraceIndex)
284+
# Restore .plotlyVariableMapping to all new traces
285+
newTraces <- lapply(newTraces, function(tr) {
286+
tr$.plotlyVariableMapping <- variableMapping
287+
tr
288+
})
289+
traces <- c(traces, newTraces)
290+
if (i == 1) traces[[1]] <- c(traces[[1]], d[attrsToTraceify[scaleAttrs]])
279291
}
280292

281293
# insert NAs to differentiate groups

R/subplots.R

Lines changed: 9 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -127,16 +127,20 @@ subplot <- function(..., nrows = 1, widths = NULL, heights = NULL, margin = 0.02
127127
x$annotations[!axes]
128128
})
129129
# collect axis objects (note a _single_ geo/mapbox object counts a both an x and y)
130+
# Note: only extract axes that actually exist in the layout. Plots like pie charts
131+
# don't have cartesian axes and shouldn't contribute NA-named axis objects (#2437)
130132
xAxes <- lapply(layouts, function(lay) {
131-
keys <- grep("^geo|^mapbox|^xaxis", names(lay), value = TRUE) %||% "xaxis"
133+
keys <- grep("^geo|^mapbox|^xaxis", names(lay), value = TRUE)
134+
if (!length(keys)) return(list())
132135
for (k in keys) {
133136
dom <- lay[[k]]$domain %||% c(0, 1)
134137
if ("x" %in% names(dom)) dom <- dom[["x"]]
135138
}
136139
lay[keys]
137140
})
138141
yAxes <- lapply(layouts, function(lay) {
139-
keys <- grep("^geo|^mapbox|^yaxis", names(lay), value = TRUE) %||% "yaxis"
142+
keys <- grep("^geo|^mapbox|^yaxis", names(lay), value = TRUE)
143+
if (!length(keys)) return(list())
140144
for (k in keys) {
141145
dom <- lay[[k]]$domain %||% c(0, 1)
142146
if ("y" %in% names(dom)) dom <- dom[["y"]]
@@ -191,9 +195,9 @@ subplot <- function(..., nrows = 1, widths = NULL, heights = NULL, margin = 0.02
191195
length(plots), nrows, margin, widths = widths, heights = heights
192196
)
193197
for (i in seq_along(plots)) {
194-
# map axis object names
195-
xMap <- xAxisMap[[i]]
196-
yMap <- yAxisMap[[i]]
198+
# map axis object names (plots without axes, like pie charts, have no mapping)
199+
xMap <- if (i <= length(xAxisMap)) xAxisMap[[i]] else character(0)
200+
yMap <- if (i <= length(yAxisMap)) yAxisMap[[i]] else character(0)
197201
xAxes[[i]] <- setNames(xAxes[[i]], names(xMap))
198202
yAxes[[i]] <- setNames(yAxes[[i]], names(yMap))
199203
# for cartesian, bump corresponding axis anchor

tests/testthat/test-hard-issues.R

Lines changed: 209 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,209 @@
1+
# Tests for hard difficulty issue fixes
2+
# Following TDD: these tests are written FIRST before implementing fixes
3+
4+
# Issue #2419: Two NAs per category cause incorrect line connection
5+
# When exactly 2 NA values exist per category with a hovertemplate,
6+
# lines incorrectly connect across the NAs instead of creating gaps.
7+
8+
test_that("Issue #2419: exactly 2 NAs per category create gaps, not connected lines", {
9+
df <- data.frame(
10+
Category = rep(c("A", "B"), each = 6),
11+
Date = c(2020, 2021, 2022, 2023, 2024, 2025, 2020, 2021, 2022, 2023, 2024, 2025),
12+
Value = c(10, 15, NA, NA, 20, 25, 12, 14, NA, 22, NA, 27)
13+
)
14+
df$Date <- factor(df$Date, levels = unique(df$Date), ordered = TRUE)
15+
16+
p <- plot_ly(
17+
df,
18+
x = ~Date,
19+
y = ~Value,
20+
color = ~Category,
21+
type = 'scatter',
22+
mode = 'lines+markers',
23+
text = ~Category,
24+
hovertemplate = paste0("Date: %{x}<br>Category: %{text}")
25+
)
26+
27+
built <- plotly_build(p)
28+
29+
# There should be 2 traces (one per category)
30+
expect_equal(length(built$x$data), 2)
31+
32+
# For category A: values are 10, 15, NA, NA, 20, 25
33+
# After NA handling, the y values should have NAs inserted to create gaps
34+
traceA <- built$x$data[[1]]
35+
36+
# The key test: NAs should be present in the y data to create gaps
37+
38+
# If exactly 2 NAs are being connected incorrectly, this would fail
39+
# We should see NA values in the output that separate the groups
40+
expect_true(any(is.na(traceA$y)))
41+
42+
# For category B: values are 12, 14, NA, 22, NA, 27
43+
traceB <- built$x$data[[2]]
44+
expect_true(any(is.na(traceB$y)))
45+
})
46+
47+
test_that("Issue #2419: single NA per category creates gaps correctly", {
48+
df <- data.frame(
49+
Category = rep(c("A", "B"), each = 6),
50+
Date = c(2020, 2021, 2022, 2023, 2024, 2025, 2020, 2021, 2022, 2023, 2024, 2025),
51+
Value = c(10, 15, NA, 18, 20, 25, 12, 14, NA, 22, 24, 27)
52+
)
53+
df$Date <- factor(df$Date, levels = unique(df$Date), ordered = TRUE)
54+
55+
p <- plot_ly(
56+
df,
57+
x = ~Date,
58+
y = ~Value,
59+
color = ~Category,
60+
type = 'scatter',
61+
mode = 'lines+markers',
62+
text = ~Category,
63+
hovertemplate = paste0("Date: %{x}<br>Category: %{text}")
64+
)
65+
66+
built <- plotly_build(p)
67+
68+
# There should be 2 traces (one per category)
69+
expect_equal(length(built$x$data), 2)
70+
71+
# Both traces should have NA values to create gaps
72+
traceA <- built$x$data[[1]]
73+
traceB <- built$x$data[[2]]
74+
expect_true(any(is.na(traceA$y)))
75+
expect_true(any(is.na(traceB$y)))
76+
})
77+
78+
79+
# Issue #2468: Pie chart color mapping doesn't work properly when aggregating data
80+
# When plotly.js aggregates pie chart data (duplicate labels), the marker.colors
81+
# don't apply correctly to the first slice.
82+
83+
test_that("Issue #2468: pie chart colors apply correctly with aggregated data", {
84+
# When there are 3 unique labels but more rows (so plotly aggregates),
85+
# marker.colors should apply to all slices correctly
86+
p <- plot_ly(
87+
mtcars[, c("cyl", "drat")],
88+
labels = ~cyl,
89+
values = ~drat,
90+
type = 'pie',
91+
marker = list(colors = c("cyan", "magenta", "black"))
92+
)
93+
94+
built <- plotly_build(p)
95+
96+
# The colors should be present in the marker (as-is, values preserved)
97+
colors <- as.character(built$x$data[[1]]$marker$colors)
98+
expect_equal(length(colors), 3)
99+
expect_equal(colors, c("cyan", "magenta", "black"))
100+
})
101+
102+
test_that("Issue #2468: pie chart colors work without aggregation", {
103+
# Without aggregation (unique labels), colors should still work
104+
p <- plot_ly(
105+
mtcars[c(1, 3, 5), c("cyl", "drat")],
106+
labels = ~cyl,
107+
values = ~drat,
108+
type = 'pie',
109+
marker = list(colors = c("cyan", "magenta", "black"))
110+
)
111+
112+
built <- plotly_build(p)
113+
114+
# The colors should be present in the marker (as-is, values preserved)
115+
colors <- as.character(built$x$data[[1]]$marker$colors)
116+
expect_equal(length(colors), 3)
117+
expect_equal(colors, c("cyan", "magenta", "black"))
118+
})
119+
120+
121+
# Issue #2437: subplot() with bar and pie chart creates NA layout attribute
122+
# When combining bar and pie charts in a subplot, an NA attribute is created
123+
# in the layout, causing a warning.
124+
125+
test_that("Issue #2437: subplot with bar and pie does not create NA layout attribute", {
126+
bar_info <- data.frame(
127+
Group = rep(c("first", "second", "third"), 2),
128+
values_monthly = c(100, 200, 300, 400, 500, 600),
129+
month = factor(rep(c("April", "May"), each = 3))
130+
)
131+
pie_info <- aggregate(values_monthly ~ Group, data = bar_info, sum)
132+
names(pie_info)[2] <- "values_total"
133+
134+
colors <- c("red", "blue", "yellow")
135+
136+
bar_chart <- plot_ly(
137+
bar_info,
138+
type = "bar",
139+
x = ~month,
140+
y = ~values_monthly,
141+
color = ~Group,
142+
colors = colors
143+
)
144+
145+
pie_chart <- plot_ly(
146+
pie_info,
147+
type = "pie",
148+
labels = ~Group,
149+
values = ~values_total,
150+
marker = list(colors = colors),
151+
domain = list(x = c(0.9, 1), y = c(0, 1)),
152+
showlegend = FALSE
153+
)
154+
155+
# Should not produce warnings about NA attributes
156+
expect_no_warning({
157+
combined_chart <- subplot(bar_chart, pie_chart, nrows = 1, widths = c(0.9, 0.1))
158+
})
159+
160+
built <- plotly_build(combined_chart)
161+
162+
# Layout should not have any attributes with NA names
163+
layout_names <- names(built$x$layout)
164+
expect_false(any(is.na(layout_names)))
165+
expect_false(any(grepl("^NA", layout_names)))
166+
})
167+
168+
test_that("Issue #2437: subplot warnings about discrete/non-discrete data", {
169+
bar_info <- data.frame(
170+
Group = rep(c("first", "second", "third"), 2),
171+
values_monthly = c(100, 200, 300, 400, 500, 600),
172+
month = factor(rep(c("April", "May"), each = 3))
173+
)
174+
pie_info <- aggregate(values_monthly ~ Group, data = bar_info, sum)
175+
names(pie_info)[2] <- "values_total"
176+
177+
colors <- c("red", "blue", "yellow")
178+
179+
bar_chart <- plot_ly(
180+
bar_info,
181+
type = "bar",
182+
x = ~month,
183+
y = ~values_monthly,
184+
color = ~Group,
185+
colors = colors
186+
)
187+
188+
pie_chart <- plot_ly(
189+
pie_info,
190+
type = "pie",
191+
labels = ~Group,
192+
values = ~values_total,
193+
marker = list(colors = colors),
194+
domain = list(x = c(0.9, 1), y = c(0, 1)),
195+
showlegend = FALSE
196+
)
197+
198+
# Specifically check that no warning about NA attributes is thrown
199+
warnings_caught <- character(0)
200+
withCallingHandlers({
201+
combined_chart <- subplot(bar_chart, pie_chart, nrows = 1, widths = c(0.9, 0.1))
202+
}, warning = function(w) {
203+
warnings_caught <<- c(warnings_caught, conditionMessage(w))
204+
invokeRestart("muffleWarning")
205+
})
206+
207+
# Should not have warning about 'NA' attribute
208+
expect_false(any(grepl("NA", warnings_caught)))
209+
})

0 commit comments

Comments
 (0)