[Rd] [Q] Get formal arguments of my implemented S4 method

John Chambers jmc at r-project.org
Thu Jan 29 14:57:15 CET 2015


On Jan 28, 2015, at 6:37 PM, Michael Lawrence <lawrence.michael at gene.com> wrote:

> At this point I would just due:
> 
> formals(body(method)[[2L]])
> 
> At some point we need to figure out what to do with this .local() confusion.

Agreed, definitely.  The current hack is to avoid re-matching arguments on method dispatch, so a fix would need to be fairly deep in the implementation.

But I don't think the expression above is quite right. body(method)[[2L]] is the assignment.  You need to evaluate the rhs.

Here is a function that does the same sort of thing, and returns the standard formals for the generic if this method does not have nonstandard arguments.  We should probably add a version of this function for 3.3.0, so user code doesn't have hacks around the current hack.

methodFormals <- function(f, signature = character()) {
    fdef <- getGeneric(f)
    method <- selectMethod(fdef, signature)
    genFormals <- base::formals(fdef)
    b <- body(method)
    if(is(b, "{") && is(b[[2]], "<-") && identical(b[[2]][[2]], as.name(".local"))) {
        local <- eval(b[[2]][[3]])
        if(is.function(local))
            return(formals(local))
        warning("Expected a .local assignment to be a function. Corrupted method?")
    }
    genFormals
}

> 
> 
> 
> 
> On Wed, Jan 28, 2015 at 10:07 AM, Roebuck,Paul L <PLRoebuck at mdanderson.org>
> wrote:
> 
>> I'm attempting to reflect the information for use with corresponding
>> fields in GUI (in a different package), to provide default values,
>> argname as key for UI label lookups, etc.
>> 
>> So I want something much more like the formals of the implementation:
>> 
>> {
>>    "object",
>>    "method":             c("median", "vs", "tukey"),
>>    "calc.medians":       TRUE,
>>    "sweep.cols":         calc.medians,
>>    "recalc.after.sweep": sweep.cols,
>>    "Š"
>> }
>> 
>> not those of the generic:
>> 
>> {
>>    "object",
>>    "Š"
>> }
>> 
>> 
>> From:  Michael Lawrence <lawrence.michael at gene.com>
>> Date:  Wednesday, January 28, 2015 11:28 AM
>> To:  "Roebuck,Paul L" <PLRoebuck at mdanderson.org>
>> Cc:  R-devel <r-devel at r-project.org>
>> Subject:  Re: [Rd] [Q] Get formal arguments of my implemented S4 method
>> 
>> 
>> Would you please clarify your exact use case?
>> 
>> 
>> Thanks,
>> Michael
>> 
>> 
>> On Wed, Jan 28, 2015 at 9:02 AM, Roebuck,Paul L
>> <PLRoebuck at mdanderson.org> wrote:
>> 
>> Interrogating some (of my own) code in another package.
>> 
>>> norm.meth <- getMethod("normalize", "MatrixLike")
>>> message("str(norm.meth)")
>>> str(norm.meth)
>> 
>>> message("show(norm.meth at .Data)")
>>> show(norm.meth at .Data)
>> 
>> 
>> Last show() displays this:
>> 
>> function (object, ...)
>> {
>>    .local <- function (object, method = c("median", "vs", "tukey"),
>>        calc.medians = TRUE, sweep.cols = calc.medians,
>>        recalc.after.sweep = sweep.cols, ...)
>>    {
>>        .do_normalize(object,
>>            method = match.arg(method),
>>            calc.medians = calc.medians,
>>            sweep.cols = sweep.cols,
>>            recalc.after.sweep = recalc.after.sweep,
>>            ...)
>>    }
>>    .local(object, ...)
>> }
>> 
>> 
>> Desire to be able to access formals() for the .local() function definition,
>> not the generic one. Have seen information desired available via "defined"
>> slot of returned 'MethodDefinition' object, but not using the code below.
>> 
>> 
>> 
>> ====================
>> 
>> library(methods)
>> 
>> if (!isGeneric("normalize")) {
>>    ## Other packages also define this generic...
>>    setGeneric("normalize",
>>               function(object, ...) standardGeneric("normalize"))
>> }
>> 
>> setClassUnion("MatrixLike", c("matrix", "data.frame"))
>> 
>> .do_normalize <- function(concs,
>>                          method,
>>                          calc.medians,
>>                          sweep.cols,
>>                          recalc.after.sweep,
>>                          ...) {
>>    message("internal routine called!")
>>    NULL
>> }
>> 
>> setMethod("normalize", signature(object="MatrixLike"),
>>          function(object,
>>                   method=c("median", "vs", "tukey"),
>>                   calc.medians=TRUE,
>>                   sweep.cols=calc.medians,
>>                   recalc.after.sweep=sweep.cols,
>>                   ...) {
>> 
>>    .do_normalize <- function(object,
>>                            method=match.arg(method),
>>                            calc.medians=calc.medians,
>>                            sweep.cols=sweep.cols,
>>                            recalc.after.sweep=recalc.after.sweep,
>>                            ...)
>> }
>> 
>> ______________________________________________
>> R-devel at r-project.org mailing list
>> https://stat.ethz.ch/mailman/listinfo/r-devel
>> 
>> 
>> 
>> 
>> 
>> 
> 
> 	[[alternative HTML version deleted]]
> 
> ______________________________________________
> R-devel at r-project.org mailing list
> https://stat.ethz.ch/mailman/listinfo/r-devel


	[[alternative HTML version deleted]]



More information about the R-devel mailing list