[Rd] Clarification on generic functions and methods

Henrik Bengtsson hb at stat.berkeley.edu
Wed Nov 11 16:43:50 CET 2009


Using

jml <- function(...) UseMethod("jml")

will do.

/Henrik


On Wed, Nov 11, 2009 at 4:26 PM, Doran, Harold <HDoran at air.org> wrote:
> I have constructed the following functions and need a little clarification:
>
> ### function to fit the model parameters
> jml.fit <- function(dat, con = 1e-3, bias=FALSE, ...){
>        do stuff ...
> }
>
> ### default function which calls jml.fit
> jml.default <- function(dat, con = 1e-3, bias=FALSE, ...){
>        result <- jml.fit(dat, con = 1e-3, bias)
>        result$call <- match.call()
>        class(result) <- "jml"
>        result
> }
>
> ### Function to make use of formula
> jml.formula <- function(formula, data, na.action, subset, ...){
>        mf <- match.call(expand.dots = FALSE)
>    m <- match(c("formula", "data", "na.action", "subset"), names(mf), 0L)
>    mf <- mf[c(1L, m)]
>    mf$drop.unused.levels <- TRUE
>    mf[[1L]] <- as.name("model.frame")
>    mf <- eval(mf, parent.frame())
>        mt <- attr(mf, "terms")
>        dat <- mf
>        result <- jml.default(dat, ...)
>        result$call <- match.call()
>        result$formula <- formula
>        result
> }
>
> ### and the generic function
> jml <- function(dat, con = 1e-3, bias=FALSE, ...) UseMethod("jml")
>
> Writing R Extensions states, "If the generic specifies defaults, all methods should use the same defaults."
>
> In my example above, the generic function has 2 defaults: one for argument con and another bias. I'm a little confused on exactly how the generic function should be structured for proper package development.
>
> I think the options are:
>
> 1) jml <- function(dat, con = 1e-3, bias=FALSE, ...) UseMethod("jml")
> 2) jml <- function(x, con = 1e-3, bias=FALSE, ...) UseMethod("jml")
> 3) jml <- function(formula, data, na.action, subset, con = 1e-3, bias = FALSE, ...) UseMethod("jml")
>
> I'm inclined to believe #3 is correct because the .Rd page needs to reflect the args in this function, is that right? Then, this generic function would include the formula, data, na.action, and subset and it includes the proper defaults as the other functions.
>
> Thank you
> Harold
>
>> sessionInfo()
> R version 2.10.0 (2009-10-26)
> i386-pc-mingw32
>
> locale:
> [1] LC_COLLATE=English_United States.1252  LC_CTYPE=English_United States.1252
> [3] LC_MONETARY=English_United States.1252 LC_NUMERIC=C
> [5] LC_TIME=English_United States.1252
>
> attached base packages:
> [1] stats     graphics  grDevices utils     datasets  methods   base
>
> other attached packages:
> [1] scoreFoo_1.1   MiscPsycho_1.4 statmod_1.4.1
>
> loaded via a namespace (and not attached):
> [1] tools_2.10.0
> ______________________________________________
> R-devel at r-project.org mailing list
> https://stat.ethz.ch/mailman/listinfo/r-devel
>



More information about the R-devel mailing list