[Rd] Changing "..." inside a function: impossible? desirable?

Philippe Grosjean phgrosjean@sciviews.org
Wed Dec 18 15:32:56 2002


Martin,

I am also fighting with this kind of problem. I consider it is logical to
"specialize" arguments as soon as they have to be used for different
features in the plot (col => col.axis, col.title, etc). For instance,
imagine one wants to create a simple function to plot two series on the same
graph:

dualplot <- function(x, y1, y2, ...){
	plot(x, y1, ...)
	lines(x, y2, ...)
}

# with for instance:
X <- 1:20
Y1 <- rnorm(20)
Y2 <- runif(20)
dualplot(X, Y1, Y2)

# so far, so good, but now, if one wants to change color of the second plot
separately. Using:
dualplot(X, Y1, Y2, col=2)
# ... changes color of BOTH plots!

# Here, it makes sens to use different arguments for the color of both
plots:
dualplot2 <- function(x, y1, y2, col1=1, col2=3, ...){
	plot(x, y1, col=col1, ...)
	lines(x, y2, col=col2, ...)
}
dualplot2(X, Y1, Y2, col1=2, col2=4)

# Or better yet, but requires additional code:
dualplot3 <- function(x, y1, y2, cols=c(1, 3), ...){
	cols <- rep(cols, length.out=3)	# For correct recycling rule
	plot(x, y1, col=cols[1], ...)
	lines(x, y2, col=cols[2], ...)
}
dualplot3(X, Y1, Y2, cols=c(2, 4))

# This could also apply for title(), axis(),... of course
# The only problem is when one wants to specialize the argument for one
subfunction only, but not for the other ones:
dualplot4 <- function(x, y1, y2, col2=3, ...){	# We want to use the standard
'col=' argument in the ... for plot(), and a specialized 'col2=' arg for
lines()
	plot(x, y1, ...)
	lines(x, y2, col=col2, ...)
}
dualplot4(X, Y1, Y2, col=2, col2=4)
# This gives an error of multiple arguments matching in lines()!

So, with this approach, we see that the only required change is to give
priority to argument 'col=col2' against what could be provided in '...'.
Eliminating 'col=' argument in ... is one solution, but the next one is
perhaps better. The alternative solution would be to add an option like
'allow.multiple.args.match', set to FALSE by default, but when set to TRUE,
only the first match of an argument is used without error message. So, our
dualplot4() function would work with:

dualplot4 <- function(x, y1, y2, col2=3,
){	
	plot(x, y1, ...)
	options(allow.multiple.args.match = TRUE)
	lines(x, y2, col=col2, ...)
	# ... other treatment susceptible to have multiple matches
	options(allow.multiple.args.match = FALSE)
}

Best,

Philippe

...........]<(({?<...............<?}))><...............................
( ( ( ( (
 ) ) ) ) )      Philippe Grosjean
( ( ( ( (
 ) ) ) ) )      IFREMER Nantes - DEL/AO
( ( ( ( (       rue de l'Ile d'Yeu, BP 21105, 44311 Nantes Cedex 3
 ) ) ) ) )      tel: (33) 02.40.37.42.29, fax: (33) 02.40.37.42.41
( ( ( ( ( 
 ) ) ) ) )      SciViews project coordinator (http://www.sciviews.org)
( ( ( ( (       e-mail: phgrosjean@sciviews.org
 ) ) ) ) ) 
( ( ( ( (       "I'm 100% confident that p is between 0 and 1"
 ) ) ) ) )                                L. Gonick & W. Smith (1993)
.......................................................................
 

-----Message d'origine-----
De : r-devel-admin@stat.math.ethz.ch
[mailto:r-devel-admin@stat.math.ethz.ch]De la part de Martin Maechler
Envoye : mardi 17 decembre 2002 19:07
A : R-devel@stat.math.ethz.ch
Objet : [Rd] Changing "..." inside a function: impossible? desirable?


This is was something like a request for your comments, thoughts
on the topic...

Many of you will know that the "..." (aka \dots) argument is
very useful for passing ``further graphical parameters'', 
but can be a pain when itself is passed to too many plotting
functions inside your own function.
An artificial example being

  myplot <- function(x,y, ...) {

   plot(0:1, 0:1, type = "n", axes = FALSE)

   result <-  <<do stuff with x,y>>

   points(result, ...)
   axis(1, ...)
   axis(2, ...)
   title(...)
  }

It's clear that some things in "..." can be passed to title() and
some to axis(), etc.
Of course the above is really silly, but I have a situation
where I'd like to see if something, say, `myarg' is par
t of "..."
{piece of cake easy, see below} but then I want to  *eliminate*
it from "..." such that I can pass "..." down to other functions
which would want to see a `myarg' argument.

Something like

if("myarg" %in% (naml <- names(list(...)))) {
   ## ok, it's there, take it out
   marg <- list(...)$ marg

   ## what I now would like is

   ...  <-  unlist( list(...)["myarg" != naml] )
}


BTW: one relatively ugly workaround is to use the above *list*
     say  nlist <- list(...)["myarg" != naml]
     and do all subsequent call where I'd had "..." as
     do.call( <funname> ,  c(list( <<other args to funnname>> ), nlist))
but this really obfuscates the code horrendously.

PS:
    I know that using a  pars = list(.) argument instead of "..."
    is another alternative (that we have been using) as well,
    but lets assume this can't be done, because of compatibility reasons.

Martin Maechler <maechler@stat.math.ethz.ch>	http://stat.ethz.ch/~maechler/
Seminar fuer Statistik, ETH-Zentrum  LEO C16	Leonhardstr. 27
ETH (Federal Inst. Technology)	8092 Zurich	SWITZERLAND
phone: x-41-1-632-3408		fax: ...-1228			<><

______________________________________________
R-devel@stat.math.ethz.ch mailing list
http://www.stat.math.ethz.ch/mailman/listinfo/r-devel