R-alpha: Re: Pretest Version + Notes --- write.table

Martin Maechler Martin Maechler <maechler@stat.math.ethz.ch>
Thu, 3 Apr 97 09:50:54 +0200


Kurt writes

KH>> * I am also not sure whether one should include the write.table()
KH>> function I posted some time ago.  It seems to be a bad idea to make a
KH>> contrib package out of it (containing only a single function ...).

Yes, I think we should have a good  "write" function for  data.frames.
However, I would go even further and 'vote' for a GENERIC function  'write'
which has methods for
	default	  (including 'matrix'  as long as 'matrix' is not a class)
	data.frame
	....	['ts', ...]

The following is code that I've been using in S-plus for a while and have
adapted to R:
--- Note that it uses something  more primitive than Kurt's write.table.
    The issue really was to be able to "write a data.frame or matrix" such that
    read.table would reproduce it.


write <- function(x, file = "data", ...) UseMethod("write")

write.default <- function (x, file = "data",
			   ncolumns = if (is.character(x)) 1 else 5,
			   append = FALSE, ...)
{
  if(is.matrix(x))
    write.matrix(x, file=file, append= FALSE, ...)
  else
    write0.basic(x, file = file, ncolumns= ncolumns, append = append)
}

write0.basic <- function (x, file, ncolumns, append = FALSE)
  cat(x, file = file, sep = c(rep(" ", ncolumns - 1), "\n"), append = append)

write.data.frame <- function(x, file = "data", rownames = TRUE)
{
  ## Purpose: Method to 'write(.)' such as to read back using  read.table(.)
  ## -------------------------------------------------------------------------
  ## Arguments:       x : data frame;			file : file name
  ##            rownames: if T, also write row names
  ## -------------------------------------------------------------------------
  ## Author: Martin Maechler <maechler@stat.math.ethz.ch>,  1992
  ## -------------------------------------------------------------------------
  ##-- NOT for "parametrized" data.frames; just ``simple'' matrix look-a-likes
  ##-- NOTE: read.table(file) may still give different data.frame --
  ##-- ~~~~  	        (namely,e.g., when some names contained padding blanks)
  ##-- 	    But the "new" names may actually be better .. (!) ..
  ## EXAMPLE:
  ##   data(women); write(women, file= "women.dat")
  ##   wm <- read.table("women.dat")) 
  ##   all.equal(wm, women) ##> TRUE
  if(!is.data.frame(x)) { #-- can only happen when called explicitely
    warning("'x' is not a data.frame; coercing it to one ...")
    x <- data.frame(x)
  }
  cat( names(x), "\n", file = file, append = FALSE)
  write0.basic(unclass(t(cbind(if(rownames)row.names(x), as.matrix(x)))),
	       ncolumns = rownames + ncol(x), file= file, append= TRUE)
}

write.matrix     <- function(x, file = "data", rownames = TRUE)
  write(data.frame(as.matrix(x)), file=file, rownames=rownames)

=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-
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
=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-