[Rd] dput(as.list(function...)...) bug

William Dunlap wdunlap at tibco.com
Tue Mar 24 02:02:51 CET 2009


> -----Original Message-----
> From: r-devel-bounces at r-project.org 
> [mailto:r-devel-bounces at r-project.org] On Behalf Of Duncan Murdoch
> Sent: Monday, March 23, 2009 5:28 PM
> To: Stavros Macrakis
> Cc: r-devel at r-project.org
> Subject: Re: [Rd] dput(as.list(function...)...) bug
> 
> On 23/03/2009 7:37 PM, Stavros Macrakis wrote:
> > Tested in R 2.8.1 Windows
> > 
> >> ff <- formals(function(x)1)
> >> ff1 <- as.list(function(x)1)[1]
> > # ff1 acts the same as ff in the examples below, but is a 
> list rather
> > than a pairlist
> > 
> >> dput( ff , control=c("warnIncomplete"))
> > list(x = )
> > 
> > This string is not parsable, but dput does not give a 
> warning as specified.

The string "list(x = )" is parsable:
  z <- parse(text="list(x = )")
Evaluating the resulting expression results in a run-time error:
  eval(z)
  Error in eval(expr, envir, enclos) :
    element 1 is empty;
     the part of the args list of 'list' being evaluated was:
     (x = )
That is the same sort of error you get from running list(,):
list wants all of its arguments to be present.

With other functions such a construct will run in R, although its result
does not match that of S+ (or SV4):

  > f<-function(x,y,z)c(x=if(missing(x))"<missing>"else x,
                        y=if(missing(y))"<missing>" else y,
                        z=if(missing(z))"<missing>" else z)
  R> f(x=,2,3)
            x           y           z
          "2"         "3" "<missing>"
  S+> f(x=,2,3)
             x   y   z
   "<missing>" "2" "3"
or
  R> f(y=,1,3)
            x           y           z
          "1"         "3" "<missing>"
  S+> f(y=,1,3)
     x           y   z
   "1" "<missing>" "3"

R and S+ act the same if you skip an argument by position
  > f(1,,3)
     x           y   z
   "1" "<missing>" "3"
but differ if you use name=<nothing>: in S+ it skips an argument by name
and in R it is ignored by ordinary functions (where
typeof(func)=="closure").

I wouldn't say this is recommended or often used or the point
of the original post.
 
Bill Dunlap
TIBCO Software Inc - Spotfire Division
wdunlap tibco.com  

> 
> That's not what "warnIncomplete" is documented to do.  The docs (in 
> ?.deparseOpts) say
> 
>   'warnIncomplete' Some exotic objects such as environments,
>            external pointers, etc. can not be deparsed properly.  This
>            option causes a warning to be issued if any of 
> those may give
>            problems.
> 
>            Also, the parser in R < 2.7.0 would only accept 
> strings of up
>            to 8192 bytes, and this option gives a warning for longer
>            strings.
> 
> As far as I can see, none of those conditions apply here:  ff 
> is not one 
> of those exotic objects or a very long string.  The really relevant 
> comment is in the dput documentation:
> 
> "Deparsing an object is difficult, and not always possible."
> 
> Yes, it would be nice if deparsing and parsing were mutual 
> inverses, but 
> they're not, and are documented not to be.
> 
> 
> >> dput( ff , control=c("all","warnIncomplete"))
> > list(x = quote())
> > 
> > This string is parseable, but quote() is not evaluable, and 
> again dput
> > does not give a warning as specified.
> > 
> > In fact, I don't know how to write out ff$x. 
> 
> I don't know of any input that will parse to it.
> 
> 
>   It appears to be the
> > zero-length name:
> > 
> >     is.name(ff$x) => TRUE
> >     as.character(ff$x) => ""
> 
> This may give you a hint:
> 
>  > y <- ff$x
>  > y
> Error: argument "y" is missing, with no default
> 
> It's a special internal thing that triggers the missing value 
> error when 
> evaluated.  It probably shouldn't be user visible at all.
> 
> Duncan Murdoch
> 
> > 
> > but there is no obvious way to create such an object:
> > 
> >     as.name("") => execution error
> >     quote(``) => parse error
> > 
> > The above examples should either produce a parseable and evaluable
> > output (preferable), or give a warning.
> > 
> >             -s
> > 
> > PS As a matter of comparative linguistics, many versions of 
> Lisp allow
> > zero-length symbols/names.  But R coerces strings to 
> symbols/names in
> > a way that Lisp does not, so that might be an invitation to obscure
> > bugs in R where it is rarely problematic in Lisp.
> > 
> > PPS dput(pairlist(23),control="all") also gives the same output as
> > dput(list(23),control="all"), but as I understand it, pairlists will
> > become non-user-visible at some point.
> > 
> > ______________________________________________
> > 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