[BioC] Re: Problem with VSN package AGAIN

w.huber at dkfz-heidelberg.de w.huber at dkfz-heidelberg.de
Wed Apr 30 19:54:57 MEST 2003


Hi Mahbub & bioC list

I reproduced this with the R 1.7.0 (2003-04-16) binary release for Windows
from CRAN, and vsn_1.0.0.zip from www.bioconductor.org. The offending code
that causes a segmentation violation can be as simple as

> library(vsn)
> summary(0)

Funny enough, nothing in vsn, and in particular not the code that is run
when the library is loaded, does anything that is directly related to the
function "summary". Also, nothing of that sort happens with an R 1.6.2
windows binary that runs on the same machine; neither with a current R
1.8.0 devel on HP-UX. It seems to be specific to R 1.7.0.

As a workaround, the problem does not seem to occur if, for example,
library(marrayNorm) is loaded before vsn.

vsn does some definition of standardGenerics and setMethod when it loads,
but nothing of this has changed since last autumn. It is all written in R,
and does not use any C code. It requires Biobase, nothing else. Could it
be that some of the method dispatching code is rather fragile in R 1.7.0?

Has anyone encountered a similar problem with this or other packages? I
haven't used the R.1.7.0 release much, is it otherwise working well? I
attach the the code that is executed when vsn is loading (zzz.R and
.initvsn()), maybe someone sees something that I don't.

Best regards
  Wolfgang




-------------------------------------
Wolfgang Huber
Division of Molecular Genome Analysis
German Cancer Research Center
Heidelberg, Germany
Phone: +49 6221 424709
Fax:   +49 6221 42524709
Http:  www.dkfz.de/mga/whuber
-------------------------------------











On Wed, 30 Apr 2003, Mahbub Latif wrote:

> Hi,
>
> I am trying to use vsn package for analysing my data.
> To show what I am facing I consider the following
> example which one can reproduce.
>
>
>
> >set.seed(123)
> >cy3 <- matrix(rnorm(30,5,1),nrow=10)
>
> >set.seed(222)
> >cy5 <- matrix(rnorm(30,2,2), nrow=10)
>
> >cy <- cbind(cy3, cy5)
>
> >library(vsn)
>
> Funny things are happenning. After loading vsn package
> (library(vsn)) I cannot use some functions such as
> summary. For example,
>
> > summary(cy3)
> Segmentation fault
>
> or
>
> >cy1 <- data.frame(cy)
> >cy1
> Segmentation fault
>
> and R terminated. But the same function work peoperly
> before loading vsn package. Some other functions I
> have cheked do not work after loading vsn package such
> as plot functions of lattice package.
>
> It would be great if someone help me on this. Before
> (when I sent my previous request) I thought this
> happen only to lymphoma data but now I found loading
> vsn package affects some R base functions.
>
> >version
> platform i686-pc-linux-gnu
> arch     i686
> os       linux-gnu
> system   i686, linux-gnu
> status
> major    1
> minor    7.0
> year     2003
> month    04
> day      16
> language R
>
>
> __________________________________
> Do you Yahoo!?

> http://search.yahoo.com
>
-------------- next part --------------
##-----------------------------------------------------------------
## .First.lib: this function is called when the package is loaded
##-----------------------------------------------------------------
.First.lib <- function(lib, pkgname, where) {
  require(Biobase, quietly=TRUE) || stop("Cannot load without package \"Biobase\"")  
  
  if(missing(where)) {
    where <- match(paste("package:", pkgname, sep=""), search())
    if(is.na(where)) {
      warning(paste("Not a package name: ",pkgname))
      return()
    }
    where <- pos.to.env(where)
  }

  .initvsn(where)
}

-------------- next part --------------
##-----------------------------------------------------------------
## .initvsn is called by .First.lib
##-----------------------------------------------------------------
.initvsn <- function(where) {
  ##------------------------------------------------------------
  ## define the class "vsn.result"
  ##------------------------------------------------------------
  setClass("vsn.result", where=where,
           representation(              ## its slots
                          h       = "matrix",
                          params  = "matrix",
                          sel     = "vector"), 
           prototype = list(            ## and default values
             h       = matrix(nrow=0, ncol=0),
             params  = matrix(nrow=0, ncol=0),
             sel     = logical(0)
             )
           )
  ##------------------------------------------------------------------
  ## params(vsn.result): will return the last column of matrix params
  ## i.e. the model parameters at the end of the iterations
  ##------------------------------------------------------------------
  if (!isGeneric("params"))
     setGeneric("params", function(object) standardGeneric("params"), where=where)
    
  setMethod("params", "vsn.result",
             function(object) object at params[,ncol(object at params)],
             where=where)
  
  ##------------------------------------------------------------
  ## plot method for vsn.result objects
  ##------------------------------------------------------------
  if (!isGeneric("plot"))
     setGeneric("plot", where=where, def=function(x, y, ...) standardGeneric("plot"))
  
  setMethod("plot", signature=c("vsn.result", "missing"), where=where,
     definition=function(x, ...) {
       if (ncol(x at h)<2 || ncol(x at h)*2 != nrow(x at params))
         stop("argument x is inconsistent")
       
       dots <- list(...)
       ind <- match("what", names(dots))
       if(!is.na(ind)) {
         what = dots$what
         dots <- dots[-ind]
       } else {
         what = "sdmean"
       }
       ind <- match("ranks", names(dots))
       if(!is.na(ind)) {
         ranks = dots$ranks
         dots <- dots[-ind]
       } else {
         ranks = TRUE
       }
       xlab <- ylab <- main <- ""
       ind <- match("xlab", names(dots))
       if(!is.na(ind)) {
         xlab <- dots$xlab
         dots <- dots[-ind]
       } 
       ind <- match("ylab", names(dots))
       if(!is.na(ind)) {
         ylab = dots$ylab
         dots <- dots[-ind]
       }
       ind <- match("main", names(dots))
       if(!is.na(ind)) {
         main = dots$main
         dots <- dots[-ind]
       }
       
       switch(what,
        sdmean = {
          cols <- c("black", "red")[as.numeric(x at sel)+1]
          n    <- length(x at sel)
          rkm  <- rank(rowMeans(x at h))
          sds  <- rowSds(x at h)
          ltsq <- length(which(x at sel))/n
          ## running quantile of width 2*dm
          dm        <- 0.1
          midpoints <- seq(dm, 1-dm, by=dm)
          rq.sds <- lapply(midpoints, function(mp) {
             median(sds[within(rkm/n, mp-dm, mp+dm)])
           })

          if(!is.logical(ranks))
            stop("argument ranks must be logical")
          if(ranks){
            px1 <- rkm; px2 <- midpoints*n
            if(xlab=="") xlab <- "rank of average intensity"
          } else {
            px1 <- rowMeans(x at h); px2 <- quantile(px1, probs=midpoints)
            if(xlab=="") xlab <- "average intensity"
          }
          if(ylab=="") ylab <- "standard deviation"
          
          args <- list(x=px1, y=sds, pch=".", col=cols, xlab=xlab, ylab=ylab)
          do.call("plot.default", append(args, dots))
          lines(px2, rq.sds, col="blue", type="b", pch=19)
        },
       ## 
       offsets = {
         d <- ncol(x at h)
         if(main=="") main <- what
         args <- list(x    = x at params[1,],
                      ylim = range(x at params[1:d,], na.rm=TRUE),
                      type = "b", pch=19, main=main, xlab=xlab, ylab=ylab)
         do.call("plot.default", append(args, dots)) 
         for (j in 2:d)
           lines(x at params[j,], type="b")
       },
       factors = {
         d <- ncol(x at h)
         if(main=="") main <- what
         args <- list(x    = x at params[d+1,],
                      ylim = range(x at params[d+(1:d),], na.rm=TRUE),
                      type = "b", pch=19, main=main, xlab=xlab, ylab=ylab)
         do.call("plot.default", append(args, dots)) 
         for (j in 2:d)
           lines(x at params[d+j,], type="b")
       },
       ##
       stop(paste("Unknown what=", what))
     ) ## end switch
   } ## end of function definition for "plot"
  )  ## end of setMethod("plot",...)
  
  ##------------------------------------------------------------
  ## print method for vsn.result objects
  ##------------------------------------------------------------
  if (!isGeneric("print"))
    setGeneric("print", where=where, def=function(x) standardGeneric("print"))
  
  setMethod("print", signature=c("vsn.result"), where=where,
     definition=function(x) {
       cat("vsn.result object\n",
         sprintf("%dx%d-matrix of transformed intensities\n", as.integer(nrow(x at h)), as.integer(ncol(x at h))),
         sprintf("%d-vector of transformation parameters\n", as.integer(nrow(x at params))))
     }
  )  ## end of setMethod("print")
  
  ##------------------------------------------------------------
  ## show method for vsn.result objects
  ##------------------------------------------------------------
  if (!isGeneric("show"))
    setGeneric("show", where=where, def=function(x) standardGeneric("show"))
  
  setMethod("show", signature=c("vsn.result"), where=where,
     definition=function(object) print(object) )
  
} ## end of .initvsn



More information about the Bioconductor mailing list