Skip to content

Commit 95112dc

Browse files
committed
plot_mapbox()/plot_geo() should not be calling add_trace() directly
1 parent ae99ee1 commit 95112dc

File tree

3 files changed

+36
-29
lines changed

3 files changed

+36
-29
lines changed

R/add.R

Lines changed: 0 additions & 14 deletions
Original file line numberDiff line numberDiff line change
@@ -82,20 +82,6 @@ add_trace <- function(p, ..., color, symbol, size, linetype,
8282
attrs <- modify_list(p$x$attrs[[1]], attrs)
8383
}
8484

85-
if (is_mapbox(p) || is_geo(p)) {
86-
attrs[["x"]] <- attrs[["x"]] %||% attrs[["lat"]]
87-
attrs[["y"]] <- attrs[["y"]] %||% attrs[["lon"]]
88-
if (!grepl("scatter|choropleth", attrs[["type"]] %||% "scatter")) {
89-
stop("Cant add a '", attrs[["type"]], "' trace to a map object", call. = FALSE)
90-
}
91-
if (is_mapbox(p)) {
92-
attrs[["type"]] <- "scattermapbox"
93-
}
94-
if (is_geo(p)) {
95-
attrs[["type"]] <- if (!is.null(attrs[["z"]])) "choropleth" else "scattergeo"
96-
}
97-
}
98-
9985
p$x$attrs <- c(
10086
p$x$attrs %||% list(),
10187
setNames(list(attrs), p$x$cur_data)

R/plotly.R

Lines changed: 7 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -166,7 +166,7 @@ plot_ly <- function(data = data.frame(), ..., type = NULL,
166166
#'
167167
#' map_data("world", "canada") %>%
168168
#' group_by(group) %>%
169-
#' plot_mapbox(x = ~lat, y = ~long) %>%
169+
#' plot_mapbox(x = ~long, y = ~lat) %>%
170170
#' add_polygons() %>%
171171
#' layout(
172172
#' mapbox = list(
@@ -176,11 +176,11 @@ plot_ly <- function(data = data.frame(), ..., type = NULL,
176176
#' }
177177
#'
178178
plot_mapbox <- function(data = data.frame(), ...) {
179-
p <- config(plot_ly(data), mapboxAccessToken = mapbox_token())
179+
p <- config(plot_ly(data, ...), mapboxAccessToken = mapbox_token())
180180
# not only do we use this for is_mapbox(), but also setting the layout attr
181181
# https://plot.ly/r/reference/#layout-mapbox
182182
p$x$layout$mapType <- "mapbox"
183-
add_trace(p, ...)
183+
p
184184
}
185185

186186
#' Initiate a plotly-geo object
@@ -198,15 +198,15 @@ plot_mapbox <- function(data = data.frame(), ...) {
198198
#'
199199
#' map_data("world", "canada") %>%
200200
#' group_by(group) %>%
201-
#' plot_geo(x = ~lat, y = ~long) %>%
202-
#' add_polygons()
201+
#' plot_geo(x = ~long, y = ~lat) %>%
202+
#' add_markers(size = I(1))
203203
#'
204204
plot_geo <- function(data = data.frame(), ...) {
205-
p <- plot_ly(data)
205+
p <- plot_ly(data, ...)
206206
# not only do we use this for is_geo(), but also setting the layout attr
207207
# https://plot.ly/r/reference/#layout-geo
208208
p$x$layout$mapType <- "geo"
209-
add_trace(p, ...)
209+
p
210210
}
211211

212212

R/plotly_build.R

Lines changed: 29 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -26,7 +26,8 @@ plotly_build.list <- function(p) {
2626

2727
#' @export
2828
plotly_build.gg <- function(p) {
29-
ggplotly(p)
29+
p <- ggplotly(p)
30+
supply_defaults(p)
3031
}
3132

3233
#' @export
@@ -71,6 +72,24 @@ plotly_build.plotly <- function(p) {
7172
p$x$attrs[[1]] <- NULL
7273
}
7374
}
75+
76+
# trace type checking and renaming for plot objects
77+
if (is_mapbox(p) || is_geo(p)) {
78+
p$x$attrs <- lapply(p$x$attrs, function(tr) {
79+
tr[["x"]] <- tr[["x"]] %||% tr[["lat"]]
80+
tr[["y"]] <- tr[["y"]] %||% tr[["lon"]]
81+
if (!grepl("scatter|choropleth", tr[["type"]] %||% "scatter")) {
82+
stop("Cant add a '", tr[["type"]], "' trace to a map object", call. = FALSE)
83+
}
84+
if (is_mapbox(p)) {
85+
tr[["type"]] <- "scattermapbox"
86+
}
87+
if (is_geo(p)) {
88+
tr[["type"]] <- if (!is.null(tr[["z"]])) "choropleth" else "scattergeo"
89+
}
90+
tr
91+
})
92+
}
7493

7594
dats <- Map(function(x, y) {
7695

@@ -270,16 +289,18 @@ plotly_build.plotly <- function(p) {
270289
}
271290
}
272291

273-
# attribute naming correction for "geo-like" traces
274-
if (is_geo(p) || is_mapbox(p)) {
275-
p$x$layout[grepl("^[x-y]axis", names(p$x$layout))] <- NULL
276-
p$x$data <- lapply(p$x$data, function(tr) {
292+
# supply trace anchor and domain information
293+
p <- supply_defaults(p)
294+
295+
# attribute naming corrections for "geo-like" traces
296+
p$x$data <- lapply(p$x$data, function(tr) {
297+
if (isTRUE(tr[["type"]] %in% c("scattermapbox", "scattergeo"))) {
277298
tr[["lat"]] <- tr[["lat"]] %||% tr[["y"]]
278299
tr[["lon"]] <- tr[["lon"]] %||% tr[["x"]]
279300
tr[c("x", "y")] <- NULL
280-
tr
281-
})
282-
}
301+
}
302+
tr
303+
})
283304

284305
# polar charts don't like null width/height keys
285306
if (is.null(p$x$layout[["height"]])) p$x$layout[["height"]] <- NULL

0 commit comments

Comments
 (0)