[Rd] List S3 methods and defining packages
    Renaud Gaujoux 
    renaud at mancala.cbio.uct.ac.za
       
    Wed Jul  8 12:09:44 CEST 2015
    
    
  
Thank you for your reply Martin.
Your code made me realize that S3 methods are added to the
.__S3MethodsTable__. of the package that defines the generic, not to
the ones defining the method itself.
How does things work in the case of a method from one package B
masking the one from another package A? I don't get any warning
message and there seems to be only one entry in the relevant
.__S3MethodsTable__.
Aren't these tables updated when the masking package B is detached?
On 7 July 2015 at 21:01, Martin Morgan <mtmorgan at fredhutch.org> wrote:
> On 07/07/2015 02:05 AM, Renaud Gaujoux wrote:
>>
>> Hi,
>>
>> from the man page ?methods, I expected to be able to build pairs
>> (class,package) for a given S3 method, e.g., print, using
>>
>> attr(methods(print), 'info').
>>
>> However all the methods, except the ones defined in base or S4
>> methods, get the 'from' value "registered S3method for print", instead
>> of the actual package name (see below for the first rows).
>>
>> Is this normal behaviour? If so, is there a way to get what I want: a
>> character vector mapping class to package (ideally in loading order,
>> but this I can re-order from search()).
>
>
> It's the way it has always been, so normal in that sense.
>
> There could be two meanings of 'from' -- the namespace in which the generic
> to which the method belongs is defined, and the namespace in which the
> method is defined. I think the former is what you're interested in, but the
> latter likely what methods() might be modified return.
>
> For your use case, maybe something like
>
>     .S3methodsInNamespace <- function(envir, pattern) {
>         mtable <- get(".__S3MethodsTable__.", envir = asNamespace(envir))
>         methods <- ls(mtable, pattern = pattern)
>         env <- vapply(methods, function(x) {
>             environmentName(environment(get(x, mtable)))
>         }, character(1))
>         setNames(names(env), unname(env))
>     }
>
>
> followed by
>
>   nmspc = loadedNamespaces()
>   lapply(setNames(nmspc, nmspc), .S3methodsInNamespace, "^plot.")
>
> which reveals the different meanings of 'from', e.g.,
>
>> lapply(setNames(nmspc, nmspc), .S3methodsInNamespace,
>> "^plot.")["graphics"]
> $graphics
>                stats             graphics                stats
>           "plot.acf"    "plot.data.frame" "plot.decomposed.ts"
>             graphics                stats                stats
>       "plot.default"    "plot.dendrogram"       "plot.density"
>                stats             graphics             graphics
>          "plot.ecdf"        "plot.factor"       "plot.formula"
>             graphics                stats             graphics
>      "plot.function"        "plot.hclust"     "plot.histogram"
>                stats                stats                stats
>   "plot.HoltWinters"        "plot.isoreg"            "plot.lm"
>                stats                stats                stats
>     "plot.medpolish"           "plot.mlm"           "plot.ppr"
>                stats                stats                stats
>        "plot.prcomp"      "plot.princomp"   "plot.profile.nls"
>             graphics                stats                stats
>        "plot.raster"          "plot.spec"       "plot.stepfun"
>                stats             graphics                stats
>           "plot.stl"         "plot.table"            "plot.ts"
>                stats                stats
>      "plot.tskernel"      "plot.TukeyHSD"
>
> Also this is for loaded, rather than attached, namespaces.
>
> Martin Morgan
>
>> Thank you.
>>
>> Bests,
>> Renaud
>>
>>                                               visible
>>         from generic  isS4
>> print.abbrev                                   FALSE registered
>> S3method for print   print FALSE
>> print.acf                                      FALSE registered
>> S3method for print   print FALSE
>> print.AES                                      FALSE registered
>> S3method for print   print FALSE
>> print.agnes                                    FALSE registered
>> S3method for print   print FALSE
>> print.anova                                    FALSE registered
>> S3method for print   print FALSE
>> print.Anova                                    FALSE registered
>> S3method for print   print FALSE
>> print.anova.loglm                              FALSE registered
>> S3method for print   print FALSE
>> print,ANY-method                                TRUE
>>         base   print  TRUE
>> print.aov                                      FALSE registered
>> S3method for print   print FALSE
>>
>> ______________________________________________
>> R-devel at r-project.org mailing list
>> https://stat.ethz.ch/mailman/listinfo/r-devel
>>
>
>
> --
> 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 R-devel
mailing list