R/match.call.default.R

Defines functions match.call.defaults

Documented in match.call.defaults

#' Argument matching with defaults
#' 
#' This is a version of \code{\link{match.call}} which also includes default arguments.
#' 
#' @param definition a function, by default the function from which match.call is called. See details.
#' @param call an unevaluated call to the function specified by definition, as generated by call.
#' @param expand.dots ogical. Should arguments matching \code{...} in the call be included or left as a \code{...} argument?
#' @param envir an environment, from which the \code{...} in call are retrieved, if any.
#' 
#' @return An object of class call.
#' 
#' @author Neal Fultz
#' @references \url{http://stackoverflow.com/questions/14397364/match-call-with-default-arguments/}
#' @export
#' 
#' @examples 
#' 
#' foo <- function(x=NULL,y=NULL,z=4, dots=TRUE, ...) {
#'   match.call.defaults(expand.dots=dots)
#' }
#' 
#' foo(4,nugan='hand')
#' foo(dots=FALSE,who='ami')
#' 

match.call.defaults <- function(definition = sys.function(sys.parent()),
           call = sys.call(sys.parent()),
           expand.dots = TRUE,
           envir = parent.frame(2L)) {
  call <- match.call(definition, call, expand.dots, envir)
  formals <- formals(definition)
  
  if(expand.dots && '...' %in% names(formals))
    formals[['...']] <- NULL
  
  for(i in setdiff(names(formals), names(call)))
    call[i] <- list( formals[[i]] )
  

  match.call(definition, call, TRUE, envir)
}

Try the stackoverflow package in your browser

Any scripts or data that you put into this service are public.

stackoverflow documentation built on Jan. 10, 2020, 9:07 a.m.