[BioC] Error loading, on Bioconductor 1.8, exprSet generated with bioconductor 1.7

Martin Morgan mtmorgan at fhcrc.org
Thu Jun 8 18:11:14 CEST 2006


Hi Raf,

Thanks for the clarification. It sounds like you've found a good
solution.

The long-term intention is to move away from exprSet as the basic
building block, and toward a similar 'ExpressionSet' class. With this
in mind, you could also have done (with the current version of
Biobase)

> obj <- as(tr7.rma, "ExpressionSet")

to obtain an ExpressionSet from your (broken) exprSet. An
ExpressionSet has methods like exprs(), phenoData(), and pData() that
work as exprSet methods, so for many purposes having an ExpressionSet
is a great replacement for exprSet.

It's important to be able to return to previous versions of objects,
and make them 'current'. To that end, the development version of
Biobase introduces ways of 'versioning' objects (so that it's easy to
figure out when the object was created) and an 'updateObject' method
to bring an object up to date. So in the next release of Biobase
(available to those already using the 'development' branch of R)
you'll be able to

> obj <- updateObject(tr76.rma)

and stand a reasonable chance of getting an object that satisfies the
current definition of exprSet.

Finally, the following function might work to update exprSet-like (and
perhaps other) objects to their current version. This might be useful
until the next release of Bioconductor.

Martin

updateObject <- function(x, xclass=class(x), verbose=FALSE) {
    if (is(x, "environment")) {
        if (verbose)
            message("returning original object of class 'environment'")
        return(x)
    }
    news <- names(getSlots(xclass))
    if (is.null(news)) {
        if (verbose) message("definition of '", xclass, "' has no slots; ",
                             "returning original object")
        return(x)
    }
    errf <- function(...)
      function(err) {
          if (verbose)
            message(..., ":\n    ", conditionMessage(err),
                    "\n    trying next method...")
          NULL
      }
    if (verbose) message("updateObject('", xclass, "')")
    olds <- attributes(unclass(x))
    joint <- intersect(names(olds), news)
    olds[joint] <- lapply(olds[joint], updateObject, verbose=verbose)
    res <- NULL
    if (is.null(res))
      res <- 
        tryCatch({
            do.call("new", c(xclass, olds[joint]))
        }, error=errf("'new(\"",xclass,"\", ...)' from slots failed"))
    if (is.null(res))
      res <- 
        tryCatch({
            obj <- do.call("new", list(xclass))
            for (slt in joint) slot(obj, slt) <- slot(x, slt)
            obj
        }, error=errf("failed to add slots to 'new(\"",xclass,"\", ...)'"))
    if (is.null(res))
      stop("could not updateObject to class '", xclass, "'")
    validObject(res)
    res
}




rcaloger <raffaele.calogero at unito.it> writes:

> You are right, I check the object creation, it was July 2005,
> therefore it was created with the release 1.6 of Bioconductor.
> This is the output of the class(tr7.rma)
> [1] "exprSet"
> attr(,"package")
> [1] "Biobase"
>
> I manage to see the content of the object with show(tr7.rma) also on
> Bioconductor 1.8.
> However, the str(tr7.rma) gives the error
>
> Error in FUN(X[[6]], ...) : no slot of name "reporterInfo" for this
> object of class "exprSet"
>
>
> I have then created a new instace of exprSet in the following way:
> pd.xx<-new("phenoData")
> pData(pd.xx)<-pData(tr7.rma)
> xx<-new('exprSet', exprs = exprs(tr7.rma), phenoData=pd.xx)
> tr7.rma<-xx
>
> I had to recreate also the phenoData instance since the varMetadata
> variable was missed in my phenoData.
> However, this problem rise the question: is ti reasonable to use
> exprSet objects as backup?
> Thanks for your help
> Raffaele
>
>  Martin Morgan wrote:
>
>>Raf --
>>
>>Can you provide just a bit more information? What's the result of
>>
>>
>>
>>>class(tr7.rma)
>>>
>>>
>>
>>Also, I suspect that tr7.rma was created not in the last release of
>>Biobase, but the release before that (at least). I say this because
>>the 'reporterInfo' slot was present in the 1.7 release.
>>
>>In the mean time, I suspect that
>>
>>
>>
>>>show(tr7.rma)
>>>
>>>
>>
>>will display the contents of your object.
>>
>>Martin
>>
>>rcaloger <raffaele.calogero at unito.it> writes:
>>
>>
>>
>>>Hi,
>>> today I was working on an Affy exprSet I saved before the new
>>> release of Bioconductor (1.8).
>>>I loaded it but I got the following error when I tried to show it:
>>>library(affy)
>>>load("tr7.rma.rda")
>>>tr7.rma
>>> Error in slot(object, what) : no slot of name "pubMedIds" for this
>>> object of class "MIAME"
>>>
>>>Furthermore, if I issue the command:
>>>str(tr7.rma)
>>>I got this error:
>>> Error in FUN(X[[6]], ...) : no slot of name "reporterInfo" for this
>>> object of class "exprSet"
>>>
>>> I was expecting that there should be some sort of back
>>> compatibility with  at least the previous release of the exprSet.
>>>The error comes using the  Biobase Version: 1.10.0.
>>> There is any way to fix the problem or Do I have to install again
>>> the old release of  Bioconductor?
>>>Thanks
>>>Raf
>>>
>>>
>>> -- 
>>>
>>>----------------------------------------
>>>Prof. Raffaele A. Calogero
>>>Bioinformatics and Genomics Unit
>>>Dipartimento di Scienze Cliniche e Biologiche
>>>c/o Az. Ospedaliera S. Luigi
>>>Regione Gonzole 10, Orbassano
>>>10043 Torino
>>>tel.   ++39 0116705420
>>>Lab.   ++39 0116705408
>>>Fax    ++39 0119038639
>>>Mobile ++39 3333827080
>>>email: raffaele.calogero at unito.it
>>>www:   www.bioinformatica.unito.it
>>>
>>>_______________________________________________
>>>Bioconductor mailing list
>>>Bioconductor at stat.math.ethz.ch
>>>https://stat.ethz.ch/mailman/listinfo/bioconductor
>>>Search the archives: http://news.gmane.org/gmane.science.biology.informatics.conductor
>>>
>>>
>
>
> -- 
>
> ----------------------------------------
> Prof. Raffaele A. Calogero
> Bioinformatics and Genomics Unit
> Dipartimento di Scienze Cliniche e Biologiche
> c/o Az. Ospedaliera S. Luigi
> Regione Gonzole 10, Orbassano
> 10043 Torino
> tel.   ++39 0116705420
> Lab.   ++39 0116705408
> Fax    ++39 0119038639
> Mobile ++39 3333827080
> email: raffaele.calogero at unito.it
> www:   www.bioinformatica.unito.it



More information about the Bioconductor mailing list