Perry de Valpine
2008-Sep-24  04:50 UTC
[Rd] function can permanently modify calling function via substitute?
Dear R-devel:
The following code seems to allow one function to permanently modify a
calling function.  I did not expect this would be allowed (short of
more creative gymnastics) and wonder if it is really intended.  (I can
see other ways to accomplish the intended task of this code [e.g. via
match.call instead of substitute below] that do not trigger the
problem, but I don't think that is the point.)
do.nothing <- function(blah) {force(blah)}
do.stuff.with.call <- function(mycall) {
  raw.mycall <- substitute(mycall);   # expected raw.mycall would be local
  print( sys.call() )
  # do.nothing( raw.mycall );  # See below re: commented lines.
  # .Call( "showNAMED", raw.mycall[[2]] )
  force( mycall );  # not relevant where (or whether) this is done
  raw.mycall[[2]] <- runif(1); # permanently modifies try.me on the
first time only
  # .Call( "showNAMED", raw.mycall[[2]] )
  raw.mycall
}
gumbo <- function(x) {
  writeLines( paste( "gumbo : x =" ,  x ) )
  return(x);
}
try.me <- function() {
  one.val <- 111;
  one.ans <- do.stuff.with.call( mycall = gumbo( x = one.val ) );
  one.ans
}
# after source()ing the above:> deparse(try.me)
[1] "function () "
[2] "{"
[3] "    one.val <- 111"
[4] "    one.ans <- do.stuff.with.call(mycall = gumbo(x =
one.val))"
[5] "    one.ans"
[6] "}"> try.me()
do.stuff.with.call(mycall = gumbo(x = one.val))
gumbo : x = 0.396524668671191
gumbo(x = 0.396524668671191)> deparse(try.me)
[1] "function () "
[2] "{"
[3] "    one.val <- 111"
[4] "    one.ans <- do.stuff.with.call(mycall = gumbo(x =
0.396524668671191))"
[5] "    one.ans"
[6] "}"> try.me()
do.stuff.with.call(mycall = gumbo(x = 0.396524668671191))
gumbo : x = 0.396524668671191
gumbo(x = 0.0078618151601404)> deparse(try.me)
[1] "function () "
[2] "{"
[3] "    one.val <- 111"
[4] "    one.ans <- do.stuff.with.call(mycall = gumbo(x =
0.396524668671191))"
[5] "    one.ans"
[6] "}"
So, after the first call of try.me(), do.stuff.with.call has
permanently replaced the name one.val in line 2 of try.me with a
numeric (0.396...).  Subsequent calls from try.me to
do.stuff.with.call now reflect that change, but do.stuff.with.call
does not modify the try.me object again. (Note this means one needs to
keep reloading try.me to investigate).
If this is a problem worth investigating, here are a couple of other
observations that may be relevant but are obviously speculative.
1. If the third line of do.stuff.with.call is uncommented (and try.me
also reloaded), the unexpected behavior does not occur.  Since
do.nothing is eponymous, I was surprised because I believed it should
not impact any other behavior.  Speculating with limited knowledge, I
thought this might implicate something that is supposed to stay
under-the-hood, such as the "`call by value' illusion" described
in
the "R internals" documentation.
2. Poking slightly further, I looked at the NAMED values using this C
code via R CMD SHLIB and dyn.load:
#include "R.h"
#include "Rdefines.h"
SEXP showNAMED(SEXP obj) {
  Rprintf("%i\n", NAMED(obj));
  return(R_NilValue);
}
Uncommenting the .Call lines in do.stuff.with.call (with the
do.nothing line re-commented) reveals that on the first time
do.stuff.with.call is called from try.me, raw.mycall[[2]] has NAMED =1 both
before and after the `[[<-` line.  On subsequent calls it has
NAMED == 2 before and NAMED == 1 after.  If I follow how NAMED is
used, this seems relevant.
Many thanks in advance for any responses.
Perry de Valpine
----------------------> sessionInfo(); ## Also checked on Windows XP Professional running R-7.2.1,
beyond my control to upgrade
R version 2.7.2 (2008-08-25)
i386-apple-darwin8.11.1
locale:
C
attached base packages:
[1] stats     graphics  grDevices utils     datasets  methods   base
loaded via a namespace (and not attached):
[1] tools_2.7.2
Peter Dalgaard
2008-Sep-24  05:54 UTC
[Rd] function can permanently modify calling function via substitute?
Perry de Valpine wrote:> Dear R-devel: > > The following code seems to allow one function to permanently modify a > calling function. I did not expect this would be allowed (short of > more creative gymnastics) and wonder if it is really intended. (I can > see other ways to accomplish the intended task of this code [e.g. via > match.call instead of substitute below] that do not trigger the > problem, but I don't think that is the point.) > > do.nothing <- function(blah) {force(blah)} > > do.stuff.with.call <- function(mycall) { > raw.mycall <- substitute(mycall); # expected raw.mycall would be local > print( sys.call() ) > > # do.nothing( raw.mycall ); # See below re: commented lines. > # .Call( "showNAMED", raw.mycall[[2]] ) > > force( mycall ); # not relevant where (or whether) this is done > raw.mycall[[2]] <- runif(1); # permanently modifies try.me on the > first time only > > # .Call( "showNAMED", raw.mycall[[2]] ) > > raw.mycall > } > > gumbo <- function(x) { > writeLines( paste( "gumbo : x =" , x ) ) > return(x); > } > > try.me <- function() { > one.val <- 111; > one.ans <- do.stuff.with.call( mycall = gumbo( x = one.val ) ); > one.ans > } > > # after source()ing the above: > >> deparse(try.me) >> > [1] "function () " > [2] "{" > [3] " one.val <- 111" > [4] " one.ans <- do.stuff.with.call(mycall = gumbo(x = one.val))" > [5] " one.ans" > [6] "}" > >> try.me() >> > do.stuff.with.call(mycall = gumbo(x = one.val)) > gumbo : x = 0.396524668671191 > gumbo(x = 0.396524668671191) > >> deparse(try.me) >> > [1] "function () " > [2] "{" > [3] " one.val <- 111" > [4] " one.ans <- do.stuff.with.call(mycall = gumbo(x = 0.396524668671191))" > [5] " one.ans" > [6] "}" > >> try.me() >> > do.stuff.with.call(mycall = gumbo(x = 0.396524668671191)) > gumbo : x = 0.396524668671191 > gumbo(x = 0.0078618151601404) > >> deparse(try.me) >> > [1] "function () " > [2] "{" > [3] " one.val <- 111" > [4] " one.ans <- do.stuff.with.call(mycall = gumbo(x = 0.396524668671191))" > [5] " one.ans" > [6] "}" > > So, after the first call of try.me(), do.stuff.with.call has > permanently replaced the name one.val in line 2 of try.me with a > numeric (0.396...). Subsequent calls from try.me to > do.stuff.with.call now reflect that change, but do.stuff.with.call > does not modify the try.me object again. (Note this means one needs to > keep reloading try.me to investigate). > > If this is a problem worth investigating, here are a couple of other > observations that may be relevant but are obviously speculative. > > 1. If the third line of do.stuff.with.call is uncommented (and try.me > also reloaded), the unexpected behavior does not occur. Since > do.nothing is eponymous, I was surprised because I believed it should > not impact any other behavior. Speculating with limited knowledge, I > thought this might implicate something that is supposed to stay > under-the-hood, such as the "`call by value' illusion" described in > the "R internals" documentation. > > 2. Poking slightly further, I looked at the NAMED values using this C > code via R CMD SHLIB and dyn.load: > #include "R.h" > #include "Rdefines.h" > SEXP showNAMED(SEXP obj) { > Rprintf("%i\n", NAMED(obj)); > return(R_NilValue); > } > Uncommenting the .Call lines in do.stuff.with.call (with the > do.nothing line re-commented) reveals that on the first time > do.stuff.with.call is called from try.me, raw.mycall[[2]] has NAMED => 1 both before and after the `[[<-` line. On subsequent calls it has > NAMED == 2 before and NAMED == 1 after. If I follow how NAMED is > used, this seems relevant. > >Yes and no. This does sound like a bug and NAMED is likely involved, but I don't think raw.mycall[[2]] is the thing to look at. More likely, the issue is that raw.mycall[ itself has NAMED == 1 because otherwise [[<- assignment would duplicate it first. This suggests that substitute has the bug. -- O__ ---- Peter Dalgaard ?ster Farimagsgade 5, Entr.B c/ /'_ --- Dept. of Biostatistics PO Box 2099, 1014 Cph. K (*) \(*) -- University of Copenhagen Denmark Ph: (+45) 35327918 ~~~~~~~~~~ - (p.dalgaard at biostat.ku.dk) FAX: (+45) 35327907