[BioC] Confusion over inconsistencies with showMethods('Rle') when loaded via GenomicRanges

Martin Morgan mtmorgan at fhcrc.org
Thu Jan 31 07:45:46 CET 2013


On 01/30/2013 06:55 PM, Steve Lianoglou wrote:
> Hi Pete,
>
> On Wed, Jan 30, 2013 at 7:17 PM,  <hickey at wehi.edu.au> wrote:
>> Hi Steve,
>>
>> Thanks for your explanation. I'm just learning about the S4 class and
>> methods so I suspected I'd missed something. I ran your example on my
>> machine and it returned the same output.
>>
>> I've now found the real problem in my code but don't understand why is
>> causing inheritance problems for Rle. Basically, there's a line in my class
>> definitions to define a class union, namely: setClassUnion('vectorOrNULL',
>> c("vector", "NULL"). Depending on whether that line is included before I try
>> to construct the GRanges object determines whether the object is
>> successfully created. Can anyone please explain this to me?
> [snip]
>
>> ## But this version does not work as intended
>> ## Firstly, start a fresh R session
>>> library(GenomicRanges)
> [snip]
>
>>> setClassUnion("vectorOrNULL", c("vector", "NULL")) ## This line is the
>>> culprit
>>> out <- list(chr = rep('chr21', 10), 1:10, start = 1:10, end = 2:11)
>>> showMethods('Rle')
>> Function: Rle (package IRanges)
>> values="missing", lengths="missing"
>> values="vectorORfactor", lengths="integer"
>> values="vectorORfactor", lengths="missing"
>> values="vectorORfactor", lengths="numeric"
>>
>>> gr <- GRanges(seqnames = out[['chr']], ranges = IRanges(start =
>>> out[['start']], end = out[['end']]))
>> Error in function (classes, fdef, mtable)  :
>>    unable to find an inherited method for function ‘Rle’ for signature
>> ‘"character", "missing"’
>>> showMethods('Rle')
>> Function: Rle (package IRanges)
>> values="missing", lengths="missing"
>> values="vectorORfactor", lengths="integer"
>> values="vectorORfactor", lengths="missing"
>> values="vectorORfactor", lengths="numeric"
>>
>> ## Inheritance problems for Rle
>
> Interesting ... my guess is because with your new class union, both of
> these are now TRUE:
>
> R> is(c('a', 'b', 'c'), 'vectorORfactor')
> [1] TRUE
>
> R> is(c('a', 'b', 'c'), 'vectorOrNULL')
> [1] TRUE
>
> But it really feels like the class union shouldn't be getting in the
> way -- I mean, if one then writes an Rle method for c("vectorOrNULL",
> "missing"), I can imagine what the problem might be, but that's not
> the case here.
>
> Hmmm ... if I were a bit bolder, I'd hazard that this might even be a
> bug somewhere in some S4 dispatching mojo, but I'm not
> well-versed-enough in its voodoo to make that claim.
>
> I suspect Martin will likely chime in to point out what is the what, here ;-)

Yep, this is a puzzler. Here's what happens in a fresh R session:

   > setClassUnion("vectorORfactor", c("vector", "factor"))
   > getClass("numeric")
   Class "numeric" [package "methods"]

   No Slots, prototype of class "numeric"

   Extends:
   Class "vector", directly
   Class "vectorORfactor", by class "vector", distance 2

   Known Subclasses:
   Class "integer", directly
   Class "ordered", by class "factor", distance 3

and then

   > setClassUnion("vectorOrNULL", c("vector", "NULL"))
   > getClass("numeric")
   Class "numeric" [package "methods"]

   No Slots, prototype of class "numeric"

   Extends:
   Class "vector", directly
   Class "vectorORfactor", by class "vector", distance 2
   Class "vectorOrNULL", by class "vector", distance 2

   Known Subclasses:
   Class "integer", directly
   Class "ordered", by class "factor", distance 3

Notice that "numeric" extends our two class unions.

Now when we're dealing with a package, focusing on the 'Extends:' component

   library(IRanges)
   > getClass("numeric")
   ...
   Extends:
   Class "vector", directly
   Class "atomic", directly
   Class "vectorORfactor", by class "vector", distance 2
   > setClassUnion("vectorOrNULL", c("vector", "NULL"))
   > getClass("numeric")
   ...
   Extends:
   Class "vector", directly
   Class "vectorOrNULL", by class "vector", distance 2

so we have replaced rather than amended Extends:. I think the error with method 
dispatch follows from this -- we end up looking for a method defined on 
vectorORNULL, and don't find one.

I think the problem is in methods::assignClassDef, but things get a bit hairy 
for me; maybe there are class definitions for numeric that are found in IRanges, 
and in methods, and the latter over-writes the former?

A work-around seems to be to setClassUnion() before loading IRanges.

I find class unions pretty weird -- reach in to the class hierarchy and saying 
no, inheritance works _this_ way and at the same time making things complicated 
for ourselves because we always have to check whether the slot is a vector or 
NULL -- I wonder what you're hoping to accomplish with this? I know the pattern 
is well-established in IRanges...

Martin

>
> -steve
>


-- 
Computational Biology / Fred Hutchinson Cancer Research Center
1100 Fairview Ave. N.
PO Box 19024 Seattle, WA 98109

Location: Arnold Building M1 B861
Phone: (206) 667-2793



More information about the Bioconductor mailing list