[Roxygen-devel] need usage advice for documentation of methods for print and summary

Paul Johnson pauljohn32 at gmail.com
Tue Jan 3 20:31:25 CET 2012


Following the nice post on stackoverflow

Roxygen2 - how to properly document S3 methods

http://stackoverflow.com/questions/7198758/roxygen2-how-to-properly-document-s3-methods

I'm pretty sure I'm doing the right roxygen2 markup for methods when I
create the generic function.

But I'm confused about writing methods for generics that are in base
R, such as print and summary.  Should I export? Do those methods
belong in different Rd files?  What @params do they inherit from R's
declaration of the generic.  I've fiddle around, trying this a lot of
ways, all of them generate warnings in R CMD check.  Either I get
redundant declarations of parameters from the R base's generic method
or, well, miscellaneous errors about incorrect use of method names in
usage files.

Can I show you my example and ask for advice? meanCenter is a generic
function, meanCenter.default is the implementation.  I think that
part's OK.

After that are summary.mcres and print.mcres. There I have trouble.


##' meanCenter selectively centers or standarizes variables in a
regression model.
##'
##' The defaults will cause a regression's numeric interactive
##' variables to be mean centered. If one wants all predictors to be
##' centered, the option centerOnlyInteractors should be set to FALSE.
The dependent
##' variable will not be centered, unless the user explicitly requests it by
##' setting centerDV = TRUE.
##' @title meanCenter
##' @param model a fitted regression model (presumably from lm)
##' @param centerOnlyInteractors If false, all predictors in the
##' regression data frame are centered before the regression is
##' conducted.
##' @param centerDV Should the dependent variable be centered?
##' @param standardize Instead of simply mean-centering the variables,
should they also be "standardized" by first mean-centering and then
dividing by the estimated standard deviation.
##' @param centerContrasts This function was originally intended only
to center numeric variables. However, this option will ask centering
of the numeric contrasts that are created in the fitting process.
##' @export meanCenter
##' @rdname meanCenter
##' @author Paul E. Johnson <pauljohn@@ku.edu>
##' @seealso \code{\link[pequod]{lmres}}
##' @example inst/examples/meanCenter-ex.R
meanCenter <- function(model, centerOnlyInteractors=TRUE,
centerDV=FALSE, standardize=FALSE, centerContrasts = F){
  UseMethod("meanCenter")
}

##' @return A list including 1) model, a fitted regression object, 2)
centeredVars, a list of the variables that were centered in the
estimation of model, and 3) call, the call that generated the model
result.
##' @rdname meanCenter
##' @export
##' @method meanCenter default
##' @S3method meanCenter default
meanCenter.default <- function(model, centerOnlyInteractors=TRUE,
centerDV=FALSE, standardize=FALSE, centerContrasts = F){

  std <- function(x) {
    if( !is.numeric(x) ){
      stop("center.lm tried to center a factor variable. No Can Do!")
    } else {
      scale(x, center = TRUE, scale = standardize)
    }
  }

  rdf <- get_all_vars(formula(model), model$model) #raw data frame
  t <- terms(model)
  tl <- attr(t, "term.labels")
  tmdc <- attr(t, "dataClasses") ##term model data classes

  isNumeric <- names(tmdc)[ which(tmdc %in% c("numeric"))]
  isFac <-  names(tmdc)[ which(tmdc %in% c("factor"))]
  if (tmdc[1] != "numeric") stop("Sorry, DV not a single numeric column")

  ##Build "nc", a vector of variable names that "need centering"
  ##
  if (!centerDV) {
    if (centerOnlyInteractors == FALSE){
      nc <- isNumeric[-1] #-1 excludes response
      unique(nc)
    }else{
      interactTerms <- tl[grep(":", tl)]
      nc <- unique(unlist(strsplit( interactTerms, ":")))
      nc <-  nc[which(nc %in% isNumeric)]
    }
  }else{
    if (centerOnlyInteractors == FALSE){
      nc <- isNumeric
    }else{
      interactTerms <- tl[grep(":", tl)]
      nc <- unique(unlist(strsplit( interactTerms, ":")))
      nc <- nc[which(nc %in% isNumeric)]
      nc <- c( names(tmdc)[1] , nc)
    }
  }


  mc <- model$call
  # run same model call, replacing non centered data with centered data.
  ## if no need to center factor contrasts:
  if (!centerContrasts)
    {
      stddat <- rdf
      for (i in nc) stddat[ , i] <- std( stddat[, i])
      mc$data <- quote(stddat)
    }else{
      ##dm: design matrix, only includes intercept and predictors
      dm <- model.matrix(model, data=rdf, contrasts.arg =
model$contrasts, xlev = model$xlevels)
      ##contrastIdx: indexes of contrast variables in dm
      contrastIdx <- which(attr(dm, "assign")== match(isFac, tl))
      contrastVars <- colnames(dm)[contrastIdx]
      nc <- c(nc, contrastVars)

      dm <- as.data.frame(dm)

      hasIntercept <- attr(t, "intercept")
      if (hasIntercept) dm <- dm[ , -1] # removes intercept, column 1

      dv <- rdf[ ,names(tmdc)[1]] #tmdc[1] is response variable name
      dm <- cbind(dv, dm)
      colnames(dm)[1] <- names(tmdc)[1] #put colname for dv

      dmnames <- colnames(dm)
      hasColon <- dmnames[grep(":", dmnames)]
      dm <- dm[ , -match(hasColon, dmnames)] ##remove vars with colons
(lm will recreate)

      ##Now, standardise the variables that need standardizing
      for (i in nc) dm[ , i] <- std( dm[, i])


      fmla <- formula(paste(dmnames[1], " ~ ",  paste(dmnames[-1],
collapse=" + ")))
      cat("This fitted model will use those centered variables\n")
      cat("Model-constructed interactions such as \"x1:x3\" are built
from centered variables\n")
      mc$formula <- formula(fmla)
      mc$data <-  quote(dm)
    }

  cat("These variables", nc, "Are centered in the design matrix \n")

  res <- eval(mc)
  class(res) <- c("mcreg", class(model))
  attr(res, "centeredVars") <- nc
  attr(res, "centerCall") <-  match.call()
  res
}


##' @author <pauljohn@@ku.edu>
##' @export
##' @S3method summary mcreg
summary.mcreg <- function(object, ...){
  nc <- attr(object, "centeredVars")
  cat("The centered variables were: \n")
  print(nc)
  cat("Even though the variables here have the same names as their
non-centered counterparts, I assure you these are centered.\n")
  mc <- attr(object, "centerCall")
  cat("These results were produced from: \n")
  print(mc)
  NextMethod(generic = "summary", object = object, ...)
}


##' @author <pauljohn@@ku.edu>
##' @export
##' @S3method print mcreg
print.mcreg <- function(x, ...){
  nc <- attr(x, "centeredVars")
  cat("The centered variables were: \n")
  print(nc)
  cat("Even though the variables here have the same names as their
non-centered counterparts, I assure you these are centered.\n")
  mc <- attr(x, "centerCall")
  cat("These results were produced from: \n")
  print(mc)
  NextMethod(generic = "print", object = x, ...)
}

-- 
Paul E. Johnson
Professor, Political Science
1541 Lilac Lane, Room 504
University of Kansas


More information about the Roxygen-devel mailing list