A set of patches for R-0.50-a1 is now available as
	ftp://stat.auckland.ac.nz/pub/R/R-0.50-a1.patch1.gz
The patches mainly fix problems reported since R-0.50-a1 but some
older problems are also fixed.
Here is the list of changes.
	Ross
 o  Many subsetting and mutation problems with the new "expression"
type
    have now been fixed.
 o  When ask=T is set in par() the user is instructed
	"Press <Return> for next plot:"
    rather than asked
	"Next Plot?"
 o  The infinite recursion observed by in Kurt Hornik in:
	R> test2
	function (x) 
	{
		attr(x, "call") <- sys.call()
		x
	}
	R> test2(x)
	Error: stack overflow
    has been cured.  There may be one or two more of these.  All the
    xxxx<- functions should be checked.
 o  Patches from Benjamin Bolker to cure some line type problems has
    been applied.
 o  Fixed the t(table(0)) problem (1-d arrays not quite handled right).
 o  Changed naming back so that pow_dd etc are available.
 o  Patches to barplot and text from Kurt Hornik.
 o  When x was a data frame,
	mode(x) <- "character"
	x
    caused a crash.  This was because a class of "data.frame"
    was being attached to a character vector.  Now only lists
    can become data frames.
 o  There is now a -gdb option to the R front end as well as -xxgdb.
 o  Documentation of NChisquare fixed.
 o  Definition of S_alloc fixed.
 o  Changed the names of seeds_in and seeds_out to seed_in and
    seed_out as per Kurt's request.
 o  "unlist(c(2))" fixed.
 o  "data.frame(x=2)" fixed.
 o  Bug in do_title fixed.
 o  Scoping for subset methods by forcing an eval of the args on
    entry fixed (bug reported by Patric Lindsay).
 o  subsetting of data frames fixed .
 o  Misc problems in Rdoc.sty reported by Kurt Hornik fixed.
 
 o  Permissions in the data subdir for quakes and sunspots fixed.
 o  Segfault in dimnames mutation
	R> x <- 1:5
	R> dimnames(x)[1,2] <- NULL
    fixed.
 o  It was observed that
	> D(expression(z * (log(z) /z)), "z")
    returns
	(log(z)/z) + z * (1/z/z - log(z)/z^2)
    This is exactly what S-Pus produces.
 o  Added the option -B 8192 to m4 in the etc/doc2* files to keep
    m4 happy.
 o  New functions "as.ordered", "data.class" and
"scale" from, Kurt
    Hornik added.
=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-
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
=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-
Ross Ihaka <ihaka@stat.auckland.ac.nz> writes:> > A set of patches for R-0.50-a1 is now available as > ftp://stat.auckland.ac.nz/pub/R/R-0.50-a1.patch1.gz > The patches mainly fix problems reported since R-0.50-a1 but some > older problems are also fixed...> o It was observed that > > D(expression(z * (log(z) /z)), "z") > returns > (log(z)/z) + z * (1/z/z - log(z)/z^2) > This is exactly what S-Pus produces.Heyheyheyheeeyyy, no need to resort to name calling, next thing, you'll be talking about Windoze, HP-SUX, and Slowlaris! ;)> o New functions "as.ordered", "data.class" and "scale" from, Kurt > Hornik added.[The end] Hmm. The "move .RData before writing to it" fix didn't seem to make it. It's a one-liner (in the most primitive version), and really quite important. Actually, the problem is worse than I thought initially: .RData can get zapped to a zero-length file whenever you destroy the xterm window containing R, not only on system shutdown. This happens on both of my Linux boxes, but it's probably a quite generic race condition. -- O__ ---- Peter Dalgaard Blegdamsvej 3 c/ /'_ --- Dept. of Biostatistics 2200 Cph. N (*) \(*) -- University of Copenhagen Denmark Ph: (+45) 35327918 ~~~~~~~~~~ - (p.dalgaard@biostat.ku.dk) FAX: (+45) 35327907 =-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=- 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 =-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-
Martin Maechler
1997-Aug-05  10:44 UTC
R-alpha: Version 0.50-a1 patches -- New and old bugs..
Thank you !
~~~~~~~~~~~
The new patches
	 (which incidentally make  0.50-a1 into  0.50-a2
	  IF you run ./configure)
really do quite a few good things.
A few comments.
1) I had to do the following to make things compile and link properly
   in	appl/cpoly.c :  line  42 : OUT-commented  (pow_di) 
   otherwise compiler barfed about redefined  pow_di	[Solaris 2.5, Sun cc]
2) In order for 'legend' and 'barplot' to work I had to edit
	src/library/base/funs/legend: 
   Last line: replace 'text=' by 'labels='  [reflect change of
text(...)]
NOTE: After applying the patch, I recommend the following
    make clean
    configure
    make
    make install
    make tests install-latex install-help install-html
---------------------
Further notes:
3) Whereas  unlist(1), unlist(c(2)), etc. work,
   the two unlist problems that Kurt reported about,
   especially
    l.ex <- list(a = list(1:5, LETTERS[1:5]), b = "Z", c = NA)
    unlist(l.ex) #-- still in 0.50-a2
    ##- INTERNAL ERROR: ans_nnames = 10    ans_length = 12
    ##- Error: incorrect names vector length
 still exist. {Nobody claimed otherwise}
4) The parser problem reported by Patrick Lindsey remains :
  ##- From: Patrick Lindsey <plindsey@luc.ac.be>
  ##- Date: Tue, 29 Jul 1997 11:28:50 +0200 (MET DST)
  ##- To: r-devel@stat.math.ethz.ch (R list)
  ##- Subject: R-alpha: Bugs in R-0.50-a1.
  ##-
  ##- Problems in R but not in S:
  ##- ---------------------------
  ##- 2) Problem with the parser: When a function contains a condition
  ##- between brackets the closing bracket must be adjacent to the last item
  ##- in R but not in S. Here is an example:
  ##- 	S> new <- function (x,y,z,k) {
  ##- 	S+ message <- list(x,y,a=if(z) k
  ##- 	S+ )
  ##- 	S+ message
  ##- 	S+ }
  ##- 	S>
  ##- 	---
  ##- 	R> new <- function (x,y,z,k) {
  ##- 	R+ message <- list(x,y,a=if(z) k
  ##- 	R+ )
  ##- 	)
  ##- 	^
  ##- 	Error: syntax error
  ##- 	R>
  ##- This occurs in R-0.49 and in R-0.50-a1, R-0.50-a2
  new <- function (x,y,z,k) {
    message <- list(x,y, a=if(z) k
		    )
  }
---------------------------------------------------------------------------
I think I found one  NEW bug  (a1 -> a2):
		     ======  	options(digits = ...) fails to work AT ALL in a 'local
environment'
which makes even my  tst2()  function 'fail' :
  
 p0 <- (0:2)/1000 ; p <- p0 + 1e-10
 p
 ## Fails in 0.50-a2, (NOT in 0.50-a1, I think):
 for(d in 1:20) { options(digits=d); cat(d,": ", p,";\t",p0,
"  ");print(p)}
 options(digits=7)
 ## Now,the print(.) at least works:
 for(d in 1:20) { options(digits=d); cat(d,": ", p,";",p0,
"  ");print(p,dig=d)}
 ##-- The following does not work as it should in  R (0.50-a1, maybe earlier)
 tst <- function(x=pi, dig =3) {.Options$digits <- as.integer(dig);
print(x);x}
 tst()
 tst(dig = 12)
 ##-- This should do the same; works as expected in S & R-0.50-a1, NOT in
-a2:
 tst2 <- function(x=pi, dig =3) {
   oo <- options(digits=dig); on.exit(options(oo)); print(x);x}
 tst2()
 tst2(dig = 12)
=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-
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
=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-
>>>>> Ross Ihaka writes:> A set of patches for R-0.50-a1 is now available as > ftp://stat.auckland.ac.nz/pub/R/R-0.50-a1.patch1.gz > The patches mainly fix problems reported since R-0.50-a1 but some > older problems are also fixed.> ...> o New functions "as.ordered", "data.class" and "scale" from, Kurt > Hornik added.Almost. `scale' seems to be missing ... -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 =-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-