@@ -165,7 +165,17 @@ geom2trace <-
165
165
L $ marker $ size <- data $ size
166
166
}
167
167
L
168
- })
168
+ },
169
+ bar = function (data , params ) {
170
+ list (x = data $ x ,
171
+ y = data $ y ,
172
+ name = params $ name ,
173
+ text = data $ text ,
174
+ type = " bar" ,
175
+ fillcolor = toRGB(params $ fill ))
176
+ }
177
+ )
178
+
169
179
170
180
# ' Convert ggplot2 aes to line parameters.
171
181
aes2line <- c(linetype = " dash" ,
@@ -175,7 +185,8 @@ aes2line <- c(linetype="dash",
175
185
markLegends <-
176
186
list (point = c(" colour" , " fill" , " shape" ),
177
187
path = c(" linetype" , " size" , " colour" ),
178
- polygon = c(" colour" , " fill" , " linetype" , " size" , " group" ))
188
+ polygon = c(" colour" , " fill" , " linetype" , " size" , " group" ),
189
+ bar = c(" fill" ))
179
190
180
191
markUnique <- as.character(unique(unlist(markLegends )))
181
192
@@ -199,7 +210,9 @@ gg2list <- function(p){
199
210
layout <- list ()
200
211
trace.list <- list ()
201
212
# # Before building the ggplot, we would like to add aes(name) to
202
- # # figure out what the object group is later.
213
+ # # figure out what the object group is later. This also copies any
214
+ # # needed global aes/data values to each layer, so we do not have to
215
+ # # worry about combining global and layer-specific aes/data later.
203
216
for (layer.i in seq_along(p $ layers )){
204
217
layer.aes <- p $ layers [[layer.i ]]$ mapping
205
218
to.copy <- names(p $ mapping )[! names(p $ mapping ) %in% names(layer.aes )]
@@ -208,36 +221,59 @@ gg2list <- function(p){
208
221
name.names <- sprintf(" %s.name" , mark.names )
209
222
layer.aes [name.names ] <- layer.aes [mark.names ]
210
223
p $ layers [[layer.i ]]$ mapping <- layer.aes
224
+ if (! is.data.frame(p $ layers [[layer.i ]]$ data )){
225
+ p $ layers [[layer.i ]]$ data <- p $ data
226
+ }
227
+ geom_type <- p $ layers [[layer.i ]]$ geom
228
+ geom_type <- strsplit(capture.output(geom_type ), " geom_" )[[1 ]][2 ]
229
+ geom_type <- strsplit(geom_type , " : " )[[1 ]]
230
+ # # Barmode.
231
+ layout $ barmode <- " group"
232
+ if (geom_type == " bar" ) {
233
+ pos <- capture.output(p $ layers [[layer.i ]]$ position )
234
+ if (length(grep(" identity" , pos )) > 0 ) {
235
+ layout $ barmode <- " overlay"
236
+ } else if (length(grep(" stack" , pos )) > 0 ) {
237
+ layout $ barmode <- " stack"
238
+ }
239
+ }
211
240
}
212
241
# # Extract data from built ggplots
213
242
built <- ggplot2 :: ggplot_build(p )
214
243
ranges <- built $ panel $ ranges [[1 ]]
215
244
for (i in seq_along(built $ plot $ layers )){
216
245
# # This is the layer from the original ggplot object.
217
246
L <- p $ layers [[i ]]
218
-
247
+
219
248
# # for each layer, there is a correpsonding data.frame which
220
249
# # evaluates the aesthetic mapping.
221
250
df <- built $ data [[i ]]
222
-
251
+
223
252
# # Test fill and color to see if they encode a quantitative
224
- # # variable. In that case, we do not make traces for separate
225
- # # colors, since there are too many!
253
+ # # variable. This may be useful for several reasons: (1) it is
254
+ # # sometimes possible to plot several different colors in the same
255
+ # # trace (e.g. points), and that is faster for large numbers of
256
+ # # data points and colors; (2) factors on x or y axes should be
257
+ # # sent to plotly as characters, not as numeric data (which is
258
+ # # what ggplot_build gives us).
226
259
misc <- list ()
227
- for (a in c(" fill" , " colour" )){
228
- fun.name <- sprintf(" scale_%s_continuous" , a )
229
- fun <- get(fun.name )
230
- misc $ is.continuous [[a ]] <- tryCatch({
231
- suppressMessages({
232
- with.scale <- p + fun()
260
+ for (a in c(" fill" , " colour" , " x" , " y" )){
261
+ for (data.type in c(" continuous" , " date" , " datetime" , " discrete" )){
262
+ fun.name <- sprintf(" scale_%s_%s" , a , data.type )
263
+ misc.name <- paste0(" is." , data.type )
264
+ misc [[misc.name ]][[a ]] <- tryCatch({
265
+ fun <- get(fun.name )
266
+ suppressMessages({
267
+ with.scale <- p + fun()
268
+ })
269
+ ggplot2 :: ggplot_build(with.scale )
270
+ TRUE
271
+ }, error = function (e ){
272
+ FALSE
233
273
})
234
- ggplot2 :: ggplot_build(with.scale )
235
- TRUE
236
- }, error = function (e ){
237
- FALSE
238
- })
274
+ }
239
275
}
240
-
276
+
241
277
# # scales are needed for legend ordering.
242
278
for (sc in p $ scales $ scales ){
243
279
a <- sc $ aesthetics
@@ -248,10 +284,10 @@ gg2list <- function(p){
248
284
misc $ breaks [[sc $ aesthetics ]] <- ranks
249
285
}
250
286
}
251
-
287
+
252
288
# # This extracts essential info for this geom/layer.
253
289
traces <- layer2traces(L , df , misc )
254
-
290
+
255
291
# # Do we really need to coord_transform?
256
292
# #g$data <- ggplot2:::coord_transform(built$plot$coord, g$data,
257
293
# # built$panel$ranges[[1]])
@@ -263,7 +299,7 @@ gg2list <- function(p){
263
299
# grid 0-1 scale). This allows transformations to be used
264
300
# out of the box, with no additional d3 coding.
265
301
theme.pars <- ggplot2 ::: plot_theme(p )
266
-
302
+
267
303
# # Flip labels if coords are flipped - transform does not take care
268
304
# # of this. Do this BEFORE checking if it is blank or not, so that
269
305
# # individual axes can be hidden appropriately, e.g. #1.
@@ -318,7 +354,15 @@ gg2list <- function(p){
318
354
ax.list $ tickfont <- theme2font(tick.text )
319
355
title.text <- e(s(" axis.title.%s" ))
320
356
ax.list $ titlefont <- theme2font(title.text )
321
- ax.list $ type <- " linear" # # TODO: log scales?
357
+ ax.list $ type <- if (misc $ is.continuous [[xy ]]){
358
+ " linear"
359
+ }else if (misc $ is.discrete [[xy ]]){
360
+ " category"
361
+ }else if (misc $ is.date [[xy ]] || misc $ is.datetime [[xy ]]){
362
+ " date"
363
+ }else {
364
+ stop(" unrecognized data type for " , xy , " axis" )
365
+ }
322
366
# # Lines drawn around the plot border:
323
367
ax.list $ showline <- ifelse(is.blank(" panel.border" ), FALSE , TRUE )
324
368
ax.list $ linecolor <- toRGB(theme.pars $ panel.border $ colour )
@@ -329,21 +373,21 @@ gg2list <- function(p){
329
373
! is.blank(s(" axis.ticks.%s" ))
330
374
layout [[s(" %saxis" )]] <- ax.list
331
375
}
332
-
376
+
333
377
# # Remove legend if theme has no legend position
334
378
if (theme.pars $ legend.position == " none" ) layout $ showlegend <- FALSE
335
-
379
+
336
380
# # Main plot title.
337
381
layout $ title <- built $ plot $ labels $ title
338
-
382
+
339
383
# # Background color.
340
384
layout $ plot_bgcolor <- toRGB(theme.pars $ panel.background $ fill )
341
385
layout $ paper_bgcolor <- toRGB(theme.pars $ plot.background $ fill )
342
-
386
+
343
387
# # Legend.
344
388
layout $ margin $ r <- 10
345
389
layout $ legend <- list (bordercolor = " transparent" , x = 100 , y = 1 / 2 )
346
-
390
+
347
391
trace.list $ kwargs <- list (layout = layout )
348
392
trace.list
349
393
}
@@ -360,6 +404,22 @@ layer2traces <- function(l, d, misc){
360
404
# # needed for when group, etc. is an expression.
361
405
g $ aes <- sapply(l $ mapping , function (k ) as.character(as.expression(k )))
362
406
407
+ # # For non-numeric data on the axes, we should take the values from
408
+ # # the original data.
409
+ for (axis.name in c(" x" , " y" )){
410
+ if (! misc $ is.continuous [[axis.name ]]){
411
+ aes.names <- paste0(axis.name , c(" " , " end" , " min" , " max" ))
412
+ aes.used <- aes.names [aes.names %in% names(g $ aes )]
413
+ for (a in aes.used ){
414
+ col.name <- g $ aes [aes.used ]
415
+ data.vec <- l $ data [[col.name ]]
416
+ if (inherits(data.vec , " POSIXt" )){
417
+ data.vec <- strftime(data.vec , " %Y-%m-%d %H:%M:%S" )
418
+ }
419
+ g $ data [[a ]] <- data.vec
420
+ }
421
+ }
422
+ }
363
423
# # use un-named parameters so that they will not be exported
364
424
# # to JSON as a named object, since that causes problems with
365
425
# # e.g. colour.
@@ -373,41 +433,41 @@ layer2traces <- function(l, d, misc){
373
433
# # {"bar":"foo"}
374
434
names(g $ params [[p.name ]]) <- NULL
375
435
}
376
-
436
+
377
437
# # Convert complex ggplot2 geoms so that they are treated as special
378
438
# # cases of basic geoms. In ggplot2, this processing is done in the
379
439
# # draw method of the geoms.
380
-
440
+
381
441
# # Every plotly trace has one of these types
382
442
# # type=scatter,bar,box,histogramx,histogram2d,heatmap
383
-
443
+
384
444
# # for type=scatter, you can define
385
445
# # mode=none,markers,lines,lines+markers where "lines" is the
386
446
# # default for 20 or more points, "lines+markers" is the default for
387
447
# # <20 points. "none" is useful mainly if fill is used to make area
388
448
# # plots with no lines.
389
-
449
+
390
450
# # marker=list(size,line,color="rgb(54,144,192)",opacity,symbol)
391
-
451
+
392
452
# # symbol=circle,square,diamond,cross,x,
393
453
# # triangle-up,triangle-down,triangle-left,triangle-right
394
-
454
+
395
455
# # First convert to a "basic" geom, e.g. segments become lines.
396
456
convert <- toBasic [[g $ geom ]]
397
457
basic <- if (is.null(convert )){
398
458
g
399
459
}else {
400
460
convert(g )
401
461
}
402
-
462
+
403
463
# # Then split on visual characteristics that will get different
404
464
# # legend entries.
405
465
data.list <- if (basic $ geom %in% names(markLegends )){
406
466
mark.names <- markLegends [[basic $ geom ]]
407
467
# # However, continuously colored points are an exception: they do
408
468
# # not need a legend entry, and they can be efficiently rendered
409
469
# # using just 1 trace.
410
-
470
+
411
471
# # Maybe it is nice to show a legend for continuous points?
412
472
# # if(basic$geom == "point"){
413
473
# # to.erase <- names(misc$is.continuous)[misc$is.continuous]
@@ -436,7 +496,7 @@ layer2traces <- function(l, d, misc){
436
496
data.list <- structure(list (list (data = basic $ data , params = basic $ params )),
437
497
names = basic $ params $ name )
438
498
}
439
-
499
+
440
500
getTrace <- geom2trace [[basic $ geom ]]
441
501
if (is.null(getTrace )){
442
502
stop(" conversion not implemented for geom_" ,
@@ -446,6 +506,12 @@ layer2traces <- function(l, d, misc){
446
506
for (data.i in seq_along(data.list )){
447
507
data.params <- data.list [[data.i ]]
448
508
tr <- do.call(getTrace , data.params )
509
+ for (v.name in c(" x" , " y" )){
510
+ vals <- tr [[v.name ]]
511
+ if (is.na(vals [length(vals )])){
512
+ tr [[v.name ]] <- vals [- length(vals )]
513
+ }
514
+ }
449
515
name.names <- grep(" [.]name$" , names(data.params $ params ), value = TRUE )
450
516
if (length(name.names )){
451
517
for (a.name in name.names ){
@@ -521,3 +587,7 @@ toRGB <- function(x){
521
587
ifelse(is.na(x ), " none" , rgb.css )
522
588
}
523
589
590
+ # ' Convert R position to plotly barmode
591
+ position2barmode <- c(" stack" = " stack" ,
592
+ " dodge" = " group" ,
593
+ " identity" = " overlay" )
0 commit comments