R-alpha: New version of R for testing

Kurt Hornik Kurt.Hornik@ci.tuwien.ac.at
Fri, 25 Jul 1997 10:57:31 +0200


>>>>> Ross Ihaka writes:

> The newest version of R for Unix (version 0.50 alpha-1) is now (or
> will soon be) available from the following sites.

> ...

Here are some comments on the new version.  Actually, quite a few ...
Hard to structure the whole thing nicely.

* My
	R> x <- 1:5
	R> dimnames(x)[1,2] <- NULL
segfault in dimnames mutation appears as Open in TASKS, and as Closed in
TASKS.OLD.

* In

R> D(expression(z * (log(z) /z)), "z")
(log(z)/z) + z * (1/z/z - log(z)/z^2)

the "1/z/z" is perhaps not optimal ...

* TASKS has

TASK:	"chisquare.test" problem
STATUS:	Open
FROM:	<venkat@biosta.mskcc.org>
	Can you change the explicit "cat" statement in the
	"chisquare.test" function which insists on writing to the
	screen even when the output is redirected to a variable? (Using
	"htest" class as in "t.test" function.)
	[ Should we switch to the library one. ]

As I already suggested, it would be nice to include all of ctest with
the distribution proper.

I have another question/suggestion re chisquare tests.  Several of my
functions in ctest now return "observed" and "expected" components.
Would it be a good idea to print these automatically (if they exist) in
print.htest?

* In src/unix/system.c, one `Rdata' should be `RData' (d -> D).

* No methods for as.data.frame exist!

* How can I return from browser()?
return() does not seem to work for me!

* TASKS has

TASK:	abline + coefficients
STATUS:	Closed
FROM:	<nobu@psrc.isac.co.jp>
	I found a little different behavior of R with S.
	at R-0.49:
	    > a
	    [1] 12 23 22 34 44 54 55 70 78
	    > plot(a)
	    > abline(lsfit(seq(1,len=length(a)), a))
	    Error: no applicable method for "coefficients"
	at S (from AT&T '92) result draw coefficient line without error.
	Then I think to need define a function as followed:
	    coefficients.default <- function(x) x$coef
	[ Default method already added for Doug Bates. ]

For me, this produces no error but abline does not produce any output
for me.  Can anyone check/confirm this?

See also

TASK:	"abline" incompatibility
STATUS:	Open
FROM:	<nobu@psrc.isac.co.jp>

and the 

* TASKS has

TASK:	ls.print
STATUS:	Open
FROM:	<maechler@stat.math.ethz.ch>
	Yes, I do confirm that the  Help page  (?NCOL) contains  '.COL'.
	Apply the following patch (to doc2ms) in  $RHOME/etc , and "all
	is well":

This seems to be fine now.  Martin?

* The ls.print problem reported by <VENKAT@biosta.mskcc.org> seems to be
gone now.  (Still labeled as Open in TASKS).

* Some of the "formula" problems in TASKS (<mikem@stat.cmu.edu>, 
<p.dalgaard@kubism.ku.dk> and <thomas@biostat.washington.edu> seem to be
gone now.

* Several of the graphics patches sent by
<kovac@figaro.stats.bris.ac.uk> (labeled Open in TASKS) seem to have
been taken care of already, in particular by integrating Martin's
patches.  Martin?

* As a remark on

TASK:	String length problems
STATUS:	Closed
FROM:	<maechler@stat.math.ethz.ch>
	This is not a  cat(.) but a  string storing/parsing problem:
	nchar("\n\n")  # gives  2  instead of 3
	[ Hmmm.  Was this typed to readline I wonder?  There it  ]
	[ seems that ^L must be escaped with ^V.  Using the ANSI ]
	[ \f will now produce a literal formfeed.  Indeed, using ]
	[ any of the ANSI C escapes will work.			 ]

note that under ESS pre 4.9,

	R> nchar("\n\n")

	[1] 2

(empty line in between!), so "^L" needs to be escaped here too.  (Same
for single quotes.)

* TASKS has

TASK:	Documentation Nit
STATUS:	Closed
FROM:	<Kurt.Hornik@ci.tuwien.ac.at>
	The documentation for ls/objects has
		ls(name, pos=2, envir=sys.frame(sys.parent()),
		   all.names=FALSE, pattern)
	but the code has
		ls <-
		function (name, pos = -1, envir = NULL,
			  all.files = FALSE, pattern)
	[ At one time these were equivalent.  Are they still? ]

However, the documentation is still unchanged!

* Re 

TASK:	"cat" problem
STATUS:	Closed
FROM:	<hornik@ci.tuwien.ac.at>
	* cat() is a bit inconsistent:

	...

	[ This is the way S does it! ]

Yes, I know that the current behavior is how S does it.  Still, there
are situations (as e.g. in the code for write.table) where I'd like to
have the different behavior.  Could we have an extra option to cat()
which suppresses a final newline even if sep contains a newline?

* It seems that S allows recycling when subscripting with logicals, but
R does not.  E.g.,

	R> x <- 1:5
	R> x
	[1] 1 2 3 4 5
	R> i <- c(F, T)
	R> x[i]
	Error: invalid subscript type
	R>

In S, this is treated as x[rep(i, length = length(x))].

* It also seems that S does not worry about excluding subscripts which
are out of bounds.  In the above, x[-6] would give x, but in R

	R> x[-6]
	Error: subscript out of bounds

* There is a problem with tapply() in the case where INDEX is a factor
with at least one of its levels not occurring in it.

In this case,
	namelist[[i]] <- levels(index)
gets all levels but
	group <- group + ngroup * (codes(index) - 1)
only those occurring in index, which subsequently causes
	names(ans) <- namelist[[1]]
to fail.

For example,

	R> f <- factor(c("a", "a", "b"), levels = letters[1:3])
	R> f
	[1] a a b
	R> codes(f)
	[1] 1 1 2
	R> levels(f)
	[1] "a" "b" "c"

which gives e.g.

	R> tapply(rep(1, length(f)), f, sum)
	Error: names attribute must be the same length as the vector

One solution is to replace

	namelist[[i]] <- levels(index)

by

	namelist[[i]] <- unique(levels(index)[index])

but perhaps there is something smarter ...

* The `shortest program to produce a segfault' now gives:

	R> t(table(1))
	Error: dimnames: number of dimensions must equal number of names

(See Peter's mail for the consecutive deparse warnings ...)

* Please add

	family.lm <- function (object) { gaussian() }

to the base library.

-k
=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-
r-devel mailing list -- Read http://www.ci.tuwien.ac.at/~hornik/R/R-FAQ.html
Send "info", "help", or "[un]subscribe"
(in the "body", not the subject !)  To: r-devel-request@stat.math.ethz.ch
=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-