[Rd] plot.table() ?

Martin Maechler Martin Maechler <maechler@stat.math.ethz.ch>
Tue, 3 Oct 2000 15:26:35 +0200


I tend to use  table() quite a bit for quick "diagnostics", summary, etc.
I have wished for a more automatic way of plotting these.

One possibility would be something like the following function;
The question is if (something like) the following is worth providing (and then
maintaining...)  at all :

plot.table <- function(x, type = "h", ylim = c(0, max(x)), lwd = 2,
                       xlab = NULL, ylab = deparse(substitute(x)),
                       frame.plot = is.num,
                       ...)
{
    rnk <- length(d <- dim(x))
    if(rnk == 0)
	stop("invalid table `x'")
    if(rnk == 1) {
        dn <- dimnames(x)
        nx <- dn[[1]]
        if(is.null(xlab)) xlab <- names(dn)
        if(is.null(xlab)) xlab <- ""
        ow <- options(warn = -1)
        is.num <- !any(is.na(xx <- as.numeric(nx))); options(ow)
        x0 <- if(is.num) xx else seq(x)
	plot(x0, unclass(x), type = type, 
             ylim = ylim, xlab = xlab, ylab = ylab, frame.plot = frame.plot,
             lwd = lwd, ..., xaxt = "n")
        axis(1, at = x0, labels = nx)
    } else
	mosaicplot(x, ...)
}

------

Note that I have `optimized' it mainly for 1-D tables, but it also a way to
make the mosaicplots more known..

Also,
     plot(table(ff))  
is quite similar to 
     plot(ff)
when `ff' is a factor (the latter using barplot).

However,    plot(table(ff, f2))  is different and sometimes more
useful than       plot(ff, f2)
compare
	data(state)
	par(mfcol=c(1,2))
	plot(      state.division, state.region)#-> plot.factor
	plot(table(state.division, state.region))#-> plot.table


Also, try things

        plot(table(state.division))

	Poiss.tab <- table(N = rpois(200, lam= 5)); plot(Poiss.tab)
-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-.-
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
_._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._