Skip to content

Commit

Permalink
Merge pull request #432 from natverse/feature/plotly_grids_labels
Browse files Browse the repository at this point in the history
Updated parameter for toggling grid lines in plotly
  • Loading branch information
jefferis committed Aug 18, 2020
2 parents 5c346d8 + c98c69f commit 7f1599c
Show file tree
Hide file tree
Showing 15 changed files with 119 additions and 25 deletions.
13 changes: 10 additions & 3 deletions R/cmtkreg.R
Original file line number Diff line number Diff line change
Expand Up @@ -144,7 +144,7 @@ cmtkreg.filetype <- function(x) {
#' }
#' @importFrom rgl plot3d
#' @export
plot3d.cmtkreg <- function(x, ..., plotengine = getOption('nat.plotengine')) {
plot3d.cmtkreg <- function(x, ..., gridlines = FALSE, plotengine = getOption('nat.plotengine')) {
plotengine <- check_plotengine(plotengine)
if (plotengine == 'plotly') {
psh <- openplotlyscene()$plotlyscenehandle
Expand Down Expand Up @@ -172,8 +172,15 @@ plot3d.cmtkreg <- function(x, ..., plotengine = getOption('nat.plotengine')) {
psh <- psh %>%
plotly::add_trace(data = plotdata, x = ~X, y = ~Y , z = ~Z,
hoverinfo = "none",type = 'scatter3d', mode = 'markers',
opacity = opacity, marker=list(color = 'black', size = 3)) %>%
plotly::layout(showlegend = FALSE, scene=list(camera=.plotly3d$camera))
opacity = opacity, marker=list(color = 'black', size = 3))

psh <- psh %>% plotly::layout(showlegend = FALSE, scene=list(camera=.plotly3d$camera))
if(gridlines == FALSE){
psh <- psh %>% plotly::layout(scene = list(xaxis=.plotly3d$xaxis,
yaxis=.plotly3d$yaxis,
zaxis=.plotly3d$zaxis))
}

assign("plotlyscenehandle", psh, envir=.plotly3d)
psh
}
Expand Down
13 changes: 10 additions & 3 deletions R/dotprops.R
Original file line number Diff line number Diff line change
Expand Up @@ -324,7 +324,8 @@ all.equal.dotprops<-function(target, current, check.attributes=FALSE,
#' }
plot3d.dotprops<-function(x, scalevecs=1.0, alpharange=NULL, color='black',
PlotPoints=FALSE, PlotVectors=TRUE, UseAlpha=FALSE,
..., plotengine = getOption('nat.plotengine')){
..., gridlines = FALSE,
plotengine = getOption('nat.plotengine')){
# rgl's generic plot3d will dispatch on this
if (!is.null(alpharange))
x=subset(x,x$alpha<=alpharange[2] & x$alpha>=alpharange[1])
Expand Down Expand Up @@ -379,8 +380,14 @@ plot3d.dotprops<-function(x, scalevecs=1.0, alpharange=NULL, color='black',
if (plotengine == 'rgl'){
invisible(rlist)
} else {
psh <- psh %>%
plotly::layout(showlegend = FALSE, scene=list(camera=.plotly3d$camera))

psh <- psh %>% plotly::layout(showlegend = FALSE, scene=list(camera=.plotly3d$camera))
if(gridlines == FALSE){
psh <- psh %>% plotly::layout(scene = list(xaxis=.plotly3d$xaxis,
yaxis=.plotly3d$yaxis,
zaxis=.plotly3d$zaxis))
}

assign("plotlyscenehandle", psh, envir=.plotly3d)
psh
}
Expand Down
11 changes: 7 additions & 4 deletions R/hxsurf.R
Original file line number Diff line number Diff line change
Expand Up @@ -376,7 +376,7 @@ write.hxsurf <- function(surf, filename) {
#' plot3d(MBL.surf, alpha=0.3,
#' materials=grep("VL", MBL.surf$RegionList, value = TRUE, invert = TRUE))
#' }
plot3d.hxsurf<-function(x, materials=NULL, col=NULL, ...,
plot3d.hxsurf<-function(x, materials=NULL, col=NULL, gridlines = FALSE, ...,
plotengine = getOption('nat.plotengine')){
plotengine <- check_plotengine(plotengine)
if (plotengine == 'rgl'){
Expand Down Expand Up @@ -427,9 +427,12 @@ plot3d.hxsurf<-function(x, materials=NULL, col=NULL, ...,
if (plotengine == 'rgl'){
invisible(rlist)
} else {
psh <- psh %>%
plotly::layout(showlegend = FALSE,
scene=list(camera=.plotly3d$camera))
psh <- psh %>% plotly::layout(showlegend = FALSE, scene=list(camera=.plotly3d$camera))
if(gridlines == FALSE){
psh <- psh %>% plotly::layout(scene = list(xaxis=.plotly3d$xaxis,
yaxis=.plotly3d$yaxis,
zaxis=.plotly3d$zaxis))
}
assign("plotlyscenehandle", psh, envir=.plotly3d)
psh
}
Expand Down
17 changes: 14 additions & 3 deletions R/neuron-plot.R
Original file line number Diff line number Diff line change
Expand Up @@ -59,6 +59,7 @@
plot3d.neuron<-function(x, WithLine=TRUE, NeuronNames=FALSE, WithNodes=TRUE,
WithAllPoints=FALSE, WithText=FALSE, PlotSubTrees=TRUE,
add=TRUE, col=NULL, soma=FALSE, ...,
gridlines = FALSE,
plotengine = getOption('nat.plotengine')){
plotengine <- check_plotengine(plotengine)
if (!add)
Expand Down Expand Up @@ -212,8 +213,13 @@ plot3d.neuron<-function(x, WithLine=TRUE, NeuronNames=FALSE, WithNodes=TRUE,
if (plotengine == 'rgl'){
invisible(rglreturnlist)
} else{
psh <- psh %>%
plotly::layout(showlegend = FALSE, scene=list(camera=.plotly3d$camera))
psh <- psh %>% plotly::layout(showlegend = FALSE, scene=list(camera=.plotly3d$camera))
if(gridlines == FALSE){
psh <- psh %>% plotly::layout(scene = list(xaxis=.plotly3d$xaxis,
yaxis=.plotly3d$yaxis,
zaxis=.plotly3d$zaxis))
}

assign("plotlyscenehandle", psh, envir=.plotly3d)
psh
}
Expand Down Expand Up @@ -546,7 +552,7 @@ plot.neuron <- function(x, WithLine=TRUE, WithNodes=TRUE, WithAllPoints=FALSE,
#' }
#'
plot3d.boundingbox <- function(x, col='black',
plotengine = getOption('nat.plotengine'), ...) {
gridlines = FALSE, plotengine = getOption('nat.plotengine'), ...) {
plotengine <- check_plotengine(plotengine)
pts <- matrix(c(
c(x[1, 1], x[1, 2], x[1, 3]),
Expand Down Expand Up @@ -580,6 +586,11 @@ plot3d.boundingbox <- function(x, col='black',
x = ~X, y = ~Y , z = ~Z,
hoverinfo = "none", type = 'scatter3d', mode = 'lines',
opacity = opacity, line=list(color = col, width = width))
if(gridlines == FALSE){
psh <- psh %>% plotly::layout(scene = list(xaxis=.plotly3d$xaxis,
yaxis=.plotly3d$yaxis,
zaxis=.plotly3d$zaxis))
}
.plotly3d$plotlyscenehandle <- psh
psh
}
Expand Down
14 changes: 11 additions & 3 deletions R/neuronlist.R
Original file line number Diff line number Diff line change
Expand Up @@ -607,6 +607,8 @@ nmapply<-function(FUN, X, ..., MoreArgs = NULL, SIMPLIFY = FALSE,
#' @param WithNodes Whether to plot points for end/branch points. Default:
#' \code{FALSE}.
#' @param ... options passed on to plot3d (such as colours, line width etc)
#' @param gridlines Whether to display gridlines when using plotly as the backend plotting
#' engine (default: \code{FALSE})
#' @param SUBSTITUTE Whether to \code{substitute} the expressions passed as
#' arguments \code{subset} and \code{col}. Default: \code{TRUE}. For expert
#' use only, when calling from another function.
Expand Down Expand Up @@ -658,6 +660,7 @@ plot3d.neuronlist<-function(x, subset=NULL, col=NULL, colpal=rainbow,
skipRedraw=ifelse(interactive(), 200L, TRUE),
WithNodes=FALSE, soma=FALSE, ...,
SUBSTITUTE=TRUE,
gridlines = FALSE,
plotengine = getOption('nat.plotengine')){
plotengine <- check_plotengine(plotengine)
# Handle Subset
Expand Down Expand Up @@ -691,7 +694,7 @@ plot3d.neuronlist<-function(x, subset=NULL, col=NULL, colpal=rainbow,
}
}

rval=mapply(plot3d, x, plotengine = plotengine,
rval=mapply(plot3d, x, plotengine = plotengine, gridlines = gridlines,
col=cols, soma=soma, ...,
MoreArgs = list(WithNodes=WithNodes), SIMPLIFY=FALSE)
if(plotengine == 'plotly'){
Expand Down Expand Up @@ -735,8 +738,13 @@ plot3d.neuronlist<-function(x, subset=NULL, col=NULL, colpal=rainbow,
attr(rval,'df')=df
invisible(rval)
} else{
psh <- psh %>%
plotly::layout(showlegend = FALSE, scene = list(camera =.plotly3d$camera))
psh <- psh %>% plotly::layout(showlegend = FALSE, scene=list(camera=.plotly3d$camera))
if(gridlines == FALSE){
psh <- psh %>% plotly::layout(scene = list(xaxis=.plotly3d$xaxis,
yaxis=.plotly3d$yaxis,
zaxis=.plotly3d$zaxis))
}

.plotly3d$plotlyscenehandle = psh
attr(psh, 'df') = df
psh
Expand Down
19 changes: 15 additions & 4 deletions R/wire3d.R
Original file line number Diff line number Diff line change
Expand Up @@ -5,6 +5,8 @@
#' @param add whether to add objects to an existing plot
#' @param plotengine Whether to use plotting backend of 'rgl' or 'plotly'
#' @param ... Additional arguments passed to \code{\link[rgl]{wire3d}} or
#' @param gridlines Whether to display gridlines when using plotly as the backend plotting
#' engine (default: \code{FALSE})
#' \code{\link[plotly]{add_trace} depending on the @param plotengine option choosen}
#' @export
#' @seealso \code{\link[rgl]{wire3d}}
Expand All @@ -25,7 +27,7 @@
#' options(nat.plotengine = 'rgl')
#' wire3d(kcs20.mesh,alpha = 0.1, add = FALSE, col = 'blue')
#' }
wire3d <- function(x, ..., add = TRUE, plotengine = getOption('nat.plotengine')) {
wire3d <- function(x, ..., add = TRUE, gridlines = FALSE, plotengine = getOption('nat.plotengine')) {
plotengine <- check_plotengine(plotengine)
if (!add)
nclear3d(plotengine = plotengine)
Expand Down Expand Up @@ -54,15 +56,15 @@ wire3d.default <- function(x, ...) {


#' @export
wire3d.plotlyshapelist3d <- function (x, override = TRUE, ...)
wire3d.plotlyshapelist3d <- function (x, override = TRUE, gridlines = FALSE, ...)
{
sapply(x, function(item) wire3d(item, override = override, ...))
sapply(x, function(item) wire3d(item, override = override, gridlines = gridlines, ...))
psh <- openplotlyscene()$plotlyscenehandle
psh
}

#' @export
wire3d.plotlymesh3d <- function(x, override = TRUE, ...) {
wire3d.plotlymesh3d <- function(x, override = TRUE, gridlines = FALSE, ...) {

psh <- openplotlyscene()$plotlyscenehandle
params=list(...)
Expand All @@ -77,6 +79,8 @@ wire3d.plotlymesh3d <- function(x, override = TRUE, ...) {
} else 'black'
width <- if("width" %in% names(params)) params$width else 2

label <- if("label" %in% names(params)) params$label else NULL

#Gather all edges for the faces..
#Here vb is the points of the mesh, it is the faces of the mesh (this just has the order)..
#To get the edges, just put the put the orders(faces) and collect the points represented by them..
Expand Down Expand Up @@ -117,9 +121,16 @@ wire3d.plotlymesh3d <- function(x, override = TRUE, ...) {
z = ptsna[,3],
mode = "lines",
opacity = opacity,
name = label,
line = list(width = width, color = color))

psh <- psh %>% plotly::layout(showlegend = FALSE, scene=list(camera=.plotly3d$camera))
if(gridlines == FALSE){
psh <- psh %>% plotly::layout(scene = list(xaxis=.plotly3d$xaxis,
yaxis=.plotly3d$yaxis,
zaxis=.plotly3d$zaxis))
}

assign("plotlyscenehandle", psh, envir=.plotly3d)
psh
}
Expand Down
7 changes: 7 additions & 0 deletions R/zzz.R
Original file line number Diff line number Diff line change
Expand Up @@ -93,3 +93,10 @@ update_igraph <- FALSE
.plotly3d$camera = list(up=list(x=0, y=0, z=1),
center=list(x=0, y=0, z=0),
eye=list(x=-0.1, y=-2.5, z=0.1))

.plotly3d$xaxis = list(title = "", zeroline = FALSE,
showline = FALSE, showticklabels = FALSE,showgrid = FALSE)
.plotly3d$yaxis = list(title = "", zeroline = FALSE,
showline = FALSE, showticklabels = FALSE,showgrid = FALSE)
.plotly3d$zaxis = list(title = "", zeroline = FALSE, ticks = "",
showline = FALSE, showticklabels = FALSE,showgrid = FALSE)
3 changes: 3 additions & 0 deletions inst/WORDLIST
Original file line number Diff line number Diff line change
Expand Up @@ -50,6 +50,7 @@ dfc
dfs
dir
dirname
DL
dof
doi
donttest
Expand All @@ -64,6 +65,7 @@ dZ
edgelist
eg
eigen
elmr
Endianness
EndPoints
enh
Expand All @@ -72,6 +74,7 @@ especiall
etc
Evers
exe
FAFB
FCWB
fftw
fijitraces
Expand Down
11 changes: 10 additions & 1 deletion man/plot3d.boundingbox.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

5 changes: 4 additions & 1 deletion man/plot3d.cmtkreg.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

4 changes: 4 additions & 0 deletions man/plot3d.dotprops.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

4 changes: 4 additions & 0 deletions man/plot3d.hxsurf.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

4 changes: 4 additions & 0 deletions man/plot3d.neuron.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

4 changes: 4 additions & 0 deletions man/plot3d.neuronlist.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

Loading

0 comments on commit 7f1599c

Please sign in to comment.