[Rd] How to avoid using gridextra via Depends instead of Imports in a package ?
Karl Forner
karl.forner at gmail.com
Wed Mar 20 17:41:04 CET 2013
Hello,
I really need some insight on a problem we encountered using grid,
lattice and gridExtra.
I tried to reduce the problem, so the plot make no sense.
we have a package: gridextrabug
with:
DESCRIPTION
------------------
Package: gridextrabug
Title: gridextrabug
Version: 0.1
Author: toto
Maintainer: toto <karl.forner at quartzbio.com>
Description: gridextrabug
Imports:
grid,
gridExtra,
lattice,
latticeExtra,
reshape,
Depends:
R (>= 2.15),
methods
Suggests:
testthat,
devtools
License: GPL (>= 3)
Collate:
'zzz.R'
'plotFDR.R'
R/plotFDR.R
----------------
plot_fdr <- function(dt,qvalue_col,pvalue_col, zoom_x=NULL, zoom_y=NULL,
fdrLimit=0,overview_plot=FALSE,...)
{
frm <- as.formula(paste(qvalue_col,"~ rank(",pvalue_col,")"))
plt <- xyplot( frm ,
data=dt,
abline=list(h=fdrLimit,lty="dashed"),
pch=16,cex=1,
type="p",
panel=panelinplot2,
subscripts= TRUE,
)
return(plt)
}
panelinplot2 <- function(x,y,subscripts,cex,type,...){
panel.xyplot(x,y,subscripts=subscripts,
ylim=c(0,1),
type=type,
cex=cex,...)
pltoverview <- xyplot(y~x,xlab=NULL,
ylab=NULL,
type="l",
par.settings=qb_theme_nopadding(),
scales=list(draw=FALSE),
cex=0.6,...)
gr <- grob(p=pltoverview, ..., cl="lattice")
grid.draw(gr) # <-----------------------------------------------
problematic call
}
NAMESPACE
------------------
export(panelinplot2)
export(plot_fdr)
importFrom(grid,gpar)
importFrom(grid,grid.draw)
importFrom(grid,grid.rect)
importFrom(grid,grid.text)
importFrom(grid,grob)
importFrom(grid,popViewport)
importFrom(grid,pushViewport)
importFrom(grid,unit)
importFrom(grid,viewport)
importFrom(gridExtra,drawDetails.lattice)
importFrom(lattice,ltext)
importFrom(lattice,panel.segments)
importFrom(lattice,panel.xyplot)
importFrom(lattice,stripplot)
importFrom(lattice,xyplot)
importFrom(latticeExtra,as.layer)
importFrom(latticeExtra,layer)
importFrom(reshape,sort_df)
Then if you execute this script:
without_extra.R
------------------
library(gridextrabug)
p <- seq(10^-10,1,0.001)
p <- p[sample(1:length(p))]
q <- p.adjust(p, "BH")
df <- data.frame(p,q)
plt <- plot_fdr(df,qvalue_col= "q", pvalue_col="p",
zoom_x=c(0,20),
fdrLimit=0.6,
overview_plot=TRUE)
X11()
print(plt)
you will not have the second plot corresponding the call to panelinplot2
If you execute this one:
with_extra.R
------------------
library(gridextrabug)
p <- seq(10^-10,1,0.001)
p <- p[sample(1:length(p))]
q <- p.adjust(p, "BH")
df <- data.frame(p,q)
plt <- plot_fdr(df,qvalue_col= "q", pvalue_col="p",
zoom_x=c(0,20),
fdrLimit=0.6,
overview_plot=TRUE)
X11()
library(gridExtra)
print(plt)
you will have the second plot.
>From what I understood, the last line of panelinplot2(), "
grid.draw(x)", dispatches to grid:::grid.draw.grob(), which in turn
calls grid:::drawGrob(), which calls grid::drawDetails() which is a S3
generic.
The gridExtra package defines the method drawDetails.lattice().
When the package is loaded in the search() path, the "grid.draw(x)"
call dispatches to gridExtra:::drawDetails.lattice().
We would rather avoid messing with the search path, which is a best
practice if I'm not mistaken, so we tried hard to solve it using
Imports.
But I came to realize that the problem was in the grid namespace, not
in our package namespace.
I tested it with the following work-around:
parent.env(parent.env(getNamespace('grid'))) <- getNamespace('gridExtra')
which works.
So my questions are:
* did we miss something obvious ?
* what is the proper way to handle this situation ?
Thanks in advance for your wisdom.
Karl Forner
More information about the R-devel
mailing list