[Rd] Expanding partial names
    Gabor Grothendieck 
    ggrothendieck at gmail.com
       
    Tue Mar  7 16:27:06 CET 2006
    
    
  
The original code was not intended to be fully finished.
It was just to give the idea so I left out the error checking.
Adding such a check is just a matter of adding an if
statement to check the pmatch for NA:
wrapper <- function(...) {
  args <- list(...)
  if (length(args)) {
     nf <- names(formals(lowlevel))
     idx <- pmatch(names(args), nf)
     if (any(is.na(idx)))
        stop(paste("Invalid names used:", names(args)[is.na(idx)]))
     nams <- nf[idx]
     args <- replace(list(longname = 2), nams, args)
  }
  do.call("lowlevel", args)
}
wrapper(long = 3)
wrapper(junk = 5)
On 3/7/06, Duncan Murdoch <murdoch at stats.uwo.ca> wrote:
> On 3/7/2006 9:42 AM, Gabor Grothendieck wrote:
> > Try this:
> >
> >
> > wrapper <- function(...) {
> >   args <- list(...)
> >   if (length(args)) {
> >         nf <- names(formals(lowlevel))
> >         nams <- nf[pmatch(names(args), nf)]
> >         args <- replace(list(longname = 2), nams, args)
> >   }
> >   do.call("lowlevel", args)
> > }
> >
> > Here is a test:
> >
> >> wrapper()
> > longname =  1
> >> wrapper(longname = 34)
> > longname =  34
> >> wrapper(long = 34)
> > longname =  34
>
> Thanks, that's getting close, but it doesn't quite handle errors cleanly:
>
>  > wrapper(junk=3)
> Error in lowlevel(longname = 2, "NA" = 3) :
>         unused argument(s) (NA ...)
>
> It looks like I'll need something fairly elaborate.
>
> Duncan Murdoch
>
> > On 3/7/06, Duncan Murdoch <murdoch at stats.uwo.ca> wrote:
> >> I'm writing wrappers for some functions that change some of the default
> >> arguments.  I'd rather not list all of the arguments for the low level
> >> functions because there are about a dozen wrapper functions, and about
> >> 20 arguments to lowlevel.  Instead I'm trying something like this:
> >>
> >> lowlevel <- function(longname = 1) {
> >>   cat("longname = ", longname, "\n")
> >> }
> >>
> >> wrapper <- function(...) {
> >>   newargs <- list(longname = 2)
> >>   newargs[names(list(...))] <- list(...)
> >>   do.call("lowlevel", newargs)
> >> }
> >>
> >> This almost works:
> >>
> >>  > wrapper()
> >> longname =  2
> >>  > wrapper(longname = 3)
> >> longname =  3
> >>
> >> But it fails if I try to use partial argument matching:
> >>
> >>  > wrapper(long=4)
> >> Error in lowlevel(longname = 2, long = 4) :
> >>         unused argument(s) (long ...)
> >>
> >> because long isn't matched to longname.  Is there a reasonable way to do
> >> this (e.g. using pmatch or charmatch) other than listing all the low
> >> level arguments in the argument list to wrapper?
> >>
> >> Duncan Murdoch
> >>
> >> ______________________________________________
> >> R-devel at r-project.org mailing list
> >> https://stat.ethz.ch/mailman/listinfo/r-devel
> >>
> >
> > ______________________________________________
> > R-devel at r-project.org mailing list
> > https://stat.ethz.ch/mailman/listinfo/r-devel
>
>
    
    
More information about the R-devel
mailing list