[Rd] plot.table() ?

Kurt Hornik Kurt.Hornik@ci.tuwien.ac.at
Tue, 3 Oct 2000 16:17:07 +0200 (CEST)


>>>>> Martin Maechler writes:

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

In general I like the idea of having a plot method for contingency
tables.

One basic question is whether we feel comfortable enough with the
"table" class that was gradually introduced.  But in any case, xtabs()
assigns class c("xtabs", "table") which should be good enough.

I am not sure how much effort we want to put into this, but here are
some remarks.  I think the Poiss.tab example looks nice, but I am not
happy with the output of plot(table(state.division)) [not that I am
happy with calling barplot() directly in this case].  I would prefer
having ALL names as labels (perhaps rotated 45 degrees).  I am also not
sure about the bars in plot.table(), they look a bit tiny, no?

Re Mosaic plots, very nice idea, but e.g. the result of
  plot(table(state.division, state.region))
looks terrible.  I think this could be very confusing to plains users.
Hmm, how could we improve this?

-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
_._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._._