Skip to content
Merged
7 changes: 7 additions & 0 deletions NEWS.md
Original file line number Diff line number Diff line change
Expand Up @@ -26,6 +26,13 @@ See the [plotly.js releases page](https://github.com/plotly/plotly.js/releases)
## Bug fixes

* `plotly_build()` now works with `ggmatrix` objects (e.g., from `GGally::ggpairs()`). (#2447)
* Closed #2415: `ggplotly()` now shows variables named 'group' in tooltips when mapped to aesthetics like `colour`.
* Closed #2455, #2460: `ggplotly()` no longer creates empty shapes when `panel.border` is `element_blank()` (ggplot2 4.0.0 compatibility).
* Closed #2466: `ggplotly()` no longer errors when `scale_*_manual()` has unused aesthetics (e.g., `aesthetics = c("colour", "fill")` when only colour is used).
* Closed #2305: `ggplotly()` now respects `geom_boxplot(outlier.shape = NA)` to hide outlier points.
* Closed #2467: `ggplotly()` now correctly shows legends and splits traces when scales have multiple aesthetics.
* Closed #2407, #2187: `ggplotly()` now translates `legend.position` theme element to plotly layout (supports "bottom", "top", "left", and numeric positions).
* Closed #2281: `ggplotly()` no longer drops legends when `geom_blank()` is present in the plot.

# plotly 4.11.0

Expand Down
56 changes: 48 additions & 8 deletions R/ggplotly.R
Original file line number Diff line number Diff line change
Expand Up @@ -411,9 +411,9 @@ gg2list <- function(p, width = NULL, height = NULL,
# of each non-positional scale for display in tooltips
for (sc in npscales$scales) {
data <- lapply(data, function(d) {
# scale may not be relevant for every layer data
if (any(names(d) %in% sc$aesthetics)) {
d[paste0(sc$aesthetics, "_plotlyDomain")] <- d[sc$aesthetics]
present_aes <- intersect(sc$aesthetics, names(d))
if (length(present_aes) > 0) {
d[paste0(present_aes, "_plotlyDomain")] <- d[present_aes]
}
d
})
Expand Down Expand Up @@ -572,13 +572,15 @@ gg2list <- function(p, width = NULL, height = NULL,
tr$hoverinfo <- tr$hoverinfo %||%"text"
tr
})
# show only one legend entry per legendgroup
# show only one legend entry per legendgroup (skip invisible traces for dedup)
grps <- sapply(traces, "[[", "legendgroup")
is_visible <- sapply(traces, function(tr) !isFALSE(tr$visible))
grps_for_dedup <- ifelse(is_visible, grps, paste0(grps, "_invisible_", seq_along(grps)))
traces <- Map(function(x, y) {
if (!is.null(x[["frame"]])) return(x)
x$showlegend <- isTRUE(x$showlegend) && y
x
}, traces, !duplicated(grps))
}, traces, !duplicated(grps_for_dedup))

# ------------------------------------------------------------------------
# axis/facet/margin conversion
Expand Down Expand Up @@ -978,12 +980,45 @@ gg2list <- function(p, width = NULL, height = NULL,
bgcolor = toRGB(theme$legend.background$fill),
bordercolor = toRGB(theme$legend.background$colour),
borderwidth = unitConvert(
theme$legend.background[[linewidth_or_size(theme$legend.background)]],
theme$legend.background[[linewidth_or_size(theme$legend.background)]],
"pixels", "width"
),
font = text2font(theme$legend.text)
)


# Translate legend.position to plotly layout
legend_pos <- theme$legend.position %||% theme[["legend.position"]]
if (!is.null(legend_pos) && !identical(legend_pos, "none")) {
if (is.character(legend_pos)) {
gglayout$legend <- switch(legend_pos,
"bottom" = modifyList(gglayout$legend, list(
orientation = "h", x = 0.5, y = -0.15, xanchor = "center", yanchor = "top"
)),
"top" = modifyList(gglayout$legend, list(
orientation = "h", x = 0.5, y = 1.02, xanchor = "center", yanchor = "bottom"
)),
"left" = modifyList(gglayout$legend, list(
x = -0.15, y = 0.5, xanchor = "right", yanchor = "middle"
)),
"inside" = {
inside_pos <- theme$legend.position.inside %||% theme[["legend.position.inside"]]
if (is.numeric(inside_pos) && length(inside_pos) == 2) {
modifyList(gglayout$legend, list(
x = inside_pos[1], y = inside_pos[2], xanchor = "left", yanchor = "bottom"
))
} else {
gglayout$legend
}
},
gglayout$legend
)
} else if (is.numeric(legend_pos) && length(legend_pos) == 2) {
gglayout$legend <- modifyList(gglayout$legend, list(
x = legend_pos[1], y = legend_pos[2], xanchor = "left", yanchor = "bottom"
))
}
}

# if theme(legend.position = "none") is used, don't show a legend _or_ guide
if (npscales$n() == 0 || identical(theme$legend.position, "none")) {
gglayout$showlegend <- FALSE
Expand Down Expand Up @@ -1389,7 +1424,12 @@ make_strip_rect <- function(xdom, ydom, theme, side = "top") {

# theme(panel.border) -> plotly.js rect shape
make_panel_border <- function(xdom, ydom, theme) {
rekt <- rect2shape(theme[["panel.border"]])
# Use calc_element to get fully resolved element with inherited values
border <- ggplot2::calc_element("panel.border", theme)
if (is.null(border) || is_blank(border)) {
return(list())
}
rekt <- rect2shape(border)
rekt$x0 <- xdom[1]
rekt$x1 <- xdom[2]
rekt$y0 <- ydom[1]
Expand Down
21 changes: 13 additions & 8 deletions R/layers2traces.R
Original file line number Diff line number Diff line change
Expand Up @@ -56,8 +56,8 @@ layers2traces <- function(data, prestats_data, layout, p) {
if (!aesName %in% names(x)) next
# TODO: should we be getting the name from scale_*(name) first?
varName <- y[[i]]
# "automatically" generated group aes is not informative
if (identical("group", unique(varName, aesName))) next
# Skip auto-generated group aesthetic, but keep explicit group mappings
if (identical(aesName, "group") && identical(varName, "group")) next
# add a line break if hovertext already exists
if ("hovertext" %in% names(x)) x$hovertext <- paste0(x$hovertext, br())
# text aestheic should be taken verbatim (for custom tooltips)
Expand All @@ -75,12 +75,13 @@ layers2traces <- function(data, prestats_data, layout, p) {
x
}, data, hoverTextAes)

# draw legends only for discrete scales
# draw legends only for discrete scales (skip scales with guide = "none")
discreteScales <- list()
for (sc in p$scales$non_position_scales()$scales) {
if (sc$is_discrete()) {
nm <- paste(sc$aesthetics, collapse = "_")
discreteScales[[nm]] <- sc
if (sc$is_discrete() && !identical(sc$guide, "none")) {
for (aes_name in sc$aesthetics) {
discreteScales[[aes_name]] <- sc
}
}
}
# Convert "high-level" geoms to their "low-level" counterpart
Expand Down Expand Up @@ -706,7 +707,7 @@ geom2trace <- function(data, params, p) {

#' @export
geom2trace.GeomBlank <- function(data, params, p) {
list(visible = FALSE)
list(visible = FALSE, showlegend = FALSE)
}

#' @export
Expand Down Expand Up @@ -870,6 +871,8 @@ geom2trace.GeomBoxplot <- function(data, params, p) {
# marker styling must inherit from GeomPoint$default_aes
# https://github.com/hadley/ggplot2/blob/ab42c2ca81458b0cf78e3ba47ed5db21f4d0fc30/NEWS#L73-L7
point_defaults <- GeomPoint$use_defaults(NULL)
hide_outliers <- isFALSE(params$outliers) || isTRUE(is.na(params$outlier_gp$shape))

compact(list(
x = data[["x"]],
y = data[["y"]],
Expand All @@ -883,6 +886,7 @@ geom2trace.GeomBoxplot <- function(data, params, p) {
aes2plotly(data, params, "fill"),
aes2plotly(data, params, "alpha")
),
boxpoints = if (hide_outliers) FALSE,
# markers/points
marker = list(
opacity = point_defaults$alpha,
Expand Down Expand Up @@ -1157,7 +1161,8 @@ linewidth_or_size.Geom <- function(x) {

#' @export
linewidth_or_size.element <- function(x) {
if ("linewidth" %in% names(x)) "linewidth" else "size"
# S7 objects (ggplot2 >= 4.0) don't have traditional names(), check for slot
if (!is.null(x$linewidth) || "linewidth" %in% names(x)) "linewidth" else "size"
}

#' @export
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -239,7 +239,7 @@
"ticks": "outside",
"tickcolor": "rgba(51,51,51,1)",
"ticklen": 3.6529680365296811,
"tickwidth": 0,
"tickwidth": 0.66417600664176002,
"showticklabels": true,
"tickfont": {
"color": "rgba(77,77,77,1)",
Expand All @@ -252,7 +252,7 @@
"linewidth": 0,
"showgrid": true,
"gridcolor": "rgba(255,255,255,1)",
"gridwidth": 0,
"gridwidth": 0.66417600664176002,
"zeroline": false,
"anchor": "y",
"title": {
Expand Down Expand Up @@ -301,7 +301,7 @@
"ticks": "outside",
"tickcolor": "rgba(51,51,51,1)",
"ticklen": 3.6529680365296811,
"tickwidth": 0,
"tickwidth": 0.66417600664176002,
"showticklabels": true,
"tickfont": {
"color": "rgba(77,77,77,1)",
Expand All @@ -314,7 +314,7 @@
"linewidth": 0,
"showgrid": true,
"gridcolor": "rgba(255,255,255,1)",
"gridwidth": 0,
"gridwidth": 0.66417600664176002,
"zeroline": false,
"anchor": "x",
"title": {
Expand All @@ -328,30 +328,13 @@
"hoverformat": ".2f"
},
"shapes": [
{
"type": "rect",
"fillcolor": null,
"line": {
"color": null,
"width": 0,
"linetype": [

]
},
"yref": "paper",
"xref": "paper",
"layer": "below",
"x0": 0,
"x1": 1,
"y0": 0,
"y1": 1
}
],
"showlegend": false,
"legend": {
"bgcolor": "rgba(255,255,255,1)",
"bordercolor": "transparent",
"borderwidth": 0,
"borderwidth": 1.8897637795275593,
"font": {
"color": "rgba(0,0,0,1)",
"family": "",
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -18,7 +18,7 @@
"plotly_afterplot-A": "\"plot\"",
"plotly_click-A": "[{\"curveNumber\":0,\"pointNumber\":7,\"x\":24.4,\"y\":3.19,\"customdata\":\"Merc 240D\"}]",
"plotly_hover-A": null,
"plotly_relayout-A": "{\"width\":962,\"height\":400}"
"plotly_relayout-A": "{\"width\":947,\"height\":400}"
},
"output": {
"brushed": "[1] \"Brush extents appear here (double-click to clear)\"",
Expand Down Expand Up @@ -242,7 +242,7 @@
"ticks": "outside",
"tickcolor": "rgba(51,51,51,1)",
"ticklen": 3.6529680365296811,
"tickwidth": 0,
"tickwidth": 0.66417600664176002,
"showticklabels": true,
"tickfont": {
"color": "rgba(77,77,77,1)",
Expand All @@ -255,7 +255,7 @@
"linewidth": 0,
"showgrid": true,
"gridcolor": "rgba(255,255,255,1)",
"gridwidth": 0,
"gridwidth": 0.66417600664176002,
"zeroline": false,
"anchor": "y",
"title": {
Expand Down Expand Up @@ -304,7 +304,7 @@
"ticks": "outside",
"tickcolor": "rgba(51,51,51,1)",
"ticklen": 3.6529680365296811,
"tickwidth": 0,
"tickwidth": 0.66417600664176002,
"showticklabels": true,
"tickfont": {
"color": "rgba(77,77,77,1)",
Expand All @@ -317,7 +317,7 @@
"linewidth": 0,
"showgrid": true,
"gridcolor": "rgba(255,255,255,1)",
"gridwidth": 0,
"gridwidth": 0.66417600664176002,
"zeroline": false,
"anchor": "x",
"title": {
Expand All @@ -331,30 +331,13 @@
"hoverformat": ".2f"
},
"shapes": [
{
"type": "rect",
"fillcolor": null,
"line": {
"color": null,
"width": 0,
"linetype": [

]
},
"yref": "paper",
"xref": "paper",
"layer": "below",
"x0": 0,
"x1": 1,
"y0": 0,
"y1": 1
}
],
"showlegend": false,
"legend": {
"bgcolor": "rgba(255,255,255,1)",
"bordercolor": "transparent",
"borderwidth": 0,
"borderwidth": 1.8897637795275593,
"font": {
"color": "rgba(0,0,0,1)",
"family": "",
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -20,7 +20,7 @@
"plotly_brushing-A": "{\"x\":[23.95978500551268,25.98332414553473],\"y\":[3.0020072289156627,3.5073743975903615]}",
"plotly_click-A": "[{\"curveNumber\":0,\"pointNumber\":7,\"x\":24.4,\"y\":3.19,\"customdata\":\"Merc 240D\"}]",
"plotly_hover-A": null,
"plotly_relayout-A": "{\"width\":962,\"height\":400}",
"plotly_relayout-A": "{\"width\":947,\"height\":400}",
"plotly_selected-A": "[{\"curveNumber\":0,\"pointNumber\":7,\"x\":24.4,\"y\":3.19,\"customdata\":\"Merc 240D\"}]",
"plotly_selecting-A": "[{\"curveNumber\":0,\"pointNumber\":7,\"x\":24.4,\"y\":3.19,\"customdata\":\"Merc 240D\"}]"
},
Expand Down Expand Up @@ -246,7 +246,7 @@
"ticks": "outside",
"tickcolor": "rgba(51,51,51,1)",
"ticklen": 3.6529680365296811,
"tickwidth": 0,
"tickwidth": 0.66417600664176002,
"showticklabels": true,
"tickfont": {
"color": "rgba(77,77,77,1)",
Expand All @@ -259,7 +259,7 @@
"linewidth": 0,
"showgrid": true,
"gridcolor": "rgba(255,255,255,1)",
"gridwidth": 0,
"gridwidth": 0.66417600664176002,
"zeroline": false,
"anchor": "y",
"title": {
Expand Down Expand Up @@ -308,7 +308,7 @@
"ticks": "outside",
"tickcolor": "rgba(51,51,51,1)",
"ticklen": 3.6529680365296811,
"tickwidth": 0,
"tickwidth": 0.66417600664176002,
"showticklabels": true,
"tickfont": {
"color": "rgba(77,77,77,1)",
Expand All @@ -321,7 +321,7 @@
"linewidth": 0,
"showgrid": true,
"gridcolor": "rgba(255,255,255,1)",
"gridwidth": 0,
"gridwidth": 0.66417600664176002,
"zeroline": false,
"anchor": "x",
"title": {
Expand All @@ -335,30 +335,13 @@
"hoverformat": ".2f"
},
"shapes": [
{
"type": "rect",
"fillcolor": null,
"line": {
"color": null,
"width": 0,
"linetype": [

]
},
"yref": "paper",
"xref": "paper",
"layer": "below",
"x0": 0,
"x1": 1,
"y0": 0,
"y1": 1
}
],
"showlegend": false,
"legend": {
"bgcolor": "rgba(255,255,255,1)",
"bordercolor": "transparent",
"borderwidth": 0,
"borderwidth": 1.8897637795275593,
"font": {
"color": "rgba(0,0,0,1)",
"family": "",
Expand Down
Loading